[Haskell-cafe] Implementing Mathematica

2007-05-30 Thread Jon Harrop
I only just subscribed to this mailing list and I am a complete Haskell newbie, so forgive me if this is too OT. I noticed a recent thread about writing a Mathematica implementation in Haskell. I think this is an excellent idea and would be a great project for a Haskell newbie. I wrote a toy

[Haskell-cafe] Efficiency question

2007-05-30 Thread Evil Bro
I'm pretty new to Haskell, so forgive me if my question is due to my non-functional way of thinking... I have the following code: module Main where main = print solution solution = solve 100 solve d = countUniqueFractions d 2 1 0 canBeSimplified (a,b) = gcd a b 1 countUniqueFractions

Re: [Haskell-cafe] Efficiency question

2007-05-30 Thread Donald Bruce Stewart
rwiggerink: I'm pretty new to Haskell, so forgive me if my question is due to my non-functional way of thinking... I have the following code: module Main where main = print solution solution = solve 100 solve d = countUniqueFractions d 2 1 0 canBeSimplified (a,b) = gcd a

Re: [Haskell-cafe] Darcs users [was: New book: Real-World Haskell!]

2007-05-30 Thread Donald Bruce Stewart
jon: On Wednesday 30 May 2007 06:58:36 Ketil Malde wrote: On Tue, 2007-05-29 at 14:05 -0500, Doug Kirk wrote: I *want* people (and companies) to move to Haskell As a complete noob considering making a commercial venture into Haskell, may I ask what people's opinions are on this? Are

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

2007-05-30 Thread Ketil Malde
On Tue, 2007-05-29 at 21:28 +0100, Andrew Coppin wrote: phantom types: the types of ghost values (in other words, we are only interested in the type, not in any value of that type). Mmm... Still not seeing a great amount of use for this one. The point is to 'tag' something with a type

Re: [Haskell-cafe] Language extensions

2007-05-30 Thread Ketil Malde
On Tue, 2007-05-29 at 21:39 +0100, Andrew Coppin wrote: My point is for most programs, trying to figure out exactly what you want the program to do is going to be much harder than implementing a program that does it. And the solution is..to not say anything about what the program should do?

Re: [Haskell-cafe] Language extensions

2007-05-30 Thread Tomasz Zielonka
On Tue, May 29, 2007 at 09:43:03PM +0100, Andrew Coppin wrote: Henning Thielemann wrote: On Sun, 27 May 2007, Andrew Coppin wrote: But every now and then I discover an expression which is apparently not expressible without them - which is odd, considering they're only sugar... Example?

Re: [Haskell-cafe] The C Equiv of != in Haskell miscommunication thread

2007-05-30 Thread Vincent Kraeutler
i would just like to say thank you for all the extensive replies. after fiddling with them for an afternoon i'm positive i grokked the concept. it's just too bad the nice wrapper concept from [1] does not seem to be directly applicable to fix in haskell, since they require untyped

Re: [Haskell-cafe] The C Equiv of != in Haskell miscommunication thread

2007-05-30 Thread Tomasz Zielonka
On Tue, May 29, 2007 at 06:40:05PM -0700, Jason Dagit wrote: Speaking of cute code, I'm fond of this: map length . List.group . Control.Monad.Fix.fix $ show fix show is cool in itself! :-) Best regards Tomek ___ Haskell-Cafe mailing list

[Haskell-cafe] Is there a Template lib like Cheetah in python?

2007-05-30 Thread Albert Lee
I am writing some webpage using haskell, I know Xhtml, but I also need some other persons to write simple htmls so I need a template system like cheetah in python, but I didn't find anything through google. any help? -- http://www.kamang.net ___

[Haskell-cafe] Re: Language extensions

2007-05-30 Thread apfelmus
Ketil Malde wrote: On Tue, 2007-05-29 at 21:39 +0100, Andrew Coppin wrote: Also, for most programs the spec is far more complicated (and hence prone to error) than the actual program, so... Since the program *is* a (complete) specification of itself, a specification need not be any longer

