{-# LANGUAGE OverloadedStrings #-}
module Test.Tasty.Sugar.Report
(
sweetsKVITable
, sweetsTextTable
)
where
import Data.KVITable
import Data.KVITable.Render.ASCII ( render
, defaultRenderConfig
, RenderConfig(..) )
import Data.Text ( Text )
import qualified Data.Text as T
import Lens.Micro ( (&), (.~) )
import qualified Prettyprinter as PP
import System.FilePath ( takeFileName )
import Test.Tasty.Sugar.Types
sweetsKVITable :: [Sweets] -> KVITable FilePath
sweetsKVITable :: [Sweets] -> KVITable FilePath
sweetsKVITable [] = KVITable FilePath
forall a. Monoid a => a
mempty
sweetsKVITable [Sweets]
sweets =
let t :: KVITable FilePath
t = [Item (KVITable FilePath)] -> KVITable FilePath
forall v. [Item (KVITable v)] -> KVITable v
fromList ([Item (KVITable FilePath)] -> KVITable FilePath)
-> [Item (KVITable FilePath)] -> KVITable FilePath
forall a b. (a -> b) -> a -> b
$ (Sweets -> [([(Text, Text)], FilePath)])
-> [Sweets] -> [([(Text, Text)], FilePath)]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap
(\Sweets
s ->
[
( (Text
"base", FilePath -> Text
T.pack (FilePath -> Text) -> FilePath -> Text
forall a b. (a -> b) -> a -> b
$ Sweets -> FilePath
rootBaseName Sweets
s)
(Text, Text) -> [(Text, Text)] -> [(Text, Text)]
forall a. a -> [a] -> [a]
: (Text
"rootFile", FilePath -> Text
T.pack (FilePath -> Text) -> FilePath -> Text
forall a b. (a -> b) -> a -> b
$ Sweets -> FilePath
rootFile Sweets
s)
(Text, Text) -> [(Text, Text)] -> [(Text, Text)]
forall a. a -> [a] -> [a]
: [ (FilePath -> Text
T.pack FilePath
pn, FilePath -> Text
T.pack (FilePath -> Text) -> FilePath -> Text
forall a b. (a -> b) -> a -> b
$ Doc Any -> FilePath
forall a. Show a => a -> FilePath
show (Doc Any -> FilePath) -> Doc Any -> FilePath
forall a b. (a -> b) -> a -> b
$ ParamMatch -> Doc Any
forall a ann. Pretty a => a -> Doc ann
PP.pretty ParamMatch
pv)
| (FilePath
pn,ParamMatch
pv) <- Expectation -> [(FilePath, ParamMatch)]
expParamsMatch Expectation
e ]
[(Text, Text)] -> [(Text, Text)] -> [(Text, Text)]
forall a. Semigroup a => a -> a -> a
<> [ (FilePath -> Text
T.pack FilePath
an, FilePath -> Text
T.pack (FilePath -> Text) -> FilePath -> Text
forall a b. (a -> b) -> a -> b
$ FilePath -> FilePath
takeFileName FilePath
af)
| (FilePath
an,FilePath
af) <- Expectation -> [(FilePath, FilePath)]
associated Expectation
e ]
, FilePath -> FilePath
takeFileName (Expectation -> FilePath
expectedFile Expectation
e)
)
| Expectation
e <- Sweets -> [Expectation]
expected Sweets
s
])
[Sweets]
sweets
in KVITable FilePath
t KVITable FilePath
-> (KVITable FilePath -> KVITable FilePath) -> KVITable FilePath
forall a b. a -> (a -> b) -> b
& (Text -> Identity Text)
-> KVITable FilePath -> Identity (KVITable FilePath)
forall v. Lens' (KVITable v) Text
valueColName ((Text -> Identity Text)
-> KVITable FilePath -> Identity (KVITable FilePath))
-> Text -> KVITable FilePath -> KVITable FilePath
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Text
"Expected File"
sweetsTextTable :: [CUBE] -> [Sweets] -> Text
sweetsTextTable :: [CUBE] -> [Sweets] -> Text
sweetsTextTable [] [Sweets]
_ = Text
"No CUBE provided for report"
sweetsTextTable [CUBE]
_ [] = Text
"No Sweets provided for report"
sweetsTextTable [CUBE]
c [Sweets]
s =
let cfg :: RenderConfig
cfg = RenderConfig
defaultRenderConfig
{ rowGroup :: [Text]
rowGroup = Text
"base"
Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
: Text
"rootFile"
Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
: (FilePath -> Text
T.pack (FilePath -> Text)
-> ((FilePath, Maybe [FilePath]) -> FilePath)
-> (FilePath, Maybe [FilePath])
-> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FilePath, Maybe [FilePath]) -> FilePath
forall a b. (a, b) -> a
fst ((FilePath, Maybe [FilePath]) -> Text)
-> [(FilePath, Maybe [FilePath])] -> [Text]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int
-> [(FilePath, Maybe [FilePath])] -> [(FilePath, Maybe [FilePath])]
forall a. Int -> [a] -> [a]
take Int
1 (CUBE -> [(FilePath, Maybe [FilePath])]
validParams (CUBE -> [(FilePath, Maybe [FilePath])])
-> CUBE -> [(FilePath, Maybe [FilePath])]
forall a b. (a -> b) -> a -> b
$ [CUBE] -> CUBE
forall a. [a] -> a
head [CUBE]
c))
, rowRepeat :: Bool
rowRepeat = Bool
False
}
in RenderConfig -> KVITable FilePath -> Text
forall v. Pretty v => RenderConfig -> KVITable v -> Text
render RenderConfig
cfg (KVITable FilePath -> Text) -> KVITable FilePath -> Text
forall a b. (a -> b) -> a -> b
$ [Sweets] -> KVITable FilePath
sweetsKVITable [Sweets]
s