@@ -576,7 +576,7 @@ let _check_subset : stopped_implicitly -> Token.t = fun t -> (t :> Token.t)
576576   - The type of token that the block parser stops at. See discussion above. *)  
577577type  ('block, 'stops_at_which_tokens) context  =
578578  | Top_level  : (Ast .block_element , stops_at_delimiters ) context 
579-   | In_implicitely_ended  :
579+   | In_implicitly_ended  :
580580      [ `Tag  | `Shorthand_list  ]
581581      -> (Ast .nestable_block_element , stopped_implicitly ) context 
582582  | In_explicit_list  : (Ast .nestable_block_element , stops_at_delimiters ) context 
@@ -593,7 +593,7 @@ let accepted_in_all_contexts :
593593 fun  context  block  ->
594594  match  context with 
595595  |  Top_level  -> (block :> Ast.block_element )
596-   |  In_implicitely_ended  (`Tag  | `Shorthand_list ) -> block
596+   |  In_implicitly_ended  (`Tag  | `Shorthand_list ) -> block
597597  |  In_explicit_list  -> block
598598  |  In_table_cell  -> block
599599  |  In_code_results  -> block
@@ -672,7 +672,7 @@ let rec block_element_list :
672672    |  { value  = `End ; _ }  as  next_token  -> (
673673        match  context with 
674674        |  Top_level  -> (List. rev acc, next_token, where_in_line)
675-         |  In_implicitely_ended  (`Tag  | `Shorthand_list ) ->
675+         |  In_implicitly_ended  (`Tag  | `Shorthand_list ) ->
676676            (List. rev acc, next_token, where_in_line)
677677        |  In_explicit_list  -> (List. rev acc, next_token, where_in_line)
678678        |  In_table_cell  -> (List. rev acc, next_token, where_in_line)
@@ -683,7 +683,7 @@ let rec block_element_list :
683683           possible values of [context]. *)  
684684        match  context with 
685685        |  Top_level  -> (List. rev acc, next_token, where_in_line)
686-         |  In_implicitely_ended  (`Tag  | `Shorthand_list ) ->
686+         |  In_implicitly_ended  (`Tag  | `Shorthand_list ) ->
687687            (List. rev acc, next_token, where_in_line)
688688        |  In_explicit_list  -> (List. rev acc, next_token, where_in_line)
689689        |  In_table_cell  -> (List. rev acc, next_token, where_in_line)
@@ -710,7 +710,7 @@ let rec block_element_list :
710710        (*  Blank lines terminate shorthand lists ([- foo]) and tags. They also
711711           terminate paragraphs, but the paragraph parser is aware of that 
712712           internally. *)  
713-         |  In_implicitely_ended  (`Tag  | `Shorthand_list ) ->
713+         |  In_implicitly_ended  (`Tag  | `Shorthand_list ) ->
714714            (List. rev acc, next_token, where_in_line)
715715        (*  Otherwise, blank lines are pretty much like single newlines. *) 
716716        |  _  ->
@@ -778,7 +778,7 @@ let rec block_element_list :
778778        (*  If a tag starts at the beginning of a line, it terminates the preceding
779779           tag and/or the current shorthand list. In this case, return to the 
780780           caller, and let the caller decide how to interpret the tag token. *)  
781-         |  In_implicitely_ended  (`Tag  | `Shorthand_list ) ->
781+         |  In_implicitly_ended  (`Tag  | `Shorthand_list ) ->
782782            if  where_in_line =  `At_start_of_line  then 
783783              (List. rev acc, next_token, where_in_line)
784784            else  recover_when_not_at_top_level context
@@ -819,7 +819,7 @@ let rec block_element_list :
819819                consume_block_elements `After_text  (tag :: acc)
820820            |  (`Deprecated  | `Return ) as  tag  ->
821821                let  content, _stream_head, where_in_line = 
822-                   block_element_list (In_implicitely_ended  `Tag )
822+                   block_element_list (In_implicitly_ended  `Tag )
823823                    ~parent_markup: token input
824824                in 
825825                let  tag = 
@@ -834,7 +834,7 @@ let rec block_element_list :
834834                consume_block_elements where_in_line (tag :: acc)
835835            |  (`Param  _  | `Raise  _  | `Before  _ ) as  tag  ->
836836                let  content, _stream_head, where_in_line = 
837-                   block_element_list (In_implicitely_ended  `Tag )
837+                   block_element_list (In_implicitly_ended  `Tag )
838838                    ~parent_markup: token input
839839                in 
840840                let  tag = 
@@ -850,7 +850,7 @@ let rec block_element_list :
850850                consume_block_elements where_in_line (tag :: acc)
851851            |  `See  (kind , target ) ->
852852                let  content, _next_token, where_in_line = 
853-                   block_element_list (In_implicitely_ended  `Tag )
853+                   block_element_list (In_implicitly_ended  `Tag )
854854                    ~parent_markup: token input
855855                in 
856856                let  location = 
@@ -1023,7 +1023,7 @@ let rec block_element_list :
10231023        |  _  -> () );
10241024
10251025        match  context with 
1026-         |  In_implicitely_ended  `Shorthand_list  ->
1026+         |  In_implicitly_ended  `Shorthand_list  ->
10271027            (List. rev acc, next_token, where_in_line)
10281028        |  _  ->
10291029            let  items, where_in_line = 
@@ -1060,7 +1060,7 @@ let rec block_element_list :
10601060        in 
10611061
10621062        match  context with 
1063-         |  In_implicitely_ended  (`Tag  | `Shorthand_list ) ->
1063+         |  In_implicitly_ended  (`Tag  | `Shorthand_list ) ->
10641064            if  where_in_line =  `At_start_of_line  then 
10651065              (List. rev acc, next_token, where_in_line)
10661066            else  recover_when_not_at_top_level context
@@ -1171,11 +1171,11 @@ let rec block_element_list :
11711171  let  where_in_line = 
11721172    match  context with 
11731173    |  Top_level  -> `At_start_of_line 
1174-     |  In_implicitely_ended  `Shorthand_list  -> `After_shorthand_bullet 
1174+     |  In_implicitly_ended  `Shorthand_list  -> `After_shorthand_bullet 
11751175    |  In_explicit_list  -> `After_explicit_list_bullet 
11761176    |  In_table_cell  -> `After_table_cell 
11771177    |  In_code_results  -> `After_tag 
1178-     |  In_implicitely_ended  `Tag  -> `After_tag 
1178+     |  In_implicitly_ended  `Tag  -> `After_tag 
11791179  in 
11801180
11811181  consume_block_elements where_in_line [] 
@@ -1215,7 +1215,7 @@ and shorthand_list_items :
12151215          junk input;
12161216
12171217          let  content, stream_head, where_in_line = 
1218-             block_element_list (In_implicitely_ended  `Shorthand_list )
1218+             block_element_list (In_implicitly_ended  `Shorthand_list )
12191219              ~parent_markup: bullet input
12201220          in 
12211221          if  content =  []  then 
0 commit comments