Skip to content

Commit

Permalink
Merge pull request #92 from msakai/ghc-9.4
Browse files Browse the repository at this point in the history
Support GHC-9.4
  • Loading branch information
msakai committed Sep 20, 2022
2 parents b225e92 + c74fce1 commit 62acc18
Show file tree
Hide file tree
Showing 7 changed files with 10 additions and 4 deletions.
1 change: 1 addition & 0 deletions app/toysat/toysat.hs
@@ -1,6 +1,7 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# OPTIONS_GHC -Wall -fno-warn-unused-do-bind #-}
-----------------------------------------------------------------------------
-- |
Expand Down
1 change: 1 addition & 0 deletions src/ToySolver/Converter/Base.hs
Expand Up @@ -2,6 +2,7 @@
{-# OPTIONS_HADDOCK show-extensions #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
-----------------------------------------------------------------------------
-- |
-- Module : ToySolver.Converter.Base
Expand Down
1 change: 1 addition & 0 deletions src/ToySolver/Data/Polynomial/Base.hs
Expand Up @@ -5,6 +5,7 @@
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# OPTIONS_GHC -Wall #-}
{-# OPTIONS_HADDOCK show-extensions #-}
-----------------------------------------------------------------------------
Expand Down
3 changes: 2 additions & 1 deletion src/ToySolver/Graph/ShortestPath.hs
Expand Up @@ -76,6 +76,7 @@ import qualified Data.IntMap.Strict as IntMap
import qualified Data.IntSet as IntSet
import qualified Data.Heap as Heap -- http://hackage.haskell.org/package/heaps
import Data.List (foldl')
import Data.Maybe (fromJust)
import Data.Monoid
import Data.Ord
import Data.Sequence (Seq)
Expand Down Expand Up @@ -304,7 +305,7 @@ bellmanFord (Fold fV fE fC fD) g ss = runST $ do
writeSTRef updatedRef IntSet.empty
forM_ (IntSet.toList us) $ \u -> do
-- modifySTRef' updatedRef (IntSet.delete u) -- possible optimization
Just (Pair du a) <- H.lookup d u
Pair du a <- liftM fromJust $ H.lookup d u
forM_ (IntMap.findWithDefault [] u g) $ \(v, c, l) -> do
m <- H.lookup d v
case m of
Expand Down
3 changes: 2 additions & 1 deletion src/ToySolver/SAT/Encoder/PB/Internal/Adder.hs
Expand Up @@ -71,7 +71,8 @@ encodePBLinAtLeastAdder' enc (lhs,rhs) = do
encodePBLinSumAdder :: forall m. PrimMonad m => Tseitin.Encoder m -> SAT.PBLinSum -> m [SAT.Lit]
encodePBLinSumAdder enc lhs = do
(buckets :: MutVar (PrimState m) (Seq (SQ.SeqQueue m SAT.Lit))) <- newMutVar Seq.empty
let insert i x = do
let insert :: Int -> Int -> m ()
insert i x = do
bs <- readMutVar buckets
let n = Seq.length bs
q <- if i < n then do
Expand Down
1 change: 1 addition & 0 deletions src/ToySolver/Text/SDPFile.hs
Expand Up @@ -3,6 +3,7 @@
{-# LANGUAGE GADTs #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeOperators #-}
{-# OPTIONS_GHC -Wall #-}
{-# OPTIONS_HADDOCK show-extensions #-}
-----------------------------------------------------------------------------
Expand Down
4 changes: 2 additions & 2 deletions toysolver.cabal
Expand Up @@ -130,8 +130,8 @@ Library
Hs-source-dirs: src
Build-Depends:
array >=0.5,
-- GHC >=8.6 && <9.3
base >=4.12 && <4.17,
-- GHC >=8.6 && <9.5
base >=4.12 && <4.18,
bytestring >=0.9.2.1 && <0.12,
bytestring-builder,
bytestring-encoding >=0.1.1.0,
Expand Down

0 comments on commit 62acc18

Please sign in to comment.