package minicaml

  1. Overview
  2. Docs
module T = ANSITerminal
module D = Util.Dict
type ide = string

A value identifier

val equal_ide : ide -> ide -> Ppx_deriving_runtime.bool
val compare_ide : ide -> ide -> Ppx_deriving_runtime.int
type complext = Complex.t

A type wrapper for complex numbers where equality, ordering and showing are defined

val show_complext : complext -> Ppx_deriving_runtime.string
val equal_complext : complext -> complext -> Ppx_deriving_runtime.bool
val compare_complext : complext -> complext -> Ppx_deriving_runtime.int
type puret =
  1. | Impure
  2. | Uncertain
  3. | Pure
  4. | Numerical

A type representing if a computation is pure or not

val equal_puret : puret -> puret -> Ppx_deriving_runtime.bool
val compare_puret : puret -> puret -> Ppx_deriving_runtime.int
val isuncertain : puret -> bool
val isnumerical : puret -> bool
val isstrictlypure : puret -> bool
val isimpure : puret -> bool
val ispure : puret -> bool
type primitiveinfo = ide * int * puret

Contains a primitive's name, number of arguments and pureness

val show_primitiveinfo : primitiveinfo -> Ppx_deriving_runtime.string
val equal_primitiveinfo : primitiveinfo -> primitiveinfo -> Ppx_deriving_runtime.bool
val compare_primitiveinfo : primitiveinfo -> primitiveinfo -> Ppx_deriving_runtime.int
type expr =
  1. | Unit
  2. | Purity of puret * expr
  3. | NumInt of int
  4. | NumFloat of float
  5. | NumComplex of complext
  6. | Boolean of bool
  7. | String of string
  8. | Symbol of ide
  9. | List of expr list
  10. | Cons of expr * expr
  11. | Concat of expr * expr
  12. | Dict of (ide * expr) list
  13. | Plus of expr * expr
  14. | Sub of expr * expr
  15. | Div of expr * expr
  16. | Mult of expr * expr
  17. | Eq of expr * expr
  18. | Gt of expr * expr
  19. | Lt of expr * expr
  20. | Ge of expr * expr
  21. | Le of expr * expr
  22. | And of expr * expr
  23. | Or of expr * expr
  24. | Not of expr
  25. | IfThenElse of expr * expr * expr
  26. | Let of assignment_type list * expr
  27. | Lambda of ide * expr
  28. | Apply of expr * expr
  29. | ApplyPrimitive of primitiveinfo * expr list
  30. | Compose of expr * expr
  31. | Sequence of expr list

The type representing Abstract Syntax Tree expressions

and assignment_type = bool * ide * expr
val show_assignment_type : assignment_type -> Ppx_deriving_runtime.string
val equal_expr : expr -> expr -> Ppx_deriving_runtime.bool
val compare_expr : expr -> expr -> Ppx_deriving_runtime.int
val compare_assignment_type : assignment_type -> assignment_type -> Ppx_deriving_runtime.int
val findbody : expr -> expr

Function that finds a nested lambda body

Function that finds and replaces a (nested) lambda body

val replacebody : expr -> expr -> expr

Function that finds and replaces a (nested) lambda body

Function that creates a list with the params of a nested lambda

val findparams : expr -> ide list

Function that creates a list with the params of a nested lambda

val simple_show_expr : expr -> Ppx_deriving_runtime.string

Show a short representation of an expression (useful for stack traces)

val lambda_from_paramlist : ide list -> expr -> expr

Creates a nested Lambda from a list of params

val apply_from_exprlist : expr list -> expr -> expr

Creates a nested Apply from a list of expressions

val symbols_from_strings : ide list -> expr list

Creates a list of Symbol from a list of string

type directive =
  1. | Dumpenv
  2. | Dumppurityenv
  3. | Includefile of string
  4. | Includefileasmodule of string * ide option
  5. | Setpurity of puret
  6. | Setverbose of int

A type containing directives information

val show_directive : directive -> Ppx_deriving_runtime.string
val equal_directive : directive -> directive -> Ppx_deriving_runtime.bool
val compare_directive : directive -> directive -> Ppx_deriving_runtime.int
type command =
  1. | Directive of directive
  2. | Expr of expr
  3. | Def of assignment_type list

A type useful for evaluating files, stating if a command is an expression or simply a "global" declaration (appended to environment)

val show_command : command -> Ppx_deriving_runtime.string
val equal_command : command -> command -> Ppx_deriving_runtime.bool
val compare_command : command -> command -> Ppx_deriving_runtime.int
type evt =
  1. | EvtUnit
  2. | EvtInt of int
  3. | EvtFloat of float
  4. | EvtComplex of complext
  5. | EvtBool of bool
  6. | EvtString of string
  7. | EvtList of evt list
  8. | EvtDict of (ide * evt) list
    (*

    Recursion is achieved by keeping an optional function name in the constructor

    *)
  9. | Closure of ide option * ide * expr * env_type
    (*

    Abstraction that permits treating primitives as closures

    *)

