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

Changeset 12977


Ignore:
Timestamp:
2020-05-27T09:35:03+02:00 (4 years ago)
Author:
andmirek
Message:

Ticket #2462 read restart with XIOS in SAS

Location:
NEMO/branches/2020/dev_12905_xios_restart/src
Files:
8 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2020/dev_12905_xios_restart/src/OCE/DOM/domain.F90

    r12950 r12977  
    5858CONTAINS 
    5959 
    60    SUBROUTINE dom_init( Kbb, Kmm, Kaa, cdstr ) 
     60   SUBROUTINE dom_init( Kbb, Kmm, Kaa ) 
    6161      !!---------------------------------------------------------------------- 
    6262      !!                  ***  ROUTINE dom_init  *** 
     
    7474      !!---------------------------------------------------------------------- 
    7575      INTEGER          , INTENT(in) :: Kbb, Kmm, Kaa          ! ocean time level indices 
    76       CHARACTER (len=*), INTENT(in) :: cdstr                  ! model: NEMO or SAS. Determines core restart variables 
    7776      ! 
    7877      INTEGER ::   ji, jj, jk, ik   ! dummy loop indices 
     
    122121      CALL dom_glo                     ! global domain versus local domain 
    123122      CALL dom_nam                     ! read namelist ( namrun, namdom ) 
    124       ! 
    125 !reset namelist for SAS 
    126       IF(cdstr == 'SAS') THEN 
    127          IF(lrxios) THEN 
    128                IF(lwp) write(numout,*) 'Disable reading restart file using XIOS for SAS' 
    129                lrxios = .FALSE. 
    130          ENDIF 
    131       ENDIF 
    132123      ! 
    133124      CALL dom_hgr                      ! Horizontal mesh 
  • NEMO/branches/2020/dev_12905_xios_restart/src/OCE/IOM/iom.F90

    r12961 r12977  
    618618#if defined key_iomput 
    619619      TYPE(xios_context) :: nemo_hdl 
    620       IF(lwp) write(numout, *) 'SWAP TO: ', TRIM(cdname),' AGRIF: ', TRIM(Agrif_CFixed()) 
    621620      IF( TRIM(Agrif_CFixed()) == '0' ) THEN 
    622621        CALL xios_get_handle(TRIM(cdname),nemo_hdl) 
  • NEMO/branches/2020/dev_12905_xios_restart/src/OCE/nemogcm.F90

    r12641 r12977  
    428428      IF( lk_c1d       )   CALL     c1d_init        ! 1D column configuration 
    429429                           CALL     wad_init        ! Wetting and drying options 
    430                            CALL     dom_init( Nbb, Nnn, Naa, "OPA") ! Domain 
     430                           CALL     dom_init( Nbb, Nnn, Naa ) ! Domain 
    431431      IF( ln_crs       )   CALL     crs_init(      Nnn )       ! coarsened grid: domain initialization  
    432432      IF( sn_cfctl%l_prtctl )   & 
  • NEMO/branches/2020/dev_12905_xios_restart/src/OCE/step.F90

    r12969 r12977  
    351351      IF( kstp == nit000 ) THEN                          ! 1st time step only 
    352352                                        CALL iom_close( numror )   ! close input  ocean restart file 
    353          IF( lroxios )                   CALL iom_context_finalize(      crxios_context         ) 
     353         IF( lroxios )                  CALL iom_context_finalize(      crxios_context         ) 
    354354         IF(lwm)                        CALL FLUSH    ( numond )   ! flush output namelist oce 
    355355         IF(lwm .AND. numoni /= -1 )    CALL FLUSH    ( numoni )   ! flush output namelist ice (if exist) 
  • NEMO/branches/2020/dev_12905_xios_restart/src/OFF/nemogcm.F90

    r12843 r12977  
    323323                           CALL     eos_init        ! Equation of state 
    324324      IF( lk_c1d       )   CALL     c1d_init        ! 1D column configuration 
    325                            CALL     dom_init( Nbb, Nnn, Naa, "OPA") ! Domain 
     325                           CALL     dom_init( Nbb, Nnn, Naa ) ! Domain 
    326326      IF( sn_cfctl%l_prtctl )   & 
    327327         &                 CALL prt_ctl_init        ! Print control 
  • NEMO/branches/2020/dev_12905_xios_restart/src/SAO/nemogcm.F90

    r12641 r12977  
    246246                           CALL phy_cst            ! Physical constants 
    247247                           CALL eos_init           ! Equation of state 
    248                            CALL dom_init( Nbb, Nnn, Naa, 'SAO')    ! Domain 
     248                           CALL dom_init( Nbb, Nnn, Naa )    ! Domain 
    249249 
    250250 
  • NEMO/branches/2020/dev_12905_xios_restart/src/SAS/nemogcm.F90

    r12641 r12977  
    370370                           CALL phy_cst         ! Physical constants 
    371371                           CALL eos_init        ! Equation of seawater 
    372                            CALL dom_init( Nbb, Nnn, Naa, 'SAS') ! Domain 
     372                           CALL dom_init( Nbb, Nnn, Naa ) ! Domain 
    373373      IF( sn_cfctl%l_prtctl )   & 
    374374         &                 CALL prt_ctl_init        ! Print control 
    375        
     375      IF( ln_rstart )      CALL rst_read_open 
    376376                           CALL day_init        ! model calendar (using both namelist and restart infos) 
    377       IF( ln_rstart )      CALL rst_read_open 
    378377 
    379378      !                                      ! external forcing  
  • NEMO/branches/2020/dev_12905_xios_restart/src/SAS/step.F90

    r12969 r12977  
    9595                                                          ! need to keep the same interface  
    9696      IF( kstp == nit000 )   CALL iom_init( cxios_context ) ! iom_put initialization (must be done after nemo_init for AGRIF+XIOS+OASIS) 
    97       IF( kstp /= nit000 )   CALL day( kstp )             ! Calendar (day was already called at nit000 in day_init) 
    9897                             CALL iom_setkt( kstp - nit000 + 1, cxios_context )   ! tell iom we are at time step kstp 
    9998      IF((kstp == nitrst) .AND. lwxios) THEN 
     
    107106#endif 
    108107      ENDIF 
     108      IF( kstp /= nit000 )   CALL day( kstp )             ! Calendar (day was already called at nit000 in day_init) 
     109 
    109110#if defined key_si3 
    110111      IF(((kstp + nn_fsbc - 1) == nitrst) .AND. lwxios) THEN 
     
    153154      ! File manipulation at the end of the first time step 
    154155      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<                          
    155       IF( kstp == nit000   ) CALL iom_close( numror )                          ! close input  ocean restart file 
     156      IF( kstp == nit000   ) THEN 
     157            CALL iom_close( numror )                          ! close input  ocean restart file 
     158            IF( lroxios )     CALL iom_context_finalize(      crxios_context      ) 
     159      ENDIF 
    156160       
    157161      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
Note: See TracChangeset for help on using the changeset viewer.