Re: [Haskell-cafe] Is there a Template lib like Cheetah in python?

2007-05-30 Thread Johan Tibell
I've been planning to write a web templating system for a while now but I haven't gotten around to it yet. I did write a small string templating library that works like Python's string.Template but it's probably not what you need. Here it is anyway:

Re: [Haskell-cafe] Distributing a program with support files

2007-05-30 Thread Duncan Coutts
On Mon, 2007-05-28 at 20:35 +0100, Neil Mitchell wrote: Hi Duncan, list the support files in the data-files: stanza in the .cabal file. Then import the Paths_pkg module that Cabal generates for you. It exports a few functions including: getDataDir :: IO FilePath A few questions:

[Haskell-cafe] Re: Shared libraries in GHC

2007-05-30 Thread Simon Marlow
Georg Sauthoff wrote: while searching, if ghc can create packages as shared libraries I found a ticket with a kind of non-accepted status: http://hackage.haskell.org/trac/summer-of-code/ticket/46 But at the google SoC page it looks like an accepted project:

Resolved: [Haskell-cafe] ffi linking problem

2007-05-30 Thread jeff p
Hello, In case anyone else finds this useful... My linking problem was finally resolved by using the -fvia-C flag when compiling with ghc. Thanks to Stefan O'Rear who pointed out the possibility and wrote: Does using -fvia-C help at all? The C compiler understands header files and is

Re: [Haskell-cafe] Language extensions

2007-05-30 Thread Jules Bean
Andrew Coppin wrote: My point is for most programs, trying to figure out exactly what you want the program to do is going to be much harder than implementing a program that does it. Also, for most programs the spec is far more complicated (and hence prone to error) than the actual program,

Re: [Haskell-cafe] Language extensions

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

[Haskell-cafe] Re: More on the random idea

2007-05-30 Thread Simon Marlow
Duncan Coutts wrote: On Mon, 2007-05-28 at 20:14 +0100, Andrew Coppin wrote: You looked at the source to GHCi itself I presume? It uses the GHC API, so it's a good place to start with building a variant of GHCi that uses the GHC API :-) No. Actually, as per the wiki, I was looking at the

Re: [Haskell-cafe] Efficiency question

2007-05-30 Thread Henning Thielemann
On Sun, 27 May 2007, Evil Bro wrote: I'm pretty new to Haskell, so forgive me if my question is due to my non-functional way of thinking... I have the following code: Counting can be done elegantly by 'filter' and 'length': length $ filter (1) $ Monad.liftM2 gcd [2..1000] [2..1000]

[Haskell-cafe] Re: More on the random idea

2007-05-30 Thread Simon Marlow
Stefan O'Rear wrote: On Sat, May 26, 2007 at 07:41:19PM +0100, Andrew Coppin wrote: Donald Bruce Stewart wrote: The #haskell people have been working on this for about 3 years now. The result is the 'runplugs' program, which I've talked about in previous mails.

Re: [Haskell-cafe] Efficiency question

2007-05-30 Thread Evil Bro
Counting can be done elegantly by 'filter' and 'length': I figured out the following code after posting: solve d = length [(y,x) | x - [2..d], y - [1..(x-1)], gcd x y == 1] main = print (solve 100) However when running it, it gave an answer of -1255316543. How on earth can a length be

[Haskell-cafe] Re: System.Timeout problems

2007-05-30 Thread Simon Marlow
Neil Mitchell wrote: Hi I'm using the System.Timeout module from base, copied into my local repo, so that I can work with GHC 6.6.1. My copy is at: http://www.cs.york.ac.uk/fp/darcs/catch/catch_1/System/TimeoutGHC.hs (but it is identical to the one in base) Sadly, it doesn't seem to work for

[Haskell-cafe] Re: Memoization

2007-05-30 Thread Simon Marlow
Rodrigo Queiro wrote: sorear pointed me to this paper a while ago: http://citeseer.ist.psu.edu/peytonjones99stretching.html I never tried any of the code in the end, but it will probably be useful? An implementation of that memo table scheme can be found here:

