Skip to content

Commit

Permalink
FEDomain examples
Browse files Browse the repository at this point in the history
  • Loading branch information
vickysharma0812 committed Apr 15, 2024
1 parent 40a618b commit e7d57f6
Show file tree
Hide file tree
Showing 22 changed files with 350 additions and 158 deletions.
10 changes: 1 addition & 9 deletions docs/docs-api/FEDomain/examples/_GetNodeCoord_test_1.F90
Original file line number Diff line number Diff line change
@@ -1,45 +1,37 @@

PROGRAM main
USE easifemBase
USE easifemClasses
USE FEDomain_Class

IMPLICIT NONE

TYPE(FEDomain_) :: obj
TYPE(HDF5File_) :: meshfile
CHARACTER(*), PARAMETER :: filename="../../Mesh/examples/meshdata/small_tri3_mesh_two_region.h5"
REAL(DFP) :: ans(3, 4)

ans(:, 1) = [0, 0, 0]
ans(:, 2) = [1, 0, 0]
ans(:, 3) = [2, 0, 0]
ans(:, 4) = [0, 1, 0]

CALL meshfile%Initiate(filename, "READ")
CALL meshfile%OPEN()
CALL obj%Initiate(meshfile, '')

BLOCK
REAL(DFP), ALLOCATABLE :: xij(:, :)
CALL Reallocate(xij, 3, obj%GetTotalNodes())
CALL obj%GetNodeCoord(xij)
CALL OK(ALL(xij(1:3, 1:4) .approxeq.ans(1:3, 1:4)), "GetNodeCoord: ")
END BLOCK

BLOCK
REAL(DFP), ALLOCATABLE :: xij(:, :)
CALL Reallocate(xij, 2, obj%GetTotalNodes())
CALL obj%GetNodeCoord(xij)
CALL OK(ALL(xij(1:2, 1:4) .approxeq.ans(1:2, 1:4)), "GetNodeCoord: ")
END BLOCK

BLOCK
REAL(DFP) :: xij(2, 4)

CALL obj%GetNodeCoord(xij, [1, 2, 3, 4])
CALL OK(ALL(xij(1:2, 1:4) .approxeq.ans(1:2, 1:4)), "GetNodeCoord: ")
END BLOCK

CALL meshfile%DEALLOCATE()
CALL obj%DEALLOCATE()
END PROGRAM main
10 changes: 8 additions & 2 deletions docs/docs-api/FEDomain/examples/_GetNodeToElements_test_2.F90
Original file line number Diff line number Diff line change
Expand Up @@ -13,11 +13,17 @@ PROGRAM main
! Initiates an instance of [[Domain_]].
CALL obj%Initiate(meshfile, '')
BLOCK
INTEGER(I4B), PARAMETER :: globalnode(2) = [3,38]
INTEGER(I4B), PARAMETER :: globalnode(2) = [3,28]
INTEGER(I4B), ALLOCATABLE :: exact(:), val(:)
LOGICAL( LGT ) :: isok
val = SORT(obj%GetNodeToElements(globalnode))
exact = [36, 37, 38, 43, 44, 45, 91, 92]
CALL OK(ALL(val .EQ. exact), "GetNodeToElements: ")
isok = ALL(val .EQ. exact)
CALL OK(isok, "GetNodeToElements: ")
if(.not. isok) then
CALL Display(val, "got: ")
CALL Display(exact, "want: ")
end if
END BLOCK
CALL meshfile%DEALLOCATE()
CALL obj%DEALLOCATE()
Expand Down
12 changes: 10 additions & 2 deletions docs/docs-api/FEDomain/examples/_GetNodeToElements_test_2.md
Original file line number Diff line number Diff line change
@@ -1,3 +1,5 @@
<!-- markdownlint-disable MD041 MD013 MD033 -->

