{-# LANGUAGE CPP #-}
-- |
-- Stability: experimental
--
-- This module contains formatters that can be used with
-- `Test.Hspec.Runner.hspecWith`.
module Test.Hspec.Core.Formatters (

-- * Formatters
  silent
, specdoc
, progress
, failed_examples

-- * Implementing a custom Formatter
-- |
-- A formatter is a set of actions.  Each action is evaluated when a certain
-- situation is encountered during a test run.
--
-- Actions live in the `FormatM` monad.  It provides access to the runner state
-- and primitives for appending to the generated report.
, Formatter (..)
, FailureReason (..)
, FormatM

-- ** Accessing the runner state
, getSuccessCount
, getPendingCount
, getFailCount
, getTotalCount

, FailureRecord (..)
, getFailMessages
, usedSeed

, Seconds(..)
, getCPUTime
, getRealTime

-- ** Appending to the generated report
, write
, writeLine
, writeTransient

-- ** Dealing with colors
, withInfoColor
, withSuccessColor
, withPendingColor
, withFailColor

, useDiff
, extraChunk
, missingChunk

-- ** Helpers
, formatException
) where

import           Prelude ()
import           Test.Hspec.Core.Compat hiding (First)

import           Data.Maybe
import           Test.Hspec.Core.Util
import           Test.Hspec.Core.Spec (Location(..))
import           Text.Printf

-- We use an explicit import list for "Test.Hspec.Formatters.Internal", to make
-- sure, that we only use the public API to implement formatters.
--
-- Everything imported here has to be re-exported, so that users can implement
-- their own formatters.
import Test.Hspec.Core.Formatters.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.Clock (Seconds(..))

import           Test.Hspec.Core.Formatters.Diff

silent :: Formatter
silent :: Formatter
silent = Formatter :: FormatM ()
-> ([String] -> String -> FormatM ())
-> 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 = \_ _ -> () -> FormatM ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
, exampleGroupDone :: FormatM ()
exampleGroupDone    = () -> FormatM ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
, exampleProgress :: Path -> Progress -> FormatM ()
exampleProgress     = \_ _ -> () -> FormatM ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
, exampleSucceeded :: Path -> String -> FormatM ()
exampleSucceeded    = \ _ _ -> () -> FormatM ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
, exampleFailed :: Path -> String -> FailureReason -> FormatM ()
exampleFailed       = \_ _ _ -> () -> FormatM ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
, examplePending :: Path -> String -> Maybe String -> FormatM ()
examplePending      = \_ _ _ -> () -> 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 ()
}

specdoc :: Formatter
specdoc :: Formatter
specdoc = Formatter
silent {

  headerFormatter :: FormatM ()
headerFormatter = do
    String -> FormatM ()
writeLine ""

, exampleGroupStarted :: [String] -> String -> FormatM ()
exampleGroupStarted = \nesting :: [String]
nesting name :: 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 = \_ p :: 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 = \(nesting :: [String]
nesting, requirement :: String
requirement) info :: 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
$ \ s :: 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]
forall a. a -> [a] -> [a]
: [String]
nesting) String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
s

, exampleFailed :: Path -> String -> FailureReason -> FormatM ()
exampleFailed = \(nesting :: [String]
nesting, requirement :: String
requirement) info :: String
info _ -> 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]
++ " 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 -> 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
$ \ s :: 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]
forall a. a -> [a] -> [a]
: [String]
nesting) String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
s

, examplePending :: Path -> String -> Maybe String -> FormatM ()
examplePending = \(nesting :: [String]
nesting, requirement :: String
requirement) info :: String
info reason :: 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
$ \ s :: 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]
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]
forall a. a -> [a] -> [a]
: [String]
nesting) String -> String -> String
forall a. [a] -> [a] -> [a]
++ "# PENDING: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> Maybe String -> String
forall a. a -> Maybe a -> a
fromMaybe "No reason given" Maybe String
reason

, failedFormatter :: FormatM ()
failedFormatter = FormatM ()
defaultFailedFormatter

, footerFormatter :: FormatM ()
footerFormatter = FormatM ()
defaultFooter
} where
    indentationFor :: t a -> String
indentationFor nesting :: 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
* 2) ' '
    formatProgress :: (a, a) -> String
formatProgress (current :: a
current, total :: a
total)
      | a
total a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== 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
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 = \_ _ -> FormatM () -> FormatM ()
forall a. FormatM a -> FormatM a
withSuccessColor (FormatM () -> FormatM ()) -> FormatM () -> FormatM ()
forall a b. (a -> b) -> a -> b
$ String -> FormatM ()
write "."
, exampleFailed :: Path -> String -> FailureReason -> FormatM ()
exampleFailed    = \_ _ _ -> FormatM () -> FormatM ()
forall a. FormatM a -> FormatM a
withFailColor    (FormatM () -> FormatM ()) -> FormatM () -> FormatM ()
forall a b. (a -> b) -> a -> b
$ String -> FormatM ()
write "F"
, examplePending :: Path -> String -> Maybe String -> FormatM ()
examplePending   = \_ _ _ -> FormatM () -> FormatM ()
forall a. FormatM a -> FormatM a
withPendingColor (FormatM () -> FormatM ()) -> FormatM () -> FormatM ()
forall a b. (a -> b) -> a -> b
$ String -> FormatM ()
write "."
, 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 ""

  [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 "Failures:"
    String -> FormatM ()
writeLine ""

    [(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 [1..] [FailureRecord]
failures) (((Int, FailureRecord) -> FormatM ()) -> FormatM ())
-> ((Int, FailureRecord) -> FormatM ()) -> FormatM ()
forall a b. (a -> b) -> a -> b
$ \x :: (Int, FailureRecord)
x -> do
      (Int, FailureRecord) -> FormatM ()
formatFailure (Int, FailureRecord)
x
      String -> FormatM ()
writeLine ""

#if __GLASGOW_HASKELL__ == 800
    withFailColor $ do
      writeLine "WARNING:"
      writeLine "  Your version of GHC is affected by https://ghc.haskell.org/trac/ghc/ticket/13285."
      writeLine "  Source locations may not work as expected."
      writeLine ""
      writeLine "  Please consider upgrading GHC!"
      writeLine ""
#endif

    String -> FormatM ()
write "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 ""
  where
    formatFailure :: (Int, FailureRecord) -> FormatM ()
    formatFailure :: (Int, FailureRecord) -> FormatM ()
formatFailure (n :: Int
n, FailureRecord mLoc :: Maybe Location
mLoc path :: Path
path reason :: 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
$ \loc :: 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
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 -> FormatM ()
writeLine (Path -> String
formatRequirement Path
path)
      case FailureReason
reason of
        NoReason -> () -> FormatM ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
        Reason err :: 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 preface :: Maybe String
preface expected :: String
expected actual :: 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
            chunks :: [Diff String]
chunks
              | Bool
b = String -> String -> [Diff String]
diff String
expected String
actual
              | Bool
otherwise = [String -> Diff String
forall a. a -> Diff a
First String
expected, String -> Diff String
forall a. a -> Diff a
Second String
actual]

          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]
++ "expected: ")
          [Diff String] -> (Diff String -> FormatM ()) -> FormatM ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ [Diff String]
chunks ((Diff String -> FormatM ()) -> FormatM ())
-> (Diff String -> FormatM ()) -> FormatM ()
forall a b. (a -> b) -> a -> b
$ \chunk :: Diff String
chunk -> case Diff String
chunk of
            Both a :: String
a _ -> (String -> FormatM ()) -> String -> FormatM ()
forall a. (String -> Free FormatF a) -> String -> Free FormatF a
indented String -> FormatM ()
write String
a
            First a :: String
a -> (String -> FormatM ()) -> String -> FormatM ()
forall a. (String -> Free FormatF a) -> String -> Free FormatF a
indented String -> FormatM ()
extraChunk String
a
            Second _ -> () -> FormatM ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
          String -> FormatM ()
writeLine ""

          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]
++ " but got: ")
          [Diff String] -> (Diff String -> FormatM ()) -> FormatM ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ [Diff String]
chunks ((Diff String -> FormatM ()) -> FormatM ())
-> (Diff String -> FormatM ()) -> FormatM ()
forall a b. (a -> b) -> a -> b
$ \chunk :: Diff String
chunk -> case Diff String
chunk of
            Both a :: String
a _ -> (String -> FormatM ()) -> String -> FormatM ()
forall a. (String -> Free FormatF a) -> String -> Free FormatF a
indented String -> FormatM ()
write String
a
            First _ -> () -> FormatM ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
            Second a :: String
a -> (String -> FormatM ()) -> String -> FormatM ()
forall a. (String -> Free FormatF a) -> String -> Free FormatF a
indented String -> FormatM ()
missingChunk String
a
          String -> FormatM ()
writeLine ""
          where
            indented :: (String -> Free FormatF a) -> String -> Free FormatF a
indented output :: String -> Free FormatF a
output text :: 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
== '\n') String
text of
              (xs :: String
xs, "") -> String -> Free FormatF a
output String
xs
              (xs :: String
xs, _ : ys :: String
ys) -> String -> Free FormatF a
output (String
xs String -> String -> String
forall a. [a] -> [a] -> [a]
++ "\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]
++ "          ") 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
        Error _ e :: 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
$ (("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 -> FormatM ()
writeLine ("  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 = "       "
        indent :: String -> FormatM ()
indent message :: 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
$ \line :: String
line -> do
            String -> FormatM ()
writeLine (String
indentation String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
line)
        formatLoc :: Location -> String
formatLoc (Location file :: String
file line :: Int
line column :: Int
column) = "  " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
file String -> String -> String
forall a. [a] -> [a] -> [a]
++ ":" 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
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
column String -> String -> String
forall a. [a] -> [a] -> [a]
++ ": "

defaultFooter :: FormatM ()
defaultFooter :: FormatM ()
defaultFooter = 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 "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 -> Seconds -> String
forall r. PrintfType r => String -> r
printf ", 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   "example"
      String -> String -> String
forall a. [a] -> [a] -> [a]
++ ", " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String -> String
pluralize Int
fails "failure"
      String -> String -> String
forall a. [a] -> [a] -> [a]
++ if Int
pending Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== 0 then "" else ", " 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]
++ " pending"
    c :: FormatM a -> FormatM a
c | Int
fails Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= 0   = FormatM a -> FormatM a
forall a. FormatM a -> FormatM a
withFailColor
      | Int
pending Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= 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