Merge branch '300-further-command-line-arguments' into 'development'

option to specify numerics configuration file and jobname

Closes #300

See merge request damask/DAMASK!772
This commit is contained in:
Philip Eisenlohr 2023-07-12 13:24:00 +00:00
commit 61f1cdf70d
7 changed files with 227 additions and 159 deletions

@ -1 +1 @@
Subproject commit 9f4ffce8b2df951191a14dc3229de1aee6e544e6
Subproject commit d61d62667fb683a61dcc41cd90194a2d9b279879

View File

@ -21,14 +21,16 @@ module CLI
implicit none(type,external)
private
integer, public, protected :: &
CLI_restartInc = 0 !< Increment at which calculation starts
CLI_restartInc = 0 !< increment at which calculation starts
character(len=:), allocatable, public, protected :: &
CLI_geomFile, & !< parameter given for geometry file
CLI_loadFile, & !< parameter given for load case file
CLI_materialFile
CLI_geomFile, & !< location of the geometry file
CLI_loadFile, & !< location of the load case file
CLI_materialFile, & !< location of the material configuration file
CLI_numericsFile, & !< location of the numerics configuration file
solverJobname
public :: &
getSolverJobName, &
getSolverJobname, &
CLI_init
contains
@ -47,148 +49,190 @@ subroutine CLI_init()
character(len=:), allocatable :: &
commandLine, & !< command line call as string
arg, & !< individual argument
loadCaseArg, & !< -l argument given to the executable
geometryArg, & !< -g argument given to the executable
materialArg, & !< -m argument given to the executable
workingDirArg !< -w argument given to the executable
geomArg, & !< -g CLI argument
loadArg, & !< -l CLI argument
materialArg, & !< -m CLI argument
numericsArg, & !< -n CLI argument
workingDirArg !< -w CLI argument
integer :: &
stat, &
i
integer, dimension(8) :: &
dateAndTime
logical :: &
hasArg
external :: &
quit
workingDirArg = getCWD()
print '(/,1x,a)', '<<<+- CLI init -+>>>'
print'(/,1x,a)', '<<<+- CLI init -+>>>'
! http://patorjk.com/software/taag/#p=display&f=Lean&t=DAMASK%203
#ifdef DEBUG
print '(a)', achar(27)//'[31m'
print '(1x,a,/)', 'debug version - debug version - debug version - debug version - debug version'
print'(a)', achar(27)//'[31m'
print'(1x,a,/)', 'debug version - debug version - debug version - debug version - debug version'
#else
print '(a)', achar(27)//'[94m'
print'(a)', achar(27)//'[94m'
#endif
print '(1x,a)', ' _/_/_/ _/_/ _/ _/ _/_/ _/_/_/ _/ _/ _/_/_/'
print '(1x,a)', ' _/ _/ _/ _/ _/_/ _/_/ _/ _/ _/ _/ _/ _/'
print '(1x,a)', ' _/ _/ _/_/_/_/ _/ _/ _/ _/_/_/_/ _/_/ _/_/ _/_/'
print '(1x,a)', ' _/ _/ _/ _/ _/ _/ _/ _/ _/ _/ _/ _/'
print '(1x,a)', '_/_/_/ _/ _/ _/ _/ _/ _/ _/_/_/ _/ _/ _/_/_/'
print'(1x,a)', ' _/_/_/ _/_/ _/ _/ _/_/ _/_/_/ _/ _/ _/_/_/'
print'(1x,a)', ' _/ _/ _/ _/ _/_/ _/_/ _/ _/ _/ _/ _/ _/'
print'(1x,a)', ' _/ _/ _/_/_/_/ _/ _/ _/ _/_/_/_/ _/_/ _/_/ _/_/'
print'(1x,a)', ' _/ _/ _/ _/ _/ _/ _/ _/ _/ _/ _/ _/'
print'(1x,a)', '_/_/_/ _/ _/ _/ _/ _/ _/ _/_/_/ _/ _/ _/_/_/'
#if defined(GRID)
print '(1x,a)', 'Grid solver'
print'(1x,a)', 'Grid solver'
#elif defined(MESH)
print '(1x,a)', 'Mesh solver'
print'(1x,a)', 'Mesh solver'
#endif
#ifdef DEBUG
print '(/,1x,a)', 'debug version - debug version - debug version - debug version - debug version'
print'(/,1x,a)', 'debug version - debug version - debug version - debug version - debug version'
#endif
print '(a)', achar(27)//'[0m'
print'(a)', achar(27)//'[0m'
print '(1x,a)', 'F. Roters et al., Computational Materials Science 158:420478, 2019'
print '(1x,a)', 'https://doi.org/10.1016/j.commatsci.2018.04.030'
print'(1x,a)', 'F. Roters et al., Computational Materials Science 158:420478, 2019'
print'(1x,a)', 'https://doi.org/10.1016/j.commatsci.2018.04.030'
print '(/,1x,a)', 'Version: '//DAMASKVERSION
print'(/,1x,a)', 'Version: '//DAMASKVERSION
print '(/,1x,a)', 'Compiled with: '//compiler_version()
print '(1x,a)', 'Compiled on: '//CMAKE_SYSTEM
print '(1x,a)', 'Compiler options: '//compiler_options()
print'(/,1x,a)', 'Compiled with: '//compiler_version()
print'(1x,a)', 'Compiled on: '//CMAKE_SYSTEM
print'(1x,a)', 'Compiler options: '//compiler_options()
! https://github.com/jeffhammond/HPCInfo/blob/master/docs/Preprocessor-Macros.md
print '(/,1x,a)', 'Compiled on: '//__DATE__//' at '//__TIME__
print'(/,1x,a)', 'Compiled on: '//__DATE__//' at '//__TIME__
print '(/,1x,a,1x,i0,a,i0,a,i0)', &
print'(/,1x,a,1x,i0,a,i0,a,i0)', &
'PETSc version:',PETSC_VERSION_MAJOR,'.',PETSC_VERSION_MINOR,'.',PETSC_VERSION_SUBMINOR
call date_and_time(values = dateAndTime)
print '(/,1x,a,1x,2(i2.2,a),i4.4)', 'Date:',dateAndTime(3),'/',dateAndTime(2),'/',dateAndTime(1)
print '(1x,a,1x,2(i2.2,a),i2.2)', 'Time:',dateAndTime(5),':',dateAndTime(6),':',dateAndTime(7)
print'(/,1x,a,1x,2(i2.2,a),i4.4)', 'Date:',dateAndTime(3),'/',dateAndTime(2),'/',dateAndTime(1)
print'(1x,a,1x,2(i2.2,a),i2.2)', 'Time:',dateAndTime(5),':',dateAndTime(6),':',dateAndTime(7)
do i = 1, command_argument_count()
hasArg = i < command_argument_count()
arg = getArg(i)
select case(trim(arg)) ! extract key
case ('-h','--help')
print '(/,1x,a)','#######################################################################'
print '(1x,a)', 'DAMASK Command Line Interface:'
print '(1x,a)', 'Düsseldorf Advanced Material Simulation Kit with PETSc-based solvers'
print '(1x,a,/)','#######################################################################'
print '(1x,a,/)','Valid command line switches:'
print '(1x,a)', ' --geom (-g, --geometry)'
print '(1x,a)', ' --load (-l, --loadcase)'
print '(1x,a)', ' --material (-m, --materialconfig)'
print '(1x,a)', ' --workingdir (-w, --wd, --workingdirectory)'
print '(1x,a)', ' --restart (-r, --rs)'
print '(1x,a)', ' --help (-h)'
print '(/,1x,a)','-----------------------------------------------------------------------'
print '(1x,a)', 'Mandatory arguments:'
print '(/,1x,a)',' --geom PathToGeomFile/NameOfGeom'
print '(1x,a)', ' Specifies the location of the geometry definition file.'
print '(/,1x,a)',' --load PathToLoadFile/NameOfLoadFile'
print '(1x,a)', ' Specifies the location of the load case definition file.'
print '(/,1x,a)',' --material PathToMaterialConfigurationFile/NameOfMaterialConfigurationFile'
print '(1x,a)', ' Specifies the location of the material configuration file.'
print '(/,1x,a)','-----------------------------------------------------------------------'
print '(1x,a)', 'Optional arguments:'
print '(/,1x,a)',' --workingdirectory PathToWorkingDirectory'
print '(1x,a)', ' Specifies the base directory of relative paths.'
print '(/,1x,a)',' --restart N'
print '(1x,a)', ' Reads in increment N and continues with calculating'
print '(1x,a)', ' increment N+1, N+2, ... based on this.'
print '(1x,a)', ' Appends to existing results file'
print '(1x,a)', ' "NameOfGeom_NameOfLoadFile_NameOfMaterialConfigurationFile.hdf5".'
print '(1x,a)', ' Works only if the restart information for increment N'
print '(1x,a)', ' is available in the base directory.'
print '(/,1x,a)','-----------------------------------------------------------------------'
print '(1x,a)', 'Help:'
print '(/,1x,a)',' --help'
print '(1x,a,/)',' Prints this message and exits'
print'(/,1x,a)','#######################################################################'
print'(1x,a)', 'DAMASK Command Line Interface:'
print'(1x,a)', 'Düsseldorf Advanced Material Simulation Kit with PETSc-based solvers'
print'(1x,a,/)','#######################################################################'
print'(1x,a,/)','Valid command line switches:'
print'(1x,a)', ' --geom (-g, --geometry)'
print'(1x,a)', ' --load (-l, --loadcase)'
print'(1x,a)', ' --material (-m, --materialconfig)'
print'(1x,a)', ' --numerics (-n, --numericsconfig)'
print'(1x,a)', ' --jobname (-j, --job)'
print'(1x,a)', ' --workingdir (-w, --wd, --workingdirectory)'
print'(1x,a)', ' --restart (-r, --rs)'
print'(1x,a)', ' --help (-h)'
print'(/,1x,a)','-----------------------------------------------------------------------'
print'(1x,a)', 'Mandatory arguments:'
print'(/,1x,a)',' --geom GEOMFILE'
print'(1x,a)', ' specify the file path of the geometry definition'
print'(/,1x,a)',' --load LOADFILE'
print'(1x,a)', ' specify the file path of the load case definition'
print'(/,1x,a)',' --material MATERIALFILE'
print'(1x,a)', ' specify the file path of the material configuration'
print'(/,1x,a)','-----------------------------------------------------------------------'
print'(1x,a)', 'Optional arguments:'
print'(/,1x,a)',' --numerics NUMERICSFILE'
print'(1x,a)', ' Specify the file path of the numerics configuration'
print'(/,1x,a)',' --jobname JOBNAME'
print'(1x,a)', ' specify the job name.'
print'(1x,a)', ' Defaults to GEOM_LOAD_MATERIAL[_NUMERICS].'
print'(/,1x,a)',' --workingdirectory WORKINGDIRECTORY'
print'(1x,a)', ' specify the base directory of relative paths.'
print'(1x,a)', ' Defaults to the current working directory'
print'(/,1x,a)',' --restart N'
print'(1x,a)', ' read in increment N and continues with calculating'
print'(1x,a)', ' increment N+1, N+2, ... based on this'
print'(1x,a)', ' works only if the restart information for increment N'
print'(1x,a)', ' is available in JOBNAME_restart.hdf5'
print'(1x,a)', ' append to existing results file JOBNAME.hdf5'
print'(/,1x,a)','-----------------------------------------------------------------------'
print'(1x,a)', 'Help:'
print'(/,1x,a)',' --help'
print'(1x,a,/)',' Prints this message and exits'
call quit(0) ! normal Termination
case ('-l', '--load', '--loadcase')
loadCaseArg = getArg(i+1)
case ('-g', '--geom', '--geometry')
geometryArg = getArg(i+1)
if (.not. hasArg) print'(/,1x,a)', 'ERROR: missing argument for --geom'
geomArg = getArg(i+1)
case ('-l', '--load', '--loadcase')
if (.not. hasArg) print'(/,1x,a)', 'ERROR: missing argument for --load'
loadArg = getArg(i+1)
case ('-m', '--material', '--materialconfig')
if (.not. hasArg) print'(/,1x,a)', 'ERROR: missing argument for --material'
materialArg = getArg(i+1)
case ('-n', '--numerics', '--numericsconfig')
if (.not. hasArg) print'(/,1x,a)', 'ERROR: missing argument for --numerics'
numericsArg = getArg(i+1)
case ('-j', '--job', '--jobname')
if (.not. hasArg) print'(/,1x,a)', 'ERROR: missing argument for --jobname'
solverJobname = getArg(i+1)
case ('-w', '--wd', '--workingdir', '--workingdirectory')
if (.not. hasArg) print'(/,1x,a)', 'ERROR: missing argument for --workingdirectory'
workingDirArg = getArg(i+1)
case ('-r', '--rs', '--restart')
if (.not. hasArg) print'(/,1x,a)', 'ERROR: missing argument for --restart'
arg = getArg(i+1)
read(arg,*,iostat=stat) CLI_restartInc
if (CLI_restartInc < 0 .or. stat /= 0) then
print'(/,1x,a)', 'ERROR: Could not parse restart increment: '//trim(arg)
print'(/,1x,a)', 'ERROR: could not parse restart increment: '//trim(arg)
call quit(1)
end if
end select
end do
if (.not. all([allocated(loadcaseArg),allocated(geometryArg),allocated(materialArg)])) then
print '(/,1x,a)', 'ERROR: Please specify geometry AND load case AND material configuration (-h for help)'
if (.not. allocated(loadArg)) then
print'(/,1x,a)', 'Error: no load case specified (-h for help)'
call quit(1)
end if
if (.not. allocated(geomArg)) then
print'(/,1x,a)', 'Error: no geometry specified (-h for help)'
call quit(1)
end if
if (.not. allocated(materialArg)) then
print'(/,1x,a)', 'Error: no material configuration specified (-h for help)'
call quit(1)
end if
call setWorkingDirectory(trim(workingDirArg))
CLI_geomFile = getPathRelCWD(geometryArg,'geometry')
CLI_loadFile = getPathRelCWD(loadCaseArg,'load case')
CLI_geomFile = getPathRelCWD(geomArg,'geometry')
CLI_loadFile = getPathRelCWD(loadArg,'load case')
CLI_materialFile = getPathRelCWD(materialArg,'material configuration')
if (allocated(numericsArg)) &
CLI_numericsFile = getPathRelCWD(numericsArg,'numerics configuration')
if (.not. allocated(solverJobname)) then
solverJobname = jobname(CLI_geomFile,CLI_loadFile,CLI_materialFile,CLI_numericsFile)
elseif (scan(solverJobname,'/') > 0) then
print'(/,1x,a)', 'ERROR: JOBNAME must not contain any slashes'
call quit(1)
endif
commandLine = getArg(-1)
print '(/,1x,a)', 'Host name: '//getHostName()
print '(1x,a)', 'User name: '//getUserName()
print'(/,1x,a)', 'Host name: '//getHostName()
print'(1x,a)', 'User name: '//getUserName()
print '(/,1x,a,/)', 'Command line call: '//trim(commandLine)
print '(1x,a)', 'Working directory: '//IO_glueDiffering(getCWD(),workingDirArg)
print '(1x,a)', 'Geometry: '//IO_glueDiffering(CLI_geomFile,geometryArg)
print '(1x,a)', 'Load case: '//IO_glueDiffering(CLI_loadFile,loadCaseArg)
print '(1x,a)', 'Material config: '//IO_glueDiffering(CLI_materialFile,materialArg)
print '(1x,a)', 'Solver job name: '//getSolverJobName()
print'(/,1x,a,/)', 'Command line call: '//trim(commandLine)
print'(1x,a)', 'Working directory: '//IO_glueDiffering(getCWD(),workingDirArg)
print'(1x,a)', 'Geometry: '//IO_glueDiffering(CLI_geomFile,geomArg)
print'(1x,a)', 'Load case: '//IO_glueDiffering(CLI_loadFile,loadArg)
print'(1x,a)', 'Material config: '//IO_glueDiffering(CLI_materialFile,materialArg)
print'(1x,a)', 'Solver job name: '//getSolverJobname()
if (CLI_restartInc > 0) &
print '(1x,a,i6.6)', 'Restart from increment: ', CLI_restartInc
print'(1x,a,i6.6)', 'Restart from increment: ', CLI_restartInc
end subroutine CLI_init
!--------------------------------------------------------------------------------------------------
!> @brief Get argument from command line.
!--------------------------------------------------------------------------------------------------
@ -242,7 +286,7 @@ subroutine setWorkingDirectory(workingDirectoryArg)
workingDirectory = trim(normpath(workingDirectory))
error = setCWD(trim(workingDirectory))
if (error) then
print '(1x,a)', 'ERROR: Invalid Working directory: '//trim(workingDirectory)
print'(1x,a)', 'ERROR: invalid working directory: '//trim(workingDirectory)
call quit(1)
end if
@ -250,26 +294,44 @@ end subroutine setWorkingDirectory
!--------------------------------------------------------------------------------------------------
!> @brief solver job name (no extension) as combination of geometry and load case name
!> @brief Return solver job name (MSC.Marc compatible).
!--------------------------------------------------------------------------------------------------
function getSolverJobName()
function getSolverJobname()
character(len=:), allocatable :: getSolverJobName
integer :: posExt,posSep
character(len=:), allocatable :: getSolverJobname
posExt = scan(CLI_geomFile,'.',back=.true.)
posSep = scan(CLI_geomFile,'/',back=.true.)
getSolverJobname = solverJobname
getSolverJobName = CLI_geomFile(posSep+1:posExt-1)
end function getSolverJobname
posExt = scan(CLI_loadFile,'.',back=.true.)
posSep = scan(CLI_loadFile,'/',back=.true.)
getSolverJobName = getSolverJobName//'_'//CLI_loadFile(posSep+1:posExt-1)
!--------------------------------------------------------------------------------------------------
!> @brief Determine solver job name.
!--------------------------------------------------------------------------------------------------
function jobname(geomFile,LoadFile,materialsFile,numericsFile)
end function getSolverJobName
character(len=:), allocatable :: jobname
character(len=*), intent(in) :: geomFile,loadFile,materialsFile
character(len=:), allocatable, intent(in) :: numericsFile
jobname = stem(geomFile)//'_'//stem(loadFile)//'_'//stem(materialsFile)
if (allocated(numericsFile)) jobname = jobname//'_'//stem(numericsFile)
contains
function stem(fullname)
character(len=:), allocatable :: stem
character(len=*), intent(in) :: fullname
stem = fullname(scan(fullname,'/',back=.true.)+1:scan(fullname,'.',back=.true.)-1)
end function stem
end function jobname
!--------------------------------------------------------------------------------------------------
@ -291,7 +353,7 @@ function getPathRelCWD(path,fileType)
inquire(file=getPathRelCWD, exist=file_exists)
if (.not. file_exists) then
print '(1x,a)', 'ERROR: '//fileType//' file does not exist: '//trim(getPathRelCWD)
print'(/,1x,a)', 'ERROR: '//fileType//' file does not exist: '//trim(getPathRelCWD)
call quit(1)
end if

