[Haskell-cafe] Language complexity & beginners (Was: New type of ($) operator in GHC 8.0 is problematic)

Michał Antkiewicz mantkiew at gsd.uwaterloo.ca
Sat Feb 6 15:32:52 UTC 2016


Richard,

That is by far the best idea I've read in this entire thread!!!

There should be no more lies, no "beginner-only" preludes, etc. All
information should be available on request, effortlessly, as in your
example interaction with GHCi. I don't like having to set special
flags to see/hide certain info, as it was proposed. Having to use the
flags can easily mislead people who are not aware of them and also it
is too much work.

There was an issue raised with Haddocks. It's 2016 and we can easily
make the haddocks more interactive by embedding some JavaScript to
exactly recreate your interaction with GHCi or even, as a poor mans
substitute, simply show more details on mouse hoover or have similar
design like for showing instances, etc.

Every programmer should understand the difference between boxed and
unboxed values. Period. The fact that Haskell allows for levity
polimorphism is something we should be proud of and leverage in
teaching, not hide it or lie about it.

Finally, I wanted to highlight explicit type application as a great
didactic tool. We can now nicely provide types the same way as values
to the function and I find it a great way to explain type parameters.

Best,
Michał


On Fri, Feb 5, 2016 at 8:51 PM, Richard Eisenberg <eir at cis.upenn.edu> wrote:
> A bit of time away from my keyboard has revealed a natural way to solve this
> problem and others: be more like Idris.
>
> Normally, of course, I'm thinking about how Haskell's type system can be
> more like Idris's. But that's not what I mean here. I want Haskell's
> interface to be more like Idris's. Imagine this interchange:
>
> λ> :t ($)
> ($) :: (a -> b) -> a -> b
> -- click on the type
> ($) :: forall a b. (a -> b) -> a -> b
> -- click on the a
> ($) :: forall (a :: *) b. (a -> b) -> a -> b
> -- click on the b
> ($) :: forall (a :: *) (b :: *). (a -> b) -> a -> b   -- where b's kind has
> a different color than usual
> -- click on b's kind
> ($) :: forall {r :: RuntimeRep} (a :: *) (b :: TYPE r). (a -> b) -> a -> b
> -- mouseover RuntimeRep or TYPE reveals a tooltip
> "($) is representation-polymorphic, meaning that `b` can have an arbitrary
> runtime representation. Please see http://.... for more details."
>
> Similarly, classes would render in a special color, allowing you to click on
> them and choose to instantiate the type at a few in-scope instances of the
> class at hand, changing Foldable f => f a -> Int to the much simpler [a] ->
> Int.
>
> This is not a minor engineering project, but it would reap wonderful
> rewards, addressing the problems in this thread and more. No more lying
> (because all lies are clickable), no more fragmented language, no more
> brakes on development.
>
> Evidently, Chris already agrees with this proposal: #10073
> (https://ghc.haskell.org/trac/ghc/ticket/10073)
>
> Also see #8809 (https://ghc.haskell.org/trac/ghc/ticket/8809)
>
> Any volunteers to implement this? :)
>
> Richard
>
> On Feb 5, 2016, at 7:47 PM, Artyom <yom at artyom.me> wrote:
>
> I’ve amended my suggestion to say basically “this type is a slight lie,
> here’s a flag/command to see the true type” – this way we aren’t scaring
> people with implementation guts, merely letting them see the guts for
> themselves and then think “I don’t care about this” (which is, I think,
> exactly what should happen; the worst scenario here is that the beginner
> falls into the “I’m an advanced user, I need all features, I need to know
> everything, so I’ll enable the flag” trap – which is why it’s important not
> to call it “an advanced type” or mention “if you know what you’re doing” or
> anything else like that).
>
> I don’t agree that levity can be compared to Java’s “class” or “static” –
> not because it’s harder to understand, but because it’s much less widely
> used; I don’t feel that you need to know about levity in order to be a good
> Haskeller. Also, unboxed types don’t imply knowledge of levity – for
> instance, I’ve been successfully using unboxed types for a while, but I only
> found out about the true type of ($) by complete accident (I think I queried
> the kind of -> and then got curious about question marks). Of
>
> On 02/06/2016 03:27 AM, Mihai Maruseac wrote:
>
>
>
> On Fri, Feb 5, 2016 at 7:09 PM, Richard Eisenberg <eir at cis.upenn.edu> wrote:
>
> Another great question that has come up is about Haddock output (Hackage). I
> think Haddock needs to add a facility where library authors can include
> specializations of an overly general type. This can be done in commentary,
> but it's not as prominent. Such a new feature would address the ($) problem,
> as ($) :: forall (a :: *) (b :: *). (a -> b) -> a -> b is a specialization
> of its real type. It would also help a great deal with FTP-related
> generalizations.
>
> This goes hand in hand with Artyom's suggestion of a warning in GHCi
> after showing the simpler type.
>
> I'm thinking of a flag which enables/disables printing the simplest
> type with warning (in GHCi) or footnote (or otherwise, in Haddock). We
> can have the default behavior of the flag be either printing the
> simpler type + extra (warning/footnote) or printing the longer type
> and include a reference in our learning materials that beginners and
> people confused by the long, complex and real type, can use
> --use-simpler-types flag.
>
>
>
>
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
>


More information about the Haskell-Cafe mailing list