Skip to main content

ImportFromToml

This method imports the configuration form a toml file and initiates the FEDOF instance.

The ImportFromToml method has two implementations:

  1. ImportFromToml1 - Imports configuration from a TOML table that's already loaded
  2. ImportFromToml2 - Imports configuration from a TOML file by name

Interface 1

In this interface to import the data we specify the toml table and mesh.

INTERFACE FEDOFImportFromToml
MODULE SUBROUTINE ImportFromToml(obj, table, mesh)
CLASS(FEDOF_), INTENT(INOUT) :: obj
TYPE(toml_table), INTENT(INOUT) :: table
CLASS(AbstractMesh_), TARGET, INTENT(IN) :: mesh
END SUBROUTINE ImportFromToml
END INTERFACE FEDOFImportFromToml

Interface 2

In this interface to import the data we specify the name of the toml file (or provide an instance of TxtFile), name of the key (tomlName), and mesh.

INTERFACE FEDOFImportFromToml
MODULE SUBROUTINE ImportFromToml(obj, tomlName, afile, &
filename, printToml, mesh)
CLASS(FEDOF_), INTENT(INOUT) :: obj
CHARACTER(*), INTENT(IN) :: tomlName
TYPE(TxtFile_), OPTIONAL, INTENT(INOUT) :: afile
CHARACTER(*), OPTIONAL, INTENT(IN) :: filename
LOGICAL(LGT), OPTIONAL, INTENT(IN) :: printToml
CLASS(AbstractMesh_), OPTIONAL, INTENT(IN) :: mesh
END SUBROUTINE ImportFromToml
END INTERFACE FEDOFImportFromToml

Template for Import for toml file

[test1]
baseContinuity = "H1"
baseInterpolation = "Hierarchical"
order = 1

[test2]
baseContinuity = "H1"
baseInterpolation = "Hierarchical"
order = 2

[test3]
baseContinuity = "H1"
baseInterpolation = "Hierarchical"
order = 3

[test4]
baseContinuity = "H1"
baseInterpolation = "Hierarchical"
order = 4

[test5]
baseContinuity = "H1"
baseInterpolation = "Hierarchical"
order = [1]

[test6]
baseContinuity = "H1"
baseInterpolation = "Hierarchical"
order = [2]

[test7]
baseContinuity = "H1"
baseInterpolation = "Hierarchical"
order = [3]

[test8]
baseContinuity = "H1"
baseInterpolation = "Hierarchical"
order = [4]

Example 1

!> author: Vikas Sharma, Ph. D.
! date: 2025-06-01
! summary: Initiate FEDOF object by import from toml

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

IMPLICIT NONE

TYPE(FEDOF_) :: obj
TYPE(FEDomain_) :: dom
CLASS(AbstractMesh_), POINTER :: meshptr => NULL()
CHARACTER(*), PARAMETER :: filename = &
"../../FEMesh/examples/meshdata/small_tri3_mesh.h5"
TYPE(HDF5File_) :: meshfile
INTEGER(I4B) :: found, want

CALL e%setQuietMode(EXCEPTION_INFORMATION, .TRUE.)
CALL meshfile%Initiate(filename, mode="READ")
CALL meshfile%OPEN()
CALL dom%Initiate(meshfile, '')

meshptr => dom%GetMeshPointer()

CALL obj%ImportFromToml(tomlName="test1", &
filename="./toml/_ImportFromToml_test_1.toml", mesh=meshptr)
!CALL fedof%Display("FEDOF:")
found = obj%GetTotalDOF()
want = meshptr%GetTotalNodes()
CALL IS(found, want, "Total DOF (order=1): ")

CALL obj%ImportFromToml(tomlName="test2", &
filename="./toml/_ImportFromToml_test_1.toml", mesh=meshptr)
found = obj%GetTotalDOF()
want = meshptr%GetTotalNodes() + meshptr%GetTotalFaces() + 0*meshptr%GetTotalCells()
CALL IS(found, want, "Total DOF (order=2): ")

