Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Non-empty random access list.
This module is designed to imported qualifed.
Synopsis
- newtype NERAList a = NE (NERAList' Leaf a)
- data NERAList' f a
- explicitShow :: Show a => NERAList a -> String
- explicitShowsPrec :: Show a => Int -> NERAList a -> ShowS
- singleton :: a -> NERAList a
- cons :: a -> NERAList a -> NERAList a
- (!) :: NERAList a -> Int -> a
- (!?) :: NERAList a -> Int -> Maybe a
- head :: NERAList a -> a
- last :: NERAList a -> a
- uncons :: NERAList a -> (a, RAList a)
- tail :: NERAList a -> RAList a
- length :: NERAList a -> Int
- null :: NERAList a -> Bool
- toNonEmpty :: NERAList a -> NonEmpty a
- fromNonEmpty :: NonEmpty a -> NERAList a
- foldMap1 :: forall a s. Semigroup s => (a -> s) -> NERAList a -> s
- foldr1Map :: (a -> b -> b) -> (a -> b) -> NERAList a -> b
- ifoldMap :: Monoid m => (Int -> a -> m) -> NERAList a -> m
- ifoldMap1 :: forall a s. Semigroup s => (Int -> a -> s) -> NERAList a -> s
- ifoldr1Map :: forall a b. (Int -> a -> b -> b) -> (Int -> a -> b) -> NERAList a -> b
- adjust :: forall a. Int -> (a -> a) -> NERAList a -> NERAList a
- map :: (a -> b) -> NERAList a -> NERAList b
- imap :: (Int -> a -> b) -> NERAList a -> NERAList b
- itraverse :: forall f a b. Applicative f => (Int -> a -> f b) -> NERAList a -> f (NERAList b)
- itraverse1 :: forall f a b. Apply f => (Int -> a -> f b) -> NERAList a -> f (NERAList b)
Documentation
Non-empty random access list.
Instances
Non-empty random access list, underlying representation.
The structure doesn't need to be hidden, as polymorphic
recursion of Node
s starting from Leaf
keeps the NERAList
values well-formed.
Instances
Showing
Construction
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
toNonEmpty :: NERAList a -> NonEmpty a Source #
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
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}
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')])