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

Changeset 11405


Ignore:
Timestamp:
2019-08-06T15:16:49+02:00 (5 years ago)
Author:
andmirek
Message:

ticket #2195: read weights for blk using XIOS

Location:
NEMO/branches/2019/dev_r11351_fldread_with_XIOS/src
Files:
23 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2019/dev_r11351_fldread_with_XIOS/src/OCE/DIA/diahsb.F90

    r10425 r11405  
    260260            IF(lwp) WRITE(numout,*) '   dia_hsb_rst : read hsb restart at it= ', kt,' date= ', ndastp 
    261261            IF(lwp) WRITE(numout,*) 
     262            IF(lrxios) CALL iom_swap( TRIM(crxios_context) ) 
    262263            CALL iom_get( numror, 'frc_v', frc_v, ldxios = lrxios ) 
    263264            CALL iom_get( numror, 'frc_t', frc_t, ldxios = lrxios ) 
     
    276277               CALL iom_get( numror, jpdom_autoglo, 'ssh_sc_loc_ini', ssh_sc_loc_ini, ldxios = lrxios ) 
    277278            ENDIF 
     279            IF(lrxios) CALL iom_swap( TRIM(crxios_context) ) 
    278280         ELSE 
    279281            IF(lwp) WRITE(numout,*) 
  • NEMO/branches/2019/dev_r11351_fldread_with_XIOS/src/OCE/DOM/daymod.F90

    r10068 r11405  
    326326         IF( iom_varid( numror, 'kt', ldstop = .FALSE. ) > 0 ) THEN 
    327327            ! Get Calendar informations 
     328            IF(lrxios) CALL iom_swap( TRIM(crxios_context) ) 
    328329            CALL iom_get( numror, 'kt', zkt, ldxios = lrxios )   ! last time-step of previous run 
    329330            IF(lwp) THEN 
     
    381382               ! note this is wrong if time step has changed during run 
    382383            ENDIF 
     384            IF(lrxios) CALL iom_swap( TRIM(cxios_context) ) 
    383385         ELSE 
    384386            ! parameters corresponding to nit000 - 1 (as we start the step loop with a call to day) 
  • NEMO/branches/2019/dev_r11351_fldread_with_XIOS/src/OCE/DOM/domvvl.F90

    r10425 r11405  
    806806         IF( ln_rstart ) THEN                   !* Read the restart file 
    807807            CALL rst_read_open                  !  open the restart file if necessary 
     808            IF(lrxios) CALL iom_swap( TRIM(crxios_context) ) 
    808809            CALL iom_get( numror, jpdom_autoglo, 'sshn'   , sshn, ldxios = lrxios    ) 
    809810            ! 
     
    881882            ENDIF 
    882883            ! 
     884            IF(lrxios) CALL iom_swap( TRIM(cxios_context) ) 
    883885         ELSE                                   !* Initialize at "rest" 
    884886            ! 
  • NEMO/branches/2019/dev_r11351_fldread_with_XIOS/src/OCE/DOM/iscplrst.F90

    r10425 r11405  
    5858      ! 
    5959      !                       ! get restart variable 
     60      IF(lrxios) CALL iom_swap( TRIM(crxios_context) )  
    6061      CALL iom_get( numror, jpdom_autoglo, 'tmask'  , ztmask_b, ldxios = lrxios   ) ! need to extrapolate T/S 
    6162      CALL iom_get( numror, jpdom_autoglo, 'umask'  , zumask_b, ldxios = lrxios   ) ! need to correct barotropic velocity 
     
    6667      CALL iom_get( numror, jpdom_autoglo, 'e3v_n'  , ze3v_b(:,:,:), ldxios = lrxios )  ! need to correct barotropic velocity 
    6768      CALL iom_get( numror, jpdom_autoglo, 'gdepw_n', zdepw_b(:,:,:), ldxios = lrxios ) ! need to interpol vertical profile (vvl) 
     69      IF(lrxios) CALL iom_swap( TRIM(cxios_context) ) 
    6870      ! 
    6971      CALL iscpl_init()       ! read namelist 
  • NEMO/branches/2019/dev_r11351_fldread_with_XIOS/src/OCE/DYN/dynspg_ts.F90

    r10742 r11405  
    14021402         !                                   ! --------------- 
    14031403         IF( ln_rstart .AND. ln_bt_fw .AND. (neuler/=0) ) THEN    !* Read the restart file 
     1404            IF(lrxios) CALL iom_swap( TRIM(crxios_context) ) 
    14041405            CALL iom_get( numror, jpdom_autoglo, 'ub2_b'  , ub2_b  (:,:), ldxios = lrxios )    
    14051406            CALL iom_get( numror, jpdom_autoglo, 'vb2_b'  , vb2_b  (:,:), ldxios = lrxios )  
     
    14211422            ENDIF 
    14221423#endif 
     1424            IF(lrxios) CALL iom_swap( TRIM(cxios_context) ) 
    14231425         ELSE                                   !* Start from rest 
    14241426            IF(lwp) WRITE(numout,*) 
  • NEMO/branches/2019/dev_r11351_fldread_with_XIOS/src/OCE/IOM/in_out_manager.F90

    r10817 r11405  
    175175   CHARACTER(lc) ::   crxios_context         !: context name used in xios to read restart 
    176176   CHARACTER(lc) ::   cwxios_context        !: context name used in xios to write restart file 
     177   CHARACTER(lc) ::   cbwxios_context  = "iom_bklw"       !: context name used in xios to read interpolation weights in sbc_blk 
     178   LOGICAL, PARAMETER, PUBLIC :: lxios_blkw    = .TRUE. 
    177179 
    178180   !!---------------------------------------------------------------------- 
  • NEMO/branches/2019/dev_r11351_fldread_with_XIOS/src/OCE/IOM/iom.F90

    r10817 r11405  
    10721072      llxios = .FALSE. 
    10731073      if(PRESENT(ldxios)) llxios = ldxios 
    1074       idvar = iom_varid( kiomid, cdvar )  
    10751074      idom = kdom 
    10761075      ! 
    10771076      IF(.NOT.llxios) THEN 
     1077         idvar = iom_varid( kiomid, cdvar ) 
    10781078         clname = iom_file(kiomid)%name   !   esier to read 
    10791079         clinfo = '          iom_get_123d, file: '//trim(clname)//', var: '//trim(cdvar) 
     
    12901290         ENDIF 
    12911291         ! 
     1292         !--- Apply scale_factor and offset 
     1293         zscf = iom_file(kiomid)%scf(idvar)      ! scale factor 
     1294         zofs = iom_file(kiomid)%ofs(idvar)      ! offset 
     1295         IF(     PRESENT(pv_r1d) ) THEN 
     1296            IF( zscf /= 1. )   pv_r1d(:) = pv_r1d(:) * zscf 
     1297            IF( zofs /= 0. )   pv_r1d(:) = pv_r1d(:) + zofs 
     1298         ELSEIF( PRESENT(pv_r2d) ) THEN 
     1299            IF( zscf /= 1.)   pv_r2d(:,:) = pv_r2d(:,:) * zscf 
     1300            IF( zofs /= 0.)   pv_r2d(:,:) = pv_r2d(:,:) + zofs 
     1301         ELSEIF( PRESENT(pv_r3d) ) THEN 
     1302            IF( zscf /= 1.)   pv_r3d(:,:,:) = pv_r3d(:,:,:) * zscf 
     1303            IF( zofs /= 0.)   pv_r3d(:,:,:) = pv_r3d(:,:,:) + zofs 
     1304         ENDIF 
    12921305      ELSE        ! read using XIOS. Only if KEY_IOMPUT is defined 
    12931306#if defined key_iomput 
    1294 !would be good to be able to check which context is active and swap only if current is not restart 
    1295          CALL iom_swap( TRIM(crxios_context) )  
    12961307         IF( PRESENT(pv_r3d) ) THEN 
    12971308            pv_r3d(:, :, :) = 0. 
    1298             if(lwp) write(numout,*) 'XIOS RST READ (3D): ',trim(cdvar) 
     1309            if(lwp) write(numout,*) 'XIOS READ (3D): ',trim(cdvar) 
    12991310            CALL xios_recv_field( trim(cdvar), pv_r3d) 
    13001311            IF(idom /= jpdom_unknown ) then 
     
    13031314         ELSEIF( PRESENT(pv_r2d) ) THEN 
    13041315            pv_r2d(:, :) = 0. 
    1305             if(lwp) write(numout,*) 'XIOS RST READ (2D): ', trim(cdvar) 
     1316            if(lwp) write(numout,*) 'XIOS READ (2D): ', trim(cdvar) 
    13061317            CALL xios_recv_field( trim(cdvar), pv_r2d) 
    13071318            IF(idom /= jpdom_unknown ) THEN 
     
    13101321         ELSEIF( PRESENT(pv_r1d) ) THEN 
    13111322            pv_r1d(:) = 0. 
    1312             if(lwp) write(numout,*) 'XIOS RST READ (1D): ', trim(cdvar) 
     1323            if(lwp) write(numout,*) 'XIOS READ (1D): ', trim(cdvar) 
    13131324            CALL xios_recv_field( trim(cdvar), pv_r1d) 
    13141325         ENDIF 
    1315          CALL iom_swap( TRIM(cxios_context) ) 
    13161326#else 
    13171327         istop = istop + 1  
     
    13231333      IF( lk_c1d .AND. PRESENT(pv_r2d) )   CALL lbc_lnk( 'iom', pv_r2d,'Z',1. ) 
    13241334      IF( lk_c1d .AND. PRESENT(pv_r3d) )   CALL lbc_lnk( 'iom', pv_r3d,'Z',1. ) 
    1325  
    1326       !--- Apply scale_factor and offset 
    1327       zscf = iom_file(kiomid)%scf(idvar)      ! scale factor 
    1328       zofs = iom_file(kiomid)%ofs(idvar)      ! offset 
    1329       IF(     PRESENT(pv_r1d) ) THEN 
    1330          IF( zscf /= 1. )   pv_r1d(:) = pv_r1d(:) * zscf  
    1331          IF( zofs /= 0. )   pv_r1d(:) = pv_r1d(:) + zofs 
    1332       ELSEIF( PRESENT(pv_r2d) ) THEN 
    1333          IF( zscf /= 1.)   pv_r2d(:,:) = pv_r2d(:,:) * zscf 
    1334          IF( zofs /= 0.)   pv_r2d(:,:) = pv_r2d(:,:) + zofs 
    1335       ELSEIF( PRESENT(pv_r3d) ) THEN 
    1336          IF( zscf /= 1.)   pv_r3d(:,:,:) = pv_r3d(:,:,:) * zscf 
    1337          IF( zofs /= 0.)   pv_r3d(:,:,:) = pv_r3d(:,:,:) + zofs 
    1338       ENDIF 
    13391335      ! 
    13401336   END SUBROUTINE iom_get_123d 
  • NEMO/branches/2019/dev_r11351_fldread_with_XIOS/src/OCE/IOM/restart.F90

    r10425 r11405  
    255255      ! Check dynamics and tracer time-step consistency and force Euler restart if changed 
    256256      IF( iom_varid( numror, 'rdt', ldstop = .FALSE. ) > 0 )   THEN 
     257         IF(lrxios) CALL iom_swap( TRIM(crxios_context) ) 
    257258         CALL iom_get( numror, 'rdt', zrdt, ldxios = lrxios ) 
     259         IF(lrxios) CALL iom_swap( TRIM(cxios_context) ) 
    258260         IF( zrdt /= rdt )   neuler = 0 
    259261      ENDIF 
     
    262264       
    263265      ! Diurnal DSST  
     266      IF(lrxios) CALL iom_swap( TRIM(crxios_context) ) 
    264267      IF( ln_diurnal ) CALL iom_get( numror, jpdom_autoglo, 'Dsst' , x_dsst, ldxios = lrxios )  
    265268      IF ( ln_diurnal_only ) THEN  
     
    292295         CALL eos( tsn, rhd, rhop, gdept_n(:,:,:) )    
    293296      ENDIF 
     297      IF(lrxios) CALL iom_swap( TRIM(cxios_context) ) 
    294298      ! 
    295299      IF( neuler == 0 ) THEN                                  ! Euler restart (neuler=0) 
  • NEMO/branches/2019/dev_r11351_fldread_with_XIOS/src/OCE/SBC/fldread.F90

    r10425 r11405  
    647647         ENDIF         
    648648      ELSE IF( LEN(TRIM(sdjf%wgtname)) > 0 ) THEN 
    649          CALL wgt_list( sdjf, iw ) 
     649         CALL wgt_list( sdjf, iw, lxios_blkw ) 
    650650         IF( sdjf%ln_tint ) THEN   ;   CALL fld_interp( sdjf%num, sdjf%clvar, iw, ipk, sdjf%fdta(:,:,:,2),          &  
    651651            &                                                                          sdjf%nrec_a(1), sdjf%lsmname ) 
     
    13451345 
    13461346 
    1347    SUBROUTINE wgt_list( sd, kwgt ) 
     1347   SUBROUTINE wgt_list( sd, kwgt, ldxios ) 
    13481348      !!--------------------------------------------------------------------- 
    13491349      !!                    ***  ROUTINE wgt_list  *** 
     
    13551355      TYPE( FLD ), INTENT(in   ) ::   sd        ! field with name of weights file 
    13561356      INTEGER    , INTENT(inout) ::   kwgt      ! index of weights 
     1357      LOGICAL    , INTENT(in), OPTIONAL :: ldxios 
    13571358      ! 
    13581359      INTEGER ::   kw, nestid   ! local integer 
    13591360      LOGICAL ::   found        ! local logical 
     1361      LOGICAL ::   luxios 
     1362      luxios = .FALSE. 
     1363      if(PRESENT(ldxios)) luxios = ldxios 
    13601364      !!---------------------------------------------------------------------- 
    13611365      ! 
     
    13811385      IF( .NOT.found ) THEN 
    13821386         kwgt = nxt_wgt 
    1383          CALL fld_weight( sd ) 
     1387         CALL fld_weight( sd, luxios ) 
    13841388      ENDIF 
    13851389      ! 
     
    14161420 
    14171421 
    1418    SUBROUTINE fld_weight( sd ) 
     1422   SUBROUTINE fld_weight( sd, ldxios ) 
    14191423      !!--------------------------------------------------------------------- 
    14201424      !!                    ***  ROUTINE fld_weight  *** 
     
    14241428      !!---------------------------------------------------------------------- 
    14251429      TYPE( FLD ), INTENT(in) ::   sd   ! field with name of weights file 
     1430      LOGICAL, INTENT(in), OPTIONAL :: ldxios 
    14261431      !! 
    14271432      INTEGER ::   jn         ! dummy loop indices 
     
    14351440      INTEGER,  DIMENSION(jpi,jpj) ::   data_src 
    14361441      REAL(wp), DIMENSION(jpi,jpj) ::   data_tmp 
     1442      LOGICAL                      ::   luxios 
    14371443      !!---------------------------------------------------------------------- 
     1444      luxios = .FALSE. 
     1445      IF(PRESENT(ldxios)) luxios = ldxios 
    14381446      ! 
    14391447      IF( nxt_wgt > tot_wgts ) THEN 
     
    14641472      CALL iom_open ( sd%wgtname, inum )   ! interpolation weights 
    14651473      IF ( inum > 0 ) THEN 
    1466  
     1474         IF(luxios) THEN  
     1475            CALL iom_swap(cbwxios_context) 
     1476         ENDIF 
    14671477         !! determine whether we have an east-west cyclic grid 
    14681478         !! from global attribute called "ew_wrap" in the weights file 
     
    15111521            WRITE(aname,'(a3,i2.2)') 'src',jn 
    15121522            data_tmp(:,:) = 0 
    1513             CALL iom_get ( inum, jpdom_data, aname, data_tmp(:,:) ) 
     1523            IF(luxios) THEN 
     1524               CALL iom_get ( inum, jpdom_data, aname//TRIM(sd%wgtname), data_tmp(:,:), ldxios = luxios ) 
     1525            ELSE 
     1526               CALL iom_get ( inum, jpdom_data, aname, data_tmp(:,:) ) 
     1527            ENDIF 
    15141528            data_src(:,:) = INT(data_tmp(:,:)) 
    15151529            ref_wgts(nxt_wgt)%data_jpj(:,:,jn) = 1 + (data_src(:,:)-1) / ref_wgts(nxt_wgt)%ddims(1) 
     
    15211535            WRITE(aname,'(a3,i2.2)') 'wgt',jn 
    15221536            ref_wgts(nxt_wgt)%data_wgt(:,:,jn) = 0.0 
    1523             CALL iom_get ( inum, jpdom_data, aname, ref_wgts(nxt_wgt)%data_wgt(:,:,jn) ) 
     1537            IF(luxios) THEN 
     1538               CALL iom_get ( inum, jpdom_data, aname//TRIM(sd%wgtname), ref_wgts(nxt_wgt)%data_wgt(:,:,jn), ldxios = luxios ) 
     1539            ELSE 
     1540               CALL iom_get ( inum, jpdom_data, aname, ref_wgts(nxt_wgt)%data_wgt(:,:,jn) ) 
     1541            ENDIF 
    15241542         END DO 
    15251543         CALL iom_close (inum) 
     
    15481566         nxt_wgt = nxt_wgt + 1 
    15491567         ! 
     1568         IF(luxios) CALL iom_swap(cxios_context) 
    15501569      ELSE  
    15511570         CALL ctl_stop( '    fld_weight : unable to read the file ' ) 
  • NEMO/branches/2019/dev_r11351_fldread_with_XIOS/src/OCE/SBC/sbcapr.F90

    r11204 r11405  
    156156         IF( ln_rstart .AND. iom_varid( numror, 'ssh_ibb', ldstop = .FALSE. ) > 0 ) THEN  
    157157            IF(lwp) WRITE(numout,*) 'sbc_apr:   ssh_ibb read in the restart file' 
     158            IF(lrxios) CALL iom_swap( TRIM(crxios_context) ) 
    158159            CALL iom_get( numror, jpdom_autoglo, 'ssh_ibb', ssh_ibb, ldxios = lrxios )   ! before inv. barometer ssh 
     160            IF(lrxios) CALL iom_swap( TRIM(cxios_context) ) 
    159161            ! 
    160162         ELSE                                         !* no restart: set from nit000 values 
  • NEMO/branches/2019/dev_r11351_fldread_with_XIOS/src/OCE/SBC/sbcblk.F90

    r10535 r11405  
    280280         ! 
    281281      ENDIF 
     282 
     283      IF(lxios_blkw) THEN 
     284         CALL iom_blk_wgt_init( cbwxios_context ) 
     285         CALL iom_swap( cxios_context ) 
     286      ENDIF 
     287       
    282288      ! 
    283289   END SUBROUTINE sbc_blk_init 
     
    681687      ! 
    682688   END FUNCTION L_vap 
     689 
     690   SUBROUTINE iom_blk_wgt_init( cdname, ld_tmppatch )  
     691#if defined key_iomput 
     692      use xios 
     693#endif 
     694      !!---------------------------------------------------------------------- 
     695      !!                     ***  ROUTINE   *** 
     696      !! 
     697      !! ** Purpose :   initialize context for reading weights for surface 
     698      !!                forcing 
     699      !! 
     700      !!---------------------------------------------------------------------- 
     701      CHARACTER(len=*),           INTENT(in)  :: cdname 
     702      LOGICAL         , OPTIONAL, INTENT(in)  :: ld_tmppatch 
     703#if defined key_iomput 
     704      ! 
     705      INTEGER, PARAMETER :: lcname = 26 
     706      CHARACTER(len=lc) :: clname 
     707      INTEGER           :: ji, jkmin 
     708      LOGICAL ::   ll_tmppatch = .TRUE.    !: seb: patch before we remove periodicity 
     709      INTEGER ::   nldi_save, nlei_save    !:      and close boundaries in output files 
     710      INTEGER ::   nldj_save, nlej_save    !: 
     711      LOGICAL ::   ll_global = .FALSE.     !: do we have variable on model grid 
     712      CHARACTER(len=lc), DIMENSION( jpts) :: cg_name(jpts) 
     713      CHARACTER(len=1), DIMENSION(lcname) :: cname 
     714      CHARACTER(len=lc)               :: cfname ! file name without .nc 
     715      TYPE(xios_duration)               :: dtime    = xios_duration(0, 0, 0, 0, 0, 0), & 
     716                                           outp_frq = xios_duration(0, 0, 0, 0, 0, 0) 
     717      TYPE(xios_domaingroup)            :: domaingroup_hdl 
     718      TYPE(xios_domain)                 :: domain_hdl 
     719      TYPE(xios_axisgroup)              :: axisgroup_hdl 
     720      TYPE(xios_axis)                   :: axis_hdl 
     721      TYPE(xios_scalar)                 :: scalar_hdl 
     722      TYPE(xios_scalargroup)            :: scalargroup_hdl 
     723      TYPE(xios_file)                   :: file_hdl 
     724      TYPE(xios_filegroup)              :: filegroup_hdl 
     725      TYPE(xios_field)                  :: field_hdl 
     726      INTEGER                           :: jf, ni, nj, ipos, jfld 
     727      INTEGER, DIMENSION(3)             :: ndims         ! size of each dimension. this is surface  
     728                                                         ! forcing, not more than 3: (x, y, t) 
     729      INTEGER                           :: ndim          ! number if dimensions  
     730      INTEGER                           :: inum          ! file id 
     731      INTEGER                           :: ivid          ! varable id in netcdf file 
     732      CHARACTER (len=5)                 :: aname         !name of the field in wght file 
     733      INTEGER                           :: numwgt        ! 
     734      LOGICAL                           :: lfound 
     735      INTEGER                           :: jg, id, jn 
     736       
     737 
     738      cname(:)= (/'a', 'b', 'c', 'd', 'e', 'f', 'g', 'h', 'i', 'j', & 
     739                  'k', 'l', 'm', 'n', 'o', 'p', 'q', 'r', 's', 't', & 
     740                  'u', 'v', 'w', 'x', 'y', 'z'/) 
     741      !!---------------------------------------------------------------------- 
     742      ! 
     743      ! seb: patch before we remove periodicity and close boundaries in output files 
     744      IF ( ll_tmppatch ) THEN 
     745         nldi_save = nldi   ;   nlei_save = nlei 
     746         nldj_save = nldj   ;   nlej_save = nlej 
     747         IF( nimpp           ==      1 ) nldi = 1 
     748         IF( nimpp + jpi - 1 == jpiglo ) nlei = jpi 
     749         IF( njmpp           ==      1 ) nldj = 1 
     750         IF( njmpp + jpj - 1 == jpjglo ) nlej = jpj 
     751      ENDIF 
     752      ! 
     753      jfld = SIZE(sf) 
     754 
     755      IF(jfld > lcname) THEN 
     756      STOP 'lcname number is too small' 
     757      ENDIF 
     758 
     759      clname = cdname 
     760      IF( TRIM(Agrif_CFixed()) /= '0' )   clname = TRIM(Agrif_CFixed())//"_"//TRIM(cdname) 
     761      CALL xios_context_initialize(TRIM(clname), mpi_comm_oce) 
     762      CALL iom_swap( cdname ) 
     763      ! Calendar type is now defined in xml file  
     764      SELECT CASE ( nleapy )        ! Choose calendar for IOIPSL 
     765      CASE ( 1)   ; CALL xios_define_calendar( TYPE = "Gregorian", time_origin = xios_date(1948, 01, 01, 00, 00, 00), & 
     766          &                                    start_date = xios_date(nyear, nmonth, nday,00,00,00) ) 
     767      CASE ( 0)   ; CALL xios_define_calendar( TYPE = "NoLeap"   , time_origin = xios_date(1948, 01, 01, 00, 00, 00), & 
     768          &                                    start_date = xios_date(nyear, nmonth, nday,00,00,00) ) 
     769      CASE (30)   ; CALL xios_define_calendar( TYPE = "D360"     , time_origin = xios_date(1948, 01, 01, 00, 00, 00), & 
     770          &                                    start_date = xios_date(nyear, nmonth, nday, 00, 00, 00) ) 
     771      END SELECT 
     772 
     773 
     774      dtime%month = 1 
     775      CALL xios_set_timestep( dtime ) 
     776 
     777      CALL xios_get_handle("domain_definition",domaingroup_hdl) 
     778      CALL xios_add_child(domaingroup_hdl, domain_hdl, "grid_global") 
     779      ni = nlei-nldi+1 
     780      nj = nlej-nldj+1 
     781      CALL xios_set_domain_attr("grid_global", ni_glo=jpiglo, nj_glo=jpjglo, ibegin=nimpp+nldi-2, jbegin=njmpp+nldj-2, ni=ni, nj=nj) 
     782      CALL xios_set_domain_attr("grid_global", data_dim=2, data_ibegin = 1-nldi, data_ni = jpi, data_jbegin = 1-nldj, data_nj = jpj) 
     783      CALL xios_set_domain_attr("grid_global", type='curvilinear') 
     784 
     785      CALL xios_get_handle("file_definition", filegroup_hdl ) 
     786 
     787      DO jf = 1, jfld 
     788!do we have weights file defined already? 
     789         lfound = .FALSE. 
     790         DO jg = 1, jf-1 
     791            IF(TRIM(sf(jf)%wgtname) == TRIM(sf(jg)%wgtname)) THEN 
     792               IF(lwp) write(numout, *) TRIM(sf(jf)%wgtname),' already defined, skipping ' 
     793               lfound = .TRUE. 
     794               exit 
     795            ENDIF 
     796         ENDDO 
     797         IF(lfound) cycle 
     798!add next weights file 
     799         ipos = index(sf(jf)%wgtname,'.nc') 
     800         cfname(1:lc) = " " 
     801         IF(ipos > 0) THEN 
     802          cfname(1:ipos-1) = sf(jf)%wgtname(1:ipos-1) 
     803         ELSE 
     804          cfname(1:lc) = sf(jf)%wgtname(1:lc) 
     805         ENDIF 
     806 
     807         CALL xios_add_child(filegroup_hdl, file_hdl, cname(jf)) 
     808         CALL xios_set_file_attr( cname(jf), name=TRIM(cfname),           & 
     809                type="one_file", par_access="collective", enabled=.TRUE., & 
     810                output_freq=xios_timestep, mode="read") 
     811 
     812         CALL iom_open ( sf(jf)%wgtname, inum ) 
     813         id = iom_varid(inum, 'src05', ldstop=.FALSE.) 
     814         IF(id <= 0) THEN 
     815             numwgt = 4 
     816         ELSE 
     817             numwgt = 16 
     818         ENDIF 
     819         CALL iom_close ( inum ) 
     820!define variables in weights file. Because all files have the same names src01, 
     821!dst01, ... add filename to the name to uniquely identify variables  
     822         aname = ' ' 
     823         DO jn = 1, numwgt 
     824            WRITE(aname,'(a3,i2.2)') 'src',jn 
     825            CALL xios_add_child(file_hdl, field_hdl, TRIM(aname)//TRIM(sf(jf)%wgtname)) 
     826            CALL xios_set_attr (field_hdl, enabled = .TRUE., & 
     827                          name = TRIM(aname), domain_ref="grid_global", & 
     828                          operation = "instant") 
     829            CALL xios_add_child(file_hdl, field_hdl, TRIM(aname)//TRIM(sf(jf)%wgtname)) 
     830            CALL xios_set_attr (field_hdl, enabled = .TRUE., & 
     831                          name = TRIM(aname), domain_ref="grid_global", & 
     832                          operation = "instant")  
     833         ENDDO  
     834      ENDDO    
     835 
     836 
     837      CALL xios_close_context_definition() 
     838      CALL xios_update_calendar( 0 ) 
     839 
     840      IF ( ll_tmppatch ) THEN 
     841         nldi = nldi_save   ;   nlei = nlei_save 
     842         nldj = nldj_save   ;   nlej = nlej_save 
     843      ENDIF 
     844#endif 
     845      ! 
     846   END SUBROUTINE iom_blk_wgt_init 
     847 
    683848 
    684849#if defined key_si3 
  • NEMO/branches/2019/dev_r11351_fldread_with_XIOS/src/OCE/SBC/sbcisf.F90

    r10536 r11405  
    207207            &   iom_varid( numror, 'fwf_isf_b', ldstop = .FALSE. ) > 0 ) THEN 
    208208            IF(lwp) WRITE(numout,*) '          nit000-1 isf tracer content forcing fields read in the restart file' 
     209            IF(lrxios) CALL iom_swap( TRIM(crxios_context) ) 
    209210            CALL iom_get( numror, jpdom_autoglo, 'fwf_isf_b', fwfisf_b(:,:)         , ldxios = lrxios )   ! before salt content isf_tsc trend 
    210211            CALL iom_get( numror, jpdom_autoglo, 'isf_sc_b' , risf_tsc_b(:,:,jp_sal), ldxios = lrxios )   ! before salt content isf_tsc trend 
    211212            CALL iom_get( numror, jpdom_autoglo, 'isf_hc_b' , risf_tsc_b(:,:,jp_tem), ldxios = lrxios )   ! before salt content isf_tsc trend 
     213            IF(lrxios) CALL iom_swap( TRIM(cxios_context) ) 
    212214         ELSE 
    213215            fwfisf_b(:,:)    = fwfisf(:,:) 
  • NEMO/branches/2019/dev_r11351_fldread_with_XIOS/src/OCE/SBC/sbcmod.F90

    r10499 r11405  
    496496            & iom_varid( numror, 'utau_b', ldstop = .FALSE. ) > 0 ) THEN 
    497497            IF(lwp) WRITE(numout,*) '          nit000-1 surface forcing fields red in the restart file' 
     498            IF(lrxios) CALL iom_swap( TRIM(crxios_context) ) 
    498499            CALL iom_get( numror, jpdom_autoglo, 'utau_b', utau_b, ldxios = lrxios )   ! before i-stress  (U-point) 
    499500            CALL iom_get( numror, jpdom_autoglo, 'vtau_b', vtau_b, ldxios = lrxios )   ! before j-stress  (V-point) 
     
    508509               sfx_b (:,:) = sfx(:,:) 
    509510            ENDIF 
     511            IF(lrxios) CALL iom_swap( TRIM(cxios_context) ) 
    510512         ELSE                                                   !* no restart: set from nit000 values 
    511513            IF(lwp) WRITE(numout,*) '          nit000-1 surface forcing fields set to nit000' 
  • NEMO/branches/2019/dev_r11351_fldread_with_XIOS/src/OCE/SBC/sbcrnf.F90

    r10523 r11405  
    146146         IF( ln_rstart .AND.    &                               !* Restart: read in restart file 
    147147            & iom_varid( numror, 'rnf_b', ldstop = .FALSE. ) > 0 ) THEN 
     148            IF(lrxios) CALL iom_swap( TRIM(crxios_context) ) 
    148149            IF(lwp) WRITE(numout,*) '          nit000-1 runoff forcing fields red in the restart file', lrxios 
    149150            CALL iom_get( numror, jpdom_autoglo, 'rnf_b', rnf_b, ldxios = lrxios )     ! before runoff 
    150151            CALL iom_get( numror, jpdom_autoglo, 'rnf_hc_b', rnf_tsc_b(:,:,jp_tem), ldxios = lrxios )   ! before heat content of runoff 
    151152            CALL iom_get( numror, jpdom_autoglo, 'rnf_sc_b', rnf_tsc_b(:,:,jp_sal), ldxios = lrxios )   ! before salinity content of runoff 
     153            IF(lrxios) CALL iom_swap( TRIM(cxios_context) ) 
    152154         ELSE                                                   !* no restart: set from nit000 values 
    153155            IF(lwp) WRITE(numout,*) '          nit000-1 runoff forcing fields set to nit000' 
  • NEMO/branches/2019/dev_r11351_fldread_with_XIOS/src/OCE/SBC/sbcssm.F90

    r10425 r11405  
    209209         IF( ln_rstart .AND. iom_varid( numror, 'nn_fsbc', ldstop = .FALSE. ) > 0 ) THEN 
    210210            l_ssm_mean = .TRUE. 
     211            IF(lrxios) CALL iom_swap( TRIM(crxios_context) ) 
    211212            CALL iom_get( numror               , 'nn_fsbc', zf_sbc, ldxios = lrxios )    ! sbc frequency of previous run 
    212213            CALL iom_get( numror, jpdom_autoglo, 'ssu_m'  , ssu_m, ldxios = lrxios  )    ! sea surface mean velocity    (U-point) 
     
    222223               frq_m(:,:) = 1._wp   ! default definition 
    223224            ENDIF 
     225            IF(lrxios) CALL iom_swap( TRIM(cxios_context) ) 
    224226            ! 
    225227            IF( zf_sbc /= REAL( nn_fsbc, wp ) ) THEN      ! nn_fsbc has changed between 2 runs 
  • NEMO/branches/2019/dev_r11351_fldread_with_XIOS/src/OCE/TRA/traqsr.F90

    r10425 r11405  
    137137            IF(lwp) WRITE(numout,*) '          nit000-1 qsr tracer content forcing field read in the restart file' 
    138138            z1_2 = 0.5_wp 
     139            IF(lrxios) CALL iom_swap( TRIM(crxios_context) ) 
    139140            CALL iom_get( numror, jpdom_autoglo, 'qsr_hc_b', qsr_hc_b, ldxios = lrxios )   ! before heat content trend due to Qsr flux 
     141            IF(lrxios) CALL iom_swap( TRIM(cxios_context) ) 
    140142         ELSE                                           ! No restart or restart not found: Euler forward time stepping 
    141143            z1_2 = 1._wp 
  • NEMO/branches/2019/dev_r11351_fldread_with_XIOS/src/OCE/TRA/trasbc.F90

    r10499 r11405  
    110110            zfact = 0.5_wp 
    111111            sbc_tsc(:,:,:) = 0._wp 
     112            IF(lrxios) CALL iom_swap( TRIM(crxios_context) ) 
    112113            CALL iom_get( numror, jpdom_autoglo, 'sbc_hc_b', sbc_tsc_b(:,:,jp_tem), ldxios = lrxios )   ! before heat content sbc trend 
    113114            CALL iom_get( numror, jpdom_autoglo, 'sbc_sc_b', sbc_tsc_b(:,:,jp_sal), ldxios = lrxios )   ! before salt content sbc trend 
     115            IF(lrxios) CALL iom_swap( TRIM(cxios_context) ) 
    114116         ELSE                                   ! No restart or restart not found: Euler forward time stepping 
    115117            zfact = 1._wp 
  • NEMO/branches/2019/dev_r11351_fldread_with_XIOS/src/OCE/ZDF/zdfgls.F90

    r10425 r11405  
    11721172            ! 
    11731173            IF( MIN( id1, id2, id3, id4 ) > 0 ) THEN        ! all required arrays exist 
     1174               IF(lrxios) CALL iom_swap( TRIM(crxios_context) ) 
    11741175               CALL iom_get( numror, jpdom_autoglo, 'en'    , en    , ldxios = lrxios ) 
    11751176               CALL iom_get( numror, jpdom_autoglo, 'avt_k' , avt_k , ldxios = lrxios ) 
    11761177               CALL iom_get( numror, jpdom_autoglo, 'avm_k' , avm_k , ldxios = lrxios ) 
    11771178               CALL iom_get( numror, jpdom_autoglo, 'hmxl_n', hmxl_n, ldxios = lrxios ) 
     1179               IF(lrxios) CALL iom_swap( TRIM(cxios_context) ) 
    11781180            ELSE                         
    11791181               IF(lwp) WRITE(numout,*) 
  • NEMO/branches/2019/dev_r11351_fldread_with_XIOS/src/OCE/ZDF/zdfosm.F90

    r10425 r11405  
    15431543     !!----------------------------------------------------------------------------- 
    15441544     IF( TRIM(cdrw) == 'READ'.AND. ln_rstart) THEN 
     1545        IF(lrxios) CALL iom_swap( TRIM(crxios_context) ) 
    15451546        id1 = iom_varid( numror, 'wn'   , ldstop = .FALSE. ) 
    15461547        IF( id1 > 0 ) THEN                       ! 'wn' exists; read 
     
    15611562           WRITE(numout,*) ' ===>>>> : previous run without osmosis scheme, hbl computed from stratification' 
    15621563        END IF 
     1564        IF(lrxios) CALL iom_swap( TRIM(cxios_context) ) 
    15631565     END IF 
    15641566 
  • NEMO/branches/2019/dev_r11351_fldread_with_XIOS/src/OCE/ZDF/zdfric.F90

    r10068 r11405  
    226226            ! 
    227227            IF( MIN( id1, id2 ) > 0 ) THEN         ! restart exists => read it 
     228               IF(lrxios) CALL iom_swap( TRIM(crxios_context) ) 
    228229               CALL iom_get( numror, jpdom_autoglo, 'avt_k', avt_k, ldxios = lrxios ) 
    229230               CALL iom_get( numror, jpdom_autoglo, 'avm_k', avm_k, ldxios = lrxios ) 
     231               IF(lrxios) CALL iom_swap( TRIM(cxios_context) ) 
    230232            ENDIF 
    231233         ENDIF 
  • NEMO/branches/2019/dev_r11351_fldread_with_XIOS/src/OCE/ZDF/zdftke.F90

    r10425 r11405  
    776776            ! 
    777777            IF( MIN( id1, id2, id3, id4 ) > 0 ) THEN      ! fields exist 
     778               IF(lrxios) CALL iom_swap( TRIM(crxios_context) )  
    778779               CALL iom_get( numror, jpdom_autoglo, 'en'   , en   , ldxios = lrxios ) 
    779780               CALL iom_get( numror, jpdom_autoglo, 'avt_k', avt_k, ldxios = lrxios ) 
    780781               CALL iom_get( numror, jpdom_autoglo, 'avm_k', avm_k, ldxios = lrxios ) 
    781782               CALL iom_get( numror, jpdom_autoglo, 'dissl', dissl, ldxios = lrxios ) 
     783               IF(lrxios) CALL iom_swap( TRIM(cxios_context) ) 
    782784            ELSE                                          ! start TKE from rest 
    783785               IF(lwp) WRITE(numout,*) 
  • NEMO/branches/2019/dev_r11351_fldread_with_XIOS/src/OCE/step.F90

    r11287 r11405  
    323323                      CALL iom_context_finalize(      cxios_context          ) ! needed for XIOS+AGRIF 
    324324                      IF(lrxios) CALL iom_context_finalize(      crxios_context          ) 
     325                      IF(lxios_blkw) CALL iom_context_finalize(  cbwxios_context         ) 
    325326         IF( ln_crs ) CALL iom_context_finalize( trim(cxios_context)//"_crs" ) !  
    326327      ENDIF 
  • NEMO/branches/2019/dev_r11351_fldread_with_XIOS/src/SAS/daymod.F90

    r10068 r11405  
    324324         IF( iom_varid( numror, 'kt', ldstop = .FALSE. ) > 0 ) THEN 
    325325            ! Get Calendar informations 
     326            IF(lrxios) CALL iom_swap( TRIM(crxios_context) ) 
    326327            CALL iom_get( numror, 'kt', zkt, ldxios = lrxios )   ! last time-step of previous run 
    327328            IF(lwp) THEN 
     
    379380               ! note this is wrong if time step has changed during run 
    380381            ENDIF 
     382            IF(lrxios) CALL iom_swap( TRIM(cxios_context) ) 
    381383         ELSE 
    382384            ! parameters corresponding to nit000 - 1 (as we start the step loop with a call to day) 
Note: See TracChangeset for help on using the changeset viewer.