forest-0.1.1.1: Tree and Forest types

Safe HaskellTrustworthy
LanguageHaskell98

Data.Tree.Forest

Contents

Synopsis

Documentation

data Tree f s a Source #

Constructors

Leaf !a 
Node !s (Forest f s a) 

Instances

Eq1 f => Eq2 (Tree f) Source # 

Methods

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

Ord1 f => Ord2 (Tree f) Source # 

Methods

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

Read1 f => Read2 (Tree f) Source # 

Methods

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

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

Show1 f => Show2 (Tree f) Source # 

Methods

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

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

Functor f => Bifunctor (Tree f) Source # 

Methods

bimap :: (a -> b) -> (c -> d) -> Tree f a c -> Tree f b d #

first :: (a -> b) -> Tree f a c -> Tree f b c #

second :: (b -> c) -> Tree f a b -> Tree f a c #

Traversable f => Bitraversable (Tree f) Source # 

Methods

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

Foldable f => Bifoldable (Tree f) Source # 

Methods

bifold :: Monoid m => Tree f m m -> m #

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

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> Tree f a b -> c #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> Tree f a b -> c #

Functor f => Monad (Tree f s) Source # 

Methods

(>>=) :: Tree f s a -> (a -> Tree f s b) -> Tree f s b #

(>>) :: Tree f s a -> Tree f s b -> Tree f s b #

return :: a -> Tree f s a #

fail :: String -> Tree f s a #

Functor f => Functor (Tree f s) Source # 

Methods

fmap :: (a -> b) -> Tree f s a -> Tree f s b #

(<$) :: a -> Tree f s b -> Tree f s a #

Functor f => Applicative (Tree f s) Source # 

Methods

pure :: a -> Tree f s a #

(<*>) :: Tree f s (a -> b) -> Tree f s a -> Tree f s b #

(*>) :: Tree f s a -> Tree f s b -> Tree f s b #

(<*) :: Tree f s a -> Tree f s b -> Tree f s a #

Foldable f => Foldable (Tree f s) Source # 

Methods

fold :: Monoid m => Tree f s m -> m #

foldMap :: Monoid m => (a -> m) -> Tree f s a -> m #

foldr :: (a -> b -> b) -> b -> Tree f s a -> b #

foldr' :: (a -> b -> b) -> b -> Tree f s a -> b #

foldl :: (b -> a -> b) -> b -> Tree f s a -> b #

foldl' :: (b -> a -> b) -> b -> Tree f s a -> b #

foldr1 :: (a -> a -> a) -> Tree f s a -> a #

foldl1 :: (a -> a -> a) -> Tree f s a -> a #

toList :: Tree f s a -> [a] #

null :: Tree f s a -> Bool #

length :: Tree f s a -> Int #

elem :: Eq a => a -> Tree f s a -> Bool #

maximum :: Ord a => Tree f s a -> a #

minimum :: Ord a => Tree f s a -> a #

sum :: Num a => Tree f s a -> a #

product :: Num a => Tree f s a -> a #

Traversable f => Traversable (Tree f s) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Tree f s a -> f (Tree f s b) #

sequenceA :: Applicative f => Tree f s (f a) -> f (Tree f s a) #

mapM :: Monad m => (a -> m b) -> Tree f s a -> m (Tree f s b) #

sequence :: Monad m => Tree f s (m a) -> m (Tree f s a) #

Generic1 (Tree f s) Source # 

Associated Types

type Rep1 (Tree f s :: * -> *) :: * -> * #

Methods

from1 :: Tree f s a -> Rep1 (Tree f s) a #

to1 :: Rep1 (Tree f s) a -> Tree f s a #

(Eq1 f, Eq s) => Eq1 (Tree f s) Source # 

Methods

liftEq :: (a -> b -> Bool) -> Tree f s a -> Tree f s b -> Bool #

(Ord1 f, Ord s) => Ord1 (Tree f s) Source # 

Methods

liftCompare :: (a -> b -> Ordering) -> Tree f s a -> Tree f s b -> Ordering #

(Read1 f, Read s) => Read1 (Tree f s) Source # 

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Tree f s a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Tree f s a] #

(Show1 f, Show s) => Show1 (Tree f s) Source # 

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Tree f s a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Tree f s a] -> ShowS #

Functor f => Apply (Tree f s) Source # 

Methods

(<.>) :: Tree f s (a -> b) -> Tree f s a -> Tree f s b #

(.>) :: Tree f s a -> Tree f s b -> Tree f s b #

(<.) :: Tree f s a -> Tree f s b -> Tree f s a #

Functor f => Bind (Tree f s) Source # 

Methods

(>>-) :: Tree f s a -> (a -> Tree f s b) -> Tree f s b #

join :: Tree f s (Tree f s a) -> Tree f s a #

