Merge branch '30_parsePhasePartOnce' into development

Changes have been reviewed by Philip, just waited for all tests to pass.
Failing tests were partly related to version mismatches on the test
server for Compiler, python etc.
This commit is contained in:
Martin Diehl 2018-06-28 12:37:40 +02:00
commit 5e5f975bff
54 changed files with 1614 additions and 1178 deletions

View File

@ -7,7 +7,7 @@ stages:
- compileSpectralGNU - compileSpectralGNU
- prepareSpectral - prepareSpectral
- spectral - spectral
- compileMarc2016 - compileMarc2017
- marc - marc
- compileAbaqus2016 - compileAbaqus2016
- compileAbaqus2017 - compileAbaqus2017
@ -69,13 +69,10 @@ variables:
# ++++++++++++ FEM +++++++++++++++++++++++++++++++++++++++++++++++++++ # ++++++++++++ FEM +++++++++++++++++++++++++++++++++++++++++++++++++++
Abaqus2016: "FEM/Abaqus/2016" Abaqus2016: "FEM/Abaqus/2016"
Abaqus2017: "FEM/Abaqus/2017" Abaqus2017: "FEM/Abaqus/2017"
MSC2014: "FEM/MSC/2014" MSC2017: "FEM/MSC/2017"
MSC2014_2: "FEM/MSC/2014.2"
MSC2015: "FEM/MSC/2015"
MSC2016: "FEM/MSC/2016"
# ------------ Defaults ---------------------------------------------- # ------------ Defaults ----------------------------------------------
Abaqus: "$Abaqus2017" Abaqus: "$Abaqus2017"
MSC: "$MSC2016" MSC: "$MSC2017"
# ++++++++++++ Documentation +++++++++++++++++++++++++++++++++++++++++ # ++++++++++++ Documentation +++++++++++++++++++++++++++++++++++++++++
Doxygen1_8_13: "Documentation/Doxygen/1.8.13" Doxygen1_8_13: "Documentation/Doxygen/1.8.13"
# ------------ Defaults ---------------------------------------------- # ------------ Defaults ----------------------------------------------
@ -330,11 +327,11 @@ TextureComponents:
################################################################################################### ###################################################################################################
Marc_compileIfort2016: Marc_compileIfort2017:
stage: compileMarc2016 stage: compileMarc2017
script: script:
- module load $IntelCompiler16_0 $MSC2016 - module load $IntelCompiler17_0 $MSC2017
- Marc_compileIfort/test.py -m 2016 - Marc_compileIfort/test.py -m 2017
except: except:
- master - master
- release - release
@ -343,7 +340,7 @@ Marc_compileIfort2016:
Hex_elastic: Hex_elastic:
stage: marc stage: marc
script: script:
- module load $IntelCompiler16_0 $MSC - module load $IntelCompiler17_0 $MSC
- Hex_elastic/test.py - Hex_elastic/test.py
except: except:
- master - master
@ -352,7 +349,7 @@ Hex_elastic:
CubicFCC_elastic: CubicFCC_elastic:
stage: marc stage: marc
script: script:
- module load $IntelCompiler16_0 $MSC - module load $IntelCompiler17_0 $MSC
- CubicFCC_elastic/test.py - CubicFCC_elastic/test.py
except: except:
- master - master
@ -361,7 +358,7 @@ CubicFCC_elastic:
CubicBCC_elastic: CubicBCC_elastic:
stage: marc stage: marc
script: script:
- module load $IntelCompiler16_0 $MSC - module load $IntelCompiler17_0 $MSC
- CubicBCC_elastic/test.py - CubicBCC_elastic/test.py
except: except:
- master - master
@ -370,7 +367,7 @@ CubicBCC_elastic:
J2_plasticBehavior: J2_plasticBehavior:
stage: marc stage: marc
script: script:
- module load $IntelCompiler16_0 $MSC - module load $IntelCompiler17_0 $MSC
- J2_plasticBehavior/test.py - J2_plasticBehavior/test.py
except: except:
- master - master

2
CONFIG
View File

@ -6,6 +6,6 @@ set DAMASK_BIN = ${DAMASK_ROOT}/bin
set DAMASK_NUM_THREADS = 4 set DAMASK_NUM_THREADS = 4
set MSC_ROOT = /opt/msc set MSC_ROOT = /opt/msc
set MARC_VERSION = 2016 set MARC_VERSION = 2017
set ABAQUS_VERSION = 2017 set ABAQUS_VERSION = 2017

@ -1 +1 @@
Subproject commit cd02f6c1a481491eb4517651516b8311348b4777 Subproject commit aead92902b3a0cf3404be9c552bfec918d7aaffb

View File

@ -3,7 +3,7 @@
#-------------------# #-------------------#
[SX] [SX]
type none mech none
#-------------------# #-------------------#
<crystallite> <crystallite>

View File

@ -9,10 +9,8 @@ class Marc(Solver):
def __init__(self): def __init__(self):
self.solver = 'Marc' self.solver = 'Marc'
self.releases = { \ self.releases = { \
'2017': ['linux64',''],
'2016': ['linux64',''], '2016': ['linux64',''],
'2015': ['linux64',''],
'2014.2':['linux64',''],
'2014' :['linux64',''],
} }

View File

@ -15,7 +15,6 @@ add_dependencies(SYSTEM_ROUTINES C_ROUTINES)
list(APPEND OBJECTFILES $<TARGET_OBJECTS:SYSTEM_ROUTINES>) list(APPEND OBJECTFILES $<TARGET_OBJECTS:SYSTEM_ROUTINES>)
add_library(PREC OBJECT "prec.f90") add_library(PREC OBJECT "prec.f90")
add_dependencies(PREC SYSTEM_ROUTINES)
list(APPEND OBJECTFILES $<TARGET_OBJECTS:PREC>) list(APPEND OBJECTFILES $<TARGET_OBJECTS:PREC>)
if (PROJECT_NAME STREQUAL "DAMASK_spectral") if (PROJECT_NAME STREQUAL "DAMASK_spectral")
@ -25,7 +24,7 @@ elseif (PROJECT_NAME STREQUAL "DAMASK_FEM")
else () else ()
message (FATAL_ERROR "Build target (PROJECT_NAME) is not defined") message (FATAL_ERROR "Build target (PROJECT_NAME) is not defined")
endif() endif()
add_dependencies(DAMASK_INTERFACE PREC) add_dependencies(DAMASK_INTERFACE PREC SYSTEM_ROUTINES)
list(APPEND OBJECTFILES $<TARGET_OBJECTS:DAMASK_INTERFACE>) list(APPEND OBJECTFILES $<TARGET_OBJECTS:DAMASK_INTERFACE>)
add_library(IO OBJECT "IO.f90") add_library(IO OBJECT "IO.f90")
@ -40,6 +39,10 @@ add_library(DEBUG OBJECT "debug.f90")
add_dependencies(DEBUG NUMERICS) add_dependencies(DEBUG NUMERICS)
list(APPEND OBJECTFILES $<TARGET_OBJECTS:DEBUG>) list(APPEND OBJECTFILES $<TARGET_OBJECTS:DEBUG>)
add_library(CONFIG OBJECT "config.f90")
add_dependencies(CONFIG DEBUG)
list(APPEND OBJECTFILES $<TARGET_OBJECTS:CONFIG>)
add_library(FEsolving OBJECT "FEsolving.f90") add_library(FEsolving OBJECT "FEsolving.f90")
add_dependencies(FEsolving DEBUG) add_dependencies(FEsolving DEBUG)
list(APPEND OBJECTFILES $<TARGET_OBJECTS:FEsolving>) list(APPEND OBJECTFILES $<TARGET_OBJECTS:FEsolving>)
@ -63,7 +66,7 @@ elseif (PROJECT_NAME STREQUAL "DAMASK_FEM")
endif() endif()
add_library(MATERIAL OBJECT "material.f90") add_library(MATERIAL OBJECT "material.f90")
add_dependencies(MATERIAL MESH) add_dependencies(MATERIAL MESH CONFIG)
list(APPEND OBJECTFILES $<TARGET_OBJECTS:MATERIAL>) list(APPEND OBJECTFILES $<TARGET_OBJECTS:MATERIAL>)
add_library(DAMASK_HELPERS OBJECT "lattice.f90") add_library(DAMASK_HELPERS OBJECT "lattice.f90")

View File

@ -62,16 +62,18 @@ subroutine CPFEM_initAll(el,ip)
numerics_init numerics_init
use debug, only: & use debug, only: &
debug_init debug_init
use config, only: &
config_init
use FEsolving, only: & use FEsolving, only: &
FE_init FE_init
use math, only: & use math, only: &
math_init math_init
use mesh, only: & use mesh, only: &
mesh_init mesh_init
use lattice, only: &
lattice_init
use material, only: & use material, only: &
material_init material_init
use lattice, only: &
lattice_init
use constitutive, only: & use constitutive, only: &
constitutive_init constitutive_init
use crystallite, only: & use crystallite, only: &
@ -93,6 +95,7 @@ subroutine CPFEM_initAll(el,ip)
call IO_init call IO_init
call numerics_init call numerics_init
call debug_init call debug_init
call config_init
call math_init call math_init
call FE_init call FE_init
call mesh_init(ip, el) ! pass on coordinates to alter calcMode of first ip call mesh_init(ip, el) ! pass on coordinates to alter calcMode of first ip
@ -143,7 +146,8 @@ subroutine CPFEM_init
material_phase, & material_phase, &
homogState, & homogState, &
phase_plasticity, & phase_plasticity, &
plasticState, & plasticState
use config, only: &
material_Nhomogenization material_Nhomogenization
use crystallite, only: & use crystallite, only: &
crystallite_F0, & crystallite_F0, &
@ -310,7 +314,8 @@ subroutine CPFEM_general(mode, parallelExecution, ffn, ffn1, temperature_inp, dt
thermal_type, & thermal_type, &
THERMAL_conduction_ID, & THERMAL_conduction_ID, &
phase_Nsources, & phase_Nsources, &
material_homog, & material_homog
use config, only: &
material_Nhomogenization material_Nhomogenization
use crystallite, only: & use crystallite, only: &
crystallite_partionedF,& crystallite_partionedF,&

View File

@ -27,16 +27,18 @@ subroutine CPFEM_initAll(el,ip)
numerics_init numerics_init
use debug, only: & use debug, only: &
debug_init debug_init
use config, only: &
config_init
use FEsolving, only: & use FEsolving, only: &
FE_init FE_init
use math, only: & use math, only: &
math_init math_init
use mesh, only: & use mesh, only: &
mesh_init mesh_init
use lattice, only: &
lattice_init
use material, only: & use material, only: &
material_init material_init
use lattice, only: &
lattice_init
use constitutive, only: & use constitutive, only: &
constitutive_init constitutive_init
use crystallite, only: & use crystallite, only: &
@ -64,6 +66,7 @@ subroutine CPFEM_initAll(el,ip)
#endif #endif
call numerics_init call numerics_init
call debug_init call debug_init
call config_init
call math_init call math_init
call FE_init call FE_init
call mesh_init(ip, el) ! pass on coordinates to alter calcMode of first ip call mesh_init(ip, el) ! pass on coordinates to alter calcMode of first ip
@ -108,7 +111,8 @@ subroutine CPFEM_init
material_phase, & material_phase, &
homogState, & homogState, &
phase_plasticity, & phase_plasticity, &
plasticState, & plasticState
use config, only: &
material_Nhomogenization material_Nhomogenization
use crystallite, only: & use crystallite, only: &
crystallite_F0, & crystallite_F0, &
@ -228,7 +232,8 @@ subroutine CPFEM_age()
hydrogenfluxState, & hydrogenfluxState, &
material_phase, & material_phase, &
phase_plasticity, & phase_plasticity, &
phase_Nsources, & phase_Nsources
use config, only: &
material_Nhomogenization material_Nhomogenization
use crystallite, only: & use crystallite, only: &
crystallite_partionedF,& crystallite_partionedF,&

View File

@ -1 +0,0 @@
DAMASK_marc.f90

View File

@ -560,8 +560,8 @@ 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):670678, 2008' write(6,'(/,a)') ' Eisenlohr et al., Computational Materials Science, 42(4):670678, 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'
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
@ -900,10 +900,10 @@ function IO_spotTagInPart(fileUnit,part,tag,Nsections)
do while (trim(line) /= IO_EOF) do while (trim(line) /= IO_EOF)
line = IO_read(fileUnit) line = IO_read(fileUnit)
if (IO_isBlank(line)) cycle ! skip empty lines if (IO_isBlank(line)) cycle ! skip empty lines
if (IO_getTag(line,'<','>') /= '') then ! stop at next part foundNextPart: if (IO_getTag(line,'<','>') /= '') then
line = IO_read(fileUnit, .true.) ! reset IO_read line = IO_read(fileUnit, .true.) ! reset IO_read
exit exit
endif endif foundNextPart
if (IO_getTag(line,'[',']') /= '') section = section + 1_pInt ! found [section] identifier if (IO_getTag(line,'[',']') /= '') section = section + 1_pInt ! found [section] identifier
if (section > 0_pInt) then if (section > 0_pInt) then
chunkPos = IO_stringPos(line) chunkPos = IO_stringPos(line)
@ -925,13 +925,10 @@ logical function IO_globalTagInPart(fileUnit,part,tag)
character(len=*),intent(in) :: part, & !< part in which tag is searched for character(len=*),intent(in) :: part, & !< part in which tag is searched for
tag !< tag to search for tag !< tag to search for
integer(pInt), allocatable, dimension(:) :: chunkPos integer(pInt), allocatable, dimension(:) :: chunkPos
integer(pInt) :: section
character(len=65536) :: line character(len=65536) :: line
IO_globalTagInPart = .false. ! assume to nowhere spot tag IO_globalTagInPart = .false. ! assume to nowhere spot tag
section = 0_pInt
line ='' line =''
rewind(fileUnit) rewind(fileUnit)
@ -942,16 +939,20 @@ logical function IO_globalTagInPart(fileUnit,part,tag)
do while (trim(line) /= IO_EOF) do while (trim(line) /= IO_EOF)
line = IO_read(fileUnit) line = IO_read(fileUnit)
if (IO_isBlank(line)) cycle ! skip empty lines if (IO_isBlank(line)) cycle ! skip empty lines
if (IO_getTag(line,'<','>') /= '') then ! stop at next part foundNextPart: if (IO_getTag(line,'<','>') /= '') then
line = IO_read(fileUnit, .true.) ! reset IO_read line = IO_read(fileUnit, .true.) ! reset IO_read
exit exit
endif endif foundNextPart
if (IO_getTag(line,'[',']') /= '') section = section + 1_pInt ! found [section] identifier foundFirstSection: if (IO_getTag(line,'[',']') /= '') then
if (section == 0_pInt) then line = IO_read(fileUnit, .true.) ! reset IO_read
chunkPos = IO_stringPos(line) exit
if (tag == trim(IO_lc(IO_stringValue(line,chunkPos,1_pInt)))) & ! match endif foundFirstSection
IO_globalTagInPart = .true. chunkPos = IO_stringPos(line)
endif match: if (tag == trim(IO_lc(IO_stringValue(line,chunkPos,1_pInt)))) then
IO_globalTagInPart = .true.
line = IO_read(fileUnit, .true.) ! reset IO_read
exit
endif match
enddo enddo
end function IO_globalTagInPart end function IO_globalTagInPart
@ -981,6 +982,10 @@ pure function IO_stringPos(string)
if ( string(left:left) == '#' ) exit if ( string(left:left) == '#' ) exit
IO_stringPos = [IO_stringPos,int(left, pInt), int(right, pInt)] IO_stringPos = [IO_stringPos,int(left, pInt), int(right, pInt)]
IO_stringPos(1) = IO_stringPos(1)+1_pInt IO_stringPos(1) = IO_stringPos(1)+1_pInt
endOfString: if (right < left) then
IO_stringPos(IO_stringPos(1)*2+1) = len_trim(string)
exit
endif endOfString
enddo enddo
end function IO_stringPos end function IO_stringPos
@ -1545,6 +1550,17 @@ subroutine IO_error(error_ID,el,ip,g,instance,ext_msg)
case (136_pInt) case (136_pInt)
msg = 'zero entry on stiffness diagonal for transformed phase' msg = 'zero entry on stiffness diagonal for transformed phase'
!--------------------------------------------------------------------------------------------------
! errors related to the parsing of material.config
case (140_pInt)
msg = 'key not found'
case (141_pInt)
msg = 'number of chunks in string differs'
case (142_pInt)
msg = 'empty list'
case (143_pInt)
msg = 'no value found for key'
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
! material error messages and related messages in mesh ! material error messages and related messages in mesh
case (150_pInt) case (150_pInt)

View File

@ -6,6 +6,7 @@
#include "IO.f90" #include "IO.f90"
#include "numerics.f90" #include "numerics.f90"
#include "debug.f90" #include "debug.f90"
#include "config.f90"
#include "math.f90" #include "math.f90"
#include "FEsolving.f90" #include "FEsolving.f90"
#include "mesh.f90" #include "mesh.f90"

692
src/config.f90 Normal file
View File

