LANGUAGE ConstraintKinds not needed to use ConstraintKinds?

Evan Laforge qdunkan at gmail.com
Mon Feb 15 02:15:21 UTC 2016


Right, that sounds like a good idea to me, it's the same reason I
added the synonym myself.

WRT not needing an extension I guess this is part of a general pattern
where you don't need extensions to use code that uses extensions.  In
this case though it seems a bit odd in that using the code that uses
extensions also requires previously illegal syntax.  But as long as
it's intentional it's fine by me.

But is the bit where the calling module needs FlexibleConstraints also
intentional?

On Mon, Feb 15, 2016 at 10:16 AM, Eric Seidel <eric at seidel.io> wrote:
> IIRC ConstraintKinds is only required in the module that defines the
> type synonym, so your module T does not need it. My guess is that
> haskell-src-exts sees 'Log.Stack =>', in which we have nullary
> constraint instead of a unary constraint, and assumes that's bogus
> without MultiParamTypeClasses. But I'm not familiar with
> haskell-src-exts' internals, so that's just a wild guess :)
>
> FYI, as of RC2 we provide a type synonym
>
>   type HasCallStack = (?callStack :: CallStack)
>
> in GHC.Stack, which is the recommended way to request a CallStack. We're
> hiding the implicit parameter from the docs and API, as the reliance on
> using the same name is a bit of a misfeature. We might also reimplement
> HasCallStack without implicit-params in the future, so in the interest
> of forward-compatibility I'd suggest using HasCallStack instead of your
> own implicit-parameters.
>
> Eric
>
>
> On Sun, Feb 14, 2016, at 16:32, Evan Laforge wrote:
>> I recently upgraded to ghc 8 and started using stacks via
>> ImplicitParams.  For that I wind up using 'type Stack = (?stack ::
>> CallStack)' and so ContraintKinds (I see that in the future GHC will
>> do this by default).
>>
>> So now I can have a file like:
>>
>> module T where
>> import qualified Log as Log
>>
>> f :: Log.Stack => IO ()
>> f = Log.warn "blah blah"
>>
>> I noticed that now haskell-src-exts refuses to parse this file, saying
>> 'MultiParamTypeClasses language extension is not enabled.'.
>>
>> I assume it's a bug with haskell-src-exts in that it should require
>> LANGUAGE ConstraintKinds instead, but then GHC itself doesn't want
>> ConstraintKinds.  Instead, it wants FlexibleContexts.  From the docs,
>> FlexibleContexts seems to be about the contexts in instance heads.
>>
>> Is this intentional?  I'll go ahead and make a bug for
>> haskell-src-exts, but the ghc behaviour here seems odd as well.  What
>> extension should haskell-src-exts require to parse this?
>> _______________________________________________
>> Glasgow-haskell-users mailing list
>> Glasgow-haskell-users at haskell.org
>> http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users
> _______________________________________________
> Glasgow-haskell-users mailing list
> Glasgow-haskell-users at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users


More information about the Glasgow-haskell-users mailing list