| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
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
- data FloatType
- data FloatValue
- data IntegerType
- data IntegerValue
- data Literal
- data LiteralType
- newtype Name = Name {}
- floatValueType :: FloatValue -> FloatType
- integerValueType :: IntegerValue -> IntegerType
- int32 :: Int -> Literal
- literalType :: Literal -> LiteralType
- string :: String -> Literal
Documentation
A floating-point type
Constructors
| FloatTypeBigfloat | |
| FloatTypeFloat32 | |
| FloatTypeFloat64 |
Instances
| Read FloatType Source # | |
| Show FloatType Source # | |
| Eq FloatType Source # | |
| Ord FloatType Source # | |
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 |
Instances
| Read FloatValue Source # | |
Defined in Hydra.Core Methods readsPrec :: Int -> ReadS FloatValue # readList :: ReadS [FloatValue] # readPrec :: ReadPrec FloatValue # readListPrec :: ReadPrec [FloatValue] # | |
| Show FloatValue Source # | |
Defined in Hydra.Core Methods showsPrec :: Int -> FloatValue -> ShowS # show :: FloatValue -> String # showList :: [FloatValue] -> ShowS # | |
| Eq FloatValue Source # | |
Defined in Hydra.Core | |
| Ord FloatValue Source # | |
Defined in Hydra.Core Methods compare :: FloatValue -> FloatValue -> Ordering # (<) :: FloatValue -> FloatValue -> Bool # (<=) :: FloatValue -> FloatValue -> Bool # (>) :: FloatValue -> FloatValue -> Bool # (>=) :: FloatValue -> FloatValue -> Bool # max :: FloatValue -> FloatValue -> FloatValue # min :: FloatValue -> FloatValue -> FloatValue # | |
data IntegerType Source #
An integer type
Constructors
| IntegerTypeBigint | |
| IntegerTypeInt8 | |
| IntegerTypeInt16 | |
| IntegerTypeInt32 | |
| IntegerTypeInt64 | |
| IntegerTypeUint8 | |
| IntegerTypeUint16 | |
| IntegerTypeUint32 | |
| IntegerTypeUint64 |
Instances
| Read IntegerType Source # | |
Defined in Hydra.Core Methods readsPrec :: Int -> ReadS IntegerType # readList :: ReadS [IntegerType] # readPrec :: ReadPrec IntegerType # readListPrec :: ReadPrec [IntegerType] # | |
| Show IntegerType Source # | |
Defined in Hydra.Core Methods showsPrec :: Int -> IntegerType -> ShowS # show :: IntegerType -> String # showList :: [IntegerType] -> ShowS # | |
| Eq IntegerType Source # | |
Defined in Hydra.Core | |
| Ord IntegerType Source # | |
Defined in Hydra.Core Methods compare :: IntegerType -> IntegerType -> Ordering # (<) :: IntegerType -> IntegerType -> Bool # (<=) :: IntegerType -> IntegerType -> Bool # (>) :: IntegerType -> IntegerType -> Bool # (>=) :: IntegerType -> IntegerType -> Bool # max :: IntegerType -> IntegerType -> IntegerType # min :: IntegerType -> IntegerType -> IntegerType # | |
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) |
Instances
| Read IntegerValue Source # | |
Defined in Hydra.Core Methods readsPrec :: Int -> ReadS IntegerValue # readList :: ReadS [IntegerValue] # | |
| Show IntegerValue Source # | |
Defined in Hydra.Core Methods showsPrec :: Int -> IntegerValue -> ShowS # show :: IntegerValue -> String # showList :: [IntegerValue] -> ShowS # | |
| Eq IntegerValue Source # | |
Defined in Hydra.Core | |
| Ord IntegerValue Source # | |
Defined in Hydra.Core Methods compare :: IntegerValue -> IntegerValue -> Ordering # (<) :: IntegerValue -> IntegerValue -> Bool # (<=) :: IntegerValue -> IntegerValue -> Bool # (>) :: IntegerValue -> IntegerValue -> Bool # (>=) :: IntegerValue -> IntegerValue -> Bool # max :: IntegerValue -> IntegerValue -> IntegerValue # min :: IntegerValue -> IntegerValue -> IntegerValue # | |
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 |
data LiteralType Source #
Any of a fixed set of literal types, also called atomic types, base types, primitive types, or type constants
Constructors
| LiteralTypeBinary | |
| LiteralTypeBoolean | |
| LiteralTypeFloat FloatType | |
| LiteralTypeInteger IntegerType | |
| LiteralTypeString |
Instances
| Read LiteralType Source # | |
Defined in Hydra.Core Methods readsPrec :: Int -> ReadS LiteralType # readList :: ReadS [LiteralType] # readPrec :: ReadPrec LiteralType # readListPrec :: ReadPrec [LiteralType] # | |
| Show LiteralType Source # | |
Defined in Hydra.Core Methods showsPrec :: Int -> LiteralType -> ShowS # show :: LiteralType -> String # showList :: [LiteralType] -> ShowS # | |
| Eq LiteralType Source # | |
Defined in Hydra.Core | |
| Ord LiteralType Source # | |
Defined in Hydra.Core Methods compare :: LiteralType -> LiteralType -> Ordering # (<) :: LiteralType -> LiteralType -> Bool # (<=) :: LiteralType -> LiteralType -> Bool # (>) :: LiteralType -> LiteralType -> Bool # (>=) :: LiteralType -> LiteralType -> Bool # max :: LiteralType -> LiteralType -> LiteralType # min :: LiteralType -> LiteralType -> LiteralType # | |
A unique identifier in some context; a string-valued key
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