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 508 for trunk/NEMO/OPA_SRC/ZDF/zdftke.F90 – NEMO

Ignore:
Timestamp:
2006-10-03T17:58:55+02:00 (18 years ago)
Author:
opalod
Message:

nemo_v1_update_071:RB: add iom for restart and reorganization of restart

File:
1 edited

Legend:

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

    r474 r508  
    55   !!                 turbulent closure parameterization 
    66   !!===================================================================== 
     7   !! History :   6.0  !  91-03  (b. blanke)  Original code 
     8   !!             7.0  !  91-11  (G. Madec)   bug fix 
     9   !!             7.1  !  92-10  (G. Madec)   new mixing length and eav 
     10   !!             7.2  !  93-03  (M. Guyon)   symetrical conditions 
     11   !!             7.3  !  94-08  (G. Madec, M. Imbard)   npdl flag 
     12   !!             7.5  !  96-01  (G. Madec)   s-coordinates 
     13   !!             8.0  !  97-07  (G. Madec)   lbc 
     14   !!             8.1  !  99-01  (E. Stretta) new option for the mixing length 
     15   !!             8.5  !  02-06  (G. Madec) add zdf_tke_init routine 
     16   !!             8.5  !  02-08  (G. Madec)  ri_c and Free form, F90 
     17   !!             9.0  !  04-10  (C. Ethe )  1D configuration 
     18   !!             9.0  !  02-08  (G. Madec)  autotasking optimization 
     19   !!             9.0  !  06-07  (S. Masson)  distributed restart using iom 
     20   !!---------------------------------------------------------------------- 
    721#if defined key_zdftke   ||   defined key_esopa 
    822   !!---------------------------------------------------------------------- 
    9    !!   'key_zdftke'                                             TKE scheme 
     23   !!   'key_zdftke'                                   TKE vertical physics 
     24   !!---------------------------------------------------------------------- 
    1025   !!---------------------------------------------------------------------- 
    1126   !!   zdf_tke      : update momentum and tracer Kz from a tke scheme 
    1227   !!   zdf_tke_init : initialization, namelist read, and parameters control 
     28   !!   tke_rst      : read/write tke restart in ocean restart file 
    1329   !!---------------------------------------------------------------------- 
    14    !! * Modules used 
    1530   USE oce             ! ocean dynamics and active tracers  
    1631   USE dom_oce         ! ocean space and time domain 
    1732   USE zdf_oce         ! ocean vertical physics 
    18    USE in_out_manager  ! I/O manager 
    19    USE lbclnk          ! ocean lateral boundary conditions (or mpp link) 
    2033   USE phycst          ! physical constants 
    2134   USE taumod          ! surface stress 
     35   USE lbclnk          ! ocean lateral boundary conditions (or mpp link) 
    2236   USE prtctl          ! Print control 
     37   USE in_out_manager  ! I/O manager 
     38   USE iom 
     39   USE restart         ! only for lrst_oce 
    2340 
    2441   IMPLICIT NONE 
    2542   PRIVATE 
    2643 
    27    !! * Routine accessibility 
    28    PUBLIC zdf_tke        ! routine called in step module 
    29    PUBLIC zdf_tke_init   ! routine called in zdftke_jki module 
    30  
    31    !! * Share Module variables 
    32    LOGICAL, PUBLIC, PARAMETER ::   lk_zdftke = .TRUE.    !: TKE vertical mixing flag 
    33    LOGICAL, PUBLIC ::         & !!: ** tke namelist (namtke) ** 
    34      ln_rstke = .FALSE.          !: =T restart with tke from a run without tke with  
    35      !                           !  a none zero initial value for en 
    36    REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpk) ::   &   !: 
    37       en                         !: now turbulent kinetic energy 
    38  
    39    INTEGER, PUBLIC ::         & !!! ** tke namelist (namtke) ** 
    40       nitke = 50 ,            &  ! number of restart iterative loops 
    41       nmxl  =  2 ,            &  ! = 0/1/2/3 flag for the type of mixing length used 
    42       npdl  =  1 ,            &  ! = 0/1/2 flag on prandtl number on vert. eddy coeff. 
    43       nave  =  1 ,            &  ! = 0/1 flag for horizontal average on avt, avmu, avmv 
    44       navb  =  0                 ! = 0/1 flag for constant or profile background avt 
    45    REAL(wp), PUBLIC ::        & !!! ** tke namlist (namtke) ** 
    46       ediff = 0.1_wp       ,  &  ! coeff. for vertical eddy coef.; avt=ediff*mxl*sqrt(e) 
    47       ediss = 0.7_wp       ,  &  ! coef. of the Kolmogoroff dissipation  
    48       ebb   = 3.75_wp      ,  &  ! coef. of the surface input of tke 
    49       efave = 1._wp        ,  &  ! coef. for the tke vert. diff. coeff.; avtke=efave*avm 
    50       emin  = 0.7071e-6_wp ,  &  ! minimum value of tke (m2/s2) 
    51       emin0 = 1.e-4_wp     ,  &  ! surface minimum value of tke (m2/s2) 
    52       ri_c  = 2._wp / 9._wp      ! critic Richardson number 
    53    REAL(wp), PUBLIC ::        & 
    54       eboost                     ! multiplicative coeff of the shear product. 
    55  
    56    !! caution vectopt_memory change the solution (last digit of the solver stat) 
     44   PUBLIC   zdf_tke        ! routine called in step module 
     45   PUBLIC   zdf_tke_init   ! routine also called in zdftke_jki module 
     46   PUBLIC   tke_rst        ! routine also called in zdftke_jki module 
     47 
     48   LOGICAL , PUBLIC, PARAMETER              ::   lk_zdftke = .TRUE.  !: TKE vertical mixing flag 
     49   REAL(wp), PUBLIC                         ::   eboost              !: multiplicative coeff of the shear product. 
     50   REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpk) ::   en                  !: now turbulent kinetic energy 
    5751# if defined key_vectopt_memory 
    58    REAL(wp), DIMENSION(jpi,jpj,jpk), PUBLIC ::   & 
    59       etmean,    &  ! coefficient used for horizontal smoothing 
    60       eumean,    &  ! at t-, u- and v-points 
    61       evmean        ! 
     52   REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpk) ::   etmean              !: coefficient used for horizontal smoothing 
     53   REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpk) ::   eumean, evmean      !: at t-, u- and v-points 
    6254# endif 
    6355 
     56   !! * Namelist (namtke) 
     57   LOGICAL , PUBLIC ::   ln_rstke = .FALSE.         !: =T restart with tke from a run without tke with  
     58     !                                              !  a none zero initial value for en 
     59   INTEGER , PUBLIC ::   nitke = 50 ,            &  !: number of restart iterative loops 
     60      &                  nmxl  =  2 ,            &  !: = 0/1/2/3 flag for the type of mixing length used 
     61      &                  npdl  =  1 ,            &  !: = 0/1/2 flag on prandtl number on vert. eddy coeff. 
     62      &                  nave  =  1 ,            &  !: = 0/1 flag for horizontal average on avt, avmu, avmv 
     63      &                  navb  =  0                 !: = 0/1 flag for constant or profile background avt 
     64   REAL(wp), PUBLIC ::   ediff = 0.1_wp       ,  &  !: coeff. for vertical eddy coef.; avt=ediff*mxl*sqrt(e) 
     65      &                  ediss = 0.7_wp       ,  &  !: coef. of the Kolmogoroff dissipation  
     66      &                  ebb   = 3.75_wp      ,  &  !: coef. of the surface input of tke 
     67      &                  efave = 1._wp        ,  &  !: coef. for the tke vert. diff. coeff.; avtke=efave*avm 
     68      &                  emin  = 0.7071e-6_wp ,  &  !: minimum value of tke (m2/s2) 
     69      &                  emin0 = 1.e-4_wp     ,  &  !: surface minimum value of tke (m2/s2) 
     70      &                  ri_c  = 2._wp / 9._wp      !: critic Richardson number 
     71   NAMELIST/namtke/ ln_rstke, ediff, ediss, ebb, efave, emin, emin0,   & 
     72      &             ri_c, nitke, nmxl, npdl, nave, navb 
     73 
    6474# if defined key_cfg_1d 
    65    REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpk) ::   &    
    66       e_dis,    &   ! dissipation turbulent lengh scale 
    67       e_mix,    &   ! mixing turbulent lengh scale 
    68       e_pdl,    &   ! prandl number 
    69       e_ric         ! local Richardson number 
     75   !                                                                   ! 1D cfg only 
     76   REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpk) ::   e_dis, e_mix,      &  ! dissipation and mixing turbulent lengh scales 
     77      &                                          e_pdl, e_ric          ! prandl and local Richardson numbers 
    7078#endif 
    7179 
     
    7482#  include "vectopt_loop_substitute.h90" 
    7583   !!---------------------------------------------------------------------- 
    76    !!   OPA 9.0 , LOCEAN-IPSL (2005)  
     84   !!   OPA 9.0 , LOCEAN-IPSL (2006)  
     85   !! $Header$  
     86   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
    7787   !!---------------------------------------------------------------------- 
    7888 
    7989CONTAINS 
    8090 
    81    SUBROUTINE zdf_tke ( kt ) 
     91   SUBROUTINE zdf_tke( kt ) 
    8292      !!---------------------------------------------------------------------- 
    8393      !!                   ***  ROUTINE zdf_tke  *** 
     
    136146      !!                update avt, avmu, avmv (before vertical eddy coef.) 
    137147      !! 
    138       !! References : 
    139       !!      Gaspar et al., jgr, 95, 1990, 
    140       !!      Blanke and Delecluse, jpo, 1991 
    141       !! History : 
    142       !!   6.0  !  91-03  (b. blanke)  Original code 
    143       !!   7.0  !  91-11  (G. Madec)   bug fix 
    144       !!   7.1  !  92-10  (G. Madec)   new mixing length and eav 
    145       !!   7.2  !  93-03  (M. Guyon)   symetrical conditions 
    146       !!   7.3  !  94-08  (G. Madec, M. Imbard)   npdl flag 
    147       !!   7.5  !  96-01  (G. Madec)   s-coordinates 
    148       !!   8.0  !  97-07  (G. Madec)   lbc 
    149       !!   8.1  !  99-01  (E. Stretta) new option for the mixing length 
    150       !!   8.5  !  02-08  (G. Madec)  ri_c and Free form, F90 
    151       !!   9.0  !  04-10  (C. Ethe )  1D configuration 
     148      !! References : Gaspar et al., jgr, 95, 1990, 
     149      !!              Blanke and Delecluse, jpo, 1991 
    152150      !!---------------------------------------------------------------------- 
    153       !! * Modules used 
    154151      USE oce     , zwd   => ua,  &  ! use ua as workspace 
    155152         &          zmxlm => ta,  &  ! use ta as workspace 
    156153         &          zmxld => sa      ! use sa as workspace 
    157  
    158       !! * arguments 
    159       INTEGER, INTENT( in  ) ::   kt ! ocean time step 
    160  
    161       !! * local declarations 
    162       INTEGER ::   ji, jj, jk        ! dummy loop arguments 
    163       REAL(wp) ::   & 
    164          zmlmin, zbbrau,          &  ! temporary scalars 
    165          zfact1, zfact2, zfact3,  &  ! 
    166          zrn2, zesurf,            &  ! 
    167          ztx2, zty2, zav,         &  ! 
    168          zcoef, zcof, zsh2,       &  ! 
    169          zdku, zdkv, zpdl, zri,   &  ! 
    170          zsqen, zesh2,            &  ! 
    171          zemxl, zemlm, zemlp 
     154      ! 
     155      INTEGER, INTENT(in) ::   kt ! ocean time step 
     156      ! 
     157      INTEGER  ::   ji, jj, jk                  ! dummy loop arguments 
     158      REAL(wp) ::   zmlmin, zbbrau,          &  ! temporary scalars 
     159         &          zfact1, zfact2, zfact3,  &  ! 
     160         &          zrn2, zesurf,            &  ! 
     161         &          ztx2, zty2, zav,         &  ! 
     162         &          zcoef, zcof, zsh2,       &  ! 
     163         &          zdku, zdkv, zpdl, zri,   &  ! 
     164         &          zsqen, zesh2,            &  ! 
     165         &          zemxl, zemlm, zemlp 
    172166      !!-------------------------------------------------------------------- 
    173167 
    174       ! Initialization (first time-step only) 
    175       ! -------------- 
    176       IF( kt == nit000  )   CALL zdf_tke_init 
    177  
    178       ! Local constant initialization 
     168      IF( kt == nit000  )   CALL zdf_tke_init      ! Initialization (first time-step only) 
     169 
     170      !                                            ! Local constant initialization 
    179171      zmlmin = 1.e-8 
    180172      zbbrau =  .5 * ebb / rau0 
     
    183175      zfact3 = 0.5 * rdt * ediss 
    184176 
    185  
    186177      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
    187178      ! I.  Mixing length 
    188179      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
    189  
    190180 
    191181      ! Buoyancy length scale: l=sqrt(2*e/n**2) 
     
    204194         END DO 
    205195      END DO 
    206  
    207196 
    208197      ! Physical limits for the mixing length 
     
    291280# endif 
    292281 
    293  
    294282      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
    295283      ! II  Tubulent kinetic energy time stepping 
    296284      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
    297  
    298285 
    299286      ! 1. Vertical eddy viscosity on tke (put in zmxlm) and first estimate of avt 
     
    475462      CALL lbc_lnk( en , 'W', 1. )   ;   CALL lbc_lnk( avt, 'W', 1. ) 
    476463 
    477  
    478464      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
    479465      ! III.  Before vertical eddy vicosity and diffusivity coefficients 
     
    601587      ! ------------------------------===== 
    602588      CALL lbc_lnk( avt, 'W', 1. ) 
     589 
     590      ! write en in restart file 
     591      ! ------------------------ 
     592      IF( lrst_oce )   CALL tke_rst( kt, 'WRITE' ) 
    603593 
    604594      IF(ln_ctl) THEN 
     
    624614      !! ** Action  :   Increase by 1 the nstop flag is setting problem encounter 
    625615      !! 
    626       !! history : 
    627       !!  8.5  ! 02-06 (G. Madec) original code 
    628616      !!---------------------------------------------------------------------- 
    629       !! * Module used 
    630617      USE dynzdf_exp 
    631618      USE trazdf_exp 
    632  
    633       !! * local declarations 
    634       !! caution vectopt_memory change the solution (last digit of the solver stat) 
     619      ! 
    635620# if defined key_vectopt_memory 
    636       INTEGER ::   ji, jj, jk, jit   ! dummy loop indices 
     621      ! caution vectopt_memory change the solution (last digit of the solver stat) 
     622      INTEGER ::   ji, jj, jk   ! dummy loop indices 
    637623# else 
    638       INTEGER ::           jk, jit   ! dummy loop indices 
     624      INTEGER ::           jk   ! dummy loop indices 
    639625# endif 
    640  
    641       NAMELIST/namtke/ ln_rstke, ediff, ediss, ebb, efave, emin, emin0,   & 
    642          ri_c, nitke, nmxl, npdl, nave, navb 
    643626      !!---------------------------------------------------------------------- 
    644627 
     
    681664      ! Check nmxl and npdl values 
    682665      IF( nmxl < 0 .OR. nmxl > 3 ) CALL ctl_stop( '          bad flag: nmxl is < 0 or > 3 ' ) 
    683       IF ( npdl < 0 .OR. npdl > 1 ) CALL ctl_stop( '          bad flag: npdl is < 0 or > 1 ' ) 
     666      IF( npdl < 0 .OR. npdl > 1 ) CALL ctl_stop( '          bad flag: npdl is < 0 or > 1 ' ) 
    684667 
    685668      ! Horizontal average : initialization of weighting arrays  
     
    691674         IF(lwp) WRITE(numout,*) '          no horizontal average on avt, avmu, avmv' 
    692675         IF(lwp) WRITE(numout,*) '          only in very high horizontal resolution !' 
    693 !! caution vectopt_memory change the solution (last digit of the solver stat) 
    694676# if defined key_vectopt_memory 
     677         ! caution vectopt_memory change the solution (last digit of the solver stat) 
    695678         ! weighting mean arrays etmean, eumean and evmean 
    696679         !           ( 1  1 )                                          ( 1 ) 
     
    720703      CASE ( 1 )                ! horizontal average  
    721704         IF(lwp) WRITE(numout,*) '          horizontal average on avt, avmu, avmv' 
    722 !! caution vectopt_memory change the solution (last digit of the solver stat) 
    723705# if defined key_vectopt_memory 
     706         ! caution vectopt_memory change the solution (last digit of the solver stat) 
    724707         ! weighting mean arrays etmean, eumean and evmean 
    725708         !           ( 1  1 )              ( 1/2  1/2 )             ( 1/2  1  1/2 ) 
     
    790773 
    791774 
    792       ! Initialization of turbulent kinetic energy ( en ) 
     775      ! read or initialize turbulent kinetic energy ( en ) 
    793776      ! ------------------------------------------------- 
    794       IF( ln_rstart ) THEN 
    795          ! no en field in the restart file, en set by iterative loop 
    796          IF( ln_rstke ) THEN 
    797             en (:,:,:) = emin * tmask(:,:,:) 
    798             DO jit = 2, nitke+1 
    799                CALL zdf_tke( jit ) 
    800             END DO 
    801          ENDIF 
    802          ! otherwise en is already read in dtrlec called by inidtr 
    803       ELSE 
    804          ! no restart: en set to emin 
    805          en(:,:,:) = emin * tmask(:,:,:) 
    806       ENDIF 
    807  
     777      CALL tke_rst( nit000, 'READ' ) 
     778      ! 
    808779   END SUBROUTINE zdf_tke_init 
     780 
     781 
     782   SUBROUTINE tke_rst( kt, cdrw ) 
     783     !!--------------------------------------------------------------------- 
     784     !!                   ***  ROUTINE ts_rst  *** 
     785     !!                      
     786     !! ** Purpose : Read or write filtered free surface arrays in restart file 
     787     !! 
     788     !! ** Method  :  
     789     !! 
     790     !!---------------------------------------------------------------------- 
     791     INTEGER         , INTENT(in) ::   kt         ! ocean time-step 
     792     CHARACTER(len=*), INTENT(in) ::   cdrw       ! "READ"/"WRITE" flag 
     793     ! 
     794     INTEGER ::   jit   ! dummy loop indices 
     795     !!---------------------------------------------------------------------- 
     796     ! 
     797     IF( TRIM(cdrw) == 'READ' ) THEN 
     798        IF( ln_rstart ) THEN 
     799           IF( iom_varid( numror, 'en' ) > 0 .AND. .NOT.(ln_rstke) ) THEN  
     800              CALL iom_get( numror, jpdom_local, 'en', en ) 
     801           ELSE 
     802              IF(lwp .AND. iom_varid(numror,'en') > 0 ) WRITE(numout,*) ' ===>>>> : previous run without tke scheme' 
     803              IF(lwp .AND. ln_rstke ) WRITE(numout,*) ' ===>>>> : We do not use en from the restart file' 
     804              IF(lwp) WRITE(numout,*) ' ===>>>> : en set by iterative loop' 
     805              IF(lwp) WRITE(numout,*) ' =======             =========' 
     806              en (:,:,:) = emin * tmask(:,:,:) 
     807              DO jit = 2, nitke+1 
     808                 CALL zdf_tke( jit ) 
     809              END DO 
     810           ENDIF 
     811        ELSE 
     812           en(:,:,:) = emin * tmask(:,:,:)      ! no restart: en set to emin 
     813        ENDIF 
     814     ELSEIF( TRIM(cdrw) == 'WRITE' ) THEN 
     815        CALL iom_rstput( kt, nitrst, numrow, 'en', en ) 
     816     ENDIF 
     817     ! 
     818   END SUBROUTINE tke_rst 
    809819 
    810820#else 
     
    812822   !!   Dummy module :                                        NO TKE scheme 
    813823   !!---------------------------------------------------------------------- 
    814    LOGICAL, PUBLIC, PARAMETER ::   lk_zdftke = .FALSE.   !: TKE flag 
     824   PUBLIC, LOGICAL, PARAMETER ::   lk_zdftke = .FALSE.   !: TKE flag 
    815825CONTAINS 
    816826   SUBROUTINE zdf_tke( kt )          ! Empty routine 
Note: See TracChangeset for help on using the changeset viewer.