{-# OPTIONS_GHC -fno-warn-deprecations #-}
module Test.Tasty.Sugar.Analysis
(
checkRoots
)
where
import Control.Parallel.Strategies
import Data.Bifunctor ( bimap )
import Data.Function ( on )
import qualified Data.List as L
import Data.Maybe ( catMaybes )
import Data.Ord ( comparing )
import qualified System.FilePath.GlobPattern as FPGP
import Test.Tasty.Sugar.ExpectCheck
import Test.Tasty.Sugar.Iterations
import Test.Tasty.Sugar.ParamCheck ( pmatchCmp )
import Test.Tasty.Sugar.Types
import Prelude hiding ( exp )
checkRoots :: CUBE -> [CandidateFile]
-> (Int, [([Sweets], [SweetExplanation])], IterStat)
checkRoots :: CUBE
-> [CandidateFile]
-> (Int, [([Sweets], [SweetExplanation])], IterStat)
checkRoots CUBE
pat [CandidateFile]
allFiles =
let isRootMatch :: CandidateFile -> Bool
isRootMatch CandidateFile
n = CandidateFile -> FilePath
candidateFile CandidateFile
n FilePath -> FilePath -> Bool
FPGP.~~ (CUBE -> FilePath
rootName CUBE
pat)
roots :: [CandidateFile]
roots = forall a. (a -> Bool) -> [a] -> [a]
L.filter CandidateFile -> Bool
isRootMatch [CandidateFile]
allFiles
allSweets :: [(([Sweets], [SweetExplanation]), IterStat)]
allSweets = (CUBE
-> [CandidateFile]
-> CandidateFile
-> (([Sweets], [SweetExplanation]), IterStat)
checkRoot CUBE
pat [CandidateFile]
allFiles) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [CandidateFile]
roots
checked :: [([Sweets], [SweetExplanation])]
checked = forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. Foldable t => t a -> Bool
null forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> a
fst) (forall a b. (a, b) -> a
fst forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(([Sweets], [SweetExplanation]), IterStat)]
allSweets)
allStats :: IterStat
allStats = forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr IterStat -> IterStat -> IterStat
joinStats IterStat
emptyStats (forall a b. (a, b) -> b
snd forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(([Sweets], [SweetExplanation]), IterStat)]
allSweets)
in (forall (t :: * -> *) a. Foldable t => t a -> Int
length [([Sweets], [SweetExplanation])]
checked, [([Sweets], [SweetExplanation])]
checked, IterStat
allStats)
checkRoot :: CUBE
-> [CandidateFile]
-> CandidateFile
-> (([Sweets], [SweetExplanation]), IterStat)
checkRoot :: CUBE
-> [CandidateFile]
-> CandidateFile
-> (([Sweets], [SweetExplanation]), IterStat)
checkRoot CUBE
pat [CandidateFile]
allFiles CandidateFile
rootF =
let params :: [ParameterPattern]
params = forall a. Ord a => [a] -> [a]
L.sort forall a b. (a -> b) -> a -> b
$ CUBE -> [ParameterPattern]
validParams CUBE
pat
combineExpRes :: (a, a) -> p [a] [a] -> p [a] [a]
combineExpRes (a
swts, a
expl) = forall (p :: * -> * -> *) a b c d.
Bifunctor p =>
(a -> b) -> (c -> d) -> p a c -> p b d
bimap (a
swts forall a. a -> [a] -> [a]
:) (a
expl forall a. a -> [a] -> [a]
:)
roots :: [([NamedParamMatch], CandidateFile)]
roots = [( CandidateFile -> [NamedParamMatch]
candidatePMatch CandidateFile
rootF
, CandidateFile
rootF { candidateFile :: FilePath
candidateFile =
let i :: Int
i = forall a. Enum a => a -> Int
fromEnum forall a b. (a -> b) -> a -> b
$ CandidateFile -> Natural
candidateMatchIdx CandidateFile
rootF
l :: Int
l = forall (t :: * -> *) a. Foldable t => t a -> Int
length forall a b. (a -> b) -> a -> b
$ CandidateFile -> FilePath
candidateFile CandidateFile
rootF
e :: Bool
e = Int
l forall a. Ord a => a -> a -> Bool
> Int
0 Bool -> Bool -> Bool
&& forall a. [a] -> a
last (CandidateFile -> FilePath
candidateFile CandidateFile
rootF) forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` (CUBE -> FilePath
separators CUBE
pat)
t :: Int
t = if Int
i forall a. Eq a => a -> a -> Bool
== Int
l Bool -> Bool -> Bool
&& Bool -> Bool
not Bool
e then Int
i else Int
i forall a. Num a => a -> a -> a
- Int
1
in forall a. Int -> [a] -> [a]
take Int
t (CandidateFile -> FilePath
candidateFile CandidateFile
rootF) }
)
, (CandidateFile -> [NamedParamMatch]
candidatePMatch CandidateFile
rootF, CandidateFile
rootF)
]
expAndStats :: [(Maybe (Sweets, SweetExplanation), IterStat)]
expAndStats = forall b a. Strategy b -> (a -> b) -> [a] -> [b]
parMap forall a. Strategy a
rpar (CUBE
-> [ParameterPattern]
-> CandidateFile
-> [CandidateFile]
-> ([NamedParamMatch], CandidateFile)
-> (Maybe (Sweets, SweetExplanation), IterStat)
findExpectation CUBE
pat [ParameterPattern]
params CandidateFile
rootF [CandidateFile]
allFiles) [([NamedParamMatch], CandidateFile)]
roots
sumStats :: IterStat
sumStats = forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr IterStat -> IterStat -> IterStat
joinStats IterStat
emptyStats (forall a b. (a, b) -> b
snd forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(Maybe (Sweets, SweetExplanation), IterStat)]
expAndStats)
exps :: ([Sweets], [SweetExplanation])
exps = forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr forall {p :: * -> * -> *} {a} {a}.
Bifunctor p =>
(a, a) -> p [a] [a] -> p [a] [a]
combineExpRes (forall a. Monoid a => a
mempty, forall a. Monoid a => a
mempty) forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *).
Foldable t =>
t (Sweets, SweetExplanation) -> [(Sweets, SweetExplanation)]
mergeSweets
forall a b. (a -> b) -> a -> b
$ forall a. [Maybe a] -> [a]
catMaybes (forall a b. (a, b) -> a
fst forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(Maybe (Sweets, SweetExplanation), IterStat)]
expAndStats)
in (([Sweets], [SweetExplanation])
exps, IterStat
sumStats)
mergeSweets :: Foldable t
=> t (Sweets, SweetExplanation) -> [(Sweets, SweetExplanation)]
mergeSweets :: forall (t :: * -> *).
Foldable t =>
t (Sweets, SweetExplanation) -> [(Sweets, SweetExplanation)]
mergeSweets t (Sweets, SweetExplanation)
swl =
let combineIfRootsMatch :: (Sweets, SweetExplanation)
-> [(Sweets, SweetExplanation)] -> [(Sweets, SweetExplanation)]
combineIfRootsMatch (Sweets, SweetExplanation)
s [(Sweets, SweetExplanation)]
sl =
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry (forall a b c. (a -> b -> c) -> b -> a -> c
flip (:))
( forall {t :: * -> *}.
Foldable t =>
(Sweets, SweetExplanation)
-> t (Sweets, SweetExplanation) -> (Sweets, SweetExplanation)
combineSweets (Sweets, SweetExplanation)
s forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. (a -> Bool) -> [a] -> ([a], [a])
L.partition (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall {b}. (Sweets, b) -> (Sweets, b) -> Bool
isRootMatch (Sweets, SweetExplanation)
s) [(Sweets, SweetExplanation)]
sl)
isRootMatch :: (Sweets, b) -> (Sweets, b) -> Bool
isRootMatch = forall a. Eq a => a -> a -> Bool
(==) forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` (Sweets -> FilePath
rootMatchName forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> a
fst)
combineSweets :: (Sweets, SweetExplanation)
-> t (Sweets, SweetExplanation) -> (Sweets, SweetExplanation)
combineSweets (Sweets, SweetExplanation)
s t (Sweets, SweetExplanation)
slm =
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (Sweets, SweetExplanation)
-> (Sweets, SweetExplanation) -> (Sweets, SweetExplanation)
chooseOrCombineExpectations (Sweets, SweetExplanation)
s t (Sweets, SweetExplanation)
slm
chooseOrCombineExpectations :: (Sweets, SweetExplanation)
-> (Sweets, SweetExplanation) -> (Sweets, SweetExplanation)
chooseOrCombineExpectations (Sweets
s,SweetExplanation
e) (Sweets
sm,SweetExplanation
sme) =
case forall a b. Ord a => (b -> a) -> b -> b -> Ordering
comparing Sweets -> FilePath
rootBaseName Sweets
s Sweets
sm of
Ordering
GT -> (Sweets
s,SweetExplanation
e)
Ordering
LT -> (Sweets
sm, SweetExplanation
sme)
Ordering
EQ -> forall {b}.
(Sweets, SweetExplanation)
-> (Sweets, b) -> (Sweets, SweetExplanation)
bestExpectations (Sweets
s,SweetExplanation
e) (Sweets
sm,SweetExplanation
sme)
bestExpectations :: (Sweets, SweetExplanation)
-> (Sweets, b) -> (Sweets, SweetExplanation)
bestExpectations (Sweets
s,SweetExplanation
e) (Sweets
sm,b
_sme) =
let swts :: Sweets
swts = Sweets
s { expected :: [Expectation]
expected =
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr Expectation -> [Expectation] -> [Expectation]
mergeExp (Sweets -> [Expectation]
expected Sweets
s) (Sweets -> [Expectation]
expected Sweets
sm)
}
mergeExp :: Expectation -> [Expectation] -> [Expectation]
mergeExp Expectation
oneExp [Expectation]
expcts =
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall a. Int -> [a] -> [a]
take Int
1)
forall a b. (a -> b) -> a -> b
$ forall a. (a -> a -> Bool) -> [a] -> [[a]]
L.groupBy (forall a. Eq a => a -> a -> Bool
(==) forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on`
(forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ParamMatch -> Maybe FilePath
getParamVal) forall b c a. (b -> c) -> (a -> b) -> a -> c
. Expectation -> [NamedParamMatch]
expParamsMatch))
forall a b. (a -> b) -> a -> b
$ forall a. (a -> a -> Ordering) -> [a] -> [a]
L.sortBy ([NamedParamMatch] -> [NamedParamMatch] -> Ordering
pmatchCmp forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` Expectation -> [NamedParamMatch]
expParamsMatch)
forall a b. (a -> b) -> a -> b
$ Expectation
oneExp forall a. a -> [a] -> [a]
: [Expectation]
expcts
in ( Sweets
swts, SweetExplanation
e { results :: Sweets
results = Sweets
swts } )
in forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (Sweets, SweetExplanation)
-> [(Sweets, SweetExplanation)] -> [(Sweets, SweetExplanation)]
combineIfRootsMatch [] t (Sweets, SweetExplanation)
swl