-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | Data Parallel Haskell segmented arrays. (sequential implementation) -- -- Sequential array data type and stream fuctions, along with a -- sequential reference implementation of the segmented array API defined -- in dph-prim-interface. @package dph-prim-seq @version 0.7.0.1 -- | Irregular 2D unboxed arrays. -- -- The difference between this type and something like Data.Vector -- (Data.Vector.Unboxed a) is that the inner arrays have kind -- # and cannot be bottom. This ensures that we can always -- lookup an element from an ArrayArray# without performing -- unboxings or checking for thunks. module Data.Array.Parallel.Unlifted.ArrayArray data MutableArrayArray s e MutableArrayArray :: (MutableArrayArray# s) -> MutableArrayArray s e data ArrayArray e ArrayArray :: ArrayArray# -> ArrayArray e -- | Create an ArrayArray with the given number of elements. newArrayArray :: Int -> ST s (MutableArrayArray s e) -- | Write a MutableByteArray to an MutableArrayArray. writeArrayArrayMut :: MutableArrayArray s (MutableByteArray s) -> Int -> MutableByteArray s -> ST s () -- | Write a ByteArray to a MutableArrayArray. writeArrayArray :: MutableArrayArray s ByteArray -> Int -> ByteArray -> ST s () -- | Read a MutableByteArray from a MutableArrayArray. readArrayArray :: MutableArrayArray s (MutableByteArray s) -> Int -> ST s (MutableByteArray s) -- | Index an ArrayArray of ByteArrays. indexArrayArray :: ArrayArray ByteArray -> Int -> ByteArray -- | Freeze a MutableArrayArray into a plain ArrayArray. unsafeFreezeArrayArray :: MutableArrayArray s e -> ST s (ArrayArray e) -- | Freeze a nested MutableArrayArray into an ArrayArray. unsafeDeepFreezeArrayArray :: MutableArrayArray s (MutableByteArray s) -> ST s (ArrayArray ByteArray) -- | Copy an ArrayArray copyArrayArray :: MutableArrayArray s ByteArray -> Int -> ArrayArray ByteArray -> Int -> Int -> ST s () -- | Irregular two dimensional arrays. module Data.Array.Parallel.Unlifted.Vectors -- | A 2-dimensional array, where the inner arrays can all have different -- lengths. data Vectors a Vectors :: {-# UNPACK #-} !Int -> {-# UNPACK #-} !ByteArray -> {-# UNPACK #-} !ByteArray -> {-# UNPACK #-} !(ArrayArray ByteArray) -> Vectors a -- | Class of element types that can be used in a Vectors class Prim a => Unboxes a -- | Construct an empty Vectors with no arrays of no elements. empty :: Vectors a -- | Construct a Vectors containing data from a single unboxed -- array. singleton :: (Unboxes a, Unbox a) => Vector a -> Vectors a -- | Yield the number of vectors in a Vectors. length :: Unboxes a => Vectors a -> Int -- | Take one of the outer vectors from a Vectors, with bounds -- checking index :: (Unboxes a, Unbox a) => String -> Vectors a -> Int -> Vector a -- | Retrieve a single element from a Vectors, given the outer and -- inner indices, with bounds checking. index2 :: Unboxes a => String -> Vectors a -> Int -> Int -> a -- | Take one of the outer vectors from a Vectors. unsafeIndex :: (Unboxes a, Unbox a) => Vectors a -> Int -> Vector a -- | Retrieve a single element from a Vectors, given the outer and -- inner indices. unsafeIndex2 :: Unboxes a => Vectors a -> Int -> Int -> a -- | Retrieve an inner array from a Vectors, returning the array -- data, starting index in the data, and vector length. unsafeIndexUnpack :: Unboxes a => Vectors a -> Int -> (ByteArray, Int, Int) -- | Appending two Vectors uses work proportional to the length of -- the outer arrays. append :: (Unboxes a, Unbox a) => Vectors a -> Vectors a -> Vectors a -- | Convert a boxed vector of unboxed vectors to a Vectors. fromVector :: (Unboxes a, Unbox a) => Vector (Vector a) -> Vectors a -- | Convert a Vectors to a boxed vector of unboxed vectors. toVector :: (Unboxes a, Unbox a) => Vectors a -> Vector (Vector a) instance (Unboxes a, Unbox a, Show a) => Show (Vectors a) instance Unboxes Double instance Unboxes Float instance Unboxes Word8 instance Unboxes Int -- | Wrappers for primitives defined in Data.Vector. -- -- module Data.Array.Parallel.Unlifted.Sequential.Vector class (Vector Vector a, MVector MVector a) => Unbox a -- | O(1) Convert a vector to a Stream stream :: Vector v a => v a -> Stream a -- | O(n) Construct a vector from a Stream unstream :: Vector v a => Stream a -> v a -- | O(1) Yield the length of the vector. length :: Unbox a => Vector a -> Int -- | O(1) Test whether a vector if empty null :: Unbox a => Vector a -> Bool -- | O(1) Empty vector empty :: Unbox a => Vector a -- | O(1) Vector with exactly one element singleton :: Unbox a => a -> Vector a -- | O(n) Prepend an element cons :: Unbox a => a -> Vector a -> Vector a units :: Int -> Vector () -- | O(n) Vector of the given length with the same value in each -- position replicate :: Unbox a => Int -> a -> Vector a -- | O(m+n) Concatenate two vectors (++) :: Unbox a => Vector a -> Vector a -> Vector a index :: Unbox a => String -> Vector a -> Int -> a interleave :: Unbox e => Vector e -> Vector e -> Vector e -- | O(n) Pair each element in a vector with its index indexed :: Unbox a => Vector a -> Vector (Int, a) repeat :: Unbox e => Int -> Vector e -> Vector e repeatS :: Unbox e => Int -> Vector e -> Stream e slice :: Unbox a => String -> Vector a -> Int -> Int -> Vector a unsafeSlice :: Unbox a => Vector a -> Int -> Int -> Vector a extract :: Unbox a => Vector a -> Int -> Int -> Vector a unsafeExtract :: Unbox a => Vector a -> Int -> Int -> Vector a -- | O(1) Yield all but the first element without copying. The -- vector may not be empty. tail :: Unbox a => Vector a -> Vector a -- | O(1) Yield at the first n elements without copying. -- The vector may contain less than n elements in which case it -- is returned unchanged. take :: Unbox a => Int -> Vector a -> Vector a -- | O(1) Yield all but the first n elements without -- copying. The vector may contain less than n elements in which -- case an empty vector is returned. drop :: Unbox a => Int -> Vector a -> Vector a -- | O(1) Yield the first n elements paired with the -- remainder without copying. -- -- Note that splitAt n v is equivalent to -- (take n v, drop n v) but slightly more -- efficient. splitAt :: Unbox a => Int -> Vector a -> (Vector a, Vector a) permute :: Unbox e => Vector e -> Vector Int -> Vector e bpermute :: Unbox e => Vector e -> Vector Int -> Vector e mbpermute :: (Unbox e, Unbox d) => (e -> d) -> Vector e -> Vector Int -> Vector d bpermuteDft :: Unbox e => Int -> (Int -> e) -> Vector (Int, e) -> Vector e -- | O(n) Reverse a vector reverse :: Unbox a => Vector a -> Vector a -- | O(m+n) For each pair (i,a) from the vector of -- index/value pairs, replace the vector element at position i -- by a. -- --
--   update <5,9,2,7> <(2,1),(0,3),(2,8)> = <3,9,8,7>
--   
update :: Unbox a => Vector a -> Vector (Int, a) -> Vector a -- | O(n) Map a function over a vector map :: (Unbox a, Unbox b) => (a -> b) -> Vector a -> Vector b -- | O(min(m,n)) Zip two vectors with the given function. zipWith :: (Unbox a, Unbox b, Unbox c) => (a -> b -> c) -> Vector a -> Vector b -> Vector c -- | Zip three vectors with the given function. zipWith3 :: (Unbox a, Unbox b, Unbox c, Unbox d) => (a -> b -> c -> d) -> Vector a -> Vector b -> Vector c -> Vector d -- | O(n) Drop elements that do not satisfy the predicate filter :: Unbox a => (a -> Bool) -> Vector a -> Vector a pack :: Unbox e => Vector e -> Vector Bool -> Vector e combine :: Unbox a => Vector Bool -> Vector a -> Vector a -> Vector a combine2ByTag :: Unbox a => Vector Tag -> Vector a -> Vector a -> Vector a foldl :: Unbox a => (b -> a -> b) -> b -> Vector a -> b foldl1 :: Unbox a => (a -> a -> a) -> Vector a -> a foldl1Maybe :: Unbox a => (a -> a -> a) -> Vector a -> Maybe a fold :: Unbox a => (a -> a -> a) -> a -> Vector a -> a fold1 :: Unbox a => (a -> a -> a) -> Vector a -> a fold1Maybe :: Unbox a => (a -> a -> a) -> Vector a -> Maybe a scanl :: (Unbox a, Unbox b) => (b -> a -> b) -> b -> Vector a -> Vector b scanl1 :: Unbox a => (a -> a -> a) -> Vector a -> Vector a scan :: Unbox a => (a -> a -> a) -> a -> Vector a -> Vector a scan1 :: Unbox a => (a -> a -> a) -> Vector a -> Vector a scanRes :: Unbox a => (a -> a -> a) -> a -> Vector a -> (Vector a, a) -- | O(n) Check if the vector contains an element elem :: (Unbox a, Eq a) => a -> Vector a -> Bool -- | O(n) Check if the vector does not contain an element (inverse -- of elem) notElem :: (Unbox a, Eq a) => a -> Vector a -> Bool -- | O(n) Check if all elements are True and :: Vector Bool -> Bool -- | O(n) Check if any element is True or :: Vector Bool -> Bool -- | O(n) Check if any element satisfies the predicate. any :: Unbox a => (a -> Bool) -> Vector a -> Bool -- | O(n) Check if all elements satisfy the predicate. all :: Unbox a => (a -> Bool) -> Vector a -> Bool -- | O(n) Compute the sum of the elements sum :: (Unbox a, Num a) => Vector a -> a -- | O(n) Compute the produce of the elements product :: (Unbox a, Num a) => Vector a -> a -- | O(n) Yield the maximum element of the vector. The vector may -- not be empty. maximum :: (Unbox a, Ord a) => Vector a -> a -- | O(n) Yield the minimum element of the vector. The vector may -- not be empty. minimum :: (Unbox a, Ord a) => Vector a -> a -- | O(n) Yield the maximum element of the vector according to the -- given comparison function. The vector may not be empty. maximumBy :: Unbox a => (a -> a -> Ordering) -> Vector a -> a -- | O(n) Yield the minimum element of the vector according to the -- given comparison function. The vector may not be empty. minimumBy :: Unbox a => (a -> a -> Ordering) -> Vector a -> a -- | O(n) Yield the index of the maximum element of the vector. The -- vector may not be empty. maxIndex :: (Unbox a, Ord a) => Vector a -> Int -- | O(n) Yield the index of the minimum element of the vector. The -- vector may not be empty. minIndex :: (Unbox a, Ord a) => Vector a -> Int -- | O(n) Yield the index of the maximum element of the vector -- according to the given comparison function. The vector may not be -- empty. maxIndexBy :: Unbox a => (a -> a -> Ordering) -> Vector a -> Int -- | O(n) Yield the index of the minimum element of the vector -- according to the given comparison function. The vector may not be -- empty. minIndexBy :: Unbox a => (a -> a -> Ordering) -> Vector a -> Int zip :: (Unbox a, Unbox b) => Vector a -> Vector b -> Vector (a, b) unzip :: (Unbox a, Unbox b) => Vector (a, b) -> (Vector a, Vector b) fsts :: (Unbox a, Unbox b) => Vector (a, b) -> Vector a snds :: (Unbox a, Unbox b) => Vector (a, b) -> Vector b zip3 :: (Unbox a, Unbox b, Unbox c) => Vector a -> Vector b -> Vector c -> Vector (a, b, c) unzip3 :: (Unbox a, Unbox b, Unbox c) => Vector (a, b, c) -> (Vector a, Vector b, Vector c) -- | O(n) Enumerate values from x to y. -- -- WARNING: This operation can be very inefficient. If at all -- possible, use enumFromN instead. enumFromTo :: (Unbox a, Enum a) => a -> a -> Vector a -- | O(n) Enumerate values from x to y with a -- specific step z. -- -- WARNING: This operation can be very inefficient. If at all -- possible, use enumFromStepN instead. enumFromThenTo :: (Unbox a, Enum a) => a -> a -> a -> Vector a enumFromStepLen :: Int -> Int -> Int -> Vector Int enumFromToEach :: Int -> Vector (Int, Int) -> Vector Int enumFromStepLenEach :: Int -> Vector Int -> Vector Int -> Vector Int -> Vector Int -- | O(n) Yield Just the first element matching the predicate -- or Nothing if no such element exists. find :: Unbox a => (a -> Bool) -> Vector a -> Maybe a -- | O(n) Yield Just the index of the first element matching -- the predicate or Nothing if no such element exists. findIndex :: Unbox a => (a -> Bool) -> Vector a -> Maybe Int -- | O(n) Convert a vector to a list toList :: Unbox a => Vector a -> [a] -- | O(n) Convert a list to a vector fromList :: Unbox a => [a] -> Vector a random :: (Unbox a, Random a, RandomGen g) => Int -> g -> Vector a randomR :: (Unbox a, Random a, RandomGen g) => Int -> (a, a) -> g -> Vector a new :: Unbox a => Int -> (forall s. MVector s a -> ST s ()) -> Vector a -- | O(n) Copy an immutable vector into a mutable one. The two -- vectors must have the same length. copy :: (Unbox a, PrimMonad m) => MVector (PrimState m) a -> Vector a -> m () newM :: Unbox a => Int -> ST s (MVector s a) -- | O(1) Unsafe convert a mutable vector to an immutable one -- without copying. The mutable vector may not be used after this -- operation. unsafeFreeze :: (Unbox a, PrimMonad m) => MVector (PrimState m) a -> m (Vector a) -- | Replace the element at the given position. write :: (PrimMonad m, Unbox a) => MVector (PrimState m) a -> Int -> a -> m () -- | Yield the element at the given position. read :: (PrimMonad m, Unbox a) => MVector (PrimState m) a -> Int -> m a mpermute :: Unbox e => MVector s e -> Vector e -> Vector Int -> ST s () mupdate :: Unbox e => MVector s e -> Vector (Int, e) -> ST s () mdrop :: Unbox a => Int -> MVector s a -> MVector s a mslice :: Unbox a => Int -> Int -> MVector s a -> MVector s a class Unbox a => UIO a hPut :: UIO a => Handle -> Vector a -> IO () hGet :: UIO a => Handle -> IO (Vector a) instance Vector Vector Integer instance MVector MVector Integer instance Unbox Integer instance Vector Vector Ordering instance MVector MVector Ordering instance Unbox Ordering instance (UIO a, UIO b) => UIO (a, b) instance UIO Double instance UIO Int -- | Segment Descriptors. -- -- See Data.Array.Parallel.Unlifted for how this works. module Data.Array.Parallel.Unlifted.Sequential.USegd -- | Segment descriptor. data USegd USegd :: !(Vector Int) -> !(Vector Int) -> !Int -> USegd -- | Length of each segment. usegd_lengths :: USegd -> !(Vector Int) -- | Starting index of each segment. usegd_indices :: USegd -> !(Vector Int) -- | Total number of elements in the flat array. usegd_elements :: USegd -> !Int -- | O(1). Construct a new segment descriptor. mkUSegd :: Vector Int -> Vector Int -> Int -> USegd -- | O(1). Check the internal consistency of a segment descriptor. -- -- As the indices and elemens field can be generated based on the segment -- lengths, we check the consistency by rebuilding these fields and -- comparing the rebuilt ones against the originals. valid :: USegd -> Bool -- | O(1). Construct an empty segment descriptor, with no elements or -- segments. empty :: USegd -- | O(1). Construct a singleton segment descriptor. The single segment -- covers the given number of elements. singleton :: Int -> USegd -- | O(segs). Convert an array of segment lengths into a segment -- descriptor. -- -- The array contains the length of each segment, and we compute the -- indices from that. fromLengths :: Vector Int -> USegd -- | O(1). Yield the overall number of segments. length :: USegd -> Int -- | O(1). Yield the lengths of the individual segments. takeLengths :: USegd -> Vector Int -- | O(1). Yield the segment indices of a segment descriptor. takeIndices :: USegd -> Vector Int -- | O(1). Yield the number of data elements. takeElements :: USegd -> Int -- | O(1). Get the length and segment index of a segment getSeg :: USegd -> Int -> (Int, Int) -- | O(segs). Produce a segment descriptor that describes the result of -- appending two arrays. append :: USegd -> USegd -> USegd -- | O(segs) Extract a slice of a segment descriptor, avoiding copying -- where possible. -- -- We can share the segment lengths with the original segment descriptor, -- but still need to recompute the starting indices of each. Hence -- runtime is O(segs) in the number of segments sliced out. slice :: USegd -> Int -> Int -> USegd -- | Extract a slice of a segment descriptor, copying everything. -- -- In contrast to slice, this function copies the array of segment -- lengths as well as recomputing the starting indices of each. extract :: USegd -> Int -> Int -> USegd instance Show USegd instance Eq USegd instance PprPhysical USegd -- | Scattered Segment Descriptors. -- -- See Data.Array.Parallel.Unlifted for how this works. module Data.Array.Parallel.Unlifted.Sequential.USSegd -- | Scattered Segment Descriptor. data USSegd USSegd :: !Bool -> Vector Int -> Vector Int -> !USegd -> USSegd -- | True when the starts are identical to the usegd indices field and the -- sources are all 0's. -- -- In this case all the data elements are in one contiguous flat array, -- and consumers can avoid looking at the real starts and sources fields. ussegd_contiguous :: USSegd -> !Bool -- | Starting index of each segment in its flat array. -- -- IMPORTANT: this field is lazy so we can avoid creating it when the -- flat array is contiguous. ussegd_starts :: USSegd -> Vector Int -- | Which flat array to take each segment from. -- -- IMPORTANT: this field is lazy so we can avoid creating it when the -- flat array is contiguous. ussegd_sources :: USSegd -> Vector Int -- | Segment descriptor relative to a contiguous index space. This defines -- the length of each segment. ussegd_usegd :: USSegd -> !USegd -- | O(1). Check the internal consistency of a scattered segment -- descriptor. valid :: USSegd -> Bool -- | O(1). Construct a new scattered segment descriptor. All the provided -- arrays must have the same lengths. mkUSSegd :: Vector Int -> Vector Int -> USegd -> USSegd -- | O(1). Construct an empty segment descriptor, with no elements or -- segments. empty :: USSegd -- | O(1). Construct a singleton segment descriptor. The single segment -- covers the given number of elements in a flat array with sourceid 0. singleton :: Int -> USSegd -- | O(segs). Promote a plain USegd to a USSegd. All segments -- are assumed to come from a flat array with sourceid 0. fromUSegd :: USegd -> USSegd -- | O(1). True when the starts are identical to the usegd indices field -- and the sources are all 0's. -- -- In this case all the data elements are in one contiguous flat array, -- and consumers can avoid looking at the real starts and sources fields. isContiguous :: USSegd -> Bool -- | O(1). Yield the overall number of segments. length :: USSegd -> Int -- | O(1). Yield the USegd of a USSegd. takeUSegd :: USSegd -> USegd -- | O(1). Yield the lengths of the segments of a USSegd. takeLengths :: USSegd -> Vector Int -- | O(1). Yield the segment indices of a USSegd. takeIndices :: USSegd -> Vector Int -- | O(1). Yield the total number of elements covered by a USSegd. takeElements :: USSegd -> Int -- | O(1). Yield the source ids of a USSegd. takeSources :: USSegd -> Vector Int -- | O(1). Yield the starting indices of a USSegd. takeStarts :: USSegd -> Vector Int -- | O(1). Get the length, segment index, starting index, and source id of -- a segment. getSeg :: USSegd -> Int -> (Int, Int, Int, Int) -- | O(n). Produce a segment descriptor that describes the result of -- appending two arrays. appendWith :: USSegd -> Int -> USSegd -> Int -> USSegd -- | Cull the segments of a USSegd down to only those reachable from -- an array of vsegids, and also update the vsegids to -- point to the same segments in the result. cullOnVSegids :: Vector Int -> USSegd -> (Vector Int, USSegd) instance Show USSegd instance PprPhysical USSegd -- | Selectors. -- -- See Data.Array.Parallel.Unlifted for how this works. module Data.Array.Parallel.Unlifted.Sequential.USel -- | Selector. data USel2 USel2 :: !(Vector Tag) -> !(Vector Int) -> !Int -> !Int -> USel2 usel2_tags :: USel2 -> !(Vector Tag) usel2_indices :: USel2 -> !(Vector Int) -- | Number of tags with value 0. usel2_elements0 :: USel2 -> !Int -- | Number of tags with value 1. usel2_elements1 :: USel2 -> !Int -- | O(1). Construct a selector. mkUSel2 :: Vector Tag -> Vector Int -> Int -> Int -> USel2 -- | O(1). Get the number of elements represented by this selector. This is -- the length of the array returned by combine. lengthUSel2 :: USel2 -> Int -- | O(1). Get the tags array of a selector. tagsUSel2 :: USel2 -> Vector Tag -- | O(1). Get the indices array of a selector. indicesUSel2 :: USel2 -> Vector Int -- | O(1). Get the number of elements that will be taken from the first -- array. elementsUSel2_0 :: USel2 -> Int -- | O(1). Get the number of elements that will be taken from the second -- array. elementsUSel2_1 :: USel2 -> Int -- | O(n). Compute the source index for each element of the result array. tagsToIndices2 :: Vector Tag -> Vector Int -- | Virtual Segment Descriptors. -- -- See Data.Array.Parallel.Unlifted for how this works. module Data.Array.Parallel.Unlifted.Sequential.UVSegd -- | Virtual segment descriptor. data UVSegd UVSegd :: !Bool -> Vector Int -> Vector Int -> USSegd -> USSegd -> UVSegd -- | When the vsegids field holds a lazy (U.enumFromTo 0 (len - -- 1)) then this field is True. This lets us perform some operations -- like demoteToUPSSegd without actually creating it. uvsegd_manifest :: UVSegd -> !Bool -- | Virtual segment identifiers that indicate what physical segment to use -- for each virtual segment. uvsegd_vsegids_redundant :: UVSegd -> Vector Int uvsegd_vsegids_culled :: UVSegd -> Vector Int -- | Scattered segment descriptor that defines how physical segments are -- layed out in memory. uvsegd_ussegd_redundant :: UVSegd -> USSegd uvsegd_ussegd_culled :: UVSegd -> USSegd -- | O(1). Check the internal consistency of a virutal segmentation -- descriptor. valid :: UVSegd -> Bool -- | O(1). Construct a new virtual segment descriptor. All the provided -- arrays must have the same lengths. mkUVSegd :: Vector Int -> USSegd -> UVSegd -- | O(segs). Promote a plain Segd to a VSegd. -- -- The result contains one virtual segment for every physical segment the -- provided SSegd. fromUSegd :: USegd -> UVSegd -- | O(segs). Promote a plain USegd to a UVSegd. -- -- The result contains one virtual segment for every physical segment the -- provided Segd. fromUSSegd :: USSegd -> UVSegd -- | O(1). Construct an empty segment descriptor, with no elements or -- segments. empty :: UVSegd -- | O(1). Construct a singleton segment descriptor. The single segment -- covers the given number of elements in a flat array with sourceid 0. singleton :: Int -> UVSegd -- | O(1). Construct a UVSegd that describes an array created by -- replicating a single segment several times. replicated :: Int -> Int -> UVSegd -- | O(1). Checks whether all the segments are manifest (unshared / -- non-virtual). If this is the case, then the vsegids field will be -- [0..len-1]. -- -- Consumers can check this field, avoid demanding the vsegids field. -- This can avoid the need for it to be generated in the first place, due -- to lazy evaluation. isManifest :: UVSegd -> Bool -- | O(1). Checks whether the starts are identical to the usegd indices -- field and the sourceids are all 0's. -- -- In this case all the data elements are in one contiguous flat array, -- and consumers can avoid looking at the real starts and sources fields. isContiguous :: UVSegd -> Bool -- | O(1). Yield the overall number of segments described by a -- UVSegd. length :: UVSegd -> Int -- | O(1). Yield the vsegids of a UVSegd takeVSegids :: UVSegd -> Vector Int -- | O(1). Take the vsegids of a UVSegd, but don't require that -- every physical segment is referenced by some virtual segment. -- -- If you're just performing indexing and don't need the invariant that -- all physical segments are reachable from some virtual segment, then -- use this version as it's faster. This sidesteps the code that -- maintains the invariant. -- -- The stated O(1) complexity assumes that the array has already been -- fully evalauted. If this is not the case then we can avoid demanding -- the result of a prior computation on the vsegids, thus reducing the -- cost attributed to that prior computation. takeVSegidsRedundant :: UVSegd -> Vector Int -- | O(1). Yield the USSegd of a UVSegd. takeUSSegd :: UVSegd -> USSegd -- | O(1). Take the UPSSegd of a UPVSegd, but don't -- require that every physical segment is referenced by some virtual -- segment. -- -- See the note in takeVSegidsRedundant. takeUSSegdRedundant :: UVSegd -> USSegd -- | O(segs). Yield the lengths of the segments described by a -- UVSegd. takeLengths :: UVSegd -> Vector Int -- | O(1). Get the length, starting index, and source id of a segment. getSeg :: UVSegd -> Int -> (Int, Int, Int) -- | O(n) Produce a segment descriptor describing the result of appending -- two arrays. appendWith :: UVSegd -> Int -> UVSegd -> Int -> UVSegd -- | O(n). Combine two virtual segment descriptors. combine2 :: USel2 -> UVSegd -> Int -> UVSegd -> Int -> UVSegd -- | Update the vsegids of UPVSegd, and then cull the physical -- segment descriptor so that all phsyical segments are reachable from -- some virtual segment. -- -- This function lets you perform filtering operations on the virtual -- segments, while maintaining the invariant that all physical segments -- are referenced by some virtual segment. updateVSegs :: (Vector Int -> Vector Int) -> UVSegd -> UVSegd -- | Update the vsegids of UPVSegd, where the result covers all -- physical segments. -- -- updateVSegsReachable :: (Vector Int -> Vector Int) -> UVSegd -> UVSegd -- | O(segs). Yield a USSegd that describes each segment of a -- UVSegd individually. -- -- unsafeDemoteToUSSegd :: UVSegd -> USSegd -- | O(segs). Yield a USegd that describes each segment of a -- UVSegd individually, assuming all segments have been -- concatenated to remove scattering. -- -- WARNING: Trying to take the UPSegd of a nested array -- that has been constructed with replication can cause index space -- overflow. This is because the virtual size of the corresponding flat -- data can be larger than physical memory. If this happens then indices -- fields and element count in the result will be invalid. unsafeDemoteToUSegd :: UVSegd -> USegd instance Show UVSegd instance PprPhysical UVSegd module Data.Array.Parallel.Unlifted.Stream -- | Tag each element of an stream with its index in that stream. -- --
--   indexed [42,93,13]
--    = [(0,42), (1,93), (2,13)]
--   
indexedS :: Stream a -> Stream (Int, a) -- | Given a stream of pairs containing a count an an element, replicate -- element the number of times given by the count. -- -- The first parameter sets the size hint of the resulting stream. -- --
--   replicateEach 10 [(2,10), (5,20), (3,30)]
--     = [10,10,20,20,20,20,20,30,30,30]
--   
replicateEachS :: Int -> Stream (Int, a) -> Stream a -- | Repeat each element in the stream the given number of times. -- --
--   replicateEach 2 [10,20,30]
--    = [10,10,20,20,30,30]
--   
replicateEachRS :: Int -> Stream a -> Stream a -- | Interleave the elements of two streams. We alternate between the first -- and second streams, stopping when we can't find a matching element. -- --
--   interleave [2,3,4] [10,20,30] = [2,10,3,20,4,30]
--   interleave [2,3]   [10,20,30] = [2,10,3,20]
--   interleave [2,3,4] [10,20]    = [2,10,3,20,4]
--   
interleaveS :: Stream a -> Stream a -> Stream a -- | Combine two streams, using a tag stream to tell us which of the data -- streams to take the next element from. -- -- If there are insufficient elements in the data strams for the provided -- tag stream then error. -- --
--   combine2ByTag [0,1,1,0,0,1] [1,2,3] [4,5,6]
--    = [1,4,5,2,3,6]
--   
combine2ByTagS :: Stream Tag -> Stream a -> Stream a -> Stream a -- | Segmented Stream combine. Like combine2ByTagS, except that the -- tags select entire segments of each data stream, instead of selecting -- one element at a time. -- --
--   combineSS [True, True, False, True, False, False]
--             [2,1,3] [10,20,30,40,50,60]
--             [1,2,3] [11,22,33,44,55,66]
--    = [10,20,30,11,40,50,60,22,33,44,55,66]
--   
-- -- This says take two elements from the first stream, then another one -- element from the first stream, then one element from the second -- stream, then three elements from the first stream... combineSS :: Stream Bool -> Stream Int -> Stream a -> Stream Int -> Stream a -> Stream a -- | Create a stream of integer ranges. The pairs in the input stream give -- the first and last value of each range. -- -- The first parameter gives the size hint for the resulting stream. -- --
--   enumFromToEach 11 [(2,5), (10,16), (20,22)]
--    = [2,3,4,5,10,11,12,13,14,15,16,20,21,22]
--   
enumFromToEachS :: Int -> Stream (Int, Int) -> Stream Int -- | Create a stream of integer ranges. The triples in the input stream -- give the first value, increment, length of each range. -- -- The first parameter gives the size hint for the resulting stream. -- --
--   enumFromStepLenEach [(1,1,5), (10,2,4), (20,3,5)]
--    = [1,2,3,4,5,10,12,14,16,20,23,26,29,32]
--   
enumFromStepLenEachS :: Int -> Stream (Int, Int, Int) -> Stream Int -- | Segmented Stream fold. Take segments from the given stream and fold -- each using the supplied function and initial element. -- --
--   foldSS (+) 0 [2, 3, 2] [10, 20, 30, 40, 50, 60, 70]
--    = [30,120,130]
--   
foldSS :: (a -> b -> a) -> a -> Stream Int -> Stream b -> Stream a -- | Like foldSS, but use the first member of each chunk as the -- initial element for the fold. fold1SS :: (a -> a -> a) -> Stream Int -> Stream a -> Stream a -- | Segmented Stream fold, with a fixed segment length. -- -- Like foldSS but use a fixed length for each segment. foldValuesR :: (a -> b -> a) -> a -> Int -> Stream b -> Stream a -- | Segmented Strem append. Append corresponding segments from each -- stream. -- --
--   appendSS [2, 1, 3] [10, 20, 30, 40, 50, 60]
--            [1, 3, 2] [11, 22, 33, 44, 55, 66]
--    = [10,20,11,30,22,33,44,40,50,60,55,66]
--   
appendSS :: Stream Int -> Stream a -> Stream Int -> Stream a -> Stream a -- | Segmented Stream indices. -- --
--   indicesSS 15 4 [3, 5, 7]
--    = [4,5,6,0,1,2,3,4,0,1,2,3,4,5,6]
--   
-- -- Note that we can set the starting value of the first segment -- independently via the second argument of indicesSS. We use this when -- distributing arrays across worker threads, as a thread's chunk may not -- start exactly at a segment boundary, so the index of a thread's first -- data element may not be zero. indicesSS :: Int -> Int -> Stream Int -> Stream Int -- | Take a stream of virtual segment and segment element indices, and -- convert it to a stream of physical segment and segment element -- indices. streamSrcIxsThroughVSegids :: Monad m => Vector Int -> Stream m (Int, Int) -> Stream m (Int, Int) -- | Take a stream of segment and segment element indices, and convert it -- to a stream of chunk and chunk element indices. streamSrcIxsThroughUSSegd :: Monad m => USSegd -> Stream m (Int, Int) -> Stream m (Int, Int) -- | Take a stream of indices, look them up from a vector, and produce a -- stream of elements. streamElemsFromVector :: (Monad m, Unbox a) => Vector a -> Stream m Int -> Stream m a -- | Take a stream of chunk and chunk element indices, look them up from -- some vectors, and produce a stream of elements. streamElemsFromVectors :: (Monad m, Unboxes a) => Vectors a -> Stream m (Int, Int) -> Stream m a -- | Take a stream of virtual segment ids and element indices, pass them -- through a UVSegd to get physical segment and element indices, -- and produce a stream of elements. streamElemsFromVectorsVSegd :: (Monad m, Unboxes a) => Vectors a -> UVSegd -> Stream m (Int, Int) -> Stream m a -- | Stream some physical segments from many data arrays. streamSegsFromNestedUSSegd :: (Unbox a, Monad m) => Vector (Vector a) -> USSegd -> Stream m a -- | Stream segments from a Vectors. -- -- streamSegsFromVectorsUSSegd :: (Unboxes a, Monad m) => Vectors a -> USSegd -> Stream m a -- | Stream segments from a Vectors. -- -- streamSegsFromVectorsUVSegd :: (Unboxes a, Monad m) => Vectors a -> UVSegd -> Stream m a streamSegsFromVectorsUSSegdSegmap :: (Unboxes a, Monad m) => Vectors a -> USSegd -> Vector Int -> Stream m a streamSegsFromVectorsUSSegd_split :: (Unboxes a, Monad m) => Vectors a -> USSegd -> Vector Int -> ((USegd, Int), Int) -> Stream m a -- | Sequential operations on unlifted arrays. -- -- module Data.Array.Parallel.Unlifted.Sequential -- | Segmented replicate of a vector based on the lengths of the segments -- of the provided USegd. replicateSU :: Unbox a => USegd -> Vector a -> Vector a -- | Regular sgemented replicate. replicateRSU :: Unbox a => Int -> Vector a -> Vector a -- | Segmented append. appendSU :: Unbox a => USegd -> Vector a -> USegd -> Vector a -> Vector a -- | Segmented indices. indicesSU :: USegd -> Vector Int indicesSU' :: Int -> USegd -> Vector Int -- | Segmented array reduction that requires an associative combination -- function with its unit foldSU :: Unbox a => (a -> a -> a) -> a -> USegd -> Vector a -> Vector a -- | Segmented array reduction that requires an associative combination -- function with its unit. For scattered segments. foldSSU :: (Unbox a, Unboxes a) => (a -> a -> a) -> a -> USSegd -> Vectors a -> Vector a -- | Segmented array reduction proceeding from the left foldlSU :: (Unbox a, Unbox b) => (b -> a -> b) -> b -> USegd -> Vector a -> Vector b -- | Segmented array reduction proceeding from the left. For scattered -- segments. foldlSSU :: (Unbox a, Unboxes a, Unbox b) => (b -> a -> b) -> b -> USSegd -> Vectors a -> Vector b -- | Regular arrar reduction foldlRU :: (Unbox a, Unbox b) => (b -> a -> b) -> b -> Int -> Vector a -> Vector b -- | Segmented array reduction from left to right with non-empty subarrays -- only foldl1SU :: Unbox a => (a -> a -> a) -> USegd -> Vector a -> Vector a -- | Segmented array reduction from left to right with non-empty subarrays -- only. For scattered segments. foldl1SSU :: (Unbox a, Unboxes a) => (a -> a -> a) -> USSegd -> Vectors a -> Vector a -- | Segmented array reduction with non-empty subarrays and an associative -- combination function. fold1SU :: Unbox a => (a -> a -> a) -> USegd -> Vector a -> Vector a -- | Segmented array reduction with non-empty subarrays and an associative -- combination function. For scattered segments. fold1SSU :: (Unbox a, Unboxes a) => (a -> a -> a) -> USSegd -> Vectors a -> Vector a -- | Compute the boolean AND of all segments in a segmented array. andSU :: USegd -> Vector Bool -> Vector Bool -- | Compute the boolean OR of all segments in a segmented array. orSU :: USegd -> Vector Bool -> Vector Bool -- | Compute the segmented sum of an array of numerals sumSU :: (Num e, Unbox e) => USegd -> Vector e -> Vector e -- | Compute the segmented sum of an array of numerals sumRU :: (Num e, Unbox e) => Int -> Vector e -> Vector e -- | Compute the segmented product of an array of numerals productSU :: (Num e, Unbox e) => USegd -> Vector e -> Vector e -- | Determine the maximum element in each subarray maximumSU :: (Ord e, Unbox e) => USegd -> Vector e -> Vector e -- | Determine the minimum element in each subarray minimumSU :: (Ord e, Unbox e) => USegd -> Vector e -> Vector e -- | Merge two segmented arrays according to flag array combineSU :: Unbox a => Vector Bool -> USegd -> Vector a -> USegd -> Vector a -> Vector a -- | Lookup elements from a Vector. indexsFromVector :: Unbox a => Vector a -> Vector Int -> Vector a -- | Lookup elements from some Vectors through a UPVSegd. indexsFromVectorsUVSegd :: (Unbox a, Unboxes a) => Vectors a -> UVSegd -> Vector (Int, Int) -> Vector a -- | Copy segments from a Vectors, concatenating them into a new -- array. extractsFromNestedUSSegd :: Unbox a => USSegd -> Vector (Vector a) -> Vector a -- | Copy segments from a Vectors, concatenating them into a new -- array. extractsFromVectorsUSSegd :: (Unboxes a, Unbox a) => USSegd -> Vectors a -> Vector a -- | Copy segments from a Vectors, concatenating them into a new -- array. extractsFromVectorsUVSegd :: (Unbox a, Unboxes a) => UVSegd -> Vectors a -> Vector a -- | Sequential implementation of the segmented array API defined in -- dph-prim-interface. -- -- There is a parallel implementation in dph-prim-par, so you -- probably want that instead. module Data.Array.Parallel.Unlifted class Unbox a => Elt a -- | Arrays are stored as unboxed vectors. They have bulk-strict semantics, -- so demanding one element demands them all. type Array = Vector -- | O(1). Construct an array with no elements. empty :: Elt a => Array a -- | Generate a new array given its length and a function to compute each -- element. generate :: Elt a => Int -> (Int -> a) -> Array a -- | O(length result). Construct a new array by replicating a single -- element the given number of times. replicate :: Elt a => Int -> a -> Array a -- | O(length result). Segmented replicate. -- -- Elements of the array are replicated according to the lengths of the -- segments defined by the Segd. replicate_s :: Elt a => Segd -> Array a -> Array a -- | O(length result). Regular segmented replicate. -- -- Like replicate_s, but all segments are assumed to have the -- given length. replicate_rs :: Elt a => Int -> Array a -> Array a -- | O(length result). Construct an array by copying a portion of another -- array. repeat :: Elt a => Int -> Int -> Array a -> Array a -- | O(length result). Tag each element of an array with its index. -- --
--   indexed [42, 93, 13] = [(0, 42), (1, 93), (2, 13)]
--   
indexed :: Elt a => Array a -> Array (Int, a) -- | O(length result). Append two arrays. (+:+) :: Elt a => Array a -> Array a -> Array a -- | O(length result). Segmented append. append_s :: Elt a => Segd -> Segd -> Array a -> Segd -> Array a -> Array a append_vs :: (Elt a, Elts a) => Segd -> VSegd -> Arrays a -> VSegd -> Arrays a -> Array a -- | O(length result). Segmented indices. -- -- Construct an array containing containing the segments defined by the -- given Segd. -- -- Each segment will contain the elements [0..len-1] where -- len is the length of that segment. indices_s :: Segd -> Array Int enumFromTo :: Int -> Int -> Array Int enumFromThenTo :: Int -> Int -> Int -> Array Int enumFromStepLen :: Int -> Int -> Int -> Array Int enumFromStepLenEach :: Int -> Array Int -> Array Int -> Array Int -> Array Int -- | O(1). Yield the number of elements in an array. length :: Elt a => Array a -> Int -- | O(1). Retrieve a numbered element from an array. -- -- The first argument gives a source-code location for out-of-bounds -- errors. index :: Elt a => String -> Array a -> Int -> a -- | O(length result). Scattered indexing from a single Array. -- -- This is an alias for bpermute. indexs :: Elt a => Array a -> Array Int -> Array a -- | O(length result). Scattered indexing through a VSegd. -- -- The index array contains pairs of segment id and the index within that -- segment. -- -- We use the VSegd to map the pairs to 2D indices within the -- Arrays, and return an array of the resulting elements. indexs_avs :: (Elt a, Elts a) => Arrays a -> VSegd -> Array (Int, Int) -> Array a -- | O(length result). Extract a subrange of elements from an array. -- --
--   extract [23, 42, 93, 50, 27] 1 3  = [42, 93, 50]
--   
extract :: Elt a => Array a -> Int -> Int -> Array a -- | O(length result). Extract segments defined by a SSegd from a -- vector of arrays. -- -- NOTE: This is a transitory interface, and will be removed in future -- versions. Use extracts_ass instead. extracts_nss :: Elt a => SSegd -> Vector (Array a) -> Array a -- | O(length result). Extract segments defined by a SSegd. -- -- Extract all the segments defined by the SSegd from the -- Arrays, returning them concatenated in a fresh Array. extracts_ass :: (Elt a, Elts a) => SSegd -> Arrays a -> Array a -- | O(length result). Extract segments defined by a VSegd. -- -- Extract all the segments defined by the VSegd from the -- Arrays, returning them concatenated in a fresh Array. extracts_avs :: (Elt a, Elts a) => VSegd -> Arrays a -> Array a -- | O(length result). Drop elements from the front of an array, returning -- the latter portion. drop :: Elt a => Int -> Array a -> Array a -- | O(length result). Copy the source array while replacing some elements -- by new ones in the result. update :: Elt a => Array a -> Array (Int, a) -> Array a -- | O(length result). Forwards permutation of array elements. permute :: Elt a => Array a -> Array Int -> Array a -- | O(length result). Backwards permutation of array elements. -- --
--   bpermute [50, 60, 20, 30] [0, 3, 2] = [50, 30, 20]
--   
bpermute :: Elt a => Array a -> Array Int -> Array a -- | Combination of map and bpermute. -- -- The advantage of using this combined version is that we don't need to -- apply the parameter function to source elements that don't appear in -- the result. mbpermute :: (Elt a, Elt b) => (a -> b) -> Array a -> Array Int -> Array b -- | Default backwards permutation. -- -- The values of the index-value pairs are written into the position in -- the result array that is indicated by the corresponding index. -- -- All positions not covered by the index-value pairs will have the value -- determined by the initialiser function for that index position. bpermuteDft :: Elt e => Int -> (Int -> e) -> Array (Int, e) -> Array e -- | O(1). Zip two arrays into an array of pairs. If one array is short, -- excess elements of the longer array are discarded. zip :: (Elt a, Elt b) => Array a -> Array b -> Array (a, b) -- | O(1). Zip three arrays into an array of triples. If one array is -- short, excess elements of the longer arrays are discarded. zip3 :: (Elt a, Elt b, Elt c) => Array a -> Array b -> Array c -> Array (a, b, c) -- | O(1). Unzip an array of pairs into a pair of arrays. unzip :: (Elt a, Elt b) => Array (a, b) -> (Array a, Array b) -- | O(1). Unzip an array of triples into a triple of arrays. unzip3 :: (Elt a, Elt b, Elt c) => Array (a, b, c) -> (Array a, Array b, Array c) -- | O(1). Take the first elements of an array of pairs. fsts :: (Elt a, Elt b) => Array (a, b) -> Array a -- | O(1). Take the second elements of an array of pairs. snds :: (Elt a, Elt b) => Array (a, b) -> Array b -- | Apply a worker function to each element of an array, yielding a new -- array. map :: (Elt a, Elt b) => (a -> b) -> Array a -> Array b -- | Apply a worker function to correponding elements of two arrays. zipWith :: (Elt a, Elt b, Elt c) => (a -> b -> c) -> Array a -> Array b -> Array c -- | Apply a worker function to corresponding elements of three arrays. zipWith3 :: (Elt a, Elt b, Elt c, Elt d) => (a -> b -> c -> d) -> Array a -> Array b -> Array c -> Array d -- | Apply a worker function to corresponding elements of four arrays. zipWith4 :: (Elt a, Elt b, Elt c, Elt d, Elt e) => (a -> b -> c -> d -> e) -> Array a -> Array b -> Array c -> Array d -> Array e -- | Apply a worker function to corresponding elements of five arrays. zipWith5 :: (Elt a, Elt b, Elt c, Elt d, Elt e, Elt f) => (a -> b -> c -> d -> e -> f) -> Array a -> Array b -> Array c -> Array d -> Array e -> Array f -- | Apply a worker function to corresponding elements of six arrays. zipWith6 :: (Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g) => (a -> b -> c -> d -> e -> f -> g) -> Array a -> Array b -> Array c -> Array d -> Array e -> Array f -> Array g -- | Apply a worker function to corresponding elements of seven arrays. zipWith7 :: (Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h) => (a -> b -> c -> d -> e -> f -> g -> h) -> Array a -> Array b -> Array c -> Array d -> Array e -> Array f -> Array g -> Array h -- | Apply a worker function to corresponding elements of six arrays. zipWith8 :: (Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h, Elt i) => (a -> b -> c -> d -> e -> f -> g -> h -> i) -> Array a -> Array b -> Array c -> Array d -> Array e -> Array f -> Array g -> Array h -> Array i -- | Similar to foldl but return an array of the intermediate -- states, including the final state that is computed by foldl. scan :: Elt a => (a -> a -> a) -> a -> Array a -> Array a -- | Undirected fold over an array. -- -- fold :: Elt a => (a -> a -> a) -> a -> Array a -> a -- | Undirected segmented fold. -- -- All segments are folded individually, and the result contains one -- element for each segment. -- -- Same preconditions as fold. fold_s :: Elt a => (a -> a -> a) -> a -> Segd -> Array a -> Array a -- | Undirected scattered segmented fold. -- -- Like fold_s, but the segments can be scattered through an -- Arrays. -- -- Same preconditions as fold. fold_ss :: (Elts a, Elt a) => (a -> a -> a) -> a -> SSegd -> Arrays a -> Array a -- | Undirected fold over virtual segments. -- -- The physical segments defined by the VSegd are folded -- individually, and these results are replicated according to the -- virtual segment id table of the VSegd. The result contains as -- many elements as there virtual segments. -- -- Same preconditions as fold. fold_vs :: (Elts a, Elt a) => (a -> a -> a) -> a -> VSegd -> Arrays a -> Array a -- | Regular segmented fold. -- -- All segements have the given length. -- -- Same preconditions as fold. fold_r :: Elt a => (a -> a -> a) -> a -> Int -> Array a -> Array a -- | Undirected fold, using the first element to initialise the state. -- -- fold1 :: Elt a => (a -> a -> a) -> Array a -> a -- | Like fold_s, but using the first element of each segment to -- initialise the state of that segment. -- -- Same preconditions as fold1. fold1_s :: Elt a => (a -> a -> a) -> Segd -> Array a -> Array a -- | Like fold_ss, but using the first element of each segment to -- intialise the state of that segment. -- -- Same preconditions as fold1. fold1_ss :: (Elts a, Elt a) => (a -> a -> a) -> SSegd -> Arrays a -> Array a -- | Like fold_vs, but using the first element of each segment to -- initialise the state of that segment. -- -- Same preconditions as fold1. fold1_vs :: (Elts a, Elt a) => (a -> a -> a) -> VSegd -> Arrays a -> Array a -- | Same as fold (+) 0 sum :: (Num a, Elt a) => Array a -> a -- | Same as fold_s (+) 0 sum_s :: (Num a, Elt a) => Segd -> Array a -> Array a -- | Same as fold_ss (+) 0 sum_ss :: (Num a, Elts a, Elt a) => SSegd -> Arrays a -> Array a -- | Same as fold_r (+) 0 sum_r :: (Num a, Elt a) => Int -> Array a -> Array a -- | Count the number of elements in array that are equal to the given -- value. count :: (Elt a, Eq a) => Array a -> a -> Int -- | Segmented count. count_s :: (Elt a, Eq a) => Segd -> Array a -> a -> Array Int -- | Scattered segmented count. -- -- NOTE: This is a transitory interface, and will be removed in future -- versions. count_ss :: (Elt a, Eq a) => SSegd -> Vector (Array a) -> a -> Array Int -- | O(length source). Compute the conjunction of all elements in a boolean -- array. and :: Array Bool -> Bool -- | O(length result). Extract elements of an array where the associated -- flag is true. pack :: Elt a => Array a -> Array Bool -> Array a -- | O(length result). Select the elements of an array that have a -- corresponding tag. -- --
--   packByTag [12, 24, 42, 93] [1, 0, 0, 1] 0 = [24, 42]
--   
packByTag :: Elt a => Array a -> Array Tag -> Tag -> Array a -- | Extract the elements from an array that match the given predicate. filter :: Elt a => (a -> Bool) -> Array a -> Array a -- | Compute an array of flags indicating which elements match a given -- value. -- --
--   pick [4, 5, 3, 6, 5, 2, 5] 5 = [F, T, F, F, T, F, T]
--   
pick :: (Elt a, Eq a) => Array a -> a -> Array Bool -- | Combine two arrays, using a flags array to tell us where to get each -- element from. -- --
--   combine [T, F, F, T, T, F] [1, 2, 3] [4, 5, 6] = [1, 4, 5, 2, 3, 6]
--   
combine :: Elt a => Array Bool -> Array a -> Array a -> Array a -- | Like combine, but use a precomputed selector to speed up the -- process. -- -- See the description of mkSel2 for how this works. combine2 :: Elt a => Array Tag -> SelRep2 -> Array a -> Array a -> Array a -- | Interleave the elements of two arrays. -- --
--   interleave [1, 2, 3] [4, 5, 6] = [1, 4, 2, 5, 3, 6]
--   
interleave :: Elt a => Array a -> Array a -> Array a type Sel2 = USel2 -- | O(1). Construct a selector. -- -- A selector is a description of how to perform a combine -- operation. -- -- Suppose we are evaluating the following expression: -- --
--   combine [F,F,T,F,T,T] [1,2,3] [4,5,6] = [4,5,1,6,2,3]
--   
-- -- This is difficult to parallelise. For each element in the result, the -- source array we get this element from depends on the tag values -- associated with all previous elements. -- -- However, if we going to apply combine several times with the -- same flags array, we can precompute a selector that tells us where to -- get each element. The selector contains the original flags, as well as -- the source index telling us where to get each element for the result -- array. -- -- For example: -- --
--   tagsToIndices2 [F,F,T,F,T,T]   -- tags
--                = [0,1,0,2,1,2]   -- indices
--   
-- -- This says get the first element from index 0 in the second array, then -- from index 1 in the second array, then index 0 in the first array ... -- -- The selector then consists of both the tag and -- indices arrays. mkSel2 :: Array Tag -> Array Int -> Int -> Int -> SelRep2 -> Sel2 -- | O(1). Yield the tags array of a selector. tagsSel2 :: Sel2 -> Array Tag -- | O(1). Yield the indices array of a selector. indicesSel2 :: Sel2 -> Array Int -- | O(1). Yield the number of elements that will be taken from the first -- array. elementsSel2_0 :: Sel2 -> Int -- | O(1). Yield the number of elements that will be taken from the second -- array. elementsSel2_1 :: Sel2 -> Int -- | O(1). Yield the parallel representation of a selector. repSel2 :: Sel2 -> SelRep2 -- | O(n). Compute a selector from a tags array. tagsToSel2 :: Array Tag -> Sel2 type SelRep2 = () -- | O(n). Construct a parallel selector representation. -- -- A SelRep2 describes how to distribute the two data vectors -- corresponding to a Sel2 across several PEs. -- -- Suppose we want to perform the following combine operation: -- --
--   combine [F,F,T,T,F,T,F,F,T] [A0,A1,A2,A3,A4] [B0,B1,B2,B3] 
--     = [A0,A1,B0,B1,A2,B2,A3,A4,B3]
--   
-- -- The first array is the flags array, that says which of the data arrays -- to get each successive element from. As combine is difficult to -- compute in parallel, if we are going to perform several combines with -- the same flags array, we can precompute a selector that tells us where -- to get each element. The selector contains the original flags, as well -- as the source index telling us where to get each element for the -- result array. -- --
--   flags:   [F,F,T,T,F,T,F,F,T]
--   indices: [0,1,0,1,2,2,3,4,3]
--   
-- -- Suppose we want to distribute the combine operation across 3 PEs. It's -- easy to split the selector like so: -- --
--              PE0                PE1               PE2
--   flags:   [F,F,T]            [T,F,T]           [F,F,T] 
--   indices: [0,1,0]            [1,2,2]           [3,4,3]
--   
-- -- We now need to split the two data arrays. Each PE needs slices of the -- data arrays that correspond to the parts of the selector that were -- given to it. For the current example we get: -- --
--              PE0                PE1               PE2
--   data_A:   [A0,A1]            [A2]              [A3,A4]
--   data_B:   [B0]               [B1,B2]           [B3]
--   
-- -- The SelRep2 contains the starting index and length of each of -- of these slices: -- --
--         PE0                PE1               PE2
--   ((0, 0), (2, 1))   ((2, 1), (1, 2))  ((3, 3), (2, 1))
--    indices   lens      indices  lens    indices  lens
--   
mkSelRep2 :: Array Tag -> SelRep2 -- | O(1). Take the indices field from a SelRep2. indicesSelRep2 :: Array Tag -> SelRep2 -> Array Int -- | O(1). Yield the number of elements to take from the first array. elementsSelRep2_0 :: Array Tag -> SelRep2 -> Int -- | O(1). Yield the number of elements to take from the second array. elementsSelRep2_1 :: Array Tag -> SelRep2 -> Int type Segd = USegd -- | O(max(segs, threads) . log segs). Construct a segment descriptor. -- -- A segment desciptor defines an irregular 2D array based on a flat, 1D -- array of elements. The defined array is a nested array of segments, -- where every segment covers some of the elements from the flat array. -- -- -- -- Example: -- --
--   flat array data: [1 2 3 4 5 6 7 8]
--     (segmentation)  --- ----- - ---
--     segd  lengths: [2, 3, 1, 2]
--           indices: [0, 2, 5, 6]
--          elements: 8 
--   
mkSegd :: Array Int -> Array Int -> Int -> Segd -- | Check whether a Segd is well formed. validSegd :: Segd -> Bool -- | O(1). Construct an empty Segd. emptySegd :: Segd -- | O(1). Construct a Segd containing a single segment of the given -- length. singletonSegd :: Int -> Segd -- | O(max(segs, threads) . log segs). Construct a Segd from an -- array of segment lengths. lengthsToSegd :: Array Int -> Segd -- | O(1). Yield the length of a Segd. lengthSegd :: Segd -> Int -- | O(1). Yield the segment lengths of a Segd. lengthsSegd :: Segd -> Array Int -- | O(1). Yield the segment starting indices of a Segd. indicesSegd :: Segd -> Array Int -- | O(1). Yield the total number of elements defined by a Segd. elementsSegd :: Segd -> Int -- | O(max(segs, threads) . log segs). Add the lengths of corresponding -- segments in two descriptors. -- --
--   plusSegd [lens: 2 3 1] [lens: 3 1 1] = [lens: 5 4 2]
--   
plusSegd :: Segd -> Segd -> Segd type SSegd = USSegd -- | Construct a Scattered Segment Descriptor. -- -- A SSegd is an extension of a Segd that that allows the -- segments to be scattered through multiple flat arrays. -- -- Each segment is associated with a source id that indicates what flat -- array it is in, along with the starting index in that flat array. -- -- mkSSegd :: Array Int -> Array Int -> Segd -> SSegd -- | Check whether a Segd is well formed. validSSegd :: SSegd -> Bool -- | O(1). Construct an empty SSegd. emptySSegd :: SSegd -- | O(1). Construct a Segd containing a single segment of the given -- length. singletonSSegd :: Int -> SSegd -- | O(segs). Promote a Segd to a SSegd, assuming all -- segments are contiguous and come from a single array. promoteSegdToSSegd :: Segd -> SSegd -- | O(1). True when a SSegd has been constructed by promoting a -- SSegd. -- -- In this case all the data elements are in one contiguous flat array, -- and consumers can avoid looking at the real starts and sources fields. isContiguousSSegd :: SSegd -> Bool -- | O(1). Yield the length of a SSegd. lengthOfSSegd :: SSegd -> Int -- | O(1). Yield the segment lengths of a SSegd. lengthsOfSSegd :: SSegd -> Array Int -- | O(1). Yield the indices field of a SSegd. indicesOfSSegd :: SSegd -> Array Int -- | O(1). Yield the starts field of a SSegd. startsOfSSegd :: SSegd -> Array Int -- | O(1). Yield the sources field of a SSegd. sourcesOfSSegd :: SSegd -> Array Int -- | O(1). Get the length, segment index, starting index, and source id of -- a segment. getSegOfSSegd :: SSegd -> Int -> (Int, Int, Int, Int) -- | Produce a segment descriptor that describes the result of appending -- two segmented arrays. appendSSegd :: SSegd -> Int -> SSegd -> Int -> SSegd type VSegd = UVSegd -- | Construct a Virtual Segment Descriptor. -- -- A VSegd is an extension of a SSegd that allows data from -- the underlying flat array to be shared between segments. For example, -- you can define an array of 10 virtual segments that all have the same -- length and elements as a single physical segment. -- -- mkVSegd :: Array Int -> SSegd -> VSegd -- | Check whether a Segd is well formed. validVSegd :: VSegd -> Bool -- | O(1). Construct an empty SSegd. emptyVSegd :: VSegd -- | O(1). Construct a VSegd containing a single segment of the -- given length. singletonVSegd :: Int -> VSegd -- | O(len). Construct a VSegd that describes an array where all -- virtual segments point to the same physical segment. replicatedVSegd :: Int -> Int -> VSegd -- | O(segs). Promote a plain Segd to a VSegd. -- -- The result contains one virtual segment for every physical segment the -- provided Segd. promoteSegdToVSegd :: Segd -> VSegd -- | O(segs). Promote a plain SSegd to a VSegd. -- -- The result contains one virtual segment for every physical segment the -- provided SSegd. promoteSSegdToVSegd :: SSegd -> VSegd -- | O(1). If true then the segments are all unshared, and the -- vsegids field be just [0..len-1]. -- -- Consumers can check this field to avoid demanding the vsegids -- field. This can avoid the need for it to be constructed in the first -- place, due to lazy evaluation. isManifestVSegd :: VSegd -> Bool -- | O(1). If true then the starts field is identical to the -- indices field and the sourceids are all 0s. -- -- In this case all the data elements are in one contiguous flat array, -- and consumers can avoid looking at the real starts and sources fields. isContiguousVSegd :: VSegd -> Bool -- | O(1). Yield the length of a VSegd. lengthOfVSegd :: VSegd -> Int -- | O(1). Yield the vsegids of a VSegd. takeVSegidsOfVSegd :: VSegd -> Array Int -- | O(1). Yield the vsegids of a VSegd, but don't require that -- every physical segment is referenced by some virtual segment. -- -- If you're just performing indexing and don't need the invariant that -- all physical segments are reachable from some virtual segment, then -- use this version as it's faster. This sidesteps the code that -- maintains the invariant. -- -- The stated O(1) complexity assumes that the array has already been -- fully evalauted. If this is not the case then we can avoid demanding -- the result of a prior computation on the vsegids, thus -- reducing the cost attributed to that prior computation. takeVSegidsRedundantOfVSegd :: VSegd -> Array Int -- | O(1). Yield the SSegd of a VSegd. takeSSegdOfVSegd :: VSegd -> SSegd -- | O(1). Yield the SSegd of a VSegd, but don't require that -- every physical segment is referenced by some virtual segment. -- -- See the note in takeVSegidsRedundantOfVSegd. takeSSegdRedundantOfVSegd :: VSegd -> SSegd -- | O(1). Yield the segment lengths of a VSegd. takeLengthsOfVSegd :: VSegd -> Array Int -- | O(1). Get the length, starting index, and source id of a segment. getSegOfVSegd :: VSegd -> Int -> (Int, Int, Int) -- | O(segs). Yield a SSegd that describes each segment of a -- VSegd individually. -- -- By doing this we lose information about which virtual segments -- correspond to the same physical segments. -- -- WARNING: Trying to take the SSegd of a nested array that -- has been constructed with replication can cause index space overflow. -- This is because the virtual size of the corresponding flat data can be -- larger than physical memory. If this happens then indices fields and -- element count in the result will be invalid. unsafeDemoteToSSegdOfVSegd :: VSegd -> SSegd -- | O(segs). Yield a Segd that describes each segment of a -- VSegd individually. -- -- By doing this we lose information about which virtual segments -- correspond to the same physical segments. -- -- See the warning in unsafeDemoteToSSegdOfVSegd. unsafeDemoteToSegdOfVSegd :: VSegd -> Segd -- | Update the vsegids of a VSegd, and then cull the -- physical segment descriptor so that all physical segments are -- reachable from some virtual segment. updateVSegsOfVSegd :: (Array Int -> Array Int) -> VSegd -> VSegd -- | Update the vsegids of VSegd, where the result is -- guaranteed to cover all physical segments. -- -- Using this version avoids performing the cull operation which -- discards unreachable physical segments. -- -- updateVSegsReachableOfVSegd :: (Array Int -> Array Int) -> VSegd -> VSegd -- | Produce a virtual segment descriptor that describes the result of -- appending two segmented arrays. appendVSegd :: VSegd -> Int -> VSegd -> Int -> VSegd -- | Combine two virtual segment descriptors. combine2VSegd :: Sel2 -> VSegd -> Int -> VSegd -> Int -> VSegd class Unboxes a => Elts a type Arrays = Vectors -- | O(1). Construct an empty Arrays with no elements. emptys :: Arrays a -- | O(1). Construct an Arrays consisting of a single Array. singletons :: (Elt a, Elts a) => Array a -> Arrays a -- | O(1). Yield the number of Array in an Arrays. lengths :: Elts a => Arrays a -> Int -- | O(1). Take one of the outer Array from an Arrays. unsafeIndexs :: (Elt a, Elts a) => Arrays a -> Int -> Array a -- | O(1). Retrieve a single element from an Arrays, given the outer -- and inner indices. unsafeIndex2s :: (Elt a, Elts a) => Arrays a -> Int -> Int -> a -- | O(n). Append two Arrays, using work proportional to the length -- of the outer array. appends :: (Elt a, Elts a) => Arrays a -> Arrays a -> Arrays a -- | O(number of inner arrays). Convert a boxed vector of Array to -- an Arrays. fromVectors :: (Elt a, Elts a) => Vector (Array a) -> Arrays a -- | O(number of inner arrays). Convert an Arrays to a boxed vector -- of Array. toVectors :: (Elt a, Elts a) => Arrays a -> Vector (Array a) -- | Generate an array of the given length full of random data. Good for -- testing. randoms :: (Elt a, Random a, RandomGen g) => Int -> g -> Array a -- | Generate an array of the given length full of random data. Good for -- testing. randomRs :: (Elt a, Random a, RandomGen g) => Int -> (a, a) -> g -> Array a class UIO a => IOElt a -- | Read an array from a file. hGet :: IOElt a => Handle -> IO (Array a) -- | Write an array to a file. hPut :: IOElt a => Handle -> Array a -> IO () -- | Convert an array to a list of elements. toList :: Elt a => Array a -> [a] -- | Convert a list of elements to an array. fromList :: Elt a => [a] -> Array a instance (IOElt a, IOElt b) => IOElt (a, b) instance IOElt Double instance IOElt Int instance Elts Double instance Elts Float instance Elts Word8 instance Elts Int instance (Elt a, Elt b) => Elt (a, b) instance Elt Double instance Elt Float instance Elt Bool instance Elt Word8 instance Elt Int