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

module file / external_input More...

Data Types

interface  read2D
 
interface  read3D
 

Functions/Subroutines

subroutine, public file_external_input_setup
 Setup. More...
 
subroutine, public file_external_input_regist (basename, basename_add_num, number_of_files, varname, axistype, enable_periodic_year, enable_periodic_month, enable_periodic_day, step_fixed, offset, defval, check_coordinates, aggregate, allow_missing, step_limit, exist)
 Regist data. More...
 
subroutine file_external_input_update_1d (varname, time_current, var, error)
 Read data. More...
 
subroutine file_external_input_update_2d (varname, time_current, var, error)
 Read data. More...
 
subroutine file_external_input_update_3d (varname, time_current, var, error)
 Read data. More...
 

Variables

procedure(get_dims1d), pointer, public file_external_input_get_dims1d => NULL()
 
procedure(get_dims2d), pointer, public file_external_input_get_dims2d => NULL()
 
procedure(get_dims3d), pointer, public file_external_input_get_dims3d => NULL()
 
procedure(read1d), pointer, public file_external_input_read_1d => NULL()
 
procedure(read2d), pointer, public file_external_input_read_2d => NULL()
 
procedure(read3d), pointer, public file_external_input_read_3d => NULL()
 

Detailed Description

module file / external_input

Description
External file input module
Author
Team SCALE
NAMELIST
  • EXTERNAL_ITEM
    nametypedefault valuecomment
    BASENAME character(len=*)
    BASENAME_ADD_NUM logical
    NUMBER_OF_FILES integer
    VARNAME character(len=*) item name
    AXISTYPE character(len=*)
    STEP_LIMIT integer limit number for reading data
    STEP_FIXED integer fixed step position to read
    ENABLE_PERIODIC_YEAR logical treat as yearly periodic data?
    ENABLE_PERIODIC_MONTH logical treat as yearly,monthly periodic data?
    ENABLE_PERIODIC_DAY logical treat as yearly,monthly,daily periodic data?
    OFFSET real(RP)
    DEFVAL real(RP)
    CHECK_COORDINATES logical
    FILE_AGGREGATE logical
    ALLOW_MISSING logical

History Output
No history output

Function/Subroutine Documentation

◆ file_external_input_setup()

subroutine, public scale_file_external_input::file_external_input_setup

Setup.

Definition at line 207 of file scale_file_external_input.F90.

207  use scale_prc, only: &
208  prc_abort
209  use scale_const, only: &
210  undef => const_undef
211  use scale_file, only: &
212  file_aggregate_default => file_aggregate
213  implicit none
214 
215  character(len=H_LONG) :: basename
216  logical :: basename_add_num
217  integer :: number_of_files
218  character(len=H_SHORT) :: varname
219  character(len=H_SHORT) :: axistype
220  integer :: step_limit ! limit number for reading data
221  integer :: step_fixed ! fixed step position to read
222  logical :: enable_periodic_year ! treat as yearly periodic data?
223  logical :: enable_periodic_month ! treat as yearly,monthly periodic data?
224  logical :: enable_periodic_day ! treat as yearly,monthly,daily periodic data?
225  real(RP) :: offset
226  real(RP) :: defval
227  logical :: check_coordinates
228  logical :: file_aggregate
229  logical :: allow_missing
230 
231  namelist / external_item / &
232  basename, &
233  basename_add_num, &
234  number_of_files, &
235  varname, &
236  axistype, &
237  step_limit, &
238  step_fixed, &
239  enable_periodic_year, &
240  enable_periodic_month, &
241  enable_periodic_day, &
242  offset, &
243  defval, &
244  check_coordinates, &
245  file_aggregate, &
246  allow_missing
247 
248  integer :: count
249  integer :: ierr
250  !---------------------------------------------------------------------------
251 
252  log_newline
253  log_info("FILE_EXTERNAL_INPUT_setup",*) 'Setup'
254 
255  ! count external data from namelist
256  rewind(io_fid_conf)
257  do count = 1, file_external_input_item_limit
258  ! set default
259  step_limit = file_external_input_step_limit
260  basename = ''
261  basename_add_num = .false.
262  number_of_files = 1
263  varname = ''
264  axistype = ''
265  step_fixed = -1
266  enable_periodic_year = .false.
267  enable_periodic_month = .false.
268  enable_periodic_day = .false.
269  offset = 0.0_rp
270  defval = undef
271  check_coordinates = .false.
272  file_aggregate = file_aggregate_default
273  allow_missing = .false.
274 
275  ! read namelist
276  read(io_fid_conf,nml=external_item,iostat=ierr)
277  if ( ierr < 0 ) then !--- no more items
278  exit
279  elseif( ierr > 0 ) then !--- fatal error
280  log_error("FILE_EXTERNAL_INPUT_setup",*) 'Not appropriate names in namelist EXTERNAL_ITEM. Check!', count
281  call prc_abort
282  endif
283  log_nml(external_item)
284 
285  call file_external_input_regist( basename, & ! [IN]
286  basename_add_num, & ! [IN]
287  number_of_files, & ! [IN]
288  varname, & ! [IN]
289  axistype, & ! [IN]
290  enable_periodic_year, & ! [IN]
291  enable_periodic_month, & ! [IN]
292  enable_periodic_day, & ! [IN]
293  step_fixed, & ! [IN]
294  offset, & ! [IN]
295  defval, & ! [IN]
296  check_coordinates = check_coordinates, & ! [IN]
297  aggregate = file_aggregate, & ! [IN]
298  allow_missing = allow_missing, & ! [IN]
299  step_limit = step_limit ) ! [IN]
300  enddo
301 
302  return

References scale_const::const_undef, scale_file::file_aggregate, file_external_input_regist(), scale_io::io_fid_conf, and scale_prc::prc_abort().

Referenced by scale_file_external_input_cartesc::file_external_input_cartesc_setup().

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

◆ file_external_input_regist()

subroutine, public scale_file_external_input::file_external_input_regist ( character(len=*), intent(in)  basename,
logical, intent(in)  basename_add_num,
integer, intent(in)  number_of_files,
character(len=*), intent(in)  varname,
character(len=*), intent(in)  axistype,
logical, intent(in)  enable_periodic_year,
logical, intent(in)  enable_periodic_month,
logical, intent(in)  enable_periodic_day,
integer, intent(in)  step_fixed,
real(rp), intent(in)  offset,
real(rp), intent(in)  defval,
logical, intent(in), optional  check_coordinates,
logical, intent(in), optional  aggregate,
logical, intent(in), optional  allow_missing,
integer, intent(in), optional  step_limit,
logical, intent(out), optional  exist 
)

Regist data.

Definition at line 324 of file scale_file_external_input.F90.

