1 | MODULE usrdef_zgr |
---|
2 | !!====================================================================== |
---|
3 | !! *** MODULE usrdef_zgr *** |
---|
4 | !! |
---|
5 | !! === DOME case === |
---|
6 | !! |
---|
7 | !! user defined : vertical coordinate system of a user configuration |
---|
8 | !!====================================================================== |
---|
9 | !! History : 4.0 ! 2020-12 (J. Chanut) Original code |
---|
10 | !!---------------------------------------------------------------------- |
---|
11 | |
---|
12 | !!---------------------------------------------------------------------- |
---|
13 | !! usr_def_zgr : user defined vertical coordinate system (required) |
---|
14 | !! zgr_z1d : reference 1D z-coordinate |
---|
15 | !!--------------------------------------------------------------------- |
---|
16 | USE oce ! ocean variables |
---|
17 | USE dom_oce , ONLY: mi0, mi1 ! ocean space and time domain |
---|
18 | USE dom_oce , ONLY: glamt, gphit ! ocean space and time domain |
---|
19 | USE usrdef_nam ! User defined : namelist variables |
---|
20 | ! |
---|
21 | USE in_out_manager ! I/O manager |
---|
22 | USE lbclnk ! ocean lateral boundary conditions (or mpp link) |
---|
23 | USE lib_mpp ! distributed memory computing library |
---|
24 | USE timing ! Timing |
---|
25 | |
---|
26 | IMPLICIT NONE |
---|
27 | PRIVATE |
---|
28 | |
---|
29 | PUBLIC usr_def_zgr ! called by domzgr.F90 |
---|
30 | |
---|
31 | !! * Substitutions |
---|
32 | # include "do_loop_substitute.h90" |
---|
33 | !!---------------------------------------------------------------------- |
---|
34 | !! NEMO/OCE 4.0 , NEMO Consortium (2018) |
---|
35 | !! $Id: usrdef_zgr.F90 14053 2020-12-03 13:48:38Z techene $ |
---|
36 | !! Software governed by the CeCILL license (see ./LICENSE) |
---|
37 | !!---------------------------------------------------------------------- |
---|
38 | CONTAINS |
---|
39 | |
---|
40 | SUBROUTINE usr_def_zgr( ld_zco , ld_zps , ld_sco , ld_isfcav, & ! type of vertical coordinate |
---|
41 | & pdept_1d, pdepw_1d, pe3t_1d , pe3w_1d , & ! 1D reference vertical coordinate |
---|
42 | & pdept , pdepw , & ! 3D t & w-points depth |
---|
43 | & pe3t , pe3u , pe3v , pe3f , & ! vertical scale factors |
---|
44 | & pe3w , pe3uw , pe3vw, & ! - - - |
---|
45 | & k_top , k_bot ) ! top & bottom ocean level |
---|
46 | !!--------------------------------------------------------------------- |
---|
47 | !! *** ROUTINE usr_def_zgr *** |
---|
48 | !! |
---|
49 | !! ** Purpose : User defined the vertical coordinates |
---|
50 | !! |
---|
51 | !!---------------------------------------------------------------------- |
---|
52 | LOGICAL , INTENT(in ) :: ld_zco, ld_zps, ld_sco ! vertical coordinate flags ( read in namusr_def ) |
---|
53 | LOGICAL , INTENT( out) :: ld_isfcav ! under iceshelf cavity flag |
---|
54 | REAL(wp), DIMENSION(:) , INTENT( out) :: pdept_1d, pdepw_1d ! 1D grid-point depth [m] |
---|
55 | REAL(wp), DIMENSION(:) , INTENT( out) :: pe3t_1d , pe3w_1d ! 1D grid-point depth [m] |
---|
56 | REAL(wp), DIMENSION(:,:,:), INTENT( out) :: pdept, pdepw ! grid-point depth [m] |
---|
57 | REAL(wp), DIMENSION(:,:,:), INTENT( out) :: pe3t , pe3u , pe3v , pe3f ! vertical scale factors [m] |
---|
58 | REAL(wp), DIMENSION(:,:,:), INTENT( out) :: pe3w , pe3uw, pe3vw ! i-scale factors |
---|
59 | INTEGER , DIMENSION(:,:) , INTENT( out) :: k_top, k_bot ! first & last ocean level |
---|
60 | ! |
---|
61 | INTEGER :: ji, jj, jk ! dummy indices |
---|
62 | INTEGER :: ik ! local integers |
---|
63 | REAL(wp) :: zfact, z1_jpkm1 ! local scalar |
---|
64 | REAL(wp) :: ze3min ! local scalar |
---|
65 | REAL(wp), DIMENSION(jpi,jpj) :: zht, zhu, zhv, zhf, z2d ! 2D workspace |
---|
66 | !!---------------------------------------------------------------------- |
---|
67 | ! |
---|
68 | IF(lwp) WRITE(numout,*) |
---|
69 | IF(lwp) WRITE(numout,*) 'usr_def_zgr : DOME configuration (z(ps)- or s-coordinate closed box ocean without cavities)' |
---|
70 | IF(lwp) WRITE(numout,*) '~~~~~~~~~~~' |
---|
71 | ! |
---|
72 | ! |
---|
73 | ! type of vertical coordinate |
---|
74 | ! --------------------------- |
---|
75 | ! already set in usrdef_nam.F90 by reading the namusr_def namelist except for ISF |
---|
76 | ld_isfcav = .FALSE. |
---|
77 | ! |
---|
78 | ! |
---|
79 | ! Build the vertical coordinate system |
---|
80 | ! ------------------------------------ |
---|
81 | ! |
---|
82 | ! !== UNmasked meter bathymetry ==! |
---|
83 | ! |
---|
84 | zht(:,:) = MAX( 600._wp, 600._wp - gphit(:,:)*1.e3*0.01 ) |
---|
85 | ! |
---|
86 | ! at u/v/f-point: averaging zht |
---|
87 | zhu(:,:) = 600_wp ; zhv(:,:) = 600_wp ; zhf(:,:) = 600_wp |
---|
88 | DO ji = 1, jpim1 |
---|
89 | zhu(ji,:) = 0.5_wp * ( zht(ji,:) + zht(ji+1,:) ) |
---|
90 | END DO |
---|
91 | DO jj = 1, jpjm1 |
---|
92 | zhv(:,jj) = 0.5_wp * ( zht(:,jj) + zht(:,jj+1) ) |
---|
93 | END DO |
---|
94 | DO jj = 1, jpjm1 |
---|
95 | DO ji = 1, jpim1 |
---|
96 | zhf(ji,jj) = 0.25_wp * ( zht(ji,jj ) + zht(ji+1,jj ) & |
---|
97 | & + zht(ji,jj+1) + zht(ji+1,jj+1) ) |
---|
98 | END DO |
---|
99 | END DO |
---|
100 | CALL lbc_lnk_multi( 'usrdef_zgr', zhu, 'U', 1.0_wp, zhv, 'V', 1.0_wp, zhf, 'F', 1.0_wp) |
---|
101 | ! |
---|
102 | CALL zgr_z1d( pdept_1d, pdepw_1d, pe3t_1d , pe3w_1d ) ! Reference z-coordinate system |
---|
103 | ! |
---|
104 | ! |
---|
105 | ! !== top masked level bathymetry ==! (all coordinates) |
---|
106 | ! |
---|
107 | ! no ocean cavities : top ocean level is ONE, except over land |
---|
108 | ! the ocean basin surrounded by land (1 grid-point) set through lbc_lnk call as jperio=0 |
---|
109 | z2d(:,:) = 1._wp ! surface ocean is the 1st level |
---|
110 | WHERE (gphit(:,:)>0._wp) z2d(:,:) = 0._wp |
---|
111 | ! Dig inlet: |
---|
112 | WHERE ((gphit(:,:)>0._wp).AND.(glamt(:,:)>-50._wp).AND.(glamt(:,:)<50._wp)) z2d(:,:) = 1._wp |
---|
113 | CALL lbc_lnk( 'usrdef_zgr', z2d, 'T', 1. ) ! closed basin since jperio = 0 (see userdef_nam.F90) |
---|
114 | k_top(:,:) = NINT( z2d(:,:) ) |
---|
115 | ! |
---|
116 | ! |
---|
117 | ! |
---|
118 | IF ( ld_sco ) THEN !== s-coordinate ==! (terrain-following coordinate) |
---|
119 | ! |
---|
120 | k_bot(:,:) = jpkm1 * k_top(:,:) !* bottom ocean = jpk-1 (here use k_top as a land mask) |
---|
121 | ! |
---|
122 | ! !* terrain-following coordinate with e3.(k)=cst) |
---|
123 | z1_jpkm1 = 1._wp / REAL( jpkm1 , wp) |
---|
124 | DO jk = 1, jpk |
---|
125 | pdept(:,:,jk) = zht(:,:) * z1_jpkm1 * ( REAL( jk , wp ) - 0.5_wp ) |
---|
126 | pdepw(:,:,jk) = zht(:,:) * z1_jpkm1 * ( REAL( jk-1 , wp ) ) |
---|
127 | pe3t (:,:,jk) = zht(:,:) * z1_jpkm1 |
---|
128 | pe3u (:,:,jk) = zhu(:,:) * z1_jpkm1 |
---|
129 | pe3v (:,:,jk) = zhv(:,:) * z1_jpkm1 |
---|
130 | pe3f (:,:,jk) = zhf(:,:) * z1_jpkm1 |
---|
131 | pe3w (:,:,jk) = zht(:,:) * z1_jpkm1 |
---|
132 | pe3uw(:,:,jk) = zhu(:,:) * z1_jpkm1 |
---|
133 | pe3vw(:,:,jk) = zhv(:,:) * z1_jpkm1 |
---|
134 | END DO |
---|
135 | ENDIF |
---|
136 | ! |
---|
137 | ! |
---|
138 | IF ( ld_zco ) THEN !== z-coordinate ==! (step-like topography) |
---|
139 | ! |
---|
140 | ! !* bottom ocean compute from the depth of grid-points |
---|
141 | k_bot(:,:) = jpkm1 * k_top(:,:) ! here use k_top as a land mask |
---|
142 | DO jk = 1, jpkm1 |
---|
143 | WHERE( pdept_1d(jk) < zht(:,:) .AND. zht(:,:) <= pdept_1d(jk+1) ) k_bot(:,:) = jk * k_top(:,:) |
---|
144 | END DO |
---|
145 | ! !* horizontally uniform coordinate (reference z-co everywhere) |
---|
146 | DO jk = 1, jpk |
---|
147 | pdept(:,:,jk) = pdept_1d(jk) |
---|
148 | pdepw(:,:,jk) = pdepw_1d(jk) |
---|
149 | pe3t (:,:,jk) = pe3t_1d (jk) |
---|
150 | pe3u (:,:,jk) = pe3t_1d (jk) |
---|
151 | pe3v (:,:,jk) = pe3t_1d (jk) |
---|
152 | pe3f (:,:,jk) = pe3t_1d (jk) |
---|
153 | pe3w (:,:,jk) = pe3w_1d (jk) |
---|
154 | pe3uw(:,:,jk) = pe3w_1d (jk) |
---|
155 | pe3vw(:,:,jk) = pe3w_1d (jk) |
---|
156 | END DO |
---|
157 | ENDIF |
---|
158 | ! |
---|
159 | ! |
---|
160 | IF ( ld_zps ) THEN !== zps-coordinate ==! (partial bottom-steps) |
---|
161 | ! |
---|
162 | ze3min = 0.1_wp * rn_dz |
---|
163 | IF(lwp) WRITE(numout,*) ' minimum thickness of the partial cells = 10 % of e3 = ', ze3min |
---|
164 | ! |
---|
165 | ! |
---|
166 | ! !* bottom ocean compute from the depth of grid-points |
---|
167 | k_bot(:,:) = jpkm1 |
---|
168 | DO jk = jpkm1, 1, -1 |
---|
169 | WHERE( zht(:,:) < pdepw_1d(jk) + ze3min ) k_bot(:,:) = jk-1 |
---|
170 | END DO |
---|
171 | ! |
---|
172 | ! !* vertical coordinate system |
---|
173 | DO jk = 1, jpk ! initialization to the reference z-coordinate |
---|
174 | pdept(:,:,jk) = pdept_1d(jk) |
---|
175 | pdepw(:,:,jk) = pdepw_1d(jk) |
---|
176 | pe3t (:,:,jk) = pe3t_1d (jk) |
---|
177 | pe3u (:,:,jk) = pe3t_1d (jk) |
---|
178 | pe3v (:,:,jk) = pe3t_1d (jk) |
---|
179 | pe3f (:,:,jk) = pe3t_1d (jk) |
---|
180 | pe3w (:,:,jk) = pe3w_1d (jk) |
---|
181 | pe3uw(:,:,jk) = pe3w_1d (jk) |
---|
182 | pe3vw(:,:,jk) = pe3w_1d (jk) |
---|
183 | END DO |
---|
184 | DO_2D( 1, 1, 1, 1 ) |
---|
185 | ik = k_bot(ji,jj) |
---|
186 | pdepw(ji,jj,ik+1) = MIN( zht(ji,jj) , pdepw_1d(ik+1) ) |
---|
187 | pe3t (ji,jj,ik ) = pdepw(ji,jj,ik+1) - pdepw(ji,jj,ik) |
---|
188 | pe3t (ji,jj,ik+1) = pe3t (ji,jj,ik ) |
---|
189 | ! |
---|
190 | pdept(ji,jj,ik ) = pdepw(ji,jj,ik ) + pe3t (ji,jj,ik ) * 0.5_wp |
---|
191 | pdept(ji,jj,ik+1) = pdepw(ji,jj,ik+1) + pe3t (ji,jj,ik+1) * 0.5_wp |
---|
192 | pe3w (ji,jj,ik+1) = pdept(ji,jj,ik+1) - pdept(ji,jj,ik) ! = pe3t (ji,jj,ik ) |
---|
193 | pe3w (ji,jj,ik ) = pdept(ji,jj,ik ) - pdept(ji,jj,ik-1) ! st caution ik > 1 |
---|
194 | END_2D |
---|
195 | ! ! bottom scale factors and depth at U-, V-, UW and VW-points |
---|
196 | ! ! usually Computed as the minimum of neighbooring scale factors |
---|
197 | pe3u (:,:,:) = pe3t(:,:,:) ! HERE DOME configuration : |
---|
198 | pe3v (:,:,:) = pe3t(:,:,:) ! e3 increases with i-index and identical with j-index |
---|
199 | pe3f (:,:,:) = pe3t(:,:,:) ! so e3 minimum of (i,i+1) points is (i) point |
---|
200 | pe3uw(:,:,:) = pe3w(:,:,:) ! in j-direction e3v=e3t and e3f=e3v |
---|
201 | pe3vw(:,:,:) = pe3w(:,:,:) ! ==>> no need of lbc_lnk calls |
---|
202 | ! |
---|
203 | ENDIF |
---|
204 | ! |
---|
205 | END SUBROUTINE usr_def_zgr |
---|
206 | |
---|
207 | |
---|
208 | SUBROUTINE zgr_z1d( pdept_1d, pdepw_1d, pe3t_1d , pe3w_1d ) ! 1D reference vertical coordinate |
---|
209 | !!---------------------------------------------------------------------- |
---|
210 | !! *** ROUTINE zgr_z1d *** |
---|
211 | !! |
---|
212 | !! ** Purpose : set the depth of model levels and the resulting |
---|
213 | !! vertical scale factors. |
---|
214 | !! |
---|
215 | !! ** Method : 1D z-coordinate system (use in all type of coordinate) |
---|
216 | !! The depth of model levels is set from dep(k), an analytical function: |
---|
217 | !! w-level: depw_1d = dep(k) |
---|
218 | !! t-level: dept_1d = dep(k+0.5) |
---|
219 | !! The scale factors are the discrete derivative of the depth: |
---|
220 | !! e3w_1d(jk) = dk[ dept_1d ] |
---|
221 | !! e3t_1d(jk) = dk[ depw_1d ] |
---|
222 | !! |
---|
223 | !! === Here constant vertical resolution === |
---|
224 | !! |
---|
225 | !! ** Action : - pdept_1d, pdepw_1d : depth of T- and W-point (m) |
---|
226 | !! - pe3t_1d , pe3w_1d : scale factors at T- and W-levels (m) |
---|
227 | !!---------------------------------------------------------------------- |
---|
228 | REAL(wp), DIMENSION(:), INTENT(out) :: pdept_1d, pdepw_1d ! 1D grid-point depth [m] |
---|
229 | REAL(wp), DIMENSION(:), INTENT(out) :: pe3t_1d , pe3w_1d ! 1D vertical scale factors [m] |
---|
230 | ! |
---|
231 | INTEGER :: jk ! dummy loop indices |
---|
232 | REAL(wp) :: zt, zw ! local scalar |
---|
233 | !!---------------------------------------------------------------------- |
---|
234 | ! |
---|
235 | IF(lwp) THEN ! Parameter print |
---|
236 | WRITE(numout,*) |
---|
237 | WRITE(numout,*) ' zgr_z1d : Reference vertical z-coordinates: uniform dz = ', rn_dz |
---|
238 | WRITE(numout,*) ' ~~~~~~~' |
---|
239 | ENDIF |
---|
240 | ! |
---|
241 | ! Reference z-coordinate (depth - scale factor at T- and W-points) ! Madec & Imbard 1996 function |
---|
242 | ! ---------------------- |
---|
243 | DO jk = 1, jpk |
---|
244 | zw = REAL( jk , wp ) |
---|
245 | zt = REAL( jk , wp ) + 0.5_wp |
---|
246 | pdepw_1d(jk) = rn_dz * REAL( jk-1 , wp ) |
---|
247 | pdept_1d(jk) = rn_dz * ( REAL( jk-1 , wp ) + 0.5_wp ) |
---|
248 | pe3w_1d (jk) = rn_dz |
---|
249 | pe3t_1d (jk) = rn_dz |
---|
250 | END DO |
---|
251 | ! |
---|
252 | IF(lwp) THEN ! control print |
---|
253 | WRITE(numout,*) |
---|
254 | WRITE(numout,*) ' Reference 1D z-coordinate depth and scale factors:' |
---|
255 | WRITE(numout, "(9x,' level gdept_1d gdepw_1d e3t_1d e3w_1d ')" ) |
---|
256 | WRITE(numout, "(10x, i4, 4f9.2)" ) ( jk, pdept_1d(jk), pdepw_1d(jk), pe3t_1d(jk), pe3w_1d(jk), jk = 1, jpk ) |
---|
257 | ENDIF |
---|
258 | ! |
---|
259 | END SUBROUTINE zgr_z1d |
---|
260 | |
---|
261 | !!====================================================================== |
---|
262 | END MODULE usrdef_zgr |
---|