[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 [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 [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 [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 (N>1) 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

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 [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 (N>1) 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 [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 [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 [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