Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
6 changes: 3 additions & 3 deletions src/fpm/manifest/build.f90
Original file line number Diff line number Diff line change
Expand Up @@ -12,7 +12,7 @@
module fpm_manifest_build
use fpm_error, only : error_t, syntax_error, fatal_error
use fpm_strings, only : string_t
use fpm_toml, only : toml_table, toml_key, toml_stat, get_value
use fpm_toml, only : toml_table, toml_key, toml_stat, get_value, get_list
implicit none
private

Expand Down Expand Up @@ -87,10 +87,10 @@ subroutine new_build_config(self, table, error)
end if


call get_value(table, "link", self%link, error)
call get_list(table, "link", self%link, error)
if (allocated(error)) return

call get_value(table, "external-modules", self%external_modules, error)
call get_list(table, "external-modules", self%external_modules, error)
if (allocated(error)) return

end subroutine new_build_config
Expand Down
4 changes: 2 additions & 2 deletions src/fpm/manifest/example.f90
Original file line number Diff line number Diff line change
Expand Up @@ -18,7 +18,7 @@ module fpm_manifest_example
use fpm_manifest_dependency, only : dependency_config_t, new_dependencies
use fpm_manifest_executable, only : executable_config_t
use fpm_error, only : error_t, syntax_error, bad_name_error
use fpm_toml, only : toml_table, toml_key, toml_stat, get_value
use fpm_toml, only : toml_table, toml_key, toml_stat, get_value, get_list
implicit none
private

Expand Down Expand Up @@ -73,7 +73,7 @@ subroutine new_example(self, table, error)
if (allocated(error)) return
end if

call get_value(table, "link", self%link, error)
call get_list(table, "link", self%link, error)
if (allocated(error)) return

end subroutine new_example
Expand Down
4 changes: 2 additions & 2 deletions src/fpm/manifest/executable.f90
Original file line number Diff line number Diff line change
Expand Up @@ -14,7 +14,7 @@ module fpm_manifest_executable
use fpm_manifest_dependency, only : dependency_config_t, new_dependencies
use fpm_error, only : error_t, syntax_error, bad_name_error
use fpm_strings, only : string_t
use fpm_toml, only : toml_table, toml_key, toml_stat, get_value
use fpm_toml, only : toml_table, toml_key, toml_stat, get_value, get_list
implicit none
private

Expand Down Expand Up @@ -84,7 +84,7 @@ subroutine new_executable(self, table, error)
if (allocated(error)) return
end if

call get_value(table, "link", self%link, error)
call get_list(table, "link", self%link, error)
if (allocated(error)) return

end subroutine new_executable
Expand Down
4 changes: 2 additions & 2 deletions src/fpm/manifest/library.f90
Original file line number Diff line number Diff line change
Expand Up @@ -11,7 +11,7 @@
module fpm_manifest_library
use fpm_error, only : error_t, syntax_error
use fpm_strings, only: string_t, string_cat
use fpm_toml, only : toml_table, toml_key, toml_stat, get_value
use fpm_toml, only : toml_table, toml_key, toml_stat, get_value, get_list
implicit none
private

Expand Down Expand Up @@ -59,7 +59,7 @@ subroutine new_library(self, table, error)
call get_value(table, "source-dir", self%source_dir, "src")
call get_value(table, "build-script", self%build_script)

call get_value(table, "include-dir", self%include_dir, error)
call get_list(table, "include-dir", self%include_dir, error)
if (allocated(error)) return

! Set default value of include-dir if not found in manifest
Expand Down
4 changes: 2 additions & 2 deletions src/fpm/manifest/test.f90
Original file line number Diff line number Diff line change
Expand Up @@ -18,7 +18,7 @@ module fpm_manifest_test
use fpm_manifest_dependency, only : dependency_config_t, new_dependencies
use fpm_manifest_executable, only : executable_config_t
use fpm_error, only : error_t, syntax_error, bad_name_error
use fpm_toml, only : toml_table, toml_key, toml_stat, get_value
use fpm_toml, only : toml_table, toml_key, toml_stat, get_value, get_list
implicit none
private

Expand Down Expand Up @@ -73,7 +73,7 @@ subroutine new_test(self, table, error)
if (allocated(error)) return
end if

call get_value(table, "link", self%link, error)
call get_list(table, "link", self%link, error)
if (allocated(error)) return

end subroutine new_test
Expand Down
11 changes: 3 additions & 8 deletions src/fpm/toml.f90
Original file line number Diff line number Diff line change
Expand Up @@ -22,16 +22,11 @@ module fpm_toml
private

public :: read_package_file
public :: toml_table, toml_array, toml_key, toml_stat, get_value, set_value
public :: toml_table, toml_array, toml_key, toml_stat, get_value, set_value, get_list
public :: new_table, add_table, add_array, len
public :: toml_error, toml_serializer, toml_parse


interface get_value
module procedure :: get_child_value_string_list
end interface get_value


contains


Expand Down Expand Up @@ -71,7 +66,7 @@ subroutine read_package_file(table, manifest, error)
end subroutine read_package_file


subroutine get_child_value_string_list(table, key, list, error)
subroutine get_list(table, key, list, error)

!> Instance of the TOML data structure
type(toml_table), intent(inout) :: table
Expand Down Expand Up @@ -114,7 +109,7 @@ subroutine get_child_value_string_list(table, key, list, error)
end if
end if

end subroutine get_child_value_string_list
end subroutine get_list


end module fpm_toml