Skip to content

Commit

Permalink
Fmt and update tests after rebase
Browse files Browse the repository at this point in the history
  • Loading branch information
Julow committed Jun 18, 2019
1 parent 0e73d82 commit 004f25f
Show file tree
Hide file tree
Showing 10 changed files with 296 additions and 43 deletions.
6 changes: 3 additions & 3 deletions src/Fmt_ast.ml
Original file line number Diff line number Diff line change
Expand Up @@ -419,7 +419,7 @@ let parse_docstring c ~loc text =
let msg = Odoc_model.Error.to_string w in
Caml.Format.eprintf
"%a:@,Warning: Invalid documentation comment:@,%s\n%!"
Location.print_loc loc msg ) ;
Location.print_loc loc msg) ;
Error ()

let fmt_parsed_docstring c ~loc ?pro ~epi str_cmt parsed =
Expand Down Expand Up @@ -464,7 +464,7 @@ let fmt_docstring_around_item' ?(force_before = false) ?(fit = false) c doc1
| None, None -> (noop, noop)
| None, Some doc | Some doc, None -> (
let is_tag_only =
List.for_all ~f:(function Ok ([], _), _ -> true | _ -> false)
List.for_all ~f:(function Ok [], _ -> true | _ -> false)
in
let fmt_doc ?epi ?pro doc =
list_pn doc (fun ?prev:_ (parsed, ({txt; loc}, floating)) ?next ->
Expand All @@ -474,7 +474,7 @@ let fmt_docstring_around_item' ?(force_before = false) ?(fit = false) c doc1
in
let floating_doc, doc =
doc
|> List.map ~f:(fun (({txt;loc}, _) as doc) ->
|> List.map ~f:(fun (({txt; loc}, _) as doc) ->
(parse_docstring c ~loc txt, doc))
|> List.partition_tf ~f:(fun (_, (_, floating)) -> floating)
in
Expand Down
6 changes: 2 additions & 4 deletions src/Fmt_odoc.ml
Original file line number Diff line number Diff line change
Expand Up @@ -105,7 +105,7 @@ let list_block_elem elems f =
| Some _ -> fmt "@\n"
| None -> fmt ""
in
f elem $ break )
f elem $ break)

(* Format each element with [fmt_elem] *)
let fmt_styled style fmt_elem elems =
Expand Down Expand Up @@ -136,9 +136,7 @@ let rec fmt_inline_element : inline_element -> Fmt.t = function
hovbox 0 (wrap "[" "]" (str_verbatim s))
| `Raw_markup (lang, s) ->
let lang =
match lang with
| Some l -> str l $ str ":"
| None -> noop
match lang with Some l -> str l $ str ":" | None -> noop
in
wrap "{%%" "%%}" (lang $ str_verbatim s)
| `Styled (style, elems) ->
Expand Down
23 changes: 23 additions & 0 deletions test/passing/doc_comments.after.ml.ref
Original file line number Diff line number Diff line change
Expand Up @@ -221,3 +221,26 @@ end
(** A *)
exception A of int
(** C *)

(** {1:lbl Heading} *)

(** {2 heading without label} *)

module A = struct
module B = struct
(** It does not try to saturate (2) A = B + C /\ B = D + E => A = C + D
\+ E Nor combine more than 2 equations (3) A = B + C /\ B = D + E /\
F = C + D + E => A = F

xxxxxxxxxxxxxxxxxxxxxxxxxxx (2) A = B + C /\ B = D + E => A = C + D
\- E *)
let a b = ()
end
end

(* Same with get_pure, except that when we have both "x = t" and "y = t"
where t is a primed ident, * we add "x = y" to the result. This is
crucial for the normalizer, as it tend to drop "x = t" before *
processing "y = t". If we don't explicitly preserve "x = y", the
normalizer cannot pick it up *)
let _ = ()
23 changes: 23 additions & 0 deletions test/passing/doc_comments.before.ml.ref
Original file line number Diff line number Diff line change
Expand Up @@ -221,3 +221,26 @@ end
(** A *)
exception A of int
(** C *)

(** {1:lbl Heading} *)

(** {2 heading without label} *)

module A = struct
module B = struct
(** It does not try to saturate (2) A = B + C /\ B = D + E => A = C + D
\+ E Nor combine more than 2 equations (3) A = B + C /\ B = D + E /\
F = C + D + E => A = F

xxxxxxxxxxxxxxxxxxxxxxxxxxx (2) A = B + C /\ B = D + E => A = C + D
\- E *)
let a b = ()
end
end

(* Same with get_pure, except that when we have both "x = t" and "y = t"
where t is a primed ident, * we add "x = y" to the result. This is
crucial for the normalizer, as it tend to drop "x = t" before *
processing "y = t". If we don't explicitly preserve "x = y", the
normalizer cannot pick it up *)
let _ = ()
199 changes: 195 additions & 4 deletions test/passing/doc_comments.ml.ref
Original file line number Diff line number Diff line change
@@ -1,20 +1,20 @@
(** test *)
module A = B
(** test *)

(** @open *)
include A

(** @open *)

include B
(** @open *)

include A

type t = C of int (** docstring comment *)

type t = C of int [@ocaml.doc " docstring attribute "]

(** comment *)
include Mod
(** comment *)

(** before *)
let x = 2
Expand All @@ -31,6 +31,197 @@ and y = 2
let a = 0
(** A' *)

module Comment_placement : sig
type t
(** Type *)

(** Variant declaration *)
type t = T

(** Type extension *)
type t += T

module A : B
(** Module *)

(** Module *)
module A : sig
type a

type b
end

val a : b
(** Val *)

exception E
(** Exception *)

include M
(** Include *)

(** Include *)
include sig
type a

type b
end

open M
(** Open *)

external a : b = "c"
(** External *)

module rec A : B
(** Rec module *)

(** Rec module *)
module rec A : sig
type a

type b
end

module type A
(** Module type *)

(** Module type *)
module type A = sig
type a

type b
end

class a : b
(** Class *)

class type a = b
(** Class type *)

(* [@@@some attribute] *)
(* (** Attribute *) *)

[%%some extension] (** Extension *)

(** A *)
external a : b = "double_comment"
(** B *)
end = struct
type t = {a: int}
(** Type *)

(** Variant declaration *)
type t = T

(** Type extension *)
type t += T

module A = B
(** Module *)

(** Module *)
module A = struct
type a = A

type b = B
end

(** Module *)
module A : sig
type a

type b
end =
B

(** Let *)
let a = b

exception E
(** Exception *)

include M
(** Include *)

(** Include *)
include struct
type a = A

type b = B
end

open M
(** Open *)

external a : b = "c"
(** External *)

module rec A : B = C
(** Rec module *)

(** Rec module *)
module rec A : B = struct
type a = A

type b = B
end

module type A = B
(** Module type *)

(** Module type *)
module type A = sig
type a

type b
end

class a = b
(** Class *)

(** Class *)
class b =
object
method f = 0
(** Method *)

inherit a
(** Inherit *)

val x = 1
(** Val *)

constraint 'a = [> ]
(** Constraint *)

initializer do_init ()
(** Initialiser *)
end

class type a = b
(** Class type *)

(* [@@@some attribute] *)
(* (** Attribute *) *)

(** Extension *)[%%some
extension]

(* ;; *)
(* (** Eval *) *)
(* 1 + 1 *)
(* ;; *)

(** A *)
external a : b = "double_comment"
(** B *)
end

(** A *)
exception A of int
(** C *)

(** {1:lbl Heading} *)

(** {2 heading without label} *)
Expand Down
8 changes: 2 additions & 6 deletions test/passing/doc_comments.mli.ref
Original file line number Diff line number Diff line change
Expand Up @@ -233,13 +233,9 @@ end

(** @canonical Module.Foo.Bar *)

(** {v
a
v} *)
(** {v a v} *)

(** {[
b
]} *)
(** {[ b ]} *)

(** - Odoc don't parse

Expand Down
3 changes: 2 additions & 1 deletion test/passing/js_source.ml.ref
Original file line number Diff line number Diff line change
Expand Up @@ -9749,7 +9749,8 @@ if fffffffffffffff aaaaa bb
then (if b then aaaaaaaaaaaaaaaa ffff)
else aaaaaaaaaaaa qqqqqqqqqqq

include Base.Fn (** @open *)
(** @open *)
include Base.Fn

let ssmap
: (module MapT with type key = string and type data = string and type map = SSMap.map)
Expand Down
Loading

0 comments on commit 004f25f

Please sign in to comment.