GetCellOrder
The GetCellOrder
method retrieves the polynomial order of a specified cell element.
Interface
MODULE SUBROUTINE obj_GetCellOrder(obj, cellOrder, tCellOrder, globalElement, islocal)
CLASS(FEDOF_), INTENT(IN) :: obj
!! fedof object
INTEGER(I4B), INTENT(INOUT) :: cellOrder(:)
!! cell order
INTEGER(I4B), INTENT(OUT) :: tCellOrder
!! size of data written in cellOrder
INTEGER(I4B), INTENT(IN) :: globalElement
!! global or local element number
LOGICAL(LGT), OPTIONAL, INTENT(IN) :: islocal
!! if true then globalElement is local element
END SUBROUTINE obj_GetCellOrder
Description
The GetCellOrder
method retrieves the polynomial order of a specified cell element. The polynomial order determines the degree of the basis functions used for approximation within that element, which directly impacts the accuracy and computational cost of the finite element solution.
Parameters
obj
- Input,CLASS(FEDOF_)
, FEDOF object instancecellOrder
- Output,INTEGER(I4B)(:)
, pre-allocated array to store the cell ordertCellOrder
- Output,INTEGER(I4B)
, total size of data written to thecellOrder
array (typically 1)globalElement
- Input,INTEGER(I4B)
, global or local element numberislocal
- Optional Input,LOGICAL(LGT)
, if true,globalElement
is treated as a local element number
Implementation Details
The implementation converts the global element number to a local element number if needed, then retrieves the cell order from the internal storage:
INTEGER(I4B) :: jj
jj = obj%mesh%GetLocalElemNumber(globalElement=globalElement, islocal=islocal)
cellOrder(1) = obj%cellOrder(jj)
tcellOrder = 1
Usage Example
! Example to get the order of a cell
INTEGER(I4B) :: order(1), tOrder
TYPE(FEDOF_) :: myDOF
! Get order for element #5
CALL myDOF%GetCellOrder(cellOrder=order, tCellOrder=tOrder, globalElement=5)
PRINT *, "Element 5 has order:", order(1)
! Get order for element #3 using local numbering
CALL myDOF%GetCellOrder(cellOrder=order, tCellOrder=tOrder, globalElement=3, islocal=.TRUE.)
PRINT *, "Local element 3 has order:", order(1)
Important Notes
- The
cellOrder
array typically only needs one element as this method returns a single value - The
tCellOrder
return value will typically be 1, indicating a single value written tocellOrder
- In p-adaptive finite element methods, different cells may have different polynomial orders
Related Methods
GetOrders
- More comprehensive method that returns cell, face, and edge orders along with their orientationsSetCellOrder
- Sets the polynomial order for cellsGetLocalElemShapeData
- Uses the cell order to determine the appropriate shape functionsGetQuadraturePoints
- Often needs the cell order to determine appropriate quadrature rules
The GetCellOrder
method is important for finite element implementations that use p-adaptive methods or variable-order elements, where the polynomial degree may vary between elements to optimize computational efficiency.
Example
!> author: Vikas Sharma, Ph. D.
! date: 2025-06-07
! summary: Testing GetCellOrder method of FEDOF class
! H1 Heirarchical Second Order Triangular Mesh
PROGRAM main
USE FEDOF_Class
USE FEDomain_Class
USE AbstractMesh_Class
USE HDF5File_Class
USE Display_Method
USE GlobalData
USE Test_Method
USE ExceptionHandler_Class, ONLY: e, EXCEPTION_INFORMATION
USE AppendUtility
USE ArangeUtility
USE ReallocateUtility
IMPLICIT NONE
CHARACTER(*), PARAMETER :: &
filename = "../../FEMesh/examples/meshdata/small_tri3_mesh.h5", &
baseContinuity = "H1", &
baseInterpolation = "Heirarchical", &
testname = baseContinuity//" "//baseInterpolation//" GetCellDOF test"
TYPE(FEDOF_) :: fedof
TYPE(FEDomain_) :: dom
CLASS(AbstractMesh_), POINTER :: meshptr => NULL()
TYPE(HDF5File_) :: meshfile
INTEGER(I4B) :: order, totalVertexNodes, totalFaces
LOGICAL(LGT) :: isok
CALL e%SetQuietMode(EXCEPTION_INFORMATION, .TRUE.)
CALL meshfile%Initiate(filename, mode="READ")
CALL meshfile%OPEN()
CALL dom%Initiate(meshfile, '')
meshptr => dom%GetMeshPointer()
totalVertexNodes = meshptr%GetTotalVertexNodes()
totalFaces = meshptr%GetTotalFaces()
CALL test1
CALL test2
CALL test3
CALL test4
CALL dom%DEALLOCATE()
CALL meshfile%DEALLOCATE()
CONTAINS
!----------------------------------------------------------------------------
! test1
!----------------------------------------------------------------------------
SUBROUTINE test1
INTEGER(I4B) :: tsize, found(10), want(10)
order = 1
CALL fedof%Initiate(baseContinuity=baseContinuity, &
baseInterpolation=baseInterpolation, &
order=order, mesh=meshptr)
CALL fedof%GetCellOrder(globalElement=1, islocal=.TRUE., &
cellOrder=found, tCellOrder=tsize)
want(1) = 1
CALL IS(found(1), want(1), testname//" (order= "//ToString(order)//"): ")
END SUBROUTINE test1
!----------------------------------------------------------------------------
! test2
!----------------------------------------------------------------------------
SUBROUTINE test2
INTEGER(I4B) :: tsize, found(10), want(10)
order = 2
CALL fedof%Initiate(baseContinuity=baseContinuity, &
baseInterpolation=baseInterpolation, &
order=order, mesh=meshptr)
CALL fedof%GetCellOrder(globalElement=1, islocal=.TRUE., &
cellOrder=found, tCellOrder=tsize)
want(1) = 2
CALL IS(found(1), want(1), testname//" (order= "//ToString(order)//"): ")
END SUBROUTINE test2
!----------------------------------------------------------------------------
! test3
!----------------------------------------------------------------------------
SUBROUTINE test3
INTEGER(I4B) :: tsize, found(10), want(10)
order = 3
CALL fedof%Initiate(baseContinuity=baseContinuity, &
baseInterpolation=baseInterpolation, &
order=order, mesh=meshptr)
CALL fedof%GetCellOrder(globalElement=1, islocal=.TRUE., &
cellOrder=found, tCellOrder=tsize)
want(1) = 3
CALL IS(found(1), want(1), testname//" (order= "//ToString(order)//"): ")
END SUBROUTINE test3
!----------------------------------------------------------------------------
! test3
!----------------------------------------------------------------------------
SUBROUTINE test4
INTEGER(I4B) :: tsize, found(10), want(10)
order = 4
CALL fedof%Initiate(baseContinuity=baseContinuity, &
baseInterpolation=baseInterpolation, &
order=order, mesh=meshptr)
CALL fedof%GetCellOrder(globalElement=1, islocal=.TRUE., &
cellOrder=found, tCellOrder=tsize)
want(1) = 4
CALL IS(found(1), want(1), testname//" (order= "//ToString(order)//"): ")
END SUBROUTINE test4
!----------------------------------------------------------------------------
!
!----------------------------------------------------------------------------
END PROGRAM main