ral-0.2: Random access lists
Safe HaskellSafe
LanguageHaskell2010

Data.RAList.NonEmpty

Description

Non-empty random access list.

This module is designed to imported qualifed.

Synopsis

Documentation

newtype NERAList a Source #

Non-empty random access list.

Constructors

NE (NERAList' Leaf a) 

Instances

Instances details
Functor NERAList Source # 
Instance details

Defined in Data.RAList.NonEmpty.Internal

Methods

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

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

Foldable NERAList Source #
>>> I.length $ fromNonEmpty $ 'x' :| ['a' .. 'z']
27
Instance details

Defined in Data.RAList.NonEmpty.Internal

Methods

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

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

foldMap' :: Monoid m => (a -> m) -> NERAList a -> m #

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

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

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

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

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

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

toList :: NERAList a -> [a] #

null :: NERAList a -> Bool #

length :: NERAList a -> Int #

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

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

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

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

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

Traversable NERAList Source # 
Instance details

Defined in Data.RAList.NonEmpty.Internal

Methods

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

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

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

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

Arbitrary1 NERAList Source # 
Instance details

Defined in Data.RAList.NonEmpty.Internal

Methods

liftArbitrary :: Gen a -> Gen (NERAList a) #

liftShrink :: (a -> [a]) -> NERAList a -> [NERAList a] #

Traversable1 NERAList Source # 
Instance details

Defined in Data.RAList.NonEmpty.Internal

Methods

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

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

Foldable1 NERAList Source # 
Instance details

Defined in Data.RAList.NonEmpty.Internal

Methods

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

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

toNonEmpty :: NERAList a -> NonEmpty a #

FunctorWithIndex Int NERAList Source #

Since: 0.2

Instance details

Defined in Data.RAList.NonEmpty.Internal

Methods

imap :: (Int -> a -> b) -> NERAList a -> NERAList b #

FoldableWithIndex Int NERAList Source #

Since: 0.2

Instance details

Defined in Data.RAList.NonEmpty.Internal

Methods

ifoldMap :: Monoid m => (Int -> a -> m) -> NERAList a -> m #

ifoldMap' :: Monoid m => (Int -> a -> m) -> NERAList a -> m #

ifoldr :: (Int -> a -> b -> b) -> b -> NERAList a -> b #

ifoldl :: (Int -> b -> a -> b) -> b -> NERAList a -> b #

ifoldr' :: (Int -> a -> b -> b) -> b -> NERAList a -> b #

ifoldl' :: (Int -> b -> a -> b) -> b -> NERAList a -> b #

TraversableWithIndex Int NERAList Source #

Since: 0.2

Instance details

Defined in Data.RAList.NonEmpty.Internal

Methods

itraverse :: Applicative f => (Int -> a -> f b) -> NERAList a -> f (NERAList b) #

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

Defined in Data.RAList.NonEmpty.Internal

Methods

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

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

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

Defined in Data.RAList.NonEmpty.Internal

Methods

compare :: NERAList a -> NERAList a -> Ordering #

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

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

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

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

max :: NERAList a -> NERAList a -> NERAList a #

min :: NERAList a -> NERAList a -> NERAList a #

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

Defined in Data.RAList.NonEmpty.Internal

Methods

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

show :: NERAList a -> String #

showList :: [NERAList a] -> ShowS #

Semigroup (NERAList a) Source #
>>> fromNonEmpty ('a' :| "bc") <> fromNonEmpty ('x' :| "yz")
fromNonEmpty ('a' :| "bcxyz")
Instance details

Defined in Data.RAList.NonEmpty.Internal

Methods

(<>) :: NERAList a -> NERAList a -> NERAList a #

sconcat :: NonEmpty (NERAList a) -> NERAList a #

stimes :: Integral b => b -> NERAList a -> NERAList a #

Function a => Function (NERAList a) Source # 
Instance details

Defined in Data.RAList.NonEmpty.Internal

Methods

function :: (NERAList a -> b) -> NERAList a :-> b #

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

Defined in Data.RAList.NonEmpty.Internal

Methods

arbitrary :: Gen (NERAList a) #

shrink :: NERAList a -> [NERAList a] #

CoArbitrary a => CoArbitrary (NERAList a) Source # 
Instance details

Defined in Data.RAList.NonEmpty.Internal

Methods

coarbitrary :: NERAList a -> Gen b -> Gen b #

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

Defined in Data.RAList.NonEmpty.Internal

Methods

rnf :: NERAList a -> () #

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

Defined in Data.RAList.NonEmpty.Internal

Methods

hashWithSalt :: Int -> NERAList a -> Int #

hash :: NERAList a -> Int #

data NERAList' f a Source #

Non-empty random access list, underlying representation.

The structure doesn't need to be hidden, as polymorphic recursion of Nodes starting from Leaf keeps the NERAList values well-formed.

Constructors

Last (f a) 
Cons0 (NERAList' (Node f) a) 
Cons1 (f a) (NERAList' (Node f) a) 

Instances

Instances details
Functor f => Functor (NERAList' f) Source # 
Instance details

Defined in Data.RAList.NonEmpty.Internal

Methods

fmap :: (a -> b) -> NERAList' f a -> NERAList' f b #

(<$) :: a -> NERAList' f b -> NERAList' f a #

Foldable f => Foldable (NERAList' f) Source # 
Instance details

Defined in Data.RAList.NonEmpty.Internal

Methods

fold :: Monoid m => NERAList' f m -> m #

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

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

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

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

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

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

foldr1 :: (a -> a -> a) -> NERAList' f a -> a #

foldl1 :: (a -> a -> a) -> NERAList' f a -> a #

toList :: NERAList' f a -> [a] #

null :: NERAList' f a -> Bool #

length :: NERAList' f a -> Int #

elem :: Eq a => a -> NERAList' f a -> Bool #

maximum :: Ord a => NERAList' f a -> a #

minimum :: Ord a => NERAList' f a -> a #

sum :: Num a => NERAList' f a -> a #

product :: Num a => NERAList' f a -> a #

Traversable f => Traversable (NERAList' f) Source # 
Instance details

Defined in Data.RAList.NonEmpty.Internal

Methods

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

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

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

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

Traversable1 t => Traversable1 (NERAList' t) Source # 
Instance details

Defined in Data.RAList.NonEmpty.Internal

Methods

traverse1 :: Apply f => (a -> f b) -> NERAList' t a -> f (NERAList' t b) #

sequence1 :: Apply f => NERAList' t (f b) -> f (NERAList' t b) #

Foldable1 t => Foldable1 (NERAList' t) Source # 
Instance details

Defined in Data.RAList.NonEmpty.Internal

Methods

fold1 :: Semigroup m => NERAList' t m -> m #

foldMap1 :: Semigroup m => (a -> m) -> NERAList' t a -> m #

toNonEmpty :: NERAList' t a -> NonEmpty a #

Eq (f a) => Eq (NERAList' f a) Source # 
Instance details

Defined in Data.RAList.NonEmpty.Internal

Methods

(==) :: NERAList' f a -> NERAList' f a -> Bool #

(/=) :: NERAList' f a -> NERAList' f a -> Bool #

(Ord a, Foldable f, Eq (f a)) => Ord (NERAList' f a) Source # 
Instance details

Defined in Data.RAList.NonEmpty.Internal

Methods

compare :: NERAList' f a -> NERAList' f a -> Ordering #

(<) :: NERAList' f a -> NERAList' f a -> Bool #

(<=) :: NERAList' f a -> NERAList' f a -> Bool #

(>) :: NERAList' f a -> NERAList' f a -> Bool #

(>=) :: NERAList' f a -> NERAList' f a -> Bool #

max :: NERAList' f a -> NERAList' f a -> NERAList' f a #

min :: NERAList' f a -> NERAList' f a -> NERAList' f a #

Show (f a) => Show (NERAList' f a) Source # 
Instance details

Defined in Data.RAList.NonEmpty.Internal

Methods

showsPrec :: Int -> NERAList' f a -> ShowS #

show :: NERAList' f a -> String #

showList :: [NERAList' f a] -> ShowS #

NFData (t a) => NFData (NERAList' t a) Source # 
Instance details

Defined in Data.RAList.NonEmpty.Internal

Methods

rnf :: NERAList' t a -> () #

Hashable (t a) => Hashable (NERAList' t a) Source # 
Instance details

Defined in Data.RAList.NonEmpty.Internal

Methods

hashWithSalt :: Int -> NERAList' t a -> Int #

hash :: NERAList' t a -> Int #

Showing

Construction

singleton :: a -> NERAList a Source #

Single element NERAList.

cons :: a -> NERAList a -> NERAList a Source #

cons for non-empty rals.

Indexing

(!) :: NERAList a -> Int -> a Source #

List index.

>>> fromNonEmpty ('a' :| ['b'..'f']) ! 0
'a'
>>> fromNonEmpty ('a' :| ['b'..'f']) ! 5
'f'
>>> fromNonEmpty ('a' :| ['b'..'f']) ! 6
*** Exception: array index out of range: NERAList
...

(!?) :: NERAList a -> Int -> Maybe a Source #

safe list index.

>>> fromNonEmpty ('a' :| ['b'..'f']) !? 0
Just 'a'
>>> fromNonEmpty ('a' :| ['b'..'f']) !? 5
Just 'f'
>>> fromNonEmpty ('a' :| ['b'..'f']) !? 6
Nothing

head :: NERAList a -> a Source #

First value, head of the list.

>>> head $ fromNonEmpty $ 'a' :| ['b'..'f']
'a'

last :: NERAList a -> a Source #

Last value of the list

>>> last $ fromNonEmpty $  'a' :| ['b'..'f']
'f'

uncons :: NERAList a -> (a, RAList a) Source #

>>> uncons $ fromNonEmpty $ 'a' :| "bcdef"
('a',fromList "bcdef")

tail :: NERAList a -> RAList a Source #

Tail of non-empty list can be empty.

>>> tail $ fromNonEmpty $ 'a' :| "bcdef"
fromList "bcdef"

Conversions

fromNonEmpty :: NonEmpty a -> NERAList a Source #

>>> fromNonEmpty ('a' :| ['b'..'f'])
fromNonEmpty ('a' :| "bcdef")
>>> explicitShow (fromNonEmpty ('a' :| ['b'..'f']))
"NE (Cons0 (Cons1 (Nd (Lf 'a') (Lf 'b')) (Last (Nd (Nd (Lf 'c') (Lf 'd')) (Nd (Lf 'e') (Lf 'f'))))))"

Folding

foldMap1 :: forall a s. Semigroup s => (a -> s) -> NERAList a -> s Source #

foldr1Map :: (a -> b -> b) -> (a -> b) -> NERAList a -> b Source #

ifoldMap :: Monoid m => (Int -> a -> m) -> NERAList a -> m Source #

ifoldMap1 :: forall a s. Semigroup s => (Int -> a -> s) -> NERAList a -> s Source #

>>> import Data.Semigroup (Min (..))
>>> ifoldMap1 (\_ x -> Min x) $ fromNonEmpty $ 5 :| [3,1,2,4]
Min {getMin = 1}
>>> ifoldMap1 (\i x -> Min (i + x)) $ fromNonEmpty $ 5 :| [3,1,2,4]
Min {getMin = 3}

ifoldr1Map :: forall a b. (Int -> a -> b -> b) -> (Int -> a -> b) -> NERAList a -> b Source #

Mapping

adjust :: forall a. Int -> (a -> a) -> NERAList a -> NERAList a Source #

Adjust a value in the list.

>>> adjust 3 toUpper $ fromNonEmpty $ 'a' :| "bcdef"
fromNonEmpty ('a' :| "bcDef")

If index is out of bounds, the list is returned unmodified.

>>> adjust 10 toUpper $ fromNonEmpty $ 'a' :| "bcdef"
fromNonEmpty ('a' :| "bcdef")
>>> adjust (-1) toUpper $ fromNonEmpty $ 'a' :| "bcdef"
fromNonEmpty ('a' :| "bcdef")

map :: (a -> b) -> NERAList a -> NERAList b Source #

>>> map toUpper (fromNonEmpty ('a' :| ['b'..'f']))
fromNonEmpty ('A' :| "BCDEF")

imap :: (Int -> a -> b) -> NERAList a -> NERAList b Source #

>>> imap (,) (fromNonEmpty ('a' :| ['b'..'f']))
fromNonEmpty ((0,'a') :| [(1,'b'),(2,'c'),(3,'d'),(4,'e'),(5,'f')])

itraverse :: forall f a b. Applicative f => (Int -> a -> f b) -> NERAList a -> f (NERAList b) Source #

itraverse1 :: forall f a b. Apply f => (Int -> a -> f b) -> NERAList a -> f (NERAList b) Source #