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 7924 for branches/UKMO/dev_r5518_GO6_package_XIOS_read/NEMOGCM/NEMO/OPA_SRC/IOM/restart.F90 – NEMO

Ignore:
Timestamp:
2017-04-18T15:42:46+02:00 (7 years ago)
Author:
andmirek
Message:

first commit with XIOS restart read functionality

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/UKMO/dev_r5518_GO6_package_XIOS_read/NEMOGCM/NEMO/OPA_SRC/IOM/restart.F90

    r6755 r7924  
    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       
     226      IF(.NOT.lxios_set) lxios_read = lxios_read.AND.lxios_sini 
     227      print *,'SINGLE FILE RESTART?: ',lxios_sini,' USE XIOS? :',lxios_read 
     228      IF( lxios_read) THEN 
     229         if(.NOT.lxios_set) then 
     230             rxios_context = 'nemo_rst' 
     231             call iom_init( rxios_context ) 
     232             lxios_set = .TRUE. 
     233         endif 
     234       ENDIF 
     235       
     236      ENDIF 
     237 
    221238   END SUBROUTINE rst_read_open 
    222239 
     
    232249      INTEGER  ::   jk 
    233250      LOGICAL  ::   llok 
     251      TYPE(xios_duration):: dtime 
     252      integer::ni,nj,nk 
    234253      !!---------------------------------------------------------------------- 
    235254 
     
    238257      ! Check dynamics and tracer time-step consistency and force Euler restart if changed 
    239258      IF( iom_varid( numror, 'rdt', ldstop = .FALSE. ) > 0 )   THEN 
    240          CALL iom_get( numror, 'rdt', zrdt ) 
     259         CALL iom_get( numror, 'rdt', zrdt, lrxios = lxios_read ) 
    241260         IF( zrdt /= rdt )   neuler = 0 
    242261      ENDIF 
    243262      IF( iom_varid( numror, 'rdttra1', ldstop = .FALSE. ) > 0 )   THEN 
    244          CALL iom_get( numror, 'rdttra1', zrdttra1 ) 
     263         CALL iom_get( numror, 'rdttra1', zrdttra1, lrxios = lxios_read ) 
    245264         IF( zrdttra1 /= rdttra(1) )   neuler = 0 
    246265      ENDIF 
    247266      !  
    248267      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    ) 
     268         CALL iom_get( numror, jpdom_autoglo, 'ub'     , ub, lrxios = lxios_read )   ! before fields 
     269         CALL iom_get( numror, jpdom_autoglo, 'vb'     , vb, lrxios = lxios_read ) 
     270         CALL iom_get( numror, jpdom_autoglo, 'tb'     , tsb(:,:,:,jp_tem), lrxios = lxios_read ) 
     271         CALL iom_get( numror, jpdom_autoglo, 'sb'     , tsb(:,:,:,jp_sal), lrxios = lxios_read ) 
     272         CALL iom_get( numror, jpdom_autoglo, 'rotb'   , rotb, lrxios = lxios_read ) 
     273         CALL iom_get( numror, jpdom_autoglo, 'hdivb'  , hdivb, lrxios = lxios_read ) 
     274         CALL iom_get( numror, jpdom_autoglo, 'sshb'   , sshb, lrxios = lxios_read ) 
    256275      ELSE 
    257276         neuler = 0 
    258277      ENDIF 
    259278      ! 
    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    ) 
     279      CALL iom_get( numror, jpdom_autoglo, 'un'     , un, lrxios = lxios_read )   ! now    fields 
     280      CALL iom_get( numror, jpdom_autoglo, 'vn'     , vn, lrxios = lxios_read ) 
     281      CALL iom_get( numror, jpdom_autoglo, 'tn'     , tsn(:,:,:,jp_tem), lrxios = lxios_read ) 
     282      CALL iom_get( numror, jpdom_autoglo, 'sn'     , tsn(:,:,:,jp_sal), lrxios = lxios_read ) 
     283      CALL iom_get( numror, jpdom_autoglo, 'sshn'   , sshn, lrxios = lxios_read ) 
    265284      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  ) 
     285         CALL iom_get( numror, jpdom_autoglo, 'rotn'   , rotn, lrxios = lxios_read ) 
     286         CALL iom_get( numror, jpdom_autoglo, 'hdivn'  , hdivn, lrxios = lxios_read ) 
    268287      ELSE 
    269288         CALL div_cur( 0 )                              ! Horizontal divergence & Relative vorticity 
    270289      ENDIF 
    271290      IF( iom_varid( numror, 'rhop', ldstop = .FALSE. ) > 0 ) THEN 
    272          CALL iom_get( numror, jpdom_autoglo, 'rhop'   , rhop    )   ! now    potential density 
     291         CALL iom_get( numror, jpdom_autoglo, 'rhop'   , rhop, lrxios = lxios_read )   ! now    potential density 
    273292      ELSE 
    274293         CALL eos    ( tsn, rhd, rhop, fsdept_n(:,:,:) )    
     
    276295#if defined key_zdfkpp 
    277296      IF( iom_varid( numror, 'rhd', ldstop = .FALSE. ) > 0 ) THEN 
    278          CALL iom_get( numror, jpdom_autoglo, 'rhd'    , rhd    )   ! now    in situ density anomaly 
     297         CALL iom_get( numror, jpdom_autoglo, 'rhd'    , rhd, lrxios = lxios_read )   ! now    in situ density anomaly 
    279298      ELSE 
    280299         CALL eos( tsn, rhd, fsdept_n(:,:,:) )   ! compute rhd 
     
    283302      ! 
    284303      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 ) 
     304         CALL iom_get( numror, 'greenland_icesheet_mass', greenland_icesheet_mass, lrxios = lxios_read ) 
     305         CALL iom_get( numror, 'greenland_icesheet_timelapsed', greenland_icesheet_timelapsed, lrxios = lxios_read ) 
     306         CALL iom_get( numror, 'greenland_icesheet_mass_roc', greenland_icesheet_mass_rate_of_change, lrxios = lxios_read ) 
    288307      ELSE 
    289308         greenland_icesheet_mass = 0.0  
     
    292311      ENDIF 
    293312      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 ) 
     313         CALL iom_get( numror, 'antarctica_icesheet_mass', antarctica_icesheet_mass, lrxios = lxios_read ) 
     314         CALL iom_get( numror, 'antarctica_icesheet_timelapsed', antarctica_icesheet_timelapsed, lrxios = lxios_read ) 
     315         CALL iom_get( numror, 'antarctica_icesheet_mass_roc', antarctica_icesheet_mass_rate_of_change, lrxios = lxios_read ) 
    297316      ELSE 
    298317         antarctica_icesheet_mass = 0.0  
     
    300319         antarctica_icesheet_timelapsed = 0.0 
    301320      ENDIF 
     321!     IF( nn_timing == 1 )  CALL timing_stop('iom_read') 
    302322 
    303323      IF( neuler == 0 ) THEN                                  ! Euler restart (neuler=0) 
Note: See TracChangeset for help on using the changeset viewer.