Re: [Haskell-cafe] Language extensions

2007-05-31 Thread Tomasz Zielonka
On Wed, May 30, 2007 at 05:12:48PM +0200, Henk-Jan van Tuyl wrote:
 On Wed, 30 May 2007 09:38:10 +0200, Tomasz Zielonka  
 [EMAIL PROTECTED] wrote:
 On Tue, May 29, 2007 at 09:43:03PM +0100, Andrew Coppin wrote:
 Henning Thielemann wrote:
 On Sun, 27 May 2007, Andrew Coppin wrote:
 But every now and then I discover an expression which is
 apparently  not expressible without them - which is odd,
 considering they're only sugar...
 
 Example?
 
 Until I learned the trick of using lists as monads, I was utterly
 perplexed as to how to get a Cartesian product
 
 This is far from not expressible:
 cart xs ys = concatMap (\x - map ((,) x) ys) xs
 
 A bit simpler is:
   cart xs ys = [(x, y) | x - xs, y - ys]
 
 or:
   cart xs ys =
 do
   x - xs
   y - ys
   return (x, y)

I was responding to Andrew saying that computing cartesian product is
apparently not expressible without list comprehensions.

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


Re: [Haskell-cafe] Language extensions

2007-05-31 Thread Roberto Zunino

Tomasz Zielonka wrote:

On Wed, May 30, 2007 at 11:21:45PM +0200, Roberto Zunino wrote:

($!) Data.List.repeat -- ;-) unbounded types


You got me - I'm not sure how to respond to that. Let's try: this
function doesn't preserve computable equality.


Ah, silly me! I checked that inequality was preserved, but forgot that 
(==) diverges on infinite list!


Indeed, strictly speaking, Eq [] does not satisfy the Eq invariant x==x.


BTW, why so many exclamation marks in your code? Are they essential?


Only strict g's are allowed in parametericity, IIUC. Otherwise:

let g = \x - (x,4)

f (map g []) == g (f [])  iff
f [] == g bottom  iff
bottom   == (bottom,4)which is false.

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


Re: [Haskell-cafe] Language extensions [was: Memoization]

2007-05-31 Thread Martin Percossi

I really liked this explanation -- very clear, with good analogies.

Thanks!

Martin
My music: http://www.youtube.com/profile?user=thetonegrove

Claus Reinke wrote:




quantified types (forall/exist):
 an easy way to memorize this is to think of 'forall' as a big 'and'
 and of 'exists' as a big 'or'.
   e :: forall a. a  -- e has type 'Int' and type 'Bool' and type ..
   e :: exists a. a  -- e has type 'Int' or  type 'Bool' or  type ..



That doesn't entirely make sense. (What am I on about? That doesn't 
make *any* sense...)



indeed?-) then you've probably already figured out what those types
mean! there aren't many variations of an expression that has *all* types
(you can't please everyone), and if an expression has a type but we
have no way of knowing what that type is, there isn't much we can do
with it (like advice from the Oracle of Delphi).  but both of these
kinds of quantified types make a lot more sense in larger contexts.
lets take 'forall'/'big and' first: the problem with 'forall a. a' is to
produce something that is everything to everyone, which is rather hard;
but what about 'forall a. a - a'? that is like a general shipping
agency - they don't care what you give them, they just put it in a box
and move it from one place to another (if it doesn't like to be shipped
in such an indifferent way, it'll break, but that's not their problem);
such general shipping is both 'Integer' shipping *and* 'String' shipping
*and* ..; other examples are 'forall a. a - a - a', which is a general
selector (given two 'a's, it returns one of them), or 'forall a,b. a 
- b - a' (given an 'a' and a 'b', it returns the 'a').


'id :: forall a. a - a' can be instantiated to 'id :: Bool - Bool'
*and* to 'id :: Char - Char' *and* to all other identities on rank-1
types besides, so one could say that it really has *all* of those types.

what about 'exists'/'big or' then? the problem with 'exists a. a' is
that while we know there exists a type, we have no way of knowing what 
that type is, so we can't really do anything with an expression of 
such a type.

that is very much like an abstract data type, implemented on top
of a hidden representation type. what we need are some operations on 
that abstract type, so how about

   'exists r.(r a, r a - a - r a, r a - a)'

we still don't know what 'r' is, but we have some 'r a', we have a way
to combine 'r a' and 'a' into a new 'r a', and a way to extract an 'a'
from an 'r a', so we're no longer entirely helpless. in fact, that looks
a lot like an abstract container type, perhaps a stack with push and
top, or a queue with add and front, or a cell with put and get. 
whatever it may be, the 'r' is hidden, so it could be

   '([a], [a]-a-[a], [a]-a)'
*or* it could be
   '(Set a, Set a - a - Set a, Set a - a)'
*or* it could be based on *any* other rank-1 type constructor.

hth,
claus

oracle advice: 'invade :: exists great_empire. great_empire - ()'



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



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


Re: [Haskell-cafe] Language extensions

2007-05-31 Thread Jules Bean

Roberto Zunino wrote:
Ah, silly me! I checked that inequality was preserved, but forgot that 
(==) diverges on infinite list!


Indeed, strictly speaking, Eq [] does not satisfy the Eq invariant x==x.


All haskell types contain divergence. So all Eq types have exactly this 
same problem.


We 'like' infinite lists because they are a kind of 'productive 
divergence'. But they still diverge.



Jules

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


Re: [Haskell-cafe] Language extensions [was: Memoization]

2007-05-30 Thread Ketil Malde
On Tue, 2007-05-29 at 21:28 +0100, Andrew Coppin wrote:

  phantom types:
   the types of ghost values (in other words, we are only interested in
   the type, not in any value of that type).

 Mmm... Still not seeing a great amount of use for this one.

The point is to 'tag' something with a type (at compile time) without
actually having any value of that type around at run time.

For instance, you could use this to keep track of the encodings for
strings of 8-bit characters.

Say you have a data type for your strings, like so:

data FPS enc = FPS [Word8] deriving Show

'enc' is now a phantom type, it has no bearing on the actual value,
which is always a list of Word8s, right?

You can then define a set of encoding data types, and class for them:

data Latin1
data KOI8R

class Encoding e where
   w2c :: e - Word8 - Char
   c2w :: e - Char  - Word8

The Latin1 instance is easy:

instance Encoding Latin1 where
   w2c _ = chr . fromIntegral
   c2w _ = fromIntegral . ord

KOI8 is a bit more involved, so I omit that.  Now we can define
functions for converting to/from [Char]:

pack :: forall e . Encoding e = String - FPS e
pack = FPS . map (c2w (undefined :: e))

unpack :: forall e . Encoding e = FPS e - String 
unpack (FPS s) = map (w2c (undefined :: e)) s

Loading this in GHCi (requires -fglasgow-exts), you can do:

*Main pack foobar  :: FPS Latin1
FPS [102,111,111,98,97,114]

i.e. ord 'f' to ord 'r'.

*Main pack foobar  :: FPS KOI8R
FPS [202,211,211,198,197,214]

This is a fake KOI8R instance, but demonstrates the point: by requiring
a different type, a different result is achieved.  Note that the
resulting FPS retains the type, so that when I do:

*Main unpack it
foobar

...I get back the original string.

Disclaimers: There are more elaborate and elegant examples of phantom
types out there, look for e.g. Oleg's posts on the subject.  The above
does not constitute legal advice.  Slippery when wet, do not cover,
batteries not included, and your mileage may vary.

-k




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


Re: [Haskell-cafe] Language extensions

2007-05-30 Thread Ketil Malde
On Tue, 2007-05-29 at 21:39 +0100, Andrew Coppin wrote:

 My point is for most programs, trying to figure out exactly what you 
 want the program to do is going to be much harder than implementing a 
 program that does it.

And the solution is..to not say anything about what the program should
do? :-)

 Also, for most programs the spec is far more complicated (and hence 
 prone to error) than the actual program, so...

Since the program *is* a (complete) specification of itself, a
specification need not be any longer or more complicated than the
program.

Realistically, I think it is good practice to specify explicit type
signatures and quickcheck properties (or similar unit tests).  The
advantage over other documentation, is that they are verified or tested
(respectively) against the actual code.

The code itself explains how, type signatures and unit tests explain
what, which leaves only why to comments.

-k

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


Re: [Haskell-cafe] Language extensions

2007-05-30 Thread Tomasz Zielonka
On Tue, May 29, 2007 at 09:43:03PM +0100, Andrew Coppin wrote:
 Henning Thielemann wrote:
 On Sun, 27 May 2007, Andrew Coppin wrote:
 But every now and then I discover an expression which is apparently not
 expressible without them - which is odd, considering they're only
 sugar...
 
 Example?
 
 Until I learned the trick of using lists as monads, I was utterly 
 perplexed as to how to get a Cartesian product

This is far from not expressible:
cart xs ys = concatMap (\x - map ((,) x) ys) xs

 or why there's no library function to do this!

sequence?

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


Re: [Haskell-cafe] Language extensions

2007-05-30 Thread Jules Bean

Andrew Coppin wrote:
My point is for most programs, trying to figure out exactly what you 
want the program to do is going to be much harder than implementing a 
program that does it.


Also, for most programs the spec is far more complicated (and hence 
prone to error) than the actual program, so...


If you can't figure out exactly what the program is supposed to do, then 
your program clearly can't do it. So your program is buggy. Or, you got 
it precisely right, by chance, despite your ignorance. That's unlikely.


Most existing programs are in this category: unspecified, and hence buggy.

It *is* hard to work out *exactly* what a program should do. It's 
important though. If you don't do it, then no one knows what your 
program does...


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


Re: [Haskell-cafe] Language extensions

2007-05-30 Thread Henning Thielemann

On Tue, 29 May 2007, Andrew Coppin wrote:

 OTOH, how many function can you write with :: [Int] - Int? I can think
 of a few...

You will probably more like to implement functions like
  Ord a = [a] - a
  Num a = [a] - a
 and those generalized signatures tell you more. :-)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Language extensions

2007-05-30 Thread Tomasz Zielonka
On Wed, May 30, 2007 at 02:35:38PM +0200, Henning Thielemann wrote:
 
 On Tue, 29 May 2007, Andrew Coppin wrote:
 
  OTOH, how many function can you write with :: [Int] - Int? I can think
  of a few...
 
 You will probably more like to implement functions like
   Ord a = [a] - a
   Num a = [a] - a
  and those generalized signatures tell you more. :-)

Nice observation! Let's see what these types guarantee...

