Skip to content

Commit

Permalink
Merge branch 'main' into patch-for-fortran-lang#734
Browse files Browse the repository at this point in the history
  • Loading branch information
awvwgk authored Sep 7, 2022
2 parents 22f5317 + a5d9c70 commit feace99
Show file tree
Hide file tree
Showing 48 changed files with 505 additions and 50 deletions.
3 changes: 2 additions & 1 deletion README.md
Original file line number Diff line number Diff line change
Expand Up @@ -66,7 +66,8 @@ or from [miniconda](https://docs.conda.io/en/latest/miniconda.html).

#### [MSYS2]

Fpm is available as MinGW package in the MSYS2 package manager.
Fpm is available as MinGW package in the MSYS2 package manager,
which supports parallelization of the target compilation.
To install fpm with pacman use

```
Expand Down
16 changes: 16 additions & 0 deletions ci/run_tests.sh
100755 → 100644
Original file line number Diff line number Diff line change
Expand Up @@ -92,6 +92,10 @@ pushd submodules
"$fpm" build
popd

pushd app_with_submodule
"$fpm" run --all
popd

pushd program_with_module
"$fpm" build
"$fpm" run --target Program_with_module
Expand All @@ -118,6 +122,14 @@ pushd c_main
"$fpm" run
popd

pushd app_with_c
"$fpm" run
popd

pushd hello_fpm_path
"$fpm" run
popd

pushd preprocess_cpp
"$fpm" build
popd
Expand All @@ -130,5 +142,9 @@ pushd fpm_test_exe_issues
"$fpm" build
popd

pushd cpp_files
"$fpm" test
popd

# Cleanup
rm -rf ./*/build
2 changes: 2 additions & 0 deletions example_packages/README.md
Original file line number Diff line number Diff line change
Expand Up @@ -6,6 +6,8 @@ the features demonstrated in each package and which versions of fpm are supporte

| Name | Features | Bootstrap (Haskell) fpm | fpm |
|---------------------|---------------------------------------------------------------|:-----------------------:|:---:|
| app_with_c | C files located in app directory (not src) | N | Y |
| app_with_submodule | Submodules located in app directory (not src) | N | Y |
| auto_discovery_off | Default layout with auto-discovery disabled | N | Y |
| c_header_only | C header-only library | N | Y |
| c_includes | C library with c include directory and dependency includes | N | Y |
Expand Down
1 change: 1 addition & 0 deletions example_packages/app_with_c/.gitignore
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
build/*
11 changes: 11 additions & 0 deletions example_packages/app_with_c/app/c_code.c
Original file line number Diff line number Diff line change
@@ -0,0 +1,11 @@
#include <sys/stat.h>
/*
* Decides whether a given file name is a directory.
* return 1 if file exists and is a directory
* Source (Public domain): https://github.com/urbanjost/M_system
*/
int my_isdir(const char *path)
{
struct stat sb;
return stat(path, &sb) == 0 && S_ISDIR(sb.st_mode);
}
37 changes: 37 additions & 0 deletions example_packages/app_with_c/app/main.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,37 @@
module with_c
use iso_c_binding, only: c_char, c_int, c_null_char
implicit none

contains

function system_isdir(dirname)
! Source (Public domain): https://github.com/urbanjost/M_system
!
implicit none
character(len=*), intent(in) :: dirname
logical :: system_isdir

interface
function c_isdir(dirname) bind(C, name="my_isdir") result(c_ierr)
import c_char, c_int
character(kind=c_char, len=1), intent(in) :: dirname(*)
integer(kind=c_int) :: c_ierr
end function c_isdir
end interface

system_isdir = c_isdir(trim(dirname)//c_null_char) == 1

end function system_isdir

end module with_c

program with_c_app
use with_c
implicit none

write (*, *) "isdir('app') = ", system_isdir('app')
write (*, *) "isdir('src') = ", system_isdir('src')
write (*, *) "isdir('test') = ", system_isdir('test')
write (*, *) "isdir('bench') = ", system_isdir('bench')

end program with_c_app
1 change: 1 addition & 0 deletions example_packages/app_with_c/fpm.toml
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
name = "with_c"
1 change: 1 addition & 0 deletions example_packages/app_with_submodule/.gitignore
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
build/*
16 changes: 16 additions & 0 deletions example_packages/app_with_submodule/app/app1/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/app_with_submodule/app/app1/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 = 1
end procedure my_fun

end submodule grandchild
14 changes: 14 additions & 0 deletions example_packages/app_with_submodule/app/app1/main1.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,14 @@
program test
use parent
implicit none

integer :: a

call my_sub1(a)

if (a /= 1) then
write(*,*) 'FAILED: Unexpected value of a'
stop 1
end if

end program test
10 changes: 10 additions & 0 deletions example_packages/app_with_submodule/app/app2/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_sub1
a = 2
end procedure my_sub1

end submodule child2
14 changes: 14 additions & 0 deletions example_packages/app_with_submodule/app/app2/main2.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,14 @@
program test
use parent
implicit none

integer :: a

call my_sub1(a)

if (a /= 2) then
write(*,*) 'FAILED: Unexpected value of a'
stop 1
end if

end program test
1 change: 1 addition & 0 deletions example_packages/app_with_submodule/fpm.toml
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
name = "app_with_submodule"
11 changes: 11 additions & 0 deletions example_packages/app_with_submodule/src/parent.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,11 @@
module parent
implicit none

interface

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

end module parent
2 changes: 2 additions & 0 deletions example_packages/cpp_files/README.md
Original file line number Diff line number Diff line change
@@ -0,0 +1,2 @@
# cpp_files
My cool new project!
1 change: 1 addition & 0 deletions example_packages/cpp_files/fpm.toml
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
name = "cpp_files"
15 changes: 15 additions & 0 deletions example_packages/cpp_files/src/cpp_files.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,15 @@
module cpp_files
use, intrinsic :: ISO_C_Binding
implicit none
private

public :: intvec_maxval

interface
integer function intvec_maxval(array, n) bind(C, name = "intvec_maxval")
import :: c_int, c_size_t
integer(c_int), intent(in) :: array(*)
integer(c_size_t), intent(in), value :: n
end function intvec_maxval
end interface
end module cpp_files
14 changes: 14 additions & 0 deletions example_packages/cpp_files/src/hello_world.cpp
Original file line number Diff line number Diff line change
@@ -0,0 +1,14 @@
#include <vector>
#include <algorithm>

extern "C" {

int intvec_maxval(int* array, size_t n){

std::vector<int> vec(array, array + n);

return *(std::max_element(vec.begin(), vec.end()));

}

}
18 changes: 18 additions & 0 deletions example_packages/cpp_files/test/check.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,18 @@
program check
use iso_c_binding, only: c_size_t
use cpp_files
implicit none

integer :: i, max_element
integer, parameter :: array(*) = [(i,i=-50,10)]

max_element = intvec_maxval(array,size(array,1,c_size_t))

if (max_element == maxval(array)) then
write(*,*) ' PASSED: Max element is ',max_element
else
write(*,*) ' (!) FAILED: Incorrect max element returned'
stop 1
end if

end program check
10 changes: 10 additions & 0 deletions example_packages/hello_fpm_path/app/main.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,10 @@
program hello_fpm
use utils1_m, only: say_hello1
use utils1_1_m, only: say_hello1_1
use utils2_m, only: say_hello2

call say_hello1()
call say_hello1_1()
call say_hello2()

end program hello_fpm
4 changes: 4 additions & 0 deletions example_packages/hello_fpm_path/crate/utils1/fpm.toml
Original file line number Diff line number Diff line change
@@ -0,0 +1,4 @@
name = "utils1"

[dependencies]
utils1_1 = { path = "../utils1_1" }
11 changes: 11 additions & 0 deletions example_packages/hello_fpm_path/crate/utils1/src/say_hello.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,11 @@
module utils1_m

implicit none

contains

subroutine say_hello1()
print '(a)', "Hello, utils1."
end subroutine say_hello1

end module utils1_m
1 change: 1 addition & 0 deletions example_packages/hello_fpm_path/crate/utils1_1/fpm.toml
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
name = "utils1_1"
11 changes: 11 additions & 0 deletions example_packages/hello_fpm_path/crate/utils1_1/src/say_hello.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,11 @@
module utils1_1_m

implicit none

contains

subroutine say_hello1_1()
print '(a)', "Hello, utils1_1."
end subroutine say_hello1_1

end module utils1_1_m
1 change: 1 addition & 0 deletions example_packages/hello_fpm_path/crate/utils2/fpm.toml
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
name = "utils2"
11 changes: 11 additions & 0 deletions example_packages/hello_fpm_path/crate/utils2/src/say_hello.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,11 @@
module utils2_m

implicit none

contains

subroutine say_hello2()
print '(a)', "Hello, utils2."
end subroutine say_hello2

end module utils2_m
5 changes: 5 additions & 0 deletions example_packages/hello_fpm_path/fpm.toml
Original file line number Diff line number Diff line change
@@ -0,0 +1,5 @@
name = "hello_fpm_path"

[dependencies]
utils1 = { path = "crate/utils1" }
utils2 = { path = "crate/utils2" }
8 changes: 6 additions & 2 deletions src/fpm.f90
Original file line number Diff line number Diff line change
Expand Up @@ -43,7 +43,7 @@ subroutine build_model(model, settings, package, error)

integer :: i, j
type(package_config_t) :: dependency
character(len=:), allocatable :: manifest, lib_dir, flags, cflags, ldflags
character(len=:), allocatable :: manifest, lib_dir, flags, cflags, cxxflags, ldflags
character(len=:), allocatable :: version

logical :: duplicates_found = .false.
Expand All @@ -65,7 +65,7 @@ subroutine build_model(model, settings, package, error)
end if

call new_compiler(model%compiler, settings%compiler, settings%c_compiler, &
& echo=settings%verbose, verbose=settings%verbose)
& settings%cxx_compiler, echo=settings%verbose, verbose=settings%verbose)
call new_archiver(model%archiver, settings%archiver, &
& echo=settings%verbose, verbose=settings%verbose)

Expand All @@ -82,6 +82,7 @@ subroutine build_model(model, settings, package, error)
call set_preprocessor_flags(model%compiler%id, flags, package)

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

if (model%compiler%is_unknown()) then
Expand All @@ -93,6 +94,7 @@ subroutine build_model(model, settings, package, error)

model%fortran_compile_flags = flags
model%c_compile_flags = cflags
model%cxx_compile_flags = cxxflags
model%link_flags = ldflags

model%include_tests = settings%build_tests
Expand Down Expand Up @@ -218,8 +220,10 @@ subroutine build_model(model, settings, package, error)
write(*,*)'<INFO> BUILD_NAME: ',model%build_prefix
write(*,*)'<INFO> COMPILER: ',model%compiler%fc
write(*,*)'<INFO> C COMPILER: ',model%compiler%cc
write(*,*)'<INFO> CXX COMPILER: ',model%compiler%cxx
write(*,*)'<INFO> COMPILER OPTIONS: ', model%fortran_compile_flags
write(*,*)'<INFO> C COMPILER OPTIONS: ', model%c_compile_flags
write(*,*)'<INFO> CXX COMPILER OPTIONS: ', model%cxx_compile_flags
write(*,*)'<INFO> LINKER OPTIONS: ', model%link_flags
write(*,*)'<INFO> INCLUDE DIRECTORIES: [', string_cat(model%include_dirs,','),']'
end if
Expand Down
4 changes: 2 additions & 2 deletions src/fpm/cmd/new.f90
Original file line number Diff line number Diff line change
Expand Up @@ -369,8 +369,8 @@ subroutine cmd_new(settings)
&' ',&
&'#M_strings = { path = "M_strings" } ',&
&' ',&
&' # If you specify paths outside of your repository (ie. paths with a ',&
&' # slash in them) things will not work for your users! ',&
&' # This tells fpm that we depend on a crate called M_strings which is found ',&
&' # in the M_strings folder (relative to the fpm.toml it’s written in). ',&
&' # ',&
&' # For a more verbose layout use normal tables rather than inline tables ',&
&' # to specify dependencies: ',&
Expand Down
Loading

0 comments on commit feace99

Please sign in to comment.