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
2 changes: 0 additions & 2 deletions app/main.f90
Original file line number Diff line number Diff line change
Expand Up @@ -89,8 +89,6 @@ function has_manifest(dir)
character(len=*), intent(in) :: dir
logical :: has_manifest

character(len=:), allocatable :: manifest

has_manifest = exists(join_path(dir, "fpm.toml"))
end function has_manifest

Expand Down
2 changes: 1 addition & 1 deletion src/fpm/cmd/install.f90
Original file line number Diff line number Diff line change
Expand Up @@ -27,7 +27,7 @@ subroutine cmd_install(settings)
type(fpm_model_t) :: model
type(build_target_ptr), allocatable :: targets(:)
type(installer_t) :: installer
character(len=:), allocatable :: lib, exe, dir
character(len=:), allocatable :: lib, dir
logical :: installable

call get_package_data(package, "fpm.toml", error, apply_defaults=.true.)
Expand Down
9 changes: 1 addition & 8 deletions src/fpm/dependency.f90
Original file line number Diff line number Diff line change
Expand Up @@ -233,7 +233,6 @@ subroutine add_project(self, package, error)

type(dependency_config_t) :: dependency
character(len=:), allocatable :: root
logical :: main

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

integer :: id
type(package_config_t) :: package
character(len=:), allocatable :: manifest, proj_dir, revision, root
character(len=:), allocatable :: proj_dir, root

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

integer :: ii

pos = self%find(dependency%name)

end function find_dependency
Expand Down Expand Up @@ -540,7 +536,6 @@ pure function finished(self)
class(dependency_tree_t), intent(in) :: self
!> All dependencies are updated
logical :: finished
integer :: ii

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

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

character(len=:), allocatable :: url
logical :: update

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

call table%get_keys(list)

Expand Down
2 changes: 1 addition & 1 deletion src/fpm/manifest/executable.f90
Original file line number Diff line number Diff line change
Expand Up @@ -13,7 +13,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_strings, only : string_t
use fpm_toml, only : toml_table, toml_key, toml_stat, get_value
implicit none
private
Expand Down
2 changes: 1 addition & 1 deletion src/fpm/manifest/package.f90
Original file line number Diff line number Diff line change
Expand Up @@ -161,7 +161,7 @@ subroutine new_package(self, table, root, error)
end if
call new_install_config(self%install, child, error)
if (allocated(error)) return

call get_value(table, "version", version, "0")
call new_version(self%version, version, error)
if (allocated(error) .and. present(root)) then
Expand Down
5 changes: 2 additions & 3 deletions src/fpm/versioning.f90
Original file line number Diff line number Diff line change
Expand Up @@ -87,8 +87,7 @@ subroutine new_version_from_string(self, string, error)
!> Error handling
type(error_t), allocatable, intent(out) :: error

character :: tok
integer :: ii, istart, iend, stat, nn
integer :: istart, iend, stat, nn
integer :: num(max_limit)
logical :: is_number

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

integer :: ii, nn
logical :: was_number
character :: tok, last
character :: tok

was_number = is_number
nn = len(string)
Expand Down
8 changes: 3 additions & 5 deletions src/fpm_backend.f90
Original file line number Diff line number Diff line change
Expand Up @@ -83,7 +83,7 @@ subroutine build_package(targets,model)
! Check if build already failed
!$omp atomic read
skip_current = build_failed

if (.not.skip_current) then
call build_target(model,queue(j)%ptr,stat(j))
end if
Expand Down Expand Up @@ -126,8 +126,7 @@ end subroutine build_package
recursive subroutine sort_target(target)
type(build_target_t), intent(inout), target :: target

integer :: i, j, fh, stat
type(build_target_t), pointer :: exe_obj
integer :: i, fh, stat

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

integer :: ilib, fh
character(:), allocatable :: link_flags
integer :: fh

