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 12961 for NEMO/branches/2020/dev_12905_xios_restart/src/OCE/IOM – NEMO

Ignore:
Timestamp:
2020-05-22T13:51:12+02:00 (4 years ago)
Author:
andmirek
Message:

Ticket #2462: read/write restart with XIOS in TOP (with debug print statements)

Location:
NEMO/branches/2020/dev_12905_xios_restart/src/OCE/IOM
Files:
4 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2020/dev_12905_xios_restart/src/OCE/IOM/in_out_manager.F90

    r12957 r12961  
    177177   LOGICAL       ::   lwp      = .FALSE.    !: boolean : true on the 1st processor only .OR. sn_cfctl%l_oceout=T 
    178178   LOGICAL       ::   lsp_area = .TRUE.     !: to make a control print over a specific area 
    179    CHARACTER(lc) ::   cxios_context         !: context name used in xios 
    180    CHARACTER(lc) ::   crxios_context        !: context name used in xios to read restart 
    181    CHARACTER(lc) ::   cwxios_context        !: context name used in xios to write restart file 
    182    CHARACTER(lc) ::   crixios_context       !: context name used in xios to read SI3 restart 
    183    CHARACTER(lc) ::   cwixios_context       !: context name used in xios to write SI3 restart file 
     179   CHARACTER(LEN=lc) ::   cxios_context         !: context name used in xios 
     180   CHARACTER(LEN=lc) ::   crxios_context        !: context name used in xios to read OCE restart 
     181   CHARACTER(LEN=lc) ::   cwxios_context        !: context name used in xios to write OCE restart file 
     182   CHARACTER(LEN=lc) ::   crixios_context       !: context name used in xios to read SI3 restart 
     183   CHARACTER(LEN=lc) ::   cwixios_context       !: context name used in xios to write SI3 restart file 
     184   CHARACTER(LEN=lc) ::   crtxios_context       !: context name used in xios to read TOP restart 
     185   CHARACTER(LEN=lc) ::   cwtxios_context       !: context name used in xios to write TOP restart file 
     186   CHARACTER(LEN=lc) ::   crsxios_context       !: context name used in xios to read SEDIMENT restart 
     187   CHARACTER(LEN=lc) ::   cwsxios_context       !: context name used in xios to write SEDIMENT restart file 
     188 
     189 
    184190 
    185191 
  • NEMO/branches/2020/dev_12905_xios_restart/src/OCE/IOM/iom.F90

    r12957 r12961  
    9696CONTAINS 
    9797 
    98    SUBROUTINE iom_init( cdname, fname, ld_tmppatch, ld_closedef )  
     98   SUBROUTINE iom_init( cdname, fname, idfp, ld_tmppatch, ld_closedef )  
    9999      !!---------------------------------------------------------------------- 
    100100      !!                     ***  ROUTINE   *** 
     
    105105      CHARACTER(len=*),           INTENT(in)  :: cdname 
    106106      CHARACTER(len=*), OPTIONAL, INTENT(in)  :: fname 
     107      INTEGER         , OPTIONAL, INTENT(in)  :: idfp         ! pointer to netcdf file for restart reading with XIOS 
    107108      LOGICAL         , OPTIONAL, INTENT(in)  :: ld_tmppatch 
    108109      LOGICAL         , OPTIONAL, INTENT(in)  :: ld_closedef 
     
    115116      INTEGER           :: ji 
    116117      LOGICAL           :: llrst_context              ! is context related to restart 
     118      LOGICAL           :: llrstr, llrstw  
    117119      INTEGER           :: inum 
    118120      ! 
     
    149151      CALL xios_context_initialize(TRIM(clname), mpi_comm_oce) 
    150152      CALL iom_swap( cdname ) 
    151       llrst_context = (TRIM(cdname) == TRIM(crxios_context)) .OR. (TRIM(cdname) == TRIM(cwxios_context)) 
    152       llrst_context = llrst_context .OR. (TRIM(cdname) == TRIM(crixios_context)) .OR. (TRIM(cdname) == TRIM(cwixios_context)) 
     153 
     154      llrstr = (TRIM(cdname) == TRIM(crxios_context)) .OR. (TRIM(cdname) == TRIM(crixios_context)) 
     155      llrstr = llrstr .OR. (TRIM(cdname) == TRIM(crtxios_context)) 
     156      llrstr = llrstr .OR. (TRIM(cdname) == TRIM(crsxios_context)) 
     157 
     158      llrstw = (TRIM(cdname) == TRIM(cwxios_context)) .OR. (TRIM(cdname) == TRIM(cwixios_context)) 
     159      llrstw = llrstw .OR. (TRIM(cdname) == TRIM(cwtxios_context)) 
     160      llrstw = llrstw .OR. (TRIM(cdname) == TRIM(cwsxios_context)) 
     161 
     162      llrst_context = llrstr .OR. llrstw 
    153163 
    154164      ! Calendar type is now defined in xml file  
     
    266276      IF(lwp) write(numout, *) 'TEST IOM_INIT: ', TRIM(cdname), TRIM(cdname) == TRIM(crixios_context) 
    267277      IF(lwp) CALL FLUSH(numout) 
    268       IF( TRIM(cdname) == TRIM(crxios_context) .OR. TRIM(cdname) == TRIM(crixios_context)) THEN 
    269           IF(TRIM(cdname) == TRIM(crxios_context) ) THEN 
    270              inum = numror 
    271           ELSEIF(TRIM(cdname) == TRIM(crixios_context)) THEN 
    272              inum = numrir  
     278      IF(llrstr) THEN 
     279          IF(PRESENT(idfp)) THEN 
     280             CALL iom_set_rst_context(.TRUE.) 
     281!set which fields will be read from restart file 
     282             CALL iom_set_rstr_active(fname, idfp) 
    273283          ELSE 
    274              CALL ctl_stop( 'iom_init:', 'restart read with XIOS: Unknown restart context' ) 
     284             CALL ctl_stop( 'iom_init:', 'restart read with XIOS: missing pointer to NETCDF file' ) 
    275285          ENDIF 
    276           CALL iom_set_rst_context(.TRUE.) 
    277 !set which fields will be read from restart file 
    278           CALL iom_set_rstr_active(fname, inum) 
    279       ELSE IF( (TRIM(cdname) == TRIM(cwxios_context)) .OR. (TRIM(cdname) == TRIM(cwixios_context))) THEN 
     286      ELSE IF(llrstw) THEN 
    280287          CALL iom_set_rstw_file(fname) 
    281288      ELSE 
     
    314321      IF(lwp) write(numout, *) 'XIOS CLOSE definitions for: ', TRIM(cdname) 
    315322      llrstw = .FALSE. 
    316      IF(PRESENT(cdname)) THEN 
    317          IF((TRIM(cdname) == TRIM(cwxios_context)) .OR. (TRIM(cdname) == TRIM(cwixios_context))) THEN 
    318            llrstw = .TRUE. 
    319          ENDIF 
     323      IF(PRESENT(cdname)) THEN 
     324         llrstw = (TRIM(cdname) == TRIM(cwxios_context)) 
     325         llrstw = llrstw .OR. (TRIM(cdname) == TRIM(cwixios_context)) 
     326         llrstw = llrstw .OR. (TRIM(cdname) == TRIM(cwtxios_context)) 
     327         llrstw = llrstw .OR. (TRIM(cdname) == TRIM(cwsxios_context)) 
    320328      ENDIF 
    321329 
     
    323331!set names of the fields in restart file IF using XIOS to write data 
    324332          CALL iom_set_rst_context(.FALSE.) 
    325       ENDIF 
    326  
    327       CALL xios_close_context_definition() 
    328  
    329       IF(.NOT. llrstw)  CALL xios_update_calendar( 0 ) 
    330  
     333          CALL xios_close_context_definition() 
     334      ELSE 
     335          CALL xios_close_context_definition() 
     336          CALL xios_update_calendar( 0 ) 
     337      ENDIF 
    331338#else 
    332339      IF( .FALSE. )   WRITE(numout,*) 'iom_init_closedef: should not see this'   ! useless statement to avoid compilation warnings 
     
    386393             output_freq=xios_timestep) 
    387394 
    388         CALL iom_nf90_check( nf90_inquire( iom_file(idnum)%nfid, ndims, nvars, natts ), clinfo ) 
     395        CALL iom_nf90_check( nf90_inquire(idnum, ndims, nvars, natts ), clinfo ) 
    389396        ALLOCATE(indimlens(ndims), indimnames(ndims)) 
    390         CALL iom_nf90_check( nf90_inquire( iom_file(idnum)%nfid, unlimitedDimId = unlimitedDimId ), clinfo ) 
     397        CALL iom_nf90_check( nf90_inquire(idnum, unlimitedDimId = unlimitedDimId ), clinfo ) 
    391398 
    392399        DO idim = 1, ndims 
    393            CALL iom_nf90_check( nf90_inquire_dimension( iom_file(idnum)%nfid, idim, dimname, dimlen ), clinfo ) 
     400           CALL iom_nf90_check( nf90_inquire_dimension(idnum, idim, dimname, dimlen ), clinfo ) 
    394401           indimlens(idim) = dimlen 
    395402           indimnames(idim) = dimname 
     
    398405        DO jv =1, nvars 
    399406            lmeta = .FALSE. 
    400             CALL iom_nf90_check( nf90_inquire_variable( iom_file(idnum)%nfid, jv, varname, xtype, ndims, dimids, natts ), clinfo ) 
     407            CALL iom_nf90_check( nf90_inquire_variable(idnum, jv, varname, xtype, ndims, dimids, natts ), clinfo ) 
    401408            DO i = 1, NMETA 
    402409               IF(TRIM(varname) == TRIM(meta(i))) THEN 
     
    510517 
    511518        IF(PRESENT(rd3)) THEN 
     519               IF(lwp) write(numout, *) TRIM(sdfield), ' 3D ', size(rd3,3) 
     520               IF(lwp) CALL FLUSH(numout) 
    512521               CALL xios_set_attr (field_hdl, enabled = .TRUE., name = TRIM(sdfield),   & 
    513522                            domain_ref="grid_N", axis_ref=TRIM(iom_axis(size(rd3, 3))), & 
     
    516525 
    517526        IF(PRESENT(rd2)) THEN 
     527               IF(lwp) write(numout, *) TRIM(sdfield), ' 2D' 
     528               IF(lwp) CALL FLUSH(numout) 
    518529               CALL xios_set_attr (field_hdl, enabled = .TRUE., name = TRIM(sdfield), & 
    519530                                   domain_ref="grid_N", prec = 8, operation = "instant")  
     
    521532 
    522533        IF(PRESENT(rd1)) THEN 
     534               IF(lwp) write(numout, *) TRIM(sdfield), ' 1D ', size(rd1,1) 
     535               IF(lwp) CALL FLUSH(numout) 
    523536               CALL xios_set_attr (field_hdl, enabled = .TRUE., name = TRIM(sdfield), & 
    524537                                   axis_ref=TRIM(iom_axis(size(rd1, 1))), prec = 8, operation = "instant") 
     
    526539 
    527540        IF(PRESENT(rd0)) THEN 
     541               IF(lwp) write(numout, *) TRIM(sdfield), ' 0D' 
     542               IF(lwp) CALL FLUSH(numout) 
    528543               CALL xios_set_attr (field_hdl, enabled = .TRUE., name = TRIM(sdfield), & 
    529544                                         scalar_ref = "grid_scalar", prec = 8, operation = "instant") 
     
    603618#if defined key_iomput 
    604619      TYPE(xios_context) :: nemo_hdl 
    605  
     620      IF(lwp) write(numout, *) 'SWAP TO: ', TRIM(cdname),' AGRIF: ', TRIM(Agrif_CFixed()) 
    606621      IF( TRIM(Agrif_CFixed()) == '0' ) THEN 
    607622        CALL xios_get_handle(TRIM(cdname),nemo_hdl) 
  • NEMO/branches/2020/dev_12905_xios_restart/src/OCE/IOM/iom_def.F90

    r12950 r12961  
    4545   LOGICAL, PUBLIC            ::   lrxios          !: read single file restart using XIOS 
    4646   LOGICAL, PUBLIC            ::   lxios_sini = .FALSE. ! is restart in a single file 
    47    LOGICAL, PUBLIC            ::   lxios_set  = .FALSE.  
    4847 
    4948 
  • NEMO/branches/2020/dev_12905_xios_restart/src/OCE/IOM/restart.F90

    r12957 r12961  
    116116                  clpname = TRIM(Agrif_CFixed())//"_"//clname    
    117117               ENDIF 
    118                CALL iom_init( cwxios_context, TRIM(clpath)//TRIM(clpname), .false., ld_closedef = .FALSE. ) 
     118               CALL iom_init( cwxios_context, TRIM(clpath)//TRIM(clpname), ld_tmppatch = .false.,& 
     119                                                                           ld_closedef = .FALSE. ) 
    119120               CALL iom_swap(      cxios_context          ) 
    120121#else 
     
    190191      !!                the file has already been opened 
    191192      !!---------------------------------------------------------------------- 
    192       LOGICAL         ::   llok 
    193       CHARACTER(lc)   ::   clpath   ! full path to ocean output restart file 
    194       CHARACTER(lc+2) ::   clpname  ! file name including agrif prefix 
     193      LOGICAL             ::   llok 
     194      CHARACTER(len=lc)   ::   clpath   ! full path to ocean output restart file 
     195      CHARACTER(len=lc+2) ::   clpname  ! file name including agrif prefix 
    195196      !!---------------------------------------------------------------------- 
    196197      ! 
     
    209210! can handle checking if variable is in the restart file (there will be no need to open 
    210211! restart) 
    211          IF(.NOT.lxios_set) lrxios = lrxios.AND.lxios_sini 
     212         lrxios = lrxios.AND.lxios_sini 
    212213 
    213214         IF( lrxios) THEN 
    214215             crxios_context = 'oce_rst' 
    215              IF( .NOT.lxios_set ) THEN 
    216                  IF(lwp) WRITE(numout,*) 'Enable restart reading by XIOS' 
    217                  IF( TRIM(Agrif_CFixed()) == '0' ) THEN 
    218                     clpname = cn_ocerst_in 
    219                  ELSE 
    220                     clpname = TRIM(Agrif_CFixed())//"_"//cn_ocerst_in    
    221                  ENDIF 
    222                  CALL iom_init( crxios_context, fname = TRIM(clpath)//TRIM(clpname), ld_tmppatch = .TRUE. ) 
    223                  lxios_set = .TRUE. 
     216             IF(lwp) WRITE(numout,*) 'Enable restart reading by XIOS' 
     217             IF( TRIM(Agrif_CFixed()) == '0' ) THEN 
     218                clpname = cn_ocerst_in 
     219             ELSE 
     220                clpname = TRIM(Agrif_CFixed())//"_"//cn_ocerst_in    
    224221             ENDIF 
     222             CALL iom_init( crxios_context, fname = TRIM(clpath)//TRIM(clpname), & 
     223                              idfp = iom_file(numror)%nfid, ld_tmppatch = .TRUE. ) 
    225224         ENDIF 
    226225 
Note: See TracChangeset for help on using the changeset viewer.