Re: [Haskell-cafe] Problem with Gtk2hs

2007-12-10 Thread Andrew Coppin

Duncan Coutts wrote:
On Sat, 2007-12-08 at 13:08 -0800, Stefan O'Rear wrote: 
  

That's pretty obviously a bug - Graphics.UI.Gtk.Gdk.PixbufData doesn't
fully implement the (M)Array class.



The MArray class changed in ghc-6.8 and we didn't notice until the
gtk2hs release was already out.
  


Ah. I knew there'd be a reason...


So there are a couple workarounds, either grab the darcs version of the
0.9.12 branch which contains the fix:
http://darcs.haskell.org/gtk2hs-branches/gtk2hs-0.9.12/

Or use the released version with ghc-6.6.x rather than 6.8.x, since 6.6
has the previous different MArray interface.

Or use the unsafe indexing operators which bypass the bounds check which
calls getNumElements.
  


Eeek! I just recompiled my existing working code with 6.8.1, and sure 
enough it's broken. I was assuming that the new code I added was the 
problem, but no, apparently it's the change of compiler [and hence 
libraries]. Well that changes things...


What do I need to compile the darcs version? Just GHC? Or do I need the 
GTK+ header files? (Remember, I'm on Windows here.)


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


Re: [Haskell-cafe] I'm translating All about Monads to Chinese

2007-12-10 Thread Paulo J. Matos
On Dec 3, 2007 12:39 PM, Albert Lee [EMAIL PROTECTED] wrote:
 I have been confussed by monad for a long time. and I can't stand for
 it any more. so I start to translate the tutorial All About Monads
 to my mother language Chinese.
 My English is not good enough, so this work is only for my own study~
 I know there are some other Chinese fellow in this list, wish it would
 be helpful.
 I will work for one chapter everyday.


Let me just add that it was (after reading several other tutorials)
All About Monads that enlightened me about them. :)

 the address is: http://www.kamang.net
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe






-- 
Paulo Jorge Matos - pocm at soton.ac.uk
http://www.personal.soton.ac.uk/pocm
PhD Student @ ECS
University of Southampton, UK
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: type class question

2007-12-10 Thread Jules Bean

Try again without missing out the list...

Peter Padawitz wrote:
 Jules Bean wrote:
 Incidentally, I question why the compFoo are methods. Why not just 
make them polymorphic functions? They don't look like you expect 
instances to change them. The code continues to compile if I make them 
functions and amend their signatures as required.


 I put compFoo into the class for the same reason why /= is part of 
the class Eq: both functions are unique as soon as the others have been 
instantiated.


I believe you misunderstand the reason.

/= is part of Eq in case a particular instance has a particularly 
efficient way to implement /=, rather than using not and (==).


Being unique as soon as the others are implemented is not a reason not 
to make it a method.



compBlock :: (Java block command intE boolE) = Block - block
compBlock = block_ . map compCommand

still retains that property.

Jules


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


Re: [Haskell-cafe] What is the role of $!?

2007-12-10 Thread Jules Bean

David Fox wrote:
Here is a practical example I ran into a few days ago.  With this 
expression:


   writeFile path (compute text)

the file at path would be overwritten with an empty file if an error 
occurs while evaluating (compute text).  With this one:


  writeFile path $! (compute text)

the file alone when an error occurs.


If I understand you correctly, that would be because compute text is 
capable of throwing an exception.


That, then, is the danger of using exceptions in pure code.

Personally I'd use an error-signalling type (like Either) and then this 
wouldn't be an issue.


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


Re: [Haskell-cafe] Re: type class question

2007-12-10 Thread Peter Padawitz

Jules Bean wrote:


Try again without missing out the list...

Peter Padawitz wrote:
 Jules Bean wrote:
 Incidentally, I question why the compFoo are methods. Why not 
just make them polymorphic functions? They don't look like you expect 
instances to change them. The code continues to compile if I make them 
functions and amend their signatures as required.


 I put compFoo into the class for the same reason why /= is part of 
the class Eq: both functions are unique as soon as the others have 
been instantiated.


I believe you misunderstand the reason.

/= is part of Eq in case a particular instance has a particularly 
efficient way to implement /=, rather than using not and (==).


Being unique as soon as the others are implemented is not a reason 
not to make it a method.


It might not have been the reason, but it is a nice effect that is often 
taken advantage of.


What is so bad about making compFoo part of the class? It reduces the 
code (constraints can be avoided) and reflects the close connection 
between  a signature Sig (implemented by the class) and the evaluation 
(compFoo) of Sig-terms in Sig-algebras.



compBlock :: (Java block command intE boolE) = Block - block
compBlock = block_ . map compCommand

still retains that property.


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


Re: [Haskell-cafe] Re: type class question

2007-12-10 Thread Jules Bean

Peter Padawitz wrote:
What is so bad about making compFoo part of the class? It reduces the 
code (constraints can be avoided) and reflects the close connection 
between  a signature Sig (implemented by the class) and the evaluation 
(compFoo) of Sig-terms in Sig-algebras.


making it part of the class allows instances to override the implementation.

Which in this case is a strange thing to do.

Class methods are ad-hoc. They can do *anything*.

Functions which happen to have constraints are something a bit more 
parametric. Their ad-hoc-ness is bounded by the methods of the class; 
they can only be implemented using methods, so they are guaranteed to be 
 uniform to some extent.


For example:

sort is a function with an Ord constraint. If sort was part of the Ord 
class, then every ordered type would be free to supply its own sort 
routine, possibly faster, possibly broken. Writing sort as a function 
rather than a method makes it generic (parametric) over all members of 
class Ord.


Jules


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


Re: [Haskell-cafe] Problem with Gtk2hs

2007-12-10 Thread Duncan Coutts

On Mon, 2007-12-10 at 10:40 +, Andrew Coppin wrote:

 What do I need to compile the darcs version? Just GHC? Or do I need the 
 GTK+ header files? (Remember, I'm on Windows here.)

Ah, that's a bit harder. It's not for the feint of heart.

I've not updated the instructions in a while. The old ones are here:
http://haskell.org/gtk2hs/archives/2005/06/24/building-from-source-on-windows/

but we now use the official Gtk+ windows binaries and headers rather
than the ones from http://gladewin32.sourceforge.net/

Our new header bundles are here: http://haskell.org/gtk2hs/win32/
and scripts are here: http://darcs.haskell.org/gtk2hs/tools/win32/
You'd want the win32-build-* ones.

You also need mingw of course. I would not recommend starting from darcs
but from a tarball and then copying over the two changed files from
darcs. The reason for that is that trying to get autoconf and automake
working on windows is more trouble than it's worth (I've never done it)
where as the tarball contains pre-generated autoconf/automake stuff.

Duncan

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


Re: [Haskell-cafe] IO is a bad example for Monads

2007-12-10 Thread Daniel Fischer
Am Montag, 10. Dezember 2007 10:36 schrieb Ketil Malde:
 Daniel Fischer [EMAIL PROTECTED] writes:
  Well, I guess you could get pretty far using 'interact' - far enough
  in an educational setting to do lists and Maybe, and then monads,
  before introducing monadic IO.
 
  Pretty far, yes, and in an educational setting, at a university, it is
  quite common, I believe, to use an interpreter for a while, not producing
  executables (that's how I met Haskell, write pure functions and type
  expressions at the Hugs prompt). But what about a tutorial for
  programmers? How would you do

 Well, yes, some things do get complicated, and I'm not suggesting that
 interact will suffice for real programs.  I still agree with the
 faction that thinks monadic IO should be taught after non-IO
 monadics - which, especially for programmers, can be quite early in
 the curriculum.  After all, lists and algebraic data types are central
 and simple concepts.

I have no teaching experience, and I have not thought a great deal about how 
to teach monads, but I think it would be good to have some familiarity with a 
couple of monads - most notably lists - when the monad 'interface' is 
explained to give examples of how different data types share some concepts.
I think, having IO as one example among others isn't necessarily bad, but 
could be convinced otherwise.


 I don't think you *need* to teach input-print sequential programs,
 though.  This is functional programming after all, why not build a
 compiler instead?

