/[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.38 - (show annotations) (download)
Tue Jun 11 01:48:22 2013 UTC (10 years, 11 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint64q, checkpoint64p, checkpoint64s, checkpoint64r, checkpoint64i, checkpoint64k, checkpoint64j, checkpoint64m, checkpoint64l, checkpoint64o, checkpoint64n
Changes since 1.37: +14 -20 lines
allow precip from pkg/cheapaml to make snow over seaice

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

  ViewVC Help
Powered by ViewVC 1.1.22