ralist-0.4.0.0: Random access list with a list compatible interface.
Safe HaskellTrustworthy
LanguageHaskell2010

Data.RAList.Co

Synopsis

Documentation

data RAList a where Source #

This type (RAList a) indexes back to front, i.e. for nonempty lists l : head of l == (l !! (genericLength l - 1 )) and last l == l !! 0 @. RAList also has a logarithmic complexity drop operation, and different semantics for zip and related operations

for complete pattern matching, you can use any pair of:

The Reversed order pattern synonyms are provided to enable certain codes to match pen/paper notation for ordered variable environments

Bundled Patterns

pattern Cons :: forall a. a -> RAList a -> RAList a infixr 5

Cons pattern, à la : for list, prefix

pattern Nil :: forall a. RAList a

the '[]' analogue

pattern RCons :: forall a. RAList a -> a -> RAList a infixl 5

just Cons but flipped arguments

pattern (:|) :: forall a. a -> RAList a -> RAList a infixr 5

infix Cons, aka : , but for RAlist

pattern (:.) :: forall a. RAList a -> a -> RAList a infixl 5

infix RCons, aka flipped :

Instances

Instances details
Monad RAList Source # 
Instance details

Defined in Data.RAList.Co

Methods

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

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

return :: a -> RAList a #

Functor RAList Source # 
Instance details

Defined in Data.RAList.Co

Methods

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

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

Applicative RAList Source # 
Instance details

Defined in Data.RAList.Co

Methods

pure :: a -> RAList a #

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

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

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

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

Foldable RAList Source # 
Instance details

Defined in Data.RAList.Co

Methods

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

foldMap :: Monoid m => (a -> m) -> RAList a -> 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.Co

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) #

MonadZip RAList Source # 
Instance details

Defined in Data.RAList.Co

Methods

mzip :: RAList a -> RAList b -> RAList (a, b) #

mzipWith :: (a -> b -> c) -> RAList a -> RAList b -> RAList c #

munzip :: RAList (a, b) -> (RAList a, RAList b) #

NFData1 RAList Source # 
Instance details

Defined in Data.RAList.Co

Methods

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

FunctorWithIndex Word64 RAList Source # 
Instance details

Defined in Data.RAList.Co

Methods

imap :: (Word64 -> a -> b) -> RAList a -> RAList b #

FoldableWithIndex Word64 RAList Source # 
Instance details

Defined in Data.RAList.Co

Methods

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

ifoldMap' :: Monoid m => (Word64 -> a -> m) -> RAList a -> m #

ifoldr :: (Word64 -> a -> b -> b) -> b -> RAList a -> b #

ifoldl :: (Word64 -> b -> a -> b) -> b -> RAList a -> b #

ifoldr' :: (Word64 -> a -> b -> b) -> b -> RAList a -> b #

ifoldl' :: (Word64 -> b -> a -> b) -> b -> RAList a -> b #

TraversableWithIndex Word64 RAList Source # 
Instance details

Defined in Data.RAList.Co

Methods

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

IsList (RAList a) Source # 
Instance details

Defined in Data.RAList.Co

Associated Types

type Item (RAList a) #

Methods

fromList :: [Item (RAList a)] -> RAList a #

fromListN :: Int -> [Item (RAList a)] -> RAList a #

toList :: RAList a -> [Item (RAList a)] #

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

Defined in Data.RAList.Co

Methods

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

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

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

Defined in Data.RAList.Co

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.Co

Methods

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

show :: RAList a -> String #

showList :: [RAList a] -> ShowS #

Generic (RAList a) Source # 
Instance details

Defined in Data.RAList.Co

Associated Types

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

Methods

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

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

Semigroup (RAList a) Source # 
Instance details

Defined in Data.RAList.Co

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.Co

Methods

mempty :: RAList a #

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

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

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

Defined in Data.RAList.Co

Methods

rnf :: RAList a -> () #

Generic1 RAList Source # 
Instance details

Defined in Data.RAList.Co

Associated Types

type Rep1 RAList :: k -> Type #

Methods

from1 :: forall (a :: k). RAList a -> Rep1 RAList a #

to1 :: forall (a :: k). Rep1 RAList a -> RAList a #

type Rep (RAList a) Source # 
Instance details

Defined in Data.RAList.Co

type Rep (RAList a) = Rep (RAList a)
type Item (RAList a) Source # 
Instance details

Defined in Data.RAList.Co

type Item (RAList a) = Item (RAList a)
type Rep1 RAList Source # 
Instance details

Defined in Data.RAList.Co

lookups

lookup :: forall a. RAList a -> Word64 -> Maybe a Source #

lookupM :: forall a m. MonadFail m => Word64 -> RAList a -> m a Source #

lookupWithDefault :: forall t. t -> Word64 -> RAList t -> t Source #

(!!) :: RAList a -> Word64 -> a infixl 9 Source #

lookupCC :: RAList a -> Word64 -> (a -> r) -> (String -> r) -> r Source #

function form of constructing and destructing

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

implementation underlying smart constructor used by pattern synonyms

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

how matching is implemented

zipping

zip :: RAList a -> RAList b -> RAList (a, b) Source #

list zip,

zipWith :: (a -> b -> c) -> RAList a -> RAList b -> RAList c Source #

