
Hi,
I'll worry about the learning curve of beginners.
Maybe, beginners will try following session in their 1st week.
ghci> :t foldr
ghci> :t ($)
They'll get following result.
Before ghc7.8:
Prelude> :t foldr
foldr :: (a -> b -> b) -> b -> [a] -> b
Prelude> :t ($)
($) :: (a -> b) -> a -> b
Beginners should only understand about following:
* type variable (polymorphism)
After ghc8.0:
Prelude> :t foldr
foldr :: Foldable t => (a -> b -> b) -> b -> t a -> b
Prelude> :t ($)
($)
:: forall (w :: GHC.Types.Levity) a (b :: TYPE w).
(a -> b) -> a -> b
Beginners should understand about following things, more:
* higher order polymorphism (t m)
* type class (class t =>)
* universal quantification (forall)
* kind (type::kind)
* levity (lifted/unlifted)
I think it's harder in their 1st week.
I tried to draw informal illustrations about Foldable,
but beginners may need ghci-beginner’s mode or something?
Sorry I don't still have good idea.
Of course I like Haskell's abstraction :)
Regards,
Takenobu
2016-02-05 18:19 GMT+09:00 Joachim Breitner
Hi,
Am Freitag, den 05.02.2016, 09:22 +0200 schrieb Roman Cheplyaka:
On 02/05/2016 01:31 AM, Edward Z. Yang wrote:
I'm not really sure how you would change the type of 'id' based on a language pragma.
How do people feel about a cosmetic fix, where we introduce a new pragma, {-# LANGUAGE ShowLevity #-} which controls the display of levity arguments/TYPE. It's off by default but gets turned on by some extensions like MagicHash (i.e. we only show levity if you have enabled extensions where the distinction matters).
Yes, I am surprised this isn't the way it's been done. The levity arguments should totally be hidden unless requested explicitly.
I'd only expect this to be a ghc flag (-fshow-levity), not a language pragma, since it should only affect the way types are /shown/.
shouldn’t this already happen, based on -fprint-explicit-kinds? At least I would have expected this.
So we probably either want to make sure that -fno-print-explicit-kinds also prevents forall’ed kind variables, or add a new flag of that (heh) kind.
Greetings, Joachim
-- Joachim “nomeata” Breitner mail@joachim-breitner.de • http://www.joachim-breitner.de/ Jabber: nomeata@joachim-breitner.de • GPG-Key: 0xF0FBF51F Debian Developer: nomeata@debian.org
_______________________________________________ ghc-devs mailing list ghc-devs@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs