Skip to content

Commit d693d68

Browse files
authored
Merge pull request #500 from awvwgk/version-file
Allow reading version number from file
2 parents 0372313 + 63288a6 commit d693d68

File tree

11 files changed

+66
-12
lines changed

11 files changed

+66
-12
lines changed

ci/run_tests.sh

Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -62,6 +62,11 @@ test ! -x ./build/gfortran_*/app/unused
6262
test ! -x ./build/gfortran_*/test/unused_test
6363
popd
6464

65+
pushd version_file
66+
"$fpm" build
67+
"$fpm" run
68+
popd
69+
6570
pushd with_c
6671
"$fpm" build
6772
"$fpm" run --target with_c

example_packages/README.md

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -22,5 +22,6 @@ the features demonstrated in each package and which versions of fpm are supporte
2222
| submodules | Lib-only; submodules (3 levels) | N | Y |
2323
| link_external | Link external library | N | Y |
2424
| link_executable | Link external library to a single executable | N | Y |
25+
| version_file | Read version number from a file in the project root | N | Y |
2526
| with_c | Compile with `c` source files | N | Y |
2627
| with_makefile | External build command (makefile) | Y | N |

example_packages/version_file/VERSION

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1 @@
1+
5.42.1
Lines changed: 13 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,13 @@
1+
program stub
2+
implicit none
3+
logical :: exists
4+
integer :: unit
5+
character(len=100) :: line
6+
inquire(file="VERSION", exist=exists)
7+
if (.not.exists) error stop "File VERSION does not exist."
8+
open(file="VERSION", newunit=unit)
9+
read(unit, '(a)') line
10+
close(unit)
11+
12+
print '(*(a))', "File VERSION contains '", trim(line), "'"
13+
end program stub
Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,2 @@
1+
name = "version_file"
2+
version = "VERSION"

manifest-reference.md

Lines changed: 8 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -78,6 +78,14 @@ A standardized way to manage and specify versions is the [Semantic Versioning] s
7878
version = "1.0.0"
7979
```
8080

81+
The version entry can also contain a filename relative to the project root, which contains the version number of the project
82+
83+
*Example:*
84+
85+
```toml
86+
version = "VERSION"
87+
```
88+
8189
[Semantic Versioning]: https://semver.org
8290

8391

src/fpm/cmd/new.f90

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -605,7 +605,7 @@ subroutine create_verified_basic_manifest(filename)
605605
call set_value(table, "copyright", 'Copyright '//date(1:4)//', Jane Doe')
606606
! continue building of manifest
607607
! ...
608-
call new_package(package, table, error)
608+
call new_package(package, table, error=error)
609609
if (allocated(error)) stop 3
610610
if(settings%verbose)then
611611
call table%accept(ser)

src/fpm/manifest.f90

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -113,7 +113,7 @@ subroutine get_package_data(package, file, error, apply_defaults)
113113
return
114114
end if
115115

116-
call new_package(package, table, error)
116+
call new_package(package, table, dirname(file), error)
117117
if (allocated(error)) return
118118

119119
if (present(apply_defaults)) then

src/fpm/manifest/package.f90

Lines changed: 26 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -38,6 +38,7 @@ module fpm_manifest_package
3838
use fpm_manifest_library, only : library_config_t, new_library
3939
use fpm_manifest_install, only: install_config_t, new_install_config
4040
use fpm_manifest_test, only : test_config_t, new_test
41+
use fpm_filesystem, only : exists, getline, join_path
4142
use fpm_error, only : error_t, fatal_error, syntax_error
4243
use fpm_toml, only : toml_table, toml_array, toml_key, toml_stat, get_value, &
4344
& len
@@ -99,14 +100,17 @@ module fpm_manifest_package
99100

100101

101102
!> Construct a new package configuration from a TOML data structure
102-
subroutine new_package(self, table, error)
103+
subroutine new_package(self, table, root, error)
103104

104105
!> Instance of the package configuration
105106
type(package_config_t), intent(out) :: self
106107

107108
!> Instance of the TOML data structure
108109
type(toml_table), intent(inout) :: table
109110

111+
!> Root directory of the manifest
112+
character(len=*), intent(in), optional :: root
113+
110114
!> Error handling
111115
type(error_t), allocatable, intent(out) :: error
112116

@@ -116,8 +120,8 @@ subroutine new_package(self, table, error)
116120
achar(8) // achar(9) // achar(10) // achar(12) // achar(13)
117121
type(toml_table), pointer :: child, node
118122
type(toml_array), pointer :: children
119-
character(len=:), allocatable :: version
120-
integer :: ii, nn, stat
123+
character(len=:), allocatable :: version, version_file
124+
integer :: ii, nn, stat, io
121125

122126
call check(table, error)
123127
if (allocated(error)) return
@@ -157,6 +161,25 @@ subroutine new_package(self, table, error)
157161

158162
call get_value(table, "version", version, "0")
159163
call new_version(self%version, version, error)
164+
if (allocated(error) .and. present(root)) then
165+
version_file = join_path(root, version)
166+
if (exists(version_file)) then
167+
deallocate(error)
168+
open(file=version_file, newunit=io, iostat=stat)
169+
if (stat == 0) then
170+
call getline(io, version, iostat=stat)
171+
end if
172+
if (stat == 0) then
173+
close(io, iostat=stat)
174+
end if
175+
if (stat == 0) then
176+
call new_version(self%version, version, error)
177+
else
178+
call fatal_error(error, "Reading version number from file '" &
179+
& //version_file//"' failed")
180+
end if
181+
end if
182+
end if
160183
if (allocated(error)) return
161184

162185
call get_value(table, "dependencies", child, requested=.false.)

src/fpm_filesystem.f90

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -184,6 +184,7 @@ function dirname(path) result (dir)
184184
character(:), allocatable :: dir
185185

186186
dir = path(1:scan(path,'/\',back=.true.))
187+
if (len_trim(dir) == 0) dir = "."
187188

188189
end function dirname
189190

0 commit comments

Comments
 (0)