PrimitiveArray-0.7.1.0: Efficient multidimensional arrays

Safe HaskellNone
LanguageHaskell2010

Data.PrimitiveArray.Index.Subword

Description

Index structure for context-free grammars on strings. A Subword captures a pair (i,j) with i<=j.

Synopsis

Documentation

newtype Subword t Source #

A subword wraps a pair of Int indices i,j with i<=j.

Subwords always yield the upper-triangular part of a rect-angular array. This gives the quite curious effect that (0,N) points to the `largest' index, while (0,0) ... (1,1) ... (k,k) ... (N,N) point to the smallest. We do, however, use (0,0) as the smallest as (0,k) gives successively smaller upper triangular parts.

Constructors

Subword 

Fields

Instances

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

Methods

series :: Series m (Subword t) #

Vector Vector (Subword t0) Source # 
MVector MVector (Subword t0) Source # 
Eq (Subword t) Source # 

Methods

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

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

Ord (Subword t) Source # 

Methods

compare :: Subword t -> Subword t -> Ordering #

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

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

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

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

max :: Subword t -> Subword t -> Subword t #

min :: Subword t -> Subword t -> Subword t #

Read (Subword t) Source # 
Show (Subword t) Source # 

Methods

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

show :: Subword t -> String #

showList :: [Subword t] -> ShowS #

Generic (Subword t) Source # 

Associated Types

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

Methods

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

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

Arbitrary (Subword t) Source # 

Methods

arbitrary :: Gen (Subword t) #

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

Hashable (Subword t) Source # 

Methods

hashWithSalt :: Int -> Subword t -> Int #

hash :: Subword t -> Int #

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

Methods

put :: Subword t -> Put #

get :: Get (Subword t) #

putList :: [Subword t] -> Put #

Serialize (Subword t) Source # 

Methods

put :: Putter (Subword t) #

get :: Get (Subword t) #

NFData (Subword t) Source # 

Methods

rnf :: Subword t -> () #

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

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

data MVector s (Subword t0) Source # 
data MVector s (Subword t0) = MV_Subword (MVector s (Int, Int))
type Rep (Subword t) Source # 
type Rep (Subword t) = D1 (MetaData "Subword" "Data.PrimitiveArray.Index.Subword" "PrimitiveArray-0.7.1.0-B4A9oZDNxHW51HjshiHgYe" True) (C1 (MetaCons "Subword" PrefixI True) (S1 (MetaSel (Just Symbol "fromSubword") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ((:.) Int Int))))
data Vector (Subword t0) Source # 

subword :: Int -> Int -> Subword t Source #

Create a Subword t where t is inferred.

streamUpMk :: Monad m => t1 -> t -> m (t, t1, t1) Source #

generic mk for streamUp / streamDown

streamUpStep :: Monad m => Int -> Int -> (t1, Int, Int) -> m (Step (t1, Int, Int) ((:.) t1 (Subword t))) Source #

streamDownMk :: Monad m => t1 -> t2 -> t -> m (t, t1, t2) Source #

streamDownStep :: Monad m => Int -> (t1, Int, Int) -> m (Step (t1, Int, Int) ((:.) t1 (Subword t))) Source #