hydra-0.8.0: Type-aware transformations for data and programs
Safe HaskellSafe-Inferred
LanguageHaskell2010

Hydra.Core

Description

Hydra's core data model, defining types, terms, and their dependencies

Synopsis

Documentation

data Application Source #

A term which applies a function to an argument

Constructors

Application 

Fields

data Elimination Source #

A corresponding elimination for an introduction term

Constructors

EliminationList Term

Eliminates a list using a fold function; this function has the signature b -> [a] -> b

EliminationOptional OptionalCases

Eliminates an optional term by matching over the two possible cases

EliminationProduct TupleProjection

Eliminates a tuple by projecting the component at a given 0-indexed offset

EliminationRecord Projection

Eliminates a record by projecting a given field

EliminationUnion CaseStatement

Eliminates a union term by matching over the fields of the union. This is a case statement.

EliminationWrap Name

Unwrap a wrapped term

data Field Source #

A name/term pair

Constructors

Field 

Fields

Instances

Instances details
Read Field Source # 
Instance details

Defined in Hydra.Core

Show Field Source # 
Instance details

Defined in Hydra.Core

Methods

showsPrec :: Int -> Field -> ShowS #

show :: Field -> String #

showList :: [Field] -> ShowS #

Eq Field Source # 
Instance details

Defined in Hydra.Core

Methods

(==) :: Field -> Field -> Bool #

(/=) :: Field -> Field -> Bool #

Ord Field Source # 
Instance details

Defined in Hydra.Core

Methods

compare :: Field -> Field -> Ordering #

(<) :: Field -> Field -> Bool #

(<=) :: Field -> Field -> Bool #

(>) :: Field -> Field -> Bool #

(>=) :: Field -> Field -> Bool #

max :: Field -> Field -> Field #

min :: Field -> Field -> Field #

data FieldType Source #

A name/type pair

Constructors

FieldType 

Instances

Instances details
Read FieldType Source # 
Instance details

Defined in Hydra.Core

Show FieldType Source # 
Instance details

Defined in Hydra.Core

Eq FieldType Source # 
Instance details

Defined in Hydra.Core

Ord FieldType Source # 
Instance details

Defined in Hydra.Core

data FloatType Source #

A floating-point type

Instances

Instances details
Read FloatType Source # 
Instance details

Defined in Hydra.Core

Show FloatType Source # 
Instance details

Defined in Hydra.Core

Eq FloatType Source # 
Instance details

Defined in Hydra.Core

Ord FloatType Source # 
Instance details

Defined in Hydra.Core

data FloatValue Source #

A floating-point literal value

Constructors

FloatValueBigfloat Double

An arbitrary-precision floating-point value

FloatValueFloat32 Float

A 32-bit floating-point value

FloatValueFloat64 Double

A 64-bit floating-point value

data Function Source #

A function

Constructors

FunctionElimination Elimination

An elimination for any of a few term variants

FunctionLambda Lambda

A function abstraction (lambda)

FunctionPrimitive Name

A reference to a built-in (primitive) function

Instances

Instances details
Read Function Source # 
Instance details

Defined in Hydra.Core

Show Function Source # 
Instance details

Defined in Hydra.Core

Eq Function Source # 
Instance details

Defined in Hydra.Core

Ord Function Source # 
Instance details

Defined in Hydra.Core

data Injection Source #

An instance of a union type; i.e. a string-indexed generalization of inl() or inr()

Instances

Instances details
Read Injection Source # 
Instance details

Defined in Hydra.Core

Show Injection Source # 
Instance details

Defined in Hydra.Core

Eq Injection Source # 
Instance details

Defined in Hydra.Core

Ord Injection Source # 
Instance details

Defined in Hydra.Core

data IntegerValue Source #

An integer literal value

Constructors

IntegerValueBigint Integer

An arbitrary-precision integer value

IntegerValueInt8 Int8

An 8-bit signed integer value

IntegerValueInt16 Int16

A 16-bit signed integer value (short value)

IntegerValueInt32 Int

A 32-bit signed integer value (int value)

IntegerValueInt64 Int64

A 64-bit signed integer value (long value)

IntegerValueUint8 Int16

An 8-bit unsigned integer value (byte)

IntegerValueUint16 Int

A 16-bit unsigned integer value

IntegerValueUint32 Int64

A 32-bit unsigned integer value (unsigned int)

IntegerValueUint64 Integer

A 64-bit unsigned integer value (unsigned long)

data Lambda Source #

A function abstraction (lambda)

Constructors

Lambda 

Fields

Instances

Instances details
Read Lambda Source # 
Instance details

Defined in Hydra.Core

Show Lambda Source # 
Instance details

Defined in Hydra.Core

Eq Lambda Source # 
Instance details

Defined in Hydra.Core

Methods

(==) :: Lambda -> Lambda -> Bool #

(/=) :: Lambda -> Lambda -> Bool #

Ord Lambda Source # 
Instance details

Defined in Hydra.Core

data LambdaType Source #

