BiobaseFasta-0.4.0.1: streaming FASTA parser
Safe HaskellNone
LanguageHaskell2010

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

Documentation

data Fasta which ty Source #

A *strict* Fasta entry.

Constructors

Fasta 

Fields

Instances

Instances details
Eq (Fasta which ty) Source # 
Instance details

Defined in Biobase.Fasta.Strict

Methods

(==) :: Fasta which ty -> Fasta which ty -> Bool #

(/=) :: Fasta which ty -> Fasta which ty -> Bool #

Ord (Fasta which ty) Source # 
Instance details

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 #

max :: Fasta which ty -> Fasta which ty -> Fasta which ty #

min :: Fasta which ty -> Fasta which ty -> Fasta which ty #

Read (Fasta which ty) Source # 
Instance details

Defined in Biobase.Fasta.Strict

Methods

readsPrec :: Int -> ReadS (Fasta which ty) #

readList :: ReadS [Fasta which ty] #

readPrec :: ReadPrec (Fasta which ty) #

readListPrec :: ReadPrec [Fasta which ty] #

Show (Fasta which ty) Source # 
Instance details

Defined in Biobase.Fasta.Strict

Methods

showsPrec :: Int -> Fasta which ty -> ShowS #

show :: Fasta which ty -> String #

showList :: [Fasta which ty] -> ShowS #

Generic (Fasta which ty) Source # 
Instance details

Defined in Biobase.Fasta.Strict

Associated Types

type Rep (Fasta which ty) :: Type -> Type #

Methods

from :: Fasta which ty -> Rep (Fasta which ty) x #

to :: Rep (Fasta which ty) x -> Fasta which ty #

type Rep (Fasta which ty) Source # 
Instance details

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))))

type FastaUntyped = Fasta Void Void Source #

If you don't want to deal with the phantom types.

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.