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 2498 for branches – NEMO

Changeset 2498 for branches


Ignore:
Timestamp:
2010-12-21T15:22:05+01:00 (13 years ago)
Author:
gm
Message:

v3.3beta: #657 declare a variable for character size

Location:
branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC
Files:
5 edited

Legend:

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

    r2372 r2498  
    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 
    21    USE nc4interface 
     19   USE par_oce       ! ocean parameter 
     20   USE lib_print     ! formated print library 
     21   USE nc4interface  ! NetCDF4 interface 
    2222 
    2323   IMPLICIT NONE 
     
    2727   !!                   namrun namelist parameters 
    2828   !!---------------------------------------------------------------------- 
    29    CHARACTER(len=16) ::   cn_exp        = "exp0"      !: experiment name used for output filename 
    30    CHARACTER(len=32) ::   cn_ocerst_in  = "restart"   !: suffix of ocean restart name (input) 
    31    CHARACTER(len=32) ::   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 
     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 
    4444                                                       !:                  (T): 1 file per proc 
    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 (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) 
    4848#if defined key_netcdf4 
    4949   !!---------------------------------------------------------------------- 
    50    !!                   namnc4 namelist parameters 
    51    !!---------------------------------------------------------------------- 
    52                                                        !: ========================================================================= 
    53                                                        !: The following four values determine the partitioning of the output fields 
    54                                                        !: into netcdf4 chunks. They are unrelated to the nn_chunk_sz setting which is 
    55                                                        !: for runtime optimisation. The individual netcdf4 chunks can be optionally  
    56                                                        !: gzipped (recommended) leading to significant reductions in I/O volumes  
    57    INTEGER            ::   nn_nchunks_i  = 1           !: number of chunks required in the i-dimension (only with iom_nf90 routines and key_netcdf4) 
    58    INTEGER            ::   nn_nchunks_j  = 1           !: number of chunks required in the j-dimension (only with iom_nf90 routines and key_netcdf4) 
    59    INTEGER            ::   nn_nchunks_k  = 1           !: number of chunks required in the k-dimension (only with iom_nf90 routines and key_netcdf4) 
    60    INTEGER            ::   nn_nchunks_t  = 1           !: number of chunks required in the t-dimension (only with iom_nf90 routines and key_netcdf4) 
    61    LOGICAL            ::   ln_nc4zip     = .TRUE.      !: netcdf4 usage. (T): chunk and compress output datasets using the HDF5 sublayers of netcdf4 
    62                                                        !:                (F): ignore chunking request and use the netcdf4 library to produce netcdf3-compatible files  
     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  
    6364#endif 
    64  
    6565!$AGRIF_DO_NOT_TREAT 
    66    TYPE(snc4_ctl)     :: snc4set                       !: netcdf4 chunking control structure (always needed for decision making) 
     66   TYPE(snc4_ctl)     :: snc4set        !: netcdf4 chunking control structure (always needed for decision making) 
    6767!$AGRIF_END_DO_NOT_TREAT 
    6868 
     
    7171   !! (this should disappear in a near futur) 
    7272 
    73    CHARACTER(len=16) ::   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 
     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 
    8383 
    8484   !!---------------------------------------------------------------------- 
    8585   !! was in restart but moved here because of the OFF line... better solution should be found... 
    8686   !!---------------------------------------------------------------------- 
    87    INTEGER            ::   nitrst                 !: time step at which restart file should be written 
     87   INTEGER ::   nitrst   !: time step at which restart file should be written 
    8888 
    8989   !!---------------------------------------------------------------------- 
    9090   !!                    output monitoring 
    9191   !!---------------------------------------------------------------------- 
    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    !                                              !: OLD namelist names 
    104    INTEGER ::   nprint, nictls, nictle, njctls, njctle, isplt, jsplt, nbench 
    105  
    106    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 
    107107 
    108108   !!---------------------------------------------------------------------- 
    109109   !!                        logical units 
    110110   !!---------------------------------------------------------------------- 
    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 
     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 
    117117 
    118118   !!---------------------------------------------------------------------- 
    119119   !!                          Run control   
    120120   !!---------------------------------------------------------------------- 
    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(len=200) ::   ctmp1, ctmp2, ctmp3      !: temporary characters 1 to 3 
    124    CHARACTER(len=200) ::   ctmp4, ctmp5, ctmp6      !: temporary characters 4 to 6 
    125    CHARACTER(len=200) ::   ctmp7, ctmp8, ctmp9      !: temporary characters 7 to 9 
    126    CHARACTER(len=200) ::   ctmp10                   !: temporary character 10 
    127    CHARACTER (len=64) ::   cform_err = "(/,' ===>>> : E R R O R',     /,'         ===========',/)"       !: 
    128    CHARACTER (len=64) ::   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 
     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 
    131132   !!---------------------------------------------------------------------- 
    132133   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
    133134   !! $Id$ 
    134    !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
    135    !!---------------------------------------------------------------------- 
    136  
     135   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
     136   !!---------------------------------------------------------------------- 
    137137CONTAINS 
    138138 
     
    151151      nstop = nstop + 1  
    152152      IF(lwp) THEN 
    153          WRITE(numout,"(/,' ===>>> : E R R O R',     /,'         ===========',/)")  
     153         WRITE(numout,cform_err) 
    154154         IF( PRESENT(cd1 ) ) WRITE(numout,*) cd1 
    155155         IF( PRESENT(cd2 ) ) WRITE(numout,*) cd2 
     
    185185      nwarn = nwarn + 1  
    186186      IF(lwp) THEN 
    187          WRITE(numout,"(/,' ===>>> : W A R N I N G', /,'         ===============',/)")  
     187         WRITE(numout,cform_war) 
    188188         IF( PRESENT(cd1 ) ) WRITE(numout,*) cd1 
    189189         IF( PRESENT(cd2 ) ) WRITE(numout,*) cd2 
     
    202202 
    203203 
    204    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 ) 
    205205      !!---------------------------------------------------------------------- 
    206206      !!                  ***  ROUTINE ctl_opn  *** 
     
    209209      !! 
    210210      !! ** Method  :   Fortan open 
    211       !! 
    212       !! History : 
    213       !!        !  1995-12  (G. Madec)  Original code 
    214       !!   8.5  !  2002-06  (G. Madec)  F90: Free form and module 
    215       !!---------------------------------------------------------------------- 
    216  
     211      !!---------------------------------------------------------------------- 
    217212      INTEGER          , INTENT(  out) ::   knum      ! logical unit to open 
    218213      CHARACTER(len=*) , INTENT(in   ) ::   cdfile    ! file name to open 
     
    227222      CHARACTER(len=80) ::   clfile 
    228223      INTEGER           ::   iost 
     224      !!---------------------------------------------------------------------- 
    229225 
    230226      ! adapt filename 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/module_example

    r2433 r2498  
    2626 
    2727   TYPE ::   FLD_E                !: Structure type definition 
    28       CHARACTER(len = 256) ::   clname      ! clname description  
    29       INTEGER              ::   nfreqh      ! nfreqh description  
     28      CHARACTER(lc) ::   clname      ! clname description (default length, lc, is 256, see par_kind.F90) 
     29      INTEGER       ::   nfreqh      ! nfreqh description  
    3030   END TYPE FLD_E  
    3131 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/nemogcm.F90

    r2496 r2498  
    7575   PUBLIC   nemo_init   ! needed by AGRIF 
    7676 
    77    CHARACTER (len=64) ::   cform_aaa="( /, 'AAAAAAAA', / ) "     ! flag for output listing 
     77   CHARACTER(lc) ::   cform_aaa="( /, 'AAAAAAAA', / ) "     ! flag for output listing 
    7878 
    7979   !!---------------------------------------------------------------------- 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/oce.F90

    r2287 r2498  
    1414 
    1515   LOGICAL         , PUBLIC ::   l_traldf_rot = .FALSE.  !: rotated laplacian operator for lateral diffusion 
    16    CHARACTER(len=3), PUBLIC ::   l_adv                   !: flag for the advection scheme used (= 'ce2', 'tvd' ...) 
    1716 
    1817   !! dynamics and tracer fields                  ! before ! now    ! after   ! the after trends becomes the fields 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/par_kind.F90

    r2287 r2498  
    44   !! Ocean :  define the kind of real for the whole model 
    55   !!====================================================================== 
    6    !! History : 
    7    !!   8.5   02/06  (G. Madec)  Original code 
    8    !!---------------------------------------------------------------------- 
    9    !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
    10    !! $Id$  
    11    !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
     6   !! History :  1.0  ! 2002-06  (G. Madec)  Original code 
     7   !!            3.3  ! 2010-12  (G. Madec)  add a standard length of character strings 
    128   !!---------------------------------------------------------------------- 
    139 
     
    1511   PRIVATE 
    1612 
    17    INTEGER, PUBLIC, PARAMETER ::    &  !: 
    18       jpbyt   = 8       ,           &  !: real size for mpp communications 
    19       jpbytda = 4       ,           &  !: real size in input data files 4 or 8 
    20       jpbi3e  = 4                      !: real size for T3E 
     13   INTEGER, PUBLIC, PARAMETER ::   jpbyt   = 8    !: real size for mpp communications 
     14   INTEGER, PUBLIC, PARAMETER ::   jpbytda = 4    !: real size in input data files 4 or 8 
    2115 
    2216   ! Number model from which the SELECTED_*_KIND are requested: 
     
    2721   !            exponent = 37     exponent = 307 
    2822 
    29    INTEGER, PUBLIC, PARAMETER ::        &  !: Floating point section 
    30       sp = SELECTED_REAL_KIND( 6, 37),  &  !: single precision (real 4) 
    31       dp = SELECTED_REAL_KIND(12,307),  &  !: double precision (real 8) 
    32       wp = dp                              !: working precision 
     23   !                                                                !!** Floating point ** 
     24   INTEGER, PUBLIC, PARAMETER ::   sp = SELECTED_REAL_KIND( 6, 37)   !: single precision (real 4) 
     25   INTEGER, PUBLIC, PARAMETER ::   dp = SELECTED_REAL_KIND(12,307)   !: double precision (real 8) 
     26   INTEGER, PUBLIC, PARAMETER ::   wp = dp                              !: working precision 
    3327 
    34    INTEGER, PUBLIC, PARAMETER ::        &  !: Integer section 
    35       i4 = SELECTED_INT_KIND(9) ,       &  !: single precision (integer 4) 
    36       i8 = SELECTED_INT_KIND(14)           !: double precision (integer 8) 
     28   !                                                                !!** Integer ** 
     29   INTEGER, PUBLIC, PARAMETER ::   i4 = SELECTED_INT_KIND( 9)        !: single precision (integer 4) 
     30   INTEGER, PUBLIC, PARAMETER ::   i8 = SELECTED_INT_KIND(14)        !: double precision (integer 8) 
     31    
     32   !                                                                !!** Integer ** 
     33   INTEGER, PUBLIC, PARAMETER ::   lc = 256                          !: Lenght of Character strings 
    3734 
    38 !!---------------------------------------------------------------------- 
     35   !!---------------------------------------------------------------------- 
     36   !! NEMO 3.3 , NEMO Consortium (2010) 
     37   !! $Id$  
     38   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
     39   !!---------------------------------------------------------------------- 
    3940END MODULE par_kind 
Note: See TracChangeset for help on using the changeset viewer.