module Hydra.Dsl.PhantomLiterals where
import Hydra.Phantoms
import qualified Hydra.Dsl.Terms as Terms
import Data.Int
type Bigfloat = Double
type Binary = String
bigfloat :: Bigfloat -> TTerm Bigfloat
bigfloat :: Bigfloat -> TTerm Bigfloat
bigfloat = Term -> TTerm Bigfloat
forall a. Term -> TTerm a
TTerm (Term -> TTerm Bigfloat)
-> (Bigfloat -> Term) -> Bigfloat -> TTerm Bigfloat
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bigfloat -> Term
Terms.bigfloat
bigint :: Integer -> TTerm Integer
bigint :: Integer -> TTerm Integer
bigint = Term -> TTerm Integer
forall a. Term -> TTerm a
TTerm (Term -> TTerm Integer)
-> (Integer -> Term) -> Integer -> TTerm Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Term
Terms.bigint
binary :: Binary -> TTerm Binary
binary :: Binary -> TTerm Binary
binary = Term -> TTerm Binary
forall a. Term -> TTerm a
TTerm (Term -> TTerm Binary)
-> (Binary -> Term) -> Binary -> TTerm Binary
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Binary -> Term
Terms.binary
bool :: Bool -> TTerm Bool
bool :: Bool -> TTerm Bool
bool = Term -> TTerm Bool
forall a. Term -> TTerm a
TTerm (Term -> TTerm Bool) -> (Bool -> Term) -> Bool -> TTerm Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Term
Terms.boolean
boolean :: Bool -> TTerm Bool
boolean :: Bool -> TTerm Bool
boolean = Bool -> TTerm Bool
bool
double :: Double -> TTerm Double
double :: Bigfloat -> TTerm Bigfloat
double = Bigfloat -> TTerm Bigfloat
float64
false :: TTerm Bool
false :: TTerm Bool
false = Bool -> TTerm Bool
bool Bool
False
float :: Float -> TTerm Float
float :: Float -> TTerm Float
float = Float -> TTerm Float
float32
float32 :: Float -> TTerm Float
float32 :: Float -> TTerm Float
float32 = Term -> TTerm Float
forall a. Term -> TTerm a
TTerm (Term -> TTerm Float) -> (Float -> Term) -> Float -> TTerm Float
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Float -> Term
Terms.float32
float64 :: Double -> TTerm Double
float64 :: Bigfloat -> TTerm Bigfloat
float64 = Term -> TTerm Bigfloat
forall a. Term -> TTerm a
TTerm (Term -> TTerm Bigfloat)
-> (Bigfloat -> Term) -> Bigfloat -> TTerm Bigfloat
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bigfloat -> Term
Terms.float64
int :: Int -> TTerm Int
int :: Int -> TTerm Int
int = Int -> TTerm Int
int32
int8 :: Int8 -> TTerm Int8
int8 :: Int8 -> TTerm Int8
int8 = Term -> TTerm Int8
forall a. Term -> TTerm a
TTerm (Term -> TTerm Int8) -> (Int8 -> Term) -> Int8 -> TTerm Int8
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int8 -> Term
Terms.int8
int16 :: Int16 -> TTerm Int16
int16 :: Int16 -> TTerm Int16
int16 = Term -> TTerm Int16
forall a. Term -> TTerm a
TTerm (Term -> TTerm Int16) -> (Int16 -> Term) -> Int16 -> TTerm Int16
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int16 -> Term
Terms.int16
int32 :: Int -> TTerm Int
int32 :: Int -> TTerm Int
int32 = Term -> TTerm Int
forall a. Term -> TTerm a
TTerm (Term -> TTerm Int) -> (Int -> Term) -> Int -> TTerm Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Term
Terms.int32
int64 :: Int64 -> TTerm Int64
int64 :: Int64 -> TTerm Int64
int64 = Term -> TTerm Int64
forall a. Term -> TTerm a
TTerm (Term -> TTerm Int64) -> (Int64 -> Term) -> Int64 -> TTerm Int64
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int64 -> Term
Terms.int64
string :: String -> TTerm String
string :: Binary -> TTerm Binary
string = Term -> TTerm Binary
forall a. Term -> TTerm a
TTerm (Term -> TTerm Binary)
-> (Binary -> Term) -> Binary -> TTerm Binary
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Binary -> Term
Terms.string
true :: TTerm Bool
true :: TTerm Bool
true = Bool -> TTerm Bool
bool Bool
True
uint8 :: Int8 -> TTerm Int8
uint8 :: Int8 -> TTerm Int8
uint8 = Int8 -> TTerm Int8
int8
uint16 :: Int16 -> TTerm Int16
uint16 :: Int16 -> TTerm Int16
uint16 = Int16 -> TTerm Int16
int16
uint32 :: Int -> TTerm Int
uint32 :: Int -> TTerm Int
uint32 = Int -> TTerm Int
int
uint64 :: Int64 -> TTerm Int64
uint64 :: Int64 -> TTerm Int64
uint64 = Int64 -> TTerm Int64
int64