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 5987 for branches/2014/dev_r4650_UKMO7_STARTHOUR/NEMOGCM/NEMO/OPA_SRC/DOM/domain.F90 – NEMO

Ignore:
Timestamp:
2015-12-02T18:00:22+01:00 (8 years ago)
Author:
timgraham
Message:

Merged head of trunk (r5936) into branch

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2014/dev_r4650_UKMO7_STARTHOUR/NEMOGCM/NEMO/OPA_SRC/DOM/domain.F90

    r5985 r5987  
    1919   !!   dom_nam        : read and contral domain namelists 
    2020   !!   dom_ctl        : control print for the ocean domain 
     21   !!   dom_stiff      : diagnose maximum grid stiffness/hydrostatic consistency (s-coordinate) 
    2122   !!---------------------------------------------------------------------- 
    2223   USE oce             ! ocean variables 
     
    2526   USE phycst          ! physical constants 
    2627   USE closea          ! closed seas 
    27    USE in_out_manager  ! I/O manager 
    28    USE lib_mpp         ! distributed memory computing library 
    29  
    3028   USE domhgr          ! domain: set the horizontal mesh 
    3129   USE domzgr          ! domain: set the vertical mesh 
     
    3634   USE c1d             ! 1D vertical configuration 
    3735   USE dyncor_c1d      ! Coriolis term (c1d case)         (cor_c1d routine) 
     36   ! 
     37   USE in_out_manager  ! I/O manager 
     38   USE lib_mpp         ! distributed memory computing library 
     39   USE lbclnk          ! ocean lateral boundary condition (or mpp link) 
    3840   USE timing          ! Timing 
    39    USE lbclnk          ! ocean lateral boundary condition (or mpp link) 
    4041 
    4142   IMPLICIT NONE 
     
    8182      ENDIF 
    8283      ! 
    83                              CALL dom_nam      ! read namelist ( namrun, namdom, namcla ) 
     84                             CALL dom_nam      ! read namelist ( namrun, namdom ) 
    8485                             CALL dom_clo      ! Closed seas and lake 
    8586                             CALL dom_hgr      ! Horizontal mesh 
     
    8889      IF( ln_sco )           CALL dom_stiff    ! Maximum stiffness ratio/hydrostatic consistency 
    8990      ! 
    90       ht_0(:,:) = 0.0_wp                       ! Reference ocean depth at T-points 
    91       hu_0(:,:) = 0.0_wp                       ! Reference ocean depth at U-points 
    92       hv_0(:,:) = 0.0_wp                       ! Reference ocean depth at V-points 
     91      ht_0(:,:) = 0._wp                        ! Reference ocean depth at T-points 
     92      hu_0(:,:) = 0._wp                        ! Reference ocean depth at U-points 
     93      hv_0(:,:) = 0._wp                        ! Reference ocean depth at V-points 
    9394      DO jk = 1, jpk 
    9495         ht_0(:,:) = ht_0(:,:) + e3t_0(:,:,jk) * tmask(:,:,jk) 
     
    9798      END DO 
    9899      ! 
    99       IF( lk_vvl )           CALL dom_vvl_init ! Vertical variable mesh 
     100      IF( lk_vvl         )   CALL dom_vvl_init ! Vertical variable mesh 
    100101      ! 
    101102      IF( lk_c1d         )   CALL cor_c1d      ! 1D configuration: Coriolis set at T-point 
     
    131132      !! ** input   : - namrun namelist 
    132133      !!              - namdom namelist 
    133       !!              - namcla namelist 
    134134      !!              - namnc4 namelist   ! "key_netcdf4" only 
    135135      !!---------------------------------------------------------------------- 
     
    147147         &             ppsur, ppa0, ppa1, ppkth, ppacr, ppdzmin, pphmax, ldbletanh, & 
    148148         &             ppa2, ppkth2, ppacr2 
    149       NAMELIST/namcla/ nn_cla 
    150149#if defined key_netcdf4 
    151150      NAMELIST/namnc4/ nn_nchunks_i, nn_nchunks_j, nn_nchunks_k, ln_nc4zip 
     
    156155      REWIND( numnam_ref )              ! Namelist namrun in reference namelist : Parameters of the run 
    157156      READ  ( numnam_ref, namrun, IOSTAT = ios, ERR = 901) 
    158 901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namrun in reference namelist', lwp ) 
     157901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namrun in reference namelist', lwp ) 
    159158 
    160159      REWIND( numnam_cfg )              ! Namelist namrun in configuration namelist : Parameters of the run 
    161160      READ  ( numnam_cfg, namrun, IOSTAT = ios, ERR = 902 ) 
    162 902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namrun in configuration namelist', lwp ) 
     161902   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namrun in configuration namelist', lwp ) 
    163162      IF(lwm) WRITE ( numond, namrun ) 
    164163      ! 
     
    253252904   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namdom in configuration namelist', lwp ) 
    254253      IF(lwm) WRITE ( numond, namdom ) 
    255  
     254      ! 
    256255      IF(lwp) THEN 
    257256         WRITE(numout,*) 
     
    295294         WRITE(numout,*) '                                      ppacr2            = ', ppacr2 
    296295      ENDIF 
    297  
     296      ! 
    298297      ntopo     = nn_bathy          ! conversion DOCTOR names into model names (this should disappear soon) 
    299298      e3zps_min = rn_e3zps_min 
     
    306305      rdtmax    = rn_rdtmin 
    307306      rdth      = rn_rdth 
    308  
    309       REWIND( numnam_ref )              ! Namelist namcla in reference namelist : Cross land advection 
    310       READ  ( numnam_ref, namcla, IOSTAT = ios, ERR = 905) 
    311 905   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namcla in reference namelist', lwp ) 
    312  
    313       REWIND( numnam_cfg )              ! Namelist namcla in configuration namelist : Cross land advection 
    314       READ  ( numnam_cfg, namcla, IOSTAT = ios, ERR = 906 ) 
    315 906   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namcla in configuration namelist', lwp ) 
    316       IF(lwm) WRITE( numond, namcla ) 
    317  
    318       IF(lwp) THEN 
    319          WRITE(numout,*) 
    320          WRITE(numout,*) '   Namelist namcla' 
    321          WRITE(numout,*) '      cross land advection                 nn_cla    = ', nn_cla 
    322       ENDIF 
    323       IF ( nn_cla .EQ. 1 ) THEN 
    324          IF  ( cp_cfg == "orca" .AND. jp_cfg == 2 ) THEN   ! ORCA R2  
    325             CONTINUE 
    326          ELSE 
    327             CALL ctl_stop( 'STOP', 'Cross land advation iplemented only for ORCA2 configuration: cp_cfg = "orca" and jp_cfg = 2 ' ) 
    328          ENDIF 
    329       ENDIF 
    330307 
    331308#if defined key_netcdf4 
     
    411388   END SUBROUTINE dom_ctl 
    412389 
     390 
    413391   SUBROUTINE dom_stiff 
    414392      !!---------------------------------------------------------------------- 
     
    429407      REAL(wp), DIMENSION(4) :: zr1 
    430408      !!---------------------------------------------------------------------- 
    431       rx1(:,:) = 0.e0 
    432       zrxmax   = 0.e0 
    433       zr1(:)   = 0.e0 
    434        
     409      rx1(:,:) = 0._wp 
     410      zrxmax   = 0._wp 
     411      zr1(:)   = 0._wp 
     412      ! 
    435413      DO ji = 2, jpim1 
    436414         DO jj = 2, jpjm1 
     
    457435         END DO 
    458436      END DO 
    459  
    460437      CALL lbc_lnk( rx1, 'T', 1. ) 
    461  
    462       zrxmax = MAXVAL(rx1) 
    463  
     438      ! 
     439      zrxmax = MAXVAL( rx1 ) 
     440      ! 
    464441      IF( lk_mpp )   CALL mpp_max( zrxmax ) ! max over the global domain 
    465  
     442      ! 
    466443      IF(lwp) THEN 
    467444         WRITE(numout,*) 
     
    469446         WRITE(numout,*) '~~~~~~~~~' 
    470447      ENDIF 
    471  
     448      ! 
    472449   END SUBROUTINE dom_stiff 
    473  
    474  
    475450 
    476451   !!====================================================================== 
Note: See TracChangeset for help on using the changeset viewer.