submodules allow inter-module communication

This commit is contained in:
Martin Diehl 2019-12-04 20:50:46 +01:00
parent 7d6a57dc17
commit ab1f0dc16b
4 changed files with 87 additions and 43 deletions

View File

@ -6,6 +6,7 @@
module constitutive module constitutive
use prec use prec
use math use math
use rotations
use debug use debug
use numerics use numerics
use IO use IO
@ -14,7 +15,6 @@ module constitutive
use results use results
use lattice use lattice
use discretization use discretization
use plastic_nonlocal
use geometry_plastic_nonlocal use geometry_plastic_nonlocal
use source_thermal_dissipation use source_thermal_dissipation
use source_thermal_externalheat use source_thermal_externalheat
@ -54,6 +54,9 @@ module constitutive
module subroutine plastic_disloUCLA_init module subroutine plastic_disloUCLA_init
end subroutine plastic_disloUCLA_init end subroutine plastic_disloUCLA_init
module subroutine plastic_nonlocal_init
end subroutine plastic_nonlocal_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) :: &
@ -123,6 +126,23 @@ module constitutive
instance, & instance, &
of of
end subroutine plastic_disloUCLA_LpAndItsTangent end subroutine plastic_disloUCLA_LpAndItsTangent
module subroutine plastic_nonlocal_LpAndItsTangent(Lp, dLp_dMp, &
Mp, Temperature, volume, ip, el)
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) :: &
Temperature, &
volume
integer, intent(in) :: &
ip, & !< current integration point
el !< current element number
end subroutine plastic_nonlocal_LpAndItsTangent
module subroutine plastic_isotropic_LiAndItsTangent(Li,dLi_dMi,Mi,instance,of) module subroutine plastic_isotropic_LiAndItsTangent(Li,dLi_dMi,Mi,instance,of)
@ -182,6 +202,21 @@ module constitutive
instance, & instance, &
of of
end subroutine plastic_disloUCLA_dotState end subroutine plastic_disloUCLA_dotState
module subroutine plastic_nonlocal_dotState(Mp, Fe, Fp, Temperature, &
timestep,ip,el)
integer, intent(in) :: &
ip, & !< current integration point
el !< current element number
real(pReal), intent(in) :: &
Temperature, & !< temperature
timestep !< substepped crystallite time increment
real(pReal), dimension(3,3), intent(in) ::&
Mp !< MandelStress
real(pReal), dimension(3,3,homogenization_maxNgrains,discretization_nIP,discretization_nElem), intent(in) :: &
Fe, & !< elastic deformation gradient
Fp !< plastic deformation gradient
end subroutine plastic_nonlocal_dotState
module subroutine plastic_dislotwin_dependentState(T,instance,of) module subroutine plastic_dislotwin_dependentState(T,instance,of)
@ -197,6 +232,15 @@ module constitutive
instance, & instance, &
of of
end subroutine plastic_disloUCLA_dependentState end subroutine plastic_disloUCLA_dependentState
module subroutine plastic_nonlocal_dependentState(Fe, Fp, ip, el)
integer, intent(in) :: &
ip, &
el
real(pReal), dimension(3,3), intent(in) :: &
Fe, &
Fp
end subroutine plastic_nonlocal_dependentState
module subroutine plastic_kinehardening_deltaState(Mp,instance,of) module subroutine plastic_kinehardening_deltaState(Mp,instance,of)
@ -206,6 +250,14 @@ module constitutive
instance, & instance, &
of of
end subroutine plastic_kinehardening_deltaState end subroutine plastic_kinehardening_deltaState
module subroutine plastic_nonlocal_deltaState(Mp,ip,el)
integer, intent(in) :: &
ip, &
el
real(pReal), dimension(3,3), intent(in) :: &
Mp
end subroutine plastic_nonlocal_deltaState
module function plastic_dislotwin_homogenizedC(ipc,ip,el) result(homogenizedC) module function plastic_dislotwin_homogenizedC(ipc,ip,el) result(homogenizedC)
@ -217,6 +269,14 @@ module constitutive
el !< element el !< element
end function plastic_dislotwin_homogenizedC end function plastic_dislotwin_homogenizedC
module subroutine plastic_nonlocal_updateCompatibility(orientation,i,e)
integer, intent(in) :: &
i, &
e
type(rotation), dimension(1,discretization_nIP,discretization_nElem), intent(in) :: &
orientation !< crystal orientation
end subroutine plastic_nonlocal_updateCompatibility
module subroutine plastic_isotropic_results(instance,group) module subroutine plastic_isotropic_results(instance,group)
integer, intent(in) :: instance integer, intent(in) :: instance
@ -242,10 +302,16 @@ module constitutive
integer, intent(in) :: instance integer, intent(in) :: instance
character(len=*), intent(in) :: group character(len=*), intent(in) :: group
end subroutine plastic_disloUCLA_results end subroutine plastic_disloUCLA_results
module subroutine plastic_nonlocal_results(instance,group)
integer, intent(in) :: instance
character(len=*), intent(in) :: group
end subroutine plastic_nonlocal_results
end interface end interface
public :: & public :: &
plastic_nonlocal_updateCompatibility, &
constitutive_init, & constitutive_init, &
constitutive_homogenizedC, & constitutive_homogenizedC, &
constitutive_microstructure, & constitutive_microstructure, &
@ -446,8 +512,7 @@ end subroutine constitutive_microstructure
! Mp in, dLp_dMp out ! Mp in, dLp_dMp out
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
subroutine constitutive_LpAndItsTangents(Lp, dLp_dS, dLp_dFi, & subroutine constitutive_LpAndItsTangents(Lp, dLp_dS, dLp_dFi, &
S, Fi, ipc, ip, el) S, Fi, ipc, ip, el)
integer, intent(in) :: & integer, intent(in) :: &
ipc, & !< component-ID of integration point ipc, & !< component-ID of integration point
ip, & !< integration point ip, & !< integration point

