{-# OPTIONS_GHC -fno-warn-deprecations #-}
module Test.Tasty.Sugar.Analysis
(
checkRoots
)
where
import Control.Monad.Logic
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.RootCheck
import Test.Tasty.Sugar.ParamCheck ( pmatchCmp )
import Test.Tasty.Sugar.Types
checkRoots :: CUBE -> [CandidateFile]
-> (Int, [([Sweets], [SweetExplanation])])
checkRoots :: CUBE -> [CandidateFile] -> (Int, [([Sweets], [SweetExplanation])])
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 = (CandidateFile -> Bool) -> [CandidateFile] -> [CandidateFile]
forall a. (a -> Bool) -> [a] -> [a]
filter CandidateFile -> Bool
isRootMatch [CandidateFile]
allFiles
checked :: [([Sweets], [SweetExplanation])]
checked = (([Sweets], [SweetExplanation]) -> Bool)
-> [([Sweets], [SweetExplanation])]
-> [([Sweets], [SweetExplanation])]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool)
-> (([Sweets], [SweetExplanation]) -> Bool)
-> ([Sweets], [SweetExplanation])
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Sweets] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null ([Sweets] -> Bool)
-> (([Sweets], [SweetExplanation]) -> [Sweets])
-> ([Sweets], [SweetExplanation])
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Sweets], [SweetExplanation]) -> [Sweets]
forall a b. (a, b) -> a
fst)
((CUBE
-> [CandidateFile]
-> CandidateFile
-> ([Sweets], [SweetExplanation])
checkRoot CUBE
pat [CandidateFile]
allFiles) (CandidateFile -> ([Sweets], [SweetExplanation]))
-> [CandidateFile] -> [([Sweets], [SweetExplanation])]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [CandidateFile]
roots)
in ([([Sweets], [SweetExplanation])] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [([Sweets], [SweetExplanation])]
checked, [([Sweets], [SweetExplanation])]
checked)
checkRoot :: CUBE
-> [CandidateFile]
-> CandidateFile
-> ([Sweets], [SweetExplanation])
checkRoot :: CUBE
-> [CandidateFile]
-> CandidateFile
-> ([Sweets], [SweetExplanation])
checkRoot CUBE
pat [CandidateFile]
allFiles CandidateFile
rootF =
let seps :: FilePath
seps = CUBE -> FilePath
separators CUBE
pat
params :: [ParameterPattern]
params = CUBE -> [ParameterPattern]
validParams CUBE
pat
combineExpRes :: (a, a) -> p [a] [a] -> p [a] [a]
combineExpRes (a
swts, a
expl) = ([a] -> [a]) -> ([a] -> [a]) -> p [a] [a] -> p [a] [a]
forall (p :: * -> * -> *) a b c d.
Bifunctor p =>
(a -> b) -> (c -> d) -> p a c -> p b d
bimap (a
swts a -> [a] -> [a]
forall a. a -> [a] -> [a]
:) (a
expl a -> [a] -> [a]
forall a. a -> [a] -> [a]
:)
mergeSweets :: 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 =
([(Sweets, SweetExplanation)]
-> (Sweets, SweetExplanation) -> [(Sweets, SweetExplanation)])
-> ([(Sweets, SweetExplanation)], (Sweets, SweetExplanation))
-> [(Sweets, SweetExplanation)]
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry (((Sweets, SweetExplanation)
-> [(Sweets, SweetExplanation)] -> [(Sweets, SweetExplanation)])
-> [(Sweets, SweetExplanation)]
-> (Sweets, SweetExplanation)
-> [(Sweets, SweetExplanation)]
forall a b c. (a -> b -> c) -> b -> a -> c
flip (:))
( (Sweets, SweetExplanation)
-> [(Sweets, SweetExplanation)] -> (Sweets, SweetExplanation)
forall (t :: * -> *).
Foldable t =>
(Sweets, SweetExplanation)
-> t (Sweets, SweetExplanation) -> (Sweets, SweetExplanation)
combineSweets (Sweets, SweetExplanation)
s ([(Sweets, SweetExplanation)] -> (Sweets, SweetExplanation))
-> ([(Sweets, SweetExplanation)], [(Sweets, SweetExplanation)])
-> ([(Sweets, SweetExplanation)], (Sweets, SweetExplanation))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ((Sweets, SweetExplanation) -> Bool)
-> [(Sweets, SweetExplanation)]
-> ([(Sweets, SweetExplanation)], [(Sweets, SweetExplanation)])
forall a. (a -> Bool) -> [a] -> ([a], [a])
L.partition (Bool -> Bool
not (Bool -> Bool)
-> ((Sweets, SweetExplanation) -> Bool)
-> (Sweets, SweetExplanation)
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Sweets, SweetExplanation) -> (Sweets, SweetExplanation) -> Bool
forall b. (Sweets, b) -> (Sweets, b) -> Bool
isRootMatch (Sweets, SweetExplanation)
s) [(Sweets, SweetExplanation)]
sl)
isRootMatch :: (Sweets, b) -> (Sweets, b) -> Bool
isRootMatch = FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
(==) (FilePath -> FilePath -> Bool)
-> ((Sweets, b) -> FilePath) -> (Sweets, b) -> (Sweets, b) -> Bool
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` (Sweets -> FilePath
rootMatchName (Sweets -> FilePath)
-> ((Sweets, b) -> Sweets) -> (Sweets, b) -> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Sweets, b) -> Sweets
forall a b. (a, b) -> a
fst)
combineSweets :: (Sweets, SweetExplanation)
-> t (Sweets, SweetExplanation) -> (Sweets, SweetExplanation)
combineSweets (Sweets, SweetExplanation)
s t (Sweets, SweetExplanation)
slm =
((Sweets, SweetExplanation)
-> (Sweets, SweetExplanation) -> (Sweets, SweetExplanation))
-> (Sweets, SweetExplanation)
-> t (Sweets, SweetExplanation)
-> (Sweets, SweetExplanation)
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 (Sweets -> FilePath) -> Sweets -> Sweets -> Ordering
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 -> (Sweets, SweetExplanation)
-> (Sweets, SweetExplanation) -> (Sweets, SweetExplanation)
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 =
(Expectation -> [Expectation] -> [Expectation])
-> [Expectation] -> [Expectation] -> [Expectation]
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]
exps =
[[Expectation]] -> [Expectation]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
([[Expectation]] -> [Expectation])
-> [[Expectation]] -> [Expectation]
forall a b. (a -> b) -> a -> b
$ ([Expectation] -> [Expectation])
-> [[Expectation]] -> [[Expectation]]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Int -> [Expectation] -> [Expectation]
forall a. Int -> [a] -> [a]
take Int
1)
([[Expectation]] -> [[Expectation]])
-> [[Expectation]] -> [[Expectation]]
forall a b. (a -> b) -> a -> b
$ (Expectation -> Expectation -> Bool)
-> [Expectation] -> [[Expectation]]
forall a. (a -> a -> Bool) -> [a] -> [[a]]
L.groupBy ([(FilePath, Maybe FilePath)]
-> [(FilePath, Maybe FilePath)] -> Bool
forall a. Eq a => a -> a -> Bool
(==) ([(FilePath, Maybe FilePath)]
-> [(FilePath, Maybe FilePath)] -> Bool)
-> (Expectation -> [(FilePath, Maybe FilePath)])
-> Expectation
-> Expectation
-> Bool
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on`
(((FilePath, ParamMatch) -> (FilePath, Maybe FilePath))
-> [(FilePath, ParamMatch)] -> [(FilePath, Maybe FilePath)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((ParamMatch -> Maybe FilePath)
-> (FilePath, ParamMatch) -> (FilePath, Maybe FilePath)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ParamMatch -> Maybe FilePath
getParamVal) ([(FilePath, ParamMatch)] -> [(FilePath, Maybe FilePath)])
-> (Expectation -> [(FilePath, ParamMatch)])
-> Expectation
-> [(FilePath, Maybe FilePath)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Expectation -> [(FilePath, ParamMatch)]
expParamsMatch))
([Expectation] -> [[Expectation]])
-> [Expectation] -> [[Expectation]]
forall a b. (a -> b) -> a -> b
$ (Expectation -> Expectation -> Ordering)
-> [Expectation] -> [Expectation]
forall a. (a -> a -> Ordering) -> [a] -> [a]
L.sortBy ([(FilePath, ParamMatch)] -> [(FilePath, ParamMatch)] -> Ordering
pmatchCmp ([(FilePath, ParamMatch)] -> [(FilePath, ParamMatch)] -> Ordering)
-> (Expectation -> [(FilePath, ParamMatch)])
-> Expectation
-> Expectation
-> Ordering
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` Expectation -> [(FilePath, ParamMatch)]
expParamsMatch)
([Expectation] -> [Expectation]) -> [Expectation] -> [Expectation]
forall a b. (a -> b) -> a -> b
$ Expectation
oneExp Expectation -> [Expectation] -> [Expectation]
forall a. a -> [a] -> [a]
: [Expectation]
exps
in ( Sweets
swts, SweetExplanation
e { results :: Sweets
results = Sweets
swts } )
in ((Sweets, SweetExplanation)
-> [(Sweets, SweetExplanation)] -> [(Sweets, SweetExplanation)])
-> [(Sweets, SweetExplanation)]
-> t (Sweets, SweetExplanation)
-> [(Sweets, SweetExplanation)]
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
in ((Sweets, SweetExplanation)
-> ([Sweets], [SweetExplanation])
-> ([Sweets], [SweetExplanation]))
-> ([Sweets], [SweetExplanation])
-> [(Sweets, SweetExplanation)]
-> ([Sweets], [SweetExplanation])
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (Sweets, SweetExplanation)
-> ([Sweets], [SweetExplanation]) -> ([Sweets], [SweetExplanation])
forall (p :: * -> * -> *) a a.
Bifunctor p =>
(a, a) -> p [a] [a] -> p [a] [a]
combineExpRes ([], []) ([(Sweets, SweetExplanation)] -> ([Sweets], [SweetExplanation]))
-> [(Sweets, SweetExplanation)] -> ([Sweets], [SweetExplanation])
forall a b. (a -> b) -> a -> b
$
[(Sweets, SweetExplanation)] -> [(Sweets, SweetExplanation)]
forall (t :: * -> *).
Foldable t =>
t (Sweets, SweetExplanation) -> [(Sweets, SweetExplanation)]
mergeSweets ([(Sweets, SweetExplanation)] -> [(Sweets, SweetExplanation)])
-> [(Sweets, SweetExplanation)] -> [(Sweets, SweetExplanation)]
forall a b. (a -> b) -> a -> b
$
[Maybe (Sweets, SweetExplanation)] -> [(Sweets, SweetExplanation)]
forall a. [Maybe a] -> [a]
catMaybes ([Maybe (Sweets, SweetExplanation)]
-> [(Sweets, SweetExplanation)])
-> [Maybe (Sweets, SweetExplanation)]
-> [(Sweets, SweetExplanation)]
forall a b. (a -> b) -> a -> b
$
(([(FilePath, ParamMatch)], CandidateFile, FilePath)
-> Maybe (Sweets, SweetExplanation))
-> [([(FilePath, ParamMatch)], CandidateFile, FilePath)]
-> [Maybe (Sweets, SweetExplanation)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (CUBE
-> CandidateFile
-> [CandidateFile]
-> ([(FilePath, ParamMatch)], CandidateFile, FilePath)
-> Maybe (Sweets, SweetExplanation)
findExpectation CUBE
pat CandidateFile
rootF [CandidateFile]
allFiles) ([([(FilePath, ParamMatch)], CandidateFile, FilePath)]
-> [Maybe (Sweets, SweetExplanation)])
-> [([(FilePath, ParamMatch)], CandidateFile, FilePath)]
-> [Maybe (Sweets, SweetExplanation)]
forall a b. (a -> b) -> a -> b
$
Logic ([(FilePath, ParamMatch)], CandidateFile, FilePath)
-> [([(FilePath, ParamMatch)], CandidateFile, FilePath)]
forall a. Logic a -> [a]
observeAll (Logic ([(FilePath, ParamMatch)], CandidateFile, FilePath)
-> [([(FilePath, ParamMatch)], CandidateFile, FilePath)])
-> Logic ([(FilePath, ParamMatch)], CandidateFile, FilePath)
-> [([(FilePath, ParamMatch)], CandidateFile, FilePath)]
forall a b. (a -> b) -> a -> b
$
CandidateFile
-> FilePath
-> [ParameterPattern]
-> FilePath
-> Logic ([(FilePath, ParamMatch)], CandidateFile, FilePath)
rootMatch CandidateFile
rootF FilePath
seps [ParameterPattern]
params (CUBE -> FilePath
rootName CUBE
pat)