package reason-parser

  1. Overview
  2. Docs
Legend:
Library
Module
Module type
Parameter
Class
Class type
type commentCategory =
  1. | EndOfLine
  2. | SingleLine
  3. | Regular
type commentWithCategory = (String.t * commentCategory * Ast_404.Location.t) list
val print_easy : Easy_format.t -> string
val (|>) : 'a -> ('a -> 'b) -> 'b
val (<|) : ('a -> 'b) -> 'a -> 'b
exception NotPossible of string
val case_not_implemented : string -> Ast_404.Location.t -> (string * int * int) -> unit
val exprDescrString : Ast_404.Parsetree.expression -> string
type ruleInfoData = {
  1. reducePrecedence : precedence;
  2. shiftPrecedence : precedence;
}
and ruleCategory =
  1. | FunctionApplication of layoutNode list
  2. | SpecificInfixPrecedence of ruleInfoData * layoutNode
  3. | PotentiallyLowPrecedence of layoutNode
  4. | Simple of layoutNode
and associativity =
  1. | Right
  2. | Nonassoc
  3. | Left
and precedenceEntryType =
  1. | TokenPrecedence
  2. | CustomPrecedence
and precedence =
  1. | Token of string
  2. | Custom of string
and whenToDoSomething =
  1. | Never
  2. | IfNeed
  3. | Always
  4. | Always_rec
and tokenFixity =
  1. | AlmostSimplePrefix of string
  2. | UnaryPlusPrefix of string
  3. | UnaryMinusPrefix of string
  4. | Infix of string
  5. | Normal
and easyFormatLabelFormatter = Easy_format.t -> Easy_format.t -> Easy_format.t
and listConfig = {
  1. newlinesAboveItems : int;
  2. newlinesAboveComments : int;
  3. newlinesAboveDocComments : int;
  4. interleaveComments : bool;
  5. renderFinalSep : bool;
  6. break : whenToDoSomething;
  7. wrap : string * string;
  8. inline : bool * bool;
  9. sep : string;
  10. indent : int;
  11. sepLeft : bool;
  12. preSpace : bool;
  13. postSpace : bool;
  14. pad : bool * bool;
  15. listConfigIfCommentsInterleaved : (listConfig -> listConfig) option;
  16. listConfigIfEolCommentsInterleaved : (listConfig -> listConfig) option;
}
and layoutNode =
  1. | SourceMap of Ast_404.Location.t * layoutNode
  2. | WithEOLComment of string * layoutNode
  3. | Sequence of listConfig * layoutNode list
  4. | Label of easyFormatLabelFormatter * layoutNode * layoutNode
  5. | Easy of Easy_format.t

* These represent "intent to format" the AST, with some parts being annotated * with original source location. The benefit of tracking this in an * intermediate structure, is that we can then interleave comments throughout * the tree before generating the final representation. That prevents the * formatting code from having to thread comments everywhere. * * The final representation is rendered using Easy_format.

val print_comment_type : commentCategory -> string
val print_comments : (string * commentCategory * Ast_404.Location.t) list -> unit
val print_easy_rec : ?indent:int -> Easy_format.t -> unit
val print_layout : ?indent:int -> layoutNode -> unit
val longIdentSame : (Ast_404.Longident.t * Ast_404.Longident.t) -> bool
val trueForEachPair : 'a list -> 'b list -> ('a -> 'b -> bool) -> bool
val same_ast_modulo_varification_and_extensions : Ast_404.Parsetree.core_type -> Ast_404.Parsetree.core_type -> bool
val wrapLayoutWithLoc : Ast_404.Location.t option -> layoutNode -> layoutNode
val expandLocation : Ast_404.Location.t -> expand:(int * int) -> Ast_404.Location.t
type attributesPartition = {
  1. arityAttrs : Ast_404.Parsetree.attributes;
  2. docAttrs : Ast_404.Parsetree.attributes;
  3. stdAttrs : Ast_404.Parsetree.attributes;
  4. jsxAttrs : Ast_404.Parsetree.attributes;
}