In the Ord variant, the result value pretty much has to come from the
input list or be bottom. It has to be bottom for the empty list. If
f :: Ord a = [a] - a and g preserves order (is monotonic) then
f (map g l) == g (f l)
This could be nice for testing Ord instances. Unfortunately, for bounded
types the only order preserving function is id.

In Num variant, the result for the empty list with be an integer (or
bottom), no matter what type is 'a'.

All this assuming 'a' has sane Num and Ord instances.

More ideas?

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


Re: [Haskell-cafe] Language extensions [was: Memoization]

2007-05-30 Thread Claus Reinke



quantified types (forall/exist):
 an easy way to memorize this is to think of 'forall' as a big 'and'
 and of 'exists' as a big 'or'.
   e :: forall a. a  -- e has type 'Int' and type 'Bool' and type ..
   e :: exists a. a  -- e has type 'Int' or  type 'Bool' or  type ..


That doesn't entirely make sense. (What am I on about? That doesn't 
make *any* sense...)


indeed?-) then you've probably already figured out what those types
mean! there aren't many variations of an expression that has *all* types
(you can't please everyone), and if an expression has a type but we
have no way of knowing what that type is, there isn't much we can do
with it (like advice from the Oracle of Delphi).  but both of these
kinds of quantified types make a lot more sense in larger contexts. 


lets take 'forall'/'big and' first: the problem with 'forall a. a' is to
produce something that is everything to everyone, which is rather hard;
but what about 'forall a. a - a'? that is like a general shipping
agency - they don't care what you give them, they just put it in a box
and move it from one place to another (if it doesn't like to be shipped
in such an indifferent way, it'll break, but that's not their problem);
such general shipping is both 'Integer' shipping *and* 'String' shipping
*and* ..; other examples are 'forall a. a - a - a', which is a general
selector (given two 'a's, it returns one of them), or 
'forall a,b. a - b - a' (given an 'a' and a 'b', it returns the 'a').


'id :: forall a. a - a' can be instantiated to 'id :: Bool - Bool'
*and* to 'id :: Char - Char' *and* to all other identities on rank-1
types besides, so one could say that it really has *all* of those types.

what about 'exists'/'big or' then? the problem with 'exists a. a' is
that while we know there exists a type, we have no way of knowing 
what that type is, so we can't really do anything with an expression 
of such a type. 


that is very much like an abstract data type, implemented on top
of a hidden representation type. what we need are some operations 
on that abstract type, so how about 


   'exists r.(r a, r a - a - r a, r a - a)'

we still don't know what 'r' is, but we have some 'r a', we have a way
to combine 'r a' and 'a' into a new 'r a', and a way to extract an 'a'
from an 'r a', so we're no longer entirely helpless. in fact, that looks
a lot like an abstract container type, perhaps a stack with push and
top, or a queue with add and front, or a cell with put and get. 
whatever it may be, the 'r' is hidden, so it could be 

   '([a], [a]-a-[a], [a]-a)' 

*or* it could be 

   '(Set a, Set a - a - Set a, Set a - a)' 


*or* it could be based on *any* other rank-1 type constructor.

hth,
claus

oracle advice: 'invade :: exists great_empire. great_empire - ()'



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


Re: [Haskell-cafe] Language extensions [was: Memoization]

2007-05-30 Thread Creighton Hogg

On 5/29/07, Andrew Coppin [EMAIL PROTECTED] wrote:


Claus Reinke wrote:







 phantom types:
  the types of ghost values (in other words, we are only interested in
  the type, not in any value of that type).

Mmm... Still not seeing a great amount of use for this one.



Okay, well phantom types are something I like because they allow some notion
of static capabilities, a la
http://okmij.org/ftp/papers/lightweight-static-capabilities.pdf
One of my big interests is how much of a true capability based security
system can be pushed up into the type level.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Language extensions

2007-05-30 Thread Henk-Jan van Tuyl
On Wed, 30 May 2007 09:38:10 +0200, Tomasz Zielonka  
[EMAIL PROTECTED] wrote:



On Tue, May 29, 2007 at 09:43:03PM +0100, Andrew Coppin wrote:

Henning Thielemann wrote:
On Sun, 27 May 2007, Andrew Coppin wrote:
But every now and then I discover an expression which is apparently  
not

expressible without them - which is odd, considering they're only
sugar...

Example?

Until I learned the trick of using lists as monads, I was utterly
perplexed as to how to get a Cartesian product


This is far from not expressible:
cart xs ys = concatMap (\x - map ((,) x) ys) xs



A bit simpler is:
  cart xs ys = [(x, y) | x - xs, y - ys]

or:
  cart xs ys =
do
  x - xs
  y - ys
  return (x, y)

--
Met vriendelijke groet,
Henk-Jan van Tuyl


--
http://Van.Tuyl.eu/
--

Using Opera's revolutionary e-mail client:
https://secure.bmtmicro.com/opera/buy-opera.html?AID=789433

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


Re: [Haskell-cafe] Language extensions

2007-05-30 Thread Roberto Zunino
Tomasz Zielonka wrote:
 In the Ord variant, the result value pretty much has to come from the
 input list or be bottom. It has to be bottom for the empty list. If
 f :: Ord a = [a] - a and g preserves order (is monotonic) then
 f (map g l) == g (f l)
 This could be nice for testing Ord instances. Unfortunately, for bounded
 types the only order preserving function is id.

Interesting... are the following g allowed? (I am relatively new to
parametericity results.)

(\!x - (x,4))-- bounded types (?)
($!) Data.List.repeat -- ;-) unbounded types

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


Re: [Haskell-cafe] Language extensions

2007-05-29 Thread Tomasz Zielonka
On Mon, May 28, 2007 at 11:43:47AM +0100, Andrew Coppin wrote:
 - Chapter 2 is... puzzling. Personally I've never seen the point of 
 trying to check a program against a specification. If you find a 
 mismatch then which thing is wrong - the program, or the spec?

Knowing that one of them is wrong is already a very useful information,
don't you think?

 - Chapter 12 is incomprehensible (to me at least). Fun with Phantom 
 Types I've read it several times, and I still couldn't tell you what a 
 phantom type is...

Ironically, this chapter contains the following (at least the version
at http://www.informatik.uni-bonn.de/~ralf/publications/With.pdf):

 Of course, whenever you add a new feature to a language, you should
 throw out an existing one (especially if the language at hand is
 named after a logician). Now, for this chapter we abandon type
 classes - judge for yourself how well we get along without
 Haskell's most beloved feature.

You've found a language extension soulmate! ;-)

BTW, I really liked Ralf's chapter.

 There are some bits that are sort-of interesting but not really to do
 with anything I'm passionate about, and then there are bits that I
 can't comprehend...

Passionate... perhaps this is the root of the problem? Different people
are passionate about different things.

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


Re: [Haskell-cafe] Language extensions [was: Memoization]

2007-05-29 Thread Henning Thielemann

Hi Andrew!

I share your concerns about the simplicity of the language. Once
extensions exists, they are used widely, and readers of programs must
understand them, also if the extensions are used without need. I
understand the motivations for many type extensions, but library writers
tend to use language extensions instead of thinking hard how to avoid
them. At least people should separate advanced code from simple one.
  http://www.haskell.org/haskellwiki/Use_of_language_extensions
 Indeed the State monad and State monad transformer are quite simple and
fit very well into Haskell 98. The langaguage extension is only needed
because there shall be class methods like 'get' and 'put' that can be used
without modification on both the State monad and its transformer variant.
It would be easy to separate the concrete types State and StateT from the
class MonadState, but this has not been done.
 I wish the compilers would allow more fine grained switches on languages
extensions. -fglasgow-exts switches them all on, but in most cases I'm
interested only in one. Then typing errors or design flaws (like 'type
Synonym = Type', instead of wanted 'type Synonym a = Type a'; extended
instance declarations) are accepted without warnings.



On Sun, 27 May 2007, Andrew Coppin wrote:

  Keep in mind also that many of these extensions are part of Haskell
  Prime, which last I checked is supposed to become official sometime
  later this year.

 This worries me greatly. I'm really afraid that Haskell will go from
 being this wonderful, simple language that you can explain in a page or
 two of text to being this incomprehensible mass of complex type
 machinery that I and most other human beings will never be able to learn
 or use. :-(

I hope that compilers will have a Prime switch in order to distinguish
Haskell 98 programs from Haskell' ones. This way I could reliably test,
whether my programs use simple or advanced language features.


Let me cite from the book
  Programming in Modula-3: An Introduction in Programming with Style,
  Conclusion / Why programming?, page 425:
 In a lecture in March 1995 at the University of Klagenfurt, Niklaus
Wirth analyzed the phenomenon of software chaos. He challenged that the
ever rising complexity of software is not necessary, and indeed that it is
bound to the loss of certain engineering qualities, such as an
appreciation of efficiency and simplicity.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Language extensions

2007-05-29 Thread Henning Thielemann

On Sun, 27 May 2007, Andrew Coppin wrote:

 Personally, I try to avoid ever using list comprehensions.

Me too. Successfully, I have to add.

 But every now and then I discover an expression which is apparently not
 expressible without them - which is odd, considering they're only
 sugar...

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


RE: [Haskell-cafe] Language extensions [was: Memoization]

2007-05-29 Thread Simon Peyton-Jones
|  I wish the compilers would allow more fine grained switches on languages
| extensions. -fglasgow-exts switches them all on, but in most cases I'm
| interested only in one. Then typing errors or design flaws (like 'type
| Synonym = Type', instead of wanted 'type Synonym a = Type a'; extended
| instance declarations) are accepted without warnings.

Yes, we have an open Trac feature request for exactly this.  We keep not doing 
it for lack of bandwidth. Does anyone feel like taking it on?

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


Re: [Haskell-cafe] Language extensions [was: Memoization]

2007-05-29 Thread Isaac Dupree
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

Simon Peyton-Jones wrote:
 |  I wish the compilers would allow more fine grained switches on languages
 | extensions. -fglasgow-exts switches them all on, but in most cases I'm
 | interested only in one. Then typing errors or design flaws (like 'type
 | Synonym = Type', instead of wanted 'type Synonym a = Type a'; extended
 | instance declarations) are accepted without warnings.
 
 Yes, we have an open Trac feature request for exactly this.
 We keep not doing it for lack of bandwidth. Does anyone feel like taking it 
 on?

(not me in the immediate future, maybe later)

ticket # what?

I would think that preferable to inventing lots of compiler flags is
reusing some of the names from the LANGUAGE pragma, where practical.
(To some extent, this goes along with Cabal needing help, and the idea
of compilers offering a standard interface to it, I guess)

Isaac
-BEGIN PGP SIGNATURE-
Version: GnuPG v1.4.6 (GNU/Linux)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org

iD8DBQFGXFeuHgcxvIWYTTURAscAAJ9pR57h5Gi/8cdSzNEAnClIJbwyiwCdGGE9
wRBJZf46GarajlroryJ7wMw=
=FVe+
-END PGP SIGNATURE-
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Language extensions [was: Memoization]

2007-05-29 Thread Ian Lynagh
On Tue, May 29, 2007 at 12:41:19PM -0400, Isaac Dupree wrote:
 Simon Peyton-Jones wrote:
  |  I wish the compilers would allow more fine grained switches on languages
  | extensions. -fglasgow-exts switches them all on, but in most cases I'm
  | interested only in one. Then typing errors or design flaws (like 'type
  | Synonym = Type', instead of wanted 'type Synonym a = Type a'; extended
  | instance declarations) are accepted without warnings.
  
  Yes, we have an open Trac feature request for exactly this.
 
 ticket # what?

http://hackage.haskell.org/trac/ghc/ticket/16

 I would think that preferable to inventing lots of compiler flags is
 reusing some of the names from the LANGUAGE pragma, where practical.

Agreed, as discussed in
http://www.haskell.org/pipermail/cabal-devel/2007-March/000460.html

I've also just added a note from an offline discussion that we should
use shorter names than I suggest in the above URL, and make them the
primary/only names.


Thanks
Ian

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


Re: [Haskell-cafe] Language extensions [was: Memoization]

2007-05-29 Thread Andrew Coppin

Claus Reinke wrote:


I'm thinking more about things like phantom types, rank-N 
polymorphism, functional dependencies, GADTs, etc etc etc that nobody 
actually understands.


this seems to be overly polymorphic in generalising over all types of
Haskell programmers, rather than admitting the existence of some types
of programmers who might have different values. qualifying such
generalisations by grouping types of programmers into classes with
different methods would seem a more Haskellish way, don't you think?-)

and although it isn't nice to typecast people, sometimes one only needs
to know the type, not the person, and sometime one needs even less
information, such as a property of a type or its relation to other
types. and especially if one is interested in relationships between
different types, it is helpful to know if one type of person in such a
relationship always occurs in combination with one and the same other
type. and if there are times when one might even generalise over
generalisations (although one doesn't like to generalise over so many
people all at once;-), there are other times when one might need to be
rather specific about which of several possible alternative types one is
putting together in a single construction.

there, does that cover everything in that list? sorry, couldn't
resist!-)


Hahahaha!

Thanks for a good laugh! I should print this out and *frame* it or 
something...



in exchange, below is a quick summary (didn't we have a
dictionary/quick-reference somewhere at haskell.org? i can't seem to 
find it right now, but if you know where it is, and it doesn't
already contain better explanations, feel free to add the text below - 
but check the draft for errors first, please;)


claus

--
phantom types:
 the types of ghost values (in other words, we are only interested in
 the type, not in any value of that type).


Mmm... Still not seeing a great amount of use for this one.


quantified types (forall/exist):
 an easy way to memorize this is to think of 'forall' as a big 'and'
 and of 'exists' as a big 'or'.
   e :: forall a. a  -- e has type 'Int' and type 'Bool' and type ..
   e :: exists a. a  -- e has type 'Int' or  type 'Bool' or  type ..


That doesn't entirely make sense. (What am I on about? That doesn't make 
*any* sense...)



