/[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.17 - (show annotations) (download)
Fri May 20 01:23:11 2011 UTC (12 years, 11 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint62z, checkpoint62y, checkpoint63g, checkpoint63, checkpoint63l, checkpoint63m, checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63k, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63a, checkpoint63b, checkpoint63c
Changes since 1.16: +2 -2 lines
fix previous modif

1 C $Header: /u/gcmpack/MITgcm/model/src/calc_surf_dr.F,v 1.16 2011/05/20 01:11:59 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 = ( rSurftmp(i,j)-MAX(rF(ks+1),R_low(i,j,bi,bj))
91 & )*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----------
110
111 C-- Continue with Rmin_surf:
112 IF ( i.GE.1.AND.i.LE.sNx .AND.
113 & j.GE.1.AND.j.LE.sNy ) THEN
114 adjust_nb_pt = adjust_nb_pt + 1.
115 adjust_volum = adjust_volum
116 & + rA(i,j,bi,bj)*(Rmin_surf(i,j,bi,bj)-rSurftmp(i,j))
117 ENDIF
118 rSurftmp(i,j) = Rmin_surf(i,j,bi,bj)
119 C----------
120 ENDIF
121
122 C-- Set hFac_surfC :
123 hFac_surfC(i,j,bi,bj) =
124 & ( rSurftmp(i,j) - MAX(rF(ks+1), R_low(i,j,bi,bj))
125 & )*recip_drF(ks)*maskC(i,j,ks,bi,bj)
126
127 C-- Usefull warning when hFac becomes very large:
128 IF ( numbWrite.LE.numbWrMax .AND.
129 & hFac_surfC(i,j,bi,bj).GT.hFacSup ) THEN
130 numbWrite = numbWrite + 1
131 WRITE(errorMessageUnit,'(2A,6I4,I10)')
132 & 'WARNING: hFacC > hFacSup at:',
133 & ' i,j,k,bi,bj,Thid,Iter=',i,j,ks,bi,bj,myThid,myIter
134 WRITE(errorMessageUnit,'(A,2F10.6,1PE14.6)')
135 & 'hFac_n-1,hFac_n,eta =', hfacC(i,j,ks,bi,bj),
136 & hFac_surfC(i,j,bi,bj), etaFld(i,j,bi,bj)
137 ENDIF
138 C----------
139 ENDIF
140
141 ENDDO
142 ENDDO
143
144 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
145 C-- Compute fractional thickness of surface level, for U & V point:
146
147 DO j=1,sNy
148 DO i=1,sNx+1
149 ks = kSurfW(i,j,bi,bj)
150 IF (ks.LE.Nr) THEN
151 hhm = rF(ks)
152 IF(ks.EQ.kSurfC(i-1,j,bi,bj)) hhm = rSurftmp(i-1,j)
153 hhp = rF(ks)
154 IF(ks.EQ.kSurfC(i,j,bi,bj)) hhp = rSurftmp(i,j)
155 hFac_surfW(i,j,bi,bj) =
156 & ( MIN(hhm,hhp)
157 & - MAX(rF(ks+1),R_low(i-1,j,bi,bj),R_low(i,j,bi,bj))
158 & )*recip_drF(ks)*maskW(i,j,ks,bi,bj)
159 ENDIF
160 ENDDO
161 ENDDO
162
163 DO j=1,sNy+1
164 DO i=1,sNx
165 ks = kSurfS(i,j,bi,bj)
166 IF (ks.LE.Nr) THEN
167 hhm = rF(ks)
168 IF(ks.EQ.kSurfC(i,j-1,bi,bj)) hhm = rSurftmp(i,j-1)
169 hhp = rF(ks)
170 IF(ks.EQ.kSurfC(i,j,bi,bj)) hhp = rSurftmp(i,j)
171 hFac_surfS(i,j,bi,bj) =
172 & ( MIN(hhm,hhp)
173 & - MAX(rF(ks+1),R_low(i,j-1,bi,bj),R_low(i,j,bi,bj))
174 & )*recip_drF(ks)*maskS(i,j,ks,bi,bj)
175 ENDIF
176 ENDDO
177 ENDDO
178
179 #ifdef ALLOW_OBCS
180 C-- Apply OBC to hFac_surfW,S before the EXCH calls
181 IF ( useOBCS ) THEN
182 CALL OBCS_APPLY_SURF_DR(
183 I bi, bj, etaFld,
184 U hFac_surfC, hFac_surfW, hFac_surfS,
185 I myTime, myIter, myThid )
186 ENDIF
187 #endif /* ALLOW_OBCS */
188
189 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
190
191 C- end bi,bj loop.
192 ENDDO
193 ENDDO
194
195 C-- Global diagnostic :
196 _GLOBAL_SUM_RL( adjust_nb_pt , myThid )
197 _GLOBAL_SUM_RL( adjust_volum , myThid )
198 IF (adjust_nb_pt .GE.1.) THEN
199 _BEGIN_MASTER( myThid )
200 WRITE(standardMessageUnit,'(2(A,I10),1PE16.8)')
201 & ' SURF_ADJUSTMENT: Iter=', myIter,
202 & ' Nb_pts,Vol=', nint(adjust_nb_pt), adjust_volum
203 _END_MASTER( myThid )
204 ENDIF
205
206 _EXCH_XY_RS(hFac_surfC, myThid )
207 CALL EXCH_UV_XY_RS(hFac_surfW,hFac_surfS,.FALSE.,myThid)
208
209 C-----
210 C Note: testing kSurfW,S is equivalent to a full height mask
211 C ==> no need for applying the mask here.
212 C and with "partial thin wall" ==> mask could be applied in S/R UPDATE_SURF_DR
213 C-----
214
215 c IF ( myIter.GE.0 ) THEN
216 c WRITE(suff,'(I10.10)') myIter
217 c CALL WRITE_FLD_XY_RS( 'hFac_surfC.', suff, hFac_surfC,
218 c & myIter, myThid )
219 c ENDIF
220
221 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
222 #endif /* NONLIN_FRSURF */
223
224 RETURN
225 END

  ViewVC Help
Powered by ViewVC 1.1.22