25

最近、私はHaskellにナイーブなDPLL Sat Solverを実装しました。これは、JohnHarrisonのHandbookof Practical Logic andAutomatedReasoningを基にしています。

DPLLはさまざまなバックトラック検索であるため、 Oleg KiselyovetalのLogicモナドを使用して実験したいと思います。しかし、何を変える必要があるのか​​よくわかりません。

これが私が持っているコードです。

  • ロジックモナドを使用するには、どのコードを変更する必要がありますか?
  • ボーナス:ロジックモナドを使用することによる具体的なパフォーマンス上の利点はありますか?

{-# LANGUAGE MonadComprehensions #-}
module DPLL where
import Prelude hiding (foldr)
import Control.Monad (join,mplus,mzero,guard,msum)
import Data.Set.Monad (Set, (\\), member, partition, toList, foldr)
import Data.Maybe (listToMaybe)

-- "Literal" propositions are either true or false
data Lit p = T p | F p deriving (Show,Ord,Eq)

neg :: Lit p -> Lit p
neg (T p) = F p
neg (F p) = T p

-- We model DPLL like a sequent calculus
-- LHS: a set of assumptions / partial model (set of literals)
-- RHS: a set of goals 
data Sequent p = (Set (Lit p)) :|-: Set (Set (Lit p)) deriving Show

{- --------------------------- Goal Reduction Rules -------------------------- -}
{- "Unit Propogation" takes literal x and A :|-: B to A,x :|-: B',
 - where B' has no clauses with x, 
 - and all instances of -x are deleted -}
unitP :: Ord p => Lit p -> Sequent p -> Sequent p
unitP x (assms :|-:  clauses) = (assms' :|-:  clauses')
  where
    assms' = (return x) `mplus` assms
    clauses_ = [ c | c <- clauses, not (x `member` c) ]
    clauses' = [ [ u | u <- c, u /= neg x] | c <- clauses_ ]

{- Find literals that only occur positively or negatively
 - and perform unit propogation on these -}
pureRule :: Ord p => Sequent p -> Maybe (Sequent p)
pureRule sequent@(_ :|-:  clauses) = 
  let 
    sign (T _) = True
    sign (F _) = False
    -- Partition the positive and negative formulae
    (positive,negative) = partition sign (join clauses)
    -- Compute the literals that are purely positive/negative
    purePositive = positive \\ (fmap neg negative)
    pureNegative = negative \\ (fmap neg positive)
    pure = purePositive `mplus` pureNegative 
    -- Unit Propagate the pure literals
    sequent' = foldr unitP sequent pure
  in if (pure /= mzero) then Just sequent'
     else Nothing

{- Add any singleton clauses to the assumptions 
 - and simplify the clauses -}
oneRule :: Ord p => Sequent p -> Maybe (Sequent p)
oneRule sequent@(_ :|-:  clauses) = 
   do
   -- Extract literals that occur alone and choose one
   let singletons = join [ c | c <- clauses, isSingle c ]
   x <- (listToMaybe . toList) singletons
   -- Return the new simplified problem
   return $ unitP x sequent
   where
     isSingle c = case (toList c) of { [a] -> True ; _ -> False }

{- ------------------------------ DPLL Algorithm ----------------------------- -}
dpll :: Ord p => Set (Set (Lit p)) -> Maybe (Set (Lit p))
dpll goalClauses = dpll' $ mzero :|-: goalClauses
  where 
     dpll' sequent@(assms :|-: clauses) = do 
       -- Fail early if falsum is a subgoal
       guard $ not (mzero `member` clauses)
       case (toList . join) $ clauses of
         -- Return the assumptions if there are no subgoals left
         []  -> return assms
         -- Otherwise try various tactics for resolving goals
         x:_ -> dpll' =<< msum [ pureRule sequent
                               , oneRule sequent
                               , return $ unitP x sequent
                               , return $ unitP (neg x) sequent ]
