Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
7 changes: 4 additions & 3 deletions src/modules/AbstractMesh/CMakeLists.txt
Original file line number Diff line number Diff line change
Expand Up @@ -26,11 +26,12 @@ target_sources(
${src_path}/EdgeDataList_Class.F90
${src_path}/EdgeDataBinaryTree_Class.F90
${src_path}/EdgeDataBinaryTreeUtility.F90
${src_path}/FaceData_Class.F90
${src_path}/FaceDataList_Class.F90
${src_path}/FaceDataBinaryTree_Class.F90
${src_path}/FaceDataBinaryTreeUtility.F90
${src_path}/ElemData_Class.F90
${src_path}/ElemDataList_Class.F90
${src_path}/ElemDataBinaryTree_Class.F90
${src_path}/FacetData_Class.F90
# ${src_path}/EdgeTreeData_Class.F90
# ${src_path}/EdgeBinaryTree_Class.F90
# ${src_path}/EdgeBinaryTreeUtility.F90
${src_path}/ElementShapeFunctionData_Class.F90)
75 changes: 75 additions & 0 deletions src/modules/AbstractMesh/src/FaceDataBinaryTreeUtility.F90
Original file line number Diff line number Diff line change
@@ -0,0 +1,75 @@
! This program is a part of EASIFEM library
! Copyright (C) 2020-2021 Vikas Sharma, Ph.D
!
! This program is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! This program is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with this program. If not, see <https: //www.gnu.org/licenses/>

MODULE FaceDataBinaryTreeUtility
USE GlobalData, ONLY: I4B
USE FaceDataBinaryTree_Class
USE FaceData_Class
IMPLICIT NONE
PRIVATE

PUBLIC :: FaceDataBinaryTree_GetArray

CONTAINS

!----------------------------------------------------------------------------
! FaceDataBinaryTree_GetArray
!----------------------------------------------------------------------------

RECURSIVE SUBROUTINE FaceDataBinaryTree_GetArray(obj, VALUE)
TYPE(FaceDataBinaryTree_), INTENT(INOUT) :: obj
!! Binary tree of edge data
INTEGER(I4B), INTENT(INOUT) :: VALUE(:, :)
!! The number of rows in value should be 2
!! The number of columns in value should be total number of edges

TYPE(FaceDataBinaryTree_) :: anode
TYPE(FaceData_), POINTER :: value_ptr
INTEGER(I4B) :: ii

IF (.NOT. obj%ASSOCIATED()) RETURN

! Get left
anode = obj%GetNode(opt=-1)
IF (anode%ASSOCIATED()) THEN
CALL FaceDataBinaryTree_GetArray(anode, VALUE)
END IF

! Get node value

value_ptr => obj%GetValuePointer()
IF (ASSOCIATED(value_ptr)) THEN
DO ii = 1, SIZE(value_ptr%VALUE)
VALUE(ii, value_ptr%id) = value_ptr%VALUE(ii)
END DO
END IF

! Get right
anode = obj%GetNode(opt=1)
IF (anode%ASSOCIATED()) THEN
CALL FaceDataBinaryTree_GetArray(anode, VALUE)
END IF

NULLIFY (value_ptr)
CALL anode%Unlink()

END SUBROUTINE FaceDataBinaryTree_GetArray

!----------------------------------------------------------------------------
!
!----------------------------------------------------------------------------

END MODULE FaceDataBinaryTreeUtility
32 changes: 32 additions & 0 deletions src/modules/AbstractMesh/src/FaceDataBinaryTree_Class.F90
Original file line number Diff line number Diff line change
@@ -0,0 +1,32 @@
! This program is a part of EASIFEM library
! Copyright (C) Vikas Sharma, Ph.D
!
! This program is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! This program is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with this program. If not, see <https: //www.gnu.org/licenses/>

#define Binary_Tree_Type_Name FaceDataBinaryTree_
#define Binary_Tree_Activate_SetID_Method
MODULE FaceDataBinaryTree_Class
USE FaceData_Class, ONLY: TreeData_ => FaceData_, &
& TreeData_Deallocate => FaceData_Deallocate, &
& TreeData_Display => FaceData_Display, &
& TreeData_lt => FaceData_lt, &
& TreeData_eq => FaceData_eq, &
& TreeData_SetID => FaceData_SetID

