{-# LANGUAGE CPP #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
module Test.Tasty.Sugar.Types where
import           Data.Function ( on )
import qualified Data.List as L
import           Data.Maybe ( catMaybes )
import qualified System.FilePath.GlobPattern as FPGP
#if MIN_VERSION_prettyprinter(1,7,0)
import Prettyprinter
#else
import Data.Text.Prettyprint.Doc
#endif
import Prelude hiding ( exp )
type FileSuffix = String
data CUBE = CUBE
   {
     
     
     
     CUBE -> FilePath
inputDir :: FilePath
     
     
     
     
     
     
     
     
     
     
     
     
     , CUBE -> FilePath
rootName :: FPGP.GlobPattern
     
     
     
     
     
     
     
     
     
     
     
     
     
     
     , CUBE -> FilePath
expectedSuffix :: FileSuffix
     
     
     
     
     
     
     
     
     
     
     
     
     
     , CUBE -> FilePath
separators :: Separators
     
     
     
     
     
     
     
     
     
     
     
     , CUBE -> [(FilePath, FilePath)]
associatedNames :: [ (String, FileSuffix) ]
     
     
     
     
     
     
     
     
     
     
     
     
     
     
     
     
     
     
     
     
     
     
     
     
     
     
     
     
     
     
     
     
     
     
     
     
     
     
     
     
     
     , CUBE -> [ParameterPattern]
validParams :: [ParameterPattern]
   }
   deriving (Int -> CUBE -> ShowS
[CUBE] -> ShowS
CUBE -> FilePath
(Int -> CUBE -> ShowS)
-> (CUBE -> FilePath) -> ([CUBE] -> ShowS) -> Show CUBE
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [CUBE] -> ShowS
$cshowList :: [CUBE] -> ShowS
show :: CUBE -> FilePath
$cshow :: CUBE -> FilePath
showsPrec :: Int -> CUBE -> ShowS
$cshowsPrec :: Int -> CUBE -> ShowS
Show, ReadPrec [CUBE]
ReadPrec CUBE
Int -> ReadS CUBE
ReadS [CUBE]
(Int -> ReadS CUBE)
-> ReadS [CUBE] -> ReadPrec CUBE -> ReadPrec [CUBE] -> Read CUBE
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CUBE]
$creadListPrec :: ReadPrec [CUBE]
readPrec :: ReadPrec CUBE
$creadPrec :: ReadPrec CUBE
readList :: ReadS [CUBE]
$creadList :: ReadS [CUBE]
readsPrec :: Int -> ReadS CUBE
$creadsPrec :: Int -> ReadS CUBE
Read)
type ParameterPattern = (String, Maybe [String])
type Separators = String
mkCUBE :: CUBE
mkCUBE :: CUBE
mkCUBE = CUBE :: FilePath
-> FilePath
-> FilePath
-> FilePath
-> [(FilePath, FilePath)]
-> [ParameterPattern]
-> CUBE
CUBE { inputDir :: FilePath
inputDir = FilePath
"test/samples"
              , separators :: FilePath
separators = FilePath
".-"
              , rootName :: FilePath
rootName = FilePath
"*"
              , associatedNames :: [(FilePath, FilePath)]
associatedNames = []
              , expectedSuffix :: FilePath
expectedSuffix = FilePath
"exp"
              , validParams :: [ParameterPattern]
validParams = []
              }
instance Pretty CUBE where
  pretty :: CUBE -> Doc ann
pretty CUBE
cube =
    let assoc :: Maybe (Doc ann)
assoc = [(FilePath, FilePath)] -> Maybe (Doc ann)
forall ann. [(FilePath, FilePath)] -> Maybe (Doc ann)
prettyAssocNames ([(FilePath, FilePath)] -> Maybe (Doc ann))
-> [(FilePath, FilePath)] -> Maybe (Doc ann)
forall a b. (a -> b) -> a -> b
$ CUBE -> [(FilePath, FilePath)]
associatedNames CUBE
cube
        parms :: Maybe (Doc ann)
