-- | Different types of energies and conversion between.
--
-- TODO enthalpy
-- TODO entropy

module Biobase.Types.Energy where

import Control.DeepSeq
import Control.Lens
import Data.Aeson (FromJSON, ToJSON)
import Data.Binary (Binary)
import Data.Data
import Data.Default
import Data.Hashable
import GHC.Real
import Data.Serialize (Serialize)
import Data.Vector.Unboxed.Deriving
import GHC.Generics

import Algebra.Structure.Semiring
import Numeric.Discretized
import Numeric.Limits



-- | 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?

newtype DG = DG { DG -> Double
dG :: Double }
  deriving (DG -> DG -> Bool
(DG -> DG -> Bool) -> (DG -> DG -> Bool) -> Eq DG
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DG -> DG -> Bool
$c/= :: DG -> DG -> Bool
== :: DG -> DG -> Bool
$c== :: DG -> DG -> Bool
Eq,Eq DG
Eq DG
-> (DG -> DG -> Ordering)
-> (DG -> DG -> Bool)
-> (DG -> DG -> Bool)
-> (DG -> DG -> Bool)
-> (DG -> DG -> Bool)
-> (DG -> DG -> DG)
-> (DG -> DG -> DG)
-> Ord DG
DG -> DG -> Bool
DG -> DG -> Ordering
DG -> DG -> DG
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: DG -> DG -> DG
$cmin :: DG -> DG -> DG
max :: DG -> DG -> DG
$cmax :: DG -> DG -> DG
>= :: DG -> DG -> Bool
$c>= :: DG -> DG -> Bool
> :: DG -> DG -> Bool
$c> :: DG -> DG -> Bool
<= :: DG -> DG -> Bool
$c<= :: DG -> DG -> Bool
< :: DG -> DG -> Bool
$c< :: DG -> DG -> Bool
compare :: DG -> DG -> Ordering
$ccompare :: DG -> DG -> Ordering
$cp1Ord :: Eq DG
Ord,Integer -> DG
DG -> DG
DG -> DG -> DG
(DG -> DG -> DG)
-> (DG -> DG -> DG)
-> (DG -> DG -> DG)
-> (DG -> DG)
-> (DG -> DG)
-> (DG -> DG)
-> (Integer -> DG)
-> Num DG
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> DG
$cfromInteger :: Integer -> DG
signum :: DG -> DG
$csignum :: DG -> DG
abs :: DG -> DG
$cabs :: DG -> DG
negate :: DG -> DG
$cnegate :: DG -> DG
* :: DG -> DG -> DG
$c* :: DG -> DG -> DG
- :: DG -> DG -> DG
$c- :: DG -> DG -> DG
+ :: DG -> DG -> DG
$c+ :: DG -> DG -> DG
Num,Num DG
Num DG
-> (DG -> DG -> DG)
-> (DG -> DG)
-> (Rational -> DG)
-> Fractional DG
Rational -> DG
DG -> DG
DG -> DG -> DG
forall a.
Num a
-> (a -> a -> a) -> (a -> a) -> (Rational -> a) -> Fractional a
fromRational :: Rational -> DG
$cfromRational :: Rational -> DG
recip :: DG -> DG
$crecip :: DG -> DG
/ :: DG -> DG -> DG
$c/ :: DG -> DG -> DG
$cp1Fractional :: Num DG
Fractional,ReadPrec [DG]
ReadPrec DG
Int -> ReadS DG
ReadS [DG]
(Int -> ReadS DG)
-> ReadS [DG] -> ReadPrec DG -> ReadPrec [DG] -> Read DG
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DG]
$creadListPrec :: ReadPrec [DG]
readPrec :: ReadPrec DG
$creadPrec :: ReadPrec DG
readList :: ReadS [DG]
$creadList :: ReadS [DG]
readsPrec :: Int -> ReadS DG
$creadsPrec :: Int -> ReadS DG
Read,Int -> DG -> ShowS
[DG] -> ShowS
DG -> String
(Int -> DG -> ShowS)
-> (DG -> String) -> ([DG] -> ShowS) -> Show DG
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DG] -> ShowS
$cshowList :: [DG] -> ShowS
show :: DG -> String
$cshow :: DG -> String
showsPrec :: Int -> DG -> ShowS
$cshowsPrec :: Int -> DG -> ShowS
Show,(forall x. DG -> Rep DG x)
-> (forall x. Rep DG x -> DG) -> Generic DG
forall x. Rep DG x -> DG
forall x. DG -> Rep DG x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DG x -> DG
$cfrom :: forall x. DG -> Rep DG x
Generic,Typeable DG
DataType
Constr
Typeable DG
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> DG -> c DG)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c DG)
-> (DG -> Constr)
-> (DG -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c DG))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DG))
-> ((forall b. Data b => b -> b) -> DG -> DG)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DG -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DG -> r)
-> (forall u. (forall d. Data d => d -> u) -> DG -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> DG -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> DG -> m DG)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> DG -> m DG)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> DG -> m DG)
-> Data DG
DG -> DataType
DG -> Constr
(forall b. Data b => b -> b) -> DG -> DG
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> DG -> c DG
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c DG
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> DG -> u
forall u. (forall d. Data d => d -> u) -> DG -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DG -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DG -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> DG -> m DG
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> DG -> m DG
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c DG
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> DG -> c DG
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c DG)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DG)
$cDG :: Constr
$tDG :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> DG -> m DG
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> DG -> m DG
gmapMp :: (forall d. Data d => d -> m d) -> DG -> m DG
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> DG -> m DG
gmapM :: (forall d. Data d => d -> m d) -> DG -> m DG
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> DG -> m DG
gmapQi :: Int -> (forall d. Data d => d -> u) -> DG -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> DG -> u
gmapQ :: (forall d. Data d => d -> u) -> DG -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> DG -> [u]
gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DG -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DG -> r
gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DG -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DG -> r
gmapT :: (forall b. Data b => b -> b) -> DG -> DG
$cgmapT :: (forall b. Data b => b -> b) -> DG -> DG
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DG)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DG)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c DG)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c DG)
dataTypeOf :: DG -> DataType
$cdataTypeOf :: DG -> DataType
toConstr :: DG -> Constr
$ctoConstr :: DG -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c DG
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c DG
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> DG -> c DG
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> DG -> c DG
$cp1Data :: Typeable DG
Data,Typeable)
makeLenses ''DG

