/[MITgcm]/MITgcm/pkg/icefront/icefront_thermodynamics.F
ViewVC logotype

Annotation of /MITgcm/pkg/icefront/icefront_thermodynamics.F

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


Revision 1.3 - (hide annotations) (download)
Mon Jan 25 22:37:19 2010 UTC (14 years, 4 months ago) by dimitri
Branch: MAIN
CVS Tags: checkpoint62b
Changes since 1.2: +9 -9 lines
adding some 3D diagnostics

1 dimitri 1.3 C $Header: /u/gcmpack/MITgcm/pkg/icefront/icefront_thermodynamics.F,v 1.2 2010/01/22 00:51:54 dimitri Exp $
2 dimitri 1.1 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,Kp1,bi,bj :: loop counters
48     C tLoc, sLoc, pLoc :: local in-situ temperature, salinity, pressure
49     C theta/saltFreeze :: temperature and salinity of water at the
50     C ice-ocean interface (at the freezing point)
51     C freshWaterFlux :: local variable for fresh water melt flux due to
52     C melting in kg/m^2/s (negative density x melt rate)
53     C convertFW2SaltLoc:: local copy of convertFW2Salt
54     C cFac :: 1 for conservative form, 0, otherwise
55     C auxiliary variables and abbreviations:
56     C a0, a1, a2, b, c0
57     C eps1, eps2, eps3, eps4, eps5, eps6, eps7
58     C aqe, bqe, cqe, discrim, recip_aqe
59     C drKp1, recip_drLoc
60     INTEGER I,J,K,Kp1
61     INTEGER bi,bj
62     _RL tLoc(1:sNx,1:sNy)
63     _RL sLoc(1:sNx,1:sNy)
64     _RL pLoc(1:sNx,1:sNy)
65     _RL thetaFreeze, saltFreeze
66     _RL freshWaterFlux, convertFW2SaltLoc
67     _RL a0, a1, a2, b, c0
68     _RL eps1, eps2, eps3, eps4, eps5, eps6, eps7
69     _RL cFac, rFac
70     _RL aqe, bqe, cqe, discrim, recip_aqe
71     _RL drKp1, recip_drLoc
72     _RL tmpFac
73    
74     _RL SW_TEMP
75     EXTERNAL SW_TEMP
76    
77     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
78    
79     C are we doing the conservative form of Jenkins et al. (2001)?
80     cFac = 0. _d 0
81     IF ( ICEFRONTconserve ) cFac = 1. _d 0
82     C with "real fresh water flux" (affecting ETAN), there is more to modify
83     rFac = 1. _d 0
84     IF ( ICEFRONTconserve .AND. useRealFreshWaterFlux ) rFac = 0. _d 0
85     C linear dependence of freezing point on salinity
86     a0 = -0.0575 _d 0
87     a1 = 0.0 _d -0
88     a2 = 0.0 _d -0
89     c0 = 0.0901 _d 0
90     b = -7.61 _d -4
91     #ifdef ALLOW_ISOMIP_TD
92     IF ( useISOMIPTD ) THEN
93     C non-linear dependence of freezing point on salinity
94     a0 = -0.0575 _d 0
95     a1 = 1.710523 _d -3
96     a2 = -2.154996 _d -4
97     b = -7.53 _d -4
98     c0 = 0. _d 0
99     ENDIF
100     convertFW2SaltLoc = convertFW2Salt
101     C hardcoding this value here is OK because it only applies to ISOMIP
102     C where this value is part of the protocol
103     IF ( convertFW2SaltLoc .EQ. -1. ) convertFW2SaltLoc = 33.4 _d 0
104     #endif /* ALLOW_ISOMIP_TD */
105    
106     DO bj = myByLo(myThid), myByHi(myThid)
107     DO bi = myBxLo(myThid), myBxHi(myThid)
108     DO J = 1-Oly,sNy+Oly
109     DO I = 1-Olx,sNx+Olx
110     icefrontHeatFlux (I,J,bi,bj) = 0. _d 0
111     icefrontFreshWaterFlux(I,J,bi,bj) = 0. _d 0
112     icefrontForcingT (I,J,bi,bj) = 0. _d 0
113     icefrontForcingS (I,J,bi,bj) = 0. _d 0
114     ENDDO
115     ENDDO
116     DO J = 1, sNy
117     DO I = 1, sNx
118     C-- make local copies of temperature, salinity and depth (pressure)
119     C-- underneath the ice
120 dimitri 1.2 K = 1
121 dimitri 1.1 pLoc(I,J) = ABS(R_icefront(I,J,bi,bj))
122     tLoc(I,J) = theta(I,J,K,bi,bj)
123     sLoc(I,J) = MAX(salt(I,J,K,bi,bj), 0. _d 0)
124     ENDDO
125     ENDDO
126    
127     C-- turn potential temperature into in-situ temperature relative
128     C-- to the surface
129     DO J = 1, sNy
130     DO I = 1, sNx
131     tLoc(I,J) = SW_TEMP(sLoc(I,J),tLoc(I,J),pLoc(I,J),0.D0)
132     ENDDO
133     ENDDO
134    
135     #ifdef ALLOW_ISOMIP_TD
136     IF ( useISOMIPTD ) THEN
137     DO J = 1, sNy
138     DO I = 1, sNx
139 dimitri 1.2 K = 1
140 dimitri 1.1 IF ( K .NE. 0 .AND. pLoc(I,J) .GT. 0. _d 0 ) THEN
141     C-- Calculate freezing temperature as a function of salinity and pressure
142     thetaFreeze =
143     & sLoc(I,J) * ( a0 + a1*sqrt(sLoc(I,J)) + a2*sLoc(I,J) )
144     & + b*pLoc(I,J) + c0
145     C-- Calculate the upward heat and fresh water fluxes
146     icefrontHeatFlux(I,J,bi,bj) = maskC(I,J,K,bi,bj) *
147     & ICEFRONTheatTransCoeff * ( tLoc(I,J) - thetaFreeze )
148     & *HeatCapacity_Cp*rUnit2mass
149     C upward heat flux into the shelf-ice implies basal melting,
150     C thus a downward (negative upward) fresh water flux (as a mass flux),
151     C and vice versa
152     icefrontFreshWaterFlux(I,J,bi,bj) =
153     & - icefrontHeatFlux(I,J,bi,bj)
154     & *recip_ICEFRONTlatentHeat
155     C-- compute surface tendencies
156     icefrontForcingT(i,j,bi,bj) =
157     & - icefrontHeatFlux(I,J,bi,bj)
158     & *recip_Cp*mass2rUnit
159     & - cFac * icefrontFreshWaterFlux(I,J,bi,bj)*mass2rUnit
160     & * ( thetaFreeze - tLoc(I,J) )
161     icefrontForcingS(i,j,bi,bj) =
162     & icefrontFreshWaterFlux(I,J,bi,bj) * mass2rUnit
163     & * ( cFac*sLoc(I,J) + (1. _d 0-cFac)*convertFW2SaltLoc )
164     C-- stress at the ice/water interface is computed in separate
165     C routines that are called from mom_fluxform/mom_vecinv
166     ELSE
167     icefrontHeatFlux (I,J,bi,bj) = 0. _d 0
168     icefrontFreshWaterFlux(I,J,bi,bj) = 0. _d 0
169     icefrontForcingT (I,J,bi,bj) = 0. _d 0
170     icefrontForcingS (I,J,bi,bj) = 0. _d 0
171     ENDIF
172     ENDDO
173     ENDDO
174     ELSE
175     #else
176     IF ( .TRUE. ) THEN
177     #endif /* ALLOW_ISOMIP_TD */
178     C use BRIOS thermodynamics, following Hellmers PhD thesis:
179     C Hellmer, H., 1989, A two-dimensional model for the thermohaline
180     C circulation under an ice shelf, Reports on Polar Research, No. 60
181     C (in German).
182    
183     C a few abbreviations
184     eps1 = rUnit2mass*HeatCapacity_Cp*ICEFRONTheatTransCoeff
185     eps2 = rUnit2mass*ICEFRONTlatentHeat*ICEFRONTsaltTransCoeff
186     eps5 = rUnit2mass*HeatCapacity_Cp*ICEFRONTsaltTransCoeff
187    
188     DO J = 1, sNy
189     DO I = 1, sNx
190 dimitri 1.2 K = 1
191 dimitri 1.1 IF ( K .NE. 0 .AND. pLoc(I,J) .GT. 0. _d 0 ) THEN
192     C solve quadratic equation to get salinity at icefront-ocean interface
193     C note: this part of the code is not very intuitive as it involves
194     C many arbitrary abbreviations that were introduced to derive the
195     C correct form of the quadratic equation for salinity. The abbreviations
196     C only make sense in connection with my notes on this (M.Losch)
197     eps3 = rhoIcefront*ICEFRONTheatCapacity_Cp
198     & * ICEFRONTkappa/pLoc(I,J)
199     eps4 = b*pLoc(I,J) + c0
200     eps6 = eps4 - tLoc(I,J)
201     eps7 = eps4 - ICEFRONTthetaSurface
202     aqe = a0 *(eps1+eps3)
203     recip_aqe = 0. _d 0
204     IF ( aqe .NE. 0. _d 0 ) recip_aqe = 0.5 _d 0/aqe
205     bqe = eps1*eps6 + eps3*eps7 - eps2
206     cqe = eps2*sLoc(I,J)
207     discrim = bqe*bqe - 4. _d 0*aqe*cqe
208     #undef ALLOW_ICEFRONT_DEBUG
209     #ifdef ALLOW_ICEFRONT_DEBUG
210     IF ( discrim .LT. 0. _d 0 ) THEN
211     print *, 'ml-icefront: discrim = ', discrim,aqe,bqe,cqe
212     print *, 'ml-icefront: pLoc = ', pLoc(I,J)
213     print *, 'ml-icefront: tLoc = ', tLoc(I,J)
214     print *, 'ml-icefront: sLoc = ', sLoc(I,J)
215     print *, 'ml-icefront: tsurface= ',
216     & ICEFRONTthetaSurface
217     print *, 'ml-icefront: eps1 = ', eps1
218     print *, 'ml-icefront: eps2 = ', eps2
219     print *, 'ml-icefront: eps3 = ', eps3
220     print *, 'ml-icefront: eps4 = ', eps4
221     print *, 'ml-icefront: eps5 = ', eps5
222     print *, 'ml-icefront: eps6 = ', eps6
223     print *, 'ml-icefront: eps7 = ', eps7
224     print *, 'ml-icefront: rU2mass = ', rUnit2mass
225     print *, 'ml-icefront: rhoIce = ', rhoIcefront
226     print *, 'ml-icefront: cFac = ', cFac
227     print *, 'ml-icefront: Cp_W = ', HeatCapacity_Cp
228     print *, 'ml-icefront: Cp_I = ',
229     & ICEFRONTHeatCapacity_Cp
230     print *, 'ml-icefront: gammaT = ',
231     & ICEFRONTheatTransCoeff
232     print *, 'ml-icefront: gammaS = ',
233     & ICEFRONTsaltTransCoeff
234     print *, 'ml-icefront: lat.heat= ',
235     & ICEFRONTlatentHeat
236     STOP 'ABNORMAL END in S/R ICEFRONT_THERMODYNAMICS'
237     ENDIF
238     #endif /* ALLOW_ICEFRONT_DEBUG */
239     saltFreeze = (- bqe - SQRT(discrim))*recip_aqe
240     IF ( saltFreeze .LT. 0. _d 0 )
241     & saltFreeze = (- bqe + SQRT(discrim))*recip_aqe
242     thetaFreeze = a0*saltFreeze + eps4
243     C-- upward fresh water flux due to melting (in kg/m^2/s)
244     freshWaterFlux = rUnit2mass*ICEFRONTsaltTransCoeff
245     & * ( saltFreeze - sLoc(I,J) ) / saltFreeze
246     C-- Calculate the upward heat and fresh water fluxes;
247     C-- MITgcm sign conventions: downward (negative) fresh water flux
248     C-- implies melting and due to upward (positive) heat flux
249     icefrontHeatFlux(I,J,bi,bj) =
250     & ( eps3*( thetaFreeze - ICEFRONTthetaSurface )
251     & - cFac*freshWaterFlux*( ICEFRONTlatentHeat
252     & - HeatCapacity_Cp*( thetaFreeze - rFac*tLoc(I,J) ) )
253     & )
254     icefrontFreshWaterFlux(I,J,bi,bj) = freshWaterFlux
255     C-- compute surface tendencies
256     icefrontForcingT(i,j,bi,bj) =
257     & ( ICEFRONTheatTransCoeff
258     & - cFac*icefrontFreshWaterFlux(I,J,bi,bj)*mass2rUnit )
259     & * ( thetaFreeze - tLoc(I,J) )
260     icefrontForcingS(i,j,bi,bj) =
261     & ( ICEFRONTsaltTransCoeff
262     & - cFac*icefrontFreshWaterFlux(I,J,bi,bj)*mass2rUnit )
263     & * ( saltFreeze - sLoc(I,J) )
264     ELSE
265     icefrontHeatFlux (I,J,bi,bj) = 0. _d 0
266     icefrontFreshWaterFlux(I,J,bi,bj) = 0. _d 0
267     icefrontForcingT (I,J,bi,bj) = 0. _d 0
268     icefrontForcingS (I,J,bi,bj) = 0. _d 0
269     ENDIF
270     ENDDO
271     ENDDO
272     ENDIF
273     C endif (not) useISOMIPTD
274     ENDDO
275     ENDDO
276    
277     #ifdef ALLOW_DIAGNOSTICS
278     IF ( useDiagnostics ) THEN
279 dimitri 1.3 CALL DIAGNOSTICS_FILL_RS(icefrontFreshWaterFlux,'ICFfwFlx',
280     & 0,Nr,0,1,1,myThid)
281     CALL DIAGNOSTICS_FILL_RS(icefrontHeatFlux, 'ICFhtFlx',
282     & 0,Nr,0,1,1,myThid)
283     C SHIForcT (Ice front forcing for theta [W/m2], >0 increases theta)
284 dimitri 1.1 tmpFac = HeatCapacity_Cp*rUnit2mass
285     CALL DIAGNOSTICS_SCALE_FILL(icefrontForcingT,tmpFac,1,
286 dimitri 1.3 & 'ICFForcT',0, Nr,0,1,1,myThid)
287     C SHIForcS (Ice front forcing for salt [g/m2/s], >0 increases salt)
288 dimitri 1.1 tmpFac = rUnit2mass
289     CALL DIAGNOSTICS_SCALE_FILL(icefrontForcingS,tmpFac,1,
290 dimitri 1.3 & 'ICFForcS',0, Nr,0,1,1,myThid)
291 dimitri 1.1 ENDIF
292     #endif /* ALLOW_DIAGNOSTICS */
293    
294     #endif /* ALLOW_ICEFRONT */
295     RETURN
296     END

  ViewVC Help
Powered by ViewVC 1.1.22