Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data a :. b = !a :. !b
- data a :> b = !a :> !b
- data Z = Z
- class Index i where
- data LimitType i :: *
- linearIndex :: LimitType i -> i -> Int
- fromLinearIndex :: LimitType i -> Int -> i
- size :: LimitType i -> Int
- inBounds :: LimitType i -> i -> Bool
- zeroBound :: i
- zeroBound' :: LimitType i
- totalSize :: LimitType i -> [Integer]
- showBound :: LimitType i -> [String]
- showIndex :: i -> [String]
- sizeIsValid :: Monad m => Word -> [[Integer]] -> ExceptT SizeError m CellSize
- newtype SizeError = SizeError String
- newtype CellSize = CellSize Word
- class Index i => IndexStream i where
- class SparseBucket sh where
Documentation
Strict pairs -- as in repa
.
!a :. !b infixl 3 |
Instances
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 |
Instances
(Unbox a, Unbox b) => Vector Vector (a :> b) Source # | |
Defined in Data.PrimitiveArray.Index.Class basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (a :> b) -> m (Vector (a :> b)) # basicUnsafeThaw :: PrimMonad m => Vector (a :> b) -> m (Mutable Vector (PrimState m) (a :> b)) # basicLength :: Vector (a :> b) -> Int # basicUnsafeSlice :: Int -> Int -> Vector (a :> b) -> Vector (a :> b) # basicUnsafeIndexM :: Monad m => Vector (a :> b) -> Int -> m (a :> b) # basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (a :> b) -> Vector (a :> b) -> m () # | |
(Unbox a, Unbox b) => MVector MVector (a :> b) Source # | |
Defined in Data.PrimitiveArray.Index.Class basicLength :: MVector s (a :> b) -> Int # basicUnsafeSlice :: Int -> Int -> MVector s (a :> b) -> MVector s (a :> b) # basicOverlaps :: MVector s (a :> b) -> MVector s (a :> b) -> Bool # basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) (a :> b)) # basicInitialize :: PrimMonad m => MVector (PrimState m) (a :> b) -> m () # basicUnsafeReplicate :: PrimMonad m => Int -> (a :> b) -> m (MVector (PrimState m) (a :> b)) # basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (a :> b) -> Int -> m (a :> b) # basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (a :> b) -> Int -> (a :> b) -> m () # basicClear :: PrimMonad m => MVector (PrimState m) (a :> b) -> m () # basicSet :: PrimMonad m => MVector (PrimState m) (a :> b) -> (a :> b) -> m () # basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (a :> b) -> MVector (PrimState m) (a :> b) -> m () # basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (a :> b) -> MVector (PrimState m) (a :> b) -> m () # basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (a :> b) -> Int -> m (MVector (PrimState m) (a :> b)) # | |
(Eq a, Eq b) => Eq (a :> b) Source # | |
(Data a, Data b) => Data (a :> b) Source # | |
Defined in Data.PrimitiveArray.Index.Class gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> (a :> b) -> c (a :> b) # gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (a :> b) # toConstr :: (a :> b) -> Constr # dataTypeOf :: (a :> b) -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (a :> b)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (a :> b)) # gmapT :: (forall b0. Data b0 => b0 -> b0) -> (a :> b) -> a :> b # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> (a :> b) -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> (a :> b) -> r # gmapQ :: (forall d. Data d => d -> u) -> (a :> b) -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> (a :> b) -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> (a :> b) -> m (a :> b) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> (a :> b) -> m (a :> b) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> (a :> b) -> m (a :> b) # | |
(Ord a, Ord b) => Ord (a :> b) Source # | |
Defined in Data.PrimitiveArray.Index.Class | |
(Read a, Read b) => Read (a :> b) Source # | |
(Show a, Show b) => Show (a :> b) Source # | |
Generic (a :> b) Source # | |
(NFData a, NFData b) => NFData (a :> b) Source # | |
Defined in Data.PrimitiveArray.Index.Class | |
(Hashable a, Hashable b) => Hashable (a :> b) Source # | |
Defined in Data.PrimitiveArray.Index.Class | |
(ToJSON a, ToJSON b) => ToJSON (a :> b) Source # | |
Defined in Data.PrimitiveArray.Index.Class | |
(FromJSON a, FromJSON b) => FromJSON (a :> b) Source # | |
(Binary a, Binary b) => Binary (a :> b) Source # | |
(Serialize a, Serialize b) => Serialize (a :> b) Source # | |
(Unbox a, Unbox b) => Unbox (a :> b) Source # | |
Defined in Data.PrimitiveArray.Index.Class | |
newtype MVector s (a :> b) Source # | |
Defined in Data.PrimitiveArray.Index.Class | |
type Rep (a :> b) Source # | |
Defined in Data.PrimitiveArray.Index.Class type Rep (a :> b) = D1 ('MetaData ":>" "Data.PrimitiveArray.Index.Class" "PrimitiveArray-0.10.1.0-8LhqXNFuZNc70s43xh6tNJ" 'False) (C1 ('MetaCons ":>" ('InfixI 'RightAssociative 3) 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b))) | |
newtype Vector (a :> b) Source # | |
Defined in Data.PrimitiveArray.Index.Class |
Base data constructor for multi-dimensional indices.
Instances
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 :: LimitType i -> i -> Int Source #
Given a maximal size, and a current index, calculate the linear index.
fromLinearIndex :: LimitType i -> Int -> i Source #
Given a maximal size and a valid Int
, return the index.
size :: LimitType i -> Int Source #
Given the LimitType
, return the number of cells required for storage.
inBounds :: LimitType i -> i -> Bool Source #
Check if an index is within the bounds.
A lower bound of zero
zeroBound' :: LimitType i Source #
A lower bound of zero
but for a LimitType i
.
totalSize :: LimitType i -> [Integer] Source #
The list of cell sizes for each dimension. its product yields the total size.
showBound :: LimitType i -> [String] Source #
Pretty-print all upper bounds
showIndex :: i -> [String] Source #
Pretty-print all indices
Instances
sizeIsValid :: Monad m => Word -> [[Integer]] -> ExceptT SizeError m CellSize Source #
Given the maximal number of cells (Word
, because this is the pointer
limit for the machine), and the list of sizes, will check if this is still
legal. Consider dividing the Word
by the actual memory requirements for
each cell, to get better exception handling for too large arrays.
One list should be given for each array.
In case totalSize
or variants thereof produce a size that is too big to
handle.
The total number of cells that are allocated.
Instances
Bounded CellSize Source # | |
Enum CellSize Source # | |
Defined in Data.PrimitiveArray.Index.Class | |
Eq CellSize Source # | |
Integral CellSize Source # | |
Defined in Data.PrimitiveArray.Index.Class | |
Num CellSize Source # | |
Ord CellSize Source # | |
Defined in Data.PrimitiveArray.Index.Class | |
Real CellSize Source # | |
Defined in Data.PrimitiveArray.Index.Class toRational :: CellSize -> Rational # | |
Show CellSize Source # | |
class Index i => 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 => LimitType i -> LimitType i -> Stream m i Source #
Generate an index stream using LimitType
s. This prevents having to
figure out how the actual limits for complicated index types (like Set
)
would look like, since for Set
, for example, the LimitType Set == Int
provides just the number of bits.
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 => LimitType i -> LimitType 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.
Instances
Somewhat experimental lens support.
Operations for sparsity.
class SparseBucket sh where Source #
manhattan
turns an index sh
into a starting point within sparseIndices
of the Sparse
data structure. This should reduce the time required to search sparseIndices
, because
manhattanStart[manhattan sh]
yields a left bound, while manhattanStart[manhattan sh +1]
will
yield an excluded right bound.
Uses the Manhattan
distance.
TODO This should probably be moved into the Index
module.
manhattan :: LimitType sh -> sh -> Int Source #
The manhattan distance for an index.
manhattanMax :: LimitType sh -> Int Source #
The maximal possible manhattan distance.
Instances
SparseBucket Z Source # | |
(SparseBucket i, SparseBucket is) => SparseBucket (is :. i) Source # | Manhattan distances add up. |
SparseBucket (PointL O) Source # | TODO Is this instance correct? Outside indices shrink? |
SparseBucket (PointL I) Source # | |