/[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.24 - (show annotations) (download)
Fri Dec 24 00:55:40 2010 UTC (13 years, 4 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint63p, checkpoint63q, checkpoint63l, checkpoint63m, checkpoint63n, checkpoint63o, checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63k, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63g, checkpoint63a, checkpoint63b, checkpoint63c, checkpoint63, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62w, checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62z, checkpoint62y, checkpoint62x
Changes since 1.23: +32 -22 lines
fix the case useEXF without useSEAICE

1 C $Header: /u/gcmpack/MITgcm/pkg/thsice/thsice_main.F,v 1.23 2010/12/17 04:00:14 gforget 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 "GRID.h"
27 #include "SURFACE.h"
28 #include "DYNVARS.h"
29 #include "FFIELDS.h"
30 #include "THSICE_PARAMS.h"
31 #include "THSICE_SIZE.h"
32 #include "THSICE_VARS.h"
33 #ifdef ALLOW_AUTODIFF_TAMC
34 # include "tamc.h"
35 # include "tamc_keys.h"
36 #endif
37
38 C !INPUT/OUTPUT PARAMETERS:
39 C === Routine arguments ===
40 C myTime :: Current time in simulation (s)
41 C myIter :: Current iteration number
42 C myThid :: My Thread Id. number
43 _RL myTime
44 INTEGER myIter
45 INTEGER myThid
46 CEOP
47
48 #ifdef ALLOW_THSICE
49 C !LOCAL VARIABLES:
50 C === Local variables ===
51 INTEGER i,j
52 INTEGER bi,bj
53 INTEGER iMin, iMax
54 INTEGER jMin, jMax
55 _RL prcAtm(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
117 C-- Mixed layer thickness: take the 1rst layer
118 #ifdef NONLIN_FRSURF
119 IF ( staggerTimeStep .AND. nonlinFreeSurf.GT.0 ) THEN
120 IF ( select_rStar.GT.0 ) THEN
121 DO j=1-OLy,sNy+OLy
122 DO i=1-OLx,sNx+OLx
123 hOceMxL(i,j,bi,bj) = drF(1)*h0FacC(i,j,1,bi,bj)
124 & *rStarFacC(i,j,bi,bj)
125 ENDDO
126 ENDDO
127 ELSE
128 DO j=1-OLy,sNy+OLy
129 DO i=1-OLx,sNx+OLx
130 IF ( ksurfC(i,j,bi,bj).EQ.1 ) THEN
131 hOceMxL(i,j,bi,bj) = drF(1)*hFac_surfC(i,j,bi,bj)
132 ELSE
133 hOceMxL(i,j,bi,bj) = drF(1)*hFacC(i,j,1,bi,bj)
134 ENDIF
135 ENDDO
136 ENDDO
137 ENDIF
138 ELSE
139 #else /* ndef NONLIN_FRSURF */
140 IF (.TRUE.) THEN
141 #endif /* NONLIN_FRSURF */
142 DO j=1-OLy,sNy+OLy
143 DO i=1-OLx,sNx+OLx
144 hOceMxL(i,j,bi,bj) = drF(1)*hFacC(i,j,1,bi,bj)
145 ENDDO
146 ENDDO
147 ENDIF
148
149 #ifdef ALLOW_AUTODIFF_TAMC
150 CADJ STORE uvel (:,:,1,bi,bj) = comlev1_bibj, key=ticekey, byte=isbyte
151 CADJ STORE vvel (:,:,1,bi,bj) = comlev1_bibj, key=ticekey, byte=isbyte
152 #endif
153
154 DO j = jMin, jMax
155 DO i = iMin, iMax
156 tOceMxL(i,j,bi,bj) = theta(i,j,1,bi,bj)
157 sOceMxL(i,j,bi,bj) = salt (i,j,1,bi,bj)
158 v2ocMxL(i,j,bi,bj) =
159 & ( uvel(i,j,1,bi,bj)*uvel(i,j,1,bi,bj)
160 & + uvel(i+1,j,1,bi,bj)*uvel(i+1,j,1,bi,bj)
161 & + vvel(i,j+1,1,bi,bj)*vvel(i,j+1,1,bi,bj)
162 & + vvel(i,j,1,bi,bj)*vvel(i,j,1,bi,bj)
163 & )*0.5 _d 0
164 prcAtm(i,j) = 0.
165 icFrwAtm(i,j,bi,bj) = 0. _d 0
166 icFlxAtm(i,j,bi,bj) = 0. _d 0
167 icFlxSW (i,j,bi,bj) = 0. _d 0
168 snowPrc(i,j,bi,bj) = 0. _d 0
169 siceAlb(i,j,bi,bj) = 0. _d 0
170 ENDDO
171 ENDDO
172
173 #ifdef ALLOW_AUTODIFF_TAMC
174 CADJ STORE iceMask(:,:,bi,bj) = comlev1_bibj, key = ticekey
175 CADJ STORE iceHeight(:,:,bi,bj) = comlev1_bibj, key = ticekey
176 CADJ STORE snowHeight(:,:,bi,bj) = comlev1_bibj, key = ticekey
177 CADJ STORE Tsrf(:,:,bi,bj) = comlev1_bibj, key = ticekey
178 CADJ STORE Qice1(:,:,bi,bj) = comlev1_bibj, key = ticekey
179 CADJ STORE Qice2(:,:,bi,bj) = comlev1_bibj, key = ticekey
180 CADJ STORE snowAge(:,:,bi,bj) = comlev1_bibj, key = ticekey
181 CADJ STORE snowPrc(:,:,bi,bj) = comlev1_bibj, key = ticekey
182
183 CADJ STORE hOceMxL(:,:,bi,bj) = comlev1_bibj, key = ticekey
184 CADJ STORE tOceMxL(:,:,bi,bj) = comlev1_bibj, key = ticekey
185 CADJ STORE sOceMxL(:,:,bi,bj) = comlev1_bibj, key = ticekey
186 CADJ STORE v2ocMxL(:,:,bi,bj) = comlev1_bibj, key = ticekey
187 #endif
188
189 C- do sea-ice advection before getting surface fluxes
190 C Note: will inline this S/R once thSIce in Atmos. set-up is settled
191 IF ( thSIceAdvScheme.GT.0 )
192 & CALL THSICE_DO_ADVECT(
193 I bi,bj, myTime, myIter, myThid )
194
195 #ifdef ALLOW_BULK_FORCE
196 IF ( useBulkforce ) THEN
197 CALL THSICE_GET_PRECIP(
198 I iceMask,
199 O prcAtm, snowPrc(1-OLx,1-OLy,bi,bj),
200 O icFlxSW(1-OLx,1-OLy,bi,bj),
201 I iMin,iMax,jMin,jMax, bi,bj, myThid )
202 ENDIF
203 #endif
204 #ifdef ALLOW_EXF
205 IF ( useEXF ) THEN
206 CALL THSICE_MAP_EXF(
207 I iceMask,
208 O prcAtm, snowPrc(1-OLx,1-OLy,bi,bj),
209 O icFlxSW(1-OLx,1-OLy,bi,bj),
210 I iMin,iMax,jMin,jMax, bi,bj, myThid )
211 ENDIF
212 #endif
213
214 #ifdef ALLOW_AUTODIFF_TAMC
215 CADJ STORE sheating(:,:,bi,bj) = comlev1_bibj, key = ticekey
216 CADJ STORE tice1(:,:,bi,bj) = comlev1_bibj, key = ticekey
217 CADJ STORE tice2(:,:,bi,bj) = comlev1_bibj, key = ticekey
218 #endif
219 CALL THSICE_STEP_TEMP(
220 I bi, bj, iMin, iMax, jMin, jMax,
221 I myTime, myIter, myThid )
222
223 #ifdef ALLOW_AUTODIFF_TAMC
224 CADJ STORE empmr(:,:,bi,bj) = comlev1_bibj, key = ticekey
225 CADJ STORE qnet(:,:,bi,bj) = comlev1_bibj, key = ticekey
226 CADJ STORE iceMask(:,:,bi,bj) = comlev1_bibj, key = ticekey
227 CADJ STORE iceHeight(:,:,bi,bj) = comlev1_bibj, key = ticekey
228 CADJ STORE snowHeight(:,:,bi,bj) = comlev1_bibj, key = ticekey
229 cphCADJ STORE Tsrf(:,:,bi,bj) = comlev1_bibj, key = ticekey
230 CADJ STORE Qice1(:,:,bi,bj) = comlev1_bibj, key = ticekey
231 CADJ STORE Qice2(:,:,bi,bj) = comlev1_bibj, key = ticekey
232 CADJ STORE snowAge(:,:,bi,bj) = comlev1_bibj, key = ticekey
233 CADJ STORE sheating(:,:,bi,bj) = comlev1_bibj, key = ticekey
234 #endif
235
236 CALL THSICE_STEP_FWD(
237 I bi, bj, iMin, iMax, jMin, jMax,
238 I prcAtm,
239 I myTime, myIter, myThid )
240
241 CALL THSICE_AVE(
242 I bi,bj, myTime, myIter, myThid )
243
244 C-- end bi,bj loop
245 ENDDO
246 ENDDO
247
248 C add a small piece of code to check AddFluid implementation:
249 c#include "thsice_test_addfluid.h"
250
251 IF ( useSEAICE .OR. thSIceAdvScheme.GT.0 ) THEN
252 C-- Exchange fields that are advected by seaice dynamics
253 _EXCH_XY_RL( iceMask, myThid )
254 _EXCH_XY_RL( iceHeight, myThid )
255 _EXCH_XY_RL( snowHeight, myThid )
256 _EXCH_XY_RL( Qice1, myThid )
257 _EXCH_XY_RL( Qice2, myThid )
258 ELSEIF ( useEXF .AND. stressReduction.GT. 0. _d 0 ) THEN
259 _EXCH_XY_RL( iceMask, myThid )
260 ENDIF
261 #ifdef ATMOSPHERIC_LOADING
262 IF ( useRealFreshWaterFlux .AND. (useEXF.OR.useSEAICE ) )
263 & _EXCH_XY_RS( sIceLoad, myThid )
264 #endif
265
266 DO bj=myByLo(myThid),myByHi(myThid)
267 DO bi=myBxLo(myThid),myBxHi(myThid)
268 C-- note: If useSEAICE=.true., the stress is computed in seaice_model,
269 C-- and stressReduction is always set to zero
270 #ifdef ALLOW_AUTODIFF_TAMC
271 CADJ STORE fu(:,:,bi,bj) = comlev1_bibj, key=ticekey, byte=isbyte
272 CADJ STORE fv(:,:,bi,bj) = comlev1_bibj, key=ticekey, byte=isbyte
273 #endif
274 IF ( stressReduction.GT. 0. _d 0 ) THEN
275 DO j = jMin, jMax
276 DO i = iMin+1,iMax
277 tauFac = stressReduction
278 & *(iceMask(i-1,j,bi,bj)+iceMask(i,j,bi,bj))*0.5 _d 0
279 fu(i,j,bi,bj) = (1. _d 0 - tauFac)*fu(i,j,bi,bj)
280 ENDDO
281 ENDDO
282 DO j = jMin+1, jMax
283 DO i = iMin, iMax
284 tauFac = stressReduction
285 & *(iceMask(i,j-1,bi,bj)+iceMask(i,j,bi,bj))*0.5 _d 0
286 fv(i,j,bi,bj) = (1. _d 0 - tauFac)*fv(i,j,bi,bj)
287 ENDDO
288 ENDDO
289 ENDIF
290
291 C-- end bi,bj loop
292 ENDDO
293 ENDDO
294
295 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
296 #endif /*ALLOW_THSICE*/
297
298 RETURN
299 END

  ViewVC Help
Powered by ViewVC 1.1.22