Re: [Haskell-cafe] Type vs TypeClass duality

2007-10-24 Thread Sterling Clover
I'm relatively new to Haskell, so maybe this answer is a bit off, in  
that I'm sure there are times when some sort of auto-existential  
creation may have a point, but generally I've found that when I want  
it I've been thinking about the problem wrong.


The bigger issue is that as soon as you get fancier types classes,  
they'll probably be paramaterized over more than one type, not to  
mention with possible functional dependencies, etc., and very likely  
be polymorphic over return value as well. in fact, I suspect, Show  
and maybe fromIntegral or such aside, cases like you describe where  
you might even have the possibility of doing what you're looking for  
(i.e., a list of a typeclass such that a function in it is guaranteed  
a single return type) look fairly rare.


Integrals are a good example of what I ran into early on -- suppose  
you had a [Integral] rather than one of Integral a = [a]. What  
would be the advantage of this? It would actually make your code  
messier -- instead of a case of, e.g. [x:x':xs] - x+x' you wold need  
one of [x:x':xs] - fromIntegral x + fromIntegral x', otherwise you  
would have no guarantee the types would match! And even then, what  
would the return type of this function be? Polymorphic over Integral?  
You'd just be spreading the fuzziness over type to the rest of your  
program, and probably introducing a load of potential inefficiencies  
to boot.


I suspect that you may still be trying to code with an OO mentality  
which thinks of the methods of a typeclass as within it as they are  
within an object, rather than as _on_ it.


--s

On Oct 23, 2007, at 4:09 AM, TJ wrote:


Hi again,

Following up on my previous thread, I have figured out why it bothered
me that we cannot have a list such as the following: [abc, 123, (1,
2)] :: Show a = [a]

It seems to me that there is an annoying duality in treating simple
algebraic data type vs type classes. As it stands, I can only have a
list where all the elements are of the same basic, ADT, type. There is
no way to express directly a list where all the elements satisfy a
given type class constraint.

If I am not mistaken, type classes are currently implemented in GHC  
like so:


Given a function show of type Show a = a - string, and the
expression show 10, GHC will pass the Int dictionary for class
Show's methods and the integer 10 to the function show. In other
words, for each type class constraint in the function type, there will
be a hidden dictionary parameter managed entirely by the compiler.

What I find strange is, if we can have functions with hidden
parameters, why can't we have the same for, say, elements of a list?

Suppose that I have a list of type Show a = [a], I imagine that it
would not be particularly difficult to have GHC insert a hidden item
along with each value I cons onto the list, in effect making the
concrete type of the list [(Dictionary Show, a)]. I'm assuming that it
will not be particularly difficult because GHC will know the types of
the values I cons onto it, so it will most definitely be able to find
the Show dictionary implemented by that type, or report a type
mismatch error. No dynamic type information is necessary.

I am not an OO programming zealot, but I'd like to note here that this
is also how (class based) OO languages would allow the programmer to
mix types. e.g. I can have a ListShow where the elements can be
instances of Show, or instances of subclasses of Show.

Why does this second rate treatment of type classes exist in Haskell?


TJ
___
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] XML parser recommendation?

2007-10-24 Thread Uwe Schmidt
Rene de Visser wrote:

 I think a step towards support medium size documents in HXT would be to 
 store the tags and content more efficiently.
 If I undertand the coding correctly every tag is stored as a seperate 
 Haskell string. As each byte of a string under GHC takes 12 bytes this alone 
 leads to high memory usage. Tags tend to repeat. You could store them 
 uniquely using a hash table. Content could be stored in compressed byte 
 strings.

Yes, storing element and attribute names in a packed format, something
similar to ByteString but for unicode values, would reduce the amount
of storage. A perhaps small shortcomming of that aproach are the conversions 
between
String and the internal representation when processing names.

The hashtable approach would of course reduce memory usage, but this
would require a global change of the processing model: A document then
does not longer consist of a single tree, it alway consists of a pair of a tree 
and a map.

By the way, the amount of memory used for strings ([Char] values) in Haskell is
a problem for ALL text processing tasks. Its not limited HXT, nor is it special 
to XML.

For me the efficieny problems with strings as list of chars and a possible
solution by e.g. implementing String data transparenty more efficent than other 
lists
is an issue for Haskell' (or Haskell'') and/or it's a challage for the language 
implementors.

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


Re: [Haskell-cafe] A possibly stupid doubt about the GHC's overlapping instances flag's

2007-10-24 Thread Bas van Dijk
[only replying to haskell-cafe]

On 10/20/07, Rodrigo Geraldo [EMAIL PROTECTED] wrote:
 Hi!

 Suppose that the GHC's flag -fallow-incoherent-instances is enabled. In this
 situation, when a instance will be rejected?
 And if the flag -fallow-overlapping-instances is enabled. When a instance
 will be rejected?

 Thanks!

 Rodrigo

The following is mainly from the GHC Userguide:
http://www.haskell.org/ghc/docs/latest/html/users_guide/type-extensions.html#instance-overlap

Suppose you have:


{-# OPTIONS_GHC -fglasgow-exts  -fallow-overlapping-instances #-}

classC a   b where foo :: a - b - (a, b)

instance C Int a where foo n x  = (n+1, x)   -- (A)
instance C a   Bool  where foo x b  = (x,   not b)   -- (B)
instance C Int [a]   where foo n xs = (n+1, xs)  -- (C)
instance C Int [Int] where foo n ns = (n+1, map (+1) ns) -- (D)

f :: [b] - [b]
f xs = snd $ foo (1 :: Int) xs


In the right hand sight of 'f', 'foo' is applied to an Int and a [b]
so it seems that instance C should match. However GHC rejects this
program because in a later call 'f' can be applied to  a list of Ints
(like in: g = f ([1,2,3] :: [Int])) by which 'b' instantiates to an
Int, by which instance D should really match.

If you enable -fallow-incoherent-instances then 'f' will use instance
C without complaining about the problem of subsequent instantiations.

However if you then define 'g' you will get the error:

Couldn't match expected type `Int' against inferred type `[a]'
In the first argument of `f', namely `([1, 2, 3] :: Int)'

regards,

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


Re: [Haskell-cafe] A possibly stupid doubt about the GHC's overlapping instances flag's

2007-10-24 Thread Daniel Fischer
Am Mittwoch, 24. Oktober 2007 10:35 schrieb Bas van Dijk:

 Suppose you have:


 {-# OPTIONS_GHC -fglasgow-exts  -fallow-overlapping-instances #-}

 classC a   b where foo :: a - b - (a, b)

 instance C Int a where foo n x  = (n+1, x)   -- (A)
 instance C a   Bool  where foo x b  = (x,   not b)   -- (B)
 instance C Int [a]   where foo n xs = (n+1, xs)  -- (C)
 instance C Int [Int] where foo n ns = (n+1, map (+1) ns) -- (D)

 f :: [b] - [b]
 f xs = snd $ foo (1 :: Int) xs


 In the right hand sight of 'f', 'foo' is applied to an Int and a [b]
 so it seems that instance C should match. However GHC rejects this
 program because in a later call 'f' can be applied to  a list of Ints
 (like in: g = f ([1,2,3] :: [Int])) by which 'b' instantiates to an
 Int, by which instance D should really match.

 If you enable -fallow-incoherent-instances then 'f' will use instance
 C without complaining about the problem of subsequent instantiations.

 However if you then define 'g' you will get the error:

 Couldn't match expected type `Int' against inferred type `[a]'
 In the first argument of `f', namely `([1, 2, 3] :: Int)'

This seems to be a typo. 
g = f ([1,2,3] :: [Int]) is accepted.

g = f ([1,2,3] :: Int) can never be, overlapping/incoherent instances or not


 regards,

 Bas.

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


[Haskell-cafe] Existential types (Was: Type vs TypeClass duality)

2007-10-24 Thread apfelmus

TJ wrote:


data Showable = forall a. Show a = Showable a
stuff = [Showable 42, Showable hello, Showable 'w']


Which is exactly the kind of 2nd-rate treatment I dislike.

I am saying that Haskell's type system forces me to write boilerplate.


Nice :) I mean, the already powerful Hindley-Milner type system is free 
of type annotations (= boilerplate). It's existential types and other 
higher-rank types that require annotations because type inference in 
full System F (the basis of Haskell's type system so to speak) is not 
decidable. In other words, there is simply no way to have System F 
without boilerplate.


That being said, there is still the quest for a minimal amount of 
boilerplate and in the right place. That's quite a hard problem, but 
people are working on that, see for instance


http://research.microsoft.com/~simonpj/papers/gadt/index.htm
http://research.microsoft.com/~simonpj/papers/higher-rank/index.htm
http://research.microsoft.com/users/daan/download/papers/mlftof.pdf
http://research.microsoft.com/users/daan/download/papers/existentials.pdf



 [exists a. Show a = a]


I actually don't understand that line. Substituting forall for exists,
someone in my previous thread said that it means every element in the
list is polymorphic, which I don't understand at all, since trying to
cons anything onto the list in GHCi results in type errors.


Let's clear the eerie fog surrounding universal quantification in this 
thread.


-+- The mathematical symbol for  forall  is  ∀  (Unicode)
 exists  is  ∃

-+- ∀a.(a - a) means:
you give me a function (a - a) that I can apply
to _all_ argument types  a  I want.

  ∃a.(a - a) means:
you give me a function (a - a) and tell me that
_there is_ a type  a  that I can apply this function to.
But you don't tell me the type  a  itself. So, this particular
example ∃a.(a - a) is quite useless and can be replaced with ().

-+- A more useful example is

∃a. Show a = a   i.e.  ∃a.(a - String, a)

So, given a value (f,x) :: ∃a.(a - String, a), we can do

f x :: String

but that's pretty much all we can do. The type is isomorphic to a simple 
String.


∃a.(a - String, a)  ~  String

So, instead of storing a list [∃a. Show a = a], you may as well store a 
list of strings [String].


-+- Since ∀ and ∃ are clearly different, why does Haskell have only one 
of them and even uses ∀ to declare existential types? The answer is the 
following relation:


  ∃a.(a - a) = ∀b. (∀a.(a - a) - b) - b

So, how to compute a value  b  from an existential type ∃a.(a - a)? 
Well, we have to use a function  ∀a.(a - a) - b  that works for any 
input type (a - a) since we don't know which one it will be.


More generally, we have

  ∃a.(f a)= ∀b. (∀a.(f a) - b) - b

for any type  f a  that involves a, like

  f a = Show a = a
  f a = a - a
  f a = (a - String, a)

and so on.

Now, the declaration

  data Showable = forall a. Show a = Showable a

means that the constructor Showable gets the type

  Showable :: ∀a. Show a = a - Showable

and the deconstructor is

  caseS :: Showable - ∀b. (∀a.(Show a = a) - b) - b
  caseS sx f = case sx of { Showable x - f x }

which is the same as

  caseS :: Showable - ∃a. Show a = a

. GADT-notation clearly shows the ∀

  data Showable where
Showable :: ∀a - Showable


-+- The position of the quantifier matters.
- Exercise 1: Explain why

  [∀a.a]  ∀a.[a]  [∃a.a]  and  ∃a.[a]

are all different.
- Exercise 2: ∀ can be lifted along function arrows, whereas ∃ can't. 
Explain why


  String - ∀a.a   =   ∀a.String - a
  String - ∃a.a  =/=  ∃a.String - a

Since ∀ can always be lifted to the top, we usually don't write it 
explicitly in Haskell.


-+- Existential types are rather limited when used for OO-like stuff but 
are interesting for ensuring invariants via the type system or when 
implementing algebraic data types. Here the mother of all monads in 
GADT-notation


  data FreeMonad a where
return :: a - FreeMonad a
(=)  :: ∀b. FreeMonad b - (b - FreeMonad a) - FreeMonad a

Note the existential quantification of  b . (The ∀b can be dropped, like 
the ∀a has been.)



Regards,
apfelmus

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


Re: [Haskell-cafe] A possibly stupid doubt about the GHC's overlapping instances flag's

2007-10-24 Thread Bas van Dijk
On 10/24/07, Daniel Fischer [EMAIL PROTECTED] wrote:
 This seems to be a typo.
 g = f ([1,2,3] :: [Int]) is accepted.

Oops, a typo it is!

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


[Haskell-cafe] Re: XML parser recommendation?

2007-10-24 Thread apfelmus

Uwe Schmidt wrote:

The hashtable approach would of course reduce memory usage,


Note that hashtables are evil :) I'm all for tries instead.


but this
would require a global change of the processing model: A document then
does not longer consist of a single tree, it alway consists of a pair of a tree 
and a map.


Ah! I got struck by a trick: it's possible to store every tag name in 
full only once but still present a simple tree with full tag names to 
the user. You simply share all the tag names. For instance, in


  let x = mytagname in Tree (Tag x) [Tree (Tag x) [Text foobar]]

the string mytagname is stored in memory only once although there are 
two tags with this name.


When parsing an XML-file, you look up every parsed tag name in a finite 
map (i.e. the trie). If it's already in, you don't store the parsed tag 
name in the XML tree but the one stored at the leaf in the trie. Of 
course, these two strings are equal. But they're not (pointer-) 
identical! After parsing, all equal tag names now are pointers to one 
and the same leaf in the finite map. You can drop the finite map 
structure afterwards, the pointers to the leaves will remain.


That would be quite the memory reduction for large XML trees which are 
likely to have many many identical tag names.


Regards,
apfelmus

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


Re: [Haskell-cafe] Type vs TypeClass duality

2007-10-24 Thread Tristan Allwood
On Wed, Oct 24, 2007 at 11:00:14AM +0800, TJ wrote:
 Tristan Allwood:
 
 Very cool. I don't understand some (a lot of) parts though:
 
  instance Show a = Reify (ShowConstraint a) where reify = ShowC
 
 ShowC has type (Show a) = ShowConstraint a, whereas reify is
 supposed to have type ShowConstraint a.
Yes.  ShowC is a constant that wraps up the knowledge of (Show a =) for
ShowConstraint.  So (in this case) 

reify :: ShowConstraint a
reify = ShowC  

(since ShowC is the only non-bottom value ShowConstraint can take)

But in order to return ShowC, we must know that a 'is in' Show, which is
why the instance declaration requires that at the point you use reify
you can demonstrate that a is in Show:

instance Show a = Reify (ShowConstraint a) where
 ^

If the Show a = bit is removed, then the type checker rightly
complains, because the ShowC doesn't have a Show a context that it
needs.

So the trick is that in the cons (#) function which uses reify, you need
to prove 'Reify (a b)', and it just so happens that by the instance
declaration above, wherever you have 'Show a' then you have 'Reify
(ShowConstraint a)' which is why testList needs nothing more than the
values to put into it like a normal list.

 
  data SingleList (a :: * - *) where Cons :: (a b) - b - SingleList
  a - SingleList a Nil :: SingleList a
 
 Cons has a type variable b in its signature, but no forall. I
 suppose it comes from the * - * in SingleList's type?
Nope.  The (a :: * - *) is a kind annotation and means that the a is a
type that is parameterised by a type (e.g. Maybe :: * - *, whereas
Maybe Int :: *), which is why you can write (a b).  I think technically
it's a redundant annotation here as it can be inferred from the (a b)
useage.

The b is 'just' a normal, exisistentially quantified variable - GADTs
don't require you to write forall in their declarations - see the very
last sentence on
http://www.haskell.org/ghc/docs/latest/html/users_guide/gadt.html
 
 
 That's all I can come up with for now. A great deal of high level
 coding flying around above my head now.
Hope that helps some, 

Regards,

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


[Haskell-cafe] ANN: new version of matrix library (GSLHaskell)

2007-10-24 Thread Alberto Ruiz
Dear Haskellers,

I am happy to announce a new version of GSLHaskell, a basic library for matrix 
computations and other numeric algorithms based on LAPACK, BLAS and 
GSL. The goal is that simple problems involving singular values, linear 
systems, etc, can be easily solved using Haskell. The library is horribly 
incomplete, I don't recommend it for any serious work. But at least I enjoy 
using it in my projects...

Some features of this release are:

* Improved internal implementation, most code has been refactored.

* It works on Linux, Windows, and MacOS X (see the README of the 
distribution).

* Automatic bindings to 200+ GSL special functions.

Source code, documentation, updated tutorial, and more information is 
available from:

   http://dis.um.es/~alberto/GSLHaskell

I'd like to upload a decent version to hackage, so any kind of feedback is 
very welcome!

Thanks,

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


Re: [Haskell-cafe] Re: XML parser recommendation?

2007-10-24 Thread Uwe Schmidt
apfelmus wrote:

 Ah! I got struck by a trick: it's possible to store every tag name in
 full only once but still present a simple tree with full tag names to
 the user. You simply share all the tag names. For instance, in

let x = mytagname in Tree (Tag x) [Tree (Tag x) [Text foobar]]

 the string mytagname is stored in memory only once although there are
 two tags with this name.

 When parsing an XML-file, you look up every parsed tag name in a finite
 map (i.e. the trie). If it's already in, you don't store the parsed tag
 name in the XML tree but the one stored at the leaf in the trie. Of
 course, these two strings are equal. But they're not (pointer-)
 identical! After parsing, all equal tag names now are pointers to one
 and the same leaf in the finite map. You can drop the finite map
 structure afterwards, the pointers to the leaves will remain.

 That would be quite the memory reduction for large XML trees which are
 likely to have many many identical tag names.

I've also thought about this approach. It sounds a bit weired,
to built a map (or a trie) for the identity function. But it would
solve a part of the space problem, at least when building XML
documents by parsing.
So I guess, there is a new project:
A simple, small and lazy parser (no parsec), at least for the content
part of XML.

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


[Haskell-cafe] Job: web development in Haskell

2007-10-24 Thread red nucleus
Anyone who is serious about doing web development in Haskell is
welcome to apply for the job outlined below. If we found a good
functional programmer, we can ignore the bits about Rails.

Web Developer

RedNucleus Ltd (rednucleus.co.uk) is seeking a highly motivated
programmer for a full or part-time posititon developing social web
applications. Initially you will develop and maintain applications
using RubyOnRails or a similar framework, but there will be
opportunities to explore new web programming paradigms with
declarative languages.

The successful application will have:
-a good degree in computer science or a quantitative topic.
-good independent programming and quantitative analysis skills.
-some familiarity with HTML, CSS, JavaScript and SQL, and with network
programming.
-exposure to functional programming methodologies, e.g. in Haskell,
Lisp or Erlang.

Graduate level qualifications in computer science and expertise in web
development including RubyOnRails would be a plus.

RedNucleus is based in Beeston, Nottingham. The successful application
could work here or mostly from home.

Salary depends on experience and qualifications, starting from £22,000
plus performance bonus.

To apply, please prepare a single pdf file containing your cover
letter and CV, and name the file with your surname, e.g. smith.pdf.
Then send the file to: [EMAIL PROTECTED] Informal enquiries can
be directed to the same address.

The closing date for applications is 22nd November 2007
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Existential types (Was: Type vs TypeClass duality)

2007-10-24 Thread Alfonso Acosta
Thanks for posting this, I finally understand existentials!

This bit was specially helpful:

So, how to compute a value  b  from an existential type ∃a.(a - a)? ...

Could you give a specific example of computing existential types?

I think this shows why digested tutorials, as opposed to research
papers (which tend require a strong background), are needed in the
Haskell community to make life easier for the newcomer.

Things as existentials (which are not part of the standard yet but
used frequently in real world applications)  should be documented in a
friendly way.

The Haskell Wikibook is usually be helpful but unfortunately it wasn't
that clear in the case of existentials (for me at least). I think the
existentials article misses the clarity shown by aplemus' explanation
and furthermore does not cover the computing a value from an
existantial type directly. Maybe it would be a good idea to extend
it.

Thanks apfelmus!

PS: Can't wait for the Real World Haskell Book to be released.


On 10/24/07, apfelmus [EMAIL PROTECTED] wrote:
 TJ wrote:
 
  data Showable = forall a. Show a = Showable a
  stuff = [Showable 42, Showable hello, Showable 'w']
 
  Which is exactly the kind of 2nd-rate treatment I dislike.
 
  I am saying that Haskell's type system forces me to write boilerplate.

 Nice :) I mean, the already powerful Hindley-Milner type system is free
 of type annotations (= boilerplate). It's existential types and other
 higher-rank types that require annotations because type inference in
 full System F (the basis of Haskell's type system so to speak) is not
 decidable. In other words, there is simply no way to have System F
 without boilerplate.

 That being said, there is still the quest for a minimal amount of
 boilerplate and in the right place. That's quite a hard problem, but
 people are working on that, see for instance

 http://research.microsoft.com/~simonpj/papers/gadt/index.htm
 http://research.microsoft.com/~simonpj/papers/higher-rank/index.htm
 http://research.microsoft.com/users/daan/download/papers/mlftof.pdf
 http://research.microsoft.com/users/daan/download/papers/existentials.pdf

 
   [exists a. Show a = a]
 
  I actually don't understand that line. Substituting forall for exists,
  someone in my previous thread said that it means every element in the
  list is polymorphic, which I don't understand at all, since trying to
  cons anything onto the list in GHCi results in type errors.

 Let's clear the eerie fog surrounding universal quantification in this
 thread.

 -+- The mathematical symbol for  forall  is  ∀  (Unicode)
   exists  is  ∃

 -+- ∀a.(a - a) means:
  you give me a function (a - a) that I can apply
  to _all_ argument types  a  I want.

∃a.(a - a) means:
  you give me a function (a - a) and tell me that
  _there is_ a type  a  that I can apply this function to.
  But you don't tell me the type  a  itself. So, this particular
  example ∃a.(a - a) is quite useless and can be replaced with ().

 -+- A more useful example is

  ∃a. Show a = a   i.e.  ∃a.(a - String, a)

 So, given a value (f,x) :: ∃a.(a - String, a), we can do

  f x :: String

 but that's pretty much all we can do. The type is isomorphic to a simple
 String.

  ∃a.(a - String, a)  ~  String

 So, instead of storing a list [∃a. Show a = a], you may as well store a
 list of strings [String].

 -+- Since ∀ and ∃ are clearly different, why does Haskell have only one
 of them and even uses ∀ to declare existential types? The answer is the
 following relation:

∃a.(a - a) = ∀b. (∀a.(a - a) - b) - b

 So, how to compute a value  b  from an existential type ∃a.(a - a)?
 Well, we have to use a function  ∀a.(a - a) - b  that works for any
 input type (a - a) since we don't know which one it will be.

 More generally, we have

∃a.(f a)= ∀b. (∀a.(f a) - b) - b

 for any type  f a  that involves a, like

f a = Show a = a
f a = a - a
f a = (a - String, a)

 and so on.

 Now, the declaration

data Showable = forall a. Show a = Showable a

 means that the constructor Showable gets the type

Showable :: ∀a. Show a = a - Showable

 and the deconstructor is

caseS :: Showable - ∀b. (∀a.(Show a = a) - b) - b
caseS sx f = case sx of { Showable x - f x }

 which is the same as

caseS :: Showable - ∃a. Show a = a

 . GADT-notation clearly shows the ∀

data Showable where
  Showable :: ∀a - Showable


 -+- The position of the quantifier matters.
 - Exercise 1: Explain why

[∀a.a]  ∀a.[a]  [∃a.a]  and  ∃a.[a]

 are all different.
 - Exercise 2: ∀ can be lifted along function arrows, whereas ∃ can't.
 Explain why

String - ∀a.a   =   ∀a.String - a
String - ∃a.a  =/=  ∃a.String - a

 Since ∀ can always be lifted to the top, we usually don't write it
 explicitly in Haskell.

 -+- Existential types are rather limited when used for OO-like stuff but
 are interesting for ensuring invariants 

Re: [Haskell-cafe] will the real quicksort please stand up? (or: sorting a million element list)

2007-10-24 Thread Brent Yorgey
On 10/23/07, Thomas Hartman [EMAIL PROTECTED] wrote:


 Actually I can't compile it, with or without -O2. loads fine into ghci,
 but when I try to create an executable I get

 ghc quicksort.hs -o quicksort
 quicksort.o: In function `r1Nc_info': undefined reference to
 `QuickCheckzm1zi0zi1_TestziQuickCheck_vector_closure'
 quicksort.o: In function `r1Nc_info': undefined reference to
 `QuickCheckzm1zi0zi1_TestziQuickCheck_zdf16_closure'
 quicksort.o: In function `s1Ws_info': undefined reference to
 `QuickCheckzm1zi0zi1_TestziQuickCheck_generate_closure'
 quicksort.o: In function `r1Nc_srt': undefined reference to
 `QuickCheckzm1zi0zi1_TestziQuickCheck_vector_closure'
 quicksort.o: In function `r1Nc_srt': undefined reference to
 `QuickCheckzm1zi0zi1_TestziQuickCheck_zdf16_closure'
 quicksort.o: In function `rzC_srt': undefined reference to
 `QuickCheckzm1zi0zi1_TestziQuickCheck_generate_closure'
 collect2: ld returned 1 exit status


hmm, try adding --make to the ghc command line?  Unfortunately, GHC doesn't
automatically chase down dependencies for linking; you must specify them
explicitly with -package, or tell it to auto-chase dependencies with --make.

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


Re: [Haskell-cafe] ANNOUNCE: dataenc 0.9

2007-10-24 Thread Magnus Therning
On Tue, Oct 23, 2007 at 15:50:54 +0200, Yitzchak Gale wrote:
Magnus Therning wrote:
 My collection of data encoding functions are now available

Nice!

Should this effort be coordinated with Unicode-related
encoding/decoding? See the Encoding class in Twan van Laarhoven's
CompactString library:

http://twan.home.fmf.nl/compact-string/

and Johan Tibell's UnicodeByteString proposal:

http://haskell.org/haskellwiki/UnicodeByteString

There was a recent discussion about these, mostly the latter:

http://www.haskell.org/pipermail/haskell-cafe/2007-September/032195.html

Yes, I somewhat followed the beginning of that discussion but my
Unicode-fu isn't very strong.

If you have concrete suggestions for changes to the API then please let
me know.  I have vague plans of writing a uuencode/uudecode in Haskell
so that might bring up some issues with the current API.

I hate to keep bringing up serpents, but note that Python has a nice
codec abstraction that provides efficient encoding and decoding of
character encodings, data encodings, data compression, etc., all with
the same interface. You can attach these things to file handles, or
apply them to strings. Makes sense to me.

It would be great to see something equally unified in Haskell in the
future.

/M

-- 
Magnus Therning (OpenPGP: 0xAB4DFBA4)
magnus@therning.org Jabber: magnus.therning@gmail.com
http://therning.org/magnus


pgpXhAh4Bln31.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] freebsd-7.0BETA1 and ghc

2007-10-24 Thread brad clawsie
a note recently went out regarding the first beta release of freebsd7

note that ghc is still marked as broken in the 7-branch ports tree due
to issues regarding the move from gcc3x to gcc4x. if you rely on ghc,
you may want to hold off on an upgrade


pgpPRFO4Q1yxk.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haskell Report??

2007-10-24 Thread Brent Yorgey
On 10/23/07, Galchin Vasili [EMAIL PROTECTED] wrote:

 Hello,

   I am trying to use a Haskell shell (Hsh.hs). I am a little
 frustrated. There are two modules that are imported:

 import LibPosix
 import LibSystem

 I am running WinHugs (Windows) and hugs/ghci can't find LibSystem. I am
 confused about 1) what are currently standard libraries, etc. in Haskell, 2)
 what is deprecated  and 3) what are  home grown tomatoes ;^) How current
 and definitive is the Haskell Report?

 Kind regards, Bill  Halchin


