PrimitiveArray-0.9.0.0: Efficient multidimensional arrays

Safe HaskellNone
LanguageHaskell2010

Data.PrimitiveArray.Index.Point

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
Vector Vector (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

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

Defined in Data.PrimitiveArray.Index.Point

Methods

series :: Series m (PointL t) #

MVector MVector (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Eq (LimitType (PointL t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Methods

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

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

Read (LimitType (PointL t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Show (LimitType (PointL t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Generic (LimitType (PointL t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Associated Types

type Rep (LimitType (PointL t)) :: Type -> Type #

Methods

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

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

Eq (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Methods

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

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

Ord (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

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 # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Show (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Methods

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

show :: PointL t -> String #

showList :: [PointL t] -> ShowS #

Generic (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Associated Types

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

Methods

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

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

Arbitrary (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Methods

arbitrary :: Gen (PointL t) #

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

Hashable (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Methods

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

hash :: PointL t -> Int #

ToJSON (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

ToJSONKey (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

FromJSON (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

FromJSONKey (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Binary (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Methods

put :: PointL t -> Put #

get :: Get (PointL t) #

putList :: [PointL t] -> Put #

Serialize (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Methods

put :: Putter (PointL t) #

get :: Get (PointL t) #

NFData (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Methods

rnf :: PointL t -> () #

Unbox (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

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

Defined in Data.PrimitiveArray.Index.Point

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

Defined in Data.PrimitiveArray.Index.Point

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

Defined in Data.PrimitiveArray.Index.Point

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

Defined in Data.PrimitiveArray.Index.Point

Index (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Associated Types

data LimitType (PointL t) :: Type Source #

data MVector s (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

type Rep (LimitType (PointL t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

type Rep (LimitType (PointL t)) = D1 (MetaData "LimitType" "Data.PrimitiveArray.Index.Point" "PrimitiveArray-0.9.0.0-7o4e78MXLzPCxIvR95QAvs" True) (C1 (MetaCons "LtPointL" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))
type Rep (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

type Rep (PointL t) = D1 (MetaData "PointL" "Data.PrimitiveArray.Index.Point" "PrimitiveArray-0.9.0.0-7o4e78MXLzPCxIvR95QAvs" True) (C1 (MetaCons "PointL" PrefixI True) (S1 (MetaSel (Just "fromPointL") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))
data Vector (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

data LimitType (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

newtype PointR t Source #

A point in a right-linear grammars.

Constructors

PointR 

Fields

Instances
Eq (PointR t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Methods

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

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

Ord (PointR t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

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 # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Show (PointR t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Methods

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

show :: PointR t -> String #

showList :: [PointR t] -> ShowS #

Generic (PointR t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Associated Types

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

Methods

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

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

type Rep (PointR t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

type Rep (PointR t) = D1 (MetaData "PointR" "Data.PrimitiveArray.Index.Point" "PrimitiveArray-0.9.0.0-7o4e78MXLzPCxIvR95QAvs" True) (C1 (MetaCons "PointR" PrefixI True) (S1 (MetaSel (Just "fromPointR") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))

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 #