if (.not.exists(dirname(target%output_file))) then
call mkdir(dirname(target%output_file))
Expand Down
50 changes: 26 additions & 24 deletions src/fpm_command_line.f90
Original file line number Diff line number Diff line change
Expand Up @@ -537,17 +537,18 @@ subroutine set_help()
' ']
help_list_dash = [character(len=80) :: &
' ', &
' build [--compiler COMPILER_NAME] [--profile PROF] [--flag FFLAGS] [--list] ', &
' build [--compiler COMPILER_NAME] [--profile PROF] [--flag FFLAGS] [--list] ', &
' help [NAME(s)] ', &
' new NAME [[--lib|--src] [--app] [--test] [--example]]| ', &
' [--full|--bare][--backfill] ', &
' update [NAME(s)] [--fetch-only] [--clean] [--verbose] ', &
' list [--list] ', &
' run [[--target] NAME(s) [--example] [--profile PROF] [--flag FFLAGS] [--all] ', &
' run [[--target] NAME(s) [--example] [--profile PROF] [--flag FFLAGS] [--all] ', &
' [--runner "CMD"] [--compiler COMPILER_NAME] [--list] [-- ARGS] ', &
' test [[--target] NAME(s)] [--profile PROF] [--flag FFLAGS] [--runner "CMD"] [--list]', &
' [--compiler COMPILER_NAME] [-- ARGS] ', &
' install [--profile PROF] [--flag FFLAGS] [--no-rebuild] [--prefix PATH] [options] ', &
' test [[--target] NAME(s)] [--profile PROF] [--flag FFLAGS] [--runner "CMD"] ', &
' [--list] [--compiler COMPILER_NAME] [-- ARGS] ', &
' install [--profile PROF] [--flag FFLAGS] [--no-rebuild] [--prefix PATH] ', &
' [options] ', &
' ']
help_usage=[character(len=80) :: &
'' ]
Expand Down Expand Up @@ -652,20 +653,21 @@ subroutine set_help()
' + install Install project ', &
' ', &
' Their syntax is ', &
' ', &
' build [--profile PROF] [--flag FFLAGS] [--list] [--compiler COMPILER_NAME]', &
' new NAME [[--lib|--src] [--app] [--test] [--example]]| ', &
' [--full|--bare][--backfill] ', &
' update [NAME(s)] [--fetch-only] [--clean] ', &
' run [[--target] NAME(s)] [--profile PROF] [--flag FFLAGS] [--list] [--example]', &
' [--all] [--runner "CMD"] [--compiler COMPILER_NAME] [-- ARGS] ', &
' test [[--target] NAME(s)] [--profile PROF] [--flag FFLAGS] [--list] ', &
' [--runner "CMD"] [--compiler COMPILER_NAME] [-- ARGS] ', &
' help [NAME(s)] ', &
' list [--list] ', &
' install [--profile PROF] [--flag FFLAGS] [--no-rebuild] [--prefix PATH] [options]', &
' ', &
'SUBCOMMAND OPTIONS ', &
' ', &
' build [--profile PROF] [--flag FFLAGS] [--list] [--compiler COMPILER_NAME] ', &
' new NAME [[--lib|--src] [--app] [--test] [--example]]| ', &
' [--full|--bare][--backfill] ', &
' update [NAME(s)] [--fetch-only] [--clean] ', &
' run [[--target] NAME(s)] [--profile PROF] [--flag FFLAGS] [--list] [--all] ', &
' [--example] [--runner "CMD"] [--compiler COMPILER_NAME] [-- ARGS] ', &
' test [[--target] NAME(s)] [--profile PROF] [--flag FFLAGS] [--list] ', &
' [--runner "CMD"] [--compiler COMPILER_NAME] [-- ARGS] ', &
' help [NAME(s)] ', &
' list [--list] ', &
' install [--profile PROF] [--flag FFLAGS] [--no-rebuild] [--prefix PATH] ', &
' [options] ', &
' ', &
'SUBCOMMAND OPTIONS ', &
' -C, --directory PATH', &
' Change working directory to PATH before running any command', &
' --profile PROF selects the compilation profile for the build.',&
Expand Down Expand Up @@ -730,11 +732,11 @@ subroutine set_help()
' fpm run ', &
' fpm run --example ', &
' fpm new --help ', &
' fpm run myprogram --profile release -- -x 10 -y 20 --title "my title"', &
' fpm install --prefix ~/.local ', &
' ', &
'SEE ALSO ', &
' ', &
' fpm run myprogram --profile release -- -x 10 -y 20 --title "my title" ', &
' fpm install --prefix ~/.local ', &
' ', &
'SEE ALSO ', &
' ', &
' + The fpm(1) home page is at https://github.com/fortran-lang/fpm ', &
' + Registered fpm(1) packages are at https://fortran-lang.org/packages ', &
' + The fpm(1) TOML file format is described at ', &
Expand Down
6 changes: 3 additions & 3 deletions src/fpm_filesystem.f90
Original file line number Diff line number Diff line change
Expand Up @@ -45,7 +45,7 @@ end subroutine env_variable

