[Haskell-cafe] Skolems!

evan@evan-borden.com evan at evanrutledgeborden.dreamhosters.com
Fri Feb 27 18:23:45 UTC 2015


An extension of the message Tom sent a little while back, we've discovered
a more in depth example of this possible GHC bug. It is exacerbated by
GADTs, but can be fixed with NoMonoLocalBinds. Without GADTs and just
leveraging ExistentialQuanitification 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)
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20150227/2a5b2260/attachment.html>


More information about the Haskell-Cafe mailing list