Changeset 12961
- Timestamp:
- 2020-05-22T13:51:12+02:00 (5 years ago)
- Location:
- NEMO/branches/2020/dev_12905_xios_restart/src
- Files:
-
- 17 edited
Legend:
- Unmodified
- Added
- Removed
-
NEMO/branches/2020/dev_12905_xios_restart/src/ICE/icerst.F90
r12957 r12961 91 91 clpname = TRIM(Agrif_CFixed())//"_"//clname 92 92 ENDIF 93 CALL iom_init( cwixios_context, TRIM(clpath)//TRIM(clpname), .false., ld_closedef = .FALSE. ) 93 CALL iom_init( cwixios_context, TRIM(clpath)//TRIM(clpname), ld_tmppatch = .false.,& 94 ld_closedef = .FALSE. ) 94 95 CALL iom_swap( cxios_context ) 95 96 #else … … 223 224 clpname = TRIM(Agrif_CFixed())//"_"//cn_icerst_in 224 225 ENDIF 225 CALL iom_init( crixios_context, fname = TRIM(cn_icerst_indir)//'/'//TRIM(clpname), ld_tmppatch = .TRUE. ) 226 CALL iom_init( crixios_context, fname = TRIM(cn_icerst_indir)//'/'//TRIM(clpname), & 227 idfp = iom_file(numrir)%nfid, ld_tmppatch = .TRUE. ) 226 228 ENDIF 227 229 -
NEMO/branches/2020/dev_12905_xios_restart/src/ICE/icestp.F90
r12489 r12961 280 280 END WHERE 281 281 282 IF( ln_rstart ) CALL iom_close( numrir ) ! close input ice restart file 282 IF( ln_rstart ) THEN 283 CALL iom_close( numrir ) ! close input ice restart file 284 IF(lrxios) CALL iom_context_finalize( crixios_context ) 285 ENDIF 283 286 ! 284 287 END SUBROUTINE ice_init -
NEMO/branches/2020/dev_12905_xios_restart/src/OCE/IOM/in_out_manager.F90
r12957 r12961 177 177 LOGICAL :: lwp = .FALSE. !: boolean : true on the 1st processor only .OR. sn_cfctl%l_oceout=T 178 178 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 184 190 185 191 -
NEMO/branches/2020/dev_12905_xios_restart/src/OCE/IOM/iom.F90
r12957 r12961 96 96 CONTAINS 97 97 98 SUBROUTINE iom_init( cdname, fname, ld_tmppatch, ld_closedef )98 SUBROUTINE iom_init( cdname, fname, idfp, ld_tmppatch, ld_closedef ) 99 99 !!---------------------------------------------------------------------- 100 100 !! *** ROUTINE *** … … 105 105 CHARACTER(len=*), INTENT(in) :: cdname 106 106 CHARACTER(len=*), OPTIONAL, INTENT(in) :: fname 107 INTEGER , OPTIONAL, INTENT(in) :: idfp ! pointer to netcdf file for restart reading with XIOS 107 108 LOGICAL , OPTIONAL, INTENT(in) :: ld_tmppatch 108 109 LOGICAL , OPTIONAL, INTENT(in) :: ld_closedef … … 115 116 INTEGER :: ji 116 117 LOGICAL :: llrst_context ! is context related to restart 118 LOGICAL :: llrstr, llrstw 117 119 INTEGER :: inum 118 120 ! … … 149 151 CALL xios_context_initialize(TRIM(clname), mpi_comm_oce) 150 152 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 153 163 154 164 ! Calendar type is now defined in xml file … … 266 276 IF(lwp) write(numout, *) 'TEST IOM_INIT: ', TRIM(cdname), TRIM(cdname) == TRIM(crixios_context) 267 277 IF(lwp) CALL FLUSH(numout) 268 IF( TRIM(cdname) == TRIM(crxios_context) .OR. TRIM(cdname) == TRIM(crixios_context)) THEN269 IF( TRIM(cdname) == TRIM(crxios_context)) THEN270 inum = numror271 ELSEIF(TRIM(cdname) == TRIM(crixios_context)) THEN 272 inum = numrir278 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) 273 283 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' ) 275 285 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 280 287 CALL iom_set_rstw_file(fname) 281 288 ELSE … … 314 321 IF(lwp) write(numout, *) 'XIOS CLOSE definitions for: ', TRIM(cdname) 315 322 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)) 320 328 ENDIF 321 329 … … 323 331 !set names of the fields in restart file IF using XIOS to write data 324 332 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 331 338 #else 332 339 IF( .FALSE. ) WRITE(numout,*) 'iom_init_closedef: should not see this' ! useless statement to avoid compilation warnings … … 386 393 output_freq=xios_timestep) 387 394 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 ) 389 396 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 ) 391 398 392 399 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 ) 394 401 indimlens(idim) = dimlen 395 402 indimnames(idim) = dimname … … 398 405 DO jv =1, nvars 399 406 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 ) 401 408 DO i = 1, NMETA 402 409 IF(TRIM(varname) == TRIM(meta(i))) THEN … … 510 517 511 518 IF(PRESENT(rd3)) THEN 519 IF(lwp) write(numout, *) TRIM(sdfield), ' 3D ', size(rd3,3) 520 IF(lwp) CALL FLUSH(numout) 512 521 CALL xios_set_attr (field_hdl, enabled = .TRUE., name = TRIM(sdfield), & 513 522 domain_ref="grid_N", axis_ref=TRIM(iom_axis(size(rd3, 3))), & … … 516 525 517 526 IF(PRESENT(rd2)) THEN 527 IF(lwp) write(numout, *) TRIM(sdfield), ' 2D' 528 IF(lwp) CALL FLUSH(numout) 518 529 CALL xios_set_attr (field_hdl, enabled = .TRUE., name = TRIM(sdfield), & 519 530 domain_ref="grid_N", prec = 8, operation = "instant") … … 521 532 522 533 IF(PRESENT(rd1)) THEN 534 IF(lwp) write(numout, *) TRIM(sdfield), ' 1D ', size(rd1,1) 535 IF(lwp) CALL FLUSH(numout) 523 536 CALL xios_set_attr (field_hdl, enabled = .TRUE., name = TRIM(sdfield), & 524 537 axis_ref=TRIM(iom_axis(size(rd1, 1))), prec = 8, operation = "instant") … … 526 539 527 540 IF(PRESENT(rd0)) THEN 541 IF(lwp) write(numout, *) TRIM(sdfield), ' 0D' 542 IF(lwp) CALL FLUSH(numout) 528 543 CALL xios_set_attr (field_hdl, enabled = .TRUE., name = TRIM(sdfield), & 529 544 scalar_ref = "grid_scalar", prec = 8, operation = "instant") … … 603 618 #if defined key_iomput 604 619 TYPE(xios_context) :: nemo_hdl 605 620 IF(lwp) write(numout, *) 'SWAP TO: ', TRIM(cdname),' AGRIF: ', TRIM(Agrif_CFixed()) 606 621 IF( TRIM(Agrif_CFixed()) == '0' ) THEN 607 622 CALL xios_get_handle(TRIM(cdname),nemo_hdl) -
NEMO/branches/2020/dev_12905_xios_restart/src/OCE/IOM/iom_def.F90
r12950 r12961 45 45 LOGICAL, PUBLIC :: lrxios !: read single file restart using XIOS 46 46 LOGICAL, PUBLIC :: lxios_sini = .FALSE. ! is restart in a single file 47 LOGICAL, PUBLIC :: lxios_set = .FALSE.48 47 49 48 -
NEMO/branches/2020/dev_12905_xios_restart/src/OCE/IOM/restart.F90
r12957 r12961 116 116 clpname = TRIM(Agrif_CFixed())//"_"//clname 117 117 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. ) 119 120 CALL iom_swap( cxios_context ) 120 121 #else … … 190 191 !! the file has already been opened 191 192 !!---------------------------------------------------------------------- 192 LOGICAL :: llok193 CHARACTER(l c) :: clpath ! full path to ocean output restart file194 CHARACTER(l c+2) :: clpname ! file name including agrif prefix193 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 195 196 !!---------------------------------------------------------------------- 196 197 ! … … 209 210 ! can handle checking if variable is in the restart file (there will be no need to open 210 211 ! restart) 211 IF(.NOT.lxios_set)lrxios = lrxios.AND.lxios_sini212 lrxios = lrxios.AND.lxios_sini 212 213 213 214 IF( lrxios) THEN 214 215 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 224 221 ENDIF 222 CALL iom_init( crxios_context, fname = TRIM(clpath)//TRIM(clpname), & 223 idfp = iom_file(numror)%nfid, ld_tmppatch = .TRUE. ) 225 224 ENDIF 226 225 -
NEMO/branches/2020/dev_12905_xios_restart/src/OCE/step.F90
r12957 r12961 127 127 CALL iom_init_closedef(cwxios_context) 128 128 CALL iom_setkt( kstp - nit000 + 1, cwxios_context ) 129 #if defined key_top 130 CALL iom_swap( cwtxios_context ) 131 CALL iom_init_closedef(cwtxios_context) 132 CALL iom_setkt( kstp - nit000 + 1, cwtxios_context ) 133 #endif 129 134 ENDIF 130 135 #if defined key_si3 … … 346 351 IF( kstp == nit000 ) THEN ! 1st time step only 347 352 CALL iom_close( numror ) ! close input ocean restart file 353 IF( lrxios ) CALL iom_context_finalize( crxios_context ) 348 354 IF(lwm) CALL FLUSH ( numond ) ! flush output namelist oce 349 355 IF(lwm .AND. numoni /= -1 ) CALL FLUSH ( numoni ) ! flush output namelist ice (if exist) … … 362 368 IF( kstp == nitend .OR. indic < 0 ) THEN 363 369 CALL iom_context_finalize( cxios_context ) ! needed for XIOS+AGRIF 364 IF( lrxios ) THEN365 CALL iom_context_finalize( crxios_context )366 #if defined key_si3367 CALL iom_context_finalize( crixios_context )368 #endif369 ENDIF370 370 IF( ln_crs ) CALL iom_context_finalize( trim(cxios_context)//"_crs" ) ! 371 371 ENDIF -
NEMO/branches/2020/dev_12905_xios_restart/src/TOP/C14/trcini_c14.F90
r12377 r12961 68 68 IF(lwp) WRITE(numout,*) ' ~~~~~~~~~~~~~~' 69 69 ! 70 CALL iom_get( numrtr, 'co2sbc', co2sbc ) 71 CALL iom_get( numrtr, jpdom_autoglo, 'c14sbc', c14sbc ) 72 CALL iom_get( numrtr, jpdom_autoglo, 'exch_co2', exch_co2 ) 73 CALL iom_get( numrtr, jpdom_autoglo, 'exch_c14', exch_c14 ) 74 CALL iom_get( numrtr, jpdom_autoglo, 'qtr_c14', qtr_c14 ) 70 IF(lrxios) CALL iom_swap(crtxios_context) 71 CALL iom_get( numrtr, 'co2sbc', co2sbc, ldxios = lrxios ) 72 CALL iom_get( numrtr, jpdom_autoglo, 'c14sbc', c14sbc, ldxios = lrxios ) 73 CALL iom_get( numrtr, jpdom_autoglo, 'exch_co2', exch_co2, ldxios = lrxios ) 74 CALL iom_get( numrtr, jpdom_autoglo, 'exch_c14', exch_c14, ldxios = lrxios ) 75 CALL iom_get( numrtr, jpdom_autoglo, 'qtr_c14', qtr_c14, ldxios = lrxios ) 76 IF(lrxios) CALL iom_swap(cxios_context) 75 77 ! 76 78 END IF … … 85 87 ELSE 86 88 ! 87 CALL iom_get( numrtr, jpdom_autoglo, 'qint_c14', qint_c14 ) 89 IF(lrxios) CALL iom_swap(crtxios_context) 90 CALL iom_get( numrtr, jpdom_autoglo, 'qint_c14', qint_c14, ldxios = lrxios ) 91 IF(lrxios) CALL iom_swap(cxios_context) 88 92 ! 89 93 ENDIF -
NEMO/branches/2020/dev_12905_xios_restart/src/TOP/C14/trcsms_c14.F90
r12489 r12961 143 143 IF(lwp) WRITE(numout,*) ' ~~~~~~~~~~~~~~' 144 144 ! 145 CALL iom_rstput( kt, nitrst, numrtw, 'co2sbc', co2sbc ) ! These five need & 146 CALL iom_rstput( kt, nitrst, numrtw, 'c14sbc', c14sbc ) ! & to be written & 147 CALL iom_rstput( kt, nitrst, numrtw, 'exch_co2', exch_co2 ) ! & for temporal & 148 CALL iom_rstput( kt, nitrst, numrtw, 'exch_c14', exch_c14 ) ! & averages & 149 CALL iom_rstput( kt, nitrst, numrtw, 'qtr_c14', qtr_c14 ) ! & to be coherent. 150 CALL iom_rstput( kt, nitrst, numrtw, 'qint_c14', qint_c14 ) ! Cumulative 145 IF( lwxios ) CALL iom_swap( cwtxios_context ) 146 CALL iom_rstput( kt, nitrst, numrtw, 'co2sbc', co2sbc, ldxios = lwxios ) ! These five need & 147 CALL iom_rstput( kt, nitrst, numrtw, 'c14sbc', c14sbc, ldxios = lwxios ) ! & to be written & 148 CALL iom_rstput( kt, nitrst, numrtw, 'exch_co2', exch_co2, ldxios = lwxios ) ! & for temporal & 149 CALL iom_rstput( kt, nitrst, numrtw, 'exch_c14', exch_c14, ldxios = lwxios ) ! & averages & 150 CALL iom_rstput( kt, nitrst, numrtw, 'qtr_c14', qtr_c14, ldxios = lwxios ) ! & to be coherent. 151 CALL iom_rstput( kt, nitrst, numrtw, 'qint_c14', qint_c14, ldxios = lwxios ) ! Cumulative 152 IF( lwxios ) CALL iom_swap( cxios_context ) 151 153 ! 152 154 ENDIF -
NEMO/branches/2020/dev_12905_xios_restart/src/TOP/CFC/trcsms_cfc.F90
r12489 r12961 178 178 IF(lwp) WRITE(numout,*) '~~~~' 179 179 jl = 0 180 IF( lwxios ) CALL iom_swap( cwtxios_context ) 180 181 DO jn = jp_cfc0, jp_cfc1 181 182 jl = jl + 1 182 CALL iom_rstput( kt, nitrst, numrtw, 'qint_'//ctrcnm(jn), qint_cfc(:,:,jl) )183 CALL iom_rstput( kt, nitrst, numrtw, 'qint_'//ctrcnm(jn), qint_cfc(:,:,jl), ldxios = lwxios ) 183 184 END DO 185 IF( lwxios ) CALL iom_swap( cxios_context ) 184 186 ENDIF 185 187 ! … … 295 297 ! 296 298 jl = 0 299 IF(lrxios) CALL iom_swap(crtxios_context) 297 300 DO jn = jp_cfc0, jp_cfc1 298 301 jl = jl + 1 299 CALL iom_get( numrtr, jpdom_autoglo, 'qint_'//ctrcnm(jn), qint_cfc(:,:,jl) )302 CALL iom_get( numrtr, jpdom_autoglo, 'qint_'//ctrcnm(jn), qint_cfc(:,:,jl), ldxios = lrxios ) 300 303 END DO 304 IF(lrxios) CALL iom_swap(cxios_context) 301 305 ENDIF 302 306 IF(lwp) WRITE(numout,*) -
NEMO/branches/2020/dev_12905_xios_restart/src/TOP/PISCES/P2Z/p2zexp.F90
r12489 r12961 133 133 & 'at it= ', kt,' date= ', ndastp 134 134 IF(lwp) WRITE(numout,*) '~~~~' 135 CALL iom_rstput( kt, nitrst, numrtw, 'SEDB'//ctrcnm(jpdet), sedpocb(:,:) ) 136 CALL iom_rstput( kt, nitrst, numrtw, 'SEDN'//ctrcnm(jpdet), sedpocn(:,:) ) 135 IF( lwxios ) CALL iom_swap( cwtxios_context ) 136 CALL iom_rstput( kt, nitrst, numrtw, 'SEDB'//ctrcnm(jpdet), sedpocb(:,:), ldxios = lwxios ) 137 CALL iom_rstput( kt, nitrst, numrtw, 'SEDN'//ctrcnm(jpdet), sedpocn(:,:), ldxios = lwxios ) 138 IF( lwxios ) CALL iom_swap( cxios_context ) 137 139 ENDIF 138 140 ! … … 213 215 ! 214 216 IF( ln_rsttr ) THEN 215 CALL iom_get( numrtr, jpdom_autoglo, 'SEDB'//ctrcnm(jpdet), sedpocb(:,:) ) 216 CALL iom_get( numrtr, jpdom_autoglo, 'SEDN'//ctrcnm(jpdet), sedpocn(:,:) ) 217 IF(lrxios) CALL iom_swap(crtxios_context) 218 CALL iom_get( numrtr, jpdom_autoglo, 'SEDB'//ctrcnm(jpdet), sedpocb(:,:), ldxios = lrxios ) 219 CALL iom_get( numrtr, jpdom_autoglo, 'SEDN'//ctrcnm(jpdet), sedpocn(:,:), ldxios = lrxios ) 220 IF(lrxios) CALL iom_swap(cxios_context) 217 221 ELSE 218 222 sedpocb(:,:) = 0._wp -
NEMO/branches/2020/dev_12905_xios_restart/src/TOP/PISCES/P4Z/p4zsms.F90
r12489 r12961 339 339 IF(lwp) WRITE(numout,*) ' ~~~~~~~~~~~~~~' 340 340 ! 341 IF(lrxios) CALL iom_swap(crtxios_context) 341 342 IF( iom_varid( numrtr, 'PH', ldstop = .FALSE. ) > 0 ) THEN 342 CALL iom_get( numrtr, jpdom_autoglo, 'PH' , hi(:,:,:) )343 CALL iom_get( numrtr, jpdom_autoglo, 'PH' , hi(:,:,:), ldxios = lrxios ) 343 344 ELSE 344 345 CALL p4z_che( Kbb, Kmm ) ! initialize the chemical constants 345 346 CALL ahini_for_at( hi, Kbb ) 346 347 ENDIF 347 CALL iom_get( numrtr, jpdom_autoglo, 'Silicalim', xksi(:,:) )348 CALL iom_get( numrtr, jpdom_autoglo, 'Silicalim', xksi(:,:), ldxios = lrxios ) 348 349 IF( iom_varid( numrtr, 'Silicamax', ldstop = .FALSE. ) > 0 ) THEN 349 CALL iom_get( numrtr, jpdom_autoglo, 'Silicamax' , xksimax(:,:) )350 CALL iom_get( numrtr, jpdom_autoglo, 'Silicamax' , xksimax(:,:), ldxios = lrxios ) 350 351 ELSE 351 352 xksimax(:,:) = xksi(:,:) … … 353 354 ! 354 355 IF( iom_varid( numrtr, 'tcflxcum', ldstop = .FALSE. ) > 0 ) THEN ! cumulative total flux of carbon 355 CALL iom_get( numrtr, 'tcflxcum' , t_oce_co2_flx_cum )356 CALL iom_get( numrtr, 'tcflxcum' , t_oce_co2_flx_cum, ldxios = lrxios ) 356 357 ELSE 357 358 t_oce_co2_flx_cum = 0._wp … … 360 361 IF( ln_p5z ) THEN 361 362 IF( iom_varid( numrtr, 'sized', ldstop = .FALSE. ) > 0 ) THEN 362 CALL iom_get( numrtr, jpdom_autoglo, 'sizep' , sizep(:,:,:) )363 CALL iom_get( numrtr, jpdom_autoglo, 'sizen' , sizen(:,:,:) )364 CALL iom_get( numrtr, jpdom_autoglo, 'sized' , sized(:,:,:) )363 CALL iom_get( numrtr, jpdom_autoglo, 'sizep' , sizep(:,:,:), ldxios = lrxios ) 364 CALL iom_get( numrtr, jpdom_autoglo, 'sizen' , sizen(:,:,:), ldxios = lrxios ) 365 CALL iom_get( numrtr, jpdom_autoglo, 'sized' , sized(:,:,:), ldxios = lrxios ) 365 366 ELSE 366 367 sizep(:,:,:) = 1. … … 369 370 ENDIF 370 371 ENDIF 372 IF(lrxios) CALL iom_swap(cxios_context) 371 373 ! 372 374 ELSEIF( TRIM(cdrw) == 'WRITE' ) THEN … … 376 378 IF(lwp) WRITE(numout,*) '~~~~~~~' 377 379 ENDIF 378 CALL iom_rstput( kt, nitrst, numrtw, 'PH', hi(:,:,:) ) 379 CALL iom_rstput( kt, nitrst, numrtw, 'Silicalim', xksi(:,:) ) 380 CALL iom_rstput( kt, nitrst, numrtw, 'Silicamax', xksimax(:,:) ) 381 CALL iom_rstput( kt, nitrst, numrtw, 'tcflxcum', t_oce_co2_flx_cum ) 380 IF( lwxios ) CALL iom_swap( cwtxios_context ) 381 CALL iom_rstput( kt, nitrst, numrtw, 'PH', hi(:,:,:), ldxios = lwxios ) 382 CALL iom_rstput( kt, nitrst, numrtw, 'Silicalim', xksi(:,:), ldxios = lwxios ) 383 CALL iom_rstput( kt, nitrst, numrtw, 'Silicamax', xksimax(:,:), ldxios = lwxios ) 384 CALL iom_rstput( kt, nitrst, numrtw, 'tcflxcum', t_oce_co2_flx_cum, ldxios = lwxios ) 382 385 IF( ln_p5z ) THEN 383 CALL iom_rstput( kt, nitrst, numrtw, 'sizep', sizep(:,:,:) ) 384 CALL iom_rstput( kt, nitrst, numrtw, 'sizen', sizen(:,:,:) ) 385 CALL iom_rstput( kt, nitrst, numrtw, 'sized', sized(:,:,:) ) 386 ENDIF 386 CALL iom_rstput( kt, nitrst, numrtw, 'sizep', sizep(:,:,:), ldxios = lwxios ) 387 CALL iom_rstput( kt, nitrst, numrtw, 'sizen', sizen(:,:,:), ldxios = lwxios ) 388 CALL iom_rstput( kt, nitrst, numrtw, 'sized', sized(:,:,:), ldxios = lwxios ) 389 ENDIF 390 IF( lwxios ) CALL iom_swap( cxios_context ) 387 391 ENDIF 388 392 ! -
NEMO/branches/2020/dev_12905_xios_restart/src/TOP/PISCES/SED/sedrst.F90
r12649 r12961 42 42 CHARACTER(LEN=50) :: clname ! trc output restart file name 43 43 CHARACTER(LEN=256) :: clpath ! full path to ocean output restart file 44 CHARACTER(LEN=52) :: clpname ! trc output restart file name including AGRIF 44 45 !!---------------------------------------------------------------------- 45 46 ! … … 80 81 IF(lwp) WRITE(numsed,*) & 81 82 ' open sed restart.output NetCDF file: ',TRIM(clpath)//clname 82 CALL iom_open( TRIM(clpath)//TRIM(clname), numrsw, ldwrt = .TRUE., kdlev = jpksed, cdcomp = 'SED' ) 83 IF(.NOT.lwxios) THEN 84 CALL iom_open( TRIM(clpath)//TRIM(clname), numrsw, ldwrt = .TRUE., kdlev = jpksed, cdcomp = 'SED' ) 85 ELSE 86 #if defined key_iomput 87 cwsxios_context = "rstws_"//TRIM(ADJUSTL(clkt)) 88 IF( TRIM(Agrif_CFixed()) == '0' ) THEN 89 clpname = clname 90 ELSE 91 clpname = TRIM(Agrif_CFixed())//"_"//clname 92 ENDIF 93 CALL iom_init( cwsxios_context, TRIM(clpath)//TRIM(clpname), ld_tmppatch = .false.,& 94 ld_closedef = .FALSE. ) 95 CALL iom_swap( cxios_context ) 96 #else 97 clinfo = 'Can not use XIOS in trc_rst_opn' 98 CALL ctl_stop(TRIM(clinfo)) 99 #endif 100 ENDIF 101 83 102 lrst_sed = .TRUE. 84 103 ENDIF … … 120 139 zdta2 = 0. 121 140 141 IF(lrxios) CALL iom_swap(crsxios_context) 122 142 DO jn = 1, jptrased 123 143 cltra = TRIM(sedtrcd(jn)) 124 144 IF( iom_varid( numrsr, TRIM(cltra) , ldstop = .FALSE. ) > 0 ) THEN 125 CALL iom_get( numrsr, jpdom_autoglo, TRIM(cltra), zdta(:,:,:,jn) )145 CALL iom_get( numrsr, jpdom_autoglo, TRIM(cltra), zdta(:,:,:,jn), ldxios = lrxios ) 126 146 ELSE 127 147 zdta(:,:,:,jn) = 0.0 … … 142 162 cltra = TRIM(seddia3d(jn)) 143 163 IF( iom_varid( numrsr, TRIM(cltra) , ldstop = .FALSE. ) > 0 ) THEN 144 CALL iom_get( numrsr, jpdom_autoglo, TRIM(cltra), zdta1(:,:,:,jn) )164 CALL iom_get( numrsr, jpdom_autoglo, TRIM(cltra), zdta1(:,:,:,jn), ldxios = lrxios ) 145 165 ELSE 146 166 zdta1(:,:,:,jn) = 0.0 … … 169 189 cltra = "dbioturb" 170 190 IF( iom_varid( numrsr, TRIM(cltra) , ldstop = .FALSE. ) > 0 ) THEN 171 CALL iom_get( numrsr, jpdom_autoglo, TRIM(cltra), zdta2(:,:,:) )191 CALL iom_get( numrsr, jpdom_autoglo, TRIM(cltra), zdta2(:,:,:), ldxios = lrxios ) 172 192 ELSE 173 193 zdta2(:,:,:) = 0.0 … … 179 199 cltra = "irrig" 180 200 IF( iom_varid( numrsr, TRIM(cltra) , ldstop = .FALSE. ) > 0 ) THEN 181 CALL iom_get( numrsr, jpdom_autoglo, TRIM(cltra), zdta2(:,:,:) )201 CALL iom_get( numrsr, jpdom_autoglo, TRIM(cltra), zdta2(:,:,:), ldxios = lrxios ) 182 202 ELSE 183 203 zdta2(:,:,:) = 0.0 … … 189 209 cltra = "sedligand" 190 210 IF( iom_varid( numrsr, TRIM(cltra) , ldstop = .FALSE. ) > 0 ) THEN 191 CALL iom_get( numrsr, jpdom_autoglo, TRIM(cltra), zdta2(:,:,:) )211 CALL iom_get( numrsr, jpdom_autoglo, TRIM(cltra), zdta2(:,:,:), ldxios = lrxios ) 192 212 ELSE 193 213 zdta2(:,:,:) = 0.0 … … 196 216 CALL pack_arr( jpoce, sedligand(1:jpoce,1:jpksed), & 197 217 & zdta2(1:jpi,1:jpj,1:jpksed), iarroce(1:jpoce) ) 198 218 IF(lrxios) CALL iom_swap(cxios_context) 199 219 IF( ln_timing ) CALL timing_stop('sed_rst_read') 200 220 … … 240 260 !! 1. WRITE in nutwrs 241 261 !! ------------------ 242 243 244 CALL iom_rstput( kt, nitrst, numrsw, 'kt', zinfo)262 IF( lwxios ) CALL iom_swap( cwsxios_context ) 263 ! zinfo(1) = REAL( kt) 264 CALL iom_rstput( kt, nitrst, numrsw, 'kt', REAL( kt , wp), ldxios = lwxios ) 245 265 246 266 ! Back to 2D geometry … … 272 292 DO jn = 1, jptrased 273 293 cltra = TRIM(sedtrcd(jn)) 274 CALL iom_rstput( kt, nitrst, numrsw, TRIM(cltra), trcsedi(:,:,:,jn) )294 CALL iom_rstput( kt, nitrst, numrsw, TRIM(cltra), trcsedi(:,:,:,jn), ldxios = lwxios ) 275 295 ENDDO 276 296 277 297 DO jn = 1, 2 278 298 cltra = TRIM(seddia3d(jn)) 279 CALL iom_rstput( kt, nitrst, numrsw, TRIM(cltra), flxsedi3d(:,:,:,jn) )299 CALL iom_rstput( kt, nitrst, numrsw, TRIM(cltra), flxsedi3d(:,:,:,jn), ldxios = lwxios ) 280 300 ENDDO 281 301 … … 284 304 285 305 cltra = "dbioturb" 286 CALL iom_rstput( kt, nitrst, numrsw, TRIM(cltra), zdta2(:,:,:) )306 CALL iom_rstput( kt, nitrst, numrsw, TRIM(cltra), zdta2(:,:,:), ldxios = lwxios ) 287 307 288 308 CALL unpack_arr( jpoce, zdta2(1:jpi,1:jpj,1:jpksed) , iarroce(1:jpoce), & … … 290 310 291 311 cltra = "irrig" 292 CALL iom_rstput( kt, nitrst, numrsw, TRIM(cltra), zdta2(:,:,:) )312 CALL iom_rstput( kt, nitrst, numrsw, TRIM(cltra), zdta2(:,:,:), ldxios = lwxios ) 293 313 294 314 CALL unpack_arr( jpoce, zdta2(1:jpi,1:jpj,1:jpksed) , iarroce(1:jpoce), & … … 296 316 297 317 cltra = "sedligand" 298 CALL iom_rstput( kt, nitrst, numrsw, TRIM(cltra), zdta2(:,:,:) ) 318 CALL iom_rstput( kt, nitrst, numrsw, TRIM(cltra), zdta2(:,:,:), ldxios = lwxios ) 319 IF( lwxios ) CALL iom_swap( cxios_context ) 299 320 300 321 IF( kt == nitrst ) THEN 301 CALL iom_close( numrsw ) ! close the restart file (only at last time step) 322 IF(.NOT.lwxios) THEN 323 CALL iom_close( numrsw ) ! close the restart file (only at last time step) 324 ELSE 325 CALL iom_context_finalize( cwsxios_context ) 326 ENDIF 302 327 IF( l_offline .AND. ln_rst_list ) THEN 303 328 nrst_lst = nrst_lst + 1 … … 342 367 REAL(wp) :: zkt, zrdttrc1 343 368 REAL(wp) :: zndastp 369 CHARACTER(len = 82) :: clpname 344 370 345 371 ! Time domain : restart … … 353 379 354 380 IF( ln_rst_sed ) THEN 381 lxios_sini = .FALSE. 355 382 CALL iom_open( TRIM(cn_sedrst_indir)//'/'//cn_sedrst_in, numrsr ) 356 CALL iom_get ( numrsr, 'kt', zkt ) ! last time-step of previous run 357 383 384 IF( lrxios .AND. .NOT. lxios_sini) THEN 385 CALL ctl_stop('OCE and SED restart must be in a single file when XIOS is used to read restart') 386 ENDIF 387 IF( lrxios) THEN 388 crsxios_context = 'sed_rst' 389 IF(lwp) WRITE(numout,*) 'Enable restart reading by XIOS for SED' 390 IF( TRIM(Agrif_CFixed()) == '0' ) THEN 391 clpname = cn_sedrst_in 392 ELSE 393 clpname = TRIM(Agrif_CFixed())//"_"//cn_sedrst_in 394 ENDIF 395 CALL iom_init( crsxios_context, fname = TRIM(cn_sedrst_indir)//'/'//TRIM(clpname), & 396 idfp = iom_file(numrsr)%nfid, ld_tmppatch = .TRUE. ) 397 ENDIF 398 IF(lrxios) CALL iom_swap(crsxios_context) 399 CALL iom_get ( numrsr, 'kt', zkt, ldxios = lrxios ) ! last time-step of previous run 400 IF(lrxios) CALL iom_swap(cxios_context) 358 401 IF(lwp) THEN 359 402 WRITE(numsed,*) ' *** Info read in restart : ' … … 376 419 ! ! set the date in offline mode 377 420 IF( ln_rst_sed .AND. nn_rstsed == 2 ) THEN 378 CALL iom_get( numrsr, 'ndastp', zndastp ) 421 IF(lrxios) CALL iom_swap(crsxios_context) 422 CALL iom_get( numrsr, 'ndastp', zndastp, ldxios = lrxios ) 379 423 ndastp = NINT( zndastp ) 380 CALL iom_get( numrsr, 'adatrj', adatrj ) 424 CALL iom_get( numrsr, 'adatrj', adatrj, ldxios = lrxios ) 425 IF(lrxios) CALL iom_swap(crxios_context) 381 426 ELSE 382 427 ndastp = ndate0 - 1 ! ndate0 read in the namelist in dom_nam … … 402 447 IF(lwp) WRITE(numsed,*) 'trc_wri : write the TOP restart file (NetCDF) at it= ', kt, ' date= ', ndastp 403 448 IF(lwp) WRITE(numsed,*) '~~~~~~~' 404 ENDIF 405 CALL iom_rstput( kt, nitrst, numrsw, 'kt' , REAL( kt , wp) ) ! time-step 406 CALL iom_rstput( kt, nitrst, numrsw, 'ndastp' , REAL( ndastp, wp) ) ! date 407 CALL iom_rstput( kt, nitrst, numrsw, 'adatrj' , adatrj ) ! number of elapsed days since 408 ! ! the begining of the run [s] 449 IF( lwxios ) CALL iom_init_closedef(cwsxios_context) 450 ENDIF 451 IF( lwxios ) CALL iom_swap( cwsxios_context ) 452 CALL iom_rstput( kt, nitrst, numrsw, 'kt' , REAL( kt , wp), ldxios = lwxios ) ! time-step 453 CALL iom_rstput( kt, nitrst, numrsw, 'ndastp' , REAL( ndastp, wp), ldxios = lwxios ) ! date 454 CALL iom_rstput( kt, nitrst, numrsw, 'adatrj' , adatrj, ldxios = lwxios ) ! number of elapsed days since 455 ! ! the begining of the run [s] 456 IF( lwxios ) CALL iom_swap( cxios_context ) 409 457 ENDIF 410 458 -
NEMO/branches/2020/dev_12905_xios_restart/src/TOP/PISCES/SED/sedstp.F90
r12489 r12961 86 86 IF( kt == nitsed000 ) THEN 87 87 CALL iom_close( numrsr ) ! close input tracer restart file 88 IF(lrxios) CALL iom_context_finalize( crsxios_context ) 88 89 ! IF(lwm) CALL FLUSH( numont ) ! flush namelist output 89 90 ENDIF -
NEMO/branches/2020/dev_12905_xios_restart/src/TOP/TRP/trcsbc.F90
r12489 r12961 86 86 IF(lwp) WRITE(numout,*) ' nittrc000-1 surface tracer content forcing fields read in the restart file' 87 87 zfact = 0.5_wp 88 IF(lrxios) CALL iom_swap(crtxios_context) 88 89 DO jn = 1, jptra 89 CALL iom_get( numrtr, jpdom_autoglo, 'sbc_'//TRIM(ctrcnm(jn))//'_b', sbc_trc_b(:,:,jn) ) ! before tracer content sbc90 CALL iom_get( numrtr, jpdom_autoglo, 'sbc_'//TRIM(ctrcnm(jn))//'_b', sbc_trc_b(:,:,jn), ldxios = lrxios ) ! before tracer content sbc 90 91 END DO 92 IF(lrxios) CALL iom_swap(cxios_context) 91 93 ELSE ! No restart or restart not found: Euler forward time stepping 92 94 zfact = 1._wp … … 180 182 & 'at it= ', kt,' date= ', ndastp 181 183 IF(lwp) WRITE(numout,*) '~~~~' 182 DO jn = 1, jptra 183 CALL iom_rstput( kt, nitrst, numrtw, 'sbc_'//TRIM(ctrcnm(jn))//'_b', sbc_trc(:,:,jn) ) 184 END DO 184 IF( lwxios ) CALL iom_swap( cwtxios_context ) 185 DO jn = 1, jptra 186 CALL iom_rstput( kt, nitrst, numrtw, 'sbc_'//TRIM(ctrcnm(jn))//'_b', sbc_trc(:,:,jn), ldxios = lwxios ) 187 END DO 188 IF( lwxios ) CALL iom_swap( cxios_context ) 185 189 ENDIF 186 190 ! -
NEMO/branches/2020/dev_12905_xios_restart/src/TOP/trcrst.F90
r12489 r12961 51 51 CHARACTER(LEN=50) :: clname ! trc output restart file name 52 52 CHARACTER(LEN=256) :: clpath ! full path to ocean output restart file 53 CHARACTER(LEN=50) :: clpname ! trc output restart file name including AGRIF 53 54 !!---------------------------------------------------------------------- 54 55 ! … … 90 91 IF(lwp) WRITE(numout,*) & 91 92 ' open trc restart.output NetCDF file: ',TRIM(clpath)//clname 92 CALL iom_open( TRIM(clpath)//TRIM(clname), numrtw, ldwrt = .TRUE. ) 93 IF(.NOT.lwxios) THEN 94 CALL iom_open( TRIM(clpath)//TRIM(clname), numrtw, ldwrt = .TRUE. ) 95 ELSE 96 #if defined key_iomput 97 cwtxios_context = "rstwt_"//TRIM(ADJUSTL(clkt)) 98 IF( TRIM(Agrif_CFixed()) == '0' ) THEN 99 clpname = clname 100 ELSE 101 clpname = TRIM(Agrif_CFixed())//"_"//clname 102 ENDIF 103 CALL iom_init( cwtxios_context, TRIM(clpath)//TRIM(clpname), ld_tmppatch = .false.,& 104 ld_closedef = .FALSE. ) 105 CALL iom_swap( cxios_context ) 106 #else 107 clinfo = 'Can not use XIOS in trc_rst_opn' 108 CALL ctl_stop(TRIM(clinfo)) 109 #endif 110 ENDIF 93 111 lrst_trc = .TRUE. 94 112 ENDIF … … 112 130 113 131 ! READ prognostic variables and computes diagnostic variable 132 IF(lrxios) CALL iom_swap(crtxios_context) 114 133 DO jn = 1, jptra 115 CALL iom_get( numrtr, jpdom_autoglo, 'TRN'//ctrcnm(jn), tr(:,:,:,jn,Kmm) )134 CALL iom_get( numrtr, jpdom_autoglo, 'TRN'//ctrcnm(jn), tr(:,:,:,jn,Kmm), ldxios = lrxios ) 116 135 END DO 117 136 118 137 DO jn = 1, jptra 119 CALL iom_get( numrtr, jpdom_autoglo, 'TRB'//ctrcnm(jn), tr(:,:,:,jn,Kbb) )138 CALL iom_get( numrtr, jpdom_autoglo, 'TRB'//ctrcnm(jn), tr(:,:,:,jn,Kbb), ldxios = lrxios ) 120 139 END DO 121 140 ! 122 141 CALL iom_delay_rst( 'READ', 'TOP', numrtr ) ! read only TOP delayed global communication variables 123 142 IF(lrxios) CALL iom_swap(cxios_context) 124 143 END SUBROUTINE trc_rst_read 125 144 … … 136 155 !!---------------------------------------------------------------------- 137 156 ! 138 CALL iom_rstput( kt, nitrst, numrtw, 'rdttrc1', rn_Dt ) ! passive tracer time step (= ocean time step) 157 IF( lwxios ) CALL iom_swap( cwtxios_context ) 158 CALL iom_rstput( kt, nitrst, numrtw, 'rdttrc1', rn_Dt, ldxios = lwxios ) ! passive tracer time step (= ocean time step) 139 159 ! prognostic variables 140 160 ! -------------------- 141 161 DO jn = 1, jptra 142 CALL iom_rstput( kt, nitrst, numrtw, 'TRN'//ctrcnm(jn), tr(:,:,:,jn,Kmm) )162 CALL iom_rstput( kt, nitrst, numrtw, 'TRN'//ctrcnm(jn), tr(:,:,:,jn,Kmm), ldxios = lwxios ) 143 163 END DO 144 164 145 165 DO jn = 1, jptra 146 CALL iom_rstput( kt, nitrst, numrtw, 'TRB'//ctrcnm(jn), tr(:,:,:,jn,Kbb) ) 147 END DO 166 CALL iom_rstput( kt, nitrst, numrtw, 'TRB'//ctrcnm(jn), tr(:,:,:,jn,Kbb), ldxios = lwxios ) 167 END DO 168 IF( lwxios ) CALL iom_swap( cxios_context ) 148 169 ! 149 170 CALL iom_delay_rst( 'WRITE', 'TOP', numrtw ) ! save only TOP delayed global communication variables … … 151 172 IF( kt == nitrst ) THEN 152 173 CALL trc_rst_stat( Kmm, Krhs ) ! statistics 153 CALL iom_close( numrtw ) ! close the restart file (only at last time step) 174 IF(lwxios) THEN 175 CALL iom_context_finalize( cwtxios_context ) 176 ELSE 177 CALL iom_close( numrtw ) ! close the restart file (only at last time step) 178 ENDIF 154 179 #if ! defined key_trdmxl_trc 155 180 lrst_trc = .FALSE. … … 195 220 REAL(wp) :: zrdttrc1, zkt, zndastp, zdayfrac, ksecs, ktime 196 221 INTEGER :: ihour, iminute 222 CHARACTER(len=82) :: clpname 197 223 198 224 ! Time domain : restart … … 206 232 207 233 IF( ln_rsttr ) THEN 234 lxios_sini = .FALSE. 208 235 CALL iom_open( TRIM(cn_trcrst_indir)//'/'//cn_trcrst_in, numrtr ) 209 CALL iom_get ( numrtr, 'kt', zkt ) ! last time-step of previous run 236 IF( lrxios .AND. .NOT. lxios_sini) THEN 237 CALL ctl_stop('OCE and TOP restart must be in a single file when XIOS is used to read restart') 238 ENDIF 239 IF( lrxios) THEN 240 crtxios_context = 'top_rst' 241 IF(lwp) WRITE(numout,*) 'Enable restart reading by XIOS for TOP' 242 IF( TRIM(Agrif_CFixed()) == '0' ) THEN 243 clpname = cn_trcrst_in 244 ELSE 245 clpname = TRIM(Agrif_CFixed())//"_"//cn_trcrst_in 246 ENDIF 247 CALL iom_init( crtxios_context, fname = TRIM(cn_trcrst_indir)//'/'//TRIM(clpname), & 248 idfp = iom_file(numrtr)%nfid, ld_tmppatch = .TRUE. ) 249 ENDIF 250 251 IF(lrxios) CALL iom_swap(crtxios_context) 252 CALL iom_get ( numrtr, 'kt', zkt, ldxios = lrxios ) ! last time-step of previous run 253 IF(lrxios) CALL iom_swap(cxios_context) 210 254 211 255 IF(lwp) THEN … … 229 273 ! ! set the date in offline mode 230 274 IF( ln_rsttr .AND. nn_rsttr == 2 ) THEN 231 CALL iom_get( numrtr, 'ndastp', zndastp ) 275 IF(lrxios) CALL iom_swap(crtxios_context) 276 CALL iom_get( numrtr, 'ndastp', zndastp, ldxios = lrxios ) 232 277 ndastp = NINT( zndastp ) 233 CALL iom_get( numrtr, 'adatrj', adatrj ) 234 CALL iom_get( numrtr, 'ntime' , ktime ) 278 CALL iom_get( numrtr, 'adatrj', adatrj, ldxios = lrxios ) 279 CALL iom_get( numrtr, 'ntime' , ktime, ldxios = lrxios ) 280 IF(lrxios) CALL iom_swap(cxios_context) 235 281 nn_time0=INT(ktime) 236 282 ! calculate start time in hours and minutes … … 291 337 IF(lwp) WRITE(numout,*) '~~~~~~~' 292 338 ENDIF 293 CALL iom_rstput( kt, nitrst, numrtw, 'kt' , REAL( kt , wp) ) ! time-step 294 CALL iom_rstput( kt, nitrst, numrtw, 'ndastp' , REAL( ndastp, wp) ) ! date 295 CALL iom_rstput( kt, nitrst, numrtw, 'adatrj' , adatrj ) ! number of elapsed days since 339 IF( lwxios ) CALL iom_swap( cwtxios_context ) 340 CALL iom_rstput( kt, nitrst, numrtw, 'kt' , REAL( kt , wp) , ldxios = lwxios ) ! time-step 341 CALL iom_rstput( kt, nitrst, numrtw, 'ndastp' , REAL( ndastp, wp) , ldxios = lwxios ) ! date 342 CALL iom_rstput( kt, nitrst, numrtw, 'adatrj' , adatrj , ldxios = lwxios ) ! number of elapsed days since 296 343 ! ! the begining of the run [s] 297 CALL iom_rstput( kt, nitrst, numrtw, 'ntime' , REAL( nn_time0, wp)) ! time 344 CALL iom_rstput( kt, nitrst, numrtw, 'ntime' , REAL( nn_time0, wp), ldxios = lwxios ) ! time 345 IF( lwxios ) CALL iom_swap( cxios_context ) 298 346 ENDIF 299 347 -
NEMO/branches/2020/dev_12905_xios_restart/src/TOP/trcstp.F90
r12620 r12961 109 109 IF( kt == nittrc000 ) THEN 110 110 CALL iom_close( numrtr ) ! close input tracer restart file 111 IF(lrxios) CALL iom_context_finalize( crtxios_context ) 111 112 IF(lwm) CALL FLUSH( numont ) ! flush namelist output 112 113 ENDIF … … 195 196 & .AND. iom_varid( numrtr, 'ktdcy' , ldstop = .FALSE. ) > 0 & 196 197 & .AND. iom_varid( numrtr, 'nrdcy' , ldstop = .FALSE. ) > 0 ) THEN 197 198 CALL iom_get( numrtr, 'ktdcy', zkt )198 IF(lrxios) CALL iom_swap(crtxios_context) 199 CALL iom_get( numrtr, 'ktdcy', zkt, ldxios = lrxios ) 199 200 rsecfst = INT( zkt ) * rn_Dt 200 201 IF(lwp) WRITE(numout,*) 'trc_qsr_mean: qsr_mean read in the restart file at time-step rsecfst =', rsecfst, ' s ' 201 CALL iom_get( numrtr, jpdom_autoglo, 'qsr_mean', qsr_mean ) ! A mean of qsr202 CALL iom_get( numrtr, 'nrdcy', zrec ) ! Number of record per days202 CALL iom_get( numrtr, jpdom_autoglo, 'qsr_mean', qsr_mean, ldxios = lrxios ) ! A mean of qsr 203 CALL iom_get( numrtr, 'nrdcy', zrec, ldxios = lrxios ) ! Number of record per days 203 204 IF( INT( zrec ) == nb_rec_per_day ) THEN 204 205 DO jn = 1, nb_rec_per_day 205 206 IF( jn <= 9 ) THEN 206 207 WRITE(cl1,'(i1)') jn 207 CALL iom_get( numrtr, jpdom_autoglo, 'qsr_arr_'//cl1, qsr_arr(:,:,jn) ) ! A mean of qsr208 CALL iom_get( numrtr, jpdom_autoglo, 'qsr_arr_'//cl1, qsr_arr(:,:,jn), ldxios = lrxios ) ! A mean of qsr 208 209 ELSE 209 210 WRITE(cl2,'(i2.2)') jn 210 CALL iom_get( numrtr, jpdom_autoglo, 'qsr_arr_'//cl2, qsr_arr(:,:,jn) ) ! A mean of qsr211 CALL iom_get( numrtr, jpdom_autoglo, 'qsr_arr_'//cl2, qsr_arr(:,:,jn), ldxios = lrxios ) ! A mean of qsr 211 212 ENDIF 212 213 END DO … … 216 217 ENDDO 217 218 ENDIF 219 IF(lrxios) CALL iom_swap(cxios_context) 218 220 ELSE !* no restart: set from nit000 values 219 221 IF(lwp) WRITE(numout,*) 'trc_qsr_mean: qsr_mean set to nit000 values' … … 249 251 zkt = REAL( ktdcy, wp ) 250 252 zrec = REAL( nb_rec_per_day, wp ) 251 CALL iom_rstput( kt, nitrst, numrtw, 'ktdcy', zkt ) 252 CALL iom_rstput( kt, nitrst, numrtw, 'nrdcy', zrec ) 253 IF( lwxios ) CALL iom_swap( cwtxios_context ) 254 CALL iom_rstput( kt, nitrst, numrtw, 'ktdcy', zkt, ldxios = lwxios ) 255 CALL iom_rstput( kt, nitrst, numrtw, 'nrdcy', zrec, ldxios = lwxios ) 253 256 DO jn = 1, nb_rec_per_day 254 257 IF( jn <= 9 ) THEN 255 258 WRITE(cl1,'(i1)') jn 256 CALL iom_rstput( kt, nitrst, numrtw, 'qsr_arr_'//cl1, qsr_arr(:,:,jn) )259 CALL iom_rstput( kt, nitrst, numrtw, 'qsr_arr_'//cl1, qsr_arr(:,:,jn), ldxios = lwxios ) 257 260 ELSE 258 261 WRITE(cl2,'(i2.2)') jn 259 CALL iom_rstput( kt, nitrst, numrtw, 'qsr_arr_'//cl2, qsr_arr(:,:,jn) )262 CALL iom_rstput( kt, nitrst, numrtw, 'qsr_arr_'//cl2, qsr_arr(:,:,jn), ldxios = lwxios ) 260 263 ENDIF 261 264 END DO 262 CALL iom_rstput( kt, nitrst, numrtw, 'qsr_mean', qsr_mean(:,:) ) 265 CALL iom_rstput( kt, nitrst, numrtw, 'qsr_mean', qsr_mean(:,:), ldxios = lwxios ) 266 IF( lwxios ) CALL iom_swap( cxios_context ) 263 267 ENDIF 264 268 !
Note: See TracChangeset
for help on using the changeset viewer.