324  use scale_file_h, only: &
325  file_fread
326  use scale_file, only: &
327  file_aggregate, &
328  file_open, &
329  file_get_all_datainfo, &
330  file_read
331  use scale_prc, only: &
332  prc_myrank, &
333  prc_abort
334  use scale_calendar, only: &
340  i_year, &
341  i_month, &
342  i_day
343  use scale_time, only: &
345  time_nowdaysec, &
347  use scale_file_cartesc, only: &
348  file_cartesc_check_coordinates
349  implicit none
350 
351  character(len=*), intent(in) :: basename
352  logical, intent(in) :: basename_add_num
353  integer, intent(in) :: number_of_files
354  character(len=*), intent(in) :: varname
355  character(len=*), intent(in) :: axistype
356  integer, intent(in) :: step_fixed ! fixed step position to read
357  logical, intent(in) :: enable_periodic_year ! treat as yearly periodic data?
358  logical, intent(in) :: enable_periodic_month ! treat as yearly,monthly periodic data?
359  logical, intent(in) :: enable_periodic_day ! treat as yearly,monthly,daily periodic data?
360  real(RP), intent(in) :: offset
361  real(RP), intent(in) :: defval
362 
363  logical, intent(in), optional :: check_coordinates
364  logical, intent(in), optional :: aggregate
365  logical, intent(in), optional :: allow_missing
366  integer, intent(in), optional :: step_limit ! limit number for reading data
367  logical, intent(out), optional :: exist
368 
369  integer :: step_nmax
370  character(len=H_MID) :: description
371  character(len=H_SHORT) :: unit
372  character(len=H_MID) :: standard_name
373  integer :: datatype
374  integer :: dim_rank
375  character(len=H_SHORT) :: dim_name (FILE_EXTERNAL_INPUT_dim_limit)
376  integer :: dim_size (FILE_EXTERNAL_INPUT_dim_limit)
377  integer :: var_size (FILE_EXTERNAL_INPUT_dim_limit)
378  integer :: natts
379  character(len=H_SHORT) :: att_name (FILE_EXTERNAL_INPUT_att_limit)
380  integer :: att_type (FILE_EXTERNAL_INPUT_att_limit)
381  integer :: att_len (FILE_EXTERNAL_INPUT_att_limit)
382  real(DP) :: time_start(FILE_EXTERNAL_INPUT_step_limit)
383  real(DP) :: time_end (FILE_EXTERNAL_INPUT_step_limit)
384  character(len=H_MID) :: time_units
385  character(len=H_SHORT) :: calendar
386 
387  integer :: datadate(6)
388  real(DP) :: datasubsec
389  integer :: dataday
390  real(DP) :: datasec
391  integer :: offset_year
392 
393  integer :: dim1_size, dim1_max, dim1_S
394  integer :: dim2_size, dim2_max, dim2_S
395  integer :: dim3_size, dim3_max, dim3_S
396 
397  integer :: step_limit_
398  logical :: aggregate_
399  logical :: allow_missing_
400 
401  character(len=H_LONG) :: filename
402 
403  integer :: fid
404  integer :: nid, n
405  !---------------------------------------------------------------------------
406 
407  if ( present(step_limit) ) then
408  if ( step_limit > 0 ) then
409  step_limit_ = step_limit
410  else
411  step_limit_ = file_external_input_step_limit
412  endif
413  else
414  step_limit_ = file_external_input_step_limit
415  endif
416 
417  if ( present(aggregate) ) then
418  aggregate_ = aggregate
419  else
420  aggregate_ = file_aggregate
421  end if
422 
423  if ( present(allow_missing) ) then
424  allow_missing_ = allow_missing
425  else
426  allow_missing_ = .false.
427  end if
428 
429  do nid = 1, file_external_input_item_count
430  if ( file_external_input_item(nid)%varname == varname ) then
431  log_error("FILE_EXTERNAL_INPUT_regist",*) 'Data is already registered! basename,varname = ', trim(basename), ', ', trim(varname)
432  call prc_abort
433  endif
434  enddo
435 
436  file_external_input_item_count = file_external_input_item_count + 1
437 
438  if ( file_external_input_item_count > file_external_input_item_limit ) then
439  log_error("FILE_EXTERNAL_INPUT_regist",*) 'Number of EXT data exceedes the limit', file_external_input_item_count, file_external_input_item_limit
440  call prc_abort
441  endif
442 
443  if ( number_of_files > 1 .or. basename_add_num ) then
444  filename = trim(basename) // '_00000'
445  else
446  filename = basename
447  end if
448 
449  call file_open( filename, & ! [IN]
450  fid, & ! [OUT]
451  aggregate=aggregate_, & ! [IN]
452  rankid=prc_myrank ) ! [IN]
453 
454  ! read from file
455  call file_get_all_datainfo( fid, varname, & ! [IN]
456  step_nmax, & ! [OUT]
457  description, unit, standard_name, & ! [OUT]
458  datatype, & ! [OUT]
459  dim_rank, dim_name(:), dim_size(:), & ! [OUT]
460  natts, att_name(:), att_type(:), att_len(:), & ! [OUT]
461  time_start(1:step_limit_), time_end(1:step_limit_), & ! [OUT]
462  time_units, calendar ) ! [OUT]
463 
464  if ( step_nmax > 0 ) then
465  if ( present(exist) ) then
466  exist = .true.
467  endif
468  else
469  if ( present(exist) ) then
470  exist = .false.
471  return
472  else
473  log_error("FILE_EXTERNAL_INPUT_regist",*) 'Data not found! filename,varname = ', trim(filename), ', ', trim(varname)
474  call prc_abort
475  endif
476  endif
477 
478  do n = dim_rank+1, 3
479  dim_size(n) = 1
480  var_size(n) = 1
481  enddo
482 
483  nid = file_external_input_item_count
484 
485  file_external_input_item(nid)%nfile = number_of_files
486  file_external_input_item(nid)%file_current = 1
487  file_external_input_item(nid)%data_step_offset = 0
488 
489  allocate( file_external_input_item(nid)%basename(number_of_files) )
490  if ( number_of_files > 1 .or. basename_add_num ) then
491  do n = 1, number_of_files
492  write(filename,'(A,A,I5.5)') trim(basename), '_', n - 1
493  file_external_input_item(nid)%basename(n) = filename
494  enddo
495  else
496  file_external_input_item(nid)%basename(1) = basename
497  end if
498 
499  ! setup item
500  file_external_input_item(nid)%fid = fid
501  file_external_input_item(nid)%varname = varname
502  file_external_input_item(nid)%axistype = axistype
503  file_external_input_item(nid)%ndim = dim_rank
504  file_external_input_item(nid)%step_num = step_nmax
505  file_external_input_item(nid)%step_limit = step_limit_
506  file_external_input_item(nid)%allow_missing = allow_missing_
507  file_external_input_item(nid)%aggregate = aggregate_
508 
509 
510  select case ( dim_rank )
511  case ( 1 )
512 
513  call file_external_input_get_dims1d( dim1_size, dim1_max, dim1_s, & ! [OUT]
514  varname, axistype ) ! [IN]
515 
516  if ( aggregate_ ) then
517  dim_size(1) = dim1_max
518  var_size(1) = dim1_size
519  file_external_input_item(nid)%var_start(1) = dim1_s
520  else
521  if ( dim1_max /= dim_size(1) ) then
522  log_error("FILE_EXTERNAL_INPUT_regist",*) 'data length does not match! ', trim(axistype), ' item:', trim(varname)
523  log_error_cont(*) 'dim 1 (data,requested) : ', dim_size(1), dim1_max
524  call prc_abort
525  endif
526  var_size(1) = dim1_max
527  file_external_input_item(nid)%var_start(1) = 1
528  end if
529 
530  file_external_input_item(nid)%transpose = .false.
531  file_external_input_item(nid)%dim_start(1) = dim1_s
532 
533  case ( 2 )
534 
535  call file_external_input_get_dims2d( dim1_size, dim1_max, dim1_s, & ! [OUT]
536  dim2_size, dim2_max, dim2_s, & ! [OUT]
537  file_external_input_item(nid)%transpose, & ! [OUT]
538  varname, axistype ) ! [IN]
539 
540  if ( aggregate_ ) then
541  dim_size(1) = dim1_max
542  var_size(1) = dim1_size
543  dim_size(2) = dim2_max
544  var_size(2) = dim2_size
545  file_external_input_item(nid)%var_start(1) = dim1_s
546  file_external_input_item(nid)%var_start(1) = dim2_s
547  else
548  if ( dim1_max /= dim_size(1) &
549  .OR. dim2_max /= dim_size(2) ) then
550  log_error("FILE_EXTERNAL_INPUT_regist",*) 'data length does not match! ', trim(axistype), ' item:', trim(varname)
551  log_error_cont(*) 'dim 1 (data,requested) : ', dim_size(1), dim1_max
552  log_error_cont(*) 'dim 2 (data,requested) : ', dim_size(2), dim2_max
553  call prc_abort
554  endif
555  var_size(1) = dim1_max
556  var_size(2) = dim2_max
557  file_external_input_item(nid)%var_start(1) = 1
558  file_external_input_item(nid)%var_start(1) = 1
559  end if
560 
561  file_external_input_item(nid)%dim_start(1) = dim1_s
562  file_external_input_item(nid)%dim_start(2) = dim2_s
563 
564  case ( 3 )
565 
566  call file_external_input_get_dims3d( dim1_size, dim1_max, dim1_s, & ! [OUT]
567  dim2_size, dim2_max, dim2_s, & ! [OUT]
568  dim3_size, dim3_max, dim3_s, & ! [OUT]
569  file_external_input_item(nid)%transpose, & ! [OUT]
570  varname, axistype ) ! [IN]
571 
572  if ( aggregate_ ) then
573  dim_size(1) = dim1_max
574  var_size(1) = dim1_size
575  dim_size(2) = dim2_max
576  var_size(2) = dim2_size
577  dim_size(3) = dim3_max
578  var_size(3) = dim3_size
579  file_external_input_item(nid)%var_start(1) = dim1_s
580  file_external_input_item(nid)%var_start(2) = dim2_s
581  file_external_input_item(nid)%var_start(3) = dim3_s
582  else
583  if ( dim1_max /= dim_size(1) &
584  .OR. dim2_max /= dim_size(2) &
585  .OR. dim3_max /= dim_size(3) ) then
586  log_error("FILE_EXTERNAL_INPUT_regist",*) 'data length does not match! ', trim(axistype), ' item:', trim(varname)
587  log_error_cont(*) 'dim 1 (data,requested) : ', dim_size(1), dim1_max
588  log_error_cont(*) 'dim 2 (data,requested) : ', dim_size(2), dim2_max
589  log_error_cont(*) 'dim 3 (data,requested) : ', dim_size(3), dim3_max
590  call prc_abort
591  endif
592  var_size(1) = dim1_max
593  var_size(2) = dim2_max
594  var_size(3) = dim3_max
595  file_external_input_item(nid)%var_start(1) = 1
596  file_external_input_item(nid)%var_start(2) = 1
597  file_external_input_item(nid)%var_start(3) = 1
598  end if
599 
600  file_external_input_item(nid)%dim_start(1) = dim1_s
601  file_external_input_item(nid)%dim_start(2) = dim2_s
602  file_external_input_item(nid)%dim_start(3) = dim3_s
603 
604  case default
605  log_error("FILE_EXTERNAL_INPUT_regist",*) 'Unexpected dim rank: ', dim_rank
606  call prc_abort
607  end select
608 
609  file_external_input_item(nid)%dim_size(:) = dim_size(:)
610 
611 
612  if ( enable_periodic_day ) then
613  file_external_input_item(nid)%flag_periodic = i_periodic_day
614  elseif( enable_periodic_month ) then
615  file_external_input_item(nid)%flag_periodic = i_periodic_month
616  elseif( enable_periodic_year ) then
617  file_external_input_item(nid)%flag_periodic = i_periodic_year
618  else
619  file_external_input_item(nid)%flag_periodic = 0
620  endif
621 
622  allocate( file_external_input_item(nid)%value(var_size(1),var_size(2),var_size(3),2) )
623 
624 
625  file_external_input_item(nid)%value(:,:,:,:) = defval
626  file_external_input_item(nid)%offset = offset
627 
628  allocate( file_external_input_item(nid)%time(step_limit_) )
629  file_external_input_item(nid)%time(:) = 0.0_dp
630 
631  do n = 1, file_external_input_item(nid)%step_num
632  file_external_input_item(nid)%time(n) = calendar_cfunits2sec( time_end(n), time_units, time_offset_year, time_startdaysec )
633  enddo
634 
635  if ( file_external_input_item(nid)%step_num == 1 ) then
636 
637  file_external_input_item(nid)%fixed_step = .true.
638  file_external_input_item(nid)%data_step_prev = 1
639  file_external_input_item(nid)%data_step_next = 1
640 
641  else if ( step_fixed > 0 ) then ! fixed time step mode
642 
643  file_external_input_item(nid)%fixed_step = .true.
644  file_external_input_item(nid)%data_step_prev = step_fixed
645  file_external_input_item(nid)%data_step_next = step_fixed
646 
647  else
648 
649  file_external_input_item(nid)%fixed_step = .false.
650 
651  ! seek start position
652  file_external_input_item(nid)%data_step_next = 1
653  do n = 1, file_external_input_item(nid)%step_num
654  if ( file_external_input_item(nid)%time(n) > time_nowdaysec ) exit
655  file_external_input_item(nid)%data_step_next = n + 1
656  enddo
657 
658  file_external_input_item(nid)%data_step_prev = file_external_input_item(nid)%data_step_next - 1
659 
660  if ( file_external_input_item(nid)%flag_periodic > 0 ) then ! periodic time step mode
661 
662  if ( file_external_input_item(nid)%data_step_next == 1 ) then ! between first-1 and first
663 
664  ! first-1 = last
665  file_external_input_item(nid)%data_step_prev = file_external_input_item(nid)%step_num
666 
667  elseif( file_external_input_item(nid)%data_step_next == file_external_input_item(nid)%step_num+1 ) then ! between last and last+1
668 
669  ! last+1 = first
670  file_external_input_item(nid)%data_step_next = 1
671 
672  ! update data time in periodic condition
673  do n = 1, file_external_input_item(nid)%step_num
674  dataday = 0
675  datasec = file_external_input_item(nid)%time(n)
676  offset_year = 0
677  call calendar_adjust_daysec( dataday, datasec ) ! [INOUT]
678 
679  call calendar_daysec2date( datadate(:), & ! [OUT]
680  datasubsec, & ! [OUT]
681  dataday, & ! [IN]
682  datasec, & ! [IN]
683  offset_year ) ! [IN]
684 
685  if ( file_external_input_item(nid)%flag_periodic == i_periodic_day ) then
686  datadate(i_day) = datadate(i_day) + 1
687  elseif( file_external_input_item(nid)%flag_periodic == i_periodic_month ) then
688  datadate(i_month) = datadate(i_month) + 1
689  elseif( file_external_input_item(nid)%flag_periodic == i_periodic_year ) then
690  datadate(i_year) = datadate(i_year) + 1
691  endif
692 
693  call calendar_date2daysec( dataday, & ! [OUT]
694  datasec, & ! [OUT]
695  datadate(:), & ! [IN]
696  datasubsec, & ! [IN]
697  offset_year ) ! [IN]
698 
699  file_external_input_item(nid)%time(n) = calendar_combine_daysec( dataday, datasec )
700  enddo
701 
702  log_info("FILE_EXTERNAL_INPUT_regist",*) 'data time is updated.'
703  endif
704 
705  else ! normal mode
706 
707  if ( file_external_input_item(nid)%data_step_next == 1 &
708  .OR. file_external_input_item(nid)%data_step_next == file_external_input_item(nid)%step_num+1 ) then
709  log_error("FILE_EXTERNAL_INPUT_regist",*) 'Current time is out of period of external data! ', trim(varname)
710  call prc_abort
711  endif
712 
713  endif
714 
715  endif
716 
717  !--- read first data
718  log_info("FILE_EXTERNAL_INPUT_regist",'(1x,A,A15)') 'Initial read of external data : ', trim(varname)
719 
720  select case ( dim_rank )
721  case ( 1 )
722 
723  ! read prev
724  log_info("FILE_EXTERNAL_INPUT_regist",'(1x,A,A,A,I4,A)') &
725  'Read 1D var : ', trim(file_external_input_item(nid)%varname), &
726  ' (step= ', file_external_input_item(nid)%data_step_prev, ')'
727 
728  if ( file_external_input_item(nid)%aggregate ) then
729  call file_external_input_read_1d( file_external_input_item(nid)%fid, & ! [IN]
730  file_external_input_item(nid)%varname, & ! [IN]
731  file_external_input_item(nid)%axistype, & ! [IN]
732  file_external_input_item(nid)%value(:,1,1,i_prev), & ! [OUT]
733  step=file_external_input_item(nid)%data_step_prev ) ! [IN]
734  else
735  call file_read( file_external_input_item(nid)%fid, & ! [IN]
736  file_external_input_item(nid)%varname, & ! [IN]
737  file_external_input_item(nid)%value(:,1,1,i_prev), & ! [OUT]
738  step=file_external_input_item(nid)%data_step_prev ) ! [IN]
739  end if
740 
741  ! read next
742  log_info("FILE_EXTERNAL_INPUT_regist",'(1x,A,A,A,I4,A)') &
743  'Read 1D var : ', trim(file_external_input_item(nid)%varname), &
744  ' (step= ', file_external_input_item(nid)%data_step_next, ')'
745 
746  if ( file_external_input_item(nid)%aggregate ) then
747  call file_external_input_read_1d( file_external_input_item(nid)%fid, & ! [IN]
748  file_external_input_item(nid)%varname, & ! [IN]
749  file_external_input_item(nid)%axistype, & ! [IN]
750  file_external_input_item(nid)%value(:,1,1,i_next), & ! [OUT]
751  step=file_external_input_item(nid)%data_step_next ) ! [IN]
752  else
753  call file_read( file_external_input_item(nid)%fid, & ! [IN]
754  file_external_input_item(nid)%varname, & ! [IN]
755  file_external_input_item(nid)%value(:,1,1,i_next), & ! [OUT]
756  step=file_external_input_item(nid)%data_step_next ) ! [IN]
757  end if
758 
759  case ( 2 )
760 
761  ! read prev
762  log_info("FILE_EXTERNAL_INPUT_regist",'(1x,A,A,A,I4,A)') &
763  'Read 2D var : ', trim(file_external_input_item(nid)%varname), &
764  ' (step= ', file_external_input_item(nid)%data_step_prev, ')'
765 
766  if ( file_external_input_item(nid)%aggregate ) then
767  call file_external_input_read_2d( file_external_input_item(nid)%fid, & ! [IN]
768  file_external_input_item(nid)%varname, & ! [IN]
769  file_external_input_item(nid)%axistype, & ! [IN]
770  file_external_input_item(nid)%value(:,:,1,i_prev), & ! [OUT]
771  step=file_external_input_item(nid)%data_step_prev ) ! [IN]
772  else
773  call file_read( file_external_input_item(nid)%fid, & ! [IN]
774  file_external_input_item(nid)%varname, & ! [IN]
775  file_external_input_item(nid)%value(:,:,1,i_prev), & ! [OUT]
776  step=file_external_input_item(nid)%data_step_prev ) ! [IN]
777  end if
778  ! read next
779  log_info("FILE_EXTERNAL_INPUT_regist",'(1x,A,A,A,I4,A)') &
780  'Read 2D var : ', trim(file_external_input_item(nid)%varname), &
781  ' (step= ', file_external_input_item(nid)%data_step_next, ')'
782 
783  if ( file_external_input_item(nid)%aggregate ) then
784  call file_external_input_read_2d( file_external_input_item(nid)%fid, & ! [IN]
785  file_external_input_item(nid)%varname, & ! [IN]
786  file_external_input_item(nid)%axistype, & ! [IN]
787  file_external_input_item(nid)%value(:,:,1,i_next), & ! [OUT]
788  step=file_external_input_item(nid)%data_step_next ) ! [IN]
789  else
790  call file_read( file_external_input_item(nid)%fid, & ! [IN]
791  file_external_input_item(nid)%varname, & ! [IN]
792  file_external_input_item(nid)%value(:,:,1,i_next), & ! [OUT]
793  step=file_external_input_item(nid)%data_step_next ) ! [IN]
794  end if
795 
796  case ( 3 )
797 
798  ! read prev
799  log_info("FILE_EXTERNAL_INPUT_regist",'(1x,A,A,A,I4,A)') &
800  'Read 3D var : ', trim(file_external_input_item(nid)%varname), &
801  ' (step= ', file_external_input_item(nid)%data_step_prev, ')'
802 
803  if ( file_external_input_item(nid)%aggregate ) then
804  call file_external_input_read_3d( file_external_input_item(nid)%fid, & ! [IN]
805  file_external_input_item(nid)%varname, & ! [IN]
806  file_external_input_item(nid)%axistype, & ! [IN]
807  file_external_input_item(nid)%value(:,:,:,i_prev), & ! [OUT]
808  step=file_external_input_item(nid)%data_step_prev ) ! [IN]
809  else
810  call file_read( file_external_input_item(nid)%fid, & ! [IN]
811  file_external_input_item(nid)%varname, & ! [IN]
812  file_external_input_item(nid)%value(:,:,:,i_prev), & ! [OUT]
813  step=file_external_input_item(nid)%data_step_prev ) ! [IN]
814  end if
815 
816  ! read next
817  log_info("FILE_EXTERNAL_INPUT_regist",'(1x,A,A,A,I4,A)') &
818  'Read 3D var : ', trim(file_external_input_item(nid)%varname), &
819  ' (step= ', file_external_input_item(nid)%data_step_next, ')'
820 
821  if ( file_external_input_item(nid)%aggregate ) then
822  call file_external_input_read_3d( file_external_input_item(nid)%fid, & ! [IN]
823  file_external_input_item(nid)%varname, & ! [IN]
824  file_external_input_item(nid)%axistype, & ! [IN]
825  file_external_input_item(nid)%value(:,:,:,i_next), & ! [OUT]
826  step=file_external_input_item(nid)%data_step_next ) ! [IN]
827  else
828  call file_read( file_external_input_item(nid)%fid, & ! [IN]
829  file_external_input_item(nid)%varname, & ! [IN]
830  file_external_input_item(nid)%value(:,:,:,i_next), & ! [OUT]
831  step=file_external_input_item(nid)%data_step_next ) ! [IN]
832  end if
833 
834  case default
835  log_error("FILE_EXTERNAL_INPUT_regist",*) 'Unexpected dim rank: ', dim_rank
836  call prc_abort
837  end select
838 
839  if ( present(check_coordinates) ) then
840  if ( check_coordinates ) then
841  call file_cartesc_check_coordinates( fid, &
842  atmos = file_external_input_item(nid)%ndim==3, &
843  transpose = file_external_input_item(nid)%transpose )
844  endif
845  endif
846 
847 
848  return

