This commit is contained in:
Sharan Roongta 2020-06-18 18:14:53 +02:00
parent eb71c1033d
commit 0cf06a77d4
9 changed files with 34 additions and 14 deletions

View File

@ -4,7 +4,6 @@
!> @details Reads the material configuration file, where solverJobName.materialConfig takes !> @details Reads the material configuration file, where solverJobName.materialConfig takes
!! precedence over material.config. Stores the raw strings and the positions of delimiters for the !! precedence over material.config. Stores the raw strings and the positions of delimiters for the
!! parts 'homogenization', 'crystallite', 'phase', 'texture', and 'microstucture' !! parts 'homogenization', 'crystallite', 'phase', 'texture', and 'microstucture'
!! Reads numerics.config and debug.config
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
module config module config
use prec use prec
@ -50,11 +49,14 @@ subroutine config_init
line, & line, &
part part
character(len=pStringLen), dimension(:), allocatable :: fileContent character(len=pStringLen), dimension(:), allocatable :: fileContent
class(tNode), pointer :: &
debug_material
logical :: fileExists logical :: fileExists
write(6,'(/,a)') ' <<<+- config init -+>>>'; flush(6) write(6,'(/,a)') ' <<<+- config init -+>>>'; flush(6)
verbose = iand(debug_level(debug_material),debug_levelBasic) /= 0 debug_material => debug_root%get('material',defaultVal=emptyList)
verbose = debug_material%contains('basic')
inquire(file=trim(getSolverJobName())//'.materialConfig',exist=fileExists) inquire(file=trim(getSolverJobName())//'.materialConfig',exist=fileExists)
if(fileExists) then if(fileExists) then

View File

@ -17,10 +17,6 @@ module debug
class(tNode), pointer, public :: & class(tNode), pointer, public :: &
debug_root debug_root
#ifdef PETSc
character(len=1024), parameter, public :: &
PETSCDEBUG = ' -snes_view -snes_monitor '
#endif
public :: debug_init public :: debug_init
contains contains

View File

@ -190,7 +190,8 @@ subroutine spectral_utilities_init
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=pStringLen) :: &
petsc_options petsc_options, &
PETSCDEBUG = ' -snes_view -snes_monitor '
class (tNode) , pointer :: & class (tNode) , pointer :: &
num_grid, & num_grid, &
num_generic, & num_generic, &

View File

@ -491,6 +491,10 @@ subroutine partitionDeformation(subF,ip,el)
integer, intent(in) :: & integer, intent(in) :: &
ip, & !< integration point ip, & !< integration point
el !< element number el !< element number
class(tNode), pointer :: &
debug_homogenization
debug_homogenization => debug_root%get('homogenization',defaultVal=emptyList)
chosenHomogenization: select case(homogenization_type(material_homogenizationAt(el))) chosenHomogenization: select case(homogenization_type(material_homogenizationAt(el)))
@ -507,7 +511,7 @@ subroutine partitionDeformation(subF,ip,el)
crystallite_partionedF(1:3,1:3,1:homogenization_Ngrains(material_homogenizationAt(el)),ip,el), & crystallite_partionedF(1:3,1:3,1:homogenization_Ngrains(material_homogenizationAt(el)),ip,el), &
subF,& subF,&
ip, & ip, &
el) el,debug_homogenization)
end select chosenHomogenization end select chosenHomogenization
end subroutine partitionDeformation end subroutine partitionDeformation
@ -527,6 +531,10 @@ function updateState(subdt,subF,ip,el)
ip, & !< integration point ip, & !< integration point
el !< element number el !< element number
logical, dimension(2) :: updateState logical, dimension(2) :: updateState
class(tNode), pointer :: &
debug_homogenization
debug_homogenization => debug_root%get('homogenization',defaultVal=emptyList)
updateState = .true. updateState = .true.
chosenHomogenization: select case(homogenization_type(material_homogenizationAt(el))) chosenHomogenization: select case(homogenization_type(material_homogenizationAt(el)))
@ -540,7 +548,7 @@ function updateState(subdt,subF,ip,el)
subdt, & subdt, &
crystallite_dPdF(1:3,1:3,1:3,1:3,1:homogenization_Ngrains(material_homogenizationAt(el)),ip,el), & crystallite_dPdF(1:3,1:3,1:3,1:3,1:homogenization_Ngrains(material_homogenizationAt(el)),ip,el), &
ip, & ip, &
el) el,debug_homogenization)
end select chosenHomogenization end select chosenHomogenization
chosenThermal: select case (thermal_type(material_homogenizationAt(el))) chosenThermal: select case (thermal_type(material_homogenizationAt(el)))

View File

@ -58,7 +58,8 @@ subroutine discretization_marc_init
homogenizationAt homogenizationAt
integer:: & integer:: &
Nnodes, & !< total number of nodes in the mesh Nnodes, & !< total number of nodes in the mesh
Nelems !< total number of elements in the mesh Nelems, & !< total number of elements in the mesh
debug_e, debug_i
real(pReal), dimension(:,:), allocatable :: & real(pReal), dimension(:,:), allocatable :: &
IP_reshaped IP_reshaped
@ -74,10 +75,18 @@ subroutine discretization_marc_init
write(6,'(/,a)') ' <<<+- discretization_marc init -+>>>'; flush(6) write(6,'(/,a)') ' <<<+- discretization_marc init -+>>>'; flush(6)
!---------------------------------------------------------------------------------
! read debug parameters
debug_e = debug_root%get_asInt('element',defaultVal=1)
debug_i = debug_root%get_asInt('integrationpoint',defaultVal=1)
!--------------------------------------------------------------------------------
! read numerics parameter and do sanity check
num_commercialFEM => numerics_root%get('commercialFEM',defaultVal = emptyDict) num_commercialFEM => numerics_root%get('commercialFEM',defaultVal = emptyDict)
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)

View File

@ -108,7 +108,8 @@ subroutine FEM_utilities_init
debug_mesh debug_mesh
integer :: structOrder !< order of displacement shape functions integer :: structOrder !< order of displacement shape functions
character(len=pStringLen) :: & character(len=pStringLen) :: &
petsc_options petsc_options, &
PETSCDEBUG = ' -snes_view -snes_monitor '
PetscErrorCode :: ierr PetscErrorCode :: ierr
write(6,'(/,a)') ' <<<+- DAMASK_FEM_utilities init -+>>>' write(6,'(/,a)') ' <<<+- DAMASK_FEM_utilities init -+>>>'

View File

@ -8,6 +8,7 @@ module source_damage_isoDuctile
use prec use prec
use debug use debug
use IO use IO
use YAML_types
use discretization use discretization
use material use material
use config use config

View File

@ -7,6 +7,7 @@
module source_thermal_dissipation module source_thermal_dissipation
use prec use prec
use debug use debug
use YAML_types
use discretization use discretization
use material use material
use config use config

View File

@ -7,6 +7,7 @@
module source_thermal_externalheat module source_thermal_externalheat
use prec use prec
use debug use debug
use YAML_types
use discretization use discretization
use material use material
use config use config