Merge branch 'development' into 38-introduce-rudimentary-PETSc-based-FEM-solver

This commit is contained in:
Martin Diehl 2018-08-20 09:09:15 +02:00
commit 543c49426f
13 changed files with 35 additions and 46 deletions

@ -1 +1 @@
Subproject commit 737427a967e098e1cc82f69f5447fd1a02ffa855 Subproject commit c4471725893e301044924eb0990e2ad619aa0a46

View File

@ -1 +1 @@
v2.0.2-374-g3e4f6598 v2.0.2-381-gc03ea8f5

4
env/DAMASK.csh vendored
View File

@ -19,7 +19,9 @@ if ( "x$DAMASK_NUM_THREADS" == "x" ) then
endif endif
# currently, there is no information that unlimited causes problems # currently, there is no information that unlimited causes problems
# still, http://software.intel.com/en-us/forums/topic/501500 suggest to fix it # still, http://software.intel.com/en-us/forums/topic/501500 suggest to fix it
# more info https://jblevins.org/log/segfault
# https://stackoverflow.com/questions/79923/what-and-where-are-the-stack-and-heap
# http://superuser.com/questions/220059/what-parameters-has-ulimit # http://superuser.com/questions/220059/what-parameters-has-ulimit
limit datasize unlimited # maximum heap size (kB) limit datasize unlimited # maximum heap size (kB)
limit stacksize unlimited # maximum stack size (kB) limit stacksize unlimited # maximum stack size (kB)

4
env/DAMASK.sh vendored
View File

@ -42,7 +42,9 @@ PROCESSING=$(type -p postResults || true 2>/dev/null)
[ "x$DAMASK_NUM_THREADS" == "x" ] && DAMASK_NUM_THREADS=1 [ "x$DAMASK_NUM_THREADS" == "x" ] && DAMASK_NUM_THREADS=1
# currently, there is no information that unlimited causes problems # currently, there is no information that unlimited causes problems
# still, http://software.intel.com/en-us/forums/topic/501500 suggest to fix it # still, http://software.intel.com/en-us/forums/topic/501500 suggest to fix it
# more info https://jblevins.org/log/segfault
# https://stackoverflow.com/questions/79923/what-and-where-are-the-stack-and-heap
# http://superuser.com/questions/220059/what-parameters-has-ulimit # http://superuser.com/questions/220059/what-parameters-has-ulimit
ulimit -d unlimited 2>/dev/null # maximum heap size (kB) ulimit -d unlimited 2>/dev/null # maximum heap size (kB)
ulimit -s unlimited 2>/dev/null # maximum stack size (kB) ulimit -s unlimited 2>/dev/null # maximum stack size (kB)

4
env/DAMASK.zsh vendored
View File

@ -33,7 +33,9 @@ PROCESSING=$(which postResults || true 2>/dev/null)
[ "x$DAMASK_NUM_THREADS" = "x" ] && DAMASK_NUM_THREADS=1 [ "x$DAMASK_NUM_THREADS" = "x" ] && DAMASK_NUM_THREADS=1
# currently, there is no information that unlimited causes problems # currently, there is no information that unlimited causes problems
# still, http://software.intel.com/en-us/forums/topic/501500 suggest to fix it # still, http://software.intel.com/en-us/forums/topic/501500 suggest to fix it
# more info https://jblevins.org/log/segfault
# https://stackoverflow.com/questions/79923/what-and-where-are-the-stack-and-heap
# http://superuser.com/questions/220059/what-parameters-has-ulimit # http://superuser.com/questions/220059/what-parameters-has-ulimit
ulimit -d unlimited 2>/dev/null # maximum heap size (kB) ulimit -d unlimited 2>/dev/null # maximum heap size (kB)
ulimit -s unlimited 2>/dev/null # maximum stack size (kB) ulimit -s unlimited 2>/dev/null # maximum stack size (kB)

View File

@ -38,7 +38,7 @@ plasticity none
[Ti matrix] [Ti matrix]
lattice_structure hex lattice_structure hex
covera_ratio 1.587 c/a 1.587
plasticity none plasticity none
{config/elastic_Ti.config} {config/elastic_Ti.config}
{config/thermal.config} {config/thermal.config}
@ -65,7 +65,7 @@ plasticity none
[Ti inclusion] [Ti inclusion]
lattice_structure hex lattice_structure hex
covera_ratio 1.587 c/a 1.587
plasticity none plasticity none
{config/elastic_Ti.config} {config/elastic_Ti.config}
{config/thermal.config} {config/thermal.config}

