Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Fuzz testing for math programming backends.
Synopsis
- newtype Variable = Variable Int
- newtype Constraint = Constraint Int
- newtype Objective = Objective Int
- data LPAction
- newtype LPActions = LPActions [LPAction]
- data LPState v c o = LPState {
- _variables :: Map Variable v
- _variableNames :: Map Variable Text
- _constraints :: Map Constraint c
- _constraintNames :: Map Constraint Text
- _objectives :: Map Objective o
- _objectiveNames :: Map Objective Text
- _pending :: [LPAction]
- _randomGen :: IOGenM StdGen
- variables :: forall v c o v. Lens (LPState v c o) (LPState v c o) (Map Variable v) (Map Variable v)
- variableNames :: forall v c o. Lens' (LPState v c o) (Map Variable Text)
- randomGen :: forall v c o. Lens' (LPState v c o) (IOGenM StdGen)
- pending :: forall v c o. Lens' (LPState v c o) [LPAction]
- objectives :: forall v c o o. Lens (LPState v c o) (LPState v c o) (Map Objective o) (Map Objective o)
- objectiveNames :: forall v c o. Lens' (LPState v c o) (Map Objective Text)
- constraints :: forall v c o c. Lens (LPState v c o) (LPState v c o) (Map Constraint c) (Map Constraint c)
- constraintNames :: forall v c o. Lens' (LPState v c o) (Map Constraint Text)
- initLPState :: Int -> [LPAction] -> IO (LPState v c o)
- type LPFuzz v c o m = (MonadState (LPState v c o) m, MonadLP v c o m, MonadWriter (Seq String) m, MonadIO m)
- evalPending :: LPFuzz v c o m => m ()
- evalAction :: LPFuzz v c o m => LPAction -> m ()
- evalAction' :: LPFuzz v c o m => LPAction -> m ()
- add :: (LPFuzz v c o m, Ord k) => k -> m a -> ASetter' (LPState v c o) (Map k a) -> m ()
- addThenRemove :: (LPFuzz v c o m, Ord k) => k -> m a -> (a -> m ()) -> Lens' (LPState v c o) (Map k a) -> m ()
- makeConstraint :: LPFuzz v c o m => m c
- chooseExpr :: LPFuzz v c o m => m (Expr v)
- chooseInequality :: LPFuzz v c o m => m (Expr v -> Expr v -> m c)
- makeObjective :: LPFuzz v c o m => m o
- makeFuzzTests :: (MonadIO m, MonadLP v c o m) => (m (Seq String) -> IO ()) -> Spec
Documentation
newtype Constraint Source #
Instances
Show Constraint Source # | |
Defined in Math.Programming.Tests.Fuzz showsPrec :: Int -> Constraint -> ShowS # show :: Constraint -> String # showList :: [Constraint] -> ShowS # | |
Eq Constraint Source # | |
Defined in Math.Programming.Tests.Fuzz (==) :: Constraint -> Constraint -> Bool # (/=) :: Constraint -> Constraint -> Bool # | |
Ord Constraint Source # | |
Defined in Math.Programming.Tests.Fuzz compare :: Constraint -> Constraint -> Ordering # (<) :: Constraint -> Constraint -> Bool # (<=) :: Constraint -> Constraint -> Bool # (>) :: Constraint -> Constraint -> Bool # (>=) :: Constraint -> Constraint -> Bool # max :: Constraint -> Constraint -> Constraint # min :: Constraint -> Constraint -> Constraint # |
The types of actions we can perform on a linear program
Instances
LPState | |
|
variables :: forall v c o v. Lens (LPState v c o) (LPState v c o) (Map Variable v) (Map Variable v) Source #
objectives :: forall v c o o. Lens (LPState v c o) (LPState v c o) (Map Objective o) (Map Objective o) Source #
constraints :: forall v c o c. Lens (LPState v c o) (LPState v c o) (Map Constraint c) (Map Constraint c) Source #
constraintNames :: forall v c o. Lens' (LPState v c o) (Map Constraint Text) Source #
type LPFuzz v c o m = (MonadState (LPState v c o) m, MonadLP v c o m, MonadWriter (Seq String) m, MonadIO m) Source #
evalPending :: LPFuzz v c o m => m () Source #
evalAction :: LPFuzz v c o m => LPAction -> m () Source #
evalAction' :: LPFuzz v c o m => LPAction -> m () Source #
addThenRemove :: (LPFuzz v c o m, Ord k) => k -> m a -> (a -> m ()) -> Lens' (LPState v c o) (Map k a) -> m () Source #
makeConstraint :: LPFuzz v c o m => m c Source #
chooseExpr :: LPFuzz v c o m => m (Expr v) Source #
chooseInequality :: LPFuzz v c o m => m (Expr v -> Expr v -> m c) Source #
makeObjective :: LPFuzz v c o m => m o Source #