parms = [ParameterPattern] -> Maybe (Doc ann)
forall ann. [ParameterPattern] -> Maybe (Doc ann)
prettyParamPatterns ([ParameterPattern] -> Maybe (Doc ann))
-> [ParameterPattern] -> Maybe (Doc ann)
forall a b. (a -> b) -> a -> b
$ CUBE -> [ParameterPattern]
validParams CUBE
cube
        hdrs :: [Doc ann]
hdrs = [ Doc ann
"input dir: " Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> FilePath -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty (CUBE -> FilePath
inputDir CUBE
cube)
               , Doc ann
"rootName: " Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> FilePath -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty (CUBE -> FilePath
rootName CUBE
cube)
               , Doc ann
"expected: " Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+>
                 Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann
brackets (FilePath -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty (FilePath -> Doc ann) -> FilePath -> Doc ann
forall a b. (a -> b) -> a -> b
$ CUBE -> FilePath
separators CUBE
cube) Doc ann -> Doc ann -> Doc ann
forall a. Semigroup a => a -> a -> a
<>
                 FilePath -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty (CUBE -> FilePath
expectedSuffix CUBE
cube)
               ]
    in Doc ann
"Sugar.CUBE" Doc ann -> Doc ann -> Doc ann
forall a. Semigroup a => a -> a -> a
<> (Int -> Doc ann -> Doc ann
forall ann. Int -> Doc ann -> Doc ann
indent Int
1 (Doc ann -> Doc ann) -> Doc ann -> Doc ann
forall a b. (a -> b) -> a -> b
$ [Doc ann] -> Doc ann
forall ann. [Doc ann] -> Doc ann
vsep ([Doc ann] -> Doc ann) -> [Doc ann] -> Doc ann
forall a b. (a -> b) -> a -> b
$ [Doc ann]
forall ann. [Doc ann]
hdrs [Doc ann] -> [Doc ann] -> [Doc ann]
forall a. Semigroup a => a -> a -> a
<> [Maybe (Doc ann)] -> [Doc ann]
forall a. [Maybe a] -> [a]
catMaybes [Maybe (Doc ann)
forall ann. Maybe (Doc ann)
assoc, Maybe (Doc ann)
forall ann. Maybe (Doc ann)
parms])
prettyAssocNames :: [(String, String)] -> Maybe (Doc ann)
prettyAssocNames :: [(FilePath, FilePath)] -> Maybe (Doc ann)
prettyAssocNames = \case
  [] -> Maybe (Doc ann)
forall a. Maybe a
Nothing
  [(FilePath, FilePath)]
nms -> Doc ann -> Maybe (Doc ann)
forall a. a -> Maybe a
Just (Doc ann -> Maybe (Doc ann)) -> Doc ann -> Maybe (Doc ann)
forall a b. (a -> b) -> a -> b
$ Doc ann
"associated:" Doc ann -> Doc ann -> Doc ann
forall a. Semigroup a => a -> a -> a
<> (Int -> Doc ann -> Doc ann
forall ann. Int -> Doc ann -> Doc ann
indent Int
1 (Doc ann -> Doc ann) -> Doc ann -> Doc ann
forall a b. (a -> b) -> a -> b
$ [Doc ann] -> Doc ann
forall ann. [Doc ann] -> Doc ann
vsep ([Doc ann] -> Doc ann) -> [Doc ann] -> Doc ann
forall a b. (a -> b) -> a -> b
$ ((FilePath, FilePath) -> Doc ann)
-> [(FilePath, FilePath)] -> [Doc ann]
forall a b. (a -> b) -> [a] -> [b]
map ((FilePath, FilePath) -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty ((FilePath, FilePath) -> Doc ann)
-> ((FilePath, FilePath) -> (FilePath, FilePath))
-> (FilePath, FilePath)
-> Doc ann
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShowS -> (FilePath, FilePath) -> (FilePath, FilePath)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ShowS
forall a. Show a => a -> FilePath
show) [(FilePath, FilePath)]
nms)
prettyParamPatterns :: [ParameterPattern] -> Maybe (Doc ann)
prettyParamPatterns :: [ParameterPattern] -> Maybe (Doc ann)
prettyParamPatterns = \case
  [] -> Maybe (Doc ann)
forall a. Maybe a
Nothing
  [ParameterPattern]
