PrimitiveArray-0.8.0.1: 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 ((:.) a0 b0) Source # 

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (a0 :. b0) -> m (Vector (a0 :. b0)) #

basicUnsafeThaw :: PrimMonad m => Vector (a0 :. b0) -> m (Mutable Vector (PrimState m) (a0 :. b0)) #

basicLength :: Vector (a0 :. b0) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (a0 :. b0) -> Vector (a0 :. b0) #

basicUnsafeIndexM :: Monad m => Vector (a0 :. b0) -> Int -> m (a0 :. b0) #

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (a0 :. b0) -> Vector (a0 :. b0) -> m () #

elemseq :: Vector (a0 :. b0) -> (a0 :. b0) -> b -> b #

(Unbox a0, Unbox b0) => MVector MVector ((:.) a0 b0) Source # 

Methods

basicLength :: MVector s (a0 :. b0) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (a0 :. b0) -> MVector s (a0 :. b0) #

basicOverlaps :: MVector s (a0 :. b0) -> MVector s (a0 :. b0) -> Bool #

basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) (a0 :. b0)) #

basicInitialize :: PrimMonad m => MVector (PrimState m) (a0 :. b0) -> m () #

basicUnsafeReplicate :: PrimMonad m => Int -> (a0 :. b0) -> m (MVector (PrimState m) (a0 :. b0)) #

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (a0 :. b0) -> Int -> m (a0 :. b0) #

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (a0 :. b0) -> Int -> (a0 :. b0) -> m () #

basicClear :: PrimMonad m => MVector (PrimState m) (a0 :. b0) -> m () #

basicSet :: PrimMonad m => MVector (PrimState m) (a0 :. b0) -> (a0 :. b0) -> m () #

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (a0 :. b0) -> MVector (PrimState m) (a0 :. b0) -> m () #

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (a0 :. b0) -> MVector (PrimState m) (a0 :. b0) -> m () #

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (a0 :. b0) -> Int -> m (MVector (PrimState m) (a0 :. b0)) #

(Functor m, Applicative m, Monad m, PrimMonad m, FreezeTables m ts, PrimArrayOps arr sh elm) => FreezeTables m ((:.) ts (MutArr m (arr sh elm))) Source # 

Associated Types

type Frozen ((:.) ts (MutArr m (arr sh elm))) :: * Source #

Methods

freezeTables :: (ts :. MutArr m (arr sh elm)) -> m (Frozen (ts :. MutArr m (arr sh elm))) Source #

(WriteCell m cs sh, Monad m, MPrimArrayOps arr sh a, PrimMonad m) => WriteCell m ((:.) cs (MutArr m (arr sh a), sh -> m a)) sh Source # 

Methods

unsafeWriteCell :: (cs :. (MutArr m (arr sh a), sh -> m a)) -> sh -> m () Source #

writeCell :: (cs :. (MutArr m (arr sh a), sh -> m a)) -> sh -> m () Source #

(Eq b, Eq a) => Eq ((:.) a b) Source # 

Methods

(==) :: (a :. b) -> (a :. b) -> Bool #

(/=) :: (a :. b) -> (a :. b) -> Bool #

(Ord b, Ord a) => Ord ((:.) a b) Source # 

Methods

compare :: (a :. b) -> (a :. b) -> Ordering #

(<) :: (a :. b) -> (a :. b) -> Bool #

(<=) :: (a :. b) -> (a :. b) -> Bool #

(>) :: (a :. b) -> (a :. b) -> Bool #

(>=) :: (a :. b) -> (a :. b) -> Bool #

max :: (a :. b) -> (a :. b) -> a :. b #

min :: (a :. b) -> (a :. b) -> a :. b #

(Read a, Read b) => Read ((:.) a b) Source # 

Methods

readsPrec :: Int -> ReadS (a :. b) #

readList :: ReadS [a :. b] #

readPrec :: ReadPrec (a :. b) #

readListPrec :: ReadPrec [a :. b] #

(Show b, Show a) => Show ((:.) a b) Source # 

Methods

showsPrec :: Int -> (a :. b) -> ShowS #

show :: (a :. b) -> String #

showList :: [a :. b] -> ShowS #

Generic ((:.) a b) Source # 

Associated Types

type Rep ((:.) a b) :: * -> * #

Methods

from :: (a :. b) -> Rep (a :. b) x #

to :: Rep (a :. b) x -> a :. b #

(Arbitrary a, Arbitrary b) => Arbitrary ((:.) a b) Source # 

Methods

arbitrary :: Gen (a :. b) #

shrink :: (a :. b) -> [a :. b] #

(Hashable a, Hashable b) => Hashable ((:.) a b) Source # 

Methods