#include "../../BinaryTree/src/BinaryTree.inc"

END MODULE FaceDataBinaryTree_Class

#undef Binary_Tree_Type_Name
#undef Binary_Tree_Activate_SetID_Method
29 changes: 29 additions & 0 deletions src/modules/AbstractMesh/src/FaceDataList_Class.F90
Original file line number Diff line number Diff line change
@@ -0,0 +1,29 @@
! This program is a part of EASIFEM library
! Copyright (C) 2020-2021 Vikas Sharma, Ph.D
!
! This program is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! This program is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with this program. If not, see <https: //www.gnu.org/licenses/>
!

#define FTL_TEMPLATE_TYPE FaceData_
#define FTL_TEMPLATE_TYPE_IS_DERIVED
#define FTL_TEMPLATE_TYPE_IS_CLASS
#define FTL_TEMPLATE_TYPE_NAME FaceData
#define FTL_INSTANTIATE_TEMPLATE

MODULE FaceDataList_Class
USE GlobalData, ONLY: DFP, I4B, LGT
USE Display_Method
USE FaceData_Class
#include "../../ftlMacros/ftlList.inc"
END MODULE FaceDataList_Class
187 changes: 187 additions & 0 deletions src/modules/AbstractMesh/src/FaceData_Class.F90
Original file line number Diff line number Diff line change
@@ -0,0 +1,187 @@
! This program is a part of EASIFEM library
! Copyright (C) (Since 2020) Vikas Sharma, Ph.D
!
! This program is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! This program is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with this program. If not, see <https: //www.gnu.org/licenses/>
!

MODULE FaceData_Class
USE GlobalData, ONLY: DFP, I4B, LGT
USE Display_Method
IMPLICIT NONE
PRIVATE
PUBLIC :: FaceData_
PUBLIC :: FaceData_Pointer
PUBLIC :: FaceData_Deallocate
PUBLIC :: FaceData_Display
PUBLIC :: FaceData_lt
PUBLIC :: FaceData_eq
PUBLIC :: FaceData_SetID
PUBLIC :: FaceData_Copy
PUBLIC :: Initiate
PUBLIC :: ASSIGNMENT(=)
PUBLIC :: Display

INTERFACE Initiate
MODULE PROCEDURE FaceData_Initiate
END INTERFACE Initiate

INTERFACE ASSIGNMENT(=)
MODULE PROCEDURE FaceData_Initiate
END INTERFACE

INTEGER(I4B), PARAMETER :: INT_SIZE_IN_TREE_DATA = 4_I4B

INTERFACE Display
MODULE PROCEDURE FaceData_Display
END INTERFACE Display

!----------------------------------------------------------------------------
! FaceData_
!----------------------------------------------------------------------------

!> author: Vikas Sharma, Ph. D.
! date: 2024-01-23
! summary: TreeData stored at each node level

TYPE FaceData_
INTEGER(I4B) :: VALUE(INT_SIZE_IN_TREE_DATA) = 0_I4B
INTEGER(I4B) :: id = 0
END TYPE FaceData_

CONTAINS

!----------------------------------------------------------------------------
! Copy
!----------------------------------------------------------------------------

!> author: Vikas Sharma, Ph. D.
! date: 2024-03-07
! summary: Copy

SUBROUTINE FaceData_Copy(obj1, obj2)
TYPE(FaceData_), INTENT(INOUT) :: obj1
TYPE(FaceData_), INTENT(IN) :: obj2

obj1%VALUE = obj2%VALUE
obj1%id = obj2%id
END SUBROUTINE FaceData_Copy

!----------------------------------------------------------------------------
! Deallocate
!----------------------------------------------------------------------------

!> author: Vikas Sharma, Ph. D.
! date: 2024-01-23
! summary: Deallocate tree data

SUBROUTINE FaceData_Deallocate(obj)
TYPE(FaceData_), INTENT(INOUT) :: obj
obj%VALUE = 0
obj%id = 0
END SUBROUTINE FaceData_Deallocate

!----------------------------------------------------------------------------
! Display
!----------------------------------------------------------------------------

