Merge branch '30_parsePhasePartOnce' into 20-NewStyleDislotwin
This commit is contained in:
commit
158e6fd601
|
@ -561,7 +561,7 @@ function IO_hybridIA(Nast,ODFfileName)
|
||||||
IO_hybridIA = 0.0_pReal ! initialize return value for case of error
|
IO_hybridIA = 0.0_pReal ! initialize return value for case of error
|
||||||
write(6,'(/,a,/)',advance='no') ' Using linear ODF file: '//trim(ODFfileName)
|
write(6,'(/,a,/)',advance='no') ' Using linear ODF file: '//trim(ODFfileName)
|
||||||
write(6,'(/,a)') ' Eisenlohr et al., Computational Materials Science, 42(4):670–678, 2008'
|
write(6,'(/,a)') ' Eisenlohr et al., Computational Materials Science, 42(4):670–678, 2008'
|
||||||
write(6,'(/,a)') 'https://doi.org/10.1016/j.commatsci.2007.09.015'
|
write(6,'(a)') ' https://doi.org/10.1016/j.commatsci.2007.09.015'
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
|
|
210
src/config.f90
210
src/config.f90
|
@ -24,6 +24,7 @@ module config
|
||||||
contains
|
contains
|
||||||
procedure :: add => add
|
procedure :: add => add
|
||||||
procedure :: show => show
|
procedure :: show => show
|
||||||
|
procedure :: free => free
|
||||||
|
|
||||||
procedure :: keyExists => keyExists
|
procedure :: keyExists => keyExists
|
||||||
procedure :: countKeys => countKeys
|
procedure :: countKeys => countKeys
|
||||||
|
@ -40,12 +41,12 @@ module config
|
||||||
|
|
||||||
type(tPartitionedStringList), public :: emptyList
|
type(tPartitionedStringList), public :: emptyList
|
||||||
|
|
||||||
type(tPartitionedStringList), public, protected, allocatable, dimension(:) :: &
|
type(tPartitionedStringList), public, protected, allocatable, dimension(:) :: & ! QUESTION: rename to config_XXX?
|
||||||
phaseConfig, &
|
config_phase, &
|
||||||
microstructureConfig, &
|
config_microstructure, &
|
||||||
homogenizationConfig, &
|
config_homogenization, &
|
||||||
textureConfig, &
|
config_texture, &
|
||||||
crystalliteConfig
|
config_crystallite
|
||||||
|
|
||||||
character(len=64), dimension(:), allocatable, public, protected :: &
|
character(len=64), dimension(:), allocatable, public, protected :: &
|
||||||
phase_name, & !< name of each phase
|
phase_name, & !< name of each phase
|
||||||
|
@ -59,12 +60,12 @@ module config
|
||||||
MATERIAL_partHomogenization = 'homogenization', & !< keyword for homogenization part
|
MATERIAL_partHomogenization = 'homogenization', & !< keyword for homogenization part
|
||||||
MATERIAL_partCrystallite = 'crystallite', & !< keyword for crystallite part
|
MATERIAL_partCrystallite = 'crystallite', & !< keyword for crystallite part
|
||||||
MATERIAL_partPhase = 'phase', & !< keyword for phase part
|
MATERIAL_partPhase = 'phase', & !< keyword for phase part
|
||||||
MATERIAL_partMicrostructure = 'microstructure', & !< keyword for microstructure part
|
MATERIAL_partMicrostructure = 'microstructure' !< keyword for microstructure part
|
||||||
|
character(len=*), parameter, private :: &
|
||||||
MATERIAL_partTexture = 'texture' !< keyword for texture part
|
MATERIAL_partTexture = 'texture' !< keyword for texture part
|
||||||
|
|
||||||
! ToDo: Remove, use size(phaseConfig) etc
|
! ToDo: Remove, use size(config_phase) etc
|
||||||
integer(pInt), public, protected :: &
|
integer(pInt), public, protected :: &
|
||||||
material_Ntexture, & !< number of textures
|
|
||||||
material_Nphase, & !< number of phases
|
material_Nphase, & !< number of phases
|
||||||
material_Nhomogenization, & !< number of homogenizations
|
material_Nhomogenization, & !< number of homogenizations
|
||||||
material_Nmicrostructure, & !< number of microstructures
|
material_Nmicrostructure, & !< number of microstructures
|
||||||
|
@ -76,10 +77,15 @@ module config
|
||||||
MATERIAL_localFileExt = 'materialConfig' !< extension of solver job name depending material configuration file
|
MATERIAL_localFileExt = 'materialConfig' !< extension of solver job name depending material configuration file
|
||||||
|
|
||||||
|
|
||||||
public :: config_init
|
public :: &
|
||||||
|
config_init, &
|
||||||
|
config_deallocate
|
||||||
|
|
||||||
contains
|
contains
|
||||||
|
|
||||||
|
!--------------------------------------------------------------------------------------------------
|
||||||
|
!> @brief reads material.config and stores its content per part
|
||||||
|
!--------------------------------------------------------------------------------------------------
|
||||||
subroutine config_init()
|
subroutine config_init()
|
||||||
#if defined(__GFORTRAN__) || __INTEL_COMPILER >= 1800
|
#if defined(__GFORTRAN__) || __INTEL_COMPILER >= 1800
|
||||||
use, intrinsic :: iso_fortran_env, only: &
|
use, intrinsic :: iso_fortran_env, only: &
|
||||||
|
@ -108,13 +114,12 @@ subroutine config_init()
|
||||||
line, &
|
line, &
|
||||||
part
|
part
|
||||||
|
|
||||||
|
write(6,'(/,a)') ' <<<+- config init -+>>>'
|
||||||
myDebug = debug_level(debug_material)
|
|
||||||
|
|
||||||
write(6,'(/,a)') ' <<<+- material init -+>>>'
|
|
||||||
write(6,'(a15,a)') ' Current time: ',IO_timeStamp()
|
write(6,'(a15,a)') ' Current time: ',IO_timeStamp()
|
||||||
#include "compilation_info.f90"
|
#include "compilation_info.f90"
|
||||||
|
|
||||||
|
myDebug = debug_level(debug_material)
|
||||||
|
|
||||||
if (.not. IO_open_jobFile_stat(FILEUNIT,material_localFileExt)) & ! no local material configuration present...
|
if (.not. IO_open_jobFile_stat(FILEUNIT,material_localFileExt)) & ! no local material configuration present...
|
||||||
call IO_open_file(FILEUNIT,material_configFile) ! ...open material.config file
|
call IO_open_file(FILEUNIT,material_configFile) ! ...open material.config file
|
||||||
|
|
||||||
|
@ -126,23 +131,23 @@ subroutine config_init()
|
||||||
select case (trim(part))
|
select case (trim(part))
|
||||||
|
|
||||||
case (trim(material_partPhase))
|
case (trim(material_partPhase))
|
||||||
call parseFile(line,phase_name,phaseConfig,FILEUNIT)
|
call parseFile(line,phase_name,config_phase,FILEUNIT)
|
||||||
if (iand(myDebug,debug_levelBasic) /= 0_pInt) write(6,'(a)') ' Phase parsed'; flush(6)
|
if (iand(myDebug,debug_levelBasic) /= 0_pInt) write(6,'(a)') ' Phase parsed'; flush(6)
|
||||||
|
|
||||||
case (trim(material_partMicrostructure))
|
case (trim(material_partMicrostructure))
|
||||||
call parseFile(line,microstructure_name,microstructureConfig,FILEUNIT)
|
call parseFile(line,microstructure_name,config_microstructure,FILEUNIT)
|
||||||
if (iand(myDebug,debug_levelBasic) /= 0_pInt) write(6,'(a)') ' Microstructure parsed'; flush(6)
|
if (iand(myDebug,debug_levelBasic) /= 0_pInt) write(6,'(a)') ' Microstructure parsed'; flush(6)
|
||||||
|
|
||||||
case (trim(material_partCrystallite))
|
case (trim(material_partCrystallite))
|
||||||
call parseFile(line,crystallite_name,crystalliteConfig,FILEUNIT)
|
call parseFile(line,crystallite_name,config_crystallite,FILEUNIT)
|
||||||
if (iand(myDebug,debug_levelBasic) /= 0_pInt) write(6,'(a)') ' Crystallite parsed'; flush(6)
|
if (iand(myDebug,debug_levelBasic) /= 0_pInt) write(6,'(a)') ' Crystallite parsed'; flush(6)
|
||||||
|
|
||||||
case (trim(material_partHomogenization))
|
case (trim(material_partHomogenization))
|
||||||
call parseFile(line,homogenization_name,homogenizationConfig,FILEUNIT)
|
call parseFile(line,homogenization_name,config_homogenization,FILEUNIT)
|
||||||
if (iand(myDebug,debug_levelBasic) /= 0_pInt) write(6,'(a)') ' Homogenization parsed'; flush(6)
|
if (iand(myDebug,debug_levelBasic) /= 0_pInt) write(6,'(a)') ' Homogenization parsed'; flush(6)
|
||||||
|
|
||||||
case (trim(material_partTexture))
|
case (trim(material_partTexture))
|
||||||
call parseFile(line,texture_name,textureConfig,FILEUNIT)
|
call parseFile(line,texture_name,config_texture,FILEUNIT)
|
||||||
if (iand(myDebug,debug_levelBasic) /= 0_pInt) write(6,'(a)') ' Texture parsed'; flush(6)
|
if (iand(myDebug,debug_levelBasic) /= 0_pInt) write(6,'(a)') ' Texture parsed'; flush(6)
|
||||||
|
|
||||||
case default
|
case default
|
||||||
|
@ -152,22 +157,21 @@ subroutine config_init()
|
||||||
|
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
material_Nhomogenization = size(homogenizationConfig)
|
material_Nhomogenization = size(config_homogenization)
|
||||||
if (material_Nhomogenization < 1_pInt) call IO_error(160_pInt,ext_msg=material_partHomogenization)
|
if (material_Nhomogenization < 1_pInt) call IO_error(160_pInt,ext_msg=material_partHomogenization)
|
||||||
material_Nmicrostructure = size(microstructureConfig)
|
material_Nmicrostructure = size(config_microstructure)
|
||||||
if (material_Nmicrostructure < 1_pInt) call IO_error(160_pInt,ext_msg=material_partMicrostructure)
|
if (material_Nmicrostructure < 1_pInt) call IO_error(160_pInt,ext_msg=material_partMicrostructure)
|
||||||
material_Ncrystallite = size(crystalliteConfig)
|
material_Ncrystallite = size(config_crystallite)
|
||||||
if (material_Ncrystallite < 1_pInt) call IO_error(160_pInt,ext_msg=material_partCrystallite)
|
if (material_Ncrystallite < 1_pInt) call IO_error(160_pInt,ext_msg=material_partCrystallite)
|
||||||
material_Nphase = size(phaseConfig)
|
material_Nphase = size(config_phase)
|
||||||
if (material_Nphase < 1_pInt) call IO_error(160_pInt,ext_msg=material_partPhase)
|
if (material_Nphase < 1_pInt) call IO_error(160_pInt,ext_msg=material_partPhase)
|
||||||
material_Ntexture = size(textureConfig)
|
if (size(config_texture) < 1_pInt) call IO_error(160_pInt,ext_msg=material_partTexture)
|
||||||
if (material_Ntexture < 1_pInt) call IO_error(160_pInt,ext_msg=material_partTexture)
|
|
||||||
|
|
||||||
|
|
||||||
end subroutine config_init
|
end subroutine config_init
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief parses the homogenization part in the material configuration file
|
!> @brief parses the material.config file
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
subroutine parseFile(line,&
|
subroutine parseFile(line,&
|
||||||
sectionNames,part,fileUnit)
|
sectionNames,part,fileUnit)
|
||||||
|
@ -201,7 +205,7 @@ subroutine parseFile(line,&
|
||||||
line = IO_read(fileUnit)
|
line = IO_read(fileUnit)
|
||||||
if (IO_isBlank(line)) cycle ! skip empty lines
|
if (IO_isBlank(line)) cycle ! skip empty lines
|
||||||
foundNextPart: if (IO_getTag(line,'<','>') /= '') then
|
foundNextPart: if (IO_getTag(line,'<','>') /= '') then
|
||||||
devNull = IO_read(fileUnit, .true.) ! reset IO_read
|
devNull = IO_read(fileUnit, .true.) ! reset IO_read to close any recursively included files
|
||||||
exit
|
exit
|
||||||
endif foundNextPart
|
endif foundNextPart
|
||||||
nextSection: if (IO_getTag(line,'[',']') /= '') then
|
nextSection: if (IO_getTag(line,'[',']') /= '') then
|
||||||
|
@ -213,6 +217,7 @@ subroutine parseFile(line,&
|
||||||
else GfortranBug86033
|
else GfortranBug86033
|
||||||
sectionNames = [sectionNames,tag]
|
sectionNames = [sectionNames,tag]
|
||||||
endif GfortranBug86033
|
endif GfortranBug86033
|
||||||
|
cycle
|
||||||
endif nextSection
|
endif nextSection
|
||||||
chunkPos = IO_stringPos(line)
|
chunkPos = IO_stringPos(line)
|
||||||
tag = IO_lc(IO_stringValue(trim(line),chunkPos,1_pInt)) ! extract key
|
tag = IO_lc(IO_stringValue(trim(line),chunkPos,1_pInt)) ! extract key
|
||||||
|
@ -228,8 +233,57 @@ subroutine parseFile(line,&
|
||||||
call part(s)%show()
|
call part(s)%show()
|
||||||
end do
|
end do
|
||||||
end if
|
end if
|
||||||
|
|
||||||
end subroutine parseFile
|
end subroutine parseFile
|
||||||
|
|
||||||
|
subroutine config_deallocate(what)
|
||||||
|
use IO, only: &
|
||||||
|
IO_error
|
||||||
|
|
||||||
|
implicit none
|
||||||
|
character(len=*), intent(in) :: what
|
||||||
|
integer(pInt) :: i
|
||||||
|
|
||||||
|
select case(what)
|
||||||
|
|
||||||
|
case('material.config/phase')
|
||||||
|
do i=1, size(config_phase)
|
||||||
|
call config_phase(i)%free
|
||||||
|
enddo
|
||||||
|
deallocate(config_phase)
|
||||||
|
|
||||||
|
case('material.config/microstructure')
|
||||||
|
do i=1, size(config_microstructure)
|
||||||
|
call config_microstructure(i)%free
|
||||||
|
enddo
|
||||||
|
deallocate(config_microstructure)
|
||||||
|
|
||||||
|
case('material.config/crystallite')
|
||||||
|
do i=1, size(config_crystallite)
|
||||||
|
call config_crystallite(i)%free
|
||||||
|
enddo
|
||||||
|
deallocate(config_crystallite)
|
||||||
|
|
||||||
|
case('material.config/homogenization')
|
||||||
|
do i=1, size(config_homogenization)
|
||||||
|
call config_homogenization(i)%free
|
||||||
|
enddo
|
||||||
|
deallocate(config_homogenization)
|
||||||
|
|
||||||
|
case('material.config/texture')
|
||||||
|
do i=1, size(config_texture)
|
||||||
|
call config_texture(i)%free
|
||||||
|
enddo
|
||||||
|
deallocate(config_texture)
|
||||||
|
|
||||||
|
case default
|
||||||
|
call IO_error(0_pInt,ext_msg='config_deallocate')
|
||||||
|
|
||||||
|
end select
|
||||||
|
|
||||||
|
end subroutine config_deallocate
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief add element
|
!> @brief add element
|
||||||
!> @details Adds a string together with the start/end position of chunks in this string. The new
|
!> @details Adds a string together with the start/end position of chunks in this string. The new
|
||||||
|
@ -282,23 +336,26 @@ end subroutine show
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief deallocates all elements of a given list
|
!> @brief cleans entire list
|
||||||
!> @details Strings are printed in order of insertion (FIFO)
|
!> @details list head is remains alive
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! subroutine free_all()
|
subroutine free(this)
|
||||||
! implicit none
|
|
||||||
!
|
implicit none
|
||||||
! type(node), pointer :: item
|
class(tPartitionedStringList), target, intent(in) :: this
|
||||||
!
|
type(tPartitionedStringList), pointer :: new, item
|
||||||
! do
|
|
||||||
! item => first
|
if (.not. associated(this%next)) return
|
||||||
!
|
|
||||||
! if (associated(item) .eqv. .FALSE.) exit
|
item => this%next
|
||||||
!
|
do while (associated(item%next))
|
||||||
! first => first%next
|
new => item
|
||||||
! deallocate(item)
|
deallocate(item)
|
||||||
! end do
|
item => new%next
|
||||||
! end subroutine free_all
|
enddo
|
||||||
|
deallocate(item)
|
||||||
|
|
||||||
|
end subroutine free
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
|
@ -368,8 +425,8 @@ real(pReal) function getFloat(this,key,defaultVal)
|
||||||
type(tPartitionedStringList), pointer :: item
|
type(tPartitionedStringList), pointer :: item
|
||||||
logical :: found
|
logical :: found
|
||||||
|
|
||||||
if (present(defaultVal)) getFloat = defaultVal
|
|
||||||
found = present(defaultVal)
|
found = present(defaultVal)
|
||||||
|
if (found) getFloat = defaultVal
|
||||||
|
|
||||||
item => this%next
|
item => this%next
|
||||||
do while (associated(item))
|
do while (associated(item))
|
||||||
|
@ -404,8 +461,8 @@ integer(pInt) function getInt(this,key,defaultVal)
|
||||||
type(tPartitionedStringList), pointer :: item
|
type(tPartitionedStringList), pointer :: item
|
||||||
logical :: found
|
logical :: found
|
||||||
|
|
||||||
if (present(defaultVal)) getInt = defaultVal
|
|
||||||
found = present(defaultVal)
|
found = present(defaultVal)
|
||||||
|
if (found) getInt = defaultVal
|
||||||
|
|
||||||
item => this%next
|
item => this%next
|
||||||
do while (associated(item))
|
do while (associated(item))
|
||||||
|
@ -440,11 +497,14 @@ character(len=65536) function getString(this,key,defaultVal,raw)
|
||||||
logical, intent(in), optional :: raw
|
logical, intent(in), optional :: raw
|
||||||
type(tPartitionedStringList), pointer :: item
|
type(tPartitionedStringList), pointer :: item
|
||||||
logical :: found, &
|
logical :: found, &
|
||||||
split
|
whole
|
||||||
|
|
||||||
if (present(defaultVal)) getString = defaultVal
|
whole = merge(raw,.false.,present(raw)) ! whole string or white space splitting
|
||||||
split = merge(.not. raw,.true.,present(raw))
|
|
||||||
found = present(defaultVal)
|
found = present(defaultVal)
|
||||||
|
if (found) then
|
||||||
|
getString = trim(defaultVal)
|
||||||
|
if (len_trim(getString) /= len_trim(defaultVal)) call IO_error(0_pInt,ext_msg='getString')
|
||||||
|
endif
|
||||||
|
|
||||||
item => this%next
|
item => this%next
|
||||||
do while (associated(item))
|
do while (associated(item))
|
||||||
|
@ -452,10 +512,10 @@ character(len=65536) function getString(this,key,defaultVal,raw)
|
||||||
found = .true.
|
found = .true.
|
||||||
if (item%string%pos(1) < 2_pInt) call IO_error(143_pInt,ext_msg=key)
|
if (item%string%pos(1) < 2_pInt) call IO_error(143_pInt,ext_msg=key)
|
||||||
|
|
||||||
if (split) then
|
if (whole) then
|
||||||
getString = IO_StringValue(item%string%val,item%string%pos,2)
|
|
||||||
else
|
|
||||||
getString = trim(item%string%val(item%string%pos(4):)) ! raw string starting a second chunk
|
getString = trim(item%string%val(item%string%pos(4):)) ! raw string starting a second chunk
|
||||||
|
else
|
||||||
|
getString = IO_StringValue(item%string%val,item%string%pos,2)
|
||||||
endif
|
endif
|
||||||
endif
|
endif
|
||||||
item => item%next
|
item => item%next
|
||||||
|
@ -496,10 +556,7 @@ function getFloats(this,key,defaultVal)
|
||||||
do while (associated(item))
|
do while (associated(item))
|
||||||
if (trim(IO_stringValue(item%string%val,item%string%pos,1)) == trim(key)) then
|
if (trim(IO_stringValue(item%string%val,item%string%pos,1)) == trim(key)) then
|
||||||
found = .true.
|
found = .true.
|
||||||
if (.not. cumulative) then
|
if (.not. cumulative) getFloats = [real(pReal)::]
|
||||||
deallocate(getFloats) ! use here rhs allocation with empty list
|
|
||||||
allocate(getFloats(0))
|
|
||||||
endif
|
|
||||||
if (item%string%pos(1) < 2_pInt) call IO_error(143_pInt,ext_msg=key)
|
if (item%string%pos(1) < 2_pInt) call IO_error(143_pInt,ext_msg=key)
|
||||||
do i = 2_pInt, item%string%pos(1)
|
do i = 2_pInt, item%string%pos(1)
|
||||||
getFloats = [getFloats,IO_FloatValue(item%string%val,item%string%pos,i)]
|
getFloats = [getFloats,IO_FloatValue(item%string%val,item%string%pos,i)]
|
||||||
|
@ -508,11 +565,9 @@ function getFloats(this,key,defaultVal)
|
||||||
item => item%next
|
item => item%next
|
||||||
end do
|
end do
|
||||||
|
|
||||||
if (present(defaultVal) .and. .not. found) then
|
if (.not. found) then
|
||||||
getFloats = defaultVal
|
if (present(defaultVal)) then; getFloats = defaultVal; else; call IO_error(140_pInt,ext_msg=key); endif
|
||||||
found = .true.
|
|
||||||
endif
|
endif
|
||||||
if (.not. found) call IO_error(140_pInt,ext_msg=key)
|
|
||||||
|
|
||||||
end function getFloats
|
end function getFloats
|
||||||
|
|
||||||
|
@ -547,10 +602,7 @@ function getInts(this,key,defaultVal)
|
||||||
do while (associated(item))
|
do while (associated(item))
|
||||||
if (trim(IO_stringValue(item%string%val,item%string%pos,1)) == trim(key)) then
|
if (trim(IO_stringValue(item%string%val,item%string%pos,1)) == trim(key)) then
|
||||||
found = .true.
|
found = .true.
|
||||||
if (.not. cumulative) then
|
if (.not. cumulative) getInts = [integer(pInt)::]
|
||||||
deallocate(getInts) ! use here rhs allocation with empty list
|
|
||||||
allocate(getInts(0))
|
|
||||||
endif
|
|
||||||
if (item%string%pos(1) < 2_pInt) call IO_error(143_pInt,ext_msg=key)
|
if (item%string%pos(1) < 2_pInt) call IO_error(143_pInt,ext_msg=key)
|
||||||
do i = 2_pInt, item%string%pos(1)
|
do i = 2_pInt, item%string%pos(1)
|
||||||
getInts = [getInts,IO_IntValue(item%string%val,item%string%pos,i)]
|
getInts = [getInts,IO_IntValue(item%string%val,item%string%pos,i)]
|
||||||
|
@ -559,11 +611,9 @@ function getInts(this,key,defaultVal)
|
||||||
item => item%next
|
item => item%next
|
||||||
end do
|
end do
|
||||||
|
|
||||||
if (present(defaultVal) .and. .not. found) then
|
if (.not. found) then
|
||||||
getInts = defaultVal
|
if (present(defaultVal)) then; getInts = defaultVal; else; call IO_error(140_pInt,ext_msg=key); endif
|
||||||
found = .true.
|
|
||||||
endif
|
endif
|
||||||
if (.not. found) call IO_error(140_pInt,ext_msg=key)
|
|
||||||
|
|
||||||
end function getInts
|
end function getInts
|
||||||
|
|
||||||
|
@ -589,11 +639,11 @@ function getStrings(this,key,defaultVal,raw)
|
||||||
character(len=65536) :: str
|
character(len=65536) :: str
|
||||||
integer(pInt) :: i
|
integer(pInt) :: i
|
||||||
logical :: found, &
|
logical :: found, &
|
||||||
split, &
|
whole, &
|
||||||
cumulative
|
cumulative
|
||||||
|
|
||||||
cumulative = (key(1:1) == '(' .and. key(len_trim(key):len_trim(key)) == ')')
|
cumulative = (key(1:1) == '(' .and. key(len_trim(key):len_trim(key)) == ')')
|
||||||
split = merge(.not. raw,.true.,present(raw))
|
whole = merge(raw,.false.,present(raw))
|
||||||
found = .false.
|
found = .false.
|
||||||
|
|
||||||
item => this%next
|
item => this%next
|
||||||
|
@ -604,36 +654,34 @@ function getStrings(this,key,defaultVal,raw)
|
||||||
if (item%string%pos(1) < 2_pInt) call IO_error(143_pInt,ext_msg=key)
|
if (item%string%pos(1) < 2_pInt) call IO_error(143_pInt,ext_msg=key)
|
||||||
|
|
||||||
notAllocated: if (.not. allocated(getStrings)) then
|
notAllocated: if (.not. allocated(getStrings)) then
|
||||||
if (split) then
|
if (whole) then
|
||||||
|
str = item%string%val(item%string%pos(4):)
|
||||||
|
getStrings = [str]
|
||||||
|
else
|
||||||
str = IO_StringValue(item%string%val,item%string%pos,2_pInt)
|
str = IO_StringValue(item%string%val,item%string%pos,2_pInt)
|
||||||
allocate(getStrings(1),source=str)
|
allocate(getStrings(1),source=str)
|
||||||
do i=3_pInt,item%string%pos(1)
|
do i=3_pInt,item%string%pos(1)
|
||||||
str = IO_StringValue(item%string%val,item%string%pos,i)
|
str = IO_StringValue(item%string%val,item%string%pos,i)
|
||||||
getStrings = [getStrings,str]
|
getStrings = [getStrings,str]
|
||||||
enddo
|
enddo
|
||||||
else
|
|
||||||
str = item%string%val(item%string%pos(4):)
|
|
||||||
getStrings = [str]
|
|
||||||
endif
|
endif
|
||||||
else notAllocated
|
else notAllocated
|
||||||
if (split) then
|
if (whole) then
|
||||||
|
getStrings = [getStrings,str]
|
||||||
|
else
|
||||||
do i=2_pInt,item%string%pos(1)
|
do i=2_pInt,item%string%pos(1)
|
||||||
str = IO_StringValue(item%string%val,item%string%pos,i)
|
str = IO_StringValue(item%string%val,item%string%pos,i)
|
||||||
getStrings = [getStrings,str]
|
getStrings = [getStrings,str]
|
||||||
enddo
|
enddo
|
||||||
else
|
|
||||||
getStrings = [getStrings,str]
|
|
||||||
endif
|
endif
|
||||||
endif notAllocated
|
endif notAllocated
|
||||||
endif
|
endif
|
||||||
item => item%next
|
item => item%next
|
||||||
end do
|
end do
|
||||||
|
|
||||||
if (present(defaultVal) .and. .not. found) then
|
if (.not. found) then
|
||||||
getStrings = defaultVal
|
if (present(defaultVal)) then; getStrings = defaultVal; else; call IO_error(140_pInt,ext_msg=key); endif
|
||||||
found = .true.
|
|
||||||
endif
|
endif
|
||||||
if (.not. found) call IO_error(140_pInt,ext_msg=key)
|
|
||||||
|
|
||||||
end function getStrings
|
end function getStrings
|
||||||
|
|
||||||
|
|
|
@ -57,6 +57,8 @@ subroutine constitutive_init()
|
||||||
IO_write_jobFile, &
|
IO_write_jobFile, &
|
||||||
IO_write_jobIntFile, &
|
IO_write_jobIntFile, &
|
||||||
IO_timeStamp
|
IO_timeStamp
|
||||||
|
use config, only: &
|
||||||
|
config_deallocate
|
||||||
use mesh, only: &
|
use mesh, only: &
|
||||||
FE_geomtype
|
FE_geomtype
|
||||||
use config, only: &
|
use config, only: &
|
||||||
|
@ -190,6 +192,8 @@ subroutine constitutive_init()
|
||||||
if (any(phase_kinematics == KINEMATICS_hydrogen_strain_ID)) call kinematics_hydrogen_strain_init(FILEUNIT)
|
if (any(phase_kinematics == KINEMATICS_hydrogen_strain_ID)) call kinematics_hydrogen_strain_init(FILEUNIT)
|
||||||
close(FILEUNIT)
|
close(FILEUNIT)
|
||||||
|
|
||||||
|
call config_deallocate('material.config/phase')
|
||||||
|
|
||||||
write(6,'(/,a)') ' <<<+- constitutive init -+>>>'
|
write(6,'(/,a)') ' <<<+- constitutive init -+>>>'
|
||||||
write(6,'(a15,a)') ' Current time: ',IO_timeStamp()
|
write(6,'(a15,a)') ' Current time: ',IO_timeStamp()
|
||||||
#include "compilation_info.f90"
|
#include "compilation_info.f90"
|
||||||
|
@ -336,30 +340,6 @@ subroutine constitutive_init()
|
||||||
enddo PhaseLoop2
|
enddo PhaseLoop2
|
||||||
|
|
||||||
|
|
||||||
#ifdef TODO
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! report
|
|
||||||
constitutive_maxSizeState = maxval(constitutive_sizeState)
|
|
||||||
constitutive_plasticity_maxSizeDotState = maxval(constitutive_sizeDotState)
|
|
||||||
|
|
||||||
if (iand(debug_level(debug_constitutive),debug_levelBasic) /= 0_pInt) then
|
|
||||||
write(6,'(a32,1x,7(i8,1x))') 'constitutive_state0: ', shape(constitutive_state0)
|
|
||||||
write(6,'(a32,1x,7(i8,1x))') 'constitutive_partionedState0: ', shape(constitutive_partionedState0)
|
|
||||||
write(6,'(a32,1x,7(i8,1x))') 'constitutive_subState0: ', shape(constitutive_subState0)
|
|
||||||
write(6,'(a32,1x,7(i8,1x))') 'constitutive_state: ', shape(constitutive_state)
|
|
||||||
write(6,'(a32,1x,7(i8,1x))') 'constitutive_aTolState: ', shape(constitutive_aTolState)
|
|
||||||
write(6,'(a32,1x,7(i8,1x))') 'constitutive_dotState: ', shape(constitutive_dotState)
|
|
||||||
write(6,'(a32,1x,7(i8,1x))') 'constitutive_deltaState: ', shape(constitutive_deltaState)
|
|
||||||
write(6,'(a32,1x,7(i8,1x))') 'constitutive_sizeState: ', shape(constitutive_sizeState)
|
|
||||||
write(6,'(a32,1x,7(i8,1x))') 'constitutive_sizeDotState: ', shape(constitutive_sizeDotState)
|
|
||||||
write(6,'(a32,1x,7(i8,1x),/)') 'constitutive_sizePostResults: ', shape(constitutive_sizePostResults)
|
|
||||||
write(6,'(a32,1x,7(i8,1x))') 'maxSizeState: ', constitutive_maxSizeState
|
|
||||||
write(6,'(a32,1x,7(i8,1x))') 'maxSizeDotState: ', constitutive_plasticity_maxSizeDotState
|
|
||||||
write(6,'(a32,1x,7(i8,1x))') 'maxSizePostResults: ', constitutive_plasticity_maxSizePostResults
|
|
||||||
endif
|
|
||||||
flush(6)
|
|
||||||
#endif
|
|
||||||
|
|
||||||
|
|
||||||
end subroutine constitutive_init
|
end subroutine constitutive_init
|
||||||
|
|
||||||
|
|
|
@ -171,7 +171,10 @@ subroutine crystallite_init
|
||||||
IO_write_jobFile, &
|
IO_write_jobFile, &
|
||||||
IO_error
|
IO_error
|
||||||
use material
|
use material
|
||||||
use config
|
use config, only: &
|
||||||
|
config_crystallite, &
|
||||||
|
crystallite_name, &
|
||||||
|
config_deallocate
|
||||||
use constitutive, only: &
|
use constitutive, only: &
|
||||||
constitutive_initialFi, &
|
constitutive_initialFi, &
|
||||||
constitutive_microstructure ! derived (shortcut) quantities of given state
|
constitutive_microstructure ! derived (shortcut) quantities of given state
|
||||||
|
@ -259,21 +262,21 @@ subroutine crystallite_init
|
||||||
allocate(crystallite_clearToCutback(iMax,eMax), source=.true.)
|
allocate(crystallite_clearToCutback(iMax,eMax), source=.true.)
|
||||||
allocate(crystallite_neighborEnforcedCutback(iMax,eMax), source=.false.)
|
allocate(crystallite_neighborEnforcedCutback(iMax,eMax), source=.false.)
|
||||||
allocate(crystallite_output(maxval(crystallite_Noutput), &
|
allocate(crystallite_output(maxval(crystallite_Noutput), &
|
||||||
material_Ncrystallite)) ; crystallite_output = ''
|
size(config_crystallite))) ; crystallite_output = ''
|
||||||
allocate(crystallite_outputID(maxval(crystallite_Noutput), &
|
allocate(crystallite_outputID(maxval(crystallite_Noutput), &
|
||||||
material_Ncrystallite), source=undefined_ID)
|
size(config_crystallite)), source=undefined_ID)
|
||||||
allocate(crystallite_sizePostResults(material_Ncrystallite),source=0_pInt)
|
allocate(crystallite_sizePostResults(size(config_crystallite)),source=0_pInt)
|
||||||
allocate(crystallite_sizePostResult(maxval(crystallite_Noutput), &
|
allocate(crystallite_sizePostResult(maxval(crystallite_Noutput), &
|
||||||
material_Ncrystallite), source=0_pInt)
|
size(config_crystallite)), source=0_pInt)
|
||||||
|
|
||||||
|
|
||||||
do c = 1_pInt, material_Ncrystallite
|
do c = 1_pInt, size(config_crystallite)
|
||||||
#if defined(__GFORTRAN__)
|
#if defined(__GFORTRAN__)
|
||||||
str = ['GfortranBug86277']
|
str = ['GfortranBug86277']
|
||||||
str = crystalliteConfig(c)%getStrings('(output)',defaultVal=str)
|
str = config_crystallite(c)%getStrings('(output)',defaultVal=str)
|
||||||
if (str(1) == 'GfortranBug86277') str = [character(len=65536)::]
|
if (str(1) == 'GfortranBug86277') str = [character(len=65536)::]
|
||||||
#else
|
#else
|
||||||
str = crystalliteConfig(c)%getStrings('(output)',defaultVal=[character(len=65536)::])
|
str = config_crystallite(c)%getStrings('(output)',defaultVal=[character(len=65536)::])
|
||||||
#endif
|
#endif
|
||||||
do o = 1_pInt, size(str)
|
do o = 1_pInt, size(str)
|
||||||
crystallite_output(o,c) = str(o)
|
crystallite_output(o,c) = str(o)
|
||||||
|
@ -329,7 +332,7 @@ subroutine crystallite_init
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
|
|
||||||
do r = 1_pInt,material_Ncrystallite
|
do r = 1_pInt,size(config_crystallite)
|
||||||
do o = 1_pInt,crystallite_Noutput(r)
|
do o = 1_pInt,crystallite_Noutput(r)
|
||||||
select case(crystallite_outputID(o,r))
|
select case(crystallite_outputID(o,r))
|
||||||
case(phase_ID,texture_ID,volume_ID,grainrotationx_ID,grainrotationy_ID,grainrotationz_ID)
|
case(phase_ID,texture_ID,volume_ID,grainrotationx_ID,grainrotationy_ID,grainrotationz_ID)
|
||||||
|
@ -361,7 +364,7 @@ subroutine crystallite_init
|
||||||
if (worldrank == 0_pInt) then
|
if (worldrank == 0_pInt) then
|
||||||
call IO_write_jobFile(FILEUNIT,'outputCrystallite')
|
call IO_write_jobFile(FILEUNIT,'outputCrystallite')
|
||||||
|
|
||||||
do r = 1_pInt,material_Ncrystallite
|
do r = 1_pInt,size(config_crystallite)
|
||||||
if (any(microstructure_crystallite(mesh_element(4,:)) == r)) then
|
if (any(microstructure_crystallite(mesh_element(4,:)) == r)) then
|
||||||
write(FILEUNIT,'(/,a,/)') '['//trim(crystallite_name(r))//']'
|
write(FILEUNIT,'(/,a,/)') '['//trim(crystallite_name(r))//']'
|
||||||
do o = 1_pInt,crystallite_Noutput(r)
|
do o = 1_pInt,crystallite_Noutput(r)
|
||||||
|
@ -373,6 +376,8 @@ subroutine crystallite_init
|
||||||
close(FILEUNIT)
|
close(FILEUNIT)
|
||||||
endif
|
endif
|
||||||
|
|
||||||
|
call config_deallocate('material.config/crystallite')
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! initialize
|
! initialize
|
||||||
!$OMP PARALLEL DO PRIVATE(myNcomponents)
|
!$OMP PARALLEL DO PRIVATE(myNcomponents)
|
||||||
|
|
|
@ -100,8 +100,13 @@ subroutine homogenization_init
|
||||||
use crystallite, only: &
|
use crystallite, only: &
|
||||||
crystallite_maxSizePostResults
|
crystallite_maxSizePostResults
|
||||||
#endif
|
#endif
|
||||||
|
use config, only: &
|
||||||
|
config_deallocate, &
|
||||||
|
material_configFile, &
|
||||||
|
material_localFileExt, &
|
||||||
|
config_homogenization, &
|
||||||
|
homogenization_name
|
||||||
use material
|
use material
|
||||||
use config
|
|
||||||
use homogenization_none
|
use homogenization_none
|
||||||
use homogenization_isostrain
|
use homogenization_isostrain
|
||||||
use homogenization_RGC
|
use homogenization_RGC
|
||||||
|
@ -197,7 +202,7 @@ subroutine homogenization_init
|
||||||
! write description file for homogenization output
|
! write description file for homogenization output
|
||||||
mainProcess2: if (worldrank == 0) then
|
mainProcess2: if (worldrank == 0) then
|
||||||
call IO_write_jobFile(FILEUNIT,'outputHomogenization')
|
call IO_write_jobFile(FILEUNIT,'outputHomogenization')
|
||||||
do p = 1,material_Nhomogenization
|
do p = 1,size(config_homogenization)
|
||||||
if (any(material_homog == p)) then
|
if (any(material_homog == p)) then
|
||||||
i = homogenization_typeInstance(p) ! which instance of this homogenization type
|
i = homogenization_typeInstance(p) ! which instance of this homogenization type
|
||||||
valid = .true. ! assume valid
|
valid = .true. ! assume valid
|
||||||
|
@ -370,6 +375,8 @@ subroutine homogenization_init
|
||||||
close(FILEUNIT)
|
close(FILEUNIT)
|
||||||
endif mainProcess2
|
endif mainProcess2
|
||||||
|
|
||||||
|
call config_deallocate('material.config/homogenization')
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! allocate and initialize global variables
|
! allocate and initialize global variables
|
||||||
allocate(materialpoint_dPdF(3,3,3,3,mesh_maxNips,mesh_NcpElems), source=0.0_pReal)
|
allocate(materialpoint_dPdF(3,3,3,3,mesh_maxNips,mesh_NcpElems), source=0.0_pReal)
|
||||||
|
@ -395,7 +402,7 @@ subroutine homogenization_init
|
||||||
vacancyflux_maxSizePostResults = 0_pInt
|
vacancyflux_maxSizePostResults = 0_pInt
|
||||||
porosity_maxSizePostResults = 0_pInt
|
porosity_maxSizePostResults = 0_pInt
|
||||||
hydrogenflux_maxSizePostResults = 0_pInt
|
hydrogenflux_maxSizePostResults = 0_pInt
|
||||||
do p = 1,material_Nhomogenization
|
do p = 1,size(config_homogenization)
|
||||||
homogenization_maxSizePostResults = max(homogenization_maxSizePostResults,homogState (p)%sizePostResults)
|
homogenization_maxSizePostResults = max(homogenization_maxSizePostResults,homogState (p)%sizePostResults)
|
||||||
thermal_maxSizePostResults = max(thermal_maxSizePostResults, thermalState (p)%sizePostResults)
|
thermal_maxSizePostResults = max(thermal_maxSizePostResults, thermalState (p)%sizePostResults)
|
||||||
damage_maxSizePostResults = max(damage_maxSizePostResults ,damageState (p)%sizePostResults)
|
damage_maxSizePostResults = max(damage_maxSizePostResults ,damageState (p)%sizePostResults)
|
||||||
|
|
342
src/material.f90
342
src/material.f90
|
@ -1,13 +1,13 @@
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @author Franz Roters, Max-Planck-Institut für Eisenforschung GmbH
|
!> @author Franz Roters, Max-Planck-Institut für Eisenforschung GmbH
|
||||||
!> @author Philip Eisenlohr, 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 Parses material config file, either solverJobName.materialConfig or material.config
|
!> @brief Parses material config file, either solverJobName.materialConfig or material.config
|
||||||
!> @details reads the material configuration file, where solverJobName.materialConfig takes
|
!> @details reads the material configuration file, where solverJobName.materialConfig takes
|
||||||
!! precedence over material.config and parses the sections 'homogenization', 'crystallite',
|
!! precedence over material.config and parses the sections 'homogenization', 'crystallite',
|
||||||
!! 'phase', 'texture', and 'microstucture'
|
!! 'phase', 'texture', and 'microstucture'
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
module material
|
module material
|
||||||
use config
|
|
||||||
use prec, only: &
|
use prec, only: &
|
||||||
pReal, &
|
pReal, &
|
||||||
pInt, &
|
pInt, &
|
||||||
|
@ -351,6 +351,17 @@ subroutine material_init()
|
||||||
debug_material, &
|
debug_material, &
|
||||||
debug_levelBasic, &
|
debug_levelBasic, &
|
||||||
debug_levelExtensive
|
debug_levelExtensive
|
||||||
|
use config, only: &
|
||||||
|
config_crystallite, &
|
||||||
|
config_homogenization, &
|
||||||
|
config_microstructure, &
|
||||||
|
config_phase, &
|
||||||
|
config_texture, &
|
||||||
|
homogenization_name, &
|
||||||
|
microstructure_name, &
|
||||||
|
phase_name, &
|
||||||
|
texture_name, &
|
||||||
|
config_deallocate
|
||||||
use mesh, only: &
|
use mesh, only: &
|
||||||
mesh_maxNips, &
|
mesh_maxNips, &
|
||||||
mesh_NcpElems, &
|
mesh_NcpElems, &
|
||||||
|
@ -391,44 +402,44 @@ subroutine material_init()
|
||||||
call material_parseTexture()
|
call material_parseTexture()
|
||||||
if (iand(myDebug,debug_levelBasic) /= 0_pInt) write(6,'(a)') ' Texture parsed'; flush(6)
|
if (iand(myDebug,debug_levelBasic) /= 0_pInt) write(6,'(a)') ' Texture parsed'; flush(6)
|
||||||
|
|
||||||
allocate(plasticState (material_Nphase))
|
allocate(plasticState (size(config_phase)))
|
||||||
allocate(sourceState (material_Nphase))
|
allocate(sourceState (size(config_phase)))
|
||||||
do myPhase = 1,material_Nphase
|
do myPhase = 1,size(config_phase)
|
||||||
allocate(sourceState(myPhase)%p(phase_Nsources(myPhase)))
|
allocate(sourceState(myPhase)%p(phase_Nsources(myPhase)))
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
allocate(homogState (material_Nhomogenization))
|
allocate(homogState (size(config_homogenization)))
|
||||||
allocate(thermalState (material_Nhomogenization))
|
allocate(thermalState (size(config_homogenization)))
|
||||||
allocate(damageState (material_Nhomogenization))
|
allocate(damageState (size(config_homogenization)))
|
||||||
allocate(vacancyfluxState (material_Nhomogenization))
|
allocate(vacancyfluxState (size(config_homogenization)))
|
||||||
allocate(porosityState (material_Nhomogenization))
|
allocate(porosityState (size(config_homogenization)))
|
||||||
allocate(hydrogenfluxState (material_Nhomogenization))
|
allocate(hydrogenfluxState (size(config_homogenization)))
|
||||||
|
|
||||||
allocate(thermalMapping (material_Nhomogenization))
|
allocate(thermalMapping (size(config_homogenization)))
|
||||||
allocate(damageMapping (material_Nhomogenization))
|
allocate(damageMapping (size(config_homogenization)))
|
||||||
allocate(vacancyfluxMapping (material_Nhomogenization))
|
allocate(vacancyfluxMapping (size(config_homogenization)))
|
||||||
allocate(porosityMapping (material_Nhomogenization))
|
allocate(porosityMapping (size(config_homogenization)))
|
||||||
allocate(hydrogenfluxMapping(material_Nhomogenization))
|
allocate(hydrogenfluxMapping(size(config_homogenization)))
|
||||||
|
|
||||||
allocate(temperature (material_Nhomogenization))
|
allocate(temperature (size(config_homogenization)))
|
||||||
allocate(damage (material_Nhomogenization))
|
allocate(damage (size(config_homogenization)))
|
||||||
allocate(vacancyConc (material_Nhomogenization))
|
allocate(vacancyConc (size(config_homogenization)))
|
||||||
allocate(porosity (material_Nhomogenization))
|
allocate(porosity (size(config_homogenization)))
|
||||||
allocate(hydrogenConc (material_Nhomogenization))
|
allocate(hydrogenConc (size(config_homogenization)))
|
||||||
|
|
||||||
allocate(temperatureRate (material_Nhomogenization))
|
allocate(temperatureRate (size(config_homogenization)))
|
||||||
allocate(vacancyConcRate (material_Nhomogenization))
|
allocate(vacancyConcRate (size(config_homogenization)))
|
||||||
allocate(hydrogenConcRate (material_Nhomogenization))
|
allocate(hydrogenConcRate (size(config_homogenization)))
|
||||||
|
|
||||||
do m = 1_pInt,material_Nmicrostructure
|
do m = 1_pInt,size(config_microstructure)
|
||||||
if(microstructure_crystallite(m) < 1_pInt .or. &
|
if(microstructure_crystallite(m) < 1_pInt .or. &
|
||||||
microstructure_crystallite(m) > material_Ncrystallite) &
|
microstructure_crystallite(m) > size(config_crystallite)) &
|
||||||
call IO_error(150_pInt,m,ext_msg='crystallite')
|
call IO_error(150_pInt,m,ext_msg='crystallite')
|
||||||
if(minval(microstructure_phase(1:microstructure_Nconstituents(m),m)) < 1_pInt .or. &
|
if(minval(microstructure_phase(1:microstructure_Nconstituents(m),m)) < 1_pInt .or. &
|
||||||
maxval(microstructure_phase(1:microstructure_Nconstituents(m),m)) > material_Nphase) &
|
maxval(microstructure_phase(1:microstructure_Nconstituents(m),m)) > size(config_phase)) &
|
||||||
call IO_error(150_pInt,m,ext_msg='phase')
|
call IO_error(150_pInt,m,ext_msg='phase')
|
||||||
if(minval(microstructure_texture(1:microstructure_Nconstituents(m),m)) < 1_pInt .or. &
|
if(minval(microstructure_texture(1:microstructure_Nconstituents(m),m)) < 1_pInt .or. &
|
||||||
maxval(microstructure_texture(1:microstructure_Nconstituents(m),m)) > material_Ntexture) &
|
maxval(microstructure_texture(1:microstructure_Nconstituents(m),m)) > size(config_texture)) &
|
||||||
call IO_error(150_pInt,m,ext_msg='texture')
|
call IO_error(150_pInt,m,ext_msg='texture')
|
||||||
if(microstructure_Nconstituents(m) < 1_pInt) &
|
if(microstructure_Nconstituents(m) < 1_pInt) &
|
||||||
call IO_error(151_pInt,m)
|
call IO_error(151_pInt,m)
|
||||||
|
@ -437,11 +448,11 @@ subroutine material_init()
|
||||||
debugOut: if (iand(myDebug,debug_levelExtensive) /= 0_pInt) then
|
debugOut: if (iand(myDebug,debug_levelExtensive) /= 0_pInt) then
|
||||||
write(6,'(/,a,/)') ' MATERIAL configuration'
|
write(6,'(/,a,/)') ' MATERIAL configuration'
|
||||||
write(6,'(a32,1x,a16,1x,a6)') 'homogenization ','type ','grains'
|
write(6,'(a32,1x,a16,1x,a6)') 'homogenization ','type ','grains'
|
||||||
do h = 1_pInt,material_Nhomogenization
|
do h = 1_pInt,size(config_homogenization)
|
||||||
write(6,'(1x,a32,1x,a16,1x,i6)') homogenization_name(h),homogenization_type(h),homogenization_Ngrains(h)
|
write(6,'(1x,a32,1x,a16,1x,i6)') homogenization_name(h),homogenization_type(h),homogenization_Ngrains(h)
|
||||||
enddo
|
enddo
|
||||||
write(6,'(/,a14,18x,1x,a11,1x,a12,1x,a13)') 'microstructure','crystallite','constituents','homogeneous'
|
write(6,'(/,a14,18x,1x,a11,1x,a12,1x,a13)') 'microstructure','crystallite','constituents','homogeneous'
|
||||||
do m = 1_pInt,material_Nmicrostructure
|
do m = 1_pInt,size(config_microstructure)
|
||||||
write(6,'(1x,a32,1x,i11,1x,i12,1x,l13)') microstructure_name(m), &
|
write(6,'(1x,a32,1x,i11,1x,i12,1x,l13)') microstructure_name(m), &
|
||||||
microstructure_crystallite(m), &
|
microstructure_crystallite(m), &
|
||||||
microstructure_Nconstituents(m), &
|
microstructure_Nconstituents(m), &
|
||||||
|
@ -458,6 +469,7 @@ subroutine material_init()
|
||||||
endif debugOut
|
endif debugOut
|
||||||
|
|
||||||
call material_populateGrains
|
call material_populateGrains
|
||||||
|
call config_deallocate('material.config/microstructure')
|
||||||
|
|
||||||
allocate(phaseAt ( homogenization_maxNgrains,mesh_maxNips,mesh_NcpElems),source=0_pInt)
|
allocate(phaseAt ( homogenization_maxNgrains,mesh_maxNips,mesh_NcpElems),source=0_pInt)
|
||||||
allocate(phasememberAt ( homogenization_maxNgrains,mesh_maxNips,mesh_NcpElems),source=0_pInt)
|
allocate(phasememberAt ( homogenization_maxNgrains,mesh_maxNips,mesh_NcpElems),source=0_pInt)
|
||||||
|
@ -465,9 +477,9 @@ subroutine material_init()
|
||||||
allocate(mappingCrystallite (2,homogenization_maxNgrains, mesh_NcpElems),source=0_pInt)
|
allocate(mappingCrystallite (2,homogenization_maxNgrains, mesh_NcpElems),source=0_pInt)
|
||||||
allocate(mappingHomogenizationConst( mesh_maxNips,mesh_NcpElems),source=1_pInt)
|
allocate(mappingHomogenizationConst( mesh_maxNips,mesh_NcpElems),source=1_pInt)
|
||||||
|
|
||||||
allocate(ConstitutivePosition (material_Nphase), source=0_pInt)
|
allocate(ConstitutivePosition (size(config_phase)), source=0_pInt)
|
||||||
allocate(HomogenizationPosition(material_Nhomogenization),source=0_pInt)
|
allocate(HomogenizationPosition(size(config_homogenization)),source=0_pInt)
|
||||||
allocate(CrystallitePosition (material_Nphase), source=0_pInt)
|
allocate(CrystallitePosition (size(config_phase)), source=0_pInt)
|
||||||
|
|
||||||
ElemLoop:do e = 1_pInt,mesh_NcpElems
|
ElemLoop:do e = 1_pInt,mesh_NcpElems
|
||||||
myHomog = mesh_element(3,e)
|
myHomog = mesh_element(3,e)
|
||||||
|
@ -484,7 +496,7 @@ subroutine material_init()
|
||||||
enddo ElemLoop
|
enddo ElemLoop
|
||||||
|
|
||||||
! hack needed to initialize field values used during constitutive and crystallite initializations
|
! hack needed to initialize field values used during constitutive and crystallite initializations
|
||||||
do myHomog = 1,material_Nhomogenization
|
do myHomog = 1,size(config_homogenization)
|
||||||
thermalMapping (myHomog)%p => mappingHomogenizationConst
|
thermalMapping (myHomog)%p => mappingHomogenizationConst
|
||||||
damageMapping (myHomog)%p => mappingHomogenizationConst
|
damageMapping (myHomog)%p => mappingHomogenizationConst
|
||||||
vacancyfluxMapping (myHomog)%p => mappingHomogenizationConst
|
vacancyfluxMapping (myHomog)%p => mappingHomogenizationConst
|
||||||
|
@ -508,7 +520,7 @@ end subroutine material_init
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
subroutine material_parseHomogenization
|
subroutine material_parseHomogenization
|
||||||
use config, only : &
|
use config, only : &
|
||||||
homogenizationConfig
|
config_homogenization
|
||||||
use IO, only: &
|
use IO, only: &
|
||||||
IO_error
|
IO_error
|
||||||
use mesh, only: &
|
use mesh, only: &
|
||||||
|
@ -518,54 +530,54 @@ subroutine material_parseHomogenization
|
||||||
integer(pInt) :: h
|
integer(pInt) :: h
|
||||||
character(len=65536) :: tag
|
character(len=65536) :: tag
|
||||||
|
|
||||||
allocate(homogenization_type(material_Nhomogenization), source=HOMOGENIZATION_undefined_ID)
|
allocate(homogenization_type(size(config_homogenization)), source=HOMOGENIZATION_undefined_ID)
|
||||||
allocate(thermal_type(material_Nhomogenization), source=THERMAL_isothermal_ID)
|
allocate(thermal_type(size(config_homogenization)), source=THERMAL_isothermal_ID)
|
||||||
allocate(damage_type (material_Nhomogenization), source=DAMAGE_none_ID)
|
allocate(damage_type (size(config_homogenization)), source=DAMAGE_none_ID)
|
||||||
allocate(vacancyflux_type(material_Nhomogenization), source=VACANCYFLUX_isoconc_ID)
|
allocate(vacancyflux_type(size(config_homogenization)), source=VACANCYFLUX_isoconc_ID)
|
||||||
allocate(porosity_type (material_Nhomogenization), source=POROSITY_none_ID)
|
allocate(porosity_type (size(config_homogenization)), source=POROSITY_none_ID)
|
||||||
allocate(hydrogenflux_type(material_Nhomogenization), source=HYDROGENFLUX_isoconc_ID)
|
allocate(hydrogenflux_type(size(config_homogenization)), source=HYDROGENFLUX_isoconc_ID)
|
||||||
allocate(homogenization_typeInstance(material_Nhomogenization), source=0_pInt)
|
allocate(homogenization_typeInstance(size(config_homogenization)), source=0_pInt)
|
||||||
allocate(thermal_typeInstance(material_Nhomogenization), source=0_pInt)
|
allocate(thermal_typeInstance(size(config_homogenization)), source=0_pInt)
|
||||||
allocate(damage_typeInstance(material_Nhomogenization), source=0_pInt)
|
allocate(damage_typeInstance(size(config_homogenization)), source=0_pInt)
|
||||||
allocate(vacancyflux_typeInstance(material_Nhomogenization), source=0_pInt)
|
allocate(vacancyflux_typeInstance(size(config_homogenization)), source=0_pInt)
|
||||||
allocate(porosity_typeInstance(material_Nhomogenization), source=0_pInt)
|
allocate(porosity_typeInstance(size(config_homogenization)), source=0_pInt)
|
||||||
allocate(hydrogenflux_typeInstance(material_Nhomogenization), source=0_pInt)
|
allocate(hydrogenflux_typeInstance(size(config_homogenization)), source=0_pInt)
|
||||||
allocate(homogenization_Ngrains(material_Nhomogenization), source=0_pInt)
|
allocate(homogenization_Ngrains(size(config_homogenization)), source=0_pInt)
|
||||||
allocate(homogenization_Noutput(material_Nhomogenization), source=0_pInt)
|
allocate(homogenization_Noutput(size(config_homogenization)), source=0_pInt)
|
||||||
allocate(homogenization_active(material_Nhomogenization), source=.false.) !!!!!!!!!!!!!!!
|
allocate(homogenization_active(size(config_homogenization)), source=.false.) !!!!!!!!!!!!!!!
|
||||||
allocate(thermal_initialT(material_Nhomogenization), source=300.0_pReal)
|
allocate(thermal_initialT(size(config_homogenization)), source=300.0_pReal)
|
||||||
allocate(damage_initialPhi(material_Nhomogenization), source=1.0_pReal)
|
allocate(damage_initialPhi(size(config_homogenization)), source=1.0_pReal)
|
||||||
allocate(vacancyflux_initialCv(material_Nhomogenization), source=0.0_pReal)
|
allocate(vacancyflux_initialCv(size(config_homogenization)), source=0.0_pReal)
|
||||||
allocate(porosity_initialPhi(material_Nhomogenization), source=1.0_pReal)
|
allocate(porosity_initialPhi(size(config_homogenization)), source=1.0_pReal)
|
||||||
allocate(hydrogenflux_initialCh(material_Nhomogenization), source=0.0_pReal)
|
allocate(hydrogenflux_initialCh(size(config_homogenization)), source=0.0_pReal)
|
||||||
|
|
||||||
forall (h = 1_pInt:material_Nhomogenization) homogenization_active(h) = any(mesh_element(3,:) == h)
|
forall (h = 1_pInt:size(config_homogenization)) homogenization_active(h) = any(mesh_element(3,:) == h)
|
||||||
|
|
||||||
|
|
||||||
do h=1_pInt, material_Nhomogenization
|
do h=1_pInt, size(config_homogenization)
|
||||||
homogenization_Noutput(h) = homogenizationConfig(h)%countKeys('(output)')
|
homogenization_Noutput(h) = config_homogenization(h)%countKeys('(output)')
|
||||||
|
|
||||||
tag = homogenizationConfig(h)%getString('mech')
|
tag = config_homogenization(h)%getString('mech')
|
||||||
select case (trim(tag))
|
select case (trim(tag))
|
||||||
case(HOMOGENIZATION_NONE_label)
|
case(HOMOGENIZATION_NONE_label)
|
||||||
homogenization_type(h) = HOMOGENIZATION_NONE_ID
|
homogenization_type(h) = HOMOGENIZATION_NONE_ID
|
||||||
homogenization_Ngrains(h) = 1_pInt
|
homogenization_Ngrains(h) = 1_pInt
|
||||||
case(HOMOGENIZATION_ISOSTRAIN_label)
|
case(HOMOGENIZATION_ISOSTRAIN_label)
|
||||||
homogenization_type(h) = HOMOGENIZATION_ISOSTRAIN_ID
|
homogenization_type(h) = HOMOGENIZATION_ISOSTRAIN_ID
|
||||||
homogenization_Ngrains(h) = homogenizationConfig(h)%getInt('nconstituents')
|
homogenization_Ngrains(h) = config_homogenization(h)%getInt('nconstituents')
|
||||||
case(HOMOGENIZATION_RGC_label)
|
case(HOMOGENIZATION_RGC_label)
|
||||||
homogenization_type(h) = HOMOGENIZATION_RGC_ID
|
homogenization_type(h) = HOMOGENIZATION_RGC_ID
|
||||||
homogenization_Ngrains(h) = homogenizationConfig(h)%getInt('nconstituents')
|
homogenization_Ngrains(h) = config_homogenization(h)%getInt('nconstituents')
|
||||||
case default
|
case default
|
||||||
call IO_error(500_pInt,ext_msg=trim(tag))
|
call IO_error(500_pInt,ext_msg=trim(tag))
|
||||||
end select
|
end select
|
||||||
|
|
||||||
homogenization_typeInstance(h) = count(homogenization_type==homogenization_type(h))
|
homogenization_typeInstance(h) = count(homogenization_type==homogenization_type(h))
|
||||||
|
|
||||||
if (homogenizationConfig(h)%keyExists('thermal')) then
|
if (config_homogenization(h)%keyExists('thermal')) then
|
||||||
thermal_initialT(h) = homogenizationConfig(h)%getFloat('t0',defaultVal=300.0_pReal)
|
thermal_initialT(h) = config_homogenization(h)%getFloat('t0',defaultVal=300.0_pReal)
|
||||||
|
|
||||||
tag = homogenizationConfig(h)%getString('thermal')
|
tag = config_homogenization(h)%getString('thermal')
|
||||||
select case (trim(tag))
|
select case (trim(tag))
|
||||||
case(THERMAL_isothermal_label)
|
case(THERMAL_isothermal_label)
|
||||||
thermal_type(h) = THERMAL_isothermal_ID
|
thermal_type(h) = THERMAL_isothermal_ID
|
||||||
|
@ -579,10 +591,10 @@ subroutine material_parseHomogenization
|
||||||
|
|
||||||
endif
|
endif
|
||||||
|
|
||||||
if (homogenizationConfig(h)%keyExists('damage')) then
|
if (config_homogenization(h)%keyExists('damage')) then
|
||||||
damage_initialPhi(h) = homogenizationConfig(h)%getFloat('initialdamage',defaultVal=1.0_pReal)
|
damage_initialPhi(h) = config_homogenization(h)%getFloat('initialdamage',defaultVal=1.0_pReal)
|
||||||
|
|
||||||
tag = homogenizationConfig(h)%getString('damage')
|
tag = config_homogenization(h)%getString('damage')
|
||||||
select case (trim(tag))
|
select case (trim(tag))
|
||||||
case(DAMAGE_NONE_label)
|
case(DAMAGE_NONE_label)
|
||||||
damage_type(h) = DAMAGE_none_ID
|
damage_type(h) = DAMAGE_none_ID
|
||||||
|
@ -596,10 +608,10 @@ subroutine material_parseHomogenization
|
||||||
|
|
||||||
endif
|
endif
|
||||||
|
|
||||||
if (homogenizationConfig(h)%keyExists('vacancyflux')) then
|
if (config_homogenization(h)%keyExists('vacancyflux')) then
|
||||||
vacancyflux_initialCv(h) = homogenizationConfig(h)%getFloat('cv0',defaultVal=0.0_pReal)
|
vacancyflux_initialCv(h) = config_homogenization(h)%getFloat('cv0',defaultVal=0.0_pReal)
|
||||||
|
|
||||||
tag = homogenizationConfig(h)%getString('vacancyflux')
|
tag = config_homogenization(h)%getString('vacancyflux')
|
||||||
select case (trim(tag))
|
select case (trim(tag))
|
||||||
case(VACANCYFLUX_isoconc_label)
|
case(VACANCYFLUX_isoconc_label)
|
||||||
vacancyflux_type(h) = VACANCYFLUX_isoconc_ID
|
vacancyflux_type(h) = VACANCYFLUX_isoconc_ID
|
||||||
|
@ -613,10 +625,10 @@ subroutine material_parseHomogenization
|
||||||
|
|
||||||
endif
|
endif
|
||||||
|
|
||||||
if (homogenizationConfig(h)%keyExists('porosity')) then
|
if (config_homogenization(h)%keyExists('porosity')) then
|
||||||
!ToDo?
|
!ToDo?
|
||||||
|
|
||||||
tag = homogenizationConfig(h)%getString('porosity')
|
tag = config_homogenization(h)%getString('porosity')
|
||||||
select case (trim(tag))
|
select case (trim(tag))
|
||||||
case(POROSITY_NONE_label)
|
case(POROSITY_NONE_label)
|
||||||
porosity_type(h) = POROSITY_none_ID
|
porosity_type(h) = POROSITY_none_ID
|
||||||
|
@ -628,10 +640,10 @@ subroutine material_parseHomogenization
|
||||||
|
|
||||||
endif
|
endif
|
||||||
|
|
||||||
if (homogenizationConfig(h)%keyExists('hydrogenflux')) then
|
if (config_homogenization(h)%keyExists('hydrogenflux')) then
|
||||||
hydrogenflux_initialCh(h) = homogenizationConfig(h)%getFloat('ch0',defaultVal=0.0_pReal)
|
hydrogenflux_initialCh(h) = config_homogenization(h)%getFloat('ch0',defaultVal=0.0_pReal)
|
||||||
|
|
||||||
tag = homogenizationConfig(h)%getString('hydrogenflux')
|
tag = config_homogenization(h)%getString('hydrogenflux')
|
||||||
select case (trim(tag))
|
select case (trim(tag))
|
||||||
case(HYDROGENFLUX_isoconc_label)
|
case(HYDROGENFLUX_isoconc_label)
|
||||||
hydrogenflux_type(h) = HYDROGENFLUX_isoconc_ID
|
hydrogenflux_type(h) = HYDROGENFLUX_isoconc_ID
|
||||||
|
@ -645,7 +657,7 @@ subroutine material_parseHomogenization
|
||||||
|
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
do h=1_pInt, material_Nhomogenization
|
do h=1_pInt, size(config_homogenization)
|
||||||
homogenization_typeInstance(h) = count(homogenization_type(1:h) == homogenization_type(h))
|
homogenization_typeInstance(h) = count(homogenization_type(1:h) == homogenization_type(h))
|
||||||
thermal_typeInstance(h) = count(thermal_type (1:h) == thermal_type (h))
|
thermal_typeInstance(h) = count(thermal_type (1:h) == thermal_type (h))
|
||||||
damage_typeInstance(h) = count(damage_type (1:h) == damage_type (h))
|
damage_typeInstance(h) = count(damage_type (1:h) == damage_type (h))
|
||||||
|
@ -671,6 +683,9 @@ subroutine material_parseMicrostructure
|
||||||
IO_stringValue, &
|
IO_stringValue, &
|
||||||
IO_stringPos, &
|
IO_stringPos, &
|
||||||
IO_error
|
IO_error
|
||||||
|
use config, only: &
|
||||||
|
config_microstructure, &
|
||||||
|
microstructure_name
|
||||||
use mesh, only: &
|
use mesh, only: &
|
||||||
mesh_element, &
|
mesh_element, &
|
||||||
mesh_NcpElems
|
mesh_NcpElems
|
||||||
|
@ -683,29 +698,29 @@ subroutine material_parseMicrostructure
|
||||||
character(len=65536) :: &
|
character(len=65536) :: &
|
||||||
tag
|
tag
|
||||||
|
|
||||||
allocate(microstructure_crystallite(material_Nmicrostructure), source=0_pInt)
|
allocate(microstructure_crystallite(size(config_microstructure)), source=0_pInt)
|
||||||
allocate(microstructure_Nconstituents(material_Nmicrostructure), source=0_pInt)
|
allocate(microstructure_Nconstituents(size(config_microstructure)), source=0_pInt)
|
||||||
allocate(microstructure_active(material_Nmicrostructure), source=.false.)
|
allocate(microstructure_active(size(config_microstructure)), source=.false.)
|
||||||
allocate(microstructure_elemhomo(material_Nmicrostructure), source=.false.)
|
allocate(microstructure_elemhomo(size(config_microstructure)), source=.false.)
|
||||||
|
|
||||||
if(any(mesh_element(4,1:mesh_NcpElems) > material_Nmicrostructure)) &
|
if(any(mesh_element(4,1:mesh_NcpElems) > size(config_microstructure))) &
|
||||||
call IO_error(155_pInt,ext_msg='More microstructures in geometry than sections in material.config')
|
call IO_error(155_pInt,ext_msg='More microstructures in geometry than sections in material.config')
|
||||||
|
|
||||||
forall (e = 1_pInt:mesh_NcpElems) microstructure_active(mesh_element(4,e)) = .true. ! current microstructure used in model? Elementwise view, maximum N operations for N elements
|
forall (e = 1_pInt:mesh_NcpElems) microstructure_active(mesh_element(4,e)) = .true. ! current microstructure used in model? Elementwise view, maximum N operations for N elements
|
||||||
|
|
||||||
do m=1_pInt, material_Nmicrostructure
|
do m=1_pInt, size(config_microstructure)
|
||||||
microstructure_Nconstituents(m) = microstructureConfig(m)%countKeys('(constituent)')
|
microstructure_Nconstituents(m) = config_microstructure(m)%countKeys('(constituent)')
|
||||||
microstructure_crystallite(m) = microstructureConfig(m)%getInt('crystallite')
|
microstructure_crystallite(m) = config_microstructure(m)%getInt('crystallite')
|
||||||
microstructure_elemhomo(m) = microstructureConfig(m)%keyExists('/elementhomogeneous/')
|
microstructure_elemhomo(m) = config_microstructure(m)%keyExists('/elementhomogeneous/')
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
microstructure_maxNconstituents = maxval(microstructure_Nconstituents)
|
microstructure_maxNconstituents = maxval(microstructure_Nconstituents)
|
||||||
allocate(microstructure_phase (microstructure_maxNconstituents,material_Nmicrostructure),source=0_pInt)
|
allocate(microstructure_phase (microstructure_maxNconstituents,size(config_microstructure)),source=0_pInt)
|
||||||
allocate(microstructure_texture (microstructure_maxNconstituents,material_Nmicrostructure),source=0_pInt)
|
allocate(microstructure_texture (microstructure_maxNconstituents,size(config_microstructure)),source=0_pInt)
|
||||||
allocate(microstructure_fraction(microstructure_maxNconstituents,material_Nmicrostructure),source=0.0_pReal)
|
allocate(microstructure_fraction(microstructure_maxNconstituents,size(config_microstructure)),source=0.0_pReal)
|
||||||
|
|
||||||
do m=1_pInt, material_Nmicrostructure
|
do m=1_pInt, size(config_microstructure)
|
||||||
str = microstructureConfig(m)%getStrings('(constituent)',raw=.true.)
|
str = config_microstructure(m)%getStrings('(constituent)',raw=.true.)
|
||||||
do c = 1_pInt, size(str)
|
do c = 1_pInt, size(str)
|
||||||
chunkPos = IO_stringPos(str(c))
|
chunkPos = IO_stringPos(str(c))
|
||||||
|
|
||||||
|
@ -725,7 +740,7 @@ subroutine material_parseMicrostructure
|
||||||
enddo
|
enddo
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
do m = 1_pInt, material_Nmicrostructure
|
do m = 1_pInt, size(config_microstructure)
|
||||||
if (dNeq(sum(microstructure_fraction(:,m)),1.0_pReal)) &
|
if (dNeq(sum(microstructure_fraction(:,m)),1.0_pReal)) &
|
||||||
call IO_error(153_pInt,ext_msg=microstructure_name(m))
|
call IO_error(153_pInt,ext_msg=microstructure_name(m))
|
||||||
enddo
|
enddo
|
||||||
|
@ -737,13 +752,15 @@ end subroutine material_parseMicrostructure
|
||||||
!> @brief parses the crystallite part in the material configuration file
|
!> @brief parses the crystallite part in the material configuration file
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
subroutine material_parseCrystallite
|
subroutine material_parseCrystallite
|
||||||
|
use config, only: &
|
||||||
|
config_crystallite
|
||||||
|
|
||||||
implicit none
|
implicit none
|
||||||
integer(pInt) :: c
|
integer(pInt) :: c
|
||||||
|
|
||||||
allocate(crystallite_Noutput(material_Ncrystallite),source=0_pInt)
|
allocate(crystallite_Noutput(size(config_crystallite)),source=0_pInt)
|
||||||
do c=1_pInt, material_Ncrystallite
|
do c=1_pInt, size(config_crystallite)
|
||||||
crystallite_Noutput(c) = crystalliteConfig(c)%countKeys('(output)')
|
crystallite_Noutput(c) = config_crystallite(c)%countKeys('(output)')
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
end subroutine material_parseCrystallite
|
end subroutine material_parseCrystallite
|
||||||
|
@ -757,35 +774,37 @@ subroutine material_parsePhase
|
||||||
IO_error, &
|
IO_error, &
|
||||||
IO_getTag, &
|
IO_getTag, &
|
||||||
IO_stringValue
|
IO_stringValue
|
||||||
|
use config, only: &
|
||||||
|
config_phase
|
||||||
|
|
||||||
implicit none
|
implicit none
|
||||||
integer(pInt) :: sourceCtr, kinematicsCtr, stiffDegradationCtr, p
|
integer(pInt) :: sourceCtr, kinematicsCtr, stiffDegradationCtr, p
|
||||||
character(len=65536), dimension(:), allocatable :: str
|
character(len=65536), dimension(:), allocatable :: str
|
||||||
|
|
||||||
|
|
||||||
allocate(phase_elasticity(material_Nphase),source=ELASTICITY_undefined_ID)
|
allocate(phase_elasticity(size(config_phase)),source=ELASTICITY_undefined_ID)
|
||||||
allocate(phase_plasticity(material_Nphase),source=PLASTICITY_undefined_ID)
|
allocate(phase_plasticity(size(config_phase)),source=PLASTICITY_undefined_ID)
|
||||||
allocate(phase_Nsources(material_Nphase), source=0_pInt)
|
allocate(phase_Nsources(size(config_phase)), source=0_pInt)
|
||||||
allocate(phase_Nkinematics(material_Nphase), source=0_pInt)
|
allocate(phase_Nkinematics(size(config_phase)), source=0_pInt)
|
||||||
allocate(phase_NstiffnessDegradations(material_Nphase),source=0_pInt)
|
allocate(phase_NstiffnessDegradations(size(config_phase)),source=0_pInt)
|
||||||
allocate(phase_Noutput(material_Nphase), source=0_pInt)
|
allocate(phase_Noutput(size(config_phase)), source=0_pInt)
|
||||||
allocate(phase_localPlasticity(material_Nphase), source=.false.)
|
allocate(phase_localPlasticity(size(config_phase)), source=.false.)
|
||||||
|
|
||||||
do p=1_pInt, material_Nphase
|
do p=1_pInt, size(config_phase)
|
||||||
phase_Noutput(p) = phaseConfig(p)%countKeys('(output)')
|
phase_Noutput(p) = config_phase(p)%countKeys('(output)')
|
||||||
phase_Nsources(p) = phaseConfig(p)%countKeys('(source)')
|
phase_Nsources(p) = config_phase(p)%countKeys('(source)')
|
||||||
phase_Nkinematics(p) = phaseConfig(p)%countKeys('(kinematics)')
|
phase_Nkinematics(p) = config_phase(p)%countKeys('(kinematics)')
|
||||||
phase_NstiffnessDegradations(p) = phaseConfig(p)%countKeys('(stiffness_degradation)')
|
phase_NstiffnessDegradations(p) = config_phase(p)%countKeys('(stiffness_degradation)')
|
||||||
phase_localPlasticity(p) = .not. phaseConfig(p)%KeyExists('/nonlocal/')
|
phase_localPlasticity(p) = .not. config_phase(p)%KeyExists('/nonlocal/')
|
||||||
|
|
||||||
select case (phaseConfig(p)%getString('elasticity'))
|
select case (config_phase(p)%getString('elasticity'))
|
||||||
case (ELASTICITY_HOOKE_label)
|
case (ELASTICITY_HOOKE_label)
|
||||||
phase_elasticity(p) = ELASTICITY_HOOKE_ID
|
phase_elasticity(p) = ELASTICITY_HOOKE_ID
|
||||||
case default
|
case default
|
||||||
call IO_error(200_pInt,ext_msg=trim(phaseConfig(p)%getString('elasticity')))
|
call IO_error(200_pInt,ext_msg=trim(config_phase(p)%getString('elasticity')))
|
||||||
end select
|
end select
|
||||||
|
|
||||||
select case (phaseConfig(p)%getString('plasticity'))
|
select case (config_phase(p)%getString('plasticity'))
|
||||||
case (PLASTICITY_NONE_label)
|
case (PLASTICITY_NONE_label)
|
||||||
phase_plasticity(p) = PLASTICITY_NONE_ID
|
phase_plasticity(p) = PLASTICITY_NONE_ID
|
||||||
case (PLASTICITY_ISOTROPIC_label)
|
case (PLASTICITY_ISOTROPIC_label)
|
||||||
|
@ -801,22 +820,22 @@ subroutine material_parsePhase
|
||||||
case (PLASTICITY_NONLOCAL_label)
|
case (PLASTICITY_NONLOCAL_label)
|
||||||
phase_plasticity(p) = PLASTICITY_NONLOCAL_ID
|
phase_plasticity(p) = PLASTICITY_NONLOCAL_ID
|
||||||
case default
|
case default
|
||||||
call IO_error(201_pInt,ext_msg=trim(phaseConfig(p)%getString('plasticity')))
|
call IO_error(201_pInt,ext_msg=trim(config_phase(p)%getString('plasticity')))
|
||||||
end select
|
end select
|
||||||
|
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
allocate(phase_source(maxval(phase_Nsources),material_Nphase), source=SOURCE_undefined_ID)
|
allocate(phase_source(maxval(phase_Nsources),size(config_phase)), source=SOURCE_undefined_ID)
|
||||||
allocate(phase_kinematics(maxval(phase_Nkinematics),material_Nphase), source=KINEMATICS_undefined_ID)
|
allocate(phase_kinematics(maxval(phase_Nkinematics),size(config_phase)), source=KINEMATICS_undefined_ID)
|
||||||
allocate(phase_stiffnessDegradation(maxval(phase_NstiffnessDegradations),material_Nphase), &
|
allocate(phase_stiffnessDegradation(maxval(phase_NstiffnessDegradations),size(config_phase)), &
|
||||||
source=STIFFNESS_DEGRADATION_undefined_ID)
|
source=STIFFNESS_DEGRADATION_undefined_ID)
|
||||||
do p=1_pInt, material_Nphase
|
do p=1_pInt, size(config_phase)
|
||||||
#if defined(__GFORTRAN__)
|
#if defined(__GFORTRAN__)
|
||||||
str = ['GfortranBug86277']
|
str = ['GfortranBug86277']
|
||||||
str = phaseConfig(p)%getStrings('(source)',defaultVal=str)
|
str = config_phase(p)%getStrings('(source)',defaultVal=str)
|
||||||
if (str(1) == 'GfortranBug86277') str = [character(len=65536)::]
|
if (str(1) == 'GfortranBug86277') str = [character(len=65536)::]
|
||||||
#else
|
#else
|
||||||
str = phaseConfig(p)%getStrings('(source)',defaultVal=[character(len=65536)::])
|
str = config_phase(p)%getStrings('(source)',defaultVal=[character(len=65536)::])
|
||||||
#endif
|
#endif
|
||||||
do sourceCtr = 1_pInt, size(str)
|
do sourceCtr = 1_pInt, size(str)
|
||||||
select case (trim(str(sourceCtr)))
|
select case (trim(str(sourceCtr)))
|
||||||
|
@ -843,10 +862,10 @@ subroutine material_parsePhase
|
||||||
|
|
||||||
#if defined(__GFORTRAN__)
|
#if defined(__GFORTRAN__)
|
||||||
str = ['GfortranBug86277']
|
str = ['GfortranBug86277']
|
||||||
str = phaseConfig(p)%getStrings('(kinematics)',defaultVal=str)
|
str = config_phase(p)%getStrings('(kinematics)',defaultVal=str)
|
||||||
if (str(1) == 'GfortranBug86277') str = [character(len=65536)::]
|
if (str(1) == 'GfortranBug86277') str = [character(len=65536)::]
|
||||||
#else
|
#else
|
||||||
str = phaseConfig(p)%getStrings('(kinematics)',defaultVal=[character(len=65536)::])
|
str = config_phase(p)%getStrings('(kinematics)',defaultVal=[character(len=65536)::])
|
||||||
#endif
|
#endif
|
||||||
do kinematicsCtr = 1_pInt, size(str)
|
do kinematicsCtr = 1_pInt, size(str)
|
||||||
select case (trim(str(kinematicsCtr)))
|
select case (trim(str(kinematicsCtr)))
|
||||||
|
@ -864,10 +883,10 @@ subroutine material_parsePhase
|
||||||
enddo
|
enddo
|
||||||
#if defined(__GFORTRAN__)
|
#if defined(__GFORTRAN__)
|
||||||
str = ['GfortranBug86277']
|
str = ['GfortranBug86277']
|
||||||
str = phaseConfig(p)%getStrings('(stiffness_degradation)',defaultVal=str)
|
str = config_phase(p)%getStrings('(stiffness_degradation)',defaultVal=str)
|
||||||
if (str(1) == 'GfortranBug86277') str = [character(len=65536)::]
|
if (str(1) == 'GfortranBug86277') str = [character(len=65536)::]
|
||||||
#else
|
#else
|
||||||
str = phaseConfig(p)%getStrings('(stiffness_degradation)',defaultVal=[character(len=65536)::])
|
str = config_phase(p)%getStrings('(stiffness_degradation)',defaultVal=[character(len=65536)::])
|
||||||
#endif
|
#endif
|
||||||
do stiffDegradationCtr = 1_pInt, size(str)
|
do stiffDegradationCtr = 1_pInt, size(str)
|
||||||
select case (trim(str(stiffDegradationCtr)))
|
select case (trim(str(stiffDegradationCtr)))
|
||||||
|
@ -879,10 +898,10 @@ subroutine material_parsePhase
|
||||||
enddo
|
enddo
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
allocate(phase_plasticityInstance(material_Nphase), source=0_pInt)
|
allocate(phase_plasticityInstance(size(config_phase)), source=0_pInt)
|
||||||
allocate(phase_elasticityInstance(material_Nphase), source=0_pInt)
|
allocate(phase_elasticityInstance(size(config_phase)), source=0_pInt)
|
||||||
|
|
||||||
do p=1_pInt, material_Nphase
|
do p=1_pInt, size(config_phase)
|
||||||
phase_elasticityInstance(p) = count(phase_elasticity(1:p) == phase_elasticity(p))
|
phase_elasticityInstance(p) = count(phase_elasticity(1:p) == phase_elasticity(p))
|
||||||
phase_plasticityInstance(p) = count(phase_plasticity(1:p) == phase_plasticity(p))
|
phase_plasticityInstance(p) = count(phase_plasticity(1:p) == phase_plasticity(p))
|
||||||
enddo
|
enddo
|
||||||
|
@ -900,6 +919,9 @@ subroutine material_parseTexture
|
||||||
IO_stringPos, &
|
IO_stringPos, &
|
||||||
IO_floatValue, &
|
IO_floatValue, &
|
||||||
IO_stringValue
|
IO_stringValue
|
||||||
|
use config, only: &
|
||||||
|
config_texture, &
|
||||||
|
config_deallocate
|
||||||
use math, only: &
|
use math, only: &
|
||||||
inRad, &
|
inRad, &
|
||||||
math_sampleRandomOri, &
|
math_sampleRandomOri, &
|
||||||
|
@ -912,31 +934,31 @@ subroutine material_parseTexture
|
||||||
integer(pInt), dimension(:), allocatable :: chunkPos
|
integer(pInt), dimension(:), allocatable :: chunkPos
|
||||||
character(len=65536) :: tag
|
character(len=65536) :: tag
|
||||||
|
|
||||||
allocate(texture_ODFfile(material_Ntexture)); texture_ODFfile=''
|
allocate(texture_ODFfile(size(config_texture))); texture_ODFfile=''
|
||||||
allocate(texture_symmetry(material_Ntexture), source=1_pInt)
|
allocate(texture_symmetry(size(config_texture)), source=1_pInt)
|
||||||
allocate(texture_Ngauss(material_Ntexture), source=0_pInt)
|
allocate(texture_Ngauss(size(config_texture)), source=0_pInt)
|
||||||
allocate(texture_Nfiber(material_Ntexture), source=0_pInt)
|
allocate(texture_Nfiber(size(config_texture)), source=0_pInt)
|
||||||
|
|
||||||
do t=1_pInt, material_Ntexture
|
do t=1_pInt, size(config_texture)
|
||||||
texture_Ngauss(t) = textureConfig(t)%countKeys('(gauss)') &
|
texture_Ngauss(t) = config_texture(t)%countKeys('(gauss)') &
|
||||||
+ textureConfig(t)%countKeys('(random)')
|
+ config_texture(t)%countKeys('(random)')
|
||||||
texture_Nfiber(t) = textureConfig(t)%countKeys('(fiber)')
|
texture_Nfiber(t) = config_texture(t)%countKeys('(fiber)')
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
texture_maxNgauss = maxval(texture_Ngauss)
|
texture_maxNgauss = maxval(texture_Ngauss)
|
||||||
texture_maxNfiber = maxval(texture_Nfiber)
|
texture_maxNfiber = maxval(texture_Nfiber)
|
||||||
allocate(texture_Gauss (5,texture_maxNgauss,material_Ntexture), source=0.0_pReal)
|
allocate(texture_Gauss (5,texture_maxNgauss,size(config_texture)), source=0.0_pReal)
|
||||||
allocate(texture_Fiber (6,texture_maxNfiber,material_Ntexture), source=0.0_pReal)
|
allocate(texture_Fiber (6,texture_maxNfiber,size(config_texture)), source=0.0_pReal)
|
||||||
allocate(texture_transformation(3,3,material_Ntexture), source=0.0_pReal)
|
allocate(texture_transformation(3,3,size(config_texture)), source=0.0_pReal)
|
||||||
texture_transformation = spread(math_I3,3,material_Ntexture)
|
texture_transformation = spread(math_I3,3,size(config_texture))
|
||||||
|
|
||||||
do t=1_pInt, material_Ntexture
|
do t=1_pInt, size(config_texture)
|
||||||
section = t
|
section = t
|
||||||
gauss = 0_pInt
|
gauss = 0_pInt
|
||||||
fiber = 0_pInt
|
fiber = 0_pInt
|
||||||
|
|
||||||
if (textureConfig(t)%keyExists('axes')) then
|
if (config_texture(t)%keyExists('axes')) then
|
||||||
strings = textureConfig(t)%getStrings('axes')
|
strings = config_texture(t)%getStrings('axes')
|
||||||
do j = 1_pInt, 3_pInt ! look for "x", "y", and "z" entries
|
do j = 1_pInt, 3_pInt ! look for "x", "y", and "z" entries
|
||||||
select case (strings(j))
|
select case (strings(j))
|
||||||
case('x', '+x')
|
case('x', '+x')
|
||||||
|
@ -959,10 +981,10 @@ subroutine material_parseTexture
|
||||||
endif
|
endif
|
||||||
|
|
||||||
tag=''
|
tag=''
|
||||||
texture_ODFfile(t) = textureConfig(t)%getString('hybridia',defaultVal=tag)
|
texture_ODFfile(t) = config_texture(t)%getString('hybridia',defaultVal=tag)
|
||||||
|
|
||||||
if (textureConfig(t)%keyExists('symmetry')) then
|
if (config_texture(t)%keyExists('symmetry')) then
|
||||||
select case (textureConfig(t)%getString('symmetry'))
|
select case (config_texture(t)%getString('symmetry'))
|
||||||
case('orthotropic')
|
case('orthotropic')
|
||||||
texture_symmetry(t) = 4_pInt
|
texture_symmetry(t) = 4_pInt
|
||||||
case('monoclinic')
|
case('monoclinic')
|
||||||
|
@ -972,8 +994,8 @@ subroutine material_parseTexture
|
||||||
end select
|
end select
|
||||||
endif
|
endif
|
||||||
|
|
||||||
if (textureConfig(t)%keyExists('(random)')) then
|
if (config_texture(t)%keyExists('(random)')) then
|
||||||
strings = textureConfig(t)%getStrings('(random)',raw=.true.)
|
strings = config_texture(t)%getStrings('(random)',raw=.true.)
|
||||||
do i = 1_pInt, size(strings)
|
do i = 1_pInt, size(strings)
|
||||||
gauss = gauss + 1_pInt
|
gauss = gauss + 1_pInt
|
||||||
texture_Gauss(1:3,gauss,t) = math_sampleRandomOri()
|
texture_Gauss(1:3,gauss,t) = math_sampleRandomOri()
|
||||||
|
@ -990,9 +1012,9 @@ subroutine material_parseTexture
|
||||||
endif
|
endif
|
||||||
|
|
||||||
|
|
||||||
if (textureConfig(t)%keyExists('(gauss)')) then
|
if (config_texture(t)%keyExists('(gauss)')) then
|
||||||
gauss = gauss + 1_pInt
|
gauss = gauss + 1_pInt
|
||||||
strings = textureConfig(t)%getStrings('(gauss)',raw= .true.)
|
strings = config_texture(t)%getStrings('(gauss)',raw= .true.)
|
||||||
do i = 1_pInt , size(strings)
|
do i = 1_pInt , size(strings)
|
||||||
chunkPos = IO_stringPos(strings(i))
|
chunkPos = IO_stringPos(strings(i))
|
||||||
do j = 1_pInt,9_pInt,2_pInt
|
do j = 1_pInt,9_pInt,2_pInt
|
||||||
|
@ -1013,9 +1035,9 @@ subroutine material_parseTexture
|
||||||
endif
|
endif
|
||||||
|
|
||||||
|
|
||||||
if (textureConfig(t)%keyExists('(fiber)')) then
|
if (config_texture(t)%keyExists('(fiber)')) then
|
||||||
gauss = gauss + 1_pInt
|
fiber = fiber + 1_pInt
|
||||||
strings = textureConfig(t)%getStrings('(fiber)',raw= .true.)
|
strings = config_texture(t)%getStrings('(fiber)',raw= .true.)
|
||||||
do i = 1_pInt, size(strings)
|
do i = 1_pInt, size(strings)
|
||||||
chunkPos = IO_stringPos(strings(i))
|
chunkPos = IO_stringPos(strings(i))
|
||||||
do j = 1_pInt,11_pInt,2_pInt
|
do j = 1_pInt,11_pInt,2_pInt
|
||||||
|
@ -1038,6 +1060,7 @@ subroutine material_parseTexture
|
||||||
endif
|
endif
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
|
call config_deallocate('material.config/texture')
|
||||||
|
|
||||||
end subroutine material_parseTexture
|
end subroutine material_parseTexture
|
||||||
|
|
||||||
|
@ -1066,6 +1089,11 @@ subroutine material_populateGrains
|
||||||
mesh_ipVolume, &
|
mesh_ipVolume, &
|
||||||
FE_Nips, &
|
FE_Nips, &
|
||||||
FE_geomtype
|
FE_geomtype
|
||||||
|
use config, only: &
|
||||||
|
config_homogenization, &
|
||||||
|
config_microstructure, &
|
||||||
|
homogenization_name, &
|
||||||
|
microstructure_name
|
||||||
use IO, only: &
|
use IO, only: &
|
||||||
IO_error, &
|
IO_error, &
|
||||||
IO_hybridIA
|
IO_hybridIA
|
||||||
|
@ -1102,8 +1130,8 @@ subroutine material_populateGrains
|
||||||
allocate(material_texture(homogenization_maxNgrains,mesh_maxNips,mesh_NcpElems), source=0_pInt)
|
allocate(material_texture(homogenization_maxNgrains,mesh_maxNips,mesh_NcpElems), source=0_pInt)
|
||||||
allocate(material_EulerAngles(3,homogenization_maxNgrains,mesh_maxNips,mesh_NcpElems),source=0.0_pReal)
|
allocate(material_EulerAngles(3,homogenization_maxNgrains,mesh_maxNips,mesh_NcpElems),source=0.0_pReal)
|
||||||
|
|
||||||
allocate(Ngrains(material_Nhomogenization,material_Nmicrostructure), source=0_pInt)
|
allocate(Ngrains(size(config_homogenization),size(config_microstructure)), source=0_pInt)
|
||||||
allocate(Nelems(material_Nhomogenization,material_Nmicrostructure), source=0_pInt)
|
allocate(Nelems (size(config_homogenization),size(config_microstructure)), source=0_pInt)
|
||||||
|
|
||||||
! populating homogenization schemes in each
|
! populating homogenization schemes in each
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
|
@ -1118,9 +1146,9 @@ subroutine material_populateGrains
|
||||||
micro = mesh_element(4,e)
|
micro = mesh_element(4,e)
|
||||||
Nelems(homog,micro) = Nelems(homog,micro) + 1_pInt
|
Nelems(homog,micro) = Nelems(homog,micro) + 1_pInt
|
||||||
enddo
|
enddo
|
||||||
allocate(elemsOfHomogMicro(material_Nhomogenization,material_Nmicrostructure))
|
allocate(elemsOfHomogMicro(size(config_homogenization),size(config_microstructure)))
|
||||||
do homog = 1,material_Nhomogenization
|
do homog = 1,size(config_homogenization)
|
||||||
do micro = 1,material_Nmicrostructure
|
do micro = 1,size(config_microstructure)
|
||||||
if (Nelems(homog,micro) > 0_pInt) then
|
if (Nelems(homog,micro) > 0_pInt) then
|
||||||
allocate(elemsOfHomogMicro(homog,micro)%p(Nelems(homog,micro)))
|
allocate(elemsOfHomogMicro(homog,micro)%p(Nelems(homog,micro)))
|
||||||
elemsOfHomogMicro(homog,micro)%p = 0_pInt
|
elemsOfHomogMicro(homog,micro)%p = 0_pInt
|
||||||
|
@ -1135,9 +1163,9 @@ subroutine material_populateGrains
|
||||||
t = FE_geomtype(mesh_element(2,e))
|
t = FE_geomtype(mesh_element(2,e))
|
||||||
homog = mesh_element(3,e)
|
homog = mesh_element(3,e)
|
||||||
micro = mesh_element(4,e)
|
micro = mesh_element(4,e)
|
||||||
if (homog < 1_pInt .or. homog > material_Nhomogenization) & ! out of bounds
|
if (homog < 1_pInt .or. homog > size(config_homogenization)) & ! out of bounds
|
||||||
call IO_error(154_pInt,e,0_pInt,0_pInt)
|
call IO_error(154_pInt,e,0_pInt,0_pInt)
|
||||||
if (micro < 1_pInt .or. micro > material_Nmicrostructure) & ! out of bounds
|
if (micro < 1_pInt .or. micro > size(config_microstructure)) & ! out of bounds
|
||||||
call IO_error(155_pInt,e,0_pInt,0_pInt)
|
call IO_error(155_pInt,e,0_pInt,0_pInt)
|
||||||
if (microstructure_elemhomo(micro)) then ! how many grains are needed at this element?
|
if (microstructure_elemhomo(micro)) then ! how many grains are needed at this element?
|
||||||
dGrains = homogenization_Ngrains(homog) ! only one set of Ngrains (other IPs are plain copies)
|
dGrains = homogenization_Ngrains(homog) ! only one set of Ngrains (other IPs are plain copies)
|
||||||
|
@ -1158,9 +1186,9 @@ subroutine material_populateGrains
|
||||||
write(6,'(/,a/)') ' MATERIAL grain population'
|
write(6,'(/,a/)') ' MATERIAL grain population'
|
||||||
write(6,'(a32,1x,a32,1x,a6)') 'homogenization_name','microstructure_name','grain#'
|
write(6,'(a32,1x,a32,1x,a6)') 'homogenization_name','microstructure_name','grain#'
|
||||||
endif
|
endif
|
||||||
homogenizationLoop: do homog = 1_pInt,material_Nhomogenization
|
homogenizationLoop: do homog = 1_pInt,size(config_homogenization)
|
||||||
dGrains = homogenization_Ngrains(homog) ! grain number per material point
|
dGrains = homogenization_Ngrains(homog) ! grain number per material point
|
||||||
microstructureLoop: do micro = 1_pInt,material_Nmicrostructure ! all pairs of homog and micro
|
microstructureLoop: do micro = 1_pInt,size(config_microstructure) ! all pairs of homog and micro
|
||||||
activePair: if (Ngrains(homog,micro) > 0_pInt) then
|
activePair: if (Ngrains(homog,micro) > 0_pInt) then
|
||||||
myNgrains = Ngrains(homog,micro) ! assign short name for total number of grains to populate
|
myNgrains = Ngrains(homog,micro) ! assign short name for total number of grains to populate
|
||||||
myNconstituents = microstructure_Nconstituents(micro) ! assign short name for number of constituents
|
myNconstituents = microstructure_Nconstituents(micro) ! assign short name for number of constituents
|
||||||
|
|
|
@ -100,7 +100,7 @@ use IO
|
||||||
plasticState
|
plasticState
|
||||||
use config, only: &
|
use config, only: &
|
||||||
MATERIAL_partPhase, &
|
MATERIAL_partPhase, &
|
||||||
phaseConfig
|
config_phase
|
||||||
|
|
||||||
use lattice
|
use lattice
|
||||||
|
|
||||||
|
@ -145,29 +145,29 @@ use IO
|
||||||
if (phase_plasticity(phase) == PLASTICITY_ISOTROPIC_ID) then
|
if (phase_plasticity(phase) == PLASTICITY_ISOTROPIC_ID) then
|
||||||
instance = phase_plasticityInstance(phase)
|
instance = phase_plasticityInstance(phase)
|
||||||
prm => param(instance) ! shorthand pointer to parameter object of my constitutive law
|
prm => param(instance) ! shorthand pointer to parameter object of my constitutive law
|
||||||
prm%tau0 = phaseConfig(phase)%getFloat('tau0')
|
prm%tau0 = config_phase(phase)%getFloat('tau0')
|
||||||
prm%tausat = phaseConfig(phase)%getFloat('tausat')
|
prm%tausat = config_phase(phase)%getFloat('tausat')
|
||||||
prm%gdot0 = phaseConfig(phase)%getFloat('gdot0')
|
prm%gdot0 = config_phase(phase)%getFloat('gdot0')
|
||||||
prm%n = phaseConfig(phase)%getFloat('n')
|
prm%n = config_phase(phase)%getFloat('n')
|
||||||
prm%h0 = phaseConfig(phase)%getFloat('h0')
|
prm%h0 = config_phase(phase)%getFloat('h0')
|
||||||
prm%fTaylor = phaseConfig(phase)%getFloat('m')
|
prm%fTaylor = config_phase(phase)%getFloat('m')
|
||||||
prm%h0_slopeLnRate = phaseConfig(phase)%getFloat('h0_slopelnrate', defaultVal=0.0_pReal)
|
prm%h0_slopeLnRate = config_phase(phase)%getFloat('h0_slopelnrate', defaultVal=0.0_pReal)
|
||||||
prm%tausat_SinhFitA = phaseConfig(phase)%getFloat('tausat_sinhfita',defaultVal=0.0_pReal)
|
prm%tausat_SinhFitA = config_phase(phase)%getFloat('tausat_sinhfita',defaultVal=0.0_pReal)
|
||||||
prm%tausat_SinhFitB = phaseConfig(phase)%getFloat('tausat_sinhfitb',defaultVal=0.0_pReal)
|
prm%tausat_SinhFitB = config_phase(phase)%getFloat('tausat_sinhfitb',defaultVal=0.0_pReal)
|
||||||
prm%tausat_SinhFitC = phaseConfig(phase)%getFloat('tausat_sinhfitc',defaultVal=0.0_pReal)
|
prm%tausat_SinhFitC = config_phase(phase)%getFloat('tausat_sinhfitc',defaultVal=0.0_pReal)
|
||||||
prm%tausat_SinhFitD = phaseConfig(phase)%getFloat('tausat_sinhfitd',defaultVal=0.0_pReal)
|
prm%tausat_SinhFitD = config_phase(phase)%getFloat('tausat_sinhfitd',defaultVal=0.0_pReal)
|
||||||
prm%a = phaseConfig(phase)%getFloat('a')
|
prm%a = config_phase(phase)%getFloat('a')
|
||||||
prm%aTolFlowStress = phaseConfig(phase)%getFloat('atol_flowstress',defaultVal=1.0_pReal)
|
prm%aTolFlowStress = config_phase(phase)%getFloat('atol_flowstress',defaultVal=1.0_pReal)
|
||||||
prm%aTolShear = phaseConfig(phase)%getFloat('atol_shear',defaultVal=1.0e-6_pReal)
|
prm%aTolShear = config_phase(phase)%getFloat('atol_shear',defaultVal=1.0e-6_pReal)
|
||||||
|
|
||||||
prm%dilatation = phaseConfig(phase)%keyExists('/dilatation/')
|
prm%dilatation = config_phase(phase)%keyExists('/dilatation/')
|
||||||
|
|
||||||
#if defined(__GFORTRAN__)
|
#if defined(__GFORTRAN__)
|
||||||
outputs = ['GfortranBug86277']
|
outputs = ['GfortranBug86277']
|
||||||
outputs = phaseConfig(phase)%getStrings('(output)',defaultVal=outputs)
|
outputs = config_phase(phase)%getStrings('(output)',defaultVal=outputs)
|
||||||
if (outputs(1) == 'GfortranBug86277') outputs = [character(len=65536)::]
|
if (outputs(1) == 'GfortranBug86277') outputs = [character(len=65536)::]
|
||||||
#else
|
#else
|
||||||
outputs = phaseConfig(phase)%getStrings('(output)',defaultVal=[character(len=65536)::])
|
outputs = config_phase(phase)%getStrings('(output)',defaultVal=[character(len=65536)::])
|
||||||
#endif
|
#endif
|
||||||
allocate(prm%outputID(0))
|
allocate(prm%outputID(0))
|
||||||
do i=1_pInt, size(outputs)
|
do i=1_pInt, size(outputs)
|
||||||
|
|
Loading…
Reference in New Issue