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/2021/dev_r14116_HPC-10_mcastril_Mixed_Precision_implementation/src/OCE/TRA – NEMO

source: NEMO/branches/2021/dev_r14116_HPC-10_mcastril_Mixed_Precision_implementation/src/OCE/TRA/trabbl.F90

Last change on this file was 15540, checked in by sparonuz, 3 years ago

Mixed precision version, tested up to 30 years on ORCA2.

  • Property svn:keywords set to Id
File size: 31.7 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(dp), 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 "do_loop_substitute.h90"
70#  include "domzgr_substitute.h90"
71#  include "single_precision_substitute.h90"
72   !!----------------------------------------------------------------------
73   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
74   !! $Id$
75   !! Software governed by the CeCILL license (see ./LICENSE)
76   !!----------------------------------------------------------------------
77CONTAINS
78
79   INTEGER FUNCTION tra_bbl_alloc()
80      !!----------------------------------------------------------------------
81      !!                ***  FUNCTION tra_bbl_alloc  ***
82      !!----------------------------------------------------------------------
83      ALLOCATE( utr_bbl  (jpi,jpj) , ahu_bbl  (jpi,jpj) , mbku_d(jpi,jpj) , mgrhu(jpi,jpj) ,     &
84         &      vtr_bbl  (jpi,jpj) , ahv_bbl  (jpi,jpj) , mbkv_d(jpi,jpj) , mgrhv(jpi,jpj) ,     &
85         &      ahu_bbl_0(jpi,jpj) , ahv_bbl_0(jpi,jpj) ,                                        &
86         &      e3u_bbl_0(jpi,jpj) , e3v_bbl_0(jpi,jpj) ,                                    STAT=tra_bbl_alloc )
87         !
88      CALL mpp_sum ( 'trabbl', tra_bbl_alloc )
89      IF( tra_bbl_alloc > 0 )   CALL ctl_warn('tra_bbl_alloc: allocation of arrays failed.')
90   END FUNCTION tra_bbl_alloc
91
92
93   SUBROUTINE tra_bbl( kt, Kbb, Kmm, pts, Krhs )
94      !!----------------------------------------------------------------------
95      !!                  ***  ROUTINE bbl  ***
96      !!
97      !! ** Purpose :   Compute the before tracer (t & s) trend associated
98      !!              with the bottom boundary layer and add it to the general
99      !!              trend of tracer equations.
100      !!
101      !! ** Method  :   Depending on namtra_bbl namelist parameters the bbl
102      !!              diffusive and/or advective contribution to the tracer trend
103      !!              is added to the general tracer trend
104      !!----------------------------------------------------------------------
105      INTEGER,                                   INTENT(in   ) :: kt              ! ocean time-step
106      INTEGER,                                   INTENT(in   ) :: Kbb, Kmm, Krhs  ! time level indices
107      REAL(dp), DIMENSION(jpi,jpj,jpk,jpts,jpt), INTENT(inout) :: pts             ! active tracers and RHS of tracer equation
108      !
109      INTEGER  ::   ji, jj, jk   ! Dummy loop indices
110      REAL(dp), ALLOCATABLE, DIMENSION(:,:,:) ::   ztrdt, ztrds
111      !!----------------------------------------------------------------------
112      !
113      IF( ln_timing )   CALL timing_start( 'tra_bbl')
114      !
115      IF( l_trdtra )   THEN                         !* Save the T-S input trends
116         ALLOCATE( ztrdt(jpi,jpj,jpk), ztrds(jpi,jpj,jpk) )
117         ztrdt(:,:,:) = pts(:,:,:,jp_tem,Krhs)
118         ztrds(:,:,:) = pts(:,:,:,jp_sal,Krhs)
119      ENDIF
120
121      IF( l_bbl )   CALL bbl( kt, nit000, 'TRA', Kbb, Kmm )   !* bbl coef. and transport (only if not already done in trcbbl)
122
123      IF( nn_bbl_ldf == 1 ) THEN                    !* Diffusive bbl
124         !
125         CALL tra_bbl_dif( pts(:,:,:,:,Kbb), pts(:,:,:,:,Krhs), jpts, Kmm )
126         IF( sn_cfctl%l_prtctl )  &
127         CALL prt_ctl( tab3d_1=pts(:,:,:,jp_tem,Krhs), clinfo1=' bbl_ldf  - Ta: ', mask1=tmask, &
128            &          tab3d_2=pts(:,:,:,jp_sal,Krhs), clinfo2=           ' Sa: ', mask2=tmask, clinfo3='tra' )
129         CALL iom_put( "ahu_bbl", ahu_bbl )   ! bbl diffusive flux i-coef
130         CALL iom_put( "ahv_bbl", ahv_bbl )   ! bbl diffusive flux j-coef
131         !
132      ENDIF
133      !
134      IF( nn_bbl_adv /= 0 ) THEN                    !* Advective bbl
135         !
136CALL tra_bbl_adv( pts(:,:,:,:,Kbb), pts(:,:,:,:,Krhs), jpts, Kmm )
137         IF(sn_cfctl%l_prtctl)   &
138         CALL prt_ctl( tab3d_1=pts(:,:,:,jp_tem,Krhs), clinfo1=' bbl_adv  - Ta: ', mask1=tmask, &
139            &          tab3d_2=pts(:,:,:,jp_sal,Krhs), clinfo2=           ' Sa: ', mask2=tmask, clinfo3='tra' )
140         CALL iom_put( "uoce_bbl", utr_bbl )  ! bbl i-transport
141         CALL iom_put( "voce_bbl", vtr_bbl )  ! bbl j-transport
142         !
143      ENDIF
144
145      IF( l_trdtra )   THEN                      ! send the trends for further diagnostics
146         ztrdt(:,:,:) = pts(:,:,:,jp_tem,Krhs) - ztrdt(:,:,:)
147         ztrds(:,:,:) = pts(:,:,:,jp_sal,Krhs) - ztrds(:,:,:)
148         CALL trd_tra( kt, Kmm, Krhs, 'TRA', jp_tem, jptra_bbl, ztrdt )
149         CALL trd_tra( kt, Kmm, Krhs, 'TRA', jp_sal, jptra_bbl, ztrds )
150         DEALLOCATE( ztrdt, ztrds )
151      ENDIF
152      !
153      IF( ln_timing )  CALL timing_stop( 'tra_bbl')
154      !
155   END SUBROUTINE tra_bbl
156
157
158   SUBROUTINE tra_bbl_dif( pt, pt_rhs, kjpt, Kmm )
159      !!----------------------------------------------------------------------
160      !!                  ***  ROUTINE tra_bbl_dif  ***
161      !!
162      !! ** Purpose :   Computes the bottom boundary horizontal and vertical
163      !!                advection terms.
164      !!
165      !! ** Method  : * diffusive bbl only (nn_bbl_ldf=1) :
166      !!        When the product grad( rho) * grad(h) < 0 (where grad is an
167      !!      along bottom slope gradient) an additional lateral 2nd order
168      !!      diffusion along the bottom slope is added to the general
169      !!      tracer trend, otherwise the additional trend is set to 0.
170      !!      A typical value of ahbt is 2000 m2/s (equivalent to
171      !!      a downslope velocity of 20 cm/s if the condition for slope
172      !!      convection is satified)
173      !!
174      !! ** Action  :   pt_rhs   increased by the bbl diffusive trend
175      !!
176      !! References : Beckmann, A., and R. Doscher, 1997, J. Phys.Oceanogr., 581-591.
177      !!              Campin, J.-M., and H. Goosse, 1999, Tellus, 412-430.
178      !!----------------------------------------------------------------------
179      INTEGER                              , INTENT(in   ) ::   kjpt   ! number of tracers
180      REAL(dp), DIMENSION(jpi,jpj,jpk,kjpt), INTENT(in   ) ::   pt     ! before and now tracer fields
181      REAL(dp), DIMENSION(jpi,jpj,jpk,kjpt), INTENT(inout) ::   pt_rhs ! tracer trend
182      INTEGER                              , INTENT(in   ) ::   Kmm    ! time level indices
183      !
184      INTEGER  ::   ji, jj, jn   ! dummy loop indices
185      INTEGER  ::   ik           ! local integers
186      REAL(dp) ::   zbtr         ! local scalars
187      REAL(wp), DIMENSION(A2D(nn_hls)) ::   zptb   ! workspace
188      !!----------------------------------------------------------------------
189      !
190      DO jn = 1, kjpt                                     ! tracer loop
191         !                                                ! ===========
192         DO_2D( 1, 1, 1, 1 )
193            ik = mbkt(ji,jj)                             ! bottom T-level index
194            zptb(ji,jj) = pt(ji,jj,ik,jn)                ! bottom before T and S
195         END_2D
196         !
197         DO_2D( 0, 0, 0, 0 )                               ! Compute the trend
198            ik = mbkt(ji,jj)                            ! bottom T-level index
199            pt_rhs(ji,jj,ik,jn) = pt_rhs(ji,jj,ik,jn)                                                  &
200               &                + (  ahu_bbl(ji  ,jj  ) * ( zptb(ji+1,jj  ) - zptb(ji  ,jj  ) )     &
201               &                   - ahu_bbl(ji-1,jj  ) * ( zptb(ji  ,jj  ) - zptb(ji-1,jj  ) )     &
202               &                   + ahv_bbl(ji  ,jj  ) * ( zptb(ji  ,jj+1) - zptb(ji  ,jj  ) )     &
203               &                   - ahv_bbl(ji  ,jj-1) * ( zptb(ji  ,jj  ) - zptb(ji  ,jj-1) )  )  &
204               &                * r1_e1e2t(ji,jj) / e3t(ji,jj,ik,Kmm)
205         END_2D
206         !                                                  ! ===========
207      END DO                                                ! end tracer
208      !                                                     ! ===========
209   END SUBROUTINE tra_bbl_dif
210
211
212   ! NOTE: [tiling] tiling changes the results, but only the order of floating point operations is different
213   SUBROUTINE tra_bbl_adv( pt, pt_rhs, kjpt, Kmm )
214      !!----------------------------------------------------------------------
215      !!                  ***  ROUTINE trc_bbl  ***
216      !!
217      !! ** Purpose :   Compute the before passive tracer trend associated
218      !!     with the bottom boundary layer and add it to the general trend
219      !!     of tracer equations.
220      !! ** Method  :   advective bbl (nn_bbl_adv = 1 or 2) :
221      !!      nn_bbl_adv = 1   use of the ocean near bottom velocity as bbl velocity
222      !!      nn_bbl_adv = 2   follow Campin and Goosse (1999) implentation i.e.
223      !!                       transport proportional to the along-slope density gradient
224      !!
225      !! References : Beckmann, A., and R. Doscher, 1997, J. Phys.Oceanogr., 581-591.
226      !!              Campin, J.-M., and H. Goosse, 1999, Tellus, 412-430.
227      !!----------------------------------------------------------------------
228      INTEGER                              , INTENT(in   ) ::   kjpt   ! number of tracers
229      REAL(dp), DIMENSION(jpi,jpj,jpk,kjpt), INTENT(in   ) ::   pt     ! before and now tracer fields
230      REAL(dp), DIMENSION(jpi,jpj,jpk,kjpt), INTENT(inout) ::   pt_rhs ! tracer trend
231      INTEGER                              , INTENT(in   ) ::   Kmm    ! time level indices
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(dp) ::   zbtr, ztra               ! local scalars
237      REAL(dp) ::   zu_bbl, zv_bbl           !   -      -
238      !!----------------------------------------------------------------------
239      !                                                          ! ===========
240      DO jn = 1, kjpt                                            ! tracer loop
241         !                                                       ! ===========
242         DO_2D_OVR( 1, 0, 1, 0 )            ! CAUTION start from i=1 to update i=2 when cyclic east-west
243            IF( utr_bbl(ji,jj) /= 0.e0 ) THEN            ! non-zero i-direction bbl advection
244               ! down-slope i/k-indices (deep)      &   up-slope i/k indices (shelf)
245               iid  = ji + MAX( 0, mgrhu(ji,jj) )   ;   iis  = ji + 1 - MAX( 0, mgrhu(ji,jj) )
246               ikud = mbku_d(ji,jj)                 ;   ikus = mbku(ji,jj)
247               zu_bbl = ABS( utr_bbl(ji,jj) )
248               !
249               !                                               ! up  -slope T-point (shelf bottom point)
250               zbtr = r1_e1e2t(iis,jj) / e3t(iis,jj,ikus,Kmm)
251               ztra = zu_bbl * ( pt(iid,jj,ikus,jn) - pt(iis,jj,ikus,jn) ) * zbtr
252               pt_rhs(iis,jj,ikus,jn) = pt_rhs(iis,jj,ikus,jn) + ztra
253               !
254               DO jk = ikus, ikud-1                            ! down-slope upper to down T-point (deep column)
255                  zbtr = r1_e1e2t(iid,jj) / e3t(iid,jj,jk,Kmm)
256                  ztra = zu_bbl * ( pt(iid,jj,jk+1,jn) - pt(iid,jj,jk,jn) ) * zbtr
257                  pt_rhs(iid,jj,jk,jn) = pt_rhs(iid,jj,jk,jn) + ztra
258               END DO
259               !
260               zbtr = r1_e1e2t(iid,jj) / e3t(iid,jj,ikud,Kmm)
261               ztra = zu_bbl * ( pt(iis,jj,ikus,jn) - pt(iid,jj,ikud,jn) ) * zbtr
262               pt_rhs(iid,jj,ikud,jn) = pt_rhs(iid,jj,ikud,jn) + ztra
263            ENDIF
264            !
265            IF( vtr_bbl(ji,jj) /= 0.e0 ) THEN            ! non-zero j-direction bbl advection
266               ! down-slope j/k-indices (deep)        &   up-slope j/k indices (shelf)
267               ijd  = jj + MAX( 0, mgrhv(ji,jj) )     ;   ijs  = jj + 1 - MAX( 0, mgrhv(ji,jj) )
268               ikvd = mbkv_d(ji,jj)                   ;   ikvs = mbkv(ji,jj)
269               zv_bbl = ABS( vtr_bbl(ji,jj) )
270               !
271               ! up  -slope T-point (shelf bottom point)
272               zbtr = r1_e1e2t(ji,ijs) / e3t(ji,ijs,ikvs,Kmm)
273               ztra = zv_bbl * ( pt(ji,ijd,ikvs,jn) - pt(ji,ijs,ikvs,jn) ) * zbtr
274               pt_rhs(ji,ijs,ikvs,jn) = pt_rhs(ji,ijs,ikvs,jn) + ztra
275               !
276               DO jk = ikvs, ikvd-1                            ! down-slope upper to down T-point (deep column)
277                  zbtr = r1_e1e2t(ji,ijd) / e3t(ji,ijd,jk,Kmm)
278                  ztra = zv_bbl * ( pt(ji,ijd,jk+1,jn) - pt(ji,ijd,jk,jn) ) * zbtr
279                  pt_rhs(ji,ijd,jk,jn) = pt_rhs(ji,ijd,jk,jn)  + ztra
280               END DO
281               !                                               ! down-slope T-point (deep bottom point)
282               zbtr = r1_e1e2t(ji,ijd) / e3t(ji,ijd,ikvd,Kmm)
283               ztra = zv_bbl * ( pt(ji,ijs,ikvs,jn) - pt(ji,ijd,ikvd,jn) ) * zbtr
284               pt_rhs(ji,ijd,ikvd,jn) = pt_rhs(ji,ijd,ikvd,jn) + ztra
285            ENDIF
286         END_2D
287         !                                                       ! ===========
288      END DO                                                     ! end tracer
289      !                                                          ! ===========
290   END SUBROUTINE tra_bbl_adv
291
292
293   SUBROUTINE bbl( kt, kit000, cdtype, Kbb, Kmm )
294      !!----------------------------------------------------------------------
295      !!                  ***  ROUTINE bbl  ***
296      !!
297      !! ** Purpose :   Computes the bottom boundary horizontal and vertical
298      !!                advection terms.
299      !!
300      !! ** Method  : * diffusive bbl (nn_bbl_ldf=1) :
301      !!        When the product grad( rho) * grad(h) < 0 (where grad is an
302      !!      along bottom slope gradient) an additional lateral 2nd order
303      !!      diffusion along the bottom slope is added to the general
304      !!      tracer trend, otherwise the additional trend is set to 0.
305      !!      A typical value of ahbt is 2000 m2/s (equivalent to
306      !!      a downslope velocity of 20 cm/s if the condition for slope
307      !!      convection is satified)
308      !!              * advective bbl (nn_bbl_adv=1 or 2) :
309      !!      nn_bbl_adv = 1   use of the ocean velocity as bbl velocity
310      !!      nn_bbl_adv = 2   follow Campin and Goosse (1999) implentation
311      !!        i.e. transport proportional to the along-slope density gradient
312      !!
313      !!      NB: the along slope density gradient is evaluated using the
314      !!      local density (i.e. referenced at a common local depth).
315      !!
316      !! References : Beckmann, A., and R. Doscher, 1997, J. Phys.Oceanogr., 581-591.
317      !!              Campin, J.-M., and H. Goosse, 1999, Tellus, 412-430.
318      !!----------------------------------------------------------------------
319      INTEGER         , INTENT(in   ) ::   kt       ! ocean time-step index
320      INTEGER         , INTENT(in   ) ::   kit000   ! first time step index
321      CHARACTER(len=3), INTENT(in   ) ::   cdtype   ! =TRA or TRC (tracer indicator)
322      INTEGER         , INTENT(in   ) ::   Kbb, Kmm ! ocean time level index
323      !
324      INTEGER  ::   ji, jj                    ! dummy loop indices
325      INTEGER  ::   ik                        ! local integers
326      INTEGER  ::   iis, iid, ikus, ikud      !   -       -
327      INTEGER  ::   ijs, ijd, ikvs, ikvd      !   -       -
328      REAL(wp) ::   za, zb, zgdrho            ! local scalars
329      REAL(wp) ::   zsign, zsigna, zgbbl      !   -      -
330      REAL(wp), DIMENSION(A2D(nn_hls),jpts)    :: zts! 3D workspace
331      REAL(dp), DIMENSION(A2D(nn_hls),jpts)    :: zab! 3D workspace
332      REAL(wp), DIMENSION(A2D(nn_hls))        :: zub, zvb, zdep   ! 2D workspace
333      !!----------------------------------------------------------------------
334      !
335      IF( .NOT. l_istiled .OR. ntile == 1 )  THEN                       ! Do only on the first tile
336         IF( kt == kit000 )  THEN
337            IF(lwp)  WRITE(numout,*)
338            IF(lwp)  WRITE(numout,*) 'trabbl:bbl : Compute bbl velocities and diffusive coefficients in ', cdtype
339            IF(lwp)  WRITE(numout,*) '~~~~~~~~~~'
340         ENDIF
341      ENDIF
342      !                                        !* bottom variables (T, S, alpha, beta, depth, velocity)
343      DO_2D( 1, 1, 1, 1 )
344         ik = mbkt(ji,jj)                             ! bottom T-level index
345         zts (ji,jj,jp_tem) = ts(ji,jj,ik,jp_tem,Kbb) ! bottom before T and S
346         zts (ji,jj,jp_sal) = ts(ji,jj,ik,jp_sal,Kbb)
347         !
348         zdep(ji,jj) = gdept(ji,jj,ik,Kmm)            ! bottom T-level reference depth
349         zub (ji,jj) = uu(ji,jj,mbku(ji,jj),Kmm)      ! bottom velocity
350         zvb (ji,jj) = vv(ji,jj,mbkv(ji,jj),Kmm)
351      END_2D
352      !
353      CALL eos_rab( CASTDP(zts), CASTDP(zdep), zab, Kmm )
354      !
355      !                                   !-------------------!
356      IF( nn_bbl_ldf == 1 ) THEN          !   diffusive bbl   !
357         !                                !-------------------!
358         DO_2D_OVR( 1, 0, 1, 0 )                   ! (criteria for non zero flux: grad(rho).grad(h) < 0 )
359            !                                                   ! i-direction
360            za = zab(ji+1,jj,jp_tem) + zab(ji,jj,jp_tem)              ! 2*(alpha,beta) at u-point
361            zb = zab(ji+1,jj,jp_sal) + zab(ji,jj,jp_sal)
362            !                                                         ! 2*masked bottom density gradient
363            zgdrho = (  za * ( zts(ji+1,jj,jp_tem) - zts(ji,jj,jp_tem) )    &
364               &      - zb * ( zts(ji+1,jj,jp_sal) - zts(ji,jj,jp_sal) )  ) * umask(ji,jj,1)
365            !
366            zsign  = SIGN(  0.5_wp, -zgdrho * REAL( mgrhu(ji,jj))  )    ! sign of ( i-gradient * i-slope )
367            ahu_bbl(ji,jj) = ( 0.5 - zsign ) * ahu_bbl_0(ji,jj)       ! masked diffusive flux coeff.
368            !
369            !                                                   ! j-direction
370            za = zab(ji,jj+1,jp_tem) + zab(ji,jj,jp_tem)              ! 2*(alpha,beta) at v-point
371            zb = zab(ji,jj+1,jp_sal) + zab(ji,jj,jp_sal)
372            !                                                         ! 2*masked bottom density gradient
373            zgdrho = (  za * ( zts(ji,jj+1,jp_tem) - zts(ji,jj,jp_tem) )    &
374               &      - zb * ( zts(ji,jj+1,jp_sal) - zts(ji,jj,jp_sal) )  ) * vmask(ji,jj,1)
375            !
376            zsign = SIGN(  0.5_wp, -zgdrho * REAL( mgrhv(ji,jj))  )     ! sign of ( j-gradient * j-slope )
377            ahv_bbl(ji,jj) = ( 0.5 - zsign ) * ahv_bbl_0(ji,jj)
378         END_2D
379         !
380      ENDIF
381      !
382      !                                   !-------------------!
383      IF( nn_bbl_adv /= 0 ) THEN          !   advective bbl   !
384         !                                !-------------------!
385         SELECT CASE ( nn_bbl_adv )             !* bbl transport type
386         !
387         CASE( 1 )                                   != use of upper velocity
388            DO_2D_OVR( 1, 0, 1, 0 )                              ! criteria: grad(rho).grad(h)<0  and grad(rho).grad(h)<0
389               !                                                  ! i-direction
390               za = zab(ji+1,jj,jp_tem) + zab(ji,jj,jp_tem)               ! 2*(alpha,beta) at u-point
391               zb = zab(ji+1,jj,jp_sal) + zab(ji,jj,jp_sal)
392               !                                                          ! 2*masked bottom density gradient
393               zgdrho = (  za * ( zts(ji+1,jj,jp_tem) - zts(ji,jj,jp_tem) )    &
394                         - zb * ( zts(ji+1,jj,jp_sal) - zts(ji,jj,jp_sal) )  ) * umask(ji,jj,1)
395               !
396               zsign = SIGN(  0.5_wp, - zgdrho   * REAL( mgrhu(ji,jj))  )   ! sign of i-gradient * i-slope
397               zsigna= SIGN(  0.5_wp, zub(ji,jj) * REAL( mgrhu(ji,jj))  )   ! sign of u * i-slope
398               !
399               !                                                          ! bbl velocity
400               utr_bbl(ji,jj) = ( 0.5 + zsigna ) * ( 0.5 - zsign ) * e2u(ji,jj) * e3u_bbl_0(ji,jj) * zub(ji,jj)
401               !
402               !                                                  ! j-direction
403               za = zab(ji,jj+1,jp_tem) + zab(ji,jj,jp_tem)               ! 2*(alpha,beta) at v-point
404               zb = zab(ji,jj+1,jp_sal) + zab(ji,jj,jp_sal)
405               !                                                          ! 2*masked bottom density gradient
406               zgdrho = (  za * ( zts(ji,jj+1,jp_tem) - zts(ji,jj,jp_tem) )    &
407                  &      - zb * ( zts(ji,jj+1,jp_sal) - zts(ji,jj,jp_sal) )  ) * vmask(ji,jj,1)
408               zsign = SIGN(  0.5_wp, - zgdrho   * REAL( mgrhv(ji,jj))  )   ! sign of j-gradient * j-slope
409               zsigna= SIGN(  0.5_wp, zvb(ji,jj) * REAL( mgrhv(ji,jj))  )   ! sign of u * i-slope
410               !
411               !                                                          ! bbl transport
412               vtr_bbl(ji,jj) = ( 0.5 + zsigna ) * ( 0.5 - zsign ) * e1v(ji,jj) * e3v_bbl_0(ji,jj) * zvb(ji,jj)
413            END_2D
414            !
415         CASE( 2 )                                 != bbl velocity = F( delta rho )
416            zgbbl = grav * rn_gambbl
417            DO_2D_OVR( 1, 0, 1, 0 )                         ! criteria: rho_up > rho_down
418               !                                                  ! i-direction
419               ! down-slope T-point i/k-index (deep)  &   up-slope T-point i/k-index (shelf)
420               iid  = ji + MAX( 0, mgrhu(ji,jj) )
421               iis  = ji + 1 - MAX( 0, mgrhu(ji,jj) )
422               !
423               ikud = mbku_d(ji,jj)
424               ikus = mbku(ji,jj)
425               !
426               za = zab(ji+1,jj,jp_tem) + zab(ji,jj,jp_tem)               ! 2*(alpha,beta) at u-point
427               zb = zab(ji+1,jj,jp_sal) + zab(ji,jj,jp_sal)
428               !                                                          !   masked bottom density gradient
429               zgdrho = 0.5 * (  za * ( zts(iid,jj,jp_tem) - zts(iis,jj,jp_tem) )    &
430                  &            - zb * ( zts(iid,jj,jp_sal) - zts(iis,jj,jp_sal) )  ) * umask(ji,jj,1)
431               zgdrho = MAX( 0.e0, zgdrho )                               ! only if shelf is denser than deep
432               !
433               !                                                          ! bbl transport (down-slope direction)
434               utr_bbl(ji,jj) = e2u(ji,jj) * e3u_bbl_0(ji,jj) * zgbbl * zgdrho * REAL( mgrhu(ji,jj) )
435               !
436               !                                                  ! j-direction
437               !  down-slope T-point j/k-index (deep)  &   of the up  -slope T-point j/k-index (shelf)
438               ijd  = jj + MAX( 0, mgrhv(ji,jj) )
439               ijs  = jj + 1 - MAX( 0, mgrhv(ji,jj) )
440               !
441               ikvd = mbkv_d(ji,jj)
442               ikvs = mbkv(ji,jj)
443               !
444               za = zab(ji,jj+1,jp_tem) + zab(ji,jj,jp_tem)               ! 2*(alpha,beta) at v-point
445               zb = zab(ji,jj+1,jp_sal) + zab(ji,jj,jp_sal)
446               !                                                          !   masked bottom density gradient
447               zgdrho = 0.5 * (  za * ( zts(ji,ijd,jp_tem) - zts(ji,ijs,jp_tem) )    &
448                  &            - zb * ( zts(ji,ijd,jp_sal) - zts(ji,ijs,jp_sal) )  ) * vmask(ji,jj,1)
449               zgdrho = MAX( 0.e0, zgdrho )                               ! only if shelf is denser than deep
450               !
451               !                                                          ! bbl transport (down-slope direction)
452               vtr_bbl(ji,jj) = e1v(ji,jj) * e3v_bbl_0(ji,jj) * zgbbl * zgdrho * REAL( mgrhv(ji,jj) )
453            END_2D
454         END SELECT
455         !
456      ENDIF
457      !
458   END SUBROUTINE bbl
459
460
461   SUBROUTINE tra_bbl_init
462      !!----------------------------------------------------------------------
463      !!                  ***  ROUTINE tra_bbl_init  ***
464      !!
465      !! ** Purpose :   Initialization for the bottom boundary layer scheme.
466      !!
467      !! ** Method  :   Read the nambbl namelist and check the parameters
468      !!              called by nemo_init at the first timestep (kit000)
469      !!----------------------------------------------------------------------
470      INTEGER ::   ji, jj                      ! dummy loop indices
471      INTEGER ::   ii0, ii1, ij0, ij1, ios     ! local integer
472      REAL(dp), DIMENSION(jpi,jpj) ::   zmbku, zmbkv   ! workspace
473      !!
474      NAMELIST/nambbl/ ln_trabbl, nn_bbl_ldf, nn_bbl_adv, rn_ahtbbl, rn_gambbl
475      !!----------------------------------------------------------------------
476      !
477      READ  ( numnam_ref, nambbl, IOSTAT = ios, ERR = 901)
478901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'nambbl in reference namelist' )
479      !
480      READ  ( numnam_cfg, nambbl, IOSTAT = ios, ERR = 902 )
481902   IF( ios >  0 )   CALL ctl_nam ( ios , 'nambbl in configuration namelist' )
482      IF(lwm) WRITE ( numond, nambbl )
483      !
484      l_bbl = .TRUE.                 !* flag to compute bbl coef and transport
485      !
486      IF(lwp) THEN                   !* Parameter control and print
487         WRITE(numout,*)
488         WRITE(numout,*) 'tra_bbl_init : bottom boundary layer initialisation'
489         WRITE(numout,*) '~~~~~~~~~~~~'
490         WRITE(numout,*) '       Namelist nambbl : set bbl parameters'
491         WRITE(numout,*) '          bottom boundary layer flag          ln_trabbl  = ', ln_trabbl
492      ENDIF
493      IF( .NOT.ln_trabbl )   RETURN
494      !
495      IF(lwp) THEN
496         WRITE(numout,*) '          diffusive bbl (=1)   or not (=0)    nn_bbl_ldf = ', nn_bbl_ldf
497         WRITE(numout,*) '          advective bbl (=1/2) or not (=0)    nn_bbl_adv = ', nn_bbl_adv
498         WRITE(numout,*) '          diffusive bbl coefficient           rn_ahtbbl  = ', rn_ahtbbl, ' m2/s'
499         WRITE(numout,*) '          advective bbl coefficient           rn_gambbl  = ', rn_gambbl, ' s'
500      ENDIF
501      !
502      !                              ! allocate trabbl arrays
503      IF( tra_bbl_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'tra_bbl_init : unable to allocate arrays' )
504      !
505      IF(lwp) THEN
506         IF( nn_bbl_adv == 1 )    WRITE(numout,*) '       * Advective BBL using upper velocity'
507         IF( nn_bbl_adv == 2 )    WRITE(numout,*) '       * Advective BBL using velocity = F( delta rho)'
508      ENDIF
509      !
510      !                             !* vertical index of  "deep" bottom u- and v-points
511      DO_2D( 1, 0, 1, 0 )                 ! (the "shelf" bottom k-indices are mbku and mbkv)
512         mbku_d(ji,jj) = MAX(  mbkt(ji+1,jj  ) , mbkt(ji,jj)  )   ! >= 1 as mbkt=1 over land
513         mbkv_d(ji,jj) = MAX(  mbkt(ji  ,jj+1) , mbkt(ji,jj)  )
514      END_2D
515      ! converte into REAL to use lbc_lnk ; impose a min value of 1 as a zero can be set in lbclnk
516      zmbku(:,:) = REAL( mbku_d(:,:), wp )   ;     zmbkv(:,:) = REAL( mbkv_d(:,:), wp )
517      CALL lbc_lnk( 'trabbl', zmbku,'U',1.0_wp, zmbkv,'V',1.0_wp)
518      mbku_d(:,:) = MAX( INT( zmbku(:,:) ), 1 ) ;  mbkv_d(:,:) = MAX( NINT( zmbkv(:,:) ), 1 )
519      !
520      !                             !* sign of grad(H) at u- and v-points; zero if grad(H) = 0
521      mgrhu(:,:) = 0   ;   mgrhv(:,:) = 0
522      DO_2D( 1, 0, 1, 0 )
523         IF( gdept_0(ji+1,jj,mbkt(ji+1,jj)) - gdept_0(ji,jj,mbkt(ji,jj)) /= 0._wp ) THEN
524            mgrhu(ji,jj) = INT(  SIGN( 1.0_wp, gdept_0(ji+1,jj,mbkt(ji+1,jj)) - gdept_0(ji,jj,mbkt(ji,jj)) )  )
525         ENDIF
526         !
527         IF( gdept_0(ji,jj+1,mbkt(ji,jj+1)) - gdept_0(ji,jj,mbkt(ji,jj)) /= 0._wp ) THEN
528            mgrhv(ji,jj) = INT(  SIGN( 1.0_wp, gdept_0(ji,jj+1,mbkt(ji,jj+1)) - gdept_0(ji,jj,mbkt(ji,jj)) )  )
529         ENDIF
530      END_2D
531      !
532      DO_2D( 1, 0, 1, 0 )           !* bbl thickness at u- (v-) point; minimum of top & bottom e3u_0 (e3v_0)
533         e3u_bbl_0(ji,jj) = MIN( e3u_0(ji,jj,mbkt(ji+1,jj  )), e3u_0(ji,jj,mbkt(ji,jj)) )
534         e3v_bbl_0(ji,jj) = MIN( e3v_0(ji,jj,mbkt(ji  ,jj+1)), e3v_0(ji,jj,mbkt(ji,jj)) )
535      END_2D
536      CALL lbc_lnk( 'trabbl', e3u_bbl_0, 'U', 1.0_wp , e3v_bbl_0, 'V', 1.0_wp )      ! lateral boundary conditions
537      !
538      !                             !* masked diffusive flux coefficients
539      ahu_bbl_0(:,:) = rn_ahtbbl * e2_e1u(:,:) * e3u_bbl_0(:,:) * umask(:,:,1)
540      ahv_bbl_0(:,:) = rn_ahtbbl * e1_e2v(:,:) * e3v_bbl_0(:,:) * vmask(:,:,1)
541      !
542   END SUBROUTINE tra_bbl_init
543
544   !!======================================================================
545END MODULE trabbl
546
Note: See TracBrowser for help on using the repository browser.