/[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.3 - (show annotations) (download)
Wed Sep 26 18:09:14 2001 UTC (22 years, 8 months ago) by cnh
Branch: MAIN
CVS Tags: checkpoint43a-release1mods, release1_b1, checkpoint43, icebear5, icebear4, icebear3, icebear2, release1-branch_tutorials, ecco_c44_e19, ecco_c44_e18, ecco_c44_e17, ecco_c44_e16, release1-branch-end, ecco_ice2, ecco_ice1, ecco_c44_e22, ecco_c44_e25, ecco_c44_e23, ecco_c44_e20, ecco_c44_e21, ecco_c44_e26, ecco_c44_e27, ecco_c44_e24, ecco-branch-mod1, ecco-branch-mod2, ecco-branch-mod3, ecco-branch-mod4, ecco-branch-mod5, release1_beta1, checkpoint42, checkpoint41, checkpoint44, release1-branch_branchpoint
Branch point for: c24_e25_ice, release1-branch, release1, ecco-branch, icebear, release1_coupled
Changes since 1.2: +26 -20 lines
Bringing comments up to data and formatting for document extraction.

1 C $Header: /u/gcmpack/models/MITgcmUV/model/src/calc_surf_dr.F,v 1.2 2001/08/30 18:44:59 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,k,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.nIter0) 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 Rmin_surf(i,j,bi,bj) = Ro_surf(i,j,bi,bj)
77 ENDDO
78 ENDDO
79
80 C-- Compute the mimimum value of r_surf (used for computing hFac_surfC)
81 DO j=1,sNy
82 DO i=1,sNx
83 ks = ksurfC(i,j,bi,bj)
84 IF (ks.LE.Nr) THEN
85 Rmin_tmp = rF(ks+1)
86 IF ( ks.EQ.ksurfW(i,j,bi,bj))
87 & Rmin_tmp = MAX(Rmin_tmp, R_low(i-1,j,bi,bj))
88 IF ( ks.EQ.ksurfW(i+1,j,bi,bj))
89 & Rmin_tmp = MAX(Rmin_tmp, R_low(i+1,j,bi,bj))
90 IF ( ks.EQ.ksurfS(i,j,bi,bj))
91 & Rmin_tmp = MAX(Rmin_tmp, R_low(i,j-1,bi,bj))
92 IF ( ks.EQ.ksurfS(i,j+1,bi,bj))
93 & Rmin_tmp = MAX(Rmin_tmp, R_low(i,j+1,bi,bj))
94
95 Rmin_surf(i,j,bi,bj) =
96 & MAX( MAX(rF(ks+1),R_low(i,j,bi,bj)) + hFacInf*drF(ks),
97 & Rmin_tmp + hFacInfMOM*drF(ks)
98 & )
99 ENDIF
100 ENDDO
101 ENDDO
102
103 C- end bi,bj loop.
104 ENDDO
105 ENDDO
106
107 _EXCH_XY_R8( Rmin_surf, myThid )
108
109 C- end of initialization block
110 ENDIF
111
112 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
113
114 adjust_nb_pt = 0.
115 adjust_volum = 0.
116
117 DO bj=myByLo(myThid), myByHi(myThid)
118 DO bi=myBxLo(myThid), myBxHi(myThid)
119
120 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
121 C-- Compute the new fractional thickness of surface level (ksurfC):
122
123 DO j=0,sNy+1
124 DO i=0,sNx+1
125 rSurftmp(i,j) = Ro_surf(i,j,bi,bj)+etaFld(i,j,bi,bj)
126 ks = ksurfC(i,j,bi,bj)
127 IF (ks.LE.Nr) THEN
128 IF (rSurftmp(i,j) .LT. Rmin_surf(i,j,bi,bj)) THEN
129 C-- Needs to do something :
130 hFactmp = ( rSurftmp(i,j)-MAX(rF(ks+1),R_low(i,j,bi,bj))
131 & )*recip_drF(ks)
132 IF (hFactmp.LT.hFacInf) THEN
133 write(0,'(2A,6I4,I10)') 'WARNING: hFacC < hFacInf at:',
134 & ' i,j,k,bi,bj,Thid,Iter=',i,j,ks,bi,bj,myThid,myIter
135 ELSE
136 write(0,'(2A,6I4,I10)') 'WARNING: hFac < hFacInf near:',
137 & ' i,j,k,bi,bj,Thid,Iter=',i,j,ks,bi,bj,myThid,myIter
138 ENDIF
139 write(0,'(A,2F10.6,1PE14.6)') 'hFac_n-1,hFac_n,eta =',
140 & hfacC(i,j,ks,bi,bj), hFactmp, etaFld(i,j,bi,bj)
141 C-- Decide to STOP :
142 c write(0,'(2A)') 'STOP in CALC_SURF_DR :',
143 c & ' too SMALL hFac !'
144 c STOP 'ABNORMAL END: S/R CALC_SURF_DR'
145 C----------
146
147 C-- Continue with Rmin_surf:
148 IF ( i.GE.1.AND.i.LE.sNx .AND.
149 & j.GE.1.AND.j.LE.sNy ) THEN
150 adjust_nb_pt = adjust_nb_pt + 1.
151 adjust_volum = adjust_volum
152 & + rA(i,j,bi,bj)*(Rmin_surf(i,j,bi,bj)-rSurftmp(i,j))
153 ENDIF
154 rSurftmp(i,j) = Rmin_surf(i,j,bi,bj)
155 C----------
156 ENDIF
157
158 C-- Set hFac_surfC :
159 hFac_surfC(i,j,bi,bj) =
160 & ( rSurftmp(i,j) - MAX(rF(ks+1), R_low(i,j,bi,bj))
161 & )*recip_drF(ks)*maskC(i,j,ks,bi,bj)
162
163 IF (hFac_surfC(i,j,bi,bj).GT.hFacSup) THEN
164 C-- Usefull warning when hFac becomes very large:
165 write(0,'(2A,6I4,I10)') 'WARNING: hFacC > hFacSup at:',
166 & ' i,j,k,bi,bj,Thid,Iter=',i,j,ks,bi,bj,myThid,myIter
167 write(0,'(A,2F10.6,1PE14.6)') 'hFac_n-1,hFac_n,eta =',
168 & hfacC(i,j,ks,bi,bj), hFac_surfC(i,j,bi,bj),
169 & etaFld(i,j,bi,bj)
170 C-- Decide to STOP :
171 c write(0,'(2A)') 'STOP in CALC_SURF_DR :',
172 c & ' too LARGE hFac !'
173 c STOP 'ABNORMAL END: S/R CALC_SURF_DR'
174 C----------
175 ENDIF
176 ENDIF
177
178 ENDDO
179 ENDDO
180
181 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
182 C-- Compute fractional thickness of surface level, for U & V point:
183
184 DO j=1,sNy
185 DO i=1,sNx+1
186 ks = ksurfW(i,j,bi,bj)
187 IF (ks.LE.Nr) THEN
188 hhm = rF(ks)
189 IF(ks.EQ.ksurfC(i-1,j,bi,bj)) hhm = rSurftmp(i-1,j)
190 hhp = rF(ks)
191 IF(ks.EQ.ksurfC(i,j,bi,bj)) hhp = rSurftmp(i,j)
192 hFac_surfW(i,j,bi,bj) =
193 & ( MIN(hhm,hhp)
194 & - MAX(rF(ks+1),R_low(i-1,j,bi,bj),R_low(i,j,bi,bj))
195 & )*recip_drF(ks)*maskW(i,j,ks,bi,bj)
196 ENDIF
197 ENDDO
198 ENDDO
199
200 DO j=1,sNy+1
201 DO i=1,sNx
202 ks = ksurfS(i,j,bi,bj)
203 IF (ks.LE.Nr) THEN
204 hhm = rF(ks)
205 IF(ks.EQ.ksurfC(i,j-1,bi,bj)) hhm = rSurftmp(i,j-1)
206 hhp = rF(ks)
207 IF(ks.EQ.ksurfC(i,j,bi,bj)) hhp = rSurftmp(i,j)
208 hFac_surfS(i,j,bi,bj) =
209 & ( MIN(hhm,hhp)
210 & - MAX(rF(ks+1),R_low(i,j-1,bi,bj),R_low(i,j,bi,bj))
211 & )*recip_drF(ks)*maskS(i,j,ks,bi,bj)
212 ENDIF
213 ENDDO
214 ENDDO
215
216 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
217
218 C- end bi,bj loop.
219 ENDDO
220 ENDDO
221
222 C-- Global diagnostic :
223 _GLOBAL_SUM_R8( adjust_nb_pt , myThid )
224 _GLOBAL_SUM_R8( adjust_volum , myThid )
225 IF (adjust_nb_pt .GE.1.) THEN
226 _BEGIN_MASTER( myThid )
227 write(*,'(2(A,I10),1PE16.8)') ' SURF_ADJUSTMENT: Iter=',
228 & myIter, ' Nb_pts,Vol=', nint(adjust_nb_pt), adjust_volum
229 _END_MASTER( )
230 ENDIF
231
232 _EXCH_XY_R4(hFac_surfC, myThid )
233 CALL EXCH_UV_XY_RS(hFac_surfW,hFac_surfS,.FALSE.,myThid)
234
235 C-----
236 C Note: testing ksurfW,S is equivalent to a full height mask
237 C ==> no need for applying the mask here.
238 C and with "partial thin wall" ==> mask could be applied in S/R UPDATE_SURF_DR
239 C-----
240
241 WRITE(suff,'(I10.10)') myIter
242 c CALL WRITE_FLD_XY_RS('hFac_surfC.',suff,hFac_surfC,
243 c & myIter,myThid)
244
245 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
246 #endif /* NONLIN_FRSURF */
247
248 RETURN
249 END

  ViewVC Help
Powered by ViewVC 1.1.22