/[MITgcm]/MITgcm_contrib/icefront/3D_example/code/icefront_thermodynamics.F
ViewVC logotype

Annotation of /MITgcm_contrib/icefront/3D_example/code/icefront_thermodynamics.F

Parent Directory Parent Directory | Revision Log Revision Log | View Revision Graph Revision Graph


Revision 1.1 - (hide annotations) (download)
Fri Jan 24 23:03:22 2014 UTC (11 years, 5 months ago) by yunx
Branch: MAIN
CVS Tags: HEAD
Checking in an example of 3D tidewater glacier configuration, with subglacial
freshwater plume resoved at 1-m resolution.

1 yunx 1.1 C $Header: /u/gcmpack/MITgcm/pkg/icefront/icefront_thermodynamics.F,v 1.8 2010/04/22 18:24:44 yunx Exp $
2     C $Name: $
3    
4     #include "ICEFRONT_OPTIONS.h"
5    
6     CBOP
7     C !ROUTINE: ICEFRONT_THERMODYNAMICS
8     C !INTERFACE:
9     SUBROUTINE ICEFRONT_THERMODYNAMICS(
10     I myTime, myIter, myThid )
11     C !DESCRIPTION: \bv
12     C *=============================================================*
13     C | S/R ICEFRONT_THERMODYNAMICS
14     C | o shelf-ice main routine.
15     C | compute temperature and (virtual) salt flux at the
16     C | shelf-ice ocean interface
17     C |
18     C | stresses at the ice/water interface are computed in separate
19     C | routines that are called from mom_fluxform/mom_vecinv
20     C *=============================================================*
21    
22     C !USES:
23     IMPLICIT NONE
24    
25     C === Global variables ===
26     #include "SIZE.h"
27     #include "EEPARAMS.h"
28     #include "PARAMS.h"
29     #include "GRID.h"
30     #include "DYNVARS.h"
31     #include "FFIELDS.h"
32     #include "ICEFRONT.h"
33    
34     C !INPUT/OUTPUT PARAMETERS:
35     C === Routine arguments ===
36     C myIter :: iteration counter for this thread
37     C myTime :: time counter for this thread
38     C myThid :: thread number for this instance of the routine.
39     _RL myTime
40     INTEGER myIter
41     INTEGER myThid
42     CEOP
43    
44     #ifdef ALLOW_ICEFRONT
45     C !LOCAL VARIABLES :
46     C === Local variables ===
47     C I,J,K,bi,bj :: loop counters
48     C tLoc, sLoc, pLoc :: local in-situ temperature, salinity, pressure
49     C thetaICE :: averaged temperature of glacier interior
50     C theta/saltFreeze :: temperature and salinity of water at the
51     C ice-ocean interface (at the freezing point)
52     C FreshWaterFlux :: fresh water flux due to freezing or melting of ice
53     C front in kg/m^2/s (positive increases ocean salinity)
54     C HeatFlux :: ice front heat flux in W/m^2
55     C (positive decreases ocean temperature)
56     C auxiliary variables and abbreviations:
57     C a0, b, c0
58     C eps1, eps2, eps3, eps4, eps5, eps6, eps7
59     C aqe, bqe, cqe, discrim, recip_aqe
60     INTEGER I,J,K
61     INTEGER bi,bj
62     _RL tLoc, sLoc, pLoc
63     _RL uLoc, vLoc, wLoc, speedLoc
64     _RL thetaICE
65     _RL thetaFreeze, saltFreeze
66     _RS FreshWaterFlux( 1:sNx, 1:sNy )
67     _RS HeatFlux ( 1:sNx, 1:sNy )
68     _RS ICEFRONTheatTransCoeff ( 1:sNx, 1:sNy )
69     _RS ICEFRONTsaltTransCoeff ( 1:sNx, 1:sNy )
70     _RL a0, b, c0
71     _RL eps1, eps2, eps3, eps4, eps5, eps6, eps7
72     _RL aqe, bqe, cqe, discrim, recip_aqe
73    
74    
75     _RL SW_TEMP
76     EXTERNAL SW_TEMP
77    
78     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
79    
80     #ifdef ALLOW_SUBGLACIAL_RUNOFF
81     IF ( SGrunofffile .NE. ' ' ) THEN
82     CALL SGRUNOFF_READ(myTime, myIter, myThid)
83     ENDIF
84     #endif /* ALLOW_SUBGLACIAL_RUNOFF*/
85    
86     C Linear dependence of freezing point on salinity.
87     a0 = -0.0575 _d 0
88     c0 = 0.0901 _d 0
89     b = -7.61 _d -4
90    
91    
92     DO bj = myByLo(myThid), myByHi(myThid)
93     DO bi = myBxLo(myThid), myBxHi(myThid)
94     DO K = 1, Nr
95     DO J = 1, sNy
96     DO I = 1, sNx
97    
98     IF( ICEFRONTlength(I,J,bi,bj) .GT. 0. _d 0
99     & .AND. K .LE. K_icefront(I,J,bi,bj) ) THEN
100    
101     C Make local copies of velocity, temperature, salinity and depth (pressure).
102     uLoc = 0.5*(uVel(I,J,K,bi,bj) +uVel(I+1,J,K,bi,bj))
103     vLoc = 0.5*(vVel(I,J,K,bi,bj) +vVel(I,J+1,K,bi,bj))
104     wLoc = 0.5*(wVel(I,J,K,bi,bj) +wVel(I,J,K+1,bi,bj))
105     speedLoc = SQRT(uLoc*uLoc + vLoc*vLoc + wLoc*wLoc)
106    
107     C A few abbreviations.
108     C IF (myTime .GT. 600) THEN
109     ICEFRONTheatTransCoeff(I,J) = 1.1 _d -03
110     C & *abs(wVEL(I,J,K,bi,bj))
111     & *abs(speedLoc)
112     & +1.0 _d -04
113     ICEFRONTsaltTransCoeff(I,J) = 3.1 _d -05
114     C & *abs(wVEL(I,J,K,bi,bj))
115     & *abs(speedLoc)
116     & +5.05 _d -07
117     C ENDIF
118    
119     eps1 = rUnit2mass*HeatCapacity_Cp*ICEFRONTheatTransCoeff(I,J)
120     eps2 = rUnit2mass*ICEFRONTlatentHeat*ICEFRONTsaltTransCoeff(I,J)
121     eps3 = rUnit2mass*ICEFRONTheatCapacity_Cp
122     & *ICEFRONTsaltTransCoeff(I,J)
123     eps5 = mass2rUnit/HeatCapacity_Cp
124     aqe = a0 *(-eps1+eps3)
125     recip_aqe = 0.5 _d 0/aqe
126     C Make local copies of temperature, salinity and depth (pressure).
127     pLoc = ABS(rC(k))
128     tLoc = theta(I,J,K,bi,bj)
129     sLoc = MAX(salt(I,J,K,bi,bj), 0. _d 0)
130    
131     C Turn potential temperature into in-situ temperature.
132     tLoc = SW_TEMP(sLoc,tLoc,pLoc,0.D0)
133    
134     C Get ice temperature. Assume linear ice temperature change from
135     C the surface (ICEFRONTthetaSurface) to the base(0 degree C).
136     IF ( K .EQ. K_icefront(I,J,bi,bj)) THEN
137     pLoc = 0.5*(ABS(R_icefront(I,J,bi,bj))+ABS(rF(K)))
138     ENDIF
139     thetaICE = ICEFRONTthetaSurface*
140     & (R_icefront(I,J,bi,bj)-pLoc)
141     & / R_icefront(I,J,bi,bj)
142    
143     C A few more abbreviations.
144     eps4 = b*pLoc + c0
145     eps6 = eps4 - tLoc
146     eps7 = eps4 - thetaIce
147    
148     C Solve quadratic equation to get salinity at icefront-ocean interface.
149     bqe = - eps1*eps6 -sLoc*a0*eps3 + eps3*eps7 + eps2
150     cqe = -(eps2+eps3*eps7)*sLoc
151     discrim = bqe*bqe - 4. _d 0*aqe*cqe
152     saltFreeze = (- bqe - SQRT(discrim))*recip_aqe
153     IF ( saltFreeze .LT. 0. _d 0 )
154     & saltFreeze = (- bqe + SQRT(discrim))*recip_aqe
155     thetaFreeze = a0*saltFreeze + eps4
156    
157     C-- Calculate the outward (leaving the ocean) heat (W/m^2)
158     C and freshwater (kg/m^2/s).
159     C Sign convention: inward (negative) fresh water flux implies glacier
160     C melting due to outward (positive) heat flux.
161     FreshWaterFlux(I,J) = maskC(I,J,K,bi,bj) *
162     & eps1 * ( thetaFreeze - tLoc ) /
163     & (ICEFRONTlatentHeat + ICEFRONTheatCapacity_cp*
164     & (thetaFreeze - thetaIce))
165     HeatFlux(I,J) = maskC(I,J,K,bi,bj) * HeatCapacity_Cp *
166     & ( -rUnit2mass*ICEFRONTheatTransCoeff(I,J) +
167     & FreshWaterFlux(I,J) ) * ( thetaFreeze - tLoc )
168    
169     C Compute tendencies.
170     icefront_TendT(i,j,K,bi,bj) = - HeatFlux(I,J)* eps5
171     icefront_TendS(i,j,K,bi,bj) = FreshWaterFlux(I,J) *
172     & mass2rUnit * sLoc
173    
174     C Scale by icefrontlength, which is the ratio of the horizontal length
175     C of the ice front in each model grid cell divided by the grid cell area.
176     IF (k .LT. k_icefront(i,j,bi,bj)) THEN
177     icefront_TendT(i,j,K,bi,bj) = icefront_TendT(i,j,K,bi,bj)
178     & * ICEFRONTlength(i,j,bi,bj)
179     icefront_TendS(i,j,K,bi,bj) = icefront_TendS(i,j,K,bi,bj)
180     & * ICEFRONTlength(i,j,bi,bj)
181     ELSEIF (k .EQ. k_icefront(i,j,bi,bj)) THEN
182     C At the bottom of the ice shelf there is additional scaling due
183     C to the partial depth of the ice front.
184     icefront_TendT(i,j,K,bi,bj) = icefront_TendT(i,j,K,bi,bj)
185     & * ICEFRONTlength(i,j,bi,bj)
186     & * (ABS(R_icefront(I,J,bi,bj))-ABS(rF(K)))
187     & * recip_drF(K)
188     icefront_TendS(i,j,K,bi,bj) = icefront_TendS(i,j,K,bi,bj)
189     & * ICEFRONTlength(i,j,bi,bj)
190     & * (ABS(R_icefront(I,J,bi,bj))-ABS(rF(K)))
191     & * recip_drF(K)
192     ENDIF
193    
194     ELSE ! K .LE. K_icefront
195    
196     HeatFlux (I,J) = 0. _d 0
197     FreshWaterFlux(I,J) = 0. _d 0
198    
199     ENDIF ! K .LE. K_icefront
200    
201     ENDDO ! I = 1, sNx
202     ENDDO ! J = 1, sNy
203    
204     #ifdef ALLOW_DIAGNOSTICS
205     IF ( useDiagnostics ) THEN
206     CALL DIAGNOSTICS_FILL_RS(FreshWaterFlux,'ICFfwFlx',
207     & k,1,3,bi,bj,myThid)
208     CALL DIAGNOSTICS_FILL_RS(HeatFlux, 'ICFhtFlx',
209     & k,1,3,bi,bj,myThid)
210     ENDIF
211     #endif /* ALLOW_DIAGNOSTICS */
212    
213     ENDDO ! K = 1, Nr
214     ENDDO ! bi = myBxLo, myBxHi
215     ENDDO ! bj = myByLo, myByHi
216    
217     #endif /* ALLOW_ICEFRONT */
218     RETURN
219     END

  ViewVC Help
Powered by ViewVC 1.1.22