ral-0.1: Random access lists

Safe HaskellSafe
LanguageHaskell2010

Data.RAList

Contents

Description

Random access list.

This module is designed to imported qualifed.

Synopsis

Documentation

data RAList a Source #

Random access list.

Constructors

Empty 
NonEmpty (NERAList a) 
Instances
Functor RAList Source # 
Instance details

Defined in Data.RAList.Internal

Methods

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

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

Foldable RAList Source #
>>> I.length $ fromList $ ['a' .. 'z']
26
Instance details

Defined in Data.RAList.Internal

Methods

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

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

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

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

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

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

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

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

toList :: RAList a -> [a] #

null :: RAList a -> Bool #

length :: RAList a -> Int #

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

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

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

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

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

Traversable RAList Source # 
Instance details

Defined in Data.RAList.Internal

Methods

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

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

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

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

Arbitrary1 RAList Source # 
Instance details

Defined in Data.RAList.Internal

Methods

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

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

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

Defined in Data.RAList.Internal

Methods

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

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

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

Defined in Data.RAList.Internal

Methods

compare :: RAList a -> RAList a -> Ordering #

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

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

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

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

max :: RAList a -> RAList a -> RAList a #

min :: RAList a -> RAList a -> RAList a #

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

Defined in Data.RAList.Internal

Methods

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

show :: RAList a -> String #

showList :: [RAList a] -> ShowS #

Semigroup (RAList a) Source #
>>> fromList "abc" <> fromList "xyz"
fromList "abcxyz"
Instance details

Defined in Data.RAList.Internal

Methods

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

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

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

Monoid (RAList a) Source # 
Instance details

Defined in Data.RAList.Internal

Methods

mempty :: RAList a #

mappend :: RAList a -> RAList a -> RAList a #

mconcat :: [RAList a] -> RAList a #

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

Defined in Data.RAList.Internal

Methods

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

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

Defined in Data.RAList.Internal

Methods

arbitrary :: Gen (RAList a) #

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

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

Defined in Data.RAList.Internal

Methods

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

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

Defined in Data.RAList.Internal

Methods

rnf :: RAList a -> () #

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

Defined in Data.RAList.Internal

Methods

hashWithSalt :: Int -> RAList a -> Int #

hash :: RAList a -> Int #

Showing

Construction

empty :: RAList a Source #

Empty RAList.

>>> empty :: RAList Int
fromList []

singleton :: a -> RAList a Source #

Single element RAList.

cons :: a -> RAList a -> RAList a Source #

cons for non-empty rals.

Indexing

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

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

safe list index.

>>> fromList ['a'..'f'] !? 0
Just 'a'
>>> fromList ['a'..'f'] !? 5
Just 'f'
>>> fromList ['a'..'f'] !? 6
Nothing

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

>>> uncons $ fromList []
Nothing
>>> uncons $ fromList "abcdef"
Just ('a',fromList "bcdef")

Conversions

toList :: RAList a -> [a] Source #

fromList :: [a] -> RAList a Source #

>>> fromList ['a' .. 'f']
fromList "abcdef"
>>> explicitShow $ fromList ['a' .. 'f']
"NonEmpty (NE (Cons0 (Cons1 (Nd (Lf 'a') (Lf 'b')) (Last (Nd (Nd (Lf 'c') (Lf 'd')) (Nd (Lf 'e') (Lf 'f')))))))"

Folding

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

Mapping

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

Adjust a value in the list.

>>> adjust 3 toUpper $ fromList "bcdef"
fromList "bcdEf"

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

>>> adjust 10 toUpper $ fromList "bcdef"
fromList "bcdef"
>>> adjust (-1) toUpper $ fromList "bcdef"
fromList "bcdef"

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

>>> map toUpper (fromList ['a'..'f'])
fromList "ABCDEF"

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

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

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