2023-02-19 02:00:57 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @author Martin Diehl, KU Leuven
|
|
|
|
!> @author Philip Eisenlohr, Michigan State University
|
|
|
|
!> @brief Miscellaneous tools.
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
module misc
|
|
|
|
use prec
|
2023-07-18 05:04:40 +05:30
|
|
|
use constants
|
2023-02-19 02:00:57 +05:30
|
|
|
|
|
|
|
implicit none(type,external)
|
|
|
|
private
|
|
|
|
|
|
|
|
interface misc_optional
|
|
|
|
module procedure misc_optional_bool
|
2023-06-04 10:51:41 +05:30
|
|
|
module procedure misc_optional_int
|
2023-02-19 02:00:57 +05:30
|
|
|
module procedure misc_optional_real
|
2023-06-04 10:47:38 +05:30
|
|
|
module procedure misc_optional_str
|
2023-02-19 02:00:57 +05:30
|
|
|
end interface misc_optional
|
|
|
|
|
|
|
|
public :: &
|
2023-04-14 14:00:03 +05:30
|
|
|
misc_init, &
|
2023-07-31 14:34:58 +05:30
|
|
|
misc_selfTest, &
|
2023-07-18 05:04:40 +05:30
|
|
|
misc_optional, &
|
2023-12-05 04:08:58 +05:30
|
|
|
misc_prefixOptions, &
|
|
|
|
misc_ones, &
|
|
|
|
misc_zeros
|
2023-02-19 02:00:57 +05:30
|
|
|
|
|
|
|
contains
|
|
|
|
|
|
|
|
|
2023-04-14 14:00:03 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief Do self test.
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
subroutine misc_init()
|
|
|
|
|
|
|
|
print'(/,1x,a)', '<<<+- misc init -+>>>'
|
|
|
|
|
|
|
|
call misc_selfTest()
|
|
|
|
|
|
|
|
end subroutine misc_init
|
|
|
|
|
|
|
|
|
2023-02-19 02:00:57 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief Return bool value if given, otherwise default.
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
pure function misc_optional_bool(given,default) result(var)
|
|
|
|
|
|
|
|
logical, intent(in), optional :: given
|
|
|
|
logical, intent(in) :: default
|
|
|
|
logical :: var
|
|
|
|
|
|
|
|
|
|
|
|
if (present(given)) then
|
|
|
|
var = given
|
|
|
|
else
|
|
|
|
var = default
|
|
|
|
end if
|
|
|
|
|
|
|
|
end function misc_optional_bool
|
|
|
|
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief Return integer value if given, otherwise default.
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2023-06-04 10:51:41 +05:30
|
|
|
pure function misc_optional_int(given,default) result(var)
|
2023-02-19 02:00:57 +05:30
|
|
|
|
|
|
|
integer, intent(in), optional :: given
|
|
|
|
integer, intent(in) :: default
|
|
|
|
integer :: var
|
|
|
|
|
|
|
|
|
|
|
|
if (present(given)) then
|
|
|
|
var = given
|
|
|
|
else
|
|
|
|
var = default
|
|
|
|
end if
|
|
|
|
|
2023-06-04 10:51:41 +05:30
|
|
|
end function misc_optional_int
|
2023-02-19 02:00:57 +05:30
|
|
|
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief Return real value if given, otherwise default.
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
pure function misc_optional_real(given,default) result(var)
|
|
|
|
|
2023-06-04 10:52:25 +05:30
|
|
|
real(pREAL), intent(in), optional :: given
|
|
|
|
real(pREAL), intent(in) :: default
|
|
|
|
real(pREAL) :: var
|
2023-02-19 02:00:57 +05:30
|
|
|
|
|
|
|
|
|
|
|
if (present(given)) then
|
|
|
|
var = given
|
|
|
|
else
|
|
|
|
var = default
|
|
|
|
end if
|
|
|
|
|
|
|
|
end function misc_optional_real
|
|
|
|
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief Return string value if given, otherwise default.
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2023-06-04 10:47:38 +05:30
|
|
|
pure function misc_optional_str(given,default) result(var)
|
2023-02-19 02:00:57 +05:30
|
|
|
|
|
|
|
character(len=*), intent(in), optional :: given
|
|
|
|
character(len=*), intent(in) :: default
|
|
|
|
character(len=:), allocatable :: var
|
|
|
|
|
|
|
|
|
|
|
|
if (present(given)) then
|
|
|
|
var = given
|
|
|
|
else
|
|
|
|
var = default
|
|
|
|
end if
|
|
|
|
|
2023-06-04 10:47:38 +05:30
|
|
|
end function misc_optional_str
|
2023-02-19 02:00:57 +05:30
|
|
|
|
2023-07-18 05:04:40 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief Add prefix to options in string.
|
|
|
|
!> @detail An option starts with a dash followed by at least one letter.
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
pure function misc_prefixOptions(string,prefix) result(prefixed)
|
|
|
|
|
|
|
|
character(len=*), intent(in) :: string,prefix
|
|
|
|
character(len=:), allocatable :: prefixed
|
|
|
|
|
|
|
|
integer :: i,N
|
|
|
|
|
|
|
|
|
|
|
|
prefixed = ''
|
|
|
|
N = len(string)
|
|
|
|
do i = 1, N
|
|
|
|
prefixed = prefixed//string(i:i)
|
|
|
|
if (string(i:i) == '-' .and. verify(string(min(i+1,N):min(i+1,N)),LOWER//UPPER) == 0) &
|
|
|
|
prefixed = prefixed//prefix
|
|
|
|
end do
|
|
|
|
|
|
|
|
end function misc_prefixOptions
|
|
|
|
|
2023-04-14 14:00:03 +05:30
|
|
|
|
2023-12-05 04:08:58 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief 1D array of zeros.
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
pure function misc_zeros(N)
|
|
|
|
|
2023-12-05 20:28:06 +05:30
|
|
|
integer, intent(in) :: N !< number of zeros
|
2023-12-05 04:08:58 +05:30
|
|
|
real(pREAL), dimension(N) :: misc_zeros
|
|
|
|
|
|
|
|
|
|
|
|
misc_zeros = 0._pREAL
|
|
|
|
|
|
|
|
end function misc_zeros
|
|
|
|
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief 1D array of ones.
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
pure function misc_ones(N)
|
|
|
|
|
|
|
|
integer, intent(in) :: N !< number of ones
|
|
|
|
real(pREAL), dimension(N) :: misc_ones
|
|
|
|
|
|
|
|
|
|
|
|
misc_ones = 1._pREAL
|
|
|
|
|
|
|
|
end function misc_ones
|
|
|
|
|
|
|
|
|
2023-04-14 14:00:03 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief Check correctness of some misc functions.
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
subroutine misc_selfTest()
|
|
|
|
|
2023-06-04 10:52:25 +05:30
|
|
|
real(pREAL) :: r
|
2023-07-18 05:04:40 +05:30
|
|
|
character(len=:), allocatable :: str,out
|
2023-12-05 04:08:58 +05:30
|
|
|
integer :: N
|
2023-04-14 14:00:03 +05:30
|
|
|
|
|
|
|
call random_number(r)
|
2023-06-04 10:47:38 +05:30
|
|
|
if (test_str('DAMASK') /= 'DAMASK') error stop 'optional_str, present'
|
|
|
|
if (test_str() /= 'default') error stop 'optional_str, not present'
|
|
|
|
if (misc_optional(default='default') /= 'default') error stop 'optional_str, default only'
|
2023-04-14 14:00:03 +05:30
|
|
|
if (test_int(20191102) /= 20191102) error stop 'optional_int, present'
|
|
|
|
if (test_int() /= 42) error stop 'optional_int, not present'
|
|
|
|
if (misc_optional(default=20191102) /= 20191102) error stop 'optional_int, default only'
|
2023-06-03 20:36:32 +05:30
|
|
|
if (dNeq(test_real(r),r)) error stop 'optional_real, present'
|
2023-06-04 10:52:25 +05:30
|
|
|
if (dNeq(test_real(),0.0_pREAL)) error stop 'optional_real, not present'
|
2023-06-03 20:36:32 +05:30
|
|
|
if (dNeq(misc_optional(default=r),r)) error stop 'optional_real, default only'
|
2023-06-04 10:52:25 +05:30
|
|
|
if (test_bool(r<0.5_pREAL) .neqv. r<0.5_pREAL) error stop 'optional_bool, present'
|
2023-04-14 14:00:03 +05:30
|
|
|
if (.not. test_bool()) error stop 'optional_bool, not present'
|
2023-06-04 10:52:25 +05:30
|
|
|
if (misc_optional(default=r>0.5_pREAL) .neqv. r>0.5_pREAL) error stop 'optional_bool, default only'
|
2023-04-14 14:00:03 +05:30
|
|
|
|
2023-07-18 05:04:40 +05:30
|
|
|
str='-a -1 -more 123 -flag -'
|
|
|
|
out=misc_prefixOptions(str,'p_')
|
|
|
|
if (out /= '-p_a -1 -p_more 123 -p_flag -') error stop 'misc_prefixOptions'
|
|
|
|
|
2023-12-05 04:08:58 +05:30
|
|
|
N = int(r*99._pReal)
|
|
|
|
if (size(misc_zeros(N)) /= N) error stop 'shape zeros'
|
|
|
|
if (size(misc_ones(N)) /= N) error stop 'shape ones'
|
|
|
|
if (any(dNeq(misc_zeros(N),0.0_pReal))) error stop 'value zeros'
|
|
|
|
if (any(dNeq(misc_ones(N),1.0_pReal))) error stop 'value ones'
|
|
|
|
|
2023-04-14 14:00:03 +05:30
|
|
|
contains
|
|
|
|
|
|
|
|
function test_str(str_in) result(str_out)
|
|
|
|
|
2023-06-04 10:51:41 +05:30
|
|
|
character(len=:), allocatable :: str_out
|
2023-04-14 14:00:03 +05:30
|
|
|
character(len=*), intent(in), optional :: str_in
|
|
|
|
|
|
|
|
|
2023-06-04 10:47:38 +05:30
|
|
|
str_out = misc_optional_str(str_in,'default')
|
2023-04-14 14:00:03 +05:30
|
|
|
|
|
|
|
end function test_str
|
|
|
|
|
|
|
|
|
|
|
|
function test_int(int_in) result(int_out)
|
|
|
|
|
|
|
|
integer :: int_out
|
|
|
|
integer, intent(in), optional :: int_in
|
|
|
|
|
|
|
|
|
2023-06-04 10:51:41 +05:30
|
|
|
int_out = misc_optional_int(int_in,42)
|
2023-04-14 14:00:03 +05:30
|
|
|
|
|
|
|
end function test_int
|
|
|
|
|
|
|
|
|
|
|
|
function test_real(real_in) result(real_out)
|
|
|
|
|
2023-06-04 10:52:25 +05:30
|
|
|
real(pREAL) :: real_out
|
|
|
|
real(pREAL), intent(in), optional :: real_in
|
2023-04-14 14:00:03 +05:30
|
|
|
|
|
|
|
|
2023-06-04 10:52:25 +05:30
|
|
|
real_out = misc_optional_real(real_in,0.0_pREAL)
|
2023-04-14 14:00:03 +05:30
|
|
|
|
|
|
|
end function test_real
|
|
|
|
|
|
|
|
|
|
|
|
function test_bool(bool_in) result(bool_out)
|
|
|
|
|
|
|
|
logical :: bool_out
|
|
|
|
logical, intent(in), optional :: bool_in
|
|
|
|
|
|
|
|
|
|
|
|
bool_out = misc_optional_bool(bool_in,.true.)
|
|
|
|
|
|
|
|
end function test_bool
|
|
|
|
|
|
|
|
|
|
|
|
end subroutine misc_selfTest
|
|
|
|
|
2023-02-19 02:00:57 +05:30
|
|
|
end module misc
|