Safe Haskell | None |
---|---|
Language | Haskell2010 |
Biological sequence data is oftentimes indexed either 0-
or
1-
based. The Index
type developed provides static guarantees that
there is no confusion what index is in use.
This module does not export the ctor Index
. If you want to (unsafely)
use it, import Biobase.Types.Index.Type
directly. Use fromInt0
to
make clear that you count from 0 and transform to an Index t
. I.e.
fromInt0 0 :: Index 1
yields the lowest 1-base index.
- checkIndex :: forall t. KnownNat t => Index t -> Index t
- reIndex :: forall n m. (KnownNat n, KnownNat m) => Index n -> Index m
- (+.) :: forall t. KnownNat t => Index t -> Int -> Index t
- unsafePlus :: forall t. KnownNat t => Index t -> Int -> Index t
- (-.) :: forall t. KnownNat t => Index t -> Int -> Index t
- unsafeMinus :: forall t. KnownNat t => Index t -> Int -> Index t
- toInt0 :: forall t. KnownNat t => Index t -> Int
- fromInt0 :: forall t. KnownNat t => Int -> Index t
- type I0 = Index 0
- type I1 = Index 1
- getIndex :: Index t -> Int
- index :: forall t. KnownNat t => Int -> Index t
- maybeIndex :: forall t. KnownNat t => Int -> Maybe (Index t)
- data Index t
Documentation
checkIndex :: forall t. KnownNat t => Index t -> Index t Source
reIndex :: forall n m. (KnownNat n, KnownNat m) => Index n -> Index m Source
Re-Index an index of type Index n
as Index m
. This is always safe,
as 0 :: Index 0
gives 1 :: Index 1
for example. I.e. valid indices
become valid indices.
toInt0 :: forall t. KnownNat t => Index t -> Int Source
Return the index as an Int
-style index that is zero-based.
fromInt0 :: forall t. KnownNat t => Int -> Index t Source
As an index from an Int
-style zero-based one.
TODO We might want to check that the argument is [0..]
.
A linear Int
-based index type.
Vector Vector (Index t) Source | |
MVector MVector (Index t) Source | |
Eq (Index t) Source | |
KnownNat t => Num (Index t) Source | |
Ord (Index t) Source | |
Read (Index t) Source | |
Show (Index t) Source | |
Ix (Index t) Source | |
Generic (Index t) Source | |
KnownNat t => Index (Index t) Source | |
IndexStream (Index t) Source | |
Arbitrary (Index t) Source | |
ToJSON (Index t) Source | |
FromJSON (Index t) Source | |
Binary (Index t) Source | |
Serialize (Index t) Source | |
NFData (Index t) Source | |
Hashable (Index t) Source | |
Unbox (Index t) Source | |
IndexStream z => IndexStream ((:.) z (Index t)) Source | |
data MVector s0 (Index t0) = MV_Index (MVector s Int) Source | |
type Rep (Index t) Source | |
data Vector (Index t0) = V_Index (Vector Int) Source |