generics-mrsop-2.0.0: Generic Programming with Mutually Recursive Sums of Products.

Safe HaskellSafe
LanguageHaskell2010

Generics.MRSOP.Util

Contents

Description

Useful utilities we need accross multiple modules.

Synopsis

Utility Functions and Types

(&&&) :: Arrow a => forall b c c'. a b c -> a b c' -> a b (c, c') infixr 3 #

Fanout: send the input to both argument arrows and combine their output.

The default definition may be overridden with a more efficient version if desired.

(***) :: Arrow a => forall b c b' c'. a b c -> a b' c' -> a (b, b') (c, c') infixr 3 #

Split the input between the two argument arrows and combine their output. Note that this is in general not a functor.

The default definition may be overridden with a more efficient version if desired.

type (:->) f g = forall n. f n -> g n Source #

Natural transformations

(<.>) :: Monad m => (b -> m c) -> (a -> m b) -> a -> m c infixr 8 Source #

Kleisli Composition

Poly-kind indexed product functionality

data Product k (f :: k -> *) (g :: k -> *) (a :: k) :: forall k. (k -> *) -> (k -> *) -> k -> * #

Lifted product of functors.

Constructors

Pair (f a) (g a) 

Instances

Generic1 k (Product k f g) 

Associated Types

type Rep1 (Product k f g) (f :: Product k f g -> *) :: k -> * #

Methods

from1 :: f a -> Rep1 (Product k f g) f a #

to1 :: Rep1 (Product k f g) f a -> f a #

(ShowHO ki f, ShowHO ki g) => ShowHO ki (Product ki f g) Source # 

Methods

showHO :: f k -> String Source #

(EqHO ki f, EqHO ki g) => EqHO ki (Product ki f g) Source # 

Methods

eqHO :: f k -> f k -> Bool Source #

(Monad f, Monad g) => Monad (Product * f g)

Since: 4.9.0.0

Methods

(>>=) :: Product * f g a -> (a -> Product * f g b) -> Product * f g b #

(>>) :: Product * f g a -> Product * f g b -> Product * f g b #

return :: a -> Product * f g a #

fail :: String -> Product * f g a #

(Functor f, Functor g) => Functor (Product * f g)

Since: 4.9.0.0

Methods

fmap :: (a -> b) -> Product * f g a -> Product * f g b #

(<$) :: a -> Product * f g b -> Product * f g a #

(MonadFix f, MonadFix g) => MonadFix (Product * f g)

Since: 4.9.0.0

Methods

mfix :: (a -> Product * f g a) -> Product * f g a #

(Applicative f, Applicative g) => Applicative (Product * f g)

Since: 4.9.0.0

Methods

pure :: a -> Product * f g a #

(<*>) :: Product * f g (a -> b) -> Product * f g a -> Product * f g b #

liftA2 :: (a -> b -> c) -> Product * f g a -> Product * f g b -> Product * f g c #

(*>) :: Product * f g a -> Product * f g b -> Product * f g b #

(<*) :: Product * f g a -> Product * f g b -> Product * f g a #

(Foldable f, Foldable g) => Foldable (Product * f g)

Since: 4.9.0.0

Methods

fold :: Monoid m => Product * f g m -> m #

foldMap :: Monoid m => (a -> m) -> Product * f g a -> m #

foldr :: (a -> b -> b) -> b -> Product * f g a -> b #

foldr' :: (a -> b -> b) -> b -> Product * f g a -> b #

foldl :: (b -> a -> b) -> b -> Product * f g a -> b #

foldl' :: (b -> a -> b) -> b -> Product * f g a -> b #

foldr1 :: (a -> a -> a) -> Product * f g a -> a #

foldl1 :: (a -> a -> a) -> Product * f g a -> a #

toList :: Product * f g a -> [a] #

null :: Product * f g a -> Bool #

length :: Product * f g a -> Int #

elem :: Eq a => a -> Product * f g a -> Bool #

maximum :: Ord a => Product * f g a -> a #

minimum :: Ord a => Product * f g a -> a #

sum :: Num a => Product * f g a -> a #

product :: Num a => Product * f g a -> a #

(Traversable f, Traversable g) => Traversable (Product * f g)

Since: 4.9.0.0

Methods

traverse :: Applicative f => (a -> f b) -> Product * f g a -> f (Product * f g b) #

sequenceA :: Applicative f => Product * f g (f a) -> f (Product * f g a) #

mapM :: Monad m => (a -> m b) -> Product * f g a -> m (Product * f g b) #

sequence :: Monad m => Product * f g (m a) -> m (Product * f g a) #

(Eq1 f, Eq1 g) => Eq1 (Product * f g)

Since: 4.9.0.0

Methods

liftEq :: (a -> b -> Bool) -> Product * f g a -> Product * f g b -> Bool #

(Ord1 f, Ord1 g) => Ord1 (Product * f g)

Since: 4.9.0.0

Methods

liftCompare :: (a -> b -> Ordering) -> Product * f g a -> Product * f g b -> Ordering #

(Read1 f, Read1 g) => Read1 (Product * f g)

Since: 4.9.0.0

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Product * f g a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Product * f g a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Product * f g a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Product * f g a] #

