doctest-parallel-0.3.1: Test interactive Haskell examples
Safe HaskellSafe-Inferred
LanguageHaskell2010

Test.DocTest.Internal.Options

Synopsis

Documentation

data Result a Source #

Instances

Instances details
Functor Result Source # 
Instance details

Defined in Test.DocTest.Internal.Options

Methods

fmap :: (a -> b) -> Result a -> Result b #

(<$) :: a -> Result b -> Result a #

Show a => Show (Result a) Source # 
Instance details

Defined in Test.DocTest.Internal.Options

Methods

showsPrec :: Int -> Result a -> ShowS #

show :: Result a -> String #

showList :: [Result a] -> ShowS #

Eq a => Eq (Result a) Source # 
Instance details

Defined in Test.DocTest.Internal.Options

Methods

(==) :: Result a -> Result a -> Bool #

(/=) :: Result a -> Result a -> Bool #

data Config Source #

Constructors

Config 

Fields

Instances

Instances details
Generic Config Source # 
Instance details

Defined in Test.DocTest.Internal.Options

Associated Types

type Rep Config :: Type -> Type #

Methods

from :: Config -> Rep Config x #

to :: Rep Config x -> Config #

Show Config Source # 
Instance details

Defined in Test.DocTest.Internal.Options

NFData Config Source # 
Instance details

Defined in Test.DocTest.Internal.Options

Methods

rnf :: Config -> () #

Eq Config Source # 
Instance details

Defined in Test.DocTest.Internal.Options

Methods

(==) :: Config -> Config -> Bool #

(/=) :: Config -> Config -> Bool #

type Rep Config Source # 
Instance details

Defined in Test.DocTest.Internal.Options

data ModuleConfig Source #

Constructors

ModuleConfig 

Fields

Instances

Instances details
Generic ModuleConfig Source # 
Instance details

Defined in Test.DocTest.Internal.Options

Associated Types

type Rep ModuleConfig :: Type -> Type #

Show ModuleConfig Source # 
Instance details

Defined in Test.DocTest.Internal.Options

NFData ModuleConfig Source # 
Instance details

Defined in Test.DocTest.Internal.Options

Methods

rnf :: ModuleConfig -> () #

Eq ModuleConfig Source # 
Instance details

Defined in Test.DocTest.Internal.Options

type Rep ModuleConfig Source # 
Instance details

Defined in Test.DocTest.Internal.Options

type Rep ModuleConfig = D1 ('MetaData "ModuleConfig" "Test.DocTest.Internal.Options" "doctest-parallel-0.3.1-inplace" 'False) (C1 ('MetaCons "ModuleConfig" 'PrefixI 'True) ((S1 ('MetaSel ('Just "cfgPreserveIt") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "cfgRandomizeOrder") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)) :*: (S1 ('MetaSel ('Just "cfgSeed") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)) :*: S1 ('MetaSel ('Just "cfgImplicitModuleImport") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))))

parseGhcArg :: String -> Maybe String Source #

Parse ghc-arg argument

>>> parseGhcArg "--ghc-arg=foobar"
Just "foobar"

parseSeed :: String -> Maybe Int Source #

Parse seed argument

>>> parseSeed "--seed=6"
Just 6
>>> parseSeed "--seeeed=6"
Nothing

parseLogLevel :: String -> Maybe LogLevel Source #

Parse seed argument

>>> parseLogLevel "--log-level=Debug"
Just Debug
>>> parseLogLevel "--log-level=debug"
Just Debug
>>> parseSeed "---log-level=debug"
Nothing

parseThreads :: String -> Maybe Int Source #

Parse number of threads argument

>>> parseThreads "-j6"
Just 6
>>> parseThreads "-j-2"
Nothing
>>> parseThreads "-jA"
Nothing

parseSpecificFlag :: String -> String -> Maybe String Source #

Parse a specific flag with a value, or return Nothing

>>> parseSpecificFlag "--foo" "foo"
Nothing
>>> parseSpecificFlag "--foo=" "foo"
Nothing
>>> parseSpecificFlag "--foo=5" "foo"
Just "5"
>>> parseSpecificFlag "--foo=5" "bar"
Nothing

parseFlag :: String -> (String, Maybe String) Source #

Parse a flag into its flag and argument component.

Example:

>>> parseFlag "--optghc=foo"
("--optghc",Just "foo")
>>> parseFlag "--optghc="
("--optghc",Nothing)
>>> parseFlag "--fast"
("--fast",Nothing)