binary-list-0.3.5.0: Lists of size length a power of two.

Safe HaskellNone

Data.BinaryList

Contents

Description

Binary lists are lists whose number of elements is a power of two. This data structure is efficient for some computations like:

  • Splitting a list in half.
  • Appending two lists of the same length.
  • Extracting an element from the list.

All the functions exported are total except for fromListWithDefault. It is impossible for the user of this library to create a binary list whose length is not a power of two.

Since many names in this module clash with the names of some Prelude functions, you probably want to import this module this way:

 import Data.BinaryList (BinList)
 import qualified Data.BinaryList as BL

Remember that binary lists are an instance of the Foldable and Traversable classes. If you are missing a function here, look for functions using those instances.

Note that some functions like replicate, generate, or take, don't use the length of the list as argument, but the exponent of its length expressed as a power of two. Throughout this document, this is referred (perhaps improperly) as the length index. For example, if the list has length 16, its length index is 4 since 2^4 = 16. Therefore replicate 4 0 will create a list with 16 zeroes. Keep this in mind when using this library. Note as well that this implies that there is no need to check that the length argument is or is not a power of two.

Synopsis

Type

data BinList a Source

A binary list is a list containing a power of two elements. Note that a binary list is never empty.

Instances

Functor BinList 
Foldable BinList 
Traversable BinList 
Eq a => Eq (BinList a) 
Show a => Show (BinList a) 

Construction

singleton :: a -> BinList aSource

O(1). Build a list with a single element.

append :: BinList a -> BinList a -> Maybe (BinList a)Source

O(1). Append two binary lists. This is only possible if both lists have the same length. If this condition is not hold, Nothing is returned.

replicate :: Int -> a -> BinList aSource

O(log n). Calling replicate n x builds a binary list with 2^n occurences of x.

replicateA :: Applicative f => Int -> f a -> f (BinList a)Source

Calling replicateA n f builds a binary list collecting the results of executing 2^n times the applicative action f.

replicateAR :: Applicative f => Int -> f a -> f (BinList a)Source

The same as replicateA, but the actions are executed in reversed order.

generate :: Int -> (Int -> a) -> BinList aSource

O(n). Build a binary list with the given length index (see lengthIndex) by applying a function to each index.

generateM :: (Applicative m, Monad m) => Int -> (Int -> m a) -> m (BinList a)Source

Like generate, but the generator function returns a value in a Monad. Therefore, the result is as well contained in a Monad.

Queries

lengthIndex :: BinList a -> IntSource

O(1). Given a binary list l with length 2^k:

 lengthIndex l = k

length :: BinList a -> IntSource

O(1). Number of elements in the list.

lookup :: BinList a -> Int -> Maybe aSource

O(log n). Lookup an element in the list by its index (starting from 0). If the index is out of range, Nothing is returned.

head :: BinList a -> aSource

O(log n). Get the first element of a binary list.

last :: BinList a -> aSource

O(log n). Get the last element of a binary list.

Deconstruction

split :: BinList a -> Either a (BinList a, BinList a)Source

O(1). Split a binary list into two sublists of half the length, unless the list only contains one element. In that case, it just returns that element.

take :: Int -> BinList a -> BinList aSource

O(log n). Calling take n xs returns the first min (2^n) (length xs) elements of xs.

takeEnd :: Int -> BinList a -> BinList aSource

O(log n). Calling takeEnd n xs returns the last min (2^n) (length xs) elements of xs.

Transformation

replaceSource

Arguments

:: Int

Index to look for

-> a

Element to insert

-> BinList a 
-> BinList a 

O(log n). Replace a single element in the list. If the index is out of range, returns the original list.

reverse :: BinList a -> BinList aSource

O(n). Reverse a binary list.

Tuples

joinPairs :: BinList (a, a) -> BinList aSource

O(n). Transform a list of pairs into a flat list. The resulting list will have twice more elements than the original.

disjoinPairs :: BinList a -> Maybe (BinList (a, a))Source

O(n). Opposite transformation of joinPairs. It halves the number of elements of the input. As a result, when applied to a binary list with a single element, it returns Nothing.

Zipping and Unzipping

zip :: BinList a -> BinList b -> BinList (a, b)Source

O(n). Zip two binary lists in pairs.

unzip :: BinList (a, b) -> (BinList a, BinList b)Source

O(n). Unzip a binary list of pairs.

zipWith :: (a -> b -> c) -> BinList a -> BinList b -> BinList cSource

O(n). Zip two binary lists using an operator.

Lists

From list

fromList :: [a] -> Maybe (BinList a)Source

O(n). Build a binary list from a linked list. If the input list has length different from a power of two, it returns Nothing.

fromListWithDefault :: a -> [a] -> BinList aSource

O(n). Build a binary list from a linked list. If the input list has length different from a power of two, fill to the next power of two with a default element.

Warning: this function crashes if the input list length is larger than any power of two in the type 'Int'. However, this is very unlikely.

fromListSplitSource

Arguments

:: a

Default element

-> Int

Length index

-> [a]

Input list

-> (BinList a, [a]) 

O(n). Build a binary list from a linked list. It returns a binary list with length 2 ^ n (where n is the supplied Int argument), and the list of elements of the original list that were not used. If the input list is shorter than 2 ^ n, a default element will be used to complete the binary list. This method for building binary lists is faster than both fromList and fromListWithDefault.

To list

toListFilter :: (a -> Bool) -> BinList a -> [a]Source

O(n). Create a list from the elements of a binary list matching a given condition.

toListSegment :: Int -> Int -> BinList a -> [a]Source

O(n). Create a list extracting a sublist of elements from a binary list.

Others

traverseSegment :: Applicative f => (a -> f ()) -> Int -> Int -> BinList a -> f ()Source

Apply an applicative action to every element in a segment of a binary list, from left to right.

Example: Radix-2 FFT

This is an example demonstrating the use of binary lists to calculate the Discrete Fourier Transform of complex vectors with the Radix-2 Fast Fourier Transform algorithm.

 import Data.BinaryList (BinList)
 import qualified Data.BinaryList as BL
 
 import Data.Complex
 import Data.Maybe (fromJust)
 
 i :: Complex Double
 i = 0 :+ 1
 
 fft :: BinList (Complex Double) -> BinList (Complex Double)
 fft xs =
   case BL.disjoinPairs xs of
     Nothing -> xs
     Just ps ->
       let (evens,odds) = BL.unzip ps
           n = BL.lengthIndex xs - 1
           q = negate $ pi * i / fromIntegral (2^n)
           twiddles = BL.generate n $ \k -> exp $ q * fromIntegral k
           oddsfft = BL.zipWith (*) twiddles $ fft odds
           evensfft = fft evens
       in  fromJust $
             BL.append (BL.zipWith (+) evensfft oddsfft)
                       (BL.zipWith (-) evensfft oddsfft)