{-# LANGUAGE CPP #-}
{-# LANGUAGE QuasiQuotes #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Language.C.Smart where
import Language.C.Quote.C
import Language.C.Syntax as C
#if !MIN_VERSION_template_haskell(2,7,0)
import qualified Data.Loc
import qualified Language.C.Syntax
#endif /* !MIN_VERSION_template_haskell(2,7,0) */
instance Enum Exp where
toEnum :: Int -> Exp
toEnum Int
n = [cexp|$int:n|]
fromEnum :: Exp -> Int
fromEnum Exp
[cexp|$int:n|] = Integer -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
n
fromEnum Exp
[cexp|$uint:n|] = Integer -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
n
fromEnum Exp
[cexp|$lint:n|] = Integer -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
n
fromEnum Exp
[cexp|$ulint:n|] = Integer -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
n
fromEnum Exp
_ =
String -> Int
forall a. HasCallStack => String -> a
error String
"fromEnum: non-integer constant C expressions"
instance Num C.Exp where
Exp
e1 + :: Exp -> Exp -> Exp
+ Exp
e2 = [cexp|$exp:e1 + $exp:e2|]
Exp
e1 * :: Exp -> Exp -> Exp
* Exp
e2 = [cexp|$exp:e1 * $exp:e2|]
Exp
e1 - :: Exp -> Exp -> Exp
- Exp
e2 = [cexp|$exp:e1 - $exp:e2|]
negate :: Exp -> Exp
negate Exp
e = [cexp|-$exp:e|]
abs :: Exp -> Exp
abs Exp
e = [cexp|abs($exp:e)|]
signum :: Exp -> Exp
signum Exp
e = [cexp|$exp:e > 0 ? 1 : ($exp:e < 0 ? -1 : 0)|]
fromInteger :: Integer -> Exp
fromInteger Integer
n = [cexp|$int:n|]
instance Real C.Exp where
toRational :: Exp -> Rational
toRational Exp
[cexp|$float:n|] = Float -> Rational
forall a. Real a => a -> Rational
toRational Float
n
toRational Exp
[cexp|$double:n|] = Double -> Rational
forall a. Real a => a -> Rational
toRational Double
n
toRational Exp
[cexp|$ldouble:n|] = Double -> Rational
forall a. Real a => a -> Rational
toRational Double
n
toRational Exp
_ =
String -> Rational
forall a. HasCallStack => String -> a
error String
"fromEnum: non-rational constant C expressions"
instance Integral C.Exp where
Exp
e1 quotRem :: Exp -> Exp -> (Exp, Exp)
`quotRem` Exp
e2 = ([cexp|$exp:e1 / $exp:e2|], [cexp|$exp:e1 % $exp:e2|])
toInteger :: Exp -> Integer
toInteger Exp
[cexp|$int:n|] = Integer
n
toInteger Exp
[cexp|$uint:n|] = Integer
n
toInteger Exp
[cexp|$lint:n|] = Integer
n
toInteger Exp
[cexp|$ulint:n|] = Integer
n
toInteger Exp
_ =
String -> Integer
forall a. HasCallStack => String -> a
error String
"fromInteger: non-integer constant C expressions"
instance Fractional C.Exp where
Exp
e1 / :: Exp -> Exp -> Exp
/ Exp
e2 = [cexp|$exp:e1 / $exp:e2|]
recip :: Exp -> Exp
recip Exp
e = [cexp|1 / $exp:e|]
fromRational :: Rational -> Exp
fromRational Rational
n = [cexp|$double:(fromRational n)|]
instance Floating C.Exp where
pi :: Exp
pi = [cexp|3.141592653589793238|]
exp :: Exp -> Exp
exp Exp
e = [cexp|exp($exp:e)|]
sqrt :: Exp -> Exp
sqrt Exp
e = [cexp|sqrt($exp:e)|]
log :: Exp -> Exp
log Exp
e = [cexp|log($exp:e)|]
Exp
e1 ** :: Exp -> Exp -> Exp
** Exp
e2 = [cexp|pow($exp:e1, $exp:e2)|]
logBase :: Exp -> Exp -> Exp
logBase Exp
e1 Exp
e2 = [cexp|log($exp:e2)/log($exp:e1)|]
sin :: Exp -> Exp
sin Exp
e = [cexp|sin($exp:e)|]
tan :: Exp -> Exp
tan Exp
e = [cexp|tan($exp:e)|]
cos :: Exp -> Exp
cos Exp
e = [cexp|cos($exp:e)|]
asin :: Exp -> Exp
asin Exp
e = [cexp|asin($exp:e)|]
atan :: Exp -> Exp
atan Exp
e = [cexp|atan($exp:e)|]
acos :: Exp -> Exp
acos Exp
e = [cexp|acos($exp:e)|]
sinh :: Exp -> Exp
sinh Exp
e = [cexp|sinh($exp:e)|]
tanh :: Exp -> Exp
tanh Exp
e = [cexp|tanh($exp:e)|]
cosh :: Exp -> Exp
cosh Exp
e = [cexp|cosh($exp:e)|]
asinh :: Exp -> Exp
asinh Exp
e = [cexp|asinh($exp:e)|]
atanh :: Exp -> Exp
atanh Exp
e = [cexp|atanh($exp:e)|]
acosh :: Exp -> Exp
acosh Exp
e = [cexp|acosh($exp:e)|]
infix 4 ===
(===) :: C.Exp -> C.Exp -> C.Stm
Exp
e1 === :: Exp -> Exp -> Stm
=== Exp
e2 = [cstm|$exp:e1 = $exp:e2;|]
infix 4 +=
(+=) :: C.Exp -> C.Exp -> C.Stm
Exp
e1 += :: Exp -> Exp -> Stm
+= Exp
e2 = [cstm|$exp:e1 += $exp:e2;|]