module Data.PseudoBoolean.Types
(
Formula (..)
, Constraint
, Op (..)
, SoftFormula (..)
, SoftConstraint
, Sum
, WeightedTerm
, Term
, Lit
, Var
, pbComputeNumVars
, wboComputeNumVars
) where
import GHC.Generics (Generic)
import Control.DeepSeq
import Data.Data
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