2009-08-31 20:39:15 +05:30
!* $Id$
2009-03-04 19:31:36 +05:30
!************************************
!* Module: CONSTITUTIVE *
!************************************
!* contains: *
!* - constitutive equations *
!* - parameters definition *
!************************************
2009-03-06 15:32:36 +05:30
2009-03-04 19:31:36 +05:30
MODULE constitutive
2009-03-06 15:32:36 +05:30
2009-03-04 19:31:36 +05:30
!*** Include other modules ***
use prec
implicit none
2009-03-06 15:32:36 +05:30
2009-05-07 21:57:36 +05:30
type ( p_vec ) , dimension ( : , : , : ) , allocatable :: 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
2009-08-11 22:01:57 +05:30
constitutive_state , & ! pointer array to current microstructure (end of converged time step)
2010-09-13 14:43:25 +05:30
constitutive_state_backup , & ! pointer array to backed up microstructure (end of converged time step)
2009-09-18 21:07:14 +05:30
constitutive_dotState , & ! pointer array to evolution of current microstructure
2010-09-13 14:43:25 +05:30
constitutive_previousDotState , & ! pointer array to previous evolution of current microstructure
constitutive_previousDotState2 , & ! pointer array to 2nd previous evolution of current microstructure
2010-10-01 17:48:49 +05:30
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
2010-10-26 18:46:37 +05:30
constitutive_aTolState ! pointer array to absolute state tolerance
2010-10-01 17:48:49 +05:30
type ( p_vec ) , dimension ( : , : , : , : ) , allocatable :: constitutive_RKCK45dotState ! pointer array to evolution of microstructure used by Cash-Karp Runge-Kutta method
2009-05-07 21:57:36 +05:30
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
2009-08-11 22:01:57 +05:30
integer ( pInt ) constitutive_maxSizeDotState , &
constitutive_maxSizeState , &
constitutive_maxSizePostResults
2009-03-06 15:32:36 +05:30
2009-03-04 19:31:36 +05:30
CONTAINS
!****************************************
!* - constitutive_init
!* - constitutive_homogenizedC
2010-03-24 18:50:12 +05:30
!* - constitutive_averageBurgers
2009-03-04 19:31:36 +05:30
!* - constitutive_microstructure
!* - constitutive_LpAndItsTangent
2009-08-11 22:01:57 +05:30
!* - constitutive_collectDotState
!* - constitutive_collectDotTemperature
2009-03-04 19:31:36 +05:30
!* - constitutive_postResults
!****************************************
2009-03-06 15:32:36 +05:30
2009-03-04 19:31:36 +05:30
subroutine constitutive_init ( )
!**************************************
!* Module initialization *
!**************************************
use prec , only : pReal , pInt
2010-02-17 18:51:36 +05:30
use debug , only : debugger , selectiveDebugger , debug_e , debug_i , debug_g
2011-02-23 13:59:51 +05:30
use numerics , only : numerics_integrator
2009-07-22 21:37:19 +05:30
use IO , only : IO_error , IO_open_file , IO_open_jobFile
2009-03-04 19:31:36 +05:30
use mesh , only : mesh_maxNips , mesh_NcpElems , mesh_element , FE_Nips
use material
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
2009-03-06 15:32:36 +05:30
2009-03-04 19:31:36 +05:30
integer ( pInt ) , parameter :: fileunit = 200
2010-10-01 17:48:49 +05:30
integer ( pInt ) e , i , g , p , s , myInstance , myNgrains
2009-07-22 21:37:19 +05:30
integer ( pInt ) , dimension ( : , : ) , pointer :: thisSize
2009-10-16 01:32:52 +05:30
character ( len = 64 ) , dimension ( : , : ) , pointer :: thisOutput
2009-07-22 21:37:19 +05:30
logical knownConstitution
2009-03-04 19:31:36 +05:30
if ( . not . IO_open_file ( fileunit , material_configFile ) ) call IO_error ( 100 ) ! corrupt config file
2009-03-05 20:06:01 +05:30
2009-07-22 21:37:19 +05:30
call constitutive_j2_init ( fileunit ) ! parse all phases of this constitution
call constitutive_phenopowerlaw_init ( fileunit )
2010-09-13 14:59:03 +05:30
call constitutive_titanmod_init ( fileunit )
2009-10-06 20:46:03 +05:30
call constitutive_dislotwin_init ( fileunit )
2009-08-11 22:01:57 +05:30
call constitutive_nonlocal_init ( fileunit )
2009-03-05 20:06:01 +05:30
2009-03-04 19:31:36 +05:30
close ( fileunit )
2009-03-06 15:32:36 +05:30
2009-07-22 21:37:19 +05:30
! write description file for constitutive phase output
if ( . not . IO_open_jobFile ( fileunit , 'outputConstitutive' ) ) call IO_error ( 50 ) ! problems in writing file
do p = 1 , material_Nphase
i = phase_constitutionInstance ( p ) ! which instance of a constitution is present phase
knownConstitution = . true . ! assume valid
select case ( phase_constitution ( p ) ) ! split per constitiution
case ( constitutive_j2_label )
thisOutput = > constitutive_j2_output
thisSize = > constitutive_j2_sizePostResult
case ( constitutive_phenopowerlaw_label )
thisOutput = > constitutive_phenopowerlaw_output
thisSize = > constitutive_phenopowerlaw_sizePostResult
2010-09-13 14:59:03 +05:30
case ( constitutive_titanmod_label )
thisOutput = > constitutive_titanmod_output
thisSize = > constitutive_titanmod_sizePostResult
2009-10-06 20:46:03 +05:30
case ( constitutive_dislotwin_label )
thisOutput = > constitutive_dislotwin_output
thisSize = > constitutive_dislotwin_sizePostResult
2009-08-11 22:01:57 +05:30
case ( constitutive_nonlocal_label )
thisOutput = > constitutive_nonlocal_output
thisSize = > constitutive_nonlocal_sizePostResult
2009-07-22 21:37:19 +05:30
case default
knownConstitution = . false .
end select
write ( fileunit , * )
write ( fileunit , '(a)' ) '[' / / trim ( phase_name ( p ) ) / / ']'
write ( fileunit , * )
if ( knownConstitution ) then
2010-02-25 23:09:11 +05:30
write ( fileunit , '(a)' ) '(constitution)' / / char ( 9 ) / / trim ( phase_constitution ( p ) )
2009-07-22 21:37:19 +05:30
do e = 1 , phase_Noutput ( p )
write ( fileunit , '(a,i4)' ) trim ( thisOutput ( e , i ) ) / / char ( 9 ) , thisSize ( e , i )
enddo
endif
enddo
close ( fileunit )
! allocate memory for state management
2009-05-07 21:57:36 +05:30
allocate ( constitutive_state0 ( homogenization_maxNgrains , mesh_maxNips , mesh_NcpElems ) )
allocate ( constitutive_partionedState0 ( homogenization_maxNgrains , mesh_maxNips , mesh_NcpElems ) )
allocate ( constitutive_subState0 ( homogenization_maxNgrains , mesh_maxNips , mesh_NcpElems ) )
allocate ( constitutive_state ( homogenization_maxNgrains , mesh_maxNips , mesh_NcpElems ) )
2010-09-13 14:43:25 +05:30
allocate ( constitutive_state_backup ( homogenization_maxNgrains , mesh_maxNips , mesh_NcpElems ) )
2009-08-11 22:01:57 +05:30
allocate ( constitutive_dotState ( homogenization_maxNgrains , mesh_maxNips , mesh_NcpElems ) )
2010-09-13 14:43:25 +05:30
allocate ( constitutive_dotState_backup ( homogenization_maxNgrains , mesh_maxNips , mesh_NcpElems ) )
2010-10-26 18:46:37 +05:30
allocate ( constitutive_aTolState ( homogenization_maxNgrains , mesh_maxNips , mesh_NcpElems ) )
2009-08-11 22:01:57 +05:30
allocate ( constitutive_sizeDotState ( homogenization_maxNgrains , mesh_maxNips , mesh_NcpElems ) ) ; constitutive_sizeDotState = 0_pInt
allocate ( constitutive_sizeState ( homogenization_maxNgrains , mesh_maxNips , mesh_NcpElems ) ) ; constitutive_sizeState = 0_pInt
allocate ( constitutive_sizePostResults ( homogenization_maxNgrains , mesh_maxNips , mesh_NcpElems ) ) ; constitutive_sizePostResults = 0_pInt
2011-02-23 13:59:51 +05:30
if ( any ( numerics_integrator == 1 ) ) then
2010-10-01 17:48:49 +05:30
allocate ( constitutive_previousDotState ( homogenization_maxNgrains , mesh_maxNips , mesh_NcpElems ) )
allocate ( constitutive_previousDotState2 ( homogenization_maxNgrains , mesh_maxNips , mesh_NcpElems ) )
endif
2011-02-23 13:59:51 +05:30
if ( any ( numerics_integrator == 4 ) ) &
2010-10-12 17:41:24 +05:30
allocate ( constitutive_RK4dotState ( homogenization_maxNgrains , mesh_maxNips , mesh_NcpElems ) )
2011-02-23 13:59:51 +05:30
if ( any ( numerics_integrator == 5 ) ) &
2010-10-01 17:48:49 +05:30
allocate ( constitutive_RKCK45dotState ( 6 , homogenization_maxNgrains , mesh_maxNips , mesh_NcpElems ) )
2009-09-18 21:07:14 +05:30
2009-03-04 19:31:36 +05:30
do e = 1 , mesh_NcpElems ! loop over elements
2009-05-07 21:57:36 +05:30
myNgrains = homogenization_Ngrains ( mesh_element ( 3 , e ) )
2009-03-04 19:31:36 +05:30
do i = 1 , FE_Nips ( mesh_element ( 2 , e ) ) ! loop over IPs
2009-05-07 21:57:36 +05:30
do g = 1 , myNgrains ! loop over grains
2009-03-04 19:31:36 +05:30
myInstance = phase_constitutionInstance ( material_phase ( g , i , e ) )
2009-09-18 21:07:14 +05:30
select case ( phase_constitution ( material_phase ( g , i , e ) ) )
2009-03-05 20:06:01 +05:30
case ( constitutive_j2_label )
2009-05-07 21:57:36 +05:30
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 ) ) )
2010-09-13 14:43:25 +05:30
allocate ( constitutive_state_backup ( g , i , e ) % p ( constitutive_j2_sizeState ( myInstance ) ) )
2010-10-26 18:46:37 +05:30
allocate ( constitutive_aTolState ( g , i , e ) % p ( constitutive_j2_sizeState ( myInstance ) ) )
2009-08-11 22:01:57 +05:30
allocate ( constitutive_dotState ( g , i , e ) % p ( constitutive_j2_sizeDotState ( myInstance ) ) )
2010-09-13 14:43:25 +05:30
allocate ( constitutive_dotState_backup ( g , i , e ) % p ( constitutive_j2_sizeDotState ( myInstance ) ) )
2011-02-23 13:59:51 +05:30
if ( any ( numerics_integrator == 1 ) ) then
2010-10-01 17:48:49 +05:30
allocate ( constitutive_previousDotState ( g , i , e ) % p ( constitutive_j2_sizeDotState ( myInstance ) ) )
allocate ( constitutive_previousDotState2 ( g , i , e ) % p ( constitutive_j2_sizeDotState ( myInstance ) ) )
endif
2011-02-23 13:59:51 +05:30
if ( any ( numerics_integrator == 4 ) ) &
2010-10-01 17:48:49 +05:30
allocate ( constitutive_RK4dotState ( g , i , e ) % p ( constitutive_j2_sizeDotState ( myInstance ) ) )
2011-02-23 13:59:51 +05:30
if ( any ( numerics_integrator == 5 ) ) then
2010-10-01 17:48:49 +05:30
do s = 1 , 6
allocate ( constitutive_RKCK45dotState ( s , g , i , e ) % p ( constitutive_j2_sizeDotState ( myInstance ) ) )
enddo
endif
2009-05-07 21:57:36 +05:30
constitutive_state0 ( g , i , e ) % p = constitutive_j2_stateInit ( myInstance )
2010-10-26 18:46:37 +05:30
constitutive_aTolState ( g , i , e ) % p = constitutive_j2_aTolState ( myInstance )
2009-03-26 14:13:31 +05:30
constitutive_sizeState ( g , i , e ) = constitutive_j2_sizeState ( myInstance )
2009-08-11 22:01:57 +05:30
constitutive_sizeDotState ( g , i , e ) = constitutive_j2_sizeDotState ( myInstance )
2009-03-26 14:13:31 +05:30
constitutive_sizePostResults ( g , i , e ) = constitutive_j2_sizePostResults ( myInstance )
2009-09-18 21:07:14 +05:30
2009-08-11 22:01:57 +05:30
case ( constitutive_phenopowerlaw_label )
2009-07-22 21:37:19 +05:30
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 ) ) )
2010-09-13 14:43:25 +05:30
allocate ( constitutive_state_backup ( g , i , e ) % p ( constitutive_phenopowerlaw_sizeState ( myInstance ) ) )
2010-10-26 18:46:37 +05:30
allocate ( constitutive_aTolState ( g , i , e ) % p ( constitutive_phenopowerlaw_sizeState ( myInstance ) ) )
2009-08-11 22:01:57 +05:30
allocate ( constitutive_dotState ( g , i , e ) % p ( constitutive_phenopowerlaw_sizeDotState ( myInstance ) ) )
2010-09-13 14:43:25 +05:30
allocate ( constitutive_dotState_backup ( g , i , e ) % p ( constitutive_phenopowerlaw_sizeDotState ( myInstance ) ) )
2011-02-23 13:59:51 +05:30
if ( any ( numerics_integrator == 1 ) ) then
2010-10-01 17:48:49 +05:30
allocate ( constitutive_previousDotState ( g , i , e ) % p ( constitutive_phenopowerlaw_sizeDotState ( myInstance ) ) )
allocate ( constitutive_previousDotState2 ( g , i , e ) % p ( constitutive_phenopowerlaw_sizeDotState ( myInstance ) ) )
endif
2011-02-23 13:59:51 +05:30
if ( any ( numerics_integrator == 4 ) ) &
2010-10-01 17:48:49 +05:30
allocate ( constitutive_RK4dotState ( g , i , e ) % p ( constitutive_phenopowerlaw_sizeDotState ( myInstance ) ) )
2011-02-23 13:59:51 +05:30
if ( any ( numerics_integrator == 5 ) ) then
2010-10-01 17:48:49 +05:30
do s = 1 , 6
allocate ( constitutive_RKCK45dotState ( s , g , i , e ) % p ( constitutive_phenopowerlaw_sizeDotState ( myInstance ) ) )
enddo
endif
2009-07-22 21:37:19 +05:30
constitutive_state0 ( g , i , e ) % p = constitutive_phenopowerlaw_stateInit ( myInstance )
2010-10-26 18:46:37 +05:30
constitutive_aTolState ( g , i , e ) % p = constitutive_phenopowerlaw_aTolState ( myInstance )
2009-07-22 21:37:19 +05:30
constitutive_sizeState ( g , i , e ) = constitutive_phenopowerlaw_sizeState ( myInstance )
2009-08-11 22:01:57 +05:30
constitutive_sizeDotState ( g , i , e ) = constitutive_phenopowerlaw_sizeDotState ( myInstance )
2009-07-22 21:37:19 +05:30
constitutive_sizePostResults ( g , i , e ) = constitutive_phenopowerlaw_sizePostResults ( myInstance )
2010-09-13 14:59:03 +05:30
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 ) ) )
2010-10-26 18:46:37 +05:30
allocate ( constitutive_aTolState ( g , i , e ) % p ( constitutive_titanmod_sizeState ( myInstance ) ) )
2010-09-13 14:59:03 +05:30
allocate ( constitutive_dotState ( g , i , e ) % p ( constitutive_titanmod_sizeDotState ( myInstance ) ) )
allocate ( constitutive_dotState_backup ( g , i , e ) % p ( constitutive_titanmod_sizeDotState ( myInstance ) ) )
2011-02-23 13:59:51 +05:30
if ( any ( numerics_integrator == 1 ) ) then
2010-10-01 17:48:49 +05:30
allocate ( constitutive_previousDotState ( g , i , e ) % p ( constitutive_titanmod_sizeDotState ( myInstance ) ) )
allocate ( constitutive_previousDotState2 ( g , i , e ) % p ( constitutive_titanmod_sizeDotState ( myInstance ) ) )
endif
2011-02-23 13:59:51 +05:30
if ( any ( numerics_integrator == 4 ) ) &
2010-10-01 17:48:49 +05:30
allocate ( constitutive_RK4dotState ( g , i , e ) % p ( constitutive_titanmod_sizeDotState ( myInstance ) ) )
2011-02-23 13:59:51 +05:30
if ( any ( numerics_integrator == 5 ) ) then
2010-10-01 17:48:49 +05:30
do s = 1 , 6
allocate ( constitutive_RKCK45dotState ( s , g , i , e ) % p ( constitutive_titanmod_sizeDotState ( myInstance ) ) )
enddo
endif
2010-09-13 14:59:03 +05:30
constitutive_state0 ( g , i , e ) % p = constitutive_titanmod_stateInit ( myInstance )
2010-10-26 18:46:37 +05:30
constitutive_aTolState ( g , i , e ) % p = constitutive_titanmod_aTolState ( myInstance )
2010-09-13 14:59:03 +05:30
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 )
2009-09-18 21:07:14 +05:30
2009-10-06 20:46:03 +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 ) ) )
2010-09-13 14:43:25 +05:30
allocate ( constitutive_state_backup ( g , i , e ) % p ( constitutive_dislotwin_sizeState ( myInstance ) ) )
2010-10-26 18:46:37 +05:30
allocate ( constitutive_aTolState ( g , i , e ) % p ( constitutive_dislotwin_sizeState ( myInstance ) ) )
2009-10-06 20:46:03 +05:30
allocate ( constitutive_dotState ( g , i , e ) % p ( constitutive_dislotwin_sizeDotState ( myInstance ) ) )
2010-09-13 14:43:25 +05:30
allocate ( constitutive_dotState_backup ( g , i , e ) % p ( constitutive_dislotwin_sizeDotState ( myInstance ) ) )
2011-02-23 13:59:51 +05:30
if ( any ( numerics_integrator == 1 ) ) then
2010-10-01 17:48:49 +05:30
allocate ( constitutive_previousDotState ( g , i , e ) % p ( constitutive_dislotwin_sizeDotState ( myInstance ) ) )
allocate ( constitutive_previousDotState2 ( g , i , e ) % p ( constitutive_dislotwin_sizeDotState ( myInstance ) ) )
endif
2011-02-23 13:59:51 +05:30
if ( any ( numerics_integrator == 4 ) ) &
2010-10-01 17:48:49 +05:30
allocate ( constitutive_RK4dotState ( g , i , e ) % p ( constitutive_dislotwin_sizeDotState ( myInstance ) ) )
2011-02-23 13:59:51 +05:30
if ( any ( numerics_integrator == 5 ) ) then
2010-10-01 17:48:49 +05:30
do s = 1 , 6
allocate ( constitutive_RKCK45dotState ( s , g , i , e ) % p ( constitutive_dislotwin_sizeDotState ( myInstance ) ) )
enddo
endif
2009-10-06 20:46:03 +05:30
constitutive_state0 ( g , i , e ) % p = constitutive_dislotwin_stateInit ( myInstance )
2010-10-26 18:46:37 +05:30
constitutive_aTolState ( g , i , e ) % p = constitutive_dislotwin_aTolState ( myInstance )
2009-10-06 20:46:03 +05:30
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 )
2009-09-18 21:07:14 +05:30
2009-08-11 22:01:57 +05:30
case ( constitutive_nonlocal_label )
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 ) ) )
2010-09-13 14:43:25 +05:30
allocate ( constitutive_state_backup ( g , i , e ) % p ( constitutive_nonlocal_sizeState ( myInstance ) ) )
2010-10-26 18:46:37 +05:30
allocate ( constitutive_aTolState ( g , i , e ) % p ( constitutive_nonlocal_sizeState ( myInstance ) ) )
2009-08-11 22:01:57 +05:30
allocate ( constitutive_dotState ( g , i , e ) % p ( constitutive_nonlocal_sizeDotState ( myInstance ) ) )
2010-09-13 14:43:25 +05:30
allocate ( constitutive_dotState_backup ( g , i , e ) % p ( constitutive_nonlocal_sizeDotState ( myInstance ) ) )
2011-02-23 13:59:51 +05:30
if ( any ( numerics_integrator == 1 ) ) then
2010-10-01 17:48:49 +05:30
allocate ( constitutive_previousDotState ( g , i , e ) % p ( constitutive_nonlocal_sizeDotState ( myInstance ) ) )
allocate ( constitutive_previousDotState2 ( g , i , e ) % p ( constitutive_nonlocal_sizeDotState ( myInstance ) ) )
endif
2011-02-23 13:59:51 +05:30
if ( any ( numerics_integrator == 4 ) ) &
2010-10-01 17:48:49 +05:30
allocate ( constitutive_RK4dotState ( g , i , e ) % p ( constitutive_nonlocal_sizeDotState ( myInstance ) ) )
2011-02-23 13:59:51 +05:30
if ( any ( numerics_integrator == 5 ) ) then
2010-10-01 17:48:49 +05:30
do s = 1 , 6
allocate ( constitutive_RKCK45dotState ( s , g , i , e ) % p ( constitutive_nonlocal_sizeDotState ( myInstance ) ) )
enddo
endif
2009-08-11 22:01:57 +05:30
constitutive_state0 ( g , i , e ) % p = constitutive_nonlocal_stateInit ( myInstance )
2010-10-26 18:46:37 +05:30
constitutive_aTolState ( g , i , e ) % p = constitutive_nonlocal_aTolState ( myInstance )
2009-08-11 22:01:57 +05:30
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 )
2009-09-18 21:07:14 +05:30
2009-03-04 19:31:36 +05:30
case default
call IO_error ( 200 , material_phase ( g , i , e ) ) ! unknown constitution
2009-09-18 21:07:14 +05:30
2009-03-04 19:31:36 +05:30
end select
2009-05-07 21:57:36 +05:30
constitutive_partionedState0 ( g , i , e ) % p = constitutive_state0 ( g , i , e ) % p
2009-03-04 19:31:36 +05:30
enddo
enddo
enddo
2010-10-01 17:48:49 +05:30
2009-03-04 19:31:36 +05:30
constitutive_maxSizeState = maxval ( constitutive_sizeState )
2009-08-11 22:01:57 +05:30
constitutive_maxSizeDotState = maxval ( constitutive_sizeDotState )
2009-03-04 19:31:36 +05:30
constitutive_maxSizePostResults = maxval ( constitutive_sizePostResults )
2009-03-06 15:32:36 +05:30
2009-12-15 13:50:31 +05:30
!$OMP CRITICAL (write2out)
2009-05-07 21:57:36 +05:30
write ( 6 , * )
write ( 6 , * ) '<<<+- constitutive init -+>>>'
2009-08-31 20:39:15 +05:30
write ( 6 , * ) '$Id$'
2009-05-07 21:57:36 +05:30
write ( 6 , * )
write ( 6 , '(a32,x,7(i5,x))' ) 'constitutive_state0: ' , shape ( constitutive_state0 )
write ( 6 , '(a32,x,7(i5,x))' ) 'constitutive_partionedState0: ' , shape ( constitutive_partionedState0 )
write ( 6 , '(a32,x,7(i5,x))' ) 'constitutive_subState0: ' , shape ( constitutive_subState0 )
write ( 6 , '(a32,x,7(i5,x))' ) 'constitutive_state: ' , shape ( constitutive_state )
2010-10-26 18:46:37 +05:30
write ( 6 , '(a32,x,7(i5,x))' ) 'constitutive_aTolState: ' , shape ( constitutive_aTolState )
2009-08-11 22:01:57 +05:30
write ( 6 , '(a32,x,7(i5,x))' ) 'constitutive_dotState: ' , shape ( constitutive_dotState )
2009-05-07 21:57:36 +05:30
write ( 6 , '(a32,x,7(i5,x))' ) 'constitutive_sizeState: ' , shape ( constitutive_sizeState )
write ( 6 , '(a32,x,7(i5,x))' ) 'constitutive_sizeDotState: ' , shape ( constitutive_sizeDotState )
write ( 6 , '(a32,x,7(i5,x))' ) 'constitutive_sizePostResults: ' , shape ( constitutive_sizePostResults )
write ( 6 , * )
write ( 6 , '(a32,x,7(i5,x))' ) 'maxSizeState: ' , constitutive_maxSizeState
constitutive_nonlocal:
- read in activation energy for dislocation glide from material.config
- changed naming of dDipMin/Max to dLower/dUpper
- added new outputs: rho_dot, rho_dot_dip, rho_dot_gen, rho_dot_sgl2dip, rho_dot_dip2sgl, rho_dot_ann_ath, rho_dot_ann_the, rho_dot_flux, d_upper_edge, d_upper_screw, d_upper_dot_edge, d_upper_dot_screw
- poisson's ratio is now calculated from elastic constants
- microstrucutre has state as first argument, since this is our output variable
- periodic boundary conditions are taken into account for fluxes and internal stresses. for the moment, flag has to be set in constitutive_nonlocal.
- corrected calculation for dipole formation by glide
- added terms for dipole formation/annihilation by stress decrease/increase
constitutive:
- passing of arguments is adapted for constitutive_nonlocal model
crystallite:
- in stiffness calculation: call to collect_dotState used wrong arguments
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
homogenization:
- crystallite_postResults uses own Tstar_v and temperature, no need for passing them from materialpoint_postResults
IO:
- changed error message 229
material.config:
- changed example for nonlocal constitution according to constitutive_nonlocal
all:
- added some flush statements
2009-10-20 20:06:03 +05:30
write ( 6 , '(a32,x,7(i5,x))' ) 'maxSizeDotState: ' , constitutive_maxSizeDotState
2009-05-07 21:57:36 +05:30
write ( 6 , '(a32,x,7(i5,x))' ) 'maxSizePostResults: ' , constitutive_maxSizePostResults
2009-12-15 13:50:31 +05:30
call flush ( 6 )
!$OMP END CRITICAL (write2out)
2009-03-04 19:31:36 +05:30
return
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
2009-03-04 19:31:36 +05:30
function constitutive_homogenizedC ( ipc , ip , el )
!*********************************************************************
!* This function returns the homogenized elacticity matrix *
!* INPUT: *
!* - state : state variables *
!* - ipc : component-ID of current integration point *
!* - ip : current integration point *
!* - el : current element *
!*********************************************************************
use prec , only : pReal , pInt
use material , only : phase_constitution , material_phase
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
2009-03-04 19:31:36 +05:30
implicit none
2009-03-06 15:32:36 +05:30
2009-03-04 19:31:36 +05:30
!* Definition of variables
integer ( pInt ) ipc , ip , el
real ( pReal ) , dimension ( 6 , 6 ) :: constitutive_homogenizedC
2009-03-06 15:32:36 +05:30
2009-03-04 19:31:36 +05:30
select case ( phase_constitution ( material_phase ( ipc , ip , el ) ) )
2009-08-11 22:01:57 +05:30
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
2009-03-04 19:31:36 +05:30
return
2009-08-11 22:01:57 +05:30
endfunction
2009-03-06 15:32:36 +05:30
2010-03-24 18:50:12 +05:30
function constitutive_averageBurgers ( ipc , ip , el )
!*********************************************************************
!* 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 *
!*********************************************************************
use prec , only : pReal , pInt
use material , only : phase_constitution , material_phase
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
implicit none
!* Definition of variables
integer ( pInt ) ipc , ip , el
real ( pReal ) :: constitutive_averageBurgers
select case ( phase_constitution ( material_phase ( ipc , ip , el ) ) )
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
return
endfunction
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 *
!*********************************************************************
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_microstructure ( Temperature , Tstar_v , Fe , Fp , ipc , ip , el )
use prec , only : pReal , pInt
use material , only : phase_constitution , &
2009-08-11 22:01:57 +05:30
material_phase , &
homogenization_maxNgrains
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 , &
2010-06-07 21:31:37 +05:30
mesh_maxNips , &
mesh_maxNipNeighbors
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
implicit none
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
!*** 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 ) , intent ( in ) , dimension ( 6 ) :: Tstar_v ! 2nd Piola-Kirchhoff stress
real ( pReal ) , dimension ( 3 , 3 , homogenization_maxNgrains , mesh_maxNips , mesh_NcpElems ) , 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 ***!
select case ( phase_constitution ( material_phase ( ipc , ip , el ) ) )
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 )
call constitutive_nonlocal_microstructure ( constitutive_state , Temperature , Tstar_v , 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
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 prec , only : pReal , pInt
use material , only : phase_constitution , &
material_phase
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
implicit none
2009-03-06 15:32:36 +05:30
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
!*** 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
!*** output variables ***!
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)
!*** local variables ***!
select case ( phase_constitution ( material_phase ( ipc , ip , el ) ) )
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 )
call constitutive_nonlocal_LpAndItsTangent ( Lp , dLp_dTstar , Tstar_v , Temperature , constitutive_state , ipc , ip , el )
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 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
subroutine constitutive_collectDotState ( Tstar_v , Fe , Fp , Temperature , subdt , orientation , ipc , ip , el )
2009-12-15 13:50:31 +05:30
use prec , only : pReal , pInt
use debug , only : debug_cumDotStateCalls , &
debug_cumDotStateTicks
use mesh , only : mesh_NcpElems , &
2009-12-18 21:16:33 +05:30
mesh_maxNips , &
mesh_maxNipNeighbors
2009-12-15 13:50:31 +05:30
use material , only : phase_constitution , &
material_phase , &
homogenization_maxNgrains
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
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
2010-10-15 18:49:26 +05:30
real ( pReal ) , dimension ( 4 , 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
orientation ! crystal orientation (quaternion)
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)
!*** output variables ***!
2009-12-15 13:50:31 +05:30
!*** local variables
integer ( pLongInt ) tick , tock , &
tickrate , &
maxticks
call system_clock ( count = tick , count_rate = tickrate , count_max = maxticks )
select case ( phase_constitution ( material_phase ( ipc , ip , el ) ) )
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 )
2011-02-25 15:23:20 +05:30
call constitutive_nonlocal_dotState ( constitutive_dotState , Tstar_v , Fe , Fp , Temperature , constitutive_state , &
constitutive_aTolState , subdt , orientation , ipc , ip , el )
2009-12-15 13:50:31 +05:30
end select
2009-03-06 15:32:36 +05:30
2009-12-15 13:50:31 +05:30
call system_clock ( count = tock , count_rate = tickrate , count_max = maxticks )
2010-11-19 22:49:03 +05:30
!$OMP CRITICAL (debugTimingDotState)
debug_cumDotStateCalls = debug_cumDotStateCalls + 1_pInt
debug_cumDotStateTicks = debug_cumDotStateTicks + tock - tick
if ( tock < tick ) debug_cumDotStateTicks = debug_cumDotStateTicks + maxticks
!$OMP END CRITICAL (debugTimingDotState)
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-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 )
2010-10-01 17:48:49 +05:30
use prec , only : pReal , pInt
use debug , only : debug_cumDotTemperatureCalls , &
debug_cumDotTemperatureTicks
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 material , only : phase_constitution , &
material_phase
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
implicit none
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
!*** 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
2010-10-01 17:48:49 +05:30
call system_clock ( count = tick , count_rate = tickrate , count_max = maxticks )
2010-09-13 14:59:03 +05:30
2010-10-01 17:48:49 +05:30
select case ( phase_constitution ( material_phase ( ipc , ip , el ) ) )
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
call system_clock ( count = tock , count_rate = tickrate , count_max = maxticks )
2010-11-19 22:49:03 +05:30
!$OMP CRITICAL (debugTimingDotTemperature)
debug_cumDotTemperatureCalls = debug_cumDotTemperatureCalls + 1_pInt
debug_cumDotTemperatureTicks = debug_cumDotTemperatureTicks + tock - tick
if ( tock < tick ) debug_cumDotTemperatureTicks = debug_cumDotTemperatureTicks + maxticks
!$OMP END CRITICAL (debugTimingDotTemperature)
2010-10-01 17:48:49 +05:30
2009-08-11 22:01:57 +05:30
endfunction
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
2011-02-25 15:23:20 +05:30
function constitutive_postResults ( Tstar_v , Fe , Temperature , dt , ipc , ip , el )
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 *
!*********************************************************************
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 prec , only : pReal , pInt
use mesh , only : mesh_NcpElems , &
mesh_maxNips , &
mesh_maxNipNeighbors
use material , only : phase_constitution , &
material_phase , &
homogenization_maxNgrains
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
implicit none
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
!*** 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
real ( pReal ) , dimension ( 3 , 3 ) , intent ( in ) :: &
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
select case ( phase_constitution ( material_phase ( ipc , ip , el ) ) )
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 , &
constitutive_dotstate , ipc , ip , el )
end select
2009-08-11 22:01:57 +05:30
endfunction
2009-03-06 15:32:36 +05:30
2010-03-24 21:53:21 +05:30
END MODULE