hashWithSalt :: Int -> (a :. b) -> Int #

hash :: (a :. b) -> Int #

(ToJSON a, ToJSON b) => ToJSON ((:.) a b) Source # 

Methods

toJSON :: (a :. b) -> Value #

toEncoding :: (a :. b) -> Encoding #

toJSONList :: [a :. b] -> Value #

toEncodingList :: [a :. b] -> Encoding #

(ToJSON a, ToJSONKey a, ToJSON b, ToJSONKey b) => ToJSONKey ((:.) a b) Source # 
(FromJSON a, FromJSON b) => FromJSON ((:.) a b) Source # 

Methods

parseJSON :: Value -> Parser (a :. b) #

parseJSONList :: Value -> Parser [a :. b] #

(FromJSON a, FromJSONKey a, FromJSON b, FromJSONKey b) => FromJSONKey ((:.) a b) Source # 
(Binary a, Binary b) => Binary ((:.) a b) Source # 

Methods

put :: (a :. b) -> Put #

get :: Get (a :. b) #

putList :: [a :. b] -> Put #

(Serialize a, Serialize b) => Serialize ((:.) a b) Source # 

Methods

put :: Putter (a :. b) #

get :: Get (a :. b) #

(NFData a, NFData b) => NFData ((:.) a b) Source # 

Methods

rnf :: (a :. b) -> () #

(Unbox a0, Unbox b0) => Unbox ((:.) a0 b0) Source # 
IndexStream z => IndexStream ((:.) z (EdgeBoundary C)) Source #

EdgeBoundary C (complement)

IndexStream z => IndexStream ((:.) z (EdgeBoundary O)) Source #

EdgeBoundary O (outside).

Note: streamUp really needs to use streamDownMk / streamDownStep for the right order of indices!

IndexStream z => IndexStream ((:.) z (EdgeBoundary I)) Source #

EdgeBoundary I (inside)

IndexStream z => IndexStream ((:.) z (PInt C p)) Source # 

Methods

streamUp :: Monad m => (z :. PInt C p) -> (z :. PInt C p) -> Stream m (z :. PInt C p) Source #

streamDown :: Monad m => (z :. PInt C p) -> (z :. PInt C p) -> Stream m (z :. PInt C p) Source #

IndexStream z => IndexStream ((:.) z (PInt O p)) Source # 

Methods

streamUp :: Monad m => (z :. PInt O p) -> (z :. PInt O p) -> Stream m (z :. PInt O p) Source #

streamDown :: Monad m => (z :. PInt O p) -> (z :. PInt O p) -> Stream m (z :. PInt O p) Source #

IndexStream z => IndexStream ((:.) z (PInt I p)) Source # 

Methods

streamUp :: Monad m => (z :. PInt I p) -> (z :. PInt I p) -> Stream m (z :. PInt I p) Source #

streamDown :: Monad m => (z :. PInt I p) -> (z :. PInt I p) -> Stream m (z :. PInt I p) Source #

IndexStream z => IndexStream ((:.) z (PointL C)) Source # 

Methods

streamUp :: Monad m => (z :. PointL C) -> (z :. PointL C) -> Stream m (z :. PointL C) Source #

streamDown :: Monad m => (z :. PointL C) -> (z :. PointL C) -> Stream m (z :. PointL C) Source #

IndexStream z => IndexStream ((:.) z (PointL O)) Source # 

Methods

streamUp :: Monad m => (z :. PointL O) -> (z :. PointL O) -> Stream m (z :. PointL O) Source #

streamDown :: Monad m => (z :. PointL O) -> (z :. PointL O) -> Stream m (z :. PointL O) Source #

IndexStream z => IndexStream ((:.) z (PointL I)) Source # 

Methods

streamUp :: Monad m => (z :. PointL I) -> (z :. PointL I) -> Stream m (z :. PointL I) Source #

streamDown :: Monad m => (z :. PointL I) -> (z :. PointL I) -> Stream m (z :. PointL I) Source #

IndexStream z => IndexStream ((:.) z (Boundary k I)) Source # 

Methods

streamUp :: Monad m => (z :. Boundary k I) -> (z :. Boundary k I) -> Stream m (z :. Boundary k I) Source #

streamDown :: Monad m => (z :. Boundary k I) -> (z :. Boundary k I) -> Stream m (z :. Boundary k I) Source #

IndexStream z => IndexStream ((:.) z (BS2 i j C)) Source # 

Methods

streamUp :: Monad m => (z :. BS2 i j C) -> (z :. BS2 i j C) -> Stream m (z :. BS2 i j C) Source #

streamDown :: Monad m => (z :. BS2 i j C) -> (z :. BS2 i j C) -> Stream m (z :. BS2 i j C) Source #