prms -> Doc ann -> Maybe (Doc ann)
forall a. a -> Maybe a
Just (Doc ann -> Maybe (Doc ann)) -> Doc ann -> Maybe (Doc ann)
forall a b. (a -> b) -> a -> b
$ Doc ann
"params:" Doc ann -> Doc ann -> Doc ann
forall a. Semigroup a => a -> a -> a
<>
          (let pp :: (a, Maybe [a]) -> Doc ann
pp (a
pn,Maybe [a]
mpv) =
                 a -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty a
pn Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc ann
forall ann. Doc ann
equals Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+>
                 case Maybe [a]
mpv of
                   Maybe [a]
Nothing -> Doc ann
"*"
                   Just [a]
vl -> [Doc ann] -> Doc ann
forall ann. [Doc ann] -> Doc ann
hsep ([Doc ann] -> Doc ann) -> [Doc ann] -> Doc ann
forall a b. (a -> b) -> a -> b
$
                              Doc ann -> [Doc ann] -> [Doc ann]
forall a. a -> [a] -> [a]
L.intersperse Doc ann
forall ann. Doc ann
pipe ([Doc ann] -> [Doc ann]) -> [Doc ann] -> [Doc ann]
forall a b. (a -> b) -> a -> b
$
                              (a -> Doc ann) -> [a] -> [Doc ann]
forall a b. (a -> b) -> [a] -> [b]
map a -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty [a]
vl
            in Int -> Doc ann -> Doc ann
forall ann. Int -> Doc ann -> Doc ann
indent Int
1 (Doc ann -> Doc ann) -> Doc ann -> Doc ann
forall a b. (a -> b) -> a -> b
$ [Doc ann] -> Doc ann
forall ann. [Doc ann] -> Doc ann
vsep ([Doc ann] -> Doc ann) -> [Doc ann] -> Doc ann
forall a b. (a -> b) -> a -> b
$ (ParameterPattern -> Doc ann) -> [ParameterPattern] -> [Doc ann]
forall a b. (a -> b) -> [a] -> [b]
map ParameterPattern -> Doc ann
forall a a ann. (Pretty a, Pretty a) => (a, Maybe [a]) -> Doc ann
pp [ParameterPattern]
prms)
data Sweets = Sweets
  { Sweets -> FilePath
rootBaseName :: String 
  , Sweets -> FilePath
rootMatchName :: String 
  , Sweets -> FilePath
rootFile :: FilePath    
  , Sweets -> [ParameterPattern]
cubeParams :: [ParameterPattern] 
  , Sweets -> [Expectation]
expected :: [Expectation] 
  }
  deriving (Int -> Sweets -> ShowS
[Sweets] -> ShowS
Sweets -> FilePath
(Int -> Sweets -> ShowS)
-> (Sweets -> FilePath) -> ([Sweets] -> ShowS) -> Show Sweets
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [Sweets] -> ShowS
$cshowList :: [Sweets] -> ShowS
show :: Sweets -> FilePath
$cshow :: Sweets -> FilePath
showsPrec :: Int -> Sweets -> ShowS
$cshowsPrec :: Int -> Sweets -> ShowS
Show, Sweets -> Sweets -> Bool
(Sweets -> Sweets -> Bool)
-> (Sweets -> Sweets -> Bool) -> Eq Sweets
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Sweets -> Sweets -> Bool
$c/= :: Sweets -> Sweets -> Bool
== :: Sweets -> Sweets -> Bool
$c== :: Sweets -> Sweets -> Bool
Eq)
instance Pretty Sweets where
  pretty :: Sweets -> Doc ann
