Skip to content

Commit

Permalink
Clean the code and fix the tests output
Browse files Browse the repository at this point in the history
Signed-off-by: Alpha DIALLO <moyodiallo@gmail.com>
  • Loading branch information
moyodiallo committed Feb 2, 2023
1 parent 03df1d7 commit d13411b
Show file tree
Hide file tree
Showing 4 changed files with 42 additions and 27 deletions.
21 changes: 7 additions & 14 deletions bin/describe.ml
Original file line number Diff line number Diff line change
Expand Up @@ -627,22 +627,15 @@ module External_lib_deps = struct

let to_dyn t =
let open Dyn in
let names =
if t.kind = Kind.Library then ("name", String (List.hd t.names))
else ("names", (list string) t.names)
in
let package =
match t.package with
| Some p ->
[ ("package", String (p |> Package.name |> Package.Name.to_string)) ]
| None -> []
in
let record =
record
([ names ] @ package
@ [ ("source_dir", String (Path.Source.to_string t.dir))
; ("external_deps", list external_lib_dep_to_dyn t.external_deps)
])
[ ("names", (list string) t.names)
; ( "package"
, option Package.Name.to_dyn (Option.map ~f:Package.name t.package)
)
; ("source_dir", String (Path.Source.to_string t.dir))
; ("external_deps", list external_lib_dep_to_dyn t.external_deps)
]
in
Variant (Kind.to_string t.kind, [ record ])
end
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -4,5 +4,13 @@ print only the external libraries by dir.

$ dune describe external-lib-deps
(default
((. ((a required)))
(lib ((a required)))))
((library
((names (foo))
(package ())
(source_dir .)
(external_deps ((a required)))))
(library
((names (inter_lib))
(package ())
(source_dir lib)
(external_deps ((a required)))))))
29 changes: 19 additions & 10 deletions test/blackbox-tests/test-cases/external-lib-deps/simple-pps.t/run.t
Original file line number Diff line number Diff line change
Expand Up @@ -2,13 +2,22 @@ Expected: To get all required and pps packages

$ dune describe external-lib-deps
(default
((.
((a________ required)
(b________ required)
(c________ required)
(d________ required)
(e________ required)
(f________ required)
(h________ required)
(i________ required)
(j________ required)))))
((library
((names (foo))
(package ())
(source_dir .)
(external_deps
((a________ required)
(b________ required)
(c________ required)
(f________ required)
(e________ required)
(d________ required)))))
(executables
((names (prog))
(package ())
(source_dir .)
(external_deps
((h________ required)
(i________ required)
(j________ required)))))))
Original file line number Diff line number Diff line change
Expand Up @@ -8,4 +8,9 @@ external library dependencies of a simple project
> (libraries base doesnotexist.foo))
> EOF
$ dune describe external-lib-deps
(default ((. ((base required) (doesnotexist.foo required)))))
(default
((library
((names (dummypkg))
(package (dummypkg))
(source_dir .)
(external_deps ((base required) (doesnotexist.foo required)))))))

0 comments on commit d13411b

Please sign in to comment.