(Eq a, Eq s, Eq (Forest f s a)) => Eq (Tree f s a) Source # 

Methods

(==) :: Tree f s a -> Tree f s a -> Bool #

(/=) :: Tree f s a -> Tree f s a -> Bool #

(Ord a, Ord s, Ord (Forest f s a), Ord (f (Tree f s a))) => Ord (Tree f s a) Source # 

Methods

compare :: Tree f s a -> Tree f s a -> Ordering #

(<) :: Tree f s a -> Tree f s a -> Bool #

(<=) :: Tree f s a -> Tree f s a -> Bool #

(>) :: Tree f s a -> Tree f s a -> Bool #

(>=) :: Tree f s a -> Tree f s a -> Bool #

max :: Tree f s a -> Tree f s a -> Tree f s a #

min :: Tree f s a -> Tree f s a -> Tree f s a #

(Read a, Read s, Read (Forest f s a)) => Read (Tree f s a) Source # 

Methods

readsPrec :: Int -> ReadS (Tree f s a) #

readList :: ReadS [Tree f s a] #

readPrec :: ReadPrec (Tree f s a) #

readListPrec :: ReadPrec [Tree f s a] #

(Show a, Show s, Show (Forest f s a)) => Show (Tree f s a) Source # 

Methods

showsPrec :: Int -> Tree f s a -> ShowS #

show :: Tree f s a -> String #

showList :: [Tree f s a] -> ShowS #

Generic (Tree f s a) Source # 

Associated Types

type Rep (Tree f s a) :: * -> * #

Methods

from :: Tree f s a -> Rep (Tree f s a) x #

to :: Rep (Tree f s a) x -> Tree f s a #

(Hashable s, Hashable a, Hashable (f (Tree f s a))) => Hashable (Tree f s a) Source # 

Methods

hashWithSalt :: Int -> Tree f s a -> Int #

hash :: Tree f s a -> Int #

(ToJSON s, ToJSON a, ToJSON (f (Tree f s a))) => ToJSON (Tree f s a) Source # 

Methods

toJSON :: Tree f s a -> Value #

toEncoding :: Tree f s a -> Encoding #

toJSONList :: [Tree f s a] -> Value #

toEncodingList :: [Tree f s a] -> Encoding #

ToJSON (Tree f s a) => ToJSONKey (Tree f s a) Source # 
(FromJSON s, FromJSON a, FromJSON (f (Tree f s a))) => FromJSON (Tree f s a) Source # 

Methods

parseJSON :: Value -> Parser (Tree f s a) #

parseJSONList :: Value -> Parser [Tree f s a] #

FromJSON (Tree f s a) => FromJSONKey (Tree f s a) Source # 
(NFData s, NFData a, NFData (f (Tree f s a))) => NFData (Tree f s a) Source # 

Methods

rnf :: Tree f s a -> () #

type Rep1 (Tree f s) Source # 
type Rep (Tree f s a) Source # 

newtype Forest f s a Source #

Constructors

Forest (f (Tree f s a)) 

Instances

Eq1 f => Eq2 (Forest f) Source # 

Methods

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

Ord1 f => Ord2 (Forest f) Source # 

Methods

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

Read1 f => Read2 (Forest f) Source # 

Methods

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

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

Show1 f => Show2 (Forest f) Source # 

Methods

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

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

Functor f => Bifunctor (Forest f) Source # 

Methods

bimap :: (a -> b) -> (c -> d) -> Forest f a c -> Forest f b d #

first :: (a -> b) -> Forest f a c -> Forest f b c #

second :: (b -> c) -> Forest f a b -> Forest f a c #

Traversable f => Bitraversable (Forest f) Source # 

Methods

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

Foldable f => Bifoldable (Forest f) Source # 

Methods

bifold :: Monoid m => Forest f m m -> m #

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

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> Forest f a b -> c #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> Forest f a b -> c #

(Applicative f, Monad f, Traversable f) => Monad (Forest f s) Source # 

Methods

(>>=) :: Forest f s a -> (a -> Forest f s b) -> Forest f s b #

(>>) :: Forest f s a -> Forest f s b -> Forest f s b #

return :: a -> Forest f s a #

fail :: String -> Forest f s a #

Functor f => Functor (Forest f s) Source # 

Methods

fmap :: (a -> b) -> Forest f s a -> Forest f s b #

(<$) :: a -> Forest f s b -> Forest f s a #

(MonadFail f, Traversable f) => MonadFail (Forest f s) Source # 

Methods

fail :: String -> Forest f s a #

Applicative f => Applicative (Forest f s) Source # 

Methods

pure :: a -> Forest f s a #

(<*>) :: Forest f s (a -> b) -> Forest f s a -> Forest f s b #