IndexStream z => IndexStream ((:.) z (BS2 i j O)) Source # 

Methods

streamUp :: Monad m => (z :. BS2 i j O) -> (z :. BS2 i j O) -> Stream m (z :. BS2 i j O) Source #

streamDown :: Monad m => (z :. BS2 i j O) -> (z :. BS2 i j O) -> Stream m (z :. BS2 i j O) Source #

IndexStream z => IndexStream ((:.) z (BS2 i j I)) Source # 

Methods

streamUp :: Monad m => (z :. BS2 i j I) -> (z :. BS2 i j I) -> Stream m (z :. BS2 i j I) Source #

streamDown :: Monad m => (z :. BS2 i j I) -> (z :. BS2 i j I) -> Stream m (z :. BS2 i j I) Source #

IndexStream z => IndexStream ((:.) z (BS1 i C)) Source # 

Methods

streamUp :: Monad m => (z :. BS1 i C) -> (z :. BS1 i C) -> Stream m (z :. BS1 i C) Source #

streamDown :: Monad m => (z :. BS1 i C) -> (z :. BS1 i C) -> Stream m (z :. BS1 i C) Source #

IndexStream z => IndexStream ((:.) z (BS1 i O)) Source # 

Methods

streamUp :: Monad m => (z :. BS1 i O) -> (z :. BS1 i O) -> Stream m (z :. BS1 i O) Source #

streamDown :: Monad m => (z :. BS1 i O) -> (z :. BS1 i O) -> Stream m (z :. BS1 i O) Source #

IndexStream z => IndexStream ((:.) z (BS1 i I)) Source # 

Methods

streamUp :: Monad m => (z :. BS1 i I) -> (z :. BS1 i I) -> Stream m (z :. BS1 i I) Source #

streamDown :: Monad m => (z :. BS1 i I) -> (z :. BS1 i I) -> Stream m (z :. BS1 i I) Source #

IndexStream z => IndexStream ((:.) z (BitSet C)) Source # 

Methods

streamUp :: Monad m => (z :. BitSet C) -> (z :. BitSet C) -> Stream m (z :. BitSet C) Source #

streamDown :: Monad m => (z :. BitSet C) -> (z :. BitSet C) -> Stream m (z :. BitSet C) Source #

IndexStream z => IndexStream ((:.) z (BitSet O)) Source # 

Methods

streamUp :: Monad m => (z :. BitSet O) -> (z :. BitSet O) -> Stream m (z :. BitSet O) Source #

streamDown :: Monad m => (z :. BitSet O) -> (z :. BitSet O) -> Stream m (z :. BitSet O) Source #

IndexStream z => IndexStream ((:.) z (BitSet I)) Source # 

Methods

streamUp :: Monad m => (z :. BitSet I) -> (z :. BitSet I) -> Stream m (z :. BitSet I) Source #

streamDown :: Monad m => (z :. BitSet I) -> (z :. BitSet I) -> Stream m (z :. BitSet I) Source #

IndexStream z => IndexStream ((:.) z (Subword C)) Source #

Subword C (complement)

Methods

streamUp :: Monad m => (z :. Subword C) -> (z :. Subword C) -> Stream m (z :. Subword C) Source #

streamDown :: Monad m => (z :. Subword C) -> (z :. Subword C) -> Stream m (z :. Subword C) Source #

IndexStream z => IndexStream ((:.) z (Subword O)) Source #

Subword O (outside).

Note: streamUp really needs to use streamDownMk / streamDownStep for the right order of indices!

Methods

streamUp :: Monad m => (z :. Subword O) -> (z :. Subword O) -> Stream m (z :. Subword O) Source #

streamDown :: Monad m => (z :. Subword O) -> (z :. Subword O) -> Stream m (z :. Subword O) Source #

IndexStream z => IndexStream ((:.) z (Subword I)) Source #

Subword I (inside)

Methods

streamUp :: Monad m => (z :. Subword I) -> (z :. Subword I) -> Stream m (z :. Subword I) Source #

streamDown :: Monad m => (z :. Subword I) -> (z :. Subword I) -> Stream m (z :. Subword I) Source #

IndexStream z => IndexStream ((:.) z (Unit t)) Source # 

Methods

streamUp :: Monad m => (z :. Unit t) -> (z :. Unit t) -> Stream m (z :. Unit t) Source #

streamDown :: Monad m => (z :. Unit t) -> (z :. Unit t) -> Stream m (z :. Unit t) Source #

(Index zs, Index z) => Index ((:.) zs z) Source # 

Methods

linearIndex :: (zs :. z) -> (zs :. z) -> (zs :. z) -> Int Source #

smallestLinearIndex :: (zs :. z) -> Int Source #

