Safe Haskell | None |
---|---|
Language | Haskell2010 |
- data a :. b = !a :. !b
- data a :> b = !a :> !b
- data Z = Z
- class Index i where
- linearIndex :: i -> i -> i -> Int
- smallestLinearIndex :: i -> Int
- largestLinearIndex :: i -> Int
- size :: i -> i -> Int
- inBounds :: i -> i -> i -> Bool
- class IndexStream i where
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.
!a :> !b infixl 3 |
Base data constructor for multi-dimensional indices.
Eq Z | |
Ord Z | |
Read Z | |
Show Z | |
Generic Z | |
Arbitrary Z | |
ToJSON Z | |
FromJSON Z | |
Binary Z | |
Serialize Z | |
NFData Z | |
Unbox Z | |
IndexStream Z | |
Index Z | |
Vector Vector Z | |
MVector MVector Z | |
Applicative m => FreezeTables m Z | |
Monad m => WriteCell m Z sh | |
type Rep Z | |
data Vector Z = V_Z (Vector ()) | |
type Frozen Z = Z | |
data MVector s0 Z = MV_Z (MVector s ()) |
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.
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.
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.
Nothing
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.
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.
IndexStream Int | |
IndexStream Z | |
IndexStream PointL | |
IndexStream Subword | |
IndexStream i => IndexStream (Complement i) | |
IndexStream i => IndexStream (Outside i) | |
IndexStream (PInt p) | |
IndexStream z => IndexStream ((:.) z Int) | |
IndexStream z => IndexStream ((:.) z (PInt p)) | |
IndexStream z => IndexStream ((:.) z PointL) | |
IndexStream z => IndexStream ((:.) z ((:>) ((:>) BitSet (Interface i)) (Interface j))) | |
IndexStream z => IndexStream ((:.) z ((:>) BitSet (Interface i))) | |
IndexStream z => IndexStream ((:.) z BitSet) | |
IndexStream z => IndexStream ((:.) z Subword) |