{-# LANGUAGE CPP #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE FlexibleContexts #-}
{-# OPTIONS_GHC -Wall #-}
module Data.Boolean.Numbers
( NumB(..)
, IntegralB(..)
, RealFracB(..)
, RealFloatB(..)
, evenB, oddB
, fromIntegralB
) where
import Prelude hiding
( quotRem, divMod
, quot, rem
, div, mod
, properFraction
, fromInteger, toInteger )
import qualified Prelude as P
import Control.Arrow (first)
import Data.Boolean
infixr 9 .:
(.:) :: (c -> c') -> (a -> b -> c) -> (a -> b -> c')
.: :: (c -> c') -> (a -> b -> c) -> a -> b -> c'
(.:) = ((b -> c) -> b -> c') -> (a -> b -> c) -> a -> b -> c'
forall b c a. (b -> c) -> (a -> b) -> a -> c
(.)(((b -> c) -> b -> c') -> (a -> b -> c) -> a -> b -> c')
-> ((c -> c') -> (b -> c) -> b -> c')
-> (c -> c')
-> (a -> b -> c)
-> a
-> b
-> c'
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(c -> c') -> (b -> c) -> b -> c'
forall b c a. (b -> c) -> (a -> b) -> a -> c
(.)
(##) :: (a -> b -> c) -> (a -> b -> d) -> a -> b -> (c,d)
(a -> b -> c
f ## :: (a -> b -> c) -> (a -> b -> d) -> a -> b -> (c, d)
## a -> b -> d
g) a
x b
y = (a -> b -> c
f a
x b
y, a -> b -> d
g a
x b
y)
class Num a => NumB a where
type IntegerOf a
fromIntegerB :: IntegerOf a -> a
class (NumB a, OrdB a) => IntegralB a where
quot :: a -> a -> a
quot = (a, a) -> a
forall a b. (a, b) -> a
fst ((a, a) -> a) -> (a -> a -> (a, a)) -> a -> a -> a
forall c c' a b. (c -> c') -> (a -> b -> c) -> a -> b -> c'
.: a -> a -> (a, a)
forall a. IntegralB a => a -> a -> (a, a)
quotRem
rem :: a -> a -> a
rem = (a, a) -> a
forall a b. (a, b) -> b
snd ((a, a) -> a) -> (a -> a -> (a, a)) -> a -> a -> a
forall c c' a b. (c -> c') -> (a -> b -> c) -> a -> b -> c'
.: a -> a -> (a, a)
forall a. IntegralB a => a -> a -> (a, a)
quotRem
div :: a -> a -> a
div = (a, a) -> a
forall a b. (a, b) -> a
fst ((a, a) -> a) -> (a -> a -> (a, a)) -> a -> a -> a
forall c c' a b. (c -> c') -> (a -> b -> c) -> a -> b -> c'
.: a -> a -> (a, a)
forall a. IntegralB a => a -> a -> (a, a)
divMod
mod :: a -> a -> a
mod = (a, a) -> a
forall a b. (a, b) -> b
snd ((a, a) -> a) -> (a -> a -> (a, a)) -> a -> a -> a
forall c c' a b. (c -> c') -> (a -> b -> c) -> a -> b -> c'
.: a -> a -> (a, a)
forall a. IntegralB a => a -> a -> (a, a)
divMod
quotRem :: a -> a -> (a,a)
quotRem = a -> a -> a
forall a. IntegralB a => a -> a -> a
quot (a -> a -> a) -> (a -> a -> a) -> a -> a -> (a, a)
forall a b c d. (a -> b -> c) -> (a -> b -> d) -> a -> b -> (c, d)
## a -> a -> a
forall a. IntegralB a => a -> a -> a
rem
divMod :: a -> a -> (a,a)
divMod = a -> a -> a
forall a. IntegralB a => a -> a -> a
div (a -> a -> a) -> (a -> a -> a) -> a -> a -> (a, a)
forall a b c d. (a -> b -> c) -> (a -> b -> d) -> a -> b -> (c, d)
## a -> a -> a
forall a. IntegralB a => a -> a -> a
mod
toIntegerB :: a -> IntegerOf a
class (NumB a, OrdB a, Fractional a) => RealFracB a where
properFraction :: (IntegerOf a ~ IntegerOf b, IntegralB b) => a -> (b, a)
truncate :: (IntegerOf a ~ IntegerOf b, IntegralB b) => a -> b
truncate = (b, a) -> b
forall a b. (a, b) -> a
fst ((b, a) -> b) -> (a -> (b, a)) -> a -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> (b, a)
forall a b.
(RealFracB a, IntegerOf a ~ IntegerOf b, IntegralB b) =>
a -> (b, a)
properFraction
round :: (IntegerOf a ~ IntegerOf b, IntegralB b) => a -> b
ceiling :: (IntegerOf a ~ IntegerOf b, IntegralB b) => a -> b
floor :: (IntegerOf a ~ IntegerOf b, IntegralB b) => a -> b
class (Boolean (BooleanOf a), RealFracB a, Floating a) => RealFloatB a where
isNaN :: a -> BooleanOf a
isInfinite :: a -> BooleanOf a
isNegativeZero :: a -> BooleanOf a
isIEEE :: a -> BooleanOf a
atan2 :: a -> a -> a
evenB :: (IfB a, EqB a, IntegralB a) => a -> BooleanOf a
evenB :: a -> BooleanOf a
evenB a
n = a
n a -> a -> a
forall a. IntegralB a => a -> a -> a
`rem` a
2 a -> a -> BooleanOf a
forall a bool. (EqB a, bool ~ BooleanOf a) => a -> a -> bool
==* a
0
oddB :: (IfB a, EqB a, IntegralB a) => a -> BooleanOf a
oddB :: a -> BooleanOf a
oddB = BooleanOf a -> BooleanOf a
forall b. Boolean b => b -> b
notB (BooleanOf a -> BooleanOf a)
-> (a -> BooleanOf a) -> a -> BooleanOf a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> BooleanOf a
forall a. (IfB a, EqB a, IntegralB a) => a -> BooleanOf a
evenB
fromIntegralB :: (IntegerOf a ~ IntegerOf b, IntegralB a, NumB b) => a -> b
fromIntegralB :: a -> b
fromIntegralB = IntegerOf b -> b
forall a. NumB a => IntegerOf a -> a
fromIntegerB (IntegerOf b -> b) -> (a -> IntegerOf b) -> a -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> IntegerOf b
forall a. IntegralB a => a -> IntegerOf a
toIntegerB
fromInteger' :: (Integer ~ IntegerOf b, NumB b) => Integer -> b
fromInteger' :: Integer -> b
fromInteger' = Integer -> b
forall a b.
(IntegerOf a ~ IntegerOf b, IntegralB a, NumB b) =>
a -> b
fromIntegralB
#define DefaultNumBInstance(Ty) \
instance NumB (Ty) where {\
type IntegerOf (Ty) = Integer ;\
fromIntegerB = P.fromInteger }
#define DefaultIntegralBInstance(Ty) \
instance IntegralB (Ty) where {\
quotRem = P.quotRem ;\
divMod = P.divMod ;\
toIntegerB = P.toInteger }
#define DefaultRealFracFloatBInstance(Ty) \
instance RealFracB (Ty) where {\
properFraction = first fromInteger' . P.properFraction ;\
round = fromInteger' . P.round ;\
floor = fromInteger' . P.floor ;\
ceiling = fromInteger' . P.ceiling };\
instance RealFloatB (Ty) where {\
isNaN = P.isNaN ;\
isInfinite = P.isInfinite ;\
isNegativeZero = P.isNegativeZero ;\
isIEEE = P.isIEEE ;\
atan2 = P.atan2 }
DefaultNumBInstance(Int)
DefaultNumBInstance(Integer)
DefaultNumBInstance(Float)
DefaultNumBInstance(Double)
DefaultIntegralBInstance(Int)
DefaultIntegralBInstance(Integer)
DefaultRealFracFloatBInstance(Float)
DefaultRealFracFloatBInstance(Double)