Skip to content
This commit does not belong to any branch on this repository, and may belong to a fork outside of the repository.

Commit 8aa8f09

Browse files
committedApr 22, 2021
Fix #3619
When the repository is empty, substitute version with dummy values Signed-off-by: Rudi Grinberg <me@rgrinberg.com>
1 parent 01f9ae9 commit 8aa8f09

File tree

8 files changed

+135
-72
lines changed

8 files changed

+135
-72
lines changed
 

‎CHANGES.md

+2
Original file line numberDiff line numberDiff line change
@@ -3,6 +3,8 @@ Unreleased
33

44
- Allow multiple cinaps stanzas in the same directory (#4460, @rgrinberg)
55

6+
- Fix `$ dune subst` in empty git repositories (#4441, fixes #3619, @rgrinberg)
7+
68
- Improve interpretation of ansi escape sequence when spawning processes (#4408,
79
fixes #2665, @rgrinberg)
810

‎bin/install_uninstall.ml

+9-5
Original file line numberDiff line numberDiff line change
@@ -158,12 +158,16 @@ module File_ops_real (W : Workspace) : File_operations = struct
158158
| Some package -> Memo.Build.run (get_vcs (Package.dir package)))
159159
>>= function
160160
| None -> plain_copy ()
161-
| Some vcs ->
161+
| Some vcs -> (
162162
let open Fiber.O in
163-
let+ version = Memo.Build.run (Dune_engine.Vcs.describe vcs) in
164-
let ppf = Format.formatter_of_out_channel oc in
165-
print ppf ~version;
166-
Format.pp_print_flush ppf ())
163+
let* version = Memo.Build.run (Dune_engine.Vcs.describe vcs) in
164+
match version with
165+
| None -> plain_copy ()
166+
| Some version ->
167+
let ppf = Format.formatter_of_out_channel oc in
168+
print ppf ~version;
169+
Format.pp_print_flush ppf ();
170+
Fiber.return ()))
167171

168172
let process_meta ic =
169173
let lb = Lexing.from_channel ic in

‎src/dune_engine/vcs.ml

+59-13
Original file line numberDiff line numberDiff line change
@@ -79,9 +79,21 @@ let run t args =
7979
in
8080
String.trim s
8181

82-
let run_zero_separated t args =
83-
Process.run_capture_zero_separated Strict (prog t) args ~dir:t.root
84-
~env:Env.initial
82+
let git_accept () =
83+
Process.Accept (Predicate_lang.union [ Element 0; Element 128 ])
84+
85+
let run_git t args =
86+
let res =
87+
Process.run_capture (git_accept ()) (prog t) args ~dir:t.root
88+
~env:Env.initial
89+
~stderr_to:(Process.Io.file Config.dev_null Out)
90+
in
91+
let open Fiber.O in
92+
let+ res = res in
93+
match res with
94+
| Ok s -> Some (String.trim s)
95+
| Error 128 -> None
96+
| Error _ -> assert false
8597

8698
let hg_describe t =
8799
let open Fiber.O in
@@ -114,25 +126,57 @@ let make_fun name ~output ~doc ~git ~hg =
114126
in
115127
Staged.stage (Memo.exec memo)
116128

129+
module Option_output (S : sig
130+
type t
131+
132+
val to_dyn : t -> Dyn.t
133+
end) =
134+
struct
135+
type t = S.t option
136+
137+
let to_dyn t = Dyn.Encoder.option S.to_dyn t
138+
end
139+
117140
let describe =
118141
Staged.unstage
119142
@@ make_fun "vcs-describe"
120143
~doc:"Obtain a nice description of the tip from the vcs"
121-
~output:(Simple (module String))
122-
~git:(fun t -> run t [ "describe"; "--always"; "--dirty" ])
123-
~hg:hg_describe
144+
~output:(Simple (module Option_output (String)))
145+
~git:(fun t -> run_git t [ "describe"; "--always"; "--dirty" ])
146+
~hg:(fun x ->
147+
let open Fiber.O in
148+
let+ res = hg_describe x in
149+
Some res)
124150

125151
let commit_id =
126152
Staged.unstage
127153
@@ make_fun "vcs-commit-id" ~doc:"The hash of the head commit"
128-
~output:(Simple (module String))
129-
~git:(fun t -> run t [ "rev-parse"; "HEAD" ])
130-
~hg:(fun t -> run t [ "id"; "-i" ])
154+
~output:(Simple (module Option_output (String)))
155+
~git:(fun t -> run_git t [ "rev-parse"; "HEAD" ])
156+
~hg:(fun t ->
157+
let open Fiber.O in
158+
let+ res = run t [ "id"; "-i" ] in
159+
Some res)
131160