largestLinearIndex :: (zs :. z) -> Int Source #

size :: (zs :. z) -> (zs :. z) -> Int Source #

inBounds :: (zs :. z) -> (zs :. z) -> (zs :. z) -> Bool Source #

data MVector s ((:.) a0 b0) Source # 
data MVector s ((:.) a0 b0) = MV_StrictPair (MVector s (a, b))
type Rep ((:.) a b) Source # 
type Rep ((:.) a b) = D1 (MetaData ":." "Data.PrimitiveArray.Index.Class" "PrimitiveArray-0.8.0.1-H8L9mO6Qdgd6EjLRyswnkq" False) (C1 (MetaCons ":." (InfixI LeftAssociative 3) False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 a)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 b))))
data Vector ((:.) a0 b0) Source # 
data Vector ((:.) a0 b0) = V_StrictPair (Vector (a, b))
type Frozen ((:.) ts (MutArr m (arr sh elm))) Source # 
type Frozen ((:.) ts (MutArr m (arr sh elm))) = (:.) (Frozen ts) (arr sh elm)

data a :> b infixr 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.

This one is infixr so that in a :> b we can have the main type in a and the specializing types in b and then dispatch on a :> ts with ts maybe a chain of :>.

Constructors

!a :> !b infixr 3 

Instances

(Unbox a0, Unbox b0) => Vector Vector ((:>) a0 b0) Source # 

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (a0 :> b0) -> m (Vector (a0 :> b0)) #

basicUnsafeThaw :: PrimMonad m => Vector (a0 :> b0) -> m (Mutable Vector (PrimState m) (a0 :> b0)) #

basicLength :: Vector (a0 :> b0) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (a0 :> b0) -> Vector (a0 :> b0) #

basicUnsafeIndexM :: Monad m => Vector (a0 :> b0) -> Int -> m (a0 :> b0) #

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (a0 :> b0) -> Vector (a0 :> b0) -> m () #

elemseq :: Vector (a0 :> b0) -> (a0 :> b0) -> b -> b #

(Unbox a0, Unbox b0) => MVector MVector ((:>) a0 b0) Source # 

Methods

basicLength :: MVector s (a0 :> b0) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (a0 :> b0) -> MVector s (a0 :> b0) #

basicOverlaps :: MVector s (a0 :> b0) -> MVector s (a0 :> b0) -> Bool #

basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) (a0 :> b0)) #

basicInitialize :: PrimMonad m => MVector (PrimState m) (a0 :> b0) -> m () #

basicUnsafeReplicate :: PrimMonad m => Int -> (a0 :> b0) -> m (MVector (PrimState m) (a0 :> b0)) #

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (a0 :> b0) -> Int -> m (a0 :> b0) #

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (a0 :> b0) -> Int -> (a0 :> b0) -> m () #

basicClear :: PrimMonad m => MVector (PrimState m) (a0 :> b0) -> m () #

basicSet :: PrimMonad m => MVector (PrimState m) (a0 :> b0) -> (a0 :> b0) -> m () #

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (a0 :> b0) -> MVector (PrimState m) (a0 :> b0) -> m () #

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (a0 :> b0) -> MVector (PrimState m) (a0 :> b0) -> m () #

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (a0 :> b0) -> Int -> m (MVector (PrimState m) (a0 :> b0)) #

(Eq b, Eq a) => Eq ((:>) a b) Source # 

Methods

(==) :: (a :> b) -> (a :> b) -> Bool #

(/=) :: (a :> b) -> (a :> b) -> Bool #

(Ord b, Ord a) => Ord ((:>) a b) Source # 

Methods

compare :: (a :> b) -> (a :> b) -> Ordering #

(<) :: (a :> b) -> (a :> b) -> Bool #

(<=) :: (a :> b) -> (a :> b) -> Bool #

(>) :: (a :> b) -> (a :> b) -> Bool #

(>=) :: (a :> b) -> (a :> b) -> Bool #

max :: (a :> b) -> (a :> b) -> a :> b #

min :: (a :> b) -> (a :> b) -> a :> b #

(Read a, Read b) => Read ((:>) a b) Source # 

Methods

readsPrec :: Int -> ReadS (a :> b) #

readList :: ReadS [a :> b] #

readPrec :: ReadPrec (a :> b) #

readListPrec :: ReadPrec [a :> b] #

(Show b, Show a) => Show ((:>) a b) Source # 

Methods

showsPrec :: Int -> (a :> b) -> ShowS #

show :: (a :> b) -> String #

showList :: [a :> b] -> ShowS #

Generic ((:>) a b) Source # 

Associated Types

type Rep ((:>) a b) :: * -> * #

Methods