pretty Sweets
inp = Doc ann
"Sweet" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+>
               (Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann
align (Doc ann -> Doc ann) -> Doc ann -> Doc ann
forall a b. (a -> b) -> a -> b
$ [Doc ann] -> Doc ann
forall ann. [Doc ann] -> Doc ann
vsep ([Doc ann] -> Doc ann) -> [Doc ann] -> Doc ann
forall a b. (a -> b) -> a -> b
$ [Maybe (Doc ann)] -> [Doc ann]
forall a. [Maybe a] -> [a]
catMaybes
                 [ Doc ann -> Maybe (Doc ann)
forall a. a -> Maybe a
Just (Doc ann -> Maybe (Doc ann)) -> Doc ann -> Maybe (Doc ann)
forall a b. (a -> b) -> a -> b
$ FilePath -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty (Sweets -> FilePath
rootMatchName Sweets
inp)
                 , Doc ann -> Maybe (Doc ann)
forall a. a -> Maybe a
Just (Doc ann -> Maybe (Doc ann)) -> Doc ann -> Maybe (Doc ann)
forall a b. (a -> b) -> a -> b
$ Doc ann
"root:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+>
                   Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann
align ([Doc ann] -> Doc ann
forall ann. [Doc ann] -> Doc ann
vsep [ FilePath -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty (Sweets -> FilePath
rootBaseName Sweets
inp)
                               , FilePath -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty (Sweets -> FilePath
rootFile Sweets
inp)
                               ])
                 , [ParameterPattern] -> Maybe (Doc ann)
forall ann. [ParameterPattern] -> Maybe (Doc ann)
prettyParamPatterns ([ParameterPattern] -> Maybe (Doc ann))
-> [ParameterPattern] -> Maybe (Doc ann)
forall a b. (a -> b) -> a -> b
$ Sweets -> [ParameterPattern]
cubeParams Sweets
inp
                 , Doc ann -> Maybe (Doc ann)
forall a. a -> Maybe a
Just (Doc ann -> Maybe (Doc ann)) -> Doc ann -> Maybe (Doc ann)
forall a b. (a -> b) -> a -> b
$ [Doc ann] -> Doc ann
forall ann. [Doc ann] -> Doc ann
vsep ([Doc ann] -> Doc ann) -> [Doc ann] -> Doc ann
forall a b. (a -> b) -> a -> b
$ (Expectation -> Doc ann) -> [Expectation] -> [Doc ann]
forall a b. (a -> b) -> [a] -> [b]
map Expectation -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty ([Expectation] -> [Doc ann]) -> [Expectation] -> [Doc ann]
forall a b. (a -> b) -> a -> b
$ Sweets -> [Expectation]
expected Sweets
inp
                 ])
type Association = (String, FilePath)
type NamedParamMatch = (String, ParamMatch)
data Expectation = Expectation
  { Expectation -> FilePath
expectedFile :: FilePath  
  , Expectation -> [NamedParamMatch]
expParamsMatch :: [ NamedParamMatch ] 
                                          
                                          
  , Expectation -> [(FilePath, FilePath)]
associated :: [ Association ] 
  }
  deriving Int -> Expectation -> ShowS
[Expectation] -> ShowS
Expectation -> FilePath
(Int -> Expectation -> ShowS)
-> (Expectation -> FilePath)
-> ([Expectation] -> ShowS)
-> Show Expectation
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [Expectation] -> ShowS
$cshowList :: [Expectation] -> ShowS
show :: Expectation -> FilePath
$cshow :: Expectation -> FilePath
showsPrec :: Int -> Expectation -> ShowS
$cshowsPrec :: Int -> Expectation -> ShowS
Show
instance Eq Expectation where
  Expectation
e1 == :: Expectation -> Expectation -> Bool
== Expectation
e2 = let bagCmp :: [a] -> [a] -> Bool
bagCmp [a]
a [a]
b = ([a] -> Bool) -> [[a]] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any ([a]
a [a] -> [a] -> Bool
forall a. Eq a => a -> a -> Bool
==) ([[a]] -> Bool) -> [[a]] -> Bool
forall a b. (a -> b) -> a -> b
$ [a] -> [[a]]
forall a. [a] -> [[a]]
L.permutations [a]
b
             in [Bool] -> Bool
