Re: [Haskell-cafe] [ANN] Haskell Cheatsheet v1.0

2008-10-11 Thread Adrian Neumann
Thank you for your work! I just glanced over it but I'll suggest it  
to be linked to from the homepage of my university's functional  
programming course.
However, thirteen pages can hardly be called cheatsheet. It's more  
like a quick reference.


You could add [100,99..] infinite liste of numbers from 100  
downwards to you numbers section, as it is an example where the  
range does go backward.


Adrian

Am 11.10.2008 um 01:08 schrieb Justin Bailey:


All,

I've created a cheat sheet for Haskell. It's a PDF that tries to
summarize Haskell 98's syntax, keywords and other language elements.
It's currently available on hackage[1]. Once downloaded, unpack the
archive and you'll see the PDF. A literate source file is also
included.

If you install with cabal install cheatsheet, run cheatsheet
afterwards and the program will tell you where the PDF is located.

The audience for this document is beginning to intermediate Haskell
programmers. I found it difficult to look up some of the less-used
syntax and other language stumbling blocks as I learned Haskell over
the last few years, so I hope this document can help others in the
future.

This is a beta release (which is why I've limited the audience by
using hackage) to get feedback before distributing the PDF to a wider
audience. With that in mind, I welcome your comments or patches[2].

Justin

[1] http://hackage.haskell.org/cgi-bin/hackage-scripts/package/ 
CheatSheet

[2] git://github.com/m4dc4p/cheatsheet.git
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe




PGP.sig
Description: Signierter Teil der Nachricht
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] How to translate Haskell to other languages?

2008-10-11 Thread Jason Dagit
Hello,

I was thinking about translating Haskell to other languages, python being
the main one at the moment.

Here is my attempt at manually encoding Haskell in Python:
\begin{code}
import types

class thunk:
'''Thunks allow us to delay a computation and they also store their
   value inside themselves once they have been accessed.'''

def __init__(self, v):
self.v = v

def value(self):
'''Force the thunk to be calculated by referencing it.'''
while self.isReducible():
self.reduce()
return self.v

def reduce(self):
'''Reduces the thunk, by either calling the represented function
   or reducing the layers of thunk.'''
if (type(self.v) == types.FunctionType):
self.v = self.v()
else:
self.v = self.v.value()
return self.v

def isReducible(self):
'''Returns True when the thunk is still callable.'''
return isinstance(self.v, thunk) or \
   type(self.v) == types.FunctionType

class nil:
'''Empty list element'''
def __init__(self):
pass

class cons:
'''Non-empty lists'''
def __init__(self, head, tail):
self.head = head
self.tail = tail
'''Unpack the cons cell'''
def uncons(self):
return self.head, self.tail

def htail(t):
'''This function works like Haskell's tail function.'''
l = t.value()
x, xs = l.uncons()
return xs

def plus(t1, t2):
'''Adds numbers'''
i1 = t1.value()
i2 = t2.value()
return thunk(i1+i2)

def zipWith(f, t1, t2):
'''This is like Haskell's zipWith function.'''
l1 = t1.value()
if isinstance(l1, nil): return thunk(nil())
l2 = t2.value()
if isinstance(l2, nil): return thunk(nil())
x, xs = l1.uncons()
y, ys = l2.uncons()
zw = thunk(lambda: zipWith(f, xs, ys))
fxy = thunk(lambda: f(x,y))
return thunk(cons(fxy, zw))

def fibs():
'''This is the classic fibs:
fibs = 1 : 1 : zipWith (+) fibs (tail fibs)'''
f1 = thunk(1)
f2 = thunk(1)
fn = thunk(fibs)
rest = thunk(lambda: zipWith(plus, fn, htail(fn)))
restlist = thunk(cons(f2, rest))
fiblist = thunk(cons(f1, restlist))
return fiblist

def hmap(f, t):
'''map _ [] = []
map f (x:xs) = f x : map f xs'''
l = t.value()
if isinstance(l, nil): return thunk(nil())
x, xs = l.uncons()
fx = thunk(lambda: f(x))
mapfxs = thunk(lambda: hmap(f, xs))
return thunk(cons(fx, mapfxs))

def show(t):
'''show :: a - String'''
v = t.value()
return thunk(str(v))

def printList(t):
'''This just gives us a way to debug lists.'''
v = t.value()
print [,
while True:
h,t = v.uncons()
print %s % h.value(),
if isinstance(t.value(), nil): break
else: print , ,
v = t.value()
print ]

def take(tn, tl):
'''take n _ | n = 0 = []
take _ [] = []
take n (x:xs) = x : take (n-1) xs'''
n = tn.value()
if n = 0: return thunk(nil())
l = tl.value()
if isinstance(l, nil): return thunk(nil())
x,xs = l.uncons()
nminusone = thunk(lambda: plus(tn, thunk(-1)))
takerec = thunk(lambda: take(nminusone, xs))
return thunk(cons(x, takerec))
\end{code}

You can try this out in python with:
tenfibs = take(thunk(10), fibs())
printList(tenfibs)

This will print the first 10 fibs.

Questions:
I think the examples above are correctly lazy.  Have I missed something?

I noticed my thunks can get wrapped in each other, is this to be expected,
or am I doing it wrong?

Is there an easier encoding using generators?  When I started I was using
generators instead of thunk, but I found it was complicating my design so I
removed it.  And yet, since generators are python's version of thunks, it
seems like there should be a more natural encoding there.

I'm not explicitly using a graph reduction algorithm to reach WHNF, does
this mean my translation is wrong?

Are there some well known test cases I should try?  Anyone know of a paper
that discusses making this translation?

I am trying to avoid writing an interpreter in Python for Haskell.  My goal
is to translate Haskell functions into the equivalent Python.  I'm also
hoping to avoid needing a G-machine.

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


Re: [Haskell-cafe] Haskell in Artificial Intelligence

2008-10-11 Thread Chryssochoidis Christos


On 11 Οκτ 2008, at 10:57 ΠΜ, Krasimir Angelov wrote:


Hi Christos

We use Haskell for natural language processing. See here:

http://www.cs.chalmers.se/~aarne/GF/

Best regards,
 Krasimir



Thank you very much for your response Krasimir.

Best regards,
Christos




On Fri, Oct 10, 2008 at 8:45 PM, Christos Chryssochoidis
[EMAIL PROTECTED] wrote:

Greetings,

I'm interested in doing a survey about the use of Haskell in the  
field of
Artificial Intelligence. I searched in Google, and found in the  
HaskellWiki,
at www.haskell.org/haskellwiki/Haskell_in_industry, two  
organizations that
use Haskell and do work related to AI. Besides that, I haven't  
found much
else. Could somebody from the Haskell community give me some  
pointer to a

project or system related to AI that uses Haskell?

Thank you very much in advance.

- CC




___
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] Haskell in Artificial Intelligence

2008-10-11 Thread Bartosz Wójcik
Hi CC,

