simplified
This commit is contained in:
parent
a421525d15
commit
3ca34c8f80
|
@ -163,8 +163,8 @@ subroutine constitutive_init()
|
|||
call IO_checkAndRewind(FILEUNIT)
|
||||
if (any(phase_source == SOURCE_thermal_dissipation_ID)) call source_thermal_dissipation_init(FILEUNIT)
|
||||
if (any(phase_source == SOURCE_thermal_externalheat_ID)) call source_thermal_externalheat_init(FILEUNIT)
|
||||
if (any(phase_source == SOURCE_damage_isoBrittle_ID)) call source_damage_isoBrittle_init(FILEUNIT)
|
||||
if (any(phase_source == SOURCE_damage_isoDuctile_ID)) call source_damage_isoDuctile_init(FILEUNIT)
|
||||
if (any(phase_source == SOURCE_damage_isoBrittle_ID)) call source_damage_isoBrittle_init
|
||||
if (any(phase_source == SOURCE_damage_isoDuctile_ID)) call source_damage_isoDuctile_init
|
||||
if (any(phase_source == SOURCE_damage_anisoBrittle_ID)) call source_damage_anisoBrittle_init(FILEUNIT)
|
||||
if (any(phase_source == SOURCE_damage_anisoDuctile_ID)) call source_damage_anisoDuctile_init(FILEUNIT)
|
||||
|
||||
|
|
|
@ -12,7 +12,6 @@ module source_damage_anisoBrittle
|
|||
implicit none
|
||||
private
|
||||
integer(pInt), dimension(:), allocatable, public, protected :: &
|
||||
source_damage_anisoBrittle_sizePostResults, & !< cumulative size of post results
|
||||
source_damage_anisoBrittle_offset, & !< which source is my current source mechanism?
|
||||
source_damage_anisoBrittle_instance !< instance of source mechanism
|
||||
|
||||
|
@ -22,12 +21,6 @@ module source_damage_anisoBrittle
|
|||
character(len=64), dimension(:,:), allocatable, target, public :: &
|
||||
source_damage_anisoBrittle_output !< name of each post result output
|
||||
|
||||
integer(pInt), dimension(:), allocatable, target, public :: &
|
||||
source_damage_anisoBrittle_Noutput !< number of outputs per instance of this source
|
||||
|
||||
integer(pInt), dimension(:), allocatable, private :: &
|
||||
source_damage_anisoBrittle_totalNcleavage !< total number of cleavage systems
|
||||
|
||||
integer(pInt), dimension(:,:), allocatable, private :: &
|
||||
source_damage_anisoBrittle_Ncleavage !< number of cleavage systems per family
|
||||
|
||||
|
@ -40,9 +33,6 @@ module source_damage_anisoBrittle
|
|||
damage_drivingforce_ID
|
||||
end enum
|
||||
|
||||
integer(kind(undefined_ID)), dimension(:,:), allocatable, private :: &
|
||||
source_damage_anisoBrittle_outputID !< ID of each post result output
|
||||
|
||||
|
||||
type, private :: tParameters !< container type for internal constitutive parameters
|
||||
real(pReal) :: &
|
||||
|
@ -158,17 +148,13 @@ subroutine source_damage_anisoBrittle_init(fileUnit)
|
|||
enddo
|
||||
enddo
|
||||
|
||||
allocate(source_damage_anisoBrittle_sizePostResults(Ninstance), source=0_pInt)
|
||||
allocate(source_damage_anisoBrittle_sizePostResult(maxval(phase_Noutput),Ninstance), source=0_pInt)
|
||||
allocate(source_damage_anisoBrittle_output(maxval(phase_Noutput),Ninstance))
|
||||
source_damage_anisoBrittle_output = ''
|
||||
allocate(source_damage_anisoBrittle_outputID(maxval(phase_Noutput),Ninstance), source=undefined_ID)
|
||||
allocate(source_damage_anisoBrittle_Noutput(Ninstance), source=0_pInt)
|
||||
|
||||
allocate(source_damage_anisoBrittle_critDisp(lattice_maxNcleavageFamily,Ninstance), source=0.0_pReal)
|
||||
allocate(source_damage_anisoBrittle_critLoad(lattice_maxNcleavageFamily,Ninstance), source=0.0_pReal)
|
||||
allocate(source_damage_anisoBrittle_Ncleavage(lattice_maxNcleavageFamily,Ninstance), source=0_pInt)
|
||||
allocate(source_damage_anisoBrittle_totalNcleavage(Ninstance), source=0_pInt)
|
||||
|
||||
allocate(param(Ninstance))
|
||||
|
||||
|
@ -202,7 +188,11 @@ subroutine source_damage_anisoBrittle_init(fileUnit)
|
|||
do i=1_pInt, size(outputs)
|
||||
outputID = undefined_ID
|
||||
select case(outputs(i))
|
||||
|
||||
case ('anisobrittle_drivingforce')
|
||||
source_damage_anisoBrittle_sizePostResult(i,source_damage_anisoBrittle_instance(p)) = 1_pInt
|
||||
source_damage_anisoBrittle_output(i,source_damage_anisoBrittle_instance(p)) = outputs(i)
|
||||
prm%outputID = [prm%outputID, damage_drivingforce_ID]
|
||||
|
||||
end select
|
||||
|
||||
|
@ -210,6 +200,16 @@ subroutine source_damage_anisoBrittle_init(fileUnit)
|
|||
|
||||
end associate
|
||||
|
||||
phase = p
|
||||
NofMyPhase=count(material_phase==phase)
|
||||
instance = source_damage_anisoBrittle_instance(phase)
|
||||
sourceOffset = source_damage_anisoBrittle_offset(phase)
|
||||
|
||||
|
||||
call material_allocateSourceState(phase,sourceOffset,NofMyPhase,1_pInt)
|
||||
sourceState(phase)%p(sourceOffset)%sizePostResults = sum(source_damage_anisoBrittle_sizePostResult(:,instance))
|
||||
sourceState(phase)%p(sourceOffset)%aTolState=param(instance)%aTol
|
||||
|
||||
enddo
|
||||
|
||||
rewind(fileUnit)
|
||||
|
@ -234,14 +234,6 @@ subroutine source_damage_anisoBrittle_init(fileUnit)
|
|||
chunkPos = IO_stringPos(line)
|
||||
tag = IO_lc(IO_stringValue(line,chunkPos,1_pInt)) ! extract key
|
||||
select case(tag)
|
||||
case ('(output)')
|
||||
select case(IO_lc(IO_stringValue(line,chunkPos,2_pInt)))
|
||||
case ('anisobrittle_drivingforce')
|
||||
source_damage_anisoBrittle_Noutput(instance) = source_damage_anisoBrittle_Noutput(instance) + 1_pInt
|
||||
source_damage_anisoBrittle_outputID(source_damage_anisoBrittle_Noutput(instance),instance) = damage_drivingforce_ID
|
||||
source_damage_anisoBrittle_output(source_damage_anisoBrittle_Noutput(instance),instance) = &
|
||||
IO_lc(IO_stringValue(line,chunkPos,2_pInt))
|
||||
end select
|
||||
|
||||
case ('ncleavage') !
|
||||
Nchunks_CleavageFamilies = chunkPos(1) - 1_pInt
|
||||
|
@ -268,11 +260,6 @@ subroutine source_damage_anisoBrittle_init(fileUnit)
|
|||
sanityChecks: do phase = 1_pInt, material_Nphase
|
||||
myPhase: if (any(phase_source(:,phase) == SOURCE_damage_anisoBrittle_ID)) then
|
||||
instance = source_damage_anisoBrittle_instance(phase)
|
||||
source_damage_anisoBrittle_Ncleavage(1:lattice_maxNcleavageFamily,instance) = &
|
||||
min(lattice_NcleavageSystem(1:lattice_maxNcleavageFamily,phase),& ! limit active cleavage systems per family to min of available and requested
|
||||
source_damage_anisoBrittle_Ncleavage(1:lattice_maxNcleavageFamily,instance))
|
||||
source_damage_anisoBrittle_totalNcleavage(instance) = sum(source_damage_anisoBrittle_Ncleavage(:,instance)) ! how many cleavage systems altogether
|
||||
|
||||
|
||||
if (any(source_damage_anisoBrittle_critDisp(1:Nchunks_CleavageFamilies,instance) < 0.0_pReal)) &
|
||||
call IO_error(211_pInt,el=instance,ext_msg='critical_displacement ('//SOURCE_damage_anisoBrittle_LABEL//')')
|
||||
|
@ -283,34 +270,6 @@ subroutine source_damage_anisoBrittle_init(fileUnit)
|
|||
endif myPhase
|
||||
enddo sanityChecks
|
||||
|
||||
initializeInstances: do phase = 1_pInt, material_Nphase
|
||||
if (any(phase_source(:,phase) == SOURCE_damage_anisoBrittle_ID)) then
|
||||
NofMyPhase=count(material_phase==phase)
|
||||
instance = source_damage_anisoBrittle_instance(phase)
|
||||
sourceOffset = source_damage_anisoBrittle_offset(phase)
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
! Determine size of postResults array
|
||||
outputsLoop: do o = 1_pInt,source_damage_anisoBrittle_Noutput(instance)
|
||||
select case(source_damage_anisoBrittle_outputID(o,instance))
|
||||
case(damage_drivingforce_ID)
|
||||
mySize = 1_pInt
|
||||
end select
|
||||
|
||||
if (mySize > 0_pInt) then ! any meaningful output found
|
||||
source_damage_anisoBrittle_sizePostResult(o,instance) = mySize
|
||||
source_damage_anisoBrittle_sizePostResults(instance) = source_damage_anisoBrittle_sizePostResults(instance) + mySize
|
||||
endif
|
||||
enddo outputsLoop
|
||||
|
||||
call material_allocateSourceState(phase,sourceOffset,NofMyPhase,1_pInt)
|
||||
sourceState(phase)%p(sourceOffset)%sizePostResults = source_damage_anisoBrittle_sizePostResults(instance)
|
||||
sourceState(phase)%p(sourceOffset)%aTolState=param(instance)%aTol
|
||||
|
||||
|
||||
endif
|
||||
|
||||
enddo initializeInstances
|
||||
end subroutine source_damage_anisoBrittle_init
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
|
@ -417,8 +376,8 @@ function source_damage_anisoBrittle_postResults(phase, constituent)
|
|||
integer(pInt), intent(in) :: &
|
||||
phase, &
|
||||
constituent
|
||||
real(pReal), dimension(source_damage_anisoBrittle_sizePostResults( &
|
||||
source_damage_anisoBrittle_instance(phase))) :: &
|
||||
real(pReal), dimension(sum(source_damage_anisoBrittle_sizePostResult(:, &
|
||||
source_damage_anisoBrittle_instance(phase)))) :: &
|
||||
source_damage_anisoBrittle_postResults
|
||||
|
||||
integer(pInt) :: &
|
||||
|
@ -428,10 +387,9 @@ function source_damage_anisoBrittle_postResults(phase, constituent)
|
|||
sourceOffset = source_damage_anisoBrittle_offset(phase)
|
||||
|
||||
c = 0_pInt
|
||||
source_damage_anisoBrittle_postResults = 0.0_pReal
|
||||
|
||||
do o = 1_pInt,source_damage_anisoBrittle_Noutput(instance)
|
||||
select case(source_damage_anisoBrittle_outputID(o,instance))
|
||||
do o = 1_pInt,size(param(instance)%outputID)
|
||||
select case(param(instance)%outputID(o))
|
||||
case (damage_drivingforce_ID)
|
||||
source_damage_anisoBrittle_postResults(c+1_pInt) = &
|
||||
sourceState(phase)%p(sourceOffset)%state(1,constituent)
|
||||
|
|
|
@ -12,7 +12,6 @@ module source_damage_anisoDuctile
|
|||
implicit none
|
||||
private
|
||||
integer(pInt), dimension(:), allocatable, public, protected :: &
|
||||
source_damage_anisoDuctile_sizePostResults, & !< cumulative size of post results
|
||||
source_damage_anisoDuctile_offset, & !< which source is my current damage mechanism?
|
||||
source_damage_anisoDuctile_instance !< instance of damage source mechanism
|
||||
|
||||
|
@ -22,11 +21,6 @@ module source_damage_anisoDuctile
|
|||
character(len=64), dimension(:,:), allocatable, target, public :: &
|
||||
source_damage_anisoDuctile_output !< name of each post result output
|
||||
|
||||
integer(pInt), dimension(:), allocatable, target, public :: &
|
||||
source_damage_anisoDuctile_Noutput !< number of outputs per instance of this damage
|
||||
|
||||
integer(pInt), dimension(:), allocatable, private :: &
|
||||
source_damage_anisoDuctile_totalNslip !< total number of slip systems
|
||||
|
||||
integer(pInt), dimension(:,:), allocatable, private :: &
|
||||
source_damage_anisoDuctile_Nslip !< number of slip systems per family
|
||||
|
@ -42,9 +36,6 @@ module source_damage_anisoDuctile
|
|||
damage_drivingforce_ID
|
||||
end enum
|
||||
|
||||
integer(kind(undefined_ID)), dimension(:,:), allocatable, private :: &
|
||||
source_damage_anisoDuctile_outputID !< ID of each post result output
|
||||
|
||||
|
||||
type, private :: tParameters !< container type for internal constitutive parameters
|
||||
real(pReal) :: &
|
||||
|
@ -159,17 +150,13 @@ subroutine source_damage_anisoDuctile_init(fileUnit)
|
|||
enddo
|
||||
enddo
|
||||
|
||||
allocate(source_damage_anisoDuctile_sizePostResults(Ninstance), source=0_pInt)
|
||||
allocate(source_damage_anisoDuctile_sizePostResult(maxval(phase_Noutput),Ninstance),source=0_pInt)
|
||||
allocate(source_damage_anisoDuctile_output(maxval(phase_Noutput),Ninstance))
|
||||
source_damage_anisoDuctile_output = ''
|
||||
allocate(source_damage_anisoDuctile_outputID(maxval(phase_Noutput),Ninstance), source=undefined_ID)
|
||||
allocate(source_damage_anisoDuctile_Noutput(Ninstance), source=0_pInt)
|
||||
|
||||
allocate(source_damage_anisoDuctile_critLoad(lattice_maxNslipFamily,Ninstance), source=0.0_pReal)
|
||||
allocate(source_damage_anisoDuctile_critPlasticStrain(lattice_maxNslipFamily,Ninstance),source=0.0_pReal)
|
||||
allocate(source_damage_anisoDuctile_Nslip(lattice_maxNslipFamily,Ninstance), source=0_pInt)
|
||||
allocate(source_damage_anisoDuctile_totalNslip(Ninstance), source=0_pInt)
|
||||
|
||||
allocate(param(Ninstance))
|
||||
|
||||
|
@ -201,7 +188,11 @@ subroutine source_damage_anisoDuctile_init(fileUnit)
|
|||
do i=1_pInt, size(outputs)
|
||||
outputID = undefined_ID
|
||||
select case(outputs(i))
|
||||
|
||||
case ('anisoductile_drivingforce')
|
||||
source_damage_anisoDuctile_sizePostResult(i,source_damage_anisoDuctile_instance(p)) = 1_pInt
|
||||
source_damage_anisoDuctile_output(i,source_damage_anisoDuctile_instance(p)) = outputs(i)
|
||||
prm%outputID = [prm%outputID, damage_drivingforce_ID]
|
||||
|
||||
end select
|
||||
|
||||
|
@ -209,6 +200,16 @@ subroutine source_damage_anisoDuctile_init(fileUnit)
|
|||
|
||||
end associate
|
||||
|
||||
phase = p
|
||||
|
||||
NofMyPhase=count(material_phase==phase)
|
||||
instance = source_damage_anisoDuctile_instance(phase)
|
||||
sourceOffset = source_damage_anisoDuctile_offset(phase)
|
||||
|
||||
call material_allocateSourceState(phase,sourceOffset,NofMyPhase,1_pInt)
|
||||
sourceState(phase)%p(sourceOffset)%sizePostResults = sum(source_damage_anisoDuctile_sizePostResult(:,instance))
|
||||
sourceState(phase)%p(sourceOffset)%aTolState=param(instance)%aTol
|
||||
|
||||
enddo
|
||||
|
||||
rewind(fileUnit)
|
||||
|
@ -233,14 +234,6 @@ subroutine source_damage_anisoDuctile_init(fileUnit)
|
|||
chunkPos = IO_stringPos(line)
|
||||
tag = IO_lc(IO_stringValue(line,chunkPos,1_pInt)) ! extract key
|
||||
select case(tag)
|
||||
case ('(output)')
|
||||
select case(IO_lc(IO_stringValue(line,chunkPos,2_pInt)))
|
||||
case ('anisoductile_drivingforce')
|
||||
source_damage_anisoDuctile_Noutput(instance) = source_damage_anisoDuctile_Noutput(instance) + 1_pInt
|
||||
source_damage_anisoDuctile_outputID(source_damage_anisoDuctile_Noutput(instance),instance) = damage_drivingforce_ID
|
||||
source_damage_anisoDuctile_output(source_damage_anisoDuctile_Noutput(instance),instance) = &
|
||||
IO_lc(IO_stringValue(line,chunkPos,2_pInt))
|
||||
end select
|
||||
|
||||
case ('nslip') !
|
||||
Nchunks_SlipFamilies = chunkPos(1) - 1_pInt
|
||||
|
@ -267,10 +260,6 @@ subroutine source_damage_anisoDuctile_init(fileUnit)
|
|||
sanityChecks: do phase = 1_pInt, size(phase_source)
|
||||
myPhase: if (any(phase_source(:,phase) == SOURCE_damage_anisoDuctile_ID)) then
|
||||
instance = source_damage_anisoDuctile_instance(phase)
|
||||
source_damage_anisoDuctile_Nslip(1:lattice_maxNslipFamily,instance) = &
|
||||
min(lattice_NslipSystem(1:lattice_maxNslipFamily,phase),& ! limit active cleavage systems per family to min of available and requested
|
||||
source_damage_anisoDuctile_Nslip(1:lattice_maxNslipFamily,instance))
|
||||
source_damage_anisoDuctile_totalNslip(instance) = sum(source_damage_anisoDuctile_Nslip(:,instance))
|
||||
|
||||
if (any(source_damage_anisoDuctile_critPlasticStrain(:,instance) < 0.0_pReal)) &
|
||||
call IO_error(211_pInt,el=instance,ext_msg='criticaPlasticStrain ('//SOURCE_damage_anisoDuctile_LABEL//')')
|
||||
|
@ -278,34 +267,6 @@ subroutine source_damage_anisoDuctile_init(fileUnit)
|
|||
endif myPhase
|
||||
enddo sanityChecks
|
||||
|
||||
|
||||
initializeInstances: do phase = 1_pInt, material_Nphase
|
||||
if (any(phase_source(:,phase) == SOURCE_damage_anisoDuctile_ID)) then
|
||||
NofMyPhase=count(material_phase==phase)
|
||||
instance = source_damage_anisoDuctile_instance(phase)
|
||||
sourceOffset = source_damage_anisoDuctile_offset(phase)
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
! Determine size of postResults array
|
||||
outputsLoop: do o = 1_pInt,source_damage_anisoDuctile_Noutput(instance)
|
||||
select case(source_damage_anisoDuctile_outputID(o,instance))
|
||||
case(damage_drivingforce_ID)
|
||||
mySize = 1_pInt
|
||||
end select
|
||||
|
||||
if (mySize > 0_pInt) then ! any meaningful output found
|
||||
source_damage_anisoDuctile_sizePostResult(o,instance) = mySize
|
||||
source_damage_anisoDuctile_sizePostResults(instance) = source_damage_anisoDuctile_sizePostResults(instance) + mySize
|
||||
endif
|
||||
enddo outputsLoop
|
||||
|
||||
call material_allocateSourceState(phase,sourceOffset,NofMyPhase,1_pInt)
|
||||
sourceState(phase)%p(sourceOffset)%sizePostResults = source_damage_anisoDuctile_sizePostResults(instance)
|
||||
sourceState(phase)%p(sourceOffset)%aTolState=param(instance)%aTol
|
||||
|
||||
endif
|
||||
|
||||
enddo initializeInstances
|
||||
end subroutine source_damage_anisoDuctile_init
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
|
@ -398,8 +359,8 @@ function source_damage_anisoDuctile_postResults(phase, constituent)
|
|||
integer(pInt), intent(in) :: &
|
||||
phase, &
|
||||
constituent
|
||||
real(pReal), dimension(source_damage_anisoDuctile_sizePostResults( &
|
||||
source_damage_anisoDuctile_instance(phase))) :: &
|
||||
real(pReal), dimension(sum(source_damage_anisoDuctile_sizePostResult(:, &
|
||||
source_damage_anisoDuctile_instance(phase)))) :: &
|
||||
source_damage_anisoDuctile_postResults
|
||||
|
||||
integer(pInt) :: &
|
||||
|
@ -409,10 +370,9 @@ function source_damage_anisoDuctile_postResults(phase, constituent)
|
|||
sourceOffset = source_damage_anisoDuctile_offset(phase)
|
||||
|
||||
c = 0_pInt
|
||||
source_damage_anisoDuctile_postResults = 0.0_pReal
|
||||
|
||||
do o = 1_pInt,source_damage_anisoDuctile_Noutput(instance)
|
||||
select case(source_damage_anisoDuctile_outputID(o,instance))
|
||||
do o = 1_pInt,size(param(instance)%outputID)
|
||||
select case(param(instance)%outputID(o))
|
||||
case (damage_drivingforce_ID)
|
||||
source_damage_anisoDuctile_postResults(c+1_pInt) = &
|
||||
sourceState(phase)%p(sourceOffset)%state(1,constituent)
|
||||
|
|
|
@ -12,7 +12,6 @@ module source_damage_isoBrittle
|
|||
implicit none
|
||||
private
|
||||
integer(pInt), dimension(:), allocatable, public, protected :: &
|
||||
source_damage_isoBrittle_sizePostResults, & !< cumulative size of post results
|
||||
source_damage_isoBrittle_offset, & !< which source is my current damage mechanism?
|
||||
source_damage_isoBrittle_instance !< instance of damage source mechanism
|
||||
|
||||
|
@ -22,17 +21,11 @@ module source_damage_isoBrittle
|
|||
character(len=64), dimension(:,:), allocatable, target, public :: &
|
||||
source_damage_isoBrittle_output !< name of each post result output
|
||||
|
||||
integer(pInt), dimension(:), allocatable, target, public :: &
|
||||
source_damage_isoBrittle_Noutput !< number of outputs per instance of this damage
|
||||
|
||||
enum, bind(c)
|
||||
enumerator :: undefined_ID, &
|
||||
damage_drivingforce_ID
|
||||
end enum !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!11 ToDo
|
||||
|
||||
integer(kind(undefined_ID)), dimension(:,:), allocatable, private :: &
|
||||
source_damage_isoBrittle_outputID !< ID of each post result output
|
||||
|
||||
|
||||
type, private :: tParameters !< container type for internal constitutive parameters
|
||||
real(pReal) :: &
|
||||
|
@ -59,7 +52,7 @@ contains
|
|||
!> @brief module initialization
|
||||
!> @details reads in material parameters, allocates arrays, and does sanity checks
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine source_damage_isoBrittle_init(fileUnit)
|
||||
subroutine source_damage_isoBrittle_init
|
||||
#if defined(__GFORTRAN__) || __INTEL_COMPILER >= 1800
|
||||
use, intrinsic :: iso_fortran_env, only: &
|
||||
compiler_version, &
|
||||
|
@ -72,14 +65,6 @@ subroutine source_damage_isoBrittle_init(fileUnit)
|
|||
debug_constitutive,&
|
||||
debug_levelBasic
|
||||
use IO, only: &
|
||||
IO_read, &
|
||||
IO_lc, &
|
||||
IO_getTag, &
|
||||
IO_isBlank, &
|
||||
IO_stringPos, &
|
||||
IO_stringValue, &
|
||||
IO_floatValue, &
|
||||
IO_intValue, &
|
||||
IO_warning, &
|
||||
IO_error, &
|
||||
IO_timeStamp, &
|
||||
|
@ -99,14 +84,9 @@ subroutine source_damage_isoBrittle_init(fileUnit)
|
|||
MATERIAL_partPhase
|
||||
|
||||
implicit none
|
||||
integer(pInt), intent(in) :: fileUnit
|
||||
|
||||
integer(pInt), allocatable, dimension(:) :: chunkPos
|
||||
integer(pInt) :: Ninstance,mySize=0_pInt,phase,instance,source,sourceOffset,o
|
||||
integer(pInt) :: Ninstance,phase,instance,source,sourceOffset,o
|
||||
integer(pInt) :: NofMyPhase,p,i
|
||||
character(len=65536) :: &
|
||||
tag = '', &
|
||||
line = ''
|
||||
character(len=65536), dimension(0), parameter :: emptyStringArray = [character(len=65536)::]
|
||||
integer(kind(undefined_ID)) :: &
|
||||
outputID
|
||||
|
@ -136,12 +116,9 @@ subroutine source_damage_isoBrittle_init(fileUnit)
|
|||
enddo
|
||||
enddo
|
||||
|
||||
allocate(source_damage_isoBrittle_sizePostResults(Ninstance), source=0_pInt)
|
||||
allocate(source_damage_isoBrittle_sizePostResult(maxval(phase_Noutput),Ninstance),source=0_pInt)
|
||||
allocate(source_damage_isoBrittle_output(maxval(phase_Noutput),Ninstance))
|
||||
source_damage_isoBrittle_output = ''
|
||||
allocate(source_damage_isoBrittle_outputID(maxval(phase_Noutput),Ninstance), source=undefined_ID)
|
||||
allocate(source_damage_isoBrittle_Noutput(Ninstance), source=0_pInt)
|
||||
|
||||
allocate(param(Ninstance))
|
||||
|
||||
|
@ -173,7 +150,11 @@ subroutine source_damage_isoBrittle_init(fileUnit)
|
|||
do i=1_pInt, size(outputs)
|
||||
outputID = undefined_ID
|
||||
select case(outputs(i))
|
||||
|
||||
case ('isobrittle_drivingforce')
|
||||
source_damage_isoBrittle_sizePostResult(i,source_damage_isoBrittle_instance(p)) = 1_pInt
|
||||
source_damage_isoBrittle_output(i,source_damage_isoBrittle_instance(p)) = outputs(i)
|
||||
prm%outputID = [prm%outputID, damage_drivingforce_ID]
|
||||
|
||||
end select
|
||||
|
||||
|
@ -181,70 +162,18 @@ subroutine source_damage_isoBrittle_init(fileUnit)
|
|||
|
||||
end associate
|
||||
|
||||
enddo
|
||||
phase = p
|
||||
|
||||
rewind(fileUnit)
|
||||
phase = 0_pInt
|
||||
do while (trim(line) /= IO_EOF .and. IO_lc(IO_getTag(line,'<','>')) /= MATERIAL_partPhase) ! wind forward to <phase>
|
||||
line = IO_read(fileUnit)
|
||||
enddo
|
||||
|
||||
parsingFile: do while (trim(line) /= IO_EOF) ! read through sections of phase part
|
||||
line = IO_read(fileUnit)
|
||||
if (IO_isBlank(line)) cycle ! skip empty lines
|
||||
if (IO_getTag(line,'<','>') /= '') then ! stop at next part
|
||||
line = IO_read(fileUnit, .true.) ! reset IO_read
|
||||
exit
|
||||
endif
|
||||
if (IO_getTag(line,'[',']') /= '') then ! next phase section
|
||||
phase = phase + 1_pInt ! advance phase section counter
|
||||
cycle ! skip to next line
|
||||
endif
|
||||
if (phase > 0_pInt ) then; if (any(phase_source(:,phase) == SOURCE_damage_isoBrittle_ID)) then ! do not short-circuit here (.and. with next if statemen). It's not safe in Fortran
|
||||
instance = source_damage_isoBrittle_instance(phase) ! which instance of my damage is present phase
|
||||
chunkPos = IO_stringPos(line)
|
||||
tag = IO_lc(IO_stringValue(line,chunkPos,1_pInt)) ! extract key
|
||||
select case(tag)
|
||||
case ('(output)')
|
||||
select case(IO_lc(IO_stringValue(line,chunkPos,2_pInt)))
|
||||
case ('isobrittle_drivingforce')
|
||||
source_damage_isoBrittle_Noutput(instance) = source_damage_isoBrittle_Noutput(instance) + 1_pInt
|
||||
source_damage_isoBrittle_outputID(source_damage_isoBrittle_Noutput(instance),instance) = damage_drivingforce_ID
|
||||
source_damage_isoBrittle_output(source_damage_isoBrittle_Noutput(instance),instance) = &
|
||||
IO_lc(IO_stringValue(line,chunkPos,2_pInt))
|
||||
end select
|
||||
|
||||
end select
|
||||
endif; endif
|
||||
enddo parsingFile
|
||||
|
||||
|
||||
initializeInstances: do phase = 1_pInt, material_Nphase
|
||||
if (any(phase_source(:,phase) == SOURCE_damage_isoBrittle_ID)) then
|
||||
NofMyPhase=count(material_phase==phase)
|
||||
instance = source_damage_isoBrittle_instance(phase)
|
||||
sourceOffset = source_damage_isoBrittle_offset(phase)
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
! Determine size of postResults array
|
||||
outputsLoop: do o = 1_pInt,source_damage_isoBrittle_Noutput(instance)
|
||||
select case(source_damage_isoBrittle_outputID(o,instance))
|
||||
case(damage_drivingforce_ID)
|
||||
mySize = 1_pInt
|
||||
end select
|
||||
|
||||
if (mySize > 0_pInt) then ! any meaningful output found
|
||||
source_damage_isoBrittle_sizePostResult(o,instance) = mySize
|
||||
source_damage_isoBrittle_sizePostResults(instance) = source_damage_isoBrittle_sizePostResults(instance) + mySize
|
||||
endif
|
||||
enddo outputsLoop
|
||||
|
||||
call material_allocateSourceState(phase,sourceOffset,NofMyPhase,1_pInt)
|
||||
sourceState(phase)%p(sourceOffset)%sizePostResults = source_damage_isoBrittle_sizePostResults(instance)
|
||||
sourceState(phase)%p(sourceOffset)%sizePostResults = sum(source_damage_isoBrittle_sizePostResult(:,instance))
|
||||
sourceState(phase)%p(sourceOffset)%aTolState=param(instance)%aTol
|
||||
|
||||
endif
|
||||
enddo
|
||||
|
||||
enddo initializeInstances
|
||||
end subroutine source_damage_isoBrittle_init
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
|
@ -341,8 +270,8 @@ function source_damage_isoBrittle_postResults(phase, constituent)
|
|||
integer(pInt), intent(in) :: &
|
||||
phase, &
|
||||
constituent
|
||||
real(pReal), dimension(source_damage_isoBrittle_sizePostResults( &
|
||||
source_damage_isoBrittle_instance(phase))) :: &
|
||||
real(pReal), dimension(sum(source_damage_isoBrittle_sizePostResult(:, &
|
||||
source_damage_isoBrittle_instance(phase)))) :: &
|
||||
source_damage_isoBrittle_postResults
|
||||
|
||||
integer(pInt) :: &
|
||||
|
@ -352,10 +281,9 @@ function source_damage_isoBrittle_postResults(phase, constituent)
|
|||
sourceOffset = source_damage_isoBrittle_offset(phase)
|
||||
|
||||
c = 0_pInt
|
||||
source_damage_isoBrittle_postResults = 0.0_pReal
|
||||
|
||||
do o = 1_pInt,source_damage_isoBrittle_Noutput(instance)
|
||||
select case(source_damage_isoBrittle_outputID(o,instance))
|
||||
do o = 1_pInt,size(param(instance)%outputID)
|
||||
select case(param(instance)%outputID(o))
|
||||
case (damage_drivingforce_ID)
|
||||
source_damage_isoBrittle_postResults(c+1_pInt) = sourceState(phase)%p(sourceOffset)%state(1,constituent)
|
||||
c = c + 1
|
||||
|
|
|
@ -12,7 +12,6 @@ module source_damage_isoDuctile
|
|||
implicit none
|
||||
private
|
||||
integer(pInt), dimension(:), allocatable, public, protected :: &
|
||||
source_damage_isoDuctile_sizePostResults, & !< cumulative size of post results
|
||||
source_damage_isoDuctile_offset, & !< which source is my current damage mechanism?
|
||||
source_damage_isoDuctile_instance !< instance of damage source mechanism
|
||||
|
||||
|
@ -22,19 +21,12 @@ module source_damage_isoDuctile
|
|||
character(len=64), dimension(:,:), allocatable, target, public :: &
|
||||
source_damage_isoDuctile_output !< name of each post result output
|
||||
|
||||
integer(pInt), dimension(:), allocatable, target, public :: &
|
||||
source_damage_isoDuctile_Noutput !< number of outputs per instance of this damage
|
||||
|
||||
|
||||
enum, bind(c)
|
||||
enumerator :: undefined_ID, &
|
||||
damage_drivingforce_ID
|
||||
end enum !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!11 ToDo
|
||||
|
||||
integer(kind(undefined_ID)), dimension(:,:), allocatable, private :: &
|
||||
source_damage_isoDuctile_outputID !< ID of each post result output
|
||||
|
||||
|
||||
type, private :: tParameters !< container type for internal constitutive parameters
|
||||
real(pReal) :: &
|
||||
critPlasticStrain, &
|
||||
|
@ -60,7 +52,7 @@ contains
|
|||
!> @brief module initialization
|
||||
!> @details reads in material parameters, allocates arrays, and does sanity checks
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine source_damage_isoDuctile_init(fileUnit)
|
||||
subroutine source_damage_isoDuctile_init
|
||||
#if defined(__GFORTRAN__) || __INTEL_COMPILER >= 1800
|
||||
use, intrinsic :: iso_fortran_env, only: &
|
||||
compiler_version, &
|
||||
|
@ -73,14 +65,6 @@ subroutine source_damage_isoDuctile_init(fileUnit)
|
|||
debug_constitutive,&
|
||||
debug_levelBasic
|
||||
use IO, only: &
|
||||
IO_read, &
|
||||
IO_lc, &
|
||||
IO_getTag, &
|
||||
IO_isBlank, &
|
||||
IO_stringPos, &
|
||||
IO_stringValue, &
|
||||
IO_floatValue, &
|
||||
IO_intValue, &
|
||||
IO_warning, &
|
||||
IO_error, &
|
||||
IO_timeStamp, &
|
||||
|
@ -100,14 +84,9 @@ subroutine source_damage_isoDuctile_init(fileUnit)
|
|||
MATERIAL_partPhase
|
||||
|
||||
implicit none
|
||||
integer(pInt), intent(in) :: fileUnit
|
||||
|
||||
integer(pInt), allocatable, dimension(:) :: chunkPos
|
||||
integer(pInt) :: Ninstance,mySize=0_pInt,phase,instance,source,sourceOffset,o
|
||||
integer(pInt) :: Ninstance,phase,instance,source,sourceOffset,o
|
||||
integer(pInt) :: NofMyPhase,p,i
|
||||
character(len=65536) :: &
|
||||
tag = '', &
|
||||
line = ''
|
||||
character(len=65536), dimension(0), parameter :: emptyStringArray = [character(len=65536)::]
|
||||
integer(kind(undefined_ID)) :: &
|
||||
outputID
|
||||
|
@ -137,12 +116,9 @@ subroutine source_damage_isoDuctile_init(fileUnit)
|
|||
enddo
|
||||
enddo
|
||||
|
||||
allocate(source_damage_isoDuctile_sizePostResults(Ninstance), source=0_pInt)
|
||||
allocate(source_damage_isoDuctile_sizePostResult(maxval(phase_Noutput),Ninstance),source=0_pInt)
|
||||
allocate(source_damage_isoDuctile_output(maxval(phase_Noutput),Ninstance))
|
||||
source_damage_isoDuctile_output = ''
|
||||
allocate(source_damage_isoDuctile_outputID(maxval(phase_Noutput),Ninstance), source=undefined_ID)
|
||||
allocate(source_damage_isoDuctile_Noutput(Ninstance), source=0_pInt)
|
||||
|
||||
allocate(param(Ninstance))
|
||||
|
||||
|
@ -174,7 +150,11 @@ subroutine source_damage_isoDuctile_init(fileUnit)
|
|||
do i=1_pInt, size(outputs)
|
||||
outputID = undefined_ID
|
||||
select case(outputs(i))
|
||||
|
||||
case ('isoductile_drivingforce')
|
||||
source_damage_isoDuctile_sizePostResult(i,source_damage_isoDuctile_instance(p)) = 1_pInt
|
||||
source_damage_isoDuctile_output(i,source_damage_isoDuctile_instance(p)) = outputs(i)
|
||||
prm%outputID = [prm%outputID, damage_drivingforce_ID]
|
||||
|
||||
end select
|
||||
|
||||
|
@ -182,69 +162,18 @@ subroutine source_damage_isoDuctile_init(fileUnit)
|
|||
|
||||
end associate
|
||||
|
||||
enddo
|
||||
|
||||
rewind(fileUnit)
|
||||
phase = 0_pInt
|
||||
do while (trim(line) /= IO_EOF .and. IO_lc(IO_getTag(line,'<','>')) /= MATERIAL_partPhase) ! wind forward to <phase>
|
||||
line = IO_read(fileUnit)
|
||||
enddo
|
||||
|
||||
parsingFile: do while (trim(line) /= IO_EOF) ! read through sections of phase part
|
||||
line = IO_read(fileUnit)
|
||||
if (IO_isBlank(line)) cycle ! skip empty lines
|
||||
if (IO_getTag(line,'<','>') /= '') then ! stop at next part
|
||||
line = IO_read(fileUnit, .true.) ! reset IO_read
|
||||
exit
|
||||
endif
|
||||
if (IO_getTag(line,'[',']') /= '') then ! next phase section
|
||||
phase = phase + 1_pInt ! advance phase section counter
|
||||
cycle ! skip to next line
|
||||
endif
|
||||
if (phase > 0_pInt ) then; if (any(phase_source(:,phase) == SOURCE_damage_isoDuctile_ID)) then ! do not short-circuit here (.and. with next if statemen). It's not safe in Fortran
|
||||
instance = source_damage_isoDuctile_instance(phase) ! which instance of my damage is present phase
|
||||
chunkPos = IO_stringPos(line)
|
||||
tag = IO_lc(IO_stringValue(line,chunkPos,1_pInt)) ! extract key
|
||||
select case(tag)
|
||||
case ('(output)')
|
||||
select case(IO_lc(IO_stringValue(line,chunkPos,2_pInt)))
|
||||
case ('isoductile_drivingforce')
|
||||
source_damage_isoDuctile_Noutput(instance) = source_damage_isoDuctile_Noutput(instance) + 1_pInt
|
||||
source_damage_isoDuctile_outputID(source_damage_isoDuctile_Noutput(instance),instance) = damage_drivingforce_ID
|
||||
source_damage_isoDuctile_output(source_damage_isoDuctile_Noutput(instance),instance) = &
|
||||
IO_lc(IO_stringValue(line,chunkPos,2_pInt))
|
||||
end select
|
||||
|
||||
end select
|
||||
endif; endif
|
||||
enddo parsingFile
|
||||
|
||||
initializeInstances: do phase = 1_pInt, material_Nphase
|
||||
if (any(phase_source(:,phase) == SOURCE_damage_isoDuctile_ID)) then
|
||||
phase = p
|
||||
NofMyPhase=count(material_phase==phase)
|
||||
instance = source_damage_isoDuctile_instance(phase)
|
||||
sourceOffset = source_damage_isoDuctile_offset(phase)
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
! Determine size of postResults array
|
||||
outputsLoop: do o = 1_pInt,source_damage_isoDuctile_Noutput(instance)
|
||||
select case(source_damage_isoDuctile_outputID(o,instance))
|
||||
case(damage_drivingforce_ID)
|
||||
mySize = 1_pInt
|
||||
end select
|
||||
|
||||
if (mySize > 0_pInt) then ! any meaningful output found
|
||||
source_damage_isoDuctile_sizePostResult(o,instance) = mySize
|
||||
source_damage_isoDuctile_sizePostResults(instance) = source_damage_isoDuctile_sizePostResults(instance) + mySize
|
||||
endif
|
||||
enddo outputsLoop
|
||||
|
||||
call material_allocateSourceState(phase,sourceOffset,NofMyPhase,1_pInt)
|
||||
sourceState(phase)%p(sourceOffset)%sizePostResults = source_damage_isoDuctile_sizePostResults(instance)
|
||||
sourceState(phase)%p(sourceOffset)%sizePostResults = sum(source_damage_isoDuctile_sizePostResult(:,instance))
|
||||
sourceState(phase)%p(sourceOffset)%aTolState=param(instance)%aTol
|
||||
|
||||
endif
|
||||
|
||||
enddo initializeInstances
|
||||
enddo
|
||||
|
||||
end subroutine source_damage_isoDuctile_init
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
|
@ -321,8 +250,8 @@ function source_damage_isoDuctile_postResults(phase, constituent)
|
|||
integer(pInt), intent(in) :: &
|
||||
phase, &
|
||||
constituent
|
||||
real(pReal), dimension(source_damage_isoDuctile_sizePostResults( &
|
||||
source_damage_isoDuctile_instance(phase))) :: &
|
||||
real(pReal), dimension(sum(source_damage_isoDuctile_sizePostResult(:, &
|
||||
source_damage_isoDuctile_instance(phase)))) :: &
|
||||
source_damage_isoDuctile_postResults
|
||||
|
||||
integer(pInt) :: &
|
||||
|
@ -332,10 +261,9 @@ function source_damage_isoDuctile_postResults(phase, constituent)
|
|||
sourceOffset = source_damage_isoDuctile_offset(phase)
|
||||
|
||||
c = 0_pInt
|
||||
source_damage_isoDuctile_postResults = 0.0_pReal
|
||||
|
||||
do o = 1_pInt,source_damage_isoDuctile_Noutput(instance)
|
||||
select case(source_damage_isoDuctile_outputID(o,instance))
|
||||
do o = 1_pInt,size(param(instance)%outputID)
|
||||
select case(param(instance)%outputID(o))
|
||||
case (damage_drivingforce_ID)
|
||||
source_damage_isoDuctile_postResults(c+1_pInt) = sourceState(phase)%p(sourceOffset)%state(1,constituent)
|
||||
c = c + 1
|
||||
|
|
Loading…
Reference in New Issue