[GHC] #11374: `-Woverlapping-patterns` induced memory-blowup
GHC
ghc-devs at haskell.org
Thu Jan 7 20:10:43 UTC 2016
#11374: `-Woverlapping-patterns` induced memory-blowup
-------------------------------------+-------------------------------------
Reporter: hvr | Owner: gkaracha
Type: bug | Status: new
Priority: highest | Milestone: 8.0.1
Component: Compiler | Version: 8.1
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: None/Unknown
Unknown/Multiple |
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
I'm afraid I've found yet another case that still let's the pattern
checker go crazy (courtesy of hackage:cryptol-2.2.5):
{{{#!hs
{-# LANGUAGE Haskell2010 #-}
{-# OPTIONS_GHC -Woverlapping-patterns #-}
module Bug where
data Type = TCon TCon [Type]
| TUser String [Type] Type
| TRec [(String,Type)]
deriving (Show,Eq,Ord)
data TCon = TC TC
| TF TFun
deriving (Show,Eq,Ord)
data TC = TCNum Integer
| TCInf
| TCBit
| TCSeq
| TCFun
| TCTuple Int
deriving (Show,Eq,Ord)
data TFun = TCAdd
| TCSub
| TCMul
| TCDiv
| TCMod
| TCLg2
| TCExp
| TCWidth
| TCMin
| TCMax
| TCLenFromThen
| TCLenFromThenTo
deriving (Show, Eq, Ord, Bounded, Enum)
simpFinTy :: Type -> Maybe [Type]
simpFinTy ty = case ty of
TCon (TC (TCNum _)) _ -> Just []
TCon (TF tf) [t1]
| TCLg2 <- tf -> Just [t1]
| TCWidth <- tf -> Just [t1]
TCon (TF tf) [t1,t2]
| TCAdd <- tf -> Just [t1, t2]
| TCSub <- tf -> Just [t1]
| TCMul <- tf -> Just [t1, t2]
| TCDiv <- tf -> Just [t1]
| TCMod <- tf -> Just []
| TCExp <- tf -> Just [t1, t2]
| TCMin <- tf -> Nothing
| TCMax <- tf -> Just [t1, t2]
TCon (TF tf) [_,_,_]
| TCLenFromThen <- tf -> Just []
| TCLenFromThenTo <- tf -> Just []
_ -> Nothing
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/11374>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list