(Show1 f, Show1 g) => Show1 (Product * f g)

Since: 4.9.0.0

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Product * f g a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Product * f g a] -> ShowS #

(MonadZip f, MonadZip g) => MonadZip (Product * f g)

Since: 4.9.0.0

Methods

mzip :: Product * f g a -> Product * f g b -> Product * f g (a, b) #

mzipWith :: (a -> b -> c) -> Product * f g a -> Product * f g b -> Product * f g c #

munzip :: Product * f g (a, b) -> (Product * f g a, Product * f g b) #

(Alternative f, Alternative g) => Alternative (Product * f g)

Since: 4.9.0.0

Methods

empty :: Product * f g a #

(<|>) :: Product * f g a -> Product * f g a -> Product * f g a #

some :: Product * f g a -> Product * f g [a] #

many :: Product * f g a -> Product * f g [a] #

(MonadPlus f, MonadPlus g) => MonadPlus (Product * f g)

Since: 4.9.0.0

Methods

mzero :: Product * f g a #

mplus :: Product * f g a -> Product * f g a -> Product * f g a #

(Eq1 f, Eq1 g, Eq a) => Eq (Product * f g a)

Since: 4.9.0.0

Methods

(==) :: Product * f g a -> Product * f g a -> Bool #

(/=) :: Product * f g a -> Product * f g a -> Bool #

(Data (g a), Data (f a), Typeable * k, Typeable (k -> *) g, Typeable (k -> *) f, Typeable k a) => Data (Product k f g a) 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall b. b -> c b) -> Product k f g a -> c (Product k f g a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Product k f g a) #

toConstr :: Product k f g a -> Constr #

dataTypeOf :: Product k f g a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Product k f g a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Product k f g a)) #

