Add some .mli files

Generated: these would need cleanup, formatting, insertion of the doc
comments, and removal of non-shared values.
This commit is contained in:
Louis Gesbert 2021-02-11 18:48:59 +01:00
parent edd94dcc0e
commit 70f4e46dcc
29 changed files with 15423 additions and 0 deletions

288
src/catala/dcalc/ast.mli Normal file
View File

@ -0,0 +1,288 @@
module ScopeName :
sig
type t
type info = Utils.Uid.MarkedString.info
val fresh : info -> t
val get_info : t -> info
val compare : t -> t -> int
val format_t : Format.formatter -> t -> unit
val hash : t -> int
end
module StructName :
sig
type t
type info = Utils.Uid.MarkedString.info
val fresh : info -> t
val get_info : t -> info
val compare : t -> t -> int
val format_t : Format.formatter -> t -> unit
val hash : t -> int
end
module StructFieldName :
sig
type t
type info = Utils.Uid.MarkedString.info
val fresh : info -> t
val get_info : t -> info
val compare : t -> t -> int
val format_t : Format.formatter -> t -> unit
val hash : t -> int
end
module StructMap :
sig
type key = StructName.t
type +'a t
val empty : 'a t
val is_empty : 'a t -> bool
val mem : key -> 'a t -> bool
val add : key -> 'a -> 'a t -> 'a t
val update : key -> ('a option -> 'a option) -> 'a t -> 'a t
val singleton : key -> 'a -> 'a t
val remove : key -> 'a t -> 'a t
val merge :
(key -> 'a option -> 'b option -> 'c option) -> 'a t -> 'b t -> 'c t
val union : (key -> 'a -> 'a -> 'a option) -> 'a t -> 'a t -> 'a t
val compare : ('a -> 'a -> int) -> 'a t -> 'a t -> int
val equal : ('a -> 'a -> bool) -> 'a t -> 'a t -> bool
val iter : (key -> 'a -> unit) -> 'a t -> unit
val fold : (key -> 'a -> 'b -> 'b) -> 'a t -> 'b -> 'b
val for_all : (key -> 'a -> bool) -> 'a t -> bool
val exists : (key -> 'a -> bool) -> 'a t -> bool
val filter : (key -> 'a -> bool) -> 'a t -> 'a t
val filter_map : (key -> 'a -> 'b option) -> 'a t -> 'b t
val partition : (key -> 'a -> bool) -> 'a t -> 'a t * 'a t
val cardinal : 'a t -> int
val bindings : 'a t -> (key * 'a) list
val min_binding : 'a t -> key * 'a
val min_binding_opt : 'a t -> (key * 'a) option
val max_binding : 'a t -> key * 'a
val max_binding_opt : 'a t -> (key * 'a) option
val choose : 'a t -> key * 'a
val choose_opt : 'a t -> (key * 'a) option
val split : key -> 'a t -> 'a t * 'a option * 'a t
val find : key -> 'a t -> 'a
val find_opt : key -> 'a t -> 'a option
val find_first : (key -> bool) -> 'a t -> key * 'a
val find_first_opt : (key -> bool) -> 'a t -> (key * 'a) option
val find_last : (key -> bool) -> 'a t -> key * 'a
val find_last_opt : (key -> bool) -> 'a t -> (key * 'a) option
val map : ('a -> 'b) -> 'a t -> 'b t
val mapi : (key -> 'a -> 'b) -> 'a t -> 'b t
val to_seq : 'a t -> (key * 'a) Seq.t
val to_seq_from : key -> 'a t -> (key * 'a) Seq.t
val add_seq : (key * 'a) Seq.t -> 'a t -> 'a t
val of_seq : (key * 'a) Seq.t -> 'a t
end
module EnumName :
sig
type t
type info = Utils.Uid.MarkedString.info
val fresh : info -> t
val get_info : t -> info
val compare : t -> t -> int
val format_t : Format.formatter -> t -> unit
val hash : t -> int
end
module EnumConstructor :
sig
type t
type info = Utils.Uid.MarkedString.info
val fresh : info -> t
val get_info : t -> info
val compare : t -> t -> int
val format_t : Format.formatter -> t -> unit
val hash : t -> int
end
module EnumMap :
sig
type key = EnumName.t
type +'a t
val empty : 'a t
val is_empty : 'a t -> bool
val mem : key -> 'a t -> bool
val add : key -> 'a -> 'a t -> 'a t
val update : key -> ('a option -> 'a option) -> 'a t -> 'a t
val singleton : key -> 'a -> 'a t
val remove : key -> 'a t -> 'a t
val merge :
(key -> 'a option -> 'b option -> 'c option) -> 'a t -> 'b t -> 'c t
val union : (key -> 'a -> 'a -> 'a option) -> 'a t -> 'a t -> 'a t
val compare : ('a -> 'a -> int) -> 'a t -> 'a t -> int
val equal : ('a -> 'a -> bool) -> 'a t -> 'a t -> bool
val iter : (key -> 'a -> unit) -> 'a t -> unit
val fold : (key -> 'a -> 'b -> 'b) -> 'a t -> 'b -> 'b
val for_all : (key -> 'a -> bool) -> 'a t -> bool
val exists : (key -> 'a -> bool) -> 'a t -> bool
val filter : (key -> 'a -> bool) -> 'a t -> 'a t
val filter_map : (key -> 'a -> 'b option) -> 'a t -> 'b t
val partition : (key -> 'a -> bool) -> 'a t -> 'a t * 'a t
val cardinal : 'a t -> int
val bindings : 'a t -> (key * 'a) list
val min_binding : 'a t -> key * 'a
val min_binding_opt : 'a t -> (key * 'a) option
val max_binding : 'a t -> key * 'a
val max_binding_opt : 'a t -> (key * 'a) option
val choose : 'a t -> key * 'a
val choose_opt : 'a t -> (key * 'a) option
val split : key -> 'a t -> 'a t * 'a option * 'a t
val find : key -> 'a t -> 'a
val find_opt : key -> 'a t -> 'a option
val find_first : (key -> bool) -> 'a t -> key * 'a
val find_first_opt : (key -> bool) -> 'a t -> (key * 'a) option
val find_last : (key -> bool) -> 'a t -> key * 'a
val find_last_opt : (key -> bool) -> 'a t -> (key * 'a) option
val map : ('a -> 'b) -> 'a t -> 'b t
val mapi : (key -> 'a -> 'b) -> 'a t -> 'b t
val to_seq : 'a t -> (key * 'a) Seq.t
val to_seq_from : key -> 'a t -> (key * 'a) Seq.t
val add_seq : (key * 'a) Seq.t -> 'a t -> 'a t
val of_seq : (key * 'a) Seq.t -> 'a t
end
type typ_lit = TBool | TUnit | TInt | TRat | TMoney | TDate | TDuration
type typ =
TLit of typ_lit
| TTuple of typ Utils.Pos.marked list * StructName.t option
| TEnum of typ Utils.Pos.marked list * EnumName.t
| TArrow of typ Utils.Pos.marked * typ Utils.Pos.marked
| TArray of typ Utils.Pos.marked
| TAny
type date = CalendarLib.Date.t
type duration = CalendarLib.Date.Period.t
type lit =
LBool of bool
| LEmptyError
| LInt of Z.t
| LRat of Q.t
| LMoney of Z.t
| LUnit
| LDate of date
| LDuration of duration
type op_kind = KInt | KRat | KMoney | KDate | KDuration
type ternop = Fold
type binop =
And
| Or
| Add of op_kind
| Sub of op_kind
| Mult of op_kind
| Div of op_kind
| Lt of op_kind
| Lte of op_kind
| Gt of op_kind
| Gte of op_kind
| Eq
| Neq
| Map
| Filter
type log_entry = VarDef | BeginCall | EndCall | PosRecordIfTrueBool
type unop =
Not
| Minus of op_kind
| ErrorOnEmpty
| Log of log_entry * Utils.Uid.MarkedString.info list
| Length
| IntToRat
| GetDay
| GetMonth
| GetYear
type operator = Ternop of ternop | Binop of binop | Unop of unop
type expr =
EVar of expr Bindlib.var Utils.Pos.marked
| ETuple of expr Utils.Pos.marked list * StructName.t option
| ETupleAccess of expr Utils.Pos.marked * int * StructName.t option *
typ Utils.Pos.marked list
| EInj of expr Utils.Pos.marked * int * EnumName.t *
typ Utils.Pos.marked list
| EMatch of expr Utils.Pos.marked * expr Utils.Pos.marked list * EnumName.t
| EArray of expr Utils.Pos.marked list
| ELit of lit
| EAbs of Utils.Pos.t * (expr, expr Utils.Pos.marked) Bindlib.mbinder *
typ Utils.Pos.marked list
| EApp of expr Utils.Pos.marked * expr Utils.Pos.marked list
| EAssert of expr Utils.Pos.marked
| EOp of operator
| EDefault of expr Utils.Pos.marked list * expr Utils.Pos.marked *
expr Utils.Pos.marked
| EIfThenElse of expr Utils.Pos.marked * expr Utils.Pos.marked *
expr Utils.Pos.marked
type struct_ctx = (StructFieldName.t * typ Utils.Pos.marked) list StructMap.t
type enum_ctx = (EnumConstructor.t * typ Utils.Pos.marked) list EnumMap.t
type decl_ctx = { ctx_enums : enum_ctx; ctx_structs : struct_ctx; }
module Var :
sig
type t = expr Bindlib.var
val make : string Utils.Pos.marked -> t
val compare : 'a Bindlib.var -> 'b Bindlib.var -> int
end
module VarMap :
sig
type key = Var.t
type 'a t = 'a Stdlib__map.Make(Var).t
val empty : 'a t
val is_empty : 'a t -> bool
val mem : key -> 'a t -> bool
val add : key -> 'a -> 'a t -> 'a t
val update : key -> ('a option -> 'a option) -> 'a t -> 'a t
val singleton : key -> 'a -> 'a t
val remove : key -> 'a t -> 'a t
val merge :
(key -> 'a option -> 'b option -> 'c option) -> 'a t -> 'b t -> 'c t
val union : (key -> 'a -> 'a -> 'a option) -> 'a t -> 'a t -> 'a t
val compare : ('a -> 'a -> int) -> 'a t -> 'a t -> int
val equal : ('a -> 'a -> bool) -> 'a t -> 'a t -> bool
val iter : (key -> 'a -> unit) -> 'a t -> unit
val fold : (key -> 'a -> 'b -> 'b) -> 'a t -> 'b -> 'b
val for_all : (key -> 'a -> bool) -> 'a t -> bool
val exists : (key -> 'a -> bool) -> 'a t -> bool
val filter : (key -> 'a -> bool) -> 'a t -> 'a t
val filter_map : (key -> 'a -> 'b option) -> 'a t -> 'b t
val partition : (key -> 'a -> bool) -> 'a t -> 'a t * 'a t
val cardinal : 'a t -> int
val bindings : 'a t -> (key * 'a) list
val min_binding : 'a t -> key * 'a
val min_binding_opt : 'a t -> (key * 'a) option
val max_binding : 'a t -> key * 'a
val max_binding_opt : 'a t -> (key * 'a) option
val choose : 'a t -> key * 'a
val choose_opt : 'a t -> (key * 'a) option
val split : key -> 'a t -> 'a t * 'a option * 'a t
val find : key -> 'a t -> 'a
val find_opt : key -> 'a t -> 'a option
val find_first : (key -> bool) -> 'a t -> key * 'a
val find_first_opt : (key -> bool) -> 'a t -> (key * 'a) option
val find_last : (key -> bool) -> 'a t -> key * 'a
val find_last_opt : (key -> bool) -> 'a t -> (key * 'a) option
val map : ('a -> 'b) -> 'a t -> 'b t
val mapi : (key -> 'a -> 'b) -> 'a t -> 'b t
val to_seq : 'a t -> (key * 'a) Seq.t
val to_seq_from : key -> 'a t -> (key * 'a) Seq.t
val add_seq : (key * 'a) Seq.t -> 'a t -> 'a t
val of_seq : (key * 'a) Seq.t -> 'a t
end
type vars = expr Bindlib.mvar
val make_var : Var.t Utils.Pos.marked -> expr Utils.Pos.marked Bindlib.box
val make_abs :
vars ->
expr Utils.Pos.marked Bindlib.box ->
Utils.Pos.t ->
typ Utils.Pos.marked list ->
Utils.Pos.t -> expr Utils.Pos.marked Bindlib.box
val make_app :
expr Utils.Pos.marked Bindlib.box ->
expr Utils.Pos.marked Bindlib.box list ->
Utils.Pos.t -> expr Utils.Pos.marked Bindlib.box
val make_let_in :
Var.t ->
typ Utils.Pos.marked ->
expr Utils.Pos.marked Bindlib.box ->
expr Utils.Pos.marked Bindlib.box -> expr Utils.Pos.marked Bindlib.box
val make_multiple_let_in :
Var.t array ->
typ Utils.Pos.marked list ->
expr Utils.Pos.marked list Bindlib.box ->
expr Utils.Pos.marked Bindlib.box -> expr Utils.Pos.marked Bindlib.box
type binder = (expr, expr Utils.Pos.marked) Bindlib.binder
type program = {
decl_ctx : decl_ctx;
scopes : (Var.t * expr Utils.Pos.marked) list;
}

View File

@ -0,0 +1,18 @@
module A = Ast
val is_empty_error : A.expr Utils.Pos.marked -> bool
val empty_thunked_term : Ast.expr Utils.Pos.marked
val type_eq : A.typ Utils.Pos.marked -> A.typ Utils.Pos.marked -> bool
val log_indent : int ref
val compare_periods :
CalendarLib.Date.Period.t Utils.Pos.marked ->
CalendarLib.Date.Period.t Utils.Pos.marked -> int
val evaluate_operator :
Ast.decl_ctx ->
A.operator Utils.Pos.marked ->
A.expr Utils.Pos.marked list -> A.expr Utils.Pos.marked
val evaluate_expr :
Ast.decl_ctx -> A.expr Utils.Pos.marked -> A.expr Utils.Pos.marked
val interpret_program :
Ast.decl_ctx ->
Ast.expr Utils.Pos.marked ->
(Utils.Uid.MarkedString.info * Ast.expr Utils.Pos.marked) list

View File

@ -0,0 +1,22 @@
val typ_needs_parens : Ast.typ Utils.Pos.marked -> bool
val is_uppercase : CamomileLibraryDefault.Camomile.UChar.t -> bool
val begins_with_uppercase : string -> bool
val format_uid_list :
Format.formatter -> Utils.Uid.MarkedString.info list -> unit
val format_tlit : Format.formatter -> Ast.typ_lit -> unit
val format_typ :
Ast.decl_ctx ->
Format.formatter -> Ast.typ Utils.Pos.marked -> unit
val format_lit : Format.formatter -> Ast.lit Utils.Pos.marked -> unit
val format_op_kind : Format.formatter -> Ast.op_kind -> unit
val format_binop :
Format.formatter -> Ast.binop Utils.Pos.marked -> unit
val format_ternop :
Format.formatter -> Ast.ternop Utils.Pos.marked -> unit
val format_log_entry : Format.formatter -> Ast.log_entry -> unit
val format_unop : Format.formatter -> Ast.unop Utils.Pos.marked -> unit
val needs_parens : Ast.expr Utils.Pos.marked -> bool
val format_var : Format.formatter -> Ast.Var.t -> unit
val format_expr :
Ast.decl_ctx ->
Format.formatter -> Ast.expr Utils.Pos.marked -> unit

View File

@ -0,0 +1,46 @@
module A = Ast
module Any :
sig
type t
type info = unit
val fresh : info -> t
val get_info : t -> info
val compare : t -> t -> int
val format_t : Format.formatter -> t -> unit
val hash : t -> int
end
type typ =
TLit of A.typ_lit
| TArrow of typ Utils.Pos.marked UnionFind.elem *
typ Utils.Pos.marked UnionFind.elem
| TTuple of typ Utils.Pos.marked UnionFind.elem list *
Ast.StructName.t option
| TEnum of typ Utils.Pos.marked UnionFind.elem list * Ast.EnumName.t
| TArray of typ Utils.Pos.marked UnionFind.elem
| TAny of Any.t
val typ_needs_parens : typ Utils.Pos.marked UnionFind.elem -> bool
val format_typ :
Ast.decl_ctx ->
Format.formatter -> typ Utils.Pos.marked UnionFind.elem -> unit
val unify :
Ast.decl_ctx ->
typ Utils.Pos.marked UnionFind.elem ->
typ Utils.Pos.marked UnionFind.elem -> unit
val op_type :
A.operator Utils.Pos.marked -> typ Utils.Pos.marked UnionFind.elem
val ast_to_typ : A.typ -> typ
val typ_to_ast :
typ Utils.Pos.marked UnionFind.elem -> A.typ Utils.Pos.marked
type env = typ Utils.Pos.marked UnionFind.elem A.VarMap.t
val typecheck_expr_bottom_up :
Ast.decl_ctx ->
env -> A.expr Utils.Pos.marked -> typ Utils.Pos.marked UnionFind.elem
val typecheck_expr_top_down :
Ast.decl_ctx ->
env ->
A.expr Utils.Pos.marked -> typ Utils.Pos.marked UnionFind.elem -> unit
val infer_type :
Ast.decl_ctx -> A.expr Utils.Pos.marked -> A.typ Utils.Pos.marked
val check_type :
Ast.decl_ctx ->
A.expr Utils.Pos.marked -> A.typ Utils.Pos.marked -> unit

View File

@ -0,0 +1,281 @@
module IdentMap :
sig
type key = String.t
type +'a t
val empty : 'a t
val is_empty : 'a t -> bool
val mem : key -> 'a t -> bool
val add : key -> 'a -> 'a t -> 'a t
val update : key -> ('a option -> 'a option) -> 'a t -> 'a t
val singleton : key -> 'a -> 'a t
val remove : key -> 'a t -> 'a t
val merge :
(key -> 'a option -> 'b option -> 'c option) -> 'a t -> 'b t -> 'c t
val union : (key -> 'a -> 'a -> 'a option) -> 'a t -> 'a t -> 'a t
val compare : ('a -> 'a -> int) -> 'a t -> 'a t -> int
val equal : ('a -> 'a -> bool) -> 'a t -> 'a t -> bool
val iter : (key -> 'a -> unit) -> 'a t -> unit
val fold : (key -> 'a -> 'b -> 'b) -> 'a t -> 'b -> 'b
val for_all : (key -> 'a -> bool) -> 'a t -> bool
val exists : (key -> 'a -> bool) -> 'a t -> bool
val filter : (key -> 'a -> bool) -> 'a t -> 'a t
val filter_map : (key -> 'a -> 'b option) -> 'a t -> 'b t
val partition : (key -> 'a -> bool) -> 'a t -> 'a t * 'a t
val cardinal : 'a t -> int
val bindings : 'a t -> (key * 'a) list
val min_binding : 'a t -> key * 'a
val min_binding_opt : 'a t -> (key * 'a) option
val max_binding : 'a t -> key * 'a
val max_binding_opt : 'a t -> (key * 'a) option
val choose : 'a t -> key * 'a
val choose_opt : 'a t -> (key * 'a) option
val split : key -> 'a t -> 'a t * 'a option * 'a t
val find : key -> 'a t -> 'a
val find_opt : key -> 'a t -> 'a option
val find_first : (key -> bool) -> 'a t -> key * 'a
val find_first_opt : (key -> bool) -> 'a t -> (key * 'a) option
val find_last : (key -> bool) -> 'a t -> key * 'a
val find_last_opt : (key -> bool) -> 'a t -> (key * 'a) option
val map : ('a -> 'b) -> 'a t -> 'b t
val mapi : (key -> 'a -> 'b) -> 'a t -> 'b t
val to_seq : 'a t -> (key * 'a) Seq.t
val to_seq_from : key -> 'a t -> (key * 'a) Seq.t
val add_seq : (key * 'a) Seq.t -> 'a t -> 'a t
val of_seq : (key * 'a) Seq.t -> 'a t
end
module RuleName :
sig
type t
type info = Utils.Uid.MarkedString.info
val fresh : info -> t
val get_info : t -> info
val compare : t -> t -> int
val format_t : Format.formatter -> t -> unit
val hash : t -> int
end
module RuleMap :
sig
type key = RuleName.t
type +'a t
val empty : 'a t
val is_empty : 'a t -> bool
val mem : key -> 'a t -> bool
val add : key -> 'a -> 'a t -> 'a t
val update : key -> ('a option -> 'a option) -> 'a t -> 'a t
val singleton : key -> 'a -> 'a t
val remove : key -> 'a t -> 'a t
val merge :
(key -> 'a option -> 'b option -> 'c option) -> 'a t -> 'b t -> 'c t
val union : (key -> 'a -> 'a -> 'a option) -> 'a t -> 'a t -> 'a t
val compare : ('a -> 'a -> int) -> 'a t -> 'a t -> int
val equal : ('a -> 'a -> bool) -> 'a t -> 'a t -> bool
val iter : (key -> 'a -> unit) -> 'a t -> unit
val fold : (key -> 'a -> 'b -> 'b) -> 'a t -> 'b -> 'b
val for_all : (key -> 'a -> bool) -> 'a t -> bool
val exists : (key -> 'a -> bool) -> 'a t -> bool
val filter : (key -> 'a -> bool) -> 'a t -> 'a t
val filter_map : (key -> 'a -> 'b option) -> 'a t -> 'b t
val partition : (key -> 'a -> bool) -> 'a t -> 'a t * 'a t
val cardinal : 'a t -> int
val bindings : 'a t -> (key * 'a) list
val min_binding : 'a t -> key * 'a
val min_binding_opt : 'a t -> (key * 'a) option
val max_binding : 'a t -> key * 'a
val max_binding_opt : 'a t -> (key * 'a) option
val choose : 'a t -> key * 'a
val choose_opt : 'a t -> (key * 'a) option
val split : key -> 'a t -> 'a t * 'a option * 'a t
val find : key -> 'a t -> 'a
val find_opt : key -> 'a t -> 'a option
val find_first : (key -> bool) -> 'a t -> key * 'a
val find_first_opt : (key -> bool) -> 'a t -> (key * 'a) option
val find_last : (key -> bool) -> 'a t -> key * 'a
val find_last_opt : (key -> bool) -> 'a t -> (key * 'a) option
val map : ('a -> 'b) -> 'a t -> 'b t
val mapi : (key -> 'a -> 'b) -> 'a t -> 'b t
val to_seq : 'a t -> (key * 'a) Seq.t
val to_seq_from : key -> 'a t -> (key * 'a) Seq.t
val add_seq : (key * 'a) Seq.t -> 'a t -> 'a t
val of_seq : (key * 'a) Seq.t -> 'a t
end
module RuleSet :
sig
type elt = RuleName.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 disjoint : t -> t -> bool
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 filter_map : (elt -> elt option) -> t -> t
val partition : (elt -> bool) -> t -> t * t
val cardinal : t -> int
val elements : t -> elt list
val min_elt : t -> elt
val min_elt_opt : t -> elt option
val max_elt : t -> elt
val max_elt_opt : t -> elt option
val choose : t -> elt
val choose_opt : t -> elt option
val split : elt -> t -> t * bool * t
val find : elt -> t -> elt
val find_opt : elt -> t -> elt option
val find_first : (elt -> bool) -> t -> elt
val find_first_opt : (elt -> bool) -> t -> elt option
val find_last : (elt -> bool) -> t -> elt
val find_last_opt : (elt -> bool) -> t -> elt option
val of_list : elt list -> t
val to_seq_from : elt -> t -> elt Seq.t
val to_seq : t -> elt Seq.t
val add_seq : elt Seq.t -> t -> t
val of_seq : elt Seq.t -> t
end
module ScopeDef :
sig
type t =
Var of Scopelang.Ast.ScopeVar.t
| SubScopeVar of Scopelang.Ast.SubScopeName.t *
Scopelang.Ast.ScopeVar.t
val compare : t -> t -> int
val get_position : t -> Utils.Pos.t
val format_t : Format.formatter -> t -> unit
val hash : t -> int
end
module ScopeDefMap :
sig
type key = ScopeDef.t
type +'a t
val empty : 'a t
val is_empty : 'a t -> bool
val mem : key -> 'a t -> bool
val add : key -> 'a -> 'a t -> 'a t
val update : key -> ('a option -> 'a option) -> 'a t -> 'a t
val singleton : key -> 'a -> 'a t
val remove : key -> 'a t -> 'a t
val merge :
(key -> 'a option -> 'b option -> 'c option) -> 'a t -> 'b t -> 'c t
val union : (key -> 'a -> 'a -> 'a option) -> 'a t -> 'a t -> 'a t
val compare : ('a -> 'a -> int) -> 'a t -> 'a t -> int
val equal : ('a -> 'a -> bool) -> 'a t -> 'a t -> bool
val iter : (key -> 'a -> unit) -> 'a t -> unit
val fold : (key -> 'a -> 'b -> 'b) -> 'a t -> 'b -> 'b
val for_all : (key -> 'a -> bool) -> 'a t -> bool
val exists : (key -> 'a -> bool) -> 'a t -> bool
val filter : (key -> 'a -> bool) -> 'a t -> 'a t
val filter_map : (key -> 'a -> 'b option) -> 'a t -> 'b t
val partition : (key -> 'a -> bool) -> 'a t -> 'a t * 'a t
val cardinal : 'a t -> int
val bindings : 'a t -> (key * 'a) list
val min_binding : 'a t -> key * 'a
val min_binding_opt : 'a t -> (key * 'a) option
val max_binding : 'a t -> key * 'a
val max_binding_opt : 'a t -> (key * 'a) option
val choose : 'a t -> key * 'a
val choose_opt : 'a t -> (key * 'a) option
val split : key -> 'a t -> 'a t * 'a option * 'a t
val find : key -> 'a t -> 'a
val find_opt : key -> 'a t -> 'a option
val find_first : (key -> bool) -> 'a t -> key * 'a
val find_first_opt : (key -> bool) -> 'a t -> (key * 'a) option
val find_last : (key -> bool) -> 'a t -> key * 'a
val find_last_opt : (key -> bool) -> 'a t -> (key * 'a) option
val map : ('a -> 'b) -> 'a t -> 'b t
val mapi : (key -> 'a -> 'b) -> 'a t -> 'b t
val to_seq : 'a t -> (key * 'a) Seq.t
val to_seq_from : key -> 'a t -> (key * 'a) Seq.t
val add_seq : (key * 'a) Seq.t -> 'a t -> 'a t
val of_seq : (key * 'a) Seq.t -> 'a t
end
module ScopeDefSet :
sig
type elt = ScopeDef.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 disjoint : t -> t -> bool
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 filter_map : (elt -> elt option) -> t -> t
val partition : (elt -> bool) -> t -> t * t
val cardinal : t -> int
val elements : t -> elt list
val min_elt : t -> elt
val min_elt_opt : t -> elt option
val max_elt : t -> elt
val max_elt_opt : t -> elt option
val choose : t -> elt
val choose_opt : t -> elt option
val split : elt -> t -> t * bool * t
val find : elt -> t -> elt
val find_opt : elt -> t -> elt option
val find_first : (elt -> bool) -> t -> elt
val find_first_opt : (elt -> bool) -> t -> elt option
val find_last : (elt -> bool) -> t -> elt
val find_last_opt : (elt -> bool) -> t -> elt option
val of_list : elt list -> t
val to_seq_from : elt -> t -> elt Seq.t
val to_seq : t -> elt Seq.t
val add_seq : elt Seq.t -> t -> t
val of_seq : elt Seq.t -> t
end
type rule = {
just : Scopelang.Ast.expr Utils.Pos.marked Bindlib.box;
cons : Scopelang.Ast.expr Utils.Pos.marked Bindlib.box;
parameter :
(Scopelang.Ast.Var.t * Scopelang.Ast.typ Utils.Pos.marked) option;
exception_to_rule : RuleName.t Utils.Pos.marked option;
}
val empty_rule :
Utils.Pos.t -> Scopelang.Ast.typ Utils.Pos.marked option -> rule
val always_false_rule :
Utils.Pos.t -> Scopelang.Ast.typ Utils.Pos.marked option -> rule
type assertion = Scopelang.Ast.expr Utils.Pos.marked Bindlib.box
type variation_typ = Increasing | Decreasing
type reference_typ = Decree | Law
type meta_assertion =
FixedBy of reference_typ Utils.Pos.marked
| VariesWith of unit * variation_typ Utils.Pos.marked option
type scope = {
scope_vars : Scopelang.Ast.ScopeVarSet.t;
scope_sub_scopes : Scopelang.Ast.ScopeName.t Scopelang.Ast.SubScopeMap.t;
scope_uid : Scopelang.Ast.ScopeName.t;
scope_defs :
(rule RuleMap.t * Scopelang.Ast.typ Utils.Pos.marked * bool)
ScopeDefMap.t;
scope_assertions : assertion list;
scope_meta_assertions : meta_assertion list;
}
type program = {
program_scopes : scope Scopelang.Ast.ScopeMap.t;
program_enums : Scopelang.Ast.enum_ctx;
program_structs : Scopelang.Ast.struct_ctx;
}
val free_variables : rule RuleMap.t -> Utils.Pos.t ScopeDefMap.t

View File

@ -0,0 +1,185 @@
module Vertex :
sig
type t =
Var of Scopelang.Ast.ScopeVar.t
| SubScope of Scopelang.Ast.SubScopeName.t
val hash : t -> int
val compare : 'a -> 'a -> int
val equal : t -> t -> bool
val format_t : Format.formatter -> t -> unit
end
module Edge :
sig
type t = Utils.Pos.t
val compare : 'a -> 'a -> int
val default : Utils.Pos.t
end
module ScopeDependencies :
sig
type t =
Graph__Persistent.Digraph.ConcreteBidirectionalLabeled(Vertex)(Edge).t
module V :
sig
type t = Vertex.t
val compare : t -> t -> int
val hash : t -> int
val equal : t -> t -> bool
type label = Vertex.t
val create : label -> t
val label : t -> label
end
type vertex = V.t
module E :
sig
type t = Vertex.t * Edge.t * Vertex.t
val compare : t -> t -> int
type nonrec vertex = vertex
val src : t -> vertex
val dst : t -> vertex
type label = Edge.t
val create : vertex -> label -> vertex -> t
val label : t -> label
end
type edge = E.t
val is_directed : bool
val is_empty : t -> bool
val nb_vertex : t -> int
val nb_edges : t -> int
val out_degree : t -> vertex -> int
val in_degree : t -> vertex -> int
val mem_vertex : t -> vertex -> bool
val mem_edge : t -> vertex -> vertex -> bool
val mem_edge_e : t -> edge -> bool
val find_edge : t -> vertex -> vertex -> edge
val find_all_edges : t -> vertex -> vertex -> edge list
val succ : t -> vertex -> vertex list
val pred : t -> vertex -> vertex list
val succ_e : t -> vertex -> edge list
val pred_e : t -> vertex -> edge list
val iter_vertex : (vertex -> unit) -> t -> unit
val fold_vertex : (vertex -> 'a -> 'a) -> t -> 'a -> 'a
val iter_edges : (vertex -> vertex -> unit) -> t -> unit
val fold_edges : (vertex -> vertex -> 'a -> 'a) -> t -> 'a -> 'a
val iter_edges_e : (edge -> unit) -> t -> unit
val fold_edges_e : (edge -> 'a -> 'a) -> t -> 'a -> 'a
val map_vertex : (vertex -> vertex) -> t -> t
val iter_succ : (vertex -> unit) -> t -> vertex -> unit
val iter_pred : (vertex -> unit) -> t -> vertex -> unit
val fold_succ : (vertex -> 'a -> 'a) -> t -> vertex -> 'a -> 'a
val fold_pred : (vertex -> 'a -> 'a) -> t -> vertex -> 'a -> 'a
val iter_succ_e : (edge -> unit) -> t -> vertex -> unit
val fold_succ_e : (edge -> 'a -> 'a) -> t -> vertex -> 'a -> 'a
val iter_pred_e : (edge -> unit) -> t -> vertex -> unit
val fold_pred_e : (edge -> 'a -> 'a) -> t -> vertex -> 'a -> 'a
val empty : t
val add_vertex : t -> vertex -> t
val remove_vertex : t -> vertex -> t
val add_edge : t -> vertex -> vertex -> t
val add_edge_e : t -> edge -> t
val remove_edge : t -> vertex -> vertex -> t
val remove_edge_e : t -> edge -> t
end
module TopologicalTraversal :
sig
val fold :
(ScopeDependencies.V.t -> 'a -> 'a) -> ScopeDependencies.t -> 'a -> 'a
val iter : (ScopeDependencies.V.t -> unit) -> ScopeDependencies.t -> unit
end
module SCC :
sig
val scc : ScopeDependencies.t -> int * (ScopeDependencies.V.t -> int)
val scc_array : ScopeDependencies.t -> ScopeDependencies.V.t list array
val scc_list : ScopeDependencies.t -> ScopeDependencies.V.t list list
end
val correct_computation_ordering : ScopeDependencies.t -> Vertex.t list
val check_for_cycle : Ast.scope -> ScopeDependencies.t -> unit
val build_scope_dependencies : Ast.scope -> ScopeDependencies.t
module ExceptionVertex :
sig
type t = Desugared__Ast.RuleName.t
type info = Utils.Uid.MarkedString.info
val fresh : info -> t
val get_info : t -> info
val compare : t -> t -> int
val format_t : Format.formatter -> t -> unit
val hash : t -> int
val equal : t -> t -> bool
end
module ExceptionsDependencies :
sig
type t =
Graph__Persistent.Digraph.ConcreteBidirectionalLabeled(ExceptionVertex)(Edge).t
module V :
sig
type t = ExceptionVertex.t
val compare : t -> t -> int
val hash : t -> int
val equal : t -> t -> bool
type label = ExceptionVertex.t
val create : label -> t
val label : t -> label
end
type vertex = V.t
module E :
sig
type t = ExceptionVertex.t * Edge.t * ExceptionVertex.t
val compare : t -> t -> int
type nonrec vertex = vertex
val src : t -> vertex
val dst : t -> vertex
type label = Edge.t
val create : vertex -> label -> vertex -> t
val label : t -> label
end
type edge = E.t
val is_directed : bool
val is_empty : t -> bool
val nb_vertex : t -> int
val nb_edges : t -> int
val out_degree : t -> vertex -> int
val in_degree : t -> vertex -> int
val mem_vertex : t -> vertex -> bool
val mem_edge : t -> vertex -> vertex -> bool
val mem_edge_e : t -> edge -> bool
val find_edge : t -> vertex -> vertex -> edge
val find_all_edges : t -> vertex -> vertex -> edge list
val succ : t -> vertex -> vertex list
val pred : t -> vertex -> vertex list
val succ_e : t -> vertex -> edge list
val pred_e : t -> vertex -> edge list
val iter_vertex : (vertex -> unit) -> t -> unit
val fold_vertex : (vertex -> 'a -> 'a) -> t -> 'a -> 'a
val iter_edges : (vertex -> vertex -> unit) -> t -> unit
val fold_edges : (vertex -> vertex -> 'a -> 'a) -> t -> 'a -> 'a
val iter_edges_e : (edge -> unit) -> t -> unit
val fold_edges_e : (edge -> 'a -> 'a) -> t -> 'a -> 'a
val map_vertex : (vertex -> vertex) -> t -> t
val iter_succ : (vertex -> unit) -> t -> vertex -> unit
val iter_pred : (vertex -> unit) -> t -> vertex -> unit
val fold_succ : (vertex -> 'a -> 'a) -> t -> vertex -> 'a -> 'a
val fold_pred : (vertex -> 'a -> 'a) -> t -> vertex -> 'a -> 'a
val iter_succ_e : (edge -> unit) -> t -> vertex -> unit
val fold_succ_e : (edge -> 'a -> 'a) -> t -> vertex -> 'a -> 'a
val iter_pred_e : (edge -> unit) -> t -> vertex -> unit
val fold_pred_e : (edge -> 'a -> 'a) -> t -> vertex -> 'a -> 'a
val empty : t
val add_vertex : t -> vertex -> t
val remove_vertex : t -> vertex -> t
val add_edge : t -> vertex -> vertex -> t
val add_edge_e : t -> edge -> t
val remove_edge : t -> vertex -> vertex -> t
val remove_edge_e : t -> edge -> t
end
module ExceptionsSCC :
sig
val scc :
ExceptionsDependencies.t -> int * (ExceptionsDependencies.V.t -> int)
val scc_array :
ExceptionsDependencies.t -> ExceptionsDependencies.V.t list array
val scc_list :
ExceptionsDependencies.t -> ExceptionsDependencies.V.t list list
end
val build_exceptions_graph :
Ast.rule Ast.RuleMap.t ->
Ast.ScopeDef.t -> ExceptionsDependencies.t
val check_for_exception_cycle : ExceptionsDependencies.t -> unit

View File

@ -0,0 +1,18 @@
type rule_tree =
Leaf of Ast.rule
| Node of rule_tree list * Ast.rule
val def_map_to_tree :
Ast.ScopeDef.t ->
Ast.rule Ast.RuleMap.t -> rule_tree list
val rule_tree_to_expr :
toplevel:bool ->
Utils.Pos.t ->
Scopelang.Ast.Var.t option ->
rule_tree -> Scopelang.Ast.expr Utils.Pos.marked Bindlib.box
val translate_def :
Ast.ScopeDef.t ->
Ast.rule Ast.RuleMap.t ->
Scopelang.Ast.typ Utils.Pos.marked ->
bool -> Scopelang.Ast.expr Utils.Pos.marked
val translate_scope : Ast.scope -> Scopelang.Ast.scope_decl
val translate_program : Ast.program -> Scopelang.Ast.program

103
src/catala/lcalc/ast.mli Normal file
View File

@ -0,0 +1,103 @@
module D = Dcalc.Ast
type lit =
LBool of bool
| LInt of Z.t
| LRat of Q.t
| LMoney of Z.t
| LUnit
| LDate of D.date
| LDuration of D.duration
type except = ConflictError | EmptyError | Crash
type expr =
EVar of expr Bindlib.var Utils.Pos.marked
| ETuple of expr Utils.Pos.marked list * D.StructName.t option
| ETupleAccess of expr Utils.Pos.marked * int * D.StructName.t option *
D.typ Utils.Pos.marked list
| EInj of expr Utils.Pos.marked * int * D.EnumName.t *
D.typ Utils.Pos.marked list
| EMatch of expr Utils.Pos.marked * expr Utils.Pos.marked list *
D.EnumName.t
| EArray of expr Utils.Pos.marked list
| ELit of lit
| EAbs of Utils.Pos.t * (expr, expr Utils.Pos.marked) Bindlib.mbinder *
D.typ Utils.Pos.marked list
| EApp of expr Utils.Pos.marked * expr Utils.Pos.marked list
| EAssert of expr Utils.Pos.marked
| EOp of D.operator
| EIfThenElse of expr Utils.Pos.marked * expr Utils.Pos.marked *
expr Utils.Pos.marked
| ERaise of except
| ECatch of expr Utils.Pos.marked * except * expr Utils.Pos.marked
module Var :
sig
type t = expr Bindlib.var
val make : string Utils.Pos.marked -> t
val compare : 'a Bindlib.var -> 'b Bindlib.var -> int
end
module VarMap :
sig
type key = Var.t
type 'a t = 'a Stdlib__map.Make(Var).t
val empty : 'a t
val is_empty : 'a t -> bool
val mem : key -> 'a t -> bool
val add : key -> 'a -> 'a t -> 'a t
val update : key -> ('a option -> 'a option) -> 'a t -> 'a t
val singleton : key -> 'a -> 'a t
val remove : key -> 'a t -> 'a t
val merge :
(key -> 'a option -> 'b option -> 'c option) -> 'a t -> 'b t -> 'c t
val union : (key -> 'a -> 'a -> 'a option) -> 'a t -> 'a t -> 'a t
val compare : ('a -> 'a -> int) -> 'a t -> 'a t -> int
val equal : ('a -> 'a -> bool) -> 'a t -> 'a t -> bool
val iter : (key -> 'a -> unit) -> 'a t -> unit
val fold : (key -> 'a -> 'b -> 'b) -> 'a t -> 'b -> 'b
val for_all : (key -> 'a -> bool) -> 'a t -> bool
val exists : (key -> 'a -> bool) -> 'a t -> bool
val filter : (key -> 'a -> bool) -> 'a t -> 'a t
val filter_map : (key -> 'a -> 'b option) -> 'a t -> 'b t
val partition : (key -> 'a -> bool) -> 'a t -> 'a t * 'a t
val cardinal : 'a t -> int
val bindings : 'a t -> (key * 'a) list
val min_binding : 'a t -> key * 'a
val min_binding_opt : 'a t -> (key * 'a) option
val max_binding : 'a t -> key * 'a
val max_binding_opt : 'a t -> (key * 'a) option
val choose : 'a t -> key * 'a
val choose_opt : 'a t -> (key * 'a) option
val split : key -> 'a t -> 'a t * 'a option * 'a t
val find : key -> 'a t -> 'a
val find_opt : key -> 'a t -> 'a option
val find_first : (key -> bool) -> 'a t -> key * 'a
val find_first_opt : (key -> bool) -> 'a t -> (key * 'a) option
val find_last : (key -> bool) -> 'a t -> key * 'a
val find_last_opt : (key -> bool) -> 'a t -> (key * 'a) option
val map : ('a -> 'b) -> 'a t -> 'b t
val mapi : (key -> 'a -> 'b) -> 'a t -> 'b t
val to_seq : 'a t -> (key * 'a) Seq.t
val to_seq_from : key -> 'a t -> (key * 'a) Seq.t
val add_seq : (key * 'a) Seq.t -> 'a t -> 'a t
val of_seq : (key * 'a) Seq.t -> 'a t
end
type vars = expr Bindlib.mvar
val make_var : Var.t Utils.Pos.marked -> expr Utils.Pos.marked Bindlib.box
val make_abs :
vars ->
expr Utils.Pos.marked Bindlib.box ->
Utils.Pos.t ->
D.typ Utils.Pos.marked list ->
Utils.Pos.t -> expr Utils.Pos.marked Bindlib.box
val make_app :
expr Utils.Pos.marked Bindlib.box ->
expr Utils.Pos.marked Bindlib.box list ->
Utils.Pos.t -> expr Utils.Pos.marked Bindlib.box
val make_let_in :
Var.t ->
D.typ Utils.Pos.marked ->
expr Utils.Pos.marked Bindlib.box ->
expr Utils.Pos.marked Bindlib.box -> expr Utils.Pos.marked Bindlib.box
type binder = (expr, expr Utils.Pos.marked) Bindlib.binder
type program = {
decl_ctx : D.decl_ctx;
scopes : (Var.t * expr Utils.Pos.marked) list;
}

View File

@ -0,0 +1,17 @@
module D = Dcalc.Ast
module A = Ast
type ctx = A.expr Utils.Pos.marked Bindlib.box D.VarMap.t
val handle_default : Utils.Pos.t -> A.expr Utils.Pos.marked Bindlib.box
val translate_lit : D.lit -> A.expr
val thunk_expr :
A.expr Utils.Pos.marked Bindlib.box ->
Utils.Pos.t -> A.expr Utils.Pos.marked Bindlib.box
val translate_default :
ctx ->
D.expr Utils.Pos.marked list ->
D.expr Utils.Pos.marked ->
D.expr Utils.Pos.marked ->
Utils.Pos.t -> A.expr Utils.Pos.marked Bindlib.box
val translate_expr :
ctx -> D.expr Utils.Pos.marked -> A.expr Utils.Pos.marked Bindlib.box
val translate_program : D.program -> A.program

View File

@ -0,0 +1,30 @@
val format_lit : Format.formatter -> Ast.lit Utils.Pos.marked -> unit
val format_op_kind : Format.formatter -> Dcalc.Ast.op_kind -> unit
val format_log_entry : Format.formatter -> Dcalc.Ast.log_entry -> unit
val format_binop :
Format.formatter -> Dcalc.Ast.binop Utils.Pos.marked -> unit
val format_ternop :
Format.formatter -> Dcalc.Ast.ternop Utils.Pos.marked -> unit
val format_unop : Format.formatter -> Dcalc.Ast.unop Utils.Pos.marked -> unit
val to_ascii : string -> string
val to_lowercase : string -> string
val format_struct_name : Format.formatter -> Dcalc.Ast.StructName.t -> unit
val format_struct_field_name :
Format.formatter -> Dcalc.Ast.StructFieldName.t -> unit
val format_enum_name : Format.formatter -> Dcalc.Ast.EnumName.t -> unit
val format_enum_cons_name :
Format.formatter -> Dcalc.Ast.EnumConstructor.t -> unit
val typ_needs_parens : Dcalc.Ast.typ Utils.Pos.marked -> bool
val format_typ : Format.formatter -> Dcalc.Ast.typ Utils.Pos.marked -> unit
val format_var : Format.formatter -> Ast.Var.t -> unit
val needs_parens : Ast.expr Utils.Pos.marked -> bool
val format_exception : Format.formatter -> Ast.except -> unit
val format_expr :
Dcalc.Ast.decl_ctx ->
Format.formatter -> Ast.expr Utils.Pos.marked -> unit
val format_ctx :
Scopelang.Dependency.TVertex.t list ->
Format.formatter -> Ast.D.decl_ctx -> unit
val format_program :
Format.formatter ->
Ast.program -> Scopelang.Dependency.TVertex.t list -> unit

View File

@ -0,0 +1,24 @@
module A = Surface.Ast
module P = Printf
module R = Re.Pcre
module C = Utils.Cli
val pre_html : string -> string
val raise_failed_pygments : string -> int -> 'a
val wrap_html :
string list ->
string option ->
Utils.Cli.backend_lang ->
Format.formatter -> (Format.formatter -> unit) -> unit
val pygmentize_code :
string Utils.Pos.marked -> C.backend_lang -> string option -> string
val law_article_item_to_html :
string option ->
C.backend_lang -> Format.formatter -> A.law_article_item -> unit
val law_structure_to_html :
string option ->
C.backend_lang -> Format.formatter -> A.law_structure -> unit
val program_item_to_html :
string option ->
C.backend_lang -> Format.formatter -> A.program_item -> unit
val ast_to_html :
string option -> C.backend_lang -> Format.formatter -> A.program -> unit

View File

@ -0,0 +1,16 @@
module A = Surface.Ast
module R = Re.Pcre
module C = Utils.Cli
val pre_latexify : string -> string
val wrap_latex :
string list ->
string option ->
C.backend_lang -> Format.formatter -> (Format.formatter -> unit) -> unit
val math_syms_replace : string -> string
val law_article_item_to_latex :
C.backend_lang -> Format.formatter -> A.law_article_item -> unit
val law_structure_to_latex :
C.backend_lang -> Format.formatter -> A.law_structure -> unit
val program_item_to_latex :
C.backend_lang -> Format.formatter -> A.program_item -> unit
val ast_to_latex : C.backend_lang -> Format.formatter -> A.program -> unit

View File

@ -0,0 +1,551 @@
module ScopeName = Dcalc.Ast.ScopeName
module ScopeNameSet :
sig
type elt = ScopeName.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 disjoint : t -> t -> bool
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 filter_map : (elt -> elt option) -> t -> t
val partition : (elt -> bool) -> t -> t * t
val cardinal : t -> int
val elements : t -> elt list
val min_elt : t -> elt
val min_elt_opt : t -> elt option
val max_elt : t -> elt
val max_elt_opt : t -> elt option
val choose : t -> elt
val choose_opt : t -> elt option
val split : elt -> t -> t * bool * t
val find : elt -> t -> elt
val find_opt : elt -> t -> elt option
val find_first : (elt -> bool) -> t -> elt
val find_first_opt : (elt -> bool) -> t -> elt option
val find_last : (elt -> bool) -> t -> elt
val find_last_opt : (elt -> bool) -> t -> elt option
val of_list : elt list -> t
val to_seq_from : elt -> t -> elt Seq.t
val to_seq : t -> elt Seq.t
val add_seq : elt Seq.t -> t -> t
val of_seq : elt Seq.t -> t
end
module ScopeMap :
sig
type key = ScopeName.t
type +'a t
val empty : 'a t
val is_empty : 'a t -> bool
val mem : key -> 'a t -> bool
val add : key -> 'a -> 'a t -> 'a t
val update : key -> ('a option -> 'a option) -> 'a t -> 'a t
val singleton : key -> 'a -> 'a t
val remove : key -> 'a t -> 'a t
val merge :
(key -> 'a option -> 'b option -> 'c option) -> 'a t -> 'b t -> 'c t
val union : (key -> 'a -> 'a -> 'a option) -> 'a t -> 'a t -> 'a t
val compare : ('a -> 'a -> int) -> 'a t -> 'a t -> int
val equal : ('a -> 'a -> bool) -> 'a t -> 'a t -> bool
val iter : (key -> 'a -> unit) -> 'a t -> unit
val fold : (key -> 'a -> 'b -> 'b) -> 'a t -> 'b -> 'b
val for_all : (key -> 'a -> bool) -> 'a t -> bool
val exists : (key -> 'a -> bool) -> 'a t -> bool
val filter : (key -> 'a -> bool) -> 'a t -> 'a t
val filter_map : (key -> 'a -> 'b option) -> 'a t -> 'b t
val partition : (key -> 'a -> bool) -> 'a t -> 'a t * 'a t
val cardinal : 'a t -> int
val bindings : 'a t -> (key * 'a) list
val min_binding : 'a t -> key * 'a
val min_binding_opt : 'a t -> (key * 'a) option
val max_binding : 'a t -> key * 'a
val max_binding_opt : 'a t -> (key * 'a) option
val choose : 'a t -> key * 'a
val choose_opt : 'a t -> (key * 'a) option
val split : key -> 'a t -> 'a t * 'a option * 'a t
val find : key -> 'a t -> 'a
val find_opt : key -> 'a t -> 'a option
val find_first : (key -> bool) -> 'a t -> key * 'a
val find_first_opt : (key -> bool) -> 'a t -> (key * 'a) option
val find_last : (key -> bool) -> 'a t -> key * 'a
val find_last_opt : (key -> bool) -> 'a t -> (key * 'a) option
val map : ('a -> 'b) -> 'a t -> 'b t
val mapi : (key -> 'a -> 'b) -> 'a t -> 'b t
val to_seq : 'a t -> (key * 'a) Seq.t
val to_seq_from : key -> 'a t -> (key * 'a) Seq.t
val add_seq : (key * 'a) Seq.t -> 'a t -> 'a t
val of_seq : (key * 'a) Seq.t -> 'a t
end
module SubScopeName :
sig
type t
type info = Utils.Uid.MarkedString.info
val fresh : info -> t
val get_info : t -> info
val compare : t -> t -> int
val format_t : Format.formatter -> t -> unit
val hash : t -> int
end
module SubScopeNameSet :
sig
type elt = SubScopeName.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 disjoint : t -> t -> bool
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 filter_map : (elt -> elt option) -> t -> t
val partition : (elt -> bool) -> t -> t * t
val cardinal : t -> int
val elements : t -> elt list
val min_elt : t -> elt
val min_elt_opt : t -> elt option
val max_elt : t -> elt
val max_elt_opt : t -> elt option
val choose : t -> elt
val choose_opt : t -> elt option
val split : elt -> t -> t * bool * t
val find : elt -> t -> elt
val find_opt : elt -> t -> elt option
val find_first : (elt -> bool) -> t -> elt
val find_first_opt : (elt -> bool) -> t -> elt option
val find_last : (elt -> bool) -> t -> elt
val find_last_opt : (elt -> bool) -> t -> elt option
val of_list : elt list -> t
val to_seq_from : elt -> t -> elt Seq.t
val to_seq : t -> elt Seq.t
val add_seq : elt Seq.t -> t -> t
val of_seq : elt Seq.t -> t
end
module SubScopeMap :
sig
type key = SubScopeName.t
type +'a t
val empty : 'a t
val is_empty : 'a t -> bool
val mem : key -> 'a t -> bool
val add : key -> 'a -> 'a t -> 'a t
val update : key -> ('a option -> 'a option) -> 'a t -> 'a t
val singleton : key -> 'a -> 'a t
val remove : key -> 'a t -> 'a t
val merge :
(key -> 'a option -> 'b option -> 'c option) -> 'a t -> 'b t -> 'c t
val union : (key -> 'a -> 'a -> 'a option) -> 'a t -> 'a t -> 'a t
val compare : ('a -> 'a -> int) -> 'a t -> 'a t -> int
val equal : ('a -> 'a -> bool) -> 'a t -> 'a t -> bool
val iter : (key -> 'a -> unit) -> 'a t -> unit
val fold : (key -> 'a -> 'b -> 'b) -> 'a t -> 'b -> 'b
val for_all : (key -> 'a -> bool) -> 'a t -> bool
val exists : (key -> 'a -> bool) -> 'a t -> bool
val filter : (key -> 'a -> bool) -> 'a t -> 'a t
val filter_map : (key -> 'a -> 'b option) -> 'a t -> 'b t
val partition : (key -> 'a -> bool) -> 'a t -> 'a t * 'a t
val cardinal : 'a t -> int
val bindings : 'a t -> (key * 'a) list
val min_binding : 'a t -> key * 'a
val min_binding_opt : 'a t -> (key * 'a) option
val max_binding : 'a t -> key * 'a
val max_binding_opt : 'a t -> (key * 'a) option
val choose : 'a t -> key * 'a
val choose_opt : 'a t -> (key * 'a) option
val split : key -> 'a t -> 'a t * 'a option * 'a t
val find : key -> 'a t -> 'a
val find_opt : key -> 'a t -> 'a option
val find_first : (key -> bool) -> 'a t -> key * 'a
val find_first_opt : (key -> bool) -> 'a t -> (key * 'a) option
val find_last : (key -> bool) -> 'a t -> key * 'a
val find_last_opt : (key -> bool) -> 'a t -> (key * 'a) option
val map : ('a -> 'b) -> 'a t -> 'b t
val mapi : (key -> 'a -> 'b) -> 'a t -> 'b t
val to_seq : 'a t -> (key * 'a) Seq.t
val to_seq_from : key -> 'a t -> (key * 'a) Seq.t
val add_seq : (key * 'a) Seq.t -> 'a t -> 'a t
val of_seq : (key * 'a) Seq.t -> 'a t
end
module ScopeVar :
sig
type t
type info = Utils.Uid.MarkedString.info
val fresh : info -> t
val get_info : t -> info
val compare : t -> t -> int
val format_t : Format.formatter -> t -> unit
val hash : t -> int
end
module ScopeVarSet :
sig
type elt = ScopeVar.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 disjoint : t -> t -> bool
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 filter_map : (elt -> elt option) -> t -> t
val partition : (elt -> bool) -> t -> t * t
val cardinal : t -> int
val elements : t -> elt list
val min_elt : t -> elt
val min_elt_opt : t -> elt option
val max_elt : t -> elt
val max_elt_opt : t -> elt option
val choose : t -> elt
val choose_opt : t -> elt option
val split : elt -> t -> t * bool * t
val find : elt -> t -> elt
val find_opt : elt -> t -> elt option
val find_first : (elt -> bool) -> t -> elt
val find_first_opt : (elt -> bool) -> t -> elt option
val find_last : (elt -> bool) -> t -> elt
val find_last_opt : (elt -> bool) -> t -> elt option
val of_list : elt list -> t
val to_seq_from : elt -> t -> elt Seq.t
val to_seq : t -> elt Seq.t
val add_seq : elt Seq.t -> t -> t
val of_seq : elt Seq.t -> t
end
module ScopeVarMap :
sig
type key = ScopeVar.t
type +'a t
val empty : 'a t
val is_empty : 'a t -> bool
val mem : key -> 'a t -> bool
val add : key -> 'a -> 'a t -> 'a t
val update : key -> ('a option -> 'a option) -> 'a t -> 'a t
val singleton : key -> 'a -> 'a t
val remove : key -> 'a t -> 'a t
val merge :
(key -> 'a option -> 'b option -> 'c option) -> 'a t -> 'b t -> 'c t
val union : (key -> 'a -> 'a -> 'a option) -> 'a t -> 'a t -> 'a t
val compare : ('a -> 'a -> int) -> 'a t -> 'a t -> int
val equal : ('a -> 'a -> bool) -> 'a t -> 'a t -> bool
val iter : (key -> 'a -> unit) -> 'a t -> unit
val fold : (key -> 'a -> 'b -> 'b) -> 'a t -> 'b -> 'b
val for_all : (key -> 'a -> bool) -> 'a t -> bool
val exists : (key -> 'a -> bool) -> 'a t -> bool
val filter : (key -> 'a -> bool) -> 'a t -> 'a t
val filter_map : (key -> 'a -> 'b option) -> 'a t -> 'b t
val partition : (key -> 'a -> bool) -> 'a t -> 'a t * 'a t
val cardinal : 'a t -> int
val bindings : 'a t -> (key * 'a) list
val min_binding : 'a t -> key * 'a
val min_binding_opt : 'a t -> (key * 'a) option
val max_binding : 'a t -> key * 'a
val max_binding_opt : 'a t -> (key * 'a) option
val choose : 'a t -> key * 'a
val choose_opt : 'a t -> (key * 'a) option
val split : key -> 'a t -> 'a t * 'a option * 'a t
val find : key -> 'a t -> 'a
val find_opt : key -> 'a t -> 'a option
val find_first : (key -> bool) -> 'a t -> key * 'a
val find_first_opt : (key -> bool) -> 'a t -> (key * 'a) option
val find_last : (key -> bool) -> 'a t -> key * 'a
val find_last_opt : (key -> bool) -> 'a t -> (key * 'a) option
val map : ('a -> 'b) -> 'a t -> 'b t
val mapi : (key -> 'a -> 'b) -> 'a t -> 'b t
val to_seq : 'a t -> (key * 'a) Seq.t
val to_seq_from : key -> 'a t -> (key * 'a) Seq.t
val add_seq : (key * 'a) Seq.t -> 'a t -> 'a t
val of_seq : (key * 'a) Seq.t -> 'a t
end
module StructName = Dcalc.Ast.StructName
module StructMap = Dcalc.Ast.StructMap
module StructFieldName = Dcalc.Ast.StructFieldName
module StructFieldMap :
sig
type key = StructFieldName.t
type +'a t
val empty : 'a t
val is_empty : 'a t -> bool
val mem : key -> 'a t -> bool
val add : key -> 'a -> 'a t -> 'a t
val update : key -> ('a option -> 'a option) -> 'a t -> 'a t
val singleton : key -> 'a -> 'a t
val remove : key -> 'a t -> 'a t
val merge :
(key -> 'a option -> 'b option -> 'c option) -> 'a t -> 'b t -> 'c t
val union : (key -> 'a -> 'a -> 'a option) -> 'a t -> 'a t -> 'a t
val compare : ('a -> 'a -> int) -> 'a t -> 'a t -> int
val equal : ('a -> 'a -> bool) -> 'a t -> 'a t -> bool
val iter : (key -> 'a -> unit) -> 'a t -> unit
val fold : (key -> 'a -> 'b -> 'b) -> 'a t -> 'b -> 'b
val for_all : (key -> 'a -> bool) -> 'a t -> bool
val exists : (key -> 'a -> bool) -> 'a t -> bool
val filter : (key -> 'a -> bool) -> 'a t -> 'a t
val filter_map : (key -> 'a -> 'b option) -> 'a t -> 'b t
val partition : (key -> 'a -> bool) -> 'a t -> 'a t * 'a t
val cardinal : 'a t -> int
val bindings : 'a t -> (key * 'a) list
val min_binding : 'a t -> key * 'a
val min_binding_opt : 'a t -> (key * 'a) option
val max_binding : 'a t -> key * 'a
val max_binding_opt : 'a t -> (key * 'a) option
val choose : 'a t -> key * 'a
val choose_opt : 'a t -> (key * 'a) option
val split : key -> 'a t -> 'a t * 'a option * 'a t
val find : key -> 'a t -> 'a
val find_opt : key -> 'a t -> 'a option
val find_first : (key -> bool) -> 'a t -> key * 'a
val find_first_opt : (key -> bool) -> 'a t -> (key * 'a) option
val find_last : (key -> bool) -> 'a t -> key * 'a
val find_last_opt : (key -> bool) -> 'a t -> (key * 'a) option
val map : ('a -> 'b) -> 'a t -> 'b t
val mapi : (key -> 'a -> 'b) -> 'a t -> 'b t
val to_seq : 'a t -> (key * 'a) Seq.t
val to_seq_from : key -> 'a t -> (key * 'a) Seq.t
val add_seq : (key * 'a) Seq.t -> 'a t -> 'a t
val of_seq : (key * 'a) Seq.t -> 'a t
end
module EnumName = Dcalc.Ast.EnumName
module EnumMap = Dcalc.Ast.EnumMap
module EnumConstructor = Dcalc.Ast.EnumConstructor
module EnumConstructorMap :
sig
type key = EnumConstructor.t
type +'a t
val empty : 'a t
val is_empty : 'a t -> bool
val mem : key -> 'a t -> bool
val add : key -> 'a -> 'a t -> 'a t
val update : key -> ('a option -> 'a option) -> 'a t -> 'a t
val singleton : key -> 'a -> 'a t
val remove : key -> 'a t -> 'a t
val merge :
(key -> 'a option -> 'b option -> 'c option) -> 'a t -> 'b t -> 'c t
val union : (key -> 'a -> 'a -> 'a option) -> 'a t -> 'a t -> 'a t
val compare : ('a -> 'a -> int) -> 'a t -> 'a t -> int
val equal : ('a -> 'a -> bool) -> 'a t -> 'a t -> bool
val iter : (key -> 'a -> unit) -> 'a t -> unit
val fold : (key -> 'a -> 'b -> 'b) -> 'a t -> 'b -> 'b
val for_all : (key -> 'a -> bool) -> 'a t -> bool
val exists : (key -> 'a -> bool) -> 'a t -> bool
val filter : (key -> 'a -> bool) -> 'a t -> 'a t
val filter_map : (key -> 'a -> 'b option) -> 'a t -> 'b t
val partition : (key -> 'a -> bool) -> 'a t -> 'a t * 'a t
val cardinal : 'a t -> int
val bindings : 'a t -> (key * 'a) list
val min_binding : 'a t -> key * 'a
val min_binding_opt : 'a t -> (key * 'a) option
val max_binding : 'a t -> key * 'a
val max_binding_opt : 'a t -> (key * 'a) option
val choose : 'a t -> key * 'a
val choose_opt : 'a t -> (key * 'a) option
val split : key -> 'a t -> 'a t * 'a option * 'a t
val find : key -> 'a t -> 'a
val find_opt : key -> 'a t -> 'a option
val find_first : (key -> bool) -> 'a t -> key * 'a
val find_first_opt : (key -> bool) -> 'a t -> (key * 'a) option
val find_last : (key -> bool) -> 'a t -> key * 'a
val find_last_opt : (key -> bool) -> 'a t -> (key * 'a) option
val map : ('a -> 'b) -> 'a t -> 'b t
val mapi : (key -> 'a -> 'b) -> 'a t -> 'b t
val to_seq : 'a t -> (key * 'a) Seq.t
val to_seq_from : key -> 'a t -> (key * 'a) Seq.t
val add_seq : (key * 'a) Seq.t -> 'a t -> 'a t
val of_seq : (key * 'a) Seq.t -> 'a t
end
type location =
ScopeVar of ScopeVar.t Utils.Pos.marked
| SubScopeVar of ScopeName.t * SubScopeName.t Utils.Pos.marked *
ScopeVar.t Utils.Pos.marked
module LocationSet :
sig
type elt = location Utils.Pos.marked
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 disjoint : t -> t -> bool
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 filter_map : (elt -> elt option) -> t -> t
val partition : (elt -> bool) -> t -> t * t
val cardinal : t -> int
val elements : t -> elt list
val min_elt : t -> elt
val min_elt_opt : t -> elt option
val max_elt : t -> elt
val max_elt_opt : t -> elt option
val choose : t -> elt
val choose_opt : t -> elt option
val split : elt -> t -> t * bool * t
val find : elt -> t -> elt
val find_opt : elt -> t -> elt option
val find_first : (elt -> bool) -> t -> elt
val find_first_opt : (elt -> bool) -> t -> elt option
val find_last : (elt -> bool) -> t -> elt
val find_last_opt : (elt -> bool) -> t -> elt option
val of_list : elt list -> t
val to_seq_from : elt -> t -> elt Seq.t
val to_seq : t -> elt Seq.t
val add_seq : elt Seq.t -> t -> t
val of_seq : elt Seq.t -> t
end
type typ =
TLit of Dcalc.Ast.typ_lit
| TStruct of StructName.t
| TEnum of EnumName.t
| TArrow of typ Utils.Pos.marked * typ Utils.Pos.marked
| TArray of typ
| TAny
type expr =
ELocation of location
| EVar of expr Bindlib.var Utils.Pos.marked
| EStruct of StructName.t * expr Utils.Pos.marked StructFieldMap.t
| EStructAccess of expr Utils.Pos.marked * StructFieldName.t * StructName.t
| EEnumInj of expr Utils.Pos.marked * EnumConstructor.t * EnumName.t
| EMatch of expr Utils.Pos.marked * EnumName.t *
expr Utils.Pos.marked EnumConstructorMap.t
| ELit of Dcalc.Ast.lit
| EAbs of Utils.Pos.t * (expr, expr Utils.Pos.marked) Bindlib.mbinder *
typ Utils.Pos.marked list
| EApp of expr Utils.Pos.marked * expr Utils.Pos.marked list
| EOp of Dcalc.Ast.operator
| EDefault of expr Utils.Pos.marked list * expr Utils.Pos.marked *
expr Utils.Pos.marked
| EIfThenElse of expr Utils.Pos.marked * expr Utils.Pos.marked *
expr Utils.Pos.marked
| EArray of expr Utils.Pos.marked list
val locations_used : expr Utils.Pos.marked -> LocationSet.t
type rule =
Definition of location Utils.Pos.marked * typ Utils.Pos.marked *
expr Utils.Pos.marked
| Assertion of expr Utils.Pos.marked
| Call of ScopeName.t * SubScopeName.t
type scope_decl = {
scope_decl_name : ScopeName.t;
scope_sig : typ Utils.Pos.marked ScopeVarMap.t;
scope_decl_rules : rule list;
}
type struct_ctx = (StructFieldName.t * typ Utils.Pos.marked) list StructMap.t
type enum_ctx = (EnumConstructor.t * typ Utils.Pos.marked) list EnumMap.t
type program = {
program_scopes : scope_decl ScopeMap.t;
program_enums : enum_ctx;
program_structs : struct_ctx;
}
module Var :
sig
type t = expr Bindlib.var
val make : string Utils.Pos.marked -> t
val compare : 'a Bindlib.var -> 'b Bindlib.var -> int
end
type vars = expr Bindlib.mvar
val make_var : Var.t Utils.Pos.marked -> expr Utils.Pos.marked Bindlib.box
val make_abs :
vars ->
expr Utils.Pos.marked Bindlib.box ->
Utils.Pos.t ->
typ Utils.Pos.marked list ->
Utils.Pos.t -> expr Utils.Pos.marked Bindlib.box
val make_app :
expr Utils.Pos.marked Bindlib.box ->
expr Utils.Pos.marked Bindlib.box list ->
Utils.Pos.t -> expr Utils.Pos.marked Bindlib.box
val make_let_in :
Var.t ->
typ Utils.Pos.marked ->
expr Utils.Pos.marked Bindlib.box ->
expr Utils.Pos.marked Bindlib.box -> expr Utils.Pos.marked Bindlib.box
module VarMap :
sig
type key = Var.t
type 'a t = 'a Stdlib__map.Make(Var).t
val empty : 'a t
val is_empty : 'a t -> bool
val mem : key -> 'a t -> bool
val add : key -> 'a -> 'a t -> 'a t
val update : key -> ('a option -> 'a option) -> 'a t -> 'a t
val singleton : key -> 'a -> 'a t
val remove : key -> 'a t -> 'a t
val merge :
(key -> 'a option -> 'b option -> 'c option) -> 'a t -> 'b t -> 'c t
val union : (key -> 'a -> 'a -> 'a option) -> 'a t -> 'a t -> 'a t
val compare : ('a -> 'a -> int) -> 'a t -> 'a t -> int
val equal : ('a -> 'a -> bool) -> 'a t -> 'a t -> bool
val iter : (key -> 'a -> unit) -> 'a t -> unit
val fold : (key -> 'a -> 'b -> 'b) -> 'a t -> 'b -> 'b
val for_all : (key -> 'a -> bool) -> 'a t -> bool
val exists : (key -> 'a -> bool) -> 'a t -> bool
val filter : (key -> 'a -> bool) -> 'a t -> 'a t
val filter_map : (key -> 'a -> 'b option) -> 'a t -> 'b t
val partition : (key -> 'a -> bool) -> 'a t -> 'a t * 'a t
val cardinal : 'a t -> int
val bindings : 'a t -> (key * 'a) list
val min_binding : 'a t -> key * 'a
val min_binding_opt : 'a t -> (key * 'a) option
val max_binding : 'a t -> key * 'a
val max_binding_opt : 'a t -> (key * 'a) option
val choose : 'a t -> key * 'a
val choose_opt : 'a t -> (key * 'a) option
val split : key -> 'a t -> 'a t * 'a option * 'a t
val find : key -> 'a t -> 'a
val find_opt : key -> 'a t -> 'a option
val find_first : (key -> bool) -> 'a t -> key * 'a
val find_first_opt : (key -> bool) -> 'a t -> (key * 'a) option
val find_last : (key -> bool) -> 'a t -> key * 'a
val find_last_opt : (key -> bool) -> 'a t -> (key * 'a) option
val map : ('a -> 'b) -> 'a t -> 'b t
val mapi : (key -> 'a -> 'b) -> 'a t -> 'b t
val to_seq : 'a t -> (key * 'a) Seq.t
val to_seq_from : key -> 'a t -> (key * 'a) Seq.t
val add_seq : (key * 'a) Seq.t -> 'a t -> 'a t
val of_seq : (key * 'a) Seq.t -> 'a t
end

View File

@ -0,0 +1,240 @@
module SVertex :
sig
type t = Ast.ScopeName.t
val hash : Ast.ScopeName.t -> int
val compare :
Ast.ScopeName.t -> Ast.ScopeName.t -> int
val equal :
Ast.ScopeName.t -> Ast.ScopeName.t -> bool
val format_t : Format.formatter -> t -> unit
end
module SEdge :
sig
type t = Utils.Pos.t
val compare : 'a -> 'a -> int
val default : Utils.Pos.t
end
module SDependencies :
sig
type t =
Graph__Persistent.Digraph.ConcreteBidirectionalLabeled(SVertex)(SEdge).t
module V :
sig
type t = SVertex.t
val compare : t -> t -> int
val hash : t -> int
val equal : t -> t -> bool
type label = SVertex.t
val create : label -> t
val label : t -> label
end
type vertex = V.t
module E :
sig
type t = SVertex.t * SEdge.t * SVertex.t
val compare : t -> t -> int
type nonrec vertex = vertex
val src : t -> vertex
val dst : t -> vertex
type label = SEdge.t
val create : vertex -> label -> vertex -> t
val label : t -> label
end
type edge = E.t
val is_directed : bool
val is_empty : t -> bool
val nb_vertex : t -> int
val nb_edges : t -> int
val out_degree : t -> vertex -> int
val in_degree : t -> vertex -> int
val mem_vertex : t -> vertex -> bool
val mem_edge : t -> vertex -> vertex -> bool
val mem_edge_e : t -> edge -> bool
val find_edge : t -> vertex -> vertex -> edge
val find_all_edges : t -> vertex -> vertex -> edge list
val succ : t -> vertex -> vertex list
val pred : t -> vertex -> vertex list
val succ_e : t -> vertex -> edge list
val pred_e : t -> vertex -> edge list
val iter_vertex : (vertex -> unit) -> t -> unit
val fold_vertex : (vertex -> 'a -> 'a) -> t -> 'a -> 'a
val iter_edges : (vertex -> vertex -> unit) -> t -> unit
val fold_edges : (vertex -> vertex -> 'a -> 'a) -> t -> 'a -> 'a
val iter_edges_e : (edge -> unit) -> t -> unit
val fold_edges_e : (edge -> 'a -> 'a) -> t -> 'a -> 'a
val map_vertex : (vertex -> vertex) -> t -> t
val iter_succ : (vertex -> unit) -> t -> vertex -> unit
val iter_pred : (vertex -> unit) -> t -> vertex -> unit
val fold_succ : (vertex -> 'a -> 'a) -> t -> vertex -> 'a -> 'a
val fold_pred : (vertex -> 'a -> 'a) -> t -> vertex -> 'a -> 'a
val iter_succ_e : (edge -> unit) -> t -> vertex -> unit
val fold_succ_e : (edge -> 'a -> 'a) -> t -> vertex -> 'a -> 'a
val iter_pred_e : (edge -> unit) -> t -> vertex -> unit
val fold_pred_e : (edge -> 'a -> 'a) -> t -> vertex -> 'a -> 'a
val empty : t
val add_vertex : t -> vertex -> t
val remove_vertex : t -> vertex -> t
val add_edge : t -> vertex -> vertex -> t
val add_edge_e : t -> edge -> t
val remove_edge : t -> vertex -> vertex -> t
val remove_edge_e : t -> edge -> t
end
module STopologicalTraversal :
sig
val fold : (SDependencies.V.t -> 'a -> 'a) -> SDependencies.t -> 'a -> 'a
val iter : (SDependencies.V.t -> unit) -> SDependencies.t -> unit
end
module SSCC :
sig
val scc : SDependencies.t -> int * (SDependencies.V.t -> int)
val scc_array : SDependencies.t -> SDependencies.V.t list array
val scc_list : SDependencies.t -> SDependencies.V.t list list
end
val build_program_dep_graph : Ast.program -> SDependencies.t
val check_for_cycle_in_scope : SDependencies.t -> unit
val get_scope_ordering : SDependencies.t -> Ast.ScopeName.t list
module TVertex :
sig
type t =
Struct of Ast.StructName.t
| Enum of Ast.EnumName.t
val hash : t -> int
val compare : t -> t -> int
val equal : t -> t -> bool
val format_t : Format.formatter -> t -> unit
val get_info : t -> Ast.StructName.info
end
module TVertexSet :
sig
type elt = TVertex.t
type t = Stdlib__set.Make(TVertex).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 disjoint : t -> t -> bool
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 filter_map : (elt -> elt option) -> t -> t
val partition : (elt -> bool) -> t -> t * t
val cardinal : t -> int
val elements : t -> elt list
val min_elt : t -> elt
val min_elt_opt : t -> elt option
val max_elt : t -> elt
val max_elt_opt : t -> elt option
val choose : t -> elt
val choose_opt : t -> elt option
val split : elt -> t -> t * bool * t
val find : elt -> t -> elt
val find_opt : elt -> t -> elt option
val find_first : (elt -> bool) -> t -> elt
val find_first_opt : (elt -> bool) -> t -> elt option
val find_last : (elt -> bool) -> t -> elt
val find_last_opt : (elt -> bool) -> t -> elt option
val of_list : elt list -> t
val to_seq_from : elt -> t -> elt Seq.t
val to_seq : t -> elt Seq.t
val add_seq : elt Seq.t -> t -> t
val of_seq : elt Seq.t -> t
end
module TEdge :
sig
type t = Utils.Pos.t
val compare : 'a -> 'a -> int
val default : Utils.Pos.t
end
module TDependencies :
sig
type t =
Graph__Persistent.Digraph.ConcreteBidirectionalLabeled(TVertex)(TEdge).t
module V :
sig
type t = TVertex.t
val compare : t -> t -> int
val hash : t -> int
val equal : t -> t -> bool
type label = TVertex.t
val create : label -> t
val label : t -> label
end
type vertex = V.t
module E :
sig
type t = TVertex.t * TEdge.t * TVertex.t
val compare : t -> t -> int
type nonrec vertex = vertex
val src : t -> vertex
val dst : t -> vertex
type label = TEdge.t
val create : vertex -> label -> vertex -> t
val label : t -> label
end
type edge = E.t
val is_directed : bool
val is_empty : t -> bool
val nb_vertex : t -> int
val nb_edges : t -> int
val out_degree : t -> vertex -> int
val in_degree : t -> vertex -> int
val mem_vertex : t -> vertex -> bool
val mem_edge : t -> vertex -> vertex -> bool
val mem_edge_e : t -> edge -> bool
val find_edge : t -> vertex -> vertex -> edge
val find_all_edges : t -> vertex -> vertex -> edge list
val succ : t -> vertex -> vertex list
val pred : t -> vertex -> vertex list
val succ_e : t -> vertex -> edge list
val pred_e : t -> vertex -> edge list
val iter_vertex : (vertex -> unit) -> t -> unit
val fold_vertex : (vertex -> 'a -> 'a) -> t -> 'a -> 'a
val iter_edges : (vertex -> vertex -> unit) -> t -> unit
val fold_edges : (vertex -> vertex -> 'a -> 'a) -> t -> 'a -> 'a
val iter_edges_e : (edge -> unit) -> t -> unit
val fold_edges_e : (edge -> 'a -> 'a) -> t -> 'a -> 'a
val map_vertex : (vertex -> vertex) -> t -> t
val iter_succ : (vertex -> unit) -> t -> vertex -> unit
val iter_pred : (vertex -> unit) -> t -> vertex -> unit
val fold_succ : (vertex -> 'a -> 'a) -> t -> vertex -> 'a -> 'a
val fold_pred : (vertex -> 'a -> 'a) -> t -> vertex -> 'a -> 'a
val iter_succ_e : (edge -> unit) -> t -> vertex -> unit
val fold_succ_e : (edge -> 'a -> 'a) -> t -> vertex -> 'a -> 'a
val iter_pred_e : (edge -> unit) -> t -> vertex -> unit
val fold_pred_e : (edge -> 'a -> 'a) -> t -> vertex -> 'a -> 'a
val empty : t
val add_vertex : t -> vertex -> t
val remove_vertex : t -> vertex -> t
val add_edge : t -> vertex -> vertex -> t
val add_edge_e : t -> edge -> t
val remove_edge : t -> vertex -> vertex -> t
val remove_edge_e : t -> edge -> t
end
module TTopologicalTraversal :
sig
val fold : (TDependencies.V.t -> 'a -> 'a) -> TDependencies.t -> 'a -> 'a
val iter : (TDependencies.V.t -> unit) -> TDependencies.t -> unit
end
module TSCC :
sig
val scc : TDependencies.t -> int * (TDependencies.V.t -> int)
val scc_array : TDependencies.t -> TDependencies.V.t list array
val scc_list : TDependencies.t -> TDependencies.V.t list list
end
val get_structs_or_enums_in_type :
Ast.typ Utils.Pos.marked -> TVertexSet.t
val build_type_graph :
Ast.struct_ctx -> Ast.enum_ctx -> TDependencies.t
val check_type_cycles :
Ast.struct_ctx -> Ast.enum_ctx -> TVertex.t list

View File

@ -0,0 +1,8 @@
val needs_parens : Ast.expr Utils.Pos.marked -> bool
val format_var : Format.formatter -> Ast.Var.t -> unit
val format_location : Format.formatter -> Ast.location -> unit
val typ_needs_parens : Ast.typ Utils.Pos.marked -> bool
val format_typ :
Format.formatter -> Ast.typ Utils.Pos.marked -> unit
val format_expr :
Format.formatter -> Ast.expr Utils.Pos.marked -> unit

View File

@ -0,0 +1,66 @@
type scope_sigs_ctx =
((Ast.ScopeVar.t * Dcalc.Ast.typ) list * Dcalc.Ast.Var.t *
Dcalc.Ast.Var.t * Ast.StructName.t *
Ast.StructName.t)
Ast.ScopeMap.t
type ctx = {
structs : Ast.struct_ctx;
enums : Ast.enum_ctx;
scope_name : Ast.ScopeName.t;
scopes_parameters : scope_sigs_ctx;
scope_vars : (Dcalc.Ast.Var.t * Dcalc.Ast.typ) Ast.ScopeVarMap.t;
subscope_vars :
(Dcalc.Ast.Var.t * Dcalc.Ast.typ) Ast.ScopeVarMap.t
Ast.SubScopeMap.t;
local_vars : Dcalc.Ast.Var.t Ast.VarMap.t;
}
val empty_ctx :
Ast.struct_ctx ->
Ast.enum_ctx ->
scope_sigs_ctx -> Ast.ScopeName.t -> ctx
type scope_ctx = Dcalc.Ast.Var.t Ast.ScopeMap.t
val hole_var : Dcalc.Ast.Var.t
val translate_typ :
ctx -> Ast.typ Utils.Pos.marked -> Dcalc.Ast.typ Utils.Pos.marked
val merge_defaults :
Dcalc.Ast.expr Utils.Pos.marked Bindlib.box ->
Dcalc.Ast.expr Utils.Pos.marked Bindlib.box ->
Dcalc.Ast.expr Utils.Pos.marked Bindlib.box
val tag_with_log_entry :
Dcalc.Ast.expr Utils.Pos.marked Bindlib.box ->
Dcalc.Ast.log_entry ->
Utils.Uid.MarkedString.info list ->
Dcalc.Ast.expr Utils.Pos.marked Bindlib.box
val translate_expr :
ctx ->
Ast.expr Utils.Pos.marked ->
Dcalc.Ast.expr Utils.Pos.marked Bindlib.box
val translate_rule :
ctx ->
Ast.rule ->
Ast.rule list ->
Utils.Uid.MarkedString.info ->
Ast.StructName.t ->
Dcalc.Ast.expr Utils.Pos.marked Bindlib.box * ctx
val translate_rules :
ctx ->
Ast.rule list ->
Utils.Uid.MarkedString.info ->
Ast.StructName.t ->
Dcalc.Ast.expr Utils.Pos.marked Bindlib.box * ctx
val translate_scope_decl :
Ast.struct_ctx ->
Ast.enum_ctx ->
scope_sigs_ctx ->
Ast.ScopeName.t ->
Ast.scope_decl ->
Dcalc.Ast.expr Utils.Pos.marked Bindlib.box * Dcalc.Ast.struct_ctx
val build_scope_typ_from_sig :
(Ast.ScopeVar.t * Dcalc.Ast.typ) list ->
Ast.StructName.t ->
Ast.StructName.t -> Utils.Pos.t -> Dcalc.Ast.typ Utils.Pos.marked
val translate_program :
Ast.program ->
Ast.ScopeName.t ->
Dcalc.Ast.program * Dcalc.Ast.expr Utils.Pos.marked *
Dependency.TVertex.t list

12569
src/catala/surface/ast.mli Normal file

File diff suppressed because it is too large Load Diff

View File

@ -0,0 +1,75 @@
val translate_op_kind : Ast.op_kind -> Dcalc.Ast.op_kind
val translate_binop : Ast.binop -> Dcalc.Ast.binop
val translate_unop : Ast.unop -> Dcalc.Ast.unop
module LiftStructFieldMap :
sig
val lift_box :
'a Bindlib.box Scopelang.Ast.StructFieldMap.t ->
'a Scopelang.Ast.StructFieldMap.t Bindlib.box
end
module LiftEnumConstructorMap :
sig
val lift_box :
'a Bindlib.box Scopelang.Ast.EnumConstructorMap.t ->
'a Scopelang.Ast.EnumConstructorMap.t Bindlib.box
end
val disambiguate_constructor :
Name_resolution.context ->
(string Utils.Pos.marked option * string Utils.Pos.marked) list ->
Utils.Pos.t -> Scopelang.Ast.EnumName.t * Scopelang.Ast.EnumConstructor.t
val translate_expr :
Scopelang.Ast.ScopeName.t ->
Name_resolution.context ->
Ast.expression Utils.Pos.marked ->
Scopelang.Ast.expr Utils.Pos.marked Bindlib.box
val disambiguate_match_and_build_expression :
Scopelang.Ast.ScopeName.t ->
Name_resolution.context ->
Ast.match_cases ->
Scopelang.Ast.expr Utils.Pos.marked Bindlib.box
Scopelang.Ast.EnumConstructorMap.t * Scopelang.Ast.EnumName.t
val merge_conditions :
Scopelang.Ast.expr Utils.Pos.marked Bindlib.box option ->
Scopelang.Ast.expr Utils.Pos.marked Bindlib.box option ->
Utils.Pos.t -> Scopelang.Ast.expr Utils.Pos.marked Bindlib.box
val process_default :
Name_resolution.context ->
Scopelang.Ast.ScopeName.t ->
Desugared.Ast.ScopeDef.t Utils.Pos.marked ->
Scopelang.Ast.Var.t Utils.Pos.marked option ->
Scopelang.Ast.expr Utils.Pos.marked Bindlib.box option ->
Desugared.Ast.RuleName.t Utils.Pos.marked option ->
Ast.expression Utils.Pos.marked option ->
Ast.expression Utils.Pos.marked -> Desugared.Ast.rule
val process_def :
Scopelang.Ast.expr Utils.Pos.marked Bindlib.box option ->
Scopelang.Ast.ScopeName.t ->
Name_resolution.context ->
Desugared.Ast.program -> Ast.definition -> Desugared.Ast.program
val rule_to_def : Ast.rule -> Ast.definition
val process_rule :
Scopelang.Ast.expr Utils.Pos.marked Bindlib.box option ->
Scopelang.Ast.ScopeName.t ->
Name_resolution.context ->
Desugared.Ast.program -> Ast.rule -> Desugared.Ast.program
val process_assert :
Scopelang.Ast.expr Utils.Pos.marked Bindlib.box option ->
Scopelang.Ast.ScopeName.t ->
Name_resolution.context ->
Desugared.Ast.program -> Ast.assertion -> Desugared.Ast.program
val process_scope_use_item :
Ast.expression Utils.Pos.marked option ->
Scopelang.Ast.ScopeName.t ->
Name_resolution.context ->
Desugared.Ast.program ->
Ast.scope_use_item Utils.Pos.marked -> Desugared.Ast.program
val check_unlabeled_exception :
Scopelang.Ast.ScopeName.t ->
Name_resolution.context ->
Ast.scope_use_item Utils.Pos.marked -> unit
val process_scope_use :
Name_resolution.context ->
Desugared.Ast.program -> Ast.scope_use -> Desugared.Ast.program
val desugar_program :
Name_resolution.context ->
Ast.program -> Desugared.Ast.program

View File

@ -0,0 +1,2 @@
val fill_pos_with_legislative_info :
Ast.program -> Ast.program

View File

@ -0,0 +1,221 @@
val __sedlex_table_92 : string
val __sedlex_table_8 : string
val __sedlex_table_16 : string
val __sedlex_table_10 : string
val __sedlex_table_13 : string
val __sedlex_table_19 : string
val __sedlex_table_22 : string
val __sedlex_table_23 : string
val __sedlex_table_24 : string
val __sedlex_table_25 : string
val __sedlex_table_26 : string
val __sedlex_table_27 : string
val __sedlex_table_33 : string
val __sedlex_table_43 : string
val __sedlex_table_62 : string
val __sedlex_table_63 : string
val __sedlex_table_64 : string
val __sedlex_table_65 : string
val __sedlex_table_87 : string
val __sedlex_table_94 : string
val __sedlex_table_1 : string
val __sedlex_table_3 : string
val __sedlex_table_4 : string
val __sedlex_table_5 : string
val __sedlex_table_6 : string
val __sedlex_table_7 : string
val __sedlex_table_11 : string
val __sedlex_table_18 : string
val __sedlex_table_21 : string
val __sedlex_table_29 : string
val __sedlex_table_30 : string
val __sedlex_table_32 : string
val __sedlex_table_34 : string
val __sedlex_table_35 : string
val __sedlex_table_36 : string
val __sedlex_table_37 : string
val __sedlex_table_40 : string
val __sedlex_table_41 : string
val __sedlex_table_44 : string
val __sedlex_table_45 : string
val __sedlex_table_47 : string
val __sedlex_table_48 : string
val __sedlex_table_49 : string
val __sedlex_table_51 : string
val __sedlex_table_56 : string
val __sedlex_table_60 : string
val __sedlex_table_67 : string
val __sedlex_table_69 : string
val __sedlex_table_70 : string
val __sedlex_table_71 : string
val __sedlex_table_72 : string
val __sedlex_table_73 : string
val __sedlex_table_74 : string
val __sedlex_table_76 : string
val __sedlex_table_79 : string
val __sedlex_table_80 : string
val __sedlex_table_81 : string
val __sedlex_table_82 : string
val __sedlex_table_84 : string
val __sedlex_table_85 : string
val __sedlex_table_86 : string
val __sedlex_table_89 : string
val __sedlex_table_90 : string
val __sedlex_table_91 : string
val __sedlex_table_93 : string
val __sedlex_table_97 : string
val __sedlex_table_14 : string
val __sedlex_table_31 : string
val __sedlex_table_46 : string
val __sedlex_table_53 : string
val __sedlex_table_98 : string
val __sedlex_table_68 : string
val __sedlex_table_96 : string
val __sedlex_table_54 : string
val __sedlex_table_9 : string
val __sedlex_table_20 : string
val __sedlex_table_52 : string
val __sedlex_table_59 : string
val __sedlex_table_39 : string
val __sedlex_table_2 : string
val __sedlex_table_12 : string
val __sedlex_table_55 : string
val __sedlex_table_88 : string
val __sedlex_table_15 : string
val __sedlex_table_95 : string
val __sedlex_table_17 : string
val __sedlex_table_77 : string
val __sedlex_table_28 : string
val __sedlex_table_42 : string
val __sedlex_table_57 : string
val __sedlex_table_58 : string
val __sedlex_table_66 : string
val __sedlex_table_75 : string
val __sedlex_table_83 : string
val __sedlex_table_38 : string
val __sedlex_table_50 : string
val __sedlex_table_78 : string
val __sedlex_table_61 : string
val __sedlex_partition_51 : Uchar.t option -> int
val __sedlex_partition_3 : Uchar.t option -> int
val __sedlex_partition_30 : Uchar.t option -> int
val __sedlex_partition_44 : Uchar.t option -> int
val __sedlex_partition_19 : Uchar.t option -> int
val __sedlex_partition_93 : Uchar.t option -> int
val __sedlex_partition_37 : Uchar.t option -> int
val __sedlex_partition_27 : Uchar.t option -> int
val __sedlex_partition_78 : Uchar.t option -> int
val __sedlex_partition_74 : Uchar.t option -> int
val __sedlex_partition_6 : Uchar.t option -> int
val __sedlex_partition_11 : Uchar.t option -> int
val __sedlex_partition_103 : Uchar.t option -> int
val __sedlex_partition_33 : Uchar.t option -> int
val __sedlex_partition_41 : Uchar.t option -> int
val __sedlex_partition_102 : Uchar.t option -> int
val __sedlex_partition_4 : Uchar.t option -> int
val __sedlex_partition_12 : Uchar.t option -> int
val __sedlex_partition_15 : Uchar.t option -> int
val __sedlex_partition_82 : Uchar.t option -> int
val __sedlex_partition_5 : Uchar.t option -> int
val __sedlex_partition_61 : Uchar.t option -> int
val __sedlex_partition_86 : Uchar.t option -> int
val __sedlex_partition_90 : Uchar.t option -> int
val __sedlex_partition_60 : Uchar.t option -> int
val __sedlex_partition_101 : Uchar.t option -> int
val __sedlex_partition_104 : Uchar.t option -> int
val __sedlex_partition_106 : Uchar.t option -> int
val __sedlex_partition_108 : Uchar.t option -> int
val __sedlex_partition_110 : Uchar.t option -> int
val __sedlex_partition_112 : Uchar.t option -> int
val __sedlex_partition_13 : Uchar.t option -> int
val __sedlex_partition_46 : Uchar.t option -> int
val __sedlex_partition_56 : Uchar.t option -> int
val __sedlex_partition_65 : Uchar.t option -> int
val __sedlex_partition_94 : Uchar.t option -> int
val __sedlex_partition_64 : Uchar.t option -> int
val __sedlex_partition_39 : Uchar.t option -> int
val __sedlex_partition_105 : Uchar.t option -> int
val __sedlex_partition_31 : Uchar.t option -> int
val __sedlex_partition_34 : Uchar.t option -> int
val __sedlex_partition_22 : Uchar.t option -> int
val __sedlex_partition_54 : Uchar.t option -> int
val __sedlex_partition_98 : Uchar.t option -> int
val __sedlex_partition_1 : Uchar.t option -> int
val __sedlex_partition_29 : Uchar.t option -> int
val __sedlex_partition_7 : Uchar.t option -> int
val __sedlex_partition_18 : Uchar.t option -> int
val __sedlex_partition_89 : Uchar.t option -> int
val __sedlex_partition_63 : Uchar.t option -> int
val __sedlex_partition_109 : Uchar.t option -> int
val __sedlex_partition_57 : Uchar.t option -> int
val __sedlex_partition_58 : Uchar.t option -> int
val __sedlex_partition_91 : Uchar.t option -> int
val __sedlex_partition_66 : Uchar.t option -> int
val __sedlex_partition_17 : Uchar.t option -> int
val __sedlex_partition_96 : Uchar.t option -> int
val __sedlex_partition_23 : Uchar.t option -> int
val __sedlex_partition_55 : Uchar.t option -> int
val __sedlex_partition_83 : Uchar.t option -> int
val __sedlex_partition_2 : Uchar.t option -> int
val __sedlex_partition_45 : Uchar.t option -> int
val __sedlex_partition_81 : Uchar.t option -> int
val __sedlex_partition_95 : Uchar.t option -> int
val __sedlex_partition_97 : Uchar.t option -> int
val __sedlex_partition_10 : Uchar.t option -> int
val __sedlex_partition_36 : Uchar.t option -> int
val __sedlex_partition_80 : Uchar.t option -> int
val __sedlex_partition_70 : Uchar.t option -> int
val __sedlex_partition_72 : Uchar.t option -> int
val __sedlex_partition_28 : Uchar.t option -> int
val __sedlex_partition_87 : Uchar.t option -> int
val __sedlex_partition_100 : Uchar.t option -> int
val __sedlex_partition_107 : Uchar.t option -> int
val __sedlex_partition_111 : Uchar.t option -> int
val __sedlex_partition_113 : Uchar.t option -> int
val __sedlex_partition_9 : Uchar.t option -> int
val __sedlex_partition_26 : Uchar.t option -> int
val __sedlex_partition_85 : Uchar.t option -> int
val __sedlex_partition_40 : Uchar.t option -> int
val __sedlex_partition_42 : Uchar.t option -> int
val __sedlex_partition_52 : Uchar.t option -> int
val __sedlex_partition_59 : Uchar.t option -> int
val __sedlex_partition_25 : Uchar.t option -> int
val __sedlex_partition_43 : Uchar.t option -> int
val __sedlex_partition_62 : Uchar.t option -> int
val __sedlex_partition_20 : Uchar.t option -> int
val __sedlex_partition_99 : Uchar.t option -> int
val __sedlex_partition_21 : Uchar.t option -> int
val __sedlex_partition_68 : Uchar.t option -> int
val __sedlex_partition_88 : Uchar.t option -> int
val __sedlex_partition_53 : Uchar.t option -> int
val __sedlex_partition_32 : Uchar.t option -> int
val __sedlex_partition_16 : Uchar.t option -> int
val __sedlex_partition_67 : Uchar.t option -> int
val __sedlex_partition_71 : Uchar.t option -> int
val __sedlex_partition_8 : Uchar.t option -> int
val __sedlex_partition_24 : Uchar.t option -> int
val __sedlex_partition_35 : Uchar.t option -> int
val __sedlex_partition_50 : Uchar.t option -> int
val __sedlex_partition_76 : Uchar.t option -> int
val __sedlex_partition_79 : Uchar.t option -> int
val __sedlex_partition_14 : Uchar.t option -> int
val __sedlex_partition_38 : Uchar.t option -> int
val __sedlex_partition_49 : Uchar.t option -> int
val __sedlex_partition_77 : Uchar.t option -> int
val __sedlex_partition_48 : Uchar.t option -> int
val __sedlex_partition_73 : Uchar.t option -> int
val __sedlex_partition_84 : Uchar.t option -> int
val __sedlex_partition_69 : Uchar.t option -> int
val __sedlex_partition_47 : Uchar.t option -> int
val __sedlex_partition_75 : Uchar.t option -> int
val __sedlex_partition_92 : Uchar.t option -> int
module R = Re.Pcre
val is_code : bool ref
val code_string_acc : string ref
val update_acc : Sedlexing.lexbuf -> unit
val raise_lexer_error : Utils.Pos.t -> string -> 'a
val token_list_language_agnostic : (string * Parser.token) list
val token_list : (string * Parser.token) list
val lex_code : Sedlexing.lexbuf -> Parser.token
val lex_law : Sedlexing.lexbuf -> Parser.token
val lexer : Sedlexing.lexbuf -> Parser.token

View File

@ -0,0 +1,225 @@
val __sedlex_table_93 : string
val __sedlex_table_9 : string
val __sedlex_table_17 : string
val __sedlex_table_11 : string
val __sedlex_table_13 : string
val __sedlex_table_20 : string
val __sedlex_table_23 : string
val __sedlex_table_24 : string
val __sedlex_table_25 : string
val __sedlex_table_26 : string
val __sedlex_table_27 : string
val __sedlex_table_28 : string
val __sedlex_table_36 : string
val __sedlex_table_46 : string
val __sedlex_table_65 : string
val __sedlex_table_66 : string
val __sedlex_table_67 : string
val __sedlex_table_68 : string
val __sedlex_table_88 : string
val __sedlex_table_95 : string
val __sedlex_table_1 : string
val __sedlex_table_3 : string
val __sedlex_table_4 : string
val __sedlex_table_5 : string
val __sedlex_table_6 : string
val __sedlex_table_7 : string
val __sedlex_table_8 : string
val __sedlex_table_15 : string
val __sedlex_table_19 : string
val __sedlex_table_22 : string
val __sedlex_table_30 : string
val __sedlex_table_31 : string
val __sedlex_table_32 : string
val __sedlex_table_34 : string
val __sedlex_table_35 : string
val __sedlex_table_37 : string
val __sedlex_table_38 : string
val __sedlex_table_39 : string
val __sedlex_table_40 : string
val __sedlex_table_41 : string
val __sedlex_table_43 : string
val __sedlex_table_44 : string
val __sedlex_table_48 : string
val __sedlex_table_49 : string
val __sedlex_table_50 : string
val __sedlex_table_51 : string
val __sedlex_table_53 : string
val __sedlex_table_58 : string
val __sedlex_table_60 : string
val __sedlex_table_63 : string
val __sedlex_table_70 : string
val __sedlex_table_72 : string
val __sedlex_table_73 : string
val __sedlex_table_74 : string
val __sedlex_table_75 : string
val __sedlex_table_76 : string
val __sedlex_table_77 : string
val __sedlex_table_79 : string
val __sedlex_table_81 : string
val __sedlex_table_82 : string
val __sedlex_table_85 : string
val __sedlex_table_86 : string
val __sedlex_table_87 : string
val __sedlex_table_90 : string
val __sedlex_table_91 : string
val __sedlex_table_92 : string
val __sedlex_table_94 : string
val __sedlex_table_97 : string
val __sedlex_table_99 : string
val __sedlex_table_14 : string
val __sedlex_table_33 : string
val __sedlex_table_47 : string
val __sedlex_table_55 : string
val __sedlex_table_100 : string
val __sedlex_table_71 : string
val __sedlex_table_98 : string
val __sedlex_table_56 : string
val __sedlex_table_10 : string
val __sedlex_table_21 : string
val __sedlex_table_54 : string
val __sedlex_table_62 : string
val __sedlex_table_83 : string
val __sedlex_table_2 : string
val __sedlex_table_12 : string
val __sedlex_table_57 : string
val __sedlex_table_89 : string
val __sedlex_table_16 : string
val __sedlex_table_96 : string
val __sedlex_table_18 : string
val __sedlex_table_29 : string
val __sedlex_table_45 : string
val __sedlex_table_59 : string
val __sedlex_table_61 : string
val __sedlex_table_69 : string
val __sedlex_table_78 : string
val __sedlex_table_84 : string
val __sedlex_table_42 : string
val __sedlex_table_52 : string
val __sedlex_table_80 : string
val __sedlex_table_64 : string
val __sedlex_partition_54 : Uchar.t option -> int
val __sedlex_partition_3 : Uchar.t option -> int
val __sedlex_partition_48 : Uchar.t option -> int
val __sedlex_partition_18 : Uchar.t option -> int
val __sedlex_partition_99 : Uchar.t option -> int
val __sedlex_partition_44 : Uchar.t option -> int
val __sedlex_partition_59 : Uchar.t option -> int
val __sedlex_partition_28 : Uchar.t option -> int
val __sedlex_partition_32 : Uchar.t option -> int
val __sedlex_partition_84 : Uchar.t option -> int
val __sedlex_partition_66 : Uchar.t option -> int
val __sedlex_partition_80 : Uchar.t option -> int
val __sedlex_partition_6 : Uchar.t option -> int
val __sedlex_partition_10 : Uchar.t option -> int
val __sedlex_partition_65 : Uchar.t option -> int
val __sedlex_partition_109 : Uchar.t option -> int
val __sedlex_partition_39 : Uchar.t option -> int
val __sedlex_partition_108 : Uchar.t option -> int
val __sedlex_partition_4 : Uchar.t option -> int
val __sedlex_partition_60 : Uchar.t option -> int
val __sedlex_partition_74 : Uchar.t option -> int
val __sedlex_partition_11 : Uchar.t option -> int
val __sedlex_partition_88 : Uchar.t option -> int
val __sedlex_partition_5 : Uchar.t option -> int
val __sedlex_partition_63 : Uchar.t option -> int
val __sedlex_partition_92 : Uchar.t option -> int
val __sedlex_partition_96 : Uchar.t option -> int
val __sedlex_partition_62 : Uchar.t option -> int
val __sedlex_partition_107 : Uchar.t option -> int
val __sedlex_partition_110 : Uchar.t option -> int
val __sedlex_partition_112 : Uchar.t option -> int
val __sedlex_partition_114 : Uchar.t option -> int
val __sedlex_partition_116 : Uchar.t option -> int
val __sedlex_partition_118 : Uchar.t option -> int
val __sedlex_partition_12 : Uchar.t option -> int
val __sedlex_partition_50 : Uchar.t option -> int
val __sedlex_partition_71 : Uchar.t option -> int
val __sedlex_partition_29 : Uchar.t option -> int
val __sedlex_partition_58 : Uchar.t option -> int
val __sedlex_partition_100 : Uchar.t option -> int
val __sedlex_partition_35 : Uchar.t option -> int
val __sedlex_partition_70 : Uchar.t option -> int
val __sedlex_partition_46 : Uchar.t option -> int
val __sedlex_partition_111 : Uchar.t option -> int
val __sedlex_partition_25 : Uchar.t option -> int
val __sedlex_partition_30 : Uchar.t option -> int
val __sedlex_partition_26 : Uchar.t option -> int
val __sedlex_partition_24 : Uchar.t option -> int
val __sedlex_partition_57 : Uchar.t option -> int
val __sedlex_partition_104 : Uchar.t option -> int
val __sedlex_partition_34 : Uchar.t option -> int
val __sedlex_partition_17 : Uchar.t option -> int
val __sedlex_partition_95 : Uchar.t option -> int
val __sedlex_partition_69 : Uchar.t option -> int
val __sedlex_partition_115 : Uchar.t option -> int
val __sedlex_partition_97 : Uchar.t option -> int
val __sedlex_partition_72 : Uchar.t option -> int
val __sedlex_partition_15 : Uchar.t option -> int
val __sedlex_partition_102 : Uchar.t option -> int
val __sedlex_partition_22 : Uchar.t option -> int
val __sedlex_partition_31 : Uchar.t option -> int
val __sedlex_partition_47 : Uchar.t option -> int
val __sedlex_partition_89 : Uchar.t option -> int
val __sedlex_partition_2 : Uchar.t option -> int
val __sedlex_partition_49 : Uchar.t option -> int
val __sedlex_partition_87 : Uchar.t option -> int
val __sedlex_partition_101 : Uchar.t option -> int
val __sedlex_partition_103 : Uchar.t option -> int
val __sedlex_partition_9 : Uchar.t option -> int
val __sedlex_partition_43 : Uchar.t option -> int
val __sedlex_partition_86 : Uchar.t option -> int
val __sedlex_partition_14 : Uchar.t option -> int
val __sedlex_partition_76 : Uchar.t option -> int
val __sedlex_partition_78 : Uchar.t option -> int
val __sedlex_partition_33 : Uchar.t option -> int
val __sedlex_partition_93 : Uchar.t option -> int
val __sedlex_partition_106 : Uchar.t option -> int
val __sedlex_partition_113 : Uchar.t option -> int
val __sedlex_partition_117 : Uchar.t option -> int
val __sedlex_partition_119 : Uchar.t option -> int
val __sedlex_partition_8 : Uchar.t option -> int
val __sedlex_partition_21 : Uchar.t option -> int
val __sedlex_partition_91 : Uchar.t option -> int
val __sedlex_partition_67 : Uchar.t option -> int
val __sedlex_partition_73 : Uchar.t option -> int
val __sedlex_partition_41 : Uchar.t option -> int
val __sedlex_partition_16 : Uchar.t option -> int
val __sedlex_partition_36 : Uchar.t option -> int
val __sedlex_partition_40 : Uchar.t option -> int
val __sedlex_partition_64 : Uchar.t option -> int
val __sedlex_partition_55 : Uchar.t option -> int
val __sedlex_partition_61 : Uchar.t option -> int
val __sedlex_partition_68 : Uchar.t option -> int
val __sedlex_partition_19 : Uchar.t option -> int
val __sedlex_partition_105 : Uchar.t option -> int
val __sedlex_partition_20 : Uchar.t option -> int
val __sedlex_partition_94 : Uchar.t option -> int
val __sedlex_partition_56 : Uchar.t option -> int
val __sedlex_partition_38 : Uchar.t option -> int
val __sedlex_partition_77 : Uchar.t option -> int
val __sedlex_partition_1 : Uchar.t option -> int
val __sedlex_partition_7 : Uchar.t option -> int
val __sedlex_partition_23 : Uchar.t option -> int
val __sedlex_partition_27 : Uchar.t option -> int
val __sedlex_partition_37 : Uchar.t option -> int
val __sedlex_partition_82 : Uchar.t option -> int
val __sedlex_partition_85 : Uchar.t option -> int
val __sedlex_partition_13 : Uchar.t option -> int
val __sedlex_partition_45 : Uchar.t option -> int
val __sedlex_partition_53 : Uchar.t option -> int
val __sedlex_partition_83 : Uchar.t option -> int
val __sedlex_partition_52 : Uchar.t option -> int
val __sedlex_partition_79 : Uchar.t option -> int
val __sedlex_partition_90 : Uchar.t option -> int
val __sedlex_partition_42 : Uchar.t option -> int
val __sedlex_partition_75 : Uchar.t option -> int
val __sedlex_partition_51 : Uchar.t option -> int
val __sedlex_partition_81 : Uchar.t option -> int
val __sedlex_partition_98 : Uchar.t option -> int
module L = Lexer
module R = Re.Pcre
val token_list_en : (string * Parser.token) list
val lex_code_en : Sedlexing.lexbuf -> Parser.token
val lex_law_en : Sedlexing.lexbuf -> Parser.token
val lexer_en : Sedlexing.lexbuf -> Parser.token

View File

@ -0,0 +1,224 @@
val __sedlex_table_89 : string
val __sedlex_table_25 : string
val __sedlex_table_43 : string
val __sedlex_table_18 : string
val __sedlex_table_52 : string
val __sedlex_table_16 : string
val __sedlex_table_37 : string
val __sedlex_table_8 : string
val __sedlex_table_12 : string
val __sedlex_table_20 : string
val __sedlex_table_22 : string
val __sedlex_table_23 : string
val __sedlex_table_24 : string
val __sedlex_table_63 : string
val __sedlex_table_65 : string
val __sedlex_table_85 : string
val __sedlex_table_1 : string
val __sedlex_table_3 : string
val __sedlex_table_4 : string
val __sedlex_table_5 : string
val __sedlex_table_6 : string
val __sedlex_table_7 : string
val __sedlex_table_9 : string
val __sedlex_table_10 : string
val __sedlex_table_13 : string
val __sedlex_table_15 : string
val __sedlex_table_19 : string
val __sedlex_table_26 : string
val __sedlex_table_29 : string
val __sedlex_table_30 : string
val __sedlex_table_31 : string
val __sedlex_table_33 : string
val __sedlex_table_34 : string
val __sedlex_table_35 : string
val __sedlex_table_36 : string
val __sedlex_table_39 : string
val __sedlex_table_41 : string
val __sedlex_table_44 : string
val __sedlex_table_46 : string
val __sedlex_table_47 : string
val __sedlex_table_49 : string
val __sedlex_table_51 : string
val __sedlex_table_53 : string
val __sedlex_table_58 : string
val __sedlex_table_66 : string
val __sedlex_table_67 : string
val __sedlex_table_68 : string
val __sedlex_table_70 : string
val __sedlex_table_72 : string
val __sedlex_table_73 : string
val __sedlex_table_74 : string
val __sedlex_table_75 : string
val __sedlex_table_76 : string
val __sedlex_table_77 : string
val __sedlex_table_79 : string
val __sedlex_table_80 : string
val __sedlex_table_81 : string
val __sedlex_table_82 : string
val __sedlex_table_83 : string
val __sedlex_table_86 : string
val __sedlex_table_87 : string
val __sedlex_table_88 : string
val __sedlex_table_93 : string
val __sedlex_table_94 : string
val __sedlex_table_17 : string
val __sedlex_table_27 : string
val __sedlex_table_28 : string
val __sedlex_table_32 : string
val __sedlex_table_42 : string
val __sedlex_table_56 : string
val __sedlex_table_57 : string
val __sedlex_table_95 : string
val __sedlex_table_69 : string
val __sedlex_table_45 : string
val __sedlex_table_48 : string
val __sedlex_table_92 : string
val __sedlex_table_55 : string
val __sedlex_table_91 : string
val __sedlex_table_21 : string
val __sedlex_table_54 : string
val __sedlex_table_62 : string
val __sedlex_table_11 : string
val __sedlex_table_2 : string
val __sedlex_table_60 : string
val __sedlex_table_14 : string
val __sedlex_table_84 : string
val __sedlex_table_90 : string
val __sedlex_table_40 : string
val __sedlex_table_59 : string
val __sedlex_table_61 : string
val __sedlex_table_71 : string
val __sedlex_table_38 : string
val __sedlex_table_50 : string
val __sedlex_table_78 : string
val __sedlex_table_64 : string
val __sedlex_partition_65 : Uchar.t option -> int
val __sedlex_partition_3 : Uchar.t option -> int
val __sedlex_partition_20 : Uchar.t option -> int
val __sedlex_partition_74 : Uchar.t option -> int
val __sedlex_partition_24 : Uchar.t option -> int
val __sedlex_partition_109 : Uchar.t option -> int
val __sedlex_partition_29 : Uchar.t option -> int
val __sedlex_partition_101 : Uchar.t option -> int
val __sedlex_partition_116 : Uchar.t option -> int
val __sedlex_partition_48 : Uchar.t option -> int
val __sedlex_partition_16 : Uchar.t option -> int
val __sedlex_partition_42 : Uchar.t option -> int
val __sedlex_partition_83 : Uchar.t option -> int
val __sedlex_partition_1 : Uchar.t option -> int
val __sedlex_partition_13 : Uchar.t option -> int
val __sedlex_partition_37 : Uchar.t option -> int
val __sedlex_partition_41 : Uchar.t option -> int
val __sedlex_partition_117 : Uchar.t option -> int
val __sedlex_partition_23 : Uchar.t option -> int
val __sedlex_partition_36 : Uchar.t option -> int
val __sedlex_partition_51 : Uchar.t option -> int
val __sedlex_partition_86 : Uchar.t option -> int
val __sedlex_partition_72 : Uchar.t option -> int
val __sedlex_partition_110 : Uchar.t option -> int
val __sedlex_partition_91 : Uchar.t option -> int
val __sedlex_partition_61 : Uchar.t option -> int
val __sedlex_partition_98 : Uchar.t option -> int
val __sedlex_partition_106 : Uchar.t option -> int
val __sedlex_partition_115 : Uchar.t option -> int
val __sedlex_partition_120 : Uchar.t option -> int
val __sedlex_partition_123 : Uchar.t option -> int
val __sedlex_partition_5 : Uchar.t option -> int
val __sedlex_partition_49 : Uchar.t option -> int
val __sedlex_partition_111 : Uchar.t option -> int
val __sedlex_partition_12 : Uchar.t option -> int
val __sedlex_partition_39 : Uchar.t option -> int
val __sedlex_partition_53 : Uchar.t option -> int
val __sedlex_partition_67 : Uchar.t option -> int
val __sedlex_partition_62 : Uchar.t option -> int
val __sedlex_partition_11 : Uchar.t option -> int
val __sedlex_partition_26 : Uchar.t option -> int
val __sedlex_partition_31 : Uchar.t option -> int
val __sedlex_partition_34 : Uchar.t option -> int
val __sedlex_partition_47 : Uchar.t option -> int
val __sedlex_partition_87 : Uchar.t option -> int
val __sedlex_partition_102 : Uchar.t option -> int
val __sedlex_partition_19 : Uchar.t option -> int
val __sedlex_partition_88 : Uchar.t option -> int
val __sedlex_partition_18 : Uchar.t option -> int
val __sedlex_partition_107 : Uchar.t option -> int
val __sedlex_partition_56 : Uchar.t option -> int
val __sedlex_partition_14 : Uchar.t option -> int
val __sedlex_partition_30 : Uchar.t option -> int
val __sedlex_partition_94 : Uchar.t option -> int
val __sedlex_partition_113 : Uchar.t option -> int
val __sedlex_partition_7 : Uchar.t option -> int
val __sedlex_partition_25 : Uchar.t option -> int
val __sedlex_partition_50 : Uchar.t option -> int
val __sedlex_partition_103 : Uchar.t option -> int
val __sedlex_partition_10 : Uchar.t option -> int
val __sedlex_partition_68 : Uchar.t option -> int
val __sedlex_partition_89 : Uchar.t option -> int
val __sedlex_partition_57 : Uchar.t option -> int
val __sedlex_partition_2 : Uchar.t option -> int
val __sedlex_partition_4 : Uchar.t option -> int
val __sedlex_partition_66 : Uchar.t option -> int
val __sedlex_partition_90 : Uchar.t option -> int
val __sedlex_partition_97 : Uchar.t option -> int
val __sedlex_partition_112 : Uchar.t option -> int
val __sedlex_partition_8 : Uchar.t option -> int
val __sedlex_partition_59 : Uchar.t option -> int
val __sedlex_partition_95 : Uchar.t option -> int
val __sedlex_partition_6 : Uchar.t option -> int
val __sedlex_partition_79 : Uchar.t option -> int
val __sedlex_partition_81 : Uchar.t option -> int
val __sedlex_partition_73 : Uchar.t option -> int
val __sedlex_partition_82 : Uchar.t option -> int
val __sedlex_partition_104 : Uchar.t option -> int
val __sedlex_partition_122 : Uchar.t option -> int
val __sedlex_partition_21 : Uchar.t option -> int
val __sedlex_partition_28 : Uchar.t option -> int
val __sedlex_partition_38 : Uchar.t option -> int
val __sedlex_partition_64 : Uchar.t option -> int
val __sedlex_partition_93 : Uchar.t option -> int
val __sedlex_partition_75 : Uchar.t option -> int
val __sedlex_partition_40 : Uchar.t option -> int
val __sedlex_partition_44 : Uchar.t option -> int
val __sedlex_partition_100 : Uchar.t option -> int
val __sedlex_partition_46 : Uchar.t option -> int
val __sedlex_partition_52 : Uchar.t option -> int
val __sedlex_partition_114 : Uchar.t option -> int
val __sedlex_partition_119 : Uchar.t option -> int
val __sedlex_partition_45 : Uchar.t option -> int
val __sedlex_partition_54 : Uchar.t option -> int
val __sedlex_partition_55 : Uchar.t option -> int
val __sedlex_partition_43 : Uchar.t option -> int
val __sedlex_partition_63 : Uchar.t option -> int
val __sedlex_partition_27 : Uchar.t option -> int
val __sedlex_partition_32 : Uchar.t option -> int
val __sedlex_partition_105 : Uchar.t option -> int
val __sedlex_partition_118 : Uchar.t option -> int
val __sedlex_partition_33 : Uchar.t option -> int
val __sedlex_partition_58 : Uchar.t option -> int
val __sedlex_partition_80 : Uchar.t option -> int
val __sedlex_partition_17 : Uchar.t option -> int
val __sedlex_partition_22 : Uchar.t option -> int
val __sedlex_partition_35 : Uchar.t option -> int
val __sedlex_partition_99 : Uchar.t option -> int
val __sedlex_partition_121 : Uchar.t option -> int
val __sedlex_partition_15 : Uchar.t option -> int
val __sedlex_partition_60 : Uchar.t option -> int
val __sedlex_partition_69 : Uchar.t option -> int
val __sedlex_partition_77 : Uchar.t option -> int
val __sedlex_partition_96 : Uchar.t option -> int
val __sedlex_partition_85 : Uchar.t option -> int
val __sedlex_partition_92 : Uchar.t option -> int
val __sedlex_partition_9 : Uchar.t option -> int
val __sedlex_partition_71 : Uchar.t option -> int
val __sedlex_partition_78 : Uchar.t option -> int
val __sedlex_partition_70 : Uchar.t option -> int
val __sedlex_partition_76 : Uchar.t option -> int
val __sedlex_partition_84 : Uchar.t option -> int
val __sedlex_partition_108 : Uchar.t option -> int
module L = Lexer
module R = Re.Pcre
val token_list_fr : (string * Parser.token) list
val lex_code_fr : Sedlexing.lexbuf -> Parser.token
val lex_law_fr : Sedlexing.lexbuf -> Parser.token
val lexer_fr : Sedlexing.lexbuf -> Parser.token

View File

@ -0,0 +1,97 @@
type ident = string
type typ = Scopelang.Ast.typ
type unique_rulename = Ambiguous | Unique of Desugared.Ast.RuleName.t
type scope_context = {
var_idmap : Scopelang.Ast.ScopeVar.t Desugared.Ast.IdentMap.t;
label_idmap : Desugared.Ast.RuleName.t Desugared.Ast.IdentMap.t;
default_rulemap : unique_rulename Desugared.Ast.ScopeDefMap.t;
sub_scopes_idmap : Scopelang.Ast.SubScopeName.t Desugared.Ast.IdentMap.t;
sub_scopes : Scopelang.Ast.ScopeName.t Scopelang.Ast.SubScopeMap.t;
}
type struct_context = typ Utils.Pos.marked Scopelang.Ast.StructFieldMap.t
type enum_context = typ Utils.Pos.marked Scopelang.Ast.EnumConstructorMap.t
type context = {
local_var_idmap : Scopelang.Ast.Var.t Desugared.Ast.IdentMap.t;
scope_idmap : Scopelang.Ast.ScopeName.t Desugared.Ast.IdentMap.t;
struct_idmap : Scopelang.Ast.StructName.t Desugared.Ast.IdentMap.t;
field_idmap :
Scopelang.Ast.StructFieldName.t Scopelang.Ast.StructMap.t
Desugared.Ast.IdentMap.t;
enum_idmap : Scopelang.Ast.EnumName.t Desugared.Ast.IdentMap.t;
constructor_idmap :
Scopelang.Ast.EnumConstructor.t Scopelang.Ast.EnumMap.t
Desugared.Ast.IdentMap.t;
scopes : scope_context Scopelang.Ast.ScopeMap.t;
structs : struct_context Scopelang.Ast.StructMap.t;
enums : enum_context Scopelang.Ast.EnumMap.t;
var_typs : (typ Utils.Pos.marked * bool) Scopelang.Ast.ScopeVarMap.t;
}
val raise_unsupported_feature : string -> Utils.Pos.t -> 'a
val raise_unknown_identifier : string -> ident Utils.Pos.marked -> 'a
val get_var_typ : context -> Scopelang.Ast.ScopeVar.t -> typ Utils.Pos.marked
val is_var_cond : context -> Scopelang.Ast.ScopeVar.t -> bool
val get_var_uid :
Scopelang.Ast.ScopeName.t ->
context -> ident Utils.Pos.marked -> Scopelang.Ast.ScopeVar.t
val get_subscope_uid :
Scopelang.Ast.ScopeName.t ->
context -> ident Utils.Pos.marked -> Scopelang.Ast.SubScopeName.t
val is_subscope_uid : Scopelang.Ast.ScopeName.t -> context -> ident -> bool
val belongs_to :
context -> Scopelang.Ast.ScopeVar.t -> Scopelang.Ast.ScopeName.t -> bool
val get_def_typ : context -> Desugared.Ast.ScopeDef.t -> typ Utils.Pos.marked
val is_def_cond : context -> Desugared.Ast.ScopeDef.t -> bool
val process_subscope_decl :
Scopelang.Ast.ScopeName.t ->
context -> Ast.scope_decl_context_scope -> context
val is_type_cond : Ast.typ Utils.Pos.marked -> bool
val process_base_typ :
context ->
Ast.base_typ Utils.Pos.marked -> Scopelang.Ast.typ Utils.Pos.marked
val process_type :
context ->
Ast.typ Utils.Pos.marked -> Scopelang.Ast.typ Utils.Pos.marked
val process_data_decl :
Scopelang.Ast.ScopeName.t ->
context -> Ast.scope_decl_context_data -> context
val process_item_decl :
Scopelang.Ast.ScopeName.t ->
context -> Ast.scope_decl_context_item -> context
val add_def_local_var :
context -> ident Utils.Pos.marked -> context * Scopelang.Ast.Var.t
val process_scope_decl : context -> Ast.scope_decl -> context
val process_struct_decl : context -> Ast.struct_decl -> context
val process_enum_decl : context -> Ast.enum_decl -> context
val process_decl_item :
context -> Ast.code_item Utils.Pos.marked -> context
val process_code_block :
context ->
Ast.code_block ->
(context -> Ast.code_item Utils.Pos.marked -> context) -> context
val process_law_article_item :
context ->
Ast.law_article_item ->
(context -> Ast.code_item Utils.Pos.marked -> context) -> context
val process_law_structure :
context ->
Ast.law_structure ->
(context -> Ast.code_item Utils.Pos.marked -> context) -> context
val process_program_item :
context ->
Ast.program_item ->
(context -> Ast.code_item Utils.Pos.marked -> context) -> context
val get_def_key :
Ast.qident ->
Scopelang.Ast.ScopeName.t ->
context -> Utils.Pos.t -> Desugared.Ast.ScopeDef.t
val process_rule :
context -> Scopelang.Ast.ScopeName.t -> Ast.rule -> context
val process_definition :
context -> Scopelang.Ast.ScopeName.t -> Ast.definition -> context
val process_scope_use_item :
Scopelang.Ast.ScopeName.t ->
context -> Ast.scope_use_item Utils.Pos.marked -> context
val process_scope_use : context -> Ast.scope_use -> context
val process_use_item :
context -> Ast.code_item Utils.Pos.marked -> context
val form_context : Ast.program -> context

View File

@ -0,0 +1 @@
val current_file : string ref

View File

@ -0,0 +1,33 @@
module I = Parser.MenhirInterpreter
val state : 'semantic_value I.env -> int
val minimum : 'a -> 'a -> 'a -> 'a
val levenshtein_distance : string -> string -> int
val law_struct_list_to_tree :
Ast.program_item list -> Ast.program_item list
val syntax_hints_style : ANSITerminal.style list
val raise_parser_error :
Utils.Pos.t -> Utils.Pos.t option -> string -> string -> 'a
val fail :
Sedlexing.lexbuf ->
'semantic_value I.env ->
(string * Parser.token) list -> 'semantic_value I.env option -> 'a
val loop :
(unit -> Parser.token * Lexing.position * Lexing.position) ->
(string * Parser.token) list ->
Sedlexing.lexbuf ->
Ast.source_file_or_master I.env option ->
Ast.source_file_or_master I.checkpoint ->
Ast.source_file_or_master
val sedlex_with_menhir :
(Sedlexing.lexbuf -> Parser.token) ->
(string * Parser.token) list ->
(Lexing.position -> Ast.source_file_or_master I.checkpoint) ->
Sedlexing.lexbuf -> Ast.source_file_or_master
val parse_source_file :
Utils.Pos.input_file -> Utils.Cli.frontend_lang -> Ast.program
val expand_includes :
string ->
Ast.program_item list ->
Utils.Cli.frontend_lang -> Ast.program
val parse_top_level_file :
Utils.Pos.input_file -> Utils.Cli.frontend_lang -> Ast.program

View File

@ -0,0 +1 @@
val message : int -> string

View File

@ -0,0 +1,2 @@
val format_primitive_typ :
Format.formatter -> Ast.primitive_typ -> unit

49
src/catala/utils/cli.mli Normal file
View File

@ -0,0 +1,49 @@
type frontend_lang = [ `En | `Fr | `NonVerbose ]
type backend_lang = [ `En | `Fr ]
val to_backend_lang : frontend_lang -> backend_lang
val source_files : string list ref
val locale_lang : backend_lang ref
val contents : string ref
val debug_flag : bool ref
val style_flag : bool ref
val max_prec_digits : int ref
val trace_flag : bool ref
val file : string Cmdliner.Term.t
val debug : bool Cmdliner.Term.t
val unstyled : bool Cmdliner.Term.t
val trace_opt : bool Cmdliner.Term.t
val wrap_weaved_output : bool Cmdliner.Term.t
val backend : string Cmdliner.Term.t
type backend_option = Latex | Makefile | Html | Run | OCaml
val language : string option Cmdliner.Term.t
val max_prec_digits_opt : int option Cmdliner.Term.t
val ex_scope : string option Cmdliner.Term.t
val output : string option Cmdliner.Term.t
val pygmentize_loc : string option Cmdliner.Term.t
val catala_t :
(string ->
bool ->
bool ->
bool ->
string option ->
string ->
string option ->
int option -> bool -> string option -> string option -> 'a) ->
'a Cmdliner.Term.t
val version : string
val info : Cmdliner.Term.info
val print_with_style :
ANSITerminal.style list -> ('a, unit, string) format -> 'a
val debug_marker : unit -> string
val error_marker : unit -> string
val warning_marker : unit -> string
val result_marker : unit -> string
val log_marker : unit -> string
val concat_with_line_depending_prefix_and_suffix :
(int -> string) -> (int -> string) -> string list -> string
val add_prefix_to_each_line : string -> (int -> string) -> string
val debug_print : string -> unit
val error_print : string -> unit
val warning_print : string -> unit
val result_print : string -> unit
val log_print : string -> unit

View File

@ -0,0 +1,11 @@
exception StructuredError of (string * (string option * Pos.t) list)
val print_structured_error :
string -> (string option * Pos.t) list -> string
val raise_spanned_error : string -> ?span_msg:string -> Pos.t -> 'a
val raise_multispanned_error :
string -> (string option * Pos.t) list -> 'a
val raise_error : string -> 'a
val print_multispanned_warning :
string -> (string option * Pos.t) list -> unit
val print_spanned_warning : string -> ?span_msg:string -> Pos.t -> unit
val print_warning : string -> unit