References scale_calendar::calendar_adjust_daysec(), scale_calendar::calendar_cfunits2sec(), scale_calendar::calendar_combine_daysec(), scale_calendar::calendar_date2daysec(), scale_calendar::calendar_daysec2date(), scale_file::file_aggregate, file_external_input_get_dims1d, file_external_input_get_dims2d, file_external_input_get_dims3d, file_external_input_read_1d, file_external_input_read_2d, file_external_input_read_3d, scale_file_h::file_fread, scale_file::file_open(), scale_calendar::i_day, scale_calendar::i_month, scale_calendar::i_year, scale_prc::prc_abort(), scale_prc::prc_myrank, scale_time::time_nowdaysec, scale_time::time_offset_year, and scale_time::time_startdaysec.

Referenced by scale_atmos_phy_ae_offline::atmos_phy_ae_offline_setup(), scale_atmos_phy_rd_offline::atmos_phy_rd_offline_setup(), file_external_input_setup(), scale_land_dyn_bucket::land_dyn_bucket_setup(), scale_ocean_dyn_offline::ocean_dyn_offline_setup(), scale_ocean_dyn_slab::ocean_dyn_slab_setup(), and scale_ocean_phy_ice_simple::ocean_phy_ice_setup().

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

◆ file_external_input_update_1d()