gmapT :: (forall b. Data b => b -> b) -> Product k f g a -> Product k f g a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Product k f g a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Product k f g a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Product k f g a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Product k f g a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Product k f g a -> m (Product k f g a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Product k f g a -> m (Product k f g a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Product k f g a -> m (Product k f g a) #

(Ord1 f, Ord1 g, Ord a) => Ord (Product * f g a)

Since: 4.9.0.0

Methods

compare :: Product * f g a -> Product * f g a -> Ordering #

(<) :: Product * f g a -> Product * f g a -> Bool #

(<=) :: Product * f g a -> Product * f g a -> Bool #

(>) :: Product * f g a -> Product * f g a -> Bool #

(>=) :: Product * f g a -> Product * f g a -> Bool #

max :: Product * f g a -> Product * f g a -> Product * f g a #

min :: Product * f g a -> Product * f g a -> Product * f g a #

(Read1 f, Read1 g, Read a) => Read (Product * f g a)

Since: 4.9.0.0

Methods

readsPrec :: Int -> ReadS (Product * f g a) #

readList :: ReadS [Product * f g a] #

readPrec :: ReadPrec (Product * f g a) #

readListPrec :: ReadPrec [Product * f g a] #

(Show1 f, Show1 g, Show a) => Show (Product * f g a)

Since: 4.9.0.0

Methods

showsPrec :: Int -> Product * f g a -> ShowS #

show :: Product * f g a -> String #

showList :: [Product * f g a] -> ShowS #

Generic (Product k f g a) 

Associated Types

type Rep (Product k f g a) :: * -> * #

Methods

from :: Product k f g a -> Rep (Product k f g a) x #

to :: Rep (Product k f g a) x -> Product k f g a #

type Rep1 k (Product k f g) 
type Rep (Product k f g a) 

pattern (:*:) :: f a -> g a -> Product f g a Source #

type Delta f = Product f f Source #

Diagonal indexed functor

curry' :: (Product f g x -> a) -> f x -> g x -> a Source #

Lifted curry

uncurry' :: (f x -> g x -> a) -> Product f g x -> a Source #

Lifted uncurry

delta :: f :-> Delta f Source #

Duplicates its argument

Poly-kind indexed sums

data Sum k (f :: k -> *) (g :: k -> *) (a :: k) :: forall k. (k -> *) -> (k -> *) -> k -> * #

Lifted sum of functors.

Constructors

InL (f a) 
InR (g a) 

Instances

Generic1 k (Sum k f g) 

Associated Types

type Rep1 (Sum k f g) (f :: Sum k f g -> *) :: k -> * #

Methods

from1 :: f a -> Rep1 (Sum k f g) f a #

to1 :: Rep1 (Sum k f g) f a -> f a #

(ShowHO ki f, ShowHO ki g) => ShowHO ki (Sum ki f g) Source # 

Methods

showHO :: f k -> String Source #

(EqHO ki f, EqHO ki g) => EqHO ki (Sum ki f g) Source # 

Methods

eqHO :: f k -> f k -> Bool Source #

(Functor f, Functor g) => Functor (Sum * f g)

Since: 4.9.0.0

Methods

fmap :: (a -> b) -> Sum * f g a -> Sum * f g b #

(<$) :: a -> Sum * f g b -> Sum * f g a #

(Foldable f, Foldable g) => Foldable (Sum * f g)

Since: 4.9.0.0

Methods

fold :: Monoid m => Sum * f g m -> m #

foldMap :: Monoid m => (a -> m) -> Sum * f g a -> m #

foldr :: (a -> b -> b) -> b -> Sum * f g a -> b #

foldr' :: (a -> b -> b) -> b -> Sum * f g a -> b #

foldl :: (b -> a -> b) -> b -> Sum * f g a -> b #

foldl' :: (b -> a -> b) -> b -> Sum * f g a -> b #

foldr1 :: (a -> a -> a) -> Sum * f g a -> a #

foldl1 :: (a -> a -> a) -> Sum * f g a -> a #

toList :: Sum * f g a -> [a] #

null :: Sum * f g a -> Bool #

length :: Sum * f g a -> Int #

elem :: Eq a => a -> Sum * f g a -> Bool #

maximum :: Ord a => Sum * f g a -> a #

minimum :: Ord a => Sum * f g a -> a #

sum :: Num a => Sum * f g a -> a #

product :: Num a => Sum * f g a -> a #

(Traversable f, Traversable g) => Traversable (Sum * f g)

Since: 4.9.0.0

Methods

traverse :: Applicative f => (a -> f b) -> Sum * f g a -> f (Sum * f g b) #

sequenceA :: Applicative f => Sum * f g (f a) -> f (Sum * f g a) #

mapM :: Monad m => (a -> m b) -> Sum * f g a -> m (Sum * f g b) #

sequence :: Monad m => Sum * f g (m a) -> m (Sum * f g a) #

(Eq1 f, Eq1 g) => Eq1 (Sum * f g)

Since: 4.9.0.0

Methods

liftEq :: (a -> b -> Bool) -> Sum * f g a -> Sum * f g b -> Bool #

(Ord1 f, Ord1 g) => Ord1 (Sum * f g)

Since: 4.9.0.0

Methods

liftCompare :: (a -> b -> Ordering) -> Sum * f g a -> Sum * f g b -> Ordering #

(Read1 f, Read1 g) => Read1 (Sum * f g)

Since: 4.9.0.0

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Sum * f g a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Sum * f g a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Sum * f g a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Sum * f g a] #

(Show1 f, Show1 g) => Show1 (Sum * f g)

Since: 4.9.0.0

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Sum * f g a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Sum * f g a] -> ShowS #

(Eq1 f, Eq1 g, Eq a) => Eq (Sum * f g a)

Since: 4.9.0.0

Methods

(==) :: Sum * f g a -> Sum * f g a -> Bool #

(/=) :: Sum * f g a -> Sum * f g a -> Bool #

(Data (g a), Data (f a), Typeable * k, Typeable (k -> *) g, Typeable (k -> *) f, Typeable k a) => Data (Sum k f g a) 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall b. b -> c b) -> Sum k f g a -> c (Sum k f g a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Sum k f g a) #

toConstr :: Sum k f g a -> Constr #

dataTypeOf :: Sum k f g a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Sum k f g a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Sum k f g a)) #