!> author: Vikas Sharma, Ph. D.
! date: 2024-01-23
! summary: Display data

SUBROUTINE FaceData_Display(obj, msg, unitno)
TYPE(FaceData_), INTENT(IN) :: obj
CHARACTER(*), INTENT(IN) :: msg
INTEGER(I4B), OPTIONAL, INTENT(IN) :: unitno
CALL Display(obj%VALUE, msg//"("//tostring(obj%id)//"):", unitno=unitno)
END SUBROUTINE FaceData_Display

!----------------------------------------------------------------------------
! lt
!----------------------------------------------------------------------------

!> author: Vikas Sharma, Ph. D.
! date: 2024-01-23
! summary: Lesser than

FUNCTION FaceData_lt(obj, obj2) RESULT(ans)
TYPE(FaceData_), INTENT(IN) :: obj
TYPE(FaceData_), INTENT(IN) :: obj2
LOGICAL(LGT) :: ans
ans = obj%VALUE(1) .LT. obj2%VALUE(1)
END FUNCTION FaceData_lt

!----------------------------------------------------------------------------
! eq
!----------------------------------------------------------------------------

!> author: Vikas Sharma, Ph. D.
! date: 2024-01-23
! summary: equality

FUNCTION FaceData_eq(obj, obj2) RESULT(ans)
TYPE(FaceData_), INTENT(IN) :: obj
TYPE(FaceData_), INTENT(IN) :: obj2
LOGICAL(LGT) :: ans
ans = ALL(obj%VALUE .EQ. obj2%VALUE)
END FUNCTION FaceData_eq

!----------------------------------------------------------------------------
! Initiate
!----------------------------------------------------------------------------

!> author: Vikas Sharma, Ph. D.
! date: 2024-01-23
! summary: Initiate the data

SUBROUTINE FaceData_Initiate(obj, VALUE)
TYPE(FaceData_), INTENT(INOUT) :: obj
INTEGER(I4B), INTENT(IN) :: VALUE(:)

! internal variables
INTEGER(I4B) :: ii
DO ii = 1, SIZE(VALUE)
obj%VALUE(ii) = VALUE(ii)
END DO
END SUBROUTINE FaceData_Initiate

!----------------------------------------------------------------------------
! FaceData_Pointer
!----------------------------------------------------------------------------

!> author: Vikas Sharma, Ph. D.
! date: 2024-01-23
! summary: FaceData_Pointer

FUNCTION FaceData_Pointer(VALUE) RESULT(ans)
INTEGER(I4B), INTENT(IN) :: VALUE(:)
TYPE(FaceData_), POINTER :: ans
ALLOCATE (ans)
CALL FaceData_Initiate(ans, VALUE)
END FUNCTION FaceData_Pointer

!----------------------------------------------------------------------------
! SetID
!----------------------------------------------------------------------------

!> author: Vikas Sharma, Ph. D.
! date: 2024-01-23
! summary: Initiate the data

SUBROUTINE FaceData_SetID(obj, id)
TYPE(FaceData_), INTENT(INOUT) :: obj
INTEGER(I4B), INTENT(IN) :: id
obj%id = id
END SUBROUTINE FaceData_SetID

END MODULE FaceData_Class
20 changes: 20 additions & 0 deletions src/modules/easifemClasses/src/easifemClasses.F90
Original file line number Diff line number Diff line change
Expand Up @@ -31,9 +31,29 @@ MODULE easifemClasses
USE StringList_Class
USE ElementList_Class
USE ElementPointerVector_Class

USE ElemData_Class
USE ElemDataBinaryTree_Class
USE ElemDataList_Class

USE NodeData_Class
USE NodeDataList_Class
USE NodeDataBinaryTree_Class

USE EdgeData_Class
USE EdgeDataList_Class
USE EdgeDataBinaryTree_Class

USE FaceData_Class
USE FaceDataList_Class
USE FaceDataBinaryTree_Class

USE FacetData_Class

USE AbstractMesh_Class
USE Mesh_Class
USE MeshPointerVector_Class

USE Domain_Class
USE DomainUtility
USE DomainConnectivity_Class
Expand Down