hydra-0.1.1: 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 Annotated a m Source #

An object, such as a type or term, together with an annotation

Constructors

Annotated 

Instances

Instances details
(Read a, Read m) => Read (Annotated a m) Source # 
Instance details

Defined in Hydra.Core

(Show a, Show m) => Show (Annotated a m) Source # 
Instance details

Defined in Hydra.Core

Methods

showsPrec :: Int -> Annotated a m -> ShowS #

show :: Annotated a m -> String #

showList :: [Annotated a m] -> ShowS #

(Eq a, Eq m) => Eq (Annotated a m) Source # 
Instance details

Defined in Hydra.Core

Methods

(==) :: Annotated a m -> Annotated a m -> Bool #

(/=) :: Annotated a m -> Annotated a m -> Bool #

(Ord a, Ord m) => Ord (Annotated a m) Source # 
Instance details

Defined in Hydra.Core

Methods

compare :: Annotated a m -> Annotated a m -> Ordering #

(<) :: Annotated a m -> Annotated a m -> Bool #

(<=) :: Annotated a m -> Annotated a m -> Bool #

(>) :: Annotated a m -> Annotated a m -> Bool #

(>=) :: Annotated a m -> Annotated a m -> Bool #

max :: Annotated a m -> Annotated a m -> Annotated a m #

min :: Annotated a m -> Annotated a m -> Annotated a m #

data Application m Source #

A term which applies a function to an argument

Constructors

Application 

Fields

Instances

Instances details
(Read m, Ord m) => Read (Application m) Source # 
Instance details

Defined in Hydra.Core

Show m => Show (Application m) Source # 
Instance details

Defined in Hydra.Core

Eq m => Eq (Application m) Source # 
Instance details

Defined in Hydra.Core

Ord m => Ord (Application m) Source # 
Instance details

Defined in Hydra.Core

data ApplicationType m Source #

The type-level analog of an application term

Constructors

ApplicationType 

Fields

data CaseStatement m Source #

A union elimination; a case statement

Instances

Instances details
(Read m, Ord m) => Read (CaseStatement m) Source # 
Instance details

Defined in Hydra.Core

Show m => Show (CaseStatement m) Source # 
Instance details

Defined in Hydra.Core

Eq m => Eq (CaseStatement m) Source # 
Instance details

Defined in Hydra.Core

Ord m => Ord (CaseStatement m) Source # 
Instance details

Defined in Hydra.Core

data Elimination m Source #

A corresponding elimination for an introduction term

Constructors

EliminationElement

Eliminates an element by mapping it to its data term. This is Hydra's delta function.

EliminationList (Term m)

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

EliminationNominal Name

Eliminates a nominal term by extracting the wrapped term

EliminationOptional (OptionalCases m)

Eliminates an optional term by matching over the two possible cases

EliminationRecord Projection

Eliminates a record by projecting a given field

EliminationUnion (CaseStatement m)

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

Instances

Instances details
(Read m, Ord m) => Read (Elimination m) Source # 
Instance details

Defined in Hydra.Core

Show m => Show (Elimination m) Source # 
Instance details

Defined in Hydra.Core

Eq m => Eq (Elimination m) Source # 
Instance details

Defined in Hydra.Core

Ord m => Ord (Elimination m) Source # 
Instance details

Defined in Hydra.Core

data Field m Source #

A labeled term

Constructors

Field 

Instances

Instances details
(Read m, Ord m) => Read (Field m) Source # 
Instance details

Defined in Hydra.Core

Show m => Show (Field m) Source # 
Instance details

Defined in Hydra.Core

Methods

showsPrec :: Int -> Field m -> ShowS #

show :: Field m -> String #

showList :: [Field m] -> ShowS #

Eq m => Eq (Field m) Source # 
Instance details

Defined in Hydra.Core

Methods

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

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

Ord m => Ord (Field m) Source # 
Instance details

Defined in Hydra.Core

Methods

compare :: Field m -> Field m -> Ordering #

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

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

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

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

max :: Field m -> Field m -> Field m #

min :: Field m -> Field m -> Field m #

newtype FieldName Source #

The name of a field, unique within a record or union type

Constructors

FieldName 

Fields

