simplified and unified style
This commit is contained in:
parent
7e30c10e82
commit
73491f3be9
|
@ -67,11 +67,9 @@ contains
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
subroutine source_damage_anisoBrittle_init
|
subroutine source_damage_anisoBrittle_init
|
||||||
|
|
||||||
integer :: Ninstance,phase,instance,source,sourceOffset
|
integer :: Ninstance,instance,source,sourceOffset,NofMyPhase,p,i
|
||||||
integer :: NofMyPhase,p ,i
|
|
||||||
integer(kind(undefined_ID)) :: &
|
integer(kind(undefined_ID)) :: &
|
||||||
outputID
|
outputID
|
||||||
|
|
||||||
character(len=pStringLen) :: &
|
character(len=pStringLen) :: &
|
||||||
extmsg = ''
|
extmsg = ''
|
||||||
character(len=pStringLen), dimension(:), allocatable :: &
|
character(len=pStringLen), dimension(:), allocatable :: &
|
||||||
|
@ -79,28 +77,25 @@ subroutine source_damage_anisoBrittle_init
|
||||||
|
|
||||||
write(6,'(/,a)') ' <<<+- source_'//SOURCE_DAMAGE_ANISOBRITTLE_LABEL//' init -+>>>'; flush(6)
|
write(6,'(/,a)') ' <<<+- source_'//SOURCE_DAMAGE_ANISOBRITTLE_LABEL//' init -+>>>'; flush(6)
|
||||||
|
|
||||||
Ninstance = count(phase_source == SOURCE_damage_anisoBrittle_ID)
|
Ninstance = count(phase_source == SOURCE_DAMAGE_ANISOBRITTLE_ID)
|
||||||
if (Ninstance == 0) return
|
|
||||||
|
|
||||||
if (iand(debug_level(debug_constitutive),debug_levelBasic) /= 0) &
|
if (iand(debug_level(debug_constitutive),debug_levelBasic) /= 0) &
|
||||||
write(6,'(a16,1x,i5,/)') '# instances:',Ninstance
|
write(6,'(a16,1x,i5,/)') '# instances:',Ninstance
|
||||||
|
|
||||||
allocate(source_damage_anisoBrittle_offset(material_Nphase), source=0)
|
allocate(source_damage_anisoBrittle_offset (size(config_phase)), source=0)
|
||||||
allocate(source_damage_anisoBrittle_instance(material_Nphase), source=0)
|
allocate(source_damage_anisoBrittle_instance(size(config_phase)), source=0)
|
||||||
do phase = 1, material_Nphase
|
allocate(param(Ninstance))
|
||||||
source_damage_anisoBrittle_instance(phase) = count(phase_source(:,1:phase) == source_damage_anisoBrittle_ID)
|
|
||||||
do source = 1, phase_Nsources(phase)
|
|
||||||
if (phase_source(source,phase) == source_damage_anisoBrittle_ID) &
|
|
||||||
source_damage_anisoBrittle_offset(phase) = source
|
|
||||||
enddo
|
|
||||||
enddo
|
|
||||||
|
|
||||||
allocate(source_damage_anisoBrittle_Ncleavage(lattice_maxNcleavageFamily,Ninstance), source=0)
|
allocate(source_damage_anisoBrittle_Ncleavage(lattice_maxNcleavageFamily,Ninstance), source=0)
|
||||||
|
|
||||||
allocate(param(Ninstance))
|
do p = 1, size(config_phase)
|
||||||
|
source_damage_anisoBrittle_instance(p) = count(phase_source(:,1:p) == SOURCE_DAMAGE_ANISOBRITTLE_ID)
|
||||||
|
do source = 1, phase_Nsources(p)
|
||||||
|
if (phase_source(source,p) == SOURCE_DAMAGE_ANISOBRITTLE_ID) &
|
||||||
|
source_damage_anisoBrittle_offset(p) = source
|
||||||
|
enddo
|
||||||
|
|
||||||
do p=1, size(config_phase)
|
|
||||||
if (all(phase_source(:,p) /= SOURCE_DAMAGE_ANISOBRITTLE_ID)) cycle
|
if (all(phase_source(:,p) /= SOURCE_DAMAGE_ANISOBRITTLE_ID)) cycle
|
||||||
|
|
||||||
associate(prm => param(source_damage_anisoBrittle_instance(p)), &
|
associate(prm => param(source_damage_anisoBrittle_instance(p)), &
|
||||||
config => config_phase(p))
|
config => config_phase(p))
|
||||||
|
|
||||||
|
@ -129,6 +124,7 @@ subroutine source_damage_anisoBrittle_init
|
||||||
|
|
||||||
if (any(prm%critLoad < 0.0_pReal)) extmsg = trim(extmsg)//' anisobrittle_criticalload'
|
if (any(prm%critLoad < 0.0_pReal)) extmsg = trim(extmsg)//' anisobrittle_criticalload'
|
||||||
if (any(prm%critDisp < 0.0_pReal)) extmsg = trim(extmsg)//' anisobrittle_criticaldisplacement'
|
if (any(prm%critDisp < 0.0_pReal)) extmsg = trim(extmsg)//' anisobrittle_criticaldisplacement'
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! exit if any parameter is out of range
|
! exit if any parameter is out of range
|
||||||
if (extmsg /= '') &
|
if (extmsg /= '') &
|
||||||
|
@ -151,15 +147,12 @@ subroutine source_damage_anisoBrittle_init
|
||||||
|
|
||||||
end associate
|
end associate
|
||||||
|
|
||||||
phase = p
|
NofMyPhase=count(material_phaseAt==p) * discretization_nIP
|
||||||
NofMyPhase=count(material_phaseAt==phase) * discretization_nIP
|
instance = source_damage_anisoBrittle_instance(p)
|
||||||
instance = source_damage_anisoBrittle_instance(phase)
|
sourceOffset = source_damage_anisoBrittle_offset(p)
|
||||||
sourceOffset = source_damage_anisoBrittle_offset(phase)
|
|
||||||
|
|
||||||
|
|
||||||
call material_allocateSourceState(phase,sourceOffset,NofMyPhase,1,1,0)
|
|
||||||
sourceState(phase)%p(sourceOffset)%aTolState=param(instance)%aTol
|
|
||||||
|
|
||||||
|
call material_allocateSourceState(p,sourceOffset,NofMyPhase,1,1,0)
|
||||||
|
sourceState(p)%p(sourceOffset)%aTolState=param(instance)%aTol
|
||||||
|
|
||||||
source_damage_anisoBrittle_Ncleavage(1:size(param(instance)%Ncleavage),instance) = param(instance)%Ncleavage
|
source_damage_anisoBrittle_Ncleavage(1:size(param(instance)%Ncleavage),instance) = param(instance)%Ncleavage
|
||||||
enddo
|
enddo
|
||||||
|
|
|
@ -59,12 +59,9 @@ contains
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
subroutine source_damage_anisoDuctile_init
|
subroutine source_damage_anisoDuctile_init
|
||||||
|
|
||||||
integer :: Ninstance,phase,instance,source,sourceOffset
|
integer :: Ninstance,instance,source,sourceOffset,NofMyPhase,p,i
|
||||||
integer :: NofMyPhase,p ,i
|
|
||||||
|
|
||||||
integer(kind(undefined_ID)) :: &
|
integer(kind(undefined_ID)) :: &
|
||||||
outputID
|
outputID
|
||||||
|
|
||||||
character(len=pStringLen) :: &
|
character(len=pStringLen) :: &
|
||||||
extmsg = ''
|
extmsg = ''
|
||||||
character(len=pStringLen), dimension(:), allocatable :: &
|
character(len=pStringLen), dimension(:), allocatable :: &
|
||||||
|
@ -72,26 +69,23 @@ subroutine source_damage_anisoDuctile_init
|
||||||
|
|
||||||
write(6,'(/,a)') ' <<<+- source_'//SOURCE_DAMAGE_ANISODUCTILE_LABEL//' init -+>>>'; flush(6)
|
write(6,'(/,a)') ' <<<+- source_'//SOURCE_DAMAGE_ANISODUCTILE_LABEL//' init -+>>>'; flush(6)
|
||||||
|
|
||||||
Ninstance = count(phase_source == SOURCE_damage_anisoDuctile_ID)
|
Ninstance = count(phase_source == SOURCE_DAMAGE_ANISODUCTILE_ID)
|
||||||
if (Ninstance == 0) return
|
|
||||||
|
|
||||||
if (iand(debug_level(debug_constitutive),debug_levelBasic) /= 0) &
|
if (iand(debug_level(debug_constitutive),debug_levelBasic) /= 0) &
|
||||||
write(6,'(a16,1x,i5,/)') '# instances:',Ninstance
|
write(6,'(a16,1x,i5,/)') '# instances:',Ninstance
|
||||||
|
|
||||||
allocate(source_damage_anisoDuctile_offset(size(config_phase)), source=0)
|
allocate(source_damage_anisoDuctile_offset (size(config_phase)), source=0)
|
||||||
allocate(source_damage_anisoDuctile_instance(size(config_phase)), source=0)
|
allocate(source_damage_anisoDuctile_instance(size(config_phase)), source=0)
|
||||||
do phase = 1, size(config_phase)
|
|
||||||
source_damage_anisoDuctile_instance(phase) = count(phase_source(:,1:phase) == source_damage_anisoDuctile_ID)
|
|
||||||
do source = 1, phase_Nsources(phase)
|
|
||||||
if (phase_source(source,phase) == source_damage_anisoDuctile_ID) &
|
|
||||||
source_damage_anisoDuctile_offset(phase) = source
|
|
||||||
enddo
|
|
||||||
enddo
|
|
||||||
|
|
||||||
allocate(param(Ninstance))
|
allocate(param(Ninstance))
|
||||||
|
|
||||||
do p=1, size(config_phase)
|
do p = 1, size(config_phase)
|
||||||
|
source_damage_anisoDuctile_instance(p) = count(phase_source(:,1:p) == SOURCE_DAMAGE_ANISODUCTILE_ID)
|
||||||
|
do source = 1, phase_Nsources(p)
|
||||||
|
if (phase_source(source,p) == SOURCE_DAMAGE_ANISODUCTILE_ID) &
|
||||||
|
source_damage_anisoDuctile_offset(p) = source
|
||||||
|
enddo
|
||||||
|
|
||||||
if (all(phase_source(:,p) /= SOURCE_DAMAGE_ANISODUCTILE_ID)) cycle
|
if (all(phase_source(:,p) /= SOURCE_DAMAGE_ANISODUCTILE_ID)) cycle
|
||||||
|
|
||||||
associate(prm => param(source_damage_anisoDuctile_instance(p)), &
|
associate(prm => param(source_damage_anisoDuctile_instance(p)), &
|
||||||
config => config_phase(p))
|
config => config_phase(p))
|
||||||
|
|
||||||
|
@ -101,7 +95,6 @@ subroutine source_damage_anisoDuctile_init
|
||||||
prm%totalNslip = sum(prm%Nslip)
|
prm%totalNslip = sum(prm%Nslip)
|
||||||
! sanity checks
|
! sanity checks
|
||||||
if (prm%aTol < 0.0_pReal) extmsg = trim(extmsg)//' anisoductile_atol'
|
if (prm%aTol < 0.0_pReal) extmsg = trim(extmsg)//' anisoductile_atol'
|
||||||
|
|
||||||
if (prm%N <= 0.0_pReal) extmsg = trim(extmsg)//' anisoductile_ratesensitivity'
|
if (prm%N <= 0.0_pReal) extmsg = trim(extmsg)//' anisoductile_ratesensitivity'
|
||||||
|
|
||||||
prm%Nslip = config%getInts('nslip',defaultVal=emptyIntArray)
|
prm%Nslip = config%getInts('nslip',defaultVal=emptyIntArray)
|
||||||
|
@ -134,14 +127,12 @@ subroutine source_damage_anisoDuctile_init
|
||||||
|
|
||||||
end associate
|
end associate
|
||||||
|
|
||||||
phase = p
|
NofMyPhase=count(material_phaseAt==p) * discretization_nIP
|
||||||
|
instance = source_damage_anisoDuctile_instance(p)
|
||||||
|
sourceOffset = source_damage_anisoDuctile_offset(p)
|
||||||
|
|
||||||
NofMyPhase=count(material_phaseAt==phase) * discretization_nIP
|
call material_allocateSourceState(p,sourceOffset,NofMyPhase,1,1,0)
|
||||||
instance = source_damage_anisoDuctile_instance(phase)
|
sourceState(p)%p(sourceOffset)%aTolState=param(instance)%aTol
|
||||||
sourceOffset = source_damage_anisoDuctile_offset(phase)
|
|
||||||
|
|
||||||
call material_allocateSourceState(phase,sourceOffset,NofMyPhase,1,1,0)
|
|
||||||
sourceState(phase)%p(sourceOffset)%aTolState=param(instance)%aTol
|
|
||||||
|
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
|
|
|
@ -54,11 +54,9 @@ contains
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
subroutine source_damage_isoBrittle_init
|
subroutine source_damage_isoBrittle_init
|
||||||
|
|
||||||
integer :: Ninstance,phase,instance,source,sourceOffset
|
integer :: Ninstance,instance,source,sourceOffset,NofMyPhase,p,i
|
||||||
integer :: NofMyPhase,p,i
|
|
||||||
integer(kind(undefined_ID)) :: &
|
integer(kind(undefined_ID)) :: &
|
||||||
outputID
|
outputID
|
||||||
|
|
||||||
character(len=pStringLen) :: &
|
character(len=pStringLen) :: &
|
||||||
extmsg = ''
|
extmsg = ''
|
||||||
character(len=pStringLen), dimension(:), allocatable :: &
|
character(len=pStringLen), dimension(:), allocatable :: &
|
||||||
|
@ -66,26 +64,23 @@ subroutine source_damage_isoBrittle_init
|
||||||
|
|
||||||
write(6,'(/,a)') ' <<<+- source_'//SOURCE_DAMAGE_ISOBRITTLE_LABEL//' init -+>>>'; flush(6)
|
write(6,'(/,a)') ' <<<+- source_'//SOURCE_DAMAGE_ISOBRITTLE_LABEL//' init -+>>>'; flush(6)
|
||||||
|
|
||||||
Ninstance = count(phase_source == SOURCE_damage_isoBrittle_ID)
|
Ninstance = count(phase_source == SOURCE_DAMAGE_ISOBRITTLE_ID)
|
||||||
if (Ninstance == 0) return
|
|
||||||
|
|
||||||
if (iand(debug_level(debug_constitutive),debug_levelBasic) /= 0) &
|
if (iand(debug_level(debug_constitutive),debug_levelBasic) /= 0) &
|
||||||
write(6,'(a16,1x,i5,/)') '# instances:',Ninstance
|
write(6,'(a16,1x,i5,/)') '# instances:',Ninstance
|
||||||
|
|
||||||
allocate(source_damage_isoBrittle_offset(material_Nphase), source=0)
|
allocate(source_damage_isoBrittle_offset (size(config_phase)), source=0)
|
||||||
allocate(source_damage_isoBrittle_instance(material_Nphase), source=0)
|
allocate(source_damage_isoBrittle_instance(size(config_phase)), source=0)
|
||||||
do phase = 1, material_Nphase
|
|
||||||
source_damage_isoBrittle_instance(phase) = count(phase_source(:,1:phase) == source_damage_isoBrittle_ID)
|
|
||||||
do source = 1, phase_Nsources(phase)
|
|
||||||
if (phase_source(source,phase) == source_damage_isoBrittle_ID) &
|
|
||||||
source_damage_isoBrittle_offset(phase) = source
|
|
||||||
enddo
|
|
||||||
enddo
|
|
||||||
|
|
||||||
allocate(param(Ninstance))
|
allocate(param(Ninstance))
|
||||||
|
|
||||||
do p=1, size(config_phase)
|
do p = 1, size(config_phase)
|
||||||
|
source_damage_isoBrittle_instance(p) = count(phase_source(:,1:p) == SOURCE_DAMAGE_ISOBRITTLE_ID)
|
||||||
|
do source = 1, phase_Nsources(p)
|
||||||
|
if (phase_source(source,p) == SOURCE_DAMAGE_ISOBRITTLE_ID) &
|
||||||
|
source_damage_isoBrittle_offset(p) = source
|
||||||
|
enddo
|
||||||
|
|
||||||
if (all(phase_source(:,p) /= SOURCE_DAMAGE_ISOBRITTLE_ID)) cycle
|
if (all(phase_source(:,p) /= SOURCE_DAMAGE_ISOBRITTLE_ID)) cycle
|
||||||
|
|
||||||
associate(prm => param(source_damage_isoBrittle_instance(p)), &
|
associate(prm => param(source_damage_isoBrittle_instance(p)), &
|
||||||
config => config_phase(p))
|
config => config_phase(p))
|
||||||
|
|
||||||
|
@ -122,14 +117,12 @@ subroutine source_damage_isoBrittle_init
|
||||||
|
|
||||||
end associate
|
end associate
|
||||||
|
|
||||||
phase = p
|
NofMyPhase = count(material_phaseAt==p) * discretization_nIP
|
||||||
|
instance = source_damage_isoBrittle_instance(p)
|
||||||
|
sourceOffset = source_damage_isoBrittle_offset(p)
|
||||||
|
|
||||||
NofMyPhase = count(material_phaseAt==phase) * discretization_nIP
|
call material_allocateSourceState(p,sourceOffset,NofMyPhase,1,1,1)
|
||||||
instance = source_damage_isoBrittle_instance(phase)
|
sourceState(p)%p(sourceOffset)%aTolState=param(instance)%aTol
|
||||||
sourceOffset = source_damage_isoBrittle_offset(phase)
|
|
||||||
|
|
||||||
call material_allocateSourceState(phase,sourceOffset,NofMyPhase,1,1,1)
|
|
||||||
sourceState(phase)%p(sourceOffset)%aTolState=param(instance)%aTol
|
|
||||||
|
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
|
|
|
@ -51,38 +51,33 @@ contains
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
subroutine source_damage_isoDuctile_init
|
subroutine source_damage_isoDuctile_init
|
||||||
|
|
||||||
integer :: Ninstance,phase,instance,source,sourceOffset
|
integer :: Ninstance,instance,source,sourceOffset,NofMyPhase,p,i
|
||||||
integer :: NofMyPhase,p,i
|
|
||||||
integer(kind(undefined_ID)) :: &
|
integer(kind(undefined_ID)) :: &
|
||||||
outputID
|
outputID
|
||||||
|
|
||||||
character(len=pStringLen) :: &
|
character(len=pStringLen) :: &
|
||||||
extmsg = ''
|
extmsg = ''
|
||||||
character(len=pStringLen), dimension(:), allocatable :: &
|
character(len=pStringLen), dimension(:), allocatable :: &
|
||||||
outputs
|
outputs
|
||||||
|
|
||||||
write(6,'(/,a)') ' <<<+- source_'//SOURCE_DAMAGE_ISODUCTILE_LABEL//' init -+>>>'
|
write(6,'(/,a)') ' <<<+- source_'//SOURCE_DAMAGE_ISODUCTILE_LABEL//' init -+>>>'; flush(6)
|
||||||
|
|
||||||
Ninstance = count(phase_source == SOURCE_damage_isoDuctile_ID)
|
|
||||||
if (Ninstance == 0) return
|
|
||||||
|
|
||||||
|
Ninstance = count(phase_source == SOURCE_DAMAGE_ISODUCTILE_ID)
|
||||||
if (iand(debug_level(debug_constitutive),debug_levelBasic) /= 0) &
|
if (iand(debug_level(debug_constitutive),debug_levelBasic) /= 0) &
|
||||||
write(6,'(a16,1x,i5,/)') '# instances:',Ninstance
|
write(6,'(a16,1x,i5,/)') '# instances:',Ninstance
|
||||||
|
|
||||||
allocate(source_damage_isoDuctile_offset(material_Nphase), source=0)
|
allocate(source_damage_isoDuctile_offset (size(config_phase)), source=0)
|
||||||
allocate(source_damage_isoDuctile_instance(material_Nphase), source=0)
|
allocate(source_damage_isoDuctile_instance(size(config_phase)), source=0)
|
||||||
do phase = 1, material_Nphase
|
|
||||||
source_damage_isoDuctile_instance(phase) = count(phase_source(:,1:phase) == source_damage_isoDuctile_ID)
|
|
||||||
do source = 1, phase_Nsources(phase)
|
|
||||||
if (phase_source(source,phase) == source_damage_isoDuctile_ID) &
|
|
||||||
source_damage_isoDuctile_offset(phase) = source
|
|
||||||
enddo
|
|
||||||
enddo
|
|
||||||
|
|
||||||
allocate(param(Ninstance))
|
allocate(param(Ninstance))
|
||||||
|
|
||||||
do p=1, size(config_phase)
|
do p = 1, size(config_phase)
|
||||||
|
source_damage_isoDuctile_instance(p) = count(phase_source(:,1:p) == SOURCE_DAMAGE_ISODUCTILE_ID)
|
||||||
|
do source = 1, phase_Nsources(p)
|
||||||
|
if (phase_source(source,p) == SOURCE_DAMAGE_ISODUCTILE_ID) &
|
||||||
|
source_damage_isoDuctile_offset(p) = source
|
||||||
|
enddo
|
||||||
|
|
||||||
if (all(phase_source(:,p) /= SOURCE_DAMAGE_ISODUCTILE_ID)) cycle
|
if (all(phase_source(:,p) /= SOURCE_DAMAGE_ISODUCTILE_ID)) cycle
|
||||||
|
|
||||||
associate(prm => param(source_damage_isoDuctile_instance(p)), &
|
associate(prm => param(source_damage_isoDuctile_instance(p)), &
|
||||||
config => config_phase(p))
|
config => config_phase(p))
|
||||||
|
|
||||||
|
@ -119,13 +114,13 @@ subroutine source_damage_isoDuctile_init
|
||||||
|
|
||||||
end associate
|
end associate
|
||||||
|
|
||||||
phase = p
|
|
||||||
NofMyPhase=count(material_phaseAt==phase) * discretization_nIP
|
|
||||||
instance = source_damage_isoDuctile_instance(phase)
|
|
||||||
sourceOffset = source_damage_isoDuctile_offset(phase)
|
|
||||||
|
|
||||||
call material_allocateSourceState(phase,sourceOffset,NofMyPhase,1,1,0)
|
NofMyPhase=count(material_phaseAt==p) * discretization_nIP
|
||||||
sourceState(phase)%p(sourceOffset)%aTolState=param(instance)%aTol
|
instance = source_damage_isoDuctile_instance(p)
|
||||||
|
sourceOffset = source_damage_isoDuctile_offset(p)
|
||||||
|
|
||||||
|
call material_allocateSourceState(p,sourceOffset,NofMyPhase,1,1,0)
|
||||||
|
sourceState(p)%p(sourceOffset)%aTolState=param(instance)%aTol
|
||||||
|
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
|
|
|
@ -43,26 +43,23 @@ subroutine source_thermal_dissipation_init
|
||||||
|
|
||||||
write(6,'(/,a)') ' <<<+- source_'//SOURCE_thermal_dissipation_label//' init -+>>>'; flush(6)
|
write(6,'(/,a)') ' <<<+- source_'//SOURCE_thermal_dissipation_label//' init -+>>>'; flush(6)
|
||||||
|
|
||||||
|
Ninstance = count(phase_source == SOURCE_THERMAL_DISSIPATION_ID)
|
||||||
Ninstance = count(phase_source == SOURCE_thermal_dissipation_ID)
|
|
||||||
if (Ninstance == 0) return
|
|
||||||
if (iand(debug_level(debug_constitutive),debug_levelBasic) /= 0) &
|
if (iand(debug_level(debug_constitutive),debug_levelBasic) /= 0) &
|
||||||
write(6,'(a16,1x,i5,/)') '# instances:',Ninstance
|
write(6,'(a16,1x,i5,/)') '# instances:',Ninstance
|
||||||
|
|
||||||
allocate(source_thermal_dissipation_offset(material_Nphase), source=0)
|
allocate(source_thermal_dissipation_offset (size(config_phase)), source=0)
|
||||||
allocate(source_thermal_dissipation_instance(material_Nphase), source=0)
|
allocate(source_thermal_dissipation_instance(size(config_phase)), source=0)
|
||||||
allocate(param(Ninstance))
|
allocate(param(Ninstance))
|
||||||
|
|
||||||
do p = 1, material_Nphase
|
do p = 1, size(config_phase)
|
||||||
source_thermal_dissipation_instance(p) = count(phase_source(:,1:p) == SOURCE_thermal_dissipation_ID)
|
source_thermal_dissipation_instance(p) = count(phase_source(:,1:p) == SOURCE_THERMAL_DISSIPATION_ID)
|
||||||
do source = 1, phase_Nsources(p)
|
do source = 1, phase_Nsources(p)
|
||||||
if (phase_source(source,p) == SOURCE_thermal_dissipation_ID) &
|
if (phase_source(source,p) == SOURCE_THERMAL_DISSIPATION_ID) &
|
||||||
source_thermal_dissipation_offset(p) = source
|
source_thermal_dissipation_offset(p) = source
|
||||||
enddo
|
enddo
|
||||||
enddo
|
|
||||||
|
|
||||||
do p=1, size(config_phase)
|
|
||||||
if (all(phase_source(:,p) /= SOURCE_THERMAL_DISSIPATION_ID)) cycle
|
if (all(phase_source(:,p) /= SOURCE_THERMAL_DISSIPATION_ID)) cycle
|
||||||
|
|
||||||
instance = source_thermal_dissipation_instance(p)
|
instance = source_thermal_dissipation_instance(p)
|
||||||
param(instance)%kappa = config_phase(p)%getFloat('dissipation_coldworkcoeff')
|
param(instance)%kappa = config_phase(p)%getFloat('dissipation_coldworkcoeff')
|
||||||
NofMyPhase = count(material_phaseAt==p) * discretization_nIP
|
NofMyPhase = count(material_phaseAt==p) * discretization_nIP
|
||||||
|
@ -76,7 +73,7 @@ end subroutine source_thermal_dissipation_init
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief returns dissipation rate
|
!> @brief Ninstances dissipation rate
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
subroutine source_thermal_dissipation_getRateAndItsTangent(TDot, dTDOT_dT, Tstar, Lp, phase)
|
subroutine source_thermal_dissipation_getRateAndItsTangent(TDot, dTDOT_dT, Tstar, Lp, phase)
|
||||||
|
|
||||||
|
|
|
@ -43,31 +43,27 @@ contains
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
subroutine source_thermal_externalheat_init
|
subroutine source_thermal_externalheat_init
|
||||||
|
|
||||||
integer :: maxNinstance,instance,source,sourceOffset,NofMyPhase,p
|
integer :: Ninstance,instance,source,sourceOffset,NofMyPhase,p
|
||||||
|
|
||||||
write(6,'(/,a)') ' <<<+- source_'//SOURCE_thermal_externalheat_label//' init -+>>>'; flush(6)
|
write(6,'(/,a)') ' <<<+- source_'//SOURCE_thermal_externalheat_label//' init -+>>>'; flush(6)
|
||||||
|
|
||||||
|
Ninstance = count(phase_source == SOURCE_thermal_externalheat_ID)
|
||||||
maxNinstance = count(phase_source == SOURCE_thermal_externalheat_ID)
|
|
||||||
if (maxNinstance == 0) return
|
|
||||||
if (iand(debug_level(debug_constitutive),debug_levelBasic) /= 0) &
|
if (iand(debug_level(debug_constitutive),debug_levelBasic) /= 0) &
|
||||||
write(6,'(a16,1x,i5,/)') '# instances:',maxNinstance
|
write(6,'(a16,1x,i5,/)') '# instances:',Ninstance
|
||||||
|
|
||||||
allocate(source_thermal_externalheat_offset(material_Nphase), source=0)
|
allocate(source_thermal_externalheat_offset (size(config_phase)), source=0)
|
||||||
allocate(source_thermal_externalheat_instance(material_Nphase), source=0)
|
allocate(source_thermal_externalheat_instance(size(config_phase)), source=0)
|
||||||
|
allocate(param(Ninstance))
|
||||||
|
|
||||||
do p = 1, material_Nphase
|
do p = 1, size(config_phase)
|
||||||
source_thermal_externalheat_instance(p) = count(phase_source(:,1:p) == SOURCE_thermal_externalheat_ID)
|
source_thermal_externalheat_instance(p) = count(phase_source(:,1:p) == SOURCE_thermal_externalheat_ID)
|
||||||
do source = 1, phase_Nsources(p)
|
do source = 1, phase_Nsources(p)
|
||||||
if (phase_source(source,p) == SOURCE_thermal_externalheat_ID) &
|
if (phase_source(source,p) == SOURCE_thermal_externalheat_ID) &
|
||||||
source_thermal_externalheat_offset(p) = source
|
source_thermal_externalheat_offset(p) = source
|
||||||
enddo
|
enddo
|
||||||
enddo
|
|
||||||
|
|
||||||
allocate(param(maxNinstance))
|
|
||||||
|
|
||||||
do p=1, size(config_phase)
|
|
||||||
if (all(phase_source(:,p) /= SOURCE_thermal_externalheat_ID)) cycle
|
if (all(phase_source(:,p) /= SOURCE_thermal_externalheat_ID)) cycle
|
||||||
|
|
||||||
instance = source_thermal_externalheat_instance(p)
|
instance = source_thermal_externalheat_instance(p)
|
||||||
sourceOffset = source_thermal_externalheat_offset(p)
|
sourceOffset = source_thermal_externalheat_offset(p)
|
||||||
NofMyPhase = count(material_phaseAt==p) * discretization_nIP
|
NofMyPhase = count(material_phaseAt==p) * discretization_nIP
|
||||||
|
|
Loading…
Reference in New Issue