some doxygen corrections
This commit is contained in:
parent
1f4d7c2ca4
commit
60633ffd98
|
@ -16,25 +16,29 @@
|
||||||
! You should have received a copy of the GNU General Public License
|
! You should have received a copy of the GNU General Public License
|
||||||
! along with DAMASK. If not, see <http://www.gnu.org/licenses/>.
|
! along with DAMASK. If not, see <http://www.gnu.org/licenses/>.
|
||||||
!
|
!
|
||||||
!##############################################################
|
!--------------------------------------------------------------------------------------------------
|
||||||
!* $Id$
|
! $Id$
|
||||||
!##############################################################
|
!--------------------------------------------------------------------------------------------------
|
||||||
|
!> @author Franz Roters, Max-Planck-Institut für Eisenforschung GmbH
|
||||||
|
!> @author Philip Eisenlohr, Max-Planck-Institut für Eisenforschung GmbH
|
||||||
|
!> @brief CPFEM engine
|
||||||
|
!--------------------------------------------------------------------------------------------------
|
||||||
module CPFEM
|
module CPFEM
|
||||||
!##############################################################
|
use prec, only: &
|
||||||
! *** CPFEM engine ***
|
pReal, &
|
||||||
|
pInt
|
||||||
|
|
||||||
use prec, only: pReal, pInt
|
|
||||||
implicit none
|
implicit none
|
||||||
real(pReal), parameter :: CPFEM_odd_stress = 1e15_pReal, &
|
real(pReal), parameter :: CPFEM_odd_stress = 1e15_pReal, & !< return value for stress in case of ping pong dummy cycle
|
||||||
CPFEM_odd_jacobian = 1e50_pReal
|
CPFEM_odd_jacobian = 1e50_pReal !< return value for jacobian in case of ping pong dummy cycle
|
||||||
|
|
||||||
real(pReal), dimension (:,:,:), allocatable :: CPFEM_cs !> Cauchy stress
|
real(pReal), dimension (:,:,:), allocatable :: CPFEM_cs !< Cauchy stress
|
||||||
real(pReal), dimension (:,:,:,:), allocatable :: CPFEM_dcsdE !> Cauchy stress tangent
|
real(pReal), dimension (:,:,:,:), allocatable :: CPFEM_dcsdE !< Cauchy stress tangent
|
||||||
real(pReal), dimension (:,:,:,:), allocatable :: CPFEM_dcsdE_knownGood !> known good tangent
|
real(pReal), dimension (:,:,:,:), allocatable :: CPFEM_dcsdE_knownGood !< known good tangent
|
||||||
|
|
||||||
logical :: CPFEM_init_done = .false., & !> remember whether init has been done already
|
logical :: CPFEM_init_done = .false., & !< remember whether init has been done already
|
||||||
CPFEM_init_inProgress = .false., & !> remember whether first IP is currently performing init
|
CPFEM_init_inProgress = .false., & !< remember whether first IP is currently performing init
|
||||||
CPFEM_calc_done = .false. !> remember whether first IP has already calced the results
|
CPFEM_calc_done = .false. !< remember whether first IP has already calced the results
|
||||||
logical, public, protected :: usePingPong = .false.
|
logical, public, protected :: usePingPong = .false.
|
||||||
integer(pInt), parameter, public :: &
|
integer(pInt), parameter, public :: &
|
||||||
CPFEM_CALCRESULTS = 2_pInt**0_pInt, &
|
CPFEM_CALCRESULTS = 2_pInt**0_pInt, &
|
||||||
|
@ -46,24 +50,35 @@ module CPFEM
|
||||||
|
|
||||||
contains
|
contains
|
||||||
|
|
||||||
!*********************************************************
|
|
||||||
!*** call (thread safe) all module initializations ***
|
|
||||||
!*********************************************************
|
|
||||||
|
|
||||||
|
!--------------------------------------------------------------------------------------------------
|
||||||
|
!> @brief call (thread safe) all module initializations
|
||||||
|
!--------------------------------------------------------------------------------------------------
|
||||||
subroutine CPFEM_initAll(Temperature,element,IP)
|
subroutine CPFEM_initAll(Temperature,element,IP)
|
||||||
|
use prec, only: &
|
||||||
use prec, only: prec_init
|
prec_init
|
||||||
use numerics, only: numerics_init
|
use numerics, only: &
|
||||||
use debug, only: debug_init
|
numerics_init
|
||||||
use FEsolving, only: FE_init
|
use debug, only: &
|
||||||
use math, only: math_init
|
debug_init
|
||||||
use mesh, only: mesh_init
|
use FEsolving, only: &
|
||||||
use lattice, only: lattice_init
|
FE_init
|
||||||
use material, only: material_init
|
use math, only: &
|
||||||
use constitutive, only: constitutive_init
|
math_init
|
||||||
use crystallite, only: crystallite_init
|
use mesh, only: &
|
||||||
use homogenization, only: homogenization_init
|
mesh_init
|
||||||
use IO, only: IO_init
|
use lattice, only: &
|
||||||
|
lattice_init
|
||||||
|
use material, only: &
|
||||||
|
material_init
|
||||||
|
use constitutive, only: &
|
||||||
|
constitutive_init
|
||||||
|
use crystallite, only: &
|
||||||
|
crystallite_init
|
||||||
|
use homogenization, only: &
|
||||||
|
homogenization_init
|
||||||
|
use IO, only: &
|
||||||
|
IO_init
|
||||||
use DAMASK_interface
|
use DAMASK_interface
|
||||||
|
|
||||||
implicit none
|
implicit none
|
||||||
|
@ -112,11 +127,10 @@ subroutine CPFEM_initAll(Temperature,element,IP)
|
||||||
|
|
||||||
end subroutine CPFEM_initAll
|
end subroutine CPFEM_initAll
|
||||||
|
|
||||||
!*********************************************************
|
|
||||||
!*** allocate the arrays defined in module CPFEM ***
|
|
||||||
!*** and initialize them ***
|
|
||||||
!*********************************************************
|
|
||||||
|
|
||||||
|
!--------------------------------------------------------------------------------------------------
|
||||||
|
!> @brief allocate the arrays defined in module CPFEM and initialize them
|
||||||
|
!--------------------------------------------------------------------------------------------------
|
||||||
subroutine CPFEM_init
|
subroutine CPFEM_init
|
||||||
use, intrinsic :: iso_fortran_env ! to get compiler_version and compiler_options (at least for gfortran 4.6 at the moment)
|
use, intrinsic :: iso_fortran_env ! to get compiler_version and compiler_options (at least for gfortran 4.6 at the moment)
|
||||||
use prec, only: &
|
use prec, only: &
|
||||||
|
@ -246,10 +260,9 @@ subroutine CPFEM_init
|
||||||
end subroutine CPFEM_init
|
end subroutine CPFEM_init
|
||||||
|
|
||||||
|
|
||||||
!***********************************************************************
|
!--------------------------------------------------------------------------------------------------
|
||||||
!*** perform initialization at first call, update variables and ***
|
!> @brief perform initialization at first call, update variables and call the actual material model
|
||||||
!*** call the actual material model ***
|
!--------------------------------------------------------------------------------------------------
|
||||||
!***********************************************************************
|
|
||||||
subroutine CPFEM_general(mode, ffn, ffn1, Temperature, dt, element, IP, cauchyStress,&
|
subroutine CPFEM_general(mode, ffn, ffn1, Temperature, dt, element, IP, cauchyStress,&
|
||||||
& jacobian, pstress, dPdF)
|
& jacobian, pstress, dPdF)
|
||||||
! note: cauchyStress = Cauchy stress cs(6) and jacobian = Consistent tangent dcs/dE
|
! note: cauchyStress = Cauchy stress cs(6) and jacobian = Consistent tangent dcs/dE
|
||||||
|
@ -608,20 +621,20 @@ subroutine CPFEM_general(mode, ffn, ffn1, Temperature, dt, element, IP, cauchySt
|
||||||
if (mode < 3) then
|
if (mode < 3) then
|
||||||
cauchyStress33 = math_Mandel6to33(cauchyStress)
|
cauchyStress33 = math_Mandel6to33(cauchyStress)
|
||||||
if (maxval(cauchyStress33) > debug_stressMax) then
|
if (maxval(cauchyStress33) > debug_stressMax) then
|
||||||
debug_stressMaxLocation = (/cp_en, IP/)
|
debug_stressMaxLocation = [cp_en, IP]
|
||||||
debug_stressMax = maxval(cauchyStress33)
|
debug_stressMax = maxval(cauchyStress33)
|
||||||
endif
|
endif
|
||||||
if (minval(cauchyStress33) < debug_stressMin) then
|
if (minval(cauchyStress33) < debug_stressMin) then
|
||||||
debug_stressMinLocation = (/cp_en, IP/)
|
debug_stressMinLocation = [cp_en, IP]
|
||||||
debug_stressMin = minval(cauchyStress33)
|
debug_stressMin = minval(cauchyStress33)
|
||||||
endif
|
endif
|
||||||
jacobian3333 = math_Mandel66to3333(jacobian)
|
jacobian3333 = math_Mandel66to3333(jacobian)
|
||||||
if (maxval(jacobian3333) > debug_jacobianMax) then
|
if (maxval(jacobian3333) > debug_jacobianMax) then
|
||||||
debug_jacobianMaxLocation = (/cp_en, IP/)
|
debug_jacobianMaxLocation = [cp_en, IP]
|
||||||
debug_jacobianMax = maxval(jacobian3333)
|
debug_jacobianMax = maxval(jacobian3333)
|
||||||
endif
|
endif
|
||||||
if (minval(jacobian3333) < debug_jacobianMin) then
|
if (minval(jacobian3333) < debug_jacobianMin) then
|
||||||
debug_jacobianMinLocation = (/cp_en, IP/)
|
debug_jacobianMinLocation = [cp_en, IP]
|
||||||
debug_jacobianMin = minval(jacobian3333)
|
debug_jacobianMin = minval(jacobian3333)
|
||||||
endif
|
endif
|
||||||
endif
|
endif
|
||||||
|
|
|
@ -17,10 +17,10 @@
|
||||||
! along with DAMASK. If not, see <http://www.gnu.org/licenses/>.
|
! along with DAMASK. If not, see <http://www.gnu.org/licenses/>.
|
||||||
!
|
!
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!* $Id$
|
! $Id$
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @author Franz Roters, Max-Planck-Institut für Eisenforschung GmbH
|
!> @author Franz Roters, Max-Planck-Institut für Eisenforschung GmbH
|
||||||
!! Philip Eisenlohr, Max-Planck-Institut für Eisenforschung GmbH
|
!> @author Philip Eisenlohr, Max-Planck-Institut für Eisenforschung GmbH
|
||||||
!> @brief elasticity, plasticity, internal microstructure state
|
!> @brief elasticity, plasticity, internal microstructure state
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
module constitutive
|
module constitutive
|
||||||
|
|
Loading…
Reference in New Issue