Skip to content

Commit

Permalink
Switch to external odoc-parser library
Browse files Browse the repository at this point in the history
  • Loading branch information
jonludlam committed Jul 5, 2021
1 parent 7f2a50e commit 995acaa
Show file tree
Hide file tree
Showing 30 changed files with 57 additions and 7,294 deletions.
2 changes: 1 addition & 1 deletion .github/workflows/build.yml
Expand Up @@ -38,7 +38,7 @@ jobs:
odoc.opam
- name: Install dependencies
run: opam install -y --deps-only -t ./odoc.opam ./odoc-parser.opam
run: opam install -y --deps-only -t ./odoc.opam

- name: dune runtest
run: opam exec -- dune runtest
Expand Down
39 changes: 0 additions & 39 deletions odoc-parser.opam

This file was deleted.

2 changes: 1 addition & 1 deletion odoc.opam
Expand Up @@ -23,7 +23,7 @@ delimited with `(** ... *)`, and outputs HTML.
"""

depends: [
"odoc-parser"
"odoc-parser" {>= "0.9.0"}
"astring"
"cmdliner"
"cppo" {build}
Expand Down
1 change: 1 addition & 0 deletions package.json
Expand Up @@ -46,6 +46,7 @@
"@opam/sexplib0": "*",
"@opam/tyxml": "4.3.0",
"@opam/ocamlfind-secondary":"1.8.1",
"@opam/odoc-parser":"0.9.0",
"ocaml": "~4.2.0"
},
"resolutions": {
Expand Down
3 changes: 2 additions & 1 deletion src/document/comment.ml
Expand Up @@ -195,7 +195,8 @@ let rec nestable_block_element : Comment.nestable_block_element -> Block.one =
fun content ->
match content with
| `Paragraph p -> paragraph p
| `Code_block (_, code) -> block @@ Source (source_of_code code)
| `Code_block (_, code) ->
block @@ Source (source_of_code (Odoc_model.Location_.value code))
| `Verbatim s -> block @@ Verbatim s
| `Modules ms -> module_references ms
| `List (kind, items) ->
Expand Down
2 changes: 1 addition & 1 deletion src/model/comment.ml
Expand Up @@ -40,7 +40,7 @@ type module_reference = {

type nestable_block_element =
[ `Paragraph of paragraph
| `Code_block of string option * string
| `Code_block of string with_location option * string with_location
| `Verbatim of string
| `Modules of module_reference list
| `List of
Expand Down
5 changes: 3 additions & 2 deletions src/model/error.ml
Expand Up @@ -128,9 +128,10 @@ let unpack_warnings ww = (ww.value, List.map (fun w -> w.w) ww.warnings)
let t_of_parser_t : Odoc_parser.Warning.t -> t =
fun x -> (`With_full_location x :> t)

let raise_parser_warnings { Odoc_parser.ast; warnings } =
let raise_parser_warnings v =
(* Parsing errors may be fatal. *)
let warnings = Odoc_parser.warnings v in
let non_fatal = false in
raise_warnings'
(List.map (fun p -> { w = t_of_parser_t p; non_fatal }) warnings);
ast
Odoc_parser.ast v
8 changes: 6 additions & 2 deletions src/model_desc/comment_desc.ml
Expand Up @@ -18,7 +18,7 @@ and general_link_content = general_inline_element with_location list

type general_block_element =
[ `Paragraph of general_link_content
| `Code_block of string option * string
| `Code_block of string with_location option * string with_location
| `Verbatim of string
| `Modules of Comment.module_reference list
| `List of
Expand Down Expand Up @@ -89,7 +89,11 @@ let rec block_element : general_block_element t =
(function
| `Paragraph x -> C ("`Paragraph", x, link_content)
| `Code_block (x, y) ->
C ("`Code_block", (x, y), Pair (Option string, string))
C
( "`Code_block",
( (match x with None -> None | Some x -> Some (ignore_loc x)),
ignore_loc y ),
Pair (Option string, string) )
| `Verbatim x -> C ("`Verbatim", x, string)
| `Modules x -> C ("`Modules", x, List module_reference)
| `List (x1, x2) ->
Expand Down
13 changes: 11 additions & 2 deletions src/odoc/dune
@@ -1,8 +1,17 @@
(library
(name odoc_odoc)
(public_name odoc.odoc)
(libraries compiler-libs.common fpath odoc_html odoc_manpage odoc_latex
odoc_loader odoc_model odoc_xref2 tyxml unix)
(libraries
compiler-libs.common
fpath
odoc_html
odoc_manpage
odoc_latex
odoc_loader
odoc_model
odoc_xref2
tyxml
unix)
(instrumentation
(backend bisect_ppx)))

Expand Down
74 changes: 0 additions & 74 deletions src/parser/ast.ml

This file was deleted.

8 changes: 0 additions & 8 deletions src/parser/dune

This file was deleted.

10 changes: 0 additions & 10 deletions src/parser/lexer.mli

This file was deleted.

0 comments on commit 995acaa

Please sign in to comment.