/[MITgcm]/MITgcm_contrib/shelfice_remeshing/code/shelfice_remeshing.F
ViewVC logotype

Annotation of /MITgcm_contrib/shelfice_remeshing/code/shelfice_remeshing.F

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


Revision 1.1 - (hide annotations) (download)
Tue Jul 21 14:52:40 2015 UTC (10 years ago) by dgoldberg
Branch: MAIN
*** empty log message ***

1 dgoldberg 1.1 C $Header: /u/gcmpack/MITgcm/pkg/shelfice/shelfice_thermodynamics.F,v 1.44 2015/02/15 15:46:24 jmc Exp $
2     C $Name: $
3    
4     #include "SHELFICE_OPTIONS.h"
5     #ifdef ALLOW_AUTODIFF
6     # include "AUTODIFF_OPTIONS.h"
7     #endif
8     #ifdef ALLOW_CTRL
9     # include "CTRL_OPTIONS.h"
10     #endif
11    
12     CBOP
13     C !ROUTINE: SHELFICE_THERMODYNAMICS
14     C !INTERFACE:
15     SUBROUTINE SHELFICE_REMESHING(
16     I myTime, myIter, myThid )
17     C !DESCRIPTION: \bv
18     C *=============================================================*
19     C | S/R SHELFICE_THERMODYNAMICS
20     C | o shelf-ice main routine.
21     C | compute temperature and (virtual) salt flux at the
22     C | shelf-ice ocean interface
23     C |
24     C | stresses at the ice/water interface are computed in separate
25     C | routines that are called from mom_fluxform/mom_vecinv
26     C *=============================================================*
27     C \ev
28    
29     C !USES:
30     IMPLICIT NONE
31    
32     C === Global variables ===
33     #include "SIZE.h"
34     #include "EEPARAMS.h"
35     #include "PARAMS.h"
36     #include "GRID.h"
37     #include "DYNVARS.h"
38     #include "FFIELDS.h"
39     #include "SHELFICE.h"
40     #include "SHELFICE_COST.h"
41     #ifdef ALLOW_AUTODIFF
42     # include "CTRL_SIZE.h"
43     # include "ctrl.h"
44     # include "ctrl_dummy.h"
45     #endif /* ALLOW_AUTODIFF */
46     #ifdef ALLOW_AUTODIFF_TAMC
47     # ifdef SHI_ALLOW_GAMMAFRICT
48     # include "tamc.h"
49     # include "tamc_keys.h"
50     # endif /* SHI_ALLOW_GAMMAFRICT */
51     #endif /* ALLOW_AUTODIFF_TAMC */
52    
53     C === Functions ====
54     LOGICAL DIFFERENT_MULTIPLE
55     EXTERNAL DIFFERENT_MULTIPLE
56    
57     C !INPUT/OUTPUT PARAMETERS:
58     C === Routine arguments ===
59     C myIter :: iteration counter for this thread
60     C myTime :: time counter for this thread
61     C myThid :: thread number for this instance of the routine.
62     _RL myTime
63     INTEGER myIter
64     INTEGER myThid
65     _RL hFacCtmp
66     _RL hFacMnSz
67     _RS tmpfld(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
68    
69     C === Local variables ===
70     C I,J,K,Kp1,bi,bj :: loop counters
71     C tLoc, sLoc, pLoc :: local in-situ temperature, salinity, pressure
72     C theta/saltFreeze :: temperature and salinity of water at the
73     C ice-ocean interface (at the freezing point)
74     C freshWaterFlux :: local variable for fresh water melt flux due
75     C to melting in kg/m^2/s
76     C (negative density x melt rate)
77     C convertFW2SaltLoc:: local copy of convertFW2Salt
78     C cFac :: 1 for conservative form, 0, otherwise
79     C rFac :: realFreshWaterFlux factor
80     C dFac :: 0 for diffusive heat flux (Holland and Jenkins, 1999,
81     C eq21)
82     C 1 for advective and diffusive heat flux (eq22, 26, 31)
83     C fwflxFac :: only effective for dFac=1, 1 if we expect a melting
84     C fresh water flux, 0 otherwise
85     C auxiliary variables and abbreviations:
86     C a0, a1, a2, b, c0
87     C eps1, eps2, eps3, eps3a, eps4, eps5, eps6, eps7, eps8
88     C aqe, bqe, cqe, discrim, recip_aqe
89     C drKp1, recip_drLoc
90     INTEGER I,J,K,Kp1
91     INTEGER bi,bj
92     _RL tLoc(1:sNx,1:sNy)
93     _RL sLoc(1:sNx,1:sNy)
94     _RL pLoc(1:sNx,1:sNy)
95     _RL uLoc(1:sNx,1:sNy)
96     _RL vLoc(1:sNx,1:sNy)
97     _RL u_topdr(1:sNx+1,1:sNy+1,nSx,nSy)
98     _RL v_topdr(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
99     _RL thetaFreeze, saltFreeze, recip_Cp
100     _RL freshWaterFlux, convertFW2SaltLoc
101     _RL a0, a1, a2, b, c0
102     _RL eps1, eps2, eps3, eps3a, eps4, eps5, eps6, eps7, eps8
103     _RL cFac, rFac, dFac, fwflxFac
104     _RL aqe, bqe, cqe, discrim, recip_aqe
105     _RL drKp1, recip_drLoc
106     _RL recip_latentHeat
107     _RL tmpFac
108    
109    
110     _RL shiPr, shiSc, shiLo, recip_shiKarman, shiTwoThirds
111     _RL gammaTmoleT, gammaTmoleS, gammaTurb, gammaTurbConst
112     _RL ustar, ustarSq, etastar
113     CEOP
114     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
115    
116    
117    
118    
119     IF ( SHELFICERemeshFrequency .EQ. myTime) THEN
120     print *, 'JJ WOZ HERE',R_shelfIce
121     DO bj = myByLo(myThid), myByHi(myThid)
122     DO bi = myBxLo(myThid), myBxHi(myThid)
123     DO J = 1, sNy+1
124     DO I = 1, sNx+1
125     IF (etaN(I,J,bi,bj) .GT. 4.4 ) THEN
126     K = MAX(1,kTopC(I,J,bi,bj))
127     c salt(I,J,bi,bj,K-1)=salt(I,J,bi,bj,K)
128     c theta(I,J,bi,bj,K-1)=theta(I,J,bi,bj,K)
129     c uVel(I,J,bi,bj,K-1)=uVel(I,J,bi,bj,K)
130     c uVel(I+1,J,bi,bj,K-1)=uVel(I+1,J,bi,bj,K)
131     c vVel(I,J,bi,bj,K-1)=uVel(I,J,bi,bj,K)
132     c vVel(I,J+1,bi,bj,K-1)=uVel(I,J+1,bi,bj,K)
133     etaN(I,J,bi,bj) = etaN(I,J,bi,bj) - 10.0
134     R_shelfIce(I,J,bi,bj) = R_shelfIce(I,J,bi,bj) + 10.0
135     ENDIF
136     ENDDO
137     ENDDO
138     ENDDO
139     ENDDO
140    
141    
142     DO K=1, Nr
143     hFacMnSz=max( hFacMin, min(hFacMinDr*recip_drF(k),1. _d 0) )
144     DO J=1-OLy,sNy+OLy
145     DO I=1-OLx,sNx+OLx
146     c o Non-dimensional distance between grid boundary and model surface
147     hFacCtmp = (rF(k)-R_shelfIce(I,J,bi,bj))*recip_drF(K)
148     C o Reduce the previous fraction : substract the outside part.
149     hFacCtmp = hFacC(I,J,K,bi,bj) - max( hFacCtmp, 0. _d 0)
150     c o set to zero if empty Column :
151     hFacCtmp = max( hFacCtmp, 0. _d 0)
152     C o Impose minimum fraction and/or size (dimensional)
153     IF (hFacCtmp.LT.hFacMnSz) THEN
154     IF (hFacCtmp.LT.hFacMnSz*0.5) THEN
155     hFacC(I,J,K,bi,bj)=0.
156     ELSE
157     hFacC(I,J,K,bi,bj)=hFacMnSz
158     ENDIF
159     ELSE
160     hFacC(I,J,K,bi,bj)=hFacCtmp
161     ENDIF
162     ENDDO
163     ENDDO
164     ENDDO
165     c
166     cC- Re-calculate Reference surface position, taking into account hFacC
167     cC initialize Total column fluid thickness and surface k index
168     cC Note: if no fluid (continent) ==> kSurf = Nr+1
169     DO bj=myByLo(myThid), myByHi(myThid)
170     DO bi=myBxLo(myThid), myBxHi(myThid)
171     DO j=1-OLy,sNy+OLy
172     DO i=1-OLx,sNx+OLx
173     tmpfld(i,j,bi,bj) = 0.
174     kSurfC(i,j,bi,bj) = Nr+1
175     c maskH(i,j,bi,bj) = 0.
176     Ro_surf(i,j,bi,bj) = R_low(i,j,bi,bj)
177     DO k=Nr,1,-1
178     Ro_surf(i,j,bi,bj)=Ro_surf(i,j,bi,bj)
179     & +drF(k)*hFacC(i,j,k,bi,bj)
180     IF (hFacC(i,j,k,bi,bj).NE.0.) THEN
181     kSurfC(i,j,bi,bj) = k
182     c maskH(i,j,bi,bj) = 1.
183     tmpfld(i,j,bi,bj) = tmpfld(i,j,bi,bj) + 1.
184     ENDIF
185     ENDDO
186     kLowC(i,j,bi,bj) = 0
187     DO k= 1, Nr
188     IF (hFacC(i,j,k,bi,bj).NE.0) THEN
189     kLowC(i,j,bi,bj) = k
190     ENDIF
191     ENDDO
192     maskInC(i,j,bi,bj)= 0.
193     C Weird IF loop here JJ
194     IF ( kSurfC(i,j,bi,bj).LE.Nr ) THEN
195     maskInC(i,j,bi,bj)= 1.
196     ENDIF
197     ENDDO
198     ENDDO
199     C- end bi,bj loops.
200     ENDDO
201     ENDDO
202     c
203     c IF ( printDomain ) THEN
204     cc CALL PLOT_FIELD_XYRS( tmpfld,
205     c & 'Model Depths K Index' , -1, myThid )
206     c CALL PLOT_FIELD_XYRS(R_low,
207     c & 'Model R_low (ini_masks_etc)', -1, myThid )
208     c CALL PLOT_FIELD_XYRS(Ro_surf,
209     c & 'Model Ro_surf (ini_masks_etc)', -1, myThid )
210     c ENDIF
211     c
212     cC-- Calculate quantities derived from XY depth map
213     DO bj = myByLo(myThid), myByHi(myThid)
214     DO bi = myBxLo(myThid), myBxHi(myThid)
215     DO j=1-OLy,sNy+OLy
216     DO i=1-OLx,sNx+OLx
217     C Total fluid column thickness (r_unit) :
218     c Rcolumn(i,j,bi,bj)= Ro_surf(i,j,bi,bj) - R_low(i,j,bi,bj)
219     tmpfld(i,j,bi,bj) = Ro_surf(i,j,bi,bj) - R_low(i,j,bi,bj)
220     C Inverse of fluid column thickness (1/r_unit)
221     IF ( tmpfld(i,j,bi,bj) .LE. 0. ) THEN
222     recip_Rcol(i,j,bi,bj) = 0.
223     ELSE
224     recip_Rcol(i,j,bi,bj) = 1. _d 0 / tmpfld(i,j,bi,bj)
225     ENDIF
226     ENDDO
227     ENDDO
228     ENDDO
229     ENDDO
230     c
231     cC-- hFacW and hFacS (at U and V points)
232     DO bj=myByLo(myThid), myByHi(myThid)
233     DO bi=myBxLo(myThid), myBxHi(myThid)
234     DO k=1, Nr
235     DO j=1-OLy,sNy+OLy
236     hFacW(1-OLx,j,k,bi,bj)= 0.
237     DO i=2-OLx,sNx+OLx
238     hFacW(i,j,k,bi,bj)=
239     & MIN(hFacC(i,j,k,bi,bj),hFacC(i-1,j,k,bi,bj))
240     ENDDO
241     ENDDO
242     DO i=1-OLx,sNx+OLx
243     hFacS(i,1-OLy,k,bi,bj)= 0.
244     ENDDO
245     DO j=2-OLy,sNy+oly
246     DO i=1-OLx,sNx+OLx
247     hFacS(i,j,k,bi,bj)=
248     & MIN(hFacC(i,j,k,bi,bj),hFacC(i,j-1,k,bi,bj))
249     ENDDO
250     ENDDO
251     ENDDO
252     c
253     cC rLow & reference rSurf at Western & Southern edges (U and V points)
254     i = 1-OLx
255     DO j=1-OLy,sNy+OLy
256     rLowW (i,j,bi,bj) = 0.
257     rSurfW(i,j,bi,bj) = 0.
258     ENDDO
259     j = 1-OLy
260     DO i=1-OLx,sNx+OLx
261     rLowS (i,j,bi,bj) = 0.
262     rSurfS(i,j,bi,bj) = 0.
263     ENDDO
264     DO j=1-OLy,sNy+OLy
265     DO i=2-OLx,sNx+OLx
266     rLowW(i,j,bi,bj) =
267     & MAX( R_low(i-1,j,bi,bj), R_low(i,j,bi,bj) )
268     rSurfW(i,j,bi,bj) =
269     & MIN( Ro_surf(i-1,j,bi,bj), Ro_surf(i,j,bi,bj) )
270     rSurfW(i,j,bi,bj) =
271     & MAX( rSurfW(i,j,bi,bj), rLowW(i,j,bi,bj) )
272     ENDDO
273     ENDDO
274    
275     DO j=2-OLy,sNy+OLy
276     DO i=1-OLx,sNx+OLx
277     rLowS(i,j,bi,bj) =
278     & MAX( R_low(i,j-1,bi,bj), R_low(i,j,bi,bj) )
279     rSurfS(i,j,bi,bj) =
280     & MIN( Ro_surf(i,j-1,bi,bj), Ro_surf(i,j,bi,bj) )
281     rSurfS(i,j,bi,bj) =
282     & MAX( rSurfS(i,j,bi,bj), rLowS(i,j,bi,bj) )
283     ENDDO
284     ENDDO
285     C- end bi,bj loops.
286     ENDDO
287     ENDDO
288     CALL EXCH_UV_XYZ_RS(hFacW,hFacS,.FALSE.,myThid)
289     CALL EXCH_UV_XY_RS( rSurfW, rSurfS, .FALSE., myThid )
290     CALL EXCH_UV_XY_RS( rLowW, rLowS, .FALSE., myThid )
291     c
292     cC-- Addtional closing of Western and Southern grid-cell edges: for example,
293     cC a) might add some "thin walls" in specific location
294     cC-- b) close non-periodic N & S boundaries of lat-lon grid at the N/S poles.
295     CALL ADD_WALLS2MASKS( myThid )
296     cC-- Calculate surface k index for interface W & S (U & V points)
297     DO bj=myByLo(myThid), myByHi(myThid)
298     DO bi=myBxLo(myThid), myBxHi(myThid)
299     DO j=1-OLy,sNy+OLy
300     DO i=1-OLx,sNx+OLx
301     kSurfW(i,j,bi,bj) = Nr+1
302     kSurfS(i,j,bi,bj) = Nr+1
303     DO k=Nr,1,-1
304     IF (hFacW(i,j,k,bi,bj).NE.0.) kSurfW(i,j,bi,bj) = k
305     IF (hFacS(i,j,k,bi,bj).NE.0.) kSurfS(i,j,bi,bj) = k
306     ENDDO
307     maskInW(i,j,bi,bj)= 0.
308     cC Wierd if statements JJ
309     c
310     IF ( kSurfW(i,j,bi,bj).LE.Nr ) THEN
311     maskInW(i,j,bi,bj)= 1.
312     maskInS(i,j,bi,bj)= 0.
313     ENDIF
314     IF ( kSurfS(i,j,bi,bj).LE.Nr ) THEN
315     maskInS(i,j,bi,bj)= 1.
316     ENDIF
317     ENDDO
318     ENDDO
319     ENDDO
320     ENDDO
321    
322     c ELSE
323     #ifndef DISABLE_SIGMA_CODE
324     C--- Sigma and Hybrid-Sigma set-up:
325     CALL INI_SIGMA_HFAC( myThid )
326     c#endif /* DISABLE_SIGMA_CODE */
327     cc ENDIF
328     cC---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
329    
330     C-- Write to disk: Total Column Thickness & hFac(C,W,S):
331     C This I/O is now done in write_grid.F
332     c CALL WRITE_FLD_XY_RS( 'Depth',' ',tmpfld,0,myThid)
333     c CALL WRITE_FLD_XYZ_RS( 'hFacC',' ',hFacC,0,myThid)
334     c CALL WRITE_FLD_XYZ_RS( 'hFacW',' ',hFacW,0,myThid)
335     c CALL WRITE_FLD_XYZ_RS( 'hFacS',' ',hFacS,0,myThid)
336     c
337     IF ( printDomain ) THEN
338     CALL PLOT_FIELD_XYZRS( hFacC, 'hFacC' , Nr, 0, myThid )
339     CALL PLOT_FIELD_XYZRS( hFacW, 'hFacW' , Nr, 0, myThid )
340     CALL PLOT_FIELD_XYZRS( hFacS, 'hFacS' , Nr, 0, myThid )
341     ENDIF
342     C-- Masks and reciprocals of hFac[CWS]
343     DO bj = myByLo(myThid), myByHi(myThid)
344     DO bi = myBxLo(myThid), myBxHi(myThid)
345     DO k=1,Nr
346     DO j=1-OLy,sNy+OLy
347     DO i=1-OLx,sNx+OLx
348     IF (hFacC(i,j,k,bi,bj) .NE. 0. ) THEN
349     c recip_hFacC(i,j,k,bi,bj) = 1. _d 0 / hFacC(i,j,k,bi,bj)
350     c maskC(i,j,k,bi,bj) = 1.
351     ELSE
352     c recip_hFacC(i,j,k,bi,bj) = 0.
353     c maskC(i,j,k,bi,bj) = 0.
354     ENDIF
355     IF (hFacW(i,j,k,bi,bj) .NE. 0. ) THEN
356     c recip_hFacW(i,j,k,bi,bj) = 1. _d 0 / hFacW(i,j,k,bi,bj)
357     c maskW(i,j,k,bi,bj) = 1.
358     ELSE
359     c recip_hFacW(i,j,k,bi,bj) = 0.
360     c maskW(i,j,k,bi,bj) = 0.
361     ENDIF
362     IF (hFacS(i,j,k,bi,bj) .NE. 0. ) THEN
363     c recip_hFacS(i,j,k,bi,bj) = 1. _d 0 / hFacS(i,j,k,bi,bj)
364     c maskS(i,j,k,bi,bj) = 1.
365     ELSE
366     c recip_hFacS(i,j,k,bi,bj) = 0.
367     c maskS(i,j,k,bi,bj) = 0.
368     ENDIF
369     ENDDO
370     ENDDO
371     ENDDO
372    
373     c#ifdef NONLIN_FRSURF
374     C-- Save initial geometrical hFac factor into h0Fac (fixed in time):
375     C Note: In case 1 pkg modifies hFac (from packages_init_fixed, called
376     C later in sequence of calls) this pkg would need also to update h0Fac.
377     c DO k=1,Nr
378     c DO j=1-OLy,sNy+OLy
379     c DO i=1-OLx,sNx+OLx
380     c h0FacC(i,j,k,bi,bj) = _hFacC(i,j,k,bi,bj)
381     c h0FacW(i,j,k,bi,bj) = _hFacW(i,j,k,bi,bj)
382     c h0FacS(i,j,k,bi,bj) = _hFacS(i,j,k,bi,bj)
383     c ENDDO
384     c ENDDO
385     c ENDDO
386     #endif /* NONLIN_FRSURF */
387     C- end bi,bj loops.
388     ENDDO
389     ENDDO
390    
391    
392     ENDIF
393     RETURN
394     END

  ViewVC Help
Powered by ViewVC 1.1.22