Skip to content

Commit

Permalink
prepare the vertex connection lists in the build Edges. counting and …
Browse files Browse the repository at this point in the history
…output to hdf5 still missing.
  • Loading branch information
project-fluxo-old committed Nov 24, 2023
1 parent 82ffe5d commit 8de8f10
Show file tree
Hide file tree
Showing 2 changed files with 131 additions and 18 deletions.
74 changes: 63 additions & 11 deletions src/mesh/mesh_basis.f90
Original file line number Diff line number Diff line change
Expand Up @@ -614,9 +614,9 @@ SUBROUTINE buildEdges()
! If the edge is not oriented, it goes from orientedNode(i+1)-> orientedNode(i)
!===================================================================================================================================
! MODULES
USE MOD_Mesh_Vars,ONLY:tElem,tSide,tEdge,tNode,tEdgePtr,tLocalEdge
USE MOD_Mesh_Vars,ONLY:tElem,tSide,tEdge,tNode,tEdgePtr,tLocalEdge,tVertex
USE MOD_Mesh_Vars,ONLY:firstElem
USE MOD_Mesh_Vars,ONLY:GetNewEdge,getNewLocalEdge
USE MOD_Mesh_Vars,ONLY:GetNewEdge,getNewLocalEdge,getNewVertex
IMPLICIT NONE
!-----------------------------------------------------------------------------------------------------------------------------------
! INPUT VARIABLES
Expand All @@ -629,8 +629,9 @@ SUBROUTINE buildEdges()
TYPE(tEdge),POINTER :: aEdge,bEdge ! ?
TYPE(tLocalEdge),POINTER :: lEdge,nextlEdge ! ?
TYPE(tEdgePtr) :: smallEdges(4) ! ?
TYPE(tNode),POINTER :: aNode,bNode ! ?
INTEGER :: iSide,jSide,iEdge,jEdge,kEdge,iNode,iPlus,nSides,EdgeInd,nNodes ! ?
TYPE(tNode),POINTER :: aNode,bNode ! ?
TYPE(tVertex),POINTER :: vert,next_vert
INTEGER :: i,iSide,jSide,iEdge,jEdge,kEdge,iNode,iPlus,nSides,EdgeInd,nNodes ! ?
INTEGER :: indA(2),indB(2,4),indTmp(2)
INTEGER :: edgeCount ! ?
LOGICAL :: edgeFound ! ?
Expand Down Expand Up @@ -812,6 +813,8 @@ SUBROUTINE buildEdges()
DO iEdge=1,aSide%nNodes
iPlus=iEdge+1
IF(iEdge.EQ.aSide%nNodes) iPlus=1

! aSide + edge from aNode->bNode
IF(aSide%edgeOrientation(iEdge))THEN
aNode=>aSide%OrientedNode(iEdge)%np
bNode=>aSide%OrientedNode(iPlus)%np
Expand All @@ -822,7 +825,7 @@ SUBROUTINE buildEdges()
indA(1)=aNode%ind
indA(2)=bNode%ind
edgeFound=.FALSE.
aEdge=>aNode%firstEdge
aEdge=>aNode%firstEdge ! edge list of edges that have the aNode as their first index
DO WHILE (ASSOCIATED(aEdge))
indTmp(1)=aEdge%Node(1)%np%ind
indTmp(2)=aEdge%Node(2)%np%ind
Expand All @@ -833,8 +836,9 @@ SUBROUTINE buildEdges()
aEdge=>aEdge%nextEdge
END DO
IF(.NOT.edgeFound) STOP 'problem in finding periodic side aEdge'
!now for the periodic side (bSide)
IF(bSide%edgeOrientation(iEdge))THEN

