PrimitiveArray-0.8.0.0: Efficient multidimensional arrays

Safe HaskellNone
LanguageHaskell2010

Data.PrimitiveArray.Index.Point

Contents

Description

Point index structures are used for left- and right-linear grammars. Such grammars have at most one syntactic symbol on each r.h.s. of a rule. The syntactic symbol needs to be in an outermost position.

Synopsis

Documentation

newtype PointL t Source #

A point in a left-linear grammar. The syntactic symbol is in left-most position.

Constructors

PointL 

Fields

Instances

Monad m => Serial m (PointL t) Source # 

Methods

series :: Series m (PointL t) #

Vector Vector (PointL t0) Source # 
MVector MVector (PointL t0) Source # 

Methods

basicLength :: MVector s (PointL t0) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (PointL t0) -> MVector s (PointL t0) #

basicOverlaps :: MVector s (PointL t0) -> MVector s (PointL t0) -> Bool #

basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) (PointL t0)) #

basicInitialize :: PrimMonad m => MVector (PrimState m) (PointL t0) -> m () #

basicUnsafeReplicate :: PrimMonad m => Int -> PointL t0 -> m (MVector (PrimState m) (PointL t0)) #

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (PointL t0) -> Int -> m (PointL t0) #

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (PointL t0) -> Int -> PointL t0 -> m () #

basicClear :: PrimMonad m => MVector (PrimState m) (PointL t0) -> m () #

basicSet :: PrimMonad m => MVector (PrimState m) (PointL t0) -> PointL t0 -> m () #

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (PointL t0) -> MVector (PrimState m) (PointL t0) -> m () #

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (PointL t0) -> MVector (PrimState m) (PointL t0) -> m () #

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (PointL t0) -> Int -> m (MVector (PrimState m) (PointL t0)) #

Eq (PointL t) Source # 

Methods

(==) :: PointL t -> PointL t -> Bool #

(/=) :: PointL t -> PointL t -> Bool #

Ord (PointL t) Source # 

Methods

compare :: PointL t -> PointL t -> Ordering #

(<) :: PointL t -> PointL t -> Bool #

(<=) :: PointL t -> PointL t -> Bool #

(>) :: PointL t -> PointL t -> Bool #

(>=) :: PointL t -> PointL t -> Bool #

max :: PointL t -> PointL t -> PointL t #

min :: PointL t -> PointL t -> PointL t #

Read (PointL t) Source # 
Show (PointL t) Source # 

Methods

showsPrec :: Int -> PointL t -> ShowS #

show :: PointL t -> String #

showList :: [PointL t] -> ShowS #

Generic (PointL t) Source # 

Associated Types

type Rep (PointL t) :: * -> * #

Methods

from :: PointL t -> Rep (PointL t) x #

to :: Rep (PointL t) x -> PointL t #

Arbitrary (PointL t) Source # 

Methods

arbitrary :: Gen (PointL t) #

shrink :: PointL t -> [PointL t] #

Hashable (PointL t) Source # 

Methods

hashWithSalt :: Int -> PointL t -> Int #

hash :: PointL t -> Int #

ToJSON (PointL t) Source # 
ToJSONKey (PointL t) Source # 
FromJSON (PointL t) Source # 
FromJSONKey (PointL t) Source # 
Binary (PointL t) Source # 

Methods

put :: PointL t -> Put #

get :: Get (PointL t) #

putList :: [PointL t] -> Put #

Serialize (PointL t) Source # 

Methods

put :: Putter (PointL t) #

get :: Get (PointL t) #

NFData (PointL t) Source # 

Methods

rnf :: PointL t -> () #

Unbox (PointL t0) 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 #

Index (PointL t) 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 #

