Copyright | (c) 2015-2017 Rudy Matela |
---|---|
License | 3-Clause BSD (see the file LICENSE) |
Maintainer | Rudy Matela <rudy@matela.com.br> |
Safe Haskell | None |
Language | Haskell2010 |
Exports "main" functions for FitSpec.
They work exactly by report
and reportWith
but can be customized by
command line arguments.
main = mainWith args { ... } functions properties
Synopsis
- mainWith :: (Mutable a, ShowMutable a) => Args -> a -> (a -> [Property]) -> IO ()
- defaultMain :: (Mutable a, ShowMutable a) => a -> (a -> [Property]) -> IO ()
- getArgs :: IO Args
- getArgsWith :: Args -> IO Args
- module Test.FitSpec.Report
Documentation
mainWith :: (Mutable a, ShowMutable a) => Args -> a -> (a -> [Property]) -> IO () Source #
Same as reportWith
, but allow overriding of configuration via command
line arguments.
defaultMain :: (Mutable a, ShowMutable a) => a -> (a -> [Property]) -> IO () Source #
Same as report
, but allow configuration via command line arguments.
module Test.FitSpec.Report
Orphan instances
Data Args Source # | |
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Args -> c Args # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Args # dataTypeOf :: Args -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Args) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Args) # gmapT :: (forall b. Data b => b -> b) -> Args -> Args # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Args -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Args -> r # gmapQ :: (forall d. Data d => d -> u) -> Args -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Args -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Args -> m Args # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Args -> m Args # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Args -> m Args # | |
Data ShowMutantAs Source # | |
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ShowMutantAs -> c ShowMutantAs # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ShowMutantAs # toConstr :: ShowMutantAs -> Constr # dataTypeOf :: ShowMutantAs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ShowMutantAs) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ShowMutantAs) # gmapT :: (forall b. Data b => b -> b) -> ShowMutantAs -> ShowMutantAs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ShowMutantAs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ShowMutantAs -> r # gmapQ :: (forall d. Data d => d -> u) -> ShowMutantAs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ShowMutantAs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ShowMutantAs -> m ShowMutantAs # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ShowMutantAs -> m ShowMutantAs # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ShowMutantAs -> m ShowMutantAs # |