New type of ($) operator in GHC 8.0 is problematic

Yuras Shumovich shumovichy at gmail.com
Sat Feb 13 16:40:09 UTC 2016


On Sat, 2016-02-13 at 13:41 +0100, Ben Gamari wrote:
> Ryan Scott <ryan.gl.scott at gmail.com> writes:
> 
> > Hi Chris,
> > 
> > The change to ($)'s type is indeed intentional. The short answer is
> > that ($)'s type prior to GHC 8.0 was lying a little bit. If you
> > defined something like this:
> > 
> >     unwrapInt :: Int -> Int#
> >     unwrapInt (I# i) = i
> > 
> ...
> 
> Hello everyone,
> 
> While this thread continues to smolder, it seems that the arguments
> relevant to the levity polymorphism change have been sussed out. Now
> seems like a good time to review what we have all learned,
> 
>  * In 7.10 and earlier the type of ($) is a bit of a lie as it did
> not
>    reflect the fact that the result type was open-kinded.
> 
>    ($) also has magic to allow impredicative uses, although this is
>    orthogonal to the present levity discussion.
>        
>  * the type of ($) has changed to become more truthful in 8.0: we now
>    capture lifted-ness in the type system with the notion of Levity.
> 
>  * there is widespread belief that the new type is too noisy and
>    obfuscates the rather simple concept embodied by ($). This is
>    especially concerning for those teaching and learning the
> language.
> 
>  * One approach to fix this would be to specialize ($) for lifted
> types
>    and introduce a new levity polymorphic variant. This carries the
>    potential to break existing users of ($), although it's unclear
> how
>    much code this would affect in practice.
> 
>  * Another approach would be to preserve the current lie with
>    pretty-printer behavior. This would be relatively easy to do and
>    would allow us to avoid breaking existing users of ($). This,
>    however, comes at the expense of some potential confusion when
>    polymorphism is needed.

Thank you for the summary! The thread is too big to find anything in
it.

I'd like to present a bit different approach, kind of a compromise,
without lie and code breakage: introduce a language pragma for levity
polymorphism and default levity polymorphic signatures to "*" when the
pragma is not enabled.

For example, ($) could be defined like it is right now:

($)
  :: forall (w :: GHC.Types.Levity) a (b :: TYPE w).
     (a -> b) -> a -> b

But when it is used in a module without levity polymorphism enabled,
"w" is defaulted to "Lifted", "b" gets kind "*", and ($) gets its old
type:

($)
  :: (a -> b) -> a -> b

So any use of ($) with types on kind "#" is disallowed.

But with levily polymorphism enabled, one will see the full type and
use ($) with unlifted types. To prevent breakage of the existing code,
MagicHash extension should by default imply levity polymorphism.

What do you think? Am I missing something?

Thanks,
Yuras.

>  * There are further questions regarding the appropriate kinds
>    of (->) and (.) [1]
> 
>  * Incidentally, there is a GHC or Haddock bug [2] which causes kind
>    signatures to be unnecessarily shown in documentation for some
> types,
>    exposing levities to the user.
> 
> The current plan to address this situation is as follows,
> 
>  * Introduce [3] a flag, -fshow-runtime-rep, which when disabled will
>    cause the pretty-printer to instantiate levity-polymorphic types
> as
>    lifted (e.g. resulting in *). This flag will be off by default,
>    meaning that users will in most cases see the usual lifted types
>    unless they explicitly request otherwise.
> 
>  * Fix the GHC/Haddock bug, restoring elision of unnecessary kind
>    signatures in documentation.
> 
>  * In the future we should seriously consider introducing an
> alternate
>    Prelude for beginners
>  
> As far as I can tell from the discussion, this was an acceptable
> solution to all involved. If there are any remaining objections or
> concerns let's discuss them in another thread.
> 
> Thanks to everyone who contributed to this effort.
> 
> Cheers,
> 
> - Ben
> 
> 
> [1] https://ghc.haskell.org/trac/ghc/ticket/10343#comment:27
> [2] https://ghc.haskell.org/trac/ghc/ticket/11567
> [3] https://ghc.haskell.org/trac/ghc/ticket/11549
> _______________________________________________
> ghc-devs mailing list
> ghc-devs at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


More information about the ghc-devs mailing list