derivingUnbox "DG"
  [t| DG -> Double |]  [| dG |]  [| DG |]

instance Hashable  DG
instance Binary    DG
instance Serialize DG
instance FromJSON  DG
instance ToJSON    DG
instance NFData    DG

deriving instance NumericLimits DG
deriving instance NumericEpsilon  DG

instance Default DG where
  def :: DG
def = DG
forall x. NumericLimits x => x
maxFinite DG -> DG -> DG
forall a. Fractional a => a -> a -> a
/ DG
100
  {-# Inline def #-}



-- | Discretized @DG@.

newtype DDG = DDG { DDG -> Discretized (1 ':% 100)
dDG  Discretized (1 :% 100) }
  deriving (DDG -> DDG -> Bool
(DDG -> DDG -> Bool) -> (DDG -> DDG -> Bool) -> Eq DDG
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DDG -> DDG -> Bool
$c/= :: DDG -> DDG -> Bool
== :: DDG -> DDG -> Bool
$c== :: DDG -> DDG -> Bool
Eq,Eq DDG
Eq DDG
-> (DDG -> DDG -> Ordering)
-> (DDG -> DDG -> Bool)
-> (DDG -> DDG -> Bool)
-> (DDG -> DDG -> Bool)
-> (DDG -> DDG -> Bool)
-> (DDG -> DDG -> DDG)
-> (DDG -> DDG -> DDG)
-> Ord DDG
DDG -> DDG -> Bool
DDG -> DDG -> Ordering
DDG -> DDG -> DDG
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: DDG -> DDG -> DDG
$cmin :: DDG -> DDG -> DDG
max :: DDG -> DDG -> DDG
$cmax :: DDG -> DDG -> DDG
>= :: DDG -> DDG -> Bool
$c>= :: DDG -> DDG -> Bool
> :: DDG -> DDG -> Bool
$c> :: DDG -> DDG -> Bool
<= :: DDG -> DDG -> Bool
$c<= :: DDG -> DDG -> Bool
< :: DDG -> DDG -> Bool
$c< :: DDG -> DDG -> Bool
compare :: DDG -> DDG -> Ordering
$ccompare :: DDG -> DDG -> Ordering
$cp1Ord :: Eq DDG
Ord,Integer -> DDG
DDG -> DDG
DDG -> DDG -> DDG
(DDG -> DDG -> DDG)
-> (DDG -> DDG -> DDG)
-> (DDG -> DDG -> DDG)
-> (DDG -> DDG)
-> (DDG -> DDG)
-> (DDG -> DDG)
-> (Integer -> DDG)
-> Num DDG
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> DDG
$cfromInteger :: Integer -> DDG
signum :: DDG -> DDG
$csignum :: DDG -> DDG
abs :: DDG -> DDG
$cabs :: DDG -> DDG
negate :: DDG -> DDG
$cnegate :: DDG -> DDG
* :: DDG -> DDG -> DDG
$c* :: DDG -> DDG -> DDG
- :: DDG -> DDG -> DDG
$c- :: DDG -> DDG -> DDG
+ :: DDG -> DDG -> DDG
$c+ :: DDG -> DDG -> DDG
Num,ReadPrec [DDG]
ReadPrec DDG
Int -> ReadS DDG
ReadS [DDG]
(Int -> ReadS DDG)
-> ReadS [DDG] -> ReadPrec DDG -> ReadPrec [DDG] -> Read DDG
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DDG]
$creadListPrec :: ReadPrec [DDG]
readPrec :: ReadPrec DDG
$creadPrec :: ReadPrec DDG
readList :: ReadS [DDG]
$creadList :: ReadS [DDG]
readsPrec :: Int -> ReadS DDG
$creadsPrec :: Int -> ReadS DDG
Read,(forall x. DDG -> Rep DDG x)
-> (forall x. Rep DDG x -> DDG) -> Generic DDG
forall x. Rep DDG x -> DDG
forall x. DDG -> Rep DDG x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DDG x -> DDG
$cfrom :: forall x. DDG -> Rep DDG x
Generic,Num DDG
Ord DDG
Num DDG -> Ord DDG -> (DDG -> Rational) -> Real DDG
DDG -> Rational
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
toRational :: DDG -> Rational
$ctoRational :: DDG -> Rational
$cp2Real :: Ord DDG
$cp1Real :: Num DDG
Real,Int -> DDG
DDG -> Int
DDG -> [DDG]
DDG -> DDG
DDG -> DDG -> [DDG]
DDG -> DDG -> DDG -> [DDG]
(DDG -> DDG)
-> (DDG -> DDG)
-> (Int -> DDG)
-> (DDG -> Int)
-> (DDG -> [DDG])
-> (DDG -> DDG -> [DDG])
-> (DDG -> DDG -> [DDG])
-> (DDG -> DDG -> DDG -> [DDG])
-> Enum DDG
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: DDG -> DDG -> DDG -> [DDG]
$cenumFromThenTo :: DDG -> DDG -> DDG -> [DDG]
enumFromTo :: DDG -> DDG -> [DDG]
$cenumFromTo :: DDG -> DDG -> [DDG]
enumFromThen :: DDG -> DDG -> [DDG]
$cenumFromThen :: DDG -> DDG -> [DDG]
enumFrom :: DDG -> [DDG]
$cenumFrom :: DDG -> [DDG]
fromEnum :: DDG -> Int
$cfromEnum :: DDG -> Int
toEnum :: Int -> DDG
$ctoEnum :: Int -> DDG
pred :: DDG -> DDG
$cpred :: DDG -> DDG
succ :: DDG -> DDG
$csucc :: DDG -> DDG
Enum)

instance Show DDG where
  show :: DDG -> String
show (DDG Discretized (1 ':% 100)
e) = Discretized (1 ':% 100) -> String
forall a. Show a => a -> String
show Discretized (1 ':% 100)
e

ddg2Int :: DDG -> Int
ddg2Int :: DDG -> Int
ddg2Int (DDG (Discretized Int
e)) = Int
e

derivingUnbox "DDG"
  [t| DDG -> Int |]  [| getDiscretized . dDG |]  [| DDG . Discretized |]

instance Semiring DDG where
  plus :: DDG -> DDG -> DDG
plus  (DDG Discretized (1 ':% 100)
x) (DDG Discretized (1 ':% 100)
y) = Discretized (1 ':% 100) -> DDG
DDG (Discretized (1 ':% 100) -> DDG) -> Discretized (1 ':% 100) -> DDG
forall a b. (a -> b) -> a -> b
$ Discretized (1 ':% 100)
-> Discretized (1 ':% 100) -> Discretized (1 ':% 100)
forall a. Ord a => a -> a -> a
min Discretized (1 ':% 100)
x Discretized (1 ':% 100)
y
  times :: DDG -> DDG -> DDG
times (DDG Discretized (1 ':% 100)
x) (DDG Discretized (1 ':% 100)
y) = Discretized (1 ':% 100) -> DDG
DDG (Discretized (1 ':% 100) -> DDG) -> Discretized (1 ':% 100) -> DDG
forall a b. (a -> b) -> a -> b
$ Discretized (1 ':% 100)
x Discretized (1 ':% 100)
-> Discretized (1 ':% 100) -> Discretized (1 ':% 100)
forall a. Semiring a => a -> a -> a
`plus` Discretized (1 ':% 100)
y
  zero :: DDG
zero = Discretized (1 ':% 100) -> DDG
DDG Discretized (1 ':% 100)
forall x. NumericLimits x => x
maxFinite
  one :: DDG
one  = Discretized (1 ':% 100) -> DDG
DDG Discretized (1 ':% 100)
forall a. Semiring a => a
zero
  {-# Inline plus  #-}
  {-# Inline times #-}
  {-# Inline zero  #-}
  {-# Inline one   #-}

--instance Hashable  DeltaDekaGibbs
--instance Binary    DeltaDekaGibbs
--instance Serialize DeltaDekaGibbs
--instance FromJSON  DeltaDekaGibbs
--instance ToJSON    DeltaDekaGibbs
--instance NFData    DeltaDekaGibbs
--
--deriving instance NumericLimits DeltaDekaGibbs
--
--instance Default DeltaDekaGibbs where
--  def = maxFinite `div` 100
--  {-# Inline def #-}
--