Re: [Haskell-cafe] Most Important GHC extensions to learn/use?

2012-06-03 Thread Gábor Lehel
On Fri, Jun 1, 2012 at 4:37 PM, James Cook mo...@deepbondi.net wrote:
 On Jun 1, 2012, at 6:11 AM, Gábor Lehel wrote:

 On Fri, Jun 1, 2012 at 6:29 AM, wren ng thornton w...@freegeek.org wrote:

    TypeFamilies (aka TFs)
        These are really nifty and they're all the rage these days. In
        a formal sense they're equivalent to fundeps, but in practice
        they're weaker than fundeps.

 Is that still true? The reason used to be that we didn't have
 superclass equalities, but we do have them now since 7.2. The only
 drawbacks I know of relative to FDs are that it's sometimes more
 typing, not supported by GeneralizedNewtypeDeriving, and doesn't allow
 OverlappingInstances (ick).

 In addition to other things mentioned today in the Fundeps and overlapping 
 instances thread, type families have no way of defining injective type 
 functions where the range includes already-existing types.

 For example, if you define:

 type family Succ a

 there is no way (that I've found) to define it in such a way that the 
 compiler can see that Succ a ~ Succ b = a ~ b.

 The equivalent in MPTCs+FDs would be:

 class Succ a b | a - b, b - a

class (S a ~ b, P b ~ a) = Succ a b where
type S a
type P b

(Succ a c, Succ b c)
=
(S a ~ c, P c ~ a, S b ~ c, P c ~ b)
=
(P c ~ a, P c ~ b)
=
(a ~ P c, P c ~ b)
=
(a ~ b)


 There is more discussion of this particular weakness at 
 http://hackage.haskell.org/trac/ghc/ticket/6018 .

 Also, there are less-common usages of fundeps that may be translatable to 
 type families but not easily, when there are complex interrelationships 
 between type variables.  For example, type-level binary operations will 
 sometimes have fundeps such as a b - c, a c - b, b c - a - that is to 
 say, any two determines the third.

Like above:

class (FD1 a b ~ c, FD2 b c ~ a, FD3 c a ~ b) = BinOp a b c where
type FD1 a b
type FD2 b c
type FD3 c a

You can mechanically translate MPTCs with FDs into MPTCs with ATs and
superclass equalities in this way, and your fingers will get a lot of
exercise. But that's the basis for the claim that TFs with superclass
equalities are no less powerful than FDs. It's true that this doesn't
always allow you to express everything as just plain top-level type
families, but then, neither do FDs :).

@wren, did you have some other examples in mind?

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Most Important GHC extensions to learn/use?

2012-06-01 Thread Gábor Lehel
On Fri, Jun 1, 2012 at 6:29 AM, wren ng thornton w...@freegeek.org wrote:

    TypeFamilies (aka TFs)
        These are really nifty and they're all the rage these days. In
        a formal sense they're equivalent to fundeps, but in practice
        they're weaker than fundeps.

Is that still true? The reason used to be that we didn't have
superclass equalities, but we do have them now since 7.2. The only
drawbacks I know of relative to FDs are that it's sometimes more
typing, not supported by GeneralizedNewtypeDeriving, and doesn't allow
OverlappingInstances (ick).

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Most Important GHC extensions to learn/use?

2012-06-01 Thread James Cook
On Jun 1, 2012, at 6:11 AM, Gábor Lehel wrote:

 On Fri, Jun 1, 2012 at 6:29 AM, wren ng thornton w...@freegeek.org wrote:
 
TypeFamilies (aka TFs)
These are really nifty and they're all the rage these days. In
a formal sense they're equivalent to fundeps, but in practice
they're weaker than fundeps.
 
 Is that still true? The reason used to be that we didn't have
 superclass equalities, but we do have them now since 7.2. The only
 drawbacks I know of relative to FDs are that it's sometimes more
 typing, not supported by GeneralizedNewtypeDeriving, and doesn't allow
 OverlappingInstances (ick).

In addition to other things mentioned today in the Fundeps and overlapping 
instances thread, type families have no way of defining injective type 
functions where the range includes already-existing types.

For example, if you define:

 type family Succ a