@ -0,0 +1,692 @@
!--------------------------------------------------------------------------------------------------
!> @author Martin Diehl, Max-Planck-Institut für Eisenforschung GmbH
!> @brief Reads in the material configuration from file
!> @details Reads the material configuration file, where solverJobName.materialConfig takes
!! precedence over material.config. Stores the raw strings and the positions of delimiters for the
!! parts 'homogenization', 'crystallite', 'phase', 'texture', and 'microstucture'
!--------------------------------------------------------------------------------------------------
module config
use prec, only: &
pReal, &
pInt
implicit none
private
type, private :: tPartitionedString
character(len=:), allocatable :: val
integer(pInt), dimension(:), allocatable :: pos
end type tPartitionedString
type, public :: tPartitionedStringList
type(tPartitionedString) :: string
type(tPartitionedStringList), pointer :: next => null()
contains
procedure :: add => add
procedure :: show => show
procedure :: free => free
procedure :: keyExists => keyExists
procedure :: countKeys => countKeys
procedure :: getFloat => getFloat
procedure :: getInt => getInt
procedure :: getString => getString
procedure :: getFloats => getFloats
procedure :: getInts => getInts
procedure :: getStrings => getStrings
end type tPartitionedStringList
type(tPartitionedStringList), public :: emptyList
type(tPartitionedStringList), public, protected, allocatable, dimension(:) :: & ! QUESTION: rename to config_XXX?
config_phase, &
config_microstructure, &
config_homogenization, &
config_texture, &
config_crystallite
character(len=64), dimension(:), allocatable, public, protected :: &
phase_name, & !< name of each phase
homogenization_name, & !< name of each homogenization
crystallite_name, & !< name of each crystallite setting
microstructure_name, & !< name of each microstructure
texture_name !< name of each texture
! ToDo: make private, no one needs to know that
character(len=*), parameter, public :: &
MATERIAL_partHomogenization = 'homogenization', & !< keyword for homogenization part
MATERIAL_partCrystallite = 'crystallite', & !< keyword for crystallite part
MATERIAL_partPhase = 'phase', & !< keyword for phase part
MATERIAL_partMicrostructure = 'microstructure' !< keyword for microstructure part
character(len=*), parameter, private :: &
MATERIAL_partTexture = 'texture' !< keyword for texture part
! ToDo: Remove, use size(config_phase) etc
integer(pInt), public, protected :: &
material_Nphase, & !< number of phases
material_Nhomogenization, & !< number of homogenizations
material_Nmicrostructure, & !< number of microstructures
material_Ncrystallite !< number of crystallite settings
! ToDo: make private, no one needs to know that
character(len=*), parameter, public :: &
MATERIAL_configFile = 'material.config', & !< generic name for material configuration file
MATERIAL_localFileExt = 'materialConfig' !< extension of solver job name depending material configuration file
public :: &
config_init, &
config_deallocate
contains
!--------------------------------------------------------------------------------------------------
!> @brief reads material.config and stores its content per part
!--------------------------------------------------------------------------------------------------
subroutine config_init()
#if defined(__GFORTRAN__) || __INTEL_COMPILER >= 1800
use, intrinsic :: iso_fortran_env, only: &
compiler_version, &
compiler_options
#endif
use IO, only: &
IO_error, &
IO_open_file, &
IO_read, &
IO_lc, &
IO_open_jobFile_stat, &
IO_getTag, &
IO_timeStamp, &
IO_EOF
use debug, only: &
debug_level, &
debug_material, &
debug_levelBasic
implicit none
integer(pInt), parameter :: FILEUNIT = 200_pInt
integer(pInt) :: myDebug
character(len=65536) :: &
line, &
part
write(6,'(/,a)') ' <<<+- config init -+>>>'
write(6,'(a15,a)') ' Current time: ',IO_timeStamp()
#include "compilation_info.f90"
myDebug = debug_level(debug_material)
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
rewind(fileUnit)
line = '' ! to have it initialized
do while (trim(line) /= IO_EOF)
part = IO_lc(IO_getTag(line,'<','>'))
select case (trim(part))
case (trim(material_partPhase))
call parseFile(line,phase_name,config_phase,FILEUNIT)
if (iand(myDebug,debug_levelBasic) /= 0_pInt) write(6,'(a)') ' Phase parsed'; flush(6)
case (trim(material_partMicrostructure))
call parseFile(line,microstructure_name,config_microstructure,FILEUNIT)
if (iand(myDebug,debug_levelBasic) /= 0_pInt) write(6,'(a)') ' Microstructure parsed'; flush(6)
case (trim(material_partCrystallite))
call parseFile(line,crystallite_name,config_crystallite,FILEUNIT)
if (iand(myDebug,debug_levelBasic) /= 0_pInt) write(6,'(a)') ' Crystallite parsed'; flush(6)
case (trim(material_partHomogenization))
call parseFile(line,homogenization_name,config_homogenization,FILEUNIT)
if (iand(myDebug,debug_levelBasic) /= 0_pInt) write(6,'(a)') ' Homogenization parsed'; flush(6)
case (trim(material_partTexture))
call parseFile(line,texture_name,config_texture,FILEUNIT)
if (iand(myDebug,debug_levelBasic) /= 0_pInt) write(6,'(a)') ' Texture parsed'; flush(6)
case default
line = IO_read(fileUnit)
end select
enddo
material_Nhomogenization = size(config_homogenization)
if (material_Nhomogenization < 1_pInt) call IO_error(160_pInt,ext_msg=material_partHomogenization)
material_Nmicrostructure = size(config_microstructure)
if (material_Nmicrostructure < 1_pInt) call IO_error(160_pInt,ext_msg=material_partMicrostructure)
material_Ncrystallite = size(config_crystallite)
if (material_Ncrystallite < 1_pInt) call IO_error(160_pInt,ext_msg=material_partCrystallite)
material_Nphase = size(config_phase)
if (material_Nphase < 1_pInt) call IO_error(160_pInt,ext_msg=material_partPhase)
if (size(config_texture) < 1_pInt) call IO_error(160_pInt,ext_msg=material_partTexture)
end subroutine config_init
!--------------------------------------------------------------------------------------------------
!> @brief parses the material.config file
!--------------------------------------------------------------------------------------------------
subroutine parseFile(line,&
sectionNames,part,fileUnit)
use IO, only: &
IO_read, &
IO_error, &
IO_lc, &
IO_getTag, &
IO_isBlank, &
IO_stringValue, &
IO_stringPos, &
IO_EOF
implicit none
integer(pInt), intent(in) :: fileUnit
character(len=*), dimension(:), allocatable, intent(inout) :: sectionNames
type(tPartitionedStringList), allocatable, dimension(:), intent(inout) :: part
character(len=65536),intent(out) :: line
integer(pInt), allocatable, dimension(:) :: chunkPos
integer(pInt) :: s
character(len=65536) :: devNull
character(len=64) :: tag
logical :: echo
echo = .false.
allocate(part(0))
s = 0_pInt
do while (trim(line) /= IO_EOF) ! read through sections of material part
line = IO_read(fileUnit)
if (IO_isBlank(line)) cycle ! skip empty lines
foundNextPart: if (IO_getTag(line,'<','>') /= '') then
devNull = IO_read(fileUnit, .true.) ! reset IO_read to close any recursively included files
exit
endif foundNextPart
nextSection: if (IO_getTag(line,'[',']') /= '') then
s = s + 1_pInt
part = [part, emptyList]
tag = IO_getTag(line,'[',']')
GfortranBug86033: if (.not. allocated(sectionNames)) then
allocate(sectionNames(1),source=tag)
else GfortranBug86033
sectionNames = [sectionNames,tag]
endif GfortranBug86033
cycle
endif nextSection
chunkPos = IO_stringPos(line)
tag = IO_lc(IO_stringValue(trim(line),chunkPos,1_pInt)) ! extract key
inSection: if (s > 0_pInt) then
call part(s)%add(IO_lc(trim(line)))
else inSection
echo = (trim(tag) == '/echo/')
endif inSection
enddo
if (echo) then
do s = 1, size(sectionNames)
call part(s)%show()
end do
end if
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
!> @details Adds a string together with the start/end position of chunks in this string. The new
!! element is added at the end of the list. Empty strings are not added. All strings are converted
!! to lower case
!--------------------------------------------------------------------------------------------------
subroutine add(this,string)
use IO, only: &
IO_isBlank, &
IO_lc, &
IO_stringPos
implicit none
class(tPartitionedStringList), target, intent(in) :: this
character(len=*), intent(in) :: string
type(tPartitionedStringList), pointer :: new, item
if (IO_isBlank(string)) return
allocate(new)
new%string%val = IO_lc (trim(string))
new%string%pos = IO_stringPos(trim(string))
item => this
do while (associated(item%next))
item => item%next
enddo
item%next => new
end subroutine add
!--------------------------------------------------------------------------------------------------
!> @brief prints all elements
!> @details Strings are printed in order of insertion (FIFO)
!--------------------------------------------------------------------------------------------------
subroutine show(this)
implicit none
class(tPartitionedStringList) :: this
type(tPartitionedStringList), pointer :: item
item => this%next
do while (associated(item))
write(6,'(a)') trim(item%string%val)
item => item%next
end do
end subroutine show
!--------------------------------------------------------------------------------------------------
!> @brief cleans entire list
!> @details list head is remains alive
!--------------------------------------------------------------------------------------------------
subroutine free(this)
implicit none
class(tPartitionedStringList), target, intent(in) :: this
type(tPartitionedStringList), pointer :: new, item
if (.not. associated(this%next)) return
item => this%next
do while (associated(item%next))
new => item
deallocate(item)
item => new%next
enddo
deallocate(item)
end subroutine free
!--------------------------------------------------------------------------------------------------
!> @brief reports wether a given key (string value at first position) exists in the list
!--------------------------------------------------------------------------------------------------
logical function keyExists(this,key)
use IO, only: &
IO_stringValue
implicit none
class(tPartitionedStringList), intent(in) :: this
character(len=*), intent(in) :: key
type(tPartitionedStringList), pointer :: item
keyExists = .false.
item => this%next
do while (associated(item) .and. .not. keyExists)
keyExists = trim(IO_stringValue(item%string%val,item%string%pos,1)) == trim(key)
item => item%next
end do
end function keyExists
!--------------------------------------------------------------------------------------------------
!> @brief count number of key appearances
!> @details traverses list and counts each occurrence of specified key
!--------------------------------------------------------------------------------------------------
integer(pInt) function countKeys(this,key)
use IO, only: &
IO_stringValue
implicit none
class(tPartitionedStringList), intent(in) :: this
character(len=*), intent(in) :: key
type(tPartitionedStringList), pointer :: item
countKeys = 0_pInt
item => this%next
do while (associated(item))
if (trim(IO_stringValue(item%string%val,item%string%pos,1)) == trim(key)) &
countKeys = countKeys + 1_pInt
item => item%next
end do
end function countKeys
!--------------------------------------------------------------------------------------------------
!> @brief gets float value of for a given key from a linked list
!> @details gets the last value if the key occurs more than once. If key is not found exits with
!! error unless default is given
!--------------------------------------------------------------------------------------------------
real(pReal) function getFloat(this,key,defaultVal)
use IO, only : &
IO_error, &
IO_stringValue, &
IO_FloatValue
implicit none
class(tPartitionedStringList), intent(in) :: this
character(len=*), intent(in) :: key
real(pReal), intent(in), optional :: defaultVal
type(tPartitionedStringList), pointer :: item
logical :: found
found = present(defaultVal)
if (found) getFloat = defaultVal
item => this%next
do while (associated(item))
if (trim(IO_stringValue(item%string%val,item%string%pos,1)) == trim(key)) then
found = .true.
if (item%string%pos(1) < 2_pInt) call IO_error(143_pInt,ext_msg=key)
getFloat = IO_FloatValue(item%string%val,item%string%pos,2)
endif
item => item%next
end do
if (.not. found) call IO_error(140_pInt,ext_msg=key)
end function getFloat
!--------------------------------------------------------------------------------------------------
!> @brief gets integer value of for a given key from a linked list
!> @details gets the last value if the key occurs more than once. If key is not found exits with
!! error unless default is given
!--------------------------------------------------------------------------------------------------
integer(pInt) function getInt(this,key,defaultVal)
use IO, only: &
IO_error, &
IO_stringValue, &
IO_IntValue
implicit none
class(tPartitionedStringList), intent(in) :: this
character(len=*), intent(in) :: key
integer(pInt), intent(in), optional :: defaultVal
type(tPartitionedStringList), pointer :: item
logical :: found
found = present(defaultVal)
if (found) getInt = defaultVal
item => this%next
do while (associated(item))
if (trim(IO_stringValue(item%string%val,item%string%pos,1)) == trim(key)) then
found = .true.
if (item%string%pos(1) < 2_pInt) call IO_error(143_pInt,ext_msg=key)
getInt = IO_IntValue(item%string%val,item%string%pos,2)
endif
item => item%next
end do
if (.not. found) call IO_error(140_pInt,ext_msg=key)
end function getInt
!--------------------------------------------------------------------------------------------------
!> @brief gets string value of for a given key from a linked list
!> @details gets the last value if the key occurs more than once. If key is not found exits with
!! error unless default is given. If raw is true, the the complete string is returned, otherwise
!! the individual chunks are returned
!--------------------------------------------------------------------------------------------------
character(len=65536) function getString(this,key,defaultVal,raw)
use IO, only: &
IO_error, &
IO_stringValue
implicit none
class(tPartitionedStringList), intent(in) :: this
character(len=*), intent(in) :: key
character(len=65536), intent(in), optional :: defaultVal
logical, intent(in), optional :: raw
type(tPartitionedStringList), pointer :: item
logical :: found, &
whole
whole = merge(raw,.false.,present(raw)) ! whole string or white space splitting
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
do while (associated(item))
if (trim(IO_stringValue(item%string%val,item%string%pos,1)) == trim(key)) then
found = .true.
if (item%string%pos(1) < 2_pInt) call IO_error(143_pInt,ext_msg=key)
if (whole) then
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
item => item%next
end do
if (.not. found) call IO_error(140_pInt,ext_msg=key)
end function getString
!--------------------------------------------------------------------------------------------------
!> @brief gets array of float values of for a given key from a linked list
!> @details for cumulative keys, "()", values from all occurrences are return. Otherwise only all
!! values from the last occurrence. If key is not found exits with error unless default is given.
!--------------------------------------------------------------------------------------------------
function getFloats(this,key,defaultVal,requiredShape)
use IO, only: &
IO_error, &
IO_stringValue, &
IO_FloatValue
implicit none
real(pReal), dimension(:), allocatable :: getFloats
class(tPartitionedStringList), intent(in) :: this
character(len=*), intent(in) :: key
real(pReal), dimension(:), intent(in), optional :: defaultVal
integer(pInt), dimension(:), intent(in), optional :: requiredShape
type(tPartitionedStringList), pointer :: item
integer(pInt) :: i
logical :: found, &
cumulative
cumulative = (key(1:1) == '(' .and. key(len_trim(key):len_trim(key)) == ')')
found = .false.
allocate(getFloats(0))
item => this%next
do while (associated(item))
if (trim(IO_stringValue(item%string%val,item%string%pos,1)) == trim(key)) then
found = .true.
if (.not. cumulative) getFloats = [real(pReal)::]
if (item%string%pos(1) < 2_pInt) call IO_error(143_pInt,ext_msg=key)
do i = 2_pInt, item%string%pos(1)
getFloats = [getFloats,IO_FloatValue(item%string%val,item%string%pos,i)]
enddo
endif
item => item%next
end do
if (.not. found) then
if (present(defaultVal)) then; getFloats = defaultVal; else; call IO_error(140_pInt,ext_msg=key); endif
endif
end function getFloats
!--------------------------------------------------------------------------------------------------
!> @brief gets array of integer values of for a given key from a linked list
!> @details for cumulative keys, "()", values from all occurrences are return. Otherwise only all
!! values from the last occurrence. If key is not found exits with error unless default is given.
!--------------------------------------------------------------------------------------------------
function getInts(this,key,defaultVal,requiredShape)
use IO, only: &
IO_error, &
IO_stringValue, &
IO_IntValue
implicit none
integer(pInt), dimension(:), allocatable :: getInts
class(tPartitionedStringList), intent(in) :: this
character(len=*), intent(in) :: key
integer(pInt), dimension(:), intent(in), optional :: defaultVal, &
requiredShape
type(tPartitionedStringList), pointer :: item
integer(pInt) :: i
logical :: found, &
cumulative
cumulative = (key(1:1) == '(' .and. key(len_trim(key):len_trim(key)) == ')')
found = .false.
allocate(getInts(0))
item => this%next
do while (associated(item))
if (trim(IO_stringValue(item%string%val,item%string%pos,1)) == trim(key)) then
found = .true.
if (.not. cumulative) getInts = [integer(pInt)::]
if (item%string%pos(1) < 2_pInt) call IO_error(143_pInt,ext_msg=key)
do i = 2_pInt, item%string%pos(1)
getInts = [getInts,IO_IntValue(item%string%val,item%string%pos,i)]
enddo
endif
item => item%next
end do
if (.not. found) then
if (present(defaultVal)) then; getInts = defaultVal; else; call IO_error(140_pInt,ext_msg=key); endif
endif
end function getInts
!--------------------------------------------------------------------------------------------------
!> @brief gets array of string values of for a given key from a linked list
!> @details for cumulative keys, "()", values from all occurrences are return. Otherwise only all
!! values from the last occurrence. If key is not found exits with error unless default is given.
!! If raw is true, the the complete string is returned, otherwise the individual chunks are returned
!--------------------------------------------------------------------------------------------------
function getStrings(this,key,defaultVal,requiredShape,raw)
use IO, only: &
IO_error, &
IO_StringValue
implicit none
character(len=65536),dimension(:), allocatable :: getStrings
class(tPartitionedStringList), intent(in) :: this
character(len=*), intent(in) :: key
character(len=65536),dimension(:), intent(in), optional :: defaultVal
integer(pInt), dimension(:), intent(in), optional :: requiredShape
logical, intent(in), optional :: raw
type(tPartitionedStringList), pointer :: item
character(len=65536) :: str
integer(pInt) :: i
logical :: found, &
whole, &
cumulative
cumulative = (key(1:1) == '(' .and. key(len_trim(key):len_trim(key)) == ')')
whole = merge(raw,.false.,present(raw))
found = .false.
item => this%next
do while (associated(item))
if (trim(IO_stringValue(item%string%val,item%string%pos,1)) == trim(key)) then
found = .true.
if (allocated(getStrings) .and. .not. cumulative) deallocate(getStrings)
if (item%string%pos(1) < 2_pInt) call IO_error(143_pInt,ext_msg=key)
notAllocated: if (.not. allocated(getStrings)) 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)
allocate(getStrings(1),source=str)
do i=3_pInt,item%string%pos(1)
str = IO_StringValue(item%string%val,item%string%pos,i)
getStrings = [getStrings,str]
enddo
endif
else notAllocated
if (whole) then
getStrings = [getStrings,str]
else
do i=2_pInt,item%string%pos(1)
str = IO_StringValue(item%string%val,item%string%pos,i)
getStrings = [getStrings,str]
enddo
endif
endif notAllocated
endif
item => item%next
end do
if (.not. found) then
if (present(defaultVal)) then; getStrings = defaultVal; else; call IO_error(140_pInt,ext_msg=key); endif
endif
end function getStrings
end module config

