{-# LANGUAGE LambdaCase #-}
{-# OPTIONS_GHC -fno-warn-deprecations #-}
module Test.Tasty.Sugar.ExpectCheck
(
findExpectation
, removeNonExplicitMatchingExpectations
)
where
import Control.Monad
import Control.Monad.Logic
import qualified Data.List as L
import Test.Tasty.Sugar.AssocCheck
import Test.Tasty.Sugar.ParamCheck
import Test.Tasty.Sugar.Types
findExpectation :: CUBE
-> CandidateFile
-> [CandidateFile]
-> ([NamedParamMatch], CandidateFile, String)
-> Maybe ( Sweets, SweetExplanation )
findExpectation :: CUBE
-> CandidateFile
-> [CandidateFile]
-> ([NamedParamMatch], CandidateFile, FilePath)
-> Maybe (Sweets, SweetExplanation)
findExpectation CUBE
pat CandidateFile
rootN [CandidateFile]
allNames ([NamedParamMatch]
rootPMatches, CandidateFile
matchPrefix, FilePath
_) =
let r :: Maybe Sweets
r = [Expectation] -> Maybe Sweets
mkSweet forall a b. (a -> b) -> a -> b
$
[Expectation] -> [Expectation]
trimExpectations forall a b. (a -> b) -> a -> b
$
forall a. Logic a -> [a]
observeAll forall a b. (a -> b) -> a -> b
$
do forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> Bool
not forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a. Foldable t => t a -> Bool
null [CandidateFile]
candidates)
CandidateFile
-> [NamedParamMatch]
-> FilePath
-> [ParameterPattern]
-> FilePath
-> [(FilePath, FilePath)]
-> [CandidateFile]
-> Logic Expectation
expectedSearch
CandidateFile
matchPrefix
[NamedParamMatch]
rootPMatches FilePath
seps [ParameterPattern]
params FilePath
expSuffix [(FilePath, FilePath)]
o
[CandidateFile]
candidates
o :: [(FilePath, FilePath)]
o = CUBE -> [(FilePath, FilePath)]
associatedNames CUBE
pat
seps :: FilePath
seps = CUBE -> FilePath
separators CUBE
pat
params :: [ParameterPattern]
params = CUBE -> [ParameterPattern]
validParams CUBE
pat
expSuffix :: FilePath
expSuffix = CUBE -> FilePath
expectedSuffix CUBE
pat
candidates :: [CandidateFile]
candidates = forall a. (a -> Bool) -> [a] -> [a]
filter CandidateFile -> Bool
possible [CandidateFile]
allNames
possible :: CandidateFile -> Bool
possible CandidateFile
f = forall (t :: * -> *). Foldable t => t Bool -> Bool
and [ CandidateFile -> FilePath
candidateFile CandidateFile
matchPrefix forall a. Eq a => [a] -> [a] -> Bool
`L.isPrefixOf` CandidateFile -> FilePath
candidateFile CandidateFile
f
, CandidateFile
rootN forall a. Eq a => a -> a -> Bool
/= CandidateFile
f
]
mkSweet :: [Expectation] -> Maybe Sweets
mkSweet [Expectation]
e = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ Sweets { rootMatchName :: FilePath
rootMatchName = CandidateFile -> FilePath
candidateFile CandidateFile
rootN
, rootBaseName :: FilePath
rootBaseName = CandidateFile -> FilePath
candidateFile CandidateFile
matchPrefix
, rootFile :: FilePath
rootFile = CandidateFile -> FilePath
candidateToPath CandidateFile
rootN
, cubeParams :: [ParameterPattern]
cubeParams = CUBE -> [ParameterPattern]
validParams CUBE
pat
, expected :: [Expectation]
expected = [Expectation]
e
}
trimExpectations :: [Expectation] -> [Expectation]
trimExpectations :: [Expectation] -> [Expectation]
trimExpectations =
[Expectation] -> [Expectation]
removeNonExplicitMatchingExpectations
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Eq a => [a] -> [a]
L.nub
in case Maybe Sweets
r of
Maybe Sweets
Nothing -> forall a. Maybe a
Nothing
Just Sweets
r' | [] <- Sweets -> [Expectation]
expected Sweets
r' -> forall a. Maybe a
Nothing
Just Sweets
r' -> forall a. a -> Maybe a
Just ( Sweets
r'
, SweetExpl { rootPath :: FilePath
rootPath = CandidateFile -> FilePath
candidateToPath CandidateFile
rootN
, base :: FilePath
base = CandidateFile -> FilePath
candidateToPath CandidateFile
matchPrefix
, expectedNames :: [FilePath]
expectedNames =
forall a. (a -> Bool) -> [a] -> [a]
filter
(if forall (t :: * -> *) a. Foldable t => t a -> Bool
null FilePath
expSuffix then forall a b. a -> b -> a
const Bool
True
else (FilePath
expSuffix forall a. Eq a => [a] -> [a] -> Bool
`L.isSuffixOf`))
(CandidateFile -> FilePath
candidateToPath forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [CandidateFile]
candidates)
, results :: Sweets
results = Sweets
r'
})
expectedSearch :: CandidateFile
-> [NamedParamMatch]
-> Separators
-> [ParameterPattern]
-> FileSuffix
-> [ (String, FileSuffix) ]
-> [CandidateFile]
-> Logic Expectation
expectedSearch :: CandidateFile
-> [NamedParamMatch]
-> FilePath
-> [ParameterPattern]
-> FilePath
-> [(FilePath, FilePath)]
-> [CandidateFile]
-> Logic Expectation
expectedSearch CandidateFile
rootPrefix [NamedParamMatch]
rootPVMatches FilePath
seps [ParameterPattern]
params FilePath
expSuffix [(FilePath, FilePath)]
assocNames [CandidateFile]
allNames =
do [ParameterPattern]
params' <- [NamedParamMatch] -> [ParameterPattern] -> Logic [ParameterPattern]
singlePVals [NamedParamMatch]
rootPVMatches [ParameterPattern]
params
(CandidateFile
expFile, [NamedParamMatch]
pmatch, [(FilePath, CandidateFile)]
assocFiles) <-
let bestRanked :: (Eq a, Eq b, Eq c)
=> [((a, Int, [b]),c)] -> Logic (a, [b], c)
bestRanked :: forall a b c.
(Eq a, Eq b, Eq c) =>
[((a, Int, [b]), c)] -> Logic (a, [b], c)
bestRanked [((a, Int, [b]), c)]
l =
if forall (t :: * -> *) a. Foldable t => t a -> Bool
null [((a, Int, [b]), c)]
l then forall (m :: * -> *) a. MonadPlus m => m a
mzero
else let m :: Int
m = forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
maximum forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall {a} {b} {c} {b}. ((a, b, c), b) -> b
rankValue [((a, Int, [b]), c)]
l
rankValue :: ((a, b, c), b) -> b
rankValue ((a
_,b
r,c
_),b
_) = b
r
rankMatching :: a -> ((a, a, c), b) -> Bool
rankMatching a
v ((a
_,a
r,c
_),b
_) = a
v forall a. Eq a => a -> a -> Bool
== a
r
dropRank :: ((a, b, b), c) -> (a, b, c)
dropRank ((a
a,b
_,b
b),c
c) = (a
a,b
b,c
c)
in forall a. [a] -> Logic a
eachFrom forall a b. (a -> b) -> a -> b
$ forall a. Eq a => [a] -> [a]
L.nub forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall {a} {b} {b} {c}. ((a, b, b), c) -> (a, b, c)
dropRank forall a b. (a -> b) -> a -> b
$ forall a. (a -> Bool) -> [a] -> [a]
filter (forall {a} {a} {c} {b}. Eq a => a -> ((a, a, c), b) -> Bool
rankMatching Int
m) [((a, Int, [b]), c)]
l
in forall a b c.
(Eq a, Eq b, Eq c) =>
[((a, Int, [b]), c)] -> Logic (a, [b], c)
bestRanked forall a b. (a -> b) -> a -> b
$
forall a. Logic a -> [a]
observeAll forall a b. (a -> b) -> a -> b
$
do [ParameterPattern]
pseq <- forall a. [a] -> Logic a
eachFrom forall a b. (a -> b) -> a -> b
$
([] forall a. a -> [a] -> [a]
:) forall a b. (a -> b) -> a -> b
$
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 a b. (a -> b) -> a -> b
$
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap forall a. [a] -> [[a]]
L.inits forall a b. (a -> b) -> a -> b
$
forall a. [a] -> [[a]]
L.permutations [ParameterPattern]
params'
[(FilePath, Maybe FilePath)]
pvals <- [ParameterPattern] -> Logic [(FilePath, Maybe FilePath)]
getPVals [ParameterPattern]
pseq
let compatNames :: [CandidateFile]
compatNames = forall a. (a -> Bool) -> [a] -> [a]
filter (FilePath
-> [ParameterPattern]
-> [(FilePath, Maybe FilePath)]
-> CandidateFile
-> Bool
isCompatible FilePath
seps [ParameterPattern]
params [(FilePath, Maybe FilePath)]
pvals) [CandidateFile]
allNames
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> Bool
not forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a. Foldable t => t a -> Bool
null [CandidateFile]
compatNames)
e :: (CandidateFile, Int, [NamedParamMatch])
e@(CandidateFile
_,Int
_,[NamedParamMatch]
pmatch) <- CandidateFile
-> [NamedParamMatch]
-> FilePath
-> [ParameterPattern]
-> [(FilePath, Maybe FilePath)]
-> FilePath
-> [CandidateFile]
-> Logic (CandidateFile, Int, [NamedParamMatch])
getExp CandidateFile
rootPrefix [NamedParamMatch]
rootPVMatches FilePath
seps [ParameterPattern]
params [(FilePath, Maybe FilePath)]
pvals
FilePath
expSuffix [CandidateFile]
compatNames
[(FilePath, CandidateFile)]
a <- (CandidateFile
-> FilePath
-> [NamedParamMatch]
-> [(FilePath, FilePath)]
-> [CandidateFile]
-> Logic [(FilePath, CandidateFile)]
getAssoc CandidateFile
rootPrefix FilePath
seps [NamedParamMatch]
pmatch [(FilePath, FilePath)]
assocNames [CandidateFile]
compatNames)
forall (m :: * -> *) a. Monad m => a -> m a
return ((CandidateFile, Int, [NamedParamMatch])
e,[(FilePath, CandidateFile)]
a)
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Expectation { expectedFile :: FilePath
expectedFile = CandidateFile -> FilePath
candidateToPath CandidateFile
expFile
, associated :: [(FilePath, FilePath)]
associated = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap CandidateFile -> FilePath
candidateToPath forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(FilePath, CandidateFile)]
assocFiles
, expParamsMatch :: [NamedParamMatch]
expParamsMatch = forall a. Ord a => [a] -> [a]
L.sort [NamedParamMatch]
pmatch
}
getExp :: CandidateFile
-> [NamedParamMatch]
-> Separators
-> [ParameterPattern]
-> [(String, Maybe String)]
-> FileSuffix
-> [CandidateFile]
-> Logic (CandidateFile, Int, [NamedParamMatch])
getExp :: CandidateFile
-> [NamedParamMatch]
-> FilePath
-> [ParameterPattern]
-> [(FilePath, Maybe FilePath)]
-> FilePath
-> [CandidateFile]
-> Logic (CandidateFile, Int, [NamedParamMatch])
getExp CandidateFile
rootPrefix [NamedParamMatch]
rootPMatches FilePath
seps [ParameterPattern]
params [(FilePath, Maybe FilePath)]
pvals FilePath
expSuffix [CandidateFile]
allNames =
do
let rootMatchesInSubdir :: CandidateFile -> [NamedParamMatch]
rootMatchesInSubdir :: CandidateFile -> [NamedParamMatch]
rootMatchesInSubdir CandidateFile
f =
let chkRootMatch :: FilePath -> [NamedParamMatch] -> [NamedParamMatch]
chkRootMatch FilePath
d [NamedParamMatch]
r =
let chkRPMatch :: (a, ParamMatch) -> [(a, ParamMatch)] -> [(a, ParamMatch)]
chkRPMatch (a, ParamMatch)
p [(a, ParamMatch)]
r' =
case ParamMatch -> Maybe FilePath
getExplicit forall a b. (a -> b) -> a -> b
$ forall a b. (a, b) -> b
snd (a, ParamMatch)
p of
Just FilePath
v -> if FilePath
d forall a. Eq a => a -> a -> Bool
== FilePath
v then (a, ParamMatch)
p forall a. a -> [a] -> [a]
: [(a, ParamMatch)]
r' else [(a, ParamMatch)]
r'
Maybe FilePath
Nothing -> [(a, ParamMatch)]
r'
in forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr forall {a}.
(a, ParamMatch) -> [(a, ParamMatch)] -> [(a, ParamMatch)]
chkRPMatch [NamedParamMatch]
r [NamedParamMatch]
rootPMatches
in forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr FilePath -> [NamedParamMatch] -> [NamedParamMatch]
chkRootMatch forall a. Monoid a => a
mempty forall a b. (a -> b) -> a -> b
$ CandidateFile -> [FilePath]
candidateSubdirs CandidateFile
f
let inpDirMatches :: [(CandidateFile, [NamedParamMatch])]
inpDirMatches = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap CandidateFile -> [NamedParamMatch]
rootMatchesInSubdir forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a b. [a] -> [b] -> [(a, b)]
zip [CandidateFile]
allNames [CandidateFile]
allNames
(CandidateFile
dirName, [NamedParamMatch]
inpDirMatch) <- forall a. [a] -> Logic a
eachFrom [(CandidateFile, [NamedParamMatch])]
inpDirMatches
let nonRootMatchPVals :: [(FilePath, Maybe FilePath)]
nonRootMatchPVals = forall a b. [(FilePath, a)] -> [(FilePath, b)] -> [(FilePath, a)]
removePVals [(FilePath, Maybe FilePath)]
pvals [NamedParamMatch]
inpDirMatch
([NamedParamMatch]
otherMatchesInSubdir, [ParameterPattern]
_) <-
CandidateFile
-> [ParameterPattern]
-> [ParameterPattern]
-> Logic ([NamedParamMatch], [ParameterPattern])
dirMatches CandidateFile
dirName [ParameterPattern]
params forall a b. (a -> b) -> a -> b
$ (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 (forall a. a -> [a] -> [a]
:[])) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(FilePath, Maybe FilePath)]
nonRootMatchPVals)
let remPVals :: [(FilePath, Maybe FilePath)]
remPVals = forall a b. [(FilePath, a)] -> [(FilePath, b)] -> [(FilePath, a)]
removePVals [(FilePath, Maybe FilePath)]
nonRootMatchPVals [NamedParamMatch]
otherMatchesInSubdir
let remRootMatches :: [NamedParamMatch]
remRootMatches = forall a b. [(FilePath, a)] -> [(FilePath, b)] -> [(FilePath, a)]
removePVals [NamedParamMatch]
rootPMatches [NamedParamMatch]
inpDirMatch
let validNames :: [CandidateFile]
validNames = [ CandidateFile
dirName ]
(CandidateFile
fp, Int
cnt, [NamedParamMatch]
npm) <- CandidateFile
-> [NamedParamMatch]
-> FilePath
-> [(FilePath, Maybe FilePath)]
-> FilePath
-> [CandidateFile]
-> Logic (CandidateFile, Int, [NamedParamMatch])
getExpFileParams CandidateFile
rootPrefix
[NamedParamMatch]
remRootMatches
FilePath
seps [(FilePath, Maybe FilePath)]
remPVals FilePath
expSuffix [CandidateFile]
validNames
let dpm :: [NamedParamMatch]
dpm = [NamedParamMatch]
inpDirMatch forall a. Semigroup a => a -> a -> a
<> [NamedParamMatch]
otherMatchesInSubdir
let conflict :: Bool
conflict = let chkNPM :: NamedParamMatch -> Bool -> Bool
chkNPM (FilePath
pn,ParamMatch
pv) Bool
acc =
Bool
acc Bool -> Bool -> Bool
|| case forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup FilePath
pn [NamedParamMatch]
dpm of
Maybe ParamMatch
Nothing -> Bool
False
Just ParamMatch
v -> ParamMatch
v forall a. Eq a => a -> a -> Bool
/= ParamMatch
pv
in forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr NamedParamMatch -> Bool -> Bool
chkNPM Bool
False [NamedParamMatch]
npm
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> Bool
not Bool
conflict)
forall (m :: * -> *) a. Monad m => a -> m a
return (CandidateFile
fp, forall (t :: * -> *) a. Foldable t => t a -> Int
length [NamedParamMatch]
dpm forall a. Num a => a -> a -> a
+ Int
cnt, [NamedParamMatch]
dpm forall a. Semigroup a => a -> a -> a
<> [NamedParamMatch]
npm)
getExpFileParams :: CandidateFile
-> [NamedParamMatch]
-> Separators
-> [(String, Maybe String)]
-> FileSuffix
-> [CandidateFile]
-> Logic (CandidateFile, Int, [NamedParamMatch])
getExpFileParams :: CandidateFile
-> [NamedParamMatch]
-> FilePath
-> [(FilePath, Maybe FilePath)]
-> FilePath
-> [CandidateFile]
-> Logic (CandidateFile, Int, [NamedParamMatch])
getExpFileParams CandidateFile
rootPrefix [NamedParamMatch]
rootPMatches FilePath
seps [(FilePath, Maybe FilePath)]
pvals FilePath
expSuffix [CandidateFile]
hereNames =
do let suffixSpecifiesSep :: Bool
suffixSpecifiesSep = forall (t :: * -> *). Foldable t => t Bool -> Bool
and [ Bool -> Bool
not (forall (t :: * -> *) a. Foldable t => t a -> Bool
null FilePath
expSuffix)
, forall a. [a] -> a
head FilePath
expSuffix forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` FilePath
seps
]
([NamedParamMatch]
pm, Int
pmcnt, FilePath
pmstr) <- FilePath
-> [NamedParamMatch]
-> [(FilePath, Maybe FilePath)]
-> Logic ([NamedParamMatch], Int, FilePath)
pvalMatch FilePath
seps [NamedParamMatch]
rootPMatches [(FilePath, Maybe FilePath)]
pvals
let suffixSepMatch :: Bool
suffixSepMatch = Bool -> Bool
not Bool
suffixSpecifiesSep
Bool -> Bool -> Bool
|| forall (t :: * -> *). Foldable t => t Bool -> Bool
and [ Bool -> Bool
not (forall (t :: * -> *) a. Foldable t => t a -> Bool
null FilePath
pmstr)
, forall a. [a] -> a
last FilePath
pmstr forall a. Eq a => a -> a -> Bool
== forall a. [a] -> a
head FilePath
expSuffix
]
forall (f :: * -> *). Alternative f => Bool -> f ()
guard Bool
suffixSepMatch
let ending :: FilePath
ending = if Bool
suffixSpecifiesSep then forall a. [a] -> [a]
tail FilePath
expSuffix else FilePath
expSuffix
CandidateFile
expFile <-
forall a. [a] -> Logic a
eachFrom
forall a b. (a -> b) -> a -> b
$ forall a. (a -> Bool) -> [a] -> [a]
filter (((CandidateFile -> FilePath
candidateFile CandidateFile
rootPrefix forall a. Semigroup a => a -> a -> a
<> FilePath
pmstr forall a. Semigroup a => a -> a -> a
<> FilePath
ending) forall a. Eq a => a -> a -> Bool
==) forall b c a. (b -> c) -> (a -> b) -> a -> c
. CandidateFile -> FilePath
candidateFile)
forall a b. (a -> b) -> a -> b
$ [CandidateFile]
hereNames
forall (m :: * -> *) a. Monad m => a -> m a
return (CandidateFile
expFile, Int
pmcnt, [NamedParamMatch]
pm)
removeNonExplicitMatchingExpectations :: [Expectation] -> [Expectation]
removeNonExplicitMatchingExpectations :: [Expectation] -> [Expectation]
removeNonExplicitMatchingExpectations =
let removeNonExplicits :: Expectation -> [Expectation] -> [Expectation]
removeNonExplicits Expectation
e [Expectation]
l =
let ([Expectation]
similarExpl, [Expectation]
diffExpl) = forall a. (a -> Bool) -> [a] -> ([a], [a])
L.partition (Expectation -> Expectation -> Bool
cmpPVals Expectation
e) [Expectation]
l
cmpPVals :: Expectation -> Expectation -> Bool
cmpPVals Expectation
ref Expectation
ps =
if forall (t :: * -> *) a. Foldable t => t a -> Int
length (Expectation -> [NamedParamMatch]
expParamsMatch Expectation
ref) forall a. Ord a => a -> a -> Bool
< forall (t :: * -> *) a. Foldable t => t a -> Int
length (Expectation -> [NamedParamMatch]
expParamsMatch Expectation
ps)
then Expectation -> Expectation -> [Maybe FilePath]
expPVals Expectation
ref Expectation
ref forall a. Eq a => a -> a -> Bool
== Expectation -> Expectation -> [Maybe FilePath]
expPVals Expectation
ref Expectation
ps
else Expectation -> Expectation -> [Maybe FilePath]
expPVals Expectation
ps Expectation
ps forall a. Eq a => a -> a -> Bool
== Expectation -> Expectation -> [Maybe FilePath]
expPVals Expectation
ps Expectation
ref
expPVals :: Expectation -> Expectation -> [Maybe FilePath]
expPVals Expectation
ref Expectation
ps =
let ps' :: [NamedParamMatch]
ps' = Expectation -> [NamedParamMatch]
expParamsMatch Expectation
ps
ref' :: [NamedParamMatch]
ref' = Expectation -> [NamedParamMatch]
expParamsMatch Expectation
ref
refNames :: [FilePath]
refNames = forall a b. (a, b) -> a
fst forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [NamedParamMatch]
ref'
in (\FilePath
n -> forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup FilePath
n [NamedParamMatch]
ps' forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ParamMatch -> Maybe FilePath
getParamVal) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [FilePath]
refNames
in if forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Expectation]
similarExpl
then Expectation
e forall a. a -> [a] -> [a]
: [Expectation]
l
else (forall a. (a -> [NamedParamMatch]) -> a -> a -> a
pmatchMax Expectation -> [NamedParamMatch]
expParamsMatch Expectation
e forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Expectation]
similarExpl) forall a. Semigroup a => a -> a -> a
<> [Expectation]
diffExpl
in forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr Expectation -> [Expectation] -> [Expectation]
removeNonExplicits forall a. Monoid a => a
mempty