Skip to content

Commit

Permalink
Merge pull request #117 from nmizukami/feature/mpi-pio-multi-file
Browse files Browse the repository at this point in the history
some minor restructures (moved routine calls) and further cleanups
  • Loading branch information
nmizukami authored Jul 16, 2020
2 parents af0444d + 5fc47a8 commit 47134c8
Show file tree
Hide file tree
Showing 3 changed files with 44 additions and 71 deletions.
2 changes: 0 additions & 2 deletions route/build/src/dataTypes.f90
Original file line number Diff line number Diff line change
Expand Up @@ -138,8 +138,6 @@ MODULE dataTypes
real(dp) , allocatable :: timevar(:) ! the time varibale from the netcdf file
real(dp) :: convTime2Days ! the time varibale from the netcdf file
real(dp) :: ncrefjulday ! the julian day for the reference of the nc file
real(dp) :: ncstartjulday ! the julian day for the start of the nc file
real(dp) :: ncendjulday ! the julian day for the end of the nc file
character(len=strLen) :: infilename ! the name of the input file name
character(len=strLen) :: calendar ! the calendar
character(len=strLen) :: unit ! the unit of time
Expand Down
105 changes: 44 additions & 61 deletions route/build/src/standalone/model_setup.f90
Original file line number Diff line number Diff line change
Expand Up @@ -24,7 +24,6 @@ MODULE model_setup
public :: init_mpi
public :: init_data
public :: infile_name
public :: inFile_pop

CONTAINS

