-- | Provides newtypes for odds, log-odds, and discretized versions.
--
-- TODO This is currently quite ad-hoc and needs better formalization. In
-- particular in terms of wrapping and usage of @Num@ and @Semiring@.

module Statistics.Odds where

import Control.DeepSeq (NFData(..))
import Data.Aeson (FromJSON(..),ToJSON(..))
import Data.Binary (Binary)
import Data.Hashable (Hashable)
import Data.Serialize (Serialize)
import Data.Vector.Unboxed.Deriving
import GHC.Generics (Generic)

import Data.Info

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



-- | Odds.

newtype Odds = Odds { Odds -> Double
getOdds  Double }
  deriving ((forall x. Odds -> Rep Odds x)
-> (forall x. Rep Odds x -> Odds) -> Generic Odds
forall x. Rep Odds x -> Odds
forall x. Odds -> Rep Odds x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Odds x -> Odds
$cfrom :: forall x. Odds -> Rep Odds x
Generic,Odds -> Odds -> Bool
(Odds -> Odds -> Bool) -> (Odds -> Odds -> Bool) -> Eq Odds
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Odds -> Odds -> Bool
$c/= :: Odds -> Odds -> Bool
== :: Odds -> Odds -> Bool
$c== :: Odds -> Odds -> Bool
Eq,Eq Odds
Eq Odds
-> (Odds -> Odds -> Ordering)
-> (Odds -> Odds -> Bool)
-> (Odds -> Odds -> Bool)
-> (Odds -> Odds -> Bool)
-> (Odds -> Odds -> Bool)
-> (Odds -> Odds -> Odds)
-> (Odds -> Odds -> Odds)
-> Ord Odds
Odds -> Odds -> Bool
Odds -> Odds -> Ordering
Odds -> Odds -> Odds
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 :: Odds -> Odds -> Odds
$cmin :: Odds -> Odds -> Odds
max :: Odds -> Odds -> Odds
$cmax :: Odds -> Odds -> Odds
>= :: Odds -> Odds -> Bool
$c>= :: Odds -> Odds -> Bool
> :: Odds -> Odds -> Bool
$c> :: Odds -> Odds -> Bool
<= :: Odds -> Odds -> Bool
$c<= :: Odds -> Odds -> Bool
< :: Odds -> Odds -> Bool
$c< :: Odds -> Odds -> Bool
compare :: Odds -> Odds -> Ordering
$ccompare :: Odds -> Odds -> Ordering
$cp1Ord :: Eq Odds
Ord,Int -> Odds -> ShowS
[Odds] -> ShowS
Odds -> String
(Int -> Odds -> ShowS)
-> (Odds -> String) -> ([Odds] -> ShowS) -> Show Odds
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Odds] -> ShowS
$cshowList :: [Odds] -> ShowS
show :: Odds -> String
$cshow :: Odds -> String
showsPrec :: Int -> Odds -> ShowS
$cshowsPrec :: Int -> Odds -> ShowS
Show,ReadPrec [Odds]
ReadPrec Odds
Int -> ReadS Odds
ReadS [Odds]
(Int -> ReadS Odds)
-> ReadS [Odds] -> ReadPrec Odds -> ReadPrec [Odds] -> Read Odds
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Odds]
$creadListPrec :: ReadPrec [Odds]
readPrec :: ReadPrec Odds
$creadPrec :: ReadPrec Odds
readList :: ReadS [Odds]
$creadList :: ReadS [Odds]
readsPrec :: Int -> ReadS Odds
$creadsPrec :: Int -> ReadS Odds
Read,Integer -> Odds
Odds -> Odds
Odds -> Odds -> Odds
(Odds -> Odds -> Odds)
-> (Odds -> Odds -> Odds)
-> (Odds -> Odds -> Odds)
-> (Odds -> Odds)
-> (Odds -> Odds)
-> (Odds -> Odds)
-> (Integer -> Odds)
-> Num Odds
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> Odds
$cfromInteger :: Integer -> Odds
signum :: Odds -> Odds
$csignum :: Odds -> Odds
abs :: Odds -> Odds
$cabs :: Odds -> Odds
negate :: Odds -> Odds
$cnegate :: Odds -> Odds
* :: Odds -> Odds -> Odds
$c* :: Odds -> Odds -> Odds
- :: Odds -> Odds -> Odds
$c- :: Odds -> Odds -> Odds
+ :: Odds -> Odds -> Odds
$c+ :: Odds -> Odds -> Odds
Num)

instance NFData Odds

deriving newtype instance Semiring Odds



-- | Encodes log-odds that have been rounded or clamped to integral numbers.
-- One advantage this provides is more efficient "maximum/minimum" calculations
-- compared to using @Double@s.
--
-- Note that these are "explicit" log-odds. Each numeric operation uses the
-- underlying operation on @Int@. If you want automatic handling, choose @Log
-- Odds@.

