[commit: ghc] wip/gadtpm: minor stuff (8ea3741)
git at git.haskell.org
git at git.haskell.org
Thu Sep 17 13:01:46 UTC 2015
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/gadtpm
Link : http://ghc.haskell.org/trac/ghc/changeset/8ea37413839c010bc743641c74368db4a1a308d6/ghc
>---------------------------------------------------------------
commit 8ea37413839c010bc743641c74368db4a1a308d6
Author: George Karachalias <george.karachalias at gmail.com>
Date: Thu Sep 17 15:03:33 2015 +0200
minor stuff
>---------------------------------------------------------------
8ea37413839c010bc743641c74368db4a1a308d6
compiler/deSugar/Check.hs | 6 +-----
compiler/deSugar/Match.hs | 4 +---
2 files changed, 2 insertions(+), 8 deletions(-)
diff --git a/compiler/deSugar/Check.hs b/compiler/deSugar/Check.hs
index 6164b04..6cc9594 100644
--- a/compiler/deSugar/Check.hs
+++ b/compiler/deSugar/Check.hs
@@ -169,10 +169,9 @@ checkMatches vars matches
initial_uncovered :: [Id] -> DsM ValSetAbs
initial_uncovered vars = do
- us <- getUniqueSupplyM
ty_cs <- TyConstraint . bagToList <$> getDictsDs
tm_cs <- map (uncurry TmConstraint) . bagToList <$> getTmCsDs
- let vsa = map (VA . PmVar) vars -- zipWith mkValAbsVar (listSplitUniqSupply us) tys
+ let vsa = map (VA . PmVar) vars
return $ mkConstraint (ty_cs:tm_cs) (foldr Cons Singleton vsa)
{-
@@ -635,9 +634,6 @@ mkPatternVarSM ty = flip mkPatternVar ty <$> getUniqueSupplyM
mkPatternVarsSM :: [Type] -> UniqSM PatVec
mkPatternVarsSM tys = mapM mkPatternVarSM tys
-mkPmIdSM :: Type -> UniqSM Id
-mkPmIdSM ty = flip mkPmId ty <$> getUniqueSupplyM
-
mkPmId :: UniqSupply -> Type -> Id
mkPmId usupply ty = mkLocalId name ty
where
diff --git a/compiler/deSugar/Match.hs b/compiler/deSugar/Match.hs
index d542613..338a73b 100644
--- a/compiler/deSugar/Match.hs
+++ b/compiler/deSugar/Match.hs
@@ -19,7 +19,6 @@ import HsSyn
import TcHsSyn
import TcEvidence
import TcRnMonad
-import PmExpr
import Check
import CoreSyn
import Literal
@@ -717,8 +716,7 @@ matchEquations :: HsMatchContext Name
-> [Id] -> [EquationInfo] -> Type
-> DsM CoreExpr
matchEquations ctxt vars eqns_info rhs_ty
- = do { locn <- getSrcSpanDs
- ; let error_doc = matchContextErrString ctxt
+ = do { let error_doc = matchContextErrString ctxt
; match_result <- match vars rhs_ty eqns_info
More information about the ghc-commits
mailing list