{-# 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, Typeable)
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
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Verbosity -> Verbosity -> Bool
$c/= :: Verbosity -> Verbosity -> Bool
== :: Verbosity -> Verbosity -> Bool
$c== :: Verbosity -> Verbosity -> Bool
Eq, Eq 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
min :: Verbosity -> Verbosity -> Verbosity
$cmin :: Verbosity -> Verbosity -> Verbosity
max :: Verbosity -> Verbosity -> Verbosity
$cmax :: Verbosity -> Verbosity -> Verbosity
>= :: Verbosity -> Verbosity -> Bool
$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
compare :: Verbosity -> Verbosity -> Ordering
$ccompare :: Verbosity -> Verbosity -> Ordering
Ord, Verbosity
forall a. a -> a -> Bounded a
maxBound :: Verbosity
$cmaxBound :: Verbosity
minBound :: Verbosity
$cminBound :: Verbosity
Bounded, Int -> Verbosity
Verbosity -> Int
Verbosity -> [Verbosity]
Verbosity -> Verbosity
Verbosity -> Verbosity -> [Verbosity]
Verbosity -> Verbosity -> Verbosity -> [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
enumFromThenTo :: Verbosity -> Verbosity -> Verbosity -> [Verbosity]
$cenumFromThenTo :: Verbosity -> Verbosity -> Verbosity -> [Verbosity]
enumFromTo :: Verbosity -> Verbosity -> [Verbosity]
$cenumFromTo :: Verbosity -> Verbosity -> [Verbosity]
enumFromThen :: Verbosity -> Verbosity -> [Verbosity]
$cenumFromThen :: Verbosity -> Verbosity -> [Verbosity]
enumFrom :: Verbosity -> [Verbosity]
$cenumFrom :: Verbosity -> [Verbosity]
fromEnum :: Verbosity -> Int
$cfromEnum :: Verbosity -> Int
toEnum :: Int -> Verbosity
$ctoEnum :: Int -> Verbosity
pred :: Verbosity -> Verbosity
$cpred :: Verbosity -> Verbosity
succ :: Verbosity -> Verbosity
$csucc :: Verbosity -> Verbosity
Enum, ReadPrec [Verbosity]
ReadPrec Verbosity
Int -> ReadS Verbosity
ReadS [Verbosity]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Verbosity]
$creadListPrec :: ReadPrec [Verbosity]
readPrec :: ReadPrec Verbosity
$creadPrec :: ReadPrec Verbosity
readList :: ReadS [Verbosity]
$creadList :: ReadS [Verbosity]
readsPrec :: Int -> ReadS Verbosity
$creadsPrec :: Int -> ReadS Verbosity
Read, Int -> Verbosity -> ShowS
[Verbosity] -> ShowS
Verbosity -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Verbosity] -> ShowS
$cshowList :: [Verbosity] -> ShowS
show :: Verbosity -> String
$cshow :: Verbosity -> String
showsPrec :: Int -> Verbosity -> ShowS
$cshowsPrec :: Int -> Verbosity -> ShowS
Show, Typeable, Typeable Verbosity
Verbosity -> DataType
Verbosity -> Constr
(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)
gmapMo :: 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
gmapMp :: forall (m :: * -> *).
MonadPlus 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
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Verbosity -> m Verbosity
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Verbosity -> m Verbosity
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Verbosity -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Verbosity -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> Verbosity -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Verbosity -> [u]
gmapQr :: 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
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Verbosity -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Verbosity -> r
gmapT :: (forall b. Data b => b -> b) -> Verbosity -> Verbosity
$cgmapT :: (forall b. Data b => b -> b) -> Verbosity -> Verbosity
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Verbosity)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Verbosity)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Verbosity)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Verbosity)
dataTypeOf :: Verbosity -> DataType
$cdataTypeOf :: Verbosity -> DataType
toConstr :: Verbosity -> Constr
$ctoConstr :: Verbosity -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Verbosity
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Verbosity
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Verbosity -> c Verbosity
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Verbosity -> c Verbosity
Data,
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
$cto :: forall x. Rep Verbosity x -> Verbosity
$cfrom :: forall x. Verbosity -> Rep Verbosity x
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
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Config -> Config -> Bool
$c/= :: Config -> Config -> Bool
== :: Config -> Config -> Bool
$c== :: Config -> Config -> Bool
Eq, ReadPrec [Config]
ReadPrec Config
Int -> ReadS Config
ReadS [Config]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Config]
$creadListPrec :: ReadPrec [Config]
readPrec :: ReadPrec Config
$creadPrec :: ReadPrec Config
readList :: ReadS [Config]
$creadList :: ReadS [Config]
readsPrec :: Int -> ReadS Config
$creadsPrec :: Int -> ReadS Config
Read, Int -> Config -> ShowS
[Config] -> ShowS
Config -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Config] -> ShowS
$cshowList :: [Config] -> ShowS
show :: Config -> String
$cshow :: Config -> String
showsPrec :: Int -> Config -> ShowS
$cshowsPrec :: Int -> Config -> ShowS
Show, Typeable, Typeable Config
Config -> DataType
Config -> Constr
(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)
gmapMo :: 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
gmapMp :: forall (m :: * -> *).
MonadPlus 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
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Config -> m Config
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Config -> m Config
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Config -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Config -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> Config -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Config -> [u]
gmapQr :: 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
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Config -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Config -> r
gmapT :: (forall b. Data b => b -> b) -> Config -> Config
$cgmapT :: (forall b. Data b => b -> b) -> Config -> Config
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Config)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Config)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Config)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Config)
dataTypeOf :: Config -> DataType
$cdataTypeOf :: Config -> DataType
toConstr :: Config -> Constr
$ctoConstr :: Config -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Config
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Config
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Config -> c Config
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Config -> c Config
Data, 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
$cto :: forall x. Rep Config x -> Config
$cfrom :: forall x. Config -> Rep Config x
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
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Outliers -> Outliers -> Bool
$c/= :: Outliers -> Outliers -> Bool
== :: Outliers -> Outliers -> Bool
$c== :: Outliers -> Outliers -> Bool
Eq, ReadPrec [Outliers]
ReadPrec Outliers
Int -> ReadS Outliers
ReadS [Outliers]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Outliers]
$creadListPrec :: ReadPrec [Outliers]
readPrec :: ReadPrec Outliers
$creadPrec :: ReadPrec Outliers
readList :: ReadS [Outliers]
$creadList :: ReadS [Outliers]
readsPrec :: Int -> ReadS Outliers
$creadsPrec :: Int -> ReadS Outliers
Read, Int -> Outliers -> ShowS
[Outliers] -> ShowS
Outliers -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Outliers] -> ShowS
$cshowList :: [Outliers] -> ShowS
show :: Outliers -> String
$cshow :: Outliers -> String
showsPrec :: Int -> Outliers -> ShowS
$cshowsPrec :: Int -> Outliers -> ShowS
Show, Typeable, Typeable Outliers
Outliers -> DataType
Outliers -> Constr
(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)
gmapMo :: 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
gmapMp :: forall (m :: * -> *).
MonadPlus 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
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Outliers -> m Outliers
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Outliers -> m Outliers
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Outliers -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Outliers -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> Outliers -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Outliers -> [u]
gmapQr :: 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
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Outliers -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Outliers -> r
gmapT :: (forall b. Data b => b -> b) -> Outliers -> Outliers
$cgmapT :: (forall b. Data b => b -> b) -> Outliers -> Outliers
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Outliers)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Outliers)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Outliers)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Outliers)
dataTypeOf :: Outliers -> DataType
$cdataTypeOf :: Outliers -> DataType
toConstr :: Outliers -> Constr
$ctoConstr :: Outliers -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Outliers
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Outliers
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Outliers -> c Outliers
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Outliers -> c Outliers
Data, 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
$cto :: forall x. Rep Outliers x -> Outliers
$cfrom :: forall x. Outliers -> Rep Outliers x
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) = forall t. Binary t => t -> Put
put Int64
v forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall t. Binary t => t -> Put
put Int64
w forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall t. Binary t => t -> Put
put Int64
x forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall t. Binary t => t -> Put
put Int64
y forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall t. Binary t => t -> Put
put Int64
z
get :: Get Outliers
get = Int64 -> Int64 -> Int64 -> Int64 -> Int64 -> Outliers
Outliers forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall t. Binary t => Get t
get forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall t. Binary t => Get t
get forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall t. Binary t => Get t
get forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall t. Binary t => Get t
get forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall t. Binary t => Get t
get
instance NFData Outliers
data OutlierEffect = Unaffected
| Slight
| Moderate
| Severe
deriving (OutlierEffect -> OutlierEffect -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OutlierEffect -> OutlierEffect -> Bool
$c/= :: OutlierEffect -> OutlierEffect -> Bool
== :: OutlierEffect -> OutlierEffect -> Bool
$c== :: OutlierEffect -> OutlierEffect -> Bool
Eq, Eq 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
min :: OutlierEffect -> OutlierEffect -> OutlierEffect
$cmin :: OutlierEffect -> OutlierEffect -> OutlierEffect
max :: OutlierEffect -> OutlierEffect -> OutlierEffect
$cmax :: OutlierEffect -> OutlierEffect -> OutlierEffect
>= :: OutlierEffect -> OutlierEffect -> Bool
$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
compare :: OutlierEffect -> OutlierEffect -> Ordering
$ccompare :: OutlierEffect -> OutlierEffect -> Ordering
Ord, ReadPrec [OutlierEffect]
ReadPrec OutlierEffect
Int -> ReadS OutlierEffect
ReadS [OutlierEffect]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [OutlierEffect]
$creadListPrec :: ReadPrec [OutlierEffect]
readPrec :: ReadPrec OutlierEffect
$creadPrec :: ReadPrec OutlierEffect
readList :: ReadS [OutlierEffect]
$creadList :: ReadS [OutlierEffect]
readsPrec :: Int -> ReadS OutlierEffect
$creadsPrec :: Int -> ReadS OutlierEffect
Read, Int -> OutlierEffect -> ShowS
[OutlierEffect] -> ShowS
OutlierEffect -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [OutlierEffect] -> ShowS
$cshowList :: [OutlierEffect] -> ShowS
show :: OutlierEffect -> String
$cshow :: OutlierEffect -> String
showsPrec :: Int -> OutlierEffect -> ShowS
$cshowsPrec :: Int -> OutlierEffect -> ShowS
Show, Typeable, Typeable OutlierEffect
OutlierEffect -> DataType
OutlierEffect -> Constr
(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)
gmapMo :: 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
gmapMp :: forall (m :: * -> *).
MonadPlus 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
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> OutlierEffect -> m OutlierEffect
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> OutlierEffect -> m OutlierEffect
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> OutlierEffect -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> OutlierEffect -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> OutlierEffect -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> OutlierEffect -> [u]
gmapQr :: 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
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> OutlierEffect -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> OutlierEffect -> r
gmapT :: (forall b. Data b => b -> b) -> OutlierEffect -> OutlierEffect
$cgmapT :: (forall b. Data b => b -> b) -> OutlierEffect -> OutlierEffect
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c OutlierEffect)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c OutlierEffect)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c OutlierEffect)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c OutlierEffect)
dataTypeOf :: OutlierEffect -> DataType
$cdataTypeOf :: OutlierEffect -> DataType
toConstr :: OutlierEffect -> Constr
$ctoConstr :: OutlierEffect -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OutlierEffect
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OutlierEffect
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OutlierEffect -> c OutlierEffect
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OutlierEffect -> c OutlierEffect
Data, 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
$cto :: forall x. Rep OutlierEffect x -> OutlierEffect
$cfrom :: forall x. OutlierEffect -> Rep OutlierEffect x
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 -> forall (m :: * -> *) a. Monad m => a -> m a
return OutlierEffect
Unaffected
Word8
1 -> forall (m :: * -> *) a. Monad m => a -> m a
return OutlierEffect
Slight
Word8
2 -> forall (m :: * -> *) a. Monad m => a -> m a
return OutlierEffect
Moderate
Word8
3 -> forall (m :: * -> *) a. Monad m => a -> m a
return OutlierEffect
Severe
Word8
_ -> forall (m :: * -> *) a. MonadFail m => String -> m a
fail forall a b. (a -> b) -> a -> b
$ String
"get for OutlierEffect: unexpected " forall a. [a] -> [a] -> [a]
++ 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
sforall a. Num a => a -> a -> a
+Int64
t) (Int64
aforall a. Num a => a -> a -> a
+Int64
w) (Int64
bforall a. Num a => a -> a -> a
+Int64
x) (Int64
cforall a. Num a => a -> a -> a
+Int64
y) (Int64
dforall 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
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OutlierVariance -> OutlierVariance -> Bool
$c/= :: OutlierVariance -> OutlierVariance -> Bool
== :: OutlierVariance -> OutlierVariance -> Bool
$c== :: OutlierVariance -> OutlierVariance -> Bool
Eq, ReadPrec [OutlierVariance]
ReadPrec OutlierVariance
Int -> ReadS OutlierVariance
ReadS [OutlierVariance]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [OutlierVariance]
$creadListPrec :: ReadPrec [OutlierVariance]
readPrec :: ReadPrec OutlierVariance
$creadPrec :: ReadPrec OutlierVariance
readList :: ReadS [OutlierVariance]
$creadList :: ReadS [OutlierVariance]
readsPrec :: Int -> ReadS OutlierVariance
$creadsPrec :: Int -> ReadS OutlierVariance
Read, Int -> OutlierVariance -> ShowS
[OutlierVariance] -> ShowS
OutlierVariance -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [OutlierVariance] -> ShowS
$cshowList :: [OutlierVariance] -> ShowS
show :: OutlierVariance -> String
$cshow :: OutlierVariance -> String
showsPrec :: Int -> OutlierVariance -> ShowS
$cshowsPrec :: Int -> OutlierVariance -> ShowS
Show, Typeable, Typeable OutlierVariance
OutlierVariance -> DataType
OutlierVariance -> Constr
(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)
gmapMo :: 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
gmapMp :: forall (m :: * -> *).
MonadPlus 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
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> OutlierVariance -> m OutlierVariance
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> OutlierVariance -> m OutlierVariance
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> OutlierVariance -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> OutlierVariance -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> OutlierVariance -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> OutlierVariance -> [u]
gmapQr :: 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
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> OutlierVariance -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> OutlierVariance -> r
gmapT :: (forall b. Data b => b -> b) -> OutlierVariance -> OutlierVariance
$cgmapT :: (forall b. Data b => b -> b) -> OutlierVariance -> OutlierVariance
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c OutlierVariance)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c OutlierVariance)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c OutlierVariance)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c OutlierVariance)
dataTypeOf :: OutlierVariance -> DataType
$cdataTypeOf :: OutlierVariance -> DataType
toConstr :: OutlierVariance -> Constr
$ctoConstr :: OutlierVariance -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OutlierVariance
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OutlierVariance
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OutlierVariance -> c OutlierVariance
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OutlierVariance -> c OutlierVariance
Data, 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
$cto :: forall x. Rep OutlierVariance x -> OutlierVariance
$cfrom :: forall x. OutlierVariance -> Rep OutlierVariance x
Generic)
instance FromJSON OutlierVariance
instance ToJSON OutlierVariance
instance Binary OutlierVariance where
put :: OutlierVariance -> Put
put (OutlierVariance OutlierEffect
x String
y Double
z) = forall t. Binary t => t -> Put
put OutlierEffect
x forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall t. Binary t => t -> Put
put String
y forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall t. Binary t => t -> Put
put Double
z
get :: Get OutlierVariance
get = OutlierEffect -> String -> Double -> OutlierVariance
OutlierVariance forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall t. Binary t => Get t
get forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall t. Binary t => Get t
get forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall t. Binary t => Get t
get
instance NFData OutlierVariance where
rnf :: OutlierVariance -> ()
rnf OutlierVariance{Double
String
OutlierEffect
ovFraction :: Double
ovDesc :: String
ovEffect :: OutlierEffect
ovFraction :: OutlierVariance -> Double
ovDesc :: OutlierVariance -> String
ovEffect :: OutlierVariance -> OutlierEffect
..} = forall a. NFData a => a -> ()
rnf OutlierEffect
ovEffect seq :: forall a b. a -> b -> b
`seq` forall a. NFData a => a -> ()
rnf String
ovDesc seq :: forall a b. a -> b -> b
`seq` 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
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Regression -> Regression -> Bool
$c/= :: Regression -> Regression -> Bool
== :: Regression -> Regression -> Bool
$c== :: Regression -> Regression -> Bool
Eq, ReadPrec [Regression]
ReadPrec Regression
Int -> ReadS Regression
ReadS [Regression]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Regression]
$creadListPrec :: ReadPrec [Regression]
readPrec :: ReadPrec Regression
$creadPrec :: ReadPrec Regression
readList :: ReadS [Regression]
$creadList :: ReadS [Regression]
readsPrec :: Int -> ReadS Regression
$creadsPrec :: Int -> ReadS Regression
Read, Int -> Regression -> ShowS
[Regression] -> ShowS
Regression -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Regression] -> ShowS
$cshowList :: [Regression] -> ShowS
show :: Regression -> String
$cshow :: Regression -> String
showsPrec :: Int -> Regression -> ShowS
$cshowsPrec :: Int -> Regression -> ShowS
Show, Typeable, 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
$cto :: forall x. Rep Regression x -> Regression
$cfrom :: forall x. Regression -> Rep Regression x
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
regRSquare :: Estimate ConfInt Double
regCoeffs :: Map String (Estimate ConfInt Double)
regResponder :: String
regRSquare :: Regression -> Estimate ConfInt Double
regCoeffs :: Regression -> Map String (Estimate ConfInt Double)
regResponder :: Regression -> String
..} =
forall t. Binary t => t -> Put
put String
regResponder forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall t. Binary t => t -> Put
put Map String (Estimate ConfInt Double)
regCoeffs forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> 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 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall t. Binary t => Get t
get forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall t. Binary t => Get t
get forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall t. Binary t => Get t
get
instance NFData Regression where
rnf :: Regression -> ()
rnf Regression{String
Map String (Estimate ConfInt Double)
Estimate ConfInt Double
regRSquare :: Estimate ConfInt Double
regCoeffs :: Map String (Estimate ConfInt Double)
regResponder :: String
regRSquare :: Regression -> Estimate ConfInt Double
regCoeffs :: Regression -> Map String (Estimate ConfInt Double)
regResponder :: Regression -> String
..} =
forall a. NFData a => a -> ()
rnf String
regResponder seq :: forall a b. a -> b -> b
`seq` forall a. NFData a => a -> ()
rnf Map String (Estimate ConfInt Double)
regCoeffs seq :: forall a b. a -> b -> b
`seq` 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
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SampleAnalysis -> SampleAnalysis -> Bool
$c/= :: SampleAnalysis -> SampleAnalysis -> Bool
== :: SampleAnalysis -> SampleAnalysis -> Bool
$c== :: SampleAnalysis -> SampleAnalysis -> Bool
Eq, ReadPrec [SampleAnalysis]
ReadPrec SampleAnalysis
Int -> ReadS SampleAnalysis
ReadS [SampleAnalysis]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SampleAnalysis]
$creadListPrec :: ReadPrec [SampleAnalysis]
readPrec :: ReadPrec SampleAnalysis
$creadPrec :: ReadPrec SampleAnalysis
readList :: ReadS [SampleAnalysis]
$creadList :: ReadS [SampleAnalysis]
readsPrec :: Int -> ReadS SampleAnalysis
$creadsPrec :: Int -> ReadS SampleAnalysis
Read, Int -> SampleAnalysis -> ShowS
[SampleAnalysis] -> ShowS
SampleAnalysis -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SampleAnalysis] -> ShowS
$cshowList :: [SampleAnalysis] -> ShowS
show :: SampleAnalysis -> String
$cshow :: SampleAnalysis -> String
showsPrec :: Int -> SampleAnalysis -> ShowS
$cshowsPrec :: Int -> SampleAnalysis -> ShowS
Show, Typeable, 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
$cto :: forall x. Rep SampleAnalysis x -> SampleAnalysis
$cfrom :: forall x. SampleAnalysis -> Rep SampleAnalysis x
Generic)
instance FromJSON SampleAnalysis
instance ToJSON SampleAnalysis
instance Binary SampleAnalysis where
put :: SampleAnalysis -> Put
put SampleAnalysis{[Regression]
Estimate ConfInt Double
OutlierVariance
anOutlierVar :: OutlierVariance
anStdDev :: Estimate ConfInt Double
anMean :: Estimate ConfInt Double
anRegress :: [Regression]
anOutlierVar :: SampleAnalysis -> OutlierVariance
anStdDev :: SampleAnalysis -> Estimate ConfInt Double
anMean :: SampleAnalysis -> Estimate ConfInt Double
anRegress :: SampleAnalysis -> [Regression]
..} = do
forall t. Binary t => t -> Put
put [Regression]
anRegress; forall t. Binary t => t -> Put
put Estimate ConfInt Double
anMean; forall t. Binary t => t -> Put
put Estimate ConfInt Double
anStdDev; forall t. Binary t => t -> Put
put OutlierVariance
anOutlierVar
get :: Get SampleAnalysis
get = [Regression]
-> Estimate ConfInt Double
-> Estimate ConfInt Double
-> OutlierVariance
-> SampleAnalysis
SampleAnalysis forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall t. Binary t => Get t
get forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall t. Binary t => Get t
get forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall t. Binary t => Get t
get forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall t. Binary t => Get t
get
instance NFData SampleAnalysis where
rnf :: SampleAnalysis -> ()
rnf SampleAnalysis{[Regression]
Estimate ConfInt Double
OutlierVariance
anOutlierVar :: OutlierVariance
anStdDev :: Estimate ConfInt Double
anMean :: Estimate ConfInt Double
anRegress :: [Regression]
anOutlierVar :: SampleAnalysis -> OutlierVariance
anStdDev :: SampleAnalysis -> Estimate ConfInt Double
anMean :: SampleAnalysis -> Estimate ConfInt Double
anRegress :: SampleAnalysis -> [Regression]
..} =
forall a. NFData a => a -> ()
rnf [Regression]
anRegress seq :: forall a b. a -> b -> b
`seq` forall a. NFData a => a -> ()
rnf Estimate ConfInt Double
anMean seq :: forall a b. a -> b -> b
`seq`
forall a. NFData a => a -> ()
rnf Estimate ConfInt Double
anStdDev seq :: forall a b. a -> b -> b
`seq` 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
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: KDE -> KDE -> Bool
$c/= :: KDE -> KDE -> Bool
== :: KDE -> KDE -> Bool
$c== :: KDE -> KDE -> Bool
Eq, ReadPrec [KDE]
ReadPrec KDE
Int -> ReadS KDE
ReadS [KDE]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [KDE]
$creadListPrec :: ReadPrec [KDE]
readPrec :: ReadPrec KDE
$creadPrec :: ReadPrec KDE
readList :: ReadS [KDE]
$creadList :: ReadS [KDE]
readsPrec :: Int -> ReadS KDE
$creadsPrec :: Int -> ReadS KDE
Read, Int -> KDE -> ShowS
[KDE] -> ShowS
KDE -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [KDE] -> ShowS
$cshowList :: [KDE] -> ShowS
show :: KDE -> String
$cshow :: KDE -> String
showsPrec :: Int -> KDE -> ShowS
$cshowsPrec :: Int -> KDE -> ShowS
Show, Typeable, Typeable KDE
KDE -> DataType
KDE -> Constr
(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)
gmapMo :: 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
gmapMp :: forall (m :: * -> *).
MonadPlus 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
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> KDE -> m KDE
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> KDE -> m KDE
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> KDE -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> KDE -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> KDE -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> KDE -> [u]
gmapQr :: 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
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> KDE -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> KDE -> r
gmapT :: (forall b. Data b => b -> b) -> KDE -> KDE
$cgmapT :: (forall b. Data b => b -> b) -> KDE -> KDE
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c KDE)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c KDE)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c KDE)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c KDE)
dataTypeOf :: KDE -> DataType
$cdataTypeOf :: KDE -> DataType
toConstr :: KDE -> Constr
$ctoConstr :: KDE -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c KDE
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c KDE
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> KDE -> c KDE
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> KDE -> c KDE
Data, 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
$cto :: forall x. Rep KDE x -> KDE
$cfrom :: forall x. KDE -> Rep KDE x
Generic)
instance FromJSON KDE
instance ToJSON KDE
instance Binary KDE where
put :: KDE -> Put
put KDE{String
Vector Double
kdePDF :: Vector Double
kdeValues :: Vector Double
kdeType :: String
kdePDF :: KDE -> Vector Double
kdeValues :: KDE -> Vector Double
kdeType :: KDE -> String
..} = forall t. Binary t => t -> Put
put String
kdeType forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall t. Binary t => t -> Put
put Vector Double
kdeValues forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall t. Binary t => t -> Put
put Vector Double
kdePDF
get :: Get KDE
get = String -> Vector Double -> Vector Double -> KDE
KDE forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall t. Binary t => Get t
get forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall t. Binary t => Get t
get forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall t. Binary t => Get t
get
instance NFData KDE where
rnf :: KDE -> ()
rnf KDE{String
Vector Double
kdePDF :: Vector Double
kdeValues :: Vector Double
kdeType :: String
kdePDF :: KDE -> Vector Double
kdeValues :: KDE -> Vector Double
kdeType :: KDE -> String
..} = forall a. NFData a => a -> ()
rnf String
kdeType seq :: forall a b. a -> b -> b
`seq` forall a. NFData a => a -> ()
rnf Vector Double
kdeValues seq :: forall a b. a -> b -> b
`seq` 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
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Report -> Report -> Bool
$c/= :: Report -> Report -> Bool
== :: Report -> Report -> Bool
$c== :: Report -> Report -> Bool
Eq, ReadPrec [Report]
ReadPrec Report
Int -> ReadS Report
ReadS [Report]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Report]
$creadListPrec :: ReadPrec [Report]
readPrec :: ReadPrec Report
$creadPrec :: ReadPrec Report
readList :: ReadS [Report]
$creadList :: ReadS [Report]
readsPrec :: Int -> ReadS Report
$creadsPrec :: Int -> ReadS Report
Read, Int -> Report -> ShowS
[Report] -> ShowS
Report -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Report] -> ShowS
$cshowList :: [Report] -> ShowS
show :: Report -> String
$cshow :: Report -> String
showsPrec :: Int -> Report -> ShowS
$cshowsPrec :: Int -> Report -> ShowS
Show, Typeable, 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
$cto :: forall x. Rep Report x -> Report
$cfrom :: forall x. Report -> Rep Report x
Generic)
instance FromJSON Report
instance ToJSON Report
instance Binary Report where
put :: Report -> Put
put Report{Int
String
[String]
[KDE]
Vector Measured
SampleAnalysis
Outliers
reportKDEs :: [KDE]
reportOutliers :: Outliers
reportAnalysis :: SampleAnalysis
reportMeasured :: Vector Measured
reportKeys :: [String]
reportName :: String
reportNumber :: Int
reportKDEs :: Report -> [KDE]
reportOutliers :: Report -> Outliers
reportAnalysis :: Report -> SampleAnalysis
reportMeasured :: Report -> Vector Measured
reportKeys :: Report -> [String]
reportName :: Report -> String
reportNumber :: Report -> Int
..} =
forall t. Binary t => t -> Put
put Int
reportNumber forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall t. Binary t => t -> Put
put String
reportName forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall t. Binary t => t -> Put
put [String]
reportKeys forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
forall t. Binary t => t -> Put
put Vector Measured
reportMeasured forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall t. Binary t => t -> Put
put SampleAnalysis
reportAnalysis forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall t. Binary t => t -> Put
put Outliers
reportOutliers forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
forall t. Binary t => t -> Put
put [KDE]
reportKDEs
get :: Get Report
get = Int
-> String
-> [String]
-> Vector Measured
-> SampleAnalysis
-> Outliers
-> [KDE]
-> Report
Report forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall t. Binary t => Get t
get forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall t. Binary t => Get t
get forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall t. Binary t => Get t
get forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall t. Binary t => Get t
get forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall t. Binary t => Get t
get forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall t. Binary t => Get t
get forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall t. Binary t => Get t
get
instance NFData Report where
rnf :: Report -> ()
rnf Report{Int
String
[String]
[KDE]
Vector Measured
SampleAnalysis
Outliers
reportKDEs :: [KDE]
reportOutliers :: Outliers
reportAnalysis :: SampleAnalysis
reportMeasured :: Vector Measured
reportKeys :: [String]
reportName :: String
reportNumber :: Int
reportKDEs :: Report -> [KDE]
reportOutliers :: Report -> Outliers
reportAnalysis :: Report -> SampleAnalysis
reportMeasured :: Report -> Vector Measured
reportKeys :: Report -> [String]
reportName :: Report -> String
reportNumber :: Report -> Int
..} =
forall a. NFData a => a -> ()
rnf Int
reportNumber seq :: forall a b. a -> b -> b
`seq` forall a. NFData a => a -> ()
rnf String
reportName seq :: forall a b. a -> b -> b
`seq` forall a. NFData a => a -> ()
rnf [String]
reportKeys seq :: forall a b. a -> b -> b
`seq`
forall a. NFData a => a -> ()
rnf Vector Measured
reportMeasured seq :: forall a b. a -> b -> b
`seq` forall a. NFData a => a -> ()
rnf SampleAnalysis
reportAnalysis seq :: forall a b. a -> b -> b
`seq` forall a. NFData a => a -> ()
rnf Outliers
reportOutliers seq :: forall a b. a -> b -> b
`seq`
forall a. NFData a => a -> ()
rnf [KDE]
reportKDEs
data DataRecord = Measurement Int String (V.Vector Measured)
| Analysed Report
deriving (DataRecord -> DataRecord -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DataRecord -> DataRecord -> Bool
$c/= :: DataRecord -> DataRecord -> Bool
== :: DataRecord -> DataRecord -> Bool
$c== :: DataRecord -> DataRecord -> Bool
Eq, ReadPrec [DataRecord]
ReadPrec DataRecord
Int -> ReadS DataRecord
ReadS [DataRecord]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DataRecord]
$creadListPrec :: ReadPrec [DataRecord]
readPrec :: ReadPrec DataRecord
$creadPrec :: ReadPrec DataRecord
readList :: ReadS [DataRecord]
$creadList :: ReadS [DataRecord]
readsPrec :: Int -> ReadS DataRecord
$creadsPrec :: Int -> ReadS DataRecord
Read, Int -> DataRecord -> ShowS
[DataRecord] -> ShowS
DataRecord -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DataRecord] -> ShowS
$cshowList :: [DataRecord] -> ShowS
show :: DataRecord -> String
$cshow :: DataRecord -> String
showsPrec :: Int -> DataRecord -> ShowS
$cshowsPrec :: Int -> DataRecord -> ShowS
Show, Typeable, 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
$cto :: forall x. Rep DataRecord x -> DataRecord
$cfrom :: forall x. DataRecord -> Rep DataRecord x
Generic)
instance Binary DataRecord where
put :: DataRecord -> Put
put (Measurement Int
i String
n Vector Measured
v) = Word8 -> Put
putWord8 Word8
0 forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall t. Binary t => t -> Put
put Int
i forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall t. Binary t => t -> Put
put String
n forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall t. Binary t => t -> Put
put Vector Measured
v
put (Analysed Report
r) = Word8 -> Put
putWord8 Word8
1 forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> 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 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall t. Binary t => Get t
get forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall t. Binary t => Get t
get forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall t. Binary t => Get t
get
Word8
1 -> Report -> DataRecord
Analysed forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall t. Binary t => Get t
get
Word8
_ -> forall a. HasCallStack => String -> a
error (String
"bad tag " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Word8
w)
instance NFData DataRecord where
rnf :: DataRecord -> ()
rnf (Measurement Int
i String
n Vector Measured
v) = forall a. NFData a => a -> ()
rnf Int
i seq :: forall a b. a -> b -> b
`seq` forall a. NFData a => a -> ()
rnf String
n seq :: forall a b. a -> b -> b
`seq` forall a. NFData a => a -> ()
rnf Vector Measured
v
rnf (Analysed Report
r) = forall a. NFData a => a -> ()
rnf Report
r
instance FromJSON DataRecord
instance ToJSON DataRecord