subroutine scale_file_external_input::file_external_input_update_1d ( character(len=*), intent(in)  varname,
real(dp), intent(in)  time_current,
real(rp), dimension(:), intent(out)  var,
logical, intent(out)  error 
)

Read data.

Definition at line 858 of file scale_file_external_input.F90.

858  use scale_const, only: &
859  undef => const_undef
860  use scale_file, only: &
861  file_read
862  implicit none
863  character(len=*), intent(in) :: varname ! item name
864  real(DP), intent(in) :: time_current ! current time
865  real(RP), intent(out) :: var(:) ! variable
866  logical, intent(out) :: error ! error code
867 
868  integer :: nid
869  real(RP) :: weight
870  logical :: do_readfile
871  integer :: step_next
872 
873  integer :: n
874  integer :: n1
875  integer :: nn1
876  !---------------------------------------------------------------------------
877 
878  ! searching the data ID
879  nid = -1
880  do n = 1, file_external_input_item_count
881  if( varname == file_external_input_item(n)%varname ) nid = n
882  enddo
883 
884  if ( nid == 0 ) then
885  log_info("FILE_EXTERNAL_INPUT_update_1D",*) 'Variable was not registered: ', trim(varname)
886  error = .true.
887  return
888  endif
889 
890  if ( file_external_input_item(nid)%ndim /= 1 ) then
891  log_info("FILE_EXTERNAL_INPUT_update_1D",*) 'Data is not 1D var: ', trim(file_external_input_item(nid)%varname)
892  error = .true.
893  return
894  endif
895 
896  call file_external_input_time_advance( nid, & ! [IN]
897  time_current, & ! [IN]
898  weight, & ! [OUT]
899  do_readfile ) ! [OUT]
900 
901  if ( do_readfile ) then
902  step_next = file_external_input_item(nid)%data_step_next - file_external_input_item(nid)%data_step_offset
903 
904  log_info("FILE_EXTERNAL_INPUT_update_1D",'(1x,A,A,A,I4,A,I4,A)') &
905  'Read 1D var : ', trim(file_external_input_item(nid)%varname), &
906  ' (step= ', file_external_input_item(nid)%data_step_next, ', file step=', step_next, ')'
907 
908  ! next -> prev
909  file_external_input_item(nid)%value(:,:,:,i_prev) = file_external_input_item(nid)%value(:,:,:,i_next)
910 
911  ! read next
912  if ( file_external_input_item(nid)%aggregate ) then
913  call file_external_input_read_1d( file_external_input_item(nid)%fid, & ! [IN]
914  file_external_input_item(nid)%varname, & ! [IN]
915  file_external_input_item(nid)%axistype, & ! [IN]
916  file_external_input_item(nid)%value(:,1,1,i_next), & ! [OUT]
917  step=file_external_input_item(nid)%data_step_next ) ! [IN]
918  else
919  call file_read( file_external_input_item(nid)%fid, & ! [IN]
920  file_external_input_item(nid)%varname, & ! [IN]
921  file_external_input_item(nid)%value(:,1,1,i_next), & ! [OUT]
922  step=step_next ) ! [IN]
923  end if
924  endif
925 
926  error = .false.
927 
928  ! store data with weight
929  do n1 = 1, file_external_input_item(nid)%dim_size(1)
930  nn1 = n1 + file_external_input_item(nid)%dim_start(1) - 1
931 
932  if ( abs( file_external_input_item(nid)%value(n1,1,1,i_prev) - undef ) > abs( undef * 0.1_rp ) &
933  .and. abs( file_external_input_item(nid)%value(n1,1,1,i_next) - undef ) > abs( undef * 0.1_rp ) ) then
934  var(nn1) = ( 1.0_rp-weight ) * file_external_input_item(nid)%value(n1,1,1,i_prev) &
935  + ( weight ) * file_external_input_item(nid)%value(n1,1,1,i_next)
936  else
937  if ( file_external_input_item(nid)%allow_missing ) then
938  var(nn1) = undef
939  else
940  log_info("FILE_EXTERNAL_INPUT_update_1D",*) 'missing value is found in ', &
941  trim(file_external_input_item(nid)%varname), ' at (',n1,')'
942  error = .true.
943  exit
944  end if
945  end if
946  enddo
947 
948  return

