{-# LANGUAGE CPP #-}
{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE DeriveDataTypeable, DeriveGeneric, GADTs, RecordWildCards #-}
{-# OPTIONS_GHC -funbox-strict-fields #-}
module Criterion.Types
(
Config(..)
, Verbosity(..)
, Benchmarkable(..)
, Benchmark(..)
, Measured(..)
, fromInt
, toInt
, fromDouble
, toDouble
, measureAccessors
, measureKeys
, measure
, rescale
, env
, envWithCleanup
, perBatchEnv
, perBatchEnvWithCleanup
, perRunEnv
, perRunEnvWithCleanup
, toBenchmarkable
, bench
, bgroup
, addPrefix
, benchNames
, nf
, whnf
, nfIO
, whnfIO
, nfAppIO
, whnfAppIO
, Outliers(..)
, OutlierEffect(..)
, OutlierVariance(..)
, Regression(..)
, KDE(..)
, Report(..)
, SampleAnalysis(..)
, DataRecord(..)
) where
import Control.DeepSeq (NFData(rnf))
import Criterion.Measurement.Types
import Data.Aeson (FromJSON(..), ToJSON(..))
import Data.Binary (Binary(..), putWord8, getWord8)
import Data.Binary.Orphans ()
import Data.Data (Data)
import Data.Int (Int64)
import Data.Map (Map)
import GHC.Generics (Generic)
import Prelude ()
import Prelude.Compat
import qualified Data.Vector as V
import qualified Data.Vector.Unboxed as U
import qualified Statistics.Types as St
import Statistics.Resampling.Bootstrap ()
data Verbosity = Quiet
| Normal
| Verbose
deriving (Verbosity -> Verbosity -> Bool
(Verbosity -> Verbosity -> Bool)
-> (Verbosity -> Verbosity -> Bool) -> Eq Verbosity
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Verbosity -> Verbosity -> Bool
== :: Verbosity -> Verbosity -> Bool
$c/= :: Verbosity -> Verbosity -> Bool
/= :: Verbosity -> Verbosity -> Bool
Eq, Eq Verbosity
Eq Verbosity =>
(Verbosity -> Verbosity -> Ordering)
-> (Verbosity -> Verbosity -> Bool)
-> (Verbosity -> Verbosity -> Bool)
-> (Verbosity -> Verbosity -> Bool)
-> (Verbosity -> Verbosity -> Bool)
-> (Verbosity -> Verbosity -> Verbosity)
-> (Verbosity -> Verbosity -> Verbosity)
-> Ord Verbosity
Verbosity -> Verbosity -> Bool
Verbosity -> Verbosity -> Ordering
Verbosity -> Verbosity -> Verbosity
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
$ccompare :: Verbosity -> Verbosity -> Ordering
compare :: Verbosity -> Verbosity -> Ordering
$c< :: Verbosity -> Verbosity -> Bool
< :: Verbosity -> Verbosity -> Bool
$c<= :: Verbosity -> Verbosity -> Bool
<= :: Verbosity -> Verbosity -> Bool
$c> :: Verbosity -> Verbosity -> Bool
> :: Verbosity -> Verbosity -> Bool
$c>= :: Verbosity -> Verbosity -> Bool
>= :: Verbosity -> Verbosity -> Bool
$cmax :: Verbosity -> Verbosity -> Verbosity
max :: Verbosity -> Verbosity -> Verbosity
$cmin :: Verbosity -> Verbosity -> Verbosity
min :: Verbosity -> Verbosity -> Verbosity
Ord, Verbosity
Verbosity -> Verbosity -> Bounded Verbosity
forall a. a -> a -> Bounded a
$cminBound :: Verbosity
minBound :: Verbosity
$cmaxBound :: Verbosity
maxBound :: Verbosity
Bounded, Int -> Verbosity
Verbosity -> Int
Verbosity -> [Verbosity]
Verbosity -> Verbosity
Verbosity -> Verbosity -> [Verbosity]
Verbosity -> Verbosity -> Verbosity -> [Verbosity]
(Verbosity -> Verbosity)
-> (Verbosity -> Verbosity)
-> (Int -> Verbosity)
-> (Verbosity -> Int)
-> (Verbosity -> [Verbosity])
-> (Verbosity -> Verbosity -> [Verbosity])
-> (Verbosity -> Verbosity -> [Verbosity])
-> (Verbosity -> Verbosity -> Verbosity -> [Verbosity])
-> Enum Verbosity
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: Verbosity -> Verbosity
succ :: Verbosity -> Verbosity
$cpred :: Verbosity -> Verbosity
pred :: Verbosity -> Verbosity
$ctoEnum :: Int -> Verbosity
toEnum :: Int -> Verbosity
$cfromEnum :: Verbosity -> Int
fromEnum :: Verbosity -> Int
$cenumFrom :: Verbosity -> [Verbosity]
enumFrom :: Verbosity -> [Verbosity]
$cenumFromThen :: Verbosity -> Verbosity -> [Verbosity]
enumFromThen :: Verbosity -> Verbosity -> [Verbosity]
$cenumFromTo :: Verbosity -> Verbosity -> [Verbosity]
enumFromTo :: Verbosity -> Verbosity -> [Verbosity]
$cenumFromThenTo :: Verbosity -> Verbosity -> Verbosity -> [Verbosity]
enumFromThenTo :: Verbosity -> Verbosity -> Verbosity -> [Verbosity]
Enum, ReadPrec [Verbosity]
ReadPrec Verbosity
Int -> ReadS Verbosity
ReadS [Verbosity]
(Int -> ReadS Verbosity)
-> ReadS [Verbosity]
-> ReadPrec Verbosity
-> ReadPrec [Verbosity]
-> Read Verbosity
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Verbosity
readsPrec :: Int -> ReadS Verbosity
$creadList :: ReadS [Verbosity]
readList :: ReadS [Verbosity]
$creadPrec :: ReadPrec Verbosity
readPrec :: ReadPrec Verbosity
$creadListPrec :: ReadPrec [Verbosity]
readListPrec :: ReadPrec [Verbosity]
Read, Int -> Verbosity -> ShowS
[Verbosity] -> ShowS
Verbosity -> String
(Int -> Verbosity -> ShowS)
-> (Verbosity -> String)
-> ([Verbosity] -> ShowS)
-> Show Verbosity
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Verbosity -> ShowS
showsPrec :: Int -> Verbosity -> ShowS
$cshow :: Verbosity -> String
show :: Verbosity -> String
$cshowList :: [Verbosity] -> ShowS
showList :: [Verbosity] -> ShowS
Show, Typeable Verbosity
Typeable Verbosity =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Verbosity -> c Verbosity)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Verbosity)
-> (Verbosity -> Constr)
-> (Verbosity -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Verbosity))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Verbosity))
-> ((forall b. Data b => b -> b) -> Verbosity -> Verbosity)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Verbosity -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Verbosity -> r)
-> (forall u. (forall d. Data d => d -> u) -> Verbosity -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> Verbosity -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Verbosity -> m Verbosity)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Verbosity -> m Verbosity)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Verbosity -> m Verbosity)
-> Data Verbosity
Verbosity -> Constr
Verbosity -> DataType
(forall b. Data b => b -> b) -> Verbosity -> Verbosity
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) -> Verbosity -> u
forall u. (forall d. Data d => d -> u) -> Verbosity -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Verbosity -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Verbosity -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Verbosity -> m Verbosity
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Verbosity -> m Verbosity
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Verbosity
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Verbosity -> c Verbosity
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Verbosity)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Verbosity)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Verbosity -> c Verbosity
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Verbosity -> c Verbosity
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Verbosity
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Verbosity
$ctoConstr :: Verbosity -> Constr
toConstr :: Verbosity -> Constr
$cdataTypeOf :: Verbosity -> DataType
dataTypeOf :: Verbosity -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Verbosity)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Verbosity)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Verbosity)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Verbosity)
$cgmapT :: (forall b. Data b => b -> b) -> Verbosity -> Verbosity
gmapT :: (forall b. Data b => b -> b) -> Verbosity -> Verbosity
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Verbosity -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Verbosity -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Verbosity -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Verbosity -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Verbosity -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Verbosity -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Verbosity -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Verbosity -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Verbosity -> m Verbosity
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Verbosity -> m Verbosity
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Verbosity -> m Verbosity
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Verbosity -> m Verbosity
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Verbosity -> m Verbosity
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Verbosity -> m Verbosity
Data,
(forall x. Verbosity -> Rep Verbosity x)
-> (forall x. Rep Verbosity x -> Verbosity) -> Generic Verbosity
forall x. Rep Verbosity x -> Verbosity
forall x. Verbosity -> Rep Verbosity x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Verbosity -> Rep Verbosity x
from :: forall x. Verbosity -> Rep Verbosity x
$cto :: forall x. Rep Verbosity x -> Verbosity
to :: forall x. Rep Verbosity x -> Verbosity
Generic)
data Config = Config {
Config -> CL Double
confInterval :: St.CL Double
, Config -> Double
timeLimit :: Double
, Config -> Int
resamples :: Int
, Config -> [([String], String)]
regressions :: [([String], String)]
, Config -> Maybe String
rawDataFile :: Maybe FilePath
, Config -> Maybe String
reportFile :: Maybe FilePath
, Config -> Maybe String
csvFile :: Maybe FilePath
, Config -> Maybe String
jsonFile :: Maybe FilePath
, Config -> Maybe String
junitFile :: Maybe FilePath
, Config -> Verbosity
verbosity :: Verbosity
, Config -> String
template :: FilePath
} deriving (Config -> Config -> Bool
(Config -> Config -> Bool)
-> (Config -> Config -> Bool) -> Eq Config
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Config -> Config -> Bool
== :: Config -> Config -> Bool
$c/= :: Config -> Config -> Bool
/= :: Config -> Config -> Bool
Eq, ReadPrec [Config]
ReadPrec Config
Int -> ReadS Config
ReadS [Config]
(Int -> ReadS Config)
-> ReadS [Config]
-> ReadPrec Config
-> ReadPrec [Config]
-> Read Config
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Config
readsPrec :: Int -> ReadS Config
$creadList :: ReadS [Config]
readList :: ReadS [Config]
$creadPrec :: ReadPrec Config
readPrec :: ReadPrec Config
$creadListPrec :: ReadPrec [Config]
readListPrec :: ReadPrec [Config]
Read, Int -> Config -> ShowS
[Config] -> ShowS
Config -> String
(Int -> Config -> ShowS)
-> (Config -> String) -> ([Config] -> ShowS) -> Show Config
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Config -> ShowS
showsPrec :: Int -> Config -> ShowS
$cshow :: Config -> String
show :: Config -> String
$cshowList :: [Config] -> ShowS
showList :: [Config] -> ShowS
Show, Typeable Config
Typeable Config =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Config -> c Config)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Config)
-> (Config -> Constr)
-> (Config -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Config))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Config))
-> ((forall b. Data b => b -> b) -> Config -> Config)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Config -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Config -> r)
-> (forall u. (forall d. Data d => d -> u) -> Config -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Config -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Config -> m Config)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Config -> m Config)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Config -> m Config)
-> Data Config
Config -> Constr
Config -> DataType
(forall b. Data b => b -> b) -> Config -> Config
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) -> Config -> u
forall u. (forall d. Data d => d -> u) -> Config -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Config -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Config -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Config -> m Config
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Config -> m Config
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Config
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Config -> c Config
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Config)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Config)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Config -> c Config
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Config -> c Config
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Config
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Config
$ctoConstr :: Config -> Constr
toConstr :: Config -> Constr
$cdataTypeOf :: Config -> DataType
dataTypeOf :: Config -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Config)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Config)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Config)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Config)
$cgmapT :: (forall b. Data b => b -> b) -> Config -> Config
gmapT :: (forall b. Data b => b -> b) -> Config -> Config
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Config -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Config -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Config -> r
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Config -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Config -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Config -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Config -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Config -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Config -> m Config
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Config -> m Config
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Config -> m Config
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Config -> m Config
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Config -> m Config
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Config -> m Config
Data, (forall x. Config -> Rep Config x)
-> (forall x. Rep Config x -> Config) -> Generic Config
forall x. Rep Config x -> Config
forall x. Config -> Rep Config x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Config -> Rep Config x
from :: forall x. Config -> Rep Config x
$cto :: forall x. Rep Config x -> Config
to :: forall x. Rep Config x -> Config
Generic)
data Outliers = Outliers {
Outliers -> Int64
samplesSeen :: !Int64
, Outliers -> Int64
lowSevere :: !Int64
, Outliers -> Int64
lowMild :: !Int64
, Outliers -> Int64
highMild :: !Int64
, Outliers -> Int64
highSevere :: !Int64
} deriving (Outliers -> Outliers -> Bool
(Outliers -> Outliers -> Bool)
-> (Outliers -> Outliers -> Bool) -> Eq Outliers
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Outliers -> Outliers -> Bool
== :: Outliers -> Outliers -> Bool
$c/= :: Outliers -> Outliers -> Bool
/= :: Outliers -> Outliers -> Bool
Eq, ReadPrec [Outliers]
ReadPrec Outliers
Int -> ReadS Outliers
ReadS [Outliers]
(Int -> ReadS Outliers)
-> ReadS [Outliers]
-> ReadPrec Outliers
-> ReadPrec [Outliers]
-> Read Outliers
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Outliers
readsPrec :: Int -> ReadS Outliers
$creadList :: ReadS [Outliers]
readList :: ReadS [Outliers]
$creadPrec :: ReadPrec Outliers
readPrec :: ReadPrec Outliers
$creadListPrec :: ReadPrec [Outliers]
readListPrec :: ReadPrec [Outliers]
Read, Int -> Outliers -> ShowS
[Outliers] -> ShowS
Outliers -> String
(Int -> Outliers -> ShowS)
-> (Outliers -> String) -> ([Outliers] -> ShowS) -> Show Outliers
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Outliers -> ShowS
showsPrec :: Int -> Outliers -> ShowS
$cshow :: Outliers -> String
show :: Outliers -> String
$cshowList :: [Outliers] -> ShowS
showList :: [Outliers] -> ShowS
Show, Typeable Outliers
Typeable Outliers =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Outliers -> c Outliers)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Outliers)
-> (Outliers -> Constr)
-> (Outliers -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Outliers))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Outliers))
-> ((forall b. Data b => b -> b) -> Outliers -> Outliers)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Outliers -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Outliers -> r)
-> (forall u. (forall d. Data d => d -> u) -> Outliers -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Outliers -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Outliers -> m Outliers)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Outliers -> m Outliers)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Outliers -> m Outliers)
-> Data Outliers
Outliers -> Constr
Outliers -> DataType
(forall b. Data b => b -> b) -> Outliers -> Outliers
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) -> Outliers -> u
forall u. (forall d. Data d => d -> u) -> Outliers -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Outliers -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Outliers -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Outliers -> m Outliers
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Outliers -> m Outliers
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Outliers
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Outliers -> c Outliers
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Outliers)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Outliers)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Outliers -> c Outliers
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Outliers -> c Outliers
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Outliers
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Outliers
$ctoConstr :: Outliers -> Constr
toConstr :: Outliers -> Constr
$cdataTypeOf :: Outliers -> DataType
dataTypeOf :: Outliers -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Outliers)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Outliers)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Outliers)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Outliers)
$cgmapT :: (forall b. Data b => b -> b) -> Outliers -> Outliers
gmapT :: (forall b. Data b => b -> b) -> Outliers -> Outliers
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Outliers -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Outliers -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Outliers -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Outliers -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Outliers -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Outliers -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Outliers -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Outliers -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Outliers -> m Outliers
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Outliers -> m Outliers
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Outliers -> m Outliers
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Outliers -> m Outliers
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Outliers -> m Outliers
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Outliers -> m Outliers
Data, (forall x. Outliers -> Rep Outliers x)
-> (forall x. Rep Outliers x -> Outliers) -> Generic Outliers
forall x. Rep Outliers x -> Outliers
forall x. Outliers -> Rep Outliers x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Outliers -> Rep Outliers x
from :: forall x. Outliers -> Rep Outliers x
$cto :: forall x. Rep Outliers x -> Outliers
to :: forall x. Rep Outliers x -> Outliers
Generic)
instance FromJSON Outliers
instance ToJSON Outliers
instance Binary Outliers where
put :: Outliers -> Put
put (Outliers Int64
v Int64
w Int64
x Int64
y Int64
z) = Int64 -> Put
forall t. Binary t => t -> Put
put Int64
v Put -> Put -> Put
forall a b. PutM a -> PutM b -> PutM b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Int64 -> Put
forall t. Binary t => t -> Put
put Int64
w Put -> Put -> Put
forall a b. PutM a -> PutM b -> PutM b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Int64 -> Put
forall t. Binary t => t -> Put
put Int64
x Put -> Put -> Put
forall a b. PutM a -> PutM b -> PutM b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Int64 -> Put
forall t. Binary t => t -> Put
put Int64
y Put -> Put -> Put
forall a b. PutM a -> PutM b -> PutM b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Int64 -> Put
forall t. Binary t => t -> Put
put Int64
z
get :: Get Outliers
get = Int64 -> Int64 -> Int64 -> Int64 -> Int64 -> Outliers
Outliers (Int64 -> Int64 -> Int64 -> Int64 -> Int64 -> Outliers)
-> Get Int64 -> Get (Int64 -> Int64 -> Int64 -> Int64 -> Outliers)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Int64
forall t. Binary t => Get t
get Get (Int64 -> Int64 -> Int64 -> Int64 -> Outliers)
-> Get Int64 -> Get (Int64 -> Int64 -> Int64 -> Outliers)
forall a b. Get (a -> b) -> Get a -> Get b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get Int64
forall t. Binary t => Get t
get Get (Int64 -> Int64 -> Int64 -> Outliers)
-> Get Int64 -> Get (Int64 -> Int64 -> Outliers)
forall a b. Get (a -> b) -> Get a -> Get b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get Int64
forall t. Binary t => Get t
get Get (Int64 -> Int64 -> Outliers)
-> Get Int64 -> Get (Int64 -> Outliers)
forall a b. Get (a -> b) -> Get a -> Get b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get Int64
forall t. Binary t => Get t
get Get (Int64 -> Outliers) -> Get Int64 -> Get Outliers
forall a b. Get (a -> b) -> Get a -> Get b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get Int64
forall t. Binary t => Get t
get
instance NFData Outliers
data OutlierEffect = Unaffected
| Slight
| Moderate
| Severe
deriving (OutlierEffect -> OutlierEffect -> Bool
(OutlierEffect -> OutlierEffect -> Bool)
-> (OutlierEffect -> OutlierEffect -> Bool) -> Eq OutlierEffect
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: OutlierEffect -> OutlierEffect -> Bool
== :: OutlierEffect -> OutlierEffect -> Bool
$c/= :: OutlierEffect -> OutlierEffect -> Bool
/= :: OutlierEffect -> OutlierEffect -> Bool
Eq, Eq OutlierEffect
Eq OutlierEffect =>
(OutlierEffect -> OutlierEffect -> Ordering)
-> (OutlierEffect -> OutlierEffect -> Bool)
-> (OutlierEffect -> OutlierEffect -> Bool)
-> (OutlierEffect -> OutlierEffect -> Bool)
-> (OutlierEffect -> OutlierEffect -> Bool)
-> (OutlierEffect -> OutlierEffect -> OutlierEffect)
-> (OutlierEffect -> OutlierEffect -> OutlierEffect)
-> Ord OutlierEffect
OutlierEffect -> OutlierEffect -> Bool
OutlierEffect -> OutlierEffect -> Ordering
OutlierEffect -> OutlierEffect -> OutlierEffect
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
$ccompare :: OutlierEffect -> OutlierEffect -> Ordering
compare :: OutlierEffect -> OutlierEffect -> Ordering
$c< :: OutlierEffect -> OutlierEffect -> Bool
< :: OutlierEffect -> OutlierEffect -> Bool
$c<= :: OutlierEffect -> OutlierEffect -> Bool
<= :: OutlierEffect -> OutlierEffect -> Bool
$c> :: OutlierEffect -> OutlierEffect -> Bool
> :: OutlierEffect -> OutlierEffect -> Bool
$c>= :: OutlierEffect -> OutlierEffect -> Bool
>= :: OutlierEffect -> OutlierEffect -> Bool
$cmax :: OutlierEffect -> OutlierEffect -> OutlierEffect
max :: OutlierEffect -> OutlierEffect -> OutlierEffect
$cmin :: OutlierEffect -> OutlierEffect -> OutlierEffect
min :: OutlierEffect -> OutlierEffect -> OutlierEffect
Ord, ReadPrec [OutlierEffect]
ReadPrec OutlierEffect
Int -> ReadS OutlierEffect
ReadS [OutlierEffect]
(Int -> ReadS OutlierEffect)
-> ReadS [OutlierEffect]
-> ReadPrec OutlierEffect
-> ReadPrec [OutlierEffect]
-> Read OutlierEffect
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS OutlierEffect
readsPrec :: Int -> ReadS OutlierEffect
$creadList :: ReadS [OutlierEffect]
readList :: ReadS [OutlierEffect]
$creadPrec :: ReadPrec OutlierEffect
readPrec :: ReadPrec OutlierEffect
$creadListPrec :: ReadPrec [OutlierEffect]
readListPrec :: ReadPrec [OutlierEffect]
Read, Int -> OutlierEffect -> ShowS
[OutlierEffect] -> ShowS
OutlierEffect -> String
(Int -> OutlierEffect -> ShowS)
-> (OutlierEffect -> String)
-> ([OutlierEffect] -> ShowS)
-> Show OutlierEffect
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> OutlierEffect -> ShowS
showsPrec :: Int -> OutlierEffect -> ShowS
$cshow :: OutlierEffect -> String
show :: OutlierEffect -> String
$cshowList :: [OutlierEffect] -> ShowS
showList :: [OutlierEffect] -> ShowS
Show, Typeable OutlierEffect
Typeable OutlierEffect =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OutlierEffect -> c OutlierEffect)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OutlierEffect)
-> (OutlierEffect -> Constr)
-> (OutlierEffect -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c OutlierEffect))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c OutlierEffect))
-> ((forall b. Data b => b -> b) -> OutlierEffect -> OutlierEffect)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> OutlierEffect -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OutlierEffect -> r)
-> (forall u. (forall d. Data d => d -> u) -> OutlierEffect -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> OutlierEffect -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> OutlierEffect -> m OutlierEffect)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> OutlierEffect -> m OutlierEffect)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> OutlierEffect -> m OutlierEffect)
-> Data OutlierEffect
OutlierEffect -> Constr
OutlierEffect -> DataType
(forall b. Data b => b -> b) -> OutlierEffect -> OutlierEffect
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) -> OutlierEffect -> u
forall u. (forall d. Data d => d -> u) -> OutlierEffect -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> OutlierEffect -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OutlierEffect -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> OutlierEffect -> m OutlierEffect
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> OutlierEffect -> m OutlierEffect
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OutlierEffect
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OutlierEffect -> c OutlierEffect
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c OutlierEffect)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c OutlierEffect)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OutlierEffect -> c OutlierEffect
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OutlierEffect -> c OutlierEffect
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OutlierEffect
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OutlierEffect
$ctoConstr :: OutlierEffect -> Constr
toConstr :: OutlierEffect -> Constr
$cdataTypeOf :: OutlierEffect -> DataType
dataTypeOf :: OutlierEffect -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c OutlierEffect)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c OutlierEffect)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c OutlierEffect)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c OutlierEffect)
$cgmapT :: (forall b. Data b => b -> b) -> OutlierEffect -> OutlierEffect
gmapT :: (forall b. Data b => b -> b) -> OutlierEffect -> OutlierEffect
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> OutlierEffect -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> OutlierEffect -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OutlierEffect -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OutlierEffect -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> OutlierEffect -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> OutlierEffect -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> OutlierEffect -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> OutlierEffect -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> OutlierEffect -> m OutlierEffect
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> OutlierEffect -> m OutlierEffect
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> OutlierEffect -> m OutlierEffect
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> OutlierEffect -> m OutlierEffect
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> OutlierEffect -> m OutlierEffect
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> OutlierEffect -> m OutlierEffect
Data, (forall x. OutlierEffect -> Rep OutlierEffect x)
-> (forall x. Rep OutlierEffect x -> OutlierEffect)
-> Generic OutlierEffect
forall x. Rep OutlierEffect x -> OutlierEffect
forall x. OutlierEffect -> Rep OutlierEffect x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. OutlierEffect -> Rep OutlierEffect x
from :: forall x. OutlierEffect -> Rep OutlierEffect x
$cto :: forall x. Rep OutlierEffect x -> OutlierEffect
to :: forall x. Rep OutlierEffect x -> OutlierEffect
Generic)
instance FromJSON OutlierEffect
instance ToJSON OutlierEffect
instance Binary OutlierEffect where
put :: OutlierEffect -> Put
put OutlierEffect
Unaffected = Word8 -> Put
putWord8 Word8
0
put OutlierEffect
Slight = Word8 -> Put
putWord8 Word8
1
put OutlierEffect
Moderate = Word8 -> Put
putWord8 Word8
2
put OutlierEffect
Severe = Word8 -> Put
putWord8 Word8
3
get :: Get OutlierEffect
get = do
Word8
i <- Get Word8
getWord8
case Word8
i of
Word8
0 -> OutlierEffect -> Get OutlierEffect
forall a. a -> Get a
forall (m :: * -> *) a. Monad m => a -> m a
return OutlierEffect
Unaffected
Word8
1 -> OutlierEffect -> Get OutlierEffect
forall a. a -> Get a
forall (m :: * -> *) a. Monad m => a -> m a
return OutlierEffect
Slight
Word8
2 -> OutlierEffect -> Get OutlierEffect
forall a. a -> Get a
forall (m :: * -> *) a. Monad m => a -> m a
return OutlierEffect
Moderate
Word8
3 -> OutlierEffect -> Get OutlierEffect
forall a. a -> Get a
forall (m :: * -> *) a. Monad m => a -> m a
return OutlierEffect
Severe
Word8
_ -> String -> Get OutlierEffect
forall a. String -> Get a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Get OutlierEffect) -> String -> Get OutlierEffect
forall a b. (a -> b) -> a -> b
$ String
"get for OutlierEffect: unexpected " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Word8 -> String
forall a. Show a => a -> String
show Word8
i
instance NFData OutlierEffect
instance Semigroup Outliers where
<> :: Outliers -> Outliers -> Outliers
(<>) = Outliers -> Outliers -> Outliers
addOutliers
instance Monoid Outliers where
mempty :: Outliers
mempty = Int64 -> Int64 -> Int64 -> Int64 -> Int64 -> Outliers
Outliers Int64
0 Int64
0 Int64
0 Int64
0 Int64
0
#if !(MIN_VERSION_base(4,11,0))
mappend = addOutliers
#endif
addOutliers :: Outliers -> Outliers -> Outliers
addOutliers :: Outliers -> Outliers -> Outliers
addOutliers (Outliers Int64
s Int64
a Int64
b Int64
c Int64
d) (Outliers Int64
t Int64
w Int64
x Int64
y Int64
z) =
Int64 -> Int64 -> Int64 -> Int64 -> Int64 -> Outliers
Outliers (Int64
sInt64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
+Int64
t) (Int64
aInt64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
+Int64
w) (Int64
bInt64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
+Int64
x) (Int64
cInt64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
+Int64
y) (Int64
dInt64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
+Int64
z)
{-# INLINE addOutliers #-}
data OutlierVariance = OutlierVariance {
OutlierVariance -> OutlierEffect
ovEffect :: OutlierEffect
, OutlierVariance -> String
ovDesc :: String
, OutlierVariance -> Double
ovFraction :: Double
} deriving (OutlierVariance -> OutlierVariance -> Bool
(OutlierVariance -> OutlierVariance -> Bool)
-> (OutlierVariance -> OutlierVariance -> Bool)
-> Eq OutlierVariance
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: OutlierVariance -> OutlierVariance -> Bool
== :: OutlierVariance -> OutlierVariance -> Bool
$c/= :: OutlierVariance -> OutlierVariance -> Bool
/= :: OutlierVariance -> OutlierVariance -> Bool
Eq, ReadPrec [OutlierVariance]
ReadPrec OutlierVariance
Int -> ReadS OutlierVariance
ReadS [OutlierVariance]
(Int -> ReadS OutlierVariance)
-> ReadS [OutlierVariance]
-> ReadPrec OutlierVariance
-> ReadPrec [OutlierVariance]
-> Read OutlierVariance
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS OutlierVariance
readsPrec :: Int -> ReadS OutlierVariance
$creadList :: ReadS [OutlierVariance]
readList :: ReadS [OutlierVariance]
$creadPrec :: ReadPrec OutlierVariance
readPrec :: ReadPrec OutlierVariance
$creadListPrec :: ReadPrec [OutlierVariance]
readListPrec :: ReadPrec [OutlierVariance]
Read, Int -> OutlierVariance -> ShowS
[OutlierVariance] -> ShowS
OutlierVariance -> String
(Int -> OutlierVariance -> ShowS)
-> (OutlierVariance -> String)
-> ([OutlierVariance] -> ShowS)
-> Show OutlierVariance
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> OutlierVariance -> ShowS
showsPrec :: Int -> OutlierVariance -> ShowS
$cshow :: OutlierVariance -> String
show :: OutlierVariance -> String
$cshowList :: [OutlierVariance] -> ShowS
showList :: [OutlierVariance] -> ShowS
Show, Typeable OutlierVariance
Typeable OutlierVariance =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OutlierVariance -> c OutlierVariance)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OutlierVariance)
-> (OutlierVariance -> Constr)
-> (OutlierVariance -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c OutlierVariance))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c OutlierVariance))
-> ((forall b. Data b => b -> b)
-> OutlierVariance -> OutlierVariance)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> OutlierVariance -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OutlierVariance -> r)
-> (forall u.
(forall d. Data d => d -> u) -> OutlierVariance -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> OutlierVariance -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> OutlierVariance -> m OutlierVariance)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> OutlierVariance -> m OutlierVariance)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> OutlierVariance -> m OutlierVariance)
-> Data OutlierVariance
OutlierVariance -> Constr
OutlierVariance -> DataType
(forall b. Data b => b -> b) -> OutlierVariance -> OutlierVariance
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) -> OutlierVariance -> u
forall u. (forall d. Data d => d -> u) -> OutlierVariance -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> OutlierVariance -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OutlierVariance -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> OutlierVariance -> m OutlierVariance
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> OutlierVariance -> m OutlierVariance
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OutlierVariance
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OutlierVariance -> c OutlierVariance
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c OutlierVariance)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c OutlierVariance)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OutlierVariance -> c OutlierVariance
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OutlierVariance -> c OutlierVariance
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OutlierVariance
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OutlierVariance
$ctoConstr :: OutlierVariance -> Constr
toConstr :: OutlierVariance -> Constr
$cdataTypeOf :: OutlierVariance -> DataType
dataTypeOf :: OutlierVariance -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c OutlierVariance)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c OutlierVariance)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c OutlierVariance)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c OutlierVariance)
$cgmapT :: (forall b. Data b => b -> b) -> OutlierVariance -> OutlierVariance
gmapT :: (forall b. Data b => b -> b) -> OutlierVariance -> OutlierVariance
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> OutlierVariance -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> OutlierVariance -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OutlierVariance -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OutlierVariance -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> OutlierVariance -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> OutlierVariance -> [u]
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> OutlierVariance -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> OutlierVariance -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> OutlierVariance -> m OutlierVariance
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> OutlierVariance -> m OutlierVariance
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> OutlierVariance -> m OutlierVariance
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> OutlierVariance -> m OutlierVariance
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> OutlierVariance -> m OutlierVariance
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> OutlierVariance -> m OutlierVariance
Data, (forall x. OutlierVariance -> Rep OutlierVariance x)
-> (forall x. Rep OutlierVariance x -> OutlierVariance)
-> Generic OutlierVariance
forall x. Rep OutlierVariance x -> OutlierVariance
forall x. OutlierVariance -> Rep OutlierVariance x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. OutlierVariance -> Rep OutlierVariance x
from :: forall x. OutlierVariance -> Rep OutlierVariance x
$cto :: forall x. Rep OutlierVariance x -> OutlierVariance
to :: forall x. Rep OutlierVariance x -> OutlierVariance
Generic)
instance FromJSON OutlierVariance
instance ToJSON OutlierVariance
instance Binary OutlierVariance where
put :: OutlierVariance -> Put
put (OutlierVariance OutlierEffect
x String
y Double
z) = OutlierEffect -> Put
forall t. Binary t => t -> Put
put OutlierEffect
x Put -> Put -> Put
forall a b. PutM a -> PutM b -> PutM b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> String -> Put
forall t. Binary t => t -> Put
put String
y Put -> Put -> Put
forall a b. PutM a -> PutM b -> PutM b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Double -> Put
forall t. Binary t => t -> Put
put Double
z
get :: Get OutlierVariance
get = OutlierEffect -> String -> Double -> OutlierVariance
OutlierVariance (OutlierEffect -> String -> Double -> OutlierVariance)
-> Get OutlierEffect -> Get (String -> Double -> OutlierVariance)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get OutlierEffect
forall t. Binary t => Get t
get Get (String -> Double -> OutlierVariance)
-> Get String -> Get (Double -> OutlierVariance)
forall a b. Get (a -> b) -> Get a -> Get b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get String
forall t. Binary t => Get t
get Get (Double -> OutlierVariance)
-> Get Double -> Get OutlierVariance
forall a b. Get (a -> b) -> Get a -> Get b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get Double
forall t. Binary t => Get t
get
instance NFData OutlierVariance where
rnf :: OutlierVariance -> ()
rnf OutlierVariance{Double
String
OutlierEffect
ovEffect :: OutlierVariance -> OutlierEffect
ovDesc :: OutlierVariance -> String
ovFraction :: OutlierVariance -> Double
ovEffect :: OutlierEffect
ovDesc :: String
ovFraction :: Double
..} = OutlierEffect -> ()
forall a. NFData a => a -> ()
rnf OutlierEffect
ovEffect () -> () -> ()
forall a b. a -> b -> b
`seq` String -> ()
forall a. NFData a => a -> ()
rnf String
ovDesc () -> () -> ()
forall a b. a -> b -> b
`seq` Double -> ()
forall a. NFData a => a -> ()
rnf Double
ovFraction
data Regression = Regression {
Regression -> String
regResponder :: String
, Regression -> Map String (Estimate ConfInt Double)
regCoeffs :: Map String (St.Estimate St.ConfInt Double)
, Regression -> Estimate ConfInt Double
regRSquare :: St.Estimate St.ConfInt Double
} deriving (Regression -> Regression -> Bool
(Regression -> Regression -> Bool)
-> (Regression -> Regression -> Bool) -> Eq Regression
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Regression -> Regression -> Bool
== :: Regression -> Regression -> Bool
$c/= :: Regression -> Regression -> Bool
/= :: Regression -> Regression -> Bool
Eq, ReadPrec [Regression]
ReadPrec Regression
Int -> ReadS Regression
ReadS [Regression]
(Int -> ReadS Regression)
-> ReadS [Regression]
-> ReadPrec Regression
-> ReadPrec [Regression]
-> Read Regression
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Regression
readsPrec :: Int -> ReadS Regression
$creadList :: ReadS [Regression]
readList :: ReadS [Regression]
$creadPrec :: ReadPrec Regression
readPrec :: ReadPrec Regression
$creadListPrec :: ReadPrec [Regression]
readListPrec :: ReadPrec [Regression]
Read, Int -> Regression -> ShowS
[Regression] -> ShowS
Regression -> String
(Int -> Regression -> ShowS)
-> (Regression -> String)
-> ([Regression] -> ShowS)
-> Show Regression
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Regression -> ShowS
showsPrec :: Int -> Regression -> ShowS
$cshow :: Regression -> String
show :: Regression -> String
$cshowList :: [Regression] -> ShowS
showList :: [Regression] -> ShowS
Show, (forall x. Regression -> Rep Regression x)
-> (forall x. Rep Regression x -> Regression) -> Generic Regression
forall x. Rep Regression x -> Regression
forall x. Regression -> Rep Regression x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Regression -> Rep Regression x
from :: forall x. Regression -> Rep Regression x
$cto :: forall x. Rep Regression x -> Regression
to :: forall x. Rep Regression x -> Regression
Generic)
instance FromJSON Regression
instance ToJSON Regression
instance Binary Regression where
put :: Regression -> Put
put Regression{String
Map String (Estimate ConfInt Double)
Estimate ConfInt Double
regResponder :: Regression -> String
regCoeffs :: Regression -> Map String (Estimate ConfInt Double)
regRSquare :: Regression -> Estimate ConfInt Double
regResponder :: String
regCoeffs :: Map String (Estimate ConfInt Double)
regRSquare :: Estimate ConfInt Double
..} =
String -> Put
forall t. Binary t => t -> Put
put String
regResponder Put -> Put -> Put
forall a b. PutM a -> PutM b -> PutM b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Map String (Estimate ConfInt Double) -> Put
forall t. Binary t => t -> Put
put Map String (Estimate ConfInt Double)
regCoeffs Put -> Put -> Put
forall a b. PutM a -> PutM b -> PutM b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Estimate ConfInt Double -> Put
forall t. Binary t => t -> Put
put Estimate ConfInt Double
regRSquare
get :: Get Regression
get = String
-> Map String (Estimate ConfInt Double)
-> Estimate ConfInt Double
-> Regression
Regression (String
-> Map String (Estimate ConfInt Double)
-> Estimate ConfInt Double
-> Regression)
-> Get String
-> Get
(Map String (Estimate ConfInt Double)
-> Estimate ConfInt Double -> Regression)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get String
forall t. Binary t => Get t
get Get
(Map String (Estimate ConfInt Double)
-> Estimate ConfInt Double -> Regression)
-> Get (Map String (Estimate ConfInt Double))
-> Get (Estimate ConfInt Double -> Regression)
forall a b. Get (a -> b) -> Get a -> Get b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get (Map String (Estimate ConfInt Double))
forall t. Binary t => Get t
get Get (Estimate ConfInt Double -> Regression)
-> Get (Estimate ConfInt Double) -> Get Regression
forall a b. Get (a -> b) -> Get a -> Get b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get (Estimate ConfInt Double)
forall t. Binary t => Get t
get
instance NFData Regression where
rnf :: Regression -> ()
rnf Regression{String
Map String (Estimate ConfInt Double)
Estimate ConfInt Double
regResponder :: Regression -> String
regCoeffs :: Regression -> Map String (Estimate ConfInt Double)
regRSquare :: Regression -> Estimate ConfInt Double
regResponder :: String
regCoeffs :: Map String (Estimate ConfInt Double)
regRSquare :: Estimate ConfInt Double
..} =
String -> ()
forall a. NFData a => a -> ()
rnf String
regResponder () -> () -> ()
forall a b. a -> b -> b
`seq` Map String (Estimate ConfInt Double) -> ()
forall a. NFData a => a -> ()
rnf Map String (Estimate ConfInt Double)
regCoeffs () -> () -> ()
forall a b. a -> b -> b
`seq` Estimate ConfInt Double -> ()
forall a. NFData a => a -> ()
rnf Estimate ConfInt Double
regRSquare
data SampleAnalysis = SampleAnalysis {
SampleAnalysis -> [Regression]
anRegress :: [Regression]
, SampleAnalysis -> Estimate ConfInt Double
anMean :: St.Estimate St.ConfInt Double
, SampleAnalysis -> Estimate ConfInt Double
anStdDev :: St.Estimate St.ConfInt Double
, SampleAnalysis -> OutlierVariance
anOutlierVar :: OutlierVariance
} deriving (SampleAnalysis -> SampleAnalysis -> Bool
(SampleAnalysis -> SampleAnalysis -> Bool)
-> (SampleAnalysis -> SampleAnalysis -> Bool) -> Eq SampleAnalysis
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SampleAnalysis -> SampleAnalysis -> Bool
== :: SampleAnalysis -> SampleAnalysis -> Bool
$c/= :: SampleAnalysis -> SampleAnalysis -> Bool
/= :: SampleAnalysis -> SampleAnalysis -> Bool
Eq, ReadPrec [SampleAnalysis]
ReadPrec SampleAnalysis
Int -> ReadS SampleAnalysis
ReadS [SampleAnalysis]
(Int -> ReadS SampleAnalysis)
-> ReadS [SampleAnalysis]
-> ReadPrec SampleAnalysis
-> ReadPrec [SampleAnalysis]
-> Read SampleAnalysis
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS SampleAnalysis
readsPrec :: Int -> ReadS SampleAnalysis
$creadList :: ReadS [SampleAnalysis]
readList :: ReadS [SampleAnalysis]
$creadPrec :: ReadPrec SampleAnalysis
readPrec :: ReadPrec SampleAnalysis
$creadListPrec :: ReadPrec [SampleAnalysis]
readListPrec :: ReadPrec [SampleAnalysis]
Read, Int -> SampleAnalysis -> ShowS
[SampleAnalysis] -> ShowS
SampleAnalysis -> String
(Int -> SampleAnalysis -> ShowS)
-> (SampleAnalysis -> String)
-> ([SampleAnalysis] -> ShowS)
-> Show SampleAnalysis
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SampleAnalysis -> ShowS
showsPrec :: Int -> SampleAnalysis -> ShowS
$cshow :: SampleAnalysis -> String
show :: SampleAnalysis -> String
$cshowList :: [SampleAnalysis] -> ShowS
showList :: [SampleAnalysis] -> ShowS
Show, (forall x. SampleAnalysis -> Rep SampleAnalysis x)
-> (forall x. Rep SampleAnalysis x -> SampleAnalysis)
-> Generic SampleAnalysis
forall x. Rep SampleAnalysis x -> SampleAnalysis
forall x. SampleAnalysis -> Rep SampleAnalysis x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. SampleAnalysis -> Rep SampleAnalysis x
from :: forall x. SampleAnalysis -> Rep SampleAnalysis x
$cto :: forall x. Rep SampleAnalysis x -> SampleAnalysis
to :: forall x. Rep SampleAnalysis x -> SampleAnalysis
Generic)
instance FromJSON SampleAnalysis
instance ToJSON SampleAnalysis
instance Binary SampleAnalysis where
put :: SampleAnalysis -> Put
put SampleAnalysis{[Regression]
Estimate ConfInt Double
OutlierVariance
anRegress :: SampleAnalysis -> [Regression]
anMean :: SampleAnalysis -> Estimate ConfInt Double
anStdDev :: SampleAnalysis -> Estimate ConfInt Double
anOutlierVar :: SampleAnalysis -> OutlierVariance
anRegress :: [Regression]
anMean :: Estimate ConfInt Double
anStdDev :: Estimate ConfInt Double
anOutlierVar :: OutlierVariance
..} = do
[Regression] -> Put
forall t. Binary t => t -> Put
put [Regression]
anRegress; Estimate ConfInt Double -> Put
forall t. Binary t => t -> Put
put Estimate ConfInt Double
anMean; Estimate ConfInt Double -> Put
forall t. Binary t => t -> Put
put Estimate ConfInt Double
anStdDev; OutlierVariance -> Put
forall t. Binary t => t -> Put
put OutlierVariance
anOutlierVar
get :: Get SampleAnalysis
get = [Regression]
-> Estimate ConfInt Double
-> Estimate ConfInt Double
-> OutlierVariance
-> SampleAnalysis
SampleAnalysis ([Regression]
-> Estimate ConfInt Double
-> Estimate ConfInt Double
-> OutlierVariance
-> SampleAnalysis)
-> Get [Regression]
-> Get
(Estimate ConfInt Double
-> Estimate ConfInt Double -> OutlierVariance -> SampleAnalysis)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get [Regression]
forall t. Binary t => Get t
get Get
(Estimate ConfInt Double
-> Estimate ConfInt Double -> OutlierVariance -> SampleAnalysis)
-> Get (Estimate ConfInt Double)
-> Get
(Estimate ConfInt Double -> OutlierVariance -> SampleAnalysis)
forall a b. Get (a -> b) -> Get a -> Get b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get (Estimate ConfInt Double)
forall t. Binary t => Get t
get Get (Estimate ConfInt Double -> OutlierVariance -> SampleAnalysis)
-> Get (Estimate ConfInt Double)
-> Get (OutlierVariance -> SampleAnalysis)
forall a b. Get (a -> b) -> Get a -> Get b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get (Estimate ConfInt Double)
forall t. Binary t => Get t
get Get (OutlierVariance -> SampleAnalysis)
-> Get OutlierVariance -> Get SampleAnalysis
forall a b. Get (a -> b) -> Get a -> Get b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get OutlierVariance
forall t. Binary t => Get t
get
instance NFData SampleAnalysis where
rnf :: SampleAnalysis -> ()
rnf SampleAnalysis{[Regression]
Estimate ConfInt Double
OutlierVariance
anRegress :: SampleAnalysis -> [Regression]
anMean :: SampleAnalysis -> Estimate ConfInt Double
anStdDev :: SampleAnalysis -> Estimate ConfInt Double
anOutlierVar :: SampleAnalysis -> OutlierVariance
anRegress :: [Regression]
anMean :: Estimate ConfInt Double
anStdDev :: Estimate ConfInt Double
anOutlierVar :: OutlierVariance
..} =
[Regression] -> ()
forall a. NFData a => a -> ()
rnf [Regression]
anRegress () -> () -> ()
forall a b. a -> b -> b
`seq` Estimate ConfInt Double -> ()
forall a. NFData a => a -> ()
rnf Estimate ConfInt Double
anMean () -> () -> ()
forall a b. a -> b -> b
`seq`
Estimate ConfInt Double -> ()
forall a. NFData a => a -> ()
rnf Estimate ConfInt Double
anStdDev () -> () -> ()
forall a b. a -> b -> b
`seq` OutlierVariance -> ()
forall a. NFData a => a -> ()
rnf OutlierVariance
anOutlierVar
data KDE = KDE {
KDE -> String
kdeType :: String
, KDE -> Vector Double
kdeValues :: U.Vector Double
, KDE -> Vector Double
kdePDF :: U.Vector Double
} deriving (KDE -> KDE -> Bool
(KDE -> KDE -> Bool) -> (KDE -> KDE -> Bool) -> Eq KDE
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: KDE -> KDE -> Bool
== :: KDE -> KDE -> Bool
$c/= :: KDE -> KDE -> Bool
/= :: KDE -> KDE -> Bool
Eq, ReadPrec [KDE]
ReadPrec KDE
Int -> ReadS KDE
ReadS [KDE]
(Int -> ReadS KDE)
-> ReadS [KDE] -> ReadPrec KDE -> ReadPrec [KDE] -> Read KDE
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS KDE
readsPrec :: Int -> ReadS KDE
$creadList :: ReadS [KDE]
readList :: ReadS [KDE]
$creadPrec :: ReadPrec KDE
readPrec :: ReadPrec KDE
$creadListPrec :: ReadPrec [KDE]
readListPrec :: ReadPrec [KDE]
Read, Int -> KDE -> ShowS
[KDE] -> ShowS
KDE -> String
(Int -> KDE -> ShowS)
-> (KDE -> String) -> ([KDE] -> ShowS) -> Show KDE
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> KDE -> ShowS
showsPrec :: Int -> KDE -> ShowS
$cshow :: KDE -> String
show :: KDE -> String
$cshowList :: [KDE] -> ShowS
showList :: [KDE] -> ShowS
Show, Typeable KDE
Typeable KDE =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> KDE -> c KDE)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c KDE)
-> (KDE -> Constr)
-> (KDE -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c KDE))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c KDE))
-> ((forall b. Data b => b -> b) -> KDE -> KDE)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> KDE -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> KDE -> r)
-> (forall u. (forall d. Data d => d -> u) -> KDE -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> KDE -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> KDE -> m KDE)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> KDE -> m KDE)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> KDE -> m KDE)
-> Data KDE
KDE -> Constr
KDE -> DataType
(forall b. Data b => b -> b) -> KDE -> KDE
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) -> KDE -> u
forall u. (forall d. Data d => d -> u) -> KDE -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> KDE -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> KDE -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> KDE -> m KDE
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> KDE -> m KDE
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c KDE
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> KDE -> c KDE
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c KDE)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c KDE)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> KDE -> c KDE
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> KDE -> c KDE
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c KDE
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c KDE
$ctoConstr :: KDE -> Constr
toConstr :: KDE -> Constr
$cdataTypeOf :: KDE -> DataType
dataTypeOf :: KDE -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c KDE)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c KDE)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c KDE)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c KDE)
$cgmapT :: (forall b. Data b => b -> b) -> KDE -> KDE
gmapT :: (forall b. Data b => b -> b) -> KDE -> KDE
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> KDE -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> KDE -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> KDE -> r
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> KDE -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> KDE -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> KDE -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> KDE -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> KDE -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> KDE -> m KDE
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> KDE -> m KDE
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> KDE -> m KDE
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> KDE -> m KDE
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> KDE -> m KDE
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> KDE -> m KDE
Data, (forall x. KDE -> Rep KDE x)
-> (forall x. Rep KDE x -> KDE) -> Generic KDE
forall x. Rep KDE x -> KDE
forall x. KDE -> Rep KDE x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. KDE -> Rep KDE x
from :: forall x. KDE -> Rep KDE x
$cto :: forall x. Rep KDE x -> KDE
to :: forall x. Rep KDE x -> KDE
Generic)
instance FromJSON KDE
instance ToJSON KDE
instance Binary KDE where
put :: KDE -> Put
put KDE{String
Vector Double
kdeType :: KDE -> String
kdeValues :: KDE -> Vector Double
kdePDF :: KDE -> Vector Double
kdeType :: String
kdeValues :: Vector Double
kdePDF :: Vector Double
..} = String -> Put
forall t. Binary t => t -> Put
put String
kdeType Put -> Put -> Put
forall a b. PutM a -> PutM b -> PutM b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Vector Double -> Put
forall t. Binary t => t -> Put
put Vector Double
kdeValues Put -> Put -> Put
forall a b. PutM a -> PutM b -> PutM b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Vector Double -> Put
forall t. Binary t => t -> Put
put Vector Double
kdePDF
get :: Get KDE
get = String -> Vector Double -> Vector Double -> KDE
KDE (String -> Vector Double -> Vector Double -> KDE)
-> Get String -> Get (Vector Double -> Vector Double -> KDE)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get String
forall t. Binary t => Get t
get Get (Vector Double -> Vector Double -> KDE)
-> Get (Vector Double) -> Get (Vector Double -> KDE)
forall a b. Get (a -> b) -> Get a -> Get b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get (Vector Double)
forall t. Binary t => Get t
get Get (Vector Double -> KDE) -> Get (Vector Double) -> Get KDE
forall a b. Get (a -> b) -> Get a -> Get b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get (Vector Double)
forall t. Binary t => Get t
get
instance NFData KDE where
rnf :: KDE -> ()
rnf KDE{String
Vector Double
kdeType :: KDE -> String
kdeValues :: KDE -> Vector Double
kdePDF :: KDE -> Vector Double
kdeType :: String
kdeValues :: Vector Double
kdePDF :: Vector Double
..} = String -> ()
forall a. NFData a => a -> ()
rnf String
kdeType () -> () -> ()
forall a b. a -> b -> b
`seq` Vector Double -> ()
forall a. NFData a => a -> ()
rnf Vector Double
kdeValues () -> () -> ()
forall a b. a -> b -> b
`seq` Vector Double -> ()
forall a. NFData a => a -> ()
rnf Vector Double
kdePDF
data Report = Report {
Report -> Int
reportNumber :: Int
, Report -> String
reportName :: String
, Report -> [String]
reportKeys :: [String]
, Report -> Vector Measured
reportMeasured :: V.Vector Measured
, Report -> SampleAnalysis
reportAnalysis :: SampleAnalysis
, Report -> Outliers
reportOutliers :: Outliers
, Report -> [KDE]
reportKDEs :: [KDE]
} deriving (Report -> Report -> Bool
(Report -> Report -> Bool)
-> (Report -> Report -> Bool) -> Eq Report
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Report -> Report -> Bool
== :: Report -> Report -> Bool
$c/= :: Report -> Report -> Bool
/= :: Report -> Report -> Bool
Eq, ReadPrec [Report]
ReadPrec Report
Int -> ReadS Report
ReadS [Report]
(Int -> ReadS Report)
-> ReadS [Report]
-> ReadPrec Report
-> ReadPrec [Report]
-> Read Report
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Report
readsPrec :: Int -> ReadS Report
$creadList :: ReadS [Report]
readList :: ReadS [Report]
$creadPrec :: ReadPrec Report
readPrec :: ReadPrec Report
$creadListPrec :: ReadPrec [Report]
readListPrec :: ReadPrec [Report]
Read, Int -> Report -> ShowS
[Report] -> ShowS
Report -> String
(Int -> Report -> ShowS)
-> (Report -> String) -> ([Report] -> ShowS) -> Show Report
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Report -> ShowS
showsPrec :: Int -> Report -> ShowS
$cshow :: Report -> String
show :: Report -> String
$cshowList :: [Report] -> ShowS
showList :: [Report] -> ShowS
Show, (forall x. Report -> Rep Report x)
-> (forall x. Rep Report x -> Report) -> Generic Report
forall x. Rep Report x -> Report
forall x. Report -> Rep Report x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Report -> Rep Report x
from :: forall x. Report -> Rep Report x
$cto :: forall x. Rep Report x -> Report
to :: forall x. Rep Report x -> Report
Generic)
instance FromJSON Report
instance ToJSON Report
instance Binary Report where
put :: Report -> Put
put Report{Int
String
[String]
[KDE]
Vector Measured
SampleAnalysis
Outliers
reportNumber :: Report -> Int
reportName :: Report -> String
reportKeys :: Report -> [String]
reportMeasured :: Report -> Vector Measured
reportAnalysis :: Report -> SampleAnalysis
reportOutliers :: Report -> Outliers
reportKDEs :: Report -> [KDE]
reportNumber :: Int
reportName :: String
reportKeys :: [String]
reportMeasured :: Vector Measured
reportAnalysis :: SampleAnalysis
reportOutliers :: Outliers
reportKDEs :: [KDE]
..} =
Int -> Put
forall t. Binary t => t -> Put
put Int
reportNumber Put -> Put -> Put
forall a b. PutM a -> PutM b -> PutM b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> String -> Put
forall t. Binary t => t -> Put
put String
reportName Put -> Put -> Put
forall a b. PutM a -> PutM b -> PutM b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> [String] -> Put
forall t. Binary t => t -> Put
put [String]
reportKeys Put -> Put -> Put
forall a b. PutM a -> PutM b -> PutM b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
Vector Measured -> Put
forall t. Binary t => t -> Put
put Vector Measured
reportMeasured Put -> Put -> Put
forall a b. PutM a -> PutM b -> PutM b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> SampleAnalysis -> Put
forall t. Binary t => t -> Put
put SampleAnalysis
reportAnalysis Put -> Put -> Put
forall a b. PutM a -> PutM b -> PutM b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Outliers -> Put
forall t. Binary t => t -> Put
put Outliers
reportOutliers Put -> Put -> Put
forall a b. PutM a -> PutM b -> PutM b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
[KDE] -> Put
forall t. Binary t => t -> Put
put [KDE]
reportKDEs
get :: Get Report
get = Int
-> String
-> [String]
-> Vector Measured
-> SampleAnalysis
-> Outliers
-> [KDE]
-> Report
Report (Int
-> String
-> [String]
-> Vector Measured
-> SampleAnalysis
-> Outliers
-> [KDE]
-> Report)
-> Get Int
-> Get
(String
-> [String]
-> Vector Measured
-> SampleAnalysis
-> Outliers
-> [KDE]
-> Report)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Int
forall t. Binary t => Get t
get Get
(String
-> [String]
-> Vector Measured
-> SampleAnalysis
-> Outliers
-> [KDE]
-> Report)
-> Get String
-> Get
([String]
-> Vector Measured
-> SampleAnalysis
-> Outliers
-> [KDE]
-> Report)
forall a b. Get (a -> b) -> Get a -> Get b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get String
forall t. Binary t => Get t
get Get
([String]
-> Vector Measured
-> SampleAnalysis
-> Outliers
-> [KDE]
-> Report)
-> Get [String]
-> Get
(Vector Measured -> SampleAnalysis -> Outliers -> [KDE] -> Report)
forall a b. Get (a -> b) -> Get a -> Get b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get [String]
forall t. Binary t => Get t
get Get
(Vector Measured -> SampleAnalysis -> Outliers -> [KDE] -> Report)
-> Get (Vector Measured)
-> Get (SampleAnalysis -> Outliers -> [KDE] -> Report)
forall a b. Get (a -> b) -> Get a -> Get b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get (Vector Measured)
forall t. Binary t => Get t
get Get (SampleAnalysis -> Outliers -> [KDE] -> Report)
-> Get SampleAnalysis -> Get (Outliers -> [KDE] -> Report)
forall a b. Get (a -> b) -> Get a -> Get b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get SampleAnalysis
forall t. Binary t => Get t
get Get (Outliers -> [KDE] -> Report)
-> Get Outliers -> Get ([KDE] -> Report)
forall a b. Get (a -> b) -> Get a -> Get b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get Outliers
forall t. Binary t => Get t
get Get ([KDE] -> Report) -> Get [KDE] -> Get Report
forall a b. Get (a -> b) -> Get a -> Get b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get [KDE]
forall t. Binary t => Get t
get
instance NFData Report where
rnf :: Report -> ()
rnf Report{Int
String
[String]
[KDE]
Vector Measured
SampleAnalysis
Outliers
reportNumber :: Report -> Int
reportName :: Report -> String
reportKeys :: Report -> [String]
reportMeasured :: Report -> Vector Measured
reportAnalysis :: Report -> SampleAnalysis
reportOutliers :: Report -> Outliers
reportKDEs :: Report -> [KDE]
reportNumber :: Int
reportName :: String
reportKeys :: [String]
reportMeasured :: Vector Measured
reportAnalysis :: SampleAnalysis
reportOutliers :: Outliers
reportKDEs :: [KDE]
..} =
Int -> ()
forall a. NFData a => a -> ()
rnf Int
reportNumber () -> () -> ()
forall a b. a -> b -> b
`seq` String -> ()
forall a. NFData a => a -> ()
rnf String
reportName () -> () -> ()
forall a b. a -> b -> b
`seq` [String] -> ()
forall a. NFData a => a -> ()
rnf [String]
reportKeys () -> () -> ()
forall a b. a -> b -> b
`seq`
Vector Measured -> ()
forall a. NFData a => a -> ()
rnf Vector Measured
reportMeasured () -> () -> ()
forall a b. a -> b -> b
`seq` SampleAnalysis -> ()
forall a. NFData a => a -> ()
rnf SampleAnalysis
reportAnalysis () -> () -> ()
forall a b. a -> b -> b
`seq` Outliers -> ()
forall a. NFData a => a -> ()
rnf Outliers
reportOutliers () -> () -> ()
forall a b. a -> b -> b
`seq`
[KDE] -> ()
forall a. NFData a => a -> ()
rnf [KDE]
reportKDEs
data DataRecord = Measurement Int String (V.Vector Measured)
| Analysed Report
deriving (DataRecord -> DataRecord -> Bool
(DataRecord -> DataRecord -> Bool)
-> (DataRecord -> DataRecord -> Bool) -> Eq DataRecord
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DataRecord -> DataRecord -> Bool
== :: DataRecord -> DataRecord -> Bool
$c/= :: DataRecord -> DataRecord -> Bool
/= :: DataRecord -> DataRecord -> Bool
Eq, ReadPrec [DataRecord]
ReadPrec DataRecord
Int -> ReadS DataRecord
ReadS [DataRecord]
(Int -> ReadS DataRecord)
-> ReadS [DataRecord]
-> ReadPrec DataRecord
-> ReadPrec [DataRecord]
-> Read DataRecord
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS DataRecord
readsPrec :: Int -> ReadS DataRecord
$creadList :: ReadS [DataRecord]
readList :: ReadS [DataRecord]
$creadPrec :: ReadPrec DataRecord
readPrec :: ReadPrec DataRecord
$creadListPrec :: ReadPrec [DataRecord]
readListPrec :: ReadPrec [DataRecord]
Read, Int -> DataRecord -> ShowS
[DataRecord] -> ShowS
DataRecord -> String
(Int -> DataRecord -> ShowS)
-> (DataRecord -> String)
-> ([DataRecord] -> ShowS)
-> Show DataRecord
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DataRecord -> ShowS
showsPrec :: Int -> DataRecord -> ShowS
$cshow :: DataRecord -> String
show :: DataRecord -> String
$cshowList :: [DataRecord] -> ShowS
showList :: [DataRecord] -> ShowS
Show, (forall x. DataRecord -> Rep DataRecord x)
-> (forall x. Rep DataRecord x -> DataRecord) -> Generic DataRecord
forall x. Rep DataRecord x -> DataRecord
forall x. DataRecord -> Rep DataRecord x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. DataRecord -> Rep DataRecord x
from :: forall x. DataRecord -> Rep DataRecord x
$cto :: forall x. Rep DataRecord x -> DataRecord
to :: forall x. Rep DataRecord x -> DataRecord
Generic)
instance Binary DataRecord where
put :: DataRecord -> Put
put (Measurement Int
i String
n Vector Measured
v) = Word8 -> Put
putWord8 Word8
0 Put -> Put -> Put
forall a b. PutM a -> PutM b -> PutM b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Int -> Put
forall t. Binary t => t -> Put
put Int
i Put -> Put -> Put
forall a b. PutM a -> PutM b -> PutM b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> String -> Put
forall t. Binary t => t -> Put
put String
n Put -> Put -> Put
forall a b. PutM a -> PutM b -> PutM b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Vector Measured -> Put
forall t. Binary t => t -> Put
put Vector Measured
v
put (Analysed Report
r) = Word8 -> Put
putWord8 Word8
1 Put -> Put -> Put
forall a b. PutM a -> PutM b -> PutM b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Report -> Put
forall t. Binary t => t -> Put
put Report
r
get :: Get DataRecord
get = do
Word8
w <- Get Word8
getWord8
case Word8
w of
Word8
0 -> Int -> String -> Vector Measured -> DataRecord
Measurement (Int -> String -> Vector Measured -> DataRecord)
-> Get Int -> Get (String -> Vector Measured -> DataRecord)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Int
forall t. Binary t => Get t
get Get (String -> Vector Measured -> DataRecord)
-> Get String -> Get (Vector Measured -> DataRecord)
forall a b. Get (a -> b) -> Get a -> Get b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get String
forall t. Binary t => Get t
get Get (Vector Measured -> DataRecord)
-> Get (Vector Measured) -> Get DataRecord
forall a b. Get (a -> b) -> Get a -> Get b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get (Vector Measured)
forall t. Binary t => Get t
get
Word8
1 -> Report -> DataRecord
Analysed (Report -> DataRecord) -> Get Report -> Get DataRecord
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Report
forall t. Binary t => Get t
get
Word8
_ -> String -> Get DataRecord
forall a. HasCallStack => String -> a
error (String
"bad tag " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Word8 -> String
forall a. Show a => a -> String
show Word8
w)
instance NFData DataRecord where
rnf :: DataRecord -> ()
rnf (Measurement Int
i String
n Vector Measured
v) = Int -> ()
forall a. NFData a => a -> ()
rnf Int
i () -> () -> ()
forall a b. a -> b -> b
`seq` String -> ()
forall a. NFData a => a -> ()
rnf String
n () -> () -> ()
forall a b. a -> b -> b
`seq` Vector Measured -> ()
forall a. NFData a => a -> ()
rnf Vector Measured
v
rnf (Analysed Report
r) = Report -> ()
forall a. NFData a => a -> ()
rnf Report
r
instance FromJSON DataRecord
instance ToJSON DataRecord