Skip to content
Snippets Groups Projects

Compare revisions

Changes are shown as if the source revision was being merged into the target revision. Learn more about comparing revisions.

Source

Select target project
No results found

Target

Select target project
  • hd-model/hd-couple
1 result
Show changes
......@@ -20,12 +20,22 @@
!
! out_expname CHARACTER experiment name
! out_datapath CHARACTER path to where the output data shall be written
! year1 INTEGER initial year of the run
! month1 INTEGER initial month of the run
! date_start CHARACTER start date of the run, format YYYYMMDD or YYYY-MM-DD
! date_end CHARACTER end date of the run, format YYYYMMDD or YYYY-MM-DD
! nstep INTEGER number of time steps within the run if date_start & date_end are not provided
! delta_time REAL(dp) model time step lenght in seconds
!
! Time control
! year1 INTEGER Initial year of the run
! month1 INTEGER Initial month of the run
! date_start CHARACTER Start date of the run, format YYYYMMDD or YYYY-MM-DD
! date_end CHARACTER End date of the run, format YYYYMMDD or YYYY-MM-DD
! nstep INTEGER Number of time steps within the run if date_start & date_end are not provided
! delta_time REAL(dp) Model time step length in seconds
! time_start CHARACTER Start time of the run, format HHMMSS or HH:MM:SS (Def.: none)
! If you set time_start, you must also set date_start.
! time_end CHARACTER End time of the run, HHMMSS or HH:MM:SS (Def.: none)
! If you set time_end, you must also set date_end.
! date_rest CHARACTER Date of the first restart file writing, format YYYYMMDD or YYYY-MM-DD (Def.: none)
! time_rest CHARACTER Time of the first restart file writing, format HHMMSS or HH:MM:SS (Def.: none)
! irest_regular INTEGER Switch for regular writing of restart files (0=none, 1=annual)
!
! ufakru REAL(dp) unit factor for runoff and drainage input data
! runoff_file CHARACTER file with input runoff data
! drainage_file CHARACTER file with input drainage data
......@@ -58,6 +68,7 @@
NAMELIST /HD_CTL/ &
OUT_EXPNAME, OUT_DATAPATH, YEAR1, MONTH1, DATE_START, DATE_END, NSTEP, DELTA_TIME, &
TIME_START, TIME_END, DATE_REST, TIME_REST, IREST_REGULAR, &
UFAKRU, RUNOFF_FILE, DRAINAGE_FILE, FORCING_FREQ, IOUT, &
COUPLING_TYPE, LCOUPLING_ATM, LCOUPLING_OCE, ICPL_SINKS, ICPL_MASK_TOHD, &
COUPLING_FILE, LCOUPLING_OUT, IFORM_INPUT, LTRANSPORT, IBC_TYPE, DN_BCPARA, LBC_WRITE
......
......@@ -81,7 +81,7 @@ PROGRAM hd_driver
USE mo_time_control, ONLY: l_trigfiles, dt_start, init_manager, delta_time, &
init_times, ec_manager_init, time_reset, &
no_steps, time_set, current_date, &
write_date, day_difference
write_date, day_difference, calc_nstep, update_regular_restart
USE mo_exception, ONLY: finish, message, message_text
!OSBJSB USE mo_jsbach_interface, ONLY: get_dates
USE mo_control, ONLY: nlon, ngl, nproca, nprocb, nprocio
......@@ -116,11 +116,15 @@ PROGRAM hd_driver
INTEGER :: step ! hd model time step counter
INTEGER :: istep ! initial time step
! local variables defined in namelist HD_CTL
! local variables defined in namelist HD_CTL or config_hd
INTEGER :: nstep
REAL(dp) :: ufakru
INTEGER :: year1, month1
CHARACTER(LEN=10) :: date_start, date_end
INTEGER :: year1, month1, day1
INTEGER :: hour1, minute1, second1
CHARACTER(LEN=10) :: date_start, date_end, date_rest
CHARACTER(LEN=8) :: time_start, time_end, time_rest
INTEGER :: nstep_rest ! Number of time steps until a dedicated writing of restart file
INTEGER :: irest_regular ! Switch for regular writing of restart files (0=none, 1=annual, 2=monthly)
INTEGER :: forcing_freq
INTEGER :: iout
LOGICAL :: lcoupling_out ! Write output for coupling_type 2 (no/yes)
......@@ -203,7 +207,7 @@ write(nout,*) 'OTBmachine_setup '
! initialization of the echam time manager
dt_start = (/year1,month1,1,0,0,0/) ! start date: Jan 1st of year1
dt_start = (/year1,month1,day1,hour1,minute1,second1/) ! start date: e.g. Jan 1st of year1
no_steps = nstep ! number of time steps within the run
write(nout,*) 'OTBget_dates ', no_steps, ' Start year from namelist: ', year1
......@@ -356,7 +360,16 @@ write(nout,*) 'OTBhd_init_io'
CALL hd_write_output
! write restart file
IF (step == istep+nstep) CALL hydrology_restart
IF (step == istep+nstep) THEN ! End of simulation restart
IF (LEN_TRIM(date_rest).GT.0 .AND. step == istep+nstep_rest) THEN
CALL hydrology_restart(date_rest, time_rest)
ELSE
CALL hydrology_restart
ENDIF
ELSE IF (step == istep+nstep_rest) THEN ! Dedicated or regular restart
CALL hydrology_restart(date_rest, time_rest)
IF (irest_regular.GT.0) CALL update_regular_restart(irest_regular, nstep_rest, date_rest)
ENDIF
! update model time step
CALL time_reset
......@@ -581,6 +594,12 @@ CONTAINS
! date_end end date of the run, format YYYYMMDD or YYYY-MM-DD
! nstep number of time steps within the run if date_start & date_end are not provided
! delta_time model time step lenght in seconds
! time_start Start time of the run, format HHMMSS or HH:MM:SS (Def.: none)
! time_end End time of the run, HHMMSS or HH:MM:SS (Def.: none)
! date_rest Date of the first restart file writing, format YYYYMMDD or YYYY-MM-DD (Def.: none)
! time_rest Time of the first restart file writing, format HHMMSS or HH:MM:SS (Def.: none)
! irest_regular Switch for regular writing of restart files (0=none, 1=annual, 2=monthly)
!
! runoff_file file with input runoff data
! drainage_file file with input drainage data
! ufakru unit factor for runoff and drainage input data
......@@ -608,12 +627,13 @@ CONTAINS
! local variables
INTEGER :: read_status, inml, iunit, ndays, day1
INTEGER :: read_status, inml, iunit, ndays
INTEGER :: coupling_type
INTEGER :: month_next
INCLUDE 'hd_ctl.inc'
! set default values of the namelist parmeters
! set default values of the namelist parameters
out_expname = 'hd'
out_datapath = './'
......@@ -623,6 +643,11 @@ CONTAINS
date_end = ''
nstep = 365
delta_time = 86400._dp ! time step in seconds (one day)
time_start = ''
time_end = ''
date_rest = ''
time_rest = ''
irest_regular = 0
ufakru = 1._dp
runoff_file = "runoff.nc"
drainage_file = "drainage.nc"
......@@ -654,16 +679,95 @@ CONTAINS
! Check Run period and calculate number of time steps if start and end date are provided
IF (LEN_TRIM(time_start).GT.0 .AND. LEN_TRIM(date_start).LE.0) THEN
WRITE (message_text,*) 'time_start is set but date_start is not --> Unclean setting --> Please correct!'
CALL finish ('config_hd', message_text)
ENDIF
IF (LEN_TRIM(time_end).GT.0 .AND. LEN_TRIM(date_end).LE.0) THEN
WRITE (message_text,*) 'time_end is set but date_end is not --> Unclean setting --> Please correct!'
CALL finish ('config_hd', message_text)
ENDIF
IF (LEN_TRIM(date_start).GT.0 .AND. LEN_TRIM(date_end).GT.0) THEN
CALL day_difference(date_start, date_end, year1, month1, day1, ndays)
nstep = ndays * NINT(86400._dp / delta_time)
WRITE (message_text,'(A,I2.2,A1,I2.2,A1,I4.4)') 'Start date: ', day1, '.', month1, '.', year1
CALL message('config_hd', message_text)
WRITE (message_text,*) 'Calculated no. of time steps. ', nstep
CALL message('config_hd', message_text)
IF (LEN_TRIM(time_start).GT.0 .AND. LEN_TRIM(time_end).GT.0) THEN
CALL calc_nstep(date_start, time_start, date_end, time_end, nstep, year1, month1, day1, hour1, minute1, second1)
WRITE (message_text,'(A,I2.2,A1,I2.2,A1,I4.4)') 'Start date: ', day1, '.', month1, '.', year1
CALL message('config_hd', message_text)
WRITE (message_text,'(A,I2.2,A1,I2.2,A1,I4.4)') 'Start time: ', hour1, ':', minute1, ':', second1
CALL message('config_hd', message_text)
WRITE (message_text,*) 'Calculated no. of time steps. ', nstep
CALL message('config_hd', message_text)
ELSE
CALL day_difference(date_start, date_end, year1, month1, day1, ndays)
nstep = ndays * NINT(86400._dp / delta_time)
WRITE (message_text,'(A,I2.2,A1,I2.2,A1,I4.4)') 'Start date: ', day1, '.', month1, '.', year1
CALL message('config_hd', message_text)
WRITE (message_text,*) 'Calculated no. of time steps. ', nstep
CALL message('config_hd', message_text)
hour1 = 0 ; minute1 = 0 ; second1 = 0
ENDIF
ELSE
WRITE (message_text,*) 'No. of time steps taken from namelist (Def.: 365): ', nstep
CALL message('config_hd', message_text)
day1 = 0 ; hour1 = 0 ; minute1 = 0 ; second1 = 0
ENDIF
! Check whether the writing of a restart file at a speficied point in time is requested.
nstep_rest = 0
IF (LEN_TRIM(date_rest).GT.0) THEN
IF (LEN_TRIM(time_rest).GT.0) THEN
IF (LEN_TRIM(time_start).GT.0) THEN
CALL calc_nstep(date_start, time_start, date_rest, time_rest, nstep_rest)
ELSE ! If time_start not set, midnight (0 am) is assumed.
CALL calc_nstep(date_start, '00:00:00', date_rest, time_rest, nstep_rest)
WRITE (message_text,*) 'time_start is not set --> Assuming start at midnight (0 am)'
CALL message('config_hd', message_text)
ENDIF
nstep_rest = nstep_rest - 1 ! time_rest is exact time, not begin time of a timestep.
ELSE ! It is assumed that restart file shall be written after date_rest is calculated.
time_rest = '00:00:00'
CALL calc_nstep(date_start, '00:00:00', date_rest, time_rest, nstep_rest)
nstep_rest = nstep_rest + NINT(86400._dp / delta_time) ! --> add no. of timesteps of one day.
WRITE (message_text,*) 'time_rest is not set --> Restart will be written after date_rest is calculated'
CALL message('config_hd', message_text)
ENDIF
ENDIF
! Check whether the regular writing of a restart file is requested.
IF (irest_regular.GT.0) THEN
IF (LEN_TRIM(date_rest).GT.0) THEN
WRITE (message_text,*) 'A dedicated and regular restart file writings are both set -> Inconsistent -> Please correct!'
CALL finish ('config_hd', message_text)
ENDIF
SELECT CASE(irest_regular)
CASE(1) ! Annual
date_rest = 'yyyy-01-01'
WRITE(date_rest(1:4), '(I4.4)') year1+1
CASE(2) ! monthly
month_next = month1 + 1
IF (month_next.EQ.13) THEN
date_rest = 'yyyy-01-01'
WRITE(date_rest(1:4), '(I4.4)') year1+1
ELSE
date_rest = 'yyyy-mm-01'
WRITE(date_rest(1:4), '(I4.4)') year1
WRITE(date_rest(6:7), '(I2.2)') month_next
ENDIF
CASE default
WRITE (message_text,*) 'irest_regular = ', irest_regular, ' is not defined -> Program terminated'
CALL finish ('config_hd', message_text)
END SELECT
IF (LEN_TRIM(date_start).LE.0) THEN
date_start = 'yyyy-mm-01'
WRITE(date_start(1:4), '(I4.4)') year1
WRITE(date_start(6:7), '(I2.2)') month1
ENDIF
time_rest = '00:00:00'
CALL calc_nstep(date_start, '00:00:00', date_rest, time_rest, nstep_rest)
nstep_rest = nstep_rest - 1 ! time_rest is exact time, not begin time of a timestep.
ENDIF
! Check coupling information
......
......@@ -57,7 +57,7 @@ MODULE mo_hydrology
delta_time, ev_puthd, get_interval_seconds, &
io_time_event, &
initial_date, start_date, out_convert_date, inp_convert_date, &
current_date
current_date, cdate2ymd, ctime2hms, calc_current_end_date
USE mo_array_utils, ONLY: dec_monotonic_closest_midpoint, &
inc_monotonic_closest_midpoint
USE mo_coupling, ONLY: set_grid_dimensions, set_local_partition, &
......@@ -576,7 +576,7 @@ CONTAINS
END SUBROUTINE read_hydrology
SUBROUTINE hydrology_restart
SUBROUTINE hydrology_restart(date_rest, time_rest)
!
! **** Routine that writes the restart file for the HD model
......@@ -593,6 +593,9 @@ CONTAINS
! S.Legutke MPI M&D, Jan 2002, deallocate variables at end of
! rerun cycle
!
! ***** Version 1.2 - February 2025 - Stefan Hagemann, Hereon
! Include option for intermediate restart writing
!
! ****** list of variables
!
! frfmem(nl, nb, nmemrf) = Intermediate content of reservoir cascade
......@@ -607,6 +610,9 @@ CONTAINS
! finfl = Inflow data array for each gridbox for time step nstep
!
CHARACTER(LEN=*), OPTIONAL, INTENT(in) :: date_rest ! Date of dedicated restart file writing
CHARACTER(LEN=*), OPTIONAL, INTENT(in) :: time_rest ! Time of dedicated restart file writing
TYPE (FILE_INFO) :: restartfile
INTEGER :: nvarid, fileID, i, dims(2), xdimid, ydimid, xvarid, yvarid
......@@ -615,6 +621,8 @@ CONTAINS
CHARACTER(len=80) :: fname, string
CHARACTER(len=7) :: varname
CHARACTER(len=8) :: cymd
CHARACTER(len=6) :: chms
REAL(dp), ALLOCATABLE :: lons(:)
REAL(dp), ALLOCATABLE :: lats(:)
......@@ -623,7 +631,15 @@ CONTAINS
ALLOCATE(lons(grid_hd%nlon))
ALLOCATE(lats(grid_hd%nlat))
fname = 'hdrestart.nc'
IF (PRESENT(date_rest)) THEN
CALL cdate2ymd(date_rest, yyyymmdd)
CALL ctime2hms(time_rest, hhmmss)
WRITE(cymd, '(I8.8)') yyyymmdd
WRITE(chms, '(I6.6)') hhmmss
fname = 'hdrestart_' // cymd // '_' // chms // '.nc'
ELSE
fname = 'hdrestart.nc'
ENDIF
istep = get_time_step() + 1 ! get_time_step seems yo yield the step-1
......@@ -641,8 +657,15 @@ CONTAINS
CALL IO_put_att_int (fileID, NF_GLOBAL, 'riverflow_timestep', riverflow_timestep)
CALL out_convert_date (initial_date, yyyymmdd, hhmmss)
CALL IO_put_att_int (fileID, NF_GLOBAL, 'initial_date', yyyymmdd)
CALL out_convert_date (current_date, yyyymmdd, hhmmss)
CALL IO_put_att_int (fileID, NF_GLOBAL, 'current_date', yyyymmdd)
IF (PRESENT(date_rest)) THEN
CALL IO_put_att_text (fileID, NF_GLOBAL, 'restart_date', date_rest)
CALL IO_put_att_text (fileID, NF_GLOBAL, 'restart_time', time_rest)
ELSE
CALL calc_current_end_date (yyyymmdd, hhmmss)
CALL IO_put_att_int (fileID, NF_GLOBAL, 'restart_date', yyyymmdd)
WRITE(chms, '(I6.6)') hhmmss
CALL IO_put_att_text (fileID, NF_GLOBAL, 'restart_time', chms)
ENDIF
CALL IO_def_dim (fileID, 'lon', grid_hd%nlon, xdimid)
CALL IO_def_dim (fileID, 'lat', grid_hd%nlat, ydimid)
......@@ -726,10 +749,12 @@ CONTAINS
CALL IO_close (restartfile)
! close output streams
! close output streams only for final restart writing
IF (nhd_diag > 0) CALL hd_close_timeseries
IF (lhd_highres) CALL hd_highres_close(highres_file_id)
IF (.NOT. PRESENT(date_rest)) THEN
IF (nhd_diag > 0) CALL hd_close_timeseries
IF (lhd_highres) CALL hd_highres_close(highres_file_id)
ENDIF
DEALLOCATE (lons)
DEALLOCATE (lats)
......
......@@ -402,6 +402,10 @@ MODULE mo_time_control
PUBLIC :: get_cycle ! provide the current cycle
PUBLIC :: day_difference ! Calculate the difference in days for two ISO dates
PUBLIC :: calc_nstep ! Calculate the number of time steps between two ISO dates & times
PUBLIC :: update_regular_restart ! Updates the time step number nstep_rest
! when the next regular restart file shall be written
PUBLIC :: calc_current_end_date ! Calculate the date/time at the end of the current time step
CONTAINS
!+
......@@ -2271,8 +2275,7 @@ CONTAINS
INTEGER, INTENT(OUT) :: day_start ! start day
INTEGER, INTENT(OUT) :: ndays ! difference in days including date_end
INTEGER :: ymd1, ymd2, day1, day2, sec1, sec2, ios
INTEGER :: yyyy, mm, dd
INTEGER :: ymd1, ymd2, day1, day2, sec1, sec2
INTEGER :: zero = 0
TYPE(time_days) :: date1
TYPE(time_days) :: date2
......@@ -2280,55 +2283,216 @@ CONTAINS
!
! *** Convert ASCII dates to ymd numbers
IF (LEN_TRIM(date_start).EQ.8) THEN
READ(date_start,'(I8)', iostat=ios) ymd1
CALL cdate2ymd(date_start, ymd1)
CALL cdate2ymd(date_end, ymd2)
! Specify day, month and year of start date
CALL inp_convert_date (ymd1, zero, date1)
CALL TC_convert(date1, date_nat)
CALL TC_get (date_nat, year_start, month_start, day_start)
!
! *** Calculate difference in days
CALL inp_convert_date (ymd2, zero, date2)
! Calculate days from ymd1 to ymd2 incl. ymd2
CALL TC_get(date1, day1, sec1)
CALL TC_get(date2, day2, sec2)
ndays = day2 - day1 + 1 + (sec2-sec1)/86400._dp
END SUBROUTINE day_difference
!+
!*********************************
SUBROUTINE calc_nstep(date_start, time_start, date_end, time_end, nstep, &
year_start, month_start, day_start, hour_start, min_start, sec_start)
!*********************************
! Convert the ASCII ISO dates date_start & date_end into the respective ymd values and
! calculate the difference in days including date_end
!
! Stefan Hagemann - Helmholtz-Zentrum Hereon - August 2023
!
CHARACTER(LEN=10), INTENT(IN) :: date_start ! start date, format YYYYMMDD or YYYY-MM-DD
CHARACTER(LEN=8), INTENT(IN) :: time_start ! start time, format HHMMSS or HH:MM:SS
CHARACTER(LEN=10), INTENT(IN) :: date_end ! end date, format YYYYMMDD or YYYY-MM-DD
CHARACTER(LEN=8), INTENT(IN) :: time_end ! end time, format HHMMSS or HH:MM:SS
INTEGER, INTENT(OUT) :: nstep ! No. of time steps from date_start/time_start to date_end/time_end
INTEGER, INTENT(OUT), OPTIONAL :: year_start ! start year
INTEGER, INTENT(OUT), OPTIONAL :: month_start ! start month
INTEGER, INTENT(OUT), OPTIONAL :: day_start ! start day
INTEGER, INTENT(OUT), OPTIONAL :: hour_start ! start hour
INTEGER, INTENT(OUT), OPTIONAL :: min_start ! start minute
INTEGER, INTENT(OUT), OPTIONAL :: sec_start ! start second
INTEGER :: ymd1, ymd2, day1, day2, sec1, sec2
INTEGER :: hms1, hms2
TYPE(time_days) :: date1
TYPE(time_days) :: date2
TYPE(time_native) :: date_nat
!
! *** Convert ASCII dates and time to ymd and hms numbers, respectively.
CALL cdate2ymd(date_start, ymd1)
CALL cdate2ymd(date_end, ymd2)
CALL ctime2hms(time_start, hms1)
CALL ctime2hms(time_end, hms2)
CALL inp_convert_date (ymd1, hms1, date1)
! Specify day, month, year, hour, minute and second of start date
IF (PRESENT(year_start)) THEN ! It is assumed that no or all timestep values are requested
CALL TC_convert(date1, date_nat)
CALL TC_get (date_nat, year_start, month_start, day_start, hour_start, min_start, sec_start)
ENDIF
!
! *** Calculate difference in time steps
CALL inp_convert_date (ymd2, hms2, date2)
! Calculate steps from ymd1,hms1 to ymd2,hms2 which denote the respective time step beginnings
CALL TC_get(date1, day1, sec1)
CALL TC_get(date2, day2, sec2)
nstep = NINT( ( (day2 - day1 ) * 86400._dp + sec2-sec1 ) / delta_time ) + 1
IF (nstep.LE.0) THEN
WRITE (message_text,*) 'ERROR: Number of time steps <= 0: nstep = ', nstep
CALL finish ('calc_nstep', message_text)
ENDIF
END SUBROUTINE calc_nstep
!*********************************
SUBROUTINE cdate2ymd(cdate, ymd)
!*********************************
! Convert an ASCII ISO date cdate into the respective ymd value
!
! Stefan Hagemann - Helmholtz-Zentrum Hereon - January 2025
!
CHARACTER(LEN=10), INTENT(IN) :: cdate ! date string, format YYYYMMDD or YYYY-MM-DD
INTEGER, INTENT(OUT) :: ymd ! date converted to integer YYYYMMDD
INTEGER :: ios, year, month, day
IF (LEN_TRIM(cdate).EQ.8) THEN
READ(cdate,'(I8)', iostat=ios) ymd
IF (ios.NE.0) THEN
WRITE (message_text,*) 'Error while reading date_start --> checkISO-format: either YYYYMMDD or YYYY-MM-DD'
CALL finish ('config_hd', message_text)
WRITE (message_text,*) 'Error while reading cdate --> checkISO-format: either YYYYMMDD or YYYY-MM-DD'
CALL finish ('cdate2ymd', message_text)
ENDIF
CALL inp_convert_date (ymd1, zero, date1)
CALL TC_convert(date1, date_nat)
CALL TC_get (date_nat, year_start, month_start, day_start)
ELSE IF (LEN_TRIM(date_start).EQ.10) THEN
READ(date_start,'(I4,1X,I2,1X,I2)', iostat=ios) year_start, month_start, day_start
ELSE IF (LEN_TRIM(cdate).EQ.10) THEN
READ(cdate,'(I4,1X,I2,1X,I2)', iostat=ios) year, month, day
IF (ios.NE.0) THEN
WRITE (message_text,*) 'Error while reading date_start --> checkISO-format: either YYYY-MM-DD or YYYYMMDD'
CALL finish ('config_hd', message_text)
WRITE (message_text,*) 'Error while reading cdate --> checkISO-format: either YYYY-MM-DD or YYYYMMDD'
CALL finish ('cdate2ymd', message_text)
ENDIF
ymd1 = 10000 * year_start + 100 * month_start + day_start
CALL inp_convert_date (ymd1, zero, date1)
ymd = 10000 * year + 100 * month + day
ELSE
WRITE (message_text,*) 'date_start has no ISO-format, neither YYYYMMDD nor YYYY-MM-DD -> Error'
CALL finish ('config_hd', message_text)
WRITE (message_text,*) 'cdate has no ISO-format, neither YYYYMMDD nor YYYY-MM-DD -> Error'
CALL finish ('cdate2ymd', message_text)
ENDIF
!
IF (LEN_TRIM(date_end).EQ.8) THEN
READ(date_end,'(I8)', iostat=ios) ymd2
END SUBROUTINE cdate2ymd
!*********************************
SUBROUTINE ctime2hms(ctime, hms)
!*********************************
! Convert an ASCII ISO time ctime into the respective hms value
!
! Stefan Hagemann - Helmholtz-Zentrum Hereon - January 2025
!
CHARACTER(LEN=8), INTENT(IN) :: ctime ! time string, format HHMMSS or HH:MM:SS
INTEGER, INTENT(OUT) :: hms ! Time converted to integer HHMMSS
INTEGER :: ios, hour, minute, sec
IF (LEN_TRIM(ctime).EQ.6) THEN
READ(ctime,'(I6)', iostat=ios) hms
IF (ios.NE.0) THEN
WRITE (message_text,*) 'Error while reading date_end --> checkISO-format: either YYYYMMDD or YYYY-MM-DD'
CALL finish ('config_hd', message_text)
WRITE (message_text,*) 'Error while reading ctime --> checkISO-format: either HHMMSS or HH:MM:SS'
CALL finish ('ctime2hms', message_text)
ENDIF
ELSE IF (LEN_TRIM(date_end).EQ.10) THEN
READ(date_end,'(I4,1X,I2,1X,I2)', iostat=ios) yyyy, mm, dd
ELSE IF (LEN_TRIM(ctime).EQ.8) THEN
READ(ctime,'(I2,1X,I2,1X,I2)', iostat=ios) hour, minute, sec
IF (ios.NE.0) THEN
WRITE (message_text,*) 'Error while reading date_end --> checkISO-format: either YYYY-MM-DD or YYYYMMDD'
CALL finish ('config_hd', message_text)
WRITE (message_text,*) 'Error while reading ctime --> checkISO-format: either HHMMSS or HH:MM:SS'
CALL finish ('ctime2hms', message_text)
ENDIF
ymd2 = 10000 * yyyy + 100 * mm + dd
hms = 10000 * hour + 100 * minute + sec
ELSE
WRITE (message_text,*) 'date_end has no ISO-format, neither YYYYMMDD nor YYYY-MM-DD -> Error'
CALL finish ('config_hd', message_text)
WRITE (message_text,*) 'ctime has no ISO-format, neither HHMMSS nor HH:MM:SS -> Error'
CALL finish ('ctime2hms', message_text)
ENDIF
!
! *** Calculate difference in days
CALL inp_convert_date (ymd2, zero, date2)
! Calculate days from ymd1 to ymd2 incl. ymd2
CALL TC_get(date1, day1, sec1)
CALL TC_get(date2, day2, sec2)
ndays = day2 - day1 + 1 + (sec2-sec1)/86400._dp
END SUBROUTINE ctime2hms
END SUBROUTINE day_difference
!*****************************************************************************
SUBROUTINE update_regular_restart(irest_regular, nstep_rest, date_rest)
!*****************************************************************************
! Updates the time step number nstep_rest when the next regular restart file shall be written
! if irest_regular ist set > 0.
INTEGER, INTENT(in) :: irest_regular ! Switch for regular writing of restart files
! (0=none, 1=annual, 2=monthly)
INTEGER, INTENT(inout) :: nstep_rest ! Number of time steps until next writing of restart file
CHARACTER(LEN=*), INTENT(inout) :: date_rest ! Date of next regular restart file writing
INTEGER :: ymd, year_rest, month_rest, day_rest, month_next, ndum
INTEGER :: zero = 0
TYPE(time_days) :: date1
TYPE(time_native) :: date_nat
CHARACTER(LEN=10) :: date_old
date_old = date_rest
CALL cdate2ymd(date_rest, ymd)
! Determine day, month and year of previous restart date
CALL inp_convert_date (ymd, zero, date1)
CALL TC_convert(date1, date_nat)
CALL TC_get (date_nat, year_rest, month_rest, day_rest)
SELECT CASE(irest_regular)
CASE(1) ! Annual
WRITE(date_rest(1:4), '(I4.4)') year_rest+1
CASE(2) ! monthly
month_next = month_rest + 1
IF (month_next.EQ.13) THEN
date_rest = 'yyyy-01-01'
WRITE(date_rest(1:4), '(I4.4)') year_rest+1
ELSE
date_rest = 'yyyy-mm-01'
WRITE(date_rest(1:4), '(I4.4)') year_rest
WRITE(date_rest(6:7), '(I2.2)') month_next
ENDIF
CASE default
WRITE (message_text,*) 'irest_regular = ', irest_regular, ' is not defined -> Program terminated'
CALL finish ('update_regular_restart', message_text)
END SELECT
CALL calc_nstep(date_old, '00:00:00', date_rest, '00:00:00', ndum)
ndum = ndum - 1 ! time_rest is exact time, not begin time of a timestep --> -1 step for previous step.
nstep_rest = nstep_rest + ndum
END SUBROUTINE update_regular_restart
!*****************************************************************************
SUBROUTINE calc_current_end_date(ymd_end, hms_end)
!*****************************************************************************
! Calculate the date ymd_end and time hms_end at the end current date time step
INTEGER, INTENT(out) :: ymd_end, hms_end
TYPE(time_days) :: date1
INTEGER :: i0 = 0
INTEGER :: idt
idt = NINT(delta_time)
date1 = current_date
CALL add_date(i0, idt, date1)
CALL out_convert_date (date1, ymd_end, hms_end)
END SUBROUTINE calc_current_end_date
!+
! ------------------------------------------------------------------------------
......
......@@ -7,7 +7,7 @@ Copyright (C) 2021, Institute of Coastal Systems - Analysis and Modelling, Helmh
SPDX-License-Identifier: CC-BY-4.0
See ./LICENSES/ for license information
Authors: Stefan Hagemann
Author: Stefan Hagemann
Contact: <stefan.hagemann@hereon.de>
_________________________________________
```
......@@ -17,6 +17,21 @@ All notable changes to this project will be documented in this file.
The format is based on [Keep a Changelog](https://keepachangelog.com/en/1.0.0/),
and this project adheres to [Semantic Versioning](https://semver.org/spec/v2.0.0.html).
## HD Model Version 5.2.4, 11 March 2025
### Added
+ For coupled modeling using YAC, the script ./autogen.sh is added. The configure script is automatically generated and should not be edited manually. Please, use this new script to update configure when you change ./configure.ac or anything inside ./build-aux/m4.
+ Implement optional setting of start and end times and related nstep calculation to allow a simulation for a specific number of subdaily time steps. The HD offline scripts have also been adapted for running only a few days (IWORK=5) or using subdaily timesteps with daily forcing. For the steering of these offline runs, a sub-script ./scr/hd_subdaily_settings.ksh has been introduced.
+ Implement the possibility of a dedicated restart writing at a specified time step.
+ Implement an option to periodically restart file writing on a monthly or annual basis.
### Changed
+ The MO_YAC_FINTERFACE is deprecated starting YAC 3.2.0 and will be removed in one of the next ICON releases. The configure script and the code is updated to use the new YAC module.
+ Regenerate configure script, which drops several manually introduced lines.
### Fixed
+ Correct date/time global attributes in restart file at simulation end.
## HD Model Version 5.2.3, 18 November 2024
### Remark
......
......@@ -25,12 +25,21 @@ The namelists have to be written by the HD run script into the HD run directory.
out_expname CHARACTER experiment name, Default: 'hd'
out_datapath CHARACTER path to where the output data shall be written, Default: './'
Time Control
year1 INTEGER initial year of the run, Default: 1900
month1 INTEGER initial month of the run, Default: 1
date_start CHARACTER start date of the run, format YYYYMMDD or YYYY-MM-DD
date_end CHARACTER end date of the run, format YYYYMMDD or YYYY-MM-DD
nstep INTEGER number of time steps within the run (Def. 365) if date_start & date_end are not provided
delta_time REAL(dp) model time step length in seconds, Default: 86400.
time_start CHARACTER Start time of the run, format HHMMSS or HH:MM:SS (Def.: none)
If you set time_start, you must also set date_start.
time_end CHARACTER End of the run: Begin time of final time step, HHMMSS or HH:MM:SS (Def.: none)
If you set time_end, you must also set date_end.
date_rest CHARACTER Date of the first restart file writing, format YYYYMMDD or YYYY-MM-DD (Def.: none)
time_rest CHARACTER Time of the first restart file writing, format HHMMSS or HH:MM:SS (Def.: none)
irest_regular INTEGER Switch for regular writing of restart files (0=none, 1=annual, 2=monthly)
ufakru REAL(dp) unit factor for runoff and drainage input data so that their unit becomes [m/s], Default: 1.
runoff_file CHARACTER file with input runoff data if stand alone run, Default: "runoff.nc"
drainage_file CHARACTER file with input drainage data if stand alone run, Default: "drainage.nc"
......
......@@ -28,6 +28,7 @@ This readme file comprises a checklist to perform standalone model runs with the
1.4. Adapt run script settings in *run_hdmodel.ksh*
1.5. Choose from where you start a new model run
1.6. Adapt run script settings in subscript *hd_run_settings.ksh*
1.7. Alternative and more detailed settings of the simulation period
2. Coupling the HD model
3. Necessary preparations for a new regional HD 5 min. domain
3.1. Preparation of 5 Min. subdomain from the global 5 min. HD parameter
......@@ -161,6 +162,8 @@ file
c. Set first (YYYY) and last (YEND) year of your simulation.
- The first year "YYYY=" of the whole simulation should be kept on its initial value
even if you add more years later by increasing the last year YEND.
- Alternatively, you may steer the simulation by specifying date_start and date_end.
Section 1.7 provides some details on more elaborate settings of the simulation period.
d. Select forcing "IFORCE=" and HD Model resolution "HDRES="
......@@ -197,6 +200,7 @@ file
| 2 | monthly, not fully explored |
| 3 | annual with 30-day months |
| 4 | as 1 but final year with nday_final days |
| 5 | Detailled steering by settings in *./scr/hd_subdaily_settings.ksh* |
- Set Variable nday_final if IWORK=4, e.g. nday_final=212 (Jan-July)
......@@ -237,6 +241,15 @@ file
- On a slurm system, (e.g. Levante at DKRZ) use:
`sbatch run_hdmodel.ksh`
7. Alternative and more detailed settings of the simulation period
* Instead of specifying the last year (YEND) in *./scr/hd_run_settings.ksh* or the number of time steps (nstep) in *namelist.hd*, you may steer the simulation by specifying date_start and date_end of your simulation.
* You may use a more detailed steering of the simulation period by setting start (time_start) and end (time_end) times of your simulation. Note that if time_start or time_end are set, you must also set date_start and date_end, respectively. If time_start is not specified, it is set to 0 am. If time_end is not specified, the simulation will end after the final time step of date_end.
* In addition to writing a restart file in the end of the simulation period, an additional restart file may be written at a specified date (date_rest) and time (time_rest). If time_rest is not provided, the restart file will be written in the end of day date_rest.
* When using *./scr/hd_run_settings.ksh*, you may set IWORK=5 and specify such detailed settings in *./scr/hd_subdaily_settings.ksh*
## 2. Coupling the HD model
......
......@@ -253,6 +253,7 @@ Levante
55171 as 55170 but using the HydroPy with updated WFDE5 run (57004) started from 55170
55202 as 57020 using HD 1.11 and HydroPy-ERA5 run 57020 and starting from 55170: 1940-2022
55203 as 55202 using HD 1.12
55208 as 55203 Tests for introduding dedicated restart writing
--------------------------------------
ICON-based using HD Model version 1.11: IFORCE=6
......@@ -319,6 +320,7 @@ HD Vs. 5.1
62059 ICON-CLM standalone run 2008-2018, Nukleus grid
62060 GCOAST-AHOI 2.0 coupled simulation: 2010-2018 using ICON-CLM from 62059
62061 ICON-CLM UDAG evaluation run 1950-2023, Nukleus grid
62062 ICON-CLM ROAM - Veras evaluation run 1979-2021, Nukleus grid
Australia
......
......@@ -40,7 +40,7 @@ HDOUT=${HDDIR}/${EXP}/out # HD Output dir
cd $HDDIR/$EXP
typeset -Z2 MM_NEXT
typeset -Z2 MM_NEXT DD_NEXT DDP1
if (( ${IWORK} == 1 )) ; then
let "YYYY_NEXT = ${YYYY} +1"
MM_NEXT=01
......@@ -86,9 +86,39 @@ elif (( ${IWORK} == 4 )) ; then
fi
cyear=${YYYY}_${nday_final}days
fi
elif (( ${IWORK} == 5 )) ; then
xd="$date_end"
DD=${xd:6:2}
if (( ${MM} == 12 )) && (( ${DD} == 31 )) ; then
let "YYYY_NEXT = ${YYYY} +1"
MM_NEXT=01
DD_NEXT=01
else
YYYY_NEXT=${YYYY}
MM_NEXT=$MM
let "DD_NEXT = ${DD} +1"
if (( ${DD_NEXT} == 32 )) ; then
DD_NEXT=01
let "MM_NEXT = ${MM} +1"
else
case $MM_NEXT in
04 | 06 | 09 | 11 ) if (( ${DD_NEXT} == 31 )) ; then
DD_NEXT=01
let "MM_NEXT = ${MM} +1"
fi ;;
02 ) if (( ${DD_NEXT} == 29 )) ; then
DD_NEXT=01
let "MM_NEXT = ${MM} +1"
fi ;;
esac
fi
fi
cyear=${date_start}-${date_end}
fi
echo "Next year was calculated"
case $IWORK in
5 ) echo "Next day was calculated" ;;
* ) echo "Next year/day was calculated" ;;
esac
#
if [ -s hd_outflow_07.log ] ; then mv hd_outflow_07.log ${HDOUT}/${EXP}_outflow_07_${cyear}.log ; fi
if [ -s hd_outflow_99.log ] ; then mv hd_outflow_99.log ${HDOUT}/${EXP}_outflow_99_${cyear}.log ; fi
......@@ -96,17 +126,36 @@ if [ -s hd_outflow_99.log ] ; then mv hd_outflow_99.log ${HDOUT}/${EXP}_outflow_
mv hdrestart.nc ${HDOUT}/${EXP}_hdrestart_${YYYY_NEXT}${MM_NEXT}.nc
echo "HD Log and Restart files were moved to ${HDOUT}"
#
if [ -s meanflowbin.srv ] ; then
cdo -b 32 -f nc4 -z zip_2 setgrid,grid_hd.txt meanflowbin.srv ${HDOUT}/${EXP}_meanflow_${cyear}.nc
rm meanflowbin.srv
elif [ -s outhd_${YYYY}-${MM}-02_hd_meanflow.nc ] ; then # *** ncks uses too much memory,cdo increases file size
## ncks -O -h -v friv outhd_${YYYY}-${MM}-02_hd_meanflow.nc ${HDOUT}/${EXP}_meanflow_${cyear}.nc
nccopy -V friv,lon,lat,time outhd_${YYYY}-${MM}-02_hd_meanflow.nc ${HDOUT}/${EXP}_meanflow_${cyear}.nc
rm outhd_${YYYY}-${MM}-02_hd_meanflow.nc
elif [ -s outhd_${YYYY}-${MM}-01_hd_meanflow.nc ] ; then
nccopy -V friv,lon,lat,time outhd_${YYYY}-${MM}-01_hd_meanflow.nc ${HDOUT}/${EXP}_meanflow_${cyear}.nc
rm outhd_${YYYY}-${MM}-01_hd_meanflow.nc
fi
case $IWORK in
5 ) echo 'By default, HD sometimes adds one day to the name of the output file -> TODO'
xd="$date_start"
DD=${xd:6:2}
let "DDP1 = ${DD} +1"
dnout=outhd_${YYYY}-${MM}-${DD}_hd_meanflow.nc
if [ -s $dnout ] ; then
nccopy -V friv,lon,lat,time outhd_${YYYY}-${MM}-${DD}_hd_meanflow.nc ${HDOUT}/${EXP}_meanflow_${cyear}.nc
rm outhd_${YYYY}-${MM}-${DD}_hd_meanflow.nc
elif [ -s outhd_${YYYY}-${MM}-${DDP1}_hd_meanflow.nc ] ; then
nccopy -V friv,lon,lat,time outhd_${YYYY}-${MM}-${DDP1}_hd_meanflow.nc ${HDOUT}/${EXP}_meanflow_${cyear}.nc
rm outhd_${YYYY}-${MM}-${DDP1}_hd_meanflow.nc
else
echo "HD discharge output file $dnout not found"
exit
fi ;;
* ) if [ -s meanflowbin.srv ] ; then
cdo -b 32 -f nc4 -z zip_2 setgrid,grid_hd.txt meanflowbin.srv ${HDOUT}/${EXP}_meanflow_${cyear}.nc
rm meanflowbin.srv
elif [ -s outhd_${YYYY}-${MM}-02_hd_meanflow.nc ] ; then # *** ncks uses too much memory,cdo increases file size
nccopy -V friv,lon,lat,time outhd_${YYYY}-${MM}-02_hd_meanflow.nc ${HDOUT}/${EXP}_meanflow_${cyear}.nc
rm outhd_${YYYY}-${MM}-02_hd_meanflow.nc
elif [ -s outhd_${YYYY}-${MM}-01_hd_meanflow.nc ] ; then
nccopy -V friv,lon,lat,time outhd_${YYYY}-${MM}-01_hd_meanflow.nc ${HDOUT}/${EXP}_meanflow_${cyear}.nc
rm outhd_${YYYY}-${MM}-01_hd_meanflow.nc
else
echo "HD discharge output file not found"
exit
fi ;;
esac
echo "HD discharge file was moved (using nccopy) to ${HDOUT}"
#
# Bias corrected outflows?
......@@ -125,13 +174,12 @@ if (( ${INEU} == 1 )) ; then
ncatted -O -h -a start_file,global,o,c,"${HDFILE}/${HDSTART}" ${HDOUT}/${EXP}_meanflow_${cyear}.nc
fi
#
if (( ${IWORK} == 1 )) || (( ${IWORK} == 3 )) ; then
cdo -f nc4 -z zip_2 monmean ${HDOUT}/${EXP}_meanflow_${YYYY}.nc ${HDOUT}/mon_${EXP}_${YYYY}.nc
echo "Monthly mean HD discharge file was generated in ${HDOUT}"
elif (( ${IWORK} == 4 )) ; then
cdo -f nc4 -z zip_2 monmean ${HDOUT}/${EXP}_meanflow_${YYYY}.nc ${HDOUT}/mon_${EXP}_${cyear}.nc
echo "Monthly mean HD discharge file was generated in ${HDOUT}"
fi
case $IWORK in
1 | 3 ) cdo -f nc4 -z zip_2 monmean ${HDOUT}/${EXP}_meanflow_${YYYY}.nc ${HDOUT}/mon_${EXP}_${YYYY}.nc
echo "Monthly mean HD discharge file was generated in ${HDOUT}" ;;
4 ) cdo -f nc4 -z zip_2 monmean ${HDOUT}/${EXP}_meanflow_${YYYY}.nc ${HDOUT}/mon_${EXP}_${cyear}.nc
echo "Monthly mean HD discharge file was generated in ${HDOUT}" ;;
esac
if (( ${ICOUPLE} == 2 )) ; then
mv discharge_on_ocean.nc ${HDOUT}/${EXP}_discharge_on_ocean_${YYYY}.nc
echo "Discharge on ocean file was moved to ${HDOUT}"
......@@ -148,11 +196,16 @@ fi
cat > ${HDMAIN}/log/${EXP}.year << EOF
${YYYY_NEXT}
EOF
if (( ${IWORK} == 2 )) || (( ${IWORK} == 4 )); then
cat > ${HDMAIN}/log/${EXP}.month << EOF1
case $IWORK in
2 | 4 ) cat > ${HDMAIN}/log/${EXP}.month << EOF1
${MM_NEXT}
EOF1
fi
echo 'Writing next month info' ;;
5 ) cat > ${HDMAIN}/log/${EXP}.day << EOF1
${YYYY_NEXT}${MM_NEXT}${DD_NEXT}
EOF1
echo 'Writing next day info' ;;
esac
#
set +x
echo ${HDMAIN}/${EXP}
......@@ -161,10 +214,12 @@ ls -al run_hdmodel_${EXP}.ksh
date
#
# *** End of simulation or submit next
if [ ${YYYY_NEXT} -le ${YEND} ] ; then
if (( ${IWORK} != 4 )) || (( ${YYYY} != ${YEND} )) ; then
echo 'YEAR: ' ${YYYY_NEXT}
sbatch run_hdmodel_${EXP}.ksh
if (( ${IWORK} != 5 )) ; then
if [ ${YYYY_NEXT} -le ${YEND} ] ; then
if (( ${IWORK} != 4 )) || (( ${YYYY} != ${YEND} )) ; then
echo 'YEAR: ' ${YYYY_NEXT}
sbatch run_hdmodel_${EXP}.ksh
fi
fi
fi
if [ ${YYYY} -eq ${YEND} ] ; then
......
......@@ -13,13 +13,13 @@
#
# ***** HD and forcing Experiment nos. and HD settings ********************************
#
EXPINP=57020 # Exp. no. of forcing - used for CCLM, HydroPy, Remo
# ERA5 (55053/54) & JSBACH forcing (25288,25410)
##EXP=70${EXPINP}
EXP=7055207
EXPINP=62062 # Exp. no. of forcing - used for CCLM, HydroPy, Remo
# HPy-ERA5 (57020) & JSBACH forcing (25288,25410)
EXP=70${EXPINP}
##EXP=7055208
typeset -Z4 YYYY
YYYY=1970 # First year of simulation
YYYY=1979 # First year of simulation
#
# *** Restart or Cold Start
if [ -e ${HDMAIN}/log/${EXP}.year ] ; then
......@@ -31,11 +31,11 @@ else
INEU=1
cstart='Cold-Start'
fi
YEND=1970 # Last year of simulation
YEND=1979 # Last year of simulation
IFORCE=1 # Forcing: 1 = HydroPy, 2 = JSBACH-PF, 3 = CCLM, 4 = REMO, 5=WRF, 6=ICON
IFORCE=3 # Forcing: 1 = HydroPy, 2 = JSBACH-PF, 3 = CCLM, 4 = REMO, 5=WRF, 6=ICON
# Note that JSBACH forcing must be shifted by cdo remapnn,grid_0_5.txt
HDRES=1 # HD Resolution: 0=0.5 Grad, 1=5 Min, 2= Euro 5 Min with 0.5° or 5 Min. input
HDRES=2 # HD Resolution: 0=0.5 Grad, 1=5 Min, 2= Euro 5 Min with 0.5° or 5 Min. input
# 3 = Australia, 4=SEA=South East Asia
FORCE_RES=99 # Forcing data resolution (original, without cdo), 99= any non-HD, (for IFORCE=1)
CFORM=nc # Format of forcing files: 'srv' = Service Format (Default), 'nc' = NetCDCF
......@@ -44,8 +44,13 @@ DNCOUPLE=${HDFILE}/nemo/hdcouple_hd_vs5_1_to_nemo_imode2.nc
IWORK=1 # Run time: 1=1 year, 2=1 month, 3=year with 30 day months
# 4=as 1 but final year with nday_final days
# 5=Manually steered by settings in hd_subdaily_settings
nday_final=212 # Jan-July: 90+91+31
ndate_end=20210731 # end date of run for IWORK=4
#irest_regular=2 # Regular writing of restart file (0=no, 1=annual, 2=monthly)
MM=01 # Start month
# BIAS CORRECTION
IBC_TYPE=0 # Bias correction type: 0=None, 1 = Mean Bias, 2 = Low, Mid and High Biases
......@@ -67,6 +72,7 @@ case $IWORK in
if (( $YYYY == $YEND )) ; then
date_end=$ndate_end
fi ;;
5 ) source ${HDMAIN}/scr/hd_subdaily_settings.ksh ;;
* ) date_start=${YYYY}-${MM}-01 ; date_end=${YYYY}-12-31 ;;
esac
#
......@@ -144,7 +150,8 @@ case ${HDRES} in
#
# *** Examples if restart files from previous runs are used for initialization.
case $EXP in
706206? ) HDSTART="hdstart/hdstart_euro5min_7062061_1950.nc" ;; # 3h time step
7062061 ) HDSTART="hdstart/hdstart_euro5min_7062061_1950.nc" ;; # 3h time step
706206? ) HDSTART="hdstart/7062061/7062061_hdrestart_${YYYY}01.nc" ;; # UDAG Eval. run
7062054 ) HDSTART="hdstart/7055192/7055192_hdrestart_${YYYY}01.nc" ;; # CMOR daily time step
70620?? | 706220? | 706021[03]) if (( $YYYY <= 1979 )) ; then # Hourly time step
HDSTART="hdstart/7062008/7062008_hdrestart_${YYYY}01.nc"
......
#!/bin/ksh
#
# hd_subdaily_settings.ksh - Sub-script with settings for sub-daily HD runs sourced from hd_run_settings.ksh
#
# Copyright (C) 2025, Institute of Coastal Systems - Analysis and Modelling, Helmholtz-Zentrum Hereon
# SPDX-License-Identifier: Apache-2.0
# See ./LICENSES/ for license information
#
# Authors: Stefan Hagemann
# Contact: <stefan.hagemann@hereon.de>
#_________________________________________
#
# HD sub-daily settings
echo " ***** HD subdaily settings *****"
#
# Start and end dates/times (Note that time 24:00:00 is not allowed)
date_start=${YYYY}0707 ; date_end=${YYYY}0707
time_start="00:00:00" ; time_end="04:00:00" # time_end is starting time of final time step
xd="$date_start"
MM=${xd:4:2} ; YYYY=${xd:0:4}
echo " Startdate: $date_start time: $time_start Enddate: $date_end time: $time_end"
#
# set time step: no. of time steps per day
ndt_set=48
if (( $ndt_set > 0 )) ; then
echo " Number of time steps per day set to $ndt_set"
fi
#
# Write an additional retart file
date_rest=${YYYY}0707
time_rest="03:00:00"
#
......@@ -103,7 +103,7 @@ case ${IFORCE} in
ndt_day=1 ;; # ICON-CLM Nukleus = CCLM Nukleus
62059 ) GRIDCCLM=${HDMAIN}/grid/grid_icon_nukleus.txt ;; # ICON-CLM Nukleus
6203[4567] | 6204[45679] | 6205? ) GRIDCCLM=${HDMAIN}/grid/grid_cclm_ha.txt ;; # Ha: CoastDat3 incl. Boundary zone
62061 ) GRIDCCLM=${HDMAIN}/grid/grid_icon_nukleus.txt # UDAG = ICON-CLM Nukleus
6206[12] ) GRIDCCLM=${HDMAIN}/grid/grid_icon_nukleus.txt # UDAG = ICON-CLM Nukleus
ndt_day=4 ; UFAK=4.62963E-8 ;; # Input: mm/6h --> 1/1000/21600
* ) echo 'CCLM exp. nr. not defined --> Abbruch!' ; exit ;;
esac
......
......@@ -24,10 +24,9 @@
#SBATCH --partition=shared # Specify partition name
#SBATCH --ntasks=1 # Specify max. number of tasks to be invoked
# #SBATCH --mem=5G
# #SBATCH --mem-per-cpu=500 # Specify real memory required per CPU in MegaBytes
# #SBATCH --mem-per-cpu=2000 # Specify real memory for global 5 min run or levante
#SBATCH --mem-per-cpu=4000 # Specify real memory for global 5 min run or levante
#SBATCH --time=01:00:00 # Set a limit on the total run time (0:30 for reg., 1:20 for G)
#SBATCH --mem-per-cpu=2000 # Specify real memory for global 5 min run or levante
# #SBATCH --mem-per-cpu=4000 # Specify real memory for global 5 min run or levante
#SBATCH --time=00:10:00 # Set a limit on the total run time (0:30 for reg., 1:20 for G)
###############################################################################
#
# Levante numbers - Global 5 Min. mem_per_cpu: 3500, time: 0:40
......@@ -211,12 +210,40 @@ if (( ${ndt_day} <= 0 )) ; then
echo "Number of forcing time steps per day < 0 --> Error"
exit
fi
NFF=0 # stepwise forcing"
if (( ${IWORK} == 5 )) ; then
cdo seldate,$date_start,$date_end hdforcing.nc hdfsel.nc
# for testing only {
## cdo settime,0:00:00 -seldate,$date_start hdfsel.nc infile.nc
## cp -p infile.nc infile_cat.nc
## for i in $(seq 1 47) ; do
## let "nmin = ${i} * 30"
## shift="${nmin}min"
## cdo -shifttime,${shift} infile.nc next_year.nc
## cdo -cat infile_cat.nc next_year.nc tmp.nc
## mv tmp.nc infile_cat.nc
## done
## ndt_day=48
## mv infile_cat.nc hdfsel.nc
# }
if (( ${ndt_set} > 0 )) && (( ${ndt_set} != ${ndt_day} )) ; then
if (( ${ndt_day} == 1 )) ; then
NFF=1 # daily forcing"
ndt_day=$ndt_set
else
let "nsub = ${ndt_set} / ${ndt_day}"
echo "Forcing ${ndt_day} per day, but HD time steps ${ndt_set} per day"
echo " --> Action required --> Script terminates here !!!"
exit
fi
fi
mv hdfsel.nc hdforcing.nc
fi
#
# ******* Linking of necessary HD model files ******************************
if (( ${INEU} == 1 )) ; then
set +e ; rm grid_hd.txt hdpara.nc masks.nc hdstart.nc rmp_hd.nc ; set -e
fi
if [ -e ${HDOUT}/${EXP}_hdrestart_${YYYY}${MM}.nc ];then
elif [ -e ${HDOUT}/${EXP}_hdrestart_${YYYY}${MM}.nc ];then
set +e ; rm hdstart.nc ; set -e
ln -s ${HDOUT}/${EXP}_hdrestart_${YYYY}${MM}.nc hdstart.nc
fi
......@@ -224,7 +251,10 @@ if [ -e hdpara.nc ];then echo 'hdpara.nc exists' ; else
ln -sf ${HDFILE}/${DNPARA} hdpara.nc
fi
#
if [ -e hdstart.nc ];then echo 'hdstart.nc exists' ; else
if [ -e hdstart.nc ];then
echo 'hdstart.nc exists'
ls -al hdstart.nc
else
if (( ${IZIP_START} == 1 )) ; then
if [ -e ${HDFILE}/${HDSTART}.gz ];then
cp -p ${HDFILE}/${HDSTART}.gz ./hdstart.nc.gz
......@@ -272,6 +302,8 @@ elif (( ${IWORK} == 3 )) ; then
ndays=360
elif (( ${IWORK} == 4 )) ; then
ndays=$nday_final
elif (( ${IWORK} == 5 )) ; then
ndays=0 # ndays = dummy?
fi
if (( ${IWORK} < 3 )) ; then
......@@ -322,7 +354,7 @@ else
fi
#
rm -f namelist.hd
cat > namelist.hd << end_hdalone_ctl
cat > namelist.hd << end_hdalone_ctl1
&HD_CTL
YEAR1 = ${YYYY}
MONTH1 = ${MM}
......@@ -333,7 +365,7 @@ cat > namelist.hd << end_hdalone_ctl
delta_time = ${dt} !! 3600 ! 7200 ! 14400 ! 21600 ! 28800 ! 43200 ! 86400
runoff_file = $DNRUN
drainage_file = $DNDR
forcing_freq = 0 !! 0: stepwise, 1: daily
forcing_freq = $NFF !! 0: stepwise, 1: daily
IOUT = 6 !! 5: monthly, 6: daily
OUT_DATAPATH = "${HDOUT}"
UFAKRU = ${UFAK}
......@@ -344,8 +376,32 @@ cat > namelist.hd << end_hdalone_ctl
ibc_type = ${IBC_TYPE} ! Bias correction type: 0=None, 1 = Mean Bias, 2 = Low, Mid and High Biases
dn_bcpara = "${DN_BCPARA}"
lbc_write = ${lbc_write}
end_hdalone_ctl1
#
if [ "$time_start" != "" ] ; then
cat >> namelist.hd << end_hdalone_ctl2
time_start = "$time_start"
time_end = "$time_end"
end_hdalone_ctl2
fi
#
if [ "$date_rest" != "" ] ; then
cat >> namelist.hd << end_hdalone_ctl3
date_rest = "$date_rest"
time_rest = "$time_rest"
end_hdalone_ctl3
fi
#
if [ "$irest_regular" != "" ] ; then
cat >> namelist.hd << end_hdalone_ctl4
irest_regular = $irest_regular
end_hdalone_ctl4
fi
#
cat >> namelist.hd << end_hdalone_ctlz
/
end_hdalone_ctl
end_hdalone_ctlz
#.................... NOTE for IOUT of HD ..................................
#! *** IOUT = Mittelungsartvariable, d.h. ueber wieviel Zeitschritte
#! *** 1 30-Day Averages --> NT = 30 * hd_steps_per_day
......