small polishing, exchanged stops in math.f90 with calls to IO_error

This commit is contained in:
Martin Diehl 2012-02-13 14:08:07 +00:00
parent a6864bf599
commit f03e7c459c
6 changed files with 48 additions and 45 deletions

View File

@ -1348,6 +1348,10 @@ endfunction
case (800_pInt)
msg = 'matrix inversion error'
case (801_pInt)
msg = 'I_TO_HALTON-error: An input base BASE is <= 1'
case (802_pInt)
msg = 'Prime-error: N must be between 0 and PRIME_MAX'
! Error messages related to parsing of Abaqus input file
case (900_pInt)

View File

@ -65,7 +65,7 @@ CONTAINS
!********************************************************************
subroutine debug_init()
use, intrinsic :: iso_fortran_env
use, intrinsic :: iso_fortran_env ! to get compiler_version and compiler_options (at least for gfortran 4.6 at the moment)
use prec, only: pInt
use numerics, only: nStress, &
nState, &

View File

@ -140,6 +140,7 @@ real(pReal), dimension(4,36), parameter :: math_symOperations = &
!**************************************************************************
SUBROUTINE math_init ()
use, intrinsic :: iso_fortran_env ! to get compiler_version and compiler_options (at least for gfortran 4.6 at the moment)
use prec, only: tol_math_check
use numerics, only: fixedSeed
use IO, only: IO_error
@ -491,11 +492,8 @@ real(pReal), dimension(4,36), parameter :: math_symOperations = &
real(pReal), dimension(3,3), intent(in) :: B
real(pReal), dimension(3,3) :: math_mul3333xx33
do i = 1_pInt,3_pInt
do j = 1_pInt,3_pInt
forall(i = 1_pInt:3_pInt,j = 1_pInt:3_pInt)&
math_mul3333xx33(i,j) = sum(A(i,j,1:3,1:3)*B(1:3,1:3))
enddo; enddo
endfunction math_mul3333xx33
@ -2555,18 +2553,7 @@ end subroutine
r(1:ndim) = 0.0_pReal
if (any (base(1:ndim) <= 1_pInt)) then
!$OMP CRITICAL (write2out)
write (*, '(a)') ' '
write (*, '(a)') 'I_TO_HALTON - Fatal error!'
write (*, '(a)') ' An input base BASE is <= 1!'
do i = 1, ndim
write (*, '(i6,i6)') i, base(i)
enddo
call flush(6)
!$OMP END CRITICAL (write2out)
stop
end if
if (any (base(1:ndim) <= 1_pInt)) call IO_error(error_ID=801_pInt)
base_inv(1:ndim) = 1.0_pReal / real (base(1:ndim), pReal)
@ -2807,16 +2794,8 @@ end subroutine
prime = 1_pInt
else if (n <= prime_max) then
prime = npvec(n)
else ! why not use io_error here?
prime = 0_pInt
!$OMP CRITICAL (write2out)
write (6, '(a)') ' '
write (6, '(a)') 'PRIME - Fatal error!'
write (6, '(a,i6)') ' Illegal prime index N = ', n
write (6, '(a,i6)') ' N must be between 0 and PRIME_MAX = ', prime_max
call flush(6)
!$OMP END CRITICAL (write2out)
stop
else
call IO_error(error_ID=802_pInt)
end if
endfunction prime

View File

@ -92,7 +92,7 @@ CONTAINS
!*******************************************
subroutine numerics_init()
use, intrinsic :: iso_fortran_env
use, intrinsic :: iso_fortran_env ! to get compiler_version and compiler_options (at least for gfortran 4.6 at the moment)
!*** variables and functions from other modules ***!
use prec, only: pInt, &
pReal

View File

