Skip to content

Commit cd10478

Browse files
authored
Merge pull request #157 from awvwgk/fortran-impl
Implement reading of fpm.toml
2 parents 39fb22d + 7036ed9 commit cd10478

17 files changed

+2002
-23
lines changed

ci/run_tests.bat

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -9,6 +9,9 @@ if errorlevel 1 exit 1
99
fpm run
1010
if errorlevel 1 exit 1
1111

12+
fpm test
13+
if errorlevel 1 exit 1
14+
1215
build\gfortran_debug\app\fpm
1316
if errorlevel 1 exit 1
1417

ci/run_tests.sh

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -5,6 +5,7 @@ set -ex
55
cd fpm
66
fpm build
77
fpm run
8+
fpm test
89
build/gfortran_debug/app/fpm
910
cd ../test/example_packages/hello_world
1011
../../../fpm/build/gfortran_debug/app/fpm build

fpm/fpm.toml

Lines changed: 10 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -4,3 +4,13 @@ license = "MIT"
44
author = "fpm maintainers"
55
maintainer = ""
66
copyright = "2020 fpm contributors"
7+
8+
[dependencies]
9+
[dependencies.toml-f]
10+
git = "https://github.com/toml-f/toml-f"
11+
rev = "290ba87671ab593e7bd51599e1d80ea736b3cd36"
12+
13+
[[test]]
14+
name = "fpm-test"
15+
source-dir = "test"
16+
main = "main.f90"

fpm/src/fpm.f90

Lines changed: 47 additions & 23 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,8 @@
11
module fpm
22
use environment, only: get_os_type, OS_LINUX, OS_MACOS, OS_WINDOWS
3+
use fpm_manifest, only : get_package_data, default_executable, default_library, &
4+
& package_t
5+
use fpm_error, only : error_t
36
implicit none
47
private
58
public :: cmd_build, cmd_install, cmd_new, cmd_run, cmd_test
@@ -85,34 +88,55 @@ logical function str_ends_with(s, e) result(r)
8588
end if
8689
end function
8790

