SCALE-RM
Data Types | Functions/Subroutines | Variables
scale_file Module Reference

module file More...

Functions/Subroutines

subroutine, public file_setup (myrank)
 setup More...
 
subroutine, public file_finalize
 finalize More...
 
subroutine, public file_create (basename, title, source, institution, fid, existed, rankid, single, aggregate, time_units, calendar, allnodes, append)
 create file fid is >= 1 More...
 
subroutine, public file_add_associatedvariable (fid, vname, existed)
 
subroutine, public file_set_option (fid, filetype, key, val)
 
subroutine, public file_open (basename, fid, mode, single, allnodes, aggregate, rankid, postfix)
 
logical function, public file_opened (fid)
 check if the file is opened? More...
 
logical function, public file_single (fid)
 check if the file is single More...
 
logical function, public file_allnodes (fid)
 check if the file is allnodes More...
 
subroutine, public file_get_dimlength (fid, dimname, len, error)
 get length of dimension More...
 
subroutine, public file_def_axis (fid, name, desc, units, dim_name, dtype, dim_size, bounds)
 
subroutine, public file_def_associatedcoordinate (fid, name, desc, units, dim_names, dtype)
 
subroutine, public file_def_variable (fid, varname, desc, units, standard_name, ndims, dims, dtype, vid, time_int, time_stats, existed)
 
subroutine, public file_get_stepsize (fid, varname, len, error)
 get number of steps More...
 
subroutine, public file_enddef (fid)
 
subroutine, public file_redef (fid)
 
subroutine, public file_attach_buffer (fid, buf_amount)
 
subroutine, public file_detach_buffer (fid)
 
subroutine, public file_flush (fid)
 
subroutine, public file_close (fid, abort)
 
subroutine, public file_close_all (skip_abort)
 
subroutine, public file_get_cftunits (date, tunits)
 get unit of time More...
 
logical function, public file_get_aggregate (fid)
 

Variables

logical, public file_aggregate
 
logical, public do
 
logical, public parallel
 
logical, public i
 
logical, public o
 
logical, public through
 
logical, dimension(default setting), public pnetcdf
 

Detailed Description

module file

Description
file I/O hundring
Author
Team SCALE
NAMELIST
  • PARAM_FILE
    nametypedefault valuecomment
    FILE_AGGREGATE logical > do parallel I/O through PnetCDF (default setting)

History Output
No history output

Function/Subroutine Documentation

◆ file_setup()

subroutine, public scale_file::file_setup ( integer, intent(in)  myrank)

setup

Definition at line 236 of file scale_file.F90.

236  use scale_prc, only: &
238  implicit none
239 
240  integer, intent(in) :: myrank
241 
242  namelist / param_file / &
243  file_aggregate
244 
245  integer :: fid
246  integer :: ierr
247 
248  file_aggregate = .false.
249 
250  !--- read namelist
251  rewind(io_fid_conf)
252  read(io_fid_conf,nml=param_file,iostat=ierr)
253  if( ierr < 0 ) then !--- missing
254  log_info("FILE_setup",*) 'Not found namelist. Default used.'
255  elseif( ierr > 0 ) then !--- fatal error
256  log_error("FILE_setup",*) 'Not appropriate names in namelist PARAM_FILE. Check!'
257  call prc_abort
258  endif
259  log_nml(param_file)
260 
261  mpi_myrank = myrank
262 
263  call prc_set_file_closer( file_close_all )
264 
265  do fid = 1, file_file_max
266  file_files(fid)%fid = -1
267  file_files(fid)%name = ""
268  end do
269 
270  return

References file_aggregate, file_close_all(), scale_file_h::file_file_max, scale_io::io_fid_conf, and scale_prc::prc_set_file_closer().

Referenced by scale_file_cartesc::file_cartesc_setup().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ file_finalize()

subroutine, public scale_file::file_finalize

finalize

Definition at line 277 of file scale_file.F90.

277 
278  file_nfiles = 0
279  file_nvars = 0
280 
281  return

Referenced by mod_rm_driver::rm_driver(), and mod_rm_prep::rm_prep().

Here is the caller graph for this function:

◆ file_create()

subroutine, public scale_file::file_create ( character(len=*), intent(in)  basename,
character(len=*), intent(in)  title,
character(len=*), intent(in)  source,
character(len=*), intent(in)  institution,
integer, intent(out)  fid,
logical, intent(out)  existed,
integer, intent(in), optional  rankid,
logical, intent(in), optional  single,
logical, intent(in), optional  aggregate,
character(len=*), intent(in), optional  time_units,
character(len=*), intent(in), optional  calendar,
logical, intent(in), optional  allnodes,
logical, intent(in), optional  append 
)

create file fid is >= 1

Definition at line 295 of file scale_file.F90.