!> Extract filename from path with/without suffix
function basename(path,suffix) result (base)

character(*), intent(In) :: path
logical, intent(in), optional :: suffix
character(:), allocatable :: base
Expand Down Expand Up @@ -90,7 +90,7 @@ function canon_path(path)
character(len=:), allocatable :: canon_path
character(len=:), allocatable :: nixpath

integer :: ii, istart, iend, stat, nn, last
integer :: istart, iend, nn, last
logical :: is_path, absolute

nixpath = unix_path(path)
Expand Down Expand Up @@ -141,7 +141,7 @@ subroutine next(string, istart, iend, is_path)
logical, intent(inout) :: is_path

integer :: ii, nn
character :: tok, last
character :: tok

nn = len(string)

Expand Down
1 change: 0 additions & 1 deletion src/fpm_model.f90
Original file line number Diff line number Diff line change
Expand Up @@ -251,7 +251,6 @@ function info_srcfile_short(source) result(s)
! Prints a shortened version of srcfile_t
type(srcfile_t), intent(in) :: source
character(:), allocatable :: s
integer :: i
s = "srcfile_t("
s = s // 'file_name="' // source%file_name // '"'
s = s // ", ...)"
Expand Down
4 changes: 2 additions & 2 deletions src/fpm_strings.f90
Original file line number Diff line number Diff line change
Expand Up @@ -6,15 +6,15 @@
!!### Types
!! - **TYPE(STRING_T)** define a type to contain strings of variable length
!!### Type Conversions
!! - [[F_STRING]] return Fortran **CHARACTER** variable when given a C-like array of
!! - [[F_STRING]] return Fortran **CHARACTER** variable when given a C-like array of
!! single characters terminated with a C_NULL_CHAR **CHARACTER**
!! - [[STR]] Converts **INTEGER** or** LOGICAL** to **CHARACTER** string
!!### Case
!! - [[LOWER]] Changes a string to lowercase over optional specified column range
!!### Parsing and joining
!! - [[SPLIT]] parse string on delimiter characters and store tokens into an allocatable array
!! - [[STRING_CAT]] Concatenate an array of **type(string_t)** into a single **CHARACTER** variable
!! - [[JOIN]] append an array of **CHARACTER** variables into a single **CHARACTER** variable
!! - [[JOIN]] append an array of **CHARACTER** variables into a single **CHARACTER** variable
!!### Testing
!! - [[STR_ENDS_WITH]] test if a **CHARACTER** string or array ends with a specified suffix
!! - [[STRING_ARRAY_CONTAINS]] Check if array of **TYPE(STRING_T)** matches a particular **CHARACTER** string
Expand Down
3 changes: 0 additions & 3 deletions src/fpm_targets.f90
Original file line number Diff line number Diff line change
Expand Up @@ -160,7 +160,6 @@ subroutine build_target_list(targets,model)