88-
subroutine package_name(name)
89-
character(:), allocatable, intent(out) :: name
90-
! Currrently a heuristic. We should update this to read the name from fpm.toml
91-
if (exists("src/fpm.f90")) then
92-
name = "fpm"
93-
else
94-
name = "hello_world"
95-
end if
96-
end subroutine
97-
9891
subroutine cmd_build()
92+
type(package_t) :: package
93+
type(error_t), allocatable :: error
9994
type(string_t), allocatable :: files(:)
100-
character(:), allocatable :: basename, pkg_name, linking
95+
character(:), allocatable :: basename, linking
10196
integer :: i, n
102-
print *, "# Building project"
103-
call list_files("src", files)
97+
call get_package_data(package, "fpm.toml", error)
98+
if (allocated(error)) then
99+
print '(a)', error%message
100+
error stop 1
101+
end if
102+
103+
! Populate library in case we find the default src directory
104+
if (.not.allocated(package%library) .and. exists("src")) then
105+
call default_library(package%library)
106+
end if
107+
108+
! Populate executable in case we find the default app directory
109+
if (.not.allocated(package%executable) .and. exists("app")) then
110+
allocate(package%executable(1))
111+
call default_executable(package%executable(1), package%name)
112+
end if
113+
114+
if (.not.(allocated(package%library) .or. allocated(package%executable))) then
115+
print '(a)', "Neither library nor executable found, there is nothing to do"
116+
error stop 1
117+
end if
118+
104119
linking = ""
105-
do i = 1, size(files)
106-
if (str_ends_with(files(i)%s, ".f90")) then
107-
n = len(files(i)%s)
108-
basename = files(i)%s(1:n-4)
109-
call run("gfortran -c src/" // basename // ".f90 -o " // basename // ".o")
110-
linking = linking // " " // basename // ".o"
111-
end if
120+
if (allocated(package%library)) then
121+
call list_files(package%library%source_dir, files)
122+
do i = 1, size(files)
123+
if (str_ends_with(files(i)%s, ".f90")) then
124+
n = len(files(i)%s)
125+
basename = files(i)%s
126+
call run("gfortran -c " // package%library%source_dir // "/" // &
127+
& basename // " -o " // basename // ".o")
128+
linking = linking // " " // basename // ".o"
129+
end if
130+
end do
131+
end if
132+
133+
do i = 1, size(package%executable)
134+
basename = package%executable(i)%main
135+
call run("gfortran -c " // package%executable(i)%source_dir // "/" // &
136+
& basename // " -o " // basename // ".o")
137+
call run("gfortran " // basename // ".o " // linking // " -o " // &
138+
& package%executable(i)%name)
112139
end do
113-
call run("gfortran -c app/main.f90 -o main.o")
114-
call package_name(pkg_name)
115-
call run("gfortran main.o " // linking // " -o " // pkg_name)
116140
end subroutine
117141

118142
subroutine cmd_install()

fpm/src/fpm/error.f90

Lines changed: 58 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,58 @@
1+
!> Implementation of basic error handling.
2+
module fpm_error
3+
implicit none
4+
private
5+
6+
public :: error_t
7+
public :: fatal_error, syntax_error, file_not_found_error
8+
9+
10+
!> Data type defining an error
11+
type :: error_t
12+
13+
!> Error message
14+
character(len=:), allocatable :: message
15+
16+
end type error_t
17+
18+
19+
!> Alias syntax errors to fatal errors for now
20+
interface syntax_error
21+
module procedure :: fatal_error
22+
end interface syntax_error
23+
24+
25+
contains
26+
27+
28+
!> Generic fatal runtime error
29+
subroutine fatal_error(error, message)
30+
31+
!> Instance of the error data
32+
type(error_t), allocatable, intent(out) :: error
33+
34+
!> Error message
35+
character(len=*), intent(in) :: message
36+
37+
allocate(error)
38+
error%message = message
39+
40+
end subroutine fatal_error
41+
42+
43+
!> Error created when a file is missing or not found
44+
subroutine file_not_found_error(error, file_name)
45+
46+
!> Instance of the error data
47+
type(error_t), allocatable, intent(out) :: error
48+
49+
!> Name of the missing file
50+
character(len=*), intent(in) :: file_name
51+
52+
allocate(error)
53+
error%message = "'"//file_name//"' could not be found, check if the file exists"
54+
55+
end subroutine file_not_found_error
56+
57+
58+
end module fpm_error

fpm/src/fpm/git.f90

Lines changed: 170 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,170 @@
1+
!> Implementation for interacting with git repositories.
2+
module fpm_git
3+
implicit none
4+
5+
public :: git_target_t
6+
public :: git_target_default, git_target_branch, git_target_tag, &
7+
& git_target_revision
8+
9+
10+
!> Possible git target
11+
type :: enum_descriptor
12+
13+
!> Default target
14+
integer :: default = 200
15+
16+
!> Branch in git repository
17+
integer :: branch = 201
18+
19+
!> Tag in git repository
20+
integer :: tag = 202
21+
22+
!> Commit hash
23+
integer :: revision = 203
24+
25+
end type enum_descriptor
26+
27+
!> Actual enumerator for descriptors
28+
type(enum_descriptor), parameter :: git_descriptor = enum_descriptor()
29+
30+
31+
!> Description of an git target
32+
type :: git_target_t
33+
private
34+
35+
!> Kind of the git target
36+
integer :: descriptor = git_descriptor%default
37+
38+
!> Target URL of the git repository
39+
character(len=:), allocatable :: url
40+
41+
!> Additional descriptor of the git object
42+
character(len=:), allocatable :: object
43+
44+
contains
45+
46+
!> Show information on instance
47+
procedure :: info
48+
49+
end type git_target_t
50+
51+
52+
contains
53+
54+
55+
!> Default target
56+
function git_target_default(url) result(self)
57+
58+
!> Target URL of the git repository
59+
character(len=*), intent(in) :: url
60+
61+
!> New git target
62+
type(git_target_t) :: self
63+
64+
self%descriptor = git_descriptor%default
65+
self%url = url
66+
67+
end function git_target_default
68+
69+
70+
!> Target a branch in the git repository
71+
function git_target_branch(url, branch) result(self)
72+
73+
!> Target URL of the git repository
74+
character(len=*), intent(in) :: url
75+
76+
!> Name of the branch of interest
77+
character(len=*), intent(in) :: branch
78+
79+
!> New git target
80+
type(git_target_t) :: self
81+
82+
self%descriptor = git_descriptor%branch
83+
self%url = url
84+
self%object = branch
85+
86+
end function git_target_branch
87+
88+
89+
!> Target a specific git revision
90+
function git_target_revision(url, sha1) result(self)
91+
92+
!> Target URL of the git repository
93+
character(len=*), intent(in) :: url
94+
95+
!> Commit hash of interest
96+
character(len=*), intent(in) :: sha1
97+
98+
!> New git target
99+
type(git_target_t) :: self
100+
101+
self%descriptor = git_descriptor%revision
102+
self%url = url
103+
self%object = sha1
104+
105+
end function git_target_revision
106+
107+
108+
!> Target a git tag
109+
function git_target_tag(url, tag) result(self)
110+
111+
!> Target URL of the git repository
112+
character(len=*), intent(in) :: url
113+
114+
!> Tag name of interest
115+
character(len=*), intent(in) :: tag
116+
117+
!> New git target
118+
type(git_target_t) :: self
119+
120+
self%descriptor = git_descriptor%tag
121+
self%url = url
122+
self%object = tag
123+
124+
end function git_target_tag
125+
126+
127+
!> Show information on git target
128+
subroutine info(self, unit, verbosity)
129+
130+
!> Instance of the git target
131+
class(git_target_t), intent(in) :: self
132+
133+
!> Unit for IO
134+
integer, intent(in) :: unit
135+
136+
!> Verbosity of the printout
137+
integer, intent(in), optional :: verbosity
138+
139+
integer :: pr
140+
character(len=*), parameter :: fmt = '("#", 1x, a, t30, a)'
141+
142+
if (present(verbosity)) then
143+
pr = verbosity
144+
else
145+
pr = 1
146+
end if
147+
148+
if (pr < 1) return
149+
150+
write(unit, fmt) "Git target"
151+
if (allocated(self%url)) then
152+
write(unit, fmt) "- URL", self%url
153+
end if
154+
if (allocated(self%object)) then
155+
select case(self%descriptor)
156+
case default
157+
write(unit, fmt) "- object", self%object
158+
case(git_descriptor%tag)
159+
write(unit, fmt) "- tag", self%object
160+
case(git_descriptor%branch)
161+
write(unit, fmt) "- branch", self%object
162+
case(git_descriptor%revision)
163+
write(unit, fmt) "- sha1", self%object
164+
end select
165+
end if
166+
167+
end subroutine info
168+
169+
170+
end module fpm_git

0 commit comments

Comments
 (0)