standard names

This commit is contained in:
Martin Diehl 2020-03-16 18:29:15 +01:00
parent e4792e56fb
commit 9733f4a140
8 changed files with 168 additions and 168 deletions

View File

@ -165,7 +165,7 @@ module subroutine plastic_nonlocal_init
integer :: &
sizeState, sizeDotState,sizeDependentState, sizeDeltaState, &
maxNinstances, &
Ninstance, &
p, &
l, &
s1, s2, &
@ -174,7 +174,7 @@ module subroutine plastic_nonlocal_init
c
character(len=pStringLen) :: &
extmsg = ''
integer :: NofMyPhase
integer :: NipcMyPhase
write(6,'(/,a)') ' <<<+- constitutive_'//PLASTICITY_NONLOCAL_LABEL//' init -+>>>'; flush(6)
@ -184,17 +184,17 @@ module subroutine plastic_nonlocal_init
write(6,'(/,a)') ' Kords, Dissertation RWTH Aachen, 2014'
write(6,'(a)') ' http://publications.rwth-aachen.de/record/229993'
maxNinstances = count(phase_plasticity == PLASTICITY_NONLOCAL_ID)
Ninstance = count(phase_plasticity == PLASTICITY_NONLOCAL_ID)
if (iand(debug_level(debug_constitutive),debug_levelBasic) /= 0) &
write(6,'(a16,1x,i5,/)') '# instances:',maxNinstances
write(6,'(a16,1x,i5,/)') '# instances:',Ninstance
allocate(param(maxNinstances))
allocate(state(maxNinstances))
allocate(state0(maxNinstances))
allocate(dotState(maxNinstances))
allocate(deltaState(maxNinstances))
allocate(microstructure(maxNinstances))
allocate(totalNslip(maxNinstances), source=0)
allocate(param(Ninstance))
allocate(state(Ninstance))
allocate(state0(Ninstance))
allocate(dotState(Ninstance))
allocate(deltaState(Ninstance))
allocate(microstructure(Ninstance))
allocate(totalNslip(Ninstance), source=0)
do p=1, size(config_phase)
@ -339,7 +339,7 @@ module subroutine plastic_nonlocal_init
if (prm%fattack <= 0.0_pReal) extmsg = trim(extmsg)//' fattack'
if (prm%doublekinkwidth <= 0.0_pReal) extmsg = trim(extmsg)//' doublekinkwidth'
if (prm%Dsd0 < 0.0_pReal) extmsg = trim(extmsg)//' Dsd0'
if (prm%atomicVolume <= 0.0_pReal) extmsg = trim(extmsg)//' atomicVolume' ! ToDo: in disloUCLA/dislotwin, the atomic volume is given as a factor
if (prm%atomicVolume <= 0.0_pReal) extmsg = trim(extmsg)//' atomicVolume' ! ToDo: in disloUCLA, the atomic volume is given as a factor
if (prm%significantN < 0.0_pReal) extmsg = trim(extmsg)//' significantN'
if (prm%significantrho < 0.0_pReal) extmsg = trim(extmsg)//' significantrho'
@ -369,13 +369,13 @@ module subroutine plastic_nonlocal_init
!--------------------------------------------------------------------------------------------------
! allocate state arrays
NofMyPhase = count(material_phaseAt==p) * discretization_nIP
sizeDotState = size([ 'rhoSglEdgePosMobile ','rhoSglEdgeNegMobile ', &
'rhoSglScrewPosMobile ','rhoSglScrewNegMobile ', &
'rhoSglEdgePosImmobile ','rhoSglEdgeNegImmobile ', &
'rhoSglScrewPosImmobile','rhoSglScrewNegImmobile', &
'rhoDipEdge ','rhoDipScrew ', &
'gamma ' ]) * prm%totalNslip !< "basic" microstructural state variables that are independent from other state variables
NipcMyPhase = count(material_phaseAt==p) * discretization_nIP
sizeDotState = size([ 'rhoSglEdgePosMobile ','rhoSglEdgeNegMobile ', &
'rhoSglScrewPosMobile ','rhoSglScrewNegMobile ', &
'rhoSglEdgePosImmobile ','rhoSglEdgeNegImmobile ', &
'rhoSglScrewPosImmobile','rhoSglScrewNegImmobile', &
'rhoDipEdge ','rhoDipScrew ', &
'gamma ' ]) * prm%totalNslip !< "basic" microstructural state variables that are independent from other state variables
sizeDependentState = size([ 'rhoForest ']) * prm%totalNslip !< microstructural state variables that depend on other state variables
sizeState = sizeDotState + sizeDependentState &
+ size([ 'velocityEdgePos ','velocityEdgeNeg ', &
@ -383,7 +383,7 @@ module subroutine plastic_nonlocal_init
'maxDipoleHeightEdge ','maxDipoleHeightScrew' ]) * prm%totalNslip !< other dependent state variables that are not updated by microstructure
sizeDeltaState = sizeDotState
call material_allocatePlasticState(p,NofMyPhase,sizeState,sizeDotState,sizeDeltaState)
call material_allocatePlasticState(p,NipcMyPhase,sizeState,sizeDotState,sizeDeltaState)
plasticState(p)%nonlocal = .true.
plasticState(p)%offsetDeltaState = 0 ! ToDo: state structure does not follow convention
@ -452,26 +452,26 @@ module subroutine plastic_nonlocal_init
dot%rho_dip_scr => plasticState(p)%dotState (9*prm%totalNslip+1:10*prm%totalNslip,:)
del%rho_dip_scr => plasticState(p)%deltaState (9*prm%totalNslip+1:10*prm%totalNslip,:)
stt%gamma => plasticState(p)%state (10*prm%totalNslip + 1:11*prm%totalNslip ,1:NofMyPhase)
dot%gamma => plasticState(p)%dotState (10*prm%totalNslip + 1:11*prm%totalNslip ,1:NofMyPhase)
del%gamma => plasticState(p)%deltaState (10*prm%totalNslip + 1:11*prm%totalNslip ,1:NofMyPhase)
stt%gamma => plasticState(p)%state (10*prm%totalNslip + 1:11*prm%totalNslip ,1:NipcMyPhase)
dot%gamma => plasticState(p)%dotState (10*prm%totalNslip + 1:11*prm%totalNslip ,1:NipcMyPhase)
del%gamma => plasticState(p)%deltaState (10*prm%totalNslip + 1:11*prm%totalNslip ,1:NipcMyPhase)
plasticState(p)%atol(10*prm%totalNslip+1:11*prm%totalNslip ) = config%getFloat('atol_gamma', defaultVal = 1.0e-20_pReal)
if(any(plasticState(p)%atol(10*prm%totalNslip+1:11*prm%totalNslip) < 0.0_pReal)) &
extmsg = trim(extmsg)//' atol_gamma'
plasticState(p)%slipRate => plasticState(p)%dotState (10*prm%totalNslip + 1:11*prm%totalNslip ,1:NofMyPhase)
plasticState(p)%slipRate => plasticState(p)%dotState (10*prm%totalNslip + 1:11*prm%totalNslip ,1:NipcMyPhase)
stt%rho_forest => plasticState(p)%state (11*prm%totalNslip + 1:12*prm%totalNslip ,1:NofMyPhase)
stt%v => plasticState(p)%state (12*prm%totalNslip + 1:16*prm%totalNslip ,1:NofMyPhase)
stt%v_edg_pos => plasticState(p)%state (12*prm%totalNslip + 1:13*prm%totalNslip ,1:NofMyPhase)
stt%v_edg_neg => plasticState(p)%state (13*prm%totalNslip + 1:14*prm%totalNslip ,1:NofMyPhase)
stt%v_scr_pos => plasticState(p)%state (14*prm%totalNslip + 1:15*prm%totalNslip ,1:NofMyPhase)
stt%v_scr_neg => plasticState(p)%state (15*prm%totalNslip + 1:16*prm%totalNslip ,1:NofMyPhase)
stt%rho_forest => plasticState(p)%state (11*prm%totalNslip + 1:12*prm%totalNslip ,1:NipcMyPhase)
stt%v => plasticState(p)%state (12*prm%totalNslip + 1:16*prm%totalNslip ,1:NipcMyPhase)
stt%v_edg_pos => plasticState(p)%state (12*prm%totalNslip + 1:13*prm%totalNslip ,1:NipcMyPhase)
stt%v_edg_neg => plasticState(p)%state (13*prm%totalNslip + 1:14*prm%totalNslip ,1:NipcMyPhase)
stt%v_scr_pos => plasticState(p)%state (14*prm%totalNslip + 1:15*prm%totalNslip ,1:NipcMyPhase)
stt%v_scr_neg => plasticState(p)%state (15*prm%totalNslip + 1:16*prm%totalNslip ,1:NipcMyPhase)
allocate(dst%tau_pass(prm%totalNslip,NofMyPhase),source=0.0_pReal)
allocate(dst%tau_back(prm%totalNslip,NofMyPhase),source=0.0_pReal)
allocate(dst%tau_pass(prm%totalNslip,NipcMyPhase),source=0.0_pReal)
allocate(dst%tau_back(prm%totalNslip,NipcMyPhase),source=0.0_pReal)
end associate
if (NofMyPhase > 0) call stateInit(p,NofMyPhase)
if (NipcMyPhase > 0) call stateInit(p,NipcMyPhase)
plasticState(p)%state0 = plasticState(p)%state
!--------------------------------------------------------------------------------------------------
@ -484,12 +484,12 @@ module subroutine plastic_nonlocal_init
discretization_nIP,discretization_nElem), source=0.0_pReal)
! BEGIN DEPRECATED----------------------------------------------------------------------------------
allocate(iRhoU(maxval(param%totalNslip),4,maxNinstances), source=0)
allocate(iV(maxval(param%totalNslip),4,maxNinstances), source=0)
allocate(iD(maxval(param%totalNslip),2,maxNinstances), source=0)
allocate(iRhoU(maxval(param%totalNslip),4,Ninstance), source=0)
allocate(iV(maxval(param%totalNslip),4,Ninstance), source=0)
allocate(iD(maxval(param%totalNslip),2,Ninstance), source=0)
initializeInstances: do p = 1, size(phase_plasticity)
NofMyPhase = count(material_phaseAt==p) * discretization_nIP
NipcMyPhase = count(material_phaseAt==p) * discretization_nIP
myPhase2: if (phase_plasticity(p) == PLASTICITY_NONLOCAL_ID) then
!*** determine indices to state array
@ -532,11 +532,11 @@ module subroutine plastic_nonlocal_init
!--------------------------------------------------------------------------------------------------
!> @brief populates the initial dislocation density
!--------------------------------------------------------------------------------------------------
subroutine stateInit(phase,NofMyPhase)
subroutine stateInit(phase,NipcMyPhase)
integer,intent(in) ::&
phase, &
NofMyPhase
NipcMyPhase
integer :: &
e, &
i, &
@ -554,7 +554,7 @@ module subroutine plastic_nonlocal_init
totalVolume, &
densityBinning, &
minimumIpVolume
real(pReal), dimension(NofMyPhase) :: &
real(pReal), dimension(NipcMyPhase) :: &
volume
instance = phase_plasticityInstance(phase)
@ -577,14 +577,14 @@ module subroutine plastic_nonlocal_init
meanDensity = 0.0_pReal
do while(meanDensity < prm%rhoSglRandom)
call random_number(rnd)
phasemember = nint(rnd(1)*real(NofMyPhase,pReal) + 0.5_pReal)
phasemember = nint(rnd(1)*real(NipcMyPhase,pReal) + 0.5_pReal)
s = nint(rnd(2)*real(prm%totalNslip,pReal)*4.0_pReal + 0.5_pReal)
meanDensity = meanDensity + densityBinning * volume(phasemember) / totalVolume
stt%rhoSglMobile(s,phasemember) = densityBinning
enddo
! homogeneous distribution of density with some noise
else
do e = 1, NofMyPhase
do e = 1, NipcMyPhase
do f = 1,size(prm%Nslip,1)
from = 1 + sum(prm%Nslip(1:f-1))
upto = sum(prm%Nslip(1:f))