295  implicit none
296 
297  character(len=*), intent(in) :: basename
298  character(len=*), intent(in) :: title
299  character(len=*), intent(in) :: source
300  character(len=*), intent(in) :: institution
301 
302  integer, intent(out) :: fid
303  logical, intent(out) :: existed
304 
305  integer, intent(in), optional :: rankid
306  logical, intent(in), optional :: single
307  logical, intent(in), optional :: aggregate
308  character(len=*), intent(in), optional :: time_units
309  character(len=*), intent(in), optional :: calendar
310  logical, intent(in), optional :: allnodes
311  logical, intent(in), optional :: append
312 
313  character(len=FILE_HMID) :: time_units_
314  character(len=FILE_HSHORT) :: calendar_
315  integer :: rankid_
316  logical :: single_
317  integer :: mode
318 
319  integer :: error
320  !---------------------------------------------------------------------------
321 
322 
323  if ( present(rankid) ) then
324  rankid_ = rankid
325  else
326  rankid_ = mpi_myrank
327  end if
328 
329  single_ = .false.
330  if ( present(single) ) then
331  single_ = single
332  endif
333 
334  if ( present(time_units) ) then
335  time_units_ = time_units
336  else
337  time_units_ = 'seconds'
338  endif
339 
340  if ( present(calendar) ) then
341  calendar_ = calendar
342  else
343  calendar_ = ""
344  end if
345 
346  mode = file_fwrite
347  if ( present(append) ) then
348  if( append ) mode = file_fappend
349  endif
350 
351  if ( single_ .and. rankid_ /= 0 ) then
352  fid = -1
353  existed = .false.
354  return
355  end if
356 
357  call file_get_fid( basename, mode, & ! [IN]
358  rankid_, single_, & ! [IN]
359  fid, existed, & ! [OUT]
360  allnodes=allnodes, & ! [IN]
361  aggregate=aggregate ) ! [IN]
362 
363  if( existed ) return
364 
365  call prof_rapstart('FILE_Write', 2, disable_barrier = .not. file_files(fid)%allnodes )
366 
367  !--- append package header to the file
368  call file_set_attribute( fid, "global", "title" , title ) ! [IN]
369  call file_set_attribute( fid, "global", "source" , source ) ! [IN]
370  call file_set_attribute( fid, "global", "institution", institution ) ! [IN]
371 
372  if ( ( .not. present(aggregate) ) .or. .not. aggregate ) then
373  ! for shared-file parallel I/O, skip attributes related to MPI processes
374  call file_set_attribute( fid, "global", "rankid" , (/rankid_/) ) ! [IN]
375  endif
376 
377  error = file_set_tunits_c( file_files(fid)%fid, & ! [IN]
378  cstr(time_units_), &
379  cstr(calendar_ ) ) ! [IN]
380 
381  if ( error /= file_success_code ) then
382  log_error("FILE_create",*) 'failed to set time units'
383  call prc_abort
384  endif
385 
386  call prof_rapend('FILE_Write', 2, disable_barrier = .not. file_files(fid)%allnodes )
387 
388  return

References scale_file_h::cstr(), scale_file_h::file_fappend, scale_file_h::file_fwrite, file_get_nvars_c(), file_get_varname_c(), file_opened(), file_set_tunits_c(), scale_file_h::file_success_code, scale_prc::prc_abort(), scale_prof::prof_rapend(), and scale_prof::prof_rapstart().

Referenced by scale_file_cartesc::file_cartesc_create(), and scale_file_history::file_history_finalize().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ file_add_associatedvariable()

subroutine, public scale_file::file_add_associatedvariable ( integer, intent(in)  fid,
character(len=*), intent(in)  vname,
logical, intent(out), optional  existed 
)

Definition at line 464 of file scale_file.F90.

464  integer, intent(in) :: fid
465  character(len=*), intent(in) :: vname
466  logical, optional, intent(out) :: existed
467 
468  integer :: error
469 
470  if ( .not. file_opened(fid) ) then
471  log_error("FILE_add_associatedVariable",*) 'File is not opened. fid = ', fid
472  call prc_abort
473  end if
474 
475  call prof_rapstart('FILE_Write', 2, disable_barrier = .not. file_files(fid)%allnodes )
476 
477  error = file_add_associatedvariable_c( file_files(fid)%fid, cstr(vname) ) ! (in)
478 
479  call prof_rapend ('FILE_Write', 2, disable_barrier = .not. file_files(fid)%allnodes )
480 
481  if ( present(existed) ) then
482  if ( error == file_already_existed_code ) then
483  existed = .true.
484  return
485  end if
486  existed = .false.
487  end if
488 
489  if ( error /= file_success_code ) then
490  log_error("FILE_add_associatedvariable",*) 'failed to add associated variable: '//trim(vname)
491  call prc_abort
492  end if
493 
494  return

References scale_file_h::cstr(), file_add_associatedvariable_c(), scale_file_h::file_already_existed_code, file_opened(), scale_file_h::file_success_code, scale_prc::prc_abort(), scale_prof::prof_rapend(), and scale_prof::prof_rapstart().

Referenced by scale_file_cartesc::file_cartesc_def_axes(), and scale_file_history::file_history_finalize().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ file_set_option()

subroutine, public scale_file::file_set_option ( integer, intent(in)  fid,
character(len=*), intent(in)  filetype,
character(len=*), intent(in)  key,
character(len=*), intent(in)  val 
)

Definition at line 501 of file scale_file.F90.

501  integer, intent(in) :: fid
502  character(len=*), intent(in) :: filetype
503  character(len=*), intent(in) :: key
504  character(len=*), intent(in) :: val
505 
506  integer :: error
507 
508  if ( .not. file_opened(fid) ) then
509  log_error("FILE_set_option",*) 'File is not opened. fid = ', fid
510  call prc_abort
511  end if
512 
513  call prof_rapstart('FILE_Write', 2, disable_barrier = .not. file_files(fid)%allnodes )
514 
515  error = file_set_option_c( file_files(fid)%fid, cstr(filetype), cstr(key), cstr(val) ) ! (in)
516  if ( error /= file_success_code ) then
517  log_error("FILE_set_option",*) 'failed to set option'
518  call prc_abort
519  end if
520 
521  call prof_rapend ('FILE_Write', 2, disable_barrier = .not. file_files(fid)%allnodes )
522 
523  return

References scale_file_h::cstr(), file_opened(), file_set_option_c(), scale_file_h::file_success_code, scale_prc::prc_abort(), scale_prof::prof_rapend(), and scale_prof::prof_rapstart().

Referenced by scale_file_history::file_history_finalize().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ file_open()

subroutine, public scale_file::file_open ( character(len=*), intent(in)  basename,
integer, intent(out)  fid,
integer, intent(in), optional  mode,
logical, intent(in), optional  single,
logical, intent(in), optional  allnodes,
logical, intent(in), optional  aggregate,
integer, intent(in), optional  rankid,
character(len=*), intent(in), optional  postfix 
)

