'num' structure for data to avoid multiple reading of parameters

This commit is contained in:
Sharan Roongta 2020-06-24 16:31:45 +02:00
parent fdf7887b47
commit 692fc98fd5
5 changed files with 79 additions and 43 deletions

View File

@ -5,7 +5,6 @@
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
module CPFEM module CPFEM
use prec use prec
use numerics
use debug use debug
use FEsolving use FEsolving
use math use math
@ -45,6 +44,13 @@ module CPFEM
CPFEM_BACKUPJACOBIAN = 2_pInt**2_pInt, & CPFEM_BACKUPJACOBIAN = 2_pInt**2_pInt, &
CPFEM_RESTOREJACOBIAN = 2_pInt**3_pInt CPFEM_RESTOREJACOBIAN = 2_pInt**3_pInt
type, private :: tNumerics
integer :: &
iJacoStiffness !< frequency of stiffness update
end type tNumerics
type(tNumerics), private :: num
public :: & public :: &
CPFEM_general, & CPFEM_general, &
CPFEM_initAll, & CPFEM_initAll, &
@ -86,6 +92,9 @@ end subroutine CPFEM_initAll
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
subroutine CPFEM_init subroutine CPFEM_init
class(tNode), pointer :: &
num_commercialFEM
write(6,'(/,a)') ' <<<+- CPFEM init -+>>>' write(6,'(/,a)') ' <<<+- CPFEM init -+>>>'
flush(6) flush(6)
@ -93,6 +102,13 @@ subroutine CPFEM_init
allocate(CPFEM_dcsdE( 6,6,discretization_nIP,discretization_nElem), source= 0.0_pReal) allocate(CPFEM_dcsdE( 6,6,discretization_nIP,discretization_nElem), source= 0.0_pReal)
allocate(CPFEM_dcsdE_knownGood(6,6,discretization_nIP,discretization_nElem), source= 0.0_pReal) allocate(CPFEM_dcsdE_knownGood(6,6,discretization_nIP,discretization_nElem), source= 0.0_pReal)
!------------------------------------------------------------------------------
! read numerical parameters and do sanity check
num_commercialFEM => numerics_root%get('commercialFEM',defaultVal=emptyDict)
num%iJacoStiffness = num_commercialFEM%get_asInt('ijacostiffness',defaultVal=1)
if (num%iJacoStiffness < 1) call IO_error(301,ext_msg='iJacoStiffness')
!------------------------------------------------------------------------------
if (iand(debug_level(debug_CPFEM), debug_levelBasic) /= 0) then if (iand(debug_level(debug_CPFEM), debug_levelBasic) /= 0) then
write(6,'(a32,1x,6(i8,1x))') 'CPFEM_cs: ', shape(CPFEM_cs) write(6,'(a32,1x,6(i8,1x))') 'CPFEM_cs: ', shape(CPFEM_cs)
write(6,'(a32,1x,6(i8,1x))') 'CPFEM_dcsdE: ', shape(CPFEM_dcsdE) write(6,'(a32,1x,6(i8,1x))') 'CPFEM_dcsdE: ', shape(CPFEM_dcsdE)
@ -125,21 +141,12 @@ 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 !< frequency of stiffness update
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
!------------------------------------------------------------------------------
! read numerical parameters and do sanity check
num_commercialFEM => numerics_root%get('commercialFEM',defaultVal=emptyDict)
iJacoStiffness = num_commercialFEM%get_asInt('ijacostiffness',defaultVal=1)
if (iJacoStiffness < 1) call IO_error(301,ext_msg='iJacoStiffness')
elCP = mesh_FEM2DAMASK_elem(elFE) elCP = mesh_FEM2DAMASK_elem(elFE)
@ -179,7 +186,7 @@ subroutine CPFEM_general(mode, ffn, ffn1, temperature_inp, dt, elFE, ip, cauchyS
CPFEM_dcsde(1:6,1:6,ip,elCP) = ODD_JACOBIAN * math_identity2nd(6) CPFEM_dcsde(1:6,1:6,ip,elCP) = ODD_JACOBIAN * math_identity2nd(6)
else validCalculation else validCalculation
updateJaco = mod(cycleCounter,iJacoStiffness) == 0 updateJaco = mod(cycleCounter,num%iJacoStiffness) == 0
FEsolving_execElem = elCP FEsolving_execElem = elCP
FEsolving_execIP = ip FEsolving_execIP = ip
if (iand(debug_level(debug_CPFEM), debug_levelExtensive) /= 0_pInt) & if (iand(debug_level(debug_CPFEM), debug_levelExtensive) /= 0_pInt) &

View File

@ -23,9 +23,16 @@ module damage_local
output output
end type tParameters end type tParameters
type, private :: tNumerics
real(pReal) :: &
residualStiffness !< non-zero residual damage
end type tNumerics
type(tparameters), dimension(:), allocatable :: & type(tparameters), dimension(:), allocatable :: &
param param
type(tNumerics), private :: num
public :: & public :: &
damage_local_init, & damage_local_init, &
damage_local_updateState, & damage_local_updateState, &
@ -40,9 +47,17 @@ contains
subroutine damage_local_init subroutine damage_local_init
integer :: Ninstance,NofMyHomog,h integer :: Ninstance,NofMyHomog,h
class(tNode), pointer :: num_generic
write(6,'(/,a)') ' <<<+- damage_'//DAMAGE_local_label//' init -+>>>'; flush(6) write(6,'(/,a)') ' <<<+- damage_'//DAMAGE_local_label//' init -+>>>'; flush(6)
!----------------------------------------------------------------------------------------------
! read numerics parameter and do sanity check
num_generic => numerics_root%get('generic',defaultVal=emptyDict)
num%residualStiffness = num_generic%get_asFloat('residualStiffness', defaultVal=1.0e-6_pReal)
if (num%residualStiffness < 0.0_pReal) call IO_error(301,ext_msg='residualStiffness')
!----------------------------------------------------------------------------------------------
Ninstance = count(damage_type == DAMAGE_local_ID) Ninstance = count(damage_type == DAMAGE_local_ID)
allocate(param(Ninstance)) allocate(param(Ninstance))
@ -85,20 +100,14 @@ function damage_local_updateState(subdt, ip, el)
homog, & homog, &
offset offset
real(pReal) :: & real(pReal) :: &
phi, phiDot, dPhiDot_dPhi, & phi, phiDot, dPhiDot_dPhi
residualStiffness !< non-zero residual damage
class(tNode), pointer :: &
num_generic
num_generic => numerics_root%get('generic',defaultVal=emptyDict)
residualStiffness = num_generic%get_asFloat('residualStiffness', defaultVal=1.0e-6_pReal)
if (residualStiffness < 0.0_pReal) call IO_error(301,ext_msg='residualStiffness')
homog = material_homogenizationAt(el) homog = material_homogenizationAt(el)
offset = material_homogenizationMemberAt(ip,el) offset = material_homogenizationMemberAt(ip,el)
phi = damageState(homog)%subState0(1,offset) phi = damageState(homog)%subState0(1,offset)
call damage_local_getSourceAndItsTangent(phiDot, dPhiDot_dPhi, phi, ip, el) call damage_local_getSourceAndItsTangent(phiDot, dPhiDot_dPhi, phi, ip, el)
phi = max(residualStiffness,min(1.0_pReal,phi + subdt*phiDot)) phi = max(num%residualStiffness,min(1.0_pReal,phi + subdt*phiDot))
damage_local_updateState = [ abs(phi - damageState(homog)%state(1,offset)) & damage_local_updateState = [ abs(phi - damageState(homog)%state(1,offset)) &
<= 1.0e-2_pReal & <= 1.0e-2_pReal &

View File

@ -24,8 +24,15 @@ module damage_nonlocal
output output
end type tParameters end type tParameters
type, private :: tNumerics
real(pReal) :: &
charLength !< characteristic length scale for gradient problems
end type tNumerics
type(tparameters), dimension(:), allocatable :: & type(tparameters), dimension(:), allocatable :: &
param param
type(tNumerics), private :: &
num
public :: & public :: &
damage_nonlocal_init, & damage_nonlocal_init, &
@ -44,9 +51,17 @@ contains
subroutine damage_nonlocal_init subroutine damage_nonlocal_init
integer :: Ninstance,NofMyHomog,h integer :: Ninstance,NofMyHomog,h
class(tNode), pointer :: &
num_generic
write(6,'(/,a)') ' <<<+- damage_'//DAMAGE_nonlocal_label//' init -+>>>'; flush(6) write(6,'(/,a)') ' <<<+- damage_'//DAMAGE_nonlocal_label//' init -+>>>'; flush(6)
!------------------------------------------------------------------------------------
! read numerics parameter
num_generic => numerics_root%get('generic',defaultVal= emptyDict)
num%charLength = num_generic%get_asFloat('charLength',defaultVal=1.0_pReal)
!------------------------------------------------------------------------------------
Ninstance = count(damage_type == DAMAGE_nonlocal_ID) Ninstance = count(damage_type == DAMAGE_nonlocal_ID)
allocate(param(Ninstance)) allocate(param(Ninstance))
@ -139,13 +154,6 @@ function damage_nonlocal_getDiffusion(ip,el)
integer :: & integer :: &
homog, & homog, &
grain grain
real(pReal) :: &
charLength !< characteristic length scale for gradient problems
class(tNode), pointer :: &
num_generic
num_generic => numerics_root%get('generic',defaultVal= emptyDict)
charLength = num_generic%get_asFloat('charLength',defaultVal=1.0_pReal)
homog = material_homogenizationAt(el) homog = material_homogenizationAt(el)
damage_nonlocal_getDiffusion = 0.0_pReal damage_nonlocal_getDiffusion = 0.0_pReal
@ -155,7 +163,7 @@ function damage_nonlocal_getDiffusion(ip,el)
enddo enddo
damage_nonlocal_getDiffusion = & damage_nonlocal_getDiffusion = &
charLength**2*damage_nonlocal_getDiffusion/real(homogenization_Ngrains(homog),pReal) num%charLength**2*damage_nonlocal_getDiffusion/real(homogenization_Ngrains(homog),pReal)
end function damage_nonlocal_getDiffusion end function damage_nonlocal_getDiffusion

View File

@ -61,7 +61,6 @@ program DAMASK_grid
i, j, k, l, field, & i, j, k, l, field, &
errorID = 0, & errorID = 0, &
cutBackLevel = 0, & !< cut back level \f$ t = \frac{t_{inc}}{2^l} \f$ cutBackLevel = 0, & !< cut back level \f$ t = \frac{t_{inc}}{2^l} \f$
maxCutBack, & !< max number of cut backs
stepFraction = 0 !< fraction of current time interval stepFraction = 0 !< fraction of current time interval
integer :: & integer :: &
currentLoadcase = 0, & !< current load case currentLoadcase = 0, & !< current load case
@ -69,12 +68,18 @@ program DAMASK_grid
totalIncsCounter = 0, & !< total # of increments totalIncsCounter = 0, & !< total # of increments
statUnit = 0, & !< file unit for statistics output statUnit = 0, & !< file unit for statistics output
stagIter, & stagIter, &
stagItMax, & !< max number of field level staggered iterations
nActiveFields = 0 nActiveFields = 0
character(len=pStringLen), dimension(:), allocatable :: fileContent character(len=pStringLen), dimension(:), allocatable :: fileContent
character(len=pStringLen) :: & character(len=pStringLen) :: &
incInfo, & incInfo, &
loadcase_string loadcase_string
type :: tNumerics
integer :: &
maxCutBack, & !< max number of cut backs
stagItMax !< max number of field level staggered iterations
end type tNumerics
type(tNumerics) :: num
type(tLoadCase), allocatable, dimension(:) :: loadCases !< array of all load cases type(tLoadCase), allocatable, dimension(:) :: loadCases !< array of all load cases
type(tLoadCase) :: newLoadCase type(tLoadCase) :: newLoadCase
type(tSolutionState), allocatable, dimension(:) :: solres type(tSolutionState), allocatable, dimension(:) :: solres
@ -114,11 +119,11 @@ program DAMASK_grid
!------------------------------------------------------------------------------------------------- !-------------------------------------------------------------------------------------------------
! reading field paramters from numerics file and do sanity checks ! reading field paramters from numerics file and do sanity checks
num_grid => numerics_root%get('grid', defaultVal=emptyDict) num_grid => numerics_root%get('grid', defaultVal=emptyDict)
stagItMax = num_grid%get_asInt('maxStaggeredIter',defaultVal=10) num%stagItMax = num_grid%get_asInt('maxStaggeredIter',defaultVal=10)
maxCutBack = num_grid%get_asInt('maxCutBack',defaultVal=3) num%maxCutBack = num_grid%get_asInt('maxCutBack',defaultVal=3)
if (stagItMax < 0) call IO_error(301,ext_msg='maxStaggeredIter') if (num%stagItMax < 0) call IO_error(301,ext_msg='maxStaggeredIter')
if (maxCutBack < 0) call IO_error(301,ext_msg='maxCutBack') if (num%maxCutBack < 0) call IO_error(301,ext_msg='maxCutBack')
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
! assign mechanics solver depending on selected type ! assign mechanics solver depending on selected type
@ -449,7 +454,7 @@ program DAMASK_grid
enddo enddo
stagIter = stagIter + 1 stagIter = stagIter + 1
stagIterate = stagIter < stagItMax & stagIterate = stagIter < num%stagItMax &
.and. all(solres(:)%converged) & .and. all(solres(:)%converged) &
.and. .not. all(solres(:)%stagConverged) ! stationary with respect to staggered iteration .and. .not. all(solres(:)%stagConverged) ! stationary with respect to staggered iteration
enddo enddo
@ -468,7 +473,7 @@ program DAMASK_grid
solres%converged, solres%iterationsNeeded solres%converged, solres%iterationsNeeded
flush(statUnit) flush(statUnit)
endif endif
elseif (cutBackLevel < maxCutBack) then ! further cutbacking tolerated? elseif (cutBackLevel < num%maxCutBack) then ! further cutbacking tolerated?
cutBack = .true. cutBack = .true.
stepFraction = (stepFraction - 1) * subStepFactor ! adjust to new denominator stepFraction = (stepFraction - 1) * subStepFactor ! adjust to new denominator
cutBackLevel = cutBackLevel + 1 cutBackLevel = cutBackLevel + 1

View File

@ -72,6 +72,14 @@ module math
3,2, & 3,2, &
3,3 & 3,3 &
],shape(MAPPLAIN)) !< arrangement in Plain notation ],shape(MAPPLAIN)) !< arrangement in Plain notation
type, private :: tNumerics
integer :: &
randomSeed !< fixed seeding for pseudo-random number generator, Default 0: use random seed
end type
type(tNumerics), private :: num
interface math_eye interface math_eye
module procedure math_identity2nd module procedure math_identity2nd
@ -91,8 +99,7 @@ subroutine math_init
real(pReal), dimension(4) :: randTest real(pReal), dimension(4) :: randTest
integer :: & integer :: &
randSize, & randSize
randomSeed !< fixed seeding for pseudo-random number generator, Default 0: use random seed
integer, dimension(:), allocatable :: randInit integer, dimension(:), allocatable :: randInit
class(tNode), pointer :: & class(tNode), pointer :: &
num_generic num_generic
@ -100,12 +107,12 @@ subroutine math_init
write(6,'(/,a)') ' <<<+- math init -+>>>'; flush(6) write(6,'(/,a)') ' <<<+- math init -+>>>'; flush(6)
num_generic => numerics_root%get('generic',defaultVal=emptyDict) num_generic => numerics_root%get('generic',defaultVal=emptyDict)
randomSeed = num_generic%get_asInt('random_seed', defaultVal = 0) num%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 (num%randomSeed > 0) then
randInit = randomSeed randInit = num%randomSeed
else else
call random_seed() call random_seed()
call random_seed(get = randInit) call random_seed(get = randInit)