bugfixes:

theMesh%Nelems need to be set (using an intermediate function until a
routine does that)
spectral.geom file can have "N+n to N" (backwards counting)
This commit is contained in:
Martin Diehl 2019-02-02 11:46:38 +01:00
parent 3a5a50cb03
commit 94a24e45ee
5 changed files with 28 additions and 8 deletions

View File

@ -276,6 +276,7 @@ subroutine mesh_init()
!!!!!!!!!!!!!!!!!!!!!!!!
allocate(mesh_node0(3,mesh_Nnodes),source=0.0_pReal)
call theMesh%init(dimplex,integrationOrder,mesh_node0)
call theMesh%setNelems(mesh_NcpElems)
end subroutine mesh_init

View File

@ -421,6 +421,7 @@ subroutine tMesh_abaqus_init(self,elemType,nodes)
integer(pInt), intent(in) :: elemType
call self%tMesh%init('mesh',elemType,nodes)
call theMesh%setNelems(mesh_NcpElems)
end subroutine tMesh_abaqus_init

View File

@ -45,6 +45,7 @@ module mesh_base
connectivity
contains
procedure, pass(self) :: tMesh_base_init
procedure :: setNelems => tMesh_base_setNelems ! not needed once we compute the cells from the connectivity
generic, public :: init => tMesh_base_init
end type tMesh
@ -68,4 +69,15 @@ subroutine tMesh_base_init(self,meshType,elemType,nodes)
end subroutine tMesh_base_init
subroutine tMesh_base_setNelems(self,Nelems)
implicit none
class(tMesh) :: self
integer(pInt), intent(in) :: Nelems
self%Nelems = Nelems
end subroutine tMesh_base_setNelems
end module mesh_base

View File

@ -442,7 +442,7 @@ subroutine mesh_init(ip,el)
mesh_microstructureAt = mesh_element(4,:)
mesh_CPnodeID = mesh_element(5:4+mesh_NipsPerElem,:)
!!!!!!!!!!!!!!!!!!!!!!!!
call theMesh%setNelems(mesh_NcpElems)
end subroutine mesh_init
!--------------------------------------------------------------------------------------------------
@ -686,6 +686,8 @@ end function mesh_cellCenterCoordinates
!--------------------------------------------------------------------------------------------------
!> @brief Parses geometry file
!> @details important variables have an implicit "save" attribute. Therefore, this function is
! supposed to be called only once!
!--------------------------------------------------------------------------------------------------
subroutine mesh_spectral_read_grid()
use IO, only: &
@ -706,12 +708,16 @@ subroutine mesh_spectral_read_grid()
real(pReal), dimension(3) :: s = -1_pInt
integer(pInt) :: h =- 1_pInt
integer(pInt) :: &
headerLength = -1_pInt, &
fileLength, &
headerLength = -1_pInt, & !< length of header (in lines)
fileLength, & !< lenght of the geom file (in characters)
fileUnit, &
startPos, endPos, &
myStat, &
l, i, j, e, c
l, & !< line counter
c, & !< counter for # microstructures in line
o, & !< order of "to" packing
e, & !< "element", i.e. spectral collocation point
i, j
logical :: &
gotGrid = .false., &
gotSize = .false., &
@ -807,8 +813,9 @@ subroutine mesh_spectral_read_grid()
c = IO_intValue(line,chunkPos,1)
microGlobal(e:e+c-1_pInt) = [(IO_intValue(line,chunkPos,3),i = 1_pInt,IO_intValue(line,chunkPos,1))]
else if (IO_lc(IO_stringValue(line,chunkPos,2)) == 'to') then
c = IO_intValue(line,chunkPos,3) - IO_intValue(line,chunkPos,1) + 1_pInt
microGlobal(e:e+c-1_pInt) = [(i, i = IO_intValue(line,chunkPos,1),IO_intValue(line,chunkPos,3))]
c = abs(IO_intValue(line,chunkPos,3) - IO_intValue(line,chunkPos,1)) + 1_pInt
o = merge(+1_pInt, -1_pInt, IO_intValue(line,chunkPos,3) > IO_intValue(line,chunkPos,1))
microGlobal(e:e+c-1_pInt) = [(i, i = IO_intValue(line,chunkPos,1),IO_intValue(line,chunkPos,3),o)]
else
c = chunkPos(1)
do i = 0_pInt, c - 1_pInt
@ -822,7 +829,6 @@ subroutine mesh_spectral_read_grid()
enddo
endif
e = e+c
end do

View File

@ -560,7 +560,7 @@ subroutine mesh_init(ip,el)
mesh_CPnodeID = mesh_element(5:4+mesh_NipsPerElem,:)
!!!!!!!!!!!!!!!!!!!!!!!!
call theMesh%init(mesh_element(2,1),mesh_node0)
call theMesh%setNelems(mesh_NcpElems)
end subroutine mesh_init