Definition at line 536 of file scale_file.F90.

536  implicit none
537 
538  character(len=*), intent( in) :: basename
539  integer, intent(out) :: fid
540  integer, intent( in), optional :: mode
541  logical, intent( in), optional :: single
542  logical, intent( in), optional :: allnodes
543  logical, intent( in), optional :: aggregate
544  integer, intent( in), optional :: rankid
545  character(len=*), intent( in), optional :: postfix
546 
547  integer :: mode_
548  integer :: rankid_
549  logical :: existed
550  logical :: single_
551 
552  single_ = .false.
553 
554  if ( present(mode) ) then
555  mode_ = mode
556  else
557  mode_ = file_fread
558  end if
559 
560  if ( present(single) ) single_ = single
561  if ( present(rankid) ) then
562  rankid_ = rankid
563  else
564  rankid_ = mpi_myrank
565  end if
566 
567  call file_get_fid( basename, mode_, rankid_, single_, & ! (in)
568  fid, existed, & ! (out)
569  allnodes=allnodes, & ! (in)
570  aggregate=aggregate, postfix=postfix ) ! (in)
571 
572  return

References scale_file_h::file_fread.

Referenced by scale_atmos_grid_cartesc::atmos_grid_cartesc_allocate(), scale_atmos_phy_rd_profile::atmos_phy_rd_profile_finalize(), mod_realinput_netcdf::check_filetype(), scale_comm_cartesc_nest::comm_cartesc_nest_domain_regist_file(), scale_comm_cartesc_nest::comm_cartesc_nest_setup(), mod_copytopo::copytopo_get_data_scale(), mod_copytopo::copytopo_get_data_wrfarw(), mod_copytopo::copytopo_get_size_wrfarw(), scale_file_cartesc::file_cartesc_finalize(), scale_file_cartesc::file_cartesc_open(), file_def_variable(), scale_file_external_input::file_external_input_query(), scale_file_external_input::file_external_input_regist_file(), file_get_stepsize(), scale_land_grid_cartesc::land_grid_cartesc_finalize(), scale_land_grid_icoa::land_grid_icoa_finalize(), scale_ocean_grid_cartesc::ocean_grid_cartesc_finalize(), scale_ocean_grid_icoa::ocean_grid_icoa_setup(), mod_realinput_netcdf::parentatmosopennetcdf(), mod_realinput_nicam::parentatmosopennicam(), mod_realinput_netcdf::parentlandopennetcdf(), mod_realinput_netcdf::parentoceanopennetcdf(), scale_urban_grid_cartesc::urban_grid_cartesc_finalize(), and scale_urban_grid_icoa::urban_grid_icoa_finalize().

Here is the caller graph for this function:

◆ file_opened()

logical function, public scale_file::file_opened ( integer, intent(in)  fid)

check if the file is opened?

Definition at line 578 of file scale_file.F90.

578  implicit none
579 
580  integer, intent( in) :: fid
581  logical :: FILE_opened
582 
583  if ( fid < 1 ) then
584  file_opened = .false.
585  else
586  file_opened = file_files(fid)%fid >= 0
587  end if
588 
589  return

Referenced by file_add_associatedvariable(), file_attach_buffer(), scale_file_cartesc::file_cartesc_close(), scale_file_cartesc::file_cartesc_def_axes(), scale_file_cartesc::file_cartesc_def_var(), scale_file_cartesc::file_cartesc_enddef(), scale_file_cartesc::file_cartesc_flush(), scale_file_cartesc::file_cartesc_put_globalattributes(), scale_file_cartesc::file_cartesc_read_1d(), scale_file_cartesc::file_cartesc_read_auto_2d(), scale_file_cartesc::file_cartesc_read_auto_3d(), scale_file_cartesc::file_cartesc_read_var_2d(), scale_file_cartesc::file_cartesc_read_var_3d(), scale_file_cartesc::file_cartesc_read_var_4d(), scale_file_cartesc::file_cartesc_write_axes(), scale_file_cartesc::file_cartesc_write_var_1d(), scale_file_cartesc::file_cartesc_write_var_2d(), scale_file_cartesc::file_cartesc_write_var_3d(), scale_file_cartesc::file_cartesc_write_var_3d_t(), scale_file_cartesc::file_cartesc_write_var_4d(), file_close(), file_create(), file_def_associatedcoordinate(), file_def_axis(), file_def_variable(), file_detach_buffer(), file_enddef(), file_flush(), file_get_aggregate(), file_get_dimlength(), file_get_stepsize(), file_redef(), and file_set_option().

Here is the caller graph for this function:

◆ file_single()

logical function, public scale_file::file_single ( integer, intent(in)  fid)

check if the file is single

Definition at line 595 of file scale_file.F90.

595  implicit none
596 
597  integer, intent( in) :: fid
598  logical :: FILE_single
599 
600  if ( fid < 1 ) then
601  file_single = .false.
602  else
603  file_single = file_files(fid)%single
604  end if
605 
606  return

◆ file_allnodes()

logical function, public scale_file::file_allnodes ( integer, intent(in)  fid)

◆ file_get_dimlength()

subroutine, public scale_file::file_get_dimlength ( integer, intent(in)  fid,
character(len=*), intent(in)  dimname,
integer, intent(out)  len,
logical, intent(out), optional  error 
)

get length of dimension

Definition at line 633 of file scale_file.F90.

