{-# LANGUAGE CPP #-}
#if (__GLASGOW_HASKELL__ < 709)
{-# LANGUAGE OverlappingInstances #-}
{-# OPTIONS_GHC -fno-warn-unrecognised-pragmas #-}
#endif
module Data.HList.TypeEqO where
import Data.HList.FakePrelude
#if !NEW_TYPE_EQ
instance {-# OVERLAPPING #-} HEq x x True
instance {-# OVERLAPPABLE #-} False ~ b => HEq x y b
#endif
class TupleType (t :: *) (b :: Bool) | t -> b
instance {-# OVERLAPPING #-} TupleType () True
instance {-# OVERLAPPING #-} TupleType (x,y) True
instance {-# OVERLAPPING #-} TupleType (x,y,z) True
instance {-# OVERLAPPABLE #-} False ~ b => TupleType x b
instance {-# OVERLAPPING #-} Show (Proxy True) where show :: Proxy 'True -> String
show Proxy 'True
_ = String
"HTrue"
instance {-# OVERLAPPING #-} Show (Proxy False) where show :: Proxy 'False -> String
show Proxy 'False
_ = String
"HFalse"
instance {-# OVERLAPPING #-} HNat2Integral n => Show (Proxy (n :: HNat)) where
show :: Proxy n -> String
show Proxy n
n = String
"H" forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show (forall (n :: HNat) i. (HNat2Integral n, Integral i) => Proxy n -> i
hNat2Integral Proxy n
n :: Integer)
instance {-# OVERLAPPABLE #-} hZero ~ HZero => ArityFwd f hZero
instance {-# OVERLAPPING #-} Arity f n => ArityFwd (x -> f) (HSucc n)
class IsKeyFN (t :: *) (flag :: Bool) | t-> flag
instance {-# OVERLAPPABLE #-} (False ~ flag) => IsKeyFN t flag