BiobaseTypes-0.1.2.1: Collection of types for bioinformatics

Safe HaskellNone
LanguageHaskell2010

Biobase.Types.Index.Type

Synopsis

Documentation

newtype Index t Source #

A linear Int-based index type.

Constructors

Index 

Fields

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)

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.