sig
module SI :
sig
type elt = Ident.t
type t
val empty : t
val is_empty : t -> bool
val mem : elt -> t -> bool
val add : elt -> t -> t
val singleton : elt -> t
val remove : elt -> t -> t
val union : t -> t -> t
val inter : t -> t -> t
val diff : t -> t -> t
val compare : t -> t -> int
val equal : t -> t -> bool
val subset : t -> t -> bool
val iter : (elt -> unit) -> t -> unit
val map : (elt -> elt) -> t -> t
val fold : (elt -> 'a -> 'a) -> t -> 'a -> 'a
val for_all : (elt -> bool) -> t -> bool
val exists : (elt -> bool) -> t -> bool
val filter : (elt -> bool) -> t -> t
val partition : (elt -> bool) -> t -> t * t
val cardinal : t -> int
val elements : t -> elt list
val min_elt : t -> elt
val max_elt : t -> elt
val choose : t -> elt
val split : elt -> t -> t * bool * t
val find : elt -> t -> elt
val of_list : elt list -> t
end
exception Parser_error
type ident = string
type index = string
type clock_expr =
ClockTrue
| ClockPos of LustreAst.ident
| ClockNeg of LustreAst.ident
| ClockConstr of LustreAst.ident * LustreAst.ident
type expr =
Ident of Lib.position * LustreAst.ident
| ModeRef of Lib.position * LustreAst.ident list
| RecordProject of Lib.position * LustreAst.expr * LustreAst.index
| TupleProject of Lib.position * LustreAst.expr * LustreAst.expr
| StructUpdate of Lib.position * LustreAst.expr *
LustreAst.label_or_index list * LustreAst.expr
| True of Lib.position
| False of Lib.position
| Num of Lib.position * string
| Dec of Lib.position * string
| ToInt of Lib.position * LustreAst.expr
| ToReal of Lib.position * LustreAst.expr
| ExprList of Lib.position * LustreAst.expr list
| TupleExpr of Lib.position * LustreAst.expr list
| ArrayExpr of Lib.position * LustreAst.expr list
| ArrayConstr of Lib.position * LustreAst.expr * LustreAst.expr
| ArraySlice of Lib.position * LustreAst.expr *
(LustreAst.expr * LustreAst.expr)
| ArrayConcat of Lib.position * LustreAst.expr * LustreAst.expr
| RecordExpr of Lib.position * LustreAst.ident *
(LustreAst.ident * LustreAst.expr) list
| Not of Lib.position * LustreAst.expr
| And of Lib.position * LustreAst.expr * LustreAst.expr
| Or of Lib.position * LustreAst.expr * LustreAst.expr
| Xor of Lib.position * LustreAst.expr * LustreAst.expr
| Impl of Lib.position * LustreAst.expr * LustreAst.expr
| Forall of Lib.position * LustreAst.typed_ident list * LustreAst.expr
| Exists of Lib.position * LustreAst.typed_ident list * LustreAst.expr
| OneHot of Lib.position * LustreAst.expr list
| Uminus of Lib.position * LustreAst.expr
| Mod of Lib.position * LustreAst.expr * LustreAst.expr
| Minus of Lib.position * LustreAst.expr * LustreAst.expr
| Plus of Lib.position * LustreAst.expr * LustreAst.expr
| Div of Lib.position * LustreAst.expr * LustreAst.expr
| Times of Lib.position * LustreAst.expr * LustreAst.expr
| IntDiv of Lib.position * LustreAst.expr * LustreAst.expr
| Ite of Lib.position * LustreAst.expr * LustreAst.expr * LustreAst.expr
| With of Lib.position * LustreAst.expr * LustreAst.expr * LustreAst.expr
| Eq of Lib.position * LustreAst.expr * LustreAst.expr
| Neq of Lib.position * LustreAst.expr * LustreAst.expr
| Lte of Lib.position * LustreAst.expr * LustreAst.expr
| Lt of Lib.position * LustreAst.expr * LustreAst.expr
| Gte of Lib.position * LustreAst.expr * LustreAst.expr
| Gt of Lib.position * LustreAst.expr * LustreAst.expr
| When of Lib.position * LustreAst.expr * LustreAst.clock_expr
| Current of Lib.position * LustreAst.expr
| Condact of Lib.position * LustreAst.expr * LustreAst.expr *
LustreAst.ident * LustreAst.expr list * LustreAst.expr list
| Activate of Lib.position * LustreAst.ident * LustreAst.expr *
LustreAst.expr * LustreAst.expr list
| Merge of Lib.position * LustreAst.ident *
(LustreAst.ident * LustreAst.expr) list
| RestartEvery of Lib.position * LustreAst.ident * LustreAst.expr list *
LustreAst.expr
| Pre of Lib.position * LustreAst.expr
| Last of Lib.position * LustreAst.ident
| Fby of Lib.position * LustreAst.expr * int * LustreAst.expr
| Arrow of Lib.position * LustreAst.expr * LustreAst.expr
| Call of Lib.position * LustreAst.ident * LustreAst.expr list
| CallParam of Lib.position * LustreAst.ident *
LustreAst.lustre_type list * LustreAst.expr list
and lustre_type =
Bool of Lib.position
| Int of Lib.position
| IntRange of Lib.position * LustreAst.expr * LustreAst.expr
| Real of Lib.position
| UserType of Lib.position * LustreAst.ident
| TupleType of Lib.position * LustreAst.lustre_type list
| RecordType of Lib.position * LustreAst.typed_ident list
| ArrayType of Lib.position * (LustreAst.lustre_type * LustreAst.expr)
| EnumType of Lib.position * LustreAst.ident option *
LustreAst.ident list
and typed_ident = Lib.position * LustreAst.ident * LustreAst.lustre_type
and label_or_index =
Label of Lib.position * LustreAst.index
| Index of Lib.position * LustreAst.expr
type type_decl =
AliasType of Lib.position * LustreAst.ident * LustreAst.lustre_type
| FreeType of Lib.position * LustreAst.ident
type clocked_typed_decl =
Lib.position * LustreAst.ident * LustreAst.lustre_type *
LustreAst.clock_expr
type const_clocked_typed_decl =
Lib.position * LustreAst.ident * LustreAst.lustre_type *
LustreAst.clock_expr * bool
type const_decl =
FreeConst of Lib.position * LustreAst.ident * LustreAst.lustre_type
| UntypedConst of Lib.position * LustreAst.ident * LustreAst.expr
| TypedConst of Lib.position * LustreAst.ident * LustreAst.expr *
LustreAst.lustre_type
type node_param = TypeParam of LustreAst.ident
type node_local_decl =
NodeConstDecl of Lib.position * LustreAst.const_decl
| NodeVarDecl of Lib.position * LustreAst.clocked_typed_decl
type struct_item =
SingleIdent of Lib.position * LustreAst.ident
| TupleStructItem of Lib.position * LustreAst.struct_item list
| TupleSelection of Lib.position * LustreAst.ident * LustreAst.expr
| FieldSelection of Lib.position * LustreAst.ident * LustreAst.ident
| ArraySliceStructItem of Lib.position * LustreAst.ident *
(LustreAst.expr * LustreAst.expr) list
| ArrayDef of Lib.position * LustreAst.ident * LustreAst.ident list
type eq_lhs = StructDef of Lib.position * LustreAst.struct_item list
type transition_to =
TransRestart of Lib.position * (Lib.position * LustreAst.ident)
| TransResume of Lib.position * (Lib.position * LustreAst.ident)
type transition_branch =
Target of LustreAst.transition_to
| TransIf of Lib.position * LustreAst.expr *
LustreAst.transition_branch * LustreAst.transition_branch option
type automaton_transition = Lib.position * LustreAst.transition_branch
type auto_returns = Given of LustreAst.ident list | Inferred
type node_equation =
Assert of Lib.position * LustreAst.expr
| Equation of Lib.position * LustreAst.eq_lhs * LustreAst.expr
| Automaton of Lib.position * LustreAst.ident option *
LustreAst.state list * LustreAst.auto_returns
and state =
State of Lib.position * LustreAst.ident * bool *
LustreAst.node_local_decl list * LustreAst.node_equation list *
LustreAst.automaton_transition option *
LustreAst.automaton_transition option
type node_item =
Body of LustreAst.node_equation
| AnnotMain of bool
| AnnotProperty of Lib.position * string option * LustreAst.expr
type contract_ghost_const = LustreAst.const_decl
type contract_ghost_var = LustreAst.const_decl
type contract_assume = Lib.position * string option * LustreAst.expr
type contract_guarantee = Lib.position * string option * LustreAst.expr
type contract_require = Lib.position * string option * LustreAst.expr
type contract_ensure = Lib.position * string option * LustreAst.expr
type contract_mode =
Lib.position * LustreAst.ident * LustreAst.contract_require list *
LustreAst.contract_ensure list
type contract_call =
Lib.position * LustreAst.ident * LustreAst.expr list *
LustreAst.expr list
type contract_node_equation =
GhostConst of LustreAst.contract_ghost_const
| GhostVar of LustreAst.contract_ghost_var
| Assume of LustreAst.contract_assume
| Guarantee of LustreAst.contract_guarantee
| Mode of LustreAst.contract_mode
| ContractCall of LustreAst.contract_call
type contract = LustreAst.contract_node_equation list
type node_decl =
LustreAst.ident * bool * LustreAst.node_param list *
LustreAst.const_clocked_typed_decl list *
LustreAst.clocked_typed_decl list * LustreAst.node_local_decl list *
LustreAst.node_item list * LustreAst.contract option
type contract_node_decl =
LustreAst.ident * LustreAst.node_param list *
LustreAst.const_clocked_typed_decl list *
LustreAst.clocked_typed_decl list * LustreAst.contract
type node_param_inst =
LustreAst.ident * LustreAst.ident * LustreAst.lustre_type list
type declaration =
TypeDecl of Lib.position * LustreAst.type_decl
| ConstDecl of Lib.position * LustreAst.const_decl
| NodeDecl of Lib.position * LustreAst.node_decl
| FuncDecl of Lib.position * LustreAst.node_decl
| ContractNodeDecl of Lib.position * LustreAst.contract_node_decl
| NodeParamInst of Lib.position * LustreAst.node_param_inst
type t = LustreAst.declaration list
val pp_print_node_param_list :
Format.formatter -> LustreAst.node_param list -> unit
val pp_print_ident : Format.formatter -> LustreAst.ident -> unit
val pp_print_expr : Format.formatter -> LustreAst.expr -> unit
val pp_print_array_slice :
Format.formatter -> LustreAst.expr * LustreAst.expr -> unit
val pp_print_field_assign :
Format.formatter -> LustreAst.ident * LustreAst.expr -> unit
val pp_print_clock_expr : Format.formatter -> LustreAst.clock_expr -> unit
val pp_print_lustre_type :
Format.formatter -> LustreAst.lustre_type -> unit
val pp_print_typed_ident :
Format.formatter -> LustreAst.typed_ident -> unit
val pp_print_clocked_typed_ident :
Format.formatter ->
Lib.position * LustreAst.ident * LustreAst.lustre_type *
LustreAst.clock_expr -> unit
val pp_print_const_clocked_typed_ident :
Format.formatter ->
Lib.position * LustreAst.ident * LustreAst.lustre_type *
LustreAst.clock_expr * bool -> unit
val pp_print_type_decl : Format.formatter -> LustreAst.type_decl -> unit
val pp_print_var_decl :
Format.formatter ->
Lib.position * LustreAst.ident * LustreAst.lustre_type *
LustreAst.clock_expr -> unit
val pp_print_const_decl : Format.formatter -> LustreAst.const_decl -> unit
val pp_print_node_local_decl_var :
Format.formatter -> LustreAst.node_local_decl -> unit
val pp_print_node_local_decl_const :
Format.formatter -> LustreAst.node_local_decl -> unit
val pp_print_node_local_decl :
Format.formatter -> LustreAst.node_local_decl list -> unit
val pp_print_struct_item :
Format.formatter -> LustreAst.struct_item -> unit
val pp_print_node_item : Format.formatter -> LustreAst.node_item -> unit
val pp_print_declaration :
Format.formatter -> LustreAst.declaration -> unit
val pp_print_program : Format.formatter -> LustreAst.t -> unit
val pp_print_contract_item :
Format.formatter -> LustreAst.contract_node_equation -> unit
val pp_print_contract_node :
Format.formatter -> LustreAst.contract_node_decl -> unit
val pos_of_expr : LustreAst.expr -> Lib.position
val has_unguarded_pre : LustreAst.expr -> bool
val has_pre_or_arrow : LustreAst.expr -> Lib.position option
val contract_has_pre_or_arrow : LustreAst.contract -> Lib.position option
val node_local_decl_has_pre_or_arrow :
LustreAst.node_local_decl -> Lib.position option
val node_item_has_pre_or_arrow : LustreAst.node_item -> Lib.position option
val replace_lasts :
string list ->
string ->
LustreAst.SI.t -> LustreAst.expr -> LustreAst.expr * LustreAst.SI.t
end