1 | MODULE zdfbfr |
---|
2 | !!====================================================================== |
---|
3 | !! *** MODULE zdfbfr *** |
---|
4 | !! Ocean physics: Bottom friction |
---|
5 | !!====================================================================== |
---|
6 | !! History : OPA ! 1997-06 (G. Madec, A.-M. Treguier) Original code |
---|
7 | !! NEMO 1.0 ! 2002-06 (G. Madec) F90: Free form and module |
---|
8 | !! 3.2 ! 2009-09 (A.C.Coward) Correction to include barotropic contribution |
---|
9 | !! 3.3 ! 2010-10 (C. Ethe, G. Madec) reorganisation of initialisation phase |
---|
10 | !!---------------------------------------------------------------------- |
---|
11 | |
---|
12 | !!---------------------------------------------------------------------- |
---|
13 | !! zdf_bfr : update momentum Kz at the ocean bottom due to the type of bottom friction chosen |
---|
14 | !! zdf_bfr_init : read in namelist and control the bottom friction parameters. |
---|
15 | !! zdf_bfr_2d : read in namelist and control the bottom friction parameters. |
---|
16 | !!---------------------------------------------------------------------- |
---|
17 | USE oce ! ocean dynamics and tracers variables |
---|
18 | USE dom_oce ! ocean space and time domain variables |
---|
19 | USE zdf_oce ! ocean vertical physics variables |
---|
20 | USE in_out_manager ! I/O manager |
---|
21 | USE lbclnk ! ocean lateral boundary conditions (or mpp link) |
---|
22 | USE lib_mpp ! distributed memory computing |
---|
23 | USE prtctl ! Print control |
---|
24 | |
---|
25 | IMPLICIT NONE |
---|
26 | PRIVATE |
---|
27 | |
---|
28 | PUBLIC zdf_bfr ! called by step.F90 |
---|
29 | PUBLIC zdf_bfr_init ! called by opa.F90 |
---|
30 | |
---|
31 | ! !!* Namelist nambfr: bottom friction namelist * |
---|
32 | INTEGER :: nn_bfr = 0 ! = 0/1/2/3 type of bottom friction |
---|
33 | REAL(wp) :: rn_bfri1 = 4.0e-4_wp ! bottom drag coefficient (linear case) |
---|
34 | REAL(wp) :: rn_bfri2 = 1.0e-3_wp ! bottom drag coefficient (non linear case) |
---|
35 | REAL(wp) :: rn_bfeb2 = 2.5e-3_wp ! background bottom turbulent kinetic energy [m2/s2] |
---|
36 | REAL(wp) :: rn_bfrien = 30._wp ! local factor to enhance coefficient bfri |
---|
37 | LOGICAL :: ln_bfr2d = .false. ! logical switch for 2D enhancement |
---|
38 | |
---|
39 | REAL(wp), DIMENSION(jpi,jpj) :: bfrcoef2d = 1.e-3_wp ! 2D bottom drag coefficient |
---|
40 | |
---|
41 | !! * Substitutions |
---|
42 | # include "vectopt_loop_substitute.h90" |
---|
43 | # include "domzgr_substitute.h90" |
---|
44 | !!---------------------------------------------------------------------- |
---|
45 | !! NEMO/OPA 3.3 , NEMO Consortium (2010) |
---|
46 | !! $Id$ |
---|
47 | !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) |
---|
48 | !!---------------------------------------------------------------------- |
---|
49 | CONTAINS |
---|
50 | |
---|
51 | SUBROUTINE zdf_bfr( kt ) |
---|
52 | !!---------------------------------------------------------------------- |
---|
53 | !! *** ROUTINE zdf_bfr *** |
---|
54 | !! |
---|
55 | !! ** Purpose : compute the bottom friction coefficient. |
---|
56 | !! |
---|
57 | !! ** Method : Calculate and store part of the momentum trend due |
---|
58 | !! to bottom friction following the chosen friction type |
---|
59 | !! (free-slip, linear, or quadratic). The component |
---|
60 | !! calculated here is multiplied by the bottom velocity in |
---|
61 | !! dyn_bfr to provide the trend term. |
---|
62 | !! The coefficients are updated at each time step only |
---|
63 | !! in the quadratic case. |
---|
64 | !! |
---|
65 | !! ** Action : bfrua , bfrva bottom friction coefficients |
---|
66 | !!---------------------------------------------------------------------- |
---|
67 | INTEGER, INTENT( in ) :: kt ! ocean time-step index |
---|
68 | !! |
---|
69 | INTEGER :: ji, jj ! dummy loop indices |
---|
70 | INTEGER :: ikbu, ikbv ! local integers |
---|
71 | REAL(wp) :: zvu, zuv, zecu, zecv ! temporary scalars |
---|
72 | !!---------------------------------------------------------------------- |
---|
73 | |
---|
74 | IF( nn_bfr == 2 ) THEN ! quadratic botton friction |
---|
75 | ! Calculate and store the quadratic bottom friction coefficient bfrua and bfrva |
---|
76 | ! where bfrUa = C_d*SQRT(u_bot^2 + v_bot^2 + e_b) {U=[u,v]} |
---|
77 | ! from these the trend due to bottom friction: -F_h/e3U can be calculated |
---|
78 | ! where -F_h/e3U_bot = bfrUa*Ub/e3U_bot {U=[u,v]} |
---|
79 | ! |
---|
80 | # if defined key_vectopt_loop |
---|
81 | DO jj = 1, 1 |
---|
82 | !CDIR NOVERRCHK |
---|
83 | DO ji = jpi+2, jpij-jpi-1 ! vector opt. (forced unrolling) |
---|
84 | # else |
---|
85 | !CDIR NOVERRCHK |
---|
86 | DO jj = 2, jpjm1 |
---|
87 | !CDIR NOVERRCHK |
---|
88 | DO ji = 2, jpim1 |
---|
89 | # endif |
---|
90 | ikbu = mbku(ji,jj) ! ocean bottom level at u- and v-points |
---|
91 | ikbv = mbkv(ji,jj) ! (deepest ocean u- and v-points) |
---|
92 | ! |
---|
93 | zvu = 0.25 * ( vn(ji,jj ,ikbu) + vn(ji+1,jj ,ikbu) & |
---|
94 | & + vn(ji,jj-1,ikbu) + vn(ji+1,jj-1,ikbu) ) |
---|
95 | zuv = 0.25 * ( un(ji,jj ,ikbv) + un(ji-1,jj ,ikbv) & |
---|
96 | & + un(ji,jj+1,ikbv) + un(ji-1,jj+1,ikbv) ) |
---|
97 | ! |
---|
98 | zecu = SQRT( un(ji,jj,ikbu) * un(ji,jj,ikbu) + zvu*zvu + rn_bfeb2 ) |
---|
99 | zecv = SQRT( vn(ji,jj,ikbv) * vn(ji,jj,ikbv) + zuv*zuv + rn_bfeb2 ) |
---|
100 | ! |
---|
101 | bfrua(ji,jj) = - 0.5_wp * ( bfrcoef2d(ji,jj) + bfrcoef2d(ji+1,jj ) ) * zecu |
---|
102 | bfrva(ji,jj) = - 0.5_wp * ( bfrcoef2d(ji,jj) + bfrcoef2d(ji ,jj+1) ) * zecv |
---|
103 | END DO |
---|
104 | END DO |
---|
105 | ! |
---|
106 | CALL lbc_lnk( bfrua, 'U', 1. ) ; CALL lbc_lnk( bfrva, 'V', 1. ) ! Lateral boundary condition |
---|
107 | ! |
---|
108 | IF(ln_ctl) CALL prt_ctl( tab2d_1=bfrua, clinfo1=' bfr - u: ', mask1=umask, & |
---|
109 | & tab2d_2=bfrva, clinfo2= ' v: ', mask2=vmask,ovlap=1 ) |
---|
110 | ENDIF |
---|
111 | ! |
---|
112 | END SUBROUTINE zdf_bfr |
---|
113 | |
---|
114 | |
---|
115 | SUBROUTINE zdf_bfr_init |
---|
116 | !!---------------------------------------------------------------------- |
---|
117 | !! *** ROUTINE zdf_bfr_init *** |
---|
118 | !! |
---|
119 | !! ** Purpose : Initialization of the bottom friction |
---|
120 | !! |
---|
121 | !! ** Method : Read the nammbf namelist and check their consistency |
---|
122 | !! called at the first timestep (nit000) |
---|
123 | !!---------------------------------------------------------------------- |
---|
124 | USE iom ! I/O module for ehanced bottom friction file |
---|
125 | !! |
---|
126 | INTEGER :: inum ! logical unit for enhanced bottom friction file |
---|
127 | INTEGER :: ji, jj ! dummy loop indexes |
---|
128 | INTEGER :: ikbu, ikbv ! temporary integers |
---|
129 | INTEGER :: ictu, ictv ! - - |
---|
130 | REAL(wp) :: zminbfr, zmaxbfr ! temporary scalars |
---|
131 | REAL(wp) :: zfru, zfrv ! - - |
---|
132 | !! |
---|
133 | NAMELIST/nambfr/ nn_bfr, rn_bfri1, rn_bfri2, rn_bfeb2, ln_bfr2d, rn_bfrien |
---|
134 | !!---------------------------------------------------------------------- |
---|
135 | |
---|
136 | REWIND ( numnam ) !* Read Namelist nam_bfr : bottom momentum boundary condition |
---|
137 | READ ( numnam, nambfr ) |
---|
138 | |
---|
139 | ! !* Parameter control and print |
---|
140 | IF(lwp) WRITE(numout,*) |
---|
141 | IF(lwp) WRITE(numout,*) 'zdf_bfr : momentum bottom friction' |
---|
142 | IF(lwp) WRITE(numout,*) '~~~~~~~' |
---|
143 | IF(lwp) WRITE(numout,*) ' Namelist nam_bfr : set bottom friction parameters' |
---|
144 | |
---|
145 | SELECT CASE (nn_bfr) |
---|
146 | |
---|
147 | CASE( 0 ) |
---|
148 | IF(lwp) WRITE(numout,*) ' free-slip ' |
---|
149 | bfrua(:,:) = 0.e0 |
---|
150 | bfrva(:,:) = 0.e0 |
---|
151 | ! |
---|
152 | CASE( 1 ) |
---|
153 | IF(lwp) WRITE(numout,*) ' linear botton friction' |
---|
154 | IF(lwp) WRITE(numout,*) ' friction coef. rn_bfri1 = ', rn_bfri1 |
---|
155 | IF( ln_bfr2d ) THEN |
---|
156 | IF(lwp) WRITE(numout,*) ' read coef. enhancement distribution from file ln_bfr2d = ', ln_bfr2d |
---|
157 | IF(lwp) WRITE(numout,*) ' coef rn_bfri2 enhancement factor rn_bfrien = ',rn_bfrien |
---|
158 | ENDIF |
---|
159 | ! |
---|
160 | bfrcoef2d(:,:) = rn_bfri1 ! initialize bfrcoef2d to the namelist variable |
---|
161 | ! |
---|
162 | IF(ln_bfr2d) THEN |
---|
163 | ! bfr_coef is a coefficient in [0,1] giving the mask where to apply the bfr enhancement |
---|
164 | CALL iom_open('bfr_coef.nc',inum) |
---|
165 | CALL iom_get (inum, jpdom_data, 'bfr_coef',bfrcoef2d,1) ! bfrcoef2d is used as tmp array |
---|
166 | CALL iom_close(inum) |
---|
167 | bfrcoef2d(:,:)= rn_bfri1 * ( 1 + rn_bfrien * bfrcoef2d(:,:) ) |
---|
168 | ENDIF |
---|
169 | bfrua(:,:) = - bfrcoef2d(:,:) |
---|
170 | bfrva(:,:) = - bfrcoef2d(:,:) |
---|
171 | ! |
---|
172 | CASE( 2 ) |
---|
173 | IF(lwp) WRITE(numout,*) ' quadratic botton friction' |
---|
174 | IF(lwp) WRITE(numout,*) ' friction coef. rn_bfri2 = ', rn_bfri2 |
---|
175 | IF(lwp) WRITE(numout,*) ' background tke rn_bfeb2 = ', rn_bfeb2 |
---|
176 | IF( ln_bfr2d ) THEN |
---|
177 | IF(lwp) WRITE(numout,*) ' read coef. enhancement distribution from file ln_bfr2d = ', ln_bfr2d |
---|
178 | IF(lwp) WRITE(numout,*) ' coef rn_bfri2 enhancement factor rn_bfrien = ',rn_bfrien |
---|
179 | ENDIF |
---|
180 | bfrcoef2d(:,:) = rn_bfri2 ! initialize bfrcoef2d to the namelist variable |
---|
181 | ! |
---|
182 | IF(ln_bfr2d) THEN |
---|
183 | ! bfr_coef is a coefficient in [0,1] giving the mask where to apply the bfr enhancement |
---|
184 | CALL iom_open('bfr_coef.nc',inum) |
---|
185 | CALL iom_get (inum, jpdom_data, 'bfr_coef',bfrcoef2d,1) ! bfrcoef2d is used as tmp array |
---|
186 | CALL iom_close(inum) |
---|
187 | bfrcoef2d(:,:)= rn_bfri2 * ( 1 + rn_bfrien * bfrcoef2d(:,:) ) |
---|
188 | ENDIF |
---|
189 | ! |
---|
190 | CASE DEFAULT |
---|
191 | IF(lwp) WRITE(ctmp1,*) ' bad flag value for nn_bfr = ', nn_bfr |
---|
192 | CALL ctl_stop( ctmp1 ) |
---|
193 | ! |
---|
194 | END SELECT |
---|
195 | ! |
---|
196 | ! Basic stability check on bottom friction coefficient |
---|
197 | ! |
---|
198 | ictu = 0 ! counter for stability criterion breaches at U-pts |
---|
199 | ictv = 0 ! counter for stability criterion breaches at V-pts |
---|
200 | zminbfr = 1.e10_wp ! initialise tracker for minimum of bottom friction coefficient |
---|
201 | zmaxbfr = -1.e10_wp ! initialise tracker for maximum of bottom friction coefficient |
---|
202 | ! |
---|
203 | # if defined key_vectopt_loop |
---|
204 | DO jj = 1, 1 |
---|
205 | !CDIR NOVERRCHK |
---|
206 | DO ji = jpi+2, jpij-jpi-1 ! vector opt. (forced unrolling) |
---|
207 | # else |
---|
208 | !CDIR NOVERRCHK |
---|
209 | DO jj = 2, jpjm1 |
---|
210 | !CDIR NOVERRCHK |
---|
211 | DO ji = 2, jpim1 |
---|
212 | # endif |
---|
213 | ikbu = mbku(ji,jj) ! deepest ocean level at u- and v-points |
---|
214 | ikbv = mbkv(ji,jj) |
---|
215 | zfru = 0.5 * fse3u(ji,jj,ikbu) / rdt |
---|
216 | zfrv = 0.5 * fse3v(ji,jj,ikbv) / rdt |
---|
217 | IF( ABS( bfrcoef2d(ji,jj) ) > zfru ) THEN |
---|
218 | IF( ln_ctl ) THEN |
---|
219 | WRITE(numout,*) 'BFR ', narea, nimpp+ji, njmpp+jj, ikbu |
---|
220 | WRITE(numout,*) 'BFR ', ABS( bfrcoef2d(ji,jj) ), zfru |
---|
221 | ENDIF |
---|
222 | ictu = ictu + 1 |
---|
223 | ENDIF |
---|
224 | IF( ABS( bfrcoef2d(ji,jj) ) > zfrv ) THEN |
---|
225 | IF( ln_ctl ) THEN |
---|
226 | WRITE(numout,*) 'BFR ', narea, nimpp+ji, njmpp+jj, ikbv |
---|
227 | WRITE(numout,*) 'BFR ', bfrcoef2d(ji,jj), zfrv |
---|
228 | ENDIF |
---|
229 | ictv = ictv + 1 |
---|
230 | ENDIF |
---|
231 | zminbfr = MIN( zminbfr, MIN( zfru, ABS( bfrcoef2d(ji,jj) ) ) ) |
---|
232 | zmaxbfr = MAX( zmaxbfr, MIN( zfrv, ABS( bfrcoef2d(ji,jj) ) ) ) |
---|
233 | END DO |
---|
234 | END DO |
---|
235 | IF( lk_mpp ) THEN |
---|
236 | CALL mpp_sum( ictu ) |
---|
237 | CALL mpp_sum( ictv ) |
---|
238 | CALL mpp_min( zminbfr ) |
---|
239 | CALL mpp_max( zmaxbfr ) |
---|
240 | ENDIF |
---|
241 | IF( lwp .AND. ictu + ictv > 0 ) THEN |
---|
242 | WRITE(numout,*) ' Bottom friction stability check failed at ', ictu, ' U-points ' |
---|
243 | WRITE(numout,*) ' Bottom friction stability check failed at ', ictv, ' V-points ' |
---|
244 | WRITE(numout,*) ' Bottom friction coefficient now ranges from: ', zminbfr, ' to ', zmaxbfr |
---|
245 | WRITE(numout,*) ' Bottom friction coefficient will be reduced where necessary' |
---|
246 | ENDIF |
---|
247 | ! |
---|
248 | END SUBROUTINE zdf_bfr_init |
---|
249 | |
---|
250 | !!====================================================================== |
---|
251 | END MODULE zdfbfr |
---|