| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Biobase.Fasta.Strict
Description
A convenience module for *small* Fasta entries, that are completely in
memory and *not* to be streamed.
The Data.ByteString.Strict.Lens module is very helpful for further
handling of Fasta entries.
For convenience, the convertString function from string-conversions is
supplied.
Synopsis
- data Fasta which ty = Fasta {
- _header :: !(SequenceIdentifier which)
- _fasta :: !(BioSequence ty)
- type FastaUntyped = Fasta Void Void
- fasta :: forall k (which :: k) k (ty :: k) k (ty :: k). Lens (Fasta (which :: k) (ty :: k)) (Fasta (which :: k) (ty :: k)) (BioSequence ty) (BioSequence ty)
- header :: forall k (which :: k) k (ty :: k) k (which :: k). Lens (Fasta (which :: k) (ty :: k)) (Fasta (which :: k) (ty :: k)) (SequenceIdentifier which) (SequenceIdentifier which)
- fastaToByteString :: Int -> Fasta which ty -> ByteString
- fastaToBuilder :: Int -> Fasta which ty -> Builder
- byteStringToFasta :: ByteString -> Either String (Fasta which ty)
- rawFasta :: Int -> Prism' ByteString (Fasta which ty)
- convertString :: ConvertibleStrings a b => a -> b
Documentation
A *strict* Fasta entry.
Constructors
| Fasta | |
Fields
| |
Instances
| Eq (Fasta which ty) Source # | |
| Ord (Fasta which ty) Source # | |
Defined in Biobase.Fasta.Strict Methods compare :: Fasta which ty -> Fasta which ty -> Ordering # (<) :: Fasta which ty -> Fasta which ty -> Bool # (<=) :: Fasta which ty -> Fasta which ty -> Bool # (>) :: Fasta which ty -> Fasta which ty -> Bool # (>=) :: Fasta which ty -> Fasta which ty -> Bool # | |
| Read (Fasta which ty) Source # | |
| Show (Fasta which ty) Source # | |
| Generic (Fasta which ty) Source # | |
| type Rep (Fasta which ty) Source # | |
Defined in Biobase.Fasta.Strict type Rep (Fasta which ty) = D1 ('MetaData "Fasta" "Biobase.Fasta.Strict" "BiobaseFasta-0.4.0.1-I5UInIvAd7s5DuuDcsslQC" 'False) (C1 ('MetaCons "Fasta" 'PrefixI 'True) (S1 ('MetaSel ('Just "_header") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (SequenceIdentifier which)) :*: S1 ('MetaSel ('Just "_fasta") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (BioSequence ty)))) | |
fasta :: forall k (which :: k) k (ty :: k) k (ty :: k). Lens (Fasta (which :: k) (ty :: k)) (Fasta (which :: k) (ty :: k)) (BioSequence ty) (BioSequence ty) Source #
header :: forall k (which :: k) k (ty :: k) k (which :: k). Lens (Fasta (which :: k) (ty :: k)) (Fasta (which :: k) (ty :: k)) (SequenceIdentifier which) (SequenceIdentifier which) Source #
fastaToByteString :: Int -> Fasta which ty -> ByteString Source #
Render a Fasta entry to a ByteString. Will end with a final n in
any case.
fastaToBuilder :: Int -> Fasta which ty -> Builder Source #
Render a Fasta entry to a Builder. Will end with a final n in
any case.
byteStringToFasta :: ByteString -> Either String (Fasta which ty) Source #
Try to parse a ByteString as a Fasta, failing with Left, succees
with Right.
rawFasta :: Int -> Prism' ByteString (Fasta which ty) Source #
Try to parse a ByteString as multiple Fasta entries. Even though this
is using the underlying streaming interface, this is not streaming.
A lens that goes from a BioSequenceWindow to a Fasta.
A prism from a ByteString to a Fasta. Note that this will only be an
identity if the underlying fasta file is rendered with k characters per
line.
convertString :: ConvertibleStrings a b => a -> b #