Skip to content

Commit

Permalink
Lockdir package files have .pkg extension (#8014)
Browse files Browse the repository at this point in the history
This will allow us to put a dune file in the lockdir without it
conflicting with the package file for the package "dune".

Signed-off-by: Stephen Sherratt <stephen@sherra.tt>
  • Loading branch information
gridbugs authored Jun 19, 2023
1 parent fa448e2 commit e004401
Show file tree
Hide file tree
Showing 18 changed files with 53 additions and 30 deletions.
24 changes: 19 additions & 5 deletions src/dune_pkg/lock_dir.ml
Original file line number Diff line number Diff line change
Expand Up @@ -262,11 +262,25 @@ let encode_metadata t =
; Dune_lang.Syntax.Version.encode t.version
]

module Package_filename = struct
type t = Filename.t

let file_extension = ".pkg"

let of_package_name package_name =
Package_name.to_string package_name ^ file_extension

let to_package_name package_filename =
if String.equal (Filename.extension package_filename) file_extension then
Ok (Filename.chop_extension package_filename |> Package_name.of_string)
else Error `Bad_extension
end

let file_contents_by_path t =
(metadata, [ encode_metadata t ])
:: (Package_name.Map.to_list t.packages
|> List.map ~f:(fun (name, pkg) ->
(Package_name.to_string name, Pkg.encode pkg)))
(Package_filename.of_package_name name, Pkg.encode pkg)))

(* Checks whether path refers to a valid lock directory and returns a value
indicating the status of the lock directory. [Ok _] values indicate that
Expand Down Expand Up @@ -352,7 +366,7 @@ let load_pkg ~parser_context ~lock_dir_path package_name =
Result.try_with (fun () ->
let source_path =
Path.Source.relative lock_dir_path
(Package_name.to_string package_name)
(Package_filename.of_package_name package_name)
in
let pkg_string = Io.read_file (Path.source source_path) in
let ast =
Expand Down Expand Up @@ -387,12 +401,12 @@ let read_disk ~lock_dir_path =
Sys.readdir (Path.Source.to_string lock_dir_path)
|> Array.to_list
|> List.filter_map ~f:(fun filename ->
if Filename.equal filename metadata then None
else
match Package_filename.to_package_name filename with
| Error `Bad_extension -> None
| Ok package_name ->
let package_path = Path.Source.relative lock_dir_path filename in
if Path.is_directory (Path.source package_path) then None
else
let package_name = Package_name.of_string filename in
Some
( load_pkg ~parser_context ~lock_dir_path package_name
>>| fun pkg -> (package_name, pkg) ))
Expand Down
8 changes: 8 additions & 0 deletions src/dune_pkg/lock_dir.mli
Original file line number Diff line number Diff line change
Expand Up @@ -53,6 +53,14 @@ val metadata : Filename.t

module Metadata : Dune_sexp.Versioned_file.S with type data := unit

module Package_filename : sig
type t = Filename.t

val of_package_name : Package_name.t -> t