you can find a word about possible usage of functional programming in AI in 
following paper:
http://www.cs.chalmers.se/~rjmh/Papers/whyfp.html .
Besides in HackageDB you can find separate category AI.
I had pleasure also to write an AI of simple game 
(http://en.wikipedia.org/wiki/Paper_Soccer):
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/foo .
Currently I'm working on AI of another game:
http://www.educationallearninggames.com/how-to-play-pylos-game-rules.asp .
It's not much though.

rgds,
Bartek


On Friday 10 October 2008 20:45:43 Christos Chryssochoidis wrote:
 Greetings,

 I'm interested in doing a survey about the use of Haskell in the field
 of Artificial Intelligence. I searched in Google, and found in the
 HaskellWiki, at www.haskell.org/haskellwiki/Haskell_in_industry, two
 organizations that use Haskell and do work related to AI. Besides that,
 I haven't found much else. Could somebody from the Haskell community
 give me some pointer to a project or system related to AI that uses
 Haskell?

 Thank you very much in advance.

 - CC




 ___
 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] [ANN] Haskell Cheatsheet v1.0

2008-10-11 Thread Thomas Hartman
Very nice!

I have my own cheat list, which are haskell commands I find useful but
find inconvenient or difficult to look up in the supplied
documentation. I actually hardwire my cheats into .bashrc doing
something like

thartman_haskell_cheatting() {

cat  EOF
  blah blah
cheat

}

so i can quickly see all my haskell cheats using tab completion. but a
pdf is even nicer :)

**

[EMAIL PROTECTED]:~/Desktopthartman_haskell_oneliners
  ghc -e '1+2'

[EMAIL PROTECTED]:~/Desktopthartman_haskell_regex_hints
  cabal install pcre-regex

  Most likely want:

  Prelude Text.Regex.PCRE user123 =~ ^(user)(\d*)$ ::
(String,String,String,[String])
  (,user123,,[user,123])
  That is: (before match, match, after match, subgroups)

  or maybe
Prelude Text.Regex.PCRE  user123 user456 =~ (u(se)r)(\d*) :: [[String]]
[[user123,user,se,123],[user456,user,se,456]]
if you need all submatches of all matches

since
  Prelude Text.Regex.PCRE user123 user456 =~ (user)(\d*) ::
(String,String,String,[String])
  (,user123, user456,[user,123])
  doesn't quite do what I want -- no submatches
  and there's no instance for :: (String,String,String,[String])
I don't need all submatches of all matches very often though.

  :: Bool -- did it match
  :: String -- first match
  :: [String] -- every match
  :: :: (String,String,String) -- before, matched, after

  
http://www.serpentine.com/blog/2007/02/27/a-haskell-regular-expression-tutorial/

[EMAIL PROTECTED]:~/Desktopthartman_haskell_testing_things
  import Data.Test.HUnit
  runTestTT $ TestCase $ assertEqual meh 1 2
  runTestTT $ TestList [ TestCase $ assertEqual meh 1 2 ]

[EMAIL PROTECTED]:~/Desktopthartman_haskell_hints
  offline documentation:
ghc-pkg describe bytestring | grep -i doc
  or probably just
  haddock-interfaces:
/usr/local/share/doc/ghc/libraries/bytestring/bytestring.haddock
  haddock-html: /usr/local/share/doc/ghc/libraries/bytestring
note to self:
  start using cabal install --global (or whatever the flag is)