newtype DiscLogOdds (tk) = DiscLogOdds { DiscLogOdds t -> Discretized t
getDiscLogOdds  Discretized t }
  deriving ((forall x. DiscLogOdds t -> Rep (DiscLogOdds t) x)
-> (forall x. Rep (DiscLogOdds t) x -> DiscLogOdds t)
-> Generic (DiscLogOdds t)
forall x. Rep (DiscLogOdds t) x -> DiscLogOdds t
forall x. DiscLogOdds t -> Rep (DiscLogOdds t) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall k (t :: k) x. Rep (DiscLogOdds t) x -> DiscLogOdds t
forall k (t :: k) x. DiscLogOdds t -> Rep (DiscLogOdds t) x
$cto :: forall k (t :: k) x. Rep (DiscLogOdds t) x -> DiscLogOdds t
$cfrom :: forall k (t :: k) x. DiscLogOdds t -> Rep (DiscLogOdds t) x
Generic,DiscLogOdds t -> DiscLogOdds t -> Bool
(DiscLogOdds t -> DiscLogOdds t -> Bool)
-> (DiscLogOdds t -> DiscLogOdds t -> Bool) -> Eq (DiscLogOdds t)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall k (t :: k). DiscLogOdds t -> DiscLogOdds t -> Bool
/= :: DiscLogOdds t -> DiscLogOdds t -> Bool
$c/= :: forall k (t :: k). DiscLogOdds t -> DiscLogOdds t -> Bool
== :: DiscLogOdds t -> DiscLogOdds t -> Bool
$c== :: forall k (t :: k). DiscLogOdds t -> DiscLogOdds t -> Bool
Eq,Eq (DiscLogOdds t)
Eq (DiscLogOdds t)
-> (DiscLogOdds t -> DiscLogOdds t -> Ordering)
-> (DiscLogOdds t -> DiscLogOdds t -> Bool)
-> (DiscLogOdds t -> DiscLogOdds t -> Bool)
-> (DiscLogOdds t -> DiscLogOdds t -> Bool)
-> (DiscLogOdds t -> DiscLogOdds t -> Bool)
-> (DiscLogOdds t -> DiscLogOdds t -> DiscLogOdds t)
-> (DiscLogOdds t -> DiscLogOdds t -> DiscLogOdds t)
-> Ord (DiscLogOdds t)
DiscLogOdds t -> DiscLogOdds t -> Bool
DiscLogOdds t -> DiscLogOdds t -> Ordering
DiscLogOdds t -> DiscLogOdds t -> DiscLogOdds t
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
forall k (t :: k). Eq (DiscLogOdds t)
forall k (t :: k). DiscLogOdds t -> DiscLogOdds t -> Bool
forall k (t :: k). DiscLogOdds t -> DiscLogOdds t -> Ordering
forall k (t :: k). DiscLogOdds t -> DiscLogOdds t -> DiscLogOdds t
min :: DiscLogOdds t -> DiscLogOdds t -> DiscLogOdds t
$cmin :: forall k (t :: k). DiscLogOdds t -> DiscLogOdds t -> DiscLogOdds t
max :: DiscLogOdds t -> DiscLogOdds t -> DiscLogOdds t
$cmax :: forall k (t :: k). DiscLogOdds t -> DiscLogOdds t -> DiscLogOdds t
>= :: DiscLogOdds t -> DiscLogOdds t -> Bool
$c>= :: forall k (t :: k). DiscLogOdds t -> DiscLogOdds t -> Bool
> :: DiscLogOdds t -> DiscLogOdds t -> Bool
$c> :: forall k (t :: k). DiscLogOdds t -> DiscLogOdds t -> Bool
<= :: DiscLogOdds t -> DiscLogOdds t -> Bool
$c<= :: forall k (t :: k). DiscLogOdds t -> DiscLogOdds t -> Bool
< :: DiscLogOdds t -> DiscLogOdds t -> Bool
$c< :: forall k (t :: k). DiscLogOdds t -> DiscLogOdds t -> Bool
compare :: DiscLogOdds t -> DiscLogOdds t -> Ordering
$ccompare :: forall k (t :: k). DiscLogOdds t -> DiscLogOdds t -> Ordering
$cp1Ord :: forall k (t :: k). Eq (DiscLogOdds t)
Ord,Int -> DiscLogOdds t -> ShowS
[DiscLogOdds t] -> ShowS
DiscLogOdds t -> String
(Int -> DiscLogOdds t -> ShowS)
-> (DiscLogOdds t -> String)
-> ([DiscLogOdds t] -> ShowS)
-> Show (DiscLogOdds t)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall k (t :: k). Int -> DiscLogOdds t -> ShowS
forall k (t :: k). [DiscLogOdds t] -> ShowS
forall k (t :: k). DiscLogOdds t -> String
showList :: [DiscLogOdds t] -> ShowS
$cshowList :: forall k (t :: k). [DiscLogOdds t] -> ShowS
show :: DiscLogOdds t -> String
$cshow :: forall k (t :: k). DiscLogOdds t -> String
showsPrec :: Int -> DiscLogOdds t -> ShowS
$cshowsPrec :: forall k (t :: k). Int -> DiscLogOdds t -> ShowS
Show,ReadPrec [DiscLogOdds t]
ReadPrec (DiscLogOdds t)
Int -> ReadS (DiscLogOdds t)
ReadS [DiscLogOdds t]
(Int -> ReadS (DiscLogOdds t))
-> ReadS [DiscLogOdds t]
-> ReadPrec (DiscLogOdds t)
-> ReadPrec [DiscLogOdds t]
-> Read (DiscLogOdds t)
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
forall k (t :: k). ReadPrec [DiscLogOdds t]
forall k (t :: k). ReadPrec (DiscLogOdds t)
forall k (t :: k). Int -> ReadS (DiscLogOdds t)
forall k (t :: k). ReadS [DiscLogOdds t]
readListPrec :: ReadPrec [DiscLogOdds t]
$creadListPrec :: forall k (t :: k). ReadPrec [DiscLogOdds t]
readPrec :: ReadPrec (DiscLogOdds t)
$creadPrec :: forall k (t :: k). ReadPrec (DiscLogOdds t)
readList :: ReadS [DiscLogOdds t]
$creadList :: forall k (t :: k). ReadS [DiscLogOdds t]
readsPrec :: Int -> ReadS (DiscLogOdds t)
$creadsPrec :: forall k (t :: k). Int -> ReadS (DiscLogOdds t)
Read)

