forked from fortran-lang/fpm
-
Notifications
You must be signed in to change notification settings - Fork 0
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 patch-for-fortran-lang#734
- Loading branch information
Showing
48 changed files
with
505 additions
and
50 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,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); | ||
} |
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,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 |
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 = "with_c" |
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,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
10
example_packages/app_with_submodule/app/app1/grandchild.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:child1) grandchild | ||
implicit none | ||
|
||
contains | ||
|
||
module procedure my_fun | ||
b = 1 | ||
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,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 |
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_sub1 | ||
a = 2 | ||
end procedure my_sub1 | ||
|
||
end submodule child2 |
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,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 |
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 = "app_with_submodule" |
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,11 @@ | ||
module parent | ||
implicit none | ||
|
||
interface | ||
|
||
module subroutine my_sub1(a) | ||
integer, intent(out) :: a | ||
end subroutine my_sub1 | ||
end interface | ||
|
||
end module parent |
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,2 @@ | ||
# cpp_files | ||
My cool new project! |
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 = "cpp_files" |
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 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 |
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,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())); | ||
|
||
} | ||
|
||
} |
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 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 |
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 @@ | ||
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 |
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 = "utils1" | ||
|
||
[dependencies] | ||
utils1_1 = { path = "../utils1_1" } |
11 changes: 11 additions & 0 deletions
11
example_packages/hello_fpm_path/crate/utils1/src/say_hello.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,11 @@ | ||
module utils1_m | ||
|
||
implicit none | ||
|
||
contains | ||
|
||
subroutine say_hello1() | ||
print '(a)', "Hello, utils1." | ||
end subroutine say_hello1 | ||
|
||
end module utils1_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 @@ | ||
name = "utils1_1" |
11 changes: 11 additions & 0 deletions
11
example_packages/hello_fpm_path/crate/utils1_1/src/say_hello.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,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 |
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 = "utils2" |
11 changes: 11 additions & 0 deletions
11
example_packages/hello_fpm_path/crate/utils2/src/say_hello.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,11 @@ | ||
module utils2_m | ||
|
||
implicit none | ||
|
||
contains | ||
|
||
subroutine say_hello2() | ||
print '(a)', "Hello, utils2." | ||
end subroutine say_hello2 | ||
|
||
end module utils2_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,5 @@ | ||
name = "hello_fpm_path" | ||
|
||
[dependencies] | ||
utils1 = { path = "crate/utils1" } | ||
utils2 = { path = "crate/utils2" } |
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.