Instances

Instances details
Read FieldName Source # 
Instance details

Defined in Hydra.Core

Show FieldName Source # 
Instance details

Defined in Hydra.Core

Eq FieldName Source # 
Instance details

Defined in Hydra.Core

Ord FieldName Source # 
Instance details

Defined in Hydra.Core

data FieldType m Source #

The name and type of a field

Constructors

FieldType 

Instances

Instances details
Read m => Read (FieldType m) Source # 
Instance details

Defined in Hydra.Core

Show m => Show (FieldType m) Source # 
Instance details

Defined in Hydra.Core

Eq m => Eq (FieldType m) Source # 
Instance details

Defined in Hydra.Core

Methods

(==) :: FieldType m -> FieldType m -> Bool #

(/=) :: FieldType m -> FieldType m -> Bool #

Ord m => Ord (FieldType m) 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 m Source #

A function

Constructors

FunctionCompareTo (Term m)

Compares a term with a given term of the same type, producing a Comparison

FunctionElimination (Elimination m)

An elimination for any of a few term variants

FunctionLambda (Lambda m)

A function abstraction (lambda)

FunctionPrimitive Name

A reference to a built-in (primitive) function

Instances

Instances details
(Read m, Ord m) => Read (Function m) Source # 
Instance details

Defined in Hydra.Core

Show m => Show (Function m) Source # 
Instance details

Defined in Hydra.Core

Methods

showsPrec :: Int -> Function m -> ShowS #

show :: Function m -> String #

showList :: [Function m] -> ShowS #

Eq m => Eq (Function m) Source # 
Instance details

Defined in Hydra.Core

Methods

(==) :: Function m -> Function m -> Bool #

(/=) :: Function m -> Function m -> Bool #

Ord m => Ord (Function m) Source # 
Instance details

Defined in Hydra.Core

Methods

compare :: Function m -> Function m -> Ordering #

(<) :: Function m -> Function m -> Bool #

(<=) :: Function m -> Function m -> Bool #

(>) :: Function m -> Function m -> Bool #

(>=) :: Function m -> Function m -> Bool #

max :: Function m -> Function m -> Function m #

min :: Function m -> Function m -> Function m #

data FunctionType m Source #

A function type, also known as an arrow type

Instances

Instances details
Read m => Read (FunctionType m) Source # 
Instance details

Defined in Hydra.Core

Show m => Show (FunctionType m) Source # 
Instance details

Defined in Hydra.Core

Eq m => Eq (FunctionType m) Source # 
Instance details

Defined in Hydra.Core

Ord m => Ord (FunctionType m) Source # 
Instance details

Defined in Hydra.Core

data IntegerValue Source #

An integer literal value

Constructors

IntegerValueBigint Integer

An arbitrary-precision integer value

IntegerValueInt8 Int

An 8-bit signed integer value

IntegerValueInt16 Int

A 16-bit signed integer value (short value)

IntegerValueInt32 Int

A 32-bit signed integer value (int value)

IntegerValueInt64 Integer

A 64-bit signed integer value (long value)

IntegerValueUint8 Int

An 8-bit unsigned integer value (byte)

IntegerValueUint16 Int

A 16-bit unsigned integer value

IntegerValueUint32 Integer

A 32-bit unsigned integer value (unsigned int)

IntegerValueUint64 Integer

A 64-bit unsigned integer value (unsigned long)

data Lambda m Source #

A function abstraction (lambda)

Constructors

Lambda 

Fields

Instances

Instances details
(Read m, Ord m) => Read (Lambda m) Source # 
Instance details

Defined in Hydra.Core

Show m => Show (Lambda m) Source # 
Instance details

Defined in Hydra.Core

Methods

showsPrec :: Int -> Lambda m -> ShowS #

show :: Lambda m -> String #

showList :: [Lambda m] -> ShowS #

Eq m => Eq (Lambda m) Source # 
Instance details

Defined in Hydra.Core

Methods

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

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

Ord m => Ord (Lambda m) Source # 
Instance details

Defined in Hydra.Core

Methods

compare :: Lambda m -> Lambda m -> Ordering #

(<) :: Lambda m -> Lambda m -> Bool #

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

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

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