View File

@ -709,12 +709,12 @@ end subroutine material_parseTexture
!--------------------------------------------------------------------------------------------------
!> @brief allocates the plastic state of a phase
!--------------------------------------------------------------------------------------------------
subroutine material_allocatePlasticState(phase,NofMyPhase,&
subroutine material_allocatePlasticState(phase,NipcMyPhase,&
sizeState,sizeDotState,sizeDeltaState)
integer, intent(in) :: &
phase, &
NofMyPhase, &
NipcMyPhase, &
sizeState, &
sizeDotState, &
sizeDeltaState
@ -725,22 +725,22 @@ subroutine material_allocatePlasticState(phase,NofMyPhase,&
plasticState(phase)%offsetDeltaState = sizeState-sizeDeltaState ! deltaState occupies latter part of state by definition
allocate(plasticState(phase)%atol (sizeState), source=0.0_pReal)
allocate(plasticState(phase)%state0 (sizeState,NofMyPhase), source=0.0_pReal)
allocate(plasticState(phase)%partionedState0 (sizeState,NofMyPhase), source=0.0_pReal)
allocate(plasticState(phase)%subState0 (sizeState,NofMyPhase), source=0.0_pReal)
allocate(plasticState(phase)%state (sizeState,NofMyPhase), source=0.0_pReal)
allocate(plasticState(phase)%state0 (sizeState,NipcMyPhase), source=0.0_pReal)
allocate(plasticState(phase)%partionedState0 (sizeState,NipcMyPhase), source=0.0_pReal)
allocate(plasticState(phase)%subState0 (sizeState,NipcMyPhase), source=0.0_pReal)
allocate(plasticState(phase)%state (sizeState,NipcMyPhase), source=0.0_pReal)
allocate(plasticState(phase)%dotState (sizeDotState,NofMyPhase), source=0.0_pReal)
allocate(plasticState(phase)%dotState (sizeDotState,NipcMyPhase),source=0.0_pReal)
if (numerics_integrator == 1) then
allocate(plasticState(phase)%previousDotState (sizeDotState,NofMyPhase), source=0.0_pReal)
allocate(plasticState(phase)%previousDotState2 (sizeDotState,NofMyPhase), source=0.0_pReal)
allocate(plasticState(phase)%previousDotState (sizeDotState,NipcMyPhase),source=0.0_pReal)
allocate(plasticState(phase)%previousDotState2 (sizeDotState,NipcMyPhase),source=0.0_pReal)
endif
if (numerics_integrator == 4) &
allocate(plasticState(phase)%RK4dotState (sizeDotState,NofMyPhase), source=0.0_pReal)
allocate(plasticState(phase)%RK4dotState (sizeDotState,NipcMyPhase),source=0.0_pReal)
if (numerics_integrator == 5) &
allocate(plasticState(phase)%RKCK45dotState (6,sizeDotState,NofMyPhase), source=0.0_pReal)
allocate(plasticState(phase)%RKCK45dotState (6,sizeDotState,NipcMyPhase),source=0.0_pReal)
allocate(plasticState(phase)%deltaState (sizeDeltaState,NofMyPhase), source=0.0_pReal)
allocate(plasticState(phase)%deltaState (sizeDeltaState,NipcMyPhase),source=0.0_pReal)
end subroutine material_allocatePlasticState
@ -748,13 +748,13 @@ end subroutine material_allocatePlasticState
!--------------------------------------------------------------------------------------------------
!> @brief allocates the source state of a phase
!--------------------------------------------------------------------------------------------------
subroutine material_allocateSourceState(phase,of,NofMyPhase,&
subroutine material_allocateSourceState(phase,of,NipcMyPhase,&
sizeState,sizeDotState,sizeDeltaState)
integer, intent(in) :: &
phase, &
of, &
NofMyPhase, &
NipcMyPhase, &
sizeState, sizeDotState,sizeDeltaState
sourceState(phase)%p(of)%sizeState = sizeState
@ -763,22 +763,22 @@ subroutine material_allocateSourceState(phase,of,NofMyPhase,&
sourceState(phase)%p(of)%offsetDeltaState = sizeState-sizeDeltaState ! deltaState occupies latter part of state by definition
allocate(sourceState(phase)%p(of)%atol (sizeState), source=0.0_pReal)
allocate(sourceState(phase)%p(of)%state0 (sizeState,NofMyPhase), source=0.0_pReal)
allocate(sourceState(phase)%p(of)%partionedState0 (sizeState,NofMyPhase), source=0.0_pReal)
allocate(sourceState(phase)%p(of)%subState0 (sizeState,NofMyPhase), source=0.0_pReal)
allocate(sourceState(phase)%p(of)%state (sizeState,NofMyPhase), source=0.0_pReal)
allocate(sourceState(phase)%p(of)%state0 (sizeState,NipcMyPhase), source=0.0_pReal)
allocate(sourceState(phase)%p(of)%partionedState0 (sizeState,NipcMyPhase), source=0.0_pReal)
allocate(sourceState(phase)%p(of)%subState0 (sizeState,NipcMyPhase), source=0.0_pReal)
allocate(sourceState(phase)%p(of)%state (sizeState,NipcMyPhase), source=0.0_pReal)
allocate(sourceState(phase)%p(of)%dotState (sizeDotState,NofMyPhase), source=0.0_pReal)
allocate(sourceState(phase)%p(of)%dotState (sizeDotState,NipcMyPhase),source=0.0_pReal)
if (numerics_integrator == 1) then
allocate(sourceState(phase)%p(of)%previousDotState (sizeDotState,NofMyPhase), source=0.0_pReal)
allocate(sourceState(phase)%p(of)%previousDotState2 (sizeDotState,NofMyPhase), source=0.0_pReal)
allocate(sourceState(phase)%p(of)%previousDotState (sizeDotState,NipcMyPhase),source=0.0_pReal)
allocate(sourceState(phase)%p(of)%previousDotState2 (sizeDotState,NipcMyPhase),source=0.0_pReal)
endif
if (numerics_integrator == 4) &
allocate(sourceState(phase)%p(of)%RK4dotState (sizeDotState,NofMyPhase), source=0.0_pReal)
allocate(sourceState(phase)%p(of)%RK4dotState (sizeDotState,NipcMyPhase),source=0.0_pReal)
if (numerics_integrator == 5) &
allocate(sourceState(phase)%p(of)%RKCK45dotState (6,sizeDotState,NofMyPhase), source=0.0_pReal)
allocate(sourceState(phase)%p(of)%RKCK45dotState (6,sizeDotState,NipcMyPhase),source=0.0_pReal)
allocate(sourceState(phase)%p(of)%deltaState (sizeDeltaState,NofMyPhase), source=0.0_pReal)
allocate(sourceState(phase)%p(of)%deltaState (sizeDeltaState,NipcMyPhase),source=0.0_pReal)
end subroutine material_allocateSourceState

View File

@ -57,7 +57,7 @@ contains
!--------------------------------------------------------------------------------------------------
subroutine source_damage_anisoBrittle_init
integer :: Ninstance,sourceOffset,NofMyPhase,p
integer :: Ninstance,sourceOffset,NipcMyPhase,p
character(len=pStringLen) :: extmsg = ''
write(6,'(/,a)') ' <<<+- source_'//SOURCE_DAMAGE_ANISOBRITTLE_LABEL//' init -+>>>'; flush(6)
@ -107,8 +107,8 @@ subroutine source_damage_anisoBrittle_init
if (any(prm%critLoad < 0.0_pReal)) extmsg = trim(extmsg)//' anisobrittle_critLoad'
if (any(prm%critDisp < 0.0_pReal)) extmsg = trim(extmsg)//' anisobrittle_critDisp'
NofMyPhase = count(material_phaseAt==p) * discretization_nIP
call material_allocateSourceState(p,sourceOffset,NofMyPhase,1,1,0)
NipcMyPhase = count(material_phaseAt==p) * discretization_nIP
call material_allocateSourceState(p,sourceOffset,NipcMyPhase,1,1,0)
sourceState(p)%p(sourceOffset)%atol = config%getFloat('anisobrittle_atol',defaultVal=1.0e-3_pReal)
if(any(sourceState(p)%p(sourceOffset)%atol < 0.0_pReal)) extmsg = trim(extmsg)//' anisobrittle_atol'

View File

@ -52,7 +52,7 @@ contains
!--------------------------------------------------------------------------------------------------
subroutine source_damage_anisoDuctile_init
integer :: Ninstance,sourceOffset,NofMyPhase,p
integer :: Ninstance,sourceOffset,NipcMyPhase,p
character(len=pStringLen) :: extmsg = ''
write(6,'(/,a)') ' <<<+- source_'//SOURCE_DAMAGE_ANISODUCTILE_LABEL//' init -+>>>'; flush(6)
@ -94,8 +94,8 @@ subroutine source_damage_anisoDuctile_init
if (prm%N <= 0.0_pReal) extmsg = trim(extmsg)//' anisoductile_ratesensitivity'
if (any(prm%critPlasticStrain < 0.0_pReal)) extmsg = trim(extmsg)//' anisoductile_criticalplasticstrain'
NofMyPhase=count(material_phaseAt==p) * discretization_nIP
call material_allocateSourceState(p,sourceOffset,NofMyPhase,1,1,0)
NipcMyPhase=count(material_phaseAt==p) * discretization_nIP
call material_allocateSourceState(p,sourceOffset,NipcMyPhase,1,1,0)
sourceState(p)%p(sourceOffset)%atol = config%getFloat('anisoductile_atol',defaultVal=1.0e-3_pReal)
if(any(sourceState(p)%p(sourceOffset)%atol < 0.0_pReal)) extmsg = trim(extmsg)//' anisoductile_atol'

View File

@ -47,7 +47,7 @@ contains
!--------------------------------------------------------------------------------------------------
subroutine source_damage_isoBrittle_init
integer :: Ninstance,sourceOffset,NofMyPhase,p
integer :: Ninstance,sourceOffset,NipcMyPhase,p
character(len=pStringLen) :: extmsg = ''
write(6,'(/,a)') ' <<<+- source_'//SOURCE_DAMAGE_ISOBRITTLE_LABEL//' init -+>>>'; flush(6)
@ -82,8 +82,8 @@ subroutine source_damage_isoBrittle_init
if (prm%N <= 0.0_pReal) extmsg = trim(extmsg)//' isobrittle_n'
if (prm%critStrainEnergy <= 0.0_pReal) extmsg = trim(extmsg)//' isobrittle_criticalstrainenergy'
NofMyPhase = count(material_phaseAt==p) * discretization_nIP
call material_allocateSourceState(p,sourceOffset,NofMyPhase,1,1,1)
NipcMyPhase = count(material_phaseAt==p) * discretization_nIP
call material_allocateSourceState(p,sourceOffset,NipcMyPhase,1,1,1)
sourceState(p)%p(sourceOffset)%atol = config%getFloat('isobrittle_atol',defaultVal=1.0e-3_pReal)
if(any(sourceState(p)%p(sourceOffset)%atol < 0.0_pReal)) extmsg = trim(extmsg)//' isobrittle_atol'

View File

@ -46,7 +46,7 @@ contains
!--------------------------------------------------------------------------------------------------
subroutine source_damage_isoDuctile_init
integer :: Ninstance,sourceOffset,NofMyPhase,p
integer :: Ninstance,sourceOffset,NipcMyPhase,p
character(len=pStringLen) :: extmsg = ''
write(6,'(/,a)') ' <<<+- source_'//SOURCE_DAMAGE_ISODUCTILE_LABEL//' init -+>>>'; flush(6)
@ -81,8 +81,8 @@ subroutine source_damage_isoDuctile_init
if (prm%N <= 0.0_pReal) extmsg = trim(extmsg)//' isoductile_ratesensitivity'
if (prm%critPlasticStrain <= 0.0_pReal) extmsg = trim(extmsg)//' isoductile_criticalplasticstrain'
NofMyPhase=count(material_phaseAt==p) * discretization_nIP
call material_allocateSourceState(p,sourceOffset,NofMyPhase,1,1,0)
NipcMyPhase=count(material_phaseAt==p) * discretization_nIP
call material_allocateSourceState(p,sourceOffset,NipcMyPhase,1,1,0)
sourceState(p)%p(sourceOffset)%atol = config%getFloat('isoductile_atol',defaultVal=1.0e-3_pReal)
if(any(sourceState(p)%p(sourceOffset)%atol < 0.0_pReal)) extmsg = trim(extmsg)//' isoductile_atol'

View File

@ -39,7 +39,7 @@ contains
!--------------------------------------------------------------------------------------------------
subroutine source_thermal_dissipation_init
integer :: Ninstance,sourceOffset,NofMyPhase,p
integer :: Ninstance,sourceOffset,NipcMyPhase,p
write(6,'(/,a)') ' <<<+- source_'//SOURCE_thermal_dissipation_label//' init -+>>>'; flush(6)
@ -66,8 +66,8 @@ subroutine source_thermal_dissipation_init
prm%kappa = config%getFloat('dissipation_coldworkcoeff')
NofMyPhase = count(material_phaseAt==p) * discretization_nIP
call material_allocateSourceState(p,sourceOffset,NofMyPhase,0,0,0)
NipcMyPhase = count(material_phaseAt==p) * discretization_nIP
call material_allocateSourceState(p,sourceOffset,NipcMyPhase,0,0,0)
end associate
enddo

View File

@ -43,7 +43,7 @@ contains
!--------------------------------------------------------------------------------------------------
subroutine source_thermal_externalheat_init
integer :: Ninstance,sourceOffset,NofMyPhase,p
integer :: Ninstance,sourceOffset,NipcMyPhase,p
write(6,'(/,a)') ' <<<+- source_'//SOURCE_thermal_externalheat_label//' init -+>>>'; flush(6)
@ -73,8 +73,8 @@ subroutine source_thermal_externalheat_init
prm%heat_rate = config%getFloats('externalheat_rate',requiredSize = size(prm%time))
NofMyPhase = count(material_phaseAt==p) * discretization_nIP
call material_allocateSourceState(p,sourceOffset,NofMyPhase,1,1,0)
NipcMyPhase = count(material_phaseAt==p) * discretization_nIP
call material_allocateSourceState(p,sourceOffset,NipcMyPhase,1,1,0)
end associate
enddo