/[MITgcm]/MITgcm/pkg/shelfice/shelfice_thermodynamics.F
ViewVC logotype

Contents of /MITgcm/pkg/shelfice/shelfice_thermodynamics.F

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


Revision 1.18 - (show annotations) (download)
Thu Sep 3 20:50:09 2009 UTC (14 years, 8 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint62, checkpoint61v, checkpoint61w, checkpoint61z, checkpoint61x, checkpoint61y
Changes since 1.17: +38 -38 lines
uses the right type of S/R for diagnostic filling

1 C $Header: /u/gcmpack/MITgcm/pkg/shelfice/shelfice_thermodynamics.F,v 1.17 2009/04/30 13:42:30 dimitri Exp $
2 C $Name: $
3
4 #include "SHELFICE_OPTIONS.h"
5
6 CBOP
7 C !ROUTINE: SHELFICE_THERMODYNAMICS
8 C !INTERFACE:
9 SUBROUTINE SHELFICE_THERMODYNAMICS(
10 I myTime, myIter, myThid )
11 C !DESCRIPTION: \bv
12 C *=============================================================*
13 C | S/R SHELFICE_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 "SHELFICE.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_SHELFICE
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 ( SHELFICEconserve ) 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 ( SHELFICEconserve .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 shelfIceHeatFlux (I,J,bi,bj) = 0. _d 0
111 shelfIceFreshWaterFlux(I,J,bi,bj) = 0. _d 0
112 shelficeForcingT (I,J,bi,bj) = 0. _d 0
113 shelficeForcingS (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 K = MAX(1,kTopC(I,J,bi,bj))
121 pLoc(I,J) = ABS(R_shelfIce(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 IF ( SHELFICEBoundaryLayer ) THEN
127 C-- average over boundary layer width
128 DO J = 1, sNy
129 DO I = 1, sNx
130 K = kTopC(I,J,bi,bj)
131 IF ( K .NE. 0 .AND. K .LT. Nr ) THEN
132 Kp1 = MIN(Nr,K+1)
133 C-- overlap into lower cell
134 drKp1 = drF(K)*( 1. _d 0 - _hFacC(I,J,K,bi,bj) )
135 C-- lower cell may not be as thick as required
136 drKp1 = MIN( drKp1, drF(Kp1) * _hFacC(I,J,Kp1,bi,bj) )
137 recip_drLoc = 1. _d 0 /
138 & ( drF(K)*_hFacC(I,J,K,bi,bj) + drKp1 )
139 tLoc(I,J) = ( tLoc(I,J) * drF(K)*_hFacC(I,J,K,bi,bj)
140 & + theta(I,J,Kp1,bi,bj) *drKp1 )
141 & * recip_drLoc
142 sLoc(I,J) = ( sLoc(I,J) * drF(K)*_hFacC(I,J,K,bi,bj)
143 & + MAX(salt(I,J,Kp1,bi,bj), 0. _d 0) * drKp1 )
144 & * recip_drLoc
145 ENDIF
146 ENDDO
147 ENDDO
148 ENDIF
149
150 C-- turn potential temperature into in-situ temperature relative
151 C-- to the surface
152 DO J = 1, sNy
153 DO I = 1, sNx
154 tLoc(I,J) = SW_TEMP(sLoc(I,J),tLoc(I,J),pLoc(I,J),0.D0)
155 ENDDO
156 ENDDO
157
158 #ifdef ALLOW_ISOMIP_TD
159 IF ( useISOMIPTD ) THEN
160 DO J = 1, sNy
161 DO I = 1, sNx
162 K = kTopC(I,J,bi,bj)
163 IF ( K .NE. 0 .AND. pLoc(I,J) .GT. 0. _d 0 ) THEN
164 C-- Calculate freezing temperature as a function of salinity and pressure
165 thetaFreeze =
166 & sLoc(I,J) * ( a0 + a1*sqrt(sLoc(I,J)) + a2*sLoc(I,J) )
167 & + b*pLoc(I,J) + c0
168 C-- Calculate the upward heat and fresh water fluxes
169 shelfIceHeatFlux(I,J,bi,bj) = maskC(I,J,K,bi,bj) *
170 & SHELFICEheatTransCoeff * ( tLoc(I,J) - thetaFreeze )
171 & *HeatCapacity_Cp*rUnit2mass
172 C upward heat flux into the shelf-ice implies basal melting,
173 C thus a downward (negative upward) fresh water flux (as a mass flux),
174 C and vice versa
175 shelfIceFreshWaterFlux(I,J,bi,bj) =
176 & - shelfIceHeatFlux(I,J,bi,bj)
177 & *recip_SHELFICElatentHeat
178 C-- compute surface tendencies
179 shelficeForcingT(i,j,bi,bj) =
180 & - shelfIceHeatFlux(I,J,bi,bj)
181 & *recip_Cp*mass2rUnit
182 & - cFac * shelfIceFreshWaterFlux(I,J,bi,bj)*mass2rUnit
183 & * ( thetaFreeze - tLoc(I,J) )
184 shelficeForcingS(i,j,bi,bj) =
185 & shelfIceFreshWaterFlux(I,J,bi,bj) * mass2rUnit
186 & * ( cFac*sLoc(I,J) + (1. _d 0-cFac)*convertFW2SaltLoc )
187 C-- stress at the ice/water interface is computed in separate
188 C routines that are called from mom_fluxform/mom_vecinv
189 ELSE
190 shelfIceHeatFlux (I,J,bi,bj) = 0. _d 0
191 shelfIceFreshWaterFlux(I,J,bi,bj) = 0. _d 0
192 shelficeForcingT (I,J,bi,bj) = 0. _d 0
193 shelficeForcingS (I,J,bi,bj) = 0. _d 0
194 ENDIF
195 ENDDO
196 ENDDO
197 ELSE
198 #else
199 IF ( .TRUE. ) THEN
200 #endif /* ALLOW_ISOMIP_TD */
201 C use BRIOS thermodynamics, following Hellmers PhD thesis:
202 C Hellmer, H., 1989, A two-dimensional model for the thermohaline
203 C circulation under an ice shelf, Reports on Polar Research, No. 60
204 C (in German).
205
206 C a few abbreviations
207 eps1 = rUnit2mass*HeatCapacity_Cp*SHELFICEheatTransCoeff
208 eps2 = rUnit2mass*SHELFICElatentHeat*SHELFICEsaltTransCoeff
209 eps5 = rUnit2mass*HeatCapacity_Cp*SHELFICEsaltTransCoeff
210
211 DO J = 1, sNy
212 DO I = 1, sNx
213 K = kTopC(I,J,bi,bj)
214 IF ( K .NE. 0 .AND. pLoc(I,J) .GT. 0. _d 0 ) THEN
215 C solve quadratic equation to get salinity at shelfice-ocean interface
216 C note: this part of the code is not very intuitive as it involves
217 C many arbitrary abbreviations that were introduced to derive the
218 C correct form of the quadratic equation for salinity. The abbreviations
219 C only make sense in connection with my notes on this (M.Losch)
220 eps3 = rhoShelfIce*SHELFICEheatCapacity_Cp
221 & * SHELFICEkappa/pLoc(I,J)
222 eps4 = b*pLoc(I,J) + c0
223 eps6 = eps4 - tLoc(I,J)
224 eps7 = eps4 - SHELFICEthetaSurface
225 aqe = a0 *(eps1+eps3)
226 recip_aqe = 0. _d 0
227 IF ( aqe .NE. 0. _d 0 ) recip_aqe = 0.5 _d 0/aqe
228 bqe = eps1*eps6 + eps3*eps7 - eps2
229 cqe = eps2*sLoc(I,J)
230 discrim = bqe*bqe - 4. _d 0*aqe*cqe
231 #undef ALLOW_SHELFICE_DEBUG
232 #ifdef ALLOW_SHELFICE_DEBUG
233 IF ( discrim .LT. 0. _d 0 ) THEN
234 print *, 'ml-shelfice: discrim = ', discrim,aqe,bqe,cqe
235 print *, 'ml-shelfice: pLoc = ', pLoc(I,J)
236 print *, 'ml-shelfice: tLoc = ', tLoc(I,J)
237 print *, 'ml-shelfice: sLoc = ', sLoc(I,J)
238 print *, 'ml-shelfice: tsurface= ',
239 & SHELFICEthetaSurface
240 print *, 'ml-shelfice: eps1 = ', eps1
241 print *, 'ml-shelfice: eps2 = ', eps2
242 print *, 'ml-shelfice: eps3 = ', eps3
243 print *, 'ml-shelfice: eps4 = ', eps4
244 print *, 'ml-shelfice: eps5 = ', eps5
245 print *, 'ml-shelfice: eps6 = ', eps6
246 print *, 'ml-shelfice: eps7 = ', eps7
247 print *, 'ml-shelfice: rU2mass = ', rUnit2mass
248 print *, 'ml-shelfice: rhoIce = ', rhoShelfIce
249 print *, 'ml-shelfice: cFac = ', cFac
250 print *, 'ml-shelfice: Cp_W = ', HeatCapacity_Cp
251 print *, 'ml-shelfice: Cp_I = ',
252 & SHELFICEHeatCapacity_Cp
253 print *, 'ml-shelfice: gammaT = ',
254 & SHELFICEheatTransCoeff
255 print *, 'ml-shelfice: gammaS = ',
256 & SHELFICEsaltTransCoeff
257 print *, 'ml-shelfice: lat.heat= ',
258 & SHELFICElatentHeat
259 STOP 'ABNORMAL END in S/R SHELFICE_THERMODYNAMICS'
260 ENDIF
261 #endif /* ALLOW_SHELFICE_DEBUG */
262 saltFreeze = (- bqe - SQRT(discrim))*recip_aqe
263 IF ( saltFreeze .LT. 0. _d 0 )
264 & saltFreeze = (- bqe + SQRT(discrim))*recip_aqe
265 thetaFreeze = a0*saltFreeze + eps4
266 C-- upward fresh water flux due to melting (in kg/m^2/s)
267 freshWaterFlux = rUnit2mass*SHELFICEsaltTransCoeff
268 & * ( saltFreeze - sLoc(I,J) ) / saltFreeze
269 C-- Calculate the upward heat and fresh water fluxes;
270 C-- MITgcm sign conventions: downward (negative) fresh water flux
271 C-- implies melting and due to upward (positive) heat flux
272 shelfIceHeatFlux(I,J,bi,bj) =
273 & ( eps3*( thetaFreeze - SHELFICEthetaSurface )
274 & - cFac*freshWaterFlux*( SHELFICElatentHeat
275 & - HeatCapacity_Cp*( thetaFreeze - rFac*tLoc(I,J) ) )
276 & )
277 shelfIceFreshWaterFlux(I,J,bi,bj) = freshWaterFlux
278 C-- compute surface tendencies
279 shelficeForcingT(i,j,bi,bj) =
280 & ( SHELFICEheatTransCoeff
281 & - cFac*shelfIceFreshWaterFlux(I,J,bi,bj)*mass2rUnit )
282 & * ( thetaFreeze - tLoc(I,J) )
283 shelficeForcingS(i,j,bi,bj) =
284 & ( SHELFICEsaltTransCoeff
285 & - cFac*shelfIceFreshWaterFlux(I,J,bi,bj)*mass2rUnit )
286 & * ( saltFreeze - sLoc(I,J) )
287 ELSE
288 shelfIceHeatFlux (I,J,bi,bj) = 0. _d 0
289 shelfIceFreshWaterFlux(I,J,bi,bj) = 0. _d 0
290 shelficeForcingT (I,J,bi,bj) = 0. _d 0
291 shelficeForcingS (I,J,bi,bj) = 0. _d 0
292 ENDIF
293 ENDDO
294 ENDDO
295 ENDIF
296 C endif (not) useISOMIPTD
297 ENDDO
298 ENDDO
299
300 #ifdef ALLOW_DIAGNOSTICS
301 IF ( useDiagnostics ) THEN
302 CALL DIAGNOSTICS_FILL_RS(shelfIceFreshWaterFlux,'SHIfwFlx',
303 & 0,1,0,1,1,myThid)
304 CALL DIAGNOSTICS_FILL_RS(shelfIceHeatFlux, 'SHIhtFlx',
305 & 0,1,0,1,1,myThid)
306 C SHIForcT (Ice shelf forcing for theta [W/m2], >0 increases theta)
307 tmpFac = HeatCapacity_Cp*rUnit2mass
308 CALL DIAGNOSTICS_SCALE_FILL(shelficeForcingT,tmpFac,1,
309 & 'SHIForcT',0, 1,0,1,1,myThid)
310 C SHIForcS (Ice shelf forcing for salt [g/m2/s], >0 increases salt)
311 tmpFac = rUnit2mass
312 CALL DIAGNOSTICS_SCALE_FILL(shelficeForcingS,tmpFac,1,
313 & 'SHIForcS',0, 1,0,1,1,myThid)
314 ENDIF
315 #endif /* ALLOW_DIAGNOSTICS */
316
317 #endif /* ALLOW_SHELFICE */
318 RETURN
319 END

  ViewVC Help
Powered by ViewVC 1.1.22