For currently standard GHC libraries, see here:

http://www.haskell.org/ghc/docs/latest/html/libraries/index.html

'LibPosix' and 'LibSystem' look like names from before the current
hierarchical module system was adopted, so it would seem that code is
somewhat outdated.  LibPosix should probably be System.Posix, but I'm not
sure what used to be in LibSystem and where it could be found now.  If
you're determined to get it to work, try searching the libraries for the
names of systemish-looking functions in Hsh.hs, and see if you can find in
what modules they now live, and import those.  No promises that the APIs
haven't changed, though, so you might still have problems anyway.

The Haskell Report is definitive but not very current (it is almost 10
years old at this point).  In practice, there are many extensions to the
language and libraries which are fairly widespread and standard but are not
documented in the Report.  Hopefully Haskell' will fix that, but no telling
when that will be done!

-Brent


___
 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] XML parser recommendation?

2007-10-24 Thread Malcolm Wallace
Yitzchak Gale [EMAIL PROTECTED] wrote:

 Another question about HaXML and HXT -
 what is the level of XML spec. compliance?

In HaXml, I certainly tried pretty hard to match the (draft) XML 1.0
spec, since the library was originally developed for a commercial
entity.  But that was back in 1999, and the spec has changed a little
since then.  You're right that it is a difficult target to hit though.
The spec is unnecessarily complex.