By all means, building a compiler for a simple enough language would be an 
interesting task in the course of which many concepts can be introduced.
But would Joe Programmer, who heard about this exciting language called 
Haskell and then grabbed a tutorial to see whether it's something for him be 
content to type expressions to the interpreter prompt until the compiler is 
complete, monads have been explained and only after that he is told how to 
read/write files, stdin, stdout?

  I doubt you could keep many interested without telling them how to create
  standalone programmes, including reading input from stdin and printing
  output to stdout.

 Well, my first real, standalone haskell program was reading my
 telephone log from stdin, matching against an internal database, and
 outputting calls with time and name to stdout.  I used standard
 features like shell IO redirection in and 'tee' to integrate with the
 rest of the system.

 I then moved on to monadic IO, but wish I'd done monads in general
 first.  YMMV.

 -k
Cheers,
Daniel

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


Re: [Haskell-cafe] Re: type class question

2007-12-10 Thread Jules Bean

Peter Padawitz wrote:

Jules Bean wrote:


Peter Padawitz wrote:

What is so bad about making compFoo part of the class? It reduces the 
code (constraints can be avoided) and reflects the close connection 
between  a signature Sig (implemented by the class) and the 
evaluation (compFoo) of Sig-terms in Sig-algebras.



making it part of the class allows instances to override the 
implementation.


Which in this case is a strange thing to do.


Sure, but this can only happen because Haskell does not check whether 
the instances satisfy the equations in the class. The type class concept 
would be cleaner if all methods (partially or totally) defined by 
equations within the class were not allowed to be instantiated!




I don't see why!

In the class

class Foo a where
  f :: a - Int
  g :: b - Integer
  g = fromIntegral . f

The equations within the class are defaults, not equations. The equation 
for 'g' is a default, not a rule.


If you want equations, you do it outside the class. I have written that 
class wrongly, I should actually write g = fromIntegral . f as a 
function outside the class, thus guaranteeing the implementation and 
stopping people breaking that invariant.


The purpose of methods with defaults is to allow the possibility that 
there is an obvious natural way to implement one function in terms of 
others, but there might be more efficient ways.


For example, the Foldable class should (but doesn't) have a member 
length. This could be defaulted to length . toList, but have a more 
efficient implementation in Sequence, which stores its own length anyway.


Or maybe we are at cross-purposes.

Jules

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


Re: [Haskell-cafe] Re: Do real programs need IO? (was IO is a bad example for Monads)

2007-12-10 Thread Daniel Fischer
Am Montag, 10. Dezember 2007 07:05 schrieb Maurí­cio:
(...)
 Would you deny that any useful programme has to do at least some of
  
   the following:
 -accept programme arguments at invocation
 -get input, be it from a keyboard, mouse, reading files, pipes...
 -output a result or state info, to the monitor, a file, a pipe...
  
  ===

 As long as we use current interfaces, no one
 would deny it. 

I thought Conal did, but it turned out that he just had a wider concept of RTS 
than I.

But after reading some stuff
 about Epigram language, I wonder if those
 ideas could not be used to write a better
 interface to computers. Then, all those tasks
 would be handled by your interface plug-ins,
 not by programs.

 Really, we need to do all of that today. But
 I believe reading from keyboard, files
 etc. should not be part of programs we write
 daily, just a task for a basic interface to
 which our programs should be linked.

Agreed, but until then, we need IO to write 'real' programmes. We can already 
encapsulate it somewhat using libs like TV, as I learnt yesterday, but even 
more encapsulation wouldn't be bad.

 Best,
 Maurício

Cheers,
Daniel

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


Re: [Haskell-cafe] Problem with Gtk2hs

2007-12-10 Thread Andrew Coppin

Duncan Coutts wrote:

On Mon, 2007-12-10 at 10:40 +, Andrew Coppin wrote:

  
What do I need to compile the darcs version? Just GHC? Or do I need the 
GTK+ header files? (Remember, I'm on Windows here.)



Ah, that's a bit harder. It's not for the feint of heart.

I've not updated the instructions in a while. The old ones are here:
http://haskell.org/gtk2hs/archives/2005/06/24/building-from-source-on-windows/

but we now use the official Gtk+ windows binaries and headers rather
than the ones from http://gladewin32.sourceforge.net/

Our new header bundles are here: http://haskell.org/gtk2hs/win32/
and scripts are here: http://darcs.haskell.org/gtk2hs/tools/win32/
You'd want the win32-build-* ones.

You also need mingw of course. I would not recommend starting from darcs
but from a tarball and then copying over the two changed files from
darcs. The reason for that is that trying to get autoconf and automake
working on windows is more trouble than it's worth (I've never done it)
where as the tarball contains pre-generated autoconf/automake stuff.

Duncan
  


Uh... or maybe I could just wait until the next binary release. :-}

*runs away*

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


[Haskell-cafe] help

2007-12-10 Thread Ryan Bloor
hi I am writing a basic Parser from scratch. So far I have functions;# 
removeSpaces# match - which checks if a string is a substring of another# 
orParser which combines two parser's abilities# Basic pasrers like... parseInt, 
parseTrue, parseFalse, parseBoolusing the orParser on True and False.What I 
want to do now is have a parseBinaryOp that recognises:parseBinaryOp + (5 + 
2) if  gives [(EInt 5, EInt 2, if)]So I 
think that I have to split the initial string into four parts.+ becomes op'(' 
becomes tokenF')' becomes tokenB5 becomes e12 becomes e2parseBinaryOp :: 
String - String - [(Expr, Expr, String)]parseBinaryOp op str = let 
(tokenF,e1,op,e2,tokenB) =I am not sure how to go about separating the string 
for how I need itusing my other functiuons. Ryan
_
The next generation of MSN Hotmail has arrived - Windows Live Hotmail
http://www.newhotmail.co.uk___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] [OT] A nice organized collection of threads in Haskell-Cafe

2007-12-10 Thread Brandon S. Allbery KF8NH


On Dec 10, 2007, at 0:16 , Vimal wrote:


What is the difference between In-Reply-To and References?


In-Reply-To: specifies the immediate parent message in the tree;  
References: specifies a (possibly truncated) path back to the tree's  
root.


--
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] help

2007-12-10 Thread Daniel Fischer
Am Montag, 10. Dezember 2007 14:45 schrieb Ryan Bloor:
 hi I am writing a basic Parser from scratch. So far I have functions;#
 removeSpaces# match - which checks if a string is a substring of another#
 orParser which combines two parser's abilities# Basic pasrers like...
 parseInt, parseTrue, parseFalse, parseBoolusing the orParser on True and
 False.What I want to do now is have a parseBinaryOp that
 recognises:parseBinaryOp + (5 + 2) if  gives  
   [(EInt 5, EInt 2, if)]So I think that I have to split the
 initial string into four parts.+ becomes op'(' becomes tokenF')' becomes
 tokenB5 becomes e12 becomes e2parseBinaryOp :: String - String -
 [(Expr, Expr, String)]parseBinaryOp op str = let (tokenF,e1,op,e2,tokenB)
 =I am not sure how to go about separating the string for how I need itusing
 my other functiuons. Ryan

Keep it simpler. Write combinators

parseFirstThen  :: Parser a - Parser b - Parser (a,b)

parseFirstThenWith :: (a - b - c) - Parser a - Parser b - Parser c

or 
applyToParse :: (a - b) - Parser a - Parser b

(then you would find
parseFirstThenWith f p1 p2 === applyToParse (uncurry f) (parseFirstThen p1 p2)

and 
applyToParse f p === parseFirstThenWith (const . f) p (succeed ())

where succeed x input = [(x,input)]
)
and compose your parser using these.
Better still, read
http://www.haskell.org/haskellwiki/Homework_help
and the chapter on parsing in any tutorial/textbook, docs and sources for 
parsing libraries, such as parsec.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: type class question

2007-12-10 Thread Peter Padawitz

Jules Bean wrote:


Peter Padawitz wrote:


Jules Bean wrote:


