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 2528 for trunk/NEMOGCM/NEMO/OPA_SRC/DOM/domain.F90 – NEMO

Ignore:
Timestamp:
2010-12-27T18:33:53+01:00 (13 years ago)
Author:
rblod
Message:

Update NEMOGCM from branch nemo_v3_3_beta

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMOGCM/NEMO/OPA_SRC/DOM/domain.F90

    • Property svn:eol-style deleted
    r1792 r2528  
    1111   !!   NEMO     1.0  !  2002-08  (G. Madec)  F90: Free form and module 
    1212   !!            2.0  !  2005-11  (V. Garnier) Surface pressure gradient organization 
     13   !!            3.3  !  2010-11  (G. Madec)  initialisation in C1D configuration 
    1314   !!---------------------------------------------------------------------- 
    1415    
     
    1819   !!   dom_ctl        : control print for the ocean domain 
    1920   !!---------------------------------------------------------------------- 
    20    USE oce             !  
    21    USE dom_oce         ! ocean space and time domain 
     21   USE oce             ! ocean variables 
     22   USE dom_oce         ! domain: ocean 
    2223   USE sbc_oce         ! surface boundary condition: ocean 
    2324   USE phycst          ! physical constants 
     
    3233   USE domwri          ! domain: write the meshmask file 
    3334   USE domvvl          ! variable volume 
     35   USE c1d             ! 1D vertical configuration 
     36   USE dyncor_c1d      ! Coriolis term (c1d case)         (cor_c1d routine) 
    3437 
    3538   IMPLICIT NONE 
     
    4144#  include "domzgr_substitute.h90" 
    4245   !!------------------------------------------------------------------------- 
    43    !! NEMO/OPA 3.2 , LOCEAN-IPSL (2009)  
     46   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
    4447   !! $Id$ 
    45    !! Software is governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
     48   !! Software governed by the CeCILL licence        (NEMOGCM/NEMO_CeCILL.txt) 
    4649   !!------------------------------------------------------------------------- 
    47  
    4850CONTAINS 
    4951 
     
    6264      !!              - dom_stp: defined the model time step 
    6365      !!              - dom_wri: create the meshmask file if nmsh=1 
     66      !!              - 1D configuration, move Coriolis, u and v at T-point 
    6467      !!---------------------------------------------------------------------- 
    6568      INTEGER ::   jk                ! dummy loop argument 
     
    7982                             CALL dom_msk      ! Masks 
    8083      IF( lk_vvl         )   CALL dom_vvl      ! Vertical variable mesh 
     84      ! 
     85      IF( lk_c1d ) THEN                        ! 1D configuration  
     86         CALL cor_c1d                          ! Coriolis set at T-point 
     87         umask(:,:,:) = tmask(:,:,:)           ! U, V moved at T-point 
     88         vmask(:,:,:) = tmask(:,:,:) 
     89      END IF 
    8190      ! 
    8291      hu(:,:) = 0.e0                           ! Ocean depth at U- and V-points 
     
    106115      !!              - namdom namelist 
    107116      !!              - namcla namelist 
     117      !!              - namnc4 namelist   ! "key_netcdf4" only 
    108118      !!---------------------------------------------------------------------- 
    109119      USE ioipsl 
     
    111121         &             nn_it000, nn_itend  , nn_date0    , nn_leapy     , nn_istate , nn_stock ,   & 
    112122         &             nn_write, ln_dimgnnn, ln_mskland  , ln_clobber   , nn_chunksz 
    113       NAMELIST/namdom/ nn_bathy , rn_e3zps_min, rn_e3zps_rat, nn_msh   ,   & 
    114          &             nn_acc   , rn_atfp     , rn_rdt      , rn_rdtmin,   & 
     123      NAMELIST/namdom/ nn_bathy , rn_e3zps_min, rn_e3zps_rat, nn_msh    , rn_hmin,   & 
     124         &             nn_acc   , rn_atfp     , rn_rdt      , rn_rdtmin ,            & 
    115125         &             rn_rdtmax, rn_rdth     , nn_baro     , nn_closea 
    116126      NAMELIST/namcla/ nn_cla 
     127#if defined key_netcdf4 
     128      NAMELIST/namnc4/ nn_nchunks_i, nn_nchunks_j, nn_nchunks_k, ln_nc4zip 
     129#endif 
    117130      !!---------------------------------------------------------------------- 
    118131 
     
    166179      ENDIF 
    167180 
     181#if defined key_agrif 
    168182      IF( Agrif_Root() ) THEN 
    169          SELECT CASE ( nleapy )        ! Choose calendar for IOIPSL 
    170          CASE (  1 )  
    171             CALL ioconf_calendar('gregorian') 
    172             IF(lwp) WRITE(numout,*) '   The IOIPSL calendar is "gregorian", i.e. leap year' 
    173          CASE (  0 ) 
    174             CALL ioconf_calendar('noleap') 
    175             IF(lwp) WRITE(numout,*) '   The IOIPSL calendar is "noleap", i.e. no leap year' 
    176          CASE ( 30 ) 
    177             CALL ioconf_calendar('360d') 
    178             IF(lwp) WRITE(numout,*) '   The IOIPSL calendar is "360d", i.e. 360 days in a year' 
    179          END SELECT 
    180       ENDIF 
    181  
    182       REWIND( numnam )             ! Namelist namdom : space & time domain (bathymetry, mesh, timestep) 
     183#endif 
     184      SELECT CASE ( nleapy )        ! Choose calendar for IOIPSL 
     185      CASE (  1 )  
     186         CALL ioconf_calendar('gregorian') 
     187         IF(lwp) WRITE(numout,*) '   The IOIPSL calendar is "gregorian", i.e. leap year' 
     188      CASE (  0 ) 
     189         CALL ioconf_calendar('noleap') 
     190         IF(lwp) WRITE(numout,*) '   The IOIPSL calendar is "noleap", i.e. no leap year' 
     191      CASE ( 30 ) 
     192         CALL ioconf_calendar('360d') 
     193         IF(lwp) WRITE(numout,*) '   The IOIPSL calendar is "360d", i.e. 360 days in a year' 
     194      END SELECT 
     195#if defined key_agrif 
     196      ENDIF 
     197#endif 
     198 
     199      REWIND( numnam )              ! Namelist namdom : space & time domain (bathymetry, mesh, timestep) 
    183200      READ  ( numnam, namdom ) 
    184201 
     
    187204         WRITE(numout,*) '   Namelist namdom : space & time domain' 
    188205         WRITE(numout,*) '      flag read/compute bathymetry      nn_bathy     = ', nn_bathy 
     206         WRITE(numout,*) '      min depth of the ocean    (>0) or    rn_hmin   = ', rn_hmin 
     207         WRITE(numout,*) '      min number of ocean level (<0)       ' 
    189208         WRITE(numout,*) '      minimum thickness of partial      rn_e3zps_min = ', rn_e3zps_min, ' (m)' 
    190209         WRITE(numout,*) '         step level                     rn_e3zps_rat = ', rn_e3zps_rat 
    191210         WRITE(numout,*) '      create mesh/mask file(s)          nn_msh       = ', nn_msh 
    192          WRITE(numout,*) '           = 0   no file created                 ' 
    193          WRITE(numout,*) '           = 1   mesh_mask                       ' 
    194          WRITE(numout,*) '           = 2   mesh and mask                   ' 
    195          WRITE(numout,*) '           = 3   mesh_hgr, msh_zgr and mask      ' 
     211         WRITE(numout,*) '           = 0   no file created           ' 
     212         WRITE(numout,*) '           = 1   mesh_mask                 ' 
     213         WRITE(numout,*) '           = 2   mesh and mask             ' 
     214         WRITE(numout,*) '           = 3   mesh_hgr, msh_zgr and mask' 
    196215         WRITE(numout,*) '      ocean time step                      rn_rdt    = ', rn_rdt 
    197216         WRITE(numout,*) '      asselin time filter parameter        rn_atfp   = ', rn_atfp 
     
    216235      nclosea   = nn_closea 
    217236 
    218       REWIND( numnam )             ! Namelist cross land advection 
     237      REWIND( numnam )              ! Namelist cross land advection 
    219238      READ  ( numnam, namcla ) 
    220239      IF(lwp) THEN 
     
    224243      ENDIF 
    225244 
    226       n_cla = nn_cla                ! conversion DOCTOR names into model names (this should disappear soon) 
    227  
    228       IF( nbit_cmp == 1 .AND. n_cla /= 0 )   CALL ctl_stop( ' Reproductibility tests (nbit_cmp=1) require n_cla = 0' ) 
     245#if defined key_netcdf4 
     246      !                             ! NetCDF 4 case   ("key_netcdf4" defined) 
     247      REWIND( numnam )                    ! Namelist namnc4 : netcdf4 chunking parameters 
     248      READ  ( numnam, namnc4 ) 
     249      IF(lwp) THEN                        ! control print 
     250         WRITE(numout,*) 
     251         WRITE(numout,*) '   Namelist namnc4 - Netcdf4 chunking parameters' 
     252         WRITE(numout,*) '      number of chunks in i-dimension      nn_nchunks_i   = ', nn_nchunks_i 
     253         WRITE(numout,*) '      number of chunks in j-dimension      nn_nchunks_j   = ', nn_nchunks_j 
     254         WRITE(numout,*) '      number of chunks in k-dimension      nn_nchunks_k   = ', nn_nchunks_k 
     255         WRITE(numout,*) '      apply netcdf4/hdf5 chunking & compression ln_nc4zip = ', ln_nc4zip 
     256      ENDIF 
     257 
     258      ! Put the netcdf4 settings into a simple structure (snc4set, defined in in_out_manager module) 
     259      ! Note the chunk size in the unlimited (time) dimension will be fixed at 1 
     260      snc4set%ni   = nn_nchunks_i 
     261      snc4set%nj   = nn_nchunks_j 
     262      snc4set%nk   = nn_nchunks_k 
     263      snc4set%luse = ln_nc4zip 
     264#else 
     265      snc4set%luse = .FALSE.        ! No NetCDF 4 case 
     266#endif 
    229267      ! 
    230268   END SUBROUTINE dom_nam 
Note: See TracChangeset for help on using the changeset viewer.