-
Notifications
You must be signed in to change notification settings - Fork 100
Commit
This commit does not belong to any branch on this repository, and may belong to a fork outside of the repository.
Merge branch 'main' into package_by_package
- Loading branch information
Showing
42 changed files
with
1,396 additions
and
91 deletions.
There are no files selected for viewing
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1 @@ | ||
build/* |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,4 @@ | ||
name = "preprocess_cpp" | ||
|
||
[preprocess] | ||
[preprocess.cpp] |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
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 |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1 @@ | ||
build/* |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
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 |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1 @@ | ||
name = "submodule_tree_shake" |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
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 |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
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
10
example_packages/submodule_tree_shake/src/child_unused.f90
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
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 |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
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 |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
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
12
example_packages/submodule_tree_shake/src/parent_unused.f90
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
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 |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1 @@ | ||
build/* |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
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 |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1 @@ | ||
name = "tree_shake" |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
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 |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
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 |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
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 |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
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 |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
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 |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
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 = "" | ||
|
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Oops, something went wrong.