gmapT :: (forall b. Data b => b -> b) -> Sum k f g a -> Sum k f g a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Sum k f g a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Sum k f g a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Sum k f g a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Sum k f g a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Sum k f g a -> m (Sum k f g a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Sum k f g a -> m (Sum k f g a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Sum k f g a -> m (Sum k f g a) #

(Ord1 f, Ord1 g, Ord a) => Ord (Sum * f g a)

Since: 4.9.0.0

Methods

compare :: Sum * f g a -> Sum * f g a -> Ordering #

(<) :: Sum * f g a -> Sum * f g a -> Bool #

(<=) :: Sum * f g a -> Sum * f g a -> Bool #

(>) :: Sum * f g a -> Sum * f g a -> Bool #

(>=) :: Sum * f g a -> Sum * f g a -> Bool #

max :: Sum * f g a -> Sum * f g a -> Sum * f g a #

min :: Sum * f g a -> Sum * f g a -> Sum * f g a #

(Read1 f, Read1 g, Read a) => Read (Sum * f g a)

Since: 4.9.0.0

Methods

readsPrec :: Int -> ReadS (Sum * f g a) #

readList :: ReadS [Sum * f g a] #

readPrec :: ReadPrec (Sum * f g a) #

readListPrec :: ReadPrec [Sum * f g a] #

(Show1 f, Show1 g, Show a) => Show (Sum * f g a)

Since: 4.9.0.0

Methods

showsPrec :: Int -> Sum * f g a -> ShowS #

show :: Sum * f g a -> String #

showList :: [Sum * f g a] -> ShowS #

Generic (Sum k f g a) 

Associated Types

type Rep (Sum k f g a) :: * -> * #

Methods

from :: Sum k f g a -> Rep (Sum k f g a) x #

to :: Rep (Sum k f g a) x -> Sum k f g a #

type Rep1 k (Sum k f g) 
type Rep (Sum k f g a) 

either' :: (f :-> r) -> (g :-> r) -> Sum f g :-> r Source #

Higher-order sum eliminator

either'' :: (forall x. f x -> a) -> (forall y. g y -> a) -> Sum f g r -> a Source #

Just like either', but the result type is of kind Star

Type-level Naturals

data Nat Source #

Type-level Peano Naturals

Constructors

S Nat 
Z 

Instances

Eq Nat Source # 

Methods

(==) :: Nat -> Nat -> Bool #

(/=) :: Nat -> Nat -> Bool #

Show Nat Source # 

Methods

showsPrec :: Int -> Nat -> ShowS #

show :: Nat -> String #

showList :: [Nat] -> ShowS #

TestEquality Nat SNat Source # 

Methods

testEquality :: f a -> f b -> Maybe ((SNat :~: a) b) #

TestEquality Nat (Constr k codes) # 

Methods

testEquality :: f a -> f b -> Maybe ((Constr k codes :~: a) b) #

EqHO kon ki => EqHO Nat (Fix kon ki codes) Source # 

Methods

eqHO :: f k -> f k -> Bool Source #

data SNat :: Nat -> * where Source #

Singleton Term-level natural

Constructors

SZ :: SNat Z 
SS :: SNat n -> SNat (S n) 

Instances

TestEquality Nat SNat Source # 

Methods

testEquality :: f a -> f b -> Maybe ((SNat :~: a) b) #

class IsNat (n :: Nat) where Source #

And their conversion to term-level integers.

Minimal complete definition

getSNat

Methods

getSNat :: Proxy n -> SNat n Source #

Instances

IsNat Z Source # 

Methods

getSNat :: Proxy Nat Z -> SNat Z Source #

IsNat n => IsNat (S n) Source # 

Methods

getSNat :: Proxy Nat (S n) -> SNat (S n) Source #

getSNat' :: forall (n :: Nat). IsNat n => SNat n Source #

Type-level Lists

data ListPrf :: [k] -> * where Source #

An inhabitant of ListPrf ls is *not* a singleton! It only proves that ls is, in fact, a type level list. This is useful since it enables us to pattern match on type-level lists whenever we see fit.

Constructors

Nil :: ListPrf '[] 
Cons :: ListPrf l -> ListPrf (x ': l) 

class IsList (xs :: [k]) where Source #

The IsList class allows us to construct ListPrfs in a straight forward fashion.

Minimal complete definition

listPrf

Methods

listPrf :: ListPrf xs Source #

Instances

IsList k ([] k) Source # 

Methods

listPrf :: ListPrf [k] xs Source #

IsList k xs => IsList k ((:) k x xs) Source # 

Methods

listPrf :: ListPrf ((k ': x) xs) xs Source #

type L1 xs = IsList xs Source #

Convenient constraint synonyms

type L2 xs ys = (IsList xs, IsList ys) Source #

type L3 xs ys zs = (IsList xs, IsList ys, IsList zs) Source #

type L4 xs ys zs as = (IsList xs, IsList ys, IsList zs, IsList as) Source #

type family (txs :: [k]) :++: (tys :: [k]) :: [k] where ... Source #

Appending type-level lists

Equations

'[] :++: tys = tys 
(tx ': txs) :++: tys = tx ': (txs :++: tys) 

appendIsListLemma :: ListPrf xs -> ListPrf ys -> ListPrf (xs :++: ys) Source #

Concatenation of lists is also a list.

Type-level List Lookup

type family Lkup (n :: Nat) (ks :: [k]) :: k where ... Source #

Type-level list lookup

Equations

Lkup Z (k ': ks) = k 
Lkup (S n) (k ': ks) = Lkup n ks 
Lkup _ '[] = TypeError (Text "Lkup index too big") 

type family Idx (ty :: k) (xs :: [k]) :: Nat where ... Source #

Type-level list index

Equations

Idx x (x ': ys) = Z 
Idx x (y ': ys) = S (Idx x ys) 
Idx x '[] = TypeError (Text "Element not found") 

data El :: [*] -> Nat -> * where Source #

Also list lookup, but for kind * only.

Constructors

El :: IsNat ix => {..} -> El fam ix 

Fields

getElSNat :: forall ix ls. El ls ix -> SNat ix Source #

Convenient way to cast an El index to term-level.

into :: forall fam ty ix. (ix ~ Idx ty fam, Lkup ix fam ~ ty, IsNat ix) => ty -> El fam ix Source #

Smart constructor into El

Higher-order Eq and Show

class EqHO (f :: ki -> *) where Source #

Higher order version of Eq

Minimal complete definition

eqHO

Methods

eqHO :: forall k. f k -> f k -> Bool Source #

Instances

EqHO Kon Singl Source # 

Methods

eqHO :: f k -> f k -> Bool Source #

Eq a => EqHO ki (Const ki a) Source # 

Methods

eqHO :: f k -> f k -> Bool Source #

(EqHO ki f, EqHO ki g) => EqHO ki (Sum ki f g) Source # 

Methods

eqHO :: f k -> f k -> Bool Source #

(EqHO ki f, EqHO ki g) => EqHO ki (Product ki f g) Source # 

Methods

eqHO :: f k -> f k -> Bool Source #

EqHO kon ki => EqHO Nat (Fix kon ki codes) Source # 

Methods

eqHO :: f k -> f k -> Bool Source #

EqHO k phi => EqHO [k] (NS k phi) Source # 

Methods

eqHO :: f k -> f k -> Bool Source #

EqHO k phi => EqHO [k] (NP k phi) Source # 

Methods

eqHO :: f k -> f k -> Bool Source #

(EqHO Nat phi, EqHO kon ki) => EqHO [[Atom kon]] (Rep kon ki phi) Source # 

Methods

eqHO :: f k -> f k -> Bool Source #

(EqHO Nat phi, EqHO kon ki) => EqHO (Atom kon) (NA kon ki phi) Source # 

Methods

eqHO :: f k -> f k -> Bool Source #

class ShowHO (f :: ki -> *) where Source #

Higher order version of Show

Minimal complete definition

showHO

Methods

showHO :: forall k. f k -> String Source #

Instances

ShowHO Kon Singl Source # 

Methods

showHO :: f k -> String Source #

Show a => ShowHO ki (Const ki a) Source # 

Methods

showHO :: f k -> String Source #

(ShowHO ki f, ShowHO ki g) => ShowHO ki (Sum ki f g) Source # 

Methods

showHO :: f k -> String Source #

(ShowHO ki f, ShowHO ki g) => ShowHO ki (Product ki f g) Source # 

Methods

showHO :: f k -> String Source #

ShowHO [Atom kon] (ConstructorInfo kon) Source # 

Methods

showHO :: f k -> String Source #

ShowHO (Atom kon) (FieldInfo kon) Source # 

Methods

showHO :: f k -> String Source #

ShowHO k phi => ShowHO [k] (NS k phi) Source # 

Methods

showHO :: f k -> String Source #

ShowHO k phi => ShowHO [k] (NP k phi) Source # 

Methods

showHO :: f k -> String Source #

(ShowHO Nat phi, ShowHO kon ki) => ShowHO (Atom kon) (NA kon ki phi) Source # 

Methods

showHO :: f k -> String Source #