Re: [Haskell-cafe] Language extensions

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

Re: [Haskell-cafe] Re: Frisby grammars that have context

2007-05-30 Thread Jan-Willem Maessen
On May 29, 2007, at 10:44 AM, apfelmus wrote: Mark T.B. Carroll wrote: I've been playing with Text.Parsers.Frisby to see how it stacks against other options and, while it's been great so far, I am finding that I can't encode a grammar where what's acceptable depends on what's already

Re: [Haskell-cafe] Darcs users [was: New book: Real-World Haskell!]

2007-05-30 Thread Laurent Deniau
Jon Harrop wrote: On Wednesday 30 May 2007 06:58:36 Ketil Malde wrote: On Tue, 2007-05-29 at 14:05 -0500, Doug Kirk wrote: I *want* people (and companies) to move to Haskell As a complete noob considering making a commercial venture into Haskell, may I ask what people's opinions are on this?

Re: [Haskell-cafe] Re: Frisby grammars that have context

2007-05-30 Thread Isaac Dupree
-BEGIN PGP SIGNED MESSAGE- Hash: SHA1 Robin Green wrote: On Tue, 29 May 2007 19:28:02 -0400 Isaac Dupree [EMAIL PROTECTED] wrote: Luckily, Haskell's laziness means that doing an extra postprocessing pass doesn't necessarily yield two traversals requiring the whole file to be stored

Re: [Haskell-cafe] Efficiency question

2007-05-30 Thread Bertram Felgenhauer
Evil Bro wrote: Counting can be done elegantly by 'filter' and 'length': I figured out the following code after posting: solve d = length [(y,x) | x - [2..d], y - [1..(x-1)], gcd x y == 1] main = print (solve 100) However when running it, it gave an answer of -1255316543. How on

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

2007-05-30 Thread Claus Reinke
quantified types (forall/exist): an easy way to memorize this is to think of 'forall' as a big 'and' and of 'exists' as a big 'or'. e :: forall a. a -- e has type 'Int' and type 'Bool' and type .. e :: exists a. a -- e has type 'Int' or type 'Bool' or type .. That doesn't entirely

Re: [Haskell-cafe] Memoization

2007-05-30 Thread Creighton Hogg
On 5/26/07, Mark Engelberg [EMAIL PROTECTED] wrote: I'd like to write a memoization utility. Ideally, it would look something like this: memoize :: (a-b) - (a-b) memoize f gives you back a function that maintains a cache of previously computed values, so that subsequent calls with the same

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

2007-05-30 Thread Creighton Hogg
On 5/29/07, Andrew Coppin [EMAIL PROTECTED] wrote: Claus Reinke wrote: phantom types: the types of ghost values (in other words, we are only interested in the type, not in any value of that type). Mmm... Still not seeing a great amount of use for this one. Okay,

Re: [Haskell-cafe] Memoization

2007-05-30 Thread Isaac Dupree
-BEGIN PGP SIGNED MESSAGE- Hash: SHA1 Creighton Hogg wrote: Now maybe I'm being dense here, but would you really *want* a way in Haskell to do something like memo :: (a-b) - a-b since it changes the semantics of the function? It seems like a better abstraction would be to have memo

Re: [Haskell-cafe] Language extensions

2007-05-30 Thread Henk-Jan van Tuyl
On Wed, 30 May 2007 09:38:10 +0200, Tomasz Zielonka [EMAIL PROTECTED] wrote: On Tue, May 29, 2007 at 09:43:03PM +0100, Andrew Coppin wrote: Henning Thielemann wrote: On Sun, 27 May 2007, Andrew Coppin wrote: But every now and then I discover an expression which is apparently not

Re: [Haskell-cafe] Memoization

2007-05-30 Thread Creighton Hogg
On 5/30/07, Isaac Dupree [EMAIL PROTECTED] wrote: -BEGIN PGP SIGNED MESSAGE- Hash: SHA1 Creighton Hogg wrote: Now maybe I'm being dense here, but would you really *want* a way in Haskell to do something like memo :: (a-b) - a-b since it changes the semantics of the function? It