View File

@ -4,17 +4,8 @@
!> @author Philip Eisenlohr, Max-Planck-Institut für Eisenforschung GmbH !> @author Philip Eisenlohr, Max-Planck-Institut für Eisenforschung GmbH
!> @brief material subroutine for plasticity including dislocation flux !> @brief material subroutine for plasticity including dislocation flux
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
module plastic_nonlocal submodule(constitutive) plastic_nonlocal
use prec
use IO
use math
use debug
use material
use lattice
use rotations use rotations
use config
use lattice
use discretization
use geometry_plastic_nonlocal, only: & use geometry_plastic_nonlocal, only: &
nIPneighbors => geometry_plastic_nonlocal_nIPneighbors, & nIPneighbors => geometry_plastic_nonlocal_nIPneighbors, &
IPneighborhood => geometry_plastic_nonlocal_IPneighborhood, & IPneighborhood => geometry_plastic_nonlocal_IPneighborhood, &
@ -22,8 +13,7 @@ module plastic_nonlocal
IParea => geometry_plastic_nonlocal_IParea0, & IParea => geometry_plastic_nonlocal_IParea0, &
IPareaNormal => geometry_plastic_nonlocal_IPareaNormal0 IPareaNormal => geometry_plastic_nonlocal_IPareaNormal0
implicit none
private
real(pReal), parameter :: & real(pReal), parameter :: &
KB = 1.38e-23_pReal !< Physical parameter, Boltzmann constant in J/Kelvin KB = 1.38e-23_pReal !< Physical parameter, Boltzmann constant in J/Kelvin
@ -62,7 +52,7 @@ module plastic_nonlocal
!END DEPRECATED !END DEPRECATED
real(pReal), dimension(:,:,:,:,:,:), allocatable :: & real(pReal), dimension(:,:,:,:,:,:), allocatable :: &
compatibility !< slip system compatibility between me and my neighbors compatibility !< slip system compatibility between me and my neighbors
enum, bind(c) enum, bind(c)
enumerator :: & enumerator :: &
@ -148,7 +138,7 @@ module plastic_nonlocal
nonSchmid_neg !< combined projection of Schmid and non-Schmid contributions to the resolved shear stress (only for screws) nonSchmid_neg !< combined projection of Schmid and non-Schmid contributions to the resolved shear stress (only for screws)
integer :: & integer :: &
totalNslip totalNslip
integer, dimension(:) ,allocatable :: & integer, dimension(:) ,allocatable:: &
Nslip,& Nslip,&
colinearSystem !< colinear system to the active slip system (only valid for fcc!) colinearSystem !< colinear system to the active slip system (only valid for fcc!)
@ -204,18 +194,7 @@ module plastic_nonlocal
integer(kind(undefined_ID)), dimension(:,:), allocatable :: & integer(kind(undefined_ID)), dimension(:,:), allocatable :: &
plastic_nonlocal_outputID !< ID of each post result output plastic_nonlocal_outputID !< ID of each post result output
public :: &
plastic_nonlocal_init, &
plastic_nonlocal_dependentState, &
plastic_nonlocal_LpAndItsTangent, &
plastic_nonlocal_dotState, &
plastic_nonlocal_deltaState, &
plastic_nonlocal_updateCompatibility, &
plastic_nonlocal_results
private :: &
plastic_nonlocal_kinetics
contains contains
@ -223,7 +202,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_nonlocal_init module subroutine plastic_nonlocal_init
character(len=65536), dimension(0), parameter :: emptyStringArray = [character(len=65536)::] character(len=65536), dimension(0), parameter :: emptyStringArray = [character(len=65536)::]
integer, dimension(0), parameter :: emptyIntArray = [integer::] integer, dimension(0), parameter :: emptyIntArray = [integer::]
@ -752,7 +731,7 @@ end subroutine plastic_nonlocal_init
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief calculates quantities characterizing the microstructure !> @brief calculates quantities characterizing the microstructure
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
subroutine plastic_nonlocal_dependentState(Fe, Fp, ip, el) module subroutine plastic_nonlocal_dependentState(Fe, Fp, ip, el)
integer, intent(in) :: & integer, intent(in) :: &
ip, & ip, &
@ -1114,7 +1093,7 @@ end subroutine plastic_nonlocal_kinetics
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief calculates plastic velocity gradient and its tangent !> @brief calculates plastic velocity gradient and its tangent
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
subroutine plastic_nonlocal_LpAndItsTangent(Lp, dLp_dMp, & module subroutine plastic_nonlocal_LpAndItsTangent(Lp, dLp_dMp, &
Mp, Temperature, volume, ip, el) Mp, Temperature, volume, ip, el)
integer, intent(in) :: & integer, intent(in) :: &
@ -1244,7 +1223,7 @@ end subroutine plastic_nonlocal_LpAndItsTangent
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief (instantaneous) incremental change of microstructure !> @brief (instantaneous) incremental change of microstructure
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
subroutine plastic_nonlocal_deltaState(Mp,ip,el) module subroutine plastic_nonlocal_deltaState(Mp,ip,el)
integer, intent(in) :: & integer, intent(in) :: &
ip, & ip, &
@ -1360,8 +1339,8 @@ end subroutine plastic_nonlocal_deltaState
!--------------------------------------------------------------------------------------------------- !---------------------------------------------------------------------------------------------------
!> @brief calculates the rate of change of microstructure !> @brief calculates the rate of change of microstructure
!--------------------------------------------------------------------------------------------------- !---------------------------------------------------------------------------------------------------
subroutine plastic_nonlocal_dotState(Mp, Fe, Fp, Temperature, & module subroutine plastic_nonlocal_dotState(Mp, Fe, Fp, Temperature, &
timestep,ip,el) timestep,ip,el)
integer, intent(in) :: & integer, intent(in) :: &
ip, & !< current integration point ip, & !< current integration point
@ -1809,13 +1788,13 @@ end subroutine plastic_nonlocal_dotState
! plane normals and signed cosine of the angle between the slip directions. Only the largest values ! plane normals and signed cosine of the angle between the slip directions. Only the largest values
! that sum up to a total of 1 are considered, all others are set to zero. ! that sum up to a total of 1 are considered, all others are set to zero.
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
subroutine plastic_nonlocal_updateCompatibility(orientation,i,e) module subroutine plastic_nonlocal_updateCompatibility(orientation,i,e)
integer, intent(in) :: & integer, intent(in) :: &
i, & i, &
e e
type(rotation), dimension(1,discretization_nIP,discretization_nElem), intent(in) :: & type(rotation), dimension(1,discretization_nIP,discretization_nElem), intent(in) :: &
orientation ! crystal orientation in quaternions orientation ! crystal orientation
integer :: & integer :: &
Nneighbors, & ! number of neighbors Nneighbors, & ! number of neighbors
@ -1974,13 +1953,13 @@ end function getRho
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief writes results to HDF5 output file !> @brief writes results to HDF5 output file
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
subroutine plastic_nonlocal_results(instance,group) module subroutine plastic_nonlocal_results(instance,group)
#if defined(PETSc) || defined(DAMASK_HDF5) #if defined(PETSc) || defined(DAMASK_HDF5)
use results, only: & use results, only: &
results_writeDataset results_writeDataset
integer, intent(in) :: instance integer, intent(in) :: instance
character(len=*) :: group character(len=*),intent(in) :: group
integer :: o integer :: o
associate(prm => param(instance),dst => microstructure(instance),stt=>state(instance)) associate(prm => param(instance),dst => microstructure(instance),stt=>state(instance))
@ -2047,4 +2026,4 @@ subroutine plastic_nonlocal_results(instance,group)
end subroutine plastic_nonlocal_results end subroutine plastic_nonlocal_results
end module plastic_nonlocal end submodule plastic_nonlocal

View File

@ -21,7 +21,6 @@ module crystallite
use constitutive use constitutive
use discretization use discretization
use lattice use lattice
use plastic_nonlocal
use results use results
implicit none implicit none

View File

@ -483,7 +483,8 @@ module lattice
lattice_slip_normal, & lattice_slip_normal, &
lattice_slip_direction, & lattice_slip_direction, &
lattice_slip_transverse, & lattice_slip_transverse, &
lattice_labels_slip lattice_labels_slip, &
lattice_labels_twin
contains contains
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------