Skip to content

Commit 9e26b2d

Browse files
authored
Merge pull request #522 from urbanjost/unused
remove warnings and fix truncated help text
2 parents 1715c04 + 83f1fc0 commit 9e26b2d

20 files changed

+60
-83
lines changed

app/main.f90

Lines changed: 0 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -89,8 +89,6 @@ function has_manifest(dir)
8989
character(len=*), intent(in) :: dir
9090
logical :: has_manifest
9191

92-
character(len=:), allocatable :: manifest
93-
9492
has_manifest = exists(join_path(dir, "fpm.toml"))
9593
end function has_manifest
9694

src/fpm/cmd/install.f90

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -27,7 +27,7 @@ subroutine cmd_install(settings)
2727
type(fpm_model_t) :: model
2828
type(build_target_ptr), allocatable :: targets(:)
2929
type(installer_t) :: installer
30-
character(len=:), allocatable :: lib, exe, dir
30+
character(len=:), allocatable :: lib, dir
3131
logical :: installable
3232

3333
call get_package_data(package, "fpm.toml", error, apply_defaults=.true.)

src/fpm/dependency.f90

Lines changed: 1 addition & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -233,7 +233,6 @@ subroutine add_project(self, package, error)
233233

234234
type(dependency_config_t) :: dependency
235235
character(len=:), allocatable :: root
236-
logical :: main
237236

238237
if (allocated(self%cache)) then
239238
call self%load(self%cache, error)
@@ -386,8 +385,7 @@ subroutine update_dependency(self, name, error)
386385
type(error_t), allocatable, intent(out) :: error
387386

388387
integer :: id
389-
type(package_config_t) :: package
390-
character(len=:), allocatable :: manifest, proj_dir, revision, root
388+
character(len=:), allocatable :: proj_dir, root
391389

392390
id = self%find(name)
393391
root = "."
@@ -507,8 +505,6 @@ pure function find_dependency(self, dependency) result(pos)
507505
!> Index of the dependency
508506
integer :: pos
509507

510-
integer :: ii
511-
512508
pos = self%find(dependency%name)
513509

514510
end function find_dependency
@@ -540,7 +536,6 @@ pure function finished(self)
540536
class(dependency_tree_t), intent(in) :: self
541537
!> All dependencies are updated
542538
logical :: finished
543-
integer :: ii
544539

545540
finished = all(self%dep(:self%ndep)%done)
546541

@@ -561,7 +556,6 @@ subroutine register(self, package, root, fetch, revision, error)
561556
!> Error handling
562557
type(error_t), allocatable, intent(out) :: error
563558

564-
character(len=:), allocatable :: url
565559
logical :: update
566560

567561
update = .false.
@@ -649,7 +643,6 @@ subroutine load_from_toml(self, table, error)
649643
character(len=:), allocatable :: version, url, obj, rev, proj_dir
650644
type(toml_key), allocatable :: list(:)
651645
type(toml_table), pointer :: ptr
652-
type(dependency_config_t) :: dep
653646

654647
call table%get_keys(list)
655648

src/fpm/manifest/executable.f90

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -13,7 +13,7 @@
1313
module fpm_manifest_executable
1414
use fpm_manifest_dependency, only : dependency_config_t, new_dependencies
1515
use fpm_error, only : error_t, syntax_error, bad_name_error
16-
use fpm_strings, only : string_t
16+
use fpm_strings, only : string_t
1717
use fpm_toml, only : toml_table, toml_key, toml_stat, get_value
1818
implicit none
1919
private

src/fpm/manifest/package.f90

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -161,7 +161,7 @@ subroutine new_package(self, table, root, error)
161161
end if
162162
call new_install_config(self%install, child, error)
163163
if (allocated(error)) return
164-
164+
165165
call get_value(table, "version", version, "0")
166166
call new_version(self%version, version, error)
167167
if (allocated(error) .and. present(root)) then

src/fpm/versioning.f90

Lines changed: 2 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -87,8 +87,7 @@ subroutine new_version_from_string(self, string, error)
8787
!> Error handling
8888
type(error_t), allocatable, intent(out) :: error
8989

