@@ -84,7 +84,6 @@ module Spec = struct
8484 { prog : ('path , Action.Prog.Not_found .t ) result
8585 ; args : 'path arg Array.Immutable .t
8686 ; ocamlfind_destdir : 'path
87- ; dune_exe : 'path
8887 ; pkg : Dune_pkg.Package_name .t * Loc .t
8988 ; depexts : string list
9089 }
@@ -102,16 +101,13 @@ module Spec = struct
102101 { t with
103102 args = Array.Immutable. map t.args ~f: (map_arg ~f )
104103 ; ocamlfind_destdir = f t.ocamlfind_destdir
105- ; dune_exe = f t.dune_exe
106104 ; prog = Result. map t.prog ~f
107105 }
108106 ;;
109107
110108 let is_useful_to ~memoize :_ = true
111109
112- let encode { prog; args; ocamlfind_destdir; dune_exe; pkg = _ ; depexts = _ } path _
113- : Sexp. t
114- =
110+ let encode { prog; args; ocamlfind_destdir; pkg = _ ; depexts = _ } path _ : Sexp.t =
115111 let prog : Sexp.t =
116112 match prog with
117113 | Ok p -> path p
@@ -124,11 +120,11 @@ module Spec = struct
124120 | String s -> Sexp. Atom s
125121 | Path p -> path p)))
126122 in
127- List [ List ([ prog ] @ args); path ocamlfind_destdir; path dune_exe ]
123+ List [ List ([ prog ] @ args); path ocamlfind_destdir ]
128124 ;;
129125
130126 let action
131- { prog; args; ocamlfind_destdir; dune_exe; pkg; depexts }
127+ { prog; args; ocamlfind_destdir; pkg; depexts }
132128 ~(ectx : Action.context )
133129 ~(eenv : Action.env )
134130 =
@@ -147,8 +143,9 @@ module Spec = struct
147143 let metadata = Process. create_metadata ~purpose: ectx.metadata.purpose () in
148144 let dune_folder =
149145 let bin_folder = Temp. create Dir ~prefix: " dune" ~suffix: " self-in-path" in
146+ let src = Path. of_string Sys. executable_name in
150147 let dst = Path. relative bin_folder " dune" in
151- Io. portable_symlink ~src: dune_exe ~dst ;
148+ Io. portable_symlink ~src ~dst ;
152149 Path. to_string bin_folder
153150 in
154151 let env =
191188
192189module A = Action_ext. Make (Spec )
193190
194- let action ~pkg ~depexts prog args ~ocamlfind_destdir ~ dune_exe =
195- A. action { Spec. prog; args; ocamlfind_destdir; dune_exe; pkg; depexts }
191+ let action ~pkg ~depexts prog args ~ocamlfind_destdir =
192+ A. action { Spec. prog; args; ocamlfind_destdir; pkg; depexts }
196193;;
0 commit comments