PrimitiveArray-0.6.1.0: Efficient multidimensional arrays

Safe HaskellNone
LanguageHaskell2010

Data.PrimitiveArray.Index.Class

Synopsis

Documentation

data a :. b infixl 3 Source

Strict pairs -- as in repa.

Constructors

!a :. !b infixl 3 

Instances

(Unbox a0, Unbox b0) => Vector Vector ((:.) a b) 
(Unbox a0, Unbox b0) => MVector MVector ((:.) a b) 
(Functor m, Applicative m, Monad m, PrimMonad m, FreezeTables m ts, PrimArrayOps arr sh elm) => FreezeTables m ((:.) ts (MutArr m (arr sh elm))) 
(WriteCell m cs sh, Monad m, MPrimArrayOps arr sh a, PrimMonad m) => WriteCell m ((:.) cs (MutArr m (arr sh a), sh -> m a)) sh 
(Eq a, Eq b) => Eq ((:.) a b) 
(Ord a, Ord b) => Ord ((:.) a b) 
(Read a, Read b) => Read ((:.) a b) 
(Show a, Show b) => Show ((:.) a b) 
Generic ((:.) a b) 
(Arbitrary a, Arbitrary b) => Arbitrary ((:.) a b) 
(ToJSON a, ToJSON b) => ToJSON ((:.) a b) 
(FromJSON a, FromJSON b) => FromJSON ((:.) a b) 
(Binary a, Binary b) => Binary ((:.) a b) 
(Serialize a, Serialize b) => Serialize ((:.) a b) 
(NFData a, NFData b) => NFData ((:.) a b) 
(Unbox a0, Unbox b0) => Unbox ((:.) a b) 
IndexStream z => IndexStream ((:.) z Int) 
IndexStream z => IndexStream ((:.) z (PInt p)) 
IndexStream z => IndexStream ((:.) z PointL) 
IndexStream z => IndexStream ((:.) z ((:>) ((:>) BitSet (Interface i)) (Interface j))) 
IndexStream z => IndexStream ((:.) z ((:>) BitSet (Interface i))) 
IndexStream z => IndexStream ((:.) z BitSet) 
IndexStream z => IndexStream ((:.) z Subword) 
(Index zs, Index z) => Index ((:.) zs z) 
data MVector s0 ((:.) a0 b0) = MV_StrictPair (MVector s (a, b)) 
type Rep ((:.) a b) 
data Vector ((:.) a0 b0) = V_StrictPair (Vector (a, b)) 
type Frozen ((:.) ts (MutArr m (arr sh elm))) = (:.) (Frozen ts) (arr sh elm) 

data a :> b infixl 3 Source

A different version of strict pairs. Makes for simpler type inference in multi-tape grammars. We use :> when we have special needs, like non-recursive instances on inductives tuples, as used for set indices.

Constructors

!a :> !b infixl 3 

Instances

(Unbox a0, Unbox b0) => Vector Vector ((:>) a b) 
(Unbox a0, Unbox b0) => MVector MVector ((:>) a b) 
SetPredSucc (Fixed ((:>) ((:>) BitSet (Interface i)) (Interface j))) 
SetPredSucc (Fixed ((:>) BitSet (Interface i))) 
(Eq a, Eq b) => Eq ((:>) a b) 
(Ord a, Ord b) => Ord ((:>) a b) 
(Read a, Read b) => Read ((:>) a b) 
(Show a, Show b) => Show ((:>) a b) 
Generic ((:>) a b) 
Arbitrary ((:>) ((:>) BitSet (Interface i)) (Interface j)) 
Arbitrary ((:>) BitSet (Interface i)) 
(ToJSON a, ToJSON b) => ToJSON ((:>) a b) 
(FromJSON a, FromJSON b) => FromJSON ((:>) a b) 
(Binary a, Binary b) => Binary ((:>) a b) 
(Serialize a, Serialize b) => Serialize ((:>) a b) 
(NFData a, NFData b) => NFData ((:>) a b) 
(Unbox a0, Unbox b0) => Unbox ((:>) a b) 
IndexStream z => IndexStream ((:.) z ((:>) ((:>) BitSet (Interface i)) (Interface j))) 
IndexStream z => IndexStream ((:.) z ((:>) BitSet (Interface i))) 
(Index zs, Index z) => Index ((:>) zs z) 
ApplyMask ((:>) ((:>) BitSet (Interface i)) (Interface j)) 
ApplyMask ((:>) BitSet (Interface i)) 
SetPredSucc ((:>) ((:>) BitSet (Interface i)) (Interface j)) 
SetPredSucc ((:>) BitSet (Interface i)) 
data MVector s0 ((:>) a0 b0) = MV_StrictIxPair (MVector s (a, b)) 
type Rep ((:>) a b) 
data Vector ((:>) a0 b0) = V_StrictIxPair (Vector (a, b)) 
type Mask ((:>) ((:>) BitSet (Interface i)) (Interface j)) = BitSet 
type Mask ((:>) BitSet (Interface i)) = BitSet 

data Z Source

Base data constructor for multi-dimensional indices.

Constructors

Z 

Instances

class Index i where Source

Index structures for complex, heterogeneous indexing. Mostly designed for indexing in DP grammars, where the indices work for linear and context-free grammars on one or more tapes, for strings, sets, later on tree structures.

Methods

linearIndex :: i -> i -> i -> Int Source

Given a minimal size, a maximal size, and a current index, calculate the linear index.

smallestLinearIndex :: i -> Int Source

Given an index element from the smallest subset, calculate the highest linear index that is *not* stored.

largestLinearIndex :: i -> Int Source

Given an index element from the largest subset, calculate the highest linear index that *is* stored.

size :: i -> i -> Int Source

Given smallest and largest index, return the number of cells required for storage.

inBounds :: i -> i -> i -> Bool Source

Check if an index is within the bounds.

Instances

class IndexStream i where Source

Generate a stream of indices in correct order for dynamic programming. Since the stream generators require concatMap / flatten we have to write more specialized code for (z:.IX) stuff.

Minimal complete definition

Nothing

Methods

streamUp :: Monad m => i -> i -> Stream m i Source

This generates an index stream suitable for forward structure filling. The first index is the smallest (or the first indices considered are all equally small in partially ordered sets). Larger indices follow up until the largest one.

streamDown :: Monad m => i -> i -> Stream m i Source

If streamUp generates indices from smallest to largest, then streamDown generates indices from largest to smallest. Outside grammars make implicit use of this. Asking for an axiom in backtracking requests the first element from this stream.