self consistent solutions
This commit is contained in:
parent
bbb2441cc2
commit
285dab4451
|
@ -1411,7 +1411,6 @@ subroutine unitTest
|
||||||
real(pReal), dimension(9,9) :: t99,t99_2
|
real(pReal), dimension(9,9) :: t99,t99_2
|
||||||
logical :: e
|
logical :: e
|
||||||
|
|
||||||
integer :: i
|
|
||||||
if (any(abs([1.0_pReal,2.0_pReal,2.0_pReal,3.0_pReal,3.0_pReal,3.0_pReal] - &
|
if (any(abs([1.0_pReal,2.0_pReal,2.0_pReal,3.0_pReal,3.0_pReal,3.0_pReal] - &
|
||||||
math_expand([1.0_pReal,2.0_pReal,3.0_pReal],[1,2,3,0])) > tol_math_check)) &
|
math_expand([1.0_pReal,2.0_pReal,3.0_pReal],[1,2,3,0])) > tol_math_check)) &
|
||||||
call IO_error(401,ext_msg='math_expand [1,2,3] by [1,2,3,0] => [1,2,2,3,3,3]')
|
call IO_error(401,ext_msg='math_expand [1,2,3] by [1,2,3,0] => [1,2,2,3,3,3]')
|
||||||
|
|
62
src/prec.f90
62
src/prec.f90
|
@ -10,6 +10,7 @@ module prec
|
||||||
use, intrinsic :: IEEE_arithmetic
|
use, intrinsic :: IEEE_arithmetic
|
||||||
|
|
||||||
implicit none
|
implicit none
|
||||||
|
public
|
||||||
! https://software.intel.com/en-us/blogs/2017/03/27/doctor-fortran-in-it-takes-all-kinds
|
! https://software.intel.com/en-us/blogs/2017/03/27/doctor-fortran-in-it-takes-all-kinds
|
||||||
#ifdef Abaqus
|
#ifdef Abaqus
|
||||||
integer, parameter, public :: pReal = selected_real_kind(15,307) !< number with 15 significant digits, up to 1e+-307 (typically 64 bit)
|
integer, parameter, public :: pReal = selected_real_kind(15,307) !< number with 15 significant digits, up to 1e+-307 (typically 64 bit)
|
||||||
|
@ -83,14 +84,8 @@ module prec
|
||||||
real(pReal), private, parameter :: PREAL_EPSILON = epsilon(0.0_pReal) !< minimum positive number such that 1.0 + EPSILON /= 1.0.
|
real(pReal), private, parameter :: PREAL_EPSILON = epsilon(0.0_pReal) !< minimum positive number such that 1.0 + EPSILON /= 1.0.
|
||||||
real(pReal), private, parameter :: PREAL_MIN = tiny(0.0_pReal) !< smallest normalized floating point number
|
real(pReal), private, parameter :: PREAL_MIN = tiny(0.0_pReal) !< smallest normalized floating point number
|
||||||
|
|
||||||
public :: &
|
private :: &
|
||||||
prec_init, &
|
unitTest
|
||||||
dEq, &
|
|
||||||
dEq0, &
|
|
||||||
cEq, &
|
|
||||||
dNeq, &
|
|
||||||
dNeq0, &
|
|
||||||
cNeq
|
|
||||||
|
|
||||||
contains
|
contains
|
||||||
|
|
||||||
|
@ -100,11 +95,6 @@ contains
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
subroutine prec_init
|
subroutine prec_init
|
||||||
|
|
||||||
integer, allocatable, dimension(:) :: realloc_lhs_test
|
|
||||||
|
|
||||||
external :: &
|
|
||||||
quit
|
|
||||||
|
|
||||||
write(6,'(/,a)') ' <<<+- prec init -+>>>'
|
write(6,'(/,a)') ' <<<+- prec init -+>>>'
|
||||||
|
|
||||||
write(6,'(a,i3)') ' Size of integer in bit: ',bit_size(0)
|
write(6,'(a,i3)') ' Size of integer in bit: ',bit_size(0)
|
||||||
|
@ -114,8 +104,7 @@ subroutine prec_init
|
||||||
write(6,'(a,e10.3)') ' Minimum value: ',tiny(0.0_pReal)
|
write(6,'(a,e10.3)') ' Minimum value: ',tiny(0.0_pReal)
|
||||||
write(6,'(a,i3)') ' Decimal precision: ',precision(0.0_pReal)
|
write(6,'(a,i3)') ' Decimal precision: ',precision(0.0_pReal)
|
||||||
|
|
||||||
realloc_lhs_test = [1,2]
|
call unitTest
|
||||||
if (realloc_lhs_test(2)/=2) call quit(9000)
|
|
||||||
|
|
||||||
end subroutine prec_init
|
end subroutine prec_init
|
||||||
|
|
||||||
|
@ -153,16 +142,13 @@ logical elemental pure function dNeq(a,b,tol)
|
||||||
|
|
||||||
real(pReal), intent(in) :: a,b
|
real(pReal), intent(in) :: a,b
|
||||||
real(pReal), intent(in), optional :: tol
|
real(pReal), intent(in), optional :: tol
|
||||||
real(pReal) :: eps
|
|
||||||
|
|
||||||
if (present(tol)) then
|
if (present(tol)) then
|
||||||
eps = tol
|
dNeq = .not. dEq(a,b,tol)
|
||||||
else
|
else
|
||||||
eps = PREAL_EPSILON * maxval(abs([a,b]))
|
dNeq = .not. dEq(a,b)
|
||||||
endif
|
endif
|
||||||
|
|
||||||
dNeq = merge(.False.,.True.,abs(a-b) <= eps)
|
|
||||||
|
|
||||||
end function dNeq
|
end function dNeq
|
||||||
|
|
||||||
|
|
||||||
|
@ -199,16 +185,13 @@ logical elemental pure function dNeq0(a,tol)
|
||||||
|
|
||||||
real(pReal), intent(in) :: a
|
real(pReal), intent(in) :: a
|
||||||
real(pReal), intent(in), optional :: tol
|
real(pReal), intent(in), optional :: tol
|
||||||
real(pReal) :: eps
|
|
||||||
|
|
||||||
if (present(tol)) then
|
if (present(tol)) then
|
||||||
eps = tol
|
dNeq0 = .not. dEq0(a,tol)
|
||||||
else
|
else
|
||||||
eps = PREAL_MIN * 10.0_pReal
|
dNeq0 = .not. dEq0(a)
|
||||||
endif
|
endif
|
||||||
|
|
||||||
dNeq0 = merge(.False.,.True.,abs(a) <= eps)
|
|
||||||
|
|
||||||
end function dNeq0
|
end function dNeq0
|
||||||
|
|
||||||
|
|
||||||
|
@ -247,16 +230,35 @@ logical elemental pure function cNeq(a,b,tol)
|
||||||
|
|
||||||
complex(pReal), intent(in) :: a,b
|
complex(pReal), intent(in) :: a,b
|
||||||
real(pReal), intent(in), optional :: tol
|
real(pReal), intent(in), optional :: tol
|
||||||
real(pReal) :: eps
|
|
||||||
|
|
||||||
if (present(tol)) then
|
if (present(tol)) then
|
||||||
eps = tol
|
cNeq = .not. cEq(a,b,tol)
|
||||||
else
|
else
|
||||||
eps = PREAL_EPSILON * maxval(abs([a,b]))
|
cNeq = .not. cEq(a,b)
|
||||||
endif
|
endif
|
||||||
|
|
||||||
cNeq = merge(.False.,.True.,abs(a-b) <= eps)
|
|
||||||
|
|
||||||
end function cNeq
|
end function cNeq
|
||||||
|
|
||||||
|
|
||||||
|
!--------------------------------------------------------------------------------------------------
|
||||||
|
!> @brief check correctness of (some) prec functions
|
||||||
|
!--------------------------------------------------------------------------------------------------
|
||||||
|
subroutine unitTest
|
||||||
|
|
||||||
|
integer, allocatable, dimension(:) :: realloc_lhs_test
|
||||||
|
real(pReal), dimension(2) :: r
|
||||||
|
external :: &
|
||||||
|
quit
|
||||||
|
|
||||||
|
call random_number(r)
|
||||||
|
r = r/minval(r)
|
||||||
|
if(.not. all(dEq(r,r+PREAL_EPSILON))) call quit(9000)
|
||||||
|
if(dEq(r(1),r(2)) .and. dNeq(r(1),r(2))) call quit(9000)
|
||||||
|
if(.not. all(dEq0(r-r+PREAL_MIN))) call quit(9000)
|
||||||
|
|
||||||
|
realloc_lhs_test = [1,2]
|
||||||
|
if (any(realloc_lhs_test/=[1,2])) call quit(9000)
|
||||||
|
|
||||||
|
end subroutine unitTest
|
||||||
|
|
||||||
end module prec
|
end module prec
|
||||||
|
|
Loading…
Reference in New Issue