Skip to content

Commit

Permalink
Merge branch 'main' into anmonteiro/merlin-melangelib
Browse files Browse the repository at this point in the history
  • Loading branch information
anmonteiro authored Feb 27, 2023
2 parents 310797c + 5c967b1 commit c29aebb
Show file tree
Hide file tree
Showing 6 changed files with 85 additions and 3 deletions.
3 changes: 3 additions & 0 deletions CHANGES.md
Original file line number Diff line number Diff line change
@@ -1,6 +1,9 @@
Unreleased
----------

- Do not re-render UI on every frame if the UI doesn't change (#7186, fix
#7184, @rgrinberg)

- Fix preludes not being recorded as dependencies in the `(mdx)` stanza (#7109,
fixes #7077, @emillon).

Expand Down
9 changes: 9 additions & 0 deletions src/dune_rules/install_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -155,6 +155,15 @@ end = struct
in
(sub_dir, dst)
in
let sub_dir =
match sub_dir with
| None -> lib_subdir
| Some subdir ->
Some
(match lib_subdir with
| None -> subdir
| Some lib_subdir -> Filename.concat lib_subdir subdir)
in
make_entry ?sub_dir Lib source ?dst))
in
let { Lib_config.has_native; ext_obj; _ } = lib_config in
Expand Down
16 changes: 13 additions & 3 deletions src/dune_threaded_console/dune_threaded_console.ml
Original file line number Diff line number Diff line change
Expand Up @@ -16,10 +16,12 @@ let make (module Base : S) : (module Dune_console.Backend) =
; status_line = None
; finished = false
; finish_requested = false
; dirty = true
}

let finish () =
Mutex.lock mutex;
state.dirty <- true;
state.finish_requested <- true;
while not state.finished do
Condition.wait finish_cv mutex
Expand All @@ -28,25 +30,29 @@ let make (module Base : S) : (module Dune_console.Backend) =

let print_user_message m =
Mutex.lock mutex;
state.dirty <- true;
Queue.push state.messages m;
Mutex.unlock mutex

let set_status_line sl =
Mutex.lock mutex;
state.dirty <- true;
state.status_line <- sl;
Mutex.unlock mutex

let print_if_no_status_line _msg = ()

let reset () =
Mutex.lock mutex;
state.dirty <- true;
Queue.clear state.messages;
state.status_line <- None;
Base.reset ();
Mutex.unlock mutex

let reset_flush_history () =
Mutex.lock mutex;
state.dirty <- true;
Queue.clear state.messages;
state.status_line <- None;
Base.reset_flush_history ();
Expand Down Expand Up @@ -84,9 +90,13 @@ let make (module Base : S) : (module Dune_console.Backend) =
events and sleep for the remaining time. *)
while true do
Mutex.lock mutex;
Base.render state;
let finish_requested = state.finish_requested in
if finish_requested then raise_notrace Exit;
(match state.dirty with
| false -> ()
| true ->
Base.render state;
let finish_requested = state.finish_requested in
if finish_requested then raise_notrace Exit;
state.dirty <- false);
Mutex.unlock mutex;
let now = Unix.gettimeofday () in
let elapsed = now -. !last in
Expand Down
1 change: 1 addition & 0 deletions src/dune_threaded_console/dune_threaded_console_intf.ml
Original file line number Diff line number Diff line change
Expand Up @@ -7,6 +7,7 @@ type state =
; mutable finish_requested : bool
; mutable finished : bool
; mutable status_line : User_message.Style.t Pp.t option
; mutable dirty : bool
}

(** [Threaded] is the interface for user interfaces that are rendered in a
Expand Down
1 change: 1 addition & 0 deletions test/blackbox-tests/test-cases/ctypes/dune
Original file line number Diff line number Diff line change
Expand Up @@ -32,5 +32,6 @@
lib-external-name-need-mangling
exe-pkg_config-multiple-fd
lib-return-errno
github-5561-name-mangle
exe-pkg_config)
(deps %{bin:pkg-config}))
58 changes: 58 additions & 0 deletions test/blackbox-tests/test-cases/install/dune-package-source-path.t
Original file line number Diff line number Diff line change
Expand Up @@ -43,3 +43,61 @@ Test paths on public libraries with `.` are correct
$ cat a/_build/install/default/lib/a/dune-package | grep path
(source (path A) (impl (path sub/a.ml-gen))))
(source (path Foo) (impl (path sub/foo.ml))))))

$ mkdir -p b/child
$ cat > b/dune-project <<EOF
> (lang dune 3.7)
> (package (name b))
> EOF
$ cat > b/dune <<EOF
> (include_subdirs qualified)
> (library
> (name b)
> (public_name b.sub))
> EOF
$ cat > b/foo.ml <<EOF
> let x = "foo"
> EOF
$ cat > b/child/bar.ml <<EOF
> let x = "bar"
> EOF


$ dune build b.install --root b
Entering directory 'b'
Leaving directory 'b'

$ cat b/_build/default/b.install
lib: [
"_build/install/default/lib/b/META"
"_build/install/default/lib/b/dune-package"
"_build/install/default/lib/b/sub/b.a" {"sub/b.a"}
"_build/install/default/lib/b/sub/b.cma" {"sub/b.cma"}
"_build/install/default/lib/b/sub/b.cmi" {"sub/b.cmi"}
"_build/install/default/lib/b/sub/b.cmt" {"sub/b.cmt"}
"_build/install/default/lib/b/sub/b.cmx" {"sub/b.cmx"}
"_build/install/default/lib/b/sub/b.cmxa" {"sub/b.cmxa"}
"_build/install/default/lib/b/sub/b.ml" {"sub/b.ml"}
"_build/install/default/lib/b/sub/b__Child.cmi" {"sub/b__Child.cmi"}
"_build/install/default/lib/b/sub/b__Child.cmt" {"sub/b__Child.cmt"}
"_build/install/default/lib/b/sub/b__Child.cmx" {"sub/b__Child.cmx"}
"_build/install/default/lib/b/sub/b__Child__Bar.cmi" {"sub/b__Child__Bar.cmi"}
"_build/install/default/lib/b/sub/b__Child__Bar.cmt" {"sub/b__Child__Bar.cmt"}
"_build/install/default/lib/b/sub/b__Child__Bar.cmx" {"sub/b__Child__Bar.cmx"}
"_build/install/default/lib/b/sub/b__Foo.cmi" {"sub/b__Foo.cmi"}
"_build/install/default/lib/b/sub/b__Foo.cmt" {"sub/b__Foo.cmt"}
"_build/install/default/lib/b/sub/b__Foo.cmx" {"sub/b__Foo.cmx"}
"_build/install/default/lib/b/sub/child/bar.ml" {"sub/child/bar.ml"}
"_build/install/default/lib/b/sub/child/child.ml" {"sub/child/child.ml"}
"_build/install/default/lib/b/sub/foo.ml" {"sub/foo.ml"}
]
libexec: [
"_build/install/default/lib/b/sub/b.cmxs" {"sub/b.cmxs"}
]

$ cat b/_build/install/default/lib/b/dune-package | grep path
(source (path B) (impl (path sub/b.ml-gen))))
(source (path Child Child) (impl (path sub/b__Child.ml-gen))))
(source (path Child Bar) (impl (path sub/child/bar.ml))))))
(source (path Foo) (impl (path sub/foo.ml))))))

0 comments on commit c29aebb

Please sign in to comment.