Expand Down Expand Up @@ -82,6 +81,14 @@ SUBROUTINE init_data(pid, & ! input: proc id
! initialize error control
ierr=0; message='init_data/'

! runoff input files initialization
call inFile_pop(ierr, message)
if(ierr/=0)then; message=trim(message)//trim(cmessage); return; endif

! time initialization
call init_time(ierr, cmessage)
if(ierr/=0)then; message=trim(message)//trim(cmessage); return; endif

! network topology data initialization
call init_ntopo_data(pid, nNodes, comm, ierr, cmessage)
if(ierr/=0)then; message=trim(message)//trim(cmessage); return; endif
Expand Down Expand Up @@ -122,6 +129,9 @@ SUBROUTINE init_runoff_data(pid, & ! input: proc id
! local:
character(len=strLen) :: cmessage ! error message of downwind routine

! initialize error control
ierr=0; message='init_runoff_data/'

if (pid==0) then
! runoff and remap data initialization (TO DO: split runoff and remap initialization)
call init_runoff(is_remap, & ! input: logical whether or not runnoff needs to be mapped to river network HRU
Expand All @@ -135,7 +145,7 @@ END SUBROUTINE init_runoff_data


! *********************************************************************
! private subroutine: read the name of the netcdf files that is specified
! public subroutine: read the name of the netcdf that is specified
! in a text file, populates the filed of inFiledata dataType
! *********************************************************************
SUBROUTINE inFile_pop(ierr, message) ! output
Expand All @@ -155,10 +165,7 @@ SUBROUTINE inFile_pop(ierr, message) ! output
USE public_var, ONLY: input_dir ! directory containing input data
USE public_var, ONLY: fname_qsim ! simulated runoff txt file that includes the NetCDF file names
USE public_var, ONLY: vname_time ! variable name for time
!USE public_var,ONLY: time_units ! time units (seconds, hours, or days)
USE public_var, ONLY: dname_time !
USE public_var, ONLY: calendar ! calendar name
USE globalData, ONLY: timeVar ! time variables (unit given by runoff data)
USE globalData, ONLY: infileinfo_data ! the information of the input files

! output: error control
Expand All @@ -167,11 +174,10 @@ SUBROUTINE inFile_pop(ierr, message) ! output

! local varibales
integer(i4b) :: unit ! file unit (free unit output from file_open)
character(len=7) :: t_unit ! time units. "<time_step> since yyyy-MM-dd hh:mm:ss"
integer(i4b) :: iFile ! counter for forcing files
integer(i4b) :: nFile ! number of nc files identified in the text file
integer(i4b) :: nTime ! hard coded for now
integer(i4b) :: counter ! counter
integer(i4b) :: i ! counter
real(dp) :: convTime2Days ! conversion of the day to the local time
character(len=strLen) :: infilename ! input filename
character(len=strLen),allocatable :: dataLines(:) ! vector of lines of information (non-comment lines)
Expand All @@ -194,10 +200,10 @@ SUBROUTINE inFile_pop(ierr, message) ! output
nFile = size(dataLines) ! get the name of the lines in the file

! allocate space for forcing information
allocate(infileinfo_data(nFile))
allocate(infileinfo_data(nFile), stat=ierr)
if(ierr/=0)then; ierr=20; message=trim(message)//'problem allocating space for forcFileInfo'; return; end if

! poputate the forcingInfo structure with filenames, julian day of sart and end of the simulation
! poputate the forcingInfo structure with filenames, and time variables/attributes
do iFile=1,nFile

! split the line into "words" (expect one word: the file describing forcing data for that index)
Expand All @@ -209,12 +215,12 @@ SUBROUTINE inFile_pop(ierr, message) ! output

! get the time units
call get_var_attr(trim(input_dir)//trim(infileinfo_data(iFile)%infilename), &
trim(vname_time), 'units', infileinfo_data(iFile)%unit, ierr, cmessage)
trim(vname_time), 'units', infileinfo_data(iFile)%unit, ierr, cmessage)
if(ierr/=0)then; message=trim(message)//trim(cmessage); return; endif

! get the calendar
call get_var_attr(trim(input_dir)//trim(infileinfo_data(iFile)%infilename), &
trim(vname_time), 'calendar', infileinfo_data(iFile)%calendar, ierr, cmessage)
trim(vname_time), 'calendar', infileinfo_data(iFile)%calendar, ierr, cmessage)
if(ierr/=0)then; message=trim(message)//trim(cmessage); return; endif

! get the dimension of the time to populate nTime and pass it to the get_nc file
Expand All @@ -224,37 +230,33 @@ SUBROUTINE inFile_pop(ierr, message) ! output
nTime = infileinfo_data(iFile)%nTime ! the length of time varibale for each nc file

! allocate space for time varibale of each file
if(allocated(infileinfo_data(iFile)%timeVar)) deallocate(infileinfo_data(iFile)%timeVar)
allocate(infileinfo_data(iFile)%timeVar(nTime))
if(ierr/=0)then; ierr=20; message=trim(message)//'problem allocating space for infileinfo_data(:)%timeVar'; return; end if

! get the time varibale
call get_nc(trim(input_dir)//trim(infileinfo_data(iFile)%infilename), &
vname_time, infileinfo_data(iFile)%timeVar, 1, nTime, ierr, cmessage) ! does it needs timeVar(:)

! get the time multiplier needed to convert time to units of days for each nc file
select case( trim( infileinfo_data(iFile)%unit(1:index(infileinfo_data(iFile)%unit,' ')) ) )
t_unit = trim( infileinfo_data(iFile)%unit(1:index(infileinfo_data(iFile)%unit,' ')) )
select case( trim(t_unit) )
case('seconds','second','sec','s'); convTime2Days=86400._dp
case('minutes','minute','min','m'); convTime2Days=1440._dp
case('hours' ,'hour' ,'hr' ,'h'); convTime2Days=24._dp
case('days' ,'day' ,'d'); convTime2Days=1._dp
case default; ierr=20; message=trim(message)//'time unit must be seconds, minutes, hours or days.'; return
case default
ierr=20; message=trim(message)//'<time_units>= '//trim(t_unit)//': <time_units> must be seconds, minutes, hours or days.'; return
end select
infileinfo_data(iFile)%convTime2Days = convTime2Days

! get the reference julian day from the nc file
call process_time(trim(infileinfo_data(iFile)%unit),infileinfo_data(iFile)%calendar,infileinfo_data(iFile)%ncrefjulday,ierr, cmessage)
if(ierr/=0) then; message=trim(message)//trim(cmessage)//' [ncrefjulday]'; return; endif

! get the starting julian day of the nc file
infileinfo_data(iFile)%ncstartjulday = infileinfo_data(iFile)%timeVar(1)/infileinfo_data(iFile)%convTime2Days+infileinfo_data(iFile)%ncrefjulday

! get the ending julian day of the nc file
infileinfo_data(iFile)%ncendjulday = infileinfo_data(iFile)%timeVar(infileinfo_data(iFile)%nTime)/infileinfo_data(iFile)%convTime2Days+infileinfo_data(iFile)%ncrefjulday

! populated the index of the iTimebound for each nc file
if (iFile==1) then ! if only one file is specified in the txt file
if (iFile==1) then
infileinfo_data(iFile)%iTimebound(1) = 1
infileinfo_data(iFile)%iTimebound(2) = size(infileinfo_data(iFile)%timeVar)
infileinfo_data(iFile)%iTimebound(2) = nTime
else ! if multiple files specfied in the txt file
infileinfo_data(iFile)%iTimebound(1) = infileinfo_data(iFile-1)%iTimebound(2) + 1 ! the last index from the perivous nc file + 1
infileinfo_data(iFile)%iTimebound(2) = infileinfo_data(iFile-1)%iTimebound(2) + nTime ! the last index from the perivous nc file + 1
Expand All @@ -265,15 +267,8 @@ SUBROUTINE inFile_pop(ierr, message) ! output
! close ascii file
close(unit=unit,iostat=ierr); if(ierr/=0)then;message=trim(message)//'problem closing forcing file list'; return; end if

! here some checks can be done on the consistency of the starting and ending julian day and also calendar of each file

! passing the first nc file as global file name to read
fname_qsim = trim(infileinfo_data(1)%infilename)
! set the calendar to the first calendar calendars should be the same
calendar = infileinfo_data(1)%calendar

! call init_time_new to get the first iTime
call init_time(ierr, cmessage)

END SUBROUTINE inFile_pop

Expand All @@ -290,9 +285,6 @@ SUBROUTINE init_time(ierr, message) ! output
! derived datatype
USE dataTypes, ONLY: time ! time data type
! public data
USE public_var, ONLY: input_dir ! directory containing input data
USE public_var, ONLY: fname_qsim ! simulated runoff netCDF name
USE public_var, ONLY: vname_time ! variable name for time
USE public_var, ONLY: time_units ! time units (seconds, hours, or days)
USE public_var, ONLY: simStart ! date string defining the start of the simulation
USE public_var, ONLY: simEnd ! date string defining the end of the simulation
Expand Down Expand Up @@ -320,39 +312,44 @@ SUBROUTINE init_time(ierr, message) ! output
integer(i4b) :: ix
integer(i4b) :: counter
integer(i4b) :: nTime
integer(i4b) :: nt
integer(i4b) :: nFile ! number of nc files
integer(i4b) :: iFile ! for loop over the nc files
type(time) :: rofCal
type(time) :: simCal
real(dp) :: convTime2Days
character(len=7) :: t_unit
character(len=strLen) :: cmessage ! error message of downwind routine
character(len=50) :: fmt1='(a,I4,a,I2.2,a,I2.2,x,I2.2,a,I2.2,a,F5.2)'

! initialize error control
ierr=0; message='init_time/'

! Set time attributes for continuous time variables (saved in globalData to use for output)
calendar = infileinfo_data(1)%calendar
time_units = infileinfo_data(1)%unit
refJulday = infileinfo_data(1)%ncrefjulday

! get the number of the total time length of all the nc files
nFile = size(infileinfo_data) ! get the number of nc files
nTime = 0; ! counter set to zero
do iFile=1,nFile ! loop over the file names
nFile = size(infileinfo_data)
nTime = 0
do iFile=1,nFile
nTime = nTime + infileinfo_data(iFile)%nTime
enddo

! time initialization
! Define time varialbes: timeVar and roJulday
allocate(timeVar(nTime), roJulday(nTime), stat=ierr)
if(ierr/=0)then; message=trim(message)//trim(cmessage); return; endif

! populate roJulday
counter = 1; ! counter set to 1
do iFile=1,nFile ! loop over the file names
roJulday(counter:counter+infileinfo_data(iFile)%nTime-1) = &
infileinfo_data(iFile)%timeVar/infileinfo_data(iFile)%convTime2Days+infileinfo_data(iFile)%ncrefjulday
! roJulday: Julian day of concatenated netCDF
counter = 1;
do iFile=1,nFile
nt = infileinfo_data(iFile)%nTime
roJulday(counter:counter+nt-1) = &
infileinfo_data(iFile)%timeVar(1:nt)/infileinfo_data(iFile)%convTime2Days+infileinfo_data(iFile)%ncrefjulday
counter = counter + infileinfo_data(iFile)%nTime
end do

! populate timeVar from the roJulday based on the convTime2Days and ncrefjulday of the first nc file
timeVar = (roJulday - infileinfo_data(1)%ncrefjulday)*infileinfo_data(1)%convTime2Days
! timeVar: time variable in unit given by netCDF
timeVar(1:nTime) = (roJulday(1:nTime) - refJulday)*infileinfo_data(1)%convTime2Days

call process_time(trim(simStart),calendar, startJulday, ierr, cmessage)
if(ierr/=0) then; message=trim(message)//trim(cmessage)//' [startJulday]'; return; endif
Expand Down Expand Up @@ -429,7 +426,7 @@ END SUBROUTINE init_time


! *********************************************************************
! private subroutine: get the name of input file based on iTime, will be called
! public subroutine: get the name of input file based on iTime, will be called
! in get_hru_runoff to ajust for file name given iTime
! *********************************************************************
SUBROUTINE infile_name(ierr, message) ! output
Expand All @@ -440,21 +437,8 @@ SUBROUTINE infile_name(ierr, message) ! output
! derived datatype
USE dataTypes, ONLY: time ! time data type
! Shared data
!USE public_var, ONLY: input_dir ! directory containing input data
USE public_var, ONLY: fname_qsim ! simulated runoff netCDF name
!USE public_var, ONLY: vname_time ! variable name for time
!USE public_var, ONLY: time_units ! time units (seconds, hours, or days)
!USE public_var, ONLY: simStart ! date string defining the start of the simulation
!USE public_var, ONLY: simEnd ! date string defining the end of the simulation
!USE public_var, ONLY: calendar ! calendar name
USE globalData, ONLY: timeVar ! time variables (unit given by runoff data)
USE globalData, ONLY: iTime ! time index at simulation time step
!USE globalData, ONLY: convTime2Days ! conversion multipliers for time unit of runoff input to day
!USE globalData, ONLY: refJulday ! julian day: reference
!USE globalData, ONLY: startJulday ! julian day: start of routing simulation
!USE globalData, ONLY: endJulday ! julian day: end of routing simulation
!USE globalData, ONLY: modJulday ! julian day: at model time step
USE globalData, ONLY: modTime ! model time data (yyyy:mm:dd:hh:mm:ss)
USE globalData, ONLY: infileinfo_data ! the information of the input files
USE globalData, ONLY: iTime_local ! iTime index for the given netcdf file

Expand All @@ -465,13 +449,12 @@ SUBROUTINE infile_name(ierr, message) ! output
character(*), intent(out) :: message ! error message
! local variable
integer(i4b) :: ix
character(len=strLen) :: cmessage ! error message of downwind routine
!character(len=strLen) :: cmessage ! error message of downwind routine

! initialize error control
ierr=0; message='infile_name/'

! fast forward time to time index at simStart and save iTime and modJulday
! need to convert time unit in timeVar to day
ixloop: do ix = 1, size(infileinfo_data) !loop over number of file
if ((iTime >= infileinfo_data(ix)%iTimebound(1)).and.(iTime <= infileinfo_data(ix)%iTimebound(2))) then
iTime_local = iTime - infileinfo_data(ix)%iTimebound(1) + 1
Expand Down
8 changes: 0 additions & 8 deletions route/build/src/standalone/route_runoff.f90
Original file line number Diff line number Diff line change
Expand Up @@ -22,7 +22,6 @@ PROGRAM route_runoff
USE model_setup, ONLY: init_mpi ! initialize MPI for this program
USE model_setup, ONLY: init_data ! initialize river reach data
USE model_setup, ONLY: infile_name ! updating the file name and iTime_local based on iTime
USE model_setup, ONLY: infile_pop ! populating the file name, start and end simulation
USE init_model_data, ONLY: init_model ! model setupt - reading control file, populate metadata, read parameter file
USE init_model_data, ONLY: update_time ! Update simulation time information at each time step
! subroutines: model finalize
Expand Down Expand Up @@ -66,13 +65,6 @@ PROGRAM route_runoff
call init_model(cfile_name, ierr, cmessage)
if(ierr/=0) call handle_err(ierr, cmessage)


! *****
! *** populate the input file and iTime
! ************************
call infile_pop(ierr, cmessage)


! *****
! *** data initialization
! - river topology, properties, river network domain decomposition
Expand Down

0 comments on commit 47134c8

Please sign in to comment.