References scale_const::const_undef, and file_external_input_read_1d.

◆ file_external_input_update_2d()

subroutine scale_file_external_input::file_external_input_update_2d ( character(len=*), intent(in)  varname,
real(dp), intent(in)  time_current,
real(rp), dimension(:,:), intent(out)  var,
logical, intent(out)  error 
)

Read data.

Definition at line 958 of file scale_file_external_input.F90.

958  use scale_const, only: &
959  undef => const_undef
960  use scale_file, only: &
961  file_read
962  implicit none
963  character(len=*), intent(in) :: varname ! item name
964  real(DP), intent(in) :: time_current ! current time
965  real(RP), intent(out) :: var(:,:) ! variable
966  logical, intent(out) :: error ! error code
967 
968  integer :: nid
969  real(RP) :: weight
970  logical :: do_readfile
971  integer :: step_next
972 
973  integer :: n
974  integer :: n1, n2
975  integer :: nn1, nn2
976  !---------------------------------------------------------------------------
977 
978  ! searching the data ID
979  nid = -1
980  do n = 1, file_external_input_item_count
981  if( varname == file_external_input_item(n)%varname ) nid = n
982  enddo
983 
984  if ( nid == 0 ) then
985  log_info("FILE_EXTERNAL_INPUT_update_2D",*) 'Variable was not registered: ', trim(varname)
986  error = .true.
987  return
988  endif
989 
990  if ( file_external_input_item(nid)%ndim /= 2 ) then
991  log_info("FILE_EXTERNAL_INPUT_update_2D",*) 'Data is not 2D var: ', trim(file_external_input_item(nid)%varname)
992  error = .true.
993  return
994  endif
995 
996  call file_external_input_time_advance( nid, & ! [IN]
997  time_current, & ! [IN]
998  weight, & ! [OUT]
999  do_readfile ) ! [OUT]
1000 
1001  if ( do_readfile ) then
1002 
1003  step_next = file_external_input_item(nid)%data_step_next - file_external_input_item(nid)%data_step_offset
1004 
1005  log_info("FILE_EXTERNAL_INPUT_update_2D",'(1x,A,A,A,I4,A,I4,A)') &
1006  'Read 2D var : ', trim(file_external_input_item(nid)%varname), &
1007  ' (step= ', file_external_input_item(nid)%data_step_next, ', file step=', step_next, ')'
1008 
1009  ! next -> prev
1010  file_external_input_item(nid)%value(:,:,:,i_prev) = file_external_input_item(nid)%value(:,:,:,i_next)
1011 
1012  ! read next
1013  if ( file_external_input_item(nid)%aggregate ) then
1014  call file_external_input_read_2d( file_external_input_item(nid)%fid, & ! [IN]
1015  file_external_input_item(nid)%varname, & ! [IN]
1016  file_external_input_item(nid)%axistype, & ! [IN]
1017  file_external_input_item(nid)%value(:,:,1,i_next), & ! [OUT]
1018  step=file_external_input_item(nid)%data_step_next ) ! [IN]
1019  else
1020  call file_read( file_external_input_item(nid)%fid, & ! [IN]
1021  file_external_input_item(nid)%varname, & ! [IN]
1022  file_external_input_item(nid)%value(:,:,1,i_next), & ! [OUT]
1023  step=step_next ) ! [IN]
1024  end if
1025  endif
1026 
1027  error = .false.
1028 
1029  if ( file_external_input_item(nid)%transpose ) then
1030  ! store data with weight (x,z)->(z,x)
1031  do n1 = 1, file_external_input_item(nid)%dim_size(1)
1032  nn1 = n1 + file_external_input_item(nid)%dim_start(1) - 1
1033 
1034  do n2 = 1, file_external_input_item(nid)%dim_size(2)
1035  nn2 = n2 + file_external_input_item(nid)%dim_start(2) - 1
1036 
1037  if ( abs( file_external_input_item(nid)%value(n1,n2,1,i_prev) - undef ) > abs( undef * 0.1_rp ) &
1038  .and. abs( file_external_input_item(nid)%value(n1,n2,1,i_next) - undef ) > abs( undef * 0.1_rp ) ) then
1039  var(nn2,nn1) = ( 1.0_rp-weight ) * file_external_input_item(nid)%value(n1,n2,1,i_prev) &
1040  + ( weight ) * file_external_input_item(nid)%value(n1,n2,1,i_next)
1041  else
1042  if ( file_external_input_item(nid)%allow_missing ) then
1043  var(nn2,nn1) = undef
1044  else
1045  log_info("FILE_EXTERNAL_INPUT_update_2D",*) 'missing value is found in ', &
1046  trim(file_external_input_item(nid)%varname), ' at (',n1,',',n2,')'
1047  error = .true.
1048  exit
1049  end if
1050  end if
1051  enddo
1052  enddo
1053  else
1054  ! store data with weight
1055  do n2 = 1, file_external_input_item(nid)%dim_size(2)
1056  nn2 = n2 + file_external_input_item(nid)%dim_start(2) - 1
1057 
1058  do n1 = 1, file_external_input_item(nid)%dim_size(1)
1059  nn1 = n1 + file_external_input_item(nid)%dim_start(1) - 1
1060 
1061  if ( abs( file_external_input_item(nid)%value(n1,n2,1,i_prev) - undef ) > abs( undef * 0.1_rp ) &
1062  .and. abs( file_external_input_item(nid)%value(n1,n2,1,i_next) - undef ) > abs( undef * 0.1_rp ) ) then
1063  var(nn1,nn2) = ( 1.0_rp-weight ) * file_external_input_item(nid)%value(n1,n2,1,i_prev) &
1064  + ( weight ) * file_external_input_item(nid)%value(n1,n2,1,i_next)
1065  else
1066  if ( file_external_input_item(nid)%allow_missing ) then
1067  var(nn1,nn2) = undef
1068  else
1069  log_info("FILE_EXTERNAL_INPUT_update_2D",*) 'missing value is found in ', &
1070  trim(file_external_input_item(nid)%varname), ' at (',n1,',',n2,')'
1071  error = .true.
1072  exit
1073  end if
1074  end if
1075  enddo
1076  enddo
1077  endif
1078 
1079  return

