BiobaseBlast-0.3.1.0: BLAST-related tools

Safe HaskellNone
LanguageHaskell2010

Biobase.SubstMatrix.Types

Synopsis

Documentation

data Similarity Source #

Denotes that we are dealing with a similarity score. Higher is more similar.

data Distance Source #

Denotes that we are dealing with a distance score. Lower is more similar.

newtype AASubstMat t s a Source #

Constructors

AASubstMat 

Fields

Instances
(Eq s, Unbox s) => Eq (AASubstMat t s a) Source # 
Instance details

Defined in Biobase.SubstMatrix.Types

Methods

(==) :: AASubstMat t s a -> AASubstMat t s a -> Bool #

(/=) :: AASubstMat t s a -> AASubstMat t s a -> Bool #

(Read s, Unbox s) => Read (AASubstMat t s a) Source # 
Instance details

Defined in Biobase.SubstMatrix.Types

(Show s, Unbox s) => Show (AASubstMat t s a) Source # 
Instance details

Defined in Biobase.SubstMatrix.Types

Methods

showsPrec :: Int -> AASubstMat t s a -> ShowS #

show :: AASubstMat t s a -> String #

showList :: [AASubstMat t s a] -> ShowS #

Generic (AASubstMat t s a) Source # 
Instance details

Defined in Biobase.SubstMatrix.Types

Associated Types

type Rep (AASubstMat t s a) :: Type -> Type #

Methods

from :: AASubstMat t s a -> Rep (AASubstMat t s a) x #

to :: Rep (AASubstMat t s a) x -> AASubstMat t s a #

type Rep (AASubstMat t s a) Source # 
Instance details

Defined in Biobase.SubstMatrix.Types

type Rep (AASubstMat t s a) = D1 (MetaData "AASubstMat" "Biobase.SubstMatrix.Types" "BiobaseBlast-0.3.1.0-ExXGKuwRYfO3NhZPO3sW8q" True) (C1 (MetaCons "AASubstMat" PrefixI True) (S1 (MetaSel (Just "_aaSubstMat") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Unboxed ((Z :. Letter AA a) :. Letter AA a) s))))

aaSubstMat :: forall t s a t s a. Iso (AASubstMat t s a) (AASubstMat t s a) (Unboxed ((:.) ((:.) Z (Letter AA a)) (Letter AA a)) s) (Unboxed ((:.) ((:.) Z (Letter AA a)) (Letter AA a)) s) Source #

type SubstPAM = AASubstMat Similarity (DiscLogOdds Unknown) Source #

PAM matrices are similarity matrices.

type SubstBLOSUM = AASubstMat Distance (DiscLogOdds Unknown) Source #

BLOSUM matrices are distance matrices.

newtype ANuc3SubstMat t s a n Source #

Substitution matrix from amino acids to nucleotide triplets.

Constructors

ANuc3SubstMat 
Instances
(Eq s, Unbox s) => Eq (ANuc3SubstMat t s a n) Source # 
Instance details

Defined in Biobase.SubstMatrix.Types

Methods

(==) :: ANuc3SubstMat t s a n -> ANuc3SubstMat t s a n -> Bool #

(/=) :: ANuc3SubstMat t s a n -> ANuc3SubstMat t s a n -> Bool #

(Read s, Unbox s) => Read (ANuc3SubstMat t s a n) Source # 
Instance details

Defined in Biobase.SubstMatrix.Types

(Show s, Unbox s) => Show (ANuc3SubstMat t s a n) Source # 
Instance details

Defined in Biobase.SubstMatrix.Types

Methods

showsPrec :: Int -> ANuc3SubstMat t s a n -> ShowS #

show :: ANuc3SubstMat t s a n -> String #

showList :: [ANuc3SubstMat t s a n] -> ShowS #

Generic (ANuc3SubstMat t s a n) Source # 
Instance details

Defined in Biobase.SubstMatrix.Types

Associated Types

type Rep (ANuc3SubstMat t s a n) :: Type -> Type #

Methods

from :: ANuc3SubstMat t s a n -> Rep (ANuc3SubstMat t s a n) x #

to :: Rep (ANuc3SubstMat t s a n) x -> ANuc3SubstMat t s a n #

type Rep (ANuc3SubstMat t s a n) Source # 
Instance details

Defined in Biobase.SubstMatrix.Types

type Rep (ANuc3SubstMat t s a n) = D1 (MetaData "ANuc3SubstMat" "Biobase.SubstMatrix.Types" "BiobaseBlast-0.3.1.0-ExXGKuwRYfO3NhZPO3sW8q" True) (C1 (MetaCons "ANuc3SubstMat" PrefixI True) (S1 (MetaSel (Just "_anuc3SubstMat") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Unboxed ((((Z :. Letter AA a) :. Letter DNA n) :. Letter DNA n) :. Letter DNA n) s))))

anuc3SubstMat :: forall t s a n t s a n. Iso (ANuc3SubstMat t s a n) (ANuc3SubstMat t s a n) (Unboxed ((:.) ((:.) ((:.) ((:.) Z (Letter AA a)) (Letter DNA n)) (Letter DNA n)) (Letter DNA n)) s) (Unboxed ((:.) ((:.) ((:.) ((:.) Z (Letter AA a)) (Letter DNA n)) (Letter DNA n)) (Letter DNA n)) s) Source #

