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

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

Defined in Data.PrimitiveArray.Index.Subword

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

Defined in Data.PrimitiveArray.Index.Subword

Methods

series :: Series m (Subword t) #

MVector MVector (Subword t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

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

Defined in Data.PrimitiveArray.Index.Subword

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

Defined in Data.PrimitiveArray.Index.Subword

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

Defined in Data.PrimitiveArray.Index.Subword

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

Defined in Data.PrimitiveArray.Index.Subword

Associated Types

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

Methods

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

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

Eq (Subword t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

Methods

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

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

Ord (Subword t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

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

Defined in Data.PrimitiveArray.Index.Subword

Show (Subword t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

Methods

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

show :: Subword t -> String #

showList :: [Subword t] -> ShowS #

Generic (Subword t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

Associated Types

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

Methods

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

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

Arbitrary (Subword t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

Methods

arbitrary :: Gen (Subword t) #

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

NFData (Subword t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

Methods

rnf :: Subword t -> () #

Hashable (Subword t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

Methods

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

hash :: Subword t -> Int #

ToJSON (Subword t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

ToJSONKey (Subword t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

FromJSON (Subword t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

FromJSONKey (Subword t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

Binary (Subword t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

Methods

put :: Subword t -> Put #

get :: Get (Subword t) #

putList :: [Subword t] -> Put #

Serialize (Subword t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

Methods

put :: Putter (Subword t) #

get :: Get (Subword t) #

Unbox (Subword t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

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

Subword C (complement)

Instance details

Defined in Data.PrimitiveArray.Index.Subword

Methods

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

streamDown :: forall (m :: Type -> Type). Monad m => LimitType (z :. Subword C) -> LimitType (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!

Instance details

Defined in Data.PrimitiveArray.Index.Subword

Methods

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

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

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

Subword I (inside)

Instance details

Defined in Data.PrimitiveArray.Index.Subword

Methods

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

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

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

Defined in Data.PrimitiveArray.Index.Subword

Methods

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

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

Index (Subword t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

Associated Types

data LimitType (Subword t) Source #

newtype MVector s (Subword t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

newtype MVector s (Subword t) = MV_Subword (MVector s (Int, Int))
type Rep (LimitType (Subword t)) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

type Rep (LimitType (Subword t)) = D1 ('MetaData "LimitType" "Data.PrimitiveArray.Index.Subword" "PrimitiveArray-0.10.1.0-8LhqXNFuZNc70s43xh6tNJ" 'True) (C1 ('MetaCons "LtSubword" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))
type Rep (Subword t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

type Rep (Subword t) = D1 ('MetaData "Subword" "Data.PrimitiveArray.Index.Subword" "PrimitiveArray-0.10.1.0-8LhqXNFuZNc70s43xh6tNJ" 'True) (C1 ('MetaCons "Subword" 'PrefixI 'True) (S1 ('MetaSel ('Just "fromSubword") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Int :. Int))))
newtype Vector (Subword t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

newtype Vector (Subword t) = V_Subword (Vector (Int, Int))
newtype LimitType (Subword t) Source # 
Instance details

Defined in Data.PrimitiveArray.Index.Subword

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

Create a Subword t where t is inferred.

streamUpMk :: Monad m => c -> a -> m (a, c, c) Source #

generic mk for streamUp / streamDown

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

streamDownMk :: Monad m => b -> c -> a -> m (a, b, c) Source #

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