[commit: ghc] master: Use Proxy rather than undefined in MatchLit (1f770a5)
git at git.haskell.org
git at git.haskell.org
Thu May 11 21:33:46 UTC 2017
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/1f770a521e2331ce01007d36490d3b206afc6b4b/ghc
>---------------------------------------------------------------
commit 1f770a521e2331ce01007d36490d3b206afc6b4b
Author: Matthew Pickering <matthewtpickering at gmail.com>
Date: Thu May 11 15:42:23 2017 -0400
Use Proxy rather than undefined in MatchLit
Reviewers: austin, bgamari
Reviewed By: bgamari
Subscribers: rwbarton, thomie
Differential Revision: https://phabricator.haskell.org/D3565
>---------------------------------------------------------------
1f770a521e2331ce01007d36490d3b206afc6b4b
compiler/deSugar/MatchLit.hs | 47 ++++++++++++++++++++++----------------------
1 file changed, 24 insertions(+), 23 deletions(-)
diff --git a/compiler/deSugar/MatchLit.hs b/compiler/deSugar/MatchLit.hs
index e04e618..748de5c 100644
--- a/compiler/deSugar/MatchLit.hs
+++ b/compiler/deSugar/MatchLit.hs
@@ -49,6 +49,7 @@ import qualified GHC.LanguageExtensions as LangExt
import Control.Monad
import Data.Int
import Data.Word
+import Data.Proxy
{-
************************************************************************
@@ -156,21 +157,21 @@ warnAboutOverflowedLiterals :: DynFlags -> HsOverLit Id -> DsM ()
warnAboutOverflowedLiterals dflags lit
| wopt Opt_WarnOverflowedLiterals dflags
, Just (i, tc) <- getIntegralLit lit
- = if tc == intTyConName then check i tc (undefined :: Int)
- else if tc == int8TyConName then check i tc (undefined :: Int8)
- else if tc == int16TyConName then check i tc (undefined :: Int16)
- else if tc == int32TyConName then check i tc (undefined :: Int32)
- else if tc == int64TyConName then check i tc (undefined :: Int64)
- else if tc == wordTyConName then check i tc (undefined :: Word)
- else if tc == word8TyConName then check i tc (undefined :: Word8)
- else if tc == word16TyConName then check i tc (undefined :: Word16)
- else if tc == word32TyConName then check i tc (undefined :: Word32)
- else if tc == word64TyConName then check i tc (undefined :: Word64)
+ = if tc == intTyConName then check i tc (Proxy :: Proxy Int)
+ else if tc == int8TyConName then check i tc (Proxy :: Proxy Int8)
+ else if tc == int16TyConName then check i tc (Proxy :: Proxy Int16)
+ else if tc == int32TyConName then check i tc (Proxy :: Proxy Int32)
+ else if tc == int64TyConName then check i tc (Proxy :: Proxy Int64)
+ else if tc == wordTyConName then check i tc (Proxy :: Proxy Word)
+ else if tc == word8TyConName then check i tc (Proxy :: Proxy Word8)
+ else if tc == word16TyConName then check i tc (Proxy :: Proxy Word16)
+ else if tc == word32TyConName then check i tc (Proxy :: Proxy Word32)
+ else if tc == word64TyConName then check i tc (Proxy :: Proxy Word64)
else return ()
| otherwise = return ()
where
- check :: forall a. (Bounded a, Integral a) => Integer -> Name -> a -> DsM ()
+ check :: forall a. (Bounded a, Integral a) => Integer -> Name -> Proxy a -> DsM ()
check i tc _proxy
= when (i < minB || i > maxB) $ do
warnDs (Reason Opt_WarnOverflowedLiterals)
@@ -207,7 +208,7 @@ warnAboutEmptyEnumerations dflags fromExpr mThnExpr toExpr
, Just (from,tc) <- getLHsIntegralLit fromExpr
, Just mThn <- traverse getLHsIntegralLit mThnExpr
, Just (to,_) <- getLHsIntegralLit toExpr
- , let check :: forall a. (Enum a, Num a) => a -> DsM ()
+ , let check :: forall a. (Enum a, Num a) => Proxy a -> DsM ()
check _proxy
= when (null enumeration) $
warnDs (Reason Opt_WarnEmptyEnumerations) (text "Enumeration is empty")
@@ -217,17 +218,17 @@ warnAboutEmptyEnumerations dflags fromExpr mThnExpr toExpr
Nothing -> [fromInteger from .. fromInteger to]
Just (thn,_) -> [fromInteger from, fromInteger thn .. fromInteger to]
- = if tc == intTyConName then check (undefined :: Int)
- else if tc == int8TyConName then check (undefined :: Int8)
- else if tc == int16TyConName then check (undefined :: Int16)
- else if tc == int32TyConName then check (undefined :: Int32)
- else if tc == int64TyConName then check (undefined :: Int64)
- else if tc == wordTyConName then check (undefined :: Word)
- else if tc == word8TyConName then check (undefined :: Word8)
- else if tc == word16TyConName then check (undefined :: Word16)
- else if tc == word32TyConName then check (undefined :: Word32)
- else if tc == word64TyConName then check (undefined :: Word64)
- else if tc == integerTyConName then check (undefined :: Integer)
+ = if tc == intTyConName then check (Proxy :: Proxy Int)
+ else if tc == int8TyConName then check (Proxy :: Proxy Int8)
+ else if tc == int16TyConName then check (Proxy :: Proxy Int16)
+ else if tc == int32TyConName then check (Proxy :: Proxy Int32)
+ else if tc == int64TyConName then check (Proxy :: Proxy Int64)
+ else if tc == wordTyConName then check (Proxy :: Proxy Word)
+ else if tc == word8TyConName then check (Proxy :: Proxy Word8)
+ else if tc == word16TyConName then check (Proxy :: Proxy Word16)
+ else if tc == word32TyConName then check (Proxy :: Proxy Word32)
+ else if tc == word64TyConName then check (Proxy :: Proxy Word64)
+ else if tc == integerTyConName then check (Proxy :: Proxy Integer)
else return ()
| otherwise = return ()
More information about the ghc-commits
mailing list