rank-N polymorphism:
 in rank-1 polymorphism, type variables can only stand for monomorphic
 types (so, '($) :: (a-b) - a - b' can only apply monomorphic
 functions to their arguments, and polymorphic functions are not
 first-class citizens, as they cannot be passed as parameters without
 their types being instantiated). in rank-N (N1) polymorphism,
 type-variables can stand for rank-(N-1) polymorphic types (in other
 words, polymorphic functions can now be passed as parameters, and used
 polymorphically in the body of another function).

   f :: (forall a. [a]-Int) - ([c],[d]) - (Int,Int)
   f g (c,d) = (g c,g d)

   f length ([1..4],[True,False])


It's actually news to me that you can't do this already... (!)


functional dependencies:
 when using multi-parameter type classes, we specify relations between
 types (taken from the cartesian product of type class parameters).

 without additional measures, that tends to lead to ambiguities (some
 of the type class parameters can not be deduced unambiguously from the
 context, so no specific type class instance can be selected).

 functional dependencies are one such measure to reduce ambiguities,
 allowing us to specify that some subset A of type-class parameters
 functionally determines another subset B (so if we know the types of
 the parameters in subset A, there is only a single choice for the
 types of the parameters in subset B).


Functional dependancies kind of make sense. Personally I like the idea 
of associated types better, but never mind.



gadts:
 what really makes them different is that
 the explicit type signatures for the data constructors can give more
 specific return types for the data constructs, and such more specific
 types can be propagated through pattern matching


Finally, a definition of GADTs that actually makes some kind of sense...

