Skip to content

Commit

Permalink
Updates in Domain_Class
Browse files Browse the repository at this point in the history
- fixing the issue #317
- Import methods from toml file are added
  • Loading branch information
shishiousan committed Dec 20, 2023
1 parent 4aeb51f commit 5b0419e
Show file tree
Hide file tree
Showing 2 changed files with 199 additions and 0 deletions.
56 changes: 56 additions & 0 deletions src/modules/Domain/src/Domain_Class.F90
Original file line number Diff line number Diff line change
Expand Up @@ -31,6 +31,8 @@ MODULE Domain_Class
USE ElementFactory
USE ExceptionHandler_Class, ONLY: e
USE HDF5File_Class
USE tomlf, ONLY: toml_table
USE TxtFile_Class
IMPLICIT NONE
PRIVATE
CHARACTER(*), PARAMETER :: modName = "Domain_Class"
Expand Down Expand Up @@ -170,6 +172,12 @@ MODULE Domain_Class
PROCEDURE, PASS(Obj) :: IMPORT => Domain_Import
!! Initiates an instance of domain by importing data from meshfile
!! TODO Add an export method to [[Domain_]] class
PROCEDURE, PASS(obj) :: ImportFromToml1 => Domain_ImportFromToml1
PROCEDURE, PASS(obj) :: ImportFromToml2 => Domain_ImportFromToml2
GENERIC, PUBLIC :: ImportFromToml => ImportFromToml1, &
& ImportFromToml2
!! Initiates an instance of domain by importing meshfile name from
!! Toml file
PROCEDURE, PUBLIC, PASS(obj) :: Display => Domain_Display
!! TODO Add a display method to [[Domain_]] class
PROCEDURE, PUBLIC, PASS(obj) :: DisplayMeshFacetData => &
Expand Down Expand Up @@ -512,6 +520,54 @@ MODULE SUBROUTINE Domain_Import(obj, hdf5, group)
END SUBROUTINE Domain_Import
END INTERFACE

!----------------------------------------------------------------------------
! ImportFromToml@IOMethods
!----------------------------------------------------------------------------

!> author: Shion Shimizu
! date: 2023-12-20
! summary: Initiate an instance of domain by importing meshfile name from
! Toml file
!
! NOTE: default meshfile name is "mesh.h5"
! and default group in hdf5 is ""
!
! NOTE: meshfile (hdf5) is internally initiated and is deallocated
! after initiation of domain

INTERFACE
MODULE SUBROUTINE Domain_ImportFromToml1(obj, table)
CLASS(Domain_), INTENT(INOUT) :: obj
TYPE(toml_table), INTENT(INOUT) :: table
END SUBROUTINE Domain_ImportFromToml1
END INTERFACE

!----------------------------------------------------------------------------
! ImportFromToml1@IOMethods
!----------------------------------------------------------------------------

!> author: Shion Shimizu
! date: 2023-12-20
! summary: Initiate an instance of domain by importing meshfile name from
! Toml file
!
! NOTE: default meshfile name is "mesh.h5"
! and default group in hdf5 is ""
!
! NOTE: meshfile (hdf5) is internally initiated and is deallocated
! after initiation of domain

INTERFACE
MODULE SUBROUTINE Domain_ImportFromToml2(obj, tomlName, afile, filename, &
& printToml)
CLASS(Domain_), INTENT(INOUT) :: obj
CHARACTER(*), INTENT(IN) :: tomlName
TYPE(TxtFile_), OPTIONAL, INTENT(INOUT) :: afile
CHARACTER(*), OPTIONAL, INTENT(IN) :: filename
LOGICAL(LGT), OPTIONAL, INTENT(IN) :: printToml
END SUBROUTINE Domain_ImportFromToml2
END INTERFACE

!----------------------------------------------------------------------------
! Display@IOMethods
!----------------------------------------------------------------------------
Expand Down
143 changes: 143 additions & 0 deletions src/submodules/Domain/src/Domain_Class@IOMethods.F90
Original file line number Diff line number Diff line change
Expand Up @@ -16,6 +16,18 @@

SUBMODULE(Domain_Class) IOMethods
USE BaseMethod
USE tomlf, ONLY: &
& toml_error, &
& toml_load, &
& toml_parser_config, &
& toml_serialize, &
& toml_get => get_value, &
& toml_len => len, &
& toml_context, &
& toml_terminal, &
& toml_load, &
& toml_array, &
& toml_stat
IMPLICIT NONE
CONTAINS

Expand Down Expand Up @@ -495,6 +507,137 @@
!
END PROCEDURE Domain_Import

!----------------------------------------------------------------------------
! ImportFromToml
!----------------------------------------------------------------------------