633  integer, intent(in) :: fid
634  character(len=*), intent(in) :: dimname
635 
636  integer, intent(out) :: len
637 
638  logical, intent(out), optional :: error
639 
640  logical(c_bool) :: suppress
641  integer :: ierror
642 
643 
644  if ( .not. file_opened(fid) ) then
645  log_error("FILE_get_dimLength",*) 'File is not opened. fid = ', fid
646  call prc_abort
647  end if
648 
649  call prof_rapstart('FILE_Read', 2, disable_barrier = .not. file_files(fid)%allnodes )
650 
651  if ( present(error) ) then
652  suppress = .true.
653  else
654  suppress = .false.
655  end if
656 
657  ierror = file_get_dim_length_c( len, & ! (out)
658  file_files(fid)%fid, & ! (in)
659  cstr(dimname), & ! (in)
660  suppress ) ! (in)
661  if ( ierror /= file_success_code .and. ierror /= file_already_existed_code ) then
662  if ( present(error) ) then
663  error = .true.
664  else
665  log_error("FILE_get_dimLength",*) 'failed to get dimension length'
666  call prc_abort
667  end if
668  else
669  if ( present(error) ) error = .false.
670  end if
671 
672  call prof_rapend ('FILE_Read', 2, disable_barrier = .not. file_files(fid)%allnodes )
673 
674  return

References scale_file_h::cstr(), scale_precision::dp, scale_file_h::file_already_existed_code, file_get_dim_length_c(), file_opened(), file_put_axis_c(), scale_file_h::file_success_code, scale_prc::prc_abort(), scale_prof::prof_rapend(), scale_prof::prof_rapstart(), and scale_precision::sp.

Referenced by mod_copytopo::copytopo_get_size_wrfarw(), mod_realinput_netcdf::parentatmossetupnetcdf(), mod_realinput_netcdf::parentlandsetupnetcdf(), and mod_realinput_netcdf::parentoceansetupnetcdf().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ file_def_axis()

subroutine, public scale_file::file_def_axis ( integer, intent(in)  fid,
character(len=*), intent(in)  name,
character(len=*), intent(in)  desc,
character(len=*), intent(in)  units,
character(len=*), intent(in)  dim_name,
integer, intent(in)  dtype,
integer, intent(in)  dim_size,
logical, intent(in), optional  bounds 
)

Definition at line 770 of file scale_file.F90.

770  integer, intent(in) :: fid
771  character(len=*), intent(in) :: name
772  character(len=*), intent(in) :: desc
773  character(len=*), intent(in) :: units
774  character(len=*), intent(in) :: dim_name
775  integer, intent(in) :: dtype
776  integer, intent(in) :: dim_size
777 
778  logical, intent(in), optional :: bounds
779 
780  integer :: error
781  integer :: bounds_
782 
783  bounds_ = 0 ! .false.
784  if ( present(bounds) ) then
785  if ( bounds ) bounds_ = 1 ! .true.
786  end if
787 
788  if ( .not. file_opened(fid) ) then
789  log_error("FILE_def_axis",*) 'File is not opened. fid = ', fid
790  call prc_abort
791  end if
792 
793  call prof_rapstart('FILE_Write', 2, disable_barrier = .not. file_files(fid)%allnodes )
794 
795  error = file_def_axis_c( file_files(fid)%fid, & ! (in)
796  cstr(name), cstr(desc), cstr(units), & ! (in)
797  cstr(dim_name), dtype, dim_size, bounds_ ) ! (in)
798  if ( error /= file_success_code .and. error /= file_already_existed_code ) then
799  log_error("FILE_def_axis",*) 'failed to define axis'
800  call prc_abort
801  end if
802 
803  call prof_rapend ('FILE_Write', 2, disable_barrier = .not. file_files(fid)%allnodes )
804 
805  return

References scale_file_h::cstr(), scale_precision::dp, scale_file_h::file_already_existed_code, file_def_axis_c(), file_opened(), file_put_associatedcoordinate_c(), scale_file_h::file_success_code, file_write_axis_c(), i, scale_prc::prc_abort(), scale_prof::prof_rapend(), scale_prof::prof_rapstart(), and scale_precision::sp.

Referenced by scale_file_cartesc::file_cartesc_def_axes(), and scale_file_history::file_history_finalize().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ file_def_associatedcoordinate()

subroutine, public scale_file::file_def_associatedcoordinate ( integer, intent(in)  fid,
character(len=*), intent(in)  name,
character(len=*), intent(in)  desc,
character(len=*), intent(in)  units,
character(len=*), dimension(:), intent(in)  dim_names,
integer, intent(in)  dtype 
)

Definition at line 1472 of file scale_file.F90.

1472  integer, intent(in) :: fid
1473  character(len=*), intent(in) :: name
1474  character(len=*), intent(in) :: desc
1475  character(len=*), intent(in) :: units
1476  character(len=*), intent(in) :: dim_names(:)
1477  integer, intent(in) :: dtype
1478 
1479  type(c_ptr) :: dim_names_(size(dim_names))
1480 ! character(:,c_char), allocatable, target :: cptr(:)
1481  character(len=H_SHORT+1), allocatable, target :: cptr(:)
1482 
1483  integer :: error
1484  integer :: i
1485  intrinsic size, len
1486 
1487  if ( .not. file_opened(fid) ) then
1488  log_error("FILE_def_associatedCoordinate",*) 'File is not opened. fid = ', fid
1489  call prc_abort
1490  end if
1491 
1492  call prof_rapstart('FILE_Write', 2, disable_barrier = .not. file_files(fid)%allnodes )
1493 
1494  !allocate( character(len=len(dim_names)+1) :: cptr(size(dim_names)) )
1495  allocate( cptr(size(dim_names)) )
1496  do i = 1, size(dim_names)
1497  cptr(i) = cstr(dim_names(i))
1498  dim_names_(i) = c_loc(cptr(i))
1499  end do
1500 
1502  file_files(fid)%fid, & ! (in)
1503  cstr(name), cstr(desc), cstr(units), & ! (in)
1504  dim_names_, size(dim_names), dtype ) ! (in)
1505  if ( error /= file_success_code .and. error /= file_already_existed_code ) then
1506  log_error("FILE_def_associatedCoordinate",*) 'failed to define associated coordinate: '//trim(name)
1507  call prc_abort
1508  end if
1509 
1510  call prof_rapend ('FILE_Write', 2, disable_barrier = .not. file_files(fid)%allnodes )
1511 
1512  return

