diff --git a/CHANGES.md b/CHANGES.md index b8898e2897..d6835ed351 100644 --- a/CHANGES.md +++ b/CHANGES.md @@ -27,7 +27,8 @@ - Added a `compile-asset` command (@EmileTrotignon, @panglesd, #1170) - Allow referencing assets (@panglesd, #1171) - Added a `--asset-path` arg to `html-generate` (@panglesd, #1185) -- Add a frontmatter syntax for mld pages (@panglesd, #1187) +- Add a `@children_order` tag to specify the order in the sidebar (@panglesd, + #1187, #1243) - Add a 'remap' option to HTML generation for partial docsets (@jonludlam, #1189) - Added an `html-generate-asset` command (@panglesd, #1185) - Added syntax for images, videos, audio (@panglesd, #1184) diff --git a/src/loader/doc_attr.ml b/src/loader/doc_attr.ml index 287318f0c1..bf5856597a 100644 --- a/src/loader/doc_attr.ml +++ b/src/loader/doc_attr.ml @@ -161,11 +161,8 @@ let read_string_comment internal_tags parent loc str = read_string ~tags_allowed:true internal_tags parent (pad_loc loc) str let page parent loc str = - let doc, () = - read_string ~tags_allowed:false Odoc_model.Semantics.Expect_none parent loc.Location.loc_start + read_string ~tags_allowed:false Odoc_model.Semantics.Expect_page_tags parent loc.Location.loc_start str - in - `Docs doc let standalone parent (attr : Parsetree.attribute) : Odoc_model.Comment.docs_or_stop option = diff --git a/src/loader/doc_attr.mli b/src/loader/doc_attr.mli index 792015a8ad..d4a9117689 100644 --- a/src/loader/doc_attr.mli +++ b/src/loader/doc_attr.mli @@ -37,7 +37,7 @@ val page : Paths.Identifier.LabelParent.t -> Location.t -> string -> - Odoc_model.Comment.docs_or_stop + Odoc_model.Comment.docs * Frontmatter.t (** The parent identifier is used to define labels in the given string (i.e. for things like [{1:some_section Some title}]) and the location is used for error messages. diff --git a/src/loader/odoc_loader.mli b/src/loader/odoc_loader.mli index aabd3f72c9..68baddc13f 100644 --- a/src/loader/odoc_loader.mli +++ b/src/loader/odoc_loader.mli @@ -11,7 +11,7 @@ val read_string : Paths.Identifier.LabelParent.t -> string -> string -> - (Comment.docs_or_stop, Error.t) result Error.with_warnings + (Comment.docs * Frontmatter.t, Error.t) result Error.with_warnings val read_cmti : make_root:make_root -> diff --git a/src/markdown/odoc_md.ml b/src/markdown/odoc_md.ml index d8c37bac9a..1cbe820aba 100644 --- a/src/markdown/odoc_md.ml +++ b/src/markdown/odoc_md.ml @@ -24,7 +24,7 @@ let parse id input_s = let mk_page input_s id content = (* Construct the output file representation *) let zero_heading = Comment.find_zero_heading content in - let frontmatter, content = Comment.extract_frontmatter content in + let frontmatter = Frontmatter.empty in let digest = Digest.file input_s in let root = let file = Root.Odoc_file.create_page input_s zero_heading frontmatter in diff --git a/src/model/comment.ml b/src/model/comment.ml index b1c808a85e..929ba1bfe3 100644 --- a/src/model/comment.ml +++ b/src/model/comment.ml @@ -145,15 +145,3 @@ let find_zero_heading docs : link_content option = Some (link_content_of_inline_elements h_content) | _ -> None) docs - -let extract_frontmatter docs : _ = - let fm, rev_content = - List.fold_left - (fun (fm_acc, content_acc) doc -> - match doc.Location_.value with - | `Code_block (Some "meta", content, None) -> - (Frontmatter.parse content, content_acc) - | _ -> (fm_acc, doc :: content_acc)) - (Frontmatter.empty, []) docs - in - (fm, List.rev rev_content) diff --git a/src/model/frontmatter.ml b/src/model/frontmatter.ml index 700fce09a4..79542be3e9 100644 --- a/src/model/frontmatter.ml +++ b/src/model/frontmatter.ml @@ -1,9 +1,6 @@ type child = Page of string | Dir of string -type line = - | Children_order of child Location_.with_location list - | KV of string * string - | V of string +type line = Children_order of child Location_.with_location list type children_order = child Location_.with_location list Location_.with_location @@ -16,8 +13,9 @@ let apply fm line = | Children_order children_order, { children_order = None } -> { children_order = Some (Location_.same line children_order) } | Children_order _, { children_order = Some _ } -> - (* TODO raise warning about duplicate children field *) fm - | KV _, _ | V _, _ -> (* TODO raise warning *) fm + Error.raise_warning + (Error.make "Duplicated @children_order entry" line.location); + fm let parse_child c = if Astring.String.is_suffix ~affix:"/" c then @@ -25,24 +23,23 @@ let parse_child c = Dir c else Page c -let parse s = - let entries = - s.Location_.value - |> Astring.String.cuts ~sep:"\n" - |> List.map (fun l -> - let v = - Astring.String.cut ~sep:":" l |> function - | Some ("children", v) -> - let refs = - v - |> Astring.String.fields ~empty:false - |> List.map parse_child - |> List.map (Location_.same s) - in - Children_order refs - | Some (k, v) -> KV (k, v) - | None -> V l - in - Location_.same s v) +let parse_children_order loc co = + let rec parse_words acc words = + match words with + | [] -> Result.Ok (Location_.at loc (Children_order (List.rev acc))) + | ({ Location_.value = `Word word; _ } as w) :: tl -> + parse_words ({ w with value = parse_child word } :: acc) tl + | { Location_.value = `Space _; _ } :: tl -> parse_words acc tl + | { location; _ } :: _ -> + Error + (Error.make "Only words are accepted when specifying children order" + location) in - List.fold_left apply empty entries + match co with + | [ { Location_.value = `Paragraph words; _ } ] -> parse_words [] words + | _ -> + Error + (Error.make "Only words are accepted when specifying children order" loc) + +let of_lines lines = + Error.catch_warnings @@ fun () -> List.fold_left apply empty lines diff --git a/src/model/frontmatter.mli b/src/model/frontmatter.mli index a8c3cbc657..61f2e5d704 100644 --- a/src/model/frontmatter.mli +++ b/src/model/frontmatter.mli @@ -1,9 +1,16 @@ type child = Page of string | Dir of string +type line + type children_order = child Location_.with_location list Location_.with_location type t = { children_order : children_order option } val empty : t -val parse : string Location_.with_location -> t +val parse_children_order : + Location_.span -> + Odoc_parser.Ast.nestable_block_element Location_.with_location list -> + (line Location_.with_location, Error.t) Result.result + +val of_lines : line Location_.with_location list -> t Error.with_warnings diff --git a/src/model/semantics.ml b/src/model/semantics.ml index 5f079b7352..3ebedd3034 100644 --- a/src/model/semantics.ml +++ b/src/model/semantics.ml @@ -1,3 +1,5 @@ +open Odoc_utils + module Location = Location_ module Ast = Odoc_parser.Ast @@ -14,6 +16,7 @@ type _ handle_internal_tags = : [ `Default | `Inline | `Open | `Closed ] handle_internal_tags | Expect_canonical : Reference.path option handle_internal_tags | Expect_none : unit handle_internal_tags + | Expect_page_tags : Frontmatter.t handle_internal_tags let describe_internal_tag = function | `Canonical _ -> "@canonical" @@ -21,6 +24,7 @@ let describe_internal_tag = function | `Open -> "@open" | `Closed -> "@closed" | `Hidden -> "@hidden" + | `Children_order _ -> "@children_order" let warn_unexpected_tag { Location.value; location } = Error.raise_warning @@ -32,34 +36,64 @@ let warn_root_canonical location = Error.raise_warning @@ Error.make "Canonical paths must contain a dot, eg. X.Y." location -let rec find_tag f = function +let rec find_tag ~filter = function | [] -> None | hd :: tl -> ( - match f hd.Location.value with + match filter hd.Location.value with | Some x -> Some (x, hd.location) | None -> warn_unexpected_tag hd; - find_tag f tl) + find_tag ~filter tl) + +let rec find_tags acc ~filter = function + | [] -> List.rev acc + | hd :: tl -> ( + match filter hd.Location.value with + | Some x -> find_tags ((x, hd.location) :: acc) ~filter tl + | None -> + warn_unexpected_tag hd; + find_tags acc ~filter tl) let handle_internal_tags (type a) tags : a handle_internal_tags -> a = function | Expect_status -> ( match find_tag - (function (`Inline | `Open | `Closed) as t -> Some t | _ -> None) + ~filter:(function + | (`Inline | `Open | `Closed) as t -> Some t | _ -> None) tags with | Some (status, _) -> status | None -> `Default) | Expect_canonical -> ( - match find_tag (function `Canonical p -> Some p | _ -> None) tags with + match + find_tag ~filter:(function `Canonical p -> Some p | _ -> None) tags + with | Some (`Root _, location) -> warn_root_canonical location; None | Some ((`Dot _ as p), _) -> Some p | None -> None) + | Expect_page_tags -> + let unparsed_lines = + find_tags [] + ~filter:(function `Children_order _ as p -> Some p | _ -> None) + tags + in + let lines = + List.filter_map + (function + | `Children_order co, loc -> ( + match Frontmatter.parse_children_order loc co with + | Ok co -> Some co + | Error e -> + Error.raise_warning e; + None)) + unparsed_lines + in + Frontmatter.of_lines lines |> Error.raise_warnings | Expect_none -> (* Will raise warnings. *) - ignore (find_tag (fun _ -> None) tags); + ignore (find_tag ~filter:(fun _ -> None) tags); () (* Errors *) @@ -514,12 +548,20 @@ let top_level_block_elements status ast_elements = traverse ~top_heading_level [] ast_elements let strip_internal_tags ast : internal_tags_removed with_location list * _ = - let rec loop tags ast' = function + let rec loop ~start tags ast' = function | ({ Location.value = `Tag (#Ast.internal_tag as tag); _ } as wloc) :: tl -> ( - let next tag = loop ({ wloc with value = tag } :: tags) ast' tl in + let next tag = + loop ~start ({ wloc with value = tag } :: tags) ast' tl + in match tag with | (`Inline | `Open | `Closed | `Hidden) as tag -> next tag + | `Children_order co -> + if not start then + Error.raise_warning + (Error.make "@children_order tag has to be before any content" + wloc.location); + next (`Children_order co) | `Canonical { Location.value = s; location = r_location } -> ( match Error.raise_warnings (Reference.read_path_longident r_location s) @@ -527,7 +569,7 @@ let strip_internal_tags ast : internal_tags_removed with_location list * _ = | Result.Ok path -> next (`Canonical path) | Result.Error e -> Error.raise_warning e; - loop tags ast' tl)) + loop ~start tags ast' tl)) | ({ value = ( `Tag #Ast.ocamldoc_tag @@ -536,10 +578,10 @@ let strip_internal_tags ast : internal_tags_removed with_location list * _ = _; } as hd) :: tl -> - loop tags (hd :: ast') tl + loop ~start:false tags (hd :: ast') tl | [] -> (List.rev ast', List.rev tags) in - loop [] [] ast + loop ~start:true [] [] ast (** Append alerts at the end of the comment. Tags are favoured in case of alerts of the same name. *) let append_alerts_to_comment alerts @@ -559,7 +601,7 @@ let append_alerts_to_comment alerts comment @ (alerts : alerts :> Comment.docs) let ast_to_comment ~internal_tags ~sections_allowed ~tags_allowed - ~parent_of_sections ast alerts = + ~parent_of_sections (ast : Ast.t) alerts = Error.catch_warnings (fun () -> let status = { sections_allowed; tags_allowed; parent_of_sections } in let ast, tags = strip_internal_tags ast in diff --git a/src/model/semantics.mli b/src/model/semantics.mli index 0a7eeaf015..f9784c6d99 100644 --- a/src/model/semantics.mli +++ b/src/model/semantics.mli @@ -4,6 +4,7 @@ type _ handle_internal_tags = : [ `Default | `Inline | `Open | `Closed ] handle_internal_tags | Expect_canonical : Reference.path option handle_internal_tags | Expect_none : unit handle_internal_tags + | Expect_page_tags : Frontmatter.t handle_internal_tags type sections_allowed = [ `All | `No_titles | `None ] diff --git a/src/odoc/compile.ml b/src/odoc/compile.ml index 6a8e497d03..cf30247825 100644 --- a/src/odoc/compile.ml +++ b/src/odoc/compile.ml @@ -245,13 +245,11 @@ let mld ~parent_id ~parents_children ~output ~children ~warnings_options input = | None -> Ok (Paths.Identifier.Mk.page (parent_id, page_name))) >>= fun id -> Ok (id :> Paths.Identifier.Page.t)) >>= fun id -> - let resolve content = + let resolve content frontmatter = let zero_heading = Comment.find_zero_heading content in - let frontmatter, content = Comment.extract_frontmatter content in if (not (is_index_page id)) && has_children_order frontmatter then Error.raise_warning - (Error.filename_only - "Non-index page cannot specify (children _) in the frontmatter." + (Error.filename_only "Non-index page cannot specify @children_order." input_s); let root = let file = @@ -281,8 +279,7 @@ let mld ~parent_id ~parents_children ~output ~children ~warnings_options input = Odoc_loader.read_string (id :> Paths.Identifier.LabelParent.t) input_s str |> Error.raise_errors_and_warnings |> function - | `Stop -> resolve [] (* TODO: Error? *) - | `Docs content -> resolve content + | content, page_tags -> resolve content page_tags let handle_file_ext ext = match ext with diff --git a/src/odoc/html_fragment.ml b/src/odoc/html_fragment.ml index 415cf36807..454e45f440 100644 --- a/src/odoc/html_fragment.ml +++ b/src/odoc/html_fragment.ml @@ -9,12 +9,12 @@ let from_mld ~xref_base_uri ~resolver ~output ~warnings_options input = in let input_s = Fs.File.to_string input in let digest = Digest.file input_s in - let to_html content = + let to_html content frontmatter = (* This is a mess. *) - let frontmatter, content = Odoc_model.Comment.extract_frontmatter content in let root = let file = - Odoc_model.Root.Odoc_file.create_page page_name None frontmatter + Odoc_model.Root.Odoc_file.create_page page_name None + Odoc_model.Frontmatter.empty in { Odoc_model.Root.id; file; digest } in @@ -53,7 +53,6 @@ let from_mld ~xref_base_uri ~resolver ~output ~warnings_options input = Odoc_loader.read_string id input_s str |> Odoc_model.Error.handle_errors_and_warnings ~warnings_options >>= function - | `Docs content -> to_html content - | `Stop -> to_html []) + | content, frontmatter -> to_html content frontmatter) (* TODO: Error? *) diff --git a/src/parser/ast.ml b/src/parser/ast.ml index 8662f68e8a..c8533dca91 100644 --- a/src/parser/ast.ml +++ b/src/parser/ast.ml @@ -72,7 +72,12 @@ and nestable_block_element = and table = nestable_block_element abstract_table * [ `Light | `Heavy ] type internal_tag = - [ `Canonical of string with_location | `Inline | `Open | `Closed | `Hidden ] + [ `Canonical of string with_location + | `Inline + | `Open + | `Closed + | `Hidden + | `Children_order of nestable_block_element with_location list ] (** Internal tags are used to exercise fine control over the output of odoc. They are never rendered in the output *) diff --git a/src/parser/lexer.mll b/src/parser/lexer.mll index 864c32c25b..5a71b48836 100644 --- a/src/parser/lexer.mll +++ b/src/parser/lexer.mll @@ -540,6 +540,9 @@ and token input = parse | ("@return" | "@returns") { emit input (`Tag `Return) } + | ("@children_order") + { emit input (`Tag `Children_order) } + | "@see" horizontal_space* '<' ([^ '>']* as url) '>' { emit input (`Tag (`See (`Url, url))) } diff --git a/src/parser/syntax.ml b/src/parser/syntax.ml index c8a77a5700..5d4445543a 100644 --- a/src/parser/syntax.ml +++ b/src/parser/syntax.ml @@ -617,6 +617,7 @@ let tag_to_words = function | `See (`Url, s) -> [ `Word "@see"; `Space " "; `Word ("<" ^ s ^ ">") ] | `Since s -> [ `Word "@since"; `Space " "; `Word s ] | `Version s -> [ `Word "@version"; `Space " "; `Word s ] + | `Children_order -> [ `Word "@children_order" ] (* {3 Block element lists} *) @@ -817,7 +818,7 @@ let rec block_element_list : let tag = Loc.at location (`Tag tag) in consume_block_elements `After_text (tag :: acc) - | (`Deprecated | `Return) as tag -> + | (`Deprecated | `Return | `Children_order) as tag -> let content, _stream_head, where_in_line = block_element_list (In_implicitly_ended `Tag) ~parent_markup:token input @@ -826,6 +827,7 @@ let rec block_element_list : match tag with | `Deprecated -> `Deprecated content | `Return -> `Return content + | `Children_order -> `Children_order content in let location = location :: List.map Loc.location content |> Loc.span diff --git a/src/parser/test/test.ml b/src/parser/test/test.ml index af6be5d40a..5f24c13240 100644 --- a/src/parser/test/test.ml +++ b/src/parser/test/test.ml @@ -143,6 +143,10 @@ module Ast_to_sexp = struct @ List.map (at.at (nestable_block_element at)) es) | `Return es -> List (Atom "@return" :: List.map (at.at (nestable_block_element at)) es) + | `Children_order es -> + List + (Atom "@children_order" + :: List.map (at.at (nestable_block_element at)) es) | `See (kind, s, es) -> let kind = match kind with diff --git a/src/parser/token.ml b/src/parser/token.ml index 4db3b14eb5..6d298b8e4b 100644 --- a/src/parser/token.ml +++ b/src/parser/token.ml @@ -18,6 +18,7 @@ type tag = | `Before of string | `Version of string | `Canonical of string + | `Children_order | `Inline | `Open | `Closed @@ -130,6 +131,7 @@ let print : [< t ] -> string = function | `Tag (`Param _) -> "'@param'" | `Tag (`Raise _) -> "'@raise'" | `Tag `Return -> "'@return'" + | `Tag `Children_order -> "'@children_order'" | `Tag (`See _) -> "'@see'" | `Tag (`Since _) -> "'@since'" | `Tag (`Before _) -> "'@before'" @@ -234,6 +236,7 @@ let describe : [< t | `Comment ] -> string = function | `Tag `Open -> "'@open'" | `Tag `Closed -> "'@closed'" | `Tag `Hidden -> "'@hidden" + | `Tag `Children_order -> "'@children_order" | `Comment -> "top-level text" let describe_element = function diff --git a/test/frontmatter/dune b/test/frontmatter/dune new file mode 100644 index 0000000000..3d43ccd34c --- /dev/null +++ b/test/frontmatter/dune @@ -0,0 +1,7 @@ +(env + (_ + (binaries + (../odoc_print/odoc_print.exe as odoc_print)))) + +(cram + (deps %{bin:odoc} %{bin:odoc_print})) diff --git a/test/frontmatter/frontmatter.t/one_frontmatter.mld b/test/frontmatter/frontmatter.t/one_frontmatter.mld new file mode 100644 index 0000000000..fa90306d98 --- /dev/null +++ b/test/frontmatter/frontmatter.t/one_frontmatter.mld @@ -0,0 +1,3 @@ +@children_order page1 page2 + +{0 One frontmatter} diff --git a/test/pages/frontmatter.t/run.t b/test/frontmatter/frontmatter.t/run.t similarity index 78% rename from test/pages/frontmatter.t/run.t rename to test/frontmatter/frontmatter.t/run.t index 7286500afa..4bdb9baac7 100644 --- a/test/pages/frontmatter.t/run.t +++ b/test/frontmatter/frontmatter.t/run.t @@ -10,7 +10,7 @@ When there is one frontmatter, it is extracted from the content: $ odoc compile one_frontmatter.mld File "one_frontmatter.mld": - Warning: Non-index page cannot specify (children _) in the frontmatter. + Warning: Non-index page cannot specify @children_order. $ odoc_print page-one_frontmatter.odoc | jq '.frontmatter' { "children": { @@ -56,12 +56,25 @@ When there is one frontmatter, it is extracted from the content: } ] -When there is more than one frontmatter, they are all extracted from the content: +When there is more than one children order, we raise a warning and keep only the first entry: $ odoc compile two_frontmatters.mld + File "two_frontmatters.mld", line 2, characters 0-25: + Warning: Duplicated @children_order entry + File "two_frontmatters.mld": + Warning: Non-index page cannot specify @children_order. $ odoc_print page-two_frontmatters.odoc | jq '.frontmatter' { - "children": "None" + "children": { + "Some": [ + { + "Page": "bli1" + }, + { + "Page": "bli2" + } + ] + } } $ odoc_print page-two_frontmatters.odoc | jq '.content' [ diff --git a/test/frontmatter/frontmatter.t/two_frontmatters.mld b/test/frontmatter/frontmatter.t/two_frontmatters.mld new file mode 100644 index 0000000000..c273454083 --- /dev/null +++ b/test/frontmatter/frontmatter.t/two_frontmatters.mld @@ -0,0 +1,4 @@ +@children_order bli1 bli2 +@children_order bli3 bli4 + +{0 Two frontmatters} diff --git a/test/pages/frontmatter.t/zero_frontmatter.mld b/test/frontmatter/frontmatter.t/zero_frontmatter.mld similarity index 100% rename from test/pages/frontmatter.t/zero_frontmatter.mld rename to test/frontmatter/frontmatter.t/zero_frontmatter.mld diff --git a/test/pages/toc_order.t/content.mld b/test/frontmatter/toc_order.t/content.mld similarity index 100% rename from test/pages/toc_order.t/content.mld rename to test/frontmatter/toc_order.t/content.mld diff --git a/test/pages/toc_order.t/dir1/content_in_dir.mld b/test/frontmatter/toc_order.t/dir1/content_in_dir.mld similarity index 100% rename from test/pages/toc_order.t/dir1/content_in_dir.mld rename to test/frontmatter/toc_order.t/dir1/content_in_dir.mld diff --git a/test/pages/toc_order.t/dir1/dontent.mld b/test/frontmatter/toc_order.t/dir1/dontent.mld similarity index 100% rename from test/pages/toc_order.t/dir1/dontent.mld rename to test/frontmatter/toc_order.t/dir1/dontent.mld diff --git a/test/pages/toc_order.t/dir1/index.mld b/test/frontmatter/toc_order.t/dir1/index.mld similarity index 100% rename from test/pages/toc_order.t/dir1/index.mld rename to test/frontmatter/toc_order.t/dir1/index.mld diff --git a/test/frontmatter/toc_order.t/index.mld b/test/frontmatter/toc_order.t/index.mld new file mode 100644 index 0000000000..30817cc9f1 --- /dev/null +++ b/test/frontmatter/toc_order.t/index.mld @@ -0,0 +1,5 @@ +@children_order content dir1/ dir1/ typo + +{0 This is the main index} + +Hello diff --git a/test/pages/toc_order.t/omitted.mld b/test/frontmatter/toc_order.t/omitted.mld similarity index 100% rename from test/pages/toc_order.t/omitted.mld rename to test/frontmatter/toc_order.t/omitted.mld diff --git a/test/pages/toc_order.t/run.t b/test/frontmatter/toc_order.t/run.t similarity index 70% rename from test/pages/toc_order.t/run.t rename to test/frontmatter/toc_order.t/run.t index ad7f595bf1..87078ffbf7 100644 --- a/test/pages/toc_order.t/run.t +++ b/test/frontmatter/toc_order.t/run.t @@ -13,11 +13,11 @@ $ odoc link _odoc/pkg/dir1/page-dontent.odoc $ odoc compile-index -P test:_odoc/pkg - File "index.mld", line 5, character 7 to line 7, character 0: + File "index.mld", line 1, characters 30-35: Warning: Duplicate 'dir1/' in (children). - File "index.mld", line 5, character 7 to line 7, character 0: + File "index.mld", line 1, characters 36-40: Warning: 'typo' in (children) does not correspond to anything. - File "index.mld", line 5, character 7 to line 7, character 0: + File "index.mld", line 1, characters 0-40: Warning: (children) doesn't include 'omitted'. $ odoc html-generate --indent --index index.odoc-index -o _html _odoc/pkg/page-index.odocl @@ -70,3 +70,39 @@ but this should be a warning!
  • The name is dontent
  • This one is omitted
  • + + +Some more parsing test: + + $ mkdir errors + $ cat << EOF >> errors/index.mld + > @children_order [Some wrong content] + > {0 Test1} + > EOF + $ odoc compile --parent-id pkg/doc --output-dir _odoc errors/index.mld + File "errors/index.mld", line 1, characters 16-36: + Warning: Only words are accepted when specifying children order + + $ mkdir valid + $ cat << EOF > valid/index.mld + > @children_order a + > b c + > {0 Test1} + > EOF + $ odoc compile --parent-id pkg/doc --output-dir _odoc valid/index.mld + + $ cat << EOF > errors/index.mld + > {0 Test1} + > @children_order a + > EOF + $ odoc compile --parent-id pkg/doc --output-dir _odoc errors/index.mld + File "errors/index.mld", line 2, characters 0-17: + Warning: @children_order tag has to be before any content + + $ cat << EOF > errors/not_index.mld + > @children_order a + > {0 Test1} + > EOF + $ odoc compile --parent-id pkg/doc --output-dir _odoc errors/not_index.mld + File "errors/not_index.mld": + Warning: Non-index page cannot specify @children_order. diff --git a/test/pages/frontmatter.t/one_frontmatter.mld b/test/pages/frontmatter.t/one_frontmatter.mld deleted file mode 100644 index e7f571eb11..0000000000 --- a/test/pages/frontmatter.t/one_frontmatter.mld +++ /dev/null @@ -1,5 +0,0 @@ -{0 One frontmatter} - -{@meta[ -children: page1 page2 -]} \ No newline at end of file diff --git a/test/pages/frontmatter.t/two_frontmatters.mld b/test/pages/frontmatter.t/two_frontmatters.mld deleted file mode 100644 index 226878765a..0000000000 --- a/test/pages/frontmatter.t/two_frontmatters.mld +++ /dev/null @@ -1,10 +0,0 @@ -{0 Two frontmatters} - -{@meta[ -bli1: bloblobloblo1 -bli2: bloblobloblo2 -]} - -{@meta[ -bli3: bloblobloblo1 -]} \ No newline at end of file diff --git a/test/pages/toc_order.t/index.mld b/test/pages/toc_order.t/index.mld deleted file mode 100644 index fbae568947..0000000000 --- a/test/pages/toc_order.t/index.mld +++ /dev/null @@ -1,7 +0,0 @@ -{0 This is the main index} - -Hello - -{@meta[ -children: content dir1/ dir1/ typo -]} \ No newline at end of file