cobot-io-0.1.5.1: Biological data file formats and IO
Safe HaskellSafe-Inferred
LanguageHaskell2010

Bio.Sequence.Class

Synopsis

Documentation

class IsSequence s => SequenceDecodable a s where Source #

Class that allows to decode something into Sequence representation

Methods

sequenceDecode :: a -> Either Text s Source #

Instances

Instances details
SequenceDecodable ByteString BasecalledSequence Source #

Converts ByteString (that should be content of ABI file) into BasecalledSequence.

Instance details

Defined in Bio.ABI.Decode

SequenceDecodable ByteString BasecalledSequence Source #

Converts ByteString (that should be content of ABI file) into BasecalledSequence.

Instance details

Defined in Bio.ABI.Decode

SequenceDecodable BasecalledSequenceWithRawData BasecalledSequence Source #

Discards raw data information.

Instance details

Defined in Bio.ABI.Decode

data Sequence mk w a Source #

Instances

Instances details
Foldable (Sequence mk w) Source # 
Instance details

Defined in Bio.Sequence.Class

Methods

fold :: Monoid m => Sequence mk w m -> m #

foldMap :: Monoid m => (a -> m) -> Sequence mk w a -> m #

foldMap' :: Monoid m => (a -> m) -> Sequence mk w a -> m #

foldr :: (a -> b -> b) -> b -> Sequence mk w a -> b #

foldr' :: (a -> b -> b) -> b -> Sequence mk w a -> b #

foldl :: (b -> a -> b) -> b -> Sequence mk w a -> b #

foldl' :: (b -> a -> b) -> b -> Sequence mk w a -> b #

foldr1 :: (a -> a -> a) -> Sequence mk w a -> a #

foldl1 :: (a -> a -> a) -> Sequence mk w a -> a #

toList :: Sequence mk w a -> [a] #

null :: Sequence mk w a -> Bool #

length :: Sequence mk w a -> Int #

elem :: Eq a => a -> Sequence mk w a -> Bool #

maximum :: Ord a => Sequence mk w a -> a #

minimum :: Ord a => Sequence mk w a -> a #

sum :: Num a => Sequence mk w a -> a #

product :: Num a => Sequence mk w a -> a #

Traversable (Sequence mk w) Source # 
Instance details

Defined in Bio.Sequence.Class

Methods

traverse :: Applicative f => (a -> f b) -> Sequence mk w a -> f (Sequence mk w b) #

sequenceA :: Applicative f => Sequence mk w (f a) -> f (Sequence mk w a) #

mapM :: Monad m => (a -> m b) -> Sequence mk w a -> m (Sequence mk w b) #

sequence :: Monad m => Sequence mk w (m a) -> m (Sequence mk w a) #

Functor (Sequence mk w) Source # 
Instance details

Defined in Bio.Sequence.Class

Methods

fmap :: (a -> b) -> Sequence mk w a -> Sequence mk w b #

(<$) :: a -> Sequence mk w b -> Sequence mk w a #

Monoid (Sequence mk () a) Source # 
Instance details

Defined in Bio.Sequence.Class

Methods

mempty :: Sequence mk () a #

mappend :: Sequence mk () a -> Sequence mk () a -> Sequence mk () a #

mconcat :: [Sequence mk () a] -> Sequence mk () a #

Semigroup (Sequence mk w a) Source # 
Instance details

Defined in Bio.Sequence.Class

Methods

(<>) :: Sequence mk w a -> Sequence mk w a -> Sequence mk w a #

sconcat :: NonEmpty (Sequence mk w a) -> Sequence mk w a #

stimes :: Integral b => b -> Sequence mk w a -> Sequence mk w a #

Generic (Sequence mk w a) Source # 
Instance details

Defined in Bio.Sequence.Class

Associated Types

type Rep (Sequence mk w a) :: Type -> Type #

Methods

from :: Sequence mk w a -> Rep (Sequence mk w a) x #

to :: Rep (Sequence mk w a) x -> Sequence mk w a #

(Show a, Show mk, Show w) => Show (Sequence mk w a) Source # 
Instance details