newtype ANuc2SubstMat t s a n Source #

Substitution matrix from amino acids to degenerate nucleotide 2-tuples. The third nucleotide letter is missing.

Constructors

ANuc2SubstMat 

Fields

Instances
(Eq s, Unbox s) => Eq (ANuc2SubstMat t s a n) Source # 
Instance details

Defined in Biobase.SubstMatrix.Types

Methods

(==) :: ANuc2SubstMat t s a n -> ANuc2SubstMat t s a n -> Bool #

(/=) :: ANuc2SubstMat t s a n -> ANuc2SubstMat t s a n -> Bool #

(Read s, Unbox s) => Read (ANuc2SubstMat t s a n) Source # 
Instance details

Defined in Biobase.SubstMatrix.Types

(Show s, Unbox s) => Show (ANuc2SubstMat t s a n) Source # 
Instance details

Defined in Biobase.SubstMatrix.Types

Methods

showsPrec :: Int -> ANuc2SubstMat t s a n -> ShowS #

show :: ANuc2SubstMat t s a n -> String #

showList :: [ANuc2SubstMat t s a n] -> ShowS #

Generic (ANuc2SubstMat t s a n) Source # 
Instance details

Defined in Biobase.SubstMatrix.Types

Associated Types

type Rep (ANuc2SubstMat t s a n) :: Type -> Type #

Methods

from :: ANuc2SubstMat t s a n -> Rep (ANuc2SubstMat t s a n) x #

to :: Rep (ANuc2SubstMat t s a n) x -> ANuc2SubstMat t s a n #

type Rep (ANuc2SubstMat t s a n) Source # 
Instance details

Defined in Biobase.SubstMatrix.Types

type Rep (ANuc2SubstMat t s a n) = D1 (MetaData "ANuc2SubstMat" "Biobase.SubstMatrix.Types" "BiobaseBlast-0.3.1.0-ExXGKuwRYfO3NhZPO3sW8q" True) (C1 (MetaCons "ANuc2SubstMat" PrefixI True) (S1 (MetaSel (Just "_anuc2SubstMat") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Unboxed (((Z :. Letter AA a) :. Letter DNA n) :. Letter DNA n) s))))

anuc2SubstMat :: forall t s a n t s a n. Iso (ANuc2SubstMat t s a n) (ANuc2SubstMat t s a n) (Unboxed ((:.) ((:.) ((:.) Z (Letter AA a)) (Letter DNA n)) (Letter DNA n)) s) (Unboxed ((:.) ((:.) ((:.) Z (Letter AA a)) (Letter DNA n)) (Letter DNA n)) s) Source #

newtype ANuc1SubstMat t s a n Source #

Substitution matrix from amino acids to degenerate nucleotide 1-tuples. Two out of three nucleotides in a triplet are missing.

Constructors

ANuc1SubstMat 

Fields

Instances
(Eq s, Unbox s) => Eq (ANuc1SubstMat t s a n) Source # 
Instance details

Defined in Biobase.SubstMatrix.Types

Methods

(==) :: ANuc1SubstMat t s a n -> ANuc1SubstMat t s a n -> Bool #

(/=) :: ANuc1SubstMat t s a n -> ANuc1SubstMat t s a n -> Bool #

(Read s, Unbox s) => Read (ANuc1SubstMat t s a n) Source # 
Instance details

Defined in Biobase.SubstMatrix.Types

(Show s, Unbox s) => Show (ANuc1SubstMat t s a n) Source # 
Instance details

Defined in Biobase.SubstMatrix.Types

Methods

showsPrec :: Int -> ANuc1SubstMat t s a n -> ShowS #

show :: ANuc1SubstMat t s a n -> String #

showList :: [ANuc1SubstMat t s a n] -> ShowS #

Generic (ANuc1SubstMat t s a n) Source # 
Instance details

Defined in Biobase.SubstMatrix.Types

Associated Types

type Rep (ANuc1SubstMat t s a n) :: Type -> Type #

Methods

from :: ANuc1SubstMat t s a n -> Rep (ANuc1SubstMat t s a n) x #

to :: Rep (ANuc1SubstMat t s a n) x -> ANuc1SubstMat t s a n #

type Rep (ANuc1SubstMat t s a n) Source # 
Instance details

Defined in Biobase.SubstMatrix.Types

type Rep (ANuc1SubstMat t s a n) = D1 (MetaData "ANuc1SubstMat" "Biobase.SubstMatrix.Types" "BiobaseBlast-0.3.1.0-ExXGKuwRYfO3NhZPO3sW8q" True) (C1 (MetaCons "ANuc1SubstMat" PrefixI True) (S1 (MetaSel (Just "_anuc1SubstMat") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Unboxed ((Z :. Letter AA a) :. Letter DNA n) s))))

anuc1SubstMat :: forall t s a n t s a n. Iso (ANuc1SubstMat t s a n) (ANuc1SubstMat t s a n) (Unboxed ((:.) ((:.) Z (Letter AA a)) (Letter DNA n)) s) (Unboxed ((:.) ((:.) Z (Letter AA a)) (Letter DNA n)) s) Source #

data GapCost t Source #

Constructors

GapCost 

Fields