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

Annotation of /MITgcm/pkg/thsice/thsice_advdiff.F

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


Revision 1.3 - (hide annotations) (download)
Sun Apr 8 18:53:16 2007 UTC (17 years, 1 month ago) by jmc
Branch: MAIN
Changes since 1.2: +9 -2 lines
add #ifdef arround pkg/generic_advdiff source code.

1 jmc 1.3 C $Header: /u/gcmpack/MITgcm/pkg/thsice/thsice_advdiff.F,v 1.2 2007/04/05 22:06:43 jmc Exp $
2 jmc 1.1 C $Name: $
3    
4     #include "THSICE_OPTIONS.h"
5 jmc 1.3 #ifdef ALLOW_GENERIC_ADVDIFF
6     # include "GAD_OPTIONS.h"
7     #endif
8 jmc 1.1
9     CBOP
10     C !ROUTINE: THSICE_ADVDIFF
11    
12     C !INTERFACE: ==========================================================
13     SUBROUTINE THSICE_ADVDIFF(
14     U uIce, vIce,
15     I bi, bj, myTime, myIter, myThid )
16    
17     C !DESCRIPTION: \bv
18     C *===========================================================*
19     C | SUBROUTINE THSICE_ADVDIFF
20     C | o driver for different advection routines
21     C | calls an adaption of gad_advection to call different
22     C | advection routines of pkg/generic_advdiff
23     C *===========================================================*
24     C \ev
25    
26     C !USES: ===============================================================
27     IMPLICIT NONE
28    
29     C === Global variables ===
30     C oceFWfx :: fresh water flux to the ocean [kg/m^2/s]
31     C oceSflx :: salt flux to the ocean [psu.kg/m^2/s] (~g/m^2/s)
32     C oceQnet :: heat flux to the ocean [W/m^2]
33    
34     #include "SIZE.h"
35     #include "EEPARAMS.h"
36     #include "PARAMS.h"
37     #include "GRID.h"
38     #include "THSICE_SIZE.h"
39     #include "THSICE_PARAMS.h"
40     #include "THSICE_VARS.h"
41     #include "THSICE_2DYN.h"
42 jmc 1.3 #ifdef ALLOW_GENERIC_ADVDIFF
43     # include "GAD.h"
44     #endif
45 jmc 1.1
46     C !INPUT PARAMETERS: ===================================================
47     C === Routine arguments ===
48     C uIce/vIce :: ice velocity on C-grid [m/s]
49     C bi,bj :: Tile indices
50     C myTime :: Current time in simulation (s)
51     C myIter :: Current iteration number
52     C myThid :: My Thread Id. number
53     _RL uIce (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
54     _RL vIce (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
55     INTEGER bi,bj
56     _RL myTime
57     INTEGER myIter
58     INTEGER myThid
59     CEndOfInterface
60    
61     #ifdef ALLOW_THSICE
62     C !LOCAL VARIABLES: ====================================================
63     C === Local variables ===
64     C i,j, :: Loop counters
65     C uTrans :: sea-ice area transport, x direction
66     C vTrans :: sea-ice area transport, y direction
67     C uTrIce :: sea-ice volume transport, x direction
68     C vTrIce :: sea-ice volume transport, y direction
69     C afx :: horizontal advective flux, x direction
70     C afy :: horizontal advective flux, y direction
71     C iceFrc :: (new) sea-ice fraction
72     C iceFld :: (new) effective sea-ice thickness
73     C iceVol :: temporary array used in advection S/R
74     C oldVol :: (old) sea-ice volume
75     C msgBuf :: Informational/error meesage buffer
76     INTEGER i, j
77     LOGICAL thSIce_multiDimAdv
78     CHARACTER*(MAX_LEN_MBUF) msgBuf
79    
80     _RL uTrans (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
81     _RL vTrans (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
82     _RL uTrIce (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
83     _RL vTrIce (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
84     _RL afx (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
85     _RL afy (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
86     _RS maskOce (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
87     _RL iceFrc (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
88     _RL iceFld (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
89     _RL iceVol (1-Olx:sNx+Olx,1-Oly:sNy+Oly)
90     _RL oldVol (1-Olx:sNx+Olx,1-Oly:sNy+Oly)
91     _RL minIcHeff, minIcArea, r_minArea
92     _RL meanCellArea, areaEpsil, vol_Epsil
93 jmc 1.2 #ifdef ALLOW_DIAGNOSTICS
94     CHARACTER*8 diagName
95     CHARACTER*4 THSICE_DIAG_SUFX, diagSufx
96     EXTERNAL THSICE_DIAG_SUFX
97     #endif
98 jmc 1.1 #ifdef ALLOW_DBUG_THSICE
99     _RL tmpVar, sumVar1, sumVar2
100     #endif
101     LOGICAL dBugFlag
102     #include "THSICE_DEBUG.h"
103     CEOP
104    
105     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
106     C areaEpsil, vol_Epsil are 2 small numbers for ice area & ice volume:
107     C if ice area (=ice fraction * grid-cell area) or ice volume (= effective
108     C thickness * grid-cell area) are too small (i.e.: < areaEpsil,vol_Epsil)
109     C will assume that ice is gone, and will loose mass or energy.
110     C However, if areaEpsil,vol_Epsil are much smaller than minimun ice area
111     C (iceMaskMin*rAc) and minimum ice volume (iceMaskMin*himin*rAc),
112     C good chance that this will never happen within 1 time step.
113    
114     dBugFlag = debugLevel.GE.debLevB
115    
116     C- definitively not an accurate computation of mean grid-cell area;
117     C but what matter here is just to have the right order of magnitude.
118     meanCellArea = Nx*Ny
119     meanCellArea = globalArea / meanCellArea
120     areaEpsil = 1. _d -10 * meanCellArea
121     vol_Epsil = 1. _d -15 * meanCellArea
122    
123     minIcArea = iceMaskMin
124     minIcHeff = iceMaskMin*himin
125     r_minArea = 0. _d 0
126     IF ( minIcArea.GT.0. _d 0 ) r_minArea = 1. _d 0 / minIcArea
127    
128     thSIce_multiDimAdv = .TRUE.
129 jmc 1.3 #ifdef ALLOW_GENERIC_ADVDIFF
130 jmc 1.1 IF ( thSIceAdvScheme.EQ.ENUM_CENTERED_2ND
131     & .OR.thSIceAdvScheme.EQ.ENUM_UPWIND_3RD
132     & .OR.thSIceAdvScheme.EQ.ENUM_CENTERED_4TH ) THEN
133     thSIce_multiDimAdv = .FALSE.
134     ENDIF
135 jmc 1.3 #endif /* ALLOW_GENERIC_ADVDIFF */
136 jmc 1.1
137     C-- Initialisation (+ build oceanic mask)
138     DO j=1-OLy,sNy+OLy
139     DO i=1-OLx,sNx+OLx
140     maskOce(i,j) = 0. _d 0
141     IF ( hOceMxL(i,j,bi,bj).GT.0. ) maskOce(i,j) = 1.
142     iceVol(i,j) = 0. _d 0
143     uTrans(i,j) = 0. _d 0
144     vTrans(i,j) = 0. _d 0
145     uTrIce(i,j) = 0. _d 0
146     vTrIce(i,j) = 0. _d 0
147     oceFWfx(i,j,bi,bj) = 0. _d 0
148     oceSflx(i,j,bi,bj) = 0. _d 0
149     oceQnet(i,j,bi,bj) = 0. _d 0
150     ENDDO
151     ENDDO
152    
153     IF ( thSIce_diffK .GT. 0. ) THEN
154     CALL THSICE_DIFFUSION(
155     I maskOce,
156     U uIce, vIce,
157     I bi, bj, myTime, myIter, myThid )
158     ENDIF
159    
160     IF ( thSIce_multiDimAdv ) THEN
161    
162     C- Calculate ice transports through tracer cell faces.
163     DO j=1-Oly,sNy+Oly
164     DO i=1-Olx+1,sNx+Olx
165     uTrIce(i,j) = uIce(i,j)*_dyG(i,j,bi,bj)
166     & *maskOce(i-1,j)*maskOce(i,j)
167     ENDDO
168     ENDDO
169     DO j=1-Oly+1,sNy+Oly
170     DO i=1-Olx,sNx+Olx
171     vTrIce(i,j) = vIce(i,j)*_dxG(i,j,bi,bj)
172     & *maskOce(i,j-1)*maskOce(i,j)
173     ENDDO
174     ENDDO
175    
176     C-- Fractional area
177     DO j=1-Oly,sNy+Oly
178     DO i=1-Olx,sNx+Olx
179     iceFrc(i,j) = iceMask(i,j,bi,bj)
180     ENDDO
181     ENDDO
182     CALL THSICE_ADVECTION(
183     I GAD_SI_FRAC, thSIceAdvScheme, .TRUE.,
184     I uTrIce, vTrIce, maskOce, thSIce_deltaT, areaEpsil,
185     U iceVol, iceFrc,
186     O uTrans, vTrans,
187     I bi, bj, myTime, myIter, myThid )
188    
189     C-- Snow thickness
190     DO j=1-Oly,sNy+Oly
191     DO i=1-Olx,sNx+Olx
192     iceVol(i,j) = iceMask(i,j,bi,bj)*rA(i,j,bi,bj)
193     ENDDO
194     ENDDO
195     CALL THSICE_ADVECTION(
196     I GAD_SI_HSNOW, thSIceAdvScheme, .FALSE.,
197     I uTrans, vTrans, maskOce, thSIce_deltaT, areaEpsil,
198     U iceVol, snowHeight(1-Olx,1-Oly,bi,bj),
199     O afx, afy,
200     I bi, bj, myTime, myIter, myThid )
201    
202     C-- sea-ice Thickness
203     DO j=1-Oly,sNy+Oly
204     DO i=1-Olx,sNx+Olx
205     iceVol(i,j) = iceMask(i,j,bi,bj)*rA(i,j,bi,bj)
206     oldVol(i,j) = iceVol(i,j)*iceHeight(i,j,bi,bj)
207     ENDDO
208     ENDDO
209     CALL THSICE_ADVECTION(
210     I GAD_SI_HICE, thSIceAdvScheme, .FALSE.,
211     I uTrans, vTrans, maskOce, thSIce_deltaT, areaEpsil,
212     U iceVol, iceHeight(1-Olx,1-Oly,bi,bj),
213     O uTrIce, vTrIce,
214     I bi, bj, myTime, myIter, myThid )
215     #ifdef ALLOW_DBUG_THSICE
216     IF ( dBugFlag ) THEN
217     sumVar1 = 0.
218     sumVar2 = 0.
219     DO j=1,sNy
220     DO i=1,sNx
221     C- Check that updated iceVol = iceFrc*rA
222     tmpVar = ABS(iceVol(i,j)-iceFrc(i,j)*rA(i,j,bi,bj))
223     IF ( tmpVar.GT.0. ) THEN
224     sumVar1 = sumVar1 + 1.
225     sumVar2 = sumVar2 + tmpVar
226     ENDIF
227     IF ( tmpVar.GT.vol_Epsil ) THEN
228     WRITE(6,'(A,2I4,2I2,I12)') 'ARE_ADV: ij,bij,it=',
229     & i,j,bi,bj,myIter
230     WRITE(6,'(2(A,1P2E14.6))') 'ARE_ADV: iceVol,iceFrc*rA=',
231     & iceVol(i,j),iceFrc(i,j)*rA(i,j,bi,bj),
232     & ' , diff=', tmpVar
233     ENDIF
234     IF ( dBug(i,j,bi,bj) ) THEN
235     WRITE(6,'(A,2I4,2I2,I12)') 'ICE_ADV: ij,bij,it=',
236     & i,j,bi,bj,myIter
237     WRITE(6,'(2(A,1P2E14.6))')
238     & 'ICE_ADV: uIce=', uIce(i,j), uIce(i+1,j),
239     & ' , vIce=', vIce(i,j), vIce(i,j+1)
240     WRITE(6,'(2(A,1P2E14.6))')
241     c & 'ICE_ADV: heff_b,a=', HEFF(i,j,2,bi,bj),HEFF(i,j,1,bi,bj)
242     c WRITE(6,'(A,1P4E14.6)') 'ICE_ADV: mFx=', gFld(i,j)
243     ENDIF
244     ENDDO
245     ENDDO
246     IF ( sumVar2.GT.vol_Epsil )
247     & WRITE(6,'(A,2I2,I10,A,I4,1P2E14.6)') 'ARE_ADV: bij,it:',
248     & bi,bj,myIter, ' ; Npts,aveDiff,Epsil=',
249     & INT(sumVar1),sumVar2/sumVar1,vol_Epsil
250     ENDIF
251     #endif
252     #ifdef ALLOW_DIAGNOSTICS
253     C-- Diagnosse advective fluxes (ice-fraction, snow & ice thickness):
254     IF ( useDiagnostics ) THEN
255     diagSufx = THSICE_DIAG_SUFX( GAD_SI_FRAC, myThid )
256     diagName = 'ADVx'//diagSufx
257     CALL DIAGNOSTICS_FILL( uTrans, diagName, 1,1,2,bi,bj, myThid )
258     diagName = 'ADVy'//diagSufx
259     CALL DIAGNOSTICS_FILL( vTrans, diagName, 1,1,2,bi,bj, myThid )
260    
261     diagSufx = THSICE_DIAG_SUFX( GAD_SI_HSNOW, myThid )
262     diagName = 'ADVx'//diagSufx
263     CALL DIAGNOSTICS_FILL( afx, diagName, 1,1,2,bi,bj, myThid )
264     diagName = 'ADVy'//diagSufx
265     CALL DIAGNOSTICS_FILL( afy, diagName, 1,1,2,bi,bj, myThid )
266    
267     diagSufx = THSICE_DIAG_SUFX( GAD_SI_HICE, myThid )
268     diagName = 'ADVx'//diagSufx
269     CALL DIAGNOSTICS_FILL( uTrIce, diagName, 1,1,2,bi,bj, myThid )
270     diagName = 'ADVy'//diagSufx
271     CALL DIAGNOSTICS_FILL( vTrIce, diagName, 1,1,2,bi,bj, myThid )
272     ENDIF
273     #endif
274    
275     C-- Enthalpy in layer 1
276     DO j=1-Oly,sNy+Oly
277     DO i=1-Olx,sNx+Olx
278     iceVol(i,j) = oldVol(i,j)
279     ENDDO
280     ENDDO
281     CALL THSICE_ADVECTION(
282     I GAD_SI_QICE1, thSIceAdvScheme, .FALSE.,
283     I uTrIce, vTrIce, maskOce, thSIce_deltaT, vol_Epsil,
284     U iceVol, Qice1(1-Olx,1-Oly,bi,bj),
285     O afx, afy,
286     I bi, bj, myTime, myIter, myThid )
287     #ifdef ALLOW_DBUG_THSICE
288     IF ( dBugFlag ) THEN
289     DO j=1,sNy
290     DO i=1,sNx
291     IF ( dBug(i,j,bi,bj) ) THEN
292     c WRITE(6,'(A,1P4E14.6)') 'ICE_ADV: Qice1_b,a=',
293     c & Qice1(i,j,bi,bj),
294     c & ( iceFld(i,j) + thSIce_deltaT * gFld(i,j)
295     c & ) * recip_heff(i,j)
296     c WRITE(6,'(A,1P4E14.6)') 'ICE_ADV: q1Fx=', gFld(i,j)
297     ENDIF
298     ENDDO
299     ENDDO
300     ENDIF
301     #endif
302     #ifdef ALLOW_DIAGNOSTICS
303     IF ( useDiagnostics ) THEN
304     diagSufx = THSICE_DIAG_SUFX( GAD_SI_QICE1, myThid )
305     diagName = 'ADVx'//diagSufx
306     CALL DIAGNOSTICS_FILL( afx, diagName, 1,1,2,bi,bj, myThid )
307     diagName = 'ADVy'//diagSufx
308     CALL DIAGNOSTICS_FILL( afy, diagName, 1,1,2,bi,bj, myThid )
309     ENDIF
310     #endif
311    
312     C-- Enthalpy in layer 2
313     DO j=1-Oly,sNy+Oly
314     DO i=1-Olx,sNx+Olx
315     iceVol(i,j) = oldVol(i,j)
316     ENDDO
317     ENDDO
318     CALL THSICE_ADVECTION(
319     I GAD_SI_QICE2, thSIceAdvScheme, .FALSE.,
320     I uTrIce, vTrIce, maskOce, thSIce_deltaT, vol_Epsil,
321     U iceVol, Qice2(1-Olx,1-Oly,bi,bj),
322     O afx, afy,
323     I bi, bj, myTime, myIter, myThid )
324     #ifdef ALLOW_DBUG_THSICE
325     IF ( dBugFlag ) THEN
326     sumVar1 = 0.
327     sumVar2 = 0.
328     DO j=1,sNy
329     DO i=1,sNx
330     C- Check that updated iceVol = Hic*Frc*rA
331     tmpVar = ABS(iceVol(i,j)
332     & -iceHeight(i,j,bi,bj)*iceFrc(i,j)*rA(i,j,bi,bj))
333     IF ( tmpVar.GT.0. ) THEN
334     sumVar1 = sumVar1 + 1.
335     sumVar2 = sumVar2 + tmpVar
336     ENDIF
337     IF ( tmpVar.GT.vol_Epsil ) THEN
338     WRITE(6,'(A,2I4,2I2,I12)') 'VOL_ADV: ij,bij,it=',
339     & i,j,bi,bj,myIter
340     WRITE(6,'(2(A,1P2E14.6))') 'VOL_ADV: iceVol,Hic*Frc*rA=',
341     & iceVol(i,j),iceHeight(i,j,bi,bj)*iceFrc(i,j)*rA(i,j,bi,bj),
342     & ' , diff=', tmpVar
343     ENDIF
344     IF ( dBug(i,j,bi,bj) ) THEN
345     c WRITE(6,'(A,1P4E14.6)') 'ICE_ADV: Qice2_b,a=',
346     c & Qice2(i,j,bi,bj),
347     c & ( iceFld(i,j) + thSIce_deltaT * gFld(i,j)
348     c & ) * recip_heff(i,j)
349     c WRITE(6,'(A,1P4E14.6)') 'ICE_ADV: q2Fx=', gFld(i,j)
350     ENDIF
351     ENDDO
352     ENDDO
353     IF ( sumVar2.GT.vol_Epsil )
354     & WRITE(6,'(A,2I2,I10,A,I4,1P2E14.6)') 'VOL_ADV: bij,it:',
355     & bi,bj,myIter, ' ; Npts,aveDiff,Epsil=',
356     & INT(sumVar1),sumVar2/sumVar1,vol_Epsil
357     ENDIF
358     #endif
359     #ifdef ALLOW_DIAGNOSTICS
360     IF ( useDiagnostics ) THEN
361     diagSufx = THSICE_DIAG_SUFX( GAD_SI_QICE2, myThid )
362     diagName = 'ADVx'//diagSufx
363     CALL DIAGNOSTICS_FILL( afx, diagName, 1,1,2,bi,bj, myThid )
364     diagName = 'ADVy'//diagSufx
365     CALL DIAGNOSTICS_FILL( afy, diagName, 1,1,2,bi,bj, myThid )
366     ENDIF
367     #endif
368    
369     C-- Update Ice Fraction, Ice thickness and snow thickness:
370     C and adjust sea-ice state if not enough ice.
371     DO j=1,sNy
372     DO i=1,sNx
373     C- store new effective ice-thickness
374     iceFld(i,j) = iceHeight(i,j,bi,bj)*iceFrc(i,j)
375     IF ( iceFld(i,j) .GE. minIcHeff ) THEN
376     C- where there is enough ice, ensure that Ice fraction is > minIcArea & < 1
377     IF ( iceFrc(i,j) .GT. 1. _d 0 ) THEN
378     iceMask(i,j,bi,bj) = 1. _d 0
379     iceHeight(i,j,bi,bj) = iceFld(i,j)
380     snowHeight(i,j,bi,bj) = snowHeight(i,j,bi,bj)*iceFrc(i,j)
381     ELSEIF ( iceFrc(i,j) .LT. minIcArea ) THEN
382     iceMask(i,j,bi,bj) = minIcArea
383     iceHeight(i,j,bi,bj) = iceFld(i,j)*r_minArea
384     snowHeight(i,j,bi,bj) = snowHeight(i,j,bi,bj)
385     & *iceFrc(i,j)*r_minArea
386     ELSE
387     iceMask(i,j,bi,bj) = iceFrc(i,j)
388     ENDIF
389     ELSE
390 jmc 1.2 C- Not enough ice, melt the tiny amount of snow & ice:
391 jmc 1.1 C and return frsh-water, salt & energy to the ocean (flx > 0 = into ocean)
392 jmc 1.2 C- - Note: using 1rst.Order Upwind, I can get the same results as when
393     C using seaice_advdiff (with SEAICEadvScheme=1) providing I comment
394     C out the following lines (and then loose conservation).
395     C- -
396 jmc 1.1 oceFWfx(i,j,bi,bj) = ( rhos*snowHeight(i,j,bi,bj)
397     & +rhoi*iceHeight(i,j,bi,bj) )
398     & *iceFrc(i,j)/thSIce_deltaT
399     oceSflx(i,j,bi,bj) =saltice*rhoi*iceFld(i,j)/thSIce_deltaT
400     oceQnet(i,j,bi,bj) = -qsnow*rhos*snowHeight(i,j,bi,bj)
401     & *iceFrc(i,j)/thSIce_deltaT
402     & -( Qice1(i,j,bi,bj)
403     & +Qice2(i,j,bi,bj) )*0.5 _d 0
404     & *rhoi*iceFld(i,j)/thSIce_deltaT
405 jmc 1.2 C- -
406 jmc 1.1 c flx2oc (i,j) = flx2oc (i,j) +
407     c frw2oc (i,j) = frw2oc (i,j) +
408     c fsalt (i,j) = fsalt (i,j) +
409     iceMask (i,j,bi,bj) = 0. _d 0
410     iceHeight (i,j,bi,bj) = 0. _d 0
411     snowHeight(i,j,bi,bj) = 0. _d 0
412     Qice1 (i,j,bi,bj) = 0. _d 0
413     Qice2 (i,j,bi,bj) = 0. _d 0
414     snowAge (i,j,bi,bj) = 0. _d 0
415     ENDIF
416     ENDDO
417     ENDDO
418    
419     #ifdef ALLOW_DBUG_THSICE
420     IF ( dBugFlag ) THEN
421     DO j=1,sNy
422     DO i=1,sNx
423     IF ( dBug(i,j,bi,bj) ) THEN
424     WRITE(6,'(2(A,1P2E14.6))')
425     c & 'ICE_ADV: area_b,a=', AREA(i,j,2,bi,bj),AREA(i,j,1,bi,bj)
426     c WRITE(6,'(A,1P4E14.6)') 'ICE_ADV: mFx=', gFld(i,j)
427     ENDIF
428     ENDDO
429     ENDDO
430     ENDIF
431     #endif
432    
433     ELSE
434     C--- if not multiDimAdvection
435    
436     WRITE(msgBuf,'(2A)') 'S/R THSICE_ADVDIFF: ',
437     & 'traditional advection/diffusion not yet implemented'
438     CALL PRINT_ERROR( msgBuf , myThid)
439     WRITE(msgBuf,'(2A)') ' ',
440     & 'for ThSice variable Qice1, Qice2, SnowHeight. Sorry!'
441     CALL PRINT_ERROR( msgBuf , myThid)
442     STOP 'ABNORMAL: END: S/R THSICE_ADVDIFF'
443    
444     C--- end if multiDimAdvection
445     ENDIF
446    
447     #endif /* ALLOW_THSICE */
448    
449     RETURN
450     END

  ViewVC Help
Powered by ViewVC 1.1.22