there is no way (that I've found) to define it in such a way that the compiler 
can see that Succ a ~ Succ b = a ~ b.

The equivalent in MPTCs+FDs would be:

 class Succ a b | a - b, b - a

There is more discussion of this particular weakness at 
http://hackage.haskell.org/trac/ghc/ticket/6018 .

Also, there are less-common usages of fundeps that may be translatable to type 
families but not easily, when there are complex interrelationships between type 
variables.  For example, type-level binary operations will sometimes have 
fundeps such as a b - c, a c - b, b c - a - that is to say, any two 
determines the third.

-- James
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Most Important GHC extensions to learn/use?

2012-06-01 Thread Ketil Malde
wren ng thornton w...@freegeek.org writes:

 There are a bunch which are mostly just syntax changes. The important
 ones are:

Also, if you have new GHC, it will often tell you if/when you need to
enable extensions.  E.g.:

  Line 8: 1 error(s), 0 warning(s)

  `Pos' has no constructors (-XEmptyDataDecls permits this)
  In the data type declaration for `Pos'

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Most Important GHC extensions to learn/use?

2012-06-01 Thread wren ng thornton
On 6/1/12 12:45 AM, Jonathan Geddes wrote:
 Thanks, Wren, I really appreciate the detailed response! Though I am
 surprised that Template Haskell isn't on your list. From the little I know
 of TH it seems like all of the interesting generic/generative stuff is done
 with TH. Do the other extensions subsume the need for TH, or is it just not
 terribly interesting?

TH is plenty interesting, but it's a very different sort of direction to
head. The extensions I mentioned are the ones I think everyone assumes a
seasoned Haskeller will know. With the exception of TFs and GADTs, those
extensions have all been around since the days of GHC 6.6 and Hugs. Thus,
most people consider them normal parts of Haskell even if they're not in
in the Report. Consequently, understanding them is necessary to understand
most of the non-H98 code on Hackage.


TH, on the other hand, is very much GHC-only and that's unlikely to
change. Also, there's a lot of unnecessary(?) grunge there. The basic
theory of staged computation which led to TH was laid out in the
MetaML/MetaOCaml papers. The version in MetaML is a lot nicer in terms of
the theory, so I'd suggest people start there before diving into TH. One
of the nice things in MetaML is that there's no limit on the levels of
meta-ness. This was removed from TH because it would require having the
compiler present in every executable; a sensible limitation, though it
complicates the theory. Another major difference is that MetaML only did
staging at the term level, whereas TH also allows splices in type
signatures, splices which generate type class instances, etc. These
extensions make TH *much* more powerful than MetaML, but also make it
*much* harder to understand and reason about. IMO the formal theory of
these non-term splices hasn't been worked out very well, which is part of
the reason why TH is so grungy to work with.

I'm a big fan of staged computation, and I'd definitely suggest any
sophisticated functional programmer should read the MetaML papers (and the
TH papers if so inclined, and the Flask papers to get a different
perspective on the theme). But very few packages require understanding TH
in order to understand them, and even fewer require understanding TH in
order to use them.

-- 
Live well,
~wren


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Most Important GHC extensions to learn/use?

2012-06-01 Thread wren ng thornton
On 6/1/12 6:11 AM, Gábor Lehel wrote:
 On Fri, Jun 1, 2012 at 6:29 AM, wren ng thorntonw...@freegeek.org  wrote:

 TypeFamilies (aka TFs)
 These are really nifty and they're all the rage these days. In
 a formal sense they're equivalent to fundeps, but in practice
 they're weaker than fundeps.

 Is that still true? The reason used to be that we didn't have
 superclass equalities, but we do have them now since 7.2. The only
 drawbacks I know of relative to FDs are that it's sometimes more
 typing, not supported by GeneralizedNewtypeDeriving, and doesn't allow
 OverlappingInstances (ick).

The superclass equalities was a big thing, but the disparity remains even
still.

The main problem is that type inference with fundeps remains more powerful
than type inference for TFs. There are still patterns of use which
infer/check easily with fundeps but which don't have an equivalent TF
implementation. I haven't messed with TFs enough to know the details here,
but there are other folks on the list who do.

In addition there's the issue of overlapping instances, which is currently
being discussed elsewhere.

-- 
Live well,
~wren


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Most Important GHC extensions to learn/use?

2012-05-31 Thread Jonathan Geddes
Haskell Hackers,

I'm pretty comfortable with all of Haskell 98 (and 2010, really). But I've
always sort of avoided extensions. I realize that this is a bit silly and
if I want to continue learning, it probably means delving into the
extensions. Which ones are the most important to know from a practical
point of view? And which ones from a {Language,Category,Math}-theoretical
point of view? (Any other interesting/important points of view I'm missing?
:D )

As always, thanks for the feedback.

Cheers,

--J Arthur
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Most Important GHC extensions to learn/use?

2012-05-31 Thread wren ng thornton

On 5/31/12 7:15 PM, Jonathan Geddes wrote:

Haskell Hackers,

I'm pretty comfortable with all of Haskell 98 (and 2010, really). But I've
always sort of avoided extensions. I realize that this is a bit silly and
if I want to continue learning, it probably means delving into the
extensions. Which ones are the most important to know from a practical
point of view? And which ones from a {Language,Category,Math}-theoretical
point of view? (Any other interesting/important points of view I'm missing?
:D )


There are a bunch which are mostly just syntax changes. The important 
ones are:


ForeignFunctionInterface (aka FFI)
Not technically part of H98, though it was a quick addition. It
is part of H2010, so it's not really an extension anymore.

ScopedTypeVariables
This one's really easy, and in the cases where you want it you
really really want it.

KindSignatures
This one's simple, and it helps expose you to the idea of
kinds, which is helpful for what's to come.

TypeOperators
This one's trivial, but it makes things a bit prettier.

FlexibleContexts, FlexibleInstances
These are essential for actually using MPTCs (described below).
IMO they should be enabled automatically whenever MPTCs are on.

And there are also a bunch of ones about extending the deriving 
mechanic to work with new classes or with newtypes.



Then there are the ones that actually change the language in a 
significant way. I'd say the critical ones to learn are:


RankNTypes (or Rank2Types if you're squeamish)
This is used in lots of nice tricks like list fusion. Learning
list fusion is a good place for the H98 veteran to explore
next, since it's easy to pick up and has many applications
outside of just doing list fusion. Also, it's been around
forever and isn't going anywhere anytime soon.

MultiParamTypeClasses (aka MPTCs)
This has been around forever, and is considered standard
Haskell by most people, even though it hasn't made it into the
Report yet (due the the fundeps vs TFs issue).

FunctionalDependencies (aka fundeps)
This is helpful for making certain MPTCs usable without too
many type signatures. Also, it's good for understanding the
fundeps vs TFs issue. Also, this one has been around forever,
and although it's fallen into disfavor it is still
indispensable due to limitations in TFs.

TypeFamilies (aka TFs)
These are really nifty and they're all the rage these days. In
a formal sense they're equivalent to fundeps, but in practice
they're weaker than fundeps.

GADTs
These are really nifty and they're all the rage these days.
Though beware, GADTs are a rabbit hole leading off to the world
of dependent types. You should be aware of the basic ideas
here, though don't worry too much about the theory (unless you
want to spend a lot of time worrying about the theory).

--
Live well,
~wren

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Most Important GHC extensions to learn/use?

2012-05-31 Thread Jonathan Geddes
Thanks, Wren, I really appreciate the detailed response! Though I am
surprised that Template Haskell isn't on your list. From the little I know
of TH it seems like all of the interesting generic/generative stuff is done
with TH. Do the other extensions subsume the need for TH, or is it just not
terribly interesting?

--J Arthur

On Thu, May 31, 2012 at 10:29 PM, wren ng thornton w...@freegeek.orgwrote:

 On 5/31/12 7:15 PM, Jonathan Geddes wrote:

 Haskell Hackers,

 I'm pretty comfortable with all of Haskell 98 (and 2010, really). But I've
 always sort of avoided extensions. I realize that this is a bit silly and
 if I want to continue learning, it probably means delving into the
 extensions. Which ones are the most important to know from a practical
 point of view? And which ones from a {Language,Category,Math}-**
 theoretical
 point of view? (Any other interesting/important points of view I'm
 missing?
 :D )


 There are a bunch which are mostly just syntax changes. The important ones
 are:

ForeignFunctionInterface (aka FFI)
Not technically part of H98, though it was a quick addition. It
is part of H2010, so it's not really an extension anymore.

ScopedTypeVariables
This one's really easy, and in the cases where you want it you
really really want it.

KindSignatures
This one's simple, and it helps expose you to the idea of
kinds, which is helpful for what's to come.

TypeOperators
This one's trivial, but it makes things a bit prettier.

FlexibleContexts, FlexibleInstances
These are essential for actually using MPTCs (described below).
IMO they should be enabled automatically whenever MPTCs are on.

 And there are also a bunch of ones about extending the deriving mechanic
 to work with new classes or with newtypes.


 Then there are the ones that actually change the language in a significant
 way. I'd say the critical ones to learn are:

RankNTypes (or Rank2Types if you're squeamish)
This is used in lots of nice tricks like list fusion. Learning
list fusion is a good place for the H98 veteran to explore
next, since it's easy to pick up and has many applications
outside of just doing list fusion. Also, it's been around
forever and isn't going anywhere anytime soon.

MultiParamTypeClasses (aka MPTCs)
This has been around forever, and is considered standard
Haskell by most people, even though it hasn't made it into the
Report yet (due the the fundeps vs TFs issue).

FunctionalDependencies (aka fundeps)
This is helpful for making certain MPTCs usable without too
many type signatures. Also, it's good for understanding the
fundeps vs TFs issue. Also, this one has been around forever,
and although it's fallen into disfavor it is still
indispensable due to limitations in TFs.

TypeFamilies (aka TFs)
These are really nifty and they're all the rage these days. In
a formal sense they're equivalent to fundeps, but in practice
they're weaker than fundeps.

GADTs
These are really nifty and they're all the rage these days.
Though beware, GADTs are a rabbit hole leading off to the world
of dependent types. You should be aware of the basic ideas
here, though don't worry too much about the theory (unless you
want to spend a lot of time worrying about the theory).

 --
 Live well,
 ~wren

 __**_
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/**mailman/listinfo/haskell-cafehttp://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe