aboutsummaryrefslogtreecommitdiff
path: root/src
diff options
context:
space:
mode:
authorSebastian Ehlert <28669218+awvwgk@users.noreply.github.com>2021-06-20 12:14:18 +0200
committerSebastian Ehlert <28669218+awvwgk@users.noreply.github.com>2021-06-20 12:14:18 +0200
commitb6b95dcc9d6563666c1358e6800cc9ff064f657c (patch)
treebe25dbaec76b8f18e9897334f5a6bceee131e7ae /src
parente6688d07c5658b1a26354be7d7aea68231679f05 (diff)
downloadfpm-b6b95dcc9d6563666c1358e6800cc9ff064f657c.tar.gz
fpm-b6b95dcc9d6563666c1358e6800cc9ff064f657c.zip
Allow reading version number from file
Diffstat (limited to 'src')
-rw-r--r--src/fpm/cmd/new.f902
-rw-r--r--src/fpm/manifest.f902
-rw-r--r--src/fpm/manifest/package.f9030
-rw-r--r--src/fpm_filesystem.f901
4 files changed, 29 insertions, 6 deletions
diff --git a/src/fpm/cmd/new.f90 b/src/fpm/cmd/new.f90
index 773d7a7..1e92678 100644
--- a/src/fpm/cmd/new.f90
+++ b/src/fpm/cmd/new.f90
@@ -605,7 +605,7 @@ character(len=*),intent(in) :: filename
call set_value(table, "copyright", 'Copyright '//date(1:4)//', Jane Doe')
! continue building of manifest
! ...
- call new_package(package, table, error)
+ call new_package(package, table, error=error)
if (allocated(error)) stop 3
if(settings%verbose)then
call table%accept(ser)
diff --git a/src/fpm/manifest.f90 b/src/fpm/manifest.f90
index 4170b91..8c39aa6 100644
--- a/src/fpm/manifest.f90
+++ b/src/fpm/manifest.f90
@@ -113,7 +113,7 @@ contains
return
end if
- call new_package(package, table, error)
+ call new_package(package, table, dirname(file), error)
if (allocated(error)) return
if (present(apply_defaults)) then
diff --git a/src/fpm/manifest/package.f90 b/src/fpm/manifest/package.f90
index bbaa51d..666d881 100644
--- a/src/fpm/manifest/package.f90
+++ b/src/fpm/manifest/package.f90
@@ -38,6 +38,7 @@ module fpm_manifest_package
use fpm_manifest_library, only : library_config_t, new_library
use fpm_manifest_install, only: install_config_t, new_install_config
use fpm_manifest_test, only : test_config_t, new_test
+ use fpm_filesystem, only : exists, getline, join_path
use fpm_error, only : error_t, fatal_error, syntax_error
use fpm_toml, only : toml_table, toml_array, toml_key, toml_stat, get_value, &
& len
@@ -99,7 +100,7 @@ contains
!> Construct a new package configuration from a TOML data structure
- subroutine new_package(self, table, error)
+ subroutine new_package(self, table, root, error)
!> Instance of the package configuration
type(package_config_t), intent(out) :: self
@@ -107,6 +108,9 @@ contains
!> Instance of the TOML data structure
type(toml_table), intent(inout) :: table
+ !> Root directory of the manifest
+ character(len=*), intent(in), optional :: root
+
!> Error handling
type(error_t), allocatable, intent(out) :: error
@@ -116,8 +120,8 @@ contains
achar(8) // achar(9) // achar(10) // achar(12) // achar(13)
type(toml_table), pointer :: child, node
type(toml_array), pointer :: children
- character(len=:), allocatable :: version
- integer :: ii, nn, stat
+ character(len=:), allocatable :: version, version_file
+ integer :: ii, nn, stat, io
call check(table, error)
if (allocated(error)) return
@@ -157,7 +161,25 @@ contains
call get_value(table, "version", version, "0")
call new_version(self%version, version, error)
- if (allocated(error)) return
+ if (allocated(error) .and. present(root)) then
+ version_file = join_path(root, version)
+ if (exists(version_file)) then
+ deallocate(error)
+ open(file=version_file, unit=io, iostat=stat)
+ if (stat == 0) then
+ call getline(io, version, iostat=stat)
+ end if
+ if (stat == 0) then
+ close(io, iostat=stat)
+ end if
+ if (stat == 0) then
+ call new_version(self%version, version, error)
+ else
+ call fatal_error(error, "Reading version number from file '" &
+ & //version_file//"' failed")
+ end if
+ end if
+ end if
call get_value(table, "dependencies", child, requested=.false.)
if (associated(child)) then
diff --git a/src/fpm_filesystem.f90 b/src/fpm_filesystem.f90
index 486e989..e6226b4 100644
--- a/src/fpm_filesystem.f90
+++ b/src/fpm_filesystem.f90
@@ -184,6 +184,7 @@ function dirname(path) result (dir)
character(:), allocatable :: dir
dir = path(1:scan(path,'/\',back=.true.))
+ if (len_trim(dir) == 0) dir = "."
end function dirname