/[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.11 - (show annotations) (download)
Thu Jul 13 20:48:47 2006 UTC (17 years, 10 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint58m_post, checkpoint58o_post, checkpoint58p_post, checkpoint58n_post
Changes since 1.10: +6 -6 lines
remove un-used variables (to reduce Nb of compiler warnings).

1 C $Header: /u/gcmpack/MITgcm/model/src/calc_surf_dr.F,v 1.10 2005/12/08 15:44:33 heimbach 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
44 C i,j,k,bi,bj :: loop counter
45 C rSurftmp :: free surface r-position that is used to compute hFac_surf
46 C adjust_nb_pt :: Nb of grid points where rSurf is adjusted (hFactInf)
47 C adjust_volum :: adjustment effect on the volume (domain size)
48 C numbWrite :: count the Number of warning written on STD-ERR file
49 C numbWrMax :: maximum Number of warning written on STD-ERR file
50 INTEGER i,j,bi,bj
51 INTEGER ks, numbWrite, numbWrMax
52 _RL hFactmp, adjust_nb_pt, adjust_volum
53 _RL rSurftmp(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
54 _RS hhm, hhp
55 CHARACTER*(MAX_LEN_MBUF) suff
56 CEOP
57 DATA numbWrite / 0 /
58 numbWrMax = Nx*Ny
59
60 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
61
62 adjust_nb_pt = 0.
63 adjust_volum = 0.
64
65 DO bj=myByLo(myThid), myByHi(myThid)
66 DO bi=myBxLo(myThid), myBxHi(myThid)
67
68 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
69 C-- Compute the new fractional thickness of surface level (ksurfC):
70
71 DO j=0,sNy+1
72 DO i=0,sNx+1
73 rSurftmp(i,j) = Ro_surf(i,j,bi,bj)+etaFld(i,j,bi,bj)
74 ks = ksurfC(i,j,bi,bj)
75 IF (ks.LE.Nr) THEN
76 IF (rSurftmp(i,j) .LT. Rmin_surf(i,j,bi,bj)) THEN
77 C-- Needs to do something :
78 IF (numbWrite.LE.numbWrMax) THEN
79 numbWrite = numbWrite + 1
80 hFactmp = ( rSurftmp(i,j)-MAX(rF(ks+1),R_low(i,j,bi,bj))
81 & )*recip_drF(ks)
82 IF (hFactmp.LT.hFacInf) THEN
83 WRITE(errorMessageUnit,'(2A,6I4,I10)')
84 & 'WARNING: hFacC < hFacInf at:',
85 & ' i,j,k,bi,bj,Thid,Iter=',i,j,ks,bi,bj,myThid,myIter
86 ELSE
87 WRITE(errorMessageUnit,'(2A,6I4,I10)')
88 & 'WARNING: hFac < hFacInf near:',
89 & ' i,j,k,bi,bj,Thid,Iter=',i,j,ks,bi,bj,myThid,myIter
90 ENDIF
91 WRITE(errorMessageUnit,'(A,2F10.6,1PE14.6)')
92 & 'hFac_n-1,hFac_n,eta =',
93 & hfacC(i,j,ks,bi,bj), hFactmp, etaFld(i,j,bi,bj)
94 ENDIF
95 C-- Decide to STOP :
96 c WRITE(errorMessageUnit,'(A)')
97 c & 'STOP in CALC_SURF_DR : too SMALL hFac !'
98 c STOP 'ABNORMAL END: S/R CALC_SURF_DR'
99 C----------
100
101 C-- Continue with Rmin_surf:
102 IF ( i.GE.1.AND.i.LE.sNx .AND.
103 & j.GE.1.AND.j.LE.sNy ) THEN
104 adjust_nb_pt = adjust_nb_pt + 1.
105 adjust_volum = adjust_volum
106 & + rA(i,j,bi,bj)*(Rmin_surf(i,j,bi,bj)-rSurftmp(i,j))
107 ENDIF
108 rSurftmp(i,j) = Rmin_surf(i,j,bi,bj)
109 C----------
110 ENDIF
111
112 C-- Set hFac_surfC :
113 hFac_surfC(i,j,bi,bj) =
114 & ( rSurftmp(i,j) - MAX(rF(ks+1), R_low(i,j,bi,bj))
115 & )*recip_drF(ks)*maskC(i,j,ks,bi,bj)
116
117 C-- Usefull warning when hFac becomes very large:
118 IF ( numbWrite.LE.numbWrMax .AND.
119 & hFac_surfC(i,j,bi,bj).GT.hFacSup ) THEN
120 numbWrite = numbWrite + 1
121 WRITE(errorMessageUnit,'(2A,6I4,I10)')
122 & 'WARNING: hFacC > hFacSup at:',
123 & ' i,j,k,bi,bj,Thid,Iter=',i,j,ks,bi,bj,myThid,myIter
124 WRITE(errorMessageUnit,'(A,2F10.6,1PE14.6)')
125 & 'hFac_n-1,hFac_n,eta =', hfacC(i,j,ks,bi,bj),
126 & hFac_surfC(i,j,bi,bj), etaFld(i,j,bi,bj)
127 ENDIF
128 C----------
129 ENDIF
130
131 ENDDO
132 ENDDO
133
134 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
135 C-- Compute fractional thickness of surface level, for U & V point:
136
137 DO j=1,sNy
138 DO i=1,sNx+1
139 ks = ksurfW(i,j,bi,bj)
140 IF (ks.LE.Nr) THEN
141 hhm = rF(ks)
142 IF(ks.EQ.ksurfC(i-1,j,bi,bj)) hhm = rSurftmp(i-1,j)
143 hhp = rF(ks)
144 IF(ks.EQ.ksurfC(i,j,bi,bj)) hhp = rSurftmp(i,j)
145 hFac_surfW(i,j,bi,bj) =
146 & ( MIN(hhm,hhp)
147 & - MAX(rF(ks+1),R_low(i-1,j,bi,bj),R_low(i,j,bi,bj))
148 & )*recip_drF(ks)*maskW(i,j,ks,bi,bj)
149 ENDIF
150 ENDDO
151 ENDDO
152
153 DO j=1,sNy+1
154 DO i=1,sNx
155 ks = ksurfS(i,j,bi,bj)
156 IF (ks.LE.Nr) THEN
157 hhm = rF(ks)
158 IF(ks.EQ.ksurfC(i,j-1,bi,bj)) hhm = rSurftmp(i,j-1)
159 hhp = rF(ks)
160 IF(ks.EQ.ksurfC(i,j,bi,bj)) hhp = rSurftmp(i,j)
161 hFac_surfS(i,j,bi,bj) =
162 & ( MIN(hhm,hhp)
163 & - MAX(rF(ks+1),R_low(i,j-1,bi,bj),R_low(i,j,bi,bj))
164 & )*recip_drF(ks)*maskS(i,j,ks,bi,bj)
165 ENDIF
166 ENDDO
167 ENDDO
168
169 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
170
171 C- end bi,bj loop.
172 ENDDO
173 ENDDO
174
175 C-- Global diagnostic :
176 _GLOBAL_SUM_R8( adjust_nb_pt , myThid )
177 _GLOBAL_SUM_R8( adjust_volum , myThid )
178 IF (adjust_nb_pt .GE.1.) THEN
179 _BEGIN_MASTER( myThid )
180 WRITE(standardMessageUnit,'(2(A,I10),1PE16.8)')
181 & ' SURF_ADJUSTMENT: Iter=', myIter,
182 & ' Nb_pts,Vol=', nint(adjust_nb_pt), adjust_volum
183 _END_MASTER( myThid )
184 ENDIF
185
186 _EXCH_XY_R4(hFac_surfC, myThid )
187 CALL EXCH_UV_XY_RS(hFac_surfW,hFac_surfS,.FALSE.,myThid)
188
189 C-----
190 C Note: testing ksurfW,S is equivalent to a full height mask
191 C ==> no need for applying the mask here.
192 C and with "partial thin wall" ==> mask could be applied in S/R UPDATE_SURF_DR
193 C-----
194
195 WRITE(suff,'(I10.10)') myIter
196 c CALL WRITE_FLD_XY_RS('hFac_surfC.',suff,hFac_surfC,
197 c & myIter,myThid)
198
199 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
200 #endif /* NONLIN_FRSURF */
201
202 RETURN
203 END

  ViewVC Help
Powered by ViewVC 1.1.22