forall (t :: * -> *). Foldable t => t Bool -> Bool
and [ Expectation -> FilePath
expectedFile Expectation
e1 FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
== Expectation -> FilePath
expectedFile Expectation
e2
                    , ([NamedParamMatch] -> [NamedParamMatch] -> Bool
forall a. Eq a => [a] -> [a] -> Bool
bagCmp ([NamedParamMatch] -> [NamedParamMatch] -> Bool)
-> (Expectation -> [NamedParamMatch])
-> Expectation
-> Expectation
-> Bool
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` Expectation -> [NamedParamMatch]
expParamsMatch) Expectation
e1 Expectation
e2
                    , ([(FilePath, FilePath)] -> [(FilePath, FilePath)] -> Bool
forall a. Eq a => [a] -> [a] -> Bool
bagCmp ([(FilePath, FilePath)] -> [(FilePath, FilePath)] -> Bool)
-> (Expectation -> [(FilePath, FilePath)])
-> Expectation
-> Expectation
-> Bool
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` Expectation -> [(FilePath, FilePath)]
associated) Expectation
e1 Expectation
e2
                    ]
instance Pretty Expectation where
  pretty :: Expectation -> Doc ann
pretty Expectation
exp =
    let p :: [NamedParamMatch]
p = Expectation -> [NamedParamMatch]
expParamsMatch Expectation
exp
        pp :: Maybe (Doc ann)
pp = if [NamedParamMatch] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [NamedParamMatch]
p
             then Maybe (Doc ann)
forall a. Maybe a
Nothing
             else Doc ann -> Maybe (Doc ann)
forall a. a -> Maybe a
Just (Doc ann -> Maybe (Doc ann)) -> Doc ann -> Maybe (Doc ann)
forall a b. (a -> b) -> a -> b
$ Doc ann
"Matched Params:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> (Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann
align (Doc ann -> Doc ann) -> Doc ann -> Doc ann
forall a b. (a -> b) -> a -> b
$ [Doc ann] -> Doc ann
forall ann. [Doc ann] -> Doc ann
vsep ([Doc ann] -> Doc ann) -> [Doc ann] -> Doc ann
forall a b. (a -> b) -> a -> b
$ (NamedParamMatch -> Doc ann) -> [NamedParamMatch] -> [Doc ann]
forall a b. (a -> b) -> [a] -> [b]
map NamedParamMatch -> Doc ann
forall a a ann. (Pretty a, Pretty a) => (a, a) -> Doc ann
ppp [NamedParamMatch]
p)
        ppp :: (a, a) -> Doc ann
ppp (a
n,a
v) = a -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty a
n Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc ann
forall ann. Doc ann
equals Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> a -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty a
v
        a :: [(FilePath, FilePath)]
a = Expectation -> [(FilePath, FilePath)]
associated Expectation
exp
        pa :: Maybe (Doc ann)
pa = if [(FilePath, FilePath)] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [(FilePath, FilePath)]
a
             then Maybe (Doc ann)
forall a. Maybe a
Nothing
             else Doc ann -> Maybe (Doc ann)
forall a. a -> Maybe a
Just (Doc ann -> Maybe (Doc ann)) -> Doc ann -> Maybe (Doc ann)
forall a b. (a -> b) -> a -> b
$ Doc ann
"Associated:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> (Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann
align (Doc ann -> Doc ann) -> Doc ann -> Doc ann
forall a b. (a -> b) -> a -> b
$ [Doc ann] -> Doc ann
forall ann. [Doc ann] -> Doc ann
vsep ([Doc ann] -> Doc ann) -> [Doc ann] -> Doc ann
forall a b. (a -> b) -> a -> b
$ ((FilePath, FilePath) -> Doc ann)
-> [(FilePath, FilePath)] -> [Doc ann]
forall a b. (a -> b) -> [a] -> [b]
map (FilePath, FilePath) -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty [(FilePath, FilePath)]
a)
    in Int -> Doc ann -> Doc ann
forall ann. Int -> Doc ann -> Doc ann
hang Int
4 (Doc ann -> Doc ann) -> Doc ann -> Doc ann
forall a b. (a -> b) -> a -> b
$ [Doc ann] -> Doc ann
forall ann. [Doc ann] -> Doc ann
vsep ([Doc ann] -> Doc ann) -> [Doc ann] -> Doc ann
forall a b. (a -> b) -> a -> b
$ [Maybe (Doc ann)] -> [Doc ann]
forall a. [Maybe a] -> [a]
catMaybes
       [ Doc ann -> Maybe (Doc ann)
forall a. a -> Maybe a
Just (Doc ann -> Maybe (Doc ann)) -> Doc ann -> Maybe (Doc ann)
forall a b. (a -> b) -> a -> b
$ Doc ann
"Expected: " Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> (Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann
align (Doc ann -> Doc ann) -> Doc ann -> Doc ann
forall a b. (a -> b) -> a -> b
$ FilePath -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty (Expectation -> FilePath
expectedFile Expectation
exp))
       , Maybe (Doc ann)
forall ann. Maybe (Doc ann)
pp
       , Maybe (Doc ann)
forall ann. Maybe (Doc ann)
pa
       ]
