Skip to content

Commit

Permalink
Changed init config
Browse files Browse the repository at this point in the history
Signed-off-by: Athish Pranav D <athishanna@gmail.com>
  • Loading branch information
Athishpranav2003 committed Sep 16, 2024
1 parent 5216503 commit b3eeb4f
Show file tree
Hide file tree
Showing 2 changed files with 26 additions and 35 deletions.
44 changes: 24 additions & 20 deletions bin/exec.ml
Original file line number Diff line number Diff line change
Expand Up @@ -227,26 +227,22 @@ let get_path_and_build_if_necessary sctx ~no_rebuild ~dir ~prog =
| Some path -> build_prog ~no_rebuild ~prog path
| None -> not_found ~dir ~prog)
| Absolute ->
let path = Path.of_string prog in
if Path.exists path
then Memo.return path
else (
let path = Path.relative_to_source_in_build_or_external ~dir prog in
Build_system.file_exists path
>>= (function
| true -> Memo.return (Some path)
| false ->
if not (Filename.check_suffix prog ".exe")
then Memo.return None
else (
let path = Path.extend_basename path ~suffix:".exe" in
Build_system.file_exists path
>>| function
| true -> Some path
| false -> None))
>>= function
| Some path -> Memo.return path
| None -> not_found ~dir ~prog)
(match
let path = Path.of_string prog in
if Path.exists path
then Some path
else (
let path = Path.extend_basename path ~suffix:Bin.exe in
if Path.exists path
then Some path
else (
let path =
Path.relative_to_source_in_build_or_external ~dir (Filename.basename prog)
in
Option.some_if (Path.exists path) path))
with
| Some path -> build_prog ~no_rebuild ~prog path
| None -> not_found ~dir ~prog)
;;

module Exec_context = struct
Expand Down Expand Up @@ -344,6 +340,14 @@ let term =
(* TODO we should make sure to finalize the current backend before exiting dune.
For watch mode, we should finalize the backend and then restart it in between
runs. *)
let builder =
match prog with
| Cmd_arg.Terminal prog ->
if String.starts_with ~prefix:"/" prog
then Common.Builder.set_root builder (Filename.dirname prog)
else builder
| _ -> builder
in
let common, config = Common.init builder in
let exec_context = Exec_context.init ~common ~context ~no_rebuild ~prog ~args in
let f =
Expand Down
17 changes: 2 additions & 15 deletions otherlibs/stdune/src/path.ml
Original file line number Diff line number Diff line change
Expand Up @@ -1204,28 +1204,15 @@ let explode_exn t =
| None -> Code_error.raise "Path.explode_exn" [ "path", to_dyn t ]
;;

let rec relative_to_source_in_build_or_external ?error_loc ~dir s =
let relative_to_source_in_build_or_external ?error_loc ~dir s =
match Build.extract_build_context dir with
| None -> relative ?error_loc (In_build_dir dir) s
| Some (bctxt, source) ->
let path = relative ?error_loc (In_source_tree source) s in
(match path with
| In_source_tree s ->
In_build_dir (Build.relative (Build.of_string bctxt) (Source0.to_string s))
| In_build_dir _ -> path
| External _ ->
let cwd =
to_absolute_filename
(of_filename_relative_to_initial_cwd Filename.current_dir_name)
in
let cwd_len = String.length cwd in
if String.starts_with ~prefix:cwd s
then
relative_to_source_in_build_or_external
?error_loc
~dir
(String.sub s ~pos:(cwd_len + 1) ~len:(String.length s - cwd_len - 1))
else path)
| In_build_dir _ | External _ -> path)
;;

let exists t =
Expand Down

0 comments on commit b3eeb4f

Please sign in to comment.