from :: (a :> b) -> Rep (a :> b) x #

to :: Rep (a :> b) x -> a :> b #

(Hashable a, Hashable b) => Hashable ((:>) a b) Source # 

Methods

hashWithSalt :: Int -> (a :> b) -> Int #

hash :: (a :> b) -> Int #

(ToJSON a, ToJSON b) => ToJSON ((:>) a b) Source # 

Methods

toJSON :: (a :> b) -> Value #

toEncoding :: (a :> b) -> Encoding #

toJSONList :: [a :> b] -> Value #

toEncodingList :: [a :> b] -> Encoding #

(FromJSON a, FromJSON b) => FromJSON ((:>) a b) Source # 

Methods

parseJSON :: Value -> Parser (a :> b) #

parseJSONList :: Value -> Parser [a :> b] #

(Binary a, Binary b) => Binary ((:>) a b) Source # 

Methods

put :: (a :> b) -> Put #

get :: Get (a :> b) #

putList :: [a :> b] -> Put #

(Serialize a, Serialize b) => Serialize ((:>) a b) Source # 

Methods

put :: Putter (a :> b) #

get :: Get (a :> b) #

(NFData a, NFData b) => NFData ((:>) a b) Source # 

Methods

rnf :: (a :> b) -> () #

(Unbox a0, Unbox b0) => Unbox ((:>) a0 b0) Source # 
(Index zs, Index z) => Index ((:>) zs z) Source # 

Methods

linearIndex :: (zs :> z) -> (zs :> z) -> (zs :> z) -> Int Source #

smallestLinearIndex :: (zs :> z) -> Int Source #

largestLinearIndex :: (zs :> z) -> Int Source #

size :: (zs :> z) -> (zs :> z) -> Int Source #

inBounds :: (zs :> z) -> (zs :> z) -> (zs :> z) -> Bool Source #

data MVector s ((:>) a0 b0) Source # 
data MVector s ((:>) a0 b0) = MV_StrictIxPair (MVector s (a, b))
type Rep ((:>) a b) Source # 
type Rep ((:>) a b) = D1 (MetaData ":>" "Data.PrimitiveArray.Index.Class" "PrimitiveArray-0.8.0.1-H8L9mO6Qdgd6EjLRyswnkq" False) (C1 (MetaCons ":>" (InfixI RightAssociative 3) False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 a)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 b))))
data Vector ((:>) a0 b0) Source # 
data Vector ((:>) a0 b0) = V_StrictIxPair (Vector (a, b))

data Z Source #

Base data constructor for multi-dimensional indices.

Constructors

Z 

Instances

Eq Z Source # 

Methods

(==) :: Z -> Z -> Bool #

(/=) :: Z -> Z -> Bool #

Ord Z Source # 

Methods

compare :: Z -> Z -> Ordering #

(<) :: Z -> Z -> Bool #

(<=) :: Z -> Z -> Bool #

(>) :: Z -> Z -> Bool #

(>=) :: Z -> Z -> Bool #

max :: Z -> Z -> Z #

min :: Z -> Z -> Z #

Read Z Source # 
Show Z Source # 

Methods

showsPrec :: Int -> Z -> ShowS #

show :: Z -> String #

showList :: [Z] -> ShowS #

Generic Z Source # 

Associated Types

type Rep Z :: * -> * #

Methods

from :: Z -> Rep Z x #

to :: Rep Z x -> Z #

Arbitrary Z Source # 

Methods

arbitrary :: Gen Z #

shrink :: Z -> [Z] #

Hashable Z Source # 

Methods

hashWithSalt :: Int -> Z -> Int #

hash :: Z -> Int #

ToJSON Z Source # 
FromJSON Z Source # 
Binary Z Source # 

Methods

put :: Z -> Put #

get :: Get Z #

putList :: [Z] -> Put #

Serialize Z Source # 

Methods

put :: Putter Z #

get :: Get Z #

NFData Z Source # 

Methods

rnf :: Z -> () #

Unbox Z Source # 
IndexStream Z Source # 

Methods

streamUp :: Monad m => Z -> Z -> Stream m Z Source #

streamDown :: Monad m => Z -> Z -> Stream m Z Source #

Index Z Source # 
Vector Vector Z Source # 
MVector MVector Z Source # 
Applicative m => FreezeTables m Z Source # 

Associated Types

type Frozen Z :: * Source #

Methods

freezeTables :: Z -> m (Frozen Z) Source #

Monad m => WriteCell m Z sh Source # 

Methods

unsafeWriteCell :: Z -> sh -> m () Source #

writeCell :: Z -> sh -> m () Source #