(I find it highly unlikely I'll ever need these, but at least I have 
some idea now what they're supposed to do.)


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


Re: [Haskell-cafe] Language extensions

2007-05-29 Thread Andrew Coppin

Tomasz Zielonka wrote:

On Mon, May 28, 2007 at 11:43:47AM +0100, Andrew Coppin wrote:
  
- Chapter 2 is... puzzling. Personally I've never seen the point of 
trying to check a program against a specification. If you find a 
mismatch then which thing is wrong - the program, or the spec?



Knowing that one of them is wrong is already a very useful information,
don't you think?
  


My point is for most programs, trying to figure out exactly what you 
want the program to do is going to be much harder than implementing a 
program that does it.


Also, for most programs the spec is far more complicated (and hence 
prone to error) than the actual program, so...


- Chapter 12 is incomprehensible (to me at least). Fun with Phantom 
Types I've read it several times, and I still couldn't tell you what a 
phantom type is...



Ironically, this chapter contains the following (at least the version
at http://www.informatik.uni-bonn.de/~ralf/publications/With.pdf):

 Of course, whenever you add a new feature to a language, you should
 throw out an existing one (especially if the language at hand is
 named after a logician). Now, for this chapter we abandon type
 classes - judge for yourself how well we get along without
 Haskell's most beloved feature.

You've found a language extension soulmate! ;-)
  


It amazes me that anybody would think removing type classes is a good 
idea... but there we are. :-}



BTW, I really liked Ralf's chapter.
  


It's a free country. ;-)


There are some bits that are sort-of interesting but not really to do
with anything I'm passionate about, and then there are bits that I
can't comprehend...



Passionate... perhaps this is the root of the problem? Different people
are passionate about different things.
  


Well, more that some things make more sense to me than others. It's 
difficult to decide whether you're passionate about something or not if 
you can't understand what it is.


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


Re: [Haskell-cafe] Language extensions

2007-05-29 Thread Andrew Coppin

Henning Thielemann wrote:

On Sun, 27 May 2007, Andrew Coppin wrote:

  

Personally, I try to avoid ever using list comprehensions.



Me too. Successfully, I have to add.

  

But every now and then I discover an expression which is apparently not
expressible without them - which is odd, considering they're only
sugar...



Example?
  


Until I learned the trick of using lists as monads, I was utterly 
perplexed as to how to get a Cartesian product - or why there's no 
library function to do this!


Thanks to the chapter on Logic Combinators, I've learned a trick or two 
about monadic list trickery... muhuhuhuhu!


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


Re: [Haskell-cafe] Language extensions

2007-05-29 Thread Tim Chevalier

On 5/29/07, Andrew Coppin [EMAIL PROTECTED] wrote:

My point is for most programs, trying to figure out exactly what you
want the program to do is going to be much harder than implementing a
program that does it.


Writing a spec can help with figuring out what you want your program to do.



Also, for most programs the spec is far more complicated (and hence
prone to error) than the actual program, so...


Really? That might be a good sign that there's something wrong with
the spec, the program, or your understanding of the problem. In
Haskell, the most common form of specification is probably type
signatures. Those are usually simpler than the corresponding
implementations.

Cheers,
Tim

--
Tim Chevalier * [EMAIL PROTECTED] * Often in error, never in doubt
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Language extensions

2007-05-29 Thread Andrew Coppin

Tim Chevalier wrote:

On 5/29/07, Andrew Coppin [EMAIL PROTECTED] wrote:

My point is for most programs, trying to figure out exactly what you
want the program to do is going to be much harder than implementing a
program that does it.


Writing a spec can help with figuring out what you want your program 
to do.


True in principle. But if writing the spec is harder than writing the 
actual program, all it means is you spend longer trying to figure out 
how to express intuitively simple concepts using advanced and very 
abstract and subtle predicate calculus.




Also, for most programs the spec is far more complicated (and hence
prone to error) than the actual program, so...


Really? That might be a good sign that there's something wrong with
the spec, the program, or your understanding of the problem. In
Haskell, the most common form of specification is probably type
signatures. Those are usually simpler than the corresponding
implementations.


One of the things I love about Haskell is the way the type signature 
alone almost tells you what the function actually does. I've never 
come across this in any other language - but then, I've never seen any 
other language with a type system as powerful as Haskell.


OTOH, how many function can you write with :: [Int] - Int? I can think 
of a few...


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


Re: [Haskell-cafe] Language extensions

2007-05-29 Thread Stefan Holdermans
True in principle. But if writing the spec is harder than writing  
the actual program, all it means is you spend longer trying to  
figure out how to express intuitively simple concepts using  
advanced and very abstract and subtle predicate calculus.


As it turns out, Haskell sometimes makes a suitable specification  
language:


  Paul Hudak and Mark P. Jones.
  Haskell vs. Ada vs. C++ vs. Awk vs:
  An experiment in software prototyping productivity.
  1994.
  http://haskell.org/papers/NSWC/jfp.ps

Cheers,

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


Re: [Haskell-cafe] Language extensions

2007-05-28 Thread Andrew Coppin

Brandon S. Allbery KF8NH wrote:


On May 27, 2007, at 17:23 , Andrew Coppin wrote:

Personally, I try to avoid ever using list comprehensions. But every 
now and then I discover an expression which is apparently not 
expressible without them - which is odd, considering they're only 
sugar...


They are.  But they're sugar for monadic operations in the list monad, 
so you have to use (=) and company to desugar them.  [x | filter 
even x, x - [1..10]] becomes do { x - [1..10]; return (filter even 
x) } becomes ([1..10] = return . filter even).


(Aren't you glad you asked?)


Mmm... LOL!

Actually, I recently read something in a book called The Fun of 
Programming. It basically explains how to implement Prolog in Haskell, 
including presenting an extremely inefficient way to factorise integers:


 factors n = do
   x - [1..100]
   y - [1..100]
   if x * y == n
 then return (x,y)
 else []

I should point out that desugaring do-blocks is possibly one of the 
hardest things for a Haskell newbie to figure out, but I think I've 
mastered it now. What we actually have above is


 factors n =
   [1..100] = \x -
   [1..100] = \y -
   if x * y == n
  then [(x,y)]
  else []

which makes it quite clear why x - [1..100] actually causes x to 
range over all the numbers in the list. (That's the great thing about 
monads - sometimes it can be hard to wrap your mind around what they 
actually do when used in nontrivial ways...)


Of course, the book explains how to write a new monad that allows 
infinite lists to be used, and yet still find all factors in finite 
time. (This involves the Evil *** Function From Hell I mentioned a 
while ago.) And then they go on to explain how to implement unification 
- something I would never have worked out in a million years. And after 
reading the whole chapter, finally I understand how it is possible for 
Prolog to exist, even though computers aren't intelligent...


Then again, later on in the very same book there's a chapter entitled 
Fun with Phantom Types, which made precisely no sense at all...


(I find this a lot with Haskell. There is stuff that is clearly written, 
fairly easily comprehensible, and extremely interesting. And then 
there's stuff that no matter how many times you read it, it just makes 
no sense at all. I'm not sure exactly why that is.)


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


Re: [Haskell-cafe] Language extensions

2007-05-28 Thread Andrew Coppin

Jim Burton wrote:

Speaking as someone who, like you, came to the language recently and for
whom many of haskell's outer corners are still confusing, I should firstly
say that I can see where you're coming from but that it puzzles me as to why
you think things ought to be obvious or why, when something isn't obvious to
you, it must be useless? Could the answer be that it will take some time
before you understand the motivation for features that don't seem natural to
you? You might need some patience and study along with everything else, I
know I do (and people have been generous with links to work that explains
the motivation). I only say this because you seem, bizarrely, to be
suggesting that you could improve things by undoing the work of all these
scary people as you call them in another post, whilst admitting that you
don't understand it.
  


Haskell 98 does an excellent job of being extremely simple, yet almost 
unbelievably powerful. Almost every day, I am blown away by how powerful 
it is. I suppose it just defies belief that you could possibly need even 
*more* power than is already in the language... and also, as I've 
mentioned, Haskell being simple is one of the most appealing things 
about it. I dislike conceptual complexity. Still, it's only my personal 
opinion, and the decision isn't actually up to me...


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


Re: [Haskell-cafe] Language extensions

2007-05-28 Thread Jim Burton



Andrew Coppin wrote:
 
 
 Haskell 98 does an excellent job of being extremely simple, yet almost 
 unbelievably powerful. Almost every day, I am blown away by how powerful 
 it is. I suppose it just defies belief that you could possibly need even 
 *more* power than is already in the language... 
 

Sounds like the blub paradox ;-) 



 and also, as I've 
 mentioned, Haskell being simple is one of the most appealing things 
 about it. I dislike conceptual complexity. Still, it's only my personal 
 opinion, and the decision isn't actually up to me...
 
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 
 

-- 
View this message in context: 
http://www.nabble.com/Memoization-tf3822500.html#a10832782
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


Re: [Haskell-cafe] Language extensions

2007-05-28 Thread Andrew Coppin

Jim Burton wrote:


Andrew Coppin wrote:
  
Haskell 98 does an excellent job of being extremely simple, yet almost 
unbelievably powerful. Almost every day, I am blown away by how powerful 
it is. I suppose it just defies belief that you could possibly need even 
*more* power than is already in the language... 




Sounds like the blub paradox ;-) 
  


OK, maybe you're right, I'm a blubber. :-P

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


Re: [Haskell-cafe] Language extensions

2007-05-28 Thread Ilya Tsindlekht
On Sun, May 27, 2007 at 05:34:33PM -0400, Brandon S. Allbery KF8NH wrote:
 
 On May 27, 2007, at 17:23 , Andrew Coppin wrote:
 
 Personally, I try to avoid ever using list comprehensions. But  
 every now and then I discover an expression which is apparently not  
 expressible without them - which is odd, considering they're only  
 sugar...
 
 They are.  But they're sugar for monadic operations in the list  
 monad, so you have to use (=) and company to desugar them.  [x |  
 filter even x, x - [1..10]] becomes do { x - [1..10]; return  
 (filter even x) } becomes ([1..10] = return . filter even).
 
The list monad is easily defineable in pure Haskell, so one can do 
without monadic operation as well if one wishes to.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Language extensions

2007-05-28 Thread David House

On 27/05/07, Andrew Coppin [EMAIL PROTECTED] wrote:

Almost all language extensions seem to be of the form hey, let's see
what happens if we randomly change the type checking rules so that
*this* is permitted. What would that be like? Usually it's an extreme
struggle to even wrap my brain around what the extension *is*, never
mind why this would be a useful thing...


I've read through pretty much all your arguments, and I think they
boil down to this:

I don't understand why X is useful, and therefore it can't be useful.

Probably the reason why you don't understand why X is useful is
because you don't understand X itself in the first place. How can you
claim GADTs, existentials etc. aren't useful without understanding
what they are in the first place? If you're looking for a good
reference to learn these, I suggest the papers apfelmus pointed you
towards, or the Wikibook at http://en.wikibooks.org/wiki/Haskell.

Moreover, if you've ever written a full-sized Haskell program you'd
probably find a use case for at least one of these extensions. For
example, you're writing low-level code, and you want in-place array
updates. Sounds like a job for the ST monad, which would completely
crippled and inherently type-unsafe without rank-2 polymorphism. Or
say, as I have done recently, you're writing some forum software, and
have a type to represent a Forum, Thread and Post. Now say you want to
write some generic code to handle the addition of any one of these --
so this one piece of code allows you to add a new forum, thread or
post. Without a splattering of type-system extensions (I used at least
MPTCs, FDs and existentials), this isn't going to be possible.

--
-David House, [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Language extensions

2007-05-28 Thread Andrew Coppin

David House wrote:

I've read through pretty much all your arguments, and I think they
boil down to this:

I don't understand why X is useful, and therefore it can't be useful.


I meant to imply more that it's very difficult to understand why it's 
useful. If an extension were truely *useless*, I doubt those guys at 
GHC would have bothered spending years implementing them.


Most of the documents that describe these things begin with suppose we 
have this extremely complicated and difficult to understand situation... 
now, we want to do X, but the type system won't let us. Which makes it 
seem like these extensions are only useful in extremely complicated and 
rare situations. The fact that my own programs hardly ever result in 
situations where I want to do X but the type system won't let me only 
reinforces this idea. Maybe it's just the kind of code I write...



Moreover, if you've ever written a full-sized Haskell program you'd
probably find a use case for at least one of these extensions.


...or the fact that I only write trivial applications...

(Well, they're not trivial to me. But I imagine everybody else would 
think them trivial.)


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


Re: [Haskell-cafe] Language extensions

2007-05-28 Thread Andrew Coppin

Chaddaï Fouché wrote:

2007/5/28, Andrew Coppin [EMAIL PROTECTED]:

Then again, later on in the very same book there's a chapter entitled
Fun with Phantom Types, which made precisely no sense at all...



You seem to think you're extremely clever since if something doesn't
make sense to you it _obviously_ doesn't make sense at all... Well it
at least made sense for the authors of the article, and lots of person
who read it.


Surely it makes sense to someone. (But then, there are people to whom 
number theory makes sense.) I didn't mean to imply that it is 
*impossible* to comprehend the article, only that it's very greatly 
beyond my capabilities.


I like to think I'm an intelligent, but... maybe I'm just kidding myself...

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


Re: [Haskell-cafe] Language extensions

2007-05-28 Thread Michael T. Richter
On Mon, 2007-28-05 at 10:35 +0100, Andrew Coppin wrote:

 Most of the documents that describe these things begin with suppose we 
 have this extremely complicated and difficult to understand situation... 
 now, we want to do X, but the type system won't let us. Which makes it 
 seem like these extensions are only useful in extremely complicated and 
 rare situations. The fact that my own programs hardly ever result in 
 situations where I want to do X but the type system won't let me only 
 reinforces this idea. Maybe it's just the kind of code I write...


I think this comes from the mathematical background of most people who
write papers about Haskell, personally.  Math is probably the least
competently-taught subject on the planet.  (History may share this
distinction.  May.)  There's a lot of purely-hypothetical situations
(suppose you'd want to map an enumeration of the set of all blah blah
blah blah to the set of blah blah blah) with no sense of motivation or
application provided.  As a result to many (obviously not all!) it looks
more like random pen-scratchings with no practical use.

Which is a pity.

Because most of it is useful in practical ways.  Even fields whose
researchers took pride in being absolutely useless are beginning to
show themselves as useful.  But math being taught the way it is makes
this connection inobvious (to put it mildly) and thus mathematics as a
field gets none of the respect and interest it deserves.

Haskell's leading practitioners and cheerleaders tend to be
mathematicians first.  There are some who write papers accessible to the
work-a-day programmer, but most do not and, as a result, it's often hard
to decode motivation for the language's features and extensions.

Now that's the bad news.  The good news is that this is changing.  Five
years ago, when I first looked at Haskell and gave up, there was almost
nothing available to teach the language that wasn't purest ivory-tower
hypothetical situations.  The materials available detailing the language
really made it look like you had to be a multiple-Ph.D. in maths and
copyright law (that latter just because it's the only thing I can think
of more complicated than maths ;)) to be smart enough and well-educated
enough to use Haskell.  This is no longer the case.  Simon Peyton-Jones,
Don Stewart and a handful of other luminaries in the community (whose
names I've temporarily forgotten because I'm lousy with names) are
beginning to produce good, high-quality papers on obscure and difficult
topics that make these topics -- almost ordinary.  Further, just in the
last year the nature of conversations in haskell-cafe has changed
dramatically.  I'm seeing a lot more real-world, work-a-day programming
questions and answers these days than I did as little as a year ago.

So it's not all hopeless, Andrew (thankfully for obvious dullards like
me).

-- 
Michael T. Richter [EMAIL PROTECTED] (GoogleTalk:
[EMAIL PROTECTED])
Never, ever, ever let systems-level engineers do human interaction
design unless they have displayed a proven secondary talent in that
area. Their opinion of what represents good human-computer interaction
tends to be a bit off-track. (Bruce Tognazzini)
attachment: smiley-4.png

signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Language extensions

2007-05-28 Thread Andrew Coppin

Michael T. Richter wrote:

On Mon, 2007-28-05 at 10:35 +0100, Andrew Coppin wrote:
Most of the documents that describe these things begin with suppose we 
have this extremely complicated and difficult to understand situation... 
now, we want to do X, but the type system won't let us. Which makes it 
seem like these extensions are only useful in extremely complicated and 
rare situations. The fact that my own programs hardly ever result in 
situations where I want to do X but the type system won't let me only 
reinforces this idea. Maybe it's just the kind of code I write...



I think this comes from the mathematical background of most people who 
write papers about Haskell, personally.  Math is probably the least 
competently-taught subject on the planet.  (History may share this 
distinction.  May.)  There's a lot of purely-hypothetical situations 
(suppose you'd want to map an enumeration of the set of all blah blah 
blah blah to the set of blah blah blah) with no sense of motivation 
or application provided.  As a result to many (obviously not all!) it 
looks more like random pen-scratchings with no practical use.


Which is a pity.

Because most of it *is* useful in practical ways.  Even fields whose 
researchers took *pride* in being absolutely useless are beginning 
to show themselves as useful.  But math being taught the way it is 
makes this connection inobvious (to put it mildly) and thus 
mathematics as a field gets none of the respect and interest it deserves.


Haskell's leading practitioners and cheerleaders tend to be 
mathematicians first.  There are some who write papers accessible to 
the work-a-day programmer, but most do not and, as a result, it's 
often hard to decode motivation for the language's features and 
extensions.


Now that's the bad news.  The good news is that this is changing.  
Five years ago, when I first looked at Haskell and gave up, there was 
almost *nothing* available to teach the language that wasn't purest 
ivory-tower hypothetical situations.  The materials available 
detailing the language really made it look like you had to be a 
multiple-Ph.D. in maths and copyright law (that latter just because 
it's the only thing I can think of more complicated than maths ;)) to 
be smart enough and well-educated enough to use Haskell.  This is no 
longer the case.  Simon Peyton-Jones, Don Stewart and a handful of 
other luminaries in the community (whose names I've temporarily 
forgotten because I'm lousy with names) are beginning to produce good, 
high-quality papers on obscure and difficult topics that make these 
topics -- almost ordinary.  Further, just in the last *year* the 
nature of conversations in haskell-cafe has changed dramatically.  I'm 
seeing a lot more real-world, work-a-day programming questions and 
answers these days than I did as little as a year ago.


So it's not all hopeless, Andrew (thankfully for obvious dullards like 
me).


The laughabout thing is that mathematics is actually one of my main 
hobbies! (Hence my question a while back about implementing Mathematica 
in Haskell.)


I've spent lots of time investigating subjects like group theory, 
differential and integral calculus, complex numbers and their 
properties, polynomials, cryptology, data compression, ray tracing, 
sound synthesis, digital signal processing, artificial intelligence, and 
all manner of other things. (Most normal humans think I'm a total nerd 
and want nothing to do with me.)


I had little trouble learning Haskell. I had (and still have) lots of 
trouble figuring out the best way to *use* Haskell, but the language 
itself is delightfully simple, elegant and natural. I guess elegance 
appeals to the mathematition in me or something, I don't know.


And yet, lots of stuff written about Haskell makes some pretty big 
assumptions about what you know. (E.g., assuming you know what 
second-order logic is.) Some of it doesn't - and that's the stuff I 
love reading. Let's take another look at The Fun of Programming.


- Chapter 1 is a delightful exercise in binary heap trees. It 
demonstrates everything that's exciting about Haskell. A few dozen lines 
of code and we have a beautiful, elegant, simple, useful data structure.
- Chapter 2 is... puzzling. Personally I've never seen the point of 
trying to check a program against a specification. If you find a 
mismatch then which thing is wrong - the program, or the spec?
- Chapter 3 is very interesting... but a little hard going. (Origami 
Programming. Did you know there are over 20 kinds of morphisms?)
- Chapter 4 is very similar to something I read somewhere else before, 
so I skipped it.
- Chapter 5 struck me as being just bizzare. Hey, rather than write 
this efficient but complicated function, let's use an inefficient but 
elegant version of it and append several pages of magical compiler hints 
so it can transform it into the efficient version. Um... and this is 
saving you work how, exactly?
- Chapter 6 is fascinating. 

Re: [Haskell-cafe] Language extensions

2007-05-28 Thread Claus Reinke
I meant to imply more that it's very difficult to understand why it's 
useful. If an extension were truely *useless*, I doubt those guys at GHC 
would have bothered spending years implementing them.


Most of the documents that describe these things begin with suppose we have 
this extremely complicated and difficult to understand situation... now, we 
want to do X, but the type system won't let us. Which makes it seem like 
these extensions are only useful in extremely complicated and rare 
situations.


keep in mind that paper space is a precious and limited resource. the
need for extensions tends to arise in practice first, but those real examples
are far too big and complex to fit into those limitations. it is very 
difficult to

come up with examples that are small enough to fit, yet complex enough to
exhibit the problem. which means that the examples usually look artificial,
but small and complete, or realistic, but so large that their presentation
has to be shallow enough to border on vague.

The fact that my own programs hardly ever result in situations where I want 
to do X but the type system won't let me only reinforces this idea. Maybe 
it's just the kind of code I write...


i find it interesting that you seem to be worried about having too many
options and features available to you, as if you were focussing on

 programming in *Haskell*

trying to make use of as many language features as possible.  in
contrast, for quite some time now, i find myself doing something quite
different, namely

 *programming* in Haskell

which works because Haskell often liberates me from having to think
about the host language i'm doing that programming in, and lets me focus
on the programs i'm interested in writing.

there are, however, occasions when the limitations of that host language
start to get in the way to such an extent that the programming i want to
do becomes painful or even impossible (for practical purposes), causing
me to divert my attention from the programming to the boundaries placed
on me

 programming *in Haskell*

in my experience, most of the extensions in Haskell have come into
Haskell because someone felt confined by those boundaries and figured
out a way to make at least some of those boundaries become obsolete,
so that they could go back to focussing on their programs again.

most of the complications in Haskell (of which there are quite a few)
stem not from features, but either from arbitrary limitations of those
features or from underspecified interactions between features. all of
which are signs that the areas in question haven't settled down yet.

think of Haskell as a large town with a reasonably solid and
well-defined center, where most of the living takes place, extending
into less solid and less well-defined corner areas, where everything is
permanently under construction. there is absolutely nothing wrong with
doing all your work in those parts of this little world that are fairly
undisputed, stable and simple ('simple' as in: a lot of work has gone
into smoothing away any rough edges, complicated limitations, or
surprising feature interactions).

in fact, it is a very sensible thing to do: if one were to move into a
new town, one'd try to live and work in a part of it that is no longer
under construction, but has all the infrastructure one needs. it is only
when one needs more than is currently provided that one needs to start
looking into those construction areas. and even then one does not look
for whatever they have that we haven't, but rather for i have this
specific problem; will any of the construction sites help me with it?.

don't expect construction work in the outer districts to stop just
because many people live and work happily in the town center. and, of
course, keep your hard hat on when visiting construction sites!-)

claus


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


Re: [Haskell-cafe] Language extensions

2007-05-28 Thread Brandon S. Allbery KF8NH


On May 28, 2007, at 4:13 , Andrew Coppin wrote:

Haskell 98 does an excellent job of being extremely simple, yet  
almost unbelievably powerful. Almost every day, I am blown away by  
how powerful it is. I suppose it just defies belief that you could  
possibly need even *more* power than is already in the language...  
and also, as I've mentioned, Haskell being simple is one of the most


*shrug*

Thing is, everything you can do in Haskell you can do in COBOL, as  
they're both Turing-complete.  That doesn't mean you *should*   
Features such as GADTs make it easier to express some things that are  
harder to express (and harder to read once expressed) in Haskell98;  
as such, they are a positive addition to the language.


Which doesn't mean every program has to use them --- I have yet to  
write any code using GADTs.  But I know they're there, and (roughly)  
how to use them, if I ever do.


--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon universityKF8NH


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


Re: [Haskell-cafe] Language extensions

2007-05-28 Thread Brandon S. Allbery KF8NH


On May 28, 2007, at 5:39 , Andrew Coppin wrote:

I like to think I'm an intelligent, but... maybe I'm just kidding  
myself...


Haskell's good at making people feel stupid.  :)

Just a little background, btw:  I'm no mathie, in fact I have some  
problems with math for various reasons.  Nor am I a CS researcher.   
I'm a career system administrator who got into computing as a  
teenager back when schools didn't offer computing courses and  
*certainly* didn't offer CS theory courses.  So I'm pretty close to  
the opposite of Haskell's target audience --- yet I find it useful  
and see productivity gains from using it (modulo the learning curve).


One of the nice things about Haskell is that you don't need to  
understand category theory to use monads, or advanced type theory to  
use GADTs or rank-N polymorphism.  You *do* need to learn what  
they're good for --- but this is really no different than any other  
language.  It's just that most other languages don't pack so many  
features into so small a space, because they don't have Haskell's  
expressiveness; this can be both blessing (you can do in libraries  
what other languages have to hardcode into the language) and curse  
(wrapping your head around e.g. GADTs or monads).


--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon universityKF8NH


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


Re: [Haskell-cafe] Language extensions

2007-05-28 Thread Brandon S. Allbery KF8NH


On May 28, 2007, at 6:43 , Andrew Coppin wrote:

I find this with Haskell books. There are some brilliant bits.  
There are some bits that are sort-of interesting but not really to  
do with anything I'm passionate about, and then there are bits that  
I can't comprehend...


This is a known problem with existing Haskell books.  Which is why  
there are more Haskell books coming out all the time that try to  
address it, and why there's a Wikibook (if you hit something  
incomprehensible, leave a comment so people know what to fix!).


--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon universityKF8NH


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


Re[2]: [Haskell-cafe] Language extensions

2007-05-28 Thread Bulat Ziganshin
Hello Andrew,

Monday, May 28, 2007, 2:43:47 PM, you wrote:

 - Chapter 12 is incomprehensible (to me at least). Fun with Phantom
 Types I've read it several times, and I still couldn't tell you what a
 phantom type is...

and noone else know! that is the whole fun is! :)

seriously, i'm known of writing tutorials for things hard to
understand: arrays, i/o, typeclasses. once i've started paper about
gadt and type system overall, i will send you my sketch which may be
helpful

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] Language extensions

