aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--README.md24
-rw-r--r--fpm/fpm.toml2
-rw-r--r--fpm/src/fpm.f9063
-rw-r--r--fpm/src/fpm/cmd/install.f9034
-rw-r--r--fpm/src/fpm_backend.f9038
-rw-r--r--fpm/src/fpm_command_line.f902
-rw-r--r--fpm/src/fpm_compiler.f9027
-rw-r--r--fpm/src/fpm_model.f90181
-rw-r--r--fpm/src/fpm_targets.f90161
-rw-r--r--fpm/test/fpm_test/test_backend.f906
-rw-r--r--fpm/test/fpm_test/test_module_dependencies.f90132
-rw-r--r--fpm/test/help_test/help_test.f90101
-rw-r--r--fpm/test/new_test/new_test.f9034
-rwxr-xr-xinstall.sh118
14 files changed, 474 insertions, 449 deletions
diff --git a/README.md b/README.md
index 00dd73d..be96b4f 100644
--- a/README.md
+++ b/README.md
@@ -72,32 +72,26 @@ $ cd fpm/
#### Build a bootstrap version of fpm
-You can use the install script to perform the build of the Haskell version of *fpm* with:
+You can use the install script to bootstrap and install *fpm*:
```bash
$ ./install.sh
```
-On Linux, the above command installs `fpm` to `${HOME}/.local/bin/`.
-
-Now you can build the Fortran *fpm* version with
+By default, the above command installs `fpm` to `${HOME}/.local/bin/`.
+To specify an alternative destination use the `--prefix=` flag, for example:
```bash
-$ cd fpm/
-$ fpm build
+$ ./install.sh --prefix=/usr/local
```
-Test that everything is working as expected
+which will install *fpm* to `/usr/local/bin`.
-```bash
-$ fpm test
-```
-
-Finally, install the Fortran *fpm* version with
+To test that everything is working as expected you can now build *fpm*
+with itself and run the tests with:
```bash
-$ fpm run --runner mv -- ~/.local/bin
+$ cd fpm
+$ fpm test
```
-Or choose another location if you do not want to overwrite the bootstrapping version.
-From now on you can rebuild *fpm* with your Fortran *fpm* version.
diff --git a/fpm/fpm.toml b/fpm/fpm.toml
index 48f5b00..e28f2bc 100644
--- a/fpm/fpm.toml
+++ b/fpm/fpm.toml
@@ -1,5 +1,5 @@
name = "fpm"
-version = "0.1.3"
+version = "0.1.4"
license = "MIT"
author = "fpm maintainers"
maintainer = ""
diff --git a/fpm/src/fpm.f90 b/fpm/src/fpm.f90
index d3a3b0c..68385cd 100644
--- a/fpm/src/fpm.f90
+++ b/fpm/src/fpm.f90
@@ -6,16 +6,16 @@ use fpm_command_line, only: fpm_build_settings, fpm_new_settings, &
use fpm_dependency, only : new_dependency_tree
use fpm_environment, only: run
use fpm_filesystem, only: is_dir, join_path, number_of_rows, list_files, exists, basename
-use fpm_model, only: fpm_model_t, srcfile_t, build_target_t, &
+use fpm_model, only: fpm_model_t, srcfile_t, show_model, &
FPM_SCOPE_UNKNOWN, FPM_SCOPE_LIB, FPM_SCOPE_DEP, &
- FPM_SCOPE_APP, FPM_SCOPE_EXAMPLE, FPM_SCOPE_TEST, &
- FPM_TARGET_EXECUTABLE, FPM_TARGET_ARCHIVE, show_model
+ FPM_SCOPE_APP, FPM_SCOPE_EXAMPLE, FPM_SCOPE_TEST
use fpm_compiler, only: add_compile_flag_defaults
use fpm_sources, only: add_executable_sources, add_sources_from_dir
use fpm_targets, only: targets_from_sources, resolve_module_dependencies, &
- resolve_target_linking
+ resolve_target_linking, build_target_t, build_target_ptr, &
+ FPM_TARGET_EXECUTABLE, FPM_TARGET_ARCHIVE
use fpm_manifest, only : get_package_data, package_config_t
use fpm_error, only : error_t, fatal_error
use fpm_manifest_test, only : test_config_t
@@ -50,11 +50,7 @@ subroutine build_model(model, settings, package, error)
model%package_name = package%name
- if (allocated(package%build%link)) then
- model%link_libraries = package%build%link
- else
- allocate(model%link_libraries(0))
- end if
+ allocate(model%link_libraries(0))
call new_dependency_tree(model%deps, cache=join_path("build", "cache.toml"))
call model%deps%add(package, error)
@@ -69,8 +65,9 @@ subroutine build_model(model, settings, package, error)
model%output_directory = join_path('build',basename(model%fortran_compiler)//'_'//settings%build_name)
call add_compile_flag_defaults(settings%build_name, basename(model%fortran_compiler), model)
-
- model%link_flags = ''
+ if(settings%verbose)then
+ write(*,*)'<INFO>COMPILER OPTIONS: ', model%fortran_compile_flags
+ endif
allocate(model%packages(model%deps%ndep))
@@ -157,20 +154,6 @@ subroutine build_model(model, settings, package, error)
end do
if (allocated(error)) return
- call targets_from_sources(model)
-
- do i = 1, size(model%link_libraries)
- model%link_flags = model%link_flags // " -l" // model%link_libraries(i)%s
- end do
-
- if (model%targets(1)%ptr%target_type == FPM_TARGET_ARCHIVE) then
- model%library_file = model%targets(1)%ptr%output_file
- end if
-
- call resolve_module_dependencies(model%targets,error)
-
- call resolve_target_linking(model%targets)
-
end subroutine build_model
@@ -178,6 +161,7 @@ subroutine cmd_build(settings)
type(fpm_build_settings), intent(in) :: settings
type(package_config_t) :: package
type(fpm_model_t) :: model
+type(build_target_ptr), allocatable :: targets(:)
type(error_t), allocatable :: error
integer :: i
@@ -194,14 +178,20 @@ if (allocated(error)) then
error stop 1
end if
+call targets_from_sources(targets,model,error)
+if (allocated(error)) then
+ print '(a)', error%message
+ error stop 1
+end if
+
if(settings%list)then
- do i=1,size(model%targets)
- write(stderr,*) model%targets(i)%ptr%output_file
+ do i=1,size(targets)
+ write(stderr,*) targets(i)%ptr%output_file
enddo
else if (settings%show_model) then
call show_model(model)
else
- call build_package(model)
+ call build_package(targets,model)
endif
end subroutine
@@ -215,6 +205,7 @@ subroutine cmd_run(settings,test)
type(error_t), allocatable :: error
type(package_config_t) :: package
type(fpm_model_t) :: model
+ type(build_target_ptr), allocatable :: targets(:)
type(string_t) :: exe_cmd
type(string_t), allocatable :: executables(:)
type(build_target_t), pointer :: exe_target
@@ -235,6 +226,12 @@ subroutine cmd_run(settings,test)
error stop 1
end if
+ call targets_from_sources(targets,model,error)
+ if (allocated(error)) then
+ print '(a)', error%message
+ error stop 1
+ end if
+
if (test) then
run_scope = FPM_SCOPE_TEST
else
@@ -245,9 +242,9 @@ subroutine cmd_run(settings,test)
col_width = -1
found(:) = .false.
allocate(executables(0))
- do i=1,size(model%targets)
+ do i=1,size(targets)
- exe_target => model%targets(i)%ptr
+ exe_target => targets(i)%ptr
if (exe_target%target_type == FPM_TARGET_EXECUTABLE .and. &
allocated(exe_target%dependencies)) then
@@ -328,7 +325,7 @@ subroutine cmd_run(settings,test)
end if
- call build_package(model)
+ call build_package(targets,model)
if (settings%list) then
call compact_list()
@@ -354,9 +351,9 @@ subroutine cmd_run(settings,test)
j = 1
nCol = LINE_WIDTH/col_width
write(stderr,*) 'Available names:'
- do i=1,size(model%targets)
+ do i=1,size(targets)
- exe_target => model%targets(i)%ptr
+ exe_target => targets(i)%ptr
if (exe_target%target_type == FPM_TARGET_EXECUTABLE .and. &
allocated(exe_target%dependencies)) then
diff --git a/fpm/src/fpm/cmd/install.f90 b/fpm/src/fpm/cmd/install.f90
index 59ba3a5..db7a9f8 100644
--- a/fpm/src/fpm/cmd/install.f90
+++ b/fpm/src/fpm/cmd/install.f90
@@ -7,8 +7,9 @@ module fpm_cmd_install
use fpm_filesystem, only : join_path, list_files
use fpm_installer, only : installer_t, new_installer
use fpm_manifest, only : package_config_t, get_package_data
- use fpm_model, only : fpm_model_t, build_target_t, FPM_TARGET_EXECUTABLE, &
- FPM_SCOPE_APP
+ use fpm_model, only : fpm_model_t, FPM_SCOPE_APP
+ use fpm_targets, only: targets_from_sources, build_target_t, &
+ build_target_ptr, FPM_TARGET_EXECUTABLE
use fpm_strings, only : string_t, resize
implicit none
private
@@ -24,6 +25,7 @@ contains
type(package_config_t) :: package
type(error_t), allocatable :: error
type(fpm_model_t) :: model
+ type(build_target_ptr), allocatable :: targets(:)
type(installer_t) :: installer
character(len=:), allocatable :: lib, exe, dir
logical :: installable
@@ -34,6 +36,9 @@ contains
call build_model(model, settings%fpm_build_settings, package, error)
call handle_error(error)
+ call targets_from_sources(targets,model,error)
+ call handle_error(error)
+
installable = (allocated(package%library) .and. package%install%library) &
.or. allocated(package%executable)
if (.not.installable) then
@@ -42,12 +47,12 @@ contains
end if
if (settings%list) then
- call install_info(output_unit, package, model)
+ call install_info(output_unit, package, model, targets)
return
end if
if (.not.settings%no_rebuild) then
- call build_package(model)
+ call build_package(targets,model)
end if
call new_installer(installer, prefix=settings%prefix, &
@@ -66,16 +71,17 @@ contains
end if
if (allocated(package%executable)) then
- call install_executables(installer, model, error)
+ call install_executables(installer, targets, error)
call handle_error(error)
end if
end subroutine cmd_install
- subroutine install_info(unit, package, model)
+ subroutine install_info(unit, package, model, targets)
integer, intent(in) :: unit
type(package_config_t), intent(in) :: package
type(fpm_model_t), intent(in) :: model
+ type(build_target_ptr), intent(in) :: targets(:)
integer :: ii, ntargets
character(len=:), allocatable :: lib
@@ -90,11 +96,11 @@ contains
"lib"//model%package_name//".a")
install_target(ntargets)%s = lib
end if
- do ii = 1, size(model%targets)
- if (is_executable_target(model%targets(ii)%ptr)) then
+ do ii = 1, size(targets)
+ if (is_executable_target(targets(ii)%ptr)) then
if (ntargets >= size(install_target)) call resize(install_target)
ntargets = ntargets + 1
- install_target(ntargets)%s = model%targets(ii)%ptr%output_file
+ install_target(ntargets)%s = targets(ii)%ptr%output_file
end if
end do
@@ -125,15 +131,15 @@ contains
end subroutine install_module_files
- subroutine install_executables(installer, model, error)
+ subroutine install_executables(installer, targets, error)
type(installer_t), intent(inout) :: installer
- type(fpm_model_t), intent(in) :: model
+ type(build_target_ptr), intent(in) :: targets(:)
type(error_t), allocatable, intent(out) :: error
integer :: ii
- do ii = 1, size(model%targets)
- if (is_executable_target(model%targets(ii)%ptr)) then
- call installer%install_executable(model%targets(ii)%ptr%output_file, error)
+ do ii = 1, size(targets)
+ if (is_executable_target(targets(ii)%ptr)) then
+ call installer%install_executable(targets(ii)%ptr%output_file, error)
if (allocated(error)) exit
end if
end do
diff --git a/fpm/src/fpm_backend.f90 b/fpm/src/fpm_backend.f90
index 9d22e25..74cef61 100644
--- a/fpm/src/fpm_backend.f90
+++ b/fpm/src/fpm_backend.f90
@@ -1,6 +1,6 @@
!># Build backend
-!> Uses a valid `[[fpm_model]]` instance to schedule and execute the
-!> compilation and linking of package targets.
+!> Uses a list of `[[build_target_ptr]]` and a valid `[[fpm_model]]` instance
+!> to schedule and execute the compilation and linking of package targets.
!>
!> The package build process (`[[build_package]]`) comprises three steps:
!>
@@ -29,7 +29,8 @@ module fpm_backend
use fpm_environment, only: run
use fpm_filesystem, only: dirname, join_path, exists, mkdir
-use fpm_model, only: fpm_model_t, build_target_t, build_target_ptr, &
+use fpm_model, only: fpm_model_t
+use fpm_targets, only: build_target_t, build_target_ptr, &
FPM_TARGET_OBJECT, FPM_TARGET_ARCHIVE, FPM_TARGET_EXECUTABLE
use fpm_strings, only: string_cat
@@ -42,8 +43,9 @@ public :: build_package, sort_target, schedule_targets
contains
!> Top-level routine to build package described by `model`
-subroutine build_package(model)
- type(fpm_model_t), intent(inout) :: model
+subroutine build_package(targets,model)
+ type(build_target_ptr), intent(inout) :: targets(:)
+ type(fpm_model_t), intent(in) :: model
integer :: i, j
type(build_target_ptr), allocatable :: queue(:)
@@ -55,14 +57,14 @@ subroutine build_package(model)
end if
! Perform depth-first topological sort of targets
- do i=1,size(model%targets)
+ do i=1,size(targets)
- call sort_target(model%targets(i)%ptr)
+ call sort_target(targets(i)%ptr)
end do
! Construct build schedule queue
- call schedule_targets(queue, schedule_ptr, model%targets)
+ call schedule_targets(queue, schedule_ptr, targets)
! Loop over parallel schedule regions
do i=1,size(schedule_ptr)-1
@@ -236,27 +238,13 @@ subroutine build_target(model,target)
select case(target%target_type)
case (FPM_TARGET_OBJECT)
- call run(model%fortran_compiler//" -c " // target%source%file_name // model%fortran_compile_flags &
+ call run(model%fortran_compiler//" -c " // target%source%file_name // target%compile_flags &
// " -o " // target%output_file)
case (FPM_TARGET_EXECUTABLE)
-
- link_flags = string_cat(target%link_objects," ")
-
- if (allocated(model%library_file)) then
- link_flags = link_flags//" "//model%library_file//" "//model%link_flags
- else
- link_flags = link_flags//" "//model%link_flags
- end if
-
- if (allocated(target%link_libraries)) then
- if (size(target%link_libraries) > 0) then
- link_flags = link_flags // " -l" // string_cat(target%link_libraries," -l")
- end if
- end if
- call run(model%fortran_compiler// " " // model%fortran_compile_flags &
- //" "//link_flags// " -o " // target%output_file)
+ call run(model%fortran_compiler// " " // target%compile_flags &
+ //" "//target%link_flags// " -o " // target%output_file)
case (FPM_TARGET_ARCHIVE)
call run("ar -rs " // target%output_file // " " // string_cat(target%link_objects," "))
diff --git a/fpm/src/fpm_command_line.f90 b/fpm/src/fpm_command_line.f90
index 3c8edbd..72a4000 100644
--- a/fpm/src/fpm_command_line.f90
+++ b/fpm/src/fpm_command_line.f90
@@ -130,7 +130,7 @@ contains
case default ; os_type = "OS Type: UNKNOWN"
end select
version_text = [character(len=80) :: &
- & 'Version: 0.1.3, alpha', &
+ & 'Version: 0.1.4, alpha', &
& 'Program: fpm(1)', &
& 'Description: A Fortran package manager and build system', &
& 'Home Page: https://github.com/fortran-lang/fpm', &
diff --git a/fpm/src/fpm_compiler.f90 b/fpm/src/fpm_compiler.f90
index cc36d8c..20c6482 100644
--- a/fpm/src/fpm_compiler.f90
+++ b/fpm/src/fpm_compiler.f90
@@ -16,7 +16,7 @@ type(fpm_model_t), intent(inout) :: model !! model to add compiler options to
! could just be a function to return a string instead of passing model
! but likely to change other components like matching C compiler
-character(len=:),allocatable :: fflags ! optional flags that might be overridden by user
+character(len=:),allocatable :: fflags ! optional flags that might be overridden by user
character(len=:),allocatable :: modpath
character(len=:),allocatable :: mandatory ! flags required for fpm to function properly;
! ie. add module path and module include directory as appropriate
@@ -46,6 +46,24 @@ character(len=:),allocatable :: mandatory ! flags required for fpm to function p
! G95 ? ? -fmod= -I -fopenmp discontinued
! Open64 ? ? -module -I -mp discontinued
! Unisys ? ? ? ? ? discontinued
+character(len=*),parameter :: names(*)=[ character(len=10) :: &
+& 'caf', &
+& 'gfortran', &
+& 'f95', &
+& 'nvfortran', &
+& 'ifort', &
+& 'ifx', &
+& 'pgfortran', &
+& 'pgf90', &
+& 'pgf95', &
+& 'flang', &
+& 'lfc', &
+& 'nagfor', &
+& 'crayftn', &
+& 'xlf90', &
+& 'unknown']
+integer :: i
+
modpath=join_path(model%output_directory,model%package_name)
fflags=''
mandatory=''
@@ -147,7 +165,6 @@ character(len=:),allocatable :: mandatory ! flags required for fpm to function p
& -reentrancy threaded&
& -nogen-interfaces&
& -assume byterecl&
- & -assume nounderscore&
&'
mandatory=' -module '//modpath//' -I '//modpath
case('debug_ifort')
@@ -223,10 +240,8 @@ character(len=:),allocatable :: mandatory ! flags required for fpm to function p
case default
fflags = ' '
mandatory=' -module '//modpath//' -I '//modpath
- write(*,*)'<WARNING> unknown compiler (',compiler,')'
- write(*,*)' and build name (',build_name,')'
- write(*,*)' combination.'
- write(*,*)' known compilers are gfortran, nvfortran, ifort'
+ write(*,'(*(a))')'<WARNING> unknown compiler (',compiler,') and build name (',build_name,') combination.'
+ write(*,'(a,*(T31,6(a:,", "),/))')' known compilers are ',(trim(names(i)),i=1,size(names)-1)
end select
model%fortran_compile_flags = fflags//' '//mandatory
diff --git a/fpm/src/fpm_model.f90 b/fpm/src/fpm_model.f90
index 9c821da..072ac5f 100644
--- a/fpm/src/fpm_model.f90
+++ b/fpm/src/fpm_model.f90
@@ -3,15 +3,11 @@
!> Defines the fpm model data types which encapsulate all information
!> required to correctly build a package and its dependencies.
!>
-!> The process (see `[[build_model(subroutine)]]`) for generating a valid `[[fpm_model]]` is as follows:
+!> The process (see `[[build_model(subroutine)]]`) for generating a valid `[[fpm_model]]` involves
+!> source files discovery ([[fpm_sources]]) and parsing ([[fpm_source_parsing]]).
!>
-!> 1. Source files are discovered ([[fpm_sources]]) and parsed ([[fpm_source_parsing]])
-!> 2. A list of build targets is generated (`[[targets_from_sources]]`) from the sources
-!> 3. Inter-target dependencies are resolved (`[[resolve_module_dependencies]]`) based on modules used and provided
-!> 4. Object link lists are generated for link targets (executables and libraries) (`[[resolve_target_linking]]`)
-!>
-!> Once a valid `[[fpm_model]]` has been constructed, it may be passed to `[[fpm_backend:build_package]]` to
-!> build the package.
+!> Once a valid `[[fpm_model]]` has been constructed, it may be passed to `[[fpm_targets:targets_from_sources]]` to
+!> generate a list of build targets for the backend.
!>
!>### Enumerations
!>
@@ -21,9 +17,6 @@
!> __Source scope:__ `FPM_SCOPE_*`
!> Describes the scoping rules for using modules — controls module dependency resolution
!>
-!> __Target type:__ `FPM_TARGET_*`
-!> Describes the type of build target — determines backend build rules
-!>
module fpm_model
use iso_fortran_env, only: int64
use fpm_strings, only: string_t, str
@@ -31,15 +24,12 @@ use fpm_dependency, only: dependency_tree_t
implicit none
private
-public :: fpm_model_t, srcfile_t, build_target_t, build_target_ptr, &
- show_model
+public :: fpm_model_t, srcfile_t, show_model
public :: FPM_UNIT_UNKNOWN, FPM_UNIT_PROGRAM, FPM_UNIT_MODULE, &
FPM_UNIT_SUBMODULE, FPM_UNIT_SUBPROGRAM, FPM_UNIT_CSOURCE, &
FPM_UNIT_CHEADER, FPM_SCOPE_UNKNOWN, FPM_SCOPE_LIB, &
- FPM_SCOPE_DEP, FPM_SCOPE_APP, FPM_SCOPE_EXAMPLE, FPM_SCOPE_TEST, &
- FPM_TARGET_UNKNOWN, FPM_TARGET_EXECUTABLE, FPM_TARGET_ARCHIVE, &
- FPM_TARGET_OBJECT
+ FPM_SCOPE_DEP, FPM_SCOPE_APP, FPM_SCOPE_EXAMPLE, FPM_SCOPE_TEST
!> Source type unknown
integer, parameter :: FPM_UNIT_UNKNOWN = -1
@@ -70,16 +60,6 @@ integer, parameter :: FPM_SCOPE_TEST = 4
integer, parameter :: FPM_SCOPE_EXAMPLE = 5
-!> Target type is unknown (ignored)
-integer, parameter :: FPM_TARGET_UNKNOWN = -1
-!> Target type is executable
-integer, parameter :: FPM_TARGET_EXECUTABLE = 1
-!> Target type is library archive
-integer, parameter :: FPM_TARGET_ARCHIVE = 2
-!> Target type is compiled object
-integer, parameter :: FPM_TARGET_OBJECT = 3
-
-
!> Type for describing a source file
type srcfile_t
!> File path relative to cwd
@@ -124,53 +104,6 @@ type package_t
end type package_t
-!> Wrapper type for constructing arrays of `[[build_target_t]]` pointers
-type build_target_ptr
-
- type(build_target_t), pointer :: ptr => null()
-
-end type build_target_ptr
-
-
-!> Type describing a generated build target
-type build_target_t
-
- !> File path of build target object relative to cwd
- character(:), allocatable :: output_file
-
- !> Primary source for this build target
- type(srcfile_t), allocatable :: source
-
- !> Resolved build dependencies
- type(build_target_ptr), allocatable :: dependencies(:)
-
- !> Target type
- integer :: target_type = FPM_TARGET_UNKNOWN
-
- !> Native libraries to link against
- type(string_t), allocatable :: link_libraries(:)
-
- !> Objects needed to link this target
- type(string_t), allocatable :: link_objects(:)
-
- !> Flag set when first visited to check for circular dependencies
- logical :: touched = .false.
-
- !> Flag set if build target is sorted for building
- logical :: sorted = .false.
-
- !> Flag set if build target will be skipped (not built)
- logical :: skip = .false.
-
- !> Targets in the same schedule group are guaranteed to be independent
- integer :: schedule = -1
-
- !> Previous source file hash
- integer(int64), allocatable :: digest_cached
-
-end type build_target_t
-
-
!> Type describing everything required to build
!> the root package and its dependencies.
type :: fpm_model_t
@@ -181,21 +114,12 @@ type :: fpm_model_t
!> Array of packages (including the root package)
type(package_t), allocatable :: packages(:)
- !> Array of targets with module-dependencies resolved
- type(build_target_ptr), allocatable :: targets(:)
-
!> Command line name to invoke fortran compiler
character(:), allocatable :: fortran_compiler
!> Command line flags passed to fortran for compilation
character(:), allocatable :: fortran_compile_flags
- !> Command line flags pass for linking
- character(:), allocatable :: link_flags
-
- !> Output file for library archive
- character(:), allocatable :: library_file
-
!> Base directory for build
character(:), allocatable :: output_directory
@@ -209,88 +133,6 @@ end type fpm_model_t
contains
-function info_build_target(t) result(s)
- type(build_target_t), intent(in) :: t
- character(:), allocatable :: s
- integer :: i
- !type build_target_t
- s = "build_target_t("
- ! character(:), allocatable :: output_file
- s = s // 'output_file="' // t%output_file // '"'
- ! type(srcfile_t), allocatable :: source
- if (allocated(t%source)) then
- s = s // ", source=" // info_srcfile_short(t%source)
- else
- s = s // ", source=()"
- end if
- ! type(build_target_ptr), allocatable :: dependencies(:)
- s = s // ", dependencies=["
- if (allocated(t%dependencies)) then
- do i = 1, size(t%dependencies)
- s = s // info_build_target_short(t%dependencies(i)%ptr)
- if (i < size(t%dependencies)) s = s // ", "
- end do
- end if
- s = s // "]"
- ! integer :: target_type = FPM_TARGET_UNKNOWN
- s = s // ", target_type="
- select case(t%target_type)
- case (FPM_TARGET_UNKNOWN)
- s = s // "FPM_TARGET_UNKNOWN"
- case (FPM_TARGET_EXECUTABLE)
- s = s // "FPM_TARGET_EXECUTABLE"
- case (FPM_TARGET_ARCHIVE)
- s = s // "FPM_TARGET_ARCHIVE"
- case (FPM_TARGET_OBJECT)
- s = s // "FPM_TARGET_OBJECT"
- case default
- s = s // "INVALID"
- end select
- ! type(string_t), allocatable :: link_libraries(:)
- s = s // ", link_libraries=["
- if (allocated(t%link_libraries)) then
- do i = 1, size(t%link_libraries)
- s = s // '"' // t%link_libraries(i)%s // '"'
- if (i < size(t%link_libraries)) s = s // ", "
- end do
- end if
- s = s // "]"
- ! type(string_t), allocatable :: link_objects(:)
- s = s // ", link_objects=["
- if (allocated(t%link_objects)) then
- do i = 1, size(t%link_objects)
- s = s // '"' // t%link_objects(i)%s // '"'
- if (i < size(t%link_objects)) s = s // ", "
- end do
- end if
- s = s // "]"
- ! logical :: touched = .false.
- s = s // ", touched=" // str(t%touched)
- ! logical :: sorted = .false.
- s = s // ", sorted=" // str(t%sorted)
- ! logical :: skip = .false.
- s = s // ", skip=" // str(t%skip)
- ! integer :: schedule = -1
- s = s // ", schedule=" // str(t%schedule)
- ! integer(int64), allocatable :: digest_cached
- if (allocated(t%digest_cached)) then
- s = s // ", digest_cached=" // str(t%digest_cached)
- else
- s = s // ", digest_cached=()"
- end if
- !end type build_target_t
- s = s // ")"
-end function info_build_target
-
-function info_build_target_short(t) result(s)
- ! Prints a shortened representation of build_target_t
- type(build_target_t), intent(in) :: t
- character(:), allocatable :: s
- integer :: i
- s = "build_target_t("
- s = s // 'output_file="' // t%output_file // '"'
- s = s // ", ...)"
-end function info_build_target_short
function info_package(p) result(s)
! Returns representation of package_t
@@ -418,21 +260,10 @@ function info_model(model) result(s)
if (i < size(model%packages)) s = s // ", "
end do
s = s // "]"
- ! type(build_target_ptr), allocatable :: targets(:)
- s = s // ", targets=["
- do i = 1, size(model%targets)
- s = s // info_build_target(model%targets(i)%ptr)
- if (i < size(model%targets)) s = s // ", "
- end do
- s = s // "]"
! character(:), allocatable :: fortran_compiler
s = s // ', fortran_compiler="' // model%fortran_compiler // '"'
! character(:), allocatable :: fortran_compile_flags
s = s // ', fortran_compile_flags="' // model%fortran_compile_flags // '"'
- ! character(:), allocatable :: link_flags
- s = s // ', link_flags="' // model%link_flags // '"'
- ! character(:), allocatable :: library_file
- s = s // ', library_file="' // model%library_file // '"'
! character(:), allocatable :: output_directory
s = s // ', output_directory="' // model%output_directory // '"'
! type(string_t), allocatable :: link_libraries(:)
diff --git a/fpm/src/fpm_targets.f90 b/fpm/src/fpm_targets.f90
index c2615a0..68cfc97 100644
--- a/fpm/src/fpm_targets.f90
+++ b/fpm/src/fpm_targets.f90
@@ -15,23 +15,120 @@
!>
!> For more information, please read the documentation for the procedures:
!>
-!> - `[[targets_from_sources]]`
+!> - `[[build_target_list]]`
!> - `[[resolve_module_dependencies]]`
!>
+!>### Enumerations
+!>
+!> __Target type:__ `FPM_TARGET_*`
+!> Describes the type of build target — determines backend build rules
+!>
module fpm_targets
+use iso_fortran_env, only: int64
use fpm_error, only: error_t, fatal_error
use fpm_model
use fpm_environment, only: get_os_type, OS_WINDOWS
use fpm_filesystem, only: dirname, join_path, canon_path
-use fpm_strings, only: string_t, operator(.in.)
+use fpm_strings, only: string_t, operator(.in.), string_cat
implicit none
private
+
+public FPM_TARGET_UNKNOWN, FPM_TARGET_EXECUTABLE, &
+ FPM_TARGET_ARCHIVE, FPM_TARGET_OBJECT
+public build_target_t, build_target_ptr
public targets_from_sources, resolve_module_dependencies
public resolve_target_linking, add_target, add_dependency
+
+
+!> Target type is unknown (ignored)
+integer, parameter :: FPM_TARGET_UNKNOWN = -1
+!> Target type is executable
+integer, parameter :: FPM_TARGET_EXECUTABLE = 1
+!> Target type is library archive
+integer, parameter :: FPM_TARGET_ARCHIVE = 2
+!> Target type is compiled object
+integer, parameter :: FPM_TARGET_OBJECT = 3
+
+
+!> Wrapper type for constructing arrays of `[[build_target_t]]` pointers
+type build_target_ptr
+
+ type(build_target_t), pointer :: ptr => null()
+
+end type build_target_ptr
+
+
+!> Type describing a generated build target
+type build_target_t
+
+ !> File path of build target object relative to cwd
+ character(:), allocatable :: output_file
+
+ !> Primary source for this build target
+ type(srcfile_t), allocatable :: source
+
+ !> Resolved build dependencies
+ type(build_target_ptr), allocatable :: dependencies(:)
+
+ !> Target type
+ integer :: target_type = FPM_TARGET_UNKNOWN
+
+ !> Native libraries to link against
+ type(string_t), allocatable :: link_libraries(:)
+
+ !> Objects needed to link this target
+ type(string_t), allocatable :: link_objects(:)
+
+ !> Link flags for this build target
+ character(:), allocatable :: link_flags
+
+ !> Compile flags for this build target
+ character(:), allocatable :: compile_flags
+
+ !> Flag set when first visited to check for circular dependencies
+ logical :: touched = .false.
+
+ !> Flag set if build target is sorted for building
+ logical :: sorted = .false.
+
+ !> Flag set if build target will be skipped (not built)
+ logical :: skip = .false.
+
+ !> Targets in the same schedule group are guaranteed to be independent
+ integer :: schedule = -1
+
+ !> Previous source file hash
+ integer(int64), allocatable :: digest_cached
+
+end type build_target_t
+
+
contains
+!> High-level wrapper to generate build target information
+subroutine targets_from_sources(targets,model,error)
+
+ !> The generated list of build targets
+ type(build_target_ptr), intent(out), allocatable :: targets(:)
+
+ !> The package model from which to construct the target list
+ type(fpm_model_t), intent(inout), target :: model
+
+ !> Error structure
+ type(error_t), intent(out), allocatable :: error
+
+ call build_target_list(targets,model)
+
+ call resolve_module_dependencies(targets,error)
+ if (allocated(error)) return
+
+ call resolve_target_linking(targets,model)
+
+end subroutine targets_from_sources
+
+
!> Constructs a list of build targets from a list of source files
!>
!>### Source-target mapping
@@ -51,11 +148,12 @@ contains
!> is a library, then the executable target has an additional dependency on the library
!> archive target.
!>
-!> @note Inter-object dependencies based on modules used and provided are generated separately
-!> in `[[resolve_module_dependencies]]` after all targets have been enumerated.
-subroutine targets_from_sources(model)
+subroutine build_target_list(targets,model)
- !> The package model within which to construct the target list
+ !> The generated list of build targets
+ type(build_target_ptr), intent(out), allocatable :: targets(:)
+
+ !> The package model from which to construct the target list
type(fpm_model_t), intent(inout), target :: model
integer :: i, j
@@ -73,7 +171,7 @@ subroutine targets_from_sources(model)
i=1,size(model%packages(j)%sources)), &
j=1,size(model%packages))])
- if (with_lib) call add_target(model%targets,type = FPM_TARGET_ARCHIVE,&
+ if (with_lib) call add_target(targets,type = FPM_TARGET_ARCHIVE,&
output_file = join_path(model%output_directory,&
model%package_name,'lib'//model%package_name//'.a'))
@@ -86,18 +184,18 @@ subroutine targets_from_sources(model)
select case (sources(i)%unit_type)
case (FPM_UNIT_MODULE,FPM_UNIT_SUBMODULE,FPM_UNIT_SUBPROGRAM,FPM_UNIT_CSOURCE)
- call add_target(model%targets,source = sources(i), &
+ call add_target(targets,source = sources(i), &
type = FPM_TARGET_OBJECT,&
output_file = get_object_name(sources(i)))
if (with_lib .and. sources(i)%unit_scope == FPM_SCOPE_LIB) then
! Archive depends on object
- call add_dependency(model%targets(1)%ptr, model%targets(size(model%targets))%ptr)
+ call add_dependency(targets(1)%ptr, targets(size(targets))%ptr)
end if
case (FPM_UNIT_PROGRAM)
- call add_target(model%targets,type = FPM_TARGET_OBJECT,&
+ call add_target(targets,type = FPM_TARGET_OBJECT,&
output_file = get_object_name(sources(i)), &
source = sources(i) &
)
@@ -116,17 +214,17 @@ subroutine targets_from_sources(model)
end if
- call add_target(model%targets,type = FPM_TARGET_EXECUTABLE,&
+ call add_target(targets,type = FPM_TARGET_EXECUTABLE,&
link_libraries = sources(i)%link_libraries, &
output_file = join_path(model%output_directory,exe_dir, &
sources(i)%exe_name//xsuffix))
! Executable depends on object
- call add_dependency(model%targets(size(model%targets))%ptr, model%targets(size(model%targets)-1)%ptr)
+ call add_dependency(targets(size(targets))%ptr, targets(size(targets)-1)%ptr)
if (with_lib) then
! Executable depends on library
- call add_dependency(model%targets(size(model%targets))%ptr, model%targets(1)%ptr)
+ call add_dependency(targets(size(targets))%ptr, targets(1)%ptr)
end if
end select
@@ -163,7 +261,7 @@ subroutine targets_from_sources(model)
end function get_object_name
-end subroutine targets_from_sources
+end subroutine build_target_list
!> Allocate a new target and append to target list
@@ -326,29 +424,56 @@ function find_module_dependency(targets,module_name,include_dir) result(target_p
end function find_module_dependency
-!> For libraries and executables, build a list of objects required for linking
-!>
-!> stored in `target%link_objects`
+!> Construct the linker flags string for each target
+!> `target%link_flags` includes non-library objects and library flags
!>
-subroutine resolve_target_linking(targets)
+subroutine resolve_target_linking(targets, model)
type(build_target_ptr), intent(inout), target :: targets(:)
+ type(fpm_model_t), intent(in) :: model
integer :: i
+ character(:), allocatable :: global_link_flags
+
+ if (targets(1)%ptr%target_type == FPM_TARGET_ARCHIVE) then
+ global_link_flags = targets(1)%ptr%output_file
+ else
+ allocate(character(0) :: global_link_flags)
+ end if
+
+ if (allocated(model%link_libraries)) then
+ if (size(model%link_libraries) > 0) then
+ global_link_flags = global_link_flags // " -l" // string_cat(model%link_libraries," -l")
+ end if
+ end if
do i=1,size(targets)
associate(target => targets(i)%ptr)
+ target%compile_flags = model%fortran_compile_flags
+
allocate(target%link_objects(0))
if (target%target_type == FPM_TARGET_ARCHIVE) then
call get_link_objects(target%link_objects,target,is_exe=.false.)
+ allocate(character(0) :: target%link_flags)
+
else if (target%target_type == FPM_TARGET_EXECUTABLE) then
call get_link_objects(target%link_objects,target,is_exe=.true.)
+ target%link_flags = string_cat(target%link_objects," ")
+
+ if (allocated(target%link_libraries)) then
+ if (size(target%link_libraries) > 0) then
+ target%link_flags = target%link_flags // " -l" // string_cat(target%link_libraries," -l")
+ end if
+ end if
+
+ target%link_flags = target%link_flags//" "//global_link_flags
+
end if
end associate
diff --git a/fpm/test/fpm_test/test_backend.f90 b/fpm/test/fpm_test/test_backend.f90
index a7a3f0b..662e470 100644
--- a/fpm/test/fpm_test/test_backend.f90
+++ b/fpm/test/fpm_test/test_backend.f90
@@ -3,9 +3,9 @@ module test_backend
use testsuite, only : new_unittest, unittest_t, error_t, test_failed
use test_module_dependencies, only: operator(.in.)
use fpm_filesystem, only: exists, mkdir, get_temp_filename
- use fpm_model, only: build_target_t, build_target_ptr, &
- FPM_TARGET_OBJECT, FPM_TARGET_ARCHIVE
- use fpm_targets, only: add_target, add_dependency
+ use fpm_targets, only: build_target_t, build_target_ptr, &
+ FPM_TARGET_OBJECT, FPM_TARGET_ARCHIVE, &
+ add_target, add_dependency
use fpm_backend, only: sort_target, schedule_targets
implicit none
private
diff --git a/fpm/test/fpm_test/test_module_dependencies.f90 b/fpm/test/fpm_test/test_module_dependencies.f90
index 0635350..7f6c0be 100644
--- a/fpm/test/fpm_test/test_module_dependencies.f90
+++ b/fpm/test/fpm_test/test_module_dependencies.f90
@@ -2,13 +2,13 @@
module test_module_dependencies
use testsuite, only : new_unittest, unittest_t, error_t, test_failed
use fpm_targets, only: targets_from_sources, resolve_module_dependencies, &
- resolve_target_linking
- use fpm_model, only: fpm_model_t, srcfile_t, build_target_t, build_target_ptr, &
+ resolve_target_linking, build_target_t, build_target_ptr, &
+ FPM_TARGET_EXECUTABLE, FPM_TARGET_OBJECT, FPM_TARGET_ARCHIVE
+ use fpm_model, only: fpm_model_t, srcfile_t, &
FPM_UNIT_UNKNOWN, FPM_UNIT_PROGRAM, FPM_UNIT_MODULE, &
FPM_UNIT_SUBMODULE, FPM_UNIT_SUBPROGRAM, FPM_UNIT_CSOURCE, &
FPM_UNIT_CHEADER, FPM_SCOPE_UNKNOWN, FPM_SCOPE_LIB, &
- FPM_SCOPE_DEP, FPM_SCOPE_APP, FPM_SCOPE_TEST, &
- FPM_TARGET_EXECUTABLE, FPM_TARGET_OBJECT, FPM_TARGET_ARCHIVE
+ FPM_SCOPE_DEP, FPM_SCOPE_APP, FPM_SCOPE_TEST
use fpm_strings, only: string_t, operator(.in.)
implicit none
private
@@ -53,6 +53,7 @@ contains
type(error_t), allocatable, intent(out) :: error
type(fpm_model_t) :: model
+ type(build_target_ptr), allocatable :: targets(:)
model%output_directory = ''
allocate(model%packages(1))
@@ -67,34 +68,32 @@ contains
provides=[string_t('my_mod_2')], &
uses=[string_t('my_mod_1')])
- call targets_from_sources(model)
- call resolve_module_dependencies(model%targets,error)
+ call targets_from_sources(targets,model,error)
+ if (allocated(error)) return
if (allocated(error)) then
return
end if
- if (size(model%targets) /= 3) then
- call test_failed(error,'Incorrect number of model%targets - expecting three')
+ if (size(targets) /= 3) then
+ call test_failed(error,'Incorrect number of targets - expecting three')
return
end if
- call resolve_target_linking(model%targets)
-
- call check_target(model%targets(1)%ptr,type=FPM_TARGET_ARCHIVE,n_depends=2, &
- deps = [model%targets(2),model%targets(3)], &
- links = model%targets(2:3), error=error)
+ call check_target(targets(1)%ptr,type=FPM_TARGET_ARCHIVE,n_depends=2, &
+ deps = [targets(2),targets(3)], &
+ links = targets(2:3), error=error)
if (allocated(error)) return
- call check_target(model%targets(2)%ptr,type=FPM_TARGET_OBJECT,n_depends=0, &
+ call check_target(targets(2)%ptr,type=FPM_TARGET_OBJECT,n_depends=0, &
source=model%packages(1)%sources(1),error=error)
if (allocated(error)) return
- call check_target(model%targets(3)%ptr,type=FPM_TARGET_OBJECT,n_depends=1, &
- deps=[model%targets(2)],source=model%packages(1)%sources(2),error=error)
+ call check_target(targets(3)%ptr,type=FPM_TARGET_OBJECT,n_depends=1, &
+ deps=[targets(2)],source=model%packages(1)%sources(2),error=error)
if (allocated(error)) return
@@ -102,7 +101,7 @@ contains
!> Check a program using a library module
- !> Each program generates two model%targets: object file and executable
+ !> Each program generates two targets: object file and executable
!>
subroutine test_program_module_use(error)
@@ -123,6 +122,7 @@ contains
integer :: i
type(fpm_model_t) :: model
+ type(build_target_ptr), allocatable :: targets(:)
character(:), allocatable :: scope_str
model%output_directory = ''
@@ -139,38 +139,32 @@ contains
scope=exe_scope, &
uses=[string_t('my_mod_1')])
- call targets_from_sources(model)
- call resolve_module_dependencies(model%targets,error)
-
- if (allocated(error)) then
- return
- end if
+ call targets_from_sources(targets,model,error)
+ if (allocated(error)) return
- if (size(model%targets) /= 4) then
- call test_failed(error,scope_str//'Incorrect number of model%targets - expecting three')
+ if (size(targets) /= 4) then
+ call test_failed(error,scope_str//'Incorrect number of targets - expecting three')
return
end if
- call resolve_target_linking(model%targets)
-
- call check_target(model%targets(1)%ptr,type=FPM_TARGET_ARCHIVE,n_depends=1, &
- deps=[model%targets(2)],links=[model%targets(2)],error=error)
+ call check_target(targets(1)%ptr,type=FPM_TARGET_ARCHIVE,n_depends=1, &
+ deps=[targets(2)],links=[targets(2)],error=error)
if (allocated(error)) return
- call check_target(model%targets(2)%ptr,type=FPM_TARGET_OBJECT,n_depends=0, &
+ call check_target(targets(2)%ptr,type=FPM_TARGET_OBJECT,n_depends=0, &
source=model%packages(1)%sources(1),error=error)
if (allocated(error)) return
- call check_target(model%targets(3)%ptr,type=FPM_TARGET_OBJECT,n_depends=1, &
- deps=[model%targets(2)],source=model%packages(1)%sources(2),error=error)
+ call check_target(targets(3)%ptr,type=FPM_TARGET_OBJECT,n_depends=1, &
+ deps=[targets(2)],source=model%packages(1)%sources(2),error=error)
if (allocated(error)) return
- call check_target(model%targets(4)%ptr,type=FPM_TARGET_EXECUTABLE,n_depends=2, &
- deps=[model%targets(1),model%targets(3)], &
- links=[model%targets(3)], error=error)
+ call check_target(targets(4)%ptr,type=FPM_TARGET_EXECUTABLE,n_depends=2, &
+ deps=[targets(1),targets(3)], &
+ links=[targets(3)], error=error)
if (allocated(error)) return
@@ -188,6 +182,7 @@ contains
integer :: i
type(fpm_model_t) :: model
+ type(build_target_ptr), allocatable :: targets(:)
model%output_directory = ''
allocate(model%packages(1))
@@ -198,28 +193,22 @@ contains
provides=[string_t('app_mod')], &
uses=[string_t('app_mod')])
- call targets_from_sources(model)
- call resolve_module_dependencies(model%targets,error)
-
- if (allocated(error)) then
- return
- end if
+ call targets_from_sources(targets,model,error)
+ if (allocated(error)) return
- if (size(model%targets) /= 2) then
- write(*,*) size(model%targets)
- call test_failed(error,'Incorrect number of model%targets - expecting two')
+ if (size(targets) /= 2) then
+ write(*,*) size(targets)
+ call test_failed(error,'Incorrect number of targets - expecting two')
return
end if
- call resolve_target_linking(model%targets)
-
- call check_target(model%targets(1)%ptr,type=FPM_TARGET_OBJECT,n_depends=0, &
+ call check_target(targets(1)%ptr,type=FPM_TARGET_OBJECT,n_depends=0, &
source=model%packages(1)%sources(1),error=error)
if (allocated(error)) return
- call check_target(model%targets(2)%ptr,type=FPM_TARGET_EXECUTABLE,n_depends=1, &
- deps=[model%targets(1)],links=[model%targets(1)],error=error)
+ call check_target(targets(2)%ptr,type=FPM_TARGET_EXECUTABLE,n_depends=1, &
+ deps=[targets(1)],links=[targets(1)],error=error)
if (allocated(error)) return
@@ -245,6 +234,7 @@ contains
type(error_t), allocatable, intent(out) :: error
type(fpm_model_t) :: model
+ type(build_target_ptr), allocatable :: targets(:)
character(:), allocatable :: scope_str
model%output_directory = ''
@@ -265,37 +255,31 @@ contains
scope=exe_scope, &
uses=[string_t('app_mod2')])
- call targets_from_sources(model)
- call resolve_module_dependencies(model%targets,error)
-
- if (allocated(error)) then
- return
- end if
+ call targets_from_sources(targets,model,error)
+ if (allocated(error)) return
- if (size(model%targets) /= 4) then
- call test_failed(error,scope_str//'Incorrect number of model%targets - expecting three')
+ if (size(targets) /= 4) then
+ call test_failed(error,scope_str//'Incorrect number of targets - expecting three')
return
end if
- call resolve_target_linking(model%targets)
-
- call check_target(model%targets(1)%ptr,type=FPM_TARGET_OBJECT,n_depends=0, &
+ call check_target(targets(1)%ptr,type=FPM_TARGET_OBJECT,n_depends=0, &
source=model%packages(1)%sources(1),error=error)
if (allocated(error)) return
- call check_target(model%targets(2)%ptr,type=FPM_TARGET_OBJECT,n_depends=1, &
- source=model%packages(1)%sources(2),deps=[model%targets(1)],error=error)
+ call check_target(targets(2)%ptr,type=FPM_TARGET_OBJECT,n_depends=1, &
+ source=model%packages(1)%sources(2),deps=[targets(1)],error=error)
if (allocated(error)) return
- call check_target(model%targets(3)%ptr,type=FPM_TARGET_OBJECT,n_depends=1, &
- source=model%packages(1)%sources(3),deps=[model%targets(2)],error=error)
+ call check_target(targets(3)%ptr,type=FPM_TARGET_OBJECT,n_depends=1, &
+ source=model%packages(1)%sources(3),deps=[targets(2)],error=error)
if (allocated(error)) return
- call check_target(model%targets(4)%ptr,type=FPM_TARGET_EXECUTABLE,n_depends=1, &
- deps=[model%targets(3)],links=model%targets(1:3), error=error)
+ call check_target(targets(4)%ptr,type=FPM_TARGET_EXECUTABLE,n_depends=1, &
+ deps=[targets(3)],links=targets(1:3), error=error)
if (allocated(error)) return
@@ -310,6 +294,7 @@ contains
type(error_t), allocatable, intent(out) :: error
type(fpm_model_t) :: model
+ type(build_target_ptr), allocatable :: targets(:)
model%output_directory = ''
allocate(model%packages(1))
@@ -324,8 +309,7 @@ contains
provides=[string_t('my_mod_2')], &
uses=[string_t('my_mod_3')])
- call targets_from_sources(model)
- call resolve_module_dependencies(model%targets,error)
+ call targets_from_sources(targets,model,error)
end subroutine test_missing_library_use
@@ -337,6 +321,7 @@ contains
type(error_t), allocatable, intent(out) :: error
type(fpm_model_t) :: model
+ type(build_target_ptr), allocatable :: targets(:)
model%output_directory = ''
allocate(model%packages(1))
@@ -350,8 +335,7 @@ contains
scope=FPM_SCOPE_APP, &
uses=[string_t('my_mod_2')])
- call targets_from_sources(model)
- call resolve_module_dependencies(model%targets,error)
+ call targets_from_sources(targets,model,error)
end subroutine test_missing_program_use
@@ -363,6 +347,7 @@ contains
type(error_t), allocatable, intent(out) :: error
type(fpm_model_t) :: model
+ type(build_target_ptr), allocatable :: targets(:)
model%output_directory = ''
allocate(model%packages(1))
@@ -377,8 +362,7 @@ contains
provides=[string_t('my_mod')], &
uses=[string_t('app_mod')])
- call targets_from_sources(model)
- call resolve_module_dependencies(model%targets,error)
+ call targets_from_sources(targets,model,error)
end subroutine test_invalid_library_use
@@ -390,6 +374,7 @@ contains
type(error_t), allocatable, intent(out) :: error
type(fpm_model_t) :: model
+ type(build_target_ptr), allocatable :: targets(:)
model%output_directory = ''
allocate(model%packages(1))
@@ -403,8 +388,7 @@ contains
scope=FPM_SCOPE_APP, &
uses=[string_t('app_mod')])
- call targets_from_sources(model)
- call resolve_module_dependencies(model%targets,error)
+ call targets_from_sources(targets,model,error)
end subroutine test_invalid_own_module_use
diff --git a/fpm/test/help_test/help_test.f90 b/fpm/test/help_test/help_test.f90
index a44786c..8f0c455 100644
--- a/fpm/test/help_test/help_test.f90
+++ b/fpm/test/help_test/help_test.f90
@@ -2,6 +2,8 @@ program help_test
! note hardcoded len=k1 instead of len=: in this test is a work-around a gfortran bug in old
! pre-v8.3 versions
use,intrinsic :: iso_fortran_env, only : stdin=>input_unit, stdout=>output_unit, stderr=>error_unit
+use fpm_filesystem, only : dirname, join_path, exists
+use fpm_environment, only : get_os_type, OS_WINDOWS
implicit none
integer :: i, j
integer :: be, af
@@ -11,7 +13,7 @@ integer,parameter :: k1=132
character(len=k1) :: message
logical,allocatable :: tally(:)
!intel-bug!character(len=:),allocatable :: book1(:), book2(:)
-character(len=k1),allocatable :: book1(:), book2(:), book3(:)
+character(len=k1),allocatable :: book1(:), book2(:)
!intel-bug!character(len=:),allocatable :: page1(:)
character(len=k1),allocatable :: page1(:)
integer :: lines
@@ -20,58 +22,57 @@ integer :: chars
character(len=*),parameter :: cmds(*) = [character(len=80) :: &
! build manual as pieces using various help commands
! debug version
-'fpm run -- --version ',& ! verify fpm version being used
-'fpm run -- --help > fpm_scratch_help.txt',&
-'fpm run -- help new >> fpm_scratch_help.txt',&
-'fpm run -- help update >> fpm_scratch_help.txt',&
-'fpm run -- build --help >> fpm_scratch_help.txt',&
-'fpm run -- help run >> fpm_scratch_help.txt',&
-'fpm run -- help test >> fpm_scratch_help.txt',&
-'fpm run -- help runner >> fpm_scratch_help.txt',&
-'fpm run -- help install >> fpm_scratch_help.txt',&
-'fpm run -- help list >> fpm_scratch_help.txt',&
-'fpm run -- help help >> fpm_scratch_help.txt',&
-'fpm run -- --version >> fpm_scratch_help.txt',&
-! release version
-'fpm run --release -- --version ',& ! verify fpm version being used
-'fpm run --release -- --help > fpm_scratch_help3.txt',&
-'fpm run --release -- help new >> fpm_scratch_help3.txt',&
-'fpm run --release -- help update >> fpm_scratch_help3.txt',&
-'fpm run --release -- build --help >> fpm_scratch_help3.txt',&
-'fpm run --release -- help run >> fpm_scratch_help3.txt',&
-'fpm run --release -- help test >> fpm_scratch_help3.txt',&
-'fpm run --release -- help runner >> fpm_scratch_help3.txt',&
-'fpm run --release -- help install >> fpm_scratch_help3.txt',&
-'fpm run --release -- help list >> fpm_scratch_help3.txt',&
-'fpm run --release -- help help >> fpm_scratch_help3.txt',&
-'fpm run --release -- --version >> fpm_scratch_help3.txt',&
+' --version ',& ! verify fpm version being used
+' --help > fpm_scratch_help.txt',&
+' help new >> fpm_scratch_help.txt',&
+' help update >> fpm_scratch_help.txt',&
+' build --help >> fpm_scratch_help.txt',&
+' help run >> fpm_scratch_help.txt',&
+' help test >> fpm_scratch_help.txt',&
+' help runner >> fpm_scratch_help.txt',&
+' help install >> fpm_scratch_help.txt',&
+' help list >> fpm_scratch_help.txt',&
+' help help >> fpm_scratch_help.txt',&
+' --version >> fpm_scratch_help.txt',&
! generate manual
-'fpm run -- help manual > fpm_scratch_manual.txt']
+' help manual > fpm_scratch_manual.txt']
!'fpm run >> fpm_scratch_help.txt',&
!'fpm run -- --list >> fpm_scratch_help.txt',&
!'fpm run -- list --list >> fpm_scratch_help.txt',&
character(len=*),parameter :: names(*)=[character(len=10) ::&
'fpm','new','update','build','run','test','runner','install','list','help']
-character(len=:),allocatable :: add
+character(len=:), allocatable :: prog
+integer :: length
+
+ ! FIXME: Super hacky way to get the name of the fpm executable,
+ ! it works better than invoking fpm again but should be replaced ASAP.
+ call get_command_argument(0, length=length)
+ allocate(character(len=length) :: prog)
+ call get_command_argument(0, prog)
+ path = dirname(prog)
+ if (get_os_type() == OS_WINDOWS) then
+ prog = join_path(path, "..", "app", "fpm.exe")
+ if (.not.exists(prog)) then
+ prog = join_path(path, "..", "..", "app", "fpm.exe")
+ end if
+ else
+ prog = join_path(path, "..", "app", "fpm")
+ if (.not.exists(prog)) then
+ prog = join_path(path, "..", "..", "app", "fpm")
+ end if
+ end if
write(*,'(g0:,1x)')'<INFO>TEST help SUBCOMMAND STARTED'
if(allocated(tally))deallocate(tally)
allocate(tally(0))
call wipe('fpm_scratch_help.txt')
- call wipe('fpm_scratch_help3.txt')
call wipe('fpm_scratch_manual.txt')
! check that output has NAME SYNOPSIS DESCRIPTION
- do j=1,2
- if(j.eq.1)then
- ADD=' '
- else
- ADD=' --release '
- endif
do i=1,size(names)
write(*,*)'<INFO>check '//names(i)//' for NAME SYNOPSIS DESCRIPTION'
- path= 'fpm run '//add//' -- help '//names(i)//' >fpm_scratch_help.txt'
+ path= prog // ' help '//names(i)//' >fpm_scratch_help.txt'
message=''
call execute_command_line(path,exitstat=estat,cmdstat=cstat,cmdmsg=message)
write(*,'(*(g0))')'<INFO>CMD=',path,' EXITSTAT=',estat,' CMDSTAT=',cstat,' MESSAGE=',trim(message)
@@ -99,13 +100,12 @@ character(len=:),allocatable :: add
write(*,*)'<INFO>have completed ',count(tally),' tests'
call wipe('fpm_scratch_help.txt')
enddo
- enddo
! execute the fpm(1) commands
do i=1,size(cmds)
message=''
- path= cmds(i)
+ path= prog // cmds(i)
call execute_command_line(path,exitstat=estat,cmdstat=cstat,cmdmsg=message)
write(*,'(*(g0))')'<INFO>CMD=',path,' EXITSTAT=',estat,' CMDSTAT=',cstat,' MESSAGE=',trim(message)
tally=[tally,all([estat.eq.0,cstat.eq.0])]
@@ -114,14 +114,11 @@ character(len=:),allocatable :: add
! compare book written in fragments with manual
call swallow('fpm_scratch_help.txt',book1)
call swallow('fpm_scratch_manual.txt',book2)
- call swallow('fpm_scratch_help3.txt',book3)
! get rid of lines from run() which is not on stderr at the moment
book1=pack(book1,index(book1,' + build/').eq.0)
book2=pack(book1,index(book2,' + build/').eq.0)
- book3=pack(book3,index(book3,' + build/').eq.0)
write(*,*)'<INFO>book1 ',size(book1), len(book1)
write(*,*)'<INFO>book2 ',size(book2), len(book2)
- write(*,*)'<INFO>book2 ',size(book3), len(book3)
if(size(book1).ne.size(book2))then
write(*,*)'<ERROR>manual and "debug" appended pages are not the same size'
tally=[tally,.false.]
@@ -134,18 +131,6 @@ character(len=:),allocatable :: add
tally=[tally,.true.]
endif
endif
- if(size(book3).ne.size(book2))then
- write(*,*)'<ERROR>manual and "release" appended pages are not the same size'
- tally=[tally,.false.]
- else
- if(all(book3.ne.book2))then
- tally=[tally,.false.]
- write(*,*)'<ERROR>manual and "release" appended pages are not the same'
- else
- write(*,*)'<INFO>manual and "release" appended pages are the same'
- tally=[tally,.true.]
- endif
- endif
! overall size of manual
!chars=size(book2)
@@ -159,19 +144,9 @@ character(len=:),allocatable :: add
write(*,*)'<INFO>"debug" manual size in bytes=',chars,' lines=',lines
tally=[tally,.true.]
endif
- chars=sum(len_trim(book3)) ! SUM TRIMMED LENGTH
- lines=size(book3)
- if( (chars.lt.12000) .or. (lines.lt.350) )then
- write(*,*)'<ERROR>"release" manual is suspiciously small, bytes=',chars,' lines=',lines
- tally=[tally,.false.]
- else
- write(*,*)'<INFO>"release" manual size in bytes=',chars,' lines=',lines
- tally=[tally,.true.]
- endif
write(*,'("<INFO>HELP TEST TALLY=",*(g0))')tally
call wipe('fpm_scratch_help.txt')
- call wipe('fpm_scratch_help3.txt')
call wipe('fpm_scratch_manual.txt')
if(all(tally))then
write(*,'(*(g0))')'<INFO>PASSED: all ',count(tally),' tests passed '
diff --git a/fpm/test/new_test/new_test.f90 b/fpm/test/new_test/new_test.f90
index 4ff00c3..3c8c453 100644
--- a/fpm/test/new_test/new_test.f90
+++ b/fpm/test/new_test/new_test.f90
@@ -1,6 +1,7 @@
program new_test
use,intrinsic :: iso_fortran_env, only : stdin=>input_unit, stdout=>output_unit, stderr=>error_unit
-use fpm_filesystem, only : is_dir, list_files, exists, windows_path, join_path
+use fpm_filesystem, only : is_dir, list_files, exists, windows_path, join_path, &
+ dirname
use fpm_strings, only : string_t, operator(.in.)
use fpm_environment, only : run, get_os_type
use fpm_environment, only : OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_CYGWIN, OS_SOLARIS, OS_FREEBSD, OS_WINDOWS
@@ -158,18 +159,29 @@ logical :: IS_OS_WINDOWS
stop 5
endif
contains
- function get_command_path() result(command_path)
- character(len=:), allocatable :: command_path
+ function get_command_path() result(prog)
+ character(len=:), allocatable :: prog
- type(string_t), allocatable :: files(:)
- integer :: i
+ character(len=:), allocatable :: path
+ integer :: length
- call list_files("build", files)
- do i = 1, size(files)
- if (index(files(i)%s, "gfortran") > 0) then
- command_path = join_path(files(i)%s, "app", "fpm")
- return
+ ! FIXME: Super hacky way to get the name of the fpm executable,
+ ! it works better than invoking fpm again but should be replaced ASAP.
+ call get_command_argument(0, length=length)
+ allocate(character(len=length) :: prog)
+ call get_command_argument(0, prog)
+ path = dirname(prog)
+ if (get_os_type() == OS_WINDOWS) then
+ prog = join_path(path, "..", "app", "fpm.exe")
+ if (.not.exists(prog)) then
+ prog = join_path(path, "..", "..", "app", "fpm.exe")
end if
- end do
+ else
+ prog = join_path(path, "..", "app", "fpm")
+ if (.not.exists(prog)) then
+ prog = join_path(path, "..", "..", "app", "fpm")
+ end if
+ end if
+
end function
end program new_test
diff --git a/install.sh b/install.sh
index 578b156..de2aaa8 100755
--- a/install.sh
+++ b/install.sh
@@ -1,33 +1,131 @@
#!/bin/sh
-set -u # error on use of undefined variable
set -e # exit on error
-install_path="$HOME/.local/bin"
+usage()
+{
+ echo "Fortran Package Manager Bootstrap Script"
+ echo ""
+ echo "USAGE:"
+ echo "./install.sh [--help | [--prefix=PREFIX] [--update[=REF]]"
+ echo " [--no-openmp] [--static] [--haskell] ]"
+ echo ""
+ echo " --help Display this help text"
+ echo " --prefix=PREFIX Install binary in 'PREFIX/bin'"
+ echo " Default prefix='\$HOME/.local/bin'"
+ echo " --update[=REF] Update repository from latest release tag"
+ echo " or from git reference REF if specified"
+ echo " --no-openmp Don't build fpm with openmp support"
+ echo " --static Statically link fpm executable"
+ echo " (implies --no-openmp)"
+ echo " --haskell Only install Haskell fpm"
+ echo ""
+ echo " '--no-openmp' and '--static' do not affect the Haskell fpm"
+ echo " build."
+ echo ""
+}
+
+PREFIX="$HOME/.local"
+UPDATE=false
+OMP=true
+STATIC=false
+HASKELL_ONLY=false
+
+STACK_BIN_PATH="$HOME/.local/bin"
+REF=$(git describe --tag --abbrev=0)
+RELEASE_FLAGS="--flag -g --flag -fbacktrace --flag -O3"
+
+while [ "$1" != "" ]; do
+ PARAM=$(echo "$1" | awk -F= '{print $1}')
+ VALUE=$(echo "$1" | awk -F= '{print $2}')
+ case $PARAM in
+ -h | --help)
+ usage
+ exit
+ ;;
+ --prefix)
+ PREFIX=$VALUE
+ ;;
+ --update)
+ UPDATE=true
+ if [ "$VALUE" != "" ]; then
+ REF=$VALUE
+ fi
+ ;;
+ --no-openmp)
+ OMP=false
+ ;;
+ --static)
+ STATIC=true
+ OMP=false
+ ;;
+ --haskell)
+ HASKELL_ONLY=true
+ ;;
+ *)
+ echo "ERROR: unknown parameter \"$PARAM\""
+ usage
+ exit 1
+ ;;
+ esac
+ shift
+done
+
+set -u # error on use of undefined variable
+
+INSTALL_PATH="$PREFIX/bin"
if command -v stack 1> /dev/null 2>&1 ; then
- echo "found stack"
+ echo "Found stack"
else
echo "Haskell stack not found."
- echo "Installing Haskell stack to."
+ echo "Installing Haskell stack"
curl -sSL https://get.haskellstack.org/ | sh
if command -v stack 1> /dev/null 2>&1 ; then
echo "Haskell stack installation successful."
else
- echo "Haskell stack installation unsuccessful."
+ echo "ERROR: Haskell stack installation unsuccessful."
exit 1
fi
fi
-if [ -x "$install_path/fpm" ]; then
- echo "Overwriting existing fpm installation in $install_path"
+if [ -x "$INSTALL_PATH/fpm" ]; then
+ echo "Overwriting existing fpm installation in $INSTALL_PATH"
+fi
+
+if [ "$UPDATE" = true ]; then
+ git checkout "$REF"
+ if [ $? != 0 ]; then
+ echo "ERROR: Unable to checkout $REF."
+ exit 1
+ fi
fi
cd bootstrap
stack install
-if [ -x "$install_path/fpm" ]; then
- echo "fpm installed successfully to $install_path"
+if [ "$STACK_BIN_PATH" != "$INSTALL_PATH" ]; then
+ mv "$STACK_BIN_PATH/fpm" "$INSTALL_PATH/"
+fi
+
+if [ "$HASKELL_ONLY" = true ]; then
+ exit
+fi
+
+if [ "$STATIC" = true ]; then
+ RELEASE_FLAGS="$RELEASE_FLAGS --flag -static"
+fi
+
+if [ "$OMP" = true ]; then
+ RELEASE_FLAGS="$RELEASE_FLAGS --flag -fopenmp"
+fi
+
+cd ../fpm
+"$INSTALL_PATH/fpm" run $RELEASE_FLAGS --runner mv -- "$INSTALL_PATH/"
+
+if [ -x "$INSTALL_PATH/fpm" ]; then
+ echo "fpm installed successfully to $INSTALL_PATH"
else
- echo "fpm installation unsuccessful: fpm not found in $install_path"
+ echo "ERROR: fpm installation unsuccessful: fpm not found in $INSTALL_PATH"
+ exit 1
fi