rose-trees-0.0.4.5: Various trie implementations in Haskell

Safe HaskellNone
LanguageHaskell2010

Data.Tree.Knuth.Forest

Contents

Synopsis

Forest

data KnuthForest a Source #

Constructors

Fork 
Nil 
Instances
Monad KnuthForest Source #

Breadth-first

Instance details

Defined in Data.Tree.Knuth.Forest

Functor KnuthForest Source # 
Instance details

Defined in Data.Tree.Knuth.Forest

Methods

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

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

Applicative KnuthForest Source #

Zippy

Instance details

Defined in Data.Tree.Knuth.Forest

Methods

pure :: a -> KnuthForest a #

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

liftA2 :: (a -> b -> c) -> KnuthForest a -> KnuthForest b -> KnuthForest c #

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

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

Foldable KnuthForest Source #

Breadth-first

Instance details

Defined in Data.Tree.Knuth.Forest

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 # 
Instance details

Defined in Data.Tree.Knuth.Forest

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 # 
Instance details

Defined in Data.Tree.Knuth.Forest

MonadPlus KnuthForest Source # 
Instance details

Defined in Data.Tree.Knuth.Forest

Filterable KnuthForest Source # 
Instance details

Defined in Data.Tree.Knuth.Forest

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 # 
Instance details

Defined in Data.Tree.Rose

HasSingleton a (KnuthForest a) Source # 
Instance details

Defined in Data.Tree.Knuth.Forest

Methods

singleton :: a -> KnuthForest a #

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

Defined in Data.Tree.Knuth.Forest

Methods

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

Eq a => Eq (KnuthForest a) Source # 
Instance details

Defined in Data.Tree.Knuth.Forest

Data a => Data (KnuthForest a) Source # 
Instance details

Defined in Data.Tree.Knuth.Forest

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

Instance details

Defined in Data.Tree.Knuth.Forest

Show a => Show (KnuthForest a) Source # 
Instance details

Defined in Data.Tree.Knuth.Forest

Generic (KnuthForest a) Source # 
Instance details

Defined in Data.Tree.Knuth.Forest

Associated Types

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

Methods

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

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

Semigroup (KnuthForest a) Source # 
Instance details

Defined in Data.Tree.Knuth.Forest

Monoid (KnuthForest a) Source # 
Instance details

Defined in Data.Tree.Knuth.Forest

Arbitrary a => Arbitrary (KnuthForest a) Source # 
Instance details

Defined in Data.Tree.Knuth.Forest

NFData a => NFData (KnuthForest a) Source # 
Instance details

Defined in Data.Tree.Knuth.Forest

Methods

rnf :: KnuthForest a -> () #

HasUnion (KnuthForest a) Source # 
Instance details

Defined in Data.Tree.Knuth.Forest

Methods

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

Eq a => HasIntersection (KnuthForest a) Source # 
Instance details

Defined in Data.Tree.Knuth.Forest

Eq a => HasDifference (KnuthForest a) Source # 
Instance details

Defined in Data.Tree.Knuth.Forest

HasEmpty (KnuthForest a) Source # 
Instance details

Defined in Data.Tree.Knuth.Forest

Methods

empty :: KnuthForest a #

HasSize (KnuthForest a) Source # 
Instance details

Defined in Data.Tree.Knuth.Forest

Methods

size :: KnuthForest a -> Int #

type Rep (KnuthForest a) Source # 
Instance details

Defined in Data.Tree.Knuth.Forest

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

Defined in Data.Tree.Rose

type Head (KnuthForest a) Source # 
Instance details

Defined in Data.Tree.Rose

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.