Skip to content

Commit f65d65b

Browse files
authored
Fortran standard compliance fixes (#1013)
2 parents 7d08e7f + d5f9b46 commit f65d65b

File tree

4 files changed

+7
-25
lines changed

4 files changed

+7
-25
lines changed

src/fpm/dependency.f90

+1-2
Original file line numberDiff line numberDiff line change
@@ -60,8 +60,7 @@ module fpm_dependency
6060
use fpm_error, only: error_t, fatal_error
6161
use fpm_filesystem, only: exists, join_path, mkdir, canon_path, windows_path, list_files, is_dir, basename, &
6262
os_delete_dir, get_temp_filename
63-
use fpm_git, only: git_target_revision, git_target_default, git_revision, operator(==), &
64-
serializable_t
63+
use fpm_git, only: git_target_revision, git_target_default, git_revision, serializable_t
6564
use fpm_manifest, only: package_config_t, dependency_config_t, get_package_data
6665
use fpm_manifest_dependency, only: manifest_has_changed, dependency_destroy
6766
use fpm_manifest_preprocess, only: operator(==)

src/fpm/git.f90

-17
Original file line numberDiff line numberDiff line change
@@ -62,11 +62,6 @@ module fpm_git
6262

6363
end type git_target_t
6464

65-
66-
interface operator(==)
67-
module procedure git_target_eq
68-
end interface
69-
7065
!> Common output format for writing to the command line
7166
character(len=*), parameter :: out_fmt = '("#", *(1x, g0))'
7267

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

145140
end function git_target_tag
146141

147-
!> Check that two git targets are equal
148-
logical function git_target_eq(this,that) result(is_equal)
149-
150-
!> Two input git targets
151-
type(git_target_t), intent(in) :: this,that
152-
153-
is_equal = this%descriptor == that%descriptor .and. &
154-
this%url == that%url .and. &
155-
this%object == that%object
156-
157-
end function git_target_eq
158-
159142
!> Check that two git targets are equal
160143
logical function git_is_same(this,that)
161144
class(git_target_t), intent(in) :: this

src/fpm/manifest/dependency.f90

+1-1
Original file line numberDiff line numberDiff line change
@@ -25,7 +25,7 @@
2525
module fpm_manifest_dependency
2626
use fpm_error, only: error_t, syntax_error, fatal_error
2727
use fpm_git, only: git_target_t, git_target_tag, git_target_branch, &
28-
& git_target_revision, git_target_default, operator(==), git_matches_manifest
28+
& git_target_revision, git_target_default, git_matches_manifest
2929
use fpm_toml, only: toml_table, toml_key, toml_stat, get_value, check_keys, serializable_t, add_table, &
3030
& set_value, set_string
3131
use fpm_filesystem, only: windows_path, join_path

src/fpm/toml.f90

+5-5
Original file line numberDiff line numberDiff line change
@@ -36,19 +36,19 @@ module fpm_toml
3636
contains
3737

3838
!> Dump to TOML table, unit, file
39-
procedure(to_toml), deferred, private :: dump_to_toml
39+
procedure(to_toml), deferred :: dump_to_toml
4040
procedure, non_overridable, private :: dump_to_file
4141
procedure, non_overridable, private :: dump_to_unit
4242
generic :: dump => dump_to_toml, dump_to_file, dump_to_unit
4343

4444
!> Load from TOML table, unit, file
45-
procedure(from_toml), deferred, private :: load_from_toml
45+
procedure(from_toml), deferred :: load_from_toml
4646
procedure, non_overridable, private :: load_from_file
4747
procedure, non_overridable, private :: load_from_unit
4848
generic :: load => load_from_toml, load_from_file, load_from_unit
4949

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

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

456456
!> The character variable
457-
character(len=:), allocatable, intent(in) :: var
457+
character(len=*), optional, intent(in) :: var
458458

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

474-
if (allocated(var)) then
474+
if (present(var)) then
475475
call set_value(table, key, var, ierr)
476476
if (ierr/=toml_stat%success) then
477477
call fatal_error(error,'cannot set character key <'//key//'> in TOML table')

0 commit comments

Comments
 (0)