Skip to content

Commit

Permalink
feature: Haiku support
Browse files Browse the repository at this point in the history
Signed-off-by: Ali Caglayan <[email protected]>
  • Loading branch information
Alizter committed Sep 29, 2023
1 parent 5d6a2bd commit bd39351
Show file tree
Hide file tree
Showing 14 changed files with 48 additions and 7 deletions.
1 change: 1 addition & 0 deletions boot/libs.ml
Original file line number Diff line number Diff line change
Expand Up @@ -110,4 +110,5 @@ let link_flags =
[ "-cclib"; "-lshell32"; "-cclib"; "-lole32"; "-cclib"; "-luuid" ])
; ("mingw64",
[ "-cclib"; "-lshell32"; "-cclib"; "-lole32"; "-cclib"; "-luuid" ])
; ("beos", [ "-cclib"; "-lbsd" ])
]
1 change: 1 addition & 0 deletions doc/changes/haiku.md
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
- Dune can now be built and installed on Haiku (#8795, fix #8551, @Alizter)
2 changes: 2 additions & 0 deletions otherlibs/stdune/src/dune
Original file line number Diff line number Diff line change
Expand Up @@ -10,6 +10,8 @@
(re_export dyn)
(re_export pp)
(re_export dune_filesystem_stubs))
(library_flags
(:include flags/sexp))
(foreign_stubs
(language c)
(names wait4_stubs platform_stubs copyfile_stubs signal_stubs))
Expand Down
10 changes: 10 additions & 0 deletions otherlibs/stdune/src/flags/dune
Original file line number Diff line number Diff line change
@@ -0,0 +1,10 @@
(executable
(name gen_flags))

(rule
(deps
(:script gen_flags.ml))
(action
(with-stdout-to
sexp
(run ./gen_flags.exe %{system}))))
1 change: 1 addition & 0 deletions otherlibs/stdune/src/flags/gen_flags.ml
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
let () = Printf.printf @@ if Sys.argv.(1) = "beos" then {|(-cclib -lbsd)|} else "()"
5 changes: 5 additions & 0 deletions otherlibs/stdune/src/platform.ml
Original file line number Diff line number Diff line change
Expand Up @@ -7,6 +7,7 @@ module OS = struct
| FreeBSD
| NetBSD
| OpenBSD
| Haiku
| Other

let equal = Poly.equal
Expand All @@ -15,6 +16,7 @@ module OS = struct
external is_freebsd : unit -> bool = "stdune_is_freebsd"
external is_netbsd : unit -> bool = "stdune_is_netbsd"
external is_openbsd : unit -> bool = "stdune_is_openbsd"
external is_haiku : unit -> bool = "stdune_is_haiku"

let to_dyn : t -> Dyn.t = function
| Windows -> Dyn.variant "Windows" []
Expand All @@ -23,6 +25,7 @@ module OS = struct
| FreeBSD -> Dyn.variant "FreeBSD" []
| NetBSD -> Dyn.variant "NetBSD" []
| OpenBSD -> Dyn.variant "OpenBSD" []
| Haiku -> Dyn.variant "Haiku" []
| Other -> Dyn.variant "Other" []
;;

Expand Down Expand Up @@ -52,6 +55,8 @@ module OS = struct
then NetBSD
else if is_openbsd ()
then OpenBSD
else if is_haiku ()
then Haiku
else Other
;;
end
Expand Down
1 change: 1 addition & 0 deletions otherlibs/stdune/src/platform.mli
Original file line number Diff line number Diff line change
Expand Up @@ -10,6 +10,7 @@ module OS : sig
| FreeBSD
| NetBSD
| OpenBSD
| Haiku
| Other