so all documentation is browsable from one place

  Use language pragmas, with commas
  And you can't put LANGUAGE and OPTIONS_GHC in the same pragma
{-# LANGUAGE NoMonomorphismRestriction, PatternSignatures #-}
{-# OPTIONS -fglasgow-exts #-}

  Debugging

toVal.hs:30:17:
  Couldn't match expected type 'blee'
 against inferred type 'bleh'
bleh is whatever is at 30:17
blee is something that's wanted by whatever is calling the value at 30:17

If the error is in the definition of some function,
then probably one function case conflicts with another, you can
ignore other functions.
In this case you will only get one line:col to look at.
If there are more than one line:col to look at, possibly separate
functions are in conflict.
So, smart to always fix in the definition of type errors first.

Still baffled? Won't compile?
Give top-level functions type signatures. Won't hurt, might help.
  :set -fwarn-missing-signatures
  or {-# OPTIONS -fwarn-missing-signatures #-}
Start commenting out calling functions until it compiles, and then
look at the signatures.
And then type the signatures in explicitly... does something look funny?
  Like, wrong number of args? Maybe currying went wrong.

  tag and bundle a distribution:
darcs tag 0.2
cabal configure
cabal sdist
cd dist; unzip, verify install does the right thing
http://hackage.haskell.org/packages/upload.html
check upload, and upload.
see also http://en.wikibooks.org/wiki/Haskell/Packaging

  group module imports from multiple modules in one place:
module MyInductiveGraph (
  module Data.Graph.Inductive,
  module EnoughFlow
)
where
import Data.Graph.Inductive
import EnoughFlow



**
2008/10/11 Justin Bailey [EMAIL PROTECTED]:
 All,

 I've created a cheat sheet for Haskell. It's a PDF that tries to
 summarize Haskell 98's syntax, keywords and other language elements.
 It's currently available on hackage[1]. Once downloaded, unpack the
 archive and you'll see the PDF. A literate source file is also
 included.

 If you install with cabal install cheatsheet, run cheatsheet
 afterwards and the program will tell you where the PDF is located.

 The audience for this document is beginning to intermediate Haskell
 programmers. I found it difficult to look up some of the less-used
 syntax and other language stumbling blocks as I learned Haskell over
 the last few years, so I hope this document can help others in the
 future.

 This is a beta release (which is why I've limited the audience by
 using hackage) to get feedback before distributing the PDF to a wider
 audience. With that in mind, I welcome your comments or patches[2].

 Justin

 [1] http://hackage.haskell.org/cgi-bin/hackage-scripts/package/CheatSheet
 [2] git://github.com/m4dc4p/cheatsheet.git
 

Re: [Haskell-cafe] [ANN] Haskell Cheatsheet v1.0

2008-10-11 Thread Holger Siegel
On Saturday 11 October 2008 01:08:15 Justin Bailey wrote:

 This is a beta release (which is why I've limited the audience by
 using hackage) to get feedback before distributing the PDF to a wider
 audience. With that in mind, I welcome your comments or patches[2].

 Justin

 [1] http://hackage.haskell.org/cgi-bin/hackage-scripts/package/CheatSheet
 [2] git://github.com/m4dc4p/cheatsheet.git

Looks good!

Some minor issues:

- sometimes it is a bit verbose for a cheatsheet; for example the reference to 
language C in the section about the layout rule.

- in the section about strings, you give an example of a syntax error; it 
would be sufficient to show what is right.

- in the section about operator precedence you define 'div1' to be right 
associative. Instead, you could show where right associativity is actually 
useful (=, ...).

- The explanation of the layout rule is wrong. If you define more than one 
value in a let declaration, then it is only required that the identifiers  
start on the same column.

- When I started to learn Haskell, I had problems with the use of (.) and ($). 
I had learned what function application and lambda abstractions look like, but 
then I looked at Haskell code written by experienced Haskellers and found 
expressions like (map (succ . succ) $  1:xs) that I did not understand.
A small section describing how to read such expressions could be useful for 
beginners.

- the section about do-notation is more a mini-tutorial than a cheatsheet. 
Instead, you could show two or three examples that demonstrate how do-
notation, list comprehensions and the operator = relate. That is what I had 
to look up more than once until I got used to it. There is also an example of 
what is wrong, where showing the right thing would have sufficed.


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


Re: [Haskell-cafe] Interesting new user perspective

2008-10-11 Thread Ryan Ingram
If you want quick examples of idiomatic haskell including stdin/stdout
I/O, I like this page:
http://www.haskell.org/haskellwiki/Simple_unix_tools

  -- ryan

On Fri, Oct 10, 2008 at 7:08 PM, Iain Barnett [EMAIL PROTECTED] wrote:
 On 9 Oct 2008, at 9:33 pm, Andrew Coppin wrote:

  I think it's just the teaching of the language that needs work, not so
 much the language itself.


 As a newer user myself, I'd agree with this statement. I'd like to see far
 more mundane tasks solved in tutorials. The number of times building a
 parser or generating prime number is used as an example is out of proportion
 to the times you'd use these things[1]. Just simple, *really* easy things
 would be better. Maybe it's just me, but if I wanted to learn perl or ruby
 or python or C# I'm not sure I'd ever see a _tutorial_ containing a prime
 number.

 Haskell is can obviously do some really interesting things, but constantly
 having wikipedia open so I can look up whatever mathematical doodah has just
 been mentioned can get draining. Even Real World Haskell suffers a bit from
 this.


 Iain


 [1] In years of programming (other languages) I've never had to generate my
 own primes or build a compiler or a parser. I may have parsed things, but
 that's different to building an entire parser, if you get my drift.

 Actually, tell a  lie. I have built a parser, but it's still not stuff for a
 beginner's tutorial IMHO.
 ___
 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] [ANN] Haskell Cheatsheet v1.0

2008-10-11 Thread Dino Morelli

On Fri, 10 Oct 2008, Justin Bailey wrote:


I've created a cheat sheet for Haskell. It's a PDF that tries to
summarize Haskell 98's syntax, keywords and other language elements.
It's currently available on hackage[1]. Once downloaded, unpack the
archive and you'll see the PDF. A literate source file is also
included.


..

The audience for this document is beginning to intermediate Haskell
programmers. I found it difficult to look up some of the less-used
syntax and other language stumbling blocks as I learned Haskell over
the last few years, so I hope this document can help others in the
future.


..

Justin

[1] http://hackage.haskell.org/cgi-bin/hackage-scripts/package/CheatSheet
[2] git://github.com/m4dc4p/cheatsheet.git
___


Justin (and everyone now contributing to this), thanks. This type of
thing is very helpful. There is a well-known one-page cheat-sheet like
this for Perl5 (and a newer one for Perl6 too). You can see it by typing
`perldoc perlcheat` on a system with Perl.

I wonder if we don't need something like that.


On a related note, I had come up with this short list to help with how
to read the Haskell symbols.

I email this out when trying to get new people started:

-
Haskell symbology

One thing that I found very difficult at first was how to read a lot of
the symbols in the Haskell code. I made up a small cheat-sheet that
explains how to read some of it:

Some definitions of Haskell symbols:

::  has type

-  to  The type 'Integer - Integer' takes Integer as an argument
and evaluates to an Integer. We say this type is
Integer to Integer

=  evaluates or reduces to

Used in function type signatures, read something like this:

   foo :: (Bar b) = b - c

For all instances of type class Bar (here referred to as b),
foo is a function from b to c. Or foo has type b to c.

[a] list of a  The family of types consisting of, for every type
a, the type of lists of a.

:   cons  List cons operator, adds first argument to the front of
second, part of the List monad:

   (:) :: a - [a] - [a]

Read: cons has type a to list of a to list of a

!!  List index operator  [ 1, 2, 3 ] !! 1 = 2  (lists are 0-based)

   (!!) :: [a] - Int - a

Read: (!!) has type list of a to Int to a

|   such that

-  drawn from


= bind  Part of class Monad



 then  Part of class Monad

-

--
Dino Morelli  email: [EMAIL PROTECTED]  web: http://ui3.info/d/  irc: dino-
pubkey: http://ui3.info/d/dino-4AA4F02D-pub.gpg
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haskell in Artificial Intelligence

2008-10-11 Thread Chryssochoidis Christos


On 11 Οκτ 2008, at 11:41 ΠΜ, Bartosz Wójcik wrote:


Hi CC,

you can find a word about possible usage of functional programming  
in AI in

following paper:
http://www.cs.chalmers.se/~rjmh/Papers/whyfp.html .
Besides in HackageDB you can find separate category AI.
I had pleasure also to write an AI of simple game
(http://en.wikipedia.org/wiki/Paper_Soccer):
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/foo .
Currently I'm working on AI of another game:
http://www.educationallearninggames.com/how-to-play-pylos-game-rules.asp 
 .

It's not much though.

rgds,
Bartek



Thanks very much for the very interesting pointers!

Best regards,
Christos




On Friday 10 October 2008 20:45:43 Christos Chryssochoidis wrote:

Greetings,

I'm interested in doing a survey about the use of Haskell in the  
field

of Artificial Intelligence. I searched in Google, and found in the
HaskellWiki, at www.haskell.org/haskellwiki/Haskell_in_industry, two
organizations that use Haskell and do work related to AI. Besides  
that,

I haven't found much else. Could somebody from the Haskell community
give me some pointer to a project or system related to AI that uses
Haskell?

Thank you very much in advance.

- CC




___
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] External Sort and unsafeInterleaveIO

2008-10-11 Thread Thomas Hartman
I kinda-sorta half-cabalized it at

darcs get http://darcsdump.dreamhosters.com/external-sort (untested
via cabal install but mostly done)

As soon as my project gets approved I'll put it up on hackage.

If Ben wants it under his account at hackage of course I'll defer to him.

Thomas.

2007/7/18 Donald Bruce Stewart [EMAIL PROTECTED]:
 midfield:
 hi --

 thanks for the useful comments!  i will definitely go through them
 carefully.  unfortunately for this code (but fortunately for me) i
 defend my dissertation on monday so i'm a little distracted right
 now.

 i'm more than happy to donate this code or whatever improvements
 happen to it.  actually, hGetContentsWithCursor seems like a candidate
 for inclusion with Data.ByteStrings or Data.Binary or something -- it
 seems like it might find other uses.  (i think you liked that bit of
 code because i ripped it off of you guys!  it's very short hamming

 Can't fault that style ;)

 distance from the original.)  anyhow, all that will have to wait a
 couple weeks or so.  also i've never cabalized anything so i may come
 begging for help.

 We have a tutorial for that, luckily:

http://haskell.org/haskellwiki/How_to_write_a_Haskell_program

 And a tool to automate it, mkcabal, so should be fairly straightforward.


 at some point i thought i saw how to do recursive external sort, to
 keep memory usage truly constant, but with my current lack of sleep i
 have lost that illusion.  i'm also curious about the performance
 characteristics of this vs Prelude sort vs the version using the
 tournament mergesort apfelmus suggested.  i need to find a computer
 with a lot more RAM than my weakling laptop.  finally, it would be
 good to be able to have the blocksize controlled by Kb of RAM rather
 than # of elements, not sure how to get that information.

 ultimately this was part of my project to write lucene for haskell.  i
 think with this out of the way, plus all the Data.Binary / ByteString
 goodness, it shouldn't take too long.  keep writing good libraries for
 me!


 Great. Good to see things working.

 -- Don
 ___
 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] Haskell on the JVM