type Rep Z Source # 
type Rep Z = D1 (MetaData "Z" "Data.PrimitiveArray.Index.Class" "PrimitiveArray-0.8.0.1-H8L9mO6Qdgd6EjLRyswnkq" False) (C1 (MetaCons "Z" PrefixI False) U1)
data Vector Z Source # 
data Vector Z = V_Z (Vector ())
type Frozen Z Source # 
type Frozen Z = Z
data MVector s Z Source # 
data MVector s Z = MV_Z (MVector s ())

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

Index Z Source # 
Index (EdgeBoundary t) Source # 
Index (PointR t) Source # 
Index (PointL t) Source # 
Index (BitSet t) Source # 
Index (Subword t) Source # 
Index (Unit t) Source # 
(Index zs, Index z) => Index ((:.) zs z) Source # 

Methods

linearIndex :: (zs :. z) -> (zs :. z) -> (zs :. z) -> Int Source #

smallestLinearIndex :: (zs :. z) -> Int Source #

largestLinearIndex :: (zs :. z) -> Int Source #

size :: (zs :. z) -> (zs :. z) -> Int Source #

inBounds :: (zs :. z) -> (zs :. z) -> (zs :. z) -> Bool Source #

(Index zs, Index z) => Index ((:>) zs z) Source # 

Methods

linearIndex :: (zs :> z) -> (zs :> z) -> (zs :> z) -> Int Source #

smallestLinearIndex :: (zs :> z) -> Int Source #

largestLinearIndex :: (zs :> z) -> Int Source #

size :: (zs :> z) -> (zs :> z) -> Int Source #

inBounds :: (zs :> z) -> (zs :> z) -> (zs :> z) -> Bool Source #

Index (PInt t p) Source # 

Methods

linearIndex :: PInt t p -> PInt t p -> PInt t p -> Int Source #

smallestLinearIndex :: PInt t p -> Int Source #

largestLinearIndex :: PInt t p -> Int Source #

size :: PInt t p -> PInt t p -> Int Source #

inBounds :: PInt t p -> PInt t p -> PInt t p -> Bool Source #

Index (BS1 i t) Source #

linearIndex explicitly maps BS1 0 whatever to 0.

Methods

linearIndex :: BS1 i t -> BS1 i t -> BS1 i t -> Int Source #

smallestLinearIndex :: BS1 i t -> Int Source #

largestLinearIndex :: BS1 i t -> Int Source #

size :: BS1 i t -> BS1 i t -> Int Source #

inBounds :: BS1 i t -> BS1 i t -> BS1 i t -> Bool Source #

Index (Boundary i t) Source # 
Index (BS2 i j t) Source # 

Methods

linearIndex :: BS2 i j t -> BS2 i j t -> BS2 i j t -> Int Source #

smallestLinearIndex :: BS2 i j t -> Int Source #

largestLinearIndex :: BS2 i j t -> Int Source #

size :: BS2 i j t -> BS2 i j t -> Int Source #

inBounds :: BS2 i j t -> BS2 i j t -> BS2 i j t -> Bool Source #

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.

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.

streamUp :: (Monad m, IndexStream (Z :. i)) => 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.

streamDown :: (Monad m, IndexStream (Z :. i)) => 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.

Instances

IndexStream Z Source # 

Methods

streamUp :: Monad m => Z -> Z -> Stream m Z Source #

streamDown :: Monad m => Z -> Z -> Stream m Z Source #

IndexStream ((:.) Z (EdgeBoundary t)) => IndexStream (EdgeBoundary t) Source # 
IndexStream ((:.) Z (PointL t)) => IndexStream (PointL t) Source # 

Methods

streamUp :: Monad m => PointL t -> PointL t -> Stream m (PointL t) Source #

streamDown :: Monad m => PointL t -> PointL t -> Stream m (PointL t) Source #

IndexStream ((:.) Z (BitSet t)) => IndexStream (BitSet t) Source # 

Methods

streamUp :: Monad m => BitSet t -> BitSet t -> Stream m (BitSet t) Source #

streamDown :: Monad m => BitSet t -> BitSet t -> Stream m (BitSet t) Source #

IndexStream ((:.) Z (Subword t)) => IndexStream (Subword t) Source # 

Methods

streamUp :: Monad m => Subword t -> Subword t -> Stream m (Subword t) Source #

streamDown :: Monad m => Subword t -> Subword t -> Stream m (Subword t) Source #

IndexStream ((:.) Z (Unit t)) => IndexStream (Unit t) Source # 

Methods

streamUp :: Monad m => Unit t -> Unit t -> Stream m (Unit t) Source #

streamDown :: Monad m => Unit t -> Unit t -> Stream m (Unit t) Source #

IndexStream z => IndexStream ((:.) z (EdgeBoundary C)) Source #

EdgeBoundary C (complement)

