2013-02-11 15:14:17 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @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
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2012-03-07 15:37:29 +05:30
|
|
|
module numerics
|
2020-06-17 21:32:22 +05:30
|
|
|
use prec
|
|
|
|
use IO
|
|
|
|
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
|
2009-06-15 18:41:21 +05:30
|
|
|
|
2020-06-17 21:32:22 +05:30
|
|
|
implicit none
|
|
|
|
private
|
|
|
|
|
|
|
|
class(tNode), pointer, public :: &
|
|
|
|
numerics_root
|
|
|
|
integer, protected, public :: &
|
|
|
|
worldrank = 0, & !< MPI worldrank (/=0 for MPI simulations only)
|
|
|
|
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
|
2012-06-15 21:40:21 +05:30
|
|
|
|
2015-05-28 22:32:23 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! field parameters:
|
2020-06-17 21:32:22 +05:30
|
|
|
integer, protected, public :: &
|
|
|
|
itmax = 250, & !< maximum number of iterations
|
|
|
|
itmin = 1 !< minimum number of iterations
|
|
|
|
|
2013-03-28 15:32:11 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! spectral parameters:
|
2019-03-23 13:57:58 +05:30
|
|
|
#ifdef Grid
|
2020-06-17 21:32:22 +05:30
|
|
|
character(len=pStringLen), protected, public :: &
|
|
|
|
petsc_options = ''
|
2012-10-02 20:56:56 +05:30
|
|
|
#endif
|
2011-02-07 20:05:42 +05:30
|
|
|
|
2014-06-06 06:08:29 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2020-04-28 14:05:43 +05:30
|
|
|
! Mesh parameters:
|
|
|
|
#ifdef Mesh
|
2020-06-17 21:32:22 +05:30
|
|
|
character(len=pStringLen), protected, public :: &
|
|
|
|
petsc_options = ''
|
2014-06-06 06:08:29 +05:30
|
|
|
#endif
|
|
|
|
|
2020-06-17 21:32:22 +05:30
|
|
|
public :: numerics_init
|
2020-03-17 02:09:53 +05:30
|
|
|
|
2012-10-02 20:56:56 +05:30
|
|
|
contains
|
2009-11-10 19:06:27 +05:30
|
|
|
|
2013-02-11 15:14:17 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief reads in parameters from numerics.config and sets openMP related parameters. Also does
|
|
|
|
! a sanity check
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2012-03-07 15:37:29 +05:30
|
|
|
subroutine numerics_init
|
2020-06-17 21:32:22 +05:30
|
|
|
|
2012-03-07 15:37:29 +05:30
|
|
|
!$ integer :: gotDAMASK_NUM_THREADS = 1
|
2020-06-17 21:32:22 +05:30
|
|
|
integer :: i, ierr
|
|
|
|
character(len=:), allocatable :: &
|
|
|
|
numerics_input, &
|
|
|
|
numerics_inFlow
|
|
|
|
class (tNode), pointer :: &
|
|
|
|
num_grid
|
|
|
|
logical :: fexist
|
2012-06-12 15:14:05 +05:30
|
|
|
!$ character(len=6) DAMASK_NumThreadsString ! environment variable DAMASK_NUM_THREADS
|
2009-08-27 21:00:40 +05:30
|
|
|
|
2014-10-10 18:38:34 +05:30
|
|
|
#ifdef PETSc
|
2020-06-17 21:32:22 +05:30
|
|
|
call MPI_Comm_rank(PETSC_COMM_WORLD,worldrank,ierr);CHKERRQ(ierr)
|
|
|
|
call MPI_Comm_size(PETSC_COMM_WORLD,worldsize,ierr);CHKERRQ(ierr)
|
2014-10-10 18:38:34 +05:30
|
|
|
#endif
|
2020-06-17 21:32:22 +05:30
|
|
|
write(6,'(/,a)') ' <<<+- numerics init -+>>>'
|
2020-03-17 02:09:53 +05:30
|
|
|
|
2012-01-31 01:46:19 +05:30
|
|
|
!$ call GET_ENVIRONMENT_VARIABLE(NAME='DAMASK_NUM_THREADS',VALUE=DAMASK_NumThreadsString,STATUS=gotDAMASK_NUM_THREADS) ! get environment variable DAMASK_NUM_THREADS...
|
2014-02-28 16:00:07 +05:30
|
|
|
!$ 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')
|
2016-12-23 18:50:29 +05:30
|
|
|
!$ DAMASK_NumThreadsInt = 1_4
|
2014-02-28 16:00:07 +05:30
|
|
|
!$ else
|
|
|
|
!$ read(DAMASK_NumThreadsString,'(i6)') DAMASK_NumThreadsInt ! read as integer
|
2016-12-23 18:50:29 +05:30
|
|
|
!$ if (DAMASK_NumThreadsInt < 1_4) DAMASK_NumThreadsInt = 1_4 ! in case of string conversion fails, set it to one
|
2014-02-28 16:00:07 +05:30
|
|
|
!$ endif
|
|
|
|
!$ call omp_set_num_threads(DAMASK_NumThreadsInt) ! set number of threads for parallel execution
|
2020-03-17 02:09:53 +05:30
|
|
|
|
2020-06-17 21:32:22 +05:30
|
|
|
numerics_root => emptyDict
|
|
|
|
inquire(file='numerics.yaml', exist=fexist)
|
|
|
|
|
|
|
|
fileExists: if (fexist) then
|
|
|
|
write(6,'(a,/)') ' using values from config file'
|
|
|
|
flush(6)
|
|
|
|
numerics_input = IO_read('numerics.yaml')
|
|
|
|
numerics_inFlow = to_flow(numerics_input)
|
|
|
|
numerics_root => parse_flow(numerics_inFlow,defaultVal=emptyDict)
|
2013-02-11 15:14:17 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2020-06-17 21:32:22 +05:30
|
|
|
! grid parameters
|
|
|
|
num_grid => numerics_root%get('grid',defaultVal=emptyDict)
|
|
|
|
itmax = num_grid%get_asInt('itmax',defaultVal=250)
|
|
|
|
itmin = num_grid%get_asInt('itmin',defaultVal=1)
|
2020-06-16 21:23:14 +05:30
|
|
|
#ifdef PETSC
|
2020-06-17 21:32:22 +05:30
|
|
|
petsc_options = num_grid%get_asString('petsc_options',defaultVal = '')
|
2020-06-16 21:23:14 +05:30
|
|
|
#endif
|
2020-06-17 21:32:22 +05:30
|
|
|
else fileExists
|
|
|
|
write(6,'(a,/)') ' using standard values'
|
|
|
|
flush(6)
|
|
|
|
endif fileExists
|
2013-02-11 15:14:17 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! openMP parameter
|
2016-06-29 20:05:49 +05:30
|
|
|
!$ write(6,'(a24,1x,i8,/)') ' number of threads: ',DAMASK_NumThreadsInt
|
2010-10-13 21:34:44 +05:30
|
|
|
|
2013-02-11 15:14:17 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2015-05-28 22:32:23 +05:30
|
|
|
! field parameters
|
2020-06-17 21:32:22 +05:30
|
|
|
write(6,'(a24,1x,i8)') ' itmax: ',itmax
|
|
|
|
write(6,'(a24,1x,i8)') ' itmin: ',itmin
|
2015-05-28 22:32:23 +05:30
|
|
|
|
2014-06-06 06:08:29 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2020-04-01 14:27:53 +05:30
|
|
|
#ifdef PETSC
|
2020-06-17 21:32:22 +05:30
|
|
|
write(6,'(a24,1x,a)') ' PETSc_options: ',trim(petsc_options)
|
2020-04-01 14:27:53 +05:30
|
|
|
#endif
|
|
|
|
|
2013-02-11 15:14:17 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! sanity checks
|
2020-06-17 21:32:22 +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')
|
2012-03-07 15:37:29 +05:30
|
|
|
|
|
|
|
end subroutine numerics_init
|
2009-06-15 18:41:21 +05:30
|
|
|
|
2012-03-07 15:37:29 +05:30
|
|
|
end module numerics
|