recursion-schemes-5.2: Representing common recursion patterns as higher-order functions

Safe HaskellSafe
LanguageHaskell2010

Data.Functor.Base

Description

Base Functors for standard types not already expressed as a fixed point.

Synopsis

Documentation

data ListF a b Source #

Base functor of [].

Constructors

Nil 
Cons a b 
Instances
Bitraversable ListF Source # 
Instance details

Defined in Data.Functor.Base

Methods

bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> ListF a b -> f (ListF c d) #

Bifoldable ListF Source # 
Instance details

Defined in Data.Functor.Base

Methods

bifold :: Monoid m => ListF m m -> m #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> ListF a b -> m #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> ListF a b -> c #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> ListF a b -> c #

Bifunctor ListF Source # 
Instance details

Defined in Data.Functor.Base

Methods

bimap :: (a -> b) -> (c -> d) -> ListF a c -> ListF b d #

first :: (a -> b) -> ListF a c -> ListF b c #

second :: (b -> c) -> ListF a b -> ListF a c #

Eq2 ListF Source # 
Instance details

Defined in Data.Functor.Base

Methods

liftEq2 :: (a -> b -> Bool) -> (c -> d -> Bool) -> ListF a c -> ListF b d -> Bool #

Ord2 ListF Source # 
Instance details

Defined in Data.Functor.Base

Methods

liftCompare2 :: (a -> b -> Ordering) -> (c -> d -> Ordering) -> ListF a c -> ListF b d -> Ordering #

Read2 ListF Source # 
Instance details

Defined in Data.Functor.Base

Methods

liftReadsPrec2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> Int -> ReadS (ListF a b) #

liftReadList2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [ListF a b] #

liftReadPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (ListF a b) #

liftReadListPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec [ListF a b] #

Show2 ListF Source # 
Instance details

Defined in Data.Functor.Base

Methods

liftShowsPrec2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> Int -> ListF a b -> ShowS #

liftShowList2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> [ListF a b] -> ShowS #

Functor (ListF a) Source # 
Instance details

Defined in Data.Functor.Base

Methods

fmap :: (a0 -> b) -> ListF a a0 -> ListF a b #

(<$) :: a0 -> ListF a b -> ListF a a0 #

Foldable (ListF a) Source # 
Instance details

Defined in Data.Functor.Base

Methods

fold :: Monoid m => ListF a m -> m #

foldMap :: Monoid m => (a0 -> m) -> ListF a a0 -> m #

foldr :: (a0 -> b -> b) -> b -> ListF a a0 -> b #

foldr' :: (a0 -> b -> b) -> b -> ListF a a0 -> b #

foldl :: (b -> a0 -> b) -> b -> ListF a a0 -> b #

foldl' :: (b -> a0 -> b) -> b -> ListF a a0 -> b #

foldr1 :: (a0 -> a0 -> a0) -> ListF a a0 -> a0 #

foldl1 :: (a0 -> a0 -> a0) -> ListF a a0 -> a0 #

toList :: ListF a a0 -> [a0] #

null :: ListF a a0 -> Bool #

length :: ListF a a0 -> Int #

elem :: Eq a0 => a0 -> ListF a a0 -> Bool #

maximum :: Ord a0 => ListF a a0 -> a0 #

minimum :: Ord a0 => ListF a a0 -> a0 #

sum :: Num a0 => ListF a a0 -> a0 #

product :: Num a0 => ListF a a0 -> a0 #

Traversable (ListF a) Source # 
Instance details

Defined in Data.Functor.Base

Methods

traverse :: Applicative f => (a0 -> f b) -> ListF a a0 -> f (ListF a b) #

sequenceA :: Applicative f => ListF a (f a0) -> f (ListF a a0) #

mapM :: Monad m => (a0 -> m b) -> ListF a a0 -> m (ListF a b) #

sequence :: Monad m => ListF a (m a0) -> m (ListF a a0) #