The major area of non-compliance in HaXml is that it doesn't do anything
with input encodings.  That is partly a limitation of Haskell
implementations themselves, which have only recently gained libraries
for the purpose.

Otherwise, Dimitry Astapov has recently been sending me patches to fix
some minor compliance problems, along with the QuickCheck properties
that discovered them.  His additions will appear probably in the next
release of HaXml.

Let me emphasise that these non-compliances are very minor.  Larger
issues that remain open do not fall into the compliance spectrum, but
are more about useability in practice.  For instance: effective support
for external catalogs of references; techniques to handle XML namespaces
in a sensible fashion, etc.

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


[Haskell-cafe] Re: Existential types (Was: Type vs TypeClass duality)

2007-10-24 Thread Peter Hercek

apfelmus wrote:
-+- Since ∀ and ∃ are clearly different, why does Haskell have only one 
of them and even uses ∀ to declare existential types? The answer is the 
following relation:


  ∃a.(a - a) = ∀b. (∀a.(a - a) - b) - b

So, how to compute a value  b  from an existential type ∃a.(a - a)? 
Well, we have to use a function  ∀a.(a - a) - b  that works for any 
input type (a - a) since we don't know which one it will be.


More generally, we have

  ∃a.(f a)= ∀b. (∀a.(f a) - b) - b


