{-# LANGUAGE CPP #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE StandaloneDeriving #-} {-# LANGUAGE MultiParamTypeClasses #-} -- | With more programs being present, a number of different types are present. -- Right now, they mostly are just "type"s, or flat Int's / Double's. This -- module provides a set of newtype wrappers to make explicit what kind of -- value is being computed. In the future, all programs should make use of -- these. -- -- All units come with unboxed vector equipment. -- -- TODO the numeric-prelude knows about Unit.SI. -- -- TODO we should use "Kelvin" from somewhere else, say the numerical-prelude -- but this would make Biobase even heavier. module Biobase.ScoreTypes where import Data.Primitive.Types import qualified Data.Vector.Generic as VG import qualified Data.Vector.Generic.Mutable as VGM import qualified Data.Vector.Unboxed as VU import Biobase.Constants -- | The ViennaRNA base unit. A bit strange, but values are tabulated in the -- energy parameter file as 1/100 kCal/mol. newtype DecaCalMol = DCM { unDCM :: Int } deriving (Eq,Ord,Read,Show) -- | Other programs just calculate with fractions of kCal/Mol. This needs to be -- double as errors in energies are around 10 cal/mol. newtype KCalMol = KCM { unKCM :: Double } deriving (Eq,Ord,Read,Show) -- | For data generated from statistical ensembles, we only have -- pseudo-energies. newtype PseudoDecaCalMol = PDCM { unPDCM :: Int } deriving (Eq,Ord,Read,Show) -- | For data generated from statistical ensembles, we only have -- pseudo-energies. newtype PseudoKCalMol = PKCM { unPKCM :: Double } deriving (Eq,Ord,Read,Show) -- | The Boltzmann statistical weight "exp(-e / kT)" of an energy newtype BoltzmannW = BoltzmannW { unBoltzmannW :: Double } deriving (Eq,Ord,Read,Show) -- | Temperature in Kelvin newtype Kelvin = Kelvin { unKelvin :: Double } deriving (Eq,Ord,Read,Show) -- * Conversion between units. Not all conversions are meaningful. -- | Convert between two similar enough units. There is no all vs. all -- conversion. -- -- NOTE If you need to convert pseudo-energies into "real" ones, do it -- explicitly by calling 'PDCM . unDCM' or similar. Conversions here are -- supposed to be somewhat safe. class Convert a b where convert :: a -> b instance Convert DecaCalMol KCalMol where convert (DCM x) = KCM $ fromIntegral x / 100 instance Convert KCalMol DecaCalMol where convert (KCM x) = DCM . round $ x * 100 instance Convert PseudoDecaCalMol PseudoKCalMol where convert (PDCM x) = PKCM $ fromIntegral x / 100 instance Convert PseudoKCalMol PseudoDecaCalMol where convert (PKCM x) = PDCM . round $ x * 100 -- | convert from and to Boltzmann weights class BoltzmannWeighted a where boltzmannWeighted :: a -> Kelvin -> BoltzmannW instance BoltzmannWeighted DecaCalMol where boltzmannWeighted (DCM x) (Kelvin t) = let k = gasconst in BoltzmannW . exp . negate $ fromIntegral x / (k * t * 100) instance BoltzmannWeighted KCalMol where boltzmannWeighted (KCM x) (Kelvin t) = let k = gasconst in BoltzmannW . exp . negate $ x / (k * t) instance BoltzmannWeighted PseudoDecaCalMol where boltzmannWeighted (PDCM x) (Kelvin t) = let k = gasconst in BoltzmannW . exp . negate $ fromIntegral x / (k * t * 100) instance BoltzmannWeighted PseudoKCalMol where boltzmannWeighted (PKCM x) (Kelvin t) = let k = gasconst in BoltzmannW . exp . negate $ x / (k * t) -- | Boltzmann weighting at default temperature of 37 Celsius. toBoltzmannW x = boltzmannWeighted x defTemp defTemp = Kelvin $ kelvinC0 + 37 -- * unboxed vector instances #define DVU(d) \ deriving instance Prim d; \ deriving instance VU.Unbox d; \ deriving instance VGM.MVector VU.MVector d; \ deriving instance VG.Vector VU.Vector d \ DVU(KCalMol) DVU(DecaCalMol) DVU(PseudoKCalMol) DVU(PseudoDecaCalMol) DVU(BoltzmannW) DVU(Kelvin)