all not compatible with new structure
This commit is contained in:
parent
13f321d992
commit
ed79c7f75c
|
@ -716,10 +716,7 @@ subroutine constitutive_hooke_SandItsTangents(S, dS_dFe, dS_dFi, Fe, Fi, ipc, ip
|
|||
phase_stiffnessDegradation, &
|
||||
damage, &
|
||||
damageMapping, &
|
||||
porosity, &
|
||||
porosityMapping, &
|
||||
STIFFNESS_DEGRADATION_damage_ID, &
|
||||
STIFFNESS_DEGRADATION_porosity_ID
|
||||
STIFFNESS_DEGRADATION_damage_ID
|
||||
|
||||
implicit none
|
||||
integer(pInt), intent(in) :: &
|
||||
|
@ -749,8 +746,6 @@ subroutine constitutive_hooke_SandItsTangents(S, dS_dFe, dS_dFi, Fe, Fi, ipc, ip
|
|||
degradationType: select case(phase_stiffnessDegradation(d,material_phase(ipc,ip,el)))
|
||||
case (STIFFNESS_DEGRADATION_damage_ID) degradationType
|
||||
C = C * damage(ho)%p(damageMapping(ho)%p(ip,el))**2_pInt
|
||||
case (STIFFNESS_DEGRADATION_porosity_ID) degradationType
|
||||
C = C * porosity(ho)%p(porosityMapping(ho)%p(ip,el))**2_pInt
|
||||
end select degradationType
|
||||
enddo DegradationLoop
|
||||
|
||||
|
|
|
@ -1,508 +0,0 @@
|
|||
!--------------------------------------------------------------------------------------------------
|
||||
!> @author Pratheek Shanthraj, Max-Planck-Institut für Eisenforschung GmbH
|
||||
!> @brief material subroutine for conservative transport of solute hydrogen
|
||||
!> @details to be done
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
module hydrogenflux_cahnhilliard
|
||||
use prec, only: &
|
||||
pReal, &
|
||||
pInt
|
||||
|
||||
implicit none
|
||||
private
|
||||
integer(pInt), dimension(:), allocatable, public, protected :: &
|
||||
hydrogenflux_cahnhilliard_sizePostResults !< cumulative size of post results
|
||||
|
||||
integer(pInt), dimension(:,:), allocatable, target, public :: &
|
||||
hydrogenflux_cahnhilliard_sizePostResult !< size of each post result output
|
||||
|
||||
character(len=64), dimension(:,:), allocatable, target, public :: &
|
||||
hydrogenflux_cahnhilliard_output !< name of each post result output
|
||||
|
||||
integer(pInt), dimension(:), allocatable, target, public :: &
|
||||
hydrogenflux_cahnhilliard_Noutput !< number of outputs per instance of this damage
|
||||
|
||||
real(pReal), parameter, private :: &
|
||||
kB = 1.3806488e-23_pReal !< Boltzmann constant in J/Kelvin
|
||||
|
||||
enum, bind(c)
|
||||
enumerator :: undefined_ID, &
|
||||
hydrogenConc_ID
|
||||
end enum
|
||||
integer(kind(undefined_ID)), dimension(:,:), allocatable, private :: &
|
||||
hydrogenflux_cahnhilliard_outputID !< ID of each post result output
|
||||
|
||||
|
||||
public :: &
|
||||
hydrogenflux_cahnhilliard_init, &
|
||||
hydrogenflux_cahnhilliard_getMobility33, &
|
||||
hydrogenflux_cahnhilliard_getDiffusion33, &
|
||||
hydrogenflux_cahnhilliard_getFormationEnergy, &
|
||||
hydrogenflux_cahnhilliard_KinematicChemPotAndItsTangent, &
|
||||
hydrogenflux_cahnhilliard_getChemPotAndItsTangent, &
|
||||
hydrogenflux_cahnhilliard_putHydrogenConcAndItsRate, &
|
||||
hydrogenflux_cahnhilliard_postResults
|
||||
|
||||
contains
|
||||
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief module initialization
|
||||
!> @details reads in material parameters, allocates arrays, and does sanity checks
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine hydrogenflux_cahnhilliard_init(fileUnit)
|
||||
#if defined(__GFORTRAN__) || __INTEL_COMPILER >= 1800
|
||||
use, intrinsic :: iso_fortran_env, only: &
|
||||
compiler_version, &
|
||||
compiler_options
|
||||
#endif
|
||||
use IO, only: &
|
||||
IO_read, &
|
||||
IO_lc, &
|
||||
IO_getTag, &
|
||||
IO_isBlank, &
|
||||
IO_stringPos, &
|
||||
IO_stringValue, &
|
||||
IO_floatValue, &
|
||||
IO_intValue, &
|
||||
IO_warning, &
|
||||
IO_error, &
|
||||
IO_timeStamp, &
|
||||
IO_EOF
|
||||
use material, only: &
|
||||
hydrogenflux_type, &
|
||||
hydrogenflux_typeInstance, &
|
||||
homogenization_Noutput, &
|
||||
HYDROGENFLUX_cahnhilliard_label, &
|
||||
HYDROGENFLUX_cahnhilliard_ID, &
|
||||
material_homog, &
|
||||
mappingHomogenization, &
|
||||
hydrogenfluxState, &
|
||||
hydrogenfluxMapping, &
|
||||
hydrogenConc, &
|
||||
hydrogenConcRate, &
|
||||
hydrogenflux_initialCh
|
||||
use config, only: &
|
||||
material_partHomogenization, &
|
||||
material_partPhase
|
||||
|
||||
implicit none
|
||||
integer(pInt), intent(in) :: fileUnit
|
||||
|
||||
integer(pInt), allocatable, dimension(:) :: chunkPos
|
||||
integer(pInt) :: maxNinstance,mySize=0_pInt,section,instance,o
|
||||
integer(pInt) :: sizeState
|
||||
integer(pInt) :: NofMyHomog
|
||||
character(len=65536) :: &
|
||||
tag = '', &
|
||||
line = ''
|
||||
|
||||
write(6,'(/,a)') ' <<<+- hydrogenflux_'//HYDROGENFLUX_cahnhilliard_label//' init -+>>>'
|
||||
write(6,'(a15,a)') ' Current time: ',IO_timeStamp()
|
||||
#include "compilation_info.f90"
|
||||
|
||||
maxNinstance = int(count(hydrogenflux_type == HYDROGENFLUX_cahnhilliard_ID),pInt)
|
||||
if (maxNinstance == 0_pInt) return
|
||||
|
||||
allocate(hydrogenflux_cahnhilliard_sizePostResults(maxNinstance), source=0_pInt)
|
||||
allocate(hydrogenflux_cahnhilliard_sizePostResult (maxval(homogenization_Noutput),maxNinstance),source=0_pInt)
|
||||
allocate(hydrogenflux_cahnhilliard_output (maxval(homogenization_Noutput),maxNinstance))
|
||||
hydrogenflux_cahnhilliard_output = ''
|
||||
allocate(hydrogenflux_cahnhilliard_outputID (maxval(homogenization_Noutput),maxNinstance),source=undefined_ID)
|
||||
allocate(hydrogenflux_cahnhilliard_Noutput (maxNinstance), source=0_pInt)
|
||||
|
||||
rewind(fileUnit)
|
||||
section = 0_pInt
|
||||
do while (trim(line) /= IO_EOF .and. IO_lc(IO_getTag(line,'<','>')) /= material_partHomogenization)! wind forward to <homogenization>
|
||||
line = IO_read(fileUnit)
|
||||
enddo
|
||||
|
||||
parsingHomog: do while (trim(line) /= IO_EOF) ! read through sections of homog part
|
||||
line = IO_read(fileUnit)
|
||||
if (IO_isBlank(line)) cycle ! skip empty lines
|
||||
if (IO_getTag(line,'<','>') /= '') then ! stop at next part
|
||||
line = IO_read(fileUnit, .true.) ! reset IO_read
|
||||
exit
|
||||
endif
|
||||
if (IO_getTag(line,'[',']') /= '') then ! next homog section
|
||||
section = section + 1_pInt ! advance homog section counter
|
||||
cycle ! skip to next line
|
||||
endif
|
||||
|
||||
if (section > 0_pInt ) then; if (hydrogenflux_type(section) == HYDROGENFLUX_cahnhilliard_ID) then ! do not short-circuit here (.and. with next if statemen). It's not safe in Fortran
|
||||
|
||||
instance = hydrogenflux_typeInstance(section) ! which instance of my hydrogenflux is present homog
|
||||
chunkPos = IO_stringPos(line)
|
||||
tag = IO_lc(IO_stringValue(line,chunkPos,1_pInt)) ! extract key
|
||||
select case(tag)
|
||||
case ('(output)')
|
||||
select case(IO_lc(IO_stringValue(line,chunkPos,2_pInt)))
|
||||
case ('hydrogenconc')
|
||||
hydrogenflux_cahnhilliard_Noutput(instance) = hydrogenflux_cahnhilliard_Noutput(instance) + 1_pInt
|
||||
hydrogenflux_cahnhilliard_outputID(hydrogenflux_cahnhilliard_Noutput(instance),instance) = hydrogenConc_ID
|
||||
hydrogenflux_cahnhilliard_output(hydrogenflux_cahnhilliard_Noutput(instance),instance) = &
|
||||
IO_lc(IO_stringValue(line,chunkPos,2_pInt))
|
||||
end select
|
||||
|
||||
end select
|
||||
endif; endif
|
||||
enddo parsingHomog
|
||||
|
||||
rewind(fileUnit)
|
||||
section = 0_pInt
|
||||
do while (trim(line) /= IO_EOF .and. IO_lc(IO_getTag(line,'<','>')) /= material_partPhase) ! wind forward to <homogenization>
|
||||
line = IO_read(fileUnit)
|
||||
enddo
|
||||
|
||||
initializeInstances: do section = 1_pInt, size(hydrogenflux_type)
|
||||
if (hydrogenflux_type(section) == HYDROGENFLUX_cahnhilliard_ID) then
|
||||
NofMyHomog=count(material_homog==section)
|
||||
instance = hydrogenflux_typeInstance(section)
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
! Determine size of postResults array
|
||||
outputsLoop: do o = 1_pInt,hydrogenflux_cahnhilliard_Noutput(instance)
|
||||
select case(hydrogenflux_cahnhilliard_outputID(o,instance))
|
||||
case(hydrogenConc_ID)
|
||||
mySize = 1_pInt
|
||||
end select
|
||||
|
||||
if (mySize > 0_pInt) then ! any meaningful output found
|
||||
hydrogenflux_cahnhilliard_sizePostResult(o,instance) = mySize
|
||||
hydrogenflux_cahnhilliard_sizePostResults(instance) = hydrogenflux_cahnhilliard_sizePostResults(instance) + mySize
|
||||
endif
|
||||
enddo outputsLoop
|
||||
|
||||
! allocate state arrays
|
||||
sizeState = 0_pInt
|
||||
hydrogenfluxState(section)%sizeState = sizeState
|
||||
hydrogenfluxState(section)%sizePostResults = hydrogenflux_cahnhilliard_sizePostResults(instance)
|
||||
allocate(hydrogenfluxState(section)%state0 (sizeState,NofMyHomog))
|
||||
allocate(hydrogenfluxState(section)%subState0(sizeState,NofMyHomog))
|
||||
allocate(hydrogenfluxState(section)%state (sizeState,NofMyHomog))
|
||||
|
||||
nullify(hydrogenfluxMapping(section)%p)
|
||||
hydrogenfluxMapping(section)%p => mappingHomogenization(1,:,:)
|
||||
deallocate(hydrogenConc (section)%p)
|
||||
deallocate(hydrogenConcRate(section)%p)
|
||||
allocate (hydrogenConc (section)%p(NofMyHomog), source=hydrogenflux_initialCh(section))
|
||||
allocate (hydrogenConcRate(section)%p(NofMyHomog), source=0.0_pReal)
|
||||
|
||||
endif
|
||||
|
||||
enddo initializeInstances
|
||||
|
||||
end subroutine hydrogenflux_cahnhilliard_init
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief returns homogenized solute mobility tensor in reference configuration
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
function hydrogenflux_cahnhilliard_getMobility33(ip,el)
|
||||
use lattice, only: &
|
||||
lattice_hydrogenfluxMobility33
|
||||
use material, only: &
|
||||
homogenization_Ngrains, &
|
||||
material_phase
|
||||
use mesh, only: &
|
||||
mesh_element
|
||||
use crystallite, only: &
|
||||
crystallite_push33ToRef
|
||||
|
||||
implicit none
|
||||
integer(pInt), intent(in) :: &
|
||||
ip, & !< integration point number
|
||||
el !< element number
|
||||
real(pReal), dimension(3,3) :: &
|
||||
hydrogenflux_cahnhilliard_getMobility33
|
||||
integer(pInt) :: &
|
||||
grain
|
||||
|
||||
hydrogenflux_cahnhilliard_getMobility33 = 0.0_pReal
|
||||
do grain = 1, homogenization_Ngrains(mesh_element(3,el))
|
||||
hydrogenflux_cahnhilliard_getMobility33 = hydrogenflux_cahnhilliard_getMobility33 + &
|
||||
crystallite_push33ToRef(grain,ip,el,lattice_hydrogenfluxMobility33(:,:,material_phase(grain,ip,el)))
|
||||
enddo
|
||||
|
||||
hydrogenflux_cahnhilliard_getMobility33 = &
|
||||
hydrogenflux_cahnhilliard_getMobility33/real(homogenization_Ngrains(mesh_element(3,el)),pReal)
|
||||
|
||||
end function hydrogenflux_cahnhilliard_getMobility33
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief returns homogenized solute nonlocal diffusion tensor in reference configuration
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
function hydrogenflux_cahnhilliard_getDiffusion33(ip,el)
|
||||
use lattice, only: &
|
||||
lattice_hydrogenfluxDiffusion33
|
||||
use material, only: &
|
||||
homogenization_Ngrains, &
|
||||
material_phase
|
||||
use mesh, only: &
|
||||
mesh_element
|
||||
use crystallite, only: &
|
||||
crystallite_push33ToRef
|
||||
|
||||
implicit none
|
||||
integer(pInt), intent(in) :: &
|
||||
ip, & !< integration point number
|
||||
el !< element number
|
||||
real(pReal), dimension(3,3) :: &
|
||||
hydrogenflux_cahnhilliard_getDiffusion33
|
||||
integer(pInt) :: &
|
||||
grain
|
||||
|
||||
hydrogenflux_cahnhilliard_getDiffusion33 = 0.0_pReal
|
||||
do grain = 1, homogenization_Ngrains(mesh_element(3,el))
|
||||
hydrogenflux_cahnhilliard_getDiffusion33 = hydrogenflux_cahnhilliard_getDiffusion33 + &
|
||||
crystallite_push33ToRef(grain,ip,el,lattice_hydrogenfluxDiffusion33(:,:,material_phase(grain,ip,el)))
|
||||
enddo
|
||||
|
||||
hydrogenflux_cahnhilliard_getDiffusion33 = &
|
||||
hydrogenflux_cahnhilliard_getDiffusion33/real(homogenization_Ngrains(mesh_element(3,el)),pReal)
|
||||
|
||||
end function hydrogenflux_cahnhilliard_getDiffusion33
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief returns homogenized solution energy
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
function hydrogenflux_cahnhilliard_getFormationEnergy(ip,el)
|
||||
use lattice, only: &
|
||||
lattice_hydrogenFormationEnergy, &
|
||||
lattice_hydrogenVol, &
|
||||
lattice_hydrogenSurfaceEnergy
|
||||
use material, only: &
|
||||
homogenization_Ngrains, &
|
||||
material_phase
|
||||
use mesh, only: &
|
||||
mesh_element
|
||||
|
||||
implicit none
|
||||
integer(pInt), intent(in) :: &
|
||||
ip, & !< integration point number
|
||||
el !< element number
|
||||
real(pReal) :: &
|
||||
hydrogenflux_cahnhilliard_getFormationEnergy
|
||||
integer(pInt) :: &
|
||||
grain
|
||||
|
||||
hydrogenflux_cahnhilliard_getFormationEnergy = 0.0_pReal
|
||||
do grain = 1, homogenization_Ngrains(mesh_element(3,el))
|
||||
hydrogenflux_cahnhilliard_getFormationEnergy = hydrogenflux_cahnhilliard_getFormationEnergy + &
|
||||
lattice_hydrogenFormationEnergy(material_phase(grain,ip,el))/ &
|
||||
lattice_hydrogenVol(material_phase(grain,ip,el))/ &
|
||||
lattice_hydrogenSurfaceEnergy(material_phase(grain,ip,el))
|
||||
enddo
|
||||
|
||||
hydrogenflux_cahnhilliard_getFormationEnergy = &
|
||||
hydrogenflux_cahnhilliard_getFormationEnergy/real(homogenization_Ngrains(mesh_element(3,el)),pReal)
|
||||
|
||||
end function hydrogenflux_cahnhilliard_getFormationEnergy
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief returns homogenized hydrogen entropy coefficient
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
function hydrogenflux_cahnhilliard_getEntropicCoeff(ip,el)
|
||||
use lattice, only: &
|
||||
lattice_hydrogenVol, &
|
||||
lattice_hydrogenSurfaceEnergy
|
||||
use material, only: &
|
||||
homogenization_Ngrains, &
|
||||
material_homog, &
|
||||
material_phase, &
|
||||
temperature, &
|
||||
thermalMapping
|
||||
|
||||
implicit none
|
||||
integer(pInt), intent(in) :: &
|
||||
ip, & !< integration point number
|
||||
el !< element number
|
||||
real(pReal) :: &
|
||||
hydrogenflux_cahnhilliard_getEntropicCoeff
|
||||
integer(pInt) :: &
|
||||
grain
|
||||
|
||||
hydrogenflux_cahnhilliard_getEntropicCoeff = 0.0_pReal
|
||||
do grain = 1, homogenization_Ngrains(material_homog(ip,el))
|
||||
hydrogenflux_cahnhilliard_getEntropicCoeff = hydrogenflux_cahnhilliard_getEntropicCoeff + &
|
||||
kB/ &
|
||||
lattice_hydrogenVol(material_phase(grain,ip,el))/ &
|
||||
lattice_hydrogenSurfaceEnergy(material_phase(grain,ip,el))
|
||||
enddo
|
||||
|
||||
hydrogenflux_cahnhilliard_getEntropicCoeff = hydrogenflux_cahnhilliard_getEntropicCoeff* &
|
||||
temperature(material_homog(ip,el))%p(thermalMapping(material_homog(ip,el))%p(ip,el))/ &
|
||||
real(homogenization_Ngrains(material_homog(ip,el)),pReal)
|
||||
|
||||
end function hydrogenflux_cahnhilliard_getEntropicCoeff
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief returns homogenized kinematic contribution to chemical potential
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine hydrogenflux_cahnhilliard_KinematicChemPotAndItsTangent(KPot, dKPot_dCh, Ch, ip, el)
|
||||
use lattice, only: &
|
||||
lattice_hydrogenSurfaceEnergy
|
||||
use material, only: &
|
||||
homogenization_Ngrains, &
|
||||
material_homog, &
|
||||
phase_kinematics, &
|
||||
phase_Nkinematics, &
|
||||
material_phase, &
|
||||
KINEMATICS_hydrogen_strain_ID
|
||||
use crystallite, only: &
|
||||
crystallite_Tstar_v, &
|
||||
crystallite_Fi0, &
|
||||
crystallite_Fi
|
||||
use kinematics_hydrogen_strain, only: &
|
||||
kinematics_hydrogen_strain_ChemPotAndItsTangent
|
||||
|
||||
implicit none
|
||||
integer(pInt), intent(in) :: &
|
||||
ip, & !< integration point number
|
||||
el !< element number
|
||||
real(pReal), intent(in) :: &
|
||||
Ch
|
||||
real(pReal), intent(out) :: &
|
||||
KPot, dKPot_dCh
|
||||
real(pReal) :: &
|
||||
my_KPot, my_dKPot_dCh
|
||||
integer(pInt) :: &
|
||||
grain, kinematics
|
||||
|
||||
KPot = 0.0_pReal
|
||||
dKPot_dCh = 0.0_pReal
|
||||
do grain = 1_pInt,homogenization_Ngrains(material_homog(ip,el))
|
||||
do kinematics = 1_pInt, phase_Nkinematics(material_phase(grain,ip,el))
|
||||
select case (phase_kinematics(kinematics,material_phase(grain,ip,el)))
|
||||
case (KINEMATICS_hydrogen_strain_ID)
|
||||
call kinematics_hydrogen_strain_ChemPotAndItsTangent(my_KPot, my_dKPot_dCh, &
|
||||
crystallite_Tstar_v(1:6,grain,ip,el), &
|
||||
crystallite_Fi0(1:3,1:3,grain,ip,el), &
|
||||
crystallite_Fi (1:3,1:3,grain,ip,el), &
|
||||
grain,ip, el)
|
||||
|
||||
case default
|
||||
my_KPot = 0.0_pReal
|
||||
my_dKPot_dCh = 0.0_pReal
|
||||
|
||||
end select
|
||||
KPot = KPot + my_KPot/lattice_hydrogenSurfaceEnergy(material_phase(grain,ip,el))
|
||||
dKPot_dCh = dKPot_dCh + my_dKPot_dCh/lattice_hydrogenSurfaceEnergy(material_phase(grain,ip,el))
|
||||
enddo
|
||||
enddo
|
||||
|
||||
KPot = KPot/real(homogenization_Ngrains(material_homog(ip,el)),pReal)
|
||||
dKPot_dCh = dKPot_dCh/real(homogenization_Ngrains(material_homog(ip,el)),pReal)
|
||||
|
||||
end subroutine hydrogenflux_cahnhilliard_KinematicChemPotAndItsTangent
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief returns homogenized chemical potential
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine hydrogenflux_cahnhilliard_getChemPotAndItsTangent(ChemPot,dChemPot_dCh,Ch,ip,el)
|
||||
use numerics, only: &
|
||||
hydrogenBoundPenalty, &
|
||||
hydrogenPolyOrder
|
||||
|
||||
implicit none
|
||||
integer(pInt), intent(in) :: &
|
||||
ip, & !< integration point number
|
||||
el !< element number
|
||||
real(pReal), intent(in) :: &
|
||||
Ch
|
||||
real(pReal), intent(out) :: &
|
||||
ChemPot, &
|
||||
dChemPot_dCh
|
||||
real(pReal) :: &
|
||||
kBT, KPot, dKPot_dCh
|
||||
integer(pInt) :: &
|
||||
o
|
||||
|
||||
ChemPot = hydrogenflux_cahnhilliard_getFormationEnergy(ip,el)
|
||||
dChemPot_dCh = 0.0_pReal
|
||||
kBT = hydrogenflux_cahnhilliard_getEntropicCoeff(ip,el)
|
||||
do o = 1_pInt, hydrogenPolyOrder
|
||||
ChemPot = ChemPot + kBT*((2.0_pReal*Ch - 1.0_pReal)**real(2_pInt*o-1_pInt,pReal))/ &
|
||||
real(2_pInt*o-1_pInt,pReal)
|
||||
dChemPot_dCh = dChemPot_dCh + 2.0_pReal*kBT*(2.0_pReal*Ch - 1.0_pReal)**real(2_pInt*o-2_pInt,pReal)
|
||||
enddo
|
||||
|
||||
call hydrogenflux_cahnhilliard_KinematicChemPotAndItsTangent(KPot, dKPot_dCh, Ch, ip, el)
|
||||
ChemPot = ChemPot + KPot
|
||||
dChemPot_dCh = dChemPot_dCh + dKPot_dCh
|
||||
|
||||
if (Ch < 0.0_pReal) then
|
||||
ChemPot = ChemPot - 3.0_pReal*hydrogenBoundPenalty*Ch*Ch
|
||||
dChemPot_dCh = dChemPot_dCh - 6.0_pReal*hydrogenBoundPenalty*Ch
|
||||
elseif (Ch > 1.0_pReal) then
|
||||
ChemPot = ChemPot + 3.0_pReal*hydrogenBoundPenalty*(1.0_pReal - Ch)*(1.0_pReal - Ch)
|
||||
dChemPot_dCh = dChemPot_dCh - 6.0_pReal*hydrogenBoundPenalty*(1.0_pReal - Ch)
|
||||
endif
|
||||
|
||||
end subroutine hydrogenflux_cahnhilliard_getChemPotAndItsTangent
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief updates hydrogen concentration with solution from Cahn-Hilliard PDE for solute transport
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine hydrogenflux_cahnhilliard_putHydrogenConcAndItsRate(Ch,Chdot,ip,el)
|
||||
use material, only: &
|
||||
mappingHomogenization, &
|
||||
hydrogenConc, &
|
||||
hydrogenConcRate, &
|
||||
hydrogenfluxMapping
|
||||
|
||||
implicit none
|
||||
integer(pInt), intent(in) :: &
|
||||
ip, & !< integration point number
|
||||
el !< element number
|
||||
real(pReal), intent(in) :: &
|
||||
Ch, &
|
||||
Chdot
|
||||
integer(pInt) :: &
|
||||
homog, &
|
||||
offset
|
||||
|
||||
homog = mappingHomogenization(2,ip,el)
|
||||
offset = hydrogenfluxMapping(homog)%p(ip,el)
|
||||
hydrogenConc (homog)%p(offset) = Ch
|
||||
hydrogenConcRate(homog)%p(offset) = Chdot
|
||||
|
||||
end subroutine hydrogenflux_cahnhilliard_putHydrogenConcAndItsRate
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief return array of hydrogen transport results
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
function hydrogenflux_cahnhilliard_postResults(ip,el)
|
||||
use material, only: &
|
||||
mappingHomogenization, &
|
||||
hydrogenflux_typeInstance, &
|
||||
hydrogenConc, &
|
||||
hydrogenfluxMapping
|
||||
|
||||
implicit none
|
||||
integer(pInt), intent(in) :: &
|
||||
ip, & !< integration point
|
||||
el !< element
|
||||
real(pReal), dimension(hydrogenflux_cahnhilliard_sizePostResults(hydrogenflux_typeInstance(mappingHomogenization(2,ip,el)))) :: &
|
||||
hydrogenflux_cahnhilliard_postResults
|
||||
|
||||
integer(pInt) :: &
|
||||
instance, homog, offset, o, c
|
||||
|
||||
homog = mappingHomogenization(2,ip,el)
|
||||
offset = hydrogenfluxMapping(homog)%p(ip,el)
|
||||
instance = hydrogenflux_typeInstance(homog)
|
||||
|
||||
c = 0_pInt
|
||||
hydrogenflux_cahnhilliard_postResults = 0.0_pReal
|
||||
|
||||
do o = 1_pInt,hydrogenflux_cahnhilliard_Noutput(instance)
|
||||
select case(hydrogenflux_cahnhilliard_outputID(o,instance))
|
||||
|
||||
case (hydrogenConc_ID)
|
||||
hydrogenflux_cahnhilliard_postResults(c+1_pInt) = hydrogenConc(homog)%p(offset)
|
||||
c = c + 1
|
||||
end select
|
||||
enddo
|
||||
end function hydrogenflux_cahnhilliard_postResults
|
||||
|
||||
end module hydrogenflux_cahnhilliard
|
|
@ -1,62 +0,0 @@
|
|||
!--------------------------------------------------------------------------------------------------
|
||||
!> @author Pratheek Shanthraj, Max-Planck-Institut für Eisenforschung GmbH
|
||||
!> @brief material subroutine for constant hydrogen concentration
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
module hydrogenflux_isoconc
|
||||
|
||||
implicit none
|
||||
private
|
||||
|
||||
public :: &
|
||||
hydrogenflux_isoconc_init
|
||||
|
||||
contains
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief allocates all neccessary fields, reads information from material configuration file
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine hydrogenflux_isoconc_init()
|
||||
#if defined(__GFORTRAN__) || __INTEL_COMPILER >= 1800
|
||||
use, intrinsic :: iso_fortran_env, only: &
|
||||
compiler_version, &
|
||||
compiler_options
|
||||
#endif
|
||||
use prec, only: &
|
||||
pReal, &
|
||||
pInt
|
||||
use IO, only: &
|
||||
IO_timeStamp
|
||||
use material
|
||||
use config
|
||||
|
||||
implicit none
|
||||
integer(pInt) :: &
|
||||
homog, &
|
||||
NofMyHomog
|
||||
|
||||
write(6,'(/,a)') ' <<<+- hydrogenflux_'//HYDROGENFLUX_isoconc_label//' init -+>>>'
|
||||
write(6,'(a15,a)') ' Current time: ',IO_timeStamp()
|
||||
#include "compilation_info.f90"
|
||||
|
||||
initializeInstances: do homog = 1_pInt, material_Nhomogenization
|
||||
|
||||
myhomog: if (hydrogenflux_type(homog) == HYDROGENFLUX_isoconc_ID) then
|
||||
NofMyHomog = count(material_homog == homog)
|
||||
hydrogenfluxState(homog)%sizeState = 0_pInt
|
||||
hydrogenfluxState(homog)%sizePostResults = 0_pInt
|
||||
allocate(hydrogenfluxState(homog)%state0 (0_pInt,NofMyHomog), source=0.0_pReal)
|
||||
allocate(hydrogenfluxState(homog)%subState0(0_pInt,NofMyHomog), source=0.0_pReal)
|
||||
allocate(hydrogenfluxState(homog)%state (0_pInt,NofMyHomog), source=0.0_pReal)
|
||||
|
||||
deallocate(hydrogenConc (homog)%p)
|
||||
deallocate(hydrogenConcRate(homog)%p)
|
||||
allocate (hydrogenConc (homog)%p(1), source=hydrogenflux_initialCh(homog))
|
||||
allocate (hydrogenConcRate(homog)%p(1), source=0.0_pReal)
|
||||
|
||||
endif myhomog
|
||||
enddo initializeInstances
|
||||
|
||||
|
||||
end subroutine hydrogenflux_isoconc_init
|
||||
|
||||
end module hydrogenflux_isoconc
|
|
@ -1,263 +0,0 @@
|
|||
!--------------------------------------------------------------------------------------------------
|
||||
!> @author Pratheek Shanthraj, Max-Planck-Institut für Eisenforschung GmbH
|
||||
!> @brief material subroutine incorporating kinematics resulting from interstitial hydrogen
|
||||
!> @details to be done
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
module kinematics_hydrogen_strain
|
||||
use prec, only: &
|
||||
pReal, &
|
||||
pInt
|
||||
|
||||
implicit none
|
||||
private
|
||||
integer(pInt), dimension(:), allocatable, public, protected :: &
|
||||
kinematics_hydrogen_strain_sizePostResults, & !< cumulative size of post results
|
||||
kinematics_hydrogen_strain_offset, & !< which kinematics is my current damage mechanism?
|
||||
kinematics_hydrogen_strain_instance !< instance of damage kinematics mechanism
|
||||
|
||||
integer(pInt), dimension(:,:), allocatable, target, public :: &
|
||||
kinematics_hydrogen_strain_sizePostResult !< size of each post result output
|
||||
|
||||
character(len=64), dimension(:,:), allocatable, target, public :: &
|
||||
kinematics_hydrogen_strain_output !< name of each post result output
|
||||
|
||||
integer(pInt), dimension(:), allocatable, target, public :: &
|
||||
kinematics_hydrogen_strain_Noutput !< number of outputs per instance of this damage
|
||||
|
||||
real(pReal), dimension(:), allocatable, private :: &
|
||||
kinematics_hydrogen_strain_coeff
|
||||
|
||||
public :: &
|
||||
kinematics_hydrogen_strain_init, &
|
||||
kinematics_hydrogen_strain_initialStrain, &
|
||||
kinematics_hydrogen_strain_LiAndItsTangent, &
|
||||
kinematics_hydrogen_strain_ChemPotAndItsTangent
|
||||
|
||||
contains
|
||||
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief module initialization
|
||||
!> @details reads in material parameters, allocates arrays, and does sanity checks
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine kinematics_hydrogen_strain_init(fileUnit)
|
||||
#if defined(__GFORTRAN__) || __INTEL_COMPILER >= 1800
|
||||
use, intrinsic :: iso_fortran_env, only: &
|
||||
compiler_version, &
|
||||
compiler_options
|
||||
#endif
|
||||
use debug, only: &
|
||||
debug_level,&
|
||||
debug_constitutive,&
|
||||
debug_levelBasic
|
||||
use IO, only: &
|
||||
IO_read, &
|
||||
IO_lc, &
|
||||
IO_getTag, &
|
||||
IO_isBlank, &
|
||||
IO_stringPos, &
|
||||
IO_stringValue, &
|
||||
IO_floatValue, &
|
||||
IO_intValue, &
|
||||
IO_warning, &
|
||||
IO_error, &
|
||||
IO_timeStamp, &
|
||||
IO_EOF
|
||||
use material, only: &
|
||||
phase_kinematics, &
|
||||
phase_Nkinematics, &
|
||||
phase_Noutput, &
|
||||
KINEMATICS_hydrogen_strain_label, &
|
||||
KINEMATICS_hydrogen_strain_ID
|
||||
use config, only: &
|
||||
material_Nphase, &
|
||||
MATERIAL_partPhase
|
||||
|
||||
implicit none
|
||||
integer(pInt), intent(in) :: fileUnit
|
||||
|
||||
integer(pInt), allocatable, dimension(:) :: chunkPos
|
||||
integer(pInt) :: maxNinstance,phase,instance,kinematics
|
||||
character(len=65536) :: &
|
||||
tag = '', &
|
||||
line = ''
|
||||
|
||||
write(6,'(/,a)') ' <<<+- kinematics_'//KINEMATICS_hydrogen_strain_LABEL//' init -+>>>'
|
||||
write(6,'(a15,a)') ' Current time: ',IO_timeStamp()
|
||||
#include "compilation_info.f90"
|
||||
|
||||
maxNinstance = int(count(phase_kinematics == KINEMATICS_hydrogen_strain_ID),pInt)
|
||||
if (maxNinstance == 0_pInt) return
|
||||
|
||||
if (iand(debug_level(debug_constitutive),debug_levelBasic) /= 0_pInt) &
|
||||
write(6,'(a16,1x,i5,/)') '# instances:',maxNinstance
|
||||
|
||||
allocate(kinematics_hydrogen_strain_offset(material_Nphase), source=0_pInt)
|
||||
allocate(kinematics_hydrogen_strain_instance(material_Nphase), source=0_pInt)
|
||||
do phase = 1, material_Nphase
|
||||
kinematics_hydrogen_strain_instance(phase) = count(phase_kinematics(:,1:phase) == kinematics_hydrogen_strain_ID)
|
||||
do kinematics = 1, phase_Nkinematics(phase)
|
||||
if (phase_kinematics(kinematics,phase) == kinematics_hydrogen_strain_ID) &
|
||||
kinematics_hydrogen_strain_offset(phase) = kinematics
|
||||
enddo
|
||||
enddo
|
||||
|
||||
allocate(kinematics_hydrogen_strain_sizePostResults(maxNinstance), source=0_pInt)
|
||||
allocate(kinematics_hydrogen_strain_sizePostResult(maxval(phase_Noutput),maxNinstance),source=0_pInt)
|
||||
allocate(kinematics_hydrogen_strain_output(maxval(phase_Noutput),maxNinstance))
|
||||
kinematics_hydrogen_strain_output = ''
|
||||
allocate(kinematics_hydrogen_strain_Noutput(maxNinstance), source=0_pInt)
|
||||
allocate(kinematics_hydrogen_strain_coeff(maxNinstance), source=0.0_pReal)
|
||||
|
||||
rewind(fileUnit)
|
||||
phase = 0_pInt
|
||||
do while (trim(line) /= IO_EOF .and. IO_lc(IO_getTag(line,'<','>')) /= MATERIAL_partPhase) ! wind forward to <phase>
|
||||
line = IO_read(fileUnit)
|
||||
enddo
|
||||
|
||||
parsingFile: do while (trim(line) /= IO_EOF) ! read through sections of phase part
|
||||
line = IO_read(fileUnit)
|
||||
if (IO_isBlank(line)) cycle ! skip empty lines
|
||||
if (IO_getTag(line,'<','>') /= '') then ! stop at next part
|
||||
line = IO_read(fileUnit, .true.) ! reset IO_read
|
||||
exit
|
||||
endif
|
||||
if (IO_getTag(line,'[',']') /= '') then ! next phase section
|
||||
phase = phase + 1_pInt ! advance phase section counter
|
||||
cycle ! skip to next line
|
||||
endif
|
||||
if (phase > 0_pInt ) then; if (any(phase_kinematics(:,phase) == KINEMATICS_hydrogen_strain_ID)) then ! do not short-circuit here (.and. with next if statemen). It's not safe in Fortran
|
||||
instance = kinematics_hydrogen_strain_instance(phase) ! which instance of my damage is present phase
|
||||
chunkPos = IO_stringPos(line)
|
||||
tag = IO_lc(IO_stringValue(line,chunkPos,1_pInt)) ! extract key
|
||||
select case(tag)
|
||||
case ('hydrogen_strain_coeff')
|
||||
kinematics_hydrogen_strain_coeff(instance) = IO_floatValue(line,chunkPos,2_pInt)
|
||||
|
||||
end select
|
||||
endif; endif
|
||||
enddo parsingFile
|
||||
|
||||
end subroutine kinematics_hydrogen_strain_init
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief report initial hydrogen strain based on current hydrogen conc deviation from
|
||||
!> equillibrium (0)
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
pure function kinematics_hydrogen_strain_initialStrain(ipc, ip, el)
|
||||
use math, only: &
|
||||
math_I3
|
||||
use material, only: &
|
||||
material_phase, &
|
||||
material_homog, &
|
||||
hydrogenConc, &
|
||||
hydrogenfluxMapping
|
||||
use lattice, only: &
|
||||
lattice_equilibriumHydrogenConcentration
|
||||
|
||||
implicit none
|
||||
integer(pInt), intent(in) :: &
|
||||
ipc, & !< grain number
|
||||
ip, & !< integration point number
|
||||
el !< element number
|
||||
real(pReal), dimension(3,3) :: &
|
||||
kinematics_hydrogen_strain_initialStrain !< initial thermal strain (should be small strain, though)
|
||||
integer(pInt) :: &
|
||||
phase, &
|
||||
homog, offset, instance
|
||||
|
||||
phase = material_phase(ipc,ip,el)
|
||||
instance = kinematics_hydrogen_strain_instance(phase)
|
||||
homog = material_homog(ip,el)
|
||||
offset = hydrogenfluxMapping(homog)%p(ip,el)
|
||||
|
||||
kinematics_hydrogen_strain_initialStrain = &
|
||||
(hydrogenConc(homog)%p(offset) - lattice_equilibriumHydrogenConcentration(phase)) * &
|
||||
kinematics_hydrogen_strain_coeff(instance)* math_I3
|
||||
|
||||
end function kinematics_hydrogen_strain_initialStrain
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief contains the constitutive equation for calculating the velocity gradient
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine kinematics_hydrogen_strain_LiAndItsTangent(Li, dLi_dTstar3333, ipc, ip, el)
|
||||
use material, only: &
|
||||
material_phase, &
|
||||
material_homog, &
|
||||
hydrogenConc, &
|
||||
hydrogenConcRate, &
|
||||
hydrogenfluxMapping
|
||||
use math, only: &
|
||||
math_I3
|
||||
use lattice, only: &
|
||||
lattice_equilibriumHydrogenConcentration
|
||||
|
||||
implicit none
|
||||
integer(pInt), intent(in) :: &
|
||||
ipc, & !< grain number
|
||||
ip, & !< integration point number
|
||||
el !< element number
|
||||
real(pReal), intent(out), dimension(3,3) :: &
|
||||
Li !< thermal velocity gradient
|
||||
real(pReal), intent(out), dimension(3,3,3,3) :: &
|
||||
dLi_dTstar3333 !< derivative of Li with respect to Tstar (4th-order tensor)
|
||||
integer(pInt) :: &
|
||||
phase, &
|
||||
instance, &
|
||||
homog, offset
|
||||
real(pReal) :: &
|
||||
Ch, ChEq, ChDot
|
||||
|
||||
phase = material_phase(ipc,ip,el)
|
||||
instance = kinematics_hydrogen_strain_instance(phase)
|
||||
homog = material_homog(ip,el)
|
||||
offset = hydrogenfluxMapping(homog)%p(ip,el)
|
||||
Ch = hydrogenConc(homog)%p(offset)
|
||||
ChDot = hydrogenConcRate(homog)%p(offset)
|
||||
ChEq = lattice_equilibriumHydrogenConcentration(phase)
|
||||
|
||||
Li = ChDot*math_I3* &
|
||||
kinematics_hydrogen_strain_coeff(instance)/ &
|
||||
(1.0_pReal + kinematics_hydrogen_strain_coeff(instance)*(Ch - ChEq))
|
||||
dLi_dTstar3333 = 0.0_pReal
|
||||
|
||||
end subroutine kinematics_hydrogen_strain_LiAndItsTangent
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief contains the kinematic contribution to hydrogen chemical potential
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine kinematics_hydrogen_strain_ChemPotAndItsTangent(ChemPot, dChemPot_dCh, Tstar_v, Fi0, Fi, ipc, ip, el)
|
||||
use material, only: &
|
||||
material_phase
|
||||
use math, only: &
|
||||
math_inv33, &
|
||||
math_mul33x33, &
|
||||
math_Mandel6to33, &
|
||||
math_transpose33
|
||||
|
||||
implicit none
|
||||
integer(pInt), intent(in) :: &
|
||||
ipc, & !< grain number
|
||||
ip, & !< integration point number
|
||||
el !< element number
|
||||
real(pReal), intent(in), dimension(6) :: &
|
||||
Tstar_v
|
||||
real(pReal), intent(in), dimension(3,3) :: &
|
||||
Fi0, Fi
|
||||
real(pReal), intent(out) :: &
|
||||
ChemPot, dChemPot_dCh
|
||||
integer(pInt) :: &
|
||||
phase, &
|
||||
instance
|
||||
|
||||
phase = material_phase(ipc,ip,el)
|
||||
instance = kinematics_hydrogen_strain_instance(phase)
|
||||
|
||||
ChemPot = -kinematics_hydrogen_strain_coeff(instance)* &
|
||||
sum(math_mul33x33(Fi,math_Mandel6to33(Tstar_v))* &
|
||||
math_mul33x33(math_mul33x33(Fi,math_inv33(Fi0)),Fi))
|
||||
dChemPot_dCh = 0.0_pReal
|
||||
|
||||
end subroutine kinematics_hydrogen_strain_ChemPotAndItsTangent
|
||||
|
||||
end module kinematics_hydrogen_strain
|
|
@ -1,264 +0,0 @@
|
|||
!--------------------------------------------------------------------------------------------------
|
||||
!> @author Pratheek Shanthraj, Max-Planck-Institut für Eisenforschung GmbH
|
||||
!> @brief material subroutine incorporating kinematics resulting from vacancy point defects
|
||||
!> @details to be done
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
module kinematics_vacancy_strain
|
||||
use prec, only: &
|
||||
pReal, &
|
||||
pInt
|
||||
|
||||
implicit none
|
||||
private
|
||||
integer(pInt), dimension(:), allocatable, public, protected :: &
|
||||
kinematics_vacancy_strain_sizePostResults, & !< cumulative size of post results
|
||||
kinematics_vacancy_strain_offset, & !< which kinematics is my current damage mechanism?
|
||||
kinematics_vacancy_strain_instance !< instance of damage kinematics mechanism
|
||||
|
||||
integer(pInt), dimension(:,:), allocatable, target, public :: &
|
||||
kinematics_vacancy_strain_sizePostResult !< size of each post result output
|
||||
|
||||
character(len=64), dimension(:,:), allocatable, target, public :: &
|
||||
kinematics_vacancy_strain_output !< name of each post result output
|
||||
|
||||
integer(pInt), dimension(:), allocatable, target, public :: &
|
||||
kinematics_vacancy_strain_Noutput !< number of outputs per instance of this damage
|
||||
|
||||
real(pReal), dimension(:), allocatable, private :: &
|
||||
kinematics_vacancy_strain_coeff
|
||||
|
||||
public :: &
|
||||
kinematics_vacancy_strain_init, &
|
||||
kinematics_vacancy_strain_initialStrain, &
|
||||
kinematics_vacancy_strain_LiAndItsTangent, &
|
||||
kinematics_vacancy_strain_ChemPotAndItsTangent
|
||||
|
||||
contains
|
||||
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief module initialization
|
||||
!> @details reads in material parameters, allocates arrays, and does sanity checks
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine kinematics_vacancy_strain_init(fileUnit)
|
||||
#if defined(__GFORTRAN__) || __INTEL_COMPILER >= 1800
|
||||
use, intrinsic :: iso_fortran_env, only: &
|
||||
compiler_version, &
|
||||
compiler_options
|
||||
#endif
|
||||
use debug, only: &
|
||||
debug_level,&
|
||||
debug_constitutive,&
|
||||
debug_levelBasic
|
||||
use IO, only: &
|
||||
IO_read, &
|
||||
IO_lc, &
|
||||
IO_getTag, &
|
||||
IO_isBlank, &
|
||||
IO_stringPos, &
|
||||
IO_stringValue, &
|
||||
IO_floatValue, &
|
||||
IO_intValue, &
|
||||
IO_warning, &
|
||||
IO_error, &
|
||||
IO_timeStamp, &
|
||||
IO_EOF
|
||||
use material, only: &
|
||||
phase_kinematics, &
|
||||
phase_Nkinematics, &
|
||||
phase_Noutput, &
|
||||
KINEMATICS_vacancy_strain_label, &
|
||||
KINEMATICS_vacancy_strain_ID
|
||||
use config, only: &
|
||||
material_Nphase, &
|
||||
MATERIAL_partPhase
|
||||
|
||||
implicit none
|
||||
integer(pInt), intent(in) :: fileUnit
|
||||
|
||||
integer(pInt), allocatable, dimension(:) :: chunkPos
|
||||
integer(pInt) :: maxNinstance,phase,instance,kinematics
|
||||
character(len=65536) :: &
|
||||
tag = '', &
|
||||
line = ''
|
||||
|
||||
write(6,'(/,a)') ' <<<+- kinematics_'//KINEMATICS_vacancy_strain_LABEL//' init -+>>>'
|
||||
write(6,'(a15,a)') ' Current time: ',IO_timeStamp()
|
||||
#include "compilation_info.f90"
|
||||
|
||||
maxNinstance = int(count(phase_kinematics == KINEMATICS_vacancy_strain_ID),pInt)
|
||||
if (maxNinstance == 0_pInt) return
|
||||
|
||||
if (iand(debug_level(debug_constitutive),debug_levelBasic) /= 0_pInt) &
|
||||
write(6,'(a16,1x,i5,/)') '# instances:',maxNinstance
|
||||
|
||||
allocate(kinematics_vacancy_strain_offset(material_Nphase), source=0_pInt)
|
||||
allocate(kinematics_vacancy_strain_instance(material_Nphase), source=0_pInt)
|
||||
do phase = 1, material_Nphase
|
||||
kinematics_vacancy_strain_instance(phase) = count(phase_kinematics(:,1:phase) == kinematics_vacancy_strain_ID)
|
||||
do kinematics = 1, phase_Nkinematics(phase)
|
||||
if (phase_kinematics(kinematics,phase) == kinematics_vacancy_strain_ID) &
|
||||
kinematics_vacancy_strain_offset(phase) = kinematics
|
||||
enddo
|
||||
enddo
|
||||
|
||||
allocate(kinematics_vacancy_strain_sizePostResults(maxNinstance), source=0_pInt)
|
||||
allocate(kinematics_vacancy_strain_sizePostResult(maxval(phase_Noutput),maxNinstance),source=0_pInt)
|
||||
allocate(kinematics_vacancy_strain_output(maxval(phase_Noutput),maxNinstance))
|
||||
kinematics_vacancy_strain_output = ''
|
||||
allocate(kinematics_vacancy_strain_Noutput(maxNinstance), source=0_pInt)
|
||||
allocate(kinematics_vacancy_strain_coeff(maxNinstance), source=0.0_pReal)
|
||||
|
||||
rewind(fileUnit)
|
||||
phase = 0_pInt
|
||||
do while (trim(line) /= IO_EOF .and. IO_lc(IO_getTag(line,'<','>')) /= MATERIAL_partPhase) ! wind forward to <phase>
|
||||
line = IO_read(fileUnit)
|
||||
enddo
|
||||
|
||||
parsingFile: do while (trim(line) /= IO_EOF) ! read through sections of phase part
|
||||
line = IO_read(fileUnit)
|
||||
if (IO_isBlank(line)) cycle ! skip empty lines
|
||||
if (IO_getTag(line,'<','>') /= '') then ! stop at next part
|
||||
line = IO_read(fileUnit, .true.) ! reset IO_read
|
||||
exit
|
||||
endif
|
||||
if (IO_getTag(line,'[',']') /= '') then ! next phase section
|
||||
phase = phase + 1_pInt ! advance phase section counter
|
||||
cycle ! skip to next line
|
||||
endif
|
||||
if (phase > 0_pInt ) then; if (any(phase_kinematics(:,phase) == KINEMATICS_vacancy_strain_ID)) then ! do not short-circuit here (.and. with next if statemen). It's not safe in Fortran
|
||||
instance = kinematics_vacancy_strain_instance(phase) ! which instance of my damage is present phase
|
||||
chunkPos = IO_stringPos(line)
|
||||
tag = IO_lc(IO_stringValue(line,chunkPos,1_pInt)) ! extract key
|
||||
select case(tag)
|
||||
case ('vacancy_strain_coeff')
|
||||
kinematics_vacancy_strain_coeff(instance) = IO_floatValue(line,chunkPos,2_pInt)
|
||||
|
||||
end select
|
||||
endif; endif
|
||||
enddo parsingFile
|
||||
|
||||
end subroutine kinematics_vacancy_strain_init
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief report initial vacancy strain based on current vacancy conc deviation from equillibrium
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
pure function kinematics_vacancy_strain_initialStrain(ipc, ip, el)
|
||||
use math, only: &
|
||||
math_I3
|
||||
use material, only: &
|
||||
material_phase, &
|
||||
material_homog, &
|
||||
vacancyConc, &
|
||||
vacancyfluxMapping
|
||||
use lattice, only: &
|
||||
lattice_equilibriumVacancyConcentration
|
||||
|
||||
implicit none
|
||||
integer(pInt), intent(in) :: &
|
||||
ipc, & !< grain number
|
||||
ip, & !< integration point number
|
||||
el !< element number
|
||||
real(pReal), dimension(3,3) :: &
|
||||
kinematics_vacancy_strain_initialStrain !< initial thermal strain (should be small strain, though)
|
||||
integer(pInt) :: &
|
||||
phase, &
|
||||
homog, offset, instance
|
||||
|
||||
phase = material_phase(ipc,ip,el)
|
||||
instance = kinematics_vacancy_strain_instance(phase)
|
||||
homog = material_homog(ip,el)
|
||||
offset = vacancyfluxMapping(homog)%p(ip,el)
|
||||
|
||||
kinematics_vacancy_strain_initialStrain = &
|
||||
(vacancyConc(homog)%p(offset) - lattice_equilibriumVacancyConcentration(phase)) * &
|
||||
kinematics_vacancy_strain_coeff(instance)* math_I3
|
||||
|
||||
end function kinematics_vacancy_strain_initialStrain
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief contains the constitutive equation for calculating the velocity gradient
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine kinematics_vacancy_strain_LiAndItsTangent(Li, dLi_dTstar3333, ipc, ip, el)
|
||||
use material, only: &
|
||||
material_phase, &
|
||||
material_homog, &
|
||||
vacancyConc, &
|
||||
vacancyConcRate, &
|
||||
vacancyfluxMapping
|
||||
use math, only: &
|
||||
math_I3
|
||||
use lattice, only: &
|
||||
lattice_equilibriumVacancyConcentration
|
||||
|
||||
implicit none
|
||||
integer(pInt), intent(in) :: &
|
||||
ipc, & !< grain number
|
||||
ip, & !< integration point number
|
||||
el !< element number
|
||||
real(pReal), intent(out), dimension(3,3) :: &
|
||||
Li !< thermal velocity gradient
|
||||
real(pReal), intent(out), dimension(3,3,3,3) :: &
|
||||
dLi_dTstar3333 !< derivative of Li with respect to Tstar (4th-order tensor)
|
||||
integer(pInt) :: &
|
||||
phase, &
|
||||
instance, &
|
||||
homog, offset
|
||||
real(pReal) :: &
|
||||
Cv, CvEq, CvDot
|
||||
|
||||
phase = material_phase(ipc,ip,el)
|
||||
instance = kinematics_vacancy_strain_instance(phase)
|
||||
homog = material_homog(ip,el)
|
||||
offset = vacancyfluxMapping(homog)%p(ip,el)
|
||||
|
||||
Cv = vacancyConc(homog)%p(offset)
|
||||
CvDot = vacancyConcRate(homog)%p(offset)
|
||||
CvEq = lattice_equilibriumvacancyConcentration(phase)
|
||||
|
||||
Li = CvDot*math_I3* &
|
||||
kinematics_vacancy_strain_coeff(instance)/ &
|
||||
(1.0_pReal + kinematics_vacancy_strain_coeff(instance)*(Cv - CvEq))
|
||||
|
||||
dLi_dTstar3333 = 0.0_pReal
|
||||
|
||||
end subroutine kinematics_vacancy_strain_LiAndItsTangent
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief contains the kinematic contribution to vacancy chemical potential
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine kinematics_vacancy_strain_ChemPotAndItsTangent(ChemPot, dChemPot_dCv, Tstar_v, Fi0, Fi, ipc, ip, el)
|
||||
use material, only: &
|
||||
material_phase
|
||||
use math, only: &
|
||||
math_inv33, &
|
||||
math_mul33x33, &
|
||||
math_Mandel6to33, &
|
||||
math_transpose33
|
||||
|
||||
implicit none
|
||||
integer(pInt), intent(in) :: &
|
||||
ipc, & !< grain number
|
||||
ip, & !< integration point number
|
||||
el !< element number
|
||||
real(pReal), intent(in), dimension(6) :: &
|
||||
Tstar_v
|
||||
real(pReal), intent(in), dimension(3,3) :: &
|
||||
Fi0, Fi
|
||||
real(pReal), intent(out) :: &
|
||||
ChemPot, dChemPot_dCv
|
||||
integer(pInt) :: &
|
||||
phase, &
|
||||
instance
|
||||
|
||||
phase = material_phase(ipc,ip,el)
|
||||
instance = kinematics_vacancy_strain_instance(phase)
|
||||
|
||||
ChemPot = -kinematics_vacancy_strain_coeff(instance)* &
|
||||
sum(math_mul33x33(Fi,math_Mandel6to33(Tstar_v))* &
|
||||
math_mul33x33(math_mul33x33(Fi,math_inv33(Fi0)),Fi))
|
||||
dChemPot_dCv = 0.0_pReal
|
||||
|
||||
end subroutine kinematics_vacancy_strain_ChemPotAndItsTangent
|
||||
|
||||
end module kinematics_vacancy_strain
|
|
@ -40,15 +40,12 @@ module material
|
|||
KINEMATICS_cleavage_opening_label = 'cleavage_opening', &
|
||||
KINEMATICS_slipplane_opening_label = 'slipplane_opening', &
|
||||
STIFFNESS_DEGRADATION_damage_label = 'damage', &
|
||||
STIFFNESS_DEGRADATION_porosity_label = 'porosity', &
|
||||
THERMAL_isothermal_label = 'isothermal', &
|
||||
THERMAL_adiabatic_label = 'adiabatic', &
|
||||
THERMAL_conduction_label = 'conduction', &
|
||||
DAMAGE_none_label = 'none', &
|
||||
DAMAGE_local_label = 'local', &
|
||||
DAMAGE_nonlocal_label = 'nonlocal', &
|
||||
POROSITY_none_label = 'none', &
|
||||
POROSITY_phasefield_label = 'phasefield', &
|
||||
HOMOGENIZATION_none_label = 'none', &
|
||||
HOMOGENIZATION_isostrain_label = 'isostrain', &
|
||||
HOMOGENIZATION_rgc_label = 'rgc'
|
||||
|
@ -89,8 +86,7 @@ module material
|
|||
|
||||
enum, bind(c)
|
||||
enumerator :: STIFFNESS_DEGRADATION_undefined_ID, &
|
||||
STIFFNESS_DEGRADATION_damage_ID, &
|
||||
STIFFNESS_DEGRADATION_porosity_ID
|
||||
STIFFNESS_DEGRADATION_damage_ID
|
||||
end enum
|
||||
|
||||
enum, bind(c)
|
||||
|
@ -105,12 +101,6 @@ module material
|
|||
DAMAGE_nonlocal_ID
|
||||
end enum
|
||||
|
||||
enum, bind(c)
|
||||
enumerator :: POROSITY_none_ID, &
|
||||
POROSITY_phasefield_ID
|
||||
end enum
|
||||
|
||||
|
||||
enum, bind(c)
|
||||
enumerator :: HOMOGENIZATION_undefined_ID, &
|
||||
HOMOGENIZATION_none_ID, &
|
||||
|
@ -126,8 +116,6 @@ module material
|
|||
thermal_type !< thermal transport model
|
||||
integer(kind(DAMAGE_none_ID)), dimension(:), allocatable, public, protected :: &
|
||||
damage_type !< nonlocal damage model
|
||||
integer(kind(POROSITY_none_ID)), dimension(:), allocatable, public, protected :: &
|
||||
porosity_type !< porosity evolution model
|
||||
|
||||
integer(kind(SOURCE_undefined_ID)), dimension(:,:), allocatable, public, protected :: &
|
||||
phase_source, & !< active sources mechanisms of each phase
|
||||
|
@ -153,13 +141,11 @@ module material
|
|||
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
|
||||
porosity_typeInstance, & !< instance of particular type of each porosity model
|
||||
microstructure_crystallite !< crystallite setting ID of each microstructure ! DEPRECATED !!!!
|
||||
|
||||
real(pReal), dimension(:), allocatable, public, protected :: &
|
||||
thermal_initialT, & !< initial temperature per each homogenization
|
||||
damage_initialPhi, & !< initial damage per each homogenization
|
||||
porosity_initialPhi !< initial posority per each homogenization
|
||||
damage_initialPhi !< initial damage per each homogenization
|
||||
|
||||
! NEW MAPPINGS
|
||||
integer(pInt), dimension(:), allocatable, public, protected :: &
|
||||
|
@ -189,8 +175,7 @@ module material
|
|||
type(tState), allocatable, dimension(:), public :: &
|
||||
homogState, &
|
||||
thermalState, &
|
||||
damageState, &
|
||||
porosityState
|
||||
damageState
|
||||
|
||||
integer(pInt), dimension(:,:,:), allocatable, public, protected :: &
|
||||
material_texture !< texture (index) of each grain,IP,element
|
||||
|
@ -240,13 +225,11 @@ module material
|
|||
|
||||
type(tHomogMapping), allocatable, dimension(:), public :: &
|
||||
thermalMapping, & !< mapping for thermal state/fields
|
||||
damageMapping, & !< mapping for damage state/fields
|
||||
porosityMapping !< mapping for porosity state/fields
|
||||
damageMapping !< mapping for damage state/fields
|
||||
|
||||
type(group_float), allocatable, dimension(:), public :: &
|
||||
temperature, & !< temperature field
|
||||
damage, & !< damage field
|
||||
porosity, & !< porosity field
|
||||
temperatureRate !< temperature change rate field
|
||||
|
||||
public :: &
|
||||
|
@ -270,15 +253,12 @@ module material
|
|||
KINEMATICS_slipplane_opening_ID, &
|
||||
KINEMATICS_thermal_expansion_ID, &
|
||||
STIFFNESS_DEGRADATION_damage_ID, &
|
||||
STIFFNESS_DEGRADATION_porosity_ID, &
|
||||
THERMAL_isothermal_ID, &
|
||||
THERMAL_adiabatic_ID, &
|
||||
THERMAL_conduction_ID, &
|
||||
DAMAGE_none_ID, &
|
||||
DAMAGE_local_ID, &
|
||||
DAMAGE_nonlocal_ID, &
|
||||
POROSITY_none_ID, &
|
||||
POROSITY_phasefield_ID, &
|
||||
HOMOGENIZATION_none_ID, &
|
||||
HOMOGENIZATION_isostrain_ID, &
|
||||
HOMOGENIZATION_RGC_ID
|
||||
|
@ -370,15 +350,12 @@ subroutine material_init()
|
|||
allocate(homogState (size(config_homogenization)))
|
||||
allocate(thermalState (size(config_homogenization)))
|
||||
allocate(damageState (size(config_homogenization)))
|
||||
allocate(porosityState (size(config_homogenization)))
|
||||
|
||||
allocate(thermalMapping (size(config_homogenization)))
|
||||
allocate(damageMapping (size(config_homogenization)))
|
||||
allocate(porosityMapping (size(config_homogenization)))
|
||||
|
||||
allocate(temperature (size(config_homogenization)))
|
||||
allocate(damage (size(config_homogenization)))
|
||||
allocate(porosity (size(config_homogenization)))
|
||||
|
||||
allocate(temperatureRate (size(config_homogenization)))
|
||||
|
||||
|
@ -453,10 +430,8 @@ subroutine material_init()
|
|||
do myHomog = 1,size(config_homogenization)
|
||||
thermalMapping (myHomog)%p => mappingHomogenizationConst
|
||||
damageMapping (myHomog)%p => mappingHomogenizationConst
|
||||
porosityMapping (myHomog)%p => mappingHomogenizationConst
|
||||
allocate(temperature (myHomog)%p(1), source=thermal_initialT(myHomog))
|
||||
allocate(damage (myHomog)%p(1), source=damage_initialPhi(myHomog))
|
||||
allocate(porosity (myHomog)%p(1), source=porosity_initialPhi(myHomog))
|
||||
allocate(temperatureRate (myHomog)%p(1), source=0.0_pReal)
|
||||
enddo
|
||||
|
||||
|
@ -481,17 +456,14 @@ subroutine material_parseHomogenization
|
|||
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)
|
||||
allocate(porosity_type (size(config_homogenization)), source=POROSITY_none_ID)
|
||||
allocate(homogenization_typeInstance(size(config_homogenization)), source=0_pInt)
|
||||
allocate(thermal_typeInstance(size(config_homogenization)), source=0_pInt)
|
||||
allocate(damage_typeInstance(size(config_homogenization)), source=0_pInt)
|
||||
allocate(porosity_typeInstance(size(config_homogenization)), source=0_pInt)
|
||||
allocate(homogenization_Ngrains(size(config_homogenization)), source=0_pInt)
|
||||
allocate(homogenization_Noutput(size(config_homogenization)), source=0_pInt)
|
||||
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)
|
||||
allocate(porosity_initialPhi(size(config_homogenization)), source=1.0_pReal)
|
||||
|
||||
forall (h = 1_pInt:size(config_homogenization)) &
|
||||
homogenization_active(h) = any(mesh_homogenizationAt == h)
|
||||
|
@ -550,25 +522,6 @@ subroutine material_parseHomogenization
|
|||
end select
|
||||
|
||||
endif
|
||||
|
||||
|
||||
|
||||
if (config_homogenization(h)%keyExists('porosity')) then
|
||||
!ToDo?
|
||||
|
||||
tag = config_homogenization(h)%getString('porosity')
|
||||
select case (trim(tag))
|
||||
case(POROSITY_NONE_label)
|
||||
porosity_type(h) = POROSITY_none_ID
|
||||
case(POROSITY_phasefield_label)
|
||||
porosity_type(h) = POROSITY_phasefield_ID
|
||||
case default
|
||||
call IO_error(500_pInt,ext_msg=trim(tag))
|
||||
end select
|
||||
|
||||
endif
|
||||
|
||||
|
||||
|
||||
enddo
|
||||
|
||||
|
@ -576,7 +529,6 @@ subroutine material_parseHomogenization
|
|||
homogenization_typeInstance(h) = count(homogenization_type(1:h) == homogenization_type(h))
|
||||
thermal_typeInstance(h) = count(thermal_type (1:h) == thermal_type (h))
|
||||
damage_typeInstance(h) = count(damage_type (1:h) == damage_type (h))
|
||||
porosity_typeInstance(h) = count(porosity_type (1:h) == porosity_type (h))
|
||||
enddo
|
||||
|
||||
homogenization_maxNgrains = maxval(homogenization_Ngrains,homogenization_active)
|
||||
|
@ -797,8 +749,6 @@ subroutine material_parsePhase
|
|||
select case (trim(str(stiffDegradationCtr)))
|
||||
case (STIFFNESS_DEGRADATION_damage_label)
|
||||
phase_stiffnessDegradation(stiffDegradationCtr,p) = STIFFNESS_DEGRADATION_damage_ID
|
||||
case (STIFFNESS_DEGRADATION_porosity_label)
|
||||
phase_stiffnessDegradation(stiffDegradationCtr,p) = STIFFNESS_DEGRADATION_porosity_ID
|
||||
end select
|
||||
enddo
|
||||
enddo
|
||||
|
|
|
@ -1,60 +0,0 @@
|
|||
!--------------------------------------------------------------------------------------------------
|
||||
!> @author Pratheek Shanthraj, Max-Planck-Institut für Eisenforschung GmbH
|
||||
!> @brief material subroutine for constant porosity
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
module porosity_none
|
||||
|
||||
implicit none
|
||||
private
|
||||
|
||||
public :: &
|
||||
porosity_none_init
|
||||
|
||||
contains
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief allocates all neccessary fields, reads information from material configuration file
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine porosity_none_init()
|
||||
#if defined(__GFORTRAN__) || __INTEL_COMPILER >= 1800
|
||||
use, intrinsic :: iso_fortran_env, only: &
|
||||
compiler_version, &
|
||||
compiler_options
|
||||
#endif
|
||||
use prec, only: &
|
||||
pReal, &
|
||||
pInt
|
||||
use IO, only: &
|
||||
IO_timeStamp
|
||||
use material
|
||||
use config
|
||||
|
||||
implicit none
|
||||
integer(pInt) :: &
|
||||
homog, &
|
||||
NofMyHomog
|
||||
|
||||
write(6,'(/,a)') ' <<<+- porosity_'//POROSITY_none_label//' init -+>>>'
|
||||
write(6,'(a15,a)') ' Current time: ',IO_timeStamp()
|
||||
#include "compilation_info.f90"
|
||||
|
||||
initializeInstances: do homog = 1_pInt, material_Nhomogenization
|
||||
|
||||
myhomog: if (porosity_type(homog) == POROSITY_none_ID) then
|
||||
NofMyHomog = count(material_homog == homog)
|
||||
porosityState(homog)%sizeState = 0_pInt
|
||||
porosityState(homog)%sizePostResults = 0_pInt
|
||||
allocate(porosityState(homog)%state0 (0_pInt,NofMyHomog), source=0.0_pReal)
|
||||
allocate(porosityState(homog)%subState0(0_pInt,NofMyHomog), source=0.0_pReal)
|
||||
allocate(porosityState(homog)%state (0_pInt,NofMyHomog), source=0.0_pReal)
|
||||
|
||||
deallocate(porosity(homog)%p)
|
||||
allocate (porosity(homog)%p(1), source=porosity_initialPhi(homog))
|
||||
|
||||
endif myhomog
|
||||
enddo initializeInstances
|
||||
|
||||
|
||||
end subroutine porosity_none_init
|
||||
|
||||
end module porosity_none
|
|
@ -1,448 +0,0 @@
|
|||
!--------------------------------------------------------------------------------------------------
|
||||
!> @author Pratheek Shanthraj, Max-Planck-Institut für Eisenforschung GmbH
|
||||
!> @brief material subroutine for phase field modelling of pore nucleation and growth
|
||||
!> @details phase field model for pore nucleation and growth based on vacancy clustering
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
module porosity_phasefield
|
||||
use prec, only: &
|
||||
pReal, &
|
||||
pInt
|
||||
|
||||
implicit none
|
||||
private
|
||||
integer(pInt), dimension(:), allocatable, public, protected :: &
|
||||
porosity_phasefield_sizePostResults !< cumulative size of post results
|
||||
|
||||
integer(pInt), dimension(:,:), allocatable, target, public :: &
|
||||
porosity_phasefield_sizePostResult !< size of each post result output
|
||||
|
||||
character(len=64), dimension(:,:), allocatable, target, public :: &
|
||||
porosity_phasefield_output !< name of each post result output
|
||||
|
||||
integer(pInt), dimension(:), allocatable, target, public :: &
|
||||
porosity_phasefield_Noutput !< number of outputs per instance of this porosity
|
||||
|
||||
enum, bind(c)
|
||||
enumerator :: undefined_ID, &
|
||||
porosity_ID
|
||||
end enum
|
||||
integer(kind(undefined_ID)), dimension(:,:), allocatable, private :: &
|
||||
porosity_phasefield_outputID !< ID of each post result output
|
||||
|
||||
|
||||
public :: &
|
||||
porosity_phasefield_init, &
|
||||
porosity_phasefield_getFormationEnergy, &
|
||||
porosity_phasefield_getSurfaceEnergy, &
|
||||
porosity_phasefield_getSourceAndItsTangent, &
|
||||
porosity_phasefield_getDiffusion33, &
|
||||
porosity_phasefield_getMobility, &
|
||||
porosity_phasefield_putPorosity, &
|
||||
porosity_phasefield_postResults
|
||||
|
||||
contains
|
||||
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief module initialization
|
||||
!> @details reads in material parameters, allocates arrays, and does sanity checks
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine porosity_phasefield_init(fileUnit)
|
||||
#if defined(__GFORTRAN__) || __INTEL_COMPILER >= 1800
|
||||
use, intrinsic :: iso_fortran_env, only: &
|
||||
compiler_version, &
|
||||
compiler_options
|
||||
#endif
|
||||
use IO, only: &
|
||||
IO_read, &
|
||||
IO_lc, &
|
||||
IO_getTag, &
|
||||
IO_isBlank, &
|
||||
IO_stringPos, &
|
||||
IO_stringValue, &
|
||||
IO_floatValue, &
|
||||
IO_intValue, &
|
||||
IO_warning, &
|
||||
IO_error, &
|
||||
IO_timeStamp, &
|
||||
IO_EOF
|
||||
use material, only: &
|
||||
porosity_type, &
|
||||
porosity_typeInstance, &
|
||||
homogenization_Noutput, &
|
||||
POROSITY_phasefield_label, &
|
||||
POROSITY_phasefield_ID, &
|
||||
material_homog, &
|
||||
mappingHomogenization, &
|
||||
porosityState, &
|
||||
porosityMapping, &
|
||||
porosity, &
|
||||
porosity_initialPhi
|
||||
use config, only: &
|
||||
material_partHomogenization, &
|
||||
material_partPhase
|
||||
|
||||
implicit none
|
||||
integer(pInt), intent(in) :: fileUnit
|
||||
|
||||
integer(pInt), allocatable, dimension(:) :: chunkPos
|
||||
integer(pInt) :: maxNinstance,mySize=0_pInt,section,instance,o
|
||||
integer(pInt) :: sizeState
|
||||
integer(pInt) :: NofMyHomog
|
||||
character(len=65536) :: &
|
||||
tag = '', &
|
||||
line = ''
|
||||
|
||||
write(6,'(/,a)') ' <<<+- porosity_'//POROSITY_phasefield_label//' init -+>>>'
|
||||
write(6,'(a15,a)') ' Current time: ',IO_timeStamp()
|
||||
#include "compilation_info.f90"
|
||||
|
||||
maxNinstance = int(count(porosity_type == POROSITY_phasefield_ID),pInt)
|
||||
if (maxNinstance == 0_pInt) return
|
||||
|
||||
allocate(porosity_phasefield_sizePostResults(maxNinstance), source=0_pInt)
|
||||
allocate(porosity_phasefield_sizePostResult (maxval(homogenization_Noutput),maxNinstance),source=0_pInt)
|
||||
allocate(porosity_phasefield_output (maxval(homogenization_Noutput),maxNinstance))
|
||||
porosity_phasefield_output = ''
|
||||
allocate(porosity_phasefield_outputID (maxval(homogenization_Noutput),maxNinstance),source=undefined_ID)
|
||||
allocate(porosity_phasefield_Noutput (maxNinstance), source=0_pInt)
|
||||
|
||||
rewind(fileUnit)
|
||||
section = 0_pInt
|
||||
do while (trim(line) /= IO_EOF .and. IO_lc(IO_getTag(line,'<','>')) /= material_partHomogenization)! wind forward to <homogenization>
|
||||
line = IO_read(fileUnit)
|
||||
enddo
|
||||
|
||||
parsingHomog: do while (trim(line) /= IO_EOF) ! read through sections of homog part
|
||||
line = IO_read(fileUnit)
|
||||
if (IO_isBlank(line)) cycle ! skip empty lines
|
||||
if (IO_getTag(line,'<','>') /= '') then ! stop at next part
|
||||
line = IO_read(fileUnit, .true.) ! reset IO_read
|
||||
exit
|
||||
endif
|
||||
if (IO_getTag(line,'[',']') /= '') then ! next homog section
|
||||
section = section + 1_pInt ! advance homog section counter
|
||||
cycle ! skip to next line
|
||||
endif
|
||||
|
||||
if (section > 0_pInt ) then; if (porosity_type(section) == POROSITY_phasefield_ID) then ! do not short-circuit here (.and. with next if statemen). It's not safe in Fortran
|
||||
|
||||
instance = porosity_typeInstance(section) ! which instance of my porosity is present homog
|
||||
chunkPos = IO_stringPos(line)
|
||||
tag = IO_lc(IO_stringValue(line,chunkPos,1_pInt)) ! extract key
|
||||
select case(tag)
|
||||
case ('(output)')
|
||||
select case(IO_lc(IO_stringValue(line,chunkPos,2_pInt)))
|
||||
case ('porosity')
|
||||
porosity_phasefield_Noutput(instance) = porosity_phasefield_Noutput(instance) + 1_pInt
|
||||
porosity_phasefield_outputID(porosity_phasefield_Noutput(instance),instance) = porosity_ID
|
||||
porosity_phasefield_output(porosity_phasefield_Noutput(instance),instance) = &
|
||||
IO_lc(IO_stringValue(line,chunkPos,2_pInt))
|
||||
end select
|
||||
|
||||
end select
|
||||
endif; endif
|
||||
enddo parsingHomog
|
||||
|
||||
initializeInstances: do section = 1_pInt, size(porosity_type)
|
||||
if (porosity_type(section) == POROSITY_phasefield_ID) then
|
||||
NofMyHomog=count(material_homog==section)
|
||||
instance = porosity_typeInstance(section)
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
! Determine size of postResults array
|
||||
outputsLoop: do o = 1_pInt,porosity_phasefield_Noutput(instance)
|
||||
select case(porosity_phasefield_outputID(o,instance))
|
||||
case(porosity_ID)
|
||||
mySize = 1_pInt
|
||||
end select
|
||||
|
||||
if (mySize > 0_pInt) then ! any meaningful output found
|
||||
porosity_phasefield_sizePostResult(o,instance) = mySize
|
||||
porosity_phasefield_sizePostResults(instance) = porosity_phasefield_sizePostResults(instance) + mySize
|
||||
endif
|
||||
enddo outputsLoop
|
||||
|
||||
! allocate state arrays
|
||||
sizeState = 0_pInt
|
||||
porosityState(section)%sizeState = sizeState
|
||||
porosityState(section)%sizePostResults = porosity_phasefield_sizePostResults(instance)
|
||||
allocate(porosityState(section)%state0 (sizeState,NofMyHomog))
|
||||
allocate(porosityState(section)%subState0(sizeState,NofMyHomog))
|
||||
allocate(porosityState(section)%state (sizeState,NofMyHomog))
|
||||
|
||||
nullify(porosityMapping(section)%p)
|
||||
porosityMapping(section)%p => mappingHomogenization(1,:,:)
|
||||
deallocate(porosity(section)%p)
|
||||
allocate(porosity(section)%p(NofMyHomog), source=porosity_initialPhi(section))
|
||||
|
||||
endif
|
||||
|
||||
enddo initializeInstances
|
||||
end subroutine porosity_phasefield_init
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief returns homogenized vacancy formation energy
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
function porosity_phasefield_getFormationEnergy(ip,el)
|
||||
use lattice, only: &
|
||||
lattice_vacancyFormationEnergy, &
|
||||
lattice_vacancyVol
|
||||
use material, only: &
|
||||
homogenization_Ngrains, &
|
||||
material_phase
|
||||
use mesh, only: &
|
||||
mesh_element
|
||||
|
||||
implicit none
|
||||
integer(pInt), intent(in) :: &
|
||||
ip, & !< integration point number
|
||||
el !< element number
|
||||
real(pReal) :: &
|
||||
porosity_phasefield_getFormationEnergy
|
||||
integer(pInt) :: &
|
||||
grain
|
||||
|
||||
porosity_phasefield_getFormationEnergy = 0.0_pReal
|
||||
do grain = 1, homogenization_Ngrains(mesh_element(3,el))
|
||||
porosity_phasefield_getFormationEnergy = porosity_phasefield_getFormationEnergy + &
|
||||
lattice_vacancyFormationEnergy(material_phase(grain,ip,el))/ &
|
||||
lattice_vacancyVol(material_phase(grain,ip,el))
|
||||
enddo
|
||||
|
||||
porosity_phasefield_getFormationEnergy = &
|
||||
porosity_phasefield_getFormationEnergy/real(homogenization_Ngrains(mesh_element(3,el)),pReal)
|
||||
|
||||
end function porosity_phasefield_getFormationEnergy
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief returns homogenized pore surface energy (normalized by characteristic length)
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
function porosity_phasefield_getSurfaceEnergy(ip,el)
|
||||
use lattice, only: &
|
||||
lattice_vacancySurfaceEnergy
|
||||
use material, only: &
|
||||
homogenization_Ngrains, &
|
||||
material_phase
|
||||
use mesh, only: &
|
||||
mesh_element
|
||||
|
||||
implicit none
|
||||
integer(pInt), intent(in) :: &
|
||||
ip, & !< integration point number
|
||||
el !< element number
|
||||
real(pReal) :: &
|
||||
porosity_phasefield_getSurfaceEnergy
|
||||
integer(pInt) :: &
|
||||
grain
|
||||
|
||||
porosity_phasefield_getSurfaceEnergy = 0.0_pReal
|
||||
do grain = 1, homogenization_Ngrains(mesh_element(3,el))
|
||||
porosity_phasefield_getSurfaceEnergy = porosity_phasefield_getSurfaceEnergy + &
|
||||
lattice_vacancySurfaceEnergy(material_phase(grain,ip,el))
|
||||
enddo
|
||||
|
||||
porosity_phasefield_getSurfaceEnergy = &
|
||||
porosity_phasefield_getSurfaceEnergy/real(homogenization_Ngrains(mesh_element(3,el)),pReal)
|
||||
|
||||
end function porosity_phasefield_getSurfaceEnergy
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief calculates homogenized local driving force for pore nucleation and growth
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine porosity_phasefield_getSourceAndItsTangent(phiDot, dPhiDot_dPhi, phi, ip, el)
|
||||
use math, only : &
|
||||
math_mul33x33, &
|
||||
math_mul66x6, &
|
||||
math_Mandel33to6, &
|
||||
math_transpose33, &
|
||||
math_I3
|
||||
use material, only: &
|
||||
homogenization_Ngrains, &
|
||||
material_homog, &
|
||||
material_phase, &
|
||||
phase_NstiffnessDegradations, &
|
||||
phase_stiffnessDegradation, &
|
||||
vacancyConc, &
|
||||
vacancyfluxMapping, &
|
||||
damage, &
|
||||
damageMapping, &
|
||||
STIFFNESS_DEGRADATION_damage_ID
|
||||
use crystallite, only: &
|
||||
crystallite_Fe
|
||||
use constitutive, only: &
|
||||
constitutive_homogenizedC
|
||||
|
||||
implicit none
|
||||
integer(pInt), intent(in) :: &
|
||||
ip, & !< integration point number
|
||||
el !< element number
|
||||
real(pReal), intent(in) :: &
|
||||
phi
|
||||
integer(pInt) :: &
|
||||
phase, &
|
||||
grain, &
|
||||
homog, &
|
||||
mech
|
||||
real(pReal) :: &
|
||||
phiDot, dPhiDot_dPhi, Cv, W_e, strain(6), C(6,6)
|
||||
|
||||
homog = material_homog(ip,el)
|
||||
Cv = vacancyConc(homog)%p(vacancyfluxMapping(homog)%p(ip,el))
|
||||
|
||||
W_e = 0.0_pReal
|
||||
do grain = 1, homogenization_Ngrains(homog)
|
||||
phase = material_phase(grain,ip,el)
|
||||
strain = math_Mandel33to6(math_mul33x33(math_transpose33(crystallite_Fe(1:3,1:3,grain,ip,el)), &
|
||||
crystallite_Fe(1:3,1:3,grain,ip,el)) - math_I3)/2.0_pReal
|
||||
C = constitutive_homogenizedC(grain,ip,el)
|
||||
do mech = 1_pInt, phase_NstiffnessDegradations(phase)
|
||||
select case(phase_stiffnessDegradation(mech,phase))
|
||||
case (STIFFNESS_DEGRADATION_damage_ID)
|
||||
C = damage(homog)%p(damageMapping(homog)%p(ip,el))* &
|
||||
damage(homog)%p(damageMapping(homog)%p(ip,el))* &
|
||||
C
|
||||
|
||||
end select
|
||||
enddo
|
||||
W_e = W_e + sum(abs(strain*math_mul66x6(C,strain)))
|
||||
enddo
|
||||
W_e = W_e/real(homogenization_Ngrains(homog),pReal)
|
||||
|
||||
phiDot = 2.0_pReal*(1.0_pReal - phi)*(1.0_pReal - Cv)*(1.0_pReal - Cv) - &
|
||||
2.0_pReal*phi*(W_e + Cv*porosity_phasefield_getFormationEnergy(ip,el))/ &
|
||||
porosity_phasefield_getSurfaceEnergy (ip,el)
|
||||
dPhiDot_dPhi = - 2.0_pReal*(1.0_pReal - Cv)*(1.0_pReal - Cv) &
|
||||
- 2.0_pReal*(W_e + Cv*porosity_phasefield_getFormationEnergy(ip,el))/ &
|
||||
porosity_phasefield_getSurfaceEnergy (ip,el)
|
||||
|
||||
end subroutine porosity_phasefield_getSourceAndItsTangent
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief returns homogenized nonlocal diffusion tensor in reference configuration
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
function porosity_phasefield_getDiffusion33(ip,el)
|
||||
use lattice, only: &
|
||||
lattice_PorosityDiffusion33
|
||||
use material, only: &
|
||||
homogenization_Ngrains, &
|
||||
material_phase, &
|
||||
mappingHomogenization
|
||||
use crystallite, only: &
|
||||
crystallite_push33ToRef
|
||||
|
||||
implicit none
|
||||
integer(pInt), intent(in) :: &
|
||||
ip, & !< integration point number
|
||||
el !< element number
|
||||
real(pReal), dimension(3,3) :: &
|
||||
porosity_phasefield_getDiffusion33
|
||||
integer(pInt) :: &
|
||||
homog, &
|
||||
grain
|
||||
|
||||
homog = mappingHomogenization(2,ip,el)
|
||||
porosity_phasefield_getDiffusion33 = 0.0_pReal
|
||||
do grain = 1, homogenization_Ngrains(homog)
|
||||
porosity_phasefield_getDiffusion33 = porosity_phasefield_getDiffusion33 + &
|
||||
crystallite_push33ToRef(grain,ip,el,lattice_PorosityDiffusion33(1:3,1:3,material_phase(grain,ip,el)))
|
||||
enddo
|
||||
|
||||
porosity_phasefield_getDiffusion33 = &
|
||||
porosity_phasefield_getDiffusion33/real(homogenization_Ngrains(homog),pReal)
|
||||
|
||||
end function porosity_phasefield_getDiffusion33
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief Returns homogenized phase field mobility
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
real(pReal) function porosity_phasefield_getMobility(ip,el)
|
||||
use mesh, only: &
|
||||
mesh_element
|
||||
use lattice, only: &
|
||||
lattice_PorosityMobility
|
||||
use material, only: &
|
||||
material_phase, &
|
||||
homogenization_Ngrains
|
||||
|
||||
implicit none
|
||||
integer(pInt), intent(in) :: &
|
||||
ip, & !< integration point number
|
||||
el !< element number
|
||||
integer(pInt) :: &
|
||||
ipc
|
||||
|
||||
porosity_phasefield_getMobility = 0.0_pReal
|
||||
|
||||
do ipc = 1, homogenization_Ngrains(mesh_element(3,el))
|
||||
porosity_phasefield_getMobility = porosity_phasefield_getMobility &
|
||||
+ lattice_PorosityMobility(material_phase(ipc,ip,el))
|
||||
enddo
|
||||
|
||||
porosity_phasefield_getMobility = &
|
||||
porosity_phasefield_getMobility/real(homogenization_Ngrains(mesh_element(3,el)),pReal)
|
||||
|
||||
end function porosity_phasefield_getMobility
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief updates porosity with solution from phasefield PDE
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine porosity_phasefield_putPorosity(phi,ip,el)
|
||||
use material, only: &
|
||||
material_homog, &
|
||||
porosityMapping, &
|
||||
porosity
|
||||
|
||||
implicit none
|
||||
integer(pInt), intent(in) :: &
|
||||
ip, & !< integration point number
|
||||
el !< element number
|
||||
real(pReal), intent(in) :: &
|
||||
phi
|
||||
integer(pInt) :: &
|
||||
homog, &
|
||||
offset
|
||||
|
||||
homog = material_homog(ip,el)
|
||||
offset = porosityMapping(homog)%p(ip,el)
|
||||
porosity(homog)%p(offset) = phi
|
||||
|
||||
end subroutine porosity_phasefield_putPorosity
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief return array of porosity results
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
function porosity_phasefield_postResults(ip,el)
|
||||
use material, only: &
|
||||
mappingHomogenization, &
|
||||
porosity_typeInstance, &
|
||||
porosity
|
||||
|
||||
implicit none
|
||||
integer(pInt), intent(in) :: &
|
||||
ip, & !< integration point
|
||||
el !< element
|
||||
real(pReal), dimension(porosity_phasefield_sizePostResults(porosity_typeInstance(mappingHomogenization(2,ip,el)))) :: &
|
||||
porosity_phasefield_postResults
|
||||
|
||||
integer(pInt) :: &
|
||||
instance, homog, offset, o, c
|
||||
|
||||
homog = mappingHomogenization(2,ip,el)
|
||||
offset = mappingHomogenization(1,ip,el)
|
||||
instance = porosity_typeInstance(homog)
|
||||
|
||||
c = 0_pInt
|
||||
porosity_phasefield_postResults = 0.0_pReal
|
||||
|
||||
do o = 1_pInt,porosity_phasefield_Noutput(instance)
|
||||
select case(porosity_phasefield_outputID(o,instance))
|
||||
|
||||
case (porosity_ID)
|
||||
porosity_phasefield_postResults(c+1_pInt) = porosity(homog)%p(offset)
|
||||
c = c + 1
|
||||
end select
|
||||
enddo
|
||||
end function porosity_phasefield_postResults
|
||||
|
||||
end module porosity_phasefield
|
|
@ -246,10 +246,7 @@ subroutine source_damage_isoBrittle_deltaState(C, Fe, ipc, ip, el)
|
|||
sourceState, &
|
||||
material_homog, &
|
||||
phase_NstiffnessDegradations, &
|
||||
phase_stiffnessDegradation, &
|
||||
porosity, &
|
||||
porosityMapping, &
|
||||
STIFFNESS_DEGRADATION_porosity_ID
|
||||
phase_stiffnessDegradation
|
||||
use math, only : &
|
||||
math_mul33x33, &
|
||||
math_mul66x6, &
|
||||
|
|
|
@ -1,248 +0,0 @@
|
|||
!--------------------------------------------------------------------------------------------------
|
||||
!> @author Pratheek Shanthraj, Max-Planck-Institut für Eisenforschung GmbH
|
||||
!> @brief material subroutine for vacancy generation due to irradiation
|
||||
!> @details to be done
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
module source_vacancy_irradiation
|
||||
use prec, only: &
|
||||
pReal, &
|
||||
pInt
|
||||
|
||||
implicit none
|
||||
private
|
||||
integer(pInt), dimension(:), allocatable, public, protected :: &
|
||||
source_vacancy_irradiation_sizePostResults, & !< cumulative size of post results
|
||||
source_vacancy_irradiation_offset, & !< which source is my current damage mechanism?
|
||||
source_vacancy_irradiation_instance !< instance of damage source mechanism
|
||||
|
||||
integer(pInt), dimension(:,:), allocatable, target, public :: &
|
||||
source_vacancy_irradiation_sizePostResult !< size of each post result output
|
||||
|
||||
character(len=64), dimension(:,:), allocatable, target, public :: &
|
||||
source_vacancy_irradiation_output !< name of each post result output
|
||||
|
||||
integer(pInt), dimension(:), allocatable, target, public :: &
|
||||
source_vacancy_irradiation_Noutput !< number of outputs per instance of this damage
|
||||
|
||||
real(pReal), dimension(:), allocatable, private :: &
|
||||
source_vacancy_irradiation_cascadeProb, &
|
||||
source_vacancy_irradiation_cascadeVolume
|
||||
|
||||
public :: &
|
||||
source_vacancy_irradiation_init, &
|
||||
source_vacancy_irradiation_deltaState, &
|
||||
source_vacancy_irradiation_getRateAndItsTangent
|
||||
|
||||
contains
|
||||
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief module initialization
|
||||
!> @details reads in material parameters, allocates arrays, and does sanity checks
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine source_vacancy_irradiation_init(fileUnit)
|
||||
#if defined(__GFORTRAN__) || __INTEL_COMPILER >= 1800
|
||||
use, intrinsic :: iso_fortran_env, only: &
|
||||
compiler_version, &
|
||||
compiler_options
|
||||
#endif
|
||||
use debug, only: &
|
||||
debug_level,&
|
||||
debug_constitutive,&
|
||||
debug_levelBasic
|
||||
use IO, only: &
|
||||
IO_read, &
|
||||
IO_lc, &
|
||||
IO_getTag, &
|
||||
IO_isBlank, &
|
||||
IO_stringPos, &
|
||||
IO_stringValue, &
|
||||
IO_floatValue, &
|
||||
IO_intValue, &
|
||||
IO_warning, &
|
||||
IO_error, &
|
||||
IO_timeStamp, &
|
||||
IO_EOF
|
||||
use material, only: &
|
||||
phase_source, &
|
||||
phase_Nsources, &
|
||||
phase_Noutput, &
|
||||
SOURCE_vacancy_irradiation_label, &
|
||||
SOURCE_vacancy_irradiation_ID, &
|
||||
material_phase, &
|
||||
sourceState
|
||||
use config, only: &
|
||||
material_Nphase, &
|
||||
MATERIAL_partPhase
|
||||
use numerics,only: &
|
||||
numerics_integrator
|
||||
|
||||
implicit none
|
||||
integer(pInt), intent(in) :: fileUnit
|
||||
|
||||
integer(pInt), allocatable, dimension(:) :: chunkPos
|
||||
integer(pInt) :: maxNinstance,phase,instance,source,sourceOffset
|
||||
integer(pInt) :: sizeState, sizeDotState, sizeDeltaState
|
||||
integer(pInt) :: NofMyPhase
|
||||
character(len=65536) :: &
|
||||
tag = '', &
|
||||
line = ''
|
||||
|
||||
write(6,'(/,a)') ' <<<+- source_'//SOURCE_vacancy_irradiation_label//' init -+>>>'
|
||||
write(6,'(a15,a)') ' Current time: ',IO_timeStamp()
|
||||
#include "compilation_info.f90"
|
||||
|
||||
maxNinstance = int(count(phase_source == SOURCE_vacancy_irradiation_ID),pInt)
|
||||
if (maxNinstance == 0_pInt) return
|
||||
if (iand(debug_level(debug_constitutive),debug_levelBasic) /= 0_pInt) &
|
||||
write(6,'(a16,1x,i5,/)') '# instances:',maxNinstance
|
||||
|
||||
allocate(source_vacancy_irradiation_offset(material_Nphase), source=0_pInt)
|
||||
allocate(source_vacancy_irradiation_instance(material_Nphase), source=0_pInt)
|
||||
do phase = 1, material_Nphase
|
||||
source_vacancy_irradiation_instance(phase) = count(phase_source(:,1:phase) == source_vacancy_irradiation_ID)
|
||||
do source = 1, phase_Nsources(phase)
|
||||
if (phase_source(source,phase) == source_vacancy_irradiation_ID) &
|
||||
source_vacancy_irradiation_offset(phase) = source
|
||||
enddo
|
||||
enddo
|
||||
|
||||
allocate(source_vacancy_irradiation_sizePostResults(maxNinstance), source=0_pInt)
|
||||
allocate(source_vacancy_irradiation_sizePostResult(maxval(phase_Noutput),maxNinstance),source=0_pInt)
|
||||
allocate(source_vacancy_irradiation_output(maxval(phase_Noutput),maxNinstance))
|
||||
source_vacancy_irradiation_output = ''
|
||||
allocate(source_vacancy_irradiation_Noutput(maxNinstance), source=0_pInt)
|
||||
allocate(source_vacancy_irradiation_cascadeProb(maxNinstance), source=0.0_pReal)
|
||||
allocate(source_vacancy_irradiation_cascadeVolume(maxNinstance), source=0.0_pReal)
|
||||
|
||||
rewind(fileUnit)
|
||||
phase = 0_pInt
|
||||
do while (trim(line) /= IO_EOF .and. IO_lc(IO_getTag(line,'<','>')) /= MATERIAL_partPhase) ! wind forward to <phase>
|
||||
line = IO_read(fileUnit)
|
||||
enddo
|
||||
|
||||
parsingFile: do while (trim(line) /= IO_EOF) ! read through sections of phase part
|
||||
line = IO_read(fileUnit)
|
||||
if (IO_isBlank(line)) cycle ! skip empty lines
|
||||
if (IO_getTag(line,'<','>') /= '') then ! stop at next part
|
||||
line = IO_read(fileUnit, .true.) ! reset IO_read
|
||||
exit
|
||||
endif
|
||||
if (IO_getTag(line,'[',']') /= '') then ! next phase section
|
||||
phase = phase + 1_pInt ! advance phase section counter
|
||||
cycle ! skip to next line
|
||||
endif
|
||||
|
||||
if (phase > 0_pInt ) then; if (any(phase_source(:,phase) == SOURCE_vacancy_irradiation_ID)) then ! do not short-circuit here (.and. with next if statemen). It's not safe in Fortran
|
||||
|
||||
instance = source_vacancy_irradiation_instance(phase) ! which instance of my vacancy is present phase
|
||||
chunkPos = IO_stringPos(line)
|
||||
tag = IO_lc(IO_stringValue(line,chunkPos,1_pInt)) ! extract key
|
||||
select case(tag)
|
||||
case ('irradiation_cascadeprobability')
|
||||
source_vacancy_irradiation_cascadeProb(instance) = IO_floatValue(line,chunkPos,2_pInt)
|
||||
|
||||
case ('irradiation_cascadevolume')
|
||||
source_vacancy_irradiation_cascadeVolume(instance) = IO_floatValue(line,chunkPos,2_pInt)
|
||||
|
||||
end select
|
||||
endif; endif
|
||||
enddo parsingFile
|
||||
|
||||
initializeInstances: do phase = 1_pInt, material_Nphase
|
||||
if (any(phase_source(:,phase) == SOURCE_vacancy_irradiation_ID)) then
|
||||
NofMyPhase=count(material_phase==phase)
|
||||
instance = source_vacancy_irradiation_instance(phase)
|
||||
sourceOffset = source_vacancy_irradiation_offset(phase)
|
||||
|
||||
sizeDotState = 2_pInt
|
||||
sizeDeltaState = 2_pInt
|
||||
sizeState = 2_pInt
|
||||
sourceState(phase)%p(sourceOffset)%sizeState = sizeState
|
||||
sourceState(phase)%p(sourceOffset)%sizeDotState = sizeDotState
|
||||
sourceState(phase)%p(sourceOffset)%sizeDeltaState = sizeDeltaState
|
||||
sourceState(phase)%p(sourceOffset)%sizePostResults = source_vacancy_irradiation_sizePostResults(instance)
|
||||
allocate(sourceState(phase)%p(sourceOffset)%aTolState (sizeState), source=0.1_pReal)
|
||||
allocate(sourceState(phase)%p(sourceOffset)%state0 (sizeState,NofMyPhase), source=0.0_pReal)
|
||||
allocate(sourceState(phase)%p(sourceOffset)%partionedState0 (sizeState,NofMyPhase), source=0.0_pReal)
|
||||
allocate(sourceState(phase)%p(sourceOffset)%subState0 (sizeState,NofMyPhase), source=0.0_pReal)
|
||||
allocate(sourceState(phase)%p(sourceOffset)%state (sizeState,NofMyPhase), source=0.0_pReal)
|
||||
|
||||
allocate(sourceState(phase)%p(sourceOffset)%dotState (sizeDotState,NofMyPhase), source=0.0_pReal)
|
||||
allocate(sourceState(phase)%p(sourceOffset)%deltaState (sizeDeltaState,NofMyPhase), source=0.0_pReal)
|
||||
if (any(numerics_integrator == 1_pInt)) then
|
||||
allocate(sourceState(phase)%p(sourceOffset)%previousDotState (sizeDotState,NofMyPhase), source=0.0_pReal)
|
||||
allocate(sourceState(phase)%p(sourceOffset)%previousDotState2 (sizeDotState,NofMyPhase), source=0.0_pReal)
|
||||
endif
|
||||
if (any(numerics_integrator == 4_pInt)) &
|
||||
allocate(sourceState(phase)%p(sourceOffset)%RK4dotState (sizeDotState,NofMyPhase), source=0.0_pReal)
|
||||
if (any(numerics_integrator == 5_pInt)) &
|
||||
allocate(sourceState(phase)%p(sourceOffset)%RKCK45dotState (6,sizeDotState,NofMyPhase),source=0.0_pReal)
|
||||
|
||||
endif
|
||||
|
||||
enddo initializeInstances
|
||||
end subroutine source_vacancy_irradiation_init
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief calculates derived quantities from state
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine source_vacancy_irradiation_deltaState(ipc, ip, el)
|
||||
use material, only: &
|
||||
phaseAt, phasememberAt, &
|
||||
sourceState
|
||||
|
||||
implicit none
|
||||
integer(pInt), intent(in) :: &
|
||||
ipc, & !< component-ID of integration point
|
||||
ip, & !< integration point
|
||||
el !< element
|
||||
integer(pInt) :: &
|
||||
phase, constituent, sourceOffset
|
||||
real(pReal) :: &
|
||||
randNo
|
||||
|
||||
phase = phaseAt(ipc,ip,el)
|
||||
constituent = phasememberAt(ipc,ip,el)
|
||||
sourceOffset = source_vacancy_irradiation_offset(phase)
|
||||
|
||||
call random_number(randNo)
|
||||
sourceState(phase)%p(sourceOffset)%deltaState(1,constituent) = &
|
||||
randNo - sourceState(phase)%p(sourceOffset)%state(1,constituent)
|
||||
call random_number(randNo)
|
||||
sourceState(phase)%p(sourceOffset)%deltaState(2,constituent) = &
|
||||
randNo - sourceState(phase)%p(sourceOffset)%state(2,constituent)
|
||||
|
||||
end subroutine source_vacancy_irradiation_deltaState
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief returns local vacancy generation rate
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine source_vacancy_irradiation_getRateAndItsTangent(CvDot, dCvDot_dCv, ipc, ip, el)
|
||||
use material, only: &
|
||||
phaseAt, phasememberAt, &
|
||||
sourceState
|
||||
|
||||
implicit none
|
||||
integer(pInt), intent(in) :: &
|
||||
ipc, & !< grain number
|
||||
ip, & !< integration point number
|
||||
el !< element number
|
||||
real(pReal), intent(out) :: &
|
||||
CvDot, dCvDot_dCv
|
||||
integer(pInt) :: &
|
||||
instance, phase, constituent, sourceOffset
|
||||
|
||||
phase = phaseAt(ipc,ip,el)
|
||||
constituent = phasememberAt(ipc,ip,el)
|
||||
instance = source_vacancy_irradiation_instance(phase)
|
||||
sourceOffset = source_vacancy_irradiation_offset(phase)
|
||||
|
||||
CvDot = 0.0_pReal
|
||||
dCvDot_dCv = 0.0_pReal
|
||||
if (sourceState(phase)%p(sourceOffset)%state0(1,constituent) < source_vacancy_irradiation_cascadeProb(instance)) &
|
||||
CvDot = sourceState(phase)%p(sourceOffset)%state0(2,constituent)*source_vacancy_irradiation_cascadeVolume(instance)
|
||||
|
||||
end subroutine source_vacancy_irradiation_getRateAndItsTangent
|
||||
|
||||
end module source_vacancy_irradiation
|
|
@ -1,210 +0,0 @@
|
|||
!--------------------------------------------------------------------------------------------------
|
||||
!> @author Pratheek Shanthraj, Max-Planck-Institut für Eisenforschung GmbH
|
||||
!> @brief material subroutine for vacancy generation due to plasticity
|
||||
!> @details to be done
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
module source_vacancy_phenoplasticity
|
||||
use prec, only: &
|
||||
pReal, &
|
||||
pInt
|
||||
|
||||
implicit none
|
||||
private
|
||||
integer(pInt), dimension(:), allocatable, public, protected :: &
|
||||
source_vacancy_phenoplasticity_sizePostResults, & !< cumulative size of post results
|
||||
source_vacancy_phenoplasticity_offset, & !< which source is my current damage mechanism?
|
||||
source_vacancy_phenoplasticity_instance !< instance of damage source mechanism
|
||||
|
||||
integer(pInt), dimension(:,:), allocatable, target, public :: &
|
||||
source_vacancy_phenoplasticity_sizePostResult !< size of each post result output
|
||||
|
||||
character(len=64), dimension(:,:), allocatable, target, public :: &
|
||||
source_vacancy_phenoplasticity_output !< name of each post result output
|
||||
|
||||
integer(pInt), dimension(:), allocatable, target, public :: &
|
||||
source_vacancy_phenoplasticity_Noutput !< number of outputs per instance of this damage
|
||||
|
||||
real(pReal), dimension(:), allocatable, private :: &
|
||||
source_vacancy_phenoplasticity_rateCoeff
|
||||
|
||||
public :: &
|
||||
source_vacancy_phenoplasticity_init, &
|
||||
source_vacancy_phenoplasticity_getRateAndItsTangent
|
||||
|
||||
contains
|
||||
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief module initialization
|
||||
!> @details reads in material parameters, allocates arrays, and does sanity checks
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine source_vacancy_phenoplasticity_init(fileUnit)
|
||||
#if defined(__GFORTRAN__) || __INTEL_COMPILER >= 1800
|
||||
use, intrinsic :: iso_fortran_env, only: &
|
||||
compiler_version, &
|
||||
compiler_options
|
||||
#endif
|
||||
use debug, only: &
|
||||
debug_level,&
|
||||
debug_constitutive,&
|
||||
debug_levelBasic
|
||||
use IO, only: &
|
||||
IO_read, &
|
||||
IO_lc, &
|
||||
IO_getTag, &
|
||||
IO_isBlank, &
|
||||
IO_stringPos, &
|
||||
IO_stringValue, &
|
||||
IO_floatValue, &
|
||||
IO_intValue, &
|
||||
IO_warning, &
|
||||
IO_error, &
|
||||
IO_timeStamp, &
|
||||
IO_EOF
|
||||
use material, only: &
|
||||
phase_source, &
|
||||
phase_Nsources, &
|
||||
phase_Noutput, &
|
||||
SOURCE_vacancy_phenoplasticity_label, &
|
||||
SOURCE_vacancy_phenoplasticity_ID, &
|
||||
material_phase, &
|
||||
sourceState
|
||||
use config, only: &
|
||||
material_Nphase, &
|
||||
MATERIAL_partPhase
|
||||
use numerics,only: &
|
||||
numerics_integrator
|
||||
|
||||
implicit none
|
||||
integer(pInt), intent(in) :: fileUnit
|
||||
|
||||
integer(pInt), allocatable, dimension(:) :: chunkPos
|
||||
integer(pInt) :: maxNinstance,phase,instance,source,sourceOffset
|
||||
integer(pInt) :: sizeState, sizeDotState, sizeDeltaState
|
||||
integer(pInt) :: NofMyPhase
|
||||
character(len=65536) :: &
|
||||
tag = '', &
|
||||
line = ''
|
||||
|
||||
write(6,'(/,a)') ' <<<+- source_'//SOURCE_vacancy_phenoplasticity_label//' init -+>>>'
|
||||
write(6,'(a15,a)') ' Current time: ',IO_timeStamp()
|
||||
#include "compilation_info.f90"
|
||||
|
||||
maxNinstance = int(count(phase_source == SOURCE_vacancy_phenoplasticity_ID),pInt)
|
||||
if (maxNinstance == 0_pInt) return
|
||||
if (iand(debug_level(debug_constitutive),debug_levelBasic) /= 0_pInt) &
|
||||
write(6,'(a16,1x,i5,/)') '# instances:',maxNinstance
|
||||
|
||||
allocate(source_vacancy_phenoplasticity_offset(material_Nphase), source=0_pInt)
|
||||
allocate(source_vacancy_phenoplasticity_instance(material_Nphase), source=0_pInt)
|
||||
do phase = 1, material_Nphase
|
||||
source_vacancy_phenoplasticity_instance(phase) = count(phase_source(:,1:phase) == source_vacancy_phenoplasticity_ID)
|
||||
do source = 1, phase_Nsources(phase)
|
||||
if (phase_source(source,phase) == source_vacancy_phenoplasticity_ID) &
|
||||
source_vacancy_phenoplasticity_offset(phase) = source
|
||||
enddo
|
||||
enddo
|
||||
|
||||
allocate(source_vacancy_phenoplasticity_sizePostResults(maxNinstance), source=0_pInt)
|
||||
allocate(source_vacancy_phenoplasticity_sizePostResult(maxval(phase_Noutput),maxNinstance),source=0_pInt)
|
||||
allocate(source_vacancy_phenoplasticity_output(maxval(phase_Noutput),maxNinstance))
|
||||
source_vacancy_phenoplasticity_output = ''
|
||||
allocate(source_vacancy_phenoplasticity_Noutput(maxNinstance), source=0_pInt)
|
||||
allocate(source_vacancy_phenoplasticity_rateCoeff(maxNinstance), source=0.0_pReal)
|
||||
|
||||
rewind(fileUnit)
|
||||
phase = 0_pInt
|
||||
do while (trim(line) /= IO_EOF .and. IO_lc(IO_getTag(line,'<','>')) /= MATERIAL_partPhase) ! wind forward to <phase>
|
||||
line = IO_read(fileUnit)
|
||||
enddo
|
||||
|
||||
parsingFile: do while (trim(line) /= IO_EOF) ! read through sections of phase part
|
||||
line = IO_read(fileUnit)
|
||||
if (IO_isBlank(line)) cycle ! skip empty lines
|
||||
if (IO_getTag(line,'<','>') /= '') then ! stop at next part
|
||||
line = IO_read(fileUnit, .true.) ! reset IO_read
|
||||
exit
|
||||
endif
|
||||
if (IO_getTag(line,'[',']') /= '') then ! next phase section
|
||||
phase = phase + 1_pInt ! advance phase section counter
|
||||
cycle ! skip to next line
|
||||
endif
|
||||
|
||||
if (phase > 0_pInt ) then; if (any(phase_source(:,phase) == SOURCE_vacancy_phenoplasticity_ID)) then ! do not short-circuit here (.and. with next if statemen). It's not safe in Fortran
|
||||
|
||||
instance = source_vacancy_phenoplasticity_instance(phase) ! which instance of my vacancy is present phase
|
||||
chunkPos = IO_stringPos(line)
|
||||
tag = IO_lc(IO_stringValue(line,chunkPos,1_pInt)) ! extract key
|
||||
select case(tag)
|
||||
case ('phenoplasticity_ratecoeff')
|
||||
source_vacancy_phenoplasticity_rateCoeff(instance) = IO_floatValue(line,chunkPos,2_pInt)
|
||||
|
||||
end select
|
||||
endif; endif
|
||||
enddo parsingFile
|
||||
|
||||
initializeInstances: do phase = 1_pInt, material_Nphase
|
||||
if (any(phase_source(:,phase) == SOURCE_vacancy_phenoplasticity_ID)) then
|
||||
NofMyPhase=count(material_phase==phase)
|
||||
instance = source_vacancy_phenoplasticity_instance(phase)
|
||||
sourceOffset = source_vacancy_phenoplasticity_offset(phase)
|
||||
|
||||
sizeDotState = 0_pInt
|
||||
sizeDeltaState = 0_pInt
|
||||
sizeState = 0_pInt
|
||||
sourceState(phase)%p(sourceOffset)%sizeState = sizeState
|
||||
sourceState(phase)%p(sourceOffset)%sizeDotState = sizeDotState
|
||||
sourceState(phase)%p(sourceOffset)%sizeDeltaState = sizeDeltaState
|
||||
sourceState(phase)%p(sourceOffset)%sizePostResults = source_vacancy_phenoplasticity_sizePostResults(instance)
|
||||
allocate(sourceState(phase)%p(sourceOffset)%aTolState (sizeState), source=0.0_pReal)
|
||||
allocate(sourceState(phase)%p(sourceOffset)%state0 (sizeState,NofMyPhase), source=0.0_pReal)
|
||||
allocate(sourceState(phase)%p(sourceOffset)%partionedState0 (sizeState,NofMyPhase), source=0.0_pReal)
|
||||
allocate(sourceState(phase)%p(sourceOffset)%subState0 (sizeState,NofMyPhase), source=0.0_pReal)
|
||||
allocate(sourceState(phase)%p(sourceOffset)%state (sizeState,NofMyPhase), source=0.0_pReal)
|
||||
|
||||
allocate(sourceState(phase)%p(sourceOffset)%dotState (sizeDotState,NofMyPhase), source=0.0_pReal)
|
||||
allocate(sourceState(phase)%p(sourceOffset)%deltaState (sizeDeltaState,NofMyPhase), source=0.0_pReal)
|
||||
if (any(numerics_integrator == 1_pInt)) then
|
||||
allocate(sourceState(phase)%p(sourceOffset)%previousDotState (sizeDotState,NofMyPhase), source=0.0_pReal)
|
||||
allocate(sourceState(phase)%p(sourceOffset)%previousDotState2 (sizeDotState,NofMyPhase), source=0.0_pReal)
|
||||
endif
|
||||
if (any(numerics_integrator == 4_pInt)) &
|
||||
allocate(sourceState(phase)%p(sourceOffset)%RK4dotState (sizeDotState,NofMyPhase), source=0.0_pReal)
|
||||
if (any(numerics_integrator == 5_pInt)) &
|
||||
allocate(sourceState(phase)%p(sourceOffset)%RKCK45dotState (6,sizeDotState,NofMyPhase),source=0.0_pReal)
|
||||
|
||||
endif
|
||||
|
||||
enddo initializeInstances
|
||||
end subroutine source_vacancy_phenoplasticity_init
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief returns local vacancy generation rate
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine source_vacancy_phenoplasticity_getRateAndItsTangent(CvDot, dCvDot_dCv, ipc, ip, el)
|
||||
use material, only: &
|
||||
phaseAt, phasememberAt, &
|
||||
plasticState
|
||||
|
||||
implicit none
|
||||
integer(pInt), intent(in) :: &
|
||||
ipc, & !< grain number
|
||||
ip, & !< integration point number
|
||||
el !< element number
|
||||
real(pReal), intent(out) :: &
|
||||
CvDot, dCvDot_dCv
|
||||
integer(pInt) :: &
|
||||
instance, phase, constituent
|
||||
|
||||
phase = phaseAt(ipc,ip,el)
|
||||
constituent = phasememberAt(ipc,ip,el)
|
||||
instance = source_vacancy_phenoplasticity_instance(phase)
|
||||
|
||||
CvDot = &
|
||||
source_vacancy_phenoplasticity_rateCoeff(instance)* &
|
||||
sum(plasticState(phase)%slipRate(:,constituent))
|
||||
dCvDot_dCv = 0.0_pReal
|
||||
|
||||
end subroutine source_vacancy_phenoplasticity_getRateAndItsTangent
|
||||
|
||||
end module source_vacancy_phenoplasticity
|
|
@ -1,250 +0,0 @@
|
|||
!--------------------------------------------------------------------------------------------------
|
||||
!> @author Pratheek Shanthraj, Max-Planck-Institut für Eisenforschung GmbH
|
||||
!> @brief material subroutine for vacancy generation due to thermal fluctuations
|
||||
!> @details to be done
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
module source_vacancy_thermalfluc
|
||||
use prec, only: &
|
||||
pReal, &
|
||||
pInt
|
||||
|
||||
implicit none
|
||||
private
|
||||
integer(pInt), dimension(:), allocatable, public, protected :: &
|
||||
source_vacancy_thermalfluc_sizePostResults, & !< cumulative size of post results
|
||||
source_vacancy_thermalfluc_offset, & !< which source is my current damage mechanism?
|
||||
source_vacancy_thermalfluc_instance !< instance of damage source mechanism
|
||||
|
||||
integer(pInt), dimension(:,:), allocatable, target, public :: &
|
||||
source_vacancy_thermalfluc_sizePostResult !< size of each post result output
|
||||
|
||||
character(len=64), dimension(:,:), allocatable, target, public :: &
|
||||
source_vacancy_thermalfluc_output !< name of each post result output
|
||||
|
||||
integer(pInt), dimension(:), allocatable, target, public :: &
|
||||
source_vacancy_thermalfluc_Noutput !< number of outputs per instance of this damage
|
||||
|
||||
real(pReal), dimension(:), allocatable, private :: &
|
||||
source_vacancy_thermalfluc_amplitude, &
|
||||
source_vacancy_thermalfluc_normVacancyEnergy
|
||||
|
||||
public :: &
|
||||
source_vacancy_thermalfluc_init, &
|
||||
source_vacancy_thermalfluc_deltaState, &
|
||||
source_vacancy_thermalfluc_getRateAndItsTangent
|
||||
|
||||
contains
|
||||
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief module initialization
|
||||
!> @details reads in material parameters, allocates arrays, and does sanity checks
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine source_vacancy_thermalfluc_init(fileUnit)
|
||||
#if defined(__GFORTRAN__) || __INTEL_COMPILER >= 1800
|
||||
use, intrinsic :: iso_fortran_env, only: &
|
||||
compiler_version, &
|
||||
compiler_options
|
||||
#endif
|
||||
use debug, only: &
|
||||
debug_level,&
|
||||
debug_constitutive,&
|
||||
debug_levelBasic
|
||||
use IO, only: &
|
||||
IO_read, &
|
||||
IO_lc, &
|
||||
IO_getTag, &
|
||||
IO_isBlank, &
|
||||
IO_stringPos, &
|
||||
IO_stringValue, &
|
||||
IO_floatValue, &
|
||||
IO_intValue, &
|
||||
IO_warning, &
|
||||
IO_error, &
|
||||
IO_timeStamp, &
|
||||
IO_EOF
|
||||
use lattice, only: &
|
||||
lattice_vacancyFormationEnergy
|
||||
use material, only: &
|
||||
phase_source, &
|
||||
phase_Nsources, &
|
||||
phase_Noutput, &
|
||||
SOURCE_vacancy_thermalfluc_label, &
|
||||
SOURCE_vacancy_thermalfluc_ID, &
|
||||
material_phase, &
|
||||
sourceState
|
||||
use config, only: &
|
||||
material_Nphase, &
|
||||
MATERIAL_partPhase
|
||||
use numerics,only: &
|
||||
numerics_integrator
|
||||
|
||||
implicit none
|
||||
integer(pInt), intent(in) :: fileUnit
|
||||
|
||||
integer(pInt), allocatable, dimension(:) :: chunkPos
|
||||
integer(pInt) :: maxNinstance,phase,instance,source,sourceOffset
|
||||
integer(pInt) :: sizeState, sizeDotState, sizeDeltaState
|
||||
integer(pInt) :: NofMyPhase
|
||||
character(len=65536) :: &
|
||||
tag = '', &
|
||||
line = ''
|
||||
|
||||
write(6,'(/,a)') ' <<<+- source_'//SOURCE_vacancy_thermalfluc_label//' init -+>>>'
|
||||
write(6,'(a15,a)') ' Current time: ',IO_timeStamp()
|
||||
#include "compilation_info.f90"
|
||||
|
||||
maxNinstance = int(count(phase_source == SOURCE_vacancy_thermalfluc_ID),pInt)
|
||||
if (maxNinstance == 0_pInt) return
|
||||
if (iand(debug_level(debug_constitutive),debug_levelBasic) /= 0_pInt) &
|
||||
write(6,'(a16,1x,i5,/)') '# instances:',maxNinstance
|
||||
|
||||
allocate(source_vacancy_thermalfluc_offset(material_Nphase), source=0_pInt)
|
||||
allocate(source_vacancy_thermalfluc_instance(material_Nphase), source=0_pInt)
|
||||
do phase = 1, material_Nphase
|
||||
source_vacancy_thermalfluc_instance(phase) = count(phase_source(:,1:phase) == source_vacancy_thermalfluc_ID)
|
||||
do source = 1, phase_Nsources(phase)
|
||||
if (phase_source(source,phase) == source_vacancy_thermalfluc_ID) &
|
||||
source_vacancy_thermalfluc_offset(phase) = source
|
||||
enddo
|
||||
enddo
|
||||
|
||||
allocate(source_vacancy_thermalfluc_sizePostResults(maxNinstance), source=0_pInt)
|
||||
allocate(source_vacancy_thermalfluc_sizePostResult(maxval(phase_Noutput),maxNinstance),source=0_pInt)
|
||||
allocate(source_vacancy_thermalfluc_output(maxval(phase_Noutput),maxNinstance))
|
||||
source_vacancy_thermalfluc_output = ''
|
||||
allocate(source_vacancy_thermalfluc_Noutput(maxNinstance), source=0_pInt)
|
||||
allocate(source_vacancy_thermalfluc_amplitude(maxNinstance), source=0.0_pReal)
|
||||
allocate(source_vacancy_thermalfluc_normVacancyEnergy(maxNinstance), source=0.0_pReal)
|
||||
|
||||
rewind(fileUnit)
|
||||
phase = 0_pInt
|
||||
do while (trim(line) /= IO_EOF .and. IO_lc(IO_getTag(line,'<','>')) /= MATERIAL_partPhase) ! wind forward to <phase>
|
||||
line = IO_read(fileUnit)
|
||||
enddo
|
||||
|
||||
parsingFile: do while (trim(line) /= IO_EOF) ! read through sections of phase part
|
||||
line = IO_read(fileUnit)
|
||||
if (IO_isBlank(line)) cycle ! skip empty lines
|
||||
if (IO_getTag(line,'<','>') /= '') then ! stop at next part
|
||||
line = IO_read(fileUnit, .true.) ! reset IO_read
|
||||
exit
|
||||
endif
|
||||
if (IO_getTag(line,'[',']') /= '') then ! next phase section
|
||||
phase = phase + 1_pInt ! advance phase section counter
|
||||
cycle ! skip to next line
|
||||
endif
|
||||
|
||||
if (phase > 0_pInt ) then; if (any(phase_source(:,phase) == SOURCE_vacancy_thermalfluc_ID)) then ! do not short-circuit here (.and. with next if statemen). It's not safe in Fortran
|
||||
|
||||
instance = source_vacancy_thermalfluc_instance(phase) ! which instance of my vacancy is present phase
|
||||
chunkPos = IO_stringPos(line)
|
||||
tag = IO_lc(IO_stringValue(line,chunkPos,1_pInt)) ! extract key
|
||||
select case(tag)
|
||||
case ('thermalfluctuation_amplitude')
|
||||
source_vacancy_thermalfluc_amplitude(instance) = IO_floatValue(line,chunkPos,2_pInt)
|
||||
|
||||
end select
|
||||
endif; endif
|
||||
enddo parsingFile
|
||||
|
||||
initializeInstances: do phase = 1_pInt, material_Nphase
|
||||
if (any(phase_source(:,phase) == SOURCE_vacancy_thermalfluc_ID)) then
|
||||
NofMyPhase=count(material_phase==phase)
|
||||
instance = source_vacancy_thermalfluc_instance(phase)
|
||||
source_vacancy_thermalfluc_normVacancyEnergy(instance) = &
|
||||
lattice_vacancyFormationEnergy(phase)/1.3806488e-23_pReal
|
||||
sourceOffset = source_vacancy_thermalfluc_offset(phase)
|
||||
|
||||
sizeDotState = 1_pInt
|
||||
sizeDeltaState = 1_pInt
|
||||
sizeState = 1_pInt
|
||||
sourceState(phase)%p(sourceOffset)%sizeState = sizeState
|
||||
sourceState(phase)%p(sourceOffset)%sizeDotState = sizeDotState
|
||||
sourceState(phase)%p(sourceOffset)%sizeDeltaState = sizeDeltaState
|
||||
sourceState(phase)%p(sourceOffset)%sizePostResults = source_vacancy_thermalfluc_sizePostResults(instance)
|
||||
allocate(sourceState(phase)%p(sourceOffset)%aTolState (sizeState), source=0.1_pReal)
|
||||
allocate(sourceState(phase)%p(sourceOffset)%state0 (sizeState,NofMyPhase), source=0.0_pReal)
|
||||
allocate(sourceState(phase)%p(sourceOffset)%partionedState0 (sizeState,NofMyPhase), source=0.0_pReal)
|
||||
allocate(sourceState(phase)%p(sourceOffset)%subState0 (sizeState,NofMyPhase), source=0.0_pReal)
|
||||
allocate(sourceState(phase)%p(sourceOffset)%state (sizeState,NofMyPhase), source=0.0_pReal)
|
||||
|
||||
allocate(sourceState(phase)%p(sourceOffset)%dotState (sizeDotState,NofMyPhase), source=0.0_pReal)
|
||||
allocate(sourceState(phase)%p(sourceOffset)%deltaState (sizeDeltaState,NofMyPhase), source=0.0_pReal)
|
||||
if (any(numerics_integrator == 1_pInt)) then
|
||||
allocate(sourceState(phase)%p(sourceOffset)%previousDotState (sizeDotState,NofMyPhase), source=0.0_pReal)
|
||||
allocate(sourceState(phase)%p(sourceOffset)%previousDotState2 (sizeDotState,NofMyPhase), source=0.0_pReal)
|
||||
endif
|
||||
if (any(numerics_integrator == 4_pInt)) &
|
||||
allocate(sourceState(phase)%p(sourceOffset)%RK4dotState (sizeDotState,NofMyPhase), source=0.0_pReal)
|
||||
if (any(numerics_integrator == 5_pInt)) &
|
||||
allocate(sourceState(phase)%p(sourceOffset)%RKCK45dotState (6,sizeDotState,NofMyPhase),source=0.0_pReal)
|
||||
|
||||
endif
|
||||
|
||||
enddo initializeInstances
|
||||
end subroutine source_vacancy_thermalfluc_init
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief calculates derived quantities from state
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine source_vacancy_thermalfluc_deltaState(ipc, ip, el)
|
||||
use material, only: &
|
||||
phaseAt, phasememberAt, &
|
||||
sourceState
|
||||
|
||||
implicit none
|
||||
integer(pInt), intent(in) :: &
|
||||
ipc, & !< component-ID of integration point
|
||||
ip, & !< integration point
|
||||
el !< element
|
||||
integer(pInt) :: &
|
||||
phase, constituent, sourceOffset
|
||||
real(pReal) :: &
|
||||
randNo
|
||||
|
||||
phase = phaseAt(ipc,ip,el)
|
||||
constituent = phasememberAt(ipc,ip,el)
|
||||
sourceOffset = source_vacancy_thermalfluc_offset(phase)
|
||||
|
||||
call random_number(randNo)
|
||||
sourceState(phase)%p(sourceOffset)%deltaState(1,constituent) = &
|
||||
randNo - 0.5_pReal - sourceState(phase)%p(sourceOffset)%state(1,constituent)
|
||||
|
||||
end subroutine source_vacancy_thermalfluc_deltaState
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief returns local vacancy generation rate
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine source_vacancy_thermalfluc_getRateAndItsTangent(CvDot, dCvDot_dCv, ipc, ip, el)
|
||||
use material, only: &
|
||||
phaseAt, phasememberAt, &
|
||||
material_homog, &
|
||||
temperature, &
|
||||
thermalMapping, &
|
||||
sourceState
|
||||
|
||||
implicit none
|
||||
integer(pInt), intent(in) :: &
|
||||
ipc, & !< grain number
|
||||
ip, & !< integration point number
|
||||
el !< element number
|
||||
real(pReal), intent(out) :: &
|
||||
CvDot, dCvDot_dCv
|
||||
integer(pInt) :: &
|
||||
instance, phase, constituent, sourceOffset
|
||||
|
||||
phase = phaseAt(ipc,ip,el)
|
||||
constituent = phasememberAt(ipc,ip,el)
|
||||
instance = source_vacancy_thermalfluc_instance(phase)
|
||||
sourceOffset = source_vacancy_thermalfluc_offset(phase)
|
||||
|
||||
CvDot = source_vacancy_thermalfluc_amplitude(instance)* &
|
||||
sourceState(phase)%p(sourceOffset)%state0(2,constituent)* &
|
||||
exp(-source_vacancy_thermalfluc_normVacancyEnergy(instance)/ &
|
||||
temperature(material_homog(ip,el))%p(thermalMapping(material_homog(ip,el))%p(ip,el)))
|
||||
dCvDot_dCv = 0.0_pReal
|
||||
|
||||
end subroutine source_vacancy_thermalfluc_getRateAndItsTangent
|
||||
|
||||
end module source_vacancy_thermalfluc
|
|
@ -1,602 +0,0 @@
|
|||
!--------------------------------------------------------------------------------------------------
|
||||
!> @author Pratheek Shanthraj, Max-Planck-Institut für Eisenforschung GmbH
|
||||
!> @brief material subroutine for conservative transport of vacancy concentration field
|
||||
!> @details to be done
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
module vacancyflux_cahnhilliard
|
||||
use prec, only: &
|
||||
pReal, &
|
||||
pInt, &
|
||||
group_float
|
||||
|
||||
implicit none
|
||||
private
|
||||
integer(pInt), dimension(:), allocatable, public, protected :: &
|
||||
vacancyflux_cahnhilliard_sizePostResults !< cumulative size of post results
|
||||
|
||||
integer(pInt), dimension(:,:), allocatable, target, public :: &
|
||||
vacancyflux_cahnhilliard_sizePostResult !< size of each post result output
|
||||
|
||||
character(len=64), dimension(:,:), allocatable, target, public :: &
|
||||
vacancyflux_cahnhilliard_output !< name of each post result output
|
||||
|
||||
integer(pInt), dimension(:), allocatable, target, public :: &
|
||||
vacancyflux_cahnhilliard_Noutput !< number of outputs per instance of this damage
|
||||
|
||||
real(pReal), dimension(:), allocatable, private :: &
|
||||
vacancyflux_cahnhilliard_flucAmplitude
|
||||
|
||||
type(group_float), dimension(:), allocatable, private :: &
|
||||
vacancyflux_cahnhilliard_thermalFluc
|
||||
|
||||
real(pReal), parameter, private :: &
|
||||
kB = 1.3806488e-23_pReal !< Boltzmann constant in J/Kelvin
|
||||
|
||||
enum, bind(c)
|
||||
enumerator :: undefined_ID, &
|
||||
vacancyConc_ID
|
||||
end enum
|
||||
integer(kind(undefined_ID)), dimension(:,:), allocatable, private :: &
|
||||
vacancyflux_cahnhilliard_outputID !< ID of each post result output
|
||||
|
||||
|
||||
public :: &
|
||||
vacancyflux_cahnhilliard_init, &
|
||||
vacancyflux_cahnhilliard_getSourceAndItsTangent, &
|
||||
vacancyflux_cahnhilliard_getMobility33, &
|
||||
vacancyflux_cahnhilliard_getDiffusion33, &
|
||||
vacancyflux_cahnhilliard_getChemPotAndItsTangent, &
|
||||
vacancyflux_cahnhilliard_putVacancyConcAndItsRate, &
|
||||
vacancyflux_cahnhilliard_postResults
|
||||
private :: &
|
||||
vacancyflux_cahnhilliard_getFormationEnergy, &
|
||||
vacancyflux_cahnhilliard_getEntropicCoeff, &
|
||||
vacancyflux_cahnhilliard_KinematicChemPotAndItsTangent
|
||||
|
||||
contains
|
||||
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief module initialization
|
||||
!> @details reads in material parameters, allocates arrays, and does sanity checks
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine vacancyflux_cahnhilliard_init(fileUnit)
|
||||
#if defined(__GFORTRAN__) || __INTEL_COMPILER >= 1800
|
||||
use, intrinsic :: iso_fortran_env, only: &
|
||||
compiler_version, &
|
||||
compiler_options
|
||||
#endif
|
||||
use IO, only: &
|
||||
IO_read, &
|
||||
IO_lc, &
|
||||
IO_getTag, &
|
||||
IO_isBlank, &
|
||||
IO_stringPos, &
|
||||
IO_stringValue, &
|
||||
IO_floatValue, &
|
||||
IO_intValue, &
|
||||
IO_warning, &
|
||||
IO_error, &
|
||||
IO_timeStamp, &
|
||||
IO_EOF
|
||||
use material, only: &
|
||||
vacancyflux_type, &
|
||||
vacancyflux_typeInstance, &
|
||||
homogenization_Noutput, &
|
||||
VACANCYFLUX_cahnhilliard_label, &
|
||||
VACANCYFLUX_cahnhilliard_ID, &
|
||||
material_homog, &
|
||||
mappingHomogenization, &
|
||||
vacancyfluxState, &
|
||||
vacancyfluxMapping, &
|
||||
vacancyConc, &
|
||||
vacancyConcRate, &
|
||||
vacancyflux_initialCv
|
||||
use config, only: &
|
||||
material_partPhase, &
|
||||
material_partHomogenization
|
||||
|
||||
implicit none
|
||||
integer(pInt), intent(in) :: fileUnit
|
||||
|
||||
integer(pInt), allocatable, dimension(:) :: chunkPos
|
||||
integer(pInt) :: maxNinstance,mySize=0_pInt,section,instance,o,offset
|
||||
integer(pInt) :: sizeState
|
||||
integer(pInt) :: NofMyHomog
|
||||
character(len=65536) :: &
|
||||
tag = '', &
|
||||
line = ''
|
||||
|
||||
write(6,'(/,a)') ' <<<+- vacancyflux_'//VACANCYFLUX_cahnhilliard_label//' init -+>>>'
|
||||
write(6,'(a15,a)') ' Current time: ',IO_timeStamp()
|
||||
#include "compilation_info.f90"
|
||||
|
||||
maxNinstance = int(count(vacancyflux_type == VACANCYFLUX_cahnhilliard_ID),pInt)
|
||||
if (maxNinstance == 0_pInt) return
|
||||
|
||||
allocate(vacancyflux_cahnhilliard_sizePostResults(maxNinstance), source=0_pInt)
|
||||
allocate(vacancyflux_cahnhilliard_sizePostResult (maxval(homogenization_Noutput),maxNinstance),source=0_pInt)
|
||||
allocate(vacancyflux_cahnhilliard_output (maxval(homogenization_Noutput),maxNinstance))
|
||||
vacancyflux_cahnhilliard_output = ''
|
||||
allocate(vacancyflux_cahnhilliard_outputID (maxval(homogenization_Noutput),maxNinstance),source=undefined_ID)
|
||||
allocate(vacancyflux_cahnhilliard_Noutput (maxNinstance), source=0_pInt)
|
||||
|
||||
allocate(vacancyflux_cahnhilliard_flucAmplitude (maxNinstance))
|
||||
allocate(vacancyflux_cahnhilliard_thermalFluc (maxNinstance))
|
||||
|
||||
rewind(fileUnit)
|
||||
section = 0_pInt
|
||||
do while (trim(line) /= IO_EOF .and. IO_lc(IO_getTag(line,'<','>')) /= material_partHomogenization)! wind forward to <homogenization>
|
||||
line = IO_read(fileUnit)
|
||||
enddo
|
||||
|
||||
parsingHomog: do while (trim(line) /= IO_EOF) ! read through sections of homog part
|
||||
line = IO_read(fileUnit)
|
||||
if (IO_isBlank(line)) cycle ! skip empty lines
|
||||
if (IO_getTag(line,'<','>') /= '') then ! stop at next part
|
||||
line = IO_read(fileUnit, .true.) ! reset IO_read
|
||||
exit
|
||||
endif
|
||||
if (IO_getTag(line,'[',']') /= '') then ! next homog section
|
||||
section = section + 1_pInt ! advance homog section counter
|
||||
cycle ! skip to next line
|
||||
endif
|
||||
|
||||
if (section > 0_pInt ) then; if (vacancyflux_type(section) == VACANCYFLUX_cahnhilliard_ID) then ! do not short-circuit here (.and. with next if statemen). It's not safe in Fortran
|
||||
|
||||
instance = vacancyflux_typeInstance(section) ! which instance of my vacancyflux is present homog
|
||||
chunkPos = IO_stringPos(line)
|
||||
tag = IO_lc(IO_stringValue(line,chunkPos,1_pInt)) ! extract key
|
||||
select case(tag)
|
||||
case ('(output)')
|
||||
select case(IO_lc(IO_stringValue(line,chunkPos,2_pInt)))
|
||||
case ('vacancyconc')
|
||||
vacancyflux_cahnhilliard_Noutput(instance) = vacancyflux_cahnhilliard_Noutput(instance) + 1_pInt
|
||||
vacancyflux_cahnhilliard_outputID(vacancyflux_cahnhilliard_Noutput(instance),instance) = vacancyConc_ID
|
||||
vacancyflux_cahnhilliard_output(vacancyflux_cahnhilliard_Noutput(instance),instance) = &
|
||||
IO_lc(IO_stringValue(line,chunkPos,2_pInt))
|
||||
end select
|
||||
|
||||
case ('vacancyflux_flucamplitude')
|
||||
vacancyflux_cahnhilliard_flucAmplitude(instance) = IO_floatValue(line,chunkPos,2_pInt)
|
||||
|
||||
end select
|
||||
endif; endif
|
||||
enddo parsingHomog
|
||||
|
||||
initializeInstances: do section = 1_pInt, size(vacancyflux_type)
|
||||
if (vacancyflux_type(section) == VACANCYFLUX_cahnhilliard_ID) then
|
||||
NofMyHomog=count(material_homog==section)
|
||||
instance = vacancyflux_typeInstance(section)
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
! Determine size of postResults array
|
||||
outputsLoop: do o = 1_pInt,vacancyflux_cahnhilliard_Noutput(instance)
|
||||
select case(vacancyflux_cahnhilliard_outputID(o,instance))
|
||||
case(vacancyConc_ID)
|
||||
mySize = 1_pInt
|
||||
end select
|
||||
|
||||
if (mySize > 0_pInt) then ! any meaningful output found
|
||||
vacancyflux_cahnhilliard_sizePostResult(o,instance) = mySize
|
||||
vacancyflux_cahnhilliard_sizePostResults(instance) = vacancyflux_cahnhilliard_sizePostResults(instance) + mySize
|
||||
endif
|
||||
enddo outputsLoop
|
||||
|
||||
! allocate state arrays
|
||||
sizeState = 0_pInt
|
||||
vacancyfluxState(section)%sizeState = sizeState
|
||||
vacancyfluxState(section)%sizePostResults = vacancyflux_cahnhilliard_sizePostResults(instance)
|
||||
allocate(vacancyfluxState(section)%state0 (sizeState,NofMyHomog))
|
||||
allocate(vacancyfluxState(section)%subState0(sizeState,NofMyHomog))
|
||||
allocate(vacancyfluxState(section)%state (sizeState,NofMyHomog))
|
||||
|
||||
allocate(vacancyflux_cahnhilliard_thermalFluc(instance)%p(NofMyHomog))
|
||||
do offset = 1_pInt, NofMyHomog
|
||||
call random_number(vacancyflux_cahnhilliard_thermalFluc(instance)%p(offset))
|
||||
vacancyflux_cahnhilliard_thermalFluc(instance)%p(offset) = &
|
||||
1.0_pReal - &
|
||||
vacancyflux_cahnhilliard_flucAmplitude(instance)* &
|
||||
(vacancyflux_cahnhilliard_thermalFluc(instance)%p(offset) - 0.5_pReal)
|
||||
enddo
|
||||
|
||||
nullify(vacancyfluxMapping(section)%p)
|
||||
vacancyfluxMapping(section)%p => mappingHomogenization(1,:,:)
|
||||
deallocate(vacancyConc (section)%p)
|
||||
allocate (vacancyConc (section)%p(NofMyHomog), source=vacancyflux_initialCv(section))
|
||||
deallocate(vacancyConcRate(section)%p)
|
||||
allocate (vacancyConcRate(section)%p(NofMyHomog), source=0.0_pReal)
|
||||
|
||||
endif
|
||||
|
||||
enddo initializeInstances
|
||||
|
||||
end subroutine vacancyflux_cahnhilliard_init
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief calculates homogenized vacancy driving forces
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine vacancyflux_cahnhilliard_getSourceAndItsTangent(CvDot, dCvDot_dCv, Cv, ip, el)
|
||||
use material, only: &
|
||||
homogenization_Ngrains, &
|
||||
mappingHomogenization, &
|
||||
phaseAt, &
|
||||
phase_source, &
|
||||
phase_Nsources, &
|
||||
SOURCE_vacancy_phenoplasticity_ID, &
|
||||
SOURCE_vacancy_irradiation_ID, &
|
||||
SOURCE_vacancy_thermalfluc_ID
|
||||
use source_vacancy_phenoplasticity, only: &
|
||||
source_vacancy_phenoplasticity_getRateAndItsTangent
|
||||
use source_vacancy_irradiation, only: &
|
||||
source_vacancy_irradiation_getRateAndItsTangent
|
||||
use source_vacancy_thermalfluc, only: &
|
||||
source_vacancy_thermalfluc_getRateAndItsTangent
|
||||
|
||||
implicit none
|
||||
integer(pInt), intent(in) :: &
|
||||
ip, & !< integration point number
|
||||
el !< element number
|
||||
real(pReal), intent(in) :: &
|
||||
Cv
|
||||
integer(pInt) :: &
|
||||
phase, &
|
||||
grain, &
|
||||
source
|
||||
real(pReal) :: &
|
||||
CvDot, dCvDot_dCv, localCvDot, dLocalCvDot_dCv
|
||||
|
||||
CvDot = 0.0_pReal
|
||||
dCvDot_dCv = 0.0_pReal
|
||||
do grain = 1, homogenization_Ngrains(mappingHomogenization(2,ip,el))
|
||||
phase = phaseAt(grain,ip,el)
|
||||
do source = 1_pInt, phase_Nsources(phase)
|
||||
select case(phase_source(source,phase))
|
||||
case (SOURCE_vacancy_phenoplasticity_ID)
|
||||
call source_vacancy_phenoplasticity_getRateAndItsTangent (localCvDot, dLocalCvDot_dCv, grain, ip, el)
|
||||
|
||||
case (SOURCE_vacancy_irradiation_ID)
|
||||
call source_vacancy_irradiation_getRateAndItsTangent (localCvDot, dLocalCvDot_dCv, grain, ip, el)
|
||||
|
||||
case (SOURCE_vacancy_thermalfluc_ID)
|
||||
call source_vacancy_thermalfluc_getRateAndItsTangent(localCvDot, dLocalCvDot_dCv, grain, ip, el)
|
||||
|
||||
end select
|
||||
CvDot = CvDot + localCvDot
|
||||
dCvDot_dCv = dCvDot_dCv + dLocalCvDot_dCv
|
||||
enddo
|
||||
enddo
|
||||
|
||||
CvDot = CvDot/real(homogenization_Ngrains(mappingHomogenization(2,ip,el)),pReal)
|
||||
dCvDot_dCv = dCvDot_dCv/real(homogenization_Ngrains(mappingHomogenization(2,ip,el)),pReal)
|
||||
|
||||
end subroutine vacancyflux_cahnhilliard_getSourceAndItsTangent
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief returns homogenized vacancy mobility tensor in reference configuration
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
function vacancyflux_cahnhilliard_getMobility33(ip,el)
|
||||
use lattice, only: &
|
||||
lattice_vacancyfluxMobility33
|
||||
use material, only: &
|
||||
homogenization_Ngrains, &
|
||||
material_phase
|
||||
use mesh, only: &
|
||||
mesh_element
|
||||
use crystallite, only: &
|
||||
crystallite_push33ToRef
|
||||
|
||||
implicit none
|
||||
integer(pInt), intent(in) :: &
|
||||
ip, & !< integration point number
|
||||
el !< element number
|
||||
real(pReal), dimension(3,3) :: &
|
||||
vacancyflux_cahnhilliard_getMobility33
|
||||
integer(pInt) :: &
|
||||
grain
|
||||
|
||||
vacancyflux_cahnhilliard_getMobility33 = 0.0_pReal
|
||||
do grain = 1, homogenization_Ngrains(mesh_element(3,el))
|
||||
vacancyflux_cahnhilliard_getMobility33 = vacancyflux_cahnhilliard_getMobility33 + &
|
||||
crystallite_push33ToRef(grain,ip,el,lattice_vacancyfluxMobility33(:,:,material_phase(grain,ip,el)))
|
||||
enddo
|
||||
|
||||
vacancyflux_cahnhilliard_getMobility33 = &
|
||||
vacancyflux_cahnhilliard_getMobility33/real(homogenization_Ngrains(mesh_element(3,el)),pReal)
|
||||
|
||||
end function vacancyflux_cahnhilliard_getMobility33
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief returns homogenized vacancy diffusion tensor in reference configuration
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
function vacancyflux_cahnhilliard_getDiffusion33(ip,el)
|
||||
use lattice, only: &
|
||||
lattice_vacancyfluxDiffusion33
|
||||
use material, only: &
|
||||
homogenization_Ngrains, &
|
||||
material_phase
|
||||
use mesh, only: &
|
||||
mesh_element
|
||||
use crystallite, only: &
|
||||
crystallite_push33ToRef
|
||||
|
||||
implicit none
|
||||
integer(pInt), intent(in) :: &
|
||||
ip, & !< integration point number
|
||||
el !< element number
|
||||
real(pReal), dimension(3,3) :: &
|
||||
vacancyflux_cahnhilliard_getDiffusion33
|
||||
integer(pInt) :: &
|
||||
grain
|
||||
|
||||
vacancyflux_cahnhilliard_getDiffusion33 = 0.0_pReal
|
||||
do grain = 1, homogenization_Ngrains(mesh_element(3,el))
|
||||
vacancyflux_cahnhilliard_getDiffusion33 = vacancyflux_cahnhilliard_getDiffusion33 + &
|
||||
crystallite_push33ToRef(grain,ip,el,lattice_vacancyfluxDiffusion33(:,:,material_phase(grain,ip,el)))
|
||||
enddo
|
||||
|
||||
vacancyflux_cahnhilliard_getDiffusion33 = &
|
||||
vacancyflux_cahnhilliard_getDiffusion33/real(homogenization_Ngrains(mesh_element(3,el)),pReal)
|
||||
|
||||
end function vacancyflux_cahnhilliard_getDiffusion33
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief returns homogenized vacancy formation energy
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
real(pReal) function vacancyflux_cahnhilliard_getFormationEnergy(ip,el)
|
||||
use lattice, only: &
|
||||
lattice_vacancyFormationEnergy, &
|
||||
lattice_vacancyVol, &
|
||||
lattice_vacancySurfaceEnergy
|
||||
use material, only: &
|
||||
homogenization_Ngrains, &
|
||||
material_phase
|
||||
use mesh, only: &
|
||||
mesh_element
|
||||
|
||||
implicit none
|
||||
integer(pInt), intent(in) :: &
|
||||
ip, & !< integration point number
|
||||
el !< element number
|
||||
integer(pInt) :: &
|
||||
grain
|
||||
|
||||
vacancyflux_cahnhilliard_getFormationEnergy = 0.0_pReal
|
||||
do grain = 1, homogenization_Ngrains(mesh_element(3,el))
|
||||
vacancyflux_cahnhilliard_getFormationEnergy = vacancyflux_cahnhilliard_getFormationEnergy + &
|
||||
lattice_vacancyFormationEnergy(material_phase(grain,ip,el))/ &
|
||||
lattice_vacancyVol(material_phase(grain,ip,el))/ &
|
||||
lattice_vacancySurfaceEnergy(material_phase(grain,ip,el))
|
||||
enddo
|
||||
|
||||
vacancyflux_cahnhilliard_getFormationEnergy = &
|
||||
vacancyflux_cahnhilliard_getFormationEnergy/real(homogenization_Ngrains(mesh_element(3,el)),pReal)
|
||||
|
||||
end function vacancyflux_cahnhilliard_getFormationEnergy
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief returns homogenized vacancy entropy coefficient
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
real(pReal) function vacancyflux_cahnhilliard_getEntropicCoeff(ip,el)
|
||||
use lattice, only: &
|
||||
lattice_vacancyVol, &
|
||||
lattice_vacancySurfaceEnergy
|
||||
use material, only: &
|
||||
homogenization_Ngrains, &
|
||||
material_homog, &
|
||||
material_phase, &
|
||||
temperature, &
|
||||
thermalMapping
|
||||
|
||||
implicit none
|
||||
integer(pInt), intent(in) :: &
|
||||
ip, & !< integration point number
|
||||
el !< element number
|
||||
integer(pInt) :: &
|
||||
grain
|
||||
|
||||
vacancyflux_cahnhilliard_getEntropicCoeff = 0.0_pReal
|
||||
do grain = 1, homogenization_Ngrains(material_homog(ip,el))
|
||||
vacancyflux_cahnhilliard_getEntropicCoeff = vacancyflux_cahnhilliard_getEntropicCoeff + &
|
||||
kB/ &
|
||||
lattice_vacancyVol(material_phase(grain,ip,el))/ &
|
||||
lattice_vacancySurfaceEnergy(material_phase(grain,ip,el))
|
||||
enddo
|
||||
|
||||
vacancyflux_cahnhilliard_getEntropicCoeff = &
|
||||
vacancyflux_cahnhilliard_getEntropicCoeff* &
|
||||
temperature(material_homog(ip,el))%p(thermalMapping(material_homog(ip,el))%p(ip,el))/ &
|
||||
real(homogenization_Ngrains(material_homog(ip,el)),pReal)
|
||||
|
||||
end function vacancyflux_cahnhilliard_getEntropicCoeff
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief returns homogenized kinematic contribution to chemical potential
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine vacancyflux_cahnhilliard_KinematicChemPotAndItsTangent(KPot, dKPot_dCv, Cv, ip, el)
|
||||
use lattice, only: &
|
||||
lattice_vacancySurfaceEnergy
|
||||
use material, only: &
|
||||
homogenization_Ngrains, &
|
||||
material_homog, &
|
||||
phase_kinematics, &
|
||||
phase_Nkinematics, &
|
||||
material_phase, &
|
||||
KINEMATICS_vacancy_strain_ID
|
||||
use crystallite, only: &
|
||||
crystallite_Tstar_v, &
|
||||
crystallite_Fi0, &
|
||||
crystallite_Fi
|
||||
use kinematics_vacancy_strain, only: &
|
||||
kinematics_vacancy_strain_ChemPotAndItsTangent
|
||||
|
||||
implicit none
|
||||
integer(pInt), intent(in) :: &
|
||||
ip, & !< integration point number
|
||||
el !< element number
|
||||
real(pReal), intent(in) :: &
|
||||
Cv
|
||||
real(pReal), intent(out) :: &
|
||||
KPot, dKPot_dCv
|
||||
real(pReal) :: &
|
||||
my_KPot, my_dKPot_dCv
|
||||
integer(pInt) :: &
|
||||
grain, kinematics
|
||||
|
||||
KPot = 0.0_pReal
|
||||
dKPot_dCv = 0.0_pReal
|
||||
do grain = 1_pInt,homogenization_Ngrains(material_homog(ip,el))
|
||||
do kinematics = 1_pInt, phase_Nkinematics(material_phase(grain,ip,el))
|
||||
select case (phase_kinematics(kinematics,material_phase(grain,ip,el)))
|
||||
case (KINEMATICS_vacancy_strain_ID)
|
||||
call kinematics_vacancy_strain_ChemPotAndItsTangent(my_KPot, my_dKPot_dCv, &
|
||||
crystallite_Tstar_v(1:6,grain,ip,el), &
|
||||
crystallite_Fi0(1:3,1:3,grain,ip,el), &
|
||||
crystallite_Fi (1:3,1:3,grain,ip,el), &
|
||||
grain,ip, el)
|
||||
|
||||
case default
|
||||
my_KPot = 0.0_pReal
|
||||
my_dKPot_dCv = 0.0_pReal
|
||||
|
||||
end select
|
||||
KPot = KPot + my_KPot/lattice_vacancySurfaceEnergy(material_phase(grain,ip,el))
|
||||
dKPot_dCv = dKPot_dCv + my_dKPot_dCv/lattice_vacancySurfaceEnergy(material_phase(grain,ip,el))
|
||||
enddo
|
||||
enddo
|
||||
|
||||
KPot = KPot/real(homogenization_Ngrains(material_homog(ip,el)),pReal)
|
||||
dKPot_dCv = dKPot_dCv/real(homogenization_Ngrains(material_homog(ip,el)),pReal)
|
||||
|
||||
end subroutine vacancyflux_cahnhilliard_KinematicChemPotAndItsTangent
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief returns homogenized chemical potential and its tangent
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine vacancyflux_cahnhilliard_getChemPotAndItsTangent(ChemPot,dChemPot_dCv,Cv,ip,el)
|
||||
use numerics, only: &
|
||||
vacancyBoundPenalty, &
|
||||
vacancyPolyOrder
|
||||
use material, only: &
|
||||
mappingHomogenization, &
|
||||
vacancyflux_typeInstance, &
|
||||
porosity, &
|
||||
porosityMapping
|
||||
|
||||
implicit none
|
||||
integer(pInt), intent(in) :: &
|
||||
ip, & !< integration point number
|
||||
el !< element number
|
||||
real(pReal), intent(in) :: &
|
||||
Cv
|
||||
real(pReal), intent(out) :: &
|
||||
ChemPot, &
|
||||
dChemPot_dCv
|
||||
real(pReal) :: &
|
||||
VoidPhaseFrac, kBT, KPot, dKPot_dCv
|
||||
integer(pInt) :: &
|
||||
homog, o
|
||||
|
||||
homog = mappingHomogenization(2,ip,el)
|
||||
VoidPhaseFrac = porosity(homog)%p(porosityMapping(homog)%p(ip,el))
|
||||
kBT = vacancyflux_cahnhilliard_getEntropicCoeff(ip,el)
|
||||
|
||||
ChemPot = vacancyflux_cahnhilliard_getFormationEnergy(ip,el)
|
||||
dChemPot_dCv = 0.0_pReal
|
||||
do o = 1_pInt, vacancyPolyOrder
|
||||
ChemPot = ChemPot + kBT*((2.0_pReal*Cv - 1.0_pReal)**real(2_pInt*o-1_pInt,pReal))/ &
|
||||
real(2_pInt*o-1_pInt,pReal)
|
||||
dChemPot_dCv = dChemPot_dCv + 2.0_pReal*kBT*(2.0_pReal*Cv - 1.0_pReal)**real(2_pInt*o-2_pInt,pReal)
|
||||
enddo
|
||||
|
||||
ChemPot = VoidPhaseFrac*VoidPhaseFrac*ChemPot &
|
||||
- 2.0_pReal*(1.0_pReal - Cv)*(1.0_pReal - VoidPhaseFrac)*(1.0_pReal - VoidPhaseFrac)
|
||||
|
||||
dChemPot_dCv = VoidPhaseFrac*VoidPhaseFrac*dChemPot_dCv &
|
||||
+ 2.0_pReal*(1.0_pReal - VoidPhaseFrac)*(1.0_pReal - VoidPhaseFrac)
|
||||
|
||||
call vacancyflux_cahnhilliard_KinematicChemPotAndItsTangent(KPot, dKPot_dCv, Cv, ip, el)
|
||||
ChemPot = ChemPot + KPot
|
||||
dChemPot_dCv = dChemPot_dCv + dKPot_dCv
|
||||
|
||||
if (Cv < 0.0_pReal) then
|
||||
ChemPot = ChemPot - 3.0_pReal*vacancyBoundPenalty*Cv*Cv
|
||||
dChemPot_dCv = dChemPot_dCv - 6.0_pReal*vacancyBoundPenalty*Cv
|
||||
elseif (Cv > 1.0_pReal) then
|
||||
ChemPot = ChemPot + 3.0_pReal*vacancyBoundPenalty*(1.0_pReal - Cv)*(1.0_pReal - Cv)
|
||||
dChemPot_dCv = dChemPot_dCv - 6.0_pReal*vacancyBoundPenalty*(1.0_pReal - Cv)
|
||||
endif
|
||||
|
||||
ChemPot = ChemPot* &
|
||||
vacancyflux_cahnhilliard_thermalFluc(vacancyflux_typeInstance(homog))%p(mappingHomogenization(1,ip,el))
|
||||
dChemPot_dCv = dChemPot_dCv* &
|
||||
vacancyflux_cahnhilliard_thermalFluc(vacancyflux_typeInstance(homog))%p(mappingHomogenization(1,ip,el))
|
||||
|
||||
end subroutine vacancyflux_cahnhilliard_getChemPotAndItsTangent
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief updated vacancy concentration and its rate with solution from transport PDE
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine vacancyflux_cahnhilliard_putVacancyConcAndItsRate(Cv,Cvdot,ip,el)
|
||||
use material, only: &
|
||||
mappingHomogenization, &
|
||||
vacancyConc, &
|
||||
vacancyConcRate, &
|
||||
vacancyfluxMapping
|
||||
|
||||
implicit none
|
||||
integer(pInt), intent(in) :: &
|
||||
ip, & !< integration point number
|
||||
el !< element number
|
||||
real(pReal), intent(in) :: &
|
||||
Cv, &
|
||||
Cvdot
|
||||
integer(pInt) :: &
|
||||
homog, &
|
||||
offset
|
||||
|
||||
homog = mappingHomogenization(2,ip,el)
|
||||
offset = vacancyfluxMapping(homog)%p(ip,el)
|
||||
vacancyConc (homog)%p(offset) = Cv
|
||||
vacancyConcRate(homog)%p(offset) = Cvdot
|
||||
|
||||
end subroutine vacancyflux_cahnhilliard_putVacancyConcAndItsRate
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief return array of vacancy transport results
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
function vacancyflux_cahnhilliard_postResults(ip,el)
|
||||
use material, only: &
|
||||
mappingHomogenization, &
|
||||
vacancyflux_typeInstance, &
|
||||
vacancyConc, &
|
||||
vacancyfluxMapping
|
||||
|
||||
implicit none
|
||||
integer(pInt), intent(in) :: &
|
||||
ip, & !< integration point
|
||||
el !< element
|
||||
real(pReal), dimension(vacancyflux_cahnhilliard_sizePostResults(vacancyflux_typeInstance(mappingHomogenization(2,ip,el)))) :: &
|
||||
vacancyflux_cahnhilliard_postResults
|
||||
|
||||
integer(pInt) :: &
|
||||
instance, homog, offset, o, c
|
||||
|
||||
homog = mappingHomogenization(2,ip,el)
|
||||
offset = vacancyfluxMapping(homog)%p(ip,el)
|
||||
instance = vacancyflux_typeInstance(homog)
|
||||
|
||||
c = 0_pInt
|
||||
vacancyflux_cahnhilliard_postResults = 0.0_pReal
|
||||
|
||||
do o = 1_pInt,vacancyflux_cahnhilliard_Noutput(instance)
|
||||
select case(vacancyflux_cahnhilliard_outputID(o,instance))
|
||||
|
||||
case (vacancyConc_ID)
|
||||
vacancyflux_cahnhilliard_postResults(c+1_pInt) = vacancyConc(homog)%p(offset)
|
||||
c = c + 1
|
||||
end select
|
||||
enddo
|
||||
end function vacancyflux_cahnhilliard_postResults
|
||||
|
||||
end module vacancyflux_cahnhilliard
|
|
@ -1,328 +0,0 @@
|
|||
!--------------------------------------------------------------------------------------------------
|
||||
!> @author Pratheek Shanthraj, Max-Planck-Institut für Eisenforschung GmbH
|
||||
!> @brief material subroutine for locally evolving vacancy concentration
|
||||
!> @details to be done
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
module vacancyflux_isochempot
|
||||
use prec, only: &
|
||||
pReal, &
|
||||
pInt
|
||||
|
||||
implicit none
|
||||
private
|
||||
integer(pInt), dimension(:), allocatable, public, protected :: &
|
||||
vacancyflux_isochempot_sizePostResults !< cumulative size of post results
|
||||
|
||||
integer(pInt), dimension(:,:), allocatable, target, public :: &
|
||||
vacancyflux_isochempot_sizePostResult !< size of each post result output
|
||||
|
||||
character(len=64), dimension(:,:), allocatable, target, public :: &
|
||||
vacancyflux_isochempot_output !< name of each post result output
|
||||
|
||||
integer(pInt), dimension(:), allocatable, target, public :: &
|
||||
vacancyflux_isochempot_Noutput !< number of outputs per instance of this damage
|
||||
|
||||
enum, bind(c)
|
||||
enumerator :: undefined_ID, &
|
||||
vacancyconc_ID
|
||||
end enum
|
||||
integer(kind(undefined_ID)), dimension(:,:), allocatable, private :: &
|
||||
vacancyflux_isochempot_outputID !< ID of each post result output
|
||||
|
||||
|
||||
public :: &
|
||||
vacancyflux_isochempot_init, &
|
||||
vacancyflux_isochempot_updateState, &
|
||||
vacancyflux_isochempot_getSourceAndItsTangent, &
|
||||
vacancyflux_isochempot_postResults
|
||||
|
||||
contains
|
||||
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief module initialization
|
||||
!> @details reads in material parameters, allocates arrays, and does sanity checks
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine vacancyflux_isochempot_init(fileUnit)
|
||||
#if defined(__GFORTRAN__) || __INTEL_COMPILER >= 1800
|
||||
use, intrinsic :: iso_fortran_env, only: &
|
||||
compiler_version, &
|
||||
compiler_options
|
||||
#endif
|
||||
use IO, only: &
|
||||
IO_read, &
|
||||
IO_lc, &
|
||||
IO_getTag, &
|
||||
IO_isBlank, &
|
||||
IO_stringPos, &
|
||||
IO_stringValue, &
|
||||
IO_floatValue, &
|
||||
IO_intValue, &
|
||||
IO_warning, &
|
||||
IO_error, &
|
||||
IO_timeStamp, &
|
||||
IO_EOF
|
||||
use material, only: &
|
||||
vacancyflux_type, &
|
||||
vacancyflux_typeInstance, &
|
||||
homogenization_Noutput, &
|
||||
VACANCYFLUX_isochempot_label, &
|
||||
VACANCYFLUX_isochempot_ID, &
|
||||
material_homog, &
|
||||
mappingHomogenization, &
|
||||
vacancyfluxState, &
|
||||
vacancyfluxMapping, &
|
||||
vacancyConc, &
|
||||
vacancyConcRate, &
|
||||
vacancyflux_initialCv
|
||||
use config, only: &
|
||||
material_partHomogenization
|
||||
|
||||
implicit none
|
||||
integer(pInt), intent(in) :: fileUnit
|
||||
|
||||
integer(pInt), allocatable, dimension(:) :: chunkPos
|
||||
integer(pInt) :: maxNinstance,mySize=0_pInt,section,instance,o
|
||||
integer(pInt) :: sizeState
|
||||
integer(pInt) :: NofMyHomog
|
||||
character(len=65536) :: &
|
||||
tag = '', &
|
||||
line = ''
|
||||
|
||||
write(6,'(/,a)') ' <<<+- vacancyflux_'//VACANCYFLUX_isochempot_label//' init -+>>>'
|
||||
write(6,'(a15,a)') ' Current time: ',IO_timeStamp()
|
||||
#include "compilation_info.f90"
|
||||
|
||||
maxNinstance = int(count(vacancyflux_type == VACANCYFLUX_isochempot_ID),pInt)
|
||||
if (maxNinstance == 0_pInt) return
|
||||
|
||||
allocate(vacancyflux_isochempot_sizePostResults(maxNinstance), source=0_pInt)
|
||||
allocate(vacancyflux_isochempot_sizePostResult (maxval(homogenization_Noutput),maxNinstance),source=0_pInt)
|
||||
allocate(vacancyflux_isochempot_output (maxval(homogenization_Noutput),maxNinstance))
|
||||
vacancyflux_isochempot_output = ''
|
||||
allocate(vacancyflux_isochempot_outputID (maxval(homogenization_Noutput),maxNinstance),source=undefined_ID)
|
||||
allocate(vacancyflux_isochempot_Noutput (maxNinstance), source=0_pInt)
|
||||
|
||||
rewind(fileUnit)
|
||||
section = 0_pInt
|
||||
do while (trim(line) /= IO_EOF .and. IO_lc(IO_getTag(line,'<','>')) /= material_partHomogenization)! wind forward to <homogenization>
|
||||
line = IO_read(fileUnit)
|
||||
enddo
|
||||
|
||||
parsingFile: do while (trim(line) /= IO_EOF) ! read through sections of homog part
|
||||
line = IO_read(fileUnit)
|
||||
if (IO_isBlank(line)) cycle ! skip empty lines
|
||||
if (IO_getTag(line,'<','>') /= '') then ! stop at next part
|
||||
line = IO_read(fileUnit, .true.) ! reset IO_read
|
||||
exit
|
||||
endif
|
||||
if (IO_getTag(line,'[',']') /= '') then ! next homog section
|
||||
section = section + 1_pInt ! advance homog section counter
|
||||
cycle ! skip to next line
|
||||
endif
|
||||
|
||||
if (section > 0_pInt ) then; if (vacancyflux_type(section) == VACANCYFLUX_isochempot_ID) then ! do not short-circuit here (.and. with next if statemen). It's not safe in Fortran
|
||||
|
||||
instance = vacancyflux_typeInstance(section) ! which instance of my vacancyflux is present homog
|
||||
chunkPos = IO_stringPos(line)
|
||||
tag = IO_lc(IO_stringValue(line,chunkPos,1_pInt)) ! extract key
|
||||
select case(tag)
|
||||
case ('(output)')
|
||||
select case(IO_lc(IO_stringValue(line,chunkPos,2_pInt)))
|
||||
case ('vacancyconc')
|
||||
vacancyflux_isochempot_Noutput(instance) = vacancyflux_isochempot_Noutput(instance) + 1_pInt
|
||||
vacancyflux_isochempot_outputID(vacancyflux_isochempot_Noutput(instance),instance) = vacancyconc_ID
|
||||
vacancyflux_isochempot_output(vacancyflux_isochempot_Noutput(instance),instance) = &
|
||||
IO_lc(IO_stringValue(line,chunkPos,2_pInt))
|
||||
end select
|
||||
|
||||
end select
|
||||
endif; endif
|
||||
enddo parsingFile
|
||||
|
||||
initializeInstances: do section = 1_pInt, size(vacancyflux_type)
|
||||
if (vacancyflux_type(section) == VACANCYFLUX_isochempot_ID) then
|
||||
NofMyHomog=count(material_homog==section)
|
||||
instance = vacancyflux_typeInstance(section)
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
! Determine size of postResults array
|
||||
outputsLoop: do o = 1_pInt,vacancyflux_isochempot_Noutput(instance)
|
||||
select case(vacancyflux_isochempot_outputID(o,instance))
|
||||
case(vacancyconc_ID)
|
||||
mySize = 1_pInt
|
||||
end select
|
||||
|
||||
if (mySize > 0_pInt) then ! any meaningful output found
|
||||
vacancyflux_isochempot_sizePostResult(o,instance) = mySize
|
||||
vacancyflux_isochempot_sizePostResults(instance) = vacancyflux_isochempot_sizePostResults(instance) + mySize
|
||||
endif
|
||||
enddo outputsLoop
|
||||
|
||||
! allocate state arrays
|
||||
sizeState = 1_pInt
|
||||
vacancyfluxState(section)%sizeState = sizeState
|
||||
vacancyfluxState(section)%sizePostResults = vacancyflux_isochempot_sizePostResults(instance)
|
||||
allocate(vacancyfluxState(section)%state0 (sizeState,NofMyHomog), source=vacancyflux_initialCv(section))
|
||||
allocate(vacancyfluxState(section)%subState0(sizeState,NofMyHomog), source=vacancyflux_initialCv(section))
|
||||
allocate(vacancyfluxState(section)%state (sizeState,NofMyHomog), source=vacancyflux_initialCv(section))
|
||||
|
||||
nullify(vacancyfluxMapping(section)%p)
|
||||
vacancyfluxMapping(section)%p => mappingHomogenization(1,:,:)
|
||||
deallocate(vacancyConc(section)%p)
|
||||
vacancyConc(section)%p => vacancyfluxState(section)%state(1,:)
|
||||
deallocate(vacancyConcRate(section)%p)
|
||||
allocate(vacancyConcRate(section)%p(NofMyHomog), source=0.0_pReal)
|
||||
|
||||
endif
|
||||
|
||||
enddo initializeInstances
|
||||
end subroutine vacancyflux_isochempot_init
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief calculates change in vacancy concentration based on local vacancy generation model
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
function vacancyflux_isochempot_updateState(subdt, ip, el)
|
||||
use numerics, only: &
|
||||
err_vacancyflux_tolAbs, &
|
||||
err_vacancyflux_tolRel
|
||||
use material, only: &
|
||||
mappingHomogenization, &
|
||||
vacancyflux_typeInstance, &
|
||||
vacancyfluxState, &
|
||||
vacancyConc, &
|
||||
vacancyConcRate, &
|
||||
vacancyfluxMapping
|
||||
|
||||
implicit none
|
||||
integer(pInt), intent(in) :: &
|
||||
ip, & !< integration point number
|
||||
el !< element number
|
||||
real(pReal), intent(in) :: &
|
||||
subdt
|
||||
logical, dimension(2) :: &
|
||||
vacancyflux_isochempot_updateState
|
||||
integer(pInt) :: &
|
||||
homog, &
|
||||
offset, &
|
||||
instance
|
||||
real(pReal) :: &
|
||||
Cv, Cvdot, dCvDot_dCv
|
||||
|
||||
homog = mappingHomogenization(2,ip,el)
|
||||
offset = mappingHomogenization(1,ip,el)
|
||||
instance = vacancyflux_typeInstance(homog)
|
||||
|
||||
Cv = vacancyfluxState(homog)%subState0(1,offset)
|
||||
call vacancyflux_isochempot_getSourceAndItsTangent(CvDot, dCvDot_dCv, Cv, ip, el)
|
||||
Cv = Cv + subdt*Cvdot
|
||||
|
||||
vacancyflux_isochempot_updateState = [ abs(Cv - vacancyfluxState(homog)%state(1,offset)) &
|
||||
<= err_vacancyflux_tolAbs &
|
||||
.or. abs(Cv - vacancyfluxState(homog)%state(1,offset)) &
|
||||
<= err_vacancyflux_tolRel*abs(vacancyfluxState(homog)%state(1,offset)), &
|
||||
.true.]
|
||||
|
||||
vacancyConc (homog)%p(vacancyfluxMapping(homog)%p(ip,el)) = Cv
|
||||
vacancyConcRate(homog)%p(vacancyfluxMapping(homog)%p(ip,el)) = &
|
||||
(vacancyfluxState(homog)%state(1,offset) - vacancyfluxState(homog)%subState0(1,offset))/(subdt+tiny(0.0_pReal))
|
||||
|
||||
end function vacancyflux_isochempot_updateState
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief calculates homogenized vacancy driving forces
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine vacancyflux_isochempot_getSourceAndItsTangent(CvDot, dCvDot_dCv, Cv, ip, el)
|
||||
use material, only: &
|
||||
homogenization_Ngrains, &
|
||||
mappingHomogenization, &
|
||||
phaseAt, &
|
||||
phase_source, &
|
||||
phase_Nsources, &
|
||||
SOURCE_vacancy_phenoplasticity_ID, &
|
||||
SOURCE_vacancy_irradiation_ID, &
|
||||
SOURCE_vacancy_thermalfluc_ID
|
||||
use source_vacancy_phenoplasticity, only: &
|
||||
source_vacancy_phenoplasticity_getRateAndItsTangent
|
||||
use source_vacancy_irradiation, only: &
|
||||
source_vacancy_irradiation_getRateAndItsTangent
|
||||
use source_vacancy_thermalfluc, only: &
|
||||
source_vacancy_thermalfluc_getRateAndItsTangent
|
||||
|
||||
implicit none
|
||||
integer(pInt), intent(in) :: &
|
||||
ip, & !< integration point number
|
||||
el !< element number
|
||||
real(pReal), intent(in) :: &
|
||||
Cv
|
||||
integer(pInt) :: &
|
||||
phase, &
|
||||
grain, &
|
||||
source
|
||||
real(pReal) :: &
|
||||
CvDot, dCvDot_dCv, localCvDot, dLocalCvDot_dCv
|
||||
|
||||
CvDot = 0.0_pReal
|
||||
dCvDot_dCv = 0.0_pReal
|
||||
do grain = 1, homogenization_Ngrains(mappingHomogenization(2,ip,el))
|
||||
phase = phaseAt(grain,ip,el)
|
||||
do source = 1_pInt, phase_Nsources(phase)
|
||||
select case(phase_source(source,phase))
|
||||
case (SOURCE_vacancy_phenoplasticity_ID)
|
||||
call source_vacancy_phenoplasticity_getRateAndItsTangent (localCvDot, dLocalCvDot_dCv, grain, ip, el)
|
||||
|
||||
case (SOURCE_vacancy_irradiation_ID)
|
||||
call source_vacancy_irradiation_getRateAndItsTangent (localCvDot, dLocalCvDot_dCv, grain, ip, el)
|
||||
|
||||
case (SOURCE_vacancy_thermalfluc_ID)
|
||||
call source_vacancy_thermalfluc_getRateAndItsTangent(localCvDot, dLocalCvDot_dCv, grain, ip, el)
|
||||
|
||||
end select
|
||||
CvDot = CvDot + localCvDot
|
||||
dCvDot_dCv = dCvDot_dCv + dLocalCvDot_dCv
|
||||
enddo
|
||||
enddo
|
||||
|
||||
CvDot = CvDot/real(homogenization_Ngrains(mappingHomogenization(2,ip,el)),pReal)
|
||||
dCvDot_dCv = dCvDot_dCv/real(homogenization_Ngrains(mappingHomogenization(2,ip,el)),pReal)
|
||||
|
||||
end subroutine vacancyflux_isochempot_getSourceAndItsTangent
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief return array of vacancy transport results
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
function vacancyflux_isochempot_postResults(ip,el)
|
||||
use material, only: &
|
||||
mappingHomogenization, &
|
||||
vacancyflux_typeInstance, &
|
||||
vacancyConc, &
|
||||
vacancyfluxMapping
|
||||
|
||||
implicit none
|
||||
integer(pInt), intent(in) :: &
|
||||
ip, & !< integration point
|
||||
el !< element
|
||||
real(pReal), dimension(vacancyflux_isochempot_sizePostResults(vacancyflux_typeInstance(mappingHomogenization(2,ip,el)))) :: &
|
||||
vacancyflux_isochempot_postResults
|
||||
|
||||
integer(pInt) :: &
|
||||
instance, homog, offset, o, c
|
||||
|
||||
homog = mappingHomogenization(2,ip,el)
|
||||
offset = vacancyfluxMapping(homog)%p(ip,el)
|
||||
instance = vacancyflux_typeInstance(homog)
|
||||
|
||||
c = 0_pInt
|
||||
vacancyflux_isochempot_postResults = 0.0_pReal
|
||||
|
||||
do o = 1_pInt,vacancyflux_isochempot_Noutput(instance)
|
||||
select case(vacancyflux_isochempot_outputID(o,instance))
|
||||
|
||||
case (vacancyconc_ID)
|
||||
vacancyflux_isochempot_postResults(c+1_pInt) = vacancyConc(homog)%p(offset)
|
||||
c = c + 1
|
||||
end select
|
||||
enddo
|
||||
end function vacancyflux_isochempot_postResults
|
||||
|
||||
end module vacancyflux_isochempot
|
|
@ -1,62 +0,0 @@
|
|||
!--------------------------------------------------------------------------------------------------
|
||||
!> @author Pratheek Shanthraj, Max-Planck-Institut für Eisenforschung GmbH
|
||||
!> @brief material subroutine for constant vacancy concentration
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
module vacancyflux_isoconc
|
||||
|
||||
implicit none
|
||||
private
|
||||
|
||||
public :: &
|
||||
vacancyflux_isoconc_init
|
||||
|
||||
contains
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief allocates all neccessary fields, reads information from material configuration file
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine vacancyflux_isoconc_init()
|
||||
#if defined(__GFORTRAN__) || __INTEL_COMPILER >= 1800
|
||||
use, intrinsic :: iso_fortran_env, only: &
|
||||
compiler_version, &
|
||||
compiler_options
|
||||
#endif
|
||||
use prec, only: &
|
||||
pReal, &
|
||||
pInt
|
||||
use IO, only: &
|
||||
IO_timeStamp
|
||||
use material
|
||||
use config
|
||||
|
||||
implicit none
|
||||
integer(pInt) :: &
|
||||
homog, &
|
||||
NofMyHomog
|
||||
|
||||
write(6,'(/,a)') ' <<<+- vacancyflux_'//VACANCYFLUX_isoconc_label//' init -+>>>'
|
||||
write(6,'(a15,a)') ' Current time: ',IO_timeStamp()
|
||||
#include "compilation_info.f90"
|
||||
|
||||
initializeInstances: do homog = 1_pInt, material_Nhomogenization
|
||||
|
||||
myhomog: if (vacancyflux_type(homog) == VACANCYFLUX_isoconc_ID) then
|
||||
NofMyHomog = count(material_homog == homog)
|
||||
vacancyfluxState(homog)%sizeState = 0_pInt
|
||||
vacancyfluxState(homog)%sizePostResults = 0_pInt
|
||||
allocate(vacancyfluxState(homog)%state0 (0_pInt,NofMyHomog))
|
||||
allocate(vacancyfluxState(homog)%subState0(0_pInt,NofMyHomog))
|
||||
allocate(vacancyfluxState(homog)%state (0_pInt,NofMyHomog))
|
||||
|
||||
deallocate(vacancyConc (homog)%p)
|
||||
allocate (vacancyConc (homog)%p(1), source=vacancyflux_initialCv(homog))
|
||||
deallocate(vacancyConcRate(homog)%p)
|
||||
allocate (vacancyConcRate(homog)%p(1), source=0.0_pReal)
|
||||
|
||||
endif myhomog
|
||||
enddo initializeInstances
|
||||
|
||||
|
||||
end subroutine vacancyflux_isoconc_init
|
||||
|
||||
end module vacancyflux_isoconc
|
Loading…
Reference in New Issue