/[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.30 - (show annotations) (download)
Thu Apr 4 00:42:06 2013 UTC (11 years, 2 months ago) by jmc
Branch: MAIN
Changes since 1.29: +11 -8 lines
Forgot to move (after the advection) THSICE_AVE call in new sequence of calls

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

  ViewVC Help
Powered by ViewVC 1.1.22