Peter Padawitz wrote:

What is so bad about making compFoo part of the class? It reduces 
the code (constraints can be avoided) and reflects the close 
connection between  a signature Sig (implemented by the class) and 
the evaluation (compFoo) of Sig-terms in Sig-algebras.


making it part of the class allows instances to override the 
implementation.


Which in this case is a strange thing to do.


Sure, but this can only happen because Haskell does not check whether 
the instances satisfy the equations in the class. The type class 
concept would be cleaner if all methods (partially or totally) 
defined by equations within the class were not allowed to be 
instantiated!



I don't see why!

In the class

class Foo a where
  f :: a - Int
  g :: b - Integer
  g = fromIntegral . f

The equations within the class are defaults, not equations. 


I must admit that I didn't know this... Nevertheless, won't you agree 
that the default and the actual instance should be semantically equivalent?



The equation for 'g' is a default, not a rule.

If you want equations, you do it outside the class. I have written 
that class wrongly, I should actually write g = fromIntegral . f as a 
function outside the class, thus guaranteeing the implementation and 
stopping people breaking that invariant.


The purpose of methods with defaults is to allow the possibility that 
there is an obvious natural way to implement one function in terms of 
others, but there might be more efficient ways.


For example, the Foldable class should (but doesn't) have a member 
length. This could be defaulted to length . toList, but have a more 
efficient implementation in Sequence, which stores its own length anyway.


Or maybe we are at cross-purposes.


No no, default functions make sense.

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


Re: [Haskell-cafe] Re: type class question

2007-12-10 Thread Bertram Felgenhauer
Peter Padawitz wrote:
 Jules Bean wrote:
 I don't see why!

 In the class

 class Foo a where
   f :: a - Int
   g :: b - Integer
   g = fromIntegral . f

 The equations within the class are defaults, not equations. 

 I must admit that I didn't know this... Nevertheless, won't you agree that 
 the default and the actual instance should be semantically equivalent?

It depends on the class, or maybe on your notion of semantical
equivalence. As an example, look at the Show class. Its interface is

 class Show a where
   showsPrec :: Int - a - ShowS
   show :: a - String
   showList :: [a] - ShowS

showsPrec has a default implementation in terms of show, and show
a default implementation in terms of showsPrec. Instances may refine
showsPrec but should still satisfy  show x = shows x .

However, the most interesting function here is showList. It comes
with a default implementation that renders a list as [item1,...].

showList is used in the Show instance for lists:

 instance Show a = Show [a]  where
 showsPrec _ = showList

By redefining showList for Char, we get a prettier representation
for String values.

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


role of seq, $!, and bangpatterns illuminated with lazy versus strict folds Re: [Haskell-cafe] What is the role of $!?

2007-12-10 Thread Thomas Hartman
rather than ask the role of $! I found it helpful to first grasp the role 
of seq, since $! is defined in terms of seq and seq is a primitive 
operation (no prelude definition, like with IO, it's a given).

What helped me grasp seq was its role in a strict fold.

Basically, try to sum all the numbers from 1 to a million. Prelude sum 
probably gives stack overflow (if not, up it to a billion ;) ), and so 
will a  naive fold, as is explained at

http://www.haskell.org/haskellwiki/Stack_overflow

The code below basically restates what was already on the wiki, but I 
found my definitions of foldl' (using seq, bang patterns, and $!) easier 
to understand than the definition on the wiki page, and the definition 
from Data.List. (Maybe I'll edit the wiki.)

t.

{-# LANGUAGE BangPatterns #-}

-- stack overflow
t1 = myfoldl (+) 0 [1..10^6]
-- works, as do myfoldl'' and myfoldl'''
t2 = myfoldl' (+) 0 [1..10^6] 

-- (myfoldl f q ) is a curried function that takes a list
-- If I understand currectly, in this lazy fold, this curried function 
isn't applied immediately, because 
-- by default the value of q is still a thunk
myfoldl f z [] = z
myfoldl f z (x:xs) = ( myfoldl f q  ) xs
  where q = z `f` x

-- here, because of the definition of seq, the curried function (myfoldl' 
f q) is applied immediately
-- because the value of q is known already, so (myfoldl' f q ) is WHNF
myfoldl' f z [] = z
myfoldl' f z (x:xs) = seq q ( myfoldl' f q ) xs
  where q = z `f` x

--same as myfoldl'
myfoldl'' f z [] = z
myfoldl'' f !z (x:xs) = ( myfoldl'' f q ) xs
  where q = z `f` x

myfoldl''' f z [] = z
myfoldl''' f z (x:xs) = (myfoldl''' f $! q) xs
  where q = z `f` x








PR Stanley [EMAIL PROTECTED] 
Sent by: [EMAIL PROTECTED]
11/14/2007 06:46 PM

To
haskell-cafe@haskell.org
cc

Subject
[Haskell-cafe] What is the role of $!?






Hi
What is the role of $! ?
As far as I can gather it's something to do with strict application. 
Could someone explain what it is meant by the term strict application 
please?
Thanks,
Paul

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



---

This e-mail may contain confidential and/or privileged information. If you 
are not the intended recipient (or have received this e-mail in error) 
please notify the sender immediately and destroy this e-mail. Any 
unauthorized copying, disclosure or distribution of the material in this 
e-mail is strictly forbidden.___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] IO is a bad example for Monads

2007-12-10 Thread Dan Piponi
On Dec 10, 2007 4:51 AM, Daniel Fischer [EMAIL PROTECTED] wrote:
 Am Montag, 10. Dezember 2007 10:36 schrieb Ketil Malde:
  Daniel Fischer [EMAIL PROTECTED] writes:
   Various other people write:
... lots of talk about monads and IO ...

When someone comes to me and says I have this Python script that
scans through these directories and finds the files that meet these
criteria and generates a report based on this template, could I do it
better in Haskell? it'd be good to have a better answer than to do
this you could use the IO monad, but to do things properly you need to
understand monads so here, learn about the List monad and the Maybe
monad first, understand how this interface abstracts from both, come
back when you've finished that, and then I'll tell you how to read and
write files. And I definitely want a better answer than Haskell I/O
is performed using the IO monad but everyone thinks this is bad so
just wait a few years and someone may write a fancy new nice
combinator library that does exactly what you want. There are
thousands of competing programming languages out there, and there are
dozens that are viable choices for the task I just mentioned. If my
response to their question takes longer than the time it would take to
find another language and implement a solution, then Haskell will
remain a niche language.

Maybe hardened Haskell programmers don't notice these things, but
there's a wall that goes up when Haskell is presented to
non-functional programmers. There are significant barriers for them to
cross (some of them imaginary): there's the infamous type system,
there's the mystique around monads, there's the fear that laziness can
impact performance, the general fear that many ordinary programmers
have about recursion, and so on. Giving people even the slightest
reason to think that there's something weird about opening files or
printing a result is just another brick in that wall, and it's
probably the biggest brick of all.
--
Dan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] IO is a bad example for Monads

2007-12-10 Thread Henning Thielemann

On Mon, 10 Dec 2007, Dan Piponi wrote:

 When someone comes to me and says I have this Python script that
 scans through these directories and finds the files that meet these
 criteria and generates a report based on this template, could I do it
 better in Haskell? it'd be good to have a better answer than to do
 this you could use the IO monad, but to do things properly you need to
 understand monads so here, learn about the List monad and the Maybe
 monad first, understand how this interface abstracts from both, come
 back when you've finished that, and then I'll tell you how to read and
 write files. And I definitely want a better answer than Haskell I/O
 is performed using the IO monad but everyone thinks this is bad so
 just wait a few years and someone may write a fancy new nice
 combinator library that does exactly what you want. There are
 thousands of competing programming languages out there, and there are
 dozens that are viable choices for the task I just mentioned. If my
 response to their question takes longer than the time it would take to
 find another language and implement a solution, then Haskell will
 remain a niche language.

I raise my question once again: Must Haskell's tutorials be tailored to
impatient programmers? Does Haskell need quickdirty hackers?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] IO is a bad example for Monads

