Skip to content

Commit

Permalink
Expose Parse.module_type
Browse files Browse the repository at this point in the history
  • Loading branch information
gpetiot committed Oct 12, 2021
1 parent 0b3f8dd commit 4e21655
Show file tree
Hide file tree
Showing 5 changed files with 3,442 additions and 3,389 deletions.
6,818 changes: 3,429 additions & 3,389 deletions boot/menhir/parser.ml

Large diffs are not rendered by default.

4 changes: 4 additions & 0 deletions boot/menhir/parser.mli
Expand Up @@ -142,6 +142,8 @@ val parse_pattern: (Lexing.lexbuf -> token) -> Lexing.lexbuf -> (Parsetree.patte

val parse_mty_longident: (Lexing.lexbuf -> token) -> Lexing.lexbuf -> (Longident.t)

val parse_module_type: (Lexing.lexbuf -> token) -> Lexing.lexbuf -> (Parsetree.module_type)

val parse_mod_longident: (Lexing.lexbuf -> token) -> Lexing.lexbuf -> (Longident.t)

val parse_mod_ext_longident: (Lexing.lexbuf -> token) -> Lexing.lexbuf -> (Longident.t)
Expand Down Expand Up @@ -181,6 +183,8 @@ module Incremental : sig

val parse_mty_longident: Lexing.position -> (Longident.t) MenhirInterpreter.checkpoint

val parse_module_type: Lexing.position -> (Parsetree.module_type) MenhirInterpreter.checkpoint

val parse_mod_longident: Lexing.position -> (Longident.t) MenhirInterpreter.checkpoint

val parse_mod_ext_longident: Lexing.position -> (Longident.t) MenhirInterpreter.checkpoint
Expand Down
1 change: 1 addition & 0 deletions parsing/parse.ml
Expand Up @@ -95,6 +95,7 @@ and use_file = wrap Parser.use_file
and core_type = wrap Parser.parse_core_type
and expression = wrap Parser.parse_expression
and pattern = wrap Parser.parse_pattern
let module_type = wrap Parser.parse_module_type

let longident = wrap Parser.parse_any_longident
let val_ident = wrap Parser.parse_val_longident
Expand Down
1 change: 1 addition & 0 deletions parsing/parse.mli
Expand Up @@ -27,6 +27,7 @@ val use_file : Lexing.lexbuf -> Parsetree.toplevel_phrase list
val core_type : Lexing.lexbuf -> Parsetree.core_type
val expression : Lexing.lexbuf -> Parsetree.expression
val pattern : Lexing.lexbuf -> Parsetree.pattern
val module_type : Lexing.lexbuf -> Parsetree.module_type

(** The functions below can be used to parse Longident safely. *)

Expand Down
7 changes: 7 additions & 0 deletions parsing/parser.mly
Expand Up @@ -855,6 +855,8 @@ The precedences must be listed from low to high.
%type <Parsetree.expression> parse_expression
%start parse_pattern
%type <Parsetree.pattern> parse_pattern
%start parse_module_type
%type <Parsetree.module_type> parse_module_type
%start parse_constr_longident
%type <Longident.t> parse_constr_longident
%start parse_val_longident
Expand Down Expand Up @@ -1213,6 +1215,11 @@ parse_pattern:
{ $1 }
;

parse_module_type:
module_type EOF
{ $1 }
;

parse_mty_longident:
mty_longident EOF
{ $1 }
Expand Down

0 comments on commit 4e21655

Please sign in to comment.