Skip to content

Commit

Permalink
Merge pull request #18 from hopr-framework/improvement.readinGmsh
Browse files Browse the repository at this point in the history
Read-in of gmsh meshes in Version 4 ASCII
  • Loading branch information
scopplestone authored Feb 5, 2023
2 parents d6fb2b0 + b0ab977 commit 8eecd27
Show file tree
Hide file tree
Showing 9 changed files with 77,612 additions and 104 deletions.
2 changes: 1 addition & 1 deletion src/mesh/globaluniquenodes.f90
Original file line number Diff line number Diff line change
Expand Up @@ -303,7 +303,7 @@ SUBROUTINE GlobalUniqueNodes(withOrientedOpt)
percent=percent+1
WRITE(0,'(I4,A23,A1)',ADVANCE='NO')percent, ' % of nodes evaluated...',ACHAR(13)
END IF ! MOD(iNode,(nTotalNodes/100)).EQ.0
END IF ! nTotalNodes.GT.100000)
END IF ! nTotalNodes.GT.100000
Node=>Nodes(iNode)%np
IF(Node%tmp.GT.0) CYCLE ! node already checked
Node%tmp=iNode !check this node
Expand Down
14 changes: 8 additions & 6 deletions src/mesh/mesh.f90
Original file line number Diff line number Diff line change
Expand Up @@ -289,7 +289,7 @@ SUBROUTINE InitMesh()

! 2.5D mesh
MeshDim=3
IF((MeshMode .EQ. 2) .OR. (MeshMode .EQ. 3))THEN
IF((MeshMode .EQ. 2) .OR. (MeshMode .EQ. 3).OR. (MeshMode .EQ. 5))THEN
! 2.5D mesh: convert 2D mesh to 3D mesh (gambit and cgns mesh only)
MeshDim=GETINT('MeshDim','3')
END IF
Expand Down Expand Up @@ -491,6 +491,7 @@ SUBROUTINE fillMesh()
CALL readStar() ! Read Star file (ANSA)
CASE(5)
CALL readGMSH() ! Read .MSH file (GMSH)
IF(MeshDim .EQ. 2) CALL fill25DMesh() ! Build 3D mesh
CASE(6)
MeshDim=3 !overwrite, build first 3D element layer in readin
CALL readSpecMesh2D()
Expand Down Expand Up @@ -722,7 +723,7 @@ SUBROUTINE fill25DMesh()
! LOCAL VARIABLES
TYPE(tElem),POINTER :: Elem,newElem,FirstElem_loc,lastElem,firstNewElem,lastNewElem ! ?
TYPE(tSide),POINTER :: Side,TempSide ! ?
REAL :: zPos ! ?
REAL :: zPos, zMin
INTEGER :: iNode,BCData(8,5),nNodes ! ?
LOGICAL :: LowerBCSide,UpperBCSide,ConnectionSide,copyBC ! ?
!===================================================================================================================================
Expand All @@ -746,7 +747,8 @@ SUBROUTINE fill25DMesh()
END DO

MeshDim = 3 ! only 3D elements
zPos = DZ
zPos = DZ ! zLength / nElemZ
zMin = FirstElem%firstSide%Node(1)%np%x(3)
NULLIFY(newElem,lastElem,firstNewElem,lastNewElem)

FirstElem_loc => FirstElem
Expand All @@ -758,9 +760,9 @@ SUBROUTINE fill25DMesh()
ConnectionSide = .TRUE.
UpperBCSide = .TRUE.
DO iNode=1,Side%nNodes
IF(ABS( Side%Node(iNode)%np%x(3)) .GT. (PP_MeshTolerance*SpaceQuandt)) LowerBCSide = .FALSE.
IF(ABS((Side%Node(iNode)%np%x(3)-zLength)) .GT. (PP_MeshTolerance*SpaceQuandt)) UpperBCSide = .FALSE.
IF(ABS((Side%Node(iNode)%np%x(3)-zPos)) .GT. (PP_MeshTolerance*SpaceQuandt)) ConnectionSide = .FALSE.
IF(ABS(Side%Node(iNode)%np%x(3) - zMin) .GT. (PP_MeshTolerance*SpaceQuandt)) LowerBCSide = .FALSE.
IF(ABS(Side%Node(iNode)%np%x(3) - zMin - zLength) .GT. (PP_MeshTolerance*SpaceQuandt)) UpperBCSide = .FALSE.
IF(ABS(Side%Node(iNode)%np%x(3) - zMin - zPos).GT.(PP_MeshTolerance*SpaceQuandt)) ConnectionSide = .FALSE.
END DO
IF(.NOT.(LowerBCSide.OR.UpperBCSide.OR.ConnectionSide))THEN
Side=>Side%nextElemSide
Expand Down
2 changes: 1 addition & 1 deletion src/mesh/mesh_vars.f90
Original file line number Diff line number Diff line change
Expand Up @@ -282,7 +282,7 @@ MODULE MOD_Mesh_Vars
!-----------------------------------------------------------------------------------------------------------------------------------
! 2.5D MESH
!-----------------------------------------------------------------------------------------------------------------------------------
REAL :: zLength ! 2.5D mesh: lenght in z-direction
REAL :: zLength ! 2.5D mesh: length in z-direction
REAL :: dz ! MESH%zLength/MESH%nElemsZ
INTEGER :: MeshDim ! Mesh dimesnions: does not need to be equal to nDim (2.5D mesh)
INTEGER :: n2dNodes=0 ! Number of nodes in the 2D mesh
Expand Down
Loading

0 comments on commit 8eecd27

Please sign in to comment.