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

Changeset 8195


Ignore:
Timestamp:
2017-06-20T12:02:35+02:00 (7 years ago)
Author:
andmirek
Message:

ticket #1914 : merge branch branches/UKMO/dev_r5518_GO6_package_XIOS_read

Location:
branches/UKMO/dev_r5518_GO6_package_fix_rnf_MOCI_TEST_SUITE/NEMOGCM
Files:
28 edited

Legend:

Unmodified
Added
Removed
  • branches/UKMO/dev_r5518_GO6_package_fix_rnf_MOCI_TEST_SUITE/NEMOGCM/CONFIG/GYRE_XIOS/EXP00/domain_def.xml

    r8193 r8195  
    191191   </domain>   
    192192 
     193     <domain_group id="grid_N"> 
     194      <domain id="grid_N" long_name="grid nomask"/> 
     195     </domain_group> 
    193196 
    194197   </domain_definition>     
  • branches/UKMO/dev_r5518_GO6_package_fix_rnf_MOCI_TEST_SUITE/NEMOGCM/CONFIG/GYRE_XIOS/EXP00/iodef.xml

    r8193 r8195  
    7979  </context> 
    8080   
     81  <context id="nemo_rst" > 
     82 
     83   <domain_definition src="./domain_def.xml"/> 
     84 
     85   <grid_definition> 
     86     <grid id="grid_T_2D" > 
     87       <domain id="grid_T" /> 
     88     </grid> 
     89     <grid id="grid_T_3D" > 
     90       <domain id="grid_T" /> 
     91       <axis id="deptht" /> 
     92     </grid> 
     93     <grid id="grid_U_2D" > 
     94       <domain id="grid_U" /> 
     95     </grid> 
     96     <grid id="grid_U_3D" > 
     97       <domain id="grid_U" /> 
     98       <axis id="depthu" /> 
     99     </grid> 
     100     <grid id="grid_V_2D" > 
     101       <domain id="grid_V" /> 
     102     </grid> 
     103     <grid id="grid_V_3D" > 
     104       <domain id="grid_V" /> 
     105       <axis id="depthv" /> 
     106     </grid> 
     107     <grid id="grid_W_2D" > 
     108       <domain id="grid_W" /> 
     109     </grid> 
     110     <grid id="grid_W_3D" > 
     111       <domain id="grid_W" /> 
     112       <axis id="depthw" /> 
     113     </grid> 
     114     <grid id="scalarpoint" /> 
     115 
     116     <grid id="Vgrid"> 
     117       <domain domain_ref="ptr" /> 
     118       <axis axis_ref="deptht" /> 
     119     </grid> 
     120 
     121     <grid id="grid_N" > 
     122       <domain domain_ref="grid_N" /> 
     123     </grid> 
     124     <grid id="grid_N_3D" > 
     125       <domain domain_ref="grid_N" /> 
     126       <axis axis_ref="deptht" /> 
     127     </grid> 
     128 
     129    </grid_definition> 
     130 
     131  </context> 
    81132 
    82133  <context id="xios"> 
  • branches/UKMO/dev_r5518_GO6_package_fix_rnf_MOCI_TEST_SUITE/NEMOGCM/CONFIG/SHARED/namelist_ref

    r8193 r8195  
    5050   ln_clobber  = .false.   !  clobber (overwrite) an existing file 
    5151   nn_chunksz  =       0   !  chunksize (bytes) for NetCDF file (works only with iom_nf90 routines) 
     52   ln_xios_read = .FALSE.  !  use XIOS to read restart file (only for a single file restart) 
    5253/ 
    5354! 
  • branches/UKMO/dev_r5518_GO6_package_fix_rnf_MOCI_TEST_SUITE/NEMOGCM/NEMO/OPA_SRC/DIA/diahsb.F90

    r6487 r8195  
    3232   USE timing          ! preformance summary 
    3333   USE wrk_nemo        ! work arrays 
     34   USE iom_def, ONLY : lxios_read 
    3435 
    3536   IMPLICIT NONE 
     
    254255           IF(lwp) WRITE(numout,*) ' dia_hsb_rst at it= ', kt,' date= ', ndastp 
    255256           IF(lwp) WRITE(numout,*) '~~~~~~~' 
    256            CALL iom_get( numror, 'frc_v', frc_v ) 
    257            CALL iom_get( numror, 'frc_t', frc_t ) 
    258            CALL iom_get( numror, 'frc_s', frc_s ) 
     257           CALL iom_get( numror, 'frc_v', frc_v, lrxios = lxios_read ) 
     258           CALL iom_get( numror, 'frc_t', frc_t, lrxios = lxios_read ) 
     259           CALL iom_get( numror, 'frc_s', frc_s, lrxios = lxios_read ) 
    259260           IF( .NOT. lk_vvl ) THEN 
    260               CALL iom_get( numror, 'frc_wn_t', frc_wn_t ) 
    261               CALL iom_get( numror, 'frc_wn_s', frc_wn_s ) 
     261              CALL iom_get( numror, 'frc_wn_t', frc_wn_t, lrxios = lxios_read ) 
     262              CALL iom_get( numror, 'frc_wn_s', frc_wn_s, lrxios = lxios_read ) 
    262263           ENDIF 
    263            CALL iom_get( numror, jpdom_autoglo, 'ssh_ini', ssh_ini ) 
    264            CALL iom_get( numror, jpdom_autoglo, 'e3t_ini', e3t_ini ) 
    265            CALL iom_get( numror, jpdom_autoglo, 'hc_loc_ini', hc_loc_ini ) 
    266            CALL iom_get( numror, jpdom_autoglo, 'sc_loc_ini', sc_loc_ini ) 
     264           CALL iom_get( numror, jpdom_autoglo, 'ssh_ini', ssh_ini, lrxios = lxios_read ) 
     265           CALL iom_get( numror, jpdom_autoglo, 'e3t_ini', e3t_ini, lrxios = lxios_read ) 
     266           CALL iom_get( numror, jpdom_autoglo, 'hc_loc_ini', hc_loc_ini, lrxios = lxios_read ) 
     267           CALL iom_get( numror, jpdom_autoglo, 'sc_loc_ini', sc_loc_ini, lrxios = lxios_read ) 
    267268           IF( .NOT. lk_vvl ) THEN 
    268               CALL iom_get( numror, jpdom_autoglo, 'ssh_hc_loc_ini', ssh_hc_loc_ini ) 
    269               CALL iom_get( numror, jpdom_autoglo, 'ssh_sc_loc_ini', ssh_sc_loc_ini ) 
     269              CALL iom_get( numror, jpdom_autoglo, 'ssh_hc_loc_ini', ssh_hc_loc_ini, lrxios = lxios_read ) 
     270              CALL iom_get( numror, jpdom_autoglo, 'ssh_sc_loc_ini', ssh_sc_loc_ini, lrxios = lxios_read ) 
    270271           ENDIF 
    271272       ELSE 
  • branches/UKMO/dev_r5518_GO6_package_fix_rnf_MOCI_TEST_SUITE/NEMOGCM/NEMO/OPA_SRC/DIA/diawri.F90

    r8193 r8195  
    250250      CALL iom_put( "avt" , avt                        )    ! T vert. eddy diff. coef. 
    251251      CALL iom_put( "avm" , avmu                       )    ! T vert. eddy visc. coef. 
     252#if defined key_zdftke   ||   defined key_esopa 
    252253      IF( lk_zdftke ) THEN    
    253254         CALL iom_put( "tke"      , en                               )    ! TKE budget: Turbulent Kinetic Energy    
    254255         CALL iom_put( "tke_niw"  , e_niw                            )    ! TKE budget: Near-inertial waves    
    255256      ENDIF  
     257#endif 
    256258      CALL iom_put( "avs" , fsavs(:,:,:)               )    ! S vert. eddy diff. coef. (useful only with key_zdfddm) 
    257259                                                            ! Log of eddy diff coef 
  • branches/UKMO/dev_r5518_GO6_package_fix_rnf_MOCI_TEST_SUITE/NEMOGCM/NEMO/OPA_SRC/DOM/daymod.F90

    r8193 r8195  
    3535   USE timing          ! Timing 
    3636   USE restart         ! restart 
     37   USE iom_def, ONLY : lxios_read 
    3738 
    3839   IMPLICIT NONE 
     
    309310         IF( iom_varid( numror, 'kt', ldstop = .FALSE. ) > 0 ) THEN 
    310311            ! Get Calendar informations 
    311             CALL iom_get( numror, 'kt', zkt )   ! last time-step of previous run 
     312            CALL iom_get( numror, 'kt', zkt, lrxios = lxios_read )   ! last time-step of previous run 
    312313            IF(lwp) THEN 
    313314               WRITE(numout,*) ' *** Info read in restart : ' 
     
    328329            IF ( nrstdt == 2 ) THEN 
    329330               ! read the parameters correspondting to nit000 - 1 (last time step of previous run) 
    330                CALL iom_get( numror, 'ndastp', zndastp ) 
     331               CALL iom_get( numror, 'ndastp', zndastp, lrxios = lxios_read ) 
    331332               ndastp = NINT( zndastp ) 
    332                CALL iom_get( numror, 'adatrj', adatrj  ) 
     333               CALL iom_get( numror, 'adatrj', adatrj, lrxios = lxios_read ) 
    333334            ELSE 
    334335               ! parameters correspondting to nit000 - 1 (as we start the step loop with a call to day) 
  • branches/UKMO/dev_r5518_GO6_package_fix_rnf_MOCI_TEST_SUITE/NEMOGCM/NEMO/OPA_SRC/DOM/domain.F90

    r8193 r8195  
    3838   USE timing          ! Timing 
    3939   USE lbclnk          ! ocean lateral boundary condition (or mpp link) 
     40   USE iom_def, ONLY:lxios_read 
    4041 
    4142   IMPLICIT NONE 
     
    138139         &             nn_no   , cn_exp    , cn_ocerst_in, cn_ocerst_out, ln_rstart , ln_rstdate, nn_rstctl,   & 
    139140         &             nn_it000, nn_itend  , nn_date0    , nn_leapy     , nn_istate , nn_stock ,   & 
    140          &             nn_write, ln_dimgnnn, ln_mskland  , ln_cfmeta    , ln_clobber, nn_chunksz, nn_euler 
     141         &             nn_write, ln_dimgnnn, ln_mskland  , ln_cfmeta    , ln_clobber, nn_chunksz, nn_euler, & 
     142         &             ln_xios_read 
    141143      NAMELIST/namdom/ nn_bathy, rn_bathy , rn_e3zps_min, rn_e3zps_rat, nn_msh, rn_hmin,   & 
    142144         &             nn_acc   , rn_atfp     , rn_rdt      , rn_rdtmin ,                  & 
     
    152154      INTEGER  ::   ios                 ! Local integer output status for namelist read 
    153155      !!---------------------------------------------------------------------- 
    154  
     156      ln_xios_read = .false.            ! set in case ln_xios_read is not in namelist 
    155157      REWIND( numnam_ref )              ! Namelist namrun in reference namelist : Parameters of the run 
    156158      READ  ( numnam_ref, namrun, IOSTAT = ios, ERR = 901) 
     
    193195         WRITE(numout,*) '      overwrite an existing file      ln_clobber = ', ln_clobber 
    194196         WRITE(numout,*) '      NetCDF chunksize (bytes)        nn_chunksz = ', nn_chunksz 
     197         WRITE(numout,*) '      READ restart for a single file using XIOS ln_xios_read =', ln_xios_read 
    195198      ENDIF 
    196199 
     
    207210      nwrite = nn_write 
    208211      neuler = nn_euler 
     212      lxios_read = ln_xios_read 
    209213      IF ( neuler == 1 .AND. .NOT. ln_rstart ) THEN 
    210214         WRITE(ctmp1,*) 'ln_rstart =.FALSE., nn_euler is forced to 0 ' 
  • branches/UKMO/dev_r5518_GO6_package_fix_rnf_MOCI_TEST_SUITE/NEMOGCM/NEMO/OPA_SRC/DOM/domvvl.F90

    r6498 r8195  
    3333   USE wrk_nemo        ! Memory allocation 
    3434   USE timing          ! Timing 
     35   USE iom_def, ONLY : lxios_read 
    3536 
    3637   IMPLICIT NONE 
     
    817818         IF( ln_rstart ) THEN                   !* Read the restart file 
    818819            CALL rst_read_open                  !  open the restart file if necessary 
    819             CALL iom_get( numror, jpdom_autoglo, 'sshn'   , sshn    ) 
     820            CALL iom_get( numror, jpdom_autoglo, 'sshn'   , sshn, lrxios = lxios_read    ) 
    820821            ! 
    821822            id1 = iom_varid( numror, 'fse3t_b', ldstop = .FALSE. ) 
     
    828829            !                             ! --------- ! 
    829830            IF( MIN( id1, id2 ) > 0 ) THEN       ! all required arrays exist 
    830                CALL iom_get( numror, jpdom_autoglo, 'fse3t_b', fse3t_b(:,:,:) ) 
    831                CALL iom_get( numror, jpdom_autoglo, 'fse3t_n', fse3t_n(:,:,:) ) 
     831               CALL iom_get( numror, jpdom_autoglo, 'fse3t_b', fse3t_b(:,:,:), lrxios = lxios_read ) 
     832               CALL iom_get( numror, jpdom_autoglo, 'fse3t_n', fse3t_n(:,:,:), lrxios = lxios_read ) 
    832833               ! needed to restart if land processor not computed  
    833834               IF(lwp) write(numout,*) 'dom_vvl_rst : fse3t_b and fse3t_n found in restart files' 
     
    843844               IF(lwp) write(numout,*) 'fse3t_n set equal to fse3t_b.' 
    844845               IF(lwp) write(numout,*) 'neuler is forced to 0' 
    845                CALL iom_get( numror, jpdom_autoglo, 'fse3t_b', fse3t_b(:,:,:) ) 
     846               CALL iom_get( numror, jpdom_autoglo, 'fse3t_b', fse3t_b(:,:,:), lrxios = lxios_read ) 
    846847               fse3t_n(:,:,:) = fse3t_b(:,:,:) 
    847848               neuler = 0 
     
    850851               IF(lwp) write(numout,*) 'fse3t_b set equal to fse3t_n.' 
    851852               IF(lwp) write(numout,*) 'neuler is forced to 0' 
    852                CALL iom_get( numror, jpdom_autoglo, 'fse3t_n', fse3t_n(:,:,:) ) 
     853               CALL iom_get( numror, jpdom_autoglo, 'fse3t_n', fse3t_n(:,:,:), lrxios = lxios_read ) 
    853854               fse3t_b(:,:,:) = fse3t_n(:,:,:) 
    854855               neuler = 0 
     
    875876               !                          ! ----------------------- ! 
    876877               IF( MIN( id3, id4 ) > 0 ) THEN  ! all required arrays exist 
    877                   CALL iom_get( numror, jpdom_autoglo, 'tilde_e3t_b', tilde_e3t_b(:,:,:) ) 
    878                   CALL iom_get( numror, jpdom_autoglo, 'tilde_e3t_n', tilde_e3t_n(:,:,:) ) 
     878                  CALL iom_get( numror, jpdom_autoglo, 'tilde_e3t_b', tilde_e3t_b(:,:,:), lrxios = lxios_read ) 
     879                  CALL iom_get( numror, jpdom_autoglo, 'tilde_e3t_n', tilde_e3t_n(:,:,:), lrxios = lxios_read ) 
    879880               ELSE                            ! one at least array is missing 
    880881                  tilde_e3t_b(:,:,:) = 0.0_wp 
     
    885886                  !                       ! ------------ ! 
    886887                  IF( id5 > 0 ) THEN  ! required array exists 
    887                      CALL iom_get( numror, jpdom_autoglo, 'hdiv_lf', hdiv_lf(:,:,:) ) 
     888                     CALL iom_get( numror, jpdom_autoglo, 'hdiv_lf', hdiv_lf(:,:,:), lrxios = lxios_read ) 
    888889                  ELSE                ! array is missing 
    889890                     hdiv_lf(:,:,:) = 0.0_wp 
  • branches/UKMO/dev_r5518_GO6_package_fix_rnf_MOCI_TEST_SUITE/NEMOGCM/NEMO/OPA_SRC/DYN/dynspg_flt.F90

    r7179 r8195  
    5151   USE agrif_opa_interp 
    5252#endif 
     53   USE iom_def, ONLY : lxios_read 
    5354 
    5455   IMPLICIT NONE 
     
    395396! Caution : extra-hallow 
    396397! gcx and gcxb are defined as: DIMENSION(1-jpr2di:jpi+jpr2di,1-jpr2dj:jpj+jpr2dj) 
    397             CALL iom_get( numror, jpdom_autoglo, 'gcx' , gcx (1:jpi,1:jpj) ) 
    398             CALL iom_get( numror, jpdom_autoglo, 'gcxb', gcxb(1:jpi,1:jpj) ) 
     398            CALL iom_get( numror, jpdom_autoglo, 'gcx' , gcx (1:jpi,1:jpj), lrxios = lxios_read ) ! make sure domain is fine!!!! 
     399            CALL iom_get( numror, jpdom_autoglo, 'gcxb', gcxb(1:jpi,1:jpj), lrxios = lxios_read ) ! make sure domain is fine!!!! 
    399400            IF( neuler == 0 )   gcxb(:,:) = gcx (:,:) 
    400401         ELSE 
  • branches/UKMO/dev_r5518_GO6_package_fix_rnf_MOCI_TEST_SUITE/NEMOGCM/NEMO/OPA_SRC/DYN/dynspg_ts.F90

    r6487 r8195  
    4848   USE asminc          ! Assimilation increment 
    4949#endif 
     50   USE iom_def, ONLY : lxios_read 
    5051 
    5152   IMPLICIT NONE 
     
    10191020      ! 
    10201021      IF( TRIM(cdrw) == 'READ' ) THEN 
    1021          CALL iom_get( numror, jpdom_autoglo, 'ub2_b'  , ub2_b  (:,:) )    
    1022          CALL iom_get( numror, jpdom_autoglo, 'vb2_b'  , vb2_b  (:,:) )  
     1022         CALL iom_get( numror, jpdom_autoglo, 'ub2_b'  , ub2_b  (:,:), lrxios = lxios_read )    
     1023         CALL iom_get( numror, jpdom_autoglo, 'vb2_b'  , vb2_b  (:,:), lrxios = lxios_read )  
    10231024         IF( .NOT.ln_bt_av ) THEN 
    1024             CALL iom_get( numror, jpdom_autoglo, 'sshbb_e'  , sshbb_e(:,:) )    
    1025             CALL iom_get( numror, jpdom_autoglo, 'ubb_e'    ,   ubb_e(:,:) )    
    1026             CALL iom_get( numror, jpdom_autoglo, 'vbb_e'    ,   vbb_e(:,:) ) 
    1027             CALL iom_get( numror, jpdom_autoglo, 'sshb_e'   ,  sshb_e(:,:) )  
    1028             CALL iom_get( numror, jpdom_autoglo, 'ub_e'     ,    ub_e(:,:) )    
    1029             CALL iom_get( numror, jpdom_autoglo, 'vb_e'     ,    vb_e(:,:) ) 
     1025            CALL iom_get( numror, jpdom_autoglo, 'sshbb_e'  , sshbb_e(:,:), lrxios = lxios_read )    
     1026            CALL iom_get( numror, jpdom_autoglo, 'ubb_e'    ,   ubb_e(:,:), lrxios = lxios_read )    
     1027            CALL iom_get( numror, jpdom_autoglo, 'vbb_e'    ,   vbb_e(:,:), lrxios = lxios_read ) 
     1028            CALL iom_get( numror, jpdom_autoglo, 'sshb_e'   ,  sshb_e(:,:), lrxios = lxios_read )  
     1029            CALL iom_get( numror, jpdom_autoglo, 'ub_e'     ,    ub_e(:,:), lrxios = lxios_read )    
     1030            CALL iom_get( numror, jpdom_autoglo, 'vb_e'     ,    vb_e(:,:), lrxios = lxios_read ) 
    10301031         ENDIF 
    10311032#if defined key_agrif 
  • branches/UKMO/dev_r5518_GO6_package_fix_rnf_MOCI_TEST_SUITE/NEMOGCM/NEMO/OPA_SRC/IOM/in_out_manager.F90

    r8193 r8195  
    4949   LOGICAL       ::   ln_clobber       !: clobber (overwrite) an existing file 
    5050   INTEGER       ::   nn_chunksz       !: chunksize (bytes) for NetCDF file (works only with iom_nf90 routines) 
     51   LOGICAL       ::   ln_xios_read     !: use xios to read single file restart 
    5152#if defined key_netcdf4 
    5253   !!---------------------------------------------------------------------- 
     
    152153   LOGICAL       ::   lsp_area = .TRUE.     !: to make a control print over a specific area 
    153154   CHARACTER(lc) ::   cxios_context         !: context name used in xios 
     155   CHARACTER(lc) ::   rxios_context         !: context name used in xios to read restart 
    154156 
    155157   !!---------------------------------------------------------------------- 
  • branches/UKMO/dev_r5518_GO6_package_fix_rnf_MOCI_TEST_SUITE/NEMOGCM/NEMO/OPA_SRC/IOM/iom.F90

    r8193 r8195  
    4141   USE dianam          ! build name of file 
    4242   USE xios 
     43   USE iom_def, ONLY : max_rst_fields, rst_fields 
    4344# endif 
    4445   USE ioipsl, ONLY :  ju2ymds    ! for calendar 
    4546   USE crs             ! Grid coarsening 
     47   USE lib_fortran  
    4648 
    4749   IMPLICIT NONE 
     
    6264   PRIVATE iom_set_domain_attr, iom_set_axis_attr, iom_set_field_attr, iom_set_file_attr, iom_get_file_attr, iom_set_grid_attr 
    6365   PRIVATE set_grid, set_grid_bounds, set_scalar, set_xmlatt, set_mooring, iom_update_file_name, iom_sdate 
     66   PRIVATE set_rst_vars, set_rstr_active 
    6467# endif 
    6568 
     
    136139          &                                    start_date = xios_date(nyear,nmonth,nday,0,0,0) ) 
    137140      END SELECT 
     141 
    138142#endif 
    139143      ! horizontal grid definition 
     
    141145      CALL set_scalar 
    142146 
    143       IF( TRIM(cdname) == TRIM(cxios_context) ) THEN   
    144          CALL set_grid( "T", glamt, gphit )  
    145          CALL set_grid( "U", glamu, gphiu ) 
    146          CALL set_grid( "V", glamv, gphiv ) 
    147          CALL set_grid( "W", glamt, gphit ) 
     147      IF( TRIM(cdname) == TRIM(cxios_context) .OR. TRIM(cdname) == TRIM(rxios_context)) THEN   
     148         CALL set_grid( "T", glamt, gphit, ln_mskland )  
     149         CALL set_grid( "U", glamu, gphiu, ln_mskland ) 
     150         CALL set_grid( "V", glamv, gphiv, ln_mskland ) 
     151         CALL set_grid( "W", glamt, gphit, ln_mskland ) 
    148152         CALL set_grid_znl( gphit ) 
     153         CALL set_grid("N",glamt, gphit, .FALSE.)        ! not masked values 
    149154         ! 
    150          IF( ln_cfmeta ) THEN   ! Add additional grid metadata 
     155         IF( ln_cfmeta .AND. TRIM(cdname) .NE. TRIM(rxios_context)) THEN   ! Add additional grid metadata 
    151156            CALL iom_set_domain_attr("grid_T", area = e12t(nldi:nlei, nldj:nlej)) 
    152157            CALL iom_set_domain_attr("grid_U", area = e12u(nldi:nlei, nldj:nlej)) 
     
    163168         CALL dom_grid_crs   ! Save the parent grid information  & Switch to coarse grid domain 
    164169         ! 
    165          CALL set_grid( "T", glamt_crs, gphit_crs )  
    166          CALL set_grid( "U", glamu_crs, gphiu_crs )  
    167          CALL set_grid( "V", glamv_crs, gphiv_crs )  
    168          CALL set_grid( "W", glamt_crs, gphit_crs )  
     170         CALL set_grid( "T", glamt_crs, gphit_crs, ln_mskland )  
     171         CALL set_grid( "U", glamu_crs, gphiu_crs, ln_mskland )  
     172         CALL set_grid( "V", glamv_crs, gphiv_crs, ln_mskland )  
     173         CALL set_grid( "W", glamt_crs, gphit_crs, ln_mskland )  
    169174         CALL set_grid_znl( gphit_crs ) 
    170175          ! 
    171176         CALL dom_grid_glo   ! Return to parent grid domain 
    172177         ! 
    173          IF( ln_cfmeta ) THEN   ! Add additional grid metadata 
     178         IF( ln_cfmeta .AND. TRIM(cdname) .NE. TRIM(rxios_context)) THEN   ! Add additional grid metadata 
    174179            CALL iom_set_domain_attr("grid_T", area = e1e2t_crs(nldi:nlei, nldj:nlej)) 
    175180            CALL iom_set_domain_attr("grid_U", area = e1u_crs(nldi:nlei, nldj:nlej) * e2u_crs(nldi:nlei, nldj:nlej)) 
     
    184189 
    185190      ! vertical grid definition 
    186       CALL iom_set_axis_attr( "deptht", gdept_1d ) 
    187       CALL iom_set_axis_attr( "depthu", gdept_1d ) 
    188       CALL iom_set_axis_attr( "depthv", gdept_1d ) 
    189       CALL iom_set_axis_attr( "depthw", gdepw_1d ) 
     191      CALL iom_set_axis_attr( "deptht", paxis = gdept_1d ) 
     192      CALL iom_set_axis_attr( "depthu", paxis = gdept_1d ) 
     193      CALL iom_set_axis_attr( "depthv", paxis = gdept_1d ) 
     194      CALL iom_set_axis_attr( "depthw", paxis = gdepw_1d ) 
    190195 
    191196      ! Add vertical grid bounds 
     
    227232       
    228233      ! automatic definitions of some of the xml attributs 
    229       CALL set_xmlatt 
     234      IF( TRIM(cdname) == TRIM(rxios_context)) THEN 
     235!set names of the fields in restart file IF using XIOS to read/write data 
     236       CALL set_rst_vars() 
     237!set which fields are to be read from restart file 
     238       CALL set_rstr_active() 
     239      ELSE 
     240       CALL set_xmlatt 
     241      ENDIF 
    230242 
    231243      CALL set_1point 
     
    241253 
    242254#endif 
    243        
     255 
    244256   END SUBROUTINE iom_init 
    245257 
     258    
     259   SUBROUTINE set_rst_vars() 
     260!set names for variables in restart file 
     261 
     262        rst_fields(:)%vname="NO_NAME";         rst_fields(:)%grid="NO_GRID" 
     263 
     264        rst_fields(1)%vname="rdt";             rst_fields(1)% grid="grid_scalar" 
     265        rst_fields(2)%vname="rdttra1";         rst_fields(2)% grid="grid_scalar"       
     266        rst_fields(3)%vname="un";              rst_fields(3)% grid="grid_N_3D" 
     267        rst_fields(4)%vname="ub";              rst_fields(4)% grid="grid_N_3D" 
     268        rst_fields(5)%vname="vn";              rst_fields(5)% grid="grid_N_3D" 
     269        rst_fields(6)%vname="vb";              rst_fields(6)% grid="grid_N_3D"   
     270        rst_fields(7)%vname="tn";              rst_fields(7)% grid="grid_N_3D" 
     271        rst_fields(8)%vname="tb";              rst_fields(8)% grid="grid_N_3D" 
     272        rst_fields(9)%vname="sn";              rst_fields(9)% grid="grid_N_3D" 
     273        rst_fields(10)%vname="sb";             rst_fields(10)%grid="grid_N_3D" 
     274        rst_fields(11)%vname="sshn";           rst_fields(11)%grid="grid_N" 
     275        rst_fields(12)%vname="sshb";           rst_fields(12)%grid="grid_N" 
     276        rst_fields(13)%vname="hdivn";          rst_fields(13)%grid="grid_N_3D" 
     277        rst_fields(14)%vname="hdivb";          rst_fields(14)%grid="grid_N_3D" 
     278        rst_fields(15)%vname="rhop";           rst_fields(15)%grid="grid_N_3D" 
     279        rst_fields(16)%vname="rotn";           rst_fields(16)%grid="grid_N_3D" 
     280        rst_fields(17)%vname="rotb";           rst_fields(17)%grid="grid_N_3D" 
     281        rst_fields(18)%vname="kt";             rst_fields(18)%grid="grid_scalar" 
     282        rst_fields(19)%vname="ndastp";         rst_fields(19)%grid="grid_scalar" 
     283        rst_fields(20)%vname="adatrj";         rst_fields(20)%grid="grid_scalar" 
     284        rst_fields(21)%vname="utau_b";         rst_fields(21)%grid="grid_N" 
     285        rst_fields(22)%vname="vtau_b";         rst_fields(22)%grid="grid_N" 
     286        rst_fields(23)%vname="qns_b";          rst_fields(23)%grid="grid_N" 
     287        rst_fields(24)%vname="emp_b";          rst_fields(24)%grid="grid_N" 
     288        rst_fields(25)%vname="sfx_b";          rst_fields(25)%grid="grid_N" 
     289        rst_fields(26)%vname="en" ;            rst_fields(26)%grid="grid_N_3D"  
     290        rst_fields(27)%vname="avt";            rst_fields(27)%grid="grid_N_3D" 
     291        rst_fields(28)%vname="avm";            rst_fields(28)%grid="grid_N_3D" 
     292        rst_fields(29)%vname="avmu";           rst_fields(29)%grid="grid_N_3D" 
     293        rst_fields(30)%vname="avmv";           rst_fields(30)%grid="grid_N_3D" 
     294        rst_fields(31)%vname="dissl";          rst_fields(31)%grid="grid_N_3D" 
     295        rst_fields(32)%vname="sbc_hc_b";       rst_fields(32)%grid="grid_N" 
     296        rst_fields(33)%vname="sbc_sc_b";       rst_fields(33)%grid="grid_N" 
     297        rst_fields(34)%vname="qsr_hc_b";       rst_fields(34)%grid="grid_N_3D" 
     298        rst_fields(35)%vname="gcx";            rst_fields(35)%grid="grid_N" 
     299        rst_fields(36)%vname="gcxb";           rst_fields(36)%grid="grid_N" 
     300        rst_fields(37)%vname="fraqsr_1lev";    rst_fields(37)%grid="grid_N" 
     301        rst_fields(38)%vname="greenland_icesheet_mass" 
     302                                               rst_fields(38)%grid="grid_scalar" 
     303        rst_fields(39)%vname="greenland_icesheet_timelapsed" 
     304                                               rst_fields(39)%grid="grid_scalar" 
     305        rst_fields(40)%vname="greenland_icesheet_mass_roc" 
     306                                               rst_fields(40)%grid="grid_scalar" 
     307        rst_fields(41)%vname="antarctica_icesheet_mass" 
     308                                               rst_fields(41)%grid="grid_scalar" 
     309        rst_fields(42)%vname="antarctica_icesheet_timelapsed" 
     310                                               rst_fields(42)%grid="grid_scalar" 
     311        rst_fields(43)%vname="antarctica_icesheet_mass_roc" 
     312                                               rst_fields(43)%grid="grid_scalar" 
     313        rst_fields(44)%vname="rhd";            rst_fields(44)%grid="grid_N_3D" 
     314        rst_fields(45)%vname="frc_v";          rst_fields(45)%grid="grid_scalar" 
     315        rst_fields(46)%vname="frc_t";          rst_fields(46)%grid="grid_scalar" 
     316        rst_fields(47)%vname="frc_s";          rst_fields(47)%grid="grid_scalar" 
     317        rst_fields(48)%vname="frc_wn_t";       rst_fields(48)%grid="grid_scalar" 
     318        rst_fields(49)%vname="frc_wn_s";       rst_fields(49)%grid="grid_scalar" 
     319        rst_fields(50)%vname="ssh_ini";        rst_fields(50)%grid="grid_N" 
     320        rst_fields(51)%vname="e3t_ini";        rst_fields(51)%grid="grid_N_3D" 
     321        rst_fields(52)%vname="hc_loc_ini";     rst_fields(52)%grid="grid_N_3D" 
     322        rst_fields(53)%vname="sc_loc_ini";     rst_fields(53)%grid="grid_N_3D" 
     323        rst_fields(54)%vname="ssh_hc_loc_ini"; rst_fields(54)%grid="grid_N" 
     324        rst_fields(55)%vname="ssh_sc_loc_ini"; rst_fields(55)%grid="grid_N" 
     325        rst_fields(56)%vname="fse3t_b";        rst_fields(56)%grid="grid_N_3D" 
     326        rst_fields(57)%vname="fse3t_n";        rst_fields(57)%grid="grid_N_3D" 
     327        rst_fields(58)%vname="tilde_e3t_b";    rst_fields(58)%grid="grid_N" 
     328        rst_fields(59)%vname="tilde_e3t_n";    rst_fields(59)%grid="grid_N" 
     329        rst_fields(60)%vname="hdiv_lf";        rst_fields(60)%grid="grid_N" 
     330        rst_fields(61)%vname="ub2_b";          rst_fields(61)%grid="grid_N" 
     331        rst_fields(62)%vname="vb2_b";          rst_fields(62)%grid="grid_N" 
     332        rst_fields(63)%vname="sshbb_e";        rst_fields(63)%grid="grid_N" 
     333        rst_fields(64)%vname="ubb_e";          rst_fields(64)%grid="grid_N" 
     334        rst_fields(65)%vname="vbb_e";          rst_fields(65)%grid="grid_N" 
     335        rst_fields(66)%vname="sshb_e";         rst_fields(66)%grid="grid_N" 
     336        rst_fields(67)%vname="ub_e";           rst_fields(67)%grid="grid_N" 
     337        rst_fields(68)%vname="vb_e";           rst_fields(68)%grid="grid_N" 
     338        rst_fields(69)%vname="fwf_isf_b";      rst_fields(69)%grid="grid_N" 
     339        rst_fields(70)%vname="isf_sc_b";       rst_fields(70)%grid="grid_N" 
     340        rst_fields(71)%vname="isf_hc_b";       rst_fields(71)%grid="grid_N" 
     341        rst_fields(72)%vname="ssh_ibb";        rst_fields(72)%grid="grid_N" 
     342        rst_fields(73)%vname="rnf_b";          rst_fields(73)%grid="grid_N" 
     343        rst_fields(74)%vname="rnf_hc_b";       rst_fields(74)%grid="grid_N" 
     344        rst_fields(75)%vname="rnf_sc_b";       rst_fields(75)%grid="grid_N" 
     345        rst_fields(76)%vname="nn_fsbc";        rst_fields(76)%grid="grid_scalar" 
     346        rst_fields(77)%vname="ssu_m";          rst_fields(77)%grid="grid_N" 
     347        rst_fields(78)%vname="ssv_m";          rst_fields(78)%grid="grid_N" 
     348        rst_fields(79)%vname="sst_m";          rst_fields(79)%grid="grid_N" 
     349        rst_fields(80)%vname="sss_m";          rst_fields(80)%grid="grid_N" 
     350        rst_fields(81)%vname="ssh_m";          rst_fields(81)%grid="grid_N" 
     351        rst_fields(82)%vname="e3t_m";          rst_fields(82)%grid="grid_N" 
     352        rst_fields(83)%vname="frq_m";          rst_fields(83)%grid="grid_N" 
     353        rst_fields(84)%vname="avmb";           rst_fields(84)%grid="Vgrid" 
     354        rst_fields(85)%vname="avtb";           rst_fields(85)%grid="Vgrid" 
     355 
     356   END SUBROUTINE set_rst_vars 
     357 
     358 
     359   SUBROUTINE set_rstr_active() 
     360!sets enabled = .TRUE. for each field in restart file 
     361#if defined key_xios2 
     362   CHARACTER(len=256) :: rst_file 
     363   TYPE(xios_field) :: field_hdl 
     364   TYPE(xios_file) :: file_hdl 
     365   TYPE(xios_filegroup) :: filegroup_hdl 
     366   INTEGER :: i 
     367   CHARACTER(lc)  ::   clpath 
     368 
     369        clpath = TRIM(cn_ocerst_indir) 
     370        IF( clpath(LEN_TRIM(clpath):) /= '/' ) clpath = TRIM(clpath) // '/' 
     371        IF( TRIM(Agrif_CFixed()) == '0' ) THEN 
     372           rst_file = TRIM(cn_ocerst_indir)//TRIM(cn_ocerst_in) 
     373        ELSE 
     374           rst_file = TRIM(cn_ocerst_indir)//'1_'//TRIM(cn_ocerst_in) 
     375        ENDIF 
     376!set name of the restart file and enable available fields 
     377        if(lwp) WRITE(numout,*) 'Setting restart filename (for XIOS) to: ',rst_file 
     378        CALL xios_get_handle("file_definition", filegroup_hdl ) 
     379        CALL xios_add_child(filegroup_hdl, file_hdl, 'rrestart') 
     380        CALL xios_set_file_attr( "rrestart", name=trim(rst_file), type="one_file", & 
     381             par_access="collective", enabled=.TRUE., mode="read",                 & 
     382             output_freq=xios_timestep) 
     383!defin files for restart context 
     384        DO i = 1, max_rst_fields 
     385         IF( TRIM(rst_fields(i)%vname) /= "NO_NAME") THEN 
     386           IF( iom_varid( numror, TRIM(rst_fields(i)%vname), ldstop = .FALSE. ) > 0 ) THEN 
     387                CALL xios_add_child(file_hdl, field_hdl, TRIM(rst_fields(i)%vname)) 
     388                CALL xios_set_attr (field_hdl, enabled = .TRUE., name = TRIM(rst_fields(i)%vname), & 
     389                     grid_ref = TRIM(rst_fields(i)%grid ), operation = "instant") 
     390                if(lwp) WRITE(numout,*) TRIM(rst_fields(i)%vname), ' enabled' 
     391           ENDIF 
     392         ENDIF 
     393        END DO 
     394#endif 
     395   END SUBROUTINE set_rstr_active 
    246396 
    247397   SUBROUTINE iom_swap( cdname ) 
     
    378528            icnt = icnt + 1 
    379529         END DO 
     530      ELSE 
     531         lxios_sini = .TRUE. 
    380532      ENDIF 
    381533      IF( llwrt ) THEN 
     
    567719   !!                   INTERFACE iom_get 
    568720   !!---------------------------------------------------------------------- 
    569    SUBROUTINE iom_g0d( kiomid, cdvar, pvar, ktime ) 
     721   SUBROUTINE iom_g0d( kiomid, cdvar, pvar, ktime, lrxios ) 
    570722      INTEGER         , INTENT(in   )                 ::   kiomid    ! Identifier of the file 
    571723      CHARACTER(len=*), INTENT(in   )                 ::   cdvar     ! Name of the variable 
    572724      REAL(wp)        , INTENT(  out)                 ::   pvar      ! read field 
    573725      INTEGER         , INTENT(in   ),     OPTIONAL   ::   ktime     ! record number 
     726      LOGICAL         , INTENT(in   ),     OPTIONAL   ::   lrxios    ! use xios to read restart 
    574727      ! 
    575728      INTEGER                                         ::   idvar     ! variable id 
     
    579732      CHARACTER(LEN=100)                              ::   clname    ! file name 
    580733      CHARACTER(LEN=1)                                ::   cldmspc   ! 
    581       ! 
    582       itime = 1 
    583       IF( PRESENT(ktime) ) itime = ktime 
    584       ! 
    585       clname = iom_file(kiomid)%name 
    586       clinfo = '          iom_g0d, file: '//trim(clname)//', var: '//trim(cdvar) 
    587       ! 
    588       IF( kiomid > 0 ) THEN 
    589          idvar = iom_varid( kiomid, cdvar ) 
    590          IF( iom_file(kiomid)%nfid > 0 .AND. idvar > 0 ) THEN 
    591             idmspc = iom_file ( kiomid )%ndims( idvar ) 
    592             IF( iom_file(kiomid)%luld(idvar) )  idmspc = idmspc - 1 
    593             WRITE(cldmspc , fmt='(i1)') idmspc 
    594             IF( idmspc > 0 )  CALL ctl_stop( TRIM(clinfo), 'When reading to a 0D array, we do not accept data', & 
    595                                  &                         'with 1 or more spatial dimensions: '//cldmspc//' were found.' , & 
    596                                  &                         'Use ncwa -a to suppress the unnecessary dimensions' ) 
    597             SELECT CASE (iom_file(kiomid)%iolib) 
    598             CASE (jpioipsl )   ;   CALL iom_ioipsl_get(  kiomid, idvar, pvar, itime ) 
    599             CASE (jpnf90   )   ;   CALL iom_nf90_get(    kiomid, idvar, pvar, itime ) 
    600             CASE (jprstdimg)   ;   CALL iom_rstdimg_get( kiomid, idvar, pvar ) 
    601             CASE DEFAULT     
    602                CALL ctl_stop( 'iom_g0d: accepted IO library are only jpioipsl, jpnf90 and jprstdimg' ) 
    603             END SELECT 
    604          ENDIF 
    605       ENDIF 
     734      LOGICAL                                         ::   lxios 
     735      ! 
     736      lxios = .FALSE. 
     737      IF( PRESENT(lrxios) ) lxios = lrxios 
     738 
     739      IF(.NOT.lxios) THEN  ! read data using default library 
     740          itime = 1 
     741          IF( PRESENT(ktime) ) itime = ktime 
     742          ! 
     743          clname = iom_file(kiomid)%name 
     744          clinfo = '          iom_g0d, file: '//trim(clname)//', var: '//trim(cdvar) 
     745          ! 
     746          IF( kiomid > 0 ) THEN 
     747             idvar = iom_varid( kiomid, cdvar ) 
     748             IF( iom_file(kiomid)%nfid > 0 .AND. idvar > 0 ) THEN 
     749                idmspc = iom_file ( kiomid )%ndims( idvar ) 
     750                IF( iom_file(kiomid)%luld(idvar) )  idmspc = idmspc - 1 
     751                WRITE(cldmspc , fmt='(i1)') idmspc 
     752                IF( idmspc > 0 )  CALL ctl_stop( TRIM(clinfo), 'When reading to a 0D array, we do not accept data', & 
     753                                     &                         'with 1 or more spatial dimensions: '//cldmspc//' were found.' , & 
     754                                     &                         'Use ncwa -a to suppress the unnecessary dimensions' ) 
     755                SELECT CASE (iom_file(kiomid)%iolib) 
     756                CASE (jpioipsl )   ;   CALL iom_ioipsl_get(  kiomid, idvar, pvar, itime ) 
     757                CASE (jpnf90   )   ;   CALL iom_nf90_get(    kiomid, idvar, pvar, itime ) 
     758                CASE (jprstdimg)   ;   CALL iom_rstdimg_get( kiomid, idvar, pvar ) 
     759                CASE DEFAULT     
     760                   CALL ctl_stop( 'iom_g0d: accepted IO library are only jpioipsl, jpnf90 and jprstdimg' ) 
     761                END SELECT 
     762             ENDIF 
     763          ENDIF 
     764      ELSE 
     765#if defined key_iomput 
     766       IF(lwp) WRITE(numout,*) 'XIOS RST READ (0D): ', trim(cdvar) 
     767       CALL iom_swap( TRIM(rxios_context) ) 
     768       CALL xios_recv_field( trim(cdvar), pvar) 
     769       CALL iom_swap( TRIM(cxios_context) ) 
     770#endif 
     771      ENDIF    
    606772   END SUBROUTINE iom_g0d 
    607773 
    608    SUBROUTINE iom_g1d( kiomid, kdom, cdvar, pvar, ktime, kstart, kcount ) 
     774   SUBROUTINE iom_g1d( kiomid, kdom, cdvar, pvar, ktime, kstart, kcount, lrxios ) 
    609775      INTEGER         , INTENT(in   )                         ::   kiomid    ! Identifier of the file 
    610776      INTEGER         , INTENT(in   )                         ::   kdom      ! Type of domain to be read 
     
    614780      INTEGER         , INTENT(in   ), DIMENSION(1), OPTIONAL ::   kstart    ! start axis position of the reading  
    615781      INTEGER         , INTENT(in   ), DIMENSION(1), OPTIONAL ::   kcount    ! number of points in each axis 
     782      LOGICAL         , INTENT(in   ),               OPTIONAL ::   lrxios    ! read data using XIOS 
    616783      ! 
    617784      IF( kiomid > 0 ) THEN 
    618785         IF( iom_file(kiomid)%nfid > 0 ) CALL iom_get_123d( kiomid, kdom       , cdvar        , pv_r1d=pvar,   & 
    619               &                                                     ktime=ktime, kstart=kstart, kcount=kcount ) 
     786              &                                                     ktime=ktime, kstart=kstart, kcount=kcount, & 
     787              &                                                     lrxios=lrxios ) 
    620788      ENDIF 
    621789   END SUBROUTINE iom_g1d 
    622790 
    623    SUBROUTINE iom_g2d( kiomid, kdom, cdvar, pvar, ktime, kstart, kcount, lrowattr ) 
     791   SUBROUTINE iom_g2d( kiomid, kdom, cdvar, pvar, ktime, kstart, kcount, lrowattr, lrxios) 
    624792      INTEGER         , INTENT(in   )                           ::   kiomid    ! Identifier of the file 
    625793      INTEGER         , INTENT(in   )                           ::   kdom      ! Type of domain to be read 
     
    633801                                                                               ! called open_ocean_jstart to set the start 
    634802                                                                               ! value for the 2nd dimension (netcdf only) 
     803      LOGICAL         , INTENT(in   ),                 OPTIONAL ::   lrxios    ! read data using XIOS 
    635804      ! 
    636805      IF( kiomid > 0 ) THEN 
    637806         IF( iom_file(kiomid)%nfid > 0 ) CALL iom_get_123d( kiomid, kdom       , cdvar        , pv_r2d=pvar,   & 
    638807              &                                                     ktime=ktime, kstart=kstart, kcount=kcount, & 
    639               &                                                     lrowattr=lrowattr ) 
     808              &                                                     lrowattr=lrowattr,  lrxios=lrxios) 
    640809      ENDIF 
    641810   END SUBROUTINE iom_g2d 
    642811 
    643    SUBROUTINE iom_g3d( kiomid, kdom, cdvar, pvar, ktime, kstart, kcount, lrowattr ) 
     812   SUBROUTINE iom_g3d( kiomid, kdom, cdvar, pvar, ktime, kstart, kcount, lrowattr, lrxios ) 
    644813      INTEGER         , INTENT(in   )                             ::   kiomid    ! Identifier of the file 
    645814      INTEGER         , INTENT(in   )                             ::   kdom      ! Type of domain to be read 
     
    653822                                                                                 ! called open_ocean_jstart to set the start 
    654823                                                                                 ! value for the 2nd dimension (netcdf only) 
     824      LOGICAL         , INTENT(in   ),                   OPTIONAL ::   lrxios    ! read data using XIOS 
    655825      ! 
    656826      IF( kiomid > 0 ) THEN 
    657827         IF( iom_file(kiomid)%nfid > 0 ) CALL iom_get_123d( kiomid, kdom       , cdvar        , pv_r3d=pvar,   & 
    658828              &                                                     ktime=ktime, kstart=kstart, kcount=kcount, & 
    659               &                                                     lrowattr=lrowattr ) 
     829              &                                                     lrowattr=lrowattr, lrxios=lrxios ) 
    660830      ENDIF 
    661831   END SUBROUTINE iom_g3d 
     
    665835         &                  pv_r1d, pv_r2d, pv_r3d,   & 
    666836         &                  ktime , kstart, kcount,   & 
    667          &                  lrowattr                ) 
     837         &                  lrowattr, lrxios        ) 
    668838      !!----------------------------------------------------------------------- 
    669839      !!                  ***  ROUTINE  iom_get_123d  *** 
     
    686856                                                                           ! called open_ocean_jstart to set the start 
    687857                                                                           ! value for the 2nd dimension (netcdf only) 
    688       ! 
     858      LOGICAL                    , INTENT(in   ), OPTIONAL ::   lrxios     ! use XIOS to read restart 
     859      ! 
     860      LOGICAL                        ::   lxios       ! local definition for XIOS read 
    689861      LOGICAL                        ::   llnoov      ! local definition to read overlap 
    690862      LOGICAL                        ::   luse_jattr  ! local definition to read open_ocean_jstart file attribute 
     
    713885      !--------------------------------------------------------------------- 
    714886      ! 
    715       clname = iom_file(kiomid)%name   !   esier to read 
    716       clinfo = '          iom_get_123d, file: '//trim(clname)//', var: '//trim(cdvar) 
    717       ! local definition of the domain ? 
     887      REAL(wp)                       :: gma, gmi 
     888      lxios = .FALSE. 
     889      if(PRESENT(lrxios)) lxios = lrxios 
     890      idvar = iom_varid( kiomid, cdvar )  
    718891      idom = kdom 
    719       ! do we read the overlap  
    720       ! ugly patch SM+JMM+RB to overwrite global definition in some cases 
    721       llnoov = (jpni * jpnj ) == jpnij .AND. .NOT. lk_agrif  
    722       ! check kcount and kstart optionals parameters... 
    723       IF( PRESENT(kcount) .AND. (.NOT. PRESENT(kstart)) ) CALL ctl_stop(trim(clinfo), 'kcount present needs kstart present') 
    724       IF( PRESENT(kstart) .AND. (.NOT. PRESENT(kcount)) ) CALL ctl_stop(trim(clinfo), 'kstart present needs kcount present') 
    725       IF( PRESENT(kstart) .AND. idom /= jpdom_unknown .AND.  idom /= jpdom_autoglo_xy  ) & 
     892 
     893      IF(.NOT.lxios) THEN 
     894          clname = iom_file(kiomid)%name   !   esier to read 
     895          clinfo = '          iom_get_123d, file: '//trim(clname)//', var: '//trim(cdvar) 
     896          ! local definition of the domain ? 
     897          ! do we read the overlap  
     898          ! ugly patch SM+JMM+RB to overwrite global definition in some cases 
     899          llnoov = (jpni * jpnj ) == jpnij .AND. .NOT. lk_agrif  
     900          ! check kcount and kstart optionals parameters... 
     901          IF( PRESENT(kcount) .AND. (.NOT. PRESENT(kstart)) ) CALL ctl_stop(trim(clinfo), 'kcount present needs kstart present') 
     902          IF( PRESENT(kstart) .AND. (.NOT. PRESENT(kcount)) ) CALL ctl_stop(trim(clinfo), 'kstart present needs kcount present') 
     903          IF( PRESENT(kstart) .AND. idom /= jpdom_unknown .AND.  idom /= jpdom_autoglo_xy  ) & 
    726904     &           CALL ctl_stop(trim(clinfo), 'kstart present needs kdom = jpdom_unknown or kdom = jpdom_autoglo_xy') 
    727905 
    728       luse_jattr = .false. 
    729       IF( PRESENT(lrowattr) ) THEN 
    730          IF( lrowattr .AND. idom /= jpdom_data   ) CALL ctl_stop(trim(clinfo), 'lrowattr present and true needs kdom = jpdom_data') 
    731          IF( lrowattr .AND. idom == jpdom_data   ) luse_jattr = .true. 
    732       ENDIF 
    733       IF( luse_jattr ) THEN 
    734          SELECT CASE (iom_file(kiomid)%iolib) 
    735          CASE (jpioipsl, jprstdimg ) 
    736              CALL ctl_warn(trim(clinfo), 'lrowattr present and true but this only works with netcdf (jpnf90)') 
    737              luse_jattr = .false. 
    738          CASE (jpnf90   )    
    739              ! Ok 
    740          CASE DEFAULT     
    741             CALL ctl_stop( TRIM(clinfo)//' accepted IO library are only jpioipsl, jpnf90 and jprstdimg' ) 
    742          END SELECT 
    743       ENDIF 
    744  
    745       ! Search for the variable in the data base (eventually actualize data) 
    746       istop = nstop 
    747       idvar = iom_varid( kiomid, cdvar ) 
    748       ! 
    749       IF( idvar > 0 ) THEN 
    750          ! to write iom_file(kiomid)%dimsz in a shorter way ! 
    751          idimsz(:) = iom_file(kiomid)%dimsz(:, idvar)  
    752          inbdim = iom_file(kiomid)%ndims(idvar)            ! number of dimensions in the file 
    753          idmspc = inbdim                                   ! number of spatial dimensions in the file 
    754          IF( iom_file(kiomid)%luld(idvar) )   idmspc = inbdim - 1 
    755          IF( idmspc > 3 )   CALL ctl_stop(trim(clinfo), 'the file has more than 3 spatial dimensions this case is not coded...')  
    756          ! 
    757          ! update idom definition... 
    758          ! Identify the domain in case of jpdom_auto(glo/dta) definition 
    759          IF( idom == jpdom_autoglo_xy ) THEN 
    760             ll_depth_spec = .TRUE. 
    761             idom = jpdom_autoglo 
    762          ELSE 
    763             ll_depth_spec = .FALSE. 
    764          ENDIF 
    765          IF( idom == jpdom_autoglo .OR. idom == jpdom_autodta ) THEN             
    766             IF( idom == jpdom_autoglo ) THEN   ;   idom = jpdom_global  
    767             ELSE                               ;   idom = jpdom_data 
    768             ENDIF 
    769             ind1 = INDEX( clname, '_', back = .TRUE. ) + 1 
    770             ind2 = INDEX( clname, '.', back = .TRUE. ) - 1 
    771             IF( ind2 > ind1 ) THEN   ;   IF( VERIFY( clname(ind1:ind2), '0123456789' ) == 0 )   idom = jpdom_local   ;   ENDIF 
    772          ENDIF 
    773          ! Identify the domain in case of jpdom_local definition 
    774          IF( idom == jpdom_local ) THEN 
    775             IF(     idimsz(1) == jpi               .AND. idimsz(2) == jpj               ) THEN   ;   idom = jpdom_local_full 
    776             ELSEIF( idimsz(1) == nlci              .AND. idimsz(2) == nlcj              ) THEN   ;   idom = jpdom_local_noextra 
    777             ELSEIF( idimsz(1) == (nlei - nldi + 1) .AND. idimsz(2) == (nlej - nldj + 1) ) THEN   ;   idom = jpdom_local_noovlap 
    778             ELSE   ;   CALL ctl_stop( trim(clinfo), 'impossible to identify the local domain' ) 
    779             ENDIF 
    780          ENDIF 
    781          ! 
    782          ! check the consistency between input array and data rank in the file 
    783          ! 
    784          ! initializations 
    785          itime = 1 
    786          IF( PRESENT(ktime) ) itime = ktime 
    787  
    788          irankpv = 1 * COUNT( (/PRESENT(pv_r1d)/) ) + 2 * COUNT( (/PRESENT(pv_r2d)/) ) + 3 * COUNT( (/PRESENT(pv_r3d)/) ) 
    789          WRITE(clrankpv, fmt='(i1)') irankpv 
    790          WRITE(cldmspc , fmt='(i1)') idmspc 
    791          ! 
    792          IF(     idmspc <  irankpv ) THEN  
    793             CALL ctl_stop( TRIM(clinfo), 'The file has only '//cldmspc//' spatial dimension',   & 
     906          luse_jattr = .false. 
     907          IF( PRESENT(lrowattr) ) THEN 
     908             IF( lrowattr .AND. idom /= jpdom_data   ) CALL ctl_stop(trim(clinfo), 'lrowattr present and true needs kdom = jpdom_data') 
     909             IF( lrowattr .AND. idom == jpdom_data   ) luse_jattr = .true. 
     910          ENDIF 
     911          IF( luse_jattr ) THEN 
     912             SELECT CASE (iom_file(kiomid)%iolib) 
     913             CASE (jpioipsl, jprstdimg ) 
     914                 CALL ctl_warn(trim(clinfo), 'lrowattr present and true but this only works with netcdf (jpnf90)') 
     915                 luse_jattr = .false. 
     916             CASE (jpnf90   )    
     917                 ! Ok 
     918             CASE DEFAULT     
     919                CALL ctl_stop( TRIM(clinfo)//' accepted IO library are only jpioipsl, jpnf90 and jprstdimg' ) 
     920             END SELECT 
     921          ENDIF 
     922 
     923          ! Search for the variable in the data base (eventually actualize data) 
     924          istop = nstop 
     925          ! 
     926          IF( idvar > 0 ) THEN 
     927             ! to write iom_file(kiomid)%dimsz in a shorter way ! 
     928             idimsz(:) = iom_file(kiomid)%dimsz(:, idvar)  
     929             inbdim = iom_file(kiomid)%ndims(idvar)            ! number of dimensions in the file 
     930             idmspc = inbdim                                   ! number of spatial dimensions in the file 
     931             IF( iom_file(kiomid)%luld(idvar) )   idmspc = inbdim - 1 
     932             IF( idmspc > 3 )   CALL ctl_stop(trim(clinfo), 'the file has more than 3 spatial dimensions this case is not coded...')  
     933             ! 
     934             ! update idom definition... 
     935             ! Identify the domain in case of jpdom_auto(glo/dta) definition 
     936             IF( idom == jpdom_autoglo_xy ) THEN 
     937                ll_depth_spec = .TRUE. 
     938                idom = jpdom_autoglo 
     939             ELSE 
     940                ll_depth_spec = .FALSE. 
     941             ENDIF 
     942             IF( idom == jpdom_autoglo .OR. idom == jpdom_autodta ) THEN             
     943                IF( idom == jpdom_autoglo ) THEN   ;   idom = jpdom_global  
     944                ELSE                               ;   idom = jpdom_data 
     945                ENDIF 
     946                ind1 = INDEX( clname, '_', back = .TRUE. ) + 1 
     947                ind2 = INDEX( clname, '.', back = .TRUE. ) - 1 
     948                IF( ind2 > ind1 ) THEN   ;   IF( VERIFY( clname(ind1:ind2), '0123456789' ) == 0 )   idom = jpdom_local   ;   ENDIF 
     949             ENDIF 
     950             ! Identify the domain in case of jpdom_local definition 
     951             IF( idom == jpdom_local ) THEN 
     952                IF(     idimsz(1) == jpi               .AND. idimsz(2) == jpj               ) THEN   ;   idom = jpdom_local_full 
     953                ELSEIF( idimsz(1) == nlci              .AND. idimsz(2) == nlcj              ) THEN   ;   idom = jpdom_local_noextra 
     954                ELSEIF( idimsz(1) == (nlei - nldi + 1) .AND. idimsz(2) == (nlej - nldj + 1) ) THEN   ;   idom = jpdom_local_noovlap 
     955                ELSE   ;   CALL ctl_stop( trim(clinfo), 'impossible to identify the local domain' ) 
     956                ENDIF 
     957             ENDIF 
     958             ! 
     959             ! check the consistency between input array and data rank in the file 
     960             ! 
     961             ! initializations 
     962             itime = 1 
     963             IF( PRESENT(ktime) ) itime = ktime 
     964 
     965             irankpv = 1 * COUNT( (/PRESENT(pv_r1d)/) ) + 2 * COUNT( (/PRESENT(pv_r2d)/) ) + 3 * COUNT( (/PRESENT(pv_r3d)/) ) 
     966             WRITE(clrankpv, fmt='(i1)') irankpv 
     967             WRITE(cldmspc , fmt='(i1)') idmspc 
     968             ! 
     969             IF(     idmspc <  irankpv ) THEN  
     970                CALL ctl_stop( TRIM(clinfo), 'The file has only '//cldmspc//' spatial dimension',   & 
    794971               &                         'it is impossible to read a '//clrankpv//'D array from this file...' ) 
    795          ELSEIF( idmspc == irankpv ) THEN 
    796             IF( PRESENT(pv_r1d) .AND. idom /= jpdom_unknown )   & 
     972             ELSEIF( idmspc == irankpv ) THEN 
     973                IF( PRESENT(pv_r1d) .AND. idom /= jpdom_unknown )   & 
    797974               &   CALL ctl_stop( TRIM(clinfo), 'case not coded...You must use jpdom_unknown' ) 
    798          ELSEIF( idmspc >  irankpv ) THEN 
    799                IF( PRESENT(pv_r2d) .AND. itime == 1 .AND. idimsz(3) == 1 .AND. idmspc == 3 ) THEN 
    800                   CALL ctl_warn( trim(clinfo), '2D array but 3 spatial dimensions for the data...'              ,   & 
     975             ELSEIF( idmspc >  irankpv ) THEN 
     976                   IF( PRESENT(pv_r2d) .AND. itime == 1 .AND. idimsz(3) == 1 .AND. idmspc == 3 ) THEN 
     977                      CALL ctl_warn( trim(clinfo), '2D array but 3 spatial dimensions for the data...'              ,   & 
    801978                        &         'As the size of the z dimension is 1 and as we try to read the first record, ',   & 
    802979                        &         'we accept this case, even if there is a possible mix-up between z and time dimension' )    
    803                   idmspc = idmspc - 1 
    804                ELSE 
    805                   CALL ctl_stop( TRIM(clinfo), 'To keep iom lisibility, when reading a '//clrankpv//'D array,'         ,   & 
     980                      idmspc = idmspc - 1 
     981                   ELSE 
     982                      CALL ctl_stop( TRIM(clinfo), 'To keep iom lisibility, when reading a '//clrankpv//'D array,'         ,   & 
    806983                     &                         'we do not accept data with '//cldmspc//' spatial dimensions',   & 
    807984                     &                         'Use ncwa -a to suppress the unnecessary dimensions' ) 
    808                ENDIF 
    809          ENDIF 
    810  
    811          ! 
    812          ! definition of istart and icnt 
    813          ! 
    814          icnt  (:) = 1 
    815          istart(:) = 1 
    816          istart(idmspc+1) = itime 
    817  
    818          IF( PRESENT(kstart) .AND. .NOT. ll_depth_spec ) THEN ; istart(1:idmspc) = kstart(1:idmspc) ; icnt(1:idmspc) = kcount(1:idmspc) 
    819          ELSE 
    820             IF(           idom == jpdom_unknown ) THEN                                                ; icnt(1:idmspc) = idimsz(1:idmspc) 
    821             ELSE  
    822                IF( .NOT. PRESENT(pv_r1d) ) THEN   !   not a 1D array 
    823                   IF(     idom == jpdom_data    ) THEN 
    824                      jstartrow = 1 
    825                      IF( luse_jattr ) THEN 
    826                         CALL iom_getatt(kiomid, 'open_ocean_jstart', jstartrow ) ! -999 is returned if the attribute is not found 
    827                         jstartrow = MAX(1,jstartrow) 
    828                      ENDIF 
    829                      istart(1:2) = (/ mig(1), mjg(1) + jstartrow - 1 /)  ! icnt(1:2) done below 
    830                   ELSEIF( idom == jpdom_global  ) THEN ; istart(1:2) = (/ nimpp , njmpp  /)  ! icnt(1:2) done below 
    831                   ENDIF 
    832                   ! we do not read the overlap                     -> we start to read at nldi, nldj 
     985                   ENDIF 
     986             ENDIF 
     987 
     988             ! 
     989             ! definition of istart and icnt 
     990             ! 
     991             icnt  (:) = 1 
     992             istart(:) = 1 
     993             istart(idmspc+1) = itime 
     994 
     995             IF( PRESENT(kstart) .AND. .NOT. ll_depth_spec ) THEN ; istart(1:idmspc) = kstart(1:idmspc) ; icnt(1:idmspc) = kcount(1:idmspc) 
     996             ELSE 
     997                IF(           idom == jpdom_unknown ) THEN                                                ; icnt(1:idmspc) = idimsz(1:idmspc) 
     998                ELSE  
     999                   IF( .NOT. PRESENT(pv_r1d) ) THEN   !   not a 1D array 
     1000                      IF(     idom == jpdom_data    ) THEN 
     1001                         jstartrow = 1 
     1002                         IF( luse_jattr ) THEN 
     1003                            CALL iom_getatt(kiomid, 'open_ocean_jstart', jstartrow ) ! -999 is returned if the attribute is not found 
     1004                            jstartrow = MAX(1,jstartrow) 
     1005                         ENDIF 
     1006                         istart(1:2) = (/ mig(1), mjg(1) + jstartrow - 1 /)  ! icnt(1:2) done below 
     1007                      ELSEIF( idom == jpdom_global  ) THEN ; istart(1:2) = (/ nimpp , njmpp  /)  ! icnt(1:2) done below 
     1008                      ENDIF 
     1009                      ! we do not read the overlap                     -> we start to read at nldi, nldj 
    8331010! JMM + SM: ugly patch before getting the new version of lib_mpp) 
    8341011!                  IF( idom /= jpdom_local_noovlap )   istart(1:2) = istart(1:2) + (/ nldi - 1, nldj - 1 /) 
    835                   IF( llnoov .AND. idom /= jpdom_local_noovlap ) istart(1:2) = istart(1:2) + (/ nldi - 1, nldj - 1 /) 
     1012                      IF( llnoov .AND. idom /= jpdom_local_noovlap ) istart(1:2) = istart(1:2) + (/ nldi - 1, nldj - 1 /) 
    8361013                  ! we do not read the overlap and the extra-halos -> from nldi to nlei and from nldj to nlej  
    8371014! JMM + SM: ugly patch before getting the new version of lib_mpp) 
    8381015!                  icnt(1:2) = (/ nlei - nldi + 1, nlej - nldj + 1 /) 
    839                   IF( llnoov ) THEN   ;   icnt(1:2) = (/ nlei - nldi + 1, nlej - nldj + 1 /) 
    840                   ELSE                ;   icnt(1:2) = (/ nlci           , nlcj            /) 
    841                   ENDIF 
    842                   IF( PRESENT(pv_r3d) ) THEN 
    843                      IF( idom == jpdom_data ) THEN                                  ; icnt(3) = jpkdta 
    844                      ELSE IF( ll_depth_spec .AND. PRESENT(kstart) ) THEN            ; istart(3) = kstart(3); icnt(3) = kcount(3) 
    845                      ELSE                                                           ; icnt(3) = jpk 
    846                      ENDIF 
    847                   ENDIF 
    848                ENDIF 
    849             ENDIF 
    850          ENDIF 
    851  
    852          ! check that istart and icnt can be used with this file 
    853          !- 
    854          DO jl = 1, jpmax_dims 
    855             itmp = istart(jl)+icnt(jl)-1 
    856             IF( itmp > idimsz(jl) .AND. idimsz(jl) /= 0 ) THEN 
    857                WRITE( ctmp1, FMT="('(istart(', i1, ') + icnt(', i1, ') - 1) = ', i5)" ) jl, jl, itmp 
    858                WRITE( ctmp2, FMT="(' is larger than idimsz(', i1,') = ', i5)"         ) jl, idimsz(jl) 
    859                CALL ctl_stop( trim(clinfo), 'start and count too big regarding to the size of the data, ', ctmp1, ctmp2 )      
    860             ENDIF 
    861          END DO 
    862  
    863          ! check that icnt matches the input array 
    864          !-      
    865          IF( idom == jpdom_unknown ) THEN 
    866             IF( irankpv == 1 )        ishape(1:1) = SHAPE(pv_r1d) 
    867             IF( irankpv == 2 )        ishape(1:2) = SHAPE(pv_r2d) 
    868             IF( irankpv == 3 )        ishape(1:3) = SHAPE(pv_r3d) 
    869             ctmp1 = 'd' 
    870          ELSE 
    871             IF( irankpv == 2 ) THEN 
     1016                      IF( llnoov ) THEN   ;   icnt(1:2) = (/ nlei - nldi + 1, nlej - nldj + 1 /) 
     1017                      ELSE                ;   icnt(1:2) = (/ nlci           , nlcj            /) 
     1018                      ENDIF 
     1019                      IF( PRESENT(pv_r3d) ) THEN 
     1020                         IF( idom == jpdom_data ) THEN                                  ; icnt(3) = jpkdta 
     1021                         ELSE IF( ll_depth_spec .AND. PRESENT(kstart) ) THEN            ; istart(3) = kstart(3); icnt(3) = kcount(3) 
     1022                         ELSE                                                           ; icnt(3) = jpk 
     1023                         ENDIF 
     1024                      ENDIF 
     1025                   ENDIF 
     1026                ENDIF 
     1027             ENDIF 
     1028 
     1029             ! check that istart and icnt can be used with this file 
     1030             !- 
     1031             DO jl = 1, jpmax_dims 
     1032                itmp = istart(jl)+icnt(jl)-1 
     1033                IF( itmp > idimsz(jl) .AND. idimsz(jl) /= 0 ) THEN 
     1034                   WRITE( ctmp1, FMT="('(istart(', i1, ') + icnt(', i1, ') - 1) = ', i5)" ) jl, jl, itmp 
     1035                   WRITE( ctmp2, FMT="(' is larger than idimsz(', i1,') = ', i5)"         ) jl, idimsz(jl) 
     1036                   CALL ctl_stop( trim(clinfo), 'start and count too big regarding to the size of the data, ', ctmp1, ctmp2 )      
     1037                ENDIF 
     1038             END DO 
     1039 
     1040             ! check that icnt matches the input array 
     1041             !-      
     1042             IF( idom == jpdom_unknown ) THEN 
     1043                IF( irankpv == 1 )        ishape(1:1) = SHAPE(pv_r1d) 
     1044                IF( irankpv == 2 )        ishape(1:2) = SHAPE(pv_r2d) 
     1045                IF( irankpv == 3 )        ishape(1:3) = SHAPE(pv_r3d) 
     1046                ctmp1 = 'd' 
     1047             ELSE 
     1048                IF( irankpv == 2 ) THEN 
    8721049! JMM + SM: ugly patch before getting the new version of lib_mpp) 
    8731050!               ishape(1:2) = SHAPE(pv_r2d(nldi:nlei,nldj:nlej  ))   ;   ctmp1 = 'd(nldi:nlei,nldj:nlej)' 
    874                IF( llnoov ) THEN ; ishape(1:2)=SHAPE(pv_r2d(nldi:nlei,nldj:nlej  )) ; ctmp1='d(nldi:nlei,nldj:nlej)' 
    875                ELSE              ; ishape(1:2)=SHAPE(pv_r2d(1   :nlci,1   :nlcj  )) ; ctmp1='d(1:nlci,1:nlcj)' 
    876                ENDIF 
    877             ENDIF 
    878             IF( irankpv == 3 ) THEN  
     1051                   IF( llnoov ) THEN ; ishape(1:2)=SHAPE(pv_r2d(nldi:nlei,nldj:nlej  )) ; ctmp1='d(nldi:nlei,nldj:nlej)' 
     1052                   ELSE              ; ishape(1:2)=SHAPE(pv_r2d(1   :nlci,1   :nlcj  )) ; ctmp1='d(1:nlci,1:nlcj)' 
     1053                   ENDIF 
     1054                ENDIF 
     1055                IF( irankpv == 3 ) THEN  
    8791056! JMM + SM: ugly patch before getting the new version of lib_mpp) 
    8801057!               ishape(1:3) = SHAPE(pv_r3d(nldi:nlei,nldj:nlej,:))   ;   ctmp1 = 'd(nldi:nlei,nldj:nlej,:)' 
    881                IF( llnoov ) THEN ; ishape(1:3)=SHAPE(pv_r3d(nldi:nlei,nldj:nlej,:)) ; ctmp1='d(nldi:nlei,nldj:nlej,:)' 
    882                ELSE              ; ishape(1:3)=SHAPE(pv_r3d(1   :nlci,1   :nlcj,:)) ; ctmp1='d(1:nlci,1:nlcj,:)' 
    883                ENDIF 
    884             ENDIF 
    885          ENDIF 
     1058                   IF( llnoov ) THEN ; ishape(1:3)=SHAPE(pv_r3d(nldi:nlei,nldj:nlej,:)) ; ctmp1='d(nldi:nlei,nldj:nlej,:)' 
     1059                   ELSE              ; ishape(1:3)=SHAPE(pv_r3d(1   :nlci,1   :nlcj,:)) ; ctmp1='d(1:nlci,1:nlcj,:)' 
     1060                   ENDIF 
     1061                ENDIF 
     1062             ENDIF 
    8861063          
    887          DO jl = 1, irankpv 
    888             WRITE( ctmp2, FMT="(', ', i1,'): ', i5,' /= icnt(', i1,'):', i5)" ) jl, ishape(jl), jl, icnt(jl) 
    889             IF( ishape(jl) /= icnt(jl) )   CALL ctl_stop( TRIM(clinfo), 'size(pv_r'//clrankpv//TRIM(ctmp1)//TRIM(ctmp2) ) 
    890          END DO 
    891  
    892       ENDIF 
    893  
    894       ! read the data 
    895       !-      
    896       IF( idvar > 0 .AND. istop == nstop ) THEN   ! no additional errors until this point... 
    897          ! 
    898          ! find the right index of the array to be read 
     1064             DO jl = 1, irankpv 
     1065                WRITE( ctmp2, FMT="(', ', i1,'): ', i5,' /= icnt(', i1,'):', i5)" ) jl, ishape(jl), jl, icnt(jl) 
     1066                IF( ishape(jl) /= icnt(jl) )   CALL ctl_stop( TRIM(clinfo), 'size(pv_r'//clrankpv//TRIM(ctmp1)//TRIM(ctmp2) ) 
     1067             END DO 
     1068 
     1069          ENDIF 
     1070 
     1071          ! read the data 
     1072          !-      
     1073          IF( idvar > 0 .AND. istop == nstop ) THEN   ! no additional errors until this point... 
     1074             ! 
     1075             ! find the right index of the array to be read 
    8991076! JMM + SM: ugly patch before getting the new version of lib_mpp) 
    9001077!         IF( idom /= jpdom_unknown ) THEN   ;   ix1 = nldi   ;   ix2 = nlei      ;   iy1 = nldj   ;   iy2 = nlej 
    9011078!         ELSE                               ;   ix1 = 1      ;   ix2 = icnt(1)   ;   iy1 = 1      ;   iy2 = icnt(2) 
    9021079!         ENDIF 
    903          IF( llnoov ) THEN 
    904             IF( idom /= jpdom_unknown ) THEN   ;   ix1 = nldi   ;   ix2 = nlei      ;   iy1 = nldj   ;   iy2 = nlej 
    905             ELSE                               ;   ix1 = 1      ;   ix2 = icnt(1)   ;   iy1 = 1      ;   iy2 = icnt(2) 
    906             ENDIF 
    907          ELSE 
    908             IF( idom /= jpdom_unknown ) THEN   ;   ix1 = 1      ;   ix2 = nlci      ;   iy1 = 1      ;   iy2 = nlcj 
    909             ELSE                               ;   ix1 = 1      ;   ix2 = icnt(1)   ;   iy1 = 1      ;   iy2 = icnt(2) 
    910             ENDIF 
    911          ENDIF 
     1080             IF( llnoov ) THEN 
     1081                IF( idom /= jpdom_unknown ) THEN   ;   ix1 = nldi   ;   ix2 = nlei      ;   iy1 = nldj   ;   iy2 = nlej 
     1082                ELSE                               ;   ix1 = 1      ;   ix2 = icnt(1)   ;   iy1 = 1      ;   iy2 = icnt(2) 
     1083                ENDIF 
     1084             ELSE 
     1085                IF( idom /= jpdom_unknown ) THEN   ;   ix1 = 1      ;   ix2 = nlci      ;   iy1 = 1      ;   iy2 = nlcj 
     1086                ELSE                               ;   ix1 = 1      ;   ix2 = icnt(1)   ;   iy1 = 1      ;   iy2 = icnt(2) 
     1087                ENDIF 
     1088             ENDIF 
    9121089       
    913          SELECT CASE (iom_file(kiomid)%iolib) 
    914          CASE (jpioipsl )   ;   CALL iom_ioipsl_get(  kiomid, idvar, inbdim, istart, icnt, ix1, ix2, iy1, iy2,   & 
    915             &                                         pv_r1d, pv_r2d, pv_r3d ) 
    916          CASE (jpnf90   )   ;   CALL iom_nf90_get(    kiomid, idvar, inbdim, istart, icnt, ix1, ix2, iy1, iy2,   & 
    917             &                                         pv_r1d, pv_r2d, pv_r3d ) 
    918          CASE (jprstdimg)   ;   CALL iom_rstdimg_get( kiomid, idom, idvar, ix1, ix2, iy1, iy2,   & 
    919             &                                         pv_r1d, pv_r2d, pv_r3d ) 
    920          CASE DEFAULT     
    921             CALL ctl_stop( TRIM(clinfo)//' accepted IO library are only jpioipsl, jpnf90 and jprstdimg' ) 
    922          END SELECT 
    923  
    924          IF( istop == nstop ) THEN   ! no additional errors until this point... 
    925             IF(lwp) WRITE(numout,"(10x,' read ',a,' (rec: ',i6,') in ',a,' ok')") TRIM(cdvar), itime, TRIM(iom_file(kiomid)%name) 
     1090             SELECT CASE (iom_file(kiomid)%iolib) 
     1091             CASE (jpioipsl )   ;   CALL iom_ioipsl_get(  kiomid, idvar, inbdim, istart, icnt, ix1, ix2, iy1, iy2,   & 
     1092                &                                         pv_r1d, pv_r2d, pv_r3d ) 
     1093             CASE (jpnf90   )   ;   CALL iom_nf90_get(    kiomid, idvar, inbdim, istart, icnt, ix1, ix2, iy1, iy2,   & 
     1094                &                                         pv_r1d, pv_r2d, pv_r3d ) 
     1095             CASE (jprstdimg)   ;   CALL iom_rstdimg_get( kiomid, idom, idvar, ix1, ix2, iy1, iy2,   & 
     1096                &                                         pv_r1d, pv_r2d, pv_r3d ) 
     1097             CASE DEFAULT     
     1098                CALL ctl_stop( TRIM(clinfo)//' accepted IO library are only jpioipsl, jpnf90 and jprstdimg' ) 
     1099             END SELECT 
     1100 
     1101             IF( istop == nstop ) THEN   ! no additional errors until this point... 
     1102                IF(lwp) WRITE(numout,"(10x,' read ',a,' (rec: ',i6,') in ',a,' ok')") TRIM(cdvar), itime, TRIM(iom_file(kiomid)%name) 
    9261103           
    927             !--- overlap areas and extra hallows (mpp) 
    928             IF(     PRESENT(pv_r2d) .AND. idom /= jpdom_unknown ) THEN 
    929                CALL lbc_lnk( pv_r2d,'Z',-999.,'no0' ) 
    930             ELSEIF( PRESENT(pv_r3d) .AND. idom /= jpdom_unknown ) THEN 
    931                ! this if could be simplified with the new lbc_lnk that works with any size of the 3rd dimension 
    932                IF( icnt(3) == jpk ) THEN 
    933                   CALL lbc_lnk( pv_r3d,'Z',-999.,'no0' ) 
    934                ELSE   ! put some arbitrary value (a call to lbc_lnk will be done later...) 
    935                   DO jj = nlcj+1, jpj   ;   pv_r3d(1:nlci, jj, :) = pv_r3d(1:nlci, nlej, :)   ;   END DO 
    936                   DO ji = nlci+1, jpi   ;   pv_r3d(ji    , : , :) = pv_r3d(nlei  , :   , :)   ;   END DO 
    937                ENDIF 
    938             ENDIF 
    939              
    940             ! C1D case : always call lbc_lnk to replicate the central value over the whole 3X3 domain 
    941             IF( lk_c1d .AND. PRESENT(pv_r2d) )   CALL lbc_lnk( pv_r2d,'Z',1. ) 
    942             IF( lk_c1d .AND. PRESENT(pv_r3d) )   CALL lbc_lnk( pv_r3d,'Z',1. ) 
    943      
    944             !--- Apply scale_factor and offset 
    945             zscf = iom_file(kiomid)%scf(idvar)      ! scale factor 
    946             zofs = iom_file(kiomid)%ofs(idvar)      ! offset 
    947             IF(     PRESENT(pv_r1d) ) THEN 
    948                IF( zscf /= 1. )   pv_r1d(:) = pv_r1d(:) * zscf  
    949                IF( zofs /= 0. )   pv_r1d(:) = pv_r1d(:) + zofs 
    950             ELSEIF( PRESENT(pv_r2d) ) THEN 
     1104                !--- overlap areas and extra hallows (mpp) 
     1105                IF(     PRESENT(pv_r2d) .AND. idom /= jpdom_unknown ) THEN 
     1106                   CALL lbc_lnk( pv_r2d,'Z',-999.,'no0' ) 
     1107                ELSEIF( PRESENT(pv_r3d) .AND. idom /= jpdom_unknown ) THEN 
     1108                   ! this if could be simplified with the new lbc_lnk that works with any size of the 3rd dimension 
     1109                   IF( icnt(3) == jpk ) THEN 
     1110                      CALL lbc_lnk( pv_r3d,'Z',-999.,'no0' ) 
     1111                   ELSE   ! put some arbitrary value (a call to lbc_lnk will be done later...) 
     1112                      DO jj = nlcj+1, jpj   ;   pv_r3d(1:nlci, jj, :) = pv_r3d(1:nlci, nlej, :)   ;   END DO 
     1113                      DO ji = nlci+1, jpi   ;   pv_r3d(ji    , : , :) = pv_r3d(nlei  , :   , :)   ;   END DO 
     1114                   ENDIF 
     1115                ENDIF 
     1116                ! 
     1117             ELSE 
     1118                ! return if istop == nstop is false 
     1119                RETURN 
     1120             ENDIF 
     1121          ELSE 
     1122             ! return if statment idvar > 0 .AND. istop == nstop is false 
     1123             RETURN 
     1124          ENDIF 
     1125          ! 
     1126       ELSE        ! read using XIOS. Only if KEY_IOMPUT is defined 
     1127#if defined key_iomput 
     1128!would be good to be able to check which context is active and swap only if current is not restart 
     1129          CALL iom_swap( TRIM(rxios_context) )  
     1130          IF( PRESENT(pv_r3d) ) THEN 
     1131             if(lwp) write(numout,*) 'XIOS RST READ (3D): ',trim(cdvar) 
     1132             CALL xios_recv_field( trim(cdvar), pv_r3d) 
     1133             IF(idom /= jpdom_unknown ) then 
     1134                 CALL lbc_lnk( pv_r3d,'Z',-999.,'no0' ) 
     1135             ENDIF 
     1136          ELSEIF( PRESENT(pv_r2d) ) THEN 
     1137             if(lwp) write(numout,*) 'XIOS RST READ (2D): ', trim(cdvar) 
     1138             CALL xios_recv_field( trim(cdvar), pv_r2d) 
     1139             IF(idom /= jpdom_unknown ) THEN 
     1140                 CALL lbc_lnk(pv_r2d,'Z',-999.,'no0') 
     1141             ENDIF 
     1142          ELSEIF( PRESENT(pv_r1d) ) THEN 
     1143             if(lwp) write(numout,*) 'XIOS RST READ (1D): ', trim(cdvar) 
     1144             CALL xios_recv_field( trim(cdvar), pv_r1d) 
     1145          ENDIF 
     1146          CALL iom_swap( TRIM(cxios_context) ) 
     1147#else 
     1148          istop = istop + 1  
     1149          clinfo = 'Can not use XIOS in iom_get_123d, file: '//trim(clname)//', var:'//trim(cdvar) 
     1150#endif 
     1151       ENDIF 
     1152!some final adjustments 
     1153       ! C1D case : always call lbc_lnk to replicate the central value over the whole 3X3 domain 
     1154       IF( lk_c1d .AND. PRESENT(pv_r2d) )   CALL lbc_lnk( pv_r2d,'Z',1. ) 
     1155       IF( lk_c1d .AND. PRESENT(pv_r3d) )   CALL lbc_lnk( pv_r3d,'Z',1. ) 
     1156 
     1157       !--- Apply scale_factor and offset 
     1158       zscf = iom_file(kiomid)%scf(idvar)      ! scale factor 
     1159       zofs = iom_file(kiomid)%ofs(idvar)      ! offset 
     1160       IF(     PRESENT(pv_r1d) ) THEN 
     1161          IF( zscf /= 1. )   pv_r1d(:) = pv_r1d(:) * zscf  
     1162          IF( zofs /= 0. )   pv_r1d(:) = pv_r1d(:) + zofs 
     1163       ELSEIF( PRESENT(pv_r2d) ) THEN 
    9511164!CDIR COLLAPSE 
    952                IF( zscf /= 1.)   pv_r2d(:,:) = pv_r2d(:,:) * zscf 
     1165          IF( zscf /= 1.)   pv_r2d(:,:) = pv_r2d(:,:) * zscf 
    9531166!CDIR COLLAPSE 
    954                IF( zofs /= 0.)   pv_r2d(:,:) = pv_r2d(:,:) + zofs 
    955             ELSEIF( PRESENT(pv_r3d) ) THEN 
     1167          IF( zofs /= 0.)   pv_r2d(:,:) = pv_r2d(:,:) + zofs 
     1168       ELSEIF( PRESENT(pv_r3d) ) THEN 
    9561169!CDIR COLLAPSE 
    957                IF( zscf /= 1.)   pv_r3d(:,:,:) = pv_r3d(:,:,:) * zscf 
     1170          IF( zscf /= 1.)   pv_r3d(:,:,:) = pv_r3d(:,:,:) * zscf 
    9581171!CDIR COLLAPSE 
    959                IF( zofs /= 0.)   pv_r3d(:,:,:) = pv_r3d(:,:,:) + zofs 
    960             ENDIF 
    961             ! 
    962          ENDIF 
    963          ! 
    964       ENDIF 
    965       ! 
     1172          IF( zofs /= 0.)   pv_r3d(:,:,:) = pv_r3d(:,:,:) + zofs 
     1173       ENDIF 
    9661174   END SUBROUTINE iom_get_123d 
    9671175 
     
    12301438            &    lonvalue_1D=lonvalue, latvalue_1D=latvalue, mask_1D=mask, nvertex=nvertex, bounds_lon_1D=bounds_lon,                  & 
    12311439            &    bounds_lat_1D=bounds_lat, area=area, type='curvilinear') 
    1232      ENDIF 
     1440      ENDIF 
    12331441      IF ( xios_is_valid_domaingroup(cdid) ) THEN 
    12341442         CALL xios_set_domaingroup_attr( cdid, ni_glo=ni_glo, nj_glo=nj_glo, ibegin=ibegin, jbegin=jbegin, ni=ni, nj=nj,   & 
     
    13671575 
    13681576 
    1369    SUBROUTINE set_grid( cdgrd, plon, plat ) 
     1577   SUBROUTINE set_grid( cdgrd, plon, plat, lmask ) 
    13701578      !!---------------------------------------------------------------------- 
    13711579      !!                     ***  ROUTINE set_grid  *** 
     
    13801588      REAL(wp), DIMENSION(jpi,jpj,jpk) ::   zmask 
    13811589      INTEGER  :: ni,nj 
     1590      LOGICAL :: lmask 
    13821591       
    13831592      ni=nlei-nldi+1 ; nj=nlej-nldj+1 
     
    13921601         &                                     latvalue = RESHAPE(plat(nldi:nlei, nldj:nlej),(/ ni*nj /)))   
    13931602 
    1394       IF ( ln_mskland ) THEN 
     1603      IF ( lmask ) THEN 
    13951604         ! mask land points, keep values on coast line -> specific mask for U, V and W points 
    13961605         SELECT CASE ( cdgrd ) 
     
    14361645      ! Offset of coordinate representing bottom-left corner 
    14371646      SELECT CASE ( TRIM(cdgrd) ) 
    1438          CASE ('T', 'W') 
     1647         CASE ('T', 'W', 'N') 
    14391648            icnr = -1 ; jcnr = -1 
    14401649         CASE ('U') 
  • branches/UKMO/dev_r5518_GO6_package_fix_rnf_MOCI_TEST_SUITE/NEMOGCM/NEMO/OPA_SRC/IOM/iom_def.F90

    r8193 r8195  
    5151!$AGRIF_DO_NOT_TREAT 
    5252   INTEGER, PUBLIC            ::   iom_open_init = 0   !: used to initialize iom_file(:)%nfid to 0 
     53!XIOS read restart    
     54   LOGICAL, PUBLIC            ::   lxios_read          !: read single file restart using XIOS 
     55   LOGICAL, PUBLIC            ::   lxios_sini = .FALSE. ! is restart in a single file 
     56   LOGICAL, PUBLIC            ::   lxios_set  = .FALSE.  
    5357 
    5458   TYPE, PUBLIC ::   file_descriptor 
     
    7074   END TYPE file_descriptor 
    7175   TYPE(file_descriptor), DIMENSION(jpmax_files), PUBLIC ::   iom_file !: array containing the info for all opened files 
     76 
     77   INTEGER, PARAMETER, PUBLIC                   :: max_rst_fields = 85   
     78!  CHARACTER(len=30),DIMENSION(max_rst_fields), PUBLIC   :: rst_fields ! names of variables in restart file 
     79 
     80   TYPE, PUBLIC :: RST_FIELD   
     81    CHARACTER(len=30) :: vname ! names of variables in restart file 
     82    CHARACTER(len=30) :: grid 
     83   END TYPE RST_FIELD 
     84   TYPE(RST_FIELD), PUBLIC :: rst_fields(max_rst_fields) 
     85 
    7286!$AGRIF_END_DO_NOT_TREAT 
    7387 
  • branches/UKMO/dev_r5518_GO6_package_fix_rnf_MOCI_TEST_SUITE/NEMOGCM/NEMO/OPA_SRC/IOM/iom_nf90.F90

    r6491 r8195  
    122122            CALL iom_nf90_check(NF90_DEF_DIM( if90id, 'x', kdompar(1,1)  , idmy ), clinfo) 
    123123            CALL iom_nf90_check(NF90_DEF_DIM( if90id, 'y', kdompar(2,1)  , idmy ), clinfo) 
    124             CALL iom_nf90_check(NF90_DEF_DIM( if90id, 'z', jpk           , idmy ), clinfo) 
    125             CALL iom_nf90_check(NF90_DEF_DIM( if90id, 't', NF90_UNLIMITED, idmy ), clinfo) 
     124            CALL iom_nf90_check(NF90_DEF_DIM( if90id, 'nav_lev', jpk           , idmy ), clinfo) 
     125            CALL iom_nf90_check(NF90_DEF_DIM( if90id, 'time_counter', NF90_UNLIMITED, idmy ), clinfo) 
    126126            ! global attributes 
    127127            CALL iom_nf90_check(NF90_PUT_ATT( if90id, NF90_GLOBAL, 'DOMAIN_number_total'   , jpnij              ), clinfo) 
  • branches/UKMO/dev_r5518_GO6_package_fix_rnf_MOCI_TEST_SUITE/NEMOGCM/NEMO/OPA_SRC/IOM/restart.F90

    r8193 r8195  
    2626   USE divcur          ! hor. divergence and curl      (div & cur routines) 
    2727   USE sbc_oce         ! for icesheet freshwater input variables 
     28   USE iom_def, ONLY : lxios_read, lxios_set, lxios_sini 
     29   USE timing 
    2830 
    2931   IMPLICIT NONE 
     
    208210            WRITE(numout,*) '~~~~~~~~' 
    209211         ENDIF 
    210  
     212         lxios_sini = .FALSE. 
    211213         clpath = TRIM(cn_ocerst_indir) 
    212214         IF( clpath(LEN_TRIM(clpath):) /= '/' ) clpath = TRIM(clpath) // '/' 
     
    218220         ENDIF 
    219221         CALL iom_open( TRIM(clpath)//cn_ocerst_in, numror, kiolib = jlibalt ) 
    220       ENDIF 
     222! are we using XIOS to read the data? Part above will have to modified once XIOS 
     223! can handle checking if variable is in the restart file (there will be no need to open 
     224! restart) 
     225         IF(.NOT.lxios_set) lxios_read = lxios_read.AND.lxios_sini 
     226         IF( lxios_read) THEN 
     227         if(.NOT.lxios_set) then 
     228             rxios_context = 'nemo_rst' 
     229             call iom_init( rxios_context ) 
     230             lxios_set = .TRUE. 
     231         endif 
     232         ENDIF 
     233         IF( TRIM(Agrif_CFixed()) /= '0' .AND. lxios_read) THEN 
     234            rxios_context = 'nemo_rst' 
     235            call iom_init( rxios_context ) 
     236         ENDIF  
     237      ENDIF 
     238 
    221239   END SUBROUTINE rst_read_open 
    222240 
     
    232250      INTEGER  ::   jk 
    233251      LOGICAL  ::   llok 
     252      TYPE(xios_duration):: dtime 
     253      integer::ni,nj,nk 
    234254      !!---------------------------------------------------------------------- 
    235255 
     
    238258      ! Check dynamics and tracer time-step consistency and force Euler restart if changed 
    239259      IF( iom_varid( numror, 'rdt', ldstop = .FALSE. ) > 0 )   THEN 
    240          CALL iom_get( numror, 'rdt', zrdt ) 
     260         CALL iom_get( numror, 'rdt', zrdt, lrxios = lxios_read ) 
    241261         IF( zrdt /= rdt )   neuler = 0 
    242262      ENDIF 
    243263      IF( iom_varid( numror, 'rdttra1', ldstop = .FALSE. ) > 0 )   THEN 
    244          CALL iom_get( numror, 'rdttra1', zrdttra1 ) 
     264         CALL iom_get( numror, 'rdttra1', zrdttra1, lrxios = lxios_read ) 
    245265         IF( zrdttra1 /= rdttra(1) )   neuler = 0 
    246266      ENDIF 
    247267      !  
    248268      IF( iom_varid( numror, 'ub', ldstop = .FALSE. ) > 0 ) THEN 
    249          CALL iom_get( numror, jpdom_autoglo, 'ub'     , ub      )   ! before fields 
    250          CALL iom_get( numror, jpdom_autoglo, 'vb'     , vb      ) 
    251          CALL iom_get( numror, jpdom_autoglo, 'tb'     , tsb(:,:,:,jp_tem) ) 
    252          CALL iom_get( numror, jpdom_autoglo, 'sb'     , tsb(:,:,:,jp_sal) ) 
    253          CALL iom_get( numror, jpdom_autoglo, 'rotb'   , rotb    ) 
    254          CALL iom_get( numror, jpdom_autoglo, 'hdivb'  , hdivb  ) 
    255          CALL iom_get( numror, jpdom_autoglo, 'sshb'   , sshb    ) 
     269         CALL iom_get( numror, jpdom_autoglo, 'ub'     , ub, lrxios = lxios_read )   ! before fields 
     270         CALL iom_get( numror, jpdom_autoglo, 'vb'     , vb, lrxios = lxios_read ) 
     271         CALL iom_get( numror, jpdom_autoglo, 'tb'     , tsb(:,:,:,jp_tem), lrxios = lxios_read ) 
     272         CALL iom_get( numror, jpdom_autoglo, 'sb'     , tsb(:,:,:,jp_sal), lrxios = lxios_read ) 
     273         CALL iom_get( numror, jpdom_autoglo, 'rotb'   , rotb, lrxios = lxios_read ) 
     274         CALL iom_get( numror, jpdom_autoglo, 'hdivb'  , hdivb, lrxios = lxios_read ) 
     275         CALL iom_get( numror, jpdom_autoglo, 'sshb'   , sshb, lrxios = lxios_read ) 
    256276      ELSE 
    257277         neuler = 0 
    258278      ENDIF 
    259279      ! 
    260       CALL iom_get( numror, jpdom_autoglo, 'un'     , un      )   ! now    fields 
    261       CALL iom_get( numror, jpdom_autoglo, 'vn'     , vn      ) 
    262       CALL iom_get( numror, jpdom_autoglo, 'tn'     , tsn(:,:,:,jp_tem) ) 
    263       CALL iom_get( numror, jpdom_autoglo, 'sn'     , tsn(:,:,:,jp_sal) ) 
    264       CALL iom_get( numror, jpdom_autoglo, 'sshn'   , sshn    ) 
     280      CALL iom_get( numror, jpdom_autoglo, 'un'     , un, lrxios = lxios_read )   ! now    fields 
     281      CALL iom_get( numror, jpdom_autoglo, 'vn'     , vn, lrxios = lxios_read ) 
     282      CALL iom_get( numror, jpdom_autoglo, 'tn'     , tsn(:,:,:,jp_tem), lrxios = lxios_read ) 
     283      CALL iom_get( numror, jpdom_autoglo, 'sn'     , tsn(:,:,:,jp_sal), lrxios = lxios_read ) 
     284      CALL iom_get( numror, jpdom_autoglo, 'sshn'   , sshn, lrxios = lxios_read ) 
    265285      IF( iom_varid( numror, 'rotn', ldstop = .FALSE. ) > 0 ) THEN 
    266          CALL iom_get( numror, jpdom_autoglo, 'rotn'   , rotn    ) 
    267          CALL iom_get( numror, jpdom_autoglo, 'hdivn'  , hdivn  ) 
     286         CALL iom_get( numror, jpdom_autoglo, 'rotn'   , rotn, lrxios = lxios_read ) 
     287         CALL iom_get( numror, jpdom_autoglo, 'hdivn'  , hdivn, lrxios = lxios_read ) 
    268288      ELSE 
    269289         CALL div_cur( 0 )                              ! Horizontal divergence & Relative vorticity 
    270290      ENDIF 
    271291      IF( iom_varid( numror, 'rhop', ldstop = .FALSE. ) > 0 ) THEN 
    272          CALL iom_get( numror, jpdom_autoglo, 'rhop'   , rhop    )   ! now    potential density 
     292         CALL iom_get( numror, jpdom_autoglo, 'rhop'   , rhop, lrxios = lxios_read )   ! now    potential density 
    273293      ELSE 
    274294         CALL eos    ( tsn, rhd, rhop, fsdept_n(:,:,:) )    
     
    276296#if defined key_zdfkpp 
    277297      IF( iom_varid( numror, 'rhd', ldstop = .FALSE. ) > 0 ) THEN 
    278          CALL iom_get( numror, jpdom_autoglo, 'rhd'    , rhd    )   ! now    in situ density anomaly 
     298         CALL iom_get( numror, jpdom_autoglo, 'rhd'    , rhd, lrxios = lxios_read )   ! now    in situ density anomaly 
    279299      ELSE 
    280300         CALL eos( tsn, rhd, fsdept_n(:,:,:) )   ! compute rhd 
     
    283303      ! 
    284304      IF( iom_varid( numror, 'greenland_icesheet_mass', ldstop = .FALSE. ) > 0 )   THEN 
    285          CALL iom_get( numror, 'greenland_icesheet_mass', greenland_icesheet_mass ) 
    286          CALL iom_get( numror, 'greenland_icesheet_timelapsed', greenland_icesheet_timelapsed ) 
    287          CALL iom_get( numror, 'greenland_icesheet_mass_roc', greenland_icesheet_mass_rate_of_change ) 
     305         CALL iom_get( numror, 'greenland_icesheet_mass', greenland_icesheet_mass, lrxios = lxios_read ) 
     306         CALL iom_get( numror, 'greenland_icesheet_timelapsed', greenland_icesheet_timelapsed, lrxios = lxios_read ) 
     307         CALL iom_get( numror, 'greenland_icesheet_mass_roc', greenland_icesheet_mass_rate_of_change, lrxios = lxios_read ) 
    288308      ELSE 
    289309         greenland_icesheet_mass = 0.0  
     
    292312      ENDIF 
    293313      IF( iom_varid( numror, 'antarctica_icesheet_mass', ldstop = .FALSE. ) > 0 )   THEN 
    294          CALL iom_get( numror, 'antarctica_icesheet_mass', antarctica_icesheet_mass ) 
    295          CALL iom_get( numror, 'antarctica_icesheet_timelapsed', antarctica_icesheet_timelapsed ) 
    296          CALL iom_get( numror, 'antarctica_icesheet_mass_roc', antarctica_icesheet_mass_rate_of_change ) 
     314         CALL iom_get( numror, 'antarctica_icesheet_mass', antarctica_icesheet_mass, lrxios = lxios_read ) 
     315         CALL iom_get( numror, 'antarctica_icesheet_timelapsed', antarctica_icesheet_timelapsed, lrxios = lxios_read ) 
     316         CALL iom_get( numror, 'antarctica_icesheet_mass_roc', antarctica_icesheet_mass_rate_of_change, lrxios = lxios_read ) 
    297317      ELSE 
    298318         antarctica_icesheet_mass = 0.0  
     
    300320         antarctica_icesheet_timelapsed = 0.0 
    301321      ENDIF 
     322!     IF( nn_timing == 1 )  CALL timing_stop('iom_read') 
    302323 
    303324      IF( neuler == 0 ) THEN                                  ! Euler restart (neuler=0) 
  • branches/UKMO/dev_r5518_GO6_package_fix_rnf_MOCI_TEST_SUITE/NEMOGCM/NEMO/OPA_SRC/SBC/sbcapr.F90

    r8193 r8195  
    6868      CHARACTER(len=100) ::  cn_dir   ! Root directory for location of ssr files 
    6969      TYPE(FLD_N)        ::  sn_apr   ! informations about the fields to be read 
     70      LOGICAL            ::  lxios_read ! read restart using XIOS? 
    7071      !! 
    7172      NAMELIST/namsbc_apr/ cn_dir, sn_apr, ln_ref_apr, rn_pref, ln_apr_obc 
     
    143144         IF( ln_rstart .AND. iom_varid( numror, 'ssh_ibb', ldstop = .FALSE. ) > 0 ) THEN  
    144145            IF(lwp) WRITE(numout,*) 'sbc_apr:   ssh_ibb read in the restart file' 
    145             CALL iom_get( numror, jpdom_autoglo, 'ssh_ibb', ssh_ibb )   ! before inv. barometer ssh 
     146            CALL iom_get( numror, jpdom_autoglo, 'ssh_ibb', ssh_ibb, lrxios = lxios_read )   ! before inv. barometer ssh 
    146147            ! 
    147148         ELSE                                         !* no restart: set from nit000 values 
  • branches/UKMO/dev_r5518_GO6_package_fix_rnf_MOCI_TEST_SUITE/NEMOGCM/NEMO/OPA_SRC/SBC/sbcisf.F90

    r7179 r8195  
    2727   USE fldread         ! read input field at current time step 
    2828   USE lib_fortran, ONLY: glob_sum 
     29   USE iom_def, ONLY : lxios_read 
    2930 
    3031   IMPLICIT NONE 
     
    409410                 & iom_varid( numror, 'fwf_isf_b', ldstop = .FALSE. ) > 0 ) THEN 
    410411               IF(lwp) WRITE(numout,*) '          nit000-1 isf tracer content forcing fields read in the restart file' 
    411                CALL iom_get( numror, jpdom_autoglo, 'fwf_isf_b', fwfisf_b(:,:) )   ! before salt content isf_tsc trend 
    412                CALL iom_get( numror, jpdom_autoglo, 'isf_sc_b', risf_tsc_b(:,:,jp_sal) )   ! before salt content isf_tsc trend 
    413                CALL iom_get( numror, jpdom_autoglo, 'isf_hc_b', risf_tsc_b(:,:,jp_tem) )   ! before salt content isf_tsc trend 
     412               CALL iom_get( numror, jpdom_autoglo, 'fwf_isf_b', fwfisf_b(:,:), lrxios = lxios_read )   ! before salt content isf_tsc trend 
     413               CALL iom_get( numror, jpdom_autoglo, 'isf_sc_b', risf_tsc_b(:,:,jp_sal), lrxios = lxios_read )   ! before salt content isf_tsc trend 
     414               CALL iom_get( numror, jpdom_autoglo, 'isf_hc_b', risf_tsc_b(:,:,jp_tem), lrxios = lxios_read )   ! before salt content isf_tsc trend 
    414415            ELSE 
    415416               fwfisf_b(:,:)    = fwfisf(:,:) 
  • branches/UKMO/dev_r5518_GO6_package_fix_rnf_MOCI_TEST_SUITE/NEMOGCM/NEMO/OPA_SRC/SBC/sbcmod.F90

    r7782 r8195  
    5454   USE sbcwave          ! Wave module 
    5555   USE bdy_par          ! Require lk_bdy 
     56   USE iom_def, ONLY : lxios_read 
    5657 
    5758   IMPLICIT NONE 
     
    420421            & iom_varid( numror, 'utau_b', ldstop = .FALSE. ) > 0 ) THEN  
    421422            IF(lwp) WRITE(numout,*) '          nit000-1 surface forcing fields red in the restart file' 
    422             CALL iom_get( numror, jpdom_autoglo, 'utau_b', utau_b )   ! before i-stress  (U-point) 
    423             CALL iom_get( numror, jpdom_autoglo, 'vtau_b', vtau_b )   ! before j-stress  (V-point) 
    424             CALL iom_get( numror, jpdom_autoglo, 'qns_b' , qns_b  )   ! before non solar heat flux (T-point) 
     423            CALL iom_get( numror, jpdom_autoglo, 'utau_b', utau_b, lrxios = lxios_read )   ! before i-stress  (U-point) 
     424            CALL iom_get( numror, jpdom_autoglo, 'vtau_b', vtau_b, lrxios = lxios_read )   ! before j-stress  (V-point) 
     425            CALL iom_get( numror, jpdom_autoglo, 'qns_b' , qns_b, lrxios = lxios_read  )   ! before non solar heat flux (T-point) 
    425426            ! The 3D heat content due to qsr forcing is treated in traqsr 
    426             ! CALL iom_get( numror, jpdom_autoglo, 'qsr_b' , qsr_b  ) ! before     solar heat flux (T-point) 
    427             CALL iom_get( numror, jpdom_autoglo, 'emp_b', emp_b  )    ! before     freshwater flux (T-point) 
     427            ! CALL iom_get( numror, jpdom_autoglo, 'qsr_b' , qsr_b, lrxios = lxios_read  ) ! before     solar heat flux (T-point) 
     428            CALL iom_get( numror, jpdom_autoglo, 'emp_b', emp_b, lrxios = lxios_read  )    ! before     freshwater flux (T-point) 
    428429            ! To ensure restart capability with 3.3x/3.4 restart files    !! to be removed in v3.6 
    429430            IF( iom_varid( numror, 'sfx_b', ldstop = .FALSE. ) > 0 ) THEN 
    430                CALL iom_get( numror, jpdom_autoglo, 'sfx_b', sfx_b )  ! before salt flux (T-point) 
     431               CALL iom_get( numror, jpdom_autoglo, 'sfx_b', sfx_b, lrxios = lxios_read )  ! before salt flux (T-point) 
    431432            ELSE 
    432433               sfx_b (:,:) = sfx(:,:) 
  • branches/UKMO/dev_r5518_GO6_package_fix_rnf_MOCI_TEST_SUITE/NEMOGCM/NEMO/OPA_SRC/SBC/sbcrnf.F90

    r7781 r8195  
    2727   USE eosbn2 
    2828   USE wrk_nemo        ! Memory allocation 
     29   USE iom_def, ONLY : lxios_read 
    2930 
    3031   IMPLICIT NONE 
     
    147148            & iom_varid( numror, 'rnf_b', ldstop = .FALSE. ) > 0 ) THEN 
    148149            IF(lwp) WRITE(numout,*) '          nit000-1 runoff forcing fields red in the restart file' 
    149             CALL iom_get( numror, jpdom_autoglo, 'rnf_b', rnf_b )     ! before runoff 
    150             CALL iom_get( numror, jpdom_autoglo, 'rnf_hc_b', rnf_tsc_b(:,:,jp_tem) )   ! before heat content of runoff 
    151             CALL iom_get( numror, jpdom_autoglo, 'rnf_sc_b', rnf_tsc_b(:,:,jp_sal) )   ! before salinity content of runoff 
     150            CALL iom_get( numror, jpdom_autoglo, 'rnf_b', rnf_b, lrxios = lxios_read )     ! before runoff 
     151            CALL iom_get( numror, jpdom_autoglo, 'rnf_hc_b', rnf_tsc_b(:,:,jp_tem), lrxios = lxios_read )   ! before heat content of runoff 
     152            CALL iom_get( numror, jpdom_autoglo, 'rnf_sc_b', rnf_tsc_b(:,:,jp_sal), lrxios = lxios_read )   ! before salinity content of runoff 
    152153         ELSE                                                   !* no restart: set from nit000 values 
    153154            IF(lwp) WRITE(numout,*) '          nit000-1 runoff forcing fields set to nit000' 
  • branches/UKMO/dev_r5518_GO6_package_fix_rnf_MOCI_TEST_SUITE/NEMOGCM/NEMO/OPA_SRC/SBC/sbcssm.F90

    r6486 r8195  
    2121   USE prtctl          ! Print control 
    2222   USE iom             ! IOM library 
     23   USE iom_def, ONLY : lxios_read 
    2324 
    2425   IMPLICIT NONE 
     
    206207         IF( ln_rstart .AND. iom_varid( numror, 'nn_fsbc', ldstop = .FALSE. ) > 0 ) THEN 
    207208            l_ssm_mean = .TRUE. 
    208             CALL iom_get( numror               , 'nn_fsbc', zf_sbc )   ! sbc frequency of previous run 
    209             CALL iom_get( numror, jpdom_autoglo, 'ssu_m'  , ssu_m  )   ! sea surface mean velocity    (T-point) 
    210             CALL iom_get( numror, jpdom_autoglo, 'ssv_m'  , ssv_m  )   !   "         "    velocity    (V-point) 
    211             CALL iom_get( numror, jpdom_autoglo, 'sst_m'  , sst_m  )   !   "         "    temperature (T-point) 
    212             CALL iom_get( numror, jpdom_autoglo, 'sss_m'  , sss_m  )   !   "         "    salinity    (T-point) 
    213             CALL iom_get( numror, jpdom_autoglo, 'ssh_m'  , ssh_m  )   !   "         "    height      (T-point) 
    214             IF( lk_vvl ) CALL iom_get( numror, jpdom_autoglo, 'e3t_m', e3t_m ) 
     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    (T-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            IF( lk_vvl ) CALL iom_get( numror, jpdom_autoglo, 'e3t_m', e3t_m, lrxios = lxios_read ) 
    215216            ! fraction of solar net radiation absorbed in 1st T level 
    216217            IF( iom_varid( numror, 'frq_m', ldstop = .FALSE. ) > 0 ) THEN 
    217                CALL iom_get( numror, jpdom_autoglo, 'frq_m'  , frq_m  ) 
     218               CALL iom_get( numror, jpdom_autoglo, 'frq_m'  , frq_m, lrxios = lxios_read  ) 
    218219            ELSE 
    219220               frq_m(:,:) = 1._wp   ! default definition 
  • branches/UKMO/dev_r5518_GO6_package_fix_rnf_MOCI_TEST_SUITE/NEMOGCM/NEMO/OPA_SRC/TRA/traldf_iso.F90

    r8193 r8195  
    355355         CALL trd_tra( kt, cdtype, jp_sal, jptra_iso_z1, ztraz )    ! 
    356356      ENDIF 
     357      DEALLOCATE( ztrax, ztray, ztraz )  
     358      IF( l_trdtra  .and. cdtype == 'TRA' ) DEALLOCATE( ztrax_T, ztray_T, ztraz_T )  
    357359      ! 
    358360      DEALLOCATE( z2d )  
  • branches/UKMO/dev_r5518_GO6_package_fix_rnf_MOCI_TEST_SUITE/NEMOGCM/NEMO/OPA_SRC/TRA/traqsr.F90

    r6498 r8195  
    3333   USE wrk_nemo       ! Memory Allocation 
    3434   USE timing         ! Timing 
    35  
     35   USE iom_def, ONLY : lxios_read 
    3636   IMPLICIT NONE 
    3737   PRIVATE 
     
    137137            IF(lwp) WRITE(numout,*) '          nit000-1 qsr tracer content forcing field red in the restart file' 
    138138            zfact = 0.5e0 
    139             CALL iom_get( numror, jpdom_autoglo, 'qsr_hc_b', qsr_hc_b )   ! before heat content trend due to Qsr flux 
     139            CALL iom_get( numror, jpdom_autoglo, 'qsr_hc_b', qsr_hc_b, lrxios = lxios_read )   ! before heat content trend due to Qsr flux 
    140140         ELSE                                           ! No restart or restart not found: Euler forward time stepping 
    141141            zfact = 1.e0 
     
    607607      ! initialisation of fraqsr_1lev used in sbcssm 
    608608      IF( iom_varid( numror, 'fraqsr_1lev', ldstop = .FALSE. ) > 0 ) THEN 
    609          CALL iom_get( numror, jpdom_autoglo, 'fraqsr_1lev'  , fraqsr_1lev  ) 
     609         CALL iom_get( numror, jpdom_autoglo, 'fraqsr_1lev'  , fraqsr_1lev, lrxios = lxios_read  ) 
    610610      ELSE 
    611611         fraqsr_1lev(:,:) = 1._wp   ! default definition 
  • branches/UKMO/dev_r5518_GO6_package_fix_rnf_MOCI_TEST_SUITE/NEMOGCM/NEMO/OPA_SRC/TRA/trasbc.F90

    r6793 r8195  
    3333   USE timing          ! Timing 
    3434   USE eosbn2 
     35   USE iom_def, ONLY : lxios_read 
    3536 
    3637   IMPLICIT NONE 
     
    154155            IF(lwp) WRITE(numout,*) '          nit000-1 surface tracer content forcing fields red in the restart file' 
    155156            zfact = 0.5_wp 
    156             CALL iom_get( numror, jpdom_autoglo, 'sbc_hc_b', sbc_tsc_b(:,:,jp_tem) )   ! before heat content sbc trend 
    157             CALL iom_get( numror, jpdom_autoglo, 'sbc_sc_b', sbc_tsc_b(:,:,jp_sal) )   ! before salt content sbc trend 
     157            CALL iom_get( numror, jpdom_autoglo, 'sbc_hc_b', sbc_tsc_b(:,:,jp_tem), lrxios = lxios_read )   ! before heat content sbc trend 
     158            CALL iom_get( numror, jpdom_autoglo, 'sbc_sc_b', sbc_tsc_b(:,:,jp_sal), lrxios = lxios_read )   ! before salt content sbc trend 
    158159         ELSE                                         ! No restart or restart not found: Euler forward time stepping 
    159160            zfact = 1._wp 
  • branches/UKMO/dev_r5518_GO6_package_fix_rnf_MOCI_TEST_SUITE/NEMOGCM/NEMO/OPA_SRC/TRD/trdmxl_rst.F90

    r6486 r8195  
    161161      IF( ln_trdmxl_instant ) THEN  
    162162         !-- Temperature 
    163          CALL iom_get( inum, jpdom_autoglo, 'tmlbb'           , tmlbb          ) 
    164          CALL iom_get( inum, jpdom_autoglo, 'tmlbn'           , tmlbn          ) 
    165          CALL iom_get( inum, jpdom_autoglo, 'tmlatfb'         , tmlatfb        ) 
    166          ! 
    167          !-- Salinity 
    168          CALL iom_get( inum, jpdom_autoglo, 'smlbb'           , smlbb          ) 
    169          CALL iom_get( inum, jpdom_autoglo, 'smlbn'           , smlbn          ) 
    170          CALL iom_get( inum, jpdom_autoglo, 'smlatfb'         , smlatfb        ) 
     163         CALL iom_get( inum, jpdom_autoglo, 'tmlbb'           , tmlbb ) 
     164         CALL iom_get( inum, jpdom_autoglo, 'tmlbn'           , tmlbn ) 
     165         CALL iom_get( inum, jpdom_autoglo, 'tmlatfb'         , tmlatfb ) 
     166         ! 
     167         !-- Salinity 
     168         CALL iom_get( inum, jpdom_autoglo, 'smlbb'           , smlbb ) 
     169         CALL iom_get( inum, jpdom_autoglo, 'smlbn'           , smlbn ) 
     170         CALL iom_get( inum, jpdom_autoglo, 'smlatfb'         , smlatfb ) 
    171171      ELSE 
    172          CALL iom_get( inum, jpdom_autoglo, 'hmxlbn'          , hmxlbn         ) ! needed for hmxl_sum 
    173          ! 
    174          !-- Temperature 
    175          CALL iom_get( inum, jpdom_autoglo, 'tmlbn'           , tmlbn          ) ! needed for tml_sum 
    176          CALL iom_get( inum, jpdom_autoglo, 'tml_sumb'        , tml_sumb       ) 
     172         CALL iom_get( inum, jpdom_autoglo, 'hmxlbn'          , hmxlbn ) ! needed for hmxl_sum 
     173         ! 
     174         !-- Temperature 
     175         CALL iom_get( inum, jpdom_autoglo, 'tmlbn'           , tmlbn ) ! needed for tml_sum 
     176         CALL iom_get( inum, jpdom_autoglo, 'tml_sumb'        , tml_sumb ) 
    177177         DO jk = 1, jpltrd 
    178178            IF( jk < 10 ) THEN   ;   WRITE(charout,FMT="('tmltrd_csum_ub_', I1)")   jk 
     
    184184         ! 
    185185         !-- Salinity 
    186          CALL iom_get( inum, jpdom_autoglo, 'smlbn'           , smlbn          ) ! needed for sml_sum 
    187          CALL iom_get( inum, jpdom_autoglo, 'sml_sumb'        , sml_sumb       ) 
     186         CALL iom_get( inum, jpdom_autoglo, 'smlbn'           , smlbn ) ! needed for sml_sum 
     187         CALL iom_get( inum, jpdom_autoglo, 'sml_sumb'        , sml_sumb ) 
    188188         DO jk = 1, jpltrd 
    189189            IF( jk < 10 ) THEN   ;   WRITE(charout,FMT="('smltrd_csum_ub_', I1)")   jk 
  • branches/UKMO/dev_r5518_GO6_package_fix_rnf_MOCI_TEST_SUITE/NEMOGCM/NEMO/OPA_SRC/ZDF/zdfgls.F90

    r6487 r8195  
    3232   USE timing         ! Timing 
    3333   USE lib_fortran    ! Fortran utilities (allows no signed zero when 'key_nosignedzero' defined)   
     34   USE iom_def, ONLY : lxios_read 
    3435 
    3536   IMPLICIT NONE 
     
    11841185            ! 
    11851186            IF( MIN( id1, id2, id3, id4, id5, id6 ) > 0 ) THEN        ! all required arrays exist 
    1186                CALL iom_get( numror, jpdom_autoglo, 'en'    , en     ) 
    1187                CALL iom_get( numror, jpdom_autoglo, 'avt'   , avt    ) 
    1188                CALL iom_get( numror, jpdom_autoglo, 'avm'   , avm    ) 
    1189                CALL iom_get( numror, jpdom_autoglo, 'avmu'  , avmu   ) 
    1190                CALL iom_get( numror, jpdom_autoglo, 'avmv'  , avmv   ) 
    1191                CALL iom_get( numror, jpdom_autoglo, 'mxln'  , mxln   ) 
     1187               CALL iom_get( numror, jpdom_autoglo, 'en'    , en, lrxios = lxios_read     ) 
     1188               CALL iom_get( numror, jpdom_autoglo, 'avt'   , avt, lrxios = lxios_read    ) 
     1189               CALL iom_get( numror, jpdom_autoglo, 'avm'   , avm, lrxios = lxios_read    ) 
     1190               CALL iom_get( numror, jpdom_autoglo, 'avmu'  , avmu, lrxios = lxios_read   ) 
     1191               CALL iom_get( numror, jpdom_autoglo, 'avmv'  , avmv, lrxios = lxios_read   ) 
     1192               CALL iom_get( numror, jpdom_autoglo, 'mxln'  , mxln, lrxios = lxios_read   ) 
    11921193            ELSE                         
    11931194               IF(lwp) WRITE(numout,*) ' ===>>>> : previous run without gls scheme, en and mxln computed by iterative loop' 
  • branches/UKMO/dev_r5518_GO6_package_fix_rnf_MOCI_TEST_SUITE/NEMOGCM/NEMO/OPA_SRC/ZDF/zdfini.F90

    r6486 r8195  
    2929   USE in_out_manager  ! I/O manager 
    3030   USE iom             ! IOM library 
     31   USE iom_def, ONLY : lxios_read 
    3132 
    3233   IMPLICIT NONE 
     
    170171         ! file in traadv_cen2 end read here.  
    171172         IF( iom_varid( numror, 'avmb', ldstop = .FALSE. ) > 0 ) THEN 
    172             CALL iom_get( numror, jpdom_unknown, 'avmb', avmb ) 
    173             CALL iom_get( numror, jpdom_unknown, 'avtb', avtb ) 
     173            CALL iom_get( numror, jpdom_unknown, 'avmb', avmb, lrxios = lxios_read ) 
     174            CALL iom_get( numror, jpdom_unknown, 'avtb', avtb, lrxios = lxios_read ) 
    174175         ENDIF 
    175176      ENDIF 
  • branches/UKMO/dev_r5518_GO6_package_fix_rnf_MOCI_TEST_SUITE/NEMOGCM/NEMO/OPA_SRC/ZDF/zdftke.F90

    r6498 r8195  
    5757   USE agrif_opa_update 
    5858#endif 
     59   USE iom_def, ONLY : lxios_read 
    5960 
    6061 
     
    935936           ! 
    936937           IF( id1 > 0 ) THEN                       ! 'en' exists 
    937               CALL iom_get( numror, jpdom_autoglo, 'en', en ) 
     938              CALL iom_get( numror, jpdom_autoglo, 'en', en, lrxios = lxios_read ) 
    938939              IF( MIN( id2, id3, id4, id5, id6 ) > 0 ) THEN        ! all required arrays exist 
    939                  CALL iom_get( numror, jpdom_autoglo, 'avt'  , avt   ) 
    940                  CALL iom_get( numror, jpdom_autoglo, 'avm'  , avm   ) 
    941                  CALL iom_get( numror, jpdom_autoglo, 'avmu' , avmu  ) 
    942                  CALL iom_get( numror, jpdom_autoglo, 'avmv' , avmv  ) 
    943                  CALL iom_get( numror, jpdom_autoglo, 'dissl', dissl ) 
     940                 CALL iom_get( numror, jpdom_autoglo, 'avt'  , avt, lrxios = lxios_read   ) 
     941                 CALL iom_get( numror, jpdom_autoglo, 'avm'  , avm, lrxios = lxios_read   ) 
     942                 CALL iom_get( numror, jpdom_autoglo, 'avmu' , avmu, lrxios = lxios_read  ) 
     943                 CALL iom_get( numror, jpdom_autoglo, 'avmv' , avmv, lrxios = lxios_read  ) 
     944                 CALL iom_get( numror, jpdom_autoglo, 'dissl', dissl, lrxios = lxios_read ) 
    944945              ELSE                                                 ! one at least array is missing 
    945946                 CALL tke_avn                                          ! compute avt, avm, avmu, avmv and dissl (approximation) 
  • branches/UKMO/dev_r5518_GO6_package_fix_rnf_MOCI_TEST_SUITE/NEMOGCM/NEMO/OPA_SRC/step.F90

    r6755 r8195  
    385385      IF( kstp == nitend .OR. indic < 0 ) THEN  
    386386                      CALL iom_context_finalize(      cxios_context          ) ! needed for XIOS+AGRIF 
     387                      CALL iom_context_finalize(      rxios_context          ) 
    387388         IF( ln_crs ) CALL iom_context_finalize( trim(cxios_context)//"_crs" ) !  
    388389      ENDIF 
Note: See TracChangeset for help on using the changeset viewer.