Re: [Haskell-cafe] ANNOUNCE: The Monad.Reader - Issue 6

2007-02-01 Thread David House
On 31/01/07, David House [EMAIL PROTECTED] wrote: dw :: (a - Bool) - [a] - [a] dw p = reverse . fst . foldl comb ([],False) where comb (xs,done) x | done = (x:xs, True) | p x = (xs, False) | otherwise = (x:xs, True) I forgot to

Re: [Haskell-cafe] Re: Channel9 Interview: Software Composability and theFu ture of Languages

2007-02-01 Thread Benjamin Franksen
[sorry, this was meant to go to the list] On Wednesday 31 January 2007 00:40, Bulat Ziganshin wrote: Saturday, January 27, 2007, 12:00:11 AM, you wrote: and support operational reasoning, i.e. creating and understanding programs by mentally modeling their execution on a machine. This form

Re: [Haskell-cafe] Re: Channel9 Interview: Software Composability and theFu ture of Languages

2007-02-01 Thread Dougal Stanton
Quoth Magnus Therning, nevermore, I'm not sure how a functional recipe would look, maybe something like this: White_sauce is a combination of ... . Chopped_onions is onions cut into small pieces. White_sauce_with_chopped_onions is the combination of white_sauce and chopped_onions.

Re: [Haskell-cafe] Re: DevRandom