References scale_const::const_undef, and file_external_input_read_2d.

◆ file_external_input_update_3d()

subroutine scale_file_external_input::file_external_input_update_3d ( character(len=*), intent(in)  varname,
real(dp), intent(in)  time_current,
real(rp), dimension(:,:,:), intent(out)  var,
logical, intent(out)  error 
)

Read data.

Definition at line 1089 of file scale_file_external_input.F90.

1089  use scale_const, only: &
1090  undef => const_undef
1091  use scale_file, only: &
1092  file_read
1093  implicit none
1094  character(len=*), intent(in) :: varname ! item name
1095  real(DP), intent(in) :: time_current ! current time
1096  real(RP), intent(out) :: var(:,:,:) ! variable
1097  logical, intent(out) :: error ! error code
1098 
1099  integer :: nid
1100  real(RP) :: weight
1101  logical :: do_readfile
1102  integer :: step_next
1103 
1104  integer :: n
1105  integer :: n1, n2, n3
1106  integer :: nn1, nn2, nn3
1107  !---------------------------------------------------------------------------
1108 
1109  ! searching the data ID
1110  nid = -1
1111  do n = 1, file_external_input_item_count
1112  if( varname == file_external_input_item(n)%varname ) nid = n
1113  enddo
1114 
1115  if ( nid == 0 ) then
1116  log_info("FILE_EXTERNAL_INPUT_update_3D",*) 'Variable was not registered: ', trim(varname)
1117  error = .true.
1118  return
1119  endif
1120 
1121  if ( file_external_input_item(nid)%ndim /= 3 ) then
1122  log_info("FILE_EXTERNAL_INPUT_update_3D",*) 'Data is not 3D var: ', trim(file_external_input_item(nid)%varname)
1123  error = .true.
1124  return
1125  endif
1126 
1127  call file_external_input_time_advance( nid, & ! [IN]
1128  time_current, & ! [IN]
1129  weight, & ! [OUT]
1130  do_readfile ) ! [OUT]
1131 
1132  if ( do_readfile ) then
1133 
1134  step_next = file_external_input_item(nid)%data_step_next - file_external_input_item(nid)%data_step_offset
1135 
1136  log_info("FILE_EXTERNAL_INPUT_update_3D",'(1x,A,A,A,I4,A,I4,A)') &
1137  'Read 3D var : ', trim(file_external_input_item(nid)%varname), &
1138  ' (step= ', file_external_input_item(nid)%data_step_next, ', file step=', step_next, ')'
1139 
1140  ! next -> prev
1141  file_external_input_item(nid)%value(:,:,:,i_prev) = file_external_input_item(nid)%value(:,:,:,i_next)
1142 
1143  ! read next
1144  if ( file_external_input_item(nid)%aggregate ) then
1145  call file_external_input_read_3d( file_external_input_item(nid)%fid, & ! [IN]
1146  file_external_input_item(nid)%varname, & ! [IN]
1147  file_external_input_item(nid)%axistype, & ! [IN]
1148  file_external_input_item(nid)%value(:,:,:,i_next), & ! [OUT]
1149  step=file_external_input_item(nid)%data_step_next ) ! [IN]
1150  else
1151  call file_read( file_external_input_item(nid)%fid, & ! [IN]
1152  file_external_input_item(nid)%varname, & ! [IN]
1153  file_external_input_item(nid)%value(:,:,:,i_next), & ! [OUT]
1154  step=step_next ) ! [IN]
1155  end if
1156  endif
1157 
1158  error = .false.
1159 
1160  if ( file_external_input_item(nid)%transpose ) then
1161  ! store data with weight (x,y,z)->(z,x,y)
1162  do n2 = 1, file_external_input_item(nid)%dim_size(2)
1163  nn2 = n2 + file_external_input_item(nid)%dim_start(2) - 1
1164 
1165  do n1 = 1, file_external_input_item(nid)%dim_size(1)
1166  nn1 = n1 + file_external_input_item(nid)%dim_start(1) - 1
1167 
1168  do n3 = 1, file_external_input_item(nid)%dim_size(3)
1169  nn3 = n3 + file_external_input_item(nid)%dim_start(3) - 1
1170 
1171  if ( abs( file_external_input_item(nid)%value(n1,n2,n3,i_prev) - undef ) > abs( undef * 0.1_rp ) &
1172  .and. abs( file_external_input_item(nid)%value(n1,n2,n3,i_next) - undef ) > abs( undef * 0.1_rp ) ) then
1173  var(nn3,nn1,nn2) = ( 1.0_rp-weight ) * file_external_input_item(nid)%value(n1,n2,n3,i_prev) &
1174  + ( weight ) * file_external_input_item(nid)%value(n1,n2,n3,i_next)
1175  else
1176  if ( file_external_input_item(nid)%allow_missing ) then
1177  var(nn3,nn1,nn2) = undef
1178  else
1179  log_info("FILE_EXTERNAL_INPUT_update_3D",*) 'missing value is found in ', &
1180  trim(file_external_input_item(nid)%varname), ' at (',n1,',',n2,',',n3,')'
1181  error = .true.
1182  exit
1183  end if
1184  end if
1185  enddo
1186  enddo
1187  enddo
1188  else
1189  ! store data with weight (z,x,y)->(z,x,y)
1190  do n3 = 1, file_external_input_item(nid)%dim_size(3)
1191  nn3 = n3 + file_external_input_item(nid)%dim_start(3) - 1
1192 
1193  do n2 = 1, file_external_input_item(nid)%dim_size(2)
1194  nn2 = n2 + file_external_input_item(nid)%dim_start(2) - 1
1195 
1196  do n1 = 1, file_external_input_item(nid)%dim_size(1)
1197  nn1 = n1 + file_external_input_item(nid)%dim_start(1) - 1
1198 
1199  if ( abs( file_external_input_item(nid)%value(n1,n2,n3,i_prev) - undef ) > abs( undef * 0.1_rp ) &
1200  .and. abs( file_external_input_item(nid)%value(n1,n2,n3,i_next) - undef ) > abs( undef * 0.1_rp ) ) then
1201  var(nn1,nn2,nn3) = ( 1.0_rp-weight ) * file_external_input_item(nid)%value(n1,n2,n3,i_prev) &
1202  + ( weight ) * file_external_input_item(nid)%value(n1,n2,n3,i_next)
1203  else
1204  if ( file_external_input_item(nid)%allow_missing ) then
1205  var(nn1,nn2,nn3) = undef
1206  else
1207  log_info("FILE_EXTERNAL_INPUT_update_3D",*) 'missing value is found in ', &
1208  trim(file_external_input_item(nid)%varname), ' at (',n1,',',n2,',',n3,')'
1209  error = .true.
1210  exit
1211  end if
1212  end if
1213  enddo
1214  enddo
1215  enddo
1216  endif
1217 
1218  return