2007-12-10 Thread Wolfgang Jeltsch
Am Montag, 10. Dezember 2007 19:44 schrieb Dan Piponi:
 […]

 Maybe hardened Haskell programmers don't notice these things, but
 there's a wall that goes up when Haskell is presented to
 non-functional programmers. There are significant barriers for them to
 cross (some of them imaginary):

That’s inavoidable if they want to learn a language which will finally be 
advantageous for them.  If they just want another Perl or Python then there 
is no point in presenting Haskell to them.

 there's the infamous type system,

You need them to get to recognize that a powerful static type system is a very 
good thing (which helps solving practical problems).

 there's the mystique around monads,

We should just say: “warm fuzzy thing”. ;-) 

 there's the fear that laziness can impact performance,

Hmm, tell them that performance isn’t all and that laziness helps you to write 
more modular programs.

 the general fear that many ordinary programmers have about recursion,

Then they might not be good programmers.

 and so on.

etc.

 Giving people even the slightest reason to think that there's something
 weird about opening files or printing a result is just another brick in that
 wall, and it's probably the biggest brick of all.

You’re right, of course.  However, finally they should arrive at the point 
where they see that sometimes there are better tools than the IO type.

 Dan

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


Re: [Haskell-cafe] IO is a bad example for Monads

2007-12-10 Thread Wolfgang Jeltsch
Am Montag, 10. Dezember 2007 20:00 schrieb Henning Thielemann:
 […]

 I raise my question once again: Must Haskell's tutorials be tailored to
 impatient programmers? Does Haskell need quickdirty hackers?

Who want Haskell to be plastered with syntactic sugar? ;-)  ;-) 

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


Re: [Haskell-cafe] IO is a bad example for Monads

2007-12-10 Thread Luke Palmer
On Dec 10, 2007 7:09 PM, Wolfgang Jeltsch [EMAIL PROTECTED] wrote:
  there's the fear that laziness can impact performance,

 Hmm, tell them that performance isn't all and that laziness helps you to write
 more modular programs.

Nah, in this case I've found it's better to realistically compare the
performance of
Haskell to Perl/Python, because it usually blows them out of the water, despite
laziness :-)

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


Re: [Haskell-cafe] Re: distinguish functions from non-functions in a class/instances

2007-12-10 Thread Dan Weston

Questioning apfelmus definitely gives me pause, but...

 id :: a - a-- arity 1
   id = ($) :: (a - b) - (a - b)  -- arity 2

I agree with the arities given above (but without quotes) and see no 
ill-definedness to arity.


But these are two different classes of functions. There are arguments of 
the first function that cannot be applied to the second (e.g. 5). The 
fact that the two have different type signatures shows that Haskell can 
distinguish them (e.g. in the instantiation of a type class).


The difficulties of Haskell's type system in the presence/intersection 
of ad hoc/parametric polymorphism is an orthogonal issue. I think that 
every function application must have a unique monomorphic type at the 
call site of the arity function (assisted or not by type annotation), 
and this type is known to converge in a Template Haskell construction.


 We have to specialize the type of  id before
 supplying it to  wrap . For example,

   wrap (id :: Int - Int)

 works just fine.

The necessity of type annotation/restriction is an orthogonal issue to 
the above.


Am I missing something more fundamental?

apfelmus wrote:

Luke Palmer wrote:


Hmm, this still seems ill-defined to me.

compose :: (Int - Int - Int) - (Int - Int) - Int - Int - Int

Is a valid expression given that definition (with a,b = Int and c = 
Int - Int),

but now the arity is 4.


That's correct, the arity of a function is not well-defined due to 
polymorphism. The simplest example is probably


id :: a - a-- arity 1
  id = ($) :: (a - b) - (a - b)  -- arity 2

Therefore, the polymorphic expression

  wrap id

is problematic. It roughly has the type

  wrap id  ~~  [String] - a

But it's clearly ambiguous: do we have

  wrap id (x:_)   = read x

or

  wrap id (f:x:_) = wrap ($) (f:x:_) = read f (read x)

or what? (assuming a read instance for function types)
GHCi gives it a type

   :type wrap id
  wrap id :: (FunWrap (a - a) y) = [String] - y

but trying to use it like in

   let x = wrap id [1] :: Int

yields lots of type errors. We have to specialize the type of  id before 
supplying it to  wrap . For example,


  wrap (id :: Int - Int)

works just fine.


I don't like this behavior of  wrap  since it violates the nice property 
of polymorphic expressions that it's unimportant when a type variable is 
instantiated, like in


   map ((+1) :: Int - Int) [1..5]
 = map (+1) ([1..5] :: [Int])
 = (map (+1) [1..5]) :: [Int]



Regards,
apfelmus

___
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


[Haskell-cafe] Software Tools in Haskell

2007-12-10 Thread Tommy McGuire

In the if anyone is interested,... department

For reasons that remain unclear, early this fall I started translating 
Brian W. Kernighan and P.J. Plaugher's classic _Software Tools in 
Pascal_ into Haskell.  I have completed most of it, up to the second 
part of chapter 8 which presents a proto-m4 preprocessor.  I have the 
code online including notes, comments, descriptions, and a few alternate 
approaches.


Attractions include:

* A fair gamut of the usual Unix suspects: proto-cat, proto-wc, 
proto-tr, proto-compress, proto-ar, proto-grep, etc.


* A usable editor, if you consider a de-featured ed-alike to be usable.

* A simple monadic regular expression engine.

* Zippers, Parsec, the State monad, the StateT monad transformer, and 
other attempts to sully Computing Science's brightest jewels.


* Lots and lots of really bad Haskell, including a fair bit that is a 
direct translation of 30-year old Pascal (see xindex in translit, Ch. 2, 
if you need to skip lunch).  Programming really has advanced, you know.


Anyway, the URL is:
  http://www.crsr.net/Programming_Languages/SoftwareTools

Questions and comments would be appreciated, especially suggestions for 
how to make the code cleaner and more understandable.  Flames and 
mockery are welcome, too, but only if they're funny---remember, I've 
been staring at Haskell, Pascal (plus my job-related Perl, CORBA, and 
C++) for a while; there's no telling what my mental state is like.


[I had intended to wait until I had the whole thing done to make this 
announcement, but I recently moved and have not made much forward 
progress since, other than putting what I had done online.]




--
Tommy M. McGuire
[EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] announcing darcs 2.0.0pre1, the first prerelease for darcs 2