MODULE PROCEDURE Domain_ImportFromToml1
CHARACTER(*), PARAMETER :: myName = "Domain_ImportFromToml()"
TYPE(HDF5File_) :: meshfile
CHARACTER(:), ALLOCATABLE :: meshfilename, ext, group
CHARACTER(*), PARAMETER :: default_meshfilename = "mesh.h5"
CHARACTER(*), PARAMETER :: default_group = ""
INTEGER(i4b) :: origin, stat
LOGICAL(LGT) :: problem

#ifdef DEBUG_VER
CALL e%RaiseInformation(modName//'::'//myName//' - '// &
& '[START] ImportFromToml()')
#endif

CALL toml_get(table, "filename", meshfilename, default_meshfilename, &
& origin=origin, stat=stat)

ext = getExtension(meshfilename)
problem = .NOT. ext .EQ. "h5"

IF (problem) THEN
CALL e%RaiseError(modName//'::'//myName//' - '// &
& '[INTERNAL ERROR] :: given filename is not HDF5File. '// &
& 'Extension should be "h5"')
END IF

CALL toml_get(table, "group", group, default_group, &
& origin=origin, stat=stat)

CALL meshfile%Initiate(meshfilename, mode="READ")
CALL meshfile%OPEN()
CALL obj%IMPORT(hdf5=meshfile, group=group)
CALL meshfile%DEALLOCATE()

#ifdef DEBUG_VER
CALL e%RaiseInformation(modName//'::'//myName//' - '// &
& '[END] ImportFromToml()')
#endif

END PROCEDURE Domain_ImportFromToml1

!----------------------------------------------------------------------------
! ImportFromToml
!----------------------------------------------------------------------------

MODULE PROCEDURE Domain_ImportFromToml2
CHARACTER(*), PARAMETER :: myName = "Domain_ImportFromToml2()"
LOGICAL(LGT) :: isNotOpen, isNotRead
LOGICAL(LGT), PARAMETER :: color = .TRUE.
INTEGER(I4B), PARAMETER :: detail = 1
TYPE(toml_error), ALLOCATABLE :: error
TYPE(toml_context) :: context
TYPE(toml_terminal) :: terminal
TYPE(toml_table), ALLOCATABLE :: table
TYPE(toml_table), POINTER :: node
INTEGER(I4B) :: origin, stat

#ifdef DEBUG_VER
CALL e%RaiseInformation(modName//'::'//myName//' - '// &
& '[START] ImportFromToml2()')
#endif

terminal = toml_terminal(color)

IF (PRESENT(afile)) THEN
isNotOpen = .NOT. afile%IsOpen()
isNotRead = .NOT. afile%IsRead()

IF (isNotRead .OR. isNotOpen) THEN
CALL e%RaiseError(modName//'::'//myName//' - '// &
& '[INTERNAL ERROR] :: The file is not open or does not have '// &
& 'the access to read!')
END IF

CALL toml_load(table, &
& afile%GetUnitNo(), &
& context=context, &
& config=toml_parser_config(color=terminal, context_detail=detail), &
& error=error &
& )

ELSEIF (PRESENT(filename)) THEN
CALL toml_load(table, &
& filename, &
& context=context, &
& config=toml_parser_config(color=terminal, context_detail=detail), &
& error=error &
& )
ELSE
CALL e%RaiseError(modName//'::'//myName//' - '// &
& '[ARG ERROR] :: either filename or afile should be present!')
RETURN
END IF

IF (ALLOCATED(error)) THEN
CALL e%RaiseError(modName//'::'//myName//' - '// &
& '[INTERNAL ERROR] :: Some error occured while parsing toml file'// &
& ' with following message: '//error%message)
END IF

node => NULL()
CALL toml_get(table, tomlName, node, origin=origin, requested=.FALSE., &
& stat=stat)

IF (.NOT. ASSOCIATED(node)) THEN
CALL e%RaiseError(modName//'::'//myName//' - '// &
& '[CONFIG ERROR] :: following error occured while reading '// &
& 'the toml file :: cannot find '//tomlName//" table in config.")
END IF

CALL obj%ImportFromToml(table=node)

#ifdef DEBUG_VER
IF (PRESENT(printToml)) THEN
CALL Display(toml_serialize(node), &
& "Domain toml config = "//CHAR_LF, &
& unitNo=stdout)
END IF
#endif

#ifdef DEBUG_VER
CALL e%RaiseInformation(modName//'::'//myName//' - '// &
& '[END] ImportFromToml2()')
#endif

END PROCEDURE Domain_ImportFromToml2

!----------------------------------------------------------------------------
!
!----------------------------------------------------------------------------
Expand Down

0 comments on commit 5b0419e

Please sign in to comment.