/[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.15 - (show annotations) (download)
Thu Apr 19 02:59:29 2007 UTC (17 years, 1 month ago) by jmc
Branch: MAIN
Changes since 1.14: +7 -7 lines
comment out "print *, 'ph-thsice" that were filling up the disk.

1 C $Header: /u/gcmpack/MITgcm/pkg/thsice/thsice_main.F,v 1.14 2007/04/17 23:42:33 heimbach 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_VARS.h"
32 #ifdef ALLOW_AUTODIFF_TAMC
33 # include "tamc.h"
34 # include "tamc_keys.h"
35 C--
36 # include "THSICE_2DYN.h"
37 C--
38 #endif
39
40 C !INPUT/OUTPUT PARAMETERS:
41 C === Routine arguments ===
42 C myTime :: Current time in simulation (s)
43 C myIter :: Current iteration number
44 C myThid :: My Thread Id. number
45 _RL myTime
46 INTEGER myIter
47 INTEGER myThid
48 CEOP
49
50 #ifdef ALLOW_THSICE
51 C !LOCAL VARIABLES:
52 C === Local variables ===
53 INTEGER i,j
54 INTEGER bi,bj
55 INTEGER iMin, iMax
56 INTEGER jMin, jMax
57 _RL prcAtm(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
58 c _RL evpAtm(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
59 c _RL flxAtm(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
60 c _RL flxSW (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
61
62 _RL tauFac
63
64 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
65
66 IF ( stressReduction.GT. 0. _d 0 ) THEN
67 C- needs new Ice Fraction in halo region to apply wind-stress reduction
68 iMin = 1-OLx
69 iMax = sNx+OLx-1
70 jMin = 1-OLy
71 jMax = sNy+OLy-1
72 #ifdef ATMOSPHERIC_LOADING
73 ELSEIF ( useRealFreshWaterFlux .AND. .NOT.useSEAICE ) THEN
74 C- needs sea-ice loading in part of the halo regions for grad.Phi0surf
75 C to be valid at the boundaries ( d/dx 1:sNx+1 ; d/dy 1:sNy+1 )
76 iMin = 0
77 iMax = sNx+1
78 jMin = 0
79 jMax = sNy+1
80 #endif /* ATMOSPHERIC_LOADING */
81 ELSE
82 iMin = 1
83 iMax = sNx
84 jMin = 1
85 jMax = sNy
86 ENDIF
87
88 DO bj=myByLo(myThid),myByHi(myThid)
89 DO bi=myBxLo(myThid),myBxHi(myThid)
90
91 #ifdef ALLOW_AUTODIFF_TAMC
92 act1 = bi - myBxLo(myThid)
93 max1 = myBxHi(myThid) - myBxLo(myThid) + 1
94 act2 = bj - myByLo(myThid)
95 max2 = myByHi(myThid) - myByLo(myThid) + 1
96 act3 = myThid - 1
97 max3 = nTx*nTy
98 act4 = ikey_dynamics - 1
99 iicekey = (act1 + 1) + act2*max1
100 & + act3*max1*max2
101 & + act4*max1*max2*max3
102 #endif /* ALLOW_AUTODIFF_TAMC */
103
104 #ifdef ALLOW_AUTODIFF_TAMC
105 CADJ STORE ocefwfx(:,:,bi,bj) = comlev1_bibj, key=iicekey, byte=isbyte
106 CADJ STORE oceqnet(:,:,bi,bj) = comlev1_bibj, key=iicekey, byte=isbyte
107 CADJ STORE ocesflx(:,:,bi,bj) = comlev1_bibj, key=iicekey, byte=isbyte
108 # ifdef ALLOW_EXF
109 CADJ STORE qsw(:,:,bi,bj) = comlev1_bibj, key=iicekey, byte=isbyte
110 # endif
111 #endif
112
113 cph(
114 c print *, 'ph-thsice-1 in thsice_main'
115 cph)
116 C-- Mixed layer thickness: take the 1rst layer
117 #ifdef NONLIN_FRSURF
118 IF ( staggerTimeStep .AND. nonlinFreeSurf.GT.0 ) THEN
119 IF ( select_rStar.GT.0 ) THEN
120 DO j = jMin, jMax
121 DO i = iMin, iMax
122 hOceMxL(i,j,bi,bj) = drF(1)*h0FacC(i,j,1,bi,bj)
123 & *rStarFacC(i,j,bi,bj)
124 ENDDO
125 ENDDO
126 ELSE
127 DO j = jMin, jMax
128 DO i = iMin, iMax
129 IF ( ksurfC(i,j,bi,bj).EQ.1 ) THEN
130 hOceMxL(i,j,bi,bj) = drF(1)*hFac_surfC(i,j,bi,bj)
131 ELSE
132 hOceMxL(i,j,bi,bj) = drF(1)*hFacC(i,j,1,bi,bj)
133 ENDIF
134 ENDDO
135 ENDDO
136 ENDIF
137 ELSE
138 #else /* ndef NONLIN_FRSURF */
139 IF (.TRUE.) THEN
140 #endif /* NONLIN_FRSURF */
141 DO j = jMin, jMax
142 DO i = iMin, iMax
143 hOceMxL(i,j,bi,bj) = drF(1)*hFacC(i,j,1,bi,bj)
144 ENDDO
145 ENDDO
146 ENDIF
147
148 #ifdef ALLOW_AUTODIFF_TAMC
149 CADJ STORE uvel (:,:,1,bi,bj) = comlev1_bibj, key=iicekey, byte=isbyte
150 CADJ STORE vvel (:,:,1,bi,bj) = comlev1_bibj, key=iicekey, byte=isbyte
151 #endif
152
153 DO j = jMin, jMax
154 DO i = iMin, iMax
155 tOceMxL(i,j,bi,bj) = theta(i,j,1,bi,bj)
156 sOceMxL(i,j,bi,bj) = salt (i,j,1,bi,bj)
157 v2ocMxL(i,j,bi,bj) =
158 & ( uvel(i,j,1,bi,bj)*uvel(i,j,1,bi,bj)
159 & + uvel(i+1,j,1,bi,bj)*uvel(i+1,j,1,bi,bj)
160 & + vvel(i,j+1,1,bi,bj)*vvel(i,j+1,1,bi,bj)
161 & + vvel(i,j,1,bi,bj)*vvel(i,j,1,bi,bj)
162 & )*0.5 _d 0
163 prcAtm(i,j) = 0.
164 icFrwAtm(i,j,bi,bj) = 0. _d 0
165 icFlxAtm(i,j,bi,bj) = 0. _d 0
166 icFlxSW (i,j,bi,bj) = 0. _d 0
167 snowPrc(i,j,bi,bj) = 0. _d 0
168 siceAlb(i,j,bi,bj) = 0. _d 0
169 ENDDO
170 ENDDO
171
172 #ifdef ALLOW_AUTODIFF_TAMC
173 CADJ STORE iceMask = comlev1, key = iicekey
174 CADJ STORE iceHeight = comlev1, key = iicekey
175 CADJ STORE snowHeight = comlev1, key = iicekey
176 CADJ STORE Tsrf = comlev1, key = iicekey
177 CADJ STORE Qice1 = comlev1, key = iicekey
178 CADJ STORE Qice2 = comlev1, key = iicekey
179 CADJ STORE snowAge = comlev1, key = iicekey
180 CADJ STORE snowPrc = comlev1, key = iicekey
181
182 CADJ STORE hOceMxL = comlev1, key = iicekey
183 CADJ STORE tOceMxL = comlev1, key = iicekey
184 CADJ STORE sOceMxL = comlev1, key = iicekey
185 CADJ STORE v2ocMxL = comlev1, key = iicekey
186
187 CADJ STORE empmr = comlev1, key = iicekey
188 CADJ STORE qnet = comlev1, key = iicekey
189 #endif
190
191 cph(
192 c print *, 'ph-thsice-2 in thsice_main'
193 cph)
194 C- do sea-ice advection before getting surface fluxes
195 C Note: will inline this S/R once thSIce in Atmos. set-up is settled
196 IF ( thSIceAdvScheme.GT.0 )
197 & CALL THSICE_DO_ADVECT(
198 I bi,bj, myTime, myIter, myThid )
199
200 #ifdef ALLOW_BULK_FORCE
201 IF ( useBulkforce ) THEN
202 CALL THSICE_GET_PRECIP(
203 I iceMask,
204 O prcAtm, snowPrc(1-OLx,1-OLy,bi,bj),
205 O icFlxSW(1-OLx,1-OLy,bi,bj),
206 I iMin,iMax,jMin,jMax, bi,bj, myThid )
207 ENDIF
208 #endif
209 #ifdef ALLOW_EXF
210 IF ( useEXF ) THEN
211 CALL THSICE_MAP_EXF(
212 I iceMask,
213 O prcAtm, snowPrc(1-OLx,1-OLy,bi,bj),
214 O icFlxSW(1-OLx,1-OLy,bi,bj),
215 I iMin,iMax,jMin,jMax, bi,bj, myThid )
216 ENDIF
217 #endif
218
219
220 cph(
221 c print *, 'ph-thsice-3 in thsice_main'
222 cph)
223 CALL THSICE_STEP_TEMP(
224 I bi, bj, iMin, iMax, jMin, jMax,
225 I myTime, myIter, myThid )
226
227 #ifdef ALLOW_AUTODIFF_TAMC
228 CADJ STORE empmr, qnet = comlev1, key = iicekey
229 CADJ STORE iceMask = comlev1, key = iicekey
230 CADJ STORE iceHeight = comlev1, key = iicekey
231 CADJ STORE snowHeight = comlev1, key = iicekey
232 CADJ STORE Tsrf = comlev1, key = iicekey
233 CADJ STORE Qice1 = comlev1, key = iicekey
234 CADJ STORE Qice2 = comlev1, key = iicekey
235 CADJ STORE snowAge = comlev1, key = iicekey
236 #endif
237
238 cph(
239 c print *, 'ph-thsice-4 in thsice_main'
240 cph)
241 CALL THSICE_STEP_FWD(
242 I bi, bj, iMin, iMax, jMin, jMax,
243 I prcAtm,
244 I myTime, myIter, myThid )
245
246 cph(
247 c print *, 'ph-thsice-5 in thsice_main'
248 cph)
249 CALL THSICE_AVE(
250 I bi,bj, myTime, myIter, myThid )
251
252 c ENDDO
253 c ENDDO
254
255 C-- note: If useSEAICE=.true., the stress is computed in seaice_model,
256 C-- and stressReduction is always set to zero
257 #ifdef ALLOW_AUTODIFF_TAMC
258 CADJ STORE fu(:,:,bi,bj) = comlev1_bibj, key=iicekey, byte=isbyte
259 CADJ STORE fv(:,:,bi,bj) = comlev1_bibj, key=iicekey, byte=isbyte
260 #endif
261 IF ( stressReduction.GT. 0. _d 0 ) THEN
262 DO j = jMin, jMax
263 DO i = iMin+1,iMax
264 tauFac = stressReduction
265 & *(iceMask(i-1,j,bi,bj)+iceMask(i,j,bi,bj))*0.5 _d 0
266 fu(i,j,bi,bj) = (1. _d 0 - tauFac)*fu(i,j,bi,bj)
267 ENDDO
268 ENDDO
269 DO j = jMin+1, jMax
270 DO i = iMin, iMax
271 tauFac = stressReduction
272 & *(iceMask(i,j-1,bi,bj)+iceMask(i,j,bi,bj))*0.5 _d 0
273 fv(i,j,bi,bj) = (1. _d 0 - tauFac)*fv(i,j,bi,bj)
274 ENDDO
275 ENDDO
276 ENDIF
277
278 C-- end bi,bj loop
279 ENDDO
280 ENDDO
281
282
283 cph(
284 c print *, 'ph-thsice-6 in thsice_main'
285 cph)
286 IF ( useSEAICE .OR. thSIceAdvScheme.GT.0 ) THEN
287 C-- Exchange fields that are advected by seaice dynamics
288 _EXCH_XY_R8( iceMask, myThid )
289 _EXCH_XY_R8( iceHeight, myThid )
290 _EXCH_XY_R8( snowHeight, myThid )
291 _EXCH_XY_R8( Qice1, myThid )
292 _EXCH_XY_R8( Qice2, myThid )
293 #ifdef ATMOSPHERIC_LOADING
294 IF (useRealFreshWaterFlux)
295 & _EXCH_XY_RS( sIceLoad, myThid )
296 #endif
297 ENDIF
298
299 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
300 #endif /*ALLOW_THSICE*/
301
302 RETURN
303 END

  ViewVC Help
Powered by ViewVC 1.1.22