Safe Haskell | Trustworthy |
---|---|
Language | Haskell2010 |
Synopsis
- data RAList a where
- lookup :: forall a. Word64 -> RAList a -> Maybe a
- lookupM :: forall a m. MonadFail m => Word64 -> RAList a -> m a
- lookupWithDefault :: forall t. t -> Word64 -> RAList t -> t
- (!!) :: RAList a -> Word64 -> a
- lookupCC :: RAList a -> Word64 -> (a -> r) -> (String -> r) -> r
- cons :: a -> RAList a -> RAList a
- uncons :: RAList a -> Maybe (a, RAList a)
- zip :: RAList a -> RAList b -> RAList (a, b)
- zipWith :: (a -> b -> c) -> RAList a -> RAList b -> RAList c
- unzip :: RAList (a, b) -> (RAList a, RAList b)
- take :: Word64 -> RAList a -> RAList a
- drop :: Word64 -> RAList a -> RAList a
- replicate :: Word64 -> a -> RAList a
- splitAt :: Word64 -> RAList a -> (RAList a, RAList a)
- foldl' :: Foldable t => (b -> a -> b) -> b -> t a -> b
- foldr :: Foldable t => (a -> b -> b) -> b -> t a -> b
- traverse :: (Traversable t, Applicative f) => (a -> f b) -> t a -> f (t b)
- mapM :: (Traversable t, Monad m) => (a -> m b) -> t a -> m (t b)
- mapM_ :: (Foldable t, Monad m) => (a -> m b) -> t a -> m ()
- unfoldr :: (b -> Maybe (a, b)) -> b -> RAList a
- ifoldMap :: (FoldableWithIndex i f, Monoid m) => (i -> a -> m) -> f a -> m
- imap :: FunctorWithIndex i f => (i -> a -> b) -> f a -> f b
- itraverse :: (TraversableWithIndex i t, Applicative f) => (i -> a -> f b) -> t a -> f (t b)
- ifoldl' :: FoldableWithIndex i f => (i -> b -> a -> b) -> b -> f a -> b
- ifoldr :: FoldableWithIndex i f => (i -> a -> b -> b) -> b -> f a -> b
- imapM :: (TraversableWithIndex i t, Monad m) => (i -> a -> m b) -> t a -> m (t b)
- filter :: forall a. (a -> Bool) -> RAList a -> RAList a
- partition :: (a -> Bool) -> RAList a -> (RAList a, RAList a)
- mapMaybe :: forall a b. (a -> Maybe b) -> RAList a -> RAList b
- catMaybes :: RAList (Maybe a) -> RAList a
- wither :: forall a b f. Applicative f => (a -> f (Maybe b)) -> RAList a -> f (RAList b)
- elem :: (Foldable t, Eq a) => a -> t a -> Bool
- length :: Foldable t => t a -> Int
- wLength :: RAList a -> Word64
- genericLength :: forall a w. Integral w => RAList a -> w
- genericTake :: forall a n. Integral n => n -> RAList a -> RAList a
- genericDrop :: Integral n => n -> RAList a -> RAList a
- genericSplitAt :: Integral n => n -> RAList a -> (RAList a, RAList a)
- genericIndex :: Integral n => RAList a -> n -> a
- genericReplicate :: Integral n => n -> a -> RAList a
- update :: Word64 -> a -> RAList a -> RAList a
- adjust :: forall a. (a -> a) -> Word64 -> RAList a -> RAList a
- (++) :: RAList a -> RAList a -> RAList a
- fromList :: [a] -> RAList a
- toList :: Foldable t => t a -> [a]
Documentation
This type (
) indexes back to front, i.e. for nonempty lists RAList
al
: head of l == (l
l - 1 ))!!
(genericLength
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
pattern Cons :: forall a. a -> RAList a -> RAList a infixr 5 | Cons pattern, à la |
pattern Nil :: forall a. RAList a | the '[]' analogue |
pattern RCons :: forall a. RAList a -> a -> RAList a infixl 5 | just |
pattern (:|) :: forall a. a -> RAList a -> RAList a infixr 5 | infix |
pattern (:.) :: forall a. RAList a -> a -> RAList a infixl 5 | infix |
Instances
lookups
lookupWithDefault :: forall t. t -> Word64 -> RAList t -> t Source #
function form of constructing and destructing
cons :: a -> RAList a -> RAList a infixr 5 Source #
implementation underlying smart constructor used by pattern synonyms
zipping
Extracting sublists
take :: Word64 -> RAList a -> RAList a Source #
, keeps the first take
i li
elements, O(i)
complexity
drop :: Word64 -> RAList a -> RAList a Source #
drops the first drop
i li
elments, O(log i)
complexity,
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_
.
indexed folds etc
itraverse :: (TraversableWithIndex i t, Applicative f) => (i -> a -> f b) -> t a -> f (t b) #
filter and friends
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 #
genericIndex :: Integral n => RAList a -> n -> a Source #
genericReplicate :: Integral n => n -> a -> RAList a Source #