File tree Expand file tree Collapse file tree 2 files changed +8
-6
lines changed Expand file tree Collapse file tree 2 files changed +8
-6
lines changed Original file line number Diff line number Diff line change @@ -45,14 +45,14 @@ let rec find_tag f = function
4545 warn_unexpected_tag hd;
4646 find_tag f 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 -> (
@@ -73,7 +73,7 @@ let handle_internal_tags (type a) tags : a handle_internal_tags -> a = function
7373 | Expect_page_tags ->
7474 let unparsed_lines =
7575 find_tags []
76- (function `Children_order _ as p -> Some p | _ -> None )
76+ ~filter: (function `Children_order _ as p -> Some p | _ -> None )
7777 tags
7878 in
7979 let lines =
Original file line number Diff line number Diff line change @@ -144,7 +144,9 @@ module Ast_to_sexp = struct
144144 | `Return es ->
145145 List (Atom "@return" :: List.map (at.at (nestable_block_element at)) es)
146146 | `Children_order es ->
147- List (Atom "@return" :: List.map (at.at (nestable_block_element at)) es)
147+ List
148+ (Atom "@children_order"
149+ :: List.map (at.at (nestable_block_element at)) es)
148150 | `See (kind, s, es) ->
149151 let kind =
150152 match kind with
You can’t perform that action at this time.
0 commit comments