2008-10-11 Thread David Leimbach
Are there, or have there been Haskell ports to the JVM?  Are any of them
alive and well?
Is there an interest in hosting GHC on the JVM (besides my own).

I know I don't have time to tackle such a project but I'd be extremely
interested in using such a thing.  Especially in my day to day work.  I
currently do a lot of Java - Erlang via JInterface, and have been for
months, yet there's many tasks I could do better in a language like Haskell.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to translate Haskell to other languages?

2008-10-11 Thread Matthew Naylor
Hi Jason,

I don't know Python, but let me share some thoughts that you might
find useful.

First, a few questions about your manual translations.  Are your
functions curried?  For example, can I partially apply zipWith?  Also,
you put a thunk around things like cons(...) --- should it not be
the arguments to cons that are thunked?

Now, on to an automatic translation.  As you may know already, Haskell
programs can be transformed to combinator programs which are quite
simple and easy to work with.  Here is what I mean by a combinator
program:

  p ::= d*(a program is a list of combinator definitions)
  d ::= c v* = e  (combinator definition)
  e ::= e e   (application)
 |  v (variable/argument)
 |  c (constant: integer literal, combinator name, etc.)

As an example of a combinator program, here is one that reverses the
list [0,1,2].

  rev v acc = v acc (rev2 acc)
  rev2 acc x xs = rev xs (cons x acc)
  cons x xs n c = c x xs
  nil n c   = n

  main  = rev (cons 0 (cons 1 (cons 2 nil))) nil

This program does not type-check in Haskell!  But Python, being
dynamically typed, doesn't suffer from this problem. :-)

A translation scheme, D[], from a combinator definition to a Python
definition might look as follows.

  D[c v* = e]   =   def c() : return (lambda v1: ... lambda vn: E[e])
  E[e0 e1]  =   E[e0] (E[e1])
  E[v]  =   v
  E[c]  =   c()

