don't clutter with use statements

This commit is contained in:
Martin Diehl 2019-05-18 06:54:45 +02:00
parent dce4775c17
commit ed8af98d69
4 changed files with 29 additions and 178 deletions

View File

@ -6,7 +6,20 @@
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
module homogenization module homogenization
use prec use prec
use IO
use config
use debug
use math
use material use material
use numerics
use constitutive
use crystallite
use mesh
use FEsolving
#if defined(PETSc) || defined(DAMASK_HDF5)
use results
use HDF5_utilities
#endif
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
! General variables for the homogenization at a material point ! General variables for the homogenization at a material point
@ -81,26 +94,6 @@ contains
!> @brief module initialization !> @brief module initialization
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
subroutine homogenization_init subroutine homogenization_init
use math, only: &
math_I3
use debug, only: &
debug_level, &
debug_homogenization, &
debug_levelBasic, &
debug_e, &
debug_g
use mesh, only: &
theMesh, &
mesh_element
use constitutive, only: &
constitutive_plasticity_maxSizePostResults, &
constitutive_source_maxSizePostResults
use crystallite, only: &
crystallite_maxSizePostResults
use config, only: &
config_deallocate, &
config_homogenization, &
homogenization_name
use homogenization_mech_RGC use homogenization_mech_RGC
use thermal_isothermal use thermal_isothermal
use thermal_adiabatic use thermal_adiabatic
@ -108,9 +101,6 @@ subroutine homogenization_init
use damage_none use damage_none
use damage_local use damage_local
use damage_nonlocal use damage_nonlocal
use IO
use numerics, only: &
worldrank
integer, parameter :: FILEUNIT = 200 integer, parameter :: FILEUNIT = 200
integer :: e,i,p integer :: e,i,p
@ -278,51 +268,6 @@ end subroutine homogenization_init
!> @brief parallelized calculation of stress and corresponding tangent at material points !> @brief parallelized calculation of stress and corresponding tangent at material points
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
subroutine materialpoint_stressAndItsTangent(updateJaco,dt) subroutine materialpoint_stressAndItsTangent(updateJaco,dt)
use numerics, only: &
subStepMinHomog, &
subStepSizeHomog, &
stepIncreaseHomog, &
nMPstate
use FEsolving, only: &
FEsolving_execElem, &
FEsolving_execIP, &
terminallyIll
use mesh, only: &
mesh_element
use crystallite, only: &
crystallite_F0, &
crystallite_Fp0, &
crystallite_Fp, &
crystallite_Fi0, &
crystallite_Fi, &
crystallite_Lp0, &
crystallite_Lp, &
crystallite_Li0, &
crystallite_Li, &
crystallite_S0, &
crystallite_S, &
crystallite_partionedF0, &
crystallite_partionedF, &
crystallite_partionedFp0, &
crystallite_partionedLp0, &
crystallite_partionedFi0, &
crystallite_partionedLi0, &
crystallite_partionedS0, &
crystallite_dt, &
crystallite_requested, &
crystallite_stress, &
crystallite_stressTangent, &
crystallite_orientations
#ifdef DEBUG
use debug, only: &
debug_level, &
debug_homogenization, &
debug_levelBasic, &
debug_levelExtensive, &
debug_levelSelective, &
debug_e, &
debug_i
#endif
real(pReal), intent(in) :: dt !< time increment real(pReal), intent(in) :: dt !< time increment
logical, intent(in) :: updateJaco !< initiating Jacobian update logical, intent(in) :: updateJaco !< initiating Jacobian update
@ -616,14 +561,6 @@ end subroutine materialpoint_stressAndItsTangent
!> @brief parallelized calculation of result array at material points !> @brief parallelized calculation of result array at material points
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
subroutine materialpoint_postResults subroutine materialpoint_postResults
use FEsolving, only: &
FEsolving_execElem, &
FEsolving_execIP
use mesh, only: &
mesh_element
use crystallite, only: &
crystallite_sizePostResults, &
crystallite_postResults
integer :: & integer :: &
thePos, & thePos, &
@ -673,10 +610,6 @@ end subroutine materialpoint_postResults
!> @brief partition material point def grad onto constituents !> @brief partition material point def grad onto constituents
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
subroutine partitionDeformation(ip,el) subroutine partitionDeformation(ip,el)
use mesh, only: &
mesh_element
use crystallite, only: &
crystallite_partionedF
use homogenization_mech_RGC, only: & use homogenization_mech_RGC, only: &
homogenization_RGC_partitionDeformation homogenization_RGC_partitionDeformation
@ -710,13 +643,6 @@ end subroutine partitionDeformation
!> "happy" with result !> "happy" with result
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
function updateState(ip,el) function updateState(ip,el)
use mesh, only: &
mesh_element
use crystallite, only: &
crystallite_P, &
crystallite_dPdF, &
crystallite_partionedF,&
crystallite_partionedF0
use homogenization_mech_RGC, only: & use homogenization_mech_RGC, only: &
homogenization_RGC_updateState homogenization_RGC_updateState
use thermal_adiabatic, only: & use thermal_adiabatic, only: &
@ -769,10 +695,6 @@ end function updateState
!> @brief derive average stress and stiffness from constituent quantities !> @brief derive average stress and stiffness from constituent quantities
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
subroutine averageStressAndItsTangent(ip,el) subroutine averageStressAndItsTangent(ip,el)
use mesh, only: &
mesh_element
use crystallite, only: &
crystallite_P,crystallite_dPdF
use homogenization_mech_RGC, only: & use homogenization_mech_RGC, only: &
homogenization_RGC_averageStressAndItsTangent homogenization_RGC_averageStressAndItsTangent
@ -810,8 +732,6 @@ end subroutine averageStressAndItsTangent
!> if homogenization_sizePostResults(i,e) > 0 !! !> if homogenization_sizePostResults(i,e) > 0 !!
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
function postResults(ip,el) function postResults(ip,el)
use mesh, only: &
mesh_element
use thermal_adiabatic, only: & use thermal_adiabatic, only: &
thermal_adiabatic_postResults thermal_adiabatic_postResults
use thermal_conduction, only: & use thermal_conduction, only: &
@ -868,14 +788,9 @@ end function postResults
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
subroutine homogenization_results subroutine homogenization_results
#if defined(PETSc) || defined(DAMASK_HDF5) #if defined(PETSc) || defined(DAMASK_HDF5)
use results
use homogenization_mech_RGC
use HDF5_utilities
use config, only: & use config, only: &
config_name_homogenization => homogenization_name ! anticipate logical name config_name_homogenization => homogenization_name ! anticipate logical name
use material, only: & use material, only: &
homogenization_typeInstance, &
material_homogenization_type => homogenization_type material_homogenization_type => homogenization_type
integer :: p integer :: p

