BiobaseTypes-0.1.2.1: Collection of types for bioinformatics

Safe HaskellNone
LanguageHaskell2010

Biobase.Types.Index

Description

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.

Synopsis

Documentation

checkIndex :: forall t. KnownNat t => Index t -> Index t Source #

Uses index to guarantee that the Index is ok.

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.

(+.) :: forall t. KnownNat t => Index t -> Int -> Index t Source #

Helper function that allows addition of an Index and an Int, with the Int on the right.

unsafePlus :: forall t. KnownNat t => Index t -> Int -> Index t Source #

Unsafe plus.

(-.) :: forall t. KnownNat t => Index t -> Int -> Index t Source #

Helper function that allows subtraction of an Index and an Int, with the Int on the right.

delta :: forall t. KnownNat t => Index t -> Index t -> Int Source #

Delta between two Index points.

unsafeMinus :: forall t. KnownNat t => Index t -> Int -> Index t Source #

Unsafe minus.

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..].

type I0 = Index 0 Source #

Zero-based indices.

type I1 = Index 1 Source #

One-based indices.

index :: forall t. KnownNat t => Int -> Index t Source #

Turn an Int into an Index safely.

maybeIndex :: forall t. KnownNat t => Int -> Maybe (Index t) Source #

Produce Just and Index or Nothing.

data Index t Source #

A linear Int-based index type.

Instances

Vector Vector (Index t0) Source # 

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (Index t0) -> m (Vector (Index t0)) #

basicUnsafeThaw :: PrimMonad m => Vector (Index t0) -> m (Mutable Vector (PrimState m) (Index t0)) #

basicLength :: Vector (Index t0) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (Index t0) -> Vector (Index t0) #

basicUnsafeIndexM :: Monad m => Vector (Index t0) -> Int -> m (Index t0) #

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (Index t0) -> Vector (Index t0) -> m () #

elemseq :: Vector (Index t0) -> Index t0 -> b -> b #

MVector MVector (Index t0) Source # 

Methods

basicLength :: MVector s (Index t0) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (Index t0) -> MVector s (Index t0) #

basicOverlaps :: MVector s (Index t0) -> MVector s (Index t0) -> Bool #

basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) (Index t0)) #

basicInitialize :: PrimMonad m => MVector (PrimState m) (Index t0) -> m () #

basicUnsafeReplicate :: PrimMonad m => Int -> Index t0 -> m (MVector (PrimState m) (Index t0)) #

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (Index t0) -> Int -> m (Index t0) #

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (Index t0) -> Int -> Index t0 -> m () #

basicClear :: PrimMonad m => MVector (PrimState m) (Index t0) -> m () #

basicSet :: PrimMonad m => MVector (PrimState m) (Index t0) -> Index t0 -> m () #

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (Index t0) -> MVector (PrimState m) (Index t0) -> m () #

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (Index t0) -> MVector (PrimState m) (Index t0) -> m () #

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (Index t0) -> Int -> m (MVector (PrimState m) (Index t0)) #

Eq (Index t) Source # 

Methods

(==) :: Index t -> Index t -> Bool #

(/=) :: Index t -> Index t -> Bool #

KnownNat t => Num (Index t) Source # 

Methods

(+) :: Index t -> Index t -> Index t #

(-) :: Index t -> Index t -> Index t #

(*) :: Index t -> Index t -> Index t #

negate :: Index t -> Index t #

abs :: Index t -> Index t #

signum :: Index t -> Index t #

fromInteger :: Integer -> Index t #

Ord (Index t) Source # 

Methods

compare :: Index t -> Index t -> Ordering #

(<) :: Index t -> Index t -> Bool #

(<=) :: Index t -> Index t -> Bool #

(>) :: Index t -> Index t -> Bool #

(>=) :: Index t -> Index t -> Bool #

max :: Index t -> Index t -> Index t #

min :: Index t -> Index t -> Index t #

Read (Index t) Source # 
Show (Index t) Source # 

Methods

showsPrec :: Int -> Index t -> ShowS #

show :: Index t -> String #

showList :: [Index t] -> ShowS #

Ix (Index t) Source # 

Methods

range :: (Index t, Index t) -> [Index t] #

index :: (Index t, Index t) -> Index t -> Int #

unsafeIndex :: (Index t, Index t) -> Index t -> Int

inRange :: (Index t, Index t) -> Index t -> Bool #

rangeSize :: (Index t, Index t) -> Int #

unsafeRangeSize :: (Index t, Index t) -> Int

Generic (Index t) Source # 

Associated Types

type Rep (Index t) :: * -> * #

Methods

from :: Index t -> Rep (Index t) x #

to :: Rep (Index t) x -> Index t #

KnownNat t => Index (Index t) Source # 

Methods

linearIndex :: Index t -> Index t -> Index t -> Int #

smallestLinearIndex :: Index t -> Int #

largestLinearIndex :: Index t -> Int #

size :: Index t -> Index t -> Int #

inBounds :: Index t -> Index t -> Index t -> Bool #

IndexStream (Index t) Source # 

Methods

streamUp :: Monad m => Index t -> Index t -> Stream m (Index t) #

streamDown :: Monad m => Index t -> Index t -> Stream m (Index t) #

Arbitrary (Index t) Source # 

Methods

arbitrary :: Gen (Index t) #

shrink :: Index t -> [Index t] #

Hashable (Index t) Source # 

Methods

hashWithSalt :: Int -> Index t -> Int #

hash :: Index t -> Int #

ToJSON (Index t) Source # 
FromJSON (Index t) Source # 
Binary (Index t) Source # 

Methods

put :: Index t -> Put #

get :: Get (Index t) #

putList :: [Index t] -> Put #

Serialize (Index t) Source # 

Methods

put :: Putter (Index t) #

get :: Get (Index t) #

NFData (Index t) Source # 

Methods

rnf :: Index t -> () #

Unbox (Index t0) Source # 
IndexStream z => IndexStream ((:.) z (Index t)) Source # 

Methods

streamUp :: Monad m => (z :. Index t) -> (z :. Index t) -> Stream m (z :. Index t) #

streamDown :: Monad m => (z :. Index t) -> (z :. Index t) -> Stream m (z :. Index t) #

data MVector s (Index t0) Source # 
data MVector s (Index t0) = MV_Index (MVector s Int)
type Rep (Index t) Source # 
type Rep (Index t) = D1 (MetaData "Index" "Biobase.Types.Index.Type" "BiobaseTypes-0.1.2.1-1LTYzU1e5OWItpBBqXiV1g" True) (C1 (MetaCons "Index" PrefixI True) (S1 (MetaSel (Just Symbol "getIndex") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))
data Vector (Index t0) Source # 
data Vector (Index t0) = V_Index (Vector Int)