A type abstraction; the type-level analog of a lambda term

Constructors

LambdaType 

Fields

data Let Source #

A set of (possibly recursive) 'let' bindings together with an environment in which they are bound

Constructors

Let 

Instances

Instances details
Read Let Source # 
Instance details

Defined in Hydra.Core

Show Let Source # 
Instance details

Defined in Hydra.Core

Methods

showsPrec :: Int -> Let -> ShowS #

show :: Let -> String #

showList :: [Let] -> ShowS #

Eq Let Source # 
Instance details

Defined in Hydra.Core

Methods

(==) :: Let -> Let -> Bool #

(/=) :: Let -> Let -> Bool #

Ord Let Source # 
Instance details

Defined in Hydra.Core

Methods

compare :: Let -> Let -> Ordering #

(<) :: Let -> Let -> Bool #

(<=) :: Let -> Let -> Bool #

(>) :: Let -> Let -> Bool #

(>=) :: Let -> Let -> Bool #

max :: Let -> Let -> Let #

min :: Let -> Let -> Let #

data LetBinding Source #

A field with an optional type scheme, used to bind variables to terms in a 'let' expression

data Literal Source #

A term constant; an instance of a literal type

Constructors

LiteralBinary String

A binary literal

LiteralBoolean Bool

A boolean literal

LiteralFloat FloatValue

A floating-point literal

LiteralInteger IntegerValue

An integer literal

LiteralString String

A string literal

Instances

Instances details
Read Literal Source # 
Instance details

Defined in Hydra.Core

Show Literal Source # 
Instance details

Defined in Hydra.Core

Eq Literal Source # 
Instance details

Defined in Hydra.Core

Methods

(==) :: Literal -> Literal -> Bool #

(/=) :: Literal -> Literal -> Bool #

Ord Literal Source # 
Instance details

Defined in Hydra.Core

data LiteralType Source #

Any of a fixed set of literal types, also called atomic types, base types, primitive types, or type constants

data MapType Source #

A map type

Constructors

MapType 

Instances

Instances details
Read MapType Source # 
Instance details

Defined in Hydra.Core

Show MapType Source # 
Instance details

Defined in Hydra.Core

Eq MapType Source # 
Instance details

Defined in Hydra.Core

Methods

(==) :: MapType -> MapType -> Bool #

(/=) :: MapType -> MapType -> Bool #

Ord MapType Source # 
Instance details

Defined in Hydra.Core

newtype Name Source #

A unique identifier in some context; a string-valued key

Constructors

Name 

Fields

Instances

Instances details
Read Name Source # 
Instance details

Defined in Hydra.Core

Show Name Source # 
Instance details

Defined in Hydra.Core

Methods

showsPrec :: Int -> Name -> ShowS #

show :: Name -> String #

showList :: [Name] -> ShowS #

Eq Name Source # 
Instance details

Defined in Hydra.Core

Methods

(==) :: Name -> Name -> Bool #

(/=) :: Name -> Name -> Bool #

Ord Name Source # 
Instance details

Defined in Hydra.Core

Methods

compare :: Name -> Name -> Ordering #

(<) :: Name -> Name -> Bool #

(<=) :: Name -> Name -> Bool #

(>) :: Name -> Name -> Bool #

(>=) :: Name -> Name -> Bool #

max :: Name -> Name -> Name #

min :: Name -> Name -> Name #

data OptionalCases Source #

A case statement for matching optional terms

Constructors

OptionalCases 

Fields

data Projection Source #

A record elimination; a projection

Constructors

Projection 

Fields

data Record Source #

A record, or labeled tuple; a map of field names to terms

Constructors

Record 

Instances

Instances details
Read Record Source # 
Instance details

Defined in Hydra.Core

Show Record Source # 
Instance details

Defined in Hydra.Core

Eq Record Source # 
Instance details

Defined in Hydra.Core

Methods

(==) :: Record -> Record -> Bool #

(/=) :: Record -> Record -> Bool #

Ord Record Source # 
Instance details

Defined in Hydra.Core

data RowType Source #

A labeled record or union type

Constructors

RowType 

Fields

Instances

Instances details
Read RowType Source # 
Instance details

Defined in Hydra.Core

Show RowType Source # 
Instance details

Defined in Hydra.Core

Eq RowType Source # 
Instance details

Defined in Hydra.Core

Methods

(==) :: RowType -> RowType -> Bool #

(/=) :: RowType -> RowType -> Bool #

Ord RowType Source # 
Instance details

Defined in Hydra.Core

data Sum Source #

The unlabeled equivalent of an Injection term

Constructors

Sum 

Fields

Instances

Instances details
Read Sum Source # 
Instance details

Defined in Hydra.Core

Show Sum Source # 
Instance details

Defined in Hydra.Core

Methods

showsPrec :: Int -> Sum -> ShowS #

show :: Sum -> String #

showList :: [Sum] -> ShowS #

Eq Sum Source # 
Instance details

Defined in Hydra.Core

Methods

