[commit: packages/hoopl] master: 1. <*> is included the Prelude of 7.10, it conflicts with Hoopl's def. change the code to use a qualified version. 2. we don't need to see warnings again in test, disable them. (a1a9a9e)

git at git.haskell.org git at git.haskell.org
Mon Dec 21 22:13:16 UTC 2015


Repository : ssh://git@git.haskell.org/hoopl

On branch  : master
Link       : http://git.haskell.org/packages/hoopl.git/commitdiff/a1a9a9e768e560a8320c946f7a108c55429b93fa

>---------------------------------------------------------------

commit a1a9a9e768e560a8320c946f7a108c55429b93fa
Author: Ning Wang <email at ningwang.org>
Date:   Tue May 5 19:21:38 2015 -0700

    1. <*> is included the Prelude of 7.10, it conflicts with Hoopl's def.  change the code to use a qualified version. 2. we don't need to see warnings again in test, disable them.


>---------------------------------------------------------------

a1a9a9e768e560a8320c946f7a108c55429b93fa
 hoopl.cabal           | 1 -
 testing/Ast2ir.hs     | 6 ++++--
 testing/EvalMonad.hs  | 2 +-
 testing/OptSupport.hs | 2 +-
 4 files changed, 6 insertions(+), 5 deletions(-)

diff --git a/hoopl.cabal b/hoopl.cabal
index aad6bc3..ac77173 100644
--- a/hoopl.cabal
+++ b/hoopl.cabal
@@ -79,7 +79,6 @@ Test-Suite hoopl-test
   Type:              exitcode-stdio-1.0
   Main-Is:           Main.hs
   Hs-Source-Dirs:    testing src
-  Ghc-Options:       -Wall
   Build-Depends:     base >= 4.3 && < 4.9, 
                      containers >= 0.4 && < 0.6,
                      parsec >= 3.1.7,
diff --git a/testing/Ast2ir.hs b/testing/Ast2ir.hs
index 56f0778..5647dfe 100644
--- a/testing/Ast2ir.hs
+++ b/testing/Ast2ir.hs
@@ -2,7 +2,9 @@
 {-# LANGUAGE CPP, RankNTypes, ScopedTypeVariables, GADTs, EmptyDataDecls, PatternGuards, TypeFamilies, NamedFieldPuns #-}
 module Ast2ir (astToIR, IdLabelMap) where
 
-import           Compiler.Hoopl
+
+import           Compiler.Hoopl hiding ((<*>))
+import qualified Compiler.Hoopl as H ((<*>))
 import           Control.Monad
 import qualified Data.Map       as M
 
@@ -52,7 +54,7 @@ toBlock (A.Block { A.first = f, A.mids = ms, A.last = l }) =
   do f'  <- toFirst f
      ms' <- mapM toMid ms
      l'  <- toLast l
-     return $ mkFirst f' <*> mkMiddles ms' <*> mkLast l'
+     return $ mkFirst f' H.<*> mkMiddles ms' H.<*> mkLast l'
 
 toFirst :: A.Lbl -> LabelMapM (I.Insn C O)
 toFirst = liftM I.Label . labelFor
diff --git a/testing/EvalMonad.hs b/testing/EvalMonad.hs
index 628a1f9..64d9ecf 100644
--- a/testing/EvalMonad.hs
+++ b/testing/EvalMonad.hs
@@ -18,7 +18,7 @@ import Control.Applicative (Applicative(..))
 import Control.Applicative (Applicative(..))
 #endif
 
-import Compiler.Hoopl
+import Compiler.Hoopl hiding ((<*>))
 import IR
 
 type ErrorM        = Either String
diff --git a/testing/OptSupport.hs b/testing/OptSupport.hs
index dacbcc4..a5c5fb9 100644
--- a/testing/OptSupport.hs
+++ b/testing/OptSupport.hs
@@ -14,7 +14,7 @@ import Control.Applicative (Applicative(..))
 import Control.Applicative (Applicative(..))
 #endif
 
-import Compiler.Hoopl
+import Compiler.Hoopl hiding ((<*>))
 import IR
 
 ----------------------------------------------



More information about the ghc-commits mailing list