2007-12-10 Thread David Roundy
We are happy to announce the first prerelease version of darcs 2! Darcs 2
will feature numerous improvements, and this prerelease will also feature a
few regressions, so we're looking for help, from both Haskell developers
and users willing to try this release out.  Read below, to see how you can
benefit from this new release, and how you can help us to make the final
darcs 2 release the best ever! (for the latter, see
http://wiki.darcs.net/index.html/DarcsTwo/HowToHelp)

(for an expanded version of this announcement, see
http://wiki.darcs.net/index.html/DarcsTwo)

Darcs 2 features user-visible changes two broad categories, and several
under-the-hood improvements designed to improve code stability and safety.
The user-visible changes are a new hashed repository format, and the new
darcs-2 conflict handling.  The new hashed repository format can be used
in a manner that is interchangeable with older darcs--although older
versions of darcs cannot read the hashed format, darcs 2 can allows you to
exchange patches between repositories in new and old formats.  The new
conflict handling benefits from the new hashed format, but also requires a
repository conversion that is not backwards-compatible, so projects
switching to darcs-2 format will have require that all their users upgrade
to darcs 2.

=== Getting darcs 2 ===
You can get a prerelease version of darcs 2 either by getting the latest
unstable darcs

darcs get http://darcs.net/repos/unstable

or by downloading the prerelease tarball from
http://darcs.net/darcs-2.0.0pre1.tar.gz.  Once you've compiled your new
darcs, you could take it for a test drive by getting a fresh copy of darcs
with the hashed repository format:

darcs get http://darcs.net/repos/unstabled-hashed

= Hashed repository format =

We expect that most testers of darcs 2 will only try the hashed repository
format.  While we'd prefer to also have many users testing out actual
darcs-2 format repositories, the two codebases have much in common, so
tests of the hashed format will greatly help us in improving darcs 2 as a
whole. 

The hashed repository format has a number of changes that are visible to
users.

 1. The hashed format allows for greater atomicity of operations.  This
 makes for greater safety and simultaneously greater efficiency.  These
 benefits, however, have not been fully realized in this release.  For
 instance, with a hashed repository, there is no need for darcs push to
 require a repository lock, so you could record patches while waiting for a
 push to finish (for instance, if it's waiting on the test suite).

 2. The _darcs/pristine directory no longer holds the pristine cache.  This
 disallows certain hackish short-cuts, but also dramatically reduces the
 danger of third-party programs (e.g. DreamWeaver) recursing into the
 pristine cache and corrupting darcs repositories.

 3. Darcs get is now much faster, and always operates in a lazy fashion,
 meaning that patches are downloaded only when they are needed.  This gives
 us much of the benefits of --partial repositories, without most of their
 disadvantages.  This approach, however, does have several new dangers.
 First, some operations may unexpectedly require the download of large
 numbers of patches, which could be slow (but you could always interrupt
 with ^C).  Secondly, if the source repository disappears, or you lose
 network connectivity, some operations may fail.  I do not believe these
 dangers will prove particularly problematic, but we may need to fine-tune
 the user interface to make it more clear what is going on.

 4. Darcs now supports caching of patches and file contents to reduce
 bandwidth and save disk space.  See below for how to enable this.  In my
 opinion, this is actually the most exciting new feature, as it greatly
 speeds up a number of operations, and is essentially transparent.  The
 only reason we don't enable it by default is because I'm uncomfortable
 creating a large directory in ~/.darcs/cache without the user's explicit
 consent.

=== Creating a repository in the hashed format ===

Creating a hashed repository is as easy as

darcs get --hashed oldrepository newrepository

or alternatively you could create a fresh repository with

darcs initialize --hashed

You can push, pull and send patches at will between hashed and
old-fashioned repositories, so you should be able to experiment with this
format even on projects that you do not control.

=== Enabling a global cache ===

It is very simple to enable a global cache.  Simply execute

$ mkdir -p $HOME/.darcs/cache
$ echo cache:$HOME/.darcs/cache  $HOME/.darcs/sources

This will cause darcs to store hard links in ~/.darcs/cache.  It is always
safe to delete this directory.

= Darcs-2 merging =

The future of darcs is in the darcs-2 repository format, which features a
new merge algorithm that introduces two major user-visible changes

 1. It should no longer be possible to confuse darcs or freeze it
 indefinitely by merging conflicting 

Re: [Haskell-cafe] IO is a bad example for Monads

2007-12-10 Thread Dan Piponi
On Dec 10, 2007 11:00 AM, Henning Thielemann
[EMAIL PROTECTED] wrote:

 Does Haskell need quickdirty hackers?

The question isn't Does Haskell need quickdirty hackers? It's
would we get better software (using your favourite metric) if we put
Haskell into the hands of quick and dirty hackers?. I think the
answer might be yes.

Note also that there are many classes of people who fit the quick and
dirty category. There are people who have busy full time jobs and who
might benefit greatly from Haskell if they could get started
relatively quickly. There are people whose primary job is not
programming but who still need to program (eg. to script their
applications). And of course there are people who who are just quick
and dirty hackers by nature.
--
Dan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re[2]: [Haskell-cafe] IO is a bad example for Monads

2007-12-10 Thread Bulat Ziganshin
Hello Dan,

Monday, December 10, 2007, 9:44:06 PM, you wrote:

 When someone comes to me and says I have this Python script that

just my cent or two for this discussion: sometime ago I've started an
introduction to IO tutorial. it's both not in English and not finished
so i'll just explain its idea: Haskell has strict distinction between
procedures that may perform side-effects and pure functions;
functions can't call procedures. there is special notion for
procedures, with do/return/... and further explanation shows various
details of building procedures. i think that such description closely
mirrors thinking of imperative-language programmers and allows to
overcome monad barrier in teaching real-world haskell

of course, this meant only as introductory course and at some moment
haskeller should read all about monads and io inside, but i
consider this as intermediate-level or even advanced material

btw, explanation in terms of functions vs procedures isn't my own,
unfortunately i don't remember its origins, but i find it very helpful
and understandable for average imperative programmers

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] IO is a bad example for Monads

2007-12-10 Thread Ketil Malde
Dan Piponi [EMAIL PROTECTED] writes:

 The question isn't Does Haskell need quickdirty hackers? It's
 would we get better software (using your favourite metric) if we put
 Haskell into the hands of quick and dirty hackers?. I think the
 answer might be yes.

This is an interesting trade-off:  if we suppose that the most
enterprising and creative (i.e. talented) [language] hackers are most
susceptible to be lured over to Haskell, this strategy will increase
the average quality of software overall, while simultaneously
decreasing the average quality of code in both languages!

 Note also that there are many classes of people who fit the quick and
 dirty category.

Encourage them to learn Haskell and only be quick.

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] IO is a bad example for Monads

2007-12-10 Thread Lennart Augustsson
If Haskell wants yo significantly widen it's audience then the tutorials
have to cater for the impatient.
Perhaps it's better to remain a fringe language.  I truly don't know.

  -- Lennart


On Dec 10, 2007 7:00 PM, Henning Thielemann [EMAIL PROTECTED]
wrote:


 On Mon, 10 Dec 2007, Dan Piponi wrote:

  When someone comes to me and says I have this Python script that
  scans through these directories and finds the files that meet these
  criteria and generates a report based on this template, could I do it
  better in Haskell? it'd be good to have a better answer than to do
  this you could use the IO monad, but to do things properly you need to
  understand monads so here, learn about the List monad and the Maybe
  monad first, understand how this interface abstracts from both, come
  back when you've finished that, and then I'll tell you how to read and
  write files. And I definitely want a better answer than Haskell I/O
  is performed using the IO monad but everyone thinks this is bad so
  just wait a few years and someone may write a fancy new nice
  combinator library that does exactly what you want. There are
  thousands of competing programming languages out there, and there are
  dozens that are viable choices for the task I just mentioned. If my
  response to their question takes longer than the time it would take to
  find another language and implement a solution, then Haskell will
  remain a niche language.

 I raise my question once again: Must Haskell's tutorials be tailored to
 impatient programmers? Does Haskell need quickdirty hackers?
 ___
 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] IO is a bad example for Monads

2007-12-10 Thread Paul Moore
On 10/12/2007, Henning Thielemann [EMAIL PROTECTED] wrote:

 On Mon, 10 Dec 2007, Dan Piponi wrote:

  When someone comes to me and says I have this Python script that
  scans through these directories and finds the files that meet these
  criteria and generates a report based on this template, could I do it
  better in Haskell? it'd be good to have a better answer than to do
  this you could use the IO monad, but to do things properly you need to
  understand monads so here, learn about the List monad and the Maybe
  monad first, understand how this interface abstracts from both, come
  back when you've finished that, and then I'll tell you how to read and
  write files. And I definitely want a better answer than Haskell I/O
  is performed using the IO monad but everyone thinks this is bad so
  just wait a few years and someone may write a fancy new nice
  combinator library that does exactly what you want. There are
  thousands of competing programming languages out there, and there are
  dozens that are viable choices for the task I just mentioned. If my
  response to their question takes longer than the time it would take to
  find another language and implement a solution, then Haskell will
  remain a niche language.

 I raise my question once again: Must Haskell's tutorials be tailored to
 impatient programmers? Does Haskell need quickdirty hackers?

Sigh. I've seen this type of comment on this list so many times, and I
still feel insulted by it. Must the Haskell community (and yes, I know
it's not everyone, it's quite probably only a few members, but it
feels like a lot) treat anyone who just wants to get a job done, while
being open minded enough to consider a new and very unconventional
language, as being impatient and a quick and dirty hacker?

