{-# LANGUAGE MultiParamTypeClasses #-} -- | Provides a converting function between different types. Most useful -- conversions are instanced here. module Biobase.Types.Convert where import Biobase.Types.Ring import Biobase.Types.Energy import Biobase.Types.Score import Biobase.Types.Partition -- | How to convert between different values. class Convert a b c where convert :: a -> b -> c -- | From (Gibbs free) energy to partition function values. -- -- TODO temperature is running around here: move to some library later on newtype Kelvin = Kelvin {unKelvin :: Double} constR = undefined instance Convert Kelvin Energy Partition where convert (Kelvin k) (Energy a) = Partition . exp $ (fromIntegral $ negate a) / (constR * k) -- | From log-odd scores to partition function. -- instance Convert Temperature Score Partition where -- convert (Score a) = Partition . exp $ (fromIntegral $ neg a) / (constR * constT)