Is that by definition or (if it a consequence of the previous formula,
 is that one by definition)? Because it kind of makes sense but that
 does not mean much. If the formulas are not by defininition,
 any pointers to explanation why they are valid?
Why it is not only like this?
∃a.(f a)= ∀b. (∀a.(f a) - b)

- Exercise 2: ∀ can be lifted along function arrows, whereas ∃ can't. 
Explain why


  String - ∀a.a   =   ∀a.String - a
  String - ∃a.a  =/=  ∃a.String - a

Since ∀ can always be lifted to the top, we usually don't write it 
explicitly in Haskell.



I do not see why forall can be lifted to the top of function arrows.
 I probably do not understand the notation at all. They all seem to be
 different to me.

 String - ∀a.a
a function which takes strings a returns a value of all types together
 for any input string (so only bottom could be the return value?)

 ∀a.(String - a)
a function which takes strings and returns a values of a type we want
 to be returned (whichever one it is; in given  contexts the return
 value type is the same for all input strings)

 String - ∃a.a
a function taking strings and returning values of some type but we do
 not know anything about the type (in the same contexts and for each
 different input string the output type can be different)

 ∃a.(String - a)
a function taking strings and returning values of some type; for each
 different input string there is the same output type

 Any pointers to explanations?

Thanks for one of the more informative posts on this subject.


