untied interlinked constitutive and CPFEM modules

now constitutive stores EulerAngles and CPFEM generates Fp_old from these
This commit is contained in:
Luc Hantcherli 2007-04-11 15:28:46 +00:00
parent cb4a85319d
commit eb292917b9
2 changed files with 9 additions and 4 deletions

View File

@ -35,11 +35,13 @@
SUBROUTINE CPFEM_init()
!
use prec, only: pReal,pInt
! use math, only: math_I3
use math, only: math_EulertoR
use mesh
use constitutive
!
implicit none
integer(pInt) e,i,g
!
! *** mpie.marc parameters ***
allocate(CPFEM_ffn_all (3,3,mesh_maxNips,mesh_NcpElems)) ; CPFEM_ffn_all = 0.0_pReal
@ -56,7 +58,9 @@
allocate(CPFEM_sigma_new(6,constitutive_maxNgrains,mesh_maxNips,mesh_NcpElems)) ; CPFEM_sigma_new = 0.0_pReal
!
! *** Plastic deformation gradient at (t=t0) and (t=t1) ***
allocate(CPFEM_Fp_old(3,3,constitutive_maxNgrains,mesh_maxNips,mesh_NcpElems)) ; CPFEM_Fp_old = 0.0_pReal
allocate(CPFEM_Fp_old(3,3,constitutive_maxNgrains,mesh_maxNips,mesh_NcpElems))
forall (e=1:mesh_NcpElems,i=1:mesh_maxNips,g=1:constitutive_maxNgrains) &
CPFEM_Fp_old(:,:,g,i,e) = math_EulerToR(constitutive_EulerAngles(:,g,i,e)) ! plastic def gradient reflects init orientation
allocate(CPFEM_Fp_new(3,3,constitutive_maxNgrains,mesh_maxNips,mesh_NcpElems)) ; CPFEM_Fp_new = 0.0_pReal
!
! *** Old jacobian (consistent tangent) ***

View File

@ -732,7 +732,7 @@ use prec, only: pReal,pInt
use math, only: math_sampleGaussOri,math_sampleFiberOri,math_sampleRandomOri,math_symmetricEulers,math_EulerToR
use mesh, only: mesh_NcpElems,FE_Nips,FE_mapElemtype,mesh_maxNips,mesh_element
use IO, only: IO_hybridIA
use CPFEM,only: CPFEM_Fp_old
implicit none
!* Definition of variables
@ -801,6 +801,7 @@ allocate(constitutive_matID(constitutive_maxNgrains,mesh_maxNips,mesh_NcpElems))
allocate(constitutive_texID(constitutive_maxNgrains,mesh_maxNips,mesh_NcpElems)) ; constitutive_texID=0_pInt
allocate(constitutive_MatVolFrac(constitutive_maxNgrains,mesh_maxNips,mesh_NcpElems)) ; constitutive_MatVolFrac=0.0_pReal
allocate(constitutive_TexVolFrac(constitutive_maxNgrains,mesh_maxNips,mesh_NcpElems)) ; constitutive_TexVolFrac=0.0_pReal
allocate(constitutive_EulerAngles(3,constitutive_maxNgrains,mesh_maxNips,mesh_NcpElems)) ; constitutive_EulerAngles=0.0_pReal
allocate(constitutive_Nresults(constitutive_maxNgrains,mesh_maxNips,mesh_NcpElems)) ; constitutive_Nresults=0_pInt
allocate(constitutive_results(constitutive_maxNresults,constitutive_maxNgrains,mesh_maxNips,mesh_NcpElems))
constitutive_results=0.0_pReal
@ -855,7 +856,7 @@ do e=1,mesh_NcpElems
constitutive_TexVolFrac(g,i,e) = texVolfrac(s)/multiplicity(texID)/Nsym(texID)
constitutive_Nstatevars(g,i,e) = material_Nslip(matID) ! number of state variables (i.e. tau_c of each slip system)
constitutive_Nresults(g,i,e) = 0 ! number of constitutive results
CPFEM_Fp_old(:,:,g,i,e) = math_EulerToR(Euler(:,s)) ! set plastic deformation gradient at t_0
constitutive_EulerAngles(:,g,i,e) = Euler(:,s) ! store initial orientation
forall (l=1:constitutive_Nstatevars(g,i,e)) ! initialize state variables
constitutive_state_old(l,g,i,e) = material_s0_slip(matID)
constitutive_state_new(l,g,i,e) = material_s0_slip(matID)