Re: [Haskell-cafe] The C Equiv of != in Haskell miscommunication thread

2007-05-30 Thread Albert Y. C. Lai
Roberto Zunino wrote: I actually misread the first one as Control.Monad.Fix.fix ((1:) . tail . scanl (+) 1) which is quite nice too, although map (2^) [0..] would be much simpler! ;-) We apply a lesson learned from my last derivation. The lesson was to look at s!!(n+1). s = 1 : tail

[Haskell-cafe] Re: [Haskell] ST vs State

2007-05-30 Thread Bulat Ziganshin
Hello Federico, Wednesday, May 30, 2007, 12:54:35 PM, you wrote: Control.Monad.ST And Control.Monad.State ST monad is just reduced IO monad which like IO organizes sequential (imperative) ordr of execution but unlike IO supports only a small closed set of operations - those working with

[Haskell-cafe] Re: Distributing a program with support files

2007-05-30 Thread Simon Marlow
Neil Mitchell wrote: Hi Duncan, list the support files in the data-files: stanza in the .cabal file. Then import the Paths_pkg module that Cabal generates for you. It exports a few functions including: getDataDir :: IO FilePath A few questions: 1) How do I test this? I'll need to develop

Re: [Haskell-cafe] Building error Gtk2Hs under GHC 6.6.1 on Solaris 10 x86

2007-05-30 Thread Duncan Coutts
On Wed, 2007-05-23 at 21:42 -0700, lebed wrote: Hi, haskell-caffe! I'm trying to build Gtk2Hs 0.9.11 under GHC 6.6.1 on Solaris 10 x86: ./mk/chsDepend -iglib:gtk:sourceview sourceview/Graphics/UI/Gtk/SourceView/Types.chs could not find {#import.chs on search path glib gtk sourceview

Re: [Haskell-cafe] Implementing Mathematica

2007-05-30 Thread Andrew Coppin
Jon Harrop wrote: I noticed a recent thread about writing a Mathematica implementation in Haskell. Yeah, that was me. I think this is an excellent idea and would be a great project for a Haskell newbie. Uh... I think it's actually a tad harder than it looks. [Understatement!] I wrote a

Re: [Haskell-cafe] Language extensions

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

Re: [Haskell-cafe] Implementing Mathematica

2007-05-30 Thread Alex Queiroz
Hallo, On 5/30/07, Andrew Coppin [EMAIL PROTECTED] wrote: OK, so you're saying that in 4 days you wrote something that out-performs Mathematica, a program that has existed for decades and has a vast, highly-funded RD effort behind it featuring some of the brightest minds in the field? I'm in

Re: [Haskell-cafe] Implementing Mathematica

2007-05-30 Thread Lennart Augustsson
Why do you seem so in awe of Mathematica? It's just another language with a good set of libraries. Claims that it is the best, fastest, etc comes from Wolfram advertising, no doubt. :) -- Lennart On Wed, 30 May 2007, Andrew Coppin wrote: Date: Wed, 30 May 2007 22:15:55 +0100 From:

Re: [Haskell-cafe] Implementing Mathematica

2007-05-30 Thread Jon Harrop
On Wednesday 30 May 2007 22:15:55 Andrew Coppin wrote: Jon Harrop wrote: I wrote a toy Mathematica implementation in OCaml while I waited to be viva'd for my PhD. It garnered so much interest that Wolfram Research bought it from me for £4,500 and gave me several free copies of

[Haskell-cafe] OpenGL

2007-05-30 Thread Jon Harrop
I've found HOpenGL and the Debian package libghc6-opengl-dev. The former seems to be very out of date (last release 2003) but I can't find any demos for the latter. Where should I go to get started with OpenGL and Haskell? -- Dr Jon D Harrop, Flying Frog Consultancy Ltd. OCaml for Scientists