2007-02-01 Thread Yitzchak Gale
Bryan Donlan wrote: {-# NOINLINE hDevRandom #-} hDevRandom = unsafePerformIO $ openFile /dev/random ReadMode I wrote: The NOINLINE guarantees that openFile is called only once. But does it guarantee that openFile is NOT called if we do not need it? We could check what the compilers actually

[Haskell-cafe] Data.ByteString.Lazy.Char8 and finding substrings

2007-02-01 Thread Magnus Therning
I'm curious, why doesn't Data.ByteString.Lazy.Char8 have the functions for searching for substrings that Data.ByteString.Char8 has (isPrefixOf, isSuffixOf, isSubstringOf, findSubstring and findSubstrings)? /M -- Magnus Therning (OpenPGP: 0xAB4DFBA4) [EMAIL PROTECTED]

RE: [Haskell-cafe] Takusen - error handling and DBM monad

2007-02-01 Thread Bayley, Alistair
From: [EMAIL PROTECTED] [mailto:[EMAIL PROTECTED] On Behalf Of Paul Moore catcher :: DBException - DBM mark Session () catcher x = do liftIO $ putStrLn $ show x main = do withSession (connect ... ... ...) ( do catchDB (do ... ) catcher ) But

Re: [Haskell-cafe] Channel9 Interview: Software Composability and the Future of Languages

2007-02-01 Thread Tomasz Zielonka
On Wed, Jan 31, 2007 at 07:46:15PM +0300, Bulat Ziganshin wrote: Wednesday, January 31, 2007, 12:01:16 PM, you wrote: there are also many other similar issues, such as lack of good syntax for for, while, break and other well-known statements, On the other hand you have an ability to

Re: [Haskell-cafe] Re: Channel9 Interview: Software Composability and theFu ture of Languages

2007-02-01 Thread Yitzchak Gale
On 1/31/07, Kirsten Chevalier [EMAIL PROTECTED] wrote: On 1/31/07, Bill Wood [EMAIL PROTECTED] wrote: On Wed, 2007-01-31 at 19:51 +1100, Donald Bruce Stewart wrote: . . . foldl (\water dish - wash water dish) soapywater dishes :: [Dishes] Nice example. First, note that you can't

Re: Re[4]: [Haskell-cafe] ANNOUNCE: binary: high performance, pure binary serialisation

2007-02-01 Thread Duncan Coutts
On Thu, 2007-02-01 at 10:47 +0300, Bulat Ziganshin wrote: Hello Duncan, Thursday, February 1, 2007, 3:39:16 AM, you wrote: Can anyone see a real serialisation use case that needs a monad for the serialisation side? I'd thought I had an example, but I was wrong. my program,

Re: [Haskell-cafe] Re: Channel9 Interview: Software Composability and theFu ture of Languages

2007-02-01 Thread Neil Bartlett
The question is --- how would an expert describe such a process? Would a professional chef give instructions in the functional or imperative style? I think a sufficiently expert chef would not even need the functional style. Everything would be declarative. Dave Thomas (of Pragmatic

Re: [Haskell-cafe] Re: Channel9 Interview: Software Composability and theFu ture of Languages

2007-02-01 Thread Donald Bruce Stewart
neil: The question is --- how would an expert describe such a process? Would a professional chef give instructions in the functional or imperative style? I think a sufficiently expert chef would not even need the functional style. Everything would be declarative. Dave Thomas (of

Re: [Haskell-cafe] Levels of recursion

2007-02-01 Thread Yitzchak Gale
Hi Andrew, You wrote: combine :: [Int] - [Int] - [[Int]] combine [] _ = [] combine (x:xs) ys = (take x ys) : (combine xs (drop x ys)) ...A much more experienced haskeller told me he preferred to write it like this: combine' :: [Int] - [Int] - [[Int]] combine' xs ys = snd $ mapAccumL aux ys xs

Re[2]: [Haskell-cafe] Channel9 Interview: Software Composability and the Future of Languages

2007-02-01 Thread Bulat Ziganshin
Hello Tomasz, Thursday, February 1, 2007, 1:15:39 PM, you wrote: while (hGetBuf h buf bufsize == bufsize) crc := updateCrc crc buf bufsize break if crc==0 print crc inContT $ callCC $ \break - do flip execStateT 0 $ do whileM (liftM (== bufsize) (hGetBuf h

Re: [Haskell-cafe] Levels of recursion

2007-02-01 Thread Cale Gibbard
On 31/01/07, Andrew Wagner [EMAIL PROTECTED] wrote: Like I said, I'm familiar with map, foldr, etc. But this is the first time it's dawned on me that I need to think in more general recursive patterns like this instead of simple, raw recursion. That map and foldr aren't JUST a nice way of

[Haskell-cafe] Modulo-foo equivalence classes in Haskell?

2007-02-01 Thread Diego Navarro
Watching the questions go by in #haskell, a still fuzzy but possibly pregnant idea popped up in my mind. Someone needed a nubBy function that returned an unique list modulo an arbitrary function foo. Well, in this case it wasn't arbitrary; he had a list of transposable matrices and wanted an

Re: [Haskell-cafe] Modulo-foo equivalence classes in Haskell?

2007-02-01 Thread Chris Kuklewicz
Diego Navarro wrote: Watching the questions go by in #haskell, a still fuzzy but possibly pregnant idea popped up in my mind. Someone needed a nubBy function that returned an unique list modulo an arbitrary function foo. Well, in this case it wasn't arbitrary; he had a list of transposable

Re: [Haskell-cafe] Modulo-foo equivalence classes in Haskell?

2007-02-01 Thread Diego Navarro
newtype Y = Y { unY :: X } instance Eq Y where (==) = foo nub' :: [X] - [X] nub' = map unY . sort . map Y Yes, I thought of that. I'm really thinking of how I can generalize the Eq class so I dont have to go around manually lifting operations that are already defined (like operations on

Re: [Haskell-cafe] Modulo-foo equivalence classes in Haskell?

2007-02-01 Thread Diego Navarro
Yes, I thought of that. I'm really thinking of how I can generalize the Eq class so I dont have to go around manually lifting operations that are already defined (like operations on integers for modulo-n rings) (I do realize it's a lucky chance that the ordinary (+) and (*) work so well on

[Haskell-cafe] Boost equivalent

2007-02-01 Thread John Ky
Hi, Does the Haskell community have an equivalent to C++ community's Boost project with the aim of writing libraries for the eventual inclusion into Haskell? Thanks -John ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

Re: [Haskell-cafe] Boost equivalent

2007-02-01 Thread Neil Mitchell
Hi John, Does the Haskell community have an equivalent to C++ community's Boost project with the aim of writing libraries for the eventual inclusion into Haskell? We have: 1) MissingH - a nice staging ground for things that may end up in the base library 2) Library submission process, to

[Haskell-cafe] Connected!

2007-02-01 Thread Bulat Ziganshin
Hello haskell-cafe, i've just got ADSL connection here! it's slow (64k) and not cheap, but at least it is completely different from dial-up i've used before -- Best regards, Bulat mailto:[EMAIL PROTECTED] ___ Haskell-Cafe

Re: [Haskell-cafe] Connected!

2007-02-01 Thread Joel Reymont
What part of Russia do you live in? On Feb 1, 2007, at 1:23 PM, Bulat Ziganshin wrote: Hello haskell-cafe, i've just got ADSL connection here! it's slow (64k) and not cheap, but at least it is completely different from dial-up i've used before -- http://wagerlabs.com/

Re: [Haskell-cafe] Boost equivalent

2007-02-01 Thread Bulat Ziganshin
Hello John, Thursday, February 1, 2007, 4:03:09 PM, you wrote: Does the Haskell community have an equivalent to C++ community's Boost project with the aim of writing libraries for the eventual inclusion into Haskell? i guess that the only reason why C++ people need such project is because

Re: [Haskell-cafe] Boost equivalent

2007-02-01 Thread Chris Kuklewicz
Bulat Ziganshin wrote: Hello John, Thursday, February 1, 2007, 4:03:09 PM, you wrote: Does the Haskell community have an equivalent to C++ community's Boost project with the aim of writing libraries for the eventual inclusion into Haskell? The Haskell community is hosted on the wiki at

Re[2]: [Haskell-cafe] Connected!

2007-02-01 Thread Bulat Ziganshin
Hello Joel, Thursday, February 1, 2007, 4:25:45 PM, you wrote: What part of Russia do you live in? Tatarstan. we make Kamaz here :) if you are interested, such situation is very common for Russia - except for Moscow and a few other largest cities, internet costs are very high. you will stop

[Haskell-cafe] data package

2007-02-01 Thread Pavel Rozenblioum
Hi, I am trying to compile the GLR examples from Happy 1.16, but I get the message that I am missing the data package. Where can I download it from? I am using GHC 6.6 /pavel ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

[Haskell-cafe] Importance of MonadRandom

2007-02-01 Thread Yitzchak Gale
I would like to point out the importance of Cale Gibbard's MonadRandom, beyond what is currently mentioned on its wiki page: http://www.haskell.org/haskellwiki/New_monads/MonadRandom This monad makes it possible to write functions that use randomness without having to specify in advance whether

Re: [Haskell-cafe] Think of a monad...

2007-02-01 Thread Frederick Ross
And we have reached the monadic equivalent of Schrodinger's cat. On 1/31/07, Eric Y. Kow [EMAIL PROTECTED] wrote: Dear Haskellers, In the recent HWN, I noticed a new monad metaphor by Don Stewart: Think of a monad as a spacesuite full of nuclear waste in the ocean next to a container of

[Haskell-cafe] Re: Takusen - error handling and DBM monad

2007-02-01 Thread Al Falloon
Bayley, Alistair wrote: Al Falloon wrote: what does withSession return if there is a DBException? Well, whatever the handler returns, same as with any other exception handler. Note that this must have the same type as whatever withSession returns, and this constraint is enforced by the type

Re: [Haskell-cafe] Think of a monad...

2007-02-01 Thread Dan Mead
so are monads whats holding the nuclear waste or whats holding the apples? ;) On 2/1/07, Frederick Ross [EMAIL PROTECTED] wrote: And we have reached the monadic equivalent of Schrodinger's cat. On 1/31/07, Eric Y. Kow [EMAIL PROTECTED] wrote: Dear Haskellers, In the recent HWN, I noticed

Re[2]: [Haskell-cafe] Think of a monad...

2007-02-01 Thread Bulat Ziganshin
Hello Frederick, Thursday, February 1, 2007, 6:11:32 PM, you wrote: And we have reached the monadic equivalent of Schrodinger's cat. yes, it's exact reason why we love monads - the appropriate fruits in container are appeared depending on environment where it's used. you send probabilistic

Re: Re[2]: [Haskell-cafe] Channel9 Interview: Software Composability andthe Future of Languages

2007-02-01 Thread Claus Reinke
while (hGetBuf h buf bufsize == bufsize) crc := updateCrc crc buf bufsize break if crc==0 print crc inContT $ callCC $ \break - do flip execStateT 0 $ do whileM (liftM (== bufsize) (hGetBuf h buf bufsize)) $ do modifyM (updateCrc buf bufsize)

Re: [Haskell-cafe] Let's welcome the Ruby hackers!

2007-02-01 Thread Martin DeMello
On 2/1/07, Donald Bruce Stewart [EMAIL PROTECTED] wrote: So a big hello to any Ruby/Rails hackers lurking out there! Free lambdas for all if you drop by #haskell... I came to Haskell from Ruby the first time around, but didn't have anything real to write in it so I lost steam somewhat. This

RE: [Haskell-cafe] Re: Takusen - error handling and DBM monad

2007-02-01 Thread Bayley, Alistair
From: [EMAIL PROTECTED] [mailto:[EMAIL PROTECTED] On Behalf Of Al Falloon Bayley, Alistair wrote: Al Falloon wrote: what does withSession return if there is a DBException? Well, whatever the handler returns, same as with any other exception handler. Note that this must have the

Re[4]: [Haskell-cafe] Channel9 Interview: Software Composability andthe Future of Languages

2007-02-01 Thread Bulat Ziganshin
Hello Claus, Thursday, February 1, 2007, 6:34:23 PM, you wrote: is it, though? what makes it longer are features that the original doesn't have, and what i don't need :) I think. so how about a less ambitious translation, with crc in an MVar and a while-loop that can be broken from the

Re: [Haskell-cafe] Boost equivalent

2007-02-01 Thread Alexy Khrabrov
One of the great strengths of Python is Boost.Python. Practitioners say it's a major advantage of Python over Ruby, for example. So the question is not whether there's a Boost in Haskell -- C++ and Haskell are too different for it to have much meaning -- but whether there's or going to

[Haskell-cafe] Circular programming (aka time-travel) resources?

2007-02-01 Thread Justin Bailey
In The Monad.Reader - Issue 6, that just came out, there is a really interesting article that uses a circular technique to implement an assembly language in Haskell. The technique demonstrated seems fascinating. Can someone point me to more resources on the topic? A quick google search turned up

Re: [Haskell-cafe] Circular programming (aka time-travel) resources?

2007-02-01 Thread Neil Mitchell
Hi Justin, A quick google search turned up a couple of blogs and some papers - but is there more out there? http://news.cs.york.ac.uk/ftpdir/pub/colin/jfp97lw.ps.gz Laziness, circularity and prime numbers all in one :) Thanks Neil ___

Re: [Haskell-cafe] Let's welcome the Ruby hackers!

2007-02-01 Thread Paul Johnson
On 2/1/07, Donald Bruce Stewart [EMAIL PROTECTED] wrote: So a big hello to any Ruby/Rails hackers lurking out there! Free lambdas for all if you drop by #haskell... I think we should also try to get some feedback about the learning experience: what tutorials work best, and what don't? Do

Re: [Haskell-cafe] Circular programming (aka time-travel) resources?

2007-02-01 Thread Wouter Swierstra
Hi Justin, In The Monad.Reader - Issue 6, that just came out, there is a really interesting article that uses a circular technique to implement an assembly language in Haskell. The technique demonstrated seems fascinating. Can someone point me to more resources on the topic? I believe the

[Haskell-cafe] Re: Boost equivalent

2007-02-01 Thread Al Falloon
Boost.Python is for extending Python with C++, or embedding Python in C++. This is especially useful because it allows you to use Python as an extension language for a C++ program. Presumably Boost.Haskell would be for integrating Haskell code with C++, which would of course be useful, but

Re: [Haskell-cafe] ANNOUNCE: The Monad.Reader - Issue 6

2007-02-01 Thread Spencer Janssen
Yet another higher order solution: dropWhile' p0 xs = foldr f (const []) xs $ p0 where f y ys p | p y = ys p | otherwise = y : ys (const False) Spencer Janssen ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

Re: [Haskell-cafe] ANNOUNCE: The Monad.Reader - Issue 6

2007-02-01 Thread Bernie Pope
David House wrote: It was a great article though, seeing fix's definition in terms of foldr was one of those mind-bending moments which makes learning Haskell what it is. It's nice to see so many new solutions posted in the cafe. The great thing about Haskell is that it keeps on giving :)

Re: [Haskell-cafe] Re: Boost equivalent

2007-02-01 Thread Slavomir Kaslev
On 2/1/07, Al Falloon [EMAIL PROTECTED] wrote: Boost.Python is for extending Python with C++, or embedding Python in C++. This is especially useful because it allows you to use Python as an extension language for a C++ program. Presumably Boost.Haskell would be for integrating Haskell code with

Re: Re[4]: [Haskell-cafe] Channel9 Interview: Software Composabilityandthe Future of Languages

2007-02-01 Thread Claus Reinke
while (hGetBuf h buf bufzise .==. (return bufsize)) $ do crc =: updateCrc crc buf bufsize breakIf ((val crc) .==. (return 0)) `orElse` do printM (val crc) od your solution is just to make lifted copy of each and every pure operation. so one should define 2^n

[Haskell-cafe] (a - [b]) vs. [a - b]

2007-02-01 Thread Chad Scherrer
Are (a - [b]) and [a - b] isomorphic? I'm trying to construct a function f :: (a - [b]) - [a - b] that is the (at least one-sided) inverse of f' :: [a - b] - a - [b] f' gs x = map ($ x) gs It seems like it should be obvious, but I haven't had any luck with it yet. Any help is greatly

[Haskell-cafe] Write Yourself a Scheme in 48 Hours

2007-02-01 Thread Shannon -jj Behrens
I'm going through the Write Yourself a Scheme in 48 Hours http://halogen.note.amherst.edu/~jdtang/scheme_in_48/tutorial/overview.html tutorial. I like it a lot, but I have some concerns. Are the exercises in the tutorial known to be solvable by mere mortals? For instance: Rewrite parseNumber

Re: [Haskell-cafe] Channel9 Interview: Software Composability and the Future of Languages

2007-02-01 Thread Steve Downey
The 70's and early 80's were very different in terms of information propagation. I really miss some the journals available back then, because the editors really did their jobs, both in selecting and helping to convey, information. OO did get oversold. The same way that putting it on the internet

Re: [Haskell-cafe] Write Yourself a Scheme in 48 Hours

2007-02-01 Thread Bryan O'Sullivan
Shannon -jj Behrens wrote: I'm going through the Write Yourself a Scheme in 48 Hours http://halogen.note.amherst.edu/~jdtang/scheme_in_48/tutorial/overview.html tutorial. I like it a lot, but I have some concerns. Are the exercises in the tutorial known to be solvable by mere mortals? The

[Haskell-cafe] strict bytestring fun

2007-02-01 Thread Donald Bruce Stewart
High performance strings on the shootout: http://shootout.alioth.debian.org/gp4/benchmark.php?test=sumcollang=all interesting alternative programs 0.5 Haskell GHC #5 1.2990,880270 1.0 Clean 2.77600 136 2.0 C gcc

Re: [Haskell-cafe] Let's welcome the Ruby hackers!

2007-02-01 Thread Alexis
On Fri, 2 Feb 2007 06:46 am, Paul Johnson wrote: I think we should also try to get some feedback about the learning experience: what tutorials work best, and what don't? Do metaphors for monads work? Fwiw, here's an excerpt from something i wrote in my blog about monads (where i've

[Haskell-cafe] snd and tuples of various sizes...

2007-02-01 Thread Tim Newsham
This seems to make using tuples of various sizes easier (and can also be applied to non-tuples). I think it more closely matches how I describe something in spoken language (when I say second its obvious what that means for any tuple size): {-# OPTIONS_GHC -fglasgow-exts #-} module Main where

Re: [Haskell-cafe] Write Yourself a Scheme in 48 Hours

2007-02-01 Thread Henk-Jan van Tuyl
See for examples of the usage of = A tour of the Haskell monad functions, URL: members.chello.nl/hjgtuyl/tourdemonad.html On Fri, 02 Feb 2007 01:31:36 +0100, Shannon -jj Behrens [EMAIL PROTECTED] wrote: I'm going through the Write Yourself a Scheme in 48 Hours