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/IOM – NEMO

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

Update NEMOGCM from branch nemo_v3_3_beta

Location:
trunk/NEMOGCM/NEMO/OPA_SRC/IOM
Files:
8 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMOGCM/NEMO/OPA_SRC/IOM/in_out_manager.F90

    • Property svn:eol-style deleted
    r1770 r2528  
    99   !!             3.0  !  2008-06  (G. Madec)   add ctmp4 to ctmp10 
    1010   !!             3.2  !  2009-08  (S. MAsson)  add new ctl_opn 
     11   !!             3.3  !  2010-10  (A. Coward)  add NetCDF4 usage 
    1112   !!---------------------------------------------------------------------- 
    1213 
     
    1617   !!   getunit    : give the index of an unused logical unit 
    1718   !!---------------------------------------------------------------------- 
    18    USE par_kind        ! kind definition 
    19    USE par_oce         ! ocean parameter 
    20    USE lib_print       ! formated print library 
     19   USE par_oce       ! ocean parameter 
     20   USE lib_print     ! formated print library 
     21   USE nc4interface  ! NetCDF4 interface 
    2122 
    2223   IMPLICIT NONE 
     
    2627   !!                   namrun namelist parameters 
    2728   !!---------------------------------------------------------------------- 
    28    CHARACTER(len=16) ::   cn_exp        = "exp0"      !: experiment name used for output filename 
    29    CHARACTER(len=32) ::   cn_ocerst_in  = "restart"   !: suffix of ocean restart name (input) 
    30    CHARACTER(len=32) ::   cn_ocerst_out = "restart"   !: suffix of ocean restart name (output) 
    31    LOGICAL            ::   ln_rstart     = .FALSE.     !: start from (F) rest or (T) a restart file 
    32    INTEGER            ::   nn_no         = 0           !: job number 
    33    INTEGER            ::   nn_rstctl     = 0           !: control of the time step (0, 1 or 2) 
    34    INTEGER            ::   nn_rstssh     = 0           !: hand made initilization of ssh or not (1/0) 
    35    INTEGER            ::   nn_it000      = 1           !: index of the first time step 
    36    INTEGER            ::   nn_itend      = 10          !: index of the last time step 
    37    INTEGER            ::   nn_date0      = 961115      !: initial calendar date aammjj 
    38    INTEGER            ::   nn_leapy      = 0           !: Leap year calendar flag (0/1 or 30) 
    39    INTEGER            ::   nn_istate     = 0           !: initial state output flag (0/1) 
    40    INTEGER            ::   nn_write      =   10        !: model standard output frequency 
    41    INTEGER            ::   nn_stock      =   10        !: restart file frequency 
    42    LOGICAL            ::   ln_dimgnnn    = .FALSE.     !: type of dimgout. (F): 1 file for all proc 
     29   CHARACTER(lc) ::   cn_exp        = "exp0"      !: experiment name used for output filename 
     30   CHARACTER(lc) ::   cn_ocerst_in  = "restart"   !: suffix of ocean restart name (input) 
     31   CHARACTER(lc) ::   cn_ocerst_out = "restart"   !: suffix of ocean restart name (output) 
     32   LOGICAL       ::   ln_rstart     = .FALSE.     !: start from (F) rest or (T) a restart file 
     33   INTEGER       ::   nn_no         = 0           !: job number 
     34   INTEGER       ::   nn_rstctl     = 0           !: control of the time step (0, 1 or 2) 
     35   INTEGER       ::   nn_rstssh     = 0           !: hand made initilization of ssh or not (1/0) 
     36   INTEGER       ::   nn_it000      = 1           !: index of the first time step 
     37   INTEGER       ::   nn_itend      = 10          !: index of the last time step 
     38   INTEGER       ::   nn_date0      = 961115      !: initial calendar date aammjj 
     39   INTEGER       ::   nn_leapy      = 0           !: Leap year calendar flag (0/1 or 30) 
     40   INTEGER       ::   nn_istate     = 0           !: initial state output flag (0/1) 
     41   INTEGER       ::   nn_write      =   10        !: model standard output frequency 
     42   INTEGER       ::   nn_stock      =   10        !: restart file frequency 
     43   LOGICAL       ::   ln_dimgnnn    = .FALSE.     !: type of dimgout. (F): 1 file for all proc 
    4344                                                       !:                  (T): 1 file per proc 
    44    LOGICAL            ::   ln_mskland    = .FALSE.     !: mask land points in NetCDF outputs (costly: + ~15%) 
    45    LOGICAL            ::   ln_clobber    = .FALSE.     !: clobber (overwrite) an existing file 
    46    INTEGER            ::   nn_chunksz    = 0           !: chunksize (bytes) for NetCDF file (working only with iom_nf90 routines) 
     45   LOGICAL       ::   ln_mskland    = .FALSE.     !: mask land points in NetCDF outputs (costly: + ~15%) 
     46   LOGICAL       ::   ln_clobber    = .FALSE.     !: clobber (overwrite) an existing file 
     47   INTEGER       ::   nn_chunksz    = 0           !: chunksize (bytes) for NetCDF file (works only with iom_nf90 routines) 
     48#if defined key_netcdf4 
     49   !!---------------------------------------------------------------------- 
     50   !!                   namnc4 namelist parameters                         (key_netcdf4) 
     51   !!---------------------------------------------------------------------- 
     52   ! The following four values determine the partitioning of the output fields 
     53   ! into netcdf4 chunks. They are unrelated to the nn_chunk_sz setting which is 
     54   ! for runtime optimisation. The individual netcdf4 chunks can be optionally  
     55   ! gzipped (recommended) leading to significant reductions in I/O volumes  
     56   !                                   !!!**  variables only used with iom_nf90 routines and key_netcdf4 ** 
     57   INTEGER ::   nn_nchunks_i = 1        !: number of chunks required in the i-dimension  
     58   INTEGER ::   nn_nchunks_j = 1        !: number of chunks required in the j-dimension  
     59   INTEGER ::   nn_nchunks_k = 1        !: number of chunks required in the k-dimension  
     60   INTEGER ::   nn_nchunks_t = 1        !: number of chunks required in the t-dimension  
     61   LOGICAL ::   ln_nc4zip    = .TRUE.   !: netcdf4 usage: (T) chunk and compress output using the HDF5 sublayers of netcdf4 
     62   !                                    !                 (F) ignore chunking request and use the netcdf4 library  
     63   !                                    !                     to produce netcdf3-compatible files  
     64#endif 
     65!$AGRIF_DO_NOT_TREAT 
     66   TYPE(snc4_ctl)     :: snc4set        !: netcdf4 chunking control structure (always needed for decision making) 
     67!$AGRIF_END_DO_NOT_TREAT 
     68 
    4769 
    4870   !! conversion of DOCTOR norm namelist name into model name 
    4971   !! (this should disappear in a near futur) 
    5072 
    51    CHARACTER(len=16) ::   cexper                      !: experiment name used for output filename 
    52    INTEGER            ::   no                          !: job number 
    53    INTEGER            ::   nrstdt                      !: control of the time step (0, 1 or 2) 
    54    INTEGER            ::   nit000                      !: index of the first time step 
    55    INTEGER            ::   nitend                      !: index of the last time step 
    56    INTEGER            ::   ndate0                      !: initial calendar date aammjj 
    57    INTEGER            ::   nleapy                      !: Leap year calendar flag (0/1 or 30) 
    58    INTEGER            ::   ninist                      !: initial state output flag (0/1) 
    59    INTEGER            ::   nwrite                      !: model standard output frequency 
    60    INTEGER            ::   nstock                      !: restart file frequency 
     73   CHARACTER(lc) ::   cexper                      !: experiment name used for output filename 
     74   INTEGER       ::   no                          !: job number 
     75   INTEGER       ::   nrstdt                      !: control of the time step (0, 1 or 2) 
     76   INTEGER       ::   nit000                      !: index of the first time step 
     77   INTEGER       ::   nitend                      !: index of the last time step 
     78   INTEGER       ::   ndate0                      !: initial calendar date aammjj 
     79   INTEGER       ::   nleapy                      !: Leap year calendar flag (0/1 or 30) 
     80   INTEGER       ::   ninist                      !: initial state output flag (0/1) 
     81   INTEGER       ::   nwrite                      !: model standard output frequency 
     82   INTEGER       ::   nstock                      !: restart file frequency 
    6183 
    6284   !!---------------------------------------------------------------------- 
    6385   !! was in restart but moved here because of the OFF line... better solution should be found... 
    6486   !!---------------------------------------------------------------------- 
    65    INTEGER            ::   nitrst                 !: time step at which restart file should be written 
     87   INTEGER ::   nitrst   !: time step at which restart file should be written 
    6688 
    6789   !!---------------------------------------------------------------------- 
    6890   !!                    output monitoring 
    6991   !!---------------------------------------------------------------------- 
    70    LOGICAL            ::   ln_ctl     = .FALSE.   !: run control for debugging 
    71    INTEGER            ::   nn_print     =    0    !: level of print (0 no print) 
    72    INTEGER            ::   nn_ictls     =    0    !: Start i indice for the SUM control 
    73    INTEGER            ::   nn_ictle     =    0    !: End   i indice for the SUM control 
    74    INTEGER            ::   nn_jctls     =    0    !: Start j indice for the SUM control 
    75    INTEGER            ::   nn_jctle     =    0    !: End   j indice for the SUM control 
    76    INTEGER            ::   nn_isplt     =    1    !: number of processors following i 
    77    INTEGER            ::   nn_jsplt     =    1    !: number of processors following j 
    78    INTEGER            ::   nn_bench     =    0    !: benchmark parameter (0/1) 
    79    INTEGER            ::   nn_bit_cmp   =    0    !: bit reproducibility  (0/1) 
    80  
    81    !                                              !: OLD namelist names 
    82    INTEGER ::   nprint, nictls, nictle, njctls, njctle, isplt, jsplt, nbench, nbit_cmp    
    83  
    84    INTEGER            ::   ijsplt     =    1      !: nb of local domain = nb of processors 
     92   LOGICAL ::   ln_ctl     = .FALSE.   !: run control for debugging 
     93   INTEGER ::   nn_print     =    0    !: level of print (0 no print) 
     94   INTEGER ::   nn_ictls     =    0    !: Start i indice for the SUM control 
     95   INTEGER ::   nn_ictle     =    0    !: End   i indice for the SUM control 
     96   INTEGER ::   nn_jctls     =    0    !: Start j indice for the SUM control 
     97   INTEGER ::   nn_jctle     =    0    !: End   j indice for the SUM control 
     98   INTEGER ::   nn_isplt     =    1    !: number of processors following i 
     99   INTEGER ::   nn_jsplt     =    1    !: number of processors following j 
     100   INTEGER ::   nn_bench     =    0    !: benchmark parameter (0/1) 
     101   INTEGER ::   nn_bit_cmp   =    0    !: bit reproducibility  (0/1) 
     102 
     103   !                                           
     104   INTEGER ::   nprint, nictls, nictle, njctls, njctle, isplt, jsplt, nbench    !: OLD namelist names 
     105 
     106   INTEGER ::   ijsplt     =    1      !: nb of local domain = nb of processors 
    85107 
    86108   !!---------------------------------------------------------------------- 
    87109   !!                        logical units 
    88110   !!---------------------------------------------------------------------- 
    89    INTEGER            ::   numstp     =   -1      !: logical unit for time step 
    90    INTEGER            ::   numout     =    6      !: logical unit for output print 
    91    INTEGER            ::   numnam     =   -1      !: logical unit for namelist 
    92    INTEGER            ::   numnam_ice =   -1      !: logical unit for ice namelist 
    93    INTEGER            ::   numevo_ice =   -1      !: logical unit for ice variables (temp. evolution) 
    94    INTEGER            ::   numsol     =   -1      !: logical unit for solver statistics 
     111   INTEGER ::   numstp     =   -1      !: logical unit for time step 
     112   INTEGER ::   numout     =    6      !: logical unit for output print 
     113   INTEGER ::   numnam     =   -1      !: logical unit for namelist 
     114   INTEGER ::   numnam_ice =   -1      !: logical unit for ice namelist 
     115   INTEGER ::   numevo_ice =   -1      !: logical unit for ice variables (temp. evolution) 
     116   INTEGER ::   numsol     =   -1      !: logical unit for solver statistics 
    95117 
    96118   !!---------------------------------------------------------------------- 
    97119   !!                          Run control   
    98120   !!---------------------------------------------------------------------- 
    99    INTEGER            ::   nstop = 0                !: error flag (=number of reason for a premature stop run) 
    100    INTEGER            ::   nwarn = 0                !: warning flag (=number of warning found during the run) 
    101    CHARACTER(len=200) ::   ctmp1, ctmp2, ctmp3      !: temporary characters 1 to 3 
    102    CHARACTER(len=200) ::   ctmp4, ctmp5, ctmp6      !: temporary characters 4 to 6 
    103    CHARACTER(len=200) ::   ctmp7, ctmp8, ctmp9      !: temporary characters 7 to 9 
    104    CHARACTER(len=200) ::   ctmp10                   !: temporary character 10 
    105    CHARACTER (len=64) ::   cform_err = "(/,' ===>>> : E R R O R',     /,'         ===========',/)"       !: 
    106    CHARACTER (len=64) ::   cform_war = "(/,' ===>>> : W A R N I N G', /,'         ===============',/)"   !: 
    107    LOGICAL            ::   lwp      = .FALSE.       !: boolean : true on the 1st processor only 
    108    LOGICAL            ::   lsp_area = .TRUE.        !: to make a control print over a specific area 
    109    !!---------------------------------------------------------------------- 
    110    !! NEMO/OPA 3.0 , LOCEAN-IPSL (2008)  
     121   INTEGER       ::   nstop = 0             !: error flag (=number of reason for a premature stop run) 
     122   INTEGER       ::   nwarn = 0             !: warning flag (=number of warning found during the run) 
     123   CHARACTER(lc) ::   ctmp1, ctmp2, ctmp3   !: temporary characters 1 to 3 
     124   CHARACTER(lc) ::   ctmp4, ctmp5, ctmp6   !: temporary characters 4 to 6 
     125   CHARACTER(lc) ::   ctmp7, ctmp8, ctmp9   !: temporary characters 7 to 9 
     126   CHARACTER(lc) ::   ctmp10                !: temporary character 10 
     127   CHARACTER(lc) ::   cform_err = "(/,' ===>>> : E R R O R',     /,'         ===========',/)"       !: 
     128   CHARACTER(lc) ::   cform_war = "(/,' ===>>> : W A R N I N G', /,'         ===============',/)"   !: 
     129   LOGICAL       ::   lwp      = .FALSE.    !: boolean : true on the 1st processor only 
     130   LOGICAL       ::   lsp_area = .TRUE.     !: to make a control print over a specific area 
     131 
     132   !!---------------------------------------------------------------------- 
     133   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
    111134   !! $Id$ 
    112    !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
    113    !!---------------------------------------------------------------------- 
    114  
     135   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
     136   !!---------------------------------------------------------------------- 
    115137CONTAINS 
    116138 
     
    129151      nstop = nstop + 1  
    130152      IF(lwp) THEN 
    131          WRITE(numout,"(/,' ===>>> : E R R O R',     /,'         ===========',/)")  
     153         WRITE(numout,cform_err) 
    132154         IF( PRESENT(cd1 ) ) WRITE(numout,*) cd1 
    133155         IF( PRESENT(cd2 ) ) WRITE(numout,*) cd2 
     
    163185      nwarn = nwarn + 1  
    164186      IF(lwp) THEN 
    165          WRITE(numout,"(/,' ===>>> : W A R N I N G', /,'         ===============',/)")  
     187         WRITE(numout,cform_war) 
    166188         IF( PRESENT(cd1 ) ) WRITE(numout,*) cd1 
    167189         IF( PRESENT(cd2 ) ) WRITE(numout,*) cd2 
     
    180202 
    181203 
    182    SUBROUTINE ctl_opn ( knum, cdfile, cdstat, cdform, cdacce, klengh, kout, ldwp, karea ) 
     204   SUBROUTINE ctl_opn( knum, cdfile, cdstat, cdform, cdacce, klengh, kout, ldwp, karea ) 
    183205      !!---------------------------------------------------------------------- 
    184206      !!                  ***  ROUTINE ctl_opn  *** 
     
    187209      !! 
    188210      !! ** Method  :   Fortan open 
    189       !! 
    190       !! History : 
    191       !!        !  1995-12  (G. Madec)  Original code 
    192       !!   8.5  !  2002-06  (G. Madec)  F90: Free form and module 
    193       !!---------------------------------------------------------------------- 
    194  
     211      !!---------------------------------------------------------------------- 
    195212      INTEGER          , INTENT(  out) ::   knum      ! logical unit to open 
    196213      CHARACTER(len=*) , INTENT(in   ) ::   cdfile    ! file name to open 
     
    205222      CHARACTER(len=80) ::   clfile 
    206223      INTEGER           ::   iost 
     224      !!---------------------------------------------------------------------- 
    207225 
    208226      ! adapt filename 
  • trunk/NEMOGCM/NEMO/OPA_SRC/IOM/iom.F90

    • Property svn:eol-style deleted
    r2499 r2528  
    4444#endif 
    4545   PUBLIC iom_init, iom_swap, iom_open, iom_close, iom_setkt, iom_varid, iom_get, iom_gettime, iom_rstput, iom_put 
     46   PUBLIC iom_getatt 
    4647 
    4748   PRIVATE iom_rp0d, iom_rp1d, iom_rp2d, iom_rp3d 
     
    5455   INTERFACE iom_get 
    5556      MODULE PROCEDURE iom_g0d, iom_g1d, iom_g2d, iom_g3d 
     57   END INTERFACE 
     58   INTERFACE iom_getatt 
     59      MODULE PROCEDURE iom_g0d_intatt 
    5660   END INTERFACE 
    5761   INTERFACE iom_rstput 
     
    6872 
    6973   !!---------------------------------------------------------------------- 
    70    !!  OPA 9.0 , LOCEAN-IPSL (2006) 
     74   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
    7175   !! $Id$ 
    72    !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
     76   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
    7377   !!---------------------------------------------------------------------- 
    7478 
     
    824828      ! 
    825829   END SUBROUTINE iom_gettime 
     830 
     831 
     832   !!---------------------------------------------------------------------- 
     833   !!                   INTERFACE iom_getatt 
     834   !!---------------------------------------------------------------------- 
     835   SUBROUTINE iom_g0d_intatt( kiomid, cdatt, pvar ) 
     836      INTEGER         , INTENT(in   )                 ::   kiomid    ! Identifier of the file 
     837      CHARACTER(len=*), INTENT(in   )                 ::   cdatt     ! Name of the attribute 
     838      INTEGER         , INTENT(  out)                 ::   pvar      ! read field 
     839      ! 
     840      IF( kiomid > 0 ) THEN 
     841         IF( iom_file(kiomid)%nfid > 0 ) THEN 
     842            SELECT CASE (iom_file(kiomid)%iolib) 
     843            CASE (jpioipsl )   ;   CALL ctl_stop('iom_getatt: only nf90 available') 
     844            CASE (jpnf90   )   ;   CALL iom_nf90_getatt( kiomid, cdatt, pvar ) 
     845            CASE (jprstdimg)   ;   CALL ctl_stop('iom_getatt: only nf90 available') 
     846            CASE DEFAULT     
     847               CALL ctl_stop( 'iom_g0d_att: accepted IO library are only jpioipsl, jpnf90 and jprstdimg' ) 
     848            END SELECT 
     849         ENDIF 
     850      ENDIF 
     851   END SUBROUTINE iom_g0d_intatt 
    826852 
    827853 
  • trunk/NEMOGCM/NEMO/OPA_SRC/IOM/iom_def.F90

    • Property svn:eol-style deleted
    r1359 r2528  
    88   !!-------------------------------------------------------------------- 
    99   !!--------------------------------------------------------------------------------- 
    10    !! OPA 9.0 , LOCEAN-IPSL (2006)  
     10   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
    1111   !! $Id$  
    12    !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
     12   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
    1313   !!--------------------------------------------------------------------------------- 
    1414 
  • trunk/NEMOGCM/NEMO/OPA_SRC/IOM/iom_ioipsl.F90

    • Property svn:eol-style deleted
    r2174 r2528  
    3535   END INTERFACE 
    3636   !!---------------------------------------------------------------------- 
    37    !!  OPA 9.0 , LOCEAN-IPSL (2006) 
     37   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
    3838   !! $Id$ 
    39    !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
     39   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
    4040   !!---------------------------------------------------------------------- 
    4141 
  • trunk/NEMOGCM/NEMO/OPA_SRC/IOM/iom_nf90.F90

    • Property svn:eol-style deleted
    r2172 r2528  
    2828 
    2929   PUBLIC iom_nf90_open, iom_nf90_close, iom_nf90_varid, iom_nf90_get, iom_nf90_gettime, iom_nf90_rstput 
     30   PUBLIC iom_nf90_getatt 
    3031 
    3132   INTERFACE iom_nf90_get 
    3233      MODULE PROCEDURE iom_nf90_g0d, iom_nf90_g123d 
     34   END INTERFACE 
     35   INTERFACE iom_nf90_getatt 
     36      MODULE PROCEDURE iom_nf90_intatt 
    3337   END INTERFACE 
    3438   INTERFACE iom_nf90_rstput 
    3539      MODULE PROCEDURE iom_nf90_rp0123d 
    3640   END INTERFACE 
     41 
    3742   !!---------------------------------------------------------------------- 
    38    !!  OPA 9.0 , LOCEAN-IPSL (2006) 
     43   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
    3944   !! $Id$ 
    40    !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
     45   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
    4146   !!---------------------------------------------------------------------- 
    4247 
     
    6368      INTEGER            ::   jl               ! loop variable 
    6469      INTEGER            ::   ichunk           ! temporary storage of nn_chunksz 
    65       INTEGER            ::   imode            ! creation mode flag: NF90_CLOBBER or NF90_NOCLOBBER 
     70      INTEGER            ::   imode            ! creation mode flag: NF90_CLOBBER or NF90_NOCLOBBER or NF90_HDF5 
     71      INTEGER            ::   ihdf5            ! local variable for retrieval of value for NF90_HDF5 
    6672      LOGICAL            ::   llclobber        ! local definition of ln_clobber 
    6773      !--------------------------------------------------------------------- 
     
    7884         IF( ldwrt ) THEN  ! ... in write mode 
    7985            IF(lwp) WRITE(numout,*) TRIM(clinfo)//' open existing file: '//TRIM(cdname)//' in WRITE mode' 
    80             CALL iom_nf90_check(NF90_OPEN( TRIM(cdname), NF90_WRITE  , if90id, chunksize = ichunk ), clinfo) 
     86            IF( snc4set%luse ) THEN 
     87               CALL iom_nf90_check(NF90_OPEN( TRIM(cdname), NF90_WRITE  , if90id ), clinfo) 
     88            ELSE 
     89               CALL iom_nf90_check(NF90_OPEN( TRIM(cdname), NF90_WRITE  , if90id, chunksize = ichunk ), clinfo) 
     90            ENDIF 
    8191            CALL iom_nf90_check(NF90_SET_FILL( if90id, NF90_NOFILL, idmy                          ), clinfo) 
    8292         ELSE              ! ... in read mode 
     
    97107            ELSE                   ;   imode = IOR( NF90_64BIT_OFFSET, NF90_NOCLOBBER )  
    98108            ENDIF 
    99             CALL iom_nf90_check(NF90_CREATE( TRIM(cdname), imode, if90id, chunksize = ichunk ), clinfo) 
     109            IF( snc4set%luse ) THEN 
     110               IF(lwp) WRITE(numout,*) TRIM(clinfo)//' creating file: '//TRIM(cdname)//' in hdf5 (netcdf4) mode' 
     111               CALL GET_NF90_SYMBOL("NF90_HDF5", ihdf5) 
     112               IF( llclobber ) THEN   ;   imode = IOR(ihdf5, NF90_CLOBBER) 
     113               ELSE                   ;   imode = IOR(ihdf5, NF90_NOCLOBBER) 
     114               ENDIF 
     115               CALL iom_nf90_check(NF90_CREATE( TRIM(cdname), imode, if90id ), clinfo) 
     116            ELSE 
     117               CALL iom_nf90_check(NF90_CREATE( TRIM(cdname), imode, if90id, chunksize = ichunk ), clinfo) 
     118            ENDIF 
    100119            CALL iom_nf90_check(NF90_SET_FILL( if90id, NF90_NOFILL, idmy                     ), clinfo) 
    101120            ! define dimensions 
     
    288307 
    289308 
     309   SUBROUTINE iom_nf90_intatt( kiomid, cdatt, pvar ) 
     310      !!----------------------------------------------------------------------- 
     311      !!                  ***  ROUTINE  iom_nf90_intatt  *** 
     312      !! 
     313      !! ** Purpose : read an integer attribute with NF90 
     314      !!----------------------------------------------------------------------- 
     315      INTEGER         , INTENT(in   ) ::   kiomid   ! Identifier of the file 
     316      CHARACTER(len=*), INTENT(in   ) ::   cdatt    ! attribute name 
     317      INTEGER         , INTENT(  out) ::   pvar     ! read field 
     318      ! 
     319      INTEGER                         ::   if90id   ! temporary integer 
     320      LOGICAL                         ::   llok     ! temporary logical 
     321      CHARACTER(LEN=100)              ::   clinfo   ! info character 
     322      !--------------------------------------------------------------------- 
     323      !  
     324      if90id = iom_file(kiomid)%nfid 
     325      llok = NF90_Inquire_attribute(if90id, NF90_GLOBAL, cdatt) == nf90_noerr 
     326      IF( llok) THEN 
     327         clinfo = 'iom_nf90_getatt, file: '//TRIM(iom_file(kiomid)%name)//', att: '//TRIM(cdatt) 
     328         CALL iom_nf90_check(NF90_GET_ATT(if90id, NF90_GLOBAL, cdatt, values=pvar), clinfo) 
     329      ELSE 
     330         CALL ctl_warn('iom_nf90_getatt: no attribute '//cdatt//' found') 
     331         pvar = -999 
     332      ENDIF 
     333      !  
     334   END SUBROUTINE iom_nf90_intatt 
     335 
     336 
    290337   SUBROUTINE iom_nf90_gettime( kiomid, kvid, ptime, cdunits, cdcalendar ) 
    291338      !!-------------------------------------------------------------------- 
     
    346393      INTEGER               :: idmy                 ! dummy variable 
    347394      INTEGER               :: itype                ! variable type 
     395      INTEGER, DIMENSION(4) :: ichunksz             ! NetCDF4 chunk sizes. Will be computed using 
     396                                                    ! nn_nchunks_[i,j,k,t] namelist parameters 
     397      INTEGER               :: ichunkalg, ishuffle,& 
     398                               ideflate, ideflate_level 
     399                                                    ! NetCDF4 internally fixed parameters 
     400      LOGICAL               :: lchunk               ! logical switch to activate chunking and compression 
     401                                                    ! when appropriate (currently chunking is applied to 4d fields only) 
    348402      !--------------------------------------------------------------------- 
    349403      ! 
     
    376430      ! =============== 
    377431      IF( kvid <= 0 ) THEN 
     432         ! 
     433         ! NetCDF4 chunking and compression fixed settings 
     434         ichunkalg = 0 
     435         ishuffle = 1 
     436         ideflate = 1 
     437         ideflate_level = 1 
     438         ! 
    378439         idvar = iom_file(kiomid)%nvars + 1 
    379440         ! are we in define mode? 
     
    406467                 &                            iom_file(kiomid)%nvid(idvar) ), clinfo) 
    407468         ENDIF 
     469         lchunk = .false. 
     470         IF( snc4set%luse .AND. idims.eq.4 ) lchunk = .true. 
    408471         ! update informations structure related the new variable we want to add... 
    409472         iom_file(kiomid)%nvars         = idvar 
     
    417480         DO jd = 1, idims 
    418481            CALL iom_nf90_check(NF90_INQUIRE_DIMENSION( if90id, idimid(jd), len = iom_file(kiomid)%dimsz(jd,idvar) ), clinfo) 
     482            IF ( lchunk ) ichunksz(jd) = iom_file(kiomid)%dimsz(jd,idvar) 
    419483         END DO 
     484         IF ( lchunk ) THEN 
     485            ! Calculate chunk sizes by partitioning each dimension as requested in namnc4 namelist 
     486            ! Disallow very small chunk sizes and prevent chunk sizes larger than each individual dimension 
     487            ichunksz(1) = MIN( ichunksz(1),MAX( (ichunksz(1)-1)/snc4set%ni + 1 ,16 ) ) ! Suggested default nc4set%ni=4 
     488            ichunksz(2) = MIN( ichunksz(2),MAX( (ichunksz(2)-1)/snc4set%nj + 1 ,16 ) ) ! Suggested default nc4set%nj=2 
     489            ichunksz(3) = MIN( ichunksz(3),MAX( (ichunksz(3)-1)/snc4set%nk + 1 , 1 ) ) ! Suggested default nc4set%nk=6 
     490            ichunksz(4) = 1                                                            ! Do not allow chunks to span the 
     491                                                                                       ! unlimited dimension 
     492            CALL iom_nf90_check(SET_NF90_DEF_VAR_CHUNKING(if90id, idvar, ichunkalg, ichunksz), clinfo) 
     493            CALL iom_nf90_check(SET_NF90_DEF_VAR_DEFLATE(if90id, idvar, ishuffle, ideflate, ideflate_level), clinfo) 
     494            IF(lwp) WRITE(numout,*) TRIM(clinfo)//' chunked ok. Chunks sizes: ', ichunksz 
     495         ENDIF 
    420496         IF(lwp) WRITE(numout,*) TRIM(clinfo)//' defined ok' 
    421497      ELSE 
     
    497573   END SUBROUTINE iom_nf90_check 
    498574 
    499  
    500575   !!====================================================================== 
    501576END MODULE iom_nf90 
  • trunk/NEMOGCM/NEMO/OPA_SRC/IOM/iom_rstdimg.F90

    • Property svn:eol-style deleted
    r1488 r2528  
    3535       
    3636   !!---------------------------------------------------------------------- 
    37    !!  OPA 9.0 , LOCEAN-IPSL (2006) 
     37   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
    3838   !! $Id$ 
    39    !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
     39   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
    4040   !!---------------------------------------------------------------------- 
    4141 
  • trunk/NEMOGCM/NEMO/OPA_SRC/IOM/prtctl.F90

    • Property svn:eol-style deleted
    r2029 r2528  
    3131   PUBLIC prt_ctl_init    ! called by opa.F90 
    3232   !!---------------------------------------------------------------------- 
    33    !!   OPA 9.0 , LOCEAN-IPSL (2005)  
     33   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
    3434   !! $Id$  
    35    !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt  
     35   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
    3636   !!---------------------------------------------------------------------- 
    3737 
  • trunk/NEMOGCM/NEMO/OPA_SRC/IOM/restart.F90

    • Property svn:eol-style deleted
    r1613 r2528  
    44   !! Ocean restart :  write the ocean restart file 
    55   !!====================================================================== 
    6    !! History :        !  99-11  (M. Imbard)  Original code 
    7    !!             8.5  !  02-08  (G. Madec)  F90: Free form 
    8    !!             9.0  !  05-11  (V. Garnier) Surface pressure gradient organization 
    9    !!             9.0  !  06-07  (S. Masson)  use IOM for restart 
     6   !! History :  OPA  !  1999-11  (M. Imbard)  Original code 
     7   !!   NEMO     1.0  !  2002-08  (G. Madec)  F90: Free form 
     8   !!            2.0  !  2006-07  (S. Masson)  use IOM for restart 
     9   !!            3.3  !  2010-04  (M. Leclair, G. Madec)  modified LF-RA 
     10   !!            - -  !  2010-10  (C. Ethe, G. Madec) TRC-TRA merge (T-S in 4D) 
    1011   !!---------------------------------------------------------------------- 
    1112 
     
    1516   !!   rst_read   : read the ocean restart file 
    1617   !!---------------------------------------------------------------------- 
     18   USE oce             ! ocean dynamics and tracers  
    1719   USE dom_oce         ! ocean space and time domain 
    18    USE oce             ! ocean dynamics and tracers  
    1920   USE phycst          ! physical constants 
    2021   USE in_out_manager  ! I/O manager 
    2122   USE iom             ! I/O module 
    22    USE c1d             ! re-initialization of u-v mask for the 1D configuration 
    23    USE zpshde          ! partial step: hor. derivative (zps_hde routine) 
    2423   USE eosbn2          ! equation of state            (eos bn2 routine) 
    25    USE zdfddm          ! double diffusion mixing  
    26    USE zdfmxl          ! mixed layer depth 
    2724   USE trdmld_oce      ! ocean active mixed layer tracers trends variables 
     25   USE domvvl          ! variable volume 
     26   USE traswp          ! swap from 4D T-S to 3D T & S and vice versa 
    2827 
    2928   IMPLICIT NONE 
     
    3433   PUBLIC   rst_read   ! routine called by opa  module 
    3534 
    36    LOGICAL, PUBLIC ::   lrst_oce =  .FALSE.       !: logical to control the oce restart write  
    37    INTEGER, PUBLIC ::   numror, numrow            !: logical unit for cean restart (read and write) 
     35   LOGICAL, PUBLIC ::   lrst_oce =  .FALSE.   !: logical to control the oce restart write  
     36   INTEGER, PUBLIC ::   numror, numrow        !: logical unit for cean restart (read and write) 
    3837 
    3938   !! * Substitutions 
     39#  include "domzgr_substitute.h90" 
    4040#  include "vectopt_loop_substitute.h90" 
    4141   !!---------------------------------------------------------------------- 
    42    !!  OPA 9.0 , LOCEAN-IPSL (2006)  
     42   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
    4343   !! $Id$ 
    44    !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
    45    !!---------------------------------------------------------------------- 
    46  
     44   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
     45   !!---------------------------------------------------------------------- 
    4746CONTAINS 
    4847 
     
    8887            CASE DEFAULT         ;   WRITE(numout,*) '             open ocean restart NetCDF file: '//clname 
    8988            END SELECT 
     89            IF ( snc4set%luse )      WRITE(numout,*) '             opened for NetCDF4 chunking and compression' 
    9090            IF( kt == nitrst - 1 ) THEN   ;   WRITE(numout,*) '             kt = nitrst - 1 = ', kt 
    9191            ELSE                          ;   WRITE(numout,*) '             kt = '             , kt 
    9292            ENDIF 
    9393         ENDIF 
    94  
     94         ! 
    9595         CALL iom_open( clname, numrow, ldwrt = .TRUE., kiolib = jprstlib ) 
    9696         lrst_oce = .TRUE. 
     
    107107      !! 
    108108      !! ** Method  :   Write in numrow when kt == nitrst in NetCDF 
    109       !!      file, save fields which are necessary for restart 
     109      !!              file, save fields which are necessary for restart 
    110110      !!---------------------------------------------------------------------- 
    111111      INTEGER, INTENT(in) ::   kt   ! ocean time-step 
    112112      !!---------------------------------------------------------------------- 
    113113 
    114       CALL iom_rstput( kt, nitrst, numrow, 'rdt'    , rdt       )   ! dynamics time step 
    115       CALL iom_rstput( kt, nitrst, numrow, 'rdttra1', rdttra(1) )   ! surface tracer time step 
    116  
    117       CALL iom_rstput( kt, nitrst, numrow, 'ub'     , ub      )     ! before fields 
    118       CALL iom_rstput( kt, nitrst, numrow, 'vb'     , vb      ) 
    119       CALL iom_rstput( kt, nitrst, numrow, 'tb'     , tb      ) 
    120       CALL iom_rstput( kt, nitrst, numrow, 'sb'     , sb      ) 
    121       CALL iom_rstput( kt, nitrst, numrow, 'rotb'   , rotb    ) 
    122       CALL iom_rstput( kt, nitrst, numrow, 'hdivb'  , hdivb   ) 
    123       CALL iom_rstput( kt, nitrst, numrow, 'sshb'   , sshb    ) 
    124       ! 
    125       CALL iom_rstput( kt, nitrst, numrow, 'un'     , un      )     ! now fields 
    126       CALL iom_rstput( kt, nitrst, numrow, 'vn'     , vn      ) 
    127       CALL iom_rstput( kt, nitrst, numrow, 'tn'     , tn      ) 
    128       CALL iom_rstput( kt, nitrst, numrow, 'sn'     , sn      ) 
    129       CALL iom_rstput( kt, nitrst, numrow, 'rotn'   , rotn    ) 
    130       CALL iom_rstput( kt, nitrst, numrow, 'hdivn'  , hdivn   ) 
    131       CALL iom_rstput( kt, nitrst, numrow, 'sshn'   , sshn    ) 
    132  
    133       CALL iom_rstput( kt, nitrst, numrow, 'rhop'   , rhop    ) 
     114                     CALL iom_rstput( kt, nitrst, numrow, 'rdt'    , rdt       )   ! dynamics time step 
     115                     CALL iom_rstput( kt, nitrst, numrow, 'rdttra1', rdttra(1) )   ! surface tracer time step 
     116 
     117                     CALL iom_rstput( kt, nitrst, numrow, 'ub'     , ub        )     ! before fields 
     118                     CALL iom_rstput( kt, nitrst, numrow, 'vb'     , vb        ) 
     119                     CALL iom_rstput( kt, nitrst, numrow, 'tb'     , tb        ) 
     120                     CALL iom_rstput( kt, nitrst, numrow, 'sb'     , sb        ) 
     121                     CALL iom_rstput( kt, nitrst, numrow, 'rotb'   , rotb      ) 
     122                     CALL iom_rstput( kt, nitrst, numrow, 'hdivb'  , hdivb     ) 
     123                     CALL iom_rstput( kt, nitrst, numrow, 'sshb'   , sshb      ) 
     124      IF( lk_vvl )   CALL iom_rstput( kt, nitrst, numrow, 'fse3t_b', fse3t_b(:,:,:) ) 
     125                     ! 
     126                     CALL iom_rstput( kt, nitrst, numrow, 'un'     , un        )     ! now fields 
     127                     CALL iom_rstput( kt, nitrst, numrow, 'vn'     , vn        ) 
     128                     CALL iom_rstput( kt, nitrst, numrow, 'tn'     , tn        ) 
     129                     CALL iom_rstput( kt, nitrst, numrow, 'sn'     , sn        ) 
     130                     CALL iom_rstput( kt, nitrst, numrow, 'rotn'   , rotn      ) 
     131                     CALL iom_rstput( kt, nitrst, numrow, 'hdivn'  , hdivn     ) 
     132                     CALL iom_rstput( kt, nitrst, numrow, 'sshn'   , sshn      ) 
     133                     CALL iom_rstput( kt, nitrst, numrow, 'rhop'   , rhop      ) 
    134134#if defined key_zdfkpp 
    135       CALL iom_rstput( kt, nitrst, numrow, 'rhd'  , rhd   ) 
     135                     CALL iom_rstput( kt, nitrst, numrow, 'rhd'    , rhd       ) 
    136136#endif 
    137  
    138137      IF( kt == nitrst ) THEN 
    139138         CALL iom_close( numrow )     ! close the restart file (only at last time step) 
     
    153152      !!---------------------------------------------------------------------- 
    154153      REAL(wp) ::   zrdt, zrdttra1 
    155       INTEGER  ::   jlibalt = jprstlib 
     154      INTEGER  ::   jk, jlibalt = jprstlib 
    156155      LOGICAL  ::   llok 
    157156      !!---------------------------------------------------------------------- 
     
    163162         CASE ( jprstdimg )   ;   WRITE(numout,*) 'rst_read : read oce binary restart file' 
    164163         END SELECT 
     164         IF ( snc4set%luse )      WRITE(numout,*) 'rst_read : configured with NetCDF4 support' 
    165165         WRITE(numout,*) '~~~~~~~~' 
    166166      ENDIF 
     
    184184      ENDIF 
    185185      !  
    186       CALL iom_get( numror, jpdom_autoglo, 'ub'   , ub    )        ! before fields 
    187       CALL iom_get( numror, jpdom_autoglo, 'vb'   , vb    ) 
    188       CALL iom_get( numror, jpdom_autoglo, 'tb'   , tb    ) 
    189       CALL iom_get( numror, jpdom_autoglo, 'sb'   , sb    ) 
    190       CALL iom_get( numror, jpdom_autoglo, 'rotb' , rotb  ) 
    191       CALL iom_get( numror, jpdom_autoglo, 'hdivb', hdivb ) 
    192       CALL iom_get( numror, jpdom_autoglo, 'sshb' , sshb  ) 
    193       ! 
    194       CALL iom_get( numror, jpdom_autoglo, 'un'   , un    )        ! now    fields 
    195       CALL iom_get( numror, jpdom_autoglo, 'vn'   , vn    ) 
    196       CALL iom_get( numror, jpdom_autoglo, 'tn'   , tn    ) 
    197       CALL iom_get( numror, jpdom_autoglo, 'sn'   , sn    ) 
    198       CALL iom_get( numror, jpdom_autoglo, 'rotn' , rotn  ) 
    199       CALL iom_get( numror, jpdom_autoglo, 'hdivn', hdivn ) 
    200       CALL iom_get( numror, jpdom_autoglo, 'sshn' , sshn  ) 
    201  
    202       CALL iom_get( numror, jpdom_autoglo, 'rhop' , rhop  )        ! now    potential density 
     186                     CALL iom_get( numror, jpdom_autoglo, 'ub'     , ub      )   ! before fields 
     187                     CALL iom_get( numror, jpdom_autoglo, 'vb'     , vb      ) 
     188                     CALL iom_get( numror, jpdom_autoglo, 'tb'     , tb      ) 
     189                     CALL iom_get( numror, jpdom_autoglo, 'sb'     , sb      ) 
     190                     CALL iom_get( numror, jpdom_autoglo, 'rotb'   , rotb    ) 
     191                     CALL iom_get( numror, jpdom_autoglo, 'hdivb'  , hdivb  ) 
     192                     CALL iom_get( numror, jpdom_autoglo, 'sshb'   , sshb    ) 
     193      IF( lk_vvl )   CALL iom_get( numror, jpdom_autoglo, 'fse3t_b', fse3t_b(:,:,:) ) 
     194                     ! 
     195                     CALL iom_get( numror, jpdom_autoglo, 'un'     , un      )   ! now    fields 
     196                     CALL iom_get( numror, jpdom_autoglo, 'vn'     , vn      ) 
     197                     CALL iom_get( numror, jpdom_autoglo, 'tn'     , tn      ) 
     198                     CALL iom_get( numror, jpdom_autoglo, 'sn'     , sn      ) 
     199                     CALL iom_get( numror, jpdom_autoglo, 'rotn'   , rotn    ) 
     200                     CALL iom_get( numror, jpdom_autoglo, 'hdivn'  , hdivn   ) 
     201                     CALL iom_get( numror, jpdom_autoglo, 'sshn'   , sshn    ) 
     202                     CALL iom_get( numror, jpdom_autoglo, 'rhop'   , rhop    )   ! now    potential density 
    203203#if defined key_zdfkpp 
    204204      IF( iom_varid( numror, 'rhd', ldstop = .FALSE. ) > 0 ) THEN 
    205          CALL iom_get( numror, jpdom_autoglo, 'rhd' , rhd  )       ! now    in situ density anomaly 
     205                     CALL iom_get( numror, jpdom_autoglo, 'rhd'    , rhd     )   ! now    in situ density anomaly 
    206206      ELSE 
    207          CALL eos( tn, sn, rhd )   ! compute rhd 
     207                     CALL tra_swap 
     208                     CALL eos( tsn, rhd )   ! compute rhd 
    208209      ENDIF 
    209210#endif 
    210  
     211      ! 
    211212      IF( neuler == 0 ) THEN                                  ! Euler restart (neuler=0) 
    212213         tb   (:,:,:) = tn   (:,:,:)                             ! all before fields set to now values 
     
    217218         hdivb(:,:,:) = hdivn(:,:,:) 
    218219         sshb (:,:)   = sshn (:,:) 
     220         IF( lk_vvl ) THEN 
     221            DO jk = 1, jpk 
     222               fse3t_b(:,:,jk) = fse3t_n(:,:,jk) 
     223            END DO 
     224         ENDIF 
    219225      ENDIF 
    220226      ! 
Note: See TracChangeset for help on using the changeset viewer.