4

2 に答える 2

19

さて、使用するコードを変更するLogicことは完全に些細なことであることがわかりました。私はすべてを調べて書き直しSet、モナドではなくプレーン関数を使用しました。これは、モナドを統一された方法でSet実際に使用しているわけSetではなく、バックトラックロジック用でもないためです。モナドの内包表記も、マップやフィルターなどとしてより明確に記述されています。これは発生する必要はありませんでしたが、発生していることを整理するのに役立ちました。また、バックトラックに使用された、実際に残っている1つのモナドがちょうどであることが明らかになりましたMaybe

いずれの場合も、、、の型アノテーションを一般化して、pureRuleだけでなく、制約を使用oneRuledpllて操作することもできます。MaybemMonadPlus m =>

次に、でpureRule、sを明示的に作成するため、型が一致しないのでMaybe、少し変更してください。

in if (pure /= mzero) then Just sequent'
   else Nothing

になります

in if (not $ S.null pure) then return sequent' else mzero

そして、でoneRule、同様にの使用法をlistToMaybe明示的な一致に変更します。

   x <- (listToMaybe . toList) singletons

になります

 case singletons of
   x:_ -> return $ unitP x sequent  -- Return the new simplified problem
   [] -> mzero

また、型アノテーションの変更以外は、変更dpllする必要はまったくありません。

これで、コードはとの両方 Maybe Logic動作します!

コードを実行するにはLogic、次のような関数を使用できます。

dpllLogic s = observe $ dpll' s

などを使用observeAllして、より多くの結果を表示できます。

参考までに、完全に機能するコードは次のとおりです。

{-# LANGUAGE MonadComprehensions #-}
module DPLL where
import Prelude hiding (foldr)
import Control.Monad (join,mplus,mzero,guard,msum)
import Data.Set (Set, (\\), member, partition, toList, foldr)
import qualified Data.Set as S
import Data.Maybe (listToMaybe)
import Control.Monad.Logic

-- "Literal" propositions are either true or false
data Lit p = T p | F p deriving (Show,Ord,Eq)

neg :: Lit p -> Lit p
neg (T p) = F p
neg (F p) = T p

-- We model DPLL like a sequent calculus
-- LHS: a set of assumptions / partial model (set of literals)
-- RHS: a set of goals
data Sequent p = (Set (Lit p)) :|-: Set (Set (Lit p)) --deriving Show

{- --------------------------- Goal Reduction Rules -------------------------- -}
{- "Unit Propogation" takes literal x and A :|-: B to A,x :|-: B',
 - where B' has no clauses with x,
 - and all instances of -x are deleted -}
unitP :: Ord p => Lit p -> Sequent p -> Sequent p
unitP x (assms :|-:  clauses) = (assms' :|-:  clauses')
  where
    assms' = S.insert x assms
    clauses_ = S.filter (not . (x `member`)) clauses
    clauses' = S.map (S.filter (/= neg x)) clauses_

{- Find literals that only occur positively or negatively
 - and perform unit propogation on these -}
pureRule sequent@(_ :|-:  clauses) =
  let
    sign (T _) = True
    sign (F _) = False
    -- Partition the positive and negative formulae
    (positive,negative) = partition sign (S.unions . S.toList $ clauses)
    -- Compute the literals that are purely positive/negative
    purePositive = positive \\ (S.map neg negative)
    pureNegative = negative \\ (S.map neg positive)
    pure = purePositive `S.union` pureNegative
    -- Unit Propagate the pure literals
    sequent' = foldr unitP sequent pure
  in if (not $ S.null pure) then return sequent'
     else mzero

{- Add any singleton clauses to the assumptions
 - and simplify the clauses -}
oneRule sequent@(_ :|-:  clauses) =
   do
   -- Extract literals that occur alone and choose one
   let singletons = concatMap toList . filter isSingle $ S.toList clauses
   case singletons of
     x:_ -> return $ unitP x sequent  -- Return the new simplified problem
     [] -> mzero
   where
     isSingle c = case (toList c) of { [a] -> True ; _ -> False }

{- ------------------------------ DPLL Algorithm ----------------------------- -}
dpll goalClauses = dpll' $ S.empty :|-: goalClauses
  where
     dpll' sequent@(assms :|-: clauses) = do
       -- Fail early if falsum is a subgoal
       guard $ not (S.empty `member` clauses)
       case concatMap S.toList $ S.toList clauses of
         -- Return the assumptions if there are no subgoals left
         []  -> return assms
         -- Otherwise try various tactics for resolving goals
         x:_ -> dpll' =<< msum [ pureRule sequent
                                , oneRule sequent
                                , return $ unitP x sequent
                                , return $ unitP (neg x) sequent ]

