{-# OPTIONS_GHC -Wall #-}
{-# OPTIONS_HADDOCK show-extensions #-}
{-# LANGUAGE CPP #-}
-----------------------------------------------------------------------------
-- |
-- Module      :  Numeric.Optimization.MIP.Base
-- Copyright   :  (c) Masahiro Sakai 2011-2019
-- License     :  BSD-style
--
-- Maintainer  :  masahiro.sakai@gmail.com
-- Stability   :  provisional
-- Portability :  non-portable
--
-- Mixed-Integer Programming Problems with some commmonly used extensions
--
-----------------------------------------------------------------------------
module Numeric.Optimization.MIP.Base
  (
  -- * The MIP Problem type
    Problem (..)
  , Label

  -- * Variables
  , Var
  , toVar
  , fromVar

  -- ** Variable types
  , VarType (..)
  , getVarType

  -- ** Variable bounds
  , BoundExpr
  , Extended (..)
  , Bounds
  , defaultBounds
  , defaultLB
  , defaultUB
  , getBounds

  -- ** Variable getters
  , variables
  , integerVariables
  , semiContinuousVariables
  , semiIntegerVariables

  -- * Expressions
  , Expr (..)
  , varExpr
  , constExpr
  , terms
  , Term (..)

  -- * Objective function
  , OptDir (..)
  , ObjectiveFunction (..)

  -- * Constraints

  -- ** Linear (or Quadratic or Polynomial) constraints
  , Constraint (..)
  , (.==.)
  , (.<=.)
  , (.>=.)
  , RelOp (..)

  -- ** SOS constraints
  , SOSType (..)
  , SOSConstraint (..)

  -- * Solutions
  , Solution (..)
  , Status (..)
  , meetStatus

  -- * File I/O options
  , FileOptions (..)

  -- * Utilities
  , 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 .<=., .>=., .==.

-- ---------------------------------------------------------------------------

-- | Problem
data Problem c
  = Problem
  { Problem c -> Maybe Text
name :: Maybe T.Text
  , Problem c -> ObjectiveFunction c
objectiveFunction :: ObjectiveFunction c
  , Problem c -> [Constraint c]
constraints :: [Constraint c]
  , Problem c -> [SOSConstraint c]
sosConstraints :: [SOSConstraint c]
  , Problem c -> [Constraint c]
userCuts :: [Constraint c]
  , Problem c -> Map Var VarType
varType :: Map Var VarType
  , 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
showList :: [Problem c] -> ShowS
$cshowList :: forall c. Show c => [Problem c] -> ShowS
show :: Problem c -> String
$cshow :: forall c. Show c => Problem c -> String
showsPrec :: Int -> Problem c -> ShowS
$cshowsPrec :: forall c. Show c => Int -> 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
/= :: Problem c -> Problem c -> Bool
$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
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
min :: Problem c -> Problem c -> Problem c
$cmin :: forall c. Ord c => Problem c -> Problem c -> Problem c
max :: Problem c -> Problem c -> Problem c
$cmax :: forall c. Ord c => Problem c -> Problem c -> Problem c
>= :: 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
$c< :: forall c. Ord c => Problem c -> Problem c -> Bool
compare :: Problem c -> Problem c -> Ordering
$ccompare :: forall c. Ord c => Problem c -> Problem c -> Ordering
$cp1Ord :: forall c. Ord c => Eq (Problem c)
Ord)

instance Default (Problem c) where
  def :: Problem c
def = Problem :: forall c.
Maybe Text
-> ObjectiveFunction c
-> [Constraint c]
-> [SOSConstraint c]
-> [Constraint c]
-> Map Var VarType
-> Map Var (Bounds c)
-> Problem c
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 :: (a -> b) -> Problem a -> Problem b
fmap a -> b
f Problem a
prob =
    Problem a
prob
    { objectiveFunction :: ObjectiveFunction b
objectiveFunction = (a -> b) -> ObjectiveFunction a -> ObjectiveFunction b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f (Problem a -> ObjectiveFunction a
forall c. Problem c -> ObjectiveFunction c
objectiveFunction Problem a
prob)
    , constraints :: [Constraint b]
constraints       = (Constraint a -> Constraint b) -> [Constraint a] -> [Constraint b]
forall a b. (a -> b) -> [a] -> [b]
map ((a -> b) -> Constraint a -> Constraint b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f) (Problem a -> [Constraint a]
forall c. Problem c -> [Constraint c]
constraints Problem a
prob)
    , sosConstraints :: [SOSConstraint b]
sosConstraints    = (SOSConstraint a -> SOSConstraint b)
-> [SOSConstraint a] -> [SOSConstraint b]
forall a b. (a -> b) -> [a] -> [b]
map ((a -> b) -> SOSConstraint a -> SOSConstraint b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f) (Problem a -> [SOSConstraint a]
forall c. Problem c -> [SOSConstraint c]
sosConstraints Problem a
prob)
    , userCuts :: [Constraint b]
userCuts          = (Constraint a -> Constraint b) -> [Constraint a] -> [Constraint b]
forall a b. (a -> b) -> [a] -> [b]
map ((a -> b) -> Constraint a -> Constraint b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f) (Problem a -> [Constraint a]
forall c. Problem c -> [Constraint c]
userCuts Problem a
prob)
    , varBounds :: Map Var (Bounds b)
varBounds         = (Bounds a -> Bounds b) -> Map Var (Bounds a) -> Map Var (Bounds b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((a -> b) -> Extended a -> Extended b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f (Extended a -> Extended b)
-> (Extended a -> Extended b) -> Bounds a -> Bounds b
forall (a :: * -> * -> *) b c b' c'.
Arrow a =>
a b c -> a b' c' -> a (b, b') (c, c')
*** (a -> b) -> Extended a -> Extended b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f) (Problem a -> Map Var (Bounds a)
forall c. Problem c -> Map Var (Bounds c)
varBounds Problem a
prob)
    }

-- | label
type Label = T.Text

-- ---------------------------------------------------------------------------

-- | variable
type Var = InternedText

-- | convert a string into a variable
toVar :: String -> Var
toVar :: String -> Var
toVar = String -> Var
forall a. IsString a => String -> a
fromString

-- | convert a variable into a string
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
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
/= :: VarType -> VarType -> Bool
$c/= :: VarType -> VarType -> Bool
== :: VarType -> VarType -> Bool
$c== :: 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
min :: VarType -> VarType -> VarType
$cmin :: VarType -> VarType -> VarType
max :: VarType -> VarType -> VarType
$cmax :: VarType -> VarType -> VarType
>= :: VarType -> VarType -> Bool
$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
compare :: VarType -> VarType -> Ordering
$ccompare :: VarType -> VarType -> Ordering
$cp1Ord :: Eq 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
showList :: [VarType] -> ShowS
$cshowList :: [VarType] -> ShowS
show :: VarType -> String
$cshow :: VarType -> String
showsPrec :: Int -> VarType -> ShowS
$cshowsPrec :: Int -> VarType -> ShowS
Show)

instance Default VarType where
  def :: VarType
def = VarType
ContinuousVariable

-- | looking up bounds for a variable
getVarType :: Problem c -> Var -> VarType
getVarType :: 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 for representing lower/upper bound of variables
type BoundExpr c = Extended c

-- | type for representing lower/upper bound of variables
type Bounds c = (BoundExpr c, BoundExpr c)

-- | default bounds
defaultBounds :: Num c => Bounds c
defaultBounds :: Bounds c
defaultBounds = (BoundExpr c
forall c. Num c => BoundExpr c
defaultLB, BoundExpr c
forall c. BoundExpr c
defaultUB)

-- | default lower bound (0)
defaultLB :: Num c => BoundExpr c
defaultLB :: BoundExpr c
defaultLB = c -> BoundExpr c
forall r. r -> Extended r
Finite c
0

-- | default upper bound (+∞)
defaultUB :: BoundExpr c
defaultUB :: BoundExpr c
defaultUB = BoundExpr c
forall c. BoundExpr c
PosInf

-- | looking up bounds for a variable
getBounds :: Num c => Problem c -> Var -> Bounds c
getBounds :: 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 :: 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)

-- ---------------------------------------------------------------------------

-- | expressions
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
/= :: Expr c -> Expr c -> Bool
$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
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
min :: Expr c -> Expr c -> Expr c
$cmin :: forall c. Ord c => Expr c -> Expr c -> Expr c
max :: Expr c -> Expr c -> Expr c
$cmax :: forall c. Ord c => Expr c -> Expr c -> Expr c
>= :: 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
$c< :: forall c. Ord c => Expr c -> Expr c -> Bool
compare :: Expr c -> Expr c -> Ordering
$ccompare :: forall c. Ord c => Expr c -> Expr c -> Ordering
$cp1Ord :: forall c. Ord c => Eq (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
showList :: [Expr c] -> ShowS
$cshowList :: forall c. Show c => [Expr c] -> ShowS
show :: Expr c -> String
$cshow :: forall c. Show c => Expr c -> String
showsPrec :: Int -> Expr c -> ShowS
$cshowsPrec :: forall c. Show c => Int -> Expr c -> ShowS
Show)

varExpr :: Num c => Var -> Expr c
varExpr :: 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 :: 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 :: 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 :: (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 (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 :: 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 (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]

-- | terms
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
/= :: Term c -> Term c -> Bool
$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
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
min :: Term c -> Term c -> Term c
$cmin :: forall c. Ord c => Term c -> Term c -> Term c
max :: Term c -> Term c -> Term c
$cmax :: forall c. Ord c => Term c -> Term c -> Term c
>= :: 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
$c< :: forall c. Ord c => Term c -> Term c -> Bool
compare :: Term c -> Term c -> Ordering
$ccompare :: forall c. Ord c => Term c -> Term c -> Ordering
$cp1Ord :: forall c. Ord c => Eq (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
showList :: [Term c] -> ShowS
$cshowList :: forall c. Show c => [Term c] -> ShowS
show :: Term c -> String
$cshow :: forall c. Show c => Term c -> String
showsPrec :: Int -> Term c -> ShowS
$cshowsPrec :: forall c. Show c => Int -> Term c -> ShowS
Show)

instance Functor Term where
  fmap :: (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

-- ---------------------------------------------------------------------------

-- | objective function
data ObjectiveFunction c
  = ObjectiveFunction
  { ObjectiveFunction c -> Maybe Text
objLabel :: Maybe Label
  , ObjectiveFunction c -> OptDir
objDir :: OptDir
  , 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
/= :: ObjectiveFunction c -> ObjectiveFunction c -> Bool
$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
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
min :: ObjectiveFunction c -> ObjectiveFunction c -> ObjectiveFunction c
$cmin :: forall c.
Ord c =>
ObjectiveFunction c -> ObjectiveFunction c -> ObjectiveFunction c
max :: ObjectiveFunction c -> ObjectiveFunction c -> ObjectiveFunction c
$cmax :: forall c.
Ord c =>
ObjectiveFunction c -> ObjectiveFunction c -> ObjectiveFunction c
>= :: 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
$c< :: forall c.
Ord c =>
ObjectiveFunction c -> ObjectiveFunction c -> Bool
compare :: ObjectiveFunction c -> ObjectiveFunction c -> Ordering
$ccompare :: forall c.
Ord c =>
ObjectiveFunction c -> ObjectiveFunction c -> Ordering
$cp1Ord :: forall c. Ord c => Eq (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
showList :: [ObjectiveFunction c] -> ShowS
$cshowList :: forall c. Show c => [ObjectiveFunction c] -> ShowS
show :: ObjectiveFunction c -> String
$cshow :: forall c. Show c => ObjectiveFunction c -> String
showsPrec :: Int -> ObjectiveFunction c -> ShowS
$cshowsPrec :: forall c. Show c => Int -> ObjectiveFunction c -> ShowS
Show)

instance Default (ObjectiveFunction c) where
  def :: ObjectiveFunction c
def =
    ObjectiveFunction :: forall c. Maybe Text -> OptDir -> Expr c -> ObjectiveFunction c
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 :: (a -> b) -> ObjectiveFunction a -> ObjectiveFunction b
fmap a -> b
f ObjectiveFunction a
obj = ObjectiveFunction a
obj{ objExpr :: Expr b
objExpr = (a -> b) -> Expr a -> Expr b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f (ObjectiveFunction a -> Expr a
forall c. ObjectiveFunction c -> Expr c
objExpr ObjectiveFunction a
obj) }

-- ---------------------------------------------------------------------------

-- | constraint
data Constraint c
  = Constraint
  { Constraint c -> Maybe Text
constrLabel     :: Maybe Label
  , Constraint c -> Maybe (Var, c)
constrIndicator :: Maybe (Var, c)
  , Constraint c -> Expr c
constrExpr      :: Expr c
  , Constraint c -> BoundExpr c
constrLB        :: BoundExpr c
  , Constraint c -> BoundExpr c
constrUB        :: BoundExpr 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
/= :: Constraint c -> Constraint c -> Bool
$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
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
min :: Constraint c -> Constraint c -> Constraint c
$cmin :: forall c. Ord c => Constraint c -> Constraint c -> Constraint c
max :: Constraint c -> Constraint c -> Constraint c
$cmax :: forall c. Ord c => Constraint c -> Constraint c -> Constraint c
>= :: 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
$c< :: forall c. Ord c => Constraint c -> Constraint c -> Bool
compare :: Constraint c -> Constraint c -> Ordering
$ccompare :: forall c. Ord c => Constraint c -> Constraint c -> Ordering
$cp1Ord :: forall c. Ord c => Eq (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
showList :: [Constraint c] -> ShowS
$cshowList :: forall c. Show c => [Constraint c] -> ShowS
show :: Constraint c -> String
$cshow :: forall c. Show c => Constraint c -> String
showsPrec :: Int -> Constraint c -> ShowS
$cshowsPrec :: forall c. Show c => Int -> Constraint c -> ShowS
Show)

-- | Equality constraint.
(.==.) :: Num c => Expr c -> Expr c -> Constraint c
Expr c
lhs .==. :: 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 :: Expr c
constrExpr = Expr c
e, constrLB :: BoundExpr c
constrLB = c -> BoundExpr c
forall r. r -> Extended r
Finite (- c
c), constrUB :: BoundExpr c
constrUB = c -> BoundExpr c
forall r. r -> Extended r
Finite (- c
c) }

-- | Inequality constraint (≤).
(.<=.) :: Num c => Expr c -> Expr c -> Constraint c
Expr c
lhs .<=. :: 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 :: Expr c
constrExpr = Expr c
e, constrUB :: BoundExpr c
constrUB = c -> BoundExpr c
forall r. r -> Extended r
Finite (- c
c) }

-- | Inequality constraint (≥).
(.>=.) :: Num c => Expr c -> Expr c -> Constraint c
Expr c
lhs .>=. :: 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 :: Expr c
constrExpr = Expr c
e, constrLB :: BoundExpr c
constrLB = c -> BoundExpr c
forall r. r -> Extended r
Finite (- c
c) }

instance Default (Constraint c) where
  def :: Constraint c
def = Constraint :: forall c.
Maybe Text
-> Maybe (Var, c)
-> Expr c
-> BoundExpr c
-> BoundExpr c
-> Bool
-> Constraint c
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 :: (a -> b) -> Constraint a -> Constraint b
fmap a -> b
f Constraint a
c =
    Constraint a
c
    { constrIndicator :: Maybe (Var, b)
constrIndicator = ((Var, a) -> (Var, b)) -> Maybe (Var, a) -> Maybe (Var, b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Var -> Var
forall a. a -> a
id (Var -> Var) -> (a -> b) -> (Var, a) -> (Var, b)
forall (a :: * -> * -> *) b c b' c'.
Arrow a =>
a b c -> a b' c' -> a (b, b') (c, c')
*** a -> b
f) (Constraint a -> Maybe (Var, a)
forall c. Constraint c -> Maybe (Var, c)
constrIndicator Constraint a
c)
    , constrExpr :: Expr b
constrExpr = (a -> b) -> Expr a -> Expr b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f (Constraint a -> Expr a
forall c. Constraint c -> Expr c
constrExpr Constraint a
c)
    , constrLB :: BoundExpr b
constrLB = (a -> b) -> Extended a -> BoundExpr b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f (Constraint a -> Extended a
forall c. Constraint c -> BoundExpr c
constrLB Constraint a
c)
    , constrUB :: BoundExpr b
constrUB = (a -> b) -> Extended a -> BoundExpr b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f (Constraint a -> Extended a
forall c. Constraint c -> BoundExpr c
constrUB Constraint a
c)
    }

-- | relational operators
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
/= :: RelOp -> RelOp -> Bool
$c/= :: RelOp -> RelOp -> Bool
== :: RelOp -> RelOp -> Bool
$c== :: 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
min :: RelOp -> RelOp -> RelOp
$cmin :: RelOp -> RelOp -> RelOp
max :: RelOp -> RelOp -> RelOp
$cmax :: RelOp -> RelOp -> RelOp
>= :: RelOp -> RelOp -> Bool
$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
compare :: RelOp -> RelOp -> Ordering
$ccompare :: RelOp -> RelOp -> Ordering
$cp1Ord :: Eq 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
enumFromThenTo :: RelOp -> RelOp -> RelOp -> [RelOp]
$cenumFromThenTo :: RelOp -> RelOp -> RelOp -> [RelOp]
enumFromTo :: RelOp -> RelOp -> [RelOp]
$cenumFromTo :: RelOp -> RelOp -> [RelOp]
enumFromThen :: RelOp -> RelOp -> [RelOp]
$cenumFromThen :: RelOp -> RelOp -> [RelOp]
enumFrom :: RelOp -> [RelOp]
$cenumFrom :: RelOp -> [RelOp]
fromEnum :: RelOp -> Int
$cfromEnum :: RelOp -> Int
toEnum :: Int -> RelOp
$ctoEnum :: Int -> RelOp
pred :: RelOp -> RelOp
$cpred :: RelOp -> RelOp
succ :: RelOp -> RelOp
$csucc :: 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
showList :: [RelOp] -> ShowS
$cshowList :: [RelOp] -> ShowS
show :: RelOp -> String
$cshow :: RelOp -> String
showsPrec :: Int -> RelOp -> ShowS
$cshowsPrec :: Int -> RelOp -> ShowS
Show)

-- ---------------------------------------------------------------------------

-- | types of SOS (special ordered sets) constraints
data SOSType
  = S1 -- ^ Type 1 SOS constraint
  | S2 -- ^ Type 2 SOS constraint
  deriving (SOSType -> SOSType -> Bool
(SOSType -> SOSType -> Bool)
-> (SOSType -> SOSType -> Bool) -> Eq SOSType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SOSType -> SOSType -> Bool
$c/= :: SOSType -> SOSType -> Bool
== :: SOSType -> SOSType -> Bool
$c== :: 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
min :: SOSType -> SOSType -> SOSType
$cmin :: SOSType -> SOSType -> SOSType
max :: SOSType -> SOSType -> SOSType
$cmax :: SOSType -> SOSType -> SOSType
>= :: SOSType -> SOSType -> Bool
$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
compare :: SOSType -> SOSType -> Ordering
$ccompare :: SOSType -> SOSType -> Ordering
$cp1Ord :: Eq 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
enumFromThenTo :: SOSType -> SOSType -> SOSType -> [SOSType]
$cenumFromThenTo :: SOSType -> SOSType -> SOSType -> [SOSType]
enumFromTo :: SOSType -> SOSType -> [SOSType]
$cenumFromTo :: SOSType -> SOSType -> [SOSType]
enumFromThen :: SOSType -> SOSType -> [SOSType]
$cenumFromThen :: SOSType -> SOSType -> [SOSType]
enumFrom :: SOSType -> [SOSType]
$cenumFrom :: SOSType -> [SOSType]
fromEnum :: SOSType -> Int
$cfromEnum :: SOSType -> Int
toEnum :: Int -> SOSType
$ctoEnum :: Int -> SOSType
pred :: SOSType -> SOSType
$cpred :: SOSType -> SOSType
succ :: SOSType -> SOSType
$csucc :: 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
showList :: [SOSType] -> ShowS
$cshowList :: [SOSType] -> ShowS
show :: SOSType -> String
$cshow :: SOSType -> String
showsPrec :: Int -> SOSType -> ShowS
$cshowsPrec :: Int -> 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
readListPrec :: ReadPrec [SOSType]
$creadListPrec :: ReadPrec [SOSType]
readPrec :: ReadPrec SOSType
$creadPrec :: ReadPrec SOSType
readList :: ReadS [SOSType]
$creadList :: ReadS [SOSType]
readsPrec :: Int -> ReadS SOSType
$creadsPrec :: Int -> ReadS SOSType
Read)

-- | SOS (special ordered sets) constraints
data SOSConstraint c
  = SOSConstraint
  { SOSConstraint c -> Maybe Text
sosLabel :: Maybe Label
  , SOSConstraint c -> SOSType
sosType  :: SOSType
  , 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
/= :: SOSConstraint c -> SOSConstraint c -> Bool
$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
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
min :: SOSConstraint c -> SOSConstraint c -> SOSConstraint c
$cmin :: forall c.
Ord c =>
SOSConstraint c -> SOSConstraint c -> SOSConstraint c
max :: SOSConstraint c -> SOSConstraint c -> SOSConstraint c
$cmax :: forall c.
Ord c =>
SOSConstraint c -> SOSConstraint c -> SOSConstraint c
>= :: 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
$c< :: forall c. Ord c => SOSConstraint c -> SOSConstraint c -> Bool
compare :: SOSConstraint c -> SOSConstraint c -> Ordering
$ccompare :: forall c. Ord c => SOSConstraint c -> SOSConstraint c -> Ordering
$cp1Ord :: forall c. Ord c => Eq (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
showList :: [SOSConstraint c] -> ShowS
$cshowList :: forall c. Show c => [SOSConstraint c] -> ShowS
show :: SOSConstraint c -> String
$cshow :: forall c. Show c => SOSConstraint c -> String
showsPrec :: Int -> SOSConstraint c -> ShowS
$cshowsPrec :: forall c. Show c => Int -> SOSConstraint c -> ShowS
Show)

instance Functor SOSConstraint where
  fmap :: (a -> b) -> SOSConstraint a -> SOSConstraint b
fmap a -> b
f SOSConstraint a
c = SOSConstraint a
c{ sosBody :: [(Var, b)]
sosBody = ((Var, a) -> (Var, b)) -> [(Var, a)] -> [(Var, b)]
forall a b. (a -> b) -> [a] -> [b]
map (Var -> Var
forall a. a -> a
id (Var -> Var) -> (a -> b) -> (Var, a) -> (Var, b)
forall (a :: * -> * -> *) b c b' c'.
Arrow a =>
a b c -> a b' c' -> a (b, b') (c, c')
*** a -> b
f) (SOSConstraint a -> [(Var, a)]
forall c. SOSConstraint c -> [(Var, c)]
sosBody SOSConstraint a
c) }

-- ---------------------------------------------------------------------------

-- | MIP status with the following partial order:
--
-- <<doc-images/MIP-Status-diagram.png>>
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
/= :: Status -> Status -> Bool
$c/= :: Status -> Status -> Bool
== :: Status -> Status -> Bool
$c== :: 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
min :: Status -> Status -> Status
$cmin :: Status -> Status -> Status
max :: Status -> Status -> Status
$cmax :: Status -> Status -> Status
>= :: Status -> Status -> Bool
$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
compare :: Status -> Status -> Ordering
$ccompare :: Status -> Status -> Ordering
$cp1Ord :: Eq 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
enumFromThenTo :: Status -> Status -> Status -> [Status]
$cenumFromThenTo :: Status -> Status -> Status -> [Status]
enumFromTo :: Status -> Status -> [Status]
$cenumFromTo :: Status -> Status -> [Status]
enumFromThen :: Status -> Status -> [Status]
$cenumFromThen :: Status -> Status -> [Status]
enumFrom :: Status -> [Status]
$cenumFrom :: Status -> [Status]
fromEnum :: Status -> Int
$cfromEnum :: Status -> Int
toEnum :: Int -> Status
$ctoEnum :: Int -> Status
pred :: Status -> Status
$cpred :: Status -> Status
succ :: Status -> Status
$csucc :: Status -> Status
Enum, Status
Status -> Status -> Bounded Status
forall a. a -> a -> Bounded a
maxBound :: Status
$cmaxBound :: Status
minBound :: Status
$cminBound :: 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
showList :: [Status] -> ShowS
$cshowList :: [Status] -> ShowS
show :: Status -> String
$cshow :: Status -> String
showsPrec :: Int -> Status -> ShowS
$cshowsPrec :: Int -> 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)
        ]

-- | /meet/ (greatest lower bound) operator of the partial order of 'Status' type.
--
-- If the version of @lattices@ is \<2, then @MeetSemiLattice@ instance can also be used.
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


-- | Type for representing a solution of MIP problem.
data Solution r
  = Solution
  { Solution r -> Status
solStatus :: Status
  , Solution r -> Maybe r
solObjectiveValue :: Maybe 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
/= :: Solution r -> Solution r -> Bool
$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
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
min :: Solution r -> Solution r -> Solution r
$cmin :: forall r. Ord r => Solution r -> Solution r -> Solution r
max :: Solution r -> Solution r -> Solution r
$cmax :: forall r. Ord r => Solution r -> Solution r -> Solution r
>= :: 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
$c< :: forall r. Ord r => Solution r -> Solution r -> Bool
compare :: Solution r -> Solution r -> Ordering
$ccompare :: forall r. Ord r => Solution r -> Solution r -> Ordering
$cp1Ord :: forall r. Ord r => Eq (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
showList :: [Solution r] -> ShowS
$cshowList :: forall r. Show r => [Solution r] -> ShowS
show :: Solution r -> String
$cshow :: forall r. Show r => Solution r -> String
showsPrec :: Int -> Solution r -> ShowS
$cshowsPrec :: forall r. Show r => Int -> Solution r -> ShowS
Show)

instance Functor Solution where
  fmap :: (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 (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 (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 :: forall r. Status -> Maybe r -> Map Var r -> Solution r
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 :: 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 :: 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 :: 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 :: 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
showList :: [FileOptions] -> ShowS
$cshowList :: [FileOptions] -> ShowS
show :: FileOptions -> String
$cshow :: FileOptions -> String
showsPrec :: Int -> FileOptions -> ShowS
$cshowsPrec :: Int -> FileOptions -> ShowS
Show)

instance Default FileOptions where
  def :: FileOptions
def =
    FileOptions :: Maybe TextEncoding -> FileOptions
FileOptions
    { optFileEncoding :: Maybe TextEncoding
optFileEncoding = Maybe TextEncoding
forall a. Maybe a
Nothing
    }