Merge branch 'MiscImprovements' of magit1.mpie.de:/damask/DAMASK into MiscImprovements
This commit is contained in:
commit
5fae924e88
|
@ -95,13 +95,13 @@ end subroutine DAMASK_interface_init
|
|||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief solver job name (no extension) as combination of geometry and load case name
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
function getSolverJobName()
|
||||
function getSolverJobName
|
||||
|
||||
character(1024) :: getSolverJobName, inputName
|
||||
character(len=:), allocatable :: getSolverJobName
|
||||
character(1024) :: inputName
|
||||
character(len=*), parameter :: pathSep = achar(47)//achar(92) ! forward and backward slash
|
||||
integer :: extPos
|
||||
|
||||
getSolverJobName=''
|
||||
inputName=''
|
||||
inquire(5, name=inputName) ! determine inputfile
|
||||
extPos = len_trim(inputName)-4
|
||||
|
|
|
@ -43,12 +43,11 @@ subroutine FE_init
|
|||
character(len=pStringLen) :: line
|
||||
integer :: myStat,fileUnit
|
||||
integer, allocatable, dimension(:) :: chunkPos
|
||||
open(newunit=fileUnit, file=trim(getSolverJobName()//INPUTFILEEXTENSION), &
|
||||
open(newunit=fileUnit, file=getSolverJobName()//INPUTFILEEXTENSION, &
|
||||
status='old', position='rewind', action='read',iostat=myStat)
|
||||
do
|
||||
read (fileUnit,'(A)',END=100) line
|
||||
chunkPos = IO_stringPos(line)
|
||||
if(IO_lc(IO_stringValue(line,chunkPos,1)) == 'solver') then
|
||||
if(index(trim(lc(line)),'solver') == 1) then
|
||||
read (fileUnit,'(A)',END=100) line ! next line
|
||||
chunkPos = IO_stringPos(line)
|
||||
symmetricSolver = (IO_intValue(line,chunkPos,2) /= 1)
|
||||
|
@ -56,6 +55,29 @@ subroutine FE_init
|
|||
enddo
|
||||
100 close(fileUnit)
|
||||
end block
|
||||
contains
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief changes characters in string to lower case
|
||||
!> @details copied from IO_lc
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
function lc(string)
|
||||
|
||||
character(len=*), intent(in) :: string !< string to convert
|
||||
character(len=len(string)) :: lc
|
||||
|
||||
character(26), parameter :: LOWER = 'abcdefghijklmnopqrstuvwxyz'
|
||||
character(26), parameter :: UPPER = 'ABCDEFGHIJKLMNOPQRSTUVWXYZ'
|
||||
|
||||
integer :: i,n
|
||||
|
||||
do i=1,len(string)
|
||||
lc(i:i) = string(i:i)
|
||||
n = index(UPPER,lc(i:i))
|
||||
if (n/=0) lc(i:i) = LOWER(n:n)
|
||||
enddo
|
||||
end function lc
|
||||
|
||||
#endif
|
||||
|
||||
end subroutine FE_init
|
||||
|
|
|
@ -454,8 +454,8 @@ pure function IO_lc(string)
|
|||
|
||||
integer :: i,n
|
||||
|
||||
IO_lc = string
|
||||
do i=1,len(string)
|
||||
IO_lc(i:i) = string(i:i)
|
||||
n = index(UPPER,IO_lc(i:i))
|
||||
if (n/=0) IO_lc(i:i) = LOWER(n:n)
|
||||
enddo
|
||||
|
|
|
@ -74,7 +74,7 @@ subroutine damage_local_init
|
|||
allocate(damageState(h)%state (1,NofMyHomog), source=damage_initialPhi(h))
|
||||
|
||||
nullify(damageMapping(h)%p)
|
||||
damageMapping(h)%p => mappingHomogenization(1,:,:)
|
||||
damageMapping(h)%p => material_homogenizationMemberAt
|
||||
deallocate(damage(h)%p)
|
||||
damage(h)%p => damageState(h)%state(1,:)
|
||||
|
||||
|
@ -103,7 +103,7 @@ function damage_local_updateState(subdt, ip, el)
|
|||
phi, phiDot, dPhiDot_dPhi
|
||||
|
||||
homog = material_homogenizationAt(el)
|
||||
offset = mappingHomogenization(1,ip,el)
|
||||
offset = material_homogenizationMemberAt(ip,el)
|
||||
phi = damageState(homog)%subState0(1,offset)
|
||||
call damage_local_getSourceAndItsTangent(phiDot, dPhiDot_dPhi, phi, ip, el)
|
||||
phi = max(residualStiffness,min(1.0_pReal,phi + subdt*phiDot))
|
||||
|
|
|
@ -79,7 +79,7 @@ subroutine damage_nonlocal_init
|
|||
allocate(damageState(h)%state (1,NofMyHomog), source=damage_initialPhi(h))
|
||||
|
||||
nullify(damageMapping(h)%p)
|
||||
damageMapping(h)%p => mappingHomogenization(1,:,:)
|
||||
damageMapping(h)%p => material_homogenizationMemberAt
|
||||
deallocate(damage(h)%p)
|
||||
damage(h)%p => damageState(h)%state(1,:)
|
||||
|
||||
|
|
|
@ -242,16 +242,16 @@ subroutine materialpoint_stressAndItsTangent(updateJaco,dt)
|
|||
materialpoint_requested(i,e) = .true. ! everybody requires calculation
|
||||
|
||||
if (homogState(material_homogenizationAt(e))%sizeState > 0) &
|
||||
homogState(material_homogenizationAt(e))%subState0(:,mappingHomogenization(1,i,e)) = &
|
||||
homogState(material_homogenizationAt(e))%State0( :,mappingHomogenization(1,i,e)) ! ...internal homogenization state
|
||||
homogState(material_homogenizationAt(e))%subState0(:,material_homogenizationMemberAt(i,e)) = &
|
||||
homogState(material_homogenizationAt(e))%State0( :,material_homogenizationMemberAt(i,e)) ! ...internal homogenization state
|
||||
|
||||
if (thermalState(material_homogenizationAt(e))%sizeState > 0) &
|
||||
thermalState(material_homogenizationAt(e))%subState0(:,mappingHomogenization(1,i,e)) = &
|
||||
thermalState(material_homogenizationAt(e))%State0( :,mappingHomogenization(1,i,e)) ! ...internal thermal state
|
||||
thermalState(material_homogenizationAt(e))%subState0(:,material_homogenizationMemberAt(i,e)) = &
|
||||
thermalState(material_homogenizationAt(e))%State0( :,material_homogenizationMemberAt(i,e)) ! ...internal thermal state
|
||||
|
||||
if (damageState(material_homogenizationAt(e))%sizeState > 0) &
|
||||
damageState(material_homogenizationAt(e))%subState0(:,mappingHomogenization(1,i,e)) = &
|
||||
damageState(material_homogenizationAt(e))%State0( :,mappingHomogenization(1,i,e)) ! ...internal damage state
|
||||
damageState(material_homogenizationAt(e))%subState0(:,material_homogenizationMemberAt(i,e)) = &
|
||||
damageState(material_homogenizationAt(e))%State0( :,material_homogenizationMemberAt(i,e)) ! ...internal damage state
|
||||
enddo
|
||||
enddo
|
||||
|
||||
|
@ -313,14 +313,14 @@ subroutine materialpoint_stressAndItsTangent(updateJaco,dt)
|
|||
enddo
|
||||
|
||||
if(homogState(material_homogenizationAt(e))%sizeState > 0) &
|
||||
homogState(material_homogenizationAt(e))%subState0(:,mappingHomogenization(1,i,e)) = &
|
||||
homogState(material_homogenizationAt(e))%State (:,mappingHomogenization(1,i,e))
|
||||
homogState(material_homogenizationAt(e))%subState0(:,material_homogenizationMemberAt(i,e)) = &
|
||||
homogState(material_homogenizationAt(e))%State (:,material_homogenizationMemberAt(i,e))
|
||||
if(thermalState(material_homogenizationAt(e))%sizeState > 0) &
|
||||
thermalState(material_homogenizationAt(e))%subState0(:,mappingHomogenization(1,i,e)) = &
|
||||
thermalState(material_homogenizationAt(e))%State (:,mappingHomogenization(1,i,e))
|
||||
thermalState(material_homogenizationAt(e))%subState0(:,material_homogenizationMemberAt(i,e)) = &
|
||||
thermalState(material_homogenizationAt(e))%State (:,material_homogenizationMemberAt(i,e))
|
||||
if(damageState(material_homogenizationAt(e))%sizeState > 0) &
|
||||
damageState(material_homogenizationAt(e))%subState0(:,mappingHomogenization(1,i,e)) = &
|
||||
damageState(material_homogenizationAt(e))%State (:,mappingHomogenization(1,i,e))
|
||||
damageState(material_homogenizationAt(e))%subState0(:,material_homogenizationMemberAt(i,e)) = &
|
||||
damageState(material_homogenizationAt(e))%State (:,material_homogenizationMemberAt(i,e))
|
||||
|
||||
materialpoint_subF0(1:3,1:3,i,e) = materialpoint_subF(1:3,1:3,i,e)
|
||||
|
||||
|
@ -375,14 +375,14 @@ subroutine materialpoint_stressAndItsTangent(updateJaco,dt)
|
|||
enddo
|
||||
enddo
|
||||
if(homogState(material_homogenizationAt(e))%sizeState > 0) &
|
||||
homogState(material_homogenizationAt(e))%State( :,mappingHomogenization(1,i,e)) = &
|
||||
homogState(material_homogenizationAt(e))%subState0(:,mappingHomogenization(1,i,e))
|
||||
homogState(material_homogenizationAt(e))%State( :,material_homogenizationMemberAt(i,e)) = &
|
||||
homogState(material_homogenizationAt(e))%subState0(:,material_homogenizationMemberAt(i,e))
|
||||
if(thermalState(material_homogenizationAt(e))%sizeState > 0) &
|
||||
thermalState(material_homogenizationAt(e))%State( :,mappingHomogenization(1,i,e)) = &
|
||||
thermalState(material_homogenizationAt(e))%subState0(:,mappingHomogenization(1,i,e))
|
||||
thermalState(material_homogenizationAt(e))%State( :,material_homogenizationMemberAt(i,e)) = &
|
||||
thermalState(material_homogenizationAt(e))%subState0(:,material_homogenizationMemberAt(i,e))
|
||||
if(damageState(material_homogenizationAt(e))%sizeState > 0) &
|
||||
damageState(material_homogenizationAt(e))%State( :,mappingHomogenization(1,i,e)) = &
|
||||
damageState(material_homogenizationAt(e))%subState0(:,mappingHomogenization(1,i,e))
|
||||
damageState(material_homogenizationAt(e))%State( :,material_homogenizationMemberAt(i,e)) = &
|
||||
damageState(material_homogenizationAt(e))%subState0(:,material_homogenizationMemberAt(i,e))
|
||||
endif
|
||||
endif converged
|
||||
|
||||
|
|
|
@ -108,7 +108,7 @@ module subroutine mech_RGC_init
|
|||
|
||||
#ifdef DEBUG
|
||||
if (h==material_homogenizationAt(debug_e)) then
|
||||
prm%of_debug = mappingHomogenization(1,debug_i,debug_e)
|
||||
prm%of_debug = material_homogenizationMemberAt(debug_i,debug_e)
|
||||
endif
|
||||
#endif
|
||||
|
||||
|
@ -261,7 +261,7 @@ module procedure mech_RGC_updateState
|
|||
endif zeroTimeStep
|
||||
|
||||
instance = homogenization_typeInstance(material_homogenizationAt(el))
|
||||
of = mappingHomogenization(1,ip,el)
|
||||
of = material_homogenizationMemberAt(ip,el)
|
||||
|
||||
associate(stt => state(instance), st0 => state0(instance), dst => dependentState(instance), prm => param(instance))
|
||||
|
||||
|
|
|
@ -113,11 +113,9 @@ module material
|
|||
phase_Nsources, & !< number of source mechanisms active in each phase
|
||||
phase_Nkinematics, & !< number of kinematic mechanisms active in each phase
|
||||
phase_NstiffnessDegradations, & !< number of stiffness degradation mechanisms active in each phase
|
||||
phase_Noutput, & !< number of '(output)' items per phase
|
||||
phase_elasticityInstance, & !< instance of particular elasticity of each phase
|
||||
phase_plasticityInstance, & !< instance of particular plasticity of each phase
|
||||
homogenization_Ngrains, & !< number of grains in each homogenization
|
||||
homogenization_Noutput, & !< number of '(output)' items per homogenization
|
||||
homogenization_typeInstance, & !< instance of particular type of each homogenization
|
||||
thermal_typeInstance, & !< instance of particular type of each thermal transport
|
||||
damage_typeInstance !< instance of particular type of each nonlocal damage
|
||||
|
@ -129,7 +127,7 @@ module material
|
|||
! NEW MAPPINGS
|
||||
integer, dimension(:), allocatable, public, protected :: & ! (elem)
|
||||
material_homogenizationAt !< homogenization ID of each element (copy of discretization_homogenizationAt)
|
||||
integer, dimension(:,:), allocatable, public, protected :: & ! (ip,elem)
|
||||
integer, dimension(:,:), allocatable, public, target :: & ! (ip,elem) ToDo: ugly target for mapping hack
|
||||
material_homogenizationMemberAt !< position of the element within its homogenization instance
|
||||
integer, dimension(:,:), allocatable, public, protected :: & ! (constituent,elem)
|
||||
material_phaseAt !< phase ID of each element
|
||||
|
@ -153,12 +151,8 @@ module material
|
|||
material_orientation0 !< initial orientation of each grain,IP,element
|
||||
|
||||
logical, dimension(:), allocatable, public, protected :: &
|
||||
microstructure_active, &
|
||||
phase_localPlasticity !< flags phases with local constitutive law
|
||||
|
||||
integer, private :: &
|
||||
microstructure_maxNconstituents !< max number of constituents in any phase
|
||||
|
||||
integer, dimension(:), allocatable, private :: &
|
||||
microstructure_Nconstituents !< number of constituents in each microstructure
|
||||
|
||||
|
@ -170,14 +164,9 @@ module material
|
|||
material_Eulers
|
||||
type(Rotation), dimension(:), allocatable, private :: &
|
||||
texture_orientation !< Euler angles in material.config (possibly rotated for alignment)
|
||||
real(pReal), dimension(:,:), allocatable, private :: &
|
||||
microstructure_fraction !< vol fraction of each constituent in microstructure
|
||||
|
||||
logical, dimension(:), allocatable, private :: &
|
||||
homogenization_active
|
||||
|
||||
! BEGIN DEPRECATED
|
||||
integer, dimension(:,:,:), allocatable, public, target :: mappingHomogenization !< mapping from material points to offset in heterogenous state/field
|
||||
integer, dimension(:,:), allocatable, private, target :: mappingHomogenizationConst !< mapping from material points to offset in constant state/field
|
||||
! END DEPRECATED
|
||||
|
||||
|
@ -294,9 +283,8 @@ subroutine material_init
|
|||
microstructure_Nconstituents(m)
|
||||
if (microstructure_Nconstituents(m) > 0) then
|
||||
do c = 1,microstructure_Nconstituents(m)
|
||||
write(6,'(a1,1x,a32,1x,a32,1x,f7.4)') '>',config_name_phase(microstructure_phase(c,m)),&
|
||||
config_name_texture(microstructure_texture(c,m)),&
|
||||
microstructure_fraction(c,m)
|
||||
write(6,'(a1,1x,a32,1x,a32)') '>',config_name_phase(microstructure_phase(c,m)),&
|
||||
config_name_texture(microstructure_texture(c,m))
|
||||
enddo
|
||||
write(6,*)
|
||||
endif
|
||||
|
@ -362,18 +350,8 @@ subroutine material_init
|
|||
|
||||
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
|
||||
! BEGIN DEPRECATED
|
||||
allocate(mappingHomogenization (2,discretization_nIP,discretization_nElem),source=0)
|
||||
allocate(mappingHomogenizationConst( discretization_nIP,discretization_nElem),source=1)
|
||||
|
||||
CounterHomogenization=0
|
||||
do e = 1,discretization_nElem
|
||||
myHomog = discretization_homogenizationAt(e)
|
||||
do i = 1, discretization_nIP
|
||||
CounterHomogenization(myHomog) = CounterHomogenization(myHomog) + 1
|
||||
mappingHomogenization(1:2,i,e) = [CounterHomogenization(myHomog),huge(1)]
|
||||
enddo
|
||||
enddo
|
||||
|
||||
! hack needed to initialize field values used during constitutive and crystallite initializations
|
||||
do myHomog = 1,size(config_homogenization)
|
||||
thermalMapping (myHomog)%p => mappingHomogenizationConst
|
||||
|
@ -394,6 +372,8 @@ subroutine material_parseHomogenization
|
|||
integer :: h
|
||||
character(len=pStringLen) :: tag
|
||||
|
||||
logical, dimension(:), allocatable :: homogenization_active
|
||||
|
||||
allocate(homogenization_type(size(config_homogenization)), source=HOMOGENIZATION_undefined_ID)
|
||||
allocate(thermal_type(size(config_homogenization)), source=THERMAL_isothermal_ID)
|
||||
allocate(damage_type (size(config_homogenization)), source=DAMAGE_none_ID)
|
||||
|
@ -401,7 +381,6 @@ subroutine material_parseHomogenization
|
|||
allocate(thermal_typeInstance(size(config_homogenization)), source=0)
|
||||
allocate(damage_typeInstance(size(config_homogenization)), source=0)
|
||||
allocate(homogenization_Ngrains(size(config_homogenization)), source=0)
|
||||
allocate(homogenization_Noutput(size(config_homogenization)), source=0)
|
||||
allocate(homogenization_active(size(config_homogenization)), source=.false.) !!!!!!!!!!!!!!!
|
||||
allocate(thermal_initialT(size(config_homogenization)), source=300.0_pReal)
|
||||
allocate(damage_initialPhi(size(config_homogenization)), source=1.0_pReal)
|
||||
|
@ -411,7 +390,6 @@ subroutine material_parseHomogenization
|
|||
|
||||
|
||||
do h=1, size(config_homogenization)
|
||||
homogenization_Noutput(h) = config_homogenization(h)%countKeys('(output)')
|
||||
|
||||
tag = config_homogenization(h)%getString('mech')
|
||||
select case (trim(tag))
|
||||
|
@ -488,16 +466,16 @@ subroutine material_parseMicrostructure
|
|||
integer :: e, m, c, i
|
||||
character(len=pStringLen) :: &
|
||||
tag
|
||||
real(pReal), dimension(:,:), allocatable :: &
|
||||
microstructure_fraction !< vol fraction of each constituent in microstructure
|
||||
integer :: &
|
||||
microstructure_maxNconstituents !< max number of constituents in any phase
|
||||
|
||||
allocate(microstructure_Nconstituents(size(config_microstructure)), source=0)
|
||||
allocate(microstructure_active(size(config_microstructure)), source=.false.)
|
||||
|
||||
if(any(discretization_microstructureAt > size(config_microstructure))) &
|
||||
call IO_error(155,ext_msg='More microstructures in geometry than sections in material.config')
|
||||
|
||||
forall (e = 1:discretization_nElem) &
|
||||
microstructure_active(discretization_microstructureAt(e)) = .true. ! current microstructure used in model? Elementwise view, maximum N operations for N elements
|
||||
|
||||
do m=1, size(config_microstructure)
|
||||
microstructure_Nconstituents(m) = config_microstructure(m)%countKeys('(constituent)')
|
||||
enddo
|
||||
|
@ -548,11 +526,9 @@ subroutine material_parsePhase
|
|||
allocate(phase_Nsources(size(config_phase)), source=0)
|
||||
allocate(phase_Nkinematics(size(config_phase)), source=0)
|
||||
allocate(phase_NstiffnessDegradations(size(config_phase)),source=0)
|
||||
allocate(phase_Noutput(size(config_phase)), source=0)
|
||||
allocate(phase_localPlasticity(size(config_phase)), source=.false.)
|
||||
|
||||
do p=1, size(config_phase)
|
||||
phase_Noutput(p) = config_phase(p)%countKeys('(output)')
|
||||
phase_Nsources(p) = config_phase(p)%countKeys('(source)')
|
||||
phase_Nkinematics(p) = config_phase(p)%countKeys('(kinematics)')
|
||||
phase_NstiffnessDegradations(p) = config_phase(p)%countKeys('(stiffness_degradation)')
|
||||
|
|
|
@ -77,7 +77,7 @@ subroutine thermal_adiabatic_init
|
|||
allocate(thermalState(h)%state (1,NofMyHomog), source=thermal_initialT(h))
|
||||
|
||||
nullify(thermalMapping(h)%p)
|
||||
thermalMapping(h)%p => mappingHomogenization(1,:,:)
|
||||
thermalMapping(h)%p => material_homogenizationMemberAt
|
||||
deallocate(temperature(h)%p)
|
||||
temperature(h)%p => thermalState(h)%state(1,:)
|
||||
deallocate(temperatureRate(h)%p)
|
||||
|
@ -109,7 +109,7 @@ function thermal_adiabatic_updateState(subdt, ip, el)
|
|||
T, Tdot, dTdot_dT
|
||||
|
||||
homog = material_homogenizationAt(el)
|
||||
offset = mappingHomogenization(1,ip,el)
|
||||
offset = material_homogenizationMemberAt(ip,el)
|
||||
|
||||
T = thermalState(homog)%subState0(1,offset)
|
||||
call thermal_adiabatic_getSourceAndItsTangent(Tdot, dTdot_dT, T, ip, el)
|
||||
|
|
|
@ -79,7 +79,7 @@ subroutine thermal_conduction_init
|
|||
allocate(thermalState(h)%state (0,NofMyHomog))
|
||||
|
||||
nullify(thermalMapping(h)%p)
|
||||
thermalMapping(h)%p => mappingHomogenization(1,:,:)
|
||||
thermalMapping(h)%p => material_homogenizationMemberAt
|
||||
deallocate(temperature (h)%p)
|
||||
allocate (temperature (h)%p(NofMyHomog), source=thermal_initialT(h))
|
||||
deallocate(temperatureRate(h)%p)
|
||||
|
@ -114,7 +114,7 @@ subroutine thermal_conduction_getSourceAndItsTangent(Tdot, dTdot_dT, T, ip, el)
|
|||
constituent
|
||||
|
||||
homog = material_homogenizationAt(el)
|
||||
offset = mappingHomogenization(1,ip,el)
|
||||
offset = material_homogenizationMemberAt(ip,el)
|
||||
instance = thermal_typeInstance(homog)
|
||||
|
||||
Tdot = 0.0_pReal
|
||||
|
|
Loading…
Reference in New Issue