Skip to content

Commit

Permalink
Merge pull request fortran-lang#743 from LKedward/fix-exe-linking
Browse files Browse the repository at this point in the history
Fix executables linking
  • Loading branch information
LKedward authored Sep 5, 2022
2 parents 2570975 + fc11893 commit e2f00d8
Show file tree
Hide file tree
Showing 15 changed files with 190 additions and 0 deletions.
8 changes: 8 additions & 0 deletions ci/run_tests.sh
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,10 @@ pushd c_main
"$fpm" run
popd

pushd app_with_c
"$fpm" run
popd

pushd hello_fpm_path
"$fpm" run
popd
Expand Down
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
53 changes: 53 additions & 0 deletions src/fpm_targets.f90
Original file line number Diff line number Diff line change
Expand Up @@ -148,6 +148,8 @@ subroutine targets_from_sources(targets,model,prune,error)

call build_target_list(targets,model)

call collect_exe_link_dependencies(targets)

call resolve_module_dependencies(targets,model%external_modules,error)
if (allocated(error)) return

Expand Down Expand Up @@ -334,6 +336,57 @@ end function get_object_name
end subroutine build_target_list


!> Add non-library non-module dependencies for executable targets
!>
!> Executable targets will link to any non-program non-module source files that
!> are in the same directory or in a subdirectory.
!>
!> (Note: Fortran module dependencies are handled separately in
!> `resolve_module_dependencies` and `resolve_target_linking`.)
!>
subroutine collect_exe_link_dependencies(targets)
type(build_target_ptr), intent(inout) :: targets(:)

integer :: i, j
character(:), allocatable :: exe_source_dir

! Add non-module dependencies for executables
do j=1,size(targets)

if (targets(j)%ptr%target_type == FPM_TARGET_EXECUTABLE) then

do i=1,size(targets)

if (i == j) cycle

associate(exe => targets(j)%ptr, dep => targets(i)%ptr)

exe_source_dir = dirname(exe%dependencies(1)%ptr%source%file_name)

if (allocated(dep%source)) then

if (dep%source%unit_scope /= FPM_SCOPE_LIB .and. &
dep%source%unit_type /= FPM_UNIT_PROGRAM .and. &
dep%source%unit_type /= FPM_UNIT_MODULE .and. &
index(dirname(dep%source%file_name), exe_source_dir) == 1) then

call add_dependency(exe, dep)

end if

end if

end associate

end do

end if

end do

end subroutine collect_exe_link_dependencies


!> Allocate a new target and append to target list
subroutine add_target(targets,package,type,output_name,source,link_libraries, macros, version)
type(build_target_ptr), allocatable, intent(inout) :: targets(:)
Expand Down

0 comments on commit e2f00d8

Please sign in to comment.