(==) :: Sum -> Sum -> Bool #

(/=) :: Sum -> Sum -> Bool #

Ord Sum Source # 
Instance details

Defined in Hydra.Core

Methods

compare :: Sum -> Sum -> Ordering #

(<) :: Sum -> Sum -> Bool #

(<=) :: Sum -> Sum -> Bool #

(>) :: Sum -> Sum -> Bool #

(>=) :: Sum -> Sum -> Bool #

max :: Sum -> Sum -> Sum #

min :: Sum -> Sum -> Sum #

data Term Source #

A data term

Constructors

TermAnnotated AnnotatedTerm

A term annotated with metadata

TermApplication Application

A function application

TermFunction Function

A function term

TermLet Let 
TermList [Term]

A list

TermLiteral Literal

A literal value

TermMap (Map Term Term)

A map of keys to values

TermOptional (Maybe Term)

An optional value

TermProduct [Term]

A tuple

TermRecord Record

A record term

TermSet (Set Term)

A set of values

TermSum Sum

A variant tuple

TermTypeAbstraction TypeAbstraction

A System F type abstraction term

TermTypeApplication TypedTerm

A System F type application term

TermTyped TypedTerm

A term annotated with its type

TermUnion Injection

An injection; an instance of a union type

TermVariable Name

A variable reference

TermWrap WrappedTerm 

Instances

Instances details
IsString Term Source # 
Instance details

Defined in Hydra.Dsl.Terms

Methods

fromString :: String -> Term #

Read Term Source # 
Instance details

Defined in Hydra.Core

Show Term Source # 
Instance details

Defined in Hydra.Core

Methods

showsPrec :: Int -> Term -> ShowS #

show :: Term -> String #

showList :: [Term] -> ShowS #

Eq Term Source # 
Instance details

Defined in Hydra.Core

Methods

(==) :: Term -> Term -> Bool #

(/=) :: Term -> Term -> Bool #

Ord Term Source # 
Instance details

Defined in Hydra.Core

Methods

compare :: Term -> Term -> Ordering #

(<) :: Term -> Term -> Bool #

(<=) :: Term -> Term -> Bool #

(>) :: Term -> Term -> Bool #

(>=) :: Term -> Term -> Bool #

max :: Term -> Term -> Term #

min :: Term -> Term -> Term #

IsString (TermCoder Term) Source # 
Instance details

Defined in Hydra.Dsl.Prims

data TupleProjection Source #

A tuple elimination; a projection from an integer-indexed product

Constructors

TupleProjection 

Fields

data Type Source #

A data type

Instances

Instances details
IsString Type Source # 
Instance details

Defined in Hydra.Dsl.Types

Methods

fromString :: String -> Type #

Read Type Source # 
Instance details

Defined in Hydra.Core

Show Type Source # 
Instance details

Defined in Hydra.Core

Methods

showsPrec :: Int -> Type -> ShowS #

show :: Type -> String #

showList :: [Type] -> ShowS #

Eq Type Source # 
Instance details

Defined in Hydra.Core

Methods

(==) :: Type -> Type -> Bool #

(/=) :: Type -> Type -> Bool #

Ord Type Source # 
Instance details

Defined in Hydra.Core

Methods

compare :: Type -> Type -> Ordering #

(<) :: Type -> Type -> Bool #

(<=) :: Type -> Type -> Bool #

(>) :: Type -> Type -> Bool #

(>=) :: Type -> Type -> Bool #

max :: Type -> Type -> Type #

min :: Type -> Type -> Type #

data TypeScheme Source #

A type expression together with free type variables occurring in the expression

Constructors

TypeScheme 

data TypedTerm Source #

A term together with its type

Constructors

TypedTerm 

Instances

Instances details
Read TypedTerm Source # 
Instance details

Defined in Hydra.Core

Show TypedTerm Source # 
Instance details

Defined in Hydra.Core

Eq TypedTerm Source # 
Instance details

Defined in Hydra.Core

Ord TypedTerm Source # 
Instance details

Defined in Hydra.Core

data Unit Source #

An empty record as a canonical unit value

Constructors

Unit 

Instances

Instances details
Read Unit Source # 
Instance details

Defined in Hydra.Core

Show Unit Source # 
Instance details

Defined in Hydra.Core

Methods

showsPrec :: Int -> Unit -> ShowS #

show :: Unit -> String #

showList :: [Unit] -> ShowS #

Eq Unit Source # 
Instance details

Defined in Hydra.Core

Methods

(==) :: Unit -> Unit -> Bool #

(/=) :: Unit -> Unit -> Bool #

Ord Unit Source # 
Instance details

Defined in Hydra.Core

Methods

compare :: Unit -> Unit -> Ordering #

(<) :: Unit -> Unit -> Bool #

(<=) :: Unit -> Unit -> Bool #

(>) :: Unit -> Unit -> Bool #

(>=) :: Unit -> Unit -> Bool #

max :: Unit -> Unit -> Unit #

min :: Unit -> Unit -> Unit #