microstructure -> material
This commit is contained in:
parent
8c83566b71
commit
fa413efcbb
2
PRIVATE
2
PRIVATE
|
@ -1 +1 @@
|
|||
Subproject commit c7accae5211531f4282285620df909b74fadd4af
|
||||
Subproject commit ff07e6d60bffff734572d46ab1dec1c2280dc4fe
|
|
@ -56,7 +56,7 @@ subroutine discretization_grid_init(restart)
|
|||
myGrid !< domain grid of this process
|
||||
|
||||
integer, dimension(:), allocatable :: &
|
||||
microstructureAt
|
||||
materialAt
|
||||
|
||||
integer :: &
|
||||
j, &
|
||||
|
@ -68,9 +68,9 @@ subroutine discretization_grid_init(restart)
|
|||
write(6,'(/,a)') ' <<<+- discretization_grid init -+>>>'; flush(6)
|
||||
|
||||
if(index(interface_geomFile,'.vtr') /= 0) then
|
||||
call readVTR(grid,geomSize,origin,microstructureAt)
|
||||
call readVTR(grid,geomSize,origin,materialAt)
|
||||
else
|
||||
call readGeom(grid,geomSize,origin,microstructureAt)
|
||||
call readGeom(grid,geomSize,origin,materialAt)
|
||||
endif
|
||||
|
||||
print'(/,a,3(i12 ))', ' grid a b c: ', grid
|
||||
|
@ -102,10 +102,9 @@ subroutine discretization_grid_init(restart)
|
|||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
! general discretization
|
||||
microstructureAt = microstructureAt(product(grid(1:2))*grid3Offset+1: &
|
||||
product(grid(1:2))*(grid3Offset+grid3)) ! reallocate/shrink in case of MPI
|
||||
materialAt = materialAt(product(grid(1:2))*grid3Offset+1:product(grid(1:2))*(grid3Offset+grid3)) ! reallocate/shrink in case of MPI
|
||||
|
||||
call discretization_init(microstructureAt, &
|
||||
call discretization_init(materialAt, &
|
||||
IPcoordinates0(myGrid,mySize,grid3Offset), &
|
||||
Nodes0(myGrid,mySize,grid3Offset),&
|
||||
merge((grid(1)+1) * (grid(2)+1) * (grid3+1),& ! write bottom layer
|
||||
|
@ -147,7 +146,7 @@ end subroutine discretization_grid_init
|
|||
!> @details important variables have an implicit "save" attribute. Therefore, this function is
|
||||
! supposed to be called only once!
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine readGeom(grid,geomSize,origin,microstructure)
|
||||
subroutine readGeom(grid,geomSize,origin,material)
|
||||
|
||||
integer, dimension(3), intent(out) :: &
|
||||
grid ! grid (across all processes!)
|
||||
|
@ -155,7 +154,7 @@ subroutine readGeom(grid,geomSize,origin,microstructure)
|
|||
geomSize, & ! size (across all processes!)
|
||||
origin ! origin (across all processes!)
|
||||
integer, dimension(:), intent(out), allocatable :: &
|
||||
microstructure
|
||||
material
|
||||
|
||||
character(len=:), allocatable :: rawData
|
||||
character(len=65536) :: line
|
||||
|
@ -167,7 +166,7 @@ subroutine readGeom(grid,geomSize,origin,microstructure)
|
|||
startPos, endPos, &
|
||||
myStat, &
|
||||
l, & !< line counter
|
||||
c, & !< counter for # microstructures in line
|
||||
c, & !< counter for # materials in line
|
||||
o, & !< order of "to" packing
|
||||
e, & !< "element", i.e. spectral collocation point
|
||||
i, j
|
||||
|
@ -266,7 +265,7 @@ subroutine readGeom(grid,geomSize,origin,microstructure)
|
|||
if(any(geomSize < 0.0_pReal)) &
|
||||
call IO_error(error_ID = 842, ext_msg='size (readGeom)')
|
||||
|
||||
allocate(microstructure(product(grid)), source = -1) ! too large in case of MPI (shrink later, not very elegant)
|
||||
allocate(material(product(grid)), source = -1) ! too large in case of MPI (shrink later, not very elegant)
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
! read and interpret content
|
||||
|
@ -281,18 +280,18 @@ subroutine readGeom(grid,geomSize,origin,microstructure)
|
|||
|
||||
noCompression: if (chunkPos(1) /= 3) then
|
||||
c = chunkPos(1)
|
||||
microstructure(e:e+c-1) = [(IO_intValue(line,chunkPos,i+1), i=0, c-1)]
|
||||
material(e:e+c-1) = [(IO_intValue(line,chunkPos,i+1), i=0, c-1)]
|
||||
else noCompression
|
||||
compression: if (IO_lc(IO_stringValue(line,chunkPos,2)) == 'of') then
|
||||
c = IO_intValue(line,chunkPos,1)
|
||||
microstructure(e:e+c-1) = [(IO_intValue(line,chunkPos,3),i = 1,IO_intValue(line,chunkPos,1))]
|
||||
material(e:e+c-1) = [(IO_intValue(line,chunkPos,3),i = 1,IO_intValue(line,chunkPos,1))]
|
||||
else if (IO_lc(IO_stringValue(line,chunkPos,2)) == 'to') then compression
|
||||
c = abs(IO_intValue(line,chunkPos,3) - IO_intValue(line,chunkPos,1)) + 1
|
||||
o = merge(+1, -1, IO_intValue(line,chunkPos,3) > IO_intValue(line,chunkPos,1))
|
||||
microstructure(e:e+c-1) = [(i, i = IO_intValue(line,chunkPos,1),IO_intValue(line,chunkPos,3),o)]
|
||||
material(e:e+c-1) = [(i, i = IO_intValue(line,chunkPos,1),IO_intValue(line,chunkPos,3),o)]
|
||||
else compression
|
||||
c = chunkPos(1)
|
||||
microstructure(e:e+c-1) = [(IO_intValue(line,chunkPos,i+1), i=0, c-1)]
|
||||
material(e:e+c-1) = [(IO_intValue(line,chunkPos,i+1), i=0, c-1)]
|
||||
endif compression
|
||||
endif noCompression
|
||||
|
||||
|
@ -308,7 +307,7 @@ end subroutine readGeom
|
|||
!> @brief Parse vtk rectilinear grid (.vtr)
|
||||
!> @details https://vtk.org/Wiki/VTK_XML_Formats
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine readVTR(grid,geomSize,origin,microstructure)
|
||||
subroutine readVTR(grid,geomSize,origin,material)
|
||||
|
||||
integer, dimension(3), intent(out) :: &
|
||||
grid ! grid (across all processes!)
|
||||
|
@ -316,7 +315,7 @@ subroutine readVTR(grid,geomSize,origin,microstructure)
|
|||
geomSize, & ! size (across all processes!)
|
||||
origin ! origin (across all processes!)
|
||||
integer, dimension(:), intent(out), allocatable :: &
|
||||
microstructure
|
||||
material
|
||||
|
||||
character(len=:), allocatable :: fileContent, dataType, headerType
|
||||
logical :: inFile,inGrid,gotCoordinates,gotCellData,compressed
|
||||
|
@ -364,7 +363,6 @@ subroutine readVTR(grid,geomSize,origin,microstructure)
|
|||
else
|
||||
if(index(fileContent(startPos:endPos),'<CellData>',kind=pI64) /= 0_pI64) then
|
||||
gotCellData = .true.
|
||||
startPos = endPos + 2_pI64
|
||||
do while (index(fileContent(startPos:endPos),'</CellData>',kind=pI64) == 0_pI64)
|
||||
if(index(fileContent(startPos:endPos),'<DataArray',kind=pI64) /= 0_pI64 .and. &
|
||||
getXMLValue(fileContent(startPos:endPos),'Name') == 'material' ) then
|
||||
|
@ -376,7 +374,7 @@ subroutine readVTR(grid,geomSize,origin,microstructure)
|
|||
startPos = endPos + 2_pI64
|
||||
endPos = startPos + index(fileContent(startPos:),IO_EOL,kind=pI64) - 2_pI64
|
||||
s = startPos + verify(fileContent(startPos:endPos),IO_WHITESPACE,kind=pI64) -1_pI64 ! start (no leading whitespace)
|
||||
microstructure = as_Int(fileContent(s:endPos),headerType,compressed,dataType)
|
||||
material = as_Int(fileContent(s:endPos),headerType,compressed,dataType)
|
||||
exit
|
||||
endif
|
||||
startPos = endPos + 2_pI64
|
||||
|
@ -415,8 +413,8 @@ subroutine readVTR(grid,geomSize,origin,microstructure)
|
|||
|
||||
end do
|
||||
|
||||
if(.not. allocated(microstructure)) call IO_error(error_ID = 844, ext_msg='materialpoint not found')
|
||||
if(size(microstructure) /= product(grid)) call IO_error(error_ID = 844, ext_msg='size(materialpoint)')
|
||||
if(.not. allocated(material)) call IO_error(error_ID = 844, ext_msg='material data not found')
|
||||
if(size(material) /= product(grid)) call IO_error(error_ID = 844, ext_msg='size(material)')
|
||||
if(any(geomSize<=0)) call IO_error(error_ID = 844, ext_msg='size')
|
||||
if(any(grid<1)) call IO_error(error_ID = 844, ext_msg='grid')
|
||||
|
||||
|
|
|
@ -52,7 +52,7 @@ subroutine discretization_marc_init
|
|||
type(tElement) :: elem
|
||||
|
||||
integer, dimension(:), allocatable :: &
|
||||
microstructureAt
|
||||
materialAt
|
||||
integer:: &
|
||||
Nnodes, & !< total number of nodes in the mesh
|
||||
Nelems, & !< total number of elements in the mesh
|
||||
|
@ -83,7 +83,7 @@ subroutine discretization_marc_init
|
|||
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')
|
||||
|
||||
call inputRead(elem,node0_elem,connectivity_elem,microstructureAt)
|
||||
call inputRead(elem,node0_elem,connectivity_elem,materialAt)
|
||||
nElems = size(connectivity_elem,2)
|
||||
|
||||
if (debug_e < 1 .or. debug_e > nElems) call IO_error(602,ext_msg='element')
|
||||
|
@ -103,7 +103,7 @@ subroutine discretization_marc_init
|
|||
call buildIPcoordinates(IP_reshaped,reshape(connectivity_cell,[elem%NcellNodesPerCell,&
|
||||
elem%nIPs*nElems]),node0_cell)
|
||||
|
||||
call discretization_init(microstructureAt,&
|
||||
call discretization_init(materialAt,&
|
||||
IP_reshaped,&
|
||||
node0_cell)
|
||||
|
||||
|
@ -172,7 +172,7 @@ end subroutine writeGeometry
|
|||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief Read mesh from marc input file
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine inputRead(elem,node0_elem,connectivity_elem,microstructureAt)
|
||||
subroutine inputRead(elem,node0_elem,connectivity_elem,materialAt)
|
||||
|
||||
type(tElement), intent(out) :: elem
|
||||
real(pReal), dimension(:,:), allocatable, intent(out) :: &
|
||||
|
@ -180,7 +180,7 @@ subroutine inputRead(elem,node0_elem,connectivity_elem,microstructureAt)
|
|||
integer, dimension(:,:), allocatable, intent(out) :: &
|
||||
connectivity_elem
|
||||
integer, dimension(:), allocatable, intent(out) :: &
|
||||
microstructureAt
|
||||
materialAt
|
||||
|
||||
integer :: &
|
||||
fileFormatVersion, &
|
||||
|
@ -226,9 +226,9 @@ subroutine inputRead(elem,node0_elem,connectivity_elem,microstructureAt)
|
|||
|
||||
connectivity_elem = inputRead_connectivityElem(nElems,elem%nNodes,inputFile)
|
||||
|
||||
call inputRead_microstructure(microstructureAt, &
|
||||
nElems,elem%nNodes,nameElemSet,mapElemSet,&
|
||||
initialcondTableStyle,inputFile)
|
||||
call inputRead_material(materialAt, &
|
||||
nElems,elem%nNodes,nameElemSet,mapElemSet,&
|
||||
initialcondTableStyle,inputFile)
|
||||
end subroutine inputRead
|
||||
|
||||
|
||||
|
@ -675,13 +675,13 @@ end function inputRead_connectivityElem
|
|||
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief Store microstructure ID
|
||||
!> @brief Store material ID
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine inputRead_microstructure(microstructureAt,&
|
||||
nElem,nNodes,nameElemSet,mapElemSet,initialcondTableStyle,fileContent)
|
||||
subroutine inputRead_material(materialAt,&
|
||||
nElem,nNodes,nameElemSet,mapElemSet,initialcondTableStyle,fileContent)
|
||||
|
||||
integer, dimension(:), allocatable, intent(out) :: &
|
||||
microstructureAt
|
||||
materialAt
|
||||
integer, intent(in) :: &
|
||||
nElem, &
|
||||
nNodes, & !< number of nodes per element
|
||||
|
@ -696,7 +696,7 @@ subroutine inputRead_microstructure(microstructureAt,&
|
|||
integer :: i,j,t,sv,myVal,e,nNodesAlreadyRead,l,k,m
|
||||
|
||||
|
||||
allocate(microstructureAt(nElem),source=0)
|
||||
allocate(materialAt(nElem),source=0)
|
||||
|
||||
do l = 1, size(fileContent)
|
||||
chunkPos = IO_stringPos(fileContent(l))
|
||||
|
@ -715,7 +715,7 @@ subroutine inputRead_microstructure(microstructureAt,&
|
|||
contInts = continuousIntValues(fileContent(l+k+m+1:),nElem,nameElemSet,mapElemSet,size(nameElemSet)) ! get affected elements
|
||||
do i = 1,contInts(1)
|
||||
e = mesh_FEM2DAMASK_elem(contInts(1+i))
|
||||
microstructureAt(e) = myVal
|
||||
materialAt(e) = myVal
|
||||
enddo
|
||||
if (initialcondTableStyle == 0) m = m + 1
|
||||
enddo
|
||||
|
@ -723,9 +723,9 @@ subroutine inputRead_microstructure(microstructureAt,&
|
|||
endif
|
||||
enddo
|
||||
|
||||
if(any(microstructureAt < 1)) call IO_error(180)
|
||||
if(any(materialAt < 1)) call IO_error(180)
|
||||
|
||||
end subroutine inputRead_microstructure
|
||||
end subroutine inputRead_material
|
||||
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
|
|
Loading…
Reference in New Issue