less variable, same style
This commit is contained in:
parent
6678770c43
commit
ac182ef536
|
@ -5,8 +5,8 @@
|
|||
module damage_local
|
||||
use prec
|
||||
use material
|
||||
use numerics
|
||||
use config
|
||||
use numerics
|
||||
use source_damage_isoBrittle
|
||||
use source_damage_isoDuctile
|
||||
use source_damage_anisoBrittle
|
||||
|
@ -22,9 +22,6 @@ module damage_local
|
|||
damage_ID
|
||||
end enum
|
||||
|
||||
integer(kind(undefined_ID)), dimension(:,:), allocatable :: &
|
||||
damage_local_outputID !< ID of each post result output
|
||||
|
||||
type :: tParameters
|
||||
integer(kind(undefined_ID)), dimension(:), allocatable :: &
|
||||
outputID
|
||||
|
@ -46,60 +43,41 @@ contains
|
|||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine damage_local_init
|
||||
|
||||
integer :: maxNinstance,homog,i
|
||||
integer :: sizeState
|
||||
integer :: NofMyHomog, h
|
||||
integer(kind(undefined_ID)) :: &
|
||||
outputID
|
||||
integer :: maxNinstance,o,NofMyHomog,h
|
||||
character(len=65536), dimension(0), parameter :: emptyStringArray = [character(len=65536)::]
|
||||
character(len=65536), dimension(:), allocatable :: &
|
||||
outputs
|
||||
character(len=65536), dimension(:), allocatable :: outputs
|
||||
|
||||
write(6,'(/,a)') ' <<<+- damage_'//DAMAGE_local_label//' init -+>>>'; flush(6)
|
||||
|
||||
maxNinstance = count(damage_type == DAMAGE_local_ID)
|
||||
if (maxNinstance == 0) return
|
||||
|
||||
allocate(damage_local_outputID (maxval(homogenization_Noutput),maxNinstance),source=undefined_ID)
|
||||
|
||||
allocate(param(maxNinstance))
|
||||
|
||||
do h = 1, size(damage_type)
|
||||
if (damage_type(h) /= DAMAGE_LOCAL_ID) cycle
|
||||
associate(prm => param(damage_typeInstance(h)), &
|
||||
config => config_homogenization(h))
|
||||
|
||||
associate(prm => param(damage_typeInstance(h)),config => config_homogenization(h))
|
||||
|
||||
outputs = config%getStrings('(output)',defaultVal=emptyStringArray)
|
||||
allocate(prm%outputID(0))
|
||||
|
||||
do i=1, size(outputs)
|
||||
outputID = undefined_ID
|
||||
select case(outputs(i))
|
||||
|
||||
case ('damage')
|
||||
prm%outputID = [prm%outputID , damage_ID]
|
||||
end select
|
||||
|
||||
do o=1, size(outputs)
|
||||
select case(outputs(o))
|
||||
case ('damage')
|
||||
prm%outputID = [prm%outputID , damage_ID]
|
||||
end select
|
||||
enddo
|
||||
|
||||
NofMyHomog = count(material_homogenizationAt == h)
|
||||
damageState(h)%sizeState = 1
|
||||
allocate(damageState(h)%state0 (1,NofMyHomog), source=damage_initialPhi(h))
|
||||
allocate(damageState(h)%subState0(1,NofMyHomog), source=damage_initialPhi(h))
|
||||
allocate(damageState(h)%state (1,NofMyHomog), source=damage_initialPhi(h))
|
||||
|
||||
homog = h
|
||||
|
||||
NofMyHomog = count(material_homogenizationAt == homog)
|
||||
|
||||
|
||||
! allocate state arrays
|
||||
sizeState = 1
|
||||
damageState(homog)%sizeState = sizeState
|
||||
allocate(damageState(homog)%state0 (sizeState,NofMyHomog), source=damage_initialPhi(homog))
|
||||
allocate(damageState(homog)%subState0(sizeState,NofMyHomog), source=damage_initialPhi(homog))
|
||||
allocate(damageState(homog)%state (sizeState,NofMyHomog), source=damage_initialPhi(homog))
|
||||
|
||||
nullify(damageMapping(homog)%p)
|
||||
damageMapping(homog)%p => mappingHomogenization(1,:,:)
|
||||
deallocate(damage(homog)%p)
|
||||
damage(homog)%p => damageState(homog)%state(1,:)
|
||||
nullify(damageMapping(h)%p)
|
||||
damageMapping(h)%p => mappingHomogenization(1,:,:)
|
||||
deallocate(damage(h)%p)
|
||||
damage(h)%p => damageState(h)%state(1,:)
|
||||
|
||||
end associate
|
||||
enddo
|
||||
|
|
|
@ -19,26 +19,23 @@ contains
|
|||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine damage_none_init
|
||||
|
||||
integer :: &
|
||||
homog, &
|
||||
NofMyHomog
|
||||
integer :: h,NofMyHomog
|
||||
|
||||
write(6,'(/,a)') ' <<<+- damage_'//DAMAGE_NONE_LABEL//' init -+>>>'
|
||||
write(6,'(/,a)') ' <<<+- damage_'//DAMAGE_NONE_LABEL//' init -+>>>'; flush(6)
|
||||
|
||||
initializeInstances: do homog = 1, size(config_homogenization)
|
||||
do h = 1, size(config_homogenization)
|
||||
if (damage_type(h) /= DAMAGE_NONE_ID) cycle
|
||||
|
||||
myhomog: if (damage_type(homog) == DAMAGE_NONE_ID) then
|
||||
NofMyHomog = count(material_homogenizationAt == homog)
|
||||
damageState(homog)%sizeState = 0
|
||||
allocate(damageState(homog)%state0 (0,NofMyHomog))
|
||||
allocate(damageState(homog)%subState0(0,NofMyHomog))
|
||||
allocate(damageState(homog)%state (0,NofMyHomog))
|
||||
NofMyHomog = count(material_homogenizationAt == h)
|
||||
damageState(h)%sizeState = 0
|
||||
allocate(damageState(h)%state0 (0,NofMyHomog))
|
||||
allocate(damageState(h)%subState0(0,NofMyHomog))
|
||||
allocate(damageState(h)%state (0,NofMyHomog))
|
||||
|
||||
deallocate(damage(homog)%p)
|
||||
allocate (damage(homog)%p(1), source=damage_initialPhi(homog))
|
||||
deallocate(damage(h)%p)
|
||||
allocate (damage(h)%p(1), source=damage_initialPhi(h))
|
||||
|
||||
endif myhomog
|
||||
enddo initializeInstances
|
||||
enddo
|
||||
|
||||
end subroutine damage_none_init
|
||||
|
||||
|
|
|
@ -1,13 +1,12 @@
|
|||
!--------------------------------------------------------------------------------------------------
|
||||
!> @author Pratheek Shanthraj, Max-Planck-Institut für Eisenforschung GmbH
|
||||
!> @brief material subroutine for non-locally evolving damage field
|
||||
!> @details to be done
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
module damage_nonlocal
|
||||
use prec
|
||||
use material
|
||||
use numerics
|
||||
use config
|
||||
use numerics
|
||||
use crystallite
|
||||
use lattice
|
||||
use source_damage_isoBrittle
|
||||
|
@ -49,14 +48,9 @@ contains
|
|||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine damage_nonlocal_init
|
||||
|
||||
integer :: maxNinstance,homog,i
|
||||
integer :: sizeState
|
||||
integer :: NofMyHomog, h
|
||||
integer(kind(undefined_ID)) :: &
|
||||
outputID
|
||||
character(len=65536), dimension(0), parameter :: emptyStringArray = [character(len=65536)::]
|
||||
character(len=65536), dimension(:), allocatable :: &
|
||||
outputs
|
||||
integer :: maxNinstance,o,NofMyHomog,h
|
||||
character(len=65536), dimension(0), parameter :: emptyStringArray = [character(len=65536)::]
|
||||
character(len=65536), dimension(:), allocatable :: outputs
|
||||
|
||||
write(6,'(/,a)') ' <<<+- damage_'//DAMAGE_nonlocal_label//' init -+>>>'; flush(6)
|
||||
|
||||
|
@ -67,40 +61,32 @@ subroutine damage_nonlocal_init
|
|||
|
||||
do h = 1, size(damage_type)
|
||||
if (damage_type(h) /= DAMAGE_NONLOCAL_ID) cycle
|
||||
associate(prm => param(damage_typeInstance(h)), &
|
||||
config => config_homogenization(h))
|
||||
associate(prm => param(damage_typeInstance(h)),config => config_homogenization(h))
|
||||
|
||||
outputs = config%getStrings('(output)',defaultVal=emptyStringArray)
|
||||
allocate(prm%outputID(0))
|
||||
|
||||
do i=1, size(outputs)
|
||||
outputID = undefined_ID
|
||||
select case(outputs(i))
|
||||
case ('damage')
|
||||
prm%outputID = [prm%outputID , damage_ID]
|
||||
end select
|
||||
|
||||
do o=1, size(outputs)
|
||||
select case(outputs(o))
|
||||
case ('damage')
|
||||
prm%outputID = [prm%outputID, damage_ID]
|
||||
end select
|
||||
enddo
|
||||
|
||||
homog = h
|
||||
NofMyHomog = count(material_homogenizationAt == h)
|
||||
damageState(h)%sizeState = 1
|
||||
allocate(damageState(h)%state0 (1,NofMyHomog), source=damage_initialPhi(h))
|
||||
allocate(damageState(h)%subState0(1,NofMyHomog), source=damage_initialPhi(h))
|
||||
allocate(damageState(h)%state (1,NofMyHomog), source=damage_initialPhi(h))
|
||||
|
||||
NofMyHomog = count(material_homogenizationAt == homog)
|
||||
|
||||
|
||||
! allocate state arrays
|
||||
sizeState = 1
|
||||
damageState(homog)%sizeState = sizeState
|
||||
allocate(damageState(homog)%state0 (sizeState,NofMyHomog), source=damage_initialPhi(homog))
|
||||
allocate(damageState(homog)%subState0(sizeState,NofMyHomog), source=damage_initialPhi(homog))
|
||||
allocate(damageState(homog)%state (sizeState,NofMyHomog), source=damage_initialPhi(homog))
|
||||
|
||||
nullify(damageMapping(homog)%p)
|
||||
damageMapping(homog)%p => mappingHomogenization(1,:,:)
|
||||
deallocate(damage(homog)%p)
|
||||
damage(homog)%p => damageState(homog)%state(1,:)
|
||||
nullify(damageMapping(h)%p)
|
||||
damageMapping(h)%p => mappingHomogenization(1,:,:)
|
||||
deallocate(damage(h)%p)
|
||||
damage(h)%p => damageState(h)%state(1,:)
|
||||
|
||||
end associate
|
||||
enddo
|
||||
|
||||
end subroutine damage_nonlocal_init
|
||||
|
||||
|
||||
|
|
|
@ -46,8 +46,8 @@ contains
|
|||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine thermal_adiabatic_init
|
||||
|
||||
integer :: maxNinstance,section,instance,i,sizeState,NofMyHomog
|
||||
character(len=65536), dimension(0), parameter :: emptyStringArray = [character(len=65536)::]
|
||||
integer :: maxNinstance,o,h,NofMyHomog
|
||||
character(len=65536), dimension(0), parameter :: emptyStringArray = [character(len=65536)::]
|
||||
character(len=65536), dimension(:), allocatable :: outputs
|
||||
|
||||
write(6,'(/,a)') ' <<<+- thermal_'//THERMAL_ADIABATIC_label//' init -+>>>'; flush(6)
|
||||
|
@ -57,38 +57,35 @@ subroutine thermal_adiabatic_init
|
|||
|
||||
allocate(param(maxNinstance))
|
||||
|
||||
initializeInstances: do section = 1, size(thermal_type)
|
||||
if (thermal_type(section) /= THERMAL_adiabatic_ID) cycle
|
||||
associate(prm => param(thermal_typeInstance(section)), &
|
||||
config => config_homogenization(section))
|
||||
do h = 1, size(thermal_type)
|
||||
if (thermal_type(h) /= THERMAL_adiabatic_ID) cycle
|
||||
associate(prm => param(thermal_typeInstance(h)),config => config_homogenization(h))
|
||||
|
||||
NofMyHomog=count(material_homogenizationAt==section)
|
||||
instance = thermal_typeInstance(section)
|
||||
outputs = config%getStrings('(output)',defaultVal=emptyStringArray)
|
||||
allocate(prm%outputID(0))
|
||||
do i=1, size(outputs)
|
||||
select case(outputs(i))
|
||||
|
||||
do o=1, size(outputs)
|
||||
select case(outputs(o))
|
||||
case('temperature')
|
||||
prm%outputID = [prm%outputID, temperature_ID]
|
||||
prm%outputID = [prm%outputID, temperature_ID]
|
||||
end select
|
||||
enddo
|
||||
|
||||
! allocate state arrays
|
||||
sizeState = 1
|
||||
thermalState(section)%sizeState = sizeState
|
||||
allocate(thermalState(section)%state0 (sizeState,NofMyHomog), source=thermal_initialT(section))
|
||||
allocate(thermalState(section)%subState0(sizeState,NofMyHomog), source=thermal_initialT(section))
|
||||
allocate(thermalState(section)%state (sizeState,NofMyHomog), source=thermal_initialT(section))
|
||||
NofMyHomog=count(material_homogenizationAt==h)
|
||||
thermalState(h)%sizeState = 1
|
||||
allocate(thermalState(h)%state0 (1,NofMyHomog), source=thermal_initialT(h))
|
||||
allocate(thermalState(h)%subState0(1,NofMyHomog), source=thermal_initialT(h))
|
||||
allocate(thermalState(h)%state (1,NofMyHomog), source=thermal_initialT(h))
|
||||
|
||||
nullify(thermalMapping(section)%p)
|
||||
thermalMapping(section)%p => mappingHomogenization(1,:,:)
|
||||
deallocate(temperature(section)%p)
|
||||
temperature(section)%p => thermalState(section)%state(1,:)
|
||||
deallocate(temperatureRate(section)%p)
|
||||
allocate (temperatureRate(section)%p(NofMyHomog), source=0.0_pReal)
|
||||
nullify(thermalMapping(h)%p)
|
||||
thermalMapping(h)%p => mappingHomogenization(1,:,:)
|
||||
deallocate(temperature(h)%p)
|
||||
temperature(h)%p => thermalState(h)%state(1,:)
|
||||
deallocate(temperatureRate(h)%p)
|
||||
allocate (temperatureRate(h)%p(NofMyHomog), source=0.0_pReal)
|
||||
|
||||
end associate
|
||||
enddo initializeInstances
|
||||
enddo
|
||||
|
||||
end subroutine thermal_adiabatic_init
|
||||
|
||||
|
|
|
@ -16,8 +16,9 @@ module thermal_conduction
|
|||
private
|
||||
|
||||
enum, bind(c)
|
||||
enumerator :: undefined_ID, &
|
||||
temperature_ID
|
||||
enumerator :: &
|
||||
undefined_ID, &
|
||||
temperature_ID
|
||||
end enum
|
||||
|
||||
type :: tParameters
|
||||
|
@ -47,10 +48,8 @@ contains
|
|||
subroutine thermal_conduction_init
|
||||
|
||||
|
||||
integer :: maxNinstance,section,instance,i
|
||||
integer :: sizeState
|
||||
integer :: NofMyHomog
|
||||
character(len=65536), dimension(0), parameter :: emptyStringArray = [character(len=65536)::]
|
||||
integer :: maxNinstance,o,NofMyHomog,h
|
||||
character(len=65536), dimension(0), parameter :: emptyStringArray = [character(len=65536)::]
|
||||
character(len=65536), dimension(:), allocatable :: outputs
|
||||
|
||||
write(6,'(/,a)') ' <<<+- thermal_'//THERMAL_CONDUCTION_label//' init -+>>>'; flush(6)
|
||||
|
@ -60,39 +59,35 @@ subroutine thermal_conduction_init
|
|||
|
||||
allocate(param(maxNinstance))
|
||||
|
||||
initializeInstances: do section = 1, size(thermal_type)
|
||||
if (thermal_type(section) /= THERMAL_conduction_ID) cycle
|
||||
associate(prm => param(thermal_typeInstance(section)), &
|
||||
config => config_homogenization(section))
|
||||
do h = 1, size(thermal_type)
|
||||
if (thermal_type(h) /= THERMAL_conduction_ID) cycle
|
||||
associate(prm => param(thermal_typeInstance(h)),config => config_homogenization(h))
|
||||
|
||||
NofMyHomog=count(material_homogenizationAt==section)
|
||||
instance = thermal_typeInstance(section)
|
||||
outputs = config%getStrings('(output)',defaultVal=emptyStringArray)
|
||||
allocate(prm%outputID(0))
|
||||
do i=1, size(outputs)
|
||||
select case(outputs(i))
|
||||
|
||||
do o=1, size(outputs)
|
||||
select case(outputs(o))
|
||||
case('temperature')
|
||||
prm%outputID = [prm%outputID, temperature_ID]
|
||||
prm%outputID = [prm%outputID, temperature_ID]
|
||||
end select
|
||||
enddo
|
||||
|
||||
NofMyHomog=count(material_homogenizationAt==h)
|
||||
thermalState(h)%sizeState = 0
|
||||
allocate(thermalState(h)%state0 (0,NofMyHomog))
|
||||
allocate(thermalState(h)%subState0(0,NofMyHomog))
|
||||
allocate(thermalState(h)%state (0,NofMyHomog))
|
||||
|
||||
! allocate state arrays
|
||||
sizeState = 0
|
||||
thermalState(section)%sizeState = sizeState
|
||||
allocate(thermalState(section)%state0 (sizeState,NofMyHomog))
|
||||
allocate(thermalState(section)%subState0(sizeState,NofMyHomog))
|
||||
allocate(thermalState(section)%state (sizeState,NofMyHomog))
|
||||
|
||||
nullify(thermalMapping(section)%p)
|
||||
thermalMapping(section)%p => mappingHomogenization(1,:,:)
|
||||
deallocate(temperature (section)%p)
|
||||
allocate (temperature (section)%p(NofMyHomog), source=thermal_initialT(section))
|
||||
deallocate(temperatureRate(section)%p)
|
||||
allocate (temperatureRate(section)%p(NofMyHomog), source=0.0_pReal)
|
||||
nullify(thermalMapping(h)%p)
|
||||
thermalMapping(h)%p => mappingHomogenization(1,:,:)
|
||||
deallocate(temperature (h)%p)
|
||||
allocate (temperature (h)%p(NofMyHomog), source=thermal_initialT(h))
|
||||
deallocate(temperatureRate(h)%p)
|
||||
allocate (temperatureRate(h)%p(NofMyHomog), source=0.0_pReal)
|
||||
|
||||
end associate
|
||||
enddo initializeInstances
|
||||
enddo
|
||||
|
||||
end subroutine thermal_conduction_init
|
||||
|
||||
|
|
|
@ -3,7 +3,6 @@
|
|||
!> @brief material subroutine for isothermal temperature field
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
module thermal_isothermal
|
||||
use prec
|
||||
use config
|
||||
use material
|
||||
|
||||
|
@ -20,27 +19,25 @@ contains
|
|||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine thermal_isothermal_init
|
||||
|
||||
integer :: &
|
||||
homog, &
|
||||
NofMyHomog
|
||||
integer :: h,NofMyHomog
|
||||
|
||||
write(6,'(/,a)') ' <<<+- thermal_'//THERMAL_isothermal_label//' init -+>>>'
|
||||
write(6,'(/,a)') ' <<<+- thermal_'//THERMAL_isothermal_label//' init -+>>>'; flush(6)
|
||||
|
||||
initializeInstances: do homog = 1, material_Nhomogenization
|
||||
do h = 1, size(config_homogenization)
|
||||
if (thermal_type(h) /= THERMAL_isothermal_ID) cycle
|
||||
|
||||
if (thermal_type(homog) /= THERMAL_isothermal_ID) cycle
|
||||
NofMyHomog = count(material_homogenizationAt == homog)
|
||||
thermalState(homog)%sizeState = 0
|
||||
allocate(thermalState(homog)%state0 (0,NofMyHomog), source=0.0_pReal)
|
||||
allocate(thermalState(homog)%subState0(0,NofMyHomog), source=0.0_pReal)
|
||||
allocate(thermalState(homog)%state (0,NofMyHomog), source=0.0_pReal)
|
||||
NofMyHomog = count(material_homogenizationAt == h)
|
||||
thermalState(h)%sizeState = 0
|
||||
allocate(thermalState(h)%state0 (0,NofMyHomog))
|
||||
allocate(thermalState(h)%subState0(0,NofMyHomog))
|
||||
allocate(thermalState(h)%state (0,NofMyHomog))
|
||||
|
||||
deallocate(temperature (homog)%p)
|
||||
allocate (temperature (homog)%p(1), source=thermal_initialT(homog))
|
||||
deallocate(temperatureRate(homog)%p)
|
||||
allocate (temperatureRate(homog)%p(1), source=0.0_pReal)
|
||||
deallocate(temperature (h)%p)
|
||||
allocate (temperature (h)%p(1), source=thermal_initialT(h))
|
||||
deallocate(temperatureRate(h)%p)
|
||||
allocate (temperatureRate(h)%p(1))
|
||||
|
||||
enddo initializeInstances
|
||||
enddo
|
||||
|
||||
end subroutine thermal_isothermal_init
|
||||
|
||||
|
|
Loading…
Reference in New Issue