use subdirectory to streamline CMake build system.
This commit is contained in:
parent
eb3c328756
commit
eae0c3c2a4
|
@ -1,5 +1,5 @@
|
||||||
# Initial attempt of using CMake to build the spectral solver
|
# INITIAL ATTEMPT OF USING CMAKE TO BUILD THE SPECTRAL SOLVER
|
||||||
# --> CMake should be able to take care of the dependence by itself.
|
# CMAKE SHOULD BE ABLE TO TAKE CARE OF THE DEPENDENCE BY ITSELF.
|
||||||
#
|
#
|
||||||
cmake_minimum_required (VERSION 3.1.0)
|
cmake_minimum_required (VERSION 3.1.0)
|
||||||
project (DAMASKSpectral Fortran)
|
project (DAMASKSpectral Fortran)
|
||||||
|
@ -52,5 +52,15 @@ else (Fortran_COMPILER_NAME MATCHES "gfortran.*")
|
||||||
endif (Fortran_COMPILER_NAME MATCHES "gfortran.*")
|
endif (Fortran_COMPILER_NAME MATCHES "gfortran.*")
|
||||||
|
|
||||||
|
|
||||||
# add code(source) directory
|
# ADD CODE(SOURCE) DIRECTORY
|
||||||
add_subdirectory(code)
|
add_subdirectory(code)
|
||||||
|
|
||||||
|
|
||||||
|
# ADD TESTING CASES
|
||||||
|
add_test (SmokeTestRun
|
||||||
|
DAMASK_spectral.exe -g test/test1.geom -l test/test.load)
|
||||||
|
|
||||||
|
|
||||||
|
# Enable Dashboard scripting
|
||||||
|
# include (CTest)
|
||||||
|
# set (CTEST_PROJECT_NAME "DAMASK")
|
||||||
|
|
|
@ -25,6 +25,11 @@ foreach (p ${SRC})
|
||||||
add_library (${p} MODULE "${p}.f90")
|
add_library (${p} MODULE "${p}.f90")
|
||||||
endforeach (p)
|
endforeach (p)
|
||||||
|
|
||||||
|
# set libraries/modules for linking
|
||||||
|
foreach (p ${SRC})
|
||||||
|
set (AUX_LIB ${AUX_LIB} ${p})
|
||||||
|
endforeach (p)
|
||||||
|
|
||||||
# compile each sub moudel
|
# compile each sub moudel
|
||||||
add_subdirectory(damage)
|
add_subdirectory(damage)
|
||||||
add_subdirectory(homogenization)
|
add_subdirectory(homogenization)
|
||||||
|
@ -39,3 +44,4 @@ add_subdirectory(vacancyflux)
|
||||||
|
|
||||||
# compile spectral solver
|
# compile spectral solver
|
||||||
add_executable(DAMASKSpectral.exe DAMASK_spectral.f90)
|
add_executable(DAMASKSpectral.exe DAMASK_spectral.f90)
|
||||||
|
target_link_libraries (DAMASKSpectral.exe ${AUX_LIB})
|
|
@ -8,3 +8,8 @@ set (DAMAGE "damage_none"
|
||||||
foreach (p ${DAMAGE})
|
foreach (p ${DAMAGE})
|
||||||
add_library (${p} MODULE "${p}.f90")
|
add_library (${p} MODULE "${p}.f90")
|
||||||
endforeach (p)
|
endforeach (p)
|
||||||
|
|
||||||
|
# set libraries for linking
|
||||||
|
foreach (p ${DAMAGE})
|
||||||
|
set (AUX_LIB ${AUX_LIB} ${P})
|
||||||
|
endforeach (p)
|
|
@ -1,327 +0,0 @@
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! $Id$
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @author Pratheek Shanthraj, Max-Planck-Institut für Eisenforschung GmbH
|
|
||||||
!> @brief material subroutine for locally evolving damage field
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
module damage_local
|
|
||||||
use prec, only: &
|
|
||||||
pReal, &
|
|
||||||
pInt
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
private
|
|
||||||
integer(pInt), dimension(:), allocatable, public, protected :: &
|
|
||||||
damage_local_sizePostResults !< cumulative size of post results
|
|
||||||
|
|
||||||
integer(pInt), dimension(:,:), allocatable, target, public :: &
|
|
||||||
damage_local_sizePostResult !< size of each post result output
|
|
||||||
|
|
||||||
character(len=64), dimension(:,:), allocatable, target, public :: &
|
|
||||||
damage_local_output !< name of each post result output
|
|
||||||
|
|
||||||
integer(pInt), dimension(:), allocatable, target, public :: &
|
|
||||||
damage_local_Noutput !< number of outputs per instance of this damage
|
|
||||||
|
|
||||||
enum, bind(c)
|
|
||||||
enumerator :: undefined_ID, &
|
|
||||||
damage_ID
|
|
||||||
end enum
|
|
||||||
integer(kind(undefined_ID)), dimension(:,:), allocatable, private :: &
|
|
||||||
damage_local_outputID !< ID of each post result output
|
|
||||||
|
|
||||||
public :: &
|
|
||||||
damage_local_init, &
|
|
||||||
damage_local_updateState, &
|
|
||||||
damage_local_postResults
|
|
||||||
private :: &
|
|
||||||
damage_local_getSourceAndItsTangent
|
|
||||||
|
|
||||||
contains
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief allocates all neccessary fields, reads information from material configuration file
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine damage_local_init(fileUnit)
|
|
||||||
use, intrinsic :: iso_fortran_env ! to get compiler_version and compiler_options (at least for gfortran 4.6 at the moment)
|
|
||||||
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: &
|
|
||||||
damage_type, &
|
|
||||||
damage_typeInstance, &
|
|
||||||
homogenization_Noutput, &
|
|
||||||
DAMAGE_local_label, &
|
|
||||||
DAMAGE_local_ID, &
|
|
||||||
material_homog, &
|
|
||||||
mappingHomogenization, &
|
|
||||||
damageState, &
|
|
||||||
damageMapping, &
|
|
||||||
damage, &
|
|
||||||
damage_initialPhi, &
|
|
||||||
material_partHomogenization
|
|
||||||
use numerics,only: &
|
|
||||||
worldrank
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
integer(pInt), intent(in) :: fileUnit
|
|
||||||
|
|
||||||
integer(pInt), allocatable, dimension(:) :: chunkPos
|
|
||||||
integer(pInt) :: maxNinstance,mySize=0_pInt,homog,instance,o
|
|
||||||
integer(pInt) :: sizeState
|
|
||||||
integer(pInt) :: NofMyHomog
|
|
||||||
character(len=65536) :: &
|
|
||||||
tag = '', &
|
|
||||||
line = ''
|
|
||||||
|
|
||||||
mainProcess: if (worldrank == 0) then
|
|
||||||
write(6,'(/,a)') ' <<<+- damage_'//DAMAGE_local_label//' init -+>>>'
|
|
||||||
write(6,'(a15,a)') ' Current time: ',IO_timeStamp()
|
|
||||||
#include "compilation_info.f90"
|
|
||||||
endif mainProcess
|
|
||||||
|
|
||||||
maxNinstance = int(count(damage_type == DAMAGE_local_ID),pInt)
|
|
||||||
if (maxNinstance == 0_pInt) return
|
|
||||||
|
|
||||||
allocate(damage_local_sizePostResults(maxNinstance), source=0_pInt)
|
|
||||||
allocate(damage_local_sizePostResult (maxval(homogenization_Noutput),maxNinstance),source=0_pInt)
|
|
||||||
allocate(damage_local_output (maxval(homogenization_Noutput),maxNinstance))
|
|
||||||
damage_local_output = ''
|
|
||||||
allocate(damage_local_outputID (maxval(homogenization_Noutput),maxNinstance),source=undefined_ID)
|
|
||||||
allocate(damage_local_Noutput (maxNinstance), source=0_pInt)
|
|
||||||
|
|
||||||
rewind(fileUnit)
|
|
||||||
homog = 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
|
|
||||||
homog = homog + 1_pInt ! advance homog section counter
|
|
||||||
cycle ! skip to next line
|
|
||||||
endif
|
|
||||||
|
|
||||||
if (homog > 0_pInt ) then; if (damage_type(homog) == DAMAGE_local_ID) then ! do not short-circuit here (.and. with next if statemen). It's not safe in Fortran
|
|
||||||
|
|
||||||
instance = damage_typeInstance(homog) ! which instance of my damage 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 ('damage')
|
|
||||||
damage_local_Noutput(instance) = damage_local_Noutput(instance) + 1_pInt
|
|
||||||
damage_local_outputID(damage_local_Noutput(instance),instance) = damage_ID
|
|
||||||
damage_local_output(damage_local_Noutput(instance),instance) = &
|
|
||||||
IO_lc(IO_stringValue(line,chunkPos,2_pInt))
|
|
||||||
end select
|
|
||||||
|
|
||||||
end select
|
|
||||||
endif; endif
|
|
||||||
enddo parsingFile
|
|
||||||
|
|
||||||
initializeInstances: do homog = 1_pInt, size(damage_type)
|
|
||||||
|
|
||||||
myhomog: if (damage_type(homog) == DAMAGE_local_ID) then
|
|
||||||
NofMyHomog = count(material_homog == homog)
|
|
||||||
instance = damage_typeInstance(homog)
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! Determine size of postResults array
|
|
||||||
outputsLoop: do o = 1_pInt,damage_local_Noutput(instance)
|
|
||||||
select case(damage_local_outputID(o,instance))
|
|
||||||
case(damage_ID)
|
|
||||||
mySize = 1_pInt
|
|
||||||
end select
|
|
||||||
|
|
||||||
if (mySize > 0_pInt) then ! any meaningful output found
|
|
||||||
damage_local_sizePostResult(o,instance) = mySize
|
|
||||||
damage_local_sizePostResults(instance) = damage_local_sizePostResults(instance) + mySize
|
|
||||||
endif
|
|
||||||
enddo outputsLoop
|
|
||||||
|
|
||||||
! allocate state arrays
|
|
||||||
sizeState = 1_pInt
|
|
||||||
damageState(homog)%sizeState = sizeState
|
|
||||||
damageState(homog)%sizePostResults = damage_local_sizePostResults(instance)
|
|
||||||
allocate(damageState(homog)%state0 (sizeState,NofMyHomog), source=damage_initialPhi(homog))
|
|
||||||
allocate(damageState(homog)%subState0(sizeState,NofMyHomog), source=damage_initialPhi(homog))
|
|
||||||
allocate(damageState(homog)%state (sizeState,NofMyHomog), source=damage_initialPhi(homog))
|
|
||||||
|
|
||||||
nullify(damageMapping(homog)%p)
|
|
||||||
damageMapping(homog)%p => mappingHomogenization(1,:,:)
|
|
||||||
deallocate(damage(homog)%p)
|
|
||||||
damage(homog)%p => damageState(homog)%state(1,:)
|
|
||||||
|
|
||||||
endif myhomog
|
|
||||||
enddo initializeInstances
|
|
||||||
|
|
||||||
|
|
||||||
end subroutine damage_local_init
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief calculates local change in damage field
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
function damage_local_updateState(subdt, ip, el)
|
|
||||||
use numerics, only: &
|
|
||||||
residualStiffness, &
|
|
||||||
err_damage_tolAbs, &
|
|
||||||
err_damage_tolRel
|
|
||||||
use material, only: &
|
|
||||||
mappingHomogenization, &
|
|
||||||
damageState
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
integer(pInt), intent(in) :: &
|
|
||||||
ip, & !< integration point number
|
|
||||||
el !< element number
|
|
||||||
real(pReal), intent(in) :: &
|
|
||||||
subdt
|
|
||||||
logical, dimension(2) :: &
|
|
||||||
damage_local_updateState
|
|
||||||
integer(pInt) :: &
|
|
||||||
homog, &
|
|
||||||
offset
|
|
||||||
real(pReal) :: &
|
|
||||||
phi, phiDot, dPhiDot_dPhi
|
|
||||||
|
|
||||||
homog = mappingHomogenization(2,ip,el)
|
|
||||||
offset = mappingHomogenization(1,ip,el)
|
|
||||||
phi = damageState(homog)%subState0(1,offset)
|
|
||||||
call damage_local_getSourceAndItsTangent(phiDot, dPhiDot_dPhi, phi, ip, el)
|
|
||||||
phi = max(residualStiffness,min(1.0_pReal,phi + subdt*phiDot))
|
|
||||||
|
|
||||||
damage_local_updateState = [ abs(phi - damageState(homog)%state(1,offset)) &
|
|
||||||
<= err_damage_tolAbs &
|
|
||||||
.or. abs(phi - damageState(homog)%state(1,offset)) &
|
|
||||||
<= err_damage_tolRel*abs(damageState(homog)%state(1,offset)), &
|
|
||||||
.true.]
|
|
||||||
|
|
||||||
damageState(homog)%state(1,offset) = phi
|
|
||||||
|
|
||||||
end function damage_local_updateState
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief calculates homogenized local damage driving forces
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine damage_local_getSourceAndItsTangent(phiDot, dPhiDot_dPhi, phi, ip, el)
|
|
||||||
use material, only: &
|
|
||||||
homogenization_Ngrains, &
|
|
||||||
mappingHomogenization, &
|
|
||||||
phaseAt, phasememberAt, &
|
|
||||||
phase_source, &
|
|
||||||
phase_Nsources, &
|
|
||||||
SOURCE_damage_isoBrittle_ID, &
|
|
||||||
SOURCE_damage_isoDuctile_ID, &
|
|
||||||
SOURCE_damage_anisoBrittle_ID, &
|
|
||||||
SOURCE_damage_anisoDuctile_ID
|
|
||||||
use source_damage_isoBrittle, only: &
|
|
||||||
source_damage_isobrittle_getRateAndItsTangent
|
|
||||||
use source_damage_isoDuctile, only: &
|
|
||||||
source_damage_isoductile_getRateAndItsTangent
|
|
||||||
use source_damage_anisoBrittle, only: &
|
|
||||||
source_damage_anisobrittle_getRateAndItsTangent
|
|
||||||
use source_damage_anisoDuctile, only: &
|
|
||||||
source_damage_anisoductile_getRateAndItsTangent
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
integer(pInt), intent(in) :: &
|
|
||||||
ip, & !< integration point number
|
|
||||||
el !< element number
|
|
||||||
real(pReal), intent(in) :: &
|
|
||||||
phi
|
|
||||||
integer(pInt) :: &
|
|
||||||
phase, &
|
|
||||||
grain, &
|
|
||||||
source
|
|
||||||
real(pReal) :: &
|
|
||||||
phiDot, dPhiDot_dPhi, localphiDot, dLocalphiDot_dPhi
|
|
||||||
|
|
||||||
phiDot = 0.0_pReal
|
|
||||||
dPhiDot_dPhi = 0.0_pReal
|
|
||||||
do grain = 1, homogenization_Ngrains(mappingHomogenization(2,ip,el))
|
|
||||||
phase = phaseAt(grain,ip,el)
|
|
||||||
do source = 1, phase_Nsources(phase)
|
|
||||||
select case(phase_source(source,phase))
|
|
||||||
case (SOURCE_damage_isoBrittle_ID)
|
|
||||||
call source_damage_isobrittle_getRateAndItsTangent (localphiDot, dLocalphiDot_dPhi, phi, grain, ip, el)
|
|
||||||
|
|
||||||
case (SOURCE_damage_isoDuctile_ID)
|
|
||||||
call source_damage_isoductile_getRateAndItsTangent (localphiDot, dLocalphiDot_dPhi, phi, grain, ip, el)
|
|
||||||
|
|
||||||
case (SOURCE_damage_anisoBrittle_ID)
|
|
||||||
call source_damage_anisobrittle_getRateAndItsTangent(localphiDot, dLocalphiDot_dPhi, phi, grain, ip, el)
|
|
||||||
|
|
||||||
case (SOURCE_damage_anisoDuctile_ID)
|
|
||||||
call source_damage_anisoductile_getRateAndItsTangent(localphiDot, dLocalphiDot_dPhi, phi, grain, ip, el)
|
|
||||||
|
|
||||||
case default
|
|
||||||
localphiDot = 0.0_pReal
|
|
||||||
dLocalphiDot_dPhi = 0.0_pReal
|
|
||||||
|
|
||||||
end select
|
|
||||||
phiDot = phiDot + localphiDot
|
|
||||||
dPhiDot_dPhi = dPhiDot_dPhi + dLocalphiDot_dPhi
|
|
||||||
enddo
|
|
||||||
enddo
|
|
||||||
|
|
||||||
phiDot = phiDot/homogenization_Ngrains(mappingHomogenization(2,ip,el))
|
|
||||||
dPhiDot_dPhi = dPhiDot_dPhi/homogenization_Ngrains(mappingHomogenization(2,ip,el))
|
|
||||||
|
|
||||||
end subroutine damage_local_getSourceAndItsTangent
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief return array of damage results
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
function damage_local_postResults(ip,el)
|
|
||||||
use material, only: &
|
|
||||||
mappingHomogenization, &
|
|
||||||
damage_typeInstance, &
|
|
||||||
damageMapping, &
|
|
||||||
damage
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
integer(pInt), intent(in) :: &
|
|
||||||
ip, & !< integration point
|
|
||||||
el !< element
|
|
||||||
real(pReal), dimension(damage_local_sizePostResults(damage_typeInstance(mappingHomogenization(2,ip,el)))) :: &
|
|
||||||
damage_local_postResults
|
|
||||||
|
|
||||||
integer(pInt) :: &
|
|
||||||
instance, homog, offset, o, c
|
|
||||||
|
|
||||||
homog = mappingHomogenization(2,ip,el)
|
|
||||||
offset = damageMapping(homog)%p(ip,el)
|
|
||||||
instance = damage_typeInstance(homog)
|
|
||||||
|
|
||||||
c = 0_pInt
|
|
||||||
damage_local_postResults = 0.0_pReal
|
|
||||||
|
|
||||||
do o = 1_pInt,damage_local_Noutput(instance)
|
|
||||||
select case(damage_local_outputID(o,instance))
|
|
||||||
|
|
||||||
case (damage_ID)
|
|
||||||
damage_local_postResults(c+1_pInt) = damage(homog)%p(offset)
|
|
||||||
c = c + 1
|
|
||||||
end select
|
|
||||||
enddo
|
|
||||||
end function damage_local_postResults
|
|
||||||
|
|
||||||
end module damage_local
|
|
|
@ -1,60 +0,0 @@
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! $Id$
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @author Pratheek Shanthraj, Max-Planck-Institut für Eisenforschung GmbH
|
|
||||||
!> @brief material subroutine for constant damage field
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
module damage_none
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
private
|
|
||||||
|
|
||||||
public :: &
|
|
||||||
damage_none_init
|
|
||||||
|
|
||||||
contains
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief allocates all neccessary fields, reads information from material configuration file
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine damage_none_init()
|
|
||||||
use, intrinsic :: iso_fortran_env ! to get compiler_version and compiler_options (at least for gfortran 4.6 at the moment)
|
|
||||||
use prec, only: &
|
|
||||||
pInt
|
|
||||||
use IO, only: &
|
|
||||||
IO_timeStamp
|
|
||||||
use material
|
|
||||||
use numerics, only: &
|
|
||||||
worldrank
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
integer(pInt) :: &
|
|
||||||
homog, &
|
|
||||||
NofMyHomog
|
|
||||||
|
|
||||||
mainProcess: if (worldrank == 0) then
|
|
||||||
write(6,'(/,a)') ' <<<+- damage_'//DAMAGE_none_label//' init -+>>>'
|
|
||||||
write(6,'(a15,a)') ' Current time: ',IO_timeStamp()
|
|
||||||
#include "compilation_info.f90"
|
|
||||||
endif mainProcess
|
|
||||||
|
|
||||||
initializeInstances: do homog = 1_pInt, material_Nhomogenization
|
|
||||||
|
|
||||||
myhomog: if (damage_type(homog) == DAMAGE_none_ID) then
|
|
||||||
NofMyHomog = count(material_homog == homog)
|
|
||||||
damageState(homog)%sizeState = 0_pInt
|
|
||||||
damageState(homog)%sizePostResults = 0_pInt
|
|
||||||
allocate(damageState(homog)%state0 (0_pInt,NofMyHomog))
|
|
||||||
allocate(damageState(homog)%subState0(0_pInt,NofMyHomog))
|
|
||||||
allocate(damageState(homog)%state (0_pInt,NofMyHomog))
|
|
||||||
|
|
||||||
deallocate(damage(homog)%p)
|
|
||||||
allocate (damage(homog)%p(1), source=damage_initialPhi(homog))
|
|
||||||
|
|
||||||
endif myhomog
|
|
||||||
enddo initializeInstances
|
|
||||||
|
|
||||||
|
|
||||||
end subroutine damage_none_init
|
|
||||||
|
|
||||||
end module damage_none
|
|
|
@ -1,380 +0,0 @@
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! $Id$
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @author Pratheek Shanthraj, Max-Planck-Institut für Eisenforschung GmbH
|
|
||||||
!> @brief material subroutine for non-locally evolving damage field
|
|
||||||
!> @details to be done
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
module damage_nonlocal
|
|
||||||
use prec, only: &
|
|
||||||
pReal, &
|
|
||||||
pInt
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
private
|
|
||||||
integer(pInt), dimension(:), allocatable, public, protected :: &
|
|
||||||
damage_nonlocal_sizePostResults !< cumulative size of post results
|
|
||||||
|
|
||||||
integer(pInt), dimension(:,:), allocatable, target, public :: &
|
|
||||||
damage_nonlocal_sizePostResult !< size of each post result output
|
|
||||||
|
|
||||||
character(len=64), dimension(:,:), allocatable, target, public :: &
|
|
||||||
damage_nonlocal_output !< name of each post result output
|
|
||||||
|
|
||||||
integer(pInt), dimension(:), allocatable, target, public :: &
|
|
||||||
damage_nonlocal_Noutput !< number of outputs per instance of this damage
|
|
||||||
|
|
||||||
enum, bind(c)
|
|
||||||
enumerator :: undefined_ID, &
|
|
||||||
damage_ID
|
|
||||||
end enum
|
|
||||||
integer(kind(undefined_ID)), dimension(:,:), allocatable, private :: &
|
|
||||||
damage_nonlocal_outputID !< ID of each post result output
|
|
||||||
|
|
||||||
|
|
||||||
public :: &
|
|
||||||
damage_nonlocal_init, &
|
|
||||||
damage_nonlocal_getSourceAndItsTangent, &
|
|
||||||
damage_nonlocal_getDiffusion33, &
|
|
||||||
damage_nonlocal_getMobility, &
|
|
||||||
damage_nonlocal_putNonLocalDamage, &
|
|
||||||
damage_nonlocal_postResults
|
|
||||||
|
|
||||||
contains
|
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief module initialization
|
|
||||||
!> @details reads in material parameters, allocates arrays, and does sanity checks
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine damage_nonlocal_init(fileUnit)
|
|
||||||
use, intrinsic :: iso_fortran_env ! to get compiler_version and compiler_options (at least for gfortran 4.6 at the moment)
|
|
||||||
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: &
|
|
||||||
damage_type, &
|
|
||||||
damage_typeInstance, &
|
|
||||||
homogenization_Noutput, &
|
|
||||||
DAMAGE_nonlocal_label, &
|
|
||||||
DAMAGE_nonlocal_ID, &
|
|
||||||
material_homog, &
|
|
||||||
mappingHomogenization, &
|
|
||||||
damageState, &
|
|
||||||
damageMapping, &
|
|
||||||
damage, &
|
|
||||||
damage_initialPhi, &
|
|
||||||
material_partHomogenization
|
|
||||||
use numerics,only: &
|
|
||||||
worldrank
|
|
||||||
|
|
||||||
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 = ''
|
|
||||||
|
|
||||||
mainProcess: if (worldrank == 0) then
|
|
||||||
write(6,'(/,a)') ' <<<+- damage_'//DAMAGE_nonlocal_label//' init -+>>>'
|
|
||||||
write(6,'(a15,a)') ' Current time: ',IO_timeStamp()
|
|
||||||
#include "compilation_info.f90"
|
|
||||||
endif mainProcess
|
|
||||||
|
|
||||||
maxNinstance = int(count(damage_type == DAMAGE_nonlocal_ID),pInt)
|
|
||||||
if (maxNinstance == 0_pInt) return
|
|
||||||
|
|
||||||
allocate(damage_nonlocal_sizePostResults(maxNinstance), source=0_pInt)
|
|
||||||
allocate(damage_nonlocal_sizePostResult (maxval(homogenization_Noutput),maxNinstance),source=0_pInt)
|
|
||||||
allocate(damage_nonlocal_output (maxval(homogenization_Noutput),maxNinstance))
|
|
||||||
damage_nonlocal_output = ''
|
|
||||||
allocate(damage_nonlocal_outputID (maxval(homogenization_Noutput),maxNinstance),source=undefined_ID)
|
|
||||||
allocate(damage_nonlocal_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 (damage_type(section) == DAMAGE_nonlocal_ID) then ! do not short-circuit here (.and. with next if statemen). It's not safe in Fortran
|
|
||||||
|
|
||||||
instance = damage_typeInstance(section) ! which instance of my damage 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 ('damage')
|
|
||||||
damage_nonlocal_Noutput(instance) = damage_nonlocal_Noutput(instance) + 1_pInt
|
|
||||||
damage_nonlocal_outputID(damage_nonlocal_Noutput(instance),instance) = damage_ID
|
|
||||||
damage_nonlocal_output(damage_nonlocal_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(damage_type)
|
|
||||||
if (damage_type(section) == DAMAGE_nonlocal_ID) then
|
|
||||||
NofMyHomog=count(material_homog==section)
|
|
||||||
instance = damage_typeInstance(section)
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! Determine size of postResults array
|
|
||||||
outputsLoop: do o = 1_pInt,damage_nonlocal_Noutput(instance)
|
|
||||||
select case(damage_nonlocal_outputID(o,instance))
|
|
||||||
case(damage_ID)
|
|
||||||
mySize = 1_pInt
|
|
||||||
end select
|
|
||||||
|
|
||||||
if (mySize > 0_pInt) then ! any meaningful output found
|
|
||||||
damage_nonlocal_sizePostResult(o,instance) = mySize
|
|
||||||
damage_nonlocal_sizePostResults(instance) = damage_nonlocal_sizePostResults(instance) + mySize
|
|
||||||
endif
|
|
||||||
enddo outputsLoop
|
|
||||||
|
|
||||||
! allocate state arrays
|
|
||||||
sizeState = 0_pInt
|
|
||||||
damageState(section)%sizeState = sizeState
|
|
||||||
damageState(section)%sizePostResults = damage_nonlocal_sizePostResults(instance)
|
|
||||||
allocate(damageState(section)%state0 (sizeState,NofMyHomog))
|
|
||||||
allocate(damageState(section)%subState0(sizeState,NofMyHomog))
|
|
||||||
allocate(damageState(section)%state (sizeState,NofMyHomog))
|
|
||||||
|
|
||||||
nullify(damageMapping(section)%p)
|
|
||||||
damageMapping(section)%p => mappingHomogenization(1,:,:)
|
|
||||||
deallocate(damage(section)%p)
|
|
||||||
allocate(damage(section)%p(NofMyHomog), source=damage_initialPhi(section))
|
|
||||||
|
|
||||||
endif
|
|
||||||
|
|
||||||
enddo initializeInstances
|
|
||||||
end subroutine damage_nonlocal_init
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief calculates homogenized damage driving forces
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine damage_nonlocal_getSourceAndItsTangent(phiDot, dPhiDot_dPhi, phi, ip, el)
|
|
||||||
use material, only: &
|
|
||||||
homogenization_Ngrains, &
|
|
||||||
mappingHomogenization, &
|
|
||||||
phaseAt, phasememberAt, &
|
|
||||||
phase_source, &
|
|
||||||
phase_Nsources, &
|
|
||||||
SOURCE_damage_isoBrittle_ID, &
|
|
||||||
SOURCE_damage_isoDuctile_ID, &
|
|
||||||
SOURCE_damage_anisoBrittle_ID, &
|
|
||||||
SOURCE_damage_anisoDuctile_ID
|
|
||||||
use source_damage_isoBrittle, only: &
|
|
||||||
source_damage_isobrittle_getRateAndItsTangent
|
|
||||||
use source_damage_isoDuctile, only: &
|
|
||||||
source_damage_isoductile_getRateAndItsTangent
|
|
||||||
use source_damage_anisoBrittle, only: &
|
|
||||||
source_damage_anisobrittle_getRateAndItsTangent
|
|
||||||
use source_damage_anisoDuctile, only: &
|
|
||||||
source_damage_anisoductile_getRateAndItsTangent
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
integer(pInt), intent(in) :: &
|
|
||||||
ip, & !< integration point number
|
|
||||||
el !< element number
|
|
||||||
real(pReal), intent(in) :: &
|
|
||||||
phi
|
|
||||||
integer(pInt) :: &
|
|
||||||
phase, &
|
|
||||||
grain, &
|
|
||||||
source
|
|
||||||
real(pReal) :: &
|
|
||||||
phiDot, dPhiDot_dPhi, localphiDot, dLocalphiDot_dPhi
|
|
||||||
|
|
||||||
phiDot = 0.0_pReal
|
|
||||||
dPhiDot_dPhi = 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_damage_isoBrittle_ID)
|
|
||||||
call source_damage_isobrittle_getRateAndItsTangent (localphiDot, dLocalphiDot_dPhi, phi, grain, ip, el)
|
|
||||||
|
|
||||||
case (SOURCE_damage_isoDuctile_ID)
|
|
||||||
call source_damage_isoductile_getRateAndItsTangent (localphiDot, dLocalphiDot_dPhi, phi, grain, ip, el)
|
|
||||||
|
|
||||||
case (SOURCE_damage_anisoBrittle_ID)
|
|
||||||
call source_damage_anisobrittle_getRateAndItsTangent(localphiDot, dLocalphiDot_dPhi, phi, grain, ip, el)
|
|
||||||
|
|
||||||
case (SOURCE_damage_anisoDuctile_ID)
|
|
||||||
call source_damage_anisoductile_getRateAndItsTangent(localphiDot, dLocalphiDot_dPhi, phi, grain, ip, el)
|
|
||||||
|
|
||||||
case default
|
|
||||||
localphiDot = 0.0_pReal
|
|
||||||
dLocalphiDot_dPhi = 0.0_pReal
|
|
||||||
|
|
||||||
end select
|
|
||||||
phiDot = phiDot + localphiDot
|
|
||||||
dPhiDot_dPhi = dPhiDot_dPhi + dLocalphiDot_dPhi
|
|
||||||
enddo
|
|
||||||
enddo
|
|
||||||
|
|
||||||
phiDot = phiDot/homogenization_Ngrains(mappingHomogenization(2,ip,el))
|
|
||||||
dPhiDot_dPhi = dPhiDot_dPhi/homogenization_Ngrains(mappingHomogenization(2,ip,el))
|
|
||||||
|
|
||||||
end subroutine damage_nonlocal_getSourceAndItsTangent
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief returns homogenized non local damage diffusion tensor in reference configuration
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
function damage_nonlocal_getDiffusion33(ip,el)
|
|
||||||
use numerics, only: &
|
|
||||||
charLength
|
|
||||||
use lattice, only: &
|
|
||||||
lattice_DamageDiffusion33
|
|
||||||
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) :: &
|
|
||||||
damage_nonlocal_getDiffusion33
|
|
||||||
integer(pInt) :: &
|
|
||||||
homog, &
|
|
||||||
grain
|
|
||||||
|
|
||||||
homog = mappingHomogenization(2,ip,el)
|
|
||||||
damage_nonlocal_getDiffusion33 = 0.0_pReal
|
|
||||||
do grain = 1, homogenization_Ngrains(homog)
|
|
||||||
damage_nonlocal_getDiffusion33 = damage_nonlocal_getDiffusion33 + &
|
|
||||||
crystallite_push33ToRef(grain,ip,el,lattice_DamageDiffusion33(1:3,1:3,material_phase(grain,ip,el)))
|
|
||||||
enddo
|
|
||||||
|
|
||||||
damage_nonlocal_getDiffusion33 = &
|
|
||||||
charLength*charLength* &
|
|
||||||
damage_nonlocal_getDiffusion33/ &
|
|
||||||
homogenization_Ngrains(homog)
|
|
||||||
|
|
||||||
end function damage_nonlocal_getDiffusion33
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief Returns homogenized nonlocal damage mobility
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
real(pReal) function damage_nonlocal_getMobility(ip,el)
|
|
||||||
use mesh, only: &
|
|
||||||
mesh_element
|
|
||||||
use lattice, only: &
|
|
||||||
lattice_damageMobility
|
|
||||||
use material, only: &
|
|
||||||
material_phase, &
|
|
||||||
homogenization_Ngrains
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
integer(pInt), intent(in) :: &
|
|
||||||
ip, & !< integration point number
|
|
||||||
el !< element number
|
|
||||||
integer(pInt) :: &
|
|
||||||
ipc
|
|
||||||
|
|
||||||
damage_nonlocal_getMobility = 0.0_pReal
|
|
||||||
|
|
||||||
do ipc = 1, homogenization_Ngrains(mesh_element(3,el))
|
|
||||||
damage_nonlocal_getMobility = damage_nonlocal_getMobility + lattice_DamageMobility(material_phase(ipc,ip,el))
|
|
||||||
enddo
|
|
||||||
|
|
||||||
damage_nonlocal_getMobility = damage_nonlocal_getMobility /homogenization_Ngrains(mesh_element(3,el))
|
|
||||||
|
|
||||||
end function damage_nonlocal_getMobility
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief updated nonlocal damage field with solution from damage phase field PDE
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine damage_nonlocal_putNonLocalDamage(phi,ip,el)
|
|
||||||
use material, only: &
|
|
||||||
material_homog, &
|
|
||||||
damageMapping, &
|
|
||||||
damage
|
|
||||||
|
|
||||||
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 = damageMapping(homog)%p(ip,el)
|
|
||||||
damage(homog)%p(offset) = phi
|
|
||||||
|
|
||||||
end subroutine damage_nonlocal_putNonLocalDamage
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief return array of damage results
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
function damage_nonlocal_postResults(ip,el)
|
|
||||||
use material, only: &
|
|
||||||
mappingHomogenization, &
|
|
||||||
damage_typeInstance, &
|
|
||||||
damage
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
integer(pInt), intent(in) :: &
|
|
||||||
ip, & !< integration point
|
|
||||||
el !< element
|
|
||||||
real(pReal), dimension(damage_nonlocal_sizePostResults(damage_typeInstance(mappingHomogenization(2,ip,el)))) :: &
|
|
||||||
damage_nonlocal_postResults
|
|
||||||
|
|
||||||
integer(pInt) :: &
|
|
||||||
instance, homog, offset, o, c
|
|
||||||
|
|
||||||
homog = mappingHomogenization(2,ip,el)
|
|
||||||
offset = mappingHomogenization(1,ip,el)
|
|
||||||
instance = damage_typeInstance(homog)
|
|
||||||
|
|
||||||
c = 0_pInt
|
|
||||||
damage_nonlocal_postResults = 0.0_pReal
|
|
||||||
|
|
||||||
do o = 1_pInt,damage_nonlocal_Noutput(instance)
|
|
||||||
select case(damage_nonlocal_outputID(o,instance))
|
|
||||||
|
|
||||||
case (damage_ID)
|
|
||||||
damage_nonlocal_postResults(c+1_pInt) = damage(homog)%p(offset)
|
|
||||||
c = c + 1
|
|
||||||
end select
|
|
||||||
enddo
|
|
||||||
end function damage_nonlocal_postResults
|
|
||||||
|
|
||||||
end module damage_nonlocal
|
|
File diff suppressed because it is too large
Load Diff
|
@ -9,3 +9,8 @@ set (HOMOGENIZATION "homogenization"
|
||||||
foreach (p ${HOMOGENIZATION})
|
foreach (p ${HOMOGENIZATION})
|
||||||
add_library (${p} MODULE "${p}.f90")
|
add_library (${p} MODULE "${p}.f90")
|
||||||
endforeach (p)
|
endforeach (p)
|
||||||
|
|
||||||
|
# set libraries/modules for linking
|
||||||
|
foreach (p ${HOMOGENIZATION})
|
||||||
|
set (AUX_LIB ${AUX_LIB} ${p})
|
||||||
|
endforeach (p)
|
File diff suppressed because it is too large
Load Diff
|
@ -1,317 +0,0 @@
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! $Id$
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @author Franz Roters, Max-Planck-Institut für Eisenforschung GmbH
|
|
||||||
!> @author Philip Eisenlohr, Max-Planck-Institut für Eisenforschung GmbH
|
|
||||||
!> @brief Isostrain (full constraint Taylor assuption) homogenization scheme
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
module homogenization_isostrain
|
|
||||||
use prec, only: &
|
|
||||||
pInt
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
private
|
|
||||||
integer(pInt), dimension(:), allocatable, public, protected :: &
|
|
||||||
homogenization_isostrain_sizePostResults
|
|
||||||
integer(pInt), dimension(:,:), allocatable, target, public :: &
|
|
||||||
homogenization_isostrain_sizePostResult
|
|
||||||
|
|
||||||
character(len=64), dimension(:,:), allocatable, target, public :: &
|
|
||||||
homogenization_isostrain_output !< name of each post result output
|
|
||||||
integer(pInt), dimension(:), allocatable, target, public :: &
|
|
||||||
homogenization_isostrain_Noutput !< number of outputs per homog instance
|
|
||||||
integer(pInt), dimension(:), allocatable, private :: &
|
|
||||||
homogenization_isostrain_Ngrains
|
|
||||||
enum, bind(c)
|
|
||||||
enumerator :: undefined_ID, &
|
|
||||||
nconstituents_ID, &
|
|
||||||
ipcoords_ID, &
|
|
||||||
avgdefgrad_ID, &
|
|
||||||
avgfirstpiola_ID
|
|
||||||
end enum
|
|
||||||
enum, bind(c)
|
|
||||||
enumerator :: parallel_ID, &
|
|
||||||
average_ID
|
|
||||||
end enum
|
|
||||||
integer(kind(undefined_ID)), dimension(:,:), allocatable, private :: &
|
|
||||||
homogenization_isostrain_outputID !< ID of each post result output
|
|
||||||
integer(kind(average_ID)), dimension(:), allocatable, private :: &
|
|
||||||
homogenization_isostrain_mapping !< mapping type
|
|
||||||
|
|
||||||
|
|
||||||
public :: &
|
|
||||||
homogenization_isostrain_init, &
|
|
||||||
homogenization_isostrain_partitionDeformation, &
|
|
||||||
homogenization_isostrain_averageStressAndItsTangent, &
|
|
||||||
homogenization_isostrain_postResults
|
|
||||||
|
|
||||||
contains
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief allocates all neccessary fields, reads information from material configuration file
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine homogenization_isostrain_init(fileUnit)
|
|
||||||
use, intrinsic :: iso_fortran_env ! to get compiler_version and compiler_options (at least for gfortran 4.6 at the moment)
|
|
||||||
use prec, only: &
|
|
||||||
pReal
|
|
||||||
use debug, only: &
|
|
||||||
debug_HOMOGENIZATION, &
|
|
||||||
debug_level, &
|
|
||||||
debug_levelBasic
|
|
||||||
use IO
|
|
||||||
use material
|
|
||||||
use numerics, only: &
|
|
||||||
worldrank
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
integer(pInt), intent(in) :: fileUnit
|
|
||||||
integer(pInt), allocatable, dimension(:) :: chunkPos
|
|
||||||
integer(pInt) :: &
|
|
||||||
section = 0_pInt, i, mySize, o
|
|
||||||
integer :: &
|
|
||||||
maxNinstance, &
|
|
||||||
homog, &
|
|
||||||
instance
|
|
||||||
integer :: &
|
|
||||||
NofMyHomog ! no pInt (stores a system dependen value from 'count'
|
|
||||||
character(len=65536) :: &
|
|
||||||
tag = '', &
|
|
||||||
line = ''
|
|
||||||
|
|
||||||
mainProcess: if (worldrank == 0) then
|
|
||||||
write(6,'(/,a)') ' <<<+- homogenization_'//HOMOGENIZATION_ISOSTRAIN_label//' init -+>>>'
|
|
||||||
write(6,'(a15,a)') ' Current time: ',IO_timeStamp()
|
|
||||||
#include "compilation_info.f90"
|
|
||||||
endif mainProcess
|
|
||||||
|
|
||||||
maxNinstance = count(homogenization_type == HOMOGENIZATION_ISOSTRAIN_ID)
|
|
||||||
if (maxNinstance == 0) return
|
|
||||||
|
|
||||||
if (iand(debug_level(debug_HOMOGENIZATION),debug_levelBasic) /= 0_pInt) &
|
|
||||||
write(6,'(a16,1x,i5,/)') '# instances:',maxNinstance
|
|
||||||
allocate(homogenization_isostrain_sizePostResults(maxNinstance), source=0_pInt)
|
|
||||||
allocate(homogenization_isostrain_sizePostResult(maxval(homogenization_Noutput),maxNinstance), &
|
|
||||||
source=0_pInt)
|
|
||||||
allocate(homogenization_isostrain_Noutput(maxNinstance), source=0_pInt)
|
|
||||||
allocate(homogenization_isostrain_Ngrains(maxNinstance), source=0_pInt)
|
|
||||||
allocate(homogenization_isostrain_mapping(maxNinstance), source=average_ID)
|
|
||||||
allocate(homogenization_isostrain_output(maxval(homogenization_Noutput),maxNinstance))
|
|
||||||
homogenization_isostrain_output = ''
|
|
||||||
allocate(homogenization_isostrain_outputID(maxval(homogenization_Noutput),maxNinstance), &
|
|
||||||
source=undefined_ID)
|
|
||||||
|
|
||||||
rewind(fileUnit)
|
|
||||||
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 homogenization 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 section
|
|
||||||
section = section + 1_pInt
|
|
||||||
cycle
|
|
||||||
endif
|
|
||||||
if (section > 0_pInt ) then ! do not short-circuit here (.and. with next if-statement). It's not safe in Fortran
|
|
||||||
if (homogenization_type(section) == HOMOGENIZATION_ISOSTRAIN_ID) then ! one of my sections
|
|
||||||
i = homogenization_typeInstance(section) ! which instance of my type is present homogenization
|
|
||||||
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('nconstituents','ngrains')
|
|
||||||
homogenization_isostrain_Noutput(i) = homogenization_isostrain_Noutput(i) + 1_pInt
|
|
||||||
homogenization_isostrain_outputID(homogenization_isostrain_Noutput(i),i) = nconstituents_ID
|
|
||||||
homogenization_isostrain_output(homogenization_isostrain_Noutput(i),i) = &
|
|
||||||
IO_lc(IO_stringValue(line,chunkPos,2_pInt))
|
|
||||||
case('ipcoords')
|
|
||||||
homogenization_isostrain_Noutput(i) = homogenization_isostrain_Noutput(i) + 1_pInt
|
|
||||||
homogenization_isostrain_outputID(homogenization_isostrain_Noutput(i),i) = ipcoords_ID
|
|
||||||
homogenization_isostrain_output(homogenization_isostrain_Noutput(i),i) = &
|
|
||||||
IO_lc(IO_stringValue(line,chunkPos,2_pInt))
|
|
||||||
case('avgdefgrad','avgf')
|
|
||||||
homogenization_isostrain_Noutput(i) = homogenization_isostrain_Noutput(i) + 1_pInt
|
|
||||||
homogenization_isostrain_outputID(homogenization_isostrain_Noutput(i),i) = avgdefgrad_ID
|
|
||||||
homogenization_isostrain_output(homogenization_isostrain_Noutput(i),i) = &
|
|
||||||
IO_lc(IO_stringValue(line,chunkPos,2_pInt))
|
|
||||||
case('avgp','avgfirstpiola','avg1stpiola')
|
|
||||||
homogenization_isostrain_Noutput(i) = homogenization_isostrain_Noutput(i) + 1_pInt
|
|
||||||
homogenization_isostrain_outputID(homogenization_isostrain_Noutput(i),i) = avgfirstpiola_ID
|
|
||||||
homogenization_isostrain_output(homogenization_isostrain_Noutput(i),i) = &
|
|
||||||
IO_lc(IO_stringValue(line,chunkPos,2_pInt))
|
|
||||||
|
|
||||||
end select
|
|
||||||
case ('nconstituents','ngrains')
|
|
||||||
homogenization_isostrain_Ngrains(i) = IO_intValue(line,chunkPos,2_pInt)
|
|
||||||
case ('mapping')
|
|
||||||
select case(IO_lc(IO_stringValue(line,chunkPos,2_pInt)))
|
|
||||||
case ('parallel','sum')
|
|
||||||
homogenization_isostrain_mapping(i) = parallel_ID
|
|
||||||
case ('average','mean','avg')
|
|
||||||
homogenization_isostrain_mapping(i) = average_ID
|
|
||||||
case default
|
|
||||||
call IO_error(211_pInt,ext_msg=trim(tag)//' ('//HOMOGENIZATION_isostrain_label//')')
|
|
||||||
end select
|
|
||||||
|
|
||||||
end select
|
|
||||||
endif
|
|
||||||
endif
|
|
||||||
enddo parsingFile
|
|
||||||
|
|
||||||
initializeInstances: do homog = 1_pInt, material_Nhomogenization
|
|
||||||
myHomog: if (homogenization_type(homog) == HOMOGENIZATION_ISOSTRAIN_ID) then
|
|
||||||
NofMyHomog = count(material_homog == homog)
|
|
||||||
instance = homogenization_typeInstance(homog)
|
|
||||||
|
|
||||||
! * Determine size of postResults array
|
|
||||||
outputsLoop: do o = 1_pInt, homogenization_isostrain_Noutput(instance)
|
|
||||||
select case(homogenization_isostrain_outputID(o,instance))
|
|
||||||
case(nconstituents_ID)
|
|
||||||
mySize = 1_pInt
|
|
||||||
case(ipcoords_ID)
|
|
||||||
mySize = 3_pInt
|
|
||||||
case(avgdefgrad_ID, avgfirstpiola_ID)
|
|
||||||
mySize = 9_pInt
|
|
||||||
case default
|
|
||||||
mySize = 0_pInt
|
|
||||||
end select
|
|
||||||
|
|
||||||
outputFound: if (mySize > 0_pInt) then
|
|
||||||
homogenization_isostrain_sizePostResult(o,instance) = mySize
|
|
||||||
homogenization_isostrain_sizePostResults(instance) = &
|
|
||||||
homogenization_isostrain_sizePostResults(instance) + mySize
|
|
||||||
endif outputFound
|
|
||||||
enddo outputsLoop
|
|
||||||
|
|
||||||
! allocate state arrays
|
|
||||||
homogState(homog)%sizeState = 0_pInt
|
|
||||||
homogState(homog)%sizePostResults = homogenization_isostrain_sizePostResults(instance)
|
|
||||||
allocate(homogState(homog)%state0 (0_pInt,NofMyHomog), source=0.0_pReal)
|
|
||||||
allocate(homogState(homog)%subState0(0_pInt,NofMyHomog), source=0.0_pReal)
|
|
||||||
allocate(homogState(homog)%state (0_pInt,NofMyHomog), source=0.0_pReal)
|
|
||||||
|
|
||||||
endif myHomog
|
|
||||||
enddo initializeInstances
|
|
||||||
|
|
||||||
end subroutine homogenization_isostrain_init
|
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief partitions the deformation gradient onto the constituents
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine homogenization_isostrain_partitionDeformation(F,avgF,el)
|
|
||||||
use prec, only: &
|
|
||||||
pReal
|
|
||||||
use mesh, only: &
|
|
||||||
mesh_element
|
|
||||||
use material, only: &
|
|
||||||
homogenization_maxNgrains, &
|
|
||||||
homogenization_Ngrains
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
real(pReal), dimension (3,3,homogenization_maxNgrains), intent(out) :: F !< partioned def grad per grain
|
|
||||||
real(pReal), dimension (3,3), intent(in) :: avgF !< my average def grad
|
|
||||||
integer(pInt), intent(in) :: &
|
|
||||||
el !< element number
|
|
||||||
F=0.0_pReal
|
|
||||||
F(1:3,1:3,1:homogenization_Ngrains(mesh_element(3,el)))= &
|
|
||||||
spread(avgF,3,homogenization_Ngrains(mesh_element(3,el)))
|
|
||||||
|
|
||||||
end subroutine homogenization_isostrain_partitionDeformation
|
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief derive average stress and stiffness from constituent quantities
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine homogenization_isostrain_averageStressAndItsTangent(avgP,dAvgPdAvgF,P,dPdF,el)
|
|
||||||
use prec, only: &
|
|
||||||
pReal
|
|
||||||
use mesh, only: &
|
|
||||||
mesh_element
|
|
||||||
use material, only: &
|
|
||||||
homogenization_maxNgrains, &
|
|
||||||
homogenization_Ngrains, &
|
|
||||||
homogenization_typeInstance
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
real(pReal), dimension (3,3), intent(out) :: avgP !< average stress at material point
|
|
||||||
real(pReal), dimension (3,3,3,3), intent(out) :: dAvgPdAvgF !< average stiffness at material point
|
|
||||||
real(pReal), dimension (3,3,homogenization_maxNgrains), intent(in) :: P !< array of current grain stresses
|
|
||||||
real(pReal), dimension (3,3,3,3,homogenization_maxNgrains), intent(in) :: dPdF !< array of current grain stiffnesses
|
|
||||||
integer(pInt), intent(in) :: el !< element number
|
|
||||||
integer(pInt) :: &
|
|
||||||
homID, &
|
|
||||||
Ngrains
|
|
||||||
|
|
||||||
homID = homogenization_typeInstance(mesh_element(3,el))
|
|
||||||
Ngrains = homogenization_Ngrains(mesh_element(3,el))
|
|
||||||
|
|
||||||
select case (homogenization_isostrain_mapping(homID))
|
|
||||||
case (parallel_ID)
|
|
||||||
avgP = sum(P,3)
|
|
||||||
dAvgPdAvgF = sum(dPdF,5)
|
|
||||||
case (average_ID)
|
|
||||||
avgP = sum(P,3) /real(Ngrains,pReal)
|
|
||||||
dAvgPdAvgF = sum(dPdF,5)/real(Ngrains,pReal)
|
|
||||||
end select
|
|
||||||
|
|
||||||
end subroutine homogenization_isostrain_averageStressAndItsTangent
|
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief return array of homogenization results for post file inclusion
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
pure function homogenization_isostrain_postResults(ip,el,avgP,avgF)
|
|
||||||
use prec, only: &
|
|
||||||
pReal
|
|
||||||
use mesh, only: &
|
|
||||||
mesh_element, &
|
|
||||||
mesh_ipCoordinates
|
|
||||||
use material, only: &
|
|
||||||
homogenization_typeInstance, &
|
|
||||||
homogenization_Noutput
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
integer(pInt), intent(in) :: &
|
|
||||||
ip, & !< integration point number
|
|
||||||
el !< element number
|
|
||||||
real(pReal), dimension(3,3), intent(in) :: &
|
|
||||||
avgP, & !< average stress at material point
|
|
||||||
avgF !< average deformation gradient at material point
|
|
||||||
real(pReal), dimension(homogenization_isostrain_sizePostResults &
|
|
||||||
(homogenization_typeInstance(mesh_element(3,el)))) :: &
|
|
||||||
homogenization_isostrain_postResults
|
|
||||||
|
|
||||||
integer(pInt) :: &
|
|
||||||
homID, &
|
|
||||||
o, c
|
|
||||||
|
|
||||||
c = 0_pInt
|
|
||||||
homID = homogenization_typeInstance(mesh_element(3,el))
|
|
||||||
homogenization_isostrain_postResults = 0.0_pReal
|
|
||||||
|
|
||||||
do o = 1_pInt,homogenization_Noutput(mesh_element(3,el))
|
|
||||||
select case(homogenization_isostrain_outputID(o,homID))
|
|
||||||
case (nconstituents_ID)
|
|
||||||
homogenization_isostrain_postResults(c+1_pInt) = real(homogenization_isostrain_Ngrains(homID),pReal)
|
|
||||||
c = c + 1_pInt
|
|
||||||
case (avgdefgrad_ID)
|
|
||||||
homogenization_isostrain_postResults(c+1_pInt:c+9_pInt) = reshape(avgF,[9])
|
|
||||||
c = c + 9_pInt
|
|
||||||
case (avgfirstpiola_ID)
|
|
||||||
homogenization_isostrain_postResults(c+1_pInt:c+9_pInt) = reshape(avgP,[9])
|
|
||||||
c = c + 9_pInt
|
|
||||||
case (ipcoords_ID)
|
|
||||||
homogenization_isostrain_postResults(c+1_pInt:c+3_pInt) = mesh_ipCoordinates(1:3,ip,el) ! current ip coordinates
|
|
||||||
c = c + 3_pInt
|
|
||||||
end select
|
|
||||||
enddo
|
|
||||||
|
|
||||||
end function homogenization_isostrain_postResults
|
|
||||||
|
|
||||||
end module homogenization_isostrain
|
|
|
@ -1,60 +0,0 @@
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! $Id$
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @author Franz Roters, Max-Planck-Institut für Eisenforschung GmbH
|
|
||||||
!> @author Philip Eisenlohr, Max-Planck-Institut für Eisenforschung GmbH
|
|
||||||
!> @author Martin Diehl, Max-Planck-Institut für Eisenforschung GmbH
|
|
||||||
!> @brief dummy homogenization homogenization scheme
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
module homogenization_none
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
private
|
|
||||||
|
|
||||||
public :: &
|
|
||||||
homogenization_none_init
|
|
||||||
|
|
||||||
contains
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief allocates all neccessary fields, reads information from material configuration file
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine homogenization_none_init()
|
|
||||||
use, intrinsic :: iso_fortran_env ! to get compiler_version and compiler_options (at least for gfortran 4.6 at the moment)
|
|
||||||
use prec, only: &
|
|
||||||
pReal, &
|
|
||||||
pInt
|
|
||||||
use IO, only: &
|
|
||||||
IO_timeStamp
|
|
||||||
use material
|
|
||||||
use numerics, only: &
|
|
||||||
worldrank
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
integer(pInt) :: &
|
|
||||||
homog, &
|
|
||||||
NofMyHomog
|
|
||||||
|
|
||||||
mainProcess: if (worldrank == 0) then
|
|
||||||
write(6,'(/,a)') ' <<<+- homogenization_'//HOMOGENIZATION_NONE_label//' init -+>>>'
|
|
||||||
write(6,'(a15,a)') ' Current time: ',IO_timeStamp()
|
|
||||||
#include "compilation_info.f90"
|
|
||||||
endif mainProcess
|
|
||||||
|
|
||||||
initializeInstances: do homog = 1_pInt, material_Nhomogenization
|
|
||||||
|
|
||||||
myhomog: if (homogenization_type(homog) == HOMOGENIZATION_none_ID) then
|
|
||||||
NofMyHomog = count(material_homog == homog)
|
|
||||||
homogState(homog)%sizeState = 0_pInt
|
|
||||||
homogState(homog)%sizePostResults = 0_pInt
|
|
||||||
allocate(homogState(homog)%state0 (0_pInt,NofMyHomog), source=0.0_pReal)
|
|
||||||
allocate(homogState(homog)%subState0(0_pInt,NofMyHomog), source=0.0_pReal)
|
|
||||||
allocate(homogState(homog)%state (0_pInt,NofMyHomog), source=0.0_pReal)
|
|
||||||
|
|
||||||
endif myhomog
|
|
||||||
enddo initializeInstances
|
|
||||||
|
|
||||||
|
|
||||||
end subroutine homogenization_none_init
|
|
||||||
|
|
||||||
end module homogenization_none
|
|
|
@ -7,3 +7,8 @@ set (HYDROGENFLUX "hydrogenflux_isoconc"
|
||||||
foreach (p ${HYDROGENFLUX})
|
foreach (p ${HYDROGENFLUX})
|
||||||
add_library (${p} MODULE "${p}.f90")
|
add_library (${p} MODULE "${p}.f90")
|
||||||
endforeach (p)
|
endforeach (p)
|
||||||
|
|
||||||
|
# set libraries/modules for linking
|
||||||
|
foreach (p ${HYDROGENFLUX})
|
||||||
|
set (AUX_LIB ${AUX_LIB} ${p})
|
||||||
|
endforeach (p)
|
|
@ -1,513 +0,0 @@
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! $Id$
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @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)
|
|
||||||
use, intrinsic :: iso_fortran_env ! to get compiler_version and compiler_options (at least for gfortran 4.6 at the moment)
|
|
||||||
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, &
|
|
||||||
material_partHomogenization, &
|
|
||||||
material_partPhase
|
|
||||||
use numerics,only: &
|
|
||||||
worldrank
|
|
||||||
|
|
||||||
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 = ''
|
|
||||||
|
|
||||||
mainProcess: if (worldrank == 0) then
|
|
||||||
write(6,'(/,a)') ' <<<+- hydrogenflux_'//HYDROGENFLUX_cahnhilliard_label//' init -+>>>'
|
|
||||||
write(6,'(a15,a)') ' Current time: ',IO_timeStamp()
|
|
||||||
#include "compilation_info.f90"
|
|
||||||
endif mainProcess
|
|
||||||
|
|
||||||
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/ &
|
|
||||||
homogenization_Ngrains(mesh_element(3,el))
|
|
||||||
|
|
||||||
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/ &
|
|
||||||
homogenization_Ngrains(mesh_element(3,el))
|
|
||||||
|
|
||||||
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/ &
|
|
||||||
homogenization_Ngrains(mesh_element(3,el))
|
|
||||||
|
|
||||||
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))/ &
|
|
||||||
homogenization_Ngrains(material_homog(ip,el))
|
|
||||||
|
|
||||||
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/homogenization_Ngrains(material_homog(ip,el))
|
|
||||||
dKPot_dCh = dKPot_dCh/homogenization_Ngrains(material_homog(ip,el))
|
|
||||||
|
|
||||||
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,63 +0,0 @@
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! $Id$
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @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()
|
|
||||||
use, intrinsic :: iso_fortran_env ! to get compiler_version and compiler_options (at least for gfortran 4.6 at the moment)
|
|
||||||
use prec, only: &
|
|
||||||
pReal, &
|
|
||||||
pInt
|
|
||||||
use IO, only: &
|
|
||||||
IO_timeStamp
|
|
||||||
use material
|
|
||||||
use numerics, only: &
|
|
||||||
worldrank
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
integer(pInt) :: &
|
|
||||||
homog, &
|
|
||||||
NofMyHomog
|
|
||||||
|
|
||||||
mainProcess: if (worldrank == 0) then
|
|
||||||
write(6,'(/,a)') ' <<<+- hydrogenflux_'//HYDROGENFLUX_isoconc_label//' init -+>>>'
|
|
||||||
write(6,'(a15,a)') ' Current time: ',IO_timeStamp()
|
|
||||||
#include "compilation_info.f90"
|
|
||||||
endif mainProcess
|
|
||||||
|
|
||||||
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
|
|
|
@ -10,3 +10,8 @@ set (KINEMATICS "kinematics_cleavage_opening"
|
||||||
foreach (p ${KINEMATICS})
|
foreach (p ${KINEMATICS})
|
||||||
add_library (${p} MODULE "${p}.f90")
|
add_library (${p} MODULE "${p}.f90")
|
||||||
endforeach (p)
|
endforeach (p)
|
||||||
|
|
||||||
|
# set libraries/modules for linking
|
||||||
|
foreach (p ${KINEMATICS})
|
||||||
|
set (AUX_LIB ${AUX_LIB} ${p})
|
||||||
|
endforeach (p)
|
|
@ -1,303 +0,0 @@
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! $Id$
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @author Luv Sharma, Max-Planck-Institut fŸr Eisenforschung GmbH
|
|
||||||
!> @author Pratheek Shanthraj, Max-Planck-Institut fŸr Eisenforschung GmbH
|
|
||||||
!> @brief material subroutine incorporating kinematics resulting from opening of cleavage planes
|
|
||||||
!> @details to be done
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
module kinematics_cleavage_opening
|
|
||||||
use prec, only: &
|
|
||||||
pReal, &
|
|
||||||
pInt
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
private
|
|
||||||
integer(pInt), dimension(:), allocatable, public, protected :: &
|
|
||||||
kinematics_cleavage_opening_sizePostResults, & !< cumulative size of post results
|
|
||||||
kinematics_cleavage_opening_offset, & !< which kinematics is my current damage mechanism?
|
|
||||||
kinematics_cleavage_opening_instance !< instance of damage kinematics mechanism
|
|
||||||
|
|
||||||
integer(pInt), dimension(:,:), allocatable, target, public :: &
|
|
||||||
kinematics_cleavage_opening_sizePostResult !< size of each post result output
|
|
||||||
|
|
||||||
character(len=64), dimension(:,:), allocatable, target, public :: &
|
|
||||||
kinematics_cleavage_opening_output !< name of each post result output
|
|
||||||
|
|
||||||
integer(pInt), dimension(:), allocatable, target, public :: &
|
|
||||||
kinematics_cleavage_opening_Noutput !< number of outputs per instance of this damage
|
|
||||||
|
|
||||||
integer(pInt), dimension(:), allocatable, private :: &
|
|
||||||
kinematics_cleavage_opening_totalNcleavage !< total number of cleavage systems
|
|
||||||
|
|
||||||
integer(pInt), dimension(:,:), allocatable, private :: &
|
|
||||||
kinematics_cleavage_opening_Ncleavage !< number of cleavage systems per family
|
|
||||||
|
|
||||||
real(pReal), dimension(:), allocatable, private :: &
|
|
||||||
kinematics_cleavage_opening_sdot_0, &
|
|
||||||
kinematics_cleavage_opening_N
|
|
||||||
|
|
||||||
real(pReal), dimension(:,:), allocatable, private :: &
|
|
||||||
kinematics_cleavage_opening_critDisp, &
|
|
||||||
kinematics_cleavage_opening_critLoad
|
|
||||||
|
|
||||||
public :: &
|
|
||||||
kinematics_cleavage_opening_init, &
|
|
||||||
kinematics_cleavage_opening_LiAndItsTangent
|
|
||||||
|
|
||||||
contains
|
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief module initialization
|
|
||||||
!> @details reads in material parameters, allocates arrays, and does sanity checks
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine kinematics_cleavage_opening_init(fileUnit)
|
|
||||||
use, intrinsic :: iso_fortran_env ! to get compiler_version and compiler_options (at least for gfortran 4.6 at the moment)
|
|
||||||
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_cleavage_opening_label, &
|
|
||||||
KINEMATICS_cleavage_opening_ID, &
|
|
||||||
material_Nphase, &
|
|
||||||
MATERIAL_partPhase
|
|
||||||
use numerics,only: &
|
|
||||||
worldrank
|
|
||||||
use lattice, only: &
|
|
||||||
lattice_maxNcleavageFamily, &
|
|
||||||
lattice_NcleavageSystem
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
integer(pInt), intent(in) :: fileUnit
|
|
||||||
|
|
||||||
integer(pInt), allocatable, dimension(:) :: chunkPos
|
|
||||||
integer(pInt) :: maxNinstance,phase,instance,kinematics
|
|
||||||
integer(pInt) :: Nchunks_CleavageFamilies = 0_pInt, j
|
|
||||||
character(len=65536) :: &
|
|
||||||
tag = '', &
|
|
||||||
line = ''
|
|
||||||
|
|
||||||
mainProcess: if (worldrank == 0) then
|
|
||||||
write(6,'(/,a)') ' <<<+- kinematics_'//KINEMATICS_cleavage_opening_LABEL//' init -+>>>'
|
|
||||||
write(6,'(a15,a)') ' Current time: ',IO_timeStamp()
|
|
||||||
#include "compilation_info.f90"
|
|
||||||
endif mainProcess
|
|
||||||
|
|
||||||
maxNinstance = int(count(phase_kinematics == KINEMATICS_cleavage_opening_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_cleavage_opening_offset(material_Nphase), source=0_pInt)
|
|
||||||
allocate(kinematics_cleavage_opening_instance(material_Nphase), source=0_pInt)
|
|
||||||
do phase = 1, material_Nphase
|
|
||||||
kinematics_cleavage_opening_instance(phase) = count(phase_kinematics(:,1:phase) == kinematics_cleavage_opening_ID)
|
|
||||||
do kinematics = 1, phase_Nkinematics(phase)
|
|
||||||
if (phase_kinematics(kinematics,phase) == kinematics_cleavage_opening_ID) &
|
|
||||||
kinematics_cleavage_opening_offset(phase) = kinematics
|
|
||||||
enddo
|
|
||||||
enddo
|
|
||||||
|
|
||||||
allocate(kinematics_cleavage_opening_sizePostResults(maxNinstance), source=0_pInt)
|
|
||||||
allocate(kinematics_cleavage_opening_sizePostResult(maxval(phase_Noutput),maxNinstance), source=0_pInt)
|
|
||||||
allocate(kinematics_cleavage_opening_output(maxval(phase_Noutput),maxNinstance))
|
|
||||||
kinematics_cleavage_opening_output = ''
|
|
||||||
allocate(kinematics_cleavage_opening_Noutput(maxNinstance), source=0_pInt)
|
|
||||||
allocate(kinematics_cleavage_opening_critDisp(lattice_maxNcleavageFamily,maxNinstance), source=0.0_pReal)
|
|
||||||
allocate(kinematics_cleavage_opening_critLoad(lattice_maxNcleavageFamily,maxNinstance), source=0.0_pReal)
|
|
||||||
allocate(kinematics_cleavage_opening_Ncleavage(lattice_maxNcleavageFamily,maxNinstance), source=0_pInt)
|
|
||||||
allocate(kinematics_cleavage_opening_totalNcleavage(maxNinstance), source=0_pInt)
|
|
||||||
allocate(kinematics_cleavage_opening_sdot_0(maxNinstance), source=0.0_pReal)
|
|
||||||
allocate(kinematics_cleavage_opening_N(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_cleavage_opening_ID)) then ! do not short-circuit here (.and. with next if statemen). It's not safe in Fortran
|
|
||||||
instance = kinematics_cleavage_opening_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 ('anisobrittle_sdot0')
|
|
||||||
kinematics_cleavage_opening_sdot_0(instance) = IO_floatValue(line,chunkPos,2_pInt)
|
|
||||||
|
|
||||||
case ('anisobrittle_ratesensitivity')
|
|
||||||
kinematics_cleavage_opening_N(instance) = IO_floatValue(line,chunkPos,2_pInt)
|
|
||||||
|
|
||||||
case ('ncleavage') !
|
|
||||||
Nchunks_CleavageFamilies = chunkPos(1) - 1_pInt
|
|
||||||
do j = 1_pInt, Nchunks_CleavageFamilies
|
|
||||||
kinematics_cleavage_opening_Ncleavage(j,instance) = IO_intValue(line,chunkPos,1_pInt+j)
|
|
||||||
enddo
|
|
||||||
|
|
||||||
case ('anisobrittle_criticaldisplacement')
|
|
||||||
do j = 1_pInt, Nchunks_CleavageFamilies
|
|
||||||
kinematics_cleavage_opening_critDisp(j,instance) = IO_floatValue(line,chunkPos,1_pInt+j)
|
|
||||||
enddo
|
|
||||||
|
|
||||||
case ('anisobrittle_criticalload')
|
|
||||||
do j = 1_pInt, Nchunks_CleavageFamilies
|
|
||||||
kinematics_cleavage_opening_critLoad(j,instance) = IO_floatValue(line,chunkPos,1_pInt+j)
|
|
||||||
enddo
|
|
||||||
|
|
||||||
end select
|
|
||||||
endif; endif
|
|
||||||
enddo parsingFile
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! sanity checks
|
|
||||||
sanityChecks: do phase = 1_pInt, material_Nphase
|
|
||||||
myPhase: if (any(phase_kinematics(:,phase) == KINEMATICS_cleavage_opening_ID)) then
|
|
||||||
instance = kinematics_cleavage_opening_instance(phase)
|
|
||||||
kinematics_cleavage_opening_Ncleavage(1:lattice_maxNcleavageFamily,instance) = &
|
|
||||||
min(lattice_NcleavageSystem(1:lattice_maxNcleavageFamily,phase),& ! limit active cleavage systems per family to min of available and requested
|
|
||||||
kinematics_cleavage_opening_Ncleavage(1:lattice_maxNcleavageFamily,instance))
|
|
||||||
kinematics_cleavage_opening_totalNcleavage(instance) = sum(kinematics_cleavage_opening_Ncleavage(:,instance)) ! how many cleavage systems altogether
|
|
||||||
if (kinematics_cleavage_opening_sdot_0(instance) <= 0.0_pReal) &
|
|
||||||
call IO_error(211_pInt,el=instance,ext_msg='sdot_0 ('//KINEMATICS_cleavage_opening_LABEL//')')
|
|
||||||
if (any(kinematics_cleavage_opening_critDisp(1:Nchunks_CleavageFamilies,instance) < 0.0_pReal)) &
|
|
||||||
call IO_error(211_pInt,el=instance,ext_msg='critical_displacement ('//KINEMATICS_cleavage_opening_LABEL//')')
|
|
||||||
if (any(kinematics_cleavage_opening_critLoad(1:Nchunks_CleavageFamilies,instance) < 0.0_pReal)) &
|
|
||||||
call IO_error(211_pInt,el=instance,ext_msg='critical_load ('//KINEMATICS_cleavage_opening_LABEL//')')
|
|
||||||
if (kinematics_cleavage_opening_N(instance) <= 0.0_pReal) &
|
|
||||||
call IO_error(211_pInt,el=instance,ext_msg='rate_sensitivity ('//KINEMATICS_cleavage_opening_LABEL//')')
|
|
||||||
endif myPhase
|
|
||||||
enddo sanityChecks
|
|
||||||
|
|
||||||
end subroutine kinematics_cleavage_opening_init
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief contains the constitutive equation for calculating the velocity gradient
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine kinematics_cleavage_opening_LiAndItsTangent(Ld, dLd_dTstar3333, Tstar_v, ipc, ip, el)
|
|
||||||
use prec, only: &
|
|
||||||
tol_math_check
|
|
||||||
use material, only: &
|
|
||||||
phaseAt, phasememberAt, &
|
|
||||||
material_homog, &
|
|
||||||
damage, &
|
|
||||||
damageMapping
|
|
||||||
use lattice, only: &
|
|
||||||
lattice_Scleavage, &
|
|
||||||
lattice_Scleavage_v, &
|
|
||||||
lattice_maxNcleavageFamily, &
|
|
||||||
lattice_NcleavageSystem
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
integer(pInt), intent(in) :: &
|
|
||||||
ipc, & !< grain number
|
|
||||||
ip, & !< integration point number
|
|
||||||
el !< element number
|
|
||||||
real(pReal), intent(in), dimension(6) :: &
|
|
||||||
Tstar_v !< 2nd Piola-Kirchhoff stress
|
|
||||||
real(pReal), intent(out), dimension(3,3) :: &
|
|
||||||
Ld !< damage velocity gradient
|
|
||||||
real(pReal), intent(out), dimension(3,3,3,3) :: &
|
|
||||||
dLd_dTstar3333 !< derivative of Ld with respect to Tstar (4th-order tensor)
|
|
||||||
integer(pInt) :: &
|
|
||||||
phase, &
|
|
||||||
constituent, &
|
|
||||||
instance, &
|
|
||||||
homog, damageOffset, &
|
|
||||||
f, i, index_myFamily, k, l, m, n
|
|
||||||
real(pReal) :: &
|
|
||||||
traction_d, traction_t, traction_n, traction_crit, &
|
|
||||||
udotd, dudotd_dt, udott, dudott_dt, udotn, dudotn_dt
|
|
||||||
|
|
||||||
phase = phaseAt(ipc,ip,el)
|
|
||||||
constituent = phasememberAt(ipc,ip,el)
|
|
||||||
instance = kinematics_cleavage_opening_instance(phase)
|
|
||||||
homog = material_homog(ip,el)
|
|
||||||
damageOffset = damageMapping(homog)%p(ip,el)
|
|
||||||
|
|
||||||
Ld = 0.0_pReal
|
|
||||||
dLd_dTstar3333 = 0.0_pReal
|
|
||||||
do f = 1_pInt,lattice_maxNcleavageFamily
|
|
||||||
index_myFamily = sum(lattice_NcleavageSystem(1:f-1_pInt,phase)) ! at which index starts my family
|
|
||||||
do i = 1_pInt,kinematics_cleavage_opening_Ncleavage(f,instance) ! process each (active) cleavage system in family
|
|
||||||
traction_d = dot_product(Tstar_v,lattice_Scleavage_v(1:6,1,index_myFamily+i,phase))
|
|
||||||
traction_t = dot_product(Tstar_v,lattice_Scleavage_v(1:6,2,index_myFamily+i,phase))
|
|
||||||
traction_n = dot_product(Tstar_v,lattice_Scleavage_v(1:6,3,index_myFamily+i,phase))
|
|
||||||
traction_crit = kinematics_cleavage_opening_critLoad(f,instance)* &
|
|
||||||
damage(homog)%p(damageOffset)*damage(homog)%p(damageOffset)
|
|
||||||
udotd = &
|
|
||||||
sign(1.0_pReal,traction_d)* &
|
|
||||||
kinematics_cleavage_opening_sdot_0(instance)* &
|
|
||||||
(max(0.0_pReal, abs(traction_d) - traction_crit)/traction_crit)**kinematics_cleavage_opening_N(instance)
|
|
||||||
if (abs(udotd) > tol_math_check) then
|
|
||||||
Ld = Ld + udotd*lattice_Scleavage(1:3,1:3,1,index_myFamily+i,phase)
|
|
||||||
dudotd_dt = sign(1.0_pReal,traction_d)*udotd*kinematics_cleavage_opening_N(instance)/ &
|
|
||||||
max(0.0_pReal, abs(traction_d) - traction_crit)
|
|
||||||
forall (k=1_pInt:3_pInt,l=1_pInt:3_pInt,m=1_pInt:3_pInt,n=1_pInt:3_pInt) &
|
|
||||||
dLd_dTstar3333(k,l,m,n) = dLd_dTstar3333(k,l,m,n) + &
|
|
||||||
dudotd_dt*lattice_Scleavage(k,l,1,index_myFamily+i,phase)* &
|
|
||||||
lattice_Scleavage(m,n,1,index_myFamily+i,phase)
|
|
||||||
endif
|
|
||||||
|
|
||||||
udott = &
|
|
||||||
sign(1.0_pReal,traction_t)* &
|
|
||||||
kinematics_cleavage_opening_sdot_0(instance)* &
|
|
||||||
(max(0.0_pReal, abs(traction_t) - traction_crit)/traction_crit)**kinematics_cleavage_opening_N(instance)
|
|
||||||
if (abs(udott) > tol_math_check) then
|
|
||||||
Ld = Ld + udott*lattice_Scleavage(1:3,1:3,2,index_myFamily+i,phase)
|
|
||||||
dudott_dt = sign(1.0_pReal,traction_t)*udott*kinematics_cleavage_opening_N(instance)/ &
|
|
||||||
max(0.0_pReal, abs(traction_t) - traction_crit)
|
|
||||||
forall (k=1_pInt:3_pInt,l=1_pInt:3_pInt,m=1_pInt:3_pInt,n=1_pInt:3_pInt) &
|
|
||||||
dLd_dTstar3333(k,l,m,n) = dLd_dTstar3333(k,l,m,n) + &
|
|
||||||
dudott_dt*lattice_Scleavage(k,l,2,index_myFamily+i,phase)* &
|
|
||||||
lattice_Scleavage(m,n,2,index_myFamily+i,phase)
|
|
||||||
endif
|
|
||||||
|
|
||||||
udotn = &
|
|
||||||
sign(1.0_pReal,traction_n)* &
|
|
||||||
kinematics_cleavage_opening_sdot_0(instance)* &
|
|
||||||
(max(0.0_pReal, abs(traction_n) - traction_crit)/traction_crit)**kinematics_cleavage_opening_N(instance)
|
|
||||||
if (abs(udotn) > tol_math_check) then
|
|
||||||
Ld = Ld + udotn*lattice_Scleavage(1:3,1:3,3,index_myFamily+i,phase)
|
|
||||||
dudotn_dt = sign(1.0_pReal,traction_n)*udotn*kinematics_cleavage_opening_N(instance)/ &
|
|
||||||
max(0.0_pReal, abs(traction_n) - traction_crit)
|
|
||||||
forall (k=1_pInt:3_pInt,l=1_pInt:3_pInt,m=1_pInt:3_pInt,n=1_pInt:3_pInt) &
|
|
||||||
dLd_dTstar3333(k,l,m,n) = dLd_dTstar3333(k,l,m,n) + &
|
|
||||||
dudotn_dt*lattice_Scleavage(k,l,3,index_myFamily+i,phase)* &
|
|
||||||
lattice_Scleavage(m,n,3,index_myFamily+i,phase)
|
|
||||||
endif
|
|
||||||
|
|
||||||
enddo
|
|
||||||
enddo
|
|
||||||
|
|
||||||
end subroutine kinematics_cleavage_opening_LiAndItsTangent
|
|
||||||
|
|
||||||
end module kinematics_cleavage_opening
|
|
|
@ -1,264 +0,0 @@
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! $Id$
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @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)
|
|
||||||
use, intrinsic :: iso_fortran_env ! to get compiler_version and compiler_options (at least for gfortran 4.6 at the moment)
|
|
||||||
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, &
|
|
||||||
material_Nphase, &
|
|
||||||
MATERIAL_partPhase
|
|
||||||
use numerics,only: &
|
|
||||||
worldrank
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
integer(pInt), intent(in) :: fileUnit
|
|
||||||
|
|
||||||
integer(pInt), allocatable, dimension(:) :: chunkPos
|
|
||||||
integer(pInt) :: maxNinstance,phase,instance,kinematics
|
|
||||||
character(len=65536) :: &
|
|
||||||
tag = '', &
|
|
||||||
line = ''
|
|
||||||
|
|
||||||
mainProcess: if (worldrank == 0) then
|
|
||||||
write(6,'(/,a)') ' <<<+- kinematics_'//KINEMATICS_hydrogen_strain_LABEL//' init -+>>>'
|
|
||||||
write(6,'(a15,a)') ' Current time: ',IO_timeStamp()
|
|
||||||
#include "compilation_info.f90"
|
|
||||||
endif mainProcess
|
|
||||||
|
|
||||||
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,323 +0,0 @@
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! $Id$
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @author Luv Sharma, Max-Planck-Institut für Eisenforschung GmbH
|
|
||||||
!> @author Pratheek Shanthraj, Max-Planck-Institut für Eisenforschung GmbH
|
|
||||||
!> @brief material subroutine incorporating kinematics resulting from opening of slip planes
|
|
||||||
!> @details to be done
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
module kinematics_slipplane_opening
|
|
||||||
use prec, only: &
|
|
||||||
pReal, &
|
|
||||||
pInt
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
private
|
|
||||||
integer(pInt), dimension(:), allocatable, public, protected :: &
|
|
||||||
kinematics_slipplane_opening_sizePostResults, & !< cumulative size of post results
|
|
||||||
kinematics_slipplane_opening_offset, & !< which kinematics is my current damage mechanism?
|
|
||||||
kinematics_slipplane_opening_instance !< instance of damage kinematics mechanism
|
|
||||||
|
|
||||||
integer(pInt), dimension(:,:), allocatable, target, public :: &
|
|
||||||
kinematics_slipplane_opening_sizePostResult !< size of each post result output
|
|
||||||
|
|
||||||
character(len=64), dimension(:,:), allocatable, target, public :: &
|
|
||||||
kinematics_slipplane_opening_output !< name of each post result output
|
|
||||||
|
|
||||||
integer(pInt), dimension(:), allocatable, target, public :: &
|
|
||||||
kinematics_slipplane_opening_Noutput !< number of outputs per instance of this damage
|
|
||||||
|
|
||||||
integer(pInt), dimension(:), allocatable, private :: &
|
|
||||||
kinematics_slipplane_opening_totalNslip !< total number of slip systems
|
|
||||||
|
|
||||||
integer(pInt), dimension(:,:), allocatable, private :: &
|
|
||||||
kinematics_slipplane_opening_Nslip !< number of slip systems per family
|
|
||||||
|
|
||||||
real(pReal), dimension(:), allocatable, private :: &
|
|
||||||
kinematics_slipplane_opening_sdot_0, &
|
|
||||||
kinematics_slipplane_opening_N
|
|
||||||
|
|
||||||
real(pReal), dimension(:,:), allocatable, private :: &
|
|
||||||
kinematics_slipplane_opening_critPlasticStrain, &
|
|
||||||
kinematics_slipplane_opening_critLoad
|
|
||||||
|
|
||||||
public :: &
|
|
||||||
kinematics_slipplane_opening_init, &
|
|
||||||
kinematics_slipplane_opening_LiAndItsTangent
|
|
||||||
|
|
||||||
contains
|
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief module initialization
|
|
||||||
!> @details reads in material parameters, allocates arrays, and does sanity checks
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine kinematics_slipplane_opening_init(fileUnit)
|
|
||||||
use, intrinsic :: iso_fortran_env ! to get compiler_version and compiler_options (at least for gfortran 4.6 at the moment)
|
|
||||||
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_slipplane_opening_label, &
|
|
||||||
KINEMATICS_slipplane_opening_ID, &
|
|
||||||
material_Nphase, &
|
|
||||||
MATERIAL_partPhase
|
|
||||||
use numerics,only: &
|
|
||||||
worldrank
|
|
||||||
use lattice, only: &
|
|
||||||
lattice_maxNslipFamily, &
|
|
||||||
lattice_NslipSystem
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
integer(pInt), intent(in) :: fileUnit
|
|
||||||
|
|
||||||
integer(pInt), allocatable, dimension(:) :: chunkPos
|
|
||||||
integer(pInt) :: maxNinstance,phase,instance,kinematics
|
|
||||||
integer(pInt) :: Nchunks_SlipFamilies = 0_pInt, j
|
|
||||||
character(len=65536) :: &
|
|
||||||
tag = '', &
|
|
||||||
line = ''
|
|
||||||
|
|
||||||
mainProcess: if (worldrank == 0) then
|
|
||||||
write(6,'(/,a)') ' <<<+- kinematics_'//KINEMATICS_slipplane_opening_LABEL//' init -+>>>'
|
|
||||||
write(6,'(a15,a)') ' Current time: ',IO_timeStamp()
|
|
||||||
#include "compilation_info.f90"
|
|
||||||
endif mainProcess
|
|
||||||
|
|
||||||
maxNinstance = int(count(phase_kinematics == KINEMATICS_slipplane_opening_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_slipplane_opening_offset(material_Nphase), source=0_pInt)
|
|
||||||
allocate(kinematics_slipplane_opening_instance(material_Nphase), source=0_pInt)
|
|
||||||
do phase = 1, material_Nphase
|
|
||||||
kinematics_slipplane_opening_instance(phase) = count(phase_kinematics(:,1:phase) == kinematics_slipplane_opening_ID)
|
|
||||||
do kinematics = 1, phase_Nkinematics(phase)
|
|
||||||
if (phase_kinematics(kinematics,phase) == kinematics_slipplane_opening_ID) &
|
|
||||||
kinematics_slipplane_opening_offset(phase) = kinematics
|
|
||||||
enddo
|
|
||||||
enddo
|
|
||||||
|
|
||||||
allocate(kinematics_slipplane_opening_sizePostResults(maxNinstance), source=0_pInt)
|
|
||||||
allocate(kinematics_slipplane_opening_sizePostResult(maxval(phase_Noutput),maxNinstance),source=0_pInt)
|
|
||||||
allocate(kinematics_slipplane_opening_output(maxval(phase_Noutput),maxNinstance))
|
|
||||||
kinematics_slipplane_opening_output = ''
|
|
||||||
allocate(kinematics_slipplane_opening_Noutput(maxNinstance), source=0_pInt)
|
|
||||||
allocate(kinematics_slipplane_opening_critLoad(lattice_maxNslipFamily,maxNinstance), source=0.0_pReal)
|
|
||||||
allocate(kinematics_slipplane_opening_critPlasticStrain(lattice_maxNslipFamily,maxNinstance),source=0.0_pReal)
|
|
||||||
allocate(kinematics_slipplane_opening_Nslip(lattice_maxNslipFamily,maxNinstance), source=0_pInt)
|
|
||||||
allocate(kinematics_slipplane_opening_totalNslip(maxNinstance), source=0_pInt)
|
|
||||||
allocate(kinematics_slipplane_opening_N(maxNinstance), source=0.0_pReal)
|
|
||||||
allocate(kinematics_slipplane_opening_sdot_0(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_slipplane_opening_ID)) then ! do not short-circuit here (.and. with next if statemen). It's not safe in Fortran
|
|
||||||
instance = kinematics_slipplane_opening_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 ('nslip') !
|
|
||||||
Nchunks_SlipFamilies = chunkPos(1) - 1_pInt
|
|
||||||
do j = 1_pInt, Nchunks_SlipFamilies
|
|
||||||
kinematics_slipplane_opening_Nslip(j,instance) = IO_intValue(line,chunkPos,1_pInt+j)
|
|
||||||
enddo
|
|
||||||
|
|
||||||
case ('anisoductile_sdot0')
|
|
||||||
kinematics_slipplane_opening_sdot_0(instance) = IO_floatValue(line,chunkPos,2_pInt)
|
|
||||||
|
|
||||||
case ('anisoductile_criticalplasticstrain')
|
|
||||||
do j = 1_pInt, Nchunks_SlipFamilies
|
|
||||||
kinematics_slipplane_opening_critPlasticStrain(j,instance) = IO_floatValue(line,chunkPos,1_pInt+j)
|
|
||||||
enddo
|
|
||||||
|
|
||||||
case ('anisoductile_ratesensitivity')
|
|
||||||
kinematics_slipplane_opening_N(instance) = IO_floatValue(line,chunkPos,2_pInt)
|
|
||||||
|
|
||||||
case ('anisoductile_criticalload')
|
|
||||||
do j = 1_pInt, Nchunks_SlipFamilies
|
|
||||||
kinematics_slipplane_opening_critLoad(j,instance) = IO_floatValue(line,chunkPos,1_pInt+j)
|
|
||||||
enddo
|
|
||||||
|
|
||||||
end select
|
|
||||||
endif; endif
|
|
||||||
enddo parsingFile
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! sanity checks
|
|
||||||
sanityChecks: do phase = 1_pInt, material_Nphase
|
|
||||||
myPhase: if (any(phase_kinematics(:,phase) == KINEMATICS_slipplane_opening_ID)) then
|
|
||||||
instance = kinematics_slipplane_opening_instance(phase)
|
|
||||||
kinematics_slipplane_opening_Nslip(1:lattice_maxNslipFamily,instance) = &
|
|
||||||
min(lattice_NslipSystem(1:lattice_maxNslipFamily,phase),& ! limit active cleavage systems per family to min of available and requested
|
|
||||||
kinematics_slipplane_opening_Nslip(1:lattice_maxNslipFamily,instance))
|
|
||||||
kinematics_slipplane_opening_totalNslip(instance) = sum(kinematics_slipplane_opening_Nslip(:,instance))
|
|
||||||
if (kinematics_slipplane_opening_sdot_0(instance) <= 0.0_pReal) &
|
|
||||||
call IO_error(211_pInt,el=instance,ext_msg='sdot_0 ('//KINEMATICS_slipplane_opening_LABEL//')')
|
|
||||||
if (any(kinematics_slipplane_opening_critPlasticStrain(:,instance) < 0.0_pReal)) &
|
|
||||||
call IO_error(211_pInt,el=instance,ext_msg='criticaPlasticStrain ('//KINEMATICS_slipplane_opening_LABEL//')')
|
|
||||||
if (kinematics_slipplane_opening_N(instance) <= 0.0_pReal) &
|
|
||||||
call IO_error(211_pInt,el=instance,ext_msg='rate_sensitivity ('//KINEMATICS_slipplane_opening_LABEL//')')
|
|
||||||
endif myPhase
|
|
||||||
enddo sanityChecks
|
|
||||||
|
|
||||||
|
|
||||||
end subroutine kinematics_slipplane_opening_init
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief contains the constitutive equation for calculating the velocity gradient
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine kinematics_slipplane_opening_LiAndItsTangent(Ld, dLd_dTstar3333, Tstar_v, ipc, ip, el)
|
|
||||||
use prec, only: &
|
|
||||||
tol_math_check
|
|
||||||
use lattice, only: &
|
|
||||||
lattice_maxNslipFamily, &
|
|
||||||
lattice_NslipSystem, &
|
|
||||||
lattice_sd, &
|
|
||||||
lattice_st, &
|
|
||||||
lattice_sn
|
|
||||||
use material, only: &
|
|
||||||
phaseAt, phasememberAt, &
|
|
||||||
material_homog, &
|
|
||||||
damage, &
|
|
||||||
damageMapping
|
|
||||||
use math, only: &
|
|
||||||
math_Plain3333to99, &
|
|
||||||
math_I3, &
|
|
||||||
math_identity4th, &
|
|
||||||
math_symmetric33, &
|
|
||||||
math_Mandel33to6, &
|
|
||||||
math_tensorproduct33, &
|
|
||||||
math_det33, &
|
|
||||||
math_mul33x33
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
integer(pInt), intent(in) :: &
|
|
||||||
ipc, & !< grain number
|
|
||||||
ip, & !< integration point number
|
|
||||||
el !< element number
|
|
||||||
real(pReal), intent(in), dimension(6) :: &
|
|
||||||
Tstar_v !< 2nd Piola-Kirchhoff stress
|
|
||||||
real(pReal), intent(out), dimension(3,3) :: &
|
|
||||||
Ld !< damage velocity gradient
|
|
||||||
real(pReal), intent(out), dimension(3,3,3,3) :: &
|
|
||||||
dLd_dTstar3333 !< derivative of Ld with respect to Tstar (4th-order tensor)
|
|
||||||
real(pReal), dimension(3,3) :: &
|
|
||||||
projection_d, projection_t, projection_n !< projection modes 3x3 tensor
|
|
||||||
real(pReal), dimension(6) :: &
|
|
||||||
projection_d_v, projection_t_v, projection_n_v !< projection modes 3x3 vector
|
|
||||||
integer(pInt) :: &
|
|
||||||
phase, &
|
|
||||||
constituent, &
|
|
||||||
instance, &
|
|
||||||
homog, damageOffset, &
|
|
||||||
f, i, index_myFamily, k, l, m, n
|
|
||||||
real(pReal) :: &
|
|
||||||
traction_d, traction_t, traction_n, traction_crit, &
|
|
||||||
udotd, dudotd_dt, udott, dudott_dt, udotn, dudotn_dt
|
|
||||||
|
|
||||||
phase = phaseAt(ipc,ip,el)
|
|
||||||
constituent = phasememberAt(ipc,ip,el)
|
|
||||||
instance = kinematics_slipplane_opening_instance(phase)
|
|
||||||
homog = material_homog(ip,el)
|
|
||||||
damageOffset = damageMapping(homog)%p(ip,el)
|
|
||||||
|
|
||||||
Ld = 0.0_pReal
|
|
||||||
dLd_dTstar3333 = 0.0_pReal
|
|
||||||
do f = 1_pInt,lattice_maxNslipFamily
|
|
||||||
index_myFamily = sum(lattice_NslipSystem(1:f-1_pInt,phase)) ! at which index starts my family
|
|
||||||
do i = 1_pInt,kinematics_slipplane_opening_Nslip(f,instance) ! process each (active) slip system in family
|
|
||||||
projection_d = math_tensorproduct33(lattice_sd(1:3,index_myFamily+i,phase),&
|
|
||||||
lattice_sn(1:3,index_myFamily+i,phase))
|
|
||||||
projection_t = math_tensorproduct33(lattice_st(1:3,index_myFamily+i,phase),&
|
|
||||||
lattice_sn(1:3,index_myFamily+i,phase))
|
|
||||||
projection_n = math_tensorproduct33(lattice_sn(1:3,index_myFamily+i,phase),&
|
|
||||||
lattice_sn(1:3,index_myFamily+i,phase))
|
|
||||||
|
|
||||||
projection_d_v(1:6) = math_Mandel33to6(math_symmetric33(projection_d(1:3,1:3)))
|
|
||||||
projection_t_v(1:6) = math_Mandel33to6(math_symmetric33(projection_t(1:3,1:3)))
|
|
||||||
projection_n_v(1:6) = math_Mandel33to6(math_symmetric33(projection_n(1:3,1:3)))
|
|
||||||
|
|
||||||
traction_d = dot_product(Tstar_v,projection_d_v(1:6))
|
|
||||||
traction_t = dot_product(Tstar_v,projection_t_v(1:6))
|
|
||||||
traction_n = dot_product(Tstar_v,projection_n_v(1:6))
|
|
||||||
|
|
||||||
traction_crit = kinematics_slipplane_opening_critLoad(f,instance)* &
|
|
||||||
damage(homog)%p(damageOffset) ! degrading critical load carrying capacity by damage
|
|
||||||
|
|
||||||
udotd = &
|
|
||||||
sign(1.0_pReal,traction_d)* &
|
|
||||||
kinematics_slipplane_opening_sdot_0(instance)* &
|
|
||||||
(abs(traction_d)/traction_crit - &
|
|
||||||
abs(traction_d)/kinematics_slipplane_opening_critLoad(f,instance))**kinematics_slipplane_opening_N(instance)
|
|
||||||
if (abs(udotd) > tol_math_check) then
|
|
||||||
Ld = Ld + udotd*projection_d
|
|
||||||
dudotd_dt = udotd*kinematics_slipplane_opening_N(instance)/traction_d
|
|
||||||
forall (k=1_pInt:3_pInt,l=1_pInt:3_pInt,m=1_pInt:3_pInt,n=1_pInt:3_pInt) &
|
|
||||||
dLd_dTstar3333(k,l,m,n) = dLd_dTstar3333(k,l,m,n) + &
|
|
||||||
dudotd_dt*projection_d(k,l)*projection_d(m,n)
|
|
||||||
endif
|
|
||||||
|
|
||||||
udott = &
|
|
||||||
sign(1.0_pReal,traction_t)* &
|
|
||||||
kinematics_slipplane_opening_sdot_0(instance)* &
|
|
||||||
(abs(traction_t)/traction_crit - &
|
|
||||||
abs(traction_t)/kinematics_slipplane_opening_critLoad(f,instance))**kinematics_slipplane_opening_N(instance)
|
|
||||||
if (abs(udott) > tol_math_check) then
|
|
||||||
Ld = Ld + udott*projection_t
|
|
||||||
dudott_dt = udott*kinematics_slipplane_opening_N(instance)/traction_t
|
|
||||||
forall (k=1_pInt:3_pInt,l=1_pInt:3_pInt,m=1_pInt:3_pInt,n=1_pInt:3_pInt) &
|
|
||||||
dLd_dTstar3333(k,l,m,n) = dLd_dTstar3333(k,l,m,n) + &
|
|
||||||
dudott_dt*projection_t(k,l)*projection_t(m,n)
|
|
||||||
endif
|
|
||||||
udotn = &
|
|
||||||
kinematics_slipplane_opening_sdot_0(instance)* &
|
|
||||||
(max(0.0_pReal,traction_n)/traction_crit - &
|
|
||||||
max(0.0_pReal,traction_n)/kinematics_slipplane_opening_critLoad(f,instance))**kinematics_slipplane_opening_N(instance)
|
|
||||||
if (abs(udotn) > tol_math_check) then
|
|
||||||
Ld = Ld + udotn*projection_n
|
|
||||||
dudotn_dt = udotn*kinematics_slipplane_opening_N(instance)/traction_n
|
|
||||||
forall (k=1_pInt:3_pInt,l=1_pInt:3_pInt,m=1_pInt:3_pInt,n=1_pInt:3_pInt) &
|
|
||||||
dLd_dTstar3333(k,l,m,n) = dLd_dTstar3333(k,l,m,n) + &
|
|
||||||
dudotn_dt*projection_n(k,l)*projection_n(m,n)
|
|
||||||
endif
|
|
||||||
enddo
|
|
||||||
enddo
|
|
||||||
|
|
||||||
end subroutine kinematics_slipplane_opening_LiAndItsTangent
|
|
||||||
|
|
||||||
end module kinematics_slipplane_opening
|
|
|
@ -1,228 +0,0 @@
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! $Id$
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @author Pratheek Shanthraj, Max-Planck-Institut für Eisenforschung GmbH
|
|
||||||
!> @brief material subroutine incorporating kinematics resulting from thermal expansion
|
|
||||||
!> @details to be done
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
module kinematics_thermal_expansion
|
|
||||||
use prec, only: &
|
|
||||||
pReal, &
|
|
||||||
pInt
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
private
|
|
||||||
integer(pInt), dimension(:), allocatable, public, protected :: &
|
|
||||||
kinematics_thermal_expansion_sizePostResults, & !< cumulative size of post results
|
|
||||||
kinematics_thermal_expansion_offset, & !< which kinematics is my current damage mechanism?
|
|
||||||
kinematics_thermal_expansion_instance !< instance of damage kinematics mechanism
|
|
||||||
|
|
||||||
integer(pInt), dimension(:,:), allocatable, target, public :: &
|
|
||||||
kinematics_thermal_expansion_sizePostResult !< size of each post result output
|
|
||||||
|
|
||||||
character(len=64), dimension(:,:), allocatable, target, public :: &
|
|
||||||
kinematics_thermal_expansion_output !< name of each post result output
|
|
||||||
|
|
||||||
integer(pInt), dimension(:), allocatable, target, public :: &
|
|
||||||
kinematics_thermal_expansion_Noutput !< number of outputs per instance of this damage
|
|
||||||
|
|
||||||
! enum, bind(c) ! ToDo kinematics need state machinery to deal with sizePostResult
|
|
||||||
! enumerator :: undefined_ID, & ! possible remedy is to decouple having state vars from having output
|
|
||||||
! thermalexpansionrate_ID ! which means to separate user-defined types tState + tOutput...
|
|
||||||
! end enum
|
|
||||||
public :: &
|
|
||||||
kinematics_thermal_expansion_init, &
|
|
||||||
kinematics_thermal_expansion_initialStrain, &
|
|
||||||
kinematics_thermal_expansion_LiAndItsTangent
|
|
||||||
|
|
||||||
contains
|
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief module initialization
|
|
||||||
!> @details reads in material parameters, allocates arrays, and does sanity checks
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine kinematics_thermal_expansion_init(fileUnit)
|
|
||||||
use, intrinsic :: iso_fortran_env ! to get compiler_version and compiler_options (at least for gfortran 4.6 at the moment)
|
|
||||||
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_thermal_expansion_label, &
|
|
||||||
KINEMATICS_thermal_expansion_ID, &
|
|
||||||
material_Nphase, &
|
|
||||||
MATERIAL_partPhase
|
|
||||||
use numerics,only: &
|
|
||||||
worldrank
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
integer(pInt), intent(in) :: fileUnit
|
|
||||||
|
|
||||||
integer(pInt), allocatable, dimension(:) :: chunkPos
|
|
||||||
integer(pInt) :: maxNinstance,phase,instance,kinematics
|
|
||||||
character(len=65536) :: &
|
|
||||||
tag = '', &
|
|
||||||
output = '', &
|
|
||||||
line = ''
|
|
||||||
|
|
||||||
mainProcess: if (worldrank == 0) then
|
|
||||||
write(6,'(/,a)') ' <<<+- kinematics_'//KINEMATICS_thermal_expansion_LABEL//' init -+>>>'
|
|
||||||
write(6,'(a15,a)') ' Current time: ',IO_timeStamp()
|
|
||||||
#include "compilation_info.f90"
|
|
||||||
endif mainProcess
|
|
||||||
|
|
||||||
maxNinstance = int(count(phase_kinematics == KINEMATICS_thermal_expansion_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_thermal_expansion_offset(material_Nphase), source=0_pInt)
|
|
||||||
allocate(kinematics_thermal_expansion_instance(material_Nphase), source=0_pInt)
|
|
||||||
do phase = 1, material_Nphase
|
|
||||||
kinematics_thermal_expansion_instance(phase) = count(phase_kinematics(:,1:phase) == kinematics_thermal_expansion_ID)
|
|
||||||
do kinematics = 1, phase_Nkinematics(phase)
|
|
||||||
if (phase_kinematics(kinematics,phase) == kinematics_thermal_expansion_ID) &
|
|
||||||
kinematics_thermal_expansion_offset(phase) = kinematics
|
|
||||||
enddo
|
|
||||||
enddo
|
|
||||||
|
|
||||||
allocate(kinematics_thermal_expansion_sizePostResults(maxNinstance), source=0_pInt)
|
|
||||||
allocate(kinematics_thermal_expansion_sizePostResult(maxval(phase_Noutput),maxNinstance),source=0_pInt)
|
|
||||||
allocate(kinematics_thermal_expansion_output(maxval(phase_Noutput),maxNinstance))
|
|
||||||
kinematics_thermal_expansion_output = ''
|
|
||||||
allocate(kinematics_thermal_expansion_Noutput(maxNinstance), source=0_pInt)
|
|
||||||
|
|
||||||
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_thermal_expansion_ID)) then ! do not short-circuit here (.and. with next if statemen). It's not safe in Fortran
|
|
||||||
instance = kinematics_thermal_expansion_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 ('(output)')
|
|
||||||
! output = IO_lc(IO_stringValue(line,chunkPos,2_pInt)) ! ...and corresponding output
|
|
||||||
! select case(output)
|
|
||||||
! case ('thermalexpansionrate')
|
|
||||||
! kinematics_thermal_expansion_Noutput(instance) = kinematics_thermal_expansion_Noutput(instance) + 1_pInt
|
|
||||||
! kinematics_thermal_expansion_outputID(kinematics_thermal_expansion_Noutput(instance),instance) = &
|
|
||||||
! thermalexpansionrate_ID
|
|
||||||
! kinematics_thermal_expansion_output(kinematics_thermal_expansion_Noutput(instance),instance) = output
|
|
||||||
! ToDo add sizePostResult loop afterwards...
|
|
||||||
|
|
||||||
end select
|
|
||||||
endif; endif
|
|
||||||
enddo parsingFile
|
|
||||||
|
|
||||||
end subroutine kinematics_thermal_expansion_init
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief report initial thermal strain based on current temperature deviation from reference
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
pure function kinematics_thermal_expansion_initialStrain(ipc, ip, el)
|
|
||||||
use material, only: &
|
|
||||||
material_phase, &
|
|
||||||
material_homog, &
|
|
||||||
temperature, &
|
|
||||||
thermalMapping
|
|
||||||
use lattice, only: &
|
|
||||||
lattice_thermalExpansion33, &
|
|
||||||
lattice_referenceTemperature
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
integer(pInt), intent(in) :: &
|
|
||||||
ipc, & !< grain number
|
|
||||||
ip, & !< integration point number
|
|
||||||
el !< element number
|
|
||||||
real(pReal), dimension(3,3) :: &
|
|
||||||
kinematics_thermal_expansion_initialStrain !< initial thermal strain (should be small strain, though)
|
|
||||||
integer(pInt) :: &
|
|
||||||
phase, &
|
|
||||||
homog, offset
|
|
||||||
|
|
||||||
phase = material_phase(ipc,ip,el)
|
|
||||||
homog = material_homog(ip,el)
|
|
||||||
offset = thermalMapping(homog)%p(ip,el)
|
|
||||||
|
|
||||||
kinematics_thermal_expansion_initialStrain = &
|
|
||||||
(temperature(homog)%p(offset) - lattice_referenceTemperature(phase)) * &
|
|
||||||
lattice_thermalExpansion33(1:3,1:3,phase)
|
|
||||||
|
|
||||||
end function kinematics_thermal_expansion_initialStrain
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief contains the constitutive equation for calculating the velocity gradient
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine kinematics_thermal_expansion_LiAndItsTangent(Li, dLi_dTstar3333, ipc, ip, el)
|
|
||||||
use material, only: &
|
|
||||||
material_phase, &
|
|
||||||
material_homog, &
|
|
||||||
temperature, &
|
|
||||||
temperatureRate, &
|
|
||||||
thermalMapping
|
|
||||||
use lattice, only: &
|
|
||||||
lattice_thermalExpansion33, &
|
|
||||||
lattice_referenceTemperature
|
|
||||||
|
|
||||||
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 defined to be zero)
|
|
||||||
integer(pInt) :: &
|
|
||||||
phase, &
|
|
||||||
homog, offset
|
|
||||||
real(pReal) :: &
|
|
||||||
T, TRef, TDot
|
|
||||||
|
|
||||||
phase = material_phase(ipc,ip,el)
|
|
||||||
homog = material_homog(ip,el)
|
|
||||||
offset = thermalMapping(homog)%p(ip,el)
|
|
||||||
T = temperature(homog)%p(offset)
|
|
||||||
TDot = temperatureRate(homog)%p(offset)
|
|
||||||
TRef = lattice_referenceTemperature(phase)
|
|
||||||
|
|
||||||
Li = TDot* &
|
|
||||||
lattice_thermalExpansion33(1:3,1:3,phase)/ &
|
|
||||||
(1.0_pReal + lattice_thermalExpansion33(1:3,1:3,phase)*(T - TRef))
|
|
||||||
dLi_dTstar3333 = 0.0_pReal
|
|
||||||
|
|
||||||
end subroutine kinematics_thermal_expansion_LiAndItsTangent
|
|
||||||
|
|
||||||
end module kinematics_thermal_expansion
|
|
|
@ -1,265 +0,0 @@
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! $Id$
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @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)
|
|
||||||
use, intrinsic :: iso_fortran_env ! to get compiler_version and compiler_options (at least for gfortran 4.6 at the moment)
|
|
||||||
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, &
|
|
||||||
material_Nphase, &
|
|
||||||
MATERIAL_partPhase
|
|
||||||
use numerics,only: &
|
|
||||||
worldrank
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
integer(pInt), intent(in) :: fileUnit
|
|
||||||
|
|
||||||
integer(pInt), allocatable, dimension(:) :: chunkPos
|
|
||||||
integer(pInt) :: maxNinstance,phase,instance,kinematics
|
|
||||||
character(len=65536) :: &
|
|
||||||
tag = '', &
|
|
||||||
line = ''
|
|
||||||
|
|
||||||
mainProcess: if (worldrank == 0) then
|
|
||||||
write(6,'(/,a)') ' <<<+- kinematics_'//KINEMATICS_vacancy_strain_LABEL//' init -+>>>'
|
|
||||||
write(6,'(a15,a)') ' Current time: ',IO_timeStamp()
|
|
||||||
#include "compilation_info.f90"
|
|
||||||
endif mainProcess
|
|
||||||
|
|
||||||
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
|
|
|
@ -14,3 +14,8 @@ set (PLASTIC "plastic_dislotwin"
|
||||||
foreach (p ${PLASTIC})
|
foreach (p ${PLASTIC})
|
||||||
add_library (${p} MODULE "${p}.f90")
|
add_library (${p} MODULE "${p}.f90")
|
||||||
endforeach (p)
|
endforeach (p)
|
||||||
|
|
||||||
|
# set libraries/modules for linking
|
||||||
|
foreach (p ${PLASTIC})
|
||||||
|
set (AUX_LIB ${AUX_LIB} ${p})
|
||||||
|
endforeach (p)
|
File diff suppressed because it is too large
Load Diff
File diff suppressed because it is too large
Load Diff
|
@ -1,678 +0,0 @@
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! $Id$
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @author Franz Roters, Max-Planck-Institut für Eisenforschung GmbH
|
|
||||||
!> @author Philip Eisenlohr, Max-Planck-Institut für Eisenforschung GmbH
|
|
||||||
!> @brief material subroutine for isotropic (ISOTROPIC) plasticity
|
|
||||||
!> @details Isotropic (ISOTROPIC) Plasticity which resembles the phenopowerlaw plasticity without
|
|
||||||
!! resolving the stress on the slip systems. Will give the response of phenopowerlaw for an
|
|
||||||
!! untextured polycrystal
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
module plastic_isotropic
|
|
||||||
#ifdef HDF
|
|
||||||
use hdf5, only: &
|
|
||||||
HID_T
|
|
||||||
#endif
|
|
||||||
|
|
||||||
use prec, only: &
|
|
||||||
pReal,&
|
|
||||||
pInt
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
private
|
|
||||||
integer(pInt), dimension(:), allocatable, public, protected :: &
|
|
||||||
plastic_isotropic_sizePostResults !< cumulative size of post results
|
|
||||||
|
|
||||||
integer(pInt), dimension(:,:), allocatable, target, public :: &
|
|
||||||
plastic_isotropic_sizePostResult !< size of each post result output
|
|
||||||
|
|
||||||
character(len=64), dimension(:,:), allocatable, target, public :: &
|
|
||||||
plastic_isotropic_output !< name of each post result output
|
|
||||||
|
|
||||||
integer(pInt), dimension(:), allocatable, target, public :: &
|
|
||||||
plastic_isotropic_Noutput !< number of outputs per instance
|
|
||||||
|
|
||||||
enum, bind(c)
|
|
||||||
enumerator :: undefined_ID, &
|
|
||||||
flowstress_ID, &
|
|
||||||
strainrate_ID
|
|
||||||
end enum
|
|
||||||
|
|
||||||
type, private :: tParameters !< container type for internal constitutive parameters
|
|
||||||
integer(kind(undefined_ID)), allocatable, dimension(:) :: &
|
|
||||||
outputID
|
|
||||||
real(pReal) :: &
|
|
||||||
fTaylor, &
|
|
||||||
tau0, &
|
|
||||||
gdot0, &
|
|
||||||
n, &
|
|
||||||
h0, &
|
|
||||||
h0_slopeLnRate, &
|
|
||||||
tausat, &
|
|
||||||
a, &
|
|
||||||
aTolFlowstress, &
|
|
||||||
aTolShear , &
|
|
||||||
tausat_SinhFitA, &
|
|
||||||
tausat_SinhFitB, &
|
|
||||||
tausat_SinhFitC, &
|
|
||||||
tausat_SinhFitD
|
|
||||||
logical :: &
|
|
||||||
dilatation
|
|
||||||
end type
|
|
||||||
|
|
||||||
type(tParameters), dimension(:), allocatable, private :: param !< containers of constitutive parameters (len Ninstance)
|
|
||||||
|
|
||||||
type, private :: tIsotropicState !< internal state aliases
|
|
||||||
real(pReal), pointer, dimension(:) :: & ! scalars along NipcMyInstance
|
|
||||||
flowstress, &
|
|
||||||
accumulatedShear
|
|
||||||
end type
|
|
||||||
type, private :: tIsotropicAbsTol !< internal alias for abs tolerance in state
|
|
||||||
real(pReal), pointer :: & ! scalars along NipcMyInstance
|
|
||||||
flowstress, &
|
|
||||||
accumulatedShear
|
|
||||||
end type
|
|
||||||
type(tIsotropicState), allocatable, dimension(:), private :: & !< state aliases per instance
|
|
||||||
state, &
|
|
||||||
state0, &
|
|
||||||
dotState
|
|
||||||
type(tIsotropicAbsTol), allocatable, dimension(:), private :: & !< state aliases per instance
|
|
||||||
stateAbsTol
|
|
||||||
|
|
||||||
public :: &
|
|
||||||
plastic_isotropic_init, &
|
|
||||||
plastic_isotropic_LpAndItsTangent, &
|
|
||||||
plastic_isotropic_LiAndItsTangent, &
|
|
||||||
plastic_isotropic_dotState, &
|
|
||||||
plastic_isotropic_postResults
|
|
||||||
|
|
||||||
contains
|
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief module initialization
|
|
||||||
!> @details reads in material parameters, allocates arrays, and does sanity checks
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine plastic_isotropic_init(fileUnit)
|
|
||||||
use, intrinsic :: iso_fortran_env ! to get compiler_version and compiler_options (at least for gfortran 4.6 at the moment)
|
|
||||||
use debug, only: &
|
|
||||||
debug_level, &
|
|
||||||
debug_constitutive, &
|
|
||||||
debug_levelBasic
|
|
||||||
use numerics, only: &
|
|
||||||
analyticJaco, &
|
|
||||||
worldrank, &
|
|
||||||
numerics_integrator
|
|
||||||
use math, only: &
|
|
||||||
math_Mandel3333to66, &
|
|
||||||
math_Voigt66to3333
|
|
||||||
use IO, only: &
|
|
||||||
IO_read, &
|
|
||||||
IO_lc, &
|
|
||||||
IO_getTag, &
|
|
||||||
IO_isBlank, &
|
|
||||||
IO_stringPos, &
|
|
||||||
IO_stringValue, &
|
|
||||||
IO_floatValue, &
|
|
||||||
IO_error, &
|
|
||||||
IO_timeStamp, &
|
|
||||||
IO_EOF
|
|
||||||
use material, only: &
|
|
||||||
phase_plasticity, &
|
|
||||||
phase_plasticityInstance, &
|
|
||||||
phase_Noutput, &
|
|
||||||
PLASTICITY_ISOTROPIC_label, &
|
|
||||||
PLASTICITY_ISOTROPIC_ID, &
|
|
||||||
material_phase, &
|
|
||||||
plasticState, &
|
|
||||||
MATERIAL_partPhase
|
|
||||||
|
|
||||||
use lattice
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
integer(pInt), intent(in) :: fileUnit
|
|
||||||
|
|
||||||
|
|
||||||
integer(pInt), allocatable, dimension(:) :: chunkPos
|
|
||||||
integer(pInt) :: &
|
|
||||||
o, &
|
|
||||||
phase, &
|
|
||||||
instance, &
|
|
||||||
maxNinstance, &
|
|
||||||
mySize, &
|
|
||||||
sizeDotState, &
|
|
||||||
sizeState, &
|
|
||||||
sizeDeltaState
|
|
||||||
character(len=65536) :: &
|
|
||||||
tag = '', &
|
|
||||||
outputtag = '', &
|
|
||||||
line = '', &
|
|
||||||
extmsg = ''
|
|
||||||
integer(pInt) :: NipcMyPhase
|
|
||||||
|
|
||||||
mainProcess: if (worldrank == 0) then
|
|
||||||
write(6,'(/,a)') ' <<<+- constitutive_'//PLASTICITY_ISOTROPIC_label//' init -+>>>'
|
|
||||||
write(6,'(a15,a)') ' Current time: ',IO_timeStamp()
|
|
||||||
#include "compilation_info.f90"
|
|
||||||
endif mainProcess
|
|
||||||
|
|
||||||
maxNinstance = int(count(phase_plasticity == PLASTICITY_ISOTROPIC_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(plastic_isotropic_sizePostResults(maxNinstance), source=0_pInt)
|
|
||||||
allocate(plastic_isotropic_sizePostResult(maxval(phase_Noutput), maxNinstance),source=0_pInt)
|
|
||||||
allocate(plastic_isotropic_output(maxval(phase_Noutput), maxNinstance))
|
|
||||||
plastic_isotropic_output = ''
|
|
||||||
allocate(plastic_isotropic_Noutput(maxNinstance), source=0_pInt)
|
|
||||||
|
|
||||||
allocate(param(maxNinstance)) ! one container of parameters per instance
|
|
||||||
|
|
||||||
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 section
|
|
||||||
phase = phase + 1_pInt ! advance section counter
|
|
||||||
if (phase_plasticity(phase) == PLASTICITY_ISOTROPIC_ID) then
|
|
||||||
instance = phase_plasticityInstance(phase)
|
|
||||||
|
|
||||||
endif
|
|
||||||
cycle ! skip to next line
|
|
||||||
endif
|
|
||||||
if (phase > 0_pInt) then; if (phase_plasticity(phase) == PLASTICITY_ISOTROPIC_ID) then ! one of my phases. Do not short-circuit here (.and. between if-statements), it's not safe in Fortran
|
|
||||||
instance = phase_plasticityInstance(phase) ! which instance of my plasticity is present phase
|
|
||||||
allocate(param(instance)%outputID(phase_Noutput(phase))) ! allocate space for IDs of every requested output
|
|
||||||
chunkPos = IO_stringPos(line)
|
|
||||||
tag = IO_lc(IO_stringValue(line,chunkPos,1_pInt)) ! extract key
|
|
||||||
extmsg = trim(tag)//' ('//PLASTICITY_ISOTROPIC_label//')' ! prepare error message identifier
|
|
||||||
|
|
||||||
select case(tag)
|
|
||||||
case ('(output)')
|
|
||||||
outputtag = IO_lc(IO_stringValue(line,chunkPos,2_pInt))
|
|
||||||
select case(outputtag)
|
|
||||||
case ('flowstress')
|
|
||||||
plastic_isotropic_Noutput(instance) = plastic_isotropic_Noutput(instance) + 1_pInt
|
|
||||||
param(instance)%outputID (plastic_isotropic_Noutput(instance)) = flowstress_ID
|
|
||||||
plastic_isotropic_output(plastic_isotropic_Noutput(instance),instance) = outputtag
|
|
||||||
case ('strainrate')
|
|
||||||
plastic_isotropic_Noutput(instance) = plastic_isotropic_Noutput(instance) + 1_pInt
|
|
||||||
param(instance)%outputID (plastic_isotropic_Noutput(instance)) = strainrate_ID
|
|
||||||
plastic_isotropic_output(plastic_isotropic_Noutput(instance),instance) = outputtag
|
|
||||||
|
|
||||||
end select
|
|
||||||
|
|
||||||
case ('/dilatation/')
|
|
||||||
param(instance)%dilatation = .true.
|
|
||||||
|
|
||||||
case ('tau0')
|
|
||||||
param(instance)%tau0 = IO_floatValue(line,chunkPos,2_pInt)
|
|
||||||
if (param(instance)%tau0 < 0.0_pReal) call IO_error(211_pInt,ext_msg=extmsg)
|
|
||||||
|
|
||||||
case ('gdot0')
|
|
||||||
param(instance)%gdot0 = IO_floatValue(line,chunkPos,2_pInt)
|
|
||||||
if (param(instance)%gdot0 <= 0.0_pReal) call IO_error(211_pInt,ext_msg=extmsg)
|
|
||||||
|
|
||||||
case ('n')
|
|
||||||
param(instance)%n = IO_floatValue(line,chunkPos,2_pInt)
|
|
||||||
if (param(instance)%n <= 0.0_pReal) call IO_error(211_pInt,ext_msg=extmsg)
|
|
||||||
|
|
||||||
case ('h0')
|
|
||||||
param(instance)%h0 = IO_floatValue(line,chunkPos,2_pInt)
|
|
||||||
|
|
||||||
case ('h0_slope','slopelnrate')
|
|
||||||
param(instance)%h0_slopeLnRate = IO_floatValue(line,chunkPos,2_pInt)
|
|
||||||
|
|
||||||
case ('tausat')
|
|
||||||
param(instance)%tausat = IO_floatValue(line,chunkPos,2_pInt)
|
|
||||||
if (param(instance)%tausat <= 0.0_pReal) call IO_error(211_pInt,ext_msg=extmsg)
|
|
||||||
|
|
||||||
case ('tausat_sinhfita')
|
|
||||||
param(instance)%tausat_SinhFitA = IO_floatValue(line,chunkPos,2_pInt)
|
|
||||||
|
|
||||||
case ('tausat_sinhfitb')
|
|
||||||
param(instance)%tausat_SinhFitB = IO_floatValue(line,chunkPos,2_pInt)
|
|
||||||
|
|
||||||
case ('tausat_sinhfitc')
|
|
||||||
param(instance)%tausat_SinhFitC = IO_floatValue(line,chunkPos,2_pInt)
|
|
||||||
|
|
||||||
case ('tausat_sinhfitd')
|
|
||||||
param(instance)%tausat_SinhFitD = IO_floatValue(line,chunkPos,2_pInt)
|
|
||||||
|
|
||||||
case ('a', 'w0')
|
|
||||||
param(instance)%a = IO_floatValue(line,chunkPos,2_pInt)
|
|
||||||
if (param(instance)%a <= 0.0_pReal) call IO_error(211_pInt,ext_msg=extmsg)
|
|
||||||
|
|
||||||
case ('taylorfactor')
|
|
||||||
param(instance)%fTaylor = IO_floatValue(line,chunkPos,2_pInt)
|
|
||||||
if (param(instance)%fTaylor <= 0.0_pReal) call IO_error(211_pInt,ext_msg=extmsg)
|
|
||||||
|
|
||||||
case ('atol_flowstress')
|
|
||||||
param(instance)%aTolFlowstress = IO_floatValue(line,chunkPos,2_pInt)
|
|
||||||
if (param(instance)%aTolFlowstress <= 0.0_pReal) call IO_error(211_pInt,ext_msg=extmsg)
|
|
||||||
|
|
||||||
case ('atol_shear')
|
|
||||||
param(instance)%aTolShear = IO_floatValue(line,chunkPos,2_pInt)
|
|
||||||
|
|
||||||
case default
|
|
||||||
|
|
||||||
end select
|
|
||||||
endif; endif
|
|
||||||
enddo parsingFile
|
|
||||||
|
|
||||||
allocate(state(maxNinstance)) ! internal state aliases
|
|
||||||
allocate(state0(maxNinstance))
|
|
||||||
allocate(dotState(maxNinstance))
|
|
||||||
allocate(stateAbsTol(maxNinstance))
|
|
||||||
|
|
||||||
initializeInstances: do phase = 1_pInt, size(phase_plasticity) ! loop over every plasticity
|
|
||||||
myPhase: if (phase_plasticity(phase) == PLASTICITY_isotropic_ID) then ! isolate instances of own constitutive description
|
|
||||||
NipcMyPhase = count(material_phase == phase) ! number of own material points (including point components ipc)
|
|
||||||
instance = phase_plasticityInstance(phase)
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! sanity checks
|
|
||||||
if (param(instance)%aTolShear <= 0.0_pReal) &
|
|
||||||
param(instance)%aTolShear = 1.0e-6_pReal ! default absolute tolerance 1e-6
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! Determine size of postResults array
|
|
||||||
outputsLoop: do o = 1_pInt,plastic_isotropic_Noutput(instance)
|
|
||||||
select case(param(instance)%outputID(o))
|
|
||||||
case(flowstress_ID,strainrate_ID)
|
|
||||||
mySize = 1_pInt
|
|
||||||
case default
|
|
||||||
end select
|
|
||||||
|
|
||||||
outputFound: if (mySize > 0_pInt) then
|
|
||||||
plastic_isotropic_sizePostResult(o,instance) = mySize
|
|
||||||
plastic_isotropic_sizePostResults(instance) = &
|
|
||||||
plastic_isotropic_sizePostResults(instance) + mySize
|
|
||||||
endif outputFound
|
|
||||||
enddo outputsLoop
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! allocate state arrays
|
|
||||||
sizeState = 2_pInt ! flowstress, accumulated_shear
|
|
||||||
sizeDotState = sizeState ! both evolve
|
|
||||||
sizeDeltaState = 0_pInt ! no sudden jumps in state
|
|
||||||
plasticState(phase)%sizeState = sizeState
|
|
||||||
plasticState(phase)%sizeDotState = sizeDotState
|
|
||||||
plasticState(phase)%sizeDeltaState = sizeDeltaState
|
|
||||||
plasticState(phase)%sizePostResults = plastic_isotropic_sizePostResults(instance)
|
|
||||||
plasticState(phase)%nSlip = 1
|
|
||||||
plasticState(phase)%nTwin = 0
|
|
||||||
plasticState(phase)%nTrans= 0
|
|
||||||
allocate(plasticState(phase)%aTolState ( sizeState))
|
|
||||||
|
|
||||||
allocate(plasticState(phase)%state0 ( sizeState,NipcMyPhase),source=0.0_pReal)
|
|
||||||
|
|
||||||
allocate(plasticState(phase)%partionedState0 ( sizeState,NipcMyPhase),source=0.0_pReal)
|
|
||||||
allocate(plasticState(phase)%subState0 ( sizeState,NipcMyPhase),source=0.0_pReal)
|
|
||||||
allocate(plasticState(phase)%state ( sizeState,NipcMyPhase),source=0.0_pReal)
|
|
||||||
allocate(plasticState(phase)%dotState (sizeDotState,NipcMyPhase),source=0.0_pReal)
|
|
||||||
allocate(plasticState(phase)%deltaState (sizeDeltaState,NipcMyPhase),source=0.0_pReal)
|
|
||||||
if (.not. analyticJaco) then
|
|
||||||
allocate(plasticState(phase)%state_backup ( sizeState,NipcMyPhase),source=0.0_pReal)
|
|
||||||
allocate(plasticState(phase)%dotState_backup (sizeDotState,NipcMyPhase),source=0.0_pReal)
|
|
||||||
endif
|
|
||||||
if (any(numerics_integrator == 1_pInt)) then
|
|
||||||
allocate(plasticState(phase)%previousDotState (sizeDotState,NipcMyPhase),source=0.0_pReal)
|
|
||||||
allocate(plasticState(phase)%previousDotState2(sizeDotState,NipcMyPhase),source=0.0_pReal)
|
|
||||||
endif
|
|
||||||
if (any(numerics_integrator == 4_pInt)) &
|
|
||||||
allocate(plasticState(phase)%RK4dotState (sizeDotState,NipcMyPhase),source=0.0_pReal)
|
|
||||||
if (any(numerics_integrator == 5_pInt)) &
|
|
||||||
allocate(plasticState(phase)%RKCK45dotState (6,sizeDotState,NipcMyPhase),source=0.0_pReal)
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! globally required state aliases
|
|
||||||
plasticState(phase)%slipRate => plasticState(phase)%dotState(2:2,1:NipcMyPhase)
|
|
||||||
plasticState(phase)%accumulatedSlip => plasticState(phase)%state (2:2,1:NipcMyPhase)
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! locally defined state aliases
|
|
||||||
state(instance)%flowstress => plasticState(phase)%state (1,1:NipcMyPhase)
|
|
||||||
state0(instance)%flowstress => plasticState(phase)%state0 (1,1:NipcMyPhase)
|
|
||||||
dotState(instance)%flowstress => plasticState(phase)%dotState (1,1:NipcMyPhase)
|
|
||||||
stateAbsTol(instance)%flowstress => plasticState(phase)%aTolState(1)
|
|
||||||
|
|
||||||
state(instance)%accumulatedShear => plasticState(phase)%state (2,1:NipcMyPhase)
|
|
||||||
state0(instance)%accumulatedShear => plasticState(phase)%state0 (2,1:NipcMyPhase)
|
|
||||||
dotState(instance)%accumulatedShear => plasticState(phase)%dotState (2,1:NipcMyPhase)
|
|
||||||
stateAbsTol(instance)%accumulatedShear => plasticState(phase)%aTolState(2)
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! init state
|
|
||||||
state0(instance)%flowstress = param(instance)%tau0
|
|
||||||
state0(instance)%accumulatedShear = 0.0_pReal
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! init absolute state tolerances
|
|
||||||
stateAbsTol(instance)%flowstress = param(instance)%aTolFlowstress
|
|
||||||
stateAbsTol(instance)%accumulatedShear = param(instance)%aTolShear
|
|
||||||
|
|
||||||
endif myPhase
|
|
||||||
enddo initializeInstances
|
|
||||||
|
|
||||||
end subroutine plastic_isotropic_init
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief calculates plastic velocity gradient and its tangent
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine plastic_isotropic_LpAndItsTangent(Lp,dLp_dTstar99,Tstar_v,ipc,ip,el)
|
|
||||||
use debug, only: &
|
|
||||||
debug_level, &
|
|
||||||
debug_constitutive, &
|
|
||||||
debug_levelBasic, &
|
|
||||||
debug_levelExtensive, &
|
|
||||||
debug_levelSelective, &
|
|
||||||
debug_e, &
|
|
||||||
debug_i, &
|
|
||||||
debug_g
|
|
||||||
use math, only: &
|
|
||||||
math_mul6x6, &
|
|
||||||
math_Mandel6to33, &
|
|
||||||
math_Plain3333to99, &
|
|
||||||
math_deviatoric33, &
|
|
||||||
math_mul33xx33, &
|
|
||||||
math_transpose33
|
|
||||||
use material, only: &
|
|
||||||
phaseAt, phasememberAt, &
|
|
||||||
plasticState, &
|
|
||||||
material_phase, &
|
|
||||||
phase_plasticityInstance
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
real(pReal), dimension(3,3), intent(out) :: &
|
|
||||||
Lp !< plastic velocity gradient
|
|
||||||
real(pReal), dimension(9,9), intent(out) :: &
|
|
||||||
dLp_dTstar99 !< derivative of Lp with respect to 2nd Piola Kirchhoff stress
|
|
||||||
|
|
||||||
real(pReal), dimension(6), intent(in) :: &
|
|
||||||
Tstar_v !< 2nd Piola Kirchhoff stress tensor in Mandel notation
|
|
||||||
integer(pInt), intent(in) :: &
|
|
||||||
ipc, & !< component-ID of integration point
|
|
||||||
ip, & !< integration point
|
|
||||||
el !< element
|
|
||||||
|
|
||||||
real(pReal), dimension(3,3) :: &
|
|
||||||
Tstar_dev_33 !< deviatoric part of the 2nd Piola Kirchhoff stress tensor as 2nd order tensor
|
|
||||||
real(pReal), dimension(3,3,3,3) :: &
|
|
||||||
dLp_dTstar_3333 !< derivative of Lp with respect to Tstar as 4th order tensor
|
|
||||||
real(pReal) :: &
|
|
||||||
gamma_dot, & !< strainrate
|
|
||||||
norm_Tstar_dev, & !< euclidean norm of Tstar_dev
|
|
||||||
squarenorm_Tstar_dev !< square of the euclidean norm of Tstar_dev
|
|
||||||
integer(pInt) :: &
|
|
||||||
instance, of, &
|
|
||||||
k, l, m, n
|
|
||||||
|
|
||||||
of = phasememberAt(ipc,ip,el) ! phasememberAt should be tackled by material and be renamed to material_phasemember
|
|
||||||
instance = phase_plasticityInstance(phaseAt(ipc,ip,el)) ! "phaseAt" equivalent to "material_phase" !!
|
|
||||||
|
|
||||||
Tstar_dev_33 = math_deviatoric33(math_Mandel6to33(Tstar_v)) ! deviatoric part of 2nd Piola-Kirchhoff stress
|
|
||||||
squarenorm_Tstar_dev = math_mul33xx33(Tstar_dev_33,Tstar_dev_33)
|
|
||||||
norm_Tstar_dev = sqrt(squarenorm_Tstar_dev)
|
|
||||||
|
|
||||||
if (norm_Tstar_dev <= 0.0_pReal) then ! Tstar == 0 --> both Lp and dLp_dTstar are zero
|
|
||||||
Lp = 0.0_pReal
|
|
||||||
dLp_dTstar99 = 0.0_pReal
|
|
||||||
else
|
|
||||||
gamma_dot = param(instance)%gdot0 &
|
|
||||||
* ( sqrt(1.5_pReal) * norm_Tstar_dev / param(instance)%fTaylor / state(instance)%flowstress(of) ) &
|
|
||||||
**param(instance)%n
|
|
||||||
|
|
||||||
Lp = Tstar_dev_33/norm_Tstar_dev * gamma_dot/param(instance)%fTaylor
|
|
||||||
|
|
||||||
if (iand(debug_level(debug_constitutive), debug_levelExtensive) /= 0_pInt &
|
|
||||||
.and. ((el == debug_e .and. ip == debug_i .and. ipc == debug_g) &
|
|
||||||
.or. .not. iand(debug_level(debug_constitutive),debug_levelSelective) /= 0_pInt)) then
|
|
||||||
write(6,'(a,i8,1x,i2,1x,i3)') '<< CONST isotropic >> at el ip g ',el,ip,ipc
|
|
||||||
write(6,'(/,a,/,3(12x,3(f12.4,1x)/))') '<< CONST isotropic >> Tstar (dev) / MPa', &
|
|
||||||
math_transpose33(Tstar_dev_33(1:3,1:3))*1.0e-6_pReal
|
|
||||||
write(6,'(/,a,/,f12.5)') '<< CONST isotropic >> norm Tstar / MPa', norm_Tstar_dev*1.0e-6_pReal
|
|
||||||
write(6,'(/,a,/,f12.5)') '<< CONST isotropic >> gdot', gamma_dot
|
|
||||||
end if
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! Calculation of the tangent of Lp
|
|
||||||
forall (k=1_pInt:3_pInt,l=1_pInt:3_pInt,m=1_pInt:3_pInt,n=1_pInt:3_pInt) &
|
|
||||||
dLp_dTstar_3333(k,l,m,n) = (param(instance)%n-1.0_pReal) * &
|
|
||||||
Tstar_dev_33(k,l)*Tstar_dev_33(m,n) / squarenorm_Tstar_dev
|
|
||||||
forall (k=1_pInt:3_pInt,l=1_pInt:3_pInt) &
|
|
||||||
dLp_dTstar_3333(k,l,k,l) = dLp_dTstar_3333(k,l,k,l) + 1.0_pReal
|
|
||||||
forall (k=1_pInt:3_pInt,m=1_pInt:3_pInt) &
|
|
||||||
dLp_dTstar_3333(k,k,m,m) = dLp_dTstar_3333(k,k,m,m) - 1.0_pReal/3.0_pReal
|
|
||||||
dLp_dTstar99 = math_Plain3333to99(gamma_dot / param(instance)%fTaylor * &
|
|
||||||
dLp_dTstar_3333 / norm_Tstar_dev)
|
|
||||||
end if
|
|
||||||
end subroutine plastic_isotropic_LpAndItsTangent
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief calculates plastic velocity gradient and its tangent
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine plastic_isotropic_LiAndItsTangent(Li,dLi_dTstar_3333,Tstar_v,ipc,ip,el)
|
|
||||||
use math, only: &
|
|
||||||
math_mul6x6, &
|
|
||||||
math_Mandel6to33, &
|
|
||||||
math_Plain3333to99, &
|
|
||||||
math_spherical33, &
|
|
||||||
math_mul33xx33
|
|
||||||
use material, only: &
|
|
||||||
phaseAt, phasememberAt, &
|
|
||||||
plasticState, &
|
|
||||||
material_phase, &
|
|
||||||
phase_plasticityInstance
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
real(pReal), dimension(3,3), intent(out) :: &
|
|
||||||
Li !< plastic velocity gradient
|
|
||||||
|
|
||||||
real(pReal), dimension(6), intent(in) :: &
|
|
||||||
Tstar_v !< 2nd Piola Kirchhoff stress tensor in Mandel notation
|
|
||||||
integer(pInt), intent(in) :: &
|
|
||||||
ipc, & !< component-ID of integration point
|
|
||||||
ip, & !< integration point
|
|
||||||
el !< element
|
|
||||||
|
|
||||||
real(pReal), dimension(3,3) :: &
|
|
||||||
Tstar_sph_33 !< sphiatoric part of the 2nd Piola Kirchhoff stress tensor as 2nd order tensor
|
|
||||||
real(pReal), dimension(3,3,3,3), intent(out) :: &
|
|
||||||
dLi_dTstar_3333 !< derivative of Li with respect to Tstar as 4th order tensor
|
|
||||||
real(pReal) :: &
|
|
||||||
gamma_dot, & !< strainrate
|
|
||||||
norm_Tstar_sph, & !< euclidean norm of Tstar_sph
|
|
||||||
squarenorm_Tstar_sph !< square of the euclidean norm of Tstar_sph
|
|
||||||
integer(pInt) :: &
|
|
||||||
instance, of, &
|
|
||||||
k, l, m, n
|
|
||||||
|
|
||||||
of = phasememberAt(ipc,ip,el) ! phasememberAt should be tackled by material and be renamed to material_phasemember
|
|
||||||
instance = phase_plasticityInstance(phaseAt(ipc,ip,el)) ! "phaseAt" equivalent to "material_phase" !!
|
|
||||||
|
|
||||||
Tstar_sph_33 = math_spherical33(math_Mandel6to33(Tstar_v)) ! spherical part of 2nd Piola-Kirchhoff stress
|
|
||||||
squarenorm_Tstar_sph = math_mul33xx33(Tstar_sph_33,Tstar_sph_33)
|
|
||||||
norm_Tstar_sph = sqrt(squarenorm_Tstar_sph)
|
|
||||||
|
|
||||||
if (param(instance)%dilatation) then
|
|
||||||
if (norm_Tstar_sph <= 0.0_pReal) then ! Tstar == 0 --> both Li and dLi_dTstar are zero
|
|
||||||
Li = 0.0_pReal
|
|
||||||
dLi_dTstar_3333 = 0.0_pReal
|
|
||||||
else
|
|
||||||
gamma_dot = param(instance)%gdot0 &
|
|
||||||
* (sqrt(1.5_pReal) * norm_Tstar_sph / param(instance)%fTaylor / state(instance)%flowstress(of) ) &
|
|
||||||
**param(instance)%n
|
|
||||||
|
|
||||||
Li = Tstar_sph_33/norm_Tstar_sph * gamma_dot/param(instance)%fTaylor
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! Calculation of the tangent of Li
|
|
||||||
forall (k=1_pInt:3_pInt,l=1_pInt:3_pInt,m=1_pInt:3_pInt,n=1_pInt:3_pInt) &
|
|
||||||
dLi_dTstar_3333(k,l,m,n) = (param(instance)%n-1.0_pReal) * &
|
|
||||||
Tstar_sph_33(k,l)*Tstar_sph_33(m,n) / squarenorm_Tstar_sph
|
|
||||||
forall (k=1_pInt:3_pInt,l=1_pInt:3_pInt) &
|
|
||||||
dLi_dTstar_3333(k,l,k,l) = dLi_dTstar_3333(k,l,k,l) + 1.0_pReal
|
|
||||||
|
|
||||||
dLi_dTstar_3333 = gamma_dot / param(instance)%fTaylor * &
|
|
||||||
dLi_dTstar_3333 / norm_Tstar_sph
|
|
||||||
endif
|
|
||||||
endif
|
|
||||||
|
|
||||||
end subroutine plastic_isotropic_LiAndItsTangent
|
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief calculates the rate of change of microstructure
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine plastic_isotropic_dotState(Tstar_v,ipc,ip,el)
|
|
||||||
use math, only: &
|
|
||||||
math_mul6x6
|
|
||||||
use material, only: &
|
|
||||||
phaseAt, phasememberAt, &
|
|
||||||
plasticState, &
|
|
||||||
material_phase, &
|
|
||||||
phase_plasticityInstance
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
real(pReal), dimension(6), intent(in):: &
|
|
||||||
Tstar_v !< 2nd Piola Kirchhoff stress tensor in Mandel notation
|
|
||||||
integer(pInt), intent(in) :: &
|
|
||||||
ipc, & !< component-ID of integration point
|
|
||||||
ip, & !< integration point
|
|
||||||
el !< element
|
|
||||||
real(pReal), dimension(6) :: &
|
|
||||||
Tstar_dev_v !< deviatoric 2nd Piola Kirchhoff stress tensor in Mandel notation
|
|
||||||
real(pReal) :: &
|
|
||||||
gamma_dot, & !< strainrate
|
|
||||||
hardening, & !< hardening coefficient
|
|
||||||
saturation, & !< saturation flowstress
|
|
||||||
norm_Tstar_v !< euclidean norm of Tstar_dev
|
|
||||||
integer(pInt) :: &
|
|
||||||
instance, & !< instance of my instance (unique number of my constitutive model)
|
|
||||||
of !< shortcut notation for offset position in state array
|
|
||||||
|
|
||||||
of = phasememberAt(ipc,ip,el) ! phasememberAt should be tackled by material and be renamed to material_phasemember
|
|
||||||
instance = phase_plasticityInstance(phaseAt(ipc,ip,el)) ! "phaseAt" equivalent to "material_phase" !!
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! norm of (deviatoric) 2nd Piola-Kirchhoff stress
|
|
||||||
if (param(instance)%dilatation) then
|
|
||||||
norm_Tstar_v = sqrt(math_mul6x6(Tstar_v,Tstar_v))
|
|
||||||
else
|
|
||||||
Tstar_dev_v(1:3) = Tstar_v(1:3) - sum(Tstar_v(1:3))/3.0_pReal
|
|
||||||
Tstar_dev_v(4:6) = Tstar_v(4:6)
|
|
||||||
norm_Tstar_v = sqrt(math_mul6x6(Tstar_dev_v,Tstar_dev_v))
|
|
||||||
end if
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! strain rate
|
|
||||||
gamma_dot = param(instance)%gdot0 * ( sqrt(1.5_pReal) * norm_Tstar_v &
|
|
||||||
/ &!-----------------------------------------------------------------------------------
|
|
||||||
(param(instance)%fTaylor*state(instance)%flowstress(of) ))**param(instance)%n
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! hardening coefficient
|
|
||||||
if (abs(gamma_dot) > 1e-12_pReal) then
|
|
||||||
if (abs(param(instance)%tausat_SinhFitA) <= tiny(0.0_pReal)) then
|
|
||||||
saturation = param(instance)%tausat
|
|
||||||
else
|
|
||||||
saturation = ( param(instance)%tausat &
|
|
||||||
+ ( log( ( gamma_dot / param(instance)%tausat_SinhFitA&
|
|
||||||
)**(1.0_pReal / param(instance)%tausat_SinhFitD)&
|
|
||||||
+ sqrt( ( gamma_dot / param(instance)%tausat_SinhFitA &
|
|
||||||
)**(2.0_pReal / param(instance)%tausat_SinhFitD) &
|
|
||||||
+ 1.0_pReal ) &
|
|
||||||
) & ! asinh(K) = ln(K + sqrt(K^2 +1))
|
|
||||||
)**(1.0_pReal / param(instance)%tausat_SinhFitC) &
|
|
||||||
/ ( param(instance)%tausat_SinhFitB &
|
|
||||||
* (gamma_dot / param(instance)%gdot0)**(1.0_pReal / param(instance)%n) &
|
|
||||||
) &
|
|
||||||
)
|
|
||||||
endif
|
|
||||||
hardening = ( param(instance)%h0 + param(instance)%h0_slopeLnRate * log(gamma_dot) ) &
|
|
||||||
* abs( 1.0_pReal - state(instance)%flowstress(of)/saturation )**param(instance)%a &
|
|
||||||
* sign(1.0_pReal, 1.0_pReal - state(instance)%flowstress(of)/saturation)
|
|
||||||
else
|
|
||||||
hardening = 0.0_pReal
|
|
||||||
endif
|
|
||||||
|
|
||||||
dotState(instance)%flowstress (of) = hardening * gamma_dot
|
|
||||||
dotState(instance)%accumulatedShear(of) = gamma_dot
|
|
||||||
|
|
||||||
end subroutine plastic_isotropic_dotState
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief return array of constitutive results
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
function plastic_isotropic_postResults(Tstar_v,ipc,ip,el)
|
|
||||||
use math, only: &
|
|
||||||
math_mul6x6
|
|
||||||
use material, only: &
|
|
||||||
material_phase, &
|
|
||||||
plasticState, &
|
|
||||||
phaseAt, phasememberAt, &
|
|
||||||
phase_plasticityInstance
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
real(pReal), dimension(6), intent(in) :: &
|
|
||||||
Tstar_v !< 2nd Piola Kirchhoff stress tensor in Mandel notation
|
|
||||||
integer(pInt), intent(in) :: &
|
|
||||||
ipc, & !< component-ID of integration point
|
|
||||||
ip, & !< integration point
|
|
||||||
el !< element
|
|
||||||
real(pReal), dimension(plastic_isotropic_sizePostResults(phase_plasticityInstance(material_phase(ipc,ip,el)))) :: &
|
|
||||||
plastic_isotropic_postResults
|
|
||||||
|
|
||||||
real(pReal), dimension(6) :: &
|
|
||||||
Tstar_dev_v !< deviatoric 2nd Piola Kirchhoff stress tensor in Mandel notation
|
|
||||||
real(pReal) :: &
|
|
||||||
norm_Tstar_v ! euclidean norm of Tstar_dev
|
|
||||||
integer(pInt) :: &
|
|
||||||
instance, & !< instance of my instance (unique number of my constitutive model)
|
|
||||||
of, & !< shortcut notation for offset position in state array
|
|
||||||
c, &
|
|
||||||
o
|
|
||||||
|
|
||||||
of = phasememberAt(ipc,ip,el) ! phasememberAt should be tackled by material and be renamed to material_phasemember
|
|
||||||
instance = phase_plasticityInstance(phaseAt(ipc,ip,el)) ! "phaseAt" equivalent to "material_phase" !!
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! norm of (deviatoric) 2nd Piola-Kirchhoff stress
|
|
||||||
if (param(instance)%dilatation) then
|
|
||||||
norm_Tstar_v = sqrt(math_mul6x6(Tstar_v,Tstar_v))
|
|
||||||
else
|
|
||||||
Tstar_dev_v(1:3) = Tstar_v(1:3) - sum(Tstar_v(1:3))/3.0_pReal
|
|
||||||
Tstar_dev_v(4:6) = Tstar_v(4:6)
|
|
||||||
norm_Tstar_v = sqrt(math_mul6x6(Tstar_dev_v,Tstar_dev_v))
|
|
||||||
end if
|
|
||||||
|
|
||||||
c = 0_pInt
|
|
||||||
plastic_isotropic_postResults = 0.0_pReal
|
|
||||||
|
|
||||||
outputsLoop: do o = 1_pInt,plastic_isotropic_Noutput(instance)
|
|
||||||
select case(param(instance)%outputID(o))
|
|
||||||
case (flowstress_ID)
|
|
||||||
plastic_isotropic_postResults(c+1_pInt) = state(instance)%flowstress(of)
|
|
||||||
c = c + 1_pInt
|
|
||||||
case (strainrate_ID)
|
|
||||||
plastic_isotropic_postResults(c+1_pInt) = &
|
|
||||||
param(instance)%gdot0 * ( sqrt(1.5_pReal) * norm_Tstar_v &
|
|
||||||
/ &!----------------------------------------------------------------------------------
|
|
||||||
(param(instance)%fTaylor * state(instance)%flowstress(of)) ) ** param(instance)%n
|
|
||||||
c = c + 1_pInt
|
|
||||||
end select
|
|
||||||
enddo outputsLoop
|
|
||||||
|
|
||||||
end function plastic_isotropic_postResults
|
|
||||||
|
|
||||||
|
|
||||||
end module plastic_isotropic
|
|
|
@ -1,579 +0,0 @@
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! $Id$
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @author Franz Roters, Max-Planck-Institut für Eisenforschung GmbH
|
|
||||||
!> @author Philip Eisenlohr, Max-Planck-Institut für Eisenforschung GmbH
|
|
||||||
!> @brief material subroutine for isotropic (J2) plasticity
|
|
||||||
!> @details Isotropic (J2) Plasticity which resembles the phenopowerlaw plasticity without
|
|
||||||
!! resolving the stress on the slip systems. Will give the response of phenopowerlaw for an
|
|
||||||
!! untextured polycrystal
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
module plastic_j2
|
|
||||||
#ifdef HDF
|
|
||||||
use hdf5, only: &
|
|
||||||
HID_T
|
|
||||||
#endif
|
|
||||||
|
|
||||||
use prec, only: &
|
|
||||||
pReal,&
|
|
||||||
pInt
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
private
|
|
||||||
integer(pInt), dimension(:), allocatable, public, protected :: &
|
|
||||||
plastic_j2_sizePostResults !< cumulative size of post results
|
|
||||||
|
|
||||||
integer(pInt), dimension(:,:), allocatable, target, public :: &
|
|
||||||
plastic_j2_sizePostResult !< size of each post result output
|
|
||||||
|
|
||||||
character(len=64), dimension(:,:), allocatable, target, public :: &
|
|
||||||
plastic_j2_output !< name of each post result output
|
|
||||||
|
|
||||||
integer(pInt), dimension(:), allocatable, target, public :: &
|
|
||||||
plastic_j2_Noutput !< number of outputs per instance
|
|
||||||
real(pReal), dimension(:), allocatable, private :: &
|
|
||||||
plastic_j2_fTaylor, & !< Taylor factor
|
|
||||||
plastic_j2_tau0, & !< initial plastic stress
|
|
||||||
plastic_j2_gdot0, & !< reference velocity
|
|
||||||
plastic_j2_n, & !< Visco-plastic parameter
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! h0 as function of h0 = A + B log (gammadot)
|
|
||||||
plastic_j2_h0, &
|
|
||||||
plastic_j2_h0_slopeLnRate, &
|
|
||||||
plastic_j2_tausat, & !< final plastic stress
|
|
||||||
plastic_j2_a, &
|
|
||||||
plastic_j2_aTolResistance, &
|
|
||||||
plastic_j2_aTolShear, &
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! tausat += (asinh((gammadot / SinhFitA)**(1 / SinhFitD)))**(1 / SinhFitC) / (SinhFitB * (gammadot / gammadot0)**(1/n))
|
|
||||||
plastic_j2_tausat_SinhFitA, & !< fitting parameter for normalized strain rate vs. stress function
|
|
||||||
plastic_j2_tausat_SinhFitB, & !< fitting parameter for normalized strain rate vs. stress function
|
|
||||||
plastic_j2_tausat_SinhFitC, & !< fitting parameter for normalized strain rate vs. stress function
|
|
||||||
plastic_j2_tausat_SinhFitD !< fitting parameter for normalized strain rate vs. stress function
|
|
||||||
|
|
||||||
enum, bind(c)
|
|
||||||
enumerator :: undefined_ID, &
|
|
||||||
flowstress_ID, &
|
|
||||||
strainrate_ID
|
|
||||||
end enum
|
|
||||||
integer(kind(undefined_ID)), dimension(:,:), allocatable, private :: &
|
|
||||||
plastic_j2_outputID !< ID of each post result output
|
|
||||||
|
|
||||||
|
|
||||||
#ifdef HDF
|
|
||||||
type plastic_j2_tOutput
|
|
||||||
real(pReal), dimension(:), allocatable, private :: &
|
|
||||||
flowstress, &
|
|
||||||
strainrate
|
|
||||||
logical :: flowstressActive = .false., strainrateActive = .false. ! if we can write the output block wise, this is not needed anymore because we can do an if(allocated(xxx))
|
|
||||||
end type plastic_j2_tOutput
|
|
||||||
type(plastic_j2_tOutput), allocatable, dimension(:) :: plastic_j2_Output2
|
|
||||||
integer(HID_T), allocatable, dimension(:) :: outID
|
|
||||||
#endif
|
|
||||||
|
|
||||||
|
|
||||||
public :: &
|
|
||||||
plastic_j2_init, &
|
|
||||||
plastic_j2_LpAndItsTangent, &
|
|
||||||
plastic_j2_dotState, &
|
|
||||||
plastic_j2_postResults
|
|
||||||
|
|
||||||
contains
|
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief module initialization
|
|
||||||
!> @details reads in material parameters, allocates arrays, and does sanity checks
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine plastic_j2_init(fileUnit)
|
|
||||||
use, intrinsic :: iso_fortran_env ! to get compiler_version and compiler_options (at least for gfortran 4.6 at the moment)
|
|
||||||
#ifdef HDF
|
|
||||||
use hdf5
|
|
||||||
#endif
|
|
||||||
use debug, only: &
|
|
||||||
debug_level, &
|
|
||||||
debug_constitutive, &
|
|
||||||
debug_levelBasic
|
|
||||||
use numerics, only: &
|
|
||||||
analyticJaco, &
|
|
||||||
worldrank, &
|
|
||||||
numerics_integrator
|
|
||||||
use math, only: &
|
|
||||||
math_Mandel3333to66, &
|
|
||||||
math_Voigt66to3333
|
|
||||||
use IO, only: &
|
|
||||||
IO_read, &
|
|
||||||
IO_lc, &
|
|
||||||
IO_getTag, &
|
|
||||||
IO_isBlank, &
|
|
||||||
IO_stringPos, &
|
|
||||||
IO_stringValue, &
|
|
||||||
IO_floatValue, &
|
|
||||||
IO_error, &
|
|
||||||
IO_timeStamp, &
|
|
||||||
#ifdef HDF
|
|
||||||
tempResults, &
|
|
||||||
HDF5_addGroup, &
|
|
||||||
HDF5_addScalarDataset,&
|
|
||||||
#endif
|
|
||||||
IO_EOF
|
|
||||||
use material, only: &
|
|
||||||
phase_plasticity, &
|
|
||||||
phase_plasticityInstance, &
|
|
||||||
phase_Noutput, &
|
|
||||||
PLASTICITY_J2_label, &
|
|
||||||
PLASTICITY_J2_ID, &
|
|
||||||
material_phase, &
|
|
||||||
plasticState, &
|
|
||||||
MATERIAL_partPhase
|
|
||||||
|
|
||||||
use lattice
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
integer(pInt), intent(in) :: fileUnit
|
|
||||||
|
|
||||||
|
|
||||||
integer(pInt), allocatable, dimension(:) :: chunkPos
|
|
||||||
integer(pInt) :: &
|
|
||||||
o, &
|
|
||||||
phase, &
|
|
||||||
maxNinstance, &
|
|
||||||
instance, &
|
|
||||||
mySize, &
|
|
||||||
sizeDotState, &
|
|
||||||
sizeState, &
|
|
||||||
sizeDeltaState
|
|
||||||
character(len=65536) :: &
|
|
||||||
tag = '', &
|
|
||||||
line = ''
|
|
||||||
integer(pInt) :: NofMyPhase
|
|
||||||
|
|
||||||
#ifdef HDF
|
|
||||||
character(len=5) :: &
|
|
||||||
str1
|
|
||||||
integer(HID_T) :: ID,ID2,ID4
|
|
||||||
#endif
|
|
||||||
|
|
||||||
mainProcess: if (worldrank == 0) then
|
|
||||||
write(6,'(/,a)') ' <<<+- constitutive_'//PLASTICITY_J2_label//' init -+>>>'
|
|
||||||
write(6,'(a15,a)') ' Current time: ',IO_timeStamp()
|
|
||||||
#include "compilation_info.f90"
|
|
||||||
endif mainProcess
|
|
||||||
|
|
||||||
maxNinstance = int(count(phase_plasticity == PLASTICITY_J2_ID),pInt)
|
|
||||||
if (maxNinstance == 0_pInt) return
|
|
||||||
|
|
||||||
if (iand(debug_level(debug_constitutive),debug_levelBasic) /= 0_pInt) &
|
|
||||||
write(6,'(a16,1x,i5,/)') '# instances:',maxNinstance
|
|
||||||
|
|
||||||
#ifdef HDF
|
|
||||||
allocate(plastic_j2_Output2(maxNinstance))
|
|
||||||
allocate(outID(maxNinstance))
|
|
||||||
#endif
|
|
||||||
|
|
||||||
allocate(plastic_j2_sizePostResults(maxNinstance), source=0_pInt)
|
|
||||||
allocate(plastic_j2_sizePostResult(maxval(phase_Noutput), maxNinstance),source=0_pInt)
|
|
||||||
allocate(plastic_j2_output(maxval(phase_Noutput), maxNinstance))
|
|
||||||
plastic_j2_output = ''
|
|
||||||
allocate(plastic_j2_outputID(maxval(phase_Noutput),maxNinstance), source=undefined_ID)
|
|
||||||
allocate(plastic_j2_Noutput(maxNinstance), source=0_pInt)
|
|
||||||
allocate(plastic_j2_fTaylor(maxNinstance), source=0.0_pReal)
|
|
||||||
allocate(plastic_j2_tau0(maxNinstance), source=0.0_pReal)
|
|
||||||
allocate(plastic_j2_gdot0(maxNinstance), source=0.0_pReal)
|
|
||||||
allocate(plastic_j2_n(maxNinstance), source=0.0_pReal)
|
|
||||||
allocate(plastic_j2_h0(maxNinstance), source=0.0_pReal)
|
|
||||||
allocate(plastic_j2_h0_slopeLnRate(maxNinstance), source=0.0_pReal)
|
|
||||||
allocate(plastic_j2_tausat(maxNinstance), source=0.0_pReal)
|
|
||||||
allocate(plastic_j2_a(maxNinstance), source=0.0_pReal)
|
|
||||||
allocate(plastic_j2_aTolResistance(maxNinstance), source=0.0_pReal)
|
|
||||||
allocate(plastic_j2_aTolShear (maxNinstance), source=0.0_pReal)
|
|
||||||
allocate(plastic_j2_tausat_SinhFitA(maxNinstance), source=0.0_pReal)
|
|
||||||
allocate(plastic_j2_tausat_SinhFitB(maxNinstance), source=0.0_pReal)
|
|
||||||
allocate(plastic_j2_tausat_SinhFitC(maxNinstance), source=0.0_pReal)
|
|
||||||
allocate(plastic_j2_tausat_SinhFitD(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 section
|
|
||||||
phase = phase + 1_pInt ! advance section counter
|
|
||||||
if (phase_plasticity(phase) == PLASTICITY_J2_ID) then
|
|
||||||
instance = phase_plasticityInstance(phase)
|
|
||||||
#ifdef HDF
|
|
||||||
outID(instance)=HDF5_addGroup(str1,tempResults)
|
|
||||||
#endif
|
|
||||||
endif
|
|
||||||
cycle ! skip to next line
|
|
||||||
endif
|
|
||||||
if (phase > 0_pInt ) then; if (phase_plasticity(phase) == PLASTICITY_J2_ID) then ! one of my phases. Do not short-circuit here (.and. between if-statements), it's not safe in Fortran
|
|
||||||
instance = phase_plasticityInstance(phase) ! which instance of my plasticity is present phase
|
|
||||||
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 ('flowstress')
|
|
||||||
plastic_j2_Noutput(instance) = plastic_j2_Noutput(instance) + 1_pInt
|
|
||||||
plastic_j2_outputID(plastic_j2_Noutput(instance),instance) = flowstress_ID
|
|
||||||
plastic_j2_output(plastic_j2_Noutput(instance),instance) = &
|
|
||||||
IO_lc(IO_stringValue(line,chunkPos,2_pInt))
|
|
||||||
#ifdef HDF
|
|
||||||
call HDF5_addScalarDataset(outID(instance),myConstituents,'flowstress','MPa')
|
|
||||||
allocate(plastic_j2_Output2(instance)%flowstress(myConstituents))
|
|
||||||
plastic_j2_Output2(instance)%flowstressActive = .true.
|
|
||||||
#endif
|
|
||||||
case ('strainrate')
|
|
||||||
plastic_j2_Noutput(instance) = plastic_j2_Noutput(instance) + 1_pInt
|
|
||||||
plastic_j2_outputID(plastic_j2_Noutput(instance),instance) = strainrate_ID
|
|
||||||
plastic_j2_output(plastic_j2_Noutput(instance),instance) = &
|
|
||||||
IO_lc(IO_stringValue(line,chunkPos,2_pInt))
|
|
||||||
#ifdef HDF
|
|
||||||
call HDF5_addScalarDataset(outID(instance),myConstituents,'strainrate','1/s')
|
|
||||||
allocate(plastic_j2_Output2(instance)%strainrate(myConstituents))
|
|
||||||
plastic_j2_Output2(instance)%strainrateActive = .true.
|
|
||||||
#endif
|
|
||||||
case default
|
|
||||||
|
|
||||||
end select
|
|
||||||
case ('tau0')
|
|
||||||
plastic_j2_tau0(instance) = IO_floatValue(line,chunkPos,2_pInt)
|
|
||||||
if (plastic_j2_tau0(instance) < 0.0_pReal) &
|
|
||||||
call IO_error(211_pInt,ext_msg=trim(tag)//' ('//PLASTICITY_J2_label//')')
|
|
||||||
case ('gdot0')
|
|
||||||
plastic_j2_gdot0(instance) = IO_floatValue(line,chunkPos,2_pInt)
|
|
||||||
if (plastic_j2_gdot0(instance) <= 0.0_pReal) &
|
|
||||||
call IO_error(211_pInt,ext_msg=trim(tag)//' ('//PLASTICITY_J2_label//')')
|
|
||||||
case ('n')
|
|
||||||
plastic_j2_n(instance) = IO_floatValue(line,chunkPos,2_pInt)
|
|
||||||
if (plastic_j2_n(instance) <= 0.0_pReal) &
|
|
||||||
call IO_error(211_pInt,ext_msg=trim(tag)//' ('//PLASTICITY_J2_label//')')
|
|
||||||
case ('h0')
|
|
||||||
plastic_j2_h0(instance) = IO_floatValue(line,chunkPos,2_pInt)
|
|
||||||
case ('h0_slope','slopelnrate')
|
|
||||||
plastic_j2_h0_slopeLnRate(instance) = IO_floatValue(line,chunkPos,2_pInt)
|
|
||||||
case ('tausat')
|
|
||||||
plastic_j2_tausat(instance) = IO_floatValue(line,chunkPos,2_pInt)
|
|
||||||
if (plastic_j2_tausat(instance) <= 0.0_pReal) &
|
|
||||||
call IO_error(211_pInt,ext_msg=trim(tag)//' ('//PLASTICITY_J2_label//')')
|
|
||||||
case ('tausat_sinhfita')
|
|
||||||
plastic_j2_tausat_SinhFitA(instance) = IO_floatValue(line,chunkPos,2_pInt)
|
|
||||||
case ('tausat_sinhfitb')
|
|
||||||
plastic_j2_tausat_SinhFitB(instance) = IO_floatValue(line,chunkPos,2_pInt)
|
|
||||||
case ('tausat_sinhfitc')
|
|
||||||
plastic_j2_tausat_SinhFitC(instance) = IO_floatValue(line,chunkPos,2_pInt)
|
|
||||||
case ('tausat_sinhfitd')
|
|
||||||
plastic_j2_tausat_SinhFitD(instance) = IO_floatValue(line,chunkPos,2_pInt)
|
|
||||||
case ('a', 'w0')
|
|
||||||
plastic_j2_a(instance) = IO_floatValue(line,chunkPos,2_pInt)
|
|
||||||
if (plastic_j2_a(instance) <= 0.0_pReal) &
|
|
||||||
call IO_error(211_pInt,ext_msg=trim(tag)//' ('//PLASTICITY_J2_label//')')
|
|
||||||
case ('taylorfactor')
|
|
||||||
plastic_j2_fTaylor(instance) = IO_floatValue(line,chunkPos,2_pInt)
|
|
||||||
if (plastic_j2_fTaylor(instance) <= 0.0_pReal) &
|
|
||||||
call IO_error(211_pInt,ext_msg=trim(tag)//' ('//PLASTICITY_J2_label//')')
|
|
||||||
case ('atol_resistance')
|
|
||||||
plastic_j2_aTolResistance(instance) = IO_floatValue(line,chunkPos,2_pInt)
|
|
||||||
if (plastic_j2_aTolResistance(instance) <= 0.0_pReal) &
|
|
||||||
call IO_error(211_pInt,ext_msg=trim(tag)//' ('//PLASTICITY_J2_label//')')
|
|
||||||
case ('atol_shear')
|
|
||||||
plastic_j2_aTolShear(instance) = IO_floatValue(line,chunkPos,2_pInt)
|
|
||||||
|
|
||||||
case default
|
|
||||||
|
|
||||||
end select
|
|
||||||
endif; endif
|
|
||||||
enddo parsingFile
|
|
||||||
|
|
||||||
initializeInstances: do phase = 1_pInt, size(phase_plasticity)
|
|
||||||
myPhase: if (phase_plasticity(phase) == PLASTICITY_j2_ID) then
|
|
||||||
NofMyPhase=count(material_phase==phase)
|
|
||||||
instance = phase_plasticityInstance(phase)
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! sanity checks
|
|
||||||
if (plastic_j2_aTolShear(instance) <= 0.0_pReal) &
|
|
||||||
plastic_j2_aTolShear(instance) = 1.0e-6_pReal ! default absolute tolerance 1e-6
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! Determine size of postResults array
|
|
||||||
outputsLoop: do o = 1_pInt,plastic_j2_Noutput(instance)
|
|
||||||
select case(plastic_j2_outputID(o,instance))
|
|
||||||
case(flowstress_ID,strainrate_ID)
|
|
||||||
mySize = 1_pInt
|
|
||||||
case default
|
|
||||||
end select
|
|
||||||
|
|
||||||
outputFound: if (mySize > 0_pInt) then
|
|
||||||
plastic_j2_sizePostResult(o,instance) = mySize
|
|
||||||
plastic_j2_sizePostResults(instance) = &
|
|
||||||
plastic_j2_sizePostResults(instance) + mySize
|
|
||||||
endif outputFound
|
|
||||||
enddo outputsLoop
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! allocate state arrays
|
|
||||||
sizeState = 2_pInt
|
|
||||||
sizeDotState = sizeState
|
|
||||||
sizeDeltaState = 0_pInt
|
|
||||||
plasticState(phase)%sizeState = sizeState
|
|
||||||
plasticState(phase)%sizeDotState = sizeDotState
|
|
||||||
plasticState(phase)%sizeDeltaState = sizeDeltaState
|
|
||||||
plasticState(phase)%sizePostResults = plastic_j2_sizePostResults(instance)
|
|
||||||
plasticState(phase)%nSlip = 1
|
|
||||||
plasticState(phase)%nTwin = 0
|
|
||||||
plasticState(phase)%nTrans= 0
|
|
||||||
allocate(plasticState(phase)%aTolState ( sizeState))
|
|
||||||
plasticState(phase)%aTolState(1) = plastic_j2_aTolResistance(instance)
|
|
||||||
plasticState(phase)%aTolState(2) = plastic_j2_aTolShear(instance)
|
|
||||||
allocate(plasticState(phase)%state0 ( sizeState,NofMyPhase))
|
|
||||||
plasticState(phase)%state0(1,1:NofMyPhase) = plastic_j2_tau0(instance)
|
|
||||||
plasticState(phase)%state0(2,1:NofMyPhase) = 0.0_pReal
|
|
||||||
allocate(plasticState(phase)%partionedState0 ( sizeState,NofMyPhase),source=0.0_pReal)
|
|
||||||
allocate(plasticState(phase)%subState0 ( sizeState,NofMyPhase),source=0.0_pReal)
|
|
||||||
allocate(plasticState(phase)%state ( sizeState,NofMyPhase),source=0.0_pReal)
|
|
||||||
allocate(plasticState(phase)%dotState (sizeDotState,NofMyPhase),source=0.0_pReal)
|
|
||||||
allocate(plasticState(phase)%deltaState (sizeDeltaState,NofMyPhase),source=0.0_pReal)
|
|
||||||
if (.not. analyticJaco) then
|
|
||||||
allocate(plasticState(phase)%state_backup ( sizeState,NofMyPhase),source=0.0_pReal)
|
|
||||||
allocate(plasticState(phase)%dotState_backup (sizeDotState,NofMyPhase),source=0.0_pReal)
|
|
||||||
endif
|
|
||||||
if (any(numerics_integrator == 1_pInt)) then
|
|
||||||
allocate(plasticState(phase)%previousDotState (sizeDotState,NofMyPhase),source=0.0_pReal)
|
|
||||||
allocate(plasticState(phase)%previousDotState2(sizeDotState,NofMyPhase),source=0.0_pReal)
|
|
||||||
endif
|
|
||||||
if (any(numerics_integrator == 4_pInt)) &
|
|
||||||
allocate(plasticState(phase)%RK4dotState (sizeDotState,NofMyPhase),source=0.0_pReal)
|
|
||||||
if (any(numerics_integrator == 5_pInt)) &
|
|
||||||
allocate(plasticState(phase)%RKCK45dotState (6,sizeDotState,NofMyPhase),source=0.0_pReal)
|
|
||||||
plasticState(phase)%slipRate => plasticState(phase)%dotState(2:2,1:NofMyPhase)
|
|
||||||
plasticState(phase)%accumulatedSlip => plasticState(phase)%state (2:2,1:NofMyPhase)
|
|
||||||
endif myPhase
|
|
||||||
enddo initializeInstances
|
|
||||||
|
|
||||||
end subroutine plastic_j2_init
|
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief calculates plastic velocity gradient and its tangent
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine plastic_j2_LpAndItsTangent(Lp,dLp_dTstar99,Tstar_v,ipc,ip,el)
|
|
||||||
use math, only: &
|
|
||||||
math_mul6x6, &
|
|
||||||
math_Mandel6to33, &
|
|
||||||
math_Plain3333to99, &
|
|
||||||
math_deviatoric33, &
|
|
||||||
math_mul33xx33
|
|
||||||
use material, only: &
|
|
||||||
phaseAt, phasememberAt, &
|
|
||||||
plasticState, &
|
|
||||||
material_phase, &
|
|
||||||
phase_plasticityInstance
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
real(pReal), dimension(3,3), intent(out) :: &
|
|
||||||
Lp !< plastic velocity gradient
|
|
||||||
real(pReal), dimension(9,9), intent(out) :: &
|
|
||||||
dLp_dTstar99 !< derivative of Lp with respect to 2nd Piola Kirchhoff stress
|
|
||||||
|
|
||||||
real(pReal), dimension(6), intent(in) :: &
|
|
||||||
Tstar_v !< 2nd Piola Kirchhoff stress tensor in Mandel notation
|
|
||||||
integer(pInt), intent(in) :: &
|
|
||||||
ipc, & !< component-ID of integration point
|
|
||||||
ip, & !< integration point
|
|
||||||
el !< element
|
|
||||||
|
|
||||||
real(pReal), dimension(3,3) :: &
|
|
||||||
Tstar_dev_33 !< deviatoric part of the 2nd Piola Kirchhoff stress tensor as 2nd order tensor
|
|
||||||
real(pReal), dimension(3,3,3,3) :: &
|
|
||||||
dLp_dTstar_3333 !< derivative of Lp with respect to Tstar as 4th order tensor
|
|
||||||
real(pReal) :: &
|
|
||||||
gamma_dot, & !< strainrate
|
|
||||||
norm_Tstar_dev, & !< euclidean norm of Tstar_dev
|
|
||||||
squarenorm_Tstar_dev !< square of the euclidean norm of Tstar_dev
|
|
||||||
integer(pInt) :: &
|
|
||||||
instance, &
|
|
||||||
k, l, m, n
|
|
||||||
|
|
||||||
instance = phase_plasticityInstance(material_phase(ipc,ip,el))
|
|
||||||
Tstar_dev_33 = math_deviatoric33(math_Mandel6to33(Tstar_v)) ! deviatoric part of 2nd Piola-Kirchhoff stress
|
|
||||||
squarenorm_Tstar_dev = math_mul33xx33(Tstar_dev_33,Tstar_dev_33)
|
|
||||||
norm_Tstar_dev = sqrt(squarenorm_Tstar_dev)
|
|
||||||
|
|
||||||
if (norm_Tstar_dev <= 0.0_pReal) then ! Tstar == 0 --> both Lp and dLp_dTstar are zero
|
|
||||||
Lp = 0.0_pReal
|
|
||||||
dLp_dTstar99 = 0.0_pReal
|
|
||||||
else
|
|
||||||
gamma_dot = plastic_j2_gdot0(instance) &
|
|
||||||
* (sqrt(1.5_pReal) * norm_Tstar_dev / (plastic_j2_fTaylor(instance) * &
|
|
||||||
plasticState(phaseAt(ipc,ip,el))%state(1,phasememberAt(ipc,ip,el)))) &
|
|
||||||
**plastic_j2_n(instance)
|
|
||||||
|
|
||||||
Lp = Tstar_dev_33/norm_Tstar_dev * gamma_dot/plastic_j2_fTaylor(instance)
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! Calculation of the tangent of Lp
|
|
||||||
forall (k=1_pInt:3_pInt,l=1_pInt:3_pInt,m=1_pInt:3_pInt,n=1_pInt:3_pInt) &
|
|
||||||
dLp_dTstar_3333(k,l,m,n) = (plastic_j2_n(instance)-1.0_pReal) * &
|
|
||||||
Tstar_dev_33(k,l)*Tstar_dev_33(m,n) / squarenorm_Tstar_dev
|
|
||||||
forall (k=1_pInt:3_pInt,l=1_pInt:3_pInt) &
|
|
||||||
dLp_dTstar_3333(k,l,k,l) = dLp_dTstar_3333(k,l,k,l) + 1.0_pReal
|
|
||||||
forall (k=1_pInt:3_pInt,m=1_pInt:3_pInt) &
|
|
||||||
dLp_dTstar_3333(k,k,m,m) = dLp_dTstar_3333(k,k,m,m) - 1.0_pReal/3.0_pReal
|
|
||||||
dLp_dTstar99 = math_Plain3333to99(gamma_dot / plastic_j2_fTaylor(instance) * &
|
|
||||||
dLp_dTstar_3333 / norm_Tstar_dev)
|
|
||||||
end if
|
|
||||||
end subroutine plastic_j2_LpAndItsTangent
|
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief calculates the rate of change of microstructure
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine plastic_j2_dotState(Tstar_v,ipc,ip,el)
|
|
||||||
use math, only: &
|
|
||||||
math_mul6x6
|
|
||||||
use material, only: &
|
|
||||||
phaseAt, phasememberAt, &
|
|
||||||
plasticState, &
|
|
||||||
material_phase, &
|
|
||||||
phase_plasticityInstance
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
real(pReal), dimension(6), intent(in):: &
|
|
||||||
Tstar_v !< 2nd Piola Kirchhoff stress tensor in Mandel notation
|
|
||||||
integer(pInt), intent(in) :: &
|
|
||||||
ipc, & !< component-ID of integration point
|
|
||||||
ip, & !< integration point
|
|
||||||
el !< element
|
|
||||||
real(pReal), dimension(6) :: &
|
|
||||||
Tstar_dev_v !< deviatoric part of the 2nd Piola Kirchhoff stress tensor in Mandel notation
|
|
||||||
real(pReal) :: &
|
|
||||||
gamma_dot, & !< strainrate
|
|
||||||
hardening, & !< hardening coefficient
|
|
||||||
saturation, & !< saturation resistance
|
|
||||||
norm_Tstar_dev !< euclidean norm of Tstar_dev
|
|
||||||
integer(pInt) :: &
|
|
||||||
instance, & !< instance of my instance (unique number of my constitutive model)
|
|
||||||
of, & !< shortcut notation for offset position in state array
|
|
||||||
ph !< shortcut notation for phase ID (unique number of all phases, regardless of constitutive model)
|
|
||||||
|
|
||||||
of = phasememberAt(ipc,ip,el)
|
|
||||||
ph = phaseAt(ipc,ip,el)
|
|
||||||
instance = phase_plasticityInstance(material_phase(ipc,ip,el))
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! norm of deviatoric part of 2nd Piola-Kirchhoff stress
|
|
||||||
Tstar_dev_v(1:3) = Tstar_v(1:3) - sum(Tstar_v(1:3))/3.0_pReal
|
|
||||||
Tstar_dev_v(4:6) = Tstar_v(4:6)
|
|
||||||
norm_Tstar_dev = sqrt(math_mul6x6(Tstar_dev_v,Tstar_dev_v))
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! strain rate
|
|
||||||
gamma_dot = plastic_j2_gdot0(instance) * ( sqrt(1.5_pReal) * norm_Tstar_dev &
|
|
||||||
/ &!-----------------------------------------------------------------------------------
|
|
||||||
(plastic_j2_fTaylor(instance)*plasticState(ph)%state(1,of)) )**plastic_j2_n(instance)
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! hardening coefficient
|
|
||||||
if (abs(gamma_dot) > 1e-12_pReal) then
|
|
||||||
if (abs(plastic_j2_tausat_SinhFitA(instance)) <= tiny(0.0_pReal)) then
|
|
||||||
saturation = plastic_j2_tausat(instance)
|
|
||||||
else
|
|
||||||
saturation = ( plastic_j2_tausat(instance) &
|
|
||||||
+ ( log( ( gamma_dot / plastic_j2_tausat_SinhFitA(instance)&
|
|
||||||
)**(1.0_pReal / plastic_j2_tausat_SinhFitD(instance))&
|
|
||||||
+ sqrt( ( gamma_dot / plastic_j2_tausat_SinhFitA(instance) &
|
|
||||||
)**(2.0_pReal / plastic_j2_tausat_SinhFitD(instance)) &
|
|
||||||
+ 1.0_pReal ) &
|
|
||||||
) & ! asinh(K) = ln(K + sqrt(K^2 +1))
|
|
||||||
)**(1.0_pReal / plastic_j2_tausat_SinhFitC(instance)) &
|
|
||||||
/ ( plastic_j2_tausat_SinhFitB(instance) &
|
|
||||||
* (gamma_dot / plastic_j2_gdot0(instance))**(1.0_pReal / plastic_j2_n(instance)) &
|
|
||||||
) &
|
|
||||||
)
|
|
||||||
endif
|
|
||||||
hardening = ( plastic_j2_h0(instance) + plastic_j2_h0_slopeLnRate(instance) * log(gamma_dot) ) &
|
|
||||||
* abs( 1.0_pReal - plasticState(ph)%state(1,of)/saturation )**plastic_j2_a(instance) &
|
|
||||||
* sign(1.0_pReal, 1.0_pReal - plasticState(ph)%state(1,of)/saturation)
|
|
||||||
else
|
|
||||||
hardening = 0.0_pReal
|
|
||||||
endif
|
|
||||||
|
|
||||||
plasticState(ph)%dotState(1,of) = hardening * gamma_dot
|
|
||||||
plasticState(ph)%dotState(2,of) = gamma_dot
|
|
||||||
|
|
||||||
end subroutine plastic_j2_dotState
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief return array of constitutive results
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
function plastic_j2_postResults(Tstar_v,ipc,ip,el)
|
|
||||||
use math, only: &
|
|
||||||
math_mul6x6
|
|
||||||
use material, only: &
|
|
||||||
material_phase, &
|
|
||||||
plasticState, &
|
|
||||||
phaseAt, phasememberAt, &
|
|
||||||
phase_plasticityInstance
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
real(pReal), dimension(6), intent(in) :: &
|
|
||||||
Tstar_v !< 2nd Piola Kirchhoff stress tensor in Mandel notation
|
|
||||||
integer(pInt), intent(in) :: &
|
|
||||||
ipc, & !< component-ID of integration point
|
|
||||||
ip, & !< integration point
|
|
||||||
el !< element
|
|
||||||
real(pReal), dimension(plastic_j2_sizePostResults(phase_plasticityInstance(material_phase(ipc,ip,el)))) :: &
|
|
||||||
plastic_j2_postResults
|
|
||||||
|
|
||||||
real(pReal), dimension(6) :: &
|
|
||||||
Tstar_dev_v ! deviatoric part of the 2nd Piola Kirchhoff stress tensor in Mandel notation
|
|
||||||
real(pReal) :: &
|
|
||||||
norm_Tstar_dev ! euclidean norm of Tstar_dev
|
|
||||||
integer(pInt) :: &
|
|
||||||
instance, & !< instance of my instance (unique number of my constitutive model)
|
|
||||||
of, & !< shortcut notation for offset position in state array
|
|
||||||
ph, & !< shortcut notation for phase ID (unique number of all phases, regardless of constitutive model)
|
|
||||||
c, &
|
|
||||||
o
|
|
||||||
|
|
||||||
of = phasememberAt(ipc,ip,el)
|
|
||||||
ph = phaseAt(ipc,ip,el)
|
|
||||||
instance = phase_plasticityInstance(material_phase(ipc,ip,el))
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! calculate deviatoric part of 2nd Piola-Kirchhoff stress and its norm
|
|
||||||
Tstar_dev_v(1:3) = Tstar_v(1:3) - sum(Tstar_v(1:3))/3.0_pReal
|
|
||||||
Tstar_dev_v(4:6) = Tstar_v(4:6)
|
|
||||||
norm_Tstar_dev = sqrt(math_mul6x6(Tstar_dev_v,Tstar_dev_v))
|
|
||||||
|
|
||||||
c = 0_pInt
|
|
||||||
plastic_j2_postResults = 0.0_pReal
|
|
||||||
|
|
||||||
outputsLoop: do o = 1_pInt,plastic_j2_Noutput(instance)
|
|
||||||
select case(plastic_j2_outputID(o,instance))
|
|
||||||
case (flowstress_ID)
|
|
||||||
plastic_j2_postResults(c+1_pInt) = plasticState(ph)%state(1,of)
|
|
||||||
c = c + 1_pInt
|
|
||||||
case (strainrate_ID)
|
|
||||||
plastic_j2_postResults(c+1_pInt) = &
|
|
||||||
plastic_j2_gdot0(instance) * ( sqrt(1.5_pReal) * norm_Tstar_dev &
|
|
||||||
/ &!----------------------------------------------------------------------------------
|
|
||||||
(plastic_j2_fTaylor(instance) * plasticState(ph)%state(1,of)) ) ** plastic_j2_n(instance)
|
|
||||||
c = c + 1_pInt
|
|
||||||
end select
|
|
||||||
enddo outputsLoop
|
|
||||||
|
|
||||||
end function plastic_j2_postResults
|
|
||||||
|
|
||||||
|
|
||||||
end module plastic_j2
|
|
|
@ -1,109 +0,0 @@
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! $Id$
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @author Franz Roters, Max-Planck-Institut für Eisenforschung GmbH
|
|
||||||
!> @author Philip Eisenlohr, Max-Planck-Institut für Eisenforschung GmbH
|
|
||||||
!> @brief material subroutine for purely elastic material
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
module plastic_none
|
|
||||||
use prec, only: &
|
|
||||||
pInt
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
private
|
|
||||||
integer(pInt), dimension(:), allocatable, public, protected :: &
|
|
||||||
plastic_none_sizePostResults
|
|
||||||
|
|
||||||
integer(pInt), dimension(:,:), allocatable, target, public :: &
|
|
||||||
plastic_none_sizePostResult !< size of each post result output
|
|
||||||
|
|
||||||
public :: &
|
|
||||||
plastic_none_init
|
|
||||||
|
|
||||||
contains
|
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief module initialization
|
|
||||||
!> @details reads in material parameters, allocates arrays, and does sanity checks
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine plastic_none_init
|
|
||||||
use, intrinsic :: iso_fortran_env ! to get compiler_version and compiler_options (at least for gfortran 4.6 at the moment)
|
|
||||||
use debug, only: &
|
|
||||||
debug_level, &
|
|
||||||
debug_constitutive, &
|
|
||||||
debug_levelBasic
|
|
||||||
use IO, only: &
|
|
||||||
IO_timeStamp
|
|
||||||
use numerics, only: &
|
|
||||||
worldrank, &
|
|
||||||
numerics_integrator
|
|
||||||
use material, only: &
|
|
||||||
phase_plasticity, &
|
|
||||||
PLASTICITY_NONE_label, &
|
|
||||||
material_phase, &
|
|
||||||
plasticState, &
|
|
||||||
PLASTICITY_none_ID
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
|
|
||||||
integer(pInt) :: &
|
|
||||||
maxNinstance, &
|
|
||||||
phase, &
|
|
||||||
NofMyPhase, &
|
|
||||||
sizeState, &
|
|
||||||
sizeDotState, &
|
|
||||||
sizeDeltaState
|
|
||||||
|
|
||||||
mainProcess: if (worldrank == 0) then
|
|
||||||
write(6,'(/,a)') ' <<<+- constitutive_'//PLASTICITY_NONE_label//' init -+>>>'
|
|
||||||
write(6,'(a15,a)') ' Current time: ',IO_timeStamp()
|
|
||||||
#include "compilation_info.f90"
|
|
||||||
endif mainProcess
|
|
||||||
|
|
||||||
maxNinstance = int(count(phase_plasticity == PLASTICITY_none_ID),pInt)
|
|
||||||
if (maxNinstance == 0_pInt) return
|
|
||||||
|
|
||||||
if (iand(debug_level(debug_constitutive),debug_levelBasic) /= 0_pInt) &
|
|
||||||
write(6,'(a16,1x,i5,/)') '# instances:',maxNinstance
|
|
||||||
|
|
||||||
initializeInstances: do phase = 1_pInt, size(phase_plasticity)
|
|
||||||
if (phase_plasticity(phase) == PLASTICITY_none_ID) then
|
|
||||||
NofMyPhase=count(material_phase==phase)
|
|
||||||
|
|
||||||
sizeState = 0_pInt
|
|
||||||
plasticState(phase)%sizeState = sizeState
|
|
||||||
sizeDotState = sizeState
|
|
||||||
plasticState(phase)%sizeDotState = sizeDotState
|
|
||||||
sizeDeltaState = 0_pInt
|
|
||||||
plasticState(phase)%sizeDeltaState = sizeDeltaState
|
|
||||||
plasticState(phase)%sizePostResults = 0_pInt
|
|
||||||
plasticState(phase)%nSlip = 0_pInt
|
|
||||||
plasticState(phase)%nTwin = 0_pInt
|
|
||||||
plasticState(phase)%nTrans = 0_pInt
|
|
||||||
allocate(plasticState(phase)%aTolState (sizeState))
|
|
||||||
allocate(plasticState(phase)%state0 (sizeState,NofMyPhase))
|
|
||||||
allocate(plasticState(phase)%partionedState0 (sizeState,NofMyPhase))
|
|
||||||
allocate(plasticState(phase)%subState0 (sizeState,NofMyPhase))
|
|
||||||
allocate(plasticState(phase)%state (sizeState,NofMyPhase))
|
|
||||||
allocate(plasticState(phase)%state_backup (sizeState,NofMyPhase))
|
|
||||||
|
|
||||||
allocate(plasticState(phase)%dotState (sizeDotState,NofMyPhase))
|
|
||||||
allocate(plasticState(phase)%deltaState (sizeDeltaState,NofMyPhase))
|
|
||||||
allocate(plasticState(phase)%dotState_backup (sizeDotState,NofMyPhase))
|
|
||||||
if (any(numerics_integrator == 1_pInt)) then
|
|
||||||
allocate(plasticState(phase)%previousDotState (sizeDotState,NofMyPhase))
|
|
||||||
allocate(plasticState(phase)%previousDotState2(sizeDotState,NofMyPhase))
|
|
||||||
endif
|
|
||||||
if (any(numerics_integrator == 4_pInt)) &
|
|
||||||
allocate(plasticState(phase)%RK4dotState (sizeDotState,NofMyPhase))
|
|
||||||
if (any(numerics_integrator == 5_pInt)) &
|
|
||||||
allocate(plasticState(phase)%RKCK45dotState (6,sizeDotState,NofMyPhase))
|
|
||||||
endif
|
|
||||||
enddo initializeInstances
|
|
||||||
|
|
||||||
allocate(plastic_none_sizePostResults(maxNinstance), source=0_pInt)
|
|
||||||
|
|
||||||
end subroutine plastic_none_init
|
|
||||||
|
|
||||||
end module plastic_none
|
|
File diff suppressed because it is too large
Load Diff
File diff suppressed because it is too large
Load Diff
File diff suppressed because it is too large
Load Diff
File diff suppressed because it is too large
Load Diff
|
@ -7,3 +7,8 @@ set (POROSITY "porosity_none"
|
||||||
foreach (p ${POROSITY})
|
foreach (p ${POROSITY})
|
||||||
add_library (${p} MODULE "${p}.f90")
|
add_library (${p} MODULE "${p}.f90")
|
||||||
endforeach (p)
|
endforeach (p)
|
||||||
|
|
||||||
|
# set libraries/modules for linking
|
||||||
|
foreach (p ${POROSITY})
|
||||||
|
set (AUX_LIB ${AUX_LIB} ${p})
|
||||||
|
endforeach (p)
|
|
@ -1,61 +0,0 @@
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! $Id$
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @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()
|
|
||||||
use, intrinsic :: iso_fortran_env ! to get compiler_version and compiler_options (at least for gfortran 4.6 at the moment)
|
|
||||||
use prec, only: &
|
|
||||||
pReal, &
|
|
||||||
pInt
|
|
||||||
use IO, only: &
|
|
||||||
IO_timeStamp
|
|
||||||
use material
|
|
||||||
use numerics, only: &
|
|
||||||
worldrank
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
integer(pInt) :: &
|
|
||||||
homog, &
|
|
||||||
NofMyHomog
|
|
||||||
|
|
||||||
mainProcess: if (worldrank == 0) then
|
|
||||||
write(6,'(/,a)') ' <<<+- porosity_'//POROSITY_none_label//' init -+>>>'
|
|
||||||
write(6,'(a15,a)') ' Current time: ',IO_timeStamp()
|
|
||||||
#include "compilation_info.f90"
|
|
||||||
endif mainProcess
|
|
||||||
|
|
||||||
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,450 +0,0 @@
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! $Id$
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @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)
|
|
||||||
use, intrinsic :: iso_fortran_env ! to get compiler_version and compiler_options (at least for gfortran 4.6 at the moment)
|
|
||||||
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, &
|
|
||||||
material_partHomogenization, &
|
|
||||||
material_partPhase
|
|
||||||
use numerics,only: &
|
|
||||||
worldrank
|
|
||||||
|
|
||||||
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 = ''
|
|
||||||
|
|
||||||
mainProcess: if (worldrank == 0) then
|
|
||||||
write(6,'(/,a)') ' <<<+- porosity_'//POROSITY_phasefield_label//' init -+>>>'
|
|
||||||
write(6,'(a15,a)') ' Current time: ',IO_timeStamp()
|
|
||||||
#include "compilation_info.f90"
|
|
||||||
endif mainProcess
|
|
||||||
|
|
||||||
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/ &
|
|
||||||
homogenization_Ngrains(mesh_element(3,el))
|
|
||||||
|
|
||||||
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/ &
|
|
||||||
homogenization_Ngrains(mesh_element(3,el))
|
|
||||||
|
|
||||||
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/homogenization_Ngrains(homog)
|
|
||||||
|
|
||||||
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/ &
|
|
||||||
homogenization_Ngrains(homog)
|
|
||||||
|
|
||||||
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/homogenization_Ngrains(mesh_element(3,el))
|
|
||||||
|
|
||||||
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
|
|
|
@ -14,3 +14,8 @@ set (SOURCE "source_thermal_dissipation"
|
||||||
foreach (p ${SOURCE})
|
foreach (p ${SOURCE})
|
||||||
add_library (${p} MODULE "${p}.f90")
|
add_library (${p} MODULE "${p}.f90")
|
||||||
endforeach (p)
|
endforeach (p)
|
||||||
|
|
||||||
|
# set libraries/modules for linking
|
||||||
|
foreach (p ${SOURCE})
|
||||||
|
set (AUX_LIB ${AUX_LIB} ${p})
|
||||||
|
endforeach (p)
|
|
@ -1,425 +0,0 @@
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! $Id$
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @author Luv Sharma, Max-Planck-Institut fŸr Eisenforschung GmbH
|
|
||||||
!> @author Pratheek Shanthraj, Max-Planck-Institut fŸr Eisenforschung GmbH
|
|
||||||
!> @brief material subroutine incorporating anisotropic brittle damage source mechanism
|
|
||||||
!> @details to be done
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
module source_damage_anisoBrittle
|
|
||||||
use prec, only: &
|
|
||||||
pReal, &
|
|
||||||
pInt
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
private
|
|
||||||
integer(pInt), dimension(:), allocatable, public, protected :: &
|
|
||||||
source_damage_anisoBrittle_sizePostResults, & !< cumulative size of post results
|
|
||||||
source_damage_anisoBrittle_offset, & !< which source is my current source mechanism?
|
|
||||||
source_damage_anisoBrittle_instance !< instance of source mechanism
|
|
||||||
|
|
||||||
integer(pInt), dimension(:,:), allocatable, target, public :: &
|
|
||||||
source_damage_anisoBrittle_sizePostResult !< size of each post result output
|
|
||||||
|
|
||||||
character(len=64), dimension(:,:), allocatable, target, public :: &
|
|
||||||
source_damage_anisoBrittle_output !< name of each post result output
|
|
||||||
|
|
||||||
integer(pInt), dimension(:), allocatable, target, public :: &
|
|
||||||
source_damage_anisoBrittle_Noutput !< number of outputs per instance of this source
|
|
||||||
|
|
||||||
integer(pInt), dimension(:), allocatable, private :: &
|
|
||||||
source_damage_anisoBrittle_totalNcleavage !< total number of cleavage systems
|
|
||||||
|
|
||||||
integer(pInt), dimension(:,:), allocatable, private :: &
|
|
||||||
source_damage_anisoBrittle_Ncleavage !< number of cleavage systems per family
|
|
||||||
|
|
||||||
real(pReal), dimension(:), allocatable, private :: &
|
|
||||||
source_damage_anisoBrittle_aTol, &
|
|
||||||
source_damage_anisoBrittle_sdot_0, &
|
|
||||||
source_damage_anisoBrittle_N
|
|
||||||
|
|
||||||
real(pReal), dimension(:,:), allocatable, private :: &
|
|
||||||
source_damage_anisoBrittle_critDisp, &
|
|
||||||
source_damage_anisoBrittle_critLoad
|
|
||||||
|
|
||||||
enum, bind(c)
|
|
||||||
enumerator :: undefined_ID, &
|
|
||||||
damage_drivingforce_ID
|
|
||||||
end enum
|
|
||||||
|
|
||||||
integer(kind(undefined_ID)), dimension(:,:), allocatable, private :: &
|
|
||||||
source_damage_anisoBrittle_outputID !< ID of each post result output
|
|
||||||
|
|
||||||
|
|
||||||
public :: &
|
|
||||||
source_damage_anisoBrittle_init, &
|
|
||||||
source_damage_anisoBrittle_dotState, &
|
|
||||||
source_damage_anisobrittle_getRateAndItsTangent, &
|
|
||||||
source_damage_anisoBrittle_postResults
|
|
||||||
|
|
||||||
contains
|
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief module initialization
|
|
||||||
!> @details reads in material parameters, allocates arrays, and does sanity checks
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine source_damage_anisoBrittle_init(fileUnit)
|
|
||||||
use, intrinsic :: iso_fortran_env ! to get compiler_version and compiler_options (at least for gfortran 4.6 at the moment)
|
|
||||||
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_damage_anisoBrittle_label, &
|
|
||||||
SOURCE_damage_anisoBrittle_ID, &
|
|
||||||
material_Nphase, &
|
|
||||||
material_phase, &
|
|
||||||
sourceState, &
|
|
||||||
MATERIAL_partPhase
|
|
||||||
use numerics,only: &
|
|
||||||
analyticJaco, &
|
|
||||||
worldrank, &
|
|
||||||
numerics_integrator
|
|
||||||
use lattice, only: &
|
|
||||||
lattice_maxNcleavageFamily, &
|
|
||||||
lattice_NcleavageSystem
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
integer(pInt), intent(in) :: fileUnit
|
|
||||||
|
|
||||||
integer(pInt), allocatable, dimension(:) :: chunkPos
|
|
||||||
integer(pInt) :: maxNinstance,mySize=0_pInt,phase,instance,source,sourceOffset,o
|
|
||||||
integer(pInt) :: sizeState, sizeDotState, sizeDeltaState
|
|
||||||
integer(pInt) :: NofMyPhase
|
|
||||||
integer(pInt) :: Nchunks_CleavageFamilies = 0_pInt, j
|
|
||||||
character(len=65536) :: &
|
|
||||||
tag = '', &
|
|
||||||
line = ''
|
|
||||||
|
|
||||||
mainProcess: if (worldrank == 0) then
|
|
||||||
write(6,'(/,a)') ' <<<+- source_'//SOURCE_damage_anisoBrittle_LABEL//' init -+>>>'
|
|
||||||
write(6,'(a15,a)') ' Current time: ',IO_timeStamp()
|
|
||||||
#include "compilation_info.f90"
|
|
||||||
endif mainProcess
|
|
||||||
|
|
||||||
maxNinstance = int(count(phase_source == SOURCE_damage_anisoBrittle_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_damage_anisoBrittle_offset(material_Nphase), source=0_pInt)
|
|
||||||
allocate(source_damage_anisoBrittle_instance(material_Nphase), source=0_pInt)
|
|
||||||
do phase = 1, material_Nphase
|
|
||||||
source_damage_anisoBrittle_instance(phase) = count(phase_source(:,1:phase) == source_damage_anisoBrittle_ID)
|
|
||||||
do source = 1, phase_Nsources(phase)
|
|
||||||
if (phase_source(source,phase) == source_damage_anisoBrittle_ID) &
|
|
||||||
source_damage_anisoBrittle_offset(phase) = source
|
|
||||||
enddo
|
|
||||||
enddo
|
|
||||||
|
|
||||||
allocate(source_damage_anisoBrittle_sizePostResults(maxNinstance), source=0_pInt)
|
|
||||||
allocate(source_damage_anisoBrittle_sizePostResult(maxval(phase_Noutput),maxNinstance), source=0_pInt)
|
|
||||||
allocate(source_damage_anisoBrittle_output(maxval(phase_Noutput),maxNinstance))
|
|
||||||
source_damage_anisoBrittle_output = ''
|
|
||||||
allocate(source_damage_anisoBrittle_outputID(maxval(phase_Noutput),maxNinstance), source=undefined_ID)
|
|
||||||
allocate(source_damage_anisoBrittle_Noutput(maxNinstance), source=0_pInt)
|
|
||||||
allocate(source_damage_anisoBrittle_critDisp(lattice_maxNcleavageFamily,maxNinstance), source=0.0_pReal)
|
|
||||||
allocate(source_damage_anisoBrittle_critLoad(lattice_maxNcleavageFamily,maxNinstance), source=0.0_pReal)
|
|
||||||
allocate(source_damage_anisoBrittle_Ncleavage(lattice_maxNcleavageFamily,maxNinstance), source=0_pInt)
|
|
||||||
allocate(source_damage_anisoBrittle_totalNcleavage(maxNinstance), source=0_pInt)
|
|
||||||
allocate(source_damage_anisoBrittle_aTol(maxNinstance), source=0.0_pReal)
|
|
||||||
allocate(source_damage_anisoBrittle_sdot_0(maxNinstance), source=0.0_pReal)
|
|
||||||
allocate(source_damage_anisoBrittle_N(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_damage_anisoBrittle_ID)) then ! do not short-circuit here (.and. with next if statemen). It's not safe in Fortran
|
|
||||||
instance = source_damage_anisoBrittle_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 ('(output)')
|
|
||||||
select case(IO_lc(IO_stringValue(line,chunkPos,2_pInt)))
|
|
||||||
case ('anisobrittle_drivingforce')
|
|
||||||
source_damage_anisoBrittle_Noutput(instance) = source_damage_anisoBrittle_Noutput(instance) + 1_pInt
|
|
||||||
source_damage_anisoBrittle_outputID(source_damage_anisoBrittle_Noutput(instance),instance) = damage_drivingforce_ID
|
|
||||||
source_damage_anisoBrittle_output(source_damage_anisoBrittle_Noutput(instance),instance) = &
|
|
||||||
IO_lc(IO_stringValue(line,chunkPos,2_pInt))
|
|
||||||
end select
|
|
||||||
|
|
||||||
case ('anisobrittle_atol')
|
|
||||||
source_damage_anisoBrittle_aTol(instance) = IO_floatValue(line,chunkPos,2_pInt)
|
|
||||||
|
|
||||||
case ('anisobrittle_sdot0')
|
|
||||||
source_damage_anisoBrittle_sdot_0(instance) = IO_floatValue(line,chunkPos,2_pInt)
|
|
||||||
|
|
||||||
case ('anisobrittle_ratesensitivity')
|
|
||||||
source_damage_anisoBrittle_N(instance) = IO_floatValue(line,chunkPos,2_pInt)
|
|
||||||
|
|
||||||
case ('ncleavage') !
|
|
||||||
Nchunks_CleavageFamilies = chunkPos(1) - 1_pInt
|
|
||||||
do j = 1_pInt, Nchunks_CleavageFamilies
|
|
||||||
source_damage_anisoBrittle_Ncleavage(j,instance) = IO_intValue(line,chunkPos,1_pInt+j)
|
|
||||||
enddo
|
|
||||||
|
|
||||||
case ('anisobrittle_criticaldisplacement')
|
|
||||||
do j = 1_pInt, Nchunks_CleavageFamilies
|
|
||||||
source_damage_anisoBrittle_critDisp(j,instance) = IO_floatValue(line,chunkPos,1_pInt+j)
|
|
||||||
enddo
|
|
||||||
|
|
||||||
case ('anisobrittle_criticalload')
|
|
||||||
do j = 1_pInt, Nchunks_CleavageFamilies
|
|
||||||
source_damage_anisoBrittle_critLoad(j,instance) = IO_floatValue(line,chunkPos,1_pInt+j)
|
|
||||||
enddo
|
|
||||||
|
|
||||||
end select
|
|
||||||
endif; endif
|
|
||||||
enddo parsingFile
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! sanity checks
|
|
||||||
sanityChecks: do phase = 1_pInt, material_Nphase
|
|
||||||
myPhase: if (any(phase_source(:,phase) == SOURCE_damage_anisoBrittle_ID)) then
|
|
||||||
instance = source_damage_anisoBrittle_instance(phase)
|
|
||||||
source_damage_anisoBrittle_Ncleavage(1:lattice_maxNcleavageFamily,instance) = &
|
|
||||||
min(lattice_NcleavageSystem(1:lattice_maxNcleavageFamily,phase),& ! limit active cleavage systems per family to min of available and requested
|
|
||||||
source_damage_anisoBrittle_Ncleavage(1:lattice_maxNcleavageFamily,instance))
|
|
||||||
source_damage_anisoBrittle_totalNcleavage(instance) = sum(source_damage_anisoBrittle_Ncleavage(:,instance)) ! how many cleavage systems altogether
|
|
||||||
if (source_damage_anisoBrittle_aTol(instance) < 0.0_pReal) &
|
|
||||||
source_damage_anisoBrittle_aTol(instance) = 1.0e-3_pReal ! default absolute tolerance 1e-3
|
|
||||||
if (source_damage_anisoBrittle_sdot_0(instance) <= 0.0_pReal) &
|
|
||||||
call IO_error(211_pInt,el=instance,ext_msg='sdot_0 ('//SOURCE_damage_anisoBrittle_LABEL//')')
|
|
||||||
if (any(source_damage_anisoBrittle_critDisp(1:Nchunks_CleavageFamilies,instance) < 0.0_pReal)) &
|
|
||||||
call IO_error(211_pInt,el=instance,ext_msg='critical_displacement ('//SOURCE_damage_anisoBrittle_LABEL//')')
|
|
||||||
if (any(source_damage_anisoBrittle_critLoad(1:Nchunks_CleavageFamilies,instance) < 0.0_pReal)) &
|
|
||||||
call IO_error(211_pInt,el=instance,ext_msg='critical_load ('//SOURCE_damage_anisoBrittle_LABEL//')')
|
|
||||||
if (source_damage_anisoBrittle_N(instance) <= 0.0_pReal) &
|
|
||||||
call IO_error(211_pInt,el=instance,ext_msg='rate_sensitivity ('//SOURCE_damage_anisoBrittle_LABEL//')')
|
|
||||||
endif myPhase
|
|
||||||
enddo sanityChecks
|
|
||||||
|
|
||||||
initializeInstances: do phase = 1_pInt, material_Nphase
|
|
||||||
if (any(phase_source(:,phase) == SOURCE_damage_anisoBrittle_ID)) then
|
|
||||||
NofMyPhase=count(material_phase==phase)
|
|
||||||
instance = source_damage_anisoBrittle_instance(phase)
|
|
||||||
sourceOffset = source_damage_anisoBrittle_offset(phase)
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! Determine size of postResults array
|
|
||||||
outputsLoop: do o = 1_pInt,source_damage_anisoBrittle_Noutput(instance)
|
|
||||||
select case(source_damage_anisoBrittle_outputID(o,instance))
|
|
||||||
case(damage_drivingforce_ID)
|
|
||||||
mySize = 1_pInt
|
|
||||||
end select
|
|
||||||
|
|
||||||
if (mySize > 0_pInt) then ! any meaningful output found
|
|
||||||
source_damage_anisoBrittle_sizePostResult(o,instance) = mySize
|
|
||||||
source_damage_anisoBrittle_sizePostResults(instance) = source_damage_anisoBrittle_sizePostResults(instance) + mySize
|
|
||||||
endif
|
|
||||||
enddo outputsLoop
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! Determine size of state array
|
|
||||||
sizeDotState = 1_pInt
|
|
||||||
sizeDeltaState = 0_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_damage_anisoBrittle_sizePostResults(instance)
|
|
||||||
allocate(sourceState(phase)%p(sourceOffset)%aTolState (sizeState), &
|
|
||||||
source=source_damage_anisoBrittle_aTol(instance))
|
|
||||||
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 (.not. analyticJaco) then
|
|
||||||
allocate(sourceState(phase)%p(sourceOffset)%state_backup (sizeState,NofMyPhase), source=0.0_pReal)
|
|
||||||
allocate(sourceState(phase)%p(sourceOffset)%dotState_backup (sizeDotState,NofMyPhase), source=0.0_pReal)
|
|
||||||
endif
|
|
||||||
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_damage_anisoBrittle_init
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief calculates derived quantities from state
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine source_damage_anisoBrittle_dotState(Tstar_v, ipc, ip, el)
|
|
||||||
use material, only: &
|
|
||||||
phaseAt, phasememberAt, &
|
|
||||||
sourceState, &
|
|
||||||
material_homog, &
|
|
||||||
damage, &
|
|
||||||
damageMapping
|
|
||||||
use lattice, only: &
|
|
||||||
lattice_Scleavage_v, &
|
|
||||||
lattice_maxNcleavageFamily, &
|
|
||||||
lattice_NcleavageSystem
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
integer(pInt), intent(in) :: &
|
|
||||||
ipc, & !< component-ID of integration point
|
|
||||||
ip, & !< integration point
|
|
||||||
el !< element
|
|
||||||
real(pReal), intent(in), dimension(6) :: &
|
|
||||||
Tstar_v !< 2nd Piola Kirchhoff stress tensor (Mandel)
|
|
||||||
integer(pInt) :: &
|
|
||||||
phase, &
|
|
||||||
constituent, &
|
|
||||||
instance, &
|
|
||||||
sourceOffset, &
|
|
||||||
damageOffset, &
|
|
||||||
homog, &
|
|
||||||
f, i, index_myFamily
|
|
||||||
real(pReal) :: &
|
|
||||||
traction_d, traction_t, traction_n, traction_crit
|
|
||||||
|
|
||||||
phase = phaseAt(ipc,ip,el)
|
|
||||||
constituent = phasememberAt(ipc,ip,el)
|
|
||||||
instance = source_damage_anisoBrittle_instance(phase)
|
|
||||||
sourceOffset = source_damage_anisoBrittle_offset(phase)
|
|
||||||
homog = material_homog(ip,el)
|
|
||||||
damageOffset = damageMapping(homog)%p(ip,el)
|
|
||||||
|
|
||||||
sourceState(phase)%p(sourceOffset)%dotState(1,constituent) = 0.0_pReal
|
|
||||||
do f = 1_pInt,lattice_maxNcleavageFamily
|
|
||||||
index_myFamily = sum(lattice_NcleavageSystem(1:f-1_pInt,phase)) ! at which index starts my family
|
|
||||||
do i = 1_pInt,source_damage_anisoBrittle_Ncleavage(f,instance) ! process each (active) cleavage system in family
|
|
||||||
traction_d = dot_product(Tstar_v,lattice_Scleavage_v(1:6,1,index_myFamily+i,phase))
|
|
||||||
traction_t = dot_product(Tstar_v,lattice_Scleavage_v(1:6,2,index_myFamily+i,phase))
|
|
||||||
traction_n = dot_product(Tstar_v,lattice_Scleavage_v(1:6,3,index_myFamily+i,phase))
|
|
||||||
|
|
||||||
traction_crit = source_damage_anisoBrittle_critLoad(f,instance)* &
|
|
||||||
damage(homog)%p(damageOffset)*damage(homog)%p(damageOffset)
|
|
||||||
sourceState(phase)%p(sourceOffset)%dotState(1,constituent) = &
|
|
||||||
sourceState(phase)%p(sourceOffset)%dotState(1,constituent) + &
|
|
||||||
source_damage_anisoBrittle_sdot_0(instance)* &
|
|
||||||
((max(0.0_pReal, abs(traction_d) - traction_crit)/traction_crit)**source_damage_anisoBrittle_N(instance) + &
|
|
||||||
(max(0.0_pReal, abs(traction_t) - traction_crit)/traction_crit)**source_damage_anisoBrittle_N(instance) + &
|
|
||||||
(max(0.0_pReal, abs(traction_n) - traction_crit)/traction_crit)**source_damage_anisoBrittle_N(instance))/ &
|
|
||||||
source_damage_anisoBrittle_critDisp(f,instance)
|
|
||||||
|
|
||||||
enddo
|
|
||||||
enddo
|
|
||||||
|
|
||||||
end subroutine source_damage_anisoBrittle_dotState
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief returns local part of nonlocal damage driving force
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine source_damage_anisobrittle_getRateAndItsTangent(localphiDot, dLocalphiDot_dPhi, phi, 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
|
|
||||||
real(pReal), intent(in) :: &
|
|
||||||
phi
|
|
||||||
real(pReal), intent(out) :: &
|
|
||||||
localphiDot, &
|
|
||||||
dLocalphiDot_dPhi
|
|
||||||
integer(pInt) :: &
|
|
||||||
phase, constituent, sourceOffset
|
|
||||||
|
|
||||||
phase = phaseAt(ipc,ip,el)
|
|
||||||
constituent = phasememberAt(ipc,ip,el)
|
|
||||||
sourceOffset = source_damage_anisoBrittle_offset(phase)
|
|
||||||
|
|
||||||
localphiDot = 1.0_pReal - &
|
|
||||||
sourceState(phase)%p(sourceOffset)%state(1,constituent)*phi
|
|
||||||
|
|
||||||
dLocalphiDot_dPhi = -sourceState(phase)%p(sourceOffset)%state(1,constituent)
|
|
||||||
|
|
||||||
end subroutine source_damage_anisobrittle_getRateAndItsTangent
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief return array of local damage results
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
function source_damage_anisoBrittle_postResults(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
|
|
||||||
real(pReal), dimension(source_damage_anisoBrittle_sizePostResults( &
|
|
||||||
source_damage_anisoBrittle_instance(phaseAt(ipc,ip,el)))) :: &
|
|
||||||
source_damage_anisoBrittle_postResults
|
|
||||||
|
|
||||||
integer(pInt) :: &
|
|
||||||
instance, phase, constituent, sourceOffset, o, c
|
|
||||||
|
|
||||||
phase = phaseAt(ipc,ip,el)
|
|
||||||
constituent = phasememberAt(ipc,ip,el)
|
|
||||||
instance = source_damage_anisoBrittle_instance(phase)
|
|
||||||
sourceOffset = source_damage_anisoBrittle_offset(phase)
|
|
||||||
|
|
||||||
c = 0_pInt
|
|
||||||
source_damage_anisoBrittle_postResults = 0.0_pReal
|
|
||||||
|
|
||||||
do o = 1_pInt,source_damage_anisoBrittle_Noutput(instance)
|
|
||||||
select case(source_damage_anisoBrittle_outputID(o,instance))
|
|
||||||
case (damage_drivingforce_ID)
|
|
||||||
source_damage_anisoBrittle_postResults(c+1_pInt) = &
|
|
||||||
sourceState(phase)%p(sourceOffset)%state(1,constituent)
|
|
||||||
c = c + 1_pInt
|
|
||||||
|
|
||||||
end select
|
|
||||||
enddo
|
|
||||||
end function source_damage_anisoBrittle_postResults
|
|
||||||
|
|
||||||
end module source_damage_anisoBrittle
|
|
|
@ -1,415 +0,0 @@
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! $Id$
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @author Luv Sharma, Max-Planck-Institut für Eisenforschung GmbH
|
|
||||||
!> @author Pratheek Shanthraj, Max-Planck-Institut für Eisenforschung GmbH
|
|
||||||
!> @brief material subroutine incorporating anisotropic ductile damage source mechanism
|
|
||||||
!> @details to be done
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
module source_damage_anisoDuctile
|
|
||||||
use prec, only: &
|
|
||||||
pReal, &
|
|
||||||
pInt
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
private
|
|
||||||
integer(pInt), dimension(:), allocatable, public, protected :: &
|
|
||||||
source_damage_anisoDuctile_sizePostResults, & !< cumulative size of post results
|
|
||||||
source_damage_anisoDuctile_offset, & !< which source is my current damage mechanism?
|
|
||||||
source_damage_anisoDuctile_instance !< instance of damage source mechanism
|
|
||||||
|
|
||||||
integer(pInt), dimension(:,:), allocatable, target, public :: &
|
|
||||||
source_damage_anisoDuctile_sizePostResult !< size of each post result output
|
|
||||||
|
|
||||||
character(len=64), dimension(:,:), allocatable, target, public :: &
|
|
||||||
source_damage_anisoDuctile_output !< name of each post result output
|
|
||||||
|
|
||||||
integer(pInt), dimension(:), allocatable, target, public :: &
|
|
||||||
source_damage_anisoDuctile_Noutput !< number of outputs per instance of this damage
|
|
||||||
|
|
||||||
integer(pInt), dimension(:), allocatable, private :: &
|
|
||||||
source_damage_anisoDuctile_totalNslip !< total number of slip systems
|
|
||||||
|
|
||||||
integer(pInt), dimension(:,:), allocatable, private :: &
|
|
||||||
source_damage_anisoDuctile_Nslip !< number of slip systems per family
|
|
||||||
|
|
||||||
real(pReal), dimension(:), allocatable, private :: &
|
|
||||||
source_damage_anisoDuctile_aTol
|
|
||||||
|
|
||||||
real(pReal), dimension(:,:), allocatable, private :: &
|
|
||||||
source_damage_anisoDuctile_critPlasticStrain
|
|
||||||
|
|
||||||
real(pReal), dimension(:), allocatable, private :: &
|
|
||||||
source_damage_anisoDuctile_sdot_0, &
|
|
||||||
source_damage_anisoDuctile_N
|
|
||||||
|
|
||||||
real(pReal), dimension(:,:), allocatable, private :: &
|
|
||||||
source_damage_anisoDuctile_critLoad
|
|
||||||
|
|
||||||
enum, bind(c)
|
|
||||||
enumerator :: undefined_ID, &
|
|
||||||
damage_drivingforce_ID
|
|
||||||
end enum
|
|
||||||
|
|
||||||
integer(kind(undefined_ID)), dimension(:,:), allocatable, private :: &
|
|
||||||
source_damage_anisoDuctile_outputID !< ID of each post result output
|
|
||||||
|
|
||||||
|
|
||||||
public :: &
|
|
||||||
source_damage_anisoDuctile_init, &
|
|
||||||
source_damage_anisoDuctile_dotState, &
|
|
||||||
source_damage_anisoDuctile_getRateAndItsTangent, &
|
|
||||||
source_damage_anisoDuctile_postResults
|
|
||||||
|
|
||||||
contains
|
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief module initialization
|
|
||||||
!> @details reads in material parameters, allocates arrays, and does sanity checks
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine source_damage_anisoDuctile_init(fileUnit)
|
|
||||||
use, intrinsic :: iso_fortran_env ! to get compiler_version and compiler_options (at least for gfortran 4.6 at the moment)
|
|
||||||
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_damage_anisoDuctile_label, &
|
|
||||||
SOURCE_damage_anisoDuctile_ID, &
|
|
||||||
material_Nphase, &
|
|
||||||
material_phase, &
|
|
||||||
sourceState, &
|
|
||||||
MATERIAL_partPhase
|
|
||||||
use numerics,only: &
|
|
||||||
analyticJaco, &
|
|
||||||
worldrank, &
|
|
||||||
numerics_integrator
|
|
||||||
use lattice, only: &
|
|
||||||
lattice_maxNslipFamily, &
|
|
||||||
lattice_NslipSystem
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
integer(pInt), intent(in) :: fileUnit
|
|
||||||
|
|
||||||
integer(pInt), allocatable, dimension(:) :: chunkPos
|
|
||||||
integer(pInt) :: maxNinstance,mySize=0_pInt,phase,instance,source,sourceOffset,o
|
|
||||||
integer(pInt) :: sizeState, sizeDotState, sizeDeltaState
|
|
||||||
integer(pInt) :: NofMyPhase
|
|
||||||
integer(pInt) :: Nchunks_SlipFamilies = 0_pInt, j
|
|
||||||
character(len=65536) :: &
|
|
||||||
tag = '', &
|
|
||||||
line = ''
|
|
||||||
|
|
||||||
mainProcess: if (worldrank == 0) then
|
|
||||||
write(6,'(/,a)') ' <<<+- source_'//SOURCE_damage_anisoDuctile_LABEL//' init -+>>>'
|
|
||||||
write(6,'(a15,a)') ' Current time: ',IO_timeStamp()
|
|
||||||
#include "compilation_info.f90"
|
|
||||||
endif mainProcess
|
|
||||||
|
|
||||||
maxNinstance = int(count(phase_source == SOURCE_damage_anisoDuctile_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_damage_anisoDuctile_offset(material_Nphase), source=0_pInt)
|
|
||||||
allocate(source_damage_anisoDuctile_instance(material_Nphase), source=0_pInt)
|
|
||||||
do phase = 1, material_Nphase
|
|
||||||
source_damage_anisoDuctile_instance(phase) = count(phase_source(:,1:phase) == source_damage_anisoDuctile_ID)
|
|
||||||
do source = 1, phase_Nsources(phase)
|
|
||||||
if (phase_source(source,phase) == source_damage_anisoDuctile_ID) &
|
|
||||||
source_damage_anisoDuctile_offset(phase) = source
|
|
||||||
enddo
|
|
||||||
enddo
|
|
||||||
|
|
||||||
allocate(source_damage_anisoDuctile_sizePostResults(maxNinstance), source=0_pInt)
|
|
||||||
allocate(source_damage_anisoDuctile_sizePostResult(maxval(phase_Noutput),maxNinstance),source=0_pInt)
|
|
||||||
allocate(source_damage_anisoDuctile_output(maxval(phase_Noutput),maxNinstance))
|
|
||||||
source_damage_anisoDuctile_output = ''
|
|
||||||
allocate(source_damage_anisoDuctile_outputID(maxval(phase_Noutput),maxNinstance), source=undefined_ID)
|
|
||||||
allocate(source_damage_anisoDuctile_Noutput(maxNinstance), source=0_pInt)
|
|
||||||
allocate(source_damage_anisoDuctile_critLoad(lattice_maxNslipFamily,maxNinstance), source=0.0_pReal)
|
|
||||||
allocate(source_damage_anisoDuctile_critPlasticStrain(lattice_maxNslipFamily,maxNinstance),source=0.0_pReal)
|
|
||||||
allocate(source_damage_anisoDuctile_Nslip(lattice_maxNslipFamily,maxNinstance), source=0_pInt)
|
|
||||||
allocate(source_damage_anisoDuctile_totalNslip(maxNinstance), source=0_pInt)
|
|
||||||
allocate(source_damage_anisoDuctile_N(maxNinstance), source=0.0_pReal)
|
|
||||||
allocate(source_damage_anisoDuctile_sdot_0(maxNinstance), source=0.0_pReal)
|
|
||||||
allocate(source_damage_anisoDuctile_aTol(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_damage_anisoDuctile_ID)) then ! do not short-circuit here (.and. with next if statemen). It's not safe in Fortran
|
|
||||||
instance = source_damage_anisoDuctile_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 ('(output)')
|
|
||||||
select case(IO_lc(IO_stringValue(line,chunkPos,2_pInt)))
|
|
||||||
case ('anisoductile_drivingforce')
|
|
||||||
source_damage_anisoDuctile_Noutput(instance) = source_damage_anisoDuctile_Noutput(instance) + 1_pInt
|
|
||||||
source_damage_anisoDuctile_outputID(source_damage_anisoDuctile_Noutput(instance),instance) = damage_drivingforce_ID
|
|
||||||
source_damage_anisoDuctile_output(source_damage_anisoDuctile_Noutput(instance),instance) = &
|
|
||||||
IO_lc(IO_stringValue(line,chunkPos,2_pInt))
|
|
||||||
end select
|
|
||||||
|
|
||||||
case ('anisoductile_atol')
|
|
||||||
source_damage_anisoDuctile_aTol(instance) = IO_floatValue(line,chunkPos,2_pInt)
|
|
||||||
|
|
||||||
case ('nslip') !
|
|
||||||
Nchunks_SlipFamilies = chunkPos(1) - 1_pInt
|
|
||||||
do j = 1_pInt, Nchunks_SlipFamilies
|
|
||||||
source_damage_anisoDuctile_Nslip(j,instance) = IO_intValue(line,chunkPos,1_pInt+j)
|
|
||||||
enddo
|
|
||||||
|
|
||||||
case ('anisoductile_sdot0')
|
|
||||||
source_damage_anisoDuctile_sdot_0(instance) = IO_floatValue(line,chunkPos,2_pInt)
|
|
||||||
|
|
||||||
case ('anisoductile_criticalplasticstrain')
|
|
||||||
do j = 1_pInt, Nchunks_SlipFamilies
|
|
||||||
source_damage_anisoDuctile_critPlasticStrain(j,instance) = IO_floatValue(line,chunkPos,1_pInt+j)
|
|
||||||
enddo
|
|
||||||
|
|
||||||
case ('anisoductile_ratesensitivity')
|
|
||||||
source_damage_anisoDuctile_N(instance) = IO_floatValue(line,chunkPos,2_pInt)
|
|
||||||
|
|
||||||
case ('anisoductile_criticalload')
|
|
||||||
do j = 1_pInt, Nchunks_SlipFamilies
|
|
||||||
source_damage_anisoDuctile_critLoad(j,instance) = IO_floatValue(line,chunkPos,1_pInt+j)
|
|
||||||
enddo
|
|
||||||
|
|
||||||
end select
|
|
||||||
endif; endif
|
|
||||||
enddo parsingFile
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! sanity checks
|
|
||||||
sanityChecks: do phase = 1_pInt, size(phase_source)
|
|
||||||
myPhase: if (any(phase_source(:,phase) == SOURCE_damage_anisoDuctile_ID)) then
|
|
||||||
instance = source_damage_anisoDuctile_instance(phase)
|
|
||||||
source_damage_anisoDuctile_Nslip(1:lattice_maxNslipFamily,instance) = &
|
|
||||||
min(lattice_NslipSystem(1:lattice_maxNslipFamily,phase),& ! limit active cleavage systems per family to min of available and requested
|
|
||||||
source_damage_anisoDuctile_Nslip(1:lattice_maxNslipFamily,instance))
|
|
||||||
source_damage_anisoDuctile_totalNslip(instance) = sum(source_damage_anisoDuctile_Nslip(:,instance))
|
|
||||||
if (source_damage_anisoDuctile_aTol(instance) < 0.0_pReal) &
|
|
||||||
source_damage_anisoDuctile_aTol(instance) = 1.0e-3_pReal ! default absolute tolerance 1e-3
|
|
||||||
if (source_damage_anisoDuctile_sdot_0(instance) <= 0.0_pReal) &
|
|
||||||
call IO_error(211_pInt,el=instance,ext_msg='sdot_0 ('//SOURCE_damage_anisoDuctile_LABEL//')')
|
|
||||||
if (any(source_damage_anisoDuctile_critPlasticStrain(:,instance) < 0.0_pReal)) &
|
|
||||||
call IO_error(211_pInt,el=instance,ext_msg='criticaPlasticStrain ('//SOURCE_damage_anisoDuctile_LABEL//')')
|
|
||||||
if (source_damage_anisoDuctile_N(instance) <= 0.0_pReal) &
|
|
||||||
call IO_error(211_pInt,el=instance,ext_msg='rate_sensitivity ('//SOURCE_damage_anisoDuctile_LABEL//')')
|
|
||||||
endif myPhase
|
|
||||||
enddo sanityChecks
|
|
||||||
|
|
||||||
|
|
||||||
initializeInstances: do phase = 1_pInt, material_Nphase
|
|
||||||
if (any(phase_source(:,phase) == SOURCE_damage_anisoDuctile_ID)) then
|
|
||||||
NofMyPhase=count(material_phase==phase)
|
|
||||||
instance = source_damage_anisoDuctile_instance(phase)
|
|
||||||
sourceOffset = source_damage_anisoDuctile_offset(phase)
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! Determine size of postResults array
|
|
||||||
outputsLoop: do o = 1_pInt,source_damage_anisoDuctile_Noutput(instance)
|
|
||||||
select case(source_damage_anisoDuctile_outputID(o,instance))
|
|
||||||
case(damage_drivingforce_ID)
|
|
||||||
mySize = 1_pInt
|
|
||||||
end select
|
|
||||||
|
|
||||||
if (mySize > 0_pInt) then ! any meaningful output found
|
|
||||||
source_damage_anisoDuctile_sizePostResult(o,instance) = mySize
|
|
||||||
source_damage_anisoDuctile_sizePostResults(instance) = source_damage_anisoDuctile_sizePostResults(instance) + mySize
|
|
||||||
endif
|
|
||||||
enddo outputsLoop
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! Determine size of state array
|
|
||||||
sizeDotState = 1_pInt
|
|
||||||
sizeDeltaState = 0_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_damage_anisoDuctile_sizePostResults(instance)
|
|
||||||
allocate(sourceState(phase)%p(sourceOffset)%aTolState (sizeState), &
|
|
||||||
source=source_damage_anisoDuctile_aTol(instance))
|
|
||||||
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 (.not. analyticJaco) then
|
|
||||||
allocate(sourceState(phase)%p(sourceOffset)%state_backup (sizeState,NofMyPhase), source=0.0_pReal)
|
|
||||||
allocate(sourceState(phase)%p(sourceOffset)%dotState_backup (sizeDotState,NofMyPhase), source=0.0_pReal)
|
|
||||||
endif
|
|
||||||
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_damage_anisoDuctile_init
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief calculates derived quantities from state
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine source_damage_anisoDuctile_dotState(ipc, ip, el)
|
|
||||||
use material, only: &
|
|
||||||
phaseAt, phasememberAt, &
|
|
||||||
plasticState, &
|
|
||||||
sourceState, &
|
|
||||||
material_homog, &
|
|
||||||
damage, &
|
|
||||||
damageMapping
|
|
||||||
use lattice, only: &
|
|
||||||
lattice_maxNslipFamily
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
integer(pInt), intent(in) :: &
|
|
||||||
ipc, & !< component-ID of integration point
|
|
||||||
ip, & !< integration point
|
|
||||||
el !< element
|
|
||||||
integer(pInt) :: &
|
|
||||||
phase, &
|
|
||||||
constituent, &
|
|
||||||
sourceOffset, &
|
|
||||||
homog, damageOffset, &
|
|
||||||
instance, &
|
|
||||||
index, f, i
|
|
||||||
|
|
||||||
phase = phaseAt(ipc,ip,el)
|
|
||||||
constituent = phasememberAt(ipc,ip,el)
|
|
||||||
instance = source_damage_anisoDuctile_instance(phase)
|
|
||||||
sourceOffset = source_damage_anisoDuctile_offset(phase)
|
|
||||||
homog = material_homog(ip,el)
|
|
||||||
damageOffset = damageMapping(homog)%p(ip,el)
|
|
||||||
|
|
||||||
index = 1_pInt
|
|
||||||
sourceState(phase)%p(sourceOffset)%dotState(1,constituent) = 0.0_pReal
|
|
||||||
do f = 1_pInt,lattice_maxNslipFamily
|
|
||||||
do i = 1_pInt,source_damage_anisoDuctile_Nslip(f,instance) ! process each (active) slip system in family
|
|
||||||
sourceState(phase)%p(sourceOffset)%dotState(1,constituent) = &
|
|
||||||
sourceState(phase)%p(sourceOffset)%dotState(1,constituent) + &
|
|
||||||
plasticState(phase)%slipRate(index,constituent)/ &
|
|
||||||
((damage(homog)%p(damageOffset))**source_damage_anisoDuctile_N(instance))/ &
|
|
||||||
source_damage_anisoDuctile_critPlasticStrain(f,instance)
|
|
||||||
|
|
||||||
index = index + 1_pInt
|
|
||||||
enddo
|
|
||||||
enddo
|
|
||||||
|
|
||||||
end subroutine source_damage_anisoDuctile_dotState
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief returns local part of nonlocal damage driving force
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine source_damage_anisoDuctile_getRateAndItsTangent(localphiDot, dLocalphiDot_dPhi, phi, 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
|
|
||||||
real(pReal), intent(in) :: &
|
|
||||||
phi
|
|
||||||
real(pReal), intent(out) :: &
|
|
||||||
localphiDot, &
|
|
||||||
dLocalphiDot_dPhi
|
|
||||||
integer(pInt) :: &
|
|
||||||
phase, constituent, sourceOffset
|
|
||||||
|
|
||||||
phase = phaseAt(ipc,ip,el)
|
|
||||||
constituent = phasememberAt(ipc,ip,el)
|
|
||||||
sourceOffset = source_damage_anisoDuctile_offset(phase)
|
|
||||||
|
|
||||||
localphiDot = 1.0_pReal - &
|
|
||||||
sourceState(phase)%p(sourceOffset)%state(1,constituent)* &
|
|
||||||
phi
|
|
||||||
|
|
||||||
dLocalphiDot_dPhi = -sourceState(phase)%p(sourceOffset)%state(1,constituent)
|
|
||||||
|
|
||||||
end subroutine source_damage_anisoDuctile_getRateAndItsTangent
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief return array of local damage results
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
function source_damage_anisoDuctile_postResults(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
|
|
||||||
real(pReal), dimension(source_damage_anisoDuctile_sizePostResults( &
|
|
||||||
source_damage_anisoDuctile_instance(phaseAt(ipc,ip,el)))) :: &
|
|
||||||
source_damage_anisoDuctile_postResults
|
|
||||||
|
|
||||||
integer(pInt) :: &
|
|
||||||
instance, phase, constituent, sourceOffset, o, c
|
|
||||||
|
|
||||||
phase = phaseAt(ipc,ip,el)
|
|
||||||
constituent = phasememberAt(ipc,ip,el)
|
|
||||||
instance = source_damage_anisoDuctile_instance(phase)
|
|
||||||
sourceOffset = source_damage_anisoDuctile_offset(phase)
|
|
||||||
|
|
||||||
c = 0_pInt
|
|
||||||
source_damage_anisoDuctile_postResults = 0.0_pReal
|
|
||||||
|
|
||||||
do o = 1_pInt,source_damage_anisoDuctile_Noutput(instance)
|
|
||||||
select case(source_damage_anisoDuctile_outputID(o,instance))
|
|
||||||
case (damage_drivingforce_ID)
|
|
||||||
source_damage_anisoDuctile_postResults(c+1_pInt) = &
|
|
||||||
sourceState(phase)%p(sourceOffset)%state(1,constituent)
|
|
||||||
c = c + 1_pInt
|
|
||||||
|
|
||||||
end select
|
|
||||||
enddo
|
|
||||||
end function source_damage_anisoDuctile_postResults
|
|
||||||
|
|
||||||
end module source_damage_anisoDuctile
|
|
|
@ -1,383 +0,0 @@
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! $Id$
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @author Pratheek Shanthraj, Max-Planck-Institut für Eisenforschung GmbH
|
|
||||||
!> @author Luv Sharma, Max-Planck-Institut für Eisenforschung GmbH
|
|
||||||
!> @brief material subroutine incoprorating isotropic brittle damage source mechanism
|
|
||||||
!> @details to be done
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
module source_damage_isoBrittle
|
|
||||||
use prec, only: &
|
|
||||||
pReal, &
|
|
||||||
pInt
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
private
|
|
||||||
integer(pInt), dimension(:), allocatable, public, protected :: &
|
|
||||||
source_damage_isoBrittle_sizePostResults, & !< cumulative size of post results
|
|
||||||
source_damage_isoBrittle_offset, & !< which source is my current damage mechanism?
|
|
||||||
source_damage_isoBrittle_instance !< instance of damage source mechanism
|
|
||||||
|
|
||||||
integer(pInt), dimension(:,:), allocatable, target, public :: &
|
|
||||||
source_damage_isoBrittle_sizePostResult !< size of each post result output
|
|
||||||
|
|
||||||
character(len=64), dimension(:,:), allocatable, target, public :: &
|
|
||||||
source_damage_isoBrittle_output !< name of each post result output
|
|
||||||
|
|
||||||
integer(pInt), dimension(:), allocatable, target, public :: &
|
|
||||||
source_damage_isoBrittle_Noutput !< number of outputs per instance of this damage
|
|
||||||
|
|
||||||
real(pReal), dimension(:), allocatable, private :: &
|
|
||||||
source_damage_isoBrittle_aTol, &
|
|
||||||
source_damage_isoBrittle_N, &
|
|
||||||
source_damage_isoBrittle_critStrainEnergy
|
|
||||||
|
|
||||||
enum, bind(c)
|
|
||||||
enumerator :: undefined_ID, &
|
|
||||||
damage_drivingforce_ID
|
|
||||||
end enum !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!11 ToDo
|
|
||||||
|
|
||||||
integer(kind(undefined_ID)), dimension(:,:), allocatable, private :: &
|
|
||||||
source_damage_isoBrittle_outputID !< ID of each post result output
|
|
||||||
|
|
||||||
|
|
||||||
public :: &
|
|
||||||
source_damage_isoBrittle_init, &
|
|
||||||
source_damage_isoBrittle_deltaState, &
|
|
||||||
source_damage_isoBrittle_getRateAndItsTangent, &
|
|
||||||
source_damage_isoBrittle_postResults
|
|
||||||
|
|
||||||
contains
|
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief module initialization
|
|
||||||
!> @details reads in material parameters, allocates arrays, and does sanity checks
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine source_damage_isoBrittle_init(fileUnit)
|
|
||||||
use, intrinsic :: iso_fortran_env ! to get compiler_version and compiler_options (at least for gfortran 4.6 at the moment)
|
|
||||||
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_damage_isoBrittle_label, &
|
|
||||||
SOURCE_damage_isoBrittle_ID, &
|
|
||||||
material_Nphase, &
|
|
||||||
material_phase, &
|
|
||||||
sourceState, &
|
|
||||||
MATERIAL_partPhase
|
|
||||||
use numerics,only: &
|
|
||||||
analyticJaco, &
|
|
||||||
worldrank, &
|
|
||||||
numerics_integrator
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
integer(pInt), intent(in) :: fileUnit
|
|
||||||
|
|
||||||
integer(pInt), allocatable, dimension(:) :: chunkPos
|
|
||||||
integer(pInt) :: maxNinstance,mySize=0_pInt,phase,instance,source,sourceOffset,o
|
|
||||||
integer(pInt) :: sizeState, sizeDotState, sizeDeltaState
|
|
||||||
integer(pInt) :: NofMyPhase
|
|
||||||
character(len=65536) :: &
|
|
||||||
tag = '', &
|
|
||||||
line = ''
|
|
||||||
|
|
||||||
mainProcess: if (worldrank == 0) then
|
|
||||||
write(6,'(/,a)') ' <<<+- source_'//SOURCE_damage_isoBrittle_label//' init -+>>>'
|
|
||||||
write(6,'(a15,a)') ' Current time: ',IO_timeStamp()
|
|
||||||
#include "compilation_info.f90"
|
|
||||||
endif mainProcess
|
|
||||||
|
|
||||||
maxNinstance = int(count(phase_source == SOURCE_damage_isoBrittle_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_damage_isoBrittle_offset(material_Nphase), source=0_pInt)
|
|
||||||
allocate(source_damage_isoBrittle_instance(material_Nphase), source=0_pInt)
|
|
||||||
do phase = 1, material_Nphase
|
|
||||||
source_damage_isoBrittle_instance(phase) = count(phase_source(:,1:phase) == source_damage_isoBrittle_ID)
|
|
||||||
do source = 1, phase_Nsources(phase)
|
|
||||||
if (phase_source(source,phase) == source_damage_isoBrittle_ID) &
|
|
||||||
source_damage_isoBrittle_offset(phase) = source
|
|
||||||
enddo
|
|
||||||
enddo
|
|
||||||
|
|
||||||
allocate(source_damage_isoBrittle_sizePostResults(maxNinstance), source=0_pInt)
|
|
||||||
allocate(source_damage_isoBrittle_sizePostResult(maxval(phase_Noutput),maxNinstance),source=0_pInt)
|
|
||||||
allocate(source_damage_isoBrittle_output(maxval(phase_Noutput),maxNinstance))
|
|
||||||
source_damage_isoBrittle_output = ''
|
|
||||||
allocate(source_damage_isoBrittle_outputID(maxval(phase_Noutput),maxNinstance), source=undefined_ID)
|
|
||||||
allocate(source_damage_isoBrittle_Noutput(maxNinstance), source=0_pInt)
|
|
||||||
allocate(source_damage_isoBrittle_critStrainEnergy(maxNinstance), source=0.0_pReal)
|
|
||||||
allocate(source_damage_isoBrittle_N(maxNinstance), source=1.0_pReal)
|
|
||||||
allocate(source_damage_isoBrittle_aTol(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_damage_isoBrittle_ID)) then ! do not short-circuit here (.and. with next if statemen). It's not safe in Fortran
|
|
||||||
instance = source_damage_isoBrittle_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 ('(output)')
|
|
||||||
select case(IO_lc(IO_stringValue(line,chunkPos,2_pInt)))
|
|
||||||
case ('isobrittle_drivingforce')
|
|
||||||
source_damage_isoBrittle_Noutput(instance) = source_damage_isoBrittle_Noutput(instance) + 1_pInt
|
|
||||||
source_damage_isoBrittle_outputID(source_damage_isoBrittle_Noutput(instance),instance) = damage_drivingforce_ID
|
|
||||||
source_damage_isoBrittle_output(source_damage_isoBrittle_Noutput(instance),instance) = &
|
|
||||||
IO_lc(IO_stringValue(line,chunkPos,2_pInt))
|
|
||||||
end select
|
|
||||||
|
|
||||||
case ('isobrittle_criticalstrainenergy')
|
|
||||||
source_damage_isoBrittle_critStrainEnergy(instance) = IO_floatValue(line,chunkPos,2_pInt)
|
|
||||||
|
|
||||||
case ('isobrittle_n')
|
|
||||||
source_damage_isoBrittle_N(instance) = IO_floatValue(line,chunkPos,2_pInt)
|
|
||||||
|
|
||||||
case ('isobrittle_atol')
|
|
||||||
source_damage_isoBrittle_aTol(instance) = IO_floatValue(line,chunkPos,2_pInt)
|
|
||||||
|
|
||||||
end select
|
|
||||||
endif; endif
|
|
||||||
enddo parsingFile
|
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! sanity checks
|
|
||||||
sanityChecks: do phase = 1_pInt, material_Nphase
|
|
||||||
myPhase: if (any(phase_source(:,phase) == SOURCE_damage_isoBrittle_ID)) then
|
|
||||||
instance = source_damage_isoBrittle_instance(phase)
|
|
||||||
if (source_damage_isoBrittle_aTol(instance) < 0.0_pReal) &
|
|
||||||
source_damage_isoBrittle_aTol(instance) = 1.0e-3_pReal ! default absolute tolerance 1e-3
|
|
||||||
if (source_damage_isoBrittle_critStrainEnergy(instance) <= 0.0_pReal) &
|
|
||||||
call IO_error(211_pInt,el=instance,ext_msg='criticalStrainEnergy ('//SOURCE_damage_isoBrittle_LABEL//')')
|
|
||||||
endif myPhase
|
|
||||||
enddo sanityChecks
|
|
||||||
|
|
||||||
initializeInstances: do phase = 1_pInt, material_Nphase
|
|
||||||
if (any(phase_source(:,phase) == SOURCE_damage_isoBrittle_ID)) then
|
|
||||||
NofMyPhase=count(material_phase==phase)
|
|
||||||
instance = source_damage_isoBrittle_instance(phase)
|
|
||||||
sourceOffset = source_damage_isoBrittle_offset(phase)
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! Determine size of postResults array
|
|
||||||
outputsLoop: do o = 1_pInt,source_damage_isoBrittle_Noutput(instance)
|
|
||||||
select case(source_damage_isoBrittle_outputID(o,instance))
|
|
||||||
case(damage_drivingforce_ID)
|
|
||||||
mySize = 1_pInt
|
|
||||||
end select
|
|
||||||
|
|
||||||
if (mySize > 0_pInt) then ! any meaningful output found
|
|
||||||
source_damage_isoBrittle_sizePostResult(o,instance) = mySize
|
|
||||||
source_damage_isoBrittle_sizePostResults(instance) = source_damage_isoBrittle_sizePostResults(instance) + mySize
|
|
||||||
endif
|
|
||||||
enddo outputsLoop
|
|
||||||
! Determine size of state array
|
|
||||||
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_damage_isoBrittle_sizePostResults(instance)
|
|
||||||
allocate(sourceState(phase)%p(sourceOffset)%aTolState (sizeState), &
|
|
||||||
source=source_damage_isoBrittle_aTol(instance))
|
|
||||||
allocate(sourceState(phase)%p(sourceOffset)%state0 (sizeState,NofMyPhase), source=.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 (.not. analyticJaco) then
|
|
||||||
allocate(sourceState(phase)%p(sourceOffset)%state_backup (sizeState,NofMyPhase), source=0.0_pReal)
|
|
||||||
allocate(sourceState(phase)%p(sourceOffset)%dotState_backup (sizeDotState,NofMyPhase), source=0.0_pReal)
|
|
||||||
endif
|
|
||||||
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_damage_isoBrittle_init
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief calculates derived quantities from state
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine source_damage_isoBrittle_deltaState(C, Fe, ipc, ip, el)
|
|
||||||
use material, only: &
|
|
||||||
phaseAt, phasememberAt, &
|
|
||||||
sourceState, &
|
|
||||||
material_homog, &
|
|
||||||
phase_NstiffnessDegradations, &
|
|
||||||
phase_stiffnessDegradation, &
|
|
||||||
porosity, &
|
|
||||||
porosityMapping, &
|
|
||||||
STIFFNESS_DEGRADATION_porosity_ID
|
|
||||||
use math, only : &
|
|
||||||
math_mul33x33, &
|
|
||||||
math_mul66x6, &
|
|
||||||
math_Mandel33to6, &
|
|
||||||
math_transpose33, &
|
|
||||||
math_I3
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
integer(pInt), intent(in) :: &
|
|
||||||
ipc, & !< component-ID of integration point
|
|
||||||
ip, & !< integration point
|
|
||||||
el !< element
|
|
||||||
real(pReal), intent(in), dimension(3,3) :: &
|
|
||||||
Fe
|
|
||||||
real(pReal), intent(in), dimension(6,6) :: &
|
|
||||||
C
|
|
||||||
integer(pInt) :: &
|
|
||||||
phase, constituent, instance, sourceOffset, mech
|
|
||||||
real(pReal) :: &
|
|
||||||
strain(6), &
|
|
||||||
stiffness(6,6), &
|
|
||||||
strainenergy
|
|
||||||
|
|
||||||
phase = phaseAt(ipc,ip,el) !< phase ID at ipc,ip,el
|
|
||||||
constituent = phasememberAt(ipc,ip,el) !< state array offset for phase ID at ipc,ip,el
|
|
||||||
! ToDo: capability for multiple instances of SAME source within given phase. Needs Ninstance loop from here on!
|
|
||||||
instance = source_damage_isoBrittle_instance(phase) !< instance of damage_isoBrittle source
|
|
||||||
sourceOffset = source_damage_isoBrittle_offset(phase)
|
|
||||||
|
|
||||||
stiffness = C
|
|
||||||
do mech = 1_pInt, phase_NstiffnessDegradations(phase)
|
|
||||||
select case(phase_stiffnessDegradation(mech,phase))
|
|
||||||
case (STIFFNESS_DEGRADATION_porosity_ID)
|
|
||||||
stiffness = porosity(material_homog(ip,el))%p(porosityMapping(material_homog(ip,el))%p(ip,el))* &
|
|
||||||
porosity(material_homog(ip,el))%p(porosityMapping(material_homog(ip,el))%p(ip,el))* &
|
|
||||||
stiffness
|
|
||||||
end select
|
|
||||||
enddo
|
|
||||||
strain = 0.5_pReal*math_Mandel33to6(math_mul33x33(math_transpose33(Fe),Fe)-math_I3)
|
|
||||||
|
|
||||||
strainenergy = 2.0_pReal*sum(strain*math_mul66x6(stiffness,strain))/ &
|
|
||||||
source_damage_isoBrittle_critStrainEnergy(instance)
|
|
||||||
if (strainenergy > sourceState(phase)%p(sourceOffset)%subState0(1,constituent)) then
|
|
||||||
sourceState(phase)%p(sourceOffset)%deltaState(1,constituent) = &
|
|
||||||
strainenergy - sourceState(phase)%p(sourceOffset)%state(1,constituent)
|
|
||||||
else
|
|
||||||
sourceState(phase)%p(sourceOffset)%deltaState(1,constituent) = &
|
|
||||||
sourceState(phase)%p(sourceOffset)%subState0(1,constituent) - &
|
|
||||||
sourceState(phase)%p(sourceOffset)%state(1,constituent)
|
|
||||||
endif
|
|
||||||
|
|
||||||
end subroutine source_damage_isoBrittle_deltaState
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief returns local part of nonlocal damage driving force
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine source_damage_isoBrittle_getRateAndItsTangent(localphiDot, dLocalphiDot_dPhi, phi, 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
|
|
||||||
real(pReal), intent(in) :: &
|
|
||||||
phi
|
|
||||||
real(pReal), intent(out) :: &
|
|
||||||
localphiDot, &
|
|
||||||
dLocalphiDot_dPhi
|
|
||||||
integer(pInt) :: &
|
|
||||||
phase, constituent, instance, sourceOffset
|
|
||||||
|
|
||||||
phase = phaseAt(ipc,ip,el)
|
|
||||||
constituent = phasememberAt(ipc,ip,el)
|
|
||||||
instance = source_damage_isoBrittle_instance(phase)
|
|
||||||
sourceOffset = source_damage_isoBrittle_offset(phase)
|
|
||||||
|
|
||||||
localphiDot = (1.0_pReal - phi)**(source_damage_isoBrittle_N(instance) - 1.0_pReal) - &
|
|
||||||
phi*sourceState(phase)%p(sourceOffset)%state(1,constituent)
|
|
||||||
dLocalphiDot_dPhi = - (source_damage_isoBrittle_N(instance) - 1.0_pReal)* &
|
|
||||||
(1.0_pReal - phi)**max(0.0_pReal,source_damage_isoBrittle_N(instance) - 2.0_pReal) &
|
|
||||||
- sourceState(phase)%p(sourceOffset)%state(1,constituent)
|
|
||||||
|
|
||||||
end subroutine source_damage_isoBrittle_getRateAndItsTangent
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief return array of local damage results
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
function source_damage_isoBrittle_postResults(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
|
|
||||||
real(pReal), dimension(source_damage_isoBrittle_sizePostResults( &
|
|
||||||
source_damage_isoBrittle_instance(phaseAt(ipc,ip,el)))) :: &
|
|
||||||
source_damage_isoBrittle_postResults
|
|
||||||
|
|
||||||
integer(pInt) :: &
|
|
||||||
instance, phase, constituent, sourceOffset, o, c
|
|
||||||
|
|
||||||
phase = phaseAt(ipc,ip,el)
|
|
||||||
constituent = phasememberAt(ipc,ip,el)
|
|
||||||
instance = source_damage_isoBrittle_instance(phase)
|
|
||||||
sourceOffset = source_damage_isoBrittle_offset(phase)
|
|
||||||
|
|
||||||
c = 0_pInt
|
|
||||||
source_damage_isoBrittle_postResults = 0.0_pReal
|
|
||||||
|
|
||||||
do o = 1_pInt,source_damage_isoBrittle_Noutput(instance)
|
|
||||||
select case(source_damage_isoBrittle_outputID(o,instance))
|
|
||||||
case (damage_drivingforce_ID)
|
|
||||||
source_damage_isoBrittle_postResults(c+1_pInt) = sourceState(phase)%p(sourceOffset)%state(1,constituent)
|
|
||||||
c = c + 1
|
|
||||||
|
|
||||||
end select
|
|
||||||
enddo
|
|
||||||
end function source_damage_isoBrittle_postResults
|
|
||||||
|
|
||||||
end module source_damage_isoBrittle
|
|
|
@ -1,350 +0,0 @@
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! $Id$
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @author Pratheek Shanthraj, Max-Planck-Institut fŸr Eisenforschung GmbH
|
|
||||||
!> @author Luv Sharma, Max-Planck-Institut fŸr Eisenforschung GmbH
|
|
||||||
!> @brief material subroutine incoprorating isotropic ductile damage source mechanism
|
|
||||||
!> @details to be done
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
module source_damage_isoDuctile
|
|
||||||
use prec, only: &
|
|
||||||
pReal, &
|
|
||||||
pInt
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
private
|
|
||||||
integer(pInt), dimension(:), allocatable, public, protected :: &
|
|
||||||
source_damage_isoDuctile_sizePostResults, & !< cumulative size of post results
|
|
||||||
source_damage_isoDuctile_offset, & !< which source is my current damage mechanism?
|
|
||||||
source_damage_isoDuctile_instance !< instance of damage source mechanism
|
|
||||||
|
|
||||||
integer(pInt), dimension(:,:), allocatable, target, public :: &
|
|
||||||
source_damage_isoDuctile_sizePostResult !< size of each post result output
|
|
||||||
|
|
||||||
character(len=64), dimension(:,:), allocatable, target, public :: &
|
|
||||||
source_damage_isoDuctile_output !< name of each post result output
|
|
||||||
|
|
||||||
integer(pInt), dimension(:), allocatable, target, public :: &
|
|
||||||
source_damage_isoDuctile_Noutput !< number of outputs per instance of this damage
|
|
||||||
|
|
||||||
real(pReal), dimension(:), allocatable, private :: &
|
|
||||||
source_damage_isoDuctile_aTol, &
|
|
||||||
source_damage_isoDuctile_critPlasticStrain, &
|
|
||||||
source_damage_isoDuctile_N
|
|
||||||
|
|
||||||
enum, bind(c)
|
|
||||||
enumerator :: undefined_ID, &
|
|
||||||
damage_drivingforce_ID
|
|
||||||
end enum !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!11 ToDo
|
|
||||||
|
|
||||||
integer(kind(undefined_ID)), dimension(:,:), allocatable, private :: &
|
|
||||||
source_damage_isoDuctile_outputID !< ID of each post result output
|
|
||||||
|
|
||||||
|
|
||||||
public :: &
|
|
||||||
source_damage_isoDuctile_init, &
|
|
||||||
source_damage_isoDuctile_dotState, &
|
|
||||||
source_damage_isoDuctile_getRateAndItsTangent, &
|
|
||||||
source_damage_isoDuctile_postResults
|
|
||||||
|
|
||||||
contains
|
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief module initialization
|
|
||||||
!> @details reads in material parameters, allocates arrays, and does sanity checks
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine source_damage_isoDuctile_init(fileUnit)
|
|
||||||
use, intrinsic :: iso_fortran_env ! to get compiler_version and compiler_options (at least for gfortran 4.6 at the moment)
|
|
||||||
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_damage_isoDuctile_label, &
|
|
||||||
SOURCE_damage_isoDuctile_ID, &
|
|
||||||
material_Nphase, &
|
|
||||||
material_phase, &
|
|
||||||
sourceState, &
|
|
||||||
MATERIAL_partPhase
|
|
||||||
use numerics,only: &
|
|
||||||
analyticJaco, &
|
|
||||||
worldrank, &
|
|
||||||
numerics_integrator
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
integer(pInt), intent(in) :: fileUnit
|
|
||||||
|
|
||||||
integer(pInt), allocatable, dimension(:) :: chunkPos
|
|
||||||
integer(pInt) :: maxNinstance,mySize=0_pInt,phase,instance,source,sourceOffset,o
|
|
||||||
integer(pInt) :: sizeState, sizeDotState, sizeDeltaState
|
|
||||||
integer(pInt) :: NofMyPhase
|
|
||||||
character(len=65536) :: &
|
|
||||||
tag = '', &
|
|
||||||
line = ''
|
|
||||||
|
|
||||||
mainProcess: if (worldrank == 0) then
|
|
||||||
write(6,'(/,a)') ' <<<+- source_'//SOURCE_damage_isoDuctile_label//' init -+>>>'
|
|
||||||
write(6,'(a15,a)') ' Current time: ',IO_timeStamp()
|
|
||||||
#include "compilation_info.f90"
|
|
||||||
endif mainProcess
|
|
||||||
|
|
||||||
maxNinstance = int(count(phase_source == SOURCE_damage_isoDuctile_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_damage_isoDuctile_offset(material_Nphase), source=0_pInt)
|
|
||||||
allocate(source_damage_isoDuctile_instance(material_Nphase), source=0_pInt)
|
|
||||||
do phase = 1, material_Nphase
|
|
||||||
source_damage_isoDuctile_instance(phase) = count(phase_source(:,1:phase) == source_damage_isoDuctile_ID)
|
|
||||||
do source = 1, phase_Nsources(phase)
|
|
||||||
if (phase_source(source,phase) == source_damage_isoDuctile_ID) &
|
|
||||||
source_damage_isoDuctile_offset(phase) = source
|
|
||||||
enddo
|
|
||||||
enddo
|
|
||||||
|
|
||||||
allocate(source_damage_isoDuctile_sizePostResults(maxNinstance), source=0_pInt)
|
|
||||||
allocate(source_damage_isoDuctile_sizePostResult(maxval(phase_Noutput),maxNinstance),source=0_pInt)
|
|
||||||
allocate(source_damage_isoDuctile_output(maxval(phase_Noutput),maxNinstance))
|
|
||||||
source_damage_isoDuctile_output = ''
|
|
||||||
allocate(source_damage_isoDuctile_outputID(maxval(phase_Noutput),maxNinstance), source=undefined_ID)
|
|
||||||
allocate(source_damage_isoDuctile_Noutput(maxNinstance), source=0_pInt)
|
|
||||||
allocate(source_damage_isoDuctile_critPlasticStrain(maxNinstance), source=0.0_pReal)
|
|
||||||
allocate(source_damage_isoDuctile_N(maxNinstance), source=0.0_pReal)
|
|
||||||
allocate(source_damage_isoDuctile_aTol(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_damage_isoDuctile_ID)) then ! do not short-circuit here (.and. with next if statemen). It's not safe in Fortran
|
|
||||||
instance = source_damage_isoDuctile_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 ('(output)')
|
|
||||||
select case(IO_lc(IO_stringValue(line,chunkPos,2_pInt)))
|
|
||||||
case ('isoductile_drivingforce')
|
|
||||||
source_damage_isoDuctile_Noutput(instance) = source_damage_isoDuctile_Noutput(instance) + 1_pInt
|
|
||||||
source_damage_isoDuctile_outputID(source_damage_isoDuctile_Noutput(instance),instance) = damage_drivingforce_ID
|
|
||||||
source_damage_isoDuctile_output(source_damage_isoDuctile_Noutput(instance),instance) = &
|
|
||||||
IO_lc(IO_stringValue(line,chunkPos,2_pInt))
|
|
||||||
end select
|
|
||||||
|
|
||||||
case ('isoductile_criticalplasticstrain')
|
|
||||||
source_damage_isoDuctile_critPlasticStrain(instance) = IO_floatValue(line,chunkPos,2_pInt)
|
|
||||||
|
|
||||||
case ('isoductile_ratesensitivity')
|
|
||||||
source_damage_isoDuctile_N(instance) = IO_floatValue(line,chunkPos,2_pInt)
|
|
||||||
|
|
||||||
case ('isoductile_atol')
|
|
||||||
source_damage_isoDuctile_aTol(instance) = IO_floatValue(line,chunkPos,2_pInt)
|
|
||||||
|
|
||||||
end select
|
|
||||||
endif; endif
|
|
||||||
enddo parsingFile
|
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! sanity checks
|
|
||||||
sanityChecks: do phase = 1_pInt, material_Nphase
|
|
||||||
myPhase: if (any(phase_source(:,phase) == SOURCE_damage_isoDuctile_ID)) then
|
|
||||||
instance = source_damage_isoDuctile_instance(phase)
|
|
||||||
if (source_damage_isoDuctile_aTol(instance) < 0.0_pReal) &
|
|
||||||
source_damage_isoDuctile_aTol(instance) = 1.0e-3_pReal ! default absolute tolerance 1e-3
|
|
||||||
if (source_damage_isoDuctile_critPlasticStrain(instance) <= 0.0_pReal) &
|
|
||||||
call IO_error(211_pInt,el=instance,ext_msg='critical plastic strain ('//SOURCE_damage_isoDuctile_LABEL//')')
|
|
||||||
endif myPhase
|
|
||||||
enddo sanityChecks
|
|
||||||
|
|
||||||
initializeInstances: do phase = 1_pInt, material_Nphase
|
|
||||||
if (any(phase_source(:,phase) == SOURCE_damage_isoDuctile_ID)) then
|
|
||||||
NofMyPhase=count(material_phase==phase)
|
|
||||||
instance = source_damage_isoDuctile_instance(phase)
|
|
||||||
sourceOffset = source_damage_isoDuctile_offset(phase)
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! Determine size of postResults array
|
|
||||||
outputsLoop: do o = 1_pInt,source_damage_isoDuctile_Noutput(instance)
|
|
||||||
select case(source_damage_isoDuctile_outputID(o,instance))
|
|
||||||
case(damage_drivingforce_ID)
|
|
||||||
mySize = 1_pInt
|
|
||||||
end select
|
|
||||||
|
|
||||||
if (mySize > 0_pInt) then ! any meaningful output found
|
|
||||||
source_damage_isoDuctile_sizePostResult(o,instance) = mySize
|
|
||||||
source_damage_isoDuctile_sizePostResults(instance) = source_damage_isoDuctile_sizePostResults(instance) + mySize
|
|
||||||
endif
|
|
||||||
enddo outputsLoop
|
|
||||||
! Determine size of state array
|
|
||||||
sizeDotState = 1_pInt
|
|
||||||
sizeDeltaState = 0_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_damage_isoDuctile_sizePostResults(instance)
|
|
||||||
allocate(sourceState(phase)%p(sourceOffset)%aTolState (sizeState), &
|
|
||||||
source=source_damage_isoDuctile_aTol(instance))
|
|
||||||
allocate(sourceState(phase)%p(sourceOffset)%state0 (sizeState,NofMyPhase), source=.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 (.not. analyticJaco) then
|
|
||||||
allocate(sourceState(phase)%p(sourceOffset)%state_backup (sizeState,NofMyPhase), source=0.0_pReal)
|
|
||||||
allocate(sourceState(phase)%p(sourceOffset)%dotState_backup (sizeDotState,NofMyPhase), source=0.0_pReal)
|
|
||||||
endif
|
|
||||||
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_damage_isoDuctile_init
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief calculates derived quantities from state
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine source_damage_isoDuctile_dotState(ipc, ip, el)
|
|
||||||
use material, only: &
|
|
||||||
phaseAt, phasememberAt, &
|
|
||||||
plasticState, &
|
|
||||||
sourceState, &
|
|
||||||
material_homog, &
|
|
||||||
damage, &
|
|
||||||
damageMapping
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
integer(pInt), intent(in) :: &
|
|
||||||
ipc, & !< component-ID of integration point
|
|
||||||
ip, & !< integration point
|
|
||||||
el !< element
|
|
||||||
integer(pInt) :: &
|
|
||||||
phase, constituent, instance, homog, sourceOffset, damageOffset
|
|
||||||
|
|
||||||
phase = phaseAt(ipc,ip,el)
|
|
||||||
constituent = phasememberAt(ipc,ip,el)
|
|
||||||
instance = source_damage_isoDuctile_instance(phase)
|
|
||||||
sourceOffset = source_damage_isoDuctile_offset(phase)
|
|
||||||
homog = material_homog(ip,el)
|
|
||||||
damageOffset = damageMapping(homog)%p(ip,el)
|
|
||||||
|
|
||||||
sourceState(phase)%p(sourceOffset)%dotState(1,constituent) = &
|
|
||||||
sum(plasticState(phase)%slipRate(:,constituent))/ &
|
|
||||||
((damage(homog)%p(damageOffset))**source_damage_isoDuctile_N(instance))/ &
|
|
||||||
source_damage_isoDuctile_critPlasticStrain(instance)
|
|
||||||
|
|
||||||
end subroutine source_damage_isoDuctile_dotState
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief returns local part of nonlocal damage driving force
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine source_damage_isoDuctile_getRateAndItsTangent(localphiDot, dLocalphiDot_dPhi, phi, 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
|
|
||||||
real(pReal), intent(in) :: &
|
|
||||||
phi
|
|
||||||
real(pReal), intent(out) :: &
|
|
||||||
localphiDot, &
|
|
||||||
dLocalphiDot_dPhi
|
|
||||||
integer(pInt) :: &
|
|
||||||
phase, constituent, sourceOffset
|
|
||||||
|
|
||||||
phase = phaseAt(ipc,ip,el)
|
|
||||||
constituent = phasememberAt(ipc,ip,el)
|
|
||||||
sourceOffset = source_damage_isoDuctile_offset(phase)
|
|
||||||
|
|
||||||
localphiDot = 1.0_pReal - &
|
|
||||||
sourceState(phase)%p(sourceOffset)%state(1,constituent)* &
|
|
||||||
phi
|
|
||||||
|
|
||||||
dLocalphiDot_dPhi = -sourceState(phase)%p(sourceOffset)%state(1,constituent)
|
|
||||||
|
|
||||||
end subroutine source_damage_isoDuctile_getRateAndItsTangent
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief return array of local damage results
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
function source_damage_isoDuctile_postResults(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
|
|
||||||
real(pReal), dimension(source_damage_isoDuctile_sizePostResults( &
|
|
||||||
source_damage_isoDuctile_instance(phaseAt(ipc,ip,el)))) :: &
|
|
||||||
source_damage_isoDuctile_postResults
|
|
||||||
|
|
||||||
integer(pInt) :: &
|
|
||||||
instance, phase, constituent, sourceOffset, o, c
|
|
||||||
|
|
||||||
phase = phaseAt(ipc,ip,el)
|
|
||||||
constituent = phasememberAt(ipc,ip,el)
|
|
||||||
instance = source_damage_isoDuctile_instance(phase)
|
|
||||||
sourceOffset = source_damage_isoDuctile_offset(phase)
|
|
||||||
|
|
||||||
c = 0_pInt
|
|
||||||
source_damage_isoDuctile_postResults = 0.0_pReal
|
|
||||||
|
|
||||||
do o = 1_pInt,source_damage_isoDuctile_Noutput(instance)
|
|
||||||
select case(source_damage_isoDuctile_outputID(o,instance))
|
|
||||||
case (damage_drivingforce_ID)
|
|
||||||
source_damage_isoDuctile_postResults(c+1_pInt) = sourceState(phase)%p(sourceOffset)%state(1,constituent)
|
|
||||||
c = c + 1
|
|
||||||
|
|
||||||
end select
|
|
||||||
enddo
|
|
||||||
end function source_damage_isoDuctile_postResults
|
|
||||||
|
|
||||||
end module source_damage_isoDuctile
|
|
|
@ -1,220 +0,0 @@
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! $Id$
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @author Pratheek Shanthraj, Max-Planck-Institut für Eisenforschung GmbH
|
|
||||||
!> @brief material subroutine for thermal source due to plastic dissipation
|
|
||||||
!> @details to be done
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
module source_thermal_dissipation
|
|
||||||
use prec, only: &
|
|
||||||
pReal, &
|
|
||||||
pInt
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
private
|
|
||||||
integer(pInt), dimension(:), allocatable, public, protected :: &
|
|
||||||
source_thermal_dissipation_sizePostResults, & !< cumulative size of post results
|
|
||||||
source_thermal_dissipation_offset, & !< which source is my current thermal dissipation mechanism?
|
|
||||||
source_thermal_dissipation_instance !< instance of thermal dissipation source mechanism
|
|
||||||
|
|
||||||
integer(pInt), dimension(:,:), allocatable, target, public :: &
|
|
||||||
source_thermal_dissipation_sizePostResult !< size of each post result output
|
|
||||||
|
|
||||||
character(len=64), dimension(:,:), allocatable, target, public :: &
|
|
||||||
source_thermal_dissipation_output !< name of each post result output
|
|
||||||
|
|
||||||
integer(pInt), dimension(:), allocatable, target, public :: &
|
|
||||||
source_thermal_dissipation_Noutput !< number of outputs per instance of this source
|
|
||||||
|
|
||||||
real(pReal), dimension(:), allocatable, private :: &
|
|
||||||
source_thermal_dissipation_coldworkCoeff
|
|
||||||
|
|
||||||
public :: &
|
|
||||||
source_thermal_dissipation_init, &
|
|
||||||
source_thermal_dissipation_getRateAndItsTangent
|
|
||||||
|
|
||||||
contains
|
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief module initialization
|
|
||||||
!> @details reads in material parameters, allocates arrays, and does sanity checks
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine source_thermal_dissipation_init(fileUnit)
|
|
||||||
use, intrinsic :: iso_fortran_env ! to get compiler_version and compiler_options (at least for gfortran 4.6 at the moment)
|
|
||||||
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_thermal_dissipation_label, &
|
|
||||||
SOURCE_thermal_dissipation_ID, &
|
|
||||||
material_Nphase, &
|
|
||||||
material_phase, &
|
|
||||||
sourceState, &
|
|
||||||
MATERIAL_partPhase
|
|
||||||
use numerics,only: &
|
|
||||||
analyticJaco, &
|
|
||||||
worldrank, &
|
|
||||||
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 = ''
|
|
||||||
|
|
||||||
mainProcess: if (worldrank == 0) then
|
|
||||||
write(6,'(/,a)') ' <<<+- source_'//SOURCE_thermal_dissipation_label//' init -+>>>'
|
|
||||||
write(6,'(a15,a)') ' Current time: ',IO_timeStamp()
|
|
||||||
#include "compilation_info.f90"
|
|
||||||
endif mainProcess
|
|
||||||
|
|
||||||
maxNinstance = int(count(phase_source == SOURCE_thermal_dissipation_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_thermal_dissipation_offset(material_Nphase), source=0_pInt)
|
|
||||||
allocate(source_thermal_dissipation_instance(material_Nphase), source=0_pInt)
|
|
||||||
do phase = 1, material_Nphase
|
|
||||||
source_thermal_dissipation_instance(phase) = count(phase_source(:,1:phase) == SOURCE_thermal_dissipation_ID)
|
|
||||||
do source = 1, phase_Nsources(phase)
|
|
||||||
if (phase_source(source,phase) == SOURCE_thermal_dissipation_ID) &
|
|
||||||
source_thermal_dissipation_offset(phase) = source
|
|
||||||
enddo
|
|
||||||
enddo
|
|
||||||
|
|
||||||
allocate(source_thermal_dissipation_sizePostResults(maxNinstance), source=0_pInt)
|
|
||||||
allocate(source_thermal_dissipation_sizePostResult(maxval(phase_Noutput),maxNinstance),source=0_pInt)
|
|
||||||
allocate(source_thermal_dissipation_output (maxval(phase_Noutput),maxNinstance))
|
|
||||||
source_thermal_dissipation_output = ''
|
|
||||||
allocate(source_thermal_dissipation_Noutput(maxNinstance), source=0_pInt)
|
|
||||||
allocate(source_thermal_dissipation_coldworkCoeff(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_thermal_dissipation_ID)) then ! do not short-circuit here (.and. with next if statemen). It's not safe in Fortran
|
|
||||||
|
|
||||||
instance = source_thermal_dissipation_instance(phase) ! which instance of my source is present phase
|
|
||||||
chunkPos = IO_stringPos(line)
|
|
||||||
tag = IO_lc(IO_stringValue(line,chunkPos,1_pInt)) ! extract key
|
|
||||||
select case(tag)
|
|
||||||
case ('dissipation_coldworkcoeff')
|
|
||||||
source_thermal_dissipation_coldworkCoeff(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_thermal_dissipation_ID)) then
|
|
||||||
NofMyPhase=count(material_phase==phase)
|
|
||||||
instance = source_thermal_dissipation_instance(phase)
|
|
||||||
sourceOffset = source_thermal_dissipation_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_thermal_dissipation_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 (.not. analyticJaco) then
|
|
||||||
allocate(sourceState(phase)%p(sourceOffset)%state_backup (sizeState,NofMyPhase), source=0.0_pReal)
|
|
||||||
allocate(sourceState(phase)%p(sourceOffset)%dotState_backup (sizeDotState,NofMyPhase), source=0.0_pReal)
|
|
||||||
endif
|
|
||||||
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_thermal_dissipation_init
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief returns local vacancy generation rate
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine source_thermal_dissipation_getRateAndItsTangent(TDot, dTDOT_dT, Tstar_v, Lp, ipc, ip, el)
|
|
||||||
use math, only: &
|
|
||||||
math_Mandel6to33
|
|
||||||
use material, only: &
|
|
||||||
phaseAt, phasememberAt
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
integer(pInt), intent(in) :: &
|
|
||||||
ipc, & !< grain number
|
|
||||||
ip, & !< integration point number
|
|
||||||
el !< element number
|
|
||||||
real(pReal), intent(in), dimension(6) :: &
|
|
||||||
Tstar_v !< 2nd Piola Kirchhoff stress tensor (Mandel)
|
|
||||||
real(pReal), intent(in), dimension(3,3) :: &
|
|
||||||
Lp
|
|
||||||
real(pReal), intent(out) :: &
|
|
||||||
TDot, &
|
|
||||||
dTDOT_dT
|
|
||||||
integer(pInt) :: &
|
|
||||||
instance, phase, constituent
|
|
||||||
|
|
||||||
phase = phaseAt(ipc,ip,el)
|
|
||||||
constituent = phasememberAt(ipc,ip,el)
|
|
||||||
instance = source_thermal_dissipation_instance(phase)
|
|
||||||
|
|
||||||
TDot = source_thermal_dissipation_coldworkCoeff(instance)* &
|
|
||||||
sum(abs(math_Mandel6to33(Tstar_v)*Lp))
|
|
||||||
dTDOT_dT = 0.0_pReal
|
|
||||||
|
|
||||||
end subroutine source_thermal_dissipation_getRateAndItsTangent
|
|
||||||
|
|
||||||
end module source_thermal_dissipation
|
|
|
@ -1,277 +0,0 @@
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! $Id$
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @author Pratheek Shanthraj, Max-Planck-Institut für Eisenforschung GmbH
|
|
||||||
!> @brief material subroutine for thermal source due to plastic dissipation
|
|
||||||
!> @details to be done
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
module source_thermal_externalheat
|
|
||||||
use prec, only: &
|
|
||||||
pReal, &
|
|
||||||
pInt
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
private
|
|
||||||
integer(pInt), dimension(:), allocatable, public, protected :: &
|
|
||||||
source_thermal_externalheat_sizePostResults, & !< cumulative size of post results
|
|
||||||
source_thermal_externalheat_offset, & !< which source is my current thermal dissipation mechanism?
|
|
||||||
source_thermal_externalheat_instance !< instance of thermal dissipation source mechanism
|
|
||||||
|
|
||||||
integer(pInt), dimension(:,:), allocatable, target, public :: &
|
|
||||||
source_thermal_externalheat_sizePostResult !< size of each post result output
|
|
||||||
|
|
||||||
character(len=64), dimension(:,:), allocatable, target, public :: &
|
|
||||||
source_thermal_externalheat_output !< name of each post result output
|
|
||||||
|
|
||||||
integer(pInt), dimension(:), allocatable, target, public :: &
|
|
||||||
source_thermal_externalheat_Noutput !< number of outputs per instance of this source
|
|
||||||
|
|
||||||
integer(pInt), dimension(:), allocatable, private :: &
|
|
||||||
source_thermal_externalheat_nIntervals
|
|
||||||
|
|
||||||
real(pReal), dimension(:,:), allocatable, private :: &
|
|
||||||
source_thermal_externalheat_time, &
|
|
||||||
source_thermal_externalheat_rate
|
|
||||||
|
|
||||||
public :: &
|
|
||||||
source_thermal_externalheat_init, &
|
|
||||||
source_thermal_externalheat_dotState, &
|
|
||||||
source_thermal_externalheat_getRateAndItsTangent
|
|
||||||
|
|
||||||
contains
|
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief module initialization
|
|
||||||
!> @details reads in material parameters, allocates arrays, and does sanity checks
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine source_thermal_externalheat_init(fileUnit)
|
|
||||||
use, intrinsic :: iso_fortran_env ! to get compiler_version and compiler_options (at least for gfortran 4.6 at the moment)
|
|
||||||
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_thermal_externalheat_label, &
|
|
||||||
SOURCE_thermal_externalheat_ID, &
|
|
||||||
material_Nphase, &
|
|
||||||
material_phase, &
|
|
||||||
sourceState, &
|
|
||||||
MATERIAL_partPhase
|
|
||||||
use numerics,only: &
|
|
||||||
analyticJaco, &
|
|
||||||
worldrank, &
|
|
||||||
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,interval
|
|
||||||
character(len=65536) :: &
|
|
||||||
tag = '', &
|
|
||||||
line = ''
|
|
||||||
real(pReal), allocatable, dimension(:,:) :: temp_time, temp_rate
|
|
||||||
|
|
||||||
mainProcess: if (worldrank == 0) then
|
|
||||||
write(6,'(/,a)') ' <<<+- source_'//SOURCE_thermal_externalheat_label//' init -+>>>'
|
|
||||||
write(6,'(a15,a)') ' Current time: ',IO_timeStamp()
|
|
||||||
#include "compilation_info.f90"
|
|
||||||
endif mainProcess
|
|
||||||
|
|
||||||
maxNinstance = int(count(phase_source == SOURCE_thermal_externalheat_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_thermal_externalheat_offset(material_Nphase), source=0_pInt)
|
|
||||||
allocate(source_thermal_externalheat_instance(material_Nphase), source=0_pInt)
|
|
||||||
do phase = 1, material_Nphase
|
|
||||||
source_thermal_externalheat_instance(phase) = count(phase_source(:,1:phase) == SOURCE_thermal_externalheat_ID)
|
|
||||||
do source = 1, phase_Nsources(phase)
|
|
||||||
if (phase_source(source,phase) == SOURCE_thermal_externalheat_ID) &
|
|
||||||
source_thermal_externalheat_offset(phase) = source
|
|
||||||
enddo
|
|
||||||
enddo
|
|
||||||
|
|
||||||
allocate(source_thermal_externalheat_sizePostResults(maxNinstance), source=0_pInt)
|
|
||||||
allocate(source_thermal_externalheat_sizePostResult(maxval(phase_Noutput),maxNinstance),source=0_pInt)
|
|
||||||
allocate(source_thermal_externalheat_output (maxval(phase_Noutput),maxNinstance))
|
|
||||||
source_thermal_externalheat_output = ''
|
|
||||||
allocate(source_thermal_externalheat_Noutput(maxNinstance), source=0_pInt)
|
|
||||||
allocate(source_thermal_externalheat_nIntervals(maxNinstance), source=0_pInt)
|
|
||||||
|
|
||||||
allocate(temp_time(maxNinstance,1000), source=0.0_pReal)
|
|
||||||
allocate(temp_rate(maxNinstance,1000), 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_thermal_externalheat_ID)) then ! do not short-circuit here (.and. with next if statemen). It's not safe in Fortran
|
|
||||||
|
|
||||||
instance = source_thermal_externalheat_instance(phase) ! which instance of my source is present phase
|
|
||||||
chunkPos = IO_stringPos(line)
|
|
||||||
tag = IO_lc(IO_stringValue(line,chunkPos,1_pInt)) ! extract key
|
|
||||||
select case(tag)
|
|
||||||
case ('externalheat_time')
|
|
||||||
if (chunkPos(1) <= 2_pInt) &
|
|
||||||
call IO_error(150_pInt,ext_msg=trim(tag)//' ('//SOURCE_thermal_externalheat_label//')')
|
|
||||||
source_thermal_externalheat_nIntervals(instance) = chunkPos(1) - 2_pInt
|
|
||||||
do interval = 1, source_thermal_externalheat_nIntervals(instance) + 1_pInt
|
|
||||||
temp_time(instance, interval) = IO_floatValue(line,chunkPos,1_pInt + interval)
|
|
||||||
enddo
|
|
||||||
|
|
||||||
case ('externalheat_rate')
|
|
||||||
do interval = 1, source_thermal_externalheat_nIntervals(instance) + 1_pInt
|
|
||||||
temp_rate(instance, interval) = IO_floatValue(line,chunkPos,1_pInt + interval)
|
|
||||||
enddo
|
|
||||||
|
|
||||||
end select
|
|
||||||
endif; endif
|
|
||||||
enddo parsingFile
|
|
||||||
|
|
||||||
allocate(source_thermal_externalheat_time(maxNinstance,maxval(source_thermal_externalheat_nIntervals)+1_pInt), source=0.0_pReal)
|
|
||||||
allocate(source_thermal_externalheat_rate(maxNinstance,maxval(source_thermal_externalheat_nIntervals)+1_pInt), source=0.0_pReal)
|
|
||||||
|
|
||||||
initializeInstances: do phase = 1_pInt, material_Nphase
|
|
||||||
if (any(phase_source(:,phase) == SOURCE_thermal_externalheat_ID)) then
|
|
||||||
NofMyPhase=count(material_phase==phase)
|
|
||||||
instance = source_thermal_externalheat_instance(phase)
|
|
||||||
sourceOffset = source_thermal_externalheat_offset(phase)
|
|
||||||
source_thermal_externalheat_time(instance,1:source_thermal_externalheat_nIntervals(instance)+1_pInt) = &
|
|
||||||
temp_time(instance,1:source_thermal_externalheat_nIntervals(instance)+1_pInt)
|
|
||||||
source_thermal_externalheat_rate(instance,1:source_thermal_externalheat_nIntervals(instance)+1_pInt) = &
|
|
||||||
temp_rate(instance,1:source_thermal_externalheat_nIntervals(instance)+1_pInt)
|
|
||||||
|
|
||||||
sizeDotState = 1_pInt
|
|
||||||
sizeDeltaState = 0_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_thermal_externalheat_sizePostResults(instance)
|
|
||||||
allocate(sourceState(phase)%p(sourceOffset)%aTolState (sizeState), source=0.00001_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 (.not. analyticJaco) then
|
|
||||||
allocate(sourceState(phase)%p(sourceOffset)%state_backup (sizeState,NofMyPhase), source=0.0_pReal)
|
|
||||||
allocate(sourceState(phase)%p(sourceOffset)%dotState_backup (sizeDotState,NofMyPhase), source=0.0_pReal)
|
|
||||||
endif
|
|
||||||
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_thermal_externalheat_init
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief calculates derived quantities from state
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine source_thermal_externalheat_dotState(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
|
|
||||||
|
|
||||||
phase = phaseAt(ipc,ip,el)
|
|
||||||
constituent = phasememberAt(ipc,ip,el)
|
|
||||||
sourceOffset = source_thermal_externalheat_offset(phase)
|
|
||||||
|
|
||||||
sourceState(phase)%p(sourceOffset)%dotState(1,constituent) = 1.0_pReal
|
|
||||||
|
|
||||||
end subroutine source_thermal_externalheat_dotState
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief returns local vacancy generation rate
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine source_thermal_externalheat_getRateAndItsTangent(TDot, dTDot_dT, 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) :: &
|
|
||||||
TDot, &
|
|
||||||
dTDot_dT
|
|
||||||
integer(pInt) :: &
|
|
||||||
instance, phase, constituent, sourceOffset, interval
|
|
||||||
real(pReal) :: &
|
|
||||||
norm_time
|
|
||||||
|
|
||||||
phase = phaseAt(ipc,ip,el)
|
|
||||||
constituent = phasememberAt(ipc,ip,el)
|
|
||||||
instance = source_thermal_externalheat_instance(phase)
|
|
||||||
sourceOffset = source_thermal_externalheat_offset(phase)
|
|
||||||
|
|
||||||
do interval = 1, source_thermal_externalheat_nIntervals(instance)
|
|
||||||
norm_time = (sourceState(phase)%p(sourceOffset)%state(1,constituent) - &
|
|
||||||
source_thermal_externalheat_time(instance,interval)) / &
|
|
||||||
(source_thermal_externalheat_time(instance,interval+1) - &
|
|
||||||
source_thermal_externalheat_time(instance,interval))
|
|
||||||
if (norm_time >= 0.0_pReal .and. norm_time < 1.0_pReal) &
|
|
||||||
TDot = source_thermal_externalheat_rate(instance,interval ) * (1.0_pReal - norm_time) + &
|
|
||||||
source_thermal_externalheat_rate(instance,interval+1) * norm_time
|
|
||||||
enddo
|
|
||||||
dTDot_dT = 0.0
|
|
||||||
|
|
||||||
end subroutine source_thermal_externalheat_getRateAndItsTangent
|
|
||||||
|
|
||||||
end module source_thermal_externalheat
|
|
|
@ -1,253 +0,0 @@
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! $Id$
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @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)
|
|
||||||
use, intrinsic :: iso_fortran_env ! to get compiler_version and compiler_options (at least for gfortran 4.6 at the moment)
|
|
||||||
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_Nphase, &
|
|
||||||
material_phase, &
|
|
||||||
sourceState, &
|
|
||||||
MATERIAL_partPhase
|
|
||||||
use numerics,only: &
|
|
||||||
analyticJaco, &
|
|
||||||
worldrank, &
|
|
||||||
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 = ''
|
|
||||||
|
|
||||||
mainProcess: if (worldrank == 0) then
|
|
||||||
write(6,'(/,a)') ' <<<+- source_'//SOURCE_vacancy_irradiation_label//' init -+>>>'
|
|
||||||
write(6,'(a15,a)') ' Current time: ',IO_timeStamp()
|
|
||||||
#include "compilation_info.f90"
|
|
||||||
endif mainProcess
|
|
||||||
|
|
||||||
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 (.not. analyticJaco) then
|
|
||||||
allocate(sourceState(phase)%p(sourceOffset)%state_backup (sizeState,NofMyPhase), source=0.0_pReal)
|
|
||||||
allocate(sourceState(phase)%p(sourceOffset)%dotState_backup (sizeDotState,NofMyPhase), source=0.0_pReal)
|
|
||||||
endif
|
|
||||||
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,215 +0,0 @@
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! $Id$
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @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)
|
|
||||||
use, intrinsic :: iso_fortran_env ! to get compiler_version and compiler_options (at least for gfortran 4.6 at the moment)
|
|
||||||
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_Nphase, &
|
|
||||||
material_phase, &
|
|
||||||
sourceState, &
|
|
||||||
MATERIAL_partPhase
|
|
||||||
use numerics,only: &
|
|
||||||
analyticJaco, &
|
|
||||||
worldrank, &
|
|
||||||
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 = ''
|
|
||||||
|
|
||||||
mainProcess: if (worldrank == 0) then
|
|
||||||
write(6,'(/,a)') ' <<<+- source_'//SOURCE_vacancy_phenoplasticity_label//' init -+>>>'
|
|
||||||
write(6,'(a15,a)') ' Current time: ',IO_timeStamp()
|
|
||||||
#include "compilation_info.f90"
|
|
||||||
endif mainProcess
|
|
||||||
|
|
||||||
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 (.not. analyticJaco) then
|
|
||||||
allocate(sourceState(phase)%p(sourceOffset)%state_backup (sizeState,NofMyPhase), source=0.0_pReal)
|
|
||||||
allocate(sourceState(phase)%p(sourceOffset)%dotState_backup (sizeDotState,NofMyPhase), source=0.0_pReal)
|
|
||||||
endif
|
|
||||||
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,255 +0,0 @@
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! $Id$
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @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)
|
|
||||||
use, intrinsic :: iso_fortran_env ! to get compiler_version and compiler_options (at least for gfortran 4.6 at the moment)
|
|
||||||
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_Nphase, &
|
|
||||||
material_phase, &
|
|
||||||
sourceState, &
|
|
||||||
MATERIAL_partPhase
|
|
||||||
use numerics,only: &
|
|
||||||
analyticJaco, &
|
|
||||||
worldrank, &
|
|
||||||
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 = ''
|
|
||||||
|
|
||||||
mainProcess: if (worldrank == 0) then
|
|
||||||
write(6,'(/,a)') ' <<<+- source_'//SOURCE_vacancy_thermalfluc_label//' init -+>>>'
|
|
||||||
write(6,'(a15,a)') ' Current time: ',IO_timeStamp()
|
|
||||||
#include "compilation_info.f90"
|
|
||||||
endif mainProcess
|
|
||||||
|
|
||||||
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 (.not. analyticJaco) then
|
|
||||||
allocate(sourceState(phase)%p(sourceOffset)%state_backup (sizeState,NofMyPhase), source=0.0_pReal)
|
|
||||||
allocate(sourceState(phase)%p(sourceOffset)%dotState_backup (sizeDotState,NofMyPhase), source=0.0_pReal)
|
|
||||||
endif
|
|
||||||
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
|
|
|
@ -12,3 +12,8 @@ set (SPECTRAL "spectral_damage"
|
||||||
foreach (p ${SPECTRAL})
|
foreach (p ${SPECTRAL})
|
||||||
add_library (${p} MODULE "${p}.f90")
|
add_library (${p} MODULE "${p}.f90")
|
||||||
endforeach (p)
|
endforeach (p)
|
||||||
|
|
||||||
|
# set libraries/modules for linking
|
||||||
|
foreach (p ${SPECTRAL})
|
||||||
|
set (AUX_LIB ${AUX_LIB} ${p})
|
||||||
|
endforeach (p)
|
|
@ -1,414 +0,0 @@
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! $Id: spectral_damage.f90 4082 2015-04-11 20:28:07Z MPIE\m.diehl $
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @author Pratheek Shanthraj, Max-Planck-Institut für Eisenforschung GmbH
|
|
||||||
!> @author Shaokang Zhang, Max-Planck-Institut für Eisenforschung GmbH
|
|
||||||
!> @brief Spectral solver for nonlocal damage
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
module spectral_damage
|
|
||||||
use prec, only: &
|
|
||||||
pInt, &
|
|
||||||
pReal
|
|
||||||
use math, only: &
|
|
||||||
math_I3
|
|
||||||
use spectral_utilities, only: &
|
|
||||||
tSolutionState, &
|
|
||||||
tSolutionParams
|
|
||||||
use numerics, only: &
|
|
||||||
worldrank, &
|
|
||||||
worldsize
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
private
|
|
||||||
#include <petsc/finclude/petsc.h90>
|
|
||||||
|
|
||||||
character (len=*), parameter, public :: &
|
|
||||||
spectral_damage_label = 'spectraldamage'
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! derived types
|
|
||||||
type(tSolutionParams), private :: params
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! PETSc data
|
|
||||||
SNES, private :: damage_snes
|
|
||||||
Vec, private :: solution
|
|
||||||
PetscInt, private :: xstart, xend, ystart, yend, zstart, zend
|
|
||||||
real(pReal), private, dimension(:,:,:), allocatable :: &
|
|
||||||
damage_current, & !< field of current damage
|
|
||||||
damage_lastInc, & !< field of previous damage
|
|
||||||
damage_stagInc !< field of staggered damage
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! reference diffusion tensor, mobility etc.
|
|
||||||
integer(pInt), private :: totalIter = 0_pInt !< total iteration in current increment
|
|
||||||
real(pReal), dimension(3,3), private :: D_ref
|
|
||||||
real(pReal), private :: mobility_ref
|
|
||||||
character(len=1024), private :: incInfo
|
|
||||||
|
|
||||||
public :: &
|
|
||||||
spectral_damage_init, &
|
|
||||||
spectral_damage_solution, &
|
|
||||||
spectral_damage_forward, &
|
|
||||||
spectral_damage_destroy
|
|
||||||
external :: &
|
|
||||||
VecDestroy, &
|
|
||||||
DMDestroy, &
|
|
||||||
DMDACreate3D, &
|
|
||||||
DMCreateGlobalVector, &
|
|
||||||
DMDASNESSetFunctionLocal, &
|
|
||||||
PETScFinalize, &
|
|
||||||
SNESDestroy, &
|
|
||||||
SNESGetNumberFunctionEvals, &
|
|
||||||
SNESGetIterationNumber, &
|
|
||||||
SNESSolve, &
|
|
||||||
SNESSetDM, &
|
|
||||||
SNESGetConvergedReason, &
|
|
||||||
SNESSetConvergenceTest, &
|
|
||||||
SNESSetFromOptions, &
|
|
||||||
SNESCreate, &
|
|
||||||
MPI_Abort, &
|
|
||||||
MPI_Bcast, &
|
|
||||||
MPI_Allreduce
|
|
||||||
|
|
||||||
contains
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief allocates all neccessary fields and fills them with data, potentially from restart info
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine spectral_damage_init()
|
|
||||||
use, intrinsic :: iso_fortran_env ! to get compiler_version and compiler_options (at least for gfortran >4.6 at the moment)
|
|
||||||
use IO, only: &
|
|
||||||
IO_intOut, &
|
|
||||||
IO_read_realFile, &
|
|
||||||
IO_timeStamp
|
|
||||||
use spectral_utilities, only: &
|
|
||||||
wgt
|
|
||||||
use mesh, only: &
|
|
||||||
grid, &
|
|
||||||
grid3
|
|
||||||
use damage_nonlocal, only: &
|
|
||||||
damage_nonlocal_getDiffusion33, &
|
|
||||||
damage_nonlocal_getMobility
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
DM :: damage_grid
|
|
||||||
Vec :: uBound, lBound
|
|
||||||
PetscErrorCode :: ierr
|
|
||||||
PetscObject :: dummy
|
|
||||||
integer(pInt), dimension(:), allocatable :: localK
|
|
||||||
integer(pInt) :: proc
|
|
||||||
integer(pInt) :: i, j, k, cell
|
|
||||||
character(len=100) :: snes_type
|
|
||||||
|
|
||||||
mainProcess: if (worldrank == 0_pInt) then
|
|
||||||
write(6,'(/,a)') ' <<<+- spectral_damage init -+>>>'
|
|
||||||
write(6,'(a15,a)') ' Current time: ',IO_timeStamp()
|
|
||||||
#include "compilation_info.f90"
|
|
||||||
endif mainProcess
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! initialize solver specific parts of PETSc
|
|
||||||
call SNESCreate(PETSC_COMM_WORLD,damage_snes,ierr); CHKERRQ(ierr)
|
|
||||||
call SNESSetOptionsPrefix(damage_snes,'damage_',ierr);CHKERRQ(ierr)
|
|
||||||
allocate(localK(worldsize), source = 0); localK(worldrank+1) = grid3
|
|
||||||
do proc = 1, worldsize
|
|
||||||
call MPI_Bcast(localK(proc),1,MPI_INTEGER,proc-1,PETSC_COMM_WORLD,ierr)
|
|
||||||
enddo
|
|
||||||
call DMDACreate3d(PETSC_COMM_WORLD, &
|
|
||||||
DM_BOUNDARY_NONE, DM_BOUNDARY_NONE, DM_BOUNDARY_NONE, & !< cut off stencil at boundary
|
|
||||||
DMDA_STENCIL_BOX, & !< Moore (26) neighborhood around central point
|
|
||||||
grid(1),grid(2),grid(3), & !< global grid
|
|
||||||
1, 1, worldsize, &
|
|
||||||
1, 0, & !< #dof (damage phase field), ghost boundary width (domain overlap)
|
|
||||||
grid(1),grid(2),localK, & !< local grid
|
|
||||||
damage_grid,ierr) !< handle, error
|
|
||||||
CHKERRQ(ierr)
|
|
||||||
call SNESSetDM(damage_snes,damage_grid,ierr); CHKERRQ(ierr) !< connect snes to da
|
|
||||||
call DMCreateGlobalVector(damage_grid,solution,ierr); CHKERRQ(ierr) !< global solution vector (grid x 1, i.e. every def grad tensor)
|
|
||||||
call DMDASNESSetFunctionLocal(damage_grid,INSERT_VALUES,spectral_damage_formResidual,dummy,ierr) !< residual vector of same shape as solution vector
|
|
||||||
CHKERRQ(ierr)
|
|
||||||
call SNESSetFromOptions(damage_snes,ierr); CHKERRQ(ierr) !< pull it all together with additional cli arguments
|
|
||||||
call SNESGetType(damage_snes,snes_type,ierr); CHKERRQ(ierr)
|
|
||||||
if (trim(snes_type) == 'vinewtonrsls' .or. &
|
|
||||||
trim(snes_type) == 'vinewtonssls') then
|
|
||||||
call DMGetGlobalVector(damage_grid,lBound,ierr); CHKERRQ(ierr)
|
|
||||||
call DMGetGlobalVector(damage_grid,uBound,ierr); CHKERRQ(ierr)
|
|
||||||
call VecSet(lBound,0.0,ierr); CHKERRQ(ierr)
|
|
||||||
call VecSet(uBound,1.0,ierr); CHKERRQ(ierr)
|
|
||||||
call SNESVISetVariableBounds(damage_snes,lBound,uBound,ierr) !< variable bounds for variational inequalities like contact mechanics, damage etc.
|
|
||||||
call DMRestoreGlobalVector(damage_grid,lBound,ierr); CHKERRQ(ierr)
|
|
||||||
call DMRestoreGlobalVector(damage_grid,uBound,ierr); CHKERRQ(ierr)
|
|
||||||
endif
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! init fields
|
|
||||||
call DMDAGetCorners(damage_grid,xstart,ystart,zstart,xend,yend,zend,ierr)
|
|
||||||
CHKERRQ(ierr)
|
|
||||||
xend = xstart + xend - 1
|
|
||||||
yend = ystart + yend - 1
|
|
||||||
zend = zstart + zend - 1
|
|
||||||
call VecSet(solution,1.0,ierr); CHKERRQ(ierr)
|
|
||||||
allocate(damage_current(grid(1),grid(2),grid3), source=1.0_pReal)
|
|
||||||
allocate(damage_lastInc(grid(1),grid(2),grid3), source=1.0_pReal)
|
|
||||||
allocate(damage_stagInc(grid(1),grid(2),grid3), source=1.0_pReal)
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! damage reference diffusion update
|
|
||||||
cell = 0_pInt
|
|
||||||
D_ref = 0.0_pReal
|
|
||||||
mobility_ref = 0.0_pReal
|
|
||||||
do k = 1_pInt, grid3; do j = 1_pInt, grid(2); do i = 1_pInt,grid(1)
|
|
||||||
cell = cell + 1_pInt
|
|
||||||
D_ref = D_ref + damage_nonlocal_getDiffusion33(1,cell)
|
|
||||||
mobility_ref = mobility_ref + damage_nonlocal_getMobility(1,cell)
|
|
||||||
enddo; enddo; enddo
|
|
||||||
D_ref = D_ref*wgt
|
|
||||||
call MPI_Allreduce(MPI_IN_PLACE,D_ref,9,MPI_DOUBLE,MPI_SUM,PETSC_COMM_WORLD,ierr)
|
|
||||||
mobility_ref = mobility_ref*wgt
|
|
||||||
call MPI_Allreduce(MPI_IN_PLACE,mobility_ref,1,MPI_DOUBLE,MPI_SUM,PETSC_COMM_WORLD,ierr)
|
|
||||||
|
|
||||||
end subroutine spectral_damage_init
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief solution for the spectral damage scheme with internal iterations
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
type(tSolutionState) function spectral_damage_solution(guess,timeinc,timeinc_old,loadCaseTime)
|
|
||||||
use numerics, only: &
|
|
||||||
itmax, &
|
|
||||||
err_damage_tolAbs, &
|
|
||||||
err_damage_tolRel
|
|
||||||
use spectral_utilities, only: &
|
|
||||||
tBoundaryCondition, &
|
|
||||||
Utilities_maskedCompliance, &
|
|
||||||
Utilities_updateGamma
|
|
||||||
use mesh, only: &
|
|
||||||
grid, &
|
|
||||||
grid3
|
|
||||||
use damage_nonlocal, only: &
|
|
||||||
damage_nonlocal_putNonLocalDamage
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! input data for solution
|
|
||||||
real(pReal), intent(in) :: &
|
|
||||||
timeinc, & !< increment in time for current solution
|
|
||||||
timeinc_old, & !< increment in time of last increment
|
|
||||||
loadCaseTime !< remaining time of current load case
|
|
||||||
logical, intent(in) :: guess
|
|
||||||
integer(pInt) :: i, j, k, cell
|
|
||||||
PetscInt ::position
|
|
||||||
PetscReal :: minDamage, maxDamage, stagNorm, solnNorm
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! PETSc Data
|
|
||||||
PetscErrorCode :: ierr
|
|
||||||
SNESConvergedReason :: reason
|
|
||||||
|
|
||||||
spectral_damage_solution%converged =.false.
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! set module wide availabe data
|
|
||||||
params%timeinc = timeinc
|
|
||||||
params%timeincOld = timeinc_old
|
|
||||||
|
|
||||||
call SNESSolve(damage_snes,PETSC_NULL_OBJECT,solution,ierr); CHKERRQ(ierr)
|
|
||||||
call SNESGetConvergedReason(damage_snes,reason,ierr); CHKERRQ(ierr)
|
|
||||||
|
|
||||||
if (reason < 1) then
|
|
||||||
spectral_damage_solution%converged = .false.
|
|
||||||
spectral_damage_solution%iterationsNeeded = itmax
|
|
||||||
else
|
|
||||||
spectral_damage_solution%converged = .true.
|
|
||||||
spectral_damage_solution%iterationsNeeded = totalIter
|
|
||||||
endif
|
|
||||||
stagNorm = maxval(abs(damage_current - damage_stagInc))
|
|
||||||
solnNorm = maxval(abs(damage_current))
|
|
||||||
call MPI_Allreduce(MPI_IN_PLACE,stagNorm,1,MPI_DOUBLE,MPI_MAX,PETSC_COMM_WORLD,ierr)
|
|
||||||
call MPI_Allreduce(MPI_IN_PLACE,solnNorm,1,MPI_DOUBLE,MPI_MAX,PETSC_COMM_WORLD,ierr)
|
|
||||||
damage_stagInc = damage_current
|
|
||||||
spectral_damage_solution%stagConverged = stagNorm < err_damage_tolAbs &
|
|
||||||
.or. stagNorm < err_damage_tolRel*solnNorm
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! updating damage state
|
|
||||||
cell = 0_pInt !< material point = 0
|
|
||||||
do k = 1_pInt, grid3; do j = 1_pInt, grid(2); do i = 1_pInt,grid(1)
|
|
||||||
cell = cell + 1_pInt !< material point increase
|
|
||||||
call damage_nonlocal_putNonLocalDamage(damage_current(i,j,k),1,cell)
|
|
||||||
enddo; enddo; enddo
|
|
||||||
|
|
||||||
call VecMin(solution,position,minDamage,ierr); CHKERRQ(ierr)
|
|
||||||
call VecMax(solution,position,maxDamage,ierr); CHKERRQ(ierr)
|
|
||||||
if (worldrank == 0) then
|
|
||||||
if (spectral_damage_solution%converged) &
|
|
||||||
write(6,'(/,a)') ' ... nonlocal damage converged .....................................'
|
|
||||||
write(6,'(/,a,f8.6,2x,f8.6,2x,f8.6,/)',advance='no') ' Minimum|Maximum|Delta Damage = ',&
|
|
||||||
minDamage, maxDamage, stagNorm
|
|
||||||
write(6,'(/,a)') ' ==========================================================================='
|
|
||||||
flush(6)
|
|
||||||
endif
|
|
||||||
|
|
||||||
end function spectral_damage_solution
|
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief forms the spectral damage residual vector
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine spectral_damage_formResidual(in,x_scal,f_scal,dummy,ierr)
|
|
||||||
use numerics, only: &
|
|
||||||
residualStiffness
|
|
||||||
use mesh, only: &
|
|
||||||
grid, &
|
|
||||||
grid3
|
|
||||||
use math, only: &
|
|
||||||
math_mul33x3
|
|
||||||
use spectral_utilities, only: &
|
|
||||||
scalarField_real, &
|
|
||||||
vectorField_real, &
|
|
||||||
utilities_FFTvectorForward, &
|
|
||||||
utilities_FFTvectorBackward, &
|
|
||||||
utilities_FFTscalarForward, &
|
|
||||||
utilities_FFTscalarBackward, &
|
|
||||||
utilities_fourierGreenConvolution, &
|
|
||||||
utilities_fourierScalarGradient, &
|
|
||||||
utilities_fourierVectorDivergence
|
|
||||||
use damage_nonlocal, only: &
|
|
||||||
damage_nonlocal_getSourceAndItsTangent,&
|
|
||||||
damage_nonlocal_getDiffusion33, &
|
|
||||||
damage_nonlocal_getMobility
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
DMDALocalInfo, dimension(DMDA_LOCAL_INFO_SIZE) :: &
|
|
||||||
in
|
|
||||||
PetscScalar, dimension( &
|
|
||||||
XG_RANGE,YG_RANGE,ZG_RANGE) :: &
|
|
||||||
x_scal
|
|
||||||
PetscScalar, dimension( &
|
|
||||||
X_RANGE,Y_RANGE,Z_RANGE) :: &
|
|
||||||
f_scal
|
|
||||||
PetscObject :: dummy
|
|
||||||
PetscErrorCode :: ierr
|
|
||||||
integer(pInt) :: i, j, k, cell
|
|
||||||
real(pReal) :: phiDot, dPhiDot_dPhi, mobility
|
|
||||||
|
|
||||||
damage_current = x_scal
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! evaluate polarization field
|
|
||||||
scalarField_real = 0.0_pReal
|
|
||||||
scalarField_real(1:grid(1),1:grid(2),1:grid3) = damage_current
|
|
||||||
call utilities_FFTscalarForward()
|
|
||||||
call utilities_fourierScalarGradient() !< calculate gradient of damage field
|
|
||||||
call utilities_FFTvectorBackward()
|
|
||||||
cell = 0_pInt
|
|
||||||
do k = 1_pInt, grid3; do j = 1_pInt, grid(2); do i = 1_pInt,grid(1)
|
|
||||||
cell = cell + 1_pInt
|
|
||||||
vectorField_real(1:3,i,j,k) = math_mul33x3(damage_nonlocal_getDiffusion33(1,cell) - D_ref, &
|
|
||||||
vectorField_real(1:3,i,j,k))
|
|
||||||
enddo; enddo; enddo
|
|
||||||
call utilities_FFTvectorForward()
|
|
||||||
call utilities_fourierVectorDivergence() !< calculate damage divergence in fourier field
|
|
||||||
call utilities_FFTscalarBackward()
|
|
||||||
cell = 0_pInt
|
|
||||||
do k = 1_pInt, grid3; do j = 1_pInt, grid(2); do i = 1_pInt,grid(1)
|
|
||||||
cell = cell + 1_pInt
|
|
||||||
call damage_nonlocal_getSourceAndItsTangent(phiDot, dPhiDot_dPhi, damage_current(i,j,k), 1, cell)
|
|
||||||
mobility = damage_nonlocal_getMobility(1,cell)
|
|
||||||
scalarField_real(i,j,k) = params%timeinc*scalarField_real(i,j,k) + &
|
|
||||||
params%timeinc*phiDot + &
|
|
||||||
mobility*damage_lastInc(i,j,k) - &
|
|
||||||
mobility*damage_current(i,j,k) + &
|
|
||||||
mobility_ref*damage_current(i,j,k)
|
|
||||||
enddo; enddo; enddo
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! convolution of damage field with green operator
|
|
||||||
call utilities_FFTscalarForward()
|
|
||||||
call utilities_fourierGreenConvolution(D_ref, mobility_ref, params%timeinc)
|
|
||||||
call utilities_FFTscalarBackward()
|
|
||||||
where(scalarField_real(1:grid(1),1:grid(2),1:grid3) > damage_lastInc) &
|
|
||||||
scalarField_real(1:grid(1),1:grid(2),1:grid3) = damage_lastInc
|
|
||||||
where(scalarField_real(1:grid(1),1:grid(2),1:grid3) < residualStiffness) &
|
|
||||||
scalarField_real(1:grid(1),1:grid(2),1:grid3) = residualStiffness
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! constructing residual
|
|
||||||
f_scal = scalarField_real(1:grid(1),1:grid(2),1:grid3) - damage_current
|
|
||||||
|
|
||||||
end subroutine spectral_damage_formResidual
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief spectral damage forwarding routine
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine spectral_damage_forward(guess,timeinc,timeinc_old,loadCaseTime)
|
|
||||||
use mesh, only: &
|
|
||||||
grid, &
|
|
||||||
grid3
|
|
||||||
use spectral_utilities, only: &
|
|
||||||
cutBack, &
|
|
||||||
wgt
|
|
||||||
use damage_nonlocal, only: &
|
|
||||||
damage_nonlocal_putNonLocalDamage, &
|
|
||||||
damage_nonlocal_getDiffusion33, &
|
|
||||||
damage_nonlocal_getMobility
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
real(pReal), intent(in) :: &
|
|
||||||
timeinc_old, &
|
|
||||||
timeinc, &
|
|
||||||
loadCaseTime !< remaining time of current load case
|
|
||||||
logical, intent(in) :: guess
|
|
||||||
PetscErrorCode :: ierr
|
|
||||||
integer(pInt) :: i, j, k, cell
|
|
||||||
DM :: dm_local
|
|
||||||
PetscScalar, dimension(:,:,:), pointer :: x_scal
|
|
||||||
|
|
||||||
if (cutBack) then
|
|
||||||
damage_current = damage_lastInc
|
|
||||||
damage_stagInc = damage_lastInc
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! reverting damage field state
|
|
||||||
cell = 0_pInt
|
|
||||||
call SNESGetDM(damage_snes,dm_local,ierr); CHKERRQ(ierr)
|
|
||||||
call DMDAVecGetArrayF90(dm_local,solution,x_scal,ierr); CHKERRQ(ierr) !< get the data out of PETSc to work with
|
|
||||||
x_scal(xstart:xend,ystart:yend,zstart:zend) = damage_current
|
|
||||||
call DMDAVecRestoreArrayF90(dm_local,solution,x_scal,ierr); CHKERRQ(ierr)
|
|
||||||
do k = 1_pInt, grid3; do j = 1_pInt, grid(2); do i = 1_pInt,grid(1)
|
|
||||||
cell = cell + 1_pInt
|
|
||||||
call damage_nonlocal_putNonLocalDamage(damage_current(i,j,k),1,cell)
|
|
||||||
enddo; enddo; enddo
|
|
||||||
else
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! update rate and forward last inc
|
|
||||||
damage_lastInc = damage_current
|
|
||||||
cell = 0_pInt
|
|
||||||
D_ref = 0.0_pReal
|
|
||||||
mobility_ref = 0.0_pReal
|
|
||||||
do k = 1_pInt, grid3; do j = 1_pInt, grid(2); do i = 1_pInt,grid(1)
|
|
||||||
cell = cell + 1_pInt
|
|
||||||
D_ref = D_ref + damage_nonlocal_getDiffusion33(1,cell)
|
|
||||||
mobility_ref = mobility_ref + damage_nonlocal_getMobility(1,cell)
|
|
||||||
enddo; enddo; enddo
|
|
||||||
D_ref = D_ref*wgt
|
|
||||||
call MPI_Allreduce(MPI_IN_PLACE,D_ref,9,MPI_DOUBLE,MPI_SUM,PETSC_COMM_WORLD,ierr)
|
|
||||||
mobility_ref = mobility_ref*wgt
|
|
||||||
call MPI_Allreduce(MPI_IN_PLACE,mobility_ref,1,MPI_DOUBLE,MPI_SUM,PETSC_COMM_WORLD,ierr)
|
|
||||||
endif
|
|
||||||
|
|
||||||
end subroutine spectral_damage_forward
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief destroy routine
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine spectral_damage_destroy()
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
PetscErrorCode :: ierr
|
|
||||||
|
|
||||||
call VecDestroy(solution,ierr); CHKERRQ(ierr)
|
|
||||||
call SNESDestroy(damage_snes,ierr); CHKERRQ(ierr)
|
|
||||||
|
|
||||||
end subroutine spectral_damage_destroy
|
|
||||||
|
|
||||||
end module spectral_damage
|
|
|
@ -1,568 +0,0 @@
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! $Id$
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @author Martin Diehl, Max-Planck-Institut für Eisenforschung GmbH
|
|
||||||
!> @author Philip Eisenlohr, Max-Planck-Institut für Eisenforschung GmbH
|
|
||||||
!> @brief Interfacing between the spectral solver and the material subroutines provided
|
|
||||||
!! by DAMASK
|
|
||||||
!> @details Interfacing between the spectral solver and the material subroutines provided
|
|
||||||
!> by DAMASK. Interpretating the command line arguments or, in case of called from f2py,
|
|
||||||
!> the arguments parsed to the init routine to get load case, geometry file, working
|
|
||||||
!> directory, etc.
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
module DAMASK_interface
|
|
||||||
use prec, only: &
|
|
||||||
pInt
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
private
|
|
||||||
#ifdef PETSc
|
|
||||||
#include <petsc/finclude/petscsys.h>
|
|
||||||
#endif
|
|
||||||
logical, public, protected :: appendToOutFile = .false. !< Append to existing spectralOut file (in case of restart, not in case of regridding)
|
|
||||||
integer(pInt), public, protected :: spectralRestartInc = 1_pInt !< Increment at which calculation starts
|
|
||||||
character(len=1024), public, protected :: &
|
|
||||||
geometryFile = '', & !< parameter given for geometry file
|
|
||||||
loadCaseFile = '' !< parameter given for load case file
|
|
||||||
character(len=1024), private :: workingDirectory !< accessed by getSolverWorkingDirectoryName for compatibility reasons
|
|
||||||
|
|
||||||
public :: &
|
|
||||||
getSolverWorkingDirectoryName, &
|
|
||||||
getSolverJobName, &
|
|
||||||
DAMASK_interface_init
|
|
||||||
private :: &
|
|
||||||
storeWorkingDirectory, &
|
|
||||||
getGeometryFile, &
|
|
||||||
getLoadCaseFile, &
|
|
||||||
rectifyPath, &
|
|
||||||
makeRelativePath, &
|
|
||||||
getPathSep, &
|
|
||||||
IIO_stringValue, &
|
|
||||||
IIO_intValue, &
|
|
||||||
IIO_lc, &
|
|
||||||
IIO_stringPos
|
|
||||||
|
|
||||||
contains
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief initializes the solver by interpreting the command line arguments. Also writes
|
|
||||||
!! information on computation to screen
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine DAMASK_interface_init(loadCaseParameterIn,geometryParameterIn)
|
|
||||||
use, intrinsic :: iso_fortran_env ! to get compiler_version and compiler_options (at least for gfortran 4.6 at the moment)
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
character(len=1024), optional, intent(in) :: &
|
|
||||||
loadCaseParameterIn, & !< if using the f2py variant, the -l argument of DAMASK_spectral.exe
|
|
||||||
geometryParameterIn !< if using the f2py variant, the -g argument of DAMASK_spectral.exe
|
|
||||||
character(len=1024) :: &
|
|
||||||
commandLine, & !< command line call as string
|
|
||||||
loadCaseArg ='', & !< -l argument given to DAMASK_spectral.exe
|
|
||||||
geometryArg ='', & !< -g argument given to DAMASK_spectral.exe
|
|
||||||
workingDirArg ='', & !< -w argument given to DAMASK_spectral.exe
|
|
||||||
hostName, & !< name of machine on which DAMASK_spectral.exe is execute (might require export HOSTNAME)
|
|
||||||
userName, & !< name of user calling DAMASK_spectral.exe
|
|
||||||
tag
|
|
||||||
integer :: &
|
|
||||||
i, &
|
|
||||||
worldrank = 0
|
|
||||||
integer, allocatable, dimension(:) :: &
|
|
||||||
chunkPos
|
|
||||||
integer, dimension(8) :: &
|
|
||||||
dateAndTime ! type default integer
|
|
||||||
#ifdef PETSc
|
|
||||||
PetscErrorCode :: ierr
|
|
||||||
#endif
|
|
||||||
external :: &
|
|
||||||
quit,&
|
|
||||||
MPI_Comm_rank,&
|
|
||||||
PETScInitialize, &
|
|
||||||
MPI_abort
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! PETSc Init
|
|
||||||
#ifdef PETSc
|
|
||||||
call PetscInitialize(PETSC_NULL_CHARACTER,ierr) ! according to PETSc manual, that should be the first line in the code
|
|
||||||
CHKERRQ(ierr) ! this is a macro definition, it is case sensitive
|
|
||||||
|
|
||||||
open(6, encoding='UTF-8') ! modern fortran compilers (gfortran >4.4, ifort >11 support it)
|
|
||||||
call MPI_Comm_rank(PETSC_COMM_WORLD,worldrank,ierr);CHKERRQ(ierr)
|
|
||||||
#endif
|
|
||||||
mainProcess: if (worldrank == 0) then
|
|
||||||
call date_and_time(values = dateAndTime)
|
|
||||||
write(6,'(/,a)') ' <<<+- DAMASK_spectral -+>>>'
|
|
||||||
write(6,'(/,a)') ' Version: '//DAMASKVERSION
|
|
||||||
write(6,'(a,2(i2.2,a),i4.4)') ' Date: ',dateAndTime(3),'/',&
|
|
||||||
dateAndTime(2),'/',&
|
|
||||||
dateAndTime(1)
|
|
||||||
write(6,'(a,2(i2.2,a),i2.2)') ' Time: ',dateAndTime(5),':',&
|
|
||||||
dateAndTime(6),':',&
|
|
||||||
dateAndTime(7)
|
|
||||||
write(6,'(/,a)') ' <<<+- DAMASK_interface init -+>>>'
|
|
||||||
#include "compilation_info.f90"
|
|
||||||
endif mainProcess
|
|
||||||
|
|
||||||
if ( present(loadcaseParameterIn) .and. present(geometryParameterIn)) then ! both mandatory parameters given in function call
|
|
||||||
geometryArg = geometryParameterIn
|
|
||||||
loadcaseArg = loadcaseParameterIn
|
|
||||||
commandLine = 'n/a'
|
|
||||||
else if ( .not.( present(loadcaseParameterIn) .and. present(geometryParameterIn))) then ! none parameters given in function call, trying to get them from command line
|
|
||||||
call get_command(commandLine)
|
|
||||||
chunkPos = IIO_stringPos(commandLine)
|
|
||||||
do i = 1, chunkPos(1)
|
|
||||||
tag = IIO_lc(IIO_stringValue(commandLine,chunkPos,i)) ! extract key
|
|
||||||
select case(tag)
|
|
||||||
case ('-h','--help')
|
|
||||||
mainProcess2: if (worldrank == 0) then
|
|
||||||
write(6,'(a)') ' #######################################################################'
|
|
||||||
write(6,'(a)') ' DAMASK_spectral:'
|
|
||||||
write(6,'(a)') ' The spectral method boundary value problem solver for'
|
|
||||||
write(6,'(a)') ' the Düsseldorf Advanced Material Simulation Kit'
|
|
||||||
write(6,'(a,/)')' #######################################################################'
|
|
||||||
write(6,'(a,/)')' Valid command line switches:'
|
|
||||||
write(6,'(a)') ' --geom (-g, --geometry)'
|
|
||||||
write(6,'(a)') ' --load (-l, --loadcase)'
|
|
||||||
write(6,'(a)') ' --workingdir (-w, --wd, --workingdirectory, -d, --directory)'
|
|
||||||
write(6,'(a)') ' --restart (-r, --rs)'
|
|
||||||
write(6,'(a)') ' --regrid (--rg)'
|
|
||||||
write(6,'(a)') ' --help (-h)'
|
|
||||||
write(6,'(/,a)')' -----------------------------------------------------------------------'
|
|
||||||
write(6,'(a)') ' Mandatory arguments:'
|
|
||||||
write(6,'(/,a)')' --geom PathToGeomFile/NameOfGeom.geom'
|
|
||||||
write(6,'(a)') ' Specifies the location of the geometry definition file,'
|
|
||||||
write(6,'(a)') ' if no extension is given, .geom will be appended.'
|
|
||||||
write(6,'(a)') ' "PathToGeomFile" will be the working directory if not specified'
|
|
||||||
write(6,'(a)') ' via --workingdir.'
|
|
||||||
write(6,'(a)') ' Make sure the file "material.config" exists in the working'
|
|
||||||
write(6,'(a)') ' directory.'
|
|
||||||
write(6,'(a)') ' For further configuration place "numerics.config"'
|
|
||||||
write(6,'(a)')' and "numerics.config" in that directory.'
|
|
||||||
write(6,'(/,a)')' --load PathToLoadFile/NameOfLoadFile.load'
|
|
||||||
write(6,'(a)') ' Specifies the location of the load case definition file,'
|
|
||||||
write(6,'(a)') ' if no extension is given, .load will be appended.'
|
|
||||||
write(6,'(/,a)')' -----------------------------------------------------------------------'
|
|
||||||
write(6,'(a)') ' Optional arguments:'
|
|
||||||
write(6,'(/,a)')' --workingdirectory PathToWorkingDirectory'
|
|
||||||
write(6,'(a)') ' Specifies the working directory and overwrites the default'
|
|
||||||
write(6,'(a)') ' "PathToGeomFile".'
|
|
||||||
write(6,'(a)') ' Make sure the file "material.config" exists in the working'
|
|
||||||
write(6,'(a)') ' directory.'
|
|
||||||
write(6,'(a)') ' For further configuration place "numerics.config"'
|
|
||||||
write(6,'(a)')' and "numerics.config" in that directory.'
|
|
||||||
write(6,'(/,a)')' --restart XX'
|
|
||||||
write(6,'(a)') ' Reads in total increment No. XX-1 and continues to'
|
|
||||||
write(6,'(a)') ' calculate total increment No. XX.'
|
|
||||||
write(6,'(a)') ' Appends to existing results file '
|
|
||||||
write(6,'(a)') ' "NameOfGeom_NameOfLoadFile.spectralOut".'
|
|
||||||
write(6,'(a)') ' Works only if the restart information for total increment'
|
|
||||||
write(6,'(a)') ' No. XX-1 is available in the working directory.'
|
|
||||||
write(6,'(/,a)')' --regrid XX'
|
|
||||||
write(6,'(a)') ' Reads in total increment No. XX-1 and continues to'
|
|
||||||
write(6,'(a)') ' calculate total increment No. XX.'
|
|
||||||
write(6,'(a)') ' Attention: Overwrites existing results file '
|
|
||||||
write(6,'(a)') ' "NameOfGeom_NameOfLoadFile.spectralOut".'
|
|
||||||
write(6,'(a)') ' Works only if the restart information for total increment'
|
|
||||||
write(6,'(a)') ' No. XX-1 is available in the working directory.'
|
|
||||||
write(6,'(/,a)')' -----------------------------------------------------------------------'
|
|
||||||
write(6,'(a)') ' Help:'
|
|
||||||
write(6,'(/,a)')' --help'
|
|
||||||
write(6,'(a,/)')' Prints this message and exits'
|
|
||||||
call quit(0_pInt) ! normal Termination
|
|
||||||
endif mainProcess2
|
|
||||||
case ('-l', '--load', '--loadcase')
|
|
||||||
loadcaseArg = IIO_stringValue(commandLine,chunkPos,i+1_pInt)
|
|
||||||
case ('-g', '--geom', '--geometry')
|
|
||||||
geometryArg = IIO_stringValue(commandLine,chunkPos,i+1_pInt)
|
|
||||||
case ('-w', '-d', '--wd', '--directory', '--workingdir', '--workingdirectory')
|
|
||||||
workingDirArg = IIO_stringValue(commandLine,chunkPos,i+1_pInt)
|
|
||||||
case ('-r', '--rs', '--restart')
|
|
||||||
spectralRestartInc = IIO_IntValue(commandLine,chunkPos,i+1_pInt)
|
|
||||||
appendToOutFile = .true.
|
|
||||||
case ('--rg', '--regrid')
|
|
||||||
spectralRestartInc = IIO_IntValue(commandLine,chunkPos,i+1_pInt)
|
|
||||||
appendToOutFile = .false.
|
|
||||||
end select
|
|
||||||
enddo
|
|
||||||
endif
|
|
||||||
|
|
||||||
if (len(trim(loadcaseArg)) == 0 .or. len(trim(geometryArg)) == 0) then
|
|
||||||
write(6,'(a)') ' Please specify geometry AND load case (-h for help)'
|
|
||||||
call quit(1_pInt)
|
|
||||||
endif
|
|
||||||
|
|
||||||
workingDirectory = storeWorkingDirectory(trim(workingDirArg),trim(geometryArg))
|
|
||||||
geometryFile = getGeometryFile(geometryArg)
|
|
||||||
loadCaseFile = getLoadCaseFile(loadCaseArg)
|
|
||||||
|
|
||||||
call get_environment_variable('HOSTNAME',hostName)
|
|
||||||
call get_environment_variable('USER',userName)
|
|
||||||
mainProcess3: if (worldrank == 0) then
|
|
||||||
write(6,'(a,a)') ' Host name: ', trim(hostName)
|
|
||||||
write(6,'(a,a)') ' User name: ', trim(userName)
|
|
||||||
write(6,'(a,a)') ' Path separator: ', getPathSep()
|
|
||||||
write(6,'(a,a)') ' Command line call: ', trim(commandLine)
|
|
||||||
if (len(trim(workingDirArg))>0) &
|
|
||||||
write(6,'(a,a)') ' Working dir argument: ', trim(workingDirArg)
|
|
||||||
write(6,'(a,a)') ' Geometry argument: ', trim(geometryArg)
|
|
||||||
write(6,'(a,a)') ' Loadcase argument: ', trim(loadcaseArg)
|
|
||||||
write(6,'(a,a)') ' Working directory: ', trim(getSolverWorkingDirectoryName())
|
|
||||||
write(6,'(a,a)') ' Geometry file: ', trim(geometryFile)
|
|
||||||
write(6,'(a,a)') ' Loadcase file: ', trim(loadCaseFile)
|
|
||||||
write(6,'(a,a)') ' Solver job name: ', trim(getSolverJobName())
|
|
||||||
if (SpectralRestartInc > 1_pInt) &
|
|
||||||
write(6,'(a,i6.6)') ' Restart at increment: ', spectralRestartInc
|
|
||||||
write(6,'(a,l1,/)') ' Append to result file: ', appendToOutFile
|
|
||||||
endif mainProcess3
|
|
||||||
|
|
||||||
end subroutine DAMASK_interface_init
|
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief extract working directory from given argument or from location of geometry file,
|
|
||||||
!! possibly converting relative arguments to absolut path
|
|
||||||
!> @todo change working directory with call chdir(storeWorkingDirectory)?
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
character(len=1024) function storeWorkingDirectory(workingDirectoryArg,geometryArg)
|
|
||||||
#ifdef __INTEL_COMPILER
|
|
||||||
use IFPORT
|
|
||||||
#endif
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
character(len=*), intent(in) :: workingDirectoryArg !< working directory argument
|
|
||||||
character(len=*), intent(in) :: geometryArg !< geometry argument
|
|
||||||
character(len=1024) :: cwd
|
|
||||||
character :: pathSep
|
|
||||||
logical :: dirExists
|
|
||||||
external :: quit
|
|
||||||
integer :: error
|
|
||||||
|
|
||||||
pathSep = getPathSep()
|
|
||||||
if (len(workingDirectoryArg)>0) then ! got working directory as input
|
|
||||||
if (workingDirectoryArg(1:1) == pathSep) then ! absolute path given as command line argument
|
|
||||||
storeWorkingDirectory = workingDirectoryArg
|
|
||||||
else
|
|
||||||
error = getcwd(cwd) ! relative path given as command line argument
|
|
||||||
storeWorkingDirectory = trim(cwd)//pathSep//workingDirectoryArg
|
|
||||||
endif
|
|
||||||
if (storeWorkingDirectory(len(trim(storeWorkingDirectory)):len(trim(storeWorkingDirectory))) & ! if path seperator is not given, append it
|
|
||||||
/= pathSep) storeWorkingDirectory = trim(storeWorkingDirectory)//pathSep
|
|
||||||
#ifdef __INTEL_COMPILER
|
|
||||||
inquire(directory = trim(storeWorkingDirectory)//'.', exist=dirExists)
|
|
||||||
#else
|
|
||||||
inquire(file = trim(storeWorkingDirectory), exist=dirExists)
|
|
||||||
#endif
|
|
||||||
if(.not. dirExists) then ! check if the directory exists
|
|
||||||
write(6,'(a20,a,a16)') ' working directory "',trim(storeWorkingDirectory),'" does not exist'
|
|
||||||
call quit(1_pInt)
|
|
||||||
endif
|
|
||||||
else ! using path to geometry file as working dir
|
|
||||||
if (geometryArg(1:1) == pathSep) then ! absolute path given as command line argument
|
|
||||||
storeWorkingDirectory = geometryArg(1:scan(geometryArg,pathSep,back=.true.))
|
|
||||||
else
|
|
||||||
error = getcwd(cwd) ! relative path given as command line argument
|
|
||||||
storeWorkingDirectory = trim(cwd)//pathSep//&
|
|
||||||
geometryArg(1:scan(geometryArg,pathSep,back=.true.))
|
|
||||||
endif
|
|
||||||
endif
|
|
||||||
storeWorkingDirectory = rectifyPath(storeWorkingDirectory)
|
|
||||||
|
|
||||||
end function storeWorkingDirectory
|
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief simply returns the private string workingDir
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
character(len=1024) function getSolverWorkingDirectoryName()
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
getSolverWorkingDirectoryName = workingDirectory
|
|
||||||
|
|
||||||
end function getSolverWorkingDirectoryName
|
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief solver job name (no extension) as combination of geometry and load case name
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
character(len=1024) function getSolverJobName()
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
integer :: posExt,posSep
|
|
||||||
character :: pathSep
|
|
||||||
character(len=1024) :: tempString
|
|
||||||
|
|
||||||
pathSep = getPathSep()
|
|
||||||
|
|
||||||
tempString = geometryFile
|
|
||||||
posExt = scan(tempString,'.',back=.true.)
|
|
||||||
posSep = scan(tempString,pathSep,back=.true.)
|
|
||||||
|
|
||||||
getSolverJobName = tempString(posSep+1:posExt-1)
|
|
||||||
|
|
||||||
tempString = loadCaseFile
|
|
||||||
posExt = scan(tempString,'.',back=.true.)
|
|
||||||
posSep = scan(tempString,pathSep,back=.true.)
|
|
||||||
|
|
||||||
getSolverJobName = trim(getSolverJobName)//'_'//tempString(posSep+1:posExt-1)
|
|
||||||
|
|
||||||
end function getSolverJobName
|
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief basename of geometry file with extension from command line arguments
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
character(len=1024) function getGeometryFile(geometryParameter)
|
|
||||||
#ifdef __INTEL_COMPILER
|
|
||||||
use IFPORT
|
|
||||||
#endif
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
character(len=1024), intent(in) :: &
|
|
||||||
geometryParameter
|
|
||||||
character(len=1024) :: &
|
|
||||||
cwd
|
|
||||||
integer :: posExt, posSep
|
|
||||||
character :: pathSep
|
|
||||||
integer :: error
|
|
||||||
|
|
||||||
getGeometryFile = geometryParameter
|
|
||||||
pathSep = getPathSep()
|
|
||||||
posExt = scan(getGeometryFile,'.',back=.true.)
|
|
||||||
posSep = scan(getGeometryFile,pathSep,back=.true.)
|
|
||||||
|
|
||||||
if (posExt <= posSep) getGeometryFile = trim(getGeometryFile)//('.geom') ! no extension present
|
|
||||||
if (scan(getGeometryFile,pathSep) /= 1) then ! relative path given as command line argument
|
|
||||||
error = getcwd(cwd)
|
|
||||||
getGeometryFile = rectifyPath(trim(cwd)//pathSep//getGeometryFile)
|
|
||||||
else
|
|
||||||
getGeometryFile = rectifyPath(getGeometryFile)
|
|
||||||
endif
|
|
||||||
|
|
||||||
getGeometryFile = makeRelativePath(getSolverWorkingDirectoryName(), getGeometryFile)
|
|
||||||
|
|
||||||
end function getGeometryFile
|
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief relative path of loadcase from command line arguments
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
character(len=1024) function getLoadCaseFile(loadCaseParameter)
|
|
||||||
#ifdef __INTEL_COMPILER
|
|
||||||
use IFPORT
|
|
||||||
#endif
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
character(len=1024), intent(in) :: &
|
|
||||||
loadCaseParameter
|
|
||||||
character(len=1024) :: &
|
|
||||||
cwd
|
|
||||||
integer :: posExt, posSep, error
|
|
||||||
character :: pathSep
|
|
||||||
|
|
||||||
getLoadCaseFile = loadcaseParameter
|
|
||||||
pathSep = getPathSep()
|
|
||||||
posExt = scan(getLoadCaseFile,'.',back=.true.)
|
|
||||||
posSep = scan(getLoadCaseFile,pathSep,back=.true.)
|
|
||||||
|
|
||||||
if (posExt <= posSep) getLoadCaseFile = trim(getLoadCaseFile)//('.load') ! no extension present
|
|
||||||
if (scan(getLoadCaseFile,pathSep) /= 1) then ! relative path given as command line argument
|
|
||||||
error = getcwd(cwd)
|
|
||||||
getLoadCaseFile = rectifyPath(trim(cwd)//pathSep//getLoadCaseFile)
|
|
||||||
else
|
|
||||||
getLoadCaseFile = rectifyPath(getLoadCaseFile)
|
|
||||||
endif
|
|
||||||
|
|
||||||
getLoadCaseFile = makeRelativePath(getSolverWorkingDirectoryName(), getLoadCaseFile)
|
|
||||||
|
|
||||||
end function getLoadCaseFile
|
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief remove ../ and /./ from path
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
function rectifyPath(path)
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
character(len=*) :: path
|
|
||||||
character(len=len_trim(path)) :: rectifyPath
|
|
||||||
character :: pathSep
|
|
||||||
integer :: i,j,k,l ! no pInt
|
|
||||||
|
|
||||||
pathSep = getPathSep()
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! remove /./ from path
|
|
||||||
l = len_trim(path)
|
|
||||||
rectifyPath = path
|
|
||||||
do i = l,3,-1
|
|
||||||
if (rectifyPath(i-2:i) == pathSep//'.'//pathSep) &
|
|
||||||
rectifyPath(i-1:l) = rectifyPath(i+1:l)//' '
|
|
||||||
enddo
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! remove ../ and corresponding directory from rectifyPath
|
|
||||||
l = len_trim(rectifyPath)
|
|
||||||
i = index(rectifyPath(i:l),'..'//pathSep)
|
|
||||||
j = 0
|
|
||||||
do while (i > j)
|
|
||||||
j = scan(rectifyPath(1:i-2),pathSep,back=.true.)
|
|
||||||
rectifyPath(j+1:l) = rectifyPath(i+3:l)//repeat(' ',2+i-j)
|
|
||||||
if (rectifyPath(j+1:j+1) == pathSep) then !search for '//' that appear in case of XXX/../../XXX
|
|
||||||
k = len_trim(rectifyPath)
|
|
||||||
rectifyPath(j+1:k-1) = rectifyPath(j+2:k)
|
|
||||||
rectifyPath(k:k) = ' '
|
|
||||||
endif
|
|
||||||
i = j+index(rectifyPath(j+1:l),'..'//pathSep)
|
|
||||||
enddo
|
|
||||||
if(len_trim(rectifyPath) == 0) rectifyPath = pathSep
|
|
||||||
|
|
||||||
end function rectifyPath
|
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief relative path from absolute a to absolute b
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
character(len=1024) function makeRelativePath(a,b)
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
character (len=*) :: a,b
|
|
||||||
character :: pathSep
|
|
||||||
integer :: i,posLastCommonSlash,remainingSlashes !no pInt
|
|
||||||
|
|
||||||
pathSep = getPathSep()
|
|
||||||
posLastCommonSlash = 0
|
|
||||||
remainingSlashes = 0
|
|
||||||
|
|
||||||
do i = 1, min(1024,len_trim(a),len_trim(b))
|
|
||||||
if (a(i:i) /= b(i:i)) exit
|
|
||||||
if (a(i:i) == pathSep) posLastCommonSlash = i
|
|
||||||
enddo
|
|
||||||
do i = posLastCommonSlash+1,len_trim(a)
|
|
||||||
if (a(i:i) == pathSep) remainingSlashes = remainingSlashes + 1
|
|
||||||
enddo
|
|
||||||
makeRelativePath = repeat('..'//pathSep,remainingSlashes)//b(posLastCommonSlash+1:len_trim(b))
|
|
||||||
|
|
||||||
end function makeRelativePath
|
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief counting / and \ in $PATH System variable the character occuring more often is assumed
|
|
||||||
! to be the path separator
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
character function getPathSep()
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
character(len=2048) :: &
|
|
||||||
path
|
|
||||||
integer(pInt) :: &
|
|
||||||
backslash = 0_pInt, &
|
|
||||||
slash = 0_pInt
|
|
||||||
integer :: i
|
|
||||||
|
|
||||||
call get_environment_variable('PATH',path)
|
|
||||||
do i=1, len(trim(path))
|
|
||||||
if (path(i:i)=='/') slash = slash + 1_pInt
|
|
||||||
if (path(i:i)=='\') backslash = backslash + 1_pInt
|
|
||||||
enddo
|
|
||||||
|
|
||||||
if (backslash>slash) then
|
|
||||||
getPathSep = '\'
|
|
||||||
else
|
|
||||||
getPathSep = '/'
|
|
||||||
endif
|
|
||||||
|
|
||||||
end function getPathSep
|
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief taken from IO, check IO_stringValue for documentation
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
pure function IIO_stringValue(string,chunkPos,myChunk)
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
integer(pInt), dimension(:), intent(in) :: chunkPos !< positions of start and end of each tag/chunk in given string
|
|
||||||
integer(pInt), intent(in) :: myChunk !< position number of desired chunk
|
|
||||||
character(len=1+chunkPos(myChunk*2+1)-chunkPos(myChunk*2)) :: IIO_stringValue
|
|
||||||
character(len=*), intent(in) :: string !< raw input with known start and end of each chunk
|
|
||||||
|
|
||||||
|
|
||||||
valuePresent: if (myChunk > chunkPos(1) .or. myChunk < 1_pInt) then
|
|
||||||
IIO_stringValue = ''
|
|
||||||
else valuePresent
|
|
||||||
IIO_stringValue = string(chunkPos(myChunk*2):chunkPos(myChunk*2+1))
|
|
||||||
endif valuePresent
|
|
||||||
|
|
||||||
end function IIO_stringValue
|
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief taken from IO, check IO_intValue for documentation
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
integer(pInt) pure function IIO_intValue(string,chunkPos,myChunk)
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
character(len=*), intent(in) :: string !< raw input with known start and end of each chunk
|
|
||||||
integer(pInt), intent(in) :: myChunk !< position number of desired sub string
|
|
||||||
integer(pInt), dimension(:), intent(in) :: chunkPos !< positions of start and end of each tag/chunk in given string
|
|
||||||
|
|
||||||
|
|
||||||
valuePresent: if (myChunk > chunkPos(1) .or. myChunk < 1_pInt) then
|
|
||||||
IIO_intValue = 0_pInt
|
|
||||||
else valuePresent
|
|
||||||
read(UNIT=string(chunkPos(myChunk*2):chunkPos(myChunk*2+1)),ERR=100,FMT=*) IIO_intValue
|
|
||||||
endif valuePresent
|
|
||||||
return
|
|
||||||
100 IIO_intValue = huge(1_pInt)
|
|
||||||
|
|
||||||
end function IIO_intValue
|
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief taken from IO, check IO_lc for documentation
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
pure function IIO_lc(string)
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
character(len=*), intent(in) :: string !< string to convert
|
|
||||||
character(len=len(string)) :: IIO_lc
|
|
||||||
|
|
||||||
character(26), parameter :: LOWER = 'abcdefghijklmnopqrstuvwxyz'
|
|
||||||
character(26), parameter :: UPPER = 'ABCDEFGHIJKLMNOPQRSTUVWXYZ'
|
|
||||||
|
|
||||||
integer :: i,n ! no pInt (len returns default integer)
|
|
||||||
|
|
||||||
IIO_lc = string
|
|
||||||
do i=1,len(string)
|
|
||||||
n = index(UPPER,IIO_lc(i:i))
|
|
||||||
if (n/=0) IIO_lc(i:i) = LOWER(n:n)
|
|
||||||
enddo
|
|
||||||
|
|
||||||
end function IIO_lc
|
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief taken from IO, check IO_stringPos for documentation
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
pure function IIO_stringPos(string)
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
integer(pInt), dimension(:), allocatable :: IIO_stringPos
|
|
||||||
character(len=*), intent(in) :: string !< string in which chunks are searched for
|
|
||||||
|
|
||||||
character(len=*), parameter :: SEP=achar(44)//achar(32)//achar(9)//achar(10)//achar(13) ! comma and whitespaces
|
|
||||||
integer :: left, right ! no pInt (verify and scan return default integer)
|
|
||||||
|
|
||||||
allocate(IIO_stringPos(1), source=0_pInt)
|
|
||||||
right = 0
|
|
||||||
|
|
||||||
do while (verify(string(right+1:),SEP)>0)
|
|
||||||
left = right + verify(string(right+1:),SEP)
|
|
||||||
right = left + scan(string(left:),SEP) - 2
|
|
||||||
if ( string(left:left) == '#' ) exit
|
|
||||||
IIO_stringPos = [IIO_stringPos,int(left, pInt), int(right, pInt)]
|
|
||||||
IIO_stringPos(1) = IIO_stringPos(1)+1_pInt
|
|
||||||
enddo
|
|
||||||
|
|
||||||
end function IIO_stringPos
|
|
||||||
|
|
||||||
|
|
||||||
end module
|
|
|
@ -1,715 +0,0 @@
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! $Id$
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @author Pratheek Shanthraj, Max-Planck-Institut für Eisenforschung GmbH
|
|
||||||
!> @author Martin Diehl, Max-Planck-Institut für Eisenforschung GmbH
|
|
||||||
!> @author Philip Eisenlohr, Max-Planck-Institut für Eisenforschung GmbH
|
|
||||||
!> @brief AL scheme solver
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
module spectral_mech_AL
|
|
||||||
use prec, only: &
|
|
||||||
pInt, &
|
|
||||||
pReal
|
|
||||||
use math, only: &
|
|
||||||
math_I3
|
|
||||||
use spectral_utilities, only: &
|
|
||||||
tSolutionState, &
|
|
||||||
tSolutionParams
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
private
|
|
||||||
#include <petsc/finclude/petsc.h90>
|
|
||||||
|
|
||||||
character (len=*), parameter, public :: &
|
|
||||||
DAMASK_spectral_solverAL_label = 'al'
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! derived types
|
|
||||||
type(tSolutionParams), private :: params
|
|
||||||
real(pReal), private, dimension(3,3) :: mask_stress = 0.0_pReal
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! PETSc data
|
|
||||||
DM, private :: da
|
|
||||||
SNES, private :: snes
|
|
||||||
Vec, private :: solution_vec
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! common pointwise data
|
|
||||||
real(pReal), private, dimension(:,:,:,:,:), allocatable :: &
|
|
||||||
F_lastInc, & !< field of previous compatible deformation gradients
|
|
||||||
F_lambda_lastInc, & !< field of previous incompatible deformation gradient
|
|
||||||
Fdot, & !< field of assumed rate of compatible deformation gradient
|
|
||||||
F_lambdaDot !< field of assumed rate of incopatible deformation gradient
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! stress, stiffness and compliance average etc.
|
|
||||||
real(pReal), private, dimension(3,3) :: &
|
|
||||||
F_aimDot, & !< assumed rate of average deformation gradient
|
|
||||||
F_aim = math_I3, & !< current prescribed deformation gradient
|
|
||||||
F_aim_lastInc = math_I3, & !< previous average deformation gradient
|
|
||||||
F_av = 0.0_pReal, & !< average incompatible def grad field
|
|
||||||
P_av = 0.0_pReal, & !< average 1st Piola--Kirchhoff stress
|
|
||||||
P_avLastEval = 0.0_pReal !< average 1st Piola--Kirchhoff stress last call of CPFEM_general
|
|
||||||
character(len=1024), private :: incInfo !< time and increment information
|
|
||||||
real(pReal), private, dimension(3,3,3,3) :: &
|
|
||||||
C_volAvg = 0.0_pReal, & !< current volume average stiffness
|
|
||||||
C_volAvgLastInc = 0.0_pReal, & !< previous volume average stiffness
|
|
||||||
C_minMaxAvg = 0.0_pReal, & !< current (min+max)/2 stiffness
|
|
||||||
S = 0.0_pReal, & !< current compliance (filled up with zeros)
|
|
||||||
C_scale = 0.0_pReal, &
|
|
||||||
S_scale = 0.0_pReal
|
|
||||||
|
|
||||||
real(pReal), private :: &
|
|
||||||
err_BC, & !< deviation from stress BC
|
|
||||||
err_curl, & !< RMS of curl of F
|
|
||||||
err_div !< RMS of div of P
|
|
||||||
logical, private :: ForwardData
|
|
||||||
integer(pInt), private :: &
|
|
||||||
totalIter = 0_pInt !< total iteration in current increment
|
|
||||||
|
|
||||||
public :: &
|
|
||||||
AL_init, &
|
|
||||||
AL_solution, &
|
|
||||||
AL_forward, &
|
|
||||||
AL_destroy
|
|
||||||
external :: &
|
|
||||||
VecDestroy, &
|
|
||||||
DMDestroy, &
|
|
||||||
DMDACreate3D, &
|
|
||||||
DMCreateGlobalVector, &
|
|
||||||
DMDASNESSetFunctionLocal, &
|
|
||||||
PETScFinalize, &
|
|
||||||
SNESDestroy, &
|
|
||||||
SNESGetNumberFunctionEvals, &
|
|
||||||
SNESGetIterationNumber, &
|
|
||||||
SNESSolve, &
|
|
||||||
SNESSetDM, &
|
|
||||||
SNESGetConvergedReason, &
|
|
||||||
SNESSetConvergenceTest, &
|
|
||||||
SNESSetFromOptions, &
|
|
||||||
SNESCreate, &
|
|
||||||
MPI_Abort, &
|
|
||||||
MPI_Bcast, &
|
|
||||||
MPI_Allreduce
|
|
||||||
|
|
||||||
contains
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief allocates all neccessary fields and fills them with data, potentially from restart info
|
|
||||||
!> @todo use sourced allocation, e.g. allocate(Fdot,source = F_lastInc)
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine AL_init
|
|
||||||
use, intrinsic :: iso_fortran_env ! to get compiler_version and compiler_options (at least for gfortran >4.6 at the moment)
|
|
||||||
use IO, only: &
|
|
||||||
IO_intOut, &
|
|
||||||
IO_read_realFile, &
|
|
||||||
IO_timeStamp
|
|
||||||
use debug, only: &
|
|
||||||
debug_level, &
|
|
||||||
debug_spectral, &
|
|
||||||
debug_spectralRestart
|
|
||||||
use FEsolving, only: &
|
|
||||||
restartInc
|
|
||||||
use numerics, only: &
|
|
||||||
worldrank, &
|
|
||||||
worldsize
|
|
||||||
use DAMASK_interface, only: &
|
|
||||||
getSolverJobName
|
|
||||||
use spectral_utilities, only: &
|
|
||||||
Utilities_constitutiveResponse, &
|
|
||||||
Utilities_updateGamma, &
|
|
||||||
Utilities_updateIPcoords
|
|
||||||
use mesh, only: &
|
|
||||||
grid, &
|
|
||||||
grid3
|
|
||||||
use math, only: &
|
|
||||||
math_invSym3333
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
real(pReal), dimension(3,3,grid(1),grid(2),grid3) :: P
|
|
||||||
real(pReal), dimension(3,3) :: &
|
|
||||||
temp33_Real = 0.0_pReal
|
|
||||||
|
|
||||||
PetscErrorCode :: ierr
|
|
||||||
PetscObject :: dummy
|
|
||||||
PetscScalar, pointer, dimension(:,:,:,:) :: xx_psc, F, F_lambda
|
|
||||||
integer(pInt), dimension(:), allocatable :: localK
|
|
||||||
integer(pInt) :: proc
|
|
||||||
character(len=1024) :: rankStr
|
|
||||||
|
|
||||||
if (worldrank == 0_pInt) then
|
|
||||||
write(6,'(/,a)') ' <<<+- DAMASK_spectral_solverAL init -+>>>'
|
|
||||||
write(6,'(a15,a)') ' Current time: ',IO_timeStamp()
|
|
||||||
#include "compilation_info.f90"
|
|
||||||
endif
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! allocate global fields
|
|
||||||
allocate (F_lastInc (3,3,grid(1),grid(2),grid3),source = 0.0_pReal)
|
|
||||||
allocate (Fdot (3,3,grid(1),grid(2),grid3),source = 0.0_pReal)
|
|
||||||
allocate (F_lambda_lastInc(3,3,grid(1),grid(2),grid3),source = 0.0_pReal)
|
|
||||||
allocate (F_lambdaDot (3,3,grid(1),grid(2),grid3),source = 0.0_pReal)
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! PETSc Init
|
|
||||||
call SNESCreate(PETSC_COMM_WORLD,snes,ierr); CHKERRQ(ierr)
|
|
||||||
call SNESSetOptionsPrefix(snes,'mech_',ierr);CHKERRQ(ierr)
|
|
||||||
allocate(localK(worldsize), source = 0); localK(worldrank+1) = grid3
|
|
||||||
do proc = 1, worldsize
|
|
||||||
call MPI_Bcast(localK(proc),1,MPI_INTEGER,proc-1,PETSC_COMM_WORLD,ierr)
|
|
||||||
enddo
|
|
||||||
call DMDACreate3d(PETSC_COMM_WORLD, &
|
|
||||||
DM_BOUNDARY_NONE, DM_BOUNDARY_NONE, DM_BOUNDARY_NONE, & ! cut off stencil at boundary
|
|
||||||
DMDA_STENCIL_BOX, & ! Moore (26) neighborhood around central point
|
|
||||||
grid(1),grid(2),grid(3), & ! global grid
|
|
||||||
1 , 1, worldsize, &
|
|
||||||
18, 0, & ! #dof (F tensor), ghost boundary width (domain overlap)
|
|
||||||
grid(1),grid(2),localK, & ! local grid
|
|
||||||
da,ierr) ! handle, error
|
|
||||||
CHKERRQ(ierr)
|
|
||||||
call SNESSetDM(snes,da,ierr); CHKERRQ(ierr)
|
|
||||||
call DMCreateGlobalVector(da,solution_vec,ierr); CHKERRQ(ierr)
|
|
||||||
call DMDASNESSetFunctionLocal(da,INSERT_VALUES,AL_formResidual,dummy,ierr)
|
|
||||||
CHKERRQ(ierr)
|
|
||||||
call SNESSetConvergenceTest(snes,AL_converged,dummy,PETSC_NULL_FUNCTION,ierr)
|
|
||||||
CHKERRQ(ierr)
|
|
||||||
call SNESSetFromOptions(snes,ierr); CHKERRQ(ierr)
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! init fields
|
|
||||||
call DMDAVecGetArrayF90(da,solution_vec,xx_psc,ierr); CHKERRQ(ierr) ! places pointer xx_psc on PETSc data
|
|
||||||
F => xx_psc(0:8,:,:,:)
|
|
||||||
F_lambda => xx_psc(9:17,:,:,:)
|
|
||||||
restart: if (restartInc > 1_pInt) then
|
|
||||||
if (iand(debug_level(debug_spectral),debug_spectralRestart)/= 0 .and. worldrank == 0_pInt) &
|
|
||||||
write(6,'(/,a,'//IO_intOut(restartInc-1_pInt)//',a)') &
|
|
||||||
'reading values of increment ', restartInc - 1_pInt, ' from file'
|
|
||||||
flush(6)
|
|
||||||
write(rankStr,'(a1,i0)')'_',worldrank
|
|
||||||
call IO_read_realFile(777,'F'//trim(rankStr), trim(getSolverJobName()),size(F))
|
|
||||||
read (777,rec=1) F
|
|
||||||
close (777)
|
|
||||||
call IO_read_realFile(777,'F_lastInc'//trim(rankStr), trim(getSolverJobName()),size(F_lastInc))
|
|
||||||
read (777,rec=1) F_lastInc
|
|
||||||
close (777)
|
|
||||||
call IO_read_realFile(777,'F_lambda'//trim(rankStr),trim(getSolverJobName()),size(F_lambda))
|
|
||||||
read (777,rec=1) F_lambda
|
|
||||||
close (777)
|
|
||||||
call IO_read_realFile(777,'F_lambda_lastInc'//trim(rankStr),&
|
|
||||||
trim(getSolverJobName()),size(F_lambda_lastInc))
|
|
||||||
read (777,rec=1) F_lambda_lastInc
|
|
||||||
close (777)
|
|
||||||
call IO_read_realFile(777,'F_aim', trim(getSolverJobName()),size(F_aim))
|
|
||||||
read (777,rec=1) F_aim
|
|
||||||
close (777)
|
|
||||||
call IO_read_realFile(777,'F_aim_lastInc', trim(getSolverJobName()),size(F_aim_lastInc))
|
|
||||||
read (777,rec=1) F_aim_lastInc
|
|
||||||
close (777)
|
|
||||||
call IO_read_realFile(777,'F_aimDot',trim(getSolverJobName()),size(f_aimDot))
|
|
||||||
read (777,rec=1) f_aimDot
|
|
||||||
close (777)
|
|
||||||
elseif (restartInc == 1_pInt) then restart
|
|
||||||
F_lastInc = spread(spread(spread(math_I3,3,grid(1)),4,grid(2)),5,grid3) ! initialize to identity
|
|
||||||
F = reshape(F_lastInc,[9,grid(1),grid(2),grid3])
|
|
||||||
F_lambda = F
|
|
||||||
F_lambda_lastInc = F_lastInc
|
|
||||||
endif restart
|
|
||||||
|
|
||||||
|
|
||||||
call Utilities_updateIPcoords(reshape(F,shape(F_lastInc)))
|
|
||||||
call Utilities_constitutiveResponse(F_lastInc, reshape(F,shape(F_lastInc)), &
|
|
||||||
0.0_pReal,P,C_volAvg,C_minMaxAvg,temp33_Real,.false.,math_I3)
|
|
||||||
nullify(F)
|
|
||||||
nullify(F_lambda)
|
|
||||||
call DMDAVecRestoreArrayF90(da,solution_vec,xx_psc,ierr); CHKERRQ(ierr) ! write data back to PETSc
|
|
||||||
|
|
||||||
readRestart: if (restartInc > 1_pInt) then
|
|
||||||
if (iand(debug_level(debug_spectral),debug_spectralRestart)/= 0 .and. worldrank == 0_pInt) &
|
|
||||||
write(6,'(/,a,'//IO_intOut(restartInc-1_pInt)//',a)') &
|
|
||||||
'reading more values of increment', restartInc - 1_pInt, 'from file'
|
|
||||||
flush(6)
|
|
||||||
call IO_read_realFile(777,'C_volAvg',trim(getSolverJobName()),size(C_volAvg))
|
|
||||||
read (777,rec=1) C_volAvg
|
|
||||||
close (777)
|
|
||||||
call IO_read_realFile(777,'C_volAvgLastInc',trim(getSolverJobName()),size(C_volAvgLastInc))
|
|
||||||
read (777,rec=1) C_volAvgLastInc
|
|
||||||
close (777)
|
|
||||||
call IO_read_realFile(777,'C_ref',trim(getSolverJobName()),size(C_minMaxAvg))
|
|
||||||
read (777,rec=1) C_minMaxAvg
|
|
||||||
close (777)
|
|
||||||
endif readRestart
|
|
||||||
|
|
||||||
call Utilities_updateGamma(C_minMaxAvg,.True.)
|
|
||||||
C_scale = C_minMaxAvg
|
|
||||||
S_scale = math_invSym3333(C_minMaxAvg)
|
|
||||||
|
|
||||||
end subroutine AL_init
|
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief solution for the AL scheme with internal iterations
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
type(tSolutionState) function &
|
|
||||||
AL_solution(incInfoIn,guess,timeinc,timeinc_old,loadCaseTime,P_BC,F_BC,rotation_BC)
|
|
||||||
use IO, only: &
|
|
||||||
IO_error
|
|
||||||
use numerics, only: &
|
|
||||||
update_gamma
|
|
||||||
use math, only: &
|
|
||||||
math_invSym3333
|
|
||||||
use spectral_utilities, only: &
|
|
||||||
tBoundaryCondition, &
|
|
||||||
Utilities_maskedCompliance, &
|
|
||||||
Utilities_updateGamma
|
|
||||||
use FEsolving, only: &
|
|
||||||
restartWrite, &
|
|
||||||
terminallyIll
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! input data for solution
|
|
||||||
real(pReal), intent(in) :: &
|
|
||||||
timeinc, & !< increment in time for current solution
|
|
||||||
timeinc_old, & !< increment in time of last increment
|
|
||||||
loadCaseTime !< remaining time of current load case
|
|
||||||
logical, intent(in) :: &
|
|
||||||
guess
|
|
||||||
type(tBoundaryCondition), intent(in) :: &
|
|
||||||
P_BC, &
|
|
||||||
F_BC
|
|
||||||
character(len=*), intent(in) :: &
|
|
||||||
incInfoIn
|
|
||||||
real(pReal), dimension(3,3), intent(in) :: rotation_BC
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! PETSc Data
|
|
||||||
PetscErrorCode :: ierr
|
|
||||||
SNESConvergedReason :: reason
|
|
||||||
|
|
||||||
incInfo = incInfoIn
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! update stiffness (and gamma operator)
|
|
||||||
S = Utilities_maskedCompliance(rotation_BC,P_BC%maskLogical,C_volAvg)
|
|
||||||
if (update_gamma) then
|
|
||||||
call Utilities_updateGamma(C_minMaxAvg,restartWrite)
|
|
||||||
C_scale = C_minMaxAvg
|
|
||||||
S_scale = math_invSym3333(C_minMaxAvg)
|
|
||||||
endif
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! set module wide availabe data
|
|
||||||
mask_stress = P_BC%maskFloat
|
|
||||||
params%P_BC = P_BC%values
|
|
||||||
params%rotation_BC = rotation_BC
|
|
||||||
params%timeinc = timeinc
|
|
||||||
params%timeincOld = timeinc_old
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! solve BVP
|
|
||||||
call SNESSolve(snes,PETSC_NULL_OBJECT,solution_vec,ierr)
|
|
||||||
CHKERRQ(ierr)
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! check convergence
|
|
||||||
call SNESGetConvergedReason(snes,reason,ierr)
|
|
||||||
CHKERRQ(ierr)
|
|
||||||
AL_solution%termIll = terminallyIll
|
|
||||||
terminallyIll = .false.
|
|
||||||
if (reason == -4) call IO_error(893_pInt)
|
|
||||||
if (reason < 1) AL_solution%converged = .false.
|
|
||||||
AL_solution%iterationsNeeded = totalIter
|
|
||||||
|
|
||||||
end function AL_solution
|
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief forms the AL residual vector
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine AL_formResidual(in,x_scal,f_scal,dummy,ierr)
|
|
||||||
use numerics, only: &
|
|
||||||
itmax, &
|
|
||||||
itmin, &
|
|
||||||
polarAlpha, &
|
|
||||||
polarBeta, &
|
|
||||||
worldrank
|
|
||||||
use mesh, only: &
|
|
||||||
grid3, &
|
|
||||||
grid
|
|
||||||
use IO, only: &
|
|
||||||
IO_intOut
|
|
||||||
use math, only: &
|
|
||||||
math_rotate_backward33, &
|
|
||||||
math_transpose33, &
|
|
||||||
math_mul3333xx33, &
|
|
||||||
math_invSym3333, &
|
|
||||||
math_mul33x33
|
|
||||||
use spectral_utilities, only: &
|
|
||||||
wgt, &
|
|
||||||
tensorField_real, &
|
|
||||||
utilities_FFTtensorForward, &
|
|
||||||
utilities_fourierGammaConvolution, &
|
|
||||||
utilities_FFTtensorBackward, &
|
|
||||||
Utilities_constitutiveResponse, &
|
|
||||||
Utilities_divergenceRMS, &
|
|
||||||
Utilities_curlRMS
|
|
||||||
use debug, only: &
|
|
||||||
debug_level, &
|
|
||||||
debug_spectral, &
|
|
||||||
debug_spectralRotation
|
|
||||||
use homogenization, only: &
|
|
||||||
materialpoint_dPdF
|
|
||||||
use FEsolving, only: &
|
|
||||||
terminallyIll
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! strange syntax in the next line because otherwise macros expand beyond 132 character limit
|
|
||||||
DMDALocalInfo, dimension(&
|
|
||||||
DMDA_LOCAL_INFO_SIZE) :: &
|
|
||||||
in
|
|
||||||
PetscScalar, target, dimension(3,3,2, &
|
|
||||||
XG_RANGE,YG_RANGE,ZG_RANGE) :: &
|
|
||||||
x_scal
|
|
||||||
PetscScalar, target, dimension(3,3,2, &
|
|
||||||
X_RANGE,Y_RANGE,Z_RANGE) :: &
|
|
||||||
f_scal
|
|
||||||
PetscScalar, pointer, dimension(:,:,:,:,:) :: &
|
|
||||||
F, &
|
|
||||||
F_lambda, &
|
|
||||||
residual_F, &
|
|
||||||
residual_F_lambda
|
|
||||||
PetscInt :: &
|
|
||||||
PETScIter, &
|
|
||||||
nfuncs
|
|
||||||
PetscObject :: dummy
|
|
||||||
PetscErrorCode :: ierr
|
|
||||||
integer(pInt) :: &
|
|
||||||
i, j, k, e
|
|
||||||
|
|
||||||
F => x_scal(1:3,1:3,1,&
|
|
||||||
XG_RANGE,YG_RANGE,ZG_RANGE)
|
|
||||||
F_lambda => x_scal(1:3,1:3,2,&
|
|
||||||
XG_RANGE,YG_RANGE,ZG_RANGE)
|
|
||||||
residual_F => f_scal(1:3,1:3,1,&
|
|
||||||
X_RANGE,Y_RANGE,Z_RANGE)
|
|
||||||
residual_F_lambda => f_scal(1:3,1:3,2,&
|
|
||||||
X_RANGE,Y_RANGE,Z_RANGE)
|
|
||||||
|
|
||||||
call SNESGetNumberFunctionEvals(snes,nfuncs,ierr); CHKERRQ(ierr)
|
|
||||||
call SNESGetIterationNumber(snes,PETScIter,ierr); CHKERRQ(ierr)
|
|
||||||
|
|
||||||
F_av = sum(sum(sum(F,dim=5),dim=4),dim=3) * wgt
|
|
||||||
call MPI_Allreduce(MPI_IN_PLACE,F_av,9,MPI_DOUBLE,MPI_SUM,PETSC_COMM_WORLD,ierr)
|
|
||||||
|
|
||||||
if(nfuncs== 0 .and. PETScIter == 0) totalIter = -1_pInt ! new increment
|
|
||||||
newIteration: if(totalIter <= PETScIter) then
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! report begin of new iteration
|
|
||||||
totalIter = totalIter + 1_pInt
|
|
||||||
if (worldrank == 0_pInt) then
|
|
||||||
write(6,'(1x,a,3(a,'//IO_intOut(itmax)//'))') trim(incInfo), &
|
|
||||||
' @ Iteration ', itmin, '≤',totalIter, '≤', itmax
|
|
||||||
if (iand(debug_level(debug_spectral),debug_spectralRotation) /= 0) &
|
|
||||||
write(6,'(/,a,/,3(3(f12.7,1x)/))',advance='no') ' deformation gradient aim (lab) =', &
|
|
||||||
math_transpose33(math_rotate_backward33(F_aim,params%rotation_BC))
|
|
||||||
write(6,'(/,a,/,3(3(f12.7,1x)/))',advance='no') ' deformation gradient aim =', &
|
|
||||||
math_transpose33(F_aim)
|
|
||||||
flush(6)
|
|
||||||
endif
|
|
||||||
endif newIteration
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!
|
|
||||||
tensorField_real = 0.0_pReal
|
|
||||||
do k = 1_pInt, grid3; do j = 1_pInt, grid(2); do i = 1_pInt, grid(1)
|
|
||||||
tensorField_real(1:3,1:3,i,j,k) = &
|
|
||||||
polarBeta*math_mul3333xx33(C_scale,F(1:3,1:3,i,j,k) - math_I3) -&
|
|
||||||
polarAlpha*math_mul33x33(F(1:3,1:3,i,j,k), &
|
|
||||||
math_mul3333xx33(C_scale,F_lambda(1:3,1:3,i,j,k) - math_I3))
|
|
||||||
|
|
||||||
enddo; enddo; enddo
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! doing convolution in Fourier space
|
|
||||||
call utilities_FFTtensorForward()
|
|
||||||
call utilities_fourierGammaConvolution(math_rotate_backward33(polarBeta*F_aim,params%rotation_BC))
|
|
||||||
call utilities_FFTtensorBackward()
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! constructing residual
|
|
||||||
residual_F_lambda = polarBeta*F - tensorField_real(1:3,1:3,1:grid(1),1:grid(2),1:grid3)
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! evaluate constitutive response
|
|
||||||
P_avLastEval = P_av
|
|
||||||
call Utilities_constitutiveResponse(F_lastInc,F - residual_F_lambda/polarBeta,params%timeinc, &
|
|
||||||
residual_F,C_volAvg,C_minMaxAvg,P_av,ForwardData,params%rotation_BC)
|
|
||||||
call MPI_Allreduce(MPI_IN_PLACE,terminallyIll,1,MPI_LOGICAL,MPI_LOR,PETSC_COMM_WORLD,ierr)
|
|
||||||
ForwardData = .False.
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! calculate divergence
|
|
||||||
tensorField_real = 0.0_pReal
|
|
||||||
tensorField_real(1:3,1:3,1:grid(1),1:grid(2),1:grid3) = residual_F
|
|
||||||
call utilities_FFTtensorForward()
|
|
||||||
err_div = Utilities_divergenceRMS()
|
|
||||||
call utilities_FFTtensorBackward()
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! constructing residual
|
|
||||||
e = 0_pInt
|
|
||||||
do k = 1_pInt, grid3; do j = 1_pInt, grid(2); do i = 1_pInt, grid(1)
|
|
||||||
e = e + 1_pInt
|
|
||||||
residual_F(1:3,1:3,i,j,k) = math_mul3333xx33(math_invSym3333(materialpoint_dPdF(1:3,1:3,1:3,1:3,1,e) + C_scale), &
|
|
||||||
residual_F(1:3,1:3,i,j,k) - &
|
|
||||||
math_mul33x33(F(1:3,1:3,i,j,k), &
|
|
||||||
math_mul3333xx33(C_scale,F_lambda(1:3,1:3,i,j,k) - math_I3))) &
|
|
||||||
+ residual_F_lambda(1:3,1:3,i,j,k)
|
|
||||||
enddo; enddo; enddo
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! calculating curl
|
|
||||||
tensorField_real = 0.0_pReal
|
|
||||||
tensorField_real(1:3,1:3,1:grid(1),1:grid(2),1:grid3) = F
|
|
||||||
call utilities_FFTtensorForward()
|
|
||||||
err_curl = Utilities_curlRMS()
|
|
||||||
call utilities_FFTtensorBackward()
|
|
||||||
|
|
||||||
end subroutine AL_formResidual
|
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief convergence check
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine AL_converged(snes_local,PETScIter,xnorm,snorm,fnorm,reason,dummy,ierr)
|
|
||||||
use numerics, only: &
|
|
||||||
itmax, &
|
|
||||||
itmin, &
|
|
||||||
err_div_tolRel, &
|
|
||||||
err_div_tolAbs, &
|
|
||||||
err_curl_tolRel, &
|
|
||||||
err_curl_tolAbs, &
|
|
||||||
err_stress_tolAbs, &
|
|
||||||
err_stress_tolRel, &
|
|
||||||
worldrank
|
|
||||||
use math, only: &
|
|
||||||
math_mul3333xx33
|
|
||||||
use FEsolving, only: &
|
|
||||||
terminallyIll
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
SNES :: snes_local
|
|
||||||
PetscInt :: PETScIter
|
|
||||||
PetscReal :: &
|
|
||||||
xnorm, &
|
|
||||||
snorm, &
|
|
||||||
fnorm
|
|
||||||
SNESConvergedReason :: reason
|
|
||||||
PetscObject :: dummy
|
|
||||||
PetscErrorCode ::ierr
|
|
||||||
real(pReal) :: &
|
|
||||||
curlTol, &
|
|
||||||
divTol, &
|
|
||||||
BC_tol
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! stress BC handling
|
|
||||||
F_aim = F_aim - math_mul3333xx33(S, ((P_av - params%P_BC))) ! S = 0.0 for no bc
|
|
||||||
err_BC = maxval(abs((-mask_stress+1.0_pReal)*math_mul3333xx33(C_scale,F_aim-F_av) + &
|
|
||||||
mask_stress *(P_av - params%P_BC))) ! mask = 0.0 for no bc
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! error calculation
|
|
||||||
curlTol = max(maxval(abs(F_aim-math_I3))*err_curl_tolRel,err_curl_tolAbs)
|
|
||||||
divTol = max(maxval(abs(P_av)) *err_div_tolRel,err_div_tolAbs)
|
|
||||||
BC_tol = max(maxval(abs(P_av)) *err_stress_tolrel,err_stress_tolabs)
|
|
||||||
|
|
||||||
converged: if ((totalIter >= itmin .and. &
|
|
||||||
all([ err_div/divTol, &
|
|
||||||
err_curl/curlTol, &
|
|
||||||
err_BC/BC_tol ] < 1.0_pReal)) &
|
|
||||||
.or. terminallyIll) then
|
|
||||||
reason = 1
|
|
||||||
elseif (totalIter >= itmax) then converged
|
|
||||||
reason = -1
|
|
||||||
else converged
|
|
||||||
reason = 0
|
|
||||||
endif converged
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! report
|
|
||||||
if (worldrank == 0_pInt) then
|
|
||||||
write(6,'(1/,a)') ' ... reporting .............................................................'
|
|
||||||
write(6,'(/,a,f12.2,a,es8.2,a,es9.2,a)') ' error curl = ', &
|
|
||||||
err_curl/curlTol,' (',err_curl,' -, tol =',curlTol,')'
|
|
||||||
write(6,' (a,f12.2,a,es8.2,a,es9.2,a)') ' error divergence = ', &
|
|
||||||
err_div/divTol, ' (',err_div, ' / m, tol =',divTol,')'
|
|
||||||
write(6,' (a,f12.2,a,es8.2,a,es9.2,a)') ' error BC = ', &
|
|
||||||
err_BC/BC_tol, ' (',err_BC, ' Pa, tol =',BC_tol,')'
|
|
||||||
write(6,'(/,a)') ' ==========================================================================='
|
|
||||||
flush(6)
|
|
||||||
endif
|
|
||||||
|
|
||||||
end subroutine AL_converged
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief forwarding routine
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine AL_forward(guess,timeinc,timeinc_old,loadCaseTime,F_BC,P_BC,rotation_BC)
|
|
||||||
use math, only: &
|
|
||||||
math_mul33x33, &
|
|
||||||
math_mul3333xx33, &
|
|
||||||
math_transpose33, &
|
|
||||||
math_rotate_backward33
|
|
||||||
use numerics, only: &
|
|
||||||
worldrank
|
|
||||||
use mesh, only: &
|
|
||||||
grid3, &
|
|
||||||
grid
|
|
||||||
use spectral_utilities, only: &
|
|
||||||
Utilities_calculateRate, &
|
|
||||||
Utilities_forwardField, &
|
|
||||||
Utilities_updateIPcoords, &
|
|
||||||
tBoundaryCondition, &
|
|
||||||
cutBack
|
|
||||||
use IO, only: &
|
|
||||||
IO_write_JobRealFile
|
|
||||||
use FEsolving, only: &
|
|
||||||
restartWrite
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
real(pReal), intent(in) :: &
|
|
||||||
timeinc_old, &
|
|
||||||
timeinc, &
|
|
||||||
loadCaseTime !< remaining time of current load case
|
|
||||||
type(tBoundaryCondition), intent(in) :: &
|
|
||||||
P_BC, &
|
|
||||||
F_BC
|
|
||||||
real(pReal), dimension(3,3), intent(in) :: rotation_BC
|
|
||||||
logical, intent(in) :: &
|
|
||||||
guess
|
|
||||||
PetscErrorCode :: ierr
|
|
||||||
PetscScalar, dimension(:,:,:,:), pointer :: xx_psc, F, F_lambda
|
|
||||||
integer(pInt) :: i, j, k
|
|
||||||
real(pReal), dimension(3,3) :: F_lambda33
|
|
||||||
character(len=1024) :: rankStr
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! update coordinates and rate and forward last inc
|
|
||||||
call DMDAVecGetArrayF90(da,solution_vec,xx_psc,ierr)
|
|
||||||
F => xx_psc(0:8,:,:,:)
|
|
||||||
F_lambda => xx_psc(9:17,:,:,:)
|
|
||||||
if (restartWrite) then
|
|
||||||
if (worldrank == 0_pInt) then
|
|
||||||
write(6,'(/,a)') ' writing converged results for restart'
|
|
||||||
flush(6)
|
|
||||||
endif
|
|
||||||
write(rankStr,'(a1,i0)')'_',worldrank
|
|
||||||
call IO_write_jobRealFile(777,'F'//trim(rankStr),size(F)) ! writing deformation gradient field to file
|
|
||||||
write (777,rec=1) F
|
|
||||||
close (777)
|
|
||||||
call IO_write_jobRealFile(777,'F_lastInc'//trim(rankStr),size(F_lastInc)) ! writing F_lastInc field to file
|
|
||||||
write (777,rec=1) F_lastInc
|
|
||||||
close (777)
|
|
||||||
call IO_write_jobRealFile(777,'F_lambda'//trim(rankStr),size(F_lambda)) ! writing deformation gradient field to file
|
|
||||||
write (777,rec=1) F_lambda
|
|
||||||
close (777)
|
|
||||||
call IO_write_jobRealFile(777,'F_lambda_lastInc'//trim(rankStr),size(F_lambda_lastInc)) ! writing F_lastInc field to file
|
|
||||||
write (777,rec=1) F_lambda_lastInc
|
|
||||||
close (777)
|
|
||||||
if (worldrank == 0_pInt) then
|
|
||||||
call IO_write_jobRealFile(777,'F_aim',size(F_aim))
|
|
||||||
write (777,rec=1) F_aim
|
|
||||||
close(777)
|
|
||||||
call IO_write_jobRealFile(777,'F_aim_lastInc',size(F_aim_lastInc))
|
|
||||||
write (777,rec=1) F_aim_lastInc
|
|
||||||
close(777)
|
|
||||||
call IO_write_jobRealFile(777,'F_aimDot',size(F_aimDot))
|
|
||||||
write (777,rec=1) F_aimDot
|
|
||||||
close(777)
|
|
||||||
call IO_write_jobRealFile(777,'C_volAvg',size(C_volAvg))
|
|
||||||
write (777,rec=1) C_volAvg
|
|
||||||
close(777)
|
|
||||||
call IO_write_jobRealFile(777,'C_volAvgLastInc',size(C_volAvgLastInc))
|
|
||||||
write (777,rec=1) C_volAvgLastInc
|
|
||||||
close(777)
|
|
||||||
endif
|
|
||||||
endif
|
|
||||||
|
|
||||||
call utilities_updateIPcoords(F)
|
|
||||||
|
|
||||||
if (cutBack) then
|
|
||||||
F_aim = F_aim_lastInc
|
|
||||||
F_lambda = reshape(F_lambda_lastInc,[9,grid(1),grid(2),grid3])
|
|
||||||
F = reshape(F_lastInc, [9,grid(1),grid(2),grid3])
|
|
||||||
C_volAvg = C_volAvgLastInc
|
|
||||||
else
|
|
||||||
ForwardData = .True.
|
|
||||||
C_volAvgLastInc = C_volAvg
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! calculate rate for aim
|
|
||||||
if (F_BC%myType=='l') then ! calculate f_aimDot from given L and current F
|
|
||||||
f_aimDot = F_BC%maskFloat * math_mul33x33(F_BC%values, F_aim)
|
|
||||||
elseif(F_BC%myType=='fdot') then ! f_aimDot is prescribed
|
|
||||||
f_aimDot = F_BC%maskFloat * F_BC%values
|
|
||||||
elseif(F_BC%myType=='f') then ! aim at end of load case is prescribed
|
|
||||||
f_aimDot = F_BC%maskFloat * (F_BC%values -F_aim)/loadCaseTime
|
|
||||||
endif
|
|
||||||
if (guess) f_aimDot = f_aimDot + P_BC%maskFloat * (F_aim - F_aim_lastInc)/timeinc_old
|
|
||||||
F_aim_lastInc = F_aim
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! update coordinates and rate and forward last inc
|
|
||||||
call utilities_updateIPcoords(F)
|
|
||||||
Fdot = Utilities_calculateRate(math_rotate_backward33(f_aimDot,rotation_BC), &
|
|
||||||
timeinc_old,guess,F_lastInc,reshape(F,[3,3,grid(1),grid(2),grid3]))
|
|
||||||
F_lambdaDot = Utilities_calculateRate(math_rotate_backward33(f_aimDot,rotation_BC), &
|
|
||||||
timeinc_old,guess,F_lambda_lastInc,reshape(F_lambda,[3,3,grid(1),grid(2),grid3]))
|
|
||||||
F_lastInc = reshape(F, [3,3,grid(1),grid(2),grid3])
|
|
||||||
F_lambda_lastInc = reshape(F_lambda,[3,3,grid(1),grid(2),grid3])
|
|
||||||
endif
|
|
||||||
|
|
||||||
F_aim = F_aim + f_aimDot * timeinc
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! update local deformation gradient
|
|
||||||
F = reshape(Utilities_forwardField(timeinc,F_lastInc,Fdot, & ! ensure that it matches rotated F_aim
|
|
||||||
math_rotate_backward33(F_aim,rotation_BC)), &
|
|
||||||
[9,grid(1),grid(2),grid3])
|
|
||||||
F_lambda = reshape(Utilities_forwardField(timeinc,F_lambda_lastInc,F_lambdadot), &
|
|
||||||
[9,grid(1),grid(2),grid3]) ! does not have any average value as boundary condition
|
|
||||||
if (.not. guess) then ! large strain forwarding
|
|
||||||
do k = 1_pInt, grid3; do j = 1_pInt, grid(2); do i = 1_pInt, grid(1)
|
|
||||||
F_lambda33 = reshape(F_lambda(1:9,i,j,k),[3,3])
|
|
||||||
F_lambda33 = math_mul3333xx33(S_scale,math_mul33x33(F_lambda33, &
|
|
||||||
math_mul3333xx33(C_scale,&
|
|
||||||
math_mul33x33(math_transpose33(F_lambda33),&
|
|
||||||
F_lambda33) -math_I3))*0.5_pReal)&
|
|
||||||
+ math_I3
|
|
||||||
F_lambda(1:9,i,j,k) = reshape(F_lambda33,[9])
|
|
||||||
enddo; enddo; enddo
|
|
||||||
endif
|
|
||||||
call DMDAVecRestoreArrayF90(da,solution_vec,xx_psc,ierr); CHKERRQ(ierr)
|
|
||||||
|
|
||||||
end subroutine AL_forward
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief destroy routine
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine AL_destroy()
|
|
||||||
use spectral_utilities, only: &
|
|
||||||
Utilities_destroy
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
PetscErrorCode :: ierr
|
|
||||||
|
|
||||||
call VecDestroy(solution_vec,ierr); CHKERRQ(ierr)
|
|
||||||
call SNESDestroy(snes,ierr); CHKERRQ(ierr)
|
|
||||||
call DMDestroy(da,ierr); CHKERRQ(ierr)
|
|
||||||
|
|
||||||
end subroutine AL_destroy
|
|
||||||
|
|
||||||
end module spectral_mech_AL
|
|
|
@ -1,569 +0,0 @@
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! $Id$
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @author Pratheek Shanthraj, Max-Planck-Institut für Eisenforschung GmbH
|
|
||||||
!> @author Martin Diehl, Max-Planck-Institut für Eisenforschung GmbH
|
|
||||||
!> @author Philip Eisenlohr, Max-Planck-Institut für Eisenforschung GmbH
|
|
||||||
!> @brief Basic scheme PETSc solver
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
module spectral_mech_basic
|
|
||||||
use prec, only: &
|
|
||||||
pInt, &
|
|
||||||
pReal
|
|
||||||
use math, only: &
|
|
||||||
math_I3
|
|
||||||
use spectral_utilities, only: &
|
|
||||||
tSolutionState, &
|
|
||||||
tSolutionParams
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
private
|
|
||||||
#include <petsc/finclude/petsc.h90>
|
|
||||||
|
|
||||||
character (len=*), parameter, public :: &
|
|
||||||
DAMASK_spectral_SolverBasicPETSC_label = 'basicpetsc'
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! derived types
|
|
||||||
type(tSolutionParams), private :: params
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! PETSc data
|
|
||||||
DM, private :: da
|
|
||||||
SNES, private :: snes
|
|
||||||
Vec, private :: solution_vec
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! common pointwise data
|
|
||||||
real(pReal), private, dimension(:,:,:,:,:), allocatable :: F_lastInc, Fdot
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! stress, stiffness and compliance average etc.
|
|
||||||
real(pReal), private, dimension(3,3) :: &
|
|
||||||
F_aim = math_I3, &
|
|
||||||
F_aim_lastIter = math_I3, &
|
|
||||||
F_aim_lastInc = math_I3, &
|
|
||||||
P_av = 0.0_pReal, &
|
|
||||||
F_aimDot=0.0_pReal
|
|
||||||
character(len=1024), private :: incInfo
|
|
||||||
real(pReal), private, dimension(3,3,3,3) :: &
|
|
||||||
C_volAvg = 0.0_pReal, & !< current volume average stiffness
|
|
||||||
C_volAvgLastInc = 0.0_pReal, & !< previous volume average stiffness
|
|
||||||
C_minMaxAvg = 0.0_pReal, & !< current (min+max)/2 stiffness
|
|
||||||
S = 0.0_pReal !< current compliance (filled up with zeros)
|
|
||||||
real(pReal), private :: err_stress, err_div
|
|
||||||
logical, private :: ForwardData
|
|
||||||
integer(pInt), private :: &
|
|
||||||
totalIter = 0_pInt !< total iteration in current increment
|
|
||||||
real(pReal), private, dimension(3,3) :: mask_stress = 0.0_pReal
|
|
||||||
|
|
||||||
public :: &
|
|
||||||
basicPETSc_init, &
|
|
||||||
basicPETSc_solution, &
|
|
||||||
BasicPETSc_forward, &
|
|
||||||
basicPETSc_destroy
|
|
||||||
external :: &
|
|
||||||
VecDestroy, &
|
|
||||||
DMDestroy, &
|
|
||||||
DMDACreate3D, &
|
|
||||||
DMCreateGlobalVector, &
|
|
||||||
DMDASNESSetFunctionLocal, &
|
|
||||||
PETScFinalize, &
|
|
||||||
SNESDestroy, &
|
|
||||||
SNESGetNumberFunctionEvals, &
|
|
||||||
SNESGetIterationNumber, &
|
|
||||||
SNESSolve, &
|
|
||||||
SNESSetDM, &
|
|
||||||
SNESGetConvergedReason, &
|
|
||||||
SNESSetConvergenceTest, &
|
|
||||||
SNESSetFromOptions, &
|
|
||||||
SNESCreate, &
|
|
||||||
MPI_Abort, &
|
|
||||||
MPI_Bcast, &
|
|
||||||
MPI_Allreduce
|
|
||||||
|
|
||||||
contains
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief allocates all neccessary fields and fills them with data, potentially from restart info
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine basicPETSc_init
|
|
||||||
use, intrinsic :: iso_fortran_env ! to get compiler_version and compiler_options (at least for gfortran >4.6 at the moment)
|
|
||||||
use IO, only: &
|
|
||||||
IO_intOut, &
|
|
||||||
IO_read_realFile, &
|
|
||||||
IO_timeStamp
|
|
||||||
use debug, only: &
|
|
||||||
debug_level, &
|
|
||||||
debug_spectral, &
|
|
||||||
debug_spectralRestart
|
|
||||||
use FEsolving, only: &
|
|
||||||
restartInc
|
|
||||||
use numerics, only: &
|
|
||||||
worldrank, &
|
|
||||||
worldsize
|
|
||||||
use DAMASK_interface, only: &
|
|
||||||
getSolverJobName
|
|
||||||
use spectral_utilities, only: &
|
|
||||||
Utilities_constitutiveResponse, &
|
|
||||||
Utilities_updateGamma, &
|
|
||||||
utilities_updateIPcoords, &
|
|
||||||
wgt
|
|
||||||
use mesh, only: &
|
|
||||||
grid, &
|
|
||||||
grid3
|
|
||||||
use math, only: &
|
|
||||||
math_invSym3333
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
real(pReal), dimension(3,3,grid(1),grid(2),grid3) :: P
|
|
||||||
PetscScalar, dimension(:,:,:,:), pointer :: F
|
|
||||||
PetscErrorCode :: ierr
|
|
||||||
PetscObject :: dummy
|
|
||||||
real(pReal), dimension(3,3) :: &
|
|
||||||
temp33_Real = 0.0_pReal
|
|
||||||
integer(pInt), dimension(:), allocatable :: localK
|
|
||||||
integer(pInt) :: proc
|
|
||||||
character(len=1024) :: rankStr
|
|
||||||
|
|
||||||
mainProcess: if (worldrank == 0_pInt) then
|
|
||||||
write(6,'(/,a)') ' <<<+- DAMASK_spectral_solverBasicPETSc init -+>>>'
|
|
||||||
write(6,'(a15,a)') ' Current time: ',IO_timeStamp()
|
|
||||||
#include "compilation_info.f90"
|
|
||||||
endif mainProcess
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! allocate global fields
|
|
||||||
allocate (F_lastInc (3,3,grid(1),grid(2),grid3),source = 0.0_pReal)
|
|
||||||
allocate (Fdot (3,3,grid(1),grid(2),grid3),source = 0.0_pReal)
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! initialize solver specific parts of PETSc
|
|
||||||
call SNESCreate(PETSC_COMM_WORLD,snes,ierr); CHKERRQ(ierr)
|
|
||||||
call SNESSetOptionsPrefix(snes,'mech_',ierr);CHKERRQ(ierr)
|
|
||||||
allocate(localK(worldsize), source = 0); localK(worldrank+1) = grid3
|
|
||||||
do proc = 1, worldsize
|
|
||||||
call MPI_Bcast(localK(proc),1,MPI_INTEGER,proc-1,PETSC_COMM_WORLD,ierr)
|
|
||||||
enddo
|
|
||||||
call DMDACreate3d(PETSC_COMM_WORLD, &
|
|
||||||
DM_BOUNDARY_NONE, DM_BOUNDARY_NONE, DM_BOUNDARY_NONE, & ! cut off stencil at boundary
|
|
||||||
DMDA_STENCIL_BOX, & ! Moore (26) neighborhood around central point
|
|
||||||
grid(1),grid(2),grid(3), & ! global grid
|
|
||||||
1, 1, worldsize, &
|
|
||||||
9, 0, & ! #dof (F tensor), ghost boundary width (domain overlap)
|
|
||||||
grid (1),grid (2),localK, & ! local grid
|
|
||||||
da,ierr) ! handle, error
|
|
||||||
CHKERRQ(ierr)
|
|
||||||
call SNESSetDM(snes,da,ierr); CHKERRQ(ierr)
|
|
||||||
call DMCreateGlobalVector(da,solution_vec,ierr); CHKERRQ(ierr) ! global solution vector (grid x 9, i.e. every def grad tensor)
|
|
||||||
call DMDASNESSetFunctionLocal(da,INSERT_VALUES,BasicPETSC_formResidual,dummy,ierr) ! residual vector of same shape as solution vector
|
|
||||||
CHKERRQ(ierr)
|
|
||||||
call SNESSetDM(snes,da,ierr); CHKERRQ(ierr) ! connect snes to da
|
|
||||||
call SNESSetConvergenceTest(snes,BasicPETSC_converged,dummy,PETSC_NULL_FUNCTION,ierr) ! specify custom convergence check function "_converged"
|
|
||||||
CHKERRQ(ierr)
|
|
||||||
call SNESSetFromOptions(snes,ierr); CHKERRQ(ierr) ! pull it all together with additional cli arguments
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! init fields
|
|
||||||
call DMDAVecGetArrayF90(da,solution_vec,F,ierr); CHKERRQ(ierr) ! get the data out of PETSc to work with
|
|
||||||
|
|
||||||
restart: if (restartInc > 1_pInt) then
|
|
||||||
if (iand(debug_level(debug_spectral),debug_spectralRestart)/= 0 .and. worldrank == 0_pInt) &
|
|
||||||
write(6,'(/,a,'//IO_intOut(restartInc-1_pInt)//',a)') &
|
|
||||||
'reading values of increment ', restartInc - 1_pInt, ' from file'
|
|
||||||
flush(6)
|
|
||||||
write(rankStr,'(a1,i0)')'_',worldrank
|
|
||||||
call IO_read_realFile(777,'F'//trim(rankStr),trim(getSolverJobName()),size(F))
|
|
||||||
read (777,rec=1) F
|
|
||||||
close (777)
|
|
||||||
call IO_read_realFile(777,'F_lastInc'//trim(rankStr),trim(getSolverJobName()),size(F_lastInc))
|
|
||||||
read (777,rec=1) F_lastInc
|
|
||||||
close (777)
|
|
||||||
call IO_read_realFile(777,'F_aimDot',trim(getSolverJobName()),size(f_aimDot))
|
|
||||||
read (777,rec=1) f_aimDot
|
|
||||||
close (777)
|
|
||||||
F_aim = reshape(sum(sum(sum(F,dim=4),dim=3),dim=2) * wgt, [3,3]) ! average of F
|
|
||||||
F_aim_lastInc = sum(sum(sum(F_lastInc,dim=5),dim=4),dim=3) * wgt ! average of F_lastInc
|
|
||||||
elseif (restartInc == 1_pInt) then restart
|
|
||||||
F_lastInc = spread(spread(spread(math_I3,3,grid(1)),4,grid(2)),5,grid3) ! initialize to identity
|
|
||||||
F = reshape(F_lastInc,[9,grid(1),grid(2),grid3])
|
|
||||||
endif restart
|
|
||||||
|
|
||||||
call Utilities_updateIPcoords(reshape(F,shape(F_lastInc)))
|
|
||||||
call Utilities_constitutiveResponse(F_lastInc, reshape(F,shape(F_lastInc)), &
|
|
||||||
0.0_pReal, &
|
|
||||||
P, &
|
|
||||||
C_volAvg,C_minMaxAvg, & ! global average of stiffness and (min+max)/2
|
|
||||||
temp33_Real, &
|
|
||||||
.false., &
|
|
||||||
math_I3)
|
|
||||||
|
|
||||||
call DMDAVecRestoreArrayF90(da,solution_vec,F,ierr); CHKERRQ(ierr) ! write data back to PETSc
|
|
||||||
|
|
||||||
restartRead: if (restartInc > 1_pInt) then
|
|
||||||
if (iand(debug_level(debug_spectral),debug_spectralRestart)/= 0 .and. worldrank == 0_pInt) &
|
|
||||||
write(6,'(/,a,'//IO_intOut(restartInc-1_pInt)//',a)') &
|
|
||||||
'reading more values of increment', restartInc - 1_pInt, 'from file'
|
|
||||||
flush(6)
|
|
||||||
call IO_read_realFile(777,'C_volAvg',trim(getSolverJobName()),size(C_volAvg))
|
|
||||||
read (777,rec=1) C_volAvg
|
|
||||||
close (777)
|
|
||||||
call IO_read_realFile(777,'C_volAvgLastInc',trim(getSolverJobName()),size(C_volAvgLastInc))
|
|
||||||
read (777,rec=1) C_volAvgLastInc
|
|
||||||
close (777)
|
|
||||||
call IO_read_realFile(777,'C_ref',trim(getSolverJobName()),size(C_minMaxAvg))
|
|
||||||
read (777,rec=1) C_minMaxAvg
|
|
||||||
close (777)
|
|
||||||
endif restartRead
|
|
||||||
|
|
||||||
call Utilities_updateGamma(C_minmaxAvg,.True.)
|
|
||||||
|
|
||||||
end subroutine basicPETSc_init
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief solution for the Basic PETSC scheme with internal iterations
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
type(tSolutionState) function &
|
|
||||||
basicPETSc_solution(incInfoIn,guess,timeinc,timeinc_old,loadCaseTime,P_BC,F_BC,rotation_BC)
|
|
||||||
use IO, only: &
|
|
||||||
IO_error
|
|
||||||
use numerics, only: &
|
|
||||||
update_gamma
|
|
||||||
use spectral_utilities, only: &
|
|
||||||
tBoundaryCondition, &
|
|
||||||
Utilities_maskedCompliance, &
|
|
||||||
Utilities_updateGamma
|
|
||||||
use FEsolving, only: &
|
|
||||||
restartWrite, &
|
|
||||||
terminallyIll
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! input data for solution
|
|
||||||
real(pReal), intent(in) :: &
|
|
||||||
timeinc, & !< increment in time for current solution
|
|
||||||
timeinc_old, & !< increment in time of last increment
|
|
||||||
loadCaseTime !< remaining time of current load case
|
|
||||||
type(tBoundaryCondition), intent(in) :: &
|
|
||||||
P_BC, &
|
|
||||||
F_BC
|
|
||||||
character(len=*), intent(in) :: &
|
|
||||||
incInfoIn
|
|
||||||
real(pReal), dimension(3,3), intent(in) :: rotation_BC
|
|
||||||
logical, intent(in) :: &
|
|
||||||
guess
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! PETSc Data
|
|
||||||
PetscErrorCode :: ierr
|
|
||||||
SNESConvergedReason :: reason
|
|
||||||
incInfo = incInfoIn
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! update stiffness (and gamma operator)
|
|
||||||
S = Utilities_maskedCompliance(rotation_BC,P_BC%maskLogical,C_volAvg)
|
|
||||||
if (update_gamma) call Utilities_updateGamma(C_minmaxAvg,restartWrite)
|
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! set module wide availabe data
|
|
||||||
mask_stress = P_BC%maskFloat
|
|
||||||
params%P_BC = P_BC%values
|
|
||||||
params%rotation_BC = rotation_BC
|
|
||||||
params%timeinc = timeinc
|
|
||||||
params%timeincOld = timeinc_old
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! solve BVP
|
|
||||||
call SNESSolve(snes,PETSC_NULL_OBJECT,solution_vec,ierr)
|
|
||||||
CHKERRQ(ierr)
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! check convergence
|
|
||||||
call SNESGetConvergedReason(snes,reason,ierr)
|
|
||||||
CHKERRQ(ierr)
|
|
||||||
basicPETSc_solution%termIll = terminallyIll
|
|
||||||
terminallyIll = .false.
|
|
||||||
BasicPETSc_solution%converged =.true.
|
|
||||||
if (reason == -4) call IO_error(893_pInt)
|
|
||||||
if (reason < 1) basicPETSC_solution%converged = .false.
|
|
||||||
basicPETSC_solution%iterationsNeeded = totalIter
|
|
||||||
|
|
||||||
end function BasicPETSc_solution
|
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief forms the AL residual vector
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine BasicPETSC_formResidual(in,x_scal,f_scal,dummy,ierr)
|
|
||||||
use numerics, only: &
|
|
||||||
itmax, &
|
|
||||||
itmin
|
|
||||||
use numerics, only: &
|
|
||||||
worldrank
|
|
||||||
use mesh, only: &
|
|
||||||
grid, &
|
|
||||||
grid3
|
|
||||||
use math, only: &
|
|
||||||
math_rotate_backward33, &
|
|
||||||
math_transpose33, &
|
|
||||||
math_mul3333xx33
|
|
||||||
use debug, only: &
|
|
||||||
debug_level, &
|
|
||||||
debug_spectral, &
|
|
||||||
debug_spectralRotation
|
|
||||||
use spectral_utilities, only: &
|
|
||||||
tensorField_real, &
|
|
||||||
utilities_FFTtensorForward, &
|
|
||||||
utilities_FFTtensorBackward, &
|
|
||||||
utilities_fourierGammaConvolution, &
|
|
||||||
Utilities_constitutiveResponse, &
|
|
||||||
Utilities_divergenceRMS
|
|
||||||
use IO, only: &
|
|
||||||
IO_intOut
|
|
||||||
use FEsolving, only: &
|
|
||||||
terminallyIll
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
DMDALocalInfo, dimension(DMDA_LOCAL_INFO_SIZE) :: &
|
|
||||||
in
|
|
||||||
PetscScalar, dimension(3,3, &
|
|
||||||
XG_RANGE,YG_RANGE,ZG_RANGE) :: &
|
|
||||||
x_scal
|
|
||||||
PetscScalar, dimension(3,3, &
|
|
||||||
X_RANGE,Y_RANGE,Z_RANGE) :: &
|
|
||||||
f_scal
|
|
||||||
PetscInt :: &
|
|
||||||
PETScIter, &
|
|
||||||
nfuncs
|
|
||||||
PetscObject :: dummy
|
|
||||||
PetscErrorCode :: ierr
|
|
||||||
|
|
||||||
call SNESGetNumberFunctionEvals(snes,nfuncs,ierr); CHKERRQ(ierr)
|
|
||||||
call SNESGetIterationNumber(snes,PETScIter,ierr); CHKERRQ(ierr)
|
|
||||||
|
|
||||||
if(nfuncs== 0 .and. PETScIter == 0) totalIter = -1_pInt ! new increment
|
|
||||||
newIteration: if (totalIter <= PETScIter) then
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! report begin of new iteration
|
|
||||||
totalIter = totalIter + 1_pInt
|
|
||||||
if (worldrank == 0_pInt) then
|
|
||||||
write(6,'(1x,a,3(a,'//IO_intOut(itmax)//'))') trim(incInfo), &
|
|
||||||
' @ Iteration ', itmin, '≤',totalIter, '≤', itmax
|
|
||||||
if (iand(debug_level(debug_spectral),debug_spectralRotation) /= 0) &
|
|
||||||
write(6,'(/,a,/,3(3(f12.7,1x)/))',advance='no') ' deformation gradient aim (lab) =', &
|
|
||||||
math_transpose33(math_rotate_backward33(F_aim,params%rotation_BC))
|
|
||||||
write(6,'(/,a,/,3(3(f12.7,1x)/))',advance='no') ' deformation gradient aim =', &
|
|
||||||
math_transpose33(F_aim)
|
|
||||||
flush(6)
|
|
||||||
endif
|
|
||||||
endif newIteration
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! evaluate constitutive response
|
|
||||||
call Utilities_constitutiveResponse(F_lastInc,x_scal,params%timeinc, &
|
|
||||||
f_scal,C_volAvg,C_minmaxAvg,P_av,ForwardData,params%rotation_BC)
|
|
||||||
call MPI_Allreduce(MPI_IN_PLACE,terminallyIll,1,MPI_LOGICAL,MPI_LOR,PETSC_COMM_WORLD,ierr)
|
|
||||||
ForwardData = .false.
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! stress BC handling
|
|
||||||
F_aim_lastIter = F_aim
|
|
||||||
F_aim = F_aim - math_mul3333xx33(S, ((P_av - params%P_BC))) ! S = 0.0 for no bc
|
|
||||||
err_stress = maxval(abs(mask_stress * (P_av - params%P_BC))) ! mask = 0.0 for no bc
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! updated deformation gradient using fix point algorithm of basic scheme
|
|
||||||
tensorField_real = 0.0_pReal
|
|
||||||
tensorField_real(1:3,1:3,1:grid(1),1:grid(2),1:grid3) = f_scal
|
|
||||||
call utilities_FFTtensorForward()
|
|
||||||
err_div = Utilities_divergenceRMS()
|
|
||||||
call utilities_fourierGammaConvolution(math_rotate_backward33(F_aim_lastIter-F_aim,params%rotation_BC))
|
|
||||||
call utilities_FFTtensorBackward()
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! constructing residual
|
|
||||||
f_scal = tensorField_real(1:3,1:3,1:grid(1),1:grid(2),1:grid3)
|
|
||||||
|
|
||||||
end subroutine BasicPETSc_formResidual
|
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief convergence check
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine BasicPETSc_converged(snes_local,PETScIter,xnorm,snorm,fnorm,reason,dummy,ierr)
|
|
||||||
use numerics, only: &
|
|
||||||
itmax, &
|
|
||||||
itmin, &
|
|
||||||
err_div_tolRel, &
|
|
||||||
err_div_tolAbs, &
|
|
||||||
err_stress_tolRel, &
|
|
||||||
err_stress_tolAbs, &
|
|
||||||
worldrank
|
|
||||||
use FEsolving, only: &
|
|
||||||
terminallyIll
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
SNES :: snes_local
|
|
||||||
PetscInt :: PETScIter
|
|
||||||
PetscReal :: &
|
|
||||||
xnorm, &
|
|
||||||
snorm, &
|
|
||||||
fnorm
|
|
||||||
SNESConvergedReason :: reason
|
|
||||||
PetscObject :: dummy
|
|
||||||
PetscErrorCode :: ierr
|
|
||||||
real(pReal) :: &
|
|
||||||
divTol, &
|
|
||||||
stressTol
|
|
||||||
|
|
||||||
divTol = max(maxval(abs(P_av))*err_div_tolRel,err_div_tolAbs)
|
|
||||||
stressTol = max(maxval(abs(P_av))*err_stress_tolrel,err_stress_tolabs)
|
|
||||||
|
|
||||||
converged: if ((totalIter >= itmin .and. &
|
|
||||||
all([ err_div/divTol, &
|
|
||||||
err_stress/stressTol ] < 1.0_pReal)) &
|
|
||||||
.or. terminallyIll) then
|
|
||||||
reason = 1
|
|
||||||
elseif (totalIter >= itmax) then converged
|
|
||||||
reason = -1
|
|
||||||
else converged
|
|
||||||
reason = 0
|
|
||||||
endif converged
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! report
|
|
||||||
if (worldrank == 0_pInt) then
|
|
||||||
write(6,'(1/,a)') ' ... reporting .............................................................'
|
|
||||||
write(6,'(1/,a,f12.2,a,es8.2,a,es9.2,a)') ' error divergence = ', &
|
|
||||||
err_div/divTol, ' (',err_div,' / m, tol =',divTol,')'
|
|
||||||
write(6,'(a,f12.2,a,es8.2,a,es9.2,a)') ' error stress BC = ', &
|
|
||||||
err_stress/stressTol, ' (',err_stress, ' Pa, tol =',stressTol,')'
|
|
||||||
write(6,'(/,a)') ' ==========================================================================='
|
|
||||||
flush(6)
|
|
||||||
endif
|
|
||||||
|
|
||||||
end subroutine BasicPETSc_converged
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief forwarding routine
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine BasicPETSc_forward(guess,timeinc,timeinc_old,loadCaseTime,F_BC,P_BC,rotation_BC)
|
|
||||||
use math, only: &
|
|
||||||
math_mul33x33 ,&
|
|
||||||
math_rotate_backward33
|
|
||||||
use mesh, only: &
|
|
||||||
grid, &
|
|
||||||
grid3
|
|
||||||
use spectral_utilities, only: &
|
|
||||||
Utilities_calculateRate, &
|
|
||||||
Utilities_forwardField, &
|
|
||||||
utilities_updateIPcoords, &
|
|
||||||
tBoundaryCondition, &
|
|
||||||
cutBack
|
|
||||||
use IO, only: &
|
|
||||||
IO_write_JobRealFile
|
|
||||||
use FEsolving, only: &
|
|
||||||
restartWrite
|
|
||||||
use numerics, only: &
|
|
||||||
worldrank
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
real(pReal), intent(in) :: &
|
|
||||||
timeinc_old, &
|
|
||||||
timeinc, &
|
|
||||||
loadCaseTime !< remaining time of current load case
|
|
||||||
type(tBoundaryCondition), intent(in) :: &
|
|
||||||
P_BC, &
|
|
||||||
F_BC
|
|
||||||
real(pReal), dimension(3,3), intent(in) :: rotation_BC
|
|
||||||
logical, intent(in) :: &
|
|
||||||
guess
|
|
||||||
PetscScalar, pointer :: F(:,:,:,:)
|
|
||||||
PetscErrorCode :: ierr
|
|
||||||
character(len=1024) :: rankStr
|
|
||||||
|
|
||||||
call DMDAVecGetArrayF90(da,solution_vec,F,ierr)
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! restart information for spectral solver
|
|
||||||
if (restartWrite) then
|
|
||||||
if (worldrank == 0_pInt) then
|
|
||||||
write(6,'(/,a)') ' writing converged results for restart'
|
|
||||||
flush(6)
|
|
||||||
endif
|
|
||||||
write(rankStr,'(a1,i0)')'_',worldrank
|
|
||||||
call IO_write_jobRealFile(777,'F'//trim(rankStr),size(F)) ! writing deformation gradient field to file
|
|
||||||
write (777,rec=1) F
|
|
||||||
close (777)
|
|
||||||
call IO_write_jobRealFile(777,'F_lastInc'//trim(rankStr),size(F_lastInc)) ! writing F_lastInc field to file
|
|
||||||
write (777,rec=1) F_lastInc
|
|
||||||
close (777)
|
|
||||||
if (worldrank == 0_pInt) then
|
|
||||||
call IO_write_jobRealFile(777,'F_aimDot',size(F_aimDot))
|
|
||||||
write (777,rec=1) F_aimDot
|
|
||||||
close(777)
|
|
||||||
call IO_write_jobRealFile(777,'C_volAvg',size(C_volAvg))
|
|
||||||
write (777,rec=1) C_volAvg
|
|
||||||
close(777)
|
|
||||||
call IO_write_jobRealFile(777,'C_volAvgLastInc',size(C_volAvgLastInc))
|
|
||||||
write (777,rec=1) C_volAvgLastInc
|
|
||||||
close(777)
|
|
||||||
endif
|
|
||||||
endif
|
|
||||||
|
|
||||||
call utilities_updateIPcoords(F)
|
|
||||||
|
|
||||||
if (cutBack) then
|
|
||||||
F_aim = F_aim_lastInc
|
|
||||||
F = reshape(F_lastInc, [9,grid(1),grid(2),grid3])
|
|
||||||
C_volAvg = C_volAvgLastInc
|
|
||||||
else
|
|
||||||
ForwardData = .True.
|
|
||||||
C_volAvgLastInc = C_volAvg
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! calculate rate for aim
|
|
||||||
if (F_BC%myType=='l') then ! calculate f_aimDot from given L and current F
|
|
||||||
f_aimDot = F_BC%maskFloat * math_mul33x33(F_BC%values, F_aim)
|
|
||||||
elseif(F_BC%myType=='fdot') then ! f_aimDot is prescribed
|
|
||||||
f_aimDot = F_BC%maskFloat * F_BC%values
|
|
||||||
elseif(F_BC%myType=='f') then ! aim at end of load case is prescribed
|
|
||||||
f_aimDot = F_BC%maskFloat * (F_BC%values -F_aim)/loadCaseTime
|
|
||||||
endif
|
|
||||||
if (guess) f_aimDot = f_aimDot + P_BC%maskFloat * (F_aim - F_aim_lastInc)/timeinc_old
|
|
||||||
F_aim_lastInc = F_aim
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! update coordinates and rate and forward last inc
|
|
||||||
call utilities_updateIPcoords(F)
|
|
||||||
Fdot = Utilities_calculateRate(math_rotate_backward33(f_aimDot,rotation_BC), &
|
|
||||||
timeinc_old,guess,F_lastInc,reshape(F,[3,3,grid(1),grid(2),grid3]))
|
|
||||||
F_lastInc = reshape(F, [3,3,grid(1),grid(2),grid3])
|
|
||||||
endif
|
|
||||||
F_aim = F_aim + f_aimDot * timeinc
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! update local deformation gradient
|
|
||||||
F = reshape(Utilities_forwardField(timeinc,F_lastInc,Fdot, & ! ensure that it matches rotated F_aim
|
|
||||||
math_rotate_backward33(F_aim,rotation_BC)),[9,grid(1),grid(2),grid3])
|
|
||||||
call DMDAVecRestoreArrayF90(da,solution_vec,F,ierr); CHKERRQ(ierr)
|
|
||||||
|
|
||||||
end subroutine BasicPETSc_forward
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief destroy routine
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine BasicPETSc_destroy()
|
|
||||||
use spectral_utilities, only: &
|
|
||||||
Utilities_destroy
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
PetscErrorCode :: ierr
|
|
||||||
|
|
||||||
call VecDestroy(solution_vec,ierr); CHKERRQ(ierr)
|
|
||||||
call SNESDestroy(snes,ierr); CHKERRQ(ierr)
|
|
||||||
call DMDestroy(da,ierr); CHKERRQ(ierr)
|
|
||||||
|
|
||||||
end subroutine BasicPETSc_destroy
|
|
||||||
|
|
||||||
end module spectral_mech_basic
|
|
|
@ -1,712 +0,0 @@
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! $Id$
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @author Pratheek Shanthraj, Max-Planck-Institut für Eisenforschung GmbH
|
|
||||||
!> @author Martin Diehl, Max-Planck-Institut für Eisenforschung GmbH
|
|
||||||
!> @author Philip Eisenlohr, Max-Planck-Institut für Eisenforschung GmbH
|
|
||||||
!> @brief Polarisation scheme solver
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
module spectral_mech_Polarisation
|
|
||||||
use prec, only: &
|
|
||||||
pInt, &
|
|
||||||
pReal
|
|
||||||
use math, only: &
|
|
||||||
math_I3
|
|
||||||
use spectral_utilities, only: &
|
|
||||||
tSolutionState, &
|
|
||||||
tSolutionParams
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
private
|
|
||||||
#include <petsc/finclude/petsc.h90>
|
|
||||||
|
|
||||||
character (len=*), parameter, public :: &
|
|
||||||
DAMASK_spectral_solverPolarisation_label = 'polarisation'
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! derived types
|
|
||||||
type(tSolutionParams), private :: params
|
|
||||||
real(pReal), private, dimension(3,3) :: mask_stress = 0.0_pReal
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! PETSc data
|
|
||||||
DM, private :: da
|
|
||||||
SNES, private :: snes
|
|
||||||
Vec, private :: solution_vec
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! common pointwise data
|
|
||||||
real(pReal), private, dimension(:,:,:,:,:), allocatable :: &
|
|
||||||
F_lastInc, & !< field of previous compatible deformation gradients
|
|
||||||
F_tau_lastInc, & !< field of previous incompatible deformation gradient
|
|
||||||
Fdot, & !< field of assumed rate of compatible deformation gradient
|
|
||||||
F_tauDot !< field of assumed rate of incopatible deformation gradient
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! stress, stiffness and compliance average etc.
|
|
||||||
real(pReal), private, dimension(3,3) :: &
|
|
||||||
F_aimDot, & !< assumed rate of average deformation gradient
|
|
||||||
F_aim = math_I3, & !< current prescribed deformation gradient
|
|
||||||
F_aim_lastInc = math_I3, & !< previous average deformation gradient
|
|
||||||
F_av = 0.0_pReal, & !< average incompatible def grad field
|
|
||||||
P_av = 0.0_pReal, & !< average 1st Piola--Kirchhoff stress
|
|
||||||
P_avLastEval = 0.0_pReal !< average 1st Piola--Kirchhoff stress last call of CPFEM_general
|
|
||||||
character(len=1024), private :: incInfo !< time and increment information
|
|
||||||
real(pReal), private, dimension(3,3,3,3) :: &
|
|
||||||
C_volAvg = 0.0_pReal, & !< current volume average stiffness
|
|
||||||
C_volAvgLastInc = 0.0_pReal, & !< previous volume average stiffness
|
|
||||||
C_minMaxAvg = 0.0_pReal, & !< current (min+max)/2 stiffness
|
|
||||||
S = 0.0_pReal, & !< current compliance (filled up with zeros)
|
|
||||||
C_scale = 0.0_pReal, &
|
|
||||||
S_scale = 0.0_pReal
|
|
||||||
|
|
||||||
real(pReal), private :: &
|
|
||||||
err_BC, & !< deviation from stress BC
|
|
||||||
err_curl, & !< RMS of curl of F
|
|
||||||
err_div !< RMS of div of P
|
|
||||||
logical, private :: ForwardData
|
|
||||||
integer(pInt), private :: &
|
|
||||||
totalIter = 0_pInt !< total iteration in current increment
|
|
||||||
|
|
||||||
public :: &
|
|
||||||
Polarisation_init, &
|
|
||||||
Polarisation_solution, &
|
|
||||||
Polarisation_forward, &
|
|
||||||
Polarisation_destroy
|
|
||||||
external :: &
|
|
||||||
VecDestroy, &
|
|
||||||
DMDestroy, &
|
|
||||||
DMDACreate3D, &
|
|
||||||
DMCreateGlobalVector, &
|
|
||||||
DMDASNESSetFunctionLocal, &
|
|
||||||
PETScFinalize, &
|
|
||||||
SNESDestroy, &
|
|
||||||
SNESGetNumberFunctionEvals, &
|
|
||||||
SNESGetIterationNumber, &
|
|
||||||
SNESSolve, &
|
|
||||||
SNESSetDM, &
|
|
||||||
SNESGetConvergedReason, &
|
|
||||||
SNESSetConvergenceTest, &
|
|
||||||
SNESSetFromOptions, &
|
|
||||||
SNESCreate, &
|
|
||||||
MPI_Abort, &
|
|
||||||
MPI_Bcast, &
|
|
||||||
MPI_Allreduce
|
|
||||||
|
|
||||||
contains
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief allocates all neccessary fields and fills them with data, potentially from restart info
|
|
||||||
!> @todo use sourced allocation, e.g. allocate(Fdot,source = F_lastInc)
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine Polarisation_init
|
|
||||||
use, intrinsic :: iso_fortran_env ! to get compiler_version and compiler_options (at least for gfortran >4.6 at the moment)
|
|
||||||
use IO, only: &
|
|
||||||
IO_intOut, &
|
|
||||||
IO_read_realFile, &
|
|
||||||
IO_timeStamp
|
|
||||||
use debug, only: &
|
|
||||||
debug_level, &
|
|
||||||
debug_spectral, &
|
|
||||||
debug_spectralRestart
|
|
||||||
use FEsolving, only: &
|
|
||||||
restartInc
|
|
||||||
use numerics, only: &
|
|
||||||
worldrank, &
|
|
||||||
worldsize
|
|
||||||
use DAMASK_interface, only: &
|
|
||||||
getSolverJobName
|
|
||||||
use spectral_utilities, only: &
|
|
||||||
Utilities_constitutiveResponse, &
|
|
||||||
Utilities_updateGamma, &
|
|
||||||
Utilities_updateIPcoords
|
|
||||||
use mesh, only: &
|
|
||||||
grid, &
|
|
||||||
grid3
|
|
||||||
use math, only: &
|
|
||||||
math_invSym3333
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
real(pReal), dimension(3,3,grid(1),grid(2),grid3) :: P
|
|
||||||
real(pReal), dimension(3,3) :: &
|
|
||||||
temp33_Real = 0.0_pReal
|
|
||||||
|
|
||||||
PetscErrorCode :: ierr
|
|
||||||
PetscObject :: dummy
|
|
||||||
PetscScalar, pointer, dimension(:,:,:,:) :: xx_psc, F, F_tau
|
|
||||||
integer(pInt), dimension(:), allocatable :: localK
|
|
||||||
integer(pInt) :: proc
|
|
||||||
character(len=1024) :: rankStr
|
|
||||||
|
|
||||||
if (worldrank == 0_pInt) then
|
|
||||||
write(6,'(/,a)') ' <<<+- DAMASK_spectral_solverPolarisation init -+>>>'
|
|
||||||
write(6,'(a15,a)') ' Current time: ',IO_timeStamp()
|
|
||||||
#include "compilation_info.f90"
|
|
||||||
endif
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! allocate global fields
|
|
||||||
allocate (F_lastInc (3,3,grid(1),grid(2),grid3),source = 0.0_pReal)
|
|
||||||
allocate (Fdot (3,3,grid(1),grid(2),grid3),source = 0.0_pReal)
|
|
||||||
allocate (F_tau_lastInc(3,3,grid(1),grid(2),grid3),source = 0.0_pReal)
|
|
||||||
allocate (F_tauDot (3,3,grid(1),grid(2),grid3),source = 0.0_pReal)
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! PETSc Init
|
|
||||||
call SNESCreate(PETSC_COMM_WORLD,snes,ierr); CHKERRQ(ierr)
|
|
||||||
call SNESSetOptionsPrefix(snes,'mech_',ierr);CHKERRQ(ierr)
|
|
||||||
allocate(localK(worldsize), source = 0); localK(worldrank+1) = grid3
|
|
||||||
do proc = 1, worldsize
|
|
||||||
call MPI_Bcast(localK(proc),1,MPI_INTEGER,proc-1,PETSC_COMM_WORLD,ierr)
|
|
||||||
enddo
|
|
||||||
call DMDACreate3d(PETSC_COMM_WORLD, &
|
|
||||||
DM_BOUNDARY_NONE, DM_BOUNDARY_NONE, DM_BOUNDARY_NONE, & ! cut off stencil at boundary
|
|
||||||
DMDA_STENCIL_BOX, & ! Moore (26) neighborhood around central point
|
|
||||||
grid(1),grid(2),grid(3), & ! global grid
|
|
||||||
1 , 1, worldsize, &
|
|
||||||
18, 0, & ! #dof (F tensor), ghost boundary width (domain overlap)
|
|
||||||
grid (1),grid (2),localK, & ! local grid
|
|
||||||
da,ierr) ! handle, error
|
|
||||||
CHKERRQ(ierr)
|
|
||||||
call SNESSetDM(snes,da,ierr); CHKERRQ(ierr)
|
|
||||||
call DMCreateGlobalVector(da,solution_vec,ierr); CHKERRQ(ierr)
|
|
||||||
call DMDASNESSetFunctionLocal(da,INSERT_VALUES,Polarisation_formResidual,dummy,ierr)
|
|
||||||
CHKERRQ(ierr)
|
|
||||||
call SNESSetConvergenceTest(snes,Polarisation_converged,dummy,PETSC_NULL_FUNCTION,ierr)
|
|
||||||
CHKERRQ(ierr)
|
|
||||||
call SNESSetFromOptions(snes,ierr); CHKERRQ(ierr)
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! init fields
|
|
||||||
call DMDAVecGetArrayF90(da,solution_vec,xx_psc,ierr); CHKERRQ(ierr) ! places pointer xx_psc on PETSc data
|
|
||||||
F => xx_psc(0:8,:,:,:)
|
|
||||||
F_tau => xx_psc(9:17,:,:,:)
|
|
||||||
restart: if (restartInc > 1_pInt) then
|
|
||||||
if (iand(debug_level(debug_spectral),debug_spectralRestart)/= 0 .and. worldrank == 0_pInt) &
|
|
||||||
write(6,'(/,a,'//IO_intOut(restartInc-1_pInt)//',a)') &
|
|
||||||
'reading values of increment', restartInc - 1_pInt, 'from file'
|
|
||||||
flush(6)
|
|
||||||
write(rankStr,'(a1,i0)')'_',worldrank
|
|
||||||
call IO_read_realFile(777,'F'//trim(rankStr),trim(getSolverJobName()),size(F))
|
|
||||||
read (777,rec=1) F
|
|
||||||
close (777)
|
|
||||||
call IO_read_realFile(777,'F_lastInc'//trim(rankStr),trim(getSolverJobName()),size(F_lastInc))
|
|
||||||
read (777,rec=1) F_lastInc
|
|
||||||
close (777)
|
|
||||||
call IO_read_realFile(777,'F_tau'//trim(rankStr),trim(getSolverJobName()),size(F_tau))
|
|
||||||
read (777,rec=1) F_tau
|
|
||||||
close (777)
|
|
||||||
call IO_read_realFile(777,'F_tau_lastInc'//trim(rankStr),&
|
|
||||||
trim(getSolverJobName()),size(F_tau_lastInc))
|
|
||||||
read (777,rec=1) F_tau_lastInc
|
|
||||||
close (777)
|
|
||||||
call IO_read_realFile(777,'F_aim', trim(getSolverJobName()),size(F_aim))
|
|
||||||
read (777,rec=1) F_aim
|
|
||||||
close (777)
|
|
||||||
call IO_read_realFile(777,'F_aim_lastInc', trim(getSolverJobName()),size(F_aim_lastInc))
|
|
||||||
read (777,rec=1) F_aim_lastInc
|
|
||||||
close (777)
|
|
||||||
call IO_read_realFile(777,'F_aimDot',trim(getSolverJobName()),size(f_aimDot))
|
|
||||||
read (777,rec=1) f_aimDot
|
|
||||||
close (777)
|
|
||||||
elseif (restartInc == 1_pInt) then restart
|
|
||||||
F_lastInc = spread(spread(spread(math_I3,3,grid(1)),4,grid(2)),5,grid3) ! initialize to identity
|
|
||||||
F = reshape(F_lastInc,[9,grid(1),grid(2),grid3])
|
|
||||||
F_tau = 2.0_pReal* F
|
|
||||||
F_tau_lastInc = 2.0_pReal*F_lastInc
|
|
||||||
endif restart
|
|
||||||
|
|
||||||
call Utilities_updateIPcoords(reshape(F,shape(F_lastInc)))
|
|
||||||
call Utilities_constitutiveResponse(F_lastInc, reshape(F,shape(F_lastInc)), &
|
|
||||||
0.0_pReal,P,C_volAvg,C_minMaxAvg,temp33_Real,.false.,math_I3)
|
|
||||||
nullify(F)
|
|
||||||
nullify(F_tau)
|
|
||||||
call DMDAVecRestoreArrayF90(da,solution_vec,xx_psc,ierr); CHKERRQ(ierr) ! write data back to PETSc
|
|
||||||
|
|
||||||
readRestart: if (restartInc > 1_pInt) then
|
|
||||||
if (iand(debug_level(debug_spectral),debug_spectralRestart)/= 0 .and. worldrank == 0_pInt) &
|
|
||||||
write(6,'(/,a,'//IO_intOut(restartInc-1_pInt)//',a)') &
|
|
||||||
'reading more values of increment', restartInc - 1_pInt, 'from file'
|
|
||||||
flush(6)
|
|
||||||
call IO_read_realFile(777,'C_volAvg',trim(getSolverJobName()),size(C_volAvg))
|
|
||||||
read (777,rec=1) C_volAvg
|
|
||||||
close (777)
|
|
||||||
call IO_read_realFile(777,'C_volAvgLastInc',trim(getSolverJobName()),size(C_volAvgLastInc))
|
|
||||||
read (777,rec=1) C_volAvgLastInc
|
|
||||||
close (777)
|
|
||||||
call IO_read_realFile(777,'C_ref',trim(getSolverJobName()),size(C_minMaxAvg))
|
|
||||||
read (777,rec=1) C_minMaxAvg
|
|
||||||
close (777)
|
|
||||||
endif readRestart
|
|
||||||
|
|
||||||
call Utilities_updateGamma(C_minMaxAvg,.True.)
|
|
||||||
C_scale = C_minMaxAvg
|
|
||||||
S_scale = math_invSym3333(C_minMaxAvg)
|
|
||||||
|
|
||||||
end subroutine Polarisation_init
|
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief solution for the Polarisation scheme with internal iterations
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
type(tSolutionState) function &
|
|
||||||
Polarisation_solution(incInfoIn,guess,timeinc,timeinc_old,loadCaseTime,P_BC,F_BC,rotation_BC)
|
|
||||||
use IO, only: &
|
|
||||||
IO_error
|
|
||||||
use numerics, only: &
|
|
||||||
update_gamma
|
|
||||||
use math, only: &
|
|
||||||
math_invSym3333
|
|
||||||
use spectral_utilities, only: &
|
|
||||||
tBoundaryCondition, &
|
|
||||||
Utilities_maskedCompliance, &
|
|
||||||
Utilities_updateGamma
|
|
||||||
use FEsolving, only: &
|
|
||||||
restartWrite, &
|
|
||||||
terminallyIll
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! input data for solution
|
|
||||||
real(pReal), intent(in) :: &
|
|
||||||
timeinc, & !< increment in time for current solution
|
|
||||||
timeinc_old, & !< increment in time of last increment
|
|
||||||
loadCaseTime !< remaining time of current load case
|
|
||||||
logical, intent(in) :: &
|
|
||||||
guess
|
|
||||||
type(tBoundaryCondition), intent(in) :: &
|
|
||||||
P_BC, &
|
|
||||||
F_BC
|
|
||||||
character(len=*), intent(in) :: &
|
|
||||||
incInfoIn
|
|
||||||
real(pReal), dimension(3,3), intent(in) :: rotation_BC
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! PETSc Data
|
|
||||||
PetscErrorCode :: ierr
|
|
||||||
SNESConvergedReason :: reason
|
|
||||||
|
|
||||||
incInfo = incInfoIn
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! update stiffness (and gamma operator)
|
|
||||||
S = Utilities_maskedCompliance(rotation_BC,P_BC%maskLogical,C_volAvg)
|
|
||||||
if (update_gamma) then
|
|
||||||
call Utilities_updateGamma(C_minMaxAvg,restartWrite)
|
|
||||||
C_scale = C_minMaxAvg
|
|
||||||
S_scale = math_invSym3333(C_minMaxAvg)
|
|
||||||
endif
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! set module wide availabe data
|
|
||||||
mask_stress = P_BC%maskFloat
|
|
||||||
params%P_BC = P_BC%values
|
|
||||||
params%rotation_BC = rotation_BC
|
|
||||||
params%timeinc = timeinc
|
|
||||||
params%timeincOld = timeinc_old
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! solve BVP
|
|
||||||
call SNESSolve(snes,PETSC_NULL_OBJECT,solution_vec,ierr)
|
|
||||||
CHKERRQ(ierr)
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! check convergence
|
|
||||||
call SNESGetConvergedReason(snes,reason,ierr)
|
|
||||||
CHKERRQ(ierr)
|
|
||||||
Polarisation_solution%termIll = terminallyIll
|
|
||||||
terminallyIll = .false.
|
|
||||||
if (reason == -4) call IO_error(893_pInt)
|
|
||||||
if (reason < 1) Polarisation_solution%converged = .false.
|
|
||||||
Polarisation_solution%iterationsNeeded = totalIter
|
|
||||||
|
|
||||||
end function Polarisation_solution
|
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief forms the Polarisation residual vector
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine Polarisation_formResidual(in,x_scal,f_scal,dummy,ierr)
|
|
||||||
use numerics, only: &
|
|
||||||
itmax, &
|
|
||||||
itmin, &
|
|
||||||
polarAlpha, &
|
|
||||||
polarBeta, &
|
|
||||||
worldrank
|
|
||||||
use mesh, only: &
|
|
||||||
grid3, &
|
|
||||||
grid
|
|
||||||
use IO, only: &
|
|
||||||
IO_intOut
|
|
||||||
use math, only: &
|
|
||||||
math_rotate_backward33, &
|
|
||||||
math_transpose33, &
|
|
||||||
math_mul3333xx33, &
|
|
||||||
math_invSym3333, &
|
|
||||||
math_mul33x33
|
|
||||||
use spectral_utilities, only: &
|
|
||||||
wgt, &
|
|
||||||
tensorField_real, &
|
|
||||||
utilities_FFTtensorForward, &
|
|
||||||
utilities_fourierGammaConvolution, &
|
|
||||||
utilities_FFTtensorBackward, &
|
|
||||||
Utilities_constitutiveResponse, &
|
|
||||||
Utilities_divergenceRMS, &
|
|
||||||
Utilities_curlRMS
|
|
||||||
use debug, only: &
|
|
||||||
debug_level, &
|
|
||||||
debug_spectral, &
|
|
||||||
debug_spectralRotation
|
|
||||||
use homogenization, only: &
|
|
||||||
materialpoint_dPdF
|
|
||||||
use FEsolving, only: &
|
|
||||||
terminallyIll
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! strange syntax in the next line because otherwise macros expand beyond 132 character limit
|
|
||||||
DMDALocalInfo, dimension(&
|
|
||||||
DMDA_LOCAL_INFO_SIZE) :: &
|
|
||||||
in
|
|
||||||
PetscScalar, target, dimension(3,3,2, &
|
|
||||||
XG_RANGE,YG_RANGE,ZG_RANGE) :: &
|
|
||||||
x_scal
|
|
||||||
PetscScalar, target, dimension(3,3,2, &
|
|
||||||
X_RANGE,Y_RANGE,Z_RANGE) :: &
|
|
||||||
f_scal
|
|
||||||
PetscScalar, pointer, dimension(:,:,:,:,:) :: &
|
|
||||||
F, &
|
|
||||||
F_tau, &
|
|
||||||
residual_F, &
|
|
||||||
residual_F_tau
|
|
||||||
PetscInt :: &
|
|
||||||
PETScIter, &
|
|
||||||
nfuncs
|
|
||||||
PetscObject :: dummy
|
|
||||||
PetscErrorCode :: ierr
|
|
||||||
integer(pInt) :: &
|
|
||||||
i, j, k, e
|
|
||||||
|
|
||||||
F => x_scal(1:3,1:3,1,&
|
|
||||||
XG_RANGE,YG_RANGE,ZG_RANGE)
|
|
||||||
F_tau => x_scal(1:3,1:3,2,&
|
|
||||||
XG_RANGE,YG_RANGE,ZG_RANGE)
|
|
||||||
residual_F => f_scal(1:3,1:3,1,&
|
|
||||||
X_RANGE,Y_RANGE,Z_RANGE)
|
|
||||||
residual_F_tau => f_scal(1:3,1:3,2,&
|
|
||||||
X_RANGE,Y_RANGE,Z_RANGE)
|
|
||||||
|
|
||||||
call SNESGetNumberFunctionEvals(snes,nfuncs,ierr); CHKERRQ(ierr)
|
|
||||||
call SNESGetIterationNumber(snes,PETScIter,ierr); CHKERRQ(ierr)
|
|
||||||
|
|
||||||
F_av = sum(sum(sum(F,dim=5),dim=4),dim=3) * wgt
|
|
||||||
call MPI_Allreduce(MPI_IN_PLACE,F_av,9,MPI_DOUBLE,MPI_SUM,PETSC_COMM_WORLD,ierr)
|
|
||||||
|
|
||||||
if(nfuncs== 0 .and. PETScIter == 0) totalIter = -1_pInt ! new increment
|
|
||||||
newIteration: if(totalIter <= PETScIter) then
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! report begin of new iteration
|
|
||||||
totalIter = totalIter + 1_pInt
|
|
||||||
if (worldrank == 0_pInt) then
|
|
||||||
write(6,'(1x,a,3(a,'//IO_intOut(itmax)//'))') trim(incInfo), &
|
|
||||||
' @ Iteration ', itmin, '≤',totalIter, '≤', itmax
|
|
||||||
if (iand(debug_level(debug_spectral),debug_spectralRotation) /= 0) &
|
|
||||||
write(6,'(/,a,/,3(3(f12.7,1x)/))',advance='no') ' deformation gradient aim (lab) =', &
|
|
||||||
math_transpose33(math_rotate_backward33(F_aim,params%rotation_BC))
|
|
||||||
write(6,'(/,a,/,3(3(f12.7,1x)/))',advance='no') ' deformation gradient aim =', &
|
|
||||||
math_transpose33(F_aim)
|
|
||||||
flush(6)
|
|
||||||
endif
|
|
||||||
endif newIteration
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!
|
|
||||||
tensorField_real = 0.0_pReal
|
|
||||||
do k = 1_pInt, grid3; do j = 1_pInt, grid(2); do i = 1_pInt, grid(1)
|
|
||||||
tensorField_real(1:3,1:3,i,j,k) = &
|
|
||||||
polarBeta*math_mul3333xx33(C_scale,F(1:3,1:3,i,j,k) - math_I3) -&
|
|
||||||
polarAlpha*math_mul33x33(F(1:3,1:3,i,j,k), &
|
|
||||||
math_mul3333xx33(C_scale,F_tau(1:3,1:3,i,j,k) - F(1:3,1:3,i,j,k) - math_I3))
|
|
||||||
enddo; enddo; enddo
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! doing convolution in Fourier space
|
|
||||||
call utilities_FFTtensorForward()
|
|
||||||
call utilities_fourierGammaConvolution(math_rotate_backward33(polarBeta*F_aim,params%rotation_BC))
|
|
||||||
call utilities_FFTtensorBackward()
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! constructing residual
|
|
||||||
residual_F_tau = polarBeta*F - tensorField_real(1:3,1:3,1:grid(1),1:grid(2),1:grid3)
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! evaluate constitutive response
|
|
||||||
P_avLastEval = P_av
|
|
||||||
call Utilities_constitutiveResponse(F_lastInc,F - residual_F_tau/polarBeta,params%timeinc, &
|
|
||||||
residual_F,C_volAvg,C_minMaxAvg,P_av,ForwardData,params%rotation_BC)
|
|
||||||
call MPI_Allreduce(MPI_IN_PLACE,terminallyIll,1,MPI_LOGICAL,MPI_LOR,PETSC_COMM_WORLD,ierr)
|
|
||||||
ForwardData = .False.
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! calculate divergence
|
|
||||||
tensorField_real = 0.0_pReal
|
|
||||||
tensorField_real(1:3,1:3,1:grid(1),1:grid(2),1:grid3) = residual_F
|
|
||||||
call utilities_FFTtensorForward()
|
|
||||||
err_div = Utilities_divergenceRMS()
|
|
||||||
call utilities_FFTtensorBackward()
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! constructing residual
|
|
||||||
e = 0_pInt
|
|
||||||
do k = 1_pInt, grid3; do j = 1_pInt, grid(2); do i = 1_pInt, grid(1)
|
|
||||||
e = e + 1_pInt
|
|
||||||
residual_F(1:3,1:3,i,j,k) = &
|
|
||||||
math_mul3333xx33(math_invSym3333(materialpoint_dPdF(1:3,1:3,1:3,1:3,1,e) + C_scale), &
|
|
||||||
residual_F(1:3,1:3,i,j,k) - math_mul33x33(F(1:3,1:3,i,j,k), &
|
|
||||||
math_mul3333xx33(C_scale,F_tau(1:3,1:3,i,j,k) - F(1:3,1:3,i,j,k) - math_I3))) &
|
|
||||||
+ residual_F_tau(1:3,1:3,i,j,k)
|
|
||||||
enddo; enddo; enddo
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! calculating curl
|
|
||||||
tensorField_real = 0.0_pReal
|
|
||||||
tensorField_real(1:3,1:3,1:grid(1),1:grid(2),1:grid3) = F
|
|
||||||
call utilities_FFTtensorForward()
|
|
||||||
err_curl = Utilities_curlRMS()
|
|
||||||
call utilities_FFTtensorBackward()
|
|
||||||
|
|
||||||
end subroutine Polarisation_formResidual
|
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief convergence check
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine Polarisation_converged(snes_local,PETScIter,xnorm,snorm,fnorm,reason,dummy,ierr)
|
|
||||||
use numerics, only: &
|
|
||||||
itmax, &
|
|
||||||
itmin, &
|
|
||||||
err_div_tolRel, &
|
|
||||||
err_div_tolAbs, &
|
|
||||||
err_curl_tolRel, &
|
|
||||||
err_curl_tolAbs, &
|
|
||||||
err_stress_tolAbs, &
|
|
||||||
err_stress_tolRel, &
|
|
||||||
worldrank
|
|
||||||
use math, only: &
|
|
||||||
math_mul3333xx33
|
|
||||||
use FEsolving, only: &
|
|
||||||
terminallyIll
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
SNES :: snes_local
|
|
||||||
PetscInt :: PETScIter
|
|
||||||
PetscReal :: &
|
|
||||||
xnorm, &
|
|
||||||
snorm, &
|
|
||||||
fnorm
|
|
||||||
SNESConvergedReason :: reason
|
|
||||||
PetscObject :: dummy
|
|
||||||
PetscErrorCode ::ierr
|
|
||||||
real(pReal) :: &
|
|
||||||
curlTol, &
|
|
||||||
divTol, &
|
|
||||||
BC_tol
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! stress BC handling
|
|
||||||
F_aim = F_aim - math_mul3333xx33(S, ((P_av - params%P_BC))) ! S = 0.0 for no bc
|
|
||||||
err_BC = maxval(abs((-mask_stress+1.0_pReal)*math_mul3333xx33(C_scale,F_aim-F_av) + &
|
|
||||||
mask_stress *(P_av - params%P_BC))) ! mask = 0.0 for no bc
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! error calculation
|
|
||||||
curlTol = max(maxval(abs(F_aim-math_I3))*err_curl_tolRel,err_curl_tolAbs)
|
|
||||||
divTol = max(maxval(abs(P_av)) *err_div_tolRel,err_div_tolAbs)
|
|
||||||
BC_tol = max(maxval(abs(P_av)) *err_stress_tolrel,err_stress_tolabs)
|
|
||||||
|
|
||||||
converged: if ((totalIter >= itmin .and. &
|
|
||||||
all([ err_div/divTol, &
|
|
||||||
err_curl/curlTol, &
|
|
||||||
err_BC/BC_tol ] < 1.0_pReal)) &
|
|
||||||
.or. terminallyIll) then
|
|
||||||
reason = 1
|
|
||||||
elseif (totalIter >= itmax) then converged
|
|
||||||
reason = -1
|
|
||||||
else converged
|
|
||||||
reason = 0
|
|
||||||
endif converged
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! report
|
|
||||||
if (worldrank == 0_pInt) then
|
|
||||||
write(6,'(1/,a)') ' ... reporting .............................................................'
|
|
||||||
write(6,'(/,a,f12.2,a,es8.2,a,es9.2,a)') ' error curl = ', &
|
|
||||||
err_curl/curlTol,' (',err_curl,' -, tol =',curlTol,')'
|
|
||||||
write(6,' (a,f12.2,a,es8.2,a,es9.2,a)') ' error divergence = ', &
|
|
||||||
err_div/divTol, ' (',err_div, ' / m, tol =',divTol,')'
|
|
||||||
write(6,' (a,f12.2,a,es8.2,a,es9.2,a)') ' error BC = ', &
|
|
||||||
err_BC/BC_tol, ' (',err_BC, ' Pa, tol =',BC_tol,')'
|
|
||||||
write(6,'(/,a)') ' ==========================================================================='
|
|
||||||
flush(6)
|
|
||||||
endif
|
|
||||||
|
|
||||||
end subroutine Polarisation_converged
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief forwarding routine
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine Polarisation_forward(guess,timeinc,timeinc_old,loadCaseTime,F_BC,P_BC,rotation_BC)
|
|
||||||
use math, only: &
|
|
||||||
math_mul33x33, &
|
|
||||||
math_mul3333xx33, &
|
|
||||||
math_transpose33, &
|
|
||||||
math_rotate_backward33
|
|
||||||
use numerics, only: &
|
|
||||||
worldrank
|
|
||||||
use mesh, only: &
|
|
||||||
grid3, &
|
|
||||||
grid
|
|
||||||
use spectral_utilities, only: &
|
|
||||||
Utilities_calculateRate, &
|
|
||||||
Utilities_forwardField, &
|
|
||||||
Utilities_updateIPcoords, &
|
|
||||||
tBoundaryCondition, &
|
|
||||||
cutBack
|
|
||||||
use IO, only: &
|
|
||||||
IO_write_JobRealFile
|
|
||||||
use FEsolving, only: &
|
|
||||||
restartWrite
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
real(pReal), intent(in) :: &
|
|
||||||
timeinc_old, &
|
|
||||||
timeinc, &
|
|
||||||
loadCaseTime !< remaining time of current load case
|
|
||||||
type(tBoundaryCondition), intent(in) :: &
|
|
||||||
P_BC, &
|
|
||||||
F_BC
|
|
||||||
real(pReal), dimension(3,3), intent(in) :: rotation_BC
|
|
||||||
logical, intent(in) :: &
|
|
||||||
guess
|
|
||||||
PetscErrorCode :: ierr
|
|
||||||
PetscScalar, dimension(:,:,:,:), pointer :: xx_psc, F, F_tau
|
|
||||||
integer(pInt) :: i, j, k
|
|
||||||
real(pReal), dimension(3,3) :: F_lambda33
|
|
||||||
character(len=1024) :: rankStr
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! update coordinates and rate and forward last inc
|
|
||||||
call DMDAVecGetArrayF90(da,solution_vec,xx_psc,ierr)
|
|
||||||
F => xx_psc(0:8,:,:,:)
|
|
||||||
F_tau => xx_psc(9:17,:,:,:)
|
|
||||||
if (restartWrite) then
|
|
||||||
if (worldrank == 0_pInt) write(6,'(/,a)') ' writing converged results for restart'
|
|
||||||
flush(6)
|
|
||||||
write(rankStr,'(a1,i0)')'_',worldrank
|
|
||||||
call IO_write_jobRealFile(777,'F'//trim(rankStr),size(F)) ! writing deformation gradient field to file
|
|
||||||
write (777,rec=1) F
|
|
||||||
close (777)
|
|
||||||
call IO_write_jobRealFile(777,'F_lastInc'//trim(rankStr),size(F_lastInc)) ! writing F_lastInc field to file
|
|
||||||
write (777,rec=1) F_lastInc
|
|
||||||
close (777)
|
|
||||||
call IO_write_jobRealFile(777,'F_tau'//trim(rankStr),size(F_tau)) ! writing deformation gradient field to file
|
|
||||||
write (777,rec=1) F_tau
|
|
||||||
close (777)
|
|
||||||
call IO_write_jobRealFile(777,'F_tau_lastInc'//trim(rankStr),size(F_tau_lastInc)) ! writing F_lastInc field to file
|
|
||||||
write (777,rec=1) F_tau_lastInc
|
|
||||||
close (777)
|
|
||||||
if (worldrank == 0_pInt) then
|
|
||||||
call IO_write_jobRealFile(777,'F_aim',size(F_aim))
|
|
||||||
write (777,rec=1) F_aim
|
|
||||||
close(777)
|
|
||||||
call IO_write_jobRealFile(777,'F_aim_lastInc',size(F_aim_lastInc))
|
|
||||||
write (777,rec=1) F_aim_lastInc
|
|
||||||
close (777)
|
|
||||||
call IO_write_jobRealFile(777,'F_aimDot',size(F_aimDot))
|
|
||||||
write (777,rec=1) F_aimDot
|
|
||||||
close(777)
|
|
||||||
call IO_write_jobRealFile(777,'C_volAvg',size(C_volAvg))
|
|
||||||
write (777,rec=1) C_volAvg
|
|
||||||
close(777)
|
|
||||||
call IO_write_jobRealFile(777,'C_volAvgLastInc',size(C_volAvgLastInc))
|
|
||||||
write (777,rec=1) C_volAvgLastInc
|
|
||||||
close(777)
|
|
||||||
endif
|
|
||||||
endif
|
|
||||||
call utilities_updateIPcoords(F)
|
|
||||||
|
|
||||||
if (cutBack) then
|
|
||||||
F_aim = F_aim_lastInc
|
|
||||||
F_tau= reshape(F_tau_lastInc,[9,grid(1),grid(2),grid3])
|
|
||||||
F = reshape(F_lastInc, [9,grid(1),grid(2),grid3])
|
|
||||||
C_volAvg = C_volAvgLastInc
|
|
||||||
else
|
|
||||||
ForwardData = .True.
|
|
||||||
C_volAvgLastInc = C_volAvg
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! calculate rate for aim
|
|
||||||
if (F_BC%myType=='l') then ! calculate f_aimDot from given L and current F
|
|
||||||
f_aimDot = F_BC%maskFloat * math_mul33x33(F_BC%values, F_aim)
|
|
||||||
elseif(F_BC%myType=='fdot') then ! f_aimDot is prescribed
|
|
||||||
f_aimDot = F_BC%maskFloat * F_BC%values
|
|
||||||
elseif(F_BC%myType=='f') then ! aim at end of load case is prescribed
|
|
||||||
f_aimDot = F_BC%maskFloat * (F_BC%values -F_aim)/loadCaseTime
|
|
||||||
endif
|
|
||||||
if (guess) f_aimDot = f_aimDot + P_BC%maskFloat * (F_aim - F_aim_lastInc)/timeinc_old
|
|
||||||
F_aim_lastInc = F_aim
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! update coordinates and rate and forward last inc
|
|
||||||
call utilities_updateIPcoords(F)
|
|
||||||
Fdot = Utilities_calculateRate(math_rotate_backward33(f_aimDot,rotation_BC), &
|
|
||||||
timeinc_old,guess,F_lastInc, &
|
|
||||||
reshape(F,[3,3,grid(1),grid(2),grid3]))
|
|
||||||
F_tauDot = Utilities_calculateRate(math_rotate_backward33(2.0_pReal*f_aimDot,rotation_BC), &
|
|
||||||
timeinc_old,guess,F_tau_lastInc, &
|
|
||||||
reshape(F_tau,[3,3,grid(1),grid(2),grid3]))
|
|
||||||
F_lastInc = reshape(F, [3,3,grid(1),grid(2),grid3])
|
|
||||||
F_tau_lastInc = reshape(F_tau,[3,3,grid(1),grid(2),grid3])
|
|
||||||
endif
|
|
||||||
|
|
||||||
F_aim = F_aim + f_aimDot * timeinc
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! update local deformation gradient
|
|
||||||
F = reshape(Utilities_forwardField(timeinc,F_lastInc,Fdot, & ! ensure that it matches rotated F_aim
|
|
||||||
math_rotate_backward33(F_aim,rotation_BC)), &
|
|
||||||
[9,grid(1),grid(2),grid3])
|
|
||||||
F_tau = reshape(Utilities_forwardField(timeinc,F_tau_lastInc,F_taudot), & ! does not have any average value as boundary condition
|
|
||||||
[9,grid(1),grid(2),grid3])
|
|
||||||
if (.not. guess) then ! large strain forwarding
|
|
||||||
do k = 1_pInt, grid3; do j = 1_pInt, grid(2); do i = 1_pInt, grid(1)
|
|
||||||
F_lambda33 = reshape(F_tau(1:9,i,j,k)-F(1:9,i,j,k),[3,3])
|
|
||||||
F_lambda33 = math_mul3333xx33(S_scale,math_mul33x33(F_lambda33, &
|
|
||||||
math_mul3333xx33(C_scale,&
|
|
||||||
math_mul33x33(math_transpose33(F_lambda33),&
|
|
||||||
F_lambda33) -math_I3))*0.5_pReal)&
|
|
||||||
+ math_I3
|
|
||||||
F_tau(1:9,i,j,k) = reshape(F_lambda33,[9])+F(1:9,i,j,k)
|
|
||||||
enddo; enddo; enddo
|
|
||||||
endif
|
|
||||||
call DMDAVecRestoreArrayF90(da,solution_vec,xx_psc,ierr); CHKERRQ(ierr)
|
|
||||||
|
|
||||||
end subroutine Polarisation_forward
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief destroy routine
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine Polarisation_destroy()
|
|
||||||
use spectral_utilities, only: &
|
|
||||||
Utilities_destroy
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
PetscErrorCode :: ierr
|
|
||||||
|
|
||||||
call VecDestroy(solution_vec,ierr); CHKERRQ(ierr)
|
|
||||||
call SNESDestroy(snes,ierr); CHKERRQ(ierr)
|
|
||||||
call DMDestroy(da,ierr); CHKERRQ(ierr)
|
|
||||||
|
|
||||||
end subroutine Polarisation_destroy
|
|
||||||
|
|
||||||
end module spectral_mech_Polarisation
|
|
|
@ -1,419 +0,0 @@
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! $Id: spectral_thermal.f90 4082 2015-04-11 20:28:07Z MPIE\m.diehl $
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @author Pratheek Shanthraj, Max-Planck-Institut für Eisenforschung GmbH
|
|
||||||
!> @author Shaokang Zhang, Max-Planck-Institut für Eisenforschung GmbH
|
|
||||||
!> @brief Spectral solver for thermal conduction
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
module spectral_thermal
|
|
||||||
use prec, only: &
|
|
||||||
pInt, &
|
|
||||||
pReal
|
|
||||||
use math, only: &
|
|
||||||
math_I3
|
|
||||||
use spectral_utilities, only: &
|
|
||||||
tSolutionState, &
|
|
||||||
tSolutionParams
|
|
||||||
use numerics, only: &
|
|
||||||
worldrank, &
|
|
||||||
worldsize
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
private
|
|
||||||
#include <petsc/finclude/petsc.h90>
|
|
||||||
|
|
||||||
character (len=*), parameter, public :: &
|
|
||||||
spectral_thermal_label = 'spectralthermal'
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! derived types
|
|
||||||
type(tSolutionParams), private :: params
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! PETSc data
|
|
||||||
SNES, private :: thermal_snes
|
|
||||||
Vec, private :: solution
|
|
||||||
PetscInt, private :: xstart, xend, ystart, yend, zstart, zend
|
|
||||||
real(pReal), private, dimension(:,:,:), allocatable :: &
|
|
||||||
temperature_current, & !< field of current temperature
|
|
||||||
temperature_lastInc, & !< field of previous temperature
|
|
||||||
temperature_stagInc !< field of staggered temperature
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! reference diffusion tensor, mobility etc.
|
|
||||||
integer(pInt), private :: totalIter = 0_pInt !< total iteration in current increment
|
|
||||||
real(pReal), dimension(3,3), private :: D_ref
|
|
||||||
real(pReal), private :: mobility_ref
|
|
||||||
character(len=1024), private :: incInfo
|
|
||||||
|
|
||||||
public :: &
|
|
||||||
spectral_thermal_init, &
|
|
||||||
spectral_thermal_solution, &
|
|
||||||
spectral_thermal_forward, &
|
|
||||||
spectral_thermal_destroy
|
|
||||||
external :: &
|
|
||||||
VecDestroy, &
|
|
||||||
DMDestroy, &
|
|
||||||
DMDACreate3D, &
|
|
||||||
DMCreateGlobalVector, &
|
|
||||||
DMDASNESSetFunctionLocal, &
|
|
||||||
PETScFinalize, &
|
|
||||||
SNESDestroy, &
|
|
||||||
SNESGetNumberFunctionEvals, &
|
|
||||||
SNESGetIterationNumber, &
|
|
||||||
SNESSolve, &
|
|
||||||
SNESSetDM, &
|
|
||||||
SNESGetConvergedReason, &
|
|
||||||
SNESSetConvergenceTest, &
|
|
||||||
SNESSetFromOptions, &
|
|
||||||
SNESCreate, &
|
|
||||||
MPI_Abort, &
|
|
||||||
MPI_Bcast, &
|
|
||||||
MPI_Allreduce
|
|
||||||
|
|
||||||
contains
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief allocates all neccessary fields and fills them with data, potentially from restart info
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine spectral_thermal_init
|
|
||||||
use, intrinsic :: iso_fortran_env ! to get compiler_version and compiler_options (at least for gfortran >4.6 at the moment)
|
|
||||||
use IO, only: &
|
|
||||||
IO_intOut, &
|
|
||||||
IO_read_realFile, &
|
|
||||||
IO_timeStamp
|
|
||||||
use spectral_utilities, only: &
|
|
||||||
wgt
|
|
||||||
use mesh, only: &
|
|
||||||
grid, &
|
|
||||||
grid3
|
|
||||||
use thermal_conduction, only: &
|
|
||||||
thermal_conduction_getConductivity33, &
|
|
||||||
thermal_conduction_getMassDensity, &
|
|
||||||
thermal_conduction_getSpecificHeat
|
|
||||||
use material, only: &
|
|
||||||
mappingHomogenization, &
|
|
||||||
temperature, &
|
|
||||||
thermalMapping
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
integer(pInt), dimension(:), allocatable :: localK
|
|
||||||
integer(pInt) :: proc
|
|
||||||
integer(pInt) :: i, j, k, cell
|
|
||||||
DM :: thermal_grid
|
|
||||||
PetscScalar, pointer :: x_scal(:,:,:)
|
|
||||||
PetscErrorCode :: ierr
|
|
||||||
PetscObject :: dummy
|
|
||||||
|
|
||||||
mainProcess: if (worldrank == 0_pInt) then
|
|
||||||
write(6,'(/,a)') ' <<<+- spectral_thermal init -+>>>'
|
|
||||||
write(6,'(a15,a)') ' Current time: ',IO_timeStamp()
|
|
||||||
#include "compilation_info.f90"
|
|
||||||
endif mainProcess
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! initialize solver specific parts of PETSc
|
|
||||||
call SNESCreate(PETSC_COMM_WORLD,thermal_snes,ierr); CHKERRQ(ierr)
|
|
||||||
call SNESSetOptionsPrefix(thermal_snes,'thermal_',ierr);CHKERRQ(ierr)
|
|
||||||
allocate(localK(worldsize), source = 0); localK(worldrank+1) = grid3
|
|
||||||
do proc = 1, worldsize
|
|
||||||
call MPI_Bcast(localK(proc),1,MPI_INTEGER,proc-1,PETSC_COMM_WORLD,ierr)
|
|
||||||
enddo
|
|
||||||
call DMDACreate3d(PETSC_COMM_WORLD, &
|
|
||||||
DM_BOUNDARY_NONE, DM_BOUNDARY_NONE, DM_BOUNDARY_NONE, & ! cut off stencil at boundary
|
|
||||||
DMDA_STENCIL_BOX, & ! Moore (26) neighborhood around central point
|
|
||||||
grid(1),grid(2),grid(3), & ! global grid
|
|
||||||
1, 1, worldsize, &
|
|
||||||
1, 0, & ! #dof (temperature field), ghost boundary width (domain overlap)
|
|
||||||
grid (1),grid(2),localK, & ! local grid
|
|
||||||
thermal_grid,ierr) ! handle, error
|
|
||||||
CHKERRQ(ierr)
|
|
||||||
call SNESSetDM(thermal_snes,thermal_grid,ierr); CHKERRQ(ierr) ! connect snes to da
|
|
||||||
call DMCreateGlobalVector(thermal_grid,solution ,ierr); CHKERRQ(ierr) ! global solution vector (grid x 1, i.e. every def grad tensor)
|
|
||||||
call DMDASNESSetFunctionLocal(thermal_grid,INSERT_VALUES,spectral_thermal_formResidual,dummy,ierr) ! residual vector of same shape as solution vector
|
|
||||||
CHKERRQ(ierr)
|
|
||||||
call SNESSetFromOptions(thermal_snes,ierr); CHKERRQ(ierr) ! pull it all together with additional cli arguments
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! init fields
|
|
||||||
call DMDAGetCorners(thermal_grid,xstart,ystart,zstart,xend,yend,zend,ierr)
|
|
||||||
CHKERRQ(ierr)
|
|
||||||
xend = xstart + xend - 1
|
|
||||||
yend = ystart + yend - 1
|
|
||||||
zend = zstart + zend - 1
|
|
||||||
allocate(temperature_current(grid(1),grid(2),grid3), source=0.0_pReal)
|
|
||||||
allocate(temperature_lastInc(grid(1),grid(2),grid3), source=0.0_pReal)
|
|
||||||
allocate(temperature_stagInc(grid(1),grid(2),grid3), source=0.0_pReal)
|
|
||||||
cell = 0_pInt
|
|
||||||
do k = 1_pInt, grid3; do j = 1_pInt, grid(2); do i = 1_pInt,grid(1)
|
|
||||||
cell = cell + 1_pInt
|
|
||||||
temperature_current(i,j,k) = temperature(mappingHomogenization(2,1,cell))% &
|
|
||||||
p(thermalMapping(mappingHomogenization(2,1,cell))%p(1,cell))
|
|
||||||
temperature_lastInc(i,j,k) = temperature_current(i,j,k)
|
|
||||||
temperature_stagInc(i,j,k) = temperature_current(i,j,k)
|
|
||||||
enddo; enddo; enddo
|
|
||||||
call DMDAVecGetArrayF90(thermal_grid,solution,x_scal,ierr); CHKERRQ(ierr) !< get the data out of PETSc to work with
|
|
||||||
x_scal(xstart:xend,ystart:yend,zstart:zend) = temperature_current
|
|
||||||
call DMDAVecRestoreArrayF90(thermal_grid,solution,x_scal,ierr); CHKERRQ(ierr)
|
|
||||||
|
|
||||||
cell = 0_pInt
|
|
||||||
D_ref = 0.0_pReal
|
|
||||||
mobility_ref = 0.0_pReal
|
|
||||||
do k = 1_pInt, grid3; do j = 1_pInt, grid(2); do i = 1_pInt,grid(1)
|
|
||||||
cell = cell + 1_pInt
|
|
||||||
D_ref = D_ref + thermal_conduction_getConductivity33(1,cell)
|
|
||||||
mobility_ref = mobility_ref + thermal_conduction_getMassDensity(1,cell)* &
|
|
||||||
thermal_conduction_getSpecificHeat(1,cell)
|
|
||||||
enddo; enddo; enddo
|
|
||||||
D_ref = D_ref*wgt
|
|
||||||
call MPI_Allreduce(MPI_IN_PLACE,D_ref,9,MPI_DOUBLE,MPI_SUM,PETSC_COMM_WORLD,ierr)
|
|
||||||
mobility_ref = mobility_ref*wgt
|
|
||||||
call MPI_Allreduce(MPI_IN_PLACE,mobility_ref,1,MPI_DOUBLE,MPI_SUM,PETSC_COMM_WORLD,ierr)
|
|
||||||
|
|
||||||
end subroutine spectral_thermal_init
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief solution for the Basic PETSC scheme with internal iterations
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
type(tSolutionState) function spectral_thermal_solution(guess,timeinc,timeinc_old,loadCaseTime)
|
|
||||||
use numerics, only: &
|
|
||||||
itmax, &
|
|
||||||
err_thermal_tolAbs, &
|
|
||||||
err_thermal_tolRel
|
|
||||||
use spectral_utilities, only: &
|
|
||||||
tBoundaryCondition, &
|
|
||||||
Utilities_maskedCompliance, &
|
|
||||||
Utilities_updateGamma
|
|
||||||
use mesh, only: &
|
|
||||||
grid, &
|
|
||||||
grid3
|
|
||||||
use thermal_conduction, only: &
|
|
||||||
thermal_conduction_putTemperatureAndItsRate
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! input data for solution
|
|
||||||
real(pReal), intent(in) :: &
|
|
||||||
timeinc, & !< increment in time for current solution
|
|
||||||
timeinc_old, & !< increment in time of last increment
|
|
||||||
loadCaseTime !< remaining time of current load case
|
|
||||||
logical, intent(in) :: guess
|
|
||||||
integer(pInt) :: i, j, k, cell
|
|
||||||
PetscInt :: position
|
|
||||||
PetscReal :: minTemperature, maxTemperature, stagNorm, solnNorm
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! PETSc Data
|
|
||||||
PetscErrorCode :: ierr
|
|
||||||
SNESConvergedReason :: reason
|
|
||||||
|
|
||||||
spectral_thermal_solution%converged =.false.
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! set module wide availabe data
|
|
||||||
params%timeinc = timeinc
|
|
||||||
params%timeincOld = timeinc_old
|
|
||||||
|
|
||||||
call SNESSolve(thermal_snes,PETSC_NULL_OBJECT,solution,ierr); CHKERRQ(ierr)
|
|
||||||
call SNESGetConvergedReason(thermal_snes,reason,ierr); CHKERRQ(ierr)
|
|
||||||
|
|
||||||
if (reason < 1) then
|
|
||||||
spectral_thermal_solution%converged = .false.
|
|
||||||
spectral_thermal_solution%iterationsNeeded = itmax
|
|
||||||
else
|
|
||||||
spectral_thermal_solution%converged = .true.
|
|
||||||
spectral_thermal_solution%iterationsNeeded = totalIter
|
|
||||||
endif
|
|
||||||
stagNorm = maxval(abs(temperature_current - temperature_stagInc))
|
|
||||||
solnNorm = maxval(abs(temperature_current))
|
|
||||||
call MPI_Allreduce(MPI_IN_PLACE,stagNorm,1,MPI_DOUBLE,MPI_MAX,PETSC_COMM_WORLD,ierr)
|
|
||||||
call MPI_Allreduce(MPI_IN_PLACE,solnNorm,1,MPI_DOUBLE,MPI_MAX,PETSC_COMM_WORLD,ierr)
|
|
||||||
temperature_stagInc = temperature_current
|
|
||||||
spectral_thermal_solution%stagConverged = stagNorm < err_thermal_tolAbs &
|
|
||||||
.or. stagNorm < err_thermal_tolRel*solnNorm
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! updating thermal state
|
|
||||||
cell = 0_pInt !< material point = 0
|
|
||||||
do k = 1_pInt, grid3; do j = 1_pInt, grid(2); do i = 1_pInt,grid(1)
|
|
||||||
cell = cell + 1_pInt !< material point increase
|
|
||||||
call thermal_conduction_putTemperatureAndItsRate(temperature_current(i,j,k), &
|
|
||||||
(temperature_current(i,j,k)-temperature_lastInc(i,j,k))/params%timeinc, &
|
|
||||||
1,cell)
|
|
||||||
enddo; enddo; enddo
|
|
||||||
|
|
||||||
call VecMin(solution,position,minTemperature,ierr); CHKERRQ(ierr)
|
|
||||||
call VecMax(solution,position,maxTemperature,ierr); CHKERRQ(ierr)
|
|
||||||
if (worldrank == 0) then
|
|
||||||
if (spectral_thermal_solution%converged) &
|
|
||||||
write(6,'(/,a)') ' ... thermal conduction converged ..................................'
|
|
||||||
write(6,'(/,a,f8.4,2x,f8.4,2x,f8.4,/)',advance='no') ' Minimum|Maximum|Delta Temperature = ',&
|
|
||||||
minTemperature, maxTemperature, stagNorm
|
|
||||||
write(6,'(/,a)') ' ==========================================================================='
|
|
||||||
flush(6)
|
|
||||||
endif
|
|
||||||
|
|
||||||
end function spectral_thermal_solution
|
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief forms the spectral thermal residual vector
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine spectral_thermal_formResidual(in,x_scal,f_scal,dummy,ierr)
|
|
||||||
use mesh, only: &
|
|
||||||
grid, &
|
|
||||||
grid3
|
|
||||||
use math, only: &
|
|
||||||
math_mul33x3
|
|
||||||
use spectral_utilities, only: &
|
|
||||||
scalarField_real, &
|
|
||||||
vectorField_real, &
|
|
||||||
utilities_FFTvectorForward, &
|
|
||||||
utilities_FFTvectorBackward, &
|
|
||||||
utilities_FFTscalarForward, &
|
|
||||||
utilities_FFTscalarBackward, &
|
|
||||||
utilities_fourierGreenConvolution, &
|
|
||||||
utilities_fourierScalarGradient, &
|
|
||||||
utilities_fourierVectorDivergence
|
|
||||||
use thermal_conduction, only: &
|
|
||||||
thermal_conduction_getSourceAndItsTangent, &
|
|
||||||
thermal_conduction_getConductivity33, &
|
|
||||||
thermal_conduction_getMassDensity, &
|
|
||||||
thermal_conduction_getSpecificHeat
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
DMDALocalInfo, dimension(DMDA_LOCAL_INFO_SIZE) :: &
|
|
||||||
in
|
|
||||||
PetscScalar, dimension( &
|
|
||||||
XG_RANGE,YG_RANGE,ZG_RANGE) :: &
|
|
||||||
x_scal
|
|
||||||
PetscScalar, dimension( &
|
|
||||||
X_RANGE,Y_RANGE,Z_RANGE) :: &
|
|
||||||
f_scal
|
|
||||||
PetscObject :: dummy
|
|
||||||
PetscErrorCode :: ierr
|
|
||||||
integer(pInt) :: i, j, k, cell
|
|
||||||
real(pReal) :: Tdot, dTdot_dT
|
|
||||||
|
|
||||||
temperature_current = x_scal
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! evaluate polarization field
|
|
||||||
scalarField_real = 0.0_pReal
|
|
||||||
scalarField_real(1:grid(1),1:grid(2),1:grid3) = temperature_current
|
|
||||||
call utilities_FFTscalarForward()
|
|
||||||
call utilities_fourierScalarGradient() !< calculate gradient of damage field
|
|
||||||
call utilities_FFTvectorBackward()
|
|
||||||
cell = 0_pInt
|
|
||||||
do k = 1_pInt, grid3; do j = 1_pInt, grid(2); do i = 1_pInt,grid(1)
|
|
||||||
cell = cell + 1_pInt
|
|
||||||
vectorField_real(1:3,i,j,k) = math_mul33x3(thermal_conduction_getConductivity33(1,cell) - D_ref, &
|
|
||||||
vectorField_real(1:3,i,j,k))
|
|
||||||
enddo; enddo; enddo
|
|
||||||
call utilities_FFTvectorForward()
|
|
||||||
call utilities_fourierVectorDivergence() !< calculate damage divergence in fourier field
|
|
||||||
call utilities_FFTscalarBackward()
|
|
||||||
cell = 0_pInt
|
|
||||||
do k = 1_pInt, grid3; do j = 1_pInt, grid(2); do i = 1_pInt,grid(1)
|
|
||||||
cell = cell + 1_pInt
|
|
||||||
call thermal_conduction_getSourceAndItsTangent(Tdot, dTdot_dT, temperature_current(i,j,k), 1, cell)
|
|
||||||
scalarField_real(i,j,k) = params%timeinc*scalarField_real(i,j,k) + &
|
|
||||||
params%timeinc*Tdot + &
|
|
||||||
thermal_conduction_getMassDensity (1,cell)* &
|
|
||||||
thermal_conduction_getSpecificHeat(1,cell)*(temperature_lastInc(i,j,k) - &
|
|
||||||
temperature_current(i,j,k)) + &
|
|
||||||
mobility_ref*temperature_current(i,j,k)
|
|
||||||
enddo; enddo; enddo
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! convolution of damage field with green operator
|
|
||||||
call utilities_FFTscalarForward()
|
|
||||||
call utilities_fourierGreenConvolution(D_ref, mobility_ref, params%timeinc)
|
|
||||||
call utilities_FFTscalarBackward()
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! constructing residual
|
|
||||||
f_scal = temperature_current - scalarField_real(1:grid(1),1:grid(2),1:grid3)
|
|
||||||
|
|
||||||
end subroutine spectral_thermal_formResidual
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief forwarding routine
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine spectral_thermal_forward(guess,timeinc,timeinc_old,loadCaseTime)
|
|
||||||
use mesh, only: &
|
|
||||||
grid, &
|
|
||||||
grid3
|
|
||||||
use spectral_utilities, only: &
|
|
||||||
cutBack, &
|
|
||||||
wgt
|
|
||||||
use thermal_conduction, only: &
|
|
||||||
thermal_conduction_putTemperatureAndItsRate, &
|
|
||||||
thermal_conduction_getConductivity33, &
|
|
||||||
thermal_conduction_getMassDensity, &
|
|
||||||
thermal_conduction_getSpecificHeat
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
real(pReal), intent(in) :: &
|
|
||||||
timeinc_old, &
|
|
||||||
timeinc, &
|
|
||||||
loadCaseTime !< remaining time of current load case
|
|
||||||
logical, intent(in) :: guess
|
|
||||||
integer(pInt) :: i, j, k, cell
|
|
||||||
DM :: dm_local
|
|
||||||
PetscScalar, pointer :: x_scal(:,:,:)
|
|
||||||
PetscErrorCode :: ierr
|
|
||||||
|
|
||||||
if (cutBack) then
|
|
||||||
temperature_current = temperature_lastInc
|
|
||||||
temperature_stagInc = temperature_lastInc
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! reverting thermal field state
|
|
||||||
cell = 0_pInt !< material point = 0
|
|
||||||
call SNESGetDM(thermal_snes,dm_local,ierr); CHKERRQ(ierr)
|
|
||||||
call DMDAVecGetArrayF90(dm_local,solution,x_scal,ierr); CHKERRQ(ierr) !< get the data out of PETSc to work with
|
|
||||||
x_scal(xstart:xend,ystart:yend,zstart:zend) = temperature_current
|
|
||||||
call DMDAVecRestoreArrayF90(dm_local,solution,x_scal,ierr); CHKERRQ(ierr)
|
|
||||||
do k = 1_pInt, grid3; do j = 1_pInt, grid(2); do i = 1_pInt,grid(1)
|
|
||||||
cell = cell + 1_pInt !< material point increase
|
|
||||||
call thermal_conduction_putTemperatureAndItsRate(temperature_current(i,j,k), &
|
|
||||||
(temperature_current(i,j,k) - &
|
|
||||||
temperature_lastInc(i,j,k))/params%timeinc, &
|
|
||||||
1,cell)
|
|
||||||
enddo; enddo; enddo
|
|
||||||
else
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! update rate and forward last inc
|
|
||||||
temperature_lastInc = temperature_current
|
|
||||||
cell = 0_pInt
|
|
||||||
D_ref = 0.0_pReal
|
|
||||||
mobility_ref = 0.0_pReal
|
|
||||||
do k = 1_pInt, grid3; do j = 1_pInt, grid(2); do i = 1_pInt,grid(1)
|
|
||||||
cell = cell + 1_pInt
|
|
||||||
D_ref = D_ref + thermal_conduction_getConductivity33(1,cell)
|
|
||||||
mobility_ref = mobility_ref + thermal_conduction_getMassDensity(1,cell)* &
|
|
||||||
thermal_conduction_getSpecificHeat(1,cell)
|
|
||||||
enddo; enddo; enddo
|
|
||||||
D_ref = D_ref*wgt
|
|
||||||
call MPI_Allreduce(MPI_IN_PLACE,D_ref,9,MPI_DOUBLE,MPI_SUM,PETSC_COMM_WORLD,ierr)
|
|
||||||
mobility_ref = mobility_ref*wgt
|
|
||||||
call MPI_Allreduce(MPI_IN_PLACE,mobility_ref,1,MPI_DOUBLE,MPI_SUM,PETSC_COMM_WORLD,ierr)
|
|
||||||
endif
|
|
||||||
|
|
||||||
end subroutine spectral_thermal_forward
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief destroy routine
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine spectral_thermal_destroy()
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
PetscErrorCode :: ierr
|
|
||||||
|
|
||||||
call VecDestroy(solution,ierr); CHKERRQ(ierr)
|
|
||||||
call SNESDestroy(thermal_snes,ierr); CHKERRQ(ierr)
|
|
||||||
|
|
||||||
end subroutine spectral_thermal_destroy
|
|
||||||
|
|
||||||
end module spectral_thermal
|
|
File diff suppressed because it is too large
Load Diff
|
@ -8,3 +8,8 @@ set (THERMAL "thermal_isothermal"
|
||||||
foreach (p ${THERMAL})
|
foreach (p ${THERMAL})
|
||||||
add_library (${p} MODULE "${p}.f90")
|
add_library (${p} MODULE "${p}.f90")
|
||||||
endforeach (p)
|
endforeach (p)
|
||||||
|
|
||||||
|
# set libraries/modules for linking
|
||||||
|
foreach (p ${THERMAL})
|
||||||
|
set (AUX_LIB ${AUX_LIB} ${p})
|
||||||
|
endforeach (p)
|
|
@ -1,422 +0,0 @@
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! $Id$
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @author Pratheek Shanthraj, Max-Planck-Institut für Eisenforschung GmbH
|
|
||||||
!> @brief material subroutine for adiabatic temperature evolution
|
|
||||||
!> @details to be done
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
module thermal_adiabatic
|
|
||||||
use prec, only: &
|
|
||||||
pReal, &
|
|
||||||
pInt
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
private
|
|
||||||
integer(pInt), dimension(:), allocatable, public, protected :: &
|
|
||||||
thermal_adiabatic_sizePostResults !< cumulative size of post results
|
|
||||||
|
|
||||||
integer(pInt), dimension(:,:), allocatable, target, public :: &
|
|
||||||
thermal_adiabatic_sizePostResult !< size of each post result output
|
|
||||||
|
|
||||||
character(len=64), dimension(:,:), allocatable, target, public :: &
|
|
||||||
thermal_adiabatic_output !< name of each post result output
|
|
||||||
|
|
||||||
integer(pInt), dimension(:), allocatable, target, public :: &
|
|
||||||
thermal_adiabatic_Noutput !< number of outputs per instance of this thermal model
|
|
||||||
|
|
||||||
enum, bind(c)
|
|
||||||
enumerator :: undefined_ID, &
|
|
||||||
temperature_ID
|
|
||||||
end enum
|
|
||||||
integer(kind(undefined_ID)), dimension(:,:), allocatable, private :: &
|
|
||||||
thermal_adiabatic_outputID !< ID of each post result output
|
|
||||||
|
|
||||||
|
|
||||||
public :: &
|
|
||||||
thermal_adiabatic_init, &
|
|
||||||
thermal_adiabatic_updateState, &
|
|
||||||
thermal_adiabatic_getSourceAndItsTangent, &
|
|
||||||
thermal_adiabatic_getSpecificHeat, &
|
|
||||||
thermal_adiabatic_getMassDensity, &
|
|
||||||
thermal_adiabatic_postResults
|
|
||||||
|
|
||||||
contains
|
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief module initialization
|
|
||||||
!> @details reads in material parameters, allocates arrays, and does sanity checks
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine thermal_adiabatic_init(fileUnit)
|
|
||||||
use, intrinsic :: iso_fortran_env ! to get compiler_version and compiler_options (at least for gfortran 4.6 at the moment)
|
|
||||||
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: &
|
|
||||||
thermal_type, &
|
|
||||||
thermal_typeInstance, &
|
|
||||||
homogenization_Noutput, &
|
|
||||||
THERMAL_ADIABATIC_label, &
|
|
||||||
THERMAL_adiabatic_ID, &
|
|
||||||
material_homog, &
|
|
||||||
mappingHomogenization, &
|
|
||||||
thermalState, &
|
|
||||||
thermalMapping, &
|
|
||||||
thermal_initialT, &
|
|
||||||
temperature, &
|
|
||||||
temperatureRate, &
|
|
||||||
material_partHomogenization
|
|
||||||
use numerics,only: &
|
|
||||||
worldrank
|
|
||||||
|
|
||||||
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 = ''
|
|
||||||
|
|
||||||
mainProcess: if (worldrank == 0) then
|
|
||||||
write(6,'(/,a)') ' <<<+- thermal_'//THERMAL_ADIABATIC_label//' init -+>>>'
|
|
||||||
write(6,'(a15,a)') ' Current time: ',IO_timeStamp()
|
|
||||||
#include "compilation_info.f90"
|
|
||||||
endif mainProcess
|
|
||||||
|
|
||||||
maxNinstance = int(count(thermal_type == THERMAL_adiabatic_ID),pInt)
|
|
||||||
if (maxNinstance == 0_pInt) return
|
|
||||||
|
|
||||||
allocate(thermal_adiabatic_sizePostResults(maxNinstance), source=0_pInt)
|
|
||||||
allocate(thermal_adiabatic_sizePostResult (maxval(homogenization_Noutput),maxNinstance),source=0_pInt)
|
|
||||||
allocate(thermal_adiabatic_output (maxval(homogenization_Noutput),maxNinstance))
|
|
||||||
thermal_adiabatic_output = ''
|
|
||||||
allocate(thermal_adiabatic_outputID (maxval(homogenization_Noutput),maxNinstance),source=undefined_ID)
|
|
||||||
allocate(thermal_adiabatic_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 (thermal_type(section) == THERMAL_adiabatic_ID) then ! do not short-circuit here (.and. with next if statemen). It's not safe in Fortran
|
|
||||||
|
|
||||||
instance = thermal_typeInstance(section) ! which instance of my thermal 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 ('temperature')
|
|
||||||
thermal_adiabatic_Noutput(instance) = thermal_adiabatic_Noutput(instance) + 1_pInt
|
|
||||||
thermal_adiabatic_outputID(thermal_adiabatic_Noutput(instance),instance) = temperature_ID
|
|
||||||
thermal_adiabatic_output(thermal_adiabatic_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(thermal_type)
|
|
||||||
if (thermal_type(section) == THERMAL_adiabatic_ID) then
|
|
||||||
NofMyHomog=count(material_homog==section)
|
|
||||||
instance = thermal_typeInstance(section)
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! Determine size of postResults array
|
|
||||||
outputsLoop: do o = 1_pInt,thermal_adiabatic_Noutput(instance)
|
|
||||||
select case(thermal_adiabatic_outputID(o,instance))
|
|
||||||
case(temperature_ID)
|
|
||||||
mySize = 1_pInt
|
|
||||||
end select
|
|
||||||
|
|
||||||
if (mySize > 0_pInt) then ! any meaningful output found
|
|
||||||
thermal_adiabatic_sizePostResult(o,instance) = mySize
|
|
||||||
thermal_adiabatic_sizePostResults(instance) = thermal_adiabatic_sizePostResults(instance) + mySize
|
|
||||||
endif
|
|
||||||
enddo outputsLoop
|
|
||||||
|
|
||||||
! allocate state arrays
|
|
||||||
sizeState = 1_pInt
|
|
||||||
thermalState(section)%sizeState = sizeState
|
|
||||||
thermalState(section)%sizePostResults = thermal_adiabatic_sizePostResults(instance)
|
|
||||||
allocate(thermalState(section)%state0 (sizeState,NofMyHomog), source=thermal_initialT(section))
|
|
||||||
allocate(thermalState(section)%subState0(sizeState,NofMyHomog), source=thermal_initialT(section))
|
|
||||||
allocate(thermalState(section)%state (sizeState,NofMyHomog), source=thermal_initialT(section))
|
|
||||||
|
|
||||||
nullify(thermalMapping(section)%p)
|
|
||||||
thermalMapping(section)%p => mappingHomogenization(1,:,:)
|
|
||||||
deallocate(temperature(section)%p)
|
|
||||||
temperature(section)%p => thermalState(section)%state(1,:)
|
|
||||||
deallocate(temperatureRate(section)%p)
|
|
||||||
allocate (temperatureRate(section)%p(NofMyHomog), source=0.0_pReal)
|
|
||||||
|
|
||||||
endif
|
|
||||||
|
|
||||||
enddo initializeInstances
|
|
||||||
end subroutine thermal_adiabatic_init
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief calculates adiabatic change in temperature based on local heat generation model
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
function thermal_adiabatic_updateState(subdt, ip, el)
|
|
||||||
use numerics, only: &
|
|
||||||
err_thermal_tolAbs, &
|
|
||||||
err_thermal_tolRel
|
|
||||||
use material, only: &
|
|
||||||
mappingHomogenization, &
|
|
||||||
thermalState, &
|
|
||||||
temperature, &
|
|
||||||
temperatureRate, &
|
|
||||||
thermalMapping
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
integer(pInt), intent(in) :: &
|
|
||||||
ip, & !< integration point number
|
|
||||||
el !< element number
|
|
||||||
real(pReal), intent(in) :: &
|
|
||||||
subdt
|
|
||||||
logical, dimension(2) :: &
|
|
||||||
thermal_adiabatic_updateState
|
|
||||||
integer(pInt) :: &
|
|
||||||
homog, &
|
|
||||||
offset
|
|
||||||
real(pReal) :: &
|
|
||||||
T, Tdot, dTdot_dT
|
|
||||||
|
|
||||||
homog = mappingHomogenization(2,ip,el)
|
|
||||||
offset = mappingHomogenization(1,ip,el)
|
|
||||||
|
|
||||||
T = thermalState(homog)%subState0(1,offset)
|
|
||||||
call thermal_adiabatic_getSourceAndItsTangent(Tdot, dTdot_dT, T, ip, el)
|
|
||||||
T = T + subdt*Tdot/(thermal_adiabatic_getSpecificHeat(ip,el)*thermal_adiabatic_getMassDensity(ip,el))
|
|
||||||
|
|
||||||
thermal_adiabatic_updateState = [ abs(T - thermalState(homog)%state(1,offset)) &
|
|
||||||
<= err_thermal_tolAbs &
|
|
||||||
.or. abs(T - thermalState(homog)%state(1,offset)) &
|
|
||||||
<= err_thermal_tolRel*abs(thermalState(homog)%state(1,offset)), &
|
|
||||||
.true.]
|
|
||||||
|
|
||||||
temperature (homog)%p(thermalMapping(homog)%p(ip,el)) = T
|
|
||||||
temperatureRate(homog)%p(thermalMapping(homog)%p(ip,el)) = &
|
|
||||||
(thermalState(homog)%state(1,offset) - thermalState(homog)%subState0(1,offset))/(subdt+tiny(0.0_pReal))
|
|
||||||
|
|
||||||
end function thermal_adiabatic_updateState
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief returns heat generation rate
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine thermal_adiabatic_getSourceAndItsTangent(Tdot, dTdot_dT, T, ip, el)
|
|
||||||
use math, only: &
|
|
||||||
math_Mandel6to33
|
|
||||||
use material, only: &
|
|
||||||
homogenization_Ngrains, &
|
|
||||||
mappingHomogenization, &
|
|
||||||
phaseAt, phasememberAt, &
|
|
||||||
thermal_typeInstance, &
|
|
||||||
phase_Nsources, &
|
|
||||||
phase_source, &
|
|
||||||
SOURCE_thermal_dissipation_ID, &
|
|
||||||
SOURCE_thermal_externalheat_ID
|
|
||||||
use source_thermal_dissipation, only: &
|
|
||||||
source_thermal_dissipation_getRateAndItsTangent
|
|
||||||
use source_thermal_externalheat, only: &
|
|
||||||
source_thermal_externalheat_getRateAndItsTangent
|
|
||||||
use crystallite, only: &
|
|
||||||
crystallite_Tstar_v, &
|
|
||||||
crystallite_Lp
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
integer(pInt), intent(in) :: &
|
|
||||||
ip, & !< integration point number
|
|
||||||
el !< element number
|
|
||||||
real(pReal), intent(in) :: &
|
|
||||||
T
|
|
||||||
real(pReal), intent(out) :: &
|
|
||||||
Tdot, dTdot_dT
|
|
||||||
real(pReal) :: &
|
|
||||||
my_Tdot, my_dTdot_dT
|
|
||||||
integer(pInt) :: &
|
|
||||||
phase, &
|
|
||||||
homog, &
|
|
||||||
offset, &
|
|
||||||
instance, &
|
|
||||||
grain, &
|
|
||||||
source
|
|
||||||
|
|
||||||
homog = mappingHomogenization(2,ip,el)
|
|
||||||
offset = mappingHomogenization(1,ip,el)
|
|
||||||
instance = thermal_typeInstance(homog)
|
|
||||||
|
|
||||||
Tdot = 0.0_pReal
|
|
||||||
dTdot_dT = 0.0_pReal
|
|
||||||
do grain = 1, homogenization_Ngrains(homog)
|
|
||||||
phase = phaseAt(grain,ip,el)
|
|
||||||
do source = 1, phase_Nsources(phase)
|
|
||||||
select case(phase_source(source,phase))
|
|
||||||
case (SOURCE_thermal_dissipation_ID)
|
|
||||||
call source_thermal_dissipation_getRateAndItsTangent(my_Tdot, my_dTdot_dT, &
|
|
||||||
crystallite_Tstar_v(1:6,grain,ip,el), &
|
|
||||||
crystallite_Lp(1:3,1:3,grain,ip,el), &
|
|
||||||
grain, ip, el)
|
|
||||||
|
|
||||||
case (SOURCE_thermal_externalheat_ID)
|
|
||||||
call source_thermal_externalheat_getRateAndItsTangent(my_Tdot, my_dTdot_dT, &
|
|
||||||
grain, ip, el)
|
|
||||||
|
|
||||||
case default
|
|
||||||
my_Tdot = 0.0_pReal
|
|
||||||
my_dTdot_dT = 0.0_pReal
|
|
||||||
end select
|
|
||||||
Tdot = Tdot + my_Tdot
|
|
||||||
dTdot_dT = dTdot_dT + my_dTdot_dT
|
|
||||||
enddo
|
|
||||||
enddo
|
|
||||||
|
|
||||||
Tdot = Tdot/homogenization_Ngrains(homog)
|
|
||||||
dTdot_dT = dTdot_dT/homogenization_Ngrains(homog)
|
|
||||||
|
|
||||||
end subroutine thermal_adiabatic_getSourceAndItsTangent
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief returns homogenized specific heat capacity
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
function thermal_adiabatic_getSpecificHeat(ip,el)
|
|
||||||
use lattice, only: &
|
|
||||||
lattice_specificHeat
|
|
||||||
use material, only: &
|
|
||||||
homogenization_Ngrains, &
|
|
||||||
mappingHomogenization, &
|
|
||||||
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) :: &
|
|
||||||
thermal_adiabatic_getSpecificHeat
|
|
||||||
integer(pInt) :: &
|
|
||||||
homog, grain
|
|
||||||
|
|
||||||
thermal_adiabatic_getSpecificHeat = 0.0_pReal
|
|
||||||
|
|
||||||
homog = mappingHomogenization(2,ip,el)
|
|
||||||
|
|
||||||
do grain = 1, homogenization_Ngrains(mesh_element(3,el))
|
|
||||||
thermal_adiabatic_getSpecificHeat = thermal_adiabatic_getSpecificHeat + &
|
|
||||||
lattice_specificHeat(material_phase(grain,ip,el))
|
|
||||||
enddo
|
|
||||||
|
|
||||||
thermal_adiabatic_getSpecificHeat = &
|
|
||||||
thermal_adiabatic_getSpecificHeat/ &
|
|
||||||
homogenization_Ngrains(mesh_element(3,el))
|
|
||||||
|
|
||||||
end function thermal_adiabatic_getSpecificHeat
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief returns homogenized mass density
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
function thermal_adiabatic_getMassDensity(ip,el)
|
|
||||||
use lattice, only: &
|
|
||||||
lattice_massDensity
|
|
||||||
use material, only: &
|
|
||||||
homogenization_Ngrains, &
|
|
||||||
mappingHomogenization, &
|
|
||||||
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) :: &
|
|
||||||
thermal_adiabatic_getMassDensity
|
|
||||||
integer(pInt) :: &
|
|
||||||
homog, grain
|
|
||||||
|
|
||||||
thermal_adiabatic_getMassDensity = 0.0_pReal
|
|
||||||
|
|
||||||
homog = mappingHomogenization(2,ip,el)
|
|
||||||
|
|
||||||
do grain = 1, homogenization_Ngrains(mesh_element(3,el))
|
|
||||||
thermal_adiabatic_getMassDensity = thermal_adiabatic_getMassDensity + &
|
|
||||||
lattice_massDensity(material_phase(grain,ip,el))
|
|
||||||
enddo
|
|
||||||
|
|
||||||
thermal_adiabatic_getMassDensity = &
|
|
||||||
thermal_adiabatic_getMassDensity/ &
|
|
||||||
homogenization_Ngrains(mesh_element(3,el))
|
|
||||||
|
|
||||||
end function thermal_adiabatic_getMassDensity
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief return array of thermal results
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
function thermal_adiabatic_postResults(ip,el)
|
|
||||||
use material, only: &
|
|
||||||
mappingHomogenization, &
|
|
||||||
thermal_typeInstance, &
|
|
||||||
thermalMapping, &
|
|
||||||
temperature
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
integer(pInt), intent(in) :: &
|
|
||||||
ip, & !< integration point
|
|
||||||
el !< element
|
|
||||||
real(pReal), dimension(thermal_adiabatic_sizePostResults(thermal_typeInstance(mappingHomogenization(2,ip,el)))) :: &
|
|
||||||
thermal_adiabatic_postResults
|
|
||||||
|
|
||||||
integer(pInt) :: &
|
|
||||||
instance, homog, offset, o, c
|
|
||||||
|
|
||||||
homog = mappingHomogenization(2,ip,el)
|
|
||||||
offset = thermalMapping(homog)%p(ip,el)
|
|
||||||
instance = thermal_typeInstance(homog)
|
|
||||||
|
|
||||||
c = 0_pInt
|
|
||||||
thermal_adiabatic_postResults = 0.0_pReal
|
|
||||||
|
|
||||||
do o = 1_pInt,thermal_adiabatic_Noutput(instance)
|
|
||||||
select case(thermal_adiabatic_outputID(o,instance))
|
|
||||||
|
|
||||||
case (temperature_ID)
|
|
||||||
thermal_adiabatic_postResults(c+1_pInt) = temperature(homog)%p(offset)
|
|
||||||
c = c + 1
|
|
||||||
end select
|
|
||||||
enddo
|
|
||||||
end function thermal_adiabatic_postResults
|
|
||||||
|
|
||||||
end module thermal_adiabatic
|
|
|
@ -1,444 +0,0 @@
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! $Id$
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @author Pratheek Shanthraj, Max-Planck-Institut für Eisenforschung GmbH
|
|
||||||
!> @brief material subroutine for temperature evolution from heat conduction
|
|
||||||
!> @details to be done
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
module thermal_conduction
|
|
||||||
use prec, only: &
|
|
||||||
pReal, &
|
|
||||||
pInt
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
private
|
|
||||||
integer(pInt), dimension(:), allocatable, public, protected :: &
|
|
||||||
thermal_conduction_sizePostResults !< cumulative size of post results
|
|
||||||
|
|
||||||
integer(pInt), dimension(:,:), allocatable, target, public :: &
|
|
||||||
thermal_conduction_sizePostResult !< size of each post result output
|
|
||||||
|
|
||||||
character(len=64), dimension(:,:), allocatable, target, public :: &
|
|
||||||
thermal_conduction_output !< name of each post result output
|
|
||||||
|
|
||||||
integer(pInt), dimension(:), allocatable, target, public :: &
|
|
||||||
thermal_conduction_Noutput !< number of outputs per instance of this damage
|
|
||||||
|
|
||||||
enum, bind(c)
|
|
||||||
enumerator :: undefined_ID, &
|
|
||||||
temperature_ID
|
|
||||||
end enum
|
|
||||||
integer(kind(undefined_ID)), dimension(:,:), allocatable, private :: &
|
|
||||||
thermal_conduction_outputID !< ID of each post result output
|
|
||||||
|
|
||||||
|
|
||||||
public :: &
|
|
||||||
thermal_conduction_init, &
|
|
||||||
thermal_conduction_getSourceAndItsTangent, &
|
|
||||||
thermal_conduction_getConductivity33, &
|
|
||||||
thermal_conduction_getSpecificHeat, &
|
|
||||||
thermal_conduction_getMassDensity, &
|
|
||||||
thermal_conduction_putTemperatureAndItsRate, &
|
|
||||||
thermal_conduction_postResults
|
|
||||||
|
|
||||||
contains
|
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief module initialization
|
|
||||||
!> @details reads in material parameters, allocates arrays, and does sanity checks
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine thermal_conduction_init(fileUnit)
|
|
||||||
use, intrinsic :: iso_fortran_env ! to get compiler_version and compiler_options (at least for gfortran 4.6 at the moment)
|
|
||||||
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: &
|
|
||||||
thermal_type, &
|
|
||||||
thermal_typeInstance, &
|
|
||||||
homogenization_Noutput, &
|
|
||||||
THERMAL_conduction_label, &
|
|
||||||
THERMAL_conduction_ID, &
|
|
||||||
material_homog, &
|
|
||||||
mappingHomogenization, &
|
|
||||||
thermalState, &
|
|
||||||
thermalMapping, &
|
|
||||||
thermal_initialT, &
|
|
||||||
temperature, &
|
|
||||||
temperatureRate, &
|
|
||||||
material_partHomogenization
|
|
||||||
use numerics,only: &
|
|
||||||
worldrank
|
|
||||||
|
|
||||||
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 = ''
|
|
||||||
|
|
||||||
mainProcess: if (worldrank == 0) then
|
|
||||||
write(6,'(/,a)') ' <<<+- thermal_'//THERMAL_CONDUCTION_label//' init -+>>>'
|
|
||||||
write(6,'(a15,a)') ' Current time: ',IO_timeStamp()
|
|
||||||
#include "compilation_info.f90"
|
|
||||||
endif mainProcess
|
|
||||||
|
|
||||||
maxNinstance = int(count(thermal_type == THERMAL_conduction_ID),pInt)
|
|
||||||
if (maxNinstance == 0_pInt) return
|
|
||||||
|
|
||||||
allocate(thermal_conduction_sizePostResults(maxNinstance), source=0_pInt)
|
|
||||||
allocate(thermal_conduction_sizePostResult (maxval(homogenization_Noutput),maxNinstance),source=0_pInt)
|
|
||||||
allocate(thermal_conduction_output (maxval(homogenization_Noutput),maxNinstance))
|
|
||||||
thermal_conduction_output = ''
|
|
||||||
allocate(thermal_conduction_outputID (maxval(homogenization_Noutput),maxNinstance),source=undefined_ID)
|
|
||||||
allocate(thermal_conduction_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 (thermal_type(section) == THERMAL_conduction_ID) then ! do not short-circuit here (.and. with next if statemen). It's not safe in Fortran
|
|
||||||
|
|
||||||
instance = thermal_typeInstance(section) ! which instance of my thermal 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 ('temperature')
|
|
||||||
thermal_conduction_Noutput(instance) = thermal_conduction_Noutput(instance) + 1_pInt
|
|
||||||
thermal_conduction_outputID(thermal_conduction_Noutput(instance),instance) = temperature_ID
|
|
||||||
thermal_conduction_output(thermal_conduction_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(thermal_type)
|
|
||||||
if (thermal_type(section) == THERMAL_conduction_ID) then
|
|
||||||
NofMyHomog=count(material_homog==section)
|
|
||||||
instance = thermal_typeInstance(section)
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! Determine size of postResults array
|
|
||||||
outputsLoop: do o = 1_pInt,thermal_conduction_Noutput(instance)
|
|
||||||
select case(thermal_conduction_outputID(o,instance))
|
|
||||||
case(temperature_ID)
|
|
||||||
mySize = 1_pInt
|
|
||||||
end select
|
|
||||||
|
|
||||||
if (mySize > 0_pInt) then ! any meaningful output found
|
|
||||||
thermal_conduction_sizePostResult(o,instance) = mySize
|
|
||||||
thermal_conduction_sizePostResults(instance) = thermal_conduction_sizePostResults(instance) + mySize
|
|
||||||
endif
|
|
||||||
enddo outputsLoop
|
|
||||||
|
|
||||||
! allocate state arrays
|
|
||||||
sizeState = 0_pInt
|
|
||||||
thermalState(section)%sizeState = sizeState
|
|
||||||
thermalState(section)%sizePostResults = thermal_conduction_sizePostResults(instance)
|
|
||||||
allocate(thermalState(section)%state0 (sizeState,NofMyHomog))
|
|
||||||
allocate(thermalState(section)%subState0(sizeState,NofMyHomog))
|
|
||||||
allocate(thermalState(section)%state (sizeState,NofMyHomog))
|
|
||||||
|
|
||||||
nullify(thermalMapping(section)%p)
|
|
||||||
thermalMapping(section)%p => mappingHomogenization(1,:,:)
|
|
||||||
deallocate(temperature (section)%p)
|
|
||||||
allocate (temperature (section)%p(NofMyHomog), source=thermal_initialT(section))
|
|
||||||
deallocate(temperatureRate(section)%p)
|
|
||||||
allocate (temperatureRate(section)%p(NofMyHomog), source=0.0_pReal)
|
|
||||||
|
|
||||||
endif
|
|
||||||
|
|
||||||
enddo initializeInstances
|
|
||||||
end subroutine thermal_conduction_init
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief returns heat generation rate
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine thermal_conduction_getSourceAndItsTangent(Tdot, dTdot_dT, T, ip, el)
|
|
||||||
use math, only: &
|
|
||||||
math_Mandel6to33
|
|
||||||
use material, only: &
|
|
||||||
homogenization_Ngrains, &
|
|
||||||
mappingHomogenization, &
|
|
||||||
phaseAt, phasememberAt, &
|
|
||||||
thermal_typeInstance, &
|
|
||||||
phase_Nsources, &
|
|
||||||
phase_source, &
|
|
||||||
SOURCE_thermal_dissipation_ID, &
|
|
||||||
SOURCE_thermal_externalheat_ID
|
|
||||||
use source_thermal_dissipation, only: &
|
|
||||||
source_thermal_dissipation_getRateAndItsTangent
|
|
||||||
use source_thermal_externalheat, only: &
|
|
||||||
source_thermal_externalheat_getRateAndItsTangent
|
|
||||||
use crystallite, only: &
|
|
||||||
crystallite_Tstar_v, &
|
|
||||||
crystallite_Lp
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
integer(pInt), intent(in) :: &
|
|
||||||
ip, & !< integration point number
|
|
||||||
el !< element number
|
|
||||||
real(pReal), intent(in) :: &
|
|
||||||
T
|
|
||||||
real(pReal), intent(out) :: &
|
|
||||||
Tdot, dTdot_dT
|
|
||||||
real(pReal) :: &
|
|
||||||
my_Tdot, my_dTdot_dT
|
|
||||||
integer(pInt) :: &
|
|
||||||
phase, &
|
|
||||||
homog, &
|
|
||||||
offset, &
|
|
||||||
instance, &
|
|
||||||
grain, &
|
|
||||||
source
|
|
||||||
|
|
||||||
homog = mappingHomogenization(2,ip,el)
|
|
||||||
offset = mappingHomogenization(1,ip,el)
|
|
||||||
instance = thermal_typeInstance(homog)
|
|
||||||
|
|
||||||
Tdot = 0.0_pReal
|
|
||||||
dTdot_dT = 0.0_pReal
|
|
||||||
do grain = 1, homogenization_Ngrains(homog)
|
|
||||||
phase = phaseAt(grain,ip,el)
|
|
||||||
do source = 1, phase_Nsources(phase)
|
|
||||||
select case(phase_source(source,phase))
|
|
||||||
case (SOURCE_thermal_dissipation_ID)
|
|
||||||
call source_thermal_dissipation_getRateAndItsTangent(my_Tdot, my_dTdot_dT, &
|
|
||||||
crystallite_Tstar_v(1:6,grain,ip,el), &
|
|
||||||
crystallite_Lp(1:3,1:3,grain,ip,el), &
|
|
||||||
grain, ip, el)
|
|
||||||
|
|
||||||
case (SOURCE_thermal_externalheat_ID)
|
|
||||||
call source_thermal_externalheat_getRateAndItsTangent(my_Tdot, my_dTdot_dT, &
|
|
||||||
grain, ip, el)
|
|
||||||
|
|
||||||
case default
|
|
||||||
my_Tdot = 0.0_pReal
|
|
||||||
my_dTdot_dT = 0.0_pReal
|
|
||||||
|
|
||||||
end select
|
|
||||||
Tdot = Tdot + my_Tdot
|
|
||||||
dTdot_dT = dTdot_dT + my_dTdot_dT
|
|
||||||
enddo
|
|
||||||
enddo
|
|
||||||
|
|
||||||
Tdot = Tdot/homogenization_Ngrains(homog)
|
|
||||||
dTdot_dT = dTdot_dT/homogenization_Ngrains(homog)
|
|
||||||
|
|
||||||
end subroutine thermal_conduction_getSourceAndItsTangent
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief returns homogenized thermal conductivity in reference configuration
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
function thermal_conduction_getConductivity33(ip,el)
|
|
||||||
use lattice, only: &
|
|
||||||
lattice_thermalConductivity33
|
|
||||||
use material, only: &
|
|
||||||
homogenization_Ngrains, &
|
|
||||||
mappingHomogenization, &
|
|
||||||
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) :: &
|
|
||||||
thermal_conduction_getConductivity33
|
|
||||||
integer(pInt) :: &
|
|
||||||
homog, &
|
|
||||||
grain
|
|
||||||
|
|
||||||
homog = mappingHomogenization(2,ip,el)
|
|
||||||
|
|
||||||
thermal_conduction_getConductivity33 = 0.0_pReal
|
|
||||||
do grain = 1, homogenization_Ngrains(mesh_element(3,el))
|
|
||||||
thermal_conduction_getConductivity33 = thermal_conduction_getConductivity33 + &
|
|
||||||
crystallite_push33ToRef(grain,ip,el,lattice_thermalConductivity33(:,:,material_phase(grain,ip,el)))
|
|
||||||
enddo
|
|
||||||
|
|
||||||
thermal_conduction_getConductivity33 = &
|
|
||||||
thermal_conduction_getConductivity33/ &
|
|
||||||
homogenization_Ngrains(mesh_element(3,el))
|
|
||||||
|
|
||||||
end function thermal_conduction_getConductivity33
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief returns homogenized specific heat capacity
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
function thermal_conduction_getSpecificHeat(ip,el)
|
|
||||||
use lattice, only: &
|
|
||||||
lattice_specificHeat
|
|
||||||
use material, only: &
|
|
||||||
homogenization_Ngrains, &
|
|
||||||
mappingHomogenization, &
|
|
||||||
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) :: &
|
|
||||||
thermal_conduction_getSpecificHeat
|
|
||||||
integer(pInt) :: &
|
|
||||||
homog, grain
|
|
||||||
|
|
||||||
thermal_conduction_getSpecificHeat = 0.0_pReal
|
|
||||||
|
|
||||||
homog = mappingHomogenization(2,ip,el)
|
|
||||||
|
|
||||||
do grain = 1, homogenization_Ngrains(mesh_element(3,el))
|
|
||||||
thermal_conduction_getSpecificHeat = thermal_conduction_getSpecificHeat + &
|
|
||||||
lattice_specificHeat(material_phase(grain,ip,el))
|
|
||||||
enddo
|
|
||||||
|
|
||||||
thermal_conduction_getSpecificHeat = &
|
|
||||||
thermal_conduction_getSpecificHeat/ &
|
|
||||||
homogenization_Ngrains(mesh_element(3,el))
|
|
||||||
|
|
||||||
end function thermal_conduction_getSpecificHeat
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief returns homogenized mass density
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
function thermal_conduction_getMassDensity(ip,el)
|
|
||||||
use lattice, only: &
|
|
||||||
lattice_massDensity
|
|
||||||
use material, only: &
|
|
||||||
homogenization_Ngrains, &
|
|
||||||
mappingHomogenization, &
|
|
||||||
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) :: &
|
|
||||||
thermal_conduction_getMassDensity
|
|
||||||
integer(pInt) :: &
|
|
||||||
homog, grain
|
|
||||||
|
|
||||||
thermal_conduction_getMassDensity = 0.0_pReal
|
|
||||||
|
|
||||||
homog = mappingHomogenization(2,ip,el)
|
|
||||||
|
|
||||||
do grain = 1, homogenization_Ngrains(mesh_element(3,el))
|
|
||||||
thermal_conduction_getMassDensity = thermal_conduction_getMassDensity + &
|
|
||||||
lattice_massDensity(material_phase(grain,ip,el))
|
|
||||||
enddo
|
|
||||||
|
|
||||||
thermal_conduction_getMassDensity = &
|
|
||||||
thermal_conduction_getMassDensity/ &
|
|
||||||
homogenization_Ngrains(mesh_element(3,el))
|
|
||||||
|
|
||||||
end function thermal_conduction_getMassDensity
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief updates thermal state with solution from heat conduction PDE
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine thermal_conduction_putTemperatureAndItsRate(T,Tdot,ip,el)
|
|
||||||
use material, only: &
|
|
||||||
mappingHomogenization, &
|
|
||||||
temperature, &
|
|
||||||
temperatureRate, &
|
|
||||||
thermalMapping
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
integer(pInt), intent(in) :: &
|
|
||||||
ip, & !< integration point number
|
|
||||||
el !< element number
|
|
||||||
real(pReal), intent(in) :: &
|
|
||||||
T, &
|
|
||||||
Tdot
|
|
||||||
integer(pInt) :: &
|
|
||||||
homog, &
|
|
||||||
offset
|
|
||||||
|
|
||||||
homog = mappingHomogenization(2,ip,el)
|
|
||||||
offset = thermalMapping(homog)%p(ip,el)
|
|
||||||
temperature (homog)%p(offset) = T
|
|
||||||
temperatureRate(homog)%p(offset) = Tdot
|
|
||||||
|
|
||||||
end subroutine thermal_conduction_putTemperatureAndItsRate
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief return array of thermal results
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
function thermal_conduction_postResults(ip,el)
|
|
||||||
use material, only: &
|
|
||||||
mappingHomogenization, &
|
|
||||||
thermal_typeInstance, &
|
|
||||||
temperature, &
|
|
||||||
thermalMapping
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
integer(pInt), intent(in) :: &
|
|
||||||
ip, & !< integration point
|
|
||||||
el !< element
|
|
||||||
real(pReal), dimension(thermal_conduction_sizePostResults(thermal_typeInstance(mappingHomogenization(2,ip,el)))) :: &
|
|
||||||
thermal_conduction_postResults
|
|
||||||
|
|
||||||
integer(pInt) :: &
|
|
||||||
instance, homog, offset, o, c
|
|
||||||
|
|
||||||
homog = mappingHomogenization(2,ip,el)
|
|
||||||
offset = thermalMapping(homog)%p(ip,el)
|
|
||||||
instance = thermal_typeInstance(homog)
|
|
||||||
|
|
||||||
c = 0_pInt
|
|
||||||
thermal_conduction_postResults = 0.0_pReal
|
|
||||||
|
|
||||||
do o = 1_pInt,thermal_conduction_Noutput(instance)
|
|
||||||
select case(thermal_conduction_outputID(o,instance))
|
|
||||||
|
|
||||||
case (temperature_ID)
|
|
||||||
thermal_conduction_postResults(c+1_pInt) = temperature(homog)%p(offset)
|
|
||||||
c = c + 1
|
|
||||||
end select
|
|
||||||
enddo
|
|
||||||
end function thermal_conduction_postResults
|
|
||||||
|
|
||||||
end module thermal_conduction
|
|
|
@ -1,65 +0,0 @@
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! $Id$
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @author Pratheek Shanthraj, Max-Planck-Institut für Eisenforschung GmbH
|
|
||||||
!> @brief material subroutine for isothermal temperature field
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
module thermal_isothermal
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
private
|
|
||||||
|
|
||||||
public :: &
|
|
||||||
thermal_isothermal_init
|
|
||||||
|
|
||||||
contains
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief allocates all neccessary fields, reads information from material configuration file
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine thermal_isothermal_init()
|
|
||||||
use, intrinsic :: iso_fortran_env ! to get compiler_version and compiler_options (at least for gfortran 4.6 at the moment)
|
|
||||||
use prec, only: &
|
|
||||||
pReal, &
|
|
||||||
pInt
|
|
||||||
use IO, only: &
|
|
||||||
IO_timeStamp
|
|
||||||
use material
|
|
||||||
use numerics, only: &
|
|
||||||
worldrank
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
integer(pInt) :: &
|
|
||||||
homog, &
|
|
||||||
NofMyHomog, &
|
|
||||||
sizeState
|
|
||||||
|
|
||||||
mainProcess: if (worldrank == 0) then
|
|
||||||
write(6,'(/,a)') ' <<<+- thermal_'//THERMAL_isothermal_label//' init -+>>>'
|
|
||||||
write(6,'(a15,a)') ' Current time: ',IO_timeStamp()
|
|
||||||
#include "compilation_info.f90"
|
|
||||||
endif mainProcess
|
|
||||||
|
|
||||||
initializeInstances: do homog = 1_pInt, material_Nhomogenization
|
|
||||||
|
|
||||||
myhomog: if (thermal_type(homog) == THERMAL_isothermal_ID) then
|
|
||||||
NofMyHomog = count(material_homog == homog)
|
|
||||||
sizeState = 0_pInt
|
|
||||||
thermalState(homog)%sizeState = sizeState
|
|
||||||
thermalState(homog)%sizePostResults = sizeState
|
|
||||||
allocate(thermalState(homog)%state0 (sizeState,NofMyHomog), source=0.0_pReal)
|
|
||||||
allocate(thermalState(homog)%subState0(sizeState,NofMyHomog), source=0.0_pReal)
|
|
||||||
allocate(thermalState(homog)%state (sizeState,NofMyHomog), source=0.0_pReal)
|
|
||||||
|
|
||||||
deallocate(temperature (homog)%p)
|
|
||||||
allocate (temperature (homog)%p(1), source=thermal_initialT(homog))
|
|
||||||
deallocate(temperatureRate(homog)%p)
|
|
||||||
allocate (temperatureRate(homog)%p(1), source=0.0_pReal)
|
|
||||||
|
|
||||||
endif myhomog
|
|
||||||
enddo initializeInstances
|
|
||||||
|
|
||||||
|
|
||||||
end subroutine thermal_isothermal_init
|
|
||||||
|
|
||||||
end module thermal_isothermal
|
|
|
@ -8,3 +8,8 @@ set (VACANCYFLUX "vacancyflux_isoconc"
|
||||||
foreach (p ${VACANCYFLUX})
|
foreach (p ${VACANCYFLUX})
|
||||||
add_library (${p} MODULE "${p}.f90")
|
add_library (${p} MODULE "${p}.f90")
|
||||||
endforeach (p)
|
endforeach (p)
|
||||||
|
|
||||||
|
# set libraries/modules for linking
|
||||||
|
foreach (p ${VACANCYFLUX})
|
||||||
|
set (AUX_LIB ${AUX_LIB} ${p})
|
||||||
|
endforeach (p)
|
|
@ -1,606 +0,0 @@
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! $Id$
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @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, &
|
|
||||||
p_vec
|
|
||||||
|
|
||||||
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(p_vec), 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)
|
|
||||||
use, intrinsic :: iso_fortran_env ! to get compiler_version and compiler_options (at least for gfortran 4.6 at the moment)
|
|
||||||
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, &
|
|
||||||
material_partHomogenization, &
|
|
||||||
material_partPhase
|
|
||||||
use numerics,only: &
|
|
||||||
worldrank
|
|
||||||
|
|
||||||
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 = ''
|
|
||||||
|
|
||||||
mainProcess: if (worldrank == 0) then
|
|
||||||
write(6,'(/,a)') ' <<<+- vacancyflux_'//VACANCYFLUX_cahnhilliard_label//' init -+>>>'
|
|
||||||
write(6,'(a15,a)') ' Current time: ',IO_timeStamp()
|
|
||||||
#include "compilation_info.f90"
|
|
||||||
endif mainProcess
|
|
||||||
|
|
||||||
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, phasememberAt, &
|
|
||||||
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/homogenization_Ngrains(mappingHomogenization(2,ip,el))
|
|
||||||
dCvDot_dCv = dCvDot_dCv/homogenization_Ngrains(mappingHomogenization(2,ip,el))
|
|
||||||
|
|
||||||
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/ &
|
|
||||||
homogenization_Ngrains(mesh_element(3,el))
|
|
||||||
|
|
||||||
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/ &
|
|
||||||
homogenization_Ngrains(mesh_element(3,el))
|
|
||||||
|
|
||||||
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/ &
|
|
||||||
homogenization_Ngrains(mesh_element(3,el))
|
|
||||||
|
|
||||||
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))/ &
|
|
||||||
homogenization_Ngrains(material_homog(ip,el))
|
|
||||||
|
|
||||||
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/homogenization_Ngrains(material_homog(ip,el))
|
|
||||||
dKPot_dCv = dKPot_dCv/homogenization_Ngrains(material_homog(ip,el))
|
|
||||||
|
|
||||||
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,329 +0,0 @@
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! $Id$
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @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)
|
|
||||||
use, intrinsic :: iso_fortran_env ! to get compiler_version and compiler_options (at least for gfortran 4.6 at the moment)
|
|
||||||
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, &
|
|
||||||
material_partHomogenization
|
|
||||||
use numerics,only: &
|
|
||||||
worldrank
|
|
||||||
|
|
||||||
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 = ''
|
|
||||||
|
|
||||||
mainProcess: if (worldrank == 0) then
|
|
||||||
write(6,'(/,a)') ' <<<+- vacancyflux_'//VACANCYFLUX_isochempot_label//' init -+>>>'
|
|
||||||
write(6,'(a15,a)') ' Current time: ',IO_timeStamp()
|
|
||||||
#include "compilation_info.f90"
|
|
||||||
endif mainProcess
|
|
||||||
|
|
||||||
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, phasememberAt, &
|
|
||||||
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/homogenization_Ngrains(mappingHomogenization(2,ip,el))
|
|
||||||
dCvDot_dCv = dCvDot_dCv/homogenization_Ngrains(mappingHomogenization(2,ip,el))
|
|
||||||
|
|
||||||
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,63 +0,0 @@
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! $Id$
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @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()
|
|
||||||
use, intrinsic :: iso_fortran_env ! to get compiler_version and compiler_options (at least for gfortran 4.6 at the moment)
|
|
||||||
use prec, only: &
|
|
||||||
pReal, &
|
|
||||||
pInt
|
|
||||||
use IO, only: &
|
|
||||||
IO_timeStamp
|
|
||||||
use material
|
|
||||||
use numerics, only: &
|
|
||||||
worldrank
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
integer(pInt) :: &
|
|
||||||
homog, &
|
|
||||||
NofMyHomog
|
|
||||||
|
|
||||||
mainProcess: if (worldrank == 0) then
|
|
||||||
write(6,'(/,a)') ' <<<+- vacancyflux_'//VACANCYFLUX_isoconc_label//' init -+>>>'
|
|
||||||
write(6,'(a15,a)') ' Current time: ',IO_timeStamp()
|
|
||||||
#include "compilation_info.f90"
|
|
||||||
endif mainProcess
|
|
||||||
|
|
||||||
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