(*>) :: Forest f s a -> Forest f s b -> Forest f s b #

(<*) :: Forest f s a -> Forest f s b -> Forest f s a #

Foldable f => Foldable (Forest f s) Source # 

Methods

fold :: Monoid m => Forest f s m -> m #

foldMap :: Monoid m => (a -> m) -> Forest f s a -> m #

foldr :: (a -> b -> b) -> b -> Forest f s a -> b #

foldr' :: (a -> b -> b) -> b -> Forest f s a -> b #

foldl :: (b -> a -> b) -> b -> Forest f s a -> b #

foldl' :: (b -> a -> b) -> b -> Forest f s a -> b #

foldr1 :: (a -> a -> a) -> Forest f s a -> a #

foldl1 :: (a -> a -> a) -> Forest f s a -> a #

toList :: Forest f s a -> [a] #

null :: Forest f s a -> Bool #

length :: Forest f s a -> Int #

elem :: Eq a => a -> Forest f s a -> Bool #

maximum :: Ord a => Forest f s a -> a #

minimum :: Ord a => Forest f s a -> a #

sum :: Num a => Forest f s a -> a #

product :: Num a => Forest f s a -> a #

Traversable f => Traversable (Forest f s) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Forest f s a -> f (Forest f s b) #

sequenceA :: Applicative f => Forest f s (f a) -> f (Forest f s a) #

mapM :: Monad m => (a -> m b) -> Forest f s a -> m (Forest f s b) #

sequence :: Monad m => Forest f s (m a) -> m (Forest f s a) #

Functor f => Generic1 (Forest f s) Source # 

Associated Types

type Rep1 (Forest f s :: * -> *) :: * -> * #

Methods

from1 :: Forest f s a -> Rep1 (Forest f s) a #

to1 :: Rep1 (Forest f s) a -> Forest f s a #

Alternative f => Alternative (Forest f s) Source # 

Methods

empty :: Forest f s a #

(<|>) :: Forest f s a -> Forest f s a -> Forest f s a #

some :: Forest f s a -> Forest f s [a] #

many :: Forest f s a -> Forest f s [a] #

(Alternative f, Monad f, Traversable f) => MonadPlus (Forest f s) Source # 

Methods

mzero :: Forest f s a #

mplus :: Forest f s a -> Forest f s a -> Forest f s a #

(Eq1 f, Eq s) => Eq1 (Forest f s) Source # 

Methods

liftEq :: (a -> b -> Bool) -> Forest f s a -> Forest f s b -> Bool #

(Ord1 f, Ord s) => Ord1 (Forest f s) Source # 

Methods

liftCompare :: (a -> b -> Ordering) -> Forest f s a -> Forest f s b -> Ordering #

(Read1 f, Read s) => Read1 (Forest f s) Source # 

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Forest f s a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Forest f s a] #

(Show1 f, Show s) => Show1 (Forest f s) Source # 

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Forest f s a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Forest f s a] -> ShowS #

Plus f => Plus (Forest f s) Source # 

Methods

zero :: Forest f s a #

Alt f => Alt (Forest f s) Source # 

Methods

(<!>) :: Forest f s a -> Forest f s a -> Forest f s a #

some :: Applicative (Forest f s) => Forest f s a -> Forest f s [a] #

many :: Applicative (Forest f s) => Forest f s a -> Forest f s [a] #

Apply f => Apply (Forest f s) Source # 

Methods

(<.>) :: Forest f s (a -> b) -> Forest f s a -> Forest f s b #

(.>) :: Forest f s a -> Forest f s b -> Forest f s b #

(<.) :: Forest f s a -> Forest f s b -> Forest f s a #

(Applicative f, Bind f, Traversable f) => Bind (Forest f s) Source # 

Methods

(>>-) :: Forest f s a -> (a -> Forest f s b) -> Forest f s b #

join :: Forest f s (Forest f s a) -> Forest f s a #

IsList (f (Tree f s a)) => IsList (Forest f s a) Source # 

Associated Types

type Item (Forest f s a) :: * #

Methods

fromList :: [Item (Forest f s a)] -> Forest f s a #

fromListN :: Int -> [Item (Forest f s a)] -> Forest f s a #

toList :: Forest f s a -> [Item (Forest f s a)] #

Eq (f (Tree f s a)) => Eq (Forest f s a) Source # 

Methods

(==) :: Forest f s a -> Forest f s a -> Bool #

(/=) :: Forest f s a -> Forest f s a -> Bool #

Ord (f (Tree f s a)) => Ord (Forest f s a) Source # 

Methods

compare :: Forest f s a -> Forest f s a -> Ordering #

(<) :: Forest f s a -> Forest f s a -> Bool #

(<=) :: Forest f s a -> Forest f s a -> Bool #

