BiobaseTypes-0.1.3.0: Collection of types for bioinformatics

Safe HaskellNone
LanguageHaskell2010

Biobase.Types.Energy

Description

Different types of energies and conversion between.

TODO enthalpy TODO entropy

Synopsis

Documentation

newtype DG Source #

Gibbs free energy change.

For RNA structure, the change in energy from the unfolded structure to the given structure.

In units of kcal / mol.

TODO shall we phantom-type the actual units?

Constructors

DG 

Fields

Instances

Eq DG Source # 

Methods

(==) :: DG -> DG -> Bool #

(/=) :: DG -> DG -> Bool #

Fractional DG Source # 

Methods

(/) :: DG -> DG -> DG #

recip :: DG -> DG #

fromRational :: Rational -> DG #

Data DG Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DG -> c DG #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DG #

toConstr :: DG -> Constr #

dataTypeOf :: DG -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c DG) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DG) #

gmapT :: (forall b. Data b => b -> b) -> DG -> DG #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DG -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DG -> r #

gmapQ :: (forall d. Data d => d -> u) -> DG -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DG -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DG -> m DG #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DG -> m DG #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DG -> m DG #

Num DG Source # 

Methods

(+) :: DG -> DG -> DG #

(-) :: DG -> DG -> DG #

(*) :: DG -> DG -> DG #

negate :: DG -> DG #

abs :: DG -> DG #

signum :: DG -> DG #

fromInteger :: Integer -> DG #

Ord DG Source # 

Methods

compare :: DG -> DG -> Ordering #

(<) :: DG -> DG -> Bool #

(<=) :: DG -> DG -> Bool #

(>) :: DG -> DG -> Bool #

(>=) :: DG -> DG -> Bool #

max :: DG -> DG -> DG #

min :: DG -> DG -> DG #

Read DG Source # 
Show DG Source # 

Methods

showsPrec :: Int -> DG -> ShowS #

show :: DG -> String #

showList :: [DG] -> ShowS #

Generic DG Source # 

Associated Types

type Rep DG :: * -> * #

Methods

from :: DG -> Rep DG x #

to :: Rep DG x -> DG #

Hashable DG Source # 

Methods

hashWithSalt :: Int -> DG -> Int #

hash :: DG -> Int #

FromJSON DG Source # 
ToJSON DG Source # 
Binary DG Source # 

Methods

put :: DG -> Put #

get :: Get DG #

putList :: [DG] -> Put #

Serialize DG Source # 

Methods

put :: Putter DG #

get :: Get DG #

Default DG Source # 

Methods

def :: DG #

NFData DG Source # 

Methods

rnf :: DG -> () #

Unbox DG Source # 
NumericalEpsilon DG Source # 

Methods

epsilon :: DG Source #

NumericalExtremes DG Source # 
Vector Vector DG Source # 
MVector MVector DG Source # 
type Rep DG Source # 
type Rep DG = D1 (MetaData "DG" "Biobase.Types.Energy" "BiobaseTypes-0.1.3.0-7EMqsaldKh99G4UiC4Kzi1" True) (C1 (MetaCons "DG" PrefixI True) (S1 (MetaSel (Just Symbol "dG") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Double)))
data Vector DG Source # 
data MVector s DG Source # 

newtype DeltaDekaGibbs Source #

round $ DG / 100.

Constructors

DekaG 

Fields

Instances

Eq DeltaDekaGibbs Source # 
Num DeltaDekaGibbs Source # 
Ord DeltaDekaGibbs Source # 
Read DeltaDekaGibbs Source # 
Show DeltaDekaGibbs Source # 
Generic DeltaDekaGibbs Source # 

Associated Types

type Rep DeltaDekaGibbs :: * -> * #

Hashable DeltaDekaGibbs Source # 
FromJSON DeltaDekaGibbs Source # 
ToJSON DeltaDekaGibbs Source # 
Binary DeltaDekaGibbs Source # 
Serialize DeltaDekaGibbs Source # 
Default DeltaDekaGibbs Source # 

Methods

def :: DeltaDekaGibbs #

NFData DeltaDekaGibbs Source # 

Methods

rnf :: DeltaDekaGibbs -> () #

Unbox DeltaDekaGibbs Source # 
NumericalExtremes DeltaDekaGibbs Source # 
Vector Vector DeltaDekaGibbs Source # 
MVector MVector DeltaDekaGibbs Source # 
type Rep DeltaDekaGibbs Source # 
type Rep DeltaDekaGibbs = D1 (MetaData "DeltaDekaGibbs" "Biobase.Types.Energy" "BiobaseTypes-0.1.3.0-7EMqsaldKh99G4UiC4Kzi1" True) (C1 (MetaCons "DekaG" PrefixI True) (S1 (MetaSel (Just Symbol "getDekaG") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))
data Vector DeltaDekaGibbs Source # 
data MVector s DeltaDekaGibbs Source #