@@ -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,14 +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 _
110+ let encode { prog; args; ocamlfind_destdir; pkg = _ ; depexts = _ } path _
113111 : Sexp. t
114112 =
115113 let prog : Sexp.t =
@@ -124,11 +122,11 @@ module Spec = struct
124122 | String s -> Sexp. Atom s
125123 | Path p -> path p)))
126124 in
127- List [ List ([ prog ] @ args); path ocamlfind_destdir; path dune_exe ]
125+ List [ List ([ prog ] @ args); path ocamlfind_destdir ]
128126 ;;
129127
130128 let action
131- { prog; args; ocamlfind_destdir; dune_exe; pkg; depexts }
129+ { prog; args; ocamlfind_destdir; pkg; depexts }
132130 ~(ectx : Action.context )
133131 ~(eenv : Action.env )
134132 =
@@ -147,8 +145,9 @@ module Spec = struct
147145 let metadata = Process. create_metadata ~purpose: ectx.metadata.purpose () in
148146 let dune_folder =
149147 let bin_folder = Temp. create Dir ~prefix: " dune" ~suffix: " self-in-path" in
148+ let src = Path. of_string Sys. executable_name in
150149 let dst = Path. relative bin_folder " dune" in
151- Io. portable_symlink ~src: dune_exe ~dst ;
150+ Io. portable_symlink ~src ~dst ;
152151 Path. to_string bin_folder
153152 in
154153 let env =
191190
192191module A = Action_ext. Make (Spec )
193192
194- let action ~pkg ~depexts prog args ~ocamlfind_destdir ~ dune_exe =
195- A. action { Spec. prog; args; ocamlfind_destdir; dune_exe; pkg; depexts }
193+ let action ~pkg ~depexts prog args ~ocamlfind_destdir =
194+ A. action { Spec. prog; args; ocamlfind_destdir; pkg; depexts }
196195;;
0 commit comments