I'm sorry. I left it quite a while before I responded, so that my
initial annoyed feeling could subside, but it didn't. I've hit all of
Dan's barriers (apart from fear of recursion :-)) and yet I would not
characterise myself as you describe (OK, maybe somewhat impatient
:-)). Also, I have a fair bit of experience with non-imperative styles
- I have, over the years, learnt a number of languages including Lisp,
Prolog, Scheme and many others with functional or non-imperative
aspects (I even recall looking a little at Hope and Miranda a long
while ago).

Haskell is the most practical functional language I have encountered,
but I still feel that IO (in the most general sense of interaction
with the outside world) is hard in Haskell[1]. Maybe it *can* be easy,
but it isn't yet. And ignoring that fact isn't helping anyone.

Paul.

[1] Certainly you can toss out examples of easy IO in Haskell. Things
like interact help a lot. But ultimately, you hit something hard -
maybe it's handling errors robustly while using IO, or interacting
with a database rather than a screen, or whatever. But at some point,
you run out of clean off-the-shelf encapsulations, and get to
genuinely hard stuff - and that happens in a huge step change, rather
than a gradual increase of complexity that you can take as slowly as
you need to.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] IO is a bad example for Monads

2007-12-10 Thread jerzy . karczmarczuk
Paul Moore after Henning Thielemann after Dan Piponi: 




 There are
 thousands of competing programming languages out there, and there are
 dozens that are viable choices for the task I just mentioned. If my
 response to their question takes longer than the time it would take to
 find another language and implement a solution, then Haskell will
 remain a niche language. 


I raise my question once again: Must Haskell's tutorials be tailored to
impatient programmers? Does Haskell need quickdirty hackers?


Sigh. I've seen this type of comment on this list so many times, and I
still feel insulted by it. Must the Haskell community (and yes, I know
it's not everyone, it's quite probably only a few members, but it
feels like a lot) treat anyone who just wants to get a job done, while
being open minded enough to consider a new and very unconventional
language, as being impatient and a quick and dirty hacker?

...

I still feel that IO (in the most general sense of interaction
with the outside world) is hard in Haskell[1]. Maybe it *can* be easy,
but it isn't yet. And ignoring that fact isn't helping anyone.


I think that 


1. Nobody ignores that.
2. Nobody really tries to insult people who want to find fast, elegant and
 efficient solutions to their problems.
3. People often *are* impatient, and this is not an insult.
4. Some comments from the other side, addressed to Haskellers can
 sometimes also be qualified as almost insulting (if somebody wishes to
 adopt such personal attitude). 


Paul Moore has seen this type of comment many times. I have seen his
reaction, and the whole of this discussion at least as many times. Will it
help us, all of us?... 


Look, all of you. There was time, where the theory of Einstein was
considered as something so high-brow, that a few guys in this world would
understand it. Now it is a standard undergraduate topic. Some *formal*
elements of the Special Relativity may be taught in High School. Some
*qualitative* elements of the General Relativity, as well. 


Do you imagine the concrete application - for the impatient - of the
differential calculus, at the time of Newton and Leibniz? And now? 


EVERYTHING here is a problem of education. It is different now than 300
years ago, and even than 60 years ago. Everything is much faster. But our
physiology, the speed of assimilation did not progress much. We REALLY need
time to assimilate new things. So, they should start earlier. 


The basic recursion schemata should be taught to 13-15 years old people.
The teaching of algebra may, and often is much more abstract than 30 years
ago, but still there is a reluctance of teachers to illustrate math through
programming, at a sufficiently abstract level. 


I really think that such languages as Haskell are investing for the future.
My main grief is completely different from these expressed by people who
want to sell Haskell for the Humanity rrright now. 


I think seriously that one of the weakest points of Haskell is that it is
*alone*. That there is no competition.
Clean stagnates a bit, the Clean mailing list is at least 40 times less
popular than this one. Pity, it is, or could be a worthy opponent,
concerning IO, the relation between types and strictness, etc. 


Some work on functional approach to scientific programming goes along the
lines far, far from Haskell, inspired rather by SISAL, etc. (for example the
SAC system). 


So my sincere recommendation for people unhappy with the monadic IO is:
propose something alternative, and implement it. If you are unhappy with
the language, tell us what you concretely want, but don't try to say
that you don't like our submarine, because you want to ride on it to the
top of Mount Everest. 

Jerzy Karczmarczuk 



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


Re: [Haskell-cafe] [OT] A nice organized collection of threads in Haskell-Cafe

2007-12-10 Thread Albert Y. C. Lai

Vimal wrote:

What is the difference between In-Reply-To and References?


There was a time In-Reply-To was for emails and References was for Usenet.

Nowadays emails have both In-Reply-To and References. Usenet still 
sticks with just References.

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


Re: role of seq, $!, and bangpatterns illuminated with lazy versus strict folds Re: [Haskell-cafe] What is the role of $!?

2007-12-10 Thread Albert Y. C. Lai

Thomas Hartman wrote:

-- (myfoldl f q ) is a curried function that takes a list
-- If I understand currectly, in this lazy fold, this curried function 
isn't applied immediately, because

-- by default the value of q is still a thunk
myfoldl f z [] = z
myfoldl f z (x:xs) = ( myfoldl f q  ) xs
  where q = z `f` x


Sorry to say this curried function isn't applied immediately is wrong. 
The curried function is applied immediately. This is independent of what 
happens to q. q remains a thunk. myfoldl f q xs moves on immediately. 
Next iteration's z is this iteration's q, and remains a thunk too.


It is also noteworthy that

  a b c d
= (a b c) d
= ((a b) c) d

They are syntactic sugar of each other.