CALL obj%ImportFromToml(tomlName="test3", &
filename="./toml/_ImportFromToml_test_1.toml", mesh=meshptr)
found = obj%GetTotalDOF()
want = meshptr%GetTotalNodes() + 2*meshptr%GetTotalFaces() + 1*meshptr%GetTotalCells()
CALL IS(found, want, "Total DOF (order=3): ")

CALL obj%ImportFromToml(tomlName="test4", &
filename="./toml/_ImportFromToml_test_1.toml", mesh=meshptr)
found = obj%GetTotalDOF()
want = meshptr%GetTotalNodes() + 3*meshptr%GetTotalFaces() + 3*meshptr%GetTotalCells()
CALL OK(found == want, "Total DOF (order=4): ")

CALL obj%ImportFromToml(tomlName="test5", &
filename="./toml/_ImportFromToml_test_1.toml", mesh=meshptr)
!CALL fedof%Display("FEDOF:")
found = obj%GetTotalDOF()
want = meshptr%GetTotalNodes()
CALL IS(found, want, "Total DOF (order=1): ")

CALL obj%ImportFromToml(tomlName="test6", &
filename="./toml/_ImportFromToml_test_1.toml", mesh=meshptr)
found = obj%GetTotalDOF()
want = meshptr%GetTotalNodes() + meshptr%GetTotalFaces() + 0*meshptr%GetTotalCells()
CALL IS(found, want, "Total DOF (order=2): ")

CALL obj%ImportFromToml(tomlName="test7", &
filename="./toml/_ImportFromToml_test_1.toml", mesh=meshptr)
found = obj%GetTotalDOF()
want = meshptr%GetTotalNodes() + 2*meshptr%GetTotalFaces() + 1*meshptr%GetTotalCells()
CALL IS(found, want, "Total DOF (order=3): ")

CALL obj%ImportFromToml(tomlName="test8", &
filename="./toml/_ImportFromToml_test_1.toml", mesh=meshptr)
found = obj%GetTotalDOF()
want = meshptr%GetTotalNodes() + 3*meshptr%GetTotalFaces() + 3*meshptr%GetTotalCells()
CALL OK(found == want, "Total DOF (order=4): ")

!CALL dom%Display("domain:")
CALL dom%DEALLOCATE()
CALL meshfile%DEALLOCATE()

END PROGRAM main

Example 2

!> author: Vikas Sharma, Ph. D.
! date:
! summary: Initiate fedof with H1 and Heirarchical bases, order is a vector.

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 ReallocateUtility

IMPLICIT NONE

TYPE(FEDOF_) :: fedof
TYPE(FEDomain_) :: dom
CLASS(AbstractMesh_), POINTER :: meshptr => NULL()
CHARACTER(*), PARAMETER :: filename = &
"../../FEMesh/examples/meshdata/small_tri3_mesh.h5"
TYPE(HDF5File_) :: meshfile
LOGICAL(LGT) :: isok
INTEGER(I4B) :: found, want, order, ii, iel

CALL e%setQuietMode(EXCEPTION_INFORMATION, .TRUE.)
CALL meshfile%Initiate(filename, mode="READ")
CALL meshfile%OPEN()
CALL dom%Initiate(meshfile, '')

meshptr => dom%GetMeshPointer()

CALL fedof%ImportFromToml(tomlName="test1", &
filename="./toml/_ImportFromToml_test_2.toml", mesh=meshptr)

! CALL fedof%DisplayCellOrder("Debug Cell order", full=.TRUE.)

found = fedof%GetTotalDOF()
want = 39
isok = found == want
CALL IS(found, want, "Total DOF ")

! CALL Display(fedof%GetConnectivity(globalElement=13, islocal=.FALSE., opt="A"), &
! "connectivity of global element 13", full=.TRUE.)

CALL dom%DEALLOCATE()
CALL meshfile%DEALLOCATE()

END PROGRAM main