dpllLogic s = observe $ dpll s
于 2012-07-31T17:41:07.937 に答える
7

Logicモナドを使用することによる具体的なパフォーマンス上の利点はありますか?

TL; DR:私が見つけることができるわけではありません。オーバーヘッドが少ないため、Maybeパフォーマンスが優れているように見えます。Logic


Logic対のパフォーマンスをチェックするために、簡単なベンチマークを実装することにしましたMaybe。私のテストでは、句を使用して5000個のCNFをランダムに作成しn、各句には3つのリテラルが含まれています。n句の数を変えてパフォーマンスを評価します。

私のコードでは、dpllLogic次のように変更しました。

dpllLogic s = listToMaybe $ observeMany 1 $ dpll s

また、次のように、公正な論理和dpllで変更をテストしました。

dpll goalClauses = dpll' $ S.empty :|-: goalClauses
  where
     dpll' sequent@(assms :|-: clauses) = do
       -- Fail early if falsum is a subgoal
       guard $ not (S.empty `member` clauses)
       case concatMap S.toList $ S.toList clauses of
         -- Return the assumptions if there are no subgoals left
         []  -> return assms
         -- Otherwise try various tactics for resolving goals
         x:_ -> msum [ pureRule sequent
                     , oneRule sequent
                     , return $ unitP x sequent
                     , return $ unitP (neg x) sequent ]
                >>- dpll'

Maybe次に、、、を使用して、公正な論理和Logicでテストしました。Logic

このテストのベンチマーク結果は次のとおりです。 たぶんモナドv。ロジックモナドv。論理和の論理和

ご覧のとおりLogic、この場合の公正な論理和の有無にかかわらず、違いはありません。モナドを使用したdpll解決はMaybe、で線形時間で実行されているように見えますが、モナドnを使用するとLogic追加のオーバーヘッドが発生します。頭上で高原が発生したようです。

Main.hsこれらのテストを生成するために使用されるファイルは次のとおりです。これらのベンチマークを再現したい人は、プロファイリングに関するHaskellのメモを確認したいと思うかもしれません。

module Main where
import DPLL
import System.Environment (getArgs)
import System.Random
import Control.Monad (replicateM)
import Data.Set (fromList)

randLit = do let clauses = [ T p | p <- ['a'..'f'] ]
                        ++ [ F p | p <- ['a'..'f'] ]
             r <- randomRIO (0, (length clauses) - 1)
             return $ clauses !! r

randClause n = fmap fromList $ replicateM n $ fmap fromList $ replicateM 3 randLit

main = do args <- getArgs
          let n = read (args !! 0) :: Int
          clauses <- replicateM 5000 $ randClause n
          -- To use the Maybe monad
          --let satisfiable = filter (/= Nothing) $ map dpll clauses
          let satisfiable = filter (/= Nothing) $ map dpllLogic clauses
          putStrLn $ (show $ length satisfiable) ++ " satisfiable out of "
                  ++ (show $ length clauses)
于 2012-08-06T04:37:36.450 に答える