-- here, because of the definition of seq, the curried function 
(myfoldl' f q) is applied immediately

-- because the value of q is known already, so (myfoldl' f q ) is WHNF
myfoldl' f z [] = z
myfoldl' f z (x:xs) = seq q ( myfoldl' f q ) xs
  where q = z `f` x


The seq causes q to become WHNF. This is independent of what happens to 
(myfoldl' f q).


In general in many compilers seq x y digresses to reduce x to WHNF, then 
we now return you to the scheduled programming of whatever should 
happen to y.



--same as myfoldl'
myfoldl'' f z [] = z
myfoldl'' f !z (x:xs) = ( myfoldl'' f q ) xs
  where q = z `f` x


This is not the same as myfoldl'. This does not reduce q to WHNF - not 
now. Instead, z is reduced to WHNF now. As for q, this iteration's q 
becomes the next iteration's z, so this iteration's q will become WHNF 
next iteration.


It is unusual to observe any difference because usually one experiments 
with number crunching only, where no one cares whether evaluation is one 
iteration early or late. However, this operator will show the difference.


mydisj _ True = True
mydisj True False = True
mydisj False False = False

myfoldl' mydisj (error bottom) [True]  -- True
myfoldl'' mydisj (error bottom) [True] -- exception: bottom


myfoldl''' f z [] = z
myfoldl''' f z (x:xs) = (myfoldl''' f $! q) xs
  where q = z `f` x


This is the same as myfold'.

myfold' and myfold''' are the same as what's on the wiki.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] IO is a bad example for Monads

2007-12-10 Thread Claus Reinke

Maybe hardened Haskell programmers don't notice these things, but
there's a wall that goes up when Haskell is presented to
non-functional programmers. There are significant barriers for them to
cross (some of them imaginary): there's the infamous type system,
there's the mystique around monads, there's the fear that laziness can
impact performance, the general fear that many ordinary programmers
have about recursion, and so on. Giving people even the slightest
reason to think that there's something weird about opening files or
printing a result is just another brick in that wall, and it's
probably the biggest brick of all.


this discussion could fall off the cliff at both ends. as far as i can tell,
the problem is that with the haskell community so big, subcommunities
only have different needs, different tools, different ways of thinking.
and even if some of the subcommunities live and work at the cutting
edge and expect everyone to follow, that won't necessarily happen
anytime soon.

one one side are the rocket engineers who feel genuinely displeased 
if people keep trying to sell horseless carriages as the best form of 
transport. and they are right, in a way: not only is this view rather 
limiting, but it keeps people form seeing not only that rockets exist, 
but that there are places where horseless carriages cannot take us,
that we have actually been to the moon using rockets, a very long 
time ago, and that there are other places, and other technologies
that might take us there. these people see past technology 
promoted everywhere at the expense of support for and interest 
in their own or similar advanced work.


on the other side are the people who need to get from A to B, and
are used to the tools of the horsecarriage industry. they feel
genuinely unsure about those horseless carriage things, and they
tend to lose it completely if all the manuals and sales brochures
talk about different types of automobiles, with not a word being
said about horses and carriages. that talk about rocket engines
goes right over their head, but that doesn't worry them as they 
don't expect to have to get to the moon anytime soon.


of course, there is that question of satellites, which turn out to
be awfully useful even if you don't otherwise want to leave the
earth, and which are a real pain to put in place with carriages,
horseless or otherwise.

claus


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


Re: [Haskell-cafe] What is the role of $!?

2007-12-10 Thread Dean Herington

Thanks, Tom, for a nice description of lazy evaluation.

Besides the minor things Derek pointed out, there's one more subtle 
but important thing to correct:


At 7:29 AM + 11/29/07, Thomas Davie wrote:


$! is the special case, which means strictly apply.  It evaluates 
its argument first, *then* does the application.  This may or may 
not be faster (and usually isn't, due to evaluating more of the 
argument):


f ($!) x = seq x (f x)

seq is a special function that says first fully evaluate my first 
argument, then return my second argument, it breaks non-strict 
semantics.


seq doesn't fully evaluate its first argument, rather only to what's 
called weak head normal form.  Roughly, that means only enough to 
establish the top-level constructor (e.g., to distinguish [] from 
(_:_)).


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


Re: [Haskell-cafe] [OT] A nice organized collection of threads in Haskell-Cafe

2007-12-10 Thread Vimal
Hi,
Thanks for the info.

 Vimal wrote:
  What is the difference between In-Reply-To and References?

 There was a time In-Reply-To was for emails and References was for Usenet.

My friend wrote a parser for Haskell-cafe messages from the mailman
archives as suggested.

He told that there were a lot of messages that he had to reject
because they didnt have a valid In-Reply-To header. i.e., the
In-Reply-To header referred to some message that wasnt in the list of
messages!

Perhaps it was from another month's message!

Thanks,
Vimal
On 11/12/2007, Albert Y. C. Lai [EMAIL PROTECTED] wrote:
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] IO is a bad example for Monads

2007-12-10 Thread David Menendez
On Dec 10, 2007 1:44 PM, Dan Piponi [EMAIL PROTECTED] wrote:

 When someone comes to me and says I have this Python script that
 scans through these directories and finds the files that meet these
 criteria and generates a report based on this template, could I do it
 better in Haskell? it'd be good to have a better answer than to do
 this you could use the IO monad, but to do things properly you need to
 understand monads so here, learn about the List monad and the Maybe
 monad first, understand how this interface abstracts from both, come
 back when you've finished that, and then I'll tell you how to read and
 write files.


I thought your blog post about the IO monad for people who don't care about
monads (yet) was a pretty good start.

As it happens, the IO monad was one of the things that attracted me to
Haskell. When I was learning SML in college, I wondered how one could do I/O
in a functional style. SML provides I/O via functions with side-effects,
which struck me as crude and contrary to the functional style.

Years later, I encountered Haskell and learned that it handled I/O tasks
using something called the IO monad. I had no idea what a monad was, but I
understood the implications: Haskell could be referentially transparent
*and* do I/O. This was what inspired me to learn the language.

As I learned more Haskell, I discovered the other monads and the Monad class
and the full generality of the do notation. Eventually, a light came on
and monads suddenly made sense.

I don't know if it's best to learn the IO monad before or after other
monads. I suspect no choice is right for everyone. An experienced programmer
who is new to Haskell is going to have different questions than a beginning
programmer with no preconceived notions.

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


[Haskell-cafe] Re: group-by (Was: Nested guards?)

2007-12-10 Thread Anthony Clayden
Henning Thielemann lemming at henning-thielemann.de writes:

 
 
 On Fri, 7 Dec 2007, Simon Peyton-Jones wrote:
 
  | And I think that the solution is not to make the language larger and 
larger
  | everytime someone wants a feature but to give people the tools to provide
  | features without language changes.
 
  Of course that would be even better!  (Provided of course the resulting
  programs were comprehensible.)  Haskell is already pretty good in this
  respect, thanks to type classes, higher order functions, and laziness;
  that's why it's so good at embedded domain-specific languages.
 
 When I learned about GROUP BY and HAVING in SQL with its rules about what
 is allowed in GROUP BY and SELECT I considered GROUP BY a terrible hack,
 that was just introduced because the SQL people didn't want to allow types
 different from TABLE, namely lists of tables. I try to convince my data
 base colleagues that GROUP BY can nicely be handled in relational algebra
 by allowing sets of sets and that this is a fine combinatorial approach. I
 [snip]

I agree with Henning that HAVING is a 'terrible hack', but then SQL altogether 
is a terrible hack. I would expect the Haskell approach to be based on the 
much sounder theoretical principles of Relational Algebra, and I applaud that 
Wadler+SPJ's 'Comprehensive Comprehensions' restricts itself to a subset of 
SQL that corresponds to Relational Algebra. In that context, GROUP BY is 
reasonably well-defined as a mapping from a table to a table. (The hack in SQL 
vintage 1975 is in trying to squeeze GROUP BY into the structure of SELECT ... 
FROM ... WHERE ..., the mess now can be blamed on trying to preserve backwards 
compatability.)

As that paper points out, HAVING is unnecessary - it's just a filter on the 
result set of group-by. And relational theorists agree that HAVING is 
unneccessary (see for example 'The Importance of Column Names', Hugh Darwen 
2003 from www.thethirdmanifesto.com).

It's crucial that in Relational Algebra everything is a table. (See Codd's 12 
rules). The result of GROUP BY we might want to pass to another GROUP BY, or 
JOIN to another table, etc -- or does Henning propose a hierarchy of sets of 
sets ... of tables, presumably with a hierarchy of HAVINGHAVING's?




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


Re: [Haskell-cafe] Re: distinguish functions from non-functions in a class/instances

2007-12-10 Thread Jonathan Cast

On 10 Dec 2007, at 11:33 AM, Dan Weston wrote:


Questioning apfelmus definitely gives me pause, but...

 id :: a - a-- arity 1
   id = ($) :: (a - b) - (a - b)  -- arity 2

I agree with the arities given above (but without quotes) and see  
no ill-definedness to arity.


But these are two different classes of functions. There are  
arguments of the first function that cannot be applied to the  
second (e.g. 5). The fact that the two have different type  
signatures shows that Haskell can distinguish them (e.g. in the  
instantiation of a type class)


Not really.  The types of id and ($) can't be instances of a type  
class, since an instance of a type class has to be a monomorphic  
type.  So the decision as to which instance to use has to be made  
based on the particular monomorphic type id or ($) is used at.  But  
that monomorphic type may still contain free type variables; those  
type variables themselves represent some single monomorphic type,  
which may or may not be a function type.  So we still don't know what  
the arity of an arbitrary expression is.  (We don't know what its  
type is, even the way we know the type of id or ($), if it or any of  
its free variables is lambda-bound).


The difficulties of Haskell's type system in the presence/ 
intersection of ad hoc/parametric polymorphism is an orthogonal  
issue. I think that every function application must have a unique  
monomorphic type at the call site of the arity function (assisted  
or not by type annotation), and this type is known to converge in a  
Template Haskell construction.


 We have to specialize the type of  id before
 supplying it to  wrap . For example,

   wrap (id :: Int - Int)

 works just fine.

The necessity of type annotation/restriction is an orthogonal issue  
to the above.


Am I missing something more fundamental?

apfelmus wrote:

Luke Palmer wrote:


Hmm, this still seems ill-defined to me.

compose :: (Int - Int - Int) - (Int - Int) - Int - Int - Int

Is a valid expression given that definition (with a,b = Int and c  
= Int - Int),

but now the arity is 4.
That's correct, the arity of a function is not well-defined due to  
polymorphism. The simplest example is probably

id :: a - a-- arity 1
  id = ($) :: (a - b) - (a - b)  -- arity 2
Therefore, the polymorphic expression
  wrap id
is problematic. It roughly has the type
  wrap id  ~~  [String] - a
But it's clearly ambiguous: do we have
  wrap id (x:_)   = read x
or
  wrap id (f:x:_) = wrap ($) (f:x:_) = read f (read x)
or what? (assuming a read instance for function types)
GHCi gives it a type
   :type wrap id
  wrap id :: (FunWrap (a - a) y) = [String] - y
but trying to use it like in
   let x = wrap id [1] :: Int
yields lots of type errors. We have to specialize the type of  id  
before supplying it to  wrap . For example,

  wrap (id :: Int - Int)
works just fine.
I don't like this behavior of  wrap  since it violates the nice  
property of polymorphic expressions that it's unimportant when a  
type variable is instantiated, like in

   map ((+1) :: Int - Int) [1..5]
 = map (+1) ([1..5] :: [Int])
 = (map (+1) [1..5]) :: [Int]
Regards,
apfelmus
___
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


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


Re: [Haskell-cafe] IO is a bad example for Monads

2007-12-10 Thread Michael Vanier
I haven't been following this thread closely, but would it be rude to suggest that someone who 
doesn't want to put the effort into learning the (admittedly difficult) concepts that Haskell 
embodies shouldn't be using the language?  Haskell was never intended to be The Next Big Popular 
Language.  It was intended to be a purely functional language for people who want to use purely 
functional languages and who are willing to learn new concepts if it enables them to program in that 
 style.  That now includes IO and monads, so if people aren't willing to learn that, they should go 
on using python or whatever.  That said, of course we should strive to have better teaching 
materials, but there are a number of good IO/monad tutorials on the web.


I used to love programming in python, but then I learned Scheme, then Ocaml, and then Haskell and at 
each stage I absorbed a few new concepts.  Now programming in python feels very primitive to me. 
Haskell is interesting because it enables us to write programs more effectively (in many cases, at 
least) than we can in other languages, but the learning curve is steep -- there ain't no such thing 
as a free lunch.


Mike

David Menendez wrote:
On Dec 10, 2007 1:44 PM, Dan Piponi [EMAIL PROTECTED] 
mailto:[EMAIL PROTECTED] wrote:


When someone comes to me and says I have this Python script that
scans through these directories and finds the files that meet these
criteria and generates a report based on this template, could I do it
better in Haskell? it'd be good to have a better answer than to do
this you could use the IO monad, but to do things properly you need to
understand monads so here, learn about the List monad and the Maybe
monad first, understand how this interface abstracts from both, come
back when you've finished that, and then I'll tell you how to read and
write files. 



I thought your blog post about the IO monad for people who don't care 
about monads (yet) was a pretty good start.


As it happens, the IO monad was one of the things that attracted me to 
Haskell. When I was learning SML in college, I wondered how one could do 
I/O in a functional style. SML provides I/O via functions with 
side-effects, which struck me as crude and contrary to the functional 
style.


Years later, I encountered Haskell and learned that it handled I/O tasks 
using something called the IO monad. I had no idea what a monad was, 
but I understood the implications: Haskell could be referentially 
transparent *and* do I/O. This was what inspired me to learn the language.


As I learned more Haskell, I discovered the other monads and the Monad 
class and the full generality of the do notation. Eventually, a light 
came on and monads suddenly made sense.


I don't know if it's best to learn the IO monad before or after other 
monads. I suspect no choice is right for everyone. An experienced 
programmer who is new to Haskell is going to have different questions 
than a beginning programmer with no preconceived notions.


--
Dave Menendez [EMAIL PROTECTED] mailto:[EMAIL PROTECTED]
http://www.eyrie.org/~zednenem/ http://www.eyrie.org/~zednenem/




___
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] Re: group-by (Was: Nested guards?)

