Quick hacks to try to get this working again in 2021. test-20210812
authorMatt McCutchen <matt@mattmccutchen.net>
Thu, 12 Aug 2021 16:19:44 +0000 (12:19 -0400)
committerMatt McCutchen <matt@mattmccutchen.net>
Thu, 12 Aug 2021 16:19:44 +0000 (12:19 -0400)
program/BellmanFord.hs
program/PMDefaults.hs
program/README
program/RandomizedMonad.hs
program/TestUtils.hs
program/run

index 34e2a63..67e4b6a 100644 (file)
@@ -1,3 +1,5 @@
+{-# LANGUAGE DatatypeContexts #-}
+
 module BellmanFord (bellmanFord, BFPath(BFPath)) where
 import Data.Graph.Inductive.Graph
 import Data.Graph.Inductive.Internal.Queue
index f7de456..fc788a5 100644 (file)
@@ -12,13 +12,13 @@ pmDefaults = PMConfig {
 
 -- A naive implementation that is slow for all but the smallest instances
 -- (30s on a 20x50 example).
---minCostFlow = NaiveMinCostFlow.minCostFlow,
+minCostFlow = NaiveMinCostFlow.minCostFlow,
 
 -- Uses CS2 (http://www.igsystems.com/cs2/), which requires a license for
 -- non-research use but is faster (<1s on a 20x50 example, 64s on a 60x500
 -- example).  Configure the path to cs2.exe in CS2MinCostFlow.hs.  Remember to
 -- compile CS2 with -DPRINT_ANS, or this won't work!
-minCostFlow = CS2MinCostFlow.minCostFlow,
+--minCostFlow = CS2MinCostFlow.minCostFlow,
 
 -- The number of reviews each proposal should get.
 reviewsEachProposal = 4,
index ca47783..e6a24bb 100644 (file)
@@ -13,6 +13,8 @@ Requirements:
 - GHC on your $PATH
 - GHC "fgl" package
 
+(Required packages on Fedora 33 as of 2021-08-12: ghc-{fgl,random}-devel)
+
 Compile with "make".
 
 Interactive experimentation
index 22b98aa..59b8b92 100644 (file)
@@ -7,6 +7,7 @@ module RandomizedMonad (
        filterRandomized,
        indReplicateRandom, indRepeatRandom, indRandomArray
 ) where
+import Control.Monad
 import System.Random
 import Data.Array.IArray
 import Data.Ix
@@ -16,6 +17,17 @@ newtype Randomized a = Randomized (forall g. RandomGen g => (g -> (a, g)))
 
 -- This implementation threads a single RandomGen through the whole process in
 -- order to satisfy the monad laws.
+
+-- Migrate according to the guide at
+-- https://gitlab.haskell.org/ghc/ghc/-/wikis/migration/7.10#ghc-says-no-instance-for-applicative-
+-- ~ 2021-08-12
+instance Functor Randomized where
+       fmap = liftM
+
+instance Applicative Randomized where
+       pure x = Randomized (\g -> (x, g))
+       (<*>) = ap
+
 instance Monad Randomized where
        ma >>= amb = Randomized (\g -> let
                        Randomized fa = ma
@@ -23,7 +35,6 @@ instance Monad Randomized where
                        Randomized fb = amb a
                        in fb g2
                )
-       return x = Randomized (\g -> (x, g))
 
 -- Splits the generator and runs the argument on the left generator while
 -- threading the right generator on.  C.f. unsaveInterleaveIO.  Use this to
index 60b6f62..e842587 100644 (file)
@@ -2,14 +2,17 @@ module TestUtils where
 import Control.Concurrent
 import Data.Array.IArray
 import Data.Graph.Inductive.Graph
-import Data.Graph.Inductive.Graphviz
+-- I couldn't find this module any more. ~ 2021-08-12
+--import Data.Graph.Inductive.Graphviz
 import Data.Graph.Inductive.Tree
 import Data.List
 import System.IO
 import System.Random
 import System.Posix.IO
 import System.Posix.Time
-import System.Process
+-- createPipe creates an ambiguity with System.Posix.IO.createPipe. I think
+-- either should work, so hide this one.
+import System.Process hiding (createPipe)
 import PMInstance
 import PMConfig
 import ProposalMatcher
@@ -65,6 +68,9 @@ createHandlePipe = do
        wH <- fdToHandle wFd
        return (rH, wH)
 
+{- Comment this out because it depends on Data.Graph.Inductive.Graphviz, which I
+   don't have access to at the moment.
+
 -- GHCi seems to crash if I call this on a "showInstanceAsGraph" result without
 -- having previously forced evaluation of the matching.
 goGraph :: (Show a, Show b, Graph gr) => gr a b -> IO ()
@@ -81,6 +87,8 @@ goGraph theGraph =
        -- Then open the file.
        goFile fname
 
+-}
+
 -- Both-ways list difference
 (/\) :: Eq a => [a] -> [a] -> ([a], [a])
 l1 /\ l2 = (l1 \\ l2, l2 \\ l1)
index ab7d9d2..3bce7da 100755 (executable)
@@ -1,2 +1,2 @@
 #!/bin/bash
-make && exec ghci -cpp Test "$@"
+make && exec ghci -cpp -fglasgow-exts Test "$@"