Skip to content

Commit

Permalink
Merge pull request #494 from easifem/fedomain-dev
Browse files Browse the repository at this point in the history
Fedomain dev
  • Loading branch information
vickysharma0812 authored Jun 4, 2024
2 parents a986088 + 821102e commit c94ddb7
Show file tree
Hide file tree
Showing 11 changed files with 35 additions and 20 deletions.
2 changes: 2 additions & 0 deletions src/modules/AbstractKernel/src/AbstractKernel_Class.F90
Original file line number Diff line number Diff line change
Expand Up @@ -151,6 +151,8 @@ MODULE AbstractKernel_Class
!! algorithm
INTEGER(I4B) :: vtkOutputFreq = 0
!! frequency of output with WriteData_vtk
INTEGER(I4B) :: hdfOutputFreq = 0
!! frequency of output with WriteData_vtk
TYPE(String) :: name
!! This is the name of the kernel. It can be anything you want.
TYPE(String) :: engine
Expand Down
8 changes: 4 additions & 4 deletions src/modules/AbstractMesh/src/ElemData_Class.F90
Original file line number Diff line number Diff line change
Expand Up @@ -18,8 +18,8 @@
MODULE ElemData_Class
USE GlobalData, ONLY: I4B, DFP, LGT, INT8
USE Display_Method, ONLY: Display
USE ReferenceElement_Method, ONLY: REFELEM_MAX_FACES, &
& REFELEM_MAX_POINTS, RefElemGetGeoParam, ElementName
USE ReferenceElement_Method, ONLY: PARAM_REFELEM_MAX_FACES, &
& PARAM_REFELEM_MAX_POINTS, RefElemGetGeoParam, ElementName
USE ReferenceQuadrangle_Method, ONLY: HelpFaceData_Quadrangle, &
& FaceShapeMetaData_Quadrangle
USE SortUtility
Expand Down Expand Up @@ -439,8 +439,8 @@ SUBROUTINE ElemData_GetGlobalFaceCon(obj, globalFaceCon, localFaceCon)
INTEGER(I4B), INTENT(INOUT) :: globalFaceCon(:, :)
INTEGER(I4B), OPTIONAL, INTENT(INOUT) :: localFaceCon(:, :)

INTEGER(I4B) :: tFaces, tNodes, localFaces0(4_I4B, REFELEM_MAX_FACES), &
& faceElemType(REFELEM_MAX_FACES), tFaceNodes(REFELEM_MAX_FACES), &
INTEGER(I4B) :: tFaces, tNodes, localFaces0(4_I4B, PARAM_REFELEM_MAX_FACES), &
& faceElemType(PARAM_REFELEM_MAX_FACES), tFaceNodes(PARAM_REFELEM_MAX_FACES), &
& iface, face_temp(4), aint