```fortran
PROGRAM main
USE easifemBase
Expand All @@ -17,12 +19,18 @@ CALL meshfile%OPEN()
CALL obj%Initiate(meshfile, '')
BLOCK
INTEGER(I4B), PARAMETER :: globalnode(2) = [3,38]
INTEGER(I4B), PARAMETER :: globalnode(2) = [3,28]
INTEGER(I4B), ALLOCATABLE :: exact(:), val(:)
LOGICAL( LGT ) :: isok
val = SORT(obj%GetNodeToElements(globalnode))
exact = [36, 37, 38, 43, 44, 45, 91, 92]
CALL OK(ALL(val .EQ. exact), "GetNodeToElements: ")
isok = ALL(val .EQ. exact)
CALL OK(isok, "GetNodeToElements: ")
if(.not. isok) then
CALL Display(val, "got: ")
CALL Display(exact, "want: ")
end if
END BLOCK
CALL meshfile%DEALLOCATE()
Expand Down
9 changes: 1 addition & 8 deletions docs/docs-api/FEDomain/examples/_GetNptrs_test_1.F90
Original file line number Diff line number Diff line change
@@ -1,40 +1,33 @@

PROGRAM main
USE easifemBase
USE easifemClasses
USE FEDomain_Class

IMPLICIT NONE

TYPE(FEDomain_) :: obj
TYPE(HDF5File_) :: meshfile
CHARACTER(*), PARAMETER :: filename="../../Mesh/examples/meshdata/small_tri3_mesh_two_region.h5"

CALL meshfile%Initiate(filename, "READ")
CALL meshfile%OPEN()
CALL obj%Initiate(meshfile, '')

BLOCK
INTEGER(I4B), ALLOCATABLE :: nptrs(:)
nptrs = obj%GetNptrs(2)
CALL HeapSort(nptrs)
CALL OK(ALL(nptrs .EQ. arange(1, obj%GetTotalNodes())), "GetNptrs: ")
END BLOCK

BLOCK
INTEGER(I4B), ALLOCATABLE :: nptrs(:)
nptrs = obj%GetNptrs(1)
CALL HeapSort(nptrs)
CALL OK(ALL(nptrs .EQ. arange(1, obj%GetTotalNodes(1))), "GetNptrs: ")
END BLOCK

BLOCK
INTEGER(I4B), ALLOCATABLE :: nptrs(:)
nptrs = obj%GetNptrs(0)
CALL HeapSort(nptrs)
CALL OK(ALL(nptrs .EQ. arange(1, obj%GetTotalNodes(0))), "GetNptrs: ")
END BLOCK

CALL meshfile%DEALLOCATE()
CALL obj%DEALLOCATE()

END PROGRAM main
2 changes: 2 additions & 0 deletions docs/docs-api/FEDomain/examples/_GetNptrs_test_1.md
Original file line number Diff line number Diff line change
@@ -1,3 +1,5 @@
<!-- markdownlint-disable MD041 MD013 MD033 -->

```fortran
PROGRAM main
USE easifemBase
Expand Down
8 changes: 1 addition & 7 deletions docs/docs-api/FEDomain/examples/_GetNptrs_test_2.F90
Original file line number Diff line number Diff line change
@@ -1,35 +1,29 @@

PROGRAM main
USE easifemBase
USE easifemClasses
USE FEDomain_Class

IMPLICIT NONE

TYPE(FEDomain_) :: obj
TYPE(HDF5File_) :: meshfile
CHARACTER(*), PARAMETER :: filename="../../Mesh/examples/meshdata/small_tri3_mesh_two_region.h5"

CALL meshfile%Initiate(filename, "READ")
CALL meshfile%OPEN()
CALL obj%Initiate(meshfile, '')

BLOCK
INTEGER(I4B), ALLOCATABLE :: nptrs(:)
CALL Reallocate(nptrs, obj%GetTotalNodes())
CALL obj%GetNptrs_(nptrs=nptrs, dim=2)
CALL HeapSort(nptrs)
CALL OK(ALL(nptrs .EQ. arange(1, obj%GetTotalNodes())), "GetNptrs: ")
END BLOCK

BLOCK
INTEGER(I4B), ALLOCATABLE :: nptrs(:)
CALL Reallocate(nptrs, obj%GetTotalNodes(1))
CALL obj%GetNptrs_(nptrs=nptrs, dim=1)
CALL HeapSort(nptrs)
CALL OK(ALL(nptrs .EQ. arange(1, obj%GetTotalNodes(1))), "GetNptrs: ")
END BLOCK

CALL meshfile%DEALLOCATE()
CALL obj%DEALLOCATE()

END PROGRAM main
10 changes: 1 addition & 9 deletions docs/docs-api/FEDomain/examples/_GetTotalNodes_test_1.F90
Original file line number Diff line number Diff line change
@@ -1,43 +1,35 @@

PROGRAM main
USE easifemBase
USE easifemClasses
USE FEDomain_Class

IMPLICIT NONE

