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

Changeset 14559


Ignore:
Timestamp:
2021-03-01T14:37:10+01:00 (3 years ago)
Author:
andmirek
Message:

Ticket #2631: first implementation (with debug prints)

Location:
NEMO/branches/2021/dev_14544_xios_ancil/src/OCE
Files:
6 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2021/dev_14544_xios_ancil/src/OCE/DOM/domain.F90

    r14433 r14559  
    442442      ! 
    443443      IF( TRIM(Agrif_CFixed()) == '0' ) THEN 
    444          lrxios = ln_xios_read .AND. ln_rstart 
     444         lrxios = ln_xios_read                 !.AND. ln_rstart use XIOS to read information about domain 
    445445         IF( nn_wxios > 0 )   lwxios = .TRUE.           !* set output file type for XIOS based on NEMO namelist 
    446446         nxioso = nn_wxios 
  • NEMO/branches/2021/dev_14544_xios_ancil/src/OCE/DOM/domhgr.F90

    r13286 r14559  
    176176      REAL(wp), DIMENSION(:,:), INTENT(out) ::   pe1e2u, pe1e2v              ! u- & v-surfaces (if found in file) 
    177177      ! 
    178       INTEGER  ::   inum                  ! logical unit 
    179178      !!---------------------------------------------------------------------- 
    180179      ! 
     
    185184      ENDIF 
    186185      ! 
    187       CALL iom_open( cn_domcfg, inum ) 
    188       ! 
    189       CALL iom_get( inum, jpdom_global, 'glamt', plamt, cd_type = 'T', psgn = 1._wp ) 
    190       CALL iom_get( inum, jpdom_global, 'glamu', plamu, cd_type = 'U', psgn = 1._wp ) 
    191       CALL iom_get( inum, jpdom_global, 'glamv', plamv, cd_type = 'V', psgn = 1._wp ) 
    192       CALL iom_get( inum, jpdom_global, 'glamf', plamf, cd_type = 'F', psgn = 1._wp ) 
    193       ! 
    194       CALL iom_get( inum, jpdom_global, 'gphit', pphit, cd_type = 'T', psgn = 1._wp ) 
    195       CALL iom_get( inum, jpdom_global, 'gphiu', pphiu, cd_type = 'U', psgn = 1._wp ) 
    196       CALL iom_get( inum, jpdom_global, 'gphiv', pphiv, cd_type = 'V', psgn = 1._wp ) 
    197       CALL iom_get( inum, jpdom_global, 'gphif', pphif, cd_type = 'F', psgn = 1._wp ) 
    198       ! 
    199       CALL iom_get( inum, jpdom_global, 'e1t'  , pe1t , cd_type = 'T', psgn = 1._wp, kfill = jpfillcopy ) 
    200       CALL iom_get( inum, jpdom_global, 'e1u'  , pe1u , cd_type = 'U', psgn = 1._wp, kfill = jpfillcopy ) 
    201       CALL iom_get( inum, jpdom_global, 'e1v'  , pe1v , cd_type = 'V', psgn = 1._wp, kfill = jpfillcopy ) 
    202       CALL iom_get( inum, jpdom_global, 'e1f'  , pe1f , cd_type = 'F', psgn = 1._wp, kfill = jpfillcopy ) 
    203       ! 
    204       CALL iom_get( inum, jpdom_global, 'e2t'  , pe2t , cd_type = 'T', psgn = 1._wp, kfill = jpfillcopy ) 
    205       CALL iom_get( inum, jpdom_global, 'e2u'  , pe2u , cd_type = 'U', psgn = 1._wp, kfill = jpfillcopy ) 
    206       CALL iom_get( inum, jpdom_global, 'e2v'  , pe2v , cd_type = 'V', psgn = 1._wp, kfill = jpfillcopy ) 
    207       CALL iom_get( inum, jpdom_global, 'e2f'  , pe2f , cd_type = 'F', psgn = 1._wp, kfill = jpfillcopy ) 
    208       ! 
    209       IF(  iom_varid( inum, 'ff_f', ldstop = .FALSE. ) > 0  .AND.  & 
    210          & iom_varid( inum, 'ff_t', ldstop = .FALSE. ) > 0    ) THEN 
     186      CALL iom_open( cn_domcfg, numdom ) 
     187      IF(ln_xios_read) THEN  
     188         CALL iom_dom_context(cn_domcfg, numdom)  
     189         CALL iom_swap( cr_dom_cxt )  
     190      ENDIF  
     191      ! 
     192      CALL iom_get( numdom, jpdom_global, 'glamt', plamt, cd_type = 'T', psgn = 1._wp ) 
     193      CALL iom_get( numdom, jpdom_global, 'glamu', plamu, cd_type = 'U', psgn = 1._wp ) 
     194      CALL iom_get( numdom, jpdom_global, 'glamv', plamv, cd_type = 'V', psgn = 1._wp ) 
     195      CALL iom_get( numdom, jpdom_global, 'glamf', plamf, cd_type = 'F', psgn = 1._wp  ) 
     196      ! 
     197      CALL iom_get( numdom, jpdom_global, 'gphit', pphit, cd_type = 'T', psgn = 1._wp ) 
     198      CALL iom_get( numdom, jpdom_global, 'gphiu', pphiu, cd_type = 'U', psgn = 1._wp ) 
     199      CALL iom_get( numdom, jpdom_global, 'gphiv', pphiv, cd_type = 'V', psgn = 1._wp ) 
     200      CALL iom_get( numdom, jpdom_global, 'gphif', pphif, cd_type = 'F', psgn = 1._wp ) 
     201      ! 
     202      CALL iom_get( numdom, jpdom_global, 'e1t'  , pe1t , cd_type = 'T', psgn = 1._wp, kfill = jpfillcopy ) 
     203      CALL iom_get( numdom, jpdom_global, 'e1u'  , pe1u , cd_type = 'U', psgn = 1._wp, kfill = jpfillcopy ) 
     204      CALL iom_get( numdom, jpdom_global, 'e1v'  , pe1v , cd_type = 'V', psgn = 1._wp, kfill = jpfillcopy ) 
     205      CALL iom_get( numdom, jpdom_global, 'e1f'  , pe1f , cd_type = 'F', psgn = 1._wp, kfill = jpfillcopy ) 
     206      ! 
     207      CALL iom_get( numdom, jpdom_global, 'e2t'  , pe2t , cd_type = 'T', psgn = 1._wp, kfill = jpfillcopy ) 
     208      CALL iom_get( numdom, jpdom_global, 'e2u'  , pe2u , cd_type = 'U', psgn = 1._wp, kfill = jpfillcopy ) 
     209      CALL iom_get( numdom, jpdom_global, 'e2v'  , pe2v , cd_type = 'V', psgn = 1._wp, kfill = jpfillcopy ) 
     210      CALL iom_get( numdom, jpdom_global, 'e2f'  , pe2f , cd_type = 'F', psgn = 1._wp, kfill = jpfillcopy ) 
     211      ! 
     212      IF(  iom_varid( numdom, 'ff_f', ldstop = .FALSE. ) > 0  .AND.  & 
     213         & iom_varid( numdom, 'ff_t', ldstop = .FALSE. ) > 0    ) THEN 
    211214         IF(lwp) WRITE(numout,*) '           Coriolis factor at f- and t-points read in ', TRIM( cn_domcfg ), ' file' 
    212          CALL iom_get( inum, jpdom_global, 'ff_f', pff_f, cd_type = 'F', psgn = 1._wp ) 
    213          CALL iom_get( inum, jpdom_global, 'ff_t', pff_t, cd_type = 'T', psgn = 1._wp ) 
     215         CALL iom_get( numdom, jpdom_global, 'ff_f', pff_f, cd_type = 'F', psgn = 1._wp ) 
     216         CALL iom_get( numdom, jpdom_global, 'ff_t', pff_t, cd_type = 'T', psgn = 1._wp ) 
    214217         kff = 1 
    215218      ELSE 
     
    217220      ENDIF 
    218221      ! 
    219       IF( iom_varid( inum, 'e1e2u', ldstop = .FALSE. ) > 0 ) THEN 
     222      IF( iom_varid( numdom, 'e1e2u', ldstop = .FALSE. ) > 0 ) THEN 
    220223         IF(lwp) WRITE(numout,*) '           e1e2u & e1e2v read in ', TRIM( cn_domcfg ), ' file' 
    221          CALL iom_get( inum, jpdom_global, 'e1e2u', pe1e2u, cd_type = 'U', psgn = 1._wp, kfill = jpfillcopy ) 
    222          CALL iom_get( inum, jpdom_global, 'e1e2v', pe1e2v, cd_type = 'V', psgn = 1._wp, kfill = jpfillcopy ) 
     224         CALL iom_get( numdom, jpdom_global, 'e1e2u', pe1e2u, cd_type = 'U', psgn = 1._wp, kfill = jpfillcopy ) 
     225         CALL iom_get( numdom, jpdom_global, 'e1e2v', pe1e2v, cd_type = 'V', psgn = 1._wp, kfill = jpfillcopy ) 
    223226         ke1e2u_v = 1 
    224227      ELSE 
     
    226229      ENDIF 
    227230      ! 
    228       CALL iom_close( inum ) 
     231!     CALL iom_close( numdom ) 
    229232      ! 
    230233   END SUBROUTINE hgr_read 
  • NEMO/branches/2021/dev_14544_xios_ancil/src/OCE/DOM/domzgr.F90

    r14433 r14559  
    225225      ! 
    226226      INTEGER  ::   jk     ! dummy loop index 
    227       INTEGER  ::   inum, iatt 
     227      INTEGER  ::   iatt 
    228228      REAL(WP) ::   z_zco, z_zps, z_sco, z_cav 
    229229      REAL(wp), DIMENSION(jpi,jpj) ::   z2d   ! 2D workspace 
     
    237237      ENDIF 
    238238      ! 
    239       CALL iom_open( cn_domcfg, inum ) 
     239      CALL iom_open( cn_domcfg, numdom ) 
     240      IF(lrxios) CALL iom_swap( cr_dom_cxt ) 
    240241      ! 
    241242      !                          !* type of vertical coordinate 
    242       CALL iom_getatt( inum, 'VertCoord', catt )   ! returns 'UNKNOWN' if not found 
     243      CALL iom_getatt( numdom, 'VertCoord', catt )   ! returns 'UNKNOWN' if not found 
    243244      ld_zco = catt == 'zco'          ! default = .false. 
    244245      ld_zps = catt == 'zps'          ! default = .false. 
    245246      ld_sco = catt == 'sco'          ! default = .false. 
    246247      !                          !* ocean cavities under iceshelves 
    247       CALL iom_getatt( inum,    'IsfCav', iatt )   ! returns -999 if not found 
     248      CALL iom_getatt( numdom,    'IsfCav', iatt )   ! returns -999 if not found 
    248249      ld_isfcav = iatt == 1           ! default = .false. 
    249250      ! 
    250251      ! ------- keep compatibility with OLD VERSION... start ------- 
    251252      IF( catt == 'UNKNOWN' ) THEN 
    252          CALL iom_get( inum,    'ln_zco', z_zco )   ;   ld_zco = z_zco /= 0._wp 
    253          CALL iom_get( inum,    'ln_zps', z_zps )   ;   ld_zps = z_zps /= 0._wp 
    254          CALL iom_get( inum,    'ln_sco', z_sco )   ;   ld_sco = z_sco /= 0._wp 
     253         CALL iom_get( numdom,    'ln_zco', z_zco )   ;   ld_zco = z_zco /= 0._wp 
     254         CALL iom_get( numdom,    'ln_zps', z_zps )   ;   ld_zps = z_zps /= 0._wp 
     255         CALL iom_get( numdom,    'ln_sco', z_sco )   ;   ld_sco = z_sco /= 0._wp 
    255256      ENDIF 
    256257      IF( iatt == -999 ) THEN 
    257          CALL iom_get( inum, 'ln_isfcav', z_cav )   ;   ld_isfcav = z_cav /= 0._wp 
     258         CALL iom_get( numdom, 'ln_isfcav', z_cav )   ;   ld_isfcav = z_cav /= 0._wp 
    258259      ENDIF 
    259260      ! ------- keep compatibility with OLD VERSION... end ------- 
    260261      ! 
    261262      !                          !* vertical scale factors 
    262       CALL iom_get( inum, jpdom_unknown, 'e3t_1d'  , pe3t_1d  )                     ! 1D reference coordinate 
    263       CALL iom_get( inum, jpdom_unknown, 'e3w_1d'  , pe3w_1d  ) 
    264       ! 
    265       CALL iom_get( inum, jpdom_global, 'e3t_0'  , pe3t , cd_type = 'T', psgn = 1._wp, kfill = jpfillcopy )    ! 3D coordinate 
    266       CALL iom_get( inum, jpdom_global, 'e3u_0'  , pe3u , cd_type = 'U', psgn = 1._wp, kfill = jpfillcopy ) 
    267       CALL iom_get( inum, jpdom_global, 'e3v_0'  , pe3v , cd_type = 'V', psgn = 1._wp, kfill = jpfillcopy ) 
    268       CALL iom_get( inum, jpdom_global, 'e3f_0'  , pe3f , cd_type = 'F', psgn = 1._wp, kfill = jpfillcopy ) 
    269       CALL iom_get( inum, jpdom_global, 'e3w_0'  , pe3w , cd_type = 'W', psgn = 1._wp, kfill = jpfillcopy ) 
    270       CALL iom_get( inum, jpdom_global, 'e3uw_0' , pe3uw, cd_type = 'U', psgn = 1._wp, kfill = jpfillcopy ) 
    271       CALL iom_get( inum, jpdom_global, 'e3vw_0' , pe3vw, cd_type = 'V', psgn = 1._wp, kfill = jpfillcopy ) 
     263      CALL iom_get( numdom, jpdom_unknown, 'e3t_1d'  , pe3t_1d  )                     ! 1D reference coordinate 
     264      CALL iom_get( numdom, jpdom_unknown, 'e3w_1d'  , pe3w_1d  ) 
     265      ! 
     266      CALL iom_get( numdom, jpdom_global, 'e3t_0'  , pe3t , cd_type = 'T', psgn = 1._wp, kfill = jpfillcopy )    ! 3D coordinate 
     267      CALL iom_get( numdom, jpdom_global, 'e3u_0'  , pe3u , cd_type = 'U', psgn = 1._wp, kfill = jpfillcopy ) 
     268      CALL iom_get( numdom, jpdom_global, 'e3v_0'  , pe3v , cd_type = 'V', psgn = 1._wp, kfill = jpfillcopy ) 
     269      CALL iom_get( numdom, jpdom_global, 'e3f_0'  , pe3f , cd_type = 'F', psgn = 1._wp, kfill = jpfillcopy ) 
     270      CALL iom_get( numdom, jpdom_global, 'e3w_0'  , pe3w , cd_type = 'W', psgn = 1._wp, kfill = jpfillcopy ) 
     271      CALL iom_get( numdom, jpdom_global, 'e3uw_0' , pe3uw, cd_type = 'U', psgn = 1._wp, kfill = jpfillcopy ) 
     272      CALL iom_get( numdom, jpdom_global, 'e3vw_0' , pe3vw, cd_type = 'V', psgn = 1._wp, kfill = jpfillcopy ) 
    272273      ! 
    273274      !                          !* depths 
    274275      !                                   !- old depth definition (obsolescent feature) 
    275       IF(  iom_varid( inum, 'gdept_1d', ldstop = .FALSE. ) > 0  .AND.  & 
    276          & iom_varid( inum, 'gdepw_1d', ldstop = .FALSE. ) > 0  .AND.  & 
    277          & iom_varid( inum, 'gdept_0' , ldstop = .FALSE. ) > 0  .AND.  & 
    278          & iom_varid( inum, 'gdepw_0' , ldstop = .FALSE. ) > 0    ) THEN 
     276      IF(  iom_varid( numdom, 'gdept_1d', ldstop = .FALSE. ) > 0  .AND.  & 
     277         & iom_varid( numdom, 'gdepw_1d', ldstop = .FALSE. ) > 0  .AND.  & 
     278         & iom_varid( numdom, 'gdept_0' , ldstop = .FALSE. ) > 0  .AND.  & 
     279         & iom_varid( numdom, 'gdepw_0' , ldstop = .FALSE. ) > 0    ) THEN 
    279280         CALL ctl_warn( 'zgr_read : old definition of depths and scale factors used ', &  
    280281            &           '           depths at t- and w-points read in the domain configuration file') 
    281          CALL iom_get( inum, jpdom_unknown, 'gdept_1d', pdept_1d )    
    282          CALL iom_get( inum, jpdom_unknown, 'gdepw_1d', pdepw_1d ) 
    283          CALL iom_get( inum, jpdom_global , 'gdept_0' , pdept, kfill = jpfillcopy ) 
    284          CALL iom_get( inum, jpdom_global , 'gdepw_0' , pdepw, kfill = jpfillcopy ) 
     282         CALL iom_get( numdom, jpdom_unknown, 'gdept_1d', pdept_1d )    
     283         CALL iom_get( numdom, jpdom_unknown, 'gdepw_1d', pdepw_1d ) 
     284         CALL iom_get( numdom, jpdom_global , 'gdept_0' , pdept, kfill = jpfillcopy ) 
     285         CALL iom_get( numdom, jpdom_global , 'gdepw_0' , pdepw, kfill = jpfillcopy ) 
    285286         ! 
    286287      ELSE                                !- depths computed from e3. scale factors 
     
    296297      ! 
    297298      !                          !* ocean top and bottom level 
    298       CALL iom_get( inum, jpdom_global, 'top_level'    , z2d   )   ! 1st wet T-points (ISF) 
     299      CALL iom_get( numdom, jpdom_global, 'top_level'    , z2d   )   ! 1st wet T-points (ISF) 
    299300      k_top(:,:) = NINT( z2d(:,:) ) 
    300       CALL iom_get( inum, jpdom_global, 'bottom_level' , z2d   )   ! last wet T-points 
     301      CALL iom_get( numdom, jpdom_global, 'bottom_level' , z2d   )   ! last wet T-points 
    301302      k_bot(:,:) = NINT( z2d(:,:) ) 
    302303      ! 
    303304      ! reference depth for negative bathy (wetting and drying only) 
    304       IF( ll_wd )  CALL iom_get( inum,  'rn_wd_ref_depth' , ssh_ref   ) 
    305       ! 
    306       CALL iom_close( inum ) 
     305      IF( ll_wd )  CALL iom_get( numdom,  'rn_wd_ref_depth' , ssh_ref   ) 
     306      ! 
     307      IF(ln_xios_read) THEN  
     308         CALL iom_context_finalize( cr_dom_cxt )  
     309      ENDIF  
     310      CALL iom_close( numdom ) 
    307311      ! 
    308312   END SUBROUTINE zgr_read 
  • NEMO/branches/2021/dev_14544_xios_ancil/src/OCE/IOM/in_out_manager.F90

    r14072 r14559  
    9898   INTEGER ::   numrsr = 0            !: logical unit for sed restart (read) 
    9999   INTEGER ::   numrsw = 0            !: logical unit for sed restart (write) 
     100   INTEGER ::   numdom = 0            !: logical unit for configuration data (read)  
    100101 
    101102   INTEGER ::   nrst_lst              !: number of restart to output next 
     
    180181   CHARACTER(LEN=lc) ::   cw_sedrst_cxt     !: context name used in xios to write SEDIMENT restart file 
    181182 
     183   CHARACTER(LEN=lc) ::   cr_dom_cxt = "dom_context"     !: context name used in xios to read data from dom routines 
     184 
    182185 
    183186 
  • NEMO/branches/2021/dev_14544_xios_ancil/src/OCE/IOM/iom.F90

    r14239 r14559  
    6161   PUBLIC iom_use, iom_context_finalize, iom_update_file_name, iom_miss_val 
    6262   PUBLIC iom_xios_setid 
     63   PUBLIC iom_dom_context 
    6364 
    6465   PRIVATE iom_rp0d_sp, iom_rp1d_sp, iom_rp2d_sp, iom_rp3d_sp 
     
    344345 
    345346#if defined key_xios 
    346       INTEGER                                    :: ndims, nvars, natts, unlimitedDimId, dimlen, xtype,mdims 
     347      INTEGER                                    :: ndims, nvars, mdims 
    347348      TYPE(xios_field)                           :: field_hdl 
    348349      TYPE(xios_file)                            :: file_hdl 
     
    350351      INTEGER                                    :: dimids(4), jv,i, idim 
    351352      CHARACTER(LEN=256)                         :: clinfo               ! info character 
    352       INTEGER, ALLOCATABLE                       :: indimlens(:) 
    353       CHARACTER(LEN=nf90_max_name), ALLOCATABLE  :: indimnames(:) 
    354       CHARACTER(LEN=nf90_max_name)               :: dimname, varname 
     353      INTEGER                                    :: indimlens(4) 
     354      CHARACTER(LEN=lc)                          :: dimname, varname 
    355355      INTEGER                                    :: iln 
     356      INTEGER                                    :: ivid 
    356357      CHARACTER(LEN=lc)                          :: fname 
     358      LOGICAL                                    :: lud 
    357359      LOGICAL                                    :: lmeta 
    358360!metadata in restart file for restart read with XIOS 
     
    371373      meta(9) = "y" 
    372374      meta(10) = "numcat" 
     375!     meta(11) = "t" 
    373376 
    374377      clinfo = '          iom_set_vars_active, file: '//TRIM(iom_file(idnum)%name) 
     
    384387!set name of the restart file and enable available fields 
    385388      CALL xios_get_handle("file_definition", filegroup_hdl ) 
    386       CALL xios_add_child(filegroup_hdl, file_hdl, 'rrestart') 
    387       CALL xios_set_file_attr( "rrestart", name=fname, type="one_file",      & 
     389      CALL xios_add_child(filegroup_hdl, file_hdl, 'finput') 
     390      CALL xios_set_file_attr( "finput", name=fname, type="one_file",      & 
    388391           par_access="collective", enabled=.TRUE., mode="read",              & 
    389392                                                    output_freq=xios_timestep ) 
    390393 
    391       CALL iom_nf90_check( nf90_inquire(iom_file(idnum)%nfid, ndims, nvars, natts ), clinfo ) 
    392       ALLOCATE(indimlens(ndims), indimnames(ndims)) 
    393       CALL iom_nf90_check( nf90_inquire(iom_file(idnum)%nfid, unlimitedDimId = unlimitedDimId ), clinfo ) 
    394  
    395       DO idim = 1, ndims 
    396          CALL iom_nf90_check( nf90_inquire_dimension(iom_file(idnum)%nfid, idim, dimname, dimlen ), clinfo ) 
    397          indimlens(idim) = dimlen 
    398          indimnames(idim) = dimname 
    399       ENDDO 
    400  
    401       DO jv =1, nvars 
     394      nvars = iom_nf90_nvars( idnum ) 
     395      IF(lwp) write(numout, *) 'File ', TRIM(fname), ' NVARS = ',nvars 
     396      DO jv = 1, nvars 
     397         varname = iom_nf90_vname(idnum, jv) 
     398 
    402399         lmeta = .FALSE. 
    403          CALL iom_nf90_check( nf90_inquire_variable(iom_file(idnum)%nfid, jv, varname, xtype, ndims, dimids, natts ), clinfo ) 
    404400         DO i = 1, NMETA 
    405401           IF(varname == meta(i)) THEN 
    406              lmeta = .TRUE. 
     402               lmeta = .TRUE.  
     403               CYCLE 
    407404           ENDIF 
    408405         ENDDO 
    409          IF(.NOT.lmeta) THEN 
    410             CALL xios_add_child(file_hdl, field_hdl, varname) 
    411             mdims = ndims 
    412  
    413             IF(ANY(dimids(1:ndims) == unlimitedDimId)) THEN 
    414                mdims = mdims - 1 
    415             ENDIF 
    416  
    417             IF(mdims == 3) THEN 
    418                CALL xios_set_attr (field_hdl, enabled = .TRUE., name = varname,   & 
    419                                    domain_ref="grid_N",                           & 
    420                                    axis_ref=iom_axis(indimlens(dimids(mdims))),   & 
    421                                    prec = 8, operation = "instant"                ) 
    422             ELSEIF(mdims == 2) THEN 
    423                CALL xios_set_attr (field_hdl, enabled = .TRUE., name = varname,  & 
    424                                    domain_ref="grid_N", prec = 8,                & 
    425                                    operation = "instant"                         ) 
    426             ELSEIF(mdims == 1) THEN 
    427                CALL xios_set_attr (field_hdl, enabled = .TRUE., name = varname, & 
    428                                    axis_ref=iom_axis(indimlens(dimids(mdims))), & 
    429                                    prec = 8, operation = "instant"              ) 
    430             ELSEIF(mdims == 0) THEN 
    431                CALL xios_set_attr (field_hdl, enabled = .TRUE., name = varname, & 
    432                                    scalar_ref = "grid_scalar", prec = 8,        & 
    433                                    operation = "instant"                        ) 
    434             ELSE 
    435                WRITE(ctmp1,*) 'iom_set_vars_active: variable ', TRIM(varname) ,' incorrect number of dimensions' 
    436                CALL ctl_stop( 'iom_set_vars_active:', ctmp1 ) 
    437             ENDIF 
    438          ENDIF 
     406 
     407         IF(lmeta) CYCLE 
     408 
     409         ivid = iom_varid ( idnum, varname, kdimsz = indimlens, kndims = mdims, lduld = lud, ldstop = .TRUE.) 
     410         IF(lud) mdims = mdims - 1 
     411 
     412         CALL xios_add_child(file_hdl, field_hdl, varname) 
     413 
     414         IF(mdims == 3) THEN 
     415           CALL xios_set_attr (field_hdl, enabled = .TRUE., name = varname,   & 
     416                               domain_ref="grid_N",                           & 
     417                               axis_ref=iom_axis(indimlens(mdims)),   & 
     418                               prec = 8, operation = "instant"                ) 
     419         ELSEIF(mdims == 2) THEN 
     420           CALL xios_set_attr (field_hdl, enabled = .TRUE., name = varname,  & 
     421                               domain_ref="grid_N", prec = 8,                & 
     422                               operation = "instant"                         ) 
     423         ELSEIF(mdims == 1) THEN 
     424           CALL xios_set_attr (field_hdl, enabled = .TRUE., name = varname, & 
     425                               axis_ref=iom_axis(indimlens(mdims)), & 
     426                               prec = 8, operation = "instant"              ) 
     427         ELSEIF(mdims == 0) THEN 
     428           CALL xios_set_attr (field_hdl, enabled = .TRUE., name = varname, & 
     429                               scalar_ref = "grid_scalar", prec = 8,        & 
     430                               operation = "instant"                        ) 
     431         ELSE 
     432           WRITE(ctmp1,*) 'iom_set_vars_active: variable ', TRIM(varname) ,' incorrect number of dimensions' 
     433           CALL ctl_stop( 'iom_set_vars_active:', ctmp1 ) 
     434         ENDIF 
     435         IF(lwp) write(numout, *) 'Variable ', TRIM(varname) ,' active in XIOS context' 
    439436      ENDDO 
    440       DEALLOCATE(indimlens, indimnames) 
    441437#endif 
    442438   END SUBROUTINE iom_set_vars_active 
     
    632628 
    633629      cdcont = "NONE" 
    634  
     630!read restart 
    635631      IF(lrxios) THEN 
    636632         IF(kdid == numror) THEN 
     
    642638         ELSEIF(kdid == numrsr) THEN 
    643639            cdcont = cr_sedrst_cxt 
    644          ENDIF 
    645       ENDIF 
    646  
     640         ELSEIF(kdid == numdom) THEN 
     641            cdcont = cr_dom_cxt 
     642         ENDIF 
     643      ENDIF 
     644!write restart 
    647645      IF(lwxios) THEN 
    648646         IF(kdid == numrow) THEN 
     
    654652         ELSEIF(kdid == numrsw) THEN 
    655653            cdcont = cw_sedrst_cxt 
     654         ENDIF 
     655      ENDIF 
     656!read other than restart files 
     657      IF(ln_xios_read) THEN 
     658         IF(kdid == numdom) THEN 
     659            cdcont = cr_dom_cxt 
    656660         ENDIF 
    657661      ENDIF 
     
    956960      ELSE 
    957961#if defined key_xios 
    958          IF(lwp) WRITE(numout,*) 'XIOS RST READ (0D): ', trim(cdvar) 
     962         IF(lwp) WRITE(numout,*) 'XIOS READ (0D): ', trim(cdvar) 
    959963         CALL iom_swap(context) 
    960964         CALL xios_recv_field( trim(cdvar), pvar) 
    961          CALL iom_swap(cxios_context) 
     965         IF(context /= cr_dom_cxt) CALL iom_swap(cxios_context) 
    962966#else 
    963967         WRITE(ctmp1,*) 'Can not use XIOS in iom_g0d, file: '//trim(clname)//', var:'//trim(cdvar) 
     
    10041008      ELSE 
    10051009#if defined key_xios 
    1006          IF(lwp) WRITE(numout,*) 'XIOS RST READ (0D): ', trim(cdvar) 
     1010         IF(lwp) WRITE(numout,*) 'XIOS READ (0D): ', trim(cdvar) 
    10071011         CALL iom_swap(context) 
    10081012         CALL xios_recv_field( trim(cdvar), pvar) 
    1009          CALL iom_swap(cxios_context) 
     1013         IF(context /= cr_dom_cxt) CALL iom_swap(cxios_context) 
    10101014#else 
    10111015         WRITE(ctmp1,*) 'Can not use XIOS in iom_g0d, file: '//trim(clname)//', var:'//trim(cdvar) 
     
    13771381 
    13781382         IF( PRESENT(pv_r3d) ) THEN 
    1379             IF(lwp) WRITE(numout,*) 'XIOS RST READ (3D): ',TRIM(cdvar) 
     1383            IF(lwp) WRITE(numout,*) 'XIOS READ (3D): ',TRIM(cdvar) 
    13801384            CALL xios_recv_field( trim(cdvar), pv_r3d(:, :, :)) 
    13811385            IF(idom /= jpdom_unknown .AND. cl_type /= 'Z' ) THEN 
     
    13831387            ENDIF 
    13841388         ELSEIF( PRESENT(pv_r2d) ) THEN 
    1385             IF(lwp) WRITE(numout,*) 'XIOS RST READ (2D): ', TRIM(cdvar) 
     1389            IF(lwp) WRITE(numout,*) 'XIOS READ (2D): ', TRIM(cdvar) 
    13861390            CALL xios_recv_field( trim(cdvar), pv_r2d(:, :)) 
    13871391            IF(idom /= jpdom_unknown .AND. cl_type /= 'Z' ) THEN 
     
    13891393            ENDIF 
    13901394         ELSEIF( PRESENT(pv_r1d) ) THEN 
    1391             IF(lwp) WRITE(numout,*) 'XIOS RST READ (1D): ', TRIM(cdvar) 
     1395            IF(lwp) WRITE(numout,*) 'XIOS READ (1D): ', TRIM(cdvar) 
    13921396            CALL xios_recv_field( trim(cdvar), pv_r1d) 
    13931397         ENDIF 
    1394          CALL iom_swap(cxios_context) 
     1398         IF(context /= cr_dom_cxt) CALL iom_swap(cxios_context) 
    13951399#else 
    13961400         istop = istop + 1 
     
    14311435#endif 
    14321436   END SUBROUTINE iom_get_var 
     1437 
     1438   SUBROUTINE iom_dom_context(fdname, numr)   
     1439      !!----------------------------------------------------------------------- 
     1440      !!                  ***  SUBROUTINE  iom_dom_context  *** 
     1441      !! 
     1442      !! ** Purpose : initialize context for reading domain information 
     1443      !!----------------------------------------------------------------------- 
     1444      CHARACTER(len=*), INTENT(IN)         :: fdname 
     1445      INTEGER,          INTENT(IN)         :: numr 
     1446      !local variables 
     1447      CHARACTER(len=lc)                    :: cxname 
     1448      CHARACTER(len=lc)                    :: cfile 
     1449      TYPE(xios_domaingroup)               :: domaingroup_hdl  
     1450      TYPE(xios_domain)                    :: domain_hdl  
     1451      TYPE(xios_axisgroup)                 :: axisgroup_hdl  
     1452      TYPE(xios_axis)                      :: axis_hdl  
     1453      TYPE(xios_scalar)                    :: scalar_hdl  
     1454      TYPE(xios_scalargroup)               :: scalargroup_hdl  
     1455      TYPE(xios_field) :: field_hdl 
     1456      TYPE(xios_file) :: file_hdl 
     1457      TYPE(xios_filegroup) :: filegroup_hdl 
     1458      TYPE(xios_duration) :: dtime    = xios_duration(0, 0, 0, 0, 0, 0) 
     1459      !!----------------------------------------------------------------------- 
     1460 
     1461#if defined key_xios 
     1462      cxname = cr_dom_cxt 
     1463      IF( TRIM(Agrif_CFixed()) .NE. '0' ) THEN 
     1464         CALL xios_context_initialize(TRIM(Agrif_CFixed())//"_"//TRIM(cxname), mpi_comm_oce) 
     1465      ELSE 
     1466         CALL xios_context_initialize(TRIM(cxname), mpi_comm_oce) 
     1467      ENDIF 
     1468      CALL iom_swap( cxname ) 
     1469!calendar must be defined always 
     1470      CALL xios_define_calendar( TYPE = "NoLeap"   , time_origin = xios_date(1,1,1,00,00,00), & 
     1471          &                                    start_date = xios_date(1,1,1,0,0,0) ) 
     1472      CALL xios_get_handle("domain_definition",domaingroup_hdl)  
     1473      CALL xios_add_child(domaingroup_hdl, domain_hdl, "grid_N")  
     1474      ! 
     1475      CALL iom_set_domain_attr("grid_N", ni_glo=Ni0glo,nj_glo=Nj0glo,ibegin=mig0(Nis0)-1,jbegin=mjg0(Njs0)-1,ni=Ni_0,nj=Nj_0) 
     1476      CALL iom_set_domain_attr("grid_N", data_dim=2, data_ibegin = -nn_hls, data_ni=jpi, data_jbegin = -nn_hls, data_nj=jpj) 
     1477 
     1478      CALL xios_get_handle("axis_definition",axisgroup_hdl)  
     1479      CALL xios_add_child(axisgroup_hdl, axis_hdl, "nav_lev")  
     1480!AGRIF fails to compile when unit= is in call to xios_set_axis_attr 
     1481!     CALL xios_set_axis_attr( "nav_lev", long_name="Vertical levels in meters", positive="down") 
     1482      CALL xios_set_axis_attr ("nav_lev", n_glo=jpk ) 
     1483 
     1484      CALL xios_get_handle("scalar_definition", scalargroup_hdl)  
     1485      CALL xios_add_child(scalargroup_hdl, scalar_hdl, "grid_scalar")  
     1486 
     1487      IF( TRIM(Agrif_CFixed()) == '0' ) THEN 
     1488         cfile = TRIM(fdname) 
     1489      ELSE 
     1490         cfile = TRIM(Agrif_CFixed())//"_"//TRIM(fdname) 
     1491      ENDIF 
     1492      CALL iom_set_vars_active(numr) 
     1493      ! set time step length 
     1494      dtime%second = rn_Dt 
     1495      CALL xios_set_timestep( dtime ) 
     1496      IF(lwp) write(numout, *) 'Before CLOSE dom_context definition' 
     1497      IF(lwp) CALL flush(numout) 
     1498      CALL iom_init_closedef 
     1499      IF(lwp) write(numout, *) 'CLOSE dom_context definition' 
     1500      IF(lwp) CALL flush(numout) 
     1501#endif 
     1502   END SUBROUTINE iom_dom_context 
    14331503 
    14341504 
     
    22812351      CALL iom_set_domain_attr("grid_"//cdgrd, ni_glo=Ni0glo,nj_glo=Nj0glo,ibegin=mig0(Nis0)-1,jbegin=mjg0(Njs0)-1,ni=Ni_0,nj=Nj_0) 
    22822352      CALL iom_set_domain_attr("grid_"//cdgrd, data_dim=2, data_ibegin = -nn_hls, data_ni=jpi, data_jbegin = -nn_hls, data_nj=jpj) 
    2283 !don't define lon and lat for restart reading context. 
     2353!don't define lon and lat for xios reading context. 
    22842354      IF ( .NOT.ldrxios ) & 
    22852355         CALL iom_set_domain_attr("grid_"//cdgrd, lonvalue = real(RESHAPE(plon(Nis0:Nie0, Njs0:Nje0),(/ Ni_0*Nj_0 /)),dp),   & 
  • NEMO/branches/2021/dev_14544_xios_ancil/src/OCE/IOM/iom_nf90.F90

    r14433 r14559  
    3131   PUBLIC iom_nf90_open  , iom_nf90_close, iom_nf90_varid, iom_nf90_get, iom_nf90_rstput 
    3232   PUBLIC iom_nf90_chkatt, iom_nf90_getatt, iom_nf90_putatt 
     33   PUBLIC iom_nf90_nvars , iom_nf90_vname 
    3334   PUBLIC iom_nf90_check 
    3435 
     
    273274   END FUNCTION iom_nf90_varid 
    274275 
     276   FUNCTION iom_nf90_nvars( kiomid ) 
     277      !!----------------------------------------------------------------------- 
     278      !!                  ***  ROUTINE  iom_nf90_nvars  *** 
     279      !! 
     280      !! ** Purpose : get number of variables in netcdf file 
     281      !!----------------------------------------------------------------------- 
     282      INTEGER ,               INTENT(in   )            ::   kiomid           ! Identifier of the file 
     283      INTEGER                                          ::   iom_nf90_nvars   ! number of variables 
     284      ! 
     285      CHARACTER(LEN=100)      ::   clinfo   ! info character 
     286      !--------------------------------------------------------------------- 
     287      clinfo = 'iom_nf90_nvars , file: '//TRIM(iom_file(kiomid)%name) 
     288      CALL iom_nf90_check( nf90_inquire(iom_file(kiomid)%nfid, nVariables = iom_nf90_nvars ), clinfo ) 
     289   END FUNCTION iom_nf90_nvars 
     290 
     291   FUNCTION iom_nf90_vname( kiomid, ivar ) 
     292      !!----------------------------------------------------------------------- 
     293      !!                  ***  ROUTINE  iom_nf90_nvars  *** 
     294      !! 
     295      !! ** Purpose : get number of variables in netcdf file 
     296      !!----------------------------------------------------------------------- 
     297      INTEGER ,               INTENT(in   )            ::   kiomid           ! Identifier of the file 
     298      INTEGER ,               INTENT(in   )            ::   ivar             ! variable id 
     299      CHARACTER(LEN=lc)                                ::   iom_nf90_vname   ! iom variable Id 
     300      INTEGER                                          ::   nvars, natts     ! needed for call to netcdf function but not used 
     301      ! 
     302      CHARACTER(LEN=100)      ::   clinfo   ! info character 
     303      !--------------------------------------------------------------------- 
     304      clinfo = 'iom_nf90_vname , file: '//TRIM(iom_file(kiomid)%name) 
     305      CALL iom_nf90_check( nf90_inquire_variable(iom_file(kiomid)%nfid, ivar, name = iom_nf90_vname), clinfo ) 
     306   END FUNCTION iom_nf90_vname 
     307 
     308 
    275309   !!---------------------------------------------------------------------- 
    276310   !!                   INTERFACE iom_nf90_get 
Note: See TracChangeset for help on using the changeset viewer.