2012-06-15 21:40:21 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2013-04-18 22:10:49 +05:30
|
|
|
!> @author Franz Roters, Max-Planck-Institut für Eisenforschung GmbH
|
|
|
|
!> @author Philip Eisenlohr, Max-Planck-Institut für Eisenforschung GmbH
|
2019-10-31 01:39:17 +05:30
|
|
|
!> @author Christoph Kords, Max-Planck-Institut für Eisenforschung GmbH
|
2013-04-18 22:10:49 +05:30
|
|
|
!> @author Martin Diehl, Max-Planck-Institut für Eisenforschung GmbH
|
2019-01-28 19:06:44 +05:30
|
|
|
!> @brief Sets up the mesh for the solver MSC.Marc
|
2012-06-15 21:40:21 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2014-04-29 23:20:59 +05:30
|
|
|
module mesh
|
2019-06-13 04:09:35 +05:30
|
|
|
use IO
|
|
|
|
use prec
|
|
|
|
use math
|
|
|
|
use DAMASK_interface
|
|
|
|
use IO
|
|
|
|
use debug
|
|
|
|
use numerics
|
|
|
|
use FEsolving
|
|
|
|
use element
|
|
|
|
use discretization
|
|
|
|
use geometry_plastic_nonlocal
|
|
|
|
use results
|
|
|
|
|
|
|
|
implicit none
|
|
|
|
private
|
2019-10-13 15:49:37 +05:30
|
|
|
|
|
|
|
type tCellNodeDefinition
|
|
|
|
integer, dimension(:,:), allocatable :: parents
|
|
|
|
integer, dimension(:,:), allocatable :: weights
|
|
|
|
end type tCellNodeDefinition
|
|
|
|
|
2019-10-14 01:46:42 +05:30
|
|
|
type(tCellNodeDefinition), dimension(:), allocatable :: cellNodeDefinition
|
|
|
|
|
2019-06-13 04:09:35 +05:30
|
|
|
real(pReal), public, protected :: &
|
2019-10-14 00:04:20 +05:30
|
|
|
mesh_unitlength !< physical length of one unit in mesh
|
|
|
|
|
2020-01-31 04:03:33 +05:30
|
|
|
integer, dimension(:), allocatable, public :: &
|
|
|
|
mesh_FEM2DAMASK_elem, & !< DAMASK element ID for Marc element ID
|
|
|
|
mesh_FEM2DAMASK_node !< DAMASK node ID for Marc node ID
|
2012-03-09 01:55:28 +05:30
|
|
|
|
2020-01-27 03:06:32 +05:30
|
|
|
public :: &
|
2020-01-31 04:03:33 +05:30
|
|
|
mesh_init
|
2019-01-28 19:06:44 +05:30
|
|
|
|
2019-01-28 18:23:44 +05:30
|
|
|
contains
|
|
|
|
|
2012-06-15 21:40:21 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief initializes the mesh by calling all necessary private routines the mesh module
|
|
|
|
!! Order and routines strongly depend on type of solver
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2013-02-05 18:57:37 +05:30
|
|
|
subroutine mesh_init(ip,el)
|
2018-01-10 21:43:25 +05:30
|
|
|
|
2019-06-13 04:09:35 +05:30
|
|
|
integer, intent(in) :: el, ip
|
|
|
|
|
2019-10-15 17:46:03 +05:30
|
|
|
real(pReal), dimension(:,:), allocatable :: &
|
2020-01-27 02:26:08 +05:30
|
|
|
node0_elem, & !< node x,y,z coordinates (initially!)
|
2019-10-14 03:04:03 +05:30
|
|
|
node0_cell
|
2019-10-16 07:27:51 +05:30
|
|
|
type(tElement) :: elem
|
2019-10-13 01:28:26 +05:30
|
|
|
|
2019-10-15 17:46:03 +05:30
|
|
|
integer, dimension(:), allocatable :: &
|
|
|
|
microstructureAt, &
|
|
|
|
homogenizationAt
|
|
|
|
integer:: &
|
2020-02-01 13:34:02 +05:30
|
|
|
Nnodes, & !< total number of nodes in the mesh
|
|
|
|
Nelems !< total number of elements in the mesh
|
2019-10-12 18:33:26 +05:30
|
|
|
|
2019-10-15 17:46:03 +05:30
|
|
|
real(pReal), dimension(:,:), allocatable :: &
|
2020-01-27 03:06:32 +05:30
|
|
|
IP_reshaped
|
2019-10-14 01:46:42 +05:30
|
|
|
integer,dimension(:,:,:), allocatable :: &
|
2020-01-27 02:26:08 +05:30
|
|
|
connectivity_cell !< cell connectivity for each element,ip/cell
|
2019-10-15 17:46:03 +05:30
|
|
|
integer, dimension(:,:), allocatable :: &
|
|
|
|
connectivity_elem
|
2019-10-17 11:18:57 +05:30
|
|
|
real(pReal), dimension(:,:,:,:),allocatable :: &
|
|
|
|
unscaledNormals
|
2019-10-14 01:46:42 +05:30
|
|
|
|
2020-01-12 06:18:05 +05:30
|
|
|
write(6,'(/,a)') ' <<<+- mesh init -+>>>'; flush(6)
|
2019-02-03 15:42:23 +05:30
|
|
|
|
2019-10-16 08:03:26 +05:30
|
|
|
mesh_unitlength = numerics_unitlength ! set physical extent of a length unit in mesh
|
2019-10-17 03:51:48 +05:30
|
|
|
|
2019-10-16 08:03:26 +05:30
|
|
|
call inputRead(elem,node0_elem,connectivity_elem,microstructureAt,homogenizationAt)
|
|
|
|
nElems = size(connectivity_elem,2)
|
2019-10-15 17:46:03 +05:30
|
|
|
|
2019-10-17 03:51:48 +05:30
|
|
|
if (debug_e < 1 .or. debug_e > nElems) call IO_error(602,ext_msg='element')
|
|
|
|
if (debug_i < 1 .or. debug_i > elem%nIPs) call IO_error(602,ext_msg='IP')
|
|
|
|
|
2020-01-25 13:54:42 +05:30
|
|
|
FEsolving_execElem = [1,nElems]
|
|
|
|
FEsolving_execIP = [1,elem%nIPs]
|
2019-10-17 03:51:48 +05:30
|
|
|
|
|
|
|
allocate(calcMode(elem%nIPs,nElems),source=.false.) ! pretend to have collected what first call is asking (F = I)
|
2020-01-31 04:03:33 +05:30
|
|
|
calcMode(ip,mesh_FEM2DAMASK_elem(el)) = .true. ! first ip,el needs to be already pingponged to "calc"
|
2019-10-17 03:51:48 +05:30
|
|
|
|
|
|
|
|
2019-10-16 07:27:51 +05:30
|
|
|
allocate(cellNodeDefinition(elem%nNodes-1))
|
|
|
|
allocate(connectivity_cell(elem%NcellNodesPerCell,elem%nIPs,nElems))
|
2019-10-14 01:46:42 +05:30
|
|
|
call buildCells(connectivity_cell,cellNodeDefinition,&
|
2019-10-16 07:27:51 +05:30
|
|
|
elem,connectivity_elem)
|
2019-10-14 03:04:03 +05:30
|
|
|
allocate(node0_cell(3,maxval(connectivity_cell)))
|
|
|
|
call buildCellNodes(node0_cell,&
|
|
|
|
cellNodeDefinition,node0_elem)
|
2020-01-27 03:06:32 +05:30
|
|
|
allocate(IP_reshaped(3,elem%nIPs*nElems),source=0.0_pReal)
|
|
|
|
call buildIPcoordinates(IP_reshaped,reshape(connectivity_cell,[elem%NcellNodesPerCell,&
|
2019-10-17 03:51:48 +05:30
|
|
|
elem%nIPs*nElems]),node0_cell)
|
2019-10-15 17:46:03 +05:30
|
|
|
|
2019-10-08 13:00:32 +05:30
|
|
|
call discretization_init(microstructureAt,homogenizationAt,&
|
2020-01-27 03:06:32 +05:30
|
|
|
IP_reshaped,&
|
2020-01-12 23:02:20 +05:30
|
|
|
node0_cell)
|
2019-10-14 14:06:59 +05:30
|
|
|
|
2020-01-13 14:33:13 +05:30
|
|
|
call writeGeometry(elem,connectivity_elem,&
|
2019-10-17 03:51:48 +05:30
|
|
|
reshape(connectivity_cell,[elem%NcellNodesPerCell,elem%nIPs*nElems]),&
|
2020-01-27 03:06:32 +05:30
|
|
|
node0_cell,IP_reshaped)
|
2019-10-14 14:06:59 +05:30
|
|
|
|
2019-11-24 11:56:21 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! geometry information required by the nonlocal CP model
|
2019-10-17 01:30:25 +05:30
|
|
|
call geometry_plastic_nonlocal_setIPvolume(IPvolume(elem,node0_cell,connectivity_cell))
|
2019-10-17 11:18:57 +05:30
|
|
|
unscaledNormals = IPareaNormal(elem,nElems,connectivity_cell,node0_cell)
|
|
|
|
call geometry_plastic_nonlocal_setIParea(norm2(unscaledNormals,1))
|
|
|
|
call geometry_plastic_nonlocal_setIPareaNormal(unscaledNormals/spread(norm2(unscaledNormals,1),1,3))
|
2019-10-17 01:30:25 +05:30
|
|
|
call geometry_plastic_nonlocal_results
|
2019-10-17 09:24:08 +05:30
|
|
|
|
2019-10-14 14:06:59 +05:30
|
|
|
end subroutine mesh_init
|
|
|
|
|
2019-11-24 11:56:21 +05:30
|
|
|
|
2019-10-14 18:39:16 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2020-01-12 06:18:05 +05:30
|
|
|
!> @brief Write all information needed for the DADF5 geometry
|
2019-10-14 18:39:16 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2020-01-13 14:33:13 +05:30
|
|
|
subroutine writeGeometry(elem, &
|
2019-10-14 18:39:16 +05:30
|
|
|
connectivity_elem,connectivity_cell, &
|
|
|
|
coordinates_nodes,coordinates_points)
|
2019-10-14 14:06:59 +05:30
|
|
|
|
2020-01-13 14:33:13 +05:30
|
|
|
type(tElement), intent(in) :: &
|
|
|
|
elem
|
2019-10-14 14:06:59 +05:30
|
|
|
integer, dimension(:,:), intent(in) :: &
|
|
|
|
connectivity_elem, &
|
|
|
|
connectivity_cell
|
|
|
|
real(pReal), dimension(:,:), intent(in) :: &
|
|
|
|
coordinates_nodes, &
|
|
|
|
coordinates_points
|
|
|
|
|
|
|
|
integer, dimension(:,:), allocatable :: &
|
|
|
|
connectivity_temp
|
|
|
|
real(pReal), dimension(:,:), allocatable :: &
|
|
|
|
coordinates_temp
|
|
|
|
|
2019-10-12 18:33:26 +05:30
|
|
|
call results_openJobFile
|
2019-12-19 12:19:53 +05:30
|
|
|
call results_closeGroup(results_addGroup('geometry'))
|
2019-10-14 14:06:59 +05:30
|
|
|
|
|
|
|
connectivity_temp = connectivity_elem
|
|
|
|
call results_writeDataset('geometry',connectivity_temp,'T_e',&
|
2019-10-14 13:38:35 +05:30
|
|
|
'connectivity of the elements','-')
|
2019-10-14 14:06:59 +05:30
|
|
|
|
|
|
|
connectivity_temp = connectivity_cell
|
|
|
|
call results_writeDataset('geometry',connectivity_temp,'T_c', &
|
|
|
|
'connectivity of the cells','-')
|
2020-01-13 14:33:13 +05:30
|
|
|
call results_addAttribute('VTK_TYPE',elem%vtkType,'geometry/T_c')
|
2019-10-14 14:06:59 +05:30
|
|
|
|
|
|
|
coordinates_temp = coordinates_nodes
|
|
|
|
call results_writeDataset('geometry',coordinates_temp,'x_n', &
|
2020-01-12 23:02:20 +05:30
|
|
|
'initial coordinates of the nodes','m')
|
2019-10-14 14:06:59 +05:30
|
|
|
|
|
|
|
coordinates_temp = coordinates_points
|
|
|
|
call results_writeDataset('geometry',coordinates_temp,'x_p', &
|
2020-01-12 23:02:20 +05:30
|
|
|
'initial coordinates of the materialpoints','m')
|
2019-10-14 14:06:59 +05:30
|
|
|
|
2019-10-17 01:30:25 +05:30
|
|
|
call results_closeJobFile
|
2019-02-02 20:27:05 +05:30
|
|
|
|
2019-10-14 14:06:59 +05:30
|
|
|
end subroutine writeGeometry
|
2009-01-20 00:12:31 +05:30
|
|
|
|
2014-04-04 20:10:30 +05:30
|
|
|
|
2020-01-12 06:18:05 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief Read mesh from marc input file
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2019-10-16 08:03:26 +05:30
|
|
|
subroutine inputRead(elem,node0_elem,connectivity_elem,microstructureAt,homogenizationAt)
|
|
|
|
|
|
|
|
type(tElement), intent(out) :: elem
|
|
|
|
real(pReal), dimension(:,:), allocatable, intent(out) :: &
|
2020-01-26 16:28:13 +05:30
|
|
|
node0_elem !< node x,y,z coordinates (initially!)
|
2020-01-12 06:18:05 +05:30
|
|
|
integer, dimension(:,:), allocatable, intent(out) :: &
|
2019-10-16 08:03:26 +05:30
|
|
|
connectivity_elem
|
|
|
|
integer, dimension(:), allocatable, intent(out) :: &
|
|
|
|
microstructureAt, &
|
|
|
|
homogenizationAt
|
|
|
|
|
2019-10-15 16:24:46 +05:30
|
|
|
integer :: &
|
|
|
|
fileFormatVersion, &
|
|
|
|
hypoelasticTableStyle, &
|
|
|
|
initialcondTableStyle, &
|
|
|
|
nNodes, &
|
|
|
|
nElems
|
|
|
|
integer, dimension(:), allocatable :: &
|
|
|
|
matNumber !< material numbers for hypoelastic material
|
|
|
|
character(len=pStringLen), dimension(:), allocatable :: inputFile !< file content, separated per lines
|
2019-10-15 17:46:03 +05:30
|
|
|
|
2020-01-26 16:28:13 +05:30
|
|
|
character(len=pStringLen), dimension(:), allocatable :: &
|
2019-10-15 17:46:03 +05:30
|
|
|
nameElemSet
|
|
|
|
integer, dimension(:,:), allocatable :: &
|
2019-10-24 01:39:11 +05:30
|
|
|
mapElemSet !< list of elements in elementSet
|
2019-10-15 16:24:46 +05:30
|
|
|
|
2019-10-24 01:39:11 +05:30
|
|
|
inputFile = IO_read_ASCII(trim(getSolverJobName())//trim(InputFileExtension))
|
2019-10-16 07:52:21 +05:30
|
|
|
call inputRead_fileFormat(fileFormatVersion, &
|
|
|
|
inputFile)
|
|
|
|
call inputRead_tableStyles(initialcondTableStyle,hypoelasticTableStyle, &
|
|
|
|
inputFile)
|
2019-10-15 16:24:46 +05:30
|
|
|
if (fileFormatVersion > 12) &
|
2019-10-16 07:52:21 +05:30
|
|
|
call inputRead_matNumber(matNumber, &
|
|
|
|
hypoelasticTableStyle,inputFile)
|
|
|
|
call inputRead_NnodesAndElements(nNodes,nElems,&
|
|
|
|
inputFile)
|
2019-10-15 16:24:46 +05:30
|
|
|
|
|
|
|
|
2019-10-16 07:52:21 +05:30
|
|
|
call inputRead_mapElemSets(nameElemSet,mapElemSet,&
|
2020-01-25 15:28:04 +05:30
|
|
|
inputFile)
|
2019-10-16 08:03:26 +05:30
|
|
|
|
2020-01-12 05:28:12 +05:30
|
|
|
call inputRead_elemType(elem, &
|
|
|
|
nElems,inputFile)
|
|
|
|
|
2020-01-31 04:03:33 +05:30
|
|
|
call inputRead_mapElems(mesh_FEM2DAMASK_elem,&
|
|
|
|
nElems,elem%nNodes,inputFile)
|
2019-10-15 16:24:46 +05:30
|
|
|
|
2020-01-31 04:03:33 +05:30
|
|
|
call inputRead_mapNodes(mesh_FEM2DAMASK_node,&
|
|
|
|
nNodes,inputFile)
|
2019-10-16 07:27:51 +05:30
|
|
|
|
2019-10-16 08:03:26 +05:30
|
|
|
call inputRead_elemNodes(node0_elem, &
|
|
|
|
Nnodes,inputFile)
|
2019-10-16 20:49:19 +05:30
|
|
|
|
2019-10-17 09:40:00 +05:30
|
|
|
connectivity_elem = inputRead_connectivityElem(nElems,elem%nNodes,inputFile)
|
2019-10-16 08:03:26 +05:30
|
|
|
|
|
|
|
call inputRead_microstructureAndHomogenization(microstructureAt,homogenizationAt, &
|
|
|
|
nElems,elem%nNodes,nameElemSet,mapElemSet,&
|
2020-01-25 18:00:42 +05:30
|
|
|
initialcondTableStyle,inputFile)
|
2019-10-15 16:24:46 +05:30
|
|
|
end subroutine inputRead
|
|
|
|
|
|
|
|
|
2019-10-16 07:27:51 +05:30
|
|
|
|
2012-06-15 21:40:21 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2019-02-03 15:42:23 +05:30
|
|
|
!> @brief Figures out version of Marc input file format
|
2018-01-10 21:43:25 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2019-10-15 16:24:46 +05:30
|
|
|
subroutine inputRead_fileFormat(fileFormat,fileContent)
|
2019-05-15 02:42:32 +05:30
|
|
|
|
2020-01-23 12:55:49 +05:30
|
|
|
integer, intent(out) :: fileFormat
|
|
|
|
character(len=*), dimension(:), intent(in) :: fileContent !< file content, separated per lines
|
2019-10-13 01:28:26 +05:30
|
|
|
|
2019-06-13 04:09:35 +05:30
|
|
|
integer, allocatable, dimension(:) :: chunkPos
|
2019-10-13 01:28:26 +05:30
|
|
|
integer :: l
|
|
|
|
|
|
|
|
do l = 1, size(fileContent)
|
|
|
|
chunkPos = IO_stringPos(fileContent(l))
|
2020-01-29 12:30:28 +05:30
|
|
|
if(chunkPos(1) < 2) cycle
|
|
|
|
if(IO_lc(IO_stringValue(fileContent(l),chunkPos,1)) == 'version') then
|
2019-10-15 16:24:46 +05:30
|
|
|
fileFormat = IO_intValue(fileContent(l),chunkPos,2)
|
2019-06-13 04:09:35 +05:30
|
|
|
exit
|
|
|
|
endif
|
|
|
|
enddo
|
2018-01-10 21:43:25 +05:30
|
|
|
|
2019-10-15 16:24:46 +05:30
|
|
|
end subroutine inputRead_fileFormat
|
2018-01-10 21:43:25 +05:30
|
|
|
|
2018-01-11 21:41:03 +05:30
|
|
|
|
2018-01-10 21:43:25 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2019-02-03 15:42:23 +05:30
|
|
|
!> @brief Figures out table styles for initial cond and hypoelastic
|
2012-06-15 21:40:21 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2019-10-14 13:38:35 +05:30
|
|
|
subroutine inputRead_tableStyles(initialcond,hypoelastic,fileContent)
|
2019-05-15 02:42:32 +05:30
|
|
|
|
2020-01-23 12:55:49 +05:30
|
|
|
integer, intent(out) :: initialcond, hypoelastic
|
|
|
|
character(len=*), dimension(:), intent(in) :: fileContent !< file content, separated per lines
|
2018-01-10 21:43:25 +05:30
|
|
|
|
2019-06-13 04:09:35 +05:30
|
|
|
integer, allocatable, dimension(:) :: chunkPos
|
2019-10-13 01:28:26 +05:30
|
|
|
integer :: l
|
|
|
|
|
2019-06-13 04:09:35 +05:30
|
|
|
initialcond = 0
|
|
|
|
hypoelastic = 0
|
2009-10-12 21:31:49 +05:30
|
|
|
|
2019-10-13 01:28:26 +05:30
|
|
|
do l = 1, size(fileContent)
|
|
|
|
chunkPos = IO_stringPos(fileContent(l))
|
2020-01-29 12:30:28 +05:30
|
|
|
if(chunkPos(1) < 6) cycle
|
|
|
|
if(IO_lc(IO_stringValue(fileContent(l),chunkPos,1)) == 'table') then
|
2019-10-13 01:28:26 +05:30
|
|
|
initialcond = IO_intValue(fileContent(l),chunkPos,4)
|
|
|
|
hypoelastic = IO_intValue(fileContent(l),chunkPos,5)
|
2019-06-13 04:09:35 +05:30
|
|
|
exit
|
|
|
|
endif
|
|
|
|
enddo
|
2009-10-12 21:31:49 +05:30
|
|
|
|
2019-10-14 13:38:35 +05:30
|
|
|
end subroutine inputRead_tableStyles
|
2009-04-03 12:33:25 +05:30
|
|
|
|
2019-02-03 15:42:23 +05:30
|
|
|
|
2018-01-10 21:43:25 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2019-02-03 16:58:04 +05:30
|
|
|
!> @brief Figures out material number of hypoelastic material
|
2018-01-10 21:43:25 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2019-10-15 16:24:46 +05:30
|
|
|
subroutine inputRead_matNumber(matNumber, &
|
|
|
|
tableStyle,fileContent)
|
2019-05-15 02:42:32 +05:30
|
|
|
|
2020-01-23 12:55:49 +05:30
|
|
|
integer, allocatable, dimension(:), intent(out) :: matNumber
|
|
|
|
integer, intent(in) :: tableStyle
|
|
|
|
character(len=*), dimension(:), intent(in) :: fileContent !< file content, separated per lines
|
2018-01-10 21:43:25 +05:30
|
|
|
|
2019-06-13 04:09:35 +05:30
|
|
|
integer, allocatable, dimension(:) :: chunkPos
|
2019-10-13 15:06:21 +05:30
|
|
|
integer :: i, j, data_blocks, l
|
|
|
|
|
|
|
|
do l = 1, size(fileContent)
|
|
|
|
chunkPos = IO_stringPos(fileContent(l))
|
2020-01-29 12:30:28 +05:30
|
|
|
if(chunkPos(1) < 1) cycle
|
|
|
|
if(IO_lc(IO_stringValue(fileContent(l),chunkPos,1)) == 'hypoelastic') then
|
2020-01-27 01:32:32 +05:30
|
|
|
if (len_trim(fileContent(l+1))/=0) then
|
2019-10-13 15:06:21 +05:30
|
|
|
chunkPos = IO_stringPos(fileContent(l+1))
|
|
|
|
data_blocks = IO_intValue(fileContent(l+1),chunkPos,1)
|
|
|
|
else
|
|
|
|
data_blocks = 1
|
|
|
|
endif
|
2019-10-15 16:24:46 +05:30
|
|
|
allocate(matNumber(data_blocks), source = 0)
|
2019-10-13 15:06:21 +05:30
|
|
|
do i = 0, data_blocks - 1
|
|
|
|
j = i*(2+tableStyle) + 1
|
|
|
|
chunkPos = IO_stringPos(fileContent(l+1+j))
|
2019-10-15 16:24:46 +05:30
|
|
|
matNumber(i+1) = IO_intValue(fileContent(l+1+j),chunkPos,1)
|
2019-10-13 15:06:21 +05:30
|
|
|
enddo
|
|
|
|
exit
|
|
|
|
endif
|
2019-06-13 04:09:35 +05:30
|
|
|
enddo
|
2018-01-10 21:43:25 +05:30
|
|
|
|
2019-10-15 16:24:46 +05:30
|
|
|
end subroutine inputRead_matNumber
|
2018-01-10 21:43:25 +05:30
|
|
|
|
2012-06-15 21:40:21 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2019-02-03 17:24:10 +05:30
|
|
|
!> @brief Count overall number of nodes and elements
|
2012-06-15 21:40:21 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2019-10-14 13:38:35 +05:30
|
|
|
subroutine inputRead_NnodesAndElements(nNodes,nElems,&
|
|
|
|
fileContent)
|
2019-06-13 04:09:35 +05:30
|
|
|
|
2020-01-23 12:55:49 +05:30
|
|
|
integer, intent(out) :: nNodes, nElems
|
|
|
|
character(len=*), dimension(:), intent(in) :: fileContent !< file content, separated per lines
|
2019-10-13 15:06:21 +05:30
|
|
|
|
2019-06-13 04:09:35 +05:30
|
|
|
integer, allocatable, dimension(:) :: chunkPos
|
2019-10-13 15:06:21 +05:30
|
|
|
integer :: l
|
2009-01-20 00:12:31 +05:30
|
|
|
|
2019-06-13 04:09:35 +05:30
|
|
|
nNodes = 0
|
|
|
|
nElems = 0
|
2009-01-20 00:12:31 +05:30
|
|
|
|
2019-10-13 15:06:21 +05:30
|
|
|
do l = 1, size(fileContent)
|
|
|
|
chunkPos = IO_stringPos(fileContent(l))
|
2020-01-29 12:30:28 +05:30
|
|
|
if(chunkPos(1) < 1) cycle
|
|
|
|
if (IO_lc(IO_StringValue(fileContent(l),chunkPos,1)) == 'sizing') then
|
2019-10-13 15:06:21 +05:30
|
|
|
nElems = IO_IntValue (fileContent(l),chunkPos,3)
|
2020-01-29 12:30:28 +05:30
|
|
|
elseif(IO_lc(IO_StringValue(fileContent(l),chunkPos,1)) == 'coordinates') then
|
2019-10-13 15:06:21 +05:30
|
|
|
chunkPos = IO_stringPos(fileContent(l+1))
|
|
|
|
nNodes = IO_IntValue (fileContent(l+1),chunkPos,2)
|
2019-06-13 04:09:35 +05:30
|
|
|
endif
|
|
|
|
enddo
|
2009-01-20 00:12:31 +05:30
|
|
|
|
2019-10-14 13:38:35 +05:30
|
|
|
end subroutine inputRead_NnodesAndElements
|
2012-06-15 21:40:21 +05:30
|
|
|
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2019-02-03 15:42:23 +05:30
|
|
|
!> @brief Count overall number of element sets in mesh.
|
2012-06-15 21:40:21 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2019-10-14 13:38:35 +05:30
|
|
|
subroutine inputRead_NelemSets(nElemSets,maxNelemInSet,&
|
2020-01-12 06:18:05 +05:30
|
|
|
fileContent)
|
2019-05-15 02:42:32 +05:30
|
|
|
|
2020-01-23 12:55:49 +05:30
|
|
|
integer, intent(out) :: nElemSets, maxNelemInSet
|
|
|
|
character(len=*), dimension(:), intent(in) :: fileContent !< file content, separated per lines
|
2009-01-20 00:12:31 +05:30
|
|
|
|
2019-06-06 16:38:10 +05:30
|
|
|
integer, allocatable, dimension(:) :: chunkPos
|
2020-01-23 12:55:49 +05:30
|
|
|
integer :: i,l,elemInCurrentSet
|
2009-10-12 21:31:49 +05:30
|
|
|
|
2019-06-06 16:38:10 +05:30
|
|
|
nElemSets = 0
|
|
|
|
maxNelemInSet = 0
|
2009-01-20 00:12:31 +05:30
|
|
|
|
2020-01-12 06:18:05 +05:30
|
|
|
do l = 1, size(fileContent)
|
|
|
|
chunkPos = IO_stringPos(fileContent(l))
|
2020-01-29 12:30:28 +05:30
|
|
|
if(chunkPos(1) < 2) cycle
|
2020-01-29 13:43:55 +05:30
|
|
|
if(IO_lc(IO_StringValue(fileContent(l),chunkPos,1)) == 'define' .and. &
|
|
|
|
IO_lc(IO_StringValue(fileContent(l),chunkPos,2)) == 'element') then
|
2019-06-06 16:38:10 +05:30
|
|
|
nElemSets = nElemSets + 1
|
2020-01-12 06:18:05 +05:30
|
|
|
|
|
|
|
chunkPos = IO_stringPos(fileContent(l+1))
|
2020-01-29 13:43:55 +05:30
|
|
|
if(containsRange(fileContent(l+1),chunkPos)) then
|
2020-01-12 06:18:05 +05:30
|
|
|
elemInCurrentSet = 1 + abs( IO_intValue(fileContent(l+1),chunkPos,3) &
|
|
|
|
-IO_intValue(fileContent(l+1),chunkPos,1))
|
|
|
|
else
|
|
|
|
elemInCurrentSet = 0
|
|
|
|
i = 0
|
|
|
|
do while (.true.)
|
|
|
|
i = i + 1
|
|
|
|
chunkPos = IO_stringPos(fileContent(l+i))
|
2020-01-27 02:26:08 +05:30
|
|
|
elemInCurrentSet = elemInCurrentSet + chunkPos(1) - 1 ! add line's count when assuming 'c'
|
|
|
|
if(IO_lc(IO_stringValue(fileContent(l+i),chunkPos,chunkPos(1))) /= 'c') then ! line finished, read last value
|
|
|
|
elemInCurrentSet = elemInCurrentSet + 1 ! data ended
|
2020-01-12 06:18:05 +05:30
|
|
|
exit
|
|
|
|
endif
|
|
|
|
enddo
|
|
|
|
endif
|
|
|
|
maxNelemInSet = max(maxNelemInSet, elemInCurrentSet)
|
2019-06-06 16:38:10 +05:30
|
|
|
endif
|
|
|
|
enddo
|
2009-01-20 00:12:31 +05:30
|
|
|
|
2020-01-12 06:18:05 +05:30
|
|
|
end subroutine inputRead_NelemSets
|
2007-04-25 13:03:24 +05:30
|
|
|
|
2009-01-20 00:12:31 +05:30
|
|
|
|
2019-02-03 15:42:23 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief map element sets
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2020-01-25 15:28:04 +05:30
|
|
|
subroutine inputRead_mapElemSets(nameElemSet,mapElemSet,&
|
|
|
|
fileContent)
|
2019-05-15 02:42:32 +05:30
|
|
|
|
2020-01-26 16:28:13 +05:30
|
|
|
character(len=pStringLen), dimension(:), allocatable, intent(out) :: nameElemSet
|
|
|
|
integer, dimension(:,:), allocatable, intent(out) :: mapElemSet
|
|
|
|
character(len=*), dimension(:), intent(in) :: fileContent !< file content, separated per lines
|
2018-01-10 21:43:25 +05:30
|
|
|
|
2019-06-06 16:38:10 +05:30
|
|
|
integer, allocatable, dimension(:) :: chunkPos
|
2020-01-25 15:28:04 +05:30
|
|
|
integer :: elemSet, NelemSets, maxNelemInSet,l
|
2019-10-15 17:46:03 +05:30
|
|
|
|
|
|
|
|
2020-01-12 06:18:05 +05:30
|
|
|
call inputRead_NelemSets(NelemSets,maxNelemInSet,fileContent)
|
2019-10-15 17:46:03 +05:30
|
|
|
allocate(nameElemSet(NelemSets)); nameElemSet = 'n/a'
|
|
|
|
allocate(mapElemSet(1+maxNelemInSet,NelemSets),source=0)
|
2019-06-06 16:38:10 +05:30
|
|
|
elemSet = 0
|
|
|
|
|
2020-01-25 15:28:04 +05:30
|
|
|
do l = 1, size(fileContent)
|
|
|
|
chunkPos = IO_stringPos(fileContent(l))
|
2020-01-29 12:30:28 +05:30
|
|
|
if(chunkPos(1) < 2) cycle
|
|
|
|
if(IO_lc(IO_stringValue(fileContent(l),chunkPos,1)) == 'define' .and. &
|
|
|
|
IO_lc(IO_stringValue(fileContent(l),chunkPos,2)) == 'element') then
|
2019-06-06 16:38:10 +05:30
|
|
|
elemSet = elemSet+1
|
2020-01-25 15:28:04 +05:30
|
|
|
nameElemSet(elemSet) = trim(IO_stringValue(fileContent(l),chunkPos,4))
|
|
|
|
mapElemSet(:,elemSet) = continuousIntValues(fileContent(l+1:),size(mapElemSet,1)-1,nameElemSet,mapElemSet,size(nameElemSet))
|
2019-06-06 16:38:10 +05:30
|
|
|
endif
|
|
|
|
enddo
|
2018-01-10 21:43:25 +05:30
|
|
|
|
2020-01-25 15:28:04 +05:30
|
|
|
end subroutine inputRead_mapElemSets
|
2010-05-06 22:10:47 +05:30
|
|
|
|
|
|
|
|
2012-06-15 21:40:21 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief Maps elements from FE ID to internal (consecutive) representation.
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2020-01-31 04:03:33 +05:30
|
|
|
subroutine inputRead_mapElems(FEM2DAMASK, &
|
|
|
|
nElems,nNodesPerElem,fileContent)
|
2019-10-17 09:24:08 +05:30
|
|
|
|
2020-01-31 04:03:33 +05:30
|
|
|
integer, allocatable, dimension(:), intent(out) :: FEM2DAMASK
|
2020-01-12 05:28:12 +05:30
|
|
|
|
2020-01-31 04:03:33 +05:30
|
|
|
integer, intent(in) :: nElems, & !< number of elements
|
|
|
|
nNodesPerElem !< number of nodes per element
|
2020-01-27 03:28:26 +05:30
|
|
|
character(len=*), dimension(:), intent(in) :: fileContent !< file content, separated per lines
|
|
|
|
|
2020-01-31 04:03:33 +05:30
|
|
|
integer, dimension(2,nElems) :: map_unsorted
|
2020-01-29 04:12:25 +05:30
|
|
|
integer, allocatable, dimension(:) :: chunkPos
|
2020-01-12 05:28:12 +05:30
|
|
|
integer :: i,j,l,nNodesAlreadyRead
|
|
|
|
|
|
|
|
do l = 1, size(fileContent)
|
|
|
|
chunkPos = IO_stringPos(fileContent(l))
|
2020-01-29 12:30:28 +05:30
|
|
|
if(chunkPos(1) < 1) cycle
|
|
|
|
if(IO_lc(IO_stringValue(fileContent(l),chunkPos,1)) == 'connectivity') then
|
2020-01-12 05:28:12 +05:30
|
|
|
j = 0
|
2020-01-31 04:03:33 +05:30
|
|
|
do i = 1,nElems
|
2020-01-12 05:28:12 +05:30
|
|
|
chunkPos = IO_stringPos(fileContent(l+1+i+j))
|
2020-01-31 04:03:33 +05:30
|
|
|
map_unsorted(:,i) = [IO_intValue(fileContent(l+1+i+j),chunkPos,1),i]
|
2020-01-12 05:28:12 +05:30
|
|
|
nNodesAlreadyRead = chunkPos(1) - 2
|
2020-01-31 04:03:33 +05:30
|
|
|
do while(nNodesAlreadyRead < nNodesPerElem) ! read on if not all nodes in one line
|
2020-01-12 05:28:12 +05:30
|
|
|
j = j + 1
|
|
|
|
chunkPos = IO_stringPos(fileContent(l+1+i+j))
|
|
|
|
nNodesAlreadyRead = nNodesAlreadyRead + chunkPos(1)
|
|
|
|
enddo
|
|
|
|
enddo
|
|
|
|
exit
|
|
|
|
endif
|
2019-10-17 09:24:08 +05:30
|
|
|
enddo
|
2020-01-12 05:28:12 +05:30
|
|
|
|
2020-01-31 04:03:33 +05:30
|
|
|
call math_sort(map_unsorted)
|
|
|
|
allocate(FEM2DAMASK(minval(map_unsorted(1,:)):maxval(map_unsorted(1,:))),source=-1)
|
|
|
|
do i = 1, nElems
|
|
|
|
FEM2DAMASK(map_unsorted(1,i)) = map_unsorted(2,i)
|
2020-01-27 03:28:26 +05:30
|
|
|
enddo
|
2009-01-20 00:12:31 +05:30
|
|
|
|
2019-10-14 13:38:35 +05:30
|
|
|
end subroutine inputRead_mapElems
|
2009-10-12 21:31:49 +05:30
|
|
|
|
|
|
|
|
2012-06-15 21:40:21 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief Maps node from FE ID to internal (consecutive) representation.
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2020-01-31 04:03:33 +05:30
|
|
|
subroutine inputRead_mapNodes(FEM2DAMASK, &
|
|
|
|
nNodes,fileContent)
|
2012-06-15 21:40:21 +05:30
|
|
|
|
2020-01-31 04:03:33 +05:30
|
|
|
integer, allocatable, dimension(:), intent(out) :: FEM2DAMASK
|
2020-01-27 03:28:26 +05:30
|
|
|
|
2020-01-31 04:03:33 +05:30
|
|
|
integer, intent(in) :: nNodes !< number of nodes
|
2020-01-27 03:28:26 +05:30
|
|
|
character(len=*), dimension(:), intent(in) :: fileContent !< file content, separated per lines
|
2009-10-12 21:31:49 +05:30
|
|
|
|
2020-01-31 04:03:33 +05:30
|
|
|
integer, dimension(2,nNodes) :: map_unsorted
|
2019-06-13 04:09:35 +05:30
|
|
|
integer, allocatable, dimension(:) :: chunkPos
|
2019-10-13 14:12:34 +05:30
|
|
|
integer :: i, l
|
2012-06-15 21:40:21 +05:30
|
|
|
|
2019-10-13 14:12:34 +05:30
|
|
|
do l = 1, size(fileContent)
|
|
|
|
chunkPos = IO_stringPos(fileContent(l))
|
2020-01-29 12:30:28 +05:30
|
|
|
if(chunkPos(1) < 1) cycle
|
|
|
|
if(IO_lc(IO_stringValue(fileContent(l),chunkPos,1)) == 'coordinates') then
|
2020-01-31 04:03:33 +05:30
|
|
|
do i = 1,nNodes
|
2020-01-12 20:38:38 +05:30
|
|
|
chunkPos = IO_stringPos(fileContent(l+1+i))
|
2020-01-31 04:03:33 +05:30
|
|
|
map_unsorted(:,i) = [IO_intValue(fileContent(l+1+i),chunkPos,1),i]
|
2019-06-13 04:09:35 +05:30
|
|
|
enddo
|
|
|
|
exit
|
|
|
|
endif
|
|
|
|
enddo
|
2012-06-15 21:40:21 +05:30
|
|
|
|
2020-01-31 04:03:33 +05:30
|
|
|
call math_sort(map_unsorted)
|
|
|
|
allocate(FEM2DAMASK(minval(map_unsorted(1,:)):maxval(map_unsorted(1,:))),source=-1)
|
|
|
|
do i = 1, nNodes
|
|
|
|
FEM2DAMASK(map_unsorted(1,i)) = map_unsorted(2,i)
|
2020-01-27 03:28:26 +05:30
|
|
|
enddo
|
2018-01-10 21:43:25 +05:30
|
|
|
|
2019-10-14 13:38:35 +05:30
|
|
|
end subroutine inputRead_mapNodes
|
2009-10-12 21:31:49 +05:30
|
|
|
|
|
|
|
|
2012-06-15 21:40:21 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief store x,y,z coordinates of all nodes in mesh.
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2019-10-16 07:52:21 +05:30
|
|
|
subroutine inputRead_elemNodes(nodes, &
|
|
|
|
nNode,fileContent)
|
2009-10-12 21:31:49 +05:30
|
|
|
|
2019-10-16 07:52:21 +05:30
|
|
|
real(pReal), allocatable, dimension(:,:), intent(out) :: nodes
|
|
|
|
integer, intent(in) :: nNode
|
2020-01-23 12:55:49 +05:30
|
|
|
character(len=*), dimension(:), intent(in) :: fileContent !< file content, separated per lines
|
2019-10-13 14:12:34 +05:30
|
|
|
|
2019-06-13 04:09:35 +05:30
|
|
|
integer, allocatable, dimension(:) :: chunkPos
|
2019-10-13 14:12:34 +05:30
|
|
|
integer :: i,j,m,l
|
2009-10-12 21:31:49 +05:30
|
|
|
|
2019-10-16 07:52:21 +05:30
|
|
|
allocate(nodes(3,nNode))
|
|
|
|
|
2019-10-13 14:12:34 +05:30
|
|
|
do l = 1, size(fileContent)
|
|
|
|
chunkPos = IO_stringPos(fileContent(l))
|
2020-01-29 12:30:28 +05:30
|
|
|
if(chunkPos(1) < 1) cycle
|
|
|
|
if(IO_lc(IO_stringValue(fileContent(l),chunkPos,1)) == 'coordinates') then
|
2019-06-13 11:01:45 +05:30
|
|
|
do i=1,nNode
|
2020-01-12 20:38:38 +05:30
|
|
|
chunkPos = IO_stringPos(fileContent(l+1+i))
|
2020-01-31 04:03:33 +05:30
|
|
|
m = mesh_FEM2DAMASK_node(IO_intValue(fileContent(l+1+i),chunkPos,1))
|
2019-06-13 04:09:35 +05:30
|
|
|
do j = 1,3
|
2020-01-12 20:38:38 +05:30
|
|
|
nodes(j,m) = mesh_unitlength * IO_floatValue(fileContent(l+1+i),chunkPos,j+1)
|
2019-06-13 04:09:35 +05:30
|
|
|
enddo
|
|
|
|
enddo
|
|
|
|
exit
|
|
|
|
endif
|
|
|
|
enddo
|
2009-10-12 21:31:49 +05:30
|
|
|
|
2019-10-16 07:52:21 +05:30
|
|
|
end subroutine inputRead_elemNodes
|
2009-10-12 21:31:49 +05:30
|
|
|
|
2012-03-09 01:55:28 +05:30
|
|
|
|
2012-06-15 21:40:21 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2019-06-06 16:38:10 +05:30
|
|
|
!> @brief Gets element type (and checks if the whole mesh comprises of only one type)
|
2012-06-15 21:40:21 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2019-10-16 07:27:51 +05:30
|
|
|
subroutine inputRead_elemType(elem, &
|
2019-10-17 09:24:08 +05:30
|
|
|
nElem,fileContent)
|
2019-06-06 16:38:10 +05:30
|
|
|
|
2020-01-23 12:55:49 +05:30
|
|
|
type(tElement), intent(out) :: elem
|
|
|
|
integer, intent(in) :: nElem
|
|
|
|
character(len=*), dimension(:), intent(in) :: fileContent !< file content, separated per lines
|
2019-06-06 16:38:10 +05:30
|
|
|
|
|
|
|
integer, allocatable, dimension(:) :: chunkPos
|
2019-10-17 09:24:08 +05:30
|
|
|
integer :: i,j,t,l,remainingChunks
|
2019-06-06 16:38:10 +05:30
|
|
|
|
|
|
|
t = -1
|
2019-10-17 09:24:08 +05:30
|
|
|
do l = 1, size(fileContent)
|
|
|
|
chunkPos = IO_stringPos(fileContent(l))
|
2020-01-29 12:30:28 +05:30
|
|
|
if(chunkPos(1) < 1) cycle
|
|
|
|
if(IO_lc(IO_stringValue(fileContent(l),chunkPos,1)) == 'connectivity') then
|
2019-10-17 09:40:00 +05:30
|
|
|
j = 0
|
2019-06-06 16:38:10 +05:30
|
|
|
do i=1,nElem ! read all elements
|
2019-10-17 09:24:08 +05:30
|
|
|
chunkPos = IO_stringPos(fileContent(l+1+i+j))
|
2019-06-06 16:38:10 +05:30
|
|
|
if (t == -1) then
|
2019-10-17 09:24:08 +05:30
|
|
|
t = mapElemtype(IO_stringValue(fileContent(l+1+i+j),chunkPos,2))
|
2019-10-16 07:27:51 +05:30
|
|
|
call elem%init(t)
|
2019-06-06 16:38:10 +05:30
|
|
|
else
|
2019-10-17 09:24:08 +05:30
|
|
|
if (t /= mapElemtype(IO_stringValue(fileContent(l+1+i+j),chunkPos,2))) call IO_error(191,el=t,ip=i)
|
2019-06-06 16:38:10 +05:30
|
|
|
endif
|
2019-10-17 09:24:08 +05:30
|
|
|
remainingChunks = elem%nNodes - (chunkPos(1) - 2)
|
|
|
|
do while(remainingChunks > 0)
|
|
|
|
j = j + 1
|
|
|
|
chunkPos = IO_stringPos(fileContent(l+1+i+j))
|
|
|
|
remainingChunks = remainingChunks - chunkPos(1)
|
|
|
|
enddo
|
2019-06-06 16:38:10 +05:30
|
|
|
enddo
|
|
|
|
exit
|
|
|
|
endif
|
|
|
|
enddo
|
2009-10-12 21:31:49 +05:30
|
|
|
|
2019-10-05 20:48:21 +05:30
|
|
|
contains
|
2019-02-02 20:47:52 +05:30
|
|
|
|
2019-06-06 16:38:10 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief mapping of Marc element types to internal representation
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
integer function mapElemtype(what)
|
|
|
|
|
|
|
|
character(len=*), intent(in) :: what
|
|
|
|
|
|
|
|
select case (IO_lc(what))
|
|
|
|
case ( '6')
|
|
|
|
mapElemtype = 1 ! Two-dimensional Plane Strain Triangle
|
2020-01-26 12:47:25 +05:30
|
|
|
case ( '125') ! 155, 128 (need test)
|
2019-06-06 16:38:10 +05:30
|
|
|
mapElemtype = 2 ! Two-dimensional Plane Strain triangle (155: cubic shape function, 125/128: second order isoparametric)
|
2020-01-26 12:47:25 +05:30
|
|
|
!case ( '11') ! need test
|
|
|
|
! mapElemtype = 3 ! Arbitrary Quadrilateral Plane-strain
|
2019-06-06 16:38:10 +05:30
|
|
|
case ( '27')
|
|
|
|
mapElemtype = 4 ! Plane Strain, Eight-node Distorted Quadrilateral
|
|
|
|
case ( '54')
|
|
|
|
mapElemtype = 5 ! Plane Strain, Eight-node Distorted Quadrilateral with reduced integration
|
2020-01-26 12:47:25 +05:30
|
|
|
!case ( '134') ! need test
|
|
|
|
! mapElemtype = 6 ! Three-dimensional Four-node Tetrahedron
|
|
|
|
!case ( '157') ! need test
|
|
|
|
! mapElemtype = 7 ! Three-dimensional, Low-order, Tetrahedron, Herrmann Formulations
|
|
|
|
!case ( '127') ! need test
|
|
|
|
! mapElemtype = 8 ! Three-dimensional Ten-node Tetrahedron
|
|
|
|
!case ( '136') ! need test
|
|
|
|
! mapElemtype = 9 ! Three-dimensional Arbitrarily Distorted Pentahedral
|
|
|
|
case ( '117') ! 123 (need test)
|
2019-06-06 16:38:10 +05:30
|
|
|
mapElemtype = 10 ! Three-dimensional Arbitrarily Distorted linear hexahedral with reduced integration
|
|
|
|
case ( '7')
|
|
|
|
mapElemtype = 11 ! Three-dimensional Arbitrarily Distorted Brick
|
|
|
|
case ( '57')
|
|
|
|
mapElemtype = 12 ! Three-dimensional Arbitrarily Distorted quad hexahedral with reduced integration
|
|
|
|
case ( '21')
|
|
|
|
mapElemtype = 13 ! Three-dimensional Arbitrarily Distorted quadratic hexahedral
|
|
|
|
case default
|
|
|
|
call IO_error(error_ID=190,ext_msg=IO_lc(what))
|
|
|
|
end select
|
|
|
|
|
2019-10-17 09:24:08 +05:30
|
|
|
end function mapElemtype
|
2019-06-06 16:38:10 +05:30
|
|
|
|
|
|
|
|
2019-10-17 09:24:08 +05:30
|
|
|
end subroutine inputRead_elemType
|
2010-05-06 22:10:47 +05:30
|
|
|
|
|
|
|
|
2012-06-15 21:40:21 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2019-10-12 22:54:03 +05:30
|
|
|
!> @brief Stores node IDs
|
2012-06-15 21:40:21 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2019-10-17 09:40:00 +05:30
|
|
|
function inputRead_connectivityElem(nElem,nNodes,fileContent)
|
2019-05-15 02:42:32 +05:30
|
|
|
|
2019-06-06 16:38:10 +05:30
|
|
|
integer, intent(in) :: &
|
2019-06-13 10:31:35 +05:30
|
|
|
nElem, &
|
2019-10-17 09:40:00 +05:30
|
|
|
nNodes !< number of nodes per element
|
2020-01-23 12:55:49 +05:30
|
|
|
character(len=*), dimension(:), intent(in) :: fileContent !< file content, separated per lines
|
2019-10-13 02:10:00 +05:30
|
|
|
|
2019-10-14 14:55:48 +05:30
|
|
|
integer, dimension(nNodes,nElem) :: &
|
2019-10-14 14:06:59 +05:30
|
|
|
inputRead_connectivityElem
|
2019-06-06 16:38:10 +05:30
|
|
|
|
|
|
|
integer, allocatable, dimension(:) :: chunkPos
|
|
|
|
|
2019-06-13 10:31:35 +05:30
|
|
|
integer, dimension(1+nElem) :: contInts
|
2019-10-17 09:40:00 +05:30
|
|
|
integer :: i,k,j,t,e,l,nNodesAlreadyRead
|
2019-06-06 16:38:10 +05:30
|
|
|
|
2019-10-17 09:40:00 +05:30
|
|
|
do l = 1, size(fileContent)
|
|
|
|
chunkPos = IO_stringPos(fileContent(l))
|
2020-01-29 12:30:28 +05:30
|
|
|
if(chunkPos(1) < 1) cycle
|
|
|
|
if(IO_lc(IO_stringValue(fileContent(l),chunkPos,1)) == 'connectivity') then
|
2019-10-17 09:40:00 +05:30
|
|
|
j = 0
|
2019-06-13 10:31:35 +05:30
|
|
|
do i = 1,nElem
|
2019-10-17 09:40:00 +05:30
|
|
|
chunkPos = IO_stringPos(fileContent(l+1+i+j))
|
2020-01-31 04:03:33 +05:30
|
|
|
e = mesh_FEM2DAMASK_elem(IO_intValue(fileContent(l+1+i+j),chunkPos,1))
|
2019-06-06 16:38:10 +05:30
|
|
|
if (e /= 0) then ! disregard non CP elems
|
2019-10-17 09:40:00 +05:30
|
|
|
do k = 1,chunkPos(1)-2
|
|
|
|
inputRead_connectivityElem(k,e) = &
|
2020-01-31 04:03:33 +05:30
|
|
|
mesh_FEM2DAMASK_node(IO_IntValue(fileContent(l+1+i+j),chunkPos,k+2))
|
2019-06-06 16:38:10 +05:30
|
|
|
enddo
|
|
|
|
nNodesAlreadyRead = chunkPos(1) - 2
|
2019-10-05 20:48:21 +05:30
|
|
|
do while(nNodesAlreadyRead < nNodes) ! read on if not all nodes in one line
|
2019-10-17 09:40:00 +05:30
|
|
|
j = j + 1
|
|
|
|
chunkPos = IO_stringPos(fileContent(l+1+i+j))
|
|
|
|
do k = 1,chunkPos(1)
|
|
|
|
inputRead_connectivityElem(nNodesAlreadyRead+k,e) = &
|
2020-01-31 04:03:33 +05:30
|
|
|
mesh_FEM2DAMASK_node(IO_IntValue(fileContent(l+1+i+j),chunkPos,k))
|
2019-06-06 16:38:10 +05:30
|
|
|
enddo
|
|
|
|
nNodesAlreadyRead = nNodesAlreadyRead + chunkPos(1)
|
|
|
|
enddo
|
|
|
|
endif
|
|
|
|
enddo
|
|
|
|
exit
|
|
|
|
endif
|
|
|
|
enddo
|
2019-10-13 15:23:35 +05:30
|
|
|
|
2019-10-17 09:40:00 +05:30
|
|
|
end function inputRead_connectivityElem
|
2019-10-12 22:54:03 +05:30
|
|
|
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief Stores homogenization and microstructure ID
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2019-10-14 14:06:59 +05:30
|
|
|
subroutine inputRead_microstructureAndHomogenization(microstructureAt,homogenizationAt, &
|
2020-01-25 18:00:42 +05:30
|
|
|
nElem,nNodes,nameElemSet,mapElemSet,initialcondTableStyle,fileContent)
|
2019-10-12 22:54:03 +05:30
|
|
|
|
2019-10-16 08:03:26 +05:30
|
|
|
integer, dimension(:), allocatable, intent(out) :: &
|
2019-10-12 22:54:03 +05:30
|
|
|
microstructureAt, &
|
|
|
|
homogenizationAt
|
|
|
|
integer, intent(in) :: &
|
|
|
|
nElem, &
|
|
|
|
nNodes, & !< number of nodes per element
|
2020-01-25 18:00:42 +05:30
|
|
|
initialcondTableStyle
|
|
|
|
character(len=*), dimension(:), intent(in) :: nameElemSet
|
|
|
|
integer, dimension(:,:), intent(in) :: mapElemSet !< list of elements in elementSet
|
|
|
|
character(len=*), dimension(:), intent(in) :: fileContent !< file content, separated per lines
|
2019-10-12 22:54:03 +05:30
|
|
|
|
|
|
|
integer, allocatable, dimension(:) :: chunkPos
|
|
|
|
|
|
|
|
integer, dimension(1+nElem) :: contInts
|
2020-01-25 18:00:42 +05:30
|
|
|
integer :: i,j,t,sv,myVal,e,nNodesAlreadyRead,l,k,m
|
2019-10-12 22:54:03 +05:30
|
|
|
|
2019-10-16 08:03:26 +05:30
|
|
|
|
|
|
|
allocate(microstructureAt(nElem),source=0)
|
|
|
|
allocate(homogenizationAt(nElem),source=0)
|
|
|
|
|
2020-01-25 18:00:42 +05:30
|
|
|
do l = 1, size(fileContent)
|
|
|
|
chunkPos = IO_stringPos(fileContent(l))
|
2020-01-29 12:30:28 +05:30
|
|
|
if(chunkPos(1) < 2) cycle
|
|
|
|
if(IO_lc(IO_stringValue(fileContent(l),chunkPos,1)) == 'initial' .and. &
|
|
|
|
IO_lc(IO_stringValue(fileContent(l),chunkPos,2)) == 'state') then
|
2020-01-25 18:00:42 +05:30
|
|
|
k = merge(2,1,initialcondTableStyle == 2)
|
|
|
|
chunkPos = IO_stringPos(fileContent(l+k))
|
|
|
|
sv = IO_IntValue(fileContent(l+k),chunkPos,1) ! figure state variable index
|
|
|
|
if( (sv == 2) .or. (sv == 3) ) then ! only state vars 2 and 3 of interest
|
|
|
|
m = 1
|
|
|
|
chunkPos = IO_stringPos(fileContent(l+k+m))
|
|
|
|
do while (scan(IO_stringValue(fileContent(l+k+m),chunkPos,1),'+-',back=.true.)>1) ! is noEfloat value?
|
|
|
|
myVal = nint(IO_floatValue(fileContent(l+k+m),chunkPos,1))
|
|
|
|
if (initialcondTableStyle == 2) m = m + 2
|
|
|
|
contInts = continuousIntValues(fileContent(l+k+m+1:),nElem,nameElemSet,mapElemSet,size(nameElemSet)) ! get affected elements
|
2019-06-06 16:38:10 +05:30
|
|
|
do i = 1,contInts(1)
|
2020-01-31 04:03:33 +05:30
|
|
|
e = mesh_FEM2DAMASK_elem(contInts(1+i))
|
2019-10-08 13:00:32 +05:30
|
|
|
if (sv == 2) microstructureAt(e) = myVal
|
|
|
|
if (sv == 3) homogenizationAt(e) = myVal
|
2019-06-06 16:38:10 +05:30
|
|
|
enddo
|
2020-01-25 18:00:42 +05:30
|
|
|
if (initialcondTableStyle == 0) m = m + 1
|
2019-06-06 16:38:10 +05:30
|
|
|
enddo
|
|
|
|
endif
|
|
|
|
endif
|
|
|
|
enddo
|
|
|
|
|
2020-01-25 18:00:42 +05:30
|
|
|
end subroutine inputRead_microstructureAndHomogenization
|
2019-02-02 21:54:00 +05:30
|
|
|
|
|
|
|
|
2019-10-14 13:07:31 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief Calculates cell node coordinates from element node coordinates
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2019-10-14 01:46:42 +05:30
|
|
|
subroutine buildCells(connectivity_cell,cellNodeDefinition, &
|
2019-10-14 13:07:31 +05:30
|
|
|
elem,connectivity_elem)
|
2019-10-14 01:46:42 +05:30
|
|
|
|
2019-10-14 13:07:31 +05:30
|
|
|
type(tCellNodeDefinition), dimension(:), intent(out) :: cellNodeDefinition ! definition of cell nodes for increasing number of parents
|
|
|
|
integer, dimension(:,:,:),intent(out) :: connectivity_cell
|
2019-10-08 22:22:34 +05:30
|
|
|
|
2019-10-14 13:07:31 +05:30
|
|
|
type(tElement), intent(in) :: elem ! element definition
|
|
|
|
integer, dimension(:,:), intent(in) :: connectivity_elem ! connectivity of the elements
|
2019-10-08 22:22:34 +05:30
|
|
|
|
2019-10-14 01:46:42 +05:30
|
|
|
integer,dimension(:), allocatable :: candidates_local
|
|
|
|
integer,dimension(:,:), allocatable :: parentsAndWeights,candidates_global
|
2019-10-13 15:49:37 +05:30
|
|
|
|
2019-06-13 04:09:35 +05:30
|
|
|
integer :: e, n, c, p, s,i,m,j,nParentNodes,nCellNode,Nelem,candidateID
|
2019-06-12 22:38:38 +05:30
|
|
|
|
2019-10-14 14:55:48 +05:30
|
|
|
Nelem = size(connectivity_elem,2)
|
2019-05-17 16:52:52 +05:30
|
|
|
|
|
|
|
!---------------------------------------------------------------------------------------------------
|
|
|
|
! initialize global connectivity to negative local connectivity
|
2019-06-12 22:38:38 +05:30
|
|
|
connectivity_cell = -spread(elem%cell,3,Nelem) ! local cell node ID
|
2019-05-17 16:52:52 +05:30
|
|
|
|
|
|
|
!---------------------------------------------------------------------------------------------------
|
2019-06-12 22:38:38 +05:30
|
|
|
! set connectivity of cell nodes that coincide with FE nodes (defined by 1 parent node)
|
|
|
|
! and renumber local (negative) to global (positive) node ID
|
|
|
|
do e = 1, Nelem
|
|
|
|
do c = 1, elem%NcellNodes
|
|
|
|
realNode: if (count(elem%cellNodeParentNodeWeights(:,c) /= 0) == 1) then
|
2019-05-17 16:52:52 +05:30
|
|
|
where(connectivity_cell(:,:,e) == -c)
|
|
|
|
connectivity_cell(:,:,e) = connectivity_elem(c,e)
|
|
|
|
end where
|
|
|
|
endif realNode
|
|
|
|
enddo
|
|
|
|
enddo
|
2019-10-14 11:53:21 +05:30
|
|
|
|
2019-10-14 13:07:31 +05:30
|
|
|
nCellNode = maxval(connectivity_elem)
|
2019-05-17 16:52:52 +05:30
|
|
|
|
2019-06-12 22:38:38 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
|
|
|
! set connectivity of cell nodes that are defined by 2,...,nNodes real nodes
|
|
|
|
do nParentNodes = 2, elem%nNodes
|
2019-05-17 16:52:52 +05:30
|
|
|
|
2019-06-12 22:38:38 +05:30
|
|
|
! get IDs of local cell nodes that are defined by the current number of parent nodes
|
|
|
|
candidates_local = [integer::]
|
|
|
|
do c = 1, elem%NcellNodes
|
|
|
|
if (count(elem%cellNodeParentNodeWeights(:,c) /= 0) == nParentNodes) &
|
|
|
|
candidates_local = [candidates_local,c]
|
|
|
|
enddo
|
|
|
|
s = size(candidates_local)
|
|
|
|
|
|
|
|
if (allocated(candidates_global)) deallocate(candidates_global)
|
2019-06-13 10:31:35 +05:30
|
|
|
allocate(candidates_global(nParentNodes*2+2,s*Nelem)) ! stores parent node ID + weight together with element ID and cellnode id (local)
|
|
|
|
parentsAndWeights = reshape([(0, i = 1,2*nParentNodes)],[nParentNodes,2]) ! (re)allocate
|
2019-06-12 22:38:38 +05:30
|
|
|
|
|
|
|
do e = 1, Nelem
|
|
|
|
do i = 1, size(candidates_local)
|
2019-06-13 10:31:35 +05:30
|
|
|
candidateID = (e-1)*size(candidates_local)+i ! including duplicates, runs to (Nelem*size(candidates_local))
|
|
|
|
c = candidates_local(i) ! c is local cellnode ID for connectivity
|
2019-06-12 22:38:38 +05:30
|
|
|
p = 0
|
|
|
|
do j = 1, size(elem%cellNodeParentNodeWeights(:,c))
|
|
|
|
if (elem%cellNodeParentNodeWeights(j,c) /= 0) then ! real node 'j' partly defines cell node 'c'
|
|
|
|
p = p + 1
|
|
|
|
parentsAndWeights(p,1:2) = [connectivity_elem(j,e),elem%cellNodeParentNodeWeights(j,c)]
|
|
|
|
endif
|
|
|
|
enddo
|
|
|
|
! store (and order) real node IDs and their weights together with the element number and local ID
|
|
|
|
do p = 1, nParentNodes
|
|
|
|
m = maxloc(parentsAndWeights(:,1),1)
|
|
|
|
|
|
|
|
candidates_global(p, candidateID) = parentsAndWeights(m,1)
|
|
|
|
candidates_global(p+nParentNodes, candidateID) = parentsAndWeights(m,2)
|
|
|
|
candidates_global(nParentNodes*2+1:nParentNodes*2+2,candidateID) = [e,c]
|
|
|
|
|
2019-06-13 10:31:35 +05:30
|
|
|
parentsAndWeights(m,1) = -huge(parentsAndWeights(m,1)) ! out of the competition
|
2019-06-12 22:38:38 +05:30
|
|
|
enddo
|
|
|
|
enddo
|
|
|
|
enddo
|
2019-05-17 16:52:52 +05:30
|
|
|
|
2019-06-12 22:38:38 +05:30
|
|
|
! sort according to real node IDs + weight (from left to right)
|
2019-06-13 10:31:35 +05:30
|
|
|
call math_sort(candidates_global,sortDim=1) ! sort according to first column
|
2019-06-12 22:38:38 +05:30
|
|
|
|
|
|
|
do p = 2, nParentNodes*2
|
|
|
|
n = 1
|
|
|
|
do while(n <= size(candidates_local)*Nelem)
|
|
|
|
j=0
|
|
|
|
do while (n+j<= size(candidates_local)*Nelem)
|
|
|
|
if (candidates_global(p-1,n+j)/=candidates_global(p-1,n)) exit
|
|
|
|
j = j + 1
|
|
|
|
enddo
|
|
|
|
e = n+j-1
|
|
|
|
if (any(candidates_global(p,n:e)/=candidates_global(p,n))) &
|
|
|
|
call math_sort(candidates_global(:,n:e),sortDim=p)
|
|
|
|
n = e+1
|
2019-05-17 16:52:52 +05:30
|
|
|
enddo
|
2019-06-12 22:38:38 +05:30
|
|
|
enddo
|
|
|
|
|
2019-06-13 10:31:35 +05:30
|
|
|
i = uniqueRows(candidates_global(1:2*nParentNodes,:))
|
2019-10-13 15:49:37 +05:30
|
|
|
allocate(cellNodeDefinition(nParentNodes-1)%parents(i,nParentNodes))
|
|
|
|
allocate(cellNodeDefinition(nParentNodes-1)%weights(i,nParentNodes))
|
2019-06-12 22:38:38 +05:30
|
|
|
|
|
|
|
i = 1
|
|
|
|
n = 1
|
|
|
|
do while(n <= size(candidates_local)*Nelem)
|
2019-10-13 15:49:37 +05:30
|
|
|
j=0
|
|
|
|
parentsAndWeights(:,1) = candidates_global(1:nParentNodes,n+j)
|
2019-10-14 11:53:21 +05:30
|
|
|
parentsAndWeights(:,2) = candidates_global(nParentNodes+1:nParentNodes*2,n+j)
|
|
|
|
|
2019-10-13 15:49:37 +05:30
|
|
|
e = candidates_global(nParentNodes*2+1,n+j)
|
|
|
|
c = candidates_global(nParentNodes*2+2,n+j)
|
2019-06-12 22:38:38 +05:30
|
|
|
|
2019-10-13 15:49:37 +05:30
|
|
|
do while (n+j<= size(candidates_local)*Nelem)
|
|
|
|
if (any(candidates_global(1:2*nParentNodes,n+j)/=candidates_global(1:2*nParentNodes,n))) exit
|
|
|
|
where (connectivity_cell(:,:,candidates_global(nParentNodes*2+1,n+j)) == -candidates_global(nParentNodes*2+2,n+j)) ! still locally defined
|
2019-10-14 11:53:21 +05:30
|
|
|
connectivity_cell(:,:,candidates_global(nParentNodes*2+1,n+j)) = nCellNode + 1 ! gets current new cell node id
|
2019-10-13 15:49:37 +05:30
|
|
|
end where
|
2019-06-12 22:38:38 +05:30
|
|
|
|
2019-10-13 15:49:37 +05:30
|
|
|
j = j+1
|
|
|
|
enddo
|
2019-10-14 11:53:21 +05:30
|
|
|
nCellNode = nCellNode + 1
|
2019-10-13 15:49:37 +05:30
|
|
|
cellNodeDefinition(nParentNodes-1)%parents(i,:) = parentsAndWeights(:,1)
|
|
|
|
cellNodeDefinition(nParentNodes-1)%weights(i,:) = parentsAndWeights(:,2)
|
2019-10-14 11:53:21 +05:30
|
|
|
i = i + 1
|
2019-10-13 15:49:37 +05:30
|
|
|
n = n+j
|
2019-06-12 22:38:38 +05:30
|
|
|
enddo
|
2019-10-14 11:53:21 +05:30
|
|
|
|
2019-06-13 10:31:35 +05:30
|
|
|
enddo
|
2019-06-13 04:09:35 +05:30
|
|
|
|
2019-09-24 10:43:52 +05:30
|
|
|
contains
|
|
|
|
!------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief count unique rows (same rows need to be stored consecutively)
|
|
|
|
!------------------------------------------------------------------------------------------------
|
2019-06-13 10:31:35 +05:30
|
|
|
pure function uniqueRows(A) result(u)
|
|
|
|
|
|
|
|
integer, dimension(:,:), intent(in) :: A !< array, rows need to be sorted
|
|
|
|
|
|
|
|
integer :: &
|
|
|
|
u, & !< # of unique rows
|
|
|
|
r, & !< row counter
|
|
|
|
d !< duplicate counter
|
|
|
|
|
|
|
|
u = 0
|
|
|
|
r = 1
|
|
|
|
do while(r <= size(A,2))
|
|
|
|
d = 0
|
|
|
|
do while (r+d<= size(A,2))
|
|
|
|
if (any(A(:,r)/=A(:,r+d))) exit
|
|
|
|
d = d+1
|
|
|
|
enddo
|
|
|
|
u = u+1
|
|
|
|
r = r+d
|
|
|
|
enddo
|
|
|
|
|
|
|
|
end function uniqueRows
|
|
|
|
|
2019-06-13 03:35:29 +05:30
|
|
|
end subroutine buildCells
|
2019-05-17 16:52:52 +05:30
|
|
|
|
2019-06-06 11:07:37 +05:30
|
|
|
|
2019-10-14 13:07:31 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief Calculates cell node coordinates from element node coordinates
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
subroutine buildCellNodes(node_cell, &
|
2019-10-14 03:04:03 +05:30
|
|
|
definition,node_elem)
|
|
|
|
|
2019-10-14 13:07:31 +05:30
|
|
|
real(pReal), dimension(:,:), intent(out) :: node_cell !< cell node coordinates
|
|
|
|
type(tCellNodeDefinition), dimension(:), intent(in) :: definition !< cell node definition (weights and parents)
|
|
|
|
real(pReal), dimension(:,:), intent(in) :: node_elem !< element nodes
|
2019-10-14 03:04:03 +05:30
|
|
|
|
|
|
|
integer :: i, j, k, n
|
|
|
|
|
|
|
|
n = size(node_elem,2)
|
2019-10-14 13:07:31 +05:30
|
|
|
node_cell(:,1:n) = node_elem !< initial nodes coincide with element nodes
|
2019-10-14 11:53:21 +05:30
|
|
|
|
2019-10-14 03:04:03 +05:30
|
|
|
do i = 1, size(cellNodeDefinition,1)
|
|
|
|
do j = 1, size(cellNodeDefinition(i)%parents,1)
|
|
|
|
n = n+1
|
|
|
|
node_cell(:,n) = 0.0_pReal
|
|
|
|
do k = 1, size(cellNodeDefinition(i)%parents,2)
|
|
|
|
node_cell(:,n) = node_cell(:,n) &
|
|
|
|
+ node_cell(:,definition(i)%parents(j,k)) * real(definition(i)%weights(j,k),pReal)
|
|
|
|
enddo
|
|
|
|
node_cell(:,n) = node_cell(:,n)/real(sum(definition(i)%weights(j,:)),pReal)
|
|
|
|
enddo
|
|
|
|
enddo
|
|
|
|
|
|
|
|
end subroutine buildCellNodes
|
|
|
|
|
2019-10-16 20:49:19 +05:30
|
|
|
|
2019-10-14 13:07:31 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief Calculates IP coordinates as center of cell
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
subroutine buildIPcoordinates(IPcoordinates, &
|
2019-10-14 11:53:21 +05:30
|
|
|
connectivity_cell,node_cell)
|
|
|
|
|
2019-10-14 13:07:31 +05:30
|
|
|
real(pReal), dimension(:,:), intent(out):: IPcoordinates !< cell-center/IP coordinates
|
|
|
|
integer, dimension(:,:), intent(in) :: connectivity_cell !< connectivity for each cell
|
|
|
|
real(pReal), dimension(:,:), intent(in) :: node_cell !< cell node coordinates
|
2019-10-14 11:53:21 +05:30
|
|
|
|
2019-10-14 13:07:31 +05:30
|
|
|
integer :: i, n
|
2019-10-14 11:53:21 +05:30
|
|
|
|
|
|
|
do i = 1, size(connectivity_cell,2)
|
|
|
|
IPcoordinates(:,i) = 0.0_pReal
|
2019-10-14 13:07:31 +05:30
|
|
|
do n = 1, size(connectivity_cell,1)
|
2019-10-14 11:53:21 +05:30
|
|
|
IPcoordinates(:,i) = IPcoordinates(:,i) &
|
2019-10-14 13:07:31 +05:30
|
|
|
+ node_cell(:,connectivity_cell(n,i))
|
2019-10-14 11:53:21 +05:30
|
|
|
enddo
|
|
|
|
IPcoordinates(:,i) = IPcoordinates(:,i)/real(size(connectivity_cell,1),pReal)
|
|
|
|
enddo
|
|
|
|
|
|
|
|
end subroutine buildIPcoordinates
|
|
|
|
|
2019-10-14 03:04:03 +05:30
|
|
|
|
2019-10-16 20:49:19 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief Calculates IP volume.
|
|
|
|
!> @details The IP volume is calculated differently depending on the cell type.
|
2019-10-17 01:30:25 +05:30
|
|
|
!> 2D cells assume an element depth of 1.0
|
2019-10-16 20:49:19 +05:30
|
|
|
!---------------------------------------------------------------------------------------------------
|
|
|
|
function IPvolume(elem,node,connectivity)
|
|
|
|
|
2019-10-17 01:30:25 +05:30
|
|
|
type(tElement), intent(in) :: elem
|
|
|
|
real(pReal), dimension(:,:), intent(in) :: node
|
|
|
|
integer, dimension(:,:,:), intent(in) :: connectivity
|
|
|
|
|
2019-10-16 20:49:19 +05:30
|
|
|
real(pReal), dimension(elem%nIPs,size(connectivity,3)) :: IPvolume
|
2019-10-17 01:30:25 +05:30
|
|
|
real(pReal), dimension(3) :: x0,x1,x2,x3,x4,x5,x6,x7
|
2019-10-16 20:49:19 +05:30
|
|
|
|
|
|
|
integer :: e,i
|
|
|
|
|
|
|
|
do e = 1,size(connectivity,3)
|
|
|
|
do i = 1,elem%nIPs
|
|
|
|
|
|
|
|
select case (elem%cellType)
|
|
|
|
case (1) ! 2D 3node
|
|
|
|
IPvolume(i,e) = math_areaTriangle(node(1:3,connectivity(1,i,e)), &
|
|
|
|
node(1:3,connectivity(2,i,e)), &
|
|
|
|
node(1:3,connectivity(3,i,e)))
|
|
|
|
|
|
|
|
case (2) ! 2D 4node
|
|
|
|
IPvolume(i,e) = math_areaTriangle(node(1:3,connectivity(1,i,e)), & ! assume planar shape, division in two triangles suffices
|
|
|
|
node(1:3,connectivity(2,i,e)), &
|
|
|
|
node(1:3,connectivity(3,i,e))) &
|
|
|
|
+ math_areaTriangle(node(1:3,connectivity(3,i,e)), &
|
|
|
|
node(1:3,connectivity(4,i,e)), &
|
|
|
|
node(1:3,connectivity(1,i,e)))
|
|
|
|
case (3) ! 3D 4node
|
|
|
|
IPvolume(i,e) = math_volTetrahedron(node(1:3,connectivity(1,i,e)), &
|
|
|
|
node(1:3,connectivity(2,i,e)), &
|
|
|
|
node(1:3,connectivity(3,i,e)), &
|
|
|
|
node(1:3,connectivity(4,i,e)))
|
|
|
|
case (4) ! 3D 8node
|
2019-10-17 03:51:48 +05:30
|
|
|
! J. Grandy, Efficient Calculation of Volume of Hexahedral Cells
|
|
|
|
! Lawrence Livermore National Laboratory
|
|
|
|
! https://www.osti.gov/servlets/purl/632793
|
2019-10-17 01:30:25 +05:30
|
|
|
x0 = node(1:3,connectivity(1,i,e))
|
|
|
|
x1 = node(1:3,connectivity(2,i,e))
|
|
|
|
x2 = node(1:3,connectivity(4,i,e))
|
|
|
|
x3 = node(1:3,connectivity(3,i,e))
|
|
|
|
x4 = node(1:3,connectivity(5,i,e))
|
|
|
|
x5 = node(1:3,connectivity(6,i,e))
|
|
|
|
x6 = node(1:3,connectivity(8,i,e))
|
|
|
|
x7 = node(1:3,connectivity(7,i,e))
|
|
|
|
IPvolume(i,e) = dot_product((x7-x1)+(x6-x0),math_cross((x7-x2), (x3-x0))) &
|
|
|
|
+ dot_product((x6-x0), math_cross((x7-x2)+(x5-x0),(x7-x4))) &
|
|
|
|
+ dot_product((x7-x1), math_cross((x5-x0), (x7-x4)+(x3-x0)))
|
|
|
|
IPvolume(i,e) = IPvolume(i,e)/12.0_pReal
|
2019-10-16 20:49:19 +05:30
|
|
|
end select
|
|
|
|
enddo
|
|
|
|
enddo
|
|
|
|
|
|
|
|
end function IPvolume
|
|
|
|
|
2019-10-17 01:30:25 +05:30
|
|
|
|
2019-10-16 20:49:19 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2019-10-17 01:30:25 +05:30
|
|
|
!> @brief calculation of IP interface areas
|
2019-10-16 20:49:19 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2019-10-17 01:30:25 +05:30
|
|
|
function IPareaNormal(elem,nElem,connectivity,node)
|
|
|
|
|
|
|
|
type(tElement), intent(in) :: elem
|
|
|
|
integer, intent(in) :: nElem
|
|
|
|
integer, dimension(:,:,:), intent(in) :: connectivity
|
|
|
|
real(pReal), dimension(:,:), intent(in) :: node
|
|
|
|
|
|
|
|
real(pReal), dimension(3,elem%nIPneighbors,elem%nIPs,nElem) :: ipAreaNormal
|
|
|
|
|
2019-10-17 03:51:48 +05:30
|
|
|
real(pReal), dimension (3,size(elem%cellFace,1)) :: nodePos
|
2019-10-17 01:30:25 +05:30
|
|
|
integer :: e,i,f,n,m
|
2019-10-16 20:49:19 +05:30
|
|
|
|
2019-10-17 01:30:25 +05:30
|
|
|
m = size(elem%cellFace,1)
|
2019-10-16 20:49:19 +05:30
|
|
|
|
2019-10-17 03:51:48 +05:30
|
|
|
do e = 1,nElem
|
|
|
|
do i = 1,elem%nIPs
|
2019-10-17 11:18:57 +05:30
|
|
|
do f = 1,elem%nIPneighbors
|
2019-10-17 03:51:48 +05:30
|
|
|
nodePos = node(1:3,connectivity(elem%cellface(1:m,f),i,e))
|
2019-10-16 20:49:19 +05:30
|
|
|
|
2019-10-17 03:51:48 +05:30
|
|
|
select case (elem%cellType)
|
|
|
|
case (1,2) ! 2D 3 or 4 node
|
|
|
|
IPareaNormal(1,f,i,e) = nodePos(2,2) - nodePos(2,1) ! x_normal = y_connectingVector
|
|
|
|
IPareaNormal(2,f,i,e) = -(nodePos(1,2) - nodePos(1,1)) ! y_normal = -x_connectingVector
|
|
|
|
IPareaNormal(3,f,i,e) = 0.0_pReal
|
|
|
|
case (3) ! 3D 4node
|
|
|
|
IPareaNormal(1:3,f,i,e) = math_cross(nodePos(1:3,2) - nodePos(1:3,1), &
|
|
|
|
nodePos(1:3,3) - nodePos(1:3,1))
|
|
|
|
case (4) ! 3D 8node
|
|
|
|
! for this cell type we get the normal of the quadrilateral face as an average of
|
|
|
|
! four normals of triangular subfaces; since the face consists only of two triangles,
|
|
|
|
! the sum has to be divided by two; this whole prcedure tries to compensate for
|
|
|
|
! probable non-planar cell surfaces
|
|
|
|
IPareaNormal(1:3,f,i,e) = 0.0_pReal
|
|
|
|
do n = 1, m
|
|
|
|
IPareaNormal(1:3,f,i,e) = IPareaNormal(1:3,f,i,e) &
|
|
|
|
+ math_cross(nodePos(1:3,mod(n+0,m)+1) - nodePos(1:3,n), &
|
|
|
|
nodePos(1:3,mod(n+1,m)+1) - nodePos(1:3,n)) * 0.5_pReal
|
|
|
|
enddo
|
2019-10-16 20:49:19 +05:30
|
|
|
end select
|
|
|
|
enddo
|
|
|
|
enddo
|
2019-10-17 03:51:48 +05:30
|
|
|
enddo
|
|
|
|
|
2019-10-17 01:30:25 +05:30
|
|
|
end function IPareaNormal
|
|
|
|
|
2019-10-16 20:49:19 +05:30
|
|
|
|
2020-01-23 12:55:49 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief return integer list corresponding to items in consecutive lines.
|
|
|
|
!! First integer in array is counter
|
|
|
|
!> @details ints concatenated by "c" as last char, range of a "to" b, or named set
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
function continuousIntValues(fileContent,maxN,lookupName,lookupMap,lookupMaxN)
|
|
|
|
|
|
|
|
character(len=*), dimension(:), intent(in) :: fileContent !< file content, separated per lines
|
|
|
|
integer, intent(in) :: maxN
|
|
|
|
integer, intent(in) :: lookupMaxN
|
|
|
|
integer, dimension(:,:), intent(in) :: lookupMap
|
|
|
|
character(len=*), dimension(:), intent(in) :: lookupName
|
|
|
|
|
|
|
|
integer, dimension(1+maxN) :: continuousIntValues
|
|
|
|
|
|
|
|
integer :: l,i,first,last
|
|
|
|
integer, allocatable, dimension(:) :: chunkPos
|
|
|
|
logical :: rangeGeneration
|
|
|
|
|
|
|
|
continuousIntValues = 0
|
|
|
|
rangeGeneration = .false.
|
|
|
|
|
|
|
|
do l = 1, size(fileContent)
|
|
|
|
chunkPos = IO_stringPos(fileContent(l))
|
|
|
|
if (chunkPos(1) < 1) then ! empty line
|
|
|
|
exit
|
|
|
|
elseif (verify(IO_stringValue(fileContent(l),chunkPos,1),'0123456789') > 0) then ! a non-int, i.e. set name
|
|
|
|
do i = 1, lookupMaxN ! loop over known set names
|
2020-01-25 15:28:04 +05:30
|
|
|
if (IO_stringValue(fileContent(l),chunkPos,1) == lookupName(i)) then ! found matching name
|
2020-01-23 12:55:49 +05:30
|
|
|
continuousIntValues = lookupMap(:,i) ! return resp. entity list
|
|
|
|
exit
|
|
|
|
endif
|
|
|
|
enddo
|
|
|
|
exit
|
2020-01-29 13:43:55 +05:30
|
|
|
elseif(containsRange(fileContent(l),chunkPos)) then
|
2020-01-23 12:55:49 +05:30
|
|
|
first = IO_intValue(fileContent(l),chunkPos,1)
|
|
|
|
last = IO_intValue(fileContent(l),chunkPos,3)
|
|
|
|
do i = first, last, sign(1,last-first)
|
|
|
|
continuousIntValues(1) = continuousIntValues(1) + 1
|
|
|
|
continuousIntValues(1+continuousIntValues(1)) = i
|
|
|
|
enddo
|
|
|
|
exit
|
|
|
|
else
|
|
|
|
do i = 1,chunkPos(1)-1 ! interpret up to second to last value
|
|
|
|
continuousIntValues(1) = continuousIntValues(1) + 1
|
|
|
|
continuousIntValues(1+continuousIntValues(1)) = IO_intValue(fileContent(l),chunkPos,i)
|
|
|
|
enddo
|
|
|
|
if ( IO_lc(IO_stringValue(fileContent(l),chunkPos,chunkPos(1))) /= 'c' ) then ! line finished, read last value
|
|
|
|
continuousIntValues(1) = continuousIntValues(1) + 1
|
|
|
|
continuousIntValues(1+continuousIntValues(1)) = IO_intValue(fileContent(l),chunkPos,chunkPos(1))
|
|
|
|
exit
|
|
|
|
endif
|
|
|
|
endif
|
|
|
|
enddo
|
|
|
|
|
|
|
|
end function continuousIntValues
|
|
|
|
|
2020-01-29 13:43:55 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief return whether a line contains a range ('X to Y')
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
logical function containsRange(str,chunkPos)
|
|
|
|
|
|
|
|
character(len=*), intent(in) :: str
|
|
|
|
integer, dimension(:), intent(in) :: chunkPos !< positions of start and end of each tag/chunk in given string
|
|
|
|
|
|
|
|
containsRange = .False.
|
|
|
|
if(chunkPos(1) == 3) then
|
|
|
|
if(IO_lc(IO_stringValue(str,chunkPos,2)) == 'to') containsRange = .True.
|
|
|
|
endif
|
|
|
|
|
|
|
|
end function containsRange
|
|
|
|
|
|
|
|
|
2012-08-16 20:25:23 +05:30
|
|
|
end module mesh
|