{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TypeApplications #-}
module Test.Mutagen.Test.Driver
(
mutagen
, mutagenVerbose
, mutagenVerboseReport
, mutagenReport
, mutagenWith
, mutagenWithReport
)
where
import Control.Monad (void)
import Test.Mutagen.Config (Config (..), defaultConfig)
import Test.Mutagen.Property (Testable (..))
import Test.Mutagen.Report (Report)
import Test.Mutagen.Test.Loop (loop)
import Test.Mutagen.Test.State (initMutagenState)
import Test.Mutagen.Test.Terminal (brickTUI, stdoutTUI, withTerminalT)
mutagen :: (Testable p) => p -> IO ()
mutagen :: forall p. Testable p => p -> IO ()
mutagen = Config -> p -> IO ()
forall p. Testable p => Config -> p -> IO ()
mutagenWith Config
defaultConfig
mutagenVerbose :: (Testable p) => p -> IO ()
mutagenVerbose :: forall p. Testable p => p -> IO ()
mutagenVerbose = Config -> p -> IO ()
forall p. Testable p => Config -> p -> IO ()
mutagenWith Config
defaultConfig{chatty = True}
mutagenVerboseReport :: (Testable p) => p -> IO Report
mutagenVerboseReport :: forall p. Testable p => p -> IO Report
mutagenVerboseReport = Config -> p -> IO Report
forall p. Testable p => Config -> p -> IO Report
mutagenWithReport Config
defaultConfig{chatty = True}
mutagenReport :: (Testable p) => p -> IO Report
mutagenReport :: forall p. Testable p => p -> IO Report
mutagenReport = Config -> p -> IO Report
forall p. Testable p => Config -> p -> IO Report
mutagenWithReport Config
defaultConfig
mutagenWith :: (Testable p) => Config -> p -> IO ()
mutagenWith :: forall p. Testable p => Config -> p -> IO ()
mutagenWith Config
cfg p
p = IO Report -> IO ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (Config -> p -> IO Report
forall p. Testable p => Config -> p -> IO Report
mutagenWithReport Config
cfg p
p)
mutagenWithReport :: (Testable p) => Config -> p -> IO Report
mutagenWithReport :: forall p. Testable p => Config -> p -> IO Report
mutagenWithReport Config
cfg p
p = do
st <- Config -> Property -> IO MutagenState
initMutagenState Config
cfg (p -> Property
forall a. Testable a => a -> Property
property p
p)
ui <- if tui cfg then brickTUI else stdoutTUI
withTerminalT ui (loop st)