/[MITgcm]/MITgcm_contrib/ksnow/press_release/code/calc_surf_dr.F
ViewVC logotype

Contents of /MITgcm_contrib/ksnow/press_release/code/calc_surf_dr.F

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


Revision 1.1 - (show annotations) (download)
Fri Dec 16 15:23:18 2016 UTC (9 years ago) by ksnow
Branch: MAIN
CVS Tags: HEAD
Adding press_release core code files
C: ----------------------------------------------------------------------

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

  ViewVC Help
Powered by ViewVC 1.1.22