parameterized-utils-2.1.5.0: Classes and data structures for working with data-kind indexed types
Safe HaskellNone
LanguageHaskell2010

Data.Parameterized.DataKind

Documentation

data PairRepr (f :: k1 -> Type) (g :: k2 -> Type) (p :: (k1, k2)) where Source #

Constructors

PairRepr :: f a -> g b -> PairRepr f g '(a, b) 

Instances

Instances details
(TestEquality f, TestEquality g) => TestEquality (PairRepr f g :: (k1, k2) -> Type) Source # 
Instance details

Defined in Data.Parameterized.DataKind

Methods

testEquality :: forall (a :: k) (b :: k). PairRepr f g a -> PairRepr f g b -> Maybe (a :~: b) #

(ShowF f, ShowF g) => ShowF (PairRepr f g :: (k1, k2) -> Type) Source # 
Instance details

Defined in Data.Parameterized.DataKind

Methods

withShow :: forall p q (tp :: k) a. p (PairRepr f g) -> q tp -> (Show (PairRepr f g tp) => a) -> a Source #

showF :: forall (tp :: k). PairRepr f g tp -> String Source #

showsPrecF :: forall (tp :: k). Int -> PairRepr f g tp -> String -> String Source #

(OrdF f, OrdF g) => OrdF (PairRepr f g :: (k1, k2) -> Type) Source # 
Instance details

Defined in Data.Parameterized.DataKind

Methods

compareF :: forall (x :: k) (y :: k). PairRepr f g x -> PairRepr f g y -> OrderingF x y Source #

leqF :: forall (x :: k) (y :: k). PairRepr f g x -> PairRepr f g y -> Bool Source #

ltF :: forall (x :: k) (y :: k). PairRepr f g x -> PairRepr f g y -> Bool Source #

geqF :: forall (x :: k) (y :: k). PairRepr f g x -> PairRepr f g y -> Bool Source #

gtF :: forall (x :: k) (y :: k). PairRepr f g x -> PairRepr f g y -> Bool Source #

(Eq (f a), Eq (g b)) => Eq (PairRepr f g '(a, b)) Source # 
Instance details

Defined in Data.Parameterized.DataKind

Methods

(==) :: PairRepr f g '(a, b) -> PairRepr f g '(a, b) -> Bool #

(/=) :: PairRepr f g '(a, b) -> PairRepr f g '(a, b) -> Bool #

(Ord (f a), Ord (g b)) => Ord (PairRepr f g '(a, b)) Source # 
Instance details

Defined in Data.Parameterized.DataKind

Methods

compare :: PairRepr f g '(a, b) -> PairRepr f g '(a, b) -> Ordering #

(<) :: PairRepr f g '(a, b) -> PairRepr f g '(a, b) -> Bool #

(<=) :: PairRepr f g '(a, b) -> PairRepr f g '(a, b) -> Bool #

(>) :: PairRepr f g '(a, b) -> PairRepr f g '(a, b) -> Bool #

(>=) :: PairRepr f g '(a, b) -> PairRepr f g '(a, b) -> Bool #

max :: PairRepr f g '(a, b) -> PairRepr f g '(a, b) -> PairRepr f g '(a, b) #

min :: PairRepr f g '(a, b) -> PairRepr f g '(a, b) -> PairRepr f g '(a, b) #

(ShowF f, ShowF g) => Show (PairRepr f g p) Source # 
Instance details

Defined in Data.Parameterized.DataKind

Methods

showsPrec :: Int -> PairRepr f g p -> ShowS #

show :: PairRepr f g p -> String #

showList :: [PairRepr f g p] -> ShowS #

type family Fst (pair :: (k1, k2)) where ... Source #

Equations

Fst '(a, _) = a 

type family Snd (pair :: (k1, k2)) where ... Source #

Equations

Snd '(_, b) = b 

fst :: PairRepr f g p -> f (Fst p) Source #

snd :: PairRepr f g p -> g (Snd p) Source #