2007-05-28 Thread Jan-Willem Maessen


On May 28, 2007, at 7:32 AM, Claus Reinke wrote:

I meant to imply more that it's very difficult to understand why  
it's useful. If an extension were truely *useless*, I doubt those  
guys at GHC would have bothered spending years implementing them.


Most of the documents that describe these things begin with  
suppose we have this extremely complicated and difficult to  
understand situation... now, we want to do X, but the type system  
won't let us. Which makes it seem like these extensions are only  
useful in extremely complicated and rare situations.


keep in mind that paper space is a precious and limited resource. the
need for extensions tends to arise in practice first, but those  
real examples
are far too big and complex to fit into those limitations. it is  
very difficult to
come up with examples that are small enough to fit, yet complex  
enough to
exhibit the problem. which means that the examples usually look  
artificial,
but small and complete, or realistic, but so large that their  
presentation

has to be shallow enough to border on vague.


But I do wonder if we shouldn't declare a moratorium on examples that  
involve interpreters for simply-typed languages (which tend to  
characterize none of the problems I'm actually trying to solve---and  
that includes fiddling with non-simply-typed languages of a similar  
sort) in favor of examples which actually perform some sort of a  
useful manipulation.


This is why I absolutely LOVE functional pearls of all sorts, by the  
way.


-Jan-Willem Maessen




smime.p7s
Description: S/MIME cryptographic signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Language extensions [was: Memoization]

2007-05-28 Thread Claus Reinke


I'm thinking more about things like phantom types, rank-N polymorphism, 
functional dependencies, GADTs, etc etc etc that nobody actually 
understands.


this seems to be overly polymorphic in generalising over all types of
Haskell programmers, rather than admitting the existence of some types
of programmers who might have different values. qualifying such
generalisations by grouping types of programmers into classes with
different methods would seem a more Haskellish way, don't you think?-)

and although it isn't nice to typecast people, sometimes one only needs
to know the type, not the person, and sometime one needs even less
information, such as a property of a type or its relation to other
types. and especially if one is interested in relationships between
different types, it is helpful to know if one type of person in such a
relationship always occurs in combination with one and the same other
type. and if there are times when one might even generalise over
generalisations (although one doesn't like to generalise over so many
people all at once;-), there are other times when one might need to be
rather specific about which of several possible alternative types one is
putting together in a single construction.

there, does that cover everything in that list? sorry, couldn't
resist!-) in exchange, below is a quick summary (didn't we have a
dictionary/quick-reference somewhere at haskell.org? i can't seem 
to find it right now, but if you know where it is, and it doesn't
already contain better explanations, feel free to add the text 
below - but check the draft for errors first, please;)


claus

--
phantom types:
 the types of ghost values (in other words, we are only interested in
 the type, not in any value of that type). typical uses are tagging
 another value with a separate, more precise type (so that we can talk
 either about the value's own type, or about the type tag associated
 with it), or enabling type-level meta-programming via type classes.

 so, if we have

   data O = O
   data S a = S a
   data T a phantom = T a

 we can distinguish between (T True :: T Bool O) and 
 (T True :: T Bool (S O)) - even though they have the same value,

 they differ in the phantom component of their types. if you think of
 'O' as 'Object' and 'S O' as some subclass of 'O' (in the oop sense),
 this allows us to see the same value as an instance of different
 (oop-style) classes, which has been used for foreign function
 interfaces to oop languages.

monomorphism:
 a monomorphic type is a type without type variables (such as '[Char]')

polymorphism:
 a polymorphic type is a generalisation of a monomorphic type (in 
 other words, we have replaced some concrete subterms of a type 
 with type variables; as in '[a]'). polymorphic types involve implicit

 or explicit all-quantification over their type variables (in other
 words, a polymorphic type stands *for all* monomorphic types that 
 can be obtained by substituting types for type variables; so 
 'forall a.[a]' stands for '[Char]' and '[Bool]', among others)


quantified types (forall/exist):
 an easy way to memorize this is to think of 'forall' as a big 'and'
 and of 'exists' as a big 'or'. 


   e :: forall a. a  -- e has type 'Int' and type 'Bool' and type ..
   e :: exists a. a  -- e has type 'Int' or  type 'Bool' or  type ..

qualified types:
 type classes allow us to constrain type variables in quantified 
 types to instances of specified classes. so, rather than assuming 
 that equality can be defined on all types, or using type-specific

 symbols for equality at different types, we can define a single
 overloaded equality function defined over all types which provide 
 an equality test ('(==) :: forall a. Eq a = a - a - Bool').


rank-N polymorphism:
 in rank-1 polymorphism, type variables can only stand for monomorphic
 types (so, '($) :: (a-b) - a - b' can only apply monomorphic
 functions to their arguments, and polymorphic functions are not
 first-class citizens, as they cannot be passed as parameters without
 their types being instantiated). in rank-N (N1) polymorphism,
 type-variables can stand for rank-(N-1) polymorphic types (in other
 words, polymorphic functions can now be passed as parameters, and used
 polymorphically in the body of another function).

   f :: (forall a. [a]-Int) - ([c],[d]) - (Int,Int)
   f g (c,d) = (g c,g d)

   f length ([1..4],[True,False])

functional dependencies:
 when using multi-parameter type classes, we specify relations between
 types (taken from the cartesian product of type class parameters).

 without additional measures, that tends to lead to ambiguities (some
 of the type class parameters can not be deduced unambiguously from the
 context, so no specific type class instance can be selected).

 functional dependencies are one such measure to reduce ambiguities,
 allowing us to specify that some subset A of type-class parameters
 functionally determines another subset B (so if 

[Haskell-cafe] Language extensions [was: Memoization]

2007-05-27 Thread Andrew Coppin

apfelmus wrote:

Andrew Coppin wrote:
  

OOC, can anybody tell me what ∀ actually means anyway?



http://en.wikipedia.org/wiki/Universal_quantification
http://en.wikipedia.org/wiki/System_F
  


So... ∀x . P means that P holds for *all* x, and ∃ x . P means that x 
holds for *some* x? (More precisely, at least 1 possible choice of x.)



I do recall that GHC has some weird extension called existential
quantification



http://haskell.org/haskellwiki/Existential_types
http://en.wikibooks.org/wiki/Haskell/Existentially_quantified_types
  


Erm... oh...kay... That kind of makes *slightly* more sense now...

Seriously. Haskell seems to attract weird and wonderful type system 
extensions like a 4 Tesla magnet attracts iron nails... And most of 
these extensions seem to serve no useful purpose, as far as I can 
determine. And yet, all nontrivial Haskell programs *require* the use of 
at least 3 language extensions. It's as if everyone thinks that Haskell 
98 sucks so much that it can't be used for any useful programs. This 
makes me very sad. I think Haskell 98 is a wonderful language, and it's 
the language I use for almost all my stuff. I don't understand why 
people keep trying to take this small, simple, clean, elegant language 
and bolt huge, highly complex and mostly incomprehensible type system 
extensions onto it...


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


Re: [Haskell-cafe] Language extensions [was: Memoization]

2007-05-27 Thread David House

On 27/05/07, Andrew Coppin [EMAIL PROTECTED] wrote:

So... ∀x . P means that P holds for *all* x, and ∃ x . P means that x
holds for *some* x? (More precisely, at least 1 possible choice of x.)


Exactly. There's also a lesser-used there exists a unique, typically
written ∃!x. P, which means that P is true for one, and only one,
value of x. For some examples of how these quantifiers are used:

∀x in R. x^2 = 0 (real numbers have a nonnegative square)
∃x in N. x  3 (there is at least one natural number less than 3)
∃!x in N. x  1 (there is only a single natural number less than 1)

For the LaTeX versions, http://www.mathbin.net/11020.


Erm... oh...kay... That kind of makes *slightly* more sense now...


I wrote most of the second article, I'd appreciate any feedback you have on it.


Seriously. Haskell seems to attract weird and wonderful type system
extensions like a 4 Tesla magnet attracts iron nails... And most of
these extensions seem to serve no useful purpose, as far as I can
determine. And yet, all nontrivial Haskell programs *require* the use of
at least 3 language extensions. It's as if everyone thinks that Haskell
98 sucks so much that it can't be used for any useful programs. This
makes me very sad. I think Haskell 98 is a wonderful language, and it's
the language I use for almost all my stuff. I don't understand why
people keep trying to take this small, simple, clean, elegant language
and bolt huge, highly complex and mostly incomprehensible type system
extensions onto it...


Ever tried writing a nontrivial Haskell program? Like you said, they
require these type system extensions! :) Obviously they don't
require them, Haskell 98 is a Turing-complete language, but they're
useful to avoid things like code-reuse and coupling. One of Haskell's
design aims is to act as a laboratory for type theory research, which
is one of the reasons why there are so many cool features to Haskell's
type system.

Anyway, existential types (and higher-rank polymorphism), along with
multi-parameter type classes, some kind of resolution to the MPTC
dliemma -- so functional dependencies or associated types or
something similar -- and perhaps GADTs are really the only large type
system extensions likely to make it into Haskell-prime. They're really
more part of the Haskell language than extensions now, so well-used
are they.