!now for the periodic side (bSide,edge from anode->bnode)
IF(bSide%edgeOrientation(iEdge))THEN
aNode=>bSide%OrientedNode(iEdge)%np
bNode=>bSide%OrientedNode(iPlus)%np
ELSE
Expand All @@ -854,11 +858,10 @@ SUBROUTINE buildEdges()
END IF
bEdge=>bEdge%nextEdge
END DO
IF(.NOT.edgeFound) STOP 'problem in finding periodic side aEdge'
IF(.NOT.edgeFound) STOP 'problem in finding periodic side bEdge'

!set firstLocalEdge to the same global edge
IF(.NOT.ASSOCIATED(bEdge%FirstLocalEdge))THEN
ALLOCATE(bEdge%FirstLocalEdge)
IF(.NOT.ASSOCIATED(aEdge%FirstLocalEdge))THEN
CALL getNewLocalEdge(aEdge%FirstLocalEdge,Elem_in=aElem,Edge_in=aEdge)
aEdge%FirstLocalEdge%tmp=1
Expand All @@ -875,6 +878,31 @@ SUBROUTINE buildEdges()
END IF
END IF !aedge
END IF !bedge%firstlocalEdge not associated
!now the vertex periodic connections!
DO i=1,2 ! i=1: iEdge (edge first node), =2: iPlus (edge second node)
aNode=>aSide%OrientedNode(MERGE(iEdge,iPlus,i.EQ.1))%np ! node of aEdge
bNode=>bSide%OrientedNode(MERGE(iEdge,iPlus,i.EQ.1))%np !corresponding periodic node of bEdge
aNode%ind=-777
bNode%ind=-777
IF(.NOT.ASSOCIATED(bNode%FirstVertex))THEN
IF(.NOT.ASSOCIATED(aNode%FirstVertex))THEN
CALL getNewVertex(aNode%FirstVertex,Elem_in=aElem,Node_in=aNode)
aNode%FirstVertex%tmp=1
END IF! anode%firstVertex not associated
bNode%FirstVertex=>aNode%FirstVertex
aNode%FirstVertex%tmp=aNode%FirstVertex%tmp+1 !count vertex multiplicity in firstVertex%tmp
ELSE
IF(.NOT.ASSOCIATED(aNode%FirstVertex))THEN
aNode%FirstVertex=>bNode%FirstVertex
bNode%FirstVertex%tmp=bNode%FirstVertex%tmp+1 !count vertex multiplicity in firstVertex%tmp
ELSE
IF(LOC(aNode%FirstVertex%Node).NE.LOC(bNode%FirstVertex%Node))THEN
STOP 'something wrong with periodic aNode bNode'
END IF
END IF !anode
END IF !bnode%firstVertex not associated
END DO

END DO !iEdge=1,bSide%nnodes
END IF ! BC periodic
END IF ! BC side
Expand Down Expand Up @@ -927,11 +955,35 @@ SUBROUTINE buildEdges()
CGNSElemEdgeToNode(8,12,1:2)=(/8,5/)


! Build elem to localEdge
! Build elem to localEdge / Vertex
aElem=>firstElem
DO WHILE(ASSOCIATED(aElem))
aElem%nEdges=nEdges_from_nNodes(aElem%nNodes)
ALLOCATE(aElem%localEdge(aElem%nEdges))
ALLOCATE(aElem%Vertex(aElem%nNodes))
! fill element vertex
DO iNode=1,aElem%nNodes
aNode=>aElem%Node(iNode)%np
CALL GetNewVertex(aElem%Vertex(iNode)%vp,Elem_in=aElem,localVertexID_in=iNode)
vert=>aElem%Vertex(iNode)%vp
IF(.NOT.ASSOCIATED(aNode%firstVertex))THEN
IF(aNode%ind.EQ.-777) STOP 'firstVertex should be associated'
aNode%FirstVertex=>vert
vert%node=>aNode
aNode%FirstVertex%tmp=aNode%FirstVertex%tmp+1 !vertex multiplicity counted on FirstVertex%tmp (master vertex)
ELSE
IF(aNode%ind.NE.-777) STOP 'firstVertex must be already associated'
WRITE(*,*)'DEBUG',ASSOCIATED(aNode%FirstVertex),aNode%ind

