Skip to content

Commit

Permalink
ifx issue test: rename toml_table in fpm_settings
Browse files Browse the repository at this point in the history
  • Loading branch information
perazz committed Feb 10, 2024
1 parent 53a4486 commit ecd23ed
Show file tree
Hide file tree
Showing 2 changed files with 4 additions and 4 deletions.
Binary file added src/.fpm_settings.f90.swp
Binary file not shown.
8 changes: 4 additions & 4 deletions src/fpm_settings.f90
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,7 @@ module fpm_settings
use fpm_filesystem, only: exists, join_path, get_local_prefix, is_absolute_path, mkdir
use fpm_environment, only: os_is_unix
use fpm_error, only: error_t, fatal_error
use fpm_toml, only: toml_table, toml_error, toml_stat, get_value, toml_load, check_keys
use fpm_toml, only: ttable=>toml_table, toml_error, toml_stat, get_value, toml_load, check_keys
use fpm_os, only: get_current_directory, change_directory, get_absolute_path, convert_to_absolute_path

implicit none
Expand Down Expand Up @@ -47,11 +47,11 @@ subroutine get_global_settings(global_settings, error)
!> Error reading config file.
type(error_t), allocatable, intent(out) :: error
!> TOML table to be filled with global config settings.
type(toml_table), allocatable :: table
type(ttable), allocatable :: table
!> Error parsing to TOML table.
type(toml_error), allocatable :: parse_error

type(toml_table), pointer :: registry_table
type(ttable), pointer :: registry_table
integer :: stat

! Use custom path to the config file if it was specified.
Expand Down Expand Up @@ -122,7 +122,7 @@ subroutine use_default_registry_settings(global_settings)
!> Read registry settings from the global config file.
subroutine get_registry_settings(table, global_settings, error)
!> The [registry] subtable from the global config file.
type(toml_table), target, intent(inout) :: table
type(ttable), target, intent(inout) :: table
!> The global settings which can be filled with the registry settings.
type(fpm_global_settings), intent(inout) :: global_settings
!> Error handling.
Expand Down

0 comments on commit ecd23ed

Please sign in to comment.