From 4fec2b2366f3147cce972d2c91c43daf75fd95fb Mon Sep 17 00:00:00 2001 From: Paul-Elliot Date: Fri, 15 Nov 2024 14:57:37 +0100 Subject: [PATCH] Children order: review comments --- src/model/semantics.ml | 25 ++++++++++++++----------- src/parser/test/test.ml | 4 +++- 2 files changed, 17 insertions(+), 12 deletions(-) diff --git a/src/model/semantics.ml b/src/model/semantics.ml index 96f96e3365..3ebedd3034 100644 --- a/src/model/semantics.ml +++ b/src/model/semantics.ml @@ -36,35 +36,38 @@ 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 f = function +let rec find_tags acc ~filter = function | [] -> List.rev acc | hd :: tl -> ( - match f hd.Location.value with - | Some x -> find_tags ((x, hd.location) :: acc) f 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 f tl) + 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 @@ -73,7 +76,7 @@ let handle_internal_tags (type a) tags : a handle_internal_tags -> a = function | Expect_page_tags -> let unparsed_lines = find_tags [] - (function `Children_order _ as p -> Some p | _ -> None) + ~filter:(function `Children_order _ as p -> Some p | _ -> None) tags in let lines = @@ -90,7 +93,7 @@ let handle_internal_tags (type a) tags : a handle_internal_tags -> a = function 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 *) diff --git a/src/parser/test/test.ml b/src/parser/test/test.ml index ef438ee366..5f24c13240 100644 --- a/src/parser/test/test.ml +++ b/src/parser/test/test.ml @@ -144,7 +144,9 @@ module Ast_to_sexp = struct | `Return es -> List (Atom "@return" :: List.map (at.at (nestable_block_element at)) es) | `Children_order es -> - List (Atom "@return" :: List.map (at.at (nestable_block_element at)) es) + List + (Atom "@children_order" + :: List.map (at.at (nestable_block_element at)) es) | `See (kind, s, es) -> let kind = match kind with