Safe Haskell | None |
---|---|
Language | Haskell2010 |
Encoding of tabular NCBI BLAST+ output
Synopsis
- jsonLower :: Value -> Value
- newtype BlastJSON2 = BlastJSON2 {}
- newtype BlastCmdJSON2 = BlastCmdJSON2 {}
- newtype BlastOutput2 = BlastOutput2 {}
- data BlastReport = BlastReport {
- _program :: !Text
- _version :: !Text
- _reference :: !Text
- _search_target :: !SearchTarget
- _params :: !Params
- _results :: !BlastJSONResult
- newtype SearchTarget = SearchTarget {}
- data Params = Params {}
- data BlastJSONResult = BlastJSONResult {}
- data Search = Search {
- _query_id :: !Text
- _query_title :: !Text
- _query_len :: !Int
- _hits :: Seq Hit
- _stat :: !SearchStat
- data Hit = Hit {
- _num :: !Int
- _description :: ![HitDescription]
- _len :: !Int
- _hsps :: ![Hsp]
- data Hsp = Hsp {}
- data HitDescription = HitDescription {}
- data SearchStat = SearchStat {}
- data BlastTabularResult = BlastTabularResult {}
- data BlastTabularHit = BlastTabularHit {
- _queryId :: !ByteString
- _subjectId :: !ByteString
- _seqIdentity :: !Double
- _alignmentLength :: !Int
- _misMatches :: !Int
- _gapOpenScore :: !Int
- _queryStart :: !Int
- _queryEnd :: !Int
- _hitSeqStart :: !Int
- _hitSeqEnd :: !Int
- _eValue :: !Double
- _bitScore :: !Double
- _subjectFrame :: !Int
- _querySeq :: !ByteString
- _subjectSeq :: !ByteString
- data BlastProgram
- blastcmdoutput2 :: Iso' BlastCmdJSON2 [BlastOutput2]
- blastoutput2 :: Iso' BlastJSON2 BlastOutput2
- report :: Iso' BlastOutput2 BlastReport
- version :: Lens' BlastReport Text
- search_target :: Lens' BlastReport SearchTarget
- results :: Lens' BlastReport BlastJSONResult
- reference :: Lens' BlastReport Text
- program :: Lens' BlastReport Text
- params :: Lens' BlastReport Params
- sc_mismatch :: Lens' Params Int
- sc_match :: Lens' Params Int
- gap_open :: Lens' Params Int
- gap_extend :: Lens' Params Int
- filter :: Lens' Params Text
- expect :: Lens' Params Double
- search :: Iso' BlastJSONResult Search
- stat :: Lens' Search SearchStat
- query_title :: Lens' Search Text
- query_len :: Lens' Search Int
- query_id :: Lens' Search Text
- hits :: Lens' Search (Seq Hit)
- num :: Lens' Hit Int
- len :: Lens' Hit Int
- hsps :: Lens' Hit [Hsp]
- description :: Lens' Hit [HitDescription]
- score :: Lens' Hsp Int
- query_to :: Lens' Hsp Int
- query_strand :: Lens' Hsp Text
- query_from :: Lens' Hsp Int
- qseq :: Lens' Hsp Text
- midline :: Lens' Hsp Text
- identity :: Lens' Hsp Int
- hsp_num :: Lens' Hsp Int
- hseq :: Lens' Hsp Text
- hit_to :: Lens' Hsp Int
- hit_strand :: Lens' Hsp Text
- hit_from :: Lens' Hsp Int
- gaps :: Lens' Hsp Int
- evalue :: Lens' Hsp Double
- bit_score :: Lens' Hsp Double
- align_len :: Lens' Hsp Int
- title :: Lens' HitDescription Text
- taxid :: Lens' HitDescription (Maybe Int)
- id :: Lens' HitDescription Text
- accession :: Lens' HitDescription Text
- lambda :: Lens' SearchStat Double
- kappa :: Lens' SearchStat Double
- hsp_len :: Lens' SearchStat Int
- entropy :: Lens' SearchStat Double
- eff_space :: Lens' SearchStat Int
- db_num :: Lens' SearchStat Int
- db_len :: Lens' SearchStat Int
- hitLines :: Lens' BlastTabularResult (Vector BlastTabularHit)
- blastQueryId :: Lens' BlastTabularResult ByteString
- blastProgram :: Lens' BlastTabularResult BlastProgram
- blastHitNumber :: Lens' BlastTabularResult Int
- blastDatabase :: Lens' BlastTabularResult ByteString
- subjectSeq :: Lens' BlastTabularHit ByteString
- subjectId :: Lens' BlastTabularHit ByteString
- subjectFrame :: Lens' BlastTabularHit Int
- seqIdentity :: Lens' BlastTabularHit Double
- queryStart :: Lens' BlastTabularHit Int
- querySeq :: Lens' BlastTabularHit ByteString
- queryId :: Lens' BlastTabularHit ByteString
- queryEnd :: Lens' BlastTabularHit Int
- misMatches :: Lens' BlastTabularHit Int
- hitSeqStart :: Lens' BlastTabularHit Int
- hitSeqEnd :: Lens' BlastTabularHit Int
- gapOpenScore :: Lens' BlastTabularHit Int
- eValue :: Lens' BlastTabularHit Double
- bitScore :: Lens' BlastTabularHit Double
- alignmentLength :: Lens' BlastTabularHit Int
- db :: Iso' SearchTarget Text
Documentation
newtype BlastJSON2 Source #
Instances
newtype BlastCmdJSON2 Source #
Instances
newtype BlastOutput2 Source #
Instances
data BlastReport Source #
BlastReport | |
|
Instances
newtype SearchTarget Source #
Instances
Instances
Eq Params Source # | |
Show Params Source # | |
Generic Params Source # | |
ToJSON Params Source # | |
Defined in Biobase.BLAST.Types | |
FromJSON Params Source # | |
type Rep Params Source # | |
Defined in Biobase.BLAST.Types type Rep Params = D1 (MetaData "Params" "Biobase.BLAST.Types" "BiobaseBlast-0.3.1.0-ExXGKuwRYfO3NhZPO3sW8q" False) (C1 (MetaCons "Params" PrefixI True) ((S1 (MetaSel (Just "_expect") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Double) :*: (S1 (MetaSel (Just "_sc_match") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int) :*: S1 (MetaSel (Just "_sc_mismatch") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int))) :*: (S1 (MetaSel (Just "_gap_open") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int) :*: (S1 (MetaSel (Just "_gap_extend") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int) :*: S1 (MetaSel (Just "_filter") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))))) |
data BlastJSONResult Source #
Instances
Search | |
|
Instances
Eq Search Source # | |
Show Search Source # | |
Generic Search Source # | |
ToJSON Search Source # | |
Defined in Biobase.BLAST.Types | |
FromJSON Search Source # | |
type Rep Search Source # | |
Defined in Biobase.BLAST.Types type Rep Search = D1 (MetaData "Search" "Biobase.BLAST.Types" "BiobaseBlast-0.3.1.0-ExXGKuwRYfO3NhZPO3sW8q" False) (C1 (MetaCons "Search" PrefixI True) ((S1 (MetaSel (Just "_query_id") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "_query_title") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) :*: (S1 (MetaSel (Just "_query_len") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int) :*: (S1 (MetaSel (Just "_hits") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Seq Hit)) :*: S1 (MetaSel (Just "_stat") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 SearchStat))))) |
Hit | |
|
Instances
Eq Hit Source # | |
Show Hit Source # | |
Generic Hit Source # | |
ToJSON Hit Source # | |
Defined in Biobase.BLAST.Types | |
FromJSON Hit Source # | |
type Rep Hit Source # | |
Defined in Biobase.BLAST.Types type Rep Hit = D1 (MetaData "Hit" "Biobase.BLAST.Types" "BiobaseBlast-0.3.1.0-ExXGKuwRYfO3NhZPO3sW8q" False) (C1 (MetaCons "Hit" PrefixI True) ((S1 (MetaSel (Just "_num") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int) :*: S1 (MetaSel (Just "_description") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [HitDescription])) :*: (S1 (MetaSel (Just "_len") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int) :*: S1 (MetaSel (Just "_hsps") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [Hsp])))) |
Instances
data HitDescription Source #
Instances
data SearchStat Source #
Instances
data BlastTabularResult Source #
BlastTabularResult | |
|
Instances
Eq BlastTabularResult Source # | |
Defined in Biobase.BLAST.Types (==) :: BlastTabularResult -> BlastTabularResult -> Bool # (/=) :: BlastTabularResult -> BlastTabularResult -> Bool # | |
Show BlastTabularResult Source # | |
Defined in Biobase.BLAST.Types showsPrec :: Int -> BlastTabularResult -> ShowS # show :: BlastTabularResult -> String # showList :: [BlastTabularResult] -> ShowS # |
data BlastTabularHit Source #
BlastTabularHit | |
|
Instances
Eq BlastTabularHit Source # | |
Defined in Biobase.BLAST.Types (==) :: BlastTabularHit -> BlastTabularHit -> Bool # (/=) :: BlastTabularHit -> BlastTabularHit -> Bool # | |
Show BlastTabularHit Source # | |
Defined in Biobase.BLAST.Types showsPrec :: Int -> BlastTabularHit -> ShowS # show :: BlastTabularHit -> String # showList :: [BlastTabularHit] -> ShowS # |
data BlastProgram Source #
Instances
Eq BlastProgram Source # | |
Defined in Biobase.BLAST.Types (==) :: BlastProgram -> BlastProgram -> Bool # (/=) :: BlastProgram -> BlastProgram -> Bool # | |
Show BlastProgram Source # | |
Defined in Biobase.BLAST.Types showsPrec :: Int -> BlastProgram -> ShowS # show :: BlastProgram -> String # showList :: [BlastProgram] -> ShowS # | |
ToJSON BlastProgram Source # | |
Defined in Biobase.BLAST.Types toJSON :: BlastProgram -> Value # toEncoding :: BlastProgram -> Encoding # toJSONList :: [BlastProgram] -> Value # toEncodingList :: [BlastProgram] -> Encoding # | |
FromJSON BlastProgram Source # | |
Defined in Biobase.BLAST.Types parseJSON :: Value -> Parser BlastProgram # parseJSONList :: Value -> Parser [BlastProgram] # |
description :: Lens' Hit [HitDescription] Source #