@@ -36,35 +36,38 @@ let warn_root_canonical location =
3636 Error. raise_warning
3737 @@ Error. make " Canonical paths must contain a dot, eg. X.Y." location
3838
39- let rec find_tag f = function
39+ let rec find_tag ~ filter = function
4040 | [] -> None
4141 | hd :: tl -> (
42- match f hd.Location. value with
42+ match filter hd.Location. value with
4343 | Some x -> Some (x, hd.location)
4444 | None ->
4545 warn_unexpected_tag hd;
46- find_tag f tl)
46+ find_tag ~filter tl)
4747
48- let rec find_tags acc f = function
48+ let rec find_tags acc ~ filter = function
4949 | [] -> List. rev acc
5050 | hd :: tl -> (
51- match f hd.Location. value with
52- | Some x -> find_tags ((x, hd.location) :: acc) f tl
51+ match filter hd.Location. value with
52+ | Some x -> find_tags ((x, hd.location) :: acc) ~filter tl
5353 | None ->
5454 warn_unexpected_tag hd;
55- find_tags acc f tl)
55+ find_tags acc ~filter tl)
5656
5757let handle_internal_tags (type a ) tags : a handle_internal_tags -> a = function
5858 | Expect_status -> (
5959 match
6060 find_tag
61- (function (`Inline | `Open | `Closed ) as t -> Some t | _ -> None )
61+ ~filter: (function
62+ | (`Inline | `Open | `Closed ) as t -> Some t | _ -> None )
6263 tags
6364 with
6465 | Some (status , _ ) -> status
6566 | None -> `Default )
6667 | Expect_canonical -> (
67- match find_tag (function `Canonical p -> Some p | _ -> None ) tags with
68+ match
69+ find_tag ~filter: (function `Canonical p -> Some p | _ -> None ) tags
70+ with
6871 | Some (`Root _ , location ) ->
6972 warn_root_canonical location;
7073 None
@@ -73,7 +76,7 @@ let handle_internal_tags (type a) tags : a handle_internal_tags -> a = function
7376 | Expect_page_tags ->
7477 let unparsed_lines =
7578 find_tags []
76- (function `Children_order _ as p -> Some p | _ -> None )
79+ ~filter: (function `Children_order _ as p -> Some p | _ -> None )
7780 tags
7881 in
7982 let lines =
@@ -90,7 +93,7 @@ let handle_internal_tags (type a) tags : a handle_internal_tags -> a = function
9093 Frontmatter. of_lines lines |> Error. raise_warnings
9194 | Expect_none ->
9295 (* Will raise warnings. *)
93- ignore (find_tag (fun _ -> None ) tags);
96+ ignore (find_tag ~filter: (fun _ -> None ) tags);
9497 ()
9598
9699(* Errors *)
0 commit comments