funcons-tools-0.1.0.0: A modular interpreter for executing funcons

Safe HaskellNone
LanguageHaskell2010

Funcons.Core

Description

This module exports smart constructors for building funcon terms from a large collections of funcons. Module Funcons.EDSL can be used to construct funcons. Module Funcons.Tools provides functions for creating executables.

Apologies for the disorganisation of this file, most of its exports exports have been generated.

If a funcon is called 'handle-thrown', its smart constructor is called handle_thrown_ (hypens replaced by underscores and an additional underscore at the end). Each smart constructors has a single argument, a list (of type ([Funcons]) representing the actual arguments of a funcon application. For example, the funcon 'integer-add' can be applied to an arbitrary number of (integer) arguments, e.g. integer_add_ [int_ 3, int_ 4, int_ 5].

Synopsis

Documentation

list_ :: [Funcons] -> Funcons

Creates a list of funcon terms.

tuple_ :: [Funcons] -> Funcons

Creates a tuple of funcon terms.

set_ :: [Funcons] -> Funcons

Creates a set of funcon terms.

int_ :: Int -> Funcons

Creates an integer literal.

nat_ :: Int -> Funcons

Creates a natural literal.

string_ :: String -> Funcons

Creates a string literal.

entities :: [t]

entities :: [t]

left_to_right_ :: [Funcons] -> Funcons

left-to-right(X1,...,Xn) executes X1 ,...,Xn from left to right, computing a tuple of result values (V1,...,VN) .

entities :: [t]

atomic_ :: [Funcons] -> Funcons

atomic(X) treats the complete evaluation of X as one step, regardless of how many steps that evaluation actually takes.

entities :: [t]

sequential_ :: [Funcons] -> Funcons

sequential(X1,...,Xn) executes X1 ,...,Xn from left to right, computing a tuple of results. Any result values that are the empty tuple () are discarded, so the resultant tuple may be smaller.

entities :: [t]

vector_map_ :: [Funcons] -> Funcons

vector-map(F,V) maps the computation F over the vector V , from left to right, evaluating F for each given value in V .

entities :: [t]

set_map_ :: [Funcons] -> Funcons

set-map(F,S) maps the computation F over the set S , interleaved, evaluating F for each given value in S , uniting the results.

entities :: [t]

list_map_ :: [Funcons] -> Funcons

list-map(F,L) maps the computation F over the list L , from left to right, evaluating F for each given value in L .

entities :: [t]

tuple_map_ :: [Funcons] -> Funcons

tuple-map(F,Tup) maps the computation F over a tuple Tup , from left to right, evaluating F for each given value in the Tup .

entities :: [t]

map_map_ :: [Funcons] -> Funcons

map-map(X,M) maps the computation F over the map M , interleaved, evaluating F for each given keyentry pair in M/ , uniting the results.

entities :: [t]

lists_map_ :: [Funcons] -> Funcons

lists-map(F,(List+)) maps the computation F over N lists of equal length L, in parallel from left to right. F is evaluated L times, once for each given tuple of argument values, where the Nth component of each tuple is drawn from the Nth argument list.

entities :: [t]

multiset_filter_ :: [Funcons] -> Funcons

multiset-filter(P,MS) deletes all values from the the multiset MS that do not satisfy the predicate P . P is given a values /naturals pair.

entities :: [t]

set_filter_ :: [Funcons] -> Funcons

set-filter(P,S) deletes all entries from the the set S that do not satisfy the predicate P .

entities :: [t]

map_filter_ :: [Funcons] -> Funcons

map-filter(P,M) discards all entries from the map M that do not satisify the predicate P . P is given a key/value pair.

entities :: [t]

list_filter_ :: [Funcons] -> Funcons

list-filter(P,L) discards all elements from the list L that do not satisify the predicate P .

entities :: [t]

list_foldl_ :: [Funcons] -> Funcons

list-foldl(F,A,L) reduces a list L to a single value by folding it from the left, using A as the initial accumulator value, and iteratively updating the accumulator by executing the computation F with the accumulator value and the head of the remaining list as its pair of arguments.

entities :: [t]

list_foldr_ :: [Funcons] -> Funcons

list-foldr(F,A,L) reduces a list L to a single value by folding it from the right, using A as the initial accumulator value, and iteratively updating the accumulator by executing the computation F with the the last element of the remaining list and the accumulator value as its pair of arguments.

entities :: [t]

while_ :: [Funcons] -> Funcons

while(B,C) first evaluates B . Depending on whether the computed value is true or false , it then executes C and repeats, or terminates normally.

entities :: [t]

do_while_ :: [Funcons] -> Funcons

do-while(C,B) first executes C . Then it evaluates B . Depending on whether the value is true or false , it then repeats, or terminates normally.

entities :: [t]

if_then_else_ :: [Funcons] -> Funcons

if-then-else(B,X,Y) first evaluates B . Depending on whether the computed value is true or false , it then evaluates X or Y .

entities :: [t]

stuck_ :: Funcons

stuck cannot be evaluated.

entities :: [t]

handle_thrown_ :: [Funcons] -> Funcons

handle-thrown(E,H) evaluates E . If E terminates normally with value V , then V is returned and H is ignored. If E terminates abruptly with value V , then H is executed with given-value V .

entities :: [t]

finally_ :: [Funcons] -> Funcons

finally(C,F) first executes C . If C terminates normally, then F executes. If C abruptly terminates with a thrown value V , then F executes, and then V is rethrown.

entities :: [t]

throw_ :: [Funcons] -> Funcons

throw(V) terminates abruptly with value V .

entities :: [t]

handle_recursively_ :: [Funcons] -> Funcons

handle-recursively behaves similarly to handle-thrown , except that another copy of the handler attempts to handle any values thrown by the handler. Thus, many thrown values may get caught by the same handler.

entities :: [t]

plug_ :: [Funcons] -> Funcons

plug(E,V) plugs the value V into a hole that occurs as a subterm within the computation E , provided the hole is in an evaluable position.

entities :: [t]

shift_ :: [Funcons] -> Funcons

shift(F) emits a control-signal that, when handled by an enclosing reset , will cause F to the current continuation of shift(F) , Unlike control , any application of the captured continuation delimits any control operators in its body.

entities :: [t]

prompt_ :: [Funcons] -> Funcons

prompt is a delimiter for the control and call-cc operators.

entities :: [t]

control_ :: [Funcons] -> Funcons

control(F) emits a control-signal that, when handled by an enclosing prompt , will cause F to the current continuation of control(F) , instead of continuing the current computation.

entities :: [t]

call_cc_ :: [Funcons] -> Funcons

call-cc(F) emits a control-signal that, when handled by an enclosing prompt , applies F to the current continuation. If that current continuation argument is invoked, then the current computation will terminate up to the enclosing prompt when that continuation terminates.

entities :: [t]

reset_ :: [Funcons] -> Funcons

reset is a delimiter for the shift operator. A consequence of our choice of definition of shift is that the semantics of reset conincide exactly with those of prompt , and thus the two can be used interchangeably.

entities :: [t]

hole_ :: Funcons

A hole in a term cannot proceed until it receives a resume-signal containing a value to fill the hole.

entities :: [t]

abort_ :: [Funcons] -> Funcons

abort(V) emits a control-signal that, when handled by an enclosing prompt , aborts the current computation up to that enclosing prompt , returning the value V .

entities :: [t]

else_ :: [Funcons] -> Funcons

else(X1,X2,...,XN) evaluates each computation X in turn, until one does *not*fail, returning the result of the successful computation.

entities :: [t]

check_true_ :: [Funcons] -> Funcons

check-true(B) fails if B is false .

entities :: [t]

fail_ :: Funcons

fail terminates abruptly.

entities :: [t]

entities :: [t]

dereference_ :: [Funcons] -> Funcons

dereference(P) fails if the pointer P is null , otherwise it returns the value referenced by P .

entities :: [t]

print_list_ :: [Funcons] -> Funcons

print-list(L) emits the values contained in the list L on the standard-out .

entities :: [t]

print_ :: [Funcons] -> Funcons

print(E) evaluates E and emits the resulting value on the standard-out .

entities :: [t]

read_ :: Funcons

read consumes a single value from the standard-in , and returns it.

entities :: [t]

effect_ :: [Funcons] -> Funcons

effect(E) evaluates E , then discards the computed value.

entities :: [t]

allocate_map_ :: [Funcons] -> Funcons

allocate-map(M) computes a map where the entries are uninitialised variables of types given by M .

entities :: [t]

general_assign_ :: [Funcons] -> Funcons

general-assign(Var,Val) assigns the (potentially composite) value Val to the (potentialy composite) variable Var .

entities :: [t]

general_assigned_ :: [Funcons] -> Funcons

general-assigned(V) takes a (potentially composite) value V , which may contain variables , and computes the value of V with all such contained variables replaced by the values currently assigned to those variables.

entities :: [t]

allocate_vector_ :: [Funcons] -> Funcons

allocate-vector(T,N) computes a vector of length N , containing uninitialised variables of type T .

entities :: [t]

entities :: [t]

current_value_ :: [Funcons] -> Funcons

If V is a variable, current-value(V) computes the value currently assigned to V . Otherwise it evaluates to V .

entities :: [t]

assigned_ :: [Funcons] -> Funcons

assigned(Var) gives the value currently assigned to the variable Var . If this value is uninitialised , then computation fail s.

entities :: [t]

allocate_initialised_variable_ :: [Funcons] -> Funcons

allocate-initialised-variable(T,V) computes a simple variable for storing values of type T , and initialises its value to V . This fail s if the type of V is not a subtype of T .

entities :: [t]

allocate_variable_ :: [Funcons] -> Funcons

allocate-variable(T) computes an (uninitialised) simple variable for storing values of type T .

entities :: [t]

deallocate_variable_ :: [Funcons] -> Funcons

deallocate-variable(V) deletes the variable V from the current store .

entities :: [t]

assign_ :: [Funcons] -> Funcons

assign(Var,Val) assigns Val to the the variable Var , provided Var has not been deallocated and Val is of the appropriate type for storing in Var .

entities :: [t]

variable_accepting_type_ :: [Funcons] -> Funcons

variable-accepting-type(Var) returns the type of values that Var accepts. variable-producing-type(Var) returns the type of values that Var can produce.

entities :: [t]

allocate_initialised_link_ :: [Funcons] -> Funcons

allocate-initialised-link(T,V) computes a link to values of type T , and sets its value to V . This fail s if the type of V is not a subtype of T .

entities :: [t]

allocate_link_ :: [Funcons] -> Funcons

allocate-link(T) computes a link to values of type T .

entities :: [t]

follow_if_link_ :: [Funcons] -> Funcons

If V is a link, then follow-if-link(V) gives the value to which the link V has been set. Otherwise, V is returned.

entities :: [t]

link_accepting_type_ :: [Funcons] -> Funcons

link-accepting-type(L) returns the type of values that L accepts. link-producing-type(L) returns the type of values that L can produce.

entities :: [t]

follow_link_ :: [Funcons] -> Funcons

follow-link(L) gives the value linked to by L . If this value is uninitialised , then computation fail s.

entities :: [t]

entities :: [t]

set_link_ :: [Funcons] -> Funcons

set-link(L,V) sets the value linked to by L to be V . If L has already been set, then computation instead fail s.

entities :: [t]

given_ :: Funcons

given returns the current given value.

given1_ :: Funcons

given1 returns the first component of the currently given tuple. given2 returns the second component of the currently given tuple. given3 returns the third component of the currently given tuple.

entities :: [t]

give_ :: [Funcons] -> Funcons

give(V,X) evaluates X with V as the given value.

entities :: [t]

fresh_atom_ :: Funcons

fresh-atom computes a fresh atom, distinct from all other atoms previously generated by other occurrences of fresh-atom .

entities :: [t]

fresh_binder_ :: Funcons

fresh-binder generates a fresh binder, distinct from all identifiers and any binders previously generated by other occurrences of fresh-binder .

entities :: [t]

recursive_ :: [Funcons] -> Funcons

recursive(Bs,D) evaluates D with potential recursion on the binders in Bs (which need not be the same as the set of binders bound by D ).

entities :: [t]

bind_recursively_ :: [Funcons] -> Funcons

bind-recursively(B,E) binds B to the result of evaluating E , which may recursively refer to B (using bound-recursively ).

entities :: [t]

bound_recursively_ :: [Funcons] -> Funcons

bound-recursively(B) returns the value currently bound to B , unless that value is a links , in which case it returns the value linked to by that link. This is intended to be used in situations when the binder B may be a recursive binding formed using recursive or bind-recursively .

entities :: [t]

bound_ :: [Funcons] -> Funcons

bound(B) returns the value currently bound to the binder B ,

entities :: [t]

entities :: [t]

scope_ :: [Funcons] -> Funcons

scope(Rho,X) extends (possibly overriding) the current environment with Rho for the execution of X .

entities :: [t]

accumulate_ :: [Funcons] -> Funcons

accumulate(D1,D*) first evaluates D1 to Rho1 . It then lets Rho1 override the current environment during the evaluation of accumulate(D*) to Rho2 , and finally computes Rho2 overriding Rho1 . accumulate() computes map-empty .

entities :: [t]

bind_ :: [Funcons] -> Funcons

bind(B,V) gives the environment binding the binder B to the value V .

entities :: [t]

is_in_type_ :: [Funcons] -> Funcons

is-in-type(V,T) tests membership of a value in a type.

entities :: [t]

entities :: [t]

entities :: [t]

variant_tag_ :: [Funcons] -> Funcons

variants(M) is the type of tagged values variant(K,V) where V . variant-tag(V) returns the tag of a variant V variant-value(V) returns the tagged value of a variant V

entities :: [t]

entities :: [t]

entities :: [t]

is_null_ :: [Funcons] -> Funcons

is-null tests an arbitrary value to determine if it is equal to null .

entities :: [t]

entities :: [t]

entities :: [t]

newline_ :: Funcons

newline is the string containing only a line feed character (LF or "n").

entities :: [t]

entities :: [t]

entities :: [t]

quiet_not_a_number_ :: [Funcons] -> Funcons

An ieee-floats is either one of four special values: quiet-not-a-number , signals-not-a-number , positive-infinity , negative-infinity or is represented (internally) as a triple (S,C,Q). S is a sign bit: 0 denotes "+" and 1 denotes "-". C and Q determine the value. - In binary format the value is: C x 2^Q - In decimal format the value is: C x 10^Q

entities :: [t]

not_ :: [Funcons] -> Funcons

booleans is the type of truth-values. not(_) is logical negation. and(...) is logical conjunction of a tuple of booleans . or(...) is logical disjunction of a tuple of booleans . xor(_,_) is exclusive disjunction of two booleans . implies(_,_) is logical implication between two booleans . is-equal(_,_) tests equality of arbitrary values .

entities :: [t]

close_ :: [Funcons] -> Funcons

close(_) closes a thunked computation with respect to the current environment.

entities :: [t]

closure_ :: [Funcons] -> Funcons

closure(X,Rho) evaluates X using Rho as the current environment.

entities :: [t]

pattern_prefer_ :: [Funcons] -> Funcons

pattern-prefer(P1,P2) is a pattern that attempts to match the value against P1 . If this succeeds then the resulting environment is returned. Otherwise, the value is matched against P2 .

entities :: [t]

match_ :: [Funcons] -> Funcons

match(V,P) matches the (potentially composite) value V against the (potentially composite) pattern P .

entities :: [t]

entities :: [t]

pattern_unite_ :: [Funcons] -> Funcons

pattern-unite(P1,P2) is a pattern that requires the matched value to match both P1 and P2 , uniting the resulting environments .

entities :: [t]

pattern_any_ :: Funcons

pattern-any is a pattern that matches any value, computing the empty environment.

entities :: [t]

case_ :: [Funcons] -> Funcons

case(P,X) attempts to match the (potentially composite) given-value against the (potentially composite) pattern P . If successful, X is executed in the scope of any computed bindings. Otherwise, it fails.

entities :: [t]

match_loosely_ :: [Funcons] -> Funcons

match-loosely(V,P) loosely matches the (potentially composite) value V against the (potentially composite) pattern P . In the case of sets , maps and vectors , the pattern may be a sub-setsub-multisetsub-map/ sub-vector of the value being matched against (recursively).

entities :: [t]

pattern_bind_ :: [Funcons] -> Funcons

pattern-bind(B) is a pattern that matches any value V , computing the singleton environment {B |-> V}

entities :: [t]

is_ground_value_ :: [Funcons] -> Funcons

A ground-value is any (potentially composite) value that does not contain thunks anywhere within it.

entities :: [t]

apply_ :: [Funcons] -> Funcons

apply(F,V) applies the function F to the value V .

entities :: [t]

supply_ :: [Funcons] -> Funcons

supply(V,F) supplies V as the argument to the function F , without executing the function. The result is a thunk that does not depend on an argument when forced.

entities :: [t]

binding_lambda_ :: [Funcons] -> Funcons

binding-lambda(B,E) computes a statically scoped function (i.e. a closed thunk). When applied to a value V , free occurrences of bound(B) in E refer to V .

entities :: [t]

curry_ :: [Funcons] -> Funcons

curry(F) converts a function that takes a pair of arguments into a function that takes the first argument of the pair, and returns a function that takes the second argument of the pair.

entities :: [t]

lambda_ :: [Funcons] -> Funcons

lambda(E) computes a statically scoped function (i.e. a closed thunk). When applied to a value V , free occurrences of given in E refer to V .

entities :: [t]

uncurry_ :: [Funcons] -> Funcons

uncurry(F) converts a function that computes a function into a single function that takes both arguments as a pair.

entities :: [t]

partial_apply_ :: [Funcons] -> Funcons

partial-apply(F,V) provides V as the first argument to a function expecting a pair of arguments, returning a function expecting only the second argument.

entities :: [t]

compose_ :: [Funcons] -> Funcons

compose(G,F) composes two functions G and F by giving the result of F as the argument to G .

cons_ :: [Funcons] -> Funcons

Funcons for inserting a value to a list.

nil_ :: Funcons

Funcons representing the empty list.

map_unite_ :: [Funcons] -> Funcons

Computes the union over a sequence of maps. If the maps do not have disjoint domains a failure signal is raised.

map_override_ :: [Funcons] -> Funcons

Computes the left-biased union over two maps.

string_append_ :: [Funcons] -> Funcons

Concatenate a sequence of strings.

tuple_index_ :: [Funcons] -> Funcons

tuple-index(_,N) selects the Nth component of a tuple. e.g. tuple-index((true,"hello",B),2) = `"hello"