max :: Lambda m -> Lambda m -> Lambda m #

min :: Lambda m -> Lambda m -> Lambda m #

data LambdaType m Source #

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

Constructors

LambdaType 

Fields

Instances

Instances details
Read m => Read (LambdaType m) Source # 
Instance details

Defined in Hydra.Core

Show m => Show (LambdaType m) Source # 
Instance details

Defined in Hydra.Core

Eq m => Eq (LambdaType m) Source # 
Instance details

Defined in Hydra.Core

Methods

(==) :: LambdaType m -> LambdaType m -> Bool #

(/=) :: LambdaType m -> LambdaType m -> Bool #

Ord m => Ord (LambdaType m) Source # 
Instance details

Defined in Hydra.Core

data Let m Source #

A 'let' binding

Constructors

Let 

Instances

Instances details
(Read m, Ord m) => Read (Let m) Source # 
Instance details

Defined in Hydra.Core

Show m => Show (Let m) Source # 
Instance details

Defined in Hydra.Core

Methods

showsPrec :: Int -> Let m -> ShowS #

show :: Let m -> String #

showList :: [Let m] -> ShowS #

Eq m => Eq (Let m) Source # 
Instance details

Defined in Hydra.Core

Methods

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

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

Ord m => Ord (Let m) Source # 
Instance details

Defined in Hydra.Core

Methods

compare :: Let m -> Let m -> Ordering #

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

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

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

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

max :: Let m -> Let m -> Let m #

min :: Let m -> Let m -> Let m #

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 m Source #

A map type

Constructors

MapType 

Fields

Instances

Instances details
Read m => Read (MapType m) Source # 
Instance details

Defined in Hydra.Core

Show m => Show (MapType m) Source # 
Instance details

Defined in Hydra.Core

Methods

showsPrec :: Int -> MapType m -> ShowS #

show :: MapType m -> String #

showList :: [MapType m] -> ShowS #

Eq m => Eq (MapType m) Source # 
Instance details

Defined in Hydra.Core

Methods

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

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

Ord m => Ord (MapType m) Source # 
Instance details

Defined in Hydra.Core

Methods

compare :: MapType m -> MapType m -> Ordering #

(<) :: MapType m -> MapType m -> Bool #

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

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

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

max :: MapType m -> MapType m -> MapType m #

min :: MapType m -> MapType m -> MapType m #

newtype Name Source #

A unique element name

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 Named m Source #

A term annotated with a fixed, named type; an instance of a newtype

Constructors

Named 

Fields

Instances

Instances details
(Read m, Ord m) => Read (Named m) Source # 
Instance details

Defined in Hydra.Core

Show m => Show (Named m) Source # 
Instance details

Defined in Hydra.Core

Methods

showsPrec :: Int -> Named m -> ShowS #

show :: Named m -> String #

showList :: [Named m] -> ShowS #

Eq m => Eq (Named m) Source # 
Instance details

Defined in Hydra.Core

Methods

(==) :: Named m -> Named m -> Bool #

(/=) :: Named m -> Named m -> Bool #

Ord m => Ord (Named m) Source # 
Instance details

Defined in Hydra.Core

Methods

compare :: Named m -> Named m -> Ordering #

(<) :: Named m -> Named m -> Bool #

(<=) :: Named m -> Named m -> Bool #

(>) :: Named m -> Named m -> Bool #

(>=) :: Named m -> Named m -> Bool #

max :: Named m -> Named m -> Named m #

min :: Named m -> Named m -> Named m #

data OptionalCases m Source #

A case statement for matching optional terms

Constructors

OptionalCases 

Fields

Instances

Instances details
(Read m, Ord m) => Read (OptionalCases m) Source # 
Instance details

Defined in Hydra.Core

Show m => Show (OptionalCases m) Source # 
Instance details

Defined in Hydra.Core

Eq m => Eq (OptionalCases m) Source # 
Instance details

Defined in Hydra.Core

Ord m => Ord (OptionalCases m) Source # 
Instance details

Defined in Hydra.Core

data Projection Source #

A record elimination; a projection

data Record m Source #

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

Constructors

Record 

Instances

Instances details
(Read m, Ord m) => Read (Record m) Source # 
Instance details

