Safe Haskell | None |
---|---|
Language | Haskell2010 |
Index structure for context-free grammars on strings. A Subword
captures
a pair (i,j)
with i<=j
.
Synopsis
- newtype Subword t = Subword {
- fromSubword :: Int :. Int
- fromSubwordFst :: Subword t -> Int
- fromSubwordSnd :: Subword t -> Int
- subword :: Int -> Int -> Subword t
- subwordI :: Int -> Int -> Subword I
- subwordO :: Int -> Int -> Subword O
- subwordC :: Int -> Int -> Subword C
- streamUpMk :: Monad m => c -> a -> m (a, c, c)
- streamUpStep :: forall k m a (t :: k). Monad m => Int -> Int -> (a, Int, Int) -> m (Step (a, Int, Int) (a :. Subword t))
- streamDownMk :: Monad m => b -> c -> a -> m (a, b, c)
- streamDownStep :: forall k m a (t :: k). Monad m => Int -> (a, Int, Int) -> m (Step (a, Int, Int) (a :. Subword t))
Documentation
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.
Subword | |
|
Instances
fromSubwordFst :: Subword t -> Int Source #
fromSubwordSnd :: Subword t -> Int Source #
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 #