Kinds of attributes

val partitionAttributes : Ast_404.Parsetree.attribute list -> attributesPartition

Partition attributes into kinds

val almost_simple_prefix_symbols : char list
val unary_minus_prefix_symbols : string list
val unary_plus_prefix_symbols : string list
val infix_symbols : char list
val operator_chars : char list
val numeric_chars : char list
val special_infix_strings : string list
val updateToken : string
val requireIndentFor : string list
val infixTokenRequiresIndent : string -> int option
val getPrintableUnaryIdent : string -> string
val printedStringAndFixity : string -> tokenFixity
val isSimplePrefixToken : string -> bool
val rules : (precedenceEntryType * (string -> associativity * bool)) list list
val without_prefixed_backslashes : string -> string
val indexOfFirstMatch : prec:precedence -> (precedenceEntryType * (string -> 'a * bool)) list list -> ('a * int) option
val precedenceInfo : prec:precedence -> (associativity * int) option
val isLeftAssociative : prec:precedence -> bool
val isRightAssociative : prec:precedence -> bool
val higherPrecedenceThan : precedence -> precedence -> bool
val printedStringAndFixityExpr : Ast_404.Parsetree.expression -> tokenFixity
val is_predef_option : Ast_404.Longident.t -> bool
val needs_parens : string -> bool
val needs_spaces : string -> bool
val protect_ident : Format.formatter -> string -> unit
val protect_longident : Format.formatter -> (Format.formatter -> 'a -> unit) -> 'a -> string -> unit
val longident : Format.formatter -> Ast_404.Longident.t -> unit
type space_formatter = (unit, Format.formatter, unit) Pervasives.format
val override : Ast_404.Asttypes.override_flag -> string
val type_variance : Ast_404.Asttypes.variance -> string
type construct = [
  1. | `cons of Ast_404.Parsetree.expression list
  2. | `list of Ast_404.Parsetree.expression list
  3. | `nil
  4. | `normal
  5. | `simple of Ast_404.Longident.t
  6. | `tuple
]
val view_expr : Ast_404.Parsetree.expression -> [> `cons of Ast_404.Parsetree.expression list | `list of Ast_404.Parsetree.expression list | `nil | `normal | `simple of Ast_404.Longident.t | `tuple ]
val is_simple_construct : construct -> bool
type funcReturnStyle =
  1. | ReturnValOnSameLine
type funcApplicationLabelStyle =
  1. | NeverWrapFinalItem
  2. | WrapFinalListyItemIfFewerThan of int
type formatSettings = {
  1. constructorTupleImplicitArity : bool;
  2. space : int;
  3. returnStyle : funcReturnStyle;
  4. listsRecordsIndent : int;
  5. indentWrappedPatternArgs : int;
  6. indentMatchCases : int;
  7. indentAfterLabels : int;
  8. trySwitchIndent : int;
  9. funcApplicationLabelStyle : funcApplicationLabelStyle;
  10. funcCurriedPatternStyle : funcApplicationLabelStyle;
  11. width : int;
  12. assumeExplicitArity : bool;
  13. constructorLists : string list;
}
val configuredSettings : formatSettings Pervasives.ref
val configure : width:int -> assumeExplicitArity:bool -> constructorLists:string list -> unit
val string_of_formatter : (Format.formatter -> 'a -> unit) -> 'a -> string
val createFormatter : unit -> < case_list : Format.formatter -> Ast_404.Parsetree.case list -> unit ; core_type : Format.formatter -> Ast_404.Parsetree.core_type -> unit ; expression : Format.formatter -> Ast_404.Parsetree.expression -> unit ; pattern : Format.formatter -> Ast_404.Parsetree.pattern -> unit ; signature : commentWithCategory -> Format.formatter -> Ast_404.Parsetree.signature -> unit ; structure : commentWithCategory -> Format.formatter -> Ast_404.Parsetree.structure -> unit ; toplevel_phrase : Format.formatter -> Ast_404.Parsetree.toplevel_phrase -> unit >
val defaultSettings : formatSettings