migrating to submodules
This commit is contained in:
parent
226b715c46
commit
4ee2e551b8
|
@ -12,11 +12,8 @@ module constitutive
|
||||||
use config
|
use config
|
||||||
use material
|
use material
|
||||||
use results
|
use results
|
||||||
use HDF5_utilities
|
|
||||||
use lattice
|
use lattice
|
||||||
use discretization
|
use discretization
|
||||||
use plastic_dislotwin
|
|
||||||
use plastic_disloucla
|
|
||||||
use plastic_nonlocal
|
use plastic_nonlocal
|
||||||
use geometry_plastic_nonlocal
|
use geometry_plastic_nonlocal
|
||||||
use source_thermal_dissipation
|
use source_thermal_dissipation
|
||||||
|
@ -37,7 +34,6 @@ module constitutive
|
||||||
constitutive_source_maxSizePostResults, &
|
constitutive_source_maxSizePostResults, &
|
||||||
constitutive_source_maxSizeDotState
|
constitutive_source_maxSizeDotState
|
||||||
|
|
||||||
|
|
||||||
interface
|
interface
|
||||||
|
|
||||||
module subroutine plastic_none_init
|
module subroutine plastic_none_init
|
||||||
|
@ -52,6 +48,13 @@ module constitutive
|
||||||
module subroutine plastic_kinehardening_init
|
module subroutine plastic_kinehardening_init
|
||||||
end subroutine plastic_kinehardening_init
|
end subroutine plastic_kinehardening_init
|
||||||
|
|
||||||
|
module subroutine plastic_dislotwin_init
|
||||||
|
end subroutine plastic_dislotwin_init
|
||||||
|
|
||||||
|
module subroutine plastic_disloUCLA_init
|
||||||
|
end subroutine plastic_disloUCLA_init
|
||||||
|
|
||||||
|
|
||||||
module subroutine plastic_isotropic_LpAndItsTangent(Lp,dLp_dMp,Mp,instance,of)
|
module subroutine plastic_isotropic_LpAndItsTangent(Lp,dLp_dMp,Mp,instance,of)
|
||||||
real(pReal), dimension(3,3), intent(out) :: &
|
real(pReal), dimension(3,3), intent(out) :: &
|
||||||
Lp !< plastic velocity gradient
|
Lp !< plastic velocity gradient
|
||||||
|
@ -91,6 +94,36 @@ module constitutive
|
||||||
of
|
of
|
||||||
end subroutine plastic_kinehardening_LpAndItsTangent
|
end subroutine plastic_kinehardening_LpAndItsTangent
|
||||||
|
|
||||||
|
module subroutine plastic_dislotwin_LpAndItsTangent(Lp,dLp_dMp,Mp,T,instance,of)
|
||||||
|
real(pReal), dimension(3,3), intent(out) :: &
|
||||||
|
Lp !< plastic velocity gradient
|
||||||
|
real(pReal), dimension(3,3,3,3), intent(out) :: &
|
||||||
|
dLp_dMp !< derivative of Lp with respect to the Mandel stress
|
||||||
|
|
||||||
|
real(pReal), dimension(3,3), intent(in) :: &
|
||||||
|
Mp !< Mandel stress
|
||||||
|
real(pReal), intent(in) :: &
|
||||||
|
T
|
||||||
|
integer, intent(in) :: &
|
||||||
|
instance, &
|
||||||
|
of
|
||||||
|
end subroutine plastic_dislotwin_LpAndItsTangent
|
||||||
|
|
||||||
|
pure module subroutine plastic_disloUCLA_LpAndItsTangent(Lp,dLp_dMp,Mp,T,instance,of)
|
||||||
|
real(pReal), dimension(3,3), intent(out) :: &
|
||||||
|
Lp !< plastic velocity gradient
|
||||||
|
real(pReal), dimension(3,3,3,3), intent(out) :: &
|
||||||
|
dLp_dMp !< derivative of Lp with respect to the Mandel stress
|
||||||
|
|
||||||
|
real(pReal), dimension(3,3), intent(in) :: &
|
||||||
|
Mp !< Mandel stress
|
||||||
|
real(pReal), intent(in) :: &
|
||||||
|
T
|
||||||
|
integer, intent(in) :: &
|
||||||
|
instance, &
|
||||||
|
of
|
||||||
|
end subroutine plastic_disloUCLA_LpAndItsTangent
|
||||||
|
|
||||||
|
|
||||||
module subroutine plastic_isotropic_LiAndItsTangent(Li,dLi_dMi,Mi,instance,of)
|
module subroutine plastic_isotropic_LiAndItsTangent(Li,dLi_dMi,Mi,instance,of)
|
||||||
real(pReal), dimension(3,3), intent(out) :: &
|
real(pReal), dimension(3,3), intent(out) :: &
|
||||||
|
@ -130,6 +163,41 @@ module constitutive
|
||||||
of
|
of
|
||||||
end subroutine plastic_kinehardening_dotState
|
end subroutine plastic_kinehardening_dotState
|
||||||
|
|
||||||
|
module subroutine plastic_dislotwin_dotState(Mp,T,instance,of)
|
||||||
|
real(pReal), dimension(3,3), intent(in) :: &
|
||||||
|
Mp !< Mandel stress
|
||||||
|
real(pReal), intent(in) :: &
|
||||||
|
T
|
||||||
|
integer, intent(in) :: &
|
||||||
|
instance, &
|
||||||
|
of
|
||||||
|
end subroutine plastic_dislotwin_dotState
|
||||||
|
|
||||||
|
module subroutine plastic_disloUCLA_dotState(Mp,T,instance,of)
|
||||||
|
real(pReal), dimension(3,3), intent(in) :: &
|
||||||
|
Mp !< Mandel stress
|
||||||
|
real(pReal), intent(in) :: &
|
||||||
|
T
|
||||||
|
integer, intent(in) :: &
|
||||||
|
instance, &
|
||||||
|
of
|
||||||
|
end subroutine plastic_disloUCLA_dotState
|
||||||
|
|
||||||
|
|
||||||
|
module subroutine plastic_dislotwin_dependentState(T,instance,of)
|
||||||
|
integer, intent(in) :: &
|
||||||
|
instance, &
|
||||||
|
of
|
||||||
|
real(pReal), intent(in) :: &
|
||||||
|
T
|
||||||
|
end subroutine plastic_dislotwin_dependentState
|
||||||
|
|
||||||
|
module subroutine plastic_disloUCLA_dependentState(instance,of)
|
||||||
|
integer, intent(in) :: &
|
||||||
|
instance, &
|
||||||
|
of
|
||||||
|
end subroutine plastic_disloUCLA_dependentState
|
||||||
|
|
||||||
|
|
||||||
module subroutine plastic_kinehardening_deltaState(Mp,instance,of)
|
module subroutine plastic_kinehardening_deltaState(Mp,instance,of)
|
||||||
real(pReal), dimension(3,3), intent(in) :: &
|
real(pReal), dimension(3,3), intent(in) :: &
|
||||||
|
@ -140,6 +208,16 @@ module constitutive
|
||||||
end subroutine plastic_kinehardening_deltaState
|
end subroutine plastic_kinehardening_deltaState
|
||||||
|
|
||||||
|
|
||||||
|
module function plastic_dislotwin_homogenizedC(ipc,ip,el) result(homogenizedC)
|
||||||
|
real(pReal), dimension(6,6) :: &
|
||||||
|
homogenizedC
|
||||||
|
integer, intent(in) :: &
|
||||||
|
ipc, & !< component-ID of integration point
|
||||||
|
ip, & !< integration point
|
||||||
|
el !< element
|
||||||
|
end function plastic_dislotwin_homogenizedC
|
||||||
|
|
||||||
|
|
||||||
module subroutine plastic_isotropic_results(instance,group)
|
module subroutine plastic_isotropic_results(instance,group)
|
||||||
integer, intent(in) :: instance
|
integer, intent(in) :: instance
|
||||||
character(len=*), intent(in) :: group
|
character(len=*), intent(in) :: group
|
||||||
|
@ -155,6 +233,16 @@ module constitutive
|
||||||
character(len=*), intent(in) :: group
|
character(len=*), intent(in) :: group
|
||||||
end subroutine plastic_kinehardening_results
|
end subroutine plastic_kinehardening_results
|
||||||
|
|
||||||
|
module subroutine plastic_dislotwin_results(instance,group)
|
||||||
|
integer, intent(in) :: instance
|
||||||
|
character(len=*), intent(in) :: group
|
||||||
|
end subroutine plastic_dislotwin_results
|
||||||
|
|
||||||
|
module subroutine plastic_disloUCLA_results(instance,group)
|
||||||
|
integer, intent(in) :: instance
|
||||||
|
character(len=*), intent(in) :: group
|
||||||
|
end subroutine plastic_disloUCLA_results
|
||||||
|
|
||||||
end interface
|
end interface
|
||||||
|
|
||||||
public :: &
|
public :: &
|
||||||
|
@ -810,11 +898,11 @@ subroutine constitutive_results
|
||||||
character(len=256) :: group
|
character(len=256) :: group
|
||||||
do p=1,size(config_name_phase)
|
do p=1,size(config_name_phase)
|
||||||
group = trim('current/constituent')//'/'//trim(config_name_phase(p))
|
group = trim('current/constituent')//'/'//trim(config_name_phase(p))
|
||||||
call HDF5_closeGroup(results_addGroup(group))
|
call results_closeGroup(results_addGroup(group))
|
||||||
|
|
||||||
group = trim(group)//'/plastic'
|
group = trim(group)//'/plastic'
|
||||||
|
|
||||||
call HDF5_closeGroup(results_addGroup(group))
|
call results_closeGroup(results_addGroup(group))
|
||||||
select case(phase_plasticity(p))
|
select case(phase_plasticity(p))
|
||||||
|
|
||||||
case(PLASTICITY_ISOTROPIC_ID)
|
case(PLASTICITY_ISOTROPIC_ID)
|
||||||
|
|
|
@ -5,21 +5,9 @@
|
||||||
!> @author Martin Diehl, Max-Planck-Institut für Eisenforschung GmbH
|
!> @author Martin Diehl, Max-Planck-Institut für Eisenforschung GmbH
|
||||||
!> @brief crystal plasticity model for bcc metals, especially Tungsten
|
!> @brief crystal plasticity model for bcc metals, especially Tungsten
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
module plastic_disloUCLA
|
submodule(constitutive) plastic_disloUCLA
|
||||||
use prec
|
|
||||||
use debug
|
|
||||||
use math
|
|
||||||
use IO
|
|
||||||
use material
|
|
||||||
use config
|
|
||||||
use lattice
|
|
||||||
use discretization
|
|
||||||
use results
|
|
||||||
|
|
||||||
implicit none
|
real(pReal), parameter :: &
|
||||||
private
|
|
||||||
|
|
||||||
real(pReal), parameter, private :: &
|
|
||||||
kB = 1.38e-23_pReal !< Boltzmann constant in J/Kelvin
|
kB = 1.38e-23_pReal !< Boltzmann constant in J/Kelvin
|
||||||
|
|
||||||
enum, bind(c)
|
enum, bind(c)
|
||||||
|
@ -33,14 +21,14 @@ module plastic_disloUCLA
|
||||||
tau_pass_ID
|
tau_pass_ID
|
||||||
end enum
|
end enum
|
||||||
|
|
||||||
type, private :: tParameters
|
type :: tParameters
|
||||||
real(pReal) :: &
|
real(pReal) :: &
|
||||||
aTol_rho, &
|
aTol_rho, &
|
||||||
D, & !< grain size
|
D, & !< grain size
|
||||||
mu, &
|
mu, &
|
||||||
D_0, & !< prefactor for self-diffusion coefficient
|
D_0, & !< prefactor for self-diffusion coefficient
|
||||||
Q_cl !< activation energy for dislocation climb
|
Q_cl !< activation energy for dislocation climb
|
||||||
real(pReal), dimension(:), allocatable :: &
|
real(pReal), dimension(:), allocatable :: &
|
||||||
rho_mob_0, & !< initial dislocation density
|
rho_mob_0, & !< initial dislocation density
|
||||||
rho_dip_0, & !< initial dipole density
|
rho_dip_0, & !< initial dipole density
|
||||||
b_sl, & !< magnitude of burgers vector [m]
|
b_sl, & !< magnitude of burgers vector [m]
|
||||||
|
@ -58,31 +46,31 @@ module plastic_disloUCLA
|
||||||
kink_height, & !< height of the kink pair
|
kink_height, & !< height of the kink pair
|
||||||
w, & !< width of the kink pair
|
w, & !< width of the kink pair
|
||||||
omega !< attempt frequency for kink pair nucleation
|
omega !< attempt frequency for kink pair nucleation
|
||||||
real(pReal), dimension(:,:), allocatable :: &
|
real(pReal), dimension(:,:), allocatable :: &
|
||||||
h_sl_sl, & !< slip resistance from slip activity
|
h_sl_sl, & !< slip resistance from slip activity
|
||||||
forestProjectionEdge
|
forestProjectionEdge
|
||||||
real(pReal), dimension(:,:,:), allocatable :: &
|
real(pReal), dimension(:,:,:), allocatable :: &
|
||||||
Schmid, &
|
Schmid, &
|
||||||
nonSchmid_pos, &
|
nonSchmid_pos, &
|
||||||
nonSchmid_neg
|
nonSchmid_neg
|
||||||
integer :: &
|
integer :: &
|
||||||
sum_N_sl !< total number of active slip system
|
sum_N_sl !< total number of active slip system
|
||||||
integer, dimension(:), allocatable :: &
|
integer, dimension(:), allocatable :: &
|
||||||
N_sl !< number of active slip systems for each family
|
N_sl !< number of active slip systems for each family
|
||||||
integer(kind(undefined_ID)), dimension(:),allocatable :: &
|
integer(kind(undefined_ID)), dimension(:), allocatable :: &
|
||||||
outputID !< ID of each post result output
|
outputID !< ID of each post result output
|
||||||
logical :: &
|
logical :: &
|
||||||
dipoleFormation !< flag indicating consideration of dipole formation
|
dipoleFormation !< flag indicating consideration of dipole formation
|
||||||
end type !< container type for internal constitutive parameters
|
end type !< container type for internal constitutive parameters
|
||||||
|
|
||||||
type, private :: tDisloUCLAState
|
type :: tDisloUCLAState
|
||||||
real(pReal), dimension(:,:), pointer :: &
|
real(pReal), dimension(:,:), pointer :: &
|
||||||
rho_mob, &
|
rho_mob, &
|
||||||
rho_dip, &
|
rho_dip, &
|
||||||
gamma_sl
|
gamma_sl
|
||||||
end type tDisloUCLAState
|
end type tDisloUCLAState
|
||||||
|
|
||||||
type, private :: tDisloUCLAdependentState
|
type :: tDisloUCLAdependentState
|
||||||
real(pReal), dimension(:,:), allocatable :: &
|
real(pReal), dimension(:,:), allocatable :: &
|
||||||
Lambda_sl, &
|
Lambda_sl, &
|
||||||
threshold_stress
|
threshold_stress
|
||||||
|
@ -90,20 +78,11 @@ module plastic_disloUCLA
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! containers for parameters and state
|
! containers for parameters and state
|
||||||
type(tParameters), allocatable, dimension(:), private :: param
|
type(tParameters), allocatable, dimension(:) :: param
|
||||||
type(tDisloUCLAState), allocatable, dimension(:), private :: &
|
type(tDisloUCLAState), allocatable, dimension(:) :: &
|
||||||
dotState, &
|
dotState, &
|
||||||
state
|
state
|
||||||
type(tDisloUCLAdependentState), allocatable, dimension(:), private :: dependentState
|
type(tDisloUCLAdependentState), allocatable, dimension(:) :: dependentState
|
||||||
|
|
||||||
public :: &
|
|
||||||
plastic_disloUCLA_init, &
|
|
||||||
plastic_disloUCLA_dependentState, &
|
|
||||||
plastic_disloUCLA_LpAndItsTangent, &
|
|
||||||
plastic_disloUCLA_dotState, &
|
|
||||||
plastic_disloUCLA_results
|
|
||||||
private :: &
|
|
||||||
kinetics
|
|
||||||
|
|
||||||
contains
|
contains
|
||||||
|
|
||||||
|
@ -112,7 +91,7 @@ contains
|
||||||
!> @brief module initialization
|
!> @brief module initialization
|
||||||
!> @details reads in material parameters, allocates arrays, and does sanity checks
|
!> @details reads in material parameters, allocates arrays, and does sanity checks
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
subroutine plastic_disloUCLA_init()
|
module subroutine plastic_disloUCLA_init
|
||||||
|
|
||||||
integer :: &
|
integer :: &
|
||||||
Ninstance, &
|
Ninstance, &
|
||||||
|
@ -333,7 +312,7 @@ end subroutine plastic_disloUCLA_init
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief calculates plastic velocity gradient and its tangent
|
!> @brief calculates plastic velocity gradient and its tangent
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
pure subroutine plastic_disloUCLA_LpAndItsTangent(Lp,dLp_dMp, &
|
pure module subroutine plastic_disloUCLA_LpAndItsTangent(Lp,dLp_dMp, &
|
||||||
Mp,T,instance,of)
|
Mp,T,instance,of)
|
||||||
real(pReal), dimension(3,3), intent(out) :: &
|
real(pReal), dimension(3,3), intent(out) :: &
|
||||||
Lp !< plastic velocity gradient
|
Lp !< plastic velocity gradient
|
||||||
|
@ -376,7 +355,7 @@ end subroutine plastic_disloUCLA_LpAndItsTangent
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief calculates the rate of change of microstructure
|
!> @brief calculates the rate of change of microstructure
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
subroutine plastic_disloUCLA_dotState(Mp,T,instance,of)
|
module subroutine plastic_disloUCLA_dotState(Mp,T,instance,of)
|
||||||
|
|
||||||
real(pReal), dimension(3,3), intent(in) :: &
|
real(pReal), dimension(3,3), intent(in) :: &
|
||||||
Mp !< Mandel stress
|
Mp !< Mandel stress
|
||||||
|
@ -436,7 +415,7 @@ end subroutine plastic_disloUCLA_dotState
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief calculates derived quantities from state
|
!> @brief calculates derived quantities from state
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
subroutine plastic_disloUCLA_dependentState(instance,of)
|
module subroutine plastic_disloUCLA_dependentState(instance,of)
|
||||||
|
|
||||||
integer, intent(in) :: &
|
integer, intent(in) :: &
|
||||||
instance, &
|
instance, &
|
||||||
|
@ -462,7 +441,7 @@ end subroutine plastic_disloUCLA_dependentState
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief writes results to HDF5 output file
|
!> @brief writes results to HDF5 output file
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
subroutine plastic_disloUCLA_results(instance,group)
|
module subroutine plastic_disloUCLA_results(instance,group)
|
||||||
#if defined(PETSc) || defined(DAMASK_HDF5)
|
#if defined(PETSc) || defined(DAMASK_HDF5)
|
||||||
|
|
||||||
integer, intent(in) :: instance
|
integer, intent(in) :: instance
|
||||||
|
@ -615,4 +594,4 @@ pure subroutine kinetics(Mp,T,instance,of, &
|
||||||
|
|
||||||
end subroutine kinetics
|
end subroutine kinetics
|
||||||
|
|
||||||
end module plastic_disloUCLA
|
end submodule plastic_disloUCLA
|
|
@ -7,19 +7,7 @@
|
||||||
!> @brief material subroutine incoprorating dislocation and twinning physics
|
!> @brief material subroutine incoprorating dislocation and twinning physics
|
||||||
!> @details to be done
|
!> @details to be done
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
module plastic_dislotwin
|
submodule(constitutive) plastic_dislotwin
|
||||||
use prec
|
|
||||||
use debug
|
|
||||||
use math
|
|
||||||
use IO
|
|
||||||
use material
|
|
||||||
use config
|
|
||||||
use lattice
|
|
||||||
use discretization
|
|
||||||
use results
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
private
|
|
||||||
|
|
||||||
real(pReal), parameter :: &
|
real(pReal), parameter :: &
|
||||||
kB = 1.38e-23_pReal !< Boltzmann constant in J/Kelvin
|
kB = 1.38e-23_pReal !< Boltzmann constant in J/Kelvin
|
||||||
|
@ -156,14 +144,6 @@ module plastic_dislotwin
|
||||||
state
|
state
|
||||||
type(tDislotwinMicrostructure), allocatable, dimension(:) :: dependentState
|
type(tDislotwinMicrostructure), allocatable, dimension(:) :: dependentState
|
||||||
|
|
||||||
public :: &
|
|
||||||
plastic_dislotwin_init, &
|
|
||||||
plastic_dislotwin_homogenizedC, &
|
|
||||||
plastic_dislotwin_dependentState, &
|
|
||||||
plastic_dislotwin_LpAndItsTangent, &
|
|
||||||
plastic_dislotwin_dotState, &
|
|
||||||
plastic_dislotwin_results
|
|
||||||
|
|
||||||
contains
|
contains
|
||||||
|
|
||||||
|
|
||||||
|
@ -171,7 +151,7 @@ contains
|
||||||
!> @brief module initialization
|
!> @brief module initialization
|
||||||
!> @details reads in material parameters, allocates arrays, and does sanity checks
|
!> @details reads in material parameters, allocates arrays, and does sanity checks
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
subroutine plastic_dislotwin_init
|
module subroutine plastic_dislotwin_init
|
||||||
|
|
||||||
integer :: &
|
integer :: &
|
||||||
Ninstance, &
|
Ninstance, &
|
||||||
|
@ -576,14 +556,14 @@ end subroutine plastic_dislotwin_init
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief returns the homogenized elasticity matrix
|
!> @brief returns the homogenized elasticity matrix
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
function plastic_dislotwin_homogenizedC(ipc,ip,el) result(homogenizedC)
|
module function plastic_dislotwin_homogenizedC(ipc,ip,el) result(homogenizedC)
|
||||||
|
|
||||||
real(pReal), dimension(6,6) :: &
|
real(pReal), dimension(6,6) :: &
|
||||||
homogenizedC
|
homogenizedC
|
||||||
integer, intent(in) :: &
|
integer, intent(in) :: &
|
||||||
ipc, & !< component-ID of integration point
|
ipc, & !< component-ID of integration point
|
||||||
ip, & !< integration point
|
ip, & !< integration point
|
||||||
el !< element
|
el !< element
|
||||||
|
|
||||||
integer :: i, &
|
integer :: i, &
|
||||||
of
|
of
|
||||||
|
@ -615,7 +595,7 @@ end function plastic_dislotwin_homogenizedC
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief calculates plastic velocity gradient and its tangent
|
!> @brief calculates plastic velocity gradient and its tangent
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
subroutine plastic_dislotwin_LpAndItsTangent(Lp,dLp_dMp,Mp,T,instance,of)
|
module subroutine plastic_dislotwin_LpAndItsTangent(Lp,dLp_dMp,Mp,T,instance,of)
|
||||||
|
|
||||||
real(pReal), dimension(3,3), intent(out) :: Lp
|
real(pReal), dimension(3,3), intent(out) :: Lp
|
||||||
real(pReal), dimension(3,3,3,3), intent(out) :: dLp_dMp
|
real(pReal), dimension(3,3,3,3), intent(out) :: dLp_dMp
|
||||||
|
@ -730,7 +710,7 @@ end subroutine plastic_dislotwin_LpAndItsTangent
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief calculates the rate of change of microstructure
|
!> @brief calculates the rate of change of microstructure
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
subroutine plastic_dislotwin_dotState(Mp,T,instance,of)
|
module subroutine plastic_dislotwin_dotState(Mp,T,instance,of)
|
||||||
|
|
||||||
real(pReal), dimension(3,3), intent(in):: &
|
real(pReal), dimension(3,3), intent(in):: &
|
||||||
Mp !< Mandel stress
|
Mp !< Mandel stress
|
||||||
|
@ -833,7 +813,7 @@ end subroutine plastic_dislotwin_dotState
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief calculates derived quantities from state
|
!> @brief calculates derived quantities from state
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
subroutine plastic_dislotwin_dependentState(T,instance,of)
|
module subroutine plastic_dislotwin_dependentState(T,instance,of)
|
||||||
|
|
||||||
integer, intent(in) :: &
|
integer, intent(in) :: &
|
||||||
instance, &
|
instance, &
|
||||||
|
@ -925,11 +905,11 @@ end subroutine plastic_dislotwin_dependentState
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief writes results to HDF5 output file
|
!> @brief writes results to HDF5 output file
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
subroutine plastic_dislotwin_results(instance,group)
|
module subroutine plastic_dislotwin_results(instance,group)
|
||||||
#if defined(PETSc) || defined(DAMASK_HDF5)
|
#if defined(PETSc) || defined(DAMASK_HDF5)
|
||||||
|
|
||||||
integer, intent(in) :: instance
|
integer, intent(in) :: instance
|
||||||
character(len=*) :: group
|
character(len=*), intent(in) :: group
|
||||||
integer :: o
|
integer :: o
|
||||||
|
|
||||||
associate(prm => param(instance), stt => state(instance), dst => dependentState(instance))
|
associate(prm => param(instance), stt => state(instance), dst => dependentState(instance))
|
||||||
|
@ -1183,4 +1163,4 @@ pure subroutine kinetics_trans(Mp,T,dot_gamma_sl,instance,of,&
|
||||||
|
|
||||||
end subroutine kinetics_trans
|
end subroutine kinetics_trans
|
||||||
|
|
||||||
end module plastic_dislotwin
|
end submodule plastic_dislotwin
|
Loading…
Reference in New Issue