View File

@ -8,10 +8,18 @@
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
module homogenization_mech_RGC module homogenization_mech_RGC
use prec use prec
use IO
use config
use debug
use math
use material use material
use numerics
use constitutive
#if defined(PETSc) || defined(DAMASK_HDF5)
use results
#endif
implicit none implicit none
private
enum, bind(c) enum, bind(c)
enumerator :: & enumerator :: &
@ -66,34 +74,12 @@ module homogenization_mech_RGC
type(tRGCdependentState), dimension(:), allocatable :: & type(tRGCdependentState), dimension(:), allocatable :: &
dependentState dependentState
public :: &
homogenization_RGC_init, &
homogenization_RGC_partitionDeformation, &
homogenization_RGC_averageStressAndItsTangent, &
homogenization_RGC_updateState, &
mech_RGC_results ! name suited for planned submodule situation
contains contains
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief allocates all necessary fields, reads information from material configuration file !> @brief allocates all necessary fields, reads information from material configuration file
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
subroutine homogenization_RGC_init() subroutine homogenization_RGC_init
use debug, only: &
#ifdef DEBUG
debug_i, &
debug_e, &
#endif
debug_level, &
debug_homogenization, &
debug_levelBasic
use math, only: &
math_EulerToR, &
INRAD
use IO, only: &
IO_error
use config, only: &
config_homogenization
integer :: & integer :: &
Ninstance, & Ninstance, &
@ -218,12 +204,6 @@ end subroutine homogenization_RGC_init
!> @brief partitions the deformation gradient onto the constituents !> @brief partitions the deformation gradient onto the constituents
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
subroutine homogenization_RGC_partitionDeformation(F,avgF,instance,of) subroutine homogenization_RGC_partitionDeformation(F,avgF,instance,of)
#ifdef DEBUG
use debug, only: &
debug_level, &
debug_homogenization, &
debug_levelExtensive
#endif
real(pReal), dimension (:,:,:), intent(out) :: F !< partioned F per grain real(pReal), dimension (:,:,:), intent(out) :: F !< partioned F per grain
@ -275,24 +255,6 @@ end subroutine homogenization_RGC_partitionDeformation
! "happy" with result ! "happy" with result
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
function homogenization_RGC_updateState(P,F,F0,avgF,dt,dPdF,ip,el) function homogenization_RGC_updateState(P,F,F0,avgF,dt,dPdF,ip,el)
#ifdef DEBUG
use debug, only: &
debug_level, &
debug_homogenization,&
debug_levelExtensive
#endif
use math, only: &
math_invert2
use numerics, only: &
absTol_RGC, &
relTol_RGC, &
absMax_RGC, &
relMax_RGC, &
pPert_RGC, &
maxdRelax_RGC, &
viscPower_RGC, &
viscModus_RGC, &
refRelaxRate_RGC
real(pReal), dimension(:,:,:), intent(in) :: & real(pReal), dimension(:,:,:), intent(in) :: &
P,& !< array of P P,& !< array of P
@ -712,10 +674,6 @@ function homogenization_RGC_updateState(P,F,F0,avgF,dt,dPdF,ip,el)
!> @brief calculate stress-like penalty due to deformation mismatch !> @brief calculate stress-like penalty due to deformation mismatch
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
subroutine stressPenalty(rPen,nMis,avgF,fDef,ip,el,instance,of) subroutine stressPenalty(rPen,nMis,avgF,fDef,ip,el,instance,of)
use math, only: &
math_civita
use numerics, only: &
xSmoo_RGC
real(pReal), dimension (:,:,:), intent(out) :: rPen !< stress-like penalty real(pReal), dimension (:,:,:), intent(out) :: rPen !< stress-like penalty
real(pReal), dimension (:,:), intent(out) :: nMis !< total amount of mismatch real(pReal), dimension (:,:), intent(out) :: nMis !< total amount of mismatch
@ -828,13 +786,6 @@ function homogenization_RGC_updateState(P,F,F0,avgF,dt,dPdF,ip,el)
!> @brief calculate stress-like penalty due to volume discrepancy !> @brief calculate stress-like penalty due to volume discrepancy
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
subroutine volumePenalty(vPen,vDiscrep,fAvg,fDef,nGrain,instance,of) subroutine volumePenalty(vPen,vDiscrep,fAvg,fDef,nGrain,instance,of)
use math, only: &
math_det33, &
math_inv33
use numerics, only: &
maxVolDiscr_RGC,&
volDiscrMod_RGC,&
volDiscrPow_RGC
real(pReal), dimension (:,:,:), intent(out) :: vPen ! stress-like penalty due to volume real(pReal), dimension (:,:,:), intent(out) :: vPen ! stress-like penalty due to volume
real(pReal), intent(out) :: vDiscrep ! total volume discrepancy real(pReal), intent(out) :: vDiscrep ! total volume discrepancy
@ -883,8 +834,6 @@ function homogenization_RGC_updateState(P,F,F0,avgF,dt,dPdF,ip,el)
! deformation ! deformation
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
function surfaceCorrection(avgF,instance,of) function surfaceCorrection(avgF,instance,of)
use math, only: &
math_invert33
real(pReal), dimension(3) :: surfaceCorrection real(pReal), dimension(3) :: surfaceCorrection
@ -916,8 +865,6 @@ function homogenization_RGC_updateState(P,F,F0,avgF,dt,dPdF,ip,el)
!> @brief compute the equivalent shear and bulk moduli from the elasticity tensor !> @brief compute the equivalent shear and bulk moduli from the elasticity tensor
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
function equivalentModuli(grainID,ip,el) function equivalentModuli(grainID,ip,el)
use constitutive, only: &
constitutive_homogenizedC
real(pReal), dimension(2) :: equivalentModuli real(pReal), dimension(2) :: equivalentModuli
@ -1015,8 +962,6 @@ end subroutine homogenization_RGC_averageStressAndItsTangent
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
subroutine mech_RGC_results(instance,group) subroutine mech_RGC_results(instance,group)
#if defined(PETSc) || defined(DAMASK_HDF5) #if defined(PETSc) || defined(DAMASK_HDF5)
use results, only: &
results_writeDataset
integer, intent(in) :: instance integer, intent(in) :: instance
character(len=*) :: group character(len=*) :: group