TYPE(FEDomain_) :: obj
TYPE(HDF5File_) :: meshfile
CHARACTER(*), PARAMETER :: filename="../../Mesh/examples/meshdata/small_tri3_mesh_two_region.h5"
INTEGER(I4B), PARAMETER :: domain_tNodes = 45, dim1_tNodes = 27

! initiates the [[HDF5File_]] and OPEN it
CALL meshfile%Initiate(filename, "READ")
CALL meshfile%OPEN()

! Initiates an instance of [[Domain_]]
CALL obj%Initiate(meshfile, '')

! Let us now demonstrate the usage of `GetTotalNodes` which
! returns the total number of nodes in the [[Domain_]],
! or part of domain (i.e. [[Mesh_]])
! Let us Get total number of nodes in the domain.
CALL OK(obj%GetTotalNodes() .EQ. domain_tNodes, "GetTotalNodes: ")

! Let us not Get total number of nodes in the left mesh [[Mesh_]]
CALL OK(obj%GetTotalNodes(dim=2) .EQ. domain_tNodes, &
& "obj%GetTotalNodes(dim=2): ")

! It is an error to get nodes like given below.
! CALL OK( domain_tNodes .eq. obj%GetTotalNodes(dim=2), &
! & "obj%GetTotalNodes(dim=2): " )
! We can also Get total number of nodes using the operator called `.tNodes.`.
! To Get total number of nodes in the domain use the following.

CALL OK(domain_tNodes .EQ. (.tNodes.obj), "(.tNodes. obj): ")
! To Get total number of nodes in given dimension `dim` and entity Number,
! pack them in a vector of length two, that is `[dim, entityNum]`,
! and pass it to `.tNodes.` as shown below.

CALL OK(domain_tNodes .EQ. (obj.tNodes.2), "obj .tNodes. 2: ")
CALL meshfile%DEALLOCATE()
CALL obj%DEALLOCATE()
Expand Down
4 changes: 3 additions & 1 deletion docs/docs-api/FEDomain/examples/_GetTotalNodes_test_1.md
Original file line number Diff line number Diff line change
@@ -1,4 +1,6 @@
``` fortran
<!-- markdownlint-disable MD041 MD013 MD033 -->

```fortran
PROGRAM main
USE easifemBase
USE easifemClasses
Expand Down
2 changes: 1 addition & 1 deletion docs/docs-api/FEDomain/examples/_Initiate_test_1.md
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
Testing initiate method for 2D mesh.
<!-- markdownlint-disable MD041 MD013 MD033 -->