deriving newtype instance (Num (Discretized (tk)))  Num (DiscLogOdds t)
deriving newtype instance (Semiring (Discretized (tk)))  Semiring (DiscLogOdds t)
deriving newtype instance (Fractional (Discretized (tk)))  Fractional (DiscLogOdds t)
deriving newtype instance (Real (Discretized (tk)))  Real (DiscLogOdds (t::k))

derivingUnbox "DiscretizedLogOdds"
  [t| forall t . DiscLogOdds t  Int |]  [| getDiscretized . getDiscLogOdds |]  [| DiscLogOdds . Discretized |]

instance Binary    (DiscLogOdds t)
instance Serialize (DiscLogOdds t)
instance Hashable  (DiscLogOdds t)

instance ToJSON (Discretized t)  ToJSON (DiscLogOdds t) where
  toJSON :: DiscLogOdds t -> Value
toJSON = Discretized t -> Value
forall a. ToJSON a => a -> Value
toJSON (Discretized t -> Value)
-> (DiscLogOdds t -> Discretized t) -> DiscLogOdds t -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DiscLogOdds t -> Discretized t
forall k (t :: k). DiscLogOdds t -> Discretized t
getDiscLogOdds

instance FromJSON (Discretized t)  FromJSON  (DiscLogOdds t) where
  parseJSON :: Value -> Parser (DiscLogOdds t)
parseJSON = (Discretized t -> DiscLogOdds t)
-> Parser (Discretized t) -> Parser (DiscLogOdds t)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Discretized t -> DiscLogOdds t
forall k (t :: k). Discretized t -> DiscLogOdds t
DiscLogOdds (Parser (Discretized t) -> Parser (DiscLogOdds t))
-> (Value -> Parser (Discretized t))
-> Value
-> Parser (DiscLogOdds t)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value -> Parser (Discretized t)
forall a. FromJSON a => Value -> Parser a
parseJSON

instance (NFData (Discretized t))  NFData (DiscLogOdds t) where
  rnf :: DiscLogOdds t -> ()
rnf (DiscLogOdds Discretized t
k) = Discretized t -> ()
forall a. NFData a => a -> ()
rnf Discretized t
k
  {-# Inline rnf #-}

instance (NumericLimits (Discretized t))  NumericLimits (DiscLogOdds t) where
  minFinite :: DiscLogOdds t
minFinite = Discretized t -> DiscLogOdds t
forall k (t :: k). Discretized t -> DiscLogOdds t
DiscLogOdds Discretized t
forall x. NumericLimits x => x
minFinite
  {-# Inline minFinite #-}
  maxFinite :: DiscLogOdds t
maxFinite = Discretized t -> DiscLogOdds t
forall k (t :: k). Discretized t -> DiscLogOdds t
DiscLogOdds Discretized t
forall x. NumericLimits x => x
maxFinite
  {-# Inline maxFinite #-}

instance Info (DiscLogOdds t) where
  info :: DiscLogOdds t -> String
info = Discretized t -> String
forall c. Info c => c -> String
info (Discretized t -> String)
-> (DiscLogOdds t -> Discretized t) -> DiscLogOdds t -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DiscLogOdds t -> Discretized t
forall k (t :: k). DiscLogOdds t -> Discretized t
getDiscLogOdds