References file_add_variable_c(), file_def_associatedcoordinate_c(), file_opened(), file_write_associatedcoordinate_c(), and i.

Referenced by scale_file_cartesc::file_cartesc_def_axes(), and scale_file_history::file_history_finalize().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ file_def_variable()

subroutine, public scale_file::file_def_variable ( integer, intent(in)  fid,
character(len=*), intent(in)  varname,
character(len=*), intent(in)  desc,
character(len=*), intent(in)  units,
character(len=*), intent(in)  standard_name,
integer, intent(in)  ndims,
character(len=*), dimension(:), intent(in)  dims,
integer, intent(in)  dtype,
integer, intent(out)  vid,
real(dp), intent(in), optional  time_int,
character(len=*), intent(in), optional  time_stats,
logical, intent(out), optional  existed 
)

Definition at line 2381 of file scale_file.F90.

2381  integer, intent( in) :: fid
2382  character(len=*), intent( in) :: varname
2383  character(len=*), intent( in) :: desc
2384  character(len=*), intent( in) :: units
2385  character(len=*), intent( in) :: standard_name
2386  integer, intent( in) :: ndims
2387  character(len=*), intent( in) :: dims(:)
2388  integer, intent( in) :: dtype
2389  integer, intent(out) :: vid
2390  real(DP), intent( in), optional :: time_int
2391  character(len=*), intent( in), optional :: time_stats
2392  logical, intent(out), optional :: existed
2393 
2394  type(c_ptr) :: dims_(size(dims))
2395  !character(:,c_char), allocatable, target :: cptr(:)
2396  character(len=H_SHORT), allocatable, target :: cptr(:)
2397 
2398  character(len=4) :: ctstats
2399 
2400  real(DP) :: tint_
2401  integer :: cvid
2402  integer :: error
2403  integer :: n
2404 
2405  !---------------------------------------------------------------------------
2406 
2407  if ( .not. file_opened(fid) ) then
2408  log_error("FILE_def_variable",*) 'File is not opened. fid = ', fid
2409  call prc_abort
2410  end if
2411 
2412  call prof_rapstart('FILE_Write', 2, disable_barrier = .not. file_files(fid)%allnodes )
2413 
2414  vid = -1
2415  do n = 1, file_nvars
2416  if ( file_vars(n)%fid == fid .and. file_vars(n)%name == varname ) then
2417  vid = n
2418  end if
2419  enddo
2420 
2421  if ( vid < 0 ) then ! variable registration
2422 
2423  if ( present(time_int) ) then
2424  tint_ = time_int
2425  else
2426  tint_ = -1.0_dp
2427  endif
2428 
2429  ctstats = "none"
2430  if ( present(time_stats) ) then
2431  ctstats = time_stats
2432  end if
2433 
2434  !allocate( character(len=len(dims)+1) :: cptr(ndims) )
2435  allocate( cptr(ndims) )
2436  do n = 1, ndims
2437  cptr(n) = cstr(dims(n))
2438  dims_(n) = c_loc(cptr(n))
2439  end do
2440 
2441  error = file_add_variable_c( cvid, & ! [OUT]
2442  file_files(fid)%fid, & ! [IN]
2443  cstr(varname), cstr(desc), & ! [IN]
2444  cstr(units), cstr(standard_name), & ! [IN]
2445  dims_, ndims, dtype, tint_, cstr(ctstats) ) ! [IN]
2446 
2447  if ( error /= file_success_code ) then
2448  log_error("FILE_def_variable",*) 'failed to add variable: '//trim(varname)
2449  call prc_abort
2450  end if
2451 
2452  file_nvars = file_nvars + 1
2453  vid = file_nvars
2454  file_vars(vid)%name = varname
2455  file_vars(vid)%vid = cvid
2456  file_vars(vid)%fid = fid
2457 
2458  log_info("FILE_def_variable",'(1x,A,I3.3,A,I4.4,2A)') &
2459  'Variable registration : NO.', fid, ', vid = ', vid, ', name = ', trim(varname)
2460 
2461  if ( present(existed) ) existed = .false.
2462  else
2463  if ( present(existed) ) existed = .true.
2464  endif
2465 
2466  call prof_rapend ('FILE_Write', 2, disable_barrier = .not. file_files(fid)%allnodes )
2467 
2468  return

References file_add_variable_c(), file_get_attribute_double_c(), file_get_attribute_float_c(), file_get_attribute_int_c(), file_get_attribute_text_c(), file_get_datainfo_c(), file_open(), file_opened(), file_set_attribute_double_c(), file_set_attribute_float_c(), file_set_attribute_int_c(), and file_set_attribute_text_c().

Referenced by scale_file_cartesc::file_cartesc_def_var().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ file_get_stepsize()

subroutine, public scale_file::file_get_stepsize ( integer, intent(in)  fid,
character(len=*), intent(in)  varname,
integer, intent(out)  len,
logical, intent(out), optional  error 
)

get number of steps

Definition at line 3335 of file scale_file.F90.

