sig
  type token =
      WITH
    | WHILE
    | WHEN
    | VIRTUAL
    | VAL
    | UNDERSCORE
    | UIDENT of string
    | TYPE
    | TRY
    | TRUE
    | TO
    | TILDE
    | THEN
    | STRUCT
    | STRING of (string * Location.t * string option)
    | STAR
    | SIG
    | SEMISEMI
    | SEMI
    | RPAREN
    | REC
    | RBRACKET
    | RBRACE
    | QUOTED_STRING_ITEM of
        (string * Location.t * string * Location.t * string option)
    | QUOTED_STRING_EXPR of
        (string * Location.t * string * Location.t * string option)
    | QUOTE
    | QUESTION
    | PRIVATE
    | PREFIXOP of string
    | PLUSEQ
    | PLUSDOT
    | PLUS
    | PERCENT
    | OR
    | OPTLABEL of string
    | OPEN
    | OF
    | OBJECT
    | NONREC
    | NEW
    | MUTABLE
    | MODULE
    | MINUSGREATER
    | MINUSDOT
    | MINUS
    | METHOD
    | MATCH
    | LPAREN
    | LIDENT of string
    | LETOP of string
    | LET
    | LESSMINUS
    | LESS
    | LBRACKETPERCENTPERCENT
    | LBRACKETPERCENT
    | LBRACKETLESS
    | LBRACKETGREATER
    | LBRACKETBAR
    | LBRACKETATATAT
    | LBRACKETATAT
    | LBRACKETAT
    | LBRACKET
    | LBRACELESS
    | LBRACE
    | LAZY
    | LABEL of string
    | INT of (string * char option)
    | INITIALIZER
    | INHERIT
    | INFIXOP4 of string
    | INFIXOP3 of string
    | INFIXOP2 of string
    | INFIXOP1 of string
    | INFIXOP0 of string
    | INCLUDE
    | IN
    | IF
    | HASHOP of string
    | HASH
    | GREATERRBRACKET
    | GREATERRBRACE
    | GREATER
    | FUNCTOR
    | FUNCTION
    | FUN
    | FOR
    | FLOAT of (string * char option)
    | FALSE
    | EXTERNAL
    | EXCEPTION
    | EQUAL
    | EOL
    | EOF
    | END
    | ELSE
    | DOWNTO
    | DOTOP of string
    | DOTDOT
    | DOT
    | DONE
    | DOCSTRING of Docstrings.docstring
    | DO
    | CONSTRAINT
    | COMMENT of (string * Location.t)
    | COMMA
    | COLONGREATER
    | COLONEQUAL
    | COLONCOLON
    | COLON
    | CLASS
    | CHAR of char
    | BEGIN
    | BARRBRACKET
    | BARBAR
    | BAR
    | BANG
    | BACKQUOTE
    | ASSERT
    | AS
    | ANDOP of string
    | AND
    | AMPERSAND
    | AMPERAMPER
  exception Error
  val use_file :
    (Stdlib.Lexing.lexbuf -> Parser.token) ->
    Stdlib.Lexing.lexbuf -> Parsetree.toplevel_phrase list
  val toplevel_phrase :
    (Stdlib.Lexing.lexbuf -> Parser.token) ->
    Stdlib.Lexing.lexbuf -> Parsetree.toplevel_phrase
  val parse_val_longident :
    (Stdlib.Lexing.lexbuf -> Parser.token) ->
    Stdlib.Lexing.lexbuf -> Longident.t
  val parse_pattern :
    (Stdlib.Lexing.lexbuf -> Parser.token) ->
    Stdlib.Lexing.lexbuf -> Parsetree.pattern
  val parse_mty_longident :
    (Stdlib.Lexing.lexbuf -> Parser.token) ->
    Stdlib.Lexing.lexbuf -> Longident.t
  val parse_module_type :
    (Stdlib.Lexing.lexbuf -> Parser.token) ->
    Stdlib.Lexing.lexbuf -> Parsetree.module_type
  val parse_module_expr :
    (Stdlib.Lexing.lexbuf -> Parser.token) ->
    Stdlib.Lexing.lexbuf -> Parsetree.module_expr
  val parse_mod_longident :
    (Stdlib.Lexing.lexbuf -> Parser.token) ->
    Stdlib.Lexing.lexbuf -> Longident.t
  val parse_mod_ext_longident :
    (Stdlib.Lexing.lexbuf -> Parser.token) ->
    Stdlib.Lexing.lexbuf -> Longident.t
  val parse_expression :
    (Stdlib.Lexing.lexbuf -> Parser.token) ->
    Stdlib.Lexing.lexbuf -> Parsetree.expression
  val parse_core_type :
    (Stdlib.Lexing.lexbuf -> Parser.token) ->
    Stdlib.Lexing.lexbuf -> Parsetree.core_type
  val parse_constr_longident :
    (Stdlib.Lexing.lexbuf -> Parser.token) ->
    Stdlib.Lexing.lexbuf -> Longident.t
  val parse_any_longident :
    (Stdlib.Lexing.lexbuf -> Parser.token) ->
    Stdlib.Lexing.lexbuf -> Longident.t
  val interface :
    (Stdlib.Lexing.lexbuf -> Parser.token) ->
    Stdlib.Lexing.lexbuf -> Parsetree.signature
  val implementation :
    (Stdlib.Lexing.lexbuf -> Parser.token) ->
    Stdlib.Lexing.lexbuf -> Parsetree.structure
  module MenhirInterpreter :
    sig
      type token = token
      type production
      type 'a env
      type 'a checkpoint = private
          InputNeeded of 'a env
        | Shifting of 'a env * 'a env * bool
        | AboutToReduce of 'a env * production
        | HandlingError of 'a env
        | Accepted of 'a
        | Rejected
      val offer :
        'a checkpoint ->
        token * CamlinternalMenhirLib.IncrementalEngine.position *
        CamlinternalMenhirLib.IncrementalEngine.position -> 'a checkpoint
      type strategy = [ `Legacy | `Simplified ]
      val resume : ?strategy:strategy -> 'a checkpoint -> 'a checkpoint
      type supplier =
          unit ->
          token * CamlinternalMenhirLib.IncrementalEngine.position *
          CamlinternalMenhirLib.IncrementalEngine.position
      val lexer_lexbuf_to_supplier :
        (Lexing.lexbuf -> token) -> Lexing.lexbuf -> supplier
      val loop : ?strategy:strategy -> supplier -> 'a checkpoint -> 'a
      val loop_handle :
        ('-> 'answer) ->
        ('a checkpoint -> 'answer) -> supplier -> 'a checkpoint -> 'answer
      val loop_handle_undo :
        ('-> 'answer) ->
        ('a checkpoint -> 'a checkpoint -> 'answer) ->
        supplier -> 'a checkpoint -> 'answer
      val shifts : 'a checkpoint -> 'a env option
      val acceptable :
        'a checkpoint ->
        token -> CamlinternalMenhirLib.IncrementalEngine.position -> bool
      type 'a lr1state
      val number : 'a lr1state -> int
      val production_index : production -> int
      val find_production : int -> production
      type element =
          Element : 'a lr1state * 'a *
            CamlinternalMenhirLib.IncrementalEngine.position *
            CamlinternalMenhirLib.IncrementalEngine.position -> element
      type stack = element CamlinternalMenhirLib.General.stream
      val stack : 'a env -> stack
      val top : 'a env -> element option
      val pop_many : int -> 'a env -> 'a env option
      val get : int -> 'a env -> element option
      val current_state_number : 'a env -> int
      val equal : 'a env -> 'a env -> bool
      val positions :
        'a env ->
        CamlinternalMenhirLib.IncrementalEngine.position *
        CamlinternalMenhirLib.IncrementalEngine.position
      val env_has_default_reduction : 'a env -> bool
      val state_has_default_reduction : 'a lr1state -> bool
      val pop : 'a env -> 'a env option
      val force_reduction : production -> 'a env -> 'a env
      val input_needed : 'a env -> 'a checkpoint
    end
  module Incremental :
    sig
      val use_file :
        Stdlib.Lexing.position ->
        Parsetree.toplevel_phrase list Parser.MenhirInterpreter.checkpoint
      val toplevel_phrase :
        Stdlib.Lexing.position ->
        Parsetree.toplevel_phrase Parser.MenhirInterpreter.checkpoint
      val parse_val_longident :
        Stdlib.Lexing.position ->
        Longident.t Parser.MenhirInterpreter.checkpoint
      val parse_pattern :
        Stdlib.Lexing.position ->
        Parsetree.pattern Parser.MenhirInterpreter.checkpoint
      val parse_mty_longident :
        Stdlib.Lexing.position ->
        Longident.t Parser.MenhirInterpreter.checkpoint
      val parse_module_type :
        Stdlib.Lexing.position ->
        Parsetree.module_type Parser.MenhirInterpreter.checkpoint
      val parse_module_expr :
        Stdlib.Lexing.position ->
        Parsetree.module_expr Parser.MenhirInterpreter.checkpoint
      val parse_mod_longident :
        Stdlib.Lexing.position ->
        Longident.t Parser.MenhirInterpreter.checkpoint
      val parse_mod_ext_longident :
        Stdlib.Lexing.position ->
        Longident.t Parser.MenhirInterpreter.checkpoint
      val parse_expression :
        Stdlib.Lexing.position ->
        Parsetree.expression Parser.MenhirInterpreter.checkpoint
      val parse_core_type :
        Stdlib.Lexing.position ->
        Parsetree.core_type Parser.MenhirInterpreter.checkpoint
      val parse_constr_longident :
        Stdlib.Lexing.position ->
        Longident.t Parser.MenhirInterpreter.checkpoint
      val parse_any_longident :
        Stdlib.Lexing.position ->
        Longident.t Parser.MenhirInterpreter.checkpoint
      val interface :
        Stdlib.Lexing.position ->
        Parsetree.signature Parser.MenhirInterpreter.checkpoint
      val implementation :
        Stdlib.Lexing.position ->
        Parsetree.structure Parser.MenhirInterpreter.checkpoint
    end
end