PrimitiveArray-0.10.1.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

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

Num (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Methods

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

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

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

negate :: PointL t -> PointL t #

abs :: PointL t -> PointL t #

signum :: PointL t -> PointL t #

fromInteger :: Integer -> PointL t #

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] #

NFData (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Methods

rnf :: 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) #

Unbox (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

SparseBucket (PointL O) Source #

TODO Is this instance correct? Outside indices shrink?

Instance details

Defined in Data.PrimitiveArray.Index.Point

SparseBucket (PointL I) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

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

Defined in Data.PrimitiveArray.Index.Point

Methods

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

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

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

Defined in Data.PrimitiveArray.Index.Point

Methods

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

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

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

Defined in Data.PrimitiveArray.Index.Point

Methods

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

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

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

Defined in Data.PrimitiveArray.Index.Point

Methods

streamUp :: forall (m :: Type -> Type). Monad m => LimitType (PointL t) -> LimitType (PointL t) -> Stream m (PointL t) Source #

streamDown :: forall (m :: Type -> Type). Monad m => LimitType (PointL t) -> LimitType (PointL t) -> Stream m (PointL t) Source #

Index (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Associated Types

data LimitType (PointL t) Source #

newtype MVector s (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

newtype MVector s (PointL t) = MV_PointL (MVector s Int)
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.10.1.0-8LhqXNFuZNc70s43xh6tNJ" '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.10.1.0-8LhqXNFuZNc70s43xh6tNJ" 'True) (C1 ('MetaCons "PointL" 'PrefixI 'True) (S1 ('MetaSel ('Just "fromPointL") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))
newtype Vector (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

newtype Vector (PointL t) = V_PointL (Vector Int)
newtype LimitType (PointL t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

data SP z Source #

Constructors

SP !z !Int# 

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

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

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

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

PointR

newtype PointR t Source #

A point in a right-linear grammars.

Constructors

PointR 

Fields

Instances

Instances details
Vector Vector (PointR t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

MVector MVector (PointR t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

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

Defined in Data.PrimitiveArray.Index.Point

Methods

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

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

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

Defined in Data.PrimitiveArray.Index.Point

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

Defined in Data.PrimitiveArray.Index.Point

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

Defined in Data.PrimitiveArray.Index.Point

Associated Types

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

Methods

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

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

Eq (PointR t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Methods

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

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

Num (PointR t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Methods

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

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

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

negate :: PointR t -> PointR t #

abs :: PointR t -> PointR t #

signum :: PointR t -> PointR t #

fromInteger :: Integer -> PointR t #

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 #

Arbitrary (PointR t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Methods

arbitrary :: Gen (PointR t) #

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

NFData (PointR t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Methods

rnf :: PointR t -> () #

Hashable (PointR t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Methods

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

hash :: PointR t -> Int #

ToJSON (PointR t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

ToJSONKey (PointR t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

FromJSON (PointR t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

FromJSONKey (PointR t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Binary (PointR t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Methods

put :: PointR t -> Put #

get :: Get (PointR t) #

putList :: [PointR t] -> Put #

Serialize (PointR t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Methods

put :: Putter (PointR t) #

get :: Get (PointR t) #

Unbox (PointR t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

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

Defined in Data.PrimitiveArray.Index.Point

Methods

streamUp :: forall (m :: Type -> Type). Monad m => LimitType (z :. PointR O) -> LimitType (z :. PointR O) -> Stream m (z :. PointR O) Source #

streamDown :: forall (m :: Type -> Type). Monad m => LimitType (z :. PointR O) -> LimitType (z :. PointR O) -> Stream m (z :. PointR O) Source #

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

Defined in Data.PrimitiveArray.Index.Point

Methods

streamUp :: forall (m :: Type -> Type). Monad m => LimitType (z :. PointR I) -> LimitType (z :. PointR I) -> Stream m (z :. PointR I) Source #

streamDown :: forall (m :: Type -> Type). Monad m => LimitType (z :. PointR I) -> LimitType (z :. PointR I) -> Stream m (z :. PointR I) Source #

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

Defined in Data.PrimitiveArray.Index.Point

Methods

streamUp :: forall (m :: Type -> Type). Monad m => LimitType (PointR t) -> LimitType (PointR t) -> Stream m (PointR t) Source #

streamDown :: forall (m :: Type -> Type). Monad m => LimitType (PointR t) -> LimitType (PointR t) -> Stream m (PointR t) Source #

Index (PointR t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

Associated Types

data LimitType (PointR t) Source #

newtype MVector s (PointR t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

newtype MVector s (PointR t) = MV_PointR (MVector s Int)
type Rep (LimitType (PointR t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

type Rep (LimitType (PointR t)) = D1 ('MetaData "LimitType" "Data.PrimitiveArray.Index.Point" "PrimitiveArray-0.10.1.0-8LhqXNFuZNc70s43xh6tNJ" 'True) (C1 ('MetaCons "LtPointR" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))
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.10.1.0-8LhqXNFuZNc70s43xh6tNJ" 'True) (C1 ('MetaCons "PointR" 'PrefixI 'True) (S1 ('MetaSel ('Just "fromPointR") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))
newtype Vector (PointR t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point

newtype Vector (PointR t) = V_PointR (Vector Int)
newtype LimitType (PointR t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Point