reverse-list-0.2.0
Safe HaskellNone
LanguageHaskell2010

Data.List.Snoc

Description

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.

WARNING: the Foldable instance provides a toList; this simply unwraps the RList rather than reversing it. If you need to convert from revered semantics to forward semantics, use this module's toList.

Synopsis

Documentation

data RList a Source #

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.

Instances

Instances details
Functor RList Source # 
Instance details

Defined in Data.List.Snoc

Methods

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

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

Applicative RList Source # 
Instance details

Defined in Data.List.Snoc

Methods

pure :: a -> RList a #

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

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

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

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

Alternative RList Source # 
Instance details

Defined in Data.List.Snoc

Methods

empty :: RList a #

(<|>) :: RList a -> RList a -> RList a #

some :: RList a -> RList [a] #

many :: RList a -> RList [a] #

Read a => Read (RList a) Source # 
Instance details

Defined in Data.List.Snoc

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

Defined in Data.List.Snoc

Methods

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

show :: RList a -> String #

showList :: [RList a] -> ShowS #

Generic (RList a) Source # 
Instance details

Defined in Data.List.Snoc

Associated Types

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

Methods

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

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

Semigroup (RList a) Source # 
Instance details

Defined in Data.List.Snoc

Methods

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

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

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

Monoid (RList a) Source # 
Instance details

Defined in Data.List.Snoc

Methods

mempty :: RList a #

mappend :: RList a -> RList a -> RList a #

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

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

Defined in Data.List.Snoc

Methods

rnf :: RList a -> () #

type Rep (RList a) Source # 
Instance details

Defined in Data.List.Snoc

type Rep (RList a) = D1 ('MetaData "RList" "Data.List.Snoc" "reverse-list-0.2.0-inplace" 'True) (C1 ('MetaCons "RList" 'PrefixI 'True) (S1 ('MetaSel ('Just "unRList") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [a])))

type Tsil = RList Source #

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.

Introduction and Elimination

nil :: RList a Source #

The empty RList.

snoc :: RList a -> a -> RList 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.

singleton :: a -> RList a Source #

Create a single-element RList.

unsnoc :: RList a -> Maybe (RList a, a) Source #

O(1) Access the last element and initial portion of the list. See also last and init if you only need one component.

If you are looking for uncons, you should use a plain list, or a finite sequence/queue type.

Patterns

pattern Nil :: RList a Source #

An empty RList, such as nil.

pattern Snoc :: RList a -> a -> RList a Source #

The RList consisting of initial and last elements, such as created by snoc.

Queries

null :: RList a -> Bool Source #

Test if an RList is empty.

init :: RList a -> Maybe (RList a) Source #

O(1) extract the elements of a list other than the last, if they exist. See also unsnoc if you also need last at the same time.

last :: RList a -> Maybe a Source #

O(1) extract the last element of a list, if it exists. See also unsnoc if you also need init at the same time.

Traversal

catMaybes :: RList (Maybe a) -> RList a Source #

Remove all Nothings from an RList of Maybes.

Conversion

toList :: RList 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.

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

O(n) Convert from a plain list, maintaining order.

This is added for completion's sake, as I'm not sure you'll often need this adapter.

See toList for the inverse, or reverseIn for when order doesn't matter.

reverseIn :: [a] -> RList a Source #

O(0) Reverse a plain cons list, rerutning an RList.

See reverseOut for the inverse, and why you might use these.

reverseOut :: RList a -> [a] Source #

O(0) Reverse an RList, returning a plain cons list.

This is here so that when the output list is fed to an order-agnostic function, you don't have to pay the cost of reversing the representation.

See toList for when order matters.

toArrayN :: (Contiguous arr, Element arr a) => Int -> RList a -> arr a Source #

Write the contents of the RList 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.

toSet :: Ord a => RList a -> Set a Source #

Convert to a set without an intermediate conversion to a cons-list.