| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Biobase.BLAST.Types
Description
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 #
Constructors
| BlastJSON2 | |
Fields  | |
Instances
| Eq BlastJSON2 Source # | |
Defined in Biobase.BLAST.Types  | |
| Show BlastJSON2 Source # | |
Defined in Biobase.BLAST.Types Methods showsPrec :: Int -> BlastJSON2 -> ShowS # show :: BlastJSON2 -> String # showList :: [BlastJSON2] -> ShowS #  | |
| Generic BlastJSON2 Source # | |
Defined in Biobase.BLAST.Types Associated Types type Rep BlastJSON2 :: Type -> Type #  | |
| ToJSON BlastJSON2 Source # | |
Defined in Biobase.BLAST.Types Methods toJSON :: BlastJSON2 -> Value # toEncoding :: BlastJSON2 -> Encoding # toJSONList :: [BlastJSON2] -> Value # toEncodingList :: [BlastJSON2] -> Encoding #  | |
| FromJSON BlastJSON2 Source # | |
Defined in Biobase.BLAST.Types  | |
| type Rep BlastJSON2 Source # | |
Defined in Biobase.BLAST.Types type Rep BlastJSON2 = D1 (MetaData "BlastJSON2" "Biobase.BLAST.Types" "BiobaseBlast-0.3.1.0-ExXGKuwRYfO3NhZPO3sW8q" True) (C1 (MetaCons "BlastJSON2" PrefixI True) (S1 (MetaSel (Just "_blastoutput2") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 BlastOutput2)))  | |
newtype BlastCmdJSON2 Source #
Constructors
| BlastCmdJSON2 | |
Fields  | |
Instances
newtype BlastOutput2 Source #
Constructors
| BlastOutput2 | |
Fields  | |
Instances
| Eq BlastOutput2 Source # | |
Defined in Biobase.BLAST.Types  | |
| Show BlastOutput2 Source # | |
Defined in Biobase.BLAST.Types Methods showsPrec :: Int -> BlastOutput2 -> ShowS # show :: BlastOutput2 -> String # showList :: [BlastOutput2] -> ShowS #  | |
| Generic BlastOutput2 Source # | |
Defined in Biobase.BLAST.Types Associated Types type Rep BlastOutput2 :: Type -> Type #  | |
| ToJSON BlastOutput2 Source # | |
Defined in Biobase.BLAST.Types Methods toJSON :: BlastOutput2 -> Value # toEncoding :: BlastOutput2 -> Encoding # toJSONList :: [BlastOutput2] -> Value # toEncodingList :: [BlastOutput2] -> Encoding #  | |
| FromJSON BlastOutput2 Source # | |
Defined in Biobase.BLAST.Types  | |
| type Rep BlastOutput2 Source # | |
Defined in Biobase.BLAST.Types type Rep BlastOutput2 = D1 (MetaData "BlastOutput2" "Biobase.BLAST.Types" "BiobaseBlast-0.3.1.0-ExXGKuwRYfO3NhZPO3sW8q" True) (C1 (MetaCons "BlastOutput2" PrefixI True) (S1 (MetaSel (Just "_report") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 BlastReport)))  | |
data BlastReport Source #
Constructors
| BlastReport | |
Fields 
  | |
Instances
newtype SearchTarget Source #
Constructors
| SearchTarget | |
Instances
| Eq SearchTarget Source # | |
Defined in Biobase.BLAST.Types  | |
| Show SearchTarget Source # | |
Defined in Biobase.BLAST.Types Methods showsPrec :: Int -> SearchTarget -> ShowS # show :: SearchTarget -> String # showList :: [SearchTarget] -> ShowS #  | |
| Generic SearchTarget Source # | |
Defined in Biobase.BLAST.Types Associated Types type Rep SearchTarget :: Type -> Type #  | |
| ToJSON SearchTarget Source # | |
Defined in Biobase.BLAST.Types Methods toJSON :: SearchTarget -> Value # toEncoding :: SearchTarget -> Encoding # toJSONList :: [SearchTarget] -> Value # toEncodingList :: [SearchTarget] -> Encoding #  | |
| FromJSON SearchTarget Source # | |
Defined in Biobase.BLAST.Types  | |
| type Rep SearchTarget Source # | |
Defined in Biobase.BLAST.Types type Rep SearchTarget = D1 (MetaData "SearchTarget" "Biobase.BLAST.Types" "BiobaseBlast-0.3.1.0-ExXGKuwRYfO3NhZPO3sW8q" True) (C1 (MetaCons "SearchTarget" PrefixI True) (S1 (MetaSel (Just "_db") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))  | |
Constructors
| Params | |
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 #
Constructors
| BlastJSONResult | |
Instances
Constructors
| Search | |
Fields 
  | |
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)))))  | |
Constructors
| Hit | |
Fields 
  | |
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]))))  | |
Constructors
| Hsp | |
Instances
data HitDescription Source #
Constructors
| HitDescription | |
Instances
data SearchStat Source #
Constructors
| SearchStat | |
Instances
data BlastTabularResult Source #
Constructors
| BlastTabularResult | |
Fields 
  | |
Instances
| Eq BlastTabularResult Source # | |
Defined in Biobase.BLAST.Types Methods (==) :: BlastTabularResult -> BlastTabularResult -> Bool # (/=) :: BlastTabularResult -> BlastTabularResult -> Bool #  | |
| Show BlastTabularResult Source # | |
Defined in Biobase.BLAST.Types Methods showsPrec :: Int -> BlastTabularResult -> ShowS # show :: BlastTabularResult -> String # showList :: [BlastTabularResult] -> ShowS #  | |
data BlastTabularHit Source #
Constructors
| BlastTabularHit | |
Fields 
  | |
Instances
| Eq BlastTabularHit Source # | |
Defined in Biobase.BLAST.Types Methods (==) :: BlastTabularHit -> BlastTabularHit -> Bool # (/=) :: BlastTabularHit -> BlastTabularHit -> Bool #  | |
| Show BlastTabularHit Source # | |
Defined in Biobase.BLAST.Types Methods showsPrec :: Int -> BlastTabularHit -> ShowS # show :: BlastTabularHit -> String # showList :: [BlastTabularHit] -> ShowS #  | |
data BlastProgram Source #
Instances
| Eq BlastProgram Source # | |
Defined in Biobase.BLAST.Types  | |
| Show BlastProgram Source # | |
Defined in Biobase.BLAST.Types Methods showsPrec :: Int -> BlastProgram -> ShowS # show :: BlastProgram -> String # showList :: [BlastProgram] -> ShowS #  | |
| ToJSON BlastProgram Source # | |
Defined in Biobase.BLAST.Types Methods toJSON :: BlastProgram -> Value # toEncoding :: BlastProgram -> Encoding # toJSONList :: [BlastProgram] -> Value # toEncodingList :: [BlastProgram] -> Encoding #  | |
| FromJSON BlastProgram Source # | |
Defined in Biobase.BLAST.Types  | |
description :: Lens' Hit [HitDescription] Source #