CALL RefElemGetGeoParam(elemType=obj%name, &
Expand Down
2 changes: 1 addition & 1 deletion src/modules/FPL/src/FPL_Method.F90
Original file line number Diff line number Diff line change
Expand Up @@ -630,7 +630,7 @@ SUBROUTINE fpl_Get_Bool(obj, prefix, key, VALUE)
TYPE(ParameterList_), INTENT(IN) :: obj
CHARACTER(*), INTENT(IN) :: prefix
CHARACTER(*), INTENT(IN) :: key
LOGICAL(LGT), INTENT(OUT) :: VALUE
LOGICAL(LGT), INTENT(INOUT) :: VALUE
! Internal variable
INTEGER(I4B) :: ierr
TYPE(String) :: varname
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -777,6 +777,7 @@
CALL AbstractMeshFieldDeallocate(obj%Cijkl)
CALL AbstractMeshFieldDeallocate(obj%stress)
CALL AbstractMeshFieldDeallocate(obj%strain)
CALL AbstractMeshFieldDeallocate(obj%scalarCoefficient)

NULLIFY (obj%bodySourceFunc)

Expand Down
2 changes: 1 addition & 1 deletion src/submodules/AbstractMesh/src/AbstractMeshUtility.F90
Original file line number Diff line number Diff line change
Expand Up @@ -58,7 +58,7 @@ SUBROUTINE InitiateElementToElements3D(elementData, tFaceInMesh, showTime)
CHARACTER(*), PARAMETER :: myName = "obj_InitiateElementToElements3D()"
LOGICAL(LGT) :: problem, isok1, isok2, isbndy
INTEGER(I4B) :: telems, iel, aint, bint, tfaces, ii, jj, &
& temp1(3 * REFELEM_MAX_FACES), cint, bndyflag(REFELEM_MAX_FACES)
& temp1(3 * PARAM_REFELEM_MAX_FACES), cint, bndyflag(PARAM_REFELEM_MAX_FACES)
INTEGER(I4B), ALLOCATABLE :: face2elem(:, :)
LOGICAL(LGT), ALLOCATABLE :: amask(:)
TYPE(CPUTime_) :: TypeCPUTime
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -16,8 +16,8 @@
!

SUBMODULE(AbstractMesh_Class) EdgeDataMethods
USE ReferenceElement_Method, ONLY: REFELEM_MAX_EDGES, &
& REFELEM_MAX_POINTS, RefElemGetGeoParam
USE ReferenceElement_Method, ONLY: PARAM_REFELEM_MAX_EDGES, &
& PARAM_REFELEM_MAX_POINTS, RefElemGetGeoParam
USE ReferenceLine_Method, ONLY: MaxOrder_Line
USE ReallocateUtility, ONLY: Reallocate
USE EdgeData_Class
Expand All @@ -34,7 +34,7 @@
MODULE PROCEDURE obj_InitiateEdgeConnectivity
CHARACTER(*), PARAMETER :: myName = "obj_InitiateEdgeConnectivity()"
INTEGER(I4B) :: tElements, iel, elemType, tEdges, &
& localEdges(MaxOrder_Line + 1, REFELEM_MAX_EDGES), &
& localEdges(MaxOrder_Line + 1, PARAM_REFELEM_MAX_EDGES), &
& edge(2), sorted_edge(2), &
& tNodes, tsize1, tsize2, iedge
LOGICAL(LGT) :: problem
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -18,7 +18,7 @@
SUBMODULE(AbstractMesh_Class) ElementDataMethods
USE ReallocateUtility
USE Display_Method
USE ReferenceElement_Method, ONLY: REFELEM_MAX_FACES
USE ReferenceElement_Method, ONLY: PARAM_REFELEM_MAX_FACES
USE AbstractMeshUtility, ONLY: InitiateElementToElements3D, &
& InitiateElementToElements2D, &
& InitiateElementToElements1D
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -16,8 +16,8 @@
!

SUBMODULE(AbstractMesh_Class) FaceDataMethods
USE ReferenceElement_Method, ONLY: REFELEM_MAX_FACES, &
& REFELEM_MAX_POINTS, &
USE ReferenceElement_Method, ONLY: PARAM_REFELEM_MAX_FACES, &
& PARAM_REFELEM_MAX_POINTS, &
& RefElemGetGeoParam, &
& IsQuadrangle

Expand All @@ -40,9 +40,9 @@
MODULE PROCEDURE obj_InitiateFaceConnectivity
CHARACTER(*), PARAMETER :: myName = "obj_InitiateFaceConnectivity()"
INTEGER(I4B) :: tElements, iel, elemType, tFaces, &
& localFaces(4_I4B, REFELEM_MAX_FACES), face(4), sorted_face(4), &
& localFaces(4_I4B, PARAM_REFELEM_MAX_FACES), face(4), sorted_face(4), &
& tNodes, tsize1, tsize2, iface, &
& faceElemType(REFELEM_MAX_FACES), tFaceNodes(REFELEM_MAX_FACES), &
& faceElemType(PARAM_REFELEM_MAX_FACES), tFaceNodes(PARAM_REFELEM_MAX_FACES), &
& aint, faceOrient(3_I4B)
LOGICAL(LGT) :: problem, abool
TYPE(FaceDataBinaryTree_) :: faceTree
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -21,7 +21,7 @@
USE BoundingBox_Method
USE InputUtility
USE Display_Method
USE ReferenceElement_Method, ONLY: REFELEM_MAX_FACES, &
USE ReferenceElement_Method, ONLY: PARAM_REFELEM_MAX_FACES, &
& GetEdgeConnectivity, &
& GetFaceConnectivity, &
& ElementOrder, &
Expand Down Expand Up @@ -1315,8 +1315,8 @@
#endif

INTEGER(I4B) :: iel, temp4(4), elemType, order, &
& con(MaxNodesInElement, REFELEM_MAX_FACES), &
& ii, tFaceNodes(REFELEM_MAX_FACES)
& con(MaxNodesInElement, PARAM_REFELEM_MAX_FACES), &
& ii, tFaceNodes(PARAM_REFELEM_MAX_FACES)

iel = obj%GetLocalElemNumber(globalElement, islocal=islocal)

Expand Down
8 changes: 8 additions & 0 deletions src/submodules/RefElement/src/Topology_Class@Methods.F90
Original file line number Diff line number Diff line change
Expand Up @@ -231,6 +231,14 @@
ans(4)%nptrs = nptrs([4, 1, 8])
ans(1:)%xidimension = 1
ans(1:)%name = line3
CASE (Quadrangle16)
! ALLOCATE (ans(4))
ans(1)%nptrs = nptrs([1, 2, 5, 6])
ans(2)%nptrs = nptrs([2, 3, 7, 8])
ans(3)%nptrs = nptrs([3, 4, 9, 10])
ans(4)%nptrs = nptrs([4, 1, 11, 12])
ans(1:)%xidimension = 1
ans(1:)%name = line4
CASE (Quadrangle8)
! ALLOCATE (ans(4))
ans(1)%nptrs = nptrs([1, 2, 5])
Expand Down
10 changes: 7 additions & 3 deletions src/submodules/ScalarField/src/ScalarField_Class@SetMethods.F90
Original file line number Diff line number Diff line change
Expand Up @@ -369,8 +369,8 @@
CHARACTER(*), PARAMETER :: myName = "obj_SetByFunction()"
LOGICAL(LGT) :: istimes, problem
INTEGER(I4B) :: ttime, returnType, nsd, tnodes, ii, globalNode(1)
REAL(DFP), ALLOCATABLE :: xij(:, :)
REAL(DFP) :: args(4), VALUE
REAL(DFP), ALLOCATABLE :: xij(:, :), args(:)
REAL(DFP) :: VALUE
INTEGER(I4B), PARAMETER :: needed_returnType = Scalar
CLASS(Domain_), POINTER :: dom

Expand All @@ -382,11 +382,15 @@
istimes = PRESENT(times)
problem = .FALSE.

args = 0.0_DFP
IF (istimes) THEN
ALLOCATE (args(4))
args = 0.0_DFP
ttime = SIZE(times)
args(4) = times(1)
problem = ttime .NE. 1_I4B
ELSE
ALLOCATE (args(3))
args = 0.0_DFP
END IF

IF (problem) THEN
Expand Down

0 comments on commit c94ddb7

Please sign in to comment.