Here is the result of (manually) applying D to the list-reversing program.

  def nil()  : return (lambda n: lambda c: n)
  def cons() : return (lambda x: lambda xs: lambda n: lambda c: c(x)(xs))
  def rev2() : return (lambda acc: lambda x: lambda xs:
 rev()(xs)(cons()(x)(acc)))
  def rev()  : return (lambda v: lambda acc: v(acc)(rev2()(acc)))

  def main() : return (rev() (cons()(0)(
cons()(1)(
  cons()(2)(
nil()(nil()))

The result of main() is a partially-applied function, which python
won't display.  But using the helper

  def list(f) : return (f([])(lambda x: lambda xs: [x] + list(xs)))

we can see the result of main():

   list(main())
  [2, 1, 0]

Of course, Python is a strict language, so we have lost Haskell's
non-strictness during the translation.  However, there exists a
transformation which, no matter how a combinator program is evaluated
(strictly, non-strictly, or lazily), the result will be just as if it
had been evaluated non-strictly.  Let's call it N, for Non-strict or
call-by-Name.

  N[e0 e1]   =   N[e0] (\x. N[e1])
  N[v]   =   v (\x. x)
  N[f]   =   f

I've cheekily introduced lambdas on the RHS here --- they are not
valid combinator expressions!  But since Python supports lambdas, this
is not a big worry.

NOTE 1: We can't remove the lambdas above by introducing combinators
because the arguments to the combinator would be evaluated and that
would defeat the purpose of the transformation!

NOTE 2: i could be replaced with anything above --- it is never
actually inspected.

For the sake of interest, there is also a dual transformation which
gives a program that enforces strict evaluation, no matter how it is
evaluated.  Let's call it S for Strict.

  S[e0 e1]=   \k. S[e0] (\f. S[e1] (\x. k (f x)))
  S[v]=   \k. k v
  S[f]=   \k. k f

I believe this is commonly referred to as the CPS
(continuation-passing style) transformation.

Now, non-strict evaluation is all very well, but what we really want
is lazy evaluation.  Let's take the N transformation, rename it to L
for Lazy, and indulge in a side-effecting reference, ML style.

  L[e0 e1]   =   L[e0] (let r = ref None in
  \x. match !r with
 None - let b = L[e1] in r := Some b ; b
   | Some b - b)
  L[v]   =   v (\x. x)
  L[f]   =   f

I don't know enough to define L w.r.t Python.

I haven't tried too hard to fully understand your translation, and
likewise, you may not try to fully understand mine!  But I thought I'd
share my view, and hope that it might be useful (and correct!) in some
way.

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


Re: [Haskell-cafe] [ANN] Haskell Cheatsheet v1.0

2008-10-11 Thread Stephen Hicks
On Fri, Oct 10, 2008 at 7:08 PM, Justin Bailey [EMAIL PROTECTED] wrote:
 I've created a cheat sheet for Haskell. It's a PDF that tries to
 summarize Haskell 98's syntax, keywords and other language elements.
 It's currently available on hackage[1]. Once downloaded, unpack the
 archive and you'll see the PDF. A literate source file is also
 included.

It looks very nice, if a bit verbose.  One minor comment is that on
page 4 you give a type signature for if-then-else.  I would contend
that it should be Bool - a - a - a, instead.

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


Re: [Haskell-cafe] Haskell on the JVM

2008-10-11 Thread John A. De Goes


LamdaVM was the only full-fledged effort to port Haskell to the JVM,  
and like most graduate school projects, the project is now dead.


I have strong interest in hosting GHC on the JVM. And I suspect it  
would be good for the Haskell community, as the JVM already runs on  
nearly every machine known to man, has a wealth of cross-platform  
libraries, and is getting improved support for dynamic and functional  
languages (method handles, tail call).


Regards,

John A. De Goes
N-BRAIN, Inc.
http://www.n-brain.net
[n minds are better than n-1]

On Oct 11, 2008, at 10:07 AM, David Leimbach wrote:

Are there, or have there been Haskell ports to the JVM?  Are any of  
them alive and well?


Is there an interest in hosting GHC on the JVM (besides my own).

I know I don't have time to tackle such a project but I'd be  
extremely interested in using such a thing.  Especially in my day to  
day work.  I currently do a lot of Java - Erlang via JInterface,  
and have been for months, yet there's many tasks I could do better  
in a language like Haskell.



___
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] Haskell on the JVM

2008-10-11 Thread Brandon S. Allbery KF8NH

On 2008 Oct 11, at 12:07, David Leimbach wrote:
Are there, or have there been Haskell ports to the JVM?  Are any of  
them alive and well?


YHC, last I heard, was alive and well and there's a YHC Core backend  
for the JVM.



Is there an interest in hosting GHC on the JVM (besides my own).


There's interest but my understanding is that the GHC backend  
architecture is not at all friendly to work with.  That said, I hear  
in the next release (I think 6.12, not the 6.10 that's in beta) will  
have a redesigned backend architecture that is supposed to be much  
easier to work with, which will make it easier to provide native code  
generators for many currently poorly-served platforms --- including  
the JVM if anyone is so inclined.


You might want to ask on glasgow-haskell-users to get the people who  
really know.


--
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] Haskell on the JVM

2008-10-11 Thread John A. De Goes


There's a YHC that can compile to JavaScript, and JavaScript can be  
run on Java...


Which means, practically speaking, there is no YHC backend for the JVM.

Regards,

John A. De Goes
N-BRAIN, Inc.
http://www.n-brain.net
[n minds are better than n-1]

On Oct 11, 2008, at 11:08 AM, Brandon S. Allbery KF8NH wrote:


On 2008 Oct 11, at 12:07, David Leimbach wrote:
Are there, or have there been Haskell ports to the JVM?  Are any of  
them alive and well?


YHC, last I heard, was alive and well and there's a YHC Core backend  
for the JVM.



Is there an interest in hosting GHC on the JVM (besides my own).


There's interest but my understanding is that the GHC backend  
architecture is not at all friendly to work with.  That said, I hear  
in the next release (I think 6.12, not the 6.10 that's in beta) will  
have a redesigned backend architecture that is supposed to be much  
easier to work with, which will make it easier to provide native  
code generators for many currently poorly-served platforms ---  
including the JVM if anyone is so inclined.


You might want to ask on glasgow-haskell-users to get the people who  
really know.


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



___
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] Re: Interesting new user perspective

2008-10-11 Thread apfelmus
Andrew Coppin wrote:
 Martin DeMello wrote:
 http://blog.moertel.com/articles/2006/10/18/a-type-based-solution-to-the-strings-problem

 is a brilliant example of a common workaday problem found in other
 languages, and solved elegantly in Haskell
   
 
 Oh, hey, that's pretty nice...

... and a solution to a problem that you souldn't have in the first
place. I mean, if you want to construct XML or SQL statements, you ought
to use an abstract data type that ensures proper nesting etc. and not a
simple string.


Regards,
apfelmus

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


Re: [Haskell-cafe] How to translate Haskell to other languages?

2008-10-11 Thread Derek Elkins
On Sat, 2008-10-11 at 16:55 +0100, Matthew Naylor wrote:
 Hi Jason,
 
 I don't know Python, but let me share some thoughts that you might
 find useful.
 
 First, a few questions about your manual translations.  Are your
 functions curried?  For example, can I partially apply zipWith?  Also,
 you put a thunk around things like cons(...) --- should it not be
 the arguments to cons that are thunked?
 
 Now, on to an automatic translation.  As you may know already, Haskell
 programs can be transformed to combinator programs which are quite
 simple and easy to work with.  Here is what I mean by a combinator
 program:
 
   p ::= d*(a program is a list of combinator definitions)
   d ::= c v* = e  (combinator definition)
   e ::= e e   (application)
  |  v (variable/argument)
  |  c (constant: integer literal, combinator name, etc.)
 
 As an example of a combinator program, here is one that reverses the
 list [0,1,2].
 
   rev v acc = v acc (rev2 acc)
   rev2 acc x xs = rev xs (cons x acc)
   cons x xs n c = c x xs
   nil n c   = n
 
   main  = rev (cons 0 (cons 1 (cons 2 nil))) nil
 
 This program does not type-check in Haskell!  But Python, being
 dynamically typed, doesn't suffer from this problem. :-)
 
 A translation scheme, D[], from a combinator definition to a Python
 definition might look as follows.
 
   D[c v* = e]   =   def c() : return (lambda v1: ... lambda vn: E[e])
   E[e0 e1]  =   E[e0] (E[e1])
   E[v]  =   v
   E[c]  =   c()
 
 Here is the result of (manually) applying D to the list-reversing program.
 
   def nil()  : return (lambda n: lambda c: n)
   def cons() : return (lambda x: lambda xs: lambda n: lambda c: c(x)(xs))
   def rev2() : return (lambda acc: lambda x: lambda xs:
  rev()(xs)(cons()(x)(acc)))
   def rev()  : return (lambda v: lambda acc: v(acc)(rev2()(acc)))
 
   def main() : return (rev() (cons()(0)(
 cons()(1)(
   cons()(2)(
 nil()(nil()))
 
 The result of main() is a partially-applied function, which python
 won't display.  But using the helper
 
   def list(f) : return (f([])(lambda x: lambda xs: [x] + list(xs)))
 
 we can see the result of main():
 
list(main())
   [2, 1, 0]
 
 Of course, Python is a strict language, so we have lost Haskell's
 non-strictness during the translation.  However, there exists a
 transformation which, no matter how a combinator program is evaluated
 (strictly, non-strictly, or lazily), the result will be just as if it
 had been evaluated non-strictly.  Let's call it N, for Non-strict or
 call-by-Name.
 
   N[e0 e1]   =   N[e0] (\x. N[e1])
   N[v]   =   v (\x. x)
   N[f]   =   f
 
 I've cheekily introduced lambdas on the RHS here --- they are not
 valid combinator expressions!  But since Python supports lambdas, this
 is not a big worry.
 
 NOTE 1: We can't remove the lambdas above by introducing combinators
 because the arguments to the combinator would be evaluated and that
 would defeat the purpose of the transformation!
 
 NOTE 2: i could be replaced with anything above --- it is never
 actually inspected.
 
 For the sake of interest, there is also a dual transformation which
 gives a program that enforces strict evaluation, no matter how it is
 evaluated.  Let's call it S for Strict.
 
   S[e0 e1]=   \k. S[e0] (\f. S[e1] (\x. k (f x)))
   S[v]=   \k. k v
   S[f]=   \k. k f
 
 I believe this is commonly referred to as the CPS
 (continuation-passing style) transformation.

This is indeed a CPS transform.  Specifically, a call-by-value CPS
transform.  There is also a call-by-name one.
N[e0 e1] = \k. N[e0] (\f. f N[e1] k)
N[v] = v
N[c] = \k. k c

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


Re: [Haskell-cafe] Haskell on the JVM

2008-10-11 Thread Sean Leather

 Are there, or have there been Haskell ports to the JVM?  Are any of them
 alive and well?


See the thread started 9 September on Haskell and Java:

http://thread.gmane.org/gmane.comp.lang.haskell.cafe/44252

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


Re: [Haskell-cafe] Re: Interesting new user perspective

2008-10-11 Thread Iain Barnett


On 11 Oct 2008, at 6:34 pm, apfelmus wrote:


Andrew Coppin wrote:

Martin DeMello wrote:
http://blog.moertel.com/articles/2006/10/18/a-type-based-solution- 
to-the-strings-problem


is a brilliant example of a common workaday problem found in other
languages, and solved elegantly in Haskell



Oh, hey, that's pretty nice...


... and a solution to a problem that you souldn't have in the first
place. I mean, if you want to construct XML or SQL statements, you  
ought
to use an abstract data type that ensures proper nesting etc. and  
not a

simple string.


Do you have an example of what you mean?

Personally, I use stored procedures with a database as they protect  
from sql injection attacks (unless you write some really stupid  
procedures).



Iain



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


Re: [Haskell-cafe] Constraints at construction

2008-10-11 Thread Jake McArthur


On Oct 11, 2008, at 2:54 PM, Bit Connor wrote:


Smart constructors are nice but if your module doesn't also export the
regular constructor then you can't pattern match against it.

It would be cool if there was a way to export constructors from a
module, but only for use in pattern matching and not constructing new
values.


I suppose you could make a new data type to pattern match against. For  
example, say you have


data Foo A B = hidden constructors
foo :: A - B - Foo A B -- smart constructor

You could introduce and export

data FooView = Foo A B | other possible deconstructions
fooView :: Foo A B - FooView A B

You could even redefine the smart constructor as

foo : FooView A B - Foo A B

... if you wanted.

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


Re: [Haskell-cafe] Re: Interesting new user perspective

2008-10-11 Thread Iain Barnett


On 11 Oct 2008, at 9:02 pm, Svein Ove Aas wrote:

On Sat, Oct 11, 2008 at 9:30 PM, Iain Barnett [EMAIL PROTECTED]  
wrote:


Personally, I use stored procedures with a database as they  
protect from sql

injection attacks (unless you write some really stupid procedures).


Isn't this what parametrized queries are for?


they will also work (at least in MS SQL Server), but you'd lose some  
of the performance and organisational benefits.


And it stops people littering code with badly written SQL statements  
- at least I can keep track of the procedures! :)


Iain

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


Re: [Haskell-cafe] Constraints at construction

2008-10-11 Thread Bit Connor
On Thu, Oct 9, 2008 at 3:05 PM, Mitchell, Neil
[EMAIL PROTECTED] wrote:
 Hi Iain,

 The wiki page has quite a nice article:
 http://www.haskell.org/haskellwiki/Smart_constructors

Smart constructors are nice but if your module doesn't also export the
regular constructor then you can't pattern match against it.

It would be cool if there was a way to export constructors from a
module, but only for use in pattern matching and not constructing new
values.

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


Re: [Haskell-cafe] Re: Interesting new user perspective

2008-10-11 Thread Svein Ove Aas
On Sat, Oct 11, 2008 at 9:30 PM, Iain Barnett [EMAIL PROTECTED] wrote:

 Personally, I use stored procedures with a database as they protect from sql
 injection attacks (unless you write some really stupid procedures).

Isn't this what parametrized queries are for?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to translate Haskell to other languages?

2008-10-11 Thread Jason Dagit
On Sat, Oct 11, 2008 at 8:55 AM, Matthew Naylor 
[EMAIL PROTECTED] wrote:

 Hi Jason,

 I don't know Python, but let me share some thoughts that you might
 find useful.

 First, a few questions about your manual translations.  Are your
 functions curried?  For example, can I partially apply zipWith?  Also,
 you put a thunk around things like cons(...) --- should it not be
 the arguments to cons that are thunked?


I don't recall if I mentioned this in my original email.  My goal is to do
automatic translations.  So, no you can't partially apply zipWith, but then
that's because Python doesn't support partial application.  On the other
hand, you can easily use a lambda to get around this.  So in an automatic
translation I would replace partial application with lambdas.  This
shouldn't be a problem right?

My rule was to put a thunk around any Haskell value.  So I put cons cells
in thunks and I even wrapped functions in thunks.  The exception was that
there were quite a few places where I could tell by inspection that a
particular value would already be in a thunk.  For example, since I require
in my translation that putting a value in a cons requires the value to be a
thunk then when I pull values out of a cons I already know they are thunks
so no need to rewrap them.

Now, on to an automatic translation.  As you may know already, Haskell
 programs can be transformed to combinator programs which are quite
 simple and easy to work with.  Here is what I mean by a combinator
 program:

  p ::= d*(a program is a list of combinator definitions)
  d ::= c v* = e  (combinator definition)
  e ::= e e   (application)
 |  v (variable/argument)
 |  c (constant: integer literal, combinator name, etc.)

 As an example of a combinator program, here is one that reverses the
 list [0,1,2].

  rev v acc = v acc (rev2 acc)
  rev2 acc x xs = rev xs (cons x acc)
  cons x xs n c = c x xs
  nil n c   = n

  main  = rev (cons 0 (cons 1 (cons 2 nil))) nil

 This program does not type-check in Haskell!  But Python, being
 dynamically typed, doesn't suffer from this problem. :-)


I plan to exploit this in my translations as well.  I will assume type
checked Haskell programs as input to the translator.




 A translation scheme, D[], from a combinator definition to a Python
 definition might look as follows.

  D[c v* = e]   =   def c() : return (lambda v1: ... lambda vn: E[e])
  E[e0 e1]  =   E[e0] (E[e1])
  E[v]  =   v
  E[c]  =   c()

 Here is the result of (manually) applying D to the list-reversing program.


If nil() corresponds to [] in Haskell, then how did you arrive at this
definition?  As Derek Elkins points out your transformation is a CPS based.
So I'm going to guess that c is the continuation and n represents the nil?


  def nil()  : return (lambda n: lambda c: n)


This one makes a little bit of sense to me.  I see the components of the
list, the x and xs, and you apply the continuation to them.  What's going on
with n?

  def cons() : return (lambda x: lambda xs: lambda n: lambda c: c(x)(xs))


Now, now this is a getting a bit hard to read :)


  def rev2() : return (lambda acc: lambda x: lambda xs:
 rev()(xs)(cons()(x)(acc)))
  def rev()  : return (lambda v: lambda acc: v(acc)(rev2()(acc)))


I'm glad I don't have to maintain code that looks like this :)

  def main() : return (rev() (cons()(0)(
cons()(1)(
  cons()(2)(
nil()(nil()))

 The result of main() is a partially-applied function, which python
 won't display.  But using the helper

  def list(f) : return (f([])(lambda x: lambda xs: [x] + list(xs)))

 we can see the result of main():

   list(main())
  [2, 1, 0]


Cool!

So, supposing I went with a translation scheme like what you gave.  I think
I would end up with deeply nested function calls, this is probably very bad
for the python run-time.  Also, how do I allow Python to then access the
Haskell values?  I guess your definition of list above is an example of
that, but I'm not sure how I'd pull that off in general.



 Of course, Python is a strict language, so we have lost Haskell's
 non-strictness during the translation.  However, there exists a
 transformation which, no matter how a combinator program is evaluated
 (strictly, non-strictly, or lazily), the result will be just as if it
 had been evaluated non-strictly.  Let's call it N, for Non-strict or
 call-by-Name.


Interesting.




  N[e0 e1]   =   N[e0] (\x. N[e1])
  N[v]   =   v (\x. x)
  N[f]   =   f

 I've cheekily introduced lambdas on the RHS here --- they are not
 valid combinator expressions!  But since Python supports lambdas, this
 is not a big worry.


Right, not so bad.  My translation was doing the same thing actually.  A
common thing to see in my code is, x = thunk(lambda: y).



 NOTE 1: We can't remove the 

Re: [Haskell-cafe] Re: Interesting new user perspective

2008-10-11 Thread Andrew Coppin

Svein Ove Aas wrote:

On Sat, Oct 11, 2008 at 9:30 PM, Iain Barnett [EMAIL PROTECTED] wrote:
  

Personally, I use stored procedures with a database as they protect from sql
injection attacks (unless you write some really stupid procedures).



Isn't this what parametrized queries are for?
  


Yes. (And it also improves DB performance since it doesn't have to 
continually reparse the query and rebuild the query plan.)


Now consider dynamically constructing HTML and avoiding HTML injection 
attacks. There isn't an easy machine fix for that one.


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


Re: [Haskell-cafe] Re: Interesting new user perspective

2008-10-11 Thread Andrew Coppin

apfelmus wrote:

... and a solution to a problem that you souldn't have in the first
place. I mean, if you want to construct XML or SQL statements, you ought
to use an abstract data type that ensures proper nesting etc. and not a
simple string.
  


Right. And if you have 25 KB of HTML data, you're *really* going to 
transform all of that into an abstract data type just to avoid injection 
problems, right?


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


Re: [Haskell-cafe] How to translate Haskell to other languages?

2008-10-11 Thread David Menendez
2008/10/11 Jason Dagit [EMAIL PROTECTED]:

 On Sat, Oct 11, 2008 at 8:55 AM, Matthew Naylor
 [EMAIL PROTECTED] wrote:

 Here is the result of (manually) applying D to the list-reversing program.

 If nil() corresponds to [] in Haskell, then how did you arrive at this
 definition?  As Derek Elkins points out your transformation is a CPS based.
 So I'm going to guess that c is the continuation and n represents the nil?

  def nil()  : return (lambda n: lambda c: n)

I think this is known as the Church encoding. The parameters n and c
describe what to do with lists that are constructed with [] and (:),
respectively.

You can do this in Haskell, as well:

newtype List a = List { unList :: forall b. b - (a - List a - b) - b }

nil :: List a
nil = List (\n c - n)

cons :: a - List a - List a
cons x xs = List (\n c - c x xs)

foldListR :: (a - b - b) - b - List a - b
foldListR f z l = unList l z (\x xs - f x (foldListR f z xs))

compare foldListR with foldr:

foldr f z [] = z
foldr f z (x:xs) = f x (foldr f z xs)


Essentially, it represents the data in terms of how you pattern match
on it. You can in principle pull this off for any Haskell type, but
the resulting code isn't anything you'd want to work on manually.

-- 
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] [ANN] Haskell Cheatsheet v1.0

2008-10-11 Thread Justin Bailey
Thanks to everyone for their feedback. I've made some updates and
posted the PDF to my blog:

  http://blog.codeslower.com/2008/10/The-Haskell-Cheatsheet

On Sat, Oct 11, 2008 at 4:33 AM, Thomas Hartman [EMAIL PROTECTED] wrote:
 Very nice!

 I have my own cheat list, which are haskell commands I find useful but
 find inconvenient or difficult to look up in the supplied
 documentation. I actually hardwire my cheats into .bashrc doing
 something like

 thartman_haskell_cheatting() {

 cat  EOF
  blah blah
 cheat

 }

 so i can quickly see all my haskell cheats using tab completion. but a
 pdf is even nicer :)

 **

 [EMAIL PROTECTED]:~/Desktopthartman_haskell_oneliners
  ghc -e '1+2'

 [EMAIL PROTECTED]:~/Desktopthartman_haskell_regex_hints
  cabal install pcre-regex

  Most likely want:

  Prelude Text.Regex.PCRE user123 =~ ^(user)(\d*)$ ::
 (String,String,String,[String])
  (,user123,,[user,123])
  That is: (before match, match, after match, subgroups)

  or maybe
Prelude Text.Regex.PCRE  user123 user456 =~ (u(se)r)(\d*) :: 
 [[String]]
[[user123,user,se,123],[user456,user,se,456]]
if you need all submatches of all matches

since
  Prelude Text.Regex.PCRE user123 user456 =~ (user)(\d*) ::
 (String,String,String,[String])
  (,user123, user456,[user,123])
  doesn't quite do what I want -- no submatches
  and there's no instance for :: (String,String,String,[String])
I don't need all submatches of all matches very often though.

  :: Bool -- did it match
  :: String -- first match
  :: [String] -- every match
  :: :: (String,String,String) -- before, matched, after

  
 http://www.serpentine.com/blog/2007/02/27/a-haskell-regular-expression-tutorial/

 [EMAIL PROTECTED]:~/Desktopthartman_haskell_testing_things
  import Data.Test.HUnit
  runTestTT $ TestCase $ assertEqual meh 1 2
  runTestTT $ TestList [ TestCase $ assertEqual meh 1 2 ]

 [EMAIL PROTECTED]:~/Desktopthartman_haskell_hints
  offline documentation:
ghc-pkg describe bytestring | grep -i doc
  or probably just
  haddock-interfaces:
 /usr/local/share/doc/ghc/libraries/bytestring/bytestring.haddock
  haddock-html: /usr/local/share/doc/ghc/libraries/bytestring
note to self:
  start using cabal install --global (or whatever the flag is)
so all documentation is browsable from one place

  Use language pragmas, with commas
  And you can't put LANGUAGE and OPTIONS_GHC in the same pragma
{-# LANGUAGE NoMonomorphismRestriction, PatternSignatures #-}
{-# OPTIONS -fglasgow-exts #-}

  Debugging

toVal.hs:30:17:
  Couldn't match expected type 'blee'
 against inferred type 'bleh'
bleh is whatever is at 30:17
blee is something that's wanted by whatever is calling the value at 30:17

If the error is in the definition of some function,
then probably one function case conflicts with another, you can
 ignore other functions.
In this case you will only get one line:col to look at.
If there are more than one line:col to look at, possibly separate
 functions are in conflict.
So, smart to always fix in the definition of type errors first.

Still baffled? Won't compile?
Give top-level functions type signatures. Won't hurt, might help.
  :set -fwarn-missing-signatures
  or {-# OPTIONS -fwarn-missing-signatures #-}
Start commenting out calling functions until it compiles, and then
 look at the signatures.
And then type the signatures in explicitly... does something look funny?
  Like, wrong number of args? Maybe currying went wrong.

  tag and bundle a distribution:
darcs tag 0.2
cabal configure
cabal sdist
cd dist; unzip, verify install does the right thing
http://hackage.haskell.org/packages/upload.html
check upload, and upload.
see also http://en.wikibooks.org/wiki/Haskell/Packaging

  group module imports from multiple modules in one place:
module MyInductiveGraph (
  module Data.Graph.Inductive,
  module EnoughFlow
)
where
import Data.Graph.Inductive
import EnoughFlow



 **
 2008/10/11 Justin Bailey [EMAIL PROTECTED]:
 All,

 I've created a cheat sheet for Haskell. It's a PDF that tries to
 summarize Haskell 98's syntax, keywords and other language elements.
 It's currently available on hackage[1]. Once downloaded, unpack the
 archive and you'll see the PDF. A literate source file is also
 included.

 If you install with cabal install cheatsheet, run cheatsheet
 afterwards and the program will tell you where the PDF is located.

 The audience for this document is beginning to intermediate Haskell
 programmers. I found it difficult to look up some of the less-used
 syntax and other language stumbling blocks as I learned Haskell over
 the last few years, so I hope this document can help others in the
 future.

 This is a beta release (which is why I've limited the audience by
 using hackage) to get feedback before 

Re: [Haskell-cafe] [ANN] Haskell Cheatsheet v1.0

2008-10-11 Thread Justin Bailey
On Sat, Oct 11, 2008 at 5:30 AM, Holger Siegel [EMAIL PROTECTED] wrote:

 - The explanation of the layout rule is wrong. If you define more than one
 value in a let declaration, then it is only required that the identifiers
 start on the same column.

Thank you - updated.


 - When I started to learn Haskell, I had problems with the use of (.) and ($).
 I had learned what function application and lambda abstractions look like, but
 then I looked at Haskell code written by experienced Haskellers and found
 expressions like (map (succ . succ) $  1:xs) that I did not understand.
 A small section describing how to read such expressions could be useful for
 beginners.

Me too. I had a section on that originally but cut it due to time.
Patches are always welcome :)


 - the section about do-notation is more a mini-tutorial than a cheatsheet.
 Instead, you could show two or three examples that demonstrate how do-
 notation, list comprehensions and the operator = relate. That is what I had
 to look up more than once until I got used to it. There is also an example of
 what is wrong, where showing the right thing would have sufficed.


True, but I think it's helpful. That stuff really confused me at first.

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


Re: [Haskell-cafe] OT: Haskell desktop wallpaper?

2008-10-11 Thread Albert Y. C. Lai

Magnus Therning wrote:

Where can I find some nice wallpapers inspired by
Haskell, or maybe even created by Haskell code?


I once suggested a futuristic feature for xmonad or xmonad plugin: 
screensaver that randomly picks a haskell lecture video to play or a 
haskell tutorial page to display. The idea is that your colleagues do 
not know haskell yet, but they pass by your screen and learn haskell. 
Perhaps it can be extended to wallpaper as well.

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


[Haskell-cafe] Congrats. to wxHaskell

2008-10-11 Thread Don Stewart
I just want to congratulate the wxHaskell team on their new release.
With GHC 6.10 RC, cabal 1.6, and cabal-install 0.6, I was able to
simply,

cabal install wxcore wx

And it all worked. 

Well done!

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


Re: [Haskell-cafe] [] vs [()]

2008-10-11 Thread Simon Richard Clarkstone

Sam Danielson wrote:

The [] constructor takes no arguments and is like Nothing in the Maybe
type. The list : (cons) infix constructor takes two arguments, an
element of type a and a list of type a, to construct a new list. Compare
to Maybe.

data []a = []  | a : [a]
data Maybe a = Nothing | Just a

Another way of saying [()] is

():[]

which, comparing with the Maybe type, is similar to saying

Just ()

but Just only takes one argument where (:) takes two.

Both List and Maybe are containers that have a null constructor, namely
[] and Nothing. ():[] contains () similar to how Just () contains
(). You can make your own list type and put () in it as follows.


Or, in Monad terms:

[()] and Just () are both return () in their respective Monads.
[] and Nothing are both mzero in their respective MonadsPluses. 
(Both are also fail in their respective Monads, but I find fail's 
presence in Monad a bit inelegant, though handy.)


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


[Haskell-cafe] Ubuntu Haskell

2008-10-11 Thread Ashley Yakeley

Don Stewart wrote:

* Arch now has 609 Haskell packages in AUR.


Have you thought about doing this for Ubuntu? If you know how to 
automatically generate packages, you could set up a PPA (private package 
archive) on Launchpad.


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


[Haskell-cafe] Re: Ubuntu Haskell

2008-10-11 Thread Don Stewart
ashley:
 Don Stewart wrote:
 * Arch now has 609 Haskell packages in AUR.
 
 Have you thought about doing this for Ubuntu? If you know how to 
 automatically generate packages, you could set up a PPA (private package 
 archive) on Launchpad.

I've spoken with Jeremy Shaw, who has similar systems in place, based
also on Cabal (and cabal-install), for generating native packages for
Debian  Ubuntu.

However, we do need some Ubuntu champions who can work incrementally,
over a long time, to keep packages up to date on their systems.

Automation makes this a *lot* easier, so you may only need one or two
people, motivated to work on their distro.

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


Re: [Haskell-cafe] Shooting your self in the foot with Haskell

2008-10-11 Thread Simon Richard Clarkstone

John Van Enk wrote:
On Sun, Oct 5, 2008 at 11:21 PM, John Van Enk [EMAIL PROTECTED] 
mailto:[EMAIL PROTECTED] wrote:



On Sun, Oct 5, 2008 at 6:22 PM, Simon Richard Clarkstone
[EMAIL PROTECTED] mailto:[EMAIL PROTECTED] wrote:

BTW, these could go on the wiki.

I'll see about putting them there. :)


http://haskell.org/haskellwiki/Shooting_your_self_in_the_foot

This needs to be cleaned up a little (lots of dups, though they are all 
great).


You missed my one, though I think the ballistics algebra one is better.

ISTR that the point of the original list was originally to show that, 
though you can screw up with C, with every other language you can screw 
up in far more complicated and inscrutable ways.  Ballistics algebra is 
indeed a way to screw up that is not possible in C.


(Darnit Thunderbird, why don't you DWIM when I hit reply or reply-all?)

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


[Haskell-cafe] Re: How to translate Haskell to other languages?

2008-10-11 Thread mail
Jason Dagit [EMAIL PROTECTED] writes:

 I don't recall if I mentioned this in my original email.  My goal is to do 
 automatic
 translations.  So, no you can't partially apply zipWith, but then that's 
 because Python doesn't
 support partial application.  On the other hand, you can easily use a lambda 
 to get around this. 
 So in an automatic translation I would replace partial application with 
 lambdas.  This shouldn't
 be a problem right?

Partial application can be done in python, though somewhat awkwardly.
Take a look at functools.partial.

-- 
Green's Law of Debate:
Anything is possible if you don't know what you're talking about.

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