next_vert=>aNode%FirstVertex%next_connected
DO WHILE(ASSOCIATED(next_vert))
next_vert=>next_vert%next_connected
END DO
next_vert%next_connected=>vert !append to vertex connectivity list
vert%tmp=-1 ! mark as slave vertex
END IF
END DO !iNode
!fill element edges
DO iEdge=1,aElem%nEdges
aNode=>aElem%Node(CGNSElemEdgeToNode(aElem%nNodes,iEdge,1))%np
bNode=>aElem%Node(CGNSElemEdgeToNode(aElem%nNodes,iEdge,2))%np
Expand Down Expand Up @@ -963,7 +1015,7 @@ SUBROUTINE buildEdges()
DO WHILE(ASSOCIATED(nextlEdge))
nextlEdge=>nextlEdge%next_connected
END DO
nextlEdge%next_connected=>lEdge
nextlEdge%next_connected=>lEdge !append to edge connectivity list
lEdge%tmp=-1
END IF
ELSE
Expand Down
75 changes: 68 additions & 7 deletions src/mesh/mesh_vars.f90
Original file line number Diff line number Diff line change
Expand Up @@ -58,13 +58,18 @@ MODULE MOD_Mesh_Vars
TYPE(tNode),POINTER :: NP ! node pointer
END TYPE tNodePtr

TYPE tVertexPtr
TYPE(tVertex),POINTER :: VP ! vertex pointer
END TYPE tVertexPtr

! Actual derived types ------------------------------------------------------------------------------------------------------------
TYPE tElem ! provides data structure for local element
! Derived data types -----------------------------------------------!
TYPE(tSide), POINTER :: firstSide ! pointer to element's first side
TYPE(tNodePtr),POINTER :: node(:) ! pointer to element's nodes used for restart and meshing
TYPE(tNodePtr),POINTER :: curvedNode(:) ! ?
TYPE(tLocalEdgePtr),POINTER :: localEdge(:) ! allocated with number of edges in the element
TYPE(tLocalEdgePtr),POINTER :: localEdge(:) ! allocated with number of edges in the element, CGNS ordering
TYPE(tVertexPtr),POINTER :: Vertex(:) ! allocated with number of vertices in the element, CGNS ordering
TYPE(tElem),POINTER :: nextElem ! pointer to next element in order to continue a loop
TYPE(tElem),POINTER :: prevElem ! pointer to previous element in order to continue a loop
TYPE(tElem),POINTER :: tree ! pointer to tree if MortarMesh=1
Expand Down Expand Up @@ -119,31 +124,43 @@ MODULE MOD_Mesh_Vars
TYPE(tEdgePtr),POINTER :: MortarEdge(:) ! array of edge pointers to slave mortar edges
TYPE(tEdge),POINTER :: parentEdge ! parentEdge in case of non-conforming meshes
TYPE(tLocalEdge),POINTER :: FirstLocalEdge ! pointer to local edge of first connected element
INTEGER :: ind
INTEGER :: ind ! used for global edge index (geometrical)
END TYPE tEdge


TYPE tLocalEdge ! provides data structure for local element edges, needed for edge connectivity
TYPE(tEdge),POINTER :: Edge ! pointer back to geometrically unique edge
TYPE(tLocalEdge),POINTER :: next_connected ! pointer
TYPE(tElem),POINTER :: elem ! pointer to element connected to that edge
INTEGER :: localEdgeID !local edge id in connected element
INTEGER :: localEdgeID !local edge id in connected element (CGNS standard)
LOGICAL :: orientation ! orientation from local to global edge (True: same, False: opposite)
INTEGER :: ind ! edge counter
INTEGER :: tmp ! ?
INTEGER :: ind ! used for global FEMedge index (topological, so with periodic BCs)
INTEGER :: tmp ! used as counter for the list of edge connections
END TYPE tLocalEdge