2007-12-10 Thread Henning Thielemann

On Tue, 11 Dec 2007, Anthony Clayden wrote:

 I agree with Henning that HAVING is a 'terrible hack', but then SQL
 altogether is a terrible hack.

Somehow, yes.

 As that paper points out, HAVING is unnecessary - it's just a filter on
 the result set of group-by.

Yep.

 It's crucial that in Relational Algebra everything is a table. (See Codd's 12
 rules). The result of GROUP BY we might want to pass to another GROUP BY, or
 JOIN to another table, etc -- or does Henning propose a hierarchy of sets of
 sets ...

Yes, why not? Works fine in Haskell. Ok, Haskell programs do not construct
different query processing strategies and compare them at run-time, so the
comparison between Haskell compilers and databases is not quite fair.

 of tables, presumably with a hierarchy of HAVINGHAVING's?

map (map (map (filter p)))   and so on :-)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] IO is a bad example for Monads

2007-12-10 Thread Donn Cave


On Dec 10, 2007, at 12:40 PM, Dan Piponi wrote:


On Dec 10, 2007 11:00 AM, Henning Thielemann
[EMAIL PROTECTED] wrote:


Does Haskell need quickdirty hackers?


The question isn't Does Haskell need quickdirty hackers? It's
would we get better software (using your favourite metric) if we put
Haskell into the hands of quick and dirty hackers?. I think the
answer might be yes.


You are so right - at least, to the extent that Haskell has any  
potential
to exert a positive influence on anyone in that category.  A lot of  
these

wretched hackers are people who cared more about some end than
the means to it, and have accordingly accomplished things that are
now important ... and need to be maintained.  To the despair of all
concerned.

I think you'll get a better Haskell, too.  Don't let it turn into some
weird Gnostic cult where pneumatics liberate themselves from the
tainted bonds of earth by feasting on air and sunlight only.

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


Re: [Haskell-cafe] IO is a bad example for Monads

2007-12-10 Thread Henning Thielemann

On Mon, 10 Dec 2007, Paul Moore wrote:

 On 10/12/2007, Henning Thielemann [EMAIL PROTECTED] wrote:
 
  I raise my question once again: Must Haskell's tutorials be tailored to
  impatient programmers? Does Haskell need quickdirty hackers?

 Haskell is the most practical functional language I have encountered,
 but I still feel that IO (in the most general sense of interaction
 with the outside world) is hard in Haskell[1]. Maybe it *can* be easy,
 but it isn't yet. And ignoring that fact isn't helping anyone.

 I myself didn't start with IO in Haskell, because I could do this in
imperative languages. I didn't learnt Haskell in order to be able to
implement something, that I couldn't program before. I used Haskell for
implementing things more cleaner, more elegant than before.  Things that I
couldn't implement more elegant in Haskell, I didn't implement in Haskell.
I started in Haskell with what is especially easy to do in Haskell, for me
this was solving mathematical problems. GHCi was the way I interacted with
Haskell. I didn't do IO for more than half a year. My first programs with
IO only contained writing data to files, then reading from files. No
interaction with the user or argument parsing. Due to Hal Daume's tutorial
I found the State monad useful early. Later I did IO, Reader, List monad
and then monad transformers. In retrospective, the List monad should have
been earlier on my plan because it is the right tool for solving problems
by systematic search.
 I think that getting a job done (maybe even with time constraint) is not
a good way to really learn a language. You will try to solve the problems
in the way you solved them in other languages, because that is the way you
are used to, and this promises to be the fastest one.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] [OT] A nice organized collection of threads in Haskell-Cafe

2007-12-10 Thread Ketil Malde
Vimal [EMAIL PROTECTED] writes:

 Vimal wrote:
  What is the difference between In-Reply-To and References?

 There was a time In-Reply-To was for emails and References was for Usenet.

 My friend wrote a parser for Haskell-cafe messages from the mailman
 archives as suggested.

One place to look for example threading code is in the Gnus news/mail
client for Emacs.  Works fairly well, and is (was, when I looked at it
briefly ages ago) not too complicated, and in elisp, which is not
quite entirely an unfunctional language.

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe