/[MITgcm]/MITgcm/pkg/thsice/thsice_main.F
ViewVC logotype

Contents of /MITgcm/pkg/thsice/thsice_main.F

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


Revision 1.31 - (show annotations) (download)
Thu Apr 4 16:44:34 2013 UTC (11 years, 2 months ago) by jmc
Branch: MAIN
Changes since 1.30: +7 -4 lines
In case Energy-Reference-Level is used (temp_EvPrRn=0), account for
 energy content of Precip + RunOff. Assumes: 1) Rain has same temp as Air
 2) Snow has no heat capacity (consistent with seaice & thsice & exf pkgs)
 3) No distinction between sea-water Cp and fresh-water Cp
 4) Run-Off comes at the temp of surface water (with same Cp)
Note: since variations of Lf+Lv with Tsurf are neglected in Evap over ice
 and  snow (since snow has no Cp); this means that water vapor is considered
 to be released to Atmos @ 0^oC (=ERL).

1 C $Header: /u/gcmpack/MITgcm/pkg/thsice/thsice_main.F,v 1.30 2013/04/04 00:42:06 jmc Exp $
2 C $Name: $
3
4 #include "THSICE_OPTIONS.h"
5
6 CBOP
7 C !ROUTINE: THSICE_MAIN
8 C !INTERFACE:
9 SUBROUTINE THSICE_MAIN(
10 I myTime, myIter, myThid )
11 C !DESCRIPTION: \bv
12 C *==========================================================*
13 C | S/R THSICE_MAIN
14 C | o Therm_SeaIce main routine.
15 C | step forward Thermodynamic_SeaIce variables and modify
16 C | ocean surface forcing accordingly.
17 C *==========================================================*
18
19 C !USES:
20 IMPLICIT NONE
21
22 C === Global variables ===
23 #include "SIZE.h"
24 #include "EEPARAMS.h"
25 #include "PARAMS.h"
26 #include "FFIELDS.h"
27 #include "THSICE_PARAMS.h"
28 #include "THSICE_SIZE.h"
29 #include "THSICE_VARS.h"
30 #ifdef ALLOW_AUTODIFF_TAMC
31 # include "DYNVARS.h"
32 # include "tamc.h"
33 # include "tamc_keys.h"
34 #endif
35
36 C !INPUT/OUTPUT PARAMETERS:
37 C === Routine arguments ===
38 C myTime :: Current time in simulation (s)
39 C myIter :: Current iteration number
40 C myThid :: My Thread Id. number
41 _RL myTime
42 INTEGER myIter
43 INTEGER myThid
44 CEOP
45
46 #ifdef ALLOW_THSICE
47 C !LOCAL VARIABLES:
48 C === Local variables ===
49 C qPrcRn :: Energy content of Precip+RunOff (+=down) [W/m2]
50 INTEGER i,j
51 INTEGER bi,bj
52 INTEGER iMin, iMax
53 INTEGER jMin, jMax
54 _RL prcAtm(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
55 _RL qPrcRn(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
56 c _RL evpAtm(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
57 c _RL flxAtm(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
58 c _RL flxSW (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
59
60 _RL tauFac
61
62 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
63
64 IF ( useEXF .OR. useSEAICE ) THEN
65 C- EXF does not provide valid fields in overlap
66 iMin = 1
67 iMax = sNx
68 jMin = 1
69 jMax = sNy
70 ELSEIF ( stressReduction.GT. 0. _d 0 ) THEN
71 C- needs new Ice Fraction in halo region to apply wind-stress reduction
72 iMin = 1-OLx
73 iMax = sNx+OLx-1
74 jMin = 1-OLy
75 jMax = sNy+OLy-1
76 #ifdef ATMOSPHERIC_LOADING
77 ELSEIF ( useRealFreshWaterFlux ) THEN
78 C- needs sea-ice loading in part of the halo regions for grad.Phi0surf
79 C to be valid at the boundaries ( d/dx 1:sNx+1 ; d/dy 1:sNy+1 )
80 iMin = 0
81 iMax = sNx+1
82 jMin = 0
83 jMax = sNy+1
84 #endif /* ATMOSPHERIC_LOADING */
85 ELSE
86 iMin = 1
87 iMax = sNx
88 jMin = 1
89 jMax = sNy
90 ENDIF
91
92 DO bj=myByLo(myThid),myByHi(myThid)
93 DO bi=myBxLo(myThid),myBxHi(myThid)
94
95 #ifdef ALLOW_AUTODIFF_TAMC
96 act1 = bi - myBxLo(myThid)
97 max1 = myBxHi(myThid) - myBxLo(myThid) + 1
98 act2 = bj - myByLo(myThid)
99 max2 = myByHi(myThid) - myByLo(myThid) + 1
100 act3 = myThid - 1
101 max3 = nTx*nTy
102 act4 = ikey_dynamics - 1
103 ticekey = (act1 + 1) + act2*max1
104 & + act3*max1*max2
105 & + act4*max1*max2*max3
106 #endif /* ALLOW_AUTODIFF_TAMC */
107
108 #ifdef ALLOW_AUTODIFF_TAMC
109 CADJ STORE ocefwfx(:,:,bi,bj) = comlev1_bibj, key=ticekey, byte=isbyte
110 CADJ STORE oceqnet(:,:,bi,bj) = comlev1_bibj, key=ticekey, byte=isbyte
111 CADJ STORE ocesflx(:,:,bi,bj) = comlev1_bibj, key=ticekey, byte=isbyte
112 # ifdef ALLOW_EXF
113 CADJ STORE qsw(:,:,bi,bj) = comlev1_bibj, key=ticekey, byte=isbyte
114 # endif
115 #endif
116 #ifdef ALLOW_AUTODIFF_TAMC
117 CADJ STORE uvel (:,:,1,bi,bj) = comlev1_bibj, key=ticekey, byte=isbyte
118 CADJ STORE vvel (:,:,1,bi,bj) = comlev1_bibj, key=ticekey, byte=isbyte
119 #endif
120
121 DO j=1-OLy,sNy+OLy
122 DO i=1-OLx,sNx+OLx
123 prcAtm (i,j,bi,bj) = 0. _d 0
124 qPrcRn (i,j) = 0. _d 0
125 ENDDO
126 ENDDO
127
128 CALL THSICE_GET_OCEAN(
129 I bi, bj, myTime, myIter, myThid )
130
131 #ifdef ALLOW_AUTODIFF_TAMC
132 CADJ STORE iceMask(:,:,bi,bj) = comlev1_bibj, key = ticekey
133 CADJ STORE iceHeight(:,:,bi,bj) = comlev1_bibj, key = ticekey
134 CADJ STORE snowHeight(:,:,bi,bj) = comlev1_bibj, key = ticekey
135 CADJ STORE Tsrf(:,:,bi,bj) = comlev1_bibj, key = ticekey
136 CADJ STORE Qice1(:,:,bi,bj) = comlev1_bibj, key = ticekey
137 CADJ STORE Qice2(:,:,bi,bj) = comlev1_bibj, key = ticekey
138 CADJ STORE snowAge(:,:,bi,bj) = comlev1_bibj, key = ticekey
139 CADJ STORE snowPrc(:,:,bi,bj) = comlev1_bibj, key = ticekey
140
141 CADJ STORE hOceMxL(:,:,bi,bj) = comlev1_bibj, key = ticekey
142 CADJ STORE tOceMxL(:,:,bi,bj) = comlev1_bibj, key = ticekey
143 CADJ STORE sOceMxL(:,:,bi,bj) = comlev1_bibj, key = ticekey
144 CADJ STORE v2ocMxL(:,:,bi,bj) = comlev1_bibj, key = ticekey
145 #endif
146
147 #ifdef OLD_THSICE_CALL_SEQUENCE
148 C- do sea-ice advection before getting surface fluxes
149 C Note: will inline this S/R once thSIce in Atmos. set-up is settled
150 IF ( thSIceAdvScheme.GT.0 )
151 & CALL THSICE_DO_ADVECT(
152 I bi,bj, myTime, myIter, myThid )
153 #endif /* OLD_THSICE_CALL_SEQUENCE */
154
155 #ifdef ALLOW_BULK_FORCE
156 IF ( useBulkforce ) THEN
157 CALL THSICE_GET_PRECIP(
158 I iceMask,
159 O prcAtm(1-OLx,1-OLy,bi,bj),
160 O snowPrc(1-OLx,1-OLy,bi,bj),
161 O icFlxSW(1-OLx,1-OLy,bi,bj),
162 I iMin,iMax,jMin,jMax, bi,bj, myThid )
163 ENDIF
164 #endif
165 #ifdef ALLOW_EXF
166 IF ( useEXF ) THEN
167 CALL THSICE_MAP_EXF(
168 I iceMask, tOceMxL,
169 O prcAtm(1-OLx,1-OLy,bi,bj),
170 O snowPrc(1-OLx,1-OLy,bi,bj), qPrcRn,
171 O icFlxSW(1-OLx,1-OLy,bi,bj),
172 I iMin,iMax,jMin,jMax, bi,bj, myThid )
173 ENDIF
174 #endif
175
176 #ifdef ALLOW_AUTODIFF_TAMC
177 CADJ STORE sHeating(:,:,bi,bj) = comlev1_bibj, key = ticekey
178 CADJ STORE tice1(:,:,bi,bj) = comlev1_bibj, key = ticekey
179 CADJ STORE tice2(:,:,bi,bj) = comlev1_bibj, key = ticekey
180 #else
181 IF ( .NOT.thSIce_skipThermo ) THEN
182 #endif
183 CALL THSICE_STEP_TEMP(
184 I bi, bj, iMin, iMax, jMin, jMax,
185 I myTime, myIter, myThid )
186
187 #ifdef ALLOW_AUTODIFF_TAMC
188 CADJ STORE empmr(:,:,bi,bj) = comlev1_bibj, key = ticekey
189 CADJ STORE qnet(:,:,bi,bj) = comlev1_bibj, key = ticekey
190 CADJ STORE iceMask(:,:,bi,bj) = comlev1_bibj, key = ticekey
191 CADJ STORE iceHeight(:,:,bi,bj) = comlev1_bibj, key = ticekey
192 CADJ STORE snowHeight(:,:,bi,bj) = comlev1_bibj, key = ticekey
193 cphCADJ STORE Tsrf(:,:,bi,bj) = comlev1_bibj, key = ticekey
194 CADJ STORE Qice1(:,:,bi,bj) = comlev1_bibj, key = ticekey
195 CADJ STORE Qice2(:,:,bi,bj) = comlev1_bibj, key = ticekey
196 CADJ STORE snowAge(:,:,bi,bj) = comlev1_bibj, key = ticekey
197 CADJ STORE sHeating(:,:,bi,bj) = comlev1_bibj, key = ticekey
198 #else
199 ENDIF
200 IF ( .NOT.thSIce_skipThermo ) THEN
201 #endif
202 CALL THSICE_STEP_FWD(
203 I bi, bj, iMin, iMax, jMin, jMax,
204 I prcAtm(1-OLx,1-OLy,bi,bj), qPrcRn,
205 I myTime, myIter, myThid )
206 #ifndef ALLOW_AUTODIFF_TAMC
207 ENDIF
208 #endif
209
210 C-- end bi,bj loop
211 ENDDO
212 ENDDO
213
214 #ifdef ALLOW_BALANCE_FLUXES
215 C-- Balance net Fresh-Water flux from Atm+Land
216 IF ( thSIceBalanceAtmFW.NE.0 ) THEN
217 CALL THSICE_BALANCE_FRW(
218 I iMin, iMax, jMin, jMax,
219 I prcAtm, myTime, myIter, myThid )
220 ENDIF
221 #endif
222
223 C add a small piece of code to check AddFluid implementation:
224 c#include "thsice_test_addfluid.h"
225
226 C-- Exchange fields that are advected by seaice dynamics
227 IF ( useSEAICE .OR. thSIceAdvScheme.GT.0
228 & .OR. ( useEXF .AND. stressReduction.GT.zeroRL ) ) THEN
229 CALL THSICE_DO_EXCH( myThid )
230 ENDIF
231 #ifdef OLD_THSICE_CALL_SEQUENCE
232 #ifdef ATMOSPHERIC_LOADING
233 IF ( useRealFreshWaterFlux .AND.
234 & ( useEXF .OR. useSEAICE .OR. thSIceAdvScheme.GT.0 ) )
235 & _EXCH_XY_RS( sIceLoad, myThid )
236 #endif
237 #else /* OLD_THSICE_CALL_SEQUENCE */
238 #ifdef ATMOSPHERIC_LOADING
239 IF ( useRealFreshWaterFlux .AND. (useEXF.OR.useSEAICE )
240 & .AND. thSIceAdvScheme.LE.0 )
241 & _EXCH_XY_RS( sIceLoad, myThid )
242 #endif
243
244 C- when useSEAICE=.true., this S/R is called from SEAICE_MODEL;
245 C otherwise, call it from here, after thsice-thermodynamics is done
246 IF ( thSIceAdvScheme.GT.0 .AND. .NOT.useSEAICE ) THEN
247 CALL THSICE_DO_ADVECT(
248 I 0, 0, myTime, myIter, myThid )
249 ENDIF
250 #endif /* OLD_THSICE_CALL_SEQUENCE */
251
252 DO bj=myByLo(myThid),myByHi(myThid)
253 DO bi=myBxLo(myThid),myBxHi(myThid)
254 C-- Cumulate time-averaged fields and also fill-up flux diagnostics
255 C (if not done in THSICE_DO_ADVECT call)
256 #ifdef OLD_THSICE_CALL_SEQUENCE
257 IF ( .TRUE. ) THEN
258 #else /* OLD_THSICE_CALL_SEQUENCE */
259 IF ( thSIceAdvScheme.LE.0 ) THEN
260 #endif /* OLD_THSICE_CALL_SEQUENCE */
261 CALL THSICE_AVE(
262 I bi,bj, myTime, myIter, myThid )
263 ENDIF
264 C-- note: If useSEAICE=.true., the stress is computed in seaice_model,
265 C-- and stressReduction is always set to zero
266 #ifdef ALLOW_AUTODIFF_TAMC
267 CADJ STORE fu(:,:,bi,bj) = comlev1_bibj, key=ticekey, byte=isbyte
268 CADJ STORE fv(:,:,bi,bj) = comlev1_bibj, key=ticekey, byte=isbyte
269 #endif
270 IF ( stressReduction.GT. 0. _d 0 ) THEN
271 DO j = jMin, jMax
272 DO i = iMin+1,iMax
273 tauFac = stressReduction
274 & *(iceMask(i-1,j,bi,bj)+iceMask(i,j,bi,bj))*0.5 _d 0
275 fu(i,j,bi,bj) = (1. _d 0 - tauFac)*fu(i,j,bi,bj)
276 ENDDO
277 ENDDO
278 DO j = jMin+1, jMax
279 DO i = iMin, iMax
280 tauFac = stressReduction
281 & *(iceMask(i,j-1,bi,bj)+iceMask(i,j,bi,bj))*0.5 _d 0
282 fv(i,j,bi,bj) = (1. _d 0 - tauFac)*fv(i,j,bi,bj)
283 ENDDO
284 ENDDO
285 ENDIF
286
287 C-- end bi,bj loop
288 ENDDO
289 ENDDO
290
291 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
292 #endif /*ALLOW_THSICE*/
293
294 RETURN
295 END

  ViewVC Help
Powered by ViewVC 1.1.22