Defined in Bio.Sequence.Class

Methods

showsPrec :: Int -> Sequence mk w a -> ShowS #

show :: Sequence mk w a -> String #

showList :: [Sequence mk w a] -> ShowS #

(IsMarking mk, IsWeight w) => IsSequence (Sequence mk w a) Source # 
Instance details

Defined in Bio.Sequence.Class

Associated Types

type Element (Sequence mk w a) Source #

type Marking (Sequence mk w a) Source #

type Weight (Sequence mk w a) Source #

Methods

toSequence :: Sequence mk w a -> Sequence (Marking (Sequence mk w a)) (Weight (Sequence mk w a)) (Element (Sequence mk w a)) Source #

fromSequence :: Sequence (Marking (Sequence mk w a)) (Weight (Sequence mk w a)) (Element (Sequence mk w a)) -> Sequence mk w a Source #

(NFData a, NFData mk, NFData w) => NFData (Sequence mk w a) Source # 
Instance details

Defined in Bio.Sequence.Class

Methods

rnf :: Sequence mk w a -> () #

(Eq a, Eq mk, Eq w) => Eq (Sequence mk w a) Source # 
Instance details

Defined in Bio.Sequence.Class

Methods

(==) :: Sequence mk w a -> Sequence mk w a -> Bool #

(/=) :: Sequence mk w a -> Sequence mk w a -> Bool #

type Rep (Sequence mk w a) Source # 
Instance details

Defined in Bio.Sequence.Class