Eq a => Eq1 (ListF a) Source # 
Instance details

Defined in Data.Functor.Base

Methods

liftEq :: (a0 -> b -> Bool) -> ListF a a0 -> ListF a b -> Bool #

Ord a => Ord1 (ListF a) Source # 
Instance details

Defined in Data.Functor.Base

Methods

liftCompare :: (a0 -> b -> Ordering) -> ListF a a0 -> ListF a b -> Ordering #

Read a => Read1 (ListF a) Source # 
Instance details

Defined in Data.Functor.Base

Methods

liftReadsPrec :: (Int -> ReadS a0) -> ReadS [a0] -> Int -> ReadS (ListF a a0) #

liftReadList :: (Int -> ReadS a0) -> ReadS [a0] -> ReadS [ListF a a0] #

liftReadPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec (ListF a a0) #

liftReadListPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec [ListF a a0] #

Show a => Show1 (ListF a) Source # 
Instance details

Defined in Data.Functor.Base

Methods

liftShowsPrec :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> Int -> ListF a a0 -> ShowS #

liftShowList :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> [ListF a a0] -> ShowS #

Generic1 (ListF a :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Base

Associated Types

type Rep1 (ListF a) :: k -> Type #

Methods

from1 :: ListF a a0 -> Rep1 (ListF a) a0 #

to1 :: Rep1 (ListF a) a0 -> ListF a a0 #

(Eq a, Eq b) => Eq (ListF a b) Source # 
Instance details

Defined in Data.Functor.Base

Methods

(==) :: ListF a b -> ListF a b -> Bool #

(/=) :: ListF a b -> ListF a b -> Bool #

(Ord a, Ord b) => Ord (ListF a b) Source # 
Instance details

Defined in Data.Functor.Base

Methods

compare :: ListF a b -> ListF a b -> Ordering #

(<) :: ListF a b -> ListF a b -> Bool #

(<=) :: ListF a b -> ListF a b -> Bool #

(>) :: ListF a b -> ListF a b -> Bool #

(>=) :: ListF a b -> ListF a b -> Bool #

max :: ListF a b -> ListF a b -> ListF a b #

min :: ListF a b -> ListF a b -> ListF a b #

(Read a, Read b) => Read (ListF a b) Source # 
Instance details

Defined in Data.Functor.Base

(Show a, Show b) => Show (ListF a b) Source # 
Instance details

Defined in Data.Functor.Base

Methods

showsPrec :: Int -> ListF a b -> ShowS #

show :: ListF a b -> String #

showList :: [ListF a b] -> ShowS #

Generic (ListF a b) Source # 
Instance details

Defined in Data.Functor.Base

Associated Types

type Rep (ListF a b) :: Type -> Type #

Methods

from :: ListF a b -> Rep (ListF a b) x #

to :: Rep (ListF a b) x -> ListF a b #

type Rep1 (ListF a :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Base

type Rep1 (ListF a :: Type -> Type) = D1 (MetaData "ListF" "Data.Functor.Base" "recursion-schemes-5.2-Ex0tGf8Lxlf3PzdGCbpfy4" False) (C1 (MetaCons "Nil" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Cons" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1))
type Rep (ListF a b) Source # 
Instance details

Defined in Data.Functor.Base

type Rep (ListF a b) = D1 (MetaData "ListF" "Data.Functor.Base" "recursion-schemes-5.2-Ex0tGf8Lxlf3PzdGCbpfy4" False) (C1 (MetaCons "Nil" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Cons" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 b)))

data NonEmptyF a b Source #

Base Functor for NonEmpty

Constructors

NonEmptyF 

Fields

Instances
Bitraversable NonEmptyF Source # 
Instance details

Defined in Data.Functor.Base

Methods

bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> NonEmptyF a b -> f (NonEmptyF c d) #

Bifoldable NonEmptyF Source # 
Instance details

Defined in Data.Functor.Base

Methods

bifold :: Monoid m => NonEmptyF m m -> m #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> NonEmptyF a b -> m #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> NonEmptyF a b -> c #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> NonEmptyF a b -> c #

Bifunctor NonEmptyF Source # 
Instance details

Defined in Data.Functor.Base

Methods

bimap :: (a -> b) -> (c -> d) -> NonEmptyF a c -> NonEmptyF b d #

first :: (a -> b) -> NonEmptyF a c -> NonEmptyF b c #

second :: (b -> c) -> NonEmptyF a b -> NonEmptyF a c #

Eq2 NonEmptyF Source # 
Instance details

Defined in Data.Functor.Base

Methods

liftEq2 :: (a -> b -> Bool) -> (c -> d -> Bool) -> NonEmptyF a c -> NonEmptyF b d -> Bool #

Ord2 NonEmptyF Source # 
Instance details

Defined in Data.Functor.Base

Methods

liftCompare2 :: (a -> b -> Ordering) -> (c -> d -> Ordering) -> NonEmptyF a c -> NonEmptyF b d -> Ordering #

Read2 NonEmptyF Source # 
Instance details

Defined in Data.Functor.Base

Methods

liftReadsPrec2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> Int -> ReadS (NonEmptyF a b) #

liftReadList2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [NonEmptyF a b] #

liftReadPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (NonEmptyF a b) #

liftReadListPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec [NonEmptyF a b] #

Show2 NonEmptyF Source # 
Instance details

Defined in Data.Functor.Base

Methods

liftShowsPrec2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> Int -> NonEmptyF a b -> ShowS #

liftShowList2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> [NonEmptyF a b] -> ShowS #

Functor (NonEmptyF a) Source # 
Instance details

Defined in Data.Functor.Base

Methods

fmap :: (a0 -> b) -> NonEmptyF a a0 -> NonEmptyF a b #

(<$) :: a0 -> NonEmptyF a b -> NonEmptyF a a0 #

Foldable (NonEmptyF a) Source # 
Instance details

Defined in Data.Functor.Base

Methods

fold :: Monoid m => NonEmptyF a m -> m #

foldMap :: Monoid m => (a0 -> m) -> NonEmptyF a a0 -> m #

foldr :: (a0 -> b -> b) -> b -> NonEmptyF a a0 -> b #

foldr' :: (a0 -> b -> b) -> b -> NonEmptyF a a0 -> b #

foldl :: (b -> a0 -> b) -> b -> NonEmptyF a a0 -> b #

foldl' :: (b -> a0 -> b) -> b -> NonEmptyF a a0 -> b #

foldr1 :: (a0 -> a0 -> a0) -> NonEmptyF a a0 -> a0 #

foldl1 :: (a0 -> a0 -> a0) -> NonEmptyF a a0 -> a0 #

toList :: NonEmptyF a a0 -> [a0] #

null :: NonEmptyF a a0 -> Bool #

length :: NonEmptyF a a0 -> Int #

elem :: Eq a0 => a0 -> NonEmptyF a a0 -> Bool #

maximum :: Ord a0 => NonEmptyF a a0 -> a0 #

minimum :: Ord a0 => NonEmptyF a a0 -> a0 #

sum :: Num a0 => NonEmptyF a a0 -> a0 #

product :: Num a0 => NonEmptyF a a0 -> a0 #

Traversable (NonEmptyF a) Source # 
Instance details

Defined in Data.Functor.Base

Methods

traverse :: Applicative f => (a0 -> f b) -> NonEmptyF a a0 -> f (NonEmptyF a b) #

sequenceA :: Applicative f => NonEmptyF a (f a0) -> f (NonEmptyF a a0) #

mapM :: Monad m => (a0 -> m b) -> NonEmptyF a a0 -> m (NonEmptyF a b) #

sequence :: Monad m => NonEmptyF a (m a0) -> m (NonEmptyF a a0) #

Eq a => Eq1 (NonEmptyF a) Source # 
Instance details

Defined in Data.Functor.Base

Methods

liftEq :: (a0 -> b -> Bool) -> NonEmptyF a a0 -> NonEmptyF a b -> Bool #

Ord a => Ord1 (NonEmptyF a) Source # 
Instance details

Defined in Data.Functor.Base

Methods

liftCompare :: (a0 -> b -> Ordering) -> NonEmptyF a a0 -> NonEmptyF a b -> Ordering #

Read a => Read1 (NonEmptyF a) Source # 
Instance details

Defined in Data.Functor.Base

Methods

liftReadsPrec :: (Int -> ReadS a0) -> ReadS [a0] -> Int -> ReadS (NonEmptyF a a0) #

liftReadList :: (Int -> ReadS a0) -> ReadS [a0] -> ReadS [NonEmptyF a a0] #

liftReadPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec (NonEmptyF a a0) #

liftReadListPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec [NonEmptyF a a0] #

Show a => Show1 (NonEmptyF a) Source # 
Instance details

Defined in Data.Functor.Base

Methods

liftShowsPrec :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> Int -> NonEmptyF a a0 -> ShowS #

liftShowList :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> [NonEmptyF a a0] -> ShowS #

Generic1 (NonEmptyF a :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Base

Associated Types

type Rep1 (NonEmptyF a) :: k -> Type #

Methods

from1 :: NonEmptyF a a0 -> Rep1 (NonEmptyF a) a0 #

to1 :: Rep1 (NonEmptyF a) a0 -> NonEmptyF a a0 #

(Eq a, Eq b) => Eq (NonEmptyF a b) Source # 
Instance details

Defined in Data.Functor.Base

Methods

(==) :: NonEmptyF a b -> NonEmptyF a b -> Bool #

(/=) :: NonEmptyF a b -> NonEmptyF a b -> Bool #

(Ord a, Ord b) => Ord (NonEmptyF a b) Source # 
Instance details

Defined in Data.Functor.Base

Methods

compare :: NonEmptyF a b -> NonEmptyF a b -> Ordering #

(<) :: NonEmptyF a b -> NonEmptyF a b -> Bool #

(<=) :: NonEmptyF a b -> NonEmptyF a b -> Bool #

(>) :: NonEmptyF a b -> NonEmptyF a b -> Bool #

(>=) :: NonEmptyF a b -> NonEmptyF a b -> Bool #

max :: NonEmptyF a b -> NonEmptyF a b -> NonEmptyF a b #

min :: NonEmptyF a b -> NonEmptyF a b -> NonEmptyF a b #

(Read a, Read b) => Read (NonEmptyF a b) Source # 
Instance details

Defined in Data.Functor.Base

(Show a, Show b) => Show (NonEmptyF a b) Source # 
Instance details

Defined in Data.Functor.Base

Methods

showsPrec :: Int -> NonEmptyF a b -> ShowS #

show :: NonEmptyF a b -> String #

showList :: [NonEmptyF a b] -> ShowS #

Generic (NonEmptyF a b) Source # 
Instance details

Defined in Data.Functor.Base

Associated Types

type Rep (NonEmptyF a b) :: Type -> Type #

Methods

from :: NonEmptyF a b -> Rep (NonEmptyF a b) x #

to :: Rep (NonEmptyF a b) x -> NonEmptyF a b #

type Rep1 (NonEmptyF a :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Base

type Rep1 (NonEmptyF a :: Type -> Type) = D1 (MetaData "NonEmptyF" "Data.Functor.Base" "recursion-schemes-5.2-Ex0tGf8Lxlf3PzdGCbpfy4" False) (C1 (MetaCons "NonEmptyF" PrefixI True) (S1 (MetaSel (Just "head") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "tail") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 Maybe)))
type Rep (NonEmptyF a b) Source # 
Instance details

Defined in Data.Functor.Base

type Rep (NonEmptyF a b) = D1 (MetaData "NonEmptyF" "Data.Functor.Base" "recursion-schemes-5.2-Ex0tGf8Lxlf3PzdGCbpfy4" False) (C1 (MetaCons "NonEmptyF" PrefixI True) (S1 (MetaSel (Just "head") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "tail") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe b))))

data TreeF a b Source #

Base functor for Tree.

Constructors

NodeF a (ForestF a b) 
Instances
Bitraversable TreeF Source # 
Instance details

Defined in Data.Functor.Base

Methods

bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> TreeF a b -> f (TreeF c d) #

Bifoldable TreeF Source # 
Instance details

Defined in Data.Functor.Base

Methods

bifold :: Monoid m => TreeF m m -> m #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> TreeF a b -> m #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> TreeF a b -> c #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> TreeF a b -> c #

Bifunctor TreeF Source # 
Instance details

Defined in Data.Functor.Base

Methods

bimap :: (a -> b) -> (c -> d) -> TreeF a c -> TreeF b d #

first :: (a -> b) -> TreeF a c -> TreeF b c #

second :: (b -> c) -> TreeF a b -> TreeF a c #

Eq2 TreeF Source # 
Instance details

Defined in Data.Functor.Base

Methods

liftEq2 :: (a -> b -> Bool) -> (c -> d -> Bool) -> TreeF a c -> TreeF b d -> Bool #

Ord2 TreeF Source # 
Instance details

Defined in Data.Functor.Base

Methods

liftCompare2 :: (a -> b -> Ordering) -> (c -> d -> Ordering) -> TreeF a c -> TreeF b d -> Ordering #

Read2 TreeF Source # 
Instance details

Defined in Data.Functor.Base

Methods

liftReadsPrec2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> Int -> ReadS (TreeF a b) #

liftReadList2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [TreeF a b] #

liftReadPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (TreeF a b) #

liftReadListPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec [TreeF a b] #

Show2 TreeF Source # 
Instance details

Defined in Data.Functor.Base

Methods

liftShowsPrec2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> Int -> TreeF a b -> ShowS #

liftShowList2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> [TreeF a b] -> ShowS #

Functor (TreeF a) Source # 
Instance details

Defined in Data.Functor.Base

Methods

fmap :: (a0 -> b) -> TreeF a a0 -> TreeF a b #

(<$) :: a0 -> TreeF a b -> TreeF a a0 #

Foldable (TreeF a) Source # 
Instance details

Defined in Data.Functor.Base

Methods

fold :: Monoid m => TreeF a m -> m #

foldMap :: Monoid m => (a0 -> m) -> TreeF a a0 -> m #

foldr :: (a0 -> b -> b) -> b -> TreeF a a0 -> b #

foldr' :: (a0 -> b -> b) -> b -> TreeF a a0 -> b #

foldl :: (b -> a0 -> b) -> b -> TreeF a a0 -> b #

foldl' :: (b -> a0 -> b) -> b -> TreeF a a0 -> b #

foldr1 :: (a0 -> a0 -> a0) -> TreeF a a0 -> a0 #

foldl1 :: (a0 -> a0 -> a0) -> TreeF a a0 -> a0 #

toList :: TreeF a a0 -> [a0] #

null :: TreeF a a0 -> Bool #

length :: TreeF a a0 -> Int #

elem :: Eq a0 => a0 -> TreeF a a0 -> Bool #

maximum :: Ord a0 => TreeF a a0 -> a0 #

minimum :: Ord a0 => TreeF a a0 -> a0 #

sum :: Num a0 => TreeF a a0 -> a0 #

product :: Num a0 => TreeF a a0 -> a0 #

Traversable (TreeF a) Source # 
Instance details

Defined in Data.Functor.Base

Methods

traverse :: Applicative f => (a0 -> f b) -> TreeF a a0 -> f (TreeF a b) #

sequenceA :: Applicative f => TreeF a (f a0) -> f (TreeF a a0) #

mapM :: Monad m => (a0 -> m b) -> TreeF a a0 -> m (TreeF a b) #

sequence :: Monad m => TreeF a (m a0) -> m (TreeF a a0) #

Eq a => Eq1 (TreeF a) Source # 
Instance details

Defined in Data.Functor.Base

Methods

liftEq :: (a0 -> b -> Bool) -> TreeF a a0 -> TreeF a b -> Bool #

Ord a => Ord1 (TreeF a) Source # 
Instance details

Defined in Data.Functor.Base

Methods

liftCompare :: (a0 -> b -> Ordering) -> TreeF a a0 -> TreeF a b -> Ordering #

Read a => Read1 (TreeF a) Source # 
Instance details

Defined in Data.Functor.Base

Methods

liftReadsPrec :: (Int -> ReadS a0) -> ReadS [a0] -> Int -> ReadS (TreeF a a0) #

liftReadList :: (Int -> ReadS a0) -> ReadS [a0] -> ReadS [TreeF a a0] #

liftReadPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec (TreeF a a0) #

liftReadListPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec [TreeF a a0] #

Show a => Show1 (TreeF a) Source # 
Instance details

Defined in Data.Functor.Base

Methods

liftShowsPrec :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> Int -> TreeF a a0 -> ShowS #

liftShowList :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> [TreeF a a0] -> ShowS #

Generic1 (TreeF a :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Base

Associated Types

type Rep1 (TreeF a) :: k -> Type #

Methods

from1 :: TreeF a a0 -> Rep1 (TreeF a) a0 #

to1 :: Rep1 (TreeF a) a0 -> TreeF a a0 #

(Eq a, Eq b) => Eq (TreeF a b) Source # 
Instance details

Defined in Data.Functor.Base

Methods

(==) :: TreeF a b -> TreeF a b -> Bool #

(/=) :: TreeF a b -> TreeF a b -> Bool #

(Ord a, Ord b) => Ord (TreeF a b) Source # 
Instance details

Defined in Data.Functor.Base

Methods

compare :: TreeF a b -> TreeF a b -> Ordering #

(<) :: TreeF a b -> TreeF a b -> Bool #

(<=) :: TreeF a b -> TreeF a b -> Bool #

(>) :: TreeF a b -> TreeF a b -> Bool #

(>=) :: TreeF a b -> TreeF a b -> Bool #

max :: TreeF a b -> TreeF a b -> TreeF a b #

min :: TreeF a b -> TreeF a b -> TreeF a b #

(Read a, Read b) => Read (TreeF a b) Source # 
Instance details

Defined in Data.Functor.Base

(Show a, Show b) => Show (TreeF a b) Source # 
Instance details

Defined in Data.Functor.Base

Methods

showsPrec :: Int -> TreeF a b -> ShowS #

show :: TreeF a b -> String #

showList :: [TreeF a b] -> ShowS #

Generic (TreeF a b) Source # 
Instance details

Defined in Data.Functor.Base

Associated Types

type Rep (TreeF a b) :: Type -> Type #

Methods

from :: TreeF a b -> Rep (TreeF a b) x #

to :: Rep (TreeF a b) x -> TreeF a b #

type Rep1 (TreeF a :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Base

type Rep1 (TreeF a :: Type -> Type) = D1 (MetaData "TreeF" "Data.Functor.Base" "recursion-schemes-5.2-Ex0tGf8Lxlf3PzdGCbpfy4" False) (C1 (MetaCons "NodeF" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 [])))
type Rep (TreeF a b) Source # 
Instance details

Defined in Data.Functor.Base

type Rep (TreeF a b) = D1 (MetaData "TreeF" "Data.Functor.Base" "recursion-schemes-5.2-Ex0tGf8Lxlf3PzdGCbpfy4" False) (C1 (MetaCons "NodeF" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (ForestF a b))))

type ForestF a b = [b] Source #