Skip to content

Commit

Permalink
Code block: warn when content does not start on a new line
Browse files Browse the repository at this point in the history
  • Loading branch information
panglesd committed Mar 3, 2025
1 parent e780b94 commit 1c9d32e
Show file tree
Hide file tree
Showing 12 changed files with 393 additions and 161 deletions.
35 changes: 19 additions & 16 deletions sherlodoc/test/cram/base_cli.t
Original file line number Diff line number Diff line change
Expand Up @@ -9,7 +9,7 @@
248 type 'a Base.Hashtbl.S_poly.key = 'a
257 type ('a, 'b) Base.Map.S_poly.t
257 type 'elt Base.Set.S_poly.t
259 type ('a, 'cmp) Base.Set.S_poly.set
259 type ('elt, 'cmp) Base.Set.S_poly.set
260 val Base.Set.S_poly.mem : 'a t -> 'a -> bool
260 type ('a, 'b) Base.Map.S_poly.tree
260 type 'elt Base.Set.S_poly.tree
Expand Down Expand Up @@ -78,10 +78,6 @@
361 val Base.Set.S_poly.invariants : 'a t -> bool
362 val Base.Set.S_poly.choose : 'a t -> 'a option
362 val Base.Set.S_poly.elements : 'a t -> 'a list
362 val Base.Hashtbl.S_poly.merge_into : src:('k, 'a) t ->
dst:('k, 'b) t ->
f:(key:'k key -> 'a -> 'b option -> 'b Merge_into_action.t) ->
unit
363 val Base.Map.S_poly.data : (_, 'v) t -> 'v list
363 val Base.Map.S_poly.keys : ('k, _) t -> 'k list
363 val Base.Set.S_poly.diff : 'a t -> 'a t -> 'a t
Expand All @@ -100,6 +96,7 @@
365 val Base.Map.S_poly.mem : ('k, _) t -> 'k -> bool
366 val Base.Set.S_poly.nth : 'a t -> int -> 'a option
366 val Base.Set.S_poly.union_list : 'a t list -> 'a t
366 val Base.Hashtbl.S_poly.capacity : (_, _) t -> int
367 val Base.Map.S_poly.invariants : ('k, 'v) t -> bool
367 val Base.Hashtbl.S_poly.is_empty : (_, _) t -> bool
367 val Base.Hashtbl.S_poly.find_and_call1 : ('a, 'b) t ->
Expand Down Expand Up @@ -130,13 +127,19 @@
363 val Base.Set.Using_comparator.Tree.group_by
373 val Base.Hashtbl.group
427 val Base.Set.S_poly.group_by
447 val Base.Dictionary_mutable.S1.group
454 val Base.Dictionary_mutable.Creators1.group
462 val Base.Set.Accessors_generic.group_by
473 val Base.Hashtbl.Poly.group
475 val Base.Set.Creators_and_accessors_generic.group_by
480 val Base.Hashtbl.Creators.group
485 val Base.Dictionary_mutable.S2.group
487 val Base.Hashtbl.Creators.group
492 val Base.Dictionary_mutable.Creators2.group
499 val Base.Hashtbl.S_without_submodules.group
575 val Base.Hashtbl.S_poly.group
507 val Base.Dictionary_mutable.S3.group
510 val Base.Dictionary_mutable.S.group
514 val Base.Dictionary_mutable.Creators3.group
$ sherlodoc search --no-rhs "group by"
val Base.Set.group_by
val Base.Set.Poly.group_by
Expand Down Expand Up @@ -193,7 +196,8 @@
143 type 'a Base.Export.list = 'a List.t
151 type 'a Base.List.t = 'a list
154 mod Base.List
154 mod Caml.List
156 val Base.Info.of_list : t list -> t
157 val Base.Error.of_list : t list -> t
158 val Base.List.rev : 'a t -> 'a t
159 val Base.List.hd_exn : 'a t -> 'a
159 val Base.List.return : 'a -> 'a t
Expand All @@ -202,6 +206,7 @@
161 val Base.List.tl_exn : 'a t -> 'a t
161 val Base.Queue.of_list : 'a list -> 'a t
161 val Base.Stack.of_list : 'a list -> 'a t
162 val Base.List.singleton : 'a -> 'a t
163 val Base.List.concat : 'a t t -> 'a t
163 mod Shadow_stdlib.List
164 val Base.List.last : 'a t -> 'a option
Expand All @@ -212,14 +217,13 @@
165 val Base.List.ignore_m : 'a t -> unit t
165 val Base.Bytes.of_char_list : char list -> t
166 val Base.List.drop : 'a t -> int -> 'a t
166 val Base.List.take : 'a t -> int -> 'a t
167 val Base.List.nth_exn : 'a t -> int -> 'a
$ sherlodoc search --print-cost ": list"
168 val Base.List.rev : 'a t -> 'a t
169 val Base.List.return : 'a -> 'a t
170 val Base.Bytes.to_list : t -> char list
171 val Base.List.join : 'a t t -> 'a t
171 val Base.List.tl_exn : 'a t -> 'a t
172 val Base.List.singleton : 'a -> 'a t
172 val Base.String.split_lines : t -> t list
173 val Base.List.concat : 'a t t -> 'a t
175 val Base.List.ignore_m : 'a t -> unit t
Expand All @@ -239,7 +243,6 @@
204 val Base.List.append : 'a t -> 'a t -> 'a t
204 val Base.Hashtbl.keys : ('a, _) t -> 'a key list
208 val Base.List.rev_append : 'a t -> 'a t -> 'a t
211 val Base.List.intersperse : 'a t -> sep:'a -> 'a t
Partial name search:
$ sherlodoc search --print-cost "strin"
Expand All @@ -250,7 +253,6 @@ Partial name search:
167 type Base.String.elt = char
169 val Base.String.rev : t -> t
171 mod Base.String
171 mod Caml.String
172 val Base.String.hash : t -> int
172 val Base.Exn.to_string : t -> string
172 val Base.Sys.max_string_length : int
Expand All @@ -262,19 +264,19 @@ Partial name search:
175 val Base.String.uppercase : t -> t
176 type Base.String.Caseless.t = t
176 val Base.String.capitalize : t -> t
177 mod Caml.StringLabels
177 type Base.String.Utf8.t = string
177 val Base.String.append : t -> t -> t
177 val Base.Exn.to_string_mach : t -> string
177 val Base.Info.to_string_hum : t -> string
177 val Base.Sign.to_string_hum : t -> string
178 val Base.Info.to_string_mach : t -> string
179 val Base.String.equal : t -> t -> bool
179 val Base.String.prefix : t -> int -> t
$ sherlodoc search --print-cost "tring"
177 type Base.string = String.t
182 type Base.String.t = string
182 type Base.String.elt = char
184 val Base.String.rev : t -> t
186 mod Base.String
186 mod Caml.String
186 val Base.Sexp.of_string : unit
187 val Base.String.hash : t -> int
188 val Base.String.escaped : t -> t
Expand All @@ -285,12 +287,13 @@ Partial name search:
191 type Base.String.Caseless.t = t
191 val Base.String.capitalize : t -> t
192 val Base.Exn.to_string : t -> string
192 type Base.String.Utf8.t = string
192 val Base.String.append : t -> t -> t
194 val Base.String.equal : t -> t -> bool
194 val Base.String.prefix : t -> int -> t
194 val Base.String.suffix : t -> int -> t
194 val Base.Float.to_string : t -> string
195 val Base.String.compare : t -> t -> int
195 mod Shadow_stdlib.String
197 val Base.String.ascending : t -> t -> int
197 val Base.String.split_lines : t -> t list
195 type Base.String.Utf16be.t = string
195 type Base.String.Utf32le.t = string
11 changes: 9 additions & 2 deletions sherlodoc/test/cram/base_odocls.t
Original file line number Diff line number Diff line change
@@ -1,7 +1,6 @@
$ find ../docs/odoc/base/ -name '*.odocl' -exec basename '{}' ';' | grep -v "__" | sort
base.odocl
base_internalhash_types.odocl
caml.odocl
md5_lib.odocl
page-index.odocl
shadow_stdlib.odocl
Expand All @@ -27,6 +26,7 @@
base__Buffer_intf.odocl
base__Bytes.odocl
base__Bytes0.odocl
base__Bytes_intf.odocl
base__Bytes_tr.odocl
base__Char.odocl
base__Char0.odocl
Expand All @@ -36,6 +36,10 @@
base__Comparisons.odocl
base__Container.odocl
base__Container_intf.odocl
base__Dictionary_immutable.odocl
base__Dictionary_immutable_intf.odocl
base__Dictionary_mutable.odocl
base__Dictionary_mutable_intf.odocl
base__Either.odocl
base__Either0.odocl
base__Either_intf.odocl
Expand Down Expand Up @@ -77,6 +81,7 @@
base__Int_conversions.odocl
base__Int_intf.odocl
base__Int_math.odocl
base__Int_string_conversions.odocl
base__Intable.odocl
base__Invariant.odocl
base__Invariant_intf.odocl
Expand Down Expand Up @@ -131,21 +136,23 @@
base__Staged.odocl
base__String.odocl
base__String0.odocl
base__String_intf.odocl
base__Stringable.odocl
base__Sys.odocl
base__Sys0.odocl
base__T.odocl
base__Type_equal.odocl
base__Type_equal_intf.odocl
base__Uchar.odocl
base__Uchar0.odocl
base__Uchar_intf.odocl
base__Uniform_array.odocl
base__Unit.odocl
base__Variant.odocl
base__Variantslib.odocl
base__With_return.odocl
base__Word_size.odocl
base_internalhash_types.odocl
caml.odocl
md5_lib.odocl
page-index.odocl
shadow_stdlib.odocl
49 changes: 26 additions & 23 deletions sherlodoc/test/cram/multi_package.t
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
$ ODOCLS=$(find ../docs/odoc/ -name '*.odocl' | grep -v "__" | sort)
$ echo "$ODOCLS" | awk 'END { print NR }'
6
5
$ export SHERLODOC_DB=db.bin
$ export SHERLODOC_FORMAT=marshal
$ sherlodoc index --index-docstring=false $ODOCLS
Expand All @@ -11,7 +11,7 @@
248 type 'a Base.Hashtbl.S_poly.key = 'a
257 type ('a, 'b) Base.Map.S_poly.t
257 type 'elt Base.Set.S_poly.t
259 type ('a, 'cmp) Base.Set.S_poly.set
259 type ('elt, 'cmp) Base.Set.S_poly.set
260 val Base.Set.S_poly.mem : 'a t -> 'a -> bool
260 type ('a, 'b) Base.Map.S_poly.tree
260 type 'elt Base.Set.S_poly.tree
Expand Down Expand Up @@ -80,10 +80,6 @@
361 val Base.Set.S_poly.invariants : 'a t -> bool
362 val Base.Set.S_poly.choose : 'a t -> 'a option
362 val Base.Set.S_poly.elements : 'a t -> 'a list
362 val Base.Hashtbl.S_poly.merge_into : src:('k, 'a) t ->
dst:('k, 'b) t ->
f:(key:'k key -> 'a -> 'b option -> 'b Merge_into_action.t) ->
unit
363 val Base.Map.S_poly.data : (_, 'v) t -> 'v list
363 val Base.Map.S_poly.keys : ('k, _) t -> 'k list
363 val Base.Set.S_poly.diff : 'a t -> 'a t -> 'a t
Expand All @@ -102,6 +98,7 @@
365 val Base.Map.S_poly.mem : ('k, _) t -> 'k -> bool
366 val Base.Set.S_poly.nth : 'a t -> int -> 'a option
366 val Base.Set.S_poly.union_list : 'a t list -> 'a t
366 val Base.Hashtbl.S_poly.capacity : (_, _) t -> int
367 val Base.Map.S_poly.invariants : ('k, 'v) t -> bool
367 val Base.Hashtbl.S_poly.is_empty : (_, _) t -> bool
367 val Base.Hashtbl.S_poly.find_and_call1 : ('a, 'b) t ->
Expand Down Expand Up @@ -132,13 +129,19 @@
363 val Base.Set.Using_comparator.Tree.group_by
373 val Base.Hashtbl.group
427 val Base.Set.S_poly.group_by
447 val Base.Dictionary_mutable.S1.group
454 val Base.Dictionary_mutable.Creators1.group
462 val Base.Set.Accessors_generic.group_by
473 val Base.Hashtbl.Poly.group
475 val Base.Set.Creators_and_accessors_generic.group_by
480 val Base.Hashtbl.Creators.group
485 val Base.Dictionary_mutable.S2.group
487 val Base.Hashtbl.Creators.group
492 val Base.Dictionary_mutable.Creators2.group
499 val Base.Hashtbl.S_without_submodules.group
575 val Base.Hashtbl.S_poly.group
507 val Base.Dictionary_mutable.S3.group
510 val Base.Dictionary_mutable.S.group
514 val Base.Dictionary_mutable.Creators3.group
$ sherlodoc search --no-rhs "group by"
val Base.Set.group_by
val Base.Set.Poly.group_by
Expand Down Expand Up @@ -195,7 +198,8 @@
143 type 'a Base.Export.list = 'a List.t
151 type 'a Base.List.t = 'a list
154 mod Base.List
154 mod Caml.List
156 val Base.Info.of_list : t list -> t
157 val Base.Error.of_list : t list -> t
158 val Base.List.rev : 'a t -> 'a t
159 val Base.List.hd_exn : 'a t -> 'a
159 val Base.List.return : 'a -> 'a t
Expand All @@ -204,6 +208,7 @@
161 val Base.List.tl_exn : 'a t -> 'a t
161 val Base.Queue.of_list : 'a list -> 'a t
161 val Base.Stack.of_list : 'a list -> 'a t
162 val Base.List.singleton : 'a -> 'a t
163 val Base.List.concat : 'a t t -> 'a t
163 mod Shadow_stdlib.List
164 val Base.List.last : 'a t -> 'a option
Expand All @@ -214,14 +219,13 @@
165 val Base.List.ignore_m : 'a t -> unit t
165 val Base.Bytes.of_char_list : char list -> t
166 val Base.List.drop : 'a t -> int -> 'a t
166 val Base.List.take : 'a t -> int -> 'a t
167 val Base.List.nth_exn : 'a t -> int -> 'a
$ sherlodoc search --print-cost ": list"
168 val Base.List.rev : 'a t -> 'a t
169 val Base.List.return : 'a -> 'a t
170 val Base.Bytes.to_list : t -> char list
171 val Base.List.join : 'a t t -> 'a t
171 val Base.List.tl_exn : 'a t -> 'a t
172 val Base.List.singleton : 'a -> 'a t
172 val Base.String.split_lines : t -> t list
173 val Base.List.concat : 'a t t -> 'a t
175 val Base.List.ignore_m : 'a t -> unit t
Expand All @@ -241,7 +245,6 @@
204 val Base.List.append : 'a t -> 'a t -> 'a t
204 val Base.Hashtbl.keys : ('a, _) t -> 'a key list
208 val Base.List.rev_append : 'a t -> 'a t -> 'a t
211 val Base.List.intersperse : 'a t -> sep:'a -> 'a t
Partial name search:
$ sherlodoc search --print-cost "strin"
Expand All @@ -252,7 +255,6 @@ Partial name search:
167 type Base.String.elt = char
169 val Base.String.rev : t -> t
171 mod Base.String
171 mod Caml.String
172 val Base.String.hash : t -> int
172 val Base.Exn.to_string : t -> string
172 val Base.Sys.max_string_length : int
Expand All @@ -264,12 +266,13 @@ Partial name search:
175 val Base.String.uppercase : t -> t
176 type Base.String.Caseless.t = t
176 val Base.String.capitalize : t -> t
177 mod Caml.StringLabels
177 type Base.String.Utf8.t = string
177 val Base.String.append : t -> t -> t
177 val Base.Exn.to_string_mach : t -> string
177 val Base.Info.to_string_hum : t -> string
177 val Base.Sign.to_string_hum : t -> string
178 val Base.Info.to_string_mach : t -> string
179 val Base.String.equal : t -> t -> bool
179 val Base.String.prefix : t -> int -> t
$ sherlodoc search --print-cost "base strin"
162 type Base.string = String.t
174 type Base.Export.string = String.t
Expand All @@ -289,21 +292,20 @@ Partial name search:
190 val Base.String.uppercase : t -> t
191 type Base.String.Caseless.t = t
191 val Base.String.capitalize : t -> t
192 type Base.String.Utf8.t = string
192 val Base.String.append : t -> t -> t
192 val Base.Exn.to_string_mach : t -> string
192 val Base.Info.to_string_hum : t -> string
192 val Base.Sign.to_string_hum : t -> string
193 val Base.Error.to_string_hum : t -> string
193 val Base.Info.to_string_mach : t -> string
194 val Base.Error.to_string_mach : t -> string
194 val Base.String.equal : t -> t -> bool
$ sherlodoc search --print-cost "tring"
177 type Base.string = String.t
182 type Base.String.t = string
182 type Base.String.elt = char
184 val Base.String.rev : t -> t
186 mod Base.String
186 mod Caml.String
186 val Base.Sexp.of_string : unit
187 val Base.String.hash : t -> int
188 val Base.String.escaped : t -> t
Expand All @@ -314,15 +316,16 @@ Partial name search:
191 type Base.String.Caseless.t = t
191 val Base.String.capitalize : t -> t
192 val Base.Exn.to_string : t -> string
192 type Base.String.Utf8.t = string
192 val Base.String.append : t -> t -> t
194 val Base.String.equal : t -> t -> bool
194 val Base.String.prefix : t -> int -> t
194 val Base.String.suffix : t -> int -> t
194 val Base.Float.to_string : t -> string
195 val Base.String.compare : t -> t -> int
195 mod Shadow_stdlib.String
197 val Base.String.ascending : t -> t -> int
197 val Base.String.split_lines : t -> t list
195 type Base.String.Utf16be.t = string
195 type Base.String.Utf32le.t = string
$ sherlodoc search --print-cost "base tring"
192 type Base.string = String.t
197 type Base.String.t = string
Expand All @@ -339,14 +342,14 @@ Partial name search:
206 type Base.String.Caseless.t = t
206 val Base.String.capitalize : t -> t
207 val Base.Exn.to_string : t -> string
207 type Base.String.Utf8.t = string
207 val Base.String.append : t -> t -> t
209 val Base.String.equal : t -> t -> bool
209 val Base.String.prefix : t -> int -> t
209 val Base.String.suffix : t -> int -> t
209 val Base.Float.to_string : t -> string
210 val Base.String.compare : t -> t -> int
212 val Base.String.ascending : t -> t -> int
212 val Base.String.split_lines : t -> t list
212 val Base.Sys.max_string_length : int
214 val Base.String.common_suffix : t list -> t
210 type Base.String.Utf16be.t = string
210 type Base.String.Utf16le.t = string
210 type Base.String.Utf32le.t = string
Loading

0 comments on commit 1c9d32e

Please sign in to comment.