Safe Haskell | None |
---|---|
Language | Haskell2010 |
Documentation
Strict pairs -- as in repa
.
!a :. !b infixl 3 |
A different version of strict pairs. Makes for simpler type inference in
multi-tape grammars. We use :>
when we have special needs, like
non-recursive instances on inductives tuples, as used for set indices.
This one is infixr
so that in a :> b
we can have the main type in
a
and the specializing types in b
and then dispatch on a :> ts
with ts
maybe a chain of :>
.
!a :> !b infixr 3 |
(Unbox a0, Unbox b0) => Vector Vector ((:>) a0 b0) Source # | |
(Unbox a0, Unbox b0) => MVector MVector ((:>) a0 b0) Source # | |
(Eq a, Eq b) => Eq ((:>) a b) Source # | |
(Ord a, Ord b) => Ord ((:>) a b) Source # | |
(Read a, Read b) => Read ((:>) a b) Source # | |
(Show a, Show b) => Show ((:>) a b) Source # | |
Generic ((:>) a b) Source # | |
(Hashable a, Hashable b) => Hashable ((:>) a b) Source # | |
(FromJSON a, FromJSON b) => FromJSON ((:>) a b) Source # | |
(ToJSON a, ToJSON b) => ToJSON ((:>) a b) Source # | |
(Binary a, Binary b) => Binary ((:>) a b) Source # | |
(Serialize a, Serialize b) => Serialize ((:>) a b) Source # | |
(NFData a, NFData b) => NFData ((:>) a b) Source # | |
(Unbox a0, Unbox b0) => Unbox ((:>) a0 b0) Source # | |
(Index zs, Index z) => Index ((:>) zs z) Source # | |
data MVector s ((:>) a0 b0) Source # | |
type Rep ((:>) a b) Source # | |
data Vector ((:>) a0 b0) Source # | |
Base data constructor for multi-dimensional indices.
Eq Z Source # | |
Ord Z Source # | |
Read Z Source # | |
Show Z Source # | |
Generic Z Source # | |
Arbitrary Z Source # | |
Hashable Z Source # | |
FromJSON Z Source # | |
ToJSON Z Source # | |
Binary Z Source # | |
Serialize Z Source # | |
NFData Z Source # | |
Unbox Z Source # | |
IndexStream Z Source # | |
Index Z Source # | |
Vector Vector Z Source # | |
MVector MVector Z Source # | |
Applicative m => FreezeTables m Z Source # | |
Monad m => WriteCell m Z sh Source # | |
type Rep Z Source # | |
data Vector Z Source # | |
type Frozen Z Source # | |
data MVector s Z Source # | |
Index structures for complex, heterogeneous indexing. Mostly designed for indexing in DP grammars, where the indices work for linear and context-free grammars on one or more tapes, for strings, sets, later on tree structures.
linearIndex :: i -> i -> i -> Int Source #
Given a minimal size, a maximal size, and a current index, calculate the linear index.
smallestLinearIndex :: i -> Int Source #
Given an index element from the smallest subset, calculate the highest linear index that is *not* stored.
largestLinearIndex :: i -> Int Source #
Given an index element from the largest subset, calculate the highest linear index that *is* stored.
size :: i -> i -> Int Source #
Given smallest and largest index, return the number of cells required for storage.
inBounds :: i -> i -> i -> Bool Source #
Check if an index is within the bounds.
Index Z Source # | |
Index (Unit t) Source # | |
Index (PointR t) Source # | |
Index (PointL t) Source # | |
Index (BitSet t) Source # | |
Index (Interface i) Source # | |
Index (Subword t) Source # | |
(Index zs, Index z) => Index ((:.) zs z) Source # | |
(Index zs, Index z) => Index ((:>) zs z) Source # | |
Index (PInt t p) Source # | |
Index (BS1 i t) Source # | |
Index (BS2 i j t) Source # | |
class IndexStream i where Source #
Generate a stream of indices in correct order for dynamic programming.
Since the stream generators require concatMap
/ flatten
we have to
write more specialized code for (z:.IX)
stuff.
streamUp :: Monad m => i -> i -> Stream m i Source #
This generates an index stream suitable for forward
structure filling.
The first index is the smallest (or the first indices considered are all
equally small in partially ordered sets). Larger indices follow up until
the largest one.
streamUp :: (Monad m, IndexStream (Z :. i)) => i -> i -> Stream m i Source #
This generates an index stream suitable for forward
structure filling.
The first index is the smallest (or the first indices considered are all
equally small in partially ordered sets). Larger indices follow up until
the largest one.
streamDown :: Monad m => i -> i -> Stream m i Source #
If streamUp
generates indices from smallest to largest, then
streamDown
generates indices from largest to smallest. Outside grammars
make implicit use of this. Asking for an axiom in backtracking requests
the first element from this stream.
streamDown :: (Monad m, IndexStream (Z :. i)) => i -> i -> Stream m i Source #
If streamUp
generates indices from smallest to largest, then
streamDown
generates indices from largest to smallest. Outside grammars
make implicit use of this. Asking for an axiom in backtracking requests
the first element from this stream.