{-# LANGUAGE TemplateHaskell, PolyKinds, DataKinds, TypeFamilies,
TypeOperators, GADTs, ScopedTypeVariables, UndecidableInstances,
DefaultSignatures, FlexibleContexts, InstanceSigs, NoStarIsType
#-}
module Data.Singletons.Prelude.Num (
PNum(..), SNum(..), Subtract, sSubtract,
type (+@#@$), type (+@#@$$), type (+@#@$$$),
type (-@#@$), type (-@#@$$), type (-@#@$$$),
type (*@#@$), type (*@#@$$), type (*@#@$$$),
NegateSym0, NegateSym1,
AbsSym0, AbsSym1,
SignumSym0, SignumSym1,
FromIntegerSym0, FromIntegerSym1,
SubtractSym0, SubtractSym1, SubtractSym2
) where
import Data.Ord (Down(..))
import Data.Singletons.Single
import Data.Singletons.Internal
import Data.Singletons.Prelude.Ord
import Data.Singletons.TypeLits.Internal
import Data.Singletons.Decide
import qualified GHC.TypeNats as TN
import GHC.TypeNats (Nat, SomeNat(..), someNatVal)
import Unsafe.Coerce
$(singletonsOnly [d|
class Num a where
(+), (-), (*) :: a -> a -> a
infixl 6 +
infixl 6 -
infixl 7 *
negate :: a -> a
abs :: a -> a
signum :: a -> a
fromInteger :: Nat -> a
x - y = x + negate y
negate x = 0 - x
instance Num a => Num (Down a) where
Down a + Down b = Down (a + b)
Down a - Down b = Down (a - b)
Down a * Down b = Down (a * b)
negate (Down a) = Down (negate a)
abs (Down a) = Down (abs a)
signum (Down a) = Down (signum a)
fromInteger n = Down (fromInteger n)
|])
infixl 6 +
infixl 6 -
infixl 7 *
type family SignumNat (a :: Nat) :: Nat where
SignumNat 0 = 0
SignumNat x = 1
instance PNum Nat where
type a + b = a TN.+ b
type a - b = a TN.- b
type a * b = a TN.* b
type Negate (a :: Nat) = Error "Cannot negate a natural number"
type Abs (a :: Nat) = a
type Signum a = SignumNat a
type FromInteger a = a
instance SNum Nat where
sa %+ sb =
let a = fromSing sa
b = fromSing sb
ex = someNatVal (a + b)
in
case ex of
SomeNat (_ :: Proxy ab) -> unsafeCoerce (SNat :: Sing ab)
sa %- sb =
let a = fromSing sa
b = fromSing sb
ex = someNatVal (a - b)
in
case ex of
SomeNat (_ :: Proxy ab) -> unsafeCoerce (SNat :: Sing ab)
sa %* sb =
let a = fromSing sa
b = fromSing sb
ex = someNatVal (a * b)
in
case ex of
SomeNat (_ :: Proxy ab) -> unsafeCoerce (SNat :: Sing ab)
sNegate _ = error "Cannot call sNegate on a natural number singleton."
sAbs x = x
sSignum sx =
case sx %~ (sing :: Sing 0) of
Proved Refl -> sing :: Sing 0
Disproved _ -> unsafeCoerce (sing :: Sing 1)
sFromInteger x = x
$(singletonsOnly [d|
subtract :: Num a => a -> a -> a
subtract x y = y - x
|])