40 character(len=:),
allocatable :: string
67 character(len=:),
allocatable,
intent(in) :: val
80 type(
string_t),
intent(inout) :: this
82 if (
allocated(this%string))
deallocate(this%string)
89 subroutine warn_msg(code, warning_msg, already_warned)
92 integer,
intent(in) :: code
94 character(len=*),
intent(in) :: warning_msg
96 logical,
intent(inout),
optional :: already_warned
98 if (
present(already_warned))
then
99 if (already_warned)
return
101 already_warned = .true.
104 //
'): ' // trim(warning_msg)
114 integer,
intent(in) :: code
116 logical,
intent(in) :: condition_ok
118 character(len=*),
intent(in) :: warning_msg
120 if (.not. condition_ok)
then
132 integer,
intent(in) :: code
134 logical,
intent(in) :: condition_ok
136 character(len=*),
intent(in) :: error_msg
138 integer,
parameter :: kErrorFileId = 10
142 if (.not. condition_ok)
then
144 //
'): ' // trim(error_msg)
145 open(unit=kerrorfileid, file =
"error.json", action =
"WRITE")
146 write(kerrorfileid,
'(A)')
'{'
147 write(kerrorfileid,
'(A)')
' "code" : "'// &
149 write(kerrorfileid,
'(A)')
' "message" : "'//trim(error_msg)//
'"'
150 write(kerrorfileid,
'(A)')
'}'
153 call mpi_abort(mpi_comm_world, code, ierr)
167 integer,
intent(in) :: code
169 logical,
intent(in) :: condition_ok
171 if (.not. condition_ok)
then
175 call assert_msg(code, condition_ok,
'assertion failed')
186 integer,
intent(in) :: code
188 call assert(code, .false.)
198 integer,
intent(in) :: code
200 character(len=*),
intent(in) :: error_msg
221 if (.not. found_unit)
then
223 'no more units available - need to free_unit()')
235 integer,
intent(in) :: unit
249 character(len=*),
intent(in) :: filename
251 integer,
intent(out) :: unit
256 open(unit=unit, file=filename, status=
'old', action=
'read', iostat=ios)
257 call assert_msg(544344918, ios == 0,
'unable to open file ' &
270 character(len=*),
intent(in) :: filename
272 integer,
intent(out) :: unit
277 open(unit=unit, file=filename, status=
'replace', action=
'write', &
279 call assert_msg(609624199, ios == 0,
'unable to open file ' &
290 integer,
intent(in) :: unit
304 real(kind=
dp),
intent(in) :: v
316 real(kind=
dp),
intent(in) :: r
329 real(kind=
dp),
intent(in) :: r
341 real(kind=
dp),
intent(in) :: d
353 real(kind=
dp),
intent(in) :: temp
355 real(kind=
dp),
intent(in) :: pressure
357 real(kind=
dp) :: boltz, avogad, mwair, rgas, rhoair, viscosd, &
360 boltz =
const%boltzmann
361 avogad =
const%avagadro
362 mwair =
const%air_molec_weight
363 rgas =
const%univ_gas_const
365 rhoair = (pressure * mwair) / (rgas * temp)
367 viscosd = (1.8325d-5 * (296.16d0 + 120d0) / (temp + 120d0)) &
368 * (temp / 296.16d0)**1.5d0
369 viscosk = viscosd / rhoair
370 gasspeed = sqrt(8d0 * boltz * temp * avogad / (
const%pi * mwair))
382 real(kind=
dp),
intent(in) :: d1
384 real(kind=
dp),
intent(in) :: d2
386 real(kind=
dp),
intent(in),
optional :: rel_tol
388 real(kind=
dp),
intent(in),
optional :: abs_tol
397 if (
present(rel_tol)) eps = rel_tol
398 if (
present(abs_tol)) at = abs_tol
404 if (abs(d1 - d2) / (abs(d1) + abs(d2)) .lt. eps)
then
407 if (abs(d1 - d2) .le. at)
then
424 real(kind=
dp),
intent(in) :: d1
426 real(kind=
dp),
intent(in) :: d2
428 real(kind=
dp),
intent(in) :: abs_tol
431 real(kind=
dp),
parameter :: eps = 1d-8
437 if ((abs(d1 - d2) .lt. abs_tol) .or. &
438 (abs(d1 - d2) / (abs(d1) + abs(d2)) .lt. eps))
then
452 second_name, second_time)
455 character(len=*),
intent(in) :: first_name
457 real(kind=
dp),
intent(in) :: first_time
459 character(len=*),
intent(in) :: second_name
461 real(kind=
dp),
intent(in) :: second_time
463 real(kind=
dp) :: ratio
465 ratio = first_time / second_time
466 if (abs(ratio - aint(ratio)) > 1d-6)
then
467 call warn_msg(952299377, trim(first_name) &
468 //
" is not an integer multiple of " // trim(second_name))
486 real(kind=
dp),
intent(in) :: time
488 real(kind=
dp),
intent(in) :: timestep
490 real(kind=
dp),
intent(in) :: interval
492 real(kind=
dp),
intent(inout) :: last_time
494 logical,
intent(out) :: do_event
497 real(kind=
dp),
parameter :: tolerance = 1d-6
499 real(kind=
dp) closest_interval_time
502 if (time .eq. 0d0)
then
506 if ((time - last_time) .lt. interval * (1d0 - tolerance))
then
510 if ((time - last_time) .ge. interval)
then
515 closest_interval_time = anint(time / interval) * interval
516 if (abs(time - closest_interval_time) &
517 .lt. abs(time + timestep - closest_interval_time)) &
539 real(kind=
dp),
intent(in) :: min_x
541 real(kind=
dp),
intent(in) :: max_x
543 integer,
intent(in) :: n
552 call assert(999299119, n >= 0)
554 a = real(i - 1, kind=
dp) / real(n - 1, kind=
dp)
555 linspace(i) = (1d0 - a) * min_x + a * max_x
571 real(kind=
dp),
intent(in) :: min_x
573 real(kind=
dp),
intent(in) :: max_x
575 integer,
intent(in) :: n
580 real(kind=
dp),
allocatable :: log_x(:)
584 call assert(804623592, n >= 0)
586 call assert(548290438, min_x > 0d0)
587 call assert(805259035, max_x > 0d0)
588 log_x =
linspace(log(min_x), log(max_x), n)
611 real(kind=
dp),
intent(in) :: min_x
613 real(kind=
dp),
intent(in) :: max_x
615 integer,
intent(in) :: n
617 real(kind=
dp),
intent(in) :: x
624 * real(n - 1, kind=
dp)) + 1
645 real(kind=
dp),
intent(in) :: min_x
647 real(kind=
dp),
intent(in) :: max_x
649 integer,
intent(in) :: n
651 real(kind=
dp),
intent(in) :: x
671 integer,
intent(in) :: n
673 real(kind=
dp),
intent(in) :: x_vals(n)
675 real(kind=
dp),
intent(in) :: x
684 do while (x >= x_vals(p))
705 real(kind=
dp),
intent(in) :: x_vals(:)
707 real(kind=
dp),
intent(in) :: y_vals(
size(x_vals))
709 real(kind=
dp),
intent(in) :: x
712 real(kind=
dp) :: y, alpha
721 if (y_vals(p) == y_vals(p+1))
then
724 alpha = (x - x_vals(p)) / (x_vals(p+1) - x_vals(p))
725 y = (1d0 - alpha) * y_vals(p) + alpha * y_vals(p+1)
742 real(kind=
dp),
intent(in) :: x_1
744 real(kind=
dp),
intent(in) :: x_n
746 integer,
intent(in) :: n
748 integer,
intent(in) :: i
750 real(kind=
dp) :: alpha
755 alpha = real(i - 1, kind=
dp) / real(n - 1, kind=
dp)
767 character(len=*),
intent(in) :: string
772 call assert_msg(447772570, len_trim(string) <= 20, &
773 'error converting "' // trim(string) &
774 //
'" to integer: string too long')
775 read(string,
'(i20)', iostat=ios) val
777 'error converting "' // trim(string) &
789 character(len=*),
intent(in) :: string
794 call assert_msg(733728030, len_trim(string) <= 30, &
795 'error converting "' // trim(string) //
'" to real: string too long')
796 read(string,
'(f30.0)', iostat=ios) val
798 'error converting "' // trim(string) &
810 character(len=*),
intent(in) :: string
815 if ((trim(string) ==
'yes') &
816 .or. (trim(string) ==
'y') &
817 .or. (trim(string) ==
'true') &
818 .or. (trim(string) ==
't') &
819 .or. (trim(string) ==
'1'))
then
821 elseif ((trim(string) ==
'no') &
822 .or. (trim(string) ==
'n') &
823 .or. (trim(string) ==
'false') &
824 .or. (trim(string) ==
'f') &
825 .or. (trim(string) ==
'0'))
then
828 call die_msg(985010153,
'error converting "' // trim(string) &
841 integer,
intent(in) :: val
843 character(len=CAMP_UTIL_CONVERT_STRING_LEN) :: ret_val
846 write(ret_val,
'(i30)') val
857 real(kind=
dp),
intent(in) :: val
859 character(len=CAMP_UTIL_CONVERT_STRING_LEN) :: ret_val
862 write(ret_val,
'(g30.20)') val
873 real(kind=
sp),
intent(in) :: val
875 character(len=CAMP_UTIL_CONVERT_STRING_LEN) :: ret_val
878 write(ret_val,
'(g30.20)') val
889 logical,
intent(in) :: val
891 character(len=CAMP_UTIL_CONVERT_STRING_LEN) :: ret_val
909 complex(kind=dc),
intent(in) :: val
911 character(len=CAMP_UTIL_CONVERT_STRING_LEN) :: ret_val
914 ret_val =
"(" // trim(
to_string(real(val))) &
915 //
", " // trim(
to_string(aimag(val))) //
")"
923 character(len=CAMP_UTIL_CONVERT_STRING_LEN) &
927 integer,
intent(in) :: val
929 integer,
intent(in) :: max_len
931 character(len=CAMP_UTIL_CONVERT_STRING_LEN) :: ret_val
934 if (len_trim(ret_val) > max_len)
then
944 character(len=CAMP_UTIL_CONVERT_STRING_LEN) &
948 real(kind=dp),
intent(in) :: val
950 integer,
intent(in) :: max_len
952 character(len=CAMP_UTIL_CONVERT_STRING_LEN) :: ret_val, exp_str, frac_str
953 integer :: exp_val, exp_len, frac_len, use_frac_len, min_frac_len, i
954 real(kind=dp) :: frac_val
958 if (max_len >= 3)
then
969 exp_val = floor(log10(abs(val)))
970 frac_val = val / 10d0**exp_val
974 exp_len = len_trim(exp_str)
975 frac_len = len_trim(frac_str)
976 use_frac_len = max_len - 1 - exp_len
977 if (use_frac_len > frac_len)
then
978 use_frac_len = frac_len
985 if (use_frac_len < min_frac_len)
then
990 ret_val = frac_str(1:use_frac_len) //
"e" // trim(exp_str)
999 character(len=CAMP_UTIL_CONVERT_STRING_LEN) &
1003 real(kind=dp),
intent(in) :: time
1005 integer,
intent(in) :: max_len
1007 integer,
dimension(4),
parameter :: scale = (/ 1, 60, 60, 24 /)
1008 character,
dimension(4),
parameter :: unit = (/
"s",
"m",
"h",
"d" /)
1010 character(len=CAMP_UTIL_CONVERT_STRING_LEN) :: ret_val
1013 real(kind=dp) :: scaled_time
1018 scaled_time = scaled_time / real(scale(i), kind=dp)
1020 if (len_trim(ret_val) <= max_len)
then
1025 if (.not. len_ok)
then
1068 function split_char( this, splitter, compress )
result( sub_strings )
1071 type(
string_t),
allocatable :: sub_strings(:)
1073 class(
string_t),
intent(in) :: this
1075 character(len=*),
intent(in) :: splitter
1081 logical,
intent(in),
optional :: compress
1083 integer :: i, start_str, i_substr, sl, count
1084 logical :: l_comp, is_string
1086 if( .not.
allocated( this%string ) )
return
1087 if(
present( compress ) )
then
1093 sl = len( splitter )
1094 if( sl .eq. 0 )
then
1095 allocate( sub_strings( 1 ) )
1096 sub_strings(1)%string = this%string
1103 is_string = .not. l_comp
1104 do while( i .le. len( this%string ) - sl + 1 )
1105 if( this%string(i:i+sl-1) .eq. splitter )
then
1106 if( is_string )
then
1110 is_string = .not. l_comp
1116 if( is_string ) count = count + 1
1118 allocate( sub_strings( count ) )
1123 is_string = .not. l_comp
1124 do while( i .le. len( this%string ) - sl + 1 )
1125 if( this%string(i:i+sl-1) .eq. splitter )
then
1126 if( is_string )
then
1127 if( i .eq. start_str )
then
1128 sub_strings( i_substr )%string =
""
1130 sub_strings( i_substr )%string = this%string(start_str:i-1)
1132 i_substr = i_substr + 1
1136 is_string = .not. l_comp
1143 if( is_string )
then
1144 if( i .eq. start_str )
then
1145 sub_strings( i_substr )%string =
""
1147 sub_strings( i_substr )%string = &
1148 this%string( start_str:len( this%string ) )
1163 type(
string_t),
allocatable :: sub_strings(:)
1165 class(
string_t),
intent(in) :: this
1167 type(
string_t),
intent(in) :: splitter
1173 logical,
intent(in),
optional :: compress
1175 sub_strings = this%split_char( splitter%string, compress )
1188 integer,
intent(in) :: n
1190 real(kind=dp),
intent(in) :: vec_cts(n)
1192 integer,
intent(in) :: n_samp
1194 integer,
intent(out) :: vec_disc(n)
1197 real(kind=dp) :: vec_tot
1199 vec_tot = sum(vec_cts)
1202 vec_disc = nint(vec_cts / vec_tot * real(n_samp, kind=dp))
1205 do while (sum(vec_disc) < n_samp)
1206 k = minloc(abs(real(vec_disc + 1, kind=dp) - vec_cts) &
1207 - abs(real(vec_disc, kind=dp) - vec_cts))
1208 vec_disc(k) = vec_disc(k) + 1
1212 do while (sum(vec_disc) > n_samp)
1213 k = minloc(abs(real(vec_disc - 1, kind=dp) - vec_cts) &
1214 - abs(real(vec_disc, kind=dp) - vec_cts))
1215 vec_disc(k) = vec_disc(k) - 1
1218 call assert_msg(323412496, sum(vec_disc) == n_samp, &
1219 'generated incorrect number of samples')
1229 integer,
intent(in) :: int_vec(:)
1231 integer,
intent(out) :: int_avg
1233 int_avg = sum(int_vec) /
size(int_vec)
1243 real(kind=dp),
intent(in) :: real_vec(:)
1245 real(kind=dp),
intent(out) :: real_avg
1247 real_avg = sum(real_vec) / real(
size(real_vec), kind=dp)
1258 character(len=*),
intent(in) :: array(:)
1260 character(len=*),
intent(in) :: val
1276 real(kind=dp),
intent(inout),
allocatable :: x(:)
1278 integer,
intent(in) :: n
1280 logical,
intent(in),
optional :: only_grow
1283 real(kind=dp),
allocatable :: tmp_x(:)
1285 if (
allocated(x))
then
1287 if (
present(only_grow))
then
1288 new_n = max(new_n,
size(x))
1290 if (
size(x) /= new_n)
then
1291 allocate(tmp_x(new_n))
1293 tmp_x(1:min(new_n,
size(x))) = x(1:min(new_n,
size(x)))
1294 call move_alloc(tmp_x, x)
1310 real(kind=dp),
intent(inout),
allocatable :: x(:, :)
1312 integer,
intent(in) :: n1
1314 integer,
intent(in) :: n2
1316 logical,
intent(in),
optional :: only_grow
1318 integer :: new_n1, new_n2, n1_min, n2_min
1319 real(kind=dp),
allocatable :: tmp_x(:, :)
1321 if (
allocated(x))
then
1324 if (
present(only_grow))
then
1325 new_n1 = max(new_n1,
size(x, 1))
1326 new_n2 = max(new_n2,
size(x, 2))
1328 if ((
size(x, 1) /= new_n1) .or. (
size(x, 2) /= new_n2))
then
1329 allocate(tmp_x(new_n1, new_n2))
1330 n1_min = min(new_n1,
size(x, 1))
1331 n2_min = min(new_n2,
size(x, 2))
1333 tmp_x(1:n1_min, 1:n2_min) = x(1:n1_min, 1:n2_min)
1334 call move_alloc(tmp_x, x)
1350 integer,
intent(inout),
allocatable :: x(:)
1352 integer,
intent(in) :: n
1354 logical,
intent(in),
optional :: only_grow
1357 integer,
allocatable :: tmp_x(:)
1359 if (
allocated(x))
then
1361 if (
present(only_grow))
then
1362 new_n = max(new_n,
size(x))
1364 if (
size(x) /= new_n)
then
1365 allocate(tmp_x(new_n))
1367 tmp_x(1:min(new_n,
size(x))) = x(1:min(new_n,
size(x)))
1368 call move_alloc(tmp_x, x)
1384 integer,
intent(inout),
allocatable :: x(:, :)
1386 integer,
intent(in) :: n1
1388 integer,
intent(in) :: n2
1390 logical,
intent(in),
optional :: only_grow
1392 integer :: new_n1, new_n2, n1_min, n2_min
1393 integer,
allocatable :: tmp_x(:, :)
1395 if (
allocated(x))
then
1398 if (
present(only_grow))
then
1399 new_n1 = max(new_n1,
size(x, 1))
1400 new_n2 = max(new_n2,
size(x, 2))
1402 if ((
size(x, 1) /= new_n1) .or. (
size(x, 2) /= new_n2))
then
1403 allocate(tmp_x(new_n1, new_n2))
1404 n1_min = min(new_n1,
size(x, 1))
1405 n2_min = min(new_n2,
size(x, 2))
1407 tmp_x(1:n1_min, 1:n2_min) = x(1:n1_min, 1:n2_min)
1408 call move_alloc(tmp_x, x)
1424 character(len=*),
intent(inout),
allocatable :: x(:)
1426 integer,
intent(in) :: n
1428 if (
allocated(x))
then
1429 if (
size(x) /= n)
then
1449 character(len=*),
intent(in) :: filename
1451 character(len=*),
intent(out) :: basename
1454 logical :: found_period
1457 i = len_trim(basename)
1458 found_period = .false.
1459 do while ((i > 0) .and. (.not. found_period))
1464 if (basename(i:i) ==
".")
then
1465 found_period = .true.
1482 character(len=*),
intent(out) :: date_time
1484 character(len=10) :: date, time, zone
1486 call assert_msg(893219839, len(date_time) >= 29, &
1487 "date_time string must have length at least 29")
1488 call date_and_time(date, time, zone)
1490 write(date_time,
'(14a)') date(1:4),
"-", date(5:6),
"-", &
1491 date(7:8),
"T", time(1:2),
":", time(3:4),
":", &
1492 time(5:10), zone(1:3),
":", zone(4:5)
1502 real(kind=dp),
intent(in) :: deg
1504 deg2rad = deg / 180d0 * const%pi
1514 real(kind=dp),
intent(in) :: rad
1516 rad2deg = rad / const%pi * 180d0
1530 integer,
intent(inout) :: data(:)
1532 integer,
intent(out) :: perm(size(data))
1534#ifdef CAMP_USE_C_SORT
1535 integer(kind=c_int) :: n_c
1536 integer(kind=c_int),
target :: data_c(size(data))
1537 integer(kind=c_int),
target :: perm_c(size(data))
1538 type(c_ptr) :: data_ptr, perm_ptr
1540#ifndef DOXYGEN_SKIP_DOC
1542 subroutine integer_sort_c(n_c, data_ptr, perm_ptr)
bind(c)
1544 integer(kind=c_int),
value :: n_c
1545 type(c_ptr),
value :: data_ptr, perm_ptr
1546 end subroutine integer_sort_c
1550 data_c = int(
data, kind=c_int)
1552 n_c = int(
size(data), kind=c_int)
1553 data_ptr = c_loc(data_c)
1554 perm_ptr = c_loc(perm_c)
1555 call integer_sort_c(n_c, data_ptr, perm_ptr)
1570 character(len=*),
intent(in) :: filename
1572 real(kind=dp),
intent(inout),
allocatable ::
data(:,:)
1574 integer :: unit, row, col
1576 character(len=1000) :: word
1585 do while (.not. eof)
1587 if (len_trim(word) > 0)
then
1589 if (col >
size(
data, 2))
then
1593 if (col >
size(
data, 2))
then
1594 call assert_msg(516120334, col <=
size(
data, 2), &
1595 trim(filename) //
": line " &
1599 if (row >
size(
data, 1))
then
1605 if (eol .or. eof)
then
1610 (col == 1) .or. (col ==
size(
data, 2) + 1), &
1611 trim(filename) //
": line " &
1634 character(len=*),
intent(in) :: filename
1636 real(kind=dp),
intent(in) ::
data(:)
1642 write(unit,
'(e30.15e3)')
data(i)
1654 character(len=*),
intent(in) :: filename
1656 real(kind=dp),
intent(in) ::
data(:,:)
1658 integer :: unit, i, j
1661 do i = 1,
size(
data, 1)
1662 do j = 1,
size(
data, 2)
1663 write(unit,
'(e30.15e3)', advance=
'no')
data(i, j)
1677 real(kind=dp),
allocatable,
intent(inout) ::
data(:,:)
1679 integer,
intent(in) :: rows
1681 integer,
intent(in) :: cols
1683 real(kind=dp) :: tmp_data(rows, cols)
1684 integer :: data_rows, data_cols
1686 data_rows = min(rows,
size(
data, 1))
1687 data_cols = min(cols,
size(
data, 2))
1688 tmp_data(1:data_rows, 1:data_cols) =
data(1:data_rows, 1:data_cols)
1690 allocate(
data(rows, cols))
1691 data(1:data_rows, 1:data_cols) = tmp_data(1:data_rows, 1:data_cols)
1725 integer,
intent(in) :: unit
1727 character,
intent(out) :: char
1729 logical,
intent(out) :: eol
1731 logical,
intent(out) :: eof
1734 character(len=1) :: read_char
1740 read(unit=unit, fmt=
'(a)', advance=
'no',
end=100, eor=110, &
1741 iostat=ios) read_char
1743 write(0,*)
'ERROR: reading file: IOSTAT = ', ios
1769 integer,
intent(in) :: unit
1771 character(len=*),
intent(out) :: word
1773 logical,
intent(out) :: eol
1775 logical,
intent(out) :: eof
1784 do while (((ichar(char) == 9) .or. (ichar(char) == 32)) &
1785 .and. (.not. eol) .and. (.not. eof))
1788 if (eol .or. eof)
return
1794 do while ((ichar(char) /= 9) .and. (ichar(char) /= 32) &
1795 .and. (.not. eol) .and. (.not. eof) .and. (i < len(word)))
1798 if (i < len(word))
then
1814 character(len=*),
intent(in) :: string
1816 character(len=*),
intent(in) :: start_string
1818 if (len(string) < len(start_string))
then
1822 if (string(1:len(start_string)) == start_string)
then
1836 real(kind=dp),
intent(in) :: x1
1838 real(kind=dp),
intent(in) :: x2
1850 real(kind=dp),
intent(in) :: p
1867 real(kind=dp),
intent(in) :: p(:)
1879 integer,
intent(in) :: n
1887 pow2_above = ibset(0, bit_size(n) - leadz(n - 1))
Interface for to_string functions.
integer, parameter dp
Kind of a double precision real number.
type(const_t), save const
Fixed variable for accessing the constant's values.
integer, parameter sp
Kind of a single precision real number.
Common utility subroutines.
real(kind=dp) function string_to_real(string)
Convert a string to a real.
subroutine ensure_integer_array_2d_size(x, n1, n2, only_grow)
Allocate or reallocate the given array to ensure it is of the given size, preserving any data and/or ...
character(len=camp_util_convert_string_len) function real_dp_to_string(val)
Convert a double precision real to a string format.
elemental subroutine string_t_finalize(this)
Finalize a string.
subroutine check_event(time, timestep, interval, last_time, do_event)
Computes whether an event is scheduled to take place.
subroutine get_basename(filename, basename)
Strip the extension to find the basename.
real(kind=dp) function deg2rad(deg)
Convert degrees to radians.
logical function almost_equal(d1, d2, rel_tol, abs_tol)
Tests whether two real numbers are almost equal using only a relative tolerance.
logical function starts_with(string, start_string)
Checks whether a string starts with a given other string.
subroutine integer_sort(data, perm)
Sort the given data array and return the permutation defining the sort.
type(string_t) function, dimension(:), allocatable split_string(this, splitter, compress)
Splits a string on a substring.
integer, parameter camp_max_filename_len
Maximum length of filenames.
subroutine iso8601_date_and_time(date_time)
Current date and time in ISO 8601 format.
character(len=camp_util_convert_string_len) function real_sp_to_string(val)
Convert a single precision real to a string format.
subroutine open_file_write(filename, unit)
Open a file for writing with an automatically assigned unit and test that it succeeds....
subroutine average_integer(int_vec, int_avg)
Computes the average of an array of integer numbers.
real(kind=dp) elemental function diam2rad(d)
Convert diameter (m) to radius (m).
subroutine assert(code, condition_ok)
Errors unless condition_ok is true.
real(kind=dp) function rad2deg(rad)
Convert radians to degrees.
subroutine free_unit(unit)
Frees a unit number returned by get_unit().
subroutine close_file(unit)
Close a file and de-assign the unit.
integer function get_unit()
Returns an available unit number. This should be freed by free_unit().
integer function linspace_find(min_x, max_x, n, x)
Find the position of a real number in a 1D linear array.
real(kind=dp) function interp_1d(x_vals, y_vals, x)
1D linear interpolation.
subroutine ensure_real_array_2d_size(x, n1, n2, only_grow)
Allocate or reallocate the given array to ensure it is of the given size, preserving any data and/or ...
real(kind=dp) function air_mean_free_path(temp, pressure)
Calculate air molecular mean free path (m).
integer, parameter unit_offset
Minimum unit number to allocate.
character(len=camp_util_convert_string_len) function time_to_string_max_len(time, max_len)
Convert a time to a string format of maximum length.
real(kind=dp) elemental function sphere_rad2vol(r)
Convert geometric radius (m) to mass-equivalent volume (m^3) for spherical particles.
integer function string_array_find(array, val)
Return the index of the first occurance of the given value in the array, or 0 if it is not present.
integer function find_1d(n, x_vals, x)
Find the position of a real number in an arbitrary 1D array.
integer, parameter max_units
Maximum number of IO units usable simultaneously.
elemental real(kind=dp) function harmonic_mean(x1, x2)
Compute the harmonic mean of two numbers.
subroutine savetxt_2d(filename, data)
Write a real 2D array to a text file.
integer, parameter camp_util_convert_string_len
Length of string for converting numbers.
subroutine average_real(real_vec, real_avg)
Computes the average of an array of real numbers.
subroutine vec_cts_to_disc(n, vec_cts, n_samp, vec_disc)
Convert a real-valued vector into an integer-valued vector.
integer function string_to_integer(string)
Convert a string to an integer.
subroutine ensure_integer_array_size(x, n, only_grow)
Allocate or reallocate the given array to ensure it is of the given size, preserving any data and/or ...
subroutine loadtxt(filename, data)
Load a real array from a text file.
character(len=camp_util_convert_string_len) function logical_to_string(val)
Convert a logical to a string format.
character(len=camp_util_convert_string_len) function real_to_string_max_len(val, max_len)
Convert a real to a string format of maximum length.
integer function logspace_find(min_x, max_x, n, x)
Find the position of a real number in a 1D logarithmic array.
subroutine die_msg(code, error_msg)
Error immediately.
real(kind=dp) function, dimension(:), allocatable logspace(min_x, max_x, n)
Makes a logarithmically spaced array of length n from min to max.
integer function pow2_above(n)
Return the least power-of-2 that is at least equal to n.
real(kind=dp) function interp_linear_disc(x_1, x_n, n, i)
Linear interpolation over discrete indices.
subroutine savetxt_1d(filename, data)
Write a real 1D array to a text file.
subroutine open_file_read(filename, unit)
Open a file for reading with an automatically assigned unit and test that it succeeds....
subroutine die(code)
Error immediately.
type(string_t) function, pointer string_t_constructor(val)
Constructor for string_t.
type(string_t) function, dimension(:), allocatable split_char(this, splitter, compress)
Splits a string on a substring.
subroutine reallocate_real_array2d(data, rows, cols)
Reallocate a 2D real array to the given size, preserving the contents.
logical, dimension(max_units), save unit_used
Table of unit numbers storing allocation status.
subroutine assert_msg(code, condition_ok, error_msg)
Errors unless condition_ok is true.
subroutine ensure_real_array_size(x, n, only_grow)
Allocate or reallocate the given array to ensure it is of the given size, preserving any data and/or ...
subroutine warn_msg(code, warning_msg, already_warned)
Prints a warning message.
subroutine ensure_string_array_size(x, n)
Allocate or reallocate the given array to ensure it is of the given size, without preserving data.
logical function string_to_logical(string)
Convert a string to a logical.
subroutine read_word_raw(unit, word, eol, eof)
Read a white-space delimited word from a file, signaling if we have EOL or EOF. If EOL or EOF are tru...
character(len=camp_util_convert_string_len) function complex_to_string(val)
Convert a complex to a string format.
character(len=camp_util_convert_string_len) function integer_to_string(val)
Convert an integer to a string format.
subroutine check_time_multiple(first_name, first_time, second_name, second_time)
Check that the first time interval is close to an integer multiple of the second, and warn if it is n...
real(kind=dp) function entropy(p)
Compute the entropy of a probability mass function (non necessarily normalized).
elemental real(kind=dp) function nplogp(p)
Compute for computing entropy.
subroutine read_char_raw(unit, char, eol, eof)
Read a single character from a file, signaling if we have hit end-of-line (EOL) or end-of-file (EOF)....
real(kind=dp) function, dimension(:), allocatable linspace(min_x, max_x, n)
Makes a linearly spaced array from min to max.
real(kind=dp) elemental function rad2diam(r)
Convert radius (m) to diameter (m).
character(len=camp_util_convert_string_len) function integer_to_string_max_len(val, max_len)
Convert an integer to a string format of maximum length.
subroutine warn_assert_msg(code, condition_ok, warning_msg)
Prints a warning message if condition_ok is false.
logical function almost_equal_abs(d1, d2, abs_tol)
Tests whether two real numbers are almost equal using an absolute and relative tolerance.
real(kind=dp) elemental function sphere_vol2rad(v)
Convert mass-equivalent volume (m^3) to geometric radius (m) for spherical particles.
String type for building arrays of string of various size.