dph-prim-seq-0.6.1.1: Data Parallel Haskell segmented arrays. (sequential implementation)

Safe HaskellSafe-Infered

Data.Array.Parallel.Unlifted.Sequential.UVSegd

Contents

Description

Virtual Segment Descriptors.

See Data.Array.Parallel.Unlifted for how this works.

Synopsis

Types

data UVSegd Source

Virtual segment descriptor.

Constructors

UVSegd 

Fields

uvsegd_manifest :: !Bool

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_vsegids_redundant :: Vector Int

Virtual segment identifiers that indicate what physical segment to use for each virtual segment.

uvsegd_vsegids_culled :: Vector Int
 
uvsegd_ussegd_redundant :: USSegd

Scattered segment descriptor that defines how physical segments are layed out in memory.

uvsegd_ussegd_culled :: USSegd
 

Consistency check

valid :: UVSegd -> BoolSource

O(1). Check the internal consistency of a virutal segmentation descriptor.

Constructors

mkUVSegdSource

Arguments

:: Vector Int

(vsegids) Mapping from virtual to physical segments.

-> USSegd

Scattered Segment descriptor defining the physical segments.

-> UVSegd 

O(1). Construct a new virtual segment descriptor. All the provided arrays must have the same lengths.

fromUSegd :: USegd -> UVSegdSource

O(segs). Promote a plain Segd to a VSegd.

The result contains one virtual segment for every physical segment the provided SSegd.

fromUSSegd :: USSegd -> UVSegdSource

O(segs). Promote a plain USegd to a UVSegd.

The result contains one virtual segment for every physical segment the provided Segd.

empty :: UVSegdSource

O(1). Construct an empty segment descriptor, with no elements or segments.

singleton :: Int -> UVSegdSource

O(1). Construct a singleton segment descriptor. The single segment covers the given number of elements in a flat array with sourceid 0.

replicatedSource

Arguments

:: Int

Length of segment.

-> Int

Number of times replicated.

-> UVSegd 

O(1). Construct a UVSegd that describes an array created by replicating a single segment several times.

Predicates

isManifest :: UVSegd -> BoolSource

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.

isContiguous :: UVSegd -> BoolSource

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.

Projections

length :: UVSegd -> IntSource

O(1). Yield the overall number of segments described by a UVSegd.

takeVSegids :: UVSegd -> Vector IntSource

O(1). Yield the vsegids of a UVSegd

takeVSegidsRedundant :: UVSegd -> Vector IntSource

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.

takeUSSegd :: UVSegd -> USSegdSource

O(1). Yield the USSegd of a UVSegd.

takeUSSegdRedundant :: UVSegd -> USSegdSource

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.

takeLengths :: UVSegd -> Vector IntSource

O(segs). Yield the lengths of the segments described by a UVSegd.

getSeg :: UVSegd -> Int -> (Int, Int, Int)Source

O(1). Get the length, starting index, and source id of a segment.

Operators

appendWithSource

Arguments

:: UVSegd

Descriptor of first array.

-> Int

Number of flat physical arrays for first descriptor.

-> UVSegd

Descriptor of second array.

-> Int

Number of flat physical arrays for second descriptor.

-> UVSegd 

O(n) Produce a segment descriptor describing the result of appending two arrays.

combine2Source

Arguments

:: USel2

Selector for the combine operation.

-> UVSegd

Descriptor of first array.

-> Int

Number of flat physical arrays for first descriptor.

-> UVSegd

Descriptor of second array.

-> Int

Number of flat physical arrays for second descriptor.

-> UVSegd 

O(n). Combine two virtual segment descriptors.

updateVSegs :: (Vector Int -> Vector Int) -> UVSegd -> UVSegdSource

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.

updateVSegsReachable :: (Vector Int -> Vector Int) -> UVSegd -> UVSegdSource

Update the vsegids of UPVSegd, where the result covers all physical segments.

  • The resulting vsegids must cover all physical segments. If they do not then there will be physical segments that are not reachable from some virtual segment, and performing operations like segmented fold will waste work.
  • Using this version saves performing the cull operation which discards unreachable physical segments. This is O(result segments), but can be expensive in absolute terms.

unsafeDemoteToUSSegd :: UVSegd -> USSegdSource

O(segs). Yield a USSegd that describes each segment of a UVSegd individually.

  • By doing this we lose information about virtual segments corresponding to the same physical segments.
  • This operation is used in concatPR as the first step in eliminating segmentation from a nested array.

unsafeDemoteToUSegd :: UVSegd -> USegdSource

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.