InitiateNodeToNodeData
This routine initiates nodeToNode data (mapping) between two domains or parts of domains.
Interface1​
This subroutine generates the node to node connectivity between two meshes
obj%nodeToNode
will be initiateddomain1
main domaindomain2
secondary domaindim1, entitynum1
dimension and entity number of mesh indomain1
dim2, entitynum2
dimension and entity number of mesh indomain2
In this case bounds of nodeToNode
will be from 1 to mesh1%maxNptrs
.
INTERFACE
MODULE SUBROUTINE dc_InitiateNodeToNodeData1(obj, domain1, domain2, &
& dim1, dim2, entityNum1, entityNum2)
CLASS(DomainConnectivity_), INTENT(INOUT) :: obj
!! Domain connectivity object,
!! [[DomainConnectivity:nodeToNode]] will be initiated
CLASS(Domain_), INTENT(IN) :: domain1
!! Primary domain, in nodeToNode(i), i denotes the
!! global node number in domain1 domain.
CLASS(Domain_), INTENT(IN) :: domain2
!! secondary domain, => nodeToNode(i) denotes the
!! global node number in `domain2` domain.
INTEGER(I4B), INTENT(IN) :: dim1
!! dimension of mesh in domain1
INTEGER(I4B), INTENT(IN) :: dim2
!! dimension of mesh in domain2
INTEGER(I4B), INTENT(IN) :: entityNum1
!! entity num of mesh in domain1
INTEGER(I4B), INTENT(IN) :: entityNum2
!! entity num of mesh in domain2
END SUBROUTINE dc_InitiateNodeToNodeData1
END INTERFACE
- ️܀ Example 1
- ️܀ Example 2
- ️܀ Example 3
- ️܀ Example 4
- ️܀ Example 5
- ↢
In this example we will generate node to node-connectivity information between part of pressure-domain and part of pressure-Domain.
Pressure domain consists Triangle3 elements as shown below.
Importing modules and variables
PROGRAM main
USE easifemBase
USE easifemClasses
IMPLICIT NONE
TYPE(DomainConnectivity_) :: obj
TYPE( Domain_ ) :: pressureDomain
TYPE( HDF5File_ ) :: pressureMeshFile
CLASS( Mesh_ ), POINTER :: pressureMesh
INTEGER( I4B ), POINTER :: nodeToNode( : )
REAL( DFP ), POINTER :: pressureNode( :, : )
INTEGER( I4B ) :: ii
CALL pressureMeshFile%Initiate( FileName="./mesh_tri3.h5", MODE="READ" )
CALL pressureMeshFile%Open()
CALL pressureDomain%Initiate( pressureMeshFile, "")
CALL pressureMeshFile%Deallocate()
This will create node to node-connectivity data from domain1 (dim=2, entityNum=1) to domain2 (dim=2, entityNum=2).
CALL obj%InitiateNodeToNodeData( domain1=pressureDomain, &
& domain2=pressureDomain, dim1=2, entityNum1=1, dim2=2, entityNum2=1)
nodeToNode => obj%getNodeToNodePointer()
pressureMesh => pressureDomain%getMeshPointer( 2, 1 )
pressureNode => pressureDomain%getNodeCoordPointer()
DO ii = pressureMesh%minNptrs, pressureMesh%maxNptrs
IF( .NOT. pressureMesh%isNodePresent( globalNode=ii ) ) CYCLE
IF( ALL( pressureNode(:,pressureDomain%getLocalNodeNumber(ii)) &
& .APPROXEQ. &
& pressureNode(:, &
& pressureDomain%getLocalNodeNumber(nodeToNode(ii)))) ) THEN
!CALL Display( "pressure Node = " // TOSTRING(ii) &
! & // " matches with pressure Node = " // TOSTRING( nodeToNode(ii)))
ELSE
CALL Display( "ERROR: pressure Node = " // TOSTRING(ii) &
& // " not matches with pressure Node = " &
& // TOSTRING( nodeToNode(ii)))
STOP
END IF
END DO
call OK(.TRUE.)
Cleaning up.
CALL pressureDomain%Deallocate()
CALL obj%Deallocate()
END PROGRAM main
In this example we will generate node to node connectivity information between part of velocity-domain and part of velocity-Domain.
Velocity domain consists Triangle6 elements as shown below.
Import modules and define variables
PROGRAM main
USE easifemBase
USE easifemClasses
IMPLICIT NONE
TYPE(DomainConnectivity_) :: obj
TYPE( Domain_ ) :: velocityDomain
TYPE( HDF5File_ ) :: velocityMeshFile
CLASS( Mesh_ ), POINTER :: velocityMesh
INTEGER( I4B ), POINTER :: nodeToNode( : )
REAL( DFP ), POINTER :: velocityNode( :, : )
INTEGER( I4B ) :: ii
CALL velocityMeshFile%Initiate( FileName="./mesh_tri6.h5", MODE="READ" )
CALL velocityMeshFile%Open()
CALL velocityDomain%Initiate( velocityMeshFile, "")
CALL velocityMeshFile%Deallocate()
CALL obj%InitiateNodeToNodeData( domain1=velocityDomain, &
& domain2=velocityDomain, dim1=2, entityNum1=1, dim2=2, entityNum2=1)
nodeToNode => obj%getNodeToNodePointer()
velocityMesh => velocityDomain%getMeshPointer( 2, 1 )
velocityNode => velocityDomain%getNodeCoordPointer()
Simple testing
DO ii = velocityMesh%minNptrs, velocityMesh%maxNptrs
IF( .NOT. velocityMesh%isNodePresent( globalNode=ii ) ) CYCLE
IF( nodeToNode( ii ) .EQ. 0 ) THEN
CALL Display( "ERRRO: nodeToNode( "//TOSTRING(ii) // ") = 0 " )
STOP
END IF
IF( ALL( velocityNode(:,velocityDomain%getLocalNodeNumber(ii)) &
& .APPROXEQ. &
& velocityNode(:, &
& velocityDomain%getLocalNodeNumber(nodeToNode(ii)))) ) THEN
!CALL Display( "velocity Node = " // TOSTRING(ii) &
! & // " matches with velocity Node = " // TOSTRING( nodeToNode(ii)))
ELSE
CALL Display( "ERROR: velocity Node = " // TOSTRING(ii) &
& // " not matches with velocity Node = " &
& // TOSTRING( nodeToNode(ii)))
STOP
END IF
END DO
CALL OK(.true.)
cleaning up
CALL velocityDomain%Deallocate()
CALL obj%Deallocate()
END PROGRAM main
In this example we will generate node to node connectivity information between part of velocity-domain and part of pressure-Domain.
Pressure domain consists Triangle3 elements as shown below.
Velocity domain consists Triangle6 elements as shown below.
PROGRAM main
USE easifemBase
USE easifemClasses
IMPLICIT NONE
TYPE(DomainConnectivity_) :: obj
TYPE( Domain_ ) :: pressureDomain
TYPE( Domain_ ) :: velocityDomain
TYPE( HDF5File_ ) :: pressureMeshFile
TYPE( HDF5File_ ) :: velocityMeshFile
CLASS( Mesh_ ), POINTER :: velocityMesh
CLASS( Mesh_ ), POINTER :: pressureMesh
INTEGER( I4B ), POINTER :: nodeToNode( : )
REAL( DFP ), POINTER :: pressureNode( :, : )
REAL( DFP ), POINTER :: velocityNode( :, : )
INTEGER( I4B ) :: ii
CALL velocityMeshFile%Initiate( FileName="./mesh_tri6.h5", MODE="READ" )
CALL velocityMeshFile%Open()
CALL pressureMeshFile%Initiate( FileName="./mesh_tri3.h5", MODE="READ" )
CALL pressureMeshFile%Open()
CALL velocityDomain%Initiate( velocityMeshFile, "")
CALL velocityMeshFile%Deallocate()
CALL pressureDomain%Initiate( pressureMeshFile, "")
CALL pressureMeshFile%Deallocate()
CALL obj%InitiateNodeToNodeData( domain1=velocityDomain, &
& domain2=pressureDomain, dim1=2, entityNum1=1, dim2=2, entityNum2=1)
nodeToNode => obj%getNodeToNodePointer()
velocityMesh => velocityDomain%getMeshPointer( 2, 1 )
pressureMesh => pressureDomain%getMeshPointer( 2, 1 )
pressureNode => pressureDomain%getNodeCoordPointer()
velocityNode => velocityDomain%getNodeCoordPointer()
running some simple tests.
DO ii = velocityMesh%minNptrs, velocityMesh%maxNptrs
IF( .NOT. velocityMesh%isNodePresent( globalNode=ii ) ) CYCLE
IF( nodeToNode( ii ) .EQ. 0 ) CYCLE
IF( ALL( velocityNode(:,velocityDomain%getLocalNodeNumber(ii)) &
& .APPROXEQ. pressureNode(:, &
& pressureDomain%getLocalNodeNumber(nodeToNode(ii)))) ) THEN
!CALL Display( "velocity Node = " // TOSTRING(ii) &
! & // " matches with pressure Node = " // TOSTRING( nodeToNode(ii)))
ELSE
CALL Display( "ERROR: velocity Node = " // TOSTRING(ii) &
& // " not matches with pressure Node = " &
& // TOSTRING( nodeToNode(ii)))
STOP
END IF
END DO
CALL OK(.true.)
Cleanup
CALL pressureDomain%Deallocate()
CALL velocityDomain%Deallocate()
CALL obj%Deallocate()
END PROGRAM main
In this example we will generate node to node-connectivity information between part of velocity-domain (dim=2, entity=1) and part of pressure-Domain (dim=1).
Pressure domain consists Triangle3 elements as shown below.
Velocity domain consists Triangle6 elements as shown below.
PROGRAM main
USE easifemBase
USE easifemClasses
IMPLICIT NONE
TYPE(DomainConnectivity_) :: obj
TYPE( Domain_ ) :: pressureDomain
TYPE( Domain_ ) :: velocityDomain
TYPE( HDF5File_ ) :: pressureMeshFile
TYPE( HDF5File_ ) :: velocityMeshFile
CLASS( Mesh_ ), POINTER :: velocityMesh
CLASS( Mesh_ ), POINTER :: pressureMesh
INTEGER( I4B ), POINTER :: nodeToNode( : )
REAL( DFP ), POINTER :: pressureNode( :, : )
REAL( DFP ), POINTER :: velocityNode( :, : )
INTEGER( I4B ), PARAMETER :: dim1=2, dim2=1, entityNum1=1, entityNum2=1
INTEGER( I4B ) :: ii
CALL velocityMeshFile%Initiate( FileName="./mesh_tri6.h5", MODE="READ" )
CALL velocityMeshFile%Open()
CALL pressureMeshFile%Initiate( FileName="./mesh_tri3.h5", MODE="READ" )
CALL pressureMeshFile%Open()
CALL velocityDomain%Initiate( velocityMeshFile, "")
CALL velocityMeshFile%Deallocate()
CALL pressureDomain%Initiate( pressureMeshFile, "")
CALL pressureMeshFile%Deallocate()
CALL obj%InitiateNodeToNodeData( domain1=velocityDomain, &
& domain2=pressureDomain, dim1=dim1, entityNum1=entityNum1, &
& dim2=dim2, entityNum2=entityNum2 )
nodeToNode => obj%getNodeToNodePointer()
velocityMesh => velocityDomain%getMeshPointer( dim1, entityNum1 )
pressureMesh => pressureDomain%getMeshPointer( dim2, entityNum2 )
pressureNode => pressureDomain%getNodeCoordPointer()
velocityNode => velocityDomain%getNodeCoordPointer()
Simple testing
DO ii = velocityMesh%minNptrs, velocityMesh%maxNptrs
IF( .NOT. velocityMesh%isNodePresent( globalNode=ii ) ) CYCLE
IF( nodeToNode( ii ) .EQ. 0 ) CYCLE
IF( ALL( velocityNode(:,velocityDomain%getLocalNodeNumber(ii)) &
& .APPROXEQ. pressureNode(:, &
& pressureDomain%getLocalNodeNumber(nodeToNode(ii)))) ) THEN
!CALL Display( "velocity Node = " // TOSTRING(ii) &
! & // " matches with pressure Node = " // TOSTRING( nodeToNode(ii)))
ELSE
CALL Display( "ERROR: velocity Node = " // TOSTRING(ii) &
& // " not matches with pressure Node = " &
& // TOSTRING( nodeToNode(ii)))
STOP
END IF
END DO
call ok(.true.)
Cleanup
CALL pressureDomain%Deallocate()
CALL velocityDomain%Deallocate()
CALL obj%Deallocate()
END PROGRAM main
In this example we will generate node to node-connectivity information between part of velocity-domain (2,1) and part of pressure-Domain (1,2).
Pressure domain consists Triangle3 elements as shown below.
Velocity domain consists Triangle6 elements as shown below.
PROGRAM main
USE easifemBase
USE easifemClasses
IMPLICIT NONE
TYPE(DomainConnectivity_) :: obj
TYPE( Domain_ ) :: pressureDomain
TYPE( Domain_ ) :: velocityDomain
TYPE( HDF5File_ ) :: pressureMeshFile
TYPE( HDF5File_ ) :: velocityMeshFile
CLASS( Mesh_ ), POINTER :: velocityMesh
CLASS( Mesh_ ), POINTER :: pressureMesh
INTEGER( I4B ), POINTER :: nodeToNode( : )
REAL( DFP ), POINTER :: pressureNode( :, : )
REAL( DFP ), POINTER :: velocityNode( :, : )
INTEGER( I4B ), PARAMETER :: dim1=2, entityNum1=1, dim2=1, entityNum2=2
INTEGER( I4B ) :: ii
CALL velocityMeshFile%Initiate( FileName="./mesh_tri6.h5", MODE="READ" )
CALL velocityMeshFile%Open()
CALL pressureMeshFile%Initiate( FileName="./mesh_tri3.h5", MODE="READ" )
CALL pressureMeshFile%Open()
CALL velocityDomain%Initiate( velocityMeshFile, "")
CALL velocityMeshFile%Deallocate()
CALL pressureDomain%Initiate( pressureMeshFile, "")
CALL pressureMeshFile%Deallocate()
CALL obj%InitiateNodeToNodeData( domain1=velocityDomain, &
& domain2=pressureDomain, dim1=dim1, entityNum1=entityNum1, &
& dim2=dim2, entityNum2=entityNum2 )
nodeToNode => obj%getNodeToNodePointer()
velocityMesh => velocityDomain%getMeshPointer( dim1, entityNum1 )
pressureMesh => pressureDomain%getMeshPointer( dim2, entityNum2 )
pressureNode => pressureDomain%getNodeCoordPointer()
velocityNode => velocityDomain%getNodeCoordPointer()
Simple testing
DO ii = velocityMesh%minNptrs, velocityMesh%maxNptrs
IF( .NOT. velocityMesh%isNodePresent( globalNode=ii ) ) CYCLE
IF( nodeToNode( ii ) .EQ. 0 ) CYCLE
IF( ALL( velocityNode(:,velocityDomain%getLocalNodeNumber(ii)) &
& .APPROXEQ. pressureNode(:, &
& pressureDomain%getLocalNodeNumber(nodeToNode(ii)))) ) THEN
!CALL Display( "velocity Node = " // TOSTRING(ii) &
! & // " matches with pressure Node = " // TOSTRING( nodeToNode(ii)))
ELSE
CALL Display( "ERROR: velocity Node = " // TOSTRING(ii) &
& // " not matches with pressure Node = " &
& // TOSTRING( nodeToNode(ii)))
STOP
END IF
END DO
call ok(.true.)
cleanup
CALL pressureDomain%Deallocate()
CALL velocityDomain%Deallocate()
CALL obj%Deallocate()
END PROGRAM main
- ️܀ Example 6
- ️܀ Example 7
- ️܀ Example 8
- ↢
In this example we will generate node to node-connectivity information between part of velocity-domain (2,1) and part of pressure-Domain (1,3).
Pressure domain consists Triangle3 elements as shown below.
Velocity domain consists Triangle6 elements as shown below.
PROGRAM main
USE easifemBase
USE easifemClasses
IMPLICIT NONE
TYPE(DomainConnectivity_) :: obj
TYPE( Domain_ ) :: pressureDomain
TYPE( Domain_ ) :: velocityDomain
TYPE( HDF5File_ ) :: pressureMeshFile
TYPE( HDF5File_ ) :: velocityMeshFile
CLASS( Mesh_ ), POINTER :: velocityMesh
CLASS( Mesh_ ), POINTER :: pressureMesh
INTEGER( I4B ), POINTER :: nodeToNode( : )
REAL( DFP ), POINTER :: pressureNode( :, : )
REAL( DFP ), POINTER :: velocityNode( :, : )
INTEGER( I4B ), PARAMETER :: dim1=2, entityNum1=1, dim2=1, entityNum2=3
INTEGER( I4B ) :: ii
CALL velocityMeshFile%Initiate( FileName="./mesh_tri6.h5", MODE="READ" )
CALL velocityMeshFile%Open()
CALL pressureMeshFile%Initiate( FileName="./mesh_tri3.h5", MODE="READ" )
CALL pressureMeshFile%Open()
CALL velocityDomain%Initiate( velocityMeshFile, "")
CALL velocityMeshFile%Deallocate()
CALL pressureDomain%Initiate( pressureMeshFile, "")
CALL pressureMeshFile%Deallocate()
CALL obj%InitiateNodeToNodeData( domain1=velocityDomain, &
& domain2=pressureDomain, dim1=dim1, entityNum1=entityNum1, &
& dim2=dim2, entityNum2=entityNum2 )
nodeToNode => obj%getNodeToNodePointer()
velocityMesh => velocityDomain%getMeshPointer( dim1, entityNum1 )
pressureMesh => pressureDomain%getMeshPointer( dim2, entityNum2 )
pressureNode => pressureDomain%getNodeCoordPointer()
velocityNode => velocityDomain%getNodeCoordPointer()
Simple testing
DO ii = velocityMesh%minNptrs, velocityMesh%maxNptrs
IF( .NOT. velocityMesh%isNodePresent( globalNode=ii ) ) CYCLE
IF( nodeToNode( ii ) .EQ. 0 ) CYCLE
IF( ALL( velocityNode(:,velocityDomain%getLocalNodeNumber(ii)) &
& .APPROXEQ. pressureNode(:, &
& pressureDomain%getLocalNodeNumber(nodeToNode(ii)))) ) THEN
!CALL Display( "velocity Node = " // TOSTRING(ii) &
! & // " matches with pressure Node = " // TOSTRING( nodeToNode(ii)))
ELSE
CALL Display( "ERROR: velocity Node = " // TOSTRING(ii) &
& // " not matches with pressure Node = " &
& // TOSTRING( nodeToNode(ii)))
STOP
END IF
END DO
call ok(.true.)
clean up
CALL pressureDomain%Deallocate()
CALL velocityDomain%Deallocate()
CALL obj%Deallocate()
END PROGRAM main
In this example we will generate node to node connectivity information between part of velocity-domain (2,1) and part of pressure-Domain (1,4).
Pressure domain consists Triangle3 elements as shown below.
Velocity domain consists Triangle6 elements as shown below.
PROGRAM main
USE easifemBase
USE easifemClasses
IMPLICIT NONE
TYPE(DomainConnectivity_) :: obj
TYPE( Domain_ ) :: pressureDomain
TYPE( Domain_ ) :: velocityDomain
TYPE( HDF5File_ ) :: pressureMeshFile
TYPE( HDF5File_ ) :: velocityMeshFile
CLASS( Mesh_ ), POINTER :: velocityMesh
CLASS( Mesh_ ), POINTER :: pressureMesh
INTEGER( I4B ), POINTER :: nodeToNode( : )
REAL( DFP ), POINTER :: pressureNode( :, : )
REAL( DFP ), POINTER :: velocityNode( :, : )
INTEGER( I4B ), PARAMETER :: dim1=2, entityNum1=1, dim2=1, entityNum2=4
INTEGER( I4B ) :: ii
CALL velocityMeshFile%Initiate( FileName="./mesh_tri6.h5", MODE="READ" )
CALL velocityMeshFile%Open()
CALL pressureMeshFile%Initiate( FileName="./mesh_tri3.h5", MODE="READ" )
CALL pressureMeshFile%Open()
CALL velocityDomain%Initiate( velocityMeshFile, "")
CALL velocityMeshFile%Deallocate()
CALL pressureDomain%Initiate( pressureMeshFile, "")
CALL pressureMeshFile%Deallocate()
CALL obj%InitiateNodeToNodeData( domain1=velocityDomain, &
& domain2=pressureDomain, dim1=dim1, entityNum1=entityNum1, &
& dim2=dim2, entityNum2=entityNum2 )
nodeToNode => obj%getNodeToNodePointer()
velocityMesh => velocityDomain%getMeshPointer( dim1, entityNum1 )
pressureMesh => pressureDomain%getMeshPointer( dim2, entityNum2 )
pressureNode => pressureDomain%getNodeCoordPointer()
velocityNode => velocityDomain%getNodeCoordPointer()
Simple testing
DO ii = velocityMesh%minNptrs, velocityMesh%maxNptrs
IF( .NOT. velocityMesh%isNodePresent( globalNode=ii ) ) CYCLE
IF( nodeToNode( ii ) .EQ. 0 ) CYCLE
IF( ALL( velocityNode(:,velocityDomain%getLocalNodeNumber(ii)) &
& .APPROXEQ. pressureNode(:, &
& pressureDomain%getLocalNodeNumber(nodeToNode(ii)))) ) THEN
CALL Display( "velocity Node = " // TOSTRING(ii) &
& // " matches with pressure Node = " // TOSTRING( nodeToNode(ii)))
ELSE
CALL Display( "ERROR: velocity Node = " // TOSTRING(ii) &
& // " not matches with pressure Node = " &
& // TOSTRING( nodeToNode(ii)))
STOP
END IF
END DO
cleanup
CALL pressureDomain%Deallocate()
CALL velocityDomain%Deallocate()
CALL obj%Deallocate()
END PROGRAM main
In this example we will generate node to node connectivity information between part of velocity-domain (2,1) and part of pressure-Domain (2,1).
Pressure domain consists Triangle3 elements as shown below.
Velocity domain consists Triangle6 elements as shown below.
PROGRAM main
USE easifemBase
USE easifemClasses
IMPLICIT NONE
TYPE(DomainConnectivity_) :: obj
TYPE( Domain_ ) :: pressureDomain
TYPE( Domain_ ) :: velocityDomain
TYPE( HDF5File_ ) :: pressureMeshFile
TYPE( HDF5File_ ) :: velocityMeshFile
CLASS( Mesh_ ), POINTER :: velocityMesh
CLASS( Mesh_ ), POINTER :: pressureMesh
INTEGER( I4B ), POINTER :: nodeToNode( : )
REAL( DFP ), POINTER :: pressureNode( :, : )
REAL( DFP ), POINTER :: velocityNode( :, : )
INTEGER( I4B ), PARAMETER :: dim1=2, entityNum1=1, dim2=2, entityNum2=1
INTEGER( I4B ) :: ii
CALL velocityMeshFile%Initiate( FileName="./mesh_tri6.h5", MODE="READ" )
CALL velocityMeshFile%Open()
CALL pressureMeshFile%Initiate( FileName="./mesh_tri3.h5", MODE="READ" )
CALL pressureMeshFile%Open()
CALL velocityDomain%Initiate( velocityMeshFile, "")
CALL velocityMeshFile%Deallocate()
CALL pressureDomain%Initiate( pressureMeshFile, "")
CALL pressureMeshFile%Deallocate()
CALL obj%InitiateNodeToNodeData( domain2=velocityDomain, &
& domain1=pressureDomain, dim1=dim1, entityNum1=entityNum1, &
& dim2=dim2, entityNum2=entityNum2 )
nodeToNode => obj%getNodeToNodePointer()
velocityMesh => velocityDomain%getMeshPointer( dim1, entityNum1 )
pressureMesh => pressureDomain%getMeshPointer( dim2, entityNum2 )
pressureNode => pressureDomain%getNodeCoordPointer()
velocityNode => velocityDomain%getNodeCoordPointer()
Simple testing
DO ii = pressureMesh%minNptrs, pressureMesh%maxNptrs
IF( .NOT. pressureMesh%isNodePresent( globalNode=ii ) ) CYCLE
IF( nodeToNode( ii ) .EQ. 0 ) CYCLE
IF( ALL( pressureNode(:,pressureDomain%getLocalNodeNumber(ii)) &
& .APPROXEQ. velocityNode(:, &
& velocityDomain%getLocalNodeNumber(nodeToNode(ii)))) ) THEN
CALL Display( "pressure Node = " // TOSTRING(ii) &
& // " matches with velocity Node = " // TOSTRING( nodeToNode(ii)))
ELSE
CALL Display( "ERROR: pressure Node = " // TOSTRING(ii) &
& // " not matches with velocity Node = " &
& // TOSTRING( nodeToNode(ii)))
STOP
END IF
END DO
Cleanup
CALL pressureDomain%Deallocate()
CALL velocityDomain%Deallocate()
CALL obj%Deallocate()
END PROGRAM main
Interface2​
INTERFACE
MODULE SUBROUTINE dc_InitiateNodeToNodeData2(obj, domain1, domain2)
CLASS(DomainConnectivity_), INTENT(INOUT) :: obj
!! Domain connectivity object
CLASS(Domain_), INTENT(IN) :: domain1
!! Primary domain, in nodeToNode(i), i denotes the
!! global node number in domain1 domain.
CLASS(Domain_), INTENT(IN) :: domain2
!! Secondary domain => nodeToNode(i) denotes the
!! global node number in domain2 domain.
END SUBROUTINE dc_InitiateNodeToNodeData2
END INTERFACE
!# Introduction
!
! This subroutine generates the node to node connectivity between two domains
!
!@note
!In this routine nodeToNode connectivity info of all meshes in domain1 to
!all meshes in the domain2 will be generated!
!@endnote
!
! - `obj%nodeToNode` will be initiated
! - `domain1` main domain
! - `domain2` secondary domain
- ️܀ Example 1
- ️܀ Example 2
- ↢
In this example we will generate node to node connectivity information between velocity-domain and pressure-Domain.
Pressure domain consists Triangle3 elements as shown below.
Velocity domain consists Triangle6 elements as shown below.
PROGRAM main
USE easifemBase
USE easifemClasses
IMPLICIT NONE
TYPE(DomainConnectivity_) :: obj
TYPE( Domain_ ) :: pressureDomain
TYPE( Domain_ ) :: velocityDomain
TYPE( HDF5File_ ) :: pressureMeshFile
TYPE( HDF5File_ ) :: velocityMeshFile
INTEGER( I4B ), POINTER :: nodeToNode( : )
REAL( DFP ), POINTER :: pressureNode( :, : )
REAL( DFP ), POINTER :: velocityNode( :, : )
INTEGER( I4B ) :: ii
CALL velocityMeshFile%Initiate( FileName="./mesh_tri6.h5", MODE="READ" )
CALL velocityMeshFile%Open()
CALL pressureMeshFile%Initiate( FileName="./mesh_tri3.h5", MODE="READ" )
CALL pressureMeshFile%Open()
CALL velocityDomain%Initiate( velocityMeshFile, "")
CALL velocityMeshFile%Deallocate()
CALL pressureDomain%Initiate( pressureMeshFile, "")
CALL pressureMeshFile%Deallocate()
CALL obj%InitiateNodeToNodeData( domain1=velocityDomain, &
& domain2=pressureDomain )
nodeToNode => obj%getNodeToNodePointer()
pressureNode => pressureDomain%getNodeCoordPointer()
velocityNode => velocityDomain%getNodeCoordPointer()
Simple testing
DO ii = velocityDomain%minNptrs, velocityDomain%maxNptrs
IF( .NOT. velocityDomain%isNodePresent( globalNode=ii ) ) CYCLE
IF( nodeToNode( ii ) .EQ. 0 ) CYCLE
IF( ALL( velocityNode(:,velocityDomain%getLocalNodeNumber(ii)) &
& .APPROXEQ. pressureNode(:, &
& pressureDomain%getLocalNodeNumber(nodeToNode(ii)))) ) THEN
CALL Display( "velocity Node = " // TOSTRING(ii) &
& // " matches with pressure Node = " // TOSTRING( nodeToNode(ii)))
ELSE
CALL Display( "ERROR: velocity Node = " // TOSTRING(ii) &
& // " not matches with pressure Node = " &
& // TOSTRING( nodeToNode(ii)))
STOP
END IF
END DO
cleanup
CALL pressureDomain%Deallocate()
CALL velocityDomain%Deallocate()
CALL obj%Deallocate()
END PROGRAM main
In this example we will generate node to node connectivity information between velocity-domain and pressure-domain.
Pressure domain consists Triangle3 elements as shown below.
Velocity domain consists Triangle6 elements as shown below.
PROGRAM main
USE easifemBase
USE easifemClasses
IMPLICIT NONE
TYPE(DomainConnectivity_) :: obj
TYPE( Domain_ ) :: pressureDomain
TYPE( Domain_ ) :: velocityDomain
TYPE( HDF5File_ ) :: pressureMeshFile
TYPE( HDF5File_ ) :: velocityMeshFile
INTEGER( I4B ), POINTER :: nodeToNode( : )
REAL( DFP ), POINTER :: pressureNode( :, : )
REAL( DFP ), POINTER :: velocityNode( :, : )
INTEGER( I4B ) :: ii
CALL velocityMeshFile%Initiate( FileName="./mesh_tri6.h5", MODE="READ" )
CALL velocityMeshFile%Open()
CALL pressureMeshFile%Initiate( FileName="./mesh_tri3.h5", MODE="READ" )
CALL pressureMeshFile%Open()
CALL velocityDomain%Initiate( velocityMeshFile, "")
CALL velocityMeshFile%Deallocate()
CALL pressureDomain%Initiate( pressureMeshFile, "")
CALL pressureMeshFile%Deallocate()
CALL obj%InitiateNodeToNodeData( domain2=velocityDomain, &
& domain1=pressureDomain )
nodeToNode => obj%getNodeToNodePointer()
pressureNode => pressureDomain%getNodeCoordPointer()
velocityNode => velocityDomain%getNodeCoordPointer()
Simple testing
DO ii = pressureDomain%minNptrs, pressureDomain%maxNptrs
IF( .NOT. pressureDomain%isNodePresent( globalNode=ii ) ) CYCLE
IF( nodeToNode( ii ) .EQ. 0 ) CYCLE
IF( ALL( pressureNode(:,pressureDomain%getLocalNodeNumber(ii)) &
& .APPROXEQ. velocityNode(:, &
& velocityDomain%getLocalNodeNumber(nodeToNode(ii)))) ) THEN
!CALL Display( "pressure Node = " // TOSTRING(ii) &
! & // " matches with velocity Node = " // TOSTRING( nodeToNode(ii)))
ELSE
CALL Display( "ERROR: pressure Node = " // TOSTRING(ii) &
& // " not matches with velocity Node = " &
& // TOSTRING( nodeToNode(ii)))
STOP
END IF
END DO
CALL OK(.TRUE.)
cleanup
CALL pressureDomain%Deallocate()
CALL velocityDomain%Deallocate()
CALL obj%Deallocate()
END PROGRAM main
This is a powerful 🔥 and useful method. You can learn about this routine at following links.