References scale_calendar::calendar_adjust_daysec(), scale_calendar::calendar_cfunits2sec(), scale_calendar::calendar_combine_daysec(), scale_calendar::calendar_date2daysec(), scale_calendar::calendar_daysec2date(), scale_const::const_undef, file_external_input_read_3d, scale_file_h::file_fread, scale_file::file_open(), scale_calendar::i_day, scale_calendar::i_month, scale_calendar::i_year, scale_prc::prc_abort(), scale_prc::prc_myrank, scale_time::time_offset_year, and scale_time::time_startdaysec.

Here is the call graph for this function:

Variable Documentation

◆ file_external_input_get_dims1d

procedure(get_dims1d), pointer, public scale_file_external_input::file_external_input_get_dims1d => NULL()

Definition at line 134 of file scale_file_external_input.F90.

134  procedure(get_dims1D), pointer :: FILE_EXTERNAL_INPUT_get_dims1D => null()

Referenced by scale_file_external_input_cartesc::file_external_input_cartesc_setup(), and file_external_input_regist().

◆ file_external_input_get_dims2d

procedure(get_dims2d), pointer, public scale_file_external_input::file_external_input_get_dims2d => NULL()

Definition at line 135 of file scale_file_external_input.F90.

135  procedure(get_dims2D), pointer :: FILE_EXTERNAL_INPUT_get_dims2D => null()

