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 3875 for branches/2013/dev_r3853_CNRS9_ConfSetting/NEMOGCM/NEMO/OPA_SRC – NEMO

Ignore:
Timestamp:
2013-04-18T16:38:06+02:00 (11 years ago)
Author:
clevy
Message:

Configuration Setting/Step? 1, see ticket:#1074

Location:
branches/2013/dev_r3853_CNRS9_ConfSetting/NEMOGCM/NEMO/OPA_SRC
Files:
60 edited

Legend:

Unmodified
Added
Removed
  • branches/2013/dev_r3853_CNRS9_ConfSetting/NEMOGCM/NEMO/OPA_SRC/ASM/asminc.F90

    r3785 r3875  
    120120      INTEGER :: iitiaustr_date  ! Date YYYYMMDD of IAU interval start time step 
    121121      INTEGER :: iitiaufin_date  ! Date YYYYMMDD of IAU interval final time step 
     122      INTEGER :: ios             ! Local integer output status for namelist read 
    122123 
    123124      REAL(wp) :: znorm        ! Normalization factor for IAU weights 
     
    160161      niaufn    = 0 
    161162 
    162       REWIND ( numnam ) 
    163       READ   ( numnam, nam_asminc ) 
     163      REWIND( numnam_ref )              ! Namelist nam_asminc in reference namelist : Assimilation increment 
     164      READ  ( numnam_ref, nam_asminc, IOSTAT = ios, ERR = 901) 
     165901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nam_asminc in reference namelist', lwp ) 
     166 
     167      REWIND( numnam_cfg )              ! Namelist nam_asminc in configuration namelist : Assimilation increment 
     168      READ  ( numnam_cfg, nam_asminc, IOSTAT = ios, ERR = 902 ) 
     169902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nam_asminc in configuration namelist', lwp ) 
     170      WRITE ( numond, nam_asminc ) 
    164171 
    165172      ! Control print 
  • branches/2013/dev_r3853_CNRS9_ConfSetting/NEMOGCM/NEMO/OPA_SRC/BDY/bdydta.F90

    r3851 r3875  
    355355      !! 
    356356      INTEGER     ::  ib_bdy, jfld, jstart, jend, ierror  ! local indices 
     357      INTEGER      ::   ios                               ! Local integer output status for namelist read 
    357358      !! 
    358359      CHARACTER(len=100)                     ::   cn_dir        ! Root directory for location of data files 
     
    440441      ! Read namelists 
    441442      ! -------------- 
    442       REWIND(numnam) 
     443      REWIND(numnam_cfg) 
    443444      jfld = 0  
    444445      DO ib_bdy = 1, nb_bdy          
     
    463464#endif 
    464465 
     466            ! Read configuration namelist only to avoid unsuccessful overwrite 
    465467            ! Important NOT to rewind here. 
    466             READ( numnam, nambdy_dta ) 
     468!!          REWIND( numnam_ref )              ! Namelist nambdy_dta in reference namelist :  
     469!!          READ  ( numnam_ref, nambdy_dta, IOSTAT = ios, ERR = 901) 
     470!!901       IF( ios /= 0 ) CALL ctl_nam ( ios , 'nambdy_dta in reference namelist', lwp ) 
     471 
     472!!          REWIND( numnam_cfg )              ! Namelist nambdy_dta in configuration namelist :  
     473            READ  ( numnam_cfg, nambdy_dta, IOSTAT = ios, ERR = 902 ) 
     474902         IF( ios /= 0 ) CALL ctl_nam ( ios , 'nambdy_dta in configuration namelist', lwp ) 
     475            WRITE ( numond, nambdy_dta ) 
    467476 
    468477            cn_dir_array(ib_bdy) = cn_dir 
  • branches/2013/dev_r3853_CNRS9_ConfSetting/NEMOGCM/NEMO/OPA_SRC/BDY/bdyini.F90

    r3703 r3875  
    102102      !! 
    103103      NAMELIST/nambdy_index/ ctypebdy, nbdyind, nbdybeg, nbdyend 
    104  
     104      INTEGER  ::   ios                 ! Local integer output status for namelist read 
    105105      !!---------------------------------------------------------------------- 
    106106 
     
    145145      nn_rimwidth(:)    = -1  ! uninitialised flag 
    146146 
    147       REWIND( numnam )                     
    148       READ  ( numnam, nambdy ) 
     147      REWIND( numnam_ref )              ! Namelist nambdy in reference namelist :Unstructured open boundaries   
     148      READ  ( numnam_ref, nambdy, IOSTAT = ios, ERR = 901) 
     149901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nambdy in reference namelist', lwp ) 
     150 
     151      REWIND( numnam_cfg )              ! Namelist nambdy in configuration namelist :Unstructured open boundaries 
     152      READ  ( numnam_cfg, nambdy, IOSTAT = ios, ERR = 902 ) 
     153902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nambdy in configuration namelist', lwp ) 
     154      WRITE ( numond, nambdy ) 
    149155 
    150156      ! ----------------------------------------- 
     
    301307      ! Work out global dimensions of boundary data 
    302308      ! --------------------------------------------- 
    303       REWIND( numnam )                     
     309      REWIND( numnam_cfg )      
     310 
     311      !!---------------------------------------------------------------------- 
     312 
     313               
    304314                
    305315      nblendta(:,:) = 0 
     
    319329            icount = icount + 1 
    320330            ! No REWIND here because may need to read more than one nambdy_index namelist. 
    321             READ  ( numnam, nambdy_index ) 
     331            ! Read only namelist_cfg to avoid unseccessfull overwrite 
     332!!          REWIND( numnam_ref )              ! Namelist nambdy_index in reference namelist : Open boundaries indexes 
     333!!          READ  ( numnam_ref, namrun, IOSTAT = ios, ERR = 903) 
     334!!903       IF( ios /= 0 ) CALL ctl_nam ( ios , 'nambdy_index in reference namelist', lwp ) 
     335 
     336!!          REWIND( numnam_cfg )              ! Namelist nambdy_index in configuration namelist : Open boundaries indexes 
     337            READ  ( numnam_cfg, nambdy_index, IOSTAT = ios, ERR = 904 ) 
     338904         IF( ios /= 0 ) CALL ctl_nam ( ios , 'nambdy_index in configuration namelist', lwp ) 
     339            WRITE ( numond, nambdy_index ) 
    322340 
    323341            SELECT CASE ( TRIM(ctypebdy) ) 
  • branches/2013/dev_r3853_CNRS9_ConfSetting/NEMOGCM/NEMO/OPA_SRC/BDY/bdytides.F90

    r3651 r3875  
    7676      INTEGER, DIMENSION(3)                     ::   ilen0       !: length of boundary data (from OBC arrays) 
    7777      INTEGER, POINTER, DIMENSION(:)            ::   nblen, nblenrim     ! short cuts 
     78      INTEGER                                   ::   ios                 ! Local integer output status for namelist read 
    7879      CHARACTER(len=80)                         ::   clfile              !: full file name for tidal input file  
    7980      REAL(wp),ALLOCATABLE, DIMENSION(:,:,:)    ::   dta_read            !: work space to read in tidal harmonics data 
     
    9697      ln_bdytide_conj  = .FALSE. 
    9798 
    98       REWIND(numnam) 
     99      REWIND(numnam_cfg) 
     100 
    99101      DO ib_bdy = 1, nb_bdy 
    100102         IF( nn_dyn2d_dta(ib_bdy) .ge. 2 ) THEN 
     
    108110 
    109111            ! Don't REWIND here - may need to read more than one of these namelists. 
    110             READ  ( numnam, nambdy_tide ) 
     112            ! Read only configuration namelist to avoid unsecessful overwrite 
     113!!          REWIND( numnam_ref )              ! Namelist nambdy_tide in reference namelist :  
     114!!          READ  ( numnam_ref, nambdy_tide, IOSTAT = ios, ERR = 901) 
     115!!    901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nambdy_tide in reference namelist', lwp ) 
     116 
     117!!          REWIND( numnam_cfg )              ! Namelist nambdy_tide in configuration namelist :  
     118            READ  ( numnam_cfg, nambdy_tide, IOSTAT = ios, ERR = 902 ) 
     119902         IF( ios /= 0 ) CALL ctl_nam ( ios , 'nambdy_tide in configuration namelist', lwp ) 
     120            WRITE ( numond, nambdy_tide ) 
    111121            !                                               ! Parameter control and print 
    112122            IF(lwp) WRITE(numout,*) '  ' 
  • branches/2013/dev_r3853_CNRS9_ConfSetting/NEMOGCM/NEMO/OPA_SRC/DIA/diadct.F90

    r3680 r3875  
    139139     !!--------------------------------------------------------------------- 
    140140     NAMELIST/namdct/nn_dct,nn_dctwri,nn_secdebug 
     141     INTEGER  ::   ios                 ! Local integer output status for namelist read 
    141142 
    142143     IF( nn_timing == 1 )   CALL timing_start('dia_dct_init') 
    143144 
    144      !read namelist 
    145      REWIND( numnam ) 
    146      READ  ( numnam, namdct ) 
     145     REWIND( numnam_ref )              ! Namelist namdct in reference namelist : Diagnostic: transport through sections 
     146     READ  ( numnam_ref, namdct, IOSTAT = ios, ERR = 901) 
     147901  IF( ios /= 0 ) CALL ctl_nam ( ios , 'namdct in reference namelist', lwp ) 
     148 
     149     REWIND( numnam_cfg )              ! Namelist namdct in configuration namelist : Diagnostic: transport through sections 
     150     READ  ( numnam_cfg, namdct, IOSTAT = ios, ERR = 902 ) 
     151902  IF( ios /= 0 ) CALL ctl_nam ( ios , 'namdct in configuration namelist', lwp ) 
     152     WRITE ( numond, namdct ) 
    147153 
    148154     IF( lwp ) THEN 
  • branches/2013/dev_r3853_CNRS9_ConfSetting/NEMOGCM/NEMO/OPA_SRC/DIA/diaharm.F90

    r3294 r3875  
    7878      !! * Local declarations  
    7979      INTEGER :: jh, nhan, jk, ji 
     80      INTEGER ::   ios                 ! Local integer output status for namelist read 
    8081 
    8182      NAMELIST/nam_diaharm/ nit000_han, nitend_han, nstep_han, tname 
     
    9293      tname(:)='' 
    9394      ! 
    94       ! Read Namelist nam_diaharm 
    95       REWIND ( numnam ) 
    96       READ   ( numnam, nam_diaharm ) 
     95      REWIND( numnam_ref )              ! Namelist nam_diaharm in reference namelist : Tidal harmonic analysis 
     96      READ  ( numnam_ref, nam_diaharm, IOSTAT = ios, ERR = 901) 
     97901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nam_diaharm in reference namelist', lwp ) 
     98 
     99      REWIND( numnam_cfg )              ! Namelist nam_diaharm in configuration namelist : Tidal harmonic analysis 
     100      READ  ( numnam_cfg, nam_diaharm, IOSTAT = ios, ERR = 902 ) 
     101902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nam_diaharm in configuration namelist', lwp ) 
     102      WRITE ( numond, nam_diaharm ) 
    97103      ! 
    98104      IF(lwp) THEN 
  • branches/2013/dev_r3853_CNRS9_ConfSetting/NEMOGCM/NEMO/OPA_SRC/DIA/diahsb.F90

    r3625 r3875  
    163163      INTEGER            ::   jk       ! dummy loop indice 
    164164      INTEGER            ::   ierror   ! local integer 
     165      INTEGER            ::   ios      ! Local integer output status for namelist read 
    165166      !! 
    166167      NAMELIST/namhsb/ ln_diahsb 
    167168      !!---------------------------------------------------------------------- 
    168169      ! 
    169       REWIND ( numnam )              ! Read Namelist namhsb  
    170       READ   ( numnam, namhsb ) 
     170      REWIND( numnam_ref )              ! Namelist namhsb in reference namelist : Heat & salt budget 
     171      READ  ( numnam_ref, namhsb, IOSTAT = ios, ERR = 901) 
     172901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namhsb in reference namelist', lwp ) 
     173 
     174      REWIND( numnam_cfg )              ! Namelist namhsb in configuration namelist : Heat & salt budget 
     175      READ  ( numnam_cfg, namhsb, IOSTAT = ios, ERR = 902 ) 
     176902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namhsb in configuration namelist', lwp ) 
     177      WRITE ( numond, namhsb ) 
    171178      ! 
    172179      IF(lwp) THEN                   ! Control print 
  • branches/2013/dev_r3853_CNRS9_ConfSetting/NEMOGCM/NEMO/OPA_SRC/DIA/diaptr.F90

    r3764 r3875  
    449449      INTEGER ::   jn           ! dummy loop indices  
    450450      INTEGER ::   inum, ierr   ! local integers 
     451      INTEGER ::   ios          ! Local integer output status for namelist read 
    451452#if defined key_mpp_mpi 
    452453      INTEGER, DIMENSION(1) :: iglo, iloc, iabsf, iabsl, ihals, ihale, idid 
     
    456457      !!---------------------------------------------------------------------- 
    457458 
    458       REWIND( numnam )                 ! Read Namelist namptr : poleward transport parameters 
    459       READ  ( numnam, namptr ) 
     459      REWIND( numnam_ref )              ! Namelist namptr in reference namelist : Poleward transport 
     460      READ  ( numnam_ref, namptr, IOSTAT = ios, ERR = 901) 
     461901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namptr in reference namelist', lwp ) 
     462 
     463      REWIND( numnam_cfg )              ! Namelist namptr in configuration namelist : Poleward transport 
     464      READ  ( numnam_cfg, namptr, IOSTAT = ios, ERR = 902 ) 
     465902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namptr in configuration namelist', lwp ) 
     466      WRITE ( numond, namptr ) 
    460467 
    461468      IF(lwp) THEN                     ! Control print 
  • branches/2013/dev_r3853_CNRS9_ConfSetting/NEMOGCM/NEMO/OPA_SRC/DOM/domain.F90

    r3764 r3875  
    131131      NAMELIST/namnc4/ nn_nchunks_i, nn_nchunks_j, nn_nchunks_k, ln_nc4zip 
    132132#endif 
    133       !!---------------------------------------------------------------------- 
    134  
    135       REWIND( numnam )              ! Namelist namrun : parameters of the run 
    136       READ  ( numnam, namrun ) 
     133      INTEGER  ::   ios                 ! Local integer output status for namelist read 
     134      !!---------------------------------------------------------------------- 
     135 
     136      REWIND( numnam_ref )              ! Namelist namrun in reference namelist : Parameters of the run 
     137      READ  ( numnam_ref, namrun, IOSTAT = ios, ERR = 901) 
     138901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namrun in reference namelist', lwp ) 
     139 
     140      REWIND( numnam_cfg )              ! Namelist namrun in configuration namelist : Parameters of the run 
     141      READ  ( numnam_cfg, namrun, IOSTAT = ios, ERR = 902 ) 
     142902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namrun in configuration namelist', lwp ) 
     143      WRITE ( numond, namrun ) 
    137144      ! 
    138145      IF(lwp) THEN                  ! control print 
     
    200207#endif 
    201208 
    202       REWIND( numnam )              ! Namelist namdom : space & time domain (bathymetry, mesh, timestep) 
    203       READ  ( numnam, namdom ) 
     209      REWIND( numnam_ref )              ! Namelist namdom in reference namelist : space & time domain (bathymetry, mesh, timestep) 
     210      READ  ( numnam_ref, namdom, IOSTAT = ios, ERR = 903) 
     211903   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namdom in reference namelist', lwp ) 
     212 
     213      REWIND( numnam_cfg )              ! Namelist namdom in configuration namelist : space & time domain (bathymetry, mesh, timestep) 
     214      READ  ( numnam_cfg, namdom, IOSTAT = ios, ERR = 904 ) 
     215904   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namdom in configuration namelist', lwp ) 
     216      WRITE ( numond, namdom ) 
    204217 
    205218      IF(lwp) THEN 
     
    237250      rdth      = rn_rdth 
    238251 
    239       REWIND( numnam )              ! Namelist cross land advection 
    240       READ  ( numnam, namcla ) 
     252      REWIND( numnam_ref )              ! Namelist namcla in reference namelist : Cross land advection 
     253      READ  ( numnam_ref, namcla, IOSTAT = ios, ERR = 905) 
     254905   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namcla in reference namelist', lwp ) 
     255 
     256      REWIND( numnam_cfg )              ! Namelist namcla in configuration namelist : Cross land advection 
     257      READ  ( numnam_cfg, namcla, IOSTAT = ios, ERR = 906 ) 
     258906   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namcla in configuration namelist', lwp ) 
     259      WRITE( numond, namcla ) 
     260 
    241261      IF(lwp) THEN 
    242262         WRITE(numout,*) 
     
    247267#if defined key_netcdf4 
    248268      !                             ! NetCDF 4 case   ("key_netcdf4" defined) 
    249       REWIND( numnam )                    ! Namelist namnc4 : netcdf4 chunking parameters 
    250       READ  ( numnam, namnc4 ) 
     269      REWIND( numnam_ref )              ! Namelist namnc4 in reference namelist : NETCDF 
     270      READ  ( numnam_ref, namnc4, IOSTAT = ios, ERR = 907) 
     271907   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namnc4 in reference namelist', lwp ) 
     272 
     273      REWIND( numnam_cfg )              ! Namelist namnc4 in configuration namelist : NETCDF 
     274      READ  ( numnam_cfg, namnc4, IOSTAT = ios, ERR = 908 ) 
     275908   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namnc4 in configuration namelist', lwp ) 
     276      WRITE( numond, namnc4 ) 
     277 
    251278      IF(lwp) THEN                        ! control print 
    252279         WRITE(numout,*) 
  • branches/2013/dev_r3853_CNRS9_ConfSetting/NEMOGCM/NEMO/OPA_SRC/DOM/dommsk.F90

    r3294 r3875  
    133133      INTEGER  ::   iif, iil, ii0, ii1, ii   ! local integers 
    134134      INTEGER  ::   ijf, ijl, ij0, ij1       !   -       - 
     135      INTEGER  ::   ios 
    135136      INTEGER , POINTER, DIMENSION(:,:) ::  imsk 
    136137      REAL(wp), POINTER, DIMENSION(:,:) ::  zwf 
     
    144145      CALL wrk_alloc( jpi, jpj, zwf  ) 
    145146      ! 
    146       REWIND( numnam )              ! Namelist namlbc : lateral momentum boundary condition 
    147       READ  ( numnam, namlbc ) 
     147      REWIND( numnam_ref )              ! Namelist namlbc in reference namelist : Lateral momentum boundary condition 
     148      READ  ( numnam_ref, namlbc, IOSTAT = ios, ERR = 901 ) 
     149901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namlbc in reference namelist', lwp ) 
     150 
     151      REWIND( numnam_cfg )              ! Namelist namlbc in configuration namelist : Lateral momentum boundary condition 
     152      READ  ( numnam_cfg, namlbc, IOSTAT = ios, ERR = 902 ) 
     153902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namlbc in configuration namelist', lwp ) 
     154      WRITE ( numond, namlbc ) 
    148155       
    149156      IF(lwp) THEN                  ! control print 
  • branches/2013/dev_r3853_CNRS9_ConfSetting/NEMOGCM/NEMO/OPA_SRC/DOM/domzgr.F90

    r3764 r3875  
    9999      !!---------------------------------------------------------------------- 
    100100      INTEGER ::   ioptio, ibat   ! local integer 
     101      INTEGER ::   ios 
    101102      ! 
    102103      NAMELIST/namzgr/ ln_zco, ln_zps, ln_sco 
     
    105106      IF( nn_timing == 1 )   CALL timing_start('dom_zgr') 
    106107      ! 
    107       REWIND( numnam )                 ! Read Namelist namzgr : vertical coordinate' 
    108       READ  ( numnam, namzgr ) 
     108      REWIND( numnam_ref )              ! Namelist namzgr in reference namelist : Vertical coordinate 
     109      READ  ( numnam_ref, namzgr, IOSTAT = ios, ERR = 901 ) 
     110901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namzgr in reference namelist', lwp ) 
     111 
     112      REWIND( numnam_cfg )              ! Namelist namzgr in configuration namelist : Vertical coordinate 
     113      READ  ( numnam_cfg, namzgr, IOSTAT = ios, ERR = 902 ) 
     114902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namzgr in configuration namelist', lwp ) 
     115      WRITE ( numond, namzgr ) 
    109116 
    110117      IF(lwp) THEN                     ! Control print 
     
    11001107      INTEGER  ::   ji, jj, jk, jl           ! dummy loop argument 
    11011108      INTEGER  ::   iip1, ijp1, iim1, ijm1   ! temporary integers 
     1109      INTEGER  ::   ios                      ! Local integer output status for namelist read 
    11021110      REAL(wp) ::   zrmax, ztaper   ! temporary scalars 
    11031111      ! 
     
    11121120      CALL wrk_alloc( jpi, jpj,      zenv, ztmp, zmsk, zri, zrj, zhbat                           ) 
    11131121      ! 
    1114       REWIND( numnam )                       ! Read Namelist namzgr_sco : sigma-stretching parameters 
    1115       READ  ( numnam, namzgr_sco ) 
     1122      REWIND( numnam_ref )              ! Namelist namzgr_sco in reference namelist : Sigma-stretching parameters 
     1123      READ  ( numnam_ref, namzgr_sco, IOSTAT = ios, ERR = 901) 
     1124901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namzgr_sco in reference namelist', lwp ) 
     1125 
     1126      REWIND( numnam_cfg )              ! Namelist namzgr_sco in configuration namelist : Sigma-stretching parameters 
     1127      READ  ( numnam_cfg, namzgr_sco, IOSTAT = ios, ERR = 902 ) 
     1128902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namzgr_sco in configuration namelist', lwp ) 
     1129      WRITE ( numond, namzgr_sco ) 
    11161130 
    11171131      IF(lwp) THEN                           ! control print 
    11181132         WRITE(numout,*) 
    1119          WRITE(numout,*) 'dom:zgr_sco : s-coordinate or hybrid z-s-coordinate' 
     1133         WRITE(numout,*) 'domzgr_sco : s-coordinate or hybrid z-s-coordinate' 
    11201134         WRITE(numout,*) '~~~~~~~~~~~' 
    11211135         WRITE(numout,*) '   Namelist namzgr_sco' 
  • branches/2013/dev_r3853_CNRS9_ConfSetting/NEMOGCM/NEMO/OPA_SRC/DOM/dtatsd.F90

    r3294 r3875  
    6262      !! 
    6363      NAMELIST/namtsd/   ln_tsd_init, ln_tsd_tradmp, cn_dir, sn_tem, sn_sal 
     64      INTEGER  ::   ios 
    6465      !!---------------------------------------------------------------------- 
    6566      ! 
     
    7677      sn_tem = FLD_N( 'temperature',  -1.  , 'votemper',  .false.   , .true.  ,  'monthly'  , ''       , ''       ) 
    7778      sn_sal = FLD_N( 'salinity'   ,  -1.  , 'vosaline',  .false.   , .true.  ,  'monthly'  , ''       , ''       ) 
    78  
    79       REWIND( numnam )              ! read in namlist namdta_tsd  
    80       READ  ( numnam, namtsd )  
     79  
     80      REWIND( numnam_ref )              ! Namelist namtsd in reference namelist :  
     81      READ  ( numnam_ref, namtsd, IOSTAT = ios, ERR = 901) 
     82901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtsd in reference namelist', lwp ) 
     83 
     84      REWIND( numnam_cfg )              ! Namelist namtsd in configuration namelist : Parameters of the run 
     85      READ  ( numnam_cfg, namtsd, IOSTAT = ios, ERR = 902 ) 
     86902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtsd in configuration namelist', lwp ) 
     87      WRITE ( numond, namtsd ) 
    8188 
    8289      IF( PRESENT( ld_tradmp ) )   ln_tsd_tradmp = .TRUE.     ! forces the initialization when tradmp is used 
  • branches/2013/dev_r3853_CNRS9_ConfSetting/NEMOGCM/NEMO/OPA_SRC/DYN/dynadv.F90

    r3294 r3875  
    8989      !!---------------------------------------------------------------------- 
    9090      INTEGER ::   ioptio 
     91      INTEGER  ::   ios                 ! Local integer output status for namelist read 
    9192      !! 
    9293      NAMELIST/namdyn_adv/ ln_dynadv_vec, ln_dynadv_cen2 , ln_dynadv_ubs 
    9394      !!---------------------------------------------------------------------- 
    9495 
    95       REWIND ( numnam )               ! Read Namelist namdyn_adv : momentum advection scheme 
    96       READ   ( numnam, namdyn_adv ) 
     96      REWIND( numnam_ref )              ! Namelist namdyn_adv in reference namelist : Momentum advection scheme 
     97      READ  ( numnam_ref, namdyn_adv, IOSTAT = ios, ERR = 901) 
     98901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namdyn_adv in reference namelist', lwp ) 
     99 
     100      REWIND( numnam_cfg )              ! Namelist namdyn_adv in configuration namelist : Momentum advection scheme 
     101      READ  ( numnam_cfg, namdyn_adv, IOSTAT = ios, ERR = 902 ) 
     102902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namdyn_adv in configuration namelist', lwp ) 
     103      WRITE ( numond, namdyn_adv ) 
    97104 
    98105      IF(lwp) THEN                    ! Namelist print 
  • branches/2013/dev_r3853_CNRS9_ConfSetting/NEMOGCM/NEMO/OPA_SRC/DYN/dynhpg.F90

    r3764 r3875  
    122122      !!---------------------------------------------------------------------- 
    123123      INTEGER ::   ioptio = 0      ! temporary integer 
     124      INTEGER ::   ios             ! Local integer output status for namelist read 
    124125      !! 
    125126      NAMELIST/namdyn_hpg/ ln_hpg_zco, ln_hpg_zps, ln_hpg_sco,     & 
     
    127128      !!---------------------------------------------------------------------- 
    128129      ! 
    129       REWIND( numnam )               ! Read Namelist namdyn_hpg 
    130       READ  ( numnam, namdyn_hpg ) 
     130      REWIND( numnam_ref )              ! Namelist namdyn_hpg in reference namelist : Hydrostatic pressure gradient 
     131      READ  ( numnam_ref, namdyn_hpg, IOSTAT = ios, ERR = 901) 
     132901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namdyn_hpg in reference namelist', lwp ) 
     133 
     134      REWIND( numnam_cfg )              ! Namelist namdyn_hpg in configuration namelist : Hydrostatic pressure gradient 
     135      READ  ( numnam_cfg, namdyn_hpg, IOSTAT = ios, ERR = 902 ) 
     136902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namdyn_hpg in configuration namelist', lwp ) 
     137      WRITE ( numond, namdyn_hpg ) 
    131138      ! 
    132139      IF(lwp) THEN                   ! Control print 
  • branches/2013/dev_r3853_CNRS9_ConfSetting/NEMOGCM/NEMO/OPA_SRC/DYN/dynnept.F90

    r3723 r3875  
    114114      NAMELIST/namdyn_nept/ ln_neptsimp, ln_smooth_neptvel, rn_tslse, rn_tslsp,      & 
    115115                            ln_neptramp, rn_htrmin, rn_htrmax 
     116      INTEGER  ::   ios 
    116117      !!---------------------------------------------------------------------- 
    117118      ! Define the (simplified) Neptune parameters 
    118119      ! ========================================== 
    119120 
    120       REWIND( numnam )                  ! Read Namelist namdyn_nept:  Simplified Neptune 
    121       READ  ( numnam, namdyn_nept ) 
     121      REWIND( numnam_ref )              ! Namelist namdyn_nept in reference namelist : Simplified Neptune 
     122      READ  ( numnam_ref, namdyn_nept, IOSTAT = ios, ERR = 901) 
     123901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namdyn_nept in reference namelist', lwp ) 
     124 
     125      REWIND( numnam_cfg )              ! Namelist namdyn_nept in reference namelist : Simplified Neptune 
     126      READ  ( numnam_cfg, namdyn_nept, IOSTAT = ios, ERR = 902 ) 
     127902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namdyn_nept in configuration namelist', lwp ) 
     128      WRITE ( numond, namdyn_nept ) 
    122129 
    123130      IF(lwp) THEN                      ! Control print 
  • branches/2013/dev_r3853_CNRS9_ConfSetting/NEMOGCM/NEMO/OPA_SRC/DYN/dynvor.F90

    r3802 r3875  
    710710      INTEGER ::   ioptio          ! local integer 
    711711      INTEGER ::   ji, jj, jk      ! dummy loop indices 
     712      INTEGER ::   ios             ! Local integer output status for namelist read 
    712713      !! 
    713714      NAMELIST/namdyn_vor/ ln_dynvor_ens, ln_dynvor_ene, ln_dynvor_mix, ln_dynvor_een 
    714715      !!---------------------------------------------------------------------- 
    715716 
    716       REWIND ( numnam )               ! Read Namelist namdyn_vor : Vorticity scheme options 
    717       READ   ( numnam, namdyn_vor ) 
     717      REWIND( numnam_ref )              ! Namelist namdyn_vor in reference namelist : Vorticity scheme options 
     718      READ  ( numnam_ref, namdyn_vor, IOSTAT = ios, ERR = 901) 
     719901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namdyn_vor in reference namelist', lwp ) 
     720 
     721      REWIND( numnam_cfg )              ! Namelist namdyn_vor in configuration namelist : Vorticity scheme options 
     722      READ  ( numnam_cfg, namdyn_vor, IOSTAT = ios, ERR = 902 ) 
     723902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namdyn_vor in configuration namelist', lwp ) 
     724      WRITE ( numond, namdyn_vor ) 
    718725 
    719726      IF(lwp) THEN                    ! Namelist print 
     
    721728         WRITE(numout,*) 'dyn_vor_init : vorticity term : read namelist and control the consistency' 
    722729         WRITE(numout,*) '~~~~~~~~~~~~' 
    723          WRITE(numout,*) '        Namelist namdyn_vor : oice of the vorticity term scheme' 
     730         WRITE(numout,*) '        Namelist namdyn_vor : choice of the vorticity term scheme' 
    724731         WRITE(numout,*) '           energy    conserving scheme                ln_dynvor_ene = ', ln_dynvor_ene 
    725732         WRITE(numout,*) '           enstrophy conserving scheme                ln_dynvor_ens = ', ln_dynvor_ens 
  • branches/2013/dev_r3853_CNRS9_ConfSetting/NEMOGCM/NEMO/OPA_SRC/FLO/floats.F90

    r3294 r3875  
    7878      !!---------------------------------------------------------------------- 
    7979      INTEGER :: jfl 
     80      INTEGER :: ios                 ! Local integer output status for namelist read 
    8081      ! 
    8182      NAMELIST/namflo/ jpnfl, jpnnewflo, ln_rstflo, nn_writefl, nn_stockfl, ln_argo, ln_flork4, ln_ariane, ln_flo_ascii 
     
    8889      IF(lwp) WRITE(numout,*) '~~~~~~~' 
    8990 
    90       REWIND( numnam )              ! Namelist namflo : floats 
    91       READ  ( numnam, namflo ) 
     91      REWIND( numnam_ref )              ! Namelist namflo in reference namelist : Floats 
     92      READ  ( numnam_ref, namflo, IOSTAT = ios, ERR = 901) 
     93901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namflo in reference namelist', lwp ) 
     94 
     95      REWIND( numnam_cfg )              ! Namelist namflo in configuration namelist : Floats 
     96      READ  ( numnam_cfg, namflo, IOSTAT = ios, ERR = 902 ) 
     97902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namflo in configuration namelist', lwp ) 
     98      WRITE ( numond, namflo ) 
    9299      ! 
    93100      IF(lwp) THEN                  ! control print 
  • branches/2013/dev_r3853_CNRS9_ConfSetting/NEMOGCM/NEMO/OPA_SRC/ICB/icbini.F90

    r3785 r3875  
    344344      !!---------------------------------------------------------------------- 
    345345      INTEGER  ::   jn      ! dummy loop indices 
     346      INTEGER  ::   ios     ! Local integer output status for namelist read 
    346347      REAL(wp) ::   zfact   ! local scalar 
    347348      ! 
     
    359360      sn_icb = FLD_N( 'calving' ,    -1     , 'calving'  ,  .TRUE.    , .TRUE. ,   'yearly'  , ''       , ''         ) 
    360361 
    361       REWIND( numnam )              ! Namelist namrun : iceberg parameters 
    362       READ  ( numnam, namberg ) 
     362      REWIND( numnam_ref )              ! Namelist namberg in reference namelist : Iceberg parameters 
     363      READ  ( numnam_ref, namberg, IOSTAT = ios, ERR = 901) 
     364901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namberg in reference namelist', lwp ) 
     365 
     366      REWIND( numnam_cfg )              ! Namelist namberg in configuration namelist : Iceberg parameters 
     367      READ  ( numnam_cfg, namberg, IOSTAT = ios, ERR = 902 ) 
     368902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namberg in configuration namelist', lwp ) 
     369      WRITE ( numond, namberg ) 
    363370       
    364371      IF( .NOT. ln_icebergs ) THEN   ! no icebergs 
    365372         IF(lwp) THEN 
    366373            WRITE(numout,*) 
    367             WRITE(numout,*) 'icb_nam :  ln_icebergs = F , NO icebergs used' 
     374            WRITE(numout,*) 'icbini :   Namelist namberg ln_icebergs = F , NO icebergs used' 
    368375            WRITE(numout,*) '~~~~~~~~ ' 
    369376         ENDIF 
  • branches/2013/dev_r3853_CNRS9_ConfSetting/NEMOGCM/NEMO/OPA_SRC/IOM/in_out_manager.F90

    r3680 r3875  
    107107   !!                        logical units 
    108108   !!---------------------------------------------------------------------- 
    109    INTEGER ::   numstp      =   -1      !: logical unit for time step 
    110    INTEGER ::   numtime     =   -1      !: logical unit for timing 
    111    INTEGER ::   numout      =    6      !: logical unit for output print 
    112    INTEGER ::   numnam      =   -1      !: logical unit for namelist 
    113    INTEGER ::   numnam_ice  =   -1      !: logical unit for ice namelist 
    114    INTEGER ::   numevo_ice  =   -1      !: logical unit for ice variables (temp. evolution) 
    115    INTEGER ::   numsol      =   -1      !: logical unit for solver statistics 
    116    INTEGER ::   numdct_in   =   -1      !: logical unit for transports computing 
    117    INTEGER ::   numdct_vol  =   -1      !: logical unit for voulume transports output 
    118    INTEGER ::   numdct_heat =   -1      !: logical unit for heat    transports output 
    119    INTEGER ::   numdct_salt =   -1      !: logical unit for salt    transports output 
    120    INTEGER ::   numfl      =   -1      !: logical unit for floats ascii output 
    121    INTEGER ::   numflo     =   -1      !: logical unit for floats ascii output 
     109   INTEGER ::   numstp          =   -1      !: logical unit for time step 
     110   INTEGER ::   numtime         =   -1      !: logical unit for timing 
     111   INTEGER ::   numout          =    6      !: logical unit for output print 
     112   INTEGER ::   numnam_ref      =   -1      !: logical unit for reference namelist 
     113   INTEGER ::   numnam_cfg      =   -1      !: logical unit for configuration specific namelist 
     114   INTEGER ::   numond          =    7      !: logical unit for Output Namelist Dynamics 
     115   INTEGER ::   numnam_ice_ref  =   -1      !: logical unit for ice reference namelist 
     116   INTEGER ::   numnam_ice_cfg  =   -1      !: logical unit for ice reference namelist 
     117   INTEGER ::   numoni          =    8      !: logical unit for Output Namelist Ice 
     118   INTEGER ::   numevo_ice      =   -1      !: logical unit for ice variables (temp. evolution) 
     119   INTEGER ::   numsol          =   -1      !: logical unit for solver statistics 
     120   INTEGER ::   numdct_in       =   -1      !: logical unit for transports computing 
     121   INTEGER ::   numdct_vol      =   -1      !: logical unit for voulume transports output 
     122   INTEGER ::   numdct_heat     =   -1      !: logical unit for heat    transports output 
     123   INTEGER ::   numdct_salt     =   -1      !: logical unit for salt    transports output 
     124   INTEGER ::   numfl           =   -1      !: logical unit for floats ascii output 
     125   INTEGER ::   numflo          =   -1      !: logical unit for floats ascii output 
    122126 
    123127   !!---------------------------------------------------------------------- 
  • branches/2013/dev_r3853_CNRS9_ConfSetting/NEMOGCM/NEMO/OPA_SRC/IOM/restart.F90

    r3680 r3875  
    156156         WRITE(numout,*) 
    157157         SELECT CASE ( jprstlib ) 
    158          CASE ( jpnf90    )   ;   WRITE(numout,*) 'rst_read : read oce NetCDF restart file' 
     158         CASE ( jpnf90    )   ;   WRITE(numout,*) 'rst_read : read oce NetCDF restart file ',TRIM(cn_ocerst_in)//'.nc' 
    159159         CASE ( jprstdimg )   ;   WRITE(numout,*) 'rst_read : read oce binary restart file' 
    160160         END SELECT 
  • branches/2013/dev_r3853_CNRS9_ConfSetting/NEMOGCM/NEMO/OPA_SRC/LBC/lib_mpp.F90

    r3799 r3875  
    2828   !!   ctl_warn   : initialization, namelist read, and parameters control 
    2929   !!   ctl_opn    : Open file and check if required file is available. 
    30    !!   get_unit    : give the index of an unused logical unit 
     30   !!   ctl_nam    : Prints informations when an error occurs while reading a namelist 
     31   !!   get_unit   : give the index of an unused logical unit 
    3132   !!---------------------------------------------------------------------- 
    3233#if   defined key_mpp_mpi 
     
    6162   IMPLICIT NONE 
    6263   PRIVATE 
    63  
    64    PUBLIC   ctl_stop, ctl_warn, get_unit, ctl_opn 
     64    
     65   PUBLIC   ctl_stop, ctl_warn, get_unit, ctl_opn, ctl_nam 
    6566   PUBLIC   mynode, mppstop, mppsync, mpp_comm_free 
    6667   PUBLIC   mpp_ini_north, mpp_lbc_north, mpp_lbc_north_e 
     
    225226 
    226227 
    227    FUNCTION mynode( ldtxt, kumnam, kstop, localComm ) 
     228   FUNCTION mynode( ldtxt, kumnam_ref , kumnam_cfg , kumond , kstop, localComm ) 
    228229      !!---------------------------------------------------------------------- 
    229230      !!                  ***  routine mynode  *** 
     
    232233      !!---------------------------------------------------------------------- 
    233234      CHARACTER(len=*),DIMENSION(:), INTENT(  out) ::   ldtxt 
    234       INTEGER                      , INTENT(in   ) ::   kumnam       ! namelist logical unit 
    235       INTEGER                      , INTENT(inout) ::   kstop        ! stop indicator 
     235      INTEGER                      , INTENT(in   ) ::   kumnam_ref     ! logical unit for reference namelist 
     236      INTEGER                      , INTENT(in   ) ::   kumnam_cfg     ! logical unit for configuration namelist 
     237      INTEGER                      , INTENT(in   ) ::   kumond         ! logical unit for namelist output 
     238      INTEGER                      , INTENT(inout) ::   kstop          ! stop indicator 
    236239      INTEGER, OPTIONAL            , INTENT(in   ) ::   localComm 
    237240      ! 
    238       INTEGER ::   mynode, ierr, code, ji, ii 
     241      INTEGER ::   mynode, ierr, code, ji, ii, ios 
    239242      LOGICAL ::   mpi_was_called 
    240243      ! 
     
    248251      ! 
    249252      jpni = -1; jpnj = -1; jpnij = -1 
    250       REWIND( kumnam )               ! Namelist namrun : parameters of the run 
    251       READ  ( kumnam, nammpp ) 
     253 
     254      REWIND( kumnam_ref )              ! Namelist nammpp in reference namelist: mpi variables 
     255      READ  ( kumnam_ref, nammpp, IOSTAT = ios, ERR = 901) 
     256901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nammpp in reference namelist', lwp ) 
     257 
     258      REWIND( kumnam_cfg )              ! Namelist nammpp in configuration namelist: mpi variables 
     259      READ  ( kumnam_cfg, nammpp, IOSTAT = ios, ERR = 902 ) 
     260902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nammpp in configuration namelist', lwp ) 
     261      WRITE(kumond, nammpp)       
     262 
    252263      !                              ! control print 
    253264      WRITE(ldtxt(ii),*) '   Namelist nammpp'                                                     ;   ii = ii + 1 
     
    34553466   END FUNCTION lib_mpp_alloc 
    34563467 
    3457    FUNCTION mynode( ldtxt, kumnam, kstop, localComm ) RESULT (function_value) 
     3468   FUNCTION mynode( ldtxt, kumnam_ref, knumnam_cfg, kstop, localComm ) RESULT (function_value) 
    34583469      INTEGER, OPTIONAL            , INTENT(in   ) ::   localComm 
    34593470      CHARACTER(len=*),DIMENSION(:) ::   ldtxt 
    3460       INTEGER ::   kumnam, kstop 
     3471      INTEGER ::   kumnam_ref, knumnam_cfg , kstop 
    34613472      IF( PRESENT( localComm ) .OR. .NOT.PRESENT( localComm ) )   function_value = 0 
    34623473      IF( .FALSE. )   ldtxt(:) = 'never done' 
     
    36373648 
    36383649   !!---------------------------------------------------------------------- 
    3639    !!   All cases:         ctl_stop, ctl_warn, get_unit, ctl_opn   routines 
     3650   !!   All cases:         ctl_stop, ctl_warn, get_unit, ctl_opn, ctl_nam   routines 
    36403651   !!---------------------------------------------------------------------- 
    36413652 
     
    37803791   END SUBROUTINE ctl_opn 
    37813792 
     3793   SUBROUTINE ctl_nam ( kios, cdnam, ldwp ) 
     3794      !!---------------------------------------------------------------------- 
     3795      !!                  ***  ROUTINE ctl_nam  *** 
     3796      !! 
     3797      !! ** Purpose :   Informations when error while reading a namelist 
     3798      !! 
     3799      !! ** Method  :   Fortan open 
     3800      !!---------------------------------------------------------------------- 
     3801      INTEGER          , INTENT(inout) ::   kios      ! IO status after reading the namelist 
     3802      CHARACTER(len=*) , INTENT(in   ) ::   cdnam     ! group name of namelist for which error occurs 
     3803      CHARACTER(len=4)                 ::   clios     ! string to convert iostat in character for print 
     3804      LOGICAL          , INTENT(in   ) ::   ldwp      ! boolean term for print 
     3805      !!---------------------------------------------------------------------- 
     3806 
     3807      !  
     3808      ! ---------------- 
     3809      WRITE (clios, '(I4.0)') kios 
     3810      IF( kios < 0 ) THEN          
     3811         CALL ctl_warn( 'W A R N I N G:  end of record or file while reading namelist ' & 
     3812 &           // TRIM(cdnam) // ' iostat = ' // TRIM(clios) ) 
     3813      ENDIF 
     3814 
     3815      IF( kios > 0 ) THEN 
     3816         CALL ctl_stop( 'E R R O R :   misspelled variable in namelist ' & 
     3817 &           // TRIM(cdnam) // ' iostat = ' // TRIM(clios) ) 
     3818      ENDIF 
     3819      kios = 0 
     3820      RETURN 
     3821       
     3822   END SUBROUTINE ctl_nam 
    37823823 
    37833824   INTEGER FUNCTION get_unit() 
  • branches/2013/dev_r3853_CNRS9_ConfSetting/NEMOGCM/NEMO/OPA_SRC/LBC/mppini_2.h90

    r3818 r3875  
    4545      INTEGER ::  inum                        ! temporary logical unit 
    4646      INTEGER ::  idir                        ! temporary integers 
     47      INTEGER ::   ios                        ! Local integer output status for namelist read 
    4748      INTEGER ::   & 
    4849         ii, ij, ifreq, il1, il2,          &  ! temporary integers 
     
    7778      !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt 
    7879      !!---------------------------------------------------------------------- 
    79        
    80       REWIND ( numnam )              ! Read Namelist namzgr : vertical coordinate' 
    81       READ   ( numnam, namzgr ) 
     80 
     81      REWIND( numnam_ref )              ! Namelist namzgr in reference namelist : Vertical coordinate 
     82      READ  ( numnam_ref, namzgr, IOSTAT = ios, ERR = 901) 
     83901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namzgr in reference namelist', lwp ) 
     84 
     85      REWIND( numnam_cfg )              ! Namelist namzgr in configuration namelist : Vertical coordinate 
     86      READ  ( numnam_cfg, namzgr, IOSTAT = ios, ERR = 902 ) 
     87902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namzgr in configuration namelist', lwp ) 
     88      WRITE ( numond, namzgr ) 
    8289 
    8390      IF(lwp)WRITE(numout,*) 
  • branches/2013/dev_r3853_CNRS9_ConfSetting/NEMOGCM/NEMO/OPA_SRC/LDF/ldfdyn.F90

    r3634 r3875  
    6363      !!---------------------------------------------------------------------- 
    6464      INTEGER ::   ioptio         ! ??? 
     65      INTEGER ::   ios            ! Local : output status for namelist read 
    6566      LOGICAL ::   ll_print = .FALSE.    ! Logical flag for printing viscosity coef. 
    6667      !!  
     
    7374   !!---------------------------------------------------------------------- 
    7475 
    75       REWIND( numnam )                  ! Read Namelist namdyn_ldf : Lateral physics 
    76       READ  ( numnam, namdyn_ldf ) 
     76      REWIND( numnam_ref )              ! Namelist namdyn_ldf in reference namelist : Lateral physics 
     77      READ  ( numnam_ref, namdyn_ldf, IOSTAT = ios, ERR = 901) 
     78901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namdyn_ldf in reference namelist', lwp ) 
     79 
     80      REWIND( numnam_cfg )              ! Namelist namdyn_ldf in configuration namelist : Lateral physics 
     81      READ  ( numnam_cfg, namdyn_ldf, IOSTAT = ios, ERR = 902 ) 
     82902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namdyn_ldf in configuration namelist', lwp ) 
     83      WRITE ( numond, namdyn_ldf ) 
    7784 
    7885      IF(lwp) THEN                      ! Parameter print 
     
    8087         WRITE(numout,*) 'ldf_dyn : lateral momentum physics' 
    8188         WRITE(numout,*) '~~~~~~~' 
    82          WRITE(numout,*) '   Namelist nam_dynldf : set lateral mixing parameters' 
     89         WRITE(numout,*) '   Namelist namdyn_ldf : set lateral mixing parameters' 
    8390         WRITE(numout,*) '      laplacian operator                      ln_dynldf_lap   = ', ln_dynldf_lap 
    8491         WRITE(numout,*) '      bilaplacian operator                    ln_dynldf_bilap = ', ln_dynldf_bilap 
  • branches/2013/dev_r3853_CNRS9_ConfSetting/NEMOGCM/NEMO/OPA_SRC/LDF/ldftra.F90

    r3634 r3875  
    6262      !!---------------------------------------------------------------------- 
    6363      INTEGER ::   ioptio               ! temporary integer 
     64      INTEGER ::   ios                  ! temporary integer 
    6465      LOGICAL ::   ll_print = .FALSE.   ! =T print eddy coef. in numout 
    6566      !!  
     
    7677      ! ============================================= 
    7778     
    78       REWIND( numnam )                  ! Read Namelist namtra_ldf : Lateral physics on tracers 
    79       READ  ( numnam, namtra_ldf ) 
     79 
     80      REWIND( numnam_ref )              ! Namelist namtra_ldf in reference namelist : Lateral physics on tracers 
     81      READ  ( numnam_ref, namtra_ldf, IOSTAT = ios, ERR = 901) 
     82901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtra_ldf in reference namelist', lwp ) 
     83 
     84      REWIND( numnam_cfg )              ! Namelist namtra_ldf in configuration namelist : Lateral physics on tracers 
     85      READ  ( numnam_cfg, namtra_ldf, IOSTAT = ios, ERR = 902 ) 
     86902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtra_ldf in configuration namelist', lwp ) 
     87      WRITE ( numond, namtra_ldf ) 
    8088 
    8189      IF(lwp) THEN                      ! control print 
  • branches/2013/dev_r3853_CNRS9_ConfSetting/NEMOGCM/NEMO/OPA_SRC/OBC/obcini.F90

    r2715 r3875  
    5757      !! 
    5858      INTEGER  ::   ji, jj, istop , inumfbc 
     59      INTEGER  ::   ios                     ! Local integer output status for namelist read 
    5960      INTEGER, DIMENSION(4) ::   icorner 
    6061      REAL(wp), DIMENSION(2) ::   ztestmask 
     
    6667      !!---------------------------------------------------------------------- 
    6768 
    68       REWIND( numnam )              ! Namelist namobc : open boundaries 
    69       READ  ( numnam, namobc ) 
     69      REWIND( numnam_ref )              ! Namelist namobc in reference namelist : Open boundaries 
     70      READ  ( numnam_ref, namobc, IOSTAT = ios, ERR = 901) 
     71901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namobc in reference namelist', lwp ) 
     72 
     73      REWIND( numnam_cfg )              ! Namelist namobc in configuration namelist : Open boundaries 
     74      READ  ( numnam_cfg, namobc, IOSTAT = ios, ERR = 902 ) 
     75902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namobc in configuration namelist', lwp ) 
     76      WRITE ( numond, namobc ) 
    7077 
    7178      ! convert DOCTOR namelist name into the OLD names 
  • branches/2013/dev_r3853_CNRS9_ConfSetting/NEMOGCM/NEMO/OPA_SRC/OBS/diaobs.F90

    r3651 r3875  
    197197      INTEGER :: ji 
    198198      INTEGER :: jset 
     199      INTEGER :: ios                 ! Local integer output status for namelist read 
    199200      LOGICAL :: lmask(MaxNumFiles), ll_u3d, ll_v3d 
    200201 
     
    262263 
    263264      ! Read Namelist namobs : control observation diagnostics 
    264       REWIND( numnam ) 
    265       READ  ( numnam, namobs ) 
     265      REWIND( numnam_ref )              ! Namelist namobs in reference namelist : Diagnostic: control observation 
     266      READ  ( numnam_ref, namobs, IOSTAT = ios, ERR = 901) 
     267901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namobs in reference namelist', lwp ) 
     268 
     269      REWIND( numnam_cfg )              ! Namelist namobs in configuration namelist : Diagnostic: control observation 
     270      READ  ( numnam_cfg, namobs, IOSTAT = ios, ERR = 902 ) 
     271902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namobs in configuration namelist', lwp ) 
     272      WRITE ( numond, namobs ) 
    266273 
    267274      ! Count number of files for each type 
  • branches/2013/dev_r3853_CNRS9_ConfSetting/NEMOGCM/NEMO/OPA_SRC/SBC/albedo.F90

    r3625 r3875  
    199199      !! ** Method  :   Read the namelist namsbc_alb 
    200200      !!---------------------------------------------------------------------- 
     201      INTEGER  ::   ios                 ! Local integer output status for namelist read 
    201202      NAMELIST/namsbc_alb/ rn_cloud, rn_albice, rn_alphd, rn_alphdi, rn_alphc 
    202203      !!---------------------------------------------------------------------- 
     
    204205      albd_init = 1                     ! indicate that the initialization has been done 
    205206      ! 
    206       REWIND( numnam )                  ! Read Namelist namsbc_alb : albedo parameters 
    207       READ  ( numnam, namsbc_alb ) 
     207      REWIND( numnam_ref )              ! Namelist namsbc_alb in reference namelist : Albedo parameters 
     208      READ  ( numnam_ref, namsbc_alb, IOSTAT = ios, ERR = 901) 
     209901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc_alb in reference namelist', lwp ) 
     210 
     211      REWIND( numnam_cfg )              ! Namelist namsbc_alb in configuration namelist : Albedo parameters 
     212      READ  ( numnam_cfg, namsbc_alb, IOSTAT = ios, ERR = 902 ) 
     213902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc_alb in configuration namelist', lwp ) 
     214      WRITE ( numond, namsbc_alb ) 
    208215      ! 
    209216      IF(lwp) THEN                      ! Control print 
  • branches/2013/dev_r3853_CNRS9_ConfSetting/NEMOGCM/NEMO/OPA_SRC/SBC/cyclone.F90

    r3680 r3875  
    103103         sn_tc = FLD_N( 'tc_track',     6     ,  'tc'     ,  .true.    , .false. ,   'yearly'  , ''       , ''         ) 
    104104         ! 
    105          !         REWIND( numnam )                    ! ... read in namlist namsbc_core 
    106          !         READ  ( numnam, namsbc_tc ) 
    107          ! 
     105         !  Namelist is read in namsbc_core 
    108106         ! set sf structure 
    109107         ALLOCATE( sf(1), STAT=ierror ) 
  • branches/2013/dev_r3853_CNRS9_ConfSetting/NEMOGCM/NEMO/OPA_SRC/SBC/sbcana.F90

    r3625 r3875  
    6464      INTEGER, INTENT(in) ::   kt       ! ocean time step 
    6565      ! 
     66      INTEGER  ::   ios                   ! Local integer output status for namelist read 
    6667      REAL(wp) ::   zfacto                ! local scalar 
    6768      REAL(wp) ::   zrhoa  = 1.22_wp      ! Air density kg/m3 
     
    7475      IF( kt == nit000 ) THEN 
    7576         ! 
    76          REWIND( numnam )                    ! Read Namelist namsbc : surface fluxes 
    77          READ  ( numnam, namsbc_ana ) 
     77         REWIND( numnam_ref )              ! Namelist namsbc_ana in reference namelist : Analytical surface fluxes 
     78         READ  ( numnam_ref, namsbc_ana, IOSTAT = ios, ERR = 901) 
     79901      IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc_ana in reference namelist', lwp ) 
     80 
     81         REWIND( numnam_cfg )              ! Namelist namsbc_ana in configuration namelist : Analytical surface fluxes 
     82         READ  ( numnam_cfg, namsbc_ana, IOSTAT = ios, ERR = 902 ) 
     83902      IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc_ana in configuration namelist', lwp ) 
     84         WRITE ( numond, namsbc_ana ) 
    7885         ! 
    7986         IF(lwp) WRITE(numout,*)' ' 
  • branches/2013/dev_r3853_CNRS9_ConfSetting/NEMOGCM/NEMO/OPA_SRC/SBC/sbcapr.F90

    r3795 r3875  
    6565      !! 
    6666      INTEGER            ::   ierror  ! local integer  
     67      INTEGER            ::   ios     ! Local integer output status for namelist read 
    6768      !! 
    6869      CHARACTER(len=100) ::  cn_dir   ! Root directory for location of ssr files 
     
    8384         cn_dir  = './'          ! directory in which the Patm data are  
    8485 
    85          REWIND( numnam )                             !* read in namlist namsbc_apr 
    86          READ  ( numnam, namsbc_apr )  
     86         REWIND( numnam_ref )              ! Namelist namsbc_apr in reference namelist : File for atmospheric pressure forcing 
     87         READ  ( numnam_ref, namsbc_apr, IOSTAT = ios, ERR = 901) 
     88901      IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc_apr in reference namelist', lwp ) 
     89 
     90         REWIND( numnam_cfg )              ! Namelist namsbc_apr in configuration namelist : File for atmospheric pressure forcing 
     91         READ  ( numnam_cfg, namsbc_apr, IOSTAT = ios, ERR = 902 ) 
     92902      IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc_apr in configuration namelist', lwp ) 
     93         WRITE ( numond, namsbc_apr ) 
    8794         ! 
    8895         ALLOCATE( sf_apr(1), STAT=ierror )           !* allocate and fill sf_sst (forcing structure) with sn_sst 
  • branches/2013/dev_r3853_CNRS9_ConfSetting/NEMOGCM/NEMO/OPA_SRC/SBC/sbcblk_clio.F90

    r3625 r3875  
    124124      INTEGER, INTENT( in  ) ::   kt   ! ocean time step 
    125125      !! 
    126       INTEGER  ::   ifpr, jfpr   ! dummy indices 
     126      INTEGER  ::   ifpr, jfpr                   ! dummy indices 
    127127      INTEGER  ::   ierr0, ierr1, ierr2, ierr3   ! return error code 
     128      INTEGER  ::   ios                          ! Local integer output status for namelist read 
    128129      !! 
    129130      CHARACTER(len=100) ::  cn_dir                            !   Root directory for location of CLIO files 
     
    153154         sn_prec = FLD_N( 'precip' ,    -1     , 'precip' ,  .true.    , .false. ,   'yearly'  , ''       , ''       )  
    154155 
    155          REWIND( numnam )                    ! ... read in namlist namsbc_clio 
    156          READ  ( numnam, namsbc_clio ) 
     156         REWIND( numnam_ref )              ! Namelist namsbc_clio in reference namelist : CLIO files 
     157         READ  ( numnam_ref, namsbc_clio, IOSTAT = ios, ERR = 901) 
     158901      IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc_clio in reference namelist', lwp ) 
     159 
     160         REWIND( numnam_cfg )              ! Namelist namsbc_clio in configuration namelist : CLIO files 
     161         READ  ( numnam_cfg, namsbc_clio, IOSTAT = ios, ERR = 902 ) 
     162902      IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc_clio in configuration namelist', lwp ) 
     163         WRITE ( numond, namsbc_clio ) 
    157164 
    158165         ! store namelist information in an array 
  • branches/2013/dev_r3853_CNRS9_ConfSetting/NEMOGCM/NEMO/OPA_SRC/SBC/sbcblk_core.F90

    r3772 r3875  
    122122      INTEGER  ::   ifpr     ! dummy loop indice 
    123123      INTEGER  ::   jfld     ! dummy loop arguments 
     124      INTEGER  ::   ios      ! Local integer output status for namelist read 
    124125      !! 
    125126      CHARACTER(len=100) ::  cn_dir   !   Root directory for location of core files 
     
    151152         sn_tdif = FLD_N( 'taudif' ,    24     , 'taudif' ,  .true.    , .false. ,   'yearly'  , ''       , ''       ) 
    152153         ! 
    153          REWIND( numnam )                          ! read in namlist namsbc_core 
    154          READ  ( numnam, namsbc_core ) 
     154 
     155         REWIND( numnam_ref )              ! Namelist namsbc_core in reference namelist : CORE bulk parameters 
     156         READ  ( numnam_ref, namsbc_core, IOSTAT = ios, ERR = 901) 
     157901      IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc_core in reference namelist', lwp ) 
     158 
     159         REWIND( numnam_cfg )              ! Namelist namsbc_core in configuration namelist : CORE bulk parameters 
     160         READ  ( numnam_cfg, namsbc_core, IOSTAT = ios, ERR = 902 ) 
     161902      IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc_core in configuration namelist', lwp ) 
     162         WRITE ( numond, namsbc_core ) 
    155163         !                                         ! check: do we plan to use ln_dm2dc with non-daily forcing? 
    156164         IF( ln_dm2dc .AND. sn_qsr%nfreqh /= 24 )   &  
  • branches/2013/dev_r3853_CNRS9_ConfSetting/NEMOGCM/NEMO/OPA_SRC/SBC/sbcblk_mfs.F90

    r3625 r3875  
    104104      INTEGER  :: ifpr     ! dummy loop indice 
    105105      INTEGER  :: jj,ji    ! dummy loop arguments 
     106      INTEGER  ::   ios    ! Local integer output status for namelist read 
    106107      REAL(wp) :: act_hour 
    107108      !!-------------------------------------------------------------------- 
     
    147148            sn_prec = FLD_N( 'precip_cmap' ,  -1   ,  'precip'  ,  .true.    ,  .true. ,   'yearly'  , ''       , ''         ) 
    148149            ! 
    149             REWIND( numnam )                    ! ... read in namlist namsbc_mfs 
    150             READ  ( numnam, namsbc_mfs ) 
     150 
     151            REWIND( numnam_ref )              ! Namelist namsbc_msf in reference namelist : MFS files 
     152            READ  ( numnam_ref, namsbc_mfs, IOSTAT = ios, ERR = 901) 
     153901         IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc_mfs in reference namelist', lwp ) 
     154 
     155            REWIND( numnam_cfg )              ! Namelist namsbc_msf in configuration namelist : MFS files 
     156            READ  ( numnam_cfg, namsbc_mfs, IOSTAT = ios, ERR = 902 ) 
     157902         IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc_mfs in configuration namelist', lwp ) 
     158            WRITE ( numond, namsbc_mfs ) 
    151159            ! 
    152160            ! store namelist information in an array 
  • branches/2013/dev_r3853_CNRS9_ConfSetting/NEMOGCM/NEMO/OPA_SRC/SBC/sbccpl.F90

    r3680 r3875  
    221221      !! 
    222222      INTEGER ::   jn   ! dummy loop index 
     223      INTEGER ::   ios  ! Local integer output status for namelist read 
    223224      REAL(wp), POINTER, DIMENSION(:,:) ::   zacs, zaos 
    224225      !! 
     
    258259      sn_rcv_co2    = FLD_C( 'none'                ,    'no'    ,     ''      ,         ''          ,   ''    ) 
    259260 
    260       REWIND( numnam )                    ! ... read namlist namsbc_cpl 
    261       READ  ( numnam, namsbc_cpl ) 
     261      REWIND( numnam_ref )              ! Namelist namsbc_cpl in reference namelist : Variables for OASIS coupling 
     262      READ  ( numnam_ref, namsbc_cpl, IOSTAT = ios, ERR = 901) 
     263901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc_cpl in reference namelist', lwp ) 
     264 
     265      REWIND( numnam_cfg )              ! Namelist namsbc_cpl in configuration namelist : Variables for OASIS coupling 
     266      READ  ( numnam_cfg, namsbc_cpl, IOSTAT = ios, ERR = 902 ) 
     267902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc_cpl in configuration namelist', lwp ) 
     268      WRITE ( numond, namsbc_cpl ) 
    262269 
    263270      IF(lwp) THEN                        ! control print 
  • branches/2013/dev_r3853_CNRS9_ConfSetting/NEMOGCM/NEMO/OPA_SRC/SBC/sbcflx.F90

    r3625 r3875  
    7777      INTEGER  ::   ji, jj, jf            ! dummy indices 
    7878      INTEGER  ::   ierror                ! return error code 
     79      INTEGER  ::   ios                   ! Local integer output status for namelist read 
    7980      REAL(wp) ::   zfact                 ! temporary scalar 
    8081      REAL(wp) ::   zrhoa  = 1.22         ! Air density kg/m3 
     
    100101         sn_emp  = FLD_N(  'emp'  ,    24     ,  'emp'     ,  .false.   , .false. ,   'yearly'  , ''       , ''        ) 
    101102         ! 
    102          REWIND ( numnam )                         ! read in namlist namflx 
    103          READ   ( numnam, namsbc_flx )  
     103         REWIND( numnam_ref )              ! Namelist namsbc_flx in reference namelist : Files for fluxes 
     104         READ  ( numnam_ref, namsbc_flx, IOSTAT = ios, ERR = 901) 
     105901      IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc_flx in reference namelist', lwp ) 
     106 
     107         REWIND( numnam_cfg )              ! Namelist namsbc_flx in configuration namelist : Files for fluxes 
     108         READ  ( numnam_cfg, namsbc_flx, IOSTAT = ios, ERR = 902 ) 
     109902      IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc_flx in configuration namelist', lwp ) 
     110         WRITE ( numond, namsbc_flx )  
    104111         ! 
    105112         !                                         ! check: do we plan to use ln_dm2dc with non-daily forcing? 
  • branches/2013/dev_r3853_CNRS9_ConfSetting/NEMOGCM/NEMO/OPA_SRC/SBC/sbcice_cice.F90

    r3625 r3875  
    759759         sn_bot5 = FLD_N( 'botmeltn5_1m' ,    -1.    ,  'botmeltn5' ,  .true.    , .true.  ,  ' yearly'  , ''       , ''         ) 
    760760 
    761 !         REWIND ( numnam )               ! ... at some point might read in from NEMO namelist? 
    762 !         READ   ( numnam, namsbc_cice )  
     761! ... at some point might read in from NEMO namelist? 
     762!!$      REWIND( numnam_ref )              ! Namelist namsbc_cice in reference namelist :  
     763!!$      READ  ( numnam_ref, namsbc_cice, IOSTAT = ios, ERR = 901) 
     764!!$901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc_cice in reference namelist', lwp ) 
     765!!$ 
     766!!$      REWIND( numnam_cfg )              ! Namelist namsbc_cice in configuration namelist : Parameters of the run 
     767!!$      READ  ( numnam_cfg, namsbc_cice, IOSTAT = ios, ERR = 902 ) 
     768!!$902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc_cice in configuration namelist', lwp ) 
     769!!$      WRITE ( numond, namsbc_cice ) 
    763770 
    764771         ! store namelist information in an array 
  • branches/2013/dev_r3853_CNRS9_ConfSetting/NEMOGCM/NEMO/OPA_SRC/SBC/sbcice_if.F90

    r3625 r3875  
    5959      INTEGER  ::   ji, jj     ! dummy loop indices 
    6060      INTEGER  ::   ierror     ! return error code 
     61      INTEGER  ::   ios        ! Local integer output status for namelist read 
    6162      REAL(wp) ::   ztrp, zsice, zt_fzp, zfr_obs 
    6263      REAL(wp) ::   zqri, zqrj, zqrp, zqi 
     
    7677         sn_ice = FLD_N('ice_cover',    -1    ,  'ice_cov' ,  .true.    , .true. ,   'yearly'  , ''       , ''         ) 
    7778 
    78          REWIND ( numnam )               ! ... read in namlist namiif 
    79          READ   ( numnam, namsbc_iif ) 
     79         REWIND( numnam_ref )              ! Namelist namsbc_iif in reference namelist : Ice if file 
     80         READ  ( numnam_ref, namsbc_iif, IOSTAT = ios, ERR = 901) 
     81901      IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc_iif in reference namelist', lwp ) 
     82 
     83         REWIND( numnam_cfg )              ! Namelist Namelist namsbc_iif in configuration namelist : Ice if file 
     84         READ  ( numnam_cfg, namsbc_iif, IOSTAT = ios, ERR = 902 ) 
     85902      IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc_iif in configuration namelist', lwp ) 
     86         WRITE ( numond, namsbc_iif ) 
    8087 
    8188         ALLOCATE( sf_ice(1), STAT=ierror ) 
  • branches/2013/dev_r3853_CNRS9_ConfSetting/NEMOGCM/NEMO/OPA_SRC/SBC/sbcmod.F90

    r3764 r3875  
    8787         &             ln_blk_mfs, ln_apr_dyn, nn_ice,  nn_ice_embd, ln_dm2dc   , ln_rnf,   & 
    8888         &             ln_ssr    , nn_fwb    , ln_cdgw , ln_wave , ln_sdw 
     89      INTEGER  ::   ios 
    8990      !!---------------------------------------------------------------------- 
    9091 
     
    9596      ENDIF 
    9697 
    97       REWIND( numnam )           ! Read Namelist namsbc 
    98       READ  ( numnam, namsbc ) 
     98      REWIND( numnam_ref )              ! Namelist namsbc in reference namelist : Surface boundary 
     99      READ  ( numnam_ref, namsbc, IOSTAT = ios, ERR = 901) 
     100901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc in reference namelist', lwp ) 
     101 
     102      REWIND( numnam_cfg )              ! Namelist namsbc in configuration namelist : Parameters of the run 
     103      READ  ( numnam_cfg, namsbc, IOSTAT = ios, ERR = 902 ) 
     104902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc in configuration namelist', lwp ) 
     105      WRITE ( numond, namsbc ) 
    99106 
    100107      !                          ! overwrite namelist parameter using CPP key information 
  • branches/2013/dev_r3853_CNRS9_ConfSetting/NEMOGCM/NEMO/OPA_SRC/SBC/sbcrnf.F90

    r3832 r3875  
    245245      INTEGER           ::   ji, jj, jk    ! dummy loop indices 
    246246      INTEGER           ::   ierror, inum  ! temporary integer 
     247      INTEGER           ::   ios           ! Local integer output status for namelist read 
    247248      ! 
    248249      NAMELIST/namsbc_rnf/ cn_dir, ln_rnf_emp, ln_rnf_depth, ln_rnf_tem, ln_rnf_sal,   & 
     
    264265      sn_dep_rnf = FLD_N( 'runoffs',   0.  , 'rodepth'  ,  .FALSE.   , .true. ,   'yearly'  , ''    , ''  ) 
    265266      ! 
    266       REWIND ( numnam )                         ! Read Namelist namsbc_rnf 
    267       READ   ( numnam, namsbc_rnf ) 
     267      REWIND( numnam_ref )              ! Namelist namsbc_rnf in reference namelist : Runoffs  
     268      READ  ( numnam_ref, namsbc_rnf, IOSTAT = ios, ERR = 901) 
     269901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc_rnf in reference namelist', lwp ) 
     270 
     271      REWIND( numnam_cfg )              ! Namelist namsbc_rnf in configuration namelist : Runoffs 
     272      READ  ( numnam_cfg, namsbc_rnf, IOSTAT = ios, ERR = 902 ) 
     273902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc_rnf in configuration namelist', lwp ) 
     274      WRITE ( numond, namsbc_rnf ) 
    268275      ! 
    269276      !                                         ! Control print 
  • branches/2013/dev_r3853_CNRS9_ConfSetting/NEMOGCM/NEMO/OPA_SRC/SBC/sbcssr.F90

    r3764 r3875  
    7979      CHARACTER(len=100) ::  cn_dir          ! Root directory for location of ssr files 
    8080      TYPE(FLD_N) ::   sn_sst, sn_sss        ! informations about the fields to be read 
    81       NAMELIST/namsbc_ssr/ cn_dir, nn_sstr, nn_sssr, rn_dqdt, rn_deds, sn_sst, sn_sss, ln_sssr_bnd, rn_sssr_bnd 
    8281      !!---------------------------------------------------------------------- 
    8382      ! 
     
    164163      TYPE(FLD_N) ::   sn_sst, sn_sss        ! informations about the fields to be read 
    165164      NAMELIST/namsbc_ssr/ cn_dir, nn_sstr, nn_sssr, rn_dqdt, rn_deds, sn_sst, sn_sss, ln_sssr_bnd, rn_sssr_bnd 
     165      INTEGER     ::  ios 
    166166      !!---------------------------------------------------------------------- 
    167167      ! 
     
    173173      sn_sst = FLD_N( 'sst'    ,    24     ,  'sst'     ,  .false.   , .false. ,   'yearly'  , ''       , ''         ) 
    174174      sn_sss = FLD_N( 'sss'    ,    -1     ,  'sss'     ,  .true.    , .false. ,   'yearly'  , ''       , ''         ) 
    175  
    176       REWIND( numnam )             !* read in namlist namflx 
    177       READ  ( numnam, namsbc_ssr )  
     175  
     176      REWIND( numnam_ref )              ! Namelist namsbc_ssr in reference namelist :  
     177      READ  ( numnam_ref, namsbc_ssr, IOSTAT = ios, ERR = 901) 
     178901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc_ssr in reference namelist', lwp ) 
     179 
     180      REWIND( numnam_cfg )              ! Namelist namsbc_ssr in configuration namelist : 
     181      READ  ( numnam_cfg, namsbc_ssr, IOSTAT = ios, ERR = 902 ) 
     182902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc_ssr in configuration namelist', lwp ) 
     183      WRITE ( numond, namsbc_ssr ) 
    178184 
    179185      IF(lwp) THEN                 !* control print 
  • branches/2013/dev_r3853_CNRS9_ConfSetting/NEMOGCM/NEMO/OPA_SRC/SBC/sbcwave.F90

    r3680 r3875  
    6767      INTEGER                ::  ierror   ! return error code 
    6868      INTEGER                ::  ifpr, jj,ji,jk  
     69      INTEGER                ::   ios     ! Local integer output status for namelist read 
    6970      REAL(wp),DIMENSION(:,:,:),POINTER             ::  udummy,vdummy,hdivdummy,rotdummy 
    7071      REAL                                          ::  z2dt,z1_2dt 
     
    9293         cn_dir = './'          ! directory in which the wave data are  
    9394          
    94  
    95          REWIND( numnam )                             !* read in namlist namsbc_wave 
    96          READ  ( numnam, namsbc_wave )  
     95         REWIND( numnam_ref )              ! Namelist namsbc_wave in reference namelist : File for drag coeff. from wave model 
     96         READ  ( numnam_ref, namsbc_wave, IOSTAT = ios, ERR = 901) 
     97901      IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc_wave in reference namelist', lwp ) 
     98 
     99         REWIND( numnam_cfg )              ! Namelist namsbc_wave in configuration namelist : File for drag coeff. from wave model 
     100         READ  ( numnam_cfg, namsbc_wave, IOSTAT = ios, ERR = 902 ) 
     101902      IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc_wave in configuration namelist', lwp ) 
     102         WRITE ( numond, namsbc_wave ) 
    97103         ! 
    98104 
  • branches/2013/dev_r3853_CNRS9_ConfSetting/NEMOGCM/NEMO/OPA_SRC/SBC/tideini.F90

    r3651 r3875  
    4646    INTEGER, INTENT( in ) ::   kt     ! ocean time-step 
    4747    CHARACTER(LEN=4), DIMENSION(jpmax_harmo) :: clname 
     48    INTEGER  ::   ios                 ! Local integer output status for namelist read 
    4849    ! 
    4950    NAMELIST/nam_tide/ln_tide_pot, ln_tide_ramp, rdttideramp, clname 
     
    6364       ! 
    6465       ! Read Namelist nam_tide 
    65        REWIND ( numnam ) 
    66        READ   ( numnam, nam_tide ) 
     66       REWIND( numnam_ref )              ! Namelist nam_tide in reference namelist : Tides 
     67       READ  ( numnam_ref, nam_tide, IOSTAT = ios, ERR = 901) 
     68901    IF( ios /= 0 ) CALL ctl_nam ( ios , 'nam_tide in reference namelist', lwp ) 
     69 
     70       REWIND( numnam_cfg )              ! Namelist nam_tide in configuration namelist : Tides 
     71       READ  ( numnam_cfg, nam_tide, IOSTAT = ios, ERR = 902 ) 
     72902    IF( ios /= 0 ) CALL ctl_nam ( ios , 'nam_tide in configuration namelist', lwp ) 
     73       WRITE ( numond, nam_tide ) 
    6774       ! 
    6875       nb_harmo=0 
  • branches/2013/dev_r3853_CNRS9_ConfSetting/NEMOGCM/NEMO/OPA_SRC/SOL/solver.F90

    r3764 r3875  
    5151      !!---------------------------------------------------------------------- 
    5252      INTEGER, INTENT(in) :: kt 
     53      INTEGER             ::   ios       ! Local integer output status for namelist read 
    5354      !! 
    5455      NAMELIST/namsol/ nn_solv, nn_sol_arp, nn_nmin, nn_nmax, nn_nmod, rn_eps, rn_resmax, rn_sor 
     
    6263      ENDIF 
    6364 
    64       REWIND( numnam )              !* Namelist namsol : elliptic solver / free surface 
    65       READ  ( numnam, namsol ) 
     65      REWIND( numnam_ref )              ! Namelist namsol in reference namelist : Elliptic solver / free surface 
     66      READ  ( numnam_ref, namsol, IOSTAT = ios, ERR = 901) 
     67901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsol in reference namelist', lwp ) 
     68 
     69      REWIND( numnam_cfg )              ! Namelist namsol in configuration namelist : Elliptic solver / free surface 
     70      READ  ( numnam_cfg, namsol, IOSTAT = ios, ERR = 902 ) 
     71902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsol in configuration namelist', lwp ) 
     72      WRITE ( numond, namsol ) 
    6673 
    6774      IF(lwp) THEN                  !* Control print 
  • branches/2013/dev_r3853_CNRS9_ConfSetting/NEMOGCM/NEMO/OPA_SRC/TRA/eosbn2.F90

    r3625 r3875  
    708708      NAMELIST/nameos/ nn_eos, rn_alpha, rn_beta 
    709709      !!---------------------------------------------------------------------- 
    710       ! 
    711       REWIND( numnam )            ! Read Namelist nameos : equation of state 
    712       READ  ( numnam, nameos ) 
     710      INTEGER  ::   ios 
     711      ! 
     712      REWIND( numnam_ref )              ! Namelist nameos in reference namelist : equation of state 
     713      READ  ( numnam_ref, nameos, IOSTAT = ios, ERR = 901 ) 
     714901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nameos in reference namelist', lwp ) 
     715 
     716      REWIND( numnam_cfg )              ! Namelist nameos in configuration namelist : equation of state 
     717      READ  ( numnam_cfg, nameos, IOSTAT = ios, ERR = 902 ) 
     718902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nameos in configuration namelist', lwp ) 
     719      WRITE( numond, nameos ) 
    713720      ! 
    714721      IF(lwp) THEN                ! Control print 
  • branches/2013/dev_r3853_CNRS9_ConfSetting/NEMOGCM/NEMO/OPA_SRC/TRA/traadv.F90

    r3718 r3875  
    151151      !!---------------------------------------------------------------------- 
    152152      INTEGER ::   ioptio 
     153      INTEGER ::   ios                 ! Local integer output status for namelist read 
    153154      !! 
    154155      NAMELIST/namtra_adv/ ln_traadv_cen2 , ln_traadv_tvd,     & 
     
    158159      !!---------------------------------------------------------------------- 
    159160 
    160       REWIND( numnam )                ! Read Namelist namtra_adv : tracer advection scheme 
    161       READ  ( numnam, namtra_adv ) 
     161      REWIND( numnam_ref )              ! Namelist namtra_adv in reference namelist : Tracer advection scheme 
     162      READ  ( numnam_ref, namtra_adv, IOSTAT = ios, ERR = 901) 
     163901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtra_adv in reference namelist', lwp ) 
     164 
     165      REWIND( numnam_cfg )              ! Namelist namtra_adv in configuration namelist : Tracer advection scheme 
     166      READ  ( numnam_cfg, namtra_adv, IOSTAT = ios, ERR = 902 ) 
     167902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtra_adv in configuration namelist', lwp ) 
     168      WRITE ( numond, namtra_adv ) 
    162169 
    163170      IF(lwp) THEN                    ! Namelist print 
  • branches/2013/dev_r3853_CNRS9_ConfSetting/NEMOGCM/NEMO/OPA_SRC/TRA/trabbc.F90

    r3625 r3875  
    129129      INTEGER  ::   ji, jj              ! dummy loop indices 
    130130      INTEGER  ::   inum                ! temporary logical unit 
     131      INTEGER  ::   ios                 ! Local integer output status for namelist read 
    131132      !! 
    132133      NAMELIST/nambbc/ln_trabbc, nn_geoflx, rn_geoflx_cst  
    133134      !!---------------------------------------------------------------------- 
    134135 
    135       REWIND( numnam )                 ! Read Namelist nambbc : bottom momentum boundary condition 
    136       READ  ( numnam, nambbc ) 
     136      REWIND( numnam_ref )              ! Namelist nambbc in reference namelist : Bottom momentum boundary condition 
     137      READ  ( numnam_ref, nambbc, IOSTAT = ios, ERR = 901) 
     138901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nambbc in reference namelist', lwp ) 
     139 
     140      REWIND( numnam_cfg )              ! Namelist nambbc in configuration namelist : Bottom momentum boundary condition 
     141      READ  ( numnam_cfg, nambbc, IOSTAT = ios, ERR = 902 ) 
     142902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nambbc in configuration namelist', lwp ) 
     143      WRITE ( numond, nambbc ) 
    137144 
    138145      IF(lwp) THEN                     ! Control print 
  • branches/2013/dev_r3853_CNRS9_ConfSetting/NEMOGCM/NEMO/OPA_SRC/TRA/trabbl.F90

    r3764 r3875  
    560560      INTEGER ::   ji, jj               ! dummy loop indices 
    561561      INTEGER ::   ii0, ii1, ij0, ij1   ! temporary integer 
     562      INTEGER  ::   ios                 ! Local integer output status for namelist read 
    562563      REAL(wp), POINTER, DIMENSION(:,:) :: zmbk 
    563564      !! 
     
    570571      ! 
    571572 
    572       REWIND ( numnam )              !* Read Namelist nambbl : bottom boundary layer scheme 
    573       READ   ( numnam, nambbl ) 
     573      REWIND( numnam_ref )              ! Namelist nambbl in reference namelist : Bottom boundary layer scheme 
     574      READ  ( numnam_ref, nambbl, IOSTAT = ios, ERR = 901) 
     575901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nambbl in reference namelist', lwp ) 
     576 
     577      REWIND( numnam_cfg )              ! Namelist nambbl in configuration namelist : Bottom boundary layer scheme 
     578      READ  ( numnam_cfg, nambbl, IOSTAT = ios, ERR = 902 ) 
     579902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nambbl in configuration namelist', lwp ) 
     580      WRITE ( numond, nambbl ) 
    574581      ! 
    575582      l_bbl = .TRUE.                 !* flag to compute bbl coef and transport 
  • branches/2013/dev_r3853_CNRS9_ConfSetting/NEMOGCM/NEMO/OPA_SRC/TRA/tradmp.F90

    r3294 r3875  
    194194      !!---------------------------------------------------------------------- 
    195195      NAMELIST/namtra_dmp/ ln_tradmp, nn_hdmp, nn_zdmp, rn_surf, rn_bot, rn_dep, nn_file 
    196       !!---------------------------------------------------------------------- 
    197  
    198       REWIND ( numnam )                  ! Read Namelist namtra_dmp : temperature and salinity damping term 
    199       READ   ( numnam, namtra_dmp ) 
     196      INTEGER  ::   ios                 ! Local integer output status for namelist read 
     197      !!---------------------------------------------------------------------- 
     198 
     199      REWIND( numnam_ref )              ! Namelist namtra_dmp in reference namelist : Temperature and salinity damping term 
     200      READ  ( numnam_ref, namtra_dmp, IOSTAT = ios, ERR = 901) 
     201901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtra_dmp in reference namelist', lwp ) 
     202 
     203      REWIND( numnam_cfg )              ! Namelist namtra_dmp in configuration namelist : Temperature and salinity damping term 
     204      READ  ( numnam_cfg, namtra_dmp, IOSTAT = ios, ERR = 902 ) 
     205902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtra_dmp in configuration namelist', lwp ) 
     206      WRITE ( numond, namtra_dmp ) 
    200207       
    201208      IF( lzoom )   nn_zdmp = 0          ! restoring to climatology at closed north or south boundaries 
  • branches/2013/dev_r3853_CNRS9_ConfSetting/NEMOGCM/NEMO/OPA_SRC/TRA/traqsr.F90

    r3680 r3875  
    315315      !!---------------------------------------------------------------------- 
    316316      ! 
    317       INTEGER  ::   ji, jj, jk     ! dummy loop indices 
     317      INTEGER  ::   ji, jj, jk                   ! dummy loop indices 
    318318      INTEGER  ::   irgb, ierror, ioptio, nqsr   ! local integer 
     319      INTEGER  ::   ios                          ! Local integer output status for namelist read 
    319320      REAL(wp) ::   zz0, zc0  , zc1, zcoef       ! local scalars 
    320321      REAL(wp) ::   zz1, zc2  , zc3, zchl        !   -      - 
     
    342343      sn_chl = FLD_N( 'chlorophyll' ,    -1     ,  'CHLA'    ,  .true.     , .true.  ,   'yearly'  , ''       , ''         ) 
    343344      ! 
    344       REWIND( numnam )            ! Read Namelist namtra_qsr : ratio and length of penetration 
    345       READ  ( numnam, namtra_qsr ) 
     345 
     346      REWIND( numnam_ref )              ! Namelist namtra_qsr in reference namelist : Ratio and length of penetration 
     347      READ  ( numnam_ref, namtra_qsr, IOSTAT = ios, ERR = 901) 
     348901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtra_qsr in reference namelist', lwp ) 
     349 
     350      REWIND( numnam_cfg )              !  Namelist namtra_qsr in configuration namelist : Ratio and length of penetration 
     351      READ  ( numnam_cfg, namtra_qsr, IOSTAT = ios, ERR = 902 ) 
     352902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtra_qsr in configuration namelist', lwp ) 
     353      WRITE ( numond, namtra_qsr ) 
    346354      ! 
    347355      IF(lwp) THEN                ! control print 
  • branches/2013/dev_r3853_CNRS9_ConfSetting/NEMOGCM/NEMO/OPA_SRC/TRD/trdmod.F90

    r3294 r3875  
    251251      !!---------------------------------------------------------------------- 
    252252      USE in_out_manager          ! I/O manager 
     253      USE lib_mpp                 ! MPP library 
    253254      !!     
    254255      NAMELIST/namtrd/ nn_trd, nn_ctls, cn_trdrst_in, cn_trdrst_out, ln_trdmld_restart, rn_ucf, ln_trdmld_instant 
     256      INTEGER  ::   ios           ! Local integer output status for namelist read 
    255257      !!---------------------------------------------------------------------- 
    256258 
    257259      IF( l_trdtra .OR. l_trddyn )   THEN 
    258          REWIND( numnam ) 
    259          READ  ( numnam, namtrd )      ! namelist namtrd : trends diagnostic 
     260  
     261         REWIND( numnam_ref )              ! Namelist namtrd in reference namelist : Diagnostics: trends 
     262         READ  ( numnam_ref, namtrd, IOSTAT = ios, ERR = 901) 
     263901      IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrd in reference namelist', lwp ) 
     264 
     265         REWIND( numnam_cfg )              ! Namelist namtrd in configuration namelist : Diagnostics: trends 
     266         READ  ( numnam_cfg, namtrd, IOSTAT = ios, ERR = 902 ) 
     267902      IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrd in configuration namelist', lwp ) 
     268         WRITE ( numond, namtrd ) 
    260269 
    261270         IF(lwp) THEN 
  • branches/2013/dev_r3853_CNRS9_ConfSetting/NEMOGCM/NEMO/OPA_SRC/ZDF/zdfbfr.F90

    r3820 r3875  
    179179      INTEGER   ::   ikbu, ikbv   ! temporary integers 
    180180      INTEGER   ::   ictu, ictv   !    -          - 
     181      INTEGER   ::   ios 
    181182      REAL(wp)  ::   zminbfr, zmaxbfr   ! temporary scalars 
    182183      REAL(wp)  ::   zfru, zfrv         !    -         - 
     
    188189      IF( nn_timing == 1 )  CALL timing_start('zdf_bfr_init') 
    189190      ! 
    190       REWIND ( numnam )               !* Read Namelist nam_bfr : bottom momentum boundary condition 
    191       READ   ( numnam, nambfr ) 
     191      REWIND( numnam_ref )              ! Namelist nambfr in reference namelist : Bottom momentum boundary condition 
     192      READ  ( numnam_ref, nambfr, IOSTAT = ios, ERR = 901) 
     193901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nambfr in reference namelist', lwp ) 
     194 
     195      REWIND( numnam_cfg )              ! Namelist nambfr in configuration namelist : Bottom momentum boundary condition 
     196      READ  ( numnam_cfg, nambfr, IOSTAT = ios, ERR = 902 ) 
     197902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nambfr in configuration namelist', lwp ) 
     198      WRITE ( numond, nambfr ) 
    192199 
    193200      !                               !* Parameter control and print 
  • branches/2013/dev_r3853_CNRS9_ConfSetting/NEMOGCM/NEMO/OPA_SRC/ZDF/zdfddm.F90

    r3610 r3875  
    213213      !!---------------------------------------------------------------------- 
    214214      NAMELIST/namzdf_ddm/ rn_avts, rn_hsbfr 
    215       !!---------------------------------------------------------------------- 
    216       ! 
    217       REWIND( numnam )                ! Read Namelist namzdf_ddm : double diffusion mixing scheme 
    218       READ  ( numnam, namzdf_ddm ) 
     215      INTEGER  ::   ios                 ! Local integer output status for namelist read 
     216      !!---------------------------------------------------------------------- 
     217      ! 
     218      REWIND( numnam_ref )              ! Namelist namzdf_ddm in reference namelist : Double diffusion mixing scheme 
     219      READ  ( numnam_ref, namzdf_ddm, IOSTAT = ios, ERR = 901) 
     220901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namzdf_ddm in reference namelist', lwp ) 
     221 
     222      REWIND( numnam_cfg )              ! Namelist namzdf_ddm in configuration namelist : Double diffusion mixing scheme 
     223      READ  ( numnam_cfg, namzdf_ddm, IOSTAT = ios, ERR = 902 ) 
     224902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namzdf_ddm in configuration namelist', lwp ) 
     225      WRITE ( numond, namzdf_ddm ) 
    219226      ! 
    220227      IF(lwp) THEN                    ! Parameter print 
  • branches/2013/dev_r3853_CNRS9_ConfSetting/NEMOGCM/NEMO/OPA_SRC/ZDF/zdfgls.F90

    r3798 r3875  
    928928      ! 
    929929      INTEGER ::   jk    ! dummy loop indices 
     930      INTEGER ::   ios   ! Local integer output status for namelist read 
    930931      REAL(wp)::   zcr   ! local scalar 
    931932      !! 
     
    940941      IF( nn_timing == 1 )  CALL timing_start('zdf_gls_init') 
    941942      ! 
    942       REWIND( numnam )                 !* Read Namelist namzdf_gls 
    943       READ  ( numnam, namzdf_gls ) 
     943      REWIND( numnam_ref )              ! Namelist namzdf_gls in reference namelist : Vertical eddy diffivity and viscosity using gls turbulent closure scheme 
     944      READ  ( numnam_ref, namzdf_gls, IOSTAT = ios, ERR = 901) 
     945901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namzdf_gls in reference namelist', lwp ) 
     946 
     947      REWIND( numnam_cfg )              ! Namelist namzdf_gls in configuration namelist : Vertical eddy diffivity and viscosity using gls turbulent closure scheme 
     948      READ  ( numnam_cfg, namzdf_gls, IOSTAT = ios, ERR = 902 ) 
     949902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namzdf_gls in configuration namelist', lwp ) 
     950      WRITE ( numond, namzdf_gls ) 
    944951 
    945952      IF(lwp) THEN                     !* Control print 
  • branches/2013/dev_r3853_CNRS9_ConfSetting/NEMOGCM/NEMO/OPA_SRC/ZDF/zdfini.F90

    r3680 r3875  
    5151      !!---------------------------------------------------------------------- 
    5252      INTEGER ::   ioptio       ! temporary scalar 
     53      INTEGER ::   ios 
    5354      !! 
    5455      NAMELIST/namzdf/ rn_avm0, rn_avt0, nn_avb, nn_havtb, ln_zdfexp, nn_zdfexp,   & 
     
    5657      !!---------------------------------------------------------------------- 
    5758 
    58       REWIND( numnam )           !* Read namzdf namelist : vertical mixing parameters 
    59       READ  ( numnam, namzdf ) 
     59      REWIND( numnam_ref )              ! Namelist namzdf in reference namelist : Vertical mixing parameters 
     60      READ  ( numnam_ref, namzdf, IOSTAT = ios, ERR = 901) 
     61901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namzdf in reference namelist', lwp ) 
     62 
     63      REWIND( numnam_cfg )              ! Namelist namzdf in reference namelist : Vertical mixing parameters 
     64      READ  ( numnam_cfg, namzdf, IOSTAT = ios, ERR = 902 ) 
     65902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namzdf in configuration namelist', lwp ) 
     66      WRITE ( numond, namzdf ) 
    6067 
    6168      IF(lwp) THEN               !* Parameter print 
  • branches/2013/dev_r3853_CNRS9_ConfSetting/NEMOGCM/NEMO/OPA_SRC/ZDF/zdfkpp.F90

    r3792 r3875  
    13821382      REAL(wp) ::   zustar, zucube, zustvk, zeta, zehat   ! tempory scalars 
    13831383#endif 
     1384      INTEGER  ::   ios            ! Local integer output status for namelist read 
    13841385      REAL(wp) ::   zhbf           ! tempory scalars 
    13851386      LOGICAL  ::   ll_kppcustom   ! 1st ocean level taken as surface layer 
     
    13911392      IF( nn_timing == 1 )  CALL timing_start('zdf_kpp_init') 
    13921393      ! 
    1393       REWIND ( numnam )               ! Read Namelist namkpp : K-Profile Parameterisation 
    1394       READ   ( numnam, namzdf_kpp ) 
     1394      REWIND( numnam_ref )              ! Namelist namzdf_kpp in reference namelist : Vertical eddy diffivity and viscosity using kpp turbulent closure scheme 
     1395      READ  ( numnam_ref, namzdf_kpp, IOSTAT = ios, ERR = 901) 
     1396901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namzdf_kpp in reference namelist', lwp ) 
     1397 
     1398      REWIND( numnam_cfg )              ! Namelist namzdf_kpp in configuration namelist : Vertical eddy diffivity and viscosity using kpp turbulent closure scheme 
     1399      READ  ( numnam_cfg, namzdf_kpp, IOSTAT = ios, ERR = 902 ) 
     1400902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namzdf_kpp in configuration namelist', lwp ) 
     1401      WRITE ( numond, namzdf_kpp ) 
    13951402 
    13961403      IF(lwp) THEN                    ! Control print 
  • branches/2013/dev_r3853_CNRS9_ConfSetting/NEMOGCM/NEMO/OPA_SRC/ZDF/zdfric.F90

    r3625 r3875  
    247247      !!---------------------------------------------------------------------- 
    248248      INTEGER :: ji, jj, jk   ! dummy loop indices 
     249      INTEGER ::   ios        ! Local integer output status for namelist read 
    249250      !! 
    250251      NAMELIST/namzdf_ric/ rn_avmri, rn_alp   , nn_ric  , rn_ekmfc,  & 
     
    252253      !!---------------------------------------------------------------------- 
    253254      ! 
    254       REWIND( numnam )               ! Read Namelist namzdf_ric : richardson number dependent Kz 
    255       READ  ( numnam, namzdf_ric ) 
     255      REWIND( numnam_ref )              ! Namelist namzdf_ric in reference namelist : Vertical diffusion Kz depends on Richardson number 
     256      READ  ( numnam_ref, namzdf_ric, IOSTAT = ios, ERR = 901) 
     257901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namzdf_ric in reference namelist', lwp ) 
     258 
     259      REWIND( numnam_cfg )              ! Namelist namzdf_ric in configuration namelist : Vertical diffusion Kz depends on Richardson number 
     260      READ  ( numnam_cfg, namzdf_ric, IOSTAT = ios, ERR = 902 ) 
     261902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namzdf_ric in configuration namelist', lwp ) 
     262      WRITE ( numond, namzdf_ric ) 
    256263      ! 
    257264      IF(lwp) THEN                   ! Control print 
  • branches/2013/dev_r3853_CNRS9_ConfSetting/NEMOGCM/NEMO/OPA_SRC/ZDF/zdftke.F90

    r3680 r3875  
    692692      !!---------------------------------------------------------------------- 
    693693      INTEGER ::   ji, jj, jk   ! dummy loop indices 
     694      INTEGER ::   ios 
    694695      !! 
    695696      NAMELIST/namzdf_tke/ rn_ediff, rn_ediss , rn_ebb , rn_emin  ,   & 
     
    699700      !!---------------------------------------------------------------------- 
    700701      ! 
    701       REWIND ( numnam )               !* Read Namelist namzdf_tke : Turbulente Kinetic Energy 
    702       READ   ( numnam, namzdf_tke ) 
     702      REWIND( numnam_ref )              ! Namelist namzdf_tke in reference namelist : Turbulent Kinetic Energy 
     703      READ  ( numnam_ref, namzdf_tke, IOSTAT = ios, ERR = 901) 
     704901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namzdf_tke in reference namelist', lwp ) 
     705 
     706      REWIND( numnam_cfg )              ! Namelist namzdf_tke in configuration namelist : Turbulent Kinetic Energy 
     707      READ  ( numnam_cfg, namzdf_tke, IOSTAT = ios, ERR = 902 ) 
     708902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namzdf_tke in configuration namelist', lwp ) 
     709      WRITE ( numond, namzdf_tke ) 
    703710      ! 
    704711      ri_cri   = 2._wp    / ( 2._wp + rn_ediss / rn_ediff )   ! resulting critical Richardson number 
  • branches/2013/dev_r3853_CNRS9_ConfSetting/NEMOGCM/NEMO/OPA_SRC/ZDF/zdftmx.F90

    r3625 r3875  
    354354      INTEGER  ::   ji, jj, jk   ! dummy loop indices 
    355355      INTEGER  ::   inum         ! local integer 
     356      INTEGER  ::   ios 
    356357      REAL(wp) ::   ztpc, ze_z   ! local scalars 
    357358      REAL(wp), DIMENSION(:,:)  , POINTER ::  zem2, zek1   ! read M2 and K1 tidal energy 
     
    369370      CALL wrk_alloc( jpi,jpj,jpk, zpc ) 
    370371       
    371       REWIND( numnam )               ! Read Namelist namtmx : Tidal Mixing 
    372       READ  ( numnam, namzdf_tmx ) 
     372      REWIND( numnam_ref )              ! Namelist namzdf_tmx in reference namelist : Tidal Mixing 
     373      READ  ( numnam_ref, namzdf_tmx, IOSTAT = ios, ERR = 901) 
     374901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namzdf_tmx in reference namelist', lwp ) 
     375 
     376      REWIND( numnam_cfg )              ! Namelist namzdf_tmx in configuration namelist : Tidal Mixing 
     377      READ  ( numnam_cfg, namzdf_tmx, IOSTAT = ios, ERR = 902 ) 
     378902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namzdf_tmx in configuration namelist', lwp ) 
     379      WRITE ( numond, namzdf_tmx ) 
    373380 
    374381      IF(lwp) THEN                   ! Control print 
  • branches/2013/dev_r3853_CNRS9_ConfSetting/NEMOGCM/NEMO/OPA_SRC/module_example

    r2737 r3875  
    157157      !!---------------------------------------------------------------------- 
    158158      INTEGER ::   ji, jj, jk, jit   ! dummy loop indices 
     159      INTEGER  ::   ios              ! Local integer output status for namelist read 
    159160      !! 
    160161      NAMELIST/namexa/ exa_v1, exa_v2, nexa_0, sn_ex      
     
    164165      sn_ex%nfreqh = 2  
    165166      ! 
    166       REWIND( numnam )                          ! Read Namelist namexa : example parameters 
    167       READ  ( numnam, namexa ) 
     167      REWIND( numnam_ref )              ! Namelist namexa in reference namelist : Example 
     168      READ  ( numnam_ref, namexa, IOSTAT = ios, ERR = 901) 
     169901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namexa in reference namelist', lwp ) 
     170 
     171      REWIND( numnam_cfg )              ! Namelist namexa in configuration namelist : Example 
     172      READ  ( numnam_cfg, namexa, IOSTAT = ios, ERR = 902 ) 
     173902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namexa in configuration namelist', lwp ) 
     174   ! Output namelist for control 
     175      WRITE ( numond, namexa ) 
    168176      ! 
    169177      IF(lwp) THEN                              ! Control print 
  • branches/2013/dev_r3853_CNRS9_ConfSetting/NEMOGCM/NEMO/OPA_SRC/nemogcm.F90

    r3769 r3875  
    218218      INTEGER ::   ji            ! dummy loop indices 
    219219      INTEGER ::   ilocal_comm   ! local integer 
     220      INTEGER ::   ios 
    220221      CHARACTER(len=80), DIMENSION(16) ::   cltxt 
    221222      !! 
     
    227228      cltxt = '' 
    228229      ! 
    229       !                             ! open Namelist file 
    230       CALL ctl_opn( numnam, 'namelist', 'OLD', 'FORMATTED', 'SEQUENTIAL', -1, 6, .FALSE. ) 
    231       ! 
    232       READ( numnam, namctl )        ! Namelist namctl : Control prints & Benchmark 
     230      !                             ! Open reference namelist and configuration namelist files 
     231      CALL ctl_opn( numnam_ref, 'namelist_ref', 'OLD', 'FORMATTED', 'SEQUENTIAL', -1, 6, .FALSE. ) 
     232      CALL ctl_opn( numnam_cfg, 'namelist_cfg', 'OLD', 'FORMATTED', 'SEQUENTIAL', -1, 6, .FALSE. ) 
     233      CALL ctl_opn( numond, 'output.namelist.dyn', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, 6, .FALSE., narea ) 
     234      ! 
     235      REWIND( numnam_ref )              ! Namelist namctl in reference namelist : Control prints & Benchmark 
     236      READ  ( numnam_ref, namctl, IOSTAT = ios, ERR = 901 ) 
     237901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namctl in reference namelist', lwp ) 
     238 
     239      REWIND( numnam_cfg )              ! Namelist namctl in confguration namelist : Control prints & Benchmark 
     240      READ  ( numnam_cfg, namctl, IOSTAT = ios, ERR = 902 ) 
     241902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namctl in configuration namelist', lwp ) 
     242      WRITE( numond, namctl ) 
    233243      ! 
    234244      !                             !--------------------------------------------! 
     
    244254# endif 
    245255      ENDIF 
    246       narea = mynode( cltxt, numnam, nstop, ilocal_comm )   ! Nodes selection 
     256      narea = mynode( cltxt, numnam_ref, numnam_cfg, numond , nstop, ilocal_comm )   ! Nodes selection 
    247257#else 
    248258# if defined key_oasis3 || defined key_oasis4 
     
    250260         CALL cpl_prism_init( ilocal_comm )                 ! nemo local communicator given by oasis 
    251261      ENDIF 
    252       narea = mynode( cltxt, numnam, nstop, ilocal_comm )   ! Nodes selection (control print return in cltxt) 
     262      narea = mynode( cltxt, numnam_ref, numnam_cfg, numond , nstop, ilocal_comm )   ! Nodes selection (control print return in cltxt) 
    253263# else 
    254264      ilocal_comm = 0 
    255       narea = mynode( cltxt, numnam, nstop )                 ! Nodes selection (control print return in cltxt) 
     265      narea = mynode( cltxt, numnam_ref, numnam_cfg, numond , nstop )                 ! Nodes selection (control print return in cltxt) 
    256266# endif 
    257267#endif 
     
    510520      CALL iom_close                                 ! close all input/output files managed by iom_* 
    511521      ! 
    512       IF( numstp      /= -1 )   CLOSE( numstp      )   ! time-step file 
    513       IF( numsol      /= -1 )   CLOSE( numsol      )   ! solver file 
    514       IF( numnam      /= -1 )   CLOSE( numnam      )   ! oce namelist 
    515       IF( numnam_ice  /= -1 )   CLOSE( numnam_ice  )   ! ice namelist 
    516       IF( numevo_ice  /= -1 )   CLOSE( numevo_ice  )   ! ice variables (temp. evolution) 
    517       IF( numout      /=  6 )   CLOSE( numout      )   ! standard model output file 
    518       IF( numdct_vol  /= -1 )   CLOSE( numdct_vol  )   ! volume transports 
    519       IF( numdct_heat /= -1 )   CLOSE( numdct_heat )   ! heat transports 
    520       IF( numdct_salt /= -1 )   CLOSE( numdct_salt )   ! salt transports 
     522      IF( numstp          /= -1 )   CLOSE( numstp          )   ! time-step file 
     523      IF( numsol          /= -1 )   CLOSE( numsol          )   ! solver file 
     524      IF( numnam_ref      /= -1 )   CLOSE( numnam_ref      )   ! oce reference namelist 
     525      IF( numnam_cfg      /= -1 )   CLOSE( numnam_cfg      )   ! oce configuration namelist 
     526      IF( numnam_ice_ref  /= -1 )   CLOSE( numnam_ice_ref  )   ! ice reference namelist 
     527      IF( numnam_ice_cfg  /= -1 )   CLOSE( numnam_ice_cfg  )   ! ice configuration namelist 
     528      IF( numevo_ice      /= -1 )   CLOSE( numevo_ice      )   ! ice variables (temp. evolution) 
     529      IF( numout          /=  6 )   CLOSE( numout          )   ! standard model output file 
     530      IF( numdct_vol      /= -1 )   CLOSE( numdct_vol      )   ! volume transports 
     531      IF( numdct_heat     /= -1 )   CLOSE( numdct_heat     )   ! heat transports 
     532      IF( numdct_salt     /= -1 )   CLOSE( numdct_salt     )   ! salt transports 
    521533 
    522534      ! 
Note: See TracChangeset for help on using the changeset viewer.