val to_package_name : t -> (Package_name.t, [ `Bad_extension ]) result
end

val write_disk : lock_dir_path:Path.Source.t -> t -> unit

val read_disk : lock_dir_path:Path.Source.t -> t Or_exn.t
9 changes: 5 additions & 4 deletions src/dune_rules/pkg_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -89,17 +89,18 @@ module Lock_dir = struct
Fs_cache.Dir_contents.to_list content
|> List.filter_map ~f:(fun (name, (kind : Unix.file_kind)) ->
match kind with
| S_REG when name <> metadata ->
let name = Package.Name.of_string name in
Some name
| S_REG ->
Lock_dir.Package_filename.to_package_name name
|> Result.to_option
| _ ->
(* TODO *)
None)
|> Memo.parallel_map ~f:(fun name ->
let+ package =
let+ sexp =
let path =
Package.Name.to_string name |> Path.Source.relative path
Lock_dir.Package_filename.of_package_name name
|> Path.Source.relative path
in
Fs_memo.with_lexbuf_from_file (In_source_dir path)
~f:(Dune_sexp.Parser.parse ~mode:Many)
Expand Down
4 changes: 2 additions & 2 deletions test/blackbox-tests/test-cases/pkg/default-exported-env.t
Original file line number Diff line number Diff line change
Expand Up @@ -5,9 +5,9 @@ Some environment variables are automatically exported by packages:
> (lang package 0.1)
> EOF

$ touch dune.lock/test
$ touch dune.lock/test.pkg

$ cat >dune.lock/usetest <<'EOF'
$ cat >dune.lock/usetest.pkg <<'EOF'
> (deps test)
> (build
> (system "\| echo MANPATH=$MANPATH
Expand Down
4 changes: 2 additions & 2 deletions test/blackbox-tests/test-cases/pkg/exported-env.t
Original file line number Diff line number Diff line change
Expand Up @@ -4,15 +4,15 @@ Packages can export environment variables
$ cat >dune.lock/lock.dune <<EOF
> (lang package 0.1)
> EOF
$ cat >dune.lock/test <<EOF
$ cat >dune.lock/test.pkg <<EOF
> (exported_env
> (= FOO bar)
> (= BAR xxx)
> (+= BAR yyy)
> (:= BAR zzz))
> EOF

$ cat >dune.lock/usetest <<'EOF'
$ cat >dune.lock/usetest.pkg <<'EOF'
> (deps test)
> (version 1.2.3)
> (build
Expand Down
2 changes: 1 addition & 1 deletion test/blackbox-tests/test-cases/pkg/external-source.t
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,7 @@ Test that can fetch the sources from an external dir
$ cat >dune.lock/lock.dune <<EOF
> (lang package 0.1)
> EOF
$ cat >dune.lock/test <<EOF
$ cat >dune.lock/test.pkg <<EOF
> (source (copy $PWD/foo))
> (build
> (progn
Expand Down
2 changes: 1 addition & 1 deletion test/blackbox-tests/test-cases/pkg/git-source.t
Original file line number Diff line number Diff line change
Expand Up @@ -15,7 +15,7 @@ Test fetching from git
$ cat >dune.lock/lock.dune <<EOF
> (lang package 0.1)
> EOF
$ cat >dune.lock/test <<EOF
$ cat >dune.lock/test.pkg <<EOF
> (source (fetch (url "git+file://$MYGITREPO")))
> (build (run cat foo))
> EOF
Expand Down
2 changes: 1 addition & 1 deletion test/blackbox-tests/test-cases/pkg/install-action-dirs.t
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,7 @@ Install actions should have the switch directory prepared:
$ cat >dune.lock/lock.dune <<EOF
> (lang package 0.1)
> EOF
$ cat >dune.lock/test <<'EOF'
$ cat >dune.lock/test.pkg <<'EOF'
> (install (system "find %{prefix} | sort"))
> EOF

Expand Down
2 changes: 1 addition & 1 deletion test/blackbox-tests/test-cases/pkg/install-action.t
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,7 @@ Testing install actions
$ cat >dune.lock/lock.dune <<EOF
> (lang package 0.1)
> EOF
$ cat >dune.lock/test <<'EOF'
$ cat >dune.lock/test.pkg <<'EOF'
> (install (system "echo foobar; mkdir -p %{lib}; touch %{lib}/xxx"))
> EOF

Expand Down
2 changes: 1 addition & 1 deletion test/blackbox-tests/test-cases/pkg/install-missing-entry.t
Original file line number Diff line number Diff line change
Expand Up @@ -5,7 +5,7 @@ Test missing entries in the .install file
> (lang package 0.1)
> EOF
$ lockfile() {
> cat >dune.lock/test <<EOF
> cat >dune.lock/test.pkg <<EOF
> (build
> (system "echo 'lib: [ \"$1\" ]' > test.install"))
> EOF
Expand Down
4 changes: 2 additions & 2 deletions test/blackbox-tests/test-cases/pkg/installed-binary.t
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,7 @@ Test that installed binaries are visible in dependent packages
$ cat >dune.lock/lock.dune <<EOF
> (lang package 0.1)
> EOF
$ cat >dune.lock/test <<EOF
$ cat >dune.lock/test.pkg <<EOF
> (build
> (system "\| echo "#!/bin/sh\necho from test package" > foo;
> "\| chmod +x foo;
Expand All @@ -18,7 +18,7 @@ Test that installed binaries are visible in dependent packages
> ))
> EOF

$ cat >dune.lock/usetest <<EOF
$ cat >dune.lock/usetest.pkg <<EOF
> (deps test)
> (build
> (progn
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -21,19 +21,19 @@ Run the solver and generate a lock directory.
Print the name and contents of each file in the lock directory separated by
"---", sorting by filename for consistency.
$ find dune.lock -type f | sort | xargs -I{} sh -c "printf '{}:\n\n'; cat {}; printf '\n\n---\n\n'"
dune.lock/bar:
dune.lock/bar.pkg:

(version 0.4.0)

---

dune.lock/baz:
dune.lock/baz.pkg:

(version 0.1.0)

---

dune.lock/foo:
dune.lock/foo.pkg:

(version 0.0.1)
(deps baz bar)
Expand Down
2 changes: 1 addition & 1 deletion test/blackbox-tests/test-cases/pkg/package-files.t
Original file line number Diff line number Diff line change
Expand Up @@ -8,7 +8,7 @@ Additional files overlaid on top of the source can be found in the
$ cat >dune.lock/lock.dune <<EOF
> (lang package 0.1)
> EOF
$ cat >dune.lock/test <<EOF
$ cat >dune.lock/test.pkg <<EOF
> (source
> (copy $PWD/test-source))
> (build
Expand Down
2 changes: 1 addition & 1 deletion test/blackbox-tests/test-cases/pkg/patch.t
Original file line number Diff line number Diff line change
Expand Up @@ -5,7 +5,7 @@ Applying patches
$ cat >dune.lock/lock.dune <<EOF
> (lang package 0.1)
> EOF
$ cat >dune.lock/test <<EOF
$ cat >dune.lock/test.pkg <<EOF
> (source (copy $PWD/test-source))
> (build
> (progn
Expand Down
2 changes: 1 addition & 1 deletion test/blackbox-tests/test-cases/pkg/per-context.t
Original file line number Diff line number Diff line change
Expand Up @@ -17,7 +17,7 @@ TODO: versioning will be added once this feature is stable
$ cat >foo.lock/lock.dune <<EOF
> (lang package 0.1)
> EOF
$ cat >foo.lock/test <<EOF
$ cat >foo.lock/test.pkg <<EOF
> (build
> (system "echo building from %{context_name}"))
> EOF
Expand Down
2 changes: 1 addition & 1 deletion test/blackbox-tests/test-cases/pkg/simple-lock.t
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,7 @@ Test that we run the build command
$ cat >dune.lock/lock.dune <<EOF
> (lang package 0.1)
> EOF
$ cat >dune.lock/test <<EOF
$ cat >dune.lock/test.pkg <<EOF
> (build
> (progn
> (run mkdir -p %{prefix}/bin)
Expand Down
4 changes: 2 additions & 2 deletions test/blackbox-tests/test-cases/pkg/variables.t
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,7 @@ Test that we can set variables
$ cat >dune.lock/lock.dune <<EOF
> (lang package 0.1)
> EOF
$ cat >dune.lock/test <<EOF
$ cat >dune.lock/test.pkg <<EOF
> (build
> (system "\| cat >test.config <<EOF
> "\| opam-version: "2.0"
Expand All @@ -17,7 +17,7 @@ Test that we can set variables
> ))
> EOF

$ cat >dune.lock/usetest <<EOF
$ cat >dune.lock/usetest.pkg <<EOF
> (deps test)
> (build
> (progn
Expand Down
2 changes: 1 addition & 1 deletion test/blackbox-tests/test-cases/pkg/withenv.t
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,7 @@ Setting environment variables in actions
$ cat >dune.lock/lock.dune <<EOF
> (lang package 0.1)
> EOF
$ cat >dune.lock/test <<'EOF'
$ cat >dune.lock/test.pkg <<'EOF'
> (build
> (withenv
> ((= FOO myfoo)
Expand Down

0 comments on commit e004401

Please sign in to comment.