modernized

- no pInt
- consistent 2-blank indentation
- use of parameter structure
This commit is contained in:
Martin Diehl 2019-03-24 11:01:27 +01:00
parent c1d4b64b13
commit 0f2013e78a
1 changed files with 94 additions and 100 deletions

View File

@ -5,37 +5,32 @@
!> @details to be done !> @details to be done
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
module source_thermal_dissipation module source_thermal_dissipation
use prec, only: & use prec, only: &
pReal, & pReal
pInt
implicit none implicit none
private private
integer(pInt), dimension(:), allocatable, public, protected :: & integer, dimension(:), allocatable, public, protected :: &
source_thermal_dissipation_offset, & !< which source is my current thermal dissipation mechanism? source_thermal_dissipation_offset, & !< which source is my current thermal dissipation mechanism?
source_thermal_dissipation_instance !< instance of thermal dissipation source mechanism source_thermal_dissipation_instance !< instance of thermal dissipation source mechanism
integer(pInt), dimension(:,:), allocatable, target, public :: & integer, dimension(:,:), allocatable, target, public :: &
source_thermal_dissipation_sizePostResult !< size of each post result output source_thermal_dissipation_sizePostResult !< size of each post result output
character(len=64), dimension(:,:), allocatable, target, public :: & character(len=64), dimension(:,:), allocatable, target, public :: &
source_thermal_dissipation_output !< name of each post result output source_thermal_dissipation_output !< name of each post result output
real(pReal), dimension(:), allocatable, private :: & type, private :: tParameters !< container type for internal constitutive parameters
source_thermal_dissipation_coldworkCoeff real(pReal) :: &
kappa
end type tParameters
type(tParameters), dimension(:), allocatable, private :: param !< containers of constitutive parameters (len Ninstance)
type, private :: tParameters !< container type for internal constitutive parameters public :: &
real(pReal) :: & source_thermal_dissipation_init, &
coldworkCoeff source_thermal_dissipation_getRateAndItsTangent
end type tParameters
type(tParameters), dimension(:), allocatable, private :: param !< containers of constitutive parameters (len Ninstance)
public :: &
source_thermal_dissipation_init, &
source_thermal_dissipation_getRateAndItsTangent
contains contains
@ -45,61 +40,60 @@ contains
!> @details reads in material parameters, allocates arrays, and does sanity checks !> @details reads in material parameters, allocates arrays, and does sanity checks
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
subroutine source_thermal_dissipation_init subroutine source_thermal_dissipation_init
use debug, only: & use debug, only: &
debug_level,& debug_level,&
debug_constitutive,& debug_constitutive,&
debug_levelBasic debug_levelBasic
use material, only: & use material, only: &
material_allocateSourceState, & material_allocateSourceState, &
phase_source, & phase_source, &
phase_Nsources, & phase_Nsources, &
phase_Noutput, & phase_Noutput, &
SOURCE_thermal_dissipation_label, & SOURCE_thermal_dissipation_label, &
SOURCE_thermal_dissipation_ID, & SOURCE_thermal_dissipation_ID, &
material_phase, & material_phase
sourceState use config, only: &
use config, only: & config_phase, &
config_phase, & material_Nphase
material_Nphase
implicit none implicit none
integer(pInt) :: Ninstance,instance,source,sourceOffset integer :: Ninstance,instance,source,sourceOffset
integer(pInt) :: NofMyPhase,p integer :: NofMyPhase,p
write(6,'(/,a)') ' <<<+- source_'//SOURCE_thermal_dissipation_label//' init -+>>>' write(6,'(/,a)') ' <<<+- source_'//SOURCE_thermal_dissipation_label//' init -+>>>'
Ninstance = int(count(phase_source == SOURCE_thermal_dissipation_ID),pInt) Ninstance = count(phase_source == SOURCE_thermal_dissipation_ID)
if (Ninstance == 0_pInt) return if (Ninstance == 0) return
if (iand(debug_level(debug_constitutive),debug_levelBasic) /= 0_pInt) & 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_pInt) allocate(source_thermal_dissipation_offset(material_Nphase), source=0)
allocate(source_thermal_dissipation_instance(material_Nphase), source=0_pInt) allocate(source_thermal_dissipation_instance(material_Nphase), source=0)
do p = 1, material_Nphase allocate(param(Ninstance))
source_thermal_dissipation_instance(p) = count(phase_source(:,1:p) == SOURCE_thermal_dissipation_ID)
do source = 1, phase_Nsources(p)
if (phase_source(source,p) == SOURCE_thermal_dissipation_ID) &
source_thermal_dissipation_offset(p) = source
enddo
enddo
allocate(source_thermal_dissipation_sizePostResult(maxval(phase_Noutput),Ninstance),source=0_pInt) do p = 1, material_Nphase
allocate(source_thermal_dissipation_output (maxval(phase_Noutput),Ninstance)) source_thermal_dissipation_instance(p) = count(phase_source(:,1:p) == SOURCE_thermal_dissipation_ID)
source_thermal_dissipation_output = '' do source = 1, phase_Nsources(p)
if (phase_source(source,p) == SOURCE_thermal_dissipation_ID) &
source_thermal_dissipation_offset(p) = source
enddo
enddo
allocate(source_thermal_dissipation_coldworkCoeff(Ninstance), source=0.0_pReal) allocate(source_thermal_dissipation_sizePostResult(maxval(phase_Noutput),Ninstance),source=0)
allocate(source_thermal_dissipation_output (maxval(phase_Noutput),Ninstance))
source_thermal_dissipation_output = ''
do p=1, size(config_phase) 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)
source_thermal_dissipation_coldworkCoeff(instance) = config_phase(p)%getFloat('dissipation_coldworkcoeff') param(instance)%kappa = config_phase(p)%getFloat('dissipation_coldworkcoeff')
NofMyPhase=count(material_phase==p) NofMyPhase=count(material_phase==p)
sourceOffset = source_thermal_dissipation_offset(p) sourceOffset = source_thermal_dissipation_offset(p)
call material_allocateSourceState(p,sourceOffset,NofMyPhase,0_pInt,0_pInt,0_pInt) call material_allocateSourceState(p,sourceOffset,NofMyPhase,0,0,0)
enddo enddo
end subroutine source_thermal_dissipation_init end subroutine source_thermal_dissipation_init
@ -109,23 +103,23 @@ end subroutine source_thermal_dissipation_init
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
subroutine source_thermal_dissipation_getRateAndItsTangent(TDot, dTDOT_dT, Tstar, Lp, phase) subroutine source_thermal_dissipation_getRateAndItsTangent(TDot, dTDOT_dT, Tstar, Lp, phase)
implicit none implicit none
integer(pInt), intent(in) :: & integer, intent(in) :: &
phase phase
real(pReal), intent(in), dimension(3,3) :: & real(pReal), intent(in), dimension(3,3) :: &
Tstar Tstar
real(pReal), intent(in), dimension(3,3) :: & real(pReal), intent(in), dimension(3,3) :: &
Lp Lp
real(pReal), intent(out) :: & real(pReal), intent(out) :: &
TDot, & TDot, &
dTDOT_dT dTDOT_dT
integer(pInt) :: & integer :: &
instance instance
instance = source_thermal_dissipation_instance(phase) instance = source_thermal_dissipation_instance(phase)
TDot = source_thermal_dissipation_coldworkCoeff(instance)*sum(abs(Tstar*Lp)) TDot = param(instance)%kappa*sum(abs(Tstar*Lp))
dTDOT_dT = 0.0_pReal dTDOT_dT = 0.0_pReal
end subroutine source_thermal_dissipation_getRateAndItsTangent end subroutine source_thermal_dissipation_getRateAndItsTangent