moved some phase field parameters to lattice

This commit is contained in:
Pratheek Shanthraj 2015-06-11 09:01:37 +00:00
parent b3241411f5
commit e8ee5d6723
4 changed files with 72 additions and 153 deletions

View File

@ -24,10 +24,6 @@ module hydrogenflux_cahnhilliard
integer(pInt), dimension(:), allocatable, target, public :: & integer(pInt), dimension(:), allocatable, target, public :: &
hydrogenflux_cahnhilliard_Noutput !< number of outputs per instance of this damage hydrogenflux_cahnhilliard_Noutput !< number of outputs per instance of this damage
real(pReal), dimension(:), allocatable, private :: &
hydrogenflux_cahnhilliard_formationEnergyCoeff, &
hydrogenflux_cahnhilliard_kBCoeff
real(pReal), parameter, private :: & real(pReal), parameter, private :: &
kB = 1.3806488e-23_pReal !< Boltzmann constant in J/Kelvin kB = 1.3806488e-23_pReal !< Boltzmann constant in J/Kelvin
@ -71,8 +67,6 @@ subroutine hydrogenflux_cahnhilliard_init(fileUnit)
IO_error, & IO_error, &
IO_timeStamp, & IO_timeStamp, &
IO_EOF IO_EOF
use lattice, only: &
lattice_hydrogenVol
use material, only: & use material, only: &
hydrogenflux_type, & hydrogenflux_type, &
hydrogenflux_typeInstance, & hydrogenflux_typeInstance, &
@ -80,7 +74,6 @@ subroutine hydrogenflux_cahnhilliard_init(fileUnit)
HYDROGENFLUX_cahnhilliard_label, & HYDROGENFLUX_cahnhilliard_label, &
HYDROGENFLUX_cahnhilliard_ID, & HYDROGENFLUX_cahnhilliard_ID, &
material_homog, & material_homog, &
material_Nphase, &
mappingHomogenization, & mappingHomogenization, &
hydrogenfluxState, & hydrogenfluxState, &
hydrogenfluxMapping, & hydrogenfluxMapping, &
@ -120,9 +113,6 @@ subroutine hydrogenflux_cahnhilliard_init(fileUnit)
allocate(hydrogenflux_cahnhilliard_outputID (maxval(homogenization_Noutput),maxNinstance),source=undefined_ID) allocate(hydrogenflux_cahnhilliard_outputID (maxval(homogenization_Noutput),maxNinstance),source=undefined_ID)
allocate(hydrogenflux_cahnhilliard_Noutput (maxNinstance), source=0_pInt) allocate(hydrogenflux_cahnhilliard_Noutput (maxNinstance), source=0_pInt)
allocate(hydrogenflux_cahnhilliard_kBCoeff (material_Nphase), source=0.0_pReal)
allocate(hydrogenflux_cahnhilliard_formationEnergyCoeff(material_Nphase), source=0.0_pReal)
rewind(fileUnit) rewind(fileUnit)
section = 0_pInt section = 0_pInt
do while (trim(line) /= IO_EOF .and. IO_lc(IO_getTag(line,'<','>')) /= material_partHomogenization)! wind forward to <homogenization> do while (trim(line) /= IO_EOF .and. IO_lc(IO_getTag(line,'<','>')) /= material_partHomogenization)! wind forward to <homogenization>
@ -166,30 +156,6 @@ subroutine hydrogenflux_cahnhilliard_init(fileUnit)
line = IO_read(fileUnit) line = IO_read(fileUnit)
enddo enddo
parsingPhase: 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
positions = IO_stringPos(line,MAXNCHUNKS)
tag = IO_lc(IO_stringValue(line,positions,1_pInt)) ! extract key
select case(tag)
case ('hydrogenformationenergy')
hydrogenflux_cahnhilliard_formationEnergyCoeff(section) = IO_floatValue(line,positions,2_pInt)
end select
endif; endif
enddo parsingPhase
initializeInstances: do section = 1_pInt, size(hydrogenflux_type) initializeInstances: do section = 1_pInt, size(hydrogenflux_type)
if (hydrogenflux_type(section) == HYDROGENFLUX_cahnhilliard_ID) then if (hydrogenflux_type(section) == HYDROGENFLUX_cahnhilliard_ID) then
NofMyHomog=count(material_homog==section) NofMyHomog=count(material_homog==section)
@ -228,15 +194,6 @@ subroutine hydrogenflux_cahnhilliard_init(fileUnit)
enddo initializeInstances enddo initializeInstances
initializeParams: do section = 1_pInt, material_Nphase
hydrogenflux_cahnhilliard_kBCoeff(section) = &
kB/ &
hydrogenflux_cahnhilliard_formationEnergyCoeff(section)
hydrogenflux_cahnhilliard_formationEnergyCoeff(section) = &
hydrogenflux_cahnhilliard_formationEnergyCoeff(section)/ &
lattice_hydrogenVol(section)
enddo initializeParams
end subroutine hydrogenflux_cahnhilliard_init end subroutine hydrogenflux_cahnhilliard_init
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
@ -313,6 +270,10 @@ end function hydrogenflux_cahnhilliard_getDiffusion33
!> @brief returns homogenized solution energy !> @brief returns homogenized solution energy
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
function hydrogenflux_cahnhilliard_getFormationEnergy(ip,el) function hydrogenflux_cahnhilliard_getFormationEnergy(ip,el)
use lattice, only: &
lattice_hydrogenFormationEnergy, &
lattice_hydrogenVol, &
lattice_hydrogenSurfaceEnergy
use material, only: & use material, only: &
homogenization_Ngrains, & homogenization_Ngrains, &
material_phase material_phase
@ -331,7 +292,9 @@ function hydrogenflux_cahnhilliard_getFormationEnergy(ip,el)
hydrogenflux_cahnhilliard_getFormationEnergy = 0.0_pReal hydrogenflux_cahnhilliard_getFormationEnergy = 0.0_pReal
do grain = 1, homogenization_Ngrains(mesh_element(3,el)) do grain = 1, homogenization_Ngrains(mesh_element(3,el))
hydrogenflux_cahnhilliard_getFormationEnergy = hydrogenflux_cahnhilliard_getFormationEnergy + & hydrogenflux_cahnhilliard_getFormationEnergy = hydrogenflux_cahnhilliard_getFormationEnergy + &
hydrogenflux_cahnhilliard_formationEnergyCoeff(material_phase(grain,ip,el)) lattice_hydrogenFormationEnergy(material_phase(grain,ip,el))/ &
lattice_hydrogenVol(material_phase(grain,ip,el))/ &
lattice_hydrogenSurfaceEnergy(material_phase(grain,ip,el))
enddo enddo
hydrogenflux_cahnhilliard_getFormationEnergy = & hydrogenflux_cahnhilliard_getFormationEnergy = &
@ -344,6 +307,9 @@ end function hydrogenflux_cahnhilliard_getFormationEnergy
!> @brief returns homogenized hydrogen entropy coefficient !> @brief returns homogenized hydrogen entropy coefficient
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
function hydrogenflux_cahnhilliard_getEntropicCoeff(ip,el) function hydrogenflux_cahnhilliard_getEntropicCoeff(ip,el)
use lattice, only: &
lattice_hydrogenVol, &
lattice_hydrogenSurfaceEnergy
use material, only: & use material, only: &
homogenization_Ngrains, & homogenization_Ngrains, &
material_homog, & material_homog, &
@ -363,7 +329,9 @@ function hydrogenflux_cahnhilliard_getEntropicCoeff(ip,el)
hydrogenflux_cahnhilliard_getEntropicCoeff = 0.0_pReal hydrogenflux_cahnhilliard_getEntropicCoeff = 0.0_pReal
do grain = 1, homogenization_Ngrains(material_homog(ip,el)) do grain = 1, homogenization_Ngrains(material_homog(ip,el))
hydrogenflux_cahnhilliard_getEntropicCoeff = hydrogenflux_cahnhilliard_getEntropicCoeff + & hydrogenflux_cahnhilliard_getEntropicCoeff = hydrogenflux_cahnhilliard_getEntropicCoeff + &
hydrogenflux_cahnhilliard_kBCoeff(material_phase(grain,ip,el)) kB/ &
lattice_hydrogenVol(material_phase(grain,ip,el))/ &
lattice_hydrogenSurfaceEnergy(material_phase(grain,ip,el))
enddo enddo
hydrogenflux_cahnhilliard_getEntropicCoeff = & hydrogenflux_cahnhilliard_getEntropicCoeff = &
@ -377,6 +345,8 @@ end function hydrogenflux_cahnhilliard_getEntropicCoeff
!> @brief returns homogenized kinematic contribution to chemical potential !> @brief returns homogenized kinematic contribution to chemical potential
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
subroutine hydrogenflux_cahnhilliard_KinematicChemPotAndItsTangent(KPot, dKPot_dCh, Ch, ip, el) subroutine hydrogenflux_cahnhilliard_KinematicChemPotAndItsTangent(KPot, dKPot_dCh, Ch, ip, el)
use lattice, only: &
lattice_hydrogenSurfaceEnergy
use material, only: & use material, only: &
homogenization_Ngrains, & homogenization_Ngrains, &
material_homog, & material_homog, &
@ -421,8 +391,8 @@ subroutine hydrogenflux_cahnhilliard_KinematicChemPotAndItsTangent(KPot, dKPot_d
my_dKPot_dCh = 0.0_pReal my_dKPot_dCh = 0.0_pReal
end select end select
KPot = KPot + my_KPot/hydrogenflux_cahnhilliard_formationEnergyCoeff(material_phase(grain,ip,el)) KPot = KPot + my_KPot/lattice_hydrogenSurfaceEnergy(material_phase(grain,ip,el))
dKPot_dCh = dKPot_dCh + my_dKPot_dCh/hydrogenflux_cahnhilliard_formationEnergyCoeff(material_phase(grain,ip,el)) dKPot_dCh = dKPot_dCh + my_dKPot_dCh/lattice_hydrogenSurfaceEnergy(material_phase(grain,ip,el))
enddo enddo
enddo enddo
@ -453,7 +423,7 @@ subroutine hydrogenflux_cahnhilliard_getChemPotAndItsTangent(ChemPot,dChemPot_dC
integer(pInt) :: & integer(pInt) :: &
o o
ChemPot = 1.0_pReal ChemPot = hydrogenflux_cahnhilliard_getFormationEnergy(ip,el)
dChemPot_dCh = 0.0_pReal dChemPot_dCh = 0.0_pReal
kBT = hydrogenflux_cahnhilliard_getEntropicCoeff(ip,el) kBT = hydrogenflux_cahnhilliard_getEntropicCoeff(ip,el)
do o = 1_pInt, hydrogenPolyOrder do o = 1_pInt, hydrogenPolyOrder

View File

@ -840,7 +840,11 @@ module lattice
lattice_porosityMobility, & lattice_porosityMobility, &
lattice_massDensity, & lattice_massDensity, &
lattice_specificHeat, & lattice_specificHeat, &
lattice_vacancyFormationEnergy, &
lattice_vacancySurfaceEnergy, &
lattice_vacancyVol, & lattice_vacancyVol, &
lattice_hydrogenFormationEnergy, &
lattice_hydrogenSurfaceEnergy, &
lattice_hydrogenVol, & lattice_hydrogenVol, &
lattice_referenceTemperature, & lattice_referenceTemperature, &
lattice_equilibriumVacancyConcentration lattice_equilibriumVacancyConcentration
@ -1116,7 +1120,11 @@ subroutine lattice_init
allocate(lattice_PorosityMobility ( Nphases), source=0.0_pReal) allocate(lattice_PorosityMobility ( Nphases), source=0.0_pReal)
allocate(lattice_massDensity ( Nphases), source=0.0_pReal) allocate(lattice_massDensity ( Nphases), source=0.0_pReal)
allocate(lattice_specificHeat ( Nphases), source=0.0_pReal) allocate(lattice_specificHeat ( Nphases), source=0.0_pReal)
allocate(lattice_vacancyFormationEnergy ( Nphases), source=0.0_pReal)
allocate(lattice_vacancySurfaceEnergy ( Nphases), source=0.0_pReal)
allocate(lattice_vacancyVol ( Nphases), source=0.0_pReal) allocate(lattice_vacancyVol ( Nphases), source=0.0_pReal)
allocate(lattice_hydrogenFormationEnergy( Nphases), source=0.0_pReal)
allocate(lattice_hydrogenSurfaceEnergy ( Nphases), source=0.0_pReal)
allocate(lattice_hydrogenVol ( Nphases), source=0.0_pReal) allocate(lattice_hydrogenVol ( Nphases), source=0.0_pReal)
allocate(lattice_referenceTemperature ( Nphases), source=0.0_pReal) allocate(lattice_referenceTemperature ( Nphases), source=0.0_pReal)
allocate(lattice_equilibriumVacancyConcentration(Nphases), source=0.0_pReal) allocate(lattice_equilibriumVacancyConcentration(Nphases), source=0.0_pReal)
@ -1244,8 +1252,16 @@ subroutine lattice_init
lattice_thermalExpansion33(3,3,section) = IO_floatValue(line,positions,2_pInt) lattice_thermalExpansion33(3,3,section) = IO_floatValue(line,positions,2_pInt)
case ('specific_heat') case ('specific_heat')
lattice_specificHeat(section) = IO_floatValue(line,positions,2_pInt) lattice_specificHeat(section) = IO_floatValue(line,positions,2_pInt)
case ('vacancyformationenergy')
lattice_vacancyFormationEnergy(section) = IO_floatValue(line,positions,2_pInt)
case ('vacancysurfaceenergy')
lattice_vacancySurfaceEnergy(section) = IO_floatValue(line,positions,2_pInt)
case ('vacancyvolume') case ('vacancyvolume')
lattice_vacancyVol(section) = IO_floatValue(line,positions,2_pInt) lattice_vacancyVol(section) = IO_floatValue(line,positions,2_pInt)
case ('hydrogenformationenergy')
lattice_hydrogenFormationEnergy(section) = IO_floatValue(line,positions,2_pInt)
case ('hydrogensurfaceenergy')
lattice_hydrogenSurfaceEnergy(section) = IO_floatValue(line,positions,2_pInt)
case ('hydrogenvolume') case ('hydrogenvolume')
lattice_hydrogenVol(section) = IO_floatValue(line,positions,2_pInt) lattice_hydrogenVol(section) = IO_floatValue(line,positions,2_pInt)
case ('mass_density') case ('mass_density')

View File

@ -24,10 +24,6 @@ module porosity_phasefield
integer(pInt), dimension(:), allocatable, target, public :: & integer(pInt), dimension(:), allocatable, target, public :: &
porosity_phasefield_Noutput !< number of outputs per instance of this porosity porosity_phasefield_Noutput !< number of outputs per instance of this porosity
real(pReal), dimension(:), allocatable, private :: &
porosity_phasefield_specificFormationEnergy, &
porosity_phasefield_surfaceEnergy
enum, bind(c) enum, bind(c)
enumerator :: undefined_ID, & enumerator :: undefined_ID, &
porosity_ID porosity_ID
@ -68,8 +64,6 @@ subroutine porosity_phasefield_init(fileUnit)
IO_error, & IO_error, &
IO_timeStamp, & IO_timeStamp, &
IO_EOF IO_EOF
use lattice, only: &
lattice_vacancyVol
use material, only: & use material, only: &
porosity_type, & porosity_type, &
porosity_typeInstance, & porosity_typeInstance, &
@ -77,7 +71,6 @@ subroutine porosity_phasefield_init(fileUnit)
POROSITY_phasefield_label, & POROSITY_phasefield_label, &
POROSITY_phasefield_ID, & POROSITY_phasefield_ID, &
material_homog, & material_homog, &
material_Nphase, &
mappingHomogenization, & mappingHomogenization, &
porosityState, & porosityState, &
porosityMapping, & porosityMapping, &
@ -115,8 +108,6 @@ subroutine porosity_phasefield_init(fileUnit)
porosity_phasefield_output = '' porosity_phasefield_output = ''
allocate(porosity_phasefield_outputID (maxval(homogenization_Noutput),maxNinstance),source=undefined_ID) allocate(porosity_phasefield_outputID (maxval(homogenization_Noutput),maxNinstance),source=undefined_ID)
allocate(porosity_phasefield_Noutput (maxNinstance), source=0_pInt) allocate(porosity_phasefield_Noutput (maxNinstance), source=0_pInt)
allocate(porosity_phasefield_specificFormationEnergy(material_Nphase), source=0.0_pReal)
allocate(porosity_phasefield_surfaceEnergy (material_Nphase), source=0.0_pReal)
rewind(fileUnit) rewind(fileUnit)
section = 0_pInt section = 0_pInt
@ -155,40 +146,6 @@ subroutine porosity_phasefield_init(fileUnit)
endif; endif endif; endif
enddo parsingHomog 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
parsingPhase: 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
positions = IO_stringPos(line,MAXNCHUNKS)
tag = IO_lc(IO_stringValue(line,positions,1_pInt)) ! extract key
select case(tag)
case ('vacancyformationenergy')
porosity_phasefield_specificFormationEnergy(section) = IO_floatValue(line,positions,2_pInt)/&
lattice_vacancyVol(section)
case ('voidsurfaceenergy')
porosity_phasefield_surfaceEnergy(section) = IO_floatValue(line,positions,2_pInt)
end select
endif; endif
enddo parsingPhase
initializeInstances: do section = 1_pInt, size(porosity_type) initializeInstances: do section = 1_pInt, size(porosity_type)
if (porosity_type(section) == POROSITY_phasefield_ID) then if (porosity_type(section) == POROSITY_phasefield_ID) then
NofMyHomog=count(material_homog==section) NofMyHomog=count(material_homog==section)
@ -230,6 +187,9 @@ end subroutine porosity_phasefield_init
!> @brief returns homogenized vacancy formation energy !> @brief returns homogenized vacancy formation energy
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
function porosity_phasefield_getFormationEnergy(ip,el) function porosity_phasefield_getFormationEnergy(ip,el)
use lattice, only: &
lattice_vacancyFormationEnergy, &
lattice_vacancyVol
use material, only: & use material, only: &
homogenization_Ngrains, & homogenization_Ngrains, &
material_phase material_phase
@ -248,7 +208,8 @@ function porosity_phasefield_getFormationEnergy(ip,el)
porosity_phasefield_getFormationEnergy = 0.0_pReal porosity_phasefield_getFormationEnergy = 0.0_pReal
do grain = 1, homogenization_Ngrains(mesh_element(3,el)) do grain = 1, homogenization_Ngrains(mesh_element(3,el))
porosity_phasefield_getFormationEnergy = porosity_phasefield_getFormationEnergy + & porosity_phasefield_getFormationEnergy = porosity_phasefield_getFormationEnergy + &
porosity_phasefield_specificFormationEnergy(material_phase(grain,ip,el)) lattice_vacancyFormationEnergy(material_phase(grain,ip,el))/ &
lattice_vacancyVol(material_phase(grain,ip,el))
enddo enddo
porosity_phasefield_getFormationEnergy = & porosity_phasefield_getFormationEnergy = &
@ -261,6 +222,8 @@ end function porosity_phasefield_getFormationEnergy
!> @brief returns homogenized pore surface energy (normalized by characteristic length) !> @brief returns homogenized pore surface energy (normalized by characteristic length)
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
function porosity_phasefield_getSurfaceEnergy(ip,el) function porosity_phasefield_getSurfaceEnergy(ip,el)
use lattice, only: &
lattice_vacancySurfaceEnergy
use material, only: & use material, only: &
homogenization_Ngrains, & homogenization_Ngrains, &
material_phase material_phase
@ -279,7 +242,7 @@ function porosity_phasefield_getSurfaceEnergy(ip,el)
porosity_phasefield_getSurfaceEnergy = 0.0_pReal porosity_phasefield_getSurfaceEnergy = 0.0_pReal
do grain = 1, homogenization_Ngrains(mesh_element(3,el)) do grain = 1, homogenization_Ngrains(mesh_element(3,el))
porosity_phasefield_getSurfaceEnergy = porosity_phasefield_getSurfaceEnergy + & porosity_phasefield_getSurfaceEnergy = porosity_phasefield_getSurfaceEnergy + &
porosity_phasefield_surfaceEnergy(material_phase(grain,ip,el)) lattice_vacancySurfaceEnergy(material_phase(grain,ip,el))
enddo enddo
porosity_phasefield_getSurfaceEnergy = & porosity_phasefield_getSurfaceEnergy = &

View File

@ -26,9 +26,7 @@ module vacancyflux_cahnhilliard
vacancyflux_cahnhilliard_Noutput !< number of outputs per instance of this damage vacancyflux_cahnhilliard_Noutput !< number of outputs per instance of this damage
real(pReal), dimension(:), allocatable, private :: & real(pReal), dimension(:), allocatable, private :: &
vacancyflux_cahnhilliard_formationEnergyCoeff, & vacancyflux_cahnhilliard_flucAmplitude
vacancyflux_cahnhilliard_surfaceEnergy, &
vacancyflux_cahnhilliard_kBCoeff
type(p_vec), dimension(:), allocatable, private :: & type(p_vec), dimension(:), allocatable, private :: &
vacancyflux_cahnhilliard_thermalFluc vacancyflux_cahnhilliard_thermalFluc
@ -79,8 +77,6 @@ subroutine vacancyflux_cahnhilliard_init(fileUnit)
IO_error, & IO_error, &
IO_timeStamp, & IO_timeStamp, &
IO_EOF IO_EOF
use lattice, only: &
lattice_vacancyVol
use material, only: & use material, only: &
vacancyflux_type, & vacancyflux_type, &
vacancyflux_typeInstance, & vacancyflux_typeInstance, &
@ -88,7 +84,6 @@ subroutine vacancyflux_cahnhilliard_init(fileUnit)
VACANCYFLUX_cahnhilliard_label, & VACANCYFLUX_cahnhilliard_label, &
VACANCYFLUX_cahnhilliard_ID, & VACANCYFLUX_cahnhilliard_ID, &
material_homog, & material_homog, &
material_Nphase, &
mappingHomogenization, & mappingHomogenization, &
vacancyfluxState, & vacancyfluxState, &
vacancyfluxMapping, & vacancyfluxMapping, &
@ -128,11 +123,8 @@ subroutine vacancyflux_cahnhilliard_init(fileUnit)
allocate(vacancyflux_cahnhilliard_outputID (maxval(homogenization_Noutput),maxNinstance),source=undefined_ID) allocate(vacancyflux_cahnhilliard_outputID (maxval(homogenization_Noutput),maxNinstance),source=undefined_ID)
allocate(vacancyflux_cahnhilliard_Noutput (maxNinstance), source=0_pInt) allocate(vacancyflux_cahnhilliard_Noutput (maxNinstance), source=0_pInt)
allocate(vacancyflux_cahnhilliard_formationEnergyCoeff(material_Nphase), source=0.0_pReal) allocate(vacancyflux_cahnhilliard_flucAmplitude (maxNinstance))
allocate(vacancyflux_cahnhilliard_kBCoeff (material_Nphase), source=0.0_pReal) allocate(vacancyflux_cahnhilliard_thermalFluc (maxNinstance))
allocate(vacancyflux_cahnhilliard_surfaceEnergy (material_Nphase), source=0.0_pReal)
allocate(vacancyflux_cahnhilliard_thermalFluc(maxNinstance))
rewind(fileUnit) rewind(fileUnit)
section = 0_pInt section = 0_pInt
@ -167,43 +159,13 @@ subroutine vacancyflux_cahnhilliard_init(fileUnit)
IO_lc(IO_stringValue(line,positions,2_pInt)) IO_lc(IO_stringValue(line,positions,2_pInt))
end select end select
case ('vacancyflux_flucamplitude')
vacancyflux_cahnhilliard_flucAmplitude(instance) = IO_floatValue(line,positions,2_pInt)
end select end select
endif; endif endif; endif
enddo parsingHomog 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
parsingPhase: 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
positions = IO_stringPos(line,MAXNCHUNKS)
tag = IO_lc(IO_stringValue(line,positions,1_pInt)) ! extract key
select case(tag)
case ('vacancyformationenergy')
vacancyflux_cahnhilliard_formationEnergyCoeff(section) = IO_floatValue(line,positions,2_pInt)
case ('voidsurfaceenergy')
vacancyflux_cahnhilliard_surfaceEnergy(section) = IO_floatValue(line,positions,2_pInt)
end select
endif; endif
enddo parsingPhase
initializeInstances: do section = 1_pInt, size(vacancyflux_type) initializeInstances: do section = 1_pInt, size(vacancyflux_type)
if (vacancyflux_type(section) == VACANCYFLUX_cahnhilliard_ID) then if (vacancyflux_type(section) == VACANCYFLUX_cahnhilliard_ID) then
NofMyHomog=count(material_homog==section) NofMyHomog=count(material_homog==section)
@ -234,6 +196,10 @@ subroutine vacancyflux_cahnhilliard_init(fileUnit)
allocate(vacancyflux_cahnhilliard_thermalFluc(instance)%p(NofMyHomog)) allocate(vacancyflux_cahnhilliard_thermalFluc(instance)%p(NofMyHomog))
do offset = 1_pInt, NofMyHomog do offset = 1_pInt, NofMyHomog
call random_number(vacancyflux_cahnhilliard_thermalFluc(instance)%p(offset)) 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 enddo
nullify(vacancyfluxMapping(section)%p) nullify(vacancyfluxMapping(section)%p)
@ -247,17 +213,6 @@ subroutine vacancyflux_cahnhilliard_init(fileUnit)
enddo initializeInstances enddo initializeInstances
initializeParams: do section = 1_pInt, material_Nphase
vacancyflux_cahnhilliard_formationEnergyCoeff(section) = &
vacancyflux_cahnhilliard_formationEnergyCoeff(section)/ &
lattice_vacancyVol(section)/ &
vacancyflux_cahnhilliard_surfaceEnergy(section)
vacancyflux_cahnhilliard_kBCoeff(section) = &
kB/ &
lattice_vacancyVol(section)/ &
vacancyflux_cahnhilliard_surfaceEnergy(section)
enddo initializeParams
end subroutine vacancyflux_cahnhilliard_init end subroutine vacancyflux_cahnhilliard_init
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
@ -393,6 +348,10 @@ end function vacancyflux_cahnhilliard_getDiffusion33
!> @brief returns homogenized vacancy formation energy !> @brief returns homogenized vacancy formation energy
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
function vacancyflux_cahnhilliard_getFormationEnergy(ip,el) function vacancyflux_cahnhilliard_getFormationEnergy(ip,el)
use lattice, only: &
lattice_vacancyFormationEnergy, &
lattice_vacancyVol, &
lattice_vacancySurfaceEnergy
use material, only: & use material, only: &
homogenization_Ngrains, & homogenization_Ngrains, &
material_phase material_phase
@ -411,7 +370,9 @@ function vacancyflux_cahnhilliard_getFormationEnergy(ip,el)
vacancyflux_cahnhilliard_getFormationEnergy = 0.0_pReal vacancyflux_cahnhilliard_getFormationEnergy = 0.0_pReal
do grain = 1, homogenization_Ngrains(mesh_element(3,el)) do grain = 1, homogenization_Ngrains(mesh_element(3,el))
vacancyflux_cahnhilliard_getFormationEnergy = vacancyflux_cahnhilliard_getFormationEnergy + & vacancyflux_cahnhilliard_getFormationEnergy = vacancyflux_cahnhilliard_getFormationEnergy + &
vacancyflux_cahnhilliard_formationEnergyCoeff(material_phase(grain,ip,el)) lattice_vacancyFormationEnergy(material_phase(grain,ip,el))/ &
lattice_vacancyVol(material_phase(grain,ip,el))/ &
lattice_vacancySurfaceEnergy(material_phase(grain,ip,el))
enddo enddo
vacancyflux_cahnhilliard_getFormationEnergy = & vacancyflux_cahnhilliard_getFormationEnergy = &
@ -424,6 +385,9 @@ end function vacancyflux_cahnhilliard_getFormationEnergy
!> @brief returns homogenized vacancy entropy coefficient !> @brief returns homogenized vacancy entropy coefficient
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
function vacancyflux_cahnhilliard_getEntropicCoeff(ip,el) function vacancyflux_cahnhilliard_getEntropicCoeff(ip,el)
use lattice, only: &
lattice_vacancyVol, &
lattice_vacancySurfaceEnergy
use material, only: & use material, only: &
homogenization_Ngrains, & homogenization_Ngrains, &
material_homog, & material_homog, &
@ -443,7 +407,9 @@ function vacancyflux_cahnhilliard_getEntropicCoeff(ip,el)
vacancyflux_cahnhilliard_getEntropicCoeff = 0.0_pReal vacancyflux_cahnhilliard_getEntropicCoeff = 0.0_pReal
do grain = 1, homogenization_Ngrains(material_homog(ip,el)) do grain = 1, homogenization_Ngrains(material_homog(ip,el))
vacancyflux_cahnhilliard_getEntropicCoeff = vacancyflux_cahnhilliard_getEntropicCoeff + & vacancyflux_cahnhilliard_getEntropicCoeff = vacancyflux_cahnhilliard_getEntropicCoeff + &
vacancyflux_cahnhilliard_kBCoeff(material_phase(grain,ip,el)) kB/ &
lattice_vacancyVol(material_phase(grain,ip,el))/ &
lattice_vacancySurfaceEnergy(material_phase(grain,ip,el))
enddo enddo
vacancyflux_cahnhilliard_getEntropicCoeff = & vacancyflux_cahnhilliard_getEntropicCoeff = &
@ -457,6 +423,8 @@ end function vacancyflux_cahnhilliard_getEntropicCoeff
!> @brief returns homogenized kinematic contribution to chemical potential !> @brief returns homogenized kinematic contribution to chemical potential
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
subroutine vacancyflux_cahnhilliard_KinematicChemPotAndItsTangent(KPot, dKPot_dCv, Cv, ip, el) subroutine vacancyflux_cahnhilliard_KinematicChemPotAndItsTangent(KPot, dKPot_dCv, Cv, ip, el)
use lattice, only: &
lattice_vacancySurfaceEnergy
use material, only: & use material, only: &
homogenization_Ngrains, & homogenization_Ngrains, &
material_homog, & material_homog, &
@ -501,8 +469,8 @@ subroutine vacancyflux_cahnhilliard_KinematicChemPotAndItsTangent(KPot, dKPot_dC
my_dKPot_dCv = 0.0_pReal my_dKPot_dCv = 0.0_pReal
end select end select
KPot = KPot + my_KPot/vacancyflux_cahnhilliard_surfaceEnergy(material_phase(grain,ip,el)) KPot = KPot + my_KPot/lattice_vacancySurfaceEnergy(material_phase(grain,ip,el))
dKPot_dCv = dKPot_dCv + my_dKPot_dCv/vacancyflux_cahnhilliard_surfaceEnergy(material_phase(grain,ip,el)) dKPot_dCv = dKPot_dCv + my_dKPot_dCv/lattice_vacancySurfaceEnergy(material_phase(grain,ip,el))
enddo enddo
enddo enddo
@ -520,6 +488,7 @@ subroutine vacancyflux_cahnhilliard_getChemPotAndItsTangent(ChemPot,dChemPot_dCv
vacancyPolyOrder vacancyPolyOrder
use material, only: & use material, only: &
mappingHomogenization, & mappingHomogenization, &
vacancyflux_typeInstance, &
porosity, & porosity, &
porosityMapping porosityMapping
@ -541,7 +510,8 @@ subroutine vacancyflux_cahnhilliard_getChemPotAndItsTangent(ChemPot,dChemPot_dCv
VoidPhaseFrac = porosity(homog)%p(porosityMapping(homog)%p(ip,el)) VoidPhaseFrac = porosity(homog)%p(porosityMapping(homog)%p(ip,el))
kBT = vacancyflux_cahnhilliard_getEntropicCoeff(ip,el) kBT = vacancyflux_cahnhilliard_getEntropicCoeff(ip,el)
ChemPot = vacancyflux_cahnhilliard_getFormationEnergy(ip,el) ChemPot = vacancyflux_cahnhilliard_getFormationEnergy(ip,el)* &
vacancyflux_cahnhilliard_thermalFluc(vacancyflux_typeInstance(homog))%p(mappingHomogenization(1,ip,el))
dChemPot_dCv = 0.0_pReal dChemPot_dCv = 0.0_pReal
do o = 1_pInt, vacancyPolyOrder do o = 1_pInt, vacancyPolyOrder
ChemPot = ChemPot + kBT*((2.0_pReal*Cv - 1.0_pReal)**real(2_pInt*o-1_pInt,pReal))/ & ChemPot = ChemPot + kBT*((2.0_pReal*Cv - 1.0_pReal)**real(2_pInt*o-1_pInt,pReal))/ &