{-# LANGUAGE PolyKinds, DataKinds, TypeFamilies, FlexibleInstances,
UndecidableInstances, ScopedTypeVariables, RankNTypes,
GADTs, FlexibleContexts, TypeOperators, ConstraintKinds,
TypeInType, TemplateHaskell, StandaloneDeriving #-}
{-# OPTIONS_GHC -Wno-orphans #-}
module Data.Singletons.TypeLits.Internal (
Sing(..),
Nat, Symbol,
SNat, SSymbol, withKnownNat, withKnownSymbol,
Error, sError,
Undefined, sUndefined,
KnownNat, TN.natVal, KnownSymbol, symbolVal,
type (^), (%^),
type (<>), (%<>),
ErrorSym0, ErrorSym1, UndefinedSym0,
type (^@#@$), type (^@#@$$), type (^@#@$$$),
type (<>@#@$), type (<>@#@$$), type (<>@#@$$$)
) where
import Data.Singletons.Promote
import Data.Singletons.Internal
import Data.Singletons.Prelude.Eq
import Data.Singletons.Prelude.Ord
import Data.Singletons.Decide
import Data.Singletons.Prelude.Bool
import GHC.TypeLits as TL
import qualified GHC.TypeNats as TN
import Data.Monoid ((<>))
import qualified Data.Type.Equality as DTE
import Data.Type.Equality ((:~:)(..))
import Data.Proxy ( Proxy(..) )
import Numeric.Natural (Natural)
import Unsafe.Coerce
import qualified Data.Text as T
import Data.Text ( Text )
data instance Sing (n :: Nat) = KnownNat n => SNat
instance KnownNat n => SingI n where
sing = SNat
instance SingKind Nat where
type Demote Nat = Natural
fromSing (SNat :: Sing n) = TN.natVal (Proxy :: Proxy n)
toSing n = case TN.someNatVal n of
SomeNat (_ :: Proxy n) -> SomeSing (SNat :: Sing n)
data instance Sing (n :: Symbol) = KnownSymbol n => SSym
instance KnownSymbol n => SingI n where
sing = SSym
instance SingKind Symbol where
type Demote Symbol = Text
fromSing (SSym :: Sing n) = T.pack (symbolVal (Proxy :: Proxy n))
toSing s = case someSymbolVal (T.unpack s) of
SomeSymbol (_ :: Proxy n) -> SomeSing (SSym :: Sing n)
instance SDecide Nat where
(SNat :: Sing n) %~ (SNat :: Sing m)
| TN.natVal (Proxy :: Proxy n) == TN.natVal (Proxy :: Proxy m)
= Proved $ unsafeCoerce Refl
| otherwise
= Disproved (\_ -> error errStr)
where errStr = "Broken Nat singletons"
instance SDecide Symbol where
(SSym :: Sing n) %~ (SSym :: Sing m)
| symbolVal (Proxy :: Proxy n) == symbolVal (Proxy :: Proxy m)
= Proved $ unsafeCoerce Refl
| otherwise
= Disproved (\_ -> error errStr)
where errStr = "Broken Symbol singletons"
instance PEq Nat where
type (a :: Nat) == (b :: Nat) = a DTE.== b
instance PEq Symbol where
type (a :: Symbol) == (b :: Symbol) = a DTE.== b
instance SEq Nat where
a %== b
| fromSing a == fromSing b = unsafeCoerce STrue
| otherwise = unsafeCoerce SFalse
instance SEq Symbol where
a %== b
| fromSing a == fromSing b = unsafeCoerce STrue
| otherwise = unsafeCoerce SFalse
instance POrd Nat where
type (a :: Nat) `Compare` (b :: Nat) = a `TN.CmpNat` b
instance POrd Symbol where
type (a :: Symbol) `Compare` (b :: Symbol) = a `TL.CmpSymbol` b
type SNat (x :: Nat) = Sing x
type SSymbol (x :: Symbol) = Sing x
instance SOrd Nat where
a `sCompare` b = case fromSing a `compare` fromSing b of
LT -> unsafeCoerce SLT
EQ -> unsafeCoerce SEQ
GT -> unsafeCoerce SGT
instance SOrd Symbol where
a `sCompare` b = case fromSing a `compare` fromSing b of
LT -> unsafeCoerce SLT
EQ -> unsafeCoerce SEQ
GT -> unsafeCoerce SGT
withKnownNat :: Sing n -> (KnownNat n => r) -> r
withKnownNat SNat f = f
withKnownSymbol :: Sing n -> (KnownSymbol n => r) -> r
withKnownSymbol SSym f = f
type family Error (str :: k0) :: k where {}
$(genDefunSymbols [''Error])
sError :: Sing (str :: Symbol) -> a
sError sstr = error (T.unpack (fromSing sstr))
type family Undefined :: k where {}
$(genDefunSymbols [''Undefined])
sUndefined :: a
sUndefined = undefined
(%^) :: Sing a -> Sing b -> Sing (a ^ b)
sa %^ sb =
let a = fromSing sa
b = fromSing sb
ex = TN.someNatVal (a ^ b)
in
case ex of
SomeNat (_ :: Proxy ab) -> unsafeCoerce (SNat :: Sing ab)
infixr 8 %^
$(genDefunSymbols [''(^)])
type a <> b = TL.AppendSymbol a b
infixr 6 <>
(%<>) :: Sing a -> Sing b -> Sing (a <> b)
sa %<> sb =
let a = fromSing sa
b = fromSing sb
ex = someSymbolVal $ T.unpack $ a <> b
in case ex of
SomeSymbol (_ :: Proxy ab) -> unsafeCoerce (SSym :: Sing ab)
infixr 6 %<>
$(genDefunSymbols [''(<>)])