cleaning
This commit is contained in:
parent
76f0c5fc5e
commit
432609ec14
|
@ -172,8 +172,7 @@ subroutine CPFEM_general(mode, ffn, ffn1, temperature_inp, dt, elFE, ip, cauchyS
|
||||||
|
|
||||||
elCP = mesh_FEM2DAMASK_elem(elFE)
|
elCP = mesh_FEM2DAMASK_elem(elFE)
|
||||||
|
|
||||||
if (debugCPFEM%basic .and. elCP == debugCPFEM%element &
|
if (debugCPFEM%basic .and. elCP == debugCPFEM%element .and. ip == debugCPFEM%ip) then
|
||||||
.and. ip == debugCPFEM%ip) then
|
|
||||||
write(6,'(/,a)') '#############################################'
|
write(6,'(/,a)') '#############################################'
|
||||||
write(6,'(a1,a22,1x,i8,a13)') '#','element', elCP, '#'
|
write(6,'(a1,a22,1x,i8,a13)') '#','element', elCP, '#'
|
||||||
write(6,'(a1,a22,1x,i8,a13)') '#','ip', ip, '#'
|
write(6,'(a1,a22,1x,i8,a13)') '#','ip', ip, '#'
|
||||||
|
@ -249,8 +248,7 @@ subroutine CPFEM_general(mode, ffn, ffn1, temperature_inp, dt, elFE, ip, cauchyS
|
||||||
endif validCalculation
|
endif validCalculation
|
||||||
|
|
||||||
if (debugCPFEM%extensive &
|
if (debugCPFEM%extensive &
|
||||||
.and. (debugCPFEM%element == elCP .and. debugCPFEM%ip == ip) &
|
.and. (debugCPFEM%element == elCP .and. debugCPFEM%ip == ip) .or. .not. debugCPFEM%selective) then
|
||||||
.or. .not. debugCPFEM%selective) then
|
|
||||||
write(6,'(a,i8,1x,i2,/,12x,6(f10.3,1x)/)') &
|
write(6,'(a,i8,1x,i2,/,12x,6(f10.3,1x)/)') &
|
||||||
'<< CPFEM >> stress/MPa at elFE ip ', elFE, ip, CPFEM_cs(1:6,ip,elCP)*1.0e-6_pReal
|
'<< CPFEM >> stress/MPa at elFE ip ', elFE, ip, CPFEM_cs(1:6,ip,elCP)*1.0e-6_pReal
|
||||||
write(6,'(a,i8,1x,i2,/,6(12x,6(f10.3,1x)/))') &
|
write(6,'(a,i8,1x,i2,/,6(12x,6(f10.3,1x)/))') &
|
||||||
|
|
|
@ -253,20 +253,12 @@ subroutine hypela2(d,g,e,de,s,t,dt,ngens,m,nn,kcus,matus,ndi,nshear,disp, &
|
||||||
logical, save :: &
|
logical, save :: &
|
||||||
lastIncConverged = .false., & !< needs description
|
lastIncConverged = .false., & !< needs description
|
||||||
outdatedByNewInc = .false., & !< needs description
|
outdatedByNewInc = .false., & !< needs description
|
||||||
CPFEM_init_done = .false. !< remember whether init has been done already
|
CPFEM_init_done = .false., & !< remember whether init has been done already
|
||||||
|
debug_basic = .true.
|
||||||
class(tNode), pointer :: &
|
class(tNode), pointer :: &
|
||||||
debug_Marc ! pointer to Marc debug options
|
debug_Marc ! pointer to Marc debug options
|
||||||
|
|
||||||
defaultNumThreadsInt = omp_get_num_threads() ! remember number of threads set by Marc
|
if(debug_basic) then
|
||||||
call omp_set_num_threads(1) ! no openMP
|
|
||||||
|
|
||||||
if (.not. CPFEM_init_done) then
|
|
||||||
CPFEM_init_done = .true.
|
|
||||||
call CPFEM_initAll
|
|
||||||
endif
|
|
||||||
|
|
||||||
debug_Marc => debug_root%get('marc',defaultVal=emptyList)
|
|
||||||
if(debug_Marc%contains('basic')) then
|
|
||||||
write(6,'(a,/,i8,i8,i2)') ' MSC.MARC information on shape of element(2), IP:', m, nn
|
write(6,'(a,/,i8,i8,i2)') ' MSC.MARC information on shape of element(2), IP:', m, nn
|
||||||
write(6,'(a,2(i1))') ' Jacobian: ', ngens,ngens
|
write(6,'(a,2(i1))') ' Jacobian: ', ngens,ngens
|
||||||
write(6,'(a,i1)') ' Direct stress: ', ndi
|
write(6,'(a,i1)') ' Direct stress: ', ndi
|
||||||
|
@ -281,6 +273,15 @@ subroutine hypela2(d,g,e,de,s,t,dt,ngens,m,nn,kcus,matus,ndi,nshear,disp, &
|
||||||
transpose(ffn1)
|
transpose(ffn1)
|
||||||
endif
|
endif
|
||||||
|
|
||||||
|
defaultNumThreadsInt = omp_get_num_threads() ! remember number of threads set by Marc
|
||||||
|
call omp_set_num_threads(1) ! no openMP
|
||||||
|
|
||||||
|
if (.not. CPFEM_init_done) then
|
||||||
|
debug_Marc => debug_root%get('marc',defaultVal=emptyList)
|
||||||
|
debug_basic = debug_Marc%contains('basic')
|
||||||
|
CPFEM_init_done = .true.
|
||||||
|
call CPFEM_initAll
|
||||||
|
endif
|
||||||
|
|
||||||
computationMode = 0 ! save initialization value, since it does not result in any calculation
|
computationMode = 0 ! save initialization value, since it does not result in any calculation
|
||||||
if (lovl == 4 ) then ! jacobian requested by marc
|
if (lovl == 4 ) then ! jacobian requested by marc
|
||||||
|
|
|
@ -359,13 +359,12 @@ subroutine constitutive_init
|
||||||
debug_constitutive
|
debug_constitutive
|
||||||
|
|
||||||
debug_constitutive => debug_root%get('constitutive', defaultVal=emptyList)
|
debug_constitutive => debug_root%get('constitutive', defaultVal=emptyList)
|
||||||
debugConstitutive%basic = debug_constitutive%contains('basic')
|
debugConstitutive%basic = debug_constitutive%contains('basic')
|
||||||
debugConstitutive%extensive = debug_constitutive%contains('extensive')
|
debugConstitutive%extensive = debug_constitutive%contains('extensive')
|
||||||
debugConstitutive%selective = debug_constitutive%contains('selective')
|
debugConstitutive%selective = debug_constitutive%contains('selective')
|
||||||
debugConstitutive%element = debug_root%get_asInt('element',defaultVal = 1)
|
debugConstitutive%element = debug_root%get_asInt('element',defaultVal = 1)
|
||||||
debugConstitutive%ip = debug_root%get_asInt('integrationpoint',defaultVal = 1)
|
debugConstitutive%ip = debug_root%get_asInt('integrationpoint',defaultVal = 1)
|
||||||
debugConstitutive%grain = debug_root%get_asInt('grain',defaultVal = 1)
|
debugConstitutive%grain = debug_root%get_asInt('grain',defaultVal = 1)
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! initialized plasticity
|
! initialized plasticity
|
||||||
|
@ -502,7 +501,6 @@ subroutine constitutive_LpAndItsTangents(Lp, dLp_dS, dLp_dFi, &
|
||||||
integer :: &
|
integer :: &
|
||||||
i, j, instance, of
|
i, j, instance, of
|
||||||
|
|
||||||
|
|
||||||
ho = material_homogenizationAt(el)
|
ho = material_homogenizationAt(el)
|
||||||
tme = thermalMapping(ho)%p(ip,el)
|
tme = thermalMapping(ho)%p(ip,el)
|
||||||
|
|
||||||
|
|
|
@ -182,8 +182,7 @@ module subroutine plastic_isotropic_LpAndItsTangent(Lp,dLp_dMp,Mp,instance,of)
|
||||||
|
|
||||||
Lp = dot_gamma/prm%M * Mp_dev/norm_Mp_dev
|
Lp = dot_gamma/prm%M * Mp_dev/norm_Mp_dev
|
||||||
#ifdef DEBUG
|
#ifdef DEBUG
|
||||||
if (debugConstitutive%extensive &
|
if (debugConstitutive%extensive .and. (of == prm%of_debug .or. .not. debugConstitutive%selective)) then
|
||||||
.and. (of == prm%of_debug .or. .not. debugConstitutive%selective)) then
|
|
||||||
write(6,'(/,a,/,3(12x,3(f12.4,1x)/))') '<< CONST isotropic >> Tstar (dev) / MPa', &
|
write(6,'(/,a,/,3(12x,3(f12.4,1x)/))') '<< CONST isotropic >> Tstar (dev) / MPa', &
|
||||||
transpose(Mp_dev)*1.0e-6_pReal
|
transpose(Mp_dev)*1.0e-6_pReal
|
||||||
write(6,'(/,a,/,f12.5)') '<< CONST isotropic >> norm Tstar / MPa', norm_Mp_dev*1.0e-6_pReal
|
write(6,'(/,a,/,f12.5)') '<< CONST isotropic >> norm Tstar / MPa', norm_Mp_dev*1.0e-6_pReal
|
||||||
|
@ -238,8 +237,7 @@ module subroutine plastic_isotropic_LiAndItsTangent(Li,dLi_dMi,Mi,instance,of)
|
||||||
* tr * abs(tr)**(prm%n-1.0_pReal)
|
* tr * abs(tr)**(prm%n-1.0_pReal)
|
||||||
|
|
||||||
#ifdef DEBUG
|
#ifdef DEBUG
|
||||||
if (debugConstitutive%extensive &
|
if (debugConstitutive%extensive .and. (of == prm%of_debug .or. .not. debugConstitutive%selective)) then
|
||||||
.and. (of == prm%of_debug .or. .not. debugConstitutive%selective)) then
|
|
||||||
write(6,'(/,a,/,f12.5)') '<< CONST isotropic >> pressure / MPa', tr/3.0_pReal*1.0e-6_pReal
|
write(6,'(/,a,/,f12.5)') '<< CONST isotropic >> pressure / MPa', tr/3.0_pReal*1.0e-6_pReal
|
||||||
write(6,'(/,a,/,f12.5)') '<< CONST isotropic >> gdot', prm%dot_gamma_0 * (3.0_pReal*prm%M*stt%xi(of))**(-prm%n) &
|
write(6,'(/,a,/,f12.5)') '<< CONST isotropic >> gdot', prm%dot_gamma_0 * (3.0_pReal*prm%M*stt%xi(of))**(-prm%n) &
|
||||||
* tr * abs(tr)**(prm%n-1.0_pReal)
|
* tr * abs(tr)**(prm%n-1.0_pReal)
|
||||||
|
|
|
@ -328,8 +328,7 @@ module subroutine plastic_kinehardening_deltaState(Mp,instance,of)
|
||||||
|
|
||||||
#ifdef DEBUG
|
#ifdef DEBUG
|
||||||
if (debugConstitutive%extensive &
|
if (debugConstitutive%extensive &
|
||||||
.and. (of == prm%of_debug &
|
.and. (of == prm%of_debug .or. .not. debugConstitutive%selective)) then
|
||||||
.or. .not. debugConstitutive%selective)) then
|
|
||||||
write(6,'(a)') '======= kinehardening delta state ======='
|
write(6,'(a)') '======= kinehardening delta state ======='
|
||||||
write(6,*) sense,state(instance)%sense(:,of)
|
write(6,*) sense,state(instance)%sense(:,of)
|
||||||
endif
|
endif
|
||||||
|
|
|
@ -111,7 +111,6 @@ module crystallite
|
||||||
|
|
||||||
type(tDebugOptions) :: debugCrystallite
|
type(tDebugOptions) :: debugCrystallite
|
||||||
|
|
||||||
|
|
||||||
procedure(integrateStateFPI), pointer :: integrateState
|
procedure(integrateStateFPI), pointer :: integrateState
|
||||||
|
|
||||||
public :: &
|
public :: &
|
||||||
|
@ -143,7 +142,7 @@ subroutine crystallite_init
|
||||||
eMax, & !< maximum number of elements
|
eMax, & !< maximum number of elements
|
||||||
myNcomponents !< number of components at current IP
|
myNcomponents !< number of components at current IP
|
||||||
|
|
||||||
class(tNode) , pointer :: &
|
class(tNode), pointer :: &
|
||||||
num_crystallite, &
|
num_crystallite, &
|
||||||
debug_crystallite ! pointer to debug options for crystallite
|
debug_crystallite ! pointer to debug options for crystallite
|
||||||
|
|
||||||
|
|
|
@ -537,7 +537,6 @@ subroutine formResidual(in, FandF_tau, &
|
||||||
integer :: &
|
integer :: &
|
||||||
i, j, k, e
|
i, j, k, e
|
||||||
|
|
||||||
|
|
||||||
!---------------------------------------------------------------------------------------------------
|
!---------------------------------------------------------------------------------------------------
|
||||||
|
|
||||||
F => FandF_tau(1:3,1:3,1,&
|
F => FandF_tau(1:3,1:3,1,&
|
||||||
|
|
|
@ -188,9 +188,9 @@ subroutine spectral_utilities_init
|
||||||
scalarSize = 1_C_INTPTR_T, &
|
scalarSize = 1_C_INTPTR_T, &
|
||||||
vecSize = 3_C_INTPTR_T, &
|
vecSize = 3_C_INTPTR_T, &
|
||||||
tensorSize = 9_C_INTPTR_T
|
tensorSize = 9_C_INTPTR_T
|
||||||
character(len=pStringLen) :: &
|
character(len=*), parameter :: &
|
||||||
PETSCDEBUG = ' -snes_view -snes_monitor '
|
PETSCDEBUG = ' -snes_view -snes_monitor '
|
||||||
class (tNode) , pointer :: &
|
class(tNode) , pointer :: &
|
||||||
num_grid, &
|
num_grid, &
|
||||||
debug_grid ! pointer to grid debug options
|
debug_grid ! pointer to grid debug options
|
||||||
|
|
||||||
|
|
|
@ -79,6 +79,7 @@ module subroutine mech_RGC_init(num_homogMech)
|
||||||
|
|
||||||
class(tNode), pointer, intent(in) :: &
|
class(tNode), pointer, intent(in) :: &
|
||||||
num_homogMech !< pointer to mechanical homogenization numerics data
|
num_homogMech !< pointer to mechanical homogenization numerics data
|
||||||
|
|
||||||
integer :: &
|
integer :: &
|
||||||
Ninstance, &
|
Ninstance, &
|
||||||
h, &
|
h, &
|
||||||
|
|
|
@ -9,7 +9,7 @@ submodule(homogenization) homogenization_mech_none
|
||||||
contains
|
contains
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief allocates all neccessary fields, reads information from material configuration file
|
!> @brief allocates all necessary fields, reads information from material configuration file
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
module subroutine mech_none_init
|
module subroutine mech_none_init
|
||||||
|
|
||||||
|
|
|
@ -86,7 +86,6 @@ subroutine discretization_marc_init
|
||||||
mesh_unitlength = num_commercialFEM%get_asFloat('unitlength',defaultVal=1.0_pReal) ! set physical extent of a length unit in mesh
|
mesh_unitlength = num_commercialFEM%get_asFloat('unitlength',defaultVal=1.0_pReal) ! set physical extent of a length unit in mesh
|
||||||
if (mesh_unitlength <= 0.0_pReal) call IO_error(301,ext_msg='unitlength')
|
if (mesh_unitlength <= 0.0_pReal) call IO_error(301,ext_msg='unitlength')
|
||||||
|
|
||||||
|
|
||||||
call inputRead(elem,node0_elem,connectivity_elem,microstructureAt,homogenizationAt)
|
call inputRead(elem,node0_elem,connectivity_elem,microstructureAt,homogenizationAt)
|
||||||
nElems = size(connectivity_elem,2)
|
nElems = size(connectivity_elem,2)
|
||||||
|
|
||||||
|
|
|
@ -107,7 +107,7 @@ subroutine FEM_utilities_init
|
||||||
num_mesh, &
|
num_mesh, &
|
||||||
debug_mesh ! pointer to mesh debug options
|
debug_mesh ! pointer to mesh debug options
|
||||||
integer :: structOrder !< order of displacement shape functions
|
integer :: structOrder !< order of displacement shape functions
|
||||||
character(len=pStringLen) :: &
|
character(len=*), parameter :: &
|
||||||
PETSCDEBUG = ' -snes_view -snes_monitor '
|
PETSCDEBUG = ' -snes_view -snes_monitor '
|
||||||
|
|
||||||
PetscErrorCode :: ierr
|
PetscErrorCode :: ierr
|
||||||
|
|
|
@ -7,7 +7,6 @@
|
||||||
module source_damage_isoDuctile
|
module source_damage_isoDuctile
|
||||||
use prec
|
use prec
|
||||||
use IO
|
use IO
|
||||||
use YAML_types
|
|
||||||
use discretization
|
use discretization
|
||||||
use material
|
use material
|
||||||
use config
|
use config
|
||||||
|
|
|
@ -6,7 +6,6 @@
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
module source_thermal_dissipation
|
module source_thermal_dissipation
|
||||||
use prec
|
use prec
|
||||||
use YAML_types
|
|
||||||
use discretization
|
use discretization
|
||||||
use material
|
use material
|
||||||
use config
|
use config
|
||||||
|
|
|
@ -6,7 +6,6 @@
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
module source_thermal_externalheat
|
module source_thermal_externalheat
|
||||||
use prec
|
use prec
|
||||||
use YAML_types
|
|
||||||
use discretization
|
use discretization
|
||||||
use material
|
use material
|
||||||
use config
|
use config
|
||||||
|
|
Loading…
Reference in New Issue