{-# OPTIONS_GHC -Wall #-}
{-# OPTIONS_HADDOCK show-extensions #-}
{-# LANGUAGE CPP #-}
module Numeric.Optimization.MIP.Base
(
Problem (..)
, Label
, Var
, toVar
, fromVar
, VarType (..)
, getVarType
, BoundExpr
, Extended (..)
, Bounds
, defaultBounds
, defaultLB
, defaultUB
, getBounds
, variables
, integerVariables
, semiContinuousVariables
, semiIntegerVariables
, Expr (..)
, varExpr
, constExpr
, terms
, Term (..)
, OptDir (..)
, ObjectiveFunction (..)
, Constraint (..)
, (.==.)
, (.<=.)
, (.>=.)
, RelOp (..)
, SOSType (..)
, SOSConstraint (..)
, Solution (..)
, Status (..)
, meetStatus
, FileOptions (..)
, Default (..)
, Variables (..)
, intersectBounds
) where
#if !MIN_VERSION_lattices(2,0,0)
import Algebra.Lattice
#endif
import Algebra.PartialOrd
import Control.Arrow ((***))
import Data.Default.Class
import Data.Map (Map)
import qualified Data.Map as Map
import Data.Set (Set)
import qualified Data.Set as Set
import Data.Interned (unintern)
import Data.Interned.Text
import Data.ExtendedReal
import Data.OptDir
import Data.String
import qualified Data.Text as T
import System.IO (TextEncoding)
infix 4 .<=., .>=., .==.
data Problem c
= Problem
{ forall c. Problem c -> Maybe Text
name :: Maybe T.Text
, forall c. Problem c -> ObjectiveFunction c
objectiveFunction :: ObjectiveFunction c
, forall c. Problem c -> [Constraint c]
constraints :: [Constraint c]
, forall c. Problem c -> [SOSConstraint c]
sosConstraints :: [SOSConstraint c]
, forall c. Problem c -> [Constraint c]
userCuts :: [Constraint c]
, forall c. Problem c -> Map Var VarType
varType :: Map Var VarType
, forall c. Problem c -> Map Var (Bounds c)
varBounds :: Map Var (Bounds c)
}
deriving (Int -> Problem c -> ShowS
[Problem c] -> ShowS
Problem c -> String
(Int -> Problem c -> ShowS)
-> (Problem c -> String)
-> ([Problem c] -> ShowS)
-> Show (Problem c)
forall c. Show c => Int -> Problem c -> ShowS
forall c. Show c => [Problem c] -> ShowS
forall c. Show c => Problem c -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall c. Show c => Int -> Problem c -> ShowS
showsPrec :: Int -> Problem c -> ShowS
$cshow :: forall c. Show c => Problem c -> String
show :: Problem c -> String
$cshowList :: forall c. Show c => [Problem c] -> ShowS
showList :: [Problem c] -> ShowS
Show, Problem c -> Problem c -> Bool
(Problem c -> Problem c -> Bool)
-> (Problem c -> Problem c -> Bool) -> Eq (Problem c)
forall c. Eq c => Problem c -> Problem c -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall c. Eq c => Problem c -> Problem c -> Bool
== :: Problem c -> Problem c -> Bool
$c/= :: forall c. Eq c => Problem c -> Problem c -> Bool
/= :: Problem c -> Problem c -> Bool
Eq, Eq (Problem c)
Eq (Problem c) =>
(Problem c -> Problem c -> Ordering)
-> (Problem c -> Problem c -> Bool)
-> (Problem c -> Problem c -> Bool)
-> (Problem c -> Problem c -> Bool)
-> (Problem c -> Problem c -> Bool)
-> (Problem c -> Problem c -> Problem c)
-> (Problem c -> Problem c -> Problem c)
-> Ord (Problem c)
Problem c -> Problem c -> Bool
Problem c -> Problem c -> Ordering
Problem c -> Problem c -> Problem c
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall c. Ord c => Eq (Problem c)
forall c. Ord c => Problem c -> Problem c -> Bool
forall c. Ord c => Problem c -> Problem c -> Ordering
forall c. Ord c => Problem c -> Problem c -> Problem c
$ccompare :: forall c. Ord c => Problem c -> Problem c -> Ordering
compare :: Problem c -> Problem c -> Ordering
$c< :: forall c. Ord c => Problem c -> Problem c -> Bool
< :: Problem c -> Problem c -> Bool
$c<= :: forall c. Ord c => Problem c -> Problem c -> Bool
<= :: Problem c -> Problem c -> Bool
$c> :: forall c. Ord c => Problem c -> Problem c -> Bool
> :: Problem c -> Problem c -> Bool
$c>= :: forall c. Ord c => Problem c -> Problem c -> Bool
>= :: Problem c -> Problem c -> Bool
$cmax :: forall c. Ord c => Problem c -> Problem c -> Problem c
max :: Problem c -> Problem c -> Problem c
$cmin :: forall c. Ord c => Problem c -> Problem c -> Problem c
min :: Problem c -> Problem c -> Problem c
Ord)
instance Default (Problem c) where
def :: Problem c
def = Problem
{ name :: Maybe Text
name = Maybe Text
forall a. Maybe a
Nothing
, objectiveFunction :: ObjectiveFunction c
objectiveFunction = ObjectiveFunction c
forall a. Default a => a
def
, constraints :: [Constraint c]
constraints = []
, sosConstraints :: [SOSConstraint c]
sosConstraints = []
, userCuts :: [Constraint c]
userCuts = []
, varType :: Map Var VarType
varType = Map Var VarType
forall k a. Map k a
Map.empty
, varBounds :: Map Var (Bounds c)
varBounds = Map Var (Bounds c)
forall k a. Map k a
Map.empty
}
instance Functor Problem where
fmap :: forall a b. (a -> b) -> Problem a -> Problem b
fmap a -> b
f Problem a
prob =
Problem a
prob
{ objectiveFunction = fmap f (objectiveFunction prob)
, constraints = map (fmap f) (constraints prob)
, sosConstraints = map (fmap f) (sosConstraints prob)
, userCuts = map (fmap f) (userCuts prob)
, varBounds = fmap (fmap f *** fmap f) (varBounds prob)
}
type Label = T.Text
type Var = InternedText
toVar :: String -> Var
toVar :: String -> Var
toVar = String -> Var
forall a. IsString a => String -> a
fromString
fromVar :: Var -> String
fromVar :: Var -> String
fromVar = Text -> String
T.unpack (Text -> String) -> (Var -> Text) -> Var -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Var -> Text
Var -> Uninterned Var
forall t. Uninternable t => t -> Uninterned t
unintern
data VarType
= ContinuousVariable
| IntegerVariable
| SemiContinuousVariable
| SemiIntegerVariable
deriving (VarType -> VarType -> Bool
(VarType -> VarType -> Bool)
-> (VarType -> VarType -> Bool) -> Eq VarType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: VarType -> VarType -> Bool
== :: VarType -> VarType -> Bool
$c/= :: VarType -> VarType -> Bool
/= :: VarType -> VarType -> Bool
Eq, Eq VarType
Eq VarType =>
(VarType -> VarType -> Ordering)
-> (VarType -> VarType -> Bool)
-> (VarType -> VarType -> Bool)
-> (VarType -> VarType -> Bool)
-> (VarType -> VarType -> Bool)
-> (VarType -> VarType -> VarType)
-> (VarType -> VarType -> VarType)
-> Ord VarType
VarType -> VarType -> Bool
VarType -> VarType -> Ordering
VarType -> VarType -> VarType
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: VarType -> VarType -> Ordering
compare :: VarType -> VarType -> Ordering
$c< :: VarType -> VarType -> Bool
< :: VarType -> VarType -> Bool
$c<= :: VarType -> VarType -> Bool
<= :: VarType -> VarType -> Bool
$c> :: VarType -> VarType -> Bool
> :: VarType -> VarType -> Bool
$c>= :: VarType -> VarType -> Bool
>= :: VarType -> VarType -> Bool
$cmax :: VarType -> VarType -> VarType
max :: VarType -> VarType -> VarType
$cmin :: VarType -> VarType -> VarType
min :: VarType -> VarType -> VarType
Ord, Int -> VarType -> ShowS
[VarType] -> ShowS
VarType -> String
(Int -> VarType -> ShowS)
-> (VarType -> String) -> ([VarType] -> ShowS) -> Show VarType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> VarType -> ShowS
showsPrec :: Int -> VarType -> ShowS
$cshow :: VarType -> String
show :: VarType -> String
$cshowList :: [VarType] -> ShowS
showList :: [VarType] -> ShowS
Show)
instance Default VarType where
def :: VarType
def = VarType
ContinuousVariable
getVarType :: Problem c -> Var -> VarType
getVarType :: forall c. Problem c -> Var -> VarType
getVarType Problem c
mip Var
v = VarType -> Var -> Map Var VarType -> VarType
forall k a. Ord k => a -> k -> Map k a -> a
Map.findWithDefault VarType
forall a. Default a => a
def Var
v (Problem c -> Map Var VarType
forall c. Problem c -> Map Var VarType
varType Problem c
mip)
type BoundExpr c = Extended c
type Bounds c = (BoundExpr c, BoundExpr c)
defaultBounds :: Num c => Bounds c
defaultBounds :: forall c. Num c => Bounds c
defaultBounds = (BoundExpr c
forall c. Num c => BoundExpr c
defaultLB, BoundExpr c
forall c. BoundExpr c
defaultUB)
defaultLB :: Num c => BoundExpr c
defaultLB :: forall c. Num c => BoundExpr c
defaultLB = c -> Extended c
forall r. r -> Extended r
Finite c
0
defaultUB :: BoundExpr c
defaultUB :: forall c. BoundExpr c
defaultUB = Extended c
forall c. BoundExpr c
PosInf
getBounds :: Num c => Problem c -> Var -> Bounds c
getBounds :: forall c. Num c => Problem c -> Var -> Bounds c
getBounds Problem c
mip Var
v = Bounds c -> Var -> Map Var (Bounds c) -> Bounds c
forall k a. Ord k => a -> k -> Map k a -> a
Map.findWithDefault Bounds c
forall c. Num c => Bounds c
defaultBounds Var
v (Problem c -> Map Var (Bounds c)
forall c. Problem c -> Map Var (Bounds c)
varBounds Problem c
mip)
intersectBounds :: Ord c => Bounds c -> Bounds c -> Bounds c
intersectBounds :: forall c. Ord c => Bounds c -> Bounds c -> Bounds c
intersectBounds (BoundExpr c
lb1,BoundExpr c
ub1) (BoundExpr c
lb2,BoundExpr c
ub2) = (BoundExpr c -> BoundExpr c -> BoundExpr c
forall a. Ord a => a -> a -> a
max BoundExpr c
lb1 BoundExpr c
lb2, BoundExpr c -> BoundExpr c -> BoundExpr c
forall a. Ord a => a -> a -> a
min BoundExpr c
ub1 BoundExpr c
ub2)
newtype Expr c = Expr [Term c]
deriving (Expr c -> Expr c -> Bool
(Expr c -> Expr c -> Bool)
-> (Expr c -> Expr c -> Bool) -> Eq (Expr c)
forall c. Eq c => Expr c -> Expr c -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall c. Eq c => Expr c -> Expr c -> Bool
== :: Expr c -> Expr c -> Bool
$c/= :: forall c. Eq c => Expr c -> Expr c -> Bool
/= :: Expr c -> Expr c -> Bool
Eq, Eq (Expr c)
Eq (Expr c) =>
(Expr c -> Expr c -> Ordering)
-> (Expr c -> Expr c -> Bool)
-> (Expr c -> Expr c -> Bool)
-> (Expr c -> Expr c -> Bool)
-> (Expr c -> Expr c -> Bool)
-> (Expr c -> Expr c -> Expr c)
-> (Expr c -> Expr c -> Expr c)
-> Ord (Expr c)
Expr c -> Expr c -> Bool
Expr c -> Expr c -> Ordering
Expr c -> Expr c -> Expr c
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall c. Ord c => Eq (Expr c)
forall c. Ord c => Expr c -> Expr c -> Bool
forall c. Ord c => Expr c -> Expr c -> Ordering
forall c. Ord c => Expr c -> Expr c -> Expr c
$ccompare :: forall c. Ord c => Expr c -> Expr c -> Ordering
compare :: Expr c -> Expr c -> Ordering
$c< :: forall c. Ord c => Expr c -> Expr c -> Bool
< :: Expr c -> Expr c -> Bool
$c<= :: forall c. Ord c => Expr c -> Expr c -> Bool
<= :: Expr c -> Expr c -> Bool
$c> :: forall c. Ord c => Expr c -> Expr c -> Bool
> :: Expr c -> Expr c -> Bool
$c>= :: forall c. Ord c => Expr c -> Expr c -> Bool
>= :: Expr c -> Expr c -> Bool
$cmax :: forall c. Ord c => Expr c -> Expr c -> Expr c
max :: Expr c -> Expr c -> Expr c
$cmin :: forall c. Ord c => Expr c -> Expr c -> Expr c
min :: Expr c -> Expr c -> Expr c
Ord, Int -> Expr c -> ShowS
[Expr c] -> ShowS
Expr c -> String
(Int -> Expr c -> ShowS)
-> (Expr c -> String) -> ([Expr c] -> ShowS) -> Show (Expr c)
forall c. Show c => Int -> Expr c -> ShowS
forall c. Show c => [Expr c] -> ShowS
forall c. Show c => Expr c -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall c. Show c => Int -> Expr c -> ShowS
showsPrec :: Int -> Expr c -> ShowS
$cshow :: forall c. Show c => Expr c -> String
show :: Expr c -> String
$cshowList :: forall c. Show c => [Expr c] -> ShowS
showList :: [Expr c] -> ShowS
Show)
varExpr :: Num c => Var -> Expr c
varExpr :: forall c. Num c => Var -> Expr c
varExpr Var
v = [Term c] -> Expr c
forall c. [Term c] -> Expr c
Expr [c -> [Var] -> Term c
forall c. c -> [Var] -> Term c
Term c
1 [Var
v]]
constExpr :: (Eq c, Num c) => c -> Expr c
constExpr :: forall c. (Eq c, Num c) => c -> Expr c
constExpr c
0 = [Term c] -> Expr c
forall c. [Term c] -> Expr c
Expr []
constExpr c
c = [Term c] -> Expr c
forall c. [Term c] -> Expr c
Expr [c -> [Var] -> Term c
forall c. c -> [Var] -> Term c
Term c
c []]
terms :: Expr c -> [Term c]
terms :: forall c. Expr c -> [Term c]
terms (Expr [Term c]
ts) = [Term c]
ts
instance Num c => Num (Expr c) where
Expr [Term c]
e1 + :: Expr c -> Expr c -> Expr c
+ Expr [Term c]
e2 = [Term c] -> Expr c
forall c. [Term c] -> Expr c
Expr ([Term c]
e1 [Term c] -> [Term c] -> [Term c]
forall a. [a] -> [a] -> [a]
++ [Term c]
e2)
Expr [Term c]
e1 * :: Expr c -> Expr c -> Expr c
* Expr [Term c]
e2 = [Term c] -> Expr c
forall c. [Term c] -> Expr c
Expr [c -> [Var] -> Term c
forall c. c -> [Var] -> Term c
Term (c
c1c -> c -> c
forall a. Num a => a -> a -> a
*c
c2) ([Var]
vs1 [Var] -> [Var] -> [Var]
forall a. [a] -> [a] -> [a]
++ [Var]
vs2) | Term c
c1 [Var]
vs1 <- [Term c]
e1, Term c
c2 [Var]
vs2 <- [Term c]
e2]
negate :: Expr c -> Expr c
negate (Expr [Term c]
e) = [Term c] -> Expr c
forall c. [Term c] -> Expr c
Expr [c -> [Var] -> Term c
forall c. c -> [Var] -> Term c
Term (-c
c) [Var]
vs | Term c
c [Var]
vs <- [Term c]
e]
abs :: Expr c -> Expr c
abs = Expr c -> Expr c
forall a. a -> a
id
signum :: Expr c -> Expr c
signum Expr c
_ = Expr c
1
fromInteger :: Integer -> Expr c
fromInteger Integer
0 = [Term c] -> Expr c
forall c. [Term c] -> Expr c
Expr []
fromInteger Integer
c = [Term c] -> Expr c
forall c. [Term c] -> Expr c
Expr [c -> [Var] -> Term c
forall c. c -> [Var] -> Term c
Term (Integer -> c
forall a. Num a => Integer -> a
fromInteger Integer
c) []]
instance Functor Expr where
fmap :: forall a b. (a -> b) -> Expr a -> Expr b
fmap a -> b
f (Expr [Term a]
ts) = [Term b] -> Expr b
forall c. [Term c] -> Expr c
Expr ([Term b] -> Expr b) -> [Term b] -> Expr b
forall a b. (a -> b) -> a -> b
$ (Term a -> Term b) -> [Term a] -> [Term b]
forall a b. (a -> b) -> [a] -> [b]
map ((a -> b) -> Term a -> Term b
forall a b. (a -> b) -> Term a -> Term b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f) [Term a]
ts
splitConst :: Num c => Expr c -> (Expr c, c)
splitConst :: forall c. Num c => Expr c -> (Expr c, c)
splitConst Expr c
e = (Expr c
e2, c
c2)
where
e2 :: Expr c
e2 = [Term c] -> Expr c
forall c. [Term c] -> Expr c
Expr [Term c
t | t :: Term c
t@(Term c
_ (Var
_:[Var]
_)) <- Expr c -> [Term c]
forall c. Expr c -> [Term c]
terms Expr c
e]
c2 :: c
c2 = [c] -> c
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum [c
c | Term c
c [] <- Expr c -> [Term c]
forall c. Expr c -> [Term c]
terms Expr c
e]
data Term c = Term c [Var]
deriving (Term c -> Term c -> Bool
(Term c -> Term c -> Bool)
-> (Term c -> Term c -> Bool) -> Eq (Term c)
forall c. Eq c => Term c -> Term c -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall c. Eq c => Term c -> Term c -> Bool
== :: Term c -> Term c -> Bool
$c/= :: forall c. Eq c => Term c -> Term c -> Bool
/= :: Term c -> Term c -> Bool
Eq, Eq (Term c)
Eq (Term c) =>
(Term c -> Term c -> Ordering)
-> (Term c -> Term c -> Bool)
-> (Term c -> Term c -> Bool)
-> (Term c -> Term c -> Bool)
-> (Term c -> Term c -> Bool)
-> (Term c -> Term c -> Term c)
-> (Term c -> Term c -> Term c)
-> Ord (Term c)
Term c -> Term c -> Bool
Term c -> Term c -> Ordering
Term c -> Term c -> Term c
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall c. Ord c => Eq (Term c)
forall c. Ord c => Term c -> Term c -> Bool
forall c. Ord c => Term c -> Term c -> Ordering
forall c. Ord c => Term c -> Term c -> Term c
$ccompare :: forall c. Ord c => Term c -> Term c -> Ordering
compare :: Term c -> Term c -> Ordering
$c< :: forall c. Ord c => Term c -> Term c -> Bool
< :: Term c -> Term c -> Bool
$c<= :: forall c. Ord c => Term c -> Term c -> Bool
<= :: Term c -> Term c -> Bool
$c> :: forall c. Ord c => Term c -> Term c -> Bool
> :: Term c -> Term c -> Bool
$c>= :: forall c. Ord c => Term c -> Term c -> Bool
>= :: Term c -> Term c -> Bool
$cmax :: forall c. Ord c => Term c -> Term c -> Term c
max :: Term c -> Term c -> Term c
$cmin :: forall c. Ord c => Term c -> Term c -> Term c
min :: Term c -> Term c -> Term c
Ord, Int -> Term c -> ShowS
[Term c] -> ShowS
Term c -> String
(Int -> Term c -> ShowS)
-> (Term c -> String) -> ([Term c] -> ShowS) -> Show (Term c)
forall c. Show c => Int -> Term c -> ShowS
forall c. Show c => [Term c] -> ShowS
forall c. Show c => Term c -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall c. Show c => Int -> Term c -> ShowS
showsPrec :: Int -> Term c -> ShowS
$cshow :: forall c. Show c => Term c -> String
show :: Term c -> String
$cshowList :: forall c. Show c => [Term c] -> ShowS
showList :: [Term c] -> ShowS
Show)
instance Functor Term where
fmap :: forall a b. (a -> b) -> Term a -> Term b
fmap a -> b
f (Term a
c [Var]
vs) = b -> [Var] -> Term b
forall c. c -> [Var] -> Term c
Term (a -> b
f a
c) [Var]
vs
data ObjectiveFunction c
= ObjectiveFunction
{ forall c. ObjectiveFunction c -> Maybe Text
objLabel :: Maybe Label
, forall c. ObjectiveFunction c -> OptDir
objDir :: OptDir
, forall c. ObjectiveFunction c -> Expr c
objExpr :: Expr c
}
deriving (ObjectiveFunction c -> ObjectiveFunction c -> Bool
(ObjectiveFunction c -> ObjectiveFunction c -> Bool)
-> (ObjectiveFunction c -> ObjectiveFunction c -> Bool)
-> Eq (ObjectiveFunction c)
forall c.
Eq c =>
ObjectiveFunction c -> ObjectiveFunction c -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall c.
Eq c =>
ObjectiveFunction c -> ObjectiveFunction c -> Bool
== :: ObjectiveFunction c -> ObjectiveFunction c -> Bool
$c/= :: forall c.
Eq c =>
ObjectiveFunction c -> ObjectiveFunction c -> Bool
/= :: ObjectiveFunction c -> ObjectiveFunction c -> Bool
Eq, Eq (ObjectiveFunction c)
Eq (ObjectiveFunction c) =>
(ObjectiveFunction c -> ObjectiveFunction c -> Ordering)
-> (ObjectiveFunction c -> ObjectiveFunction c -> Bool)
-> (ObjectiveFunction c -> ObjectiveFunction c -> Bool)
-> (ObjectiveFunction c -> ObjectiveFunction c -> Bool)
-> (ObjectiveFunction c -> ObjectiveFunction c -> Bool)
-> (ObjectiveFunction c
-> ObjectiveFunction c -> ObjectiveFunction c)
-> (ObjectiveFunction c
-> ObjectiveFunction c -> ObjectiveFunction c)
-> Ord (ObjectiveFunction c)
ObjectiveFunction c -> ObjectiveFunction c -> Bool
ObjectiveFunction c -> ObjectiveFunction c -> Ordering
ObjectiveFunction c -> ObjectiveFunction c -> ObjectiveFunction c
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall c. Ord c => Eq (ObjectiveFunction c)
forall c.
Ord c =>
ObjectiveFunction c -> ObjectiveFunction c -> Bool
forall c.
Ord c =>
ObjectiveFunction c -> ObjectiveFunction c -> Ordering
forall c.
Ord c =>
ObjectiveFunction c -> ObjectiveFunction c -> ObjectiveFunction c
$ccompare :: forall c.
Ord c =>
ObjectiveFunction c -> ObjectiveFunction c -> Ordering
compare :: ObjectiveFunction c -> ObjectiveFunction c -> Ordering
$c< :: forall c.
Ord c =>
ObjectiveFunction c -> ObjectiveFunction c -> Bool
< :: ObjectiveFunction c -> ObjectiveFunction c -> Bool
$c<= :: forall c.
Ord c =>
ObjectiveFunction c -> ObjectiveFunction c -> Bool
<= :: ObjectiveFunction c -> ObjectiveFunction c -> Bool
$c> :: forall c.
Ord c =>
ObjectiveFunction c -> ObjectiveFunction c -> Bool
> :: ObjectiveFunction c -> ObjectiveFunction c -> Bool
$c>= :: forall c.
Ord c =>
ObjectiveFunction c -> ObjectiveFunction c -> Bool
>= :: ObjectiveFunction c -> ObjectiveFunction c -> Bool
$cmax :: forall c.
Ord c =>
ObjectiveFunction c -> ObjectiveFunction c -> ObjectiveFunction c
max :: ObjectiveFunction c -> ObjectiveFunction c -> ObjectiveFunction c
$cmin :: forall c.
Ord c =>
ObjectiveFunction c -> ObjectiveFunction c -> ObjectiveFunction c
min :: ObjectiveFunction c -> ObjectiveFunction c -> ObjectiveFunction c
Ord, Int -> ObjectiveFunction c -> ShowS
[ObjectiveFunction c] -> ShowS
ObjectiveFunction c -> String
(Int -> ObjectiveFunction c -> ShowS)
-> (ObjectiveFunction c -> String)
-> ([ObjectiveFunction c] -> ShowS)
-> Show (ObjectiveFunction c)
forall c. Show c => Int -> ObjectiveFunction c -> ShowS
forall c. Show c => [ObjectiveFunction c] -> ShowS
forall c. Show c => ObjectiveFunction c -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall c. Show c => Int -> ObjectiveFunction c -> ShowS
showsPrec :: Int -> ObjectiveFunction c -> ShowS
$cshow :: forall c. Show c => ObjectiveFunction c -> String
show :: ObjectiveFunction c -> String
$cshowList :: forall c. Show c => [ObjectiveFunction c] -> ShowS
showList :: [ObjectiveFunction c] -> ShowS
Show)
instance Default (ObjectiveFunction c) where
def :: ObjectiveFunction c
def =
ObjectiveFunction
{ objLabel :: Maybe Text
objLabel = Maybe Text
forall a. Maybe a
Nothing
, objDir :: OptDir
objDir = OptDir
OptMin
, objExpr :: Expr c
objExpr = [Term c] -> Expr c
forall c. [Term c] -> Expr c
Expr []
}
instance Functor ObjectiveFunction where
fmap :: forall a b. (a -> b) -> ObjectiveFunction a -> ObjectiveFunction b
fmap a -> b
f ObjectiveFunction a
obj = ObjectiveFunction a
obj{ objExpr = fmap f (objExpr obj) }
data Constraint c
= Constraint
{ forall c. Constraint c -> Maybe Text
constrLabel :: Maybe Label
, forall c. Constraint c -> Maybe (Var, c)
constrIndicator :: Maybe (Var, c)
, forall c. Constraint c -> Expr c
constrExpr :: Expr c
, forall c. Constraint c -> BoundExpr c
constrLB :: BoundExpr c
, forall c. Constraint c -> BoundExpr c
constrUB :: BoundExpr c
, forall c. Constraint c -> Bool
constrIsLazy :: Bool
}
deriving (Constraint c -> Constraint c -> Bool
(Constraint c -> Constraint c -> Bool)
-> (Constraint c -> Constraint c -> Bool) -> Eq (Constraint c)
forall c. Eq c => Constraint c -> Constraint c -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall c. Eq c => Constraint c -> Constraint c -> Bool
== :: Constraint c -> Constraint c -> Bool
$c/= :: forall c. Eq c => Constraint c -> Constraint c -> Bool
/= :: Constraint c -> Constraint c -> Bool
Eq, Eq (Constraint c)
Eq (Constraint c) =>
(Constraint c -> Constraint c -> Ordering)
-> (Constraint c -> Constraint c -> Bool)
-> (Constraint c -> Constraint c -> Bool)
-> (Constraint c -> Constraint c -> Bool)
-> (Constraint c -> Constraint c -> Bool)
-> (Constraint c -> Constraint c -> Constraint c)
-> (Constraint c -> Constraint c -> Constraint c)
-> Ord (Constraint c)
Constraint c -> Constraint c -> Bool
Constraint c -> Constraint c -> Ordering
Constraint c -> Constraint c -> Constraint c
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall c. Ord c => Eq (Constraint c)
forall c. Ord c => Constraint c -> Constraint c -> Bool
forall c. Ord c => Constraint c -> Constraint c -> Ordering
forall c. Ord c => Constraint c -> Constraint c -> Constraint c
$ccompare :: forall c. Ord c => Constraint c -> Constraint c -> Ordering
compare :: Constraint c -> Constraint c -> Ordering
$c< :: forall c. Ord c => Constraint c -> Constraint c -> Bool
< :: Constraint c -> Constraint c -> Bool
$c<= :: forall c. Ord c => Constraint c -> Constraint c -> Bool
<= :: Constraint c -> Constraint c -> Bool
$c> :: forall c. Ord c => Constraint c -> Constraint c -> Bool
> :: Constraint c -> Constraint c -> Bool
$c>= :: forall c. Ord c => Constraint c -> Constraint c -> Bool
>= :: Constraint c -> Constraint c -> Bool
$cmax :: forall c. Ord c => Constraint c -> Constraint c -> Constraint c
max :: Constraint c -> Constraint c -> Constraint c
$cmin :: forall c. Ord c => Constraint c -> Constraint c -> Constraint c
min :: Constraint c -> Constraint c -> Constraint c
Ord, Int -> Constraint c -> ShowS
[Constraint c] -> ShowS
Constraint c -> String
(Int -> Constraint c -> ShowS)
-> (Constraint c -> String)
-> ([Constraint c] -> ShowS)
-> Show (Constraint c)
forall c. Show c => Int -> Constraint c -> ShowS
forall c. Show c => [Constraint c] -> ShowS
forall c. Show c => Constraint c -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall c. Show c => Int -> Constraint c -> ShowS
showsPrec :: Int -> Constraint c -> ShowS
$cshow :: forall c. Show c => Constraint c -> String
show :: Constraint c -> String
$cshowList :: forall c. Show c => [Constraint c] -> ShowS
showList :: [Constraint c] -> ShowS
Show)
(.==.) :: Num c => Expr c -> Expr c -> Constraint c
Expr c
lhs .==. :: forall c. Num c => Expr c -> Expr c -> Constraint c
.==. Expr c
rhs =
case Expr c -> (Expr c, c)
forall c. Num c => Expr c -> (Expr c, c)
splitConst (Expr c
lhs Expr c -> Expr c -> Expr c
forall a. Num a => a -> a -> a
- Expr c
rhs) of
(Expr c
e, c
c) -> Constraint c
forall a. Default a => a
def{ constrExpr = e, constrLB = Finite (- c), constrUB = Finite (- c) }
(.<=.) :: Num c => Expr c -> Expr c -> Constraint c
Expr c
lhs .<=. :: forall c. Num c => Expr c -> Expr c -> Constraint c
.<=. Expr c
rhs =
case Expr c -> (Expr c, c)
forall c. Num c => Expr c -> (Expr c, c)
splitConst (Expr c
lhs Expr c -> Expr c -> Expr c
forall a. Num a => a -> a -> a
- Expr c
rhs) of
(Expr c
e, c
c) -> Constraint c
forall a. Default a => a
def{ constrExpr = e, constrUB = Finite (- c) }
(.>=.) :: Num c => Expr c -> Expr c -> Constraint c
Expr c
lhs .>=. :: forall c. Num c => Expr c -> Expr c -> Constraint c
.>=. Expr c
rhs =
case Expr c -> (Expr c, c)
forall c. Num c => Expr c -> (Expr c, c)
splitConst (Expr c
lhs Expr c -> Expr c -> Expr c
forall a. Num a => a -> a -> a
- Expr c
rhs) of
(Expr c
e, c
c) -> Constraint c
forall a. Default a => a
def{ constrExpr = e, constrLB = Finite (- c) }
instance Default (Constraint c) where
def :: Constraint c
def = Constraint
{ constrLabel :: Maybe Text
constrLabel = Maybe Text
forall a. Maybe a
Nothing
, constrIndicator :: Maybe (Var, c)
constrIndicator = Maybe (Var, c)
forall a. Maybe a
Nothing
, constrExpr :: Expr c
constrExpr = [Term c] -> Expr c
forall c. [Term c] -> Expr c
Expr []
, constrLB :: BoundExpr c
constrLB = BoundExpr c
forall c. BoundExpr c
NegInf
, constrUB :: BoundExpr c
constrUB = BoundExpr c
forall c. BoundExpr c
PosInf
, constrIsLazy :: Bool
constrIsLazy = Bool
False
}
instance Functor Constraint where
fmap :: forall a b. (a -> b) -> Constraint a -> Constraint b
fmap a -> b
f Constraint a
c =
Constraint a
c
{ constrIndicator = fmap (id *** f) (constrIndicator c)
, constrExpr = fmap f (constrExpr c)
, constrLB = fmap f (constrLB c)
, constrUB = fmap f (constrUB c)
}
data RelOp = Le | Ge | Eql
deriving (RelOp -> RelOp -> Bool
(RelOp -> RelOp -> Bool) -> (RelOp -> RelOp -> Bool) -> Eq RelOp
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RelOp -> RelOp -> Bool
== :: RelOp -> RelOp -> Bool
$c/= :: RelOp -> RelOp -> Bool
/= :: RelOp -> RelOp -> Bool
Eq, Eq RelOp
Eq RelOp =>
(RelOp -> RelOp -> Ordering)
-> (RelOp -> RelOp -> Bool)
-> (RelOp -> RelOp -> Bool)
-> (RelOp -> RelOp -> Bool)
-> (RelOp -> RelOp -> Bool)
-> (RelOp -> RelOp -> RelOp)
-> (RelOp -> RelOp -> RelOp)
-> Ord RelOp
RelOp -> RelOp -> Bool
RelOp -> RelOp -> Ordering
RelOp -> RelOp -> RelOp
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: RelOp -> RelOp -> Ordering
compare :: RelOp -> RelOp -> Ordering
$c< :: RelOp -> RelOp -> Bool
< :: RelOp -> RelOp -> Bool
$c<= :: RelOp -> RelOp -> Bool
<= :: RelOp -> RelOp -> Bool
$c> :: RelOp -> RelOp -> Bool
> :: RelOp -> RelOp -> Bool
$c>= :: RelOp -> RelOp -> Bool
>= :: RelOp -> RelOp -> Bool
$cmax :: RelOp -> RelOp -> RelOp
max :: RelOp -> RelOp -> RelOp
$cmin :: RelOp -> RelOp -> RelOp
min :: RelOp -> RelOp -> RelOp
Ord, Int -> RelOp
RelOp -> Int
RelOp -> [RelOp]
RelOp -> RelOp
RelOp -> RelOp -> [RelOp]
RelOp -> RelOp -> RelOp -> [RelOp]
(RelOp -> RelOp)
-> (RelOp -> RelOp)
-> (Int -> RelOp)
-> (RelOp -> Int)
-> (RelOp -> [RelOp])
-> (RelOp -> RelOp -> [RelOp])
-> (RelOp -> RelOp -> [RelOp])
-> (RelOp -> RelOp -> RelOp -> [RelOp])
-> Enum RelOp
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: RelOp -> RelOp
succ :: RelOp -> RelOp
$cpred :: RelOp -> RelOp
pred :: RelOp -> RelOp
$ctoEnum :: Int -> RelOp
toEnum :: Int -> RelOp
$cfromEnum :: RelOp -> Int
fromEnum :: RelOp -> Int
$cenumFrom :: RelOp -> [RelOp]
enumFrom :: RelOp -> [RelOp]
$cenumFromThen :: RelOp -> RelOp -> [RelOp]
enumFromThen :: RelOp -> RelOp -> [RelOp]
$cenumFromTo :: RelOp -> RelOp -> [RelOp]
enumFromTo :: RelOp -> RelOp -> [RelOp]
$cenumFromThenTo :: RelOp -> RelOp -> RelOp -> [RelOp]
enumFromThenTo :: RelOp -> RelOp -> RelOp -> [RelOp]
Enum, Int -> RelOp -> ShowS
[RelOp] -> ShowS
RelOp -> String
(Int -> RelOp -> ShowS)
-> (RelOp -> String) -> ([RelOp] -> ShowS) -> Show RelOp
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RelOp -> ShowS
showsPrec :: Int -> RelOp -> ShowS
$cshow :: RelOp -> String
show :: RelOp -> String
$cshowList :: [RelOp] -> ShowS
showList :: [RelOp] -> ShowS
Show)
data SOSType
= S1
| S2
deriving (SOSType -> SOSType -> Bool
(SOSType -> SOSType -> Bool)
-> (SOSType -> SOSType -> Bool) -> Eq SOSType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SOSType -> SOSType -> Bool
== :: SOSType -> SOSType -> Bool
$c/= :: SOSType -> SOSType -> Bool
/= :: SOSType -> SOSType -> Bool
Eq, Eq SOSType
Eq SOSType =>
(SOSType -> SOSType -> Ordering)
-> (SOSType -> SOSType -> Bool)
-> (SOSType -> SOSType -> Bool)
-> (SOSType -> SOSType -> Bool)
-> (SOSType -> SOSType -> Bool)
-> (SOSType -> SOSType -> SOSType)
-> (SOSType -> SOSType -> SOSType)
-> Ord SOSType
SOSType -> SOSType -> Bool
SOSType -> SOSType -> Ordering
SOSType -> SOSType -> SOSType
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: SOSType -> SOSType -> Ordering
compare :: SOSType -> SOSType -> Ordering
$c< :: SOSType -> SOSType -> Bool
< :: SOSType -> SOSType -> Bool
$c<= :: SOSType -> SOSType -> Bool
<= :: SOSType -> SOSType -> Bool
$c> :: SOSType -> SOSType -> Bool
> :: SOSType -> SOSType -> Bool
$c>= :: SOSType -> SOSType -> Bool
>= :: SOSType -> SOSType -> Bool
$cmax :: SOSType -> SOSType -> SOSType
max :: SOSType -> SOSType -> SOSType
$cmin :: SOSType -> SOSType -> SOSType
min :: SOSType -> SOSType -> SOSType
Ord, Int -> SOSType
SOSType -> Int
SOSType -> [SOSType]
SOSType -> SOSType
SOSType -> SOSType -> [SOSType]
SOSType -> SOSType -> SOSType -> [SOSType]
(SOSType -> SOSType)
-> (SOSType -> SOSType)
-> (Int -> SOSType)
-> (SOSType -> Int)
-> (SOSType -> [SOSType])
-> (SOSType -> SOSType -> [SOSType])
-> (SOSType -> SOSType -> [SOSType])
-> (SOSType -> SOSType -> SOSType -> [SOSType])
-> Enum SOSType
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: SOSType -> SOSType
succ :: SOSType -> SOSType
$cpred :: SOSType -> SOSType
pred :: SOSType -> SOSType
$ctoEnum :: Int -> SOSType
toEnum :: Int -> SOSType
$cfromEnum :: SOSType -> Int
fromEnum :: SOSType -> Int
$cenumFrom :: SOSType -> [SOSType]
enumFrom :: SOSType -> [SOSType]
$cenumFromThen :: SOSType -> SOSType -> [SOSType]
enumFromThen :: SOSType -> SOSType -> [SOSType]
$cenumFromTo :: SOSType -> SOSType -> [SOSType]
enumFromTo :: SOSType -> SOSType -> [SOSType]
$cenumFromThenTo :: SOSType -> SOSType -> SOSType -> [SOSType]
enumFromThenTo :: SOSType -> SOSType -> SOSType -> [SOSType]
Enum, Int -> SOSType -> ShowS
[SOSType] -> ShowS
SOSType -> String
(Int -> SOSType -> ShowS)
-> (SOSType -> String) -> ([SOSType] -> ShowS) -> Show SOSType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SOSType -> ShowS
showsPrec :: Int -> SOSType -> ShowS
$cshow :: SOSType -> String
show :: SOSType -> String
$cshowList :: [SOSType] -> ShowS
showList :: [SOSType] -> ShowS
Show, ReadPrec [SOSType]
ReadPrec SOSType
Int -> ReadS SOSType
ReadS [SOSType]
(Int -> ReadS SOSType)
-> ReadS [SOSType]
-> ReadPrec SOSType
-> ReadPrec [SOSType]
-> Read SOSType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS SOSType
readsPrec :: Int -> ReadS SOSType
$creadList :: ReadS [SOSType]
readList :: ReadS [SOSType]
$creadPrec :: ReadPrec SOSType
readPrec :: ReadPrec SOSType
$creadListPrec :: ReadPrec [SOSType]
readListPrec :: ReadPrec [SOSType]
Read)
data SOSConstraint c
= SOSConstraint
{ forall c. SOSConstraint c -> Maybe Text
sosLabel :: Maybe Label
, forall c. SOSConstraint c -> SOSType
sosType :: SOSType
, forall c. SOSConstraint c -> [(Var, c)]
sosBody :: [(Var, c)]
}
deriving (SOSConstraint c -> SOSConstraint c -> Bool
(SOSConstraint c -> SOSConstraint c -> Bool)
-> (SOSConstraint c -> SOSConstraint c -> Bool)
-> Eq (SOSConstraint c)
forall c. Eq c => SOSConstraint c -> SOSConstraint c -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall c. Eq c => SOSConstraint c -> SOSConstraint c -> Bool
== :: SOSConstraint c -> SOSConstraint c -> Bool
$c/= :: forall c. Eq c => SOSConstraint c -> SOSConstraint c -> Bool
/= :: SOSConstraint c -> SOSConstraint c -> Bool
Eq, Eq (SOSConstraint c)
Eq (SOSConstraint c) =>
(SOSConstraint c -> SOSConstraint c -> Ordering)
-> (SOSConstraint c -> SOSConstraint c -> Bool)
-> (SOSConstraint c -> SOSConstraint c -> Bool)
-> (SOSConstraint c -> SOSConstraint c -> Bool)
-> (SOSConstraint c -> SOSConstraint c -> Bool)
-> (SOSConstraint c -> SOSConstraint c -> SOSConstraint c)
-> (SOSConstraint c -> SOSConstraint c -> SOSConstraint c)
-> Ord (SOSConstraint c)
SOSConstraint c -> SOSConstraint c -> Bool
SOSConstraint c -> SOSConstraint c -> Ordering
SOSConstraint c -> SOSConstraint c -> SOSConstraint c
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall c. Ord c => Eq (SOSConstraint c)
forall c. Ord c => SOSConstraint c -> SOSConstraint c -> Bool
forall c. Ord c => SOSConstraint c -> SOSConstraint c -> Ordering
forall c.
Ord c =>
SOSConstraint c -> SOSConstraint c -> SOSConstraint c
$ccompare :: forall c. Ord c => SOSConstraint c -> SOSConstraint c -> Ordering
compare :: SOSConstraint c -> SOSConstraint c -> Ordering
$c< :: forall c. Ord c => SOSConstraint c -> SOSConstraint c -> Bool
< :: SOSConstraint c -> SOSConstraint c -> Bool
$c<= :: forall c. Ord c => SOSConstraint c -> SOSConstraint c -> Bool
<= :: SOSConstraint c -> SOSConstraint c -> Bool
$c> :: forall c. Ord c => SOSConstraint c -> SOSConstraint c -> Bool
> :: SOSConstraint c -> SOSConstraint c -> Bool
$c>= :: forall c. Ord c => SOSConstraint c -> SOSConstraint c -> Bool
>= :: SOSConstraint c -> SOSConstraint c -> Bool
$cmax :: forall c.
Ord c =>
SOSConstraint c -> SOSConstraint c -> SOSConstraint c
max :: SOSConstraint c -> SOSConstraint c -> SOSConstraint c
$cmin :: forall c.
Ord c =>
SOSConstraint c -> SOSConstraint c -> SOSConstraint c
min :: SOSConstraint c -> SOSConstraint c -> SOSConstraint c
Ord, Int -> SOSConstraint c -> ShowS
[SOSConstraint c] -> ShowS
SOSConstraint c -> String
(Int -> SOSConstraint c -> ShowS)
-> (SOSConstraint c -> String)
-> ([SOSConstraint c] -> ShowS)
-> Show (SOSConstraint c)
forall c. Show c => Int -> SOSConstraint c -> ShowS
forall c. Show c => [SOSConstraint c] -> ShowS
forall c. Show c => SOSConstraint c -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall c. Show c => Int -> SOSConstraint c -> ShowS
showsPrec :: Int -> SOSConstraint c -> ShowS
$cshow :: forall c. Show c => SOSConstraint c -> String
show :: SOSConstraint c -> String
$cshowList :: forall c. Show c => [SOSConstraint c] -> ShowS
showList :: [SOSConstraint c] -> ShowS
Show)
instance Functor SOSConstraint where
fmap :: forall a b. (a -> b) -> SOSConstraint a -> SOSConstraint b
fmap a -> b
f SOSConstraint a
c = SOSConstraint a
c{ sosBody = map (id *** f) (sosBody c) }
data Status
= StatusUnknown
| StatusFeasible
| StatusOptimal
| StatusInfeasibleOrUnbounded
| StatusInfeasible
| StatusUnbounded
deriving (Status -> Status -> Bool
(Status -> Status -> Bool)
-> (Status -> Status -> Bool) -> Eq Status
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Status -> Status -> Bool
== :: Status -> Status -> Bool
$c/= :: Status -> Status -> Bool
/= :: Status -> Status -> Bool
Eq, Eq Status
Eq Status =>
(Status -> Status -> Ordering)
-> (Status -> Status -> Bool)
-> (Status -> Status -> Bool)
-> (Status -> Status -> Bool)
-> (Status -> Status -> Bool)
-> (Status -> Status -> Status)
-> (Status -> Status -> Status)
-> Ord Status
Status -> Status -> Bool
Status -> Status -> Ordering
Status -> Status -> Status
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Status -> Status -> Ordering
compare :: Status -> Status -> Ordering
$c< :: Status -> Status -> Bool
< :: Status -> Status -> Bool
$c<= :: Status -> Status -> Bool
<= :: Status -> Status -> Bool
$c> :: Status -> Status -> Bool
> :: Status -> Status -> Bool
$c>= :: Status -> Status -> Bool
>= :: Status -> Status -> Bool
$cmax :: Status -> Status -> Status
max :: Status -> Status -> Status
$cmin :: Status -> Status -> Status
min :: Status -> Status -> Status
Ord, Int -> Status
Status -> Int
Status -> [Status]
Status -> Status
Status -> Status -> [Status]
Status -> Status -> Status -> [Status]
(Status -> Status)
-> (Status -> Status)
-> (Int -> Status)
-> (Status -> Int)
-> (Status -> [Status])
-> (Status -> Status -> [Status])
-> (Status -> Status -> [Status])
-> (Status -> Status -> Status -> [Status])
-> Enum Status
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: Status -> Status
succ :: Status -> Status
$cpred :: Status -> Status
pred :: Status -> Status
$ctoEnum :: Int -> Status
toEnum :: Int -> Status
$cfromEnum :: Status -> Int
fromEnum :: Status -> Int
$cenumFrom :: Status -> [Status]
enumFrom :: Status -> [Status]
$cenumFromThen :: Status -> Status -> [Status]
enumFromThen :: Status -> Status -> [Status]
$cenumFromTo :: Status -> Status -> [Status]
enumFromTo :: Status -> Status -> [Status]
$cenumFromThenTo :: Status -> Status -> Status -> [Status]
enumFromThenTo :: Status -> Status -> Status -> [Status]
Enum, Status
Status -> Status -> Bounded Status
forall a. a -> a -> Bounded a
$cminBound :: Status
minBound :: Status
$cmaxBound :: Status
maxBound :: Status
Bounded, Int -> Status -> ShowS
[Status] -> ShowS
Status -> String
(Int -> Status -> ShowS)
-> (Status -> String) -> ([Status] -> ShowS) -> Show Status
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Status -> ShowS
showsPrec :: Int -> Status -> ShowS
$cshow :: Status -> String
show :: Status -> String
$cshowList :: [Status] -> ShowS
showList :: [Status] -> ShowS
Show)
instance PartialOrd Status where
leq :: Status -> Status -> Bool
leq Status
a Status
b = (Status
a,Status
b) (Status, Status) -> Set (Status, Status) -> Bool
forall a. Ord a => a -> Set a -> Bool
`Set.member` Set (Status, Status)
rel
where
rel :: Set (Status, Status)
rel = Set (Status, Status)
-> (Set (Status, Status) -> Set (Status, Status))
-> Set (Status, Status)
forall a. Eq a => a -> (a -> a) -> a
unsafeLfpFrom Set (Status, Status)
rel0 ((Set (Status, Status) -> Set (Status, Status))
-> Set (Status, Status))
-> (Set (Status, Status) -> Set (Status, Status))
-> Set (Status, Status)
forall a b. (a -> b) -> a -> b
$ \Set (Status, Status)
r ->
Set (Status, Status)
-> Set (Status, Status) -> Set (Status, Status)
forall a. Ord a => Set a -> Set a -> Set a
Set.union Set (Status, Status)
r ([(Status, Status)] -> Set (Status, Status)
forall a. Ord a => [a] -> Set a
Set.fromList [(Status
x,Status
z) | (Status
x,Status
y) <- Set (Status, Status) -> [(Status, Status)]
forall a. Set a -> [a]
Set.toList Set (Status, Status)
r, (Status
y',Status
z) <- Set (Status, Status) -> [(Status, Status)]
forall a. Set a -> [a]
Set.toList Set (Status, Status)
r, Status
y Status -> Status -> Bool
forall a. Eq a => a -> a -> Bool
== Status
y'])
rel0 :: Set (Status, Status)
rel0 = [(Status, Status)] -> Set (Status, Status)
forall a. Ord a => [a] -> Set a
Set.fromList ([(Status, Status)] -> Set (Status, Status))
-> [(Status, Status)] -> Set (Status, Status)
forall a b. (a -> b) -> a -> b
$
[(Status
x,Status
x) | Status
x <- [Status
forall a. Bounded a => a
minBound .. Status
forall a. Bounded a => a
maxBound]] [(Status, Status)] -> [(Status, Status)] -> [(Status, Status)]
forall a. [a] -> [a] -> [a]
++
[ (Status
StatusUnknown, Status
StatusFeasible)
, (Status
StatusUnknown, Status
StatusInfeasibleOrUnbounded)
, (Status
StatusFeasible, Status
StatusOptimal)
, (Status
StatusFeasible, Status
StatusUnbounded)
, (Status
StatusInfeasibleOrUnbounded, Status
StatusUnbounded)
, (Status
StatusInfeasibleOrUnbounded, Status
StatusInfeasible)
]
meetStatus :: Status -> Status -> Status
Status
StatusUnknown meetStatus :: Status -> Status -> Status
`meetStatus` Status
_b = Status
StatusUnknown
Status
StatusFeasible `meetStatus` Status
b
| Status
StatusFeasible Status -> Status -> Bool
forall a. PartialOrd a => a -> a -> Bool
`leq` Status
b = Status
StatusFeasible
| Bool
otherwise = Status
StatusUnknown
Status
StatusOptimal `meetStatus` Status
StatusOptimal = Status
StatusOptimal
Status
StatusOptimal `meetStatus` Status
b
| Status
StatusFeasible Status -> Status -> Bool
forall a. PartialOrd a => a -> a -> Bool
`leq` Status
b = Status
StatusFeasible
| Bool
otherwise = Status
StatusUnknown
Status
StatusInfeasibleOrUnbounded `meetStatus` Status
b
| Status
StatusInfeasibleOrUnbounded Status -> Status -> Bool
forall a. PartialOrd a => a -> a -> Bool
`leq` Status
b = Status
StatusInfeasibleOrUnbounded
| Bool
otherwise = Status
StatusUnknown
Status
StatusInfeasible `meetStatus` Status
StatusInfeasible = Status
StatusInfeasible
Status
StatusInfeasible `meetStatus` Status
b
| Status
StatusInfeasibleOrUnbounded Status -> Status -> Bool
forall a. PartialOrd a => a -> a -> Bool
`leq` Status
b = Status
StatusInfeasibleOrUnbounded
| Bool
otherwise = Status
StatusUnknown
Status
StatusUnbounded `meetStatus` Status
StatusUnbounded = Status
StatusUnbounded
Status
StatusUnbounded `meetStatus` Status
b
| Status
StatusFeasible Status -> Status -> Bool
forall a. PartialOrd a => a -> a -> Bool
`leq` Status
b = Status
StatusFeasible
| Status
StatusInfeasibleOrUnbounded Status -> Status -> Bool
forall a. PartialOrd a => a -> a -> Bool
`leq` Status
b = Status
StatusInfeasibleOrUnbounded
| Bool
otherwise = Status
StatusUnknown
#if !MIN_VERSION_lattices(2,0,0)
instance MeetSemiLattice Status where
meet = meetStatus
#endif
data Solution r
= Solution
{ forall r. Solution r -> Status
solStatus :: Status
, forall r. Solution r -> Maybe r
solObjectiveValue :: Maybe r
, forall r. Solution r -> Map Var r
solVariables :: Map Var r
}
deriving (Solution r -> Solution r -> Bool
(Solution r -> Solution r -> Bool)
-> (Solution r -> Solution r -> Bool) -> Eq (Solution r)
forall r. Eq r => Solution r -> Solution r -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall r. Eq r => Solution r -> Solution r -> Bool
== :: Solution r -> Solution r -> Bool
$c/= :: forall r. Eq r => Solution r -> Solution r -> Bool
/= :: Solution r -> Solution r -> Bool
Eq, Eq (Solution r)
Eq (Solution r) =>
(Solution r -> Solution r -> Ordering)
-> (Solution r -> Solution r -> Bool)
-> (Solution r -> Solution r -> Bool)
-> (Solution r -> Solution r -> Bool)
-> (Solution r -> Solution r -> Bool)
-> (Solution r -> Solution r -> Solution r)
-> (Solution r -> Solution r -> Solution r)
-> Ord (Solution r)
Solution r -> Solution r -> Bool
Solution r -> Solution r -> Ordering
Solution r -> Solution r -> Solution r
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall r. Ord r => Eq (Solution r)
forall r. Ord r => Solution r -> Solution r -> Bool
forall r. Ord r => Solution r -> Solution r -> Ordering
forall r. Ord r => Solution r -> Solution r -> Solution r
$ccompare :: forall r. Ord r => Solution r -> Solution r -> Ordering
compare :: Solution r -> Solution r -> Ordering
$c< :: forall r. Ord r => Solution r -> Solution r -> Bool
< :: Solution r -> Solution r -> Bool
$c<= :: forall r. Ord r => Solution r -> Solution r -> Bool
<= :: Solution r -> Solution r -> Bool
$c> :: forall r. Ord r => Solution r -> Solution r -> Bool
> :: Solution r -> Solution r -> Bool
$c>= :: forall r. Ord r => Solution r -> Solution r -> Bool
>= :: Solution r -> Solution r -> Bool
$cmax :: forall r. Ord r => Solution r -> Solution r -> Solution r
max :: Solution r -> Solution r -> Solution r
$cmin :: forall r. Ord r => Solution r -> Solution r -> Solution r
min :: Solution r -> Solution r -> Solution r
Ord, Int -> Solution r -> ShowS
[Solution r] -> ShowS
Solution r -> String
(Int -> Solution r -> ShowS)
-> (Solution r -> String)
-> ([Solution r] -> ShowS)
-> Show (Solution r)
forall r. Show r => Int -> Solution r -> ShowS
forall r. Show r => [Solution r] -> ShowS
forall r. Show r => Solution r -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall r. Show r => Int -> Solution r -> ShowS
showsPrec :: Int -> Solution r -> ShowS
$cshow :: forall r. Show r => Solution r -> String
show :: Solution r -> String
$cshowList :: forall r. Show r => [Solution r] -> ShowS
showList :: [Solution r] -> ShowS
Show)
instance Functor Solution where
fmap :: forall a b. (a -> b) -> Solution a -> Solution b
fmap a -> b
f (Solution Status
status Maybe a
obj Map Var a
vs) = Status -> Maybe b -> Map Var b -> Solution b
forall r. Status -> Maybe r -> Map Var r -> Solution r
Solution Status
status ((a -> b) -> Maybe a -> Maybe b
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f Maybe a
obj) ((a -> b) -> Map Var a -> Map Var b
forall a b. (a -> b) -> Map Var a -> Map Var b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f Map Var a
vs)
instance Default (Solution r) where
def :: Solution r
def = Solution
{ solStatus :: Status
solStatus = Status
StatusUnknown
, solObjectiveValue :: Maybe r
solObjectiveValue = Maybe r
forall a. Maybe a
Nothing
, solVariables :: Map Var r
solVariables = Map Var r
forall k a. Map k a
Map.empty
}
class Variables a where
vars :: a -> Set Var
instance Variables a => Variables [a] where
vars :: [a] -> Set Var
vars = [Set Var] -> Set Var
forall (f :: * -> *) a. (Foldable f, Ord a) => f (Set a) -> Set a
Set.unions ([Set Var] -> Set Var) -> ([a] -> [Set Var]) -> [a] -> Set Var
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> Set Var) -> [a] -> [Set Var]
forall a b. (a -> b) -> [a] -> [b]
map a -> Set Var
forall a. Variables a => a -> Set Var
vars
instance (Variables a, Variables b) => Variables (Either a b) where
vars :: Either a b -> Set Var
vars (Left a
a) = a -> Set Var
forall a. Variables a => a -> Set Var
vars a
a
vars (Right b
b) = b -> Set Var
forall a. Variables a => a -> Set Var
vars b
b
instance Variables (Problem c) where
vars :: Problem c -> Set Var
vars = Problem c -> Set Var
forall c. Problem c -> Set Var
variables
instance Variables (Expr c) where
vars :: Expr c -> Set Var
vars (Expr [Term c]
e) = [Term c] -> Set Var
forall a. Variables a => a -> Set Var
vars [Term c]
e
instance Variables (Term c) where
vars :: Term c -> Set Var
vars (Term c
_ [Var]
xs) = [Var] -> Set Var
forall a. Ord a => [a] -> Set a
Set.fromList [Var]
xs
instance Variables (ObjectiveFunction c) where
vars :: ObjectiveFunction c -> Set Var
vars ObjectiveFunction{ objExpr :: forall c. ObjectiveFunction c -> Expr c
objExpr = Expr c
e } = Expr c -> Set Var
forall a. Variables a => a -> Set Var
vars Expr c
e
instance Variables (Constraint c) where
vars :: Constraint c -> Set Var
vars Constraint{ constrIndicator :: forall c. Constraint c -> Maybe (Var, c)
constrIndicator = Maybe (Var, c)
ind, constrExpr :: forall c. Constraint c -> Expr c
constrExpr = Expr c
e } = Set Var -> Set Var -> Set Var
forall a. Ord a => Set a -> Set a -> Set a
Set.union (Expr c -> Set Var
forall a. Variables a => a -> Set Var
vars Expr c
e) Set Var
vs2
where
vs2 :: Set Var
vs2 = Set Var -> ((Var, c) -> Set Var) -> Maybe (Var, c) -> Set Var
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Set Var
forall a. Set a
Set.empty (Var -> Set Var
forall a. a -> Set a
Set.singleton (Var -> Set Var) -> ((Var, c) -> Var) -> (Var, c) -> Set Var
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Var, c) -> Var
forall a b. (a, b) -> a
fst) Maybe (Var, c)
ind
instance Variables (SOSConstraint c) where
vars :: SOSConstraint c -> Set Var
vars SOSConstraint{ sosBody :: forall c. SOSConstraint c -> [(Var, c)]
sosBody = [(Var, c)]
xs } = [Var] -> Set Var
forall a. Ord a => [a] -> Set a
Set.fromList (((Var, c) -> Var) -> [(Var, c)] -> [Var]
forall a b. (a -> b) -> [a] -> [b]
map (Var, c) -> Var
forall a b. (a, b) -> a
fst [(Var, c)]
xs)
variables :: Problem c -> Set Var
variables :: forall c. Problem c -> Set Var
variables Problem c
mip = Map Var VarType -> Set Var
forall k a. Map k a -> Set k
Map.keysSet (Map Var VarType -> Set Var) -> Map Var VarType -> Set Var
forall a b. (a -> b) -> a -> b
$ Problem c -> Map Var VarType
forall c. Problem c -> Map Var VarType
varType Problem c
mip
integerVariables :: Problem c -> Set Var
integerVariables :: forall c. Problem c -> Set Var
integerVariables Problem c
mip = Map Var VarType -> Set Var
forall k a. Map k a -> Set k
Map.keysSet (Map Var VarType -> Set Var) -> Map Var VarType -> Set Var
forall a b. (a -> b) -> a -> b
$ (VarType -> Bool) -> Map Var VarType -> Map Var VarType
forall a k. (a -> Bool) -> Map k a -> Map k a
Map.filter (VarType
IntegerVariable VarType -> VarType -> Bool
forall a. Eq a => a -> a -> Bool
==) (Problem c -> Map Var VarType
forall c. Problem c -> Map Var VarType
varType Problem c
mip)
semiContinuousVariables :: Problem c -> Set Var
semiContinuousVariables :: forall c. Problem c -> Set Var
semiContinuousVariables Problem c
mip = Map Var VarType -> Set Var
forall k a. Map k a -> Set k
Map.keysSet (Map Var VarType -> Set Var) -> Map Var VarType -> Set Var
forall a b. (a -> b) -> a -> b
$ (VarType -> Bool) -> Map Var VarType -> Map Var VarType
forall a k. (a -> Bool) -> Map k a -> Map k a
Map.filter (VarType
SemiContinuousVariable VarType -> VarType -> Bool
forall a. Eq a => a -> a -> Bool
==) (Problem c -> Map Var VarType
forall c. Problem c -> Map Var VarType
varType Problem c
mip)
semiIntegerVariables :: Problem c -> Set Var
semiIntegerVariables :: forall c. Problem c -> Set Var
semiIntegerVariables Problem c
mip = Map Var VarType -> Set Var
forall k a. Map k a -> Set k
Map.keysSet (Map Var VarType -> Set Var) -> Map Var VarType -> Set Var
forall a b. (a -> b) -> a -> b
$ (VarType -> Bool) -> Map Var VarType -> Map Var VarType
forall a k. (a -> Bool) -> Map k a -> Map k a
Map.filter (VarType
SemiIntegerVariable VarType -> VarType -> Bool
forall a. Eq a => a -> a -> Bool
==) (Problem c -> Map Var VarType
forall c. Problem c -> Map Var VarType
varType Problem c
mip)
data FileOptions
= FileOptions
{ FileOptions -> Maybe TextEncoding
optFileEncoding :: Maybe TextEncoding
} deriving (Int -> FileOptions -> ShowS
[FileOptions] -> ShowS
FileOptions -> String
(Int -> FileOptions -> ShowS)
-> (FileOptions -> String)
-> ([FileOptions] -> ShowS)
-> Show FileOptions
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FileOptions -> ShowS
showsPrec :: Int -> FileOptions -> ShowS
$cshow :: FileOptions -> String
show :: FileOptions -> String
$cshowList :: [FileOptions] -> ShowS
showList :: [FileOptions] -> ShowS
Show)
instance Default FileOptions where
def :: FileOptions
def =
FileOptions
{ optFileEncoding :: Maybe TextEncoding
optFileEncoding = Maybe TextEncoding
forall a. Maybe a
Nothing
}