Referenced by scale_file_external_input_cartesc::file_external_input_cartesc_setup(), and file_external_input_regist().

◆ file_external_input_get_dims3d

procedure(get_dims3d), pointer, public scale_file_external_input::file_external_input_get_dims3d => NULL()

Definition at line 136 of file scale_file_external_input.F90.

136  procedure(get_dims3D), pointer :: FILE_EXTERNAL_INPUT_get_dims3D => null()

Referenced by scale_file_external_input_cartesc::file_external_input_cartesc_setup(), and file_external_input_regist().

◆ file_external_input_read_1d

procedure(read1d), pointer, public scale_file_external_input::file_external_input_read_1d => NULL()

Definition at line 141 of file scale_file_external_input.F90.

141  procedure(read1D), pointer :: FILE_EXTERNAL_INPUT_read_1D => null()

Referenced by scale_file_external_input_cartesc::file_external_input_cartesc_setup(), file_external_input_regist(), and file_external_input_update_1d().

◆ file_external_input_read_2d

procedure(read2d), pointer, public scale_file_external_input::file_external_input_read_2d => NULL()

Definition at line 142 of file scale_file_external_input.F90.

142  procedure(read2D), pointer :: FILE_EXTERNAL_INPUT_read_2D => null()

Referenced by scale_file_external_input_cartesc::file_external_input_cartesc_setup(), file_external_input_regist(), and file_external_input_update_2d().

◆ file_external_input_read_3d

procedure(read3d), pointer, public scale_file_external_input::file_external_input_read_3d => NULL()

Definition at line 143 of file scale_file_external_input.F90.

143  procedure(read3D), pointer :: FILE_EXTERNAL_INPUT_read_3D => null()

Referenced by scale_file_external_input_cartesc::file_external_input_cartesc_setup(), file_external_input_regist(), and file_external_input_update_3d().

scale_time::time_nowdaysec
real(dp), public time_nowdaysec
second of current time [sec]
Definition: scale_time.F90:70
scale_prc::prc_abort
subroutine, public prc_abort
Abort Process.
Definition: scale_prc.F90:342
scale_calendar::calendar_daysec2date
subroutine, public calendar_daysec2date(ymdhms, subsec, absday, abssec, offset_year)
Convert from gregorian date to absolute day/second.
Definition: scale_calendar.F90:191
scale_calendar::calendar_combine_daysec
real(dp) function, public calendar_combine_daysec(absday, abssec)
Combine day and second.
Definition: scale_calendar.F90:405
scale_prc::prc_myrank
integer, public prc_myrank
process num in local communicator
Definition: scale_prc.F90:90
scale_calendar
module CALENDAR
Definition: scale_calendar.F90:13
scale_file
module file
Definition: scale_file.F90:15
scale_prc
module PROCESS
Definition: scale_prc.F90:11
scale_const
module CONSTANT
Definition: scale_const.F90:11
scale_file::file_open
subroutine, public file_open(basename, fid, mode, single, aggregate, rankid, postfix)
Definition: scale_file.F90:487
scale_calendar::calendar_date2daysec
subroutine, public calendar_date2daysec(absday, abssec, ymdhms, subsec, offset_year)
Convert from gregorian date to absolute day/second.
Definition: scale_calendar.F90:159
scale_calendar::calendar_adjust_daysec
subroutine, public calendar_adjust_daysec(absday, abssec)
Adjust day and second.
Definition: scale_calendar.F90:380
scale_file_h
module file_h
Definition: scale_file_h.F90:11
scale_time
module TIME
Definition: scale_time.F90:11
scale_calendar::calendar_cfunits2sec
real(dp) function, public calendar_cfunits2sec(cftime, cfunits, offset_year, startdaysec)
Convert time in units of the CF convention to second.
Definition: scale_calendar.F90:488
scale_file_h::file_fread
integer, parameter, public file_fread
Definition: scale_file_h.F90:32
scale_time::time_startdaysec
real(dp), public time_startdaysec
second of start time [sec]
Definition: scale_time.F90:75
scale_file_cartesc
module file / cartesianC
Definition: scale_file_cartesC.F90:11
scale_time::time_offset_year
integer, public time_offset_year
time offset [year]
Definition: scale_time.F90:74