{-# LANGUAGE EmptyDataDecls, MultiParamTypeClasses, FunctionalDependencies #-}
{-# LANGUAGE CPP, UndecidableInstances, FlexibleInstances #-}
--
-- .$Header: c:/Source/Haskell/Type/Data/Type/RCS/Bool.hs,v 1.4 2011/09/14 01:31:14 dosuser Exp dosuser $
module Data.Type.Bool where

data TTrue
data TFalse

tTrue :: TTrue
tTrue = undefined :: TTrue

tFalse :: TFalse
tFalse = undefined :: TFalse

class TNot a r | a -> r where
    tNot :: a -> r
    tNot _ = undefined

instance TNot TFalse TTrue
instance TNot TTrue TFalse

instance TNot a b => TNot (f a) b

class TAnd a b r | a b -> r where
    tAnd :: a -> b -> r
    tAnd _ _ = undefined

{-
instance TAnd TFalse TFalse TFalse where
    tAnd _ _ = hFalse
instance TAnd TFalse TTrue TFalse where
    tAnd _ _ = hFalse
instance TAnd TTrue TFalse TFalse where
    tAnd _ _ = hFalse
instance TAnd TTrue TTrue TTrue where
    tAnd _ _ = hTrue
-}

{-
instance TAnd TFalse b TFalse where
    tAnd _ _ = hFalse
instance TAnd TTrue b b where
    tAnd _ _ = undefined
-}

instance TAnd TFalse b TFalse
instance TAnd TTrue b b where
    tAnd _ y = y

instance TAnd a b r => TAnd (f a) (g b) r

class TOr a b r | a b -> r where
    tOr :: a -> b -> r
    tOr _ _ = undefined

{-
instance TOr TFalse TFalse TFalse where
    tOr _ _ = hFalse
instance TOr TFalse TTrue TTrue where
    tOr _ _ = hTrue
instance TOr TTrue TFalse TTrue where
    tOr _ _ = hTrue
instance TOr TTrue TTrue TTrue where
    tOr _ _ = hTrue
-}

instance TOr TFalse b b where
    tOr _ y = y
instance TOr TTrue b TTrue

instance TOr a b r => TOr (f a) (g b) r

class CNot f r where
    cNot :: f a -> r
    cNot = undefined

instance TNot (f a) r => CNot f r

-- vim: expandtab:tabstop=4:shiftwidth=4