View File

@ -864,19 +864,11 @@ subroutine constitutive_collectDotState(Tstar_v, FeArray, FpArray, subdt, subfra
FpArray !< plastic deformation gradient FpArray !< plastic deformation gradient
real(pReal), intent(in), dimension(6) :: & real(pReal), intent(in), dimension(6) :: &
Tstar_v !< 2nd Piola Kirchhoff stress tensor (Mandel) Tstar_v !< 2nd Piola Kirchhoff stress tensor (Mandel)
integer(pLongInt) :: &
tick = 0_pLongInt, &
tock = 0_pLongInt, &
tickrate, &
maxticks
integer(pInt) :: & integer(pInt) :: &
ho, & !< homogenization ho, & !< homogenization
tme, & !< thermal member position tme, & !< thermal member position
s !< counter in source loop s !< counter in source loop
if (iand(debug_level(debug_constitutive), debug_levelBasic) /= 0_pInt) &
call system_clock(count=tick,count_rate=tickrate,count_max=maxticks)
ho = material_homog( ip,el) ho = material_homog( ip,el)
tme = thermalMapping(ho)%p(ip,el) tme = thermalMapping(ho)%p(ip,el)
@ -957,13 +949,6 @@ subroutine constitutive_collectDeltaState(Tstar_v, Fe, ipc, ip, el)
Fe !< elastic deformation gradient Fe !< elastic deformation gradient
integer(pInt) :: & integer(pInt) :: &
s !< counter in source loop s !< counter in source loop
integer(pLongInt) :: &
tick, tock, &
tickrate, &
maxticks
if (iand(debug_level(debug_constitutive), debug_levelBasic) /= 0_pInt) &
call system_clock(count=tick,count_rate=tickrate,count_max=maxticks)
plasticityType: select case (phase_plasticity(material_phase(ipc,ip,el))) plasticityType: select case (phase_plasticity(material_phase(ipc,ip,el)))
case (PLASTICITY_KINEHARDENING_ID) plasticityType case (PLASTICITY_KINEHARDENING_ID) plasticityType

View File

@ -1396,6 +1396,7 @@ subroutine lattice_init
lattice_C66(1,1,p) = config_phase(p)%getFloat('c11',defaultVal=0.0_pReal) lattice_C66(1,1,p) = config_phase(p)%getFloat('c11',defaultVal=0.0_pReal)
lattice_C66(1,2,p) = config_phase(p)%getFloat('c12',defaultVal=0.0_pReal) lattice_C66(1,2,p) = config_phase(p)%getFloat('c12',defaultVal=0.0_pReal)
lattice_C66(1,3,p) = config_phase(p)%getFloat('c13',defaultVal=0.0_pReal) lattice_C66(1,3,p) = config_phase(p)%getFloat('c13',defaultVal=0.0_pReal)
lattice_C66(2,2,p) = config_phase(p)%getFloat('c22',defaultVal=0.0_pReal)
lattice_C66(2,3,p) = config_phase(p)%getFloat('c23',defaultVal=0.0_pReal) lattice_C66(2,3,p) = config_phase(p)%getFloat('c23',defaultVal=0.0_pReal)
lattice_C66(3,3,p) = config_phase(p)%getFloat('c33',defaultVal=0.0_pReal) lattice_C66(3,3,p) = config_phase(p)%getFloat('c33',defaultVal=0.0_pReal)
lattice_C66(4,4,p) = config_phase(p)%getFloat('c44',defaultVal=0.0_pReal) lattice_C66(4,4,p) = config_phase(p)%getFloat('c44',defaultVal=0.0_pReal)

View File

@ -16,8 +16,8 @@ module material
tSourceState, & tSourceState, &
tHomogMapping, & tHomogMapping, &
tPhaseMapping, & tPhaseMapping, &
p_vec, & group_scalar, &
p_intvec group_int
implicit none implicit none
private private
@ -268,7 +268,7 @@ module material
porosityMapping, & !< mapping for porosity state/fields porosityMapping, & !< mapping for porosity state/fields
hydrogenfluxMapping !< mapping for hydrogen conc state/fields hydrogenfluxMapping !< mapping for hydrogen conc state/fields
type(p_vec), allocatable, dimension(:), public :: & type(group_scalar), allocatable, dimension(:), public :: &
temperature, & !< temperature field temperature, & !< temperature field
damage, & !< damage field damage, & !< damage field
vacancyConc, & !< vacancy conc field vacancyConc, & !< vacancy conc field
@ -1120,8 +1120,8 @@ subroutine material_populateGrains
phaseID,textureID,dGrains,myNgrains,myNorientations,myNconstituents, & phaseID,textureID,dGrains,myNgrains,myNorientations,myNconstituents, &
grain,constituentGrain,ipGrain,symExtension, ip grain,constituentGrain,ipGrain,symExtension, ip
real(pReal) :: deviation,extreme,rnd real(pReal) :: deviation,extreme,rnd
integer(pInt), dimension (:,:), allocatable :: Nelems ! counts number of elements in homog, micro array integer(pInt), dimension (:,:), allocatable :: Nelems ! counts number of elements in homog, micro array
type(p_intvec), dimension (:,:), allocatable :: elemsOfHomogMicro ! lists element number in homog, micro array type(group_int), dimension (:,:), allocatable :: elemsOfHomogMicro ! lists element number in homog, micro array
myDebug = debug_level(debug_material) myDebug = debug_level(debug_material)

View File

@ -28,21 +28,21 @@ module prec
integer(pInt), allocatable, dimension(:) :: realloc_lhs_test integer(pInt), allocatable, dimension(:) :: realloc_lhs_test
type, public :: p_vec !< variable length datatype used for storage of state type, public :: group_scalar !< variable length datatype used for storage of state
real(pReal), dimension(:), pointer :: p real(pReal), dimension(:), pointer :: p
end type p_vec end type group_scalar
type, public :: p_intvec type, public :: group_int
integer(pInt), dimension(:), pointer :: p integer(pInt), dimension(:), pointer :: p
end type p_intvec end type group_int
!http://stackoverflow.com/questions/3948210/can-i-have-a-pointer-to-an-item-in-an-allocatable-array !http://stackoverflow.com/questions/3948210/can-i-have-a-pointer-to-an-item-in-an-allocatable-array
type, public :: tState type, public :: tState
integer(pInt) :: & integer(pInt) :: &
sizeState = 0_pInt, & !< size of state sizeState = 0_pInt, & !< size of state
sizeDotState = 0_pInt, & !< size of dot state, i.e. state(1:sizeDot) follows time evolution by dotState rates sizeDotState = 0_pInt, & !< size of dot state, i.e. state(1:sizeDot) follows time evolution by dotState rates
offsetDeltaState = 0_pInt, & !< offset of delta state offsetDeltaState = 0_pInt, & !< index offset of delta state
sizeDeltaState = 0_pInt, & !< size of delta state, i.e. state(offset+1:offset+sizeDot) follows time evolution by deltaState increments sizeDeltaState = 0_pInt, & !< size of delta state, i.e. state(offset+1:offset+sizeDelta) follows time evolution by deltaState increments
sizePostResults = 0_pInt !< size of output data sizePostResults = 0_pInt !< size of output data
real(pReal), pointer, dimension(:), contiguous :: & real(pReal), pointer, dimension(:), contiguous :: &
atolState atolState
@ -146,7 +146,7 @@ logical elemental pure function dEq(a,b,tol)
real(pReal), intent(in), optional :: tol real(pReal), intent(in), optional :: tol
real(pReal), parameter :: eps = 2.220446049250313E-16 ! DBL_EPSILON in C real(pReal), parameter :: eps = 2.220446049250313E-16 ! DBL_EPSILON in C
dEq = merge(.True., .False.,abs(a-b) <= merge(tol,eps,present(tol))*maxval(abs([a,b]))) dEq = merge(.True.,.False.,abs(a-b) <= merge(tol,eps,present(tol))*maxval(abs([a,b])))
end function dEq end function dEq
@ -163,7 +163,7 @@ logical elemental pure function dNeq(a,b,tol)
real(pReal), intent(in), optional :: tol real(pReal), intent(in), optional :: tol
real(pReal), parameter :: eps = 2.220446049250313E-16 ! DBL_EPSILON in C real(pReal), parameter :: eps = 2.220446049250313E-16 ! DBL_EPSILON in C
dNeq = merge(.False., .True.,abs(a-b) <= merge(tol,eps,present(tol))*maxval(abs([a,b]))) dNeq = merge(.False.,.True.,abs(a-b) <= merge(tol,eps,present(tol))*maxval(abs([a,b])))
end function dNeq end function dNeq
@ -180,7 +180,7 @@ logical elemental pure function dEq0(a,tol)
real(pReal), intent(in), optional :: tol real(pReal), intent(in), optional :: tol
real(pReal), parameter :: eps = 2.2250738585072014E-308 ! smallest non-denormalized number real(pReal), parameter :: eps = 2.2250738585072014E-308 ! smallest non-denormalized number
dEq0 = merge(.True., .False.,abs(a) <= merge(tol,eps,present(tol))) dEq0 = merge(.True.,.False.,abs(a) <= merge(tol,eps,present(tol)))
end function dEq0 end function dEq0
@ -197,7 +197,7 @@ logical elemental pure function dNeq0(a,tol)
real(pReal), intent(in), optional :: tol real(pReal), intent(in), optional :: tol
real(pReal), parameter :: eps = 2.2250738585072014E-308 ! smallest non-denormalized number real(pReal), parameter :: eps = 2.2250738585072014E-308 ! smallest non-denormalized number
dNeq0 = merge(.False., .True.,abs(a) <= merge(tol,eps,present(tol))) dNeq0 = merge(.False.,.True.,abs(a) <= merge(tol,eps,present(tol)))
end function dNeq0 end function dNeq0
@ -215,7 +215,7 @@ logical elemental pure function cEq(a,b,tol)
real(pReal), intent(in), optional :: tol real(pReal), intent(in), optional :: tol
real(pReal), parameter :: eps = 2.220446049250313E-16 ! DBL_EPSILON in C real(pReal), parameter :: eps = 2.220446049250313E-16 ! DBL_EPSILON in C
cEq = merge(.True., .False.,abs(a-b) <= merge(tol,eps,present(tol))*maxval(abs([a,b]))) cEq = merge(.True.,.False.,abs(a-b) <= merge(tol,eps,present(tol))*maxval(abs([a,b])))
end function cEq end function cEq
@ -233,7 +233,7 @@ logical elemental pure function cNeq(a,b,tol)
real(pReal), intent(in), optional :: tol real(pReal), intent(in), optional :: tol
real(pReal), parameter :: eps = 2.220446049250313E-16 ! DBL_EPSILON in C real(pReal), parameter :: eps = 2.220446049250313E-16 ! DBL_EPSILON in C
cNeq = merge(.False., .True.,abs(a-b) <= merge(tol,eps,present(tol))*maxval(abs([a,b]))) cNeq = merge(.False.,.True.,abs(a-b) <= merge(tol,eps,present(tol))*maxval(abs([a,b])))
end function cNeq end function cNeq
end module prec end module prec

View File

@ -4,9 +4,8 @@
!> @brief Interfacing between the spectral solver and the material subroutines provided !> @brief Interfacing between the spectral solver and the material subroutines provided
!! by DAMASK !! by DAMASK
!> @details Interfacing between the spectral solver and the material subroutines provided !> @details Interfacing between the spectral solver and the material subroutines provided
!> by DAMASK. Interpretating the command line arguments or, in case of called from f2py, !> by DAMASK. Interpretating the command line arguments to get load case, geometry file,
!> the arguments parsed to the init routine to get load case, geometry file, working !> and working directory.
!> directory, etc.
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
module DAMASK_interface module DAMASK_interface
use prec, only: & use prec, only: &

View File

@ -65,8 +65,6 @@ subroutine spectral_thermal_init
compiler_options compiler_options
#endif #endif
use IO, only: & use IO, only: &
IO_intOut, &
IO_read_realFile, &
IO_timeStamp IO_timeStamp
use spectral_utilities, only: & use spectral_utilities, only: &
wgt wgt

View File

@ -7,7 +7,7 @@ module vacancyflux_cahnhilliard
use prec, only: & use prec, only: &
pReal, & pReal, &
pInt, & pInt, &
p_vec group_scalar
implicit none implicit none
private private
@ -26,7 +26,7 @@ module vacancyflux_cahnhilliard
real(pReal), dimension(:), allocatable, private :: & real(pReal), dimension(:), allocatable, private :: &
vacancyflux_cahnhilliard_flucAmplitude vacancyflux_cahnhilliard_flucAmplitude
type(p_vec), dimension(:), allocatable, private :: & type(group_scalar), dimension(:), allocatable, private :: &
vacancyflux_cahnhilliard_thermalFluc vacancyflux_cahnhilliard_thermalFluc
real(pReal), parameter, private :: & real(pReal), parameter, private :: &