Peter.

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


Re: [Haskell-cafe] Existential types (Was: Type vs TypeClass duality)

2007-10-24 Thread Dan Weston

Thanks for the concise explanation. I do have one minor question though.

 -+- A more useful example is

 ∃a. Show a = a   i.e.  ∃a.(a - String, a)

 So, given a value (f,x) :: ∃a.(a - String, a), we can do

 f x :: String

 but that's pretty much all we can do. The type is isomorphic to a simple
 String.

Don't you mean *epimorphic* instead of isomorphic (not that it matters)? 
For any existential type a of cardinality less than that of String, it 
is isomorphic, but if a = String, then by Cantor's theorem String - 
String has a cardinality greater than String and cannot be isomorphic to it.


 ∃a.(a - String, a)  ~  String

 So, instead of storing a list [∃a. Show a = a], you may as well store a
 list of strings [String].

True. This loses no observable information because (given the 
existential) even if there may be no unique function for a given String, 
there would be no way to tell any two such apart anyway, as the only 
thing you can do with them is to apply the functions of Show, and they 
all return the same String.


apfelmus wrote:

TJ wrote:


data Showable = forall a. Show a = Showable a
stuff = [Showable 42, Showable hello, Showable 'w']


Which is exactly the kind of 2nd-rate treatment I dislike.