View File

@ -210,9 +210,9 @@ subroutine inputRead(elem,node0_elem,connectivity_elem,materialAt)
call result_openJobFile()
call result_writeDataset_str(IO_read(trim(getSolverJobName())//InputFileExtension), 'setup', &
trim(getSolverJobName())//InputFileExtension, &
'MSC.Marc input deck')
call result_addSetupFile(IO_read(trim(getSolverJobName())//InputFileExtension), &
trim(getSolverJobName())//InputFileExtension, &
'MSC.Marc input deck')
call result_closeJobFile()
inputFile = IO_readlines(trim(getSolverJobName())//InputFileExtension)

View File

@ -34,8 +34,23 @@ subroutine config_init()
print'(/,1x,a)', '<<<+- config init -+>>>'; flush(IO_STDOUT)
call parse_material()
call parse_numerics()
#if defined(MESH) || defined(GRID)
config_material => parse(CLI_materialFile,'material configuration')
#else
config_material => parse('material.yaml','material configuration')
#endif
config_numerics => emptyDict
#if defined(MESH) || defined(GRID)
if (allocated(CLI_numericsFile)) &
config_numerics => parse(CLI_numericsFile,'numerics configuration')
#else
MSCMarc: block
logical :: exists
inquire(file='numerics.yaml',exist=exists)
if (exists) config_numerics => parse('numerics.yaml','numerics configuration')
end block MSCMarc
#endif
end subroutine config_init
@ -68,11 +83,10 @@ end subroutine config_numerics_deallocate
!--------------------------------------------------------------------------------------------------
function config_listReferences(config,indent) result(references)
type(tDict) :: config
integer, optional :: indent
type(tDict), intent(in) :: config
integer, intent(in), optional :: indent
character(len=:), allocatable :: references
type(tList), pointer :: ref
character(len=:), allocatable :: filler
integer :: r
@ -93,63 +107,27 @@ end function config_listReferences
!--------------------------------------------------------------------------------------------------
!> @brief Read material.yaml.
!> @brief Read configuration, spread over all processes, and add to DADF5.
!--------------------------------------------------------------------------------------------------
subroutine parse_material()
function parse(fname,description)
character(len=*), intent(in) :: fname, description
type(tDict), pointer :: parse
character(len=:), allocatable :: fileContent
logical :: fileExists
character(len=:), allocatable :: &
fileContent, fname
if (worldrank == 0) then
print'(/,1x,a)', 'reading material configuration'; flush(IO_STDOUT)
#if defined(MESH) || defined(GRID)
fname = CLI_materialFile
#else
fname = 'material.yaml'
#endif
print'(/,1x,a)', 'reading '//description; flush(IO_STDOUT)
fileContent = IO_read(fname)
if (scan(fname,'/') /= 0) fname = fname(scan(fname,'/',.true.)+1:)
call result_openJobFile(parallel=.false.)
call result_writeDataset_str(fileContent,'setup',fname,'material configuration')
call result_addSetupFile(fileContent,fname,description)
call result_closeJobFile()
end if
call parallelization_bcast_str(fileContent)
config_material => YAML_parse_str_asDict(fileContent)
parse => YAML_parse_str_asDict(fileContent)
end subroutine parse_material
!--------------------------------------------------------------------------------------------------
!> @brief Read numerics.yaml.
!--------------------------------------------------------------------------------------------------
subroutine parse_numerics()
logical :: fileExists
character(len=:), allocatable :: fileContent
config_numerics => emptyDict
inquire(file='numerics.yaml', exist=fileExists)
if (fileExists) then
if (worldrank == 0) then
print'(1x,a)', 'reading numerics.yaml'; flush(IO_STDOUT)
fileContent = IO_read('numerics.yaml')
if (len(fileContent) > 0) then
call result_openJobFile(parallel=.false.)
call result_writeDataset_str(fileContent,'setup','numerics.yaml','numerics configuration')
call result_closeJobFile()
end if
end if
call parallelization_bcast_str(fileContent)
config_numerics => YAML_parse_str_asDict(fileContent)
end if
end subroutine parse_numerics
end function parse
end module config

View File

@ -146,7 +146,7 @@ program DAMASK_grid
fname = CLI_loadFile
if (scan(fname,'/') /= 0) fname = fname(scan(fname,'/',.true.)+1:)
call result_openJobFile(parallel=.false.)
call result_writeDataset_str(fileContent,'setup',fname,'load case definition (grid solver)')
call result_addSetupFile(fileContent,fname,'load case definition (grid solver)')
call result_closeJobFile()
end if

View File

@ -89,7 +89,7 @@ subroutine discretization_grid_init(restart)
fname = CLI_geomFile
if (scan(fname,'/') /= 0) fname = fname(scan(fname,'/',.true.)+1:)
call result_openJobFile(parallel=.false.)
call result_writeDataset_str(fileContent,'setup',fname,'geometry definition (grid solver)')
call result_addSetupFile(fileContent,fname,'geometry definition (grid solver)')
call result_closeJobFile()
else
allocate(materialAt_global(0)) ! needed for IntelMPI

View File

@ -62,6 +62,7 @@ module result
result_writeDataset, &
result_writeDataset_str, &
result_setLink, &
result_addSetupFile, &
result_addAttribute, &
result_removeLink, &
result_mapping_phase, &
@ -166,7 +167,7 @@ end subroutine result_finalizeIncrement
!--------------------------------------------------------------------------------------------------
!> @brief open a group from the result file
!> @brief Open a group from the result file.
!--------------------------------------------------------------------------------------------------
integer(HID_T) function result_openGroup(groupName)
@ -179,7 +180,7 @@ end function result_openGroup
!--------------------------------------------------------------------------------------------------
!> @brief adds a new group to the result file
!> @brief Add a new group to the result file.
!--------------------------------------------------------------------------------------------------
integer(HID_T) function result_addGroup(groupName)
@ -192,7 +193,7 @@ end function result_addGroup
!--------------------------------------------------------------------------------------------------
!> @brief close a group
!> @brief Close a group.
!--------------------------------------------------------------------------------------------------
subroutine result_closeGroup(group_id)
@ -205,7 +206,7 @@ end subroutine result_closeGroup
!--------------------------------------------------------------------------------------------------
!> @brief set link to object in result file
!> @brief Set link to object in result file.
!--------------------------------------------------------------------------------------------------
subroutine result_setLink(path,link)
@ -216,6 +217,33 @@ subroutine result_setLink(path,link)
end subroutine result_setLink
!--------------------------------------------------------------------------------------------------
!> @brief Add file to setup folder and ensure unique name.
!--------------------------------------------------------------------------------------------------
subroutine result_addSetupFile(content,fname,description)
character(len=*), intent(in) :: content, fname, description
integer(HID_T) :: groupHandle
character(len=:), allocatable :: name,suffix
integer :: i
groupHandle = result_openGroup('setup')
name = fname(scan(fname,'/',.true.)+1:)
suffix = ''
i = 0
do while (HDF5_objectExists(groupHandle,name//suffix))
i = i+1
suffix = '.'//IO_intAsStr(i)
end do
call result_writeDataset_str(content,'setup',name//suffix,description)
call result_closeGroup(groupHandle)
end subroutine result_addSetupFile
!--------------------------------------------------------------------------------------------------
!> @brief Add a string attribute to an object in the result file.
!--------------------------------------------------------------------------------------------------