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.
trabbl.F90 in NEMO/branches/UKMO/NEMO_4.0_mirror_text_diagnostics/src/OCE/TRA – NEMO

source: NEMO/branches/UKMO/NEMO_4.0_mirror_text_diagnostics/src/OCE/TRA/trabbl.F90 @ 10986

Last change on this file since 10986 was 10986, checked in by andmirek, 5 years ago

GMED 462 add flush

File size: 32.1 KB
Line 
1MODULE trabbl
2   !!==============================================================================
3   !!                       ***  MODULE  trabbl  ***
4   !! Ocean physics :  advective and/or diffusive bottom boundary layer scheme
5   !!==============================================================================
6   !! History :  OPA  ! 1996-06  (L. Mortier)  Original code
7   !!            8.0  ! 1997-11  (G. Madec)    Optimization
8   !!   NEMO     1.0  ! 2002-08  (G. Madec)  free form + modules
9   !!             -   ! 2004-01  (A. de Miranda, G. Madec, J.M. Molines ) add advective bbl
10   !!            3.3  ! 2009-11  (G. Madec)  merge trabbl and trabbl_adv + style + optimization
11   !!             -   ! 2010-04  (G. Madec)  Campin & Goosse advective bbl
12   !!             -   ! 2010-06  (C. Ethe, G. Madec)  merge TRA-TRC
13   !!             -   ! 2010-11  (G. Madec) add mbk. arrays associated to the deepest ocean level
14   !!             -   ! 2013-04  (F. Roquet, G. Madec)  use of eosbn2 instead of local hard coded alpha and beta
15   !!            4.0  ! 2017-04  (G. Madec)  ln_trabbl namelist variable instead of a CPP key
16   !!----------------------------------------------------------------------
17
18   !!----------------------------------------------------------------------
19   !!   tra_bbl_alloc : allocate trabbl arrays
20   !!   tra_bbl       : update the tracer trends due to the bottom boundary layer (advective and/or diffusive)
21   !!   tra_bbl_dif   : generic routine to compute bbl diffusive trend
22   !!   tra_bbl_adv   : generic routine to compute bbl advective trend
23   !!   bbl           : computation of bbl diffu. flux coef. & transport in bottom boundary layer
24   !!   tra_bbl_init  : initialization, namelist read, parameters control
25   !!----------------------------------------------------------------------
26   USE oce            ! ocean dynamics and active tracers
27   USE dom_oce        ! ocean space and time domain
28   USE phycst         ! physical constant
29   USE eosbn2         ! equation of state
30   USE trd_oce        ! trends: ocean variables
31   USE trdtra         ! trends: active tracers
32   !
33   USE iom            ! IOM library               
34   USE in_out_manager ! I/O manager
35   USE lbclnk         ! ocean lateral boundary conditions
36   USE prtctl         ! Print control
37   USE timing         ! Timing
38   USE lib_fortran    ! Fortran utilities (allows no signed zero when 'key_nosignedzero' defined) 
39
40   IMPLICIT NONE
41   PRIVATE
42
43   PUBLIC   tra_bbl       !  routine called by step.F90
44   PUBLIC   tra_bbl_init  !  routine called by nemogcm.F90
45   PUBLIC   tra_bbl_dif   !  routine called by trcbbl.F90
46   PUBLIC   tra_bbl_adv   !     -      -          -
47   PUBLIC   bbl           !  routine called by trcbbl.F90 and dtadyn.F90
48
49   !                                !!* Namelist nambbl *
50   LOGICAL , PUBLIC ::   ln_trabbl   !: bottom boundary layer flag
51   INTEGER , PUBLIC ::   nn_bbl_ldf  !: =1   : diffusive bbl or not (=0)
52   INTEGER , PUBLIC ::   nn_bbl_adv  !: =1/2 : advective bbl or not (=0)
53   !                                            !  =1 : advective bbl using the bottom ocean velocity
54   !                                            !  =2 :     -      -  using utr_bbl proportional to grad(rho)
55   REAL(wp), PUBLIC ::   rn_ahtbbl   !: along slope bbl diffusive coefficient [m2/s]
56   REAL(wp), PUBLIC ::   rn_gambbl   !: lateral coeff. for bottom boundary layer scheme [s]
57
58   LOGICAL , PUBLIC ::   l_bbl       !: flag to compute bbl diffu. flux coef and transport
59
60   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:), PUBLIC ::   utr_bbl  , vtr_bbl   ! u- (v-) transport in the bottom boundary layer
61   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:), PUBLIC ::   ahu_bbl  , ahv_bbl   ! masked diffusive bbl coeff. at u & v-pts
62
63   INTEGER , ALLOCATABLE, SAVE, DIMENSION(:,:), PUBLIC ::   mbku_d   , mbkv_d      ! vertical index of the "lower" bottom ocean U/V-level (PUBLIC for TAM)
64   INTEGER , ALLOCATABLE, SAVE, DIMENSION(:,:), PUBLIC ::   mgrhu    , mgrhv       ! = +/-1, sign of grad(H) in u-(v-)direction (PUBLIC for TAM)
65   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:)         ::   ahu_bbl_0, ahv_bbl_0   ! diffusive bbl flux coefficients at u and v-points
66   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:), PUBLIC ::   e3u_bbl_0, e3v_bbl_0   ! thichness of the bbl (e3) at u and v-points (PUBLIC for TAM)
67
68   !! * Substitutions
69#  include "vectopt_loop_substitute.h90"
70   !!----------------------------------------------------------------------
71   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
72   !! $Id$
73   !! Software governed by the CeCILL license (see ./LICENSE)
74   !!----------------------------------------------------------------------
75CONTAINS
76
77   INTEGER FUNCTION tra_bbl_alloc()
78      !!----------------------------------------------------------------------
79      !!                ***  FUNCTION tra_bbl_alloc  ***
80      !!----------------------------------------------------------------------
81      ALLOCATE( utr_bbl  (jpi,jpj) , ahu_bbl  (jpi,jpj) , mbku_d(jpi,jpj) , mgrhu(jpi,jpj) ,     &
82         &      vtr_bbl  (jpi,jpj) , ahv_bbl  (jpi,jpj) , mbkv_d(jpi,jpj) , mgrhv(jpi,jpj) ,     &
83         &      ahu_bbl_0(jpi,jpj) , ahv_bbl_0(jpi,jpj) ,                                        &
84         &      e3u_bbl_0(jpi,jpj) , e3v_bbl_0(jpi,jpj) ,                                    STAT=tra_bbl_alloc )
85         !
86      CALL mpp_sum ( 'trabbl', tra_bbl_alloc )
87      IF( tra_bbl_alloc > 0 )   CALL ctl_warn('tra_bbl_alloc: allocation of arrays failed.')
88   END FUNCTION tra_bbl_alloc
89
90
91   SUBROUTINE tra_bbl( kt )
92      !!----------------------------------------------------------------------
93      !!                  ***  ROUTINE bbl  ***
94      !!
95      !! ** Purpose :   Compute the before tracer (t & s) trend associated
96      !!              with the bottom boundary layer and add it to the general
97      !!              trend of tracer equations.
98      !!
99      !! ** Method  :   Depending on namtra_bbl namelist parameters the bbl
100      !!              diffusive and/or advective contribution to the tracer trend
101      !!              is added to the general tracer trend
102      !!----------------------------------------------------------------------
103      INTEGER, INTENT( in ) ::   kt   ! ocean time-step
104      !
105      REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) ::   ztrdt, ztrds
106      !!----------------------------------------------------------------------
107      !
108      IF( ln_timing )   CALL timing_start( 'tra_bbl')
109      !
110      IF( l_trdtra )   THEN                         !* Save the T-S input trends
111         ALLOCATE( ztrdt(jpi,jpj,jpk) , ztrds(jpi,jpj,jpk) )
112         ztrdt(:,:,:) = tsa(:,:,:,jp_tem)
113         ztrds(:,:,:) = tsa(:,:,:,jp_sal)
114      ENDIF
115
116      IF( l_bbl )   CALL bbl( kt, nit000, 'TRA' )   !* bbl coef. and transport (only if not already done in trcbbl)
117
118      IF( nn_bbl_ldf == 1 ) THEN                    !* Diffusive bbl
119         !
120         CALL tra_bbl_dif( tsb, tsa, jpts )
121         IF( ln_ctl )  &
122         CALL prt_ctl( tab3d_1=tsa(:,:,:,jp_tem), clinfo1=' bbl_ldf  - Ta: ', mask1=tmask, &
123            &          tab3d_2=tsa(:,:,:,jp_sal), clinfo2=           ' Sa: ', mask2=tmask, clinfo3='tra' )
124         ! lateral boundary conditions ; just need for outputs
125         CALL lbc_lnk_multi( 'trabbl', ahu_bbl, 'U', 1. , ahv_bbl, 'V', 1. )
126         CALL iom_put( "ahu_bbl", ahu_bbl )   ! bbl diffusive flux i-coef
127         CALL iom_put( "ahv_bbl", ahv_bbl )   ! bbl diffusive flux j-coef
128         !
129      ENDIF
130      !
131      IF( nn_bbl_adv /= 0 ) THEN                    !* Advective bbl
132         !
133         CALL tra_bbl_adv( tsb, tsa, jpts )
134         IF(ln_ctl)   &
135         CALL prt_ctl( tab3d_1=tsa(:,:,:,jp_tem), clinfo1=' bbl_adv  - Ta: ', mask1=tmask,   &
136            &          tab3d_2=tsa(:,:,:,jp_sal), clinfo2=           ' Sa: ', mask2=tmask, clinfo3='tra' )
137         ! lateral boundary conditions ; just need for outputs
138         CALL lbc_lnk_multi( 'trabbl', utr_bbl, 'U', 1. , vtr_bbl, 'V', 1. )
139         CALL iom_put( "uoce_bbl", utr_bbl )  ! bbl i-transport
140         CALL iom_put( "voce_bbl", vtr_bbl )  ! bbl j-transport
141         !
142      ENDIF
143
144      IF( l_trdtra )   THEN                      ! send the trends for further diagnostics
145         ztrdt(:,:,:) = tsa(:,:,:,jp_tem) - ztrdt(:,:,:)
146         ztrds(:,:,:) = tsa(:,:,:,jp_sal) - ztrds(:,:,:)
147         CALL trd_tra( kt, 'TRA', jp_tem, jptra_bbl, ztrdt )
148         CALL trd_tra( kt, 'TRA', jp_sal, jptra_bbl, ztrds )
149         DEALLOCATE( ztrdt, ztrds )
150      ENDIF
151      !
152      IF( ln_timing )  CALL timing_stop( 'tra_bbl')
153      !
154   END SUBROUTINE tra_bbl
155
156
157   SUBROUTINE tra_bbl_dif( ptb, pta, kjpt )
158      !!----------------------------------------------------------------------
159      !!                  ***  ROUTINE tra_bbl_dif  ***
160      !!
161      !! ** Purpose :   Computes the bottom boundary horizontal and vertical
162      !!                advection terms.
163      !!
164      !! ** Method  : * diffusive bbl only (nn_bbl_ldf=1) :
165      !!        When the product grad( rho) * grad(h) < 0 (where grad is an
166      !!      along bottom slope gradient) an additional lateral 2nd order
167      !!      diffusion along the bottom slope is added to the general
168      !!      tracer trend, otherwise the additional trend is set to 0.
169      !!      A typical value of ahbt is 2000 m2/s (equivalent to
170      !!      a downslope velocity of 20 cm/s if the condition for slope
171      !!      convection is satified)
172      !!
173      !! ** Action  :   pta   increased by the bbl diffusive trend
174      !!
175      !! References : Beckmann, A., and R. Doscher, 1997, J. Phys.Oceanogr., 581-591.
176      !!              Campin, J.-M., and H. Goosse, 1999, Tellus, 412-430.
177      !!----------------------------------------------------------------------
178      INTEGER                              , INTENT(in   ) ::   kjpt   ! number of tracers
179      REAL(wp), DIMENSION(jpi,jpj,jpk,kjpt), INTENT(in   ) ::   ptb    ! before and now tracer fields
180      REAL(wp), DIMENSION(jpi,jpj,jpk,kjpt), INTENT(inout) ::   pta    ! tracer trend
181      !
182      INTEGER  ::   ji, jj, jn   ! dummy loop indices
183      INTEGER  ::   ik           ! local integers
184      REAL(wp) ::   zbtr         ! local scalars
185      REAL(wp), DIMENSION(jpi,jpj) ::   zptb   ! workspace
186      !!----------------------------------------------------------------------
187      !
188      DO jn = 1, kjpt                                     ! tracer loop
189         !                                                ! ===========
190         DO jj = 1, jpj
191            DO ji = 1, jpi
192               ik = mbkt(ji,jj)                             ! bottom T-level index
193               zptb(ji,jj) = ptb(ji,jj,ik,jn)               ! bottom before T and S
194            END DO
195         END DO
196         !               
197         DO jj = 2, jpjm1                                    ! Compute the trend
198            DO ji = 2, jpim1
199               ik = mbkt(ji,jj)                            ! bottom T-level index
200               pta(ji,jj,ik,jn) = pta(ji,jj,ik,jn)                                                  &
201                  &             + (  ahu_bbl(ji  ,jj  ) * ( zptb(ji+1,jj  ) - zptb(ji  ,jj  ) )     &
202                  &                - ahu_bbl(ji-1,jj  ) * ( zptb(ji  ,jj  ) - zptb(ji-1,jj  ) )     &
203                  &                + ahv_bbl(ji  ,jj  ) * ( zptb(ji  ,jj+1) - zptb(ji  ,jj  ) )     &
204                  &                - ahv_bbl(ji  ,jj-1) * ( zptb(ji  ,jj  ) - zptb(ji  ,jj-1) )  )  &
205                  &             * r1_e1e2t(ji,jj) / e3t_n(ji,jj,ik)
206            END DO
207         END DO
208         !                                                  ! ===========
209      END DO                                                ! end tracer
210      !                                                     ! ===========
211   END SUBROUTINE tra_bbl_dif
212
213
214   SUBROUTINE tra_bbl_adv( ptb, pta, kjpt )
215      !!----------------------------------------------------------------------
216      !!                  ***  ROUTINE trc_bbl  ***
217      !!
218      !! ** Purpose :   Compute the before passive tracer trend associated
219      !!     with the bottom boundary layer and add it to the general trend
220      !!     of tracer equations.
221      !! ** Method  :   advective bbl (nn_bbl_adv = 1 or 2) :
222      !!      nn_bbl_adv = 1   use of the ocean near bottom velocity as bbl velocity
223      !!      nn_bbl_adv = 2   follow Campin and Goosse (1999) implentation i.e.
224      !!                       transport proportional to the along-slope density gradient
225      !!
226      !! References : Beckmann, A., and R. Doscher, 1997, J. Phys.Oceanogr., 581-591.
227      !!              Campin, J.-M., and H. Goosse, 1999, Tellus, 412-430.
228      !!----------------------------------------------------------------------
229      INTEGER                              , INTENT(in   ) ::   kjpt   ! number of tracers
230      REAL(wp), DIMENSION(jpi,jpj,jpk,kjpt), INTENT(in   ) ::   ptb    ! before and now tracer fields
231      REAL(wp), DIMENSION(jpi,jpj,jpk,kjpt), INTENT(inout) ::   pta    ! tracer trend
232      !
233      INTEGER  ::   ji, jj, jk, jn           ! dummy loop indices
234      INTEGER  ::   iis , iid , ijs , ijd    ! local integers
235      INTEGER  ::   ikus, ikud, ikvs, ikvd   !   -       -
236      REAL(wp) ::   zbtr, ztra               ! local scalars
237      REAL(wp) ::   zu_bbl, zv_bbl           !   -      -
238      !!----------------------------------------------------------------------
239      !
240      !                                                          ! ===========
241      DO jn = 1, kjpt                                            ! tracer loop
242         !                                                       ! ===========
243         DO jj = 1, jpjm1
244            DO ji = 1, jpim1            ! CAUTION start from i=1 to update i=2 when cyclic east-west
245               IF( utr_bbl(ji,jj) /= 0.e0 ) THEN            ! non-zero i-direction bbl advection
246                  ! down-slope i/k-indices (deep)      &   up-slope i/k indices (shelf)
247                  iid  = ji + MAX( 0, mgrhu(ji,jj) )   ;   iis  = ji + 1 - MAX( 0, mgrhu(ji,jj) )
248                  ikud = mbku_d(ji,jj)                 ;   ikus = mbku(ji,jj)
249                  zu_bbl = ABS( utr_bbl(ji,jj) )
250                  !
251                  !                                               ! up  -slope T-point (shelf bottom point)
252                  zbtr = r1_e1e2t(iis,jj) / e3t_n(iis,jj,ikus)
253                  ztra = zu_bbl * ( ptb(iid,jj,ikus,jn) - ptb(iis,jj,ikus,jn) ) * zbtr
254                  pta(iis,jj,ikus,jn) = pta(iis,jj,ikus,jn) + ztra
255                  !
256                  DO jk = ikus, ikud-1                            ! down-slope upper to down T-point (deep column)
257                     zbtr = r1_e1e2t(iid,jj) / e3t_n(iid,jj,jk)
258                     ztra = zu_bbl * ( ptb(iid,jj,jk+1,jn) - ptb(iid,jj,jk,jn) ) * zbtr
259                     pta(iid,jj,jk,jn) = pta(iid,jj,jk,jn) + ztra
260                  END DO
261                  !
262                  zbtr = r1_e1e2t(iid,jj) / e3t_n(iid,jj,ikud)
263                  ztra = zu_bbl * ( ptb(iis,jj,ikus,jn) - ptb(iid,jj,ikud,jn) ) * zbtr
264                  pta(iid,jj,ikud,jn) = pta(iid,jj,ikud,jn) + ztra
265               ENDIF
266               !
267               IF( vtr_bbl(ji,jj) /= 0.e0 ) THEN            ! non-zero j-direction bbl advection
268                  ! down-slope j/k-indices (deep)        &   up-slope j/k indices (shelf)
269                  ijd  = jj + MAX( 0, mgrhv(ji,jj) )     ;   ijs  = jj + 1 - MAX( 0, mgrhv(ji,jj) )
270                  ikvd = mbkv_d(ji,jj)                   ;   ikvs = mbkv(ji,jj)
271                  zv_bbl = ABS( vtr_bbl(ji,jj) )
272                  !
273                  ! up  -slope T-point (shelf bottom point)
274                  zbtr = r1_e1e2t(ji,ijs) / e3t_n(ji,ijs,ikvs)
275                  ztra = zv_bbl * ( ptb(ji,ijd,ikvs,jn) - ptb(ji,ijs,ikvs,jn) ) * zbtr
276                  pta(ji,ijs,ikvs,jn) = pta(ji,ijs,ikvs,jn) + ztra
277                  !
278                  DO jk = ikvs, ikvd-1                            ! down-slope upper to down T-point (deep column)
279                     zbtr = r1_e1e2t(ji,ijd) / e3t_n(ji,ijd,jk)
280                     ztra = zv_bbl * ( ptb(ji,ijd,jk+1,jn) - ptb(ji,ijd,jk,jn) ) * zbtr
281                     pta(ji,ijd,jk,jn) = pta(ji,ijd,jk,jn)  + ztra
282                  END DO
283                  !                                               ! down-slope T-point (deep bottom point)
284                  zbtr = r1_e1e2t(ji,ijd) / e3t_n(ji,ijd,ikvd)
285                  ztra = zv_bbl * ( ptb(ji,ijs,ikvs,jn) - ptb(ji,ijd,ikvd,jn) ) * zbtr
286                  pta(ji,ijd,ikvd,jn) = pta(ji,ijd,ikvd,jn) + ztra
287               ENDIF
288            END DO
289            !
290         END DO
291         !                                                  ! ===========
292      END DO                                                ! end tracer
293      !                                                     ! ===========
294   END SUBROUTINE tra_bbl_adv
295
296
297   SUBROUTINE bbl( kt, kit000, cdtype )
298      !!----------------------------------------------------------------------
299      !!                  ***  ROUTINE bbl  ***
300      !!
301      !! ** Purpose :   Computes the bottom boundary horizontal and vertical
302      !!                advection terms.
303      !!
304      !! ** Method  : * diffusive bbl (nn_bbl_ldf=1) :
305      !!        When the product grad( rho) * grad(h) < 0 (where grad is an
306      !!      along bottom slope gradient) an additional lateral 2nd order
307      !!      diffusion along the bottom slope is added to the general
308      !!      tracer trend, otherwise the additional trend is set to 0.
309      !!      A typical value of ahbt is 2000 m2/s (equivalent to
310      !!      a downslope velocity of 20 cm/s if the condition for slope
311      !!      convection is satified)
312      !!              * advective bbl (nn_bbl_adv=1 or 2) :
313      !!      nn_bbl_adv = 1   use of the ocean velocity as bbl velocity
314      !!      nn_bbl_adv = 2   follow Campin and Goosse (1999) implentation
315      !!        i.e. transport proportional to the along-slope density gradient
316      !!
317      !!      NB: the along slope density gradient is evaluated using the
318      !!      local density (i.e. referenced at a common local depth).
319      !!
320      !! References : Beckmann, A., and R. Doscher, 1997, J. Phys.Oceanogr., 581-591.
321      !!              Campin, J.-M., and H. Goosse, 1999, Tellus, 412-430.
322      !!----------------------------------------------------------------------
323      INTEGER         , INTENT(in   ) ::   kt       ! ocean time-step index
324      INTEGER         , INTENT(in   ) ::   kit000   ! first time step index
325      CHARACTER(len=3), INTENT(in   ) ::   cdtype   ! =TRA or TRC (tracer indicator)
326      !
327      INTEGER  ::   ji, jj                    ! dummy loop indices
328      INTEGER  ::   ik                        ! local integers
329      INTEGER  ::   iis, iid, ikus, ikud      !   -       -
330      INTEGER  ::   ijs, ijd, ikvs, ikvd      !   -       -
331      REAL(wp) ::   za, zb, zgdrho            ! local scalars
332      REAL(wp) ::   zsign, zsigna, zgbbl      !   -      -
333      REAL(wp), DIMENSION(jpi,jpj,jpts)   :: zts, zab         ! 3D workspace
334      REAL(wp), DIMENSION(jpi,jpj)        :: zub, zvb, zdep   ! 2D workspace
335      !!----------------------------------------------------------------------
336      !
337      IF( kt == kit000 .AND. lwp)  THEN
338         WRITE(numout,*)
339         WRITE(numout,*) 'trabbl:bbl : Compute bbl velocities and diffusive coefficients in ', cdtype
340         WRITE(numout,*) '~~~~~~~~~~'
341         IF(lflush) CALL FLUSH(numout)
342      ENDIF
343      !                                        !* bottom variables (T, S, alpha, beta, depth, velocity)
344      DO jj = 1, jpj
345         DO ji = 1, jpi
346            ik = mbkt(ji,jj)                             ! bottom T-level index
347            zts (ji,jj,jp_tem) = tsb(ji,jj,ik,jp_tem)    ! bottom before T and S
348            zts (ji,jj,jp_sal) = tsb(ji,jj,ik,jp_sal)
349            !
350            zdep(ji,jj) = gdept_n(ji,jj,ik)              ! bottom T-level reference depth
351            zub (ji,jj) = un(ji,jj,mbku(ji,jj))          ! bottom velocity
352            zvb (ji,jj) = vn(ji,jj,mbkv(ji,jj))
353         END DO
354      END DO
355      !
356      CALL eos_rab( zts, zdep, zab )
357      !
358      !                                   !-------------------!
359      IF( nn_bbl_ldf == 1 ) THEN          !   diffusive bbl   !
360         !                                !-------------------!
361         DO jj = 1, jpjm1                      ! (criteria for non zero flux: grad(rho).grad(h) < 0 )
362            DO ji = 1, fs_jpim1   ! vector opt.
363               !                                                   ! i-direction
364               za = zab(ji+1,jj,jp_tem) + zab(ji,jj,jp_tem)              ! 2*(alpha,beta) at u-point
365               zb = zab(ji+1,jj,jp_sal) + zab(ji,jj,jp_sal)
366               !                                                         ! 2*masked bottom density gradient
367               zgdrho = (  za * ( zts(ji+1,jj,jp_tem) - zts(ji,jj,jp_tem) )    &
368                  &      - zb * ( zts(ji+1,jj,jp_sal) - zts(ji,jj,jp_sal) )  ) * umask(ji,jj,1)
369               !
370               zsign  = SIGN(  0.5, -zgdrho * REAL( mgrhu(ji,jj) )  )    ! sign of ( i-gradient * i-slope )
371               ahu_bbl(ji,jj) = ( 0.5 - zsign ) * ahu_bbl_0(ji,jj)       ! masked diffusive flux coeff.
372               !
373               !                                                   ! j-direction
374               za = zab(ji,jj+1,jp_tem) + zab(ji,jj,jp_tem)              ! 2*(alpha,beta) at v-point
375               zb = zab(ji,jj+1,jp_sal) + zab(ji,jj,jp_sal)
376               !                                                         ! 2*masked bottom density gradient
377               zgdrho = (  za * ( zts(ji,jj+1,jp_tem) - zts(ji,jj,jp_tem) )    &
378                  &      - zb * ( zts(ji,jj+1,jp_sal) - zts(ji,jj,jp_sal) )  ) * vmask(ji,jj,1)
379               !
380               zsign = SIGN(  0.5, -zgdrho * REAL( mgrhv(ji,jj) )  )     ! sign of ( j-gradient * j-slope )
381               ahv_bbl(ji,jj) = ( 0.5 - zsign ) * ahv_bbl_0(ji,jj)
382            END DO
383         END DO
384         !
385      ENDIF
386      !
387      !                                   !-------------------!
388      IF( nn_bbl_adv /= 0 ) THEN          !   advective bbl   !
389         !                                !-------------------!
390         SELECT CASE ( nn_bbl_adv )             !* bbl transport type
391         !
392         CASE( 1 )                                   != use of upper velocity
393            DO jj = 1, jpjm1                                 ! criteria: grad(rho).grad(h)<0  and grad(rho).grad(h)<0
394               DO ji = 1, fs_jpim1   ! vector opt.
395                  !                                                  ! i-direction
396                  za = zab(ji+1,jj,jp_tem) + zab(ji,jj,jp_tem)               ! 2*(alpha,beta) at u-point
397                  zb = zab(ji+1,jj,jp_sal) + zab(ji,jj,jp_sal)
398                  !                                                          ! 2*masked bottom density gradient
399                  zgdrho = (  za * ( zts(ji+1,jj,jp_tem) - zts(ji,jj,jp_tem) )    &
400                            - zb * ( zts(ji+1,jj,jp_sal) - zts(ji,jj,jp_sal) )  ) * umask(ji,jj,1)
401                  !
402                  zsign = SIGN(  0.5, - zgdrho   * REAL( mgrhu(ji,jj) )  )   ! sign of i-gradient * i-slope
403                  zsigna= SIGN(  0.5, zub(ji,jj) * REAL( mgrhu(ji,jj) )  )   ! sign of u * i-slope
404                  !
405                  !                                                          ! bbl velocity
406                  utr_bbl(ji,jj) = ( 0.5 + zsigna ) * ( 0.5 - zsign ) * e2u(ji,jj) * e3u_bbl_0(ji,jj) * zub(ji,jj)
407                  !
408                  !                                                  ! j-direction
409                  za = zab(ji,jj+1,jp_tem) + zab(ji,jj,jp_tem)               ! 2*(alpha,beta) at v-point
410                  zb = zab(ji,jj+1,jp_sal) + zab(ji,jj,jp_sal)
411                  !                                                          ! 2*masked bottom density gradient
412                  zgdrho = (  za * ( zts(ji,jj+1,jp_tem) - zts(ji,jj,jp_tem) )    &
413                     &      - zb * ( zts(ji,jj+1,jp_sal) - zts(ji,jj,jp_sal) )  ) * vmask(ji,jj,1)
414                  zsign = SIGN(  0.5, - zgdrho   * REAL( mgrhv(ji,jj) )  )   ! sign of j-gradient * j-slope
415                  zsigna= SIGN(  0.5, zvb(ji,jj) * REAL( mgrhv(ji,jj) )  )   ! sign of u * i-slope
416                  !
417                  !                                                          ! bbl transport
418                  vtr_bbl(ji,jj) = ( 0.5 + zsigna ) * ( 0.5 - zsign ) * e1v(ji,jj) * e3v_bbl_0(ji,jj) * zvb(ji,jj)
419               END DO
420            END DO
421            !
422         CASE( 2 )                                 != bbl velocity = F( delta rho )
423            zgbbl = grav * rn_gambbl
424            DO jj = 1, jpjm1                            ! criteria: rho_up > rho_down
425               DO ji = 1, fs_jpim1   ! vector opt.
426                  !                                                  ! i-direction
427                  ! down-slope T-point i/k-index (deep)  &   up-slope T-point i/k-index (shelf)
428                  iid  = ji + MAX( 0, mgrhu(ji,jj) )
429                  iis  = ji + 1 - MAX( 0, mgrhu(ji,jj) )
430                  !
431                  ikud = mbku_d(ji,jj)
432                  ikus = mbku(ji,jj)
433                  !
434                  za = zab(ji+1,jj,jp_tem) + zab(ji,jj,jp_tem)               ! 2*(alpha,beta) at u-point
435                  zb = zab(ji+1,jj,jp_sal) + zab(ji,jj,jp_sal)
436                  !                                                          !   masked bottom density gradient
437                  zgdrho = 0.5 * (  za * ( zts(iid,jj,jp_tem) - zts(iis,jj,jp_tem) )    &
438                     &            - zb * ( zts(iid,jj,jp_sal) - zts(iis,jj,jp_sal) )  ) * umask(ji,jj,1)
439                  zgdrho = MAX( 0.e0, zgdrho )                               ! only if shelf is denser than deep
440                  !
441                  !                                                          ! bbl transport (down-slope direction)
442                  utr_bbl(ji,jj) = e2u(ji,jj) * e3u_bbl_0(ji,jj) * zgbbl * zgdrho * REAL( mgrhu(ji,jj) )
443                  !
444                  !                                                  ! j-direction
445                  !  down-slope T-point j/k-index (deep)  &   of the up  -slope T-point j/k-index (shelf)
446                  ijd  = jj + MAX( 0, mgrhv(ji,jj) )
447                  ijs  = jj + 1 - MAX( 0, mgrhv(ji,jj) )
448                  !
449                  ikvd = mbkv_d(ji,jj)
450                  ikvs = mbkv(ji,jj)
451                  !
452                  za = zab(ji,jj+1,jp_tem) + zab(ji,jj,jp_tem)               ! 2*(alpha,beta) at v-point
453                  zb = zab(ji,jj+1,jp_sal) + zab(ji,jj,jp_sal)
454                  !                                                          !   masked bottom density gradient
455                  zgdrho = 0.5 * (  za * ( zts(ji,ijd,jp_tem) - zts(ji,ijs,jp_tem) )    &
456                     &            - zb * ( zts(ji,ijd,jp_sal) - zts(ji,ijs,jp_sal) )  ) * vmask(ji,jj,1)
457                  zgdrho = MAX( 0.e0, zgdrho )                               ! only if shelf is denser than deep
458                  !
459                  !                                                          ! bbl transport (down-slope direction)
460                  vtr_bbl(ji,jj) = e1v(ji,jj) * e3v_bbl_0(ji,jj) * zgbbl * zgdrho * REAL( mgrhv(ji,jj) )
461               END DO
462            END DO
463         END SELECT
464         !
465      ENDIF
466      !
467   END SUBROUTINE bbl
468
469
470   SUBROUTINE tra_bbl_init
471      !!----------------------------------------------------------------------
472      !!                  ***  ROUTINE tra_bbl_init  ***
473      !!
474      !! ** Purpose :   Initialization for the bottom boundary layer scheme.
475      !!
476      !! ** Method  :   Read the nambbl namelist and check the parameters
477      !!              called by nemo_init at the first timestep (kit000)
478      !!----------------------------------------------------------------------
479      INTEGER ::   ji, jj                      ! dummy loop indices
480      INTEGER ::   ii0, ii1, ij0, ij1, ios     ! local integer
481      REAL(wp), DIMENSION(jpi,jpj) ::   zmbku, zmbkv   ! workspace
482      !!
483      NAMELIST/nambbl/ ln_trabbl, nn_bbl_ldf, nn_bbl_adv, rn_ahtbbl, rn_gambbl
484      !!----------------------------------------------------------------------
485      !
486      REWIND( numnam_ref )              ! Namelist nambbl in reference namelist : Bottom boundary layer scheme
487      READ  ( numnam_ref, nambbl, IOSTAT = ios, ERR = 901)
488901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'nambbl in reference namelist', lwp )
489      !
490      REWIND( numnam_cfg )              ! Namelist nambbl in configuration namelist : Bottom boundary layer scheme
491      READ  ( numnam_cfg, nambbl, IOSTAT = ios, ERR = 902 )
492902   IF( ios >  0 )   CALL ctl_nam ( ios , 'nambbl in configuration namelist', lwp )
493      IF(lwm .AND. nprint > 2) WRITE ( numond, nambbl )
494      !
495      l_bbl = .TRUE.                 !* flag to compute bbl coef and transport
496      !
497      IF(lwp) THEN                   !* Parameter control and print
498         WRITE(numout,*)
499         WRITE(numout,*) 'tra_bbl_init : bottom boundary layer initialisation'
500         WRITE(numout,*) '~~~~~~~~~~~~'
501         WRITE(numout,*) '       Namelist nambbl : set bbl parameters'
502         WRITE(numout,*) '          bottom boundary layer flag          ln_trabbl  = ', ln_trabbl
503         IF(lflush) CALL FLUSH(numout)
504      ENDIF
505      IF( .NOT.ln_trabbl )   RETURN
506      !
507      IF(lwp) THEN
508         WRITE(numout,*) '          diffusive bbl (=1)   or not (=0)    nn_bbl_ldf = ', nn_bbl_ldf
509         WRITE(numout,*) '          advective bbl (=1/2) or not (=0)    nn_bbl_adv = ', nn_bbl_adv
510         WRITE(numout,*) '          diffusive bbl coefficient           rn_ahtbbl  = ', rn_ahtbbl, ' m2/s'
511         WRITE(numout,*) '          advective bbl coefficient           rn_gambbl  = ', rn_gambbl, ' s'
512         IF(lflush) CALL FLUSH(numout)
513      ENDIF
514      !
515      !                              ! allocate trabbl arrays
516      IF( tra_bbl_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'tra_bbl_init : unable to allocate arrays' )
517      !
518      IF(lwp) THEN
519         IF( nn_bbl_adv == 1 )    WRITE(numout,*) '       * Advective BBL using upper velocity'
520         IF( nn_bbl_adv == 2 )    WRITE(numout,*) '       * Advective BBL using velocity = F( delta rho)'
521      ENDIF
522      !
523      !                             !* vertical index of  "deep" bottom u- and v-points
524      DO jj = 1, jpjm1                    ! (the "shelf" bottom k-indices are mbku and mbkv)
525         DO ji = 1, jpim1
526            mbku_d(ji,jj) = MAX(  mbkt(ji+1,jj  ) , mbkt(ji,jj)  )   ! >= 1 as mbkt=1 over land
527            mbkv_d(ji,jj) = MAX(  mbkt(ji  ,jj+1) , mbkt(ji,jj)  )
528         END DO
529      END DO
530      ! converte into REAL to use lbc_lnk ; impose a min value of 1 as a zero can be set in lbclnk
531      zmbku(:,:) = REAL( mbku_d(:,:), wp )   ;     zmbkv(:,:) = REAL( mbkv_d(:,:), wp ) 
532      CALL lbc_lnk_multi( 'trabbl', zmbku,'U',1., zmbkv,'V',1.) 
533      mbku_d(:,:) = MAX( INT( zmbku(:,:) ), 1 ) ;  mbkv_d(:,:) = MAX( NINT( zmbkv(:,:) ), 1 )
534      !
535      !                             !* sign of grad(H) at u- and v-points; zero if grad(H) = 0
536      mgrhu(:,:) = 0   ;   mgrhv(:,:) = 0
537      DO jj = 1, jpjm1
538         DO ji = 1, jpim1
539            IF( gdept_0(ji+1,jj,mbkt(ji+1,jj)) - gdept_0(ji,jj,mbkt(ji,jj)) /= 0._wp ) THEN
540               mgrhu(ji,jj) = INT(  SIGN( 1.e0, gdept_0(ji+1,jj,mbkt(ji+1,jj)) - gdept_0(ji,jj,mbkt(ji,jj)) )  )
541            ENDIF
542            !
543            IF( gdept_0(ji,jj+1,mbkt(ji,jj+1)) - gdept_0(ji,jj,mbkt(ji,jj)) /= 0._wp ) THEN
544               mgrhv(ji,jj) = INT(  SIGN( 1.e0, gdept_0(ji,jj+1,mbkt(ji,jj+1)) - gdept_0(ji,jj,mbkt(ji,jj)) )  )
545            ENDIF
546         END DO
547      END DO
548      !
549      DO jj = 1, jpjm1              !* bbl thickness at u- (v-) point
550         DO ji = 1, jpim1                 ! minimum of top & bottom e3u_0 (e3v_0)
551            e3u_bbl_0(ji,jj) = MIN( e3u_0(ji,jj,mbkt(ji+1,jj  )), e3u_0(ji,jj,mbkt(ji,jj)) )
552            e3v_bbl_0(ji,jj) = MIN( e3v_0(ji,jj,mbkt(ji  ,jj+1)), e3v_0(ji,jj,mbkt(ji,jj)) )
553         END DO
554      END DO
555      CALL lbc_lnk_multi( 'trabbl', e3u_bbl_0, 'U', 1. , e3v_bbl_0, 'V', 1. )      ! lateral boundary conditions
556      !
557      !                             !* masked diffusive flux coefficients
558      ahu_bbl_0(:,:) = rn_ahtbbl * e2_e1u(:,:) * e3u_bbl_0(:,:) * umask(:,:,1)
559      ahv_bbl_0(:,:) = rn_ahtbbl * e1_e2v(:,:) * e3v_bbl_0(:,:) * vmask(:,:,1)
560      !
561   END SUBROUTINE tra_bbl_init
562
563   !!======================================================================
564END MODULE trabbl
Note: See TracBrowser for help on using the repository browser.