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

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

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


Revision 1.1 - (hide annotations) (download)
Tue Oct 13 16:04:39 2015 UTC (9 years, 9 months ago) by dgoldberg
Branch: MAIN
CVS Tags: HEAD
*** empty log message ***

1 dgoldberg 1.1 C $Header: /u/gcmpack/MITgcm_contrib/shelfice_remeshing/AUTO/code/calc_surf_dr_JJ.F,v 1.1 2015/10/12 14:39:56 dgoldberg Exp $
2     C $Name: $
3    
4     #include "PACKAGES_CONFIG.h"
5     #include "CPP_OPTIONS.h"
6    
7     CBOP
8     C !ROUTINE: CALC_SURF_DR
9     C !INTERFACE:
10     SUBROUTINE CALC_SURF_DR_JJ( etaFld,
11     I myTime, myIter, myThid )
12     C !DESCRIPTION: \bv
13     C *==========================================================*
14     C | SUBROUTINE CALC_SURF_DR
15     C | o Calculate the new surface level thickness according to
16     C | the surface r-position (Non-Linear Free-Surf)
17     C | o take decision if grid box becomes too thin or too thick
18     C *==========================================================*
19     C \ev
20    
21     C !USES:
22     IMPLICIT NONE
23     C == Global variables
24     #include "SIZE.h"
25     #include "EEPARAMS.h"
26     #include "PARAMS.h"
27     #include "GRID.h"
28     #include "SURFACE.h"
29     #include "DYNVARS.h"
30    
31     C !INPUT/OUTPUT PARAMETERS:
32     C == Routine arguments ==
33     C etaFld :: current eta field used to update the hFactor
34     C myTime :: current time in simulation
35     C myIter :: current iteration number in simulation
36     C myThid :: thread number for this instance of the routine.
37     _RL etaFld(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
38     _RL myTime
39     INTEGER myIter
40     INTEGER myThid
41    
42     #ifdef NONLIN_FRSURF
43    
44     C !LOCAL VARIABLES:
45     C Local variables
46     C i,j,k,bi,bj :: loop counter
47     C rSurftmp :: free surface r-position that is used to compute hFac_surf
48     C adjust_nb_pt :: Nb of grid points where rSurf is adjusted (hFactInf)
49     C adjust_volum :: adjustment effect on the volume (domain size)
50     C numbWrite :: count the Number of warning written on STD-ERR file
51     C numbWrMax :: maximum Number of warning written on STD-ERR file
52     INTEGER i,j,bi,bj
53     INTEGER ks, numbWrite, numbWrMax
54     _RL hFactmp, adjust_nb_pt, adjust_volum
55     _RL rSurftmp(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
56     _RS hhm, hhp
57     c CHARACTER*(MAX_LEN_MBUF) suff
58     CEOP
59     DATA numbWrite / 0 /
60     numbWrMax = Nx*Ny
61    
62     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
63    
64     adjust_nb_pt = 0.
65     adjust_volum = 0.
66    
67    
68    
69    
70     DO bj=myByLo(myThid), myByHi(myThid)
71     DO bi=myBxLo(myThid), myBxHi(myThid)
72    
73     C-- before updating hFac_surfC/S/W save current fields
74     DO j=1-OLy,sNy+OLy
75     DO i=1-OLx,sNx+OLx
76     hFac_surfNm1C(i,j,bi,bj) = hFac_surfC(i,j,bi,bj)
77     hFac_surfNm1S(i,j,bi,bj) = hFac_surfS(i,j,bi,bj)
78     hFac_surfNm1W(i,j,bi,bj) = hFac_surfW(i,j,bi,bj)
79     ENDDO
80     ENDDO
81    
82    
83     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
84     C-- Compute the new fractional thickness of surface level (kSurfC):
85    
86     DO j=0,sNy+1
87     DO i=0,sNx+1
88     rSurftmp(i,j) = Ro_surf(i,j,bi,bj)+etaFld(i,j,bi,bj)
89     ks = kSurfC(i,j,bi,bj)
90     IF (ks.LE.Nr) THEN
91     IF ( rSurftmp(i,j).LT.Rmin_surf(i,j,bi,bj) ) THEN
92     C-- Needs to do something :
93     IF (numbWrite.LE.numbWrMax) THEN
94     numbWrite = numbWrite + 1
95     hFactmp = h0FacC(i,j,ks,bi,bj)
96     & + ( rSurftmp(i,j) - Ro_surf(i,j,bi,bj) )*recip_drF(ks)
97     IF (hFactmp.LT.hFacInf) THEN
98     WRITE(errorMessageUnit,'(2A,6I4,I10)')
99     & 'WARNING: hFacC < hFacInf at:',
100     & ' i,j,k,bi,bj,Thid,Iter=',i,j,ks,bi,bj,myThid,myIter
101     ELSE
102     WRITE(errorMessageUnit,'(2A,6I4,I10)')
103     & 'WARNING: hFac < hFacInf near:',
104     & ' i,j,k,bi,bj,Thid,Iter=',i,j,ks,bi,bj,myThid,myIter
105     ENDIF
106     WRITE(errorMessageUnit,'(A,2F10.6,1PE14.6)')
107     & 'hFac_n-1,hFac_n,eta =',
108     & hfacC(i,j,ks,bi,bj), hFactmp, etaFld(i,j,bi,bj)
109     ENDIF
110     C-- Decide to STOP :
111     c WRITE(errorMessageUnit,'(A)')
112     c & 'STOP in CALC_SURF_DR : too SMALL hFac !'
113     c STOP 'ABNORMAL END: S/R CALC_SURF_DR'
114     C-- Or continue with Rmin_surf:
115     IF ( i.GE.1.AND.i.LE.sNx .AND.
116     & j.GE.1.AND.j.LE.sNy ) THEN
117     adjust_nb_pt = adjust_nb_pt + 1.
118     adjust_volum = adjust_volum
119     & + rA(i,j,bi,bj)*(Rmin_surf(i,j,bi,bj)-rSurftmp(i,j))
120     ENDIF
121     rSurftmp(i,j) = Rmin_surf(i,j,bi,bj)
122     C----------
123     ENDIF
124    
125     C-- Set hFac_surfC :
126     hFac_surfC(i,j,bi,bj) = h0FacC(i,j,ks,bi,bj)
127     & + ( rSurftmp(i,j) - Ro_surf(i,j,bi,bj)
128     & )*recip_drF(ks)*maskC(i,j,ks,bi,bj)
129    
130     C-- Usefull warning when hFac becomes very large:
131     IF ( numbWrite.LE.numbWrMax .AND.
132     & hFac_surfC(i,j,bi,bj).GT.hFacSup ) THEN
133     numbWrite = numbWrite + 1
134     WRITE(errorMessageUnit,'(2A,6I4,I10)')
135     & 'WARNING: hFacC > hFacSup at:',
136     & ' i,j,k,bi,bj,Thid,Iter=',i,j,ks,bi,bj,myThid,myIter
137     WRITE(errorMessageUnit,'(A,2F10.6,1PE14.6)')
138     & 'hFac_n-1,hFac_n,eta =', hfacC(i,j,ks,bi,bj),
139     & hFac_surfC(i,j,bi,bj), etaFld(i,j,bi,bj)
140     ENDIF
141     C----------
142     ENDIF
143    
144     ENDDO
145     ENDDO
146    
147     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
148     C-- Compute fractional thickness of surface level, for U & V point:
149    
150     DO j=1,sNy
151     DO i=1,sNx+1
152     ks = kSurfW(i,j,bi,bj)
153     IF (ks.LE.Nr) THEN
154     C- allows hFacW to be larger than surrounding hFacC=1 @ edge of a step with
155     C different kSurfC on either side (topo in p-coords, ice-shelf in z-coords)
156     hhm = rSurftmp(i-1,j)
157     hhp = rSurftmp(i,j)
158     C- make sure hFacW is not larger than the 2 surrounding hFacC
159     c hhm = rF(ks)
160     c IF(ks.EQ.kSurfC(i-1,j,bi,bj)) hhm = rSurftmp(i-1,j)
161     c hhp = rF(ks)
162     c IF(ks.EQ.kSurfC(i,j,bi,bj)) hhp = rSurftmp(i,j)
163     hFac_surfW(i,j,bi,bj) = h0FacW(i,j,ks,bi,bj)
164     & + ( MIN(hhm,hhp)
165     & - MIN( Ro_surf(i-1,j,bi,bj), Ro_surf(i,j,bi,bj) )
166     & )*recip_drF(ks)*maskW(i,j,ks,bi,bj)
167     ENDIF
168     ENDDO
169     ENDDO
170    
171     DO j=1,sNy+1
172     DO i=1,sNx
173     ks = kSurfS(i,j,bi,bj)
174     IF (ks.LE.Nr) THEN
175     C- allows hFacS to be larger than surrounding hFacC=1 @ edge of a step with
176     C different kSurfC on either side (topo in p-coords, ice-shelf in z-coords)
177     hhm = Ro_surf(i,j-1,bi,bj)+etaN(i,j-1,bi,bj)
178    
179     hhp = Ro_surf(i,j,bi,bj)+etaN(i,j,bi,bj)
180    
181     C- make sure hFacS is not larger than the 2 surrounding hFacC
182     c hhm = rF(ks)
183     c IF(ks.EQ.kSurfC(i,j-1,bi,bj)) hhm = rSurftmp(i,j-1)
184     c hhp = rF(ks)
185     c IF(ks.EQ.kSurfC(i,j,bi,bj)) hhp = rSurftmp(i,j)
186     hFac_surfS(i,j,bi,bj) = h0FacS(i,j,ks,bi,bj)
187     & + ( MIN(hhm,hhp)
188     & - MIN( Ro_surf(i,j-1,bi,bj), Ro_surf(i,j,bi,bj) )
189     & )*recip_drF(ks)*maskS(i,j,ks,bi,bj)
190     ENDIF
191     ENDDO
192     ENDDO
193    
194    
195    
196     #ifdef ALLOW_OBCS
197     C-- Apply OBC to hFac_surfW,S before the EXCH calls
198     IF ( useOBCS ) THEN
199     CALL OBCS_APPLY_SURF_DR(
200     I bi, bj, etaFld,
201     U hFac_surfC, hFac_surfW, hFac_surfS,
202     I myTime, myIter, myThid )
203     ENDIF
204     #endif /* ALLOW_OBCS */
205    
206     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
207    
208     C- end bi,bj loop.
209     ENDDO
210     ENDDO
211    
212    
213    
214    
215     C-- Global diagnostic :
216     _GLOBAL_SUM_RL( adjust_nb_pt , myThid )
217     IF ( adjust_nb_pt.GE.1. ) THEN
218     _GLOBAL_SUM_RL( adjust_volum , myThid )
219     _BEGIN_MASTER( myThid )
220     WRITE(standardMessageUnit,'(2(A,I10),1PE16.8)')
221     & ' SURF_ADJUSTMENT: Iter=', myIter,
222     & ' Nb_pts,Vol=', nint(adjust_nb_pt), adjust_volum
223     _END_MASTER( myThid )
224     ENDIF
225    
226     _EXCH_XY_RS(hFac_surfC, myThid )
227     CALL EXCH_UV_XY_RS(hFac_surfW,hFac_surfS,.FALSE.,myThid)
228    
229     C-----
230     C Note: testing kSurfW,S is equivalent to a full height mask
231     C ==> no need for applying the mask here.
232     C and with "partial thin wall" ==> mask could be applied in S/R UPDATE_SURF_DR
233     C-----
234    
235     c IF ( myIter.GE.0 ) THEN
236     c WRITE(suff,'(I10.10)') myIter
237     c CALL WRITE_FLD_XY_RS( 'hFac_surfC.', suff, hFac_surfC,
238     c & myIter, myThid )
239     c ENDIF
240    
241     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
242     #endif /* NONLIN_FRSURF */
243    
244     RETURN
245     END

  ViewVC Help
Powered by ViewVC 1.1.22