-- | A DSL for constructing literal terms using Haskell's built-in datatypes

module Hydra.Dsl.PhantomLiterals where

import Hydra.Phantoms
import qualified Hydra.Dsl.Terms as Terms

import Data.Int


-- Note: does not yet properly capture arbitrary-precision floating-point numbers,
--       because code generation does not.
type Bigfloat = Double

-- Note: does not distinguish Binary from String, because code generation does not.
type Binary = String

bigfloat :: Bigfloat -> Datum Bigfloat
bigfloat :: Bigfloat -> Datum Bigfloat
bigfloat = Term -> Datum Bigfloat
forall a. Term -> Datum a
Datum (Term -> Datum Bigfloat)
-> (Bigfloat -> Term) -> Bigfloat -> Datum Bigfloat
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bigfloat -> Term
Terms.bigfloat

bigint :: Integer -> Datum Integer
bigint :: Integer -> Datum Integer
bigint = Term -> Datum Integer
forall a. Term -> Datum a
Datum (Term -> Datum Integer)
-> (Integer -> Term) -> Integer -> Datum Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Term
Terms.bigint

binary :: Binary -> Datum Binary
binary :: Binary -> Datum Binary
binary = Term -> Datum Binary
forall a. Term -> Datum a
Datum (Term -> Datum Binary)
-> (Binary -> Term) -> Binary -> Datum Binary
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Binary -> Term
Terms.binary

bool :: Bool -> Datum Bool
bool :: Bool -> Datum Bool
bool = Term -> Datum Bool
forall a. Term -> Datum a
Datum (Term -> Datum Bool) -> (Bool -> Term) -> Bool -> Datum Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Term
Terms.boolean

boolean :: Bool -> Datum Bool
boolean :: Bool -> Datum Bool
boolean = Bool -> Datum Bool
bool

double :: Double -> Datum Double
double :: Bigfloat -> Datum Bigfloat
double = Bigfloat -> Datum Bigfloat
float64

false :: Datum Bool
false :: Datum Bool
false = Bool -> Datum Bool
bool Bool
False

float :: Float -> Datum Float
float :: Float -> Datum Float
float = Float -> Datum Float
float32

float32 :: Float -> Datum Float
float32 :: Float -> Datum Float
float32 = Term -> Datum Float
forall a. Term -> Datum a
Datum (Term -> Datum Float) -> (Float -> Term) -> Float -> Datum Float
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Float -> Term
Terms.float32

float64 :: Double -> Datum Double
float64 :: Bigfloat -> Datum Bigfloat
float64 = Term -> Datum Bigfloat
forall a. Term -> Datum a
Datum (Term -> Datum Bigfloat)
-> (Bigfloat -> Term) -> Bigfloat -> Datum Bigfloat
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bigfloat -> Term
Terms.float64

int :: Int -> Datum Int
int :: Int -> Datum Int
int = Int -> Datum Int
int32

int8 :: Int8 -> Datum Int8
int8 :: Int8 -> Datum Int8
int8 = Term -> Datum Int8
forall a. Term -> Datum a
Datum (Term -> Datum Int8) -> (Int8 -> Term) -> Int8 -> Datum Int8
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int8 -> Term
Terms.int8

int16 :: Int16 -> Datum Int16
int16 :: Int16 -> Datum Int16
int16 = Term -> Datum Int16
forall a. Term -> Datum a
Datum (Term -> Datum Int16) -> (Int16 -> Term) -> Int16 -> Datum Int16
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int16 -> Term
Terms.int16

int32 :: Int -> Datum Int
int32 :: Int -> Datum Int
int32 = Term -> Datum Int
forall a. Term -> Datum a
Datum (Term -> Datum Int) -> (Int -> Term) -> Int -> Datum Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Term
Terms.int32

int64 :: Int64 -> Datum Int64
int64 :: Int64 -> Datum Int64
int64 = Term -> Datum Int64
forall a. Term -> Datum a
Datum (Term -> Datum Int64) -> (Int64 -> Term) -> Int64 -> Datum Int64
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int64 -> Term
Terms.int64

string :: String -> Datum String
string :: Binary -> Datum Binary
string = Term -> Datum Binary
forall a. Term -> Datum a
Datum (Term -> Datum Binary)
-> (Binary -> Term) -> Binary -> Datum Binary
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Binary -> Term
Terms.string

true :: Datum Bool
true :: Datum Bool
true = Bool -> Datum Bool
bool Bool
True

-- Note: untyped integers are not yet properly supported by the DSL,
--       because they are not properly supported by code generation.
uint8 :: Int8 -> Datum Int8
uint8 :: Int8 -> Datum Int8
uint8 = Int8 -> Datum Int8
int8
uint16 :: Int16 -> Datum Int16
uint16 :: Int16 -> Datum Int16
uint16 = Int16 -> Datum Int16
int16
uint32 :: Int -> Datum Int
uint32 :: Int -> Datum Int
uint32 = Int -> Datum Int
int
uint64 :: Int64 -> Datum Int64
uint64 :: Int64 -> Datum Int64
uint64 = Int64 -> Datum Int64
int64