Re: [Haskell-cafe] OpenGL

2007-05-30 Thread Creighton Hogg
On 5/30/07, Jon Harrop [EMAIL PROTECTED] wrote: I've found HOpenGL and the Debian package libghc6-opengl-dev. The former seems to be very out of date (last release 2003) but I can't find any demos for the latter. Where should I go to get started with OpenGL and Haskell? For at least GHC

Re: [Haskell-cafe] OpenGL

2007-05-30 Thread Bryan O'Sullivan
Jon Harrop wrote: Where should I go to get started with OpenGL and Haskell? Take a look at Gtk2Hs, which has OpenGL bindings. For example, see http://darcs.haskell.org/gtk2hs/demo/opengl/ b ___ Haskell-Cafe mailing list

Re: [Haskell-cafe] Implementing Mathematica

2007-05-30 Thread Stefan O'Rear
On Wed, May 30, 2007 at 11:56:30PM +0100, Jon Harrop wrote: On Wednesday 30 May 2007 22:15:55 Andrew Coppin wrote: Jon Harrop wrote: I wrote a toy Mathematica implementation in OCaml while I waited to be viva'd for my PhD. It garnered so much interest that Wolfram Research bought it

Re: [Haskell-cafe] OpenGL

2007-05-30 Thread Duncan Coutts
On Wed, 2007-05-30 at 16:09 -0700, Bryan O'Sullivan wrote: Jon Harrop wrote: Where should I go to get started with OpenGL and Haskell? Take a look at Gtk2Hs, which has OpenGL bindings. For example, see http://darcs.haskell.org/gtk2hs/demo/opengl/ The Gtk2Hs OpenGL stuff is only a

Re: [Haskell-cafe] Implementing Mathematica

2007-05-30 Thread Tim Chevalier
On 5/30/07, Jon Harrop [EMAIL PROTECTED] wrote: Incidentally, when I try to recompile with optimizations turned on, GHC refuses to work: $ ghc htrace.hs -o htrace $ ghc -O2 htrace.hs -o htrace compilation IS NOT required I must delete the target or edit the source to get it to recompile. I

Re: [Haskell-cafe] OpenGL

2007-05-30 Thread Thomas Schilling
See the examples/RedBook directory in the source code. It gives you a good idea how the C-idioms are translated. For an actual documentation on OpenGL you'll better take a look at general OpenGL literature and translate them into Haskell. Note that it's quite complex, though. On 5/31/07, Jon

Re: [Haskell-cafe] OpenGL

2007-05-30 Thread Jason Dagit
On 5/30/07, Jon Harrop [EMAIL PROTECTED] wrote: I've found HOpenGL and the Debian package libghc6-opengl-dev. The former seems to be very out of date (last release 2003) but I can't find any demos for the latter. Where should I go to get started with OpenGL and Haskell? I started converting

[Haskell-cafe] ANNOUNCE: xmonad 0.2

2007-05-30 Thread Spencer Janssen
The xmonad dev team is pleased to announce the 0.2 release of: xmonad: a tiling window manager http://xmonad.org About: Xmonad is a tiling window manager for X. Windows are arranged automatically to tile the screen without gaps or overlap,

Re: [Haskell-cafe] Implementing Mathematica

2007-05-30 Thread Jon Harrop
On Wednesday 30 May 2007 07:04:31 Jon Harrop wrote: 3. The language: the hardest part of reimplementing Mathematica is inferring what it means (there are no formal evaluation semantics). Once you've done that it is just a case of implementing an extensible term rewriter and putting in about 20

[Haskell-cafe] Crazy idea: overloading function application notation

2007-05-30 Thread Jon Harrop
This is a crazy idea I've been working on: overload the syntax x y so it can mean function application f x = f(x) or multiplication x y = x*y. The reason is simply that I appreciate the brevity of MLs function application but I also appreciate the brevity of Mathematica's multiplication. Is

[Haskell-cafe] enumFrom* strangeness on GHC?