data MVector s (PointL t0) Source # 
data MVector s (PointL t0) = MV_PointL (MVector s Int)
type Rep (PointL t) Source # 
type Rep (PointL t) = D1 (MetaData "PointL" "Data.PrimitiveArray.Index.Point" "PrimitiveArray-0.8.0.0-BVUiv779U7I8cOf4DtXnHh" True) (C1 (MetaCons "PointL" PrefixI True) (S1 (MetaSel (Just Symbol "fromPointL") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))
data Vector (PointL t0) Source # 

newtype PointR t Source #

A point in a right-linear grammars.

Constructors

PointR 

Fields

Instances

Vector Vector (PointR t0) Source # 
MVector MVector (PointR t0) Source # 

Methods

basicLength :: MVector s (PointR t0) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (PointR t0) -> MVector s (PointR t0) #

basicOverlaps :: MVector s (PointR t0) -> MVector s (PointR t0) -> Bool #

basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) (PointR t0)) #

basicInitialize :: PrimMonad m => MVector (PrimState m) (PointR t0) -> m () #

basicUnsafeReplicate :: PrimMonad m => Int -> PointR t0 -> m (MVector (PrimState m) (PointR t0)) #

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (PointR t0) -> Int -> m (PointR t0) #

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (PointR t0) -> Int -> PointR t0 -> m () #

basicClear :: PrimMonad m => MVector (PrimState m) (PointR t0) -> m () #

basicSet :: PrimMonad m => MVector (PrimState m) (PointR t0) -> PointR t0 -> m () #

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (PointR t0) -> MVector (PrimState m) (PointR t0) -> m () #

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (PointR t0) -> MVector (PrimState m) (PointR t0) -> m () #

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (PointR t0) -> Int -> m (MVector (PrimState m) (PointR t0)) #

Eq (PointR t) Source # 

Methods

(==) :: PointR t -> PointR t -> Bool #

(/=) :: PointR t -> PointR t -> Bool #

Ord (PointR t) Source # 

Methods

compare :: PointR t -> PointR t -> Ordering #

(<) :: PointR t -> PointR t -> Bool #

(<=) :: PointR t -> PointR t -> Bool #

(>) :: PointR t -> PointR t -> Bool #

(>=) :: PointR t -> PointR t -> Bool #

max :: PointR t -> PointR t -> PointR t #

min :: PointR t -> PointR t -> PointR t #

Read (PointR t) Source # 
Show (PointR t) Source # 

Methods

showsPrec :: Int -> PointR t -> ShowS #

show :: PointR t -> String #

showList :: [PointR t] -> ShowS #

Generic (PointR t) Source # 

Associated Types

type Rep (PointR t) :: * -> * #

Methods

from :: PointR t -> Rep (PointR t) x #

to :: Rep (PointR t) x -> PointR t #

Hashable (PointR t) Source # 

Methods

hashWithSalt :: Int -> PointR t -> Int #

hash :: PointR t -> Int #

ToJSON (PointR t) Source # 
FromJSON (PointR t) Source # 
Binary (PointR t) Source # 

Methods

put :: PointR t -> Put #

get :: Get (PointR t) #

putList :: [PointR t] -> Put #

Serialize (PointR t) Source # 

Methods

put :: Putter (PointR t) #

get :: Get (PointR t) #

NFData (PointR t) Source # 

Methods

rnf :: PointR t -> () #

Unbox (PointR t0) Source # 
Index (PointR t) Source # 
data MVector s (PointR t0) Source # 
data MVector s (PointR t0) = MV_PointR (MVector s Int)
type Rep (PointR t) Source # 
type Rep (PointR t) = D1 (MetaData "PointR" "Data.PrimitiveArray.Index.Point" "PrimitiveArray-0.8.0.0-BVUiv779U7I8cOf4DtXnHh" True) (C1 (MetaCons "PointR" PrefixI True) (S1 (MetaSel (Just Symbol "fromPointR") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))
data Vector (PointR t0) Source # 

data SP z Source #

Constructors

SP !z !Int# 

streamUpMk :: Monad m => Int -> z -> m (SP z) Source #

streamUpStep :: Monad m => Int -> SP z -> m (Step (SP z) ((:.) z (PointL t))) Source #

streamDownMk :: Monad m => Int -> z -> m (SP z) Source #

streamDownStep :: Monad m => Int -> SP z -> m (Step (SP z) ((:.) z (PointL t))) Source #

PointR