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

Changeset 8668


Ignore:
Timestamp:
2017-10-30T12:44:29+01:00 (6 years ago)
Author:
andmirek
Message:

#1953 change variable names to follow NEMO coding convention

Location:
branches/2017/dev_r8600_xios_read/NEMOGCM/NEMO
Files:
20 edited

Legend:

Unmodified
Added
Removed
  • branches/2017/dev_r8600_xios_read/NEMOGCM/NEMO/OPA_SRC/DIA/diahsb.F90

    r8612 r8668  
    256256           IF(lwp) WRITE(numout,*) ' dia_hsb_rst at it= ', kt,' date= ', ndastp 
    257257           IF(lwp) WRITE(numout,*) '~~~~~~~' 
    258            CALL iom_get( numror, 'frc_v', frc_v, lrxios = lxios_read  ) 
    259            CALL iom_get( numror, 'frc_t', frc_t, lrxios = lxios_read ) 
    260            CALL iom_get( numror, 'frc_s', frc_s, lrxios = lxios_read ) 
     258           CALL iom_get( numror, 'frc_v', frc_v, ldxios = lxios_read  ) 
     259           CALL iom_get( numror, 'frc_t', frc_t, ldxios = lxios_read ) 
     260           CALL iom_get( numror, 'frc_s', frc_s, ldxios = lxios_read ) 
    261261           IF( ln_linssh ) THEN 
    262               CALL iom_get( numror, 'frc_wn_t', frc_wn_t, lrxios = lxios_read ) 
    263               CALL iom_get( numror, 'frc_wn_s', frc_wn_s, lrxios = lxios_read ) 
     262              CALL iom_get( numror, 'frc_wn_t', frc_wn_t, ldxios = lxios_read ) 
     263              CALL iom_get( numror, 'frc_wn_s', frc_wn_s, ldxios = lxios_read ) 
    264264           ENDIF 
    265            CALL iom_get( numror, jpdom_autoglo, 'surf_ini', surf_ini, lrxios = lxios_read ) ! ice sheet coupling 
    266            CALL iom_get( numror, jpdom_autoglo, 'ssh_ini', ssh_ini(:,:), lrxios = lxios_read ) 
    267            CALL iom_get( numror, jpdom_autoglo, 'e3t_ini', e3t_ini(:,:,:), lrxios = lxios_read ) 
    268            CALL iom_get( numror, jpdom_autoglo, 'hc_loc_ini', hc_loc_ini(:,:,:), lrxios = lxios_read ) 
    269            CALL iom_get( numror, jpdom_autoglo, 'sc_loc_ini', sc_loc_ini(:,:,:), lrxios = lxios_read ) 
     265           CALL iom_get( numror, jpdom_autoglo, 'surf_ini', surf_ini, ldxios = lxios_read ) ! ice sheet coupling 
     266           CALL iom_get( numror, jpdom_autoglo, 'ssh_ini', ssh_ini(:,:), ldxios = lxios_read ) 
     267           CALL iom_get( numror, jpdom_autoglo, 'e3t_ini', e3t_ini(:,:,:), ldxios = lxios_read ) 
     268           CALL iom_get( numror, jpdom_autoglo, 'hc_loc_ini', hc_loc_ini(:,:,:), ldxios = lxios_read ) 
     269           CALL iom_get( numror, jpdom_autoglo, 'sc_loc_ini', sc_loc_ini(:,:,:), ldxios = lxios_read ) 
    270270           IF( ln_linssh ) THEN 
    271               CALL iom_get( numror, jpdom_autoglo, 'ssh_hc_loc_ini', ssh_hc_loc_ini(:,:), lrxios = lxios_read ) 
    272               CALL iom_get( numror, jpdom_autoglo, 'ssh_sc_loc_ini', ssh_sc_loc_ini(:,:), lrxios = lxios_read ) 
     271              CALL iom_get( numror, jpdom_autoglo, 'ssh_hc_loc_ini', ssh_hc_loc_ini(:,:), ldxios = lxios_read ) 
     272              CALL iom_get( numror, jpdom_autoglo, 'ssh_sc_loc_ini', ssh_sc_loc_ini(:,:), ldxios = lxios_read ) 
    273273           ENDIF 
    274274       ELSE 
  • branches/2017/dev_r8600_xios_read/NEMOGCM/NEMO/OPA_SRC/DOM/daymod.F90

    r8612 r8668  
    319319         IF( iom_varid( numror, 'kt', ldstop = .FALSE. ) > 0 ) THEN 
    320320            ! Get Calendar informations 
    321             CALL iom_get( numror, 'kt', zkt, lrxios = lxios_read )   ! last time-step of previous run 
     321            CALL iom_get( numror, 'kt', zkt, ldxios = lxios_read )   ! last time-step of previous run 
    322322            IF(lwp) THEN 
    323323               WRITE(numout,*) ' *** Info read in restart : ' 
     
    338338            IF ( nrstdt == 2 ) THEN 
    339339               ! read the parameters corresponding to nit000 - 1 (last time step of previous run) 
    340                CALL iom_get( numror, 'ndastp', zndastp, lrxios = lxios_read ) 
     340               CALL iom_get( numror, 'ndastp', zndastp, ldxios = lxios_read ) 
    341341               ndastp = NINT( zndastp ) 
    342                CALL iom_get( numror, 'adatrj', adatrj, lrxios = lxios_read ) 
    343           CALL iom_get( numror, 'ntime', ktime, lrxios = lxios_read ) 
     342               CALL iom_get( numror, 'adatrj', adatrj, ldxios = lxios_read ) 
     343          CALL iom_get( numror, 'ntime', ktime, ldxios = lxios_read ) 
    344344          nn_time0=INT(ktime) 
    345345               ! calculate start time in hours and minutes 
  • branches/2017/dev_r8600_xios_read/NEMOGCM/NEMO/OPA_SRC/DOM/domvvl.F90

    r8612 r8668  
    800800         IF( ln_rstart ) THEN                   !* Read the restart file 
    801801            CALL rst_read_open                  !  open the restart file if necessary 
    802             CALL iom_get( numror, jpdom_autoglo, 'sshn'   , sshn, lrxios = lxios_read    ) 
     802            CALL iom_get( numror, jpdom_autoglo, 'sshn'   , sshn, ldxios = lxios_read    ) 
    803803            ! 
    804804            id1 = iom_varid( numror, 'e3t_b', ldstop = .FALSE. ) 
     
    811811            !                             ! --------- ! 
    812812            IF( MIN( id1, id2 ) > 0 ) THEN       ! all required arrays exist 
    813                CALL iom_get( numror, jpdom_autoglo, 'e3t_b', e3t_b(:,:,:), lrxios = lxios_read ) 
    814                CALL iom_get( numror, jpdom_autoglo, 'e3t_n', e3t_n(:,:,:), lrxios = lxios_read ) 
     813               CALL iom_get( numror, jpdom_autoglo, 'e3t_b', e3t_b(:,:,:), ldxios = lxios_read ) 
     814               CALL iom_get( numror, jpdom_autoglo, 'e3t_n', e3t_n(:,:,:), ldxios = lxios_read ) 
    815815               ! needed to restart if land processor not computed  
    816816               IF(lwp) write(numout,*) 'dom_vvl_rst : e3t_b and e3t_n found in restart files' 
     
    826826               IF(lwp) write(numout,*) 'e3t_n set equal to e3t_b.' 
    827827               IF(lwp) write(numout,*) 'neuler is forced to 0' 
    828                CALL iom_get( numror, jpdom_autoglo, 'e3t_b', e3t_b(:,:,:), lrxios = lxios_read ) 
     828               CALL iom_get( numror, jpdom_autoglo, 'e3t_b', e3t_b(:,:,:), ldxios = lxios_read ) 
    829829               e3t_n(:,:,:) = e3t_b(:,:,:) 
    830830               neuler = 0 
     
    833833               IF(lwp) write(numout,*) 'e3t_b set equal to e3t_n.' 
    834834               IF(lwp) write(numout,*) 'neuler is forced to 0' 
    835                CALL iom_get( numror, jpdom_autoglo, 'e3t_n', e3t_n(:,:,:), lrxios = lxios_read ) 
     835               CALL iom_get( numror, jpdom_autoglo, 'e3t_n', e3t_n(:,:,:), ldxios = lxios_read ) 
    836836               e3t_b(:,:,:) = e3t_n(:,:,:) 
    837837               neuler = 0 
     
    858858               !                          ! ----------------------- ! 
    859859               IF( MIN( id3, id4 ) > 0 ) THEN  ! all required arrays exist 
    860                   CALL iom_get( numror, jpdom_autoglo, 'tilde_e3t_b', tilde_e3t_b(:,:,:), lrxios = lxios_read ) 
    861                   CALL iom_get( numror, jpdom_autoglo, 'tilde_e3t_n', tilde_e3t_n(:,:,:), lrxios = lxios_read ) 
     860                  CALL iom_get( numror, jpdom_autoglo, 'tilde_e3t_b', tilde_e3t_b(:,:,:), ldxios = lxios_read ) 
     861                  CALL iom_get( numror, jpdom_autoglo, 'tilde_e3t_n', tilde_e3t_n(:,:,:), ldxios = lxios_read ) 
    862862               ELSE                            ! one at least array is missing 
    863863                  tilde_e3t_b(:,:,:) = 0.0_wp 
     
    868868                  !                       ! ------------ ! 
    869869                  IF( id5 > 0 ) THEN  ! required array exists 
    870                      CALL iom_get( numror, jpdom_autoglo, 'hdiv_lf', hdiv_lf(:,:,:), lrxios = lxios_read ) 
     870                     CALL iom_get( numror, jpdom_autoglo, 'hdiv_lf', hdiv_lf(:,:,:), ldxios = lxios_read ) 
    871871                  ELSE                ! array is missing 
    872872                     hdiv_lf(:,:,:) = 0.0_wp 
  • branches/2017/dev_r8600_xios_read/NEMOGCM/NEMO/OPA_SRC/DOM/iscplrst.F90

    r8612 r8668  
    6565 
    6666      !! get restart variable 
    67       CALL iom_get( numror, jpdom_autoglo, 'tmask'  , ztmask_b, lrxios = lxios_read   ) ! need to extrapolate T/S 
    68       CALL iom_get( numror, jpdom_autoglo, 'umask'  , zumask_b, lrxios = lxios_read   ) ! need to correct barotropic velocity 
    69       CALL iom_get( numror, jpdom_autoglo, 'vmask'  , zvmask_b, lrxios = lxios_read   ) ! need to correct barotropic velocity 
    70       CALL iom_get( numror, jpdom_autoglo, 'smask'  , zsmask_b, lrxios = lxios_read   ) ! need to correct barotropic velocity 
    71       CALL iom_get( numror, jpdom_autoglo, 'e3t_n'  , ze3t_b(:,:,:), lrxios = lxios_read )  ! need to compute temperature correction 
    72       CALL iom_get( numror, jpdom_autoglo, 'e3u_n'  , ze3u_b(:,:,:), lrxios = lxios_read )  ! need to correct barotropic velocity 
    73       CALL iom_get( numror, jpdom_autoglo, 'e3v_n'  , ze3v_b(:,:,:), lrxios = lxios_read )  ! need to correct barotropic velocity 
    74       CALL iom_get( numror, jpdom_autoglo, 'gdepw_n', zdepw_b(:,:,:), lrxios = lxios_read ) ! need to interpol vertical profile (vvl) 
     67      CALL iom_get( numror, jpdom_autoglo, 'tmask'  , ztmask_b, ldxios = lxios_read   ) ! need to extrapolate T/S 
     68      CALL iom_get( numror, jpdom_autoglo, 'umask'  , zumask_b, ldxios = lxios_read   ) ! need to correct barotropic velocity 
     69      CALL iom_get( numror, jpdom_autoglo, 'vmask'  , zvmask_b, ldxios = lxios_read   ) ! need to correct barotropic velocity 
     70      CALL iom_get( numror, jpdom_autoglo, 'smask'  , zsmask_b, ldxios = lxios_read   ) ! need to correct barotropic velocity 
     71      CALL iom_get( numror, jpdom_autoglo, 'e3t_n'  , ze3t_b(:,:,:), ldxios = lxios_read )  ! need to compute temperature correction 
     72      CALL iom_get( numror, jpdom_autoglo, 'e3u_n'  , ze3u_b(:,:,:), ldxios = lxios_read )  ! need to correct barotropic velocity 
     73      CALL iom_get( numror, jpdom_autoglo, 'e3v_n'  , ze3v_b(:,:,:), ldxios = lxios_read )  ! need to correct barotropic velocity 
     74      CALL iom_get( numror, jpdom_autoglo, 'gdepw_n', zdepw_b(:,:,:), ldxios = lxios_read ) ! need to interpol vertical profile (vvl) 
    7575 
    7676      !! read namelist 
  • branches/2017/dev_r8600_xios_read/NEMOGCM/NEMO/OPA_SRC/DYN/dynspg_ts.F90

    r8612 r8668  
    11991199      ! 
    12001200      IF( TRIM(cdrw) == 'READ' ) THEN 
    1201          CALL iom_get( numror, jpdom_autoglo, 'ub2_b'  , ub2_b  (:,:), lrxios = lxios_read )    
    1202          CALL iom_get( numror, jpdom_autoglo, 'vb2_b'  , vb2_b  (:,:), lrxios = lxios_read )  
     1201         CALL iom_get( numror, jpdom_autoglo, 'ub2_b'  , ub2_b  (:,:), ldxios = lxios_read )    
     1202         CALL iom_get( numror, jpdom_autoglo, 'vb2_b'  , vb2_b  (:,:), ldxios = lxios_read )  
    12031203         IF( .NOT.ln_bt_av ) THEN 
    1204             CALL iom_get( numror, jpdom_autoglo, 'sshbb_e'  , sshbb_e(:,:), lrxios = lxios_read )    
    1205             CALL iom_get( numror, jpdom_autoglo, 'ubb_e'    ,   ubb_e(:,:), lrxios = lxios_read )    
    1206             CALL iom_get( numror, jpdom_autoglo, 'vbb_e'    ,   vbb_e(:,:), lrxios = lxios_read ) 
    1207             CALL iom_get( numror, jpdom_autoglo, 'sshb_e'   ,  sshb_e(:,:), lrxios = lxios_read )  
    1208             CALL iom_get( numror, jpdom_autoglo, 'ub_e'     ,    ub_e(:,:), lrxios = lxios_read )    
    1209             CALL iom_get( numror, jpdom_autoglo, 'vb_e'     ,    vb_e(:,:), lrxios = lxios_read ) 
     1204            CALL iom_get( numror, jpdom_autoglo, 'sshbb_e'  , sshbb_e(:,:), ldxios = lxios_read )    
     1205            CALL iom_get( numror, jpdom_autoglo, 'ubb_e'    ,   ubb_e(:,:), ldxios = lxios_read )    
     1206            CALL iom_get( numror, jpdom_autoglo, 'vbb_e'    ,   vbb_e(:,:), ldxios = lxios_read ) 
     1207            CALL iom_get( numror, jpdom_autoglo, 'sshb_e'   ,  sshb_e(:,:), ldxios = lxios_read )  
     1208            CALL iom_get( numror, jpdom_autoglo, 'ub_e'     ,    ub_e(:,:), ldxios = lxios_read )    
     1209            CALL iom_get( numror, jpdom_autoglo, 'vb_e'     ,    vb_e(:,:), ldxios = lxios_read ) 
    12101210         ENDIF 
    12111211#if defined key_agrif 
    12121212         ! Read time integrated fluxes 
    12131213         IF ( .NOT.Agrif_Root() ) THEN 
    1214             CALL iom_get( numror, jpdom_autoglo, 'ub2_i_b'  , ub2_i_b(:,:), lrxios = lxios_read )    
    1215             CALL iom_get( numror, jpdom_autoglo, 'vb2_i_b'  , vb2_i_b(:,:), lrxios = lxios_read ) 
     1214            CALL iom_get( numror, jpdom_autoglo, 'ub2_i_b'  , ub2_i_b(:,:), ldxios = lxios_read )    
     1215            CALL iom_get( numror, jpdom_autoglo, 'vb2_i_b'  , vb2_i_b(:,:), ldxios = lxios_read ) 
    12161216         ENDIF 
    12171217#endif 
  • branches/2017/dev_r8600_xios_read/NEMOGCM/NEMO/OPA_SRC/IOM/in_out_manager.F90

    r8612 r8668  
    151151   LOGICAL       ::   lsp_area = .TRUE.     !: to make a control print over a specific area 
    152152   CHARACTER(lc) ::   cxios_context         !: context name used in xios 
    153    CHARACTER(lc) ::   rxios_context         !: context name used in xios to read restart 
     153   CHARACTER(lc) ::   crxios_context         !: context name used in xios to read restart 
    154154 
    155155   !!---------------------------------------------------------------------- 
  • branches/2017/dev_r8600_xios_read/NEMOGCM/NEMO/OPA_SRC/IOM/iom.F90

    r8616 r8668  
    106106      CHARACTER(len=10) :: clname 
    107107      INTEGER           :: ji, jkmin 
    108       LOGICAL :: lrst_context              ! is context related to restart 
     108      LOGICAL :: llrst_context              ! is context related to restart 
    109109      ! 
    110110      REAL(wp), ALLOCATABLE, DIMENSION(:,:) :: zt_bnds, zw_bnds 
     
    117117      CALL xios_context_initialize(TRIM(clname), mpi_comm_opa) 
    118118      CALL iom_swap( cdname ) 
    119       lrst_context =  (TRIM(cdname) == TRIM(rxios_context)) 
     119      llrst_context =  (TRIM(cdname) == TRIM(crxios_context)) 
    120120 
    121121      ! Calendar type is now defined in xml file  
     
    130130 
    131131      ! horizontal grid definition 
    132       IF(.NOT.lrst_context) CALL set_scalar 
     132      IF(.NOT.llrst_context) CALL set_scalar 
    133133 
    134134      IF( TRIM(cdname) == TRIM(cxios_context) ) THEN   
     
    162162         CALL dom_grid_glo   ! Return to parent grid domain 
    163163         ! 
    164          IF( ln_cfmeta .AND. TRIM(cdname) .NE. TRIM(rxios_context)) THEN   ! Add additional grid metadata 
     164         IF( ln_cfmeta .AND. TRIM(cdname) .NE. TRIM(crxios_context)) THEN   ! Add additional grid metadata 
    165165            CALL iom_set_domain_attr("grid_T", area = e1e2t_crs(nldi:nlei, nldj:nlej)) 
    166166            CALL iom_set_domain_attr("grid_U", area = e1u_crs(nldi:nlei, nldj:nlej) * e2u_crs(nldi:nlei, nldj:nlej)) 
     
    175175 
    176176      ! vertical grid definition 
    177       IF(.NOT.lrst_context) THEN 
     177      IF(.NOT.llrst_context) THEN 
    178178          CALL iom_set_axis_attr( "deptht", paxis = gdept_1d ) 
    179179          CALL iom_set_axis_attr( "depthu", paxis = gdept_1d ) 
     
    206206      ENDIF    
    207207      ! automatic definitions of some of the xml attributs 
    208       IF( lrst_context ) THEN 
     208      IF( llrst_context ) THEN 
    209209!set names of the fields in restart file IF using XIOS to read/write data 
    210210       CALL set_rst_context() 
     
    724724   !!                   INTERFACE iom_get 
    725725   !!---------------------------------------------------------------------- 
    726    SUBROUTINE iom_g0d( kiomid, cdvar, pvar, ktime, lrxios ) 
     726   SUBROUTINE iom_g0d( kiomid, cdvar, pvar, ktime, ldxios ) 
    727727      INTEGER         , INTENT(in   )                 ::   kiomid    ! Identifier of the file 
    728728      CHARACTER(len=*), INTENT(in   )                 ::   cdvar     ! Name of the variable 
    729729      REAL(wp)        , INTENT(  out)                 ::   pvar      ! read field 
    730730      INTEGER         , INTENT(in   ),     OPTIONAL   ::   ktime     ! record number 
    731       LOGICAL         , INTENT(in   ),     OPTIONAL   ::   lrxios    ! use xios to read restart 
     731      LOGICAL         , INTENT(in   ),     OPTIONAL   ::   ldxios    ! use xios to read restart 
    732732      ! 
    733733      INTEGER                                         ::   idvar     ! variable id 
     
    737737      CHARACTER(LEN=100)                              ::   clname    ! file name 
    738738      CHARACTER(LEN=1)                                ::   cldmspc   ! 
    739       LOGICAL                                         ::   lxios 
    740       ! 
    741       lxios = .FALSE. 
    742       IF( PRESENT(lrxios) ) lxios = lrxios 
    743  
    744       IF(.NOT.lxios) THEN  ! read data using default library 
     739      LOGICAL                                         ::   llxios 
     740      ! 
     741      llxios = .FALSE. 
     742      IF( PRESENT(ldxios) ) llxios = ldxios 
     743 
     744      IF(.NOT.llxios) THEN  ! read data using default library 
    745745         itime = 1 
    746746         IF( PRESENT(ktime) ) itime = ktime 
     
    767767      ELSE 
    768768         IF(lwp) WRITE(numout,*) 'XIOS RST READ (0D): ', trim(cdvar) 
    769          CALL iom_swap( TRIM(rxios_context) ) 
     769         CALL iom_swap( TRIM(crxios_context) ) 
    770770         CALL xios_recv_field( trim(cdvar), pvar) 
    771771         CALL iom_swap( TRIM(cxios_context) ) 
     
    773773   END SUBROUTINE iom_g0d 
    774774 
    775    SUBROUTINE iom_g1d( kiomid, kdom, cdvar, pvar, ktime, kstart, kcount, lrxios ) 
     775   SUBROUTINE iom_g1d( kiomid, kdom, cdvar, pvar, ktime, kstart, kcount, ldxios ) 
    776776      INTEGER         , INTENT(in   )                         ::   kiomid    ! Identifier of the file 
    777777      INTEGER         , INTENT(in   )                         ::   kdom      ! Type of domain to be read 
     
    781781      INTEGER         , INTENT(in   ), DIMENSION(1), OPTIONAL ::   kstart    ! start axis position of the reading  
    782782      INTEGER         , INTENT(in   ), DIMENSION(1), OPTIONAL ::   kcount    ! number of points in each axis 
    783       LOGICAL         , INTENT(in   ),               OPTIONAL ::   lrxios    ! read data using XIOS 
     783      LOGICAL         , INTENT(in   ),               OPTIONAL ::   ldxios    ! read data using XIOS 
    784784      ! 
    785785      IF( kiomid > 0 ) THEN 
    786786         IF( iom_file(kiomid)%nfid > 0 ) CALL iom_get_123d( kiomid, kdom       , cdvar        , pv_r1d=pvar,   & 
    787787              &                                                     ktime=ktime, kstart=kstart, kcount=kcount, & 
    788               &                                                     lrxios=lrxios ) 
     788              &                                                     ldxios=ldxios ) 
    789789      ENDIF 
    790790   END SUBROUTINE iom_g1d 
    791791 
    792    SUBROUTINE iom_g2d( kiomid, kdom, cdvar, pvar, ktime, kstart, kcount, lrowattr, lrxios) 
     792   SUBROUTINE iom_g2d( kiomid, kdom, cdvar, pvar, ktime, kstart, kcount, lrowattr, ldxios) 
    793793      INTEGER         , INTENT(in   )                           ::   kiomid    ! Identifier of the file 
    794794      INTEGER         , INTENT(in   )                           ::   kdom      ! Type of domain to be read 
     
    802802                                                                               ! called open_ocean_jstart to set the start 
    803803                                                                               ! value for the 2nd dimension (netcdf only) 
    804       LOGICAL         , INTENT(in   ),                 OPTIONAL ::   lrxios    ! read data using XIOS 
     804      LOGICAL         , INTENT(in   ),                 OPTIONAL ::   ldxios    ! read data using XIOS 
    805805      ! 
    806806      IF( kiomid > 0 ) THEN 
    807807         IF( iom_file(kiomid)%nfid > 0 ) CALL iom_get_123d( kiomid, kdom       , cdvar        , pv_r2d=pvar,   & 
    808808              &                                                     ktime=ktime, kstart=kstart, kcount=kcount, & 
    809               &                                                     lrowattr=lrowattr,  lrxios=lrxios) 
     809              &                                                     lrowattr=lrowattr,  ldxios=ldxios) 
    810810      ENDIF 
    811811   END SUBROUTINE iom_g2d 
    812812 
    813    SUBROUTINE iom_g3d( kiomid, kdom, cdvar, pvar, ktime, kstart, kcount, lrowattr, lrxios ) 
     813   SUBROUTINE iom_g3d( kiomid, kdom, cdvar, pvar, ktime, kstart, kcount, lrowattr, ldxios ) 
    814814      INTEGER         , INTENT(in   )                             ::   kiomid    ! Identifier of the file 
    815815      INTEGER         , INTENT(in   )                             ::   kdom      ! Type of domain to be read 
     
    823823                                                                                 ! called open_ocean_jstart to set the start 
    824824                                                                                 ! value for the 2nd dimension (netcdf only) 
    825       LOGICAL         , INTENT(in   ),                   OPTIONAL ::   lrxios    ! read data using XIOS 
     825      LOGICAL         , INTENT(in   ),                   OPTIONAL ::   ldxios    ! read data using XIOS 
    826826      ! 
    827827      IF( kiomid > 0 ) THEN 
    828828         IF( iom_file(kiomid)%nfid > 0 ) CALL iom_get_123d( kiomid, kdom       , cdvar        , pv_r3d=pvar,   & 
    829829              &                                                     ktime=ktime, kstart=kstart, kcount=kcount, & 
    830               &                                                     lrowattr=lrowattr, lrxios=lrxios ) 
     830              &                                                     lrowattr=lrowattr, ldxios=ldxios ) 
    831831      ENDIF 
    832832   END SUBROUTINE iom_g3d 
     
    836836         &                  pv_r1d, pv_r2d, pv_r3d,   & 
    837837         &                  ktime , kstart, kcount,   & 
    838          &                  lrowattr, lrxios        ) 
     838         &                  lrowattr, ldxios        ) 
    839839      !!----------------------------------------------------------------------- 
    840840      !!                  ***  ROUTINE  iom_get_123d  *** 
     
    857857                                                                           ! called open_ocean_jstart to set the start 
    858858                                                                           ! value for the 2nd dimension (netcdf only) 
    859       LOGICAL                    , INTENT(in   ), OPTIONAL ::   lrxios     ! use XIOS to read restart 
    860       ! 
    861       LOGICAL                        ::   lxios       ! local definition for XIOS read 
     859      LOGICAL                    , INTENT(in   ), OPTIONAL ::   ldxios     ! use XIOS to read restart 
     860      ! 
     861      LOGICAL                        ::   llxios       ! local definition for XIOS read 
    862862      LOGICAL                        ::   llnoov      ! local definition to read overlap 
    863863      LOGICAL                        ::   luse_jattr  ! local definition to read open_ocean_jstart file attribute 
     
    887887      ! 
    888888      REAL(wp)                       :: gma, gmi 
    889       lxios = .FALSE. 
    890       if(PRESENT(lrxios)) lxios = lrxios 
     889      llxios = .FALSE. 
     890      if(PRESENT(ldxios)) llxios = ldxios 
    891891      idvar = iom_varid( kiomid, cdvar )  
    892892      idom = kdom 
    893893 
    894       IF(.NOT.lxios) THEN 
     894      IF(.NOT.llxios) THEN 
    895895          clname = iom_file(kiomid)%name   !   esier to read 
    896896          clinfo = '          iom_get_123d, file: '//trim(clname)//', var: '//trim(cdvar) 
     
    11231123#if defined key_iomput 
    11241124!would be good to be able to check which context is active and swap only if current is not restart 
    1125           CALL iom_swap( TRIM(rxios_context) )  
     1125          CALL iom_swap( TRIM(crxios_context) )  
    11261126          IF( PRESENT(pv_r3d) ) THEN 
    11271127             if(lwp) write(numout,*) 'XIOS RST READ (3D): ',trim(cdvar) 
     
    16261626 
    16271627 
    1628    SUBROUTINE set_grid( cdgrd, plon, plat, lxios ) 
     1628   SUBROUTINE set_grid( cdgrd, plon, plat, ldxios ) 
    16291629      !!---------------------------------------------------------------------- 
    16301630      !!                     ***  ROUTINE set_grid  *** 
     
    16391639      REAL(wp), DIMENSION(jpi,jpj,jpk) ::   zmask 
    16401640      INTEGER  :: ni,nj 
    1641       LOGICAL, INTENT(IN) :: lxios 
     1641      LOGICAL, INTENT(IN) :: ldxios 
    16421642       
    16431643      ni=nlei-nldi+1 ; nj=nlej-nldj+1 
     
    16481648         &                                     latvalue = RESHAPE(plat(nldi:nlei, nldj:nlej),(/ ni*nj /)))   
    16491649 
    1650       IF ( ln_mskland.AND.(.NOT.lxios) ) THEN 
     1650      IF ( ln_mskland.AND.(.NOT.ldxios) ) THEN 
    16511651         ! mask land points, keep values on coast line -> specific mask for U, V and W points 
    16521652         SELECT CASE ( cdgrd ) 
  • branches/2017/dev_r8600_xios_read/NEMOGCM/NEMO/OPA_SRC/IOM/restart.F90

    r8612 r8668  
    202202         IF(.NOT.lxios_set) lxios_read = lxios_read.AND.lxios_sini 
    203203         IF( lxios_read) THEN 
    204            rxios_context = 'nemo_rst' 
     204           crxios_context = 'nemo_rst' 
    205205         if(.NOT.lxios_set) then 
    206206             IF(lwp) WRITE(numout,*) 'Enable restart reading by XIOS' 
    207              CALL iom_init( rxios_context ) 
     207             CALL iom_init( crxios_context ) 
    208208             lxios_set = .TRUE. 
    209209         endif 
    210210         ENDIF 
    211211         IF( TRIM(Agrif_CFixed()) /= '0' .AND. lxios_read) THEN 
    212             CALL iom_init( rxios_context ) 
     212            CALL iom_init( crxios_context ) 
    213213            IF(lwp) WRITE(numout,*) 'Enable restart reading by XIOS for AGRIF' 
    214214            lxios_set = .TRUE. 
     
    237237      ! Check dynamics and tracer time-step consistency and force Euler restart if changed 
    238238      IF( iom_varid( numror, 'rdt', ldstop = .FALSE. ) > 0 )   THEN 
    239          CALL iom_get( numror, 'rdt', zrdt, lrxios = lxios_read ) 
     239         CALL iom_get( numror, 'rdt', zrdt, ldxios = lxios_read ) 
    240240         IF( zrdt /= rdt )   neuler = 0 
    241241      ENDIF 
    242242 
    243243      ! Diurnal DSST  
    244       IF( ln_diurnal ) CALL iom_get( numror, jpdom_autoglo, 'Dsst' , x_dsst, lrxios = lxios_read )  
     244      IF( ln_diurnal ) CALL iom_get( numror, jpdom_autoglo, 'Dsst' , x_dsst, ldxios = lxios_read )  
    245245      IF ( ln_diurnal_only ) THEN  
    246246         IF(lwp) WRITE( numout, * ) & 
    247247         &   "rst_read:- ln_diurnal_only set, setting rhop=rau0"  
    248248         rhop = rau0 
    249          CALL iom_get( numror, jpdom_autoglo, 'tn'     , tsn(:,:,1,jp_tem), lrxios = lxios_read )  
     249         CALL iom_get( numror, jpdom_autoglo, 'tn'     , tsn(:,:,1,jp_tem), ldxios = lxios_read )  
    250250         RETURN  
    251251      ENDIF   
    252252       
    253253      IF( iom_varid( numror, 'ub', ldstop = .FALSE. ) > 0 ) THEN 
    254          CALL iom_get( numror, jpdom_autoglo, 'ub'     , ub, lrxios = lxios_read                )   ! before fields 
    255          CALL iom_get( numror, jpdom_autoglo, 'vb'     , vb, lrxios = lxios_read                ) 
    256          CALL iom_get( numror, jpdom_autoglo, 'tb'     , tsb(:,:,:,jp_tem), lrxios = lxios_read ) 
    257          CALL iom_get( numror, jpdom_autoglo, 'sb'     , tsb(:,:,:,jp_sal), lrxios = lxios_read ) 
    258          CALL iom_get( numror, jpdom_autoglo, 'sshb'   , sshb, lrxios = lxios_read              ) 
     254         CALL iom_get( numror, jpdom_autoglo, 'ub'     , ub, ldxios = lxios_read                )   ! before fields 
     255         CALL iom_get( numror, jpdom_autoglo, 'vb'     , vb, ldxios = lxios_read                ) 
     256         CALL iom_get( numror, jpdom_autoglo, 'tb'     , tsb(:,:,:,jp_tem), ldxios = lxios_read ) 
     257         CALL iom_get( numror, jpdom_autoglo, 'sb'     , tsb(:,:,:,jp_sal), ldxios = lxios_read ) 
     258         CALL iom_get( numror, jpdom_autoglo, 'sshb'   , sshb, ldxios = lxios_read              ) 
    259259      ELSE 
    260260         neuler = 0 
    261261      ENDIF 
    262262      ! 
    263       CALL iom_get( numror, jpdom_autoglo, 'un'     , un, lrxios = lxios_read )   ! now    fields 
    264       CALL iom_get( numror, jpdom_autoglo, 'vn'     , vn, lrxios = lxios_read ) 
    265       CALL iom_get( numror, jpdom_autoglo, 'tn'     , tsn(:,:,:,jp_tem), lrxios = lxios_read ) 
    266       CALL iom_get( numror, jpdom_autoglo, 'sn'     , tsn(:,:,:,jp_sal), lrxios = lxios_read ) 
    267       CALL iom_get( numror, jpdom_autoglo, 'sshn'   , sshn, lrxios = lxios_read ) 
     263      CALL iom_get( numror, jpdom_autoglo, 'un'     , un, ldxios = lxios_read )   ! now    fields 
     264      CALL iom_get( numror, jpdom_autoglo, 'vn'     , vn, ldxios = lxios_read ) 
     265      CALL iom_get( numror, jpdom_autoglo, 'tn'     , tsn(:,:,:,jp_tem), ldxios = lxios_read ) 
     266      CALL iom_get( numror, jpdom_autoglo, 'sn'     , tsn(:,:,:,jp_sal), ldxios = lxios_read ) 
     267      CALL iom_get( numror, jpdom_autoglo, 'sshn'   , sshn, ldxios = lxios_read ) 
    268268      IF( iom_varid( numror, 'rhop', ldstop = .FALSE. ) > 0 ) THEN 
    269          CALL iom_get( numror, jpdom_autoglo, 'rhop'   , rhop, lrxios = lxios_read )   ! now    potential density 
     269         CALL iom_get( numror, jpdom_autoglo, 'rhop'   , rhop, ldxios = lxios_read )   ! now    potential density 
    270270      ELSE 
    271271         CALL eos( tsn, rhd, rhop, gdept_n(:,:,:) )    
  • branches/2017/dev_r8600_xios_read/NEMOGCM/NEMO/OPA_SRC/SBC/sbcapr.F90

    r8612 r8668  
    153153         IF( ln_rstart .AND. iom_varid( numror, 'ssh_ibb', ldstop = .FALSE. ) > 0 ) THEN  
    154154            IF(lwp) WRITE(numout,*) 'sbc_apr:   ssh_ibb read in the restart file' 
    155             CALL iom_get( numror, jpdom_autoglo, 'ssh_ibb', ssh_ibb, lrxios = lxios_read )   ! before inv. barometer ssh 
     155            CALL iom_get( numror, jpdom_autoglo, 'ssh_ibb', ssh_ibb, ldxios = lxios_read )   ! before inv. barometer ssh 
    156156            ! 
    157157         ELSE                                         !* no restart: set from nit000 values 
  • branches/2017/dev_r8600_xios_read/NEMOGCM/NEMO/OPA_SRC/SBC/sbcisf.F90

    r8612 r8668  
    219219                 & iom_varid( numror, 'fwf_isf_b', ldstop = .FALSE. ) > 0 ) THEN 
    220220               IF(lwp) WRITE(numout,*) '          nit000-1 isf tracer content forcing fields read in the restart file' 
    221                CALL iom_get( numror, jpdom_autoglo, 'fwf_isf_b', fwfisf_b(:,:), lrxios = lxios_read )   ! before salt content isf_tsc trend 
    222                CALL iom_get( numror, jpdom_autoglo, 'isf_sc_b', risf_tsc_b(:,:,jp_sal), lrxios = lxios_read )   ! before salt content isf_tsc trend 
    223                CALL iom_get( numror, jpdom_autoglo, 'isf_hc_b', risf_tsc_b(:,:,jp_tem), lrxios = lxios_read )   ! before salt content isf_tsc trend 
     221               CALL iom_get( numror, jpdom_autoglo, 'fwf_isf_b', fwfisf_b(:,:), ldxios = lxios_read )   ! before salt content isf_tsc trend 
     222               CALL iom_get( numror, jpdom_autoglo, 'isf_sc_b', risf_tsc_b(:,:,jp_sal), ldxios = lxios_read )   ! before salt content isf_tsc trend 
     223               CALL iom_get( numror, jpdom_autoglo, 'isf_hc_b', risf_tsc_b(:,:,jp_tem), ldxios = lxios_read )   ! before salt content isf_tsc trend 
    224224           ELSE 
    225225               fwfisf_b(:,:)    = fwfisf(:,:) 
  • branches/2017/dev_r8600_xios_read/NEMOGCM/NEMO/OPA_SRC/SBC/sbcmod.F90

    r8612 r8668  
    458458            & iom_varid( numror, 'utau_b', ldstop = .FALSE. ) > 0 ) THEN 
    459459            IF(lwp) WRITE(numout,*) '          nit000-1 surface forcing fields red in the restart file' 
    460             CALL iom_get( numror, jpdom_autoglo, 'utau_b', utau_b, lrxios = lxios_read )   ! before i-stress  (U-point) 
    461             CALL iom_get( numror, jpdom_autoglo, 'vtau_b', vtau_b, lrxios = lxios_read )   ! before j-stress  (V-point) 
    462             CALL iom_get( numror, jpdom_autoglo, 'qns_b' , qns_b, lrxios = lxios_read  )   ! before non solar heat flux (T-point) 
     460            CALL iom_get( numror, jpdom_autoglo, 'utau_b', utau_b, ldxios = lxios_read )   ! before i-stress  (U-point) 
     461            CALL iom_get( numror, jpdom_autoglo, 'vtau_b', vtau_b, ldxios = lxios_read )   ! before j-stress  (V-point) 
     462            CALL iom_get( numror, jpdom_autoglo, 'qns_b' , qns_b, ldxios = lxios_read  )   ! before non solar heat flux (T-point) 
    463463            ! The 3D heat content due to qsr forcing is treated in traqsr 
    464             ! CALL iom_get( numror, jpdom_autoglo, 'qsr_b' , qsr_b, lrxios = lxios_read  ) ! before     solar heat flux (T-point) 
    465             CALL iom_get( numror, jpdom_autoglo, 'emp_b', emp_b, lrxios = lxios_read  )    ! before     freshwater flux (T-point) 
     464            ! CALL iom_get( numror, jpdom_autoglo, 'qsr_b' , qsr_b, ldxios = lxios_read  ) ! before     solar heat flux (T-point) 
     465            CALL iom_get( numror, jpdom_autoglo, 'emp_b', emp_b, ldxios = lxios_read  )    ! before     freshwater flux (T-point) 
    466466            ! To ensure restart capability with 3.3x/3.4 restart files    !! to be removed in v3.6 
    467467            IF( iom_varid( numror, 'sfx_b', ldstop = .FALSE. ) > 0 ) THEN 
    468                CALL iom_get( numror, jpdom_autoglo, 'sfx_b', sfx_b, lrxios = lxios_read )  ! before salt flux (T-point) 
     468               CALL iom_get( numror, jpdom_autoglo, 'sfx_b', sfx_b, ldxios = lxios_read )  ! before salt flux (T-point) 
    469469            ELSE 
    470470               sfx_b (:,:) = sfx(:,:) 
  • branches/2017/dev_r8600_xios_read/NEMOGCM/NEMO/OPA_SRC/SBC/sbcrnf.F90

    r8612 r8668  
    149149            & iom_varid( numror, 'rnf_b', ldstop = .FALSE. ) > 0 ) THEN 
    150150            IF(lwp) WRITE(numout,*) '          nit000-1 runoff forcing fields red in the restart file', lxios_read 
    151             CALL iom_get( numror, jpdom_autoglo, 'rnf_b', rnf_b, lrxios = lxios_read )     ! before runoff 
    152             CALL iom_get( numror, jpdom_autoglo, 'rnf_hc_b', rnf_tsc_b(:,:,jp_tem), lrxios = lxios_read )   ! before heat content of runoff 
    153             CALL iom_get( numror, jpdom_autoglo, 'rnf_sc_b', rnf_tsc_b(:,:,jp_sal), lrxios = lxios_read )   ! before salinity content of runoff 
     151            CALL iom_get( numror, jpdom_autoglo, 'rnf_b', rnf_b, ldxios = lxios_read )     ! before runoff 
     152            CALL iom_get( numror, jpdom_autoglo, 'rnf_hc_b', rnf_tsc_b(:,:,jp_tem), ldxios = lxios_read )   ! before heat content of runoff 
     153            CALL iom_get( numror, jpdom_autoglo, 'rnf_sc_b', rnf_tsc_b(:,:,jp_sal), ldxios = lxios_read )   ! before salinity content of runoff 
    154154         ELSE                                                   !* no restart: set from nit000 values 
    155155            IF(lwp) WRITE(numout,*) '          nit000-1 runoff forcing fields set to nit000' 
  • branches/2017/dev_r8600_xios_read/NEMOGCM/NEMO/OPA_SRC/SBC/sbcssm.F90

    r8612 r8668  
    207207         IF( ln_rstart .AND. iom_varid( numror, 'nn_fsbc', ldstop = .FALSE. ) > 0 ) THEN 
    208208            l_ssm_mean = .TRUE. 
    209             CALL iom_get( numror               , 'nn_fsbc', zf_sbc, lrxios = lxios_read )    ! sbc frequency of previous run 
    210             CALL iom_get( numror, jpdom_autoglo, 'ssu_m'  , ssu_m, lrxios = lxios_read  )    ! sea surface mean velocity    (U-point) 
    211             CALL iom_get( numror, jpdom_autoglo, 'ssv_m'  , ssv_m, lrxios = lxios_read  )    !   "         "    velocity    (V-point) 
    212             CALL iom_get( numror, jpdom_autoglo, 'sst_m'  , sst_m, lrxios = lxios_read  )    !   "         "    temperature (T-point) 
    213             CALL iom_get( numror, jpdom_autoglo, 'sss_m'  , sss_m, lrxios = lxios_read  )    !   "         "    salinity    (T-point) 
    214             CALL iom_get( numror, jpdom_autoglo, 'ssh_m'  , ssh_m, lrxios = lxios_read  )    !   "         "    height      (T-point) 
    215             CALL iom_get( numror, jpdom_autoglo, 'e3t_m'  , e3t_m, lrxios = lxios_read  )    ! 1st level thickness          (T-point) 
    216             CALL iom_get( numror, jpdom_autoglo, 'e3t_m', e3t_m, lrxios = lxios_read ) 
     209            CALL iom_get( numror               , 'nn_fsbc', zf_sbc, ldxios = lxios_read )    ! sbc frequency of previous run 
     210            CALL iom_get( numror, jpdom_autoglo, 'ssu_m'  , ssu_m, ldxios = lxios_read  )    ! sea surface mean velocity    (U-point) 
     211            CALL iom_get( numror, jpdom_autoglo, 'ssv_m'  , ssv_m, ldxios = lxios_read  )    !   "         "    velocity    (V-point) 
     212            CALL iom_get( numror, jpdom_autoglo, 'sst_m'  , sst_m, ldxios = lxios_read  )    !   "         "    temperature (T-point) 
     213            CALL iom_get( numror, jpdom_autoglo, 'sss_m'  , sss_m, ldxios = lxios_read  )    !   "         "    salinity    (T-point) 
     214            CALL iom_get( numror, jpdom_autoglo, 'ssh_m'  , ssh_m, ldxios = lxios_read  )    !   "         "    height      (T-point) 
     215            CALL iom_get( numror, jpdom_autoglo, 'e3t_m'  , e3t_m, ldxios = lxios_read  )    ! 1st level thickness          (T-point) 
     216            CALL iom_get( numror, jpdom_autoglo, 'e3t_m', e3t_m, ldxios = lxios_read ) 
    217217            ! fraction of solar net radiation absorbed in 1st T level 
    218218            IF( iom_varid( numror, 'frq_m', ldstop = .FALSE. ) > 0 ) THEN 
    219                CALL iom_get( numror, jpdom_autoglo, 'frq_m'  , frq_m, lrxios = lxios_read  ) 
     219               CALL iom_get( numror, jpdom_autoglo, 'frq_m'  , frq_m, ldxios = lxios_read  ) 
    220220            ELSE 
    221221               frq_m(:,:) = 1._wp   ! default definition 
  • branches/2017/dev_r8600_xios_read/NEMOGCM/NEMO/OPA_SRC/TRA/traqsr.F90

    r8612 r8668  
    139139            IF(lwp) WRITE(numout,*) '          nit000-1 qsr tracer content forcing field read in the restart file' 
    140140            z1_2 = 0.5_wp 
    141             CALL iom_get( numror, jpdom_autoglo, 'qsr_hc_b', qsr_hc_b, lrxios = lxios_read )   ! before heat content trend due to Qsr flux 
     141            CALL iom_get( numror, jpdom_autoglo, 'qsr_hc_b', qsr_hc_b, ldxios = lxios_read )   ! before heat content trend due to Qsr flux 
    142142         ELSE                                           ! No restart or restart not found: Euler forward time stepping 
    143143            z1_2 = 1._wp 
     
    430430      ! 1st ocean level attenuation coefficient (used in sbcssm) 
    431431      IF( iom_varid( numror, 'fraqsr_1lev', ldstop = .FALSE. ) > 0 ) THEN 
    432          CALL iom_get( numror, jpdom_autoglo, 'fraqsr_1lev'  , fraqsr_1lev, lrxios = lxios_read  ) 
     432         CALL iom_get( numror, jpdom_autoglo, 'fraqsr_1lev'  , fraqsr_1lev, ldxios = lxios_read  ) 
    433433      ELSE 
    434434         fraqsr_1lev(:,:) = 1._wp   ! default : no penetration 
  • branches/2017/dev_r8600_xios_read/NEMOGCM/NEMO/OPA_SRC/TRA/trasbc.F90

    r8612 r8668  
    109109            zfact = 0.5_wp 
    110110            sbc_tsc(:,:,:) = 0._wp 
    111             CALL iom_get( numror, jpdom_autoglo, 'sbc_hc_b', sbc_tsc_b(:,:,jp_tem), lrxios = lxios_read )   ! before heat content sbc trend 
    112             CALL iom_get( numror, jpdom_autoglo, 'sbc_sc_b', sbc_tsc_b(:,:,jp_sal), lrxios = lxios_read )   ! before salt content sbc trend 
     111            CALL iom_get( numror, jpdom_autoglo, 'sbc_hc_b', sbc_tsc_b(:,:,jp_tem), ldxios = lxios_read )   ! before heat content sbc trend 
     112            CALL iom_get( numror, jpdom_autoglo, 'sbc_sc_b', sbc_tsc_b(:,:,jp_sal), ldxios = lxios_read )   ! before salt content sbc trend 
    113113         ELSE                                   ! No restart or restart not found: Euler forward time stepping 
    114114            zfact = 1._wp 
  • branches/2017/dev_r8600_xios_read/NEMOGCM/NEMO/OPA_SRC/ZDF/zdfgls.F90

    r8612 r8668  
    11761176            ! 
    11771177            IF( MIN( id1, id2, id3, id4, id5, id6 ) > 0 ) THEN        ! all required arrays exist 
    1178                CALL iom_get( numror, jpdom_autoglo, 'en'    , en, lrxios = lxios_read     ) 
    1179                CALL iom_get( numror, jpdom_autoglo, 'avt'   , avt, lrxios = lxios_read    ) 
    1180                CALL iom_get( numror, jpdom_autoglo, 'avm'   , avm, lrxios = lxios_read    ) 
    1181                CALL iom_get( numror, jpdom_autoglo, 'avmu'  , avmu, lrxios = lxios_read   ) 
    1182                CALL iom_get( numror, jpdom_autoglo, 'avmv'  , avmv, lrxios = lxios_read   ) 
    1183                CALL iom_get( numror, jpdom_autoglo, 'mxln'  , mxln, lrxios = lxios_read   ) 
     1178               CALL iom_get( numror, jpdom_autoglo, 'en'    , en, ldxios = lxios_read     ) 
     1179               CALL iom_get( numror, jpdom_autoglo, 'avt'   , avt, ldxios = lxios_read    ) 
     1180               CALL iom_get( numror, jpdom_autoglo, 'avm'   , avm, ldxios = lxios_read    ) 
     1181               CALL iom_get( numror, jpdom_autoglo, 'avmu'  , avmu, ldxios = lxios_read   ) 
     1182               CALL iom_get( numror, jpdom_autoglo, 'avmv'  , avmv, ldxios = lxios_read   ) 
     1183               CALL iom_get( numror, jpdom_autoglo, 'mxln'  , mxln, ldxios = lxios_read   ) 
    11841184            ELSE                         
    11851185               IF(lwp) WRITE(numout,*) ' ===>>>> : previous run without gls scheme, en and mxln computed by iterative loop' 
  • branches/2017/dev_r8600_xios_read/NEMOGCM/NEMO/OPA_SRC/ZDF/zdfini.F90

    r8612 r8668  
    160160         ! file in traadv_cen2 end read here.  
    161161         IF( iom_varid( numror, 'avmb', ldstop = .FALSE. ) > 0 ) THEN 
    162             CALL iom_get( numror, jpdom_unknown, 'avmb', avmb, lrxios = lxios_read ) 
    163             CALL iom_get( numror, jpdom_unknown, 'avtb', avtb, lrxios = lxios_read ) 
     162            CALL iom_get( numror, jpdom_unknown, 'avmb', avmb, ldxios = lxios_read ) 
     163            CALL iom_get( numror, jpdom_unknown, 'avtb', avtb, ldxios = lxios_read ) 
    164164         ENDIF 
    165165      ENDIF 
  • branches/2017/dev_r8600_xios_read/NEMOGCM/NEMO/OPA_SRC/ZDF/zdftke.F90

    r8612 r8668  
    846846           ! 
    847847           IF( id1 > 0 ) THEN                       ! 'en' exists 
    848               CALL iom_get( numror, jpdom_autoglo, 'en', en, lrxios = lxios_read ) 
     848              CALL iom_get( numror, jpdom_autoglo, 'en', en, ldxios = lxios_read ) 
    849849              IF( MIN( id2, id3, id4, id5, id6 ) > 0 ) THEN        ! all required arrays exist 
    850                  CALL iom_get( numror, jpdom_autoglo, 'avt'  , avt, lrxios = lxios_read   ) 
    851                  CALL iom_get( numror, jpdom_autoglo, 'avm'  , avm, lrxios = lxios_read   ) 
    852                  CALL iom_get( numror, jpdom_autoglo, 'avmu' , avmu, lrxios = lxios_read  ) 
    853                  CALL iom_get( numror, jpdom_autoglo, 'avmv' , avmv, lrxios = lxios_read  ) 
    854                  CALL iom_get( numror, jpdom_autoglo, 'dissl', dissl, lrxios = lxios_read ) 
     850                 CALL iom_get( numror, jpdom_autoglo, 'avt'  , avt, ldxios = lxios_read   ) 
     851                 CALL iom_get( numror, jpdom_autoglo, 'avm'  , avm, ldxios = lxios_read   ) 
     852                 CALL iom_get( numror, jpdom_autoglo, 'avmu' , avmu, ldxios = lxios_read  ) 
     853                 CALL iom_get( numror, jpdom_autoglo, 'avmv' , avmv, ldxios = lxios_read  ) 
     854                 CALL iom_get( numror, jpdom_autoglo, 'dissl', dissl, ldxios = lxios_read ) 
    855855              ELSE                                                 ! one at least array is missing 
    856856                 CALL tke_avn                                          ! compute avt, avm, avmu, avmv and dissl (approximation) 
  • branches/2017/dev_r8600_xios_read/NEMOGCM/NEMO/OPA_SRC/step.F90

    r8612 r8668  
    345345      IF( kstp == nitend .OR. indic < 0 ) THEN  
    346346                      CALL iom_context_finalize(      cxios_context          ) ! needed for XIOS+AGRIF 
    347                       IF(lxios_read) CALL iom_context_finalize(      rxios_context          ) 
     347                      IF(lxios_read) CALL iom_context_finalize(      crxios_context          ) 
    348348         IF( ln_crs ) CALL iom_context_finalize( trim(cxios_context)//"_crs" ) !  
    349349      ENDIF 
  • branches/2017/dev_r8600_xios_read/NEMOGCM/NEMO/SAS_SRC/daymod.F90

    r8612 r8668  
    318318         IF( iom_varid( numror, 'kt', ldstop = .FALSE. ) > 0 ) THEN 
    319319            ! Get Calendar informations 
    320             CALL iom_get( numror, 'kt', zk, lrxios = lxios_read )   ! last time-step of previous run 
     320            CALL iom_get( numror, 'kt', zk, ldxios = lxios_read )   ! last time-step of previous run 
    321321            IF(lwp) THEN 
    322322               WRITE(numout,*) ' *** Info read in restart : ' 
     
    337337            IF ( nrstdt == 2 ) THEN 
    338338               ! read the parameters corresponding to nit000 - 1 (last time step of previous run) 
    339                CALL iom_get( numror, 'ndastp', zndastp, lrxios = lxios_read ) 
     339               CALL iom_get( numror, 'ndastp', zndastp, ldxios = lxios_read ) 
    340340               ndastp = NINT( zndastp ) 
    341                CALL iom_get( numror, 'adatrj', adatrj, lrxios = lxios_read ) 
    342           CALL iom_get( numror, 'ntime', ktime, lrxios = lxios_read ) 
     341               CALL iom_get( numror, 'adatrj', adatrj, ldxios = lxios_read ) 
     342          CALL iom_get( numror, 'ntime', ktime, ldxios = lxios_read ) 
    343343          nn_time0=INT(ktime) 
    344344               ! calculate start time in hours and minutes 
Note: See TracChangeset for help on using the changeset viewer.