132161
let files =
133-
let f args t =
162+
let run_zero_separated_hg t args =
163+
Process.run_capture_zero_separated Strict (prog t) args ~dir:t.root
164+
~env:Env.initial
165+
in
166+
let run_zero_separated_git t args =
167+
let open Fiber.O in
168+
let+ res =
169+
Process.run_capture_zero_separated (git_accept ()) (prog t) args
170+
~dir:t.root ~env:Env.initial
171+
in
172+
match res with
173+
| Ok s -> s
174+
| Error 128 -> []
175+
| Error _ -> assert false
176+
in
177+
let f run args t =
134178
let open Fiber.O in
135-
let+ l = run_zero_separated t args in
179+
let+ l = run t args in
136180
List.map l ~f:Path.in_source
137181
in
138182
Staged.unstage
@@ -144,5 +188,7 @@ let files =
144188

145189
let to_dyn = Dyn.Encoder.list Path.to_dyn
146190
end))
147-
~git:(f [ "ls-tree"; "-z"; "-r"; "--name-only"; "HEAD" ])
148-
~hg:(f [ "files"; "-0" ])
191+
~git:
192+
(f run_zero_separated_git
193+
[ "ls-tree"; "-z"; "-r"; "--name-only"; "HEAD" ])
194+
~hg:(f run_zero_separated_hg [ "files"; "-0" ])

‎src/dune_engine/vcs.mli

+2-2
Original file line numberDiff line numberDiff line change
@@ -22,10 +22,10 @@ val equal : t -> t -> bool
2222
val to_dyn : t -> Dyn.t
2323

2424
(** Nice description of the current tip *)
25-
val describe : t -> string Memo.Build.t
25+
val describe : t -> string option Memo.Build.t
2626

2727
(** String uniquely identifying the current head commit *)
28-
val commit_id : t -> string Memo.Build.t
28+
val commit_id : t -> string option Memo.Build.t
2929

3030
(** List of files committed in the repo *)
3131
val files : t -> Path.t list Memo.Build.t

‎src/dune_rules/artifact_substitution.ml

+3-1
Original file line numberDiff line numberDiff line change
@@ -135,7 +135,9 @@ let eval t ~conf =
135135
(let open Memo.Build.O in
136136
conf.get_vcs p >>= function
137137
| None -> Memo.Build.return ""
138-
| Some vcs -> Vcs.describe vcs)
138+
| Some vcs ->
139+
let+ res = Vcs.describe vcs in
140+
Option.value res ~default:"")
139141
| Location (name, lib_name) ->
140142
Fiber.return (relocatable (conf.get_location name lib_name))
141143
| Configpath d ->

‎src/dune_rules/watermarks.ml

+56-44
Original file line numberDiff line numberDiff line change
@@ -180,48 +180,51 @@ module Dune_project = struct
180180

