Why is `($)` not fully representation polymorphic?

Hi, I am writing here because I do not understand a current limitation of ($) that nobody else could explain to me: It is not fully representation polymorphic. I.e. its type is:
($) :: forall (r :: GHC.Types.RuntimeRep) a (b :: TYPE r). (a -> b) -> a -> b

The limitation is explained in the levity polymorphism section of the manual here. However, this explanation is indeed unsatisfying because this seems to be merely an implementation detail:

{-# INLINE ($) #-}
($) :: forall r a (b :: TYPE r). (a -> b) -> a -> b
f $ x =  f x

There is no reasoning on why ($) is not simply eta reduced; Indeed: defining it as:

($) :: forall repa repb (a :: TYPE repa) (b :: TYPE repb). (a -> b) -> a -> b
($) f = f -- or even ($) = id
{-# INLINE ($) #-}

infixr 0 $

seems to work perfectly fine. Now the questions are: Am I overlooking something? Are there any problems with that implementation?

See here for a showcase of this implementation being useful in cases where the original $ is not polymorphic enough.

10 Likes

It would also be nice if it were multiplicity polymorphic, such that you wouldn’t need to use the one from linear-base.

4 Likes

You might like to see [Haskell-cafe] Actual levity polymorphism for a related discussion (though not quite on exactly your topic).

2 Likes

I will open an issue in the CLC GH repo proposing this generalization if there is no issue found with this until next Tuesday.

1 Like

I have opened a proposal to generalize ($) in the github repo of the haskell core libraries commitee.

1 Like

In addition to tomjaguarpaw’s suggestion: you should also see [ghc-devs] New type of ($) operator in GHC 8.0 is problematic.

1 Like

This is not a concern anymore, try it out, this information is hidden for the normal user without enabling certain flags. Nobody is proposing to backport this change to (base compatible with) earlier GHC versions either.

(the relevant flag is -fprint-explicit-runtime-reps or -fno-print-explicit-runtime-reps for that matter)

4 Likes

Yes, anyone who’s used ghci since 2016 can attest that it doesn’t print runtime reps.

3 Likes

Good! So similar measures should be taken in this situation - place this change to ($)'s type signature under the control of an option or flag (old or new) to GHC, to avoid similarly-unexpected surprises. ($) is used everywhere in Haskell codebases, so if this particular generalisation ends up being a breaking change, it will be extremely ugly.

At the very least, as a basic test you should try to rebuild GHC with this change…

2 Likes

I mean, you can just try it out in your own ghci. Again, this is not an issue, ghci does not display the explicit runtime reps without passing :set -fprint-explicit-runtime-reps. This is generally the case, i.e. for all functions, including ones you defined yourself.

Try it out with

  • open ghci
  • type g :: () -> (a :: TYPE rep); g _ = undefined
  • type :t g
  • by default the output will be g :: () -> a

I hope it is more clear now.

2 Likes

The proposal to change this has been approved and the change will probably be in base 4.19, shipping with ghc 9.8.1 Make `($)` fully representation polymorphic · Issue #132 · haskell/core-libraries-committee · GitHub

8 Likes