Skip to content

Commit

Permalink
Merge branch 'main' into package_by_package
Browse files Browse the repository at this point in the history
  • Loading branch information
zoziha authored Jul 13, 2022
2 parents 5253412 + 408e96a commit c24ea66
Show file tree
Hide file tree
Showing 42 changed files with 1,396 additions and 91 deletions.
2 changes: 1 addition & 1 deletion README.md
Original file line number Diff line number Diff line change
Expand Up @@ -37,7 +37,7 @@ Binaries for the latest stable release are available [to download](https://githu

__Note:__ On Linux and MacOS, you will need to enable executable permission before you can use the binary.

_e.g._ `$ chmod u+x fpm-0.5.0-linux-x86_64`
_e.g._ `$ chmod u+x fpm-0.6.0-linux-x86_64`

The binaries at the [current tag](https://github.com/fortran-lang/fpm/releases/tag/current) are updated automatically to always provide the current git version from the default branch.

Expand Down
16 changes: 16 additions & 0 deletions ci/run_tests.sh
Original file line number Diff line number Diff line change
Expand Up @@ -62,6 +62,22 @@ test ! -x ./build/gfortran_*/app/unused
test ! -x ./build/gfortran_*/test/unused_test
popd

pushd tree_shake
"$fpm" build
"$fpm" run
"$fpm" test
test ! -e ./build/gfortran_*/tree_shake/src_farewell_m.f90.o
test ! -e ./build/gfortran_*/tree_shake/src_farewell_m.f90.o.log
popd

pushd submodule_tree_shake
"$fpm" run
test ! -e ./build/gfortran_*/submodule_tree_shake/src_parent_unused.f90.o
test ! -e ./build/gfortran_*/submodule_tree_shake/src_parent_unused.f90.o.log
test ! -e ./build/gfortran_*/submodule_tree_shake/src_child_unused.f90.o
test ! -e ./build/gfortran_*/submodule_tree_shake/src_child_unused.f90.o.log
popd

pushd version_file
"$fpm" build
"$fpm" run
Expand Down
2 changes: 2 additions & 0 deletions example_packages/README.md
Original file line number Diff line number Diff line change
Expand Up @@ -20,6 +20,8 @@ the features demonstrated in each package and which versions of fpm are supporte
| makefile_complex | External build command (makefile); local path dependency | Y | N |
| program_with_module | App-only; module+program in single source file | Y | Y |
| submodules | Lib-only; submodules (3 levels) | N | Y |
| tree_shake | Test tree-shaking/pruning of unused module dependencies | N | Y |
| submodule_tree_shake| Test tree-shaking/pruning with submodules dependencies | N | Y |
| link_external | Link external library | N | Y |
| link_executable | Link external library to a single executable | N | Y |
| version_file | Read version number from a file in the project root | N | Y |
Expand Down
1 change: 1 addition & 0 deletions example_packages/preprocess_cpp/.gitignore
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
build/*
4 changes: 4 additions & 0 deletions example_packages/preprocess_cpp/fpm.toml
Original file line number Diff line number Diff line change
@@ -0,0 +1,4 @@
name = "preprocess_cpp"

[preprocess]
[preprocess.cpp]
13 changes: 13 additions & 0 deletions example_packages/preprocess_cpp/src/preprocess_cpp.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,13 @@
module preprocess_cpp
implicit none
private

public :: say_hello
contains
subroutine say_hello
print *, "Hello, preprocess_cpp!"
#ifndef TESTMACRO
This breaks the build.
#endif
end subroutine say_hello
end module preprocess_cpp
1 change: 1 addition & 0 deletions example_packages/submodule_tree_shake/.gitignore
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
build/*
9 changes: 9 additions & 0 deletions example_packages/submodule_tree_shake/app/main.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,9 @@
program test
use parent

integer :: a, b

call my_sub1(a)
call my_sub2(b)

end program test
1 change: 1 addition & 0 deletions example_packages/submodule_tree_shake/fpm.toml
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
name = "submodule_tree_shake"
16 changes: 16 additions & 0 deletions example_packages/submodule_tree_shake/src/child1.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,16 @@
submodule(parent) child1
implicit none

interface
module function my_fun() result (b)
integer :: b
end function my_fun
end interface

contains

module procedure my_sub1
a = my_fun()
end procedure my_sub1

end submodule child1
10 changes: 10 additions & 0 deletions example_packages/submodule_tree_shake/src/child2.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,10 @@
submodule(parent) child2
implicit none

contains

module procedure my_sub2
a = 2
end procedure my_sub2

end submodule child2
10 changes: 10 additions & 0 deletions example_packages/submodule_tree_shake/src/child_unused.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,10 @@
submodule(parent_unused) child_unused
implicit none

contains

module procedure unused_sub
a = 1
end procedure unused_sub

end submodule child_unused
10 changes: 10 additions & 0 deletions example_packages/submodule_tree_shake/src/grandchild.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,10 @@
submodule(parent:child1) grandchild
implicit none

contains

module procedure my_fun
b = 2
end procedure my_fun

end submodule grandchild
15 changes: 15 additions & 0 deletions example_packages/submodule_tree_shake/src/parent.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,15 @@
module parent
implicit none

interface

module subroutine my_sub1(a)
integer, intent(out) :: a
end subroutine my_sub1

module subroutine my_sub2(a)
integer, intent(out) :: a
end subroutine my_sub2
end interface

end module parent
12 changes: 12 additions & 0 deletions example_packages/submodule_tree_shake/src/parent_unused.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,12 @@
module parent_unused
implicit none

interface

module subroutine unused_sub(a)
integer, intent(out) :: a
end subroutine unused_sub

end interface

end module parent_unused
1 change: 1 addition & 0 deletions example_packages/tree_shake/.gitignore
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
build/*
15 changes: 15 additions & 0 deletions example_packages/tree_shake/app/say_Hello.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,15 @@
program say_Hello
use greet_m, only: make_greeting

implicit none

interface
function external_function() result(i)
integer :: i
end function external_function
end interface

print *, make_greeting("World")
print *, external_function()

end program say_Hello
1 change: 1 addition & 0 deletions example_packages/tree_shake/fpm.toml
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
name = "tree_shake"
15 changes: 15 additions & 0 deletions example_packages/tree_shake/src/extra_m.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,15 @@
! This module is not used by any other sources,
! however because it also contains an external function
! it cannot be dropped during tree-shaking/pruning
module extra_m
use subdir_constants, only: FAREWELL_STR
implicit none
private

integer, parameter :: m = 0
end

function external_function() result(i)
integer :: i
i = 1
end function external_function
17 changes: 17 additions & 0 deletions example_packages/tree_shake/src/farewell_m.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,17 @@
! This module is not used by any other sources
! and only contains a module (no non-module subprograms),
! therefore it should be dropped during tree-shaking/pruning
module farewell_m
use subdir_constants, only: FAREWELL_STR
implicit none
private

public :: make_farewell
contains
function make_farewell(name) result(greeting)
character(len=*), intent(in) :: name
character(len=:), allocatable :: greeting

greeting = FAREWELL_STR // name // "!"
end function make_farewell
end module farewell_m
16 changes: 16 additions & 0 deletions example_packages/tree_shake/src/greet_m.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,16 @@
! This module is directly by the executables and
! hence should not be dropped during tree-shaking/pruning
module greet_m
use subdir_constants, only: GREET_STR
implicit none
private

public :: make_greeting
contains
function make_greeting(name) result(greeting)
character(len=*), intent(in) :: name
character(len=:), allocatable :: greeting

greeting = GREET_STR // name // "!"
end function make_greeting
end module greet_m
9 changes: 9 additions & 0 deletions example_packages/tree_shake/src/subdir/constants.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,9 @@
! This module is used indirectly by the executables
! and hence should not be dropped during tree-shaking/pruning
module subdir_constants
implicit none

character(*), parameter :: GREET_STR = 'Hello, '
character(*), parameter :: FAREWELL_STR = 'Goodbye, '

end module subdir_constants
18 changes: 18 additions & 0 deletions example_packages/tree_shake/test/greet_test.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,18 @@
program greet_test
use greet_m, only: make_greeting
use iso_fortran_env, only: error_unit, output_unit

implicit none

character(len=:), allocatable :: greeting

allocate(character(len=0) :: greeting)
greeting = make_greeting("World")

if (greeting == "Hello, World!") then
write(output_unit, *) "Passed"
else
write(error_unit, *) "Failed"
call exit(1)
end if
end program greet_test
2 changes: 1 addition & 1 deletion fpm.toml
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
name = "fpm"
version = "0.5.0"
version = "0.6.0"
license = "MIT"
author = "fpm maintainers"
maintainer = ""
Expand Down
2 changes: 1 addition & 1 deletion install.sh
Original file line number Diff line number Diff line change
Expand Up @@ -42,7 +42,7 @@ done

set -u # error on use of undefined variable

SOURCE_URL="https://github.com/fortran-lang/fpm/releases/download/v0.5.0/fpm-0.5.0.F90"
SOURCE_URL="https://github.com/fortran-lang/fpm/releases/download/v0.6.0/fpm-0.6.0.F90"
BOOTSTRAP_DIR="build/bootstrap"
if [ -z ${FC+x} ]; then
FC="gfortran"
Expand Down
9 changes: 6 additions & 3 deletions src/fpm.f90
Original file line number Diff line number Diff line change
Expand Up @@ -12,7 +12,7 @@ module fpm
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
use fpm_compiler, only: new_compiler, new_archiver
use fpm_compiler, only: new_compiler, new_archiver, set_preprocessor_flags


use fpm_sources, only: add_executable_sources, add_sources_from_dir
Expand Down Expand Up @@ -77,6 +77,9 @@ subroutine build_model(model, settings, package, error)
flags = flags // model%compiler%get_default_flags(settings%profile == "release")
end select
end if

call set_preprocessor_flags(model%compiler%id, flags)

cflags = trim(settings%cflag)
ldflags = trim(settings%ldflag)

Expand Down Expand Up @@ -278,7 +281,7 @@ subroutine cmd_build(settings)
call fpm_stop(1,'*cmd_build*:model error:'//error%message)
end if

call targets_from_sources(targets, model, error)
call targets_from_sources(targets, model, settings%prune, error)
if (allocated(error)) then
call fpm_stop(1,'*cmd_build*:target error:'//error%message)
end if
Expand Down Expand Up @@ -324,7 +327,7 @@ subroutine cmd_run(settings,test)
call fpm_stop(1, '*cmd_run*:model error:'//error%message)
end if

call targets_from_sources(targets, model, error)
call targets_from_sources(targets, model, settings%prune, error)
if (allocated(error)) then
call fpm_stop(1, '*cmd_run*:targets error:'//error%message)
end if
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 @@ -38,7 +38,7 @@ subroutine cmd_install(settings)
call build_model(model, settings%fpm_build_settings, package, error)
call handle_error(error)

call targets_from_sources(targets, model, error)
call targets_from_sources(targets, model, settings%prune, error)
call handle_error(error)

installable = (allocated(package%library) .and. package%install%library) &
Expand Down
3 changes: 2 additions & 1 deletion src/fpm/manifest.f90
Original file line number Diff line number Diff line change
Expand Up @@ -12,6 +12,7 @@ module fpm_manifest
use fpm_manifest_executable, only : executable_config_t
use fpm_manifest_dependency, only : dependency_config_t
use fpm_manifest_library, only : library_config_t
use fpm_mainfest_preprocess, only : preprocess_config_t
use fpm_manifest_package, only : package_config_t, new_package
use fpm_error, only : error_t, fatal_error, file_not_found_error
use fpm_toml, only : toml_table, read_package_file
Expand All @@ -23,7 +24,7 @@ module fpm_manifest

public :: get_package_data, default_executable, default_library, default_test
public :: default_example
public :: package_config_t, dependency_config_t
public :: package_config_t, dependency_config_t, preprocess_config_t


contains
Expand Down
11 changes: 10 additions & 1 deletion src/fpm/manifest/package.f90
Original file line number Diff line number Diff line change
Expand Up @@ -39,6 +39,7 @@ module fpm_manifest_package
use fpm_manifest_library, only : library_config_t, new_library
use fpm_manifest_install, only: install_config_t, new_install_config
use fpm_manifest_test, only : test_config_t, new_test
use fpm_mainfest_preprocess, only : preprocess_config_t, new_preprocessors
use fpm_filesystem, only : exists, getline, join_path
use fpm_error, only : error_t, fatal_error, syntax_error, bad_name_error
use fpm_toml, only : toml_table, toml_array, toml_key, toml_stat, get_value, &
Expand Down Expand Up @@ -89,6 +90,9 @@ module fpm_manifest_package
!> Test meta data
type(test_config_t), allocatable :: test(:)

!> Preprocess meta data
type(preprocess_config_t), allocatable :: preprocess(:)

contains

!> Print information on this instance
Expand Down Expand Up @@ -267,6 +271,11 @@ subroutine new_package(self, table, root, error)
if (allocated(error)) return
end if

call get_value(table, "preprocess", child, requested=.false.)
if (associated(child)) then
call new_preprocessors(self%preprocess, child, error)
if (allocated(error)) return
end if
end subroutine new_package


Expand Down Expand Up @@ -304,7 +313,7 @@ subroutine check(table, error)
case("version", "license", "author", "maintainer", "copyright", &
& "description", "keywords", "categories", "homepage", "build", &
& "dependencies", "dev-dependencies", "test", "executable", &
& "example", "library", "install", "extra")
& "example", "library", "install", "extra", "preprocess")
continue

end select
Expand Down
Loading

0 comments on commit c24ea66

Please sign in to comment.