IndexStream z => IndexStream ((:.) z (EdgeBoundary O)) Source #

EdgeBoundary O (outside).

Note: streamUp really needs to use streamDownMk / streamDownStep for the right order of indices!

IndexStream z => IndexStream ((:.) z (EdgeBoundary I)) Source #

EdgeBoundary I (inside)

IndexStream z => IndexStream ((:.) z (PInt C p)) Source # 

Methods

streamUp :: Monad m => (z :. PInt C p) -> (z :. PInt C p) -> Stream m (z :. PInt C p) Source #

streamDown :: Monad m => (z :. PInt C p) -> (z :. PInt C p) -> Stream m (z :. PInt C p) Source #

IndexStream z => IndexStream ((:.) z (PInt O p)) Source # 

Methods

streamUp :: Monad m => (z :. PInt O p) -> (z :. PInt O p) -> Stream m (z :. PInt O p) Source #

streamDown :: Monad m => (z :. PInt O p) -> (z :. PInt O p) -> Stream m (z :. PInt O p) Source #

IndexStream z => IndexStream ((:.) z (PInt I p)) Source # 

Methods

streamUp :: Monad m => (z :. PInt I p) -> (z :. PInt I p) -> Stream m (z :. PInt I p) Source #

streamDown :: Monad m => (z :. PInt I p) -> (z :. PInt I p) -> Stream m (z :. PInt I p) Source #

IndexStream z => IndexStream ((:.) z (PointL C)) Source # 

Methods

streamUp :: Monad m => (z :. PointL C) -> (z :. PointL C) -> Stream m (z :. PointL C) Source #

streamDown :: Monad m => (z :. PointL C) -> (z :. PointL C) -> Stream m (z :. PointL C) Source #

IndexStream z => IndexStream ((:.) z (PointL O)) Source # 

Methods

streamUp :: Monad m => (z :. PointL O) -> (z :. PointL O) -> Stream m (z :. PointL O) Source #

streamDown :: Monad m => (z :. PointL O) -> (z :. PointL O) -> Stream m (z :. PointL O) Source #

IndexStream z => IndexStream ((:.) z (PointL I)) Source # 

Methods

streamUp :: Monad m => (z :. PointL I) -> (z :. PointL I) -> Stream m (z :. PointL I) Source #

streamDown :: Monad m => (z :. PointL I) -> (z :. PointL I) -> Stream m (z :. PointL I) Source #

IndexStream z => IndexStream ((:.) z (Boundary k I)) Source # 

Methods

streamUp :: Monad m => (z :. Boundary k I) -> (z :. Boundary k I) -> Stream m (z :. Boundary k I) Source #

streamDown :: Monad m => (z :. Boundary k I) -> (z :. Boundary k I) -> Stream m (z :. Boundary k I) Source #

IndexStream z => IndexStream ((:.) z (BS2 i j C)) Source # 

Methods

streamUp :: Monad m => (z :. BS2 i j C) -> (z :. BS2 i j C) -> Stream m (z :. BS2 i j C) Source #

streamDown :: Monad m => (z :. BS2 i j C) -> (z :. BS2 i j C) -> Stream m (z :. BS2 i j C) Source #

IndexStream z => IndexStream ((:.) z (BS2 i j O)) Source # 

Methods

streamUp :: Monad m => (z :. BS2 i j O) -> (z :. BS2 i j O) -> Stream m (z :. BS2 i j O) Source #

streamDown :: Monad m => (z :. BS2 i j O) -> (z :. BS2 i j O) -> Stream m (z :. BS2 i j O) Source #

IndexStream z => IndexStream ((:.) z (BS2 i j I)) Source # 

Methods

streamUp :: Monad m => (z :. BS2 i j I) -> (z :. BS2 i j I) -> Stream m (z :. BS2 i j I) Source #

streamDown :: Monad m => (z :. BS2 i j I) -> (z :. BS2 i j I) -> Stream m (z :. BS2 i j I) Source #

IndexStream z => IndexStream ((:.) z (BS1 i C)) Source # 

Methods

streamUp :: Monad m => (z :. BS1 i C) -> (z :. BS1 i C) -> Stream m (z :. BS1 i C) Source #

streamDown :: Monad m => (z :. BS1 i C) -> (z :. BS1 i C) -> Stream m (z :. BS1 i C) Source #

IndexStream z => IndexStream ((:.) z (BS1 i O)) Source # 

Methods

streamUp :: Monad m => (z :. BS1 i O) -> (z :. BS1 i O) -> Stream m (z :. BS1 i O) Source #

streamDown :: Monad m => (z :. BS1 i O) -> (z :. BS1 i O) -> Stream m (z :. BS1 i O) Source #

