Skip to content

Commit

Permalink
store author, maintainer, copyright metadata
Browse files Browse the repository at this point in the history
  • Loading branch information
perazz committed May 18, 2023
1 parent 170070b commit ba27a3b
Showing 1 changed file with 24 additions and 0 deletions.
24 changes: 24 additions & 0 deletions src/fpm/manifest/package.f90
Original file line number Diff line number Diff line change
Expand Up @@ -82,6 +82,15 @@ module fpm_manifest_package
!> License meta data
character(len=:), allocatable :: license

!> Author meta data
character(len=:), allocatable :: author

!> Maintainer meta data
character(len=:), allocatable :: maintainer

!> Copyright meta data
character(len=:), allocatable :: copyright

!> Library meta data
type(library_config_t), allocatable :: library

Expand Down Expand Up @@ -161,6 +170,9 @@ subroutine new_package(self, table, root, error)
endif

call get_value(table, "license", self%license)
call get_value(table, "author", self%author)
call get_value(table, "maintainer", self%maintainer)
call get_value(table, "copyright", self%copyright)

if (len(self%name) <= 0) then
call syntax_error(error, "Package name must be a non-empty string")
Expand Down Expand Up @@ -532,6 +544,9 @@ logical function manifest_is_same(this,that)
if (.not.this%install==other%install) return
if (.not.this%fortran==other%fortran) return
if (.not.this%license==other%license) return
if (.not.this%author==other%author) return
if (.not.this%maintainer==other%maintainer) return
if (.not.this%copyright==other%copyright) return
if (allocated(this%library).neqv.allocated(other%library)) return
if (allocated(this%library)) then
if (.not.this%library==other%library) return
Expand Down Expand Up @@ -619,6 +634,12 @@ subroutine dump_to_toml(self, table, error)
if (allocated(error)) return
call set_string(table, "license", self%license, error, class_name)
if (allocated(error)) return
call set_string(table, "author", self%author, error, class_name)
if (allocated(error)) return
call set_string(table, "maintainer", self%maintainer, error, class_name)
if (allocated(error)) return
call set_string(table, "copyright", self%copyright, error, class_name)
if (allocated(error)) return

call add_table(table, "build", ptr, error, class_name)
if (allocated(error)) return
Expand Down Expand Up @@ -867,6 +888,9 @@ subroutine load_from_toml(self, table, error)

call get_value(table, "name", self%name)
call get_value(table, "license", self%license)
call get_value(table, "author", self%author)
call get_value(table, "maintainer", self%maintainer)
call get_value(table, "copyright", self%copyright)
call get_value(table, "version", flag)
call new_version(self%version, flag, error)
if (allocated(error)) then
Expand Down

0 comments on commit ba27a3b

Please sign in to comment.