View File

@ -5,6 +5,9 @@
!> @brief Isostrain (full constraint Taylor assuption) homogenization scheme !> @brief Isostrain (full constraint Taylor assuption) homogenization scheme
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
submodule(homogenization) homogenization_mech_isostrain submodule(homogenization) homogenization_mech_isostrain
use config
use debug
use IO
implicit none implicit none
@ -30,14 +33,6 @@ contains
!> @brief allocates all neccessary fields, reads information from material configuration file !> @brief allocates all neccessary fields, reads information from material configuration file
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
module subroutine mech_isostrain_init module subroutine mech_isostrain_init
use debug, only: &
debug_HOMOGENIZATION, &
debug_level, &
debug_levelBasic
use IO, only: &
IO_error
use config, only: &
config_homogenization
integer :: & integer :: &
Ninstance, & Ninstance, &

View File

@ -5,6 +5,8 @@
!> @brief dummy homogenization homogenization scheme for 1 constituent per material point !> @brief dummy homogenization homogenization scheme for 1 constituent per material point
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
submodule(homogenization) homogenization_mech_none submodule(homogenization) homogenization_mech_none
use config
use debug
implicit none implicit none
@ -14,12 +16,6 @@ contains
!> @brief allocates all neccessary fields, reads information from material configuration file !> @brief allocates all neccessary fields, reads information from material configuration file
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
module subroutine mech_none_init module subroutine mech_none_init
use debug, only: &
debug_HOMOGENIZATION, &
debug_level, &
debug_levelBasic
use config, only: &
config_homogenization
integer :: & integer :: &
Ninstance, & Ninstance, &