Defined in Hydra.Core

Show m => Show (Record m) Source # 
Instance details

Defined in Hydra.Core

Methods

showsPrec :: Int -> Record m -> ShowS #

show :: Record m -> String #

showList :: [Record m] -> ShowS #

Eq m => Eq (Record m) Source # 
Instance details

Defined in Hydra.Core

Methods

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

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

Ord m => Ord (Record m) Source # 
Instance details

Defined in Hydra.Core

Methods

compare :: Record m -> Record m -> Ordering #

(<) :: Record m -> Record m -> Bool #

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

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

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

max :: Record m -> Record m -> Record m #

min :: Record m -> Record m -> Record m #

data RowType m Source #

A labeled record or union type

Constructors

RowType 

Fields

  • rowTypeTypeName :: Name

    The name of the row type, which must correspond to the name of a Type element

  • rowTypeExtends :: Maybe Name

    Optionally, the name of another row type which this one extends. To the extent that field order is preserved, the inherited fields of the extended type precede those of the extension.

  • rowTypeFields :: [FieldType m]

    The fields of this row type, excluding any inherited fields

Instances

Instances details
Read m => Read (RowType m) Source # 
Instance details

Defined in Hydra.Core

Show m => Show (RowType m) Source # 
Instance details

Defined in Hydra.Core

Methods

showsPrec :: Int -> RowType m -> ShowS #

show :: RowType m -> String #

showList :: [RowType m] -> ShowS #

Eq m => Eq (RowType m) Source # 
Instance details

Defined in Hydra.Core

Methods

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

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

Ord m => Ord (RowType m) Source # 
Instance details

Defined in Hydra.Core

Methods

compare :: RowType m -> RowType m -> Ordering #

(<) :: RowType m -> RowType m -> Bool #

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

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

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

max :: RowType m -> RowType m -> RowType m #

min :: RowType m -> RowType m -> RowType m #

data Stream m Source #

An infinite stream of terms

Constructors

Stream 

Fields

Instances

Instances details
(Read m, Ord m) => Read (Stream m) Source # 
Instance details

Defined in Hydra.Core

Show m => Show (Stream m) Source # 
Instance details

Defined in Hydra.Core

Methods

showsPrec :: Int -> Stream m -> ShowS #

show :: Stream m -> String #

showList :: [Stream m] -> ShowS #

Eq m => Eq (Stream m) Source # 
Instance details

Defined in Hydra.Core

Methods

(==) :: Stream m -> Stream m -> Bool #

(/=) :: Stream m -> Stream m -> Bool #

Ord m => Ord (Stream m) Source # 
Instance details

Defined in Hydra.Core

Methods

compare :: Stream m -> Stream m -> Ordering #

(<) :: Stream m -> Stream m -> Bool #

(<=) :: Stream m -> Stream m -> Bool #

(>) :: Stream m -> Stream m -> Bool #

(>=) :: Stream m -> Stream m -> Bool #

max :: Stream m -> Stream m -> Stream m #

min :: Stream m -> Stream m -> Stream m #

data Sum m Source #

The unlabeled equivalent of a Union term

Constructors

Sum 

Fields

Instances

Instances details
(Read m, Ord m) => Read (Sum m) Source # 
Instance details

Defined in Hydra.Core

Show m => Show (Sum m) Source # 
Instance details

Defined in Hydra.Core

Methods

showsPrec :: Int -> Sum m -> ShowS #

show :: Sum m -> String #

showList :: [Sum m] -> ShowS #

Eq m => Eq (Sum m) Source # 
Instance details

Defined in Hydra.Core

Methods

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

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

Ord m => Ord (Sum m) Source # 
Instance details

Defined in Hydra.Core

Methods

compare :: Sum m -> Sum m -> Ordering #

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

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

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

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

max :: Sum m -> Sum m -> Sum m #

min :: Sum m -> Sum m -> Sum m #

data Term m Source #

A data term

Constructors

TermAnnotated (Annotated (Term m) m)

A term annotated with metadata

TermApplication (Application m)

A function application

TermElement Name

An element reference

TermFunction (Function m)

A function term

TermLet (Let m) 
TermList [Term m]

