module Data.PseudoBoolean.Types
(
Formula (..)
, Constraint
, Op (..)
, SoftFormula (..)
, SoftConstraint
, Sum
, WeightedTerm
, Term
, Lit
, Var
, pbComputeNumVars
, pbProducts
, wboComputeNumVars
, wboProducts
, wboNumSoft
) where
import GHC.Generics (Generic)
import Control.Monad
import Control.DeepSeq
import Data.Data
import Data.Set (Set)
import qualified Data.Set as Set
import Data.IntSet (IntSet)
import qualified Data.IntSet as IntSet
import Data.Hashable
import Data.Maybe
data Formula
= Formula
{ pbObjectiveFunction :: Maybe Sum
, pbConstraints :: [Constraint]
, pbNumVars :: !Int
, pbNumConstraints :: !Int
}
deriving (Eq, Ord, Show, Typeable, Data, Generic)
instance NFData Formula
instance Hashable Formula
type Constraint = (Sum, Op, Integer)
data Op
= Ge
| Eq
deriving (Eq, Ord, Show, Enum, Bounded, Typeable, Data, Generic)
instance NFData Op
instance Hashable Op
data SoftFormula
= SoftFormula
{ wboTopCost :: Maybe Integer
, wboConstraints :: [SoftConstraint]
, wboNumVars :: !Int
, wboNumConstraints :: !Int
}
deriving (Eq, Ord, Show, Typeable, Data, Generic)
instance NFData SoftFormula
instance Hashable SoftFormula
type SoftConstraint = (Maybe Integer, Constraint)
type Sum = [WeightedTerm]
type WeightedTerm = (Integer, Term)
type Term = [Lit]
type Lit = Int
type Var = Int
pbComputeNumVars :: Maybe Sum -> [Constraint] -> Int
pbComputeNumVars obj cs = maximum (0 : vs)
where
vs = do
s <- maybeToList obj ++ [s | (s,_,_) <- cs]
(_, tm) <- s
lit <- tm
return $ abs lit
wboComputeNumVars :: [SoftConstraint] -> Int
wboComputeNumVars cs = maximum (0 : vs)
where
vs = do
s <- [s | (_, (s,_,_)) <- cs]
(_, tm) <- s
lit <- tm
return $ abs lit
pbProducts :: Formula -> Set IntSet
pbProducts formula = Set.fromList $ do
s <- maybeToList (pbObjectiveFunction formula) ++ [s | (s,_,_) <- pbConstraints formula]
(_, tm) <- s
let tm2 = IntSet.fromList tm
guard $ IntSet.size tm2 > 1
return tm2
wboProducts :: SoftFormula -> Set IntSet
wboProducts softformula = Set.fromList $ do
(_,(s,_,_)) <- wboConstraints softformula
(_, tm) <- s
let tm2 = IntSet.fromList tm
guard $ IntSet.size tm2 > 1
return tm2
wboNumSoft :: SoftFormula -> Int
wboNumSoft softformula = length [() | (Just _, _) <- wboConstraints softformula]