A type that represents an evaluated (reduced) value

and type_wrapper =
  1. | LazyExpression of expr
  2. | AlreadyEvaluated of evt
and env_type = (ide, type_wrapper) D.t
and typeinfo =
  1. | TUnit
  2. | TBool
  3. | TNumber
  4. | TInt
  5. | TFloat
  6. | TComplex
  7. | TString
  8. | TList
  9. | TDict
  10. | TLambda

A type containing information about types

val show_type_wrapper : type_wrapper -> Ppx_deriving_runtime.string
val show_env_type : env_type -> Ppx_deriving_runtime.string
val show_typeinfo : typeinfo -> Ppx_deriving_runtime.string
val equal_evt : evt -> evt -> Ppx_deriving_runtime.bool
val equal_type_wrapper : type_wrapper -> type_wrapper -> Ppx_deriving_runtime.bool
val equal_env_type : env_type -> env_type -> Ppx_deriving_runtime.bool
val equal_typeinfo : typeinfo -> typeinfo -> Ppx_deriving_runtime.bool
val compare_evt : evt -> evt -> Ppx_deriving_runtime.int
val compare_type_wrapper : type_wrapper -> type_wrapper -> Ppx_deriving_runtime.int
val compare_env_type : env_type -> env_type -> Ppx_deriving_runtime.int
val compare_typeinfo : typeinfo -> typeinfo -> Ppx_deriving_runtime.int
val show_tinfo : typeinfo -> string
val generate_prim_params : int -> string list
val show_unpacked_evt : evt -> Ppx_deriving_runtime.string
val findevtparams : evt -> ide list

Function that creates a list with the params of a nested lambda in a Closure

type primitive =
  1. | Primitive of evt list -> evt * primitiveinfo

A type representing a primitive

val get_primitive_purity : primitive -> puret

Get the purity of a primitive

val get_primitive_function : primitive -> evt list -> evt

Get the actual function from a primitive type

val get_primitive_info : primitive -> primitiveinfo

Get the information from a primitive type

val lambda_from_primitive : primitive -> expr

Generate a lambda from a primitive

type purityenv_type = (ide, puret) Util.Dict.t

An environment type containing identifier - purity couples

val show_purityenv_type : purityenv_type -> Ppx_deriving_runtime.string
type stackframe =
  1. | StackValue of int * expr * stackframe
  2. | EmptyStack

A recursive type representing a stacktrace frame

val show_stackframe : stackframe -> Ppx_deriving_runtime.string
val push_stack : stackframe -> expr -> stackframe

Push an AST expression into a stack

  • parameter s

    The stack where to push the expression

  • parameter e

    The expression to push

val pop_stack : stackframe -> stackframe

Pop an AST expression from a stack

val depth_of_stack : stackframe -> int
val string_of_stack : int -> stackframe -> string
type evalstate = {
  1. env : env_type;
  2. purityenv : purityenv_type;
  3. verbosity : int;
  4. stack : stackframe;
  5. mutable printresult : bool;
  6. purity : puret;
}

Options for the eval function

type location =
  1. | Location of Lexing.position * Lexing.position
    (*

    delimited location

    *)
  2. | Nowhere
    (*

    no location

    *)

The location of a lexeme in code

val location_of_lex : Lexing.lexbuf -> location

Get the location of a lexeme

type internalerrort =
  1. | Fatal of string
  2. | InternalFailure of string
  3. | WrongPrimitiveArgs
  4. | IndexOutOfBounds
  5. | TypeError of string
  6. | UnboundVariable of string
  7. | ListError of string
  8. | DictError of string
  9. | FileNotFoundError of string
  10. | PurityError of string
  11. | SyntaxError of string

Exceptions

val show_internalerrort : internalerrort -> Ppx_deriving_runtime.string
exception InternalError of location * internalerrort * stackframe

Exception Error (loc, err, msg) indicates an error of type err with error message msg, occurring at location loc.

val sraises : Lexing.lexbuf -> string -> stackframe -> 'a

Utility function to raise a syntax error quickly

val sraise : Lexing.lexbuf -> string -> 'a
val iraises : internalerrort -> stackframe -> 'a

Utility function to raise an internal error without a location

val iraise : internalerrort -> 'a
val traises : string -> stackframe -> 'a

Utility function to raise a type error without a location

val traise : string -> 'a
val print_location : location -> string

Print the location of a lexeme

val print_message : ?color:T.color -> ?loc:location -> string -> string -> unit

Print a message at a given location loc of message type msg_type.

val print_error : (location * internalerrort * 'a) -> unit

Print the caught error

val print_stacktrace : ('a * 'b * stackframe) -> int -> unit
val read_file : (Lexing.lexbuf -> 'a) -> string -> 'a

Parse the contents from a file, using a given parser.