diff --git a/CHANGES.md b/CHANGES.md index b97bd5d401e..d9b41c17065 100644 --- a/CHANGES.md +++ b/CHANGES.md @@ -8,9 +8,6 @@ Unreleased PPX-rewriters can be taken into account by providing the `--with-pps` flag. (#6727, fixes #6486, @esope) -- Print missing newline after `$ dune exec`. (#6654, fixes #6700, @rgrinberg, - @Alizter) - - Fix binary corruption when installing or promoting in parallel (#6669, fixes #6668, @edwintorok) diff --git a/bench/bench.ml b/bench/bench.ml index 7c7ea4626fc..64d3b376d15 100644 --- a/bench/bench.ml +++ b/bench/bench.ml @@ -125,7 +125,7 @@ let () = let module Scheduler = Dune_engine.Scheduler in let config = { Scheduler.Config.concurrency = 10 - ; display = Simple { verbosity = Quiet; status_line = false } + ; display = { verbosity = Quiet; status_line = false } ; stats = None ; insignificant_changes = `React ; signal_watcher = `No diff --git a/bench/micro/dune_bench/scheduler_bench.ml b/bench/micro/dune_bench/scheduler_bench.ml index dad7fbe7240..4217cf917da 100644 --- a/bench/micro/dune_bench/scheduler_bench.ml +++ b/bench/micro/dune_bench/scheduler_bench.ml @@ -6,7 +6,7 @@ module Caml = Stdlib let config = { Scheduler.Config.concurrency = 1 - ; display = Simple { verbosity = Short; status_line = false } + ; display = { verbosity = Short; status_line = false } ; stats = None ; insignificant_changes = `React ; signal_watcher = `No diff --git a/bin/common.ml b/bin/common.ml index eb3cfd64072..efed64a12d8 100644 --- a/bin/common.ml +++ b/bin/common.ml @@ -288,6 +288,7 @@ module Options_implied_by_dash_p = struct end let display_term = + let module Display = Dune_engine.Display in one_of (let+ verbose = Arg.( @@ -295,11 +296,10 @@ let display_term = & info [ "verbose" ] ~docs:copts_sect ~doc:"Same as $(b,--display verbose)") in - Option.some_if verbose - (Dune_engine.Display.Simple { verbosity = Verbose; status_line = true })) + Option.some_if verbose { Display.verbosity = Verbose; status_line = true }) Arg.( value - & opt (some (enum Dune_engine.Display.all)) None + & opt (some (enum Display.all)) None & info [ "display" ] ~docs:copts_sect ~docv:"MODE" ~doc: {|Control the display mode of Dune. diff --git a/bin/subst.ml b/bin/subst.ml index 5a6ce61f4af..4f50a8bb3b4 100644 --- a/bin/subst.ml +++ b/bin/subst.ml @@ -425,7 +425,7 @@ let term = and+ debug_backtraces = Common.debug_backtraces in let config : Dune_config.t = { Dune_config.default with - display = Simple { verbosity = Quiet; status_line = false } + display = { verbosity = Quiet; status_line = false } ; concurrency = Fixed 1 } in diff --git a/bin/target.ml b/bin/target.ml index 146a5a129a1..0b53b57b4d5 100644 --- a/bin/target.ml +++ b/bin/target.ml @@ -161,8 +161,7 @@ let resolve_targets root (config : Dune_config.t) let+ targets = Action_builder.List.map user_targets ~f:(resolve_target root ~setup) in - (match config.display with - | Simple { verbosity = Verbose; _ } -> + if config.display.verbosity = Verbose then Log.info [ Pp.text "Actual targets:" ; Pp.enumerate @@ -172,8 +171,7 @@ let resolve_targets root (config : Dune_config.t) ~f:(function | File p -> Pp.verbatim (Path.to_string_maybe_quoted p) | Alias a -> Alias.pp a) - ] - | _ -> ()); + ]; targets let resolve_targets_exn root config setup user_targets = diff --git a/boot/libs.ml b/boot/libs.ml index 79d26204255..8ca6f59f249 100644 --- a/boot/libs.ml +++ b/boot/libs.ml @@ -14,9 +14,6 @@ let local_libraries = ; ("vendor/incremental-cycles/src", Some "Incremental_cycles", false, None) ; ("src/dag", Some "Dag", false, None) ; ("otherlibs/fiber", Some "Fiber", false, None) - ; ("vendor/uutf", None, false, None) - ; ("vendor/notty/src", None, true, None) - ; ("vendor/notty/src-unix", None, true, None) ; ("src/dune_console", Some "Dune_console", false, None) ; ("src/memo", Some "Memo", false, None) ; ("src/dune_metrics", Some "Dune_metrics", false, None) diff --git a/src/dune_config/dune_config.ml b/src/dune_config/dune_config.ml index ba4f81a6c26..0a5dbb54e9f 100644 --- a/src/dune_config/dune_config.ml +++ b/src/dune_config/dune_config.ml @@ -262,7 +262,7 @@ let hash = Poly.hash let equal a b = Poly.equal a b let default = - { display = Simple { verbosity = Quiet; status_line = not Config.inside_dune } + { display = { verbosity = Quiet; status_line = not Config.inside_dune } ; concurrency = (if Config.inside_dune then Fixed 1 else Auto) ; terminal_persistence = Clear_on_rebuild ; sandboxing_preference = [] @@ -370,11 +370,11 @@ let adapt_display config ~output_is_a_tty = (* Progress isn't meaningful if inside a terminal (or emacs), so disable it if the output is getting piped to a file or something. *) let config = - match config.display with - | Simple { verbosity; _ } - when (not output_is_a_tty) && not Config.inside_emacs -> - { config with display = Simple { verbosity; status_line = false } } - | _ -> config + if + config.display.status_line && (not output_is_a_tty) + && not Config.inside_emacs + then { config with display = { config.display with status_line = false } } + else config in (* Similarly, terminal clearing is meaningless if stderr doesn't support ANSI codes, so revert-back to Preserve in that case *) @@ -384,10 +384,7 @@ let adapt_display config ~output_is_a_tty = let init t = Console.Backend.set (Display.console_backend t.display); - Log.verbose := - match t.display with - | Simple { verbosity = Verbose; _ } -> true - | _ -> false + Log.verbose := t.display.verbosity = Verbose let auto_concurrency = lazy diff --git a/src/dune_console/dune b/src/dune_console/dune index 30871cc0ebe..325ad47ba11 100644 --- a/src/dune_console/dune +++ b/src/dune_console/dune @@ -1,5 +1,5 @@ (library (name dune_console) - (libraries stdune dune_notty dune_notty_unix threads.posix) + (libraries stdune threads.posix) (instrumentation (backend bisect_ppx))) diff --git a/src/dune_console/dune_console.ml b/src/dune_console/dune_console.ml index 22aab51fbf9..97a70fa9626 100644 --- a/src/dune_console/dune_console.ml +++ b/src/dune_console/dune_console.ml @@ -2,8 +2,6 @@ open Stdune module Backend = struct module type S = sig - val start : unit -> unit - val print_user_message : User_message.t -> unit val set_status_line : User_message.Style.t Pp.t option -> unit @@ -20,8 +18,6 @@ module Backend = struct type t = (module S) module Dumb_no_flush : S = struct - let start () = () - let finish () = () let print_user_message msg = @@ -65,7 +61,7 @@ module Backend = struct module Progress_no_flush : S = struct let status_line = ref Pp.nop - let start () = () + let finish () = () let status_line_len = ref 0 @@ -97,64 +93,9 @@ module Backend = struct let reset () = Dumb.reset () - let finish () = set_status_line None - let reset_flush_history () = Dumb.reset_flush_history () end - type state = - { messages : User_message.t Queue.t - ; mutable finish_requested : bool - ; mutable finished : bool - ; mutable status_line : User_message.Style.t Pp.t option - } - - module Tui () = struct - module Term = Notty_unix.Term - - let term = Term.create ~nosig:false () - - let start () = Unix.set_nonblock Unix.stdin - - let image ~status_line ~messages = - let status = - match (status_line : User_message.Style.t Pp.t option) with - | None -> [] - | Some message -> - [ Notty_console.image_of_user_message_style_pp message ] - in - let messages = - List.map messages ~f:(fun msg -> - Notty_console.image_of_user_message_style_pp (User_message.pp msg)) - in - Notty.I.vcat (messages @ status) - - let render state = - let messages = Queue.to_list state.messages in - let image = image ~status_line:state.status_line ~messages in - Term.image term image - - let handle_user_events ~now ~timeout mutex = - let input_fds, _, _ = Unix.select [ Unix.stdin ] [] [] timeout in - match input_fds with - | [] -> now +. timeout - | _ :: _ -> - Mutex.lock mutex; - (try - match Term.event term with - | `Key (`ASCII 'q', _) -> Unix.kill (Unix.getpid ()) Sys.sigterm - | _ -> () - with Unix.Unix_error ((EAGAIN | EWOULDBLOCK), _, _) -> ()); - Mutex.unlock mutex; - Unix.gettimeofday () - - let reset () = () - - let reset_flush_history () = () - - let finish () = Notty_unix.Term.release term - end - let dumb = (module Dumb : S) let main = ref dumb @@ -163,10 +104,6 @@ module Backend = struct let compose (module A : S) (module B : S) : (module S) = (module struct - let start () = - A.start (); - B.start () - let print_user_message msg = A.print_user_message msg; B.print_user_message msg @@ -194,56 +131,19 @@ module Backend = struct let spawn_thread = Fdecl.create Dyn.opaque - (** [Threaded] is the interface for user interfaces that are rendered in a - separate thread. *) - module type Threaded = sig - (** [start] is called by the main thread to start broadcasting the user - interface. Any initial setup should be performed here. *) - val start : unit -> unit - - (** [render state] is called by the main thread to render the current state - of the user interface. *) - val render : state -> unit - - (** [handle_user_events ~now ~timeout mutex] is called by the main thread to - handle user events such as keypresses. The function should return the - time at which the next event should be handled. A [mutex] is provided in - order to lock the state of the UI.*) - val handle_user_events : now:float -> timeout:float -> Mutex.t -> float - - (** [reset] is called by the main thread to reset the user interface. *) - val reset : unit -> unit - - (** [reset_flush_history] is called by the main thread to reset and flush - the user interface. *) - val reset_flush_history : unit -> unit - - (** [finish] is called finally by the main thread to finish broadcasting the - user interface. Any locks on the terminal should be released here. *) - val finish : unit -> unit - end - - module Progress_no_flush_threaded : Threaded = struct - include Progress_no_flush - - let render state = - while not (Queue.is_empty state.messages) do - print_user_message (Queue.pop_exn state.messages) - done; - set_status_line state.status_line; - flush stderr - - let handle_user_events ~now ~timeout _ = - Unix.sleepf timeout; - now +. timeout - end - - let threaded (module Base : Threaded) : (module S) = + let threaded (module Base : S) : (module S) = let module T = struct let mutex = Mutex.create () let finish_cv = Condition.create () + type state = + { messages : User_message.t Queue.t + ; mutable finish_requested : bool + ; mutable finished : bool + ; mutable status_line : User_message.Style.t Pp.t option + } + let state = { messages = Queue.create () ; status_line = None @@ -251,11 +151,6 @@ module Backend = struct ; finish_requested = false } - let start () = - Mutex.lock mutex; - Base.start (); - Mutex.unlock mutex - let finish () = Mutex.lock mutex; state.finish_requested <- true; @@ -294,45 +189,33 @@ module Backend = struct let open T in let last = ref (Unix.gettimeofday ()) in let frame_rate = 1. /. 60. in - let cleanup () = - state.finished <- true; - Base.finish (); - Condition.broadcast finish_cv; - Mutex.unlock mutex - in try - Base.start (); while true do Mutex.lock mutex; - Base.render state; + while not (Queue.is_empty state.messages) do + Base.print_user_message (Queue.pop_exn state.messages) + done; + Base.set_status_line state.status_line; + flush stderr; let finish_requested = state.finish_requested in if finish_requested then raise_notrace Exit; Mutex.unlock mutex; let now = Unix.gettimeofday () in let elapsed = now -. !last in - let new_time = - if elapsed >= frame_rate then - Base.handle_user_events ~now ~timeout:0.0 mutex - else - let delta = frame_rate -. elapsed in - Base.handle_user_events ~now ~timeout:delta mutex - in - last := new_time + if elapsed >= frame_rate then last := now + else + let delta = frame_rate -. elapsed in + Unix.sleepf delta; + last := delta +. now done - with - | Exit -> cleanup () - | exn -> - let exn = Exn_with_backtrace.capture exn in - cleanup (); - Exn_with_backtrace.reraise exn ); + with Exit -> + state.finished <- true; + Condition.broadcast finish_cv; + Mutex.unlock mutex ); (module T) let progress = - let t = lazy (threaded (module Progress_no_flush_threaded)) in - fun () -> Lazy.force t - - let tui = - let t = lazy (threaded (module Tui ())) in + let t = lazy (threaded (module Progress_no_flush)) in fun () -> Lazy.force t end diff --git a/src/dune_console/dune_console.mli b/src/dune_console/dune_console.mli index 8cb46f11c2b..30b2f0090ef 100644 --- a/src/dune_console/dune_console.mli +++ b/src/dune_console/dune_console.mli @@ -17,16 +17,15 @@ module Backend : sig val compose : t -> t -> t (** A dumb backend that hides the status line and simply dump the messages to - the terminal. *) + the terminal *) val dumb : t - (** A backend that just displays the status line in the terminal. *) + (** A backend that just displays the status line in the terminal *) val progress : unit -> t - (** A backend that uses Notty to display the status line in the terminal. *) - val tui : unit -> t - val spawn_thread : ((unit -> unit) -> unit) Fdecl.t + + val threaded : t -> t end (** Format and print a user message to the console *) diff --git a/src/dune_console/notty_console.ml b/src/dune_console/notty_console.ml deleted file mode 100644 index 134aa8998f7..00000000000 --- a/src/dune_console/notty_console.ml +++ /dev/null @@ -1,68 +0,0 @@ -open Stdune - -let attr_of_ansi_color_style (s : Ansi_color.Style.t) = - let open Notty in - match s with - | `Fg_black -> A.(fg black) - | `Fg_red -> A.(fg red) - | `Fg_green -> A.(fg green) - | `Fg_yellow -> A.(fg yellow) - | `Fg_blue -> A.(fg blue) - | `Fg_magenta -> A.(fg magenta) - | `Fg_cyan -> A.(fg cyan) - | `Fg_white -> A.(fg white) - | `Fg_default -> A.empty - | `Fg_bright_black -> A.(fg lightblack) - | `Fg_bright_red -> A.(fg lightred) - | `Fg_bright_green -> A.(fg lightgreen) - | `Fg_bright_yellow -> A.(fg lightyellow) - | `Fg_bright_blue -> A.(fg lightblue) - | `Fg_bright_magenta -> A.(fg lightmagenta) - | `Fg_bright_cyan -> A.(fg lightcyan) - | `Fg_bright_white -> A.(fg lightwhite) - | `Bg_black -> A.(bg black) - | `Bg_red -> A.(bg red) - | `Bg_green -> A.(bg green) - | `Bg_yellow -> A.(bg yellow) - | `Bg_blue -> A.(bg blue) - | `Bg_magenta -> A.(bg magenta) - | `Bg_cyan -> A.(bg cyan) - | `Bg_white -> A.(bg white) - | `Bg_default -> A.empty - | `Bg_bright_black -> A.(bg lightblack) - | `Bg_bright_red -> A.(bg lightred) - | `Bg_bright_green -> A.(bg lightgreen) - | `Bg_bright_yellow -> A.(bg lightyellow) - | `Bg_bright_blue -> A.(bg lightblue) - | `Bg_bright_magenta -> A.(bg lightmagenta) - | `Bg_bright_cyan -> A.(bg lightcyan) - | `Bg_bright_white -> A.(bg lightwhite) - | `Bold -> A.(st bold) - | `Italic -> A.(st italic) - | `Dim -> A.(st dim) - | `Underline -> A.(st underline) - -let attr_of_user_message_style fmt t (pp : User_message.Style.t Pp.t) : unit = - let attr = - let open Notty in - match (t : User_message.Style.t) with - | Loc -> A.(st bold) - | Error -> A.(st bold ++ fg red) - | Warning -> A.(st bold ++ fg magenta) - | Kwd -> A.(st bold ++ fg blue) - | Id -> A.(st bold ++ fg yellow) - | Prompt -> A.(st bold ++ fg green) - | Hint -> A.(st italic ++ fg white) - | Details -> A.(st dim ++ fg white) - | Ok -> A.(st italic ++ fg green) - | Debug -> A.(st underline ++ fg lightcyan) - | Success -> A.(st bold ++ fg green) - | Ansi_styles l -> - List.fold_left ~init:A.empty l ~f:(fun attr s -> - A.(attr ++ attr_of_ansi_color_style s)) - in - Notty.I.pp_attr attr Pp.to_fmt fmt pp - -let image_of_user_message_style_pp = - Notty.I.strf "%a@." - (Pp.to_fmt_with_tags ~tag_handler:attr_of_user_message_style) diff --git a/src/dune_console/notty_console.mli b/src/dune_console/notty_console.mli deleted file mode 100644 index 469692d3a36..00000000000 --- a/src/dune_console/notty_console.mli +++ /dev/null @@ -1,8 +0,0 @@ -open Stdune - -(** Pretty-printing to Notty images. *) - -(** [image_of_user_message_style_pp pp] renders the pretty-printer [pp] to a - Notty image, using an interpretation of the [User_message.Style.t] tags to - [Notty.A.t]. *) -val image_of_user_message_style_pp : User_message.Style.t Pp.t -> Notty.image diff --git a/src/dune_engine/display.ml b/src/dune_engine/display.ml index db6f8d2f5ad..3a3ae6f0230 100644 --- a/src/dune_engine/display.ml +++ b/src/dune_engine/display.ml @@ -1,44 +1,37 @@ -module Verbosity = struct - type t = - | Quiet - | Short - | Verbose +open Import - let to_dyn : t -> Dyn.t = function - | Quiet -> Variant ("Quiet", []) - | Short -> Variant ("Short", []) - | Verbose -> Variant ("Verbose", []) -end +type verbosity = + | Quiet + | Short + | Verbose type t = - | Simple of - { status_line : bool - ; verbosity : Verbosity.t - } - | Tui + { status_line : bool + ; verbosity : verbosity + } (* Even though [status_line] is true by default in most of these, the status - line is actually not shown if the output is redirected to a file or a - pipe. *) + line is actually not shown if the output is redirected to a file or a + pipe. *) let all = - [ ("progress", Simple { verbosity = Quiet; status_line = true }) - ; ("quiet", Simple { verbosity = Quiet; status_line = false }) - ; ("short", Simple { verbosity = Short; status_line = true }) - ; ("verbose", Simple { verbosity = Verbose; status_line = true }) - ; ("tui", Tui) + [ ("progress", { verbosity = Quiet; status_line = true }) + ; ("verbose", { verbosity = Verbose; status_line = true }) + ; ("short", { verbosity = Short; status_line = true }) + ; ("quiet", { verbosity = Quiet; status_line = false }) ] -let to_dyn : t -> Dyn.t = function - | Simple { verbosity; status_line } -> - Dyn.Record - [ ("verbosity", Verbosity.to_dyn verbosity) - ; ("status_line", Dyn.Bool status_line) - ] - | Tui -> Variant ("Tui", []) +let verbosity_to_dyn : verbosity -> Dyn.t = function + | Quiet -> Variant ("Quiet", []) + | Short -> Variant ("Short", []) + | Verbose -> Variant ("Verbose", []) -let console_backend = function - | Tui -> Dune_console.Backend.tui () - | Simple { status_line; _ } -> ( - match status_line with - | false -> Dune_console.Backend.dumb - | true -> Dune_console.Backend.progress ()) +let to_dyn { status_line; verbosity } : Dyn.t = + Record + [ ("status_line", Dyn.Bool status_line) + ; ("verbosity", verbosity_to_dyn verbosity) + ] + +let console_backend t = + match t.status_line with + | false -> Console.Backend.dumb + | true -> Console.Backend.progress () diff --git a/src/dune_engine/display.mli b/src/dune_engine/display.mli index 71c08f4dd63..8a27249b9f8 100644 --- a/src/dune_engine/display.mli +++ b/src/dune_engine/display.mli @@ -1,22 +1,18 @@ -module Verbosity : sig - type t = - | Quiet (** Only display errors *) - | Short (** One line per command *) - | Verbose (** Display all commands fully *) +open Import - val to_dyn : t -> Dyn.t -end +type verbosity = + | Quiet (** Only display errors *) + | Short (** One line per command *) + | Verbose (** Display all commands fully *) type t = - | Simple of - { status_line : bool - ; verbosity : Verbosity.t - } - | Tui + { status_line : bool + ; verbosity : verbosity + } val all : (string * t) list val to_dyn : t -> Dyn.t (** The console backend corresponding to the selected display mode *) -val console_backend : t -> Dune_console.Backend.t +val console_backend : t -> Console.Backend.t diff --git a/src/dune_engine/process.ml b/src/dune_engine/process.ml index 20da2b896b1..0b4cac2b7ab 100644 --- a/src/dune_engine/process.ml +++ b/src/dune_engine/process.ml @@ -429,7 +429,7 @@ module Handle_exit_status : sig val non_verbose : ('a, error) result - -> verbosity:Display.Verbosity.t + -> verbosity:Display.verbosity -> metadata:metadata -> output:string -> prog:string @@ -521,7 +521,7 @@ end = struct ++ Pp.char ' ' ++ command_line :: pp_output output) - let non_verbose t ~(verbosity : Display.Verbosity.t) ~metadata ~output ~prog + let non_verbose t ~(verbosity : Display.verbosity) ~metadata ~output ~prog ~command_line ~dir ~has_unexpected_stdout ~has_unexpected_stderr = let output = parse_output output in let show_command = @@ -623,8 +623,8 @@ let run_internal ?dir ?(stdout_to = Io.stdout) ?(stderr_to = Io.stderr) command_line ~prog:prog_str ~args ~dir ~stdout_to ~stderr_to ~stdin_from in let fancy_command_line = - match display with - | Simple { verbosity = Verbose; _ } -> + match display.verbosity with + | Verbose -> let open Pp.O in let cmdline = Fancy.command_line ~prog:prog_str ~args ~dir ~stdout_to ~stderr_to @@ -808,21 +808,14 @@ let run_internal ?dir ?(stdout_to = Io.stdout) ?(stderr_to = Io.stderr) let output = stdout ^ stderr in Log.command ~command_line ~output ~exit_status:process_info.status; let res = - match (display, exit_status', output) with - | Simple { verbosity = Quiet; _ }, Ok n, "" -> - n (* Optimisation for the common case *) - | Simple { verbosity = Verbose; _ }, _, _ -> + match (display.verbosity, exit_status', output) with + | Quiet, Ok n, "" -> n (* Optimisation for the common case *) + | Verbose, _, _ -> Handle_exit_status.verbose exit_status' ~id ~metadata ~dir ~command_line:fancy_command_line ~output - | Simple { verbosity; _ }, _, _ -> - (* If we have verbosity we preserve it *) - Handle_exit_status.non_verbose exit_status' ~prog:prog_str ~dir - ~command_line ~output ~metadata ~verbosity ~has_unexpected_stdout - ~has_unexpected_stderr | _ -> - (* Otherwise we default to Quiet *) Handle_exit_status.non_verbose exit_status' ~prog:prog_str ~dir - ~command_line ~output ~metadata ~verbosity:Display.Verbosity.Quiet + ~command_line ~output ~metadata ~verbosity:display.verbosity ~has_unexpected_stdout ~has_unexpected_stderr in (res, times)) diff --git a/test/expect-tests/csexp_rpc/csexp_rpc_tests.ml b/test/expect-tests/csexp_rpc/csexp_rpc_tests.ml index 4448e1da748..6f6332e3d85 100644 --- a/test/expect-tests/csexp_rpc/csexp_rpc_tests.ml +++ b/test/expect-tests/csexp_rpc/csexp_rpc_tests.ml @@ -81,7 +81,7 @@ let%expect_test "csexp server life cycle" = in let config = { Scheduler.Config.concurrency = 1 - ; display = Simple { verbosity = Quiet; status_line = false } + ; display = { verbosity = Quiet; status_line = false } ; stats = None ; insignificant_changes = `React ; signal_watcher = `No diff --git a/test/expect-tests/dune_config/dune_config_test.ml b/test/expect-tests/dune_config/dune_config_test.ml index 84af854ad63..870dc0240ea 100644 --- a/test/expect-tests/dune_config/dune_config_test.ml +++ b/test/expect-tests/dune_config/dune_config_test.ml @@ -20,7 +20,7 @@ let%expect_test "cache-check-probability 0.1" = parse "(cache-check-probability 0.1)"; [%expect {| - { display = { verbosity = Quiet; status_line = false } + { display = { status_line = false; verbosity = Quiet } ; concurrency = Fixed 1 ; terminal_persistence = Clear_on_rebuild ; sandboxing_preference = [] @@ -36,7 +36,7 @@ let%expect_test "cache-storage-mode copy" = parse "(cache-storage-mode copy)"; [%expect {| - { display = { verbosity = Quiet; status_line = false } + { display = { status_line = false; verbosity = Quiet } ; concurrency = Fixed 1 ; terminal_persistence = Clear_on_rebuild ; sandboxing_preference = [] @@ -52,7 +52,7 @@ let%expect_test "cache-storage-mode hardlink" = parse "(cache-storage-mode hardlink)"; [%expect {| - { display = { verbosity = Quiet; status_line = false } + { display = { status_line = false; verbosity = Quiet } ; concurrency = Fixed 1 ; terminal_persistence = Clear_on_rebuild ; sandboxing_preference = [] diff --git a/test/expect-tests/dune_rpc_e2e/dune_rpc_e2e.ml b/test/expect-tests/dune_rpc_e2e/dune_rpc_e2e.ml index c5d1b002494..8976b6123aa 100644 --- a/test/expect-tests/dune_rpc_e2e/dune_rpc_e2e.ml +++ b/test/expect-tests/dune_rpc_e2e/dune_rpc_e2e.ml @@ -164,7 +164,7 @@ let with_dune_watch ?env f = let config = { Scheduler.Config.concurrency = 1 - ; display = Simple { verbosity = Quiet; status_line = false } + ; display = { verbosity = Quiet; status_line = false } ; stats = None ; insignificant_changes = `React ; signal_watcher = `No diff --git a/test/expect-tests/dune_rpc_e2e/dune_rpc_registry_test.ml b/test/expect-tests/dune_rpc_e2e/dune_rpc_registry_test.ml index e53495e3995..95fbde954c6 100644 --- a/test/expect-tests/dune_rpc_e2e/dune_rpc_registry_test.ml +++ b/test/expect-tests/dune_rpc_e2e/dune_rpc_registry_test.ml @@ -46,7 +46,7 @@ let run = let cwd = Sys.getcwd () in let config = { Scheduler.Config.concurrency = 1 - ; display = Simple { verbosity = Quiet; status_line = false } + ; display = { verbosity = Quiet; status_line = false } ; stats = None ; insignificant_changes = `React ; signal_watcher = `No diff --git a/test/expect-tests/process_tests.ml b/test/expect-tests/process_tests.ml index c58fdd9a59e..dfa5483a0a1 100644 --- a/test/expect-tests/process_tests.ml +++ b/test/expect-tests/process_tests.ml @@ -5,7 +5,7 @@ open Dune_engine let go = let config = { Scheduler.Config.concurrency = 1 - ; display = Simple { verbosity = Short; status_line = false } + ; display = { verbosity = Short; status_line = false } ; stats = None ; insignificant_changes = `React ; signal_watcher = `Yes diff --git a/test/expect-tests/scheduler_tests.ml b/test/expect-tests/scheduler_tests.ml index fafe35d741e..bed69b1f756 100644 --- a/test/expect-tests/scheduler_tests.ml +++ b/test/expect-tests/scheduler_tests.ml @@ -5,7 +5,7 @@ open Fiber.O let default = { Scheduler.Config.concurrency = 1 - ; display = Simple { verbosity = Short; status_line = false } + ; display = { verbosity = Short; status_line = false } ; stats = None ; insignificant_changes = `React ; signal_watcher = `No diff --git a/test/expect-tests/timer_tests.ml b/test/expect-tests/timer_tests.ml index 951a5354532..32ef3c60fab 100644 --- a/test/expect-tests/timer_tests.ml +++ b/test/expect-tests/timer_tests.ml @@ -4,7 +4,7 @@ module Scheduler = Dune_engine.Scheduler let config = { Scheduler.Config.concurrency = 1 - ; display = Simple { verbosity = Short; status_line = false } + ; display = { verbosity = Short; status_line = false } ; stats = None ; insignificant_changes = `React ; signal_watcher = `No diff --git a/test/expect-tests/vcs_tests.ml b/test/expect-tests/vcs_tests.ml index 7cf6ac7190b..53ce9de1e8c 100644 --- a/test/expect-tests/vcs_tests.ml +++ b/test/expect-tests/vcs_tests.ml @@ -112,7 +112,7 @@ let run kind script = let vcs = { Vcs.kind; root = temp_dir } in let config = { Scheduler.Config.concurrency = 1 - ; display = Simple { verbosity = Short; status_line = false } + ; display = { verbosity = Short; status_line = false } ; stats = None ; insignificant_changes = `React ; signal_watcher = `No diff --git a/vendor/notty/LICENSE.md b/vendor/notty/LICENSE.md deleted file mode 100644 index 124541c7421..00000000000 --- a/vendor/notty/LICENSE.md +++ /dev/null @@ -1,13 +0,0 @@ -Copyright (c) 2016-2017 David Kaloper Meršinjak - -Permission to use, copy, modify, and/or distribute this software for any -purpose with or without fee is hereby granted, provided that the above -copyright notice and this permission notice appear in all copies. - -THE SOFTWARE IS PROVIDED "AS IS" AND THE AUTHOR DISCLAIMS ALL WARRANTIES -WITH REGARD TO THIS SOFTWARE INCLUDING ALL IMPLIED WARRANTIES OF -MERCHANTABILITY AND FITNESS. IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR -ANY SPECIAL, DIRECT, INDIRECT, OR CONSEQUENTIAL DAMAGES OR ANY DAMAGES -WHATSOEVER RESULTING FROM LOSS OF USE, DATA OR PROFITS, WHETHER IN AN -ACTION OF CONTRACT, NEGLIGENCE OR OTHER TORTIOUS ACTION, ARISING OUT OF -OR IN CONNECTION WITH THE USE OR PERFORMANCE OF THIS SOFTWARE. diff --git a/vendor/notty/src-unix/native/winsize.c b/vendor/notty/src-unix/native/winsize.c deleted file mode 100644 index 45cc1eb1529..00000000000 --- a/vendor/notty/src-unix/native/winsize.c +++ /dev/null @@ -1,30 +0,0 @@ -#include - -#ifdef _WIN32 -#include -#else -#include -#include -#endif - -CAMLprim value caml_notty_winsize (value vfd) { -#ifdef _WIN32 - (void) vfd; - caml_failwith("not implemented on windows"); -#else - int fd = Int_val (vfd); - struct winsize w; - if (ioctl (fd, TIOCGWINSZ, &w) >= 0) - return Val_int ((w.ws_col << 16) + ((w.ws_row & 0x7fff) << 1)); - return Val_int (0); -#endif -} - -CAMLprim value caml_notty_winch_number (value vunit) { - (void) vunit; -#ifdef _WIN32 - return Val_int (0); -#else - return Val_int (SIGWINCH); -#endif -} diff --git a/vendor/notty/src-unix/notty_unix.ml b/vendor/notty/src-unix/notty_unix.ml deleted file mode 100644 index ec9d02437b1..00000000000 --- a/vendor/notty/src-unix/notty_unix.ml +++ /dev/null @@ -1,181 +0,0 @@ -(* Copyright (c) 2016-2017 David Kaloper Meršinjak. All rights reserved. - See LICENSE.md. *) - -open Notty - -external c_winsize : Unix.file_descr -> int = "caml_notty_winsize" [@@noalloc] -external winch_number : unit -> int = "caml_notty_winch_number" [@@noalloc] - -let iter f = function Some x -> f x | _ -> () -let value x = function Some a -> a | _ -> x - -let winsize fd = match c_winsize fd with - | 0 -> None - | wh -> Some (wh lsr 16, wh lsr 1 land 0x7fff) - -module Private = struct - - let once f = let v = lazy (f ()) in fun () -> Lazy.force v - - let cap_for_fd = - let open Cap in - match Sys.getenv "TERM" with - | exception Not_found -> fun _ -> dumb - | (""|"dumb") -> fun _ -> dumb - | _ -> fun fd -> if Unix.isatty fd then ansi else dumb - - let setup_tcattr ~nosig fd = - let open Unix in try - let tc = tcgetattr fd in - let tc1 = { tc with c_icanon = false; c_echo = false } in - tcsetattr fd TCSANOW - ( if nosig then { tc1 with c_isig = false; c_ixon = false } else tc1 ); - `Revert (once @@ fun _ -> tcsetattr fd TCSANOW tc) - with Unix_error (ENOTTY, _, _) -> `Revert ignore - - let set_winch_handler f = - let signum = winch_number () in - let old_hdl = Sys.(signal signum (Signal_handle (fun _ -> f ()))) in - `Revert (once @@ fun () -> Sys.set_signal signum old_hdl) - - module Gen_output (O : sig - type fd - type k - val def : fd - val to_fd : fd -> Unix.file_descr - val write : fd -> Buffer.t -> k - end) = struct - - let scratch = lazy (Buffer.create 4096) - - let output ?cap ?(fd = O.def) f = - let cap = cap |> value (cap_for_fd (O.to_fd fd)) in - let buf = Lazy.force scratch in - Buffer.reset buf; f buf cap fd; O.write fd buf - - let output_image_size ?cap ?fd f = - output ?cap ?fd @@ fun buf cap fd -> - let size = winsize (O.to_fd fd) in - let i = f (value (80, 24) size) in - let dim = match size with - | Some (w, _) -> I.(w, height i) - | None -> I.(width i, height i) in - Render.to_buffer buf cap (0, 0) dim i - - let show_cursor ?cap ?fd x = - output ?cap ?fd @@ fun buf cap _ -> Direct.show_cursor buf cap x - - let move_cursor ?cap ?fd x = - output ?cap ?fd @@ fun buf cap _ -> Direct.move_cursor buf cap x - - let output_image ?cap ?fd i = output_image_size ?cap ?fd (fun _ -> i) - - let eol i = I.(i <-> void 0 1) - end -end - -open Private - -module Term = struct - - module Winch = struct - - let h = Hashtbl.create 3 - and id = ref 0 - - let add fd f = - let n = !id in - set_winch_handler (fun () -> Hashtbl.iter (fun _ f -> f ()) h) |> ignore; - Hashtbl.add h n (fun () -> winsize fd |> iter f); incr id; - `Revert (fun () -> Hashtbl.remove h n) - end - - module Input = struct - - type t = { - fd : Unix.file_descr - ; flt : Unescape.t - ; ibuf : bytes - ; cleanup : unit -> unit - } - - let bsize = 1024 - - let create ~nosig fd = - let flt = Unescape.create () - and ibuf = Bytes.create bsize - and `Revert cleanup = setup_tcattr ~nosig fd in - { fd; flt; ibuf; cleanup } - - let rec event t = - match Unescape.next t.flt with - | #Unescape.event | `End as r -> r - | `Await -> - let n = Unix.read t.fd t.ibuf 0 bsize in - Unescape.input t.flt t.ibuf 0 n; event t - end - - type t = { - output : out_channel - ; trm : Tmachine.t - ; buf : Buffer.t - ; input : Input.t - ; fds : Unix.file_descr * Unix.file_descr - ; unwinch : (unit -> unit) Lazy.t - ; mutable winched : bool - } - - let write t = - Buffer.clear t.buf; - Tmachine.output t.trm t.buf; - Buffer.output_buffer t.output t.buf; flush t.output - - let set_size t dim = Tmachine.set_size t.trm dim - let refresh t = Tmachine.refresh t.trm; write t - let image t image = Tmachine.image t.trm image; write t - let cursor t curs = Tmachine.cursor t.trm curs; write t - let size t = Tmachine.size t.trm - - let release t = - if Tmachine.release t.trm then - ( Lazy.force t.unwinch (); - t.input.Input.cleanup (); - write t ) - - let create ?(dispose=true) ?(nosig=true) ?(mouse=true) ?(bpaste=true) - ?(input=Unix.stdin) ?(output=Unix.stdout) () = - let rec t = { - output = Unix.out_channel_of_descr output - ; trm = Tmachine.create ~mouse ~bpaste (cap_for_fd input) - ; buf = Buffer.create 4096 - ; input = Input.create ~nosig input - ; fds = (input, output) - ; winched = false - ; unwinch = lazy ( - let `Revert f = Winch.add output @@ fun dim -> - Buffer.reset t.buf; t.winched <- true; set_size t dim in f) - } in - winsize output |> iter (set_size t); - (Lazy.force t.unwinch |> ignore) [@ocaml.warning "-5"]; - if dispose then at_exit (fun () -> release t); - write t; - t - - let rec event = function - | t when Tmachine.dead t.trm -> `End - | t when t.winched -> t.winched <- false; `Resize (size t) - | t -> Unix.(try Input.event t.input with Unix_error (EINTR, _, _) -> event t) - - let pending t = - not (Tmachine.dead t.trm) && - (t.winched || Unescape.pending t.input.Input.flt) - - let fds t = t.fds -end - -include Gen_output (struct - type fd = out_channel and k = unit - let def = stdout - and to_fd = Unix.descr_of_out_channel - and write = Buffer.output_buffer -end) diff --git a/vendor/notty/src-unix/notty_unix.mli b/vendor/notty/src-unix/notty_unix.mli deleted file mode 100644 index 76106428bef..00000000000 --- a/vendor/notty/src-unix/notty_unix.mli +++ /dev/null @@ -1,222 +0,0 @@ -(* Copyright (c) 2016-2017 David Kaloper Meršinjak. All rights reserved. - See LICENSE.md. *) - -(** [Notty] IO for pure [Unix]. - - This is an IO module for {!Notty}. - - {e %%VERSION%% — {{:%%PKG_HOMEPAGE%% }homepage}} *) - -open Notty - -(** {1:fullscreen Fullscreen input and output}. *) - -(** Terminal IO abstraction for fullscreen, interactive applications. - - This module provides both input and output. It assumes exclusive ownership of - the IO streams between {{!create}initialization} and {{!release}shutdown}. *) -module Term : sig - - type t - (** Representation of the terminal, giving structured access to IO. *) - - (** {1 Construction and destruction} *) - - val create : ?dispose:bool -> - ?nosig:bool -> - ?mouse:bool -> - ?bpaste:bool -> - ?input:Unix.file_descr -> - ?output:Unix.file_descr -> - unit -> t - (** [create ~dispose ~nosig ~mouse ~input ~output ()] creates a fresh - {{!t}terminal}. It has the following side effects: - {ul - {- [Unix.tcsetattr] is applied to [input] to disable {e echo} and - {e canonical mode}.} - {- [output] is set to {e alternate screen mode}, and the cursor is - hidden. Mouse and {e bracketed paste} reporting are (optionally) - enabled.} - {- [SIGWINCH] signal, normally ignored, is handled.}} - - [~dispose] arranges for automatic {{!release}cleanup} of the terminal - before the process terminates. The downside is that a reference to this - terminal is retained until the program exits. Defaults to [true]. - - [~nosig] additionally turns off signal delivery and flow control - ({e isig} and {e ixon}) on input. Inhibits automatic handling of - {e CTRL-\{C,Z,\,S,Q\}}. Defaults to [true]. - - [~mouse] activates mouse reporting. Defaults to [true]. - - [~bpaste] activates bracketed paste reporting. Defaults to [true]. - - [~input] is the input file descriptor. Defaults to [stdin]. - - [~output] is the output file descriptor. Defaults to [stdout]. *) - - val release : t -> unit - (** Dispose of this terminal. Original behavior of input fd is reinstated, - cursor is restored, mouse reporting disabled, and alternate mode is - terminated. - - It is an error to use the {{!cmds}commands} on a released terminal, and - will raise [Invalid_argument], while [release] itself is idempotent. *) - - (** {1:cmds Commands} *) - - val image : t -> image -> unit - (** [image t i] sets [i] as [t]'s current image and redraws the terminal. *) - - val refresh : t -> unit - (** [refresh t] redraws the terminal using the current image. - - Useful if the output might have become garbled. *) - - val cursor : t -> (int * int) option -> unit - (** [cursor t pos] sets and redraws the cursor. - - [None] hides it. [Some (x, y)] places it at column [x] and row [y], with - the origin at [(0, 0)], mapping to the upper-left corner. *) - - (** {1 Events} *) - - val event : t -> [ Unescape.event | `Resize of (int * int) | `End ] - (** Wait for a new event. [event t] can be: - {ul - {- [#Unescape.event], an {{!Notty.Unescape.event}[event]} from the input fd;} - {- [`End] if the input fd is closed, or the terminal was released; or} - {- [`Resize (cols, rows)] giving the current size of the output tty, if a - [SIGWINCH] was delivered before or during this call to [event].}} - - {b Note} [event] is buffered. Calls can either block or immediately - return. Use {{!pending}[pending]} to detect when the next call would not - block. *) - - val pending : t -> bool - (** [pending t] is [true] if the next call to {{!event}[event]} would not - block and the terminal has not yet been released. *) - - (** {1 Properties} *) - - val size : t -> int * int - (** [size t] is the current size of the terminal's output tty. *) - - val fds : t -> Unix.file_descr * Unix.file_descr - (** [fds t] are [t]'s input and output file descriptors. *) - - (** {1 Window size change notifications} *) - - (** Manual [SIGWINCH] handling. - - Unix delivers notifications about tty size changes through the [SIGWINCH] - signal. A handler for this signal is installed as soon as a new terminal - is {{!create}created}. Replacing the global [SIGWINCH] handler using - the [Sys] module will cause this module to malfunction, as the size change - notifications will no longer be delivered. - - You might still want to ignore resizes reported by {{!event}[event]} and - directly listen to [SIGWINCH]. This module allows installing such - listeners without conflicting with the rest of the machinery. *) - module Winch : sig - - val add : Unix.file_descr -> ((int * int) -> unit) -> [`Revert of unit -> unit] - (** [add fd f] registers a [SIGWINCH] handler. Every time the signal is - delivered, [f] is called with the current size of the tty backing [fd]. - If [fd] is not a tty, [f] is never called. - - Return value is a function that removes the handler [f]. - - Handlers are called in an unspecified order. *) - - end -end - -(** {1:inline Inline output} - - These operations do not assume exclusive access to the output. This means - that they can be combined with other means of producing output. At the same - time, it means that they are affected by the current terminal state, and - that this state is not tracked. *) - -val winsize : Unix.file_descr -> (int * int) option -(** [winsize fd] is [Some (columns, rows)], the current dimensions of [fd]'s - backing tty, or [None], when [fd] is not backed by a tty. *) - -val eol : image -> image -(** [eol image] is [image], producing an extra newline when printed. *) - -val output_image : - ?cap:Cap.t -> ?fd:out_channel -> image -> unit -(** [output_image ?cap ?fd image] writes [image] to [fd]. - - The image is displayed in its full height. If the output is a tty, image - width is clipped to the output width. Otherwise, full width is used. - - [~cap] is the {{!caps}optional} terminal capability set. - - [~fd] defaults to [stdout]. *) - -val output_image_size : ?cap:Cap.t -> ?fd:out_channel -> (int * int -> image) -> unit -(** [output_image_size ?cap ?fd f] is - [output_image ?cap ?fd (f size)] where [size] are [fd]'s current - {{!winsize}output dimensions}. - - If [fd] is not backed by a tty, as a matter of convenience, [f] is applied - to [(80, 24)]. Use {!Unix.isatty} or {{!winsize}[winsize]} to detect whether - the output has a well-defined size. *) - -val show_cursor : ?cap:Cap.t -> ?fd:out_channel -> bool -> unit -(** [show_cursor ?cap ?fd visible] toggles the cursor visibility on [fd]. *) - -val move_cursor : - ?cap:Cap.t -> ?fd:out_channel -> - [ `Home | `By of int * int | `To of int * int ] -> unit -(** [move_cursor ?cap ?fd motion] moves the cursor on [fd]. - - [motion] is one of: - {ul - {- [`To (column, line)], positioning the cursor to [(column, line)]. Origin - is [(0, 0)], the upper-left corner of the screen.} - {- [`Home], moving the cursor the beginning of line.} - {- [`By (columns, lines)], moving the cursor [columns] to the right (left if - negative) and [lines] down (up if negative). - - {b Note} Behavior is terminal dependent if the movement overshoots the - output size.}} *) - -(** {1:caps Capability detection} - - All [image] output requires {{!Notty.Cap.t}terminal capabilities}. - - When not provided, capabilities are auto-detected, by checking that the - output is a tty, that the environment variable [$TERM] is set, and that it - is not set to either [""] or ["dumb"]. If these conditions hold, - {{!Notty.Cap.ansi}ANSI} escapes are used. Otherwise, {{!Notty.Cap.dumb}no} - escapes are used. *) - -(**/**) -(** {1 Private} - - These are private interfaces, prone to breakage. Don't use them. *) -module Private : sig - - val cap_for_fd : Unix.file_descr -> Cap.t - val setup_tcattr : nosig:bool -> Unix.file_descr -> [ `Revert of (unit -> unit) ] - val set_winch_handler : (unit -> unit) -> [ `Revert of (unit -> unit) ] - - module Gen_output (O : sig - type fd - type k - val def : fd - val to_fd : fd -> Unix.file_descr - val write : fd -> Buffer.t -> k - end ) : sig - val output_image : ?cap:Cap.t -> ?fd:O.fd -> image -> O.k - val output_image_size : ?cap:Cap.t -> ?fd:O.fd -> (int * int -> image) -> O.k - val show_cursor : ?cap:Cap.t -> ?fd:O.fd -> bool -> O.k - val move_cursor : ?cap:Cap.t -> ?fd:O.fd -> [ `Home | `By of int * int | `To of int * int ] -> O.k - val eol : image -> image - end -end -(**/**) diff --git a/vendor/notty/src/dune b/vendor/notty/src/dune deleted file mode 100644 index f801f9c7e5f..00000000000 --- a/vendor/notty/src/dune +++ /dev/null @@ -1,9 +0,0 @@ -(include_subdirs unqualified) - -(library - (name dune_notty) - (synopsis "Declaring terminals") - (libraries dune_uutf) - (wrapped false) - (modules notty notty_grapheme_cluster notty_uucp notty_uucp_data) - (private_modules notty_grapheme_cluster notty_uucp notty_uucp_data)) diff --git a/vendor/notty/src/no-uucp/README.md b/vendor/notty/src/no-uucp/README.md deleted file mode 100644 index 3bc1bdf4c87..00000000000 --- a/vendor/notty/src/no-uucp/README.md +++ /dev/null @@ -1,13 +0,0 @@ -Cannibalized bits of Uucp: - -- `Notty_uucp_data` is generated from an actual Uucp installation. -- `Notty_uucp` uses it to provide the few Unicode properties that Notty needs. -- `Notty_grapheme_cluster` is `Grapheme_cluster` from Uuseg, adapted to use the - above. - -Compiled size of these is on the order of 70K. Uucp is presently a monolithic 10M. - -The idea is to remove these in favor of the actual Uucp/Uuseg, as soon as it -becomes possible to depend only on the necessary parts of Uucp. - -Uucp and Uuseg are Copyright (c) 2014 Daniel C. Bünzli. diff --git a/vendor/notty/src/no-uucp/notty_grapheme_cluster.ml b/vendor/notty/src/no-uucp/notty_grapheme_cluster.ml deleted file mode 100644 index e0ecb170b93..00000000000 --- a/vendor/notty/src/no-uucp/notty_grapheme_cluster.ml +++ /dev/null @@ -1,133 +0,0 @@ -(*--------------------------------------------------------------------------- - Copyright (c) 2014 Daniel C. Bünzli. All rights reserved. - Distributed under the ISC license, see terms at the end of the file. - %%NAME%% %%VERSION%% - ---------------------------------------------------------------------------*) - -(* These are the rules as found in [1], with property values aliases [2] - substituted. - - GB1. sot ÷ Any - GB2. Any ÷ eot - GB3. CR × LF - GB4. (CN|CR|LF) ÷ - GB5. ÷ (CN|CR|LF) - GB6. L × (L|V|LV|LVT) - GB7. (LV|V) × (V|T) - GB8. (LVT|T) × T - GB9. × (EX|ZWJ) - GB9a. × SM - GB9b. PP × - GB10. (v10.0.0) (EB|EBG) EX* × EM - GB11. (v10.0.0) ZWJ × (GAZ|EBG) - GB12. sot (RI RI)* RI × RI - GB13. [^RI] (RI RI)* × RI - GB999. Any ÷ Any - - [1]: http://www.unicode.org/reports/tr29/#Grapheme_Cluster_Boundaries - [2]: http://www.unicode.org/Public/7.0.0/ucd/PropertyValueAliases.txt - [3]: http://www.unicode.org/Public/7.0.0/ucd/auxiliary/GraphemeBreakTest.html - - By the structure of the rules we see that grapheme clusters - boundaries can *mostly* be determined by simply looking at the - grapheme cluster break property value of the character on the left - and on the right of a boundary. The exceptions are GB10 and GB12-13 - which are handled specially by enriching the segmenter state in - a horribly ad-hoc fashion. *) - -type ret = [ `Await | `Boundary | `End | `Uchar of Uchar.t ] - -type gcb = - | CN | CR | EX | EB | EBG | EM | GAZ | L | LF | LV | LVT | PP | RI - | SM | T | V | XX | ZWJ | Sot - -(* WARNING. The indexes used here need to be synchronized with those - assigned by uucp for Uucp.Break.Low.grapheme_cluster. *) - -let byte_to_gcb = - [| CN; CR; EX; EB; EBG; EM; GAZ; L; LF; LV; LVT; PP; RI; - SM; T; V; XX; ZWJ; |] - -let gcb u = byte_to_gcb.(Notty_uucp.grapheme_cluster_boundary u) - -type state = -| Fill (* get next uchar to decide boundary. *) -| Flush (* an uchar is buffered, client needs to get it out with `Await. *) -| End (* `End was added. *) - -type t = - { mutable state : state; (* current state. *) - mutable left : gcb; (* break property value left of boundary. *) - mutable odd_ri : bool; (* odd number of RI on the left. *) - mutable emoji_seq : bool; (* (EB|EBG) Extend* on the left. *) - mutable buf : [ `Uchar of Uchar.t ] } (* bufferized add. *) - -let nul_buf = `Uchar (Uchar.unsafe_of_int 0x0000) - -let create () = - { state = Fill; left = Sot; - odd_ri = false; emoji_seq = false; - buf = nul_buf (* overwritten *); } - -let break s right = match s.left, right with -| (* GB1 *) Sot, _ -> true - (* GB2 is handled by `End *) -| (* GB3 *) CR, LF -> false -| (* GB4 *) (CN|CR|LF), _ -> true -| (* GB5 *) _, (CN|CR|LF) -> true -| (* GB6 *) L, (L|V|LV|LVT) -> false -| (* GB7 *) (LV|V), (V|T) -> false -| (* GB8 *) (LVT|T), T -> false -| (* GB9+a *) _, (EX|ZWJ|SM) -> false -| (* GB9b *) PP, _ -> false -| (* GB10 *) _, EM when s.emoji_seq -> false -| (* GB11 *) ZWJ, (GAZ|EBG) -> false -| (* GB12+13 *) RI, RI when s.odd_ri -> false -| (* GB999 *) _, _ -> true - -let update_left s right = - s.left <- right; - match s.left with - | EX -> (* keep s.emoji_seq as is *) s.odd_ri <- false - | EB | EBG -> s.emoji_seq <- true; s.odd_ri <- false - | RI -> s.emoji_seq <- false; s.odd_ri <- not s.odd_ri - | _ -> s.emoji_seq <- false; s.odd_ri <- false - -let add s = function -| `Uchar u as add -> - begin match s.state with - | Fill -> - let right = gcb u in - let break = break s right in - update_left s right; - if not break then add else - (s.state <- Flush; s.buf <- add; `Boundary) - | Flush | End -> assert false - end -| `Await -> - begin match s.state with - | Flush -> s.state <- Fill; (s.buf :> ret) - | End -> `End - | Fill -> `Await - end -| `End -> - begin match s.state with - | Fill -> s.state <- End; if s.left = Sot then `End else `Boundary - | Flush | End -> assert false - end - -(*--------------------------------------------------------------------------- - Copyright (c) 2014 Daniel C. Bünzli - - Permission to use, copy, modify, and/or distribute this software for any - purpose with or without fee is hereby granted, provided that the above - copyright notice and this permission notice appear in all copies. - - THE SOFTWARE IS PROVIDED "AS IS" AND THE AUTHOR DISCLAIMS ALL WARRANTIES - WITH REGARD TO THIS SOFTWARE INCLUDING ALL IMPLIED WARRANTIES OF - MERCHANTABILITY AND FITNESS. IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR - ANY SPECIAL, DIRECT, INDIRECT, OR CONSEQUENTIAL DAMAGES OR ANY DAMAGES - WHATSOEVER RESULTING FROM LOSS OF USE, DATA OR PROFITS, WHETHER IN AN - ACTION OF CONTRACT, NEGLIGENCE OR OTHER TORTIOUS ACTION, ARISING OUT OF - OR IN CONNECTION WITH THE USE OR PERFORMANCE OF THIS SOFTWARE. - ---------------------------------------------------------------------------*) diff --git a/vendor/notty/src/no-uucp/notty_grapheme_cluster.mli b/vendor/notty/src/no-uucp/notty_grapheme_cluster.mli deleted file mode 100644 index 9474eae998f..00000000000 --- a/vendor/notty/src/no-uucp/notty_grapheme_cluster.mli +++ /dev/null @@ -1,27 +0,0 @@ -(*--------------------------------------------------------------------------- - Copyright (c) 2014 Daniel C. Bünzli. All rights reserved. - Distributed under the ISC license, see terms at the end of the file. - %%NAME%% %%VERSION%% - ---------------------------------------------------------------------------*) - -type ret = [ `Await | `Boundary | `End | `Uchar of Uchar.t ] - -type t -val create : unit -> t -val add : t -> [ `Await | `End | `Uchar of Uchar.t ] -> ret - -(*--------------------------------------------------------------------------- - Copyright (c) 2014 Daniel C. Bünzli - - Permission to use, copy, modify, and/or distribute this software for any - purpose with or without fee is hereby granted, provided that the above - copyright notice and this permission notice appear in all copies. - - THE SOFTWARE IS PROVIDED "AS IS" AND THE AUTHOR DISCLAIMS ALL WARRANTIES - WITH REGARD TO THIS SOFTWARE INCLUDING ALL IMPLIED WARRANTIES OF - MERCHANTABILITY AND FITNESS. IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR - ANY SPECIAL, DIRECT, INDIRECT, OR CONSEQUENTIAL DAMAGES OR ANY DAMAGES - WHATSOEVER RESULTING FROM LOSS OF USE, DATA OR PROFITS, WHETHER IN AN - ACTION OF CONTRACT, NEGLIGENCE OR OTHER TORTIOUS ACTION, ARISING OUT OF - OR IN CONNECTION WITH THE USE OR PERFORMANCE OF THIS SOFTWARE. - ---------------------------------------------------------------------------*) diff --git a/vendor/notty/src/no-uucp/notty_uucp.ml b/vendor/notty/src/no-uucp/notty_uucp.ml deleted file mode 100644 index c3c8cc28437..00000000000 --- a/vendor/notty/src/no-uucp/notty_uucp.ml +++ /dev/null @@ -1,48 +0,0 @@ -(* Copyright (c) 2020 David Kaloper Meršinjak. All rights reserved. - See LICENSE.md. *) - -(* Unpacked interval lookup table. *) -let find_i ~def k (xs, _, _ as tab) = - let rec go i j (los, his, vs as tab) (k: int) def = - if i > j then def else - let x = (i + j) / 2 in - if k < Array.unsafe_get los x then go i (x - 1) tab k def else - if k > Array.unsafe_get his x then go (x + 1) j tab k def else - Array.unsafe_get vs x in - go 0 (Array.length xs - 1) tab k def - -(* 12-6-6-bit (0xfff-0x3f-0x3f) trie, 3 levels, array-array-string. - Root is variable; lower levels are either empty or complete. *) -let find_t ~def k tab = - let k = if k > 0xd7ff then k - 0x800 else k in (* Pack to continuous range. *) - let b0 = (k lsr 12) land 0xfff in - if Array.length tab <= b0 then def else - match Array.unsafe_get tab b0 with - | [||] -> def - | arr -> match Array.unsafe_get arr ((k lsr 6) land 0x3f) with - | "" -> def - | str -> String.unsafe_get str (k land 0x3f) |> Char.code - -(* We catch w = -1 and default to w = 1 to minimize the table. *) -let tty_width_hint u = match Uchar.to_int u with -| 0 -> 0 -| u when u <= 0x001F || 0x007F <= u && u <= 0x009F -> -1 -| u when u <= 0x02ff -> 1 -| u -> find_i ~def:1 u Notty_uucp_data.tty_width_hint - -let grapheme_cluster_boundary u = - find_t ~def:16 (Uchar.to_int u) Notty_uucp_data.grapheme_cluster_boundary - -(* let check () = *) -(* let pp_u ppf u = Format.fprintf ppf "u+%04x" (Uchar.to_int u) in *) -(* let rec go i u = *) -(* let w1 = tty_width_hint u *) -(* and w2 = Uucp.Break.tty_width_hint u in *) -(* if w1 <> w2 then Format.printf "w: %a here: %d there: %d@." pp_u u w1 w2; *) -(* let gc1 = grapheme_cluster_boundary u *) -(* and gc2 = Uucp.Break.Low.grapheme_cluster u in *) -(* if gc1 <> gc2 then Format.printf "gc: %a here: %d there: %d@." pp_u u gc1 gc2; *) -(* if u = Uchar.max then i else go (i + 1) (Uchar.succ u) in *) -(* let n = go 1 Uchar.min in *) -(* Format.printf "Checked equality for %d code points.@." n *) - diff --git a/vendor/notty/src/no-uucp/notty_uucp.mli b/vendor/notty/src/no-uucp/notty_uucp.mli deleted file mode 100644 index 4ea151cc6ea..00000000000 --- a/vendor/notty/src/no-uucp/notty_uucp.mli +++ /dev/null @@ -1,13 +0,0 @@ -(* Copyright (c) 2020 David Kaloper Meršinjak. All rights reserved. - See LICENSE.md. *) - -(* This is a local copy of the (very few) relevant [uucp] properties. *) - -val tty_width_hint : Uchar.t -> int -(* [Uucp.Break.tty_width_hint]. *) - -val grapheme_cluster_boundary : Uchar.t -> int -(* [Uucp.Break.Low.grapheme_cluster]. *) - -(* val check : unit -> unit *) - diff --git a/vendor/notty/src/no-uucp/notty_uucp_data.ml b/vendor/notty/src/no-uucp/notty_uucp_data.ml deleted file mode 100644 index 7a45af42183..00000000000 --- a/vendor/notty/src/no-uucp/notty_uucp_data.ml +++ /dev/null @@ -1,446 +0,0 @@ -(* Do not edit. - * - * This module contains select unicode properties extracted from Uucp, - * using `./support/gen_unicode_props.ml`. - * - * Unicode version 13.0.0. - *) - - -let tty_width_hint = - ([|0x0000; 0x0300; 0x0483; 0x0591; 0x05bf; 0x05c1; 0x05c4; 0x05c7; 0x0600; - 0x0610; 0x061c; 0x064b; 0x0670; 0x06d6; 0x06df; 0x06e7; 0x06ea; 0x070f; - 0x0711; 0x0730; 0x07a6; 0x07eb; 0x07fd; 0x0816; 0x081b; 0x0825; 0x0829; - 0x0859; 0x08d3; 0x093a; 0x093c; 0x0941; 0x094d; 0x0951; 0x0962; 0x0981; - 0x09bc; 0x09c1; 0x09cd; 0x09e2; 0x09fe; 0x0a01; 0x0a3c; 0x0a41; 0x0a47; - 0x0a4b; 0x0a51; 0x0a70; 0x0a75; 0x0a81; 0x0abc; 0x0ac1; 0x0ac7; 0x0acd; - 0x0ae2; 0x0afa; 0x0b01; 0x0b3c; 0x0b3f; 0x0b41; 0x0b4d; 0x0b55; 0x0b62; - 0x0b82; 0x0bc0; 0x0bcd; 0x0c00; 0x0c04; 0x0c3e; 0x0c46; 0x0c4a; 0x0c55; - 0x0c62; 0x0c81; 0x0cbc; 0x0cbf; 0x0cc6; 0x0ccc; 0x0ce2; 0x0d00; 0x0d3b; - 0x0d41; 0x0d4d; 0x0d62; 0x0d81; 0x0dca; 0x0dd2; 0x0dd6; 0x0e31; 0x0e34; - 0x0e47; 0x0eb1; 0x0eb4; 0x0ec8; 0x0f18; 0x0f35; 0x0f37; 0x0f39; 0x0f71; - 0x0f80; 0x0f86; 0x0f8d; 0x0f99; 0x0fc6; 0x102d; 0x1032; 0x1039; 0x103d; - 0x1058; 0x105e; 0x1071; 0x1082; 0x1085; 0x108d; 0x109d; 0x1100; 0x135d; - 0x1712; 0x1732; 0x1752; 0x1772; 0x17b4; 0x17b7; 0x17c6; 0x17c9; 0x17dd; - 0x180b; 0x1885; 0x18a9; 0x1920; 0x1927; 0x1932; 0x1939; 0x1a17; 0x1a1b; - 0x1a56; 0x1a58; 0x1a60; 0x1a62; 0x1a65; 0x1a73; 0x1a7f; 0x1ab0; 0x1b00; - 0x1b34; 0x1b36; 0x1b3c; 0x1b42; 0x1b6b; 0x1b80; 0x1ba2; 0x1ba8; 0x1bab; - 0x1be6; 0x1be8; 0x1bed; 0x1bef; 0x1c2c; 0x1c36; 0x1cd0; 0x1cd4; 0x1ce2; - 0x1ced; 0x1cf4; 0x1cf8; 0x1dc0; 0x1dfb; 0x200b; 0x202a; 0x2060; 0x2066; - 0x20d0; 0x231a; 0x2329; 0x23e9; 0x23f0; 0x23f3; 0x25fd; 0x2614; 0x2648; - 0x267f; 0x2693; 0x26a1; 0x26aa; 0x26bd; 0x26c4; 0x26ce; 0x26d4; 0x26ea; - 0x26f2; 0x26f5; 0x26fa; 0x26fd; 0x2705; 0x270a; 0x2728; 0x274c; 0x274e; - 0x2753; 0x2757; 0x2795; 0x27b0; 0x27bf; 0x2b1b; 0x2b50; 0x2b55; 0x2cef; - 0x2d7f; 0x2de0; 0x2e80; 0x2e9b; 0x2f00; 0x2ff0; 0x3000; 0x302a; 0x302e; - 0x3041; 0x3099; 0x309b; 0x3105; 0x3131; 0x3190; 0x31f0; 0x3220; 0x3250; - 0x4e00; 0xa490; 0xa66f; 0xa674; 0xa69e; 0xa6f0; 0xa802; 0xa806; 0xa80b; - 0xa825; 0xa82c; 0xa8c4; 0xa8e0; 0xa8ff; 0xa926; 0xa947; 0xa960; 0xa980; - 0xa9b3; 0xa9b6; 0xa9bc; 0xa9e5; 0xaa29; 0xaa31; 0xaa35; 0xaa43; 0xaa4c; - 0xaa7c; 0xaab0; 0xaab2; 0xaab7; 0xaabe; 0xaac1; 0xaaec; 0xaaf6; 0xabe5; - 0xabe8; 0xabed; 0xac00; 0xf900; 0xfb1e; 0xfe00; 0xfe10; 0xfe20; 0xfe30; - 0xfe54; 0xfe68; 0xfeff; 0xff01; 0xffe0; 0xfff9; 0x101fd; 0x102e0; - 0x10376; 0x10a01; 0x10a05; 0x10a0c; 0x10a38; 0x10a3f; 0x10ae5; 0x10d24; - 0x10eab; 0x10f46; 0x11001; 0x11038; 0x1107f; 0x110b3; 0x110b9; 0x110bd; - 0x110cd; 0x11100; 0x11127; 0x1112d; 0x11173; 0x11180; 0x111b6; 0x111c9; - 0x111cf; 0x1122f; 0x11234; 0x11236; 0x1123e; 0x112df; 0x112e3; 0x11300; - 0x1133b; 0x11340; 0x11366; 0x11370; 0x11438; 0x11442; 0x11446; 0x1145e; - 0x114b3; 0x114ba; 0x114bf; 0x114c2; 0x115b2; 0x115bc; 0x115bf; 0x115dc; - 0x11633; 0x1163d; 0x1163f; 0x116ab; 0x116ad; 0x116b0; 0x116b7; 0x1171d; - 0x11722; 0x11727; 0x1182f; 0x11839; 0x1193b; 0x1193e; 0x11943; 0x119d4; - 0x119da; 0x119e0; 0x11a01; 0x11a33; 0x11a3b; 0x11a47; 0x11a51; 0x11a59; - 0x11a8a; 0x11a98; 0x11c30; 0x11c38; 0x11c3f; 0x11c92; 0x11caa; 0x11cb2; - 0x11cb5; 0x11d31; 0x11d3a; 0x11d3c; 0x11d3f; 0x11d47; 0x11d90; 0x11d95; - 0x11d97; 0x11ef3; 0x13430; 0x16af0; 0x16b30; 0x16f4f; 0x16f8f; 0x16fe0; - 0x16fe4; 0x16ff0; 0x17000; 0x18800; 0x18d00; 0x1b000; 0x1b150; 0x1b164; - 0x1b170; 0x1bc9d; 0x1bca0; 0x1d167; 0x1d173; 0x1d185; 0x1d1aa; 0x1d242; - 0x1da00; 0x1da3b; 0x1da75; 0x1da84; 0x1da9b; 0x1daa1; 0x1e000; 0x1e008; - 0x1e01b; 0x1e023; 0x1e026; 0x1e130; 0x1e2ec; 0x1e8d0; 0x1e944; 0x1f004; - 0x1f0cf; 0x1f18e; 0x1f191; 0x1f200; 0x1f210; 0x1f240; 0x1f250; 0x1f260; - 0x1f300; 0x1f32d; 0x1f337; 0x1f37e; 0x1f3a0; 0x1f3cf; 0x1f3e0; 0x1f3f4; - 0x1f3f8; 0x1f440; 0x1f442; 0x1f4ff; 0x1f54b; 0x1f550; 0x1f57a; 0x1f595; - 0x1f5a4; 0x1f5fb; 0x1f680; 0x1f6cc; 0x1f6d0; 0x1f6d5; 0x1f6eb; 0x1f6f4; - 0x1f7e0; 0x1f90c; 0x1f93c; 0x1f947; 0x1f97a; 0x1f9cd; 0x1fa70; 0x1fa78; - 0x1fa80; 0x1fa90; 0x1fab0; 0x1fac0; 0x1fad0; 0x20000; 0x30000; 0xe0001; - 0xe0020; 0xe0100|], - [|0x0000; 0x036f; 0x0489; 0x05bd; 0x05bf; 0x05c2; 0x05c5; 0x05c7; 0x0605; - 0x061a; 0x061c; 0x065f; 0x0670; 0x06dd; 0x06e4; 0x06e8; 0x06ed; 0x070f; - 0x0711; 0x074a; 0x07b0; 0x07f3; 0x07fd; 0x0819; 0x0823; 0x0827; 0x082d; - 0x085b; 0x0902; 0x093a; 0x093c; 0x0948; 0x094d; 0x0957; 0x0963; 0x0981; - 0x09bc; 0x09c4; 0x09cd; 0x09e3; 0x09fe; 0x0a02; 0x0a3c; 0x0a42; 0x0a48; - 0x0a4d; 0x0a51; 0x0a71; 0x0a75; 0x0a82; 0x0abc; 0x0ac5; 0x0ac8; 0x0acd; - 0x0ae3; 0x0aff; 0x0b01; 0x0b3c; 0x0b3f; 0x0b44; 0x0b4d; 0x0b56; 0x0b63; - 0x0b82; 0x0bc0; 0x0bcd; 0x0c00; 0x0c04; 0x0c40; 0x0c48; 0x0c4d; 0x0c56; - 0x0c63; 0x0c81; 0x0cbc; 0x0cbf; 0x0cc6; 0x0ccd; 0x0ce3; 0x0d01; 0x0d3c; - 0x0d44; 0x0d4d; 0x0d63; 0x0d81; 0x0dca; 0x0dd4; 0x0dd6; 0x0e31; 0x0e3a; - 0x0e4e; 0x0eb1; 0x0ebc; 0x0ecd; 0x0f19; 0x0f35; 0x0f37; 0x0f39; 0x0f7e; - 0x0f84; 0x0f87; 0x0f97; 0x0fbc; 0x0fc6; 0x1030; 0x1037; 0x103a; 0x103e; - 0x1059; 0x1060; 0x1074; 0x1082; 0x1086; 0x108d; 0x109d; 0x115f; 0x135f; - 0x1714; 0x1734; 0x1753; 0x1773; 0x17b5; 0x17bd; 0x17c6; 0x17d3; 0x17dd; - 0x180e; 0x1886; 0x18a9; 0x1922; 0x1928; 0x1932; 0x193b; 0x1a18; 0x1a1b; - 0x1a56; 0x1a5e; 0x1a60; 0x1a62; 0x1a6c; 0x1a7c; 0x1a7f; 0x1ac0; 0x1b03; - 0x1b34; 0x1b3a; 0x1b3c; 0x1b42; 0x1b73; 0x1b81; 0x1ba5; 0x1ba9; 0x1bad; - 0x1be6; 0x1be9; 0x1bed; 0x1bf1; 0x1c33; 0x1c37; 0x1cd2; 0x1ce0; 0x1ce8; - 0x1ced; 0x1cf4; 0x1cf9; 0x1df9; 0x1dff; 0x200f; 0x202e; 0x2064; 0x206f; - 0x20f0; 0x231b; 0x232a; 0x23ec; 0x23f0; 0x23f3; 0x25fe; 0x2615; 0x2653; - 0x267f; 0x2693; 0x26a1; 0x26ab; 0x26be; 0x26c5; 0x26ce; 0x26d4; 0x26ea; - 0x26f3; 0x26f5; 0x26fa; 0x26fd; 0x2705; 0x270b; 0x2728; 0x274c; 0x274e; - 0x2755; 0x2757; 0x2797; 0x27b0; 0x27bf; 0x2b1c; 0x2b50; 0x2b55; 0x2cf1; - 0x2d7f; 0x2dff; 0x2e99; 0x2ef3; 0x2fd5; 0x2ffb; 0x3029; 0x302d; 0x303e; - 0x3096; 0x309a; 0x30ff; 0x312f; 0x318e; 0x31e3; 0x321e; 0x3247; 0x4dbf; - 0xa48c; 0xa4c6; 0xa672; 0xa67d; 0xa69f; 0xa6f1; 0xa802; 0xa806; 0xa80b; - 0xa826; 0xa82c; 0xa8c5; 0xa8f1; 0xa8ff; 0xa92d; 0xa951; 0xa97c; 0xa982; - 0xa9b3; 0xa9b9; 0xa9bd; 0xa9e5; 0xaa2e; 0xaa32; 0xaa36; 0xaa43; 0xaa4c; - 0xaa7c; 0xaab0; 0xaab4; 0xaab8; 0xaabf; 0xaac1; 0xaaed; 0xaaf6; 0xabe5; - 0xabe8; 0xabed; 0xd7a3; 0xfaff; 0xfb1e; 0xfe0f; 0xfe19; 0xfe2f; 0xfe52; - 0xfe66; 0xfe6b; 0xfeff; 0xff60; 0xffe6; 0xfffb; 0x101fd; 0x102e0; - 0x1037a; 0x10a03; 0x10a06; 0x10a0f; 0x10a3a; 0x10a3f; 0x10ae6; 0x10d27; - 0x10eac; 0x10f50; 0x11001; 0x11046; 0x11081; 0x110b6; 0x110ba; 0x110bd; - 0x110cd; 0x11102; 0x1112b; 0x11134; 0x11173; 0x11181; 0x111be; 0x111cc; - 0x111cf; 0x11231; 0x11234; 0x11237; 0x1123e; 0x112df; 0x112ea; 0x11301; - 0x1133c; 0x11340; 0x1136c; 0x11374; 0x1143f; 0x11444; 0x11446; 0x1145e; - 0x114b8; 0x114ba; 0x114c0; 0x114c3; 0x115b5; 0x115bd; 0x115c0; 0x115dd; - 0x1163a; 0x1163d; 0x11640; 0x116ab; 0x116ad; 0x116b5; 0x116b7; 0x1171f; - 0x11725; 0x1172b; 0x11837; 0x1183a; 0x1193c; 0x1193e; 0x11943; 0x119d7; - 0x119db; 0x119e0; 0x11a0a; 0x11a38; 0x11a3e; 0x11a47; 0x11a56; 0x11a5b; - 0x11a96; 0x11a99; 0x11c36; 0x11c3d; 0x11c3f; 0x11ca7; 0x11cb0; 0x11cb3; - 0x11cb6; 0x11d36; 0x11d3a; 0x11d3d; 0x11d45; 0x11d47; 0x11d91; 0x11d95; - 0x11d97; 0x11ef4; 0x13438; 0x16af4; 0x16b36; 0x16f4f; 0x16f92; 0x16fe3; - 0x16fe4; 0x16ff1; 0x187f7; 0x18cd5; 0x18d08; 0x1b11e; 0x1b152; 0x1b167; - 0x1b2fb; 0x1bc9e; 0x1bca3; 0x1d169; 0x1d182; 0x1d18b; 0x1d1ad; 0x1d244; - 0x1da36; 0x1da6c; 0x1da75; 0x1da84; 0x1da9f; 0x1daaf; 0x1e006; 0x1e018; - 0x1e021; 0x1e024; 0x1e02a; 0x1e136; 0x1e2ef; 0x1e8d6; 0x1e94a; 0x1f004; - 0x1f0cf; 0x1f18e; 0x1f19a; 0x1f202; 0x1f23b; 0x1f248; 0x1f251; 0x1f265; - 0x1f320; 0x1f335; 0x1f37c; 0x1f393; 0x1f3ca; 0x1f3d3; 0x1f3f0; 0x1f3f4; - 0x1f43e; 0x1f440; 0x1f4fc; 0x1f53d; 0x1f54e; 0x1f567; 0x1f57a; 0x1f596; - 0x1f5a4; 0x1f64f; 0x1f6c5; 0x1f6cc; 0x1f6d2; 0x1f6d7; 0x1f6ec; 0x1f6fc; - 0x1f7eb; 0x1f93a; 0x1f945; 0x1f978; 0x1f9cb; 0x1f9ff; 0x1fa74; 0x1fa7a; - 0x1fa86; 0x1faa8; 0x1fab6; 0x1fac2; 0x1fad6; 0x2fffd; 0x3fffd; 0xe0001; - 0xe007f; 0xe01ef|], - [|0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; - 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; - 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; - 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; - 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 2; 0; 0; 0; 0; - 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; - 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; - 0; 0; 0; 0; 2; 2; 2; 2; 2; 2; 2; 2; 2; 2; 2; 2; 2; 2; 2; 2; 2; 2; 2; 2; - 2; 2; 2; 2; 2; 2; 2; 2; 2; 2; 2; 2; 2; 2; 0; 0; 0; 2; 2; 2; 2; 2; 0; 2; - 2; 0; 2; 2; 2; 2; 2; 2; 2; 2; 2; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; - 0; 2; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 2; - 2; 0; 0; 2; 0; 2; 2; 2; 0; 2; 2; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; - 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; - 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; - 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; - 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 2; 0; 2; 2; 2; 2; 2; 2; 2; 2; 0; - 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 2; 2; 2; - 2; 2; 2; 2; 2; 2; 2; 2; 2; 2; 2; 2; 2; 2; 2; 2; 2; 2; 2; 2; 2; 2; 2; 2; - 2; 2; 2; 2; 2; 2; 2; 2; 2; 2; 2; 2; 2; 2; 2; 2; 2; 2; 2; 2; 2; 0; 0; 0|]) - -let s000 = "" -let s001 = "\000\000\000\000\000\000\000\000\000\000\b\000\000\001\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016" -let s002 = "\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\000" -let s003 = "\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\016\016\016\016\016\016\016\016\016\016\016\016\016\000\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016" -let s004 = "\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002" -let s005 = "\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016" -let s006 = "\016\016\016\002\002\002\002\002\002\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016" -let s007 = "\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\016\002" -let s008 = "\016\002\002\016\002\002\016\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016" -let s009 = "\011\011\011\011\011\011\016\016\016\016\016\016\016\016\016\016\002\002\002\002\002\002\002\002\002\002\002\016\000\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016" -let s010 = "\016\016\016\016\016\016\016\016\016\016\016\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016" -let s011 = "\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\002\002\002\002\002\002\011\016\002\002\002\002\002\002\016\016\002\002\016\002\002\002\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016" -let s012 = "\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\011\016\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002" -let s013 = "\002\002\002\002\002\002\002\002\002\002\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016" -let s014 = "\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\002\002\002\002\002\002\002\002\002\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016" -let s015 = "\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\002\002\002\002\002\002\002\002\016\016\016\016\016\016\016\016\016\002\016\016" -let s016 = "\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\002\002\002\016\002\002\002\002\002\002\002\002\002\016\002\002\002\016\002\002\002\002\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016" -let s017 = "\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\002\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016" -let s018 = "\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\011\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002" -let s019 = "\002\002\002\r\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\r\002\016\r\r" -let s020 = "\r\002\002\002\002\002\002\002\002\r\r\r\r\002\r\r\016\002\002\002\002\002\002\002\016\016\016\016\016\016\016\016\016\016\002\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016" -let s021 = "\016\002\r\r\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\016\002\r" -let s022 = "\r\002\002\002\002\016\016\r\r\016\016\r\r\002\016\016\016\016\016\016\016\016\016\002\016\016\016\016\016\016\016\016\016\016\002\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\016" -let s023 = "\016\002\002\r\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\016\r\r" -let s024 = "\r\002\002\016\016\016\016\002\002\016\016\002\002\002\016\016\016\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\002\016\016\016\002\016\016\016\016\016\016\016\016\016\016" -let s025 = "\r\002\002\002\002\002\016\002\002\r\016\r\r\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\002\002\002\002\002" -let s026 = "\016\002\r\r\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\016\002\002" -let s027 = "\r\002\002\002\002\016\016\r\r\016\016\r\r\002\016\016\016\016\016\016\016\002\002\002\016\016\016\016\016\016\016\016\016\016\002\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016" -let s028 = "\016\016\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\r" -let s029 = "\002\r\r\016\016\016\r\r\r\016\r\r\r\002\016\016\016\016\016\016\016\016\016\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016" -let s030 = "\002\r\r\r\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\002" -let s031 = "\002\r\r\r\r\016\002\002\002\016\002\002\002\002\016\016\016\016\016\016\016\002\002\016\016\016\016\016\016\016\016\016\016\016\002\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016" -let s032 = "\016\002\r\r\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\016\r\002" -let s033 = "\r\r\002\r\r\016\002\r\r\016\r\r\002\002\016\016\016\016\016\016\016\002\002\016\016\016\016\016\016\016\016\016\016\016\002\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016" -let s034 = "\002\002\r\r\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\002\016\002\r" -let s035 = "\r\002\002\002\002\016\r\r\r\016\r\r\r\002\011\016\016\016\016\016\016\016\016\002\016\016\016\016\016\016\016\016\016\016\002\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016" -let s036 = "\016\002\r\r\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016" -let s037 = "\016\016\016\016\016\016\016\016\016\016\002\016\016\016\016\002\r\r\002\002\002\016\002\016\r\r\r\r\r\r\r\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\r\r\016\016\016\016\016\016\016\016\016\016\016\016" -let s038 = "\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\016\r\002\002\002\002\002\002\002\016\016\016\016\016" -let s039 = "\016\016\016\016\016\016\016\002\002\002\002\002\002\002\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016" -let s040 = "\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\016\r\002\002\002\002\002\002\002\002\002\016\016\016" -let s041 = "\016\016\016\016\016\016\016\016\002\002\002\002\002\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016" -let s042 = "\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\016\002\016\002\016\016\016\016\r\r" -let s043 = "\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\002\002\002\002\002\002\002\002\002\002\002\002\002\r" -let s044 = "\002\002\002\002\002\016\002\002\016\016\016\016\016\002\002\002\002\002\002\002\002\002\002\002\016\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\016\016\016" -let s045 = "\016\016\016\016\016\016\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016" -let s046 = "\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\002\002\002\r\002\002\002\002\002\002\016\002\002\r\r\002\002\016" -let s047 = "\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\r\r\002\002\016\016\016\016\002\002\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\002\002\002\016\016\016\016\016\016\016\016\016\016\016" -let s048 = "\016\016\002\016\r\002\002\016\016\016\016\016\016\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016" -let s049 = "\007\007\007\007\007\007\007\007\007\007\007\007\007\007\007\007\007\007\007\007\007\007\007\007\007\007\007\007\007\007\007\007\007\007\007\007\007\007\007\007\007\007\007\007\007\007\007\007\007\007\007\007\007\007\007\007\007\007\007\007\007\007\007\007" -let s050 = "\007\007\007\007\007\007\007\007\007\007\007\007\007\007\007\007\007\007\007\007\007\007\007\007\007\007\007\007\007\007\007\007\015\015\015\015\015\015\015\015\015\015\015\015\015\015\015\015\015\015\015\015\015\015\015\015\015\015\015\015\015\015\015\015" -let s051 = "\015\015\015\015\015\015\015\015\015\015\015\015\015\015\015\015\015\015\015\015\015\015\015\015\015\015\015\015\015\015\015\015\015\015\015\015\015\015\015\015\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014" -let s052 = "\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014" -let s053 = "\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\002\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016" -let s054 = "\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\002\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\002\002\016\016\016\016\016\016\016\016\016\016\016" -let s055 = "\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\002\016\016\016\016\016\016\016\016\016\016\016\016" -let s056 = "\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\002\r\002\002\002\002\002\002\002\r\r" -let s057 = "\r\r\r\r\r\r\002\r\r\002\002\002\002\002\002\002\002\002\002\002\016\016\016\016\016\016\016\016\016\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016" -let s058 = "\016\016\016\016\016\016\016\016\016\016\016\002\002\002\000\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016" -let s059 = "\016\016\016\016\016\002\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016" -let s060 = "\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\002\002\r\r\r\r\002\002\r\r\r\016\016\016\016\r\r\002\r\r\r\r\r\r\002\002\002\016\016\016\016" -let s061 = "\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\002\r\r\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016" -let s062 = "\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\r\002\r\002\002\002\002\002\002\002\016\002\016\002\016\016\002\002\002\002\002\002\002\002\r\r\r\r\r\r\002\002\002\002\002\002\002\002\002\002\016\016\002" -let s063 = "\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002" -let s064 = "\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016" -let s065 = "\002\002\002\002\r\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\002\002\002\002\002\002\r\002\r\r\r" -let s066 = "\r\r\002\r\r\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\002\002\002\002\002\002\002\002\016\016\016\016\016\016\016\016\016\016\016\016" -let s067 = "\002\002\r\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\r\002\002\002\002\r\r\002\002\r\002\002\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016" -let s068 = "\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\r\002\002\r\r\r\002\r\002\002\002\r\r\016\016\016\016\016\016\016\016\016\016\016\016" -let s069 = "\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\r\r\r\r\r\r\r\r\002\002\002\002\002\002\002\002\r\r\002\002\016\016\016\016\016\016\016\016" -let s070 = "\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\002\002\016\002\002\002\002\002\002\002\002\002\002\002\002\002\r\002\002\002\002\002\002\002\016\016\016\016\002\016\016\016\016\016\016\002\016\016\r\002\002\016\016\016\016\016\016" -let s071 = "\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\016\002\002\002\002\002" -let s072 = "\016\016\016\016\016\016\016\016\016\016\016\000\002\017\000\000\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\000\000\000\000\000\000\000\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016" -let s073 = "\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016" -let s074 = "\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016" -let s075 = "\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\002\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016" -let s076 = "\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002" -let s077 = "\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002" -let s078 = "\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\002\002\002\002\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016" -let s079 = "\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016" -let s080 = "\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\002\002\002\016\002\002\002\002\002\002\002\002\002\002\016\016" -let s081 = "\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016" -let s082 = "\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016" -let s083 = "\016\016\002\016\016\016\002\016\016\016\016\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\r\r\002\002\r\016\016\016\016\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016" -let s084 = "\r\r\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\r\r\r\r\r\r\r\r\r\r\r\r" -let s085 = "\r\r\r\r\002\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\016\016\016\016\016\016\016\016\016\016\016\016\016\002" -let s086 = "\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\002\002\002\002\002\002\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016" -let s087 = "\016\016\016\016\016\016\016\002\002\002\002\002\002\002\002\002\002\002\r\r\016\016\016\016\016\016\016\016\016\016\016\016\007\007\007\007\007\007\007\007\007\007\007\007\007\007\007\007\007\007\007\007\007\007\007\007\007\007\007\007\007\016\016\016" -let s088 = "\002\002\002\r\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\r\r\002\002\002\002\r\r\002\002\r\r" -let s089 = "\r\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016" -let s090 = "\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\002\002\002\002\002\r\r\002\002\r\r\002\002\016\016\016\016\016\016\016\016\016" -let s091 = "\016\016\016\002\016\016\016\016\016\016\016\016\002\r\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\016\016\016" -let s092 = "\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\016\002\002\002\016\016\002\002\016\016\016\016\016\002\002" -let s093 = "\016\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\r\002\002\r\r\016\016\016\016\016\r\002\016\016\016\016\016\016\016\016\016" -let s094 = "\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\r\r\002\r\r\002\r\r\016\r\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016" -let s095 = "\t\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\t\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\t\n\n\n\n\n\n\n" -let s096 = "\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\t\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\t\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n" -let s097 = "\n\n\n\n\n\n\n\n\n\n\n\n\t\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\t\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n" -let s098 = "\n\n\n\n\t\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\t\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\t\n\n\n" -let s099 = "\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\t\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\t\n\n\n\n\n\n\n\n\n\n\n" -let s100 = "\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\t\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\t\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n" -let s101 = "\n\n\n\n\n\n\n\n\t\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\t\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n" -let s102 = "\n\n\n\n\n\n\n\n\t\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\n\016\016\016\016\016\016\016\016\016\016\016\016\015\015\015\015\015\015\015\015\015\015\015\015\015\015\015\015" -let s103 = "\015\015\015\015\015\015\015\016\016\016\016\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\014\016\016\016\016" -let s104 = "\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016" -let s105 = "\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016" -let s106 = "\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\000\000\000\000\000\000\000\000\000\000\000\000\016\016\016\016" -let s107 = "\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\016\016" -let s108 = "\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016" -let s109 = "\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\002\002\002\002\016\016\016\016\016" -let s110 = "\016\002\002\002\016\002\002\016\016\016\016\016\002\002\002\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\002\002\016\016\016\016\002" -let s111 = "\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016" -let s112 = "\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\002\002\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016" -let s113 = "\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016" -let s114 = "\016\016\016\016\016\016\002\002\002\002\002\002\002\002\002\002\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016" -let s115 = "\r\002\r\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\002\002\002\002\002\002\002" -let s116 = "\002\002\002\002\002\002\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002" -let s117 = "\002\002\r\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\r\r\r\002\002\002\002\r\r\002\002\016\016\011\016\016" -let s118 = "\016\016\016\016\016\016\016\016\016\016\016\016\016\011\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016" -let s119 = "\002\002\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\002\002\002\002\r\002\002\002\002\002\002\002\002\016\016\016\016\016\016\016\016\016\016\016" -let s120 = "\016\016\016\016\016\r\r\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\016\016\016\016\016\016\016\016\016\016\016\016" -let s121 = "\002\002\r\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\r\r\r\002\002\002\002\002\002\002\002\002\r" -let s122 = "\r\016\011\011\016\016\016\016\016\002\002\002\002\016\r\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016" -let s123 = "\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\r\r\r\002\002\002\r\r\002\r\002\002\016\016\016\016\016\016\002\016" -let s124 = "\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\r\r\r\002\002\002\002\002\002\002\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016" -let s125 = "\002\r\r\r\r\016\016\r\r\016\016\r\r\r\016\016\016\016\016\016\016\016\016\002\016\016\016\016\016\016\016\016\016\016\r\r\016\016\002\002\002\002\002\002\002\016\016\016\002\002\002\002\002\016\016\016\016\016\016\016\016\016\016\016" -let s126 = "\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\r\r\r\002\002\002\002\002\002\002\002" -let s127 = "\r\r\002\002\002\r\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016" -let s128 = "\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\r\r\002\002\002\002\002\002\r\002\r\r\002\r\002" -let s129 = "\002\r\002\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016" -let s130 = "\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\r\r\002\002\002\002\016\016\r\r\r\r\002\002\r\002" -let s131 = "\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016" -let s132 = "\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\r\r\r\002\002\002\002\002\002\002\002\r\r\002\r\002" -let s133 = "\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\r\002\r\r\002\002\002\002\002\002\r\002\016\016\016\016\016\016\016\016" -let s134 = "\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\002\002\r\r\002\002\002\002\r\002\002\002\002\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016" -let s135 = "\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\r\r\r\002\002\002\002\002\002\002\002\002\r\002\002\016\016\016\016\016" -let s136 = "\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\r\r\r\r\r\016\r\r\016\016\002\002\r\002\011" -let s137 = "\r\011\r\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016" -let s138 = "\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\r\r\r\002\002\002\002\016\016\002\002\r\r\r\r\002\016\016\016\r\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016" -let s139 = "\016\002\002\002\002\002\002\002\002\002\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\002\002\002\002\002\r\011\002\002\002\002\016" -let s140 = "\016\016\016\016\016\016\016\002\016\016\016\016\016\016\016\016\016\002\002\002\002\002\002\r\r\002\002\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016" -let s141 = "\016\016\016\016\011\011\011\011\011\011\002\002\002\002\002\002\002\002\002\002\002\002\002\r\002\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016" -let s142 = "\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\r\002\002\002\002\002\002\002\016\002\002\002\002\002\002\r\002" -let s143 = "\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\016\r\002\002\002\002\002\002\002\r\002\002\r\002\002\016\016\016\016\016\016\016\016\016" -let s144 = "\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\002\002\002\002\002\016\016\016\002\016\002\002\016\002" -let s145 = "\002\002\002\002\002\002\011\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016" -let s146 = "\016\016\016\016\016\016\016\016\016\016\r\r\r\r\r\016\002\002\016\r\r\002\r\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016" -let s147 = "\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\002\r\r\016\016\016\016\016\016\016\016\016" -let s148 = "\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\000\000\000\000\000\000\000\000\000\016\016\016\016\016\016\016" -let s149 = "\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\002\002\002\002\016\016\016\016\016\016\016\016\016\016\016" -let s150 = "\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\002\002\002\002\002\002\016\016\016\016\016\016\016\016\016" -let s151 = "\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\016\r\r\r\r\r\r\r\r\r\r\r\r\r\r\r\r\r\r\r\r\r\r\r\r\r\r\r\r\r\r\r\r\r\r\r\r\r\r\r\r\r\r\r\r\r\r\r" -let s152 = "\r\r\r\r\r\r\r\r\016\016\016\016\016\016\016\002\002\002\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016" -let s153 = "\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\016\016\016\016\016\016\016\016\016\016\016\r\r\016\016\016\016\016\016\016\016\016\016\016\016\016\016" -let s154 = "\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\002\016\000\000\000\000\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016" -let s155 = "\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\r\002\002\002\016\016\016\r\002\002\002\002\002\000\000\000\000\000\000\000\000\002\002\002\002\002" -let s156 = "\002\002\002\016\016\002\002\002\002\002\002\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\002\002\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016" -let s157 = "\016\016\002\002\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016" -let s158 = "\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\016\016\016\016\002\002\002\002\002" -let s159 = "\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\016\016\016\016\016\016\016\016\002\016\016\016\016\016\016\016\016\016\016" -let s160 = "\016\016\016\016\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\002\002\002\002\016\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016" -let s161 = "\002\002\002\002\002\002\002\016\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\016\016\002\002\002\002\002\002\002\016\002\002\016\002\002\002\002\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016" -let s162 = "\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\002\002\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016" -let s163 = "\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\002\002\002\002\002\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016" -let s164 = "\016\016\016\016\002\002\002\002\002\002\002\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016" -let s165 = "\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\012\012\012\012\012\012\012\012\012\012\012\012\012\012\012\012\012\012\012\012\012\012\012\012\012\012" -let s166 = "\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\016\002\002\002\002\002" -let s167 = "\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002" -let s168 = "\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000" -let s169 = "\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\002\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000" - -let grapheme_cluster_boundary = - [|[|s001; s002; s003; s000; s000; s000; s000; s000; s000; s000; s000; s000; - s004; s005; s000; s000; s000; s000; s006; s000; s000; s000; s007; s008; - s009; s010; s000; s011; s012; s013; s014; s015; s016; s017; s000; s018; - s019; s020; s021; s022; s023; s024; s023; s025; s026; s027; s028; s029; - s030; s031; s032; s033; s034; s035; s036; s037; s038; s039; s040; s041; - s042; s043; s044; s045|]; - [|s046; s047; s048; s000; s049; s050; s051; s052; s000; s000; s000; s000; - s000; s053; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; - s000; s000; s000; s000; s054; s055; s056; s057; s058; s000; s059; s000; - s060; s000; s000; s000; s061; s062; s063; s064; s065; s066; s067; s068; - s069; s000; s000; s070; s000; s000; s000; s071; s000; s000; s000; s000; - s000; s000; s000; s000|]; - [|s072; s073; s000; s074; s000; s000; s000; s000; s000; s000; s000; s000; - s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; - s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; - s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; - s000; s000; s000; s075; s000; s076; s000; s077; s000; s000; s000; s000; - s000; s000; s000; s000|]; - [|s078; s000; s079; s000; s000; s000; s000; s000; s000; s000; s000; s000; - s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; - s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; - s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; - s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; - s000; s000; s000; s000|]; - [||]; [||]; [||]; [||]; [||]; [||]; - [|s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; - s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; - s000; s080; s081; s082; s000; s000; s000; s000; s083; s000; s084; s085; - s086; s087; s088; s089; s090; s091; s092; s093; s000; s000; s000; s094; - s095; s096; s097; s098; s099; s100; s101; s095; s096; s097; s098; s099; - s100; s101; s095; s096|]; - [|s097; s098; s099; s100; s101; s095; s096; s097; s098; s099; s100; s101; - s095; s096; s097; s098; s099; s100; s101; s095; s096; s097; s098; s099; - s100; s101; s095; s096; s097; s098; s099; s100; s101; s095; s096; s097; - s098; s099; s100; s101; s095; s096; s097; s098; s099; s100; s101; s095; - s096; s097; s098; s099; s100; s101; s095; s096; s097; s098; s099; s100; - s101; s095; s096; s097|]; - [|s098; s099; s100; s101; s095; s096; s097; s098; s099; s100; s101; s095; - s096; s097; s098; s099; s100; s101; s095; s096; s097; s098; s099; s100; - s101; s095; s096; s097; s098; s099; s100; s101; s095; s096; s097; s098; - s099; s100; s101; s095; s096; s097; s098; s099; s100; s101; s095; s096; - s097; s098; s099; s100; s101; s095; s096; s097; s098; s099; s100; s101; - s095; s096; s097; s098|]; - [|s099; s100; s101; s095; s096; s097; s098; s099; s100; s101; s095; s096; - s097; s098; s099; s100; s101; s095; s096; s097; s098; s099; s100; s101; - s095; s096; s097; s098; s099; s100; s102; s103; s000; s000; s000; s000; - s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; - s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; - s000; s000; s000; s000|]; - [||]; - [|s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; - s104; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; - s105; s000; s000; s002; s000; s000; s081; s106; s000; s000; s000; s000; - s000; s000; s000; s107; s000; s000; s000; s108; s000; s109; s000; s000; - s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; - s000; s000; s000; s000|]; - [|s000; s000; s000; s000; s000; s000; s000; s000; s110; s000; s000; s111; - s000; s000; s000; s000; s000; s000; s000; s000; s112; s000; s000; s000; - s000; s000; s113; s000; s000; s114; s000; s000; s115; s116; s117; s118; - s119; s120; s121; s122; s123; s000; s000; s124; s034; s125; s000; s000; - s126; s127; s128; s129; s000; s000; s130; s131; s132; s064; s133; s000; - s134; s000; s000; s000|]; - [|s135; s000; s000; s000; s136; s137; s000; s138; s139; s140; s141; s000; - s000; s000; s000; s000; s142; s000; s143; s000; s144; s145; s146; s000; - s000; s000; s000; s147; s000; s000; s000; s000; s000; s000; s000; s000; - s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; - s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; - s000; s000; s000; s000|]; - [|s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; - s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; - s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; - s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; - s148; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; - s000; s000; s000; s000|]; - [||]; [||]; [||]; - [|s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; s149; - s150; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; - s000; s000; s000; s000; s000; s151; s152; s153; s000; s000; s000; s000; - s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; - s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; - s000; s000; s000; s000|]; - [||]; [||]; [||]; [||]; - [|s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; - s000; s000; s000; s000; s000; s000; s154; s000; s000; s000; s000; s000; - s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; - s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; - s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; - s000; s000; s000; s000|]; - [|s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; - s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; - s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; - s000; s155; s156; s000; s000; s157; s000; s000; s000; s000; s000; s000; - s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; - s000; s000; s000; s000|]; - [|s000; s000; s000; s000; s000; s000; s000; s000; s158; s159; s160; s000; - s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; - s000; s000; s000; s000; s000; s000; s000; s000; s161; s000; s000; s000; - s150; s000; s000; s000; s000; s000; s000; s162; s000; s000; s000; s000; - s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; - s000; s000; s000; s000|]; - [|s000; s000; s000; s163; s000; s164; s000; s000; s000; s000; s000; s000; - s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; - s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; - s000; s000; s000; s165; s000; s000; s000; s000; s000; s000; s000; s166; - s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; - s000; s000; s000; s000|]; - [||]; [||]; [||]; [||]; [||]; [||]; [||]; [||]; [||]; [||]; [||]; - [||]; [||]; [||]; [||]; [||]; [||]; [||]; [||]; [||]; [||]; [||]; - [||]; [||]; [||]; [||]; [||]; [||]; [||]; [||]; [||]; [||]; [||]; - [||]; [||]; [||]; [||]; [||]; [||]; [||]; [||]; [||]; [||]; [||]; - [||]; [||]; [||]; [||]; [||]; [||]; [||]; [||]; [||]; [||]; [||]; - [||]; [||]; [||]; [||]; [||]; [||]; [||]; [||]; [||]; [||]; [||]; - [||]; [||]; [||]; [||]; [||]; [||]; [||]; [||]; [||]; [||]; [||]; - [||]; [||]; [||]; [||]; [||]; [||]; [||]; [||]; [||]; [||]; [||]; - [||]; [||]; [||]; [||]; [||]; [||]; [||]; [||]; [||]; [||]; [||]; - [||]; [||]; [||]; [||]; [||]; [||]; [||]; [||]; [||]; [||]; [||]; - [||]; [||]; [||]; [||]; [||]; [||]; [||]; [||]; [||]; [||]; [||]; - [||]; [||]; [||]; [||]; [||]; [||]; [||]; [||]; [||]; [||]; [||]; - [||]; [||]; [||]; [||]; [||]; [||]; [||]; [||]; [||]; [||]; [||]; - [||]; [||]; [||]; [||]; [||]; [||]; [||]; [||]; [||]; [||]; [||]; - [||]; [||]; [||]; [||]; [||]; [||]; [||]; [||]; [||]; [||]; [||]; - [||]; [||]; [||]; [||]; [||]; [||]; [||]; [||]; [||]; [||]; [||]; - [||]; [||]; [||]; [||]; [||]; [||]; [||]; [||]; [||]; [||]; [||]; - [||]; [||]; [||]; [||]; [||]; - [|s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; - s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; - s000; s000; s000; s000; s000; s000; s000; s000; s167; s004; s168; s168; - s004; s004; s004; s169; s168; s168; s168; s168; s168; s168; s168; s168; - s168; s168; s168; s168; s168; s168; s168; s168; s168; s168; s168; s168; - s168; s168; s168; s168|]; - [|s168; s168; s168; s168; s168; s168; s168; s168; s168; s168; s168; s168; - s168; s168; s168; s168; s168; s168; s168; s168; s168; s168; s168; s168; - s168; s168; s168; s168; s168; s168; s168; s168; s000; s000; s000; s000; - s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; - s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; s000; - s000; s000; s000; s000|]|] \ No newline at end of file diff --git a/vendor/notty/src/no-uucp/notty_uucp_data.mli b/vendor/notty/src/no-uucp/notty_uucp_data.mli deleted file mode 100644 index 4058ed3c39d..00000000000 --- a/vendor/notty/src/no-uucp/notty_uucp_data.mli +++ /dev/null @@ -1,14 +0,0 @@ -(* Do not edit. - * - * This module contains select unicode properties extracted from Uucp, - * using `./support/gen_unicode_props.ml`. - * - * Unicode version 13.0.0. - *) - -(* Uucp.Break.tty_width_hint *) -val tty_width_hint: int array * int array * int array - -(* Uucp.Break.Low.grapheme_cluster. *) -val grapheme_cluster_boundary: string array array - diff --git a/vendor/notty/src/notty.ml b/vendor/notty/src/notty.ml deleted file mode 100644 index e102145c961..00000000000 --- a/vendor/notty/src/notty.ml +++ /dev/null @@ -1,915 +0,0 @@ -(* Copyright (c) 2016-2017 David Kaloper Meršinjak. All rights reserved. - See LICENSE.md. *) - -let invalid_arg fmt = Format.kasprintf invalid_arg fmt - -let (&.) f g x = f (g x) - -let btw (x : int) a b = a <= x && x <= b -let bit n b = b land (1 lsl n) > 0 - -let max (a : int) b = if a > b then a else b -let min (a : int) b = if a < b then a else b - -let is_C0 x = x < 0x20 || x = 0x7f -and is_C1 x = 0x80 <= x && x < 0xa0 -let is_ctrl x = is_C0 x || is_C1 x -and is_ascii x = x < 0x80 - -let rec concatm z (@) xs = - let rec accum (@) = function - | []|[_] as xs -> xs - | a::b::xs -> (a @ b) :: accum (@) xs in - match xs with [] -> z | [x] -> x | xs -> concatm z (@) (accum (@) xs) - -let rec linspcm z (@) x n f = match n with - | 0 -> z - | 1 -> f x - | _ -> let m = n / 2 in linspcm z (@) x m f @ linspcm z (@) (x + m) (n - m) f - -let memo (type a) ?(hash=Hashtbl.hash) ?(eq=(=)) ~size f = - let module H = Ephemeron.K1.Make - (struct type t = a let (hash, equal) = (hash, eq) end) in - let t = H.create size in fun x -> - try H.find t x with Not_found -> let y = f x in H.add t x y; y - -module Buffer = struct - include Buffer - let buf = Buffer.create 1024 - let mkstring f = f buf; let res = contents buf in reset buf; res - let add_decimal b = function - | x when btw x 0 999 -> - let d1 = x / 100 and d2 = (x mod 100) / 10 and d3 = x mod 10 in - if d1 > 0 then 0x30 + d1 |> Char.unsafe_chr |> add_char b; - if (d1 + d2) > 0 then 0x30 + d2 |> Char.unsafe_chr |> add_char b; - 0x30 + d3 |> Char.unsafe_chr |> add_char b - | x -> string_of_int x |> add_string b - let add_chars b c n = for _ = 1 to n do add_char b c done -end - -module String = struct - include String - let sub0cp s i len = if i > 0 || len < length s then sub s i len else s - let of_chars_rev = function - | [] -> "" - | [c] -> String.make 1 c - | cs -> - let n = List.length cs in - let rec go bs i = Bytes.(function - | [] -> unsafe_to_string bs - | x::xs -> unsafe_set bs i x; go bs (pred i) xs - ) in go (Bytes.create n) (n - 1) cs -end - -module Option = struct - - let map f = function Some x -> Some (f x) | _ -> None - let get def = function Some x -> x | _ -> def - let to_list = function Some x -> [x] | _ -> [] - let (>>|) a f = map f a - let (>>=) a f = match a with Some x -> f x | _ -> None -end - -module Text = struct - - let err_ctrl u = invalid_arg "Notty: control char: U+%02X, %S" (Char.code u) - let err_malformed = invalid_arg "Notty: malformed UTF-8: %s, %S" - - type t = - | Ascii of string * int * int - | Utf8 of string * int array * int * int - - let equal t1 t2 = match (t1, t2) with - | (Utf8 (s1, _, i1, n1), Utf8 (s2, _, i2, n2)) - | (Ascii (s1, i1, n1), Ascii (s2, i2, n2)) -> i1 = i2 && n1 = n2 && s1 = s2 - | _ -> false - - let width = function Utf8 (_, _, _, w) -> w | Ascii (_, _, w) -> w - - let empty = Ascii ("", 0, 0) - - let is_empty t = width t = 0 - - let graphemes str = - let module Uuseg = Notty_grapheme_cluster in - let seg = Uuseg.create () in - let rec f (is, w as acc) i evt = - match Uuseg.add seg evt with - | `Await | `End -> acc - | `Uchar u -> f (is, w + Notty_uucp.tty_width_hint u) i `Await - | `Boundary -> - let is = match w with 0 -> is | 1 -> i::is | _ -> i::(-1)::is in - f (is, 0) i `Await in - let acc = Uutf.String.fold_utf_8 (fun acc i -> function - | `Malformed err -> err_malformed err str - | `Uchar _ as u -> f acc i u - ) ([0], 0) str in - f acc (String.length str) `End |> fst |> List.rev |> Array.of_list (*XXX*) - - let dead = ' ' - - let to_buffer buf = function - | Ascii (s, off, w) -> Buffer.add_substring buf s off w - | Utf8 (s, ix, off, w) -> - let x1 = match ix.(off) with - | -1 -> Buffer.add_char buf dead; ix.(off + 1) | x -> x - and x2 = ix.(off + w) in - Buffer.add_substring buf s x1 @@ - (if x2 = -1 then ix.(off + w - 1) else x2) - x1; - if x2 = -1 then Buffer.add_char buf dead - - let sub t x w = - let w1 = width t in - if w = 0 || x >= w1 then empty else - let w = min w (w1 - x) in - if w = w1 then t else match t with - Ascii (s, off, _) -> Ascii (s, off + x, w) - | Utf8 (s, ix, off, _) -> Utf8 (s, ix, off + x, w) - - let is_ascii_or_raise_ctrl s = - let (@!) s i = String.unsafe_get s i |> Char.code in - let rec go s acc i n = - if n = 0 then acc else - let x = s @! i in - if is_C0 x then - err_ctrl s.[i] s - else if x = 0xc2 && n > 1 && is_C1 (s @! (i + 1)) then - err_ctrl s.[i + 1] s - else go s (acc && is_ascii x) (i + 1) (n - 1) in - go s true 0 (String.length s) - - let of_ascii s = Ascii (s, 0, String.length s) - and of_unicode s = let x = graphemes s in Utf8 (s, x, 0, Array.length x - 1) - let of_unicode = memo ~eq:String.equal ~size:128 of_unicode - - let of_string = function - | "" -> empty - | s -> if is_ascii_or_raise_ctrl s then of_ascii s else of_unicode s - - let of_uchars ucs = of_string @@ Buffer.mkstring @@ fun buf -> - Array.iter (Buffer.add_utf_8_uchar buf) ucs - - let replicateu w u = - if is_ctrl (Uchar.to_int u) then - err_ctrl (Uchar.unsafe_to_char u) "" - else if w < 1 then empty - else if is_ascii (Uchar.to_int u) then - of_ascii (String.make w (Uchar.unsafe_to_char u)) - else of_unicode @@ Buffer.mkstring @@ fun buf -> - for _ = 1 to w do Buffer.add_utf_8_uchar buf u done - - let replicatec w c = replicateu w (Uchar.of_char c) -end - -module A = struct - - type color = int - type style = int - type t = { fg : color; bg : color; st : style } - - let equal t1 t2 = t1.fg = t2.fg && t1.bg = t2.bg && t1.st = t2.st - - let black = 0x01000000 - and red = 0x01000001 - and green = 0x01000002 - and yellow = 0x01000003 - and blue = 0x01000004 - and magenta = 0x01000005 - and cyan = 0x01000006 - and white = 0x01000007 - and lightblack = 0x01000008 - and lightred = 0x01000009 - and lightgreen = 0x0100000a - and lightyellow = 0x0100000b - and lightblue = 0x0100000c - and lightmagenta = 0x0100000d - and lightcyan = 0x0100000e - and lightwhite = 0x0100000f - - let tag c = (c land 0x03000000) lsr 24 - - let rgb ~r ~g ~b = - if r < 0 || g < 0 || b < 0 || r > 5 || g > 5 || b > 5 then - invalid_arg "Notty.A.rgb %d %d %d: channel out of range" r g b - else 0x01000000 lor (r * 36 + g * 6 + b + 16) - - let gray level = - if level < 0 || level > 23 then - invalid_arg "Notty.A.gray %d: level out of range" level - else 0x01000000 lor (level + 232) - - let rgb_888 ~r ~g ~b = - if r < 0 || g < 0 || b < 0 || r > 255 || g > 255 || b > 255 then - invalid_arg "Notty.A.rgb_888 %d %d %d: channel out of range" r g b - else 0x02000000 lor ((r lsl 16) lor (g lsl 8) lor b) - - let i x = x land 0xff - and r x = x lsr 16 land 0xff - and g x = x lsr 8 land 0xff - and b x = x land 0xff - - let bold = 1 - and italic = 2 - and dim = 3 - and underline = 4 - and blink = 8 - and reverse = 16 - - let empty = { fg = 0; bg = 0; st = 0 } - - let (++) a1 a2 = - if a1 == empty then a2 else if a2 == empty then a1 else - { fg = (match a2.fg with 0 -> a1.fg | x -> x) - ; bg = (match a2.bg with 0 -> a1.bg | x -> x) - ; st = a1.st lor a2.st } - - let fg fg = { empty with fg } - let bg bg = { empty with bg } - let st st = { empty with st } -end - -module I = struct - - type dim = int * int - - type t = - | Empty - | Segment of A.t * Text.t - | Hcompose of (t * t) * dim - | Vcompose of (t * t) * dim - | Zcompose of (t * t) * dim - | Hcrop of (t * int * int) * dim - | Vcrop of (t * int * int) * dim - | Void of dim - - let width = function - | Empty -> 0 - | Segment (_, text) -> Text.width text - | Hcompose (_, (w, _)) -> w - | Vcompose (_, (w, _)) -> w - | Zcompose (_, (w, _)) -> w - | Hcrop (_, (w, _)) -> w - | Vcrop (_, (w, _)) -> w - | Void (w, _) -> w [@@inline] - - let height = function - | Empty -> 0 - | Segment _ -> 1 - | Hcompose (_, (_, h)) -> h - | Vcompose (_, (_, h)) -> h - | Zcompose (_, (_, h)) -> h - | Hcrop (_, (_, h)) -> h - | Vcrop (_, (_, h)) -> h - | Void (_, h) -> h [@@inline] - - let equal t1 t2 = - let rec eq t1 t2 = match (t1, t2) with - | (Empty, Empty) -> true - | (Segment (a1, t1), Segment (a2, t2)) -> - A.equal a1 a2 && Text.equal t1 t2 - | (Hcompose ((a, b), _), Hcompose ((c, d), _)) - | (Vcompose ((a, b), _), Vcompose ((c, d), _)) - | (Zcompose ((a, b), _), Zcompose ((c, d), _)) -> eq a c && eq b d - | (Hcrop ((a, i1, n1), _), Hcrop ((b, i2, n2), _)) - | (Vcrop ((a, i1, n1), _), Vcrop ((b, i2, n2), _)) -> - i1 = i2 && n1 = n2 && eq a b - | (Void (a, b), Void (c, d)) -> a = c && b = d - | _ -> false in - width t1 = width t2 && height t1 = height t2 && eq t1 t2 - - let empty = Empty - - let (<|>) t1 t2 = match (t1, t2) with - | (_, Empty) -> t1 - | (Empty, _) -> t2 - | _ -> - let w = width t1 + width t2 - and h = max (height t1) (height t2) in - Hcompose ((t1, t2), (w, h)) - - let (<->) t1 t2 = match (t1, t2) with - | (_, Empty) -> t1 - | (Empty, _) -> t2 - | _ -> - let w = max (width t1) (width t2) - and h = height t1 + height t2 in - Vcompose ((t1, t2), (w, h)) - - let () t1 t2 = match (t1, t2) with - | (_, Empty) -> t1 - | (Empty, _) -> t2 - | _ -> - let w = max (width t1) (width t2) - and h = max (height t1) (height t2) in - Zcompose ((t1, t2), (w, h)) - - let void w h = - if w < 1 && h < 1 then Empty else Void (max 0 w, max 0 h) - - let lincropinv crop void (++) init fini img = - match (init >= 0, fini >= 0) with - | (true, true) -> crop init fini img - | (true, _ ) -> crop init 0 img ++ void (-fini) - | (_ , true) -> void (-init) ++ crop 0 fini img - | _ -> void (-init) ++ img ++ void (-fini) - - let hcrop = - let ctor left right img = - let h = height img and w = width img - left - right in - if w > 0 then Hcrop ((img, left, right), (w, h)) else void w h - in lincropinv ctor (fun w -> void w 0) (<|>) - - let vcrop = - let ctor top bottom img = - let w = width img and h = height img - top - bottom in - if h > 0 then Vcrop ((img, top, bottom), (w, h)) else void w h - in lincropinv ctor (void 0) (<->) - - let crop ?(l=0) ?(r=0) ?(t=0) ?(b=0) img = - let img = if l <> 0 || r <> 0 then hcrop l r img else img in - if t <> 0 || b <> 0 then vcrop t b img else img - - let hpad left right img = hcrop (-left) (-right) img - - let vpad top bottom img = vcrop (-top) (-bottom) img - - let pad ?(l=0) ?(r=0) ?(t=0) ?(b=0) img = - crop ~l:(-l) ~r:(-r) ~t:(-t) ~b:(-b) img - - let hcat = concatm empty (<|>) - - let vcat = concatm empty (<->) - - let zcat xs = List.fold_right () xs empty - - let text attr tx = - if Text.is_empty tx then void 0 1 else Segment (attr, tx) - - let string attr s = text attr (Text.of_string s) - - let uchars attr a = text attr (Text.of_uchars a) - - let tabulate m n f = - let m = max m 0 and n = max n 0 in - linspcm empty (<->) 0 n (fun y -> linspcm empty (<|>) 0 m (fun x -> f x y)) - - let chars ctor attr c w h = - if w < 1 || h < 1 then void w h else - let line = text attr (ctor w c) in tabulate 1 h (fun _ _ -> line) - - let char = chars Text.replicatec - let uchar = chars Text.replicateu - - let hsnap ?(align=`Middle) w img = - let off = width img - w in match align with - | `Left -> hcrop 0 off img - | `Right -> hcrop off 0 img - | `Middle -> let w1 = off / 2 in hcrop w1 (off - w1) img - - let vsnap ?(align=`Middle) h img = - let off = height img - h in match align with - | `Top -> vcrop 0 off img - | `Bottom -> vcrop off 0 img - | `Middle -> let h1 = off / 2 in vcrop h1 (off - h1) img - - module Fmt = struct - - open Format - - type stag += Attr of A.t - - let push r x = r := x :: !r - let pop r = r := (match !r with _::xs -> xs | _ -> []) - let top_a r = match !r with a::_ -> a | _ -> A.empty - - let create () = - let img, line, attr = ref empty, ref empty, ref [] in - let fmt = formatter_of_out_functions { - out_flush = (fun () -> - img := !img <-> !line; line := empty; attr := []) - ; out_newline = (fun () -> - img := !img <-> !line; line := void 0 1) - ; out_string = (fun s i n -> - line := !line <|> string (top_a attr) String.(sub0cp s i n)) - (* Not entirely clear; either or both could be void: *) - ; out_spaces = (fun w -> line := !line <|> char (top_a attr) ' ' w 1) - ; out_indent = (fun w -> line := !line <|> char (top_a attr) ' ' w 1) - } in - pp_set_formatter_stag_functions fmt { - (pp_get_formatter_stag_functions fmt ()) with - mark_open_stag = - (function Attr a -> push attr A.(top_a attr ++ a); "" | _ -> "") - ; mark_close_stag = (fun _ -> pop attr; "") }; - pp_set_mark_tags fmt true; - fmt, fun () -> let i = !img in img := empty; line := empty; attr := []; i - - let ppf, reset = create () - - let kstrf ?(attr = A.empty) ?(w = 1000000) k format = - let m = ref 0 in - let f1 _ () = - m := pp_get_margin ppf (); - pp_set_margin ppf w; - pp_open_stag ppf (Attr attr) - and k _ = - pp_print_flush ppf (); - pp_set_margin ppf !m; - reset () |> k - in kfprintf k ppf ("%a" ^^ format) f1 () - - let strf ?attr ?w format = kstrf ?attr ?w (fun i -> i) format - - let attr attr f fmt x = - pp_open_stag fmt (Attr attr); f fmt x; pp_close_stag fmt () - end - - let kstrf, strf, pp_attr = Fmt.(kstrf, strf, attr) -end - -module Operation = struct - - type t = - End - | Skip of int * t - | Text of A.t * Text.t * t - - let skip n k = if n = 0 then k else match k with - End -> End - | Skip (m, k) -> Skip (m + n, k) - | _ -> Skip (n, k) [@@inline] - - let rec scan x w row i k = - let open I in match i with - - | Empty | Void _ -> skip w k - - | Segment _ when row > 0 -> skip w k - | Segment (attr, text) -> - let t = Text.sub text x w in - let w1 = Text.width t in - let p = if w > w1 then skip (w - w1) k else k in - if w1 > 0 then Text (attr, t, p) else p - - | Hcompose ((i1, i2), _) -> - let w1 = width i1 - and w2 = width i2 in - if x >= w1 + w2 then skip w k else - if x >= w1 then scan (x - w1) w row i2 k else - if x + w <= w1 then scan x w row i1 k else - scan x (w1 - x) row i1 @@ scan 0 (w - w1 + x) row i2 @@ k - - | Vcompose ((i1, i2), _) -> - let h1 = height i1 - and h2 = height i2 in - if row >= h1 + h2 then skip w k else - if row >= h1 then scan x w (row - h1) i2 k else scan x w row i1 k - - | Zcompose ((i1, i2), _) -> - let rec stitch x w row i = function - | End -> scan x w row i End - | Text (a, t, ops) as opss -> - let w1 = Text.width t in - if w1 >= w then opss else - Text (a, t, stitch (x + w1) (w - w1) row i ops) - | Skip (w1, ops) -> - scan x w1 row i @@ - if w1 >= w then ops else stitch (x + w1) (w - w1) row i ops - in stitch x w row i2 @@ scan x w row i1 @@ k - - | Hcrop ((i, left, _), (w1, _)) -> - if x >= w1 then skip w k else - if x + w <= w1 then scan (x + left) w row i k else - scan (x + left) (w1 - x) row i @@ skip (w - w1 + x) k - - | Vcrop ((i, top, _), (_, h1)) -> - if row < h1 then scan x w (top + row) i k else skip w k - - let of_image (x, y) (w, h) i = - List.init h (fun off -> scan x (x + w) (y + off) i End) -end - -module Cap = struct - - type op = Buffer.t -> unit - - let (&) op1 op2 buf = op1 buf; op2 buf - - type t = { - skip : int -> op - ; sgr : A.t -> op - ; newline : op - ; clreol : op - ; cursvis : bool -> op - ; cursat : int -> int -> op - ; cubcuf : int -> op - ; cuucud : int -> op - ; cr : op - ; altscr : bool -> op - ; mouse : bool -> op - ; bpaste : bool -> op - } - - let ((<|), (<.), ( () - | 1 -> let c = A.i fg in - if c < 8 then ( buf <. ';'; buf buf <| ";38;2;"; rgb888 buf fg ); - ( match A.tag bg with - 0 -> () - | 1 -> let c = A.i bg in - if c < 8 then ( buf <. ';'; buf buf <| ";48;2;"; rgb888 buf bg ); - if st <> 0 then - ( let rec go f xs = match (f, xs) with - | (0, _) | (_, []) -> () - | (_, x::xs) -> if f land 1 > 0 then buf <| x; go (f lsr 1) xs in - go st sts ); - buf <. 'm' - - let ansi = { - skip = (fun n b -> b <| "\x1b[0m"; Buffer.add_chars b ' ' n) - ; newline = (fun b -> b <| "\x1bE") - ; altscr = (fun x b -> b <| if x then "\x1b[?1049h" else "\x1b[?1049l") - ; cursat = (fun w h b -> b <| "\x1b["; b b <| "\x1b["; b b <| "\x1b["; b b <| "\x1b[1G") - ; clreol = (fun b -> b <| "\x1b[K") - ; cursvis = (fun x b -> b <| if x then "\x1b[34h\x1b[?25h" else "\x1b[?25l") - ; mouse = (fun x b -> b <| if x then "\x1b[?1000;1002;1005;1015;1006h" - else "\x1b[?1000;1002;1005;1015;1006l") - ; bpaste = (fun x b -> b <| if x then "\x1b[?2004h" else "\x1b[?2004l") - ; sgr } - - let no0 _ = () - and no1 _ _ = () - and no2 _ _ _ = () - - let dumb = { - skip = (fun n b -> Buffer.add_chars b ' ' n) - ; newline = (fun b -> b <| "\n") - ; altscr = no1 - ; cursat = no2 - ; cubcuf = no1 - ; cuucud = no1 - ; cr = no0 - ; clreol = no0 - ; cursvis = no1 - ; sgr = no1 - ; mouse = no1 - ; bpaste = no1 - } - - let erase cap buf = cap.sgr A.empty buf; cap.clreol buf (* KEEP ETA-LONG. *) - let cursat0 cap w h = cap.cursat (max w 0 + 1) (max h 0 + 1) -end - -module Render = struct - - open Cap - open Operation - - let skip_op cap buf n = cap.skip n buf - let text_op cap buf a x = cap.sgr a buf; Text.to_buffer buf x - - let rec line cap buf = function - End -> erase cap buf - | Skip (n, End) -> erase cap buf; skip_op cap buf n - | Text (a, x, End) -> erase cap buf; text_op cap buf a x - | Skip (n, ops) -> skip_op cap buf n; line cap buf ops - | Text (a, x, ops) -> text_op cap buf a x; line cap buf ops - - let rec lines cap buf = function - [] -> () - | [ln] -> line cap buf ln; cap.sgr A.empty buf - | ln::lns -> line cap buf ln; cap.newline buf; lines cap buf lns - - let to_buffer buf cap off dim img = - Operation.of_image off dim img |> lines cap buf - - let pp cap ppf img = - let open Format in - let buf = Buffer.create (I.width img * 2) in - let h, w = I.(height img, width img |> min (pp_get_margin ppf ())) in - let img = I.(img vpad (h - 1) 0 (char A.empty ' ' w 1)) in - pp_open_vbox ppf 0; - for y = 0 to h - 1 do - Buffer.clear buf; to_buffer buf cap (0, y) (w, 1) img; - pp_print_as ppf w (Buffer.contents buf); - if y < h - 1 then pp_print_cut ppf () - done; - pp_close_box ppf () - - let pp_image = pp Cap.ansi - let pp_attr ppf a = - let string_ = I.string A.empty in - pp_image ppf I.(string_ "<" <|> string a "ATTR" <|> string_ ">") -end - -module Unescape = struct - - type special = [ - `Escape - | `Enter - | `Tab - | `Backspace - | `Insert - | `Delete - | `Home | `End - | `Arrow of [ `Up | `Down | `Left | `Right ] - | `Page of [ `Up | `Down ] - | `Function of int - ] - - type button = [ `Left | `Middle | `Right | `Scroll of [ `Up | `Down ] ] - - type mods = [ `Meta | `Ctrl | `Shift ] list - - type key = [ special | `Uchar of Uchar.t | `ASCII of char ] * mods - - type mouse = [ `Press of button | `Drag | `Release ] * (int * int) * mods - - type paste = [ `Start | `End ] - - type event = [ `Key of key | `Mouse of mouse | `Paste of paste ] - - type esc = - C0 of char - | C1 of char - | SS2 of char - | CSI of string * int list * char - | Esc_M of int * int * int - | Uchar of Uchar.t - - let uchar = function `Uchar u -> u | `ASCII c -> Uchar.of_char c - - let csi = - let open Option in - let rec priv acc = function - | x::xs when btw x 0x3c 0x3f -> priv (Char.unsafe_chr x::acc) xs - | xs -> param (String.of_chars_rev acc) None [] xs - and param prv p ps = function - | x::xs when btw x 0x30 0x39 -> param prv (Some (get 0 p * 10 + x - 0x30)) ps xs - | 0x3b::xs -> param prv None (get 0 p :: ps) xs - | xs -> code prv (List.rev (to_list p @ ps)) xs - and code prv ps = function (* Conflate two classes because urxvt... *) - | x::xs when btw x 0x20 0x2f || btw x 0x40 0x7e -> - Some (CSI (prv, ps, (Char.chr x)), xs) - | _ -> None in - priv [] - - let rec demux = - let chr = Char.chr in function - | 0x1b::0x5b::0x4d::a::b::c::xs -> Esc_M (a, b, c) :: demux xs - | 0x1b::0x5b::xs | 0x9b::xs -> - let (r, xs) = csi xs |> Option.get (C1 '\x5b', xs) in r :: demux xs - | 0x1b::0x4f::x::xs | 0x8f::x::xs - when is_ascii x -> SS2 (chr x) :: demux xs - | 0x1b::x::xs when is_C1 (x + 0x40) -> C1 (chr x) :: demux xs - | x::xs when is_C1 x -> C1 (chr (x - 0x40)) :: demux xs - | x::xs when is_C0 x -> C0 (chr x) :: demux xs - | x::xs -> Uchar (Uchar.unsafe_of_int x) :: demux xs - | [] -> [] - - let xtrm_mod_flags = function - | 2 -> Some [`Shift] - | 3 -> Some [`Meta] - | 4 -> Some [`Shift; `Meta] - | 5 -> Some [`Ctrl] - | 6 -> Some [`Shift; `Ctrl] - | 7 -> Some [`Meta; `Ctrl] - | 8 -> Some [`Shift; `Meta; `Ctrl] - | _ -> None - - let mods_xtrm = function - | [1;p] -> xtrm_mod_flags p - | [] -> Some [] - | _ -> None - - let mods_rxvt = function - | '~' -> Some [] - | '$' -> Some [`Shift] - | '^' -> Some [`Ctrl] - | '@' -> Some [`Ctrl; `Shift] - | _ -> None - - let mods_common ps code = match (ps, code) with - | ([], '~') -> Some [] - | ([], c) -> mods_rxvt c - | ([p], '~') -> xtrm_mod_flags p - | _ -> None - - let mouse_p p = - let btn = match p land 3 with - | 0 when bit 6 p -> `Scroll `Up - | 0 -> `Left - | 1 when bit 6 p -> `Scroll `Down - | 1 -> `Middle - | 2 when bit 6 p -> `ALL (* `Scroll `Left *) - | 2 -> `Right - | 3 when bit 6 p -> `ALL (* `Scroll `Right *) - | _ -> `ALL - and drag = bit 5 p - and mods = - (if bit 3 p then [`Meta] else []) @ - (if bit 4 p then [`Ctrl] else []) - in (btn, drag, mods) - - let key k mods = Some (`Key (k, mods)) - - let event_of_control_code = - let open Option in function - | Uchar u when Uchar.to_int u |> is_ascii -> - Some (`Key (`ASCII (Uchar.unsafe_to_char u), [])) - | Uchar u -> Some (`Key (`Uchar u, [])) - - | C0 '\x1b' -> key `Escape [] - | C0 ('\b'|'\x7f') -> key `Backspace [] - | C0 '\n' -> key `Enter [] - | C0 '\t' -> key `Tab [] - - | C0 x -> key (`ASCII Char.(code x + 0x40 |> unsafe_chr)) [`Ctrl] - | C1 x -> key (`ASCII x) [`Meta] - - | CSI ("",[],'Z') -> key `Tab [`Shift] - - | CSI ("",p,'A') -> mods_xtrm p >>= key (`Arrow `Up) - | CSI ("",p,'B') -> mods_xtrm p >>= key (`Arrow `Down) - | CSI ("",p,'C') -> mods_xtrm p >>= key (`Arrow `Right) - | CSI ("",p,'D') -> mods_xtrm p >>= key (`Arrow `Left) - - | CSI ("",[],'a') -> key (`Arrow `Up) [`Shift] - | CSI ("",[],'b') -> key (`Arrow `Down) [`Shift] - | CSI ("",[],'c') -> key (`Arrow `Right) [`Shift] - | CSI ("",[],'d') -> key (`Arrow `Left) [`Shift] - | SS2 ('A'|'a') -> key (`Arrow `Up) [`Ctrl] - | SS2 ('B'|'b') -> key (`Arrow `Down) [`Ctrl] - | SS2 ('C'|'c') -> key (`Arrow `Right) [`Ctrl] - | SS2 ('D'|'d') -> key (`Arrow `Left) [`Ctrl] - - | CSI ("",5::p,c) -> mods_common p c >>= key (`Page `Up) - | CSI ("",6::p,c) -> mods_common p c >>= key (`Page `Down) - - | CSI ("",2::p,c) -> mods_common p c >>= key `Insert - | CSI ("",3::p,c) -> mods_common p c >>= key `Delete - - | CSI ("",[4],'h') -> key `Insert [] - | CSI ("",[],'L') -> key `Insert [`Ctrl] - | CSI ("",[],'P') -> key `Delete [] - | CSI ("",[],'M') -> key `Delete [`Ctrl] - - | CSI ("",p,'H') -> mods_xtrm p >>= key `Home - | CSI ("",[7|1],c) -> mods_rxvt c >>= key `Home - - | CSI ("",p,'F') -> mods_xtrm p >>= key `End - | CSI ("",[8|4],c) -> mods_rxvt c >>= key `End - | CSI ("",[],'J') -> key `End [`Ctrl] - - | SS2 ('P'..'S' as c) -> key (`Function (Char.code c - 0x4f)) [] - - | CSI ("",p,('P'..'S' as c)) -> - mods_xtrm p >>= key (`Function (Char.code c - 0x4f)) - - | CSI ("",k::p,c) when btw k 11 15 || btw k 17 21 || btw k 23 26 -> - mods_common p c >>= key (`Function ((k - 10) - (k - 10) / 6)) - - | CSI ("<",[p;x;y],('M'|'m' as c)) -> - let (btn, drag, mods) = mouse_p p in - ( match (c, btn, drag) with - | ('M', (#button as b), false) -> Some (`Press b) - | ('M', #button, true) -> Some `Drag - | ('m', #button, false) -> Some `Release - (* | ('M', `ALL , true) -> Some `Move *) - | _ -> None - ) >>| fun e -> `Mouse (e, (x - 1, y - 1), mods) - - | CSI ("",[p;x;y],'M') | Esc_M (p,x,y) as evt -> - let (x, y) = match evt with Esc_M _ -> x - 32, y - 32 | _ -> x, y - and (btn, drag, mods) = mouse_p (p - 32) in - ( match (btn, drag) with - | (#button as b, false) -> Some (`Press b) - | (#button , true ) -> Some `Drag - | (`ALL , false) -> Some `Release - (* | (`ALL , true) -> Some `Move *) - | _ -> None - ) >>| fun e -> `Mouse (e, (x - 1, y - 1), mods) - - | CSI ("",[200],'~') -> Some (`Paste `Start) - | CSI ("",[201],'~') -> Some (`Paste `End) - - | CSI _ | SS2 _ -> None - - let rec events = function - | C0 '\x1b' :: cc :: ccs -> - ( match event_of_control_code cc with - | Some (`Key (k, mods)) -> `Key (k, `Meta :: mods) :: events ccs - | Some _ -> `Key (`Escape, []) :: events (cc::ccs) - | None -> events ccs ) - | cc::ccs -> (event_of_control_code cc |> Option.to_list) @ events ccs - | [] -> [] - - let decode = events &. demux &. List.map Uchar.to_int - - type t = (event list * bool) ref - - let create () = ref ([], false) - - let next t = match !t with - | (#event as e::es, eof) -> t := (es, eof) ; e - | ([], false) -> `Await - | _ -> `End - - let list_of_utf8 buf i l = - let f cs _ = function `Uchar c -> c::cs | _ -> cs in - String.sub0cp (Bytes.unsafe_to_string buf) i l - |> Uutf.String.fold_utf_8 f [] |> List.rev - - let input t buf i l = t := match !t with - | (es, false) when l > 0 -> (es @ (list_of_utf8 buf i l |> decode), false) - | (es, _) -> (es, true) - - let pending t = match !t with ([], false) -> false | _ -> true -end - -module Tmachine = struct - - open Cap - (* XXX This is sad. This should be a composable, stateless transducer. *) - - type t = { - cap : Cap.t - ; mutable write : Buffer.t -> unit - ; mutable curs : (int * int) option - ; mutable dim : (int * int) - ; mutable image : I.t - ; mutable dead : bool - } - - let emit t op = - if t.dead then - invalid_arg "Notty: use of released terminal" - else t.write <- t.write & op - - let cursor cap = function - | None -> cap.cursvis false - | Some (w, h) -> cap.cursvis true & cursat0 cap w h - - let create ~mouse ~bpaste cap = { - cap - ; curs = None - ; dim = (0, 0) - ; image = I.empty - ; dead = false - ; write = - cap.altscr true & cursor cap None & cap.mouse mouse & cap.bpaste bpaste - } - - let release t = - if t.dead then false else - ( emit t ( t.cap.altscr false & t.cap.cursvis true & - t.cap.mouse false & t.cap.bpaste false ); - t.dead <- true; true ) - - let output t buf = t.write buf; t.write <- ignore - - let refresh ({ dim; image; _ } as t) = - emit t ( cursor t.cap None & cursat0 t.cap 0 0 & - (fun buf -> Render.to_buffer buf t.cap (0, 0) dim image) & - cursor t.cap t.curs ) - - let set_size t dim = t.dim <- dim - let image t image = t.image <- image; refresh t - let cursor t curs = t.curs <- curs; emit t (cursor t.cap curs) - - let size t = t.dim - let dead t = t.dead -end - -module Direct = struct - let show_cursor buf cap x = cap.Cap.cursvis x buf - and move_cursor buf cap cmd = match cmd with - | `To (w, h) -> Cap.cursat0 cap w h buf - | `Home -> cap.Cap.cr buf - | `By (x, y) -> - Cap.(if x <> 0 then cap.cubcuf x buf; if y <> 0 then cap.cuucud y buf) -end - -type attr = A.t -type image = I.t - -module Infix = struct - let ((<->), (<|>), ()) = I.((<->), (<|>), ()) - let (++) = A.(++) -end diff --git a/vendor/notty/src/notty.mli b/vendor/notty/src/notty.mli deleted file mode 100644 index 7d0697242bd..00000000000 --- a/vendor/notty/src/notty.mli +++ /dev/null @@ -1,965 +0,0 @@ -(* Copyright (c) 2016-2017 David Kaloper Meršinjak. All rights reserved. - See LICENSE.md. *) - -(** Declaring terminals. - - Notty is a terminal library that revolves around construction and - composition of displayable images. - - This module provides the core {{!I}[image]} abstraction, standalone - {{!Render}rendering}, and escape sequence {{!Unescape}parsing}. It does not - depend on any platform code, and does not interact with the environment. - Input and output are provided by {!Notty_unix} and {!Notty_lwt}. - - Consult the {{!basics}basics}, {{!examples}examples} and - {{!limitations}limitations}. - - {e %%VERSION%% — {{:%%PKG_HOMEPAGE%% }homepage}} *) - -(** {1 Interface} *) - -type attr -(** Visual characteristics of displayed text. *) - -type image -(** Rectangles of styled characters. *) - -(** [A] is for attribute. - - Construction and composition of styling characteristics of text. - - Consult the {{!basics}basics} for an overview. *) -module A : sig - - (** {1 Colors} *) - - type color - (** An ineffable quality of light. - - There are three kinds of colors: - {ul - {- {e Core 16 colors.} - - ANSI defines 8 color {e names}, with the actual display colors - considered an implementation detail. Historically, this palette was - extended with their light (sometimes {e bright} or {e high-intensity}) - counterparts. Their presentation is undefined too, but typically - produces a brighter shade. These colors - often called the {e ANSI - colors} - tend to be unpredictable, but ubiquitously supported. - - } - {- {e Extended 256-color palette.} - - This common feature extends the palette by further 240 colors. They - come in two groups: - - {ul - {- The {e color cube}, a 6*6*6 approximation to the usual 24-bit RGB - color cube; and} - {- the {e grayscale ramp}, containing (merely) 24 shades of gray.}} - - XTerm was the first to support this extension. Many terminals have - since cloned it, so the support is wide, but not universal. - - As the extended colors are still palette-driven they do not have a - fixed presentation, and the presentation can be changed in some - terminals. Default palette tends to match {{: - https://upload.wikimedia.org/wikipedia/commons/1/15/Xterm_256color_chart.svg} - XTerm's}. - - } - {- {e True color} - - A recently established convention allows directly sending 24-bit colors - to the terminal. This has been adopted by a growing minority of - terminals. A reasonably up-to-date status document maintained by the - community can be found {{:https://gist.github.com/XVilka/8346728}here}.}} - - Some of the technical and historical background can be found in {{: - http://invisible-island.net/xterm/xterm.faq.html#problems_colors} - XTerm's FAQ}. - - {b Note} No attempt is made to remap colors depending on the terminal. - Terminals might ignore, remap, or completely misinterpret unsupported - colors. *) - - (** {2:corecolors Core 16 colors} - - The first 8 have their standard ANSI names. *) - - val black : color - val red : color - val green : color - val yellow : color - val blue : color - val magenta : color - val cyan : color - val white : color - val lightblack : color - val lightred : color - val lightgreen : color - val lightyellow : color - val lightblue : color - val lightmagenta : color - val lightcyan : color - val lightwhite : color - - (** {2 Extended 256-color palette} *) - - val rgb : r:int -> g:int -> b:int -> color - (** [rgb ~r:red ~g:green ~b:blue] is an extended-palette color from the color cube. - - All three channels must be in the range [0 - 5]. XTerm default palette maps - this to [0x00], [0x5f], [0x87], [0xaf], [0xd7], and [0xff] independently - per channel. - - @raise Invalid_argument if a channel is outside the range. *) - - val gray : int -> color - (** [gray level] is an extended-palette color from the grayscale ramp. - - [level] must be in the range [0 - 23]. XTerm default palette maps this to - [8 + level * 10] on all three channels. - - @raise Invalid_argument if the [level] is outside the range. *) - - (** {2 True Color} *) - - val rgb_888 : r:int -> g:int -> b:int -> color - (** [rgb_888 ~r:red ~g:green ~b:blue] is a 24-bit color. - - All three channels must be in the range [0 - 255]. - - @raise Invalid_argument if a channel is outside the range. *) - - (** {1 Text styles} *) - - type style - (** Additional text properties. *) - - val bold : style - val italic : style - val dim : style - val underline : style - val blink : style - val reverse : style - - (** {1 Attribute construction and composition} *) - - type t = attr - - val equal : t -> t -> bool - - val empty : attr - (** [empty] is the attribute with the default foreground and background color - and empty style set. *) - - val (++) : attr -> attr -> attr - (** [a1 ++ a2] is the concatenation of [a1] and [a2], the attribute that has - [a2]'s foreground (resp. background), unless {e unset}, in which case it - is [a1]'s, and the union of both style sets. - - [++] is left-associative, and forms a monoid with [empty]. *) - - val fg : color -> attr - (** [fg c] is [empty] with foreground [c]. *) - - val bg : color -> attr - (** [bg c] is [empty] with background [c]. *) - - val st : style -> attr - (** [st s] is [empty] with style [s]. *) -end - -(** [I] is for image. - - Construction and composition of images. - - Consult the {{!basics}basics} for an overview. *) -module I : sig - - type t = image - - val height : image -> int - val width : image -> int - - val equal : t -> t -> bool - (** [equal t1 t2] is [true] iff [t1] and [t2] are constructed by the same term. - - {b Note} This is a weak form of equality. Images that are not [equal] - could still render the same. *) - - (** {1:imgprims Primitives} *) - - val empty : image - (** [empty] is a zero-sized image. *) - - val string : attr -> string -> image - (** [string attr s] is an image containing text [s], styled with [attr]. - - @raise Invalid_argument if [string] is not a valid UTF-8 sequence, or - contains {{!ctrls}control characters}. *) - - val uchars : attr -> Uchar.t array -> image - (** [uchars attr us] is an image containing text [us], styled with [attr]. - - @raise Invalid_argument if [us] contains {{!ctrls}control characters}. *) - - val char : attr -> char -> int -> int -> image - (** [char attr c w h] is a [w * h] grid of [c]. - - @raise Invalid_argument if [c] is a {{!ctrls}control character}. *) - - val uchar : attr -> Uchar.t -> int -> int -> image - (** [uchar attr u w h] is a [w * h] grid of [u]. - - @raise Invalid_argument if [u] is a {{!ctrls}control character}. *) - - val void : int -> int -> image - (** [void w h] is a [w * h] rectangle of transparent cells. - - [void] is magical: it has geometry, but no displayable content. This is - different, for example, from the space character [U+0020], which renders - as a cell filled with the background color. This means that [void] - interacts specially with {{!()}overlays}. - - [void 0 0 = empty]. - [void] with only one dimension [0] acts as a spacing element in the other - dimension. Negative size is treated as [0]. *) - - (** {1:imgcomp Image composition} - - Three basic composition modes allow construction of more complex images - from simpler ones. - - Composition operators are left-associative and form a monoid with [void]. - *) - - val (<|>) : image -> image -> image - (** [i1 <|> i2] is the horizontal combination of [i1] and [i2]. - - [width (i1 <|> i2) = width i1 + width i2] - [height (i1 <|> i2) = max (height i1) (height i2)] - - Images are top-aligned. The missing region is implicitly filled with - {{!void}[void]}. - -{v -[x] <|> [y] = [xy] - [y] [.y] -v} - - where [.] denotes {{!void}[void]}. *) - - val (<->) : image -> image -> image - (** [i1 <-> i2] is the vertical combination of [i1] and [i2]. - - [width (i1 <-> i2) = max (width i1) (width i2)] - [height (i1 <-> i2) = height i1 + height i2] - - Images are left-aligned. The missing region is implicitly filled with - {{!void}[void]}. - -{v -[xx] <-> [y] = [xx] - [y.] -v} - *) - - val () : image -> image -> image - (** [i1 i2] is [i1] overlaid over [i2]. - - [width (i1 i2) = max (width i1) (width i2)] - [height (i1 i2) = max (height i1) (height i2)] - - Images are top-left-aligned. In the region of their overlap, only the - {{!void}[void]} cells of [i1] show fragments of [i2]. - -{v -[x.x] [yyyy] = [xyxy] -v} - *) - - (** {1:imgcrop Cropping and padding} *) - - val hcrop : int -> int -> image -> image - (** [hcrop left right i] is [i] with [left] leftmost, and [right] - rightmost columns missing. If [left + right >= width i] the result is - [empty]. - - If either [left] or [right] is negative, instead of being cropped, the - image is padded on that side. - - For example: - {ul - {- [hcrop 0 1 [abc]] = [[ab]]} - {- [hcrop 1 1 [abc]] = [[b]]} - {- [hcrop (-1) 1 [abc]] = [void 1 1 <|> hcrop 0 1 [abc]] = [[.ab]]} - {- [hcrop 2 2 [abc]] = [empty]}} *) - - val vcrop : int -> int -> image -> image - (** [vcrop top bottom i] is the vertical analogue to {{!hcrop}[hcrop]}. *) - - val crop : ?l:int -> ?r:int -> ?t:int -> ?b:int -> image -> image - (** [crop ~l:left ~r:right ~t:top ~b:bottom i] is - [vcrop left right (hcrop top bottom) i]. - - Missing arguments default to [0]. *) - - val hpad : int -> int -> image -> image - (** {{!hcrop}[hcrop]} with margins negated. *) - - val vpad : int -> int -> image -> image - (** {{!vcrop}[vcrop]} with margins negated. *) - - val pad : ?l:int -> ?r:int -> ?t:int -> ?b:int -> image -> image - (** {{!crop}[crop]} with margins negated. *) - - - (** {1 Additional combinators} *) - - val hcat : image list -> image - (** [hcat xs] horizontally concatenates [xs]. See {{!(<|>)}beside}. *) - - val vcat : image list -> image - (** [vcat xs] vertically concatenates [xs]. See {{!(<->)}above}. *) - - val zcat : image list -> image - (** [zcat xs] overlays [xs]. See {{!()}over}. *) - - val tabulate : int -> int -> (int -> int -> image) -> image - (** [tabulate m n f] is the grid of values [f x y] with [x = 0..m-1] - and [y = 0..n-1], where [x] grows to the right, and [y] growns down. - - [f a y] is to the left of [f b y] if [a < b], and [f x a] is above [f x b] - if [a < b], but the exact alignment is unspecified if the various [f x y] - have different dimensions. *) - - val hsnap : ?align:[ `Left | `Middle | `Right ] -> int -> image -> image - (** [hsnap ~align w i] is an image of width strictly [w] obtained by either - horizontally padding or cropping [i] and positioning it according to - [~align]. - - [~align] defaults to [`Middle]. *) - - val vsnap : ?align:[ `Top | `Middle | `Bottom ] -> int -> image -> image - (** [vsnap ~align h i] is an image of height strictly [h] obtained by either - vertically padding or cropping [i] and positioning it according to - [~align]. - - [~align] defaults to [`Middle]. *) - - (** {1 [Format] interoperability} *) - - val strf : ?attr:attr -> ?w:int -> ('a, Format.formatter, unit, image) format4 -> 'a - (** [strf ?attr ?w:width format ...] pretty-prints like - [Format.asprintf format ...], but returns an [image]. - - [attr] is the (outermost) attribute. Defaults to {!A.empty}. - - [width] is used to set the margin on the formatter. This is only a hint, - and does not guarantee the width of the result. Consult - {{: http://caml.inria.fr/pub/docs/manual-ocaml/libref/Format.html#VALset_margin} - [Format.set_margin]} for details. Defaults to an unspecified, large - number. - - @raise Invalid_argument if the printing process attempts to directly - output {{!ctrls}control characters}, by embedding them in [format] or a - string printed with the [%s] conversion, for example. - {{: http://caml.inria.fr/pub/docs/manual-ocaml/libref/Format.html#fpp} - Formatted printing} is allowed. *) - - val kstrf : ?attr:attr -> ?w:int -> (image -> 'a) -> ('b, Format.formatter, unit, 'a) format4 -> 'b - (** [kstrf ?attr ?w k format ...] is continuation-based [strf ?attr ?w format ...]. *) - - val pp_attr : attr -> (Format.formatter -> 'a -> unit) -> Format.formatter -> 'a -> unit - (** [pp_attr a f] is a pretty-printer like [f], except its output is styled - with [a]. This applies only outside of any styling [f] itself might embed. *) -end - -(** Operators, repeated. *) -module Infix : sig - - (** {2 [I]} - - See {{!I}[I]}. *) - - val (<->) : image -> image -> image - val (<|>) : image -> image -> image - val () : image -> image -> image - - (** {2 [A]} - - See {{!A}[A]}. *) - - val (++) : attr -> attr -> attr -end - -(** {1 Low-level interface} - - You can ignore it, unless you are porting [Notty] to a new platform not - supported by the existing IO backends. *) - -(** Terminal capabilities. - - This module describes how to output things so that a terminal understands - them. *) -module Cap : sig - - type t - (** A set of capabilities that distinguish terminals from one another. - - A bundle of magic strings, really. *) - - val ansi : t - (** The usual ANSI terminal, with colors, text styles and cursor - positioning. *) - - val dumb : t - (** Pure text output. Text attributes are stripped and positioning is done - with the character [U+0020], SPACE. *) -end - -(** Dump images to string buffers. *) -module Render : sig - - val to_buffer : Buffer.t -> Cap.t -> int * int -> int * int -> image -> unit - (** [to_buffer buf cap (x, y) (w, h) i] writes the string representation of - [i] to [buf], as interpreted by [cap]. - - It renders the [w * h] rectangle of [i], offset by [(x, y)] from the top - left. *) - - val pp : Cap.t -> Format.formatter -> image -> unit - (** [pp cap ppf i] renders [i] to the pretty-printer [ppf]. - - {b Note} [pp] is generally meant for development and debugging. It tries - to be reasonable, but dedicated IO modules handle the actual output - better. *) - - (**/**) - (* Toplevel. *) - val pp_image : Format.formatter -> image -> unit - val pp_attr : Format.formatter -> attr -> unit - (**/**) -end - -(** Parse and decode escape sequences in character streams. *) -module Unescape : sig - - (** {1 Input events} *) - - type special = [ - `Escape - | `Enter - | `Tab - | `Backspace - | `Insert - | `Delete - | `Home | `End - | `Arrow of [ `Up | `Down | `Left | `Right ] - | `Page of [ `Up | `Down ] - | `Function of int - ] - (** A selection of extra keys on the keyboard. *) - - type button = [ `Left | `Middle | `Right | `Scroll of [ `Up | `Down ] ] - (** Mouse buttons. *) - - type mods = [ `Meta | `Ctrl | `Shift ] list - (** Modifier state. *) - - type key = [ special | `Uchar of Uchar.t | `ASCII of char ] * mods - (** Keypress event. *) - - type mouse = [ `Press of button | `Drag | `Release ] * (int * int) * mods - (** Mouse event. *) - - type paste = [ `Start | `End ] - (** Paste event. *) - - type event = [ `Key of key | `Mouse of mouse | `Paste of paste ] - (** Things that terminals say to applications. - - {ul - {- [`Key (k, mods)] is keyboard input. - - [k] is a {{!key}key}, one of: - {ul - {- [`ASCII c] where [c] is a [char] in the - {{: https://tools.ietf.org/html/rfc20}ASCII} range;} - {- [`Uchar u] where [u] is any other {{!Uchar.t}unicode character}; or} - {- a {{!special}special key}.}} - - [`ASCII] and [`Uchar] together represent the textual part of the input. - These characters are guaranteed not to be {{!ctrls}control - characters}, and are safe to use when constructing images. ASCII is - separated from the rest of Unicode for convenient pattern-matching. - - [mods] are the extra {{!mods}modifier keys}. - - } - {- [`Mouse (event, (x, y), mods)] is mouse input. - - [event] is the actual mouse event: {{!button}[button]} press, release, - or motion of the mouse with buttons depressed. - - [(x, y)] are column and row position of the mouse. The origin is - [(0,0)], the upper-left corner. - - {b Note} Every [`Press (`Left|`Middle|`Right)] generates a corresponding - [`Release], but there is no portable way to detect which button was - released. [`Scroll (`Up|`Down)] presses are not followed by releases. - - } - {- [`Paste (`Start|`End)] are {e bracketed paste} events, signalling the - beginning and end of a sequence of events pasted into the terminal. - - {b Note} This mechanism is useful, but not reliable. The pasted text - could contain spurious start-of-paste or end-of-paste markers, or they - could be entered by hand. }} - - Terminal input protocols are historical cruft, and heavily overload the - ASCII range. For instance: - {ul - {- It is impossible to distinguish lower- and upper-case ASCII characters - if {b Ctrl} is pressed;} - {- several combinations of key-presses are aliased as special keys; and} - {- in a UTF-8 encoded stream, there is no representation for non-ASCII - characters with modifier keys.}} - - This means that many values that inhabit the [event] type are impossible, - while some reflect multiple different user actions. Limitations include: - - {ul - {- [`Shift] is reported only with special keys, and not all of them.} - {- [`Meta] and [`Control] are reported with mouse events, key events with - special keys, and key events with values in the ranges [0x40-0x5f] - ([@] to [_]) and [0x60-0x7e] ([`] to [~]). If {b Ctrl} is pressed, the higher - range is mapped into the lower range.} - {- Terminals will variously under-report modifier key state.}} - - Perform own experiments before relying on elaborate key combinations. *) - - val uchar : [< `Uchar of Uchar.t | `ASCII of char ] -> Uchar.t - (** [uchar x] is the {!Uchar.t} corresponding to [x]. This operations merges - the ASCII and Unicode variants of {{!key}key}. *) - - (** {1 Decoding filter} - - Simple IO-less terminal input processor. It can be used for building - custom terminal input abstractions. *) - - type t - (** Input decoding filter. - - The filter should be {{!input}fed} strings, which it first decodes from - UTF-8, and then extracts the input events. - - Malformed UTF-8 input bytes and unrecognized escape sequences are silently - discarded. *) - - val create : unit -> t - (** [create ()] is a new, empty filter. *) - - val input : t -> bytes -> int -> int -> unit - (** [input t buffer i len] feeds [len] bytes of [string] into [t], starting - from position [len]. - - [len = 0] signals the end of input. - - [buffer] is immediately processed and can be reused after the call - returns. *) - - val next : t -> [ event | `Await | `End ] - (** [next t] is the next event in the filter's input stream: - - {ul - {- [#event], an input {{!event}[event]}.} - {- [`Await] if the filter needs more {{!input}input}.} - {- [`End] if the input had ended.}} *) - - val pending : t -> bool - (** [pending t] is [true] if a call to [next], without any intervening input, - would {e not} return [`Await]. *) - - (** {1 Low-level parsing} - - {b Warning} The parsing interface is subject to change. - - Implementation of small parts of - {{: http://www.ecma-international.org/publications/standards/Ecma-035.htm}ECMA-35} - and - {{: http://www.ecma-international.org/publications/standards/Ecma-048.htm}ECMA-48}, - as needed by terminal emulators in common use. *) - - val decode : Uchar.t list -> event list - (** [decode us] are the events encoded by [us]. - - [us] are assumed to have been generated in a burst, and the end of the - list is taken to mean a pause. - Therefore, [decode us1 @ decode us2 <> decode (us1 @ us2)] if [us1] ends - with a partial escape sequence, including a lone [\x1b]. - - Unsupported escape sequences are silently discarded. *) -end - -(**/**) -(** {1 Private} - - These are private interfaces, prone to breakage. Don't use them. *) - -module Operation : sig - type t - val of_image : (int * int) -> int * int -> image -> t list -end - -module Tmachine : sig - - type t - - val create : mouse:bool -> bpaste:bool -> Cap.t -> t - val release : t -> bool - val output : t -> Buffer.t -> unit - - val refresh : t -> unit - val cursor : t -> (int * int) option -> unit - val image : t -> image -> unit - - val set_size : t -> int * int -> unit - - val size : t -> int * int - val dead : t -> bool -end - -module Direct : sig - val move_cursor : Buffer.t -> Cap.t -> [ `Home | `By of int * int | `To of int * int ] -> unit - val show_cursor : Buffer.t -> Cap.t -> bool -> unit -end -(**/**) - -(** {1:basics Basics} - - Print a red-on-black ["Wow!"] above its right-shifted copy: -{[ -let wow = I.string A.(fg red ++ bg black) "Wow!" in -I.(wow <-> (void 2 0 <|> wow)) |> Notty_unix.output_image -]} - - {2:meaning The meaning of images} - - An {{!image}[image]} value is a rectangle of styled character cells. It has a - width and height, but is not anchored to an origin. A single character with - associated display attributes, or a short fragment of text, are simple - examples of images. - - Images are created by combining text fragments with {{!attributes}display - attributes}, and composed by placing them {{!I.(<|>)}beside} each other, - {{!I.(<->)}above} each other, and {{!I.()}over} each other. - - Once constructed, an image can be rendered, and only at that point it obtains - absolute placement. - - Consult {{!I}[I]} for more details. - - {2:attributes Display attributes} - - {{!attr}[attr]} values describe the styling characteristics of fragments of - text. - - They combine a foreground and a background {{!A.color}[color]} with a - set of {{!A.style}[styles]}. Either color can be {e unset}, which corresponds to - the terminal's default foreground (resp. background) color. - - Attributes are used to construct primitive images. - - Consult {{!A}[A]} for more details. - - {2:ctrls Control characters} - - These are taken to be characters in the ranges [0x00-0x1f] ({b C0}), [0x7f] - (BACKSPACE), [0x80-0x9f] ({b C1}). This is the - {{: http://unicode.org/reports/tr44/#General_Category_Values}Unicode - general category} {b Cc}. - - As control characters directly influence the cursor positioning, they - cannot be used to create images. - - This, in particular, means that images cannot contain [U+000a] (NEWLINE). - - {1:limitations Limitations} - - [Notty] does not use Terminfo. If your terminal is particularly - idiosyncratic, things might fail to work. Get in touch with the author to - expand support. - - [Notty] assumes that the terminal is using UTF-8 for input and output. - Things might break arbitrarily if this is not the case. - - For performance considerations, consult the {{!perf}performance model}. - - {2:cwidth Unicode vs. Text geometry} - - [Notty] uses [Uucp.Break.tty_width_hint] to guess the width of text - fragments when computing geometry, and it suffers from the same - shortcomings: - - {ul - {- Geometry in general works for alphabets and east Asian scripts, mostly - works for abjad scripts, and is a matter of luck for abugidas.} - {- East Asian scripts work better when in - {{:http://unicode.org/glossary/#normalization_form_c}NFC}.} - {- For proper emoji display, [Uucp] and the terminal have to agree on the - Unicode version.}} - - When in doubt, see - {{: http://erratique.ch/software/uucp/doc/Uucp.Break.html#VALtty_width_hint} - [Uucp.Break.tty_width_hint]}. - - Unicode has special interaction with {{!I.hcrop}horizontal cropping}: - {ul - {- Strings within images are cropped at {{: - http://unicode.org/reports/tr29/#Grapheme_Cluster_Boundaries}grapheme - cluster} boundaries. This means that scalar value sequences that are - rendered combined, or overlaid, stay unbroken.} - {- When a crop splits a wide character in two, the remaining half is - replaced by [U+0020] (SPACE). Hence, character-cell-accurate cropping is - possible even in the presence of characters that horizontally occupy - more than one cell.}} - - {1:examples Examples} - - We assume a toplevel with [Notty] support ([#require "notty.top"]). - - {2 Hello} - - ["Rad!"] with default foreground and background: - - {[I.string A.empty "Rad!"]} - - Everything has to start somewhere. - - {2 Colors} - - ["Rad!"] in rad letters: - - {[I.string A.(fg lightred) "Rad!"]} - - {2 Padding and spacing} - -{[ -let a1 = A.(fg lightwhite ++ bg red) -and a2 = A.(fg red) -]} - - ["Rad"] and [" stuff!"] in different colors: - - {[I.(string a1 "Rad" <|> string a2 " stuff!")]} - - The second word hanging on a line below: - - {[I.(string a1 "Rad" <|> (string a2 "stuff!" |> vpad 1 0))]} - - {2 More geometry} - - Sierpinski triangle: - -{[ -let square = "\xe2\x96\xaa" - -let rec sierp n = - if n > 1 then - let ss = sierp (pred n) in I.(ss <-> (ss <|> ss)) - else I.(string A.(fg magenta) square |> hpad 1 0) -]} - - {[sierp 8]} - - A triangle overlaid over its shifted copy: - - {[let s = sierp 6 in I.(s vpad 1 0 s)]} - - Blinkenlights: - -{[ -let rad n color = - let a1 = A.fg color in - let a2 = A.(st blink ++ a1) in - I.((string a2 "Rad" |> hpad n 0) <-> - (string a1 "(⌐■_■)" |> hpad (n + 7) 0)) - -let colors = A.[red; green; yellow; blue; magenta; cyan] -]} - -{[ -colors |> List.mapi I.(fun i c -> rad i c |> pad ~t:i ~l:(2 * i)) - |> I.zcat -]} - - {b Note} Usage of {{!A.blink}[blink]} might be regulated by law in some - jurisdictions. - - {2 Pretty-printing} - - Images can be pretty-printed into: - - {[I.strf "(%d)" 42]} - - Attributes can be applied to the entire format string, or by decorating - {e user-defined printers} that are supplied with [%a] conversions: - - {[let pp = Format.pp_print_int]} - - {[I.strf ~attr:A.(fg lightwhite) "(%a)" (I.pp_attr A.(fg green) pp) 42]} - - {2 Now with output} - - The core module has no real IO. Examples above are simple [image]-valued - expressions, displayed by the pretty-printer that is installed by the - toplevel support. Self-contained programs need a separate IO module: - - {[#require "notty.unix"]} - - {[sierp 8 |> Notty_unix.output_image]} - - (Note the difference in cropping behavior.) - - Computations can be adapted to the current terminal size. A line can stretch - end-to-end: - -{[ -Notty_unix.output_image_size @@ fun (w, _) -> - let i1 = I.string A.(fg green) "very" - and i2 = I.string A.(fg yellow) "melon" in - I.(i1 <|> void (w - width i1 - width i2) 1 <|> i2) -]} - - The largest triangle that horizontally fits into the terminal: - -{[ -Notty_unix.output_image_size @@ fun (w, _) -> - let steps = int_of_float ((log (float w)) /. log 2.) in - sierp steps |> I.vpad 0 1 -]} - - {2 Simple interaction} - - Interactive Sierpinski: - - {[open Notty_unix]} - -{[ -let img (double, n) = - let s = sierp n in - if double then I.(s vpad 1 0 s) else s -in -let rec update t state = Term.image t (img state); loop t state -and loop t (double, n as state) = - match Term.event t with - | `Key (`Enter,_) -> () - | `Key (`Arrow `Left,_) -> update t (double, max 1 (n - 1)) - | `Key (`Arrow `Right,_) -> update t (double, min 8 (n + 1)) - | `Key (`ASCII ' ', _) -> update t (not double, n) - | `Resize _ -> update t state - | _ -> loop t state -in -let t = Term.create () -in -update t (false, 1); Term.release t -]} - - The program uses a fullscreen {{!Notty_unix.Term}terminal} and loops reading - the {{!Notty_unix.Term.event}input}. LEFT and RIGHT control the iteration - count, and SPACE toggles double-drawing. Resizing the window causes a - redraw. When the loop exits on ENTER, the terminal is - {{!Notty_unix.Term.release}cleaned up}. - - {1:perf Performance model} - - This section is only relevant if using [Notty] becomes your bottleneck. - - {b TL;DR} Shared sub-expressions do not share work, so operators stick with - you. - - The main performance parameter is {e image complexity}. This roughly - corresponds to the number of image {{!I.imgcomp}composition} and - {{!I.imgcrop}cropping} operators in the fully expanded [image] term, - {b ignoring all sharing}. - - Outline numbers: - - {ul - {- Highly complex images can be rendered and pushed out to a full-screen - terminal more than 1000 times per second.} - {- With more realistic images, this number is closer to 30,000.} - {- Input processing is somewhere around 50MB/s.}} - - - Image complexity [cplx] of an image [i] is: - {ul - {- For a {{!I.imgprims}primitive} [i], [cplx i = 1].} - {- For a {{!I.imgcomp}composition} operator [op], - [cplx (op i1 i2) = 1 + cplx i1 + cplx i2].} - {- For a {{!I.imgcomp}crop} [cr], - [cplx (cr i1) = 1 + cplx i1 - k], where [k] is the combined complexity of - all the {e maximal} sub-terms that do not contribute to the output.}} - - For example (assuming an image [i]): - -{[ - let img1 = I.((i <|> i) <-> (i <|> i)) - let img2 = I.(let x = i <|> i in x <-> x) - let img3 = I.(((i <|> i) <|> i) <|> i) -]} - - Complexity of each of these is [4 * cplx i + 3]. This might be surprising - for [img2]. - - If [width i = 1], [cplx (hcrop 1 0 img1) = 3 + 2 * cplx i], and - [cplx (hcrop 2 0 img3) = 2 + 2 * cplx i]. - - While [Notty] strives to be accommodating to all usage scenarios, these are - the things to keep in mind if the rendering becomes slow: - - {ol - {- Image composition is cheap. - - Combining images performs a negligible amount of computation. - - Constructing primitive images that contain scalar values outside of the - ASCII range does a little more work upfront and is worth holding onto. - - } - {- {{!Render}Rendering} depends on image complexity. - - As a consequence, this real-world example of wrapping renders in time - O(n{^ 2}) in the number of lines: - -{[ -let wrap1 width img = - let rec go img = img :: - if I.width img > width then go (I.hcrop width 0 img) else [] - in go img |> I.vcat |> I.hsnap ~align:`Left width -]} - - Although [crop] is applied only [lines] times, the image complexity of - each line depends on the number of preceding lines. - - An O(n) version does not iterate [crop]: - -{[ -let wrap2 width img = - let rec go off = I.hcrop off 0 img :: - if I.width img - off > width then go (off + width) else [] - in go 0 |> I.vcat |> I.hsnap ~align:`Left width -]} - } - {- Rendering depends on the {e output} dimensions, but not on the {e image} - dimensions. - - Rendering an image to [w * h] implicitly crops it to its leftmost [w] - columns and topmost [h] rows. While [w] and [h] will have an impact on - the rendering performance, the complexity of the (cropped) image tends to - be more important.}} - -*) diff --git a/vendor/update-notty.sh b/vendor/update-notty.sh deleted file mode 100755 index 8d658669a1b..00000000000 --- a/vendor/update-notty.sh +++ /dev/null @@ -1,27 +0,0 @@ -#!/bin/bash - -version=7a95a8c8c39ed0742284d42216106cb9559fe34e - -set -e -o pipefail - -TMP="$(mktemp -d)" -trap "rm -rf $TMP" EXIT - -rm -rf notty -mkdir -p notty/src - -( - cd $TMP - git clone https://github.com/ocaml-dune/notty.git - cd notty - git checkout $version -) - -SRC=$TMP/notty - -cp -v $SRC/LICENSE.md notty/ -cp -v -R $SRC/{src,src-unix} notty/ -rm notty/src/*_top*.ml - -git checkout notty/{src,src-unix}/dune -git add -A . diff --git a/vendor/update-uutf.sh b/vendor/update-uutf.sh deleted file mode 100755 index 8c23ce66908..00000000000 --- a/vendor/update-uutf.sh +++ /dev/null @@ -1,29 +0,0 @@ -#!/bin/bash - -version=8474b2a29c4cb9cbf356006612c7b2b97e9c4087 - -set -e -o pipefail - -TMP="$(mktemp -d)" -trap "rm -rf $TMP" EXIT - -PACKAGE=uutf - -rm -rf $PACKAGE -mkdir -p $PACKAGE/src - -( - cd $TMP - git clone https://github.com/dbuenzli/$PACKAGE.git - cd $PACKAGE - git checkout $version - cd src -) - -SRC=$TMP/$PACKAGE - -cp -v $SRC/LICENSE.md $PACKAGE -cp -v $SRC/src/*.{ml,mli} $PACKAGE/ - -git checkout $PACKAGE/dune -git add -A . diff --git a/vendor/uutf/LICENSE.md b/vendor/uutf/LICENSE.md deleted file mode 100644 index 6f8c2610c35..00000000000 --- a/vendor/uutf/LICENSE.md +++ /dev/null @@ -1,13 +0,0 @@ -Copyright (c) 2016 The uutf programmers - -Permission to use, copy, modify, and/or distribute this software for any -purpose with or without fee is hereby granted, provided that the above -copyright notice and this permission notice appear in all copies. - -THE SOFTWARE IS PROVIDED "AS IS" AND THE AUTHOR DISCLAIMS ALL WARRANTIES -WITH REGARD TO THIS SOFTWARE INCLUDING ALL IMPLIED WARRANTIES OF -MERCHANTABILITY AND FITNESS. IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR -ANY SPECIAL, DIRECT, INDIRECT, OR CONSEQUENTIAL DAMAGES OR ANY DAMAGES -WHATSOEVER RESULTING FROM LOSS OF USE, DATA OR PROFITS, WHETHER IN AN -ACTION OF CONTRACT, NEGLIGENCE OR OTHER TORTIOUS ACTION, ARISING OUT OF -OR IN CONNECTION WITH THE USE OR PERFORMANCE OF THIS SOFTWARE. diff --git a/vendor/uutf/dune b/vendor/uutf/dune deleted file mode 100644 index a908bcbcb3a..00000000000 --- a/vendor/uutf/dune +++ /dev/null @@ -1,3 +0,0 @@ -(library - (name dune_uutf) - (wrapped false)) diff --git a/vendor/uutf/uutf.ml b/vendor/uutf/uutf.ml deleted file mode 100644 index eafca5f60e1..00000000000 --- a/vendor/uutf/uutf.ml +++ /dev/null @@ -1,822 +0,0 @@ -(*--------------------------------------------------------------------------- - Copyright (c) 2012 The uutf programmers. All rights reserved. - Distributed under the ISC license, see terms at the end of the file. - ---------------------------------------------------------------------------*) - -let io_buffer_size = 65536 (* IO_BUFFER_SIZE 4.0.0 *) - -let pp = Format.fprintf -let invalid_encode () = invalid_arg "expected `Await encode" -let invalid_bounds j l = - invalid_arg (Printf.sprintf "invalid bounds (index %d, length %d)" j l) - -(* Unsafe string byte manipulations. If you don't believe the author's - invariants, replacing with safe versions makes everything safe in - the module. He won't be upset. *) - -let unsafe_chr = Char.unsafe_chr -let unsafe_blit = Bytes.unsafe_blit -let unsafe_array_get = Array.unsafe_get -let unsafe_byte s j = Char.code (Bytes.unsafe_get s j) -let unsafe_set_byte s j byte = Bytes.unsafe_set s j (Char.unsafe_chr byte) - -(* Unicode characters *) - -let u_bom = Uchar.unsafe_of_int 0xFEFF (* BOM. *) -let u_rep = Uchar.unsafe_of_int 0xFFFD (* replacement character. *) - -(* Unicode encoding schemes *) - -type encoding = [ `UTF_8 | `UTF_16 | `UTF_16BE | `UTF_16LE ] -type decoder_encoding = [ encoding | `US_ASCII | `ISO_8859_1 ] - -let encoding_of_string s = match String.uppercase_ascii s with (* IANA names. *) -| "UTF-8" -> Some `UTF_8 -| "UTF-16" -> Some `UTF_16 -| "UTF-16LE" -> Some `UTF_16LE -| "UTF-16BE" -> Some `UTF_16BE -| "ANSI_X3.4-1968" | "ISO-IR-6" | "ANSI_X3.4-1986" | "ISO_646.IRV:1991" -| "ASCII" | "ISO646-US" | "US-ASCII" | "US" | "IBM367" | "CP367" | "CSASCII" -> - Some `US_ASCII -| "ISO_8859-1:1987" | "ISO-IR-100" | "ISO_8859-1" | "ISO-8859-1" -| "LATIN1" | "L1" | "IBM819" | "CP819" | "CSISOLATIN1" -> - Some `ISO_8859_1 -| _ -> None - -let encoding_to_string = function -| `UTF_8 -> "UTF-8" | `UTF_16 -> "UTF-16" | `UTF_16BE -> "UTF-16BE" -| `UTF_16LE -> "UTF-16LE" | `US_ASCII -> "US-ASCII" -| `ISO_8859_1 -> "ISO-8859-1" - -(* Base character decoders. They assume enough data. *) - -let malformed s j l = `Malformed (Bytes.sub_string s j l) -let malformed_pair be hi s j l = (* missing or half low surrogate at eoi. *) - let bs1 = Bytes.(sub s j l) in - let bs0 = Bytes.create 2 in - let j0, j1 = if be then (0, 1) else (1, 0) in - unsafe_set_byte bs0 j0 (hi lsr 8); - unsafe_set_byte bs0 j1 (hi land 0xFF); - `Malformed Bytes.(unsafe_to_string (cat bs0 bs1)) - -let r_us_ascii s j = - (* assert (0 <= j && j < String.length s); *) - let b0 = unsafe_byte s j in - if b0 <= 127 then `Uchar (Uchar.unsafe_of_int b0) else malformed s j 1 - -let r_iso_8859_1 s j = - (* assert (0 <= j && j < String.length s); *) - `Uchar (Uchar.unsafe_of_int @@ unsafe_byte s j) - -let utf_8_len = [| (* uchar byte length according to first UTF-8 byte. *) - 1; 1; 1; 1; 1; 1; 1; 1; 1; 1; 1; 1; 1; 1; 1; 1; 1; 1; 1; 1; 1; 1; 1; 1; - 1; 1; 1; 1; 1; 1; 1; 1; 1; 1; 1; 1; 1; 1; 1; 1; 1; 1; 1; 1; 1; 1; 1; 1; - 1; 1; 1; 1; 1; 1; 1; 1; 1; 1; 1; 1; 1; 1; 1; 1; 1; 1; 1; 1; 1; 1; 1; 1; - 1; 1; 1; 1; 1; 1; 1; 1; 1; 1; 1; 1; 1; 1; 1; 1; 1; 1; 1; 1; 1; 1; 1; 1; - 1; 1; 1; 1; 1; 1; 1; 1; 1; 1; 1; 1; 1; 1; 1; 1; 1; 1; 1; 1; 1; 1; 1; 1; - 1; 1; 1; 1; 1; 1; 1; 1; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; - 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; - 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; - 0; 0; 2; 2; 2; 2; 2; 2; 2; 2; 2; 2; 2; 2; 2; 2; 2; 2; 2; 2; 2; 2; 2; 2; - 2; 2; 2; 2; 2; 2; 2; 2; 3; 3; 3; 3; 3; 3; 3; 3; 3; 3; 3; 3; 3; 3; 3; 3; - 4; 4; 4; 4; 4; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0; 0 |] - -let r_utf_8 s j l = - (* assert (0 <= j && 0 <= l && j + l <= String.length s); *) - let uchar c = `Uchar (Uchar.unsafe_of_int c) in - match l with - | 1 -> uchar (unsafe_byte s j) - | 2 -> - let b0 = unsafe_byte s j in let b1 = unsafe_byte s (j + 1) in - if b1 lsr 6 != 0b10 then malformed s j l else - uchar (((b0 land 0x1F) lsl 6) lor (b1 land 0x3F)) - | 3 -> - let b0 = unsafe_byte s j in let b1 = unsafe_byte s (j + 1) in - let b2 = unsafe_byte s (j + 2) in - let c = ((b0 land 0x0F) lsl 12) lor - ((b1 land 0x3F) lsl 6) lor - (b2 land 0x3F) - in - if b2 lsr 6 != 0b10 then malformed s j l else - begin match b0 with - | 0xE0 -> if b1 < 0xA0 || 0xBF < b1 then malformed s j l else uchar c - | 0xED -> if b1 < 0x80 || 0x9F < b1 then malformed s j l else uchar c - | _ -> if b1 lsr 6 != 0b10 then malformed s j l else uchar c - end - | 4 -> - let b0 = unsafe_byte s j in let b1 = unsafe_byte s (j + 1) in - let b2 = unsafe_byte s (j + 2) in let b3 = unsafe_byte s (j + 3) in - let c = (((b0 land 0x07) lsl 18) lor - ((b1 land 0x3F) lsl 12) lor - ((b2 land 0x3F) lsl 6) lor - (b3 land 0x3F)) - in - if b3 lsr 6 != 0b10 || b2 lsr 6 != 0b10 then malformed s j l else - begin match b0 with - | 0xF0 -> if b1 < 0x90 || 0xBF < b1 then malformed s j l else uchar c - | 0xF4 -> if b1 < 0x80 || 0x8F < b1 then malformed s j l else uchar c - | _ -> if b1 lsr 6 != 0b10 then malformed s j l else uchar c - end - | _ -> assert false - -let r_utf_16 s j0 j1 = (* May return a high surrogate. *) - (* assert (0 <= j0 && 0 <= j1 && max j0 j1 < String.length s); *) - let b0 = unsafe_byte s j0 in let b1 = unsafe_byte s j1 in - let u = (b0 lsl 8) lor b1 in - if u < 0xD800 || u > 0xDFFF then `Uchar (Uchar.unsafe_of_int u) else - if u > 0xDBFF then malformed s (min j0 j1) 2 else `Hi u - -let r_utf_16_lo hi s j0 j1 = (* Combines [hi] with a low surrogate. *) - (* assert (0 <= j0 && 0 <= j1 && max j0 j1 < String.length s); *) - let b0 = unsafe_byte s j0 in - let b1 = unsafe_byte s j1 in - let lo = (b0 lsl 8) lor b1 in - if lo < 0xDC00 || lo > 0xDFFF - then malformed_pair (j0 < j1 (* true => be *)) hi s (min j0 j1) 2 - else `Uchar (Uchar.unsafe_of_int ((((hi land 0x3FF) lsl 10) lor - (lo land 0x3FF)) + 0x10000)) - -let r_encoding s j l = (* guess encoding with max. 3 bytes. *) - (* assert (0 <= j && 0 <= l && j + l <= String.length s) *) - let some i = if i < l then Some (unsafe_byte s (j + i)) else None in - match (some 0), (some 1), (some 2) with - | Some 0xEF, Some 0xBB, Some 0xBF -> `UTF_8 `BOM - | Some 0xFE, Some 0xFF, _ -> `UTF_16BE `BOM - | Some 0xFF, Some 0xFE, _ -> `UTF_16LE `BOM - | Some 0x00, Some p, _ when p > 0 -> `UTF_16BE (`ASCII p) - | Some p, Some 0x00, _ when p > 0 -> `UTF_16LE (`ASCII p) - | Some u, _, _ when utf_8_len.(u) <> 0 -> `UTF_8 `Decode - | Some _, Some _, _ -> `UTF_16BE `Decode - | Some _, None , None -> `UTF_8 `Decode - | None , None , None -> `UTF_8 `End - | None , Some _, _ -> assert false - | Some _, None , Some _ -> assert false - | None , None , Some _ -> assert false - -(* Decode *) - -type src = [ `Channel of in_channel | `String of string | `Manual ] -type nln = [ `ASCII of Uchar.t | `NLF of Uchar.t | `Readline of Uchar.t ] -type decode = [ `Await | `End | `Malformed of string | `Uchar of Uchar.t] - -let pp_decode ppf = function -| `Uchar u -> pp ppf "@[`Uchar U+%04X@]" (Uchar.to_int u) -| `End -> pp ppf "`End" -| `Await -> pp ppf "`Await" -| `Malformed bs -> - let l = String.length bs in - pp ppf "@[`Malformed ("; - if l > 0 then pp ppf "%02X" (Char.code (bs.[0])); - for i = 1 to l - 1 do pp ppf " %02X" (Char.code (bs.[i])) done; - pp ppf ")@]" - -type decoder = - { src : src; (* input source. *) - mutable encoding : decoder_encoding; (* decoded encoding. *) - nln : nln option; (* newline normalization (if any). *) - nl : Uchar.t; (* newline normalization character. *) - mutable i : Bytes.t; (* current input chunk. *) - mutable i_pos : int; (* input current position. *) - mutable i_max : int; (* input maximal position. *) - t : Bytes.t; (* four bytes temporary buffer for overlapping reads. *) - mutable t_len : int; (* current byte length of [t]. *) - mutable t_need : int; (* number of bytes needed in [t]. *) - mutable removed_bom : bool; (* [true] if an initial BOM was removed. *) - mutable last_cr : bool; (* [true] if last char was CR. *) - mutable line : int; (* line number. *) - mutable col : int; (* column number. *) - mutable byte_count : int; (* byte count. *) - mutable count : int; (* char count. *) - mutable pp : (* decoder post-processor for BOM, position and nln. *) - decoder -> [ `Malformed of string | `Uchar of Uchar.t ] -> decode; - mutable k : decoder -> decode } (* decoder continuation. *) - -(* On decodes that overlap two (or more) [d.i] buffers, we use [t_fill] to copy - the input data to [d.t] and decode from there. If the [d.i] buffers are not - too small this is faster than continuation based byte per byte writes. - - End of input (eoi) is signalled by [d.i_pos = 0] and [d.i_max = min_int] - which implies that [i_rem d < 0] is [true]. *) - -let i_rem d = d.i_max - d.i_pos + 1 (* remaining bytes to read in [d.i]. *) -let eoi d = - d.i <- Bytes.empty; d.i_pos <- 0; d.i_max <- min_int (* set eoi in [d]. *) - -let src d s j l = (* set [d.i] with [s]. *) - if (j < 0 || l < 0 || j + l > Bytes.length s) then invalid_bounds j l else - if (l = 0) then eoi d else - (d.i <- s; d.i_pos <- j; d.i_max <- j + l - 1) - -let refill k d = match d.src with (* get new input in [d.i] and [k]ontinue. *) -| `Manual -> d.k <- k; `Await -| `String _ -> eoi d; k d -| `Channel ic -> - let rc = input ic d.i 0 (Bytes.length d.i) in - (src d d.i 0 rc; k d) - -let t_need d need = d.t_len <- 0; d.t_need <- need -let rec t_fill k d = (* get [d.t_need] bytes (or less if eoi) in [i.t]. *) - let blit d l = - unsafe_blit d.i d.i_pos d.t d.t_len (* write pos. *) l; - d.i_pos <- d.i_pos + l; d.t_len <- d.t_len + l; - in - let rem = i_rem d in - if rem < 0 (* eoi *) then k d else - let need = d.t_need - d.t_len in - if rem < need then (blit d rem; refill (t_fill k) d) else (blit d need; k d) - -let ret k v byte_count d = (* return post-processed [v]. *) - d.k <- k; d.byte_count <- d.byte_count + byte_count; d.pp d v - -(* Decoders. *) - -let rec decode_us_ascii d = - let rem = i_rem d in - if rem <= 0 then (if rem < 0 then `End else refill decode_us_ascii d) else - let j = d.i_pos in - d.i_pos <- d.i_pos + 1; ret decode_us_ascii (r_us_ascii d.i j) 1 d - -let rec decode_iso_8859_1 d = - let rem = i_rem d in - if rem <= 0 then (if rem < 0 then `End else refill decode_iso_8859_1 d) else - let j = d.i_pos in - d.i_pos <- d.i_pos + 1; ret decode_iso_8859_1 (r_iso_8859_1 d.i j) 1 d - -(* UTF-8 decoder *) - -let rec t_decode_utf_8 d = (* decode from [d.t]. *) - if d.t_len < d.t_need - then ret decode_utf_8 (malformed d.t 0 d.t_len) d.t_len d - else ret decode_utf_8 (r_utf_8 d.t 0 d.t_len) d.t_len d - -and decode_utf_8 d = - let rem = i_rem d in - if rem <= 0 then (if rem < 0 then `End else refill decode_utf_8 d) else - let need = unsafe_array_get utf_8_len (unsafe_byte d.i d.i_pos) in - if rem < need then (t_need d need; t_fill t_decode_utf_8 d) else - let j = d.i_pos in - if need = 0 - then (d.i_pos <- d.i_pos + 1; ret decode_utf_8 (malformed d.i j 1) 1 d) - else (d.i_pos <- d.i_pos + need; ret decode_utf_8 (r_utf_8 d.i j need) need d) - -(* UTF-16BE decoder *) - -let rec t_decode_utf_16be_lo hi d = (* decode from [d.t]. *) - let bcount = d.t_len + 2 (* hi count *) in - if d.t_len < d.t_need - then ret decode_utf_16be (malformed_pair true hi d.t 0 d.t_len) bcount d - else ret decode_utf_16be (r_utf_16_lo hi d.t 0 1) bcount d - -and t_decode_utf_16be d = (* decode from [d.t]. *) - if d.t_len < d.t_need - then ret decode_utf_16be (malformed d.t 0 d.t_len) d.t_len d - else decode_utf_16be_lo (r_utf_16 d.t 0 1) d - -and decode_utf_16be_lo v d = match v with -| `Uchar _ | `Malformed _ as v -> ret decode_utf_16be v 2 d -| `Hi hi -> - let rem = i_rem d in - if rem < 2 then (t_need d 2; t_fill (t_decode_utf_16be_lo hi) d) else - let j = d.i_pos in - d.i_pos <- d.i_pos + 2; - ret decode_utf_16be (r_utf_16_lo hi d.i j (j + 1)) 4 d - -and decode_utf_16be d = - let rem = i_rem d in - if rem <= 0 then (if rem < 0 then `End else refill decode_utf_16be d) else - if rem < 2 then (t_need d 2; t_fill t_decode_utf_16be d) else - let j = d.i_pos in - d.i_pos <- d.i_pos + 2; decode_utf_16be_lo (r_utf_16 d.i j (j + 1)) d - -(* UTF-16LE decoder, same as UTF-16BE with byte swapped. *) - -let rec t_decode_utf_16le_lo hi d = (* decode from [d.t]. *) - let bcount = d.t_len + 2 (* hi count *) in - if d.t_len < d.t_need - then ret decode_utf_16le (malformed_pair false hi d.t 0 d.t_len) bcount d - else ret decode_utf_16le (r_utf_16_lo hi d.t 1 0) bcount d - -and t_decode_utf_16le d = (* decode from [d.t]. *) - if d.t_len < d.t_need - then ret decode_utf_16le (malformed d.t 0 d.t_len) d.t_len d - else decode_utf_16le_lo (r_utf_16 d.t 1 0) d - -and decode_utf_16le_lo v d = match v with -| `Uchar _ | `Malformed _ as v -> ret decode_utf_16le v 2 d -| `Hi hi -> - let rem = i_rem d in - if rem < 2 then (t_need d 2; t_fill (t_decode_utf_16le_lo hi) d) else - let j = d.i_pos in - d.i_pos <- d.i_pos + 2; - ret decode_utf_16le (r_utf_16_lo hi d.i (j + 1) j) 4 d - -and decode_utf_16le d = - let rem = i_rem d in - if rem <= 0 then (if rem < 0 then `End else refill decode_utf_16le d) else - if rem < 2 then (t_need d 2; t_fill t_decode_utf_16le d) else - let j = d.i_pos in - d.i_pos <- d.i_pos + 2; decode_utf_16le_lo (r_utf_16 d.i (j + 1) j) d - -(* Encoding guessing. The guess is simple but starting the decoder - after is tedious, uutf's decoders are not designed to put bytes - back in the stream. *) - -let guessed_utf_8 d = (* start decoder after `UTF_8 guess. *) - let b3 d = (* handles the third read byte. *) - let b3 = unsafe_byte d.t 2 in - match utf_8_len.(b3) with - | 0 -> ret decode_utf_8 (malformed d.t 2 1) 1 d - | n -> - d.t_need <- n; d.t_len <- 1; unsafe_set_byte d.t 0 b3; - t_fill t_decode_utf_8 d - in - let b2 d = (* handle second read byte. *) - let b2 = unsafe_byte d.t 1 in - let b3 = if d.t_len > 2 then b3 else decode_utf_8 (* decodes `End *) in - match utf_8_len.(b2) with - | 0 -> ret b3 (malformed d.t 1 1) 1 d - | 1 -> ret b3 (r_utf_8 d.t 1 1) 1 d - | n -> (* copy d.t.(1-2) to d.t.(0-1) and decode *) - d.t_need <- n; - unsafe_set_byte d.t 0 b2; - if (d.t_len < 3) then d.t_len <- 1 else - (d.t_len <- 2; unsafe_set_byte d.t 1 (unsafe_byte d.t 2); ); - t_fill t_decode_utf_8 d - in - let b1 = unsafe_byte d.t 0 in (* handle first read byte. *) - let b2 = if d.t_len > 1 then b2 else decode_utf_8 (* decodes `End *) in - match utf_8_len.(b1) with - | 0 -> ret b2 (malformed d.t 0 1) 1 d - | 1 -> ret b2 (r_utf_8 d.t 0 1) 1 d - | 2 -> - if d.t_len < 2 then ret decode_utf_8 (malformed d.t 0 1) 1 d else - if d.t_len < 3 then ret decode_utf_8 (r_utf_8 d.t 0 2) 2 d else - ret b3 (r_utf_8 d.t 0 2) 2 d - | 3 -> - if d.t_len < 3 - then ret decode_utf_8 (malformed d.t 0 d.t_len) d.t_len d - else ret decode_utf_8 (r_utf_8 d.t 0 3) 3 d - | 4 -> - if d.t_len < 3 - then ret decode_utf_8 (malformed d.t 0 d.t_len) d.t_len d - else (d.t_need <- 4; t_fill t_decode_utf_8 d) - | n -> assert false - -let guessed_utf_16 d be v = (* start decoder after `UTF_16{BE,LE} guess. *) - let decode_utf_16, t_decode_utf_16, t_decode_utf_16_lo, j0, j1 = - if be then decode_utf_16be, t_decode_utf_16be, t_decode_utf_16be_lo, 0, 1 - else decode_utf_16le, t_decode_utf_16le, t_decode_utf_16le_lo, 1, 0 - in - let b3 k d = - if d.t_len < 3 then decode_utf_16 d (* decodes `End *) else - begin (* copy d.t.(2) to d.t.(0) and decode. *) - d.t_need <- 2; d.t_len <- 1; - unsafe_set_byte d.t 0 (unsafe_byte d.t 2); - t_fill k d - end - in - match v with - | `BOM -> ret (b3 t_decode_utf_16) (`Uchar u_bom) 2 d - | `ASCII u -> ret (b3 t_decode_utf_16) (`Uchar (Uchar.unsafe_of_int u)) 2 d - | `Decode -> - match r_utf_16 d.t j0 j1 with - | `Malformed _ | `Uchar _ as v -> ret (b3 t_decode_utf_16) v 2 d - | `Hi hi -> - if d.t_len < 3 - then ret decode_utf_16 (malformed_pair be hi Bytes.empty 0 0) d.t_len d - else (b3 (t_decode_utf_16_lo hi)) d - -let guess_encoding d = (* guess encoding and start decoder. *) - let setup d = match r_encoding d.t 0 d.t_len with - | `UTF_8 r -> - d.encoding <- `UTF_8; d.k <- decode_utf_8; - begin match r with - | `BOM -> ret decode_utf_8 (`Uchar u_bom) 3 d - | `Decode -> guessed_utf_8 d - | `End -> `End - end - | `UTF_16BE r -> - d.encoding <- `UTF_16BE; d.k <- decode_utf_16be; guessed_utf_16 d true r - | `UTF_16LE r -> - d.encoding <- `UTF_16LE; d.k <- decode_utf_16le; guessed_utf_16 d false r - - in - (t_need d 3; t_fill setup d) - -(* Character post-processors. Used for BOM handling, newline - normalization and position tracking. The [pp_remove_bom] is only - used for the first character to remove a possible initial BOM and - handle UTF-16 endianness recognition. *) - -let nline d = d.col <- 0; d.line <- d.line + 1 (* inlined. *) -let ncol d = d.col <- d.col + 1 (* inlined. *) -let ncount d = d.count <- d.count + 1 (* inlined. *) -let cr d b = d.last_cr <- b (* inlined. *) - -let pp_remove_bom utf16 pp d = function(* removes init. BOM, handles UTF-16. *) -| `Malformed _ as v -> d.removed_bom <- false; d.pp <- pp; d.pp d v -| `Uchar u as v -> - match Uchar.to_int u with - | 0xFEFF (* BOM *) -> - if utf16 then (d.encoding <- `UTF_16BE; d.k <- decode_utf_16be); - d.removed_bom <- true; d.pp <- pp; d.k d - | 0xFFFE (* BOM reversed from decode_utf_16be *) when utf16 -> - d.encoding <- `UTF_16LE; d.k <- decode_utf_16le; - d.removed_bom <- true; d.pp <- pp; d.k d - | _ -> - d.removed_bom <- false; d.pp <- pp; d.pp d v - -let pp_nln_none d = function -| `Malformed _ as v -> cr d false; ncount d; ncol d; v -| `Uchar u as v -> - match Uchar.to_int u with - | 0x000A (* LF *) -> - let last_cr = d.last_cr in - cr d false; ncount d; if last_cr then v else (nline d; v) - | 0x000D (* CR *) -> cr d true; ncount d; nline d; v - | (0x0085 | 0x000C | 0x2028 | 0x2029) (* NEL | FF | LS | PS *) -> - cr d false; ncount d; nline d; v - | _ -> - cr d false; ncount d; ncol d; v - -let pp_nln_readline d = function -| `Malformed _ as v -> cr d false; ncount d; ncol d; v -| `Uchar u as v -> - match Uchar.to_int u with - | 0x000A (* LF *) -> - let last_cr = d.last_cr in - cr d false; if last_cr then d.k d else (ncount d; nline d; `Uchar d.nl) - | 0x000D (* CR *) -> cr d true; ncount d; nline d; `Uchar d.nl - | (0x0085 | 0x000C | 0x2028 | 0x2029) (* NEL | FF | LS | PS *) -> - cr d false; ncount d; nline d; `Uchar d.nl - | _ -> - cr d false; ncount d; ncol d; v - -let pp_nln_nlf d = function -| `Malformed _ as v -> cr d false; ncount d; ncol d; v -| `Uchar u as v -> - match Uchar.to_int u with - | 0x000A (* LF *) -> - let last_cr = d.last_cr in - cr d false; if last_cr then d.k d else (ncount d; nline d; `Uchar d.nl) - | 0x000D (* CR *) -> cr d true; ncount d; nline d; `Uchar d.nl - | 0x0085 (* NEL *) -> cr d false; ncount d; nline d; `Uchar d.nl - | (0x000C | 0x2028 | 0x2029) (* FF | LS | PS *) -> - cr d false; ncount d; nline d; v - | _ -> - cr d false; ncount d; ncol d; v - -let pp_nln_ascii d = function -| `Malformed _ as v -> cr d false; ncount d; ncol d; v -| `Uchar u as v -> - match Uchar.to_int u with - | 0x000A (* LF *) -> - let last_cr = d.last_cr in - cr d false; if last_cr then d.k d else (ncount d; nline d; `Uchar d.nl) - | 0x000D (* CR *) -> cr d true; ncount d; nline d; `Uchar d.nl - | (0x0085 | 0x000C | 0x2028 | 0x2029) (* NEL | FF | LS | PS *) -> - cr d false; ncount d; nline d; v - | _ -> - cr d false; ncount d; ncol d; v - -let decode_fun = function -| `UTF_8 -> decode_utf_8 -| `UTF_16 -> decode_utf_16be (* see [pp_remove_bom]. *) -| `UTF_16BE -> decode_utf_16be -| `UTF_16LE -> decode_utf_16le -| `US_ASCII -> decode_us_ascii -| `ISO_8859_1 -> decode_iso_8859_1 - -let decoder ?nln ?encoding src = - let pp, nl = match nln with - | None -> pp_nln_none, Uchar.unsafe_of_int 0x000A (* not used. *) - | Some (`ASCII nl) -> pp_nln_ascii, nl - | Some (`NLF nl) -> pp_nln_nlf, nl - | Some (`Readline nl) -> pp_nln_readline, nl - in - let encoding, k = match encoding with - | None -> `UTF_8, guess_encoding - | Some e -> (e :> decoder_encoding), decode_fun e - in - let i, i_pos, i_max = match src with - | `Manual -> Bytes.empty, 1, 0 (* implies src_rem d = 0. *) - | `Channel _ -> Bytes.create io_buffer_size, 1, 0 (* idem. *) - | `String s -> Bytes.unsafe_of_string s, 0, String.length s - 1 - in - { src = (src :> src); encoding; nln = (nln :> nln option); nl; - i; i_pos; i_max; t = Bytes.create 4; t_len = 0; t_need = 0; - removed_bom = false; last_cr = false; line = 1; col = 0; - byte_count = 0; count = 0; - pp = pp_remove_bom (encoding = `UTF_16) pp; k } - -let decode d = d.k d -let decoder_line d = d.line -let decoder_col d = d.col -let decoder_byte_count d = d.byte_count -let decoder_count d = d.count -let decoder_removed_bom d = d.removed_bom -let decoder_src d = d.src -let decoder_nln d = d.nln -let decoder_encoding d = d.encoding -let set_decoder_encoding d e = - d.encoding <- (e :> decoder_encoding); d.k <- decode_fun e - -(* Encode *) - -type dst = [ `Channel of out_channel | `Buffer of Buffer.t | `Manual ] -type encode = [ `Await | `End | `Uchar of Uchar.t ] -type encoder = - { dst : dst; (* output destination. *) - encoding : encoding; (* encoded encoding. *) - mutable o : Bytes.t; (* current output chunk. *) - mutable o_pos : int; (* next output position to write. *) - mutable o_max : int; (* maximal output position to write. *) - t : Bytes.t; (* four bytes buffer for overlapping writes. *) - mutable t_pos : int; (* next position to read in [t]. *) - mutable t_max : int; (* maximal position to read in [t]. *) - mutable k : (* encoder continuation. *) - encoder -> encode -> [ `Ok | `Partial ] } - -(* On encodes that overlap two (or more) [e.o] buffers, we encode the - character to the temporary buffer [o.t] and continue with - [tmp_flush] to write this data on the different [e.o] buffers. If - the [e.o] buffers are not too small this is faster than - continuation based byte per byte writes. *) - -let o_rem e = e.o_max - e.o_pos + 1 (* remaining bytes to write in [e.o]. *) -let dst e s j l = (* set [e.o] with [s]. *) - if (j < 0 || l < 0 || j + l > Bytes.length s) then invalid_bounds j l; - e.o <- s; e.o_pos <- j; e.o_max <- j + l - 1 - -let partial k e = function `Await -> k e | `Uchar _ | `End -> invalid_encode () -let flush k e = match e.dst with(* get free storage in [d.o] and [k]ontinue. *) -| `Manual -> e.k <- partial k; `Partial -| `Channel oc -> output oc e.o 0 e.o_pos; e.o_pos <- 0; k e -| `Buffer b -> - let o = Bytes.unsafe_to_string e.o in - Buffer.add_substring b o 0 e.o_pos; e.o_pos <- 0; k e - - -let t_range e max = e.t_pos <- 0; e.t_max <- max -let rec t_flush k e = (* flush [d.t] up to [d.t_max] in [d.i]. *) - let blit e l = - unsafe_blit e.t e.t_pos e.o e.o_pos l; - e.o_pos <- e.o_pos + l; e.t_pos <- e.t_pos + l - in - let rem = o_rem e in - let len = e.t_max - e.t_pos + 1 in - if rem < len then (blit e rem; flush (t_flush k) e) else (blit e len; k e) - -(* Encoders. *) - -let rec encode_utf_8 e v = - let k e = e.k <- encode_utf_8; `Ok in - match v with - | `Await -> k e - | `End -> flush k e - | `Uchar u as v -> - let u = Uchar.to_int u in - let rem = o_rem e in - if u <= 0x007F then - if rem < 1 then flush (fun e -> encode_utf_8 e v) e else - (unsafe_set_byte e.o e.o_pos u; e.o_pos <- e.o_pos + 1; k e) - else if u <= 0x07FF then - begin - let s, j, k = - if rem < 2 then (t_range e 1; e.t, 0, t_flush k) else - let j = e.o_pos in (e.o_pos <- e.o_pos + 2; e.o, j, k) - in - unsafe_set_byte s j (0xC0 lor (u lsr 6)); - unsafe_set_byte s (j + 1) (0x80 lor (u land 0x3F)); - k e - end - else if u <= 0xFFFF then - begin - let s, j, k = - if rem < 3 then (t_range e 2; e.t, 0, t_flush k) else - let j = e.o_pos in (e.o_pos <- e.o_pos + 3; e.o, j, k) - in - unsafe_set_byte s j (0xE0 lor (u lsr 12)); - unsafe_set_byte s (j + 1) (0x80 lor ((u lsr 6) land 0x3F)); - unsafe_set_byte s (j + 2) (0x80 lor (u land 0x3F)); - k e - end - else - begin - let s, j, k = - if rem < 4 then (t_range e 3; e.t, 0, t_flush k) else - let j = e.o_pos in (e.o_pos <- e.o_pos + 4; e.o, j, k) - in - unsafe_set_byte s j (0xF0 lor (u lsr 18)); - unsafe_set_byte s (j + 1) (0x80 lor ((u lsr 12) land 0x3F)); - unsafe_set_byte s (j + 2) (0x80 lor ((u lsr 6) land 0x3F)); - unsafe_set_byte s (j + 3) (0x80 lor (u land 0x3F)); - k e - end - -let rec encode_utf_16be e v = - let k e = e.k <- encode_utf_16be; `Ok in - match v with - | `Await -> k e - | `End -> flush k e - | `Uchar u -> - let u = Uchar.to_int u in - let rem = o_rem e in - if u < 0x10000 then - begin - let s, j, k = - if rem < 2 then (t_range e 1; e.t, 0, t_flush k) else - let j = e.o_pos in (e.o_pos <- e.o_pos + 2; e.o, j, k) - in - unsafe_set_byte s j (u lsr 8); - unsafe_set_byte s (j + 1) (u land 0xFF); - k e - end else begin - let s, j, k = - if rem < 4 then (t_range e 3; e.t, 0, t_flush k) else - let j = e.o_pos in (e.o_pos <- e.o_pos + 4; e.o, j, k) - in - let u' = u - 0x10000 in - let hi = (0xD800 lor (u' lsr 10)) in - let lo = (0xDC00 lor (u' land 0x3FF)) in - unsafe_set_byte s j (hi lsr 8); - unsafe_set_byte s (j + 1) (hi land 0xFF); - unsafe_set_byte s (j + 2) (lo lsr 8); - unsafe_set_byte s (j + 3) (lo land 0xFF); - k e - end - -let rec encode_utf_16le e v = (* encode_uft_16be with bytes swapped. *) - let k e = e.k <- encode_utf_16le; `Ok in - match v with - | `Await -> k e - | `End -> flush k e - | `Uchar u -> - let u = Uchar.to_int u in - let rem = o_rem e in - if u < 0x10000 then - begin - let s, j, k = - if rem < 2 then (t_range e 1; e.t, 0, t_flush k) else - let j = e.o_pos in (e.o_pos <- e.o_pos + 2; e.o, j, k) - in - unsafe_set_byte s j (u land 0xFF); - unsafe_set_byte s (j + 1) (u lsr 8); - k e - end - else - begin - let s, j, k = - if rem < 4 then (t_range e 3; e.t, 0, t_flush k) else - let j = e.o_pos in (e.o_pos <- e.o_pos + 4; e.o, j, k) - in - let u' = u - 0x10000 in - let hi = (0xD800 lor (u' lsr 10)) in - let lo = (0xDC00 lor (u' land 0x3FF)) in - unsafe_set_byte s j (hi land 0xFF); - unsafe_set_byte s (j + 1) (hi lsr 8); - unsafe_set_byte s (j + 2) (lo land 0xFF); - unsafe_set_byte s (j + 3) (lo lsr 8); - k e - end - -let encode_fun = function -| `UTF_8 -> encode_utf_8 -| `UTF_16 -> encode_utf_16be -| `UTF_16BE -> encode_utf_16be -| `UTF_16LE -> encode_utf_16le - -let encoder encoding dst = - let o, o_pos, o_max = match dst with - | `Manual -> Bytes.empty, 1, 0 (* implies o_rem e = 0. *) - | `Buffer _ - | `Channel _ -> Bytes.create io_buffer_size, 0, io_buffer_size - 1 - in - { dst = (dst :> dst); encoding = (encoding :> encoding); o; o_pos; o_max; - t = Bytes.create 4; t_pos = 1; t_max = 0; k = encode_fun encoding} - -let encode e v = e.k e (v :> encode) -let encoder_encoding e = e.encoding -let encoder_dst e = e.dst - -(* Manual sources and destinations. *) - -module Manual = struct - let src = src - let dst = dst - let dst_rem = o_rem -end - -(* Strings folders and Buffer encoders *) - -module String = struct - let encoding_guess s = - let s = Bytes.unsafe_of_string s in - match r_encoding s 0 (max (Bytes.length s) 3) with - | `UTF_8 d -> `UTF_8, (d = `BOM) - | `UTF_16BE d -> `UTF_16BE, (d = `BOM) - | `UTF_16LE d -> `UTF_16LE, (d = `BOM) - - type 'a folder = - 'a -> int -> [ `Uchar of Uchar.t | `Malformed of string ] -> 'a - - let fold_utf_8 ?(pos = 0) ?len f acc s = - let rec loop acc f s i last = - if i > last then acc else - let need = unsafe_array_get utf_8_len (unsafe_byte s i) in - if need = 0 then loop (f acc i (malformed s i 1)) f s (i + 1) last else - let rem = last - i + 1 in - if rem < need then f acc i (malformed s i rem) else - loop (f acc i (r_utf_8 s i need)) f s (i + need) last - in - let len = match len with None -> String.length s - pos | Some l -> l in - let last = pos + len - 1 in - loop acc f (Bytes.unsafe_of_string s) pos last - - let fold_utf_16be ?(pos = 0) ?len f acc s = - let rec loop acc f s i last = - if i > last then acc else - let rem = last - i + 1 in - if rem < 2 then f acc i (malformed s i 1) else - match r_utf_16 s i (i + 1) with - | `Uchar _ | `Malformed _ as v -> loop (f acc i v) f s (i + 2) last - | `Hi hi -> - if rem < 4 then f acc i (malformed s i rem) else - loop (f acc i (r_utf_16_lo hi s (i + 2) (i + 3))) f s (i + 4) last - in - let len = match len with None -> String.length s - pos | Some l -> l in - let last = pos + len - 1 in - loop acc f (Bytes.unsafe_of_string s) pos last - - let fold_utf_16le ?(pos = 0) ?len f acc s = - (* [fold_utf_16be], bytes swapped. *) - let rec loop acc f s i last = - if i > last then acc else - let rem = last - i + 1 in - if rem < 2 then f acc i (malformed s i 1) else - match r_utf_16 s (i + 1) i with - | `Uchar _ | `Malformed _ as v -> loop (f acc i v) f s (i + 2) last - | `Hi hi -> - if rem < 4 then f acc i (malformed s i rem) else - loop (f acc i (r_utf_16_lo hi s (i + 3) (i + 2))) f s (i + 4) last - in - let len = match len with None -> String.length s - pos | Some l -> l in - let last = pos + len - 1 in - loop acc f (Bytes.unsafe_of_string s) pos last -end - -module Buffer = struct - let add_utf_8 b u = - let u = Uchar.to_int u in - let w byte = Buffer.add_char b (unsafe_chr byte) in (* inlined. *) - if u <= 0x007F then - (w u) - else if u <= 0x07FF then - (w (0xC0 lor (u lsr 6)); - w (0x80 lor (u land 0x3F))) - else if u <= 0xFFFF then - (w (0xE0 lor (u lsr 12)); - w (0x80 lor ((u lsr 6) land 0x3F)); - w (0x80 lor (u land 0x3F))) - else - (w (0xF0 lor (u lsr 18)); - w (0x80 lor ((u lsr 12) land 0x3F)); - w (0x80 lor ((u lsr 6) land 0x3F)); - w (0x80 lor (u land 0x3F))) - - let add_utf_16be b u = - let u = Uchar.to_int u in - let w byte = Buffer.add_char b (unsafe_chr byte) in (* inlined. *) - if u < 0x10000 then (w (u lsr 8); w (u land 0xFF)) else - let u' = u - 0x10000 in - let hi = (0xD800 lor (u' lsr 10)) in - let lo = (0xDC00 lor (u' land 0x3FF)) in - w (hi lsr 8); w (hi land 0xFF); - w (lo lsr 8); w (lo land 0xFF) - - let add_utf_16le b u = (* swapped add_utf_16be. *) - let u = Uchar.to_int u in - let w byte = Buffer.add_char b (unsafe_chr byte) in (* inlined. *) - if u < 0x10000 then (w (u land 0xFF); w (u lsr 8)) else - let u' = u - 0x10000 in - let hi = (0xD800 lor (u' lsr 10)) in - let lo = (0xDC00 lor (u' land 0x3FF)) in - w (hi land 0xFF); w (hi lsr 8); - w (lo land 0xFF); w (lo lsr 8) -end - -(*--------------------------------------------------------------------------- - Copyright (c) 2012 The uutf programmers - - Permission to use, copy, modify, and/or distribute this software for any - purpose with or without fee is hereby granted, provided that the above - copyright notice and this permission notice appear in all copies. - - THE SOFTWARE IS PROVIDED "AS IS" AND THE AUTHOR DISCLAIMS ALL WARRANTIES - WITH REGARD TO THIS SOFTWARE INCLUDING ALL IMPLIED WARRANTIES OF - MERCHANTABILITY AND FITNESS. IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR - ANY SPECIAL, DIRECT, INDIRECT, OR CONSEQUENTIAL DAMAGES OR ANY DAMAGES - WHATSOEVER RESULTING FROM LOSS OF USE, DATA OR PROFITS, WHETHER IN AN - ACTION OF CONTRACT, NEGLIGENCE OR OTHER TORTIOUS ACTION, ARISING OUT OF - OR IN CONNECTION WITH THE USE OR PERFORMANCE OF THIS SOFTWARE. - ---------------------------------------------------------------------------*) diff --git a/vendor/uutf/uutf.mli b/vendor/uutf/uutf.mli deleted file mode 100644 index 9c348208da9..00000000000 --- a/vendor/uutf/uutf.mli +++ /dev/null @@ -1,510 +0,0 @@ -(*--------------------------------------------------------------------------- - Copyright (c) 2012 The uutf programmers. All rights reserved. - Distributed under the ISC license, see terms at the end of the file. - ---------------------------------------------------------------------------*) - -(** Non-blocking streaming Unicode codec. - - [Uutf] is a non-blocking streaming codec to {{:#decode}decode} and - {{:#encode}encode} the {{:http://www.ietf.org/rfc/rfc3629.txt} - UTF-8}, {{:http://www.ietf.org/rfc/rfc2781.txt} UTF-16}, UTF-16LE - and UTF-16BE encoding schemes. It can efficiently work character by - character without blocking on IO. Decoders perform - character position tracking and support {{!nln}newline normalization}. - - Functions are also provided to {{!String} fold over} the characters - of UTF encoded OCaml string values and to {{!Buffer}directly encode} - characters in OCaml {!Stdlib.Buffer.t} values. {b Note} that since OCaml - 4.14, that functionality can be found in {!Stdlib.String} and - {!Stdlib.Buffer} and you are encouraged to migrate to it. - - See {{:#examples}examples} of use. - - {b References} - {ul - {- The Unicode Consortium. - {e {{:http://www.unicode.org/versions/latest}The Unicode Standard}}. - (latest version)}} -*) - - (** {1:ucharcsts Special Unicode characters} *) - -val u_bom : Uchar.t -(** [u_bom] is the {{:http://unicode.org/glossary/#byte_order_mark}byte - order mark} (BOM) character ([U+FEFF]). From OCaml 4.06 on, use - {!Uchar.bom}. *) - -val u_rep : Uchar.t -(** [u_rep] is the - {{:http://unicode.org/glossary/#replacement_character}replacement} - character ([U+FFFD]). From OCaml 4.06 on, use - {!Uchar.rep}. *) - - -(** {1:schemes Unicode encoding schemes} *) - -type encoding = [ `UTF_16 | `UTF_16BE | `UTF_16LE | `UTF_8 ] -(** The type for Unicode - {{:http://unicode.org/glossary/#character_encoding_scheme}encoding - schemes}. *) - -type decoder_encoding = [ encoding | `US_ASCII | `ISO_8859_1 ] -(** The type for encoding schemes {e decoded} by [Uutf]. Unicode encoding - schemes plus {{:http://tools.ietf.org/html/rfc20}US-ASCII} and - {{:http://www.ecma-international.org/publications/standards/Ecma-094.htm} - ISO/IEC 8859-1} (latin-1). *) - -val encoding_of_string : string -> decoder_encoding option -(** [encoding_of_string s] converts a (case insensitive) - {{:http://www.iana.org/assignments/character-sets}IANA character set name} - to an encoding. *) - -val encoding_to_string : [< decoder_encoding] -> string -(** [encoding_to_string e] is a - {{:http://www.iana.org/assignments/character-sets}IANA character set name} - for [e]. *) - -(** {1:decode Decode} *) - -type src = [ `Channel of in_channel | `String of string | `Manual ] -(** The type for input sources. With a [`Manual] source the client - must provide input with {!Manual.src}. *) - -type nln = [ `ASCII of Uchar.t | `NLF of Uchar.t | `Readline of Uchar.t ] -(** The type for newline normalizations. The variant argument is the - normalization character. - {ul - {- [`ASCII], normalizes CR ([U+000D]), LF ([U+000A]) and CRLF - (<[U+000D], [U+000A]>).} - {- [`NLF], normalizes the Unicode newline function (NLF). This is - NEL ([U+0085]) and the normalizations of [`ASCII].} - {- [`Readline], normalizes for a Unicode readline function. This is FF - ([U+000C]), LS ([U+2028]), PS ([U+2029]), and the normalizations - of [`NLF].}} - Used with an appropriate normalization character the [`NLF] and - [`Readline] normalizations allow to implement all the different - recommendations of Unicode's newline guidelines (section 5.8 in - Unicode 9.0.0). *) - -type decoder -(** The type for decoders. *) - -val decoder : ?nln:[< nln] -> ?encoding:[< decoder_encoding] -> [< src] -> - decoder -(** [decoder nln encoding src] is a decoder that inputs from [src]. - - {b Byte order mark.} - {{:http://unicode.org/glossary/#byte_order_mark}Byte order mark} - (BOM) constraints are application dependent and prone to - misunderstandings (see the - {{:http://www.unicode.org/faq/utf_bom.html#BOM}FAQ}). Hence, - [Uutf] decoders have a simple rule: an {e initial BOM is always - removed from the input and not counted in character position - tracking}. The function {!decoder_removed_bom} does however return - [true] if a BOM was removed so that all the information can be - recovered if needed. - - For UTF-16BE and UTF-16LE the above rule is a violation of - conformance D96 and D97 of the standard. [Uutf] favors the idea - that if there's a BOM, decoding with [`UTF_16] or the [`UTF_16XX] - corresponding to the BOM should decode the same character sequence - (this is not the case if you stick to the standard). The client - can however regain conformance by consulting the result of - {!decoder_removed_bom} and take appropriate action. - - {b Encoding.} [encoding] specifies the decoded encoding - scheme. If [`UTF_16] is used the endianness is determined - according to the standard: from a - {{:http://unicode.org/glossary/#byte_order_mark}BOM} - if there is one, [`UTF_16BE] otherwise. - - If [encoding] is unspecified it is guessed. The result of a guess - can only be [`UTF_8], [`UTF_16BE] or [`UTF_16LE]. The heuristic - looks at the first three bytes of input (or less if impossible) - and takes the {e first} matching byte pattern in the table below. -{v -xx = any byte -.. = any byte or no byte (input too small) -pp = positive byte -uu = valid UTF-8 first byte - -Bytes | Guess | Rationale ----------+-----------+----------------------------------------------- -EF BB BF | `UTF_8 | UTF-8 BOM -FE FF .. | `UTF_16BE | UTF-16BE BOM -FF FE .. | `UTF_16LE | UTF-16LE BOM -00 pp .. | `UTF_16BE | ASCII UTF-16BE and U+0000 is often forbidden -pp 00 .. | `UTF_16LE | ASCII UTF-16LE and U+0000 is often forbidden -uu .. .. | `UTF_8 | ASCII UTF-8 or valid UTF-8 first byte. -xx xx .. | `UTF_16BE | Not UTF-8 => UTF-16, no BOM => UTF-16BE -.. .. .. | `UTF_8 | Single malformed UTF-8 byte or no input. -v} - This heuristic is compatible both with BOM based - recognitition and - {{:http://tools.ietf.org/html/rfc4627#section-3}JSON-like encoding - recognition} that relies on ASCII being present at the beginning - of the stream. Also, {!decoder_removed_bom} will tell the client - if the guess was BOM based. - - {b Newline normalization.} If [nln] is specified, the given - newline normalization is performed, see {!nln}. Otherwise - all newlines are returned as found in the input. - - {b Character position.} The line number, column number, byte count - and character count of the last decoded character (including - [`Malformed] ones) are respectively returned by {!decoder_line}, - {!decoder_col}, {!decoder_byte_count} and {!decoder_count}. Before - the first call to {!val-decode} the line number is [1] and the column - is [0]. Each {!val-decode} returning [`Uchar] or [`Malformed] - increments the column until a newline. On a newline, the line - number is incremented and the column set to zero. For example the - line is [2] and column [0] after the first newline was - decoded. This can be understood as if {!val-decode} was moving an - insertion point to the right in the data. A {e newline} is - anything normalized by [`Readline], see {!nln}. - - [Uutf] assumes that each Unicode scalar value has a column width - of 1. The same assumption may not be made by the display program - (e.g. for [emacs]' compilation mode you need to set - [compilation-error-screen-columns] to [nil]). The problem is in - general difficult to solve without interaction or convention with the - display program's rendering engine. Depending on the context better column - increments can be implemented by using {!Uucp.Break.tty_width_hint} or - {{:http://unicode.org/reports/tr29/#Grapheme_Cluster_Boundaries} - grapheme cluster boundaries} (see {!Uuseg}). *) - -val decode : decoder -> - [ `Await | `Uchar of Uchar.t | `End | `Malformed of string] -(** [decode d] is: - {ul - {- [`Await] if [d] has a [`Manual] input source and awaits - for more input. The client must use {!Manual.src} to provide it.} - {- [`Uchar u] if a Unicode scalar value [u] was decoded.} - {- [`End] if the end of input was reached.} - {- [`Malformed bytes] if the [bytes] sequence is malformed according to - the decoded encoding scheme. If you are interested in a best-effort - decoding you can still continue to decode after an error until the - decoder synchronizes again on valid bytes. It may however be a good - idea to signal the malformed characters by adding an {!u_rep} - character to the parsed data, see the {{:#examples}examples}.}} - - {b Note.} Repeated invocation always eventually returns [`End], even - in case of errors. *) - -val decoder_encoding : decoder -> decoder_encoding -(** [decoder_encoding d] is [d]'s the decoded encoding scheme of [d]. - - {b Warning.} If the decoder guesses the encoding or uses [`UTF_16], - rely on this value only after the first [`Uchar] was decoded. *) - -(**/**) - -(* This function is dangerous, it may destroy the current continuation. - But it's needed for things like XML parsers. *) - -val set_decoder_encoding : decoder -> [< decoder_encoding] -> unit -(** [set_decoder_encoding d enc] changes the decoded encoding - to [enc] after decoding started. - - {b Warning.} Call only after {!val-decode} was called on [d] and that the - last call to it returned something different from [`Await] or data may - be lost. After encoding guess wait for at least three [`Uchar]s. *) - -(**/**) - -val decoder_line : decoder -> int -(** [decoder_line d] is the line number of the last - decoded (or malformed) character. See {!val-decoder} for details. *) - -val decoder_col : decoder -> int -(** [decoder_col d] is the column number of the last decoded - (or malformed) character. See {!val-decoder} for details. *) - -val decoder_byte_count : decoder -> int -(** [decoder_byte_count d] is the number of bytes already decoded on - [d] (including malformed ones). This is the last {!val-decode}'s - end byte offset counting from the beginning of the stream. *) - -val decoder_count : decoder -> int -(** [decoder_count d] is the number of characters already decoded on [d] - (including malformed ones). See {!val-decoder} for details. *) - -val decoder_removed_bom : decoder -> bool -(** [decoder_removed_bom d] is [true] iff an {e initial} - {{:http://unicode.org/glossary/#byte_order_mark}BOM} was - removed from the input stream. See {!val-decoder} for details. *) - -val decoder_src : decoder -> src -(** [decoder_src d] is [d]'s input source. *) - -val decoder_nln : decoder -> nln option -(** [decoder_nln d] returns [d]'s newline normalization (if any). *) - -val pp_decode : Format.formatter -> - [< `Await | `Uchar of Uchar.t | `End | `Malformed of string] -> unit -(** [pp_decode ppf v] prints an unspecified representation of [v] on - [ppf]. *) - -(** {1:encode Encode} *) - -type dst = [ `Channel of out_channel | `Buffer of Buffer.t | `Manual ] -(** The type for output destinations. With a [`Manual] destination the client - must provide output storage with {!Manual.dst}. *) - -type encoder -(** The type for Unicode encoders. *) - -val encoder : [< encoding] -> [< dst] -> encoder -(** [encoder encoding dst] is an encoder for [encoding] that outputs - to [dst]. - - {b Note.} No initial - {{:http://unicode.org/glossary/#byte_order_mark}BOM} - is encoded. If needed, this duty is left to the client. *) - -val encode : - encoder -> [<`Await | `End | `Uchar of Uchar.t ] -> [`Ok | `Partial ] -(** [encode e v] is : - {ul - {- [`Partial] iff [e] has a [`Manual] destination and needs more output - storage. The client must use {!Manual.dst} to provide a new buffer - and then call {!val-encode} with [`Await] until [`Ok] is returned.} - {- [`Ok] when the encoder is ready to encode a new [`Uchar] or [`End]}} - - For [`Manual] destination, encoding [`End] always returns - [`Partial], the client should continue as usual with [`Await] - until [`Ok] is returned at which point {!Manual.dst_rem} [e] is - guaranteed to be the size of the last provided buffer (i.e. nothing - was written). - - {b Raises.} [Invalid_argument] if an [`Uchar] or [`End] is encoded - after a [`Partial] encode. *) - -val encoder_encoding : encoder -> encoding -(** [encoder_encoding e] is [e]'s encoding. *) - -val encoder_dst : encoder -> dst -(** [encoder_dst e] is [e]'s output destination. *) - -(** {1:manual Manual sources and destinations.} *) - -(** Manual sources and destinations. - - {b Warning.} Use only with [`Manual] decoder and encoders. *) -module Manual : sig - val src : decoder -> Bytes.t -> int -> int -> unit - (** [src d s j l] provides [d] with [l] bytes to read, starting at - [j] in [s]. This byte range is read by calls to {!val-decode} with [d] - until [`Await] is returned. To signal the end of input call the function - with [l = 0]. *) - - val dst : encoder -> Bytes.t -> int -> int -> unit - (** [dst e s j l] provides [e] with [l] bytes to write, starting - at [j] in [s]. This byte range is written by calls to - {!val-encode} with [e] until [`Partial] is returned. Use {!dst_rem} to - know the remaining number of non-written free bytes in [s]. *) - - val dst_rem : encoder -> int - (** [dst_rem e] is the remaining number of non-written, free bytes - in the last buffer provided with {!Manual.dst}. *) -end - -(** {1:strbuf String folders and Buffer encoders} *) - -(** Fold over the characters of UTF encoded OCaml [string] values. - - {b Note.} Since OCaml 4.14, UTF decoders are available in - {!Stdlib.String}. You are encouraged to migrate to them. *) -module String : sig - -(** {1 Encoding guess} *) - - val encoding_guess : string -> [ `UTF_8 | `UTF_16BE | `UTF_16LE ] * bool - (** [encoding_guess s] is the encoding guessed for [s] coupled with - [true] iff there's an initial - {{:http://unicode.org/glossary/#byte_order_mark}BOM}. *) - -(** {1 String folders} - - {b Note.} Initial {{:http://unicode.org/glossary/#byte_order_mark}BOM}s - are also folded over. *) - - type 'a folder = 'a -> int -> [ `Uchar of Uchar.t | `Malformed of string ] -> - 'a - (** The type for character folders. The integer is the index in the - string where the [`Uchar] or [`Malformed] starts. *) - - val fold_utf_8 : ?pos:int -> ?len:int -> 'a folder -> 'a -> string -> 'a - (** [fold_utf_8 f a s ?pos ?len ()] is - [f (] ... [(f (f a pos u]{_0}[) j]{_1}[ u]{_1}[)] ... [)] ... [) - j]{_n}[ u]{_n} - where [u]{_i}, [j]{_i} are characters and their start position - in the UTF-8 encoded substring [s] starting at [pos] and [len] - long. The default value for [pos] is [0] and [len] is - [String.length s - pos]. *) - - val fold_utf_16be : ?pos:int -> ?len:int -> 'a folder -> 'a -> string -> 'a - (** [fold_utf_16be f a s ?pos ?len ()] is - [f (] ... [(f (f a pos u]{_0}[) j]{_1}[ u]{_1}[)] ... [)] ... [) - j]{_n}[ u]{_n} - where [u]{_i}, [j]{_i} are characters and their start position - in the UTF-8 encoded substring [s] starting at [pos] and [len] - long. The default value for [pos] is [0] and [len] is - [String.length s - pos]. *) - - val fold_utf_16le : ?pos:int -> ?len:int -> 'a folder -> 'a -> string -> 'a - (** [fold_utf_16le f a s ?pos ?len ()] is - [f (] ... [(f (f a pos u]{_0}[) j]{_1}[ u]{_1}[)] ... [)] ... [) - j]{_n}[ u]{_n} - where [u]{_i}, [j]{_i} are characters and their start position - in the UTF-8 encoded substring [s] starting at [pos] and [len] - long. The default value for [pos] is [0] and [len] is - [String.length s - pos]. *) -end - -(** UTF encode characters in OCaml {!Buffer.t} values. - - {b Note.} Since OCaml 4.06, these encoders are available in - {!Stdlib.Buffer}. You are encouraged to migrate to them. *) -module Buffer : sig - - (** {1 Buffer encoders} *) - - val add_utf_8 : Buffer.t -> Uchar.t -> unit - (** [add_utf_8 b u] adds the UTF-8 encoding of [u] to [b]. *) - - val add_utf_16be : Buffer.t -> Uchar.t -> unit - (** [add_utf_16be b u] adds the UTF-16BE encoding of [u] to [b]. *) - - val add_utf_16le : Buffer.t -> Uchar.t -> unit - (** [add_utf_16le b u] adds the UTF-16LE encoding of [u] to [b]. *) -end - -(** {1:examples Examples} - - {2:readlines Read lines} - - The value of [lines src] is the list of lines in [src] as UTF-8 - encoded OCaml strings. Line breaks are determined according to the - recommendation R4 for a [readline] function in section 5.8 of - Unicode 9.0.0. If a decoding error occurs we silently replace the - malformed sequence by the replacement character {!u_rep} and continue. -{[let lines ?encoding (src : [`Channel of in_channel | `String of string]) = - let rec loop d buf acc = match Uutf.decode d with - | `Uchar u -> - begin match Uchar.to_int u with - | 0x000A -> - let line = Buffer.contents buf in - Buffer.clear buf; loop d buf (line :: acc) - | _ -> - Uutf.Buffer.add_utf_8 buf u; loop d buf acc - end - | `End -> List.rev (Buffer.contents buf :: acc) - | `Malformed _ -> Uutf.Buffer.add_utf_8 buf Uutf.u_rep; loop d buf acc - | `Await -> assert false - in - let nln = `Readline (Uchar.of_int 0x000A) in - loop (Uutf.decoder ~nln ?encoding src) (Buffer.create 512) [] -]} - Using the [`Manual] interface, [lines_fd] does the same but on a Unix file - descriptor. -{[let lines_fd ?encoding (fd : Unix.file_descr) = - let rec loop fd s d buf acc = match Uutf.decode d with - | `Uchar u -> - begin match Uchar.to_int u with - | 0x000A -> - let line = Buffer.contents buf in - Buffer.clear buf; loop fd s d buf (line :: acc) - | _ -> - Uutf.Buffer.add_utf_8 buf u; loop fd s d buf acc - end - | `End -> List.rev (Buffer.contents buf :: acc) - | `Malformed _ -> Uutf.Buffer.add_utf_8 buf Uutf.u_rep; loop fd s d buf acc - | `Await -> - let rec unix_read fd s j l = try Unix.read fd s j l with - | Unix.Unix_error (Unix.EINTR, _, _) -> unix_read fd s j l - in - let rc = unix_read fd s 0 (Bytes.length s) in - Uutf.Manual.src d s 0 rc; loop fd s d buf acc - in - let s = Bytes.create 65536 (* UNIX_BUFFER_SIZE in 4.0.0 *) in - let nln = `Readline (Uchar.of_int 0x000A) in - loop fd s (Uutf.decoder ~nln ?encoding `Manual) (Buffer.create 512) [] -]} - - {2:recode Recode} - - The result of [recode src out_encoding dst] has the characters of - [src] written on [dst] with encoding [out_encoding]. If a - decoding error occurs we silently replace the malformed sequence - by the replacement character {!u_rep} and continue. Note that we - don't add an initial - {{:http://unicode.org/glossary/#byte_order_mark}BOM} to [dst], - recoding will thus loose the initial BOM [src] may have. Whether - this is a problem or not depends on the context. -{[let recode ?nln ?encoding out_encoding - (src : [`Channel of in_channel | `String of string]) - (dst : [`Channel of out_channel | `Buffer of Buffer.t]) - = - let rec loop d e = match Uutf.decode d with - | `Uchar _ as u -> ignore (Uutf.encode e u); loop d e - | `End -> ignore (Uutf.encode e `End) - | `Malformed _ -> ignore (Uutf.encode e (`Uchar Uutf.u_rep)); loop d e - | `Await -> assert false - in - let d = Uutf.decoder ?nln ?encoding src in - let e = Uutf.encoder out_encoding dst in - loop d e]} - Using the [`Manual] interface, [recode_fd] does the same but between - Unix file descriptors. -{[let recode_fd ?nln ?encoding out_encoding - (fdi : Unix.file_descr) - (fdo : Unix.file_descr) - = - let rec encode fd s e v = match Uutf.encode e v with `Ok -> () - | `Partial -> - let rec unix_write fd s j l = - let rec write fd s j l = try Unix.single_write fd s j l with - | Unix.Unix_error (Unix.EINTR, _, _) -> write fd s j l - in - let wc = write fd s j l in - if wc < l then unix_write fd s (j + wc) (l - wc) else () - in - unix_write fd s 0 (Bytes.length s - Uutf.Manual.dst_rem e); - Uutf.Manual.dst e s 0 (Bytes.length s); - encode fd s e `Await - in - let rec loop fdi fdo ds es d e = match Uutf.decode d with - | `Uchar _ as u -> encode fdo es e u; loop fdi fdo ds es d e - | `End -> encode fdo es e `End - | `Malformed _ -> encode fdo es e (`Uchar Uutf.u_rep); loop fdi fdo ds es d e - | `Await -> - let rec unix_read fd s j l = try Unix.read fd s j l with - | Unix.Unix_error (Unix.EINTR, _, _) -> unix_read fd s j l - in - let rc = unix_read fdi ds 0 (Bytes.length ds) in - Uutf.Manual.src d ds 0 rc; loop fdi fdo ds es d e - in - let ds = Bytes.create 65536 (* UNIX_BUFFER_SIZE in 4.0.0 *) in - let es = Bytes.create 65536 (* UNIX_BUFFER_SIZE in 4.0.0 *) in - let d = Uutf.decoder ?nln ?encoding `Manual in - let e = Uutf.encoder out_encoding `Manual in - Uutf.Manual.dst e es 0 (Bytes.length es); - loop fdi fdo ds es d e]} -*) - -(*--------------------------------------------------------------------------- - Copyright (c) 2012 The uutf programmers - - Permission to use, copy, modify, and/or distribute this software for any - purpose with or without fee is hereby granted, provided that the above - copyright notice and this permission notice appear in all copies. - - THE SOFTWARE IS PROVIDED "AS IS" AND THE AUTHOR DISCLAIMS ALL WARRANTIES - WITH REGARD TO THIS SOFTWARE INCLUDING ALL IMPLIED WARRANTIES OF - MERCHANTABILITY AND FITNESS. IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR - ANY SPECIAL, DIRECT, INDIRECT, OR CONSEQUENTIAL DAMAGES OR ANY DAMAGES - WHATSOEVER RESULTING FROM LOSS OF USE, DATA OR PROFITS, WHETHER IN AN - ACTION OF CONTRACT, NEGLIGENCE OR OTHER TORTIOUS ACTION, ARISING OUT OF - OR IN CONNECTION WITH THE USE OR PERFORMANCE OF THIS SOFTWARE. - ---------------------------------------------------------------------------*)