{-# LANGUAGE TemplateHaskell, TypeApplications, TypeFamilies, TypeOperators,
             GADTs, ScopedTypeVariables, DeriveDataTypeable, UndecidableInstances,
             DataKinds, PolyKinds #-}
module Data.Singletons.Prelude.Bool (
  
  Sing(SFalse, STrue),
  
  
  
  
  
  SBool,
  
  
  If, sIf,
  
  Not, sNot, type (&&), type (||), (%&&), (%||),
  
  
  bool_, Bool_, sBool_, Otherwise, sOtherwise,
  
  TrueSym0, FalseSym0,
  NotSym0, NotSym1,
  type (&&@#@$), type (&&@#@$$), type (&&@#@$$$),
  type (||@#@$), type (||@#@$$), type (||@#@$$$),
  Bool_Sym0, Bool_Sym1, Bool_Sym2, Bool_Sym3,
  OtherwiseSym0
  ) where
import Data.Singletons.Internal
import Data.Singletons.Prelude.Instances
import Data.Singletons.Promote
import Data.Singletons.Single
import Data.Type.Bool ( If, type (&&), type (||), Not )
$(singletons [d|
  bool_ :: a -> a -> Bool -> a
  bool_ fls _tru False = fls
  bool_ _fls tru True  = tru
 |])
$(singletonsOnly [d|
  otherwise               :: Bool
  otherwise               =  True
  |])
(%&&) :: Sing a -> Sing b -> Sing (a && b)
SFalse %&& _ = SFalse
STrue  %&& a = a
infixr 3 %&&
$(genDefunSymbols [''(&&)])
instance SingI (&&@#@$) where
  sing = singFun2 (%&&)
instance SingI x => SingI ((&&@#@$$) x) where
  sing = singFun1 (sing @x %&&)
(%||) :: Sing a -> Sing b -> Sing (a || b)
SFalse %|| a = a
STrue  %|| _ = STrue
infixr 2 %||
$(genDefunSymbols [''(||)])
instance SingI (||@#@$) where
  sing = singFun2 (%||)
instance SingI x => SingI ((||@#@$$) x) where
  sing = singFun1 (sing @x %||)
sNot :: Sing a -> Sing (Not a)
sNot SFalse = STrue
sNot STrue  = SFalse
$(genDefunSymbols [''Not])
instance SingI NotSym0 where
  sing = singFun1 sNot
sIf :: Sing a -> Sing b -> Sing c -> Sing (If a b c)
sIf STrue b _ = b
sIf SFalse _ c = c