{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE AllowAmbiguousTypes #-}
module Haskus.Utils.Types.Bool
( If
, NotB
, OrB
, AndB
, XorB
, KnownBool (..)
, Not
, And
, Or
, Xor
, AndMany
, OrMany
, XorMany
, AllFalse
, AllTrue
)
where
type family If (c :: Bool) (t :: k) (e :: k) where
If 'True t e = t
If 'False t e = e
class KnownBool a where
boolValue :: Bool
instance KnownBool 'True where
{-# INLINABLE boolValue #-}
boolValue = True
instance KnownBool 'False where
{-# INLINABLE boolValue #-}
boolValue = False
type family NotB x where
NotB 'True = 'False
NotB 'False = 'True
type family AndB x y where
AndB 'True 'True = 'True
AndB 'True 'False = 'False
AndB 'False 'True = 'False
AndB 'False 'False = 'False
type family OrB x y where
OrB 'True 'True = 'True
OrB 'False 'True = 'True
OrB 'True 'False = 'True
OrB 'False 'False = 'False
type family XorB x y where
XorB 'True 'True = 'False
XorB 'False 'True = 'True
XorB 'True 'False = 'True
XorB 'False 'False = 'False
type family Not (t :: b) (f :: b) (x :: b) :: b where
Not t f t = f
Not t f f = t
type family And (t :: b) (f :: b) (x :: b) (y :: b) :: b where
And t f t t = t
And t f t f = f
And t f f t = f
And t f f f = f
type family Or (t :: b) (f :: b) (x :: b) (y :: b) :: b where
Or t f t t = t
Or t f f t = t
Or t f t f = t
Or t f f f = f
type family Xor (t :: b) (f :: b) (x :: b) (y :: b) :: b where
Xor t f t t = f
Xor t f f t = t
Xor t f t f = t
Xor t f f f = f
type family AndMany (t :: b) (f :: b) (xs :: [b]) :: b where
AndMany t f '[t] = t
AndMany t f '[f] = f
AndMany t f (f ': xs) = f
AndMany t f (t ': xs) = AndMany t f xs
type family OrMany (t :: b) (f :: b) (xs :: [b]) :: b where
OrMany t f '[t] = t
OrMany t f '[f] = f
OrMany t f (t ': xs) = t
OrMany t f (f ': xs) = OrMany t f xs
type family XorMany (t :: b) (f :: b) (xs :: [b]) :: b where
XorMany t f '[t] = t
XorMany t f '[f] = f
XorMany t f (t ': xs) = AllFalse t f xs
XorMany t f (f ': xs) = XorMany t f xs
type family AllFalse (t :: b) (f :: b) (xs :: [b]) :: b where
AllFalse t f '[t] = f
AllFalse t f '[f] = t
AllFalse t f (t ': xs) = f
AllFalse t f (f ': xs) = AllFalse t f xs
type family AllTrue (t :: b) (f :: b) (xs :: [b]) :: b where
AllTrue t f '[t] = t
AllTrue t f '[f] = f
AllTrue t f (f ': xs) = f
AllTrue t f (t ': xs) = AllTrue t f xs