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 12957 for NEMO/branches/2020/dev_12905_xios_restart/src/OCE/IOM/iom.F90 – NEMO

Ignore:
Timestamp:
2020-05-20T18:53:27+02:00 (4 years ago)
Author:
andmirek
Message:

Ticket #2462: write/read SI3 restart with XIOS (has debug print statements)

File:
1 edited

Legend:

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

    r12951 r12957  
    114114      INTEGER             :: irefyear, irefmonth, irefday 
    115115      INTEGER           :: ji 
    116       LOGICAL :: llrst_context              ! is context related to restart 
     116      LOGICAL           :: llrst_context              ! is context related to restart 
     117      INTEGER           :: inum 
    117118      ! 
    118119      REAL(wp), ALLOCATABLE, DIMENSION(:,:) :: zt_bnds, zw_bnds 
     
    142143      ALLOCATE( zt_bnds(2,jpk), zw_bnds(2,jpk) ) 
    143144      ! 
     145      IF(lwp) write(numout, *) 'TEST IOM_INIT: ', TRIM(cdname),' File: ', TRIM(fname) 
     146      IF(lwp) CALL FLUSH(numout) 
    144147      clname = cdname 
    145148      IF( TRIM(Agrif_CFixed()) /= '0' )   clname = TRIM(Agrif_CFixed())//"_"//TRIM(cdname) 
    146149      CALL xios_context_initialize(TRIM(clname), mpi_comm_oce) 
    147150      CALL iom_swap( cdname ) 
    148       llrst_context =  (TRIM(cdname) == TRIM(crxios_context) .OR. TRIM(cdname) == TRIM(cwxios_context)) 
     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)) 
    149153 
    150154      ! Calendar type is now defined in xml file  
     
    260264      ! 
    261265      ! automatic definitions of some of the xml attributs 
    262       IF( TRIM(cdname) == TRIM(crxios_context) ) THEN 
    263 !set names of the fields in restart file IF using XIOS to read data 
     266      IF(lwp) write(numout, *) 'TEST IOM_INIT: ', TRIM(cdname), TRIM(cdname) == TRIM(crixios_context) 
     267      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  
     273          ELSE 
     274             CALL ctl_stop( 'iom_init:', 'restart read with XIOS: Unknown restart context' ) 
     275          ENDIF 
    264276          CALL iom_set_rst_context(.TRUE.) 
    265 !set which fields are to be read from restart file 
    266           CALL iom_set_rstr_active() 
    267       ELSE IF( TRIM(cdname) == TRIM(cwxios_context) ) THEN 
     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 
    268280          CALL iom_set_rstw_file(fname) 
    269281      ELSE 
     
    298310   CHARACTER(len=*), OPTIONAL, INTENT(IN) :: cdname 
    299311#if defined key_iomput 
    300       IF( TRIM(cdname) == TRIM(cwxios_context) ) THEN 
     312   LOGICAL :: llrstw 
     313 
     314      IF(lwp) write(numout, *) 'XIOS CLOSE definitions for: ', TRIM(cdname) 
     315      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 
     320      ENDIF 
     321 
     322      IF( llrstw ) THEN 
    301323!set names of the fields in restart file IF using XIOS to write data 
    302324          CALL iom_set_rst_context(.FALSE.) 
     
    305327      CALL xios_close_context_definition() 
    306328 
    307       IF(.NOT. (TRIM(cdname) == TRIM(cwxios_context)))  CALL xios_update_calendar( 0 ) 
     329      IF(.NOT. llrstw)  CALL xios_update_calendar( 0 ) 
    308330 
    309331#else 
     
    313335   END SUBROUTINE iom_init_closedef 
    314336 
    315    SUBROUTINE iom_set_rstr_active() 
     337   SUBROUTINE iom_set_rstr_active(cdfname, idnum) 
    316338      !!--------------------------------------------------------------------- 
    317339      !!                   ***  SUBROUTINE  iom_set_rstr_active  *** 
     
    322344 
    323345!sets enabled = .TRUE. for each field in restart file 
    324    CHARACTER(len=256) :: rst_file 
     346   CHARACTER(len=*), INTENT(IN) :: cdfname 
     347   INTEGER         , INTENT(IN) :: idnum  
    325348#if defined key_iomput 
    326349   INTEGER                                    :: ndims, nvars, natts, unlimitedDimId, dimlen, xtype,mdims 
     
    329352   TYPE(xios_filegroup)                       :: filegroup_hdl 
    330353   INTEGER                                    :: dimids(4), jv,i, idim 
    331    CHARACTER(LEN=lc)                          :: clpath 
    332354   CHARACTER(LEN=256)                         :: clinfo               ! info character 
    333355   INTEGER, ALLOCATABLE                       :: indimlens(:) 
     
    353375        meta(10) = "numcat" 
    354376 
    355         clpath = TRIM(cn_ocerst_indir) 
    356         IF( clpath(LEN_TRIM(clpath):) /= '/' ) clpath = TRIM(clpath) // '/' 
    357         IF( TRIM(Agrif_CFixed()) == '0' ) THEN 
    358            rst_file = TRIM(clpath)//TRIM(cn_ocerst_in) 
    359         ELSE 
    360            rst_file = TRIM(clpath)//TRIM(Agrif_CFixed())//'_'//TRIM(cn_ocerst_in) 
    361         ENDIF 
    362  
    363         clinfo = '          iom_set_rstr_active, file: '//TRIM(rst_file) 
    364  
     377        clinfo = '          iom_set_rstr_active, file: '//TRIM(cdfname) 
     378 
     379        IF(lwp) write(numout, *) TRIM(clinfo) 
     380        IF(lwp) CALL FLUSH(numout) 
    365381!set name of the restart file and enable available fields 
    366382        CALL xios_get_handle("file_definition", filegroup_hdl ) 
    367383        CALL xios_add_child(filegroup_hdl, file_hdl, 'rrestart') 
    368         CALL xios_set_file_attr( "rrestart", name=trim(rst_file), type="one_file", & 
     384        CALL xios_set_file_attr( "rrestart", name=trim(cdfname), type="one_file", & 
    369385             par_access="collective", enabled=.TRUE., mode="read",                 & 
    370386             output_freq=xios_timestep) 
    371387 
    372         CALL iom_nf90_check( nf90_inquire( iom_file(numror)%nfid, ndims, nvars, natts ), clinfo ) 
     388        CALL iom_nf90_check( nf90_inquire( iom_file(idnum)%nfid, ndims, nvars, natts ), clinfo ) 
    373389        ALLOCATE(indimlens(ndims), indimnames(ndims)) 
    374         CALL iom_nf90_check( nf90_inquire( iom_file(numror)%nfid, unlimitedDimId = unlimitedDimId ), clinfo ) 
     390        CALL iom_nf90_check( nf90_inquire( iom_file(idnum)%nfid, unlimitedDimId = unlimitedDimId ), clinfo ) 
    375391 
    376392        DO idim = 1, ndims 
    377            CALL iom_nf90_check( nf90_inquire_dimension( iom_file(numror)%nfid, idim, dimname, dimlen ), clinfo ) 
     393           CALL iom_nf90_check( nf90_inquire_dimension( iom_file(idnum)%nfid, idim, dimname, dimlen ), clinfo ) 
    378394           indimlens(idim) = dimlen 
    379395           indimnames(idim) = dimname 
     
    382398        DO jv =1, nvars 
    383399            lmeta = .FALSE. 
    384             CALL iom_nf90_check( nf90_inquire_variable( iom_file(numror)%nfid, jv, varname, xtype, ndims, dimids, natts ), clinfo ) 
     400            CALL iom_nf90_check( nf90_inquire_variable( iom_file(idnum)%nfid, jv, varname, xtype, ndims, dimids, natts ), clinfo ) 
    385401            DO i = 1, NMETA 
    386402               IF(TRIM(varname) == TRIM(meta(i))) THEN 
     
    390406            IF(.NOT.lmeta) THEN 
    391407               CALL xios_add_child(file_hdl, field_hdl, TRIM(varname)) 
     408               if(lwp) write(numout, *) 'ADD field: ', TRIM(varname) 
     409               IF(lwp) CALL FLUSH(numout) 
    392410               mdims = ndims 
    393411 
     
    397415 
    398416               IF(mdims == 3) THEN 
     417                      if(lwp) write(numout, *) '3D', indimlens(ndims) 
     418                      IF(lwp) CALL FLUSH(numout) 
     419 
    399420                      CALL xios_set_attr (field_hdl, enabled = .TRUE., name = TRIM(varname),   & 
    400421                                   domain_ref="grid_N", axis_ref=TRIM(iom_axis(indimlens(ndims))), & 
    401422                                   prec = 8, operation = "instant") 
    402423               ELSEIF(mdims == 2) THEN 
     424                      if(lwp) write(numout, *) '2D' 
     425                      IF(lwp) CALL FLUSH(numout) 
     426 
    403427                      CALL xios_set_attr (field_hdl, enabled = .TRUE., name = TRIM(varname), & 
    404428                                          domain_ref="grid_N", prec = 8, operation = "instant")  
    405429               ELSEIF(mdims == 1) THEN 
     430                      if(lwp) write(numout, *) '1D', indimlens(ndims) 
     431                      IF(lwp) CALL FLUSH(numout) 
     432 
    406433                      CALL xios_set_attr (field_hdl, enabled = .TRUE., name = TRIM(varname), & 
    407434                                          axis_ref=TRIM(iom_axis(indimlens(ndims))), prec = 8, operation = "instant") 
    408435               ELSEIF(mdims == 0) THEN 
     436                      if(lwp) write(numout, *) '0D' 
     437                      IF(lwp) CALL FLUSH(numout) 
     438 
    409439                      CALL xios_set_attr (field_hdl, enabled = .TRUE., name = TRIM(varname), & 
    410440                                                scalar_ref = "grid_scalar", prec = 8, operation = "instant") 
    411441               ELSE 
    412                    WRITE(ctmp1,*) 'iom_set_rstr_active: variable ', TRIM(varname) ,' incorrect number of dimensions'  
    413                    CALL ctl_stop( 'iom_set_rstr_active:', ctmp1 ) 
     442                      if(lwp) write(numout, *) 'WAHT?' 
     443                      IF(lwp) CALL FLUSH(numout) 
     444 
     445                      WRITE(ctmp1,*) 'iom_set_rstr_active: variable ', TRIM(varname) ,' incorrect number of dimensions'  
     446                      CALL ctl_stop( 'iom_set_rstr_active:', ctmp1 ) 
    414447               ENDIF 
    415448            ENDIF 
     
    434467!set name of the restart file and enable available fields 
    435468        IF(lwp) WRITE(numout,*) 'Setting restart filename (for XIOS write) to: ',cdrst_file 
     469        IF(lwp) CALL FLUSH(numout) 
    436470        CALL xios_get_handle("file_definition", filegroup_hdl ) 
    437471        CALL xios_add_child(filegroup_hdl, file_hdl, 'wrestart') 
     
    18691903      !!---------------------------------------------------------------------- 
    18701904      clname = cdname 
     1905      IF(lwp) write(numout, *) 'Finalize: ', TRIM(cdname) 
    18711906      IF( TRIM(Agrif_CFixed()) .NE. '0' ) clname = TRIM(Agrif_CFixed())//"_"//clname  
    18721907      IF( xios_is_valid_context(clname) ) THEN 
Note: See TracChangeset for help on using the changeset viewer.