Skip to content

Commit

Permalink
Fortran standard compliance fixes (#1013)
Browse files Browse the repository at this point in the history
  • Loading branch information
perazz authored Mar 26, 2024
2 parents 7d08e7f + d5f9b46 commit f65d65b
Show file tree
Hide file tree
Showing 4 changed files with 7 additions and 25 deletions.
3 changes: 1 addition & 2 deletions src/fpm/dependency.f90
Original file line number Diff line number Diff line change
Expand Up @@ -60,8 +60,7 @@ module fpm_dependency
use fpm_error, only: error_t, fatal_error
use fpm_filesystem, only: exists, join_path, mkdir, canon_path, windows_path, list_files, is_dir, basename, &
os_delete_dir, get_temp_filename
use fpm_git, only: git_target_revision, git_target_default, git_revision, operator(==), &
serializable_t
use fpm_git, only: git_target_revision, git_target_default, git_revision, serializable_t
use fpm_manifest, only: package_config_t, dependency_config_t, get_package_data
use fpm_manifest_dependency, only: manifest_has_changed, dependency_destroy
use fpm_manifest_preprocess, only: operator(==)
Expand Down
17 changes: 0 additions & 17 deletions src/fpm/git.f90
Original file line number Diff line number Diff line change
Expand Up @@ -62,11 +62,6 @@ module fpm_git

end type git_target_t


interface operator(==)
module procedure git_target_eq
end interface

!> Common output format for writing to the command line
character(len=*), parameter :: out_fmt = '("#", *(1x, g0))'

Expand Down Expand Up @@ -144,18 +139,6 @@ function git_target_tag(url, tag) result(self)

end function git_target_tag

!> Check that two git targets are equal
logical function git_target_eq(this,that) result(is_equal)

!> Two input git targets
type(git_target_t), intent(in) :: this,that

is_equal = this%descriptor == that%descriptor .and. &
this%url == that%url .and. &
this%object == that%object

end function git_target_eq

!> Check that two git targets are equal
logical function git_is_same(this,that)
class(git_target_t), intent(in) :: this
Expand Down
2 changes: 1 addition & 1 deletion src/fpm/manifest/dependency.f90
Original file line number Diff line number Diff line change
Expand Up @@ -25,7 +25,7 @@
module fpm_manifest_dependency
use fpm_error, only: error_t, syntax_error, fatal_error
use fpm_git, only: git_target_t, git_target_tag, git_target_branch, &
& git_target_revision, git_target_default, operator(==), git_matches_manifest
& git_target_revision, git_target_default, git_matches_manifest
use fpm_toml, only: toml_table, toml_key, toml_stat, get_value, check_keys, serializable_t, add_table, &
& set_value, set_string
use fpm_filesystem, only: windows_path, join_path
Expand Down
10 changes: 5 additions & 5 deletions src/fpm/toml.f90
Original file line number Diff line number Diff line change
Expand Up @@ -36,19 +36,19 @@ module fpm_toml
contains

!> Dump to TOML table, unit, file
procedure(to_toml), deferred, private :: dump_to_toml
procedure(to_toml), deferred :: dump_to_toml
procedure, non_overridable, private :: dump_to_file
procedure, non_overridable, private :: dump_to_unit
generic :: dump => dump_to_toml, dump_to_file, dump_to_unit

!> Load from TOML table, unit, file
procedure(from_toml), deferred, private :: load_from_toml
procedure(from_toml), deferred :: load_from_toml
procedure, non_overridable, private :: load_from_file
procedure, non_overridable, private :: load_from_unit
generic :: load => load_from_toml, load_from_file, load_from_unit

!> Serializable entities need a way to check that they're equal
procedure(is_equal), deferred, private :: serializable_is_same
procedure(is_equal), deferred :: serializable_is_same
generic :: operator(==) => serializable_is_same

!> Test load/write roundtrip
Expand Down Expand Up @@ -454,7 +454,7 @@ subroutine set_character(table, key, var, error, whereAt)
character(len=*), intent(in) :: key

!> The character variable
character(len=:), allocatable, intent(in) :: var
character(len=*), optional, intent(in) :: var

!> Error handling
type(error_t), allocatable, intent(out) :: error
Expand All @@ -471,7 +471,7 @@ subroutine set_character(table, key, var, error, whereAt)
return
end if

if (allocated(var)) then
if (present(var)) then
call set_value(table, key, var, ierr)
if (ierr/=toml_stat%success) then
call fatal_error(error,'cannot set character key <'//key//'> in TOML table')
Expand Down

0 comments on commit f65d65b

Please sign in to comment.