View File

@ -57,14 +57,17 @@ 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 material, only: & use config, only: &
material_phase, &
material_Nphase, & material_Nphase, &
material_localFileExt, & material_localFileExt, &
material_configFile, &
phase_name, & phase_name, &
material_configFile
use material, only: &
material_phase, &
phase_plasticity, & phase_plasticity, &
phase_plasticityInstance, & phase_plasticityInstance, &
phase_Nsources, & phase_Nsources, &
@ -143,7 +146,6 @@ subroutine constitutive_init()
ins !< instance of plasticity/source ins !< instance of plasticity/source
integer(pInt), dimension(:,:), pointer :: thisSize integer(pInt), dimension(:,:), pointer :: thisSize
integer(pInt), dimension(:) , pointer :: thisNoutput
character(len=64), dimension(:,:), pointer :: thisOutput character(len=64), dimension(:,:), pointer :: thisOutput
character(len=32) :: outputName !< name of output, intermediate fix until HDF5 output is ready character(len=32) :: outputName !< name of output, intermediate fix until HDF5 output is ready
logical :: knownPlasticity, knownSource, nonlocalConstitutionPresent logical :: knownPlasticity, knownSource, nonlocalConstitutionPresent
@ -157,7 +159,7 @@ subroutine constitutive_init()
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
! parse plasticities from config file ! parse plasticities from config file
if (any(phase_plasticity == PLASTICITY_NONE_ID)) call plastic_none_init if (any(phase_plasticity == PLASTICITY_NONE_ID)) call plastic_none_init
if (any(phase_plasticity == PLASTICITY_ISOTROPIC_ID)) call plastic_isotropic_init(FILEUNIT) if (any(phase_plasticity == PLASTICITY_ISOTROPIC_ID)) call plastic_isotropic_init
if (any(phase_plasticity == PLASTICITY_PHENOPOWERLAW_ID)) call plastic_phenopowerlaw_init(FILEUNIT) if (any(phase_plasticity == PLASTICITY_PHENOPOWERLAW_ID)) call plastic_phenopowerlaw_init(FILEUNIT)
if (any(phase_plasticity == PLASTICITY_KINEHARDENING_ID)) call plastic_kinehardening_init(FILEUNIT) if (any(phase_plasticity == PLASTICITY_KINEHARDENING_ID)) call plastic_kinehardening_init(FILEUNIT)
if (any(phase_plasticity == PLASTICITY_DISLOTWIN_ID)) call plastic_dislotwin_init(FILEUNIT) if (any(phase_plasticity == PLASTICITY_DISLOTWIN_ID)) call plastic_dislotwin_init(FILEUNIT)
@ -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"
@ -205,37 +209,30 @@ subroutine constitutive_init()
plasticityType: select case(phase_plasticity(p)) plasticityType: select case(phase_plasticity(p))
case (PLASTICITY_NONE_ID) plasticityType case (PLASTICITY_NONE_ID) plasticityType
outputName = PLASTICITY_NONE_label outputName = PLASTICITY_NONE_label
thisNoutput => null()
thisOutput => null() thisOutput => null()
thisSize => null() thisSize => null()
case (PLASTICITY_ISOTROPIC_ID) plasticityType case (PLASTICITY_ISOTROPIC_ID) plasticityType
outputName = PLASTICITY_ISOTROPIC_label outputName = PLASTICITY_ISOTROPIC_label
thisNoutput => plastic_isotropic_Noutput
thisOutput => plastic_isotropic_output thisOutput => plastic_isotropic_output
thisSize => plastic_isotropic_sizePostResult thisSize => plastic_isotropic_sizePostResult
case (PLASTICITY_PHENOPOWERLAW_ID) plasticityType case (PLASTICITY_PHENOPOWERLAW_ID) plasticityType
outputName = PLASTICITY_PHENOPOWERLAW_label outputName = PLASTICITY_PHENOPOWERLAW_label
thisNoutput => plastic_phenopowerlaw_Noutput
thisOutput => plastic_phenopowerlaw_output thisOutput => plastic_phenopowerlaw_output
thisSize => plastic_phenopowerlaw_sizePostResult thisSize => plastic_phenopowerlaw_sizePostResult
case (PLASTICITY_KINEHARDENING_ID) plasticityType case (PLASTICITY_KINEHARDENING_ID) plasticityType
outputName = PLASTICITY_KINEHARDENING_label outputName = PLASTICITY_KINEHARDENING_label
thisNoutput => plastic_kinehardening_Noutput
thisOutput => plastic_kinehardening_output thisOutput => plastic_kinehardening_output
thisSize => plastic_kinehardening_sizePostResult thisSize => plastic_kinehardening_sizePostResult
case (PLASTICITY_DISLOTWIN_ID) plasticityType case (PLASTICITY_DISLOTWIN_ID) plasticityType
outputName = PLASTICITY_DISLOTWIN_label outputName = PLASTICITY_DISLOTWIN_label
thisNoutput => plastic_dislotwin_Noutput
thisOutput => plastic_dislotwin_output thisOutput => plastic_dislotwin_output
thisSize => plastic_dislotwin_sizePostResult thisSize => plastic_dislotwin_sizePostResult
case (PLASTICITY_DISLOUCLA_ID) plasticityType case (PLASTICITY_DISLOUCLA_ID) plasticityType
outputName = PLASTICITY_DISLOUCLA_label outputName = PLASTICITY_DISLOUCLA_label
thisNoutput => plastic_disloucla_Noutput
thisOutput => plastic_disloucla_output thisOutput => plastic_disloucla_output
thisSize => plastic_disloucla_sizePostResult thisSize => plastic_disloucla_sizePostResult
case (PLASTICITY_NONLOCAL_ID) plasticityType case (PLASTICITY_NONLOCAL_ID) plasticityType
outputName = PLASTICITY_NONLOCAL_label outputName = PLASTICITY_NONLOCAL_label
thisNoutput => plastic_nonlocal_Noutput
thisOutput => plastic_nonlocal_output thisOutput => plastic_nonlocal_output
thisSize => plastic_nonlocal_sizePostResult thisSize => plastic_nonlocal_sizePostResult
case default plasticityType case default plasticityType
@ -246,8 +243,9 @@ subroutine constitutive_init()
write(FILEUNIT,'(a)') '(plasticity)'//char(9)//trim(outputName) write(FILEUNIT,'(a)') '(plasticity)'//char(9)//trim(outputName)
if (phase_plasticity(p) /= PLASTICITY_NONE_ID) then if (phase_plasticity(p) /= PLASTICITY_NONE_ID) then
OutputPlasticityLoop: do o = 1_pInt,thisNoutput(ins) OutputPlasticityLoop: do o = 1_pInt,size(thisOutput(:,ins))
write(FILEUNIT,'(a,i4)') trim(thisOutput(o,ins))//char(9),thisSize(o,ins) if(len(trim(thisOutput(o,ins))) > 0_pInt) &
write(FILEUNIT,'(a,i4)') trim(thisOutput(o,ins))//char(9),thisSize(o,ins)
enddo OutputPlasticityLoop enddo OutputPlasticityLoop
endif endif
endif endif
@ -257,55 +255,46 @@ subroutine constitutive_init()
case (SOURCE_thermal_dissipation_ID) sourceType case (SOURCE_thermal_dissipation_ID) sourceType
ins = source_thermal_dissipation_instance(p) ins = source_thermal_dissipation_instance(p)
outputName = SOURCE_thermal_dissipation_label outputName = SOURCE_thermal_dissipation_label
thisNoutput => source_thermal_dissipation_Noutput
thisOutput => source_thermal_dissipation_output thisOutput => source_thermal_dissipation_output
thisSize => source_thermal_dissipation_sizePostResult thisSize => source_thermal_dissipation_sizePostResult
case (SOURCE_thermal_externalheat_ID) sourceType case (SOURCE_thermal_externalheat_ID) sourceType
ins = source_thermal_externalheat_instance(p) ins = source_thermal_externalheat_instance(p)
outputName = SOURCE_thermal_externalheat_label outputName = SOURCE_thermal_externalheat_label
thisNoutput => source_thermal_externalheat_Noutput
thisOutput => source_thermal_externalheat_output thisOutput => source_thermal_externalheat_output
thisSize => source_thermal_externalheat_sizePostResult thisSize => source_thermal_externalheat_sizePostResult
case (SOURCE_damage_isoBrittle_ID) sourceType case (SOURCE_damage_isoBrittle_ID) sourceType
ins = source_damage_isoBrittle_instance(p) ins = source_damage_isoBrittle_instance(p)
outputName = SOURCE_damage_isoBrittle_label outputName = SOURCE_damage_isoBrittle_label
thisNoutput => source_damage_isoBrittle_Noutput
thisOutput => source_damage_isoBrittle_output thisOutput => source_damage_isoBrittle_output
thisSize => source_damage_isoBrittle_sizePostResult thisSize => source_damage_isoBrittle_sizePostResult
case (SOURCE_damage_isoDuctile_ID) sourceType case (SOURCE_damage_isoDuctile_ID) sourceType
ins = source_damage_isoDuctile_instance(p) ins = source_damage_isoDuctile_instance(p)
outputName = SOURCE_damage_isoDuctile_label outputName = SOURCE_damage_isoDuctile_label
thisNoutput => source_damage_isoDuctile_Noutput
thisOutput => source_damage_isoDuctile_output thisOutput => source_damage_isoDuctile_output
thisSize => source_damage_isoDuctile_sizePostResult thisSize => source_damage_isoDuctile_sizePostResult
case (SOURCE_damage_anisoBrittle_ID) sourceType case (SOURCE_damage_anisoBrittle_ID) sourceType
ins = source_damage_anisoBrittle_instance(p) ins = source_damage_anisoBrittle_instance(p)
outputName = SOURCE_damage_anisoBrittle_label outputName = SOURCE_damage_anisoBrittle_label
thisNoutput => source_damage_anisoBrittle_Noutput
thisOutput => source_damage_anisoBrittle_output thisOutput => source_damage_anisoBrittle_output
thisSize => source_damage_anisoBrittle_sizePostResult thisSize => source_damage_anisoBrittle_sizePostResult
case (SOURCE_damage_anisoDuctile_ID) sourceType case (SOURCE_damage_anisoDuctile_ID) sourceType
ins = source_damage_anisoDuctile_instance(p) ins = source_damage_anisoDuctile_instance(p)
outputName = SOURCE_damage_anisoDuctile_label outputName = SOURCE_damage_anisoDuctile_label
thisNoutput => source_damage_anisoDuctile_Noutput
thisOutput => source_damage_anisoDuctile_output thisOutput => source_damage_anisoDuctile_output
thisSize => source_damage_anisoDuctile_sizePostResult thisSize => source_damage_anisoDuctile_sizePostResult
case (SOURCE_vacancy_phenoplasticity_ID) sourceType case (SOURCE_vacancy_phenoplasticity_ID) sourceType
ins = source_vacancy_phenoplasticity_instance(p) ins = source_vacancy_phenoplasticity_instance(p)
outputName = SOURCE_vacancy_phenoplasticity_label outputName = SOURCE_vacancy_phenoplasticity_label
thisNoutput => source_vacancy_phenoplasticity_Noutput
thisOutput => source_vacancy_phenoplasticity_output thisOutput => source_vacancy_phenoplasticity_output
thisSize => source_vacancy_phenoplasticity_sizePostResult thisSize => source_vacancy_phenoplasticity_sizePostResult
case (SOURCE_vacancy_irradiation_ID) sourceType case (SOURCE_vacancy_irradiation_ID) sourceType
ins = source_vacancy_irradiation_instance(p) ins = source_vacancy_irradiation_instance(p)
outputName = SOURCE_vacancy_irradiation_label outputName = SOURCE_vacancy_irradiation_label
thisNoutput => source_vacancy_irradiation_Noutput
thisOutput => source_vacancy_irradiation_output thisOutput => source_vacancy_irradiation_output
thisSize => source_vacancy_irradiation_sizePostResult thisSize => source_vacancy_irradiation_sizePostResult
case (SOURCE_vacancy_thermalfluc_ID) sourceType case (SOURCE_vacancy_thermalfluc_ID) sourceType
ins = source_vacancy_thermalfluc_instance(p) ins = source_vacancy_thermalfluc_instance(p)
outputName = SOURCE_vacancy_thermalfluc_label outputName = SOURCE_vacancy_thermalfluc_label
thisNoutput => source_vacancy_thermalfluc_Noutput
thisOutput => source_vacancy_thermalfluc_output thisOutput => source_vacancy_thermalfluc_output
thisSize => source_vacancy_thermalfluc_sizePostResult thisSize => source_vacancy_thermalfluc_sizePostResult
case default sourceType case default sourceType
@ -313,8 +302,9 @@ subroutine constitutive_init()
end select sourceType end select sourceType
if (knownSource) then if (knownSource) then
write(FILEUNIT,'(a)') '(source)'//char(9)//trim(outputName) write(FILEUNIT,'(a)') '(source)'//char(9)//trim(outputName)
OutputSourceLoop: do o = 1_pInt,thisNoutput(ins) OutputSourceLoop: do o = 1_pInt,size(thisOutput(:,ins))
write(FILEUNIT,'(a,i4)') trim(thisOutput(o,ins))//char(9),thisSize(o,ins) if(len(trim(thisOutput(o,ins))) > 0_pInt) &
write(FILEUNIT,'(a,i4)') trim(thisOutput(o,ins))//char(9),thisSize(o,ins)
enddo OutputSourceLoop enddo OutputSourceLoop
endif endif
enddo SourceLoop enddo SourceLoop
@ -350,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

View File