TYPE tNode ! provides data structure for local node
TYPE(tNormal),POINTER :: firstNormal ! pointer to first normal of node
TYPE(tEdge),POINTER :: firstEdge ! pointer to first normal of node
REAL :: x(3) ! node coordinates
INTEGER :: ind ! node counter
INTEGER :: ind ! used for global node index (geometrical)
INTEGER :: tmp ! ?
INTEGER :: refCount ! In general nodes are used by more than
! ! one side / element -> Node%refCount > 1
! ! Node%refCount = 0 means that node is not used any more
TYPE(tVertex),POINTER :: FirstVertex ! pointer to the beginning of the vertex connection list
END TYPE tNode


TYPE tVertex ! provides data structure for local element "vertices", needed for vertex connectivity
TYPE(tNode),POINTER :: node ! pointer back to geometrically unique node
TYPE(tVertex),POINTER :: next_connected ! pointer to next connected vertex
TYPE(tElem),POINTER :: elem ! pointer to element connected to that vertex
INTEGER :: localVertexID ! local vertex id in connected element (CGNS standard)
INTEGER :: ind ! used for global FEMVertex index (topological, so with periodic BCs)
INTEGER :: tmp ! used as counter for the list of vertex connections
END TYPE tVertex


TYPE tNormal
REAL :: normal(3) ! Normals(nDim) normals vector of a node
INTEGER,ALLOCATABLE :: FaceID(:) ! FaceID(maxFaceIDs) normal vector from CAD geometry
Expand Down Expand Up @@ -364,6 +381,11 @@ MODULE MOD_Mesh_Vars
MODULE PROCEDURE getNewNode
END INTERFACE


INTERFACE getNewVertex
MODULE PROCEDURE getNewVertex
END INTERFACE

INTERFACE getNewQuad
MODULE PROCEDURE getNewQuad
END INTERFACE
Expand Down Expand Up @@ -549,6 +571,45 @@ SUBROUTINE getNewLocalEdge(lEdge,localEdgeID_in,Elem_in,edge_in)
END IF
END SUBROUTINE getNewLocalEdge

SUBROUTINE getNewVertex(vert,localVertexID_in,Elem_in,node_in)
!===================================================================================================================================
! Create "Edge" with nodes "Node1" and "Node2"
!===================================================================================================================================
! MODULES
! IMPLICIT VARIABLE HANDLING
IMPLICIT NONE
!-----------------------------------------------------------------------------------------------------------------------------------
! INPUT VARIABLES
INTEGER,INTENT(IN),OPTIONAL :: localVertexID_in
TYPE(tElem),POINTER,INTENT(IN),OPTIONAL :: Elem_in
TYPE(tNode),POINTER,INTENT(IN),OPTIONAL :: node_in
!-----------------------------------------------------------------------------------------------------------------------------------
! OUTPUT VARIABLES
TYPE(tVertex),POINTER,INTENT(INOUT) :: vert ! New edge
!-----------------------------------------------------------------------------------------------------------------------------------
! LOCAL VARIABLES
!===================================================================================================================================
ALLOCATE(vert)
vert%ind=0
vert%tmp=0
NULLIFY(vert%next_connected)
IF(PRESENT(localVertexID_in))THEN
vert%localVertexID=localVertexID_in
ELSE
vert%localVertexID=0
END IF
IF(PRESENT(elem_in))THEN
vert%elem=>elem_in
ELSE
NULLIFY(vert%elem)
END IF
IF(PRESENT(node_in))THEN
vert%node=>node_in
ELSE
NULLIFY(vert%node)
END IF
END SUBROUTINE getNewVertex


SUBROUTINE getNewNode(Node,refCount,ind)
!===================================================================================================================================
Expand Down

0 comments on commit 8de8f10

Please sign in to comment.