(** [value] is the current os we're running on. *)
Expand Down
15 changes: 12 additions & 3 deletions otherlibs/stdune/src/platform_stubs.c
Original file line number Diff line number Diff line change
Expand Up @@ -11,7 +11,7 @@ CAMLprim value stdune_is_darwin(value v_unit) {
}

CAMLprim value stdune_is_freebsd(value v_unit) {
CAMLparam1(v_unit);
CAMLparam1(v_unit);
#if defined(__FreeBSD__)
CAMLreturn(Val_true);
#else
Expand All @@ -20,7 +20,7 @@ CAMLprim value stdune_is_freebsd(value v_unit) {
}

CAMLprim value stdune_is_openbsd(value v_unit) {
CAMLparam1(v_unit);
CAMLparam1(v_unit);
#if defined(__OpenBSD__)
CAMLreturn(Val_true);
#else
Expand All @@ -29,10 +29,19 @@ CAMLprim value stdune_is_openbsd(value v_unit) {
}

CAMLprim value stdune_is_netbsd(value v_unit) {
CAMLparam1(v_unit);
CAMLparam1(v_unit);
#if defined(__NetBSD__)
CAMLreturn(Val_true);
#else
CAMLreturn(Val_false);
#endif
}

CAMLprim value stdune_is_haiku(value v_unit) {
CAMLparam1(v_unit);
#if defined(__HAIKU__)
CAMLreturn(Val_true);
#else
CAMLreturn(Val_false);
#endif
}
6 changes: 5 additions & 1 deletion src/dune_engine/scheduler.ml
Original file line number Diff line number Diff line change
Expand Up @@ -602,7 +602,11 @@ end = struct
Process_table.remove t proc_info
;;

let wait = if Sys.win32 then wait_win32 else wait_unix
let wait =
match Platform.OS.value with
| Windows -> wait_win32
| Linux | Darwin | FreeBSD | OpenBSD | NetBSD | Haiku | Other -> wait_unix
;;

let run t =
Mutex.lock t.mutex;
Expand Down
3 changes: 2 additions & 1 deletion src/dune_file_watcher/dune_file_watcher.ml
Original file line number Diff line number Diff line change
Expand Up @@ -358,6 +358,7 @@ let fswatch_backend () =
| None ->
let hints =
match Platform.OS.value with
| Haiku -> [ Pp.text "fswatch is available on HaikuPorts" ]
| FreeBSD -> [ Pp.text "pkg install fswatch-mon" ]
| _ -> []
in
Expand All @@ -372,7 +373,7 @@ let select_watcher_backend () =
else (
match Platform.OS.value with
| Windows -> `Fswatch_win
| Linux | Darwin | FreeBSD | OpenBSD | NetBSD | Other -> fswatch_backend ())
| Linux | Darwin | FreeBSD | OpenBSD | NetBSD | Haiku | Other -> fswatch_backend ())
;;

let prepare_sync () =
Expand Down
1 change: 1 addition & 0 deletions src/dune_rules/bootstrap_info.ml
Original file line number Diff line number Diff line change
Expand Up @@ -26,6 +26,7 @@ let rule sctx ~requires_link (exes : Dune_file.Executables.t) =
; "win64", win_link_flags
; "mingw", win_link_flags
; "mingw64", win_link_flags
; "beos", [ "-cclib"; "-lbsd" ] (* flags for Haiku *)
]
in
let+ locals =
Expand Down
2 changes: 1 addition & 1 deletion src/dune_tui/dune_tui.ml
Original file line number Diff line number Diff line change
Expand Up @@ -382,5 +382,5 @@ let backend =
fun () ->
match (Platform.OS.value : Platform.OS.t) with
| Windows -> User_error.raise [ Pp.text "TUI is currently not supported on Windows." ]
| Linux | Darwin | FreeBSD | OpenBSD | NetBSD | Other -> Lazy.force t
| Linux | Darwin | FreeBSD | OpenBSD | NetBSD | Haiku | Other -> Lazy.force t
;;
5 changes: 5 additions & 0 deletions vendor/notty/src-unix/native/winsize.c
Original file line number Diff line number Diff line change
Expand Up @@ -7,6 +7,11 @@
#include <signal.h>
#endif

#ifdef __HAIKU__
/* On some platforms, ioctl() is declared in <unistd.h>. */
#include <unistd.h>
#endif

CAMLprim value caml_notty_winsize (value vfd) {
#ifdef _WIN32
(void) vfd;
Expand Down
2 changes: 1 addition & 1 deletion vendor/update-notty.sh
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
#!/bin/bash

version=7a95a8c8c39ed0742284d42216106cb9559fe34e
version=cb7221c73f8009a904fa249fdeb5558c83043b8f

set -e -o pipefail

Expand Down

0 comments on commit bd39351

Please sign in to comment.