rose-trees-0.0.4.4: A collection of rose tree structures.

Safe HaskellNone
LanguageHaskell2010

Data.Tree.Knuth.Forest

Contents

Synopsis

Forest

data KnuthForest a Source #

Constructors

Fork 
Nil 

Instances

Monad KnuthForest Source #

Breadth-first

Functor KnuthForest Source # 

Methods

fmap :: (a -> b) -> KnuthForest a -> KnuthForest b #

(<$) :: a -> KnuthForest b -> KnuthForest a #

Applicative KnuthForest Source #

Zippy

Foldable KnuthForest Source #

Breadth-first

Methods

fold :: Monoid m => KnuthForest m -> m #

foldMap :: Monoid m => (a -> m) -> KnuthForest a -> m #

foldr :: (a -> b -> b) -> b -> KnuthForest a -> b #

foldr' :: (a -> b -> b) -> b -> KnuthForest a -> b #

foldl :: (b -> a -> b) -> b -> KnuthForest a -> b #

foldl' :: (b -> a -> b) -> b -> KnuthForest a -> b #

foldr1 :: (a -> a -> a) -> KnuthForest a -> a #

foldl1 :: (a -> a -> a) -> KnuthForest a -> a #

toList :: KnuthForest a -> [a] #

null :: KnuthForest a -> Bool #

length :: KnuthForest a -> Int #

elem :: Eq a => a -> KnuthForest a -> Bool #

maximum :: Ord a => KnuthForest a -> a #

minimum :: Ord a => KnuthForest a -> a #

sum :: Num a => KnuthForest a -> a #

product :: Num a => KnuthForest a -> a #

Traversable KnuthForest Source # 

Methods

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

sequenceA :: Applicative f => KnuthForest (f a) -> f (KnuthForest a) #

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

sequence :: Monad m => KnuthForest (m a) -> m (KnuthForest a) #

Alternative KnuthForest Source # 
MonadPlus KnuthForest Source # 
Filterable KnuthForest Source # 

Methods

mapMaybe :: (a -> Maybe b) -> KnuthForest a -> KnuthForest b #

catMaybes :: KnuthForest (Maybe a) -> KnuthForest a #

filter :: (a -> Bool) -> KnuthForest a -> KnuthForest a #

RoseTree KnuthForest Source # 
HasSingleton a (KnuthForest a) Source # 

Methods

singleton :: a -> KnuthForest a #

Eq a => HasDelete a (KnuthForest a) Source # 

Methods

delete :: a -> KnuthForest a -> KnuthForest a #

Eq a => Eq (KnuthForest a) Source # 
Data a => Data (KnuthForest a) Source # 

Methods

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

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (KnuthForest a) #

toConstr :: KnuthForest a -> Constr #

dataTypeOf :: KnuthForest a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (KnuthForest a)) #

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

gmapT :: (forall b. Data b => b -> b) -> KnuthForest a -> KnuthForest a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> KnuthForest a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> KnuthForest a -> r #

gmapQ :: (forall d. Data d => d -> u) -> KnuthForest a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> KnuthForest a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> KnuthForest a -> m (KnuthForest a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> KnuthForest a -> m (KnuthForest a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> KnuthForest a -> m (KnuthForest a) #

Ord a => Ord (KnuthForest a) Source #

Siblings before children

Show a => Show (KnuthForest a) Source # 
Generic (KnuthForest a) Source # 

Associated Types

type Rep (KnuthForest a) :: * -> * #

Methods

from :: KnuthForest a -> Rep (KnuthForest a) x #

to :: Rep (KnuthForest a) x -> KnuthForest a #

Semigroup (KnuthForest a) Source # 
Monoid (KnuthForest a) Source # 
Arbitrary a => Arbitrary (KnuthForest a) Source # 
NFData a => NFData (KnuthForest a) Source # 

Methods

rnf :: KnuthForest a -> () #

HasUnion (KnuthForest a) Source # 

Methods

union :: KnuthForest a -> KnuthForest a -> KnuthForest a #

Eq a => HasIntersection (KnuthForest a) Source # 
Eq a => HasDifference (KnuthForest a) Source # 
HasEmpty (KnuthForest a) Source # 

Methods

empty :: KnuthForest a #

HasSize (KnuthForest a) Source # 

Methods

size :: KnuthForest a -> Int #

type Rep (KnuthForest a) Source # 
type Rep (KnuthForest a) = D1 (MetaData "KnuthForest" "Data.Tree.Knuth.Forest" "rose-trees-0.0.4.4-J5VMBnbNq6E6urmcHMQdNe" False) ((:+:) (C1 (MetaCons "Fork" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "kNode") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)) ((:*:) (S1 (MetaSel (Just Symbol "kChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (KnuthForest a))) (S1 (MetaSel (Just Symbol "kSiblings") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (KnuthForest a)))))) (C1 (MetaCons "Nil" PrefixI False) U1))
type Tail (KnuthForest a) Source # 
type Head (KnuthForest a) Source # 
type Head (KnuthForest a) = a

Query

elem :: Eq a => a -> KnuthForest a -> Bool Source #

elemPath :: Eq a => [a] -> KnuthForest a -> Bool Source #

isChildOf :: Eq a => a -> KnuthForest a -> Bool Source #

depth of one

Construction

delete :: Eq a => a -> KnuthForest a -> KnuthForest a Source #

Combination

difference :: Eq a => KnuthForest a -> KnuthForest a -> KnuthForest a Source #

Removes the possible subtree on the right, from the left.