integer :: i, j, n_source
character(:), allocatable :: xsuffix, exe_dir
type(build_target_t), pointer :: dep
logical :: with_lib

! Check for empty build (e.g. header-only lib)
Expand Down Expand Up @@ -258,7 +257,6 @@ function get_object_name(source) result(object_file)

integer :: i
character(1), parameter :: filesep = '/'
character(:), allocatable :: dir

object_file = canon_path(source%file_name)

Expand All @@ -285,7 +283,6 @@ subroutine add_target(targets,type,output_file,source,link_libraries)
type(string_t), intent(in), optional :: link_libraries(:)

integer :: i
type(build_target_ptr), allocatable :: temp(:)
type(build_target_t), pointer :: new_target

if (.not.allocated(targets)) allocate(targets(0))
Expand Down
26 changes: 13 additions & 13 deletions test/fpm_test/test_backend.f90
Original file line number Diff line number Diff line change
Expand Up @@ -28,7 +28,7 @@ subroutine collect_backend(testsuite)
& new_unittest("schedule-targets", test_schedule_targets), &
& new_unittest("schedule-targets-empty", test_schedule_empty) &
]

end subroutine collect_backend


Expand All @@ -39,7 +39,7 @@ subroutine test_target_sort(error)
type(error_t), allocatable, intent(out) :: error

type(build_target_ptr), allocatable :: targets(:)

integer :: i

targets = new_test_package()
Expand Down Expand Up @@ -98,15 +98,15 @@ end subroutine test_target_sort



!> Check incremental rebuild for existing archive
!> Check incremental rebuild for existing archive
!> all object sources are unmodified: all objects should be skipped
subroutine test_target_sort_skip_all(error)

!> Error handling
type(error_t), allocatable, intent(out) :: error

type(build_target_ptr), allocatable :: targets(:)

integer :: fh, i

targets = new_test_package()
Expand Down Expand Up @@ -162,7 +162,7 @@ subroutine test_target_sort_rebuild_all(error)
type(error_t), allocatable, intent(out) :: error

type(build_target_ptr), allocatable :: targets(:)

integer :: fh, i

targets = new_test_package()
Expand Down Expand Up @@ -212,7 +212,7 @@ subroutine test_schedule_targets(error)
type(error_t), allocatable, intent(out) :: error

type(build_target_ptr), allocatable :: targets(:)

integer :: i, j
type(build_target_ptr), allocatable :: queue(:)
integer, allocatable :: schedule_ptr(:)
Expand Down Expand Up @@ -259,16 +259,16 @@ subroutine test_schedule_targets(error)
do i=1,size(schedule_ptr)-1

do j=schedule_ptr(i),(schedule_ptr(i+1)-1)

if (queue(j)%ptr%schedule /= i) then

call test_failed(error,"Target scheduled in the wrong region")
return

end if

end do

end do

end subroutine test_schedule_targets
Expand All @@ -282,7 +282,7 @@ subroutine test_schedule_empty(error)
type(error_t), allocatable, intent(out) :: error

type(build_target_ptr), allocatable :: targets(:)

integer :: i
type(build_target_ptr), allocatable :: queue(:)
integer, allocatable :: schedule_ptr(:)
Expand Down Expand Up @@ -310,7 +310,7 @@ subroutine test_schedule_empty(error)

call test_failed(error,"Expecting an empty build queue, but not empty")
return

end if

! Check schedule loop is not entered
Expand All @@ -336,7 +336,7 @@ function new_test_package() result(targets)
call add_target(targets,FPM_TARGET_OBJECT,get_temp_filename())

call add_target(targets,FPM_TARGET_OBJECT,get_temp_filename())

! Library depends on all objects
call add_dependency(targets(1)%ptr,targets(2)%ptr)
call add_dependency(targets(1)%ptr,targets(3)%ptr)
Expand All @@ -350,4 +350,4 @@ function new_test_package() result(targets)
end function new_test_package


end module test_backend
end module test_backend
Loading