ral-0.1: Random access lists

Safe HaskellSafe
LanguageHaskell2010

Data.RAList.Tree

Synopsis

Documentation

newtype Leaf a Source #

A Leaf is isomorphic to Identity, but we reimplement it here to have domain specific type. The short constructor name is a bonus.

Constructors

Lf a 
Instances
Functor Leaf Source # 
Instance details

Defined in Data.RAList.Tree.Internal

Methods

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

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

Foldable Leaf Source # 
Instance details

Defined in Data.RAList.Tree.Internal

Methods

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

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

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

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

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

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

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

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

toList :: Leaf a -> [a] #

null :: Leaf a -> Bool #

length :: Leaf a -> Int #

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

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

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

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

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

Traversable Leaf Source # 
Instance details

Defined in Data.RAList.Tree.Internal

Methods

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

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

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

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

Distributive Leaf Source # 
Instance details

Defined in Data.RAList.Tree.Internal

Methods

distribute :: Functor f => f (Leaf a) -> Leaf (f a) #

collect :: Functor f => (a -> Leaf b) -> f a -> Leaf (f b) #

distributeM :: Monad m => m (Leaf a) -> Leaf (m a) #

collectM :: Monad m => (a -> Leaf b) -> m a -> Leaf (m b) #

Representable Leaf Source # 
Instance details

Defined in Data.RAList.Tree.Internal

Associated Types

type Rep Leaf :: Type #

Methods

tabulate :: (Rep Leaf -> a) -> Leaf a #

index :: Leaf a -> Rep Leaf -> a #

Traversable1 Leaf Source # 
Instance details

Defined in Data.RAList.Tree.Internal

Methods

traverse1 :: Apply f => (a -> f b) -> Leaf a -> f (Leaf b) #

sequence1 :: Apply f => Leaf (f b) -> f (Leaf b) #

Foldable1 Leaf Source # 
Instance details

Defined in Data.RAList.Tree.Internal

Methods

fold1 :: Semigroup m => Leaf m -> m #

foldMap1 :: Semigroup m => (a -> m) -> Leaf a -> m #

toNonEmpty :: Leaf a -> NonEmpty a #

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

Defined in Data.RAList.Tree.Internal

Methods

(==) :: Leaf a -> Leaf a -> Bool #

(/=) :: Leaf a -> Leaf a -> Bool #

Ord a => Ord (Leaf a) Source # 
Instance details

Defined in Data.RAList.Tree.Internal

Methods

compare :: Leaf a -> Leaf a -> Ordering #

(<) :: Leaf a -> Leaf a -> Bool #

(<=) :: Leaf a -> Leaf a -> Bool #

(>) :: Leaf a -> Leaf a -> Bool #

(>=) :: Leaf a -> Leaf a -> Bool #

max :: Leaf a -> Leaf a -> Leaf a #

min :: Leaf a -> Leaf a -> Leaf a #

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

Defined in Data.RAList.Tree.Internal

Methods

showsPrec :: Int -> Leaf a -> ShowS #

show :: Leaf a -> String #

showList :: [Leaf a] -> ShowS #

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

Defined in Data.RAList.Tree.Internal

Methods

rnf :: Leaf a -> () #

Hashable a => Hashable (Leaf a) Source # 
Instance details

Defined in Data.RAList.Tree.Internal

Methods

hashWithSalt :: Int -> Leaf a -> Int #

hash :: Leaf a -> Int #

type Rep Leaf Source # 
Instance details

Defined in Data.RAList.Tree.Internal

type Rep Leaf = ()

data Node f a Source #

Node is a product of two f. This way we can form a perfect binary tree.

Constructors

Nd (f a) (f a) 
Instances
Functor f => Functor (Node f) Source # 
Instance details

Defined in Data.RAList.Tree.Internal

Methods

fmap :: (a -> b) -> Node f a -> Node f b #

(<$) :: a -> Node f b -> Node f a #

Foldable f => Foldable (Node f) Source # 
Instance details

Defined in Data.RAList.Tree.Internal

Methods

fold :: Monoid m => Node f m -> m #

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

foldr :: (a -> b -> b) -> b -> Node f a -> b #

foldr' :: (a -> b -> b) -> b -> Node f a -> b #

foldl :: (b -> a -> b) -> b -> Node f a -> b #

foldl' :: (b -> a -> b) -> b -> Node f a -> b #

foldr1 :: (a -> a -> a) -> Node f a -> a #

foldl1 :: (a -> a -> a) -> Node f a -> a #

toList :: Node f a -> [a] #

null :: Node f a -> Bool #

length :: Node f a -> Int #

elem :: Eq a => a -> Node f a -> Bool #

maximum :: Ord a => Node f a -> a #

minimum :: Ord a => Node f a -> a #

