/[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.6 - (show annotations) (download)
Sun Feb 10 20:04:11 2002 UTC (22 years, 3 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint44e_post, checkpoint44f_post, checkpoint46b_post, chkpt44d_post, checkpoint44e_pre, checkpoint45d_post, checkpoint44h_pre, checkpoint46a_post, checkpoint45a_post, checkpoint44g_post, checkpoint45b_post, checkpoint46b_pre, release1_final_v1, checkpoint46, checkpoint46a_pre, checkpoint45c_post, checkpoint44h_post, checkpoint45, checkpoint44f_pre
Branch point for: release1_final
Changes since 1.5: +3 -2 lines
initialize to zero arrays in common blocs

1 C $Header: /u/gcmpack/models/MITgcmUV/model/src/calc_surf_dr.F,v 1.5 2002/02/10 00:44:37 jmc Exp $
2 C $Name: $
3
4 #include "CPP_OPTIONS.h"
5
6 CBOP
7 C !ROUTINE: CALC_SURF_DR
8 C !INTERFACE:
9 SUBROUTINE CALC_SURF_DR(etaFld,
10 I myTime, myIter, myThid )
11 C !DESCRIPTION: \bv
12 C *==========================================================*
13 C | SUBROUTINE CALC_SURF_DR
14 C | o Calculate the new surface level thickness according to
15 C | the surface r-position (Non-Linear Free-Surf)
16 C | o take decision if grid box becomes too thin or too thick
17 C *==========================================================*
18 C \ev
19
20 C !USES:
21 IMPLICIT NONE
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
29 C !INPUT/OUTPUT PARAMETERS:
30 C == Routine arguments ==
31 C myTime :: Current time in simulation
32 C myIter :: Current iteration number in simulation
33 C myThid :: Thread number for this instance of the routine.
34 C etaFld :: current eta field used to update the hFactor
35 _RL myTime
36 INTEGER myIter
37 INTEGER myThid
38 _RL etaFld(1-Olx:sNx+Olx,1-Oly:sNy+Oly,nSx,nSy)
39
40 #ifdef NONLIN_FRSURF
41
42 C !LOCAL VARIABLES:
43 C Local variables in common block
44 C Rmin_surf :: minimum r_value of the free surface position
45 C that satisfy the hFacInf criteria
46 COMMON /LOCAL_CALC_SURF_DR/ Rmin_surf
47 _RL Rmin_surf(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
48 C Local variables
49 C i,j,k,bi,bj :: loop counter
50 C rSurftmp :: free surface r-position that is used to compute hFac_surf
51 C adjust_nb_pt :: Nb of grid points where rSurf is adjusted (hFactInf)
52 C adjust_volum :: adjustment effect on the volume (domain size)
53 INTEGER i,j,bi,bj
54 INTEGER ks
55 _RL hFacInfMOM, Rmin_tmp, hFactmp, adjust_nb_pt, adjust_volum
56 _RL rSurftmp(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
57 _RS hhm, hhp
58 CHARACTER*(MAX_LEN_MBUF) suff
59 CEOP
60
61 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
62
63 IF (myIter.EQ.-1) THEN
64
65 hFacInfMOM = hFacInf
66
67 DO bj=myByLo(myThid), myByHi(myThid)
68 DO bi=myBxLo(myThid), myBxHi(myThid)
69
70 C-- Initialise arrays :
71 DO j=1-Oly,sNy+Oly
72 DO i=1-Olx,sNx+Olx
73 hFac_surfC(i,j,bi,bj) = 0.
74 hFac_surfW(i,j,bi,bj) = 0.
75 hFac_surfS(i,j,bi,bj) = 0.
76 PmEpR(i,j,bi,bj) = 0.
77 Rmin_surf(i,j,bi,bj) = Ro_surf(i,j,bi,bj)
78 ENDDO
79 ENDDO
80
81 C-- Compute the mimimum value of r_surf (used for computing hFac_surfC)
82 DO j=1,sNy
83 DO i=1,sNx
84 ks = ksurfC(i,j,bi,bj)
85 IF (ks.LE.Nr) THEN
86 Rmin_tmp = rF(ks+1)
87 IF ( ks.EQ.ksurfW(i,j,bi,bj))
88 & Rmin_tmp = MAX(Rmin_tmp, R_low(i-1,j,bi,bj))
89 IF ( ks.EQ.ksurfW(i+1,j,bi,bj))
90 & Rmin_tmp = MAX(Rmin_tmp, R_low(i+1,j,bi,bj))
91 IF ( ks.EQ.ksurfS(i,j,bi,bj))
92 & Rmin_tmp = MAX(Rmin_tmp, R_low(i,j-1,bi,bj))
93 IF ( ks.EQ.ksurfS(i,j+1,bi,bj))
94 & Rmin_tmp = MAX(Rmin_tmp, R_low(i,j+1,bi,bj))
95
96 Rmin_surf(i,j,bi,bj) =
97 & MAX( MAX(rF(ks+1),R_low(i,j,bi,bj)) + hFacInf*drF(ks),
98 & Rmin_tmp + hFacInfMOM*drF(ks)
99 & )
100 ENDIF
101 ENDDO
102 ENDDO
103
104 C- end bi,bj loop.
105 ENDDO
106 ENDDO
107
108 _EXCH_XY_R8( Rmin_surf, myThid )
109
110 C- end of initialization block
111 ENDIF
112
113 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
114
115 adjust_nb_pt = 0.
116 adjust_volum = 0.
117
118 DO bj=myByLo(myThid), myByHi(myThid)
119 DO bi=myBxLo(myThid), myBxHi(myThid)
120
121 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
122 C-- Compute the new fractional thickness of surface level (ksurfC):
123
124 DO j=0,sNy+1
125 DO i=0,sNx+1
126 rSurftmp(i,j) = Ro_surf(i,j,bi,bj)+etaFld(i,j,bi,bj)
127 ks = ksurfC(i,j,bi,bj)
128 IF (ks.LE.Nr) THEN
129 IF (rSurftmp(i,j) .LT. Rmin_surf(i,j,bi,bj)) THEN
130 C-- Needs to do something :
131 hFactmp = ( rSurftmp(i,j)-MAX(rF(ks+1),R_low(i,j,bi,bj))
132 & )*recip_drF(ks)
133 IF (hFactmp.LT.hFacInf) THEN
134 write(0,'(2A,6I4,I10)') 'WARNING: hFacC < hFacInf at:',
135 & ' i,j,k,bi,bj,Thid,Iter=',i,j,ks,bi,bj,myThid,myIter
136 ELSE
137 write(0,'(2A,6I4,I10)') 'WARNING: hFac < hFacInf near:',
138 & ' i,j,k,bi,bj,Thid,Iter=',i,j,ks,bi,bj,myThid,myIter
139 ENDIF
140 write(0,'(A,2F10.6,1PE14.6)') 'hFac_n-1,hFac_n,eta =',
141 & hfacC(i,j,ks,bi,bj), hFactmp, etaFld(i,j,bi,bj)
142 C-- Decide to STOP :
143 c write(0,'(2A)') 'STOP in CALC_SURF_DR :',
144 c & ' too SMALL hFac !'
145 c STOP 'ABNORMAL END: S/R CALC_SURF_DR'
146 C----------
147
148 C-- Continue with Rmin_surf:
149 IF ( i.GE.1.AND.i.LE.sNx .AND.
150 & j.GE.1.AND.j.LE.sNy ) THEN
151 adjust_nb_pt = adjust_nb_pt + 1.
152 adjust_volum = adjust_volum
153 & + rA(i,j,bi,bj)*(Rmin_surf(i,j,bi,bj)-rSurftmp(i,j))
154 ENDIF
155 rSurftmp(i,j) = Rmin_surf(i,j,bi,bj)
156 C----------
157 ENDIF
158
159 C-- Set hFac_surfC :
160 hFac_surfC(i,j,bi,bj) =
161 & ( rSurftmp(i,j) - MAX(rF(ks+1), R_low(i,j,bi,bj))
162 & )*recip_drF(ks)*maskC(i,j,ks,bi,bj)
163
164 IF (hFac_surfC(i,j,bi,bj).GT.hFacSup) THEN
165 C-- Usefull warning when hFac becomes very large:
166 write(0,'(2A,6I4,I10)') 'WARNING: hFacC > hFacSup at:',
167 & ' i,j,k,bi,bj,Thid,Iter=',i,j,ks,bi,bj,myThid,myIter
168 write(0,'(A,2F10.6,1PE14.6)') 'hFac_n-1,hFac_n,eta =',
169 & hfacC(i,j,ks,bi,bj), hFac_surfC(i,j,bi,bj),
170 & etaFld(i,j,bi,bj)
171 C-- Decide to STOP :
172 c write(0,'(2A)') 'STOP in CALC_SURF_DR :',
173 c & ' too LARGE hFac !'
174 c STOP 'ABNORMAL END: S/R CALC_SURF_DR'
175 C----------
176 ENDIF
177 ENDIF
178
179 ENDDO
180 ENDDO
181
182 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
183 C-- Compute fractional thickness of surface level, for U & V point:
184
185 DO j=1,sNy
186 DO i=1,sNx+1
187 ks = ksurfW(i,j,bi,bj)
188 IF (ks.LE.Nr) THEN
189 hhm = rF(ks)
190 IF(ks.EQ.ksurfC(i-1,j,bi,bj)) hhm = rSurftmp(i-1,j)
191 hhp = rF(ks)
192 IF(ks.EQ.ksurfC(i,j,bi,bj)) hhp = rSurftmp(i,j)
193 hFac_surfW(i,j,bi,bj) =
194 & ( MIN(hhm,hhp)
195 & - MAX(rF(ks+1),R_low(i-1,j,bi,bj),R_low(i,j,bi,bj))
196 & )*recip_drF(ks)*maskW(i,j,ks,bi,bj)
197 ENDIF
198 ENDDO
199 ENDDO
200
201 DO j=1,sNy+1
202 DO i=1,sNx
203 ks = ksurfS(i,j,bi,bj)
204 IF (ks.LE.Nr) THEN
205 hhm = rF(ks)
206 IF(ks.EQ.ksurfC(i,j-1,bi,bj)) hhm = rSurftmp(i,j-1)
207 hhp = rF(ks)
208 IF(ks.EQ.ksurfC(i,j,bi,bj)) hhp = rSurftmp(i,j)
209 hFac_surfS(i,j,bi,bj) =
210 & ( MIN(hhm,hhp)
211 & - MAX(rF(ks+1),R_low(i,j-1,bi,bj),R_low(i,j,bi,bj))
212 & )*recip_drF(ks)*maskS(i,j,ks,bi,bj)
213 ENDIF
214 ENDDO
215 ENDDO
216
217 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
218
219 C- end bi,bj loop.
220 ENDDO
221 ENDDO
222
223 C-- Global diagnostic :
224 _GLOBAL_SUM_R8( adjust_nb_pt , myThid )
225 _GLOBAL_SUM_R8( adjust_volum , myThid )
226 IF (adjust_nb_pt .GE.1.) THEN
227 _BEGIN_MASTER( myThid )
228 write(*,'(2(A,I10),1PE16.8)') ' SURF_ADJUSTMENT: Iter=',
229 & myIter, ' Nb_pts,Vol=', nint(adjust_nb_pt), adjust_volum
230 _END_MASTER( )
231 ENDIF
232
233 _EXCH_XY_R4(hFac_surfC, myThid )
234 CALL EXCH_UV_XY_RS(hFac_surfW,hFac_surfS,.FALSE.,myThid)
235
236 IF (useRealFreshWaterFlux .AND. myTime.EQ.startTime)
237 & _EXCH_XY_R4( PmEpR, myThid )
238
239 C-----
240 C Note: testing ksurfW,S is equivalent to a full height mask
241 C ==> no need for applying the mask here.
242 C and with "partial thin wall" ==> mask could be applied in S/R UPDATE_SURF_DR
243 C-----
244
245 WRITE(suff,'(I10.10)') myIter
246 c CALL WRITE_FLD_XY_RS('hFac_surfC.',suff,hFac_surfC,
247 c & myIter,myThid)
248
249 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
250 #endif /* NONLIN_FRSURF */
251
252 RETURN
253 END

  ViewVC Help
Powered by ViewVC 1.1.22