181181
let subst t ~map ~version =
182182
let s =
183-
let replace_text start_ofs stop_ofs repl =
184-
sprintf "%s%s%s"
185-
(String.sub t.contents ~pos:0 ~len:start_ofs)
186-
repl
187-
(String.sub t.contents ~pos:stop_ofs
188-
~len:(String.length t.contents - stop_ofs))
189-
in
190-
match t.version with
191-
| Some v ->
192-
(* There is a [version] field, overwrite its argument *)
193-
replace_text v.loc_of_arg.start.pos_cnum v.loc_of_arg.stop.pos_cnum
194-
(Dune_lang.to_string (Dune_lang.atom_or_quoted_string version))
195-
| None ->
196-
let version_field =
197-
Dune_lang.to_string
198-
(List
199-
[ Dune_lang.atom "version"
200-
; Dune_lang.atom_or_quoted_string version
201-
])
202-
^ "\n"
203-
in
204-
let ofs =
205-
ref
206-
(match t.name with
207-
| Some { loc; _ } ->
208-
(* There is no [version] field but there is a [name] one, add the
209-
version after it *)
210-
loc.stop.pos_cnum
211-
| None ->
212-
(* If all else fails, add the [version] field after the first line
213-
of the file *)
214-
0)
183+
match version with
184+
| None -> t.contents
185+
| Some version -> (
186+
let replace_text start_ofs stop_ofs repl =
187+
sprintf "%s%s%s"
188+
(String.sub t.contents ~pos:0 ~len:start_ofs)
189+
repl
190+
(String.sub t.contents ~pos:stop_ofs
191+
~len:(String.length t.contents - stop_ofs))
215192
in
216-
let len = String.length t.contents in
217-
while !ofs < len && t.contents.[!ofs] <> '\n' do
218-
incr ofs
219-
done;
220-
if !ofs < len && t.contents.[!ofs] = '\n' then (
221-
incr ofs;
222-
replace_text !ofs !ofs version_field
223-
) else
224-
replace_text !ofs !ofs ("\n" ^ version_field)
193+
match t.version with
194+
| Some v ->
195+
(* There is a [version] field, overwrite its argument *)
196+
replace_text v.loc_of_arg.start.pos_cnum v.loc_of_arg.stop.pos_cnum
197+
(Dune_lang.to_string (Dune_lang.atom_or_quoted_string version))
198+
| None ->
199+
let version_field =
200+
Dune_lang.to_string
201+
(List
202+
[ Dune_lang.atom "version"
203+
; Dune_lang.atom_or_quoted_string version
204+
])
205+
^ "\n"
206+
in
207+
let ofs =
208+
ref
209+
(match t.name with
210+
| Some { loc; _ } ->
211+
(* There is no [version] field but there is a [name] one, add
212+
the version after it *)
213+
loc.stop.pos_cnum
214+
| None ->
215+
(* If all else fails, add the [version] field after the first
216+
line of the file *)
217+
0)
218+
in
219+
let len = String.length t.contents in
220+
while !ofs < len && t.contents.[!ofs] <> '\n' do
221+
incr ofs
222+
done;
223+
if !ofs < len && t.contents.[!ofs] = '\n' then (
224+
incr ofs;
225+
replace_text !ofs !ofs version_field
226+
) else
227+
replace_text !ofs !ofs ("\n" ^ version_field))
225228
in
226229
let s = Option.value (subst_string s ~map filename) ~default:s in
227230
if s <> t.contents then Io.write_file filename s
@@ -230,6 +233,8 @@ end
230233
let make_watermark_map ~commit ~version ~dune_project ~info =
231234
let dune_project = Dune_project.project dune_project in
232235
let version_num =
236+
let open Option.O in
237+
let+ version = version in
233238
Option.value ~default:version (String.drop_prefix version ~prefix:"v")
234239
in
235240
let name = Dune_project.name dune_project in
@@ -250,11 +255,18 @@ let make_watermark_map ~commit ~version ~dune_project ~info =
250255
| Some (Package.Source_kind.Url url) -> Ok url
251256
| None -> Error (sprintf "variable dev-repo not found in dune-project file")
252257
in
258+
let make_version = function
259+
| Some s -> Ok s
260+
| None -> Error "repository does not contain any version information"
261+
in
253262
String.Map.of_list_exn
254263
[ ("NAME", Ok (Dune_project.Name.to_string_hum name))
255-
; ("VERSION", Ok version)
256-
; ("VERSION_NUM", Ok version_num)
257-
; ("VCS_COMMIT_ID", Ok commit)
264+
; ("VERSION", make_version version)
265+
; ("VERSION_NUM", make_version version_num)
266+
; ( "VCS_COMMIT_ID"
267+
, match commit with
268+
| None -> Error "repositroy does not contain any commits"
269+
| Some s -> Ok s )
258270
; ( "PKG_MAINTAINER"
259271
, make_separated "maintainer" ", " @@ Package.Info.maintainers info )
260272
; ("PKG_AUTHORS", make_separated "authors" ", " @@ Package.Info.authors info)

‎test/blackbox-tests/test-cases/github4429.t/run.t ‎test/blackbox-tests/test-cases/github4429.t

+2-6
Original file line numberDiff line numberDiff line change
@@ -15,10 +15,6 @@ Create a repository with no HEAD commit:
1515
> (promote (until-clean)))
1616
> EOF
1717

18-
At the moment Dune fails, which is bad:
19-
20-
$ dune exec ./main.exe 2>&1 | sed 's/.*\/git/{{ git }}/; s/> .*.output/> {{ output_file }}/g'
21-
git (internal) (exit 128)
22-
{{ git }} describe --always --dirty > {{ output_file }}
23-
fatal: bad revision 'HEAD'
18+
Dune handles this gracefully since #4441
2419

20+
$ dune exec ./main.exe 2>&1

‎test/expect-tests/vcs_tests.ml

+2-1
Original file line numberDiff line numberDiff line change
@@ -77,7 +77,8 @@ let run_action (vcs : Vcs.t) action =
7777
| Hg when not has_hg -> { vcs with kind = Git }
7878
| _ -> vcs
7979
in
80-
Memo.Build.run (Vcs.describe vcs) >>| fun s ->
80+
let+ s = Memo.Build.run (Vcs.describe vcs) in
81+
let s = Option.value s ~default:"n/a" in
8182
let processed =
8283
String.split s ~on:'-'
8384
|> List.map ~f:(fun s ->

0 commit comments

Comments
 (0)
Please sign in to comment.