New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
zdfbfr.F90 in trunk/NEMO/OPA_SRC/ZDF – NEMO

source: trunk/NEMO/OPA_SRC/ZDF/zdfbfr.F90 @ 247

Last change on this file since 247 was 247, checked in by opalod, 19 years ago

CL : Add CVS Header and CeCILL licence information

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 8.7 KB
Line 
1MODULE zdfbfr
2   !!======================================================================
3   !!                       ***  MODULE  zdfbfr  ***
4   !! Ocean physics: Bottom friction
5   !!======================================================================
6
7   !!----------------------------------------------------------------------
8   !!   zdf_bfr      : update momentum Kz at the ocean bottom due to the
9   !!                  type of bottom friction chosen
10   !!   zdf_bfr_init : read in namelist and control the bottom friction
11   !!                  parameters.
12   !!----------------------------------------------------------------------
13   !! * Modules used
14   USE oce             ! ocean dynamics and tracers variables
15   USE dom_oce         ! ocean space and time domain variables
16   USE zdf_oce         ! ocean vertical physics variables
17   USE in_out_manager  ! I/O manager
18   USE lbclnk          ! ocean lateral boundary conditions (or mpp link)
19
20   IMPLICIT NONE
21   PRIVATE
22
23   !! * Routine accessibility
24   PUBLIC zdf_bfr    ! called by step.F90
25
26   !! * Module variables
27   INTEGER ::             & !!! ** bottom friction namelist (nambfr) **
28      nbotfr = 0             ! = 0/1/2/3 type of bottom friction
29   REAL(wp) ::            & !!! ** bottom friction namelist (nambfr) **
30      bfri1 = 4.0e-4_wp,  &  ! bottom drag coefficient (linear case)
31      bfri2 = 1.0e-3_wp,  &  ! bottom drag coefficient (non linear case)
32      bfeb2 = 2.5e-3_wp      ! background bottom turbulent kinetic energy  (m2/s2)
33
34   !! * Substitutions
35#  include "domzgr_substitute.h90"
36   !!----------------------------------------------------------------------
37   !!   OPA 9.0 , LOCEAN-IPSL (2005)
38   !! $Header$
39   !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt
40   !!----------------------------------------------------------------------
41
42CONTAINS
43
44   SUBROUTINE zdf_bfr( kt )
45      !!----------------------------------------------------------------------
46      !!                   ***  ROUTINE zdf_bfr  ***
47      !!                 
48      !! ** Purpose :   Applied the bottom friction through a specification of
49      !!      Kz at the ocean bottom.
50      !!
51      !! ** Method  :   Update the value of avmu and avmv at the ocean bottom
52      !!       level following the chosen friction type (no-slip, free-slip,
53      !!       linear, or quadratic)
54      !!
55      !! History :
56      !!   8.0  !  97-06  (G. Madec, A.-M. Treguier)  Original code
57      !!   8.5  !  02-06  (G. Madec)  F90: Free form and module
58      !!----------------------------------------------------------------------
59      !! * Arguments
60      INTEGER, INTENT( in ) ::   kt   ! ocean time-step index
61
62      !! * Local declarations
63      INTEGER ::   &
64         ji, jj,                   &  ! dummy loop indexes
65         ikbu, ikbv,               &  ! temporary integers
66         ikbum1, ikbvm1               !
67      REAL(wp) ::   &
68         zvu, zuv, zecu, zecv         ! temporary scalars
69      !!----------------------------------------------------------------------
70
71
72      IF( kt == nit000 )   CALL zdf_bfr_init
73
74
75      ! Compute avmu, avmv at the ocean bottom
76      ! --------------------------------------
77
78      SELECT CASE (nbotfr)
79
80      CASE( 0 )                 ! no-slip boundary condition
81# if defined key_vectopt_loop   &&   ! defined key_autotasking
82         jj = 1
83         DO ji = jpi+2, jpij-jpi-1   ! vector opt. (forced unrolling)
84# else
85         DO jj = 2, jpjm1
86            DO ji = 2, jpim1
87# endif
88               ikbu   = MIN( mbathy(ji+1,jj  ), mbathy(ji,jj) )
89               ikbv   = MIN( mbathy(ji  ,jj+1), mbathy(ji,jj) )
90               ikbum1 = MAX( ikbu-1, 1 )
91               ikbvm1 = MAX( ikbv-1, 1 )
92               avmu(ji,jj,ikbu) = 2. * avmu(ji,jj,ikbum1)
93               avmv(ji,jj,ikbv) = 2. * avmv(ji,jj,ikbvm1)
94# if ! defined key_vectopt_loop   ||   defined key_autotasking
95            END DO
96# endif
97         END DO
98
99      CASE( 1 )                 ! linear botton friction
100# if defined key_vectopt_loop   &&   ! defined key_autotasking
101         jj = 1
102         DO ji = jpi+2, jpij-jpi-1   ! vector opt. (forced unrolling)
103# else
104         DO jj = 2, jpjm1
105            DO ji = 2, jpim1
106# endif
107               ikbu = MIN( mbathy(ji+1,jj), mbathy(ji,jj) )
108               ikbv = MIN( mbathy(ji,jj+1), mbathy(ji,jj) )
109               avmu(ji,jj,ikbu) = bfri1 * fse3uw(ji,jj,ikbu)
110               avmv(ji,jj,ikbv) = bfri1 * fse3vw(ji,jj,ikbv)
111# if ! defined key_vectopt_loop   ||   defined key_autotasking
112            END DO
113# endif
114         END DO
115
116      CASE( 2 )                 ! quadratic botton friction
117# if defined key_vectopt_loop   &&   ! defined key_autotasking
118         jj = 1
119!CDIR NOVERRCHK
120         DO ji = jpi+2, jpij-jpi-1   ! vector opt. (forced unrolling)
121# else
122!CDIR NOVERRCHK
123         DO jj = 2, jpjm1
124!CDIR NOVERRCHK
125            DO ji = 2, jpim1
126# endif
127               ikbu   = MIN( mbathy(ji+1,jj  ), mbathy(ji,jj) )
128               ikbv   = MIN( mbathy(ji  ,jj+1), mbathy(ji,jj) )
129               ikbum1 = MAX( ikbu-1, 1 )
130               ikbvm1 = MAX( ikbv-1, 1 )
131               
132               zvu  = 0.25 * (  vn(ji,jj  ,ikbum1) + vn(ji+1,jj  ,ikbum1)     &
133                              + vn(ji,jj-1,ikbum1) + vn(ji+1,jj-1,ikbum1)  )
134               
135               zuv  = 0.25 * (  un(ji,jj  ,ikbvm1) + un(ji-1,jj  ,ikbvm1)     &
136                              + un(ji,jj+1,ikbvm1) + un(ji-1,jj+1,ikbvm1)  )
137               
138               zecu = SQRT(  un(ji,jj,ikbum1) * un(ji,jj,ikbum1) + zvu*zvu + bfeb2  )
139               zecv = SQRT(  vn(ji,jj,ikbvm1) * vn(ji,jj,ikbvm1) + zuv*zuv + bfeb2  )
140               
141               avmu(ji,jj,ikbu) = bfri2 * zecu * fse3uw(ji,jj,ikbu)
142               avmv(ji,jj,ikbv) = bfri2 * zecv * fse3vw(ji,jj,ikbv)
143# if ! defined key_vectopt_loop   ||   defined key_autotasking
144            END DO
145# endif
146         END DO
147
148      CASE( 3 )                 ! free-slip boundary condition
149# if defined key_vectopt_loop   &&   ! defined key_autotasking
150         jj = 1
151         DO ji = jpi+2, jpij-jpi-1   ! vector opt. (forced unrolling)
152# else
153         DO jj = 2, jpjm1
154            DO ji = 2, jpim1
155# endif
156               ikbu = MIN( mbathy(ji+1,jj  ), mbathy(ji,jj) )
157               ikbv = MIN( mbathy(ji  ,jj+1), mbathy(ji,jj) )
158               avmu(ji,jj,ikbu) = 0.e0
159               avmv(ji,jj,ikbv) = 0.e0
160# if ! defined key_vectopt_loop   ||   defined key_autotasking
161            END DO
162# endif
163         END DO
164
165      END SELECT
166
167      ! Lateral boundary condition on (avmu,avmv)   (unchanged sign)
168      ! ------------------------------===========
169      CALL lbc_lnk( avmu, 'U', 1. )
170      CALL lbc_lnk( avmv, 'V', 1. )
171
172      IF(l_ctl)   WRITE(numout,*) ' bfr  u : ', SUM( avmu(1:nictl+1,1:njctl+1,:) ), ' v : ', SUM( avmv(1:nictl+1,1:njctl+1,:) )
173
174   END SUBROUTINE zdf_bfr
175
176
177   SUBROUTINE zdf_bfr_init
178      !!----------------------------------------------------------------------
179      !!                  ***  ROUTINE zdf_bfr_init  ***
180      !!                   
181      !! ** Purpose :   Initialization of the bottom friction
182      !!
183      !! ** Method  :   Read the nammbf namelist and check their consistency
184      !!      called at the first timestep (nit000)
185      !!
186      !! History :
187      !!   9.0  !  02-06  (G. Madec)  Original code
188      !!----------------------------------------------------------------------
189      !! * Local declarations
190      NAMELIST/nambfr/ nbotfr, bfri1, bfri2, bfeb2
191      !!----------------------------------------------------------------------
192
193      ! Read Namelist nambfr : bottom momentum boundary condition
194      ! --------------------
195      REWIND ( numnam )
196      READ   ( numnam, nambfr )
197
198
199      ! Parameter control and print
200      ! ---------------------------
201      IF(lwp) WRITE(numout,*)
202      IF(lwp) WRITE(numout,*) 'zdf_bfr : momentum bottom friction'
203      IF(lwp) WRITE(numout,*) '~~~~~~~'
204      IF(lwp) WRITE(numout,*) '          Namelist nambfr : set bottom friction parameters'
205
206      SELECT CASE (nbotfr)
207
208      CASE( 0 )
209         IF(lwp) WRITE(numout,*) '            no-slip '
210
211      CASE( 1 )
212         IF(lwp) WRITE(numout,*) '            linear botton friction'
213         IF(lwp) WRITE(numout,*) '            friction coef.   bfri1  = ', bfri1
214
215      CASE( 2 )
216         IF(lwp) WRITE(numout,*) '            quadratic botton friction'
217         IF(lwp) WRITE(numout,*) '            friction coef.   bfri2  = ', bfri2
218         IF(lwp) WRITE(numout,*) '            background tke   bfeb2  = ', bfeb2
219
220      CASE( 3 )
221         IF(lwp) WRITE(numout,*) '            free-slip '
222
223      CASE DEFAULT
224         IF(lwp) WRITE(numout,cform_err)
225         IF(lwp) WRITE(numout,*) '         bad flag value for nbotfr = ', nbotfr
226         nstop = nstop + 1
227
228      END SELECT
229
230   END SUBROUTINE zdf_bfr_init
231
232   !!======================================================================
233END MODULE zdfbfr
Note: See TracBrowser for help on using the repository browser.