@ -155,7 +155,6 @@ subroutine crystallite_init
math_I3, & math_I3, &
math_EulerToR, & math_EulerToR, &
math_inv33, & math_inv33, &
math_transpose33, &
math_mul33xx33, & math_mul33xx33, &
math_mul33x33 math_mul33x33
use FEsolving, only: & use FEsolving, only: &
@ -167,28 +166,22 @@ subroutine crystallite_init
mesh_maxNips, & mesh_maxNips, &
mesh_maxNipNeighbors mesh_maxNipNeighbors
use IO, only: & use IO, only: &
IO_read, &
IO_timeStamp, & IO_timeStamp, &
IO_open_jobFile_stat, &
IO_open_file, &
IO_lc, &
IO_getTag, &
IO_isBlank, &
IO_stringPos, &
IO_stringValue, & IO_stringValue, &
IO_write_jobFile, & IO_write_jobFile, &
IO_error, & IO_error
IO_EOF
use material use material
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
implicit none implicit none
integer(pInt), parameter :: &
FILEUNIT = 200_pInt
integer(pInt), allocatable, dimension(:) :: chunkPos integer(pInt), parameter :: FILEUNIT=434_pInt
integer(pInt) :: & integer(pInt) :: &
c, & !< counter in integration point component loop c, & !< counter in integration point component loop
i, & !< counter in integration point loop i, & !< counter in integration point loop
@ -200,12 +193,11 @@ subroutine crystallite_init
eMax, & !< maximum number of elements eMax, & !< maximum number of elements
nMax, & !< maximum number of ip neighbors nMax, & !< maximum number of ip neighbors
myNcomponents, & !< number of components at current IP myNcomponents, & !< number of components at current IP
section = 0_pInt, &
mySize mySize
character(len=65536), dimension(:), allocatable :: str
character(len=65536) :: & character(len=65536) :: &
tag = '', & tag = ''
line= ''
write(6,'(/,a)') ' <<<+- crystallite init -+>>>' write(6,'(/,a)') ' <<<+- crystallite init -+>>>'
write(6,'(a15,a)') ' Current time: ',IO_timeStamp() write(6,'(a15,a)') ' Current time: ',IO_timeStamp()
@ -270,94 +262,77 @@ 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)
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
do while (trim(line) /= IO_EOF .and. IO_lc(IO_getTag(line,'<','>')) /= material_partCrystallite) ! wind forward to <crystallite> do c = 1_pInt, size(config_crystallite)
line = IO_read(FILEUNIT) #if defined(__GFORTRAN__)
enddo str = ['GfortranBug86277']
str = config_crystallite(c)%getStrings('(output)',defaultVal=str)
do while (trim(line) /= IO_EOF) ! read through sections of crystallite part if (str(1) == 'GfortranBug86277') str = [character(len=65536)::]
line = IO_read(FILEUNIT) #else
if (IO_isBlank(line)) cycle ! skip empty lines str = config_crystallite(c)%getStrings('(output)',defaultVal=[character(len=65536)::])
if (IO_getTag(line,'<','>') /= '') then ! stop at next part #endif
line = IO_read(FILEUNIT, .true.) ! reset IO_read do o = 1_pInt, size(str)
exit crystallite_output(o,c) = str(o)
endif outputName: select case(str(o))
if (IO_getTag(line,'[',']') /= '') then ! next section
section = section + 1_pInt
o = 0_pInt ! reset output counter
cycle ! skip to next line
endif
if (section > 0_pInt) then
chunkPos = IO_stringPos(line)
tag = IO_lc(IO_stringValue(line,chunkPos,1_pInt)) ! extract key
select case(tag)
case ('(output)')
o = o + 1_pInt
crystallite_output(o,section) = IO_lc(IO_stringValue(line,chunkPos,2_pInt))
outputName: select case(crystallite_output(o,section))
case ('phase') outputName case ('phase') outputName
crystallite_outputID(o,section) = phase_ID crystallite_outputID(o,c) = phase_ID
case ('texture') outputName case ('texture') outputName
crystallite_outputID(o,section) = texture_ID crystallite_outputID(o,c) = texture_ID
case ('volume') outputName case ('volume') outputName
crystallite_outputID(o,section) = volume_ID crystallite_outputID(o,c) = volume_ID
case ('grainrotationx') outputName case ('grainrotationx') outputName
crystallite_outputID(o,section) = grainrotationx_ID crystallite_outputID(o,c) = grainrotationx_ID
case ('grainrotationy') outputName case ('grainrotationy') outputName
crystallite_outputID(o,section) = grainrotationy_ID crystallite_outputID(o,c) = grainrotationy_ID
case ('grainrotationz') outputName case ('grainrotationz') outputName
crystallite_outputID(o,section) = grainrotationx_ID crystallite_outputID(o,c) = grainrotationx_ID
case ('orientation') outputName case ('orientation') outputName
crystallite_outputID(o,section) = orientation_ID crystallite_outputID(o,c) = orientation_ID
case ('grainrotation') outputName case ('grainrotation') outputName
crystallite_outputID(o,section) = grainrotation_ID crystallite_outputID(o,c) = grainrotation_ID
case ('eulerangles') outputName case ('eulerangles') outputName
crystallite_outputID(o,section) = eulerangles_ID crystallite_outputID(o,c) = eulerangles_ID
case ('defgrad','f') outputName case ('defgrad','f') outputName
crystallite_outputID(o,section) = defgrad_ID crystallite_outputID(o,c) = defgrad_ID
case ('fe') outputName case ('fe') outputName
crystallite_outputID(o,section) = fe_ID crystallite_outputID(o,c) = fe_ID
case ('fp') outputName case ('fp') outputName
crystallite_outputID(o,section) = fp_ID crystallite_outputID(o,c) = fp_ID
case ('fi') outputName case ('fi') outputName
crystallite_outputID(o,section) = fi_ID crystallite_outputID(o,c) = fi_ID
case ('lp') outputName case ('lp') outputName
crystallite_outputID(o,section) = lp_ID crystallite_outputID(o,c) = lp_ID
case ('li') outputName case ('li') outputName
crystallite_outputID(o,section) = li_ID crystallite_outputID(o,c) = li_ID
case ('e') outputName case ('e') outputName
crystallite_outputID(o,section) = e_ID crystallite_outputID(o,c) = e_ID
case ('ee') outputName case ('ee') outputName
crystallite_outputID(o,section) = ee_ID crystallite_outputID(o,c) = ee_ID
case ('p','firstpiola','1stpiola') outputName case ('p','firstpiola','1stpiola') outputName
crystallite_outputID(o,section) = p_ID crystallite_outputID(o,c) = p_ID
case ('s','tstar','secondpiola','2ndpiola') outputName case ('s','tstar','secondpiola','2ndpiola') outputName
crystallite_outputID(o,section) = s_ID crystallite_outputID(o,c) = s_ID
case ('elasmatrix') outputName case ('elasmatrix') outputName
crystallite_outputID(o,section) = elasmatrix_ID crystallite_outputID(o,c) = elasmatrix_ID
case ('neighboringip') outputName case ('neighboringip') outputName
crystallite_outputID(o,section) = neighboringip_ID crystallite_outputID(o,c) = neighboringip_ID
case ('neighboringelement') outputName case ('neighboringelement') outputName
crystallite_outputID(o,section) = neighboringelement_ID crystallite_outputID(o,c) = neighboringelement_ID
case default outputName case default outputName
call IO_error(105_pInt,ext_msg=IO_stringValue(line,chunkPos,2_pInt)//' (Crystallite)') call IO_error(105_pInt,ext_msg=tag//' (Crystallite)')
end select outputName end select outputName
end select enddo
endif
enddo enddo
close(FILEUNIT)
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)
@ -382,14 +357,14 @@ subroutine crystallite_init
crystallite_maxSizePostResults = & crystallite_maxSizePostResults = &
maxval(crystallite_sizePostResults(microstructure_crystallite),microstructure_active) maxval(crystallite_sizePostResults(microstructure_crystallite),microstructure_active)
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
! write description file for crystallite output ! write description file for crystallite output
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)
@ -401,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)
@ -537,7 +514,6 @@ subroutine crystallite_stressAndItsTangent(updateJaco)
use math, only: & use math, only: &
math_inv33, & math_inv33, &
math_identity2nd, & math_identity2nd, &
math_transpose33, &
math_mul33x33, & math_mul33x33, &
math_mul66x6, & math_mul66x6, &
math_Mandel6to33, & math_Mandel6to33, &
@ -616,17 +592,17 @@ subroutine crystallite_stressAndItsTangent(updateJaco)
write(6,'(/,a,i8,1x,a,i8,a,1x,i2,1x,i3)') '<< CRYST >> boundary values at el ip ipc ', & write(6,'(/,a,i8,1x,a,i8,a,1x,i2,1x,i3)') '<< CRYST >> boundary values at el ip ipc ', &
debug_e,'(',mesh_element(1,debug_e), ')',debug_i, debug_g debug_e,'(',mesh_element(1,debug_e), ')',debug_i, debug_g
write(6,'(a,/,3(12x,3(f14.9,1x)/))') '<< CRYST >> F ', & write(6,'(a,/,3(12x,3(f14.9,1x)/))') '<< CRYST >> F ', &
math_transpose33(crystallite_partionedF(1:3,1:3,debug_g,debug_i,debug_e)) transpose(crystallite_partionedF(1:3,1:3,debug_g,debug_i,debug_e))
write(6,'(a,/,3(12x,3(f14.9,1x)/))') '<< CRYST >> F0 ', & write(6,'(a,/,3(12x,3(f14.9,1x)/))') '<< CRYST >> F0 ', &
math_transpose33(crystallite_partionedF0(1:3,1:3,debug_g,debug_i,debug_e)) transpose(crystallite_partionedF0(1:3,1:3,debug_g,debug_i,debug_e))
write(6,'(a,/,3(12x,3(f14.9,1x)/))') '<< CRYST >> Fp0', & write(6,'(a,/,3(12x,3(f14.9,1x)/))') '<< CRYST >> Fp0', &
math_transpose33(crystallite_partionedFp0(1:3,1:3,debug_g,debug_i,debug_e)) transpose(crystallite_partionedFp0(1:3,1:3,debug_g,debug_i,debug_e))
write(6,'(a,/,3(12x,3(f14.9,1x)/))') '<< CRYST >> Fi0', & write(6,'(a,/,3(12x,3(f14.9,1x)/))') '<< CRYST >> Fi0', &
math_transpose33(crystallite_partionedFi0(1:3,1:3,debug_g,debug_i,debug_e)) transpose(crystallite_partionedFi0(1:3,1:3,debug_g,debug_i,debug_e))
write(6,'(a,/,3(12x,3(f14.9,1x)/))') '<< CRYST >> Lp0', & write(6,'(a,/,3(12x,3(f14.9,1x)/))') '<< CRYST >> Lp0', &
math_transpose33(crystallite_partionedLp0(1:3,1:3,debug_g,debug_i,debug_e)) transpose(crystallite_partionedLp0(1:3,1:3,debug_g,debug_i,debug_e))
write(6,'(a,/,3(12x,3(f14.9,1x)/))') '<< CRYST >> Li0', & write(6,'(a,/,3(12x,3(f14.9,1x)/))') '<< CRYST >> Li0', &
math_transpose33(crystallite_partionedLi0(1:3,1:3,debug_g,debug_i,debug_e)) transpose(crystallite_partionedLi0(1:3,1:3,debug_g,debug_i,debug_e))
endif endif
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
@ -1107,15 +1083,15 @@ subroutine crystallite_stressAndItsTangent(updateJaco)
.or. .not. iand(debug_level(debug_crystallite),debug_levelSelective) /= 0_pInt)) then .or. .not. iand(debug_level(debug_crystallite),debug_levelSelective) /= 0_pInt)) then
write(6,'(a,i8,1x,i2,1x,i3)') '<< CRYST >> central solution of cryst_StressAndTangent at el ip ipc ',e,i,c write(6,'(a,i8,1x,i2,1x,i3)') '<< CRYST >> central solution of cryst_StressAndTangent at el ip ipc ',e,i,c
write(6,'(/,a,/,3(12x,3(f12.4,1x)/))') '<< CRYST >> P / MPa', & write(6,'(/,a,/,3(12x,3(f12.4,1x)/))') '<< CRYST >> P / MPa', &
math_transpose33(crystallite_P(1:3,1:3,c,i,e))*1.0e-6_pReal transpose(crystallite_P(1:3,1:3,c,i,e))*1.0e-6_pReal
write(6,'(a,/,3(12x,3(f14.9,1x)/))') '<< CRYST >> Fp', & write(6,'(a,/,3(12x,3(f14.9,1x)/))') '<< CRYST >> Fp', &
math_transpose33(crystallite_Fp(1:3,1:3,c,i,e)) transpose(crystallite_Fp(1:3,1:3,c,i,e))
write(6,'(a,/,3(12x,3(f14.9,1x)/))') '<< CRYST >> Fi', & write(6,'(a,/,3(12x,3(f14.9,1x)/))') '<< CRYST >> Fi', &
math_transpose33(crystallite_Fi(1:3,1:3,c,i,e)) transpose(crystallite_Fi(1:3,1:3,c,i,e))
write(6,'(a,/,3(12x,3(f14.9,1x)/),/)') '<< CRYST >> Lp', & write(6,'(a,/,3(12x,3(f14.9,1x)/),/)') '<< CRYST >> Lp', &
math_transpose33(crystallite_Lp(1:3,1:3,c,i,e)) transpose(crystallite_Lp(1:3,1:3,c,i,e))
write(6,'(a,/,3(12x,3(f14.9,1x)/),/)') '<< CRYST >> Li', & write(6,'(a,/,3(12x,3(f14.9,1x)/),/)') '<< CRYST >> Li', &
math_transpose33(crystallite_Li(1:3,1:3,c,i,e)) transpose(crystallite_Li(1:3,1:3,c,i,e))
flush(6) flush(6)
endif endif
enddo enddo
@ -1166,7 +1142,7 @@ subroutine crystallite_stressAndItsTangent(updateJaco)
crystallite_Fi(1:3,1:3,c,i,e),c,i,e) ! call constitutive law to calculate Lp tangent in lattice configuration crystallite_Fi(1:3,1:3,c,i,e),c,i,e) ! call constitutive law to calculate Lp tangent in lattice configuration
dLpdS = math_mul3333xx3333(dLpdFi,dFidS) + dLpdS dLpdS = math_mul3333xx3333(dLpdFi,dFidS) + dLpdS
temp_33 = math_transpose33(math_mul33x33(crystallite_invFp(1:3,1:3,c,i,e), & temp_33 = transpose(math_mul33x33(crystallite_invFp(1:3,1:3,c,i,e), &
crystallite_invFi(1:3,1:3,c,i,e))) crystallite_invFi(1:3,1:3,c,i,e)))
rhs_3333 = 0.0_pReal rhs_3333 = 0.0_pReal
forall(p=1_pInt:3_pInt, o=1_pInt:3_pInt) & forall(p=1_pInt:3_pInt, o=1_pInt:3_pInt) &
@ -1208,12 +1184,12 @@ subroutine crystallite_stressAndItsTangent(updateJaco)
crystallite_dPdF(1:3,1:3,1:3,1:3,c,i,e) = 0.0_pReal crystallite_dPdF(1:3,1:3,1:3,1:3,c,i,e) = 0.0_pReal
temp_33 = math_mul33x33(crystallite_invFp(1:3,1:3,c,i,e), & temp_33 = math_mul33x33(crystallite_invFp(1:3,1:3,c,i,e), &
math_mul33x33(math_Mandel6to33(crystallite_Tstar_v(1:6,c,i,e)), & math_mul33x33(math_Mandel6to33(crystallite_Tstar_v(1:6,c,i,e)), &
math_transpose33(crystallite_invFp(1:3,1:3,c,i,e)))) transpose(crystallite_invFp(1:3,1:3,c,i,e))))
forall(p=1_pInt:3_pInt) & forall(p=1_pInt:3_pInt) &
crystallite_dPdF(p,1:3,p,1:3,c,i,e) = math_transpose33(temp_33) crystallite_dPdF(p,1:3,p,1:3,c,i,e) = transpose(temp_33)
temp_33 = math_mul33x33(math_Mandel6to33(crystallite_Tstar_v(1:6,c,i,e)), & temp_33 = math_mul33x33(math_Mandel6to33(crystallite_Tstar_v(1:6,c,i,e)), &
math_transpose33(crystallite_invFp(1:3,1:3,c,i,e))) transpose(crystallite_invFp(1:3,1:3,c,i,e)))
forall(p=1_pInt:3_pInt, o=1_pInt:3_pInt) & forall(p=1_pInt:3_pInt, o=1_pInt:3_pInt) &
crystallite_dPdF(1:3,1:3,p,o,c,i,e) = crystallite_dPdF(1:3,1:3,p,o,c,i,e) + & crystallite_dPdF(1:3,1:3,p,o,c,i,e) = crystallite_dPdF(1:3,1:3,p,o,c,i,e) + &
math_mul33x33(math_mul33x33(crystallite_subF(1:3,1:3,c,i,e),dFpinvdF(1:3,1:3,p,o)),temp_33) math_mul33x33(math_mul33x33(crystallite_subF(1:3,1:3,c,i,e),dFpinvdF(1:3,1:3,p,o)),temp_33)
@ -1223,14 +1199,14 @@ subroutine crystallite_stressAndItsTangent(updateJaco)
forall(p=1_pInt:3_pInt, o=1_pInt:3_pInt) & forall(p=1_pInt:3_pInt, o=1_pInt:3_pInt) &
crystallite_dPdF(1:3,1:3,p,o,c,i,e) = crystallite_dPdF(1:3,1:3,p,o,c,i,e) + & crystallite_dPdF(1:3,1:3,p,o,c,i,e) = crystallite_dPdF(1:3,1:3,p,o,c,i,e) + &
math_mul33x33(math_mul33x33(temp_33,dSdF(1:3,1:3,p,o)), & math_mul33x33(math_mul33x33(temp_33,dSdF(1:3,1:3,p,o)), &
math_transpose33(crystallite_invFp(1:3,1:3,c,i,e))) transpose(crystallite_invFp(1:3,1:3,c,i,e)))
temp_33 = math_mul33x33(math_mul33x33(crystallite_subF(1:3,1:3,c,i,e), & temp_33 = math_mul33x33(math_mul33x33(crystallite_subF(1:3,1:3,c,i,e), &
crystallite_invFp(1:3,1:3,c,i,e)), & crystallite_invFp(1:3,1:3,c,i,e)), &
math_Mandel6to33(crystallite_Tstar_v(1:6,c,i,e))) math_Mandel6to33(crystallite_Tstar_v(1:6,c,i,e)))
forall(p=1_pInt:3_pInt, o=1_pInt:3_pInt) & forall(p=1_pInt:3_pInt, o=1_pInt:3_pInt) &
crystallite_dPdF(1:3,1:3,p,o,c,i,e) = crystallite_dPdF(1:3,1:3,p,o,c,i,e) + & crystallite_dPdF(1:3,1:3,p,o,c,i,e) = crystallite_dPdF(1:3,1:3,p,o,c,i,e) + &
math_mul33x33(temp_33,math_transpose33(dFpinvdF(1:3,1:3,p,o))) math_mul33x33(temp_33,transpose(dFpinvdF(1:3,1:3,p,o)))
enddo; enddo enddo; enddo
enddo elementLooping6 enddo elementLooping6
@ -1272,8 +1248,9 @@ subroutine crystallite_integrateStateRK4()
plasticState, & plasticState, &
sourceState, & sourceState, &
phase_Nsources, & phase_Nsources, &
material_Nphase, &
phaseAt, phasememberAt phaseAt, phasememberAt
use config, only: &
material_Nphase
use constitutive, only: & use constitutive, only: &
constitutive_collectDotState, & constitutive_collectDotState, &
constitutive_microstructure constitutive_microstructure
@ -3195,7 +3172,6 @@ function crystallite_push33ToRef(ipc,ip,el, tensor33)
use math, only: & use math, only: &
math_mul33x33, & math_mul33x33, &
math_inv33, & math_inv33, &
math_transpose33, &
math_EulerToR math_EulerToR
use material, only: & use material, only: &
material_EulerAngles material_EulerAngles
@ -3210,8 +3186,8 @@ function crystallite_push33ToRef(ipc,ip,el, tensor33)
ipc ! grain index ipc ! grain index
T = math_mul33x33(math_EulerToR(material_EulerAngles(1:3,ipc,ip,el)), & T = math_mul33x33(math_EulerToR(material_EulerAngles(1:3,ipc,ip,el)), &
math_transpose33(math_inv33(crystallite_subF(1:3,1:3,ipc,ip,el)))) transpose(math_inv33(crystallite_subF(1:3,1:3,ipc,ip,el))))
crystallite_push33ToRef = math_mul33x33(math_transpose33(T),math_mul33x33(tensor33,T)) crystallite_push33ToRef = math_mul33x33(transpose(T),math_mul33x33(tensor33,T))
end function crystallite_push33ToRef end function crystallite_push33ToRef
@ -3260,7 +3236,6 @@ logical function crystallite_integrateStress(&
math_mul3333xx3333, & math_mul3333xx3333, &
math_mul66x6, & math_mul66x6, &
math_mul99x99, & math_mul99x99, &
math_transpose33, &
math_inv33, & math_inv33, &
math_invert, & math_invert, &
math_det33, & math_det33, &
@ -3386,7 +3361,7 @@ logical function crystallite_integrateStress(&
write(6,'(a,i8,1x,a,i8,a,1x,i2,1x,i3)') '<< CRYST >> integrateStress failed on inversion of Fp_current at el (elFE) ip ipc ',& write(6,'(a,i8,1x,a,i8,a,1x,i2,1x,i3)') '<< CRYST >> integrateStress failed on inversion of Fp_current at el (elFE) ip ipc ',&
el,'(',mesh_element(1,el),')',ip,ipc el,'(',mesh_element(1,el),')',ip,ipc
if (iand(debug_level(debug_crystallite), debug_levelExtensive) > 0_pInt) & if (iand(debug_level(debug_crystallite), debug_levelExtensive) > 0_pInt) &
write(6,'(/,a,/,3(12x,3(f12.7,1x)/))') '<< CRYST >> Fp_current',math_transpose33(Fp_current(1:3,1:3)) write(6,'(/,a,/,3(12x,3(f12.7,1x)/))') '<< CRYST >> Fp_current',transpose(Fp_current(1:3,1:3))
endif endif
#endif #endif
return return
@ -3402,7 +3377,7 @@ logical function crystallite_integrateStress(&
write(6,'(a,i8,1x,a,i8,a,1x,i2,1x,i3)') '<< CRYST >> integrateStress failed on inversion of Fi_current at el (elFE) ip ipc ',& write(6,'(a,i8,1x,a,i8,a,1x,i2,1x,i3)') '<< CRYST >> integrateStress failed on inversion of Fi_current at el (elFE) ip ipc ',&
el,'(',mesh_element(1,el),')',ip,ipc el,'(',mesh_element(1,el),')',ip,ipc
if (iand(debug_level(debug_crystallite), debug_levelExtensive) > 0_pInt) & if (iand(debug_level(debug_crystallite), debug_levelExtensive) > 0_pInt) &
write(6,'(/,a,/,3(12x,3(f12.7,1x)/))') '<< CRYST >> Fp_current',math_transpose33(Fi_current(1:3,1:3)) write(6,'(/,a,/,3(12x,3(f12.7,1x)/))') '<< CRYST >> Fp_current',transpose(Fi_current(1:3,1:3))
endif endif
#endif #endif
return return
@ -3465,9 +3440,9 @@ logical function crystallite_integrateStress(&
.and. ((el == debug_e .and. ip == debug_i .and. ipc == debug_g) & .and. ((el == debug_e .and. ip == debug_i .and. ipc == debug_g) &
.or. .not. iand(debug_level(debug_crystallite), debug_levelSelective) /= 0_pInt)) then .or. .not. iand(debug_level(debug_crystallite), debug_levelSelective) /= 0_pInt)) then
write(6,'(a,i3,/)') '<< CRYST >> stress iteration ', NiterationStressLp write(6,'(a,i3,/)') '<< CRYST >> stress iteration ', NiterationStressLp
write(6,'(a,/,3(12x,3(e20.10,1x)/))') '<< CRYST >> Lpguess', math_transpose33(Lpguess) write(6,'(a,/,3(12x,3(e20.10,1x)/))') '<< CRYST >> Lpguess', transpose(Lpguess)
write(6,'(a,/,3(12x,3(e20.10,1x)/))') '<< CRYST >> Fi', math_transpose33(Fi_new) write(6,'(a,/,3(12x,3(e20.10,1x)/))') '<< CRYST >> Fi', transpose(Fi_new)
write(6,'(a,/,3(12x,3(e20.10,1x)/))') '<< CRYST >> Fe', math_transpose33(Fe) write(6,'(a,/,3(12x,3(e20.10,1x)/))') '<< CRYST >> Fe', transpose(Fe)
write(6,'(a,/,6(e20.10,1x))') '<< CRYST >> Tstar', Tstar_v write(6,'(a,/,6(e20.10,1x))') '<< CRYST >> Tstar', Tstar_v
endif endif
#endif #endif
@ -3488,7 +3463,7 @@ logical function crystallite_integrateStress(&
if (iand(debug_level(debug_crystallite), debug_levelExtensive) /= 0_pInt & if (iand(debug_level(debug_crystallite), debug_levelExtensive) /= 0_pInt &
.and. ((el == debug_e .and. ip == debug_i .and. ipc == debug_g) & .and. ((el == debug_e .and. ip == debug_i .and. ipc == debug_g) &
.or. .not. iand(debug_level(debug_crystallite), debug_levelSelective) /= 0_pInt)) then .or. .not. iand(debug_level(debug_crystallite), debug_levelSelective) /= 0_pInt)) then
write(6,'(a,/,3(12x,3(e20.10,1x)/))') '<< CRYST >> Lp_constitutive', math_transpose33(Lp_constitutive) write(6,'(a,/,3(12x,3(e20.10,1x)/))') '<< CRYST >> Lp_constitutive', transpose(Lp_constitutive)
endif endif
#endif #endif
@ -3534,7 +3509,7 @@ logical function crystallite_integrateStress(&
if (mod(jacoCounterLp, iJacoLpresiduum) == 0_pInt) then if (mod(jacoCounterLp, iJacoLpresiduum) == 0_pInt) then
dFe_dLp3333 = 0.0_pReal dFe_dLp3333 = 0.0_pReal
forall(o=1_pInt:3_pInt,p=1_pInt:3_pInt) & forall(o=1_pInt:3_pInt,p=1_pInt:3_pInt) &
dFe_dLp3333(o,1:3,p,1:3) = A(o,p)*math_transpose33(invFi_new) ! dFe_dLp(i,j,k,l) = -dt * A(i,k) invFi(l,j) dFe_dLp3333(o,1:3,p,1:3) = A(o,p)*transpose(invFi_new) ! dFe_dLp(i,j,k,l) = -dt * A(i,k) invFi(l,j)
dFe_dLp3333 = - dt * dFe_dLp3333 dFe_dLp3333 = - dt * dFe_dLp3333
dRLp_dLp = math_identity2nd(9_pInt) & dRLp_dLp = math_identity2nd(9_pInt) &
- math_Plain3333to99(math_mul3333xx3333(math_mul3333xx3333(dLp_dT3333,dT_dFe3333),dFe_dLp3333)) - math_Plain3333to99(math_mul3333xx3333(math_mul3333xx3333(dLp_dT3333,dT_dFe3333),dFe_dLp3333))
@ -3564,10 +3539,10 @@ logical function crystallite_integrateStress(&
write(6,'(a,/,9(12x,9(e15.3,1x)/))') '<< CRYST >> dFe_dLp',transpose(math_Plain3333to99(dFe_dLp3333)) write(6,'(a,/,9(12x,9(e15.3,1x)/))') '<< CRYST >> dFe_dLp',transpose(math_Plain3333to99(dFe_dLp3333))
write(6,'(a,/,9(12x,9(e15.3,1x)/))') '<< CRYST >> dT_dFe_constitutive',transpose(math_Plain3333to99(dT_dFe3333)) write(6,'(a,/,9(12x,9(e15.3,1x)/))') '<< CRYST >> dT_dFe_constitutive',transpose(math_Plain3333to99(dT_dFe3333))
write(6,'(a,/,9(12x,9(e15.3,1x)/))') '<< CRYST >> dLp_dT_constitutive',transpose(math_Plain3333to99(dLp_dT3333)) write(6,'(a,/,9(12x,9(e15.3,1x)/))') '<< CRYST >> dLp_dT_constitutive',transpose(math_Plain3333to99(dLp_dT3333))
write(6,'(a,/,3(12x,3(e20.7,1x)/))') '<< CRYST >> A',math_transpose33(A) write(6,'(a,/,3(12x,3(e20.7,1x)/))') '<< CRYST >> A',transpose(A)
write(6,'(a,/,3(12x,3(e20.7,1x)/))') '<< CRYST >> B',math_transpose33(B) write(6,'(a,/,3(12x,3(e20.7,1x)/))') '<< CRYST >> B',transpose(B)
write(6,'(a,/,3(12x,3(e20.7,1x)/))') '<< CRYST >> Lp_constitutive',math_transpose33(Lp_constitutive) write(6,'(a,/,3(12x,3(e20.7,1x)/))') '<< CRYST >> Lp_constitutive',transpose(Lp_constitutive)
write(6,'(a,/,3(12x,3(e20.7,1x)/))') '<< CRYST >> Lpguess',math_transpose33(Lpguess) write(6,'(a,/,3(12x,3(e20.7,1x)/))') '<< CRYST >> Lpguess',transpose(Lpguess)
endif endif
endif endif
#endif #endif
@ -3597,8 +3572,8 @@ logical function crystallite_integrateStress(&
if (iand(debug_level(debug_crystallite), debug_levelExtensive) /= 0_pInt & if (iand(debug_level(debug_crystallite), debug_levelExtensive) /= 0_pInt &
.and. ((el == debug_e .and. ip == debug_i .and. ipc == debug_g) & .and. ((el == debug_e .and. ip == debug_i .and. ipc == debug_g) &
.or. .not. iand(debug_level(debug_crystallite), debug_levelSelective) /= 0_pInt)) then .or. .not. iand(debug_level(debug_crystallite), debug_levelSelective) /= 0_pInt)) then
write(6,'(a,/,3(12x,3(e20.7,1x)/))') '<< CRYST >> Li_constitutive', math_transpose33(Li_constitutive) write(6,'(a,/,3(12x,3(e20.7,1x)/))') '<< CRYST >> Li_constitutive', transpose(Li_constitutive)
write(6,'(a,/,3(12x,3(e20.7,1x)/))') '<< CRYST >> Liguess', math_transpose33(Liguess) write(6,'(a,/,3(12x,3(e20.7,1x)/))') '<< CRYST >> Liguess', transpose(Liguess)
endif endif
#endif #endif
!* update current residuum and check for convergence of loop !* update current residuum and check for convergence of loop
@ -3653,8 +3628,8 @@ logical function crystallite_integrateStress(&
write(6,'(a,/,9(12x,9(e15.3,1x)/))') '<< CRYST >> dFe_dLi',transpose(math_Plain3333to99(dFe_dLi3333)) write(6,'(a,/,9(12x,9(e15.3,1x)/))') '<< CRYST >> dFe_dLi',transpose(math_Plain3333to99(dFe_dLi3333))
write(6,'(a,/,9(12x,9(e15.3,1x)/))') '<< CRYST >> dT_dFi_constitutive',transpose(math_Plain3333to99(dT_dFi3333)) write(6,'(a,/,9(12x,9(e15.3,1x)/))') '<< CRYST >> dT_dFi_constitutive',transpose(math_Plain3333to99(dT_dFi3333))
write(6,'(a,/,9(12x,9(e15.3,1x)/))') '<< CRYST >> dLi_dT_constitutive',transpose(math_Plain3333to99(dLi_dT3333)) write(6,'(a,/,9(12x,9(e15.3,1x)/))') '<< CRYST >> dLi_dT_constitutive',transpose(math_Plain3333to99(dLi_dT3333))
write(6,'(a,/,3(12x,3(e20.7,1x)/))') '<< CRYST >> Li_constitutive',math_transpose33(Li_constitutive) write(6,'(a,/,3(12x,3(e20.7,1x)/))') '<< CRYST >> Li_constitutive',transpose(Li_constitutive)
write(6,'(a,/,3(12x,3(e20.7,1x)/))') '<< CRYST >> Liguess',math_transpose33(Liguess) write(6,'(a,/,3(12x,3(e20.7,1x)/))') '<< CRYST >> Liguess',transpose(Liguess)
endif endif
endif endif
#endif #endif
@ -3688,7 +3663,7 @@ logical function crystallite_integrateStress(&
if (iand(debug_level(debug_crystallite), debug_levelExtensive) /= 0_pInt & if (iand(debug_level(debug_crystallite), debug_levelExtensive) /= 0_pInt &
.and. ((el == debug_e .and. ip == debug_i .and. ipc == debug_g) & .and. ((el == debug_e .and. ip == debug_i .and. ipc == debug_g) &
.or. .not. iand(debug_level(debug_crystallite), debug_levelSelective) /= 0_pInt)) & .or. .not. iand(debug_level(debug_crystallite), debug_levelSelective) /= 0_pInt)) &
write(6,'(/,a,/,3(12x,3(f12.7,1x)/))') '<< CRYST >> invFp_new',math_transpose33(invFp_new) write(6,'(/,a,/,3(12x,3(f12.7,1x)/))') '<< CRYST >> invFp_new',transpose(invFp_new)
endif endif
#endif #endif
return return
@ -3699,7 +3674,7 @@ logical function crystallite_integrateStress(&
crystallite_P(1:3,1:3,ipc,ip,el) = math_mul33x33(math_mul33x33(Fg_new,invFp_new), & crystallite_P(1:3,1:3,ipc,ip,el) = math_mul33x33(math_mul33x33(Fg_new,invFp_new), &
math_mul33x33(math_Mandel6to33(Tstar_v), & math_mul33x33(math_Mandel6to33(Tstar_v), &
math_transpose33(invFp_new))) transpose(invFp_new)))
!* store local values in global variables !* store local values in global variables
@ -3719,13 +3694,13 @@ logical function crystallite_integrateStress(&
if (iand(debug_level(debug_crystallite),debug_levelExtensive) /= 0_pInt & if (iand(debug_level(debug_crystallite),debug_levelExtensive) /= 0_pInt &
.and. ((el == debug_e .and. ip == debug_i .and. ipc == debug_g) & .and. ((el == debug_e .and. ip == debug_i .and. ipc == debug_g) &
.or. .not. iand(debug_level(debug_crystallite), debug_levelSelective) /= 0_pInt)) then .or. .not. iand(debug_level(debug_crystallite), debug_levelSelective) /= 0_pInt)) then
write(6,'(a,/,3(12x,3(f12.7,1x)/))') '<< CRYST >> P / MPa',math_transpose33(crystallite_P(1:3,1:3,ipc,ip,el))*1.0e-6_pReal write(6,'(a,/,3(12x,3(f12.7,1x)/))') '<< CRYST >> P / MPa',transpose(crystallite_P(1:3,1:3,ipc,ip,el))*1.0e-6_pReal
write(6,'(a,/,3(12x,3(f12.7,1x)/))') '<< CRYST >> Cauchy / MPa', & write(6,'(a,/,3(12x,3(f12.7,1x)/))') '<< CRYST >> Cauchy / MPa', &
math_mul33x33(crystallite_P(1:3,1:3,ipc,ip,el), math_transpose33(Fg_new)) * 1.0e-6_pReal / math_det33(Fg_new) math_mul33x33(crystallite_P(1:3,1:3,ipc,ip,el), transpose(Fg_new)) * 1.0e-6_pReal / math_det33(Fg_new)
write(6,'(a,/,3(12x,3(f12.7,1x)/))') '<< CRYST >> Fe Lp Fe^-1', & write(6,'(a,/,3(12x,3(f12.7,1x)/))') '<< CRYST >> Fe Lp Fe^-1', &
math_transpose33(math_mul33x33(Fe_new, math_mul33x33(crystallite_Lp(1:3,1:3,ipc,ip,el), math_inv33(Fe_new)))) ! transpose to get correct print out order transpose(math_mul33x33(Fe_new, math_mul33x33(crystallite_Lp(1:3,1:3,ipc,ip,el), math_inv33(Fe_new)))) ! transpose to get correct print out order
write(6,'(a,/,3(12x,3(f12.7,1x)/))') '<< CRYST >> Fp',math_transpose33(crystallite_Fp(1:3,1:3,ipc,ip,el)) write(6,'(a,/,3(12x,3(f12.7,1x)/))') '<< CRYST >> Fp',transpose(crystallite_Fp(1:3,1:3,ipc,ip,el))
write(6,'(a,/,3(12x,3(f12.7,1x)/))') '<< CRYST >> Fi',math_transpose33(crystallite_Fi(1:3,1:3,ipc,ip,el)) write(6,'(a,/,3(12x,3(f12.7,1x)/))') '<< CRYST >> Fi',transpose(crystallite_Fi(1:3,1:3,ipc,ip,el))
endif endif
#endif #endif
@ -3842,7 +3817,6 @@ function crystallite_postResults(ipc, ip, el)
math_qToEuler, & math_qToEuler, &
math_qToEulerAxisAngle, & math_qToEulerAxisAngle, &
math_mul33x33, & math_mul33x33, &
math_transpose33, &
math_det33, & math_det33, &
math_I3, & math_I3, &
inDeg, & inDeg, &
@ -3945,41 +3919,41 @@ function crystallite_postResults(ipc, ip, el)
case (defgrad_ID) case (defgrad_ID)
mySize = 9_pInt mySize = 9_pInt
crystallite_postResults(c+1:c+mySize) = & crystallite_postResults(c+1:c+mySize) = &
reshape(math_transpose33(crystallite_partionedF(1:3,1:3,ipc,ip,el)),[mySize]) reshape(transpose(crystallite_partionedF(1:3,1:3,ipc,ip,el)),[mySize])
case (e_ID) case (e_ID)
mySize = 9_pInt mySize = 9_pInt
crystallite_postResults(c+1:c+mySize) = 0.5_pReal * reshape((math_mul33x33( & crystallite_postResults(c+1:c+mySize) = 0.5_pReal * reshape((math_mul33x33( &
math_transpose33(crystallite_partionedF(1:3,1:3,ipc,ip,el)), & transpose(crystallite_partionedF(1:3,1:3,ipc,ip,el)), &
crystallite_partionedF(1:3,1:3,ipc,ip,el)) - math_I3),[mySize]) crystallite_partionedF(1:3,1:3,ipc,ip,el)) - math_I3),[mySize])
case (fe_ID) case (fe_ID)
mySize = 9_pInt mySize = 9_pInt
crystallite_postResults(c+1:c+mySize) = & crystallite_postResults(c+1:c+mySize) = &
reshape(math_transpose33(crystallite_Fe(1:3,1:3,ipc,ip,el)),[mySize]) reshape(transpose(crystallite_Fe(1:3,1:3,ipc,ip,el)),[mySize])
case (ee_ID) case (ee_ID)
Ee = 0.5_pReal *(math_mul33x33(math_transpose33(crystallite_Fe(1:3,1:3,ipc,ip,el)), & Ee = 0.5_pReal *(math_mul33x33(transpose(crystallite_Fe(1:3,1:3,ipc,ip,el)), &
crystallite_Fe(1:3,1:3,ipc,ip,el)) - math_I3) crystallite_Fe(1:3,1:3,ipc,ip,el)) - math_I3)
mySize = 9_pInt mySize = 9_pInt
crystallite_postResults(c+1:c+mySize) = reshape(Ee,[mySize]) crystallite_postResults(c+1:c+mySize) = reshape(Ee,[mySize])
case (fp_ID) case (fp_ID)
mySize = 9_pInt mySize = 9_pInt
crystallite_postResults(c+1:c+mySize) = & crystallite_postResults(c+1:c+mySize) = &
reshape(math_transpose33(crystallite_Fp(1:3,1:3,ipc,ip,el)),[mySize]) reshape(transpose(crystallite_Fp(1:3,1:3,ipc,ip,el)),[mySize])
case (fi_ID) case (fi_ID)
mySize = 9_pInt mySize = 9_pInt
crystallite_postResults(c+1:c+mySize) = & crystallite_postResults(c+1:c+mySize) = &
reshape(math_transpose33(crystallite_Fi(1:3,1:3,ipc,ip,el)),[mySize]) reshape(transpose(crystallite_Fi(1:3,1:3,ipc,ip,el)),[mySize])
case (lp_ID) case (lp_ID)
mySize = 9_pInt mySize = 9_pInt
crystallite_postResults(c+1:c+mySize) = & crystallite_postResults(c+1:c+mySize) = &
reshape(math_transpose33(crystallite_Lp(1:3,1:3,ipc,ip,el)),[mySize]) reshape(transpose(crystallite_Lp(1:3,1:3,ipc,ip,el)),[mySize])
case (li_ID) case (li_ID)
mySize = 9_pInt mySize = 9_pInt
crystallite_postResults(c+1:c+mySize) = & crystallite_postResults(c+1:c+mySize) = &
reshape(math_transpose33(crystallite_Li(1:3,1:3,ipc,ip,el)),[mySize]) reshape(transpose(crystallite_Li(1:3,1:3,ipc,ip,el)),[mySize])
case (p_ID) case (p_ID)
mySize = 9_pInt mySize = 9_pInt
crystallite_postResults(c+1:c+mySize) = & crystallite_postResults(c+1:c+mySize) = &
reshape(math_transpose33(crystallite_P(1:3,1:3,ipc,ip,el)),[mySize]) reshape(transpose(crystallite_P(1:3,1:3,ipc,ip,el)),[mySize])
case (s_ID) case (s_ID)
mySize = 9_pInt mySize = 9_pInt
crystallite_postResults(c+1:c+mySize) = & crystallite_postResults(c+1:c+mySize) = &

View File

@ -70,7 +70,8 @@ subroutine damage_local_init(fileUnit)
damageState, & damageState, &
damageMapping, & damageMapping, &
damage, & damage, &
damage_initialPhi, & damage_initialPhi
use config, only: &
material_partHomogenization material_partHomogenization
implicit none implicit none

View File

@ -26,6 +26,7 @@ subroutine damage_none_init()
use IO, only: & use IO, only: &
IO_timeStamp IO_timeStamp
use material use material
use config
implicit none implicit none
integer(pInt) :: & integer(pInt) :: &

View File

@ -75,7 +75,8 @@ subroutine damage_nonlocal_init(fileUnit)
damageState, & damageState, &
damageMapping, & damageMapping, &
damage, & damage, &
damage_initialPhi, & damage_initialPhi
use config, only: &
material_partHomogenization material_partHomogenization
implicit none implicit none

View File

@ -100,6 +100,12 @@ 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 homogenization_none use homogenization_none
use homogenization_isostrain use homogenization_isostrain
@ -196,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
@ -369,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)
@ -394,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)
@ -443,11 +451,9 @@ subroutine homogenization_init
allocate(materialpoint_results(materialpoint_sizeResults,mesh_maxNips,mesh_NcpElems)) allocate(materialpoint_results(materialpoint_sizeResults,mesh_maxNips,mesh_NcpElems))
#endif #endif
mainProcess: if (worldrank == 0) then write(6,'(/,a)') ' <<<+- homogenization init -+>>>'
write(6,'(/,a)') ' <<<+- homogenization 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"
endif mainProcess
if (iand(debug_level(debug_homogenization), debug_levelBasic) /= 0_pInt) then if (iand(debug_level(debug_homogenization), debug_levelBasic) /= 0_pInt) then
#ifdef TODO #ifdef TODO
@ -475,7 +481,7 @@ subroutine homogenization_init
flush(6) flush(6)
if (debug_g < 1 .or. debug_g > homogenization_Ngrains(mesh_element(3,debug_e))) & if (debug_g < 1 .or. debug_g > homogenization_Ngrains(mesh_element(3,debug_e))) &
call IO_error(602_pInt,ext_msg='component (grain)', el=debug_e, g=debug_g) call IO_error(602_pInt,ext_msg='constituent', el=debug_e, g=debug_g)
end subroutine homogenization_init end subroutine homogenization_init

View File

@ -100,6 +100,7 @@ subroutine homogenization_RGC_init(fileUnit)
FE_geomtype FE_geomtype
use IO use IO
use material use material
use config
implicit none implicit none
integer(pInt), intent(in) :: fileUnit !< file pointer to material configuration integer(pInt), intent(in) :: fileUnit !< file pointer to material configuration

View File

@ -62,6 +62,7 @@ subroutine homogenization_isostrain_init(fileUnit)
debug_levelBasic debug_levelBasic
use IO use IO
use material use material
use config
implicit none implicit none
integer(pInt), intent(in) :: fileUnit integer(pInt), intent(in) :: fileUnit

View File

@ -29,6 +29,7 @@ subroutine homogenization_none_init()
use IO, only: & use IO, only: &
IO_timeStamp IO_timeStamp
use material use material
use config
implicit none implicit none
integer(pInt) :: & integer(pInt) :: &

View File

@ -81,7 +81,8 @@ subroutine hydrogenflux_cahnhilliard_init(fileUnit)
hydrogenfluxMapping, & hydrogenfluxMapping, &
hydrogenConc, & hydrogenConc, &
hydrogenConcRate, & hydrogenConcRate, &
hydrogenflux_initialCh, & hydrogenflux_initialCh
use config, only: &
material_partHomogenization, & material_partHomogenization, &
material_partPhase material_partPhase

View File

@ -27,6 +27,7 @@ subroutine hydrogenflux_isoconc_init()
use IO, only: & use IO, only: &
IO_timeStamp IO_timeStamp
use material use material
use config
implicit none implicit none
integer(pInt) :: & integer(pInt) :: &

View File

@ -78,7 +78,8 @@ subroutine kinematics_cleavage_opening_init(fileUnit)
phase_Nkinematics, & phase_Nkinematics, &
phase_Noutput, & phase_Noutput, &
KINEMATICS_cleavage_opening_label, & KINEMATICS_cleavage_opening_label, &
KINEMATICS_cleavage_opening_ID, & KINEMATICS_cleavage_opening_ID
use config, only: &
material_Nphase, & material_Nphase, &
MATERIAL_partPhase MATERIAL_partPhase
use lattice, only: & use lattice, only: &

View File

@ -68,7 +68,8 @@ subroutine kinematics_hydrogen_strain_init(fileUnit)
phase_Nkinematics, & phase_Nkinematics, &
phase_Noutput, & phase_Noutput, &
KINEMATICS_hydrogen_strain_label, & KINEMATICS_hydrogen_strain_label, &
KINEMATICS_hydrogen_strain_ID, & KINEMATICS_hydrogen_strain_ID
use config, only: &
material_Nphase, & material_Nphase, &
MATERIAL_partPhase MATERIAL_partPhase

View File

@ -78,7 +78,8 @@ subroutine kinematics_slipplane_opening_init(fileUnit)
phase_Nkinematics, & phase_Nkinematics, &
phase_Noutput, & phase_Noutput, &
KINEMATICS_slipplane_opening_label, & KINEMATICS_slipplane_opening_label, &
KINEMATICS_slipplane_opening_ID, & KINEMATICS_slipplane_opening_ID
use config, only: &
material_Nphase, & material_Nphase, &
MATERIAL_partPhase MATERIAL_partPhase
use lattice, only: & use lattice, only: &

View File

@ -68,7 +68,8 @@ subroutine kinematics_thermal_expansion_init(fileUnit)
phase_Nkinematics, & phase_Nkinematics, &
phase_Noutput, & phase_Noutput, &
KINEMATICS_thermal_expansion_label, & KINEMATICS_thermal_expansion_label, &
KINEMATICS_thermal_expansion_ID, & KINEMATICS_thermal_expansion_ID
use config, only: &
material_Nphase, & material_Nphase, &
MATERIAL_partPhase MATERIAL_partPhase

View File

@ -68,7 +68,8 @@ subroutine kinematics_vacancy_strain_init(fileUnit)
phase_Nkinematics, & phase_Nkinematics, &
phase_Noutput, & phase_Noutput, &
KINEMATICS_vacancy_strain_label, & KINEMATICS_vacancy_strain_label, &
KINEMATICS_vacancy_strain_ID, & KINEMATICS_vacancy_strain_ID
use config, only: &
material_Nphase, & material_Nphase, &
MATERIAL_partPhase MATERIAL_partPhase

View File

@ -1263,7 +1263,7 @@ subroutine lattice_init
IO_stringPos, & IO_stringPos, &
IO_stringValue, & IO_stringValue, &
IO_floatValue IO_floatValue
use material, only: & use config, only: &
material_configfile, & material_configfile, &
material_localFileExt, & material_localFileExt, &
material_partPhase material_partPhase

File diff suppressed because it is too large Load Diff

View File

@ -223,7 +223,6 @@ end subroutine math_init
!> @brief check correctness of (some) math functions !> @brief check correctness of (some) math functions
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
subroutine math_check subroutine math_check
use prec, only: tol_math_check use prec, only: tol_math_check
use IO, only: IO_error use IO, only: IO_error

View File

@ -151,8 +151,9 @@ subroutine plastic_disloUCLA_init(fileUnit)
phase_Noutput, & phase_Noutput, &
PLASTICITY_DISLOUCLA_label, & PLASTICITY_DISLOUCLA_label, &
PLASTICITY_DISLOUCLA_ID, & PLASTICITY_DISLOUCLA_ID, &
material_phase, & material_phase, &
plasticState, & plasticState
use config, only: &
MATERIAL_partPhase MATERIAL_partPhase
use lattice use lattice
use numerics,only: & use numerics,only: &

View File

@ -239,7 +239,8 @@ subroutine plastic_dislotwin_init(fileUnit)
PLASTICITY_DISLOTWIN_label, & PLASTICITY_DISLOTWIN_label, &
PLASTICITY_DISLOTWIN_ID, & PLASTICITY_DISLOTWIN_ID, &
material_phase, & material_phase, &
plasticState, & plasticState
use config, only: &
MATERIAL_partPhase MATERIAL_partPhase
use lattice use lattice
use numerics,only: & use numerics,only: &

View File

@ -13,15 +13,10 @@ module plastic_isotropic
implicit none implicit none
private private
integer(pInt), dimension(:), allocatable, public, protected :: &
plastic_isotropic_sizePostResults !< cumulative size of post results
integer(pInt), dimension(:,:), allocatable, target, public :: & integer(pInt), dimension(:,:), allocatable, target, public :: &
plastic_isotropic_sizePostResult !< size of each post result output plastic_isotropic_sizePostResult !< size of each post result output
character(len=64), dimension(:,:), allocatable, target, public :: & character(len=64), dimension(:,:), allocatable, target, public :: &
plastic_isotropic_output !< name of each post result output plastic_isotropic_output !< name of each post result output
integer(pInt), dimension(:), allocatable, target, public :: & integer(pInt), dimension(:), allocatable, target, public :: &
plastic_isotropic_Noutput !< number of outputs per instance plastic_isotropic_Noutput !< number of outputs per instance
@ -40,17 +35,17 @@ module plastic_isotropic
gdot0, & gdot0, &
n, & n, &
h0, & h0, &
h0_slopeLnRate = 0.0_pReal, & h0_slopeLnRate, &
tausat, & tausat, &
a, & a, &
aTolFlowstress = 1.0_pReal, & aTolFlowstress, &
aTolShear = 1.0e-6_pReal, & aTolShear, &
tausat_SinhFitA= 0.0_pReal, & tausat_SinhFitA, &
tausat_SinhFitB= 0.0_pReal, & tausat_SinhFitB, &
tausat_SinhFitC= 0.0_pReal, & tausat_SinhFitC, &
tausat_SinhFitD= 0.0_pReal tausat_SinhFitD
logical :: & logical :: &
dilatation = .false. dilatation
end type end type
type(tParameters), dimension(:), allocatable, target, private :: param !< containers of constitutive parameters (len Ninstance) type(tParameters), dimension(:), allocatable, target, private :: param !< containers of constitutive parameters (len Ninstance)
@ -79,12 +74,13 @@ contains
!> @brief module initialization !> @brief module initialization
!> @details reads in material parameters, allocates arrays, and does sanity checks !> @details reads in material parameters, allocates arrays, and does sanity checks
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
subroutine plastic_isotropic_init(fileUnit) subroutine plastic_isotropic_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: &
compiler_version, & compiler_version, &
compiler_options compiler_options
#endif #endif
use IO
use debug, only: & use debug, only: &
debug_level, & debug_level, &
debug_constitutive, & debug_constitutive, &
@ -94,17 +90,6 @@ subroutine plastic_isotropic_init(fileUnit)
use math, only: & use math, only: &
math_Mandel3333to66, & math_Mandel3333to66, &
math_Voigt66to3333 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: & use material, only: &
phase_plasticity, & phase_plasticity, &
phase_plasticityInstance, & phase_plasticityInstance, &
@ -112,17 +97,17 @@ subroutine plastic_isotropic_init(fileUnit)
PLASTICITY_ISOTROPIC_label, & PLASTICITY_ISOTROPIC_label, &
PLASTICITY_ISOTROPIC_ID, & PLASTICITY_ISOTROPIC_ID, &
material_phase, & material_phase, &
plasticState, & plasticState
MATERIAL_partPhase use config, only: &
MATERIAL_partPhase, &
config_phase
use lattice use lattice
implicit none implicit none
integer(pInt), intent(in) :: fileUnit
type(tParameters), pointer :: p type(tParameters), pointer :: prm
integer(pInt), allocatable, dimension(:) :: chunkPos
integer(pInt) :: & integer(pInt) :: &
o, & o, &
phase, & phase, &
@ -133,174 +118,103 @@ subroutine plastic_isotropic_init(fileUnit)
sizeState, & sizeState, &
sizeDeltaState sizeDeltaState
character(len=65536) :: & character(len=65536) :: &
tag = '', &
line = '', &
extmsg = '' extmsg = ''
character(len=64) :: & integer(pInt) :: NipcMyPhase,i
outputtag = '' character(len=65536), dimension(:), allocatable :: outputs
integer(pInt) :: NipcMyPhase
write(6,'(/,a)') ' <<<+- constitutive_'//PLASTICITY_ISOTROPIC_label//' init -+>>>' write(6,'(/,a)') ' <<<+- constitutive_'//PLASTICITY_ISOTROPIC_label//' 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"
maxNinstance = int(count(phase_plasticity == PLASTICITY_ISOTROPIC_ID),pInt) maxNinstance = int(count(phase_plasticity == PLASTICITY_ISOTROPIC_ID),pInt)
if (maxNinstance == 0_pInt) return
if (iand(debug_level(debug_constitutive),debug_levelBasic) /= 0_pInt) & if (iand(debug_level(debug_constitutive),debug_levelBasic) /= 0_pInt) &
write(6,'(a16,1x,i5,/)') '# instances:',maxNinstance write(6,'(a16,1x,i5,/)') '# instances:',maxNinstance
allocate(plastic_isotropic_sizePostResults(maxNinstance), source=0_pInt) ! public variables
allocate(plastic_isotropic_sizePostResult(maxval(phase_Noutput), maxNinstance),source=0_pInt) allocate(plastic_isotropic_sizePostResult(maxval(phase_Noutput), maxNinstance),source=0_pInt)
allocate(plastic_isotropic_output(maxval(phase_Noutput), maxNinstance)) allocate(plastic_isotropic_output(maxval(phase_Noutput), maxNinstance))
plastic_isotropic_output = '' plastic_isotropic_output = ''
allocate(plastic_isotropic_Noutput(maxNinstance), source=0_pInt) allocate(plastic_isotropic_Noutput(maxNinstance), source=0_pInt)
! inernal variable
allocate(param(maxNinstance)) ! one container of parameters per instance 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
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
p => param(instance) ! shorthand pointer to parameter object of my constitutive law
chunkPos = IO_stringPos(line)
tag = IO_lc(IO_stringValue(line,chunkPos,1_pInt)) ! extract key
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
plastic_isotropic_output(plastic_isotropic_Noutput(instance),instance) = outputtag
p%outputID = [p%outputID,flowstress_ID]
case ('strainrate')
plastic_isotropic_Noutput(instance) = plastic_isotropic_Noutput(instance) + 1_pInt
plastic_isotropic_output(plastic_isotropic_Noutput(instance),instance) = outputtag
p%outputID = [p%outputID,strainrate_ID]
end select
case ('/dilatation/')
p%dilatation = .true.
case ('tau0')
p%tau0 = IO_floatValue(line,chunkPos,2_pInt)
case ('gdot0')
p%gdot0 = IO_floatValue(line,chunkPos,2_pInt)
case ('n')
p%n = IO_floatValue(line,chunkPos,2_pInt)
case ('h0')
p%h0 = IO_floatValue(line,chunkPos,2_pInt)
case ('h0_slope','slopelnrate')
p%h0_slopeLnRate = IO_floatValue(line,chunkPos,2_pInt)
case ('tausat')
p%tausat = IO_floatValue(line,chunkPos,2_pInt)
case ('tausat_sinhfita')
p%tausat_SinhFitA = IO_floatValue(line,chunkPos,2_pInt)
case ('tausat_sinhfitb')
p%tausat_SinhFitB = IO_floatValue(line,chunkPos,2_pInt)
case ('tausat_sinhfitc')
p%tausat_SinhFitC = IO_floatValue(line,chunkPos,2_pInt)
case ('tausat_sinhfitd')
p%tausat_SinhFitD = IO_floatValue(line,chunkPos,2_pInt)
case ('a', 'w0')
p%a = IO_floatValue(line,chunkPos,2_pInt)
case ('taylorfactor')
p%fTaylor = IO_floatValue(line,chunkPos,2_pInt)
case ('atol_flowstress')
p%aTolFlowstress = IO_floatValue(line,chunkPos,2_pInt)
case ('atol_shear')
p%aTolShear = IO_floatValue(line,chunkPos,2_pInt)
case default
end select
endif; endif
enddo parsingFile
allocate(state(maxNinstance)) ! internal state aliases allocate(state(maxNinstance)) ! internal state aliases
allocate(dotState(maxNinstance)) allocate(dotState(maxNinstance))
initializeInstances: do phase = 1_pInt, size(phase_plasticity) ! loop over every plasticity do phase = 1_pInt, size(phase_plasticityInstance)
myPhase: if (phase_plasticity(phase) == PLASTICITY_isotropic_ID) then ! isolate instances of own constitutive description if (phase_plasticity(phase) == PLASTICITY_ISOTROPIC_ID) then
NipcMyPhase = count(material_phase == phase) ! number of own material points (including point components ipc)
instance = phase_plasticityInstance(phase) instance = phase_plasticityInstance(phase)
p => param(instance) prm => param(instance) ! shorthand pointer to parameter object of my constitutive law
extmsg = '' prm%tau0 = config_phase(phase)%getFloat('tau0')
prm%tausat = config_phase(phase)%getFloat('tausat')
prm%gdot0 = config_phase(phase)%getFloat('gdot0')
prm%n = config_phase(phase)%getFloat('n')
prm%h0 = config_phase(phase)%getFloat('h0')
prm%fTaylor = config_phase(phase)%getFloat('m')
prm%h0_slopeLnRate = config_phase(phase)%getFloat('h0_slopelnrate', defaultVal=0.0_pReal)
prm%tausat_SinhFitA = config_phase(phase)%getFloat('tausat_sinhfita',defaultVal=0.0_pReal)
prm%tausat_SinhFitB = config_phase(phase)%getFloat('tausat_sinhfitb',defaultVal=0.0_pReal)
prm%tausat_SinhFitC = config_phase(phase)%getFloat('tausat_sinhfitc',defaultVal=0.0_pReal)
prm%tausat_SinhFitD = config_phase(phase)%getFloat('tausat_sinhfitd',defaultVal=0.0_pReal)
prm%a = config_phase(phase)%getFloat('a')
prm%aTolFlowStress = config_phase(phase)%getFloat('atol_flowstress',defaultVal=1.0_pReal)
prm%aTolShear = config_phase(phase)%getFloat('atol_shear',defaultVal=1.0e-6_pReal)
prm%dilatation = config_phase(phase)%keyExists('/dilatation/')
#if defined(__GFORTRAN__)
outputs = ['GfortranBug86277']
outputs = config_phase(phase)%getStrings('(output)',defaultVal=outputs)
if (outputs(1) == 'GfortranBug86277') outputs = [character(len=65536)::]
#else
outputs = config_phase(phase)%getStrings('(output)',defaultVal=[character(len=65536)::])
#endif
allocate(prm%outputID(0))
do i=1_pInt, size(outputs)
select case(outputs(i))
case ('flowstress')
plastic_isotropic_Noutput(instance) = plastic_isotropic_Noutput(instance) + 1_pInt
plastic_isotropic_output(plastic_isotropic_Noutput(instance),instance) = outputs(i)
plasticState(phase)%sizePostResults = plasticState(phase)%sizePostResults + 1_pInt
plastic_isotropic_sizePostResult(i,instance) = 1_pInt
prm%outputID = [prm%outputID,flowstress_ID]
case ('strainrate')
plastic_isotropic_Noutput(instance) = plastic_isotropic_Noutput(instance) + 1_pInt
plastic_isotropic_output(plastic_isotropic_Noutput(instance),instance) = outputs(i)
plasticState(phase)%sizePostResults = &
plasticState(phase)%sizePostResults + 1_pInt
plastic_isotropic_sizePostResult(i,instance) = 1_pInt
prm%outputID = [prm%outputID,strainrate_ID]
end select
enddo
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
! sanity checks ! sanity checks
if (p%aTolShear <= 0.0_pReal) p%aTolShear = 1.0e-6_pReal ! default absolute tolerance 1e-6 extmsg = ''
if (p%tau0 < 0.0_pReal) extmsg = trim(extmsg)//' tau0' if (prm%aTolShear <= 0.0_pReal) extmsg = trim(extmsg)//"'aTolShear' "
if (p%gdot0 <= 0.0_pReal) extmsg = trim(extmsg)//' gdot0' if (prm%tau0 < 0.0_pReal) extmsg = trim(extmsg)//"'tau0' "
if (p%n <= 0.0_pReal) extmsg = trim(extmsg)//' n' if (prm%gdot0 <= 0.0_pReal) extmsg = trim(extmsg)//"'gdot0' "
if (p%tausat <= 0.0_pReal) extmsg = trim(extmsg)//' tausat' if (prm%n <= 0.0_pReal) extmsg = trim(extmsg)//"'n' "
if (p%a <= 0.0_pReal) extmsg = trim(extmsg)//' a' if (prm%tausat <= prm%tau0) extmsg = trim(extmsg)//"'tausat' "
if (p%fTaylor <= 0.0_pReal) extmsg = trim(extmsg)//' taylorfactor' if (prm%a <= 0.0_pReal) extmsg = trim(extmsg)//"'a' "
if (p%aTolFlowstress <= 0.0_pReal) extmsg = trim(extmsg)//' atol_flowstress' if (prm%fTaylor <= 0.0_pReal) extmsg = trim(extmsg)//"'m' "
if (extmsg /= '') then if (prm%aTolFlowstress <= 0.0_pReal) extmsg = trim(extmsg)//"'atol_flowstress' "
extmsg = trim(extmsg)//' ('//PLASTICITY_ISOTROPIC_label//')' ! prepare error message identifier if (extmsg /= '') call IO_error(211_pInt,ip=instance,&
call IO_error(211_pInt,ip=instance,ext_msg=extmsg) ext_msg=trim(extmsg)//'('//PLASTICITY_ISOTROPIC_label//')')
endif
!--------------------------------------------------------------------------------------------------
! Determine size of postResults array
outputsLoop: do o = 1_pInt,plastic_isotropic_Noutput(instance)
select case(p%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 ! allocate state arrays
NipcMyPhase = count(material_phase == phase) ! number of own material points (including point components ipc)
sizeDotState = size(["flowstress ","accumulated_shear"]) sizeDotState = size(["flowstress ","accumulated_shear"])
sizeDeltaState = 0_pInt ! no sudden jumps in state sizeDeltaState = 0_pInt ! no sudden jumps in state
sizeState = sizeDotState + sizeDeltaState sizeState = sizeDotState + sizeDeltaState
plasticState(phase)%sizeState = sizeState plasticState(phase)%sizeState = sizeState
plasticState(phase)%sizeDotState = sizeDotState plasticState(phase)%sizeDotState = sizeDotState
plasticState(phase)%sizeDeltaState = sizeDeltaState plasticState(phase)%sizeDeltaState = sizeDeltaState
plasticState(phase)%sizePostResults = plastic_isotropic_sizePostResults(instance)
plasticState(phase)%nSlip = 1 plasticState(phase)%nSlip = 1
plasticState(phase)%nTwin = 0
plasticState(phase)%nTrans= 0
allocate(plasticState(phase)%aTolState ( sizeState)) allocate(plasticState(phase)%aTolState ( sizeState))
allocate(plasticState(phase)%state0 ( sizeState,NipcMyPhase),source=0.0_pReal) allocate(plasticState(phase)%state0 ( sizeState,NipcMyPhase),source=0.0_pReal)
allocate(plasticState(phase)%partionedState0 ( 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)%subState0 ( sizeState,NipcMyPhase),source=0.0_pReal)
allocate(plasticState(phase)%state ( sizeState,NipcMyPhase),source=0.0_pReal) allocate(plasticState(phase)%state ( sizeState,NipcMyPhase),source=0.0_pReal)
@ -320,22 +234,23 @@ subroutine plastic_isotropic_init(fileUnit)
state(instance)%flowstress => plasticState(phase)%state (1,1:NipcMyPhase) state(instance)%flowstress => plasticState(phase)%state (1,1:NipcMyPhase)
dotState(instance)%flowstress => plasticState(phase)%dotState (1,1:NipcMyPhase) dotState(instance)%flowstress => plasticState(phase)%dotState (1,1:NipcMyPhase)
plasticState(phase)%state0(1,1:NipcMyPhase) = p%tau0 plasticState(phase)%state0(1,1:NipcMyPhase) = prm%tau0
plasticState(phase)%aTolState(1) = p%aTolFlowstress plasticState(phase)%aTolState(1) = prm%aTolFlowstress
state(instance)%accumulatedShear => plasticState(phase)%state (2,1:NipcMyPhase) state(instance)%accumulatedShear => plasticState(phase)%state (2,1:NipcMyPhase)
dotState(instance)%accumulatedShear => plasticState(phase)%dotState (2,1:NipcMyPhase) dotState(instance)%accumulatedShear => plasticState(phase)%dotState (2,1:NipcMyPhase)
plasticState(phase)%state0 (2,1:NipcMyPhase) = 0.0_pReal plasticState(phase)%state0 (2,1:NipcMyPhase) = 0.0_pReal
plasticState(phase)%aTolState(2) = p%aTolShear plasticState(phase)%aTolState(2) = prm%aTolShear
! global alias ! global alias
plasticState(phase)%slipRate => plasticState(phase)%dotState(2:2,1:NipcMyPhase) plasticState(phase)%slipRate => plasticState(phase)%dotState(2:2,1:NipcMyPhase)
plasticState(phase)%accumulatedSlip => plasticState(phase)%state (2:2,1:NipcMyPhase) plasticState(phase)%accumulatedSlip => plasticState(phase)%state (2:2,1:NipcMyPhase)
endif myPhase endif
enddo initializeInstances enddo
end subroutine plastic_isotropic_init end subroutine plastic_isotropic_init
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief calculates plastic velocity gradient and its tangent !> @brief calculates plastic velocity gradient and its tangent
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
@ -354,8 +269,7 @@ subroutine plastic_isotropic_LpAndItsTangent(Lp,dLp_dTstar99,Tstar_v,ipc,ip,el)
math_Mandel6to33, & math_Mandel6to33, &
math_Plain3333to99, & math_Plain3333to99, &
math_deviatoric33, & math_deviatoric33, &
math_mul33xx33, & math_mul33xx33
math_transpose33
use material, only: & use material, only: &
phasememberAt, & phasememberAt, &
material_phase, & material_phase, &
@ -374,7 +288,7 @@ subroutine plastic_isotropic_LpAndItsTangent(Lp,dLp_dTstar99,Tstar_v,ipc,ip,el)
ip, & !< integration point ip, & !< integration point
el !< element el !< element
type(tParameters), pointer :: p type(tParameters), pointer :: prm
real(pReal), dimension(3,3) :: & real(pReal), dimension(3,3) :: &
Tstar_dev_33 !< deviatoric part of the 2nd Piola Kirchhoff stress tensor as 2nd order tensor Tstar_dev_33 !< deviatoric part of the 2nd Piola Kirchhoff stress tensor as 2nd order tensor
@ -390,7 +304,7 @@ subroutine plastic_isotropic_LpAndItsTangent(Lp,dLp_dTstar99,Tstar_v,ipc,ip,el)
of = phasememberAt(ipc,ip,el) ! phasememberAt should be tackled by material and be renamed to material_phasemember of = phasememberAt(ipc,ip,el) ! phasememberAt should be tackled by material and be renamed to material_phasemember
instance = phase_plasticityInstance(material_phase(ipc,ip,el)) instance = phase_plasticityInstance(material_phase(ipc,ip,el))
p => param(instance) prm => param(instance)
Tstar_dev_33 = math_deviatoric33(math_Mandel6to33(Tstar_v)) ! deviatoric part of 2nd Piola-Kirchhoff stress 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) squarenorm_Tstar_dev = math_mul33xx33(Tstar_dev_33,Tstar_dev_33)
@ -400,31 +314,31 @@ subroutine plastic_isotropic_LpAndItsTangent(Lp,dLp_dTstar99,Tstar_v,ipc,ip,el)
Lp = 0.0_pReal Lp = 0.0_pReal
dLp_dTstar99 = 0.0_pReal dLp_dTstar99 = 0.0_pReal
else else
gamma_dot = p%gdot0 & gamma_dot = prm%gdot0 &
* ( sqrt(1.5_pReal) * norm_Tstar_dev / p%fTaylor / state(instance)%flowstress(of) ) & * ( sqrt(1.5_pReal) * norm_Tstar_dev / prm%fTaylor / state(instance)%flowstress(of) ) &
**p%n **prm%n
Lp = Tstar_dev_33/norm_Tstar_dev * gamma_dot/p%fTaylor Lp = Tstar_dev_33/norm_Tstar_dev * gamma_dot/prm%fTaylor
if (iand(debug_level(debug_constitutive), debug_levelExtensive) /= 0_pInt & if (iand(debug_level(debug_constitutive), debug_levelExtensive) /= 0_pInt &
.and. ((el == debug_e .and. ip == debug_i .and. ipc == debug_g) & .and. ((el == debug_e .and. ip == debug_i .and. ipc == debug_g) &
.or. .not. iand(debug_level(debug_constitutive),debug_levelSelective) /= 0_pInt)) then .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,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', & 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 transpose(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 >> norm Tstar / MPa', norm_Tstar_dev*1.0e-6_pReal
write(6,'(/,a,/,f12.5)') '<< CONST isotropic >> gdot', gamma_dot write(6,'(/,a,/,f12.5)') '<< CONST isotropic >> gdot', gamma_dot
end if end if
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
! Calculation of the tangent of Lp ! 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) & 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) = (p%n-1.0_pReal) * & dLp_dTstar_3333(k,l,m,n) = (prm%n-1.0_pReal) * &
Tstar_dev_33(k,l)*Tstar_dev_33(m,n) / squarenorm_Tstar_dev Tstar_dev_33(k,l)*Tstar_dev_33(m,n) / squarenorm_Tstar_dev
forall (k=1_pInt:3_pInt,l=1_pInt:3_pInt) & 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 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) & 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_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 / p%fTaylor * & dLp_dTstar99 = math_Plain3333to99(gamma_dot / prm%fTaylor * &
dLp_dTstar_3333 / norm_Tstar_dev) dLp_dTstar_3333 / norm_Tstar_dev)
end if end if
end subroutine plastic_isotropic_LpAndItsTangent end subroutine plastic_isotropic_LpAndItsTangent
@ -456,7 +370,7 @@ subroutine plastic_isotropic_LiAndItsTangent(Li,dLi_dTstar_3333,Tstar_v,ipc,ip,e
ip, & !< integration point ip, & !< integration point
el !< element el !< element
type(tParameters), pointer :: p type(tParameters), pointer :: prm
real(pReal), dimension(3,3) :: & real(pReal), dimension(3,3) :: &
Tstar_sph_33 !< sphiatoric part of the 2nd Piola Kirchhoff stress tensor as 2nd order tensor Tstar_sph_33 !< sphiatoric part of the 2nd Piola Kirchhoff stress tensor as 2nd order tensor
@ -470,28 +384,28 @@ subroutine plastic_isotropic_LiAndItsTangent(Li,dLi_dTstar_3333,Tstar_v,ipc,ip,e
of = phasememberAt(ipc,ip,el) ! phasememberAt should be tackled by material and be renamed to material_phasemember of = phasememberAt(ipc,ip,el) ! phasememberAt should be tackled by material and be renamed to material_phasemember
instance = phase_plasticityInstance(material_phase(ipc,ip,el)) instance = phase_plasticityInstance(material_phase(ipc,ip,el))
p => param(instance) prm => param(instance)
Tstar_sph_33 = math_spherical33(math_Mandel6to33(Tstar_v)) ! spherical part of 2nd Piola-Kirchhoff stress 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) squarenorm_Tstar_sph = math_mul33xx33(Tstar_sph_33,Tstar_sph_33)
norm_Tstar_sph = sqrt(squarenorm_Tstar_sph) norm_Tstar_sph = sqrt(squarenorm_Tstar_sph)
if (p%dilatation .and. norm_Tstar_sph > 0.0_pReal) then ! Tstar == 0 or J2 plascitiy --> both Li and dLi_dTstar are zero if (prm%dilatation .and. norm_Tstar_sph > 0.0_pReal) then ! Tstar == 0 or J2 plascitiy --> both Li and dLi_dTstar are zero
gamma_dot = p%gdot0 & gamma_dot = prm%gdot0 &
* (sqrt(1.5_pReal) * norm_Tstar_sph / p%fTaylor / state(instance)%flowstress(of) ) & * (sqrt(1.5_pReal) * norm_Tstar_sph / prm%fTaylor / state(instance)%flowstress(of) ) &
**p%n **prm%n
Li = Tstar_sph_33/norm_Tstar_sph * gamma_dot/p%fTaylor Li = Tstar_sph_33/norm_Tstar_sph * gamma_dot/prm%fTaylor
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
! Calculation of the tangent of Li ! 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) & 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) = (p%n-1.0_pReal) * & dLi_dTstar_3333(k,l,m,n) = (prm%n-1.0_pReal) * &
Tstar_sph_33(k,l)*Tstar_sph_33(m,n) / squarenorm_Tstar_sph Tstar_sph_33(k,l)*Tstar_sph_33(m,n) / squarenorm_Tstar_sph
forall (k=1_pInt:3_pInt,l=1_pInt:3_pInt) & 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(k,l,k,l) = dLi_dTstar_3333(k,l,k,l) + 1.0_pReal
dLi_dTstar_3333 = gamma_dot / p%fTaylor * & dLi_dTstar_3333 = gamma_dot / prm%fTaylor * &
dLi_dTstar_3333 / norm_Tstar_sph dLi_dTstar_3333 / norm_Tstar_sph
else else
Li = 0.0_pReal Li = 0.0_pReal
@ -520,7 +434,7 @@ subroutine plastic_isotropic_dotState(Tstar_v,ipc,ip,el)
ipc, & !< component-ID of integration point ipc, & !< component-ID of integration point
ip, & !< integration point ip, & !< integration point
el !< element el !< element
type(tParameters), pointer :: p type(tParameters), pointer :: prm
real(pReal), dimension(6) :: & real(pReal), dimension(6) :: &
Tstar_dev_v !< deviatoric 2nd Piola Kirchhoff stress tensor in Mandel notation Tstar_dev_v !< deviatoric 2nd Piola Kirchhoff stress tensor in Mandel notation
real(pReal) :: & real(pReal) :: &
@ -534,11 +448,11 @@ subroutine plastic_isotropic_dotState(Tstar_v,ipc,ip,el)
of = phasememberAt(ipc,ip,el) ! phasememberAt should be tackled by material and be renamed to material_phasemember of = phasememberAt(ipc,ip,el) ! phasememberAt should be tackled by material and be renamed to material_phasemember
instance = phase_plasticityInstance(material_phase(ipc,ip,el)) instance = phase_plasticityInstance(material_phase(ipc,ip,el))
p => param(instance) prm => param(instance)
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
! norm of (deviatoric) 2nd Piola-Kirchhoff stress ! norm of (deviatoric) 2nd Piola-Kirchhoff stress
if (p%dilatation) then if (prm%dilatation) then
norm_Tstar_v = sqrt(math_mul6x6(Tstar_v,Tstar_v)) norm_Tstar_v = sqrt(math_mul6x6(Tstar_v,Tstar_v))
else else
Tstar_dev_v(1:3) = Tstar_v(1:3) - sum(Tstar_v(1:3))/3.0_pReal Tstar_dev_v(1:3) = Tstar_v(1:3) - sum(Tstar_v(1:3))/3.0_pReal
@ -547,26 +461,26 @@ subroutine plastic_isotropic_dotState(Tstar_v,ipc,ip,el)
end if end if
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
! strain rate ! strain rate
gamma_dot = p%gdot0 * ( sqrt(1.5_pReal) * norm_Tstar_v & gamma_dot = prm%gdot0 * ( sqrt(1.5_pReal) * norm_Tstar_v &
/ &!----------------------------------------------------------------------------------- / &!-----------------------------------------------------------------------------------
(p%fTaylor*state(instance)%flowstress(of) ))**p%n (prm%fTaylor*state(instance)%flowstress(of) ))**prm%n
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
! hardening coefficient ! hardening coefficient
if (abs(gamma_dot) > 1e-12_pReal) then if (abs(gamma_dot) > 1e-12_pReal) then
if (dEq0(p%tausat_SinhFitA)) then if (dEq0(prm%tausat_SinhFitA)) then
saturation = p%tausat saturation = prm%tausat
else else
saturation = p%tausat & saturation = prm%tausat &
+ asinh( (gamma_dot / p%tausat_SinhFitA& + asinh( (gamma_dot / prm%tausat_SinhFitA&
)**(1.0_pReal / p%tausat_SinhFitD)& )**(1.0_pReal / prm%tausat_SinhFitD)&
)**(1.0_pReal / p%tausat_SinhFitC) & )**(1.0_pReal / prm%tausat_SinhFitC) &
/ ( p%tausat_SinhFitB & / ( prm%tausat_SinhFitB &
* (gamma_dot / p%gdot0)**(1.0_pReal / p%n) & * (gamma_dot / prm%gdot0)**(1.0_pReal / prm%n) &
) )
endif endif
hardening = ( p%h0 + p%h0_slopeLnRate * log(gamma_dot) ) & hardening = ( prm%h0 + prm%h0_slopeLnRate * log(gamma_dot) ) &
* abs( 1.0_pReal - state(instance)%flowstress(of)/saturation )**p%a & * abs( 1.0_pReal - state(instance)%flowstress(of)/saturation )**prm%a &
* sign(1.0_pReal, 1.0_pReal - state(instance)%flowstress(of)/saturation) * sign(1.0_pReal, 1.0_pReal - state(instance)%flowstress(of)/saturation)
else else
hardening = 0.0_pReal hardening = 0.0_pReal
@ -584,6 +498,7 @@ function plastic_isotropic_postResults(Tstar_v,ipc,ip,el)
use math, only: & use math, only: &
math_mul6x6 math_mul6x6
use material, only: & use material, only: &
plasticState, &
material_phase, & material_phase, &
phasememberAt, & phasememberAt, &
phase_plasticityInstance phase_plasticityInstance
@ -596,9 +511,9 @@ function plastic_isotropic_postResults(Tstar_v,ipc,ip,el)
ip, & !< integration point ip, & !< integration point
el !< element el !< element
type(tParameters), pointer :: p type(tParameters), pointer :: prm
real(pReal), dimension(plastic_isotropic_sizePostResults(phase_plasticityInstance(material_phase(ipc,ip,el)))) :: & real(pReal), dimension(plasticState(material_phase(ipc,ip,el))%sizePostResults) :: &
plastic_isotropic_postResults plastic_isotropic_postResults
real(pReal), dimension(6) :: & real(pReal), dimension(6) :: &
@ -613,11 +528,11 @@ function plastic_isotropic_postResults(Tstar_v,ipc,ip,el)
of = phasememberAt(ipc,ip,el) ! phasememberAt should be tackled by material and be renamed to material_phasemember of = phasememberAt(ipc,ip,el) ! phasememberAt should be tackled by material and be renamed to material_phasemember
instance = phase_plasticityInstance(material_phase(ipc,ip,el)) instance = phase_plasticityInstance(material_phase(ipc,ip,el))
p => param(instance) prm => param(instance)
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
! norm of (deviatoric) 2nd Piola-Kirchhoff stress ! norm of (deviatoric) 2nd Piola-Kirchhoff stress
if (p%dilatation) then if (prm%dilatation) then
norm_Tstar_v = sqrt(math_mul6x6(Tstar_v,Tstar_v)) norm_Tstar_v = sqrt(math_mul6x6(Tstar_v,Tstar_v))
else else
Tstar_dev_v(1:3) = Tstar_v(1:3) - sum(Tstar_v(1:3))/3.0_pReal Tstar_dev_v(1:3) = Tstar_v(1:3) - sum(Tstar_v(1:3))/3.0_pReal
@ -629,15 +544,15 @@ function plastic_isotropic_postResults(Tstar_v,ipc,ip,el)
plastic_isotropic_postResults = 0.0_pReal plastic_isotropic_postResults = 0.0_pReal
outputsLoop: do o = 1_pInt,plastic_isotropic_Noutput(instance) outputsLoop: do o = 1_pInt,plastic_isotropic_Noutput(instance)
select case(p%outputID(o)) select case(prm%outputID(o))
case (flowstress_ID) case (flowstress_ID)
plastic_isotropic_postResults(c+1_pInt) = state(instance)%flowstress(of) plastic_isotropic_postResults(c+1_pInt) = state(instance)%flowstress(of)
c = c + 1_pInt c = c + 1_pInt
case (strainrate_ID) case (strainrate_ID)
plastic_isotropic_postResults(c+1_pInt) = & plastic_isotropic_postResults(c+1_pInt) = &
p%gdot0 * ( sqrt(1.5_pReal) * norm_Tstar_v & prm%gdot0 * ( sqrt(1.5_pReal) * norm_Tstar_v &
/ &!---------------------------------------------------------------------------------- / &!----------------------------------------------------------------------------------
(p%fTaylor * state(instance)%flowstress(of)) ) ** p%n (prm%fTaylor * state(instance)%flowstress(of)) ) ** prm%n
c = c + 1_pInt c = c + 1_pInt
end select end select
enddo outputsLoop enddo outputsLoop

View File

@ -1,6 +1,7 @@
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @author Philip Eisenlohr, Michigan State University !> @author Philip Eisenlohr, Michigan State University
!> @author Zhuowen Zhao, Michigan State University !> @author Zhuowen Zhao, Michigan State University
!> @author Martin Diehl, Max-Planck-Institut für Eisenforschung GmbH
!> @brief Introducing Voce-type kinematic hardening rule into crystal plasticity !> @brief Introducing Voce-type kinematic hardening rule into crystal plasticity
!! formulation using a power law fitting !! formulation using a power law fitting
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
@ -145,7 +146,8 @@ subroutine plastic_kinehardening_init(fileUnit)
phase_plasticityInstance, & phase_plasticityInstance, &
phase_Noutput, & phase_Noutput, &
material_phase, & material_phase, &
plasticState, & plasticState
use config, only: &
MATERIAL_partPhase MATERIAL_partPhase
use lattice use lattice
use numerics,only: & use numerics,only: &
@ -230,6 +232,7 @@ subroutine plastic_kinehardening_init(fileUnit)
allocate(param(instance)%nonSchmidCoeff(Nchunks_nonSchmid), source=0.0_pReal) allocate(param(instance)%nonSchmidCoeff(Nchunks_nonSchmid), source=0.0_pReal)
if(allocated(tempPerSlip)) deallocate(tempPerSlip) if(allocated(tempPerSlip)) deallocate(tempPerSlip)
allocate(tempPerSlip(Nchunks_SlipFamilies)) allocate(tempPerSlip(Nchunks_SlipFamilies))
allocate(param(instance)%outputID(0))
endif endif
cycle ! skip to next line cycle ! skip to next line
endif endif

View File

@ -291,8 +291,8 @@ use material, only: phase_plasticity, &
PLASTICITY_NONLOCAL_label, & PLASTICITY_NONLOCAL_label, &
PLASTICITY_NONLOCAL_ID, & PLASTICITY_NONLOCAL_ID, &
plasticState, & plasticState, &
MATERIAL_partPhase ,&
material_phase material_phase
use config, only: MATERIAL_partPhase
use lattice use lattice
use numerics,only: & use numerics,only: &
numerics_integrator numerics_integrator

View File

@ -157,7 +157,8 @@ subroutine plastic_phenopowerlaw_init(fileUnit)
PLASTICITY_PHENOPOWERLAW_label, & PLASTICITY_PHENOPOWERLAW_label, &
PLASTICITY_PHENOPOWERLAW_ID, & PLASTICITY_PHENOPOWERLAW_ID, &
material_phase, & material_phase, &
plasticState, & plasticState
use config, only: &
MATERIAL_partPhase MATERIAL_partPhase
use lattice use lattice
use numerics,only: & use numerics,only: &

View File

@ -27,6 +27,7 @@ subroutine porosity_none_init()
use IO, only: & use IO, only: &
IO_timeStamp IO_timeStamp
use material use material
use config
implicit none implicit none
integer(pInt) :: & integer(pInt) :: &

View File

@ -77,11 +77,10 @@ subroutine porosity_phasefield_init(fileUnit)
porosityState, & porosityState, &
porosityMapping, & porosityMapping, &
porosity, & porosity, &
porosity_initialPhi, & porosity_initialPhi
use config, only: &
material_partHomogenization, & material_partHomogenization, &
material_partPhase material_partPhase
use numerics,only: &
worldrank
implicit none implicit none
integer(pInt), intent(in) :: fileUnit integer(pInt), intent(in) :: fileUnit
@ -94,11 +93,9 @@ subroutine porosity_phasefield_init(fileUnit)
tag = '', & tag = '', &
line = '' line = ''
mainProcess: if (worldrank == 0) then write(6,'(/,a)') ' <<<+- porosity_'//POROSITY_phasefield_label//' init -+>>>'
write(6,'(/,a)') ' <<<+- porosity_'//POROSITY_phasefield_label//' 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"
endif mainProcess
maxNinstance = int(count(porosity_type == POROSITY_phasefield_ID),pInt) maxNinstance = int(count(porosity_type == POROSITY_phasefield_ID),pInt)
if (maxNinstance == 0_pInt) return if (maxNinstance == 0_pInt) return

View File

@ -91,9 +91,10 @@ subroutine source_damage_anisoBrittle_init(fileUnit)
phase_Noutput, & phase_Noutput, &
SOURCE_damage_anisoBrittle_label, & SOURCE_damage_anisoBrittle_label, &
SOURCE_damage_anisoBrittle_ID, & SOURCE_damage_anisoBrittle_ID, &
material_phase, &
sourceState
use config, only: &
material_Nphase, & material_Nphase, &
material_phase, &
sourceState, &
MATERIAL_partPhase MATERIAL_partPhase
use numerics,only: & use numerics,only: &
numerics_integrator numerics_integrator

View File

@ -95,9 +95,10 @@ subroutine source_damage_anisoDuctile_init(fileUnit)
phase_Noutput, & phase_Noutput, &
SOURCE_damage_anisoDuctile_label, & SOURCE_damage_anisoDuctile_label, &
SOURCE_damage_anisoDuctile_ID, & SOURCE_damage_anisoDuctile_ID, &
material_Nphase, &
material_phase, & material_phase, &
sourceState, & sourceState
use config, only: &
material_Nphase, &
MATERIAL_partPhase MATERIAL_partPhase
use numerics,only: & use numerics,only: &
numerics_integrator numerics_integrator

View File

@ -81,9 +81,10 @@ subroutine source_damage_isoBrittle_init(fileUnit)
phase_Noutput, & phase_Noutput, &
SOURCE_damage_isoBrittle_label, & SOURCE_damage_isoBrittle_label, &
SOURCE_damage_isoBrittle_ID, & SOURCE_damage_isoBrittle_ID, &
material_Nphase, &
material_phase, & material_phase, &
sourceState, & sourceState
use config, only: &
material_Nphase, &
MATERIAL_partPhase MATERIAL_partPhase
use numerics,only: & use numerics,only: &
numerics_integrator numerics_integrator

View File

@ -81,10 +81,12 @@ subroutine source_damage_isoDuctile_init(fileUnit)
phase_Noutput, & phase_Noutput, &
SOURCE_damage_isoDuctile_label, & SOURCE_damage_isoDuctile_label, &
SOURCE_damage_isoDuctile_ID, & SOURCE_damage_isoDuctile_ID, &
material_Nphase, &
material_phase, & material_phase, &
sourceState, & sourceState
use config, only: &
material_Nphase, &
MATERIAL_partPhase MATERIAL_partPhase
use numerics,only: & use numerics,only: &
numerics_integrator numerics_integrator

View File

@ -67,9 +67,10 @@ subroutine source_thermal_dissipation_init(fileUnit)
phase_Noutput, & phase_Noutput, &
SOURCE_thermal_dissipation_label, & SOURCE_thermal_dissipation_label, &
SOURCE_thermal_dissipation_ID, & SOURCE_thermal_dissipation_ID, &
material_Nphase, &
material_phase, & material_phase, &
sourceState, & sourceState
use config, only: &
material_Nphase, &
MATERIAL_partPhase MATERIAL_partPhase
use numerics,only: & use numerics,only: &
numerics_integrator numerics_integrator

View File

@ -73,9 +73,10 @@ subroutine source_thermal_externalheat_init(fileUnit)
phase_Noutput, & phase_Noutput, &
SOURCE_thermal_externalheat_label, & SOURCE_thermal_externalheat_label, &
SOURCE_thermal_externalheat_ID, & SOURCE_thermal_externalheat_ID, &
material_Nphase, &
material_phase, & material_phase, &
sourceState, & sourceState
use config, only: &
material_Nphase, &
MATERIAL_partPhase MATERIAL_partPhase
use numerics,only: & use numerics,only: &
numerics_integrator numerics_integrator

View File

@ -69,9 +69,10 @@ subroutine source_vacancy_irradiation_init(fileUnit)
phase_Noutput, & phase_Noutput, &
SOURCE_vacancy_irradiation_label, & SOURCE_vacancy_irradiation_label, &
SOURCE_vacancy_irradiation_ID, & SOURCE_vacancy_irradiation_ID, &
material_Nphase, &
material_phase, & material_phase, &
sourceState, & sourceState
use config, only: &
material_Nphase, &
MATERIAL_partPhase MATERIAL_partPhase
use numerics,only: & use numerics,only: &
numerics_integrator numerics_integrator

View File

@ -67,9 +67,10 @@ subroutine source_vacancy_phenoplasticity_init(fileUnit)
phase_Noutput, & phase_Noutput, &
SOURCE_vacancy_phenoplasticity_label, & SOURCE_vacancy_phenoplasticity_label, &
SOURCE_vacancy_phenoplasticity_ID, & SOURCE_vacancy_phenoplasticity_ID, &
material_Nphase, &
material_phase, & material_phase, &
sourceState, & sourceState
use config, only: &
material_Nphase, &
MATERIAL_partPhase MATERIAL_partPhase
use numerics,only: & use numerics,only: &
numerics_integrator numerics_integrator

View File

@ -71,9 +71,10 @@ subroutine source_vacancy_thermalfluc_init(fileUnit)
phase_Noutput, & phase_Noutput, &
SOURCE_vacancy_thermalfluc_label, & SOURCE_vacancy_thermalfluc_label, &
SOURCE_vacancy_thermalfluc_ID, & SOURCE_vacancy_thermalfluc_ID, &
material_Nphase, &
material_phase, & material_phase, &
sourceState, & sourceState
use config, only: &
material_Nphase, &
MATERIAL_partPhase MATERIAL_partPhase
use numerics,only: & use numerics,only: &
numerics_integrator numerics_integrator

View File

@ -64,6 +64,8 @@ subroutine thermal_adiabatic_init(fileUnit)
IO_error, & IO_error, &
IO_timeStamp, & IO_timeStamp, &
IO_EOF IO_EOF
use config, only: &
material_partHomogenization
use material, only: & use material, only: &
thermal_type, & thermal_type, &
thermal_typeInstance, & thermal_typeInstance, &
@ -76,8 +78,7 @@ subroutine thermal_adiabatic_init(fileUnit)
thermalMapping, & thermalMapping, &
thermal_initialT, & thermal_initialT, &
temperature, & temperature, &
temperatureRate, & temperatureRate
material_partHomogenization
implicit none implicit none
integer(pInt), intent(in) :: fileUnit integer(pInt), intent(in) :: fileUnit

View File

@ -77,7 +77,8 @@ subroutine thermal_conduction_init(fileUnit)
thermalMapping, & thermalMapping, &
thermal_initialT, & thermal_initialT, &
temperature, & temperature, &
temperatureRate, & temperatureRate
use config, only: &
material_partHomogenization material_partHomogenization
implicit none implicit none

View File

@ -27,6 +27,7 @@ subroutine thermal_isothermal_init()
use IO, only: & use IO, only: &
IO_timeStamp IO_timeStamp
use material use material
use config
implicit none implicit none
integer(pInt) :: & integer(pInt) :: &

View File

@ -91,9 +91,10 @@ subroutine vacancyflux_cahnhilliard_init(fileUnit)
vacancyfluxMapping, & vacancyfluxMapping, &
vacancyConc, & vacancyConc, &
vacancyConcRate, & vacancyConcRate, &
vacancyflux_initialCv, & vacancyflux_initialCv
material_partHomogenization, & use config, only: &
material_partPhase material_partPhase, &
material_partHomogenization
implicit none implicit none
integer(pInt), intent(in) :: fileUnit integer(pInt), intent(in) :: fileUnit

View File

@ -74,7 +74,8 @@ subroutine vacancyflux_isochempot_init(fileUnit)
vacancyfluxMapping, & vacancyfluxMapping, &
vacancyConc, & vacancyConc, &
vacancyConcRate, & vacancyConcRate, &
vacancyflux_initialCv, & vacancyflux_initialCv
use config, only: &
material_partHomogenization material_partHomogenization
implicit none implicit none

View File

@ -27,6 +27,7 @@ subroutine vacancyflux_isoconc_init()
use IO, only: & use IO, only: &
IO_timeStamp IO_timeStamp
use material use material
use config
implicit none implicit none
integer(pInt) :: & integer(pInt) :: &