2007-05-30 Thread Felipe Almeida Lessa
Hello =), I'm puzzled, and maybe someone can help me out. Why does this happens? $ time ghci -e last $ take 100 $ [1..100] 100 real0m0.673s user0m0.554s sys 0m0.024s $ time ghci -e last $ take 100 $ [1..] *** Exception: stack overflow real0m1.305s user

Re: [Haskell-cafe] enumFrom* strangeness on GHC?

2007-05-30 Thread Stefan O'Rear
On Wed, May 30, 2007 at 11:41:55PM -0300, Felipe Almeida Lessa wrote: Hello =), I'm puzzled, and maybe someone can help me out. Why does this happens? $ time ghci -e last $ take 100 $ [1..100] 100 real0m0.673s user0m0.554s sys 0m0.024s $ time ghci -e last $

Re: [Haskell-cafe] enumFrom* strangeness on GHC?

2007-05-30 Thread Felipe Almeida Lessa
On 5/30/07, Stefan O'Rear [EMAIL PROTECTED] wrote: No, because anything you file will be closed immediately as duplicate of http://hackage.haskell.org/trac/ghc/ticket/1097; Oh, sorry for not having searched better for this problem on the net. I spend a lot of time finding out where the stack

Re: [Haskell-cafe] enumFrom* strangeness on GHC?

2007-05-30 Thread Stefan O'Rear
On Thu, May 31, 2007 at 12:15:01AM -0300, Felipe Almeida Lessa wrote: On 5/30/07, Stefan O'Rear [EMAIL PROTECTED] wrote: No, because anything you file will be closed immediately as duplicate of http://hackage.haskell.org/trac/ghc/ticket/1097; Oh, sorry for not having searched better for this

Re: [Haskell-cafe] enumFrom* strangeness on GHC?

2007-05-30 Thread Felipe Almeida Lessa
On 5/31/07, Stefan O'Rear [EMAIL PROTECTED] wrote: You don't need to feel too bad about this: [snip] Don't worry, I should have googled anyway =). BTW, how do you usually proceed when finding out why your code said Segmentation fault.? (should this question move to a new thread?) Thanks,

Re: [Haskell-cafe] enumFrom* strangeness on GHC?

2007-05-30 Thread Stefan O'Rear
On Thu, May 31, 2007 at 12:34:36AM -0300, Felipe Almeida Lessa wrote: On 5/31/07, Stefan O'Rear [EMAIL PROTECTED] wrote: You don't need to feel too bad about this: [snip] Don't worry, I should have googled anyway =). BTW, how do you usually proceed when finding out why your code said

[Haskell-cafe] updating packages

2007-05-30 Thread jeff p
Hello, I just moved to ghc-6.6.1and was wondering if there is an automatic way to update the various packages I had installed previously. thanks, jeff ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

[Haskell-cafe] What puts False before True?

2007-05-30 Thread PR Stanley
Hi What is the basic philosophy for Bool being a member of Ord? What justifies False True? many Thanks in advance, Paul ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] What puts False before True?

2007-05-30 Thread kahl
What is the basic philosophy for Bool being a member of Ord? What justifies False True? The implication ordering, which on this smallest non-trivial Boolean algebra happens to be a linear order, is therefore the natural candidate for Ord, the type class of ``default linear orders''.

Re: [Haskell-cafe] What puts False before True?

2007-05-30 Thread Marc A. Ziegert
Am Donnerstag, 31. Mai 2007 05:52 schrieb PR Stanley: What is the basic philosophy for Bool being a member of Ord? you can do sth like Data.Set.fromList [minBound .. maxBound] :: Data.Set.Set Bool What justifies False True? in most interpretations this equals: False == 0 True == 1 and == (*)

[Haskell-cafe] equations and patterns

2007-05-30 Thread mingli yuan
Hi, buddies. I am a newbie on Haskell. Recently I want to implement a simple Lattice in Haskell, but I met some difficulties. Scrap of the code is as below, but I met syntax error: class Lattice e where join :: e - e - e meet :: e - e - e -- associative law join x (join y