type Rep (Sequence mk w a) = D1 ('MetaData "Sequence" "Bio.Sequence.Class" "cobot-io-0.1.5.1-18rT459IEbVDuf0SicXNND" 'False) (C1 ('MetaCons "Sequence" 'PrefixI 'True) (S1 ('MetaSel ('Just "_sequ") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Vector a)) :*: (S1 ('MetaSel ('Just "_markings") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(mk, Range)]) :*: S1 ('MetaSel ('Just "_weights") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Vector w)))))
type Element (Sequence mk w a) Source # 
Instance details

Defined in Bio.Sequence.Class

type Element (Sequence mk w a) = a
type Marking (Sequence mk w a) Source # 
Instance details

Defined in Bio.Sequence.Class

type Marking (Sequence mk w a) = mk
type Weight (Sequence mk w a) Source # 
Instance details

Defined in Bio.Sequence.Class

type Weight (Sequence mk w a) = w

type WeightedSequence w a = Sequence () w a Source #

Type alias for sequence that has no marking but is weighted.

type MarkedSequence mk a = Sequence mk () a Source #

Type alias for sequence that is not weighted, but has markings.

type BareSequence a = Sequence () () a Source #

Type alias for sequence that is not weighted and has no markings.

data Range Source #

Instances

Instances details
Generic Range Source # 
Instance details

Defined in Bio.Sequence.Range

Associated Types

type Rep Range :: Type -> Type #

Methods

from :: Range -> Rep Range x #

to :: Rep Range x -> Range #

Show Range Source # 
Instance details

Defined in Bio.Sequence.Range

Methods

showsPrec :: Int -> Range -> ShowS #

show :: Range -> String #

showList :: [Range] -> ShowS #

NFData Range Source # 
Instance details

Defined in Bio.Sequence.Range

Methods

rnf :: Range -> () #

Eq Range Source # 
Instance details

Defined in Bio.Sequence.Range

Methods

(==) :: Range -> Range -> Bool #

(/=) :: Range -> Range -> Bool #

type Rep Range Source # 
Instance details

Defined in Bio.Sequence.Range

sequ :: Getter (Sequence mk w a) (Vector a) Source #

markings :: Getter (Sequence mk w a) [(mk, Range)] Source #

class (Eq mk, Ord mk) => IsMarking mk Source #

Class that reprsents objects that can be markings of IsSequence.

Instances

Instances details
IsMarking Feature Source # 
Instance details

Defined in Bio.GB.Type

IsMarking () Source # 
Instance details

Defined in Bio.Sequence.Class

class IsWeight w where Source #

Class that represents objects that can be weights of IsSequences Elements.

Methods

toDouble :: w -> Double Source #

Instances

Instances details
IsWeight () Source # 
Instance details

Defined in Bio.Sequence.Class

Methods

toDouble :: () -> Double Source #

IsWeight Double Source # 
Instance details

Defined in Bio.Sequence.Class

class (IsMarking (Marking s), IsWeight (Weight s)) => IsSequence s where Source #

Type class that describes object that is isomorphisc to Sequence and contains elements of type Element, is marked with marking of type Marking and is weighted with weights of type Weight.

Special cases, when IsSequence has no markings, has no weights, or has no weights and no markings at the same time are aliased: * IsWeightedSequence is alias for sequence with Marking type set to () and Weight not set to () * IsMarkedSequence is alias for sequence with Weight type set to () and Marking not set to (). * IsBareSequence is alias for sequence with Marking and Weight types set to ().

Instances of IsSequence can be built only using special constructors: * createSequence creates IsSequence that has Marking and Weight that are not set to (). * bareSequence creates IsSequence that has Marking and Weight that are set to (). * weightedSequence creates IsSequence that has Marking set to () and Weight that is not (). * markedSequence creates IsSequence that has Weight set to () and Marking that is not ().

Constraints and constructors mentioned above gaurantee that IsSequence instances that have no Weights will in compile-time have () as types assosiated with their Weights. That is used to make functions that rely on IsSequence instance having not null weights type-safe.

Associated Types

type Element s :: Type Source #

type Marking s :: Type Source #

type Weight s :: Type Source #

type IsWeightedSequence s = (IsSequence s, Unit (Marking s), NotUnit (Weight s)) Source #

Type alias for constraint that checks whether given instance of IsSequence has no markings, but is weighted.

type IsMarkedSequence s = (IsSequence s, NotUnit (Marking s), Unit (Weight s)) Source #

Type alias for constraint that checks whether given instance of IsSequence has markings, but is not weighted.

type IsBareSequence s = (IsSequence s, Unit (Marking s), Unit (Weight s)) Source #

Type alias for constraint that checks whether given instance of IsSequence has no markings and is not weighted.

type ContainsMarking s = (IsSequence s, NotUnit (Marking s)) Source #

Type alias for constraint that checks whether given instance s of IsSequence has markings, weights of s are not checked.

type ContainsNoMarking s = (IsSequence s, Unit (Marking s)) Source #

Type alias for constraint that checks whether given instance s of IsSequence has no markings, weights of s are not checked.

type ContainsWeight s = (IsSequence s, NotUnit (Weight s)) Source #

Type alias for constraint that checks whether given instance s of IsSequence has weights, markings of s are not checked.

type ContainsNoWeight s = (IsSequence s, Unit (Weight s)) Source #

Type alias for constraint that checks whether given instance s of IsSequence has no weights, markings of s are not checked.

createSequence :: (ContainsMarking s, ContainsWeight s, MonadError Text m) => [Element s] -> [(Marking s, Range)] -> [Weight s] -> m s Source #

Create IsSequence s that has both markings and weights. If any of the markings is invalid or length of weights list is not equal to length of sequence, an error will be thrown.

bareSequence :: IsBareSequence s => [Element s] -> s Source #

Create IsBareSequence s, simple sequence without markings and weights.

weightedSequence :: (IsWeightedSequence s, MonadError Text m) => [Element s] -> [Weight s] -> m s Source #

Create IsWeightedSequence s from list of Elements and Weights that correspond to each Element. If length of list of Weights is not equal to length of sequence or lis is null, an error will be thrown.

markedSequence :: (IsMarkedSequence s, MonadError Text m) => [Element s] -> [(Marking s, Range)] -> m s Source #

Create IsMarkedSequence s from list of Elements and Markings that mark it. If at least one of ranges in given list of Markings is out of bounds, an error will be thrown.

_sequenceInner :: Vector a -> [(mk, Range)] -> Vector w -> Sequence mk w a Source #

Exported constructor for Sequence. Should be used ONLY in module Bio.Sequence.