I am saying that Haskell's type system forces me to write boilerplate.


Nice :) I mean, the already powerful Hindley-Milner type system is free 
of type annotations (= boilerplate). It's existential types and other 
higher-rank types that require annotations because type inference in 
full System F (the basis of Haskell's type system so to speak) is not 
decidable. In other words, there is simply no way to have System F 
without boilerplate.


That being said, there is still the quest for a minimal amount of 
boilerplate and in the right place. That's quite a hard problem, but 
people are working on that, see for instance


http://research.microsoft.com/~simonpj/papers/gadt/index.htm
http://research.microsoft.com/~simonpj/papers/higher-rank/index.htm
http://research.microsoft.com/users/daan/download/papers/mlftof.pdf
http://research.microsoft.com/users/daan/download/papers/existentials.pdf



 [exists a. Show a = a]


I actually don't understand that line. Substituting forall for exists,
someone in my previous thread said that it means every element in the
list is polymorphic, which I don't understand at all, since trying to
cons anything onto the list in GHCi results in type errors.


Let's clear the eerie fog surrounding universal quantification in this 
thread.


-+- The mathematical symbol for  forall  is  ∀  (Unicode)
 exists  is  ∃

-+- ∀a.(a - a) means:
you give me a function (a - a) that I can apply
to _all_ argument types  a  I want.

  ∃a.(a - a) means:
you give me a function (a - a) and tell me that
_there is_ a type  a  that I can apply this function to.
But you don't tell me the type  a  itself. So, this particular
example ∃a.(a - a) is quite useless and can be replaced with ().

-+- A more useful example is

∃a. Show a = a   i.e.  ∃a.(a - String, a)

So, given a value (f,x) :: ∃a.(a - String, a), we can do

f x :: String

but that's pretty much all we can do. The type is isomorphic to a simple 
String.


∃a.(a - String, a)  ~  String

So, instead of storing a list [∃a. Show a = a], you may as well store a 
list of strings [String].


-+- Since ∀ and ∃ are clearly different, why does Haskell have only one 
of them and even uses ∀ to declare existential types? The answer is the 
following relation:


  ∃a.(a - a) = ∀b. (∀a.(a - a) - b) - b

So, how to compute a value  b  from an existential type ∃a.(a - a)? 
Well, we have to use a function  ∀a.(a - a) - b  that works for any 
input type (a - a) since we don't know which one it will be.


More generally, we have

  ∃a.(f a)= ∀b. (∀a.(f a) - b) - b

for any type  f a  that involves a, like

  f a = Show a = a
  f a = a - a
  f a = (a - String, a)

and so on.

Now, the declaration

  data Showable = forall a. Show a = Showable a

means that the constructor Showable gets the type

  Showable :: ∀a. Show a = a - Showable

and the deconstructor is

  caseS :: Showable - ∀b. (∀a.(Show a = a) - b) - b
  caseS sx f = case sx of { Showable x - f x }

which is the same as

  caseS :: Showable - ∃a. Show a = a

. GADT-notation clearly shows the ∀

  data Showable where
Showable :: ∀a - Showable


-+- The position of the quantifier matters.
- Exercise 1: Explain why

  [∀a.a]  ∀a.[a]  [∃a.a]  and  ∃a.[a]

are all different.
- Exercise 2: ∀ can be lifted along function arrows, whereas ∃ can't. 
Explain why


  String - ∀a.a   =   ∀a.String - a
  String - ∃a.a  =/=  ∃a.String - a

Since ∀ can always be lifted to the top, we usually don't write it 
explicitly in Haskell.


-+- Existential types are rather limited when used for OO-like stuff but 
are interesting for ensuring invariants via the type system or when 
implementing algebraic data types. 

[Haskell-cafe] Binary constants in Haskell

2007-10-24 Thread Maurí­cio

Hi,

Are there binary constants in Haskell, as
we have, for instance, 0o232 for octal and
0xD29A for hexadecimal?

Thanks,
Maurício

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


Re: [Haskell-cafe] Binary constants in Haskell

2007-10-24 Thread Don Stewart
briqueabraque:
 Hi,
 
 Are there binary constants in Haskell, as
 we have, for instance, 0o232 for octal and
 0xD29A for hexadecimal?

No, though it is an interesting idea.

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


Re: [Haskell-cafe] Re: Existential types (Was: Type vs TypeClass duality)

2007-10-24 Thread David Menendez
On 10/24/07, Peter Hercek [EMAIL PROTECTED] wrote:

 I do not see why forall can be lifted to the top of function arrows.
   I probably do not understand the notation at all. They all seem to be
   different to me.


Consider this simple function:

\b x y - if b then x else y

Let's say we wanted to translate that into a language like System F, where
every lambda has to have a type. We could write something like:

\(b::Bool) (x::?) (y::?) - if b then x else y

but we need something to put in those question marks. We solve this by
taking the type of x and y as an additional parameter:

\(a::*) (b::Bool) (x::a) (y::a) - if b then x else y

This would have the type forall a. Bool - a - a - a. In a dependently
typed system, we might write that type as (a::*) - (b::Bool) - (x::a) -
(y::a) - a.

Since b doesn't depend on a, we can switch their order in the argument list,

\(b::Bool) (a::*) (x::a) (y::a) - if b then x else y

This has type Bool - forall a. a - a - a or (b::Bool) - (a::*) -
(x::a) - (y::a) - a.

Haskell arranges things so that the implicit type arguments always appear
first in the argument list.

I find it helps to think of forall a. as being like a function, and exists
a. as being like a pair.

-- 
Dave Menendez [EMAIL PROTECTED]
http://www.eyrie.org/~zednenem/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Binary constants in Haskell

2007-10-24 Thread Neil Mitchell
Hi

  Are there binary constants in Haskell, as
  we have, for instance, 0o232 for octal and
  0xD29A for hexadecimal?

 No, though it is an interesting idea.

You can get pretty close with existing Haskell though:

(bin 100010011)

where bin :: Integer - Integer, and is left as an exercise for the
reader. Obviously its not as high performance, as proper binary
literals, but if you write them as top-level constants, they'll only
be computed once and shouldn't end up being in the performance
critical bits.

Thanks

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


Re: [Haskell-cafe] Binary constants in Haskell

2007-10-24 Thread Don Stewart
ndmitchell:
 Hi
 
   Are there binary constants in Haskell, as
   we have, for instance, 0o232 for octal and
   0xD29A for hexadecimal?
 
  No, though it is an interesting idea.
 
 You can get pretty close with existing Haskell though:
 
 (bin 100010011)
 
 where bin :: Integer - Integer, and is left as an exercise for the
 reader. Obviously its not as high performance, as proper binary
 literals, but if you write them as top-level constants, they'll only
 be computed once and shouldn't end up being in the performance
 critical bits.

And the call to `bin' be lifted into the Num class I suspect... leading
to raw binary literals, using overloaded literal syntax.

So I guess we do have binary literals then.

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


Re: [Haskell-cafe] Binary constants in Haskell

2007-10-24 Thread Dan Weston

Prelude read 0o232 :: Int
154
Prelude read 0xD29A :: Int
53914
Prelude

Maurí­cio wrote:

Hi,

Are there binary constants in Haskell, as
we have, for instance, 0o232 for octal and
0xD29A for hexadecimal?

Thanks,
Maurício

___
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] freebsd-7.0BETA1 and ghc

2007-10-24 Thread Xiao-Yong Jin
brad clawsie [EMAIL PROTECTED] writes:

 a note recently went out regarding the first beta release of freebsd7

 note that ghc is still marked as broken in the 7-branch ports tree due
 to issues regarding the move from gcc3x to gcc4x. if you rely on ghc,
 you may want to hold off on an upgrade

Is there any hope for it to be fixed before the freeze of
ports tree?  I use Gentoo Linux where gcc-4.1.2 is used, and
ghc compiles and works fine with that.  Wish gcc-4.2.1 used
in FreeBSD-7.0 will not differ too much.

Xiao-Yong
-- 
c/*__o/*
\ * (__
*/\  
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] freebsd-7.0BETA1 and ghc

2007-10-24 Thread brad clawsie
On Wed, Oct 24, 2007 at 06:14:49PM -0400, Xiao-Yong Jin wrote:
 Is there any hope for it to be fixed before the freeze of
 ports tree? 

i believe that is the purpose of the extended beta/rc period, to allow
ports maintainers a chance to get things fixed before the main release

as it stands a fix was submitted by a user but has not been entered
into the main ports tree (yet):

http://www.freebsd.org/cgi/query-pr.cgi?pr=117235 

my impression of freebsd beta releases is that the term beta is not
being casually applied (like google etc), but is a true cautionary label



pgpZtrOvNFm9S.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN: Math.OEIS 0.1

2007-10-24 Thread Sterling Clover
If someone organized something like that, (or even a more extended  
version like the ongoing attempts a while back to optimize for the  
language shootout) I'd be totally in. Seems like a great way for  
newer foax to take a crack at something useful and interact to get a  
better handle on the language.


--S

On Oct 22, 2007, at 10:54 AM, Brent Yorgey wrote:




The Online Encyclopedia of Integer Sequences should really contain  
more

Haskell code for describing the sequences.

Agreed!  I propose an OEIS party where we all sit around one day  
and submit Haskell code. =)


(I'm only half joking...)

-Brent
___
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