90-
character :: tok
91-
integer :: ii, istart, iend, stat, nn
90+
integer :: istart, iend, stat, nn
9291
integer :: num(max_limit)
9392
logical :: is_number
9493

@@ -147,7 +146,7 @@ subroutine next(string, istart, iend, is_number, error)
147146

148147
integer :: ii, nn
149148
logical :: was_number
150-
character :: tok, last
149+
character :: tok
151150

152151
was_number = is_number
153152
nn = len(string)

src/fpm_backend.f90

Lines changed: 3 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -83,7 +83,7 @@ subroutine build_package(targets,model)
8383
! Check if build already failed
8484
!$omp atomic read
8585
skip_current = build_failed
86-
86+
8787
if (.not.skip_current) then
8888
call build_target(model,queue(j)%ptr,stat(j))
8989
end if
@@ -126,8 +126,7 @@ end subroutine build_package
126126
recursive subroutine sort_target(target)
127127
type(build_target_t), intent(inout), target :: target
128128

129-
integer :: i, j, fh, stat
130-
type(build_target_t), pointer :: exe_obj
129+
integer :: i, fh, stat
131130

132131
! Check if target has already been processed (as a dependency)
133132
if (target%sorted .or. target%skip) then
@@ -257,8 +256,7 @@ subroutine build_target(model,target,stat)
257256
type(build_target_t), intent(in), target :: target
258257
integer, intent(out) :: stat
259258

260-
integer :: ilib, fh
261-
character(:), allocatable :: link_flags
259+
integer :: fh
262260

263261
if (.not.exists(dirname(target%output_file))) then
264262
call mkdir(dirname(target%output_file))

src/fpm_command_line.f90