sum :: Num a => Node f a -> a #

product :: Num a => Node f a -> a #

Traversable f => Traversable (Node f) Source # 
Instance details

Defined in Data.RAList.Tree.Internal

Methods

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

sequenceA :: Applicative f0 => Node f (f0 a) -> f0 (Node f a) #

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

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

Distributive f => Distributive (Node f) Source # 
Instance details

Defined in Data.RAList.Tree.Internal

Methods

distribute :: Functor f0 => f0 (Node f a) -> Node f (f0 a) #

collect :: Functor f0 => (a -> Node f b) -> f0 a -> Node f (f0 b) #

distributeM :: Monad m => m (Node f a) -> Node f (m a) #

collectM :: Monad m => (a -> Node f b) -> m a -> Node f (m b) #

Representable f => Representable (Node f) Source # 
Instance details

Defined in Data.RAList.Tree.Internal

Associated Types

type Rep (Node f) :: Type #

Methods

tabulate :: (Rep (Node f) -> a) -> Node f a #

index :: Node f a -> Rep (Node f) -> a #

Traversable1 f => Traversable1 (Node f) Source # 
Instance details

Defined in Data.RAList.Tree.Internal

Methods

traverse1 :: Apply f0 => (a -> f0 b) -> Node f a -> f0 (Node f b) #

sequence1 :: Apply f0 => Node f (f0 b) -> f0 (Node f b) #

Foldable1 f => Foldable1 (Node f) Source # 
Instance details

Defined in Data.RAList.Tree.Internal

Methods

fold1 :: Semigroup m => Node f m -> m #

foldMap1 :: Semigroup m => (a -> m) -> Node f a -> m #

toNonEmpty :: Node f a -> NonEmpty a #

Eq (f a) => Eq (Node f a) Source # 
Instance details

Defined in Data.RAList.Tree.Internal

Methods

(==) :: Node f a -> Node f a -> Bool #

(/=) :: Node f a -> Node f a -> Bool #

Ord (f a) => Ord (Node f a) Source # 
Instance details

Defined in Data.RAList.Tree.Internal

Methods

compare :: Node f a -> Node f a -> Ordering #

(<) :: Node f a -> Node f a -> Bool #

(<=) :: Node f a -> Node f a -> Bool #

(>) :: Node f a -> Node f a -> Bool #

(>=) :: Node f a -> Node f a -> Bool #

max :: Node f a -> Node f a -> Node f a #

min :: Node f a -> Node f a -> Node f a #

Show (f a) => Show (Node f a) Source # 
Instance details

Defined in Data.RAList.Tree.Internal

Methods

showsPrec :: Int -> Node f a -> ShowS #

show :: Node f a -> String #

showList :: [Node f a] -> ShowS #

NFData (f a) => NFData (Node f a) Source # 
Instance details

Defined in Data.RAList.Tree.Internal

Methods

rnf :: Node f a -> () #

Hashable (f a) => Hashable (Node f a) Source # 
Instance details

Defined in Data.RAList.Tree.Internal

Methods

hashWithSalt :: Int -> Node f a -> Int #

hash :: Node f a -> Int #

type Rep (Node f) Source # 
Instance details

Defined in Data.RAList.Tree.Internal

type Rep (Node f) = Dir (Rep f)

data Dir a Source #

Direction in Node.

Constructors

L a 
R a 
Instances
Functor Dir Source # 
Instance details

Defined in Data.RAList.Tree.Internal

Methods

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

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

Foldable Dir Source # 
Instance details

Defined in Data.RAList.Tree.Internal

Methods

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

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

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

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

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

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

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

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

toList :: Dir a -> [a] #

null :: Dir a -> Bool #

length :: Dir a -> Int #

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

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

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

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

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

Traversable Dir Source # 
Instance details

Defined in Data.RAList.Tree.Internal

Methods

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

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

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

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

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

Defined in Data.RAList.Tree.Internal

Methods

(==) :: Dir a -> Dir a -> Bool #

(/=) :: Dir a -> Dir a -> Bool #

Ord a => Ord (Dir a) Source # 
Instance details

Defined in Data.RAList.Tree.Internal

Methods

compare :: Dir a -> Dir a -> Ordering #

(<) :: Dir a -> Dir a -> Bool #

(<=) :: Dir a -> Dir a -> Bool #

(>) :: Dir a -> Dir a -> Bool #

(>=) :: Dir a -> Dir a -> Bool #

max :: Dir a -> Dir a -> Dir a #

min :: Dir a -> Dir a -> Dir a #

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

Defined in Data.RAList.Tree.Internal

Methods

showsPrec :: Int -> Dir a -> ShowS #

show :: Dir a -> String #

showList :: [Dir a] -> ShowS #