A list

TermLiteral Literal

A literal value

TermMap (Map (Term m) (Term m))

A map of keys to values

TermNominal (Named m) 
TermOptional (Maybe (Term m))

An optional value

TermProduct [Term m]

A tuple

TermRecord (Record m)

A record term

TermSet (Set (Term m))

A set of values

TermStream (Stream m)

An infinite stream of terms

TermSum (Sum m)

A variant tuple

TermUnion (Union m)

A union term

TermVariable Variable

A variable reference

Instances

Instances details
IsString (Term m) Source # 
Instance details

Defined in Hydra.Impl.Haskell.Dsl.Terms

Methods

fromString :: String -> Term m #

(Read m, Ord m) => Read (Term m) Source # 
Instance details

Defined in Hydra.Core

Show m => Show (Term m) Source # 
Instance details

Defined in Hydra.Core

Methods

showsPrec :: Int -> Term m -> ShowS #

show :: Term m -> String #

showList :: [Term m] -> ShowS #

Eq m => Eq (Term m) Source # 
Instance details

Defined in Hydra.Core

Methods

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

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

Ord m => Ord (Term m) Source # 
Instance details

Defined in Hydra.Core

Methods

compare :: Term m -> Term m -> Ordering #

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

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

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

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

max :: Term m -> Term m -> Term m #

min :: Term m -> Term m -> Term m #

data Type m Source #

A data type

Instances

Instances details
IsString (Type m) Source # 
Instance details

Defined in Hydra.Impl.Haskell.Dsl.Types

Methods

fromString :: String -> Type m #

Read m => Read (Type m) Source # 
Instance details

Defined in Hydra.Core

Show m => Show (Type m) Source # 
Instance details

Defined in Hydra.Core

Methods

showsPrec :: Int -> Type m -> ShowS #

show :: Type m -> String #

showList :: [Type m] -> ShowS #

Eq m => Eq (Type m) Source # 
Instance details

Defined in Hydra.Core

Methods

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

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

Ord m => Ord (Type m) Source # 
Instance details

Defined in Hydra.Core

Methods

compare :: Type m -> Type m -> Ordering #

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

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

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

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

max :: Type m -> Type m -> Type m #

min :: Type m -> Type m -> Type m #

newtype Variable Source #

A symbol which stands in for a term

Constructors

Variable 

Fields

Instances

Instances details
Read Variable Source # 
Instance details

Defined in Hydra.Core

Show Variable Source # 
Instance details

Defined in Hydra.Core

Eq Variable Source # 
Instance details

Defined in Hydra.Core

Ord Variable Source # 
Instance details

Defined in Hydra.Core

newtype VariableType Source #

A symbol which stands in for a type

Constructors

VariableType 

Fields

data Union m Source #

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

Constructors

Union 

Instances

Instances details
(Read m, Ord m) => Read (Union m) Source # 
Instance details

Defined in Hydra.Core

Show m => Show (Union m) Source # 
Instance details

Defined in Hydra.Core

Methods

showsPrec :: Int -> Union m -> ShowS #

show :: Union m -> String #

showList :: [Union m] -> ShowS #

Eq m => Eq (Union m) Source # 
Instance details

Defined in Hydra.Core

Methods

(==) :: Union m -> Union m -> Bool #

(/=) :: Union m -> Union m -> Bool #

Ord m => Ord (Union m) Source # 
Instance details

Defined in Hydra.Core

Methods

compare :: Union m -> Union m -> Ordering #

(<) :: Union m -> Union m -> Bool #

(<=) :: Union m -> Union m -> Bool #

(>) :: Union m -> Union m -> Bool #

(>=) :: Union m -> Union m -> Bool #

max :: Union m -> Union m -> Union m #

min :: Union m -> Union m -> Union m #

data UnitType Source #

An empty record type as a canonical unit type

Constructors

UnitType 

Instances

Instances details
Read UnitType Source # 
Instance details

Defined in Hydra.Core

Show UnitType Source # 
Instance details

Defined in Hydra.Core

Eq UnitType Source # 
Instance details

Defined in Hydra.Core

Ord UnitType Source # 
Instance details

Defined in Hydra.Core