2011-04-07 12:50:28 +05:30
|
|
|
! Copyright 2011 Max-Planck-Institut für Eisenforschung GmbH
|
2011-04-04 19:39:54 +05:30
|
|
|
!
|
|
|
|
! This file is part of DAMASK,
|
2011-04-07 12:50:28 +05:30
|
|
|
! the Düsseldorf Advanced MAterial Simulation Kit.
|
2011-04-04 19:39:54 +05:30
|
|
|
!
|
|
|
|
! DAMASK is free software: you can redistribute it and/or modify
|
|
|
|
! it under the terms of the GNU General Public License as published by
|
|
|
|
! the Free Software Foundation, either version 3 of the License, or
|
|
|
|
! (at your option) any later version.
|
|
|
|
!
|
|
|
|
! DAMASK is distributed in the hope that it will be useful,
|
|
|
|
! but WITHOUT ANY WARRANTY; without even the implied warranty of
|
|
|
|
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
|
|
|
|
! GNU General Public License for more details.
|
|
|
|
!
|
|
|
|
! You should have received a copy of the GNU General Public License
|
|
|
|
! along with DAMASK. If not, see <http://www.gnu.org/licenses/>.
|
|
|
|
!
|
2012-10-02 18:23:25 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2009-08-31 20:39:15 +05:30
|
|
|
!* $Id$
|
2012-10-02 18:23:25 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @author Franz Roters, Max-Planck-Institut für Eisenforschung GmbH
|
|
|
|
!! Philip Eisenlohr, Max-Planck-Institut für Eisenforschung GmbH
|
|
|
|
!> @brief elasticity, plasticity, internal microstructure state
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2009-03-06 15:32:36 +05:30
|
|
|
|
2012-10-02 18:23:25 +05:30
|
|
|
module constitutive
|
2009-03-06 15:32:36 +05:30
|
|
|
|
2012-03-09 01:55:28 +05:30
|
|
|
use prec, only: pInt, p_vec
|
2009-03-06 15:32:36 +05:30
|
|
|
|
2012-03-09 01:55:28 +05:30
|
|
|
implicit none
|
2012-10-02 18:23:25 +05:30
|
|
|
!private
|
2012-03-09 01:55:28 +05:30
|
|
|
type(p_vec), dimension(:,:,:), allocatable :: &
|
2012-10-02 18:23:25 +05:30
|
|
|
constitutive_state0, & !< pointer array to microstructure at start of FE inc
|
|
|
|
constitutive_partionedState0, & !< pointer array to microstructure at start of homogenization inc
|
|
|
|
constitutive_subState0, & !< pointer array to microstructure at start of crystallite inc
|
|
|
|
constitutive_state, & !< pointer array to current microstructure (end of converged time step)
|
|
|
|
constitutive_state_backup, & !< pointer array to backed up microstructure (end of converged time step)
|
|
|
|
constitutive_dotState, & !< pointer array to evolution of current microstructure
|
|
|
|
constitutive_deltaState, & !< pointer array to incremental change of current microstructure
|
|
|
|
constitutive_previousDotState,& !< pointer array to previous evolution of current microstructure
|
|
|
|
constitutive_previousDotState2,& !< pointer array to 2nd previous evolution of current microstructure
|
|
|
|
constitutive_dotState_backup, & !< pointer array to backed up evolution of current microstructure
|
|
|
|
constitutive_RK4dotState, & !< pointer array to evolution of microstructure defined by classical Runge-Kutta method
|
|
|
|
constitutive_aTolState !< pointer array to absolute state tolerance
|
|
|
|
|
|
|
|
type(p_vec), dimension(:,:,:,:), allocatable :: &
|
|
|
|
constitutive_RKCK45dotState !< pointer array to evolution of microstructure used by Cash-Karp Runge-Kutta method
|
|
|
|
|
|
|
|
integer(pInt), dimension(:,:,:), allocatable :: &
|
|
|
|
constitutive_sizeDotState, & !< size of dotState array
|
|
|
|
constitutive_sizeState, & !< size of state array per grain
|
|
|
|
constitutive_sizePostResults !< size of postResults array per grain
|
2012-03-09 01:55:28 +05:30
|
|
|
|
|
|
|
integer(pInt) :: &
|
|
|
|
constitutive_maxSizeDotState, &
|
|
|
|
constitutive_maxSizeState, &
|
|
|
|
constitutive_maxSizePostResults
|
|
|
|
|
2012-03-14 21:46:11 +05:30
|
|
|
character (len=*), parameter, public :: constitutive_hooke_label = 'hooke'
|
|
|
|
|
2012-10-02 18:23:25 +05:30
|
|
|
public :: &
|
|
|
|
constitutive_init, &
|
|
|
|
constitutive_homogenizedC, &
|
|
|
|
constitutive_averageBurgers, &
|
|
|
|
constitutive_microstructure, &
|
|
|
|
constitutive_LpAndItsTangent, &
|
|
|
|
constitutive_TandItsTangent, &
|
|
|
|
constitutive_collectDotState, &
|
|
|
|
constitutive_collectDeltaState, &
|
|
|
|
constitutive_postResults
|
|
|
|
|
|
|
|
private :: &
|
|
|
|
constitutive_hooke_TandItsTangent
|
|
|
|
|
2012-03-09 01:55:28 +05:30
|
|
|
contains
|
2012-10-02 18:23:25 +05:30
|
|
|
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief allocates arrays pointing to array of the various constitutive modules
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2012-03-09 01:55:28 +05:30
|
|
|
subroutine constitutive_init
|
2012-10-02 18:23:25 +05:30
|
|
|
use, intrinsic :: iso_fortran_env ! to get compiler_version and compiler_options (at least for gfortran 4.6 at the moment)
|
2012-07-05 15:24:50 +05:30
|
|
|
use debug, only: debug_level, &
|
2012-03-09 01:55:28 +05:30
|
|
|
debug_constitutive, &
|
|
|
|
debug_levelBasic
|
|
|
|
use numerics, only: numerics_integrator
|
|
|
|
use IO, only: IO_error, &
|
|
|
|
IO_open_file, &
|
|
|
|
IO_open_jobFile_stat, &
|
2012-08-16 20:25:23 +05:30
|
|
|
IO_write_jobFile, &
|
|
|
|
IO_write_jobBinaryIntFile
|
2012-03-09 01:55:28 +05:30
|
|
|
use mesh, only: mesh_maxNips, &
|
|
|
|
mesh_NcpElems, &
|
2012-10-02 18:27:24 +05:30
|
|
|
mesh_element, &
|
2012-11-16 04:15:20 +05:30
|
|
|
mesh_ipNeighborhood, &
|
2012-11-28 00:06:55 +05:30
|
|
|
mesh_maxNipNeighbors, &
|
2012-10-02 18:27:24 +05:30
|
|
|
FE_Nips, &
|
|
|
|
FE_NipNeighbors, &
|
2012-11-16 04:15:20 +05:30
|
|
|
FE_geomtype
|
2012-03-09 01:55:28 +05:30
|
|
|
use material, only: material_phase, &
|
|
|
|
material_Nphase, &
|
|
|
|
material_localFileExt, &
|
|
|
|
material_configFile, &
|
|
|
|
phase_name, &
|
2012-06-02 19:53:28 +05:30
|
|
|
phase_elasticity, &
|
2012-03-12 19:39:37 +05:30
|
|
|
phase_plasticity, &
|
|
|
|
phase_plasticityInstance, &
|
2012-03-09 01:55:28 +05:30
|
|
|
phase_Noutput, &
|
|
|
|
homogenization_Ngrains, &
|
|
|
|
homogenization_maxNgrains
|
2012-07-03 16:46:38 +05:30
|
|
|
use constitutive_none
|
2012-03-09 01:55:28 +05:30
|
|
|
use constitutive_j2
|
|
|
|
use constitutive_phenopowerlaw
|
|
|
|
use constitutive_titanmod
|
|
|
|
use constitutive_dislotwin
|
|
|
|
use constitutive_nonlocal
|
2009-03-06 15:32:36 +05:30
|
|
|
|
2011-03-29 12:57:19 +05:30
|
|
|
implicit none
|
2012-02-21 21:30:00 +05:30
|
|
|
integer(pInt), parameter :: fileunit = 200_pInt
|
2012-10-02 18:23:25 +05:30
|
|
|
integer(pInt) g, & ! grain number
|
|
|
|
i, & ! integration point number
|
|
|
|
e, & ! element number
|
|
|
|
gMax, & ! maximum number of grains
|
|
|
|
iMax, & ! maximum number of integration points
|
|
|
|
eMax, & ! maximum number of elements
|
2012-11-28 00:06:55 +05:30
|
|
|
n, &
|
2011-03-29 12:57:19 +05:30
|
|
|
p, &
|
|
|
|
s, &
|
|
|
|
myInstance,&
|
|
|
|
myNgrains
|
|
|
|
integer(pInt), dimension(:,:), pointer :: thisSize
|
|
|
|
character(len=64), dimension(:,:), pointer :: thisOutput
|
2012-03-12 20:13:19 +05:30
|
|
|
logical :: knownPlasticity
|
2009-03-05 20:06:01 +05:30
|
|
|
|
2009-03-06 15:32:36 +05:30
|
|
|
|
2012-03-12 20:13:19 +05:30
|
|
|
! --- PARSE PLASTICITIES FROM CONFIG FILE ---
|
2009-07-22 21:37:19 +05:30
|
|
|
|
2012-02-13 23:11:27 +05:30
|
|
|
if (.not. IO_open_jobFile_stat(fileunit,material_localFileExt)) then ! no local material configuration present...
|
|
|
|
call IO_open_file(fileunit,material_configFile) ! ... open material.config file
|
2011-08-02 15:44:16 +05:30
|
|
|
endif
|
2012-07-03 16:46:38 +05:30
|
|
|
call constitutive_none_init(fileunit)
|
2011-03-29 12:57:19 +05:30
|
|
|
call constitutive_j2_init(fileunit)
|
|
|
|
call constitutive_phenopowerlaw_init(fileunit)
|
|
|
|
call constitutive_titanmod_init(fileunit)
|
|
|
|
call constitutive_dislotwin_init(fileunit)
|
|
|
|
call constitutive_nonlocal_init(fileunit)
|
|
|
|
close(fileunit)
|
2009-07-22 21:37:19 +05:30
|
|
|
|
2012-10-09 18:04:57 +05:30
|
|
|
write(6,*)
|
|
|
|
write(6,*) '<<<+- constitutive init -+>>>'
|
|
|
|
write(6,*) '$Id$'
|
|
|
|
#include "compilation_info.f90"
|
2009-07-22 21:37:19 +05:30
|
|
|
|
2011-03-29 12:57:19 +05:30
|
|
|
! --- WRITE DESCRIPTION FILE FOR CONSTITUTIVE PHASE OUTPUT ---
|
2009-07-22 21:37:19 +05:30
|
|
|
|
2012-02-13 23:11:27 +05:30
|
|
|
call IO_write_jobFile(fileunit,'outputConstitutive')
|
2012-02-21 21:30:00 +05:30
|
|
|
do p = 1_pInt,material_Nphase
|
2012-03-12 20:13:19 +05:30
|
|
|
i = phase_plasticityInstance(p) ! which instance of a plasticity is present phase
|
|
|
|
knownPlasticity = .true. ! assume valid
|
2012-03-12 19:39:37 +05:30
|
|
|
select case(phase_plasticity(p)) ! split per constitiution
|
2012-07-03 16:46:38 +05:30
|
|
|
case (constitutive_none_label)
|
|
|
|
thisOutput => NULL() ! constitutive_none_output
|
|
|
|
thisSize => NULL() ! constitutive_none_sizePostResult
|
2011-03-29 12:57:19 +05:30
|
|
|
case (constitutive_j2_label)
|
|
|
|
thisOutput => constitutive_j2_output
|
|
|
|
thisSize => constitutive_j2_sizePostResult
|
|
|
|
case (constitutive_phenopowerlaw_label)
|
|
|
|
thisOutput => constitutive_phenopowerlaw_output
|
|
|
|
thisSize => constitutive_phenopowerlaw_sizePostResult
|
|
|
|
case (constitutive_titanmod_label)
|
|
|
|
thisOutput => constitutive_titanmod_output
|
|
|
|
thisSize => constitutive_titanmod_sizePostResult
|
|
|
|
case (constitutive_dislotwin_label)
|
|
|
|
thisOutput => constitutive_dislotwin_output
|
|
|
|
thisSize => constitutive_dislotwin_sizePostResult
|
|
|
|
case (constitutive_nonlocal_label)
|
|
|
|
thisOutput => constitutive_nonlocal_output
|
|
|
|
thisSize => constitutive_nonlocal_sizePostResult
|
|
|
|
case default
|
2012-03-12 20:13:19 +05:30
|
|
|
knownPlasticity = .false.
|
2011-03-29 12:57:19 +05:30
|
|
|
end select
|
|
|
|
write(fileunit,*)
|
|
|
|
write(fileunit,'(a)') '['//trim(phase_name(p))//']'
|
|
|
|
write(fileunit,*)
|
2012-03-12 20:13:19 +05:30
|
|
|
if (knownPlasticity) then
|
|
|
|
write(fileunit,'(a)') '(plasticity)'//char(9)//trim(phase_plasticity(p))
|
2012-02-21 21:30:00 +05:30
|
|
|
do e = 1_pInt,phase_Noutput(p)
|
2011-03-29 12:57:19 +05:30
|
|
|
write(fileunit,'(a,i4)') trim(thisOutput(e,i))//char(9),thisSize(e,i)
|
|
|
|
enddo
|
|
|
|
endif
|
|
|
|
enddo
|
|
|
|
close(fileunit)
|
2009-07-22 21:37:19 +05:30
|
|
|
|
2010-09-13 14:59:03 +05:30
|
|
|
|
2011-03-29 12:57:19 +05:30
|
|
|
! --- ALLOCATION OF STATES ---
|
|
|
|
|
|
|
|
gMax = homogenization_maxNgrains
|
|
|
|
iMax = mesh_maxNips
|
|
|
|
eMax = mesh_NcpElems
|
|
|
|
|
|
|
|
allocate(constitutive_state0(gMax,iMax,eMax))
|
|
|
|
allocate(constitutive_partionedState0(gMax,iMax,eMax))
|
|
|
|
allocate(constitutive_subState0(gMax,iMax,eMax))
|
|
|
|
allocate(constitutive_state(gMax,iMax,eMax))
|
|
|
|
allocate(constitutive_state_backup(gMax,iMax,eMax))
|
|
|
|
allocate(constitutive_dotState(gMax,iMax,eMax))
|
2012-05-16 20:13:26 +05:30
|
|
|
allocate(constitutive_deltaState(gMax,iMax,eMax))
|
2011-03-29 12:57:19 +05:30
|
|
|
allocate(constitutive_dotState_backup(gMax,iMax,eMax))
|
|
|
|
allocate(constitutive_aTolState(gMax,iMax,eMax))
|
|
|
|
allocate(constitutive_sizeDotState(gMax,iMax,eMax)) ; constitutive_sizeDotState = 0_pInt
|
|
|
|
allocate(constitutive_sizeState(gMax,iMax,eMax)) ; constitutive_sizeState = 0_pInt
|
|
|
|
allocate(constitutive_sizePostResults(gMax,iMax,eMax)); constitutive_sizePostResults = 0_pInt
|
2012-02-21 21:30:00 +05:30
|
|
|
if (any(numerics_integrator == 1_pInt)) then
|
2011-03-29 12:57:19 +05:30
|
|
|
allocate(constitutive_previousDotState(gMax,iMax,eMax))
|
|
|
|
allocate(constitutive_previousDotState2(gMax,iMax,eMax))
|
|
|
|
endif
|
2012-02-21 21:30:00 +05:30
|
|
|
if (any(numerics_integrator == 4_pInt)) then
|
2011-03-29 12:57:19 +05:30
|
|
|
allocate(constitutive_RK4dotState(gMax,iMax,eMax))
|
|
|
|
endif
|
2012-02-21 21:30:00 +05:30
|
|
|
if (any(numerics_integrator == 5_pInt)) then
|
2011-03-29 12:57:19 +05:30
|
|
|
allocate(constitutive_RKCK45dotState(6,gMax,iMax,eMax))
|
|
|
|
endif
|
|
|
|
|
2012-11-07 21:13:29 +05:30
|
|
|
do e = 1_pInt,mesh_NcpElems ! loop over elements
|
|
|
|
myNgrains = homogenization_Ngrains(mesh_element(3,e))
|
2012-11-16 04:15:20 +05:30
|
|
|
do i = 1_pInt,FE_Nips(FE_geomtype(mesh_element(2,e))) ! loop over IPs
|
2012-11-07 21:13:29 +05:30
|
|
|
do g = 1_pInt,myNgrains ! loop over grains
|
|
|
|
select case(phase_elasticity(material_phase(g,i,e)))
|
|
|
|
|
|
|
|
case (constitutive_hooke_label)
|
|
|
|
! valid elasticity but nothing to do
|
|
|
|
case default
|
|
|
|
call IO_error(200_pInt,ext_msg=trim(phase_elasticity(material_phase(g,i,e)))) ! unknown elasticity
|
|
|
|
|
|
|
|
end select
|
|
|
|
myInstance = phase_plasticityInstance(material_phase(g,i,e))
|
|
|
|
select case(phase_plasticity(material_phase(g,i,e)))
|
|
|
|
|
|
|
|
case (constitutive_none_label)
|
|
|
|
allocate(constitutive_state0(g,i,e)%p(constitutive_none_sizeState(myInstance)))
|
|
|
|
allocate(constitutive_partionedState0(g,i,e)%p(constitutive_none_sizeState(myInstance)))
|
|
|
|
allocate(constitutive_subState0(g,i,e)%p(constitutive_none_sizeState(myInstance)))
|
|
|
|
allocate(constitutive_state(g,i,e)%p(constitutive_none_sizeState(myInstance)))
|
|
|
|
allocate(constitutive_state_backup(g,i,e)%p(constitutive_none_sizeState(myInstance)))
|
|
|
|
allocate(constitutive_aTolState(g,i,e)%p(constitutive_none_sizeState(myInstance)))
|
|
|
|
allocate(constitutive_dotState(g,i,e)%p(constitutive_none_sizeDotState(myInstance)))
|
|
|
|
allocate(constitutive_deltaState(g,i,e)%p(constitutive_none_sizeDotState(myInstance)))
|
|
|
|
allocate(constitutive_dotState_backup(g,i,e)%p(constitutive_none_sizeDotState(myInstance)))
|
|
|
|
if (any(numerics_integrator == 1_pInt)) then
|
|
|
|
allocate(constitutive_previousDotState(g,i,e)%p(constitutive_none_sizeDotState(myInstance)))
|
|
|
|
allocate(constitutive_previousDotState2(g,i,e)%p(constitutive_none_sizeDotState(myInstance)))
|
|
|
|
endif
|
|
|
|
if (any(numerics_integrator == 4_pInt)) then
|
|
|
|
allocate(constitutive_RK4dotState(g,i,e)%p(constitutive_none_sizeDotState(myInstance)))
|
|
|
|
endif
|
|
|
|
if (any(numerics_integrator == 5_pInt)) then
|
|
|
|
do s = 1_pInt,6_pInt
|
|
|
|
allocate(constitutive_RKCK45dotState(s,g,i,e)%p(constitutive_none_sizeDotState(myInstance)))
|
|
|
|
enddo
|
|
|
|
endif
|
|
|
|
constitutive_state0(g,i,e)%p = constitutive_none_stateInit(myInstance)
|
|
|
|
constitutive_aTolState(g,i,e)%p = constitutive_none_aTolState(myInstance)
|
|
|
|
constitutive_sizeState(g,i,e) = constitutive_none_sizeState(myInstance)
|
|
|
|
constitutive_sizeDotState(g,i,e) = constitutive_none_sizeDotState(myInstance)
|
|
|
|
constitutive_sizePostResults(g,i,e) = constitutive_none_sizePostResults(myInstance)
|
|
|
|
|
|
|
|
case (constitutive_j2_label)
|
|
|
|
allocate(constitutive_state0(g,i,e)%p(constitutive_j2_sizeState(myInstance)))
|
|
|
|
allocate(constitutive_partionedState0(g,i,e)%p(constitutive_j2_sizeState(myInstance)))
|
|
|
|
allocate(constitutive_subState0(g,i,e)%p(constitutive_j2_sizeState(myInstance)))
|
|
|
|
allocate(constitutive_state(g,i,e)%p(constitutive_j2_sizeState(myInstance)))
|
|
|
|
allocate(constitutive_state_backup(g,i,e)%p(constitutive_j2_sizeState(myInstance)))
|
|
|
|
allocate(constitutive_aTolState(g,i,e)%p(constitutive_j2_sizeState(myInstance)))
|
|
|
|
allocate(constitutive_dotState(g,i,e)%p(constitutive_j2_sizeDotState(myInstance)))
|
|
|
|
allocate(constitutive_deltaState(g,i,e)%p(constitutive_j2_sizeDotState(myInstance)))
|
|
|
|
allocate(constitutive_dotState_backup(g,i,e)%p(constitutive_j2_sizeDotState(myInstance)))
|
|
|
|
if (any(numerics_integrator == 1_pInt)) then
|
|
|
|
allocate(constitutive_previousDotState(g,i,e)%p(constitutive_j2_sizeDotState(myInstance)))
|
|
|
|
allocate(constitutive_previousDotState2(g,i,e)%p(constitutive_j2_sizeDotState(myInstance)))
|
|
|
|
endif
|
|
|
|
if (any(numerics_integrator == 4_pInt)) then
|
|
|
|
allocate(constitutive_RK4dotState(g,i,e)%p(constitutive_j2_sizeDotState(myInstance)))
|
|
|
|
endif
|
|
|
|
if (any(numerics_integrator == 5_pInt)) then
|
|
|
|
do s = 1_pInt,6_pInt
|
|
|
|
allocate(constitutive_RKCK45dotState(s,g,i,e)%p(constitutive_j2_sizeDotState(myInstance)))
|
|
|
|
enddo
|
|
|
|
endif
|
|
|
|
constitutive_state0(g,i,e)%p = constitutive_j2_stateInit(myInstance)
|
|
|
|
constitutive_aTolState(g,i,e)%p = constitutive_j2_aTolState(myInstance)
|
|
|
|
constitutive_sizeState(g,i,e) = constitutive_j2_sizeState(myInstance)
|
|
|
|
constitutive_sizeDotState(g,i,e) = constitutive_j2_sizeDotState(myInstance)
|
|
|
|
constitutive_sizePostResults(g,i,e) = constitutive_j2_sizePostResults(myInstance)
|
|
|
|
|
|
|
|
case (constitutive_phenopowerlaw_label)
|
|
|
|
allocate(constitutive_state0(g,i,e)%p(constitutive_phenopowerlaw_sizeState(myInstance)))
|
|
|
|
allocate(constitutive_partionedState0(g,i,e)%p(constitutive_phenopowerlaw_sizeState(myInstance)))
|
|
|
|
allocate(constitutive_subState0(g,i,e)%p(constitutive_phenopowerlaw_sizeState(myInstance)))
|
|
|
|
allocate(constitutive_state(g,i,e)%p(constitutive_phenopowerlaw_sizeState(myInstance)))
|
|
|
|
allocate(constitutive_state_backup(g,i,e)%p(constitutive_phenopowerlaw_sizeState(myInstance)))
|
|
|
|
allocate(constitutive_aTolState(g,i,e)%p(constitutive_phenopowerlaw_sizeState(myInstance)))
|
|
|
|
allocate(constitutive_dotState(g,i,e)%p(constitutive_phenopowerlaw_sizeDotState(myInstance)))
|
|
|
|
allocate(constitutive_deltaState(g,i,e)%p(constitutive_phenopowerlaw_sizeDotState(myInstance)))
|
|
|
|
allocate(constitutive_dotState_backup(g,i,e)%p(constitutive_phenopowerlaw_sizeDotState(myInstance)))
|
|
|
|
if (any(numerics_integrator == 1_pInt)) then
|
|
|
|
allocate(constitutive_previousDotState(g,i,e)%p(constitutive_phenopowerlaw_sizeDotState(myInstance)))
|
|
|
|
allocate(constitutive_previousDotState2(g,i,e)%p(constitutive_phenopowerlaw_sizeDotState(myInstance)))
|
|
|
|
endif
|
|
|
|
if (any(numerics_integrator == 4_pInt)) then
|
|
|
|
allocate(constitutive_RK4dotState(g,i,e)%p(constitutive_phenopowerlaw_sizeDotState(myInstance)))
|
|
|
|
endif
|
|
|
|
if (any(numerics_integrator == 5_pInt)) then
|
|
|
|
do s = 1_pInt,6_pInt
|
|
|
|
allocate(constitutive_RKCK45dotState(s,g,i,e)%p(constitutive_phenopowerlaw_sizeDotState(myInstance)))
|
|
|
|
enddo
|
|
|
|
endif
|
|
|
|
constitutive_state0(g,i,e)%p = constitutive_phenopowerlaw_stateInit(myInstance)
|
|
|
|
constitutive_aTolState(g,i,e)%p = constitutive_phenopowerlaw_aTolState(myInstance)
|
|
|
|
constitutive_sizeState(g,i,e) = constitutive_phenopowerlaw_sizeState(myInstance)
|
|
|
|
constitutive_sizeDotState(g,i,e) = constitutive_phenopowerlaw_sizeDotState(myInstance)
|
|
|
|
constitutive_sizePostResults(g,i,e) = constitutive_phenopowerlaw_sizePostResults(myInstance)
|
|
|
|
|
|
|
|
case (constitutive_titanmod_label)
|
|
|
|
allocate(constitutive_state0(g,i,e)%p(constitutive_titanmod_sizeState(myInstance)))
|
|
|
|
allocate(constitutive_partionedState0(g,i,e)%p(constitutive_titanmod_sizeState(myInstance)))
|
|
|
|
allocate(constitutive_subState0(g,i,e)%p(constitutive_titanmod_sizeState(myInstance)))
|
|
|
|
allocate(constitutive_state(g,i,e)%p(constitutive_titanmod_sizeState(myInstance)))
|
|
|
|
allocate(constitutive_state_backup(g,i,e)%p(constitutive_titanmod_sizeState(myInstance)))
|
|
|
|
allocate(constitutive_aTolState(g,i,e)%p(constitutive_titanmod_sizeState(myInstance)))
|
|
|
|
allocate(constitutive_dotState(g,i,e)%p(constitutive_titanmod_sizeDotState(myInstance)))
|
|
|
|
allocate(constitutive_deltaState(g,i,e)%p(constitutive_titanmod_sizeDotState(myInstance)))
|
|
|
|
allocate(constitutive_dotState_backup(g,i,e)%p(constitutive_titanmod_sizeDotState(myInstance)))
|
|
|
|
if (any(numerics_integrator == 1_pInt)) then
|
|
|
|
allocate(constitutive_previousDotState(g,i,e)%p(constitutive_titanmod_sizeDotState(myInstance)))
|
|
|
|
allocate(constitutive_previousDotState2(g,i,e)%p(constitutive_titanmod_sizeDotState(myInstance)))
|
|
|
|
endif
|
|
|
|
if (any(numerics_integrator == 4_pInt)) then
|
|
|
|
allocate(constitutive_RK4dotState(g,i,e)%p(constitutive_titanmod_sizeDotState(myInstance)))
|
|
|
|
endif
|
|
|
|
if (any(numerics_integrator == 5_pInt)) then
|
|
|
|
do s = 1_pInt,6_pInt
|
|
|
|
allocate(constitutive_RKCK45dotState(s,g,i,e)%p(constitutive_titanmod_sizeDotState(myInstance)))
|
|
|
|
enddo
|
|
|
|
endif
|
|
|
|
constitutive_state0(g,i,e)%p = constitutive_titanmod_stateInit(myInstance)
|
|
|
|
constitutive_aTolState(g,i,e)%p = constitutive_titanmod_aTolState(myInstance)
|
|
|
|
constitutive_sizeState(g,i,e) = constitutive_titanmod_sizeState(myInstance)
|
|
|
|
constitutive_sizeDotState(g,i,e) = constitutive_titanmod_sizeDotState(myInstance)
|
|
|
|
constitutive_sizePostResults(g,i,e) = constitutive_titanmod_sizePostResults(myInstance)
|
2011-03-29 12:57:19 +05:30
|
|
|
|
2012-11-07 21:13:29 +05:30
|
|
|
case (constitutive_dislotwin_label)
|
|
|
|
allocate(constitutive_state0(g,i,e)%p(constitutive_dislotwin_sizeState(myInstance)))
|
|
|
|
allocate(constitutive_partionedState0(g,i,e)%p(constitutive_dislotwin_sizeState(myInstance)))
|
|
|
|
allocate(constitutive_subState0(g,i,e)%p(constitutive_dislotwin_sizeState(myInstance)))
|
|
|
|
allocate(constitutive_state(g,i,e)%p(constitutive_dislotwin_sizeState(myInstance)))
|
|
|
|
allocate(constitutive_state_backup(g,i,e)%p(constitutive_dislotwin_sizeState(myInstance)))
|
|
|
|
allocate(constitutive_aTolState(g,i,e)%p(constitutive_dislotwin_sizeState(myInstance)))
|
|
|
|
allocate(constitutive_dotState(g,i,e)%p(constitutive_dislotwin_sizeDotState(myInstance)))
|
|
|
|
allocate(constitutive_deltaState(g,i,e)%p(constitutive_dislotwin_sizeDotState(myInstance)))
|
|
|
|
allocate(constitutive_dotState_backup(g,i,e)%p(constitutive_dislotwin_sizeDotState(myInstance)))
|
|
|
|
if (any(numerics_integrator == 1_pInt)) then
|
|
|
|
allocate(constitutive_previousDotState(g,i,e)%p(constitutive_dislotwin_sizeDotState(myInstance)))
|
|
|
|
allocate(constitutive_previousDotState2(g,i,e)%p(constitutive_dislotwin_sizeDotState(myInstance)))
|
|
|
|
endif
|
|
|
|
if (any(numerics_integrator == 4_pInt)) then
|
|
|
|
allocate(constitutive_RK4dotState(g,i,e)%p(constitutive_dislotwin_sizeDotState(myInstance)))
|
|
|
|
endif
|
|
|
|
if (any(numerics_integrator == 5_pInt)) then
|
|
|
|
do s = 1_pInt,6_pInt
|
|
|
|
allocate(constitutive_RKCK45dotState(s,g,i,e)%p(constitutive_dislotwin_sizeDotState(myInstance)))
|
|
|
|
enddo
|
|
|
|
endif
|
|
|
|
constitutive_state0(g,i,e)%p = constitutive_dislotwin_stateInit(myInstance)
|
|
|
|
constitutive_aTolState(g,i,e)%p = constitutive_dislotwin_aTolState(myInstance)
|
|
|
|
constitutive_sizeState(g,i,e) = constitutive_dislotwin_sizeState(myInstance)
|
|
|
|
constitutive_sizeDotState(g,i,e) = constitutive_dislotwin_sizeDotState(myInstance)
|
|
|
|
constitutive_sizePostResults(g,i,e) = constitutive_dislotwin_sizePostResults(myInstance)
|
|
|
|
|
|
|
|
case (constitutive_nonlocal_label)
|
2012-11-16 04:15:20 +05:30
|
|
|
select case(FE_geomtype(mesh_element(2,e)))
|
|
|
|
case (7_pInt,8_pInt,9_pInt,10_pInt)
|
2012-11-07 21:13:29 +05:30
|
|
|
! all fine
|
|
|
|
case default
|
|
|
|
call IO_error(253_pInt,e,i,g)
|
|
|
|
end select
|
|
|
|
allocate(constitutive_state0(g,i,e)%p(constitutive_nonlocal_sizeState(myInstance)))
|
|
|
|
allocate(constitutive_partionedState0(g,i,e)%p(constitutive_nonlocal_sizeState(myInstance)))
|
|
|
|
allocate(constitutive_subState0(g,i,e)%p(constitutive_nonlocal_sizeState(myInstance)))
|
|
|
|
allocate(constitutive_state(g,i,e)%p(constitutive_nonlocal_sizeState(myInstance)))
|
|
|
|
allocate(constitutive_state_backup(g,i,e)%p(constitutive_nonlocal_sizeState(myInstance)))
|
|
|
|
allocate(constitutive_aTolState(g,i,e)%p(constitutive_nonlocal_sizeState(myInstance)))
|
|
|
|
allocate(constitutive_dotState(g,i,e)%p(constitutive_nonlocal_sizeDotState(myInstance)))
|
|
|
|
allocate(constitutive_deltaState(g,i,e)%p(constitutive_nonlocal_sizeDotState(myInstance)))
|
|
|
|
allocate(constitutive_dotState_backup(g,i,e)%p(constitutive_nonlocal_sizeDotState(myInstance)))
|
|
|
|
if (any(numerics_integrator == 1_pInt)) then
|
|
|
|
allocate(constitutive_previousDotState(g,i,e)%p(constitutive_nonlocal_sizeDotState(myInstance)))
|
|
|
|
allocate(constitutive_previousDotState2(g,i,e)%p(constitutive_nonlocal_sizeDotState(myInstance)))
|
|
|
|
endif
|
|
|
|
if (any(numerics_integrator == 4_pInt)) then
|
|
|
|
allocate(constitutive_RK4dotState(g,i,e)%p(constitutive_nonlocal_sizeDotState(myInstance)))
|
|
|
|
endif
|
|
|
|
if (any(numerics_integrator == 5_pInt)) then
|
|
|
|
do s = 1_pInt,6_pInt
|
|
|
|
allocate(constitutive_RKCK45dotState(s,g,i,e)%p(constitutive_nonlocal_sizeDotState(myInstance)))
|
|
|
|
enddo
|
|
|
|
endif
|
|
|
|
constitutive_aTolState(g,i,e)%p = constitutive_nonlocal_aTolState(myInstance)
|
|
|
|
constitutive_sizeState(g,i,e) = constitutive_nonlocal_sizeState(myInstance)
|
|
|
|
constitutive_sizeDotState(g,i,e) = constitutive_nonlocal_sizeDotState(myInstance)
|
|
|
|
constitutive_sizePostResults(g,i,e) = constitutive_nonlocal_sizePostResults(myInstance)
|
2011-03-29 12:57:19 +05:30
|
|
|
|
2012-11-07 21:13:29 +05:30
|
|
|
case default
|
|
|
|
call IO_error(201_pInt,ext_msg=trim(phase_plasticity(material_phase(g,i,e)))) ! unknown plasticity
|
|
|
|
|
|
|
|
end select
|
2012-10-02 18:27:24 +05:30
|
|
|
enddo
|
|
|
|
enddo
|
2012-11-07 21:13:29 +05:30
|
|
|
enddo
|
2012-10-02 18:27:24 +05:30
|
|
|
call constitutive_nonlocal_stateInit(constitutive_state0(1,1:iMax,1:eMax))
|
2012-11-07 21:13:29 +05:30
|
|
|
do e = 1_pInt,mesh_NcpElems ! loop over elements
|
|
|
|
myNgrains = homogenization_Ngrains(mesh_element(3,e))
|
2012-11-16 04:15:20 +05:30
|
|
|
forall(i = 1_pInt:FE_Nips(FE_geomtype(mesh_element(2,e))), g = 1_pInt:myNgrains)
|
2012-11-07 21:13:29 +05:30
|
|
|
constitutive_partionedState0(g,i,e)%p = constitutive_state0(g,i,e)%p
|
|
|
|
constitutive_state(g,i,e)%p = constitutive_state0(g,i,e)%p ! need to be defined for first call of constitutive_microstructure in crystallite_init
|
|
|
|
endforall
|
|
|
|
enddo
|
2010-10-01 17:48:49 +05:30
|
|
|
|
2012-05-08 20:27:06 +05:30
|
|
|
!----- write out state size file----------------
|
2012-08-16 20:25:23 +05:30
|
|
|
call IO_write_jobBinaryIntFile(777,'sizeStateConst', size(constitutive_sizeState))
|
2012-05-08 20:27:06 +05:30
|
|
|
write (777,rec=1) constitutive_sizeState
|
|
|
|
close(777)
|
|
|
|
!-----------------------------------------------
|
|
|
|
|
2011-03-29 12:57:19 +05:30
|
|
|
constitutive_maxSizeState = maxval(constitutive_sizeState)
|
|
|
|
constitutive_maxSizeDotState = maxval(constitutive_sizeDotState)
|
|
|
|
constitutive_maxSizePostResults = maxval(constitutive_sizePostResults)
|
2009-03-06 15:32:36 +05:30
|
|
|
|
2012-10-09 18:04:57 +05:30
|
|
|
if (iand(debug_level(debug_constitutive),debug_levelBasic) /= 0_pInt) then
|
|
|
|
write(6,'(a32,1x,7(i8,1x))') 'constitutive_state0: ', shape(constitutive_state0)
|
|
|
|
write(6,'(a32,1x,7(i8,1x))') 'constitutive_partionedState0: ', shape(constitutive_partionedState0)
|
|
|
|
write(6,'(a32,1x,7(i8,1x))') 'constitutive_subState0: ', shape(constitutive_subState0)
|
|
|
|
write(6,'(a32,1x,7(i8,1x))') 'constitutive_state: ', shape(constitutive_state)
|
|
|
|
write(6,'(a32,1x,7(i8,1x))') 'constitutive_aTolState: ', shape(constitutive_aTolState)
|
|
|
|
write(6,'(a32,1x,7(i8,1x))') 'constitutive_dotState: ', shape(constitutive_dotState)
|
|
|
|
write(6,'(a32,1x,7(i8,1x))') 'constitutive_deltaState: ', shape(constitutive_deltaState)
|
|
|
|
write(6,'(a32,1x,7(i8,1x))') 'constitutive_sizeState: ', shape(constitutive_sizeState)
|
|
|
|
write(6,'(a32,1x,7(i8,1x))') 'constitutive_sizeDotState: ', shape(constitutive_sizeDotState)
|
|
|
|
write(6,'(a32,1x,7(i8,1x))') 'constitutive_sizePostResults: ', shape(constitutive_sizePostResults)
|
2011-03-29 12:57:19 +05:30
|
|
|
write(6,*)
|
2012-10-09 18:04:57 +05:30
|
|
|
write(6,'(a32,1x,7(i8,1x))') 'maxSizeState: ', constitutive_maxSizeState
|
|
|
|
write(6,'(a32,1x,7(i8,1x))') 'maxSizeDotState: ', constitutive_maxSizeDotState
|
|
|
|
write(6,'(a32,1x,7(i8,1x))') 'maxSizePostResults: ', constitutive_maxSizePostResults
|
|
|
|
endif
|
|
|
|
call flush(6)
|
2009-03-06 15:32:36 +05:30
|
|
|
|
2012-10-02 18:23:25 +05:30
|
|
|
end subroutine constitutive_init
|
2009-03-06 15:32:36 +05:30
|
|
|
|
|
|
|
|
2009-03-04 19:31:36 +05:30
|
|
|
!*********************************************************************
|
|
|
|
!* This function returns the homogenized elacticity matrix *
|
|
|
|
!* INPUT: *
|
|
|
|
!* - ipc : component-ID of current integration point *
|
|
|
|
!* - ip : current integration point *
|
|
|
|
!* - el : current element *
|
|
|
|
!*********************************************************************
|
2012-11-07 21:13:29 +05:30
|
|
|
pure function constitutive_homogenizedC(ipc,ip,el)
|
2012-10-02 18:23:25 +05:30
|
|
|
|
2012-03-09 01:55:28 +05:30
|
|
|
use prec, only: pReal
|
2012-03-12 19:39:37 +05:30
|
|
|
use material, only: phase_plasticity,material_phase
|
2012-07-03 16:46:38 +05:30
|
|
|
use constitutive_none
|
2009-03-06 15:32:36 +05:30
|
|
|
use constitutive_j2
|
2009-07-22 21:37:19 +05:30
|
|
|
use constitutive_phenopowerlaw
|
2010-09-13 14:59:03 +05:30
|
|
|
use constitutive_titanmod
|
2009-10-06 20:46:03 +05:30
|
|
|
use constitutive_dislotwin
|
2009-08-11 22:01:57 +05:30
|
|
|
use constitutive_nonlocal
|
2012-03-09 01:55:28 +05:30
|
|
|
|
2009-03-04 19:31:36 +05:30
|
|
|
implicit none
|
2012-11-07 21:13:29 +05:30
|
|
|
integer(pInt), intent(in) :: ipc,ip,el
|
2009-03-04 19:31:36 +05:30
|
|
|
real(pReal), dimension(6,6) :: constitutive_homogenizedC
|
2009-03-06 15:32:36 +05:30
|
|
|
|
2012-03-12 19:39:37 +05:30
|
|
|
select case (phase_plasticity(material_phase(ipc,ip,el)))
|
2009-08-11 22:01:57 +05:30
|
|
|
|
2012-07-03 16:46:38 +05:30
|
|
|
case (constitutive_none_label)
|
|
|
|
constitutive_homogenizedC = constitutive_none_homogenizedC(constitutive_state,ipc,ip,el)
|
|
|
|
|
2009-03-05 20:06:01 +05:30
|
|
|
case (constitutive_j2_label)
|
2009-05-07 21:57:36 +05:30
|
|
|
constitutive_homogenizedC = constitutive_j2_homogenizedC(constitutive_state,ipc,ip,el)
|
2009-08-11 22:01:57 +05:30
|
|
|
|
2009-07-22 21:37:19 +05:30
|
|
|
case (constitutive_phenopowerlaw_label)
|
|
|
|
constitutive_homogenizedC = constitutive_phenopowerlaw_homogenizedC(constitutive_state,ipc,ip,el)
|
2010-09-13 14:59:03 +05:30
|
|
|
|
|
|
|
case (constitutive_titanmod_label)
|
|
|
|
constitutive_homogenizedC = constitutive_titanmod_homogenizedC(constitutive_state,ipc,ip,el)
|
|
|
|
|
2009-10-06 20:46:03 +05:30
|
|
|
case (constitutive_dislotwin_label)
|
|
|
|
constitutive_homogenizedC = constitutive_dislotwin_homogenizedC(constitutive_state,ipc,ip,el)
|
2009-08-11 22:01:57 +05:30
|
|
|
|
|
|
|
case (constitutive_nonlocal_label)
|
|
|
|
constitutive_homogenizedC = constitutive_nonlocal_homogenizedC(constitutive_state,ipc,ip,el)
|
|
|
|
|
2009-03-04 19:31:36 +05:30
|
|
|
end select
|
2009-03-06 15:32:36 +05:30
|
|
|
|
2012-10-02 18:23:25 +05:30
|
|
|
end function constitutive_homogenizedC
|
|
|
|
|
2009-03-06 15:32:36 +05:30
|
|
|
|
2010-03-24 18:50:12 +05:30
|
|
|
!*********************************************************************
|
|
|
|
!* This function returns the average length of Burgers vector *
|
|
|
|
!* INPUT: *
|
|
|
|
!* - state : state variables *
|
|
|
|
!* - ipc : component-ID of current integration point *
|
|
|
|
!* - ip : current integration point *
|
|
|
|
!* - el : current element *
|
|
|
|
!*********************************************************************
|
2012-10-02 18:23:25 +05:30
|
|
|
function constitutive_averageBurgers(ipc,ip,el)
|
|
|
|
|
2012-03-09 01:55:28 +05:30
|
|
|
use prec, only: pReal
|
2012-03-12 19:39:37 +05:30
|
|
|
use material, only: phase_plasticity,material_phase
|
2012-07-03 16:46:38 +05:30
|
|
|
use constitutive_none
|
2010-03-24 18:50:12 +05:30
|
|
|
use constitutive_j2
|
|
|
|
use constitutive_phenopowerlaw
|
2010-09-13 14:59:03 +05:30
|
|
|
use constitutive_titanmod
|
2010-03-24 18:50:12 +05:30
|
|
|
use constitutive_dislotwin
|
|
|
|
use constitutive_nonlocal
|
2012-03-09 01:55:28 +05:30
|
|
|
|
2010-03-24 18:50:12 +05:30
|
|
|
implicit none
|
2012-03-09 01:55:28 +05:30
|
|
|
integer(pInt) :: ipc,ip,el
|
2010-03-24 18:50:12 +05:30
|
|
|
real(pReal) :: constitutive_averageBurgers
|
|
|
|
|
2012-03-12 19:39:37 +05:30
|
|
|
select case (phase_plasticity(material_phase(ipc,ip,el)))
|
2010-03-24 18:50:12 +05:30
|
|
|
|
2012-07-03 16:46:38 +05:30
|
|
|
case (constitutive_none_label)
|
|
|
|
constitutive_averageBurgers = 2.5e-10_pReal !constitutive_none_averageBurgers(constitutive_state,ipc,ip,el)
|
|
|
|
|
2010-03-24 18:50:12 +05:30
|
|
|
case (constitutive_j2_label)
|
|
|
|
constitutive_averageBurgers = 2.5e-10_pReal !constitutive_j2_averageBurgers(constitutive_state,ipc,ip,el)
|
|
|
|
|
|
|
|
case (constitutive_phenopowerlaw_label)
|
|
|
|
constitutive_averageBurgers = 2.5e-10_pReal !constitutive_phenopowerlaw_averageBurgers(constitutive_state,ipc,ip,el)
|
2010-09-13 14:59:03 +05:30
|
|
|
|
|
|
|
case (constitutive_titanmod_label)
|
|
|
|
constitutive_averageBurgers = 2.5e-10_pReal !constitutive_titanmod_averageBurgers(constitutive_state,ipc,ip,el)
|
2010-03-24 18:50:12 +05:30
|
|
|
|
|
|
|
case (constitutive_dislotwin_label)
|
|
|
|
constitutive_averageBurgers = 2.5e-10_pReal !constitutive_dislotwin_averageBurgers(constitutive_state,ipc,ip,el)
|
|
|
|
|
|
|
|
case (constitutive_nonlocal_label)
|
|
|
|
constitutive_averageBurgers = 2.5e-10_pReal !constitutive_nonlocal_averageBurgers(constitutive_state,ipc,ip,el)
|
|
|
|
|
|
|
|
end select
|
|
|
|
|
2012-10-02 18:23:25 +05:30
|
|
|
end function constitutive_averageBurgers
|
2010-03-24 18:50:12 +05:30
|
|
|
|
2009-03-06 15:32:36 +05:30
|
|
|
|
openmp parallelization working again (at least for j2 and nonlocal constitutive model).
In order to keep it like that, please follow these simple rules:
DON'T use implicit array subscripts:
example: real, dimension(3,3) :: A,B
A(:,2) = B(:,1) <--- DON'T USE
A(1:3,2) = B(1:3,1) <--- BETTER USE
In many cases the use of explicit array subscripts is inevitable for parallelization. Additionally, it is an easy means to prevent memory leaks.
Enclose all write statements with the following:
!$OMP CRITICAL (write2out)
<your write statement>
!$OMP END CRITICAL (write2out)
Whenever you change something in the code and are not sure if it affects parallelization and leads to nonconforming behavior, please ask me and/or Franz to check this.
2011-03-17 16:16:17 +05:30
|
|
|
|
2009-03-04 19:31:36 +05:30
|
|
|
!*********************************************************************
|
|
|
|
!* This function calculates from state needed variables *
|
|
|
|
!*********************************************************************
|
2012-01-17 15:56:57 +05:30
|
|
|
subroutine constitutive_microstructure(Temperature, Fe, Fp, ipc, ip, el)
|
2012-03-09 01:55:28 +05:30
|
|
|
use prec, only: pReal
|
2012-03-12 19:39:37 +05:30
|
|
|
use material, only: phase_plasticity, &
|
2012-02-21 21:30:00 +05:30
|
|
|
material_phase
|
2012-07-03 16:46:38 +05:30
|
|
|
use constitutive_none, only: constitutive_none_label, &
|
|
|
|
constitutive_none_microstructure
|
openmp parallelization working again (at least for j2 and nonlocal constitutive model).
In order to keep it like that, please follow these simple rules:
DON'T use implicit array subscripts:
example: real, dimension(3,3) :: A,B
A(:,2) = B(:,1) <--- DON'T USE
A(1:3,2) = B(1:3,1) <--- BETTER USE
In many cases the use of explicit array subscripts is inevitable for parallelization. Additionally, it is an easy means to prevent memory leaks.
Enclose all write statements with the following:
!$OMP CRITICAL (write2out)
<your write statement>
!$OMP END CRITICAL (write2out)
Whenever you change something in the code and are not sure if it affects parallelization and leads to nonconforming behavior, please ask me and/or Franz to check this.
2011-03-17 16:16:17 +05:30
|
|
|
use constitutive_j2, only: constitutive_j2_label, &
|
|
|
|
constitutive_j2_microstructure
|
|
|
|
use constitutive_phenopowerlaw, only: constitutive_phenopowerlaw_label, &
|
|
|
|
constitutive_phenopowerlaw_microstructure
|
|
|
|
use constitutive_titanmod, only: constitutive_titanmod_label, &
|
|
|
|
constitutive_titanmod_microstructure
|
|
|
|
use constitutive_dislotwin, only: constitutive_dislotwin_label, &
|
|
|
|
constitutive_dislotwin_microstructure
|
|
|
|
use constitutive_nonlocal, only: constitutive_nonlocal_label, &
|
|
|
|
constitutive_nonlocal_microstructure
|
2009-03-06 15:32:36 +05:30
|
|
|
|
2012-03-09 01:55:28 +05:30
|
|
|
implicit none
|
openmp parallelization working again (at least for j2 and nonlocal constitutive model).
In order to keep it like that, please follow these simple rules:
DON'T use implicit array subscripts:
example: real, dimension(3,3) :: A,B
A(:,2) = B(:,1) <--- DON'T USE
A(1:3,2) = B(1:3,1) <--- BETTER USE
In many cases the use of explicit array subscripts is inevitable for parallelization. Additionally, it is an easy means to prevent memory leaks.
Enclose all write statements with the following:
!$OMP CRITICAL (write2out)
<your write statement>
!$OMP END CRITICAL (write2out)
Whenever you change something in the code and are not sure if it affects parallelization and leads to nonconforming behavior, please ask me and/or Franz to check this.
2011-03-17 16:16:17 +05:30
|
|
|
!*** input variables ***!
|
2012-01-17 15:56:57 +05:30
|
|
|
integer(pInt), intent(in):: ipc, & ! component-ID of current integration point
|
|
|
|
ip, & ! current integration point
|
|
|
|
el ! current element
|
|
|
|
real(pReal), intent(in) :: Temperature
|
|
|
|
real(pReal), dimension(3,3), intent(in) :: Fe, & ! elastic deformation gradient
|
|
|
|
Fp ! plastic deformation gradient
|
2009-03-06 15:32:36 +05:30
|
|
|
|
openmp parallelization working again (at least for j2 and nonlocal constitutive model).
In order to keep it like that, please follow these simple rules:
DON'T use implicit array subscripts:
example: real, dimension(3,3) :: A,B
A(:,2) = B(:,1) <--- DON'T USE
A(1:3,2) = B(1:3,1) <--- BETTER USE
In many cases the use of explicit array subscripts is inevitable for parallelization. Additionally, it is an easy means to prevent memory leaks.
Enclose all write statements with the following:
!$OMP CRITICAL (write2out)
<your write statement>
!$OMP END CRITICAL (write2out)
Whenever you change something in the code and are not sure if it affects parallelization and leads to nonconforming behavior, please ask me and/or Franz to check this.
2011-03-17 16:16:17 +05:30
|
|
|
!*** output variables ***!
|
2010-09-13 14:59:03 +05:30
|
|
|
|
openmp parallelization working again (at least for j2 and nonlocal constitutive model).
In order to keep it like that, please follow these simple rules:
DON'T use implicit array subscripts:
example: real, dimension(3,3) :: A,B
A(:,2) = B(:,1) <--- DON'T USE
A(1:3,2) = B(1:3,1) <--- BETTER USE
In many cases the use of explicit array subscripts is inevitable for parallelization. Additionally, it is an easy means to prevent memory leaks.
Enclose all write statements with the following:
!$OMP CRITICAL (write2out)
<your write statement>
!$OMP END CRITICAL (write2out)
Whenever you change something in the code and are not sure if it affects parallelization and leads to nonconforming behavior, please ask me and/or Franz to check this.
2011-03-17 16:16:17 +05:30
|
|
|
!*** local variables ***!
|
|
|
|
|
|
|
|
|
2012-03-12 19:39:37 +05:30
|
|
|
select case (phase_plasticity(material_phase(ipc,ip,el)))
|
openmp parallelization working again (at least for j2 and nonlocal constitutive model).
In order to keep it like that, please follow these simple rules:
DON'T use implicit array subscripts:
example: real, dimension(3,3) :: A,B
A(:,2) = B(:,1) <--- DON'T USE
A(1:3,2) = B(1:3,1) <--- BETTER USE
In many cases the use of explicit array subscripts is inevitable for parallelization. Additionally, it is an easy means to prevent memory leaks.
Enclose all write statements with the following:
!$OMP CRITICAL (write2out)
<your write statement>
!$OMP END CRITICAL (write2out)
Whenever you change something in the code and are not sure if it affects parallelization and leads to nonconforming behavior, please ask me and/or Franz to check this.
2011-03-17 16:16:17 +05:30
|
|
|
|
2012-07-03 16:46:38 +05:30
|
|
|
case (constitutive_none_label)
|
|
|
|
call constitutive_none_microstructure(Temperature,constitutive_state,ipc,ip,el)
|
|
|
|
|
openmp parallelization working again (at least for j2 and nonlocal constitutive model).
In order to keep it like that, please follow these simple rules:
DON'T use implicit array subscripts:
example: real, dimension(3,3) :: A,B
A(:,2) = B(:,1) <--- DON'T USE
A(1:3,2) = B(1:3,1) <--- BETTER USE
In many cases the use of explicit array subscripts is inevitable for parallelization. Additionally, it is an easy means to prevent memory leaks.
Enclose all write statements with the following:
!$OMP CRITICAL (write2out)
<your write statement>
!$OMP END CRITICAL (write2out)
Whenever you change something in the code and are not sure if it affects parallelization and leads to nonconforming behavior, please ask me and/or Franz to check this.
2011-03-17 16:16:17 +05:30
|
|
|
case (constitutive_j2_label)
|
|
|
|
call constitutive_j2_microstructure(Temperature,constitutive_state,ipc,ip,el)
|
2009-08-11 22:01:57 +05:30
|
|
|
|
openmp parallelization working again (at least for j2 and nonlocal constitutive model).
In order to keep it like that, please follow these simple rules:
DON'T use implicit array subscripts:
example: real, dimension(3,3) :: A,B
A(:,2) = B(:,1) <--- DON'T USE
A(1:3,2) = B(1:3,1) <--- BETTER USE
In many cases the use of explicit array subscripts is inevitable for parallelization. Additionally, it is an easy means to prevent memory leaks.
Enclose all write statements with the following:
!$OMP CRITICAL (write2out)
<your write statement>
!$OMP END CRITICAL (write2out)
Whenever you change something in the code and are not sure if it affects parallelization and leads to nonconforming behavior, please ask me and/or Franz to check this.
2011-03-17 16:16:17 +05:30
|
|
|
case (constitutive_phenopowerlaw_label)
|
|
|
|
call constitutive_phenopowerlaw_microstructure(Temperature,constitutive_state,ipc,ip,el)
|
|
|
|
|
|
|
|
case (constitutive_titanmod_label)
|
|
|
|
call constitutive_titanmod_microstructure(Temperature,constitutive_state,ipc,ip,el)
|
|
|
|
|
|
|
|
case (constitutive_dislotwin_label)
|
|
|
|
call constitutive_dislotwin_microstructure(Temperature,constitutive_state,ipc,ip,el)
|
|
|
|
|
|
|
|
case (constitutive_nonlocal_label)
|
2012-01-17 15:56:57 +05:30
|
|
|
call constitutive_nonlocal_microstructure(constitutive_state, Temperature, Fe, Fp, ipc, ip, el)
|
2009-08-11 22:01:57 +05:30
|
|
|
|
openmp parallelization working again (at least for j2 and nonlocal constitutive model).
In order to keep it like that, please follow these simple rules:
DON'T use implicit array subscripts:
example: real, dimension(3,3) :: A,B
A(:,2) = B(:,1) <--- DON'T USE
A(1:3,2) = B(1:3,1) <--- BETTER USE
In many cases the use of explicit array subscripts is inevitable for parallelization. Additionally, it is an easy means to prevent memory leaks.
Enclose all write statements with the following:
!$OMP CRITICAL (write2out)
<your write statement>
!$OMP END CRITICAL (write2out)
Whenever you change something in the code and are not sure if it affects parallelization and leads to nonconforming behavior, please ask me and/or Franz to check this.
2011-03-17 16:16:17 +05:30
|
|
|
end select
|
2009-03-06 15:32:36 +05:30
|
|
|
|
2009-08-11 22:01:57 +05:30
|
|
|
endsubroutine
|
2009-03-06 15:32:36 +05:30
|
|
|
|
|
|
|
|
openmp parallelization working again (at least for j2 and nonlocal constitutive model).
In order to keep it like that, please follow these simple rules:
DON'T use implicit array subscripts:
example: real, dimension(3,3) :: A,B
A(:,2) = B(:,1) <--- DON'T USE
A(1:3,2) = B(1:3,1) <--- BETTER USE
In many cases the use of explicit array subscripts is inevitable for parallelization. Additionally, it is an easy means to prevent memory leaks.
Enclose all write statements with the following:
!$OMP CRITICAL (write2out)
<your write statement>
!$OMP END CRITICAL (write2out)
Whenever you change something in the code and are not sure if it affects parallelization and leads to nonconforming behavior, please ask me and/or Franz to check this.
2011-03-17 16:16:17 +05:30
|
|
|
|
2009-03-04 19:31:36 +05:30
|
|
|
!*********************************************************************
|
|
|
|
!* This subroutine contains the constitutive equation for *
|
|
|
|
!* calculating the velocity gradient *
|
|
|
|
!*********************************************************************
|
openmp parallelization working again (at least for j2 and nonlocal constitutive model).
In order to keep it like that, please follow these simple rules:
DON'T use implicit array subscripts:
example: real, dimension(3,3) :: A,B
A(:,2) = B(:,1) <--- DON'T USE
A(1:3,2) = B(1:3,1) <--- BETTER USE
In many cases the use of explicit array subscripts is inevitable for parallelization. Additionally, it is an easy means to prevent memory leaks.
Enclose all write statements with the following:
!$OMP CRITICAL (write2out)
<your write statement>
!$OMP END CRITICAL (write2out)
Whenever you change something in the code and are not sure if it affects parallelization and leads to nonconforming behavior, please ask me and/or Franz to check this.
2011-03-17 16:16:17 +05:30
|
|
|
subroutine constitutive_LpAndItsTangent(Lp, dLp_dTstar, Tstar_v, Temperature, ipc, ip, el)
|
2009-03-06 15:32:36 +05:30
|
|
|
|
2012-03-09 01:55:28 +05:30
|
|
|
use prec, only: pReal
|
2012-03-12 19:39:37 +05:30
|
|
|
use material, only: phase_plasticity, &
|
openmp parallelization working again (at least for j2 and nonlocal constitutive model).
In order to keep it like that, please follow these simple rules:
DON'T use implicit array subscripts:
example: real, dimension(3,3) :: A,B
A(:,2) = B(:,1) <--- DON'T USE
A(1:3,2) = B(1:3,1) <--- BETTER USE
In many cases the use of explicit array subscripts is inevitable for parallelization. Additionally, it is an easy means to prevent memory leaks.
Enclose all write statements with the following:
!$OMP CRITICAL (write2out)
<your write statement>
!$OMP END CRITICAL (write2out)
Whenever you change something in the code and are not sure if it affects parallelization and leads to nonconforming behavior, please ask me and/or Franz to check this.
2011-03-17 16:16:17 +05:30
|
|
|
material_phase
|
2012-07-03 16:46:38 +05:30
|
|
|
use constitutive_none, only: constitutive_none_label, &
|
|
|
|
constitutive_none_LpAndItsTangent
|
openmp parallelization working again (at least for j2 and nonlocal constitutive model).
In order to keep it like that, please follow these simple rules:
DON'T use implicit array subscripts:
example: real, dimension(3,3) :: A,B
A(:,2) = B(:,1) <--- DON'T USE
A(1:3,2) = B(1:3,1) <--- BETTER USE
In many cases the use of explicit array subscripts is inevitable for parallelization. Additionally, it is an easy means to prevent memory leaks.
Enclose all write statements with the following:
!$OMP CRITICAL (write2out)
<your write statement>
!$OMP END CRITICAL (write2out)
Whenever you change something in the code and are not sure if it affects parallelization and leads to nonconforming behavior, please ask me and/or Franz to check this.
2011-03-17 16:16:17 +05:30
|
|
|
use constitutive_j2, only: constitutive_j2_label, &
|
|
|
|
constitutive_j2_LpAndItsTangent
|
|
|
|
use constitutive_phenopowerlaw, only: constitutive_phenopowerlaw_label, &
|
|
|
|
constitutive_phenopowerlaw_LpAndItsTangent
|
|
|
|
use constitutive_titanmod, only: constitutive_titanmod_label, &
|
|
|
|
constitutive_titanmod_LpAndItsTangent
|
|
|
|
use constitutive_dislotwin, only: constitutive_dislotwin_label, &
|
|
|
|
constitutive_dislotwin_LpAndItsTangent
|
|
|
|
use constitutive_nonlocal, only: constitutive_nonlocal_label, &
|
|
|
|
constitutive_nonlocal_LpAndItsTangent
|
2010-09-13 14:59:03 +05:30
|
|
|
|
2012-03-09 01:55:28 +05:30
|
|
|
implicit none
|
openmp parallelization working again (at least for j2 and nonlocal constitutive model).
In order to keep it like that, please follow these simple rules:
DON'T use implicit array subscripts:
example: real, dimension(3,3) :: A,B
A(:,2) = B(:,1) <--- DON'T USE
A(1:3,2) = B(1:3,1) <--- BETTER USE
In many cases the use of explicit array subscripts is inevitable for parallelization. Additionally, it is an easy means to prevent memory leaks.
Enclose all write statements with the following:
!$OMP CRITICAL (write2out)
<your write statement>
!$OMP END CRITICAL (write2out)
Whenever you change something in the code and are not sure if it affects parallelization and leads to nonconforming behavior, please ask me and/or Franz to check this.
2011-03-17 16:16:17 +05:30
|
|
|
!*** input variables ***!
|
2012-10-02 18:23:25 +05:30
|
|
|
integer(pInt), intent(in):: ipc, & ! component-ID of current integration point
|
|
|
|
ip, & ! current integration point
|
|
|
|
el ! current element
|
openmp parallelization working again (at least for j2 and nonlocal constitutive model).
In order to keep it like that, please follow these simple rules:
DON'T use implicit array subscripts:
example: real, dimension(3,3) :: A,B
A(:,2) = B(:,1) <--- DON'T USE
A(1:3,2) = B(1:3,1) <--- BETTER USE
In many cases the use of explicit array subscripts is inevitable for parallelization. Additionally, it is an easy means to prevent memory leaks.
Enclose all write statements with the following:
!$OMP CRITICAL (write2out)
<your write statement>
!$OMP END CRITICAL (write2out)
Whenever you change something in the code and are not sure if it affects parallelization and leads to nonconforming behavior, please ask me and/or Franz to check this.
2011-03-17 16:16:17 +05:30
|
|
|
real(pReal), intent(in) :: Temperature
|
2012-10-02 18:23:25 +05:30
|
|
|
real(pReal), dimension(6), intent(in) :: Tstar_v ! 2nd Piola-Kirchhoff stress
|
openmp parallelization working again (at least for j2 and nonlocal constitutive model).
In order to keep it like that, please follow these simple rules:
DON'T use implicit array subscripts:
example: real, dimension(3,3) :: A,B
A(:,2) = B(:,1) <--- DON'T USE
A(1:3,2) = B(1:3,1) <--- BETTER USE
In many cases the use of explicit array subscripts is inevitable for parallelization. Additionally, it is an easy means to prevent memory leaks.
Enclose all write statements with the following:
!$OMP CRITICAL (write2out)
<your write statement>
!$OMP END CRITICAL (write2out)
Whenever you change something in the code and are not sure if it affects parallelization and leads to nonconforming behavior, please ask me and/or Franz to check this.
2011-03-17 16:16:17 +05:30
|
|
|
|
|
|
|
!*** output variables ***!
|
2012-10-02 18:23:25 +05:30
|
|
|
real(pReal), dimension(3,3), intent(out) :: Lp ! plastic velocity gradient
|
|
|
|
real(pReal), dimension(9,9), intent(out) :: dLp_dTstar ! derivative of Lp with respect to Tstar (4th-order tensor)
|
openmp parallelization working again (at least for j2 and nonlocal constitutive model).
In order to keep it like that, please follow these simple rules:
DON'T use implicit array subscripts:
example: real, dimension(3,3) :: A,B
A(:,2) = B(:,1) <--- DON'T USE
A(1:3,2) = B(1:3,1) <--- BETTER USE
In many cases the use of explicit array subscripts is inevitable for parallelization. Additionally, it is an easy means to prevent memory leaks.
Enclose all write statements with the following:
!$OMP CRITICAL (write2out)
<your write statement>
!$OMP END CRITICAL (write2out)
Whenever you change something in the code and are not sure if it affects parallelization and leads to nonconforming behavior, please ask me and/or Franz to check this.
2011-03-17 16:16:17 +05:30
|
|
|
|
|
|
|
|
|
|
|
!*** local variables ***!
|
|
|
|
|
|
|
|
|
2012-03-12 19:39:37 +05:30
|
|
|
select case (phase_plasticity(material_phase(ipc,ip,el)))
|
openmp parallelization working again (at least for j2 and nonlocal constitutive model).
In order to keep it like that, please follow these simple rules:
DON'T use implicit array subscripts:
example: real, dimension(3,3) :: A,B
A(:,2) = B(:,1) <--- DON'T USE
A(1:3,2) = B(1:3,1) <--- BETTER USE
In many cases the use of explicit array subscripts is inevitable for parallelization. Additionally, it is an easy means to prevent memory leaks.
Enclose all write statements with the following:
!$OMP CRITICAL (write2out)
<your write statement>
!$OMP END CRITICAL (write2out)
Whenever you change something in the code and are not sure if it affects parallelization and leads to nonconforming behavior, please ask me and/or Franz to check this.
2011-03-17 16:16:17 +05:30
|
|
|
|
2012-07-03 16:46:38 +05:30
|
|
|
case (constitutive_none_label)
|
|
|
|
call constitutive_none_LpAndItsTangent(Lp,dLp_dTstar,Tstar_v,Temperature,constitutive_state,ipc,ip,el)
|
|
|
|
|
openmp parallelization working again (at least for j2 and nonlocal constitutive model).
In order to keep it like that, please follow these simple rules:
DON'T use implicit array subscripts:
example: real, dimension(3,3) :: A,B
A(:,2) = B(:,1) <--- DON'T USE
A(1:3,2) = B(1:3,1) <--- BETTER USE
In many cases the use of explicit array subscripts is inevitable for parallelization. Additionally, it is an easy means to prevent memory leaks.
Enclose all write statements with the following:
!$OMP CRITICAL (write2out)
<your write statement>
!$OMP END CRITICAL (write2out)
Whenever you change something in the code and are not sure if it affects parallelization and leads to nonconforming behavior, please ask me and/or Franz to check this.
2011-03-17 16:16:17 +05:30
|
|
|
case (constitutive_j2_label)
|
|
|
|
call constitutive_j2_LpAndItsTangent(Lp,dLp_dTstar,Tstar_v,Temperature,constitutive_state,ipc,ip,el)
|
|
|
|
|
|
|
|
case (constitutive_phenopowerlaw_label)
|
|
|
|
call constitutive_phenopowerlaw_LpAndItsTangent(Lp,dLp_dTstar,Tstar_v,Temperature,constitutive_state,ipc,ip,el)
|
|
|
|
|
|
|
|
case (constitutive_titanmod_label)
|
|
|
|
call constitutive_titanmod_LpAndItsTangent(Lp,dLp_dTstar,Tstar_v,Temperature,constitutive_state,ipc,ip,el)
|
|
|
|
|
|
|
|
case (constitutive_dislotwin_label)
|
|
|
|
call constitutive_dislotwin_LpAndItsTangent(Lp,dLp_dTstar,Tstar_v,Temperature,constitutive_state,ipc,ip,el)
|
|
|
|
|
|
|
|
case (constitutive_nonlocal_label)
|
2011-11-04 18:42:17 +05:30
|
|
|
call constitutive_nonlocal_LpAndItsTangent(Lp, dLp_dTstar, Tstar_v, Temperature, constitutive_state(ipc,ip,el), ipc, ip, el)
|
openmp parallelization working again (at least for j2 and nonlocal constitutive model).
In order to keep it like that, please follow these simple rules:
DON'T use implicit array subscripts:
example: real, dimension(3,3) :: A,B
A(:,2) = B(:,1) <--- DON'T USE
A(1:3,2) = B(1:3,1) <--- BETTER USE
In many cases the use of explicit array subscripts is inevitable for parallelization. Additionally, it is an easy means to prevent memory leaks.
Enclose all write statements with the following:
!$OMP CRITICAL (write2out)
<your write statement>
!$OMP END CRITICAL (write2out)
Whenever you change something in the code and are not sure if it affects parallelization and leads to nonconforming behavior, please ask me and/or Franz to check this.
2011-03-17 16:16:17 +05:30
|
|
|
|
|
|
|
end select
|
2009-03-06 15:32:36 +05:30
|
|
|
|
2012-10-02 18:23:25 +05:30
|
|
|
end subroutine constitutive_LpAndItsTangent
|
2009-03-06 15:32:36 +05:30
|
|
|
|
|
|
|
|
openmp parallelization working again (at least for j2 and nonlocal constitutive model).
In order to keep it like that, please follow these simple rules:
DON'T use implicit array subscripts:
example: real, dimension(3,3) :: A,B
A(:,2) = B(:,1) <--- DON'T USE
A(1:3,2) = B(1:3,1) <--- BETTER USE
In many cases the use of explicit array subscripts is inevitable for parallelization. Additionally, it is an easy means to prevent memory leaks.
Enclose all write statements with the following:
!$OMP CRITICAL (write2out)
<your write statement>
!$OMP END CRITICAL (write2out)
Whenever you change something in the code and are not sure if it affects parallelization and leads to nonconforming behavior, please ask me and/or Franz to check this.
2011-03-17 16:16:17 +05:30
|
|
|
|
2012-03-15 15:21:33 +05:30
|
|
|
!************************************************************************
|
|
|
|
!* This subroutine returns the 2nd Piola-Kirchhoff stress tensor and *
|
|
|
|
!* its tangent with respect to the elastic deformation gradient *
|
|
|
|
!* OUTPUT: *
|
|
|
|
!* - T : 2nd Piola-Kirchhoff stress tensor *
|
|
|
|
!* - dT_dFe : derivative of 2nd Piola-Kirchhoff stress tensor *
|
|
|
|
!* with respect to the elastic deformation gradient *
|
|
|
|
!* INPUT: *
|
|
|
|
!* - Fe : elastic deformation gradient *
|
|
|
|
!* - ipc : component-ID of current integration point *
|
|
|
|
!* - ip : current integration point *
|
|
|
|
!* - el : current element *
|
|
|
|
!************************************************************************
|
2012-11-07 21:13:29 +05:30
|
|
|
pure subroutine constitutive_TandItsTangent(T, dT_dFe, Fe, ipc, ip, el)
|
2012-03-15 15:21:33 +05:30
|
|
|
|
2012-11-07 21:13:29 +05:30
|
|
|
use prec, only: pReal
|
|
|
|
use material, only: phase_elasticity,material_phase
|
|
|
|
|
|
|
|
implicit none
|
|
|
|
|
|
|
|
integer(pInt), intent(in) :: ipc,ip,el
|
|
|
|
real(pReal), dimension(3,3), intent(in) :: Fe
|
|
|
|
|
|
|
|
real(pReal), dimension(3,3), intent(out) :: T
|
|
|
|
real(pReal), dimension(3,3,3,3), intent(out) :: dT_dFe
|
2012-03-15 15:21:33 +05:30
|
|
|
|
2012-11-07 21:13:29 +05:30
|
|
|
|
|
|
|
select case (phase_elasticity(material_phase(ipc,ip,el)))
|
|
|
|
|
|
|
|
case (constitutive_hooke_label)
|
|
|
|
call constitutive_hooke_TandItsTangent(T, dT_dFe, Fe, ipc, ip, el)
|
|
|
|
|
|
|
|
end select
|
2012-03-15 15:21:33 +05:30
|
|
|
|
2012-10-02 18:23:25 +05:30
|
|
|
end subroutine constitutive_TandItsTangent
|
2012-03-15 15:21:33 +05:30
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
!************************************************************************
|
|
|
|
!* This subroutine returns the 2nd Piola-Kirchhoff stress tensor and *
|
|
|
|
!* its tangent with respect to the elastic deformation gradient *
|
|
|
|
!* OUTPUT: *
|
|
|
|
!* - T : 2nd Piola-Kirchhoff stress tensor *
|
|
|
|
!* - dT_dFe : derivative of 2nd Piola-Kirchhoff stress tensor *
|
|
|
|
!* with respect to the elastic deformation gradient *
|
|
|
|
!* INPUT: *
|
|
|
|
!* - Fe : elastic deformation gradient *
|
|
|
|
!* - ipc : component-ID of current integration point *
|
|
|
|
!* - ip : current integration point *
|
|
|
|
!* - el : current element *
|
|
|
|
!************************************************************************
|
2012-11-07 21:13:29 +05:30
|
|
|
pure subroutine constitutive_hooke_TandItsTangent(T, dT_dFe, Fe, g, i, e)
|
2013-01-09 03:24:25 +05:30
|
|
|
use prec, only: &
|
|
|
|
pReal
|
2013-01-08 16:39:20 +05:30
|
|
|
use math, only : &
|
|
|
|
math_mul33x33, &
|
2013-01-09 03:24:25 +05:30
|
|
|
math_mul3333xx33, &
|
2013-01-08 16:39:20 +05:30
|
|
|
math_Mandel66to3333, &
|
2013-01-09 03:24:25 +05:30
|
|
|
math_transpose33, &
|
|
|
|
math_I3
|
2012-11-07 21:13:29 +05:30
|
|
|
implicit none
|
2012-03-15 15:21:33 +05:30
|
|
|
|
|
|
|
!* Definition of variables
|
2012-11-07 21:13:29 +05:30
|
|
|
|
|
|
|
integer(pInt), intent(in) :: g, i, e
|
|
|
|
real(pReal), dimension(3,3), intent(in) :: Fe
|
|
|
|
|
2013-01-09 03:24:25 +05:30
|
|
|
integer(pInt) :: p, o
|
2012-11-07 21:13:29 +05:30
|
|
|
real(pReal), dimension(3,3), intent(out) :: T
|
|
|
|
real(pReal), dimension(3,3,3,3), intent(out) :: dT_dFe
|
|
|
|
|
2013-01-08 16:39:20 +05:30
|
|
|
real(pReal), dimension(3,3) :: FeT
|
2012-11-07 21:13:29 +05:30
|
|
|
real(pReal), dimension(3,3,3,3) :: C
|
2012-03-15 15:21:33 +05:30
|
|
|
|
|
|
|
!* get elasticity tensor
|
|
|
|
|
2013-01-08 16:39:20 +05:30
|
|
|
C = math_Mandel66to3333(constitutive_homogenizedC(g,i,e))
|
2012-03-15 15:21:33 +05:30
|
|
|
|
2013-01-08 16:39:20 +05:30
|
|
|
FeT = math_transpose33(Fe)
|
|
|
|
T = 0.5_pReal*math_mul3333xx33(C,math_mul33x33(FeT,Fe)-math_I3)
|
2012-03-15 15:21:33 +05:30
|
|
|
|
2013-01-08 16:39:20 +05:30
|
|
|
forall (o=1_pInt:3_pInt, p=1_pInt:3_pInt) dT_dFe(o,p,1:3,1:3) = math_mul33x33(C(o,p,1:3,1:3), FeT) ! dT*_ij/dFe_kl
|
2012-03-15 15:21:33 +05:30
|
|
|
|
|
|
|
end subroutine constitutive_hooke_TandItsTangent
|
|
|
|
|
|
|
|
|
2009-03-04 19:31:36 +05:30
|
|
|
!*********************************************************************
|
|
|
|
!* This subroutine contains the constitutive equation for *
|
|
|
|
!* calculating the rate of change of microstructure *
|
|
|
|
!*********************************************************************
|
2012-11-30 00:14:00 +05:30
|
|
|
subroutine constitutive_collectDotState(Tstar_v, Fe, Fp, Temperature, subdt, subfrac, ipc, ip, el)
|
openmp parallelization working again (at least for j2 and nonlocal constitutive model).
In order to keep it like that, please follow these simple rules:
DON'T use implicit array subscripts:
example: real, dimension(3,3) :: A,B
A(:,2) = B(:,1) <--- DON'T USE
A(1:3,2) = B(1:3,1) <--- BETTER USE
In many cases the use of explicit array subscripts is inevitable for parallelization. Additionally, it is an easy means to prevent memory leaks.
Enclose all write statements with the following:
!$OMP CRITICAL (write2out)
<your write statement>
!$OMP END CRITICAL (write2out)
Whenever you change something in the code and are not sure if it affects parallelization and leads to nonconforming behavior, please ask me and/or Franz to check this.
2011-03-17 16:16:17 +05:30
|
|
|
|
2012-03-09 01:55:28 +05:30
|
|
|
use prec, only: pReal, pLongInt
|
2009-12-15 13:50:31 +05:30
|
|
|
use debug, only: debug_cumDotStateCalls, &
|
2011-03-21 16:01:17 +05:30
|
|
|
debug_cumDotStateTicks, &
|
2012-07-05 15:24:50 +05:30
|
|
|
debug_level, &
|
2012-03-09 01:55:28 +05:30
|
|
|
debug_constitutive, &
|
|
|
|
debug_levelBasic
|
2009-12-15 13:50:31 +05:30
|
|
|
use mesh, only: mesh_NcpElems, &
|
2012-11-28 00:06:55 +05:30
|
|
|
mesh_maxNips, &
|
|
|
|
mesh_maxNipNeighbors
|
2012-03-12 19:39:37 +05:30
|
|
|
use material, only: phase_plasticity, &
|
2009-12-15 13:50:31 +05:30
|
|
|
material_phase, &
|
|
|
|
homogenization_maxNgrains
|
2012-07-03 16:46:38 +05:30
|
|
|
use constitutive_none, only: constitutive_none_dotState, &
|
|
|
|
constitutive_none_label
|
2010-10-01 17:48:49 +05:30
|
|
|
use constitutive_j2, only: constitutive_j2_dotState, &
|
|
|
|
constitutive_j2_label
|
|
|
|
use constitutive_phenopowerlaw, only: constitutive_phenopowerlaw_dotState, &
|
|
|
|
constitutive_phenopowerlaw_label
|
|
|
|
use constitutive_titanmod, only: constitutive_titanmod_dotState, &
|
|
|
|
constitutive_titanmod_label
|
|
|
|
use constitutive_dislotwin, only: constitutive_dislotwin_dotState, &
|
|
|
|
constitutive_dislotwin_label
|
|
|
|
use constitutive_nonlocal, only: constitutive_nonlocal_dotState, &
|
|
|
|
constitutive_nonlocal_label
|
2009-12-15 13:50:31 +05:30
|
|
|
|
|
|
|
implicit none
|
|
|
|
!*** input variables
|
openmp parallelization working again (at least for j2 and nonlocal constitutive model).
In order to keep it like that, please follow these simple rules:
DON'T use implicit array subscripts:
example: real, dimension(3,3) :: A,B
A(:,2) = B(:,1) <--- DON'T USE
A(1:3,2) = B(1:3,1) <--- BETTER USE
In many cases the use of explicit array subscripts is inevitable for parallelization. Additionally, it is an easy means to prevent memory leaks.
Enclose all write statements with the following:
!$OMP CRITICAL (write2out)
<your write statement>
!$OMP END CRITICAL (write2out)
Whenever you change something in the code and are not sure if it affects parallelization and leads to nonconforming behavior, please ask me and/or Franz to check this.
2011-03-17 16:16:17 +05:30
|
|
|
integer(pInt), intent(in) :: ipc, & ! component-ID of current integration point
|
|
|
|
ip, & ! current integration point
|
|
|
|
el ! current element
|
2009-12-15 13:50:31 +05:30
|
|
|
real(pReal), intent(in) :: Temperature, &
|
openmp parallelization working again (at least for j2 and nonlocal constitutive model).
In order to keep it like that, please follow these simple rules:
DON'T use implicit array subscripts:
example: real, dimension(3,3) :: A,B
A(:,2) = B(:,1) <--- DON'T USE
A(1:3,2) = B(1:3,1) <--- BETTER USE
In many cases the use of explicit array subscripts is inevitable for parallelization. Additionally, it is an easy means to prevent memory leaks.
Enclose all write statements with the following:
!$OMP CRITICAL (write2out)
<your write statement>
!$OMP END CRITICAL (write2out)
Whenever you change something in the code and are not sure if it affects parallelization and leads to nonconforming behavior, please ask me and/or Franz to check this.
2011-03-17 16:16:17 +05:30
|
|
|
subdt ! timestep
|
2012-11-28 00:06:55 +05:30
|
|
|
real(pReal), dimension(homogenization_maxNgrains,mesh_maxNips,mesh_NcpElems), intent(in) :: &
|
|
|
|
subfrac ! subfraction of timestep
|
2009-12-15 13:50:31 +05:30
|
|
|
real(pReal), dimension(3,3,homogenization_maxNgrains,mesh_maxNips,mesh_NcpElems), intent(in) :: &
|
openmp parallelization working again (at least for j2 and nonlocal constitutive model).
In order to keep it like that, please follow these simple rules:
DON'T use implicit array subscripts:
example: real, dimension(3,3) :: A,B
A(:,2) = B(:,1) <--- DON'T USE
A(1:3,2) = B(1:3,1) <--- BETTER USE
In many cases the use of explicit array subscripts is inevitable for parallelization. Additionally, it is an easy means to prevent memory leaks.
Enclose all write statements with the following:
!$OMP CRITICAL (write2out)
<your write statement>
!$OMP END CRITICAL (write2out)
Whenever you change something in the code and are not sure if it affects parallelization and leads to nonconforming behavior, please ask me and/or Franz to check this.
2011-03-17 16:16:17 +05:30
|
|
|
Fe, & ! elastic deformation gradient
|
|
|
|
Fp ! plastic deformation gradient
|
2009-12-15 13:50:31 +05:30
|
|
|
real(pReal), dimension(6), intent(in) :: &
|
openmp parallelization working again (at least for j2 and nonlocal constitutive model).
In order to keep it like that, please follow these simple rules:
DON'T use implicit array subscripts:
example: real, dimension(3,3) :: A,B
A(:,2) = B(:,1) <--- DON'T USE
A(1:3,2) = B(1:3,1) <--- BETTER USE
In many cases the use of explicit array subscripts is inevitable for parallelization. Additionally, it is an easy means to prevent memory leaks.
Enclose all write statements with the following:
!$OMP CRITICAL (write2out)
<your write statement>
!$OMP END CRITICAL (write2out)
Whenever you change something in the code and are not sure if it affects parallelization and leads to nonconforming behavior, please ask me and/or Franz to check this.
2011-03-17 16:16:17 +05:30
|
|
|
Tstar_v ! 2nd Piola Kirchhoff stress tensor (Mandel)
|
2009-12-15 13:50:31 +05:30
|
|
|
!*** local variables
|
|
|
|
integer(pLongInt) tick, tock, &
|
|
|
|
tickrate, &
|
|
|
|
maxticks
|
|
|
|
|
2012-07-05 15:24:50 +05:30
|
|
|
if (iand(debug_level(debug_constitutive), debug_levelBasic) /= 0_pInt) then
|
2011-03-21 16:01:17 +05:30
|
|
|
call system_clock(count=tick,count_rate=tickrate,count_max=maxticks)
|
|
|
|
endif
|
2009-12-15 13:50:31 +05:30
|
|
|
|
2012-03-12 19:39:37 +05:30
|
|
|
select case (phase_plasticity(material_phase(ipc,ip,el)))
|
2009-12-15 13:50:31 +05:30
|
|
|
|
2012-07-03 16:46:38 +05:30
|
|
|
case (constitutive_none_label)
|
|
|
|
constitutive_dotState(ipc,ip,el)%p = constitutive_none_dotState(Tstar_v,Temperature,constitutive_state,ipc,ip,el)
|
|
|
|
|
2009-12-15 13:50:31 +05:30
|
|
|
case (constitutive_j2_label)
|
|
|
|
constitutive_dotState(ipc,ip,el)%p = constitutive_j2_dotState(Tstar_v,Temperature,constitutive_state,ipc,ip,el)
|
|
|
|
|
|
|
|
case (constitutive_phenopowerlaw_label)
|
|
|
|
constitutive_dotState(ipc,ip,el)%p = constitutive_phenopowerlaw_dotState(Tstar_v,Temperature,constitutive_state,ipc,ip,el)
|
2010-09-13 14:59:03 +05:30
|
|
|
|
|
|
|
case (constitutive_titanmod_label)
|
|
|
|
constitutive_dotState(ipc,ip,el)%p = constitutive_titanmod_dotState(Tstar_v,Temperature,constitutive_state,ipc,ip,el)
|
|
|
|
|
2009-12-15 13:50:31 +05:30
|
|
|
case (constitutive_dislotwin_label)
|
|
|
|
constitutive_dotState(ipc,ip,el)%p = constitutive_dislotwin_dotState(Tstar_v,Temperature,constitutive_state,ipc,ip,el)
|
|
|
|
|
|
|
|
case (constitutive_nonlocal_label)
|
2012-05-16 21:05:14 +05:30
|
|
|
constitutive_dotState(ipc,ip,el)%p = constitutive_nonlocal_dotState(Tstar_v, Fe, Fp, Temperature, constitutive_state, &
|
2012-11-30 00:14:00 +05:30
|
|
|
constitutive_state0, subdt, subfrac, ipc, ip, el)
|
2012-11-28 00:06:55 +05:30
|
|
|
|
2009-12-15 13:50:31 +05:30
|
|
|
end select
|
2009-03-06 15:32:36 +05:30
|
|
|
|
2012-07-05 15:24:50 +05:30
|
|
|
if (iand(debug_level(debug_constitutive), debug_levelBasic) /= 0_pInt) then
|
2011-03-21 16:01:17 +05:30
|
|
|
call system_clock(count=tock,count_rate=tickrate,count_max=maxticks)
|
|
|
|
!$OMP CRITICAL (debugTimingDotState)
|
|
|
|
debug_cumDotStateCalls = debug_cumDotStateCalls + 1_pInt
|
|
|
|
debug_cumDotStateTicks = debug_cumDotStateTicks + tock-tick
|
|
|
|
!$OMP FLUSH (debug_cumDotStateTicks)
|
|
|
|
if (tock < tick) debug_cumDotStateTicks = debug_cumDotStateTicks + maxticks
|
|
|
|
!$OMP END CRITICAL (debugTimingDotState)
|
|
|
|
endif
|
2009-03-06 15:32:36 +05:30
|
|
|
|
2012-10-02 18:23:25 +05:30
|
|
|
end subroutine constitutive_collectDotState
|
2009-03-06 15:32:36 +05:30
|
|
|
|
|
|
|
|
2012-05-16 20:13:26 +05:30
|
|
|
!*********************************************************************
|
|
|
|
!* This subroutine contains the constitutive equation for *
|
|
|
|
!* calculating the incremental change of microstructure based on the *
|
2012-05-17 17:48:30 +05:30
|
|
|
!* current stress and state *
|
2012-05-16 20:13:26 +05:30
|
|
|
!*********************************************************************
|
2012-05-17 16:34:22 +05:30
|
|
|
subroutine constitutive_collectDeltaState(Tstar_v, Temperature, ipc, ip, el)
|
2012-05-16 20:13:26 +05:30
|
|
|
|
|
|
|
use prec, only: pReal, pLongInt
|
|
|
|
use debug, only: debug_cumDeltaStateCalls, &
|
|
|
|
debug_cumDeltaStateTicks, &
|
2012-07-05 15:24:50 +05:30
|
|
|
debug_level, &
|
2012-05-16 20:13:26 +05:30
|
|
|
debug_constitutive, &
|
|
|
|
debug_levelBasic
|
|
|
|
use mesh, only: mesh_NcpElems, &
|
|
|
|
mesh_maxNips
|
|
|
|
use material, only: phase_plasticity, &
|
|
|
|
material_phase, &
|
|
|
|
homogenization_maxNgrains
|
2012-07-03 16:46:38 +05:30
|
|
|
use constitutive_none, only: constitutive_none_deltaState, &
|
|
|
|
constitutive_none_label
|
2012-05-16 20:13:26 +05:30
|
|
|
use constitutive_j2, only: constitutive_j2_deltaState, &
|
|
|
|
constitutive_j2_label
|
|
|
|
use constitutive_phenopowerlaw, only: constitutive_phenopowerlaw_deltaState, &
|
|
|
|
constitutive_phenopowerlaw_label
|
|
|
|
use constitutive_titanmod, only: constitutive_titanmod_deltaState, &
|
|
|
|
constitutive_titanmod_label
|
|
|
|
use constitutive_dislotwin, only: constitutive_dislotwin_deltaState, &
|
|
|
|
constitutive_dislotwin_label
|
|
|
|
use constitutive_nonlocal, only: constitutive_nonlocal_deltaState, &
|
|
|
|
constitutive_nonlocal_label
|
|
|
|
|
|
|
|
implicit none
|
|
|
|
!*** input variables
|
|
|
|
integer(pInt), intent(in) :: ipc, & ! component-ID of current integration point
|
|
|
|
ip, & ! current integration point
|
|
|
|
el ! current element
|
|
|
|
real(pReal), intent(in) :: Temperature
|
|
|
|
real(pReal), dimension(6), intent(in) :: &
|
|
|
|
Tstar_v ! 2nd Piola Kirchhoff stress tensor (Mandel)
|
|
|
|
!*** local variables
|
|
|
|
integer(pLongInt) tick, tock, &
|
|
|
|
tickrate, &
|
|
|
|
maxticks
|
|
|
|
|
2012-07-05 15:24:50 +05:30
|
|
|
if (iand(debug_level(debug_constitutive), debug_levelBasic) /= 0_pInt) then
|
2012-05-16 20:13:26 +05:30
|
|
|
call system_clock(count=tick,count_rate=tickrate,count_max=maxticks)
|
|
|
|
endif
|
|
|
|
|
|
|
|
select case (phase_plasticity(material_phase(ipc,ip,el)))
|
|
|
|
|
2012-07-03 16:46:38 +05:30
|
|
|
case (constitutive_none_label)
|
|
|
|
constitutive_deltaState(ipc,ip,el)%p = constitutive_none_deltaState(Tstar_v,Temperature,constitutive_state,ipc,ip,el)
|
|
|
|
|
2012-05-16 20:13:26 +05:30
|
|
|
case (constitutive_j2_label)
|
2012-05-17 17:48:30 +05:30
|
|
|
constitutive_deltaState(ipc,ip,el)%p = constitutive_j2_deltaState(Tstar_v,Temperature,constitutive_state,ipc,ip,el)
|
2012-05-16 20:13:26 +05:30
|
|
|
|
|
|
|
case (constitutive_phenopowerlaw_label)
|
2012-05-17 17:48:30 +05:30
|
|
|
constitutive_deltaState(ipc,ip,el)%p = constitutive_phenopowerlaw_deltaState(Tstar_v,Temperature,constitutive_state,ipc,ip,el)
|
2012-05-16 20:13:26 +05:30
|
|
|
|
|
|
|
case (constitutive_titanmod_label)
|
2012-05-17 17:48:30 +05:30
|
|
|
constitutive_deltaState(ipc,ip,el)%p = constitutive_titanmod_deltaState(Tstar_v,Temperature,constitutive_state,ipc,ip,el)
|
2012-05-16 20:13:26 +05:30
|
|
|
|
|
|
|
case (constitutive_dislotwin_label)
|
2012-05-17 17:48:30 +05:30
|
|
|
constitutive_deltaState(ipc,ip,el)%p = constitutive_dislotwin_deltaState(Tstar_v,Temperature,constitutive_state,ipc,ip,el)
|
2012-05-16 20:13:26 +05:30
|
|
|
|
|
|
|
case (constitutive_nonlocal_label)
|
2012-05-18 20:05:52 +05:30
|
|
|
call constitutive_nonlocal_deltaState(constitutive_deltaState(ipc,ip,el),constitutive_state, Tstar_v,Temperature,ipc,ip,el)
|
2012-05-16 20:13:26 +05:30
|
|
|
|
|
|
|
end select
|
|
|
|
|
2012-07-05 15:24:50 +05:30
|
|
|
if (iand(debug_level(debug_constitutive), debug_levelBasic) /= 0_pInt) then
|
2012-05-16 20:13:26 +05:30
|
|
|
call system_clock(count=tock,count_rate=tickrate,count_max=maxticks)
|
|
|
|
!$OMP CRITICAL (debugTimingDeltaState)
|
|
|
|
debug_cumDeltaStateCalls = debug_cumDeltaStateCalls + 1_pInt
|
|
|
|
debug_cumDeltaStateTicks = debug_cumDeltaStateTicks + tock-tick
|
|
|
|
!$OMP FLUSH (debug_cumDeltaStateTicks)
|
|
|
|
if (tock < tick) debug_cumDeltaStateTicks = debug_cumDeltaStateTicks + maxticks
|
|
|
|
!$OMP END CRITICAL (debugTimingDeltaState)
|
|
|
|
endif
|
|
|
|
|
2012-10-02 18:23:25 +05:30
|
|
|
end subroutine constitutive_collectDeltaState
|
2012-05-16 20:13:26 +05:30
|
|
|
|
|
|
|
|
openmp parallelization working again (at least for j2 and nonlocal constitutive model).
In order to keep it like that, please follow these simple rules:
DON'T use implicit array subscripts:
example: real, dimension(3,3) :: A,B
A(:,2) = B(:,1) <--- DON'T USE
A(1:3,2) = B(1:3,1) <--- BETTER USE
In many cases the use of explicit array subscripts is inevitable for parallelization. Additionally, it is an easy means to prevent memory leaks.
Enclose all write statements with the following:
!$OMP CRITICAL (write2out)
<your write statement>
!$OMP END CRITICAL (write2out)
Whenever you change something in the code and are not sure if it affects parallelization and leads to nonconforming behavior, please ask me and/or Franz to check this.
2011-03-17 16:16:17 +05:30
|
|
|
|
2009-07-01 15:59:35 +05:30
|
|
|
!*********************************************************************
|
|
|
|
!* This subroutine contains the constitutive equation for *
|
|
|
|
!* calculating the rate of change of microstructure *
|
|
|
|
!*********************************************************************
|
openmp parallelization working again (at least for j2 and nonlocal constitutive model).
In order to keep it like that, please follow these simple rules:
DON'T use implicit array subscripts:
example: real, dimension(3,3) :: A,B
A(:,2) = B(:,1) <--- DON'T USE
A(1:3,2) = B(1:3,1) <--- BETTER USE
In many cases the use of explicit array subscripts is inevitable for parallelization. Additionally, it is an easy means to prevent memory leaks.
Enclose all write statements with the following:
!$OMP CRITICAL (write2out)
<your write statement>
!$OMP END CRITICAL (write2out)
Whenever you change something in the code and are not sure if it affects parallelization and leads to nonconforming behavior, please ask me and/or Franz to check this.
2011-03-17 16:16:17 +05:30
|
|
|
function constitutive_dotTemperature(Tstar_v,Temperature,ipc,ip,el)
|
|
|
|
|
2012-03-09 01:55:28 +05:30
|
|
|
use prec, only: pReal, pLongInt
|
2010-10-01 17:48:49 +05:30
|
|
|
use debug, only: debug_cumDotTemperatureCalls, &
|
2011-03-21 16:01:17 +05:30
|
|
|
debug_cumDotTemperatureTicks, &
|
2012-07-05 15:24:50 +05:30
|
|
|
debug_level, &
|
2012-03-09 01:55:28 +05:30
|
|
|
debug_constitutive, &
|
|
|
|
debug_levelBasic
|
2012-03-12 19:39:37 +05:30
|
|
|
use material, only: phase_plasticity, &
|
openmp parallelization working again (at least for j2 and nonlocal constitutive model).
In order to keep it like that, please follow these simple rules:
DON'T use implicit array subscripts:
example: real, dimension(3,3) :: A,B
A(:,2) = B(:,1) <--- DON'T USE
A(1:3,2) = B(1:3,1) <--- BETTER USE
In many cases the use of explicit array subscripts is inevitable for parallelization. Additionally, it is an easy means to prevent memory leaks.
Enclose all write statements with the following:
!$OMP CRITICAL (write2out)
<your write statement>
!$OMP END CRITICAL (write2out)
Whenever you change something in the code and are not sure if it affects parallelization and leads to nonconforming behavior, please ask me and/or Franz to check this.
2011-03-17 16:16:17 +05:30
|
|
|
material_phase
|
2012-07-03 16:46:38 +05:30
|
|
|
use constitutive_none, only: constitutive_none_dotTemperature, &
|
|
|
|
constitutive_none_label
|
2010-10-01 17:48:49 +05:30
|
|
|
use constitutive_j2, only: constitutive_j2_dotTemperature, &
|
|
|
|
constitutive_j2_label
|
|
|
|
use constitutive_phenopowerlaw, only: constitutive_phenopowerlaw_dotTemperature, &
|
|
|
|
constitutive_phenopowerlaw_label
|
|
|
|
use constitutive_titanmod, only: constitutive_titanmod_dotTemperature, &
|
|
|
|
constitutive_titanmod_label
|
|
|
|
use constitutive_dislotwin, only: constitutive_dislotwin_dotTemperature, &
|
|
|
|
constitutive_dislotwin_label
|
|
|
|
use constitutive_nonlocal, only: constitutive_nonlocal_dotTemperature, &
|
|
|
|
constitutive_nonlocal_label
|
2009-07-01 15:59:35 +05:30
|
|
|
|
2012-03-09 01:55:28 +05:30
|
|
|
implicit none
|
openmp parallelization working again (at least for j2 and nonlocal constitutive model).
In order to keep it like that, please follow these simple rules:
DON'T use implicit array subscripts:
example: real, dimension(3,3) :: A,B
A(:,2) = B(:,1) <--- DON'T USE
A(1:3,2) = B(1:3,1) <--- BETTER USE
In many cases the use of explicit array subscripts is inevitable for parallelization. Additionally, it is an easy means to prevent memory leaks.
Enclose all write statements with the following:
!$OMP CRITICAL (write2out)
<your write statement>
!$OMP END CRITICAL (write2out)
Whenever you change something in the code and are not sure if it affects parallelization and leads to nonconforming behavior, please ask me and/or Franz to check this.
2011-03-17 16:16:17 +05:30
|
|
|
!*** input variables
|
|
|
|
integer(pInt), intent(in) :: ipc, & ! component-ID of current integration point
|
|
|
|
ip, & ! current integration point
|
|
|
|
el ! current element
|
|
|
|
real(pReal), intent(in) :: Temperature
|
|
|
|
real(pReal), dimension(6), intent(in) :: &
|
|
|
|
Tstar_v ! 2nd Piola Kirchhoff stress tensor (Mandel)
|
|
|
|
|
|
|
|
!*** output variables ***!
|
|
|
|
real(pReal) constitutive_dotTemperature ! evolution of temperature
|
|
|
|
|
|
|
|
!*** local variables
|
|
|
|
integer(pLongInt) tick, tock, &
|
|
|
|
tickrate, &
|
|
|
|
maxticks
|
|
|
|
|
2009-07-01 15:59:35 +05:30
|
|
|
|
2012-07-05 15:24:50 +05:30
|
|
|
if (iand(debug_level(debug_constitutive),debug_levelBasic) /= 0_pInt) then
|
2011-03-21 16:01:17 +05:30
|
|
|
call system_clock(count=tick,count_rate=tickrate,count_max=maxticks)
|
|
|
|
endif
|
2010-09-13 14:59:03 +05:30
|
|
|
|
2012-03-12 19:39:37 +05:30
|
|
|
select case (phase_plasticity(material_phase(ipc,ip,el)))
|
2010-10-01 17:48:49 +05:30
|
|
|
|
2012-07-03 16:46:38 +05:30
|
|
|
case (constitutive_none_label)
|
|
|
|
constitutive_dotTemperature = constitutive_none_dotTemperature(Tstar_v,Temperature,constitutive_state,ipc,ip,el)
|
|
|
|
|
2010-10-01 17:48:49 +05:30
|
|
|
case (constitutive_j2_label)
|
|
|
|
constitutive_dotTemperature = constitutive_j2_dotTemperature(Tstar_v,Temperature,constitutive_state,ipc,ip,el)
|
|
|
|
|
|
|
|
case (constitutive_phenopowerlaw_label)
|
|
|
|
constitutive_dotTemperature = constitutive_phenopowerlaw_dotTemperature(Tstar_v,Temperature,constitutive_state,ipc,ip,el)
|
|
|
|
|
|
|
|
case (constitutive_titanmod_label)
|
|
|
|
constitutive_dotTemperature = constitutive_titanmod_dotTemperature(Tstar_v,Temperature,constitutive_state,ipc,ip,el)
|
|
|
|
|
|
|
|
case (constitutive_dislotwin_label)
|
|
|
|
constitutive_dotTemperature = constitutive_dislotwin_dotTemperature(Tstar_v,Temperature,constitutive_state,ipc,ip,el)
|
|
|
|
|
|
|
|
case (constitutive_nonlocal_label)
|
|
|
|
constitutive_dotTemperature = constitutive_nonlocal_dotTemperature(Tstar_v,Temperature,constitutive_state,ipc,ip,el)
|
|
|
|
|
|
|
|
end select
|
|
|
|
|
2012-07-05 15:24:50 +05:30
|
|
|
if (iand(debug_level(debug_constitutive),debug_levelBasic) /= 0_pInt) then
|
2011-03-21 16:01:17 +05:30
|
|
|
call system_clock(count=tock,count_rate=tickrate,count_max=maxticks)
|
|
|
|
!$OMP CRITICAL (debugTimingDotTemperature)
|
|
|
|
debug_cumDotTemperatureCalls = debug_cumDotTemperatureCalls + 1_pInt
|
|
|
|
debug_cumDotTemperatureTicks = debug_cumDotTemperatureTicks + tock-tick
|
|
|
|
!$OMP FLUSH (debug_cumDotTemperatureTicks)
|
|
|
|
if (tock < tick) debug_cumDotTemperatureTicks = debug_cumDotTemperatureTicks + maxticks
|
|
|
|
!$OMP END CRITICAL (debugTimingDotTemperature)
|
|
|
|
endif
|
2010-10-01 17:48:49 +05:30
|
|
|
|
2012-10-02 18:23:25 +05:30
|
|
|
end function constitutive_dotTemperature
|
2009-07-01 15:59:35 +05:30
|
|
|
|
|
|
|
|
openmp parallelization working again (at least for j2 and nonlocal constitutive model).
In order to keep it like that, please follow these simple rules:
DON'T use implicit array subscripts:
example: real, dimension(3,3) :: A,B
A(:,2) = B(:,1) <--- DON'T USE
A(1:3,2) = B(1:3,1) <--- BETTER USE
In many cases the use of explicit array subscripts is inevitable for parallelization. Additionally, it is an easy means to prevent memory leaks.
Enclose all write statements with the following:
!$OMP CRITICAL (write2out)
<your write statement>
!$OMP END CRITICAL (write2out)
Whenever you change something in the code and are not sure if it affects parallelization and leads to nonconforming behavior, please ask me and/or Franz to check this.
2011-03-17 16:16:17 +05:30
|
|
|
|
2009-03-04 19:31:36 +05:30
|
|
|
!*********************************************************************
|
|
|
|
!* return array of constitutive results *
|
|
|
|
!* INPUT: *
|
|
|
|
!* - Tstar_v : 2nd Piola Kirchhoff stress tensor (Mandel) *
|
|
|
|
!* - dt : current time increment *
|
|
|
|
!* - ipc : component-ID of current integration point *
|
|
|
|
!* - ip : current integration point *
|
|
|
|
!* - el : current element *
|
|
|
|
!*********************************************************************
|
2012-10-02 18:23:25 +05:30
|
|
|
function constitutive_postResults(Tstar_v, Fe, Temperature, dt, ipc, ip, el)
|
2012-03-09 01:55:28 +05:30
|
|
|
use prec, only: pReal
|
openmp parallelization working again (at least for j2 and nonlocal constitutive model).
In order to keep it like that, please follow these simple rules:
DON'T use implicit array subscripts:
example: real, dimension(3,3) :: A,B
A(:,2) = B(:,1) <--- DON'T USE
A(1:3,2) = B(1:3,1) <--- BETTER USE
In many cases the use of explicit array subscripts is inevitable for parallelization. Additionally, it is an easy means to prevent memory leaks.
Enclose all write statements with the following:
!$OMP CRITICAL (write2out)
<your write statement>
!$OMP END CRITICAL (write2out)
Whenever you change something in the code and are not sure if it affects parallelization and leads to nonconforming behavior, please ask me and/or Franz to check this.
2011-03-17 16:16:17 +05:30
|
|
|
use mesh, only: mesh_NcpElems, &
|
2012-02-21 21:30:00 +05:30
|
|
|
mesh_maxNips
|
2012-03-12 19:39:37 +05:30
|
|
|
use material, only: phase_plasticity, &
|
openmp parallelization working again (at least for j2 and nonlocal constitutive model).
In order to keep it like that, please follow these simple rules:
DON'T use implicit array subscripts:
example: real, dimension(3,3) :: A,B
A(:,2) = B(:,1) <--- DON'T USE
A(1:3,2) = B(1:3,1) <--- BETTER USE
In many cases the use of explicit array subscripts is inevitable for parallelization. Additionally, it is an easy means to prevent memory leaks.
Enclose all write statements with the following:
!$OMP CRITICAL (write2out)
<your write statement>
!$OMP END CRITICAL (write2out)
Whenever you change something in the code and are not sure if it affects parallelization and leads to nonconforming behavior, please ask me and/or Franz to check this.
2011-03-17 16:16:17 +05:30
|
|
|
material_phase, &
|
|
|
|
homogenization_maxNgrains
|
2012-07-03 16:46:38 +05:30
|
|
|
use constitutive_none, only: constitutive_none_postResults, &
|
|
|
|
constitutive_none_label
|
openmp parallelization working again (at least for j2 and nonlocal constitutive model).
In order to keep it like that, please follow these simple rules:
DON'T use implicit array subscripts:
example: real, dimension(3,3) :: A,B
A(:,2) = B(:,1) <--- DON'T USE
A(1:3,2) = B(1:3,1) <--- BETTER USE
In many cases the use of explicit array subscripts is inevitable for parallelization. Additionally, it is an easy means to prevent memory leaks.
Enclose all write statements with the following:
!$OMP CRITICAL (write2out)
<your write statement>
!$OMP END CRITICAL (write2out)
Whenever you change something in the code and are not sure if it affects parallelization and leads to nonconforming behavior, please ask me and/or Franz to check this.
2011-03-17 16:16:17 +05:30
|
|
|
use constitutive_j2, only: constitutive_j2_postResults, &
|
|
|
|
constitutive_j2_label
|
|
|
|
use constitutive_phenopowerlaw, only: constitutive_phenopowerlaw_postResults, &
|
|
|
|
constitutive_phenopowerlaw_label
|
|
|
|
use constitutive_titanmod, only: constitutive_titanmod_postResults, &
|
|
|
|
constitutive_titanmod_label
|
|
|
|
use constitutive_dislotwin, only: constitutive_dislotwin_postResults, &
|
|
|
|
constitutive_dislotwin_label
|
|
|
|
use constitutive_nonlocal, only: constitutive_nonlocal_postResults, &
|
|
|
|
constitutive_nonlocal_label
|
2009-03-06 15:32:36 +05:30
|
|
|
|
2012-03-09 01:55:28 +05:30
|
|
|
implicit none
|
openmp parallelization working again (at least for j2 and nonlocal constitutive model).
In order to keep it like that, please follow these simple rules:
DON'T use implicit array subscripts:
example: real, dimension(3,3) :: A,B
A(:,2) = B(:,1) <--- DON'T USE
A(1:3,2) = B(1:3,1) <--- BETTER USE
In many cases the use of explicit array subscripts is inevitable for parallelization. Additionally, it is an easy means to prevent memory leaks.
Enclose all write statements with the following:
!$OMP CRITICAL (write2out)
<your write statement>
!$OMP END CRITICAL (write2out)
Whenever you change something in the code and are not sure if it affects parallelization and leads to nonconforming behavior, please ask me and/or Franz to check this.
2011-03-17 16:16:17 +05:30
|
|
|
!*** input variables
|
|
|
|
integer(pInt), intent(in) :: ipc, & ! component-ID of current integration point
|
|
|
|
ip, & ! current integration point
|
|
|
|
el ! current element
|
|
|
|
real(pReal), intent(in) :: Temperature, &
|
|
|
|
dt ! timestep
|
2012-01-17 15:56:57 +05:30
|
|
|
real(pReal), dimension(3,3,homogenization_maxNgrains,mesh_maxNips,mesh_NcpElems), intent(in) :: &
|
openmp parallelization working again (at least for j2 and nonlocal constitutive model).
In order to keep it like that, please follow these simple rules:
DON'T use implicit array subscripts:
example: real, dimension(3,3) :: A,B
A(:,2) = B(:,1) <--- DON'T USE
A(1:3,2) = B(1:3,1) <--- BETTER USE
In many cases the use of explicit array subscripts is inevitable for parallelization. Additionally, it is an easy means to prevent memory leaks.
Enclose all write statements with the following:
!$OMP CRITICAL (write2out)
<your write statement>
!$OMP END CRITICAL (write2out)
Whenever you change something in the code and are not sure if it affects parallelization and leads to nonconforming behavior, please ask me and/or Franz to check this.
2011-03-17 16:16:17 +05:30
|
|
|
Fe ! elastic deformation gradient
|
|
|
|
real(pReal), dimension(6), intent(in) :: &
|
|
|
|
Tstar_v ! 2nd Piola Kirchhoff stress tensor (Mandel)
|
2009-03-06 15:32:36 +05:30
|
|
|
|
openmp parallelization working again (at least for j2 and nonlocal constitutive model).
In order to keep it like that, please follow these simple rules:
DON'T use implicit array subscripts:
example: real, dimension(3,3) :: A,B
A(:,2) = B(:,1) <--- DON'T USE
A(1:3,2) = B(1:3,1) <--- BETTER USE
In many cases the use of explicit array subscripts is inevitable for parallelization. Additionally, it is an easy means to prevent memory leaks.
Enclose all write statements with the following:
!$OMP CRITICAL (write2out)
<your write statement>
!$OMP END CRITICAL (write2out)
Whenever you change something in the code and are not sure if it affects parallelization and leads to nonconforming behavior, please ask me and/or Franz to check this.
2011-03-17 16:16:17 +05:30
|
|
|
!*** output variables ***!
|
|
|
|
real(pReal), dimension(constitutive_sizePostResults(ipc,ip,el)) :: constitutive_postResults
|
|
|
|
|
|
|
|
!*** local variables
|
2010-09-13 14:59:03 +05:30
|
|
|
|
2009-03-06 15:32:36 +05:30
|
|
|
|
openmp parallelization working again (at least for j2 and nonlocal constitutive model).
In order to keep it like that, please follow these simple rules:
DON'T use implicit array subscripts:
example: real, dimension(3,3) :: A,B
A(:,2) = B(:,1) <--- DON'T USE
A(1:3,2) = B(1:3,1) <--- BETTER USE
In many cases the use of explicit array subscripts is inevitable for parallelization. Additionally, it is an easy means to prevent memory leaks.
Enclose all write statements with the following:
!$OMP CRITICAL (write2out)
<your write statement>
!$OMP END CRITICAL (write2out)
Whenever you change something in the code and are not sure if it affects parallelization and leads to nonconforming behavior, please ask me and/or Franz to check this.
2011-03-17 16:16:17 +05:30
|
|
|
constitutive_postResults = 0.0_pReal
|
2012-03-12 19:39:37 +05:30
|
|
|
select case (phase_plasticity(material_phase(ipc,ip,el)))
|
openmp parallelization working again (at least for j2 and nonlocal constitutive model).
In order to keep it like that, please follow these simple rules:
DON'T use implicit array subscripts:
example: real, dimension(3,3) :: A,B
A(:,2) = B(:,1) <--- DON'T USE
A(1:3,2) = B(1:3,1) <--- BETTER USE
In many cases the use of explicit array subscripts is inevitable for parallelization. Additionally, it is an easy means to prevent memory leaks.
Enclose all write statements with the following:
!$OMP CRITICAL (write2out)
<your write statement>
!$OMP END CRITICAL (write2out)
Whenever you change something in the code and are not sure if it affects parallelization and leads to nonconforming behavior, please ask me and/or Franz to check this.
2011-03-17 16:16:17 +05:30
|
|
|
|
2012-07-03 16:46:38 +05:30
|
|
|
case (constitutive_none_label)
|
|
|
|
constitutive_postResults = constitutive_none_postResults(Tstar_v,Temperature,dt,constitutive_state,ipc,ip,el)
|
|
|
|
|
openmp parallelization working again (at least for j2 and nonlocal constitutive model).
In order to keep it like that, please follow these simple rules:
DON'T use implicit array subscripts:
example: real, dimension(3,3) :: A,B
A(:,2) = B(:,1) <--- DON'T USE
A(1:3,2) = B(1:3,1) <--- BETTER USE
In many cases the use of explicit array subscripts is inevitable for parallelization. Additionally, it is an easy means to prevent memory leaks.
Enclose all write statements with the following:
!$OMP CRITICAL (write2out)
<your write statement>
!$OMP END CRITICAL (write2out)
Whenever you change something in the code and are not sure if it affects parallelization and leads to nonconforming behavior, please ask me and/or Franz to check this.
2011-03-17 16:16:17 +05:30
|
|
|
case (constitutive_j2_label)
|
|
|
|
constitutive_postResults = constitutive_j2_postResults(Tstar_v,Temperature,dt,constitutive_state,ipc,ip,el)
|
|
|
|
|
|
|
|
case (constitutive_phenopowerlaw_label)
|
|
|
|
constitutive_postResults = constitutive_phenopowerlaw_postResults(Tstar_v,Temperature,dt,constitutive_state,ipc,ip,el)
|
|
|
|
|
|
|
|
case (constitutive_titanmod_label)
|
|
|
|
constitutive_postResults = constitutive_titanmod_postResults(Tstar_v,Temperature,dt,constitutive_state,ipc,ip,el)
|
|
|
|
|
|
|
|
case (constitutive_dislotwin_label)
|
|
|
|
constitutive_postResults = constitutive_dislotwin_postResults(Tstar_v,Temperature,dt,constitutive_state,ipc,ip,el)
|
|
|
|
|
|
|
|
case (constitutive_nonlocal_label)
|
|
|
|
constitutive_postResults = constitutive_nonlocal_postResults(Tstar_v, Fe, Temperature, dt, constitutive_state, &
|
2012-01-17 15:56:57 +05:30
|
|
|
constitutive_dotstate(ipc,ip,el), ipc, ip, el)
|
openmp parallelization working again (at least for j2 and nonlocal constitutive model).
In order to keep it like that, please follow these simple rules:
DON'T use implicit array subscripts:
example: real, dimension(3,3) :: A,B
A(:,2) = B(:,1) <--- DON'T USE
A(1:3,2) = B(1:3,1) <--- BETTER USE
In many cases the use of explicit array subscripts is inevitable for parallelization. Additionally, it is an easy means to prevent memory leaks.
Enclose all write statements with the following:
!$OMP CRITICAL (write2out)
<your write statement>
!$OMP END CRITICAL (write2out)
Whenever you change something in the code and are not sure if it affects parallelization and leads to nonconforming behavior, please ask me and/or Franz to check this.
2011-03-17 16:16:17 +05:30
|
|
|
end select
|
|
|
|
|
2012-10-02 18:23:25 +05:30
|
|
|
end function constitutive_postResults
|
2009-03-06 15:32:36 +05:30
|
|
|
|
2012-03-14 21:46:11 +05:30
|
|
|
|
2012-10-02 18:23:25 +05:30
|
|
|
end module constitutive
|