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

Hydra.Minimal

Description

A minimal, standalone Hydra kernel which allows external tools (like @wisnesky's Algorithm W implementation) to take a lightweight dependency on Hydra types or functions, without requiring compilation of Hydra proper. There are two versions of this module: * External: has all of the necessary Hydra definitions in one file * Internal: just exports the appropriate symbols from the actual Hydra modules

Synopsis

Documentation

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 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 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

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 #

floatValueType :: FloatValue -> FloatType Source #

Find the float type for a given floating-point value

integerValueType :: IntegerValue -> IntegerType Source #

Find the integer type for a given integer value

literalType :: Literal -> LiteralType Source #

Find the literal type for a given literal value