[GHC] #10130: Rigid/Skolum produced by unassociated values.
GHC
ghc-devs at haskell.org
Mon Mar 2 19:08:30 UTC 2015
#10130: Rigid/Skolum produced by unassociated values.
-------------------------------------+-------------------------------------
Reporter: | Owner:
dukerutledge | Status: new
Type: bug | Milestone:
Priority: normal | Version: 7.8.4
Component: Compiler | Operating System: Linux
Keywords: rigid, | Type of failure: Compile-time
skolum, | crash
existentialquantification, gadts, | Blocked By:
nomonolocalbinds | Related Tickets:
Architecture: x86_64 |
(amd64) |
Test Case: |
Blocking: |
Differential Revisions: |
-------------------------------------+-------------------------------------
Here is an in depth example of a possible GHC bug. It is exacerbated by
GADTs, but can be fixed with NoMonoLocalBinds. Without GADTs and just
leveraging ExistentialQuantification it works fine. We've included a
pretty exhaustive set of examples.
{{{
{-# LANGUAGE ExistentialQuantification, GADTs #-}
{- removing MonoLocalBinds fixes all of these errors
{-# LANGUAGE ExistentialQuantification, GADTs, NoMonoLocalBinds #-}
-}
module PossibleGHCBug where
data SumType = SumFoo | SumBar
class SomeClass a where
someType :: a -> SumType
data SomeExistential = forall a. SomeClass a => SomeExistential a
noError :: String -> [SomeExistential] -> String
noError n st = n ++ concatMap cname st
where cname (SomeExistential p) = d p
d p = c $ someType p
c p = case p of
SumFoo -> "foo"
_ -> "asdf"
noError2 :: String -> [SomeExistential] -> String
noError2 n st = n ++ concatMap cname st
where cname (SomeExistential p) = d p
d p = c $ someType p
c :: SumType -> String
c p = case p of
SumFoo -> "foo"
_ -> "asdf" ++ n
noError3 :: String -> [SomeExistential] -> String
noError3 n st = n ++ concatMap cname st
where cname (SomeExistential p) = d p
d :: SomeClass a => a -> String
d p = c $ someType p
c p = case p of
SumFoo -> "foo"
_ -> "asdf" ++ n
partialTypedError :: String -> [SomeExistential] -> String
partialTypedError n st = n ++ concatMap cname st
where cname :: SomeExistential -> String
cname (SomeExistential p) = d p
d p = c $ someType p
c p = case p of
SumFoo -> "foo"
_ -> "asdf" ++ n
fullError :: String -> [SomeExistential] -> String
fullError n st = n ++ concatMap cname st
where cname (SomeExistential p) = d p
d p = c $ someType p
c p = case p of
SumFoo -> "foo"
_ -> "asdf" ++ n
justNError :: String -> [SomeExistential] -> String
justNError n st = n ++ concatMap cname st
where cname (SomeExistential p) = d p
d p = c $ someType p
c p = case p of
SumFoo -> "foo"
_ -> n
ignoreNError :: String -> [SomeExistential] -> String
ignoreNError n st = n ++ concatMap cname st
where cname (SomeExistential p) = d p
d p = c $ someType p
c p = case p of
SumFoo -> "foo"
_ -> fst ("foo", n)
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/10130>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list