```fortran
PROGRAM main
Expand Down
46 changes: 23 additions & 23 deletions docs/docs-api/FEDomain/examples/_IsElementPresent_test_1.F90
Original file line number Diff line number Diff line change
@@ -1,27 +1,27 @@

PROGRAM main
USE easifemBase
USE easifemClasses
USE FEDomain_Class
IMPLICIT NONE
TYPE(FEDomain_) :: obj
TYPE(HDF5File_) :: meshfile
USE easifemBase
USE easifemClasses
USE FEDomain_Class
IMPLICIT NONE
TYPE(FEDomain_) :: obj
TYPE(HDF5File_) :: meshfile
CHARACTER(*), PARAMETER :: filename="../../Mesh/examples/meshdata/small_tri3_mesh_two_region.h5"
CALL meshfile%Initiate(filename, "READ")
CALL meshfile%Open()
CALL obj%Initiate(meshfile, '')
! Let us now test `isElementPresent` method,
! which returns true IF a given global node is present in the domain.
CALL OK( obj%isElementPresent( 35 ), "isElementPresent : " )
CALL OK( (obj%isElementPresent( 84 )), "isElementPresent : " )
CALL OK( .NOT. (obj%isElementPresent( 7 )), "isElementPresent : " )
CALL OK( .NOT. (obj%isElementPresent( 21 )), "isElementPresent : " )
CALL OK( obj%isElementPresent( 35, 2 ), "isElementPresent : " )
CALL OK( (obj%isElementPresent( 84, 2 )), "isElementPresent : " )
CALL OK( .NOT. (obj%isElementPresent( 35, 1 )), "isElementPresent : " )
CALL OK( .NOT. (obj%isElementPresent( 84, 1 )), "isElementPresent : " )
CALL OK( .NOT. (obj%isElementPresent( 7, 2 )), "isElementPresent : " )
CALL OK( .NOT. (obj%isElementPresent( 21, 2 )), "isElementPresent : " )
CALL meshfile%Deallocate()
CALL obj%Deallocate()
CALL meshfile%Initiate(filename, "READ")
CALL meshfile%OPEN()
CALL obj%Initiate(meshfile, '')
! Let us now test `isElementPresent` method,
! which returns true IF a given global node is present in the domain.
CALL OK(obj%isElementPresent(35), "isElementPresent : ")
CALL OK((obj%isElementPresent(84)), "isElementPresent : ")
CALL OK(.NOT. (obj%isElementPresent(7)), "isElementPresent : ")
CALL OK(.NOT. (obj%isElementPresent(21)), "isElementPresent : ")
CALL OK(obj%isElementPresent(35, 2), "isElementPresent : ")
CALL OK((obj%isElementPresent(84, 2)), "isElementPresent : ")
CALL OK(.NOT. (obj%isElementPresent(35, 1)), "isElementPresent : ")
CALL OK(.NOT. (obj%isElementPresent(84, 1)), "isElementPresent : ")
CALL OK(.NOT. (obj%isElementPresent(7, 2)), "isElementPresent : ")
CALL OK(.NOT. (obj%isElementPresent(21, 2)), "isElementPresent : ")
CALL meshfile%DEALLOCATE()
CALL obj%DEALLOCATE()
END PROGRAM main
2 changes: 1 addition & 1 deletion docs/docs-api/FEDomain/examples/_IsNodePresent_test_1.md
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
``` fortran
```fortran
PROGRAM main
USE easifemBase
USE easifemClasses
Expand Down
24 changes: 24 additions & 0 deletions docs/docs-api/FEMesh/examples/_DisplayFaceData_test_1.F90
Original file line number Diff line number Diff line change
@@ -0,0 +1,24 @@
PROGRAM main
USE easifemBase
USE easifemClasses

IMPLICIT NONE

TYPE(FEMesh_) :: obj
TYPE(HDF5File_) :: meshfile
CHARACTER(LEN=*), PARAMETER :: filename = &
& "../../Mesh/examples/meshdata/small_mesh.h5"

CALL meshfile%Initiate(FileName=filename, MODE="READ")

CALL meshfile%OPEN()

CALL obj%Initiate(hdf5=meshfile, dim=2)

CALL obj%InitiateFacetElements()

CALL obj%DisplayFacetData(msg="facet data of "//filename)

CALL obj%DEALLOCATE()
CALL meshfile%DEALLOCATE()
END PROGRAM main
22 changes: 22 additions & 0 deletions docs/docs-api/FEMesh/examples/_DisplayFaceData_test_1.md
Original file line number Diff line number Diff line change
@@ -0,0 +1,22 @@
PROGRAM main
USE easifemBase
USE easifemClasses

IMPLICIT NONE

TYPE(FEMesh_) :: obj
TYPE(HDF5File_) :: meshfile
CHARACTER(LEN=*), PARAMETER :: filename = &
& "../../Mesh/examples/meshdata/small_mesh.h5"

CALL meshfile%Initiate(FileName=filename, MODE="READ")

CALL meshfile%OPEN()

CALL obj%Initiate(hdf5=meshfile, dim=2)

CALL obj%InitiateFacetElements()

CALL obj%DEALLOCATE()
CALL meshfile%DEALLOCATE()
END PROGRAM main
17 changes: 17 additions & 0 deletions docs/docs-api/FEMesh/examples/_DisplayInternalFacetData_test_1.F90
Original file line number Diff line number Diff line change
@@ -0,0 +1,17 @@

PROGRAM main
USE easifemBase
USE easifemClasses
IMPLICIT NONE
TYPE(FEMesh_) :: obj
TYPE(HDF5File_) :: meshfile
CHARACTER(LEN=*), PARAMETER :: filename = &
& "../../Mesh/examples/meshdata/small_mesh.h5"
CALL meshfile%Initiate(FileName=filename, MODE="READ")
CALL meshfile%OPEN()
CALL obj%Initiate(hdf5=meshfile, dim=2)
CALL obj%InitiateFacetElements()
CALL obj%DisplayInternalFacetData(msg="internal facet data of "//filename)
CALL obj%DEALLOCATE()
CALL meshfile%DEALLOCATE()
END PROGRAM main
Loading

0 comments on commit e7d57f6

Please sign in to comment.