module Biobase.Types.Bitscore where
import Control.DeepSeq
import Data.Aeson
import Data.Binary
import Data.Default
import Data.Hashable (Hashable)
import Data.Primitive.Types
import Data.Serialize
import Data.Vector.Unboxed.Base
import Data.Vector.Unboxed.Deriving
import GHC.Generics (Generic)
import qualified Data.Vector.Generic as VG
import qualified Data.Vector.Generic.Mutable as VGM
import qualified Data.Vector.Unboxed as VU
import Algebra.Structure.Semiring
import Numeric.Limits
newtype Bitscore = Bitscore { getBitscore :: Double }
deriving (Eq,Ord,Read,Show,Num,Fractional,Generic)
instance Semiring Bitscore where
plus = (+)
times = (*)
zero = 0
one = 1
{-# Inline plus #-}
{-# Inline times #-}
{-# Inline zero #-}
{-# Inline one #-}
instance Binary Bitscore
instance FromJSON Bitscore
instance Hashable Bitscore
instance Serialize Bitscore
instance ToJSON Bitscore
instance NFData Bitscore
deriving instance NumericLimits Bitscore
derivingUnbox "Bitscore"
[t| Bitscore -> Double |] [| getBitscore |] [| Bitscore |]
instance Default Bitscore where
def = Bitscore minFinite / 100
{-# Inline def #-}
prob2Score :: Double -> Double -> Bitscore
prob2Score null x
| x==0 = minFinite / 100
| otherwise = Bitscore $ log (x/null) / log 2
{-# Inline prob2Score #-}
score2Prob :: Double -> Bitscore -> Double
score2Prob null (Bitscore x)
| x <= minFinite / 100 = 0
| otherwise = null * exp (x * log 2)
{-# Inline score2Prob #-}