(>) :: Forest f s a -> Forest f s a -> Bool #

(>=) :: Forest f s a -> Forest f s a -> Bool #

max :: Forest f s a -> Forest f s a -> Forest f s a #

min :: Forest f s a -> Forest f s a -> Forest f s a #

Read (f (Tree f s a)) => Read (Forest f s a) Source # 

Methods

readsPrec :: Int -> ReadS (Forest f s a) #

readList :: ReadS [Forest f s a] #

readPrec :: ReadPrec (Forest f s a) #

readListPrec :: ReadPrec [Forest f s a] #

Show (f (Tree f s a)) => Show (Forest f s a) Source # 

Methods

showsPrec :: Int -> Forest f s a -> ShowS #

show :: Forest f s a -> String #

showList :: [Forest f s a] -> ShowS #

Generic (Forest f s a) Source # 

Associated Types

type Rep (Forest f s a) :: * -> * #

Methods

from :: Forest f s a -> Rep (Forest f s a) x #

to :: Rep (Forest f s a) x -> Forest f s a #

Alt f => Semigroup (Forest f s a) Source # 

Methods

(<>) :: Forest f s a -> Forest f s a -> Forest f s a #

sconcat :: NonEmpty (Forest f s a) -> Forest f s a #

stimes :: Integral b => b -> Forest f s a -> Forest f s a #

Alternative f => Monoid (Forest f s a) Source # 

Methods

mempty :: Forest f s a #

mappend :: Forest f s a -> Forest f s a -> Forest f s a #

mconcat :: [Forest f s a] -> Forest f s a #

(Hashable a, Hashable s, Hashable (f (Tree f s a))) => Hashable (Forest f s a) Source # 

Methods

hashWithSalt :: Int -> Forest f s a -> Int #

hash :: Forest f s a -> Int #

(ToJSON s, ToJSON a, ToJSON (f (Tree f s a))) => ToJSON (Forest f s a) Source # 

Methods

toJSON :: Forest f s a -> Value #

toEncoding :: Forest f s a -> Encoding #

toJSONList :: [Forest f s a] -> Value #

toEncodingList :: [Forest f s a] -> Encoding #

ToJSON (Forest f s a) => ToJSONKey (Forest f s a) Source # 
(FromJSON s, FromJSON a, FromJSON (f (Tree f s a))) => FromJSON (Forest f s a) Source # 

Methods

parseJSON :: Value -> Parser (Forest f s a) #

parseJSONList :: Value -> Parser [Forest f s a] #

FromJSON (Forest f s a) => FromJSONKey (Forest f s a) Source # 
(NFData a, NFData s, NFData (f (Tree f s a))) => NFData (Forest f s a) Source # 

Methods

rnf :: Forest f s a -> () #

type Rep1 (Forest f s) Source # 
type Rep1 (Forest f s) = D1 (MetaData "Forest" "Data.Tree.Forest" "forest-0.1.1.1-7zW1BZGc8cw8P8fQRcVOqT" True) (C1 (MetaCons "Forest" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) ((:.:) f (Rec1 (Tree f s)))))
type Rep (Forest f s a) Source # 
type Rep (Forest f s a) = D1 (MetaData "Forest" "Data.Tree.Forest" "forest-0.1.1.1-7zW1BZGc8cw8P8fQRcVOqT" True) (C1 (MetaCons "Forest" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (f (Tree f s a)))))
type Item (Forest f s a) Source # 
type Item (Forest f s a) = Item (f (Tree f s a))

Optics

_Leaf :: (Choice p, Applicative f) => p a (f a) -> p (Tree g s a) (f (Tree g s a)) Source #

_Node :: (Choice p, Applicative f) => p (s, Forest g s a) (f (s, Forest g s a)) -> p (Tree g s a) (f (Tree g s a)) Source #

_Forest :: (Profunctor p, Functor f) => p (g (Tree g s a)) (f (g (Tree g s a))) -> p (Forest g s a) (f (Forest g s a)) Source #

Higher order traversals

Trees

hmap :: Functor f => (forall x. f x -> g x) -> Tree f s a -> Tree g s a Source #

hfoldr :: Foldable f => (forall x. f x -> b -> b) -> b -> Tree f s a -> b Source #

htraverse :: (Traversable f, Applicative h, Monad h) => (forall x. f x -> h (g x)) -> Tree f s a -> h (Tree g s a) Source #

Forests

hmap' :: Functor f => (forall x. f x -> g x) -> Forest f s a -> Forest g s a Source #

hfoldr' :: Foldable f => (forall x. f x -> b -> b) -> b -> Forest f s a -> b Source #

htraverse' :: (Traversable f, Applicative h, Monad h) => (forall x. f x -> h (g x)) -> Forest f s a -> h (Forest g s a) Source #