3335  integer, intent(in) :: fid
3336  character(len=*), intent(in) :: varname
3337 
3338  integer, intent(out) :: len
3339 
3340  logical, intent(out), optional :: error
3341 
3342  integer :: ierror
3343 
3344  if ( .not. file_opened(fid) ) then
3345  log_error("FILE_get_stepSize",*) 'File is not opened. fid = ', fid
3346  call prc_abort
3347  end if
3348 
3349  call prof_rapstart('FILE_Read', 2, disable_barrier = .not. file_files(fid)%allnodes )
3350 
3351  ierror = file_get_step_size_c( len, & ! (out)
3352  file_files(fid)%fid, cstr(varname) ) ! (in)
3353  if ( ierror /= file_success_code .and. ierror /= file_already_existed_code ) then
3354  if ( present(error) ) then
3355  error = .true.
3356  else
3357  log_error("FILE_get_stepSize",*) 'failed to get number of steps'
3358  call prc_abort
3359  end if
3360  else
3361  if ( present(error) ) error = .false.
3362  end if
3363 
3364  call prof_rapend ('FILE_Read', 2, disable_barrier = .not. file_files(fid)%allnodes )
3365 
3366  return

References file_get_datainfo_c(), file_get_step_size_c(), file_open(), file_opened(), file_read_data_c(), file_write_data_c(), and i.

Here is the call graph for this function:

◆ file_enddef()

subroutine, public scale_file::file_enddef ( integer, intent(in)  fid)

Definition at line 6061 of file scale_file.F90.

6061  implicit none
6062 
6063  integer, intent(in) :: fid
6064 
6065  integer :: error
6066  !---------------------------------------------------------------------------
6067 
6068  if ( .not. file_opened(fid) ) return
6069 
6070  call prof_rapstart('FILE_Write', 2, disable_barrier = .not. file_files(fid)%allnodes )
6071 
6072  error = file_enddef_c( file_files(fid)%fid )
6073 
6074  if ( error == file_success_code ) then
6075 
6076  log_newline
6077  log_info("FILE_enddef",'(1x,A,I3.3,2A)') &
6078  'End define mode : No.', fid, ', name = ', trim(file_files(fid)%name)
6079 
6080  else
6081  log_error("FILE_enddef",*) 'failed to exit define mode'
6082  call prc_abort
6083  end if
6084 
6085  call prof_rapend ('FILE_Write', 2, disable_barrier = .not. file_files(fid)%allnodes )
6086 
6087  return

References file_enddef_c(), and file_opened().

Referenced by scale_file_cartesc::file_cartesc_enddef(), scale_file_history::file_history_set_attribute_double(), and scale_file_history::file_history_write().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ file_redef()

subroutine, public scale_file::file_redef ( integer, intent(in)  fid)

Definition at line 6093 of file scale_file.F90.

6093  implicit none
6094 
6095  integer, intent(in) :: fid
6096 
6097  integer :: error
6098  !---------------------------------------------------------------------------
6099 
6100  if ( .not. file_opened(fid) ) return
6101 
6102  call prof_rapstart('FILE_Write', 2, disable_barrier = .not. file_files(fid)%allnodes )
6103 
6104  error = file_redef_c( file_files(fid)%fid )
6105 
6106  if ( error == file_success_code ) then
6107 
6108  log_newline
6109  log_info("FILE_redef",'(1x,A,I3.3,2A)') &
6110  'Enter to define mode : No.', fid, ', name = ', trim(file_files(fid)%name)
6111 
6112  else
6113  log_error("FILE_redef",*) 'failed to enter to define mode'
6114  call prc_abort
6115  end if
6116 
6117  call prof_rapend ('FILE_Write', 2, disable_barrier = .not. file_files(fid)%allnodes )
6118 
6119  return

References file_opened(), and file_redef_c().

Referenced by scale_file_history::file_history_finalize().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ file_attach_buffer()

subroutine, public scale_file::file_attach_buffer ( integer, intent(in)  fid,
integer(8), intent(in)  buf_amount 
)

Definition at line 6127 of file scale_file.F90.

6127  implicit none
6128 
6129  integer, intent(in) :: fid
6130  integer(8), intent(in) :: buf_amount
6131 
6132  integer :: error
6133  !---------------------------------------------------------------------------
6134 
6135  if ( .not. file_opened(fid) ) return
6136 
6137  if ( file_files(fid)%buffer_size > 0 ) then
6138  call file_detach_buffer(fid)
6139  end if
6140 
6141  call prof_rapstart('FILE_Write', 2, disable_barrier = .not. file_files(fid)%allnodes )
6142 
6143  error = file_attach_buffer_c( file_files(fid)%fid, buf_amount )
6144 
6145  if ( error /= file_success_code ) then
6146  log_error("FILE_attach_buffer",*) 'failed to attach buffer in PnetCDF'
6147  call prc_abort
6148  end if
6149 
6150  log_newline
6151  log_info("FILE_attach_buffer",'(1x,A,I3.3,3A,I10)') &
6152  'Attach buffer : No.', fid, ', name = ', trim(file_files(fid)%name), &
6153  ', size = ', buf_amount
6154 
6155  file_files(fid)%buffer_size = buf_amount
6156 
6157  call prof_rapend ('FILE_Write', 2, disable_barrier = .not. file_files(fid)%allnodes )
6158 
6159  return

References file_attach_buffer_c(), file_detach_buffer(), and file_opened().

Referenced by scale_file_cartesc::file_cartesc_enddef(), and scale_file_history::file_history_finalize().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ file_detach_buffer()

subroutine, public scale_file::file_detach_buffer ( integer, intent(in)  fid)

Definition at line 6165 of file scale_file.F90.

