Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Useful for describing zippers and functional queues/buffers more naturally and safely.
We call it an RList
because this is really just a vanilla list, but where
the semantics are that the last-added thing (internally cons'ed) is
understood to be at the "end" of the list.
Synopsis
- data Tsil a
- type RList = Tsil
- nil :: Tsil a
- snoc :: Tsil a -> a -> Tsil a
- singleton :: a -> Tsil a
- unsnoc :: Tsil a -> Maybe (Tsil a, a)
- pattern Nil :: Tsil a
- pattern Snoc :: Tsil a -> a -> Tsil a
- null :: Tsil a -> Bool
- init :: Tsil a -> Maybe (Tsil a)
- last :: Tsil a -> Maybe a
- catMaybes :: Tsil (Maybe a) -> Tsil a
- toList :: Tsil a -> [a]
- fromList :: [a] -> Tsil a
- reverseIn :: [a] -> Tsil a
- reverseOut :: Tsil a -> [a]
- toArrayN :: (Contiguous arr, Element arr a) => Int -> Tsil a -> arr a
- toSet :: Ord a => Tsil a -> Set a
Documentation
This datatype defines snoc-lists: lists with O(1) append and O(n) prepend. Underneath the hood, it is just a plain list, but understood as containing its elements in reverse order.
| See? It's "List" in reverse?
I dunno, I just think RList
is an inelegant name, and word-initial t͜s
is one of my favorite phonemes.
Instances
Foldable Tsil Source # | |
Defined in Data.List.Snoc fold :: Monoid m => Tsil m -> m # foldMap :: Monoid m => (a -> m) -> Tsil a -> m # foldMap' :: Monoid m => (a -> m) -> Tsil a -> m # foldr :: (a -> b -> b) -> b -> Tsil a -> b # foldr' :: (a -> b -> b) -> b -> Tsil a -> b # foldl :: (b -> a -> b) -> b -> Tsil a -> b # foldl' :: (b -> a -> b) -> b -> Tsil a -> b # foldr1 :: (a -> a -> a) -> Tsil a -> a # foldl1 :: (a -> a -> a) -> Tsil a -> a # elem :: Eq a => a -> Tsil a -> Bool # maximum :: Ord a => Tsil a -> a # | |
Alternative Tsil Source # | |
Applicative Tsil Source # | |
Functor Tsil Source # | |
Monoid (Tsil a) Source # | |
Semigroup (Tsil a) Source # | |
Generic (Tsil a) Source # | |
Read a => Read (Tsil a) Source # | |
Show a => Show (Tsil a) Source # | |
NFData a => NFData (Tsil a) Source # | |
Defined in Data.List.Snoc | |
Eq a => Eq (Tsil a) Source # | |
type Rep (Tsil a) Source # | |
Defined in Data.List.Snoc |
Introduction and Elimination
snoc :: Tsil a -> a -> Tsil a Source #
O(1)
Append an element.
If you are looking for cons
, you should use a plain list, or a finite sequence/queue type.
Patterns
Queries
Traversal
Conversion
toList :: Tsil a -> [a] Source #
O(n)
Convert to a plain list, maintaining order.
This is here so that you can escape back out to normal cons-list land once you're done building your list.
See reverseOut
for when order doesn't matter.
reverseIn :: [a] -> Tsil a Source #
O(0)
Reverse a plain cons list, rerutning an Tsil
.
See reverseOut
for the inverse, and why you might use these.
reverseOut :: Tsil a -> [a] Source #
toArrayN :: (Contiguous arr, Element arr a) => Int -> Tsil a -> arr a Source #
Write the contents of the Tsil
into an array, assuming you know the length of the array.
This is useful in the common case of buffering an unknown-length stream before allocating contiguous space for the elements.
If you sepcify to small a langth, the initial part of the array will be uninitialized. If you specify to large a length, the initial part of the list will not be written.
If you are unaware of the size of the list, `Arr.fromList . fromList` will do the trick, but will obviously be slower.