66 subroutine read_nc(folder, nRows, nCols, varName, mask, data, target_period, lower, upper, nctimestep, &
67 fileName, nocheck, maskout, is_meteo, bound_error, nTstepForcingDay)
69 use mo_constants,
only : nodata_i4
71 use mo_kind,
only : dp, i4
72 use mo_netcdf,
only : ncdataset, ncvariable
73 use mo_string_utils,
only : num2str
74 use mo_utils,
only : eq, ne
79 character(len = *),
intent(in) :: folder
81 integer(i4),
intent(in) :: nrows
83 integer(i4),
intent(in) :: ncols
85 character(len = *),
intent(in) :: varname
87 logical,
dimension(:, :),
intent(in) :: mask
89 real(dp),
dimension(:, :, :),
allocatable,
intent(out) :: data
91 type(
period),
optional,
intent(in) :: target_period
93 real(dp),
optional,
intent(in) :: lower
95 real(dp),
optional,
intent(in) :: upper
97 integer(i4),
optional,
intent(in) :: nctimestep
99 character(256),
optional,
intent(in) :: filename
101 logical,
optional,
intent(in) :: nocheck
103 logical,
dimension(:, :, :),
allocatable,
optional,
intent(out) :: maskout
105 logical,
optional,
intent(in) :: is_meteo
107 logical,
optional,
intent(in) :: bound_error
109 integer(i4),
optional,
intent(inout) :: ntstepforcingday
112 type(ncdataset) :: nc
114 type(ncvariable) :: var, time_var
116 integer(i4),
allocatable,
dimension(:) :: var_shape
118 integer(i4) :: time_start
120 integer(i4) :: time_cnt
122 character(256) :: fname
126 real(dp) :: nodata_value
130 integer(i4) :: inctimestep
132 logical :: bound_error_
136 if (
present(nocheck)) checking = .NOT. nocheck
139 bound_error_ = .true.
140 if (
present(bound_error)) bound_error_ = bound_error
145 if (
present(filename))
then
146 fname = trim(folder) // trim(filename) //
'.nc'
148 fname = trim(folder) // trim(fname) //
'.nc'
152 nc = ncdataset(fname,
"r")
154 var = nc%getVariable(trim(varname))
157 var_shape = var%getShape()
158 if ((var_shape(1) .ne. nrows) .or. (var_shape(2) .ne. ncols))
then
159 call error_message(
'***ERROR: read_nc: mHM generated x and y are not matching NetCDF dimensions')
163 if (var%hasAttribute(
"_FillValue"))
then
164 call var%getAttribute(
'_FillValue', nodata_value)
165 else if (var%hasAttribute(
"missing_value"))
then
166 call var%getAttribute(
'missing_value', nodata_value)
168 call error_message(
'***ERROR: read_nc: there must be either the attribute "missing_value" or "_FillValue"')
172 time_var = nc%getVariable(
'time')
176 if (
present(is_meteo))
then
177 if (.not.
present(ntstepforcingday))
call error_message(
"read_nc: meteo file given but 'nTstepForcingDay' not passed")
179 select case(inctimestep)
181 if (ntstepforcingday .eq. nodata_i4)
then
182 ntstepforcingday = 1_i4
183 else if (ntstepforcingday .ne. 1_i4)
then
184 call error_message(
'***ERROR: read_forcing_nc: expected daily input forcing, but read something else. ' // &
185 'Ensure all input time steps have the same units across all input files')
188 if (ntstepforcingday .eq. nodata_i4)
then
189 ntstepforcingday = 24_i4
190 else if (ntstepforcingday .ne. 24_i4)
then
191 call error_message(
'***ERROR: read_forcing_nc: expected hourly input forcing, but read something else. ' // &
192 'Ensure all input time steps have the same units across all input files')
195 call error_message(
'***ERROR: read_nc: unknown nctimestep switch.')
201 if (
present(nctimestep))
then
202 if (inctimestep .ne. nctimestep)
then
203 call error_message(
'***ERROR: provided timestep ' // num2str(nctimestep) //&
204 ' does not match with the one in file ' // num2str(inctimestep), raise=.false.)
205 call error_message(
'File: ' // trim(fname))
210 call var%getData(
data, start = (/1, 1, time_start/), cnt = (/nrows, ncols, time_cnt/))
213 if (
present(maskout))
then
214 allocate(maskout(var_shape(1), var_shape(2), var_shape(3)))
215 maskout = ne(
data(:, :, :), nodata_value)
219 do i = 1,
size(
data, dim = 3)
222 if (any(eq(
data(:, :, i), nodata_value) .and. (mask)))
then
223 call error_message(
'***ERROR: read_nc: nodata value within domain ', raise=.false.)
224 call error_message(
' boundary in variable: ', trim(varname), raise=.false.)
225 call error_message(
' at timestep : ', trim(num2str(i)))
229 if (
present(lower))
then
230 if (any((
data(:, :, i) .lt. lower) .AND. mask(:, :)))
then
231 call error_message(
'***ERROR: read_nc: values in variable "', &
232 trim(varname),
'" are lower than ', trim(num2str(lower,
'(F7.2)')), raise=.false.)
233 call error_message(
' at timestep : ', trim(num2str(i)), raise=.false.)
234 call error_message(
'File: ', trim(fname), raise=.false.)
235 call error_message(
'Minval at timestep: ', trim(num2str(minval(
data(:, :, i)))), raise=.false.)
236 call error_message(
'Total minval: ', trim(num2str(minval(
data(:, :, :)))), raise=bound_error_)
240 if (
present(upper))
then
241 if (any((
data(:, :, i) .gt. upper) .AND. mask(:, :)))
then
242 call error_message(
'***ERROR: read_nc: values in variable "', &
243 trim(varname),
'" are greater than ', trim(num2str(upper,
'(F7.2)')), raise=.false.)
244 call error_message(
' at timestep : ', trim(num2str(i)), raise=.false.)
245 call error_message(
'File: ', trim(fname), raise=.false.)
246 call error_message(
'Maxval at timestep: ', trim(num2str(maxval(
data(:, :, i)))), raise=.false.)
247 call error_message(
'Total maxval: ', trim(num2str(maxval(
data(:, :, :)))), raise=bound_error_)
274 use mo_kind,
only: i4, dp
275 use mo_netcdf,
only: ncdataset, ncvariable
279 character(len=*),
intent(in) :: folder
280 integer(i4),
intent(in) :: nrows
281 integer(i4),
intent(in) :: ncols
282 character(len=*),
intent(in) :: varname
283 real(dp),
dimension(:,:),
allocatable,
intent(out) :: data
284 character(256),
optional,
intent(in) :: filename
287 type(ncdataset) :: nc
288 type(ncvariable) :: var
289 integer(i4),
allocatable,
dimension(:) :: var_shape
291 character(256) :: fname
292 real(dp) :: nodata_value
295 if (
present(filename))
then
296 fname = trim(folder) // trim(filename) //
'.nc'
298 fname = trim(folder) // trim(fname) //
'.nc'
302 nc = ncdataset(fname,
"r")
304 var = nc%getVariable(trim(varname))
307 var_shape = var%getShape()
308 if ( (var_shape(1) .ne. nrows) .or. (var_shape(2) .ne. ncols) )
then
309 call error_message(
'***ERROR: read_const_nc: mHM generated x and y are not matching NetCDF dimensions')
313 if (var%hasAttribute(
"_FillValue"))
then
314 call var%getAttribute(
'_FillValue', nodata_value)
315 else if (var%hasAttribute(
"missing_value"))
then
316 call var%getAttribute(
'missing_value', nodata_value)
318 call error_message(
'***ERROR: read_const_nc: there must be either the attribute "missing_value" or "_FillValue"')
322 call var%getData(
data, start=(/1,1/), cnt=(/nrows,ncols/))
343 subroutine read_weights_nc(folder, nRows, nCols, varName, data, mask, lower, upper, nocheck, maskout, fileName, bound_error)
345 use mo_kind,
only : dp, i4
346 use mo_netcdf,
only : ncdataset, ncvariable
347 use mo_string_utils,
only : num2str
348 use mo_utils,
only : eq, ne
353 character(len = *),
intent(in) :: folder
355 integer(i4),
intent(in) :: nrows
357 integer(i4),
intent(in) :: ncols
359 character(len = *),
intent(in) :: varname
361 real(dp),
dimension(:, :, :, :),
allocatable,
intent(out) :: data
363 logical,
dimension(:, :),
intent(in) :: mask
365 real(dp),
optional,
intent(in) :: lower
367 real(dp),
optional,
intent(in) :: upper
369 logical,
optional,
intent(in) :: nocheck
371 character(256),
optional,
intent(in) :: filename
373 logical,
dimension(:, :, :, :),
allocatable,
optional,
intent(out) :: maskout
375 logical,
optional,
intent(in) :: bound_error
378 character(256) :: fname
384 real(dp) :: nodata_value
388 type(ncdataset) :: nc
390 type(ncvariable) :: var
392 integer(i4),
allocatable,
dimension(:) :: var_shape
394 logical :: bound_error_
397 if (
present(nocheck)) checking = .NOT. nocheck
400 bound_error_ = .true.
401 if (
present(bound_error)) bound_error_ = bound_error
404 if (
present(filename))
then
405 fname = trim(folder) // filename
407 fname = trim(folder) // trim(fname) //
'.nc'
410 nc = ncdataset(fname,
"r")
411 var = nc%getVariable(trim(varname))
414 var_shape = var%getShape()
415 if ((var_shape(1) .ne. nrows) .or. (var_shape(2) .ne. ncols))
then
416 call error_message(
'***ERROR: read_weights_nc: mHM generated x and y are not matching NetCDF dimensions')
420 call var%getAttribute(
'missing_value', nodata_value)
423 call var%getData(data)
426 if (
present(maskout))
then
427 allocate(maskout(var_shape(1), var_shape(2), var_shape(3), var_shape(4)))
428 maskout = ne(
data(:, :, :, :), nodata_value)
432 do i = 1, var_shape(3)
433 do j = 1, var_shape(4)
436 if (any(eq(
data(:, :, i, j), nodata_value) .and. (mask)))
then
437 call error_message(
'***ERROR: read_weights_nc: nodata value within domain ', raise=.false.)
438 call error_message(
' boundary in variable: ', trim(varname), raise=.false.)
439 call error_message(
' at hour : ', trim(num2str(i)))
443 if (
present(lower))
then
444 if (any((
data(:, :, i, j) .lt. lower) .AND. mask(:, :)))
then
445 call error_message(
'***ERROR: read_weights_nc: values in variable "', &
446 trim(varname),
'" are lower than ', trim(num2str(lower,
'(F7.2)')), raise=.false.)
447 call error_message(
' at hour : ', trim(num2str(i)), raise=.false.)
448 call error_message(
'File: ', trim(fname), raise=.false.)
449 call error_message(
'Minval at hour: ', trim(num2str(minval(
data(:, :, i, j)),
'(F7.2)')), raise=.false.)
450 call error_message(
'Total minval: ', trim(num2str(minval(
data(:, :, :, :)),
'(F7.2)')), raise=bound_error_)
454 if (
present(upper))
then
455 if (any((
data(:, :, i, j) .gt. upper) .AND. mask(:, :)))
then
456 call error_message(
'***ERROR: read_weights_nc: values in variable "', &
457 trim(varname),
'" are greater than ', trim(num2str(upper,
'(F7.2)')), raise=.false.)
458 call error_message(
' at hour : ', trim(num2str(i)), raise=.false.)
459 call error_message(
'File: ', trim(fname), raise=.false.)
460 call error_message(
'Maxval at hour: ', trim(num2str(maxval(
data(:, :, i, j)),
'(F7.2)')), raise=.false.)
461 call error_message(
'Total maxval: ', trim(num2str(maxval(
data(:, :, :, :)),
'(F7.2)')), raise=bound_error_)
490 use mo_constants,
only : dayhours, daysecs, yeardays
491 use mo_julian,
only : caldat, dec2date, julday
492 use mo_kind,
only : dp, i4, i8
493 use mo_netcdf,
only : ncvariable
494 use mo_string_utils,
only : divide_string
499 type(ncvariable),
intent(in) :: var
501 character(256),
intent(in) :: fname
503 integer(i4),
intent(out) :: inctimestep
505 integer(i4),
intent(out) :: time_start
507 integer(i4),
intent(out) :: time_cnt
509 type(
period),
intent(in),
optional :: target_period
512 integer(i4) :: yRef, dRef, mRef, hRef, jRef
514 character(256) :: AttValues
516 character(256),
dimension(:),
allocatable :: strArr, date, time
518 integer(i8) :: time_step_seconds
520 integer(i8),
allocatable,
dimension(:) :: time_data
521 integer(i8),
allocatable,
dimension(:) :: time_diff
523 type(
period) :: nc_period, clip_period
524 integer(i4) :: ncJulSta1, dd, n_time
525 integer(i4) :: mmcalstart, mmcalend, yycalstart, yycalend
526 integer(i4) :: mmncstart, yyncstart
528 integer(i4) :: hstart_int, hend_int
530 call var%getAttribute(
'units', attvalues)
533 call divide_string(trim(attvalues),
' ', strarr)
536 call divide_string(trim(strarr(3)),
'-', date)
537 read(date(1), *) yref
538 read(date(2), *) mref
539 read(date(3), *) dref
541 jref = julday(dd = dref, mm = mref, yy = yref)
545 if(
size(strarr) .gt. 3)
then
546 call divide_string(trim(strarr(4)),
':', time)
547 read(time(1), *) href
551 if (strarr(1) .EQ.
'days')
then
552 time_step_seconds = int(daysecs)
553 else if (strarr(1) .eq.
'hours')
then
554 time_step_seconds = int(daysecs / dayhours)
555 else if (strarr(1) .eq.
'minutes')
then
556 time_step_seconds = int(daysecs / dayhours / 60._dp)
557 else if (strarr(1) .eq.
'seconds')
then
558 time_step_seconds = 1_i8
560 call error_message(
'***ERROR: Please provide the input data in (days, hours, minutes, seconds) ', &
561 'since YYYY-MM-DD[ HH:MM:SS] in the netcdf file. Found: ', trim(attvalues))
565 call var%getData(time_data)
567 time_data = time_data * time_step_seconds
570 if (
size(time_data) .le. 1)
then
571 call error_message(
'***ERROR: length of time dimension needs to be at least 2 in file: ' // trim(fname))
577 n_time =
size(time_data)
578 call dec2date(time_data(1) / daysecs - 0.5_dp + jref + href / 24._dp, nc_period%dStart, nc_period%mStart, &
579 nc_period%yStart, hstart_int)
580 nc_period%julStart = int(time_data(1) / daysecs + jref + href / 24._dp)
581 call dec2date(time_data(n_time) / daysecs - 0.5_dp + jref + href / 24._dp, nc_period%dEnd, nc_period%mEnd, &
582 nc_period%yEnd, hend_int)
583 nc_period%julEnd = int(time_data(n_time) / daysecs + jref + href / 24._dp)
586 if (
present(target_period))
then
587 clip_period = target_period
589 clip_period = nc_period
593 allocate(time_diff(n_time - 1))
594 time_diff = (time_data(2 : n_time) - time_data(1 : n_time - 1)) / int(daysecs, i8)
596 if (all(abs(time_diff - 1._dp) .lt. 1._dp))
then
599 else if (all(abs(time_diff) .lt. 32._dp) .and. all(abs(time_diff) .gt. 27._dp))
then
602 else if ((all(abs(time_diff) .lt. yeardays + 2)) .and. (all(abs(time_diff) .gt. yeardays - 1._dp)))
then
605 else if (all(abs((time_data(2 : n_time) - time_data(1 : n_time - 1)) / 3600._dp - 1._dp) .lt. 1.e-6))
then
608 call error_message(
'***ERROR: time_steps are not equal over all times in file and/or do not conform to' // &
609 ' requested timestep in file (', trim(fname),
')')
613 select case(inctimestep)
615 ncjulsta1 = nc_period%julStart
616 time_start = clip_period%julStart - ncjulsta1 + 1_i4
617 time_cnt = clip_period%julEnd - clip_period%julStart + 1_i4
619 call caldat(clip_period%julStart, dd, mmcalstart, yycalstart)
620 call caldat(nc_period%julStart, dd, mmncstart, yyncstart)
622 ncjulsta1 = julday(1, mmncstart, yyncstart)
623 call caldat(clip_period%julEnd, dd, mmcalend, yycalend)
624 time_start = (yycalstart * 12 + mmcalstart) - (yyncstart * 12 + mmncstart) + 1_i4
625 time_cnt = (yycalend * 12 + mmcalend) - (yycalstart * 12 + mmcalstart) + 1_i4
627 call caldat(clip_period%julStart, dd, mmcalstart, yycalstart)
628 call caldat(nc_period%julStart, dd, mmncstart, yyncstart)
630 ncjulsta1 = julday(1, 1, yyncstart)
631 call caldat(clip_period%julEnd, dd, mmcalend, yycalend)
632 time_start = yycalstart - yyncstart + 1_i4
633 time_cnt = yycalend - yycalstart + 1_i4
635 ncjulsta1 = nc_period%julStart
636 time_start = (clip_period%julStart - ncjulsta1) * 24_i4 + 1_i4
637 time_cnt = (clip_period%julEnd - clip_period%julStart + 1_i4) * 24_i4
639 call error_message(
'***ERROR: read_nc: unknown nctimestep switch.')
643 if (.not. ((ncjulsta1 .LE. clip_period%julStart) .AND. (nc_period%julEnd .GE. clip_period%julEnd)))
then
644 call error_message(
'***ERROR: read_nc: time period of input data: ', trim(fname), &
645 ' is not matching modelling period.')
649 deallocate(time_diff)
subroutine, public read_weights_nc(folder, nrows, ncols, varname, data, mask, lower, upper, nocheck, maskout, filename, bound_error)
Reads weights for meteo forcings input in NetCDF file format.
subroutine, public read_nc(folder, nrows, ncols, varname, mask, data, target_period, lower, upper, nctimestep, filename, nocheck, maskout, is_meteo, bound_error, ntstepforcingday)
Reads forcing input in NetCDF file format.