Skip to content

Commit 9d45cd1

Browse files
committed
override info output for dependency nodes
1 parent 47ce48d commit 9d45cd1

File tree

1 file changed

+45
-0
lines changed

1 file changed

+45
-0
lines changed

src/fpm/dependency.f90

Lines changed: 45 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -96,6 +96,8 @@ module fpm_dependency
9696
contains
9797
!> Update dependency from project manifest
9898
procedure :: register
99+
!> Print information on this instance
100+
procedure :: info
99101
end type dependency_node_t
100102

101103

@@ -224,6 +226,49 @@ subroutine new_dependency_node(self, dependency, version, proj_dir, update)
224226

225227
end subroutine new_dependency_node
226228

229+
!> Write information on instance
230+
subroutine info(self, unit, verbosity)
231+
232+
!> Instance of the dependency configuration
233+
class(dependency_node_t), intent(in) :: self
234+
235+
!> Unit for IO
236+
integer, intent(in) :: unit
237+
238+
!> Verbosity of the printout
239+
integer, intent(in), optional :: verbosity
240+
241+
integer :: pr
242+
character(:), allocatable :: ver
243+
character(len=*), parameter :: fmt = '("#", 1x, a, t30, a)'
244+
245+
if (present(verbosity)) then
246+
pr = verbosity
247+
else
248+
pr = 1
249+
end if
250+
251+
!> Call base object info
252+
call self%dependency_config_t%info(unit,pr)
253+
254+
if (allocated(self%version)) then
255+
call self%version%to_string(ver)
256+
write(unit, fmt) "- version", ver
257+
end if
258+
259+
if (allocated(self%proj_dir)) then
260+
write(unit, fmt) "- dir", self%proj_dir
261+
end if
262+
263+
if (allocated(self%revision)) then
264+
write(unit, fmt) "- revision", self%revision
265+
end if
266+
267+
write(unit, fmt) "- done", merge('YES','NO ',self%done)
268+
write(unit, fmt) "- update", merge('YES','NO ',self%update)
269+
270+
end subroutine info
271+
227272
!> Add project dependencies, each depth level after each other.
228273
!>
229274
!> We implement this algorithm in an interative rather than a recursive fashion

0 commit comments

Comments
 (0)