[GHC] #13482: PartialTypeSignatures, AllowAmbiguousTypes and ScopedTypeVariables don't play nicely together
GHC
ghc-devs at haskell.org
Sat Mar 25 16:37:15 UTC 2017
#13482: PartialTypeSignatures, AllowAmbiguousTypes and ScopedTypeVariables don't
play nicely together
-------------------------------------+-------------------------------------
Reporter: dramforever | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.2
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:
-------------------------------------+-------------------------------------
**Motivation**: I was playing with [http://lpaste.net/353915 something
like this] when I found this great confusion.
I was able to produce a minimal example. In each declaration/definition,
the function body is the same, but the signature varies.
I expect every single one of them to compile, resulting in the same type
as `minimal4`.
The actual results are shown in-line.
I think this sufficiently shows that this behavior is a bug.
(The line numbers in the following code aren't useful; I pasted them in
after compiling)
(The question marks are there because CMD wasn't able to display bullets,
I think.)
{{{#!hs
{-# LANGUAGE PartialTypeSignatures #-}
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE KindSignatures #-}
minimal1_noksig :: forall m. _ => Bool
minimal1_noksig = (mempty :: m) == (mempty :: m)
{-
ambi.hs:17:30: error:
? Expected a type, but ‘m’ has kind ‘k0’
? In an expression type signature: m
In the first argument of ‘(==)’, namely ‘(mempty :: m)’
In the expression: (mempty :: m) == (mempty :: m)
-}
minimal1 :: forall (m :: *). _ => Bool
minimal1 = (mempty :: m) == (mempty :: m)
{-
ambi.hs:11:1: error:
? Ambiguous type variable ‘m0’
prevents the constraint ‘(Monoid m0)’ from being solved.
? When checking that the inferred type
minimal1 :: forall m. (Monoid m, Eq m) => Bool
is as general as its (partial) signature
minimal1 :: Bool
-}
minimal2 :: forall m. (Eq m, _) => Bool
minimal2 = (mempty :: m) == (mempty :: m)
{-
ambi.hs:14:1: error:
? Could not deduce (Monoid m1)
from the context: (Eq m, Monoid m)
bound by the inferred type for ‘minimal2’:
(Eq m, Monoid m) => Bool
at ambi.hs:14:1-33
The type variable ‘m1’ is ambiguous
? When checking that the inferred type
minimal2 :: forall m. (Monoid m, Eq m) => Bool
is as general as its (partial) signature
minimal2 :: forall m. (Eq m, Monoid m) => Bool
-}
minimal3 :: forall m. (Monoid m, _) => Bool
minimal3 = (mempty :: m) == (mempty :: m)
-- Compiles
minimal4 :: forall m. (Monoid m, Eq m) => Bool
minimal4 = (mempty :: m) == (mempty :: m)
-- Compiles
}}}
The code was run in GHCi. GHC version is 8.0.2.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13482>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list