{-# LANGUAGE CPP #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeOperators #-}
#if __GLASGOW_HASKELL__ >= 800
{-# OPTIONS_GHC -Wno-redundant-constraints #-}
#endif
#if MIN_VERSION_base(4,7,0)
{-# LANGUAGE EmptyCase #-}
{-# LANGUAGE FlexibleContexts #-}
#endif
module Data.Singletons.Bool (
SBool(..),
SBoolI(..),
fromSBool,
withSomeSBool,
reflectBool,
reifyBool,
#if MIN_VERSION_base(4,7,0)
discreteBool,
#endif
#if MIN_VERSION_base(4,7,0)
sboolAnd, sboolOr, sboolNot,
eqToRefl, eqCast, sboolEqRefl,
trivialRefl,
#endif
) where
#if MIN_VERSION_base(4,7,0)
import Data.Type.Bool
import Data.Type.Dec (Dec (..))
import Data.Type.Equality
import Unsafe.Coerce (unsafeCoerce)
#endif
import Data.Proxy (Proxy (..))
data SBool (b :: Bool) where
STrue :: SBool 'True
SFalse :: SBool 'False
class SBoolI (b :: Bool) where sbool :: SBool b
instance SBoolI 'True where sbool = STrue
instance SBoolI 'False where sbool = SFalse
instance Show (SBool b) where
showsPrec _ STrue = showString "STrue"
showsPrec _ SFalse = showString "SFalse"
instance Eq (SBool b) where
_ == _ = True
instance Ord (SBool b) where
compare _ _ = EQ
fromSBool :: SBool b -> Bool
fromSBool STrue = True
fromSBool SFalse = False
withSomeSBool :: Bool -> (forall b. SBool b -> r) -> r
withSomeSBool True f = f STrue
withSomeSBool False f = f SFalse
reifyBool :: forall r. Bool -> (forall b. SBoolI b => Proxy b -> r) -> r
reifyBool True f = f (Proxy :: Proxy 'True)
reifyBool False f = f (Proxy :: Proxy 'False)
reflectBool :: forall b proxy. SBoolI b => proxy b -> Bool
reflectBool _ = fromSBool (sbool :: SBool b)
#if MIN_VERSION_base(4,7,0)
discreteBool :: forall a b. (SBoolI a, SBoolI b) => Dec (a :~: b)
discreteBool = case (sbool :: SBool a, sbool :: SBool b) of
(STrue, STrue) -> Yes Refl
(STrue, SFalse) -> No $ \p -> case p of {}
(SFalse, STrue) -> No $ \p -> case p of {}
(SFalse, SFalse) -> Yes Refl
#endif
#if MIN_VERSION_base(4,7,0)
sboolAnd :: SBool a -> SBool b -> SBool (a && b)
sboolAnd SFalse _ = SFalse
sboolAnd STrue b = b
sboolOr :: SBool a -> SBool b -> SBool (a || b)
sboolOr STrue _ = STrue
sboolOr SFalse b = b
sboolNot :: SBool a -> SBool (Not a)
sboolNot STrue = SFalse
sboolNot SFalse = STrue
eqToRefl :: (a == b) ~ 'True => a :~: b
eqToRefl = unsafeCoerce trivialRefl
eqCast :: (a == b) ~ 'True => a -> b
eqCast = unsafeCoerce
trivialRefl :: () :~: ()
trivialRefl = Refl
# if __GLASGOW_HASKELL__ >= 806
# define KVS(kvs) kvs
# else
# define KVS(kvs)
# endif
sboolEqRefl :: forall KVS(k) (a :: k) (b :: k). SBoolI (a == b) => Maybe (a :~: b)
sboolEqRefl = case sbool :: SBool (a == b) of
STrue -> Just eqToRefl
SFalse -> Nothing
#endif