Copyright | (c) 2016-2019 Rudy Matela |
---|---|
License | 3-Clause BSD (see the file LICENSE) |
Maintainer | Rudy Matela <rudy@matela.com.br> |
Safe Haskell | None |
Language | Haskell2010 |
This module is part o Speculate.
Arguments to the speculate
function and parsing of command line arguments.
Synopsis
- data Args = Args {
- maxSize :: Int
- maxTests :: Int
- constants :: [Expr]
- instances :: [Instances]
- maxSemiSize :: Int
- maxCondSize :: Int
- maxVars :: Int
- showConstants :: Bool
- showEquations :: Bool
- showSemiequations :: Bool
- showConditions :: Bool
- showConstantLaws :: Bool
- autoConstants :: Bool
- minTests :: Int -> Int
- maxConstants :: Maybe Int
- maxDepth :: Maybe Int
- showCounts :: Bool
- showTheory :: Bool
- showArgs :: Bool
- showHelp :: Bool
- evalTimeout :: Maybe Double
- force :: Bool
- extra :: [String]
- exclude :: [String]
- onlyTypes :: [String]
- showClassesFor :: [Int]
- showDot :: Bool
- quietDot :: Bool
- args :: Args
- constant :: Typeable a => String -> a -> Expr
- showConstant :: (Typeable a, Show a) => a -> Expr
- foreground :: Expr
- background :: Expr
- getArgs :: Args -> IO Args
- computeMaxSemiSize :: Args -> Int
- computeMaxCondSize :: Args -> Int
- computeInstances :: Args -> Instances
- types :: Args -> [TypeRep]
- atoms :: Args -> [[Expr]]
- keepExpr :: Args -> Expr -> Bool
- timeout :: Args -> Bool -> Bool
- shouldShowEquation :: Args -> (Expr, Expr) -> Bool
- shouldShowConditionalEquation :: Args -> (Expr, Expr, Expr) -> Bool
- reallyShowConditions :: Args -> Bool
- foregroundConstants :: Args -> [Expr]
- backgroundConstants :: Args -> [Expr]
- about :: Expr -> [Expr] -> Bool
- allAbout :: Expr -> [Expr] -> Bool
- prepareArgs :: Args -> Mode Args
- module System.Console.CmdArgs.Explicit
Documentation
Arguments to Speculate
Args | |
|
foreground :: Expr Source #
A special Expr
value.
When provided on the constants
list,
makes all the following constants foreground
constants.
background :: Expr Source #
A special Expr
value.
When provided on the constants
list,
makes all the following constants background
constants.
Background constants can appear in laws about other constants, but not by
themselves.
computeMaxSemiSize :: Args -> Int Source #
computeMaxCondSize :: Args -> Int Source #
computeInstances :: Args -> Instances Source #
reallyShowConditions :: Args -> Bool Source #
foregroundConstants :: Args -> [Expr] Source #
backgroundConstants :: Args -> [Expr] Source #