--
-David House, [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Language extensions [was: Memoization]

2007-05-27 Thread Brandon S. Allbery KF8NH


On May 27, 2007, at 9:19 , Andrew Coppin wrote:

So... ∀x . P means that P holds for *all* x, and ∃ x . P means  
that x holds for *some* x? (More precisely, at least 1 possible  
choice of x.)


Exactly.

Seriously. Haskell seems to attract weird and wonderful type system  
extensions like a 4 Tesla magnet attracts iron nails... And most of  
these extensions seem to serve no useful purpose, as far as I can  
determine. And yet, all nontrivial Haskell programs *require* the  
use of at least 3 language extensions. It's as if everyone thinks  
that Haskell 98 sucks so much that it can't be used for any useful  
programs. This makes me very sad. I think


Which ones?  The only one that comes to mind is hierarchical  
libraries, which are a Good Thing --- the H98 flat namespace becomes  
increasingly restrictive as Haskell gains more libraries (both  
included ones, and from e.g. Hackage.)


Keep in mind also that many of these extensions are part of Haskell  
Prime, which last I checked is supposed to become official sometime  
later this year.


Haskell 98 is a wonderful language, and it's the language I use for  
almost all my stuff. I don't understand why people keep trying to  
take this small, simple, clean, elegant language and bolt huge,  
highly complex and mostly incomprehensible type system extensions  
onto it...


Experimentation.  There are things you can't do with straight Haskell  
98 (even something as simple as the State monad benefits from  
functional dependencies; but fundeps are troublesome enough that  
associated types are being explored as a cleaner alternative).


Haskell's in kind of a strange position, being simultaneously a  
research language and a language which is useful in the real  
world.  The tension between these is one reason why there are  
standards (H98 and the upcoming H'):  we real world types write to  
H98 or H' (increasingly the latter), while the researchers play with  
type system extensions and the like.


--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon universityKF8NH


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


Re: [Haskell-cafe] Language extensions [was: Memoization]

2007-05-27 Thread Andrew Coppin

 Erm... oh...kay... That kind of makes *slightly* more sense now...

 I wrote most of the second article, I'd appreciate any feedback you
 have on it.

If I'm understanding this correctly, existentially quantified types
(couldn't you find a name that's any harder to
remember/pronounce/spell?) provide an opaque and nonintuitive syntax for
writing a type with a type variable hidden inside it. Is that about right?

 Ever tried writing a nontrivial Haskell program? Like you said, they
 require these type system extensions! :) Obviously they don't
 require them, Haskell 98 is a Turing-complete language, but they're
 useful to avoid things like code-reuse and coupling. One of Haskell's
 design aims is to act as a laboratory for type theory research, which
 is one of the reasons why there are so many cool features to Haskell's
 type system.

(Nitpick: Code-reuse is not something to avoid. Perhaps you meant
code duplication?)

I'm curiose about your assertion that Haskell was designed for type
system experiments. According to a paper I read recently, Haskell was
actually designed to be a single, standardised functional language
suitable for teaching. The fact that there are a lot of type system
experiments is an unexpected accident, probably due to Haskell already
having type classes. Or so the paper says anyway...

 Anyway, existential types (and higher-rank polymorphism), along with
 multi-parameter type classes, some kind of resolution to the MPTC
 dliemma -- so functional dependencies or associated types or
 something similar -- and perhaps GADTs are really the only large type
 system extensions likely to make it into Haskell-prime. They're really
 more part of the Haskell language than extensions now, so well-used
 are they.

In my book, if it's difficult to explain what a feature even *does*, you
have to wonder if that feature is really necessary...

MPTCs are a simple enough extension to the existing type system -
instead of 1 type, you can have several. I can think of an immediate
application for this:

class Convertable a b where
convert :: a - b

(I doubt I'm the first to hit upon this one.)

Associated types look very interesting, useful and intuitive. I *swear*
I read somewhere that they're in GHC 6.6.1... but apparently I'm
mistaken. :-( This is probably *the* only extension I actually want to
see in Haskell-Prime.

Apart from that, we have GADTs (um... why?), rank-N polymorphism (er...
what?), functional dependencies (I don't get it), overlapping instances
(why?), impredictive exceptions (again, I can't even comprehend what
this *is*)... the list just goes on and on!

If there's a simple, comprehensible language extension that solves a big
class of problems, sure, knock yourself out! But this just seems like
every time somebody finds a small problem it's like hey, let's invent a
whole new branch of type theory just to solve this particular edge case...

Hmm. I'm ranting...

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


Re: [Haskell-cafe] Language extensions [was: Memoization]

2007-05-27 Thread Philippa Cowderoy
On Sun, 27 May 2007, Andrew Coppin wrote:

 Seriously. Haskell seems to attract weird and wonderful type system extensions
 like a 4 Tesla magnet attracts iron nails... And most of these extensions seem
 to serve no useful purpose, as far as I can determine. And yet, all nontrivial
 Haskell programs *require* the use of at least 3 language extensions. It's as
 if everyone thinks that Haskell 98 sucks so much that it can't be used for any
 useful programs. This makes me very sad. I think Haskell 98 is a wonderful
 language, and it's the language I use for almost all my stuff. I don't
 understand why people keep trying to take this small, simple, clean, elegant
 language and bolt huge, highly complex and mostly incomprehensible type system
 extensions onto it...
 

Yeah, who needed type classes anyway?

By which I mean that that's always been the way with haskell, and once you 
get what the extensions do they tend to in fact be highly natural - 
sometimes to the extent that people forget that they were ever an 
extension (constructor classes, anyone?). 

For example, GADTs let you implement monads as interpreters by defining a 
datatype representing the abstract syntax tree that describes a 
computation - you can't get this to type without at a minimum existential 
types and for many monad operations you need the full power of GADTs to 
declare a corresponding constructor.

I imagine it would never have occurred to you to try implementing a monad 
that way, right? Similarly, a lot of the developments with type classes 
and polymorphism have been about letting people write sufficiently general 
libraries - they're driven by the demands of code that people want to 
write, but often not so much by the demands of single, simple 
applications.

Incidentally, Haskell 98 isn't that small a language itself - there's 
plenty of sugar around.

-- 
[EMAIL PROTECTED]

There is no magic bullet. There are, however, plenty of bullets that
magically home in on feet when not used in exactly the right circumstances.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Language extensions

2007-05-27 Thread Andrew Coppin

Philippa Cowderoy wrote:

On Sun, 27 May 2007, Andrew Coppin wrote:
  

Seriously. Haskell seems to attract weird and wonderful type system extensions
like a 4 Tesla magnet attracts iron nails... And most of these extensions seem
to serve no useful purpose, as far as I can determine.



Yeah, who needed type classes anyway?

By which I mean that that's always been the way with haskell, and once you 
get what the extensions do they tend to in fact be highly natural - 
sometimes to the extent that people forget that they were ever an 
extension (constructor classes, anyone?). 
  


Type classes are very easy to explain, and quite obviously useful. This, 
presumably, is why they're in the language.


Almost all language extensions seem to be of the form hey, let's see 
what happens if we randomly change the type checking rules so that 
*this* is permitted. What would that be like? Usually it's an extreme 
struggle to even wrap my brain around what the extension *is*, never 
mind why this would be a useful thing...


(OOC, what's a constructor class?)

For example, GADTs let you implement monads as interpreters by defining a 
datatype representing the abstract syntax tree that describes a 
computation - you can't get this to type without at a minimum existential 
types and for many monad operations you need the full power of GADTs to 
declare a corresponding constructor.


I imagine it would never have occurred to you to try implementing a monad 
that way, right?


Indeed, I'm still figuring out why you would want to do something like 
this. (Beyond because you can.)


Similarly, a lot of the developments with type classes 
and polymorphism have been about letting people write sufficiently general 
libraries - they're driven by the demands of code that people want to 
write, but often not so much by the demands of single, simple 
applications.
  


Well, sure enough I've run across useful things the type checker won't 
let me do. (For example, you can't make Data.Set into a monad, since it 
demands that all elements be in Ord, but a monad is required to accept 
*all* possible element types.) It's pretty rare though.


OTOH, given that I've never developed any significant Haskell 
applications or libraries, presumably everybody will simply conclude 
that I don't know what the  I'm talking about and simply ignore me...


Incidentally, Haskell 98 isn't that small a language itself - there's 
plenty of sugar around.
  


Looks like a pretty simple language to me...

I once read about this language called C++. It's supposed to be like 
C, but better. And it is - if by better you mean, exactly the same, 
but a lot more complicated. By comparison, Haskell is a *tiny* 
language. And yet, Haskell seems to allow you to express algorithms in a 
handful of lines of code that would take entire libraries in C, C++, 
Pascal, Java, Smalltalk, Tcl... and just about every other language I've 
ever seen in my life!


Seriously. Haskell seems to be pretty much the apex of programming. I 
can't imagine how you could make it any better. (Well, appart from a few 
trivial things like changing some of the poor name choices in the 
Prelude, and adding more libraries for real world stuff - but nothing 
really deep or fundamental about the language itself.) And yet, people 
keep adding more and more and more and more extensions. If it was that 
somebody added one extension that really transformed the expressiveness 
of the language, then fine. But on the contrary, it seems to be millions 
of little bits and pieces being added. It just seems messy and complicated.


(I also spent some time using a language called Eiffel. I read the 
book too. Long derrivation of why the language is the way it is, why 
each and every feature and detail is there, and how it forms a cohesive 
whole. And boy, I was pretty convinced. And Eiffel is a pretty powerful 
language. But... um... the type checking rules. OMG, *nobody* I know of 
can actually understand that stuff! I mean, in general it just does 
what you want, but if it doesn't... good luck figuring it out! 
Multiple inheritance, generics *and* specialisation in the same 
language? Hmm... good luck sorting all that out in your code! In short: 
a lovely language, but... almost too complicated to use.)


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


Re: [Haskell-cafe] Language extensions [was: Memoization]

2007-05-27 Thread Andrew Coppin

Brandon S. Allbery KF8NH wrote:
Seriously. Haskell seems to attract weird and wonderful type system 
extensions like a 4 Tesla magnet attracts iron nails... And most of 
these extensions seem to serve no useful purpose, as far as I can 
determine. And yet, all nontrivial Haskell programs *require* the use 
of at least 3 language extensions. It's as if everyone thinks that 
Haskell 98 sucks so much that it can't be used for any useful 
programs. This makes me very sad. I think


Which ones?  The only one that comes to mind is hierarchical 
libraries, which are a Good Thing --- the H98 flat namespace becomes 
increasingly restrictive as Haskell gains more libraries (both 
included ones, and from e.g. Hackage.)


Hierachical libraries are a very good extension - in fact, I can bearly 
believe they weren't in the original language spec. I was under the 
impression that this isn't an extension any more because it's been 
added to the official language report. (?)


I'm thinking more about things like phantom types, rank-N polymorphism, 
functional dependencies, GADTs, etc etc etc that nobody actually 
understands.


Keep in mind also that many of these extensions are part of Haskell 
Prime, which last I checked is supposed to become official sometime 
later this year.


This worries me greatly. I'm really afraid that Haskell will go from 
being this wonderful, simple language that you can explain in a page or 
two of text to being this incomprehensible mass of complex type 
machinery that I and most other human beings will never be able to learn 
or use. :-(


Also... sometime later this year? That's new to me...

Haskell 98 is a wonderful language, and it's the language I use for 
almost all my stuff. I don't understand why people keep trying to 
take this small, simple, clean, elegant language and bolt huge, 
highly complex and mostly incomprehensible type system extensions 
onto it...


Experimentation.  There are things you can't do with straight Haskell 
98 (even something as simple as the State monad benefits from 
functional dependencies; but fundeps are troublesome enough that 
associated types are being explored as a cleaner alternative).


Haskell's in kind of a strange position, being simultaneously a 
research language and a language which is useful in the real world.  
The tension between these is one reason why there are standards (H98 
and the upcoming H'):  we real world types write to H98 or H' 
(increasingly the latter), while the researchers play with type system 
extensions and the like.


People experimenting with the language I can live with. (Although I'd 
prefer it not to be called Haskell. Very confusing when people start 
asking me questions about this Haskell program that actually uses 
non-standard extensions that I've never heard of. And when I have to 
admit that even *I* can't comprehend what the code does, people go away 
with the notion that Haskell really *is* impossible to learn and it's 
not worth trying.)


What worries me is the day when you'll need to understand set theory and 
propositional calculus just to use any of the standard libraries. 
(Already I can't use the State monad because it requires some extension 
or other. Not that I understand why - as far as I can tell, it's 100% 
possible to define a State monad without language extensions. The 
library just doesn't, that's all. Well, I can always define my own I 
guess...)


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


Re: [Haskell-cafe] Language extensions [was: Memoization]

2007-05-27 Thread Philippa Cowderoy
On Sun, 27 May 2007, Andrew Coppin wrote:

 I'm thinking more about things like phantom types, rank-N polymorphism,
 functional dependencies, GADTs, etc etc etc that nobody actually understands.
 

I think you'll find a fair number of people do in fact understand them! 

 This worries me greatly. I'm really afraid that Haskell will go from being
 this wonderful, simple language that you can explain in a page or two of text
 to being this incomprehensible mass of complex type machinery that I and most
 other human beings will never be able to learn or use. :-(
 

So don't use type extensions in your own code? It's comparatively rare to 
have any big problems using libraries that make use of them - I remember 
banging my head briefly the first time I used ST as a newbie, but that was 
about it.

 What worries me is the day when you'll need to understand set theory and
 propositional calculus just to use any of the standard libraries.

It would be no bad thing if people were less scared of them and just 
learned - they're not complicated.

 (Already I
 can't use the State monad because it requires some extension or other. Not
 that I understand why - as far as I can tell, it's 100% possible to define a
 State monad without language extensions. The library just doesn't, that's all.
 Well, I can always define my own I guess...)
 

The library doesn't because defining a sufficiently generic notion of 
State monad (enough so that we can treat a more complex monad that 
also has a notion of state the same way) requires the extensions. It's all 
about the polymorphism - one of the reasons Haskell code stays simple is 
that the amount of polymorphism possible makes people less keen on writing 
massive overbearing frameworks.

-- 
[EMAIL PROTECTED]

There is no magic bullet. There are, however, plenty of bullets that
magically home in on feet when not used in exactly the right circumstances.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Language extensions

2007-05-27 Thread Brandon S. Allbery KF8NH


On May 27, 2007, at 17:23 , Andrew Coppin wrote:

Personally, I try to avoid ever using list comprehensions. But  
every now and then I discover an expression which is apparently not  
expressible without them - which is odd, considering they're only  
sugar...


They are.  But they're sugar for monadic operations in the list  
monad, so you have to use (=) and company to desugar them.  [x |  
filter even x, x - [1..10]] becomes do { x - [1..10]; return  
(filter even x) } becomes ([1..10] = return . filter even).


(Aren't you glad you asked?)

--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon universityKF8NH


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


Re: [Haskell-cafe] Language extensions

2007-05-27 Thread Andrew Coppin



Type classes are very easy to explain, and quite obviously useful. This,
presumably, is why they're in the language.




You'd be surprised, I've seen people twist their brains in knots before 
finally getting it.
  


Given the long debate I've just had about why (/) 7 4 is a valid 
expression but / 7 4 isn't, nothing would surprise me... *sigh*



Almost all language extensions seem to be of the form hey, let's see what
happens if we randomly change the type checking rules so that *this* is
permitted. What would that be like? Usually it's an extreme struggle to even
wrap my brain around what the extension *is*, never mind why this would be a
useful thing...




The proposer almost invariably has a use case - often a pretty big one. 
  


But usually one that's vastly too mind-bending to comprehend, it must be 
said...


I suppose it's like when mathematitions say that the Gamma function is 
of fundamental importance - and yet they can't explain what it's 
actually important for.



(OOC, what's a constructor class?)




It's a type class that's really a class of type constructors rather than 
one of types - if you like, a class whose parameter isn't of kind *. The 
canonical example is Monad. These days they're just type classes, there's 
no distinction made.
  


Oh, right. I thought that was called higher-kinded classes?


Indeed, I'm still figuring out why you would want to do something like this.
(Beyond because you can.)



It's much easier to understand than the 'traditional' style of 
implementation (which fuses the constructors with the interpreter). It's 
even more useful if you work with structures like arrows where there are 
useful things you can do with a computation without actually running it, 
as you don't have to bake the various analyses into the arrow type. I 
wouldn't chose it as the ideal release version, but I'd mechanically build 
the release code by doing everything with the GADT and then fusing once 
I'm done - and if compilers ever get good enough at deforesting, I'd 
happily elide that step!


If you're fond of the Knuth quote, then the 'traditional' implementation 
may smell a lot like premature optimisation enforced by an inflexible type 
system.
  
 
  

Well, sure enough I've run across useful things the type checker won't let me
do. (For example, you can't make Data.Set into a monad, since it demands that
all elements be in Ord, but a monad is required to accept *all* possible
element types.) It's pretty rare though.




For me, working in Haskell 98, it tends to happen as my apps grow above a 
certain size (and it's less than a thousand lines). That, and I find the 
ST monad pretty invaluable so if I'm doing something where it fits I 
won't blink before using it.
  


Perhaps it depends on the kind of code you write or something... I've 
found very few occasions where the type system defeats me. (Heterogenous 
lists, the Set monad I mentioned, a few bits like that.) Mostly I can't 
make my programs work properly because I can't come up with a working 
algorithm.


  
  

Looks like a pretty simple language to me...




It can be stripped significantly further.


True. But I mean, useful little bits of syntax aside, the semantics are 
pretty simple. (Indeed, that's what I love about the language. Figure 
out function definition, function application, currying, parametric 
polymorphism, and type classes and you've basically learned almost all 
of it.)


you can 
retain pretty much everything with variables, applications, lambdas and 
simple let and case statements.


I wish I had a parser that would parse Haskell this way... heh.

Things like do blocks and list 
comprehensions aren't strictly speaking necessary at all, and an awful lot 
of complexity's added to parsing Haskell 98 by everything that can be done 
with infix operators.
  


Yeah, parsing Haskell is pretty simple until you add comments, and 
do-blocks, and list comprehensions, and infix operators, and where 
bindings, and guards, and...


Personally, I try to avoid ever using list comprehensions. But every now 
and then I discover an expression which is apparently not expressible 
without them - which is odd, considering they're only sugar...



You're missing a lot of the conceptual background


Possibly. I find that most of what is written about Haskell tends to be 
aimed at absolute beginners, or at people with multiple PhDs. (As in, 
people to whom arcane terms like denotational semantics actually 
*means* something.) I remember seeing somebody wrote a game (!!) in 
Haskell - despite the fact that this is obviously impossible. So I went 
to read the paper about how they did it... and rapidly become completely 
lost. I get that they used something called funtional reactive 
programming, but I am still mystified as to what on earth that actually 
is, or how it functions.


But an awful lot 
of the more popular extensions are primarily about relaxing constraints 
and picking 

Re: [Haskell-cafe] Language extensions [was: Memoization]

2007-05-27 Thread Bulat Ziganshin
Hello Andrew,

Sunday, May 27, 2007, 5:19:51 PM, you wrote:

 Seriously. Haskell seems to attract weird and wonderful type system
 extensions like a 4 Tesla magnet attracts iron nails... And most of 
 these extensions seem to serve no useful purpose, as far as I can 
 determine.

existentials is something like OOP objects but without inheritance -
they pack data plus code together and make only methods available. you
can find more info here:

http://haskell.org/haskellwiki/OOP_vs_type_classes

there is also recent Simon Marlow paper about implementing dynamic
extensible extensions and, in fact, OOP with inheritance using these
existentials recursively


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] Language extensions

2007-05-27 Thread Jim Burton



Andrew Coppin wrote:
 
 
 [snip]
 You're missing a lot of the conceptual background
 
 Possibly. I find that most of what is written about Haskell tends to be 
 aimed at absolute beginners, or at people with multiple PhDs. (As in, 
 people to whom arcane terms like denotational semantics actually 
 *means* something.) I remember seeing somebody wrote a game (!!) in 
 Haskell - despite the fact that this is obviously impossible. So I went 
 to read the paper about how they did it... and rapidly become completely 
 lost. I get that they used something called funtional reactive 
 programming, but I am still mystified as to what on earth that actually 
 is, or how it functions.
 
 But an awful lot 
 of the more popular extensions are primarily about relaxing constraints 
 and picking the most natural way to follow through.
 
 Hey, let's make it so that classes can have several parameters! Um... 
 OK, that more or less makes sense. I can see uses for that.
 
 Hey, let's make it so a class instance can have one or more types 
 associated with it! Er... well, that seems straight forward enough. 
 Alright.
 
 Hey, let's make it so that class methods can have completely arbitrary 
 types! Wait, what the hell? How does *that* make sense?! o_O
 
 
Speaking as someone who, like you, came to the language recently and for
whom many of haskell's outer corners are still confusing, I should firstly
say that I can see where you're coming from but that it puzzles me as to why
you think things ought to be obvious or why, when something isn't obvious to
you, it must be useless? Could the answer be that it will take some time
before you understand the motivation for features that don't seem natural to
you? You might need some patience and study along with everything else, I
know I do (and people have been generous with links to work that explains
the motivation). I only say this because you seem, bizarrely, to be
suggesting that you could improve things by undoing the work of all these
scary people as you call them in another post, whilst admitting that you
don't understand it.



 Hey, let's make it so you can use a type variable on the RHS that 
 doesn't even appear on the LHS! Um... that's going to be tricky, but 
 sure, OK.
 
 Hey, let's make it so you can implement Prolog programs inside the type 
 system! Right, I'm getting my coat now... :-P
 
 In short, some of these relax restrictions in fairly obvious directions, 
 and others just seem downright bizzare.
 
 It helps if you can picture a matching explicitly-typed language.
   
 
 I don't really understand that statement.
 
 An idea you might find helps: what you're finding with algorithms, I find 
 with architecture when I have the extensions that let me type it.
   
 
 ...or that one...
 
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 
 

-- 
View this message in context: 
http://www.nabble.com/Memoization-tf3822500.html#a10829748
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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