module Test.Tasty.Providers.ConsoleFormat
( ResultDetailsPrinter(..)
, ConsoleFormat(..)
, ConsoleFormatPrinter
, noResultDetails
, failFormat
, infoFailFormat
, infoOkFormat
, okFormat
, skippedFormat
)
where
import System.Console.ANSI
data ConsoleFormat = ConsoleFormat
{ ConsoleFormat -> ConsoleIntensity
consoleIntensity :: ConsoleIntensity
, ConsoleFormat -> ColorIntensity
colorIntensity :: ColorIntensity
, ConsoleFormat -> Color
color :: Color
}
type ConsoleFormatPrinter
= ConsoleFormat
-> IO ()
-> IO ()
noResultDetails :: ResultDetailsPrinter
noResultDetails :: ResultDetailsPrinter
noResultDetails = (Int -> ConsoleFormatPrinter -> IO ()) -> ResultDetailsPrinter
ResultDetailsPrinter ((Int -> ConsoleFormatPrinter -> IO ()) -> ResultDetailsPrinter)
-> (IO () -> Int -> ConsoleFormatPrinter -> IO ())
-> IO ()
-> ResultDetailsPrinter
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ConsoleFormatPrinter -> IO ())
-> Int -> ConsoleFormatPrinter -> IO ()
forall a b. a -> b -> a
const ((ConsoleFormatPrinter -> IO ())
-> Int -> ConsoleFormatPrinter -> IO ())
-> (IO () -> ConsoleFormatPrinter -> IO ())
-> IO ()
-> Int
-> ConsoleFormatPrinter
-> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO () -> ConsoleFormatPrinter -> IO ()
forall a b. a -> b -> a
const (IO () -> ResultDetailsPrinter) -> IO () -> ResultDetailsPrinter
forall a b. (a -> b) -> a -> b
$ () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
newtype ResultDetailsPrinter = ResultDetailsPrinter
(Int -> ConsoleFormatPrinter -> IO ())
instance Show ResultDetailsPrinter where
show :: ResultDetailsPrinter -> String
show ResultDetailsPrinter
_printer = String
"ResultDetailsPrinter"
failFormat :: ConsoleFormat
failFormat :: ConsoleFormat
failFormat = ConsoleIntensity -> ColorIntensity -> Color -> ConsoleFormat
ConsoleFormat ConsoleIntensity
BoldIntensity ColorIntensity
Vivid Color
Red
infoFailFormat :: ConsoleFormat
infoFailFormat :: ConsoleFormat
infoFailFormat = ConsoleIntensity -> ColorIntensity -> Color -> ConsoleFormat
ConsoleFormat ConsoleIntensity
NormalIntensity ColorIntensity
Dull Color
Red
okFormat :: ConsoleFormat
okFormat :: ConsoleFormat
okFormat = ConsoleIntensity -> ColorIntensity -> Color -> ConsoleFormat
ConsoleFormat ConsoleIntensity
NormalIntensity ColorIntensity
Dull Color
Green
infoOkFormat :: ConsoleFormat
infoOkFormat :: ConsoleFormat
infoOkFormat = ConsoleIntensity -> ColorIntensity -> Color -> ConsoleFormat
ConsoleFormat ConsoleIntensity
NormalIntensity ColorIntensity
Dull Color
White
skippedFormat :: ConsoleFormat
skippedFormat :: ConsoleFormat
skippedFormat = ConsoleIntensity -> ColorIntensity -> Color -> ConsoleFormat
ConsoleFormat ConsoleIntensity
NormalIntensity ColorIntensity
Dull Color
Magenta