BiobaseTypes-0.2.1.0: Collection of types for bioinformatics
Safe HaskellNone
LanguageHaskell2010

Biobase.Types.Index.Type

Synopsis

Documentation

newtype Index (t :: Nat) Source #

A linear Int-based index type.

Constructors

Index 

Fields

Instances

Instances details
Vector Vector (Index t) Source # 
Instance details

Defined in Biobase.Types.Index.Type

MVector MVector (Index t) Source # 
Instance details

Defined in Biobase.Types.Index.Type

Eq (Index t) Source # 
Instance details

Defined in Biobase.Types.Index.Type

Methods

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

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

KnownNat t => Data (Index t) Source # 
Instance details

Defined in Biobase.Types.Index.Type

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Index t -> c (Index t) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Index t) #

toConstr :: Index t -> Constr #

dataTypeOf :: Index t -> DataType #

dataCast1 :: Typeable t0 => (forall d. Data d => c (t0 d)) -> Maybe (c (Index t)) #

dataCast2 :: Typeable t0 => (forall d e. (Data d, Data e) => c (t0 d e)) -> Maybe (c (Index t)) #

gmapT :: (forall b. Data b => b -> b) -> Index t -> Index t #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Index t -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Index t -> r #

gmapQ :: (forall d. Data d => d -> u) -> Index t -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Index t -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Index t -> m (Index t) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Index t -> m (Index t) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Index t -> m (Index t) #

KnownNat t => Num (Index t) Source # 
Instance details

Defined in Biobase.Types.Index.Type

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 # 
Instance details

Defined in Biobase.Types.Index.Type

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 # 
Instance details

Defined in Biobase.Types.Index.Type

Show (Index t) Source # 
Instance details

Defined in Biobase.Types.Index.Type

Methods

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

show :: Index t -> String #

showList :: [Index t] -> ShowS #

Ix (Index t) Source # 
Instance details

Defined in Biobase.Types.Index.Type

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 # 
Instance details

Defined in Biobase.Types.Index.Type

Associated Types

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

Methods

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

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

KnownNat t => Index (Index t) Source # 
Instance details

Defined in Biobase.Types.Index.Type

Associated Types

data LimitType (Index t) #

KnownNat t => IndexStream (Index t) Source # 
Instance details

Defined in Biobase.Types.Index.Type

Methods

streamUp :: forall (m :: Type -> Type). Monad m => LimitType (Index t) -> LimitType (Index t) -> Stream m (Index t) #

streamDown :: forall (m :: Type -> Type). Monad m => LimitType (Index t) -> LimitType (Index t) -> Stream m (Index t) #

Arbitrary (Index t) Source # 
Instance details

Defined in Biobase.Types.Index.Type

Methods

arbitrary :: Gen (Index t) #

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

Hashable (Index t) Source # 
Instance details

Defined in Biobase.Types.Index.Type

Methods

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

hash :: Index t -> Int #

ToJSON (Index t) Source # 
Instance details

Defined in Biobase.Types.Index.Type

FromJSON (Index t) Source # 
Instance details

Defined in Biobase.Types.Index.Type

Binary (Index t) Source # 
Instance details

Defined in Biobase.Types.Index.Type

Methods

put :: Index t -> Put #

get :: Get (Index t) #

putList :: [Index t] -> Put #

Serialize (Index t) Source # 
Instance details

Defined in Biobase.Types.Index.Type

Methods

put :: Putter (Index t) #

get :: Get (Index t) #

NFData (Index t) Source # 
Instance details

Defined in Biobase.Types.Index.Type

Methods

rnf :: Index t -> () #

Unbox (Index t) Source # 
Instance details

Defined in Biobase.Types.Index.Type

(KnownNat t, IndexStream z) => IndexStream (z :. Index t) Source # 
Instance details

Defined in Biobase.Types.Index.Type

Methods

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

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

newtype MVector s (Index t) Source # 
Instance details

Defined in Biobase.Types.Index.Type

newtype MVector s (Index t) = MV_Index (MVector s Int)
type Rep (Index t) Source # 
Instance details

Defined in Biobase.Types.Index.Type

type Rep (Index t) = D1 ('MetaData "Index" "Biobase.Types.Index.Type" "BiobaseTypes-0.2.1.0-KNWEaQoA0aY419BnftjfF1" 'True) (C1 ('MetaCons "Index" 'PrefixI 'True) (S1 ('MetaSel ('Just "getIndex") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))
newtype LimitType (Index t) Source # 
Instance details

Defined in Biobase.Types.Index.Type

newtype LimitType (Index t) = LtIndex Int
newtype Vector (Index t) Source # 
Instance details

Defined in Biobase.Types.Index.Type

newtype Vector (Index t) = 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.