unlifted-list-0.1.0.0: GHC Haskell lists of non-thunks (things of kind TYPE 'UnliftedRep)

Safe HaskellNone
LanguageHaskell2010

Data.List.Unlifted

Description

This module defines an API centred around linked lists of unlifted values.

Synopsis

Documentation

data UList (a :: TYPE UnliftedRep) where Source #

A linked list of unlifted values. The values stored in the list are guaranteed to not be thunks.

Constructors

UNil :: UList a 
UCons :: a -> UList a -> UList a 
Instances
Semigroup (UList a) Source # 
Instance details

Defined in Data.List.Unlifted

Methods

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

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

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

Monoid (UList a) Source # 
Instance details

Defined in Data.List.Unlifted

Methods

mempty :: UList a #

mappend :: UList a -> UList a -> UList a #

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

map :: (a -> b) -> UList a -> UList b Source #

map f xs is the list obtained by applying f to each element of xs, i.e.,

map f [x1, x2, ..., xn] == [f x1, f x2, ..., f xn]
map f [x1, x2, ...] == [f x1, f x2, ...]

foldr :: (a -> b -> b) -> b -> UList a -> b Source #

foldr, 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)...)

foldl :: forall a b. (b -> a -> b) -> b -> UList a -> b Source #

foldl, applied to a binary operator, a starting value (typically the left-identity of the operator), and a list, reduces the list using the binary operator, from left to right:

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

The list must be finite.

foldl' :: forall a b. (b -> a -> b) -> b -> UList a -> b Source #

A strict version of foldl.

null :: UList a -> Bool Source #

Test whether a list is empty.

scanl :: (b -> a -> b) -> b -> UList a -> UList b Source #

scanl is similar to foldl, but returns a list of successive reduced values from the left:

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

Note that

last (scanl f z xs) == foldl f z xs.

filter :: (a -> Bool) -> UList a -> UList a Source #

filter, applied to a predicate and a list, returns the list of those elements that satisfy the predicate; i.e.,

filter p xs = [ x | x <- xs, p x]

length :: UList a -> Int Source #

O(n). length returns the length of a finite list as an Int.

(.) :: forall (a :: TYPE UnliftedRep) (b :: TYPE UnliftedRep) (c :: TYPE UnliftedRep). (b -> c) -> (a -> b) -> a -> c Source #

Function composition.