6165  implicit none
6166 
6167  integer, intent(in) :: fid
6168 
6169  integer :: error
6170  !---------------------------------------------------------------------------
6171 
6172  if ( .not. file_opened(fid) ) return
6173 
6174  if ( file_files(fid)%fid < 0 ) return ! already closed
6175 
6176  if ( file_files(fid)%buffer_size < 0 ) return ! not attached
6177 
6178  call prof_rapstart('FILE_Write', 2, disable_barrier = .not. file_files(fid)%allnodes )
6179 
6180  error = file_detach_buffer_c( file_files(fid)%fid )
6181 
6182  if ( error /= file_success_code ) then
6183  log_error("FILE_detach_buffer",*) 'failed to detach buffer in PnetCDF'
6184  call prc_abort
6185  end if
6186 
6187  log_newline
6188  log_info("FILE_detach_buffer",'(1x,A,I3.3,2A)') &
6189  'Detach buffer : No.', fid, ', name = ', trim(file_files(fid)%name)
6190 
6191  file_files(fid)%buffer_size = -1
6192 
6193  call prof_rapend ('FILE_Write', 2, disable_barrier = .not. file_files(fid)%allnodes )
6194 
6195  return

References file_detach_buffer_c(), and file_opened().

Referenced by file_attach_buffer(), scale_file_cartesc::file_cartesc_close(), and scale_file_history::file_history_finalize().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ file_flush()

subroutine, public scale_file::file_flush ( integer, intent(in)  fid)

Definition at line 6201 of file scale_file.F90.

6201  implicit none
6202 
6203  integer, intent(in) :: fid
6204 
6205  integer :: error
6206  !---------------------------------------------------------------------------
6207 
6208  if ( .not. file_opened(fid) ) return
6209 
6210  if ( file_files(fid)%fid < 0 ) return ! already closed
6211 
6212  call prof_rapstart('FILE', 2, disable_barrier = .not. file_files(fid)%allnodes )
6213 
6214  error = file_flush_c( file_files(fid)%fid )
6215 
6216  if ( error == file_success_code ) then
6217 
6218 !!$ LOG_NEWLINE
6219 !!$ LOG_INFO("FILE_flush",'(1xA,I3.3,2A)') &
6220 !!$ 'Flush : No.', fid, ', name = ', trim(FILE_files(fid)%name)
6221 
6222  else
6223  log_error("FILE_flush",*) 'failed to flush data to netcdf file'
6224  call prc_abort
6225  end if
6226 
6227  call prof_rapend ('FILE', 2, disable_barrier = .not. file_files(fid)%allnodes )
6228 
6229  return

References file_flush_c(), and file_opened().

Referenced by scale_file_cartesc::file_cartesc_close(), scale_file_cartesc::file_cartesc_enddef(), scale_file_cartesc::file_cartesc_flush(), scale_file_history::file_history_finalize(), scale_file_history::file_history_set_attribute_double(), and scale_file_history::file_history_write().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ file_close()

subroutine, public scale_file::file_close ( integer, intent(in)  fid,
logical, intent(in), optional  abort 
)

Definition at line 6234 of file scale_file.F90.

6234  implicit none
6235  integer, intent(in) :: fid
6236  logical, intent(in), optional :: abort
6237 
6238  logical(c_bool) :: abort_
6239  integer :: error
6240  integer :: n
6241  !---------------------------------------------------------------------------
6242 
6243  if ( .not. file_opened(fid) ) return
6244 
6245  if ( file_files(fid)%fid < 0 ) return ! already closed
6246 
6247  call prof_rapstart('FILE', 2, disable_barrier = .not. file_files(fid)%allnodes )
6248 
6249  if ( present(abort) ) then
6250  abort_ = abort
6251  else
6252  abort_ = .false.
6253  end if
6254 
6255  error = file_close_c( file_files(fid)%fid, abort_ )
6256 
6257  if ( error == file_success_code ) then
6258 
6259  log_newline
6260  log_info("FILE_close",'(1x,A,I3.3,2A)') &
6261  'Close : No.', fid, ', name = ', trim(file_files(fid)%name)
6262 
6263  elseif( error /= file_already_closed_code ) then
6264  log_error("FILE_close",*) 'failed to close file: ', trim(file_files(fid)%name)
6265  if ( .not. abort_ ) call prc_abort
6266  end if
6267 
6268  file_files(fid)%fid = -1
6269  file_files(fid)%name = ''
6270  file_files(fid)%aggregate = .false.
6271  file_files(fid)%buffer_size = -1
6272 
6273  do n = 1, file_nvars
6274  if ( file_vars(n)%fid == fid ) then
6275  file_vars(n)%vid = -1
6276  file_vars(n)%name = ''
6277  end if
6278  end do
6279 
6280  call prof_rapend ('FILE', 2, disable_barrier = .not. file_files(fid)%allnodes )
6281 
6282  return

References file_close_c(), and file_opened().

Referenced by scale_atmos_phy_rd_profile::atmos_phy_rd_profile_finalize(), mod_copytopo::copytopo_get_data_scale(), mod_copytopo::copytopo_get_data_wrfarw(), scale_file_cartesc::file_cartesc_close(), file_close_all(), and scale_file_history::file_history_finalize().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ file_close_all()

subroutine, public scale_file::file_close_all ( logical, intent(in), optional  skip_abort)

Definition at line 6287 of file scale_file.F90.

6287  implicit none
6288  logical, intent(in), optional :: skip_abort
6289 
6290  integer :: fid
6291  !---------------------------------------------------------------------------
6292 
6293  do fid = 1, file_nfiles
6294  call file_close( fid, skip_abort )
6295  enddo
6296 
6297  return

References file_close().

Referenced by file_setup(), mod_rm_driver::rm_driver(), mod_rm_prep::rm_prep(), and scale::scale_finalize().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ file_get_cftunits()

subroutine, public scale_file::file_get_cftunits ( integer, dimension(6), intent(in)  date,
character(len=*), intent(out)  tunits 
)

get unit of time

Definition at line 6304 of file scale_file.F90.

6304  implicit none
6305 
6306  integer, intent(in) :: date(6)
6307  character(len=*), intent(out) :: tunits
6308  !---------------------------------------------------------------------------
6309 
6310  write(tunits,'(a,i4.4,"-",i2.2,"-",i2.2," ",i2.2,":",i2.2,":",i2.2)') 'seconds since ', date
6311 
6312  return

