{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedRecordDot #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeApplications #-}
{-# OPTIONS_GHC -Wno-partial-fields #-}
module Language.EO.Phi.Pipeline.Config where
import Control.Monad.IO.Class (MonadIO)
import Data.Aeson (ToJSON)
import Data.Aeson.Types (FromJSON)
import Data.Functor ((<&>))
import Data.List (intercalate)
import Data.Yaml (decodeFileThrow)
import GHC.Generics (Generic)
import Language.EO.Phi.Metrics.Data
import Language.EO.Phi.TH (deriveJSON)
import PyF (fmt)
import Text.Printf (printf)
data TestSetPhi = TestSetPhi
{ TestSetPhi -> String
initial :: FilePath
, TestSetPhi -> String
normalized :: FilePath
, TestSetPhi -> Maybe String
bindingsPathInitial :: Maybe String
, TestSetPhi -> Maybe String
bindingsPathNormalized :: Maybe String
}
deriving stock (Int -> TestSetPhi -> ShowS
[TestSetPhi] -> ShowS
TestSetPhi -> String
(Int -> TestSetPhi -> ShowS)
-> (TestSetPhi -> String)
-> ([TestSetPhi] -> ShowS)
-> Show TestSetPhi
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TestSetPhi -> ShowS
showsPrec :: Int -> TestSetPhi -> ShowS
$cshow :: TestSetPhi -> String
show :: TestSetPhi -> String
$cshowList :: [TestSetPhi] -> ShowS
showList :: [TestSetPhi] -> ShowS
Show, (forall x. TestSetPhi -> Rep TestSetPhi x)
-> (forall x. Rep TestSetPhi x -> TestSetPhi) -> Generic TestSetPhi
forall x. Rep TestSetPhi x -> TestSetPhi
forall x. TestSetPhi -> Rep TestSetPhi x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. TestSetPhi -> Rep TestSetPhi x
from :: forall x. TestSetPhi -> Rep TestSetPhi x
$cto :: forall x. Rep TestSetPhi x -> TestSetPhi
to :: forall x. Rep TestSetPhi x -> TestSetPhi
Generic)
$(deriveJSON ''TestSetPhi)
data MetricsChangeCategory a
= MetricsChange'Good {forall a. MetricsChangeCategory a -> a
change :: a}
| MetricsChange'Bad {change :: a}
| MetricsChange'NA
deriving stock (Int -> MetricsChangeCategory a -> ShowS
[MetricsChangeCategory a] -> ShowS
MetricsChangeCategory a -> String
(Int -> MetricsChangeCategory a -> ShowS)
-> (MetricsChangeCategory a -> String)
-> ([MetricsChangeCategory a] -> ShowS)
-> Show (MetricsChangeCategory a)
forall a. Show a => Int -> MetricsChangeCategory a -> ShowS
forall a. Show a => [MetricsChangeCategory a] -> ShowS
forall a. Show a => MetricsChangeCategory a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Show a => Int -> MetricsChangeCategory a -> ShowS
showsPrec :: Int -> MetricsChangeCategory a -> ShowS
$cshow :: forall a. Show a => MetricsChangeCategory a -> String
show :: MetricsChangeCategory a -> String
$cshowList :: forall a. Show a => [MetricsChangeCategory a] -> ShowS
showList :: [MetricsChangeCategory a] -> ShowS
Show, (forall x.
MetricsChangeCategory a -> Rep (MetricsChangeCategory a) x)
-> (forall x.
Rep (MetricsChangeCategory a) x -> MetricsChangeCategory a)
-> Generic (MetricsChangeCategory a)
forall x.
Rep (MetricsChangeCategory a) x -> MetricsChangeCategory a
forall x.
MetricsChangeCategory a -> Rep (MetricsChangeCategory a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x.
Rep (MetricsChangeCategory a) x -> MetricsChangeCategory a
forall a x.
MetricsChangeCategory a -> Rep (MetricsChangeCategory a) x
$cfrom :: forall a x.
MetricsChangeCategory a -> Rep (MetricsChangeCategory a) x
from :: forall x.
MetricsChangeCategory a -> Rep (MetricsChangeCategory a) x
$cto :: forall a x.
Rep (MetricsChangeCategory a) x -> MetricsChangeCategory a
to :: forall x.
Rep (MetricsChangeCategory a) x -> MetricsChangeCategory a
Generic, MetricsChangeCategory a -> MetricsChangeCategory a -> Bool
(MetricsChangeCategory a -> MetricsChangeCategory a -> Bool)
-> (MetricsChangeCategory a -> MetricsChangeCategory a -> Bool)
-> Eq (MetricsChangeCategory a)
forall a.
Eq a =>
MetricsChangeCategory a -> MetricsChangeCategory a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall a.
Eq a =>
MetricsChangeCategory a -> MetricsChangeCategory a -> Bool
== :: MetricsChangeCategory a -> MetricsChangeCategory a -> Bool
$c/= :: forall a.
Eq a =>
MetricsChangeCategory a -> MetricsChangeCategory a -> Bool
/= :: MetricsChangeCategory a -> MetricsChangeCategory a -> Bool
Eq)
$(deriveJSON ''MetricsChangeCategory)
type MetricsChange = Metrics Percent
newtype Percent = Percent {Percent -> Double
percent :: Double}
deriving newtype
(Value -> Parser [Percent]
Value -> Parser Percent
(Value -> Parser Percent)
-> (Value -> Parser [Percent]) -> FromJSON Percent
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
$cparseJSON :: Value -> Parser Percent
parseJSON :: Value -> Parser Percent
$cparseJSONList :: Value -> Parser [Percent]
parseJSONList :: Value -> Parser [Percent]
FromJSON, [Percent] -> Value
[Percent] -> Encoding
Percent -> Value
Percent -> Encoding
(Percent -> Value)
-> (Percent -> Encoding)
-> ([Percent] -> Value)
-> ([Percent] -> Encoding)
-> ToJSON Percent
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
$ctoJSON :: Percent -> Value
toJSON :: Percent -> Value
$ctoEncoding :: Percent -> Encoding
toEncoding :: Percent -> Encoding
$ctoJSONList :: [Percent] -> Value
toJSONList :: [Percent] -> Value
$ctoEncodingList :: [Percent] -> Encoding
toEncodingList :: [Percent] -> Encoding
ToJSON, Integer -> Percent
Percent -> Percent
Percent -> Percent -> Percent
(Percent -> Percent -> Percent)
-> (Percent -> Percent -> Percent)
-> (Percent -> Percent -> Percent)
-> (Percent -> Percent)
-> (Percent -> Percent)
-> (Percent -> Percent)
-> (Integer -> Percent)
-> Num Percent
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
$c+ :: Percent -> Percent -> Percent
+ :: Percent -> Percent -> Percent
$c- :: Percent -> Percent -> Percent
- :: Percent -> Percent -> Percent
$c* :: Percent -> Percent -> Percent
* :: Percent -> Percent -> Percent
$cnegate :: Percent -> Percent
negate :: Percent -> Percent
$cabs :: Percent -> Percent
abs :: Percent -> Percent
$csignum :: Percent -> Percent
signum :: Percent -> Percent
$cfromInteger :: Integer -> Percent
fromInteger :: Integer -> Percent
Num, Num Percent
Num Percent =>
(Percent -> Percent -> Percent)
-> (Percent -> Percent)
-> (Rational -> Percent)
-> Fractional Percent
Rational -> Percent
Percent -> Percent
Percent -> Percent -> Percent
forall a.
Num a =>
(a -> a -> a) -> (a -> a) -> (Rational -> a) -> Fractional a
$c/ :: Percent -> Percent -> Percent
/ :: Percent -> Percent -> Percent
$crecip :: Percent -> Percent
recip :: Percent -> Percent
$cfromRational :: Rational -> Percent
fromRational :: Rational -> Percent
Fractional, Fractional Percent
Percent
Fractional Percent =>
Percent
-> (Percent -> Percent)
-> (Percent -> Percent)
-> (Percent -> Percent)
-> (Percent -> Percent -> Percent)
-> (Percent -> Percent -> Percent)
-> (Percent -> Percent)
-> (Percent -> Percent)
-> (Percent -> Percent)
-> (Percent -> Percent)
-> (Percent -> Percent)
-> (Percent -> Percent)
-> (Percent -> Percent)
-> (Percent -> Percent)
-> (Percent -> Percent)
-> (Percent -> Percent)
-> (Percent -> Percent)
-> (Percent -> Percent)
-> (Percent -> Percent)
-> (Percent -> Percent)
-> (Percent -> Percent)
-> (Percent -> Percent)
-> Floating Percent
Percent -> Percent
Percent -> Percent -> Percent
forall a.
Fractional a =>
a
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> Floating a
$cpi :: Percent
pi :: Percent
$cexp :: Percent -> Percent
exp :: Percent -> Percent
$clog :: Percent -> Percent
log :: Percent -> Percent
$csqrt :: Percent -> Percent
sqrt :: Percent -> Percent
$c** :: Percent -> Percent -> Percent
** :: Percent -> Percent -> Percent
$clogBase :: Percent -> Percent -> Percent
logBase :: Percent -> Percent -> Percent
$csin :: Percent -> Percent
sin :: Percent -> Percent
$ccos :: Percent -> Percent
cos :: Percent -> Percent
$ctan :: Percent -> Percent
tan :: Percent -> Percent
$casin :: Percent -> Percent
asin :: Percent -> Percent
$cacos :: Percent -> Percent
acos :: Percent -> Percent
$catan :: Percent -> Percent
atan :: Percent -> Percent
$csinh :: Percent -> Percent
sinh :: Percent -> Percent
$ccosh :: Percent -> Percent
cosh :: Percent -> Percent
$ctanh :: Percent -> Percent
tanh :: Percent -> Percent
$casinh :: Percent -> Percent
asinh :: Percent -> Percent
$cacosh :: Percent -> Percent
acosh :: Percent -> Percent
$catanh :: Percent -> Percent
atanh :: Percent -> Percent
$clog1p :: Percent -> Percent
log1p :: Percent -> Percent
$cexpm1 :: Percent -> Percent
expm1 :: Percent -> Percent
$clog1pexp :: Percent -> Percent
log1pexp :: Percent -> Percent
$clog1mexp :: Percent -> Percent
log1mexp :: Percent -> Percent
Floating, Percent -> Percent -> Bool
(Percent -> Percent -> Bool)
-> (Percent -> Percent -> Bool) -> Eq Percent
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Percent -> Percent -> Bool
== :: Percent -> Percent -> Bool
$c/= :: Percent -> Percent -> Bool
/= :: Percent -> Percent -> Bool
Eq, Eq Percent
Eq Percent =>
(Percent -> Percent -> Ordering)
-> (Percent -> Percent -> Bool)
-> (Percent -> Percent -> Bool)
-> (Percent -> Percent -> Bool)
-> (Percent -> Percent -> Bool)
-> (Percent -> Percent -> Percent)
-> (Percent -> Percent -> Percent)
-> Ord Percent
Percent -> Percent -> Bool
Percent -> Percent -> Ordering
Percent -> Percent -> Percent
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 :: Percent -> Percent -> Ordering
compare :: Percent -> Percent -> Ordering
$c< :: Percent -> Percent -> Bool
< :: Percent -> Percent -> Bool
$c<= :: Percent -> Percent -> Bool
<= :: Percent -> Percent -> Bool
$c> :: Percent -> Percent -> Bool
> :: Percent -> Percent -> Bool
$c>= :: Percent -> Percent -> Bool
>= :: Percent -> Percent -> Bool
$cmax :: Percent -> Percent -> Percent
max :: Percent -> Percent -> Percent
$cmin :: Percent -> Percent -> Percent
min :: Percent -> Percent -> Percent
Ord, Num Percent
Ord Percent
(Num Percent, Ord Percent) => (Percent -> Rational) -> Real Percent
Percent -> Rational
forall a. (Num a, Ord a) => (a -> Rational) -> Real a
$ctoRational :: Percent -> Rational
toRational :: Percent -> Rational
Real, Fractional Percent
Real Percent
(Real Percent, Fractional Percent) =>
(forall b. Integral b => Percent -> (b, Percent))
-> (forall b. Integral b => Percent -> b)
-> (forall b. Integral b => Percent -> b)
-> (forall b. Integral b => Percent -> b)
-> (forall b. Integral b => Percent -> b)
-> RealFrac Percent
forall b. Integral b => Percent -> b
forall b. Integral b => Percent -> (b, Percent)
forall a.
(Real a, Fractional a) =>
(forall b. Integral b => a -> (b, a))
-> (forall b. Integral b => a -> b)
-> (forall b. Integral b => a -> b)
-> (forall b. Integral b => a -> b)
-> (forall b. Integral b => a -> b)
-> RealFrac a
$cproperFraction :: forall b. Integral b => Percent -> (b, Percent)
properFraction :: forall b. Integral b => Percent -> (b, Percent)
$ctruncate :: forall b. Integral b => Percent -> b
truncate :: forall b. Integral b => Percent -> b
$cround :: forall b. Integral b => Percent -> b
round :: forall b. Integral b => Percent -> b
$cceiling :: forall b. Integral b => Percent -> b
ceiling :: forall b. Integral b => Percent -> b
$cfloor :: forall b. Integral b => Percent -> b
floor :: forall b. Integral b => Percent -> b
RealFrac, Floating Percent
RealFrac Percent
(RealFrac Percent, Floating Percent) =>
(Percent -> Integer)
-> (Percent -> Int)
-> (Percent -> (Int, Int))
-> (Percent -> (Integer, Int))
-> (Integer -> Int -> Percent)
-> (Percent -> Int)
-> (Percent -> Percent)
-> (Int -> Percent -> Percent)
-> (Percent -> Bool)
-> (Percent -> Bool)
-> (Percent -> Bool)
-> (Percent -> Bool)
-> (Percent -> Bool)
-> (Percent -> Percent -> Percent)
-> RealFloat Percent
Int -> Percent -> Percent
Integer -> Int -> Percent
Percent -> Bool
Percent -> Int
Percent -> Integer
Percent -> (Int, Int)
Percent -> (Integer, Int)
Percent -> Percent
Percent -> Percent -> Percent
forall a.
(RealFrac a, Floating a) =>
(a -> Integer)
-> (a -> Int)
-> (a -> (Int, Int))
-> (a -> (Integer, Int))
-> (Integer -> Int -> a)
-> (a -> Int)
-> (a -> a)
-> (Int -> a -> a)
-> (a -> Bool)
-> (a -> Bool)
-> (a -> Bool)
-> (a -> Bool)
-> (a -> Bool)
-> (a -> a -> a)
-> RealFloat a
$cfloatRadix :: Percent -> Integer
floatRadix :: Percent -> Integer
$cfloatDigits :: Percent -> Int
floatDigits :: Percent -> Int
$cfloatRange :: Percent -> (Int, Int)
floatRange :: Percent -> (Int, Int)
$cdecodeFloat :: Percent -> (Integer, Int)
decodeFloat :: Percent -> (Integer, Int)
$cencodeFloat :: Integer -> Int -> Percent
encodeFloat :: Integer -> Int -> Percent
$cexponent :: Percent -> Int
exponent :: Percent -> Int
$csignificand :: Percent -> Percent
significand :: Percent -> Percent
$cscaleFloat :: Int -> Percent -> Percent
scaleFloat :: Int -> Percent -> Percent
$cisNaN :: Percent -> Bool
isNaN :: Percent -> Bool
$cisInfinite :: Percent -> Bool
isInfinite :: Percent -> Bool
$cisDenormalized :: Percent -> Bool
isDenormalized :: Percent -> Bool
$cisNegativeZero :: Percent -> Bool
isNegativeZero :: Percent -> Bool
$cisIEEE :: Percent -> Bool
isIEEE :: Percent -> Bool
$catan2 :: Percent -> Percent -> Percent
atan2 :: Percent -> Percent -> Percent
RealFloat)
roundToStr :: Int -> Double -> String
roundToStr :: Int -> Double -> String
roundToStr = String -> Int -> Double -> String
forall r. PrintfType r => String -> r
printf String
"%0.*f%%"
instance Show Percent where
show :: Percent -> String
show :: Percent -> String
show Percent{Double
$sel:percent:Percent :: Percent -> Double
percent :: Double
..} = Int -> Double -> String
roundToStr Int
2 (Double
percent Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
100)
type MetricsChangeCategorized = Metrics (MetricsChangeCategory Percent)
data ReportInput = ReportInput
{ ReportInput -> Maybe String
js :: Maybe FilePath
, ReportInput -> Maybe String
css :: Maybe FilePath
}
deriving stock (Int -> ReportInput -> ShowS
[ReportInput] -> ShowS
ReportInput -> String
(Int -> ReportInput -> ShowS)
-> (ReportInput -> String)
-> ([ReportInput] -> ShowS)
-> Show ReportInput
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ReportInput -> ShowS
showsPrec :: Int -> ReportInput -> ShowS
$cshow :: ReportInput -> String
show :: ReportInput -> String
$cshowList :: [ReportInput] -> ShowS
showList :: [ReportInput] -> ShowS
Show, (forall x. ReportInput -> Rep ReportInput x)
-> (forall x. Rep ReportInput x -> ReportInput)
-> Generic ReportInput
forall x. Rep ReportInput x -> ReportInput
forall x. ReportInput -> Rep ReportInput x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ReportInput -> Rep ReportInput x
from :: forall x. ReportInput -> Rep ReportInput x
$cto :: forall x. Rep ReportInput x -> ReportInput
to :: forall x. Rep ReportInput x -> ReportInput
Generic)
$(deriveJSON ''ReportInput)
data ReportOutput = ReportOutput
{ ReportOutput -> Maybe String
html :: Maybe FilePath
, ReportOutput -> Maybe String
json :: Maybe FilePath
, ReportOutput -> Maybe String
markdown :: Maybe FilePath
}
deriving stock (Int -> ReportOutput -> ShowS
[ReportOutput] -> ShowS
ReportOutput -> String
(Int -> ReportOutput -> ShowS)
-> (ReportOutput -> String)
-> ([ReportOutput] -> ShowS)
-> Show ReportOutput
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ReportOutput -> ShowS
showsPrec :: Int -> ReportOutput -> ShowS
$cshow :: ReportOutput -> String
show :: ReportOutput -> String
$cshowList :: [ReportOutput] -> ShowS
showList :: [ReportOutput] -> ShowS
Show, (forall x. ReportOutput -> Rep ReportOutput x)
-> (forall x. Rep ReportOutput x -> ReportOutput)
-> Generic ReportOutput
forall x. Rep ReportOutput x -> ReportOutput
forall x. ReportOutput -> Rep ReportOutput x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ReportOutput -> Rep ReportOutput x
from :: forall x. ReportOutput -> Rep ReportOutput x
$cto :: forall x. Rep ReportOutput x -> ReportOutput
to :: forall x. Rep ReportOutput x -> ReportOutput
Generic)
$(deriveJSON ''ReportOutput)
data ReportConfig = ReportConfig
{ ReportConfig -> Maybe ReportInput
input :: Maybe ReportInput
, ReportConfig -> ReportOutput
output :: ReportOutput
, ReportConfig -> MetricsChange
expectedMetricsChange :: MetricsChange
, ReportConfig -> Percent
expectedImprovedProgramsPercentage :: Percent
}
deriving stock (Int -> ReportConfig -> ShowS
[ReportConfig] -> ShowS
ReportConfig -> String
(Int -> ReportConfig -> ShowS)
-> (ReportConfig -> String)
-> ([ReportConfig] -> ShowS)
-> Show ReportConfig
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ReportConfig -> ShowS
showsPrec :: Int -> ReportConfig -> ShowS
$cshow :: ReportConfig -> String
show :: ReportConfig -> String
$cshowList :: [ReportConfig] -> ShowS
showList :: [ReportConfig] -> ShowS
Show, (forall x. ReportConfig -> Rep ReportConfig x)
-> (forall x. Rep ReportConfig x -> ReportConfig)
-> Generic ReportConfig
forall x. Rep ReportConfig x -> ReportConfig
forall x. ReportConfig -> Rep ReportConfig x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ReportConfig -> Rep ReportConfig x
from :: forall x. ReportConfig -> Rep ReportConfig x
$cto :: forall x. Rep ReportConfig x -> ReportConfig
to :: forall x. Rep ReportConfig x -> ReportConfig
Generic)
$(deriveJSON ''ReportConfig)
data TestSetEO = TestSetEO
{ TestSetEO -> String
original :: FilePath
, TestSetEO -> String
yaml :: FilePath
, TestSetEO -> String
filtered :: FilePath
, TestSetEO -> Maybe [String]
include :: Maybe [String]
, TestSetEO -> Maybe [String]
exclude :: Maybe [String]
}
deriving stock (Int -> TestSetEO -> ShowS
[TestSetEO] -> ShowS
TestSetEO -> String
(Int -> TestSetEO -> ShowS)
-> (TestSetEO -> String)
-> ([TestSetEO] -> ShowS)
-> Show TestSetEO
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TestSetEO -> ShowS
showsPrec :: Int -> TestSetEO -> ShowS
$cshow :: TestSetEO -> String
show :: TestSetEO -> String
$cshowList :: [TestSetEO] -> ShowS
showList :: [TestSetEO] -> ShowS
Show, (forall x. TestSetEO -> Rep TestSetEO x)
-> (forall x. Rep TestSetEO x -> TestSetEO) -> Generic TestSetEO
forall x. Rep TestSetEO x -> TestSetEO
forall x. TestSetEO -> Rep TestSetEO x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. TestSetEO -> Rep TestSetEO x
from :: forall x. TestSetEO -> Rep TestSetEO x
$cto :: forall x. Rep TestSetEO x -> TestSetEO
to :: forall x. Rep TestSetEO x -> TestSetEO
Generic)
$(deriveJSON ''TestSetEO)
data AtomsSet = AtomsSet
{ AtomsSet -> Maybe [String]
enable :: Maybe [String]
, AtomsSet -> Maybe [String]
disable :: Maybe [String]
}
deriving stock (Int -> AtomsSet -> ShowS
[AtomsSet] -> ShowS
AtomsSet -> String
(Int -> AtomsSet -> ShowS)
-> (AtomsSet -> String) -> ([AtomsSet] -> ShowS) -> Show AtomsSet
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AtomsSet -> ShowS
showsPrec :: Int -> AtomsSet -> ShowS
$cshow :: AtomsSet -> String
show :: AtomsSet -> String
$cshowList :: [AtomsSet] -> ShowS
showList :: [AtomsSet] -> ShowS
Show, (forall x. AtomsSet -> Rep AtomsSet x)
-> (forall x. Rep AtomsSet x -> AtomsSet) -> Generic AtomsSet
forall x. Rep AtomsSet x -> AtomsSet
forall x. AtomsSet -> Rep AtomsSet x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. AtomsSet -> Rep AtomsSet x
from :: forall x. AtomsSet -> Rep AtomsSet x
$cto :: forall x. Rep AtomsSet x -> AtomsSet
to :: forall x. Rep AtomsSet x -> AtomsSet
Generic)
$(deriveJSON ''AtomsSet)
data PathPrefixEO = PathPrefixEO
{ PathPrefixEO -> String
original :: FilePath
, PathPrefixEO -> String
yaml :: FilePath
, PathPrefixEO -> String
filtered :: FilePath
}
deriving stock (Int -> PathPrefixEO -> ShowS
[PathPrefixEO] -> ShowS
PathPrefixEO -> String
(Int -> PathPrefixEO -> ShowS)
-> (PathPrefixEO -> String)
-> ([PathPrefixEO] -> ShowS)
-> Show PathPrefixEO
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PathPrefixEO -> ShowS
showsPrec :: Int -> PathPrefixEO -> ShowS
$cshow :: PathPrefixEO -> String
show :: PathPrefixEO -> String
$cshowList :: [PathPrefixEO] -> ShowS
showList :: [PathPrefixEO] -> ShowS
Show, (forall x. PathPrefixEO -> Rep PathPrefixEO x)
-> (forall x. Rep PathPrefixEO x -> PathPrefixEO)
-> Generic PathPrefixEO
forall x. Rep PathPrefixEO x -> PathPrefixEO
forall x. PathPrefixEO -> Rep PathPrefixEO x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. PathPrefixEO -> Rep PathPrefixEO x
from :: forall x. PathPrefixEO -> Rep PathPrefixEO x
$cto :: forall x. Rep PathPrefixEO x -> PathPrefixEO
to :: forall x. Rep PathPrefixEO x -> PathPrefixEO
Generic)
$(deriveJSON ''PathPrefixEO)
data PathPrefixPhi = PathPrefixPhi
{ PathPrefixPhi -> String
initial :: FilePath
, PathPrefixPhi -> String
normalized :: FilePath
}
deriving stock (Int -> PathPrefixPhi -> ShowS
[PathPrefixPhi] -> ShowS
PathPrefixPhi -> String
(Int -> PathPrefixPhi -> ShowS)
-> (PathPrefixPhi -> String)
-> ([PathPrefixPhi] -> ShowS)
-> Show PathPrefixPhi
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PathPrefixPhi -> ShowS
showsPrec :: Int -> PathPrefixPhi -> ShowS
$cshow :: PathPrefixPhi -> String
show :: PathPrefixPhi -> String
$cshowList :: [PathPrefixPhi] -> ShowS
showList :: [PathPrefixPhi] -> ShowS
Show, (forall x. PathPrefixPhi -> Rep PathPrefixPhi x)
-> (forall x. Rep PathPrefixPhi x -> PathPrefixPhi)
-> Generic PathPrefixPhi
forall x. Rep PathPrefixPhi x -> PathPrefixPhi
forall x. PathPrefixPhi -> Rep PathPrefixPhi x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. PathPrefixPhi -> Rep PathPrefixPhi x
from :: forall x. PathPrefixPhi -> Rep PathPrefixPhi x
$cto :: forall x. Rep PathPrefixPhi x -> PathPrefixPhi
to :: forall x. Rep PathPrefixPhi x -> PathPrefixPhi
Generic)
$(deriveJSON ''PathPrefixPhi)
data PathPrefix = PathPrefix
{ PathPrefix -> PathPrefixEO
eo :: PathPrefixEO
, PathPrefix -> PathPrefixPhi
phi :: PathPrefixPhi
}
deriving stock (Int -> PathPrefix -> ShowS
[PathPrefix] -> ShowS
PathPrefix -> String
(Int -> PathPrefix -> ShowS)
-> (PathPrefix -> String)
-> ([PathPrefix] -> ShowS)
-> Show PathPrefix
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PathPrefix -> ShowS
showsPrec :: Int -> PathPrefix -> ShowS
$cshow :: PathPrefix -> String
show :: PathPrefix -> String
$cshowList :: [PathPrefix] -> ShowS
showList :: [PathPrefix] -> ShowS
Show, (forall x. PathPrefix -> Rep PathPrefix x)
-> (forall x. Rep PathPrefix x -> PathPrefix) -> Generic PathPrefix
forall x. Rep PathPrefix x -> PathPrefix
forall x. PathPrefix -> Rep PathPrefix x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. PathPrefix -> Rep PathPrefix x
from :: forall x. PathPrefix -> Rep PathPrefix x
$cto :: forall x. Rep PathPrefix x -> PathPrefix
to :: forall x. Rep PathPrefix x -> PathPrefix
Generic)
$(deriveJSON ''PathPrefix)
data Common = Common
{ Common -> PathPrefix
pathPrefix :: PathPrefix
, Common -> Maybe String
bindingsPath :: Maybe String
}
deriving stock (Int -> Common -> ShowS
[Common] -> ShowS
Common -> String
(Int -> Common -> ShowS)
-> (Common -> String) -> ([Common] -> ShowS) -> Show Common
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Common -> ShowS
showsPrec :: Int -> Common -> ShowS
$cshow :: Common -> String
show :: Common -> String
$cshowList :: [Common] -> ShowS
showList :: [Common] -> ShowS
Show, (forall x. Common -> Rep Common x)
-> (forall x. Rep Common x -> Common) -> Generic Common
forall x. Rep Common x -> Common
forall x. Common -> Rep Common x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Common -> Rep Common x
from :: forall x. Common -> Rep Common x
$cto :: forall x. Rep Common x -> Common
to :: forall x. Rep Common x -> Common
Generic)
$(deriveJSON ''Common)
data Individual = Individual
{ Individual -> String
name :: String
, Individual -> Maybe Bool
enable :: Maybe Bool
, Individual -> Maybe [String]
include :: Maybe [String]
, Individual -> Maybe [String]
exclude :: Maybe [String]
, Individual -> Maybe AtomsSet
atoms :: Maybe AtomsSet
}
deriving stock (Int -> Individual -> ShowS
[Individual] -> ShowS
Individual -> String
(Int -> Individual -> ShowS)
-> (Individual -> String)
-> ([Individual] -> ShowS)
-> Show Individual
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Individual -> ShowS
showsPrec :: Int -> Individual -> ShowS
$cshow :: Individual -> String
show :: Individual -> String
$cshowList :: [Individual] -> ShowS
showList :: [Individual] -> ShowS
Show, (forall x. Individual -> Rep Individual x)
-> (forall x. Rep Individual x -> Individual) -> Generic Individual
forall x. Rep Individual x -> Individual
forall x. Individual -> Rep Individual x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Individual -> Rep Individual x
from :: forall x. Individual -> Rep Individual x
$cto :: forall x. Rep Individual x -> Individual
to :: forall x. Rep Individual x -> Individual
Generic)
$(deriveJSON ''Individual)
data TestSet
= TestSetExtended
{ TestSet -> TestSetEO
eo :: TestSetEO
, TestSet -> TestSetPhi
phi :: TestSetPhi
, TestSet -> Maybe AtomsSet
atoms :: Maybe AtomsSet
, TestSet -> Maybe Bool
enable :: Maybe Bool
}
| TestSetCompact
{ TestSet -> Common
common :: Common
, TestSet -> [Individual]
individual :: [Individual]
}
deriving stock (Int -> TestSet -> ShowS
[TestSet] -> ShowS
TestSet -> String
(Int -> TestSet -> ShowS)
-> (TestSet -> String) -> ([TestSet] -> ShowS) -> Show TestSet
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TestSet -> ShowS
showsPrec :: Int -> TestSet -> ShowS
$cshow :: TestSet -> String
show :: TestSet -> String
$cshowList :: [TestSet] -> ShowS
showList :: [TestSet] -> ShowS
Show, (forall x. TestSet -> Rep TestSet x)
-> (forall x. Rep TestSet x -> TestSet) -> Generic TestSet
forall x. Rep TestSet x -> TestSet
forall x. TestSet -> Rep TestSet x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. TestSet -> Rep TestSet x
from :: forall x. TestSet -> Rep TestSet x
$cto :: forall x. Rep TestSet x -> TestSet
to :: forall x. Rep TestSet x -> TestSet
Generic)
$(deriveJSON ''TestSet)
data PipelineConfig = PipelineConfig
{ PipelineConfig -> ReportConfig
report :: ReportConfig
, PipelineConfig -> [TestSet]
testSets :: [TestSet]
}
deriving stock (Int -> PipelineConfig -> ShowS
[PipelineConfig] -> ShowS
PipelineConfig -> String
(Int -> PipelineConfig -> ShowS)
-> (PipelineConfig -> String)
-> ([PipelineConfig] -> ShowS)
-> Show PipelineConfig
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PipelineConfig -> ShowS
showsPrec :: Int -> PipelineConfig -> ShowS
$cshow :: PipelineConfig -> String
show :: PipelineConfig -> String
$cshowList :: [PipelineConfig] -> ShowS
showList :: [PipelineConfig] -> ShowS
Show, (forall x. PipelineConfig -> Rep PipelineConfig x)
-> (forall x. Rep PipelineConfig x -> PipelineConfig)
-> Generic PipelineConfig
forall x. Rep PipelineConfig x -> PipelineConfig
forall x. PipelineConfig -> Rep PipelineConfig x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. PipelineConfig -> Rep PipelineConfig x
from :: forall x. PipelineConfig -> Rep PipelineConfig x
$cto :: forall x. Rep PipelineConfig x -> PipelineConfig
to :: forall x. Rep PipelineConfig x -> PipelineConfig
Generic)
$(deriveJSON ''PipelineConfig)
data ReportFormat
= ReportFormat'Html
|
ReportFormat'Markdown
deriving stock (ReportFormat -> ReportFormat -> Bool
(ReportFormat -> ReportFormat -> Bool)
-> (ReportFormat -> ReportFormat -> Bool) -> Eq ReportFormat
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ReportFormat -> ReportFormat -> Bool
== :: ReportFormat -> ReportFormat -> Bool
$c/= :: ReportFormat -> ReportFormat -> Bool
/= :: ReportFormat -> ReportFormat -> Bool
Eq)
split :: forall a. (a -> Bool) -> [a] -> [[a]]
split :: forall a. (a -> Bool) -> [a] -> [[a]]
split a -> Bool
cond [a]
xs = [a] -> [a] -> [[a]] -> [[a]]
go [a]
xs [] []
where
go :: [a] -> [a] -> [[a]] -> [[a]]
go [] [a]
_ [[a]]
res = [[a]]
res
go (a
y : [a]
ys) [a]
curSpan [[a]]
res
| a -> Bool
cond a
y = [a] -> [a] -> [[a]] -> [[a]]
go [a]
ys [] ([[a]]
res [[a]] -> [[a]] -> [[a]]
forall a. Semigroup a => a -> a -> a
<> [[a]
curSpan])
| Bool
otherwise = [a] -> [a] -> [[a]] -> [[a]]
go [a]
ys ([a]
curSpan [a] -> [a] -> [a]
forall a. Semigroup a => a -> a -> a
<> [a
y]) [[a]]
res
toExtended :: PipelineConfig -> PipelineConfig
toExtended :: PipelineConfig -> PipelineConfig
toExtended c :: PipelineConfig
c@(PipelineConfig{[TestSet]
$sel:testSets:PipelineConfig :: PipelineConfig -> [TestSet]
testSets :: [TestSet]
testSets}) = PipelineConfig
c{testSets = concatMap go testSets}
where
go :: TestSet -> [TestSet]
go = \case
e :: TestSet
e@TestSetExtended{} -> [TestSet
e]
TestSetCompact{[Individual]
Common
$sel:common:TestSetExtended :: TestSet -> Common
$sel:individual:TestSetExtended :: TestSet -> [Individual]
common :: Common
individual :: [Individual]
..} -> Common -> Individual -> TestSet
go1 Common
common (Individual -> TestSet) -> [Individual] -> [TestSet]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Individual]
individual
go1 :: Common -> Individual -> TestSet
go1 (Common{Maybe String
PathPrefix
$sel:pathPrefix:Common :: Common -> PathPrefix
$sel:bindingsPath:Common :: Common -> Maybe String
pathPrefix :: PathPrefix
bindingsPath :: Maybe String
..}) (Individual{String
Maybe Bool
Maybe [String]
Maybe AtomsSet
$sel:name:Individual :: Individual -> String
$sel:enable:Individual :: Individual -> Maybe Bool
$sel:include:Individual :: Individual -> Maybe [String]
$sel:exclude:Individual :: Individual -> Maybe [String]
$sel:atoms:Individual :: Individual -> Maybe AtomsSet
name :: String
enable :: Maybe Bool
include :: Maybe [String]
exclude :: Maybe [String]
atoms :: Maybe AtomsSet
..}) = TestSetExtended{Maybe Bool
Maybe AtomsSet
TestSetPhi
TestSetEO
$sel:eo:TestSetExtended :: TestSetEO
$sel:phi:TestSetExtended :: TestSetPhi
$sel:atoms:TestSetExtended :: Maybe AtomsSet
$sel:enable:TestSetExtended :: Maybe Bool
enable :: Maybe Bool
atoms :: Maybe AtomsSet
eo :: TestSetEO
phi :: TestSetPhi
..}
where
mkPath :: FilePath -> String -> String
mkPath :: String -> ShowS
mkPath String
prefix String
extension = [fmt|{prefix}/{name}.{extension}|]
eo :: TestSetEO
eo =
TestSetEO
{ $sel:original:TestSetEO :: String
original = String -> ShowS
mkPath PathPrefix
pathPrefix.eo.original String
"eo"
, $sel:yaml:TestSetEO :: String
yaml = String -> ShowS
mkPath PathPrefix
pathPrefix.eo.yaml String
"yaml"
, $sel:filtered:TestSetEO :: String
filtered = String -> ShowS
mkPath PathPrefix
pathPrefix.eo.filtered String
"eo"
, Maybe [String]
$sel:include:TestSetEO :: Maybe [String]
include :: Maybe [String]
include
, Maybe [String]
$sel:exclude:TestSetEO :: Maybe [String]
exclude :: Maybe [String]
exclude
}
phi :: TestSetPhi
phi =
TestSetPhi
{ $sel:initial:TestSetPhi :: String
initial = String -> ShowS
mkPath PathPrefix
pathPrefix.phi.initial String
"phi"
, $sel:normalized:TestSetPhi :: String
normalized = String -> ShowS
mkPath PathPrefix
pathPrefix.phi.normalized String
"phi"
, $sel:bindingsPathInitial:TestSetPhi :: Maybe String
bindingsPathInitial = Maybe String
bindingsPath Maybe String -> ShowS -> Maybe String
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> ShowS
mkBindingsPathSuffix
, $sel:bindingsPathNormalized:TestSetPhi :: Maybe String
bindingsPathNormalized = Maybe String
bindingsPath Maybe String -> ShowS -> Maybe String
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> ShowS
mkBindingsPathSuffix
}
where
name' :: [String]
name' = (Char -> Bool) -> String -> [String]
forall a. (a -> Bool) -> [a] -> [[a]]
split (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'/') String
name
mkBindingsPathSuffix :: ShowS
mkBindingsPathSuffix String
x = String
x String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
"." (if [String]
name' [String] -> [String] -> Bool
forall a. Eq a => a -> a -> Bool
/= [] then [String] -> [String]
forall a. HasCallStack => [a] -> [a]
init [String]
name' else [])
readPipelineConfig :: (MonadIO m) => FilePath -> m PipelineConfig
readPipelineConfig :: forall (m :: * -> *). MonadIO m => String -> m PipelineConfig
readPipelineConfig String
path = PipelineConfig -> PipelineConfig
toExtended (PipelineConfig -> PipelineConfig)
-> m PipelineConfig -> m PipelineConfig
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *) a. (MonadIO m, FromJSON a) => String -> m a
decodeFileThrow @_ @PipelineConfig String
path