further removal of public variables

This commit is contained in:
Sharan Roongta 2020-06-17 13:24:31 +02:00
parent f234f8cd25
commit 45f1e3a986
4 changed files with 18 additions and 22 deletions

@ -1 +1 @@
Subproject commit e01b61982a1eee58ba024a4760b05ba82d2c0edc Subproject commit a22650393972eeaf4fa20bb5a5fe69f853c211fa

View File

@ -125,12 +125,19 @@ subroutine CPFEM_general(mode, ffn, ffn1, temperature_inp, dt, elFE, ip, cauchyS
H H
integer(pInt) elCP, & ! crystal plasticity element number integer(pInt) elCP, & ! crystal plasticity element number
i, j, k, l, m, n, ph, homog, mySource i, j, k, l, m, n, ph, homog, mySource, &
iJacoStiffness
logical updateJaco ! flag indicating if Jacobian has to be updated logical updateJaco ! flag indicating if Jacobian has to be updated
real(pReal), parameter :: ODD_STRESS = 1e15_pReal, & !< return value for stress if terminallyIll real(pReal), parameter :: ODD_STRESS = 1e15_pReal, & !< return value for stress if terminallyIll
ODD_JACOBIAN = 1e50_pReal !< return value for jacobian if terminallyIll ODD_JACOBIAN = 1e50_pReal !< return value for jacobian if terminallyIll
class(tNode), pointer :: &
num_commercialFEM
num_commercialFEM => numerics_root%get('commercialFEM',defaultVal=emptyDict)
iJacoStiffness = num_commercialFEM%get_asInt('ijacostiffness',defaultVal=1)
elCP = mesh_FEM2DAMASK_elem(elFE) elCP = mesh_FEM2DAMASK_elem(elFE)
if (iand(debug_level(debug_CPFEM), debug_levelBasic) /= 0_pInt & if (iand(debug_level(debug_CPFEM), debug_levelBasic) /= 0_pInt &

View File

@ -9,6 +9,7 @@ module math
use prec use prec
use IO use IO
use numerics use numerics
use YAML_types
use LAPACK_interface use LAPACK_interface
implicit none implicit none
@ -89,11 +90,16 @@ contains
subroutine math_init subroutine math_init
real(pReal), dimension(4) :: randTest real(pReal), dimension(4) :: randTest
integer :: randSize integer :: randSize,randomSeed
integer, dimension(:), allocatable :: randInit integer, dimension(:), allocatable :: randInit
class(tNode), pointer :: &
num_generic
write(6,'(/,a)') ' <<<+- math init -+>>>'; flush(6) write(6,'(/,a)') ' <<<+- math init -+>>>'; flush(6)
num_generic => numerics_root%get('generic',defaultVal=emptyDict)
randomSeed = num_generic%get_asInt('random_seed', defaultVal = 0)
call random_seed(size=randSize) call random_seed(size=randSize)
allocate(randInit(randSize)) allocate(randInit(randSize))
if (randomSeed > 0) then if (randomSeed > 0) then

View File

@ -21,8 +21,6 @@ module numerics
class(tNode), pointer, public :: & class(tNode), pointer, public :: &
numerics_root numerics_root
integer, protected, public :: & integer, protected, public :: &
iJacoStiffness = 1, & !< frequency of stiffness update
randomSeed = 0, & !< fixed seeding for pseudo-random number generator, Default 0: use random seed
worldrank = 0, & !< MPI worldrank (/=0 for MPI simulations only) worldrank = 0, & !< MPI worldrank (/=0 for MPI simulations only)
worldsize = 1 !< MPI worldsize (/=1 for MPI simulations only) worldsize = 1 !< MPI worldsize (/=1 for MPI simulations only)
integer(4), protected, public :: & integer(4), protected, public :: &
@ -129,16 +127,9 @@ subroutine numerics_init
select case(key) select case(key)
case ('defgradtolerance') case ('defgradtolerance')
defgradTolerance = num_generic%get_asFloat(key) defgradTolerance = num_generic%get_asFloat(key)
case ('ijacostiffness')
iJacoStiffness = num_generic%get_asInt(key)
case ('unitlength') case ('unitlength')
numerics_unitlength = num_generic%get_asFloat(key) numerics_unitlength = num_generic%get_asFloat(key)
!--------------------------------------------------------------------------------------------------
! random seeding parameter
case ('fixed_seed', 'random_seed')
randomSeed = num_generic%get_asInt(key)
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
! gradient parameter ! gradient parameter
case ('charLength') case ('charLength')
@ -156,15 +147,8 @@ subroutine numerics_init
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
! writing parameters to output ! writing parameters to output
write(6,'(a24,1x,es8.1)') ' defgradTolerance: ',defgradTolerance write(6,'(a24,1x,es8.1)') ' defgradTolerance: ',defgradTolerance
write(6,'(a24,1x,i8)') ' iJacoStiffness: ',iJacoStiffness
write(6,'(a24,1x,es8.1,/)')' unitlength: ',numerics_unitlength write(6,'(a24,1x,es8.1,/)')' unitlength: ',numerics_unitlength
!--------------------------------------------------------------------------------------------------
! Random seeding parameter
write(6,'(a16,1x,i16,/)') ' random_seed: ',randomSeed
if (randomSeed <= 0) &
write(6,'(a,/)') ' random seed will be generated!'
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
! gradient parameter ! gradient parameter
write(6,'(a24,1x,es8.1)') ' charLength: ',charLength write(6,'(a24,1x,es8.1)') ' charLength: ',charLength
@ -189,7 +173,6 @@ subroutine numerics_init
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
! sanity checks ! sanity checks
if (defgradTolerance <= 0.0_pReal) call IO_error(301,ext_msg='defgradTolerance') if (defgradTolerance <= 0.0_pReal) call IO_error(301,ext_msg='defgradTolerance')
if (iJacoStiffness < 1) call IO_error(301,ext_msg='iJacoStiffness')
if (numerics_unitlength <= 0.0_pReal) call IO_error(301,ext_msg='unitlength') if (numerics_unitlength <= 0.0_pReal) call IO_error(301,ext_msg='unitlength')
if (residualStiffness < 0.0_pReal) call IO_error(301,ext_msg='residualStiffness') if (residualStiffness < 0.0_pReal) call IO_error(301,ext_msg='residualStiffness')
if (itmax <= 1) call IO_error(301,ext_msg='itmax') if (itmax <= 1) call IO_error(301,ext_msg='itmax')