Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data Sequence mk w a
- class (IsMarking (Marking s), IsWeight (Weight s)) => IsSequence s where
- data Range
- class IsSequence s => SequenceDecodable a s where
- sequenceDecode :: a -> Either Text s
- type BareSequence a = Sequence () () a
- type MarkedSequence mk a = Sequence mk () a
- class (Eq mk, Ord mk) => IsMarking mk
- type WeightedSequence w a = Sequence () w a
- class IsWeight w where
- type IsWeightedSequence s = (IsSequence s, Unit (Marking s), NotUnit (Weight s))
- type IsMarkedSequence s = (IsSequence s, NotUnit (Marking s), Unit (Weight s))
- type IsBareSequence s = (IsSequence s, Unit (Marking s), Unit (Weight s))
- type ContainsMarking s = (IsSequence s, NotUnit (Marking s))
- type ContainsNoMarking s = (IsSequence s, Unit (Marking s))
- type ContainsWeight s = (IsSequence s, NotUnit (Weight s))
- type ContainsNoWeight s = (IsSequence s, Unit (Weight s))
- weightedSequence :: (IsWeightedSequence s, MonadError Text m) => [Element s] -> [Weight s] -> m s
- bareSequence :: IsBareSequence s => [Element s] -> s
- sequ :: Getter (Sequence mk w a) (Vector a)
- markedSequence :: (IsMarkedSequence s, MonadError Text m) => [Element s] -> [(Marking s, Range)] -> m s
- markings :: Getter (Sequence mk w a) [(mk, Range)]
- weights :: Getter (Sequence mk w a) (Vector w)
- bareSequ :: Lens' (BareSequence a) (Vector a)
- createSequence :: (ContainsMarking s, ContainsWeight s, MonadError Text m) => [Element s] -> [(Marking s, Range)] -> [Weight s] -> m s
- unsafeCreateSequence :: (ContainsMarking s, ContainsWeight s) => [Element s] -> [(Marking s, Range)] -> [Weight s] -> s
- unsafeWeightedSequence :: IsWeightedSequence s => [Element s] -> [Weight s] -> s
- unsafeMarkedSequence :: IsMarkedSequence s => [Element s] -> [(Marking s, Range)] -> s
- module Bio.Sequence.Functions.Sequence
- module Bio.Sequence.Functions.Weight
- module Bio.Sequence.Functions.Marking
- module Bio.Sequence.Range
Documentation
Instances
Foldable (Sequence mk w) Source # | |
Defined in Bio.Sequence.Class 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 # | |
Traversable (Sequence mk w) Source # | |
Defined in Bio.Sequence.Class | |
Functor (Sequence mk w) Source # | |
Monoid (Sequence mk () a) Source # | |
Semigroup (Sequence mk w a) Source # | |
Generic (Sequence mk w a) Source # | |
(Show a, Show mk, Show w) => Show (Sequence mk w a) Source # | |
(IsMarking mk, IsWeight w) => IsSequence (Sequence mk w a) Source # | |
(NFData a, NFData mk, NFData w) => NFData (Sequence mk w a) Source # | |
Defined in Bio.Sequence.Class | |
(Eq a, Eq mk, Eq w) => Eq (Sequence mk w a) Source # | |
(Ord a, Ord mk, Ord w) => Ord (Sequence mk w a) Source # | |
Defined in Bio.Sequence.Class compare :: Sequence mk w a -> Sequence mk w a -> Ordering # (<) :: Sequence mk w a -> Sequence mk w a -> Bool # (<=) :: Sequence mk w a -> Sequence mk w a -> Bool # (>) :: Sequence mk w a -> Sequence mk w a -> Bool # (>=) :: Sequence mk w a -> Sequence mk w a -> Bool # max :: Sequence mk w a -> Sequence mk w a -> Sequence mk w a # min :: Sequence mk w a -> Sequence mk w a -> Sequence mk w a # | |
type Rep (Sequence mk w a) Source # | |
Defined in Bio.Sequence.Class type Rep (Sequence mk w a) = D1 ('MetaData "Sequence" "Bio.Sequence.Class" "cobot-io-0.1.5.5-2fgiMxNKBm19YNVvDwIPRV" '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 # | |
Defined in Bio.Sequence.Class | |
type Marking (Sequence mk w a) Source # | |
Defined in Bio.Sequence.Class | |
type Weight (Sequence mk w a) Source # | |
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 Weight
s will in compile-time
have () as types assosiated with their Weight
s.
That is used to make functions that rely on IsSequence
instance
having not null weights type-safe.
toSequence :: s -> Sequence (Marking s) (Weight s) (Element s) Source #
fromSequence :: Sequence (Marking s) (Weight s) (Element s) -> s Source #
Instances
IsSequence BasecalledSequence Source # | |
Defined in Bio.Sequence.Basecalled.Type type Element BasecalledSequence Source # type Marking BasecalledSequence Source # type Weight BasecalledSequence Source # | |
(IsMarking mk, IsWeight w) => IsSequence (Sequence mk w a) Source # | |
Instances
class IsSequence s => SequenceDecodable a s where Source #
Class that allows to decode something into Sequence representation
sequenceDecode :: a -> Either Text s Source #
Instances
SequenceDecodable ByteString BasecalledSequence Source # | Converts |
Defined in Bio.ABI.Decode | |
SequenceDecodable ByteString BasecalledSequence Source # | Converts |
Defined in Bio.ABI.Decode | |
SequenceDecodable BasecalledSequenceWithRawData BasecalledSequence Source # | Discards raw data information. |
Defined in Bio.ABI.Decode |
type BareSequence a = Sequence () () a Source #
Type alias for sequence that is not weighted and has no markings.
type MarkedSequence mk a = Sequence mk () a Source #
Type alias for sequence that is not weighted, but has markings.
class (Eq mk, Ord mk) => IsMarking mk Source #
Class that reprsents objects that can be markings of IsSequence
.
Instances
IsMarking Feature Source # | |
Defined in Bio.GB.Type | |
IsMarking () Source # | |
Defined in Bio.Sequence.Class |
type WeightedSequence w a = Sequence () w a Source #
Type alias for sequence that has no marking but is weighted.
class IsWeight w where Source #
Class that represents objects that can be weights of IsSequence
s Element
s.
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.
weightedSequence :: (IsWeightedSequence s, MonadError Text m) => [Element s] -> [Weight s] -> m s Source #
Create IsWeightedSequence
s
from list of Element
s and Weight
s
that correspond to each Element
. If length of list of Weight
s
is not equal to length of sequence or lis is null, an error will be thrown.
bareSequence :: IsBareSequence s => [Element s] -> s Source #
Create IsBareSequence
s
, simple sequence without markings and weights.
markedSequence :: (IsMarkedSequence s, MonadError Text m) => [Element s] -> [(Marking s, Range)] -> m s Source #
Create IsMarkedSequence
s
from list of Element
s and Marking
s that
mark it. If at least one of ranges in given list of Marking
s is out of bounds,
an error will be thrown.
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.
unsafeCreateSequence :: (ContainsMarking s, ContainsWeight s) => [Element s] -> [(Marking s, Range)] -> [Weight s] -> s Source #
unsafeWeightedSequence :: IsWeightedSequence s => [Element s] -> [Weight s] -> s Source #
unsafeMarkedSequence :: IsMarkedSequence s => [Element s] -> [(Marking s, Range)] -> s Source #
module Bio.Sequence.Range