data ParamMatch =
  
  
  Explicit String
  
  
  
  
  
  | Assumed String
  
  
  
  
  
  
  | NotSpecified
  deriving (Int -> ParamMatch -> ShowS
[ParamMatch] -> ShowS
ParamMatch -> FilePath
(Int -> ParamMatch -> ShowS)
-> (ParamMatch -> FilePath)
-> ([ParamMatch] -> ShowS)
-> Show ParamMatch
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [ParamMatch] -> ShowS
$cshowList :: [ParamMatch] -> ShowS
show :: ParamMatch -> FilePath
$cshow :: ParamMatch -> FilePath
showsPrec :: Int -> ParamMatch -> ShowS
$cshowsPrec :: Int -> ParamMatch -> ShowS
Show, ParamMatch -> ParamMatch -> Bool
(ParamMatch -> ParamMatch -> Bool)
-> (ParamMatch -> ParamMatch -> Bool) -> Eq ParamMatch
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ParamMatch -> ParamMatch -> Bool
$c/= :: ParamMatch -> ParamMatch -> Bool
== :: ParamMatch -> ParamMatch -> Bool
$c== :: ParamMatch -> ParamMatch -> Bool
Eq)
instance Pretty ParamMatch where
  pretty :: ParamMatch -> Doc ann
pretty (Explicit FilePath
s) = FilePath -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty FilePath
s
  pretty (Assumed FilePath
s)  = Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann
brackets (Doc ann -> Doc ann) -> Doc ann -> Doc ann
forall a b. (a -> b) -> a -> b
$ FilePath -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty FilePath
s
  pretty ParamMatch
NotSpecified = Doc ann
"*"
paramMatchVal :: String -> ParamMatch -> Bool
paramMatchVal :: FilePath -> ParamMatch -> Bool
paramMatchVal FilePath
v (Explicit FilePath
s) = FilePath
s FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
== FilePath
v
paramMatchVal FilePath
v (Assumed FilePath
s) = FilePath
s FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
== FilePath
v
paramMatchVal FilePath
_ ParamMatch
NotSpecified = Bool
True
isExplicit :: ParamMatch -> Bool
isExplicit :: ParamMatch -> Bool
isExplicit = \case
  Explicit FilePath
_ -> Bool
True
  ParamMatch
_ -> Bool
False
getExplicit :: ParamMatch -> Maybe String
getExplicit :: ParamMatch -> Maybe FilePath
getExplicit (Explicit FilePath
v) = FilePath -> Maybe FilePath
forall a. a -> Maybe a
Just FilePath
v
getExplicit ParamMatch
_            = Maybe FilePath
forall a. Maybe a
Nothing
data SweetExplanation =
  SweetExpl { SweetExplanation -> FilePath
rootPath :: FilePath
            , SweetExplanation -> FilePath
base :: String
            , SweetExplanation -> [FilePath]
expectedNames :: [String]  
            , SweetExplanation -> [Sweets]
results :: [Sweets] 
            }
instance Pretty SweetExplanation where
  pretty :: SweetExplanation -> Doc ann
pretty SweetExplanation
expl =
    let nms :: [FilePath]
nms = SweetExplanation -> [FilePath]
expectedNames SweetExplanation
expl
    in Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann
align (Doc ann -> Doc ann) -> Doc ann -> Doc ann
forall a b. (a -> b) -> a -> b
$ [Doc ann] -> Doc ann
forall ann. [Doc ann] -> Doc ann
vsep ([Doc ann] -> Doc ann) -> [Doc ann] -> Doc ann
forall a b. (a -> b) -> a -> b
$ [Maybe (Doc ann)] -> [Doc ann]
forall a. [Maybe a] -> [a]
catMaybes [
      Doc ann -> Maybe (Doc ann)
forall a. a -> Maybe a
Just (Doc ann -> Maybe (Doc ann)) -> Doc ann -> Maybe (Doc ann)
forall a b. (a -> b) -> a -> b
$ [Doc ann] -> Doc ann
forall ann. [Doc ann] -> Doc ann
fillSep ([Doc ann] -> Doc ann) -> [Doc ann] -> Doc ann
forall a b. (a -> b) -> a -> b
$ Doc ann -> [Doc ann] -> [Doc ann]
forall ann. Doc ann -> [Doc ann] -> [Doc ann]
punctuate Doc ann
","
        [ Doc ann
"rootPath" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann
dquotes (FilePath -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty (FilePath -> Doc ann) -> FilePath -> Doc ann
forall a b. (a -> b) -> a -> b
$ SweetExplanation -> FilePath
rootPath SweetExplanation
expl)
        , Doc ann
"base" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann
dquotes (FilePath -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty (FilePath -> Doc ann) -> FilePath -> Doc ann
forall a b. (a -> b) -> a -> b
$ SweetExplanation -> FilePath
base SweetExplanation
expl)
        , if [FilePath] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [FilePath]
nms
          then Doc ann
"no matches"
          else (Int -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty (Int -> Doc ann) -> Int -> Doc ann
forall a b. (a -> b) -> a -> b
$ [FilePath] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [FilePath]
nms) Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc ann
"possible matches"
        ]
      , if [FilePath] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [FilePath]
nms
        then Maybe (Doc ann)
forall a. Maybe a
Nothing
        else Doc ann -> Maybe (Doc ann)
forall a. a -> Maybe a
Just (Doc ann -> Maybe (Doc ann)) -> Doc ann -> Maybe (Doc ann)
forall a b. (a -> b) -> a -> b
$ Int -> Doc ann -> Doc ann
forall ann. Int -> Doc ann -> Doc ann
indent Int
8 (Doc ann -> Doc ann) -> Doc ann -> Doc ann
forall a b. (a -> b) -> a -> b
$ [Doc ann] -> Doc ann
forall ann. [Doc ann] -> Doc ann
vsep ([Doc ann] -> Doc ann) -> [Doc ann] -> Doc ann
forall a b. (a -> b) -> a -> b
$ (FilePath -> Doc ann) -> [FilePath] -> [Doc ann]
forall a b. (a -> b) -> [a] -> [b]
map FilePath -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty [FilePath]
nms
      , if [Sweets] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null (SweetExplanation -> [Sweets]
results SweetExplanation
expl)
        then Maybe (Doc ann)
forall a. Maybe a
Nothing
        else Doc ann -> Maybe (Doc ann)
forall a. a -> Maybe a
Just (Doc ann -> Maybe (Doc ann)) -> Doc ann -> Maybe (Doc ann)
forall a b. (a -> b) -> a -> b
$ Int -> Doc ann -> Doc ann
forall ann. Int -> Doc ann -> Doc ann
indent Int
2 (Doc ann -> Doc ann) -> Doc ann -> Doc ann
forall a b. (a -> b) -> a -> b
$ Int -> Doc ann -> Doc ann
forall ann. Int -> Doc ann -> Doc ann
hang Int
2 (Doc ann -> Doc ann) -> Doc ann -> Doc ann
forall a b. (a -> b) -> a -> b
$ [Doc ann] -> Doc ann
forall ann. [Doc ann] -> Doc ann
vsep ([Doc ann] -> Doc ann) -> [Doc ann] -> Doc ann
forall a b. (a -> b) -> a -> b
$
             Doc ann
"Results:" Doc ann -> [Doc ann] -> [Doc ann]
forall a. a -> [a] -> [a]
: (Sweets -> Doc ann) -> [Sweets] -> [Doc ann]
forall a b. (a -> b) -> [a] -> [b]
map Sweets -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty (SweetExplanation -> [Sweets]
results SweetExplanation
expl)
    ]