DAMASK_EICMD/src/numerics.f90

138 lines
5.7 KiB
Fortran
Raw Normal View History

!--------------------------------------------------------------------------------------------------
!> @author Franz Roters, Max-Planck-Institut für Eisenforschung GmbH
!> @author Philip Eisenlohr, Max-Planck-Institut für Eisenforschung GmbH
!> @brief Managing of parameters related to numerics
!--------------------------------------------------------------------------------------------------
module numerics
2019-05-15 02:42:32 +05:30
use prec
2019-06-11 19:46:10 +05:30
use IO
2020-06-16 21:23:14 +05:30
use YAML_types
use YAML_parse
2019-06-11 19:46:10 +05:30
#ifdef PETSc
#include <petsc/finclude/petscsys.h>
use petscsys
#endif
!$ use OMP_LIB
implicit none
private
2020-06-16 21:23:14 +05:30
class(tNode), pointer, public :: &
numerics_root
2020-06-17 16:54:31 +05:30
integer, protected, public :: &
worldrank = 0, & !< MPI worldrank (/=0 for MPI simulations only)
2020-04-01 14:27:53 +05:30
worldsize = 1 !< MPI worldsize (/=1 for MPI simulations only)
integer(4), protected, public :: &
DAMASK_NumThreadsInt = 0 !< value stored in environment variable DAMASK_NUM_THREADS, set to zero if no OpenMP directive
!--------------------------------------------------------------------------------------------------
! field parameters:
2019-06-11 18:09:51 +05:30
integer, protected, public :: &
itmax = 250, & !< maximum number of iterations
2020-06-17 20:17:13 +05:30
itmin = 1 !< minimum number of iterations
!--------------------------------------------------------------------------------------------------
! spectral parameters:
2019-03-23 13:57:58 +05:30
#ifdef Grid
2020-01-26 16:28:13 +05:30
character(len=pStringLen), protected, public :: &
petsc_options = ''
#endif
!--------------------------------------------------------------------------------------------------
2020-04-28 14:05:43 +05:30
! Mesh parameters:
#ifdef Mesh
character(len=pStringLen), protected, public :: &
petsc_options = ''
#endif
public :: numerics_init
contains
!--------------------------------------------------------------------------------------------------
!> @brief reads in parameters from numerics.config and sets openMP related parameters. Also does
! a sanity check
!--------------------------------------------------------------------------------------------------
subroutine numerics_init
!$ integer :: gotDAMASK_NUM_THREADS = 1
2020-06-17 18:51:51 +05:30
integer :: i, ierr
2020-06-16 21:23:14 +05:30
character(len=:), allocatable :: &
numerics_input, &
numerics_inFlow, &
key
class (tNode), pointer :: &
2020-06-17 20:49:21 +05:30
num_grid
logical :: fexist
2012-06-12 15:14:05 +05:30
!$ character(len=6) DAMASK_NumThreadsString ! environment variable DAMASK_NUM_THREADS
#ifdef PETSc
call MPI_Comm_rank(PETSC_COMM_WORLD,worldrank,ierr);CHKERRQ(ierr)
call MPI_Comm_size(PETSC_COMM_WORLD,worldsize,ierr);CHKERRQ(ierr)
#endif
write(6,'(/,a)') ' <<<+- numerics init -+>>>'
!$ call GET_ENVIRONMENT_VARIABLE(NAME='DAMASK_NUM_THREADS',VALUE=DAMASK_NumThreadsString,STATUS=gotDAMASK_NUM_THREADS) ! get environment variable DAMASK_NUM_THREADS...
!$ if(gotDAMASK_NUM_THREADS /= 0) then ! could not get number of threads, set it to 1
2019-06-11 18:09:51 +05:30
!$ call IO_warning(35,ext_msg='BEGIN:'//DAMASK_NumThreadsString//':END')
!$ DAMASK_NumThreadsInt = 1_4
!$ else
!$ read(DAMASK_NumThreadsString,'(i6)') DAMASK_NumThreadsInt ! read as integer
!$ if (DAMASK_NumThreadsInt < 1_4) DAMASK_NumThreadsInt = 1_4 ! in case of string conversion fails, set it to one
!$ endif
!$ call omp_set_num_threads(DAMASK_NumThreadsInt) ! set number of threads for parallel execution
2020-06-16 22:17:19 +05:30
numerics_root => emptyDict
2020-06-16 21:23:14 +05:30
inquire(file='numerics.yaml', exist=fexist)
fileExists: if (fexist) then
2017-04-25 16:04:14 +05:30
write(6,'(a,/)') ' using values from config file'
flush(6)
2020-06-16 21:23:14 +05:30
numerics_input = IO_read('numerics.yaml')
numerics_inFlow = to_flow(numerics_input)
numerics_root => parse_flow(numerics_inFlow,defaultVal=emptyDict)
!--------------------------------------------------------------------------------------------------
2020-06-16 21:23:14 +05:30
! spectral parameters
num_grid => numerics_root%get('grid',defaultVal=emptyDict)
do i=1,num_grid%length
key = num_grid%getKey(i)
select case(key)
case ('itmax')
itmax = num_grid%get_asInt(key)
case ('itmin')
itmin = num_grid%get_asInt(key)
#ifdef PETSC
case ('petsc_options')
petsc_options = num_grid%get_asString(key)
#endif
endselect
enddo
else fileExists
write(6,'(a,/)') ' using standard values'
flush(6)
endif fileExists
!--------------------------------------------------------------------------------------------------
! openMP parameter
!$ write(6,'(a24,1x,i8,/)') ' number of threads: ',DAMASK_NumThreadsInt
!--------------------------------------------------------------------------------------------------
! field parameters
write(6,'(a24,1x,i8)') ' itmax: ',itmax
write(6,'(a24,1x,i8)') ' itmin: ',itmin
!--------------------------------------------------------------------------------------------------
2020-04-01 14:27:53 +05:30
#ifdef PETSC
write(6,'(a24,1x,a)') ' PETSc_options: ',trim(petsc_options)
#endif
!--------------------------------------------------------------------------------------------------
! sanity checks
2019-06-11 18:09:51 +05:30
if (itmax <= 1) call IO_error(301,ext_msg='itmax')
if (itmin > itmax .or. itmin < 1) call IO_error(301,ext_msg='itmin')
end subroutine numerics_init
end module numerics