This commit is contained in:
Martin Diehl 2021-05-23 00:10:46 +02:00
parent af9fa9e9a1
commit 72ab936ec3
7 changed files with 21 additions and 29 deletions

View File

@ -92,7 +92,7 @@ end subroutine parse_debug
!--------------------------------------------------------------------------------------------------
!> @brief Deallocate config_material.
!ToDo: deallocation of numerics debug (optional)
!ToDo: deallocation of numerics and debug (optional)
!--------------------------------------------------------------------------------------------------
subroutine config_deallocate

View File

@ -32,18 +32,15 @@ module material
material_name_homogenization !< name of each homogenization
integer, dimension(:), allocatable, public, protected :: & ! (elem)
material_homogenizationAt, & !< homogenization ID of each element
material_homogenizationID, & !< per cell
material_homogenizationEntry !< per cell
integer, dimension(:,:), allocatable :: & ! (ip,elem)
material_homogenizationMemberAt !< position of the element within its homogenization instance
material_homogenizationAt, & !< homogenization ID of each element TODO: remove
material_homogenizationID, & !< per cell TODO: material_ID_homogenization
material_homogenizationEntry !< per cell TODO: material_entry_homogenization
integer, dimension(:,:), allocatable, public, protected :: & ! (constituent,elem)
material_phaseAt, & !< phase ID of each element
material_phaseID, & !< per (constituent,cell)
material_phaseEntry !< per (constituent,cell)
material_phaseAt, & !< phase ID of each element TODO: remove
material_phaseID, & !< per (constituent,cell) TODO: material_ID_phase
material_phaseEntry !< per (constituent,cell) TODO: material_entry_phase
integer, dimension(:,:,:), allocatable, public, protected :: & ! (constituent,IP,elem)
material_phaseMemberAt !< position of the element within its phase instance
material_phaseMemberAt !TODO: remove
public :: &
tRotationContainer, &
material_orientation0, &
@ -118,7 +115,6 @@ subroutine parse()
allocate(counterHomogenization(homogenizations%length),source=0)
allocate(material_homogenizationAt(discretization_Nelems),source=0)
allocate(material_homogenizationMemberAt(discretization_nIPs,discretization_Nelems),source=0)
allocate(material_phaseAt(homogenization_maxNconstituents,discretization_Nelems),source=0)
allocate(material_phaseMemberAt(homogenization_maxNconstituents,discretization_nIPs,discretization_Nelems),source=0)
@ -136,9 +132,8 @@ subroutine parse()
do ip = 1, discretization_nIPs
ce = (el-1)*discretization_nIPs + ip
counterHomogenization(material_homogenizationAt(el)) = counterHomogenization(material_homogenizationAt(el)) + 1
material_homogenizationMemberAt(ip,el) = counterHomogenization(material_homogenizationAt(el))
material_homogenizationID(ce) = material_homogenizationAt(el)
material_homogenizationEntry(ce) = material_homogenizationMemberAt(ip,el)
material_homogenizationEntry(ce) = counterHomogenization(material_homogenizationAt(el))
material_homogenizationID(ce) = material_homogenizationAt(el)
enddo
frac = 0.0_pReal
@ -150,10 +145,9 @@ subroutine parse()
do ip = 1, discretization_nIPs
ce = (el-1)*discretization_nIPs + ip
counterPhase(material_phaseAt(co,el)) = counterPhase(material_phaseAt(co,el)) + 1
material_phaseMemberAt(co,ip,el) = counterPhase(material_phaseAt(co,el))
material_phaseID(co,ce) = material_phaseAt(co,el)
material_phaseEntry(co,ce) = material_phaseMemberAt(co,ip,el)
material_phaseMemberAt(co,ip,el) = counterPhase(material_phaseAt(co,el))
material_phaseEntry(co,ce) = counterPhase(material_phaseAt(co,el))
material_phaseID(co,ce) = material_phaseAt(co,el)
enddo
enddo

View File

@ -1140,8 +1140,7 @@ end function math_areaTriangle
!--------------------------------------------------------------------------------------------------
!> @brief limits a scalar value to a certain range (either one or two sided)
! Will return NaN if left > right
!> @brief Limit a scalar value to a certain range (either one or two sided).
!--------------------------------------------------------------------------------------------------
real(pReal) pure elemental function math_clip(a, left, right)

View File

@ -27,7 +27,7 @@ module parallelization
contains
!--------------------------------------------------------------------------------------------------
!> @brief calls subroutines that reads material, numerics and debug configuration files
!> @brief Initialize shared memory (openMP) and distributed memory (MPI) parallelization.
!--------------------------------------------------------------------------------------------------
subroutine parallelization_init
@ -42,8 +42,8 @@ subroutine parallelization_init
! If openMP is enabled, check if the MPI libary supports it and initialize accordingly.
! Otherwise, the first call to PETSc will do the initialization.
call MPI_Init_Thread(MPI_THREAD_FUNNELED,threadLevel,err)
if (err /= 0) error stop 'MPI init failed'
if (threadLevel<MPI_THREAD_FUNNELED) error stop 'MPI library does not support OpenMP'
if (err /= 0) error stop 'MPI init failed'
if (threadLevel<MPI_THREAD_FUNNELED) error stop 'MPI library does not support OpenMP'
#endif
#if defined(DEBUG)

View File

@ -564,8 +564,8 @@ subroutine crystallite_init()
!$OMP PARALLEL DO
do el = 1, size(material_phaseMemberAt,3)
do ip = 1, size(material_phaseMemberAt,2)
do el = 1, eMax
do ip = 1, iMax
do co = 1,homogenization_Nconstituents(material_homogenizationAt(el))
call crystallite_orientations(co,ip,el)
call plastic_dependentState(co,ip,el) ! update dependent state variables to be consistent with basic states

View File

@ -78,7 +78,7 @@ contains
!--------------------------------------------------------------------------------------------------
!> @brief report precision and do self test
!> @brief Report precision and do self test.
!--------------------------------------------------------------------------------------------------
subroutine prec_init

View File

@ -423,7 +423,7 @@ subroutine results_mapping_phase(ID,entry,label)
integer, dimension(size(entry,1),size(entry,2)) :: &
entryGlobal
integer, dimension(size(label),0:worldsize-1) :: entryOffset !< offset in entry counting per process
integer, dimension(size(label),0:worldsize-1) :: entryOffset !< offset in entry counting per process
integer, dimension(0:worldsize-1) :: writeSize !< amount of data written per process
integer(HSIZE_T), dimension(2) :: &
myShape, & !< shape of the dataset (this process)
@ -718,7 +718,6 @@ end subroutine results_mapping_homogenization
!--------------------------------------------------------------------------------------------------
subroutine executionStamp(path,description,SIunit)
character(len=*), intent(in) :: path,description
character(len=*), intent(in), optional :: SIunit