package liquidsoap-lang

  1. Overview
  2. Docs

Terms and values in the Liquidsoap language.

include module type of struct include Runtime_term end
module Vars = Runtime_term.Vars

Sets of variables.

module Methods = Runtime_term.Methods
type custom = Runtime_term.custom
type custom_handler = Runtime_term.custom_handler = {
  1. name : string;
  2. to_string : custom -> string;
  3. to_json : pos:Pos.t list -> custom -> Json.t;
  4. compare : custom -> custom -> int;
  5. typ : Type.t;
}
type custom_term = Runtime_term.custom_term = {
  1. value : custom;
  2. handler : custom_handler;
}
type 'a term = 'a Runtime_term.term = {
  1. t : Type.t;
  2. term : 'a;
  3. flags : Flags.flags;
  4. methods : 'a term Methods.t;
}
val has_flag : 'a term -> Flags.flag -> bool
type ('a, 'b) func_argument = ('a, 'b) Runtime_term.func_argument = {
  1. label : string;
  2. as_variable : string option;
  3. default : 'a option;
  4. typ : 'b;
}
type ('a, 'b) func = ('a, 'b) Runtime_term.func = {
  1. mutable free_vars : Vars.t option;
  2. name : string option;
  3. arguments : ('a, 'b) func_argument list;
  4. body : 'a;
}
type 'a app = 'a * (string * 'a) list
type ('a, 'b) cast = ('a, 'b) Runtime_term.cast = {
  1. cast : 'a;
  2. typ : 'b;
}
type ('a, 'b) common_ast = [
  1. | `Custom of custom_term
  2. | `Tuple of 'a list
  3. | `Null
  4. | `Cast of ('a, 'b) cast
  5. | `Open of 'a * 'a
  6. | `Var of string
  7. | `Seq of 'a * 'a
]
type 'a invoke = 'a Runtime_term.invoke = {
  1. invoked : 'a;
  2. invoke_default : 'a option;
  3. meth : string;
}
type pattern = [
  1. | `PVar of string list
  2. | `PTuple of string list
]
type 'a let_t = 'a Runtime_term.let_t = {
  1. doc : Doc.Value.t option;
  2. replace : bool;
  3. pat : pattern;
  4. mutable gen : Type.var list;
  5. def : 'a;
  6. body : 'a;
}
type cached_env = Runtime_term.cached_env = {
  1. var_name : int;
  2. var_id : int;
  3. env : Typing.env;
}
type 'a runtime_ast = [
  1. | `Int of int
  2. | `Cache_env of cached_env ref
  3. | `Float of float
  4. | `String of string
  5. | `Bool of bool
  6. | `Let of 'a let_t
  7. | `List of 'a list
  8. | `App of 'a * (string * 'a) list
  9. | `Invoke of 'a invoke
  10. | `Hide of 'a * string list
  11. | `Encoder of string * 'a {encoder_params}15
  12. | `Fun of ('a, Type.t) func
]
type t = ast term
and ast = [
  1. | (t, Type.t) common_ast
  2. | t runtime_ast
]
type encoder = t Runtime_term.encoder
type encoder_params = t Runtime_term.encoder_params
type parsed_pos = Lexing.position * Lexing.position
exception Internal_error of Pos.t list * string

An internal error. Those should not happen in theory...

exception Parse_error of parsed_pos * string

A parsing error.

exception Unsupported_encoder of Pos.t option * string

Unsupported encoder

val conf_debug : bool ref
val conf_debug_errors : bool ref
val debug : bool Lazy.t

Are we in debugging mode?

val profile : bool ref
val ref_t : ?pos:Pos.t -> Type.t -> Type.t

Terms

module Custom = Term_custom
val unit : [> `Tuple of 'a list ]
val is_ground : [> `Bool of 'b | `Float of 'c | `Int of 'd | `List of 'a list | `Null | `String of 'e | `Tuple of 'a list ] term as 'a -> bool
val string_of_pat : [< `PTuple of string list | `PVar of string list ] -> string

String representation of terms, (almost) assuming they are in normal form.

val to_string : t -> string
val id : unit -> int

Create a new value.

val free_vars_pat : [< `PList of 'a list * Vars.elt option * 'a list | `PMeth of 'a option * (Vars.elt * [< `None | `Nullable | `Pattern of 'a ]) list | `PTuple of 'a list | `PVar of Vars.elt list PVar ] as 'a -> Vars.t
val bound_vars_pat : [< `PTuple of Vars.elt list | `PVar of Vars.elt list ] -> Vars.t
val free_term_vars : [< `App of 'a term * ('b * 'a term) list | `Bool of 'c | `Cache_env of 'd | `Cast of ('a term, 'e) cast | `Custom of 'f | `Encoder of ('h * [< `Anonymous of 'i | `Encoder of 'g | `Labelled of 'j * 'a term ] list) as 'g | `Float of 'k | `Fun of ('a term, 'l) func | `Hide of 'a term * string list | `Int of 'm | `Invoke of 'a term invoke | `Let of 'a term let_t | `List of 'a term list | `Null | `Open of 'a term * 'a term | `Seq of 'a term * 'a term | `String of 'n | `Tuple of 'a term list | `Var of Vars.elt ] as 'a term -> Vars.t
val free_fun_vars : ([< `App of 'b * ('d * 'b) list | `Bool of 'e | `Cache_env of 'f | `Cast of ('b, 'g) cast | `Custom of 'h | `Encoder of ('j * [< `Anonymous of 'k | `Encoder of 'i | `Labelled of 'l * 'b ] list) as 'i | `Float of 'm | `Fun of 'a | `Hide of 'c term * string list | `Int of 'n | `Invoke of 'b invoke | `Let of 'b let_t | `List of 'b list | `Null | `Open of 'b * 'b | `Seq of 'b * 'b | `String of 'o | `Tuple of 'b list | `Var of Vars.elt ] as 'c term as 'b, 'p) func as 'a -> Vars.t
val free_vars : ?bound:string list -> [< `App of 'a * ('c * 'a) list | `Bool of 'd | `Cache_env of 'e | `Cast of ('a, 'f) cast | `Custom of 'g | `Encoder of ('i * [< `Anonymous of 'j | `Encoder of 'h | `Labelled of 'k * 'a ] list) as 'h | `Float of 'l | `Fun of ('a, 'm) func | `Hide of 'b term * string list | `Int of 'n | `Invoke of 'a invoke | `Let of 'a let_t | `List of 'a list | `Null | `Open of 'a * 'a | `Seq of 'a * 'a | `String of 'o | `Tuple of 'a list | `Var of Vars.elt ] as 'b term as 'a -> Vars.t
val can_ignore : Type.t -> bool

Values which can be ignored (and will thus not raise a warning if ignored).

Basic checks and errors

exception Unbound of Pos.Option.t * string

Trying to use an unbound variable.

exception Ignored of t

Silently discarding a meaningful value.

exception No_label of t * string * bool * t

No_label (f,lbl,first,x) indicates that the parameter x could not be passed to the function f because the latter has no label lbl. The first information tells whether lbl=x is the first parameter with label lbl in the considered application, which makes the message a bit more helpful.

exception Duplicate_label of Pos.Option.t * string

A function defines multiple arguments with the same label.

exception Missing_arguments of Pos.Option.t * (string * Type.t) list

Some mandatory arguments with given label and typed were not passed to the function during an application.

exception Unused_variable of string * Pos.t

Check that all let-bound variables are used. No check is performed for variable arguments. This cannot be done at parse-time (as for the computation of the free variables of functions) because we need types, as well as the ability to distinguish toplevel and inner let-in terms.

val check_unused : throw:(exn -> unit) -> lib:bool -> [< `App of 'a * ('c * 'a) list | `Bool of 'd | `Cache_env of 'e | `Cast of ('a, 'f) cast | `Custom of 'g | `Encoder of ('i * [< `Anonymous of 'j | `Encoder of 'h | `Labelled of 'k * 'a ] list) as 'h | `Float of 'l | `Fun of ('a, 'm) func | `Hide of 'b term * string list | `Int of 'n | `Invoke of 'a invoke | `Let of 'a let_t | `List of 'a list | `Null | `Open of 'a * 'a | `Seq of 'a * 'a | `String of 'o | `Tuple of 'a list | `Var of Vars.elt ] as 'b term as 'a -> unit
module type Custom = sig ... end
module type CustomDef = sig ... end
module MkCustom (Def : CustomDef) : sig ... end
val make : ?pos:Pos.t -> ?t:Type.t -> ?flags:Flags.flags -> ?methods:ast term Methods.t -> ast -> ast term

Create a new value.

val fresh : handler:Type.Fresh.mapper -> [< `App of 'a * ('c * 'a) list | `Bool of 'd | `Cache_env of 'e | `Cast of ('a, Type_base.t) cast | `Custom of 'f | `Encoder of ('h * [ `Anonymous of 'i | `Encoder of 'g | `Labelled of 'j * 'a ] list) as 'g | `Float of 'k | `Fun of ('a, Type_base.t) func | `Hide of 'a * 'l | `Int of 'm | `Invoke of 'a invoke | `Let of 'a let_t | `List of 'a list | `Null | `Open of 'a * 'a | `Seq of 'a * 'a | `String of 'n | `Tuple of 'a list | `Var of 'o App Cast Encoder Fun Hide Invoke Let List Null Open Seq Tuple Var ] as 'b term as 'a -> 'a
OCaml

Innovation. Community. Security.