gray/src/ini_parser.f90
Michele Guerini Rocco 72eb224568
remove unnecessary deallocations
1. Local variables are automatically deallocated when they go out of
   scope.

2. When calling exit() during CLI processing some stuff wasn't being
   deallocated, but it doesnt matter because the OS does it anyway.
   So, get rid of it entirely.
2024-11-04 12:05:50 +01:00

182 lines
5.0 KiB
Fortran

! This module provides a minimal INI parser
!
! The format is:
!
! ; comment
! [section-name]
! property-name = property-value ; comment
!
! The `parse_ini` subroutine takes a file and a handler
! function that is called with the section, name and value
! of each property in the INI file.
!
module ini_parser
use logger, only : log_error
implicit none
! INI syntax constants
character, parameter :: comment_sign = ';'
character, parameter :: property_sep = '='
character, parameter :: section_start = '['
character, parameter :: section_stop = ']'
! Errors
enum, bind(C)
enumerator :: ini_error = -1
enumerator :: ERR_SUCCESS = 0 ! no errors
enumerator :: ERR_SYNTAX = 1 ! syntax error in the INI file
enumerator :: ERR_VALUE = 2 ! invalid value for a property
enumerator :: ERR_UNKNOWN = 3 ! unknown property name
enumerator :: ERR_IO = 4 ! I/O error
end enum
abstract interface
function property_handler(section, name, value) result(error)
character(*), intent(in) :: section, name, value
integer(kind(ini_error)) :: error
end function
end interface
private
public parse_ini
public property_handler
public ini_error, ERR_SUCCESS, ERR_SYNTAX, ERR_VALUE, ERR_UNKNOWN, ERR_IO
contains
subroutine parse_ini(filepath, handler, error)
! Parses a INI file
! filepath: path of the INI file to pase
! handler: handler function
!
! The handler must have the following signature:
!
! function handler(section, name, value) result(error)
!
! where the error should be:
! ERR_SUCCESS on success;
! ERR_VALUE on invalid values for this property;
! ERR_UNKNOWN on unknown property.
!
! function argument
character(*), intent(in) :: filepath
procedure(property_handler) :: handler
integer(kind(ini_error)), intent(out) :: error
! local variables
integer :: ini, sep, n
character(256) :: msg
character(len=:), allocatable :: line
character(len=:), allocatable :: section, name, value
! open the INI file
open(newunit=ini, file=filepath, action='read', iostat=error)
if (error /= 0) then
write (msg, '("failed to open INI file: ", a)') filepath
call log_error(msg, proc='parse_ini', mod='ini_parser')
error = ERR_IO
return
end if
n = 1 ! line number
do
! get one line
call getline(ini, line, error)
if (error /= 0) exit
! skip empty lines
if (len(line) == 0) cycle
! skip comments
if (line(1:1) == comment_sign) cycle
! parse section header
if (line(1:1) == section_start) then
! split at section stop (ex. [section<here>])
sep = index(line, section_stop)
if (sep == 0) then
write (msg, '("invalid section header at line ",g0,": ",a)') n, line
call log_error(msg, proc='parse_ini', mod='ini_parser')
error = ERR_SYNTAX
exit
end if
! update the current section
section = line(2:sep - 1)
cycle
end if
! remove possible inline comments
sep = index(line, comment_sign, back=.true.)
if (sep /= 0) line = line(1:sep-1)
! split line at separator (ex. name<here>=value)
sep = index(line, property_sep)
if (sep == 0) then
write (msg, '("invalid property definition at line ",g0,": ",a)') n, line
call log_error(msg, proc='parse_ini', mod='ini_parser')
error = ERR_SYNTAX
exit
end if
name = line(1:sep - 1)
value = line(sep + 1:)
! remove leading/trailing whitespace
name = trim(adjustl(name))
value = trim(adjustl(value))
! call the handler
select case (handler(section, name, value))
case (ERR_SUCCESS)
cycle
case (ERR_VALUE)
write (msg, '("invalid value for property `",a,"`: ", a)') name, value
call log_error(msg, proc='parse_ini', mod='ini_parser')
error = ERR_VALUE
exit
case (ERR_UNKNOWN)
write (msg, '("unknown property ",a)') name
call log_error(msg, proc='parse_ini', mod='ini_parser')
error = ERR_UNKNOWN
exit
end select
end do
! parsed the whole file
if (error < 0) error = ERR_SUCCESS
close(ini)
end subroutine parse_ini
subroutine getline(unit, line, error)
! Reads a line into a deferred length string
! subroutine arguments
integer, intent(in) :: unit
character(len=:), allocatable, intent(out) :: line
integer, intent(out) :: error
integer, parameter :: bufsize = 512
character(len=bufsize) :: buffer
integer :: chunk
allocate(character(len=0) :: line)
do
read(unit, '(a)', advance='no', iostat=error, size=chunk) buffer
if (error > 0) exit
line = line // buffer(:chunk)
if (error < 0) then
if (is_iostat_eor(error)) error = 0
exit
end if
end do
end subroutine getline
end module ini_parser