Skip to content

Commit

Permalink
Merge pull request #122 from msakai/fix-some-warnings
Browse files Browse the repository at this point in the history
Fix some warnings
  • Loading branch information
msakai authored Nov 21, 2024
2 parents e6360e5 + 111b95b commit 46e1509
Show file tree
Hide file tree
Showing 8 changed files with 4 additions and 10 deletions.
3 changes: 0 additions & 3 deletions src/ToySolver/Converter/SAT2KSAT.hs
Original file line number Diff line number Diff line change
Expand Up @@ -21,14 +21,11 @@ module ToySolver.Converter.SAT2KSAT

import Control.Monad
import Control.Monad.ST
import Data.Array.MArray
import Data.Array.ST
import Data.Foldable (toList)
import Data.Sequence ((<|), (|>))
import qualified Data.Sequence as Seq
import Data.STRef

import ToySolver.Converter.Base
import ToySolver.Converter.Tseitin
import qualified ToySolver.FileFormat.CNF as CNF
import ToySolver.SAT.Formula
Expand Down
1 change: 0 additions & 1 deletion src/ToySolver/Converter/Tseitin.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,3 @@

{-# OPTIONS_GHC -Wall #-}
{-# OPTIONS_HADDOCK show-extensions #-}
{-# LANGUAGE TypeFamilies #-}
Expand Down
2 changes: 1 addition & 1 deletion src/ToySolver/FileFormat/CNF.hs
Original file line number Diff line number Diff line change
Expand Up @@ -239,7 +239,7 @@ toOldWCNF (NewWCNF cs)
, wcnfClauses = [(fromMaybe top w, c) | (w, c) <- cs]
}
where
top = sum [w | (Just w, c) <- cs] + 1
top = sum [w | (Just w, _c) <- cs] + 1

toNewWCNF :: WCNF -> NewWCNF
toNewWCNF wcnf = NewWCNF [(if w >= wcnfTopCost wcnf then Nothing else Just w, c) | (w, c) <- wcnfClauses wcnf]
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -34,7 +34,6 @@ module ToySolver.SAT.Encoder.Cardinality.Internal.Totalizer

import Control.Monad
import Control.Monad.Primitive
import Control.Monad.State.Strict
import qualified Data.IntSet as IntSet
import Data.Map.Strict (Map)
import qualified Data.Map.Strict as Map
Expand Down
2 changes: 1 addition & 1 deletion src/ToySolver/SAT/PBO/BCD2.hs
Original file line number Diff line number Diff line change
Expand Up @@ -217,7 +217,7 @@ solveWBO cxt solver opt = do
_ -> do
let torelax = unrelaxed `IntSet.intersection` failed
intersected = IntMap.elems (IntMap.restrictKeys sels failed)
disjoint = [core | (sel,(core,_)) <- IntMap.toList (IntMap.withoutKeys sels failed)]
disjoint = [core | (_sel,(core,_)) <- IntMap.toList (IntMap.withoutKeys sels failed)]
modifyIORef unrelaxedRef (`IntSet.difference` torelax)
modifyIORef relaxedRef (`IntSet.union` torelax)
delta <- do
Expand Down
1 change: 0 additions & 1 deletion test/Test/GraphShortestPath.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,6 @@
module Test.GraphShortestPath (graphShortestPathTestGroup) where

import Control.Monad
import Data.Hashable
import Data.Monoid
import Test.Tasty
import Test.Tasty.HUnit
Expand Down
2 changes: 1 addition & 1 deletion test/Test/SAT.hs
Original file line number Diff line number Diff line change
Expand Up @@ -617,7 +617,7 @@ case_setTerminateCallback = do

m <- try (SAT.solve solver)
case m of
Left (e :: SAT.Canceled) -> return ()
Left (_ :: SAT.Canceled) -> return ()
Right x -> assertFailure ("Canceled should be thrown: " ++ show x)

case_clearTerminateCallback :: IO ()
Expand Down
2 changes: 1 addition & 1 deletion test/Test/SAT/MUS.hs
Original file line number Diff line number Diff line change
Expand Up @@ -215,7 +215,7 @@ case_allMUSAssumptions_2_HYCAM = do
, [y2,y3,y5,y7,y8,y11]
, [y2,y4,y5,y6,y7,y8] -- (*)
]
mcses =
_mcses =
[ [y0,y1,y7]
, [y0,y1,y8]
, [y0,y3,y4]
Expand Down

0 comments on commit 46e1509

Please sign in to comment.