bowtie-0.6.0: Tying knots in polynomial functors
Safe HaskellSafe-Inferred
LanguageGHC2021

Bowtie.Knot

Synopsis

Documentation

newtype Knot g a Source #

A fixpoint for a Bifunctor where the second type variable contains the recursive structure.

Constructors

Knot 

Fields

Instances

Instances details
(Bifunctor g, Bifoldable g) => Foldable (Knot g) Source # 
Instance details

Defined in Bowtie.Knot

Methods

fold :: Monoid m => Knot g m -> m #

foldMap :: Monoid m => (a -> m) -> Knot g a -> m #

foldMap' :: Monoid m => (a -> m) -> Knot g a -> m #

foldr :: (a -> b -> b) -> b -> Knot g a -> b #

foldr' :: (a -> b -> b) -> b -> Knot g a -> b #

foldl :: (b -> a -> b) -> b -> Knot g a -> b #

foldl' :: (b -> a -> b) -> b -> Knot g a -> b #

foldr1 :: (a -> a -> a) -> Knot g a -> a #

foldl1 :: (a -> a -> a) -> Knot g a -> a #

toList :: Knot g a -> [a] #

null :: Knot g a -> Bool #

length :: Knot g a -> Int #

elem :: Eq a => a -> Knot g a -> Bool #

maximum :: Ord a => Knot g a -> a #

minimum :: Ord a => Knot g a -> a #

sum :: Num a => Knot g a -> a #

product :: Num a => Knot g a -> a #

Bitraversable g => Traversable (Knot g) Source # 
Instance details

Defined in Bowtie.Knot

Methods

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

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

mapM :: Monad m => (a -> m b) -> Knot g a -> m (Knot g b) #

sequence :: Monad m => Knot g (m a) -> m (Knot g a) #

Bifunctor g => Functor (Knot g) Source # 
Instance details

Defined in Bowtie.Knot

Methods

fmap :: (a -> b) -> Knot g a -> Knot g b #

(<$) :: a -> Knot g b -> Knot g a #

Bifunctor g => Corecursive1 (Knot g) Source # 
Instance details

Defined in Bowtie.Knot

Methods

embed1 :: Base1 (Knot g) a (Knot g a) -> Knot g a Source #

Bifunctor g => Recursive1 (Knot g) Source # 
Instance details

Defined in Bowtie.Knot

Methods

project1 :: Knot g a -> Base1 (Knot g) a (Knot g a) Source #

IsString (g a (Knot g a)) => IsString (Knot g a) Source # 
Instance details

Defined in Bowtie.Knot

Methods

fromString :: String -> Knot g a #

Show (g a (Knot g a)) => Show (Knot g a) Source # 
Instance details

Defined in Bowtie.Knot

Methods

showsPrec :: Int -> Knot g a -> ShowS #

show :: Knot g a -> String #

showList :: [Knot g a] -> ShowS #

Eq (g a (Knot g a)) => Eq (Knot g a) Source # 
Instance details

Defined in Bowtie.Knot

Methods

(==) :: Knot g a -> Knot g a -> Bool #

(/=) :: Knot g a -> Knot g a -> Bool #

Ord (g a (Knot g a)) => Ord (Knot g a) Source # 
Instance details

Defined in Bowtie.Knot

Methods

compare :: Knot g a -> Knot g a -> Ordering #

(<) :: Knot g a -> Knot g a -> Bool #

(<=) :: Knot g a -> Knot g a -> Bool #

(>) :: Knot g a -> Knot g a -> Bool #

(>=) :: Knot g a -> Knot g a -> Bool #

max :: Knot g a -> Knot g a -> Knot g a #

min :: Knot g a -> Knot g a -> Knot g a #

Pretty (g a (Knot g a)) => Pretty (Knot g a) Source # 
Instance details

Defined in Bowtie.Knot

Methods

pretty :: Knot g a -> Doc ann #

prettyList :: [Knot g a] -> Doc ann #

type Base1 (Knot g) Source # 
Instance details

Defined in Bowtie.Knot

type Base1 (Knot g) = g

mkKnot :: (Recursive1 f, Base1 f ~ g) => f a -> Knot g a Source #

Pull a recursive structure apart and retie as a Knot.

unMkKnot :: (Corecursive1 f, Base1 f ~ g) => Knot g a -> f a Source #

Go the other way.

transKnot :: Bifunctor g => (forall x y. g x y -> h x y) -> Knot g a -> Knot h a Source #

Transform the base Bifunctor.