IndexStream z => IndexStream ((:.) z (BS1 i I)) Source # 

Methods

streamUp :: Monad m => (z :. BS1 i I) -> (z :. BS1 i I) -> Stream m (z :. BS1 i I) Source #

streamDown :: Monad m => (z :. BS1 i I) -> (z :. BS1 i I) -> Stream m (z :. BS1 i I) Source #

IndexStream z => IndexStream ((:.) z (BitSet C)) Source # 

Methods

streamUp :: Monad m => (z :. BitSet C) -> (z :. BitSet C) -> Stream m (z :. BitSet C) Source #

streamDown :: Monad m => (z :. BitSet C) -> (z :. BitSet C) -> Stream m (z :. BitSet C) Source #

IndexStream z => IndexStream ((:.) z (BitSet O)) Source # 

Methods

streamUp :: Monad m => (z :. BitSet O) -> (z :. BitSet O) -> Stream m (z :. BitSet O) Source #

streamDown :: Monad m => (z :. BitSet O) -> (z :. BitSet O) -> Stream m (z :. BitSet O) Source #

IndexStream z => IndexStream ((:.) z (BitSet I)) Source # 

Methods

streamUp :: Monad m => (z :. BitSet I) -> (z :. BitSet I) -> Stream m (z :. BitSet I) Source #

streamDown :: Monad m => (z :. BitSet I) -> (z :. BitSet I) -> Stream m (z :. BitSet I) Source #

IndexStream z => IndexStream ((:.) z (Subword C)) Source #

Subword C (complement)

Methods

streamUp :: Monad m => (z :. Subword C) -> (z :. Subword C) -> Stream m (z :. Subword C) Source #

streamDown :: Monad m => (z :. Subword C) -> (z :. Subword C) -> Stream m (z :. Subword C) Source #

IndexStream z => IndexStream ((:.) z (Subword O)) Source #

Subword O (outside).

Note: streamUp really needs to use streamDownMk / streamDownStep for the right order of indices!

Methods

streamUp :: Monad m => (z :. Subword O) -> (z :. Subword O) -> Stream m (z :. Subword O) Source #

streamDown :: Monad m => (z :. Subword O) -> (z :. Subword O) -> Stream m (z :. Subword O) Source #

IndexStream z => IndexStream ((:.) z (Subword I)) Source #

Subword I (inside)

Methods

streamUp :: Monad m => (z :. Subword I) -> (z :. Subword I) -> Stream m (z :. Subword I) Source #

streamDown :: Monad m => (z :. Subword I) -> (z :. Subword I) -> Stream m (z :. Subword I) Source #

IndexStream z => IndexStream ((:.) z (Unit t)) Source # 

Methods

streamUp :: Monad m => (z :. Unit t) -> (z :. Unit t) -> Stream m (z :. Unit t) Source #

streamDown :: Monad m => (z :. Unit t) -> (z :. Unit t) -> Stream m (z :. Unit t) Source #

IndexStream (PInt C p) Source # 

Methods

streamUp :: Monad m => PInt C p -> PInt C p -> Stream m (PInt C p) Source #

streamDown :: Monad m => PInt C p -> PInt C p -> Stream m (PInt C p) Source #

IndexStream (PInt O p) Source # 

Methods

streamUp :: Monad m => PInt O p -> PInt O p -> Stream m (PInt O p) Source #

streamDown :: Monad m => PInt O p -> PInt O p -> Stream m (PInt O p) Source #

IndexStream (PInt I p) Source # 

Methods

streamUp :: Monad m => PInt I p -> PInt I p -> Stream m (PInt I p) Source #

streamDown :: Monad m => PInt I p -> PInt I p -> Stream m (PInt I p) Source #

IndexStream ((:.) Z (BS1 i t)) => IndexStream (BS1 i t) Source # 

Methods

streamUp :: Monad m => BS1 i t -> BS1 i t -> Stream m (BS1 i t) Source #

streamDown :: Monad m => BS1 i t -> BS1 i t -> Stream m (BS1 i t) Source #

IndexStream ((:.) Z (Boundary k I)) => IndexStream (Boundary k I) Source # 

Methods

streamUp :: Monad m => Boundary k I -> Boundary k I -> Stream m (Boundary k I) Source #

streamDown :: Monad m => Boundary k I -> Boundary k I -> Stream m (Boundary k I) Source #

IndexStream ((:.) Z (BS2 i j t)) => IndexStream (BS2 i j t) Source # 

Methods

streamUp :: Monad m => BS2 i j t -> BS2 i j t -> Stream m (BS2 i j t) Source #

streamDown :: Monad m => BS2 i j t -> BS2 i j t -> Stream m (BS2 i j t) Source #