no need for enums
no performance difference measurable but less complicated code without them
This commit is contained in:
parent
3158b65e59
commit
11d456bcd7
|
@ -25,12 +25,6 @@ module source_damage_anisoBrittle
|
||||||
integer, dimension(:,:), allocatable :: &
|
integer, dimension(:,:), allocatable :: &
|
||||||
source_damage_anisoBrittle_Ncleavage !< number of cleavage systems per family
|
source_damage_anisoBrittle_Ncleavage !< number of cleavage systems per family
|
||||||
|
|
||||||
enum, bind(c)
|
|
||||||
enumerator :: undefined_ID, &
|
|
||||||
damage_drivingforce_ID
|
|
||||||
end enum
|
|
||||||
|
|
||||||
|
|
||||||
type :: tParameters !< container type for internal constitutive parameters
|
type :: tParameters !< container type for internal constitutive parameters
|
||||||
real(pReal) :: &
|
real(pReal) :: &
|
||||||
aTol, &
|
aTol, &
|
||||||
|
@ -45,8 +39,8 @@ module source_damage_anisoBrittle
|
||||||
totalNcleavage
|
totalNcleavage
|
||||||
integer, dimension(:), allocatable :: &
|
integer, dimension(:), allocatable :: &
|
||||||
Ncleavage
|
Ncleavage
|
||||||
integer(kind(undefined_ID)), allocatable, dimension(:) :: &
|
character(len=pStringLen), allocatable, dimension(:) :: &
|
||||||
outputID !< ID of each post result output
|
output
|
||||||
end type tParameters
|
end type tParameters
|
||||||
|
|
||||||
type(tParameters), dimension(:), allocatable :: param !< containers of constitutive parameters (len Ninstance)
|
type(tParameters), dimension(:), allocatable :: param !< containers of constitutive parameters (len Ninstance)
|
||||||
|
@ -67,13 +61,9 @@ contains
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
subroutine source_damage_anisoBrittle_init
|
subroutine source_damage_anisoBrittle_init
|
||||||
|
|
||||||
integer :: Ninstance,instance,source,sourceOffset,NofMyPhase,p,i
|
integer :: Ninstance,instance,source,sourceOffset,NofMyPhase,p
|
||||||
integer(kind(undefined_ID)) :: &
|
|
||||||
outputID
|
|
||||||
character(len=pStringLen) :: &
|
character(len=pStringLen) :: &
|
||||||
extmsg = ''
|
extmsg = ''
|
||||||
character(len=pStringLen), dimension(:), allocatable :: &
|
|
||||||
outputs
|
|
||||||
|
|
||||||
write(6,'(/,a)') ' <<<+- source_'//SOURCE_DAMAGE_ANISOBRITTLE_LABEL//' init -+>>>'; flush(6)
|
write(6,'(/,a)') ' <<<+- source_'//SOURCE_DAMAGE_ANISOBRITTLE_LABEL//' init -+>>>'; flush(6)
|
||||||
|
|
||||||
|
@ -125,18 +115,7 @@ subroutine source_damage_anisoBrittle_init
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! output pararameters
|
! output pararameters
|
||||||
outputs = config%getStrings('(output)',defaultVal=emptyStringArray)
|
prm%output = config%getStrings('(output)',defaultVal=emptyStringArray)
|
||||||
allocate(prm%outputID(0))
|
|
||||||
do i=1, size(outputs)
|
|
||||||
outputID = undefined_ID
|
|
||||||
select case(outputs(i))
|
|
||||||
|
|
||||||
case ('anisobrittle_drivingforce')
|
|
||||||
prm%outputID = [prm%outputID, damage_drivingforce_ID]
|
|
||||||
|
|
||||||
end select
|
|
||||||
|
|
||||||
enddo
|
|
||||||
|
|
||||||
NofMyPhase=count(material_phaseAt==p) * discretization_nIP
|
NofMyPhase=count(material_phaseAt==p) * discretization_nIP
|
||||||
instance = source_damage_anisoBrittle_instance(p)
|
instance = source_damage_anisoBrittle_instance(p)
|
||||||
|
@ -244,15 +223,14 @@ subroutine source_damage_anisoBrittle_results(phase,group)
|
||||||
|
|
||||||
integer, intent(in) :: phase
|
integer, intent(in) :: phase
|
||||||
character(len=*), intent(in) :: group
|
character(len=*), intent(in) :: group
|
||||||
integer :: sourceOffset, o, instance
|
|
||||||
|
|
||||||
instance = source_damage_anisoBrittle_instance(phase)
|
integer :: o
|
||||||
sourceOffset = source_damage_anisoBrittle_offset(phase)
|
|
||||||
|
|
||||||
associate(prm => param(instance), stt => sourceState(phase)%p(sourceOffset)%state)
|
associate(prm => param(source_damage_anisoBrittle_instance(phase)), &
|
||||||
outputsLoop: do o = 1,size(prm%outputID)
|
stt => sourceState(phase)%p(source_damage_anisoBrittle_offset(phase))%state)
|
||||||
select case(prm%outputID(o))
|
outputsLoop: do o = 1,size(prm%output)
|
||||||
case (damage_drivingforce_ID)
|
select case(trim(prm%output(o)))
|
||||||
|
case ('anisobrittle_drivingforce')
|
||||||
call results_writeDataset(group,stt,'tbd','driving force','tbd')
|
call results_writeDataset(group,stt,'tbd','driving force','tbd')
|
||||||
end select
|
end select
|
||||||
enddo outputsLoop
|
enddo outputsLoop
|
||||||
|
|
|
@ -21,12 +21,6 @@ module source_damage_anisoDuctile
|
||||||
source_damage_anisoDuctile_offset, & !< which source is my current damage mechanism?
|
source_damage_anisoDuctile_offset, & !< which source is my current damage mechanism?
|
||||||
source_damage_anisoDuctile_instance !< instance of damage source mechanism
|
source_damage_anisoDuctile_instance !< instance of damage source mechanism
|
||||||
|
|
||||||
enum, bind(c)
|
|
||||||
enumerator :: undefined_ID, &
|
|
||||||
damage_drivingforce_ID
|
|
||||||
end enum
|
|
||||||
|
|
||||||
|
|
||||||
type, private :: tParameters !< container type for internal constitutive parameters
|
type, private :: tParameters !< container type for internal constitutive parameters
|
||||||
real(pReal) :: &
|
real(pReal) :: &
|
||||||
aTol, &
|
aTol, &
|
||||||
|
@ -37,8 +31,8 @@ module source_damage_anisoDuctile
|
||||||
totalNslip
|
totalNslip
|
||||||
integer, dimension(:), allocatable :: &
|
integer, dimension(:), allocatable :: &
|
||||||
Nslip
|
Nslip
|
||||||
integer(kind(undefined_ID)), allocatable, dimension(:) :: &
|
character(len=pStringLen), allocatable, dimension(:) :: &
|
||||||
outputID
|
output
|
||||||
end type tParameters
|
end type tParameters
|
||||||
|
|
||||||
type(tParameters), dimension(:), allocatable, private :: param !< containers of constitutive parameters (len Ninstance)
|
type(tParameters), dimension(:), allocatable, private :: param !< containers of constitutive parameters (len Ninstance)
|
||||||
|
@ -59,13 +53,9 @@ contains
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
subroutine source_damage_anisoDuctile_init
|
subroutine source_damage_anisoDuctile_init
|
||||||
|
|
||||||
integer :: Ninstance,instance,source,sourceOffset,NofMyPhase,p,i
|
integer :: Ninstance,instance,source,sourceOffset,NofMyPhase,p
|
||||||
integer(kind(undefined_ID)) :: &
|
|
||||||
outputID
|
|
||||||
character(len=pStringLen) :: &
|
character(len=pStringLen) :: &
|
||||||
extmsg = ''
|
extmsg = ''
|
||||||
character(len=pStringLen), dimension(:), allocatable :: &
|
|
||||||
outputs
|
|
||||||
|
|
||||||
write(6,'(/,a)') ' <<<+- source_'//SOURCE_DAMAGE_ANISODUCTILE_LABEL//' init -+>>>'; flush(6)
|
write(6,'(/,a)') ' <<<+- source_'//SOURCE_DAMAGE_ANISODUCTILE_LABEL//' init -+>>>'; flush(6)
|
||||||
|
|
||||||
|
@ -107,18 +97,7 @@ subroutine source_damage_anisoDuctile_init
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! output pararameters
|
! output pararameters
|
||||||
outputs = config%getStrings('(output)',defaultVal=emptyStringArray)
|
prm%output = config%getStrings('(output)',defaultVal=emptyStringArray)
|
||||||
allocate(prm%outputID(0))
|
|
||||||
do i=1, size(outputs)
|
|
||||||
outputID = undefined_ID
|
|
||||||
select case(outputs(i))
|
|
||||||
|
|
||||||
case ('anisoductile_drivingforce')
|
|
||||||
prm%outputID = [prm%outputID, damage_drivingforce_ID]
|
|
||||||
|
|
||||||
end select
|
|
||||||
|
|
||||||
enddo
|
|
||||||
|
|
||||||
NofMyPhase=count(material_phaseAt==p) * discretization_nIP
|
NofMyPhase=count(material_phaseAt==p) * discretization_nIP
|
||||||
instance = source_damage_anisoDuctile_instance(p)
|
instance = source_damage_anisoDuctile_instance(p)
|
||||||
|
@ -201,15 +180,14 @@ subroutine source_damage_anisoDuctile_results(phase,group)
|
||||||
|
|
||||||
integer, intent(in) :: phase
|
integer, intent(in) :: phase
|
||||||
character(len=*), intent(in) :: group
|
character(len=*), intent(in) :: group
|
||||||
integer :: sourceOffset, o, instance
|
|
||||||
|
|
||||||
instance = source_damage_anisoDuctile_instance(phase)
|
integer :: o
|
||||||
sourceOffset = source_damage_anisoDuctile_offset(phase)
|
|
||||||
|
|
||||||
associate(prm => param(instance), stt => sourceState(phase)%p(sourceOffset)%state)
|
associate(prm => param(source_damage_anisoDuctile_instance(phase)), &
|
||||||
outputsLoop: do o = 1,size(prm%outputID)
|
stt => sourceState(phase)%p(source_damage_anisoDuctile_offset(phase))%state)
|
||||||
select case(prm%outputID(o))
|
outputsLoop: do o = 1,size(prm%output)
|
||||||
case (damage_drivingforce_ID)
|
select case(trim(prm%output(o)))
|
||||||
|
case ('anisoductile_drivingforce')
|
||||||
call results_writeDataset(group,stt,'tbd','driving force','tbd')
|
call results_writeDataset(group,stt,'tbd','driving force','tbd')
|
||||||
end select
|
end select
|
||||||
enddo outputsLoop
|
enddo outputsLoop
|
||||||
|
|
|
@ -20,20 +20,13 @@ module source_damage_isoBrittle
|
||||||
source_damage_isoBrittle_offset, &
|
source_damage_isoBrittle_offset, &
|
||||||
source_damage_isoBrittle_instance
|
source_damage_isoBrittle_instance
|
||||||
|
|
||||||
enum, bind(c)
|
|
||||||
enumerator :: &
|
|
||||||
undefined_ID, &
|
|
||||||
damage_drivingforce_ID
|
|
||||||
end enum
|
|
||||||
|
|
||||||
|
|
||||||
type, private :: tParameters !< container type for internal constitutive parameters
|
type, private :: tParameters !< container type for internal constitutive parameters
|
||||||
real(pReal) :: &
|
real(pReal) :: &
|
||||||
critStrainEnergy, &
|
critStrainEnergy, &
|
||||||
N, &
|
N, &
|
||||||
aTol
|
aTol
|
||||||
integer(kind(undefined_ID)), allocatable, dimension(:) :: &
|
character(len=pStringLen), allocatable, dimension(:) :: &
|
||||||
outputID
|
output
|
||||||
end type tParameters
|
end type tParameters
|
||||||
|
|
||||||
type(tParameters), dimension(:), allocatable :: param !< containers of constitutive parameters (len Ninstance)
|
type(tParameters), dimension(:), allocatable :: param !< containers of constitutive parameters (len Ninstance)
|
||||||
|
@ -54,13 +47,9 @@ contains
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
subroutine source_damage_isoBrittle_init
|
subroutine source_damage_isoBrittle_init
|
||||||
|
|
||||||
integer :: Ninstance,instance,source,sourceOffset,NofMyPhase,p,i
|
integer :: Ninstance,instance,source,sourceOffset,NofMyPhase,p
|
||||||
integer(kind(undefined_ID)) :: &
|
|
||||||
outputID
|
|
||||||
character(len=pStringLen) :: &
|
character(len=pStringLen) :: &
|
||||||
extmsg = ''
|
extmsg = ''
|
||||||
character(len=pStringLen), dimension(:), allocatable :: &
|
|
||||||
outputs
|
|
||||||
|
|
||||||
write(6,'(/,a)') ' <<<+- source_'//SOURCE_DAMAGE_ISOBRITTLE_LABEL//' init -+>>>'; flush(6)
|
write(6,'(/,a)') ' <<<+- source_'//SOURCE_DAMAGE_ISOBRITTLE_LABEL//' init -+>>>'; flush(6)
|
||||||
|
|
||||||
|
@ -99,18 +88,7 @@ subroutine source_damage_isoBrittle_init
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! output pararameters
|
! output pararameters
|
||||||
outputs = config%getStrings('(output)',defaultVal=emptyStringArray)
|
prm%output = config%getStrings('(output)',defaultVal=emptyStringArray)
|
||||||
allocate(prm%outputID(0))
|
|
||||||
do i=1, size(outputs)
|
|
||||||
outputID = undefined_ID
|
|
||||||
select case(outputs(i))
|
|
||||||
|
|
||||||
case ('isobrittle_drivingforce')
|
|
||||||
prm%outputID = [prm%outputID, damage_drivingforce_ID]
|
|
||||||
|
|
||||||
end select
|
|
||||||
|
|
||||||
enddo
|
|
||||||
|
|
||||||
NofMyPhase = count(material_phaseAt==p) * discretization_nIP
|
NofMyPhase = count(material_phaseAt==p) * discretization_nIP
|
||||||
instance = source_damage_isoBrittle_instance(p)
|
instance = source_damage_isoBrittle_instance(p)
|
||||||
|
@ -201,15 +179,14 @@ subroutine source_damage_isoBrittle_results(phase,group)
|
||||||
|
|
||||||
integer, intent(in) :: phase
|
integer, intent(in) :: phase
|
||||||
character(len=*), intent(in) :: group
|
character(len=*), intent(in) :: group
|
||||||
integer :: sourceOffset, o, instance
|
|
||||||
|
|
||||||
instance = source_damage_isoBrittle_instance(phase)
|
integer :: o
|
||||||
sourceOffset = source_damage_isoBrittle_offset(phase)
|
|
||||||
|
|
||||||
associate(prm => param(instance), stt => sourceState(phase)%p(sourceOffset)%state)
|
associate(prm => param(source_damage_isoBrittle_instance(phase)), &
|
||||||
outputsLoop: do o = 1,size(prm%outputID)
|
stt => sourceState(phase)%p(source_damage_isoBrittle_offset(phase))%state)
|
||||||
select case(prm%outputID(o))
|
outputsLoop: do o = 1,size(prm%output)
|
||||||
case (damage_drivingforce_ID)
|
select case(trim(prm%output(o)))
|
||||||
|
case ('isobrittle_drivingforce')
|
||||||
call results_writeDataset(group,stt,'tbd','driving force','tbd')
|
call results_writeDataset(group,stt,'tbd','driving force','tbd')
|
||||||
end select
|
end select
|
||||||
enddo outputsLoop
|
enddo outputsLoop
|
||||||
|
|
|
@ -19,18 +19,13 @@ module source_damage_isoDuctile
|
||||||
source_damage_isoDuctile_offset, & !< which source is my current damage mechanism?
|
source_damage_isoDuctile_offset, & !< which source is my current damage mechanism?
|
||||||
source_damage_isoDuctile_instance !< instance of damage source mechanism
|
source_damage_isoDuctile_instance !< instance of damage source mechanism
|
||||||
|
|
||||||
enum, bind(c)
|
|
||||||
enumerator :: undefined_ID, &
|
|
||||||
damage_drivingforce_ID
|
|
||||||
end enum
|
|
||||||
|
|
||||||
type, private :: tParameters !< container type for internal constitutive parameters
|
type, private :: tParameters !< container type for internal constitutive parameters
|
||||||
real(pReal) :: &
|
real(pReal) :: &
|
||||||
critPlasticStrain, &
|
critPlasticStrain, &
|
||||||
N, &
|
N, &
|
||||||
aTol
|
aTol
|
||||||
integer(kind(undefined_ID)), allocatable, dimension(:) :: &
|
character(len=pStringLen), allocatable, dimension(:) :: &
|
||||||
outputID
|
output
|
||||||
end type tParameters
|
end type tParameters
|
||||||
|
|
||||||
type(tParameters), dimension(:), allocatable, private :: param !< containers of constitutive parameters (len Ninstance)
|
type(tParameters), dimension(:), allocatable, private :: param !< containers of constitutive parameters (len Ninstance)
|
||||||
|
@ -51,13 +46,9 @@ contains
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
subroutine source_damage_isoDuctile_init
|
subroutine source_damage_isoDuctile_init
|
||||||
|
|
||||||
integer :: Ninstance,instance,source,sourceOffset,NofMyPhase,p,i
|
integer :: Ninstance,instance,source,sourceOffset,NofMyPhase,p
|
||||||
integer(kind(undefined_ID)) :: &
|
|
||||||
outputID
|
|
||||||
character(len=pStringLen) :: &
|
character(len=pStringLen) :: &
|
||||||
extmsg = ''
|
extmsg = ''
|
||||||
character(len=pStringLen), dimension(:), allocatable :: &
|
|
||||||
outputs
|
|
||||||
|
|
||||||
write(6,'(/,a)') ' <<<+- source_'//SOURCE_DAMAGE_ISODUCTILE_LABEL//' init -+>>>'; flush(6)
|
write(6,'(/,a)') ' <<<+- source_'//SOURCE_DAMAGE_ISODUCTILE_LABEL//' init -+>>>'; flush(6)
|
||||||
|
|
||||||
|
@ -96,18 +87,7 @@ subroutine source_damage_isoDuctile_init
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! output pararameters
|
! output pararameters
|
||||||
outputs = config%getStrings('(output)',defaultVal=emptyStringArray)
|
prm%output = config%getStrings('(output)',defaultVal=emptyStringArray)
|
||||||
allocate(prm%outputID(0))
|
|
||||||
do i=1, size(outputs)
|
|
||||||
outputID = undefined_ID
|
|
||||||
select case(outputs(i))
|
|
||||||
|
|
||||||
case ('isoductile_drivingforce')
|
|
||||||
prm%outputID = [prm%outputID, damage_drivingforce_ID]
|
|
||||||
|
|
||||||
end select
|
|
||||||
|
|
||||||
enddo
|
|
||||||
|
|
||||||
NofMyPhase=count(material_phaseAt==p) * discretization_nIP
|
NofMyPhase=count(material_phaseAt==p) * discretization_nIP
|
||||||
instance = source_damage_isoDuctile_instance(p)
|
instance = source_damage_isoDuctile_instance(p)
|
||||||
|
@ -181,15 +161,14 @@ subroutine source_damage_isoDuctile_results(phase,group)
|
||||||
|
|
||||||
integer, intent(in) :: phase
|
integer, intent(in) :: phase
|
||||||
character(len=*), intent(in) :: group
|
character(len=*), intent(in) :: group
|
||||||
integer :: sourceOffset, o, instance
|
|
||||||
|
|
||||||
instance = source_damage_isoDuctile_instance(phase)
|
integer :: o
|
||||||
sourceOffset = source_damage_isoDuctile_offset(phase)
|
|
||||||
|
|
||||||
associate(prm => param(instance), stt => sourceState(phase)%p(sourceOffset)%state)
|
associate(prm => param(source_damage_isoDuctile_instance(phase)), &
|
||||||
outputsLoop: do o = 1,size(prm%outputID)
|
stt => sourceState(phase)%p(source_damage_isoDuctile_offset(phase))%state)
|
||||||
select case(prm%outputID(o))
|
outputsLoop: do o = 1,size(prm%output)
|
||||||
case (damage_drivingforce_ID)
|
select case(trim(prm%output(o)))
|
||||||
|
case ('isoductile_drivingforce')
|
||||||
call results_writeDataset(group,stt,'tbd','driving force','tbd')
|
call results_writeDataset(group,stt,'tbd','driving force','tbd')
|
||||||
end select
|
end select
|
||||||
enddo outputsLoop
|
enddo outputsLoop
|
||||||
|
@ -197,5 +176,4 @@ subroutine source_damage_isoDuctile_results(phase,group)
|
||||||
|
|
||||||
end subroutine source_damage_isoDuctile_results
|
end subroutine source_damage_isoDuctile_results
|
||||||
|
|
||||||
|
|
||||||
end module source_damage_isoDuctile
|
end module source_damage_isoDuctile
|
||||||
|
|
Loading…
Reference in New Issue