/[MITgcm]/MITgcm/model/src/calc_surf_dr.F
ViewVC logotype

Contents of /MITgcm/model/src/calc_surf_dr.F

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


Revision 1.20 - (show annotations) (download)
Thu Jul 24 15:41:57 2014 UTC (9 years, 9 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint65z, checkpoint65x, checkpoint65y, checkpoint65r, checkpoint65s, checkpoint65p, checkpoint65q, checkpoint65v, checkpoint65w, checkpoint65t, checkpoint65u, checkpoint65j, checkpoint65k, checkpoint65h, checkpoint65i, checkpoint65n, checkpoint65l, checkpoint65m, checkpoint65b, checkpoint65c, checkpoint65a, checkpoint65f, checkpoint65g, checkpoint65d, checkpoint65e, checkpoint66g, checkpoint66f, checkpoint66e, checkpoint66d, checkpoint66c, checkpoint66b, checkpoint66a, checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, checkpoint66k, checkpoint66j, checkpoint66i, checkpoint66h, checkpoint65o, HEAD
Changes since 1.19: +36 -28 lines
allows hFacW,S to be larger than surrounding hFacC=1 @ edge of a step with
different kSurfC on either side (topo in p-coords, ice-shelf in z-coords)

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

  ViewVC Help
Powered by ViewVC 1.1.22