Library
Module
Module type
Parameter
Class
Class type
module MenhirBasics : sig ... end
include module type of struct include MenhirBasics end
type token = MenhirBasics.token =
| WITH
| WHILE
| WHEN
| VIRTUAL
| VAL
| UNDERSCORE
| UIDENT of string
| TYPE
| TRY
| TRUE
| TO
| TILDE
| THEN
| SWITCH
| STRUCT
| STRING of string * string option
| STAR
| SLASHGREATER
| SIG
| SHARPOP of string
| SHARP
| SEMISEMI
| SEMI
| RPAREN
| REC
| RBRACKET
| RBRACE
| QUOTE
| QUESTION
| PUB
| PRI
| PREFIXOP of string
| PLUSEQ
| PLUSDOT
| PLUS
| PERCENT
| OR
| OPTIONAL_NO_DEFAULT
| OPEN
| OF
| OBJECT
| NONREC
| NEW
| NATIVEINT of nativeint
| MUTABLE
| MODULE
| MINUSGREATER
| MINUSDOT
| MINUS
| LPAREN
| LIDENTCOLONCOLON of string
| LIDENT of string
| LET
| LESSSLASHIDENTGREATER of string
| LESSSLASHGREATER
| LESSSLASH
| LESSMINUS
| LESSIDENT of string
| LESSGREATER
| LESSDOTDOTGREATER
| LESS
| LBRACKETPERCENTPERCENT
| LBRACKETPERCENT
| LBRACKETLESS
| LBRACKETGREATER
| LBRACKETBAR
| LBRACKETATATAT
| LBRACKETATAT
| LBRACKETAT
| LBRACKET
| LBRACELESS
| LBRACE
| LAZY
| 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
| GREATERRBRACE
| GREATER
| FUNCTOR
| FUNCTION
| FUN
| FOR
| FLOAT of string * char option
| FALSE
| EXTERNAL
| EXCEPTION
| EQUALGREATER
| EQUAL
| EOL
| EOF
| END
| ELSE
| DOWNTO
| DOTDOTDOT
| DOTDOT
| DOT
| DONE
| DO
| CONSTRAINT
| COMMENT of string * Location.t
| COMMA
| COLONGREATER
| COLONEQUAL
| COLONCOLONLIDENT of string
| COLONCOLON
| COLON
| CLASS
| CHAR of char
| BEGIN
| BARRBRACKET
| BARBAR
| BAR
| BANG
| BACKQUOTE
| ASSERT
| AS
| AND
| AMPERSAND
| AMPERAMPER
location.ml: ------------ let mkloc txt loc = txt ; loc
let rhs_loc n =
loc_start = Parsing.rhs_start_pos n;
loc_end = Parsing.rhs_end_pos n;
loc_ghost = false;
let symbol_rloc () =
loc_start = Parsing.symbol_start_pos ();
loc_end = Parsing.symbol_end_pos ();
loc_ghost = false;
let symbol_gloc () =
loc_start = Parsing.symbol_start_pos ();
loc_end = Parsing.symbol_end_pos ();
loc_ghost = true;
ast_helper.ml: ------------ module Typ = struct val mk: ?loc:loc -> ?attrs:attrs -> core_type_desc -> core_type let mk ?(loc = !default_loc) ?(attrs = ) d = ptyp_desc = d; ptyp_loc = loc; ptyp_attributes = attrs
.. end
parse_tree.mli -------------- and core_type =
ptyp_desc: core_type_desc;
ptyp_loc: Location.t;
ptyp_attributes: attributes; (* ... [@id1] [@id2] *)
and core_type_desc = | Ptyp_any (* _ *) | Ptyp_var of string (* 'a *) | Ptyp_arrow of label * core_type * core_type (* T1 -> T2 (label = "") ~l:T1 -> T2 (label = "l") ?l:T1 -> T2 (label = "?l") *) | Ptyp_tuple of core_type list (* T1 * ... * Tn (n >= 2) *)
reason_parser.mly --------------- In general:
syntax variant pblah_desc: core_blah_desc
pblah_loc: {txt, loc
pblah_attributes: ...
}
/ \ / \ val mkblah: ~loc -> ~attributes -> core_blah_desc -> core_blah let mkblah = Blah.mk
val dummy_loc : unit -> Migrate_parsetree.OCaml_404.Ast.Location.t
val mklocation :
Lexing.position ->
Lexing.position ->
Migrate_parsetree.OCaml_404.Ast.Location.t
val with_txt :
'a Migrate_parsetree.OCaml_404.Ast.Asttypes.loc ->
'b ->
'b Migrate_parsetree.OCaml_404.Ast.Asttypes.loc
val make_real_loc :
Migrate_parsetree.OCaml_404.Ast.Location.t ->
Migrate_parsetree.OCaml_404.Ast.Location.t
val make_ghost_loc :
Migrate_parsetree.OCaml_404.Ast.Location.t ->
Migrate_parsetree.OCaml_404.Ast.Location.t
val ghloc :
?loc:Migrate_parsetree.OCaml_404.Ast.Location.t ->
'a ->
'a Migrate_parsetree.OCaml_404.Ast.Asttypes.loc
val make_real_exp :
Migrate_parsetree.OCaml_404.Ast.Parsetree.expression ->
Migrate_parsetree.OCaml_404.Ast.Parsetree.expression
* turn an object into a real
val make_ghost_cf :
Migrate_parsetree.OCaml_404.Ast.Parsetree.class_field ->
Migrate_parsetree.OCaml_404.Ast.Parsetree.class_field
* turn a object into ghost
val make_ghost_pat :
Migrate_parsetree.OCaml_404.Ast.Parsetree.pattern ->
Migrate_parsetree.OCaml_404.Ast.Parsetree.pattern
val set_loc_state :
bool ->
Migrate_parsetree.OCaml_404.Ast.Location.t ->
Migrate_parsetree.OCaml_404.Ast.Location.t
* change the location state to be a ghost location or real location
val mkct :
string Migrate_parsetree.OCaml_404.Ast.Asttypes.loc ->
Migrate_parsetree.OCaml_404.Ast.Parsetree.core_type
Make a core_type from a as_loc(LIDENT). Useful for record type punning. type props = width: int, height: int
; type state = nbrOfClicks: int
; type component = props, state
;
val simple_ghost_text_attr :
?loc:Migrate_parsetree.OCaml_404.Ast.Location.t ->
'a ->
('a Migrate_parsetree.OCaml_404.Ast.Asttypes.loc
* Migrate_parsetree.OCaml_404.Ast.Parsetree.payload)
list
val mkExplicitArityTuplePat :
?loc:Migrate_parsetree.OCaml_404.Ast.Location.t ->
Migrate_parsetree_versions.OCaml_404.Ast.Parsetree.pattern_desc ->
Migrate_parsetree_versions.OCaml_404.Ast.Parsetree.pattern
val mkExplicitArityTupleExp :
?loc:Migrate_parsetree.OCaml_404.Ast.Location.t ->
Migrate_parsetree_versions.OCaml_404.Ast.Parsetree.expression_desc ->
Migrate_parsetree_versions.OCaml_404.Ast.Parsetree.expression
val is_pattern_list_single_any :
Migrate_parsetree.OCaml_404.Ast.Parsetree.pattern list ->
Migrate_parsetree.OCaml_404.Ast.Parsetree.pattern option
val set_structure_item_location :
Migrate_parsetree.OCaml_404.Ast.Parsetree.structure_item ->
Migrate_parsetree_versions.OCaml_404.Ast.Location.t ->
Migrate_parsetree.OCaml_404.Ast.Parsetree.structure_item
val mkoperator_loc :
string ->
Migrate_parsetree_versions.OCaml_404.Ast.Ast_helper.loc ->
Migrate_parsetree_versions.OCaml_404.Ast.Parsetree.expression
val mkoperator :
string ->
int ->
Migrate_parsetree_versions.OCaml_404.Ast.Parsetree.expression
val ghunit :
?loc:Migrate_parsetree.OCaml_404.Ast.Location.t ->
unit ->
Migrate_parsetree_versions.OCaml_404.Ast.Parsetree.expression
val mkuminus :
string ->
Migrate_parsetree.OCaml_404.Ast.Parsetree.expression ->
Migrate_parsetree_versions.OCaml_404.Ast.Parsetree.expression
val mkFunctorThatReturns :
(string Migrate_parsetree_versions.OCaml_404.Ast.Asttypes.loc
* Migrate_parsetree.OCaml_404.Ast.Parsetree.module_type option)
list ->
Migrate_parsetree.OCaml_404.Ast.Parsetree.module_expr ->
Migrate_parsetree.OCaml_404.Ast.Parsetree.module_expr
val mkexp_constructor_unit :
Migrate_parsetree.OCaml_404.Ast.Location.t ->
Migrate_parsetree.OCaml_404.Ast.Location.t ->
Migrate_parsetree_versions.OCaml_404.Ast.Parsetree.expression
val simple_pattern_list_to_tuple :
?loc:Migrate_parsetree.OCaml_404.Ast.Location.t ->
Migrate_parsetree.OCaml_404.Ast.Parsetree.pattern list ->
Migrate_parsetree_versions.OCaml_404.Ast.Parsetree.pattern
val ghexp_constraint :
Migrate_parsetree.OCaml_404.Ast.Location.t ->
Migrate_parsetree.OCaml_404.Ast.Parsetree.expression ->
(Migrate_parsetree.OCaml_404.Ast.Parsetree.core_type option
* Migrate_parsetree.OCaml_404.Ast.Parsetree.core_type option) ->
Migrate_parsetree_versions.OCaml_404.Ast.Parsetree.expression
val array_function :
?loc:Migrate_parsetree.OCaml_404.Ast.Location.t ->
string ->
string ->
Migrate_parsetree.OCaml_404.Ast.Longident.t
Migrate_parsetree.OCaml_404.Ast.Asttypes.loc
val syntax_error_str :
Migrate_parsetree_versions.OCaml_404.Ast.Ast_helper.loc ->
string ->
Migrate_parsetree_versions.OCaml_404.Ast.Parsetree.structure_item
val syntax_error_exp :
Migrate_parsetree_versions.OCaml_404.Ast.Ast_helper.loc ->
string ->
Migrate_parsetree_versions.OCaml_404.Ast.Parsetree.expression
val unclosed :
string Migrate_parsetree.OCaml_404.Ast.Asttypes.loc ->
string Migrate_parsetree.OCaml_404.Ast.Asttypes.loc ->
'a
val unclosed_extension :
string Migrate_parsetree.OCaml_404.Ast.Asttypes.loc ->
string Ast_404.Location.loc * Ast_404.Parsetree.payload
val unclosed_mod :
string Migrate_parsetree.OCaml_404.Ast.Asttypes.loc ->
string Migrate_parsetree.OCaml_404.Ast.Asttypes.loc ->
Migrate_parsetree_versions.OCaml_404.Ast.Parsetree.module_expr
val unclosed_cl :
string Migrate_parsetree.OCaml_404.Ast.Asttypes.loc ->
string Migrate_parsetree.OCaml_404.Ast.Asttypes.loc ->
Migrate_parsetree_versions.OCaml_404.Ast.Parsetree.class_expr
val unclosed_mty :
string Migrate_parsetree.OCaml_404.Ast.Asttypes.loc ->
string Migrate_parsetree.OCaml_404.Ast.Asttypes.loc ->
Migrate_parsetree_versions.OCaml_404.Ast.Parsetree.module_type
val unclosed_cty :
string Migrate_parsetree.OCaml_404.Ast.Asttypes.loc ->
string Migrate_parsetree.OCaml_404.Ast.Asttypes.loc ->
Migrate_parsetree_versions.OCaml_404.Ast.Parsetree.class_type
val unclosed_exp :
string Migrate_parsetree.OCaml_404.Ast.Asttypes.loc ->
string Migrate_parsetree.OCaml_404.Ast.Asttypes.loc ->
Migrate_parsetree_versions.OCaml_404.Ast.Parsetree.expression
val unclosed_pat :
string Migrate_parsetree.OCaml_404.Ast.Asttypes.loc ->
string Migrate_parsetree.OCaml_404.Ast.Asttypes.loc ->
Migrate_parsetree_versions.OCaml_404.Ast.Parsetree.pattern
val expecting : string Migrate_parsetree.OCaml_404.Ast.Asttypes.loc -> 'a
val expecting_pat :
string Migrate_parsetree.OCaml_404.Ast.Asttypes.loc ->
Migrate_parsetree_versions.OCaml_404.Ast.Parsetree.pattern
val not_expecting : Lexing.position -> Lexing.position -> string -> 'a
val bigarray_function :
?loc:Migrate_parsetree.OCaml_404.Ast.Location.t ->
string ->
string ->
Migrate_parsetree.OCaml_404.Ast.Longident.t
Migrate_parsetree.OCaml_404.Ast.Asttypes.loc
val bigarray_untuplify :
Migrate_parsetree.OCaml_404.Ast.Parsetree.expression ->
Migrate_parsetree.OCaml_404.Ast.Parsetree.expression list
val check_variable : string list -> Location.t -> string -> unit
val varify_constructors :
string list ->
Migrate_parsetree.OCaml_404.Ast.Parsetree.core_type ->
Migrate_parsetree.OCaml_404.Ast.Parsetree.core_type
val pexp_newtypes :
?loc:Migrate_parsetree.OCaml_404.Ast.Location.t ->
string list ->
Migrate_parsetree.OCaml_404.Ast.Parsetree.expression ->
Migrate_parsetree.OCaml_404.Ast.Parsetree.expression
val wrap_type_annotation :
string list ->
Migrate_parsetree.OCaml_404.Ast.Parsetree.core_type ->
Migrate_parsetree.OCaml_404.Ast.Parsetree.expression ->
Migrate_parsetree.OCaml_404.Ast.Parsetree.expression
* Migrate_parsetree_versions.OCaml_404.Ast.Parsetree.core_type
I believe that wrap_type_annotation will automatically generate the type arguments (type a) (type b) based on what was listed before the dot in a polymorphic type annotation that uses locally abstract types.
type let_binding = {
lb_pattern : Migrate_parsetree.OCaml_404.Ast.Parsetree.pattern;
lb_expression : Migrate_parsetree.OCaml_404.Ast.Parsetree.expression;
lb_attributes : Migrate_parsetree.OCaml_404.Ast.Parsetree.attributes;
lb_loc : Migrate_parsetree.OCaml_404.Ast.Location.t;
}
type let_bindings = {
lbs_bindings : let_binding list;
lbs_rec : Migrate_parsetree.OCaml_404.Ast.Asttypes.rec_flag;
lbs_extension : string Migrate_parsetree.OCaml_404.Ast.Asttypes.loc option;
lbs_attributes : Migrate_parsetree.OCaml_404.Ast.Parsetree.attributes;
lbs_loc : Migrate_parsetree.OCaml_404.Ast.Location.t;
}
val addlb : let_bindings -> let_binding -> let_bindings
val val_of_let_bindings :
let_bindings ->
Migrate_parsetree_versions.OCaml_404.Ast.Parsetree.structure_item
val expr_of_let_bindings :
let_bindings ->
Migrate_parsetree.OCaml_404.Ast.Parsetree.expression ->
Migrate_parsetree_versions.OCaml_404.Ast.Parsetree.expression
val class_of_let_bindings :
let_bindings ->
Migrate_parsetree.OCaml_404.Ast.Parsetree.class_expr ->
Migrate_parsetree_versions.OCaml_404.Ast.Parsetree.class_expr
val arity_conflict_resolving_mapper :
Migrate_parsetree.OCaml_404.Ast.Ast_mapper.mapper
val default_mapper_chain :
unit ->
Migrate_parsetree.OCaml_404.Ast.Ast_mapper.mapper list
val string_of_longident : Migrate_parsetree.OCaml_404.Ast.Longident.t -> string
val jsx_component :
Migrate_parsetree.OCaml_404.Ast.Longident.t ->
(Migrate_parsetree_versions.OCaml_404.Ast.Asttypes.arg_label
* Migrate_parsetree.OCaml_404.Ast.Parsetree.expression)
list ->
(Migrate_parsetree_versions.OCaml_404.Ast.Asttypes.arg_label
* Migrate_parsetree.OCaml_404.Ast.Parsetree.expression)
list ->
Migrate_parsetree.OCaml_404.Ast.Location.t ->
Migrate_parsetree_versions.OCaml_404.Ast.Parsetree.expression
val ensureTagsAreEqual :
Migrate_parsetree.OCaml_404.Ast.Longident.t ->
Migrate_parsetree.OCaml_404.Ast.Longident.t ->
Migrate_parsetree.OCaml_404.Ast.Location.t ->
unit
type core_type_object =
| Core_type of Migrate_parsetree.OCaml_404.Ast.Parsetree.core_type
| Record_type of Migrate_parsetree.OCaml_404.Ast.Parsetree.label_declaration list
val only_core_type :
core_type_object ->
Migrate_parsetree.OCaml_404.Ast.Location.t ->
Migrate_parsetree.OCaml_404.Ast.Parsetree.core_type
module Tables : sig ... end
module MenhirInterpreter : sig ... end
val use_file :
(Lexing.lexbuf -> MenhirInterpreter.token) ->
Lexing.lexbuf ->
Ast_404.Parsetree.toplevel_phrase list
val toplevel_phrase :
(Lexing.lexbuf -> MenhirInterpreter.token) ->
Lexing.lexbuf ->
Ast_404.Parsetree.toplevel_phrase
val parse_pattern :
(Lexing.lexbuf -> MenhirInterpreter.token) ->
Lexing.lexbuf ->
Ast_404.Parsetree.pattern
val parse_expression :
(Lexing.lexbuf -> MenhirInterpreter.token) ->
Lexing.lexbuf ->
Ast_404.Parsetree.expression
val parse_core_type :
(Lexing.lexbuf -> MenhirInterpreter.token) ->
Lexing.lexbuf ->
Ast_404.Parsetree.core_type
val interface :
(Lexing.lexbuf -> MenhirInterpreter.token) ->
Lexing.lexbuf ->
Ast_404.Parsetree.signature
val implementation :
(Lexing.lexbuf -> MenhirInterpreter.token) ->
Lexing.lexbuf ->
Ast_404.Parsetree.structure
module Incremental : sig ... end