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

Changeset 1642


Ignore:
Timestamp:
2009-10-07T15:43:11+02:00 (15 years ago)
Author:
cetlod
Message:

ctlopn cleanup, see changeset:1581

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMO/OFF_SRC/IOM/in_out_manager.F90

    r1481 r1642  
    55   !!                 turbulent closure parameterization 
    66   !!===================================================================== 
    7    !! History :   1.0  !  2002-06  (G. Madec)  original code 
     7   !! History :   1.0  !  2002-06  (G. Madec)   original code 
    88   !!             2.0  !  2006-07  (S. Masson)  iom, add ctl_stop, ctl_warn 
    9    !!             3.0  !  2008-06  (G. Madec)  add ctmp4 to ctmp10 
     9   !!             3.0  !  2008-06  (G. Madec)   add ctmp4 to ctmp10 
     10   !!             3.2  !  2009-08  (S. MAsson)  add new ctl_opn 
    1011   !!---------------------------------------------------------------------- 
    1112 
     
    1819   USE par_oce         ! ocean parameter 
    1920   USE lib_print       ! formated print library 
     21#if defined key_agrif 
     22   USE Agrif_Util 
     23#endif 
    2024 
    2125   IMPLICIT NONE 
     
    2529   !!                   namrun namelist parameters 
    2630   !!---------------------------------------------------------------------- 
    27    CHARACTER(len=16)  ::   cexper        = "exp0"      !: experiment name used for output filename 
     31   CHARACTER(len=16)  ::   cn_exp        = "exp0"      !: experiment name used for output filename 
    2832   CHARACTER(len=32)  ::   cn_ocerst_in  = "restart"   !: suffix of ocean restart name (input) 
    2933   CHARACTER(len=32)  ::   cn_ocerst_out = "restart"   !: suffix of ocean restart name (output) 
    3034   LOGICAL            ::   ln_rstart     = .FALSE.     !: start from (F) rest or (T) a restart file 
    31    INTEGER            ::   no            = 0           !: job number 
    32    INTEGER            ::   nrstdt        = 0           !: control of the time step (0, 1 or 2) 
     35   INTEGER            ::   nn_no         = 0           !: job number 
     36   INTEGER            ::   nn_rstctl     = 0           !: control of the time step (0, 1 or 2) 
    3337   INTEGER            ::   nn_rstssh     = 0           !: hand made initilization of ssh or not (1/0) 
    34    INTEGER            ::   nit000        = 1           !: index of the first time step 
    35    INTEGER            ::   nitend        = 10          !: index of the last time step 
    36    INTEGER            ::   ndate0        = 961115      !: initial calendar date aammjj 
    37    INTEGER            ::   nleapy        = 0           !: Leap year calendar flag (0/1 or 30) 
    38    INTEGER            ::   ninist        = 0           !: initial state output flag (0/1) 
     38   INTEGER            ::   nn_it000      = 1           !: index of the first time step 
     39   INTEGER            ::   nn_itend      = 10          !: index of the last time step 
     40   INTEGER            ::   nn_date0      = 961115      !: initial calendar date aammjj 
     41   INTEGER            ::   nn_leapy      = 0           !: Leap year calendar flag (0/1 or 30) 
     42   INTEGER            ::   nn_istate     = 0           !: initial state output flag (0/1) 
     43   INTEGER            ::   nn_write      =   10        !: model standard output frequency 
     44   INTEGER            ::   nn_stock      =   10        !: restart file frequency 
    3945   LOGICAL            ::   ln_dimgnnn    = .FALSE.     !: type of dimgout. (F): 1 file for all proc 
    4046                                                       !:                  (T): 1 file per proc 
    4147   LOGICAL            ::   ln_mskland    = .FALSE.     !: mask land points in NetCDF outputs (costly: + ~15%) 
     48   LOGICAL            ::   ln_clobber    = .FALSE.     !: clobber (overwrite) an existing file 
     49   INTEGER            ::   nn_chunksz    = 0           !: chunksize (bytes) for NetCDF file (working only with iom_nf90 routines) 
     50 
     51   !! conversion of DOCTOR norm namelist name into model name 
     52   !! (this should disappear in a near futur) 
     53 
     54   CHARACTER(len=16)  ::   cexper                      !: experiment name used for output filename 
     55   INTEGER            ::   no                          !: job number 
     56   INTEGER            ::   nrstdt                      !: control of the time step (0, 1 or 2) 
     57   INTEGER            ::   nit000                      !: index of the first time step 
     58   INTEGER            ::   nitend                      !: index of the last time step 
     59   INTEGER            ::   ndate0                      !: initial calendar date aammjj 
     60   INTEGER            ::   nleapy                      !: Leap year calendar flag (0/1 or 30) 
     61   INTEGER            ::   ninist                      !: initial state output flag (0/1) 
     62   INTEGER            ::   nwrite                      !: model standard output frequency 
     63   INTEGER            ::   nstock                      !: restart file frequency 
     64 
    4265   !!---------------------------------------------------------------------- 
    4366   !! was in restart but moved here because of the OFF line... better solution should be found... 
    4467   !!---------------------------------------------------------------------- 
    4568   INTEGER            ::   nitrst                 !: time step at which restart file should be written 
     69 
    4670   !!---------------------------------------------------------------------- 
    4771   !!                    output monitoring 
    4872   !!---------------------------------------------------------------------- 
    4973   LOGICAL            ::   ln_ctl     = .FALSE.   !: run control for debugging 
    50    INTEGER            ::   nstock     =   10      !: restart file frequency 
    51    INTEGER            ::   nprint     =    0      !: level of print (0 no print) 
    52    INTEGER            ::   nwrite     =   10      !: restart file frequency 
    53    INTEGER            ::   nictls     =    0      !: Start i indice for the SUM control 
    54    INTEGER            ::   nictle     =    0      !: End   i indice for the SUM control 
    55    INTEGER            ::   njctls     =    0      !: Start j indice for the SUM control 
    56    INTEGER            ::   njctle     =    0      !: End   j indice for the SUM control 
    57    INTEGER            ::   isplt      =    1      !: number of processors following i 
    58    INTEGER            ::   jsplt      =    1      !: number of processors following j 
     74   INTEGER            ::   nn_print     =    0    !: level of print (0 no print) 
     75   INTEGER            ::   nn_ictls     =    0    !: Start i indice for the SUM control 
     76   INTEGER            ::   nn_ictle     =    0    !: End   i indice for the SUM control 
     77   INTEGER            ::   nn_jctls     =    0    !: Start j indice for the SUM control 
     78   INTEGER            ::   nn_jctle     =    0    !: End   j indice for the SUM control 
     79   INTEGER            ::   nn_isplt      =    1   !: number of processors following i 
     80   INTEGER            ::   nn_jsplt      =    1   !: number of processors following j 
     81   INTEGER            ::   nn_bench     =    0    !: benchmark parameter (0/1) 
     82   INTEGER            ::   nn_bit_cmp   =    0    !: bit reproducibility  (0/1) 
     83 
     84   !                                              !: OLD namelist names 
     85   INTEGER ::   nprint, nictls, nictle, njctls, njctle, isplt, jsplt, nbench, nbit_cmp    
     86 
    5987   INTEGER            ::   ijsplt     =    1      !: nb of local domain = nb of processors 
    60    INTEGER            ::   nbench     =    0      !: benchmark parameter (0/1) 
    61    INTEGER            ::   nbit_cmp   =    0      !: bit reproducibility  (0/1) 
     88 
    6289   !!---------------------------------------------------------------------- 
    6390   !!                        logical units 
    6491   !!---------------------------------------------------------------------- 
    6592   INTEGER            ::   numstp                 !: logical unit for time step 
    66    INTEGER            ::   numout                 !: logical unit for output print 
     93   INTEGER            ::   numout     =    6      !: logical unit for output print 
    6794   INTEGER            ::   numnam                 !: logical unit for namelist 
    6895   INTEGER            ::   numnam_ice             !: logical unit for ice namelist 
     
    7097   INTEGER            ::   numsol                 !: logical unit for solver statistics 
    7198   INTEGER            ::   numwri                 !: logical unit for output write 
    72    INTEGER            ::   numisp                 !: logical unit for island statistics 
    7399   INTEGER            ::   numgap                 !: logical unit for differences diagnostic 
    74100   INTEGER            ::   numbol                 !: logical unit for "bol" diagnostics 
     
    79105   !!                          Run control   
    80106   !!---------------------------------------------------------------------- 
    81  
    82107   INTEGER            ::   nstop = 0                !: error flag (=number of reason for a premature stop run) 
    83108   INTEGER            ::   nwarn = 0                !: warning flag (=number of warning found during the run) 
     
    88113   CHARACTER (len=64) ::   cform_err = "(/,' ===>>> : E R R O R',     /,'         ===========',/)"       !: 
    89114   CHARACTER (len=64) ::   cform_war = "(/,' ===>>> : W A R N I N G', /,'         ===============',/)"   !: 
    90    LOGICAL            ::   lwp                      !: boolean : true on the 1st processor only 
     115   LOGICAL            ::   lwp      = .FALSE.       !: boolean : true on the 1st processor only 
    91116   LOGICAL            ::   lsp_area = .TRUE.        !: to make a control print over a specific area 
    92117   !!---------------------------------------------------------------------- 
     
    160185 
    161186 
     187   SUBROUTINE ctl_opn ( knum, cdfile, cdstat, cdform, cdacce, klengh, kout, ldwp, karea ) 
     188      !!---------------------------------------------------------------------- 
     189      !!                  ***  ROUTINE ctl_opn  *** 
     190      !! 
     191      !! ** Purpose :   Open file and check if required file is available. 
     192      !! 
     193      !! ** Method  :   Fortan open 
     194      !! 
     195      !! History : 
     196      !!        !  1995-12  (G. Madec)  Original code 
     197      !!   8.5  !  2002-06  (G. Madec)  F90: Free form and module 
     198      !!---------------------------------------------------------------------- 
     199 
     200      INTEGER          , INTENT(  out) ::   knum      ! logical unit to open 
     201      CHARACTER(len=*) , INTENT(in   ) ::   cdfile    ! file name to open 
     202      CHARACTER(len=*) , INTENT(in   ) ::   cdstat    ! disposition specifier 
     203      CHARACTER(len=*) , INTENT(in   ) ::   cdform    ! formatting specifier 
     204      CHARACTER(len=*) , INTENT(in   ) ::   cdacce    ! access specifier 
     205      INTEGER          , INTENT(in   ) ::   klengh    ! record length 
     206      INTEGER          , INTENT(in   ) ::   kout      ! number of logical units for write 
     207      LOGICAL          , INTENT(in   ) ::   ldwp      ! boolean term for print 
     208      INTEGER, OPTIONAL, INTENT(in   ) ::   karea     ! proc number 
     209      !! 
     210      CHARACTER(len=80) ::   clfile 
     211      INTEGER           ::   iost 
     212 
     213      ! adapt filename 
     214      ! ---------------- 
     215      clfile = TRIM(cdfile) 
     216      IF( PRESENT( karea ) ) THEN 
     217         IF( karea > 1 )   WRITE(clfile, "(a,'_',i4.4)") TRIM(clfile), karea-1 
     218      ENDIF 
     219#if defined key_agrif 
     220      IF( .NOT. Agrif_Root() )   clfile = TRIM(Agrif_CFixed())//'_'//TRIM(clfile) 
     221      knum=Agrif_Get_Unit() 
     222#else 
     223      knum=getunit() 
     224#endif 
     225 
     226      iost=0 
     227      IF( cdacce(1:6) == 'DIRECT' )  THEN 
     228         OPEN( UNIT=knum, FILE=clfile, FORM=cdform, ACCESS=cdacce, STATUS=cdstat, RECL=klengh, ERR=100, IOSTAT=iost ) 
     229      ELSE 
     230         OPEN( UNIT=knum, FILE=clfile, FORM=cdform, ACCESS=cdacce, STATUS=cdstat             , ERR=100, IOSTAT=iost ) 
     231      ENDIF 
     232      IF( iost == 0 ) THEN 
     233         IF(ldwp) THEN 
     234            WRITE(kout,*) '     file   : ', clfile,' open ok' 
     235            WRITE(kout,*) '     unit   = ', knum 
     236            WRITE(kout,*) '     status = ', cdstat 
     237            WRITE(kout,*) '     form   = ', cdform 
     238            WRITE(kout,*) '     access = ', cdacce 
     239            WRITE(kout,*) 
     240         ENDIF 
     241      ENDIF 
     242100   CONTINUE 
     243      IF( iost /= 0 ) THEN 
     244         IF(ldwp) THEN 
     245            WRITE(kout,*) 
     246            WRITE(kout,*) ' ===>>>> : bad opening file: ', clfile 
     247            WRITE(kout,*) ' =======   ===  ' 
     248            WRITE(kout,*) '           unit   = ', knum 
     249            WRITE(kout,*) '           status = ', cdstat 
     250            WRITE(kout,*) '           form   = ', cdform 
     251            WRITE(kout,*) '           access = ', cdacce 
     252            WRITE(kout,*) '           iostat = ', iost 
     253            WRITE(kout,*) '           we stop. verify the file ' 
     254            WRITE(kout,*) 
     255         ENDIF 
     256         STOP 'ctl_opn bad opening' 
     257      ENDIF 
     258       
     259   END SUBROUTINE ctl_opn 
     260 
     261 
    162262   FUNCTION getunit() 
    163263      !!---------------------------------------------------------------------- 
Note: See TracChangeset for help on using the changeset viewer.