Lines changed: 26 additions & 24 deletions
Original file line numberDiff line numberDiff line change
@@ -537,17 +537,18 @@ subroutine set_help()
537537
' ']
538538
help_list_dash = [character(len=80) :: &
539539
' ', &
540-
' build [--compiler COMPILER_NAME] [--profile PROF] [--flag FFLAGS] [--list] ', &
540+
' build [--compiler COMPILER_NAME] [--profile PROF] [--flag FFLAGS] [--list] ', &
541541
' help [NAME(s)] ', &
542542
' new NAME [[--lib|--src] [--app] [--test] [--example]]| ', &
543543
' [--full|--bare][--backfill] ', &
544544
' update [NAME(s)] [--fetch-only] [--clean] [--verbose] ', &
545545
' list [--list] ', &
546-
' run [[--target] NAME(s) [--example] [--profile PROF] [--flag FFLAGS] [--all] ', &
546+
' run [[--target] NAME(s) [--example] [--profile PROF] [--flag FFLAGS] [--all] ', &
547547
' [--runner "CMD"] [--compiler COMPILER_NAME] [--list] [-- ARGS] ', &
548-
' test [[--target] NAME(s)] [--profile PROF] [--flag FFLAGS] [--runner "CMD"] [--list]', &
549-
' [--compiler COMPILER_NAME] [-- ARGS] ', &
550-
' install [--profile PROF] [--flag FFLAGS] [--no-rebuild] [--prefix PATH] [options] ', &
548+
' test [[--target] NAME(s)] [--profile PROF] [--flag FFLAGS] [--runner "CMD"] ', &
549+
' [--list] [--compiler COMPILER_NAME] [-- ARGS] ', &
550+
' install [--profile PROF] [--flag FFLAGS] [--no-rebuild] [--prefix PATH] ', &
551+
' [options] ', &
551552
' ']
552553
help_usage=[character(len=80) :: &
553554
'' ]
@@ -652,20 +653,21 @@ subroutine set_help()
652653
' + install Install project ', &
653654
' ', &
654655
' Their syntax is ', &
655-
' ', &
656-
' build [--profile PROF] [--flag FFLAGS] [--list] [--compiler COMPILER_NAME]', &
657-
' new NAME [[--lib|--src] [--app] [--test] [--example]]| ', &
658-
' [--full|--bare][--backfill] ', &
659-
' update [NAME(s)] [--fetch-only] [--clean] ', &
660-
' run [[--target] NAME(s)] [--profile PROF] [--flag FFLAGS] [--list] [--example]', &
661-
' [--all] [--runner "CMD"] [--compiler COMPILER_NAME] [-- ARGS] ', &
662-
' test [[--target] NAME(s)] [--profile PROF] [--flag FFLAGS] [--list] ', &
663-
' [--runner "CMD"] [--compiler COMPILER_NAME] [-- ARGS] ', &
664-
' help [NAME(s)] ', &
665-
' list [--list] ', &
666-
' install [--profile PROF] [--flag FFLAGS] [--no-rebuild] [--prefix PATH] [options]', &
667-
' ', &
668-
'SUBCOMMAND OPTIONS ', &
656+
' ', &
657+
' build [--profile PROF] [--flag FFLAGS] [--list] [--compiler COMPILER_NAME] ', &
658+
' new NAME [[--lib|--src] [--app] [--test] [--example]]| ', &
659+
' [--full|--bare][--backfill] ', &
660+
' update [NAME(s)] [--fetch-only] [--clean] ', &
661+
' run [[--target] NAME(s)] [--profile PROF] [--flag FFLAGS] [--list] [--all] ', &
662+
' [--example] [--runner "CMD"] [--compiler COMPILER_NAME] [-- ARGS] ', &
663+
' test [[--target] NAME(s)] [--profile PROF] [--flag FFLAGS] [--list] ', &
664+
' [--runner "CMD"] [--compiler COMPILER_NAME] [-- ARGS] ', &
665+
' help [NAME(s)] ', &
666+
' list [--list] ', &
667+
' install [--profile PROF] [--flag FFLAGS] [--no-rebuild] [--prefix PATH] ', &
668+
' [options] ', &
669+
' ', &
670+
'SUBCOMMAND OPTIONS ', &
669671
' -C, --directory PATH', &
670672
' Change working directory to PATH before running any command', &
671673
' --profile PROF selects the compilation profile for the build.',&
@@ -730,11 +732,11 @@ subroutine set_help()
730732
' fpm run ', &
731733
' fpm run --example ', &
732734
' fpm new --help ', &
733-
' fpm run myprogram --profile release -- -x 10 -y 20 --title "my title"', &
734-
' fpm install --prefix ~/.local ', &
735-
' ', &
736-
'SEE ALSO ', &
737-
' ', &
735+
' fpm run myprogram --profile release -- -x 10 -y 20 --title "my title" ', &
736+
' fpm install --prefix ~/.local ', &
737+
' ', &
738+
'SEE ALSO ', &
739+
' ', &
738740
' + The fpm(1) home page is at https://github.com/fortran-lang/fpm ', &
739741
' + Registered fpm(1) packages are at https://fortran-lang.org/packages ', &
740742
' + The fpm(1) TOML file format is described at ', &

src/fpm_filesystem.f90

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -45,7 +45,7 @@ end subroutine env_variable
4545

4646
!> Extract filename from path with/without suffix
4747
function basename(path,suffix) result (base)
48-
48+
4949
character(*), intent(In) :: path
5050
logical, intent(in), optional :: suffix
5151
character(:), allocatable :: base
@@ -90,7 +90,7 @@ function canon_path(path)
9090
character(len=:), allocatable :: canon_path
9191
character(len=:), allocatable :: nixpath
9292

93-
integer :: ii, istart, iend, stat, nn, last
93+
integer :: istart, iend, nn, last
9494
logical :: is_path, absolute
9595

9696
nixpath = unix_path(path)
@@ -141,7 +141,7 @@ subroutine next(string, istart, iend, is_path)
141141
logical, intent(inout) :: is_path
142142

143143
integer :: ii, nn
144-
character :: tok, last
144+
character :: tok
145145

146146
nn = len(string)
147147

src/fpm_model.f90

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -251,7 +251,6 @@ function info_srcfile_short(source) result(s)
251251
! Prints a shortened version of srcfile_t
252252
type(srcfile_t), intent(in) :: source
253253
character(:), allocatable :: s
254-
integer :: i
255254
s = "srcfile_t("
256255
s = s // 'file_name="' // source%file_name // '"'
257256
s = s // ", ...)"

0 commit comments

Comments
 (0)