@ -21,27 +21,36 @@
!##############################################################
MODULE prec
!##############################################################
use iso_fortran_env ! to get compiler_version and compiler_options (at least for gfortran 4.6 at the moment)
implicit none
! *** Precision of real and integer variables ***
integer, parameter :: pReal = selected_real_kind(15,300) ! 15 significant digits, up to 1e+-300
integer, parameter :: pInt = selected_int_kind(9) ! up to +- 1e9
integer, parameter :: pLongInt = 8 ! should be 64bit
real(pReal), parameter :: tol_math_check = 1.0e-8_pReal
real(pReal), parameter :: tol_gravityNodePos = 1.0e-100_pReal
integer, parameter, public :: pReal = selected_real_kind(15,300) ! 15 significant digits, up to 1e+-300
integer, parameter, public :: pInt = selected_int_kind(9) ! up to +- 1e9
integer, parameter, public :: pLongInt = 8 ! should be 64bit
real(pReal), parameter, public :: tol_math_check = 1.0e-8_pReal
real(pReal), parameter, public :: tol_gravityNodePos = 1.0e-100_pReal
! NaN is precision dependent
! from http://www.hpc.unimelb.edu.au/doc/f90lrm/dfum_035.html
! copy can be found in documentation/Code/Fortran
real(pReal), parameter :: DAMASK_NaN = real(Z'7FF0000000000001', pReal)
#ifdef __INTEL_COMPILER
#if __INTEL_COMPILER<12000
real(pReal), parameter, public :: DAMASK_NaN = Z'7FF0000000000001'
#else
real(pReal), parameter, public :: DAMASK_NaN = real(Z'7FF0000000000001', pReal)
#endif
#else
real(pReal), parameter, public :: DAMASK_NaN = real(Z'7FF0000000000001', pReal)
#endif
type :: p_vec
real(pReal), dimension(:), pointer :: p
real(pReal), dimension(:), pointer, public :: p
end type p_vec
CONTAINS
subroutine prec_init
use, intrinsic :: iso_fortran_env ! to get compiler_version and compiler_options (at least for gfortran 4.6 at the moment)
implicit none
!$OMP CRITICAL (write2out)
@ -54,6 +63,7 @@ implicit none
write(6,'(a,i3)') ' Bytes for pLongInt: ',pLongInt
write(6,'(a,e3.3)') ' NaN: ',DAMASK_NAN
write(6,'(a,l3)') ' NaN /= NaN: ',DAMASK_NaN/=DAMASK_NaN
if (DAMASK_NaN == DAMASK_NaN) call quit(9000)
write(6,*)
!$OMP END CRITICAL (write2out)

View File

@ -21,27 +21,36 @@
!##############################################################
MODULE prec
!##############################################################
use iso_fortran_env ! to get compiler_version and compiler_options (at least for gfortran 4.6 at the moment)
implicit none
! *** Precision of real and integer variables ***
integer, parameter :: pReal = selected_real_kind(6,37) ! 6 significant digits, up to 1e+-37
integer, parameter :: pInt = selected_int_kind(9) ! up to +- 1e9
integer, parameter :: pLongInt = 4 ! should be 64bit
real(pReal), parameter :: tol_math_check = 1.0e-5_pReal
real(pReal), parameter :: tol_gravityNodePos = 1.0e-36_pReal
integer, parameter, public :: :: pReal = selected_real_kind(6,37) ! 6 significant digits, up to 1e+-37
integer, parameter, public :: :: pInt = selected_int_kind(9) ! up to +- 1e9
integer, parameter, public :: :: pLongInt = 4 ! should be 64bit
real(pReal), parameter, public :: :: tol_math_check = 1.0e-5_pReal
real(pReal), parameter, public :: :: tol_gravityNodePos = 1.0e-36_pReal
! NaN is precision dependent
! from http://www.hpc.unimelb.edu.au/doc/f90lrm/dfum_035.html
! copy can be found in documentation/Code/Fortran
real(pReal), parameter :: DAMASK_NaN = real(Z'7F800001', pReal)
#ifdef __INTEL_COMPILER
#if __INTEL_COMPILER<12000
real(pReal), parameter, public :: DAMASK_NaN = Z'Z'7F800001', pReal'
#else
real(pReal), parameter, public :: DAMASK_NaN = real(Z'7F800001', pReal)
#endif
#else
real(pReal), parameter, public :: DAMASK_NaN = real(Z'7F800001', pReal)
#endif
type :: p_vec
real(pReal), dimension(:), pointer :: p
real(pReal), dimension(:), pointer, public :: p
end type p_vec
CONTAINS
subroutine prec_init
use, intrinsic :: iso_fortran_env ! to get compiler_version and compiler_options (at least for gfortran 4.6 at the moment)
implicit none
!$OMP CRITICAL (write2out)
@ -54,6 +63,7 @@ implicit none
write(6,'(a,i3)') ' Bytes for pLongInt: ',pLongInt
write(6,'(a,e3.3)') ' NaN: ',DAMASK_NAN
write(6,'(a,l3)') ' NaN /= NaN: ',DAMASK_NaN/=DAMASK_NaN
if (DAMASK_NaN == DAMASK_NaN) call quit(9000)
write(6,*)
!$OMP END CRITICAL (write2out)