package links

  1. Overview
  2. Docs

The syntax tree created by the parser.

val internal_error : string -> exn
module Binder : sig ... end
type tyarg = Types.type_arg
val pp_tyarg : Ppx_deriving_runtime.Format.formatter -> tyarg -> Ppx_deriving_runtime.unit
val default_subkind : CommonTypes.Subkind.t
val default_effect_subkind : CommonTypes.Subkind.t
val pp_kind : Ppx_deriving_runtime.Format.formatter -> kind -> Ppx_deriving_runtime.unit
module SugarTypeVar : sig ... end
module SugarQuantifier : sig ... end
val rigidify : ('a * 'b * 'c) -> 'a * 'b * [> `Rigid ]
type fieldconstraint =
  1. | Readonly
  2. | Default
val pp_fieldconstraint : Ppx_deriving_runtime.Format.formatter -> fieldconstraint -> Ppx_deriving_runtime.unit
val show_fieldconstraint : fieldconstraint -> Ppx_deriving_runtime.string
module Datatype : sig ... end
type datatype' = Datatype.with_pos * Types.datatype option
val pp_datatype' : Ppx_deriving_runtime.Format.formatter -> datatype' -> Ppx_deriving_runtime.unit
val show_datatype' : datatype' -> Ppx_deriving_runtime.string
type type_arg' = Datatype.type_arg * Types.type_arg option
val pp_type_arg' : Ppx_deriving_runtime.Format.formatter -> type_arg' -> Ppx_deriving_runtime.unit
val show_type_arg' : type_arg' -> Ppx_deriving_runtime.string
module Pattern : sig ... end
module Alien : sig ... end
type spawn_kind =
  1. | Angel
  2. | Demon
  3. | Wait
val pp_spawn_kind : Ppx_deriving_runtime.Format.formatter -> spawn_kind -> Ppx_deriving_runtime.unit
val show_spawn_kind : spawn_kind -> Ppx_deriving_runtime.string
type fn_dep = string * string
val pp_fn_dep : Ppx_deriving_runtime.Format.formatter -> fn_dep -> Ppx_deriving_runtime.unit
val show_fn_dep : fn_dep -> Ppx_deriving_runtime.string
type handler_depth =
  1. | Deep
  2. | Shallow
val pp_handler_depth : Ppx_deriving_runtime.Format.formatter -> handler_depth -> Ppx_deriving_runtime.unit
val show_handler_depth : handler_depth -> Ppx_deriving_runtime.string
type replace_rhs =
  1. | Literal of string
  2. | SpliceExpr of phrase
and given_spawn_location =
  1. | ExplicitSpawnLocation of phrase
  2. | SpawnClient
  3. | NoSpawnLocation
and regex =
  1. | Range of char * char
  2. | Simply of string
  3. | Quote of regex
  4. | Any
  5. | StartAnchor
  6. | EndAnchor
  7. | Seq of regex list
  8. | Alternate of regex * regex
  9. | Group of regex
  10. | Repeat of Regex.repeat * regex
  11. | Splice of phrase
  12. | Replace of regex * replace_rhs
and clause = Pattern.with_pos * phrase
and funlit =
  1. | NormalFunlit of normal_funlit
  2. | SwitchFunlit of switch_funlit
and switch_funlit = Pattern.with_pos list list * switch_funlit_body
and switch_funlit_body = (Pattern.with_pos * phrase) list
and normal_funlit = Pattern.with_pos list list * phrase
and handler = {
  1. sh_expr : phrase;
  2. sh_effect_cases : clause list;
  3. sh_value_cases : clause list;
  4. sh_descr : handler_descriptor;
}
and handler_descriptor = {
  1. shd_depth : handler_depth;
  2. shd_types : Types.row * Types.datatype * Types.row * Types.datatype;
  3. shd_raw_row : Types.row;
  4. shd_params : handler_parameterisation option;
}
and handler_parameterisation = {
  1. shp_bindings : (Pattern.with_pos * phrase) list;
  2. shp_types : Types.datatype list;
}
and iterpatt =
  1. | List of Pattern.with_pos * phrase
  2. | Table of Pattern.with_pos * phrase
and phrasenode =
  1. | Constant of CommonTypes.Constant.t
  2. | Var of CommonTypes.Name.t
  3. | FreezeVar of CommonTypes.Name.t
  4. | QualifiedVar of CommonTypes.Name.t list
  5. | FunLit of (Types.datatype * Types.row) list option * CommonTypes.DeclaredLinearity.t * funlit * CommonTypes.Location.t
  6. | Spawn of spawn_kind * given_spawn_location * phrase * Types.row option
  7. | Query of (phrase * phrase) option * CommonTypes.QueryPolicy.t * phrase * Types.datatype option
  8. | RangeLit of phrase * phrase
  9. | ListLit of phrase list * Types.datatype option
  10. | Iteration of iterpatt list * phrase * phrase option * phrase option
  11. | Escape of Binder.with_pos * phrase
  12. | Section of Operators.Section.t
  13. | FreezeSection of Operators.Section.t
  14. | Conditional of phrase * phrase * phrase
  15. | Block of block_body
  16. | InfixAppl of tyarg list * Operators.BinaryOp.t * phrase * phrase
  17. | Regex of regex
  18. | UnaryAppl of tyarg list * Operators.UnaryOp.t * phrase
  19. | FnAppl of phrase * phrase list
  20. | TAbstr of SugarQuantifier.t list * phrase
  21. | TAppl of phrase * type_arg' list
  22. | TupleLit of phrase list
  23. | RecordLit of (CommonTypes.Name.t * phrase) list * phrase option
  24. | Projection of phrase * CommonTypes.Name.t
  25. | With of phrase * (CommonTypes.Name.t * phrase) list
  26. | TypeAnnotation of phrase * datatype'
  27. | Upcast of phrase * datatype' * datatype'
  28. | Instantiate of phrase
  29. | Generalise of phrase
  30. | ConstructorLit of CommonTypes.Name.t * phrase option * Types.datatype option
  31. | DoOperation of CommonTypes.Name.t * phrase list * Types.datatype option
  32. | Handle of handler
  33. | Switch of phrase * (Pattern.with_pos * phrase) list * Types.datatype option
  34. | Receive of (Pattern.with_pos * phrase) list * Types.datatype option
  35. | DatabaseLit of phrase * phrase option * phrase option
  36. | TableLit of phrase * Datatype.with_pos * (Types.datatype * Types.datatype * Types.datatype) option * (CommonTypes.Name.t * fieldconstraint list) list * phrase * phrase
  37. | DBDelete of Pattern.with_pos * phrase * phrase option
  38. | DBInsert of phrase * CommonTypes.Name.t list * phrase * phrase option
  39. | DBUpdate of Pattern.with_pos * phrase * phrase option * (CommonTypes.Name.t * phrase) list
  40. | LensLit of phrase * Links_core.Lens.Type.t option
  41. | LensSerialLit of phrase * string list * Links_core.Lens.Type.t option
  42. | LensKeysLit of phrase * phrase * Links_core.Lens.Type.t option
  43. | LensFunDepsLit of phrase * (string list * string list) list * Links_core.Lens.Type.t option
  44. | LensDropLit of phrase * string * string * phrase * Links_core.Lens.Type.t option
  45. | LensSelectLit of phrase * phrase * Links_core.Lens.Type.t option
  46. | LensJoinLit of phrase * phrase * phrase * phrase * phrase * Links_core.Lens.Type.t option
  47. | LensGetLit of phrase * Types.datatype option
  48. | LensCheckLit of phrase * Links_core.Lens.Type.t option
  49. | LensPutLit of phrase * phrase * Types.datatype option
  50. | Xml of CommonTypes.Name.t * (CommonTypes.Name.t * phrase list) list * phrase option * phrase list
  51. | TextNode of string
  52. | Formlet of phrase * phrase
  53. | Page of phrase
  54. | FormletPlacement of phrase * phrase * phrase
  55. | PagePlacement of phrase
  56. | FormBinding of phrase * Pattern.with_pos
  57. | Select of CommonTypes.Name.t * phrase
  58. | Offer of phrase * (Pattern.with_pos * phrase) list * Types.datatype option
  59. | CP of cp_phrase
  60. | TryInOtherwise of phrase * Pattern.with_pos * phrase * phrase * Types.datatype option
  61. | Raise
and bindingnode =
  1. | Val of Pattern.with_pos * SugarQuantifier.t list * phrase * CommonTypes.Location.t * datatype' option
  2. | Fun of function_definition
  3. | Funs of recursive_function list
  4. | Foreign of Alien.single Alien.t
  5. | Import of {
    1. pollute : bool;
    2. path : CommonTypes.Name.t list;
    }
  6. | Open of CommonTypes.Name.t list
  7. | Typenames of typename list
  8. | Infix of {
    1. assoc : Operators.Associativity.t;
    2. precedence : int;
    3. name : string;
    }
  9. | Exp of phrase
  10. | Module of {
    1. binder : Binder.with_pos;
    2. members : binding list;
    }
  11. | AlienBlock of Alien.multi Alien.t
and block_body = binding list * phrase
and cp_phrasenode =
  1. | CPUnquote of binding list * phrase
  2. | CPGrab of string * (Types.datatype * tyarg list) option * Binder.with_pos option * cp_phrase
  3. | CPGive of string * (Types.datatype * tyarg list) option * phrase option * cp_phrase
  4. | CPGiveNothing of Binder.with_pos
  5. | CPSelect of Binder.with_pos * string * cp_phrase
  6. | CPOffer of Binder.with_pos * (string * cp_phrase) list
  7. | CPComp of Binder.with_pos * cp_phrase * cp_phrase
and typenamenode = CommonTypes.Name.t * SugarQuantifier.t list * datatype'
and function_definition = {
  1. fun_binder : Binder.with_pos;
  2. fun_linearity : CommonTypes.DeclaredLinearity.t;
  3. fun_definition : SugarQuantifier.t list * funlit;
  4. fun_location : CommonTypes.Location.t;
  5. fun_signature : datatype' option;
  6. fun_unsafe_signature : bool;
  7. fun_frozen : bool;
}
and recursive_functionnode = {
  1. rec_binder : Binder.with_pos;
  2. rec_linearity : CommonTypes.DeclaredLinearity.t;
  3. rec_definition : (SugarQuantifier.t list * (Types.datatype * int option list) option) * funlit;
  4. rec_location : CommonTypes.Location.t;
  5. rec_signature : datatype' option;
  6. rec_unsafe_signature : bool;
  7. rec_frozen : bool;
}
val pp_replace_rhs : Ppx_deriving_runtime.Format.formatter -> replace_rhs -> Ppx_deriving_runtime.unit
val show_replace_rhs : replace_rhs -> Ppx_deriving_runtime.string
val pp_given_spawn_location : Ppx_deriving_runtime.Format.formatter -> given_spawn_location -> Ppx_deriving_runtime.unit
val show_given_spawn_location : given_spawn_location -> Ppx_deriving_runtime.string
val pp_regex : Ppx_deriving_runtime.Format.formatter -> regex -> Ppx_deriving_runtime.unit
val pp_clause : Ppx_deriving_runtime.Format.formatter -> clause -> Ppx_deriving_runtime.unit
val show_clause : clause -> Ppx_deriving_runtime.string
val pp_funlit : Ppx_deriving_runtime.Format.formatter -> funlit -> Ppx_deriving_runtime.unit
val show_funlit : funlit -> Ppx_deriving_runtime.string
val pp_switch_funlit : Ppx_deriving_runtime.Format.formatter -> switch_funlit -> Ppx_deriving_runtime.unit
val show_switch_funlit : switch_funlit -> Ppx_deriving_runtime.string
val pp_switch_funlit_body : Ppx_deriving_runtime.Format.formatter -> switch_funlit_body -> Ppx_deriving_runtime.unit
val show_switch_funlit_body : switch_funlit_body -> Ppx_deriving_runtime.string
val pp_normal_funlit : Ppx_deriving_runtime.Format.formatter -> normal_funlit -> Ppx_deriving_runtime.unit
val show_normal_funlit : normal_funlit -> Ppx_deriving_runtime.string
val pp_handler : Ppx_deriving_runtime.Format.formatter -> handler -> Ppx_deriving_runtime.unit
val show_handler : handler -> Ppx_deriving_runtime.string
val pp_handler_descriptor : Ppx_deriving_runtime.Format.formatter -> handler_descriptor -> Ppx_deriving_runtime.unit
val show_handler_descriptor : handler_descriptor -> Ppx_deriving_runtime.string
val pp_handler_parameterisation : Ppx_deriving_runtime.Format.formatter -> handler_parameterisation -> Ppx_deriving_runtime.unit
val show_handler_parameterisation : handler_parameterisation -> Ppx_deriving_runtime.string
val pp_iterpatt : Ppx_deriving_runtime.Format.formatter -> iterpatt -> Ppx_deriving_runtime.unit
val show_iterpatt : iterpatt -> Ppx_deriving_runtime.string
val pp_phrasenode : Ppx_deriving_runtime.Format.formatter -> phrasenode -> Ppx_deriving_runtime.unit
val show_phrasenode : phrasenode -> Ppx_deriving_runtime.string
val pp_phrase : Ppx_deriving_runtime.Format.formatter -> phrase -> Ppx_deriving_runtime.unit
val show_phrase : phrase -> Ppx_deriving_runtime.string
val pp_bindingnode : Ppx_deriving_runtime.Format.formatter -> bindingnode -> Ppx_deriving_runtime.unit
val show_bindingnode : bindingnode -> Ppx_deriving_runtime.string
val pp_binding : Ppx_deriving_runtime.Format.formatter -> binding -> Ppx_deriving_runtime.unit
val show_binding : binding -> Ppx_deriving_runtime.string
val pp_block_body : Ppx_deriving_runtime.Format.formatter -> block_body -> Ppx_deriving_runtime.unit
val show_block_body : block_body -> Ppx_deriving_runtime.string
val pp_cp_phrasenode : Ppx_deriving_runtime.Format.formatter -> cp_phrasenode -> Ppx_deriving_runtime.unit
val show_cp_phrasenode : cp_phrasenode -> Ppx_deriving_runtime.string
val pp_cp_phrase : Ppx_deriving_runtime.Format.formatter -> cp_phrase -> Ppx_deriving_runtime.unit
val show_cp_phrase : cp_phrase -> Ppx_deriving_runtime.string
val pp_typenamenode : Ppx_deriving_runtime.Format.formatter -> typenamenode -> Ppx_deriving_runtime.unit
val show_typenamenode : typenamenode -> Ppx_deriving_runtime.string
val pp_typename : Ppx_deriving_runtime.Format.formatter -> typename -> Ppx_deriving_runtime.unit
val show_typename : typename -> Ppx_deriving_runtime.string
val pp_function_definition : Ppx_deriving_runtime.Format.formatter -> function_definition -> Ppx_deriving_runtime.unit
val show_function_definition : function_definition -> Ppx_deriving_runtime.string
val pp_recursive_functionnode : Ppx_deriving_runtime.Format.formatter -> recursive_functionnode -> Ppx_deriving_runtime.unit
val show_recursive_functionnode : recursive_functionnode -> Ppx_deriving_runtime.string
val pp_recursive_function : Ppx_deriving_runtime.Format.formatter -> recursive_function -> Ppx_deriving_runtime.unit
val show_recursive_function : recursive_function -> Ppx_deriving_runtime.string
type directive = string * string list
val pp_directive : Ppx_deriving_runtime.Format.formatter -> directive -> Ppx_deriving_runtime.unit
val show_directive : directive -> Ppx_deriving_runtime.string
type sentence =
  1. | Definitions of binding list
  2. | Expression of phrase
  3. | Directive of directive
val pp_sentence : Ppx_deriving_runtime.Format.formatter -> sentence -> Ppx_deriving_runtime.unit
val show_sentence : sentence -> Ppx_deriving_runtime.string
type program = binding list * phrase option
val pp_program : Ppx_deriving_runtime.Format.formatter -> program -> Ppx_deriving_runtime.unit
val show_program : program -> Ppx_deriving_runtime.string
exception ConcreteSyntaxError of SourceCode.Position.t * string
val tabstr : (SugarQuantifier.t list * phrasenode) -> phrasenode
val tappl : (phrasenode * tyarg list) -> phrasenode
val tappl' : (phrase * tyarg list) -> phrasenode
val get_normal_funlit : funlit -> normal_funlit
module Freevars : sig ... end
OCaml

Innovation. Community. Security.