unzip :: RAList (a, b) -> (RAList a, RAList b) Source #

Extracting sublists

take :: Word64 -> RAList a -> RAList a Source #

take i l, keeps the first i elements, O(i) complexity

drop :: Word64 -> RAList a -> RAList a Source #

drop i l drops the first i elments, O(log i) complexity,

replicate :: Word64 -> a -> RAList a Source #

replicate n a makes a RAList with n values of a

splitAt :: Word64 -> RAList a -> (RAList a, RAList a) Source #

performs both drop and take

from traverse and foldable and ilk

foldl' :: Foldable t => (b -> a -> b) -> b -> t a -> b #

Left-associative fold of a structure but with strict application of the operator.

This ensures that each step of the fold is forced to weak head normal form before being applied, avoiding the collection of thunks that would otherwise occur. This is often what you want to strictly reduce a finite list to a single, monolithic result (e.g. length).

For a general Foldable structure this should be semantically identical to,

foldl' f z = foldl' f z . toList

Since: base-4.6.0.0

foldr :: Foldable t => (a -> b -> b) -> b -> t a -> b #

Right-associative fold of a structure.

In the case of lists, foldr, when applied to a binary operator, a starting value (typically the right-identity of the operator), and a list, reduces the list using the binary operator, from right to left:

foldr f z [x1, x2, ..., xn] == x1 `f` (x2 `f` ... (xn `f` z)...)

Note that, since the head of the resulting expression is produced by an application of the operator to the first element of the list, foldr can produce a terminating expression from an infinite list.

For a general Foldable structure this should be semantically identical to,

foldr f z = foldr f z . toList

traverse :: (Traversable t, Applicative f) => (a -> f b) -> t a -> f (t b) #

Map each element of a structure to an action, evaluate these actions from left to right, and collect the results. For a version that ignores the results see traverse_.

mapM :: (Traversable t, Monad m) => (a -> m b) -> t a -> m (t b) #

Map each element of a structure to a monadic action, evaluate these actions from left to right, and collect the results. For a version that ignores the results see mapM_.

mapM_ :: (Foldable t, Monad m) => (a -> m b) -> t a -> m () #

Map each element of a structure to a monadic action, evaluate these actions from left to right, and ignore the results. For a version that doesn't ignore the results see mapM.

As of base 4.8.0.0, mapM_ is just traverse_, specialized to Monad.

unfoldr :: (b -> Maybe (a, b)) -> b -> RAList a Source #

indexed folds etc

ifoldMap :: (FoldableWithIndex i f, Monoid m) => (i -> a -> m) -> f a -> m #

Fold a container by mapping value to an arbitrary Monoid with access to the index i.

When you don't need access to the index then foldMap is more flexible in what it accepts.

foldMapifoldMap . const

imap :: FunctorWithIndex i f => (i -> a -> b) -> f a -> f b #

Map with access to the index.

itraverse :: (TraversableWithIndex i t, Applicative f) => (i -> a -> f b) -> t a -> f (t b) #

Traverse an indexed container.

itraverseitraverseOf itraversed

ifoldl' :: FoldableWithIndex i f => (i -> b -> a -> b) -> b -> f a -> b #

Fold over the elements of a structure with an index, associating to the left, but strictly.

When you don't need access to the index then foldlOf' is more flexible in what it accepts.

foldlOf' l ≡ ifoldlOf' l . const

ifoldr :: FoldableWithIndex i f => (i -> a -> b -> b) -> b -> f a -> b #

Right-associative fold of an indexed container with access to the index i.

When you don't need access to the index then foldr is more flexible in what it accepts.

foldrifoldr . const

imapM :: (TraversableWithIndex i t, Monad m) => (i -> a -> m b) -> t a -> m (t b) #

Map each element of a structure to a monadic action, evaluate these actions from left to right, and collect the results, with access the index.

When you don't need access to the index mapM is more liberal in what it can accept.

mapMimapM . const

filter and friends

filter :: forall a. (a -> Bool) -> RAList a -> RAList a Source #

partition :: (a -> Bool) -> RAList a -> (RAList a, RAList a) Source #

mapMaybe :: forall a b. (a -> Maybe b) -> RAList a -> RAList b Source #

wither :: forall a b f. Applicative f => (a -> f (Maybe b)) -> RAList a -> f (RAList b) Source #

foldable cousins

elem :: (Foldable t, Eq a) => a -> t a -> Bool infix 4 #

Does the element occur in the structure?

Since: base-4.8.0.0

length :: Foldable t => t a -> Int #

Returns the size/length of a finite structure as an Int. The default implementation is optimized for structures that are similar to cons-lists, because there is no general way to do better.

Since: base-4.8.0.0

The "generic" operations

The prefix `generic' indicates an overloaded function that is a generalized version of a Prelude function.

genericLength :: forall a w. Integral w => RAList a -> w Source #

genericTake :: forall a n. Integral n => n -> RAList a -> RAList a Source #

genericIndex :: Integral n => RAList a -> n -> a Source #

Update

update :: Word64 -> a -> RAList a -> RAList a Source #

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

Append

(++) :: RAList a -> RAList a -> RAList a infixr 5 Source #

list conversion

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

friendly list to RAList conversion

toList :: Foldable t => t a -> [a] #

List of elements of a structure, from left to right.

Since: base-4.8.0.0