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 1492 – NEMO

Changeset 1492


Ignore:
Timestamp:
2009-07-17T11:48:07+02:00 (15 years ago)
Author:
ctlod
Message:

style and cosmetic changes

Location:
trunk/NEMO/OPA_SRC
Files:
3 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMO/OPA_SRC/ZDF/zdf_oce.F90

    r1417 r1492  
    44   !! Ocean physics : define vertical mixing variables 
    55   !!===================================================================== 
     6   !! history :  1.0  !  2002-06  (G. Madec) Original code 
     7   !!            3.2  !  2009-07  (G.Madec) addition of avm 
    68   !!---------------------------------------------------------------------- 
    7    !!  OPA 9.0 , LOCEAN-IPSL (2005)  
    8    !! $Id$  
    9    !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt  
     9 
    1010   !!---------------------------------------------------------------------- 
    11    !!---------------------------------------------------------------------- 
    12    !!   zdf_init    : initialization, namelist read, and parameters control 
    13    !!---------------------------------------------------------------------- 
    14    !! * Modules used 
    15    USE par_oce         ! mesh and scale factors 
     11   USE par_oce         ! ocean parameters 
    1612 
    1713   IMPLICIT NONE 
    1814   PRIVATE 
    1915 
    20    !! * Share Module variables 
    21    LOGICAL, PARAMETER, PUBLIC ::    &   !: 
    2216#if defined key_zdfcst   ||   defined key_esopa 
    23       lk_zdfcst        = .TRUE.         !: constant vertical mixing flag 
     17   LOGICAL, PARAMETER, PUBLIC ::   lk_zdfcst        = .TRUE.         !: constant vertical mixing flag 
    2418#else 
    25       lk_zdfcst        = .FALSE.        !: constant vertical mixing flag 
     19   LOGICAL, PARAMETER, PUBLIC ::   lk_zdfcst        = .FALSE.        !: constant vertical mixing flag 
    2620#endif 
    27    LOGICAL, PUBLIC ::                & !!! namzdf: vertical diffusion 
    28       ln_zdfexp        = .FALSE. ,   &  !: explicit vertical diffusion scheme flag 
    29       ln_zdfevd        = .TRUE.  ,   &  !: convection: enhanced vertical diffusion flag 
    30       ln_zdfnpc        = .FALSE.        !: convection: non-penetrative convection flag 
    3121 
    32    INTEGER, PUBLIC ::    & !!: namzdf:  vertical diffusion 
    33       n_zdfexp = 3    ,  &  !: number of sub-time step (explicit time stepping) 
    34       n_evdm   = 1          !: =0/1 flag to apply enhanced avm or not 
    35   
    36    REAL(wp), PUBLIC ::   & !!: namzdf   vertical diffusion 
    37       avm0  = 1.e-4_wp,  &  !: vertical eddy viscosity (m2/s) 
    38       avt0  = 1.e-5_wp,  &  !: vertical eddy diffusivity (m2/s) 
    39       avevd = 1._wp         !: vertical eddy coeff. for enhanced vert. diff. (m2/s) 
     22   !                                          !!* namelist namzdf: vertical diffusion 
     23   LOGICAL , PUBLIC ::   ln_zdfexp = .FALSE.   !: explicit vertical diffusion scheme flag 
     24   LOGICAL , PUBLIC ::   ln_zdfevd = .TRUE.    !: convection: enhanced vertical diffusion flag 
     25   LOGICAL , PUBLIC ::   ln_zdfnpc = .FALSE.   !: convection: non-penetrative convection flag 
     26   INTEGER , PUBLIC ::   n_zdfexp = 3          !: number of sub-time step (explicit time stepping) 
     27   INTEGER , PUBLIC ::   n_evdm   = 1          !: =0/1 flag to apply enhanced avm or not 
     28   REAL(wp), PUBLIC ::   avm0  = 1.e-4_wp      !: vertical eddy viscosity (m2/s) 
     29   REAL(wp), PUBLIC ::   avt0  = 1.e-5_wp      !: vertical eddy diffusivity (m2/s) 
     30   REAL(wp), PUBLIC ::   avevd = 1._wp         !: vertical eddy coeff. for enhanced vert. diff. (m2/s) 
    4031 
    41    REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpk) ::   &   !: 
    42       avmu,              &  !: vertical viscosity coeff. at uw-, vw-points 
    43       avmv,              &  !: vertical viscosity coeff. at uw-, vw-points 
    44       avt ,              &  !: vertical diffusivity coeff. at w-point 
    45       avt_evd,           &  !: convection: enhanced vertical diffusivity coeff. at w-point 
    46       avmu_evd              !: convection: enhanced vertical viscosity   coeff. at w-point 
     32   REAL(wp), PUBLIC, DIMENSION        (jpk) ::   avmb, avtb   !: background profile of avm and avt 
     33   REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpk) ::   avmu, avmv   !: vertical viscosity coeff. at uw- & vw-points   [m2/s] 
     34   REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpk) ::   avm , avt    !: vertical viscosity & diffusivity coeff. at  w-point   [m2/s] 
     35   REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpk) ::   avt_evd      !: enhanced vertical diffusivity coeff. at  w-point   [m2/s] 
     36   REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpk) ::   avmu_evd     !: enhanced vertical viscosity   coeff. at uw-point   [m2/s] 
    4737#if defined key_zdftmx 
    48    REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpk) ::   av_tide, av_tide_itf   !: Tidal mixing 
     38   REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpk) ::   av_tide      !: Tidal mixing 
     39   REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpk) ::   av_tide_itf  !: Tidal mixing in the Indonesian Through Flow 
    4940#endif 
    5041  
    51    REAL(wp), PUBLIC, DIMENSION(jpk) ::   &   !: 
    52       avmb, avtb            !: background profile of avm and avt 
    53   
     42   !!---------------------------------------------------------------------- 
     43   !! NEMO/OPA 3.2 , LOCEAN-IPSL (2009)  
     44   !! $Id$  
     45   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
    5446   !!====================================================================== 
    5547END MODULE zdf_oce 
  • trunk/NEMO/OPA_SRC/ZDF/zdftke2.F90

    r1481 r1492  
    55   !!                 turbulent closure parameterization 
    66   !!===================================================================== 
    7    !! History :   OPA  !  1991-03  (b. blanke)  Original code 
    8    !!             7.0  !  1991-11  (G. Madec)   bug fix 
    9    !!             7.1  !  1992-10  (G. Madec)   new mixing length and eav 
    10    !!             7.2  !  1993-03  (M. Guyon)   symetrical conditions 
    11    !!             7.3  !  1994-08  (G. Madec, M. Imbard)  nn_pdl flag 
    12    !!             7.5  !  1996-01  (G. Madec)   s-coordinates 
    13    !!             8.0  !  1997-07  (G. Madec)   lbc 
    14    !!             8.1  !  1999-01  (E. Stretta) new option for the mixing length 
    15    !!  NEMO       1.0  !  2002-06  (G. Madec) add zdf_tke2_init routine 
    16    !!              -   !  2002-08  (G. Madec)  rn_cri and Free form, F90 
    17    !!              -   !  2004-10  (C. Ethe )  1D configuration 
    18    !!             2.0  !  2006-07  (S. Masson)  distributed restart using iom 
    19    !!             3.0  !  2008-05  (C. Ethe,  G.Madec) : update TKE physics: 
    20    !!                              - tke penetration (wind steering) 
    21    !!                              - suface condition for tke & mixing length 
    22    !!                              - Langmuir cells 
    23    !!              -   !  2008-05  (J.-M. Molines, G. Madec)  2D form of avtb 
    24    !!              -   !  2008-06  (G. Madec)  style + DOCTOR name for namelist parameters 
    25    !!              -   !  2008-12  (G. Reffray) stable discretization of the production term  
     7   !! History :  OPA  !  1991-03  (b. blanke)  Original code 
     8   !!            7.0  !  1991-11  (G. Madec)   bug fix 
     9   !!            7.1  !  1992-10  (G. Madec)   new mixing length and eav 
     10   !!            7.2  !  1993-03  (M. Guyon)   symetrical conditions 
     11   !!            7.3  !  1994-08  (G. Madec, M. Imbard)  nn_pdl flag 
     12   !!            7.5  !  1996-01  (G. Madec)   s-coordinates 
     13   !!            8.0  !  1997-07  (G. Madec)   lbc 
     14   !!            8.1  !  1999-01  (E. Stretta) new option for the mixing length 
     15   !!  NEMO      1.0  !  2002-06  (G. Madec) add tke_init routine 
     16   !!             -   !  2002-08  (G. Madec)  rn_cri and Free form, F90 
     17   !!             -   !  2004-10  (C. Ethe )  1D configuration 
     18   !!            2.0  !  2006-07  (S. Masson)  distributed restart using iom 
     19   !!            3.0  !  2008-05  (C. Ethe,  G.Madec) : update TKE physics: 
     20   !!                 !           - tke penetration (wind steering) 
     21   !!                 !           - suface condition for tke & mixing length 
     22   !!                 !           - Langmuir cells 
     23   !!             -   !  2008-05  (J.-M. Molines, G. Madec)  2D form of avtb 
     24   !!             -   !  2008-06  (G. Madec)  style + DOCTOR name for namelist parameters 
     25   !!             -   !  2008-12  (G. Reffray) stable discretization of the production term  
     26   !!            3.2  !  2009-06  (G. Madec, S. Masson) TKE restart compatible with key_cpl  
     27   !!                 !                                + cleaning of the parameters + bugs correction 
    2628   !!---------------------------------------------------------------------- 
    2729#if defined key_zdftke2   ||   defined key_esopa 
     
    2931   !!   'key_zdftke2'                                  TKE vertical physics 
    3032   !!---------------------------------------------------------------------- 
    31    !!---------------------------------------------------------------------- 
    3233   !!   zdf_tke2      : update momentum and tracer Kz from a tke scheme 
    33    !!   zdf_tke2_init : initialization, namelist read, and parameters control 
     34   !!   tke_tke       : tke time stepping: update tke at now time step (en) 
     35   !!   tke_avn       : compute mixing length scale and deduce avm and avt 
     36   !!   tke_init      : initialization, namelist read, and parameters control 
    3437   !!   tke2_rst      : read/write tke restart in ocean restart file 
    3538   !!---------------------------------------------------------------------- 
    36    USE oce             ! ocean dynamics and active tracers  
    37    USE dom_oce         ! ocean space and time domain 
    38    USE zdf_oce         ! ocean vertical physics 
    39    USE sbc_oce         ! surface boundary condition: ocean 
    40    USE phycst          ! physical constants 
    41    USE zdfmxl          ! mixed layer 
    42    USE restart         ! only for lrst_oce 
    43    USE lbclnk          ! ocean lateral boundary conditions (or mpp link) 
    44    USE prtctl          ! Print control 
    45    USE in_out_manager  ! I/O manager 
    46    USE iom             ! I/O manager library 
     39   USE oce            ! ocean dynamics and active tracers  
     40   USE dom_oce        ! ocean space and time domain 
     41   USE domvvl         ! ocean space and time domain : variable volume layer 
     42   USE zdf_oce        ! ocean vertical physics 
     43   USE sbc_oce        ! surface boundary condition: ocean 
     44   USE phycst         ! physical constants 
     45   USE zdfmxl         ! mixed layer 
     46   USE restart        ! only for lrst_oce 
     47   USE lbclnk         ! ocean lateral boundary conditions (or mpp link) 
     48   USE prtctl         ! Print control 
     49   USE in_out_manager ! I/O manager 
     50   USE iom            ! I/O manager library 
    4751 
    4852   IMPLICIT NONE 
    4953   PRIVATE 
    5054 
    51    PUBLIC   zdf_tke2    ! routine called in step module 
    52    PUBLIC   tke2_rst    ! routine called in step module 
     55   PUBLIC   zdf_tke2   ! routine called in step module 
     56   PUBLIC   tke2_rst   ! routine called in step module 
    5357 
    5458   LOGICAL , PUBLIC, PARAMETER              ::   lk_zdftke2 = .TRUE.  !: TKE vertical mixing flag 
    55    REAL(wp), PUBLIC                         ::   eboost              !: multiplicative coeff of the shear product. 
    56    REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpk) ::   en                  !: now turbulent kinetic energy 
    57    REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpk) ::   avm                 !: now mixing coefficient of diffusion for TKE 
    58    REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpk) ::   dissl               !: now mixing lenght of dissipation 
    5959 
    6060#if defined key_c1d 
    61    !                                                                !!! 1D cfg only 
     61   !                                                                !!* 1D cfg only * 
    6262   REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpk) ::   e_dis, e_mix        !: dissipation and mixing turbulent lengh scales 
    6363   REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpk) ::   e_pdl, e_ric        !: prandl and local Richardson numbers 
    6464#endif 
    6565 
     66!!gm  - variables to be suppressed from the namelist: 
     67   LOGICAL  ::   ln_rstke = .FALSE.         ! =T restart with tke from a run without tke 
     68   INTEGER  ::   nn_itke  = 50              ! number of restart iterative loops 
     69   INTEGER  ::   nn_ave   =  1              ! horizontal average or not on avt, avmu, avmv (=0/1) 
     70   REAL(wp) ::   rn_cri   = 2._wp / 9._wp   ! critic Richardson number 
     71   REAL(wp) ::   rn_efave = 1._wp           ! coefficient for ave : ave=rn_efave*avm 
     72!!gm end 
     73 
     74!!gm  - variables to be added in the namelist (with a larger default value) 
     75   REAL(wp) ::   rn_bshear = 1.e-20   ! backgrounf shear (>0) 
     76!!gm 
     77 
    6678   !                                       !!! ** Namelist  namtke  ** 
    67    LOGICAL  ::   ln_rstke = .FALSE.         ! =T restart with tke from a run without tke 
    6879   LOGICAL  ::   ln_mxl0  = .FALSE.         ! mixing length scale surface value as function of wind stress or not 
    69    LOGICAL  ::   ln_lc    = .FALSE.         ! Langmuir cells (LC) as a source term of TKE or not 
    70    INTEGER  ::   nn_itke  = 50              ! number of restart iterative loops 
    7180   INTEGER  ::   nn_mxl   =  2              ! type of mixing length (=0/1/2/3) 
     81!!gm to be change: the ref value of lmin0 and lmin 
     82   REAL(wp) ::   rn_lmin0 = 0.4_wp          ! surface  min value of mixing length   [m] 
     83   REAL(wp) ::   rn_lmin  = 0.1_wp          ! interior min value of mixing length   [m] 
    7284   INTEGER  ::   nn_pdl   =  1              ! Prandtl number or not (ratio avt/avm) (=0/1) 
    73    INTEGER  ::   nn_ave   =  1              ! horizontal average or not on avt, avmu, avmv (=0/1) 
    7485   INTEGER  ::   nn_avb   =  0              ! constant or profile background on avt (=0/1) 
    7586   REAL(wp) ::   rn_ediff = 0.1_wp          ! coefficient for avt: avt=rn_ediff*mxl*sqrt(e) 
    7687   REAL(wp) ::   rn_ediss = 0.7_wp          ! coefficient of the Kolmogoroff dissipation  
    7788   REAL(wp) ::   rn_ebb   = 3.75_wp         ! coefficient of the surface input of tke 
    78    REAL(wp) ::   rn_efave = 1._wp           ! coefficient for ave : ave=rn_efave*avm 
    79    REAL(wp) ::   rn_emin  = 0.7071e-6_wp    ! minimum value of tke (m2/s2) 
    80    REAL(wp) ::   rn_emin0 = 1.e-4_wp        ! surface minimum value of tke (m2/s2) 
    81    REAL(wp) ::   rn_cri   = 2._wp / 9._wp   ! critic Richardson number 
     89   REAL(wp) ::   rn_emin  = 0.7071e-6_wp    ! minimum value of tke           [m2/s2] 
     90   REAL(wp) ::   rn_emin0 = 1.e-4_wp        ! surface minimum value of tke   [m2/s2] 
    8291   INTEGER  ::   nn_havtb = 1               ! horizontal shape or not for avtb (=0/1) 
    8392   INTEGER  ::   nn_etau  = 0               ! type of depth penetration of surface tke (=0/1/2) 
    8493   INTEGER  ::   nn_htau  = 0               ! type of tke profile of penetration (=0/1/2) 
    85    REAL(wp) ::   rn_lmin0 = 0.4_wp          ! surface  min value of mixing length 
    86    REAL(wp) ::   rn_lmin  = 0.1_wp          ! interior min value of mixing length 
    8794   REAL(wp) ::   rn_efr   = 1.0_wp          ! fraction of TKE surface value which penetrates in the ocean 
     95   LOGICAL  ::   ln_lc    = .FALSE.         ! Langmuir cells (LC) as a source term of TKE or not 
    8896   REAL(wp) ::   rn_lc    = 0.15_wp         ! coef to compute vertical velocity of Langmuir cells 
    8997 
    90    REAL(wp), DIMENSION (jpi,jpj) ::   avtb_2d   ! set in tke2_init, for other modif than ice 
     98   REAL(wp) ::   ri_cri   ! critic Richardson number (deduced from rn_ediff and rn_ediss values) 
     99 
     100   REAL(wp), DIMENSION(jpi,jpj)     ::   htau      ! depth of tke penetration (nn_htau) 
     101   REAL(wp), DIMENSION(jpi,jpj)     ::   avtb_2d   ! set in tke2_init, for other modif than ice 
     102   REAL(wp), DIMENSION(jpi,jpj,jpk) ::   en        ! now turbulent kinetic energy   [m2/s2] 
     103   REAL(wp), DIMENSION(jpi,jpj,jpk) ::   dissl     ! now mixing lenght of dissipation 
    91104 
    92105   !! * Substitutions 
     
    94107#  include "vectopt_loop_substitute.h90" 
    95108   !!---------------------------------------------------------------------- 
    96    !! NEMO/OPA 3.0 , LOCEAN-IPSL (2008)  
     109   !! NEMO/OPA 3.2 , LOCEAN-IPSL (2009)  
    97110   !! $Id: zdftke2.F90 1201 2008-09-24 13:24:21Z rblod $ 
    98111   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
     
    106119      !! 
    107120      !! ** Purpose :   Compute the vertical eddy viscosity and diffusivity 
    108       !!      coefficients using a 1.5 turbulent closure scheme. 
    109       !! 
    110       !! ** Method  :   The time evolution of the turbulent kinetic energy  
    111       !!      (tke) is computed from a prognostic equation : 
    112       !!         d(en)/dt = eboost eav (d(u)/dz)**2         ! shear production 
    113       !!                  + d( rn_efave eav d(en)/dz )/dz   ! diffusion of tke 
    114       !!                  + grav/rau0 pdl eav d(rau)/dz     ! stratif. destruc. 
    115       !!                  - rn_ediss / emxl en**(2/3)       ! dissipation 
     121      !!              coefficients using a turbulent closure scheme (TKE). 
     122      !! 
     123      !! ** Method  :   The time evolution of the turbulent kinetic energy (tke) 
     124      !!              is computed from a prognostic equation : 
     125      !!         d(en)/dt = avm (d(u)/dz)**2             ! shear production 
     126      !!                  + d( avm d(en)/dz )/dz         ! diffusion of tke 
     127      !!                  + avt N^2                      ! stratif. destruc. 
     128      !!                  - rn_ediss / emxl en**(2/3)    ! Kolmogoroff dissipation 
    116129      !!      with the boundary conditions: 
    117130      !!         surface: en = max( rn_emin0, rn_ebb sqrt(utau^2 + vtau^2) ) 
    118131      !!         bottom : en = rn_emin 
    119       !!      -1- The dissipation and mixing turbulent lengh scales are computed 
    120       !!         from the usual diagnostic buoyancy length scale:   
    121       !!         mxl= sqrt(2*en)/N  where N is the brunt-vaisala frequency 
    122       !!         with mxl = rn_lmin at the bottom minimum value of 0.4 
    123       !!      Four cases :  
    124       !!         nn_mxl=0 : mxl bounded by the distance to surface and bottom. 
    125       !!                  zmxld = zmxlm = mxl 
    126       !!         nn_mxl=1 : mxl bounded by the vertical scale factor. 
    127       !!                  zmxld = zmxlm = mxl 
    128       !!         nn_mxl=2 : mxl bounded such that the vertical derivative of mxl  
    129       !!                  is less than 1 (|d/dz(xml)|<1).  
    130       !!                  zmxld = zmxlm = mxl 
    131       !!         nn_mxl=3 : lup = mxl bounded using |d/dz(xml)|<1 from the surface  
    132       !!                        to the bottom 
    133       !!                  ldown = mxl bounded using |d/dz(xml)|<1 from the bottom  
    134       !!                        to the surface 
    135       !!                  zmxld = sqrt (lup*ldown) ; zmxlm = min(lup,ldown) 
    136       !!      -2- Compute the now Turbulent kinetic energy. The time differencing 
    137       !!      is implicit for vertical diffusion term, linearized for kolmo- 
    138       !!      goroff dissipation term, and explicit forward for both buoyancy 
    139       !!      and dynamic production terms. Thus a tridiagonal linear system is 
    140       !!      solved. 
    141       !!         Note that - the shear production is multiplied by eboost in order 
    142       !!      to set the critic richardson number to rn_cri (namelist parameter) 
    143       !!                   - the destruction by stratification term is multiplied 
    144       !!      by the Prandtl number (defined by an empirical funtion of the local  
    145       !!      Richardson number) if nn_pdl=1 (namelist parameter) 
    146       !!      coefficient (zesh2): 
    147       !!      -3- Compute the now vertical eddy vicosity and diffusivity 
    148       !!      coefficients from en (before the time stepping) and zmxlm: 
    149       !!              avm = max( avtb, rn_ediff*zmxlm*en^1/2 ) 
    150       !!              avt = max( avmb, pdl*avm )  (pdl=1 if nn_pdl=0) 
     132      !!      The associated critical Richardson number is: ri_cri = 2/(2+rn_ediss/rn_ediff)  
     133      !! 
     134      !!        The now Turbulent kinetic energy is computed using the following  
     135      !!      time stepping: implicit for vertical diffusion term, linearized semi 
     136      !!      implicit for kolmogoroff dissipation term, and explicit forward for  
     137      !!      both buoyancy and shear production terms. Therefore a tridiagonal  
     138      !!      linear system is solved. Note that buoyancy and shear terms are 
     139      !!      discretized in a energy conserving form (Bruchard 2002). 
     140      !! 
     141      !!        The dissipative and mixing length scale are computed from en and 
     142      !!      the stratification (see tke_avn) 
     143      !! 
     144      !!        The now vertical eddy vicosity and diffusivity coefficients are 
     145      !!      given by:  
     146      !!              avm = max( avtb, rn_ediff * zmxlm * en^1/2 ) 
     147      !!              avt = max( avmb, pdl * avm                 )   
    151148      !!              eav = max( avmb, avm ) 
    152       !!      avt and avm are horizontally averaged to avoid numerical insta- 
    153       !!      bilities. 
    154       !!        N.B. The computation is done from jk=2 to jpkm1 except for 
    155       !!      en. Surface value of avt avmu avmv are set once a time to 
    156       !!      their background value in routine zdf_tke2_init. 
     149      !!      where pdl, the inverse of the Prandtl number is 1 if nn_pdl=0 and 
     150      !!      given by an empirical funtion of the localRichardson number if nn_pdl=1  
    157151      !! 
    158152      !! ** Action  :   compute en (now turbulent kinetic energy) 
     
    163157      !!              Mellor and Blumberg, JPO 2004 
    164158      !!              Axell, JGR, 2002 
     159      !!              Bruchard OM 2002 
    165160      !!---------------------------------------------------------------------- 
    166  
    167       INTEGER, INTENT(in) ::   kt ! ocean time step 
    168  
    169       IF( kt == nit000 )   CALL zdf_tke2_init             ! Initialization (first time-step only) 
    170       ! 
    171       CALL tke_tke                                        ! now tke (en) 
    172       CALL tke_mlmc                                       ! now avmu, avmv, avt 
    173  
     161      INTEGER, INTENT(in) ::   kt   ! ocean time step 
     162      !!---------------------------------------------------------------------- 
     163      ! 
     164      IF( kt == nit000 )   CALL tke_init     ! initialisation  
     165                           ! 
     166                           CALL tke_tke      ! now tke (en) 
     167                           ! 
     168                           CALL tke_avn      ! now avt, avm, avmu, avmv 
     169      ! 
    174170   END SUBROUTINE zdf_tke2 
     171 
    175172 
    176173   SUBROUTINE tke_tke 
    177174      !!---------------------------------------------------------------------- 
    178       !! Now Turbulent kinetic energy (output in en) 
     175      !!                   ***  ROUTINE tke_tke  *** 
     176      !! 
     177      !! ** Purpose :   Compute the now Turbulente Kinetic Energy (TKE) 
     178      !! 
     179      !! ** Method  : - TKE surface boundary condition 
     180      !!              - source term due to Langmuir cells (ln_lc=T) 
     181      !!              - source term due to shear (saved in avmu, avmv arrays) 
     182      !!              - Now TKE : resolution of the TKE equation by inverting 
     183      !!                a tridiagonal linear system by a "methode de chasse" 
     184      !!              - increase TKE due to surface and internal wave breaking 
     185      !! 
     186      !! ** Action  : - en : now turbulent kinetic energy) 
     187      !!              - avmu, avmv : production of TKE by shear at u and v-points 
     188      !!                (= Kz dz[Ub] * dz[Un] ) 
    179189      !! --------------------------------------------------------------------- 
    180       !! Surface boundary condition for TKE 
    181       !! Resolution of a tridiagonal linear system by a "methode de chasse" 
    182       !! computation from level 2 to jpkm1  (e(1) computed and e(jpk)=0 ). 
    183       !! avm represents the turbulent coefficient of the TKE 
    184       !!---------------------------------------------------------------------- 
    185       USE oce,     zwd     =>   ua   ! use ua as workspace 
    186       USE oce,     zdiag1  =>   va   ! use va as workspace 
    187       USE oce,     zdiag2  =>   ta   ! use ta as workspace 
    188       USE oce,     ztkelc  =>   sa   ! use sa as workspace 
    189       ! 
    190       INTEGER  ::   ji, jj, jk                      ! dummy loop arguments 
    191       REAL(wp) ::   zbbrau, zesurf, zesh2           ! temporary scalars 
    192       REAL(wp) ::   zfact1, ztx2, zdku              !    -         - 
    193       REAL(wp) ::   zfact2, zty2, zdkv              !    -         - 
    194       REAL(wp) ::   zfact3, zcoef, zcof             !    -         - 
    195       REAL(wp) ::   zus, zwlc, zind                 !    -         - 
     190      USE oce,   zdiag  =>   ua   ! use ua as workspace 
     191      USE oce,   zd_up  =>   va   ! use va as workspace 
     192      USE oce,   zd_lw  =>   ta   ! use ta as workspace 
     193      !! 
     194      INTEGER  ::   ji, jj, jk                ! dummy loop arguments 
     195      REAL(wp) ::   zbbrau, zesurf, zesh2     ! temporary scalars 
     196      REAL(wp) ::   zfact1, zfact2, zfact3    !    -         - 
     197      REAL(wp) ::   ztx2  , zty2  , zcof      !    -         - 
     198      REAL(wp) ::   zus   , zwlc  , zind      !    -         - 
     199      REAL(wp) ::   zzd_up, zzd_lw            !    -         - 
    196200      INTEGER , DIMENSION(jpi,jpj)     ::   imlc    ! 2D workspace 
    197       REAL(wp), DIMENSION(jpi,jpj)     ::   zhtau   !  -      - 
    198201      REAL(wp), DIMENSION(jpi,jpj)     ::   zhlc    !  -      - 
    199202      REAL(wp), DIMENSION(jpi,jpj,jpk) ::   zpelc   ! 3D workspace 
    200203      !!-------------------------------------------------------------------- 
    201       !                                            ! Local constant initialization 
    202       zbbrau =  .5 * rn_ebb / rau0 
    203       zfact1 = -.5 * rdt * rn_efave 
     204      ! 
     205      zbbrau =  .5 * rn_ebb / rau0       ! Local constant initialisation 
     206      zfact1 = -.5 * rdt  
    204207      zfact2 = 1.5 * rdt * rn_ediss 
    205208      zfact3 = 0.5       * rn_ediss 
    206  
    207       ! Surface boundary condition on tke 
    208       ! ------------------------------------------------- 
    209       ! en(1)   = rn_ebb sqrt(utau^2+vtau^2) / rau0  (min value rn_emin0) 
    210 !CDIR NOVERRCHK 
    211       DO jj = 2, jpjm1 
     209      ! 
     210      !                     !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
     211      !                     !  Surface boundary condition on tke 
     212      !                     !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
     213!CDIR NOVERRCHK 
     214      DO jj = 2, jpjm1         ! en(1)   = rn_ebb sqrt(utau^2+vtau^2) / rau0  (min value rn_emin0) 
    212215!CDIR NOVERRCHK 
    213216         DO ji = fs_2, fs_jpim1   ! vector opt. 
    214             ztx2 = utau(ji-1,jj  ) + utau(ji,jj) 
    215             zty2 = vtau(ji  ,jj-1) + vtau(ji,jj) 
     217            ztx2   = utau(ji-1,jj  ) + utau(ji,jj) 
     218            zty2   = vtau(ji  ,jj-1) + vtau(ji,jj) 
    216219            zesurf = zbbrau * SQRT( ztx2 * ztx2 + zty2 * zty2 ) 
    217220            en(ji,jj,1) = MAX( zesurf, rn_emin0 ) * tmask(ji,jj,1) 
    218221         END DO 
    219222      END DO 
    220  
    221       !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
    222       ! Langmuir circulation source term 
    223       !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
    224       IF( ln_lc ) THEN 
     223      ! 
     224      !                     !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
     225      !                     !  Bottom boundary condition on tke 
     226      !                     !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
     227!!gm to be added soon 
     228      ! 
     229      ! 
     230      !                     !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
     231      IF( ln_lc ) THEN      !  Langmuir circulation source term added to tke 
     232         !                  !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
    225233         ! 
    226          ! Computation of total energy produce by LC : cumulative sum over jk 
     234         !                        !* total energy produce by LC : cumulative sum over jk 
    227235         zpelc(:,:,1) =  MAX( rn2b(:,:,1), 0. ) * fsdepw(:,:,1) * fse3w(:,:,1) 
    228236         DO jk = 2, jpk 
    229237            zpelc(:,:,jk)  = zpelc(:,:,jk-1) + MAX( rn2b(:,:,jk), 0. ) * fsdepw(:,:,jk) * fse3w(:,:,jk) 
    230238         END DO 
    231          ! 
    232          ! Computation of finite Langmuir Circulation depth 
    233          ! Initialization to the number of w ocean point mbathy 
    234          imlc(:,:) = mbathy(:,:) 
     239         !                        !* finite Langmuir Circulation depth 
     240         imlc(:,:) = mbathy(:,:)         ! Initialization to the number of w ocean point mbathy 
    235241         DO jk = jpkm1, 2, -1 
    236             DO jj = 1, jpj 
    237                DO ji = 1, jpi 
    238                   ! Last w-level at which zpelc>=0.5*us*us with us=0.016*wind(starting from jpk-1) 
     242            DO jj = 1, jpj               ! Last w-level at which zpelc>=0.5*us*us  
     243               DO ji = 1, jpi            !      with us=0.016*wind(starting from jpk-1) 
    239244                  zus  = 0.000128 * wndm(ji,jj) * wndm(ji,jj) 
    240245                  IF( zpelc(ji,jj,jk) > zus )   imlc(ji,jj) = jk 
     
    242247            END DO 
    243248         END DO 
    244          ! 
    245          ! finite LC depth 
    246          DO jj = 1, jpj 
     249         !                               ! finite LC depth 
     250# if defined key_vectopt_loop 
     251         DO jj = 1, 1 
     252            DO ji = 1, jpij   ! vector opt. (forced unrolling) 
     253# else 
     254         DO jj = 1, jpj  
    247255            DO ji = 1, jpi 
     256# endif 
    248257               zhlc(ji,jj) = fsdepw(ji,jj,imlc(ji,jj)) 
    249258            END DO 
    250259         END DO 
    251          ! 
    252260# if defined key_c1d 
    253261         hlc(:,:) = zhlc(:,:) * tmask(:,:,1)      ! c1d configuration: save finite Langmuir Circulation depth 
    254262# endif 
    255          ! 
    256          ! TKE Langmuir circulation source term added to en 
    257 !CDIR NOVERRCHK 
    258          DO jk = 2, jpkm1 
    259 !CDIR NOVERRCHK 
    260             DO jj = 2, jpjm1 
    261 !CDIR NOVERRCHK 
    262                DO ji = fs_2, fs_jpim1   ! vector opt. 
    263                   ! Stokes drift 
    264                   zus  = 0.016 * wndm(ji,jj) 
    265                   ! computation of vertical velocity due to LC 
     263!CDIR NOVERRCHK 
     264         DO jk = 2, jpkm1         !* TKE Langmuir circulation source term added to en 
     265!CDIR NOVERRCHK 
     266            DO jj = 2, jpjm1 
     267!CDIR NOVERRCHK 
     268               DO ji = fs_2, fs_jpim1   ! vector opt. 
     269!!gm replace here wndn by a formulation with the stress module 
     270                  zus  = 0.016 * wndm(ji,jj)                  ! Stokes drift 
     271                  !                                           ! vertical velocity due to LC 
    266272                  zind = 0.5 - SIGN( 0.5, fsdepw(ji,jj,jk) - zhlc(ji,jj) ) 
    267273                  zwlc = zind * rn_lc * zus * SIN( rpi * fsdepw(ji,jj,jk) / zhlc(ji,jj) ) 
    268                   ! TKE Langmuir circulation source term 
    269                   en(ji,jj,jk) = en(ji,jj,jk) + rdt * ( ( zwlc * zwlc * zwlc ) / zhlc(ji,jj) ) * tmask(ji,jj,jk) 
     274                  !                                           ! TKE Langmuir circulation source term 
     275                  en(ji,jj,jk) = en(ji,jj,jk) + rdt * ( zwlc * zwlc * zwlc ) / zhlc(ji,jj) * tmask(ji,jj,jk) 
    270276               END DO 
    271277            END DO 
     
    273279         ! 
    274280      ENDIF 
    275  
    276  
    277       ! Shear production at uw- and vw-points (energy conserving form) 
    278       DO jk = 2, jpkm1 
     281      ! 
     282      !                     !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
     283      !                     !  Now Turbulent kinetic energy (output in en) 
     284      !                     !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
     285      !                     ! Resolution of a tridiagonal linear system by a "methode de chasse" 
     286      !                     ! computation from level 2 to jpkm1  (e(1) already computed and e(jpk)=0 ). 
     287      !                     ! zdiag : diagonal zd_up : upper diagonal zd_lw : lower diagonal 
     288      ! 
     289      DO jk = 2, jpkm1           !* Shear production at uw- and vw-points (energy conserving form) 
     290         DO jj = 1, jpj                 ! here avmu, avmv used as workspace 
     291            DO ji = 1, jpi 
     292               avmu(ji,jj,jk) = avmu(ji,jj,jk) * ( un(ji,jj,jk-1) - un(ji,jj,jk) )   & 
     293                  &                            * ( ub(ji,jj,jk-1) - ub(ji,jj,jk) )   &  
     294                  &           / (  fse3uw_n(ji,jj,jk)         & 
     295                  &              * fse3uw_b(ji,jj,jk) ) 
     296               avmv(ji,jj,jk) = avmv(ji,jj,jk) * ( vn(ji,jj,jk-1) - vn(ji,jj,jk) )   & 
     297                  &                            * ( vb(ji,jj,jk-1) - vb(ji,jj,jk) )   & 
     298                  &                            / (  fse3vw_n(ji,jj,jk)               & 
     299                  &                              *  fse3vw_b(ji,jj,jk)  ) 
     300            END DO 
     301         END DO 
     302      END DO 
     303      ! 
     304      DO jk = 2, jpkm1           !* Matrix and right hand side in en 
    279305         DO jj = 2, jpjm1 
    280306            DO ji = fs_2, fs_jpim1   ! vector opt. 
    281                avmu(ji,jj,jk) = avmu(ji,jj,jk) * ( un(ji,jj,jk-1) - un(ji,jj,jk) ) * & 
    282                   &                              ( ub(ji,jj,jk-1) - ub(ji,jj,jk) ) / &  
    283                   &                              ( fse3uw_n(ji,jj,jk) * fse3uw_b(ji,jj,jk) ) 
    284                avmv(ji,jj,jk) = avmv(ji,jj,jk) * ( vn(ji,jj,jk-1) - vn(ji,jj,jk) ) * & 
    285                   &                              ( vb(ji,jj,jk-1) - vb(ji,jj,jk) ) / & 
    286                   &                              ( fse3vw_n(ji,jj,jk) * fse3vw_b(ji,jj,jk) ) 
    287             ENDDO 
    288          ENDDO 
    289       ENDDO 
    290  
    291       ! Lateral boundary conditions (avmu,avmv) (sign unchanged) 
    292       CALL lbc_lnk( avmu, 'U', 1. )   ;    CALL lbc_lnk( avmv, 'V', 1. ) 
    293  
    294       ! Now Turbulent kinetic energy (output in en) 
    295       ! ------------------------------- 
    296       ! Resolution of a tridiagonal linear system by a "methode de chasse" 
    297       ! computation from level 2 to jpkm1  (e(1) already computed and e(jpk)=0 ). 
    298       ! zwd : diagonal zdiag1 : upper diagonal zdiag2 : lower diagonal 
    299       ! Warning : after this step, en : right hand side of the matrix 
    300       DO jk = 2, jpkm1 
    301          DO jj = 2, jpjm1 
    302             DO ji = fs_2, fs_jpim1   ! vector opt. 
    303                !                                                             ! shear prod. at w-point weightened by mask 
     307               zcof   = zfact1 * tmask(ji,jj,jk) 
     308               zzd_up = zcof * ( avm  (ji,jj,jk+1) + avm  (ji,jj,jk  ) )   &  ! upper diagonal 
     309                  &          / ( fse3t(ji,jj,jk  ) * fse3w(ji,jj,jk  ) ) 
     310               zzd_lw = zcof * ( avm  (ji,jj,jk  ) + avm  (ji,jj,jk-1) )   &  ! lower diagonal 
     311                  &          / ( fse3t(ji,jj,jk-1) * fse3w(ji,jj,jk  ) ) 
     312                  !                                                           ! shear prod. at w-point weightened by mask 
    304313               zesh2  =  ( avmu(ji-1,jj,jk) + avmu(ji,jj,jk) ) / MAX( 1.e0 , umask(ji-1,jj,jk) + umask(ji,jj,jk) )   & 
    305314                  &    + ( avmv(ji,jj-1,jk) + avmv(ji,jj,jk) ) / MAX( 1.e0 , vmask(ji,jj-1,jk) + vmask(ji,jj,jk) )     
    306                !                                                             ! Matrix 
    307                zcof = zfact1 * tmask(ji,jj,jk) 
    308                !                                                                  ! lower diagonal 
    309                zdiag2(ji,jj,jk) = zcof * ( avm  (ji,jj,jk  ) + avm  (ji,jj,jk-1) )   & 
    310                   &                    / ( fse3t(ji,jj,jk-1) * fse3w(ji,jj,jk  ) ) 
    311                !                                                                  ! upper diagonal 
    312                zdiag1(ji,jj,jk) = zcof * ( avm  (ji,jj,jk+1) + avm  (ji,jj,jk  ) )   & 
    313                   &                    / ( fse3t(ji,jj,jk  ) * fse3w(ji,jj,jk) ) 
    314                !                                                                  ! diagonal 
    315                zwd(ji,jj,jk) = 1. - zdiag2(ji,jj,jk) - zdiag1(ji,jj,jk) + zfact2 * dissl(ji,jj,jk) * tmask(ji,jj,jk) 
     315                  ! 
     316               zd_up(ji,jj,jk) = zzd_up            ! Matrix (zdiag, zd_up, zd_lw) 
     317               zd_lw(ji,jj,jk) = zzd_lw 
     318               zdiag(ji,jj,jk) = 1.e0 - zzd_lw - zzd_up + zfact2 * dissl(ji,jj,jk) * tmask(ji,jj,jk) 
    316319               ! 
    317                !                                                             ! right hand side in en 
     320               !                                   ! right hand side in en 
    318321               en(ji,jj,jk) = en(ji,jj,jk) + rdt * (  zesh2  -   avt(ji,jj,jk) * rn2(ji,jj,jk)    & 
    319322                  &                                 + zfact3 * dissl(ji,jj,jk) * en (ji,jj,jk)  ) * tmask(ji,jj,jk) 
     
    321324         END DO 
    322325      END DO 
    323       ! Matrix inversion from level 2 (tke prescribed at level 1) 
    324       !!-------------------------------- 
     326      !                          !* Matrix inversion from level 2 (tke prescribed at level 1) 
    325327      DO jk = 3, jpkm1                             ! First recurrence : Dk = Dk - Lk * Uk-1 / Dk-1 
    326328         DO jj = 2, jpjm1 
    327329            DO ji = fs_2, fs_jpim1    ! vector opt. 
    328                zwd(ji,jj,jk) = zwd(ji,jj,jk) - zdiag2(ji,jj,jk) * zdiag1(ji,jj,jk-1) / zwd(ji,jj,jk-1) 
     330               zdiag(ji,jj,jk) = zdiag(ji,jj,jk) - zd_lw(ji,jj,jk) * zd_up(ji,jj,jk-1) / zdiag(ji,jj,jk-1) 
    329331            END DO 
    330332         END DO 
     
    332334      DO jj = 2, jpjm1                             ! Second recurrence : Lk = RHSk - Lk / Dk-1 * Lk-1 
    333335         DO ji = fs_2, fs_jpim1    ! vector opt. 
    334             zdiag2(ji,jj,2) = en(ji,jj,2) - zdiag2(ji,jj,2) * en(ji,jj,1)    ! Surface boudary conditions on tke 
     336            zd_lw(ji,jj,2) = en(ji,jj,2) - zd_lw(ji,jj,2) * en(ji,jj,1)    ! Surface boudary conditions on tke 
    335337         END DO 
    336338      END DO 
     
    338340         DO jj = 2, jpjm1 
    339341            DO ji = fs_2, fs_jpim1    ! vector opt. 
    340                zdiag2(ji,jj,jk) = en(ji,jj,jk) - zdiag2(ji,jj,jk) / zwd(ji,jj,jk-1) *zdiag2(ji,jj,jk-1) 
     342               zd_lw(ji,jj,jk) = en(ji,jj,jk) - zd_lw(ji,jj,jk) / zdiag(ji,jj,jk-1) *zd_lw(ji,jj,jk-1) 
    341343            END DO 
    342344         END DO 
     
    344346      DO jj = 2, jpjm1                             ! thrid recurrence : Ek = ( Lk - Uk * Ek+1 ) / Dk 
    345347         DO ji = fs_2, fs_jpim1    ! vector opt. 
    346             en(ji,jj,jpkm1) = zdiag2(ji,jj,jpkm1) / zwd(ji,jj,jpkm1) 
     348            en(ji,jj,jpkm1) = zd_lw(ji,jj,jpkm1) / zdiag(ji,jj,jpkm1) 
    347349         END DO 
    348350      END DO 
     
    350352         DO jj = 2, jpjm1 
    351353            DO ji = fs_2, fs_jpim1    ! vector opt. 
    352                en(ji,jj,jk) = ( zdiag2(ji,jj,jk) - zdiag1(ji,jj,jk) * en(ji,jj,jk+1) ) / zwd(ji,jj,jk) 
     354               en(ji,jj,jk) = ( zd_lw(ji,jj,jk) - zd_up(ji,jj,jk) * en(ji,jj,jk+1) ) / zdiag(ji,jj,jk) 
    353355            END DO 
    354356         END DO 
     
    362364      END DO 
    363365 
    364       ! 5. Add extra TKE due to surface and internal wave breaking (nn_etau /= 0) 
    365       !!---------------------------------------------------------- 
    366       IF( nn_etau /= 0 ) THEN        ! extra tke : en = en + rn_efr * en(1) * exp( -z/zhtau ) 
    367          ! 
    368          SELECT CASE( nn_htau )           ! Choice of the depth of penetration 
    369          CASE( 0 )                                    ! constant depth penetration (here 10 meters) 
    370             DO jj = 2, jpjm1 
    371                DO ji = fs_2, fs_jpim1   ! vector opt. 
    372                   zhtau(ji,jj) = 10. 
    373                END DO 
    374             END DO 
    375          CASE( 1 )                                    ! meridional profile  1 
    376             DO jj = 2, jpjm1                          ! ( 5m in the tropics to a maximum of 40 m at high lat.) 
    377                DO ji = fs_2, fs_jpim1   ! vector opt. 
    378                   zhtau(ji,jj) = MAX( 5., MIN( 40., 60.*ABS( SIN( rpi/180. * gphit(ji,jj) ) ) )   ) 
    379                END DO 
    380             END DO 
    381          CASE( 2 )                                    ! meridional profile 2 
    382             DO jj = 2, jpjm1                          ! ( 5m in the tropics to a maximum of 60 m at high lat.) 
    383                DO ji = fs_2, fs_jpim1   ! vector opt. 
    384                   zhtau(ji,jj) =  MAX( 5.,6./4.* MIN( 40., 60.*ABS( SIN( rpi/180. * gphit(ji,jj) ) ) )   ) 
    385                END DO 
    386             END DO 
    387          END SELECT 
    388          ! 
    389          IF( nn_etau == 1 ) THEN          ! extra term throughout the water column 
    390             DO jk = 2, jpkm1 
    391                DO jj = 2, jpjm1 
    392                   DO ji = fs_2, fs_jpim1   ! vector opt. 
    393                      en(ji,jj,jk) = en(ji,jj,jk)   & 
    394                         &         + rn_efr * en(ji,jj,1)*EXP( -fsdepw(ji,jj,jk) / zhtau(ji,jj) ) & 
    395                         &                  * ( 1.e0 - fr_i(ji,jj) )  * tmask(ji,jj,jk) 
    396                   END DO 
    397                END DO 
    398             END DO 
    399          ELSEIF( nn_etau == 2 ) THEN      ! extra term only at the base of the mixed layer 
    400             DO jj = 2, jpjm1 
    401                DO ji = fs_2, fs_jpim1   ! vector opt. 
    402                   jk = nmln(ji,jj) 
    403                   en(ji,jj,jk) = en(ji,jj,jk)    & 
    404                      &         + rn_efr * en(ji,jj,1)*EXP( -fsdepw(ji,jj,jk) / zhtau(ji,jj) ) & 
    405                      &                   * ( 1.e0 - fr_i(ji,jj) )  * tmask(ji,jj,jk) 
    406                END DO 
    407             END DO 
    408          ENDIF 
    409          ! 
     366      !                            !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
     367      !                            !  TKE due to surface and internal wave breaking 
     368      !                            !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
     369      IF( nn_etau == 1 ) THEN           !*  penetration throughout the water column 
     370         DO jk = 2, jpkm1 
     371            DO jj = 2, jpjm1 
     372               DO ji = fs_2, fs_jpim1   ! vector opt. 
     373                  en(ji,jj,jk) = en(ji,jj,jk) + rn_efr * en(ji,jj,1) * EXP( -fsdepw(ji,jj,jk) / htau(ji,jj) )   & 
     374                     &                                               * ( 1.e0 - fr_i(ji,jj) )  * tmask(ji,jj,jk) 
     375               END DO 
     376            END DO 
     377         END DO 
     378      ELSEIF( nn_etau == 2 ) THEN       !* act only at the base of the mixed layer (jk=nmln) 
     379         DO jj = 2, jpjm1 
     380            DO ji = fs_2, fs_jpim1   ! vector opt. 
     381               jk = nmln(ji,jj) 
     382               en(ji,jj,jk) = en(ji,jj,jk) + rn_efr * en(ji,jj,1) * EXP( -fsdepw(ji,jj,jk) / htau(ji,jj) )   & 
     383                  &                                               * ( 1.e0 - fr_i(ji,jj) )  * tmask(ji,jj,jk) 
     384            END DO 
     385         END DO 
    410386      ENDIF 
    411       ! Lateral boundary conditions (sign unchanged) 
    412       CALL lbc_lnk( en, 'W', 1. ) 
    413  
     387      ! 
     388      CALL lbc_lnk( en, 'W', 1. )      ! Lateral boundary conditions (sign unchanged) 
     389      ! 
    414390   END SUBROUTINE tke_tke 
    415391 
    416    SUBROUTINE tke_mlmc 
     392 
     393   SUBROUTINE tke_avn 
    417394      !!---------------------------------------------------------------------- 
    418       !! 
     395      !!                   ***  ROUTINE tke_avn  *** 
     396      !! 
     397      !! ** Purpose :   Compute the vertical eddy viscosity and diffusivity 
     398      !! 
     399      !! ** Method  :   At this stage, en, the now TKE, is known (computed in  
     400      !!              the tke_tke routine). First, the now mixing lenth is  
     401      !!      computed from en and the strafification (N^2), then the mixings 
     402      !!      coefficients are computed. 
     403      !!              - Mixing length : a first evaluation of the mixing lengh 
     404      !!      scales is: 
     405      !!                      mxl = sqrt(2*en) / N   
     406      !!      where N is the brunt-vaisala frequency, with a minimum value set 
     407      !!      to rn_lmin (rn_lmin0) in the interior (surface) ocean. 
     408      !!        The mixing and dissipative length scale are bound as follow :  
     409      !!         nn_mxl=0 : mxl bounded by the distance to surface and bottom. 
     410      !!                        zmxld = zmxlm = mxl 
     411      !!         nn_mxl=1 : mxl bounded by the e3w and zmxld = zmxlm = mxl 
     412      !!         nn_mxl=2 : mxl bounded such that the vertical derivative of mxl is  
     413      !!                    less than 1 (|d/dz(mxl)|<1) and zmxld = zmxlm = mxl 
     414      !!         nn_mxl=3 : mxl is bounded from the surface to the bottom usings 
     415      !!                    |d/dz(xml)|<1 to obtain lup, and from the bottom to  
     416      !!                    the surface to obtain ldown. the resulting length  
     417      !!                    scales are: 
     418      !!                        zmxld = sqrt( lup * ldown )  
     419      !!                        zmxlm = min ( lup , ldown ) 
     420      !!              - Vertical eddy viscosity and diffusivity: 
     421      !!                      avm = max( avtb, rn_ediff * zmxlm * en^1/2 ) 
     422      !!                      avt = max( avmb, pdlr * avm )   
     423      !!      with pdlr=1 if nn_pdl=0, pdlr=1/pdl=F(Ri) otherwise. 
     424      !! 
     425      !! ** Action  : - avt : now vertical eddy diffusivity (w-point) 
     426      !!              - avmu, avmv : now vertical eddy viscosity at uw- and vw-points 
    419427      !!---------------------------------------------------------------------- 
    420428      USE oce,     zmpdl  =>   ua   ! use ua as workspace 
    421429      USE oce,     zmxlm  =>   va   ! use va as workspace 
    422430      USE oce,     zmxld  =>   ta   ! use ta as workspace 
    423       ! 
    424       INTEGER  ::   ji, jj, jk                      ! dummy loop arguments 
    425       REAL(wp) ::   zrn2, zraug                     ! temporary scalars 
    426       REAL(wp) ::   ztx2, zdku                      !    -         - 
    427       REAL(wp) ::   zty2, zdkv                      !    -         - 
    428       REAL(wp) ::   zcoef, zav                      !    -         - 
    429       REAL(wp) ::   zpdl, zri, zsqen                !    -         - 
    430       REAL(wp) ::   zemxl, zemlm, zemlp             !    -         - 
     431      !! 
     432      INTEGER  ::   ji, jj, jk            ! dummy loop arguments 
     433      REAL(wp) ::   zrn2, zraug           ! temporary scalars 
     434      REAL(wp) ::   ztx2, zdku            !    -         - 
     435      REAL(wp) ::   zty2, zdkv            !    -         - 
     436      REAL(wp) ::   zcoef, zav            !    -         - 
     437      REAL(wp) ::   zpdlr, zri, zsqen     !    -         - 
     438      REAL(wp) ::   zemxl, zemlm, zemlp   !    -         - 
    431439      !!-------------------------------------------------------------------- 
    432440 
    433       !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
    434       ! Mixing length 
    435       !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
    436  
    437       ! Buoyancy length scale: l=sqrt(2*e/n**2) 
    438       ! --------------------- 
     441      !                     !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
     442      !                     !  Mixing length 
     443      !                     !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
     444      ! 
     445      !                     !* Buoyancy length scale: l=sqrt(2*e/n**2) 
     446      ! 
    439447      IF( ln_mxl0 ) THEN         ! surface mixing length = F(stress) : l=vkarmn*2.e5*sqrt(utau^2 + vtau^2)/(rau0*g) 
    440448!!gm  this should be useless 
     
    466474         END DO 
    467475      END DO 
    468  
    469       ! Physical limits for the mixing length 
    470       ! ------------------------------------- 
     476      ! 
     477!!gm  CAUTION: to be added here the bottom boundary condition on zmxlm 
     478      ! 
     479      !                     !* Physical limits for the mixing length 
     480      ! 
    471481      zmxld(:,:, 1 ) = zmxlm(:,:,1)   ! surface set to the minimum value 
    472482      zmxld(:,:,jpk) = rn_lmin        ! bottom  set to the minimum value 
    473  
     483      ! 
    474484      SELECT CASE ( nn_mxl ) 
    475485      ! 
     
    545555         ! 
    546556      END SELECT 
    547  
     557      ! 
    548558# if defined key_c1d 
    549       ! c1d configuration : save mixing and dissipation turbulent length scales 
    550       e_dis(:,:,:) = zmxld(:,:,:) 
     559      e_dis(:,:,:) = zmxld(:,:,:)      ! c1d configuration : save mixing and dissipation turbulent length scales 
    551560      e_mix(:,:,:) = zmxlm(:,:,:) 
    552561# endif 
    553562 
    554       !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>! 
    555       ! II  Vertical eddy viscosity on tke (put in zmxlm) and first estimate of avt ! 
    556       !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<! 
    557       ! Surface boundary condition on avt and avm : jk = 1 
    558       ! ------------------------------------------------- 
    559       ! avt(1) = avmb(1) and avt(jpk) = 0. 
    560       ! avm(1) = avmb(1) and avm(jpk) = 0. 
    561       ! 
    562 !CDIR NOVERRCHK 
    563       DO jk = 1, jpkm1 
     563      !                     !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
     564      !                     !  Vertical eddy viscosity and diffusivity  (avmu, avmv, avt) 
     565      !                     !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
     566!CDIR NOVERRCHK 
     567      DO jk = 1, jpkm1            !* vertical eddy viscosity & diffivity at w-points 
    564568!CDIR NOVERRCHK 
    565569         DO jj = 2, jpjm1 
     
    568572               zsqen = SQRT( en(ji,jj,jk) ) 
    569573               zav   = rn_ediff * zmxlm(ji,jj,jk) * zsqen 
    570                avm(ji,jj,jk) = MAX( zav,                  avmb(jk) ) * tmask(ji,jj,jk) 
    571                avt(ji,jj,jk) = MAX( zav, avtb_2d(ji,jj) * avtb(jk) ) * tmask(ji,jj,jk) 
     574               avm  (ji,jj,jk) = MAX( zav,                  avmb(jk) ) * tmask(ji,jj,jk) 
     575               avt  (ji,jj,jk) = MAX( zav, avtb_2d(ji,jj) * avtb(jk) ) * tmask(ji,jj,jk) 
    572576               dissl(ji,jj,jk) = zsqen / zmxld(ji,jj,jk) 
    573577            END DO 
    574578         END DO 
    575579      END DO 
    576  
    577       ! Lateral boundary conditions (sign unchanged) 
    578       CALL lbc_lnk( avm, 'W', 1. ) 
    579  
    580       DO jk = 2, jpkm1                                 ! only vertical eddy viscosity 
     580      CALL lbc_lnk( avm, 'W', 1. )      ! Lateral boundary conditions (sign unchanged) 
     581      ! 
     582      DO jk = 2, jpkm1            !* vertical eddy viscosity at u- and v-points 
    581583         DO jj = 2, jpjm1 
    582584            DO ji = fs_2, fs_jpim1   ! vector opt. 
     
    587589      END DO 
    588590      CALL lbc_lnk( avmu, 'U', 1. )   ;   CALL lbc_lnk( avmv, 'V', 1. )      ! Lateral boundary conditions 
    589  
    590  
    591       ! Prandtl number 
    592       ! ---------------------------------------- 
    593       IF( nn_pdl == 1 ) THEN 
     591      ! 
     592      IF( nn_pdl == 1 ) THEN      !* Prandtl number case: update avt 
    594593         DO jk = 2, jpkm1 
    595594            DO jj = 2, jpjm1 
    596595               DO ji = fs_2, fs_jpim1   ! vector opt. 
    597596                  zcoef = 0.5 / ( fse3w(ji,jj,jk) * fse3w(ji,jj,jk) ) 
    598                   ! shear 
    599                   zdku = avmu(ji-1,jj,jk) * (un(ji-1,jj,jk-1)-un(ji-1,jj,jk)) * (ub(ji-1,jj,jk-1)-ub(ji-1,jj,jk)) + & 
    600                     &    avmu(ji  ,jj,jk) * (un(ji  ,jj,jk-1)-un(ji  ,jj,jk)) * (ub(ji  ,jj,jk-1)-ub(ji  ,jj,jk)) 
    601                   zdkv = avmv(ji,jj-1,jk) * (vn(ji,jj-1,jk-1)-vn(ji,jj-1,jk)) * (vb(ji,jj-1,jk-1)-vb(ji,jj-1,jk)) + & 
    602                     &    avmv(ji,jj  ,jk) * (vn(ji,jj  ,jk-1)-vn(ji,jj  ,jk)) * (vb(ji,jj  ,jk-1)-vb(ji,jj  ,jk)) 
    603                   zri = MAX( rn2b(ji,jj,jk), 0. ) * avm(ji,jj,jk)/ (zcoef * (zdku + zdkv + 1.e-20) ) ! local Richardson number 
    604 # if defined key_cfg_1d 
     597                  !                                          ! shear 
     598                  zdku = avmu(ji-1,jj,jk) * ( un(ji-1,jj,jk-1) - un(ji-1,jj,jk) ) * ( ub(ji-1,jj,jk-1) - ub(ji-1,jj,jk) )   & 
     599                    &  + avmu(ji  ,jj,jk) * ( un(ji  ,jj,jk-1) - un(ji  ,jj,jk) ) * ( ub(ji  ,jj,jk-1) - ub(ji  ,jj,jk) ) 
     600                  zdkv = avmv(ji,jj-1,jk) * ( vn(ji,jj-1,jk-1) - vn(ji,jj-1,jk) ) * ( vb(ji,jj-1,jk-1) - vb(ji,jj-1,jk) )   & 
     601                    &  + avmv(ji,jj  ,jk) * ( vn(ji,jj  ,jk-1) - vn(ji,jj  ,jk) ) * ( vb(ji,jj  ,jk-1) - vb(ji,jj  ,jk) ) 
     602                  !                                          ! local Richardson number 
     603                  zri   = MAX( rn2b(ji,jj,jk), 0. ) * avm(ji,jj,jk) / (zcoef * (zdku + zdkv + rn_bshear ) ) 
     604                  zpdlr = MAX(  0.1,  0.2 / MAX( 0.2 , zri )  ) 
     605!!gm and even better with the use of the "true" ri_crit=0.22222...  (this change the results!) 
     606!!gm              zpdlr = MAX(  0.1,  ri_crit / MAX( ri_crit , zri )  ) 
     607                  avt(ji,jj,jk)   = MAX( zpdlr * avt(ji,jj,jk), avtb_2d(ji,jj) * avtb(jk) ) * tmask(ji,jj,jk) 
     608# if defined key_c1d 
     609                  e_pdl(ji,jj,jk) = zpdlr * tmask(ji,jj,jk)    ! c1d configuration : save masked Prandlt number 
    605610                  e_ric(ji,jj,jk) = zri * tmask(ji,jj,jk)                            ! c1d config. : save Ri 
    606611# endif 
    607                   zpdl = 1.0                                                         ! Prandtl number 
    608                   IF( zri >= 0.2 )   zpdl = 0.2 / zri 
    609                   zpdl = MAX( 0.1, zpdl ) 
    610                   avt(ji,jj,jk)   = MAX( zpdl * avt(ji,jj,jk), avtb_2d(ji,jj) * avtb(jk) ) * tmask(ji,jj,jk) 
    611                   zmpdl(ji,jj,jk) = zpdl * tmask(ji,jj,jk) 
    612612              END DO 
    613613            END DO 
    614614         END DO 
    615615      ENDIF 
    616  
    617 # if defined key_c1d 
    618       e_pdl(:,:,2:jpkm1) = zmxld(:,:,2:jpkm1)      ! c1d configuration : save masked Prandlt number 
    619       e_pdl(:,:,      1) = e_pdl(:,:,      2) 
    620       e_pdl(:,:,    jpk) = e_pdl(:,:,  jpkm1) 
    621 # endif 
    622  
    623616      CALL lbc_lnk( avt, 'W', 1. )                      ! Lateral boundary conditions on avt  (sign unchanged) 
    624617 
     
    629622      ENDIF 
    630623      ! 
    631    END SUBROUTINE tke_mlmc 
    632  
    633    SUBROUTINE zdf_tke2_init 
     624   END SUBROUTINE tke_avn 
     625 
     626 
     627   SUBROUTINE tke_init 
    634628      !!---------------------------------------------------------------------- 
    635629      !!                  ***  ROUTINE zdf_tke2_init  *** 
    636630      !!                      
    637631      !! ** Purpose :   Initialization of the vertical eddy diffivity and  
    638       !!      viscosity when using a tke turbulent closure scheme 
     632      !!              viscosity when using a tke turbulent closure scheme 
    639633      !! 
    640634      !! ** Method  :   Read the namtke namelist and check the parameters 
    641       !!      called at the first timestep (nit000) 
     635      !!              called at the first timestep (nit000) 
    642636      !! 
    643637      !! ** input   :   Namlist namtke 
    644638      !! 
    645639      !! ** Action  :   Increase by 1 the nstop flag is setting problem encounter 
    646       !! 
    647640      !!---------------------------------------------------------------------- 
    648       USE dynzdf_exp 
    649       USE trazdf_exp 
    650       ! 
    651 # if defined key_vectopt_memory 
    652641      INTEGER ::   ji, jj, jk   ! dummy loop indices 
    653 # else 
    654       INTEGER ::           jk   ! dummy loop indices 
    655 # endif 
    656642      !! 
    657643      NAMELIST/namtke/ ln_rstke, rn_ediff, rn_ediss, rn_ebb  , rn_efave, rn_emin,   & 
     
    661647      !!---------------------------------------------------------------------- 
    662648 
    663       ! Read Namelist namtke : Turbulente Kinetic Energy 
    664       ! -------------------- 
    665       REWIND ( numnam ) 
     649      REWIND ( numnam )               !* Read Namelist namtke : Turbulente Kinetic Energy 
    666650      READ   ( numnam, namtke ) 
    667  
    668       ! Compute boost associated with the Richardson critic 
    669       !     (control values: rn_cri = 0.3   ==> eboost=1.25 for nn_pdl=1) 
    670       !     (                rn_cri = 0.222 ==> eboost=1.               ) 
    671       eboost = rn_cri * ( 2. + rn_ediss / rn_ediff ) / 2. 
    672  
    673  
    674  
    675       ! Parameter control and print 
    676       ! --------------------------- 
    677       ! Control print 
    678       IF(lwp) THEN 
     651       
     652      ri_cri = 2. / ( 2. + rn_ediss / rn_ediff )      ! resulting critical Richardson number 
     653 
     654      IF(lwp) THEN                    !* Control print 
    679655         WRITE(numout,*) 
    680          WRITE(numout,*) 'zdf_tke2_init : tke turbulent closure scheme' 
    681          WRITE(numout,*) '~~~~~~~~~~~~' 
     656         WRITE(numout,*) 'zdf_tke2 : tke turbulent closure scheme - initialisation' 
     657         WRITE(numout,*) '~~~~~~~~' 
    682658         WRITE(numout,*) '          Namelist namtke : set tke mixing parameters' 
    683659         WRITE(numout,*) '             restart with tke from no tke              ln_rstke = ', ln_rstke 
     
    685661         WRITE(numout,*) '             Kolmogoroff dissipation coef.             rn_ediss = ', rn_ediss 
    686662         WRITE(numout,*) '             tke surface input coef.                   rn_ebb   = ', rn_ebb 
    687          WRITE(numout,*) '             tke diffusion coef.                       rn_efave = ', rn_efave 
    688663         WRITE(numout,*) '             minimum value of tke                      rn_emin  = ', rn_emin 
    689664         WRITE(numout,*) '             surface minimum value of tke              rn_emin0 = ', rn_emin0 
    690          WRITE(numout,*) '             number of restart iter loops              nn_itke  = ', nn_itke 
    691665         WRITE(numout,*) '             mixing length type                        nn_mxl   = ', nn_mxl 
    692666         WRITE(numout,*) '             prandl number flag                        nn_pdl   = ', nn_pdl 
    693          WRITE(numout,*) '             horizontal average flag                   nn_ave   = ', nn_ave 
    694          WRITE(numout,*) '             critic Richardson nb                      rn_cri   = ', rn_cri 
    695          WRITE(numout,*) '                and its associated coeff.              eboost   = ', eboost 
    696667         WRITE(numout,*) '             constant background or profile            nn_avb   = ', nn_avb 
    697668         WRITE(numout,*) '             surface mixing length = F(stress) or not  ln_mxl0  = ', ln_mxl0 
     
    705676         WRITE(numout,*) '             coef to compute verticla velocity of LC   rn_lc    = ', rn_lc 
    706677         WRITE(numout,*) 
     678         WRITE(numout,*) '             critical Richardson nb with your choice of coefs.  = ', ri_cri 
    707679      ENDIF 
    708680 
    709       ! Check of some namelist values 
     681      !                               !* Check of some namelist values 
    710682      IF( nn_mxl  < 0    .OR. nn_mxl  > 3   )   CALL ctl_stop( 'bad flag: nn_mxl is  0, 1 or 2 ' ) 
    711683      IF( nn_pdl  < 0    .OR. nn_pdl  > 1   )   CALL ctl_stop( 'bad flag: nn_pdl is  0 or 1    ' ) 
    712       IF( nn_ave  < 0    .OR. nn_ave  > 1   )   CALL ctl_stop( 'bad flag: nn_ave is  0 or 1    ' ) 
    713684      IF( nn_htau < 0    .OR. nn_htau > 2   )   CALL ctl_stop( 'bad flag: nn_htau is 0, 1 or 2 ' ) 
    714685      IF( rn_lc   < 0.15 .OR. rn_lc   > 0.2 )   CALL ctl_stop( 'bad value: rn_lc must be between 0.15 and 0.2 ' ) 
    715686 
    716       IF( nn_etau == 2 )   CALL zdf_mxl( nit000 )      ! Initialization of nmln  
    717  
    718       ! Horizontal average : initialization of weighting arrays  
    719       ! ------------------- 
    720       ! 
    721       IF(lwp) WRITE(numout,*) '          no horizontal average on avt, avmu, avmv' 
    722  
    723       ! Background eddy viscosity and diffusivity profil 
    724       ! ------------------------------------------------ 
    725       IF( nn_avb == 0 ) THEN      ! Define avmb, avtb from namelist parameter 
     687      IF( nn_etau == 2  )   CALL zdf_mxl( nit000 )      ! Initialization of nmln  
     688 
     689      !                               !* Background eddy viscosity and diffusivity profil 
     690      IF( nn_avb == 0 ) THEN                ! Define avmb, avtb from namelist parameter 
    726691         avmb(:) = avm0 
    727692         avtb(:) = avt0 
    728       ELSE                      ! Background profile of avt (fit a theoretical/observational profile (Krauss 1990)  
     693      ELSE                                  ! Background profile of avt (fit a theoretical/observational profile (Krauss 1990)  
    729694         avmb(:) = avm0 
    730695         avtb(:) = avt0 + ( 3.0e-4 - 2 * avt0 ) * 1.0e-4 * gdepw_0(:)   ! m2/s 
     
    732697      ENDIF 
    733698      ! 
    734       !                         ! 2D shape of the avtb 
    735       avtb_2d(:,:) = 1.e0             ! uniform  
    736       ! 
    737       IF( nn_havtb == 1 ) THEN      ! decrease avtb in the equatorial band 
     699      !                                     ! 2D shape of the avtb 
     700      avtb_2d(:,:) = 1.e0                        ! uniform  
     701      ! 
     702      IF( nn_havtb == 1 ) THEN                   ! decrease avtb in the equatorial band 
    738703           !  -15S -5S : linear decrease from avt0 to avt0/10. 
    739704           !  -5S  +5N : cst value avt0/10. 
     
    744709      ENDIF 
    745710 
    746       ! Initialization of vertical eddy coef. to the background value 
    747       ! ------------------------------------------------------------- 
     711      !                               !* depth of penetration of surface tke 
     712      IF( nn_etau /= 0 ) THEN       
     713         SELECT CASE( nn_htau )           ! Choice of the depth of penetration 
     714         CASE( 0 )                                    ! constant depth penetration (here 10 meters) 
     715            htau(:,:) = 10.e0 
     716         CASE( 1 )                                    ! F(latitude) : 5m to 40m at high lat. 
     717            DO jj = 1, jpj 
     718               DO ji = 1, jpi   
     719                  htau(ji,jj) = MAX( 5., MIN( 40., 60.*ABS( SIN( rpi/180. * gphit(ji,jj) ) ) )   ) 
     720               END DO 
     721            END DO 
     722         CASE( 2 )                                    ! F(latitude) : 5m to 60m at high lat. 
     723            DO jj = 1, jpj 
     724               DO ji = 1, jpi 
     725                  htau(ji,jj) =  MAX( 5.,6./4.* MIN( 40., 60.*ABS( SIN( rpi/180. * gphit(ji,jj) ) ) )   ) 
     726               END DO 
     727            END DO 
     728         END SELECT 
     729      ENDIF 
     730 
     731      !                               !* set vertical eddy coef. to the background value 
    748732      DO jk = 1, jpk 
    749733         avt (:,:,jk) = avtb(jk) * tmask(:,:,jk) 
     
    753737      END DO 
    754738      dissl(:,:,:) = 1.e-12 
    755  
    756       ! read or initialize turbulent kinetic energy ( en ) 
    757       ! ------------------------------------------------- 
     739      !                               !* read or initialize all required files  
    758740      CALL tke2_rst( nit000, 'READ' ) 
    759741      ! 
    760    END SUBROUTINE zdf_tke2_init 
     742   END SUBROUTINE tke_init 
    761743 
    762744 
     
    796778                 CALL iom_get( numror, jpdom_autoglo, 'avmv' , avmv  ) 
    797779                 CALL iom_get( numror, jpdom_autoglo, 'dissl', dissl ) 
    798               ELSE                                       ! one at least array is missing 
    799                  CALL tke_mlmc                               ! recompute avt, avm, avmu, avmv and dissl (approximation) 
     780              ELSE                                                 ! one at least array is missing 
     781                 CALL tke_avn                                          ! compute avt, avm, avmu, avmv and dissl (approximation) 
    800782              ENDIF 
    801783           ELSE                                     ! No TKE array found: initialisation 
    802784              IF(lwp) WRITE(numout,*) ' ===>>>> : previous run without tke scheme, en computed by iterative loop' 
    803785              en (:,:,:) = rn_emin * tmask(:,:,:) 
    804               CALL tke_mlmc                               ! recompute avt, avm, avmu, avmv and dissl (approximation) 
     786              CALL tke_avn                               ! recompute avt, avm, avmu, avmv and dissl (approximation) 
    805787              DO jit = nit000 + 1, nit000 + 10   ;   CALL zdf_tke2( jit )   ;   END DO 
    806788           ENDIF 
     
    838820      WRITE(*,*) 'zdf_tke2: You should not have seen this print! error?', kt 
    839821   END SUBROUTINE zdf_tke2 
     822   SUBROUTINE tke2_rst( kt, cdrw ) 
     823     CHARACTER(len=*) ::   cdrw 
     824     WRITE(*,*) 'tke2_rst: You should not have seen this print! error?', kt, cdwr 
     825   END SUBROUTINE tke2_rst 
    840826#endif 
    841827 
  • trunk/NEMO/OPA_SRC/step.F90

    r1482 r1492  
    55   !!====================================================================== 
    66   !! History :  OPA  !  1991-03  (G. Madec)  Original code 
    7    !!                 !  1991-11  (G. Madec) 
    8    !!                 !  1992-06  (M. Imbard)  add a first output record 
    9    !!                 !  1996-04  (G. Madec)  introduction of dynspg 
    10    !!                 !  1996-04  (M.A. Foujols)  introduction of passive tracer 
     7   !!             -   !  1991-11  (G. Madec) 
     8   !!             -   !  1992-06  (M. Imbard)  add a first output record 
     9   !!             -   !  1996-04  (G. Madec)  introduction of dynspg 
     10   !!             -   !  1996-04  (M.A. Foujols)  introduction of passive tracer 
    1111   !!            8.0  !  1997-06  (G. Madec)  new architecture of call 
    1212   !!            8.2  !  1997-06  (G. Madec, M. Imbard, G. Roullet)  free surface 
     
    1515   !!   NEMO     1.0  !  2002-06  (G. Madec)  free form, suppress macro-tasking 
    1616   !!             -   !  2004-08  (C. Talandier) New trends organization 
    17    !!                 !  2005-01  (C. Ethe) Add the KPP closure scheme 
    18    !!                 !  2005-11  (G. Madec)  Reorganisation of tra and dyn calls 
    19    !!                 !  2006-01  (L. Debreu, C. Mazauric)  Agrif implementation 
    20    !!                 !  2006-07  (S. Masson)  restart using iom 
     17   !!             -   !  2005-01  (C. Ethe) Add the KPP closure scheme 
     18   !!             -   !  2005-11  (G. Madec)  Reorganisation of tra and dyn calls 
     19   !!             -   !  2006-01  (L. Debreu, C. Mazauric)  Agrif implementation 
     20   !!             -   !  2006-07  (S. Masson)  restart using iom 
    2121   !!            3.2  !  2009-02  (G. Madec, R. Benshila)  reintroduicing z*-coordinate 
     22   !!             -   !  2009-06  (S. Masson, G. Madec)  TKE2 restart compatible with key_cpl 
    2223   !!---------------------------------------------------------------------- 
    2324 
     
    123124   PRIVATE 
    124125 
    125    PUBLIC stp            ! called by opa.F90 
     126   PUBLIC   stp        ! called by opa.F90 
    126127 
    127128   !! * Substitutions 
     
    129130#  include "zdfddm_substitute.h90" 
    130131   !!---------------------------------------------------------------------- 
    131    !!   OPA 9.0 , LOCEAN-IPSL (2005)  
     132   !! NEMO/OPA 3.2 , LOCEAN-IPSL (2009)  
    132133   !! $Id$ 
    133134   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)  
     
    179180      ! Update data, open boundaries, surface boundary condition (including sea-ice) 
    180181      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
    181  
    182182      IF( lk_dtatem  )   CALL dta_tem( kstp )         ! update 3D temperature data 
    183183      IF( lk_dtasal  )   CALL dta_sal( kstp )         ! update 3D salinity data 
    184  
    185184                         CALL sbc    ( kstp )         ! Sea Boundary Condition (including sea-ice) 
    186  
    187185      IF( lk_obc     )   CALL obc_dta( kstp )         ! update dynamic and tracer data at open boundaries 
    188186      IF( lk_obc     )   CALL obc_rad( kstp )         ! compute phase velocities at open boundaries 
    189  
    190187      IF( lk_bdy     )   CALL bdy_dta( kstp )         ! update dynamic and tracer data at unstructured open boundary 
    191188 
    192189      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
    193       !                Ocean dynamics : ssh, wn, hdiv, rot                   ! 
    194       !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
    195                        CALL div_cur( kstp )                 ! Horizontal divergence & Relative vorticity 
    196       IF( n_cla == 1 ) CALL div_cla( kstp )                 ! Cross Land Advection (Update Hor. divergence) 
    197                        CALL ssh_wzv( kstp )                 ! after ssh & vertical velocity 
    198  
    199       !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
    200       ! Ocean physics update 
    201       !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
    202       ! N.B. ua, va, ta, sa arrays are used as workspace in this section 
    203       !----------------------------------------------------------------------- 
    204  
    205                        CALL bn2( tb, sb, rn2b )              ! before Brunt-Vaisala frequency 
    206                        CALL bn2( tn, sn, rn2  )              ! now    Brunt-Vaisala frequency 
    207  
    208       !----------------------------------------------------------------------- 
    209       !  VERTICAL PHYSICS 
    210       !----------------------------------------------------------------------- 
    211       !                                                     ! Vertical eddy viscosity and diffusivity coefficients 
    212       IF( lk_zdfric )   CALL zdf_ric( kstp )                       ! Richardson number dependent Kz 
    213  
    214       IF( lk_zdftke )   CALL zdf_tke ( kstp )                      ! TKE  closure scheme for Kz 
    215       IF( lk_zdftke2)   CALL zdf_tke2( kstp )                      ! TKE2 closure scheme for Kz 
    216  
    217       IF( lk_zdfkpp )   CALL zdf_kpp( kstp )                       ! KPP closure scheme for Kz 
    218  
    219       IF( lk_zdfcst )   THEN                                       ! Constant Kz (reset avt, avm[uv] to the background value) 
     190      !  Ocean dynamics : ssh, wn, hdiv, rot                                 ! 
     191      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
     192                         CALL div_cur( kstp )         ! Horizontal divergence & Relative vorticity 
     193      IF( n_cla == 1 )   CALL div_cla( kstp )         ! Cross Land Advection (Update Hor. divergence) 
     194                         CALL ssh_wzv( kstp )         ! after ssh & vertical velocity 
     195 
     196      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
     197      ! Ocean physics update                (ua, va, ta, sa used as workspace) 
     198      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
     199                         CALL bn2( tb, sb, rn2b )     ! before Brunt-Vaisala frequency 
     200                         CALL bn2( tn, sn, rn2  )     ! now    Brunt-Vaisala frequency 
     201      ! 
     202      !  VERTICAL PHYSICS    
     203      !                                               ! Vertical eddy viscosity and diffusivity coefficients 
     204      IF( lk_zdfric  )   CALL zdf_ric( kstp )         ! Richardson number dependent Kz 
     205      IF( lk_zdftke  )   CALL zdf_tke ( kstp )        ! TKE  closure scheme for Kz 
     206      IF( lk_zdftke2 )   CALL zdf_tke2( kstp )        ! TKE2 closure scheme for Kz 
     207      IF( lk_zdfkpp  )   CALL zdf_kpp( kstp )         ! KPP closure scheme for Kz 
     208      IF( lk_zdfcst  )   THEN                         ! Constant Kz (reset avt, avm[uv] to the background value) 
    220209         avt (:,:,:) = avt0 * tmask(:,:,:) 
    221210         avmu(:,:,:) = avm0 * umask(:,:,:) 
    222211         avmv(:,:,:) = avm0 * vmask(:,:,:) 
    223212      ENDIF 
    224  
    225       IF( ln_rnf_mouth ) THEN                                ! increase diffusivity at rivers mouths 
     213      IF( ln_rnf_mouth ) THEN                         ! increase diffusivity at rivers mouths 
    226214         DO jk = 2, nkrnf   ;   avt(:,:,jk) = avt(:,:,jk) + 2.e0 * rn_avt_rnf * rnfmsk(:,:) * tmask(:,:,jk)   ;   END DO 
    227215      ENDIF 
    228  
    229       IF( ln_zdfevd )   CALL zdf_evd( kstp )                 ! enhanced vertical eddy diffusivity 
    230  
    231       IF( lk_zdftmx )   CALL zdf_tmx( kstp )                 ! tidal vertical mixing 
     216      IF( ln_zdfevd  )   CALL zdf_evd( kstp )         ! enhanced vertical eddy diffusivity 
     217 
     218      IF( lk_zdftmx  )   CALL zdf_tmx( kstp )         ! tidal vertical mixing 
    232219 
    233220      IF( lk_zdfddm .AND. .NOT. lk_zdfkpp )   & 
    234          &              CALL zdf_ddm( kstp )                 ! double diffusive mixing 
    235  
    236  
    237                         CALL zdf_bfr( kstp )                 ! bottom friction 
    238  
    239                         CALL zdf_mxl( kstp )                 ! mixed layer depth 
    240  
    241       IF( lrst_oce .AND. lk_zdftke2 )   &                    ! write tke2 information in the restart file 
    242          &               CALL tke2_rst( kstp, 'WRITE' ) 
    243  
    244       !----------------------------------------------------------------------- 
    245       !  LATERAL PHYSICS 
    246       !----------------------------------------------------------------------- 
    247       IF( lk_ldfslp )   THEN  
    248                            CALL eos( tb, sb, rhd, rhop )          ! before in situ density 
    249          IF( ln_zps )      CALL zps_hde( kstp, tb, sb, rhd,  &    ! Partial steps: before horizontal gradient 
    250             &                                gtu, gsu, gru,  &    ! of t, s, rd at the last ocean level 
    251             &                                gtv, gsv, grv ) 
    252                                CALL ldf_slp( kstp, rhd, rn2b )      ! before slope of the lateral mixing 
     221         &               CALL zdf_ddm( kstp )         ! double diffusive mixing 
     222 
     223                         CALL zdf_bfr( kstp )         ! bottom friction 
     224 
     225                         CALL zdf_mxl( kstp )         ! mixed layer depth 
     226 
     227                                                      ! write tke2 information in the restart file 
     228      IF( lrst_oce .AND. lk_zdftke2 )   CALL tke2_rst( kstp, 'WRITE' ) 
     229      ! 
     230      !  LATERAL  PHYSICS  
     231      ! 
     232      IF( lk_ldfslp ) THEN                            ! slope of lateral mixing 
     233                         CALL eos( tb, sb, rhd, rhop )          ! before in situ density 
     234         IF( ln_zps )    CALL zps_hde( kstp, tb, sb, rhd,  &    ! Partial steps: before horizontal gradient 
     235            &                              gtu, gsu, gru,  &    ! of t, s, rd at the last ocean level 
     236            &                              gtv, gsv, grv ) 
     237                         CALL ldf_slp( kstp, rhd, rn2b )        ! before slope of the lateral mixing 
    253238      ENDIF 
    254239#if defined key_traldf_c2d 
    255       IF( lk_traldf_eiv )   CALL ldf_eiv( kstp )                 ! eddy induced velocity coefficient 
     240      IF( lk_traldf_eiv )   CALL ldf_eiv( kstp )      ! eddy induced velocity coefficient 
    256241#  endif 
    257242 
    258243      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
    259       ! diagnostics and outputs 
    260       !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
    261                          CALL dia_wri( kstp, indic )         ! ocean model: outputs 
    262       IF( lk_floats  )   CALL flo_stp( kstp )                ! drifting Floats 
    263       IF( lk_diaspr  )   CALL dia_spr( kstp )                ! Surface pressure diagnostics 
    264       IF( lk_diahth  )   CALL dia_hth( kstp )                ! Thermocline depth (20 degres isotherm depth) 
    265       IF( lk_diagap  )   CALL dia_gap( kstp )                ! basin averaged diagnostics 
    266       IF( lk_diahdy  )   CALL dia_hdy( kstp )                ! dynamical heigh diagnostics 
    267       IF( lk_diafwb  )   CALL dia_fwb( kstp )                ! Fresh water budget diagnostics 
    268       IF( ln_diaptr  )   CALL dia_ptr( kstp )                ! Poleward TRansports diagnostics 
     244      ! diagnostics and outputs             (ua, va, ta, sa used as workspace) 
     245      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
     246                         CALL dia_wri( kstp, indic )  ! ocean model: outputs 
     247      IF( lk_floats  )   CALL flo_stp( kstp )         ! drifting Floats 
     248      IF( lk_diaspr  )   CALL dia_spr( kstp )         ! Surface pressure diagnostics 
     249      IF( lk_diahth  )   CALL dia_hth( kstp )         ! Thermocline depth (20 degres isotherm depth) 
     250      IF( lk_diagap  )   CALL dia_gap( kstp )         ! basin averaged diagnostics 
     251      IF( lk_diahdy  )   CALL dia_hdy( kstp )         ! dynamical heigh diagnostics 
     252      IF( lk_diafwb  )   CALL dia_fwb( kstp )         ! Fresh water budget diagnostics 
     253      IF( ln_diaptr  )   CALL dia_ptr( kstp )         ! Poleward TRansports diagnostics 
    269254 
    270255#if defined key_top 
     
    272257      ! Passive Tracer Model 
    273258      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
    274       ! N.B. ua, va, ta, sa arrays are used as workspace in this section 
    275       !----------------------------------------------------------------------- 
    276                              CALL trc_stp( kstp )            ! time-stepping 
    277 #endif 
    278  
    279       !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
    280       ! Active tracers 
    281       !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
    282       ! N.B. ua, va arrays are used as workspace in this section 
    283       !----------------------------------------------------------------------- 
     259                         CALL trc_stp( kstp )         ! time-stepping 
     260#endif 
     261 
     262      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
     263      ! Active tracers                              (ua, va used as workspace) 
     264      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
    284265                             ta(:,:,:) = 0.e0               ! set tracer trends to zero 
    285266                             sa(:,:,:) = 0.e0 
     
    300281                             CALL tra_zdf    ( kstp )       ! vertical mixing and after tracer fields 
    301282 
    302       IF( .NOT. ln_dynhpg_imp  ) THEN                       ! centered hpg (default case) 
    303                                CALL eos( tn, sn, rhd, rhop )          ! now (swap=before) in situ density for dynhpg module 
    304          IF( ln_zps    )       CALL zps_hde( kstp, tn, sn, rhd,   &   ! Partial steps: now horizontal gradient 
    305             &                                     gtu, gsu, gru,  &   ! of t, s, rd at the bottom ocean level 
    306             &                                     gtv, gsv, grv ) 
     283      IF( ln_dynhpg_imp  ) THEN                             ! semi-implicit hpg (time stepping then eos) 
     284         IF( ln_zdfnpc   )   CALL tra_npc    ( kstp )            ! update after fields by non-penetrative convection 
     285                             CALL tra_nxt    ( kstp )            ! tracer fields at next time step 
     286                             CALL eos( ta, sa, rhd, rhop )       ! Time-filtered in situ density for hpg computation 
     287         IF( ln_zps      )   CALL zps_hde( kstp, ta, sa, rhd,   &   ! Partial steps: time filtered hor. derivative 
     288            &                                   gtu, gsu, gru,  &   ! of t, s, rd at the bottom ocean level 
     289            &                                   gtv, gsv, grv ) 
     290          
     291      ELSE                                                  ! centered hpg  (eos then time stepping) 
     292                             CALL eos( tn, sn, rhd, rhop )       ! now in situ density for hpg computation 
     293         IF( ln_zps      )   CALL zps_hde( kstp, tn, sn, rhd,   &   ! Partial steps: now horizontal derivative 
     294            &                                   gtu, gsu, gru,  &   ! of t, s, rd at the bottom ocean level 
     295            &                                   gtv, gsv, grv ) 
     296         IF( ln_zdfnpc   )   CALL tra_npc    ( kstp )       ! update after fields by non-penetrative convection 
     297                             CALL tra_nxt    ( kstp )       ! tracer fields at next time step 
    307298      ENDIF  
    308       IF( ln_zdfnpc      )   CALL tra_npc    ( kstp )       ! update after fields by non-penetrative convection 
    309                              CALL tra_nxt    ( kstp )       ! tracer fields at next time step 
    310       IF( ln_dynhpg_imp  ) THEN                             ! semi-implicit hpg 
    311                                CALL eos( ta, sa, rhd, rhop )          ! Time-filtered in situ density used in dynhpg module 
    312          IF( ln_zps    )       CALL zps_hde( kstp, ta, sa, rhd,   &   ! Partial steps: time filtered hor. gradient 
    313             &                                     gtu, gsu, gru,  &   ! of t, s, rd at the bottom ocean level 
    314             &                                     gtv, gsv, grv ) 
    315       ENDIF 
    316  
    317       !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
    318       ! Dynamics 
    319       !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
    320       ! N.B. ta, sa arrays are used as workspace in this section  
    321       !----------------------------------------------------------------------- 
    322                                ua(:,:,:) = 0.e0               ! set dynamics trends to zero 
     299 
     300      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
     301      ! Dynamics                                    (ta, sa used as workspace) 
     302      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
     303                               ua(:,:,:) = 0.e0             ! set dynamics trends to zero 
    323304                               va(:,:,:) = 0.e0 
    324305 
    325                                CALL dyn_adv( kstp )           ! advection (vector or flux form) 
    326                                CALL dyn_vor( kstp )           ! vorticity term including Coriolis 
    327                                CALL dyn_ldf( kstp )           ! lateral mixing 
    328 #if defined key_agrif 
    329       IF(.NOT. Agrif_Root())   CALL Agrif_Sponge_dyn          ! momemtum sponge 
    330 #endif 
    331                                CALL dyn_hpg( kstp )           ! horizontal gradient of Hydrostatic pressure 
    332                                CALL dyn_zdf( kstp )           ! vertical diffusion 
     306                               CALL dyn_adv( kstp )         ! advection (vector or flux form) 
     307                               CALL dyn_vor( kstp )         ! vorticity term including Coriolis 
     308                               CALL dyn_ldf( kstp )         ! lateral mixing 
     309#if defined key_agrif 
     310      IF(.NOT. Agrif_Root())   CALL Agrif_Sponge_dyn        ! momemtum sponge 
     311#endif 
     312                               CALL dyn_hpg( kstp )         ! horizontal gradient of Hydrostatic pressure 
     313                               CALL dyn_zdf( kstp )         ! vertical diffusion 
    333314      IF( lk_dynspg_rl ) THEN 
    334          IF( lk_obc    )       CALL obc_spg( kstp )           ! surface pressure gradient at open boundaries 
     315         IF( lk_obc    )       CALL obc_spg( kstp )         ! surface pressure gradient at open boundaries 
    335316      ENDIF 
    336317                               indic=0 
    337                                CALL dyn_spg( kstp, indic )    ! surface pressure gradient 
    338                                CALL dyn_nxt( kstp )           ! lateral velocity at next time step 
    339  
    340                                CALL ssh_nxt( kstp )           ! sea surface height at next time step 
     318                               CALL dyn_spg( kstp, indic )  ! surface pressure gradient 
     319                               CALL dyn_nxt( kstp )         ! lateral velocity at next time step 
     320 
     321                               CALL ssh_nxt( kstp )         ! sea surface height at next time step 
    341322 
    342323      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
    343324      ! Control and restarts 
    344325      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
    345                                  CALL stp_ctl( kstp, indic ) 
    346       IF( indic < 0          )   THEN 
    347                                  CALL ctl_stop( 'step: indic < 0' ) 
    348                                  CALL dia_wri_state( 'output.abort', kstp ) 
    349       ENDIF 
    350       IF( kstp == nit000     )   CALL iom_close( numror )             ! close input  ocean restart file 
    351       IF( lrst_oce           )   CALL rst_write    ( kstp )           ! write output ocean restart file 
    352       IF( lk_obc             )   CALL obc_rst_write( kstp )           ! write open boundary restart file 
    353  
    354       !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
    355       ! Trends 
    356       !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
    357       ! N.B. ua, va, ta, sa arrays are used as workspace in this section 
    358       !----------------------------------------------------------------------- 
    359  
    360       IF( nstop == 0 ) THEN                                 ! Diagnostics: 
    361          IF( lk_trddyn  )   CALL trd_dwr( kstp )                 ! trends: dynamics  
    362          IF( lk_trdtra  )   CALL trd_twr( kstp )                 ! trends: active tracers 
    363          IF( lk_trdmld  )   CALL trd_mld( kstp )                 ! trends: Mixed-layer  
    364          IF( lk_trdvor  )   CALL trd_vor( kstp )                 ! trends: vorticity budget 
     326                               CALL stp_ctl( kstp, indic ) 
     327      IF( indic < 0        )   THEN 
     328                               CALL ctl_stop( 'step: indic < 0' ) 
     329                               CALL dia_wri_state( 'output.abort', kstp ) 
     330      ENDIF 
     331      IF( kstp == nit000   )   CALL iom_close( numror )     ! close input  ocean restart file 
     332      IF( lrst_oce         )   CALL rst_write    ( kstp )   ! write output ocean restart file 
     333      IF( lk_obc           )   CALL obc_rst_write( kstp )   ! write open boundary restart file 
     334 
     335      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
     336      ! Trends                              (ua, va, ta, sa used as workspace) 
     337      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
     338      IF( nstop == 0 ) THEN                          
     339         IF( lk_trddyn     )   CALL trd_dwr( kstp )         ! trends: dynamics  
     340         IF( lk_trdtra     )   CALL trd_twr( kstp )         ! trends: active tracers 
     341         IF( lk_trdmld     )   CALL trd_mld( kstp )         ! trends: Mixed-layer  
     342         IF( lk_trdvor     )   CALL trd_vor( kstp )         ! trends: vorticity budget 
    365343      ENDIF 
    366344 
     
    368346      ! Coupled mode 
    369347      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
    370  
    371       IF( lk_cpl )   CALL sbc_cpl_snd( kstp )                 ! coupled mode : field exchanges 
     348      IF( lk_cpl           )   CALL sbc_cpl_snd( kstp )     ! coupled mode : field exchanges 
    372349      ! 
    373350      ! 
Note: See TracChangeset for help on using the changeset viewer.