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.
Changeset 503 for trunk/NEMO/OPA_SRC/TRA/trabbl.F90 – NEMO

Ignore:
Timestamp:
2006-09-27T10:52:29+02:00 (18 years ago)
Author:
opalod
Message:

nemo_v1_update_064 : CT : general trends update including the addition of mean windows analysis possibility in the mixed layer

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMO/OPA_SRC/TRA/trabbl.F90

    r481 r503  
    44   !! Ocean physics :  advective and/or diffusive bottom boundary layer scheme 
    55   !!============================================================================== 
     6   !! History :  8.0  !  96-06  (L. Mortier)  Original code 
     7   !!            8.0  !  97-11  (G. Madec)  Optimization 
     8   !!            8.5  !  02-08  (G. Madec)  free form + modules 
     9   !!---------------------------------------------------------------------- 
    610#if   defined key_trabbl_dif   ||   defined key_trabbl_adv   || defined key_esopa 
    711   !!---------------------------------------------------------------------- 
    812   !!   'key_trabbl_dif'   or            diffusive bottom boundary layer 
    913   !!   'key_trabbl_adv'                 advective bottom boundary layer 
     14   !!---------------------------------------------------------------------- 
    1015   !!---------------------------------------------------------------------- 
    1116   !!   tra_bbl_dif  : update the active tracer trends due to the bottom 
     
    1520   !!   tra_bbl_init : initialization, namlist read, parameters control 
    1621   !!---------------------------------------------------------------------- 
    17    !! * Modules used 
    18    USE oce                  ! ocean dynamics and active tracers 
    19    USE dom_oce              ! ocean space and time domain 
    20    USE trdmod_oce           ! ocean variables trends 
    21    USE in_out_manager       ! I/O manager 
    22    USE lbclnk               ! ocean lateral boundary conditions 
    23    USE prtctl               ! Print control 
     22   USE oce                ! ocean dynamics and active tracers 
     23   USE dom_oce            ! ocean space and time domain 
     24   USE trdmod             ! ocean active tracers trends 
     25   USE trdmod_oce         ! ocean variables trends 
     26   USE in_out_manager     ! I/O manager 
     27   USE lbclnk             ! ocean lateral boundary conditions 
     28   USE prtctl             ! Print control 
    2429 
    2530   IMPLICIT NONE 
    2631   PRIVATE 
    2732 
    28    !! * Routine accessibility 
    2933   PUBLIC tra_bbl_dif    ! routine called by step.F90 
    3034   PUBLIC tra_bbl_adv    ! routine called by step.F90 
    3135 
    32    !! * Shared module variables 
    33    REAL(wp), PUBLIC ::            &  !!: * bbl namelist * 
    34       atrbbl = 1.e+3                  !: lateral coeff. for bottom boundary  
    35       !                               !  layer scheme (m2/s)  
     36   !!* Namelist nambbl: bottom boundary layer 
     37   REAL(wp), PUBLIC ::   atrbbl = 1.e+3   !: lateral coeff. for bottom boundary layer scheme (m2/s) 
     38   NAMELIST/nambbl/ atrbbl 
     39 
    3640# if defined key_trabbl_dif 
    37    LOGICAL, PUBLIC, PARAMETER ::   &  !: 
    38       lk_trabbl_dif = .TRUE.          !: diffusive bottom boundary layer flag 
     41   LOGICAL, PUBLIC, PARAMETER ::   lk_trabbl_dif = .TRUE.          !: diffusive bottom boundary layer flag 
    3942# else 
    40    LOGICAL, PUBLIC, PARAMETER ::   &  !: 
    41       lk_trabbl_dif = .FALSE.         !: diffusive bottom boundary layer flag 
     43   LOGICAL, PUBLIC, PARAMETER ::   lk_trabbl_dif = .FALSE.         !: diffusive bottom boundary layer flag 
    4244# endif 
    4345 
    4446# if defined key_trabbl_adv 
    45    LOGICAL, PUBLIC, PARAMETER ::    &  !: 
    46       lk_trabbl_adv = .TRUE.   !: advective bottom boundary layer flag 
    47    REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpk) ::   &  !: 
    48        u_bbl, v_bbl,  &  !: velocity involved in exhanges in the advective BBL 
    49        w_bbl             !: vertical increment of velocity due to advective BBL 
    50        !                 !  only affect tracer vertical advection 
     47   LOGICAL, PUBLIC, PARAMETER ::   lk_trabbl_adv = .TRUE.   !: advective bottom boundary layer flag 
     48   REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpk) ::   u_bbl      !: 3 components of the velocity 
     49   REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpk) ::   v_bbl      !: associated with advective BBL 
     50   REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpk) ::   w_bbl      !: (only affect tracer) 
    5151# else 
    52    LOGICAL, PUBLIC, PARAMETER ::    &  !: 
    53       lk_trabbl_adv = .FALSE.  !: advective bottom boundary layer flag 
     52   LOGICAL, PUBLIC, PARAMETER ::   lk_trabbl_adv = .FALSE.  !: advective bottom boundary layer flag 
    5453# endif 
    5554 
    56    !! * Module variables 
    57    INTEGER, DIMENSION(jpi,jpj) ::   &  !: 
    58       mbkt,           &   ! vertical index of the bottom ocean T-level 
    59       mbku, mbkv          ! vertical index of the bottom ocean U/V-level 
     55   INTEGER, DIMENSION(jpi,jpj) ::   mbkt          ! vertical index of the bottom ocean T-level 
     56   INTEGER, DIMENSION(jpi,jpj) ::   mbku, mbkv    ! vertical index of the bottom ocean U/V-level 
    6057 
    6158   !! * Substitutions 
     
    6360#  include "vectopt_loop_substitute.h90" 
    6461   !!---------------------------------------------------------------------- 
    65    !!   OPA 9.0 , LOCEAN-IPSL (2005)  
     62   !!   OPA 9.0 , LOCEAN-IPSL (2006)  
    6663   !! $Header$  
    67    !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt  
     64   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
    6865   !!---------------------------------------------------------------------- 
    6966 
     
    10299      !! ** Action  : - update (ta,sa) at the bottom level with the bottom 
    103100      !!                boundary layer trend 
    104       !!              - save the trends in tldfbbl/sldfbbl ('key_trdtra') 
    105       !! 
    106       !! References : 
    107       !!     Beckmann, A., and R. Doscher, 1997, J. Phys.Oceanogr., 581-591. 
    108       !! 
    109       !! History : 
    110       !!   8.0  !  96-06  (L. Mortier)  Original code 
    111       !!   8.0  !  97-11  (G. Madec)  Optimization 
    112       !!   8.5  !  02-08  (G. Madec)  free form + modules 
    113       !!   9.0  !  04-08  (C. Talandier) New trends organization 
    114       !!---------------------------------------------------------------------- 
    115       !! * Modules used      
    116       USE oce, ONLY :    ztdta => ua,     & ! use ua as 3D workspace    
    117                          ztdsa => va        ! use va as 3D workspace    
    118       USE eosbn2                            ! equation of state 
    119  
    120       !! * Arguments  
    121       INTEGER, INTENT( in ) ::   kt         ! ocean time-step 
    122  
    123       !! * Local declarations 
    124       INTEGER ::   ji, jj                   ! dummy loop indices 
    125       INTEGER ::   ik 
    126       INTEGER ::   ii0, ii1, ij0, ij1       ! temporary integers 
     101      !!              - save the trends in ztrdt/ztrds ('key_trdtra') 
     102      !! 
     103      !! References : Beckmann, A., and R. Doscher, 1997, J. Phys.Oceanogr., 581-591. 
     104      !!---------------------------------------------------------------------- 
     105      USE oce, ONLY :   ztrdt => ua   ! use ua as 3D workspace    
     106      USE oce, ONLY :   ztrds => va   ! use va as 3D workspace    
     107      USE eosbn2                      ! equation of state 
     108      !! 
     109      INTEGER, INTENT( in ) ::   kt   ! ocean time-step 
     110      !! 
     111      INTEGER  ::   ji, jj                   ! dummy loop indices 
     112      INTEGER  ::   ik 
     113      INTEGER  ::   ii0, ii1, ij0, ij1       ! temporary integers 
    127114      INTEGER  ::   iku1, iku2, ikv1,ikv2   ! temporary intergers 
    128115      REAL(wp) ::   ze3u, ze3v              ! temporary scalars 
    129       INTEGER ::   iku, ikv 
     116      INTEGER  ::   iku, ikv 
    130117      REAL(wp) ::   & 
    131118         zsign, zt, zs, zh, zalbet,      &  ! temporary scalars 
    132119         zgdrho, zbtr, zta, zsa 
    133120      REAL(wp), DIMENSION(jpi,jpj) ::    & 
    134         zki, zkj, zkw, zkx, zky, zkz,    &  ! temporary workspace arrays 
     121        zki, zkj, zkw, zkx, zky, zkz,    &  ! 2D workspace arrays 
    135122        ztnb, zsnb, zdep,                & 
    136123        ztbb, zsbb, zahu, zahv 
    137       REAL(wp) ::   & 
    138          fsalbt, pft, pfs, pfh              ! statement function 
     124      REAL(wp) ::    fsalbt, pft, pfs, pfh   ! statement function 
    139125      !!---------------------------------------------------------------------- 
    140126      ! ratio alpha/beta 
     
    161147      IF( kt == nit000 )   CALL tra_bbl_init 
    162148 
    163       ! Save ta and sa trends 
    164       IF( l_trdtra )   THEN 
    165          ztdta(:,:,:) = ta(:,:,:)  
    166          ztdsa(:,:,:) = sa(:,:,:)  
     149      IF( l_trdtra )   THEN         ! Save ta and sa trends 
     150         ztrdt(:,:,:) = ta(:,:,:)  
     151         ztrds(:,:,:) = sa(:,:,:)  
    167152      ENDIF 
    168153 
     
    170155      ! ----------------------------------------------------------------- 
    171156      ! mbathy= number of w-level, minimum value=1 (cf dommsk.F) 
    172  
    173157#  if defined key_vectopt_loop   &&   ! defined key_mpp_omp 
    174158      jj = 1 
     
    387371 
    388372      IF( cp_cfg == "orca" ) THEN 
    389  
     373         ! 
    390374         SELECT CASE ( jp_cfg ) 
    391375         !                                           ! ======================= 
     
    397381            zkx( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 4.e0 * zkx( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) 
    398382            zky( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 4.e0 * zky( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) 
    399  
     383            ! 
    400384            ! Red Sea enhancement of BBL 
    401385            ij0 =  88   ;   ij1 =  88 
     
    403387            zkx( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 10.e0 * zkx( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) 
    404388            zky( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 10.e0 * zky( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) 
    405  
     389            ! 
    406390            !                                        ! ======================= 
    407391         CASE ( 4 )                                  !  ORCA_R4 configuration 
     
    412396            zkx( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 4.e0 * zkx( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) 
    413397            zky( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 4.e0 * zky( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) 
    414  
     398            ! 
    415399         END SELECT 
    416  
     400      ! 
    417401      ENDIF 
    418402 
     
    439423      END DO 
    440424 
    441       ! save the trends for diagnostic 
    442       ! BBL lateral diffusion tracers trends 
    443       IF( l_trdtra )   THEN 
    444 #  if defined key_vectopt_loop   &&   ! defined key_mpp_omp 
    445          jj = 1 
    446          DO ji = jpi+2, jpij-jpi-1   ! vector opt. (forced unrolling) 
    447 #  else 
    448          DO jj = 2, jpjm1 
    449             DO ji = 2, jpim1 
    450 #  endif 
    451             ik = max( mbathy(ji,jj)-1, 1 ) 
    452             tldfbbl(ji,jj) = ta(ji,jj,ik) - ztdta(ji,jj,ik) 
    453             sldfbbl(ji,jj) = sa(ji,jj,ik) - ztdsa(ji,jj,ik) 
    454 #  if ! defined key_vectopt_loop   ||   defined key_mpp_omp 
    455             END DO 
    456 #  endif 
    457          END DO 
    458  
     425      IF( l_trdtra ) THEN      ! save the BBL lateral diffusion trends for diagnostic 
     426         ztrdt(:,:,:) = ta(:,:,:) - ztrdt(:,:,:) 
     427         ztrds(:,:,:) = sa(:,:,:) - ztrds(:,:,:) 
     428         CALL trd_mod(ztrdt, ztrds, jptra_trd_bbl, 'TRA', kt) 
    459429      ENDIF 
    460430 
    461       IF(ln_ctl) THEN 
    462          CALL prt_ctl(tab3d_1=ta, clinfo1=' bbl  - Ta: ', mask1=tmask, & 
    463             &         tab3d_2=sa, clinfo2=' Sa: ', mask2=tmask, clinfo3='tra') 
    464       ENDIF 
    465  
     431      IF(ln_ctl)   CALL prt_ctl( tab3d_1=ta, clinfo1=' bbl  - Ta: ', mask1=tmask,   & 
     432         &                       tab3d_2=sa, clinfo2=       ' Sa: ', mask2=tmask, clinfo3='tra' ) 
     433      ! 
    466434   END SUBROUTINE tra_bbl_dif 
    467435 
     
    489457      !! ** Method  :   Read the nambbl namelist and check the parameters 
    490458      !!      called by tra_bbl at the first timestep (nit000) 
    491       !! 
    492       !! History : 
    493       !!    8.5  !  02-08  (G. Madec)  Original code 
    494       !!---------------------------------------------------------------------- 
    495       !! * Local declarations 
     459      !!---------------------------------------------------------------------- 
    496460      INTEGER ::   ji, jj      ! dummy loop indices 
    497461      REAL(wp),  DIMENSION(jpi,jpj) :: zmbk   
    498  
    499       NAMELIST/nambbl/ atrbbl 
    500       !!---------------------------------------------------------------------- 
    501  
    502       ! Read Namelist nambbl : bottom boundary layer scheme 
    503       ! -------------------- 
    504       REWIND ( numnam ) 
     462      !!---------------------------------------------------------------------- 
     463 
     464      REWIND ( numnam )              ! Read Namelist nambbl : bottom boundary layer scheme 
    505465      READ   ( numnam, nambbl ) 
    506466 
    507  
    508       ! Parameter control and print 
    509       ! --------------------------- 
    510       IF(lwp) THEN 
     467      IF(lwp) THEN                   ! Parameter control and print 
    511468         WRITE(numout,*) 
    512469         WRITE(numout,*) 'tra_bbl_init : ' 
    513470         WRITE(numout,*) '~~~~~~~~~~~~' 
    514          IF (lk_trabbl_dif ) THEN 
    515             WRITE(numout,*) '               * Diffusive Bottom Boundary Layer' 
    516          ENDIF  
    517          IF( lk_trabbl_adv ) THEN 
    518             WRITE(numout,*) '               * Advective Bottom Boundary Layer' 
    519          ENDIF 
    520          WRITE(numout,*) '          Namelist nambbl : set bbl parameters' 
    521          WRITE(numout,*) 
     471         IF (lk_trabbl_dif )   WRITE(numout,*) '               * Diffusive Bottom Boundary Layer' 
     472         IF( lk_trabbl_adv )   WRITE(numout,*) '               * Advective Bottom Boundary Layer' 
     473         WRITE(numout,*) '       Namelist nambbl : set bbl parameters' 
    522474         WRITE(numout,*) '          bottom boundary layer coef.    atrbbl = ', atrbbl 
    523          WRITE(numout,*) 
    524475      ENDIF 
    525476  
     
    545496 
    546497# if defined key_trabbl_adv 
    547       ! initialisation of w_bbl to zero 
    548       w_bbl(:,:,:) = 0.e0     
     498      w_bbl(:,:,:) = 0.e0          ! initialisation of w_bbl to zero 
    549499# endif 
    550  
     500      ! 
    551501   END SUBROUTINE tra_bbl_init 
    552502 
     
    558508   LOGICAL, PUBLIC, PARAMETER ::   lk_trabbl_adv = .FALSE.   !: adv  bbl flag 
    559509CONTAINS 
    560    SUBROUTINE tra_bbl_dif (kt )              ! Empty routine 
    561       INTEGER, INTENT(in) :: kt 
     510   SUBROUTINE tra_bbl_dif( kt )              ! Empty routine 
    562511      WRITE(*,*) 'tra_bbl_dif: You should not have seen this print! error?', kt 
    563512   END SUBROUTINE tra_bbl_dif 
    564    SUBROUTINE tra_bbl_adv (kt )              ! Empty routine 
    565       INTEGER, INTENT(in) :: kt 
     513   SUBROUTINE tra_bbl_adv( kt )              ! Empty routine 
    566514      WRITE(*,*) 'tra_bbl_adv: You should not have seen this print! error?', kt 
    567515   END SUBROUTINE tra_bbl_adv 
Note: See TracChangeset for help on using the changeset viewer.