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 :: &
|
||||
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
|
||||
real(pReal) :: &
|
||||
aTol, &
|
||||
|
@ -45,8 +39,8 @@ module source_damage_anisoBrittle
|
|||
totalNcleavage
|
||||
integer, dimension(:), allocatable :: &
|
||||
Ncleavage
|
||||
integer(kind(undefined_ID)), allocatable, dimension(:) :: &
|
||||
outputID !< ID of each post result output
|
||||
character(len=pStringLen), allocatable, dimension(:) :: &
|
||||
output
|
||||
end type tParameters
|
||||
|
||||
type(tParameters), dimension(:), allocatable :: param !< containers of constitutive parameters (len Ninstance)
|
||||
|
@ -67,13 +61,9 @@ contains
|
|||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine source_damage_anisoBrittle_init
|
||||
|
||||
integer :: Ninstance,instance,source,sourceOffset,NofMyPhase,p,i
|
||||
integer(kind(undefined_ID)) :: &
|
||||
outputID
|
||||
integer :: Ninstance,instance,source,sourceOffset,NofMyPhase,p
|
||||
character(len=pStringLen) :: &
|
||||
extmsg = ''
|
||||
character(len=pStringLen), dimension(:), allocatable :: &
|
||||
outputs
|
||||
|
||||
write(6,'(/,a)') ' <<<+- source_'//SOURCE_DAMAGE_ANISOBRITTLE_LABEL//' init -+>>>'; flush(6)
|
||||
|
||||
|
@ -125,18 +115,7 @@ subroutine source_damage_anisoBrittle_init
|
|||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
! output pararameters
|
||||
outputs = 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
|
||||
prm%output = config%getStrings('(output)',defaultVal=emptyStringArray)
|
||||
|
||||
NofMyPhase=count(material_phaseAt==p) * discretization_nIP
|
||||
instance = source_damage_anisoBrittle_instance(p)
|
||||
|
@ -242,21 +221,20 @@ end subroutine source_damage_anisoBrittle_getRateAndItsTangent
|
|||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine source_damage_anisoBrittle_results(phase,group)
|
||||
|
||||
integer, intent(in) :: phase
|
||||
integer, intent(in) :: phase
|
||||
character(len=*), intent(in) :: group
|
||||
integer :: sourceOffset, o, instance
|
||||
|
||||
instance = source_damage_anisoBrittle_instance(phase)
|
||||
sourceOffset = source_damage_anisoBrittle_offset(phase)
|
||||
integer :: o
|
||||
|
||||
associate(prm => param(instance), stt => sourceState(phase)%p(sourceOffset)%state)
|
||||
outputsLoop: do o = 1,size(prm%outputID)
|
||||
select case(prm%outputID(o))
|
||||
case (damage_drivingforce_ID)
|
||||
call results_writeDataset(group,stt,'tbd','driving force','tbd')
|
||||
end select
|
||||
enddo outputsLoop
|
||||
end associate
|
||||
associate(prm => param(source_damage_anisoBrittle_instance(phase)), &
|
||||
stt => sourceState(phase)%p(source_damage_anisoBrittle_offset(phase))%state)
|
||||
outputsLoop: do o = 1,size(prm%output)
|
||||
select case(trim(prm%output(o)))
|
||||
case ('anisobrittle_drivingforce')
|
||||
call results_writeDataset(group,stt,'tbd','driving force','tbd')
|
||||
end select
|
||||
enddo outputsLoop
|
||||
end associate
|
||||
|
||||
end subroutine source_damage_anisoBrittle_results
|
||||
|
||||
|
|
|
@ -21,12 +21,6 @@ module source_damage_anisoDuctile
|
|||
source_damage_anisoDuctile_offset, & !< which source is my current damage 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
|
||||
real(pReal) :: &
|
||||
aTol, &
|
||||
|
@ -37,8 +31,8 @@ module source_damage_anisoDuctile
|
|||
totalNslip
|
||||
integer, dimension(:), allocatable :: &
|
||||
Nslip
|
||||
integer(kind(undefined_ID)), allocatable, dimension(:) :: &
|
||||
outputID
|
||||
character(len=pStringLen), allocatable, dimension(:) :: &
|
||||
output
|
||||
end type tParameters
|
||||
|
||||
type(tParameters), dimension(:), allocatable, private :: param !< containers of constitutive parameters (len Ninstance)
|
||||
|
@ -59,13 +53,9 @@ contains
|
|||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine source_damage_anisoDuctile_init
|
||||
|
||||
integer :: Ninstance,instance,source,sourceOffset,NofMyPhase,p,i
|
||||
integer(kind(undefined_ID)) :: &
|
||||
outputID
|
||||
integer :: Ninstance,instance,source,sourceOffset,NofMyPhase,p
|
||||
character(len=pStringLen) :: &
|
||||
extmsg = ''
|
||||
character(len=pStringLen), dimension(:), allocatable :: &
|
||||
outputs
|
||||
|
||||
write(6,'(/,a)') ' <<<+- source_'//SOURCE_DAMAGE_ANISODUCTILE_LABEL//' init -+>>>'; flush(6)
|
||||
|
||||
|
@ -97,9 +87,9 @@ subroutine source_damage_anisoDuctile_init
|
|||
prm%critPlasticStrain = math_expand(prm%critPlasticStrain, prm%Nslip)
|
||||
|
||||
! sanity checks
|
||||
if (prm%aTol < 0.0_pReal) extmsg = trim(extmsg)//' anisoductile_atol'
|
||||
if (prm%N <= 0.0_pReal) extmsg = trim(extmsg)//' anisoductile_ratesensitivity'
|
||||
if (any(prm%critPlasticStrain < 0.0_pReal)) extmsg = trim(extmsg)//' anisoductile_criticalplasticstrain'
|
||||
if (prm%aTol < 0.0_pReal) extmsg = trim(extmsg)//' anisoductile_atol'
|
||||
if (prm%N <= 0.0_pReal) extmsg = trim(extmsg)//' anisoductile_ratesensitivity'
|
||||
if (any(prm%critPlasticStrain < 0.0_pReal)) extmsg = trim(extmsg)//' anisoductile_criticalplasticstrain'
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
! exit if any parameter is out of range
|
||||
|
@ -107,18 +97,7 @@ subroutine source_damage_anisoDuctile_init
|
|||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
! output pararameters
|
||||
outputs = 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
|
||||
prm%output = config%getStrings('(output)',defaultVal=emptyStringArray)
|
||||
|
||||
NofMyPhase=count(material_phaseAt==p) * discretization_nIP
|
||||
instance = source_damage_anisoDuctile_instance(p)
|
||||
|
@ -199,21 +178,20 @@ end subroutine source_damage_anisoDuctile_getRateAndItsTangent
|
|||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine source_damage_anisoDuctile_results(phase,group)
|
||||
|
||||
integer, intent(in) :: phase
|
||||
integer, intent(in) :: phase
|
||||
character(len=*), intent(in) :: group
|
||||
integer :: sourceOffset, o, instance
|
||||
|
||||
instance = source_damage_anisoDuctile_instance(phase)
|
||||
sourceOffset = source_damage_anisoDuctile_offset(phase)
|
||||
integer :: o
|
||||
|
||||
associate(prm => param(instance), stt => sourceState(phase)%p(sourceOffset)%state)
|
||||
outputsLoop: do o = 1,size(prm%outputID)
|
||||
select case(prm%outputID(o))
|
||||
case (damage_drivingforce_ID)
|
||||
call results_writeDataset(group,stt,'tbd','driving force','tbd')
|
||||
end select
|
||||
enddo outputsLoop
|
||||
end associate
|
||||
associate(prm => param(source_damage_anisoDuctile_instance(phase)), &
|
||||
stt => sourceState(phase)%p(source_damage_anisoDuctile_offset(phase))%state)
|
||||
outputsLoop: do o = 1,size(prm%output)
|
||||
select case(trim(prm%output(o)))
|
||||
case ('anisoductile_drivingforce')
|
||||
call results_writeDataset(group,stt,'tbd','driving force','tbd')
|
||||
end select
|
||||
enddo outputsLoop
|
||||
end associate
|
||||
|
||||
end subroutine source_damage_anisoDuctile_results
|
||||
|
||||
|
|
|
@ -20,20 +20,13 @@ module source_damage_isoBrittle
|
|||
source_damage_isoBrittle_offset, &
|
||||
source_damage_isoBrittle_instance
|
||||
|
||||
enum, bind(c)
|
||||
enumerator :: &
|
||||
undefined_ID, &
|
||||
damage_drivingforce_ID
|
||||
end enum
|
||||
|
||||
|
||||
type, private :: tParameters !< container type for internal constitutive parameters
|
||||
real(pReal) :: &
|
||||
critStrainEnergy, &
|
||||
N, &
|
||||
aTol
|
||||
integer(kind(undefined_ID)), allocatable, dimension(:) :: &
|
||||
outputID
|
||||
character(len=pStringLen), allocatable, dimension(:) :: &
|
||||
output
|
||||
end type tParameters
|
||||
|
||||
type(tParameters), dimension(:), allocatable :: param !< containers of constitutive parameters (len Ninstance)
|
||||
|
@ -54,13 +47,9 @@ contains
|
|||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine source_damage_isoBrittle_init
|
||||
|
||||
integer :: Ninstance,instance,source,sourceOffset,NofMyPhase,p,i
|
||||
integer(kind(undefined_ID)) :: &
|
||||
outputID
|
||||
integer :: Ninstance,instance,source,sourceOffset,NofMyPhase,p
|
||||
character(len=pStringLen) :: &
|
||||
extmsg = ''
|
||||
character(len=pStringLen), dimension(:), allocatable :: &
|
||||
outputs
|
||||
|
||||
write(6,'(/,a)') ' <<<+- source_'//SOURCE_DAMAGE_ISOBRITTLE_LABEL//' init -+>>>'; flush(6)
|
||||
|
||||
|
@ -99,18 +88,7 @@ subroutine source_damage_isoBrittle_init
|
|||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
! output pararameters
|
||||
outputs = 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
|
||||
prm%output = config%getStrings('(output)',defaultVal=emptyStringArray)
|
||||
|
||||
NofMyPhase = count(material_phaseAt==p) * discretization_nIP
|
||||
instance = source_damage_isoBrittle_instance(p)
|
||||
|
@ -199,21 +177,20 @@ end subroutine source_damage_isoBrittle_getRateAndItsTangent
|
|||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine source_damage_isoBrittle_results(phase,group)
|
||||
|
||||
integer, intent(in) :: phase
|
||||
integer, intent(in) :: phase
|
||||
character(len=*), intent(in) :: group
|
||||
integer :: sourceOffset, o, instance
|
||||
|
||||
instance = source_damage_isoBrittle_instance(phase)
|
||||
sourceOffset = source_damage_isoBrittle_offset(phase)
|
||||
integer :: o
|
||||
|
||||
associate(prm => param(instance), stt => sourceState(phase)%p(sourceOffset)%state)
|
||||
outputsLoop: do o = 1,size(prm%outputID)
|
||||
select case(prm%outputID(o))
|
||||
case (damage_drivingforce_ID)
|
||||
call results_writeDataset(group,stt,'tbd','driving force','tbd')
|
||||
end select
|
||||
enddo outputsLoop
|
||||
end associate
|
||||
associate(prm => param(source_damage_isoBrittle_instance(phase)), &
|
||||
stt => sourceState(phase)%p(source_damage_isoBrittle_offset(phase))%state)
|
||||
outputsLoop: do o = 1,size(prm%output)
|
||||
select case(trim(prm%output(o)))
|
||||
case ('isobrittle_drivingforce')
|
||||
call results_writeDataset(group,stt,'tbd','driving force','tbd')
|
||||
end select
|
||||
enddo outputsLoop
|
||||
end associate
|
||||
|
||||
end subroutine source_damage_isoBrittle_results
|
||||
|
||||
|
|
|
@ -19,18 +19,13 @@ module source_damage_isoDuctile
|
|||
source_damage_isoDuctile_offset, & !< which source is my current damage 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
|
||||
real(pReal) :: &
|
||||
critPlasticStrain, &
|
||||
N, &
|
||||
aTol
|
||||
integer(kind(undefined_ID)), allocatable, dimension(:) :: &
|
||||
outputID
|
||||
character(len=pStringLen), allocatable, dimension(:) :: &
|
||||
output
|
||||
end type tParameters
|
||||
|
||||
type(tParameters), dimension(:), allocatable, private :: param !< containers of constitutive parameters (len Ninstance)
|
||||
|
@ -51,13 +46,9 @@ contains
|
|||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine source_damage_isoDuctile_init
|
||||
|
||||
integer :: Ninstance,instance,source,sourceOffset,NofMyPhase,p,i
|
||||
integer(kind(undefined_ID)) :: &
|
||||
outputID
|
||||
integer :: Ninstance,instance,source,sourceOffset,NofMyPhase,p
|
||||
character(len=pStringLen) :: &
|
||||
extmsg = ''
|
||||
character(len=pStringLen), dimension(:), allocatable :: &
|
||||
outputs
|
||||
|
||||
write(6,'(/,a)') ' <<<+- source_'//SOURCE_DAMAGE_ISODUCTILE_LABEL//' init -+>>>'; flush(6)
|
||||
|
||||
|
@ -96,18 +87,7 @@ subroutine source_damage_isoDuctile_init
|
|||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
! output pararameters
|
||||
outputs = 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
|
||||
prm%output = config%getStrings('(output)',defaultVal=emptyStringArray)
|
||||
|
||||
NofMyPhase=count(material_phaseAt==p) * discretization_nIP
|
||||
instance = source_damage_isoDuctile_instance(p)
|
||||
|
@ -179,23 +159,21 @@ end subroutine source_damage_isoDuctile_getRateAndItsTangent
|
|||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine source_damage_isoDuctile_results(phase,group)
|
||||
|
||||
integer, intent(in) :: phase
|
||||
integer, intent(in) :: phase
|
||||
character(len=*), intent(in) :: group
|
||||
integer :: sourceOffset, o, instance
|
||||
|
||||
instance = source_damage_isoDuctile_instance(phase)
|
||||
sourceOffset = source_damage_isoDuctile_offset(phase)
|
||||
integer :: o
|
||||
|
||||
associate(prm => param(instance), stt => sourceState(phase)%p(sourceOffset)%state)
|
||||
outputsLoop: do o = 1,size(prm%outputID)
|
||||
select case(prm%outputID(o))
|
||||
case (damage_drivingforce_ID)
|
||||
call results_writeDataset(group,stt,'tbd','driving force','tbd')
|
||||
end select
|
||||
enddo outputsLoop
|
||||
end associate
|
||||
associate(prm => param(source_damage_isoDuctile_instance(phase)), &
|
||||
stt => sourceState(phase)%p(source_damage_isoDuctile_offset(phase))%state)
|
||||
outputsLoop: do o = 1,size(prm%output)
|
||||
select case(trim(prm%output(o)))
|
||||
case ('isoductile_drivingforce')
|
||||
call results_writeDataset(group,stt,'tbd','driving force','tbd')
|
||||
end select
|
||||
enddo outputsLoop
|
||||
end associate
|
||||
|
||||
end subroutine source_damage_isoDuctile_results
|
||||
|
||||
|
||||
end module source_damage_isoDuctile
|
||||
|
|
Loading…
Reference in New Issue