{-# LANGUAGE CPP #-}
{-# LANGUAGE RecordWildCards #-}
module Test.Hspec.Core.Formatters.V1 (
silent
, checks
, specdoc
, progress
, failed_examples
, Formatter (..)
, FailureReason (..)
, FormatM
, formatterToFormat
, getSuccessCount
, getPendingCount
, getFailCount
, getTotalCount
, FailureRecord (..)
, getFailMessages
, usedSeed
, Seconds(..)
, getCPUTime
, getRealTime
, write
, writeLine
, writeTransient
, withInfoColor
, withSuccessColor
, withPendingColor
, withFailColor
, useDiff
, extraChunk
, missingChunk
, formatException
) where
import Prelude ()
import Test.Hspec.Core.Compat hiding (First)
import Data.Maybe
import Test.Hspec.Core.Util
import Test.Hspec.Core.Clock
import Test.Hspec.Core.Example (Location(..))
import Text.Printf
import Control.Monad.IO.Class
import Control.Exception
import Test.Hspec.Core.Formatters.V1.Monad (
Formatter(..)
, FailureReason(..)
, FormatM
, getSuccessCount
, getPendingCount
, getFailCount
, getTotalCount
, FailureRecord(..)
, getFailMessages
, usedSeed
, getCPUTime
, getRealTime
, write
, writeLine
, writeTransient
, withInfoColor
, withSuccessColor
, withPendingColor
, withFailColor
, useDiff
, extraChunk
, missingChunk
)
import Test.Hspec.Core.Format (FormatConfig, Format)
import Test.Hspec.Core.Formatters.Diff
import qualified Test.Hspec.Core.Formatters.V2 as V2
import Test.Hspec.Core.Formatters.V1.Monad (Item(..), Result(..), Environment(..), interpretWith)
formatterToFormat :: Formatter -> FormatConfig -> IO Format
formatterToFormat :: Formatter -> FormatConfig -> IO Format
formatterToFormat = Formatter -> FormatConfig -> IO Format
V2.formatterToFormat (Formatter -> FormatConfig -> IO Format)
-> (Formatter -> Formatter)
-> Formatter
-> FormatConfig
-> IO Format
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Formatter -> Formatter
legacyFormatterToFormatter
legacyFormatterToFormatter :: Formatter -> V2.Formatter
legacyFormatterToFormatter :: Formatter -> Formatter
legacyFormatterToFormatter Formatter{FormatM ()
[String] -> String -> FormatM ()
Path -> FormatM ()
Path -> String -> FormatM ()
Path -> String -> Maybe String -> FormatM ()
Path -> String -> FailureReason -> FormatM ()
Path -> Progress -> FormatM ()
footerFormatter :: Formatter -> FormatM ()
failedFormatter :: Formatter -> FormatM ()
examplePending :: Formatter -> Path -> String -> Maybe String -> FormatM ()
exampleFailed :: Formatter -> Path -> String -> FailureReason -> FormatM ()
exampleSucceeded :: Formatter -> Path -> String -> FormatM ()
exampleProgress :: Formatter -> Path -> Progress -> FormatM ()
exampleStarted :: Formatter -> Path -> FormatM ()
exampleGroupDone :: Formatter -> FormatM ()
exampleGroupStarted :: Formatter -> [String] -> String -> FormatM ()
headerFormatter :: Formatter -> FormatM ()
footerFormatter :: FormatM ()
failedFormatter :: FormatM ()
examplePending :: Path -> String -> Maybe String -> FormatM ()
exampleFailed :: Path -> String -> FailureReason -> FormatM ()
exampleSucceeded :: Path -> String -> FormatM ()
exampleProgress :: Path -> Progress -> FormatM ()
exampleStarted :: Path -> FormatM ()
exampleGroupDone :: FormatM ()
exampleGroupStarted :: [String] -> String -> FormatM ()
headerFormatter :: FormatM ()
..} = Formatter :: FormatM ()
-> (Path -> FormatM ())
-> (Path -> FormatM ())
-> (Path -> Progress -> FormatM ())
-> (Path -> FormatM ())
-> (Path -> Item -> FormatM ())
-> FormatM ()
-> Formatter
V2.Formatter {
formatterStarted :: FormatM ()
V2.formatterStarted = FormatM () -> FormatM ()
forall a. FormatM a -> FormatM a
interpret FormatM ()
headerFormatter
, formatterGroupStarted :: Path -> FormatM ()
V2.formatterGroupStarted = FormatM () -> FormatM ()
forall a. FormatM a -> FormatM a
interpret (FormatM () -> FormatM ())
-> (Path -> FormatM ()) -> Path -> FormatM ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([String] -> String -> FormatM ()) -> Path -> FormatM ()
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry [String] -> String -> FormatM ()
exampleGroupStarted
, formatterGroupDone :: Path -> FormatM ()
V2.formatterGroupDone = FormatM () -> FormatM ()
forall a. FormatM a -> FormatM a
interpret (FormatM () -> FormatM ())
-> (Path -> FormatM ()) -> Path -> FormatM ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FormatM () -> Path -> FormatM ()
forall a b. a -> b -> a
const FormatM ()
exampleGroupDone
, formatterProgress :: Path -> Progress -> FormatM ()
V2.formatterProgress = \ Path
path -> FormatM () -> FormatM ()
forall a. FormatM a -> FormatM a
interpret (FormatM () -> FormatM ())
-> (Progress -> FormatM ()) -> Progress -> FormatM ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Path -> Progress -> FormatM ()
exampleProgress Path
path
, formatterItemStarted :: Path -> FormatM ()
V2.formatterItemStarted = FormatM () -> FormatM ()
forall a. FormatM a -> FormatM a
interpret (FormatM () -> FormatM ())
-> (Path -> FormatM ()) -> Path -> FormatM ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Path -> FormatM ()
exampleStarted
, formatterItemDone :: Path -> Item -> FormatM ()
V2.formatterItemDone = \ Path
path Item
item -> FormatM () -> FormatM ()
forall a. FormatM a -> FormatM a
interpret (FormatM () -> FormatM ()) -> FormatM () -> FormatM ()
forall a b. (a -> b) -> a -> b
$ do
case Item -> Result
itemResult Item
item of
Result
Success -> Path -> String -> FormatM ()
exampleSucceeded Path
path (Item -> String
itemInfo Item
item)
Pending Maybe Location
_ Maybe String
reason -> Path -> String -> Maybe String -> FormatM ()
examplePending Path
path (Item -> String
itemInfo Item
item) Maybe String
reason
Failure Maybe Location
_ FailureReason
reason -> Path -> String -> FailureReason -> FormatM ()
exampleFailed Path
path (Item -> String
itemInfo Item
item) FailureReason
reason
, formatterDone :: FormatM ()
V2.formatterDone = FormatM () -> FormatM ()
forall a. FormatM a -> FormatM a
interpret (FormatM () -> FormatM ()) -> FormatM () -> FormatM ()
forall a b. (a -> b) -> a -> b
$ FormatM ()
failedFormatter FormatM () -> FormatM () -> FormatM ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> FormatM ()
footerFormatter
}
interpret :: FormatM a -> V2.FormatM a
interpret :: FormatM a -> FormatM a
interpret = Environment FormatM -> FormatM a -> FormatM a
forall (m :: * -> *) a.
Monad m =>
Environment m -> FormatM a -> m a
interpretWith Environment :: forall (m :: * -> *).
m Int
-> m Int
-> m [FailureRecord]
-> m Integer
-> m Bool
-> m (Maybe Seconds)
-> m Seconds
-> (String -> m ())
-> (String -> m ())
-> (forall a. m a -> m a)
-> (forall a. m a -> m a)
-> (forall a. m a -> m a)
-> (forall a. m a -> m a)
-> m Bool
-> (String -> m ())
-> (String -> m ())
-> (forall a. IO a -> m a)
-> Environment m
Environment {
environmentGetSuccessCount :: FormatM Int
environmentGetSuccessCount = FormatM Int
V2.getSuccessCount
, environmentGetPendingCount :: FormatM Int
environmentGetPendingCount = FormatM Int
V2.getPendingCount
, environmentGetFailMessages :: FormatM [FailureRecord]
environmentGetFailMessages = FormatM [FailureRecord]
V2.getFailMessages
, environmentUsedSeed :: FormatM Integer
environmentUsedSeed = FormatM Integer
V2.usedSeed
, environmentPrintTimes :: FormatM Bool
environmentPrintTimes = FormatM Bool
V2.printTimes
, environmentGetCPUTime :: FormatM (Maybe Seconds)
environmentGetCPUTime = FormatM (Maybe Seconds)
V2.getCPUTime
, environmentGetRealTime :: FormatM Seconds
environmentGetRealTime = FormatM Seconds
V2.getRealTime
, environmentWrite :: String -> FormatM ()
environmentWrite = String -> FormatM ()
V2.write
, environmentWriteTransient :: String -> FormatM ()
environmentWriteTransient = String -> FormatM ()
V2.writeTransient
, environmentWithFailColor :: forall a. FormatM a -> FormatM a
environmentWithFailColor = forall a. FormatM a -> FormatM a
V2.withFailColor
, environmentWithSuccessColor :: forall a. FormatM a -> FormatM a
environmentWithSuccessColor = forall a. FormatM a -> FormatM a
V2.withSuccessColor
, environmentWithPendingColor :: forall a. FormatM a -> FormatM a
environmentWithPendingColor = forall a. FormatM a -> FormatM a
V2.withPendingColor
, environmentWithInfoColor :: forall a. FormatM a -> FormatM a
environmentWithInfoColor = forall a. FormatM a -> FormatM a
V2.withInfoColor
, environmentUseDiff :: FormatM Bool
environmentUseDiff = FormatM Bool
V2.useDiff
, environmentExtraChunk :: String -> FormatM ()
environmentExtraChunk = String -> FormatM ()
V2.extraChunk
, environmentMissingChunk :: String -> FormatM ()
environmentMissingChunk = String -> FormatM ()
V2.missingChunk
, environmentLiftIO :: forall a. IO a -> FormatM a
environmentLiftIO = forall a. IO a -> FormatM a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO
}
silent :: Formatter
silent :: Formatter
silent = Formatter :: FormatM ()
-> ([String] -> String -> FormatM ())
-> FormatM ()
-> (Path -> FormatM ())
-> (Path -> Progress -> FormatM ())
-> (Path -> String -> FormatM ())
-> (Path -> String -> FailureReason -> FormatM ())
-> (Path -> String -> Maybe String -> FormatM ())
-> FormatM ()
-> FormatM ()
-> Formatter
Formatter {
headerFormatter :: FormatM ()
headerFormatter = () -> FormatM ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
, exampleGroupStarted :: [String] -> String -> FormatM ()
exampleGroupStarted = \[String]
_ String
_ -> () -> FormatM ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
, exampleGroupDone :: FormatM ()
exampleGroupDone = () -> FormatM ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
, exampleStarted :: Path -> FormatM ()
exampleStarted = \Path
_ -> () -> FormatM ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
, exampleProgress :: Path -> Progress -> FormatM ()
exampleProgress = \Path
_ Progress
_ -> () -> FormatM ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
, exampleSucceeded :: Path -> String -> FormatM ()
exampleSucceeded = \ Path
_ String
_ -> () -> FormatM ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
, exampleFailed :: Path -> String -> FailureReason -> FormatM ()
exampleFailed = \Path
_ String
_ FailureReason
_ -> () -> FormatM ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
, examplePending :: Path -> String -> Maybe String -> FormatM ()
examplePending = \Path
_ String
_ Maybe String
_ -> () -> FormatM ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
, failedFormatter :: FormatM ()
failedFormatter = () -> FormatM ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
, footerFormatter :: FormatM ()
footerFormatter = () -> FormatM ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
}
checks :: Formatter
checks :: Formatter
checks = Formatter
specdoc {
exampleStarted :: Path -> FormatM ()
exampleStarted = \([String]
nesting, String
requirement) -> do
String -> FormatM ()
writeTransient (String -> FormatM ()) -> String -> FormatM ()
forall a b. (a -> b) -> a -> b
$ [String] -> String
forall (t :: * -> *) a. Foldable t => t a -> String
indentationFor [String]
nesting String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
requirement String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" [ ]"
, exampleProgress :: Path -> Progress -> FormatM ()
exampleProgress = \([String]
nesting, String
requirement) Progress
p -> do
String -> FormatM ()
writeTransient (String -> FormatM ()) -> String -> FormatM ()
forall a b. (a -> b) -> a -> b
$ [String] -> String
forall (t :: * -> *) a. Foldable t => t a -> String
indentationFor [String]
nesting String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
requirement String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" [" String -> String -> String
forall a. [a] -> [a] -> [a]
++ (Progress -> String
forall a a. (Eq a, Num a, Show a, Show a) => (a, a) -> String
formatProgress Progress
p) String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"]"
, exampleSucceeded :: Path -> String -> FormatM ()
exampleSucceeded = \([String]
nesting, String
requirement) String
info -> do
[String] -> String -> String -> FormatM () -> FormatM ()
writeResult [String]
nesting String
requirement String
info (FormatM () -> FormatM ()) -> FormatM () -> FormatM ()
forall a b. (a -> b) -> a -> b
$ FormatM () -> FormatM ()
forall a. FormatM a -> FormatM a
withSuccessColor (FormatM () -> FormatM ()) -> FormatM () -> FormatM ()
forall a b. (a -> b) -> a -> b
$ String -> FormatM ()
write String
"✔"
, exampleFailed :: Path -> String -> FailureReason -> FormatM ()
exampleFailed = \([String]
nesting, String
requirement) String
info FailureReason
_ -> do
[String] -> String -> String -> FormatM () -> FormatM ()
writeResult [String]
nesting String
requirement String
info (FormatM () -> FormatM ()) -> FormatM () -> FormatM ()
forall a b. (a -> b) -> a -> b
$ FormatM () -> FormatM ()
forall a. FormatM a -> FormatM a
withFailColor (FormatM () -> FormatM ()) -> FormatM () -> FormatM ()
forall a b. (a -> b) -> a -> b
$ String -> FormatM ()
write String
"✘"
, examplePending :: Path -> String -> Maybe String -> FormatM ()
examplePending = \([String]
nesting, String
requirement) String
info Maybe String
reason -> do
[String] -> String -> String -> FormatM () -> FormatM ()
writeResult [String]
nesting String
requirement String
info (FormatM () -> FormatM ()) -> FormatM () -> FormatM ()
forall a b. (a -> b) -> a -> b
$ FormatM () -> FormatM ()
forall a. FormatM a -> FormatM a
withPendingColor (FormatM () -> FormatM ()) -> FormatM () -> FormatM ()
forall a b. (a -> b) -> a -> b
$ String -> FormatM ()
write String
"‐"
FormatM () -> FormatM ()
forall a. FormatM a -> FormatM a
withPendingColor (FormatM () -> FormatM ()) -> FormatM () -> FormatM ()
forall a b. (a -> b) -> a -> b
$ do
String -> FormatM ()
writeLine (String -> FormatM ()) -> String -> FormatM ()
forall a b. (a -> b) -> a -> b
$ [String] -> String
forall (t :: * -> *) a. Foldable t => t a -> String
indentationFor (String
"" String -> [String] -> [String]
forall a. a -> [a] -> [a]
: [String]
nesting) String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"# PENDING: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> Maybe String -> String
forall a. a -> Maybe a -> a
fromMaybe String
"No reason given" Maybe String
reason
} where
indentationFor :: t a -> String
indentationFor t a
nesting = Int -> Char -> String
forall a. Int -> a -> [a]
replicate (t a -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length t a
nesting Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
2) Char
' '
writeResult :: [String] -> String -> String -> FormatM () -> FormatM ()
writeResult :: [String] -> String -> String -> FormatM () -> FormatM ()
writeResult [String]
nesting String
requirement String
info FormatM ()
action = do
String -> FormatM ()
write (String -> FormatM ()) -> String -> FormatM ()
forall a b. (a -> b) -> a -> b
$ [String] -> String
forall (t :: * -> *) a. Foldable t => t a -> String
indentationFor [String]
nesting String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
requirement String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" ["
FormatM ()
action
String -> FormatM ()
writeLine String
"]"
[String] -> (String -> FormatM ()) -> FormatM ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ (String -> [String]
lines String
info) ((String -> FormatM ()) -> FormatM ())
-> (String -> FormatM ()) -> FormatM ()
forall a b. (a -> b) -> a -> b
$ \ String
s ->
String -> FormatM ()
writeLine (String -> FormatM ()) -> String -> FormatM ()
forall a b. (a -> b) -> a -> b
$ [String] -> String
forall (t :: * -> *) a. Foldable t => t a -> String
indentationFor (String
"" String -> [String] -> [String]
forall a. a -> [a] -> [a]
: [String]
nesting) String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
s
formatProgress :: (a, a) -> String
formatProgress (a
current, a
total)
| a
total a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
0 = a -> String
forall a. Show a => a -> String
show a
current
| Bool
otherwise = a -> String
forall a. Show a => a -> String
show a
current String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"/" String -> String -> String
forall a. [a] -> [a] -> [a]
++ a -> String
forall a. Show a => a -> String
show a
total
specdoc :: Formatter
specdoc :: Formatter
specdoc = Formatter
silent {
headerFormatter :: FormatM ()
headerFormatter = do
String -> FormatM ()
writeLine String
""
, exampleGroupStarted :: [String] -> String -> FormatM ()
exampleGroupStarted = \[String]
nesting String
name -> do
String -> FormatM ()
writeLine ([String] -> String
forall (t :: * -> *) a. Foldable t => t a -> String
indentationFor [String]
nesting String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
name)
, exampleProgress :: Path -> Progress -> FormatM ()
exampleProgress = \Path
_ Progress
p -> do
String -> FormatM ()
writeTransient (Progress -> String
forall a a. (Eq a, Num a, Show a, Show a) => (a, a) -> String
formatProgress Progress
p)
, exampleSucceeded :: Path -> String -> FormatM ()
exampleSucceeded = \([String]
nesting, String
requirement) String
info -> FormatM () -> FormatM ()
forall a. FormatM a -> FormatM a
withSuccessColor (FormatM () -> FormatM ()) -> FormatM () -> FormatM ()
forall a b. (a -> b) -> a -> b
$ do
String -> FormatM ()
writeLine (String -> FormatM ()) -> String -> FormatM ()
forall a b. (a -> b) -> a -> b
$ [String] -> String
forall (t :: * -> *) a. Foldable t => t a -> String
indentationFor [String]
nesting String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
requirement
[String] -> (String -> FormatM ()) -> FormatM ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ (String -> [String]
lines String
info) ((String -> FormatM ()) -> FormatM ())
-> (String -> FormatM ()) -> FormatM ()
forall a b. (a -> b) -> a -> b
$ \ String
s ->
String -> FormatM ()
writeLine (String -> FormatM ()) -> String -> FormatM ()
forall a b. (a -> b) -> a -> b
$ [String] -> String
forall (t :: * -> *) a. Foldable t => t a -> String
indentationFor (String
"" String -> [String] -> [String]
forall a. a -> [a] -> [a]
: [String]
nesting) String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
s
, exampleFailed :: Path -> String -> FailureReason -> FormatM ()
exampleFailed = \([String]
nesting, String
requirement) String
info FailureReason
_ -> FormatM () -> FormatM ()
forall a. FormatM a -> FormatM a
withFailColor (FormatM () -> FormatM ()) -> FormatM () -> FormatM ()
forall a b. (a -> b) -> a -> b
$ do
Int
n <- FormatM Int
getFailCount
String -> FormatM ()
writeLine (String -> FormatM ()) -> String -> FormatM ()
forall a b. (a -> b) -> a -> b
$ [String] -> String
forall (t :: * -> *) a. Foldable t => t a -> String
indentationFor [String]
nesting String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
requirement String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" FAILED [" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
n String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"]"
[String] -> (String -> FormatM ()) -> FormatM ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ (String -> [String]
lines String
info) ((String -> FormatM ()) -> FormatM ())
-> (String -> FormatM ()) -> FormatM ()
forall a b. (a -> b) -> a -> b
$ \ String
s ->
String -> FormatM ()
writeLine (String -> FormatM ()) -> String -> FormatM ()
forall a b. (a -> b) -> a -> b
$ [String] -> String
forall (t :: * -> *) a. Foldable t => t a -> String
indentationFor (String
"" String -> [String] -> [String]
forall a. a -> [a] -> [a]
: [String]
nesting) String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
s
, examplePending :: Path -> String -> Maybe String -> FormatM ()
examplePending = \([String]
nesting, String
requirement) String
info Maybe String
reason -> FormatM () -> FormatM ()
forall a. FormatM a -> FormatM a
withPendingColor (FormatM () -> FormatM ()) -> FormatM () -> FormatM ()
forall a b. (a -> b) -> a -> b
$ do
String -> FormatM ()
writeLine (String -> FormatM ()) -> String -> FormatM ()
forall a b. (a -> b) -> a -> b
$ [String] -> String
forall (t :: * -> *) a. Foldable t => t a -> String
indentationFor [String]
nesting String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
requirement
[String] -> (String -> FormatM ()) -> FormatM ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ (String -> [String]
lines String
info) ((String -> FormatM ()) -> FormatM ())
-> (String -> FormatM ()) -> FormatM ()
forall a b. (a -> b) -> a -> b
$ \ String
s ->
String -> FormatM ()
writeLine (String -> FormatM ()) -> String -> FormatM ()
forall a b. (a -> b) -> a -> b
$ [String] -> String
forall (t :: * -> *) a. Foldable t => t a -> String
indentationFor (String
"" String -> [String] -> [String]
forall a. a -> [a] -> [a]
: [String]
nesting) String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
s
String -> FormatM ()
writeLine (String -> FormatM ()) -> String -> FormatM ()
forall a b. (a -> b) -> a -> b
$ [String] -> String
forall (t :: * -> *) a. Foldable t => t a -> String
indentationFor (String
"" String -> [String] -> [String]
forall a. a -> [a] -> [a]
: [String]
nesting) String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"# PENDING: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> Maybe String -> String
forall a. a -> Maybe a -> a
fromMaybe String
"No reason given" Maybe String
reason
, failedFormatter :: FormatM ()
failedFormatter = FormatM ()
defaultFailedFormatter
, footerFormatter :: FormatM ()
footerFormatter = FormatM ()
defaultFooter
} where
indentationFor :: t a -> String
indentationFor t a
nesting = Int -> Char -> String
forall a. Int -> a -> [a]
replicate (t a -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length t a
nesting Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
2) Char
' '
formatProgress :: (a, a) -> String
formatProgress (a
current, a
total)
| a
total a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
0 = a -> String
forall a. Show a => a -> String
show a
current
| Bool
otherwise = a -> String
forall a. Show a => a -> String
show a
current String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"/" String -> String -> String
forall a. [a] -> [a] -> [a]
++ a -> String
forall a. Show a => a -> String
show a
total
progress :: Formatter
progress :: Formatter
progress = Formatter
silent {
exampleSucceeded :: Path -> String -> FormatM ()
exampleSucceeded = \Path
_ String
_ -> FormatM () -> FormatM ()
forall a. FormatM a -> FormatM a
withSuccessColor (FormatM () -> FormatM ()) -> FormatM () -> FormatM ()
forall a b. (a -> b) -> a -> b
$ String -> FormatM ()
write String
"."
, exampleFailed :: Path -> String -> FailureReason -> FormatM ()
exampleFailed = \Path
_ String
_ FailureReason
_ -> FormatM () -> FormatM ()
forall a. FormatM a -> FormatM a
withFailColor (FormatM () -> FormatM ()) -> FormatM () -> FormatM ()
forall a b. (a -> b) -> a -> b
$ String -> FormatM ()
write String
"F"
, examplePending :: Path -> String -> Maybe String -> FormatM ()
examplePending = \Path
_ String
_ Maybe String
_ -> FormatM () -> FormatM ()
forall a. FormatM a -> FormatM a
withPendingColor (FormatM () -> FormatM ()) -> FormatM () -> FormatM ()
forall a b. (a -> b) -> a -> b
$ String -> FormatM ()
write String
"."
, failedFormatter :: FormatM ()
failedFormatter = FormatM ()
defaultFailedFormatter
, footerFormatter :: FormatM ()
footerFormatter = FormatM ()
defaultFooter
}
failed_examples :: Formatter
failed_examples :: Formatter
failed_examples = Formatter
silent {
failedFormatter :: FormatM ()
failedFormatter = FormatM ()
defaultFailedFormatter
, footerFormatter :: FormatM ()
footerFormatter = FormatM ()
defaultFooter
}
defaultFailedFormatter :: FormatM ()
defaultFailedFormatter :: FormatM ()
defaultFailedFormatter = do
String -> FormatM ()
writeLine String
""
[FailureRecord]
failures <- FormatM [FailureRecord]
getFailMessages
Bool -> FormatM () -> FormatM ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless ([FailureRecord] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [FailureRecord]
failures) (FormatM () -> FormatM ()) -> FormatM () -> FormatM ()
forall a b. (a -> b) -> a -> b
$ do
String -> FormatM ()
writeLine String
"Failures:"
String -> FormatM ()
writeLine String
""
[(Int, FailureRecord)]
-> ((Int, FailureRecord) -> FormatM ()) -> FormatM ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ ([Int] -> [FailureRecord] -> [(Int, FailureRecord)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Int
1..] [FailureRecord]
failures) (((Int, FailureRecord) -> FormatM ()) -> FormatM ())
-> ((Int, FailureRecord) -> FormatM ()) -> FormatM ()
forall a b. (a -> b) -> a -> b
$ \(Int, FailureRecord)
x -> do
(Int, FailureRecord) -> FormatM ()
formatFailure (Int, FailureRecord)
x
String -> FormatM ()
writeLine String
""
String -> FormatM ()
write String
"Randomized with seed " FormatM () -> Free FormatF Integer -> Free FormatF Integer
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Free FormatF Integer
usedSeed Free FormatF Integer -> (Integer -> FormatM ()) -> FormatM ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= String -> FormatM ()
writeLine (String -> FormatM ())
-> (Integer -> String) -> Integer -> FormatM ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> String
forall a. Show a => a -> String
show
String -> FormatM ()
writeLine String
""
where
formatFailure :: (Int, FailureRecord) -> FormatM ()
formatFailure :: (Int, FailureRecord) -> FormatM ()
formatFailure (Int
n, FailureRecord Maybe Location
mLoc Path
path FailureReason
reason) = do
Maybe Location -> (Location -> FormatM ()) -> FormatM ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ Maybe Location
mLoc ((Location -> FormatM ()) -> FormatM ())
-> (Location -> FormatM ()) -> FormatM ()
forall a b. (a -> b) -> a -> b
$ \Location
loc -> do
FormatM () -> FormatM ()
forall a. FormatM a -> FormatM a
withInfoColor (FormatM () -> FormatM ()) -> FormatM () -> FormatM ()
forall a b. (a -> b) -> a -> b
$ String -> FormatM ()
writeLine (Location -> String
formatLoc Location
loc)
String -> FormatM ()
write (String
" " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
n String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
") ")
String -> FormatM ()
writeLine (Path -> String
formatRequirement Path
path)
case FailureReason
reason of
FailureReason
NoReason -> () -> FormatM ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
Reason String
err -> FormatM () -> FormatM ()
forall a. FormatM a -> FormatM a
withFailColor (FormatM () -> FormatM ()) -> FormatM () -> FormatM ()
forall a b. (a -> b) -> a -> b
$ String -> FormatM ()
indent String
err
ExpectedButGot Maybe String
preface String
expected String
actual -> do
(String -> FormatM ()) -> Maybe String -> FormatM ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ String -> FormatM ()
indent Maybe String
preface
Bool
b <- FormatM Bool
useDiff
let threshold :: Seconds
threshold = Seconds
2 :: Seconds
Maybe [Diff]
mchunks <- IO (Maybe [Diff]) -> Free FormatF (Maybe [Diff])
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe [Diff]) -> Free FormatF (Maybe [Diff]))
-> IO (Maybe [Diff]) -> Free FormatF (Maybe [Diff])
forall a b. (a -> b) -> a -> b
$ if Bool
b
then Seconds -> IO [Diff] -> IO (Maybe [Diff])
forall a. Seconds -> IO a -> IO (Maybe a)
timeout Seconds
threshold ([Diff] -> IO [Diff]
forall a. a -> IO a
evaluate ([Diff] -> IO [Diff]) -> [Diff] -> IO [Diff]
forall a b. (a -> b) -> a -> b
$ String -> String -> [Diff]
diff String
expected String
actual)
else Maybe [Diff] -> IO (Maybe [Diff])
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe [Diff]
forall a. Maybe a
Nothing
case Maybe [Diff]
mchunks of
Just [Diff]
chunks -> do
[Diff]
-> (String -> FormatM ()) -> (String -> FormatM ()) -> FormatM ()
forall (t :: * -> *).
Foldable t =>
t Diff
-> (String -> FormatM ()) -> (String -> FormatM ()) -> FormatM ()
writeDiff [Diff]
chunks String -> FormatM ()
extraChunk String -> FormatM ()
missingChunk
Maybe [Diff]
Nothing -> do
[Diff]
-> (String -> FormatM ()) -> (String -> FormatM ()) -> FormatM ()
forall (t :: * -> *).
Foldable t =>
t Diff
-> (String -> FormatM ()) -> (String -> FormatM ()) -> FormatM ()
writeDiff [String -> Diff
First String
expected, String -> Diff
Second String
actual] String -> FormatM ()
write String -> FormatM ()
write
where
indented :: (String -> Free FormatF a) -> String -> Free FormatF a
indented String -> Free FormatF a
output String
text = case (Char -> Bool) -> String -> (String, String)
forall a. (a -> Bool) -> [a] -> ([a], [a])
break (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'\n') String
text of
(String
xs, String
"") -> String -> Free FormatF a
output String
xs
(String
xs, Char
_ : String
ys) -> String -> Free FormatF a
output (String
xs String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"\n") Free FormatF a -> FormatM () -> FormatM ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> String -> FormatM ()
write (String
indentation String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" ") FormatM () -> Free FormatF a -> Free FormatF a
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> (String -> Free FormatF a) -> String -> Free FormatF a
indented String -> Free FormatF a
output String
ys
writeDiff :: t Diff
-> (String -> FormatM ()) -> (String -> FormatM ()) -> FormatM ()
writeDiff t Diff
chunks String -> FormatM ()
extra String -> FormatM ()
missing = do
FormatM () -> FormatM ()
forall a. FormatM a -> FormatM a
withFailColor (FormatM () -> FormatM ()) -> FormatM () -> FormatM ()
forall a b. (a -> b) -> a -> b
$ String -> FormatM ()
write (String
indentation String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"expected: ")
t Diff -> (Diff -> FormatM ()) -> FormatM ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ t Diff
chunks ((Diff -> FormatM ()) -> FormatM ())
-> (Diff -> FormatM ()) -> FormatM ()
forall a b. (a -> b) -> a -> b
$ \ Diff
chunk -> case Diff
chunk of
Both String
a -> (String -> FormatM ()) -> String -> FormatM ()
forall a. (String -> Free FormatF a) -> String -> Free FormatF a
indented String -> FormatM ()
write String
a
First String
a -> (String -> FormatM ()) -> String -> FormatM ()
forall a. (String -> Free FormatF a) -> String -> Free FormatF a
indented String -> FormatM ()
extra String
a
Second String
_ -> () -> FormatM ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
String -> FormatM ()
writeLine String
""
FormatM () -> FormatM ()
forall a. FormatM a -> FormatM a
withFailColor (FormatM () -> FormatM ()) -> FormatM () -> FormatM ()
forall a b. (a -> b) -> a -> b
$ String -> FormatM ()
write (String
indentation String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" but got: ")
t Diff -> (Diff -> FormatM ()) -> FormatM ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ t Diff
chunks ((Diff -> FormatM ()) -> FormatM ())
-> (Diff -> FormatM ()) -> FormatM ()
forall a b. (a -> b) -> a -> b
$ \ Diff
chunk -> case Diff
chunk of
Both String
a -> (String -> FormatM ()) -> String -> FormatM ()
forall a. (String -> Free FormatF a) -> String -> Free FormatF a
indented String -> FormatM ()
write String
a
First String
_ -> () -> FormatM ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
Second String
a -> (String -> FormatM ()) -> String -> FormatM ()
forall a. (String -> Free FormatF a) -> String -> Free FormatF a
indented String -> FormatM ()
missing String
a
String -> FormatM ()
writeLine String
""
Error Maybe String
_ SomeException
e -> FormatM () -> FormatM ()
forall a. FormatM a -> FormatM a
withFailColor (FormatM () -> FormatM ())
-> (String -> FormatM ()) -> String -> FormatM ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> FormatM ()
indent (String -> FormatM ()) -> String -> FormatM ()
forall a b. (a -> b) -> a -> b
$ ((String
"uncaught exception: " String -> String -> String
forall a. [a] -> [a] -> [a]
++) (String -> String)
-> (SomeException -> String) -> SomeException -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SomeException -> String
formatException) SomeException
e
String -> FormatM ()
writeLine String
""
String -> FormatM ()
writeLine (String
" To rerun use: --match " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> String
forall a. Show a => a -> String
show (Path -> String
joinPath Path
path))
where
indentation :: String
indentation = String
" "
indent :: String -> FormatM ()
indent String
message = do
[String] -> (String -> FormatM ()) -> FormatM ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ (String -> [String]
lines String
message) ((String -> FormatM ()) -> FormatM ())
-> (String -> FormatM ()) -> FormatM ()
forall a b. (a -> b) -> a -> b
$ \String
line -> do
String -> FormatM ()
writeLine (String
indentation String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
line)
formatLoc :: Location -> String
formatLoc (Location String
file Int
line Int
column) = String
" " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
file String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
":" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
line String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
":" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
column String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
": "
defaultFooter :: FormatM ()
= do
String -> FormatM ()
writeLine (String -> FormatM ()) -> Free FormatF String -> FormatM ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< String -> String -> String
forall a. [a] -> [a] -> [a]
(++)
(String -> String -> String)
-> Free FormatF String -> Free FormatF (String -> String)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (String -> Seconds -> String
forall r. PrintfType r => String -> r
printf String
"Finished in %1.4f seconds" (Seconds -> String) -> Free FormatF Seconds -> Free FormatF String
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Free FormatF Seconds
getRealTime)
Free FormatF (String -> String)
-> Free FormatF String -> Free FormatF String
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (String -> (Seconds -> String) -> Maybe Seconds -> String
forall b a. b -> (a -> b) -> Maybe a -> b
maybe String
"" (String -> Seconds -> String
forall r. PrintfType r => String -> r
printf String
", used %1.4f seconds of CPU time") (Maybe Seconds -> String)
-> Free FormatF (Maybe Seconds) -> Free FormatF String
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Free FormatF (Maybe Seconds)
getCPUTime)
Int
fails <- FormatM Int
getFailCount
Int
pending <- FormatM Int
getPendingCount
Int
total <- FormatM Int
getTotalCount
let
output :: String
output =
Int -> String -> String
pluralize Int
total String
"example"
String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
", " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String -> String
pluralize Int
fails String
"failure"
String -> String -> String
forall a. [a] -> [a] -> [a]
++ if Int
pending Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 then String
"" else String
", " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
pending String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" pending"
c :: FormatM a -> FormatM a
c | Int
fails Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= Int
0 = FormatM a -> FormatM a
forall a. FormatM a -> FormatM a
withFailColor
| Int
pending Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= Int
0 = FormatM a -> FormatM a
forall a. FormatM a -> FormatM a
withPendingColor
| Bool
otherwise = FormatM a -> FormatM a
forall a. FormatM a -> FormatM a
withSuccessColor
FormatM () -> FormatM ()
forall a. FormatM a -> FormatM a
c (FormatM () -> FormatM ()) -> FormatM () -> FormatM ()
forall a b. (a -> b) -> a -> b
$ String -> FormatM ()
writeLine String
output