Referenced by scale_file_cartesc::file_cartesc_create(), and scale_file_history_cartesc::file_history_cartesc_truncate_3d().

Here is the caller graph for this function:

◆ file_get_aggregate()

logical function, public scale_file::file_get_aggregate ( integer, intent(in)  fid)

Definition at line 6316 of file scale_file.F90.

6316  integer, intent(in) :: fid
6317  logical :: FILE_get_aggregate
6318 
6319  if ( .not. file_opened(fid) ) then
6320  file_get_aggregate = .false.
6321  else
6322  file_get_aggregate = file_files(fid)%aggregate
6323  end if
6324 
6325  return

References file_aggregate, file_open_c(), file_opened(), scale_prc::prc_comm_null, and scale_prc::prc_local_comm_world.

Referenced by mod_atmos_dyn_vars::atmos_dyn_vars_restart_read(), mod_atmos_phy_ae_vars::atmos_phy_ae_vars_restart_read(), mod_atmos_phy_bl_vars::atmos_phy_bl_vars_restart_read(), mod_atmos_phy_ch_vars::atmos_phy_ch_vars_restart_read(), mod_atmos_phy_cp_vars::atmos_phy_cp_vars_restart_read(), mod_atmos_phy_lt_vars::atmos_phy_lt_vars_restart_read(), mod_atmos_phy_mp_vars::atmos_phy_mp_vars_restart_read(), mod_atmos_phy_rd_vars::atmos_phy_rd_vars_restart_read(), mod_atmos_phy_sf_vars::atmos_phy_sf_vars_restart_read(), mod_atmos_vars::atmos_vars_restart_check(), mod_atmos_vars::atmos_vars_restart_read(), scale_file_cartesc::file_cartesc_close(), scale_file_cartesc::file_cartesc_def_axes(), scale_file_cartesc::file_cartesc_enddef(), scale_file_cartesc::file_cartesc_flush(), scale_file_cartesc::file_cartesc_read_1d(), scale_file_cartesc::file_cartesc_read_var_2d(), scale_file_cartesc::file_cartesc_read_var_3d(), scale_file_cartesc::file_cartesc_read_var_4d(), scale_file_cartesc::file_cartesc_write_axes(), scale_file_cartesc::file_cartesc_write_var_1d(), scale_file_cartesc::file_cartesc_write_var_2d(), scale_file_cartesc::file_cartesc_write_var_3d(), scale_file_cartesc::file_cartesc_write_var_3d_t(), scale_file_cartesc::file_cartesc_write_var_4d(), mod_land_vars::land_vars_restart_read(), mod_ocean_vars::ocean_vars_restart_read(), and mod_urban_vars::urban_vars_restart_read().

Here is the call graph for this function:
Here is the caller graph for this function:

Variable Documentation

◆ file_aggregate

logical, public scale_file::file_aggregate

◆ do

logical, public scale_file::do

Definition at line 196 of file scale_file.F90.

◆ parallel

logical, public scale_file::parallel

Definition at line 196 of file scale_file.F90.

◆ i

logical, public scale_file::i

◆ o

logical, public scale_file::o

Definition at line 196 of file scale_file.F90.

◆ through

logical, public scale_file::through

Definition at line 196 of file scale_file.F90.

◆ pnetcdf

logical, dimension (default setting), public scale_file::pnetcdf

Definition at line 196 of file scale_file.F90.

file_add_associatedvariable_c
int file_add_associatedvariable_c(const int fid, const char *vname)
Definition: scale_file_netcdf.c:1204
file_def_axis_c
int file_def_axis_c(const int fid, const char *name, const char *desc, const char *units, const char *dim_name, const int dtype, const int dim_size, const int bounds)
Definition: scale_file_netcdf.c:1286
file_detach_buffer_c
int file_detach_buffer_c(const int fid)
Definition: scale_file_netcdf.c:1854
scale_prc::prc_set_file_closer
subroutine, public prc_set_file_closer(routine)
Definition: scale_prc.F90:1048
file_get_dim_length_c
int file_get_dim_length_c(int *len, const int fid, const char *dimname, const bool suppress)
Definition: scale_file_netcdf.c:258
file_redef_c
int file_redef_c(const int fid)
Definition: scale_file_netcdf.c:1829
file_close_c
int file_close_c(const int fid, const bool abort)
Definition: scale_file_netcdf.c:2006
file_get_step_size_c
int file_get_step_size_c(int *len, const int fid, const char *varname)
Definition: scale_file_netcdf.c:643
scale_prc
module PROCESS
Definition: scale_prc.F90:11
file_attach_buffer_c
int file_attach_buffer_c(const int fid, const int64_t buf_amount)
Definition: scale_file_netcdf.c:1840
file_def_associatedcoordinate_c
int file_def_associatedcoordinate_c(const int fid, const char *name, const char *desc, const char *units, const char **dim_names, const int ndims, const int dtype)
Definition: scale_file_netcdf.c:1450
file_add_variable_c
int file_add_variable_c(int *vid, const int fid, const char *varname, const char *desc, const char *units, const char *stdname, const char **dims, const int ndims, const int dtype, const double tint, const char *tstats)
Definition: scale_file_netcdf.c:1550
file_set_tunits_c
int file_set_tunits_c(const int fid, const char *time_units, const char *calendar)
Definition: scale_file_netcdf.c:1227
file_set_option_c
int file_set_option_c(const int fid, const char *filetype, const char *key, const char *val)
Definition: scale_file_netcdf.c:287
file_enddef_c
int file_enddef_c(const int fid)
Definition: scale_file_netcdf.c:1818
file_flush_c
int file_flush_c(const int fid)
Definition: scale_file_netcdf.c:1867