Skip to content

Commit

Permalink
refactor: rename internal modules (#170)
Browse files Browse the repository at this point in the history
  • Loading branch information
favonia authored Oct 27, 2024
1 parent 4993f20 commit d426524
Show file tree
Hide file tree
Showing 21 changed files with 104 additions and 106 deletions.
2 changes: 1 addition & 1 deletion docs/quickstart.mld
Original file line number Diff line number Diff line change
Expand Up @@ -151,7 +151,7 @@ Reporter.emit ~loc:real_loc "wow" (* using [real_loc] instead *)

If you have seen an exception from asai like this:
{v
Invalid_argument("Asai.Explicator.explicate: <REASON>; use the debug mode")
Invalid_argument("Asai.SourceMarker.mark: <REASON>; use the debug mode")
v}
It means asai has detected invalid ranges. This usually indicates that your lexer or parser is buggy and generates invalid locations. For efficiency, asai by default will not check ranges carefully, but you can force it to do so by using the optional argument [debug]:
{[
Expand Down
8 changes: 4 additions & 4 deletions src/Asai.ml
Original file line number Diff line number Diff line change
Expand Up @@ -9,9 +9,9 @@ module MinimumSigs = MinimumSigs
module Tty = Tty
module GitHub = GitHub

module Explication = Explication
module Explicator = Explicator
module MarkedSource = MarkedSource
module SourceMarker = SourceMarker
module SourceReader = SourceReader

module UserContent = UserContent
module Flattener = Flattener
module SourceUtils = SourceUtils
module RangeFlattener = RangeFlattener
10 changes: 5 additions & 5 deletions src/Asai.mli
Original file line number Diff line number Diff line change
Expand Up @@ -50,18 +50,18 @@ module GitHub = GitHub
(** The internals are exposed for convenience, but they are subject to changes between minor versions. *)

(** The definition of highlighted text suitable for rendering. You probably do not need this module unless you want to create your own diagnostic handler. *)
module Explication = Explication
module MarkedSource = MarkedSource

(** Turning location information into highlighted text suitable for rendering. You probably do not need this module unless you want to create your own diagnostic handler. *)
module Explicator = Explicator
module SourceMarker = SourceMarker

(** Reading the source content. It uses memory-mapped I/O for files. You probably do not need this module unless you want to create your own diagnostic handler. *)
module SourceReader = SourceReader

(**/**)

(** Helper functions for handling user content. This is exposed for internal testing. Absolutely no stability guarantees. *)
module UserContent = UserContent
module SourceUtils = SourceUtils

(** The internal flattener that is tightly coupled with {!module:Explication}. This is exposed for internal testing. Absolutely no stability guarantees. *)
module Flattener = Flattener
(** The internal flattener that is tightly coupled with {!module:MarkedSource}. This is exposed for internal testing. Absolutely no stability guarantees. *)
module RangeFlattener = RangeFlattener
4 changes: 0 additions & 4 deletions src/Explicator.mli

This file was deleted.

2 changes: 1 addition & 1 deletion src/Explication.ml → src/MarkedSource.ml
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
include ExplicationData
include MarkedSourceData

let dump_marker dump_tag fmt =
function
Expand Down
2 changes: 1 addition & 1 deletion src/Explication.mli → src/MarkedSource.mli
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
(** {1 Types} *)

(* @include *)
include module type of ExplicationData
include module type of MarkedSourceData

(** {1 Debugging} *)

Expand Down
File renamed without changes.
4 changes: 2 additions & 2 deletions src/Flattener.ml → src/RangeFlattener.ml
Original file line number Diff line number Diff line change
@@ -1,8 +1,8 @@
open Bwd
open Bwd.Infix

open Explication
open ExplicatorSigs
open MarkedSource
open SourceMarkerSigs

type 'tag block =
{ begin_line_num : int
Expand Down
4 changes: 2 additions & 2 deletions src/Flattener.mli → src/RangeFlattener.mli
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
open Explication
open MarkedSource

type 'tag block =
{ begin_line_num : int
Expand All @@ -12,6 +12,6 @@ type 'tag t = (Range.source * 'tag block list) list
val dump_block : (Format.formatter -> 'tag -> unit) -> Format.formatter -> 'tag block -> unit
val dump : (Format.formatter -> 'tag -> unit) -> Format.formatter -> 'tag t -> unit

module Make (Tag : ExplicatorSigs.Tag) : sig
module Make (Tag : SourceMarkerSigs.Tag) : sig
val flatten : block_splitting_threshold:int -> (Range.t * Tag.t) list -> Tag.t t
end
48 changes: 24 additions & 24 deletions src/Explicator.ml → src/SourceMarker.ml
Original file line number Diff line number Diff line change
@@ -1,12 +1,12 @@
open Bwd
open Bwd.Infix

open Explication
include ExplicatorSigs
open MarkedSource
include SourceMarkerSigs

(* helper functions used by the register_printer below *)

let print_invalid_offset fmt : UserContent.invalid_offset -> unit =
let print_invalid_offset fmt : SourceUtils.invalid_offset -> unit =
function
| `Negative i ->
Format.fprintf fmt "its@ offset@ %d@ is@ negative." i
Expand All @@ -15,7 +15,7 @@ let print_invalid_offset fmt : UserContent.invalid_offset -> unit =
| `Within_newline (i, (s, e)) ->
Format.fprintf fmt "its@ offset@ %d@ is@ within@ a@ newline@ sequence@ [%d,%d)." i s e

let print_invalid_position fmt : UserContent.invalid_position -> unit =
let print_invalid_position fmt : SourceUtils.invalid_position -> unit =
function
| `Offset r ->
print_invalid_offset fmt r
Expand All @@ -24,7 +24,7 @@ let print_invalid_position fmt : UserContent.invalid_position -> unit =
| `Incorrect_line_num (ln, ln') ->
Format.fprintf fmt "its@ line@ number@ is@ %d@ but@ it@ should@ have@ been@ %d." ln ln'

let print_invalid_range fmt : UserContent.invalid_range -> unit =
let print_invalid_range fmt : SourceUtils.invalid_range -> unit =
function
| `Begin r ->
Format.fprintf fmt "its@ beginning@ position@ is@ invalid;@ %a" print_invalid_position r
Expand Down Expand Up @@ -59,7 +59,7 @@ module Make (Tag : Tag) = struct
String.init (end_ - begin_) @@ fun i ->
SourceReader.unsafe_get source (begin_ + i)

type explicator_state =
type marker_state =
{ lines : Tag.t line bwd
; tokens : Tag.t token bwd
; remaining_line_markers : (int * Tag.t) list
Expand All @@ -69,20 +69,20 @@ module Make (Tag : Tag) = struct
; line_num : int
}

module F = Flattener.Make(Tag)
module F = RangeFlattener.Make(Tag)

let explicate_block ~line_breaks source (b : Tag.t Flattener.block) : Tag.t block =
let mark_block ~line_breaks source (b : Tag.t RangeFlattener.block) : Tag.t block =
match b.markers with
| [] -> invalid_arg "explicate_block: empty block; should be impossible"
| [] -> invalid_arg "mark_block: empty block; should be impossible"
| ((first_loc, _) :: _) as markers ->
let source = SourceReader.load source in
let eof = SourceReader.length source in
let find_eol i = UserContent.find_eol ~line_breaks (SourceReader.unsafe_get source) (i, eof) in
let find_eol i = SourceUtils.find_eol ~line_breaks (SourceReader.unsafe_get source) (i, eof) in
let rec go state : (Range.position * Tag.t marker) list -> _ =
function
| (loc, marker) :: markers when state.cursor.line_num = loc.line_num (* on the same line *) ->
if loc.offset > eof then invalid_arg "Asai.Explicator.explicate: position beyond EOF; use the debug mode";
if loc.offset > state.eol then invalid_arg "Asai.Explicator.explicate: unexpected newline; use the debug mode";
if loc.offset > eof then invalid_arg "Asai.SourceMarker.mark: position beyond EOF; use the debug mode";
if loc.offset > state.eol then invalid_arg "Asai.SourceMarker.mark: unexpected newline; use the debug mode";
let tokens =
if loc.offset = state.cursor.offset then
state.tokens <: Marker marker
Expand Down Expand Up @@ -113,11 +113,11 @@ module Make (Tag : Tag) = struct
| [], _ ->
assert (state.line_num = b.end_line_num);
lines
| _ :: _, None -> invalid_arg "Asai.Explicator.explicate: position beyond EOF; use the debug mode"
| _ :: _, None -> invalid_arg "Asai.SourceMarker.mark: position beyond EOF; use the debug mode"
| (loc, _) :: _, Some eol_shift ->
if loc.offset > eof then invalid_arg "Asai.Explicator.explicate: position beyond EOF; use the debug mode";
if loc.offset <= state.eol then invalid_arg "Asai.Explicator.explicate: expected newline missing; use the debug mode";
if loc.offset < state.eol + eol_shift then invalid_arg "Asai.Explicator.explicate: offset within newline; use the debug mode";
if loc.offset > eof then invalid_arg "Asai.SourceMarker.mark: position beyond EOF; use the debug mode";
if loc.offset <= state.eol then invalid_arg "Asai.SourceMarker.mark: expected newline missing; use the debug mode";
if loc.offset < state.eol + eol_shift then invalid_arg "Asai.SourceMarker.mark: offset within newline; use the debug mode";
(* Okay, p is really on the next line *)
let cursor = eol_to_next_line eol_shift {state.cursor with offset = state.eol} in
let eol, eol_shift = find_eol (state.eol + eol_shift) in
Expand Down Expand Up @@ -151,23 +151,23 @@ module Make (Tag : Tag) = struct
; lines = Bwd.to_list @@ lines
}

let[@inline] explicate_blocks ~line_breaks source ranges =
List.map (explicate_block ~line_breaks source) ranges
let[@inline] mark_blocks ~line_breaks source ranges =
List.map (mark_block ~line_breaks source) ranges

let[@inline] explicate_part ~line_breaks (source, bs) : Tag.t part =
{ source; blocks = explicate_blocks ~line_breaks source bs }
let[@inline] mark_part ~line_breaks (source, bs) : Tag.t part =
{ source; blocks = mark_blocks ~line_breaks source bs }

let check_ranges ~line_breaks ranges =
List.iter
(fun (range, _) ->
let source = SourceReader.load @@ Range.source range in
let read = SourceReader.unsafe_get source in
let eof = SourceReader.length source in
try UserContent.check_range ~line_breaks ~eof read range
with UserContent.Invalid_range reason -> raise @@ Invalid_range (range, reason))
try SourceUtils.check_range ~line_breaks ~eof read range
with SourceUtils.Invalid_range reason -> raise @@ Invalid_range (range, reason))
ranges

let explicate ?(line_breaks=`Traditional) ?(block_splitting_threshold=5) ?(debug=false) ranges =
let mark ?(line_breaks=`Traditional) ?(block_splitting_threshold=5) ?(debug=false) ranges =
if debug then check_ranges ~line_breaks ranges;
List.map (explicate_part ~line_breaks) @@ F.flatten ~block_splitting_threshold ranges
List.map (mark_part ~line_breaks) @@ F.flatten ~block_splitting_threshold ranges
end
4 changes: 4 additions & 0 deletions src/SourceMarker.mli
Original file line number Diff line number Diff line change
@@ -0,0 +1,4 @@
include module type of SourceMarkerSigs

(** Making a marker. *)
module Make : functor (Tag : Tag) -> S with module Tag := Tag
12 changes: 6 additions & 6 deletions src/ExplicatorSigs.ml → src/SourceMarkerSigs.ml
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
open Explication
open MarkedSource

exception Invalid_range of Range.t * UserContent.invalid_range
(** [Invalid_range (range, reason)] means that [range] is an invalid range because of [reason]. This exception will be raised only when the debug mode is enabled. See the [debug] parameter of {!val:Explicator.S.explicate} for enabling the debug mode. *)
exception Invalid_range of Range.t * SourceUtils.invalid_range
(** [Invalid_range (range, reason)] means that [range] is an invalid range because of [reason]. This exception will be raised only when the debug mode is enabled. See the [debug] parameter of {!val:SourceMarker.S.mark} for enabling the debug mode. *)

(** The signature of tags *)
module type Tag = sig
Expand All @@ -17,12 +17,12 @@ module type Tag = sig
val dump : Format.formatter -> t -> unit
end

(** The signature of explicators. *)
(** The signature of markers. *)
module type S = sig
module Tag : Tag

val explicate : ?line_breaks:[`Unicode | `Traditional] -> ?block_splitting_threshold:int -> ?debug:bool -> (Range.t * Tag.t) list -> Tag.t t
(** Explicate a list of ranges using content from a data reader. This function must be run under [SourceReader.run].
val mark : ?line_breaks:[`Unicode | `Traditional] -> ?block_splitting_threshold:int -> ?debug:bool -> (Range.t * Tag.t) list -> Tag.t t
(** Mark content from a source reader with a list of ranges. This function must be run within [SourceReader.run].
@param line_breaks The set of character sequences that are recognized as (hard) line breaks. The [`Unicode] set contains all Unicode character sequences in {{:https://www.unicode.org/versions/Unicode15.0.0/ch05.pdf#G41643}Unicode 15.0.0 Table 5-1.} The [`Traditional] set only contains [U+000A (LF)], [U+000D (CR)], and [U+000D U+000A (CRLF)] as line breaks. The default is the [`Traditional] set.
@param block_splitting_threshold The maximum number of consecutive, non-highlighted lines allowed in a block. The function will try to minimize the number of blocks, as long as no block has too many consecutive, non-highlighted lines. A higher threshold will lead to fewer blocks. When the threshold is zero, it means no block can contain any non-highlighted line. The default value is zero.
Expand Down
3 changes: 1 addition & 2 deletions src/UserContent.ml → src/SourceUtils.ml
Original file line number Diff line number Diff line change
@@ -1,8 +1,7 @@
include UserContentData
include SourceUtilsData

exception Invalid_offset of invalid_offset
exception Invalid_position of invalid_position
exception Invalid_range of invalid_range

let find_eol_traditional read (i, eof) =
let rec go i =
Expand Down
5 changes: 1 addition & 4 deletions src/UserContent.mli → src/SourceUtils.mli
Original file line number Diff line number Diff line change
@@ -1,7 +1,4 @@
include module type of UserContentData

(** The exception indicating that a range is invalid. *)
exception Invalid_range of invalid_range
include module type of SourceUtilsData

(** [find_eol ~line_breaks read (pos, eof)] returns the end position of the first line and the length of the first newline sequence (if any) within the range [\[pos, end)]. If no newlines are found, then [None] is returned as the length.
Expand Down
3 changes: 3 additions & 0 deletions src/UserContentData.ml → src/SourceUtilsData.ml
Original file line number Diff line number Diff line change
Expand Up @@ -17,3 +17,6 @@ type invalid_range =
[ `Begin of invalid_position (** The first position of a range is invalid. *)
| `End of invalid_position (** The second position of a range is invalid. *)
]

(** The exception indicating that a range is invalid. *)
exception Invalid_range of invalid_range
44 changes: 22 additions & 22 deletions src/tty/Tty.ml
Original file line number Diff line number Diff line change
Expand Up @@ -8,7 +8,7 @@ let string_of_severity : Diagnostic.severity -> string =
| Error -> "error"
| Bug -> "bug"

module E = Explicator.Make(TtyTag)
module SM = SourceMarker.Make(TtyTag)

(* calculating the width of line numbers *)

Expand Down Expand Up @@ -51,9 +51,9 @@ let render_code ~param ~severity fmt short_code =
short_code
(Ansi.reset_string ~param style)

(* explication *)
(* marked source *)

module ExplicationRenderer :
module MarkedSourceRenderer :
sig
type param =
{
Expand All @@ -63,7 +63,7 @@ sig
ansi : Ansi.param;
}

val render : param:param -> Format.formatter -> TtyTag.t Explication.t -> unit
val render : param:param -> Format.formatter -> TtyTag.t MarkedSource.t -> unit
end
=
struct
Expand Down Expand Up @@ -97,7 +97,7 @@ struct
let style = TtyStyle.highlight ~param:param.ansi param.severity tag in
Format.fprintf fmt (highlight "%s")
(Ansi.style_string ~param:param.ansi style)
(UserContent.replace_control ~tab_size:param.tab_size segment)
(SourceUtils.replace_control ~tab_size:param.tab_size segment)
(Ansi.reset_string ~param:param.ansi style)

(* Current design:
Expand All @@ -106,16 +106,16 @@ struct
‹let x◂POS₀▸ = 1›₀ in let ‹x›₁ = «1 + ‹x›₂»◂POS₁▸
*)

let render_line ~line_num ~param fmt init_tag_set Explication.{tokens; markers} =
let render_line ~line_num ~param fmt init_tag_set MarkedSource.{tokens; markers} =
let go set =
function
| Explication.String s ->
| MarkedSource.String s ->
render_styled_segment ~param fmt (TtyTagSet.prioritized set) s; set
| Explication.Marker RangeEnd t ->
| MarkedSource.Marker RangeEnd t ->
TtyTagSet.remove t set
| Explication.Marker Point t ->
| MarkedSource.Marker Point t ->
render_styled_segment ~param fmt (Some t) "‹POS›"; set
| Explication.Marker RangeBegin t ->
| MarkedSource.Marker RangeBegin t ->
TtyTagSet.add t set
in
Format.fprintf fmt (" " ^^ highlight "%*d |" ^^ " ")
Expand All @@ -135,10 +135,10 @@ struct
(begin_line_num, TtyTagSet.empty)
lines

let render_block ~param fmt Explication.{begin_line_num; end_line_num=_; lines} =
let render_block ~param fmt MarkedSource.{begin_line_num; end_line_num=_; lines} =
render_lines ~param ~begin_line_num fmt lines

let render_part ~param fmt Explication.{source; blocks} =
let render_part ~param fmt MarkedSource.{source; blocks} =
render_source_header fmt source;
List.iter (render_block ~param fmt) blocks

Expand Down Expand Up @@ -178,15 +178,15 @@ struct
ansi : Ansi.param;
}

let line_number_width explication : int =
let max_line_number_block Explication.{end_line_num; _} = end_line_num in
let max_line_number_part Explication.{blocks; _} =
let line_number_width marked_source : int =
let max_line_number_block MarkedSource.{end_line_num; _} = end_line_num in
let max_line_number_part MarkedSource.{blocks; _} =
Utils.maximum @@ List.map max_line_number_block blocks
in
let max_line_number (parts : _ Explication.t) =
let max_line_number (parts : _ MarkedSource.t) =
Utils.maximum @@ List.map max_line_number_part parts
in
String.length @@ Int.to_string @@ max_line_number explication
String.length @@ Int.to_string @@ max_line_number marked_source

let render_textloc ~param ~severity ~extra_remarks fmt (textloc : Loctext.t) =
let located_tags, unlocated_tags =
Expand All @@ -198,12 +198,12 @@ struct
| (tag, Range.{loc = Some r; value = text}) -> Either.Left (r, (tag, text)))
(main :: extra_remarks)
in
let explication =
E.explicate ~block_splitting_threshold:param.block_splitting_threshold ~debug:param.debug located_tags
let marked_source =
SM.mark ~block_splitting_threshold:param.block_splitting_threshold ~debug:param.debug located_tags
in
let line_number_width = line_number_width explication in
let param = {ExplicationRenderer.severity = severity; tab_size = param.tab_size; line_number_width; ansi = param.ansi} in
ExplicationRenderer.render ~param fmt explication;
let line_number_width = line_number_width marked_source in
let param = {MarkedSourceRenderer.severity = severity; tab_size = param.tab_size; line_number_width; ansi = param.ansi} in
MarkedSourceRenderer.render ~param fmt marked_source;
List.iter (render_unlocated_tag ~severity:param.severity ~ansi:param.ansi fmt) unlocated_tags

let render_backtrace ~param ~severity fmt backtrace =
Expand Down
4 changes: 2 additions & 2 deletions src/tty/Tty.mli
Original file line number Diff line number Diff line change
Expand Up @@ -30,8 +30,8 @@ module Make (Message : MinimumSigs.Message) : sig
@param tab_size The number of spaces that should be used to replace a horizontal tab. Note that a horizontal tab is always expanded to the same number of spaces. The result should still be visually appealing as long as horizontal tabs are only used at the beginning of lines. The default value is [8].
@param debug Whether to enable the debug mode that performs expensive extra checking. The default is [false].
@raise Invalid_argument if [use_color] is explicitly set to [true] but [use_ansi] is explicitly set to [false], or if [tab_size < 0], or if invalid ranges are detected. When the debug mode is enabled, detection of invalid ranges will raise the more structured exception {!exception:Explicator.Invalid_range} instead.
@raise Invalid_range if the debug mode is enabled and invalid ranges are detected. See {!exception:Explicator.Invalid_range} for the detailed listing of all possible errors being reported.
@raise Invalid_argument if [use_color] is explicitly set to [true] but [use_ansi] is explicitly set to [false], or if [tab_size < 0], or if invalid ranges are detected. When the debug mode is enabled, detection of invalid ranges will raise the more structured exception {!exception:SourceMarker.Invalid_range} instead.
@raise Invalid_range if the debug mode is enabled and invalid ranges are detected. See {!exception:SourceMarker.Invalid_range} for the detailed listing of all possible errors being reported.
@see <https://no-color.org/> for the [NO_COLOR] specification
*)
Expand Down
Loading

0 comments on commit d426524

Please sign in to comment.