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

Changeset 3887


Ignore:
Timestamp:
2013-04-22T15:19:17+02:00 (11 years ago)
Author:
acc
Message:

Branch 2013/dev_r3858_NOC_ZTC, #863. Additions to nam_vvl so that all options can be controlled via the namelist and reported to ocean.output.

Location:
branches/2013/dev_r3858_NOC_ZTC/NEMOGCM
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • branches/2013/dev_r3858_NOC_ZTC/NEMOGCM/CONFIG/ORCA2_LIM/EXP00/namelist

    r3865 r3887  
    642642&nam_vvl    !   vertical coordinate options 
    643643!----------------------------------------------------------------------- 
    644    ln_vvl_zstar  = .false. !  zstar vertical coordinate                     
    645    ln_vvl_ztilde = .true.  !  hybrid verticalcoordinate: only high frequency variations 
    646    ln_vvl_layer  = .false. !  full layer vertical coordinate 
    647    rn_ahe3       = 0.e0    !  thickness diffusion coefficient  
    648    ln_vvl_dbg    = .true.  !  debug prints    (T/F) 
     644   ln_vvl_zstar  = .false.          !  zstar vertical coordinate                     
     645   ln_vvl_ztilde = .true.           !  ztilde vertical coordinate: only high frequency variations 
     646   ln_vvl_layer  = .false.          !  full layer vertical coordinate 
     647   ln_vvl_ztilde_as_zstar = .false. !  ztilde vertical coordinate emulating zstar 
     648   rn_ahe3       = 0.e0             !  thickness diffusion coefficient  
     649   rn_rst_e3t    = 30._wp           ! ztilde to zstar restoration timescale [days] 
     650   rn_lf_cutoff  = 5.0_wp           ! cutoff frequency for low-pass filter  [days] 
     651   rn_zdef_max   = 0.9_wp           ! maximum fractional e3t deformation 
     652   ln_vvl_dbg    = .true.           !  debug prints    (T/F) 
    649653/ 
    650654!----------------------------------------------------------------------- 
  • branches/2013/dev_r3858_NOC_ZTC/NEMOGCM/NEMO/OPA_SRC/DOM/domvvl.F90

    r3884 r3887  
    4444 
    4545   !!* Namelist nam_vvl 
    46    LOGICAL , PUBLIC                                      :: ln_vvl_zstar  = .FALSE.   ! zstar  vertical coordinate 
    47    LOGICAL , PUBLIC                                      :: ln_vvl_ztilde = .FALSE.   ! ztilde vertical coordinate 
    48    LOGICAL , PUBLIC                                      :: ln_vvl_layer  = .FALSE.   ! level  vertical coordinate 
    49    LOGICAL , PUBLIC                                      :: ln_vvl_kepe   = .FALSE.   ! kinetic/potential energy transfer 
    50    !                                                                                  ! conservation: not used yet 
    51    REAL(wp)                                              :: rn_ahe3       =  0.e0     ! thickness diffusion coefficient 
    52    LOGICAL , PUBLIC                                      :: ln_vvl_dbg    = .FALSE.   ! debug control prints 
     46   LOGICAL , PUBLIC                                      :: ln_vvl_zstar           = .FALSE.   ! zstar  vertical coordinate 
     47   LOGICAL , PUBLIC                                      :: ln_vvl_ztilde          = .FALSE.   ! ztilde vertical coordinate 
     48   LOGICAL , PUBLIC                                      :: ln_vvl_layer           = .FALSE.   ! level  vertical coordinate 
     49   LOGICAL , PUBLIC                                      :: ln_vvl_ztilde_as_zstar = .FALSE.   ! ztilde vertical coordinate 
     50   LOGICAL , PUBLIC                                      :: ln_vvl_kepe            = .FALSE.   ! kinetic/potential energy transfer 
     51   !                                                                                           ! conservation: not used yet 
     52   REAL(wp)                                              :: rn_ahe3                =  0.0_wp   ! thickness diffusion coefficient 
     53   REAL(wp)                                              :: rn_rst_e3t             =  30._wp   ! ztilde to zstar restoration timescale [days] 
     54   REAL(wp)                                              :: rn_lf_cutoff           =  5.0_wp   ! cutoff frequency for low-pass filter  [days] 
     55   REAL(wp)                                              :: rn_zdef_max            =  0.9_wp   ! maximum fractional e3t deformation 
     56   LOGICAL , PUBLIC                                      :: ln_vvl_dbg             = .FALSE.   ! debug control prints 
    5357 
    5458   !! * Module variables 
    55    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: un_td, vn_td              ! thickness diffusion transport 
    56    REAL(wp)        , ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: hdiv_lf                   ! low frequency part of hz divergence 
    57    REAL(wp)        , ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: tilde_e3t_b, tilde_e3t_n  ! baroclinic scale factors 
    58    REAL(wp)        , ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: tilde_e3t_a               ! baroclinic scale factors 
    59    REAL(wp)        , ALLOCATABLE, SAVE, DIMENSION(:,:)   :: frq_rst_e3t               ! retoring period for scale factors 
    60    REAL(wp)        , ALLOCATABLE, SAVE, DIMENSION(:,:)   :: frq_rst_hdv               ! retoring period for low freq. divergence 
    61  
    62    REAL(wp),         ALLOCATABLE, SAVE, DIMENSION(:)     ::   r2dt   ! vertical profile time-step, = 2 rdttra  
    63       !                                                              ! except at nit000 (=rdttra) if neuler=0 
     59   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: un_td, vn_td                       ! thickness diffusion transport 
     60   REAL(wp)        , ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: hdiv_lf                            ! low frequency part of hz divergence 
     61   REAL(wp)        , ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: tilde_e3t_b, tilde_e3t_n           ! baroclinic scale factors 
     62   REAL(wp)        , ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: tilde_e3t_a                        ! baroclinic scale factors 
     63   REAL(wp)        , ALLOCATABLE, SAVE, DIMENSION(:,:)   :: frq_rst_e3t                        ! retoring period for scale factors 
     64   REAL(wp)        , ALLOCATABLE, SAVE, DIMENSION(:,:)   :: frq_rst_hdv                        ! retoring period for low freq. divergence 
    6465 
    6566   !! * Substitutions 
     
    116117      !! Reference  : Leclair, M., and G. Madec, 2011, Ocean Modelling. 
    117118      !!---------------------------------------------------------------------- 
    118       USE phycst,  ONLY : rpi 
     119      USE phycst,  ONLY : rpi, rsmall 
    119120      !! * Local declarations 
    120121      INTEGER ::   jk 
     
    179180      ! ============================================ 
    180181      IF( ln_vvl_ztilde ) THEN 
    181          ! - ML - In the future, this should be tunable by the user (namelist) 
    182          frq_rst_e3t(:,:) = 2.e0_wp * rpi / ( 30.e0_wp * 86400.e0_wp ) 
    183          frq_rst_hdv(:,:) = 2.e0_wp * rpi / (  5.e0_wp * 86400.e0_wp ) 
    184 ! Use these next two to emulate z-star using z-tilde 
    185          frq_rst_e3t(:,:) = 0.e0_wp  
    186          frq_rst_hdv(:,:) = 1.e0_wp / rdt 
     182         ! Values in days provided via the namelist; use rsmall to avoid possible division by zero errors with faulty settings 
     183         frq_rst_e3t(:,:) = 2.e0_wp * rpi / ( MAX( rn_rst_e3t  , rsmall ) * 86400.e0_wp ) 
     184         frq_rst_hdv(:,:) = 2.e0_wp * rpi / ( MAX( rn_lf_cutoff, rsmall ) * 86400.e0_wp ) 
     185         IF( ln_vvl_ztilde_as_zstar ) THEN 
     186            ! Ignore namelist settings and use these next two to emulate z-star using z-tilde 
     187            frq_rst_e3t(:,:) = 0.e0_wp  
     188            frq_rst_hdv(:,:) = 1.e0_wp / rdt 
     189         ENDIF 
    187190      ENDIF 
    188191 
     
    222225      INTEGER , DIMENSION(3)                 :: ijk_max, ijk_min      ! temporary integers 
    223226      REAL(wp)                               :: z2dt                  ! temporary scalars 
    224       REAL(wp)                               :: z_def_max             ! temporary scalar 
    225227      REAL(wp)                               :: z_tmin, z_tmax        ! temporary scalars 
    226228      !!---------------------------------------------------------------------- 
     
    351353         ! Maximum deformation control 
    352354         ! ~~~~~~~~~~~~~~~~~~~~~~~~~~~ 
    353          ! - ML - Should perhaps be put in the namelist 
    354          z_def_max = 0.9e0 
    355355         ze3t(:,:,jpk) = 0.e0 
    356356         DO jk = 1, jpkm1 
     
    362362         IF( lk_mpp )   CALL mpp_min( z_tmin )                 ! min over the global domain 
    363363         ! - ML - test: for the moment, stop simulation for too large e3_t variations 
    364          IF( ( z_tmax .GT. z_def_max ) .OR. ( z_tmin .LT. - z_def_max ) ) THEN 
     364         IF( ( z_tmax .GT. rn_zdef_max ) .OR. ( z_tmin .LT. - rn_zdef_max ) ) THEN 
    365365            IF( lk_mpp ) THEN 
    366366               CALL mpp_maxloc( ze3t, tmask, z_tmax, ijk_max(1), ijk_max(2), ijk_max(3) ) 
     
    384384         ! - ML - end test 
    385385         ! - ML - Imposing these limits will cause a baroclinicity error which is corrected for below 
    386          tilde_e3t_a(:,:,:) = MIN( tilde_e3t_a(:,:,:),   z_def_max * e3t_0(:,:,:) ) 
    387          tilde_e3t_a(:,:,:) = MAX( tilde_e3t_a(:,:,:), - z_def_max * e3t_0(:,:,:) ) 
     386         tilde_e3t_a(:,:,:) = MIN( tilde_e3t_a(:,:,:),   rn_zdef_max * e3t_0(:,:,:) ) 
     387         tilde_e3t_a(:,:,:) = MAX( tilde_e3t_a(:,:,:), - rn_zdef_max * e3t_0(:,:,:) ) 
    388388 
    389389         ! Add "tilda" part to the after scale factor 
     
    791791      INTEGER ::   ioptio 
    792792 
    793       NAMELIST/nam_vvl/ ln_vvl_zstar, ln_vvl_ztilde, ln_vvl_layer, rn_ahe3, ln_vvl_dbg! , ln_vvl_kepe 
     793      NAMELIST/nam_vvl/ ln_vvl_zstar, ln_vvl_ztilde, ln_vvl_layer, ln_vvl_ztilde_as_zstar, & 
     794                      &      rn_ahe3,    rn_rst_e3t, rn_lf_cutoff, rn_zdef_max            , & 
     795                      &   ln_vvl_dbg               ! not yet implemented: ln_vvl_kepe 
    794796      !!----------------------------------------------------------------------  
    795797 
     
    805807         WRITE(numout,*) '              ztilde                     ln_vvl_ztilde  = ', ln_vvl_ztilde 
    806808         WRITE(numout,*) '              layer                      ln_vvl_layer   = ', ln_vvl_layer 
     809         WRITE(numout,*) '              ztilde as zstar   ln_vvl_ztilde_as_zstar  = ', ln_vvl_ztilde_as_zstar 
    807810         ! WRITE(numout,*) '           Namelist nam_vvl : chose kinetic-to-potential energy conservation' 
    808811         ! WRITE(numout,*) '                                         ln_vvl_kepe    = ', ln_vvl_kepe 
    809812         WRITE(numout,*) '           Namelist nam_vvl : thickness diffusion coefficient' 
    810813         WRITE(numout,*) '                                         rn_ahe3        = ', rn_ahe3 
     814         WRITE(numout,*) '           Namelist nam_vvl : maximum e3t deformation fractional change' 
     815         WRITE(numout,*) '                                         rn_zdef_max    = ', rn_zdef_max 
     816         IF( ln_vvl_ztilde_as_zstar ) THEN 
     817            WRITE(numout,*) '           ztilde running in zstar emulation mode; ' 
     818            WRITE(numout,*) '           ignoring namelist timescale parameters and using:' 
     819            WRITE(numout,*) '                 hard-wired : z-tilde to zstar restoration timescale (days)' 
     820            WRITE(numout,*) '                                         rn_rst_e3t     =    0.0' 
     821            WRITE(numout,*) '                 hard-wired : z-tilde cutoff frequency of low-pass filter (days)' 
     822            WRITE(numout,*) '                                         rn_lf_cutoff   =    1.0/rdt' 
     823         ELSE 
     824            WRITE(numout,*) '           Namelist nam_vvl : z-tilde to zstar restoration timescale (days)' 
     825            WRITE(numout,*) '                                         rn_rst_e3t     = ', rn_rst_e3t 
     826            WRITE(numout,*) '           Namelist nam_vvl : z-tilde cutoff frequency of low-pass filter (days)' 
     827            WRITE(numout,*) '                                         rn_lf_cutoff   = ', rn_lf_cutoff 
     828         ENDIF 
    811829         WRITE(numout,*) '           Namelist nam_vvl : debug prints' 
    812830         WRITE(numout,*) '                                         ln_vvl_dbg     = ', ln_vvl_dbg 
     
    814832 
    815833      ioptio = 0                      ! Parameter control 
    816       IF( ln_vvl_zstar     )   ioptio = ioptio + 1 
    817       IF( ln_vvl_ztilde    )   ioptio = ioptio + 1 
    818       IF( ln_vvl_layer     )   ioptio = ioptio + 1 
     834      IF( ln_vvl_ztilde_as_zstar ) ln_vvl_ztilde = .true. 
     835      IF( ln_vvl_zstar           )        ioptio = ioptio + 1 
     836      IF( ln_vvl_ztilde          )        ioptio = ioptio + 1 
     837      IF( ln_vvl_layer           )        ioptio = ioptio + 1 
    819838 
    820839      IF( ioptio /= 1 )   CALL ctl_stop( 'Choose ONE vertical coordinate in namelist nam_vvl' ) 
     
    822841      IF(lwp) THEN                   ! Print the choice 
    823842         WRITE(numout,*) 
    824          IF( ln_vvl_zstar      ) WRITE(numout,*) '              zstar vertical coordinate is used' 
    825          IF( ln_vvl_ztilde     ) WRITE(numout,*) '              ztilde vertical coordinate is used' 
    826          IF( ln_vvl_layer      ) WRITE(numout,*) '              layer vertical coordinate is used' 
     843         IF( ln_vvl_zstar           ) WRITE(numout,*) '              zstar vertical coordinate is used' 
     844         IF( ln_vvl_ztilde          ) WRITE(numout,*) '              ztilde vertical coordinate is used' 
     845         IF( ln_vvl_layer           ) WRITE(numout,*) '              layer vertical coordinate is used' 
     846         IF( ln_vvl_ztilde_as_zstar ) WRITE(numout,*) '              to emulate a zstar coordinate' 
    827847         ! - ML - Option not developed yet 
    828848         ! IF(       ln_vvl_kepe ) WRITE(numout,*) '              kinetic to potential energy transfer : option used' 
Note: See TracChangeset for help on using the changeset viewer.