2011-04-07 12:50:28 +05:30
! Copyright 2011 Max-Planck-Institut für Eisenforschung GmbH
2011-04-04 19:39:54 +05:30
!
! This file is part of DAMASK,
2012-08-28 21:38:17 +05:30
! the Düsseldorf Advanced Material Simulation Kit.
2011-04-04 19:39:54 +05:30
!
! DAMASK is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! DAMASK is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with DAMASK. If not, see <http://www.gnu.org/licenses/>.
!
2012-08-09 16:31:53 +05:30
!--------------------------------------------------------------------------------------------------
! $Id$
!--------------------------------------------------------------------------------------------------
!> @author Franz Roters, Max-Planck-Institut für Eisenforschung GmbH
!> @author Philip Eisenlohr, Max-Planck-Institut für Eisenforschung GmbH
!> @author Christoph Kords, Max-Planck-Institut für Eisenforschung GmbH
!> @author Martin Diehl, Max-Planck-Institut für Eisenforschung GmbH
2012-08-28 21:38:17 +05:30
!> @brief setting precision for real and int type depending on makros "FLOAT" and "INT"
2012-08-09 16:31:53 +05:30
!--------------------------------------------------------------------------------------------------
2012-04-28 16:16:41 +05:30
2012-03-06 20:22:48 +05:30
module prec
2012-08-09 16:31:53 +05:30
2012-03-06 20:22:48 +05:30
implicit none
private
2012-08-09 16:31:53 +05:30
2012-08-28 21:38:17 +05:30
#if (FLOAT==4)
2012-08-31 01:56:28 +05:30
#ifdef Spectral
SPECTRAL SOLVER DOES NOT SUPPORT SINGLE PRECISION , STOPING COMPILATION
#endif
2012-08-28 21:38:17 +05:30
integer , parameter , public :: pReal = 4 !< floating point single precition (was selected_real_kind(6,37), number with 6 significant digits, up to 1e+-37)
2012-10-02 22:23:03 +05:30
#ifdef __INTEL_COMPILER
2012-08-28 21:38:17 +05:30
real ( pReal ) , parameter , public :: DAMASK_NaN = Z '7F800001' !< quiet NaN for single precision (from http://www.hpc.unimelb.edu.au/doc/f90lrm/dfum_035.html, copy can be found in documentation/Code/Fortran)
2012-10-02 22:23:03 +05:30
#endif
#ifdef __GFORTRAN__
2012-08-28 21:38:17 +05:30
real ( pReal ) , parameter , public :: DAMASK_NaN = real ( Z '7F800001' , pReal ) !< quiet NaN for single precision (from http://www.hpc.unimelb.edu.au/doc/f90lrm/dfum_035.html, copy can be found in documentation/Code/Fortran)
#endif
#elif (FLOAT==8)
2012-08-29 00:40:54 +05:30
integer , parameter , public :: pReal = 8 !< floating point double precision (was selected_real_kind(15,300), number with 15 significant digits, up to 1e+-300)
2012-10-02 22:23:03 +05:30
#ifdef __INTEL_COMPILER
2012-08-28 21:38:17 +05:30
real ( pReal ) , parameter , public :: DAMASK_NaN = Z '7FF8000000000000' !< quiet NaN for double precision (from http://www.hpc.unimelb.edu.au/doc/f90lrm/dfum_035.html, copy can be found in documentation/Code/Fortran)
2012-10-02 22:23:03 +05:30
#endif
#ifdef __GFORTRAN__
2012-08-28 21:38:17 +05:30
real ( pReal ) , parameter , public :: DAMASK_NaN = real ( Z '7FF8000000000000' , pReal ) !< quiet NaN for double precision (from http://www.hpc.unimelb.edu.au/doc/f90lrm/dfum_035.html, copy can be found in documentation/Code/Fortran)
#endif
2012-08-31 01:56:28 +05:30
#else
NO SUITABLE PRECISION SELECTED , STOPING COMPILATION
2012-02-13 19:38:07 +05:30
#endif
2007-03-20 19:25:22 +05:30
2012-08-28 21:38:17 +05:30
#if (INT==4)
integer , parameter , public :: pInt = 4 !< integer representation 32 bit (was selected_int_kind(9), number with at least up to +- 1e9)
#elif (INT==8)
integer , parameter , public :: pInt = 8 !< integer representation 64 bit (was selected_int_kind(12), number with at least up to +- 1e12)
2012-08-31 01:56:28 +05:30
#else
NO SUITABLE PRECISION SELECTED , STOPING COMPILATION
2012-08-28 21:38:17 +05:30
#endif
integer , parameter , public :: pLongInt = 8 !< integer representation 64 bit (was selected_int_kind(12), number with at least up to +- 1e12)
real ( pReal ) , parameter , public :: tol_math_check = 1.0e-8_pReal
real ( pReal ) , parameter , public :: tol_gravityNodePos = 1.0e-100_pReal
2012-03-06 20:22:48 +05:30
type , public :: p_vec
real ( pReal ) , dimension ( : ) , pointer :: p
end type p_vec
2009-08-31 20:39:15 +05:30
2012-03-06 20:22:48 +05:30
public :: prec_init
contains
2012-08-28 21:38:17 +05:30
2012-08-09 16:31:53 +05:30
!--------------------------------------------------------------------------------------------------
!> @brief reporting precision and checking if DAMASK_NaN is set correctly
!--------------------------------------------------------------------------------------------------
2012-03-06 20:22:48 +05:30
subroutine prec_init
2012-08-09 16:31:53 +05:30
use , intrinsic :: iso_fortran_env ! to get compiler_version and compiler_options (at least for gfortran 4.6 at the moment)
2012-03-06 20:22:48 +05:30
implicit none
2012-03-20 17:56:21 +05:30
openmp parallelization working again (at least for j2 and nonlocal constitutive model).
In order to keep it like that, please follow these simple rules:
DON'T use implicit array subscripts:
example: real, dimension(3,3) :: A,B
A(:,2) = B(:,1) <--- DON'T USE
A(1:3,2) = B(1:3,1) <--- BETTER USE
In many cases the use of explicit array subscripts is inevitable for parallelization. Additionally, it is an easy means to prevent memory leaks.
Enclose all write statements with the following:
!$OMP CRITICAL (write2out)
<your write statement>
!$OMP END CRITICAL (write2out)
Whenever you change something in the code and are not sure if it affects parallelization and leads to nonconforming behavior, please ask me and/or Franz to check this.
2011-03-17 16:16:17 +05:30
!$OMP CRITICAL (write2out)
2012-04-28 16:16:41 +05:30
2012-03-06 20:22:48 +05:30
write ( 6 , * )
write ( 6 , * ) '<<<+- prec init -+>>>'
write ( 6 , * ) '$Id$'
2012-02-01 00:48:55 +05:30
#include "compilation_info.f90"
2012-03-06 20:22:48 +05:30
write ( 6 , '(a,i3)' ) ' Bytes for pReal: ' , pReal
write ( 6 , '(a,i3)' ) ' Bytes for pInt: ' , pInt
write ( 6 , '(a,i3)' ) ' Bytes for pLongInt: ' , pLongInt
2012-05-11 18:16:17 +05:30
write ( 6 , '(a,e10.3)' ) ' NaN: ' , DAMASK_NaN
2012-03-06 20:22:48 +05:30
write ( 6 , '(a,l3)' ) ' NaN /= NaN: ' , DAMASK_NaN / = DAMASK_NaN
2012-08-28 21:38:17 +05:30
if ( DAMASK_NaN == DAMASK_NaN ) call quit ( 9000 )
2012-10-02 22:23:03 +05:30
#ifdef Spectral
open ( 6 , encoding = 'UTF-8' ) ! modern fortran compilers (gfortran >4.4, ifort >11 support it)
write ( 6 , * ) 'using UTF-8 coded output'
#endif
write ( 6 , * )
openmp parallelization working again (at least for j2 and nonlocal constitutive model).
In order to keep it like that, please follow these simple rules:
DON'T use implicit array subscripts:
example: real, dimension(3,3) :: A,B
A(:,2) = B(:,1) <--- DON'T USE
A(1:3,2) = B(1:3,1) <--- BETTER USE
In many cases the use of explicit array subscripts is inevitable for parallelization. Additionally, it is an easy means to prevent memory leaks.
Enclose all write statements with the following:
!$OMP CRITICAL (write2out)
<your write statement>
!$OMP END CRITICAL (write2out)
Whenever you change something in the code and are not sure if it affects parallelization and leads to nonconforming behavior, please ask me and/or Franz to check this.
2011-03-17 16:16:17 +05:30
!$OMP END CRITICAL (write2out)
2009-08-31 20:39:15 +05:30
2012-03-06 20:22:48 +05:30
end subroutine prec_init
2009-08-31 20:39:15 +05:30
2012-03-06 20:22:48 +05:30
end module prec