[commit: packages/hoopl] master: Fix all warnings in testing/ (d9e9cee)
git at git.haskell.org
git at git.haskell.org
Mon Dec 21 22:13:28 UTC 2015
Repository : ssh://git@git.haskell.org/hoopl
On branch : master
Link : http://git.haskell.org/packages/hoopl.git/commitdiff/d9e9cee04b9821a263633f81d1943374012be724
>---------------------------------------------------------------
commit d9e9cee04b9821a263633f81d1943374012be724
Author: Michal Terepeta <michal.terepeta at gmail.com>
Date: Sun Jun 7 20:01:24 2015 +0200
Fix all warnings in testing/
>---------------------------------------------------------------
d9e9cee04b9821a263633f81d1943374012be724
testing/Ast.hs | 4 ++--
testing/Eval.hs | 2 +-
testing/EvalMonad.hs | 5 +----
testing/Ir2ast.hs | 2 +-
testing/Test.hs | 2 +-
5 files changed, 6 insertions(+), 9 deletions(-)
diff --git a/testing/Ast.hs b/testing/Ast.hs
index e7333d2..0f27727 100644
--- a/testing/Ast.hs
+++ b/testing/Ast.hs
@@ -51,8 +51,8 @@ instance Show Control where
show (Branch lbl) = ind $ "goto " ++ lbl
show (Cond e t f) =
ind $ "if " ++ show e ++ " then goto " ++ t ++ " else goto " ++ f
- show (Call ress f cargs succ) =
- ind $ tuple ress ++ " = " ++ f ++ tuple (map show cargs) ++ " goto " ++ succ
+ show (Call ress f cargs successor) =
+ ind $ tuple ress ++ " = " ++ f ++ tuple (map show cargs) ++ " goto " ++ successor
show (Return rargs) = ind $ "ret " ++ tuple (map show rargs)
ind :: String -> String
diff --git a/testing/Eval.hs b/testing/Eval.hs
index 9eaca6e..4c25a5d 100644
--- a/testing/Eval.hs
+++ b/testing/Eval.hs
@@ -3,7 +3,7 @@
module Eval (evalProg, ErrorM) where
-import Control.Monad.Error
+import Control.Monad.Except
import qualified Data.Map as M
import Prelude hiding (succ)
diff --git a/testing/EvalMonad.hs b/testing/EvalMonad.hs
index 64d9ecf..0878dfa 100644
--- a/testing/EvalMonad.hs
+++ b/testing/EvalMonad.hs
@@ -6,7 +6,7 @@ module EvalMonad (ErrorM, VarEnv, B, State,
get_var, set_var, get_heap, set_heap,
Event (..), event) where
-import Control.Monad.Error
+import Control.Monad.Except
import qualified Data.Map as M
import Prelude hiding (succ)
@@ -23,9 +23,6 @@ import IR
type ErrorM = Either String
type InnerErrorM v = Either (State v, String)
-instance Error (State v, String) where
- noMsg = (undefined, "")
- strMsg str = (undefined, str)
data EvalM v a = EvalM (State v -> InnerErrorM v (State v, a))
diff --git a/testing/Ir2ast.hs b/testing/Ir2ast.hs
index fdc9c77..c16cb2c 100644
--- a/testing/Ir2ast.hs
+++ b/testing/Ir2ast.hs
@@ -50,7 +50,7 @@ fromBlock blk = foldBlockNodesF3 (fromIrInstCO, fromIrInstOO, fromIrInstOC) blk
fromIrInstCO :: I.Insn C O -> () -> Rm (A.Lbl, [A.Insn])
-fromIrInstCO inst p = case inst of
+fromIrInstCO inst _ = case inst of
I.Label l -> strLabelFor l >>= \x -> return (x, [])
diff --git a/testing/Test.hs b/testing/Test.hs
index 1f83c72..94b0f06 100644
--- a/testing/Test.hs
+++ b/testing/Test.hs
@@ -3,7 +3,7 @@
module Test (parseTest, evalTest, optTest) where
import Compiler.Hoopl
-import Control.Monad.Error
+import Control.Monad.Except
import System.Exit
import qualified Ast as A
More information about the ghc-commits
mailing list