Re: [Haskell-cafe] Arrows: definition of pure arr

2008-02-17 Thread Jonathan Cast
On 16 Feb 2008, at 11:40 PM, Peter Verswyvelen wrote: After having played with some packages that use arrows, and after having read the very nice programming with arrows paper I wanted to build some of my own. Strangely my code did not work, even the simplest function got stuck in an

Re: [Haskell-cafe] Doubting Haskell

2008-02-17 Thread Derek Elkins
On Sun, 2008-02-17 at 02:46 -0500, Anton van Straaten wrote: Colin Paul Adams wrote: Cale == Cale Gibbard [EMAIL PROTECTED] writes: Cale So, the first version: Cale import System.IO import Control.Exception (try) Cale main = do mfh - try (openFile myFile ReadMode)

[Haskell-cafe] Re: Doubting Haskell

2008-02-17 Thread apfelmus
Colin Paul Adams wrote: Left? Right? Hardly descriptive terms. Sounds like a sinister language to me. The mnemonics is that Right x is right in the sense of correct. So, the error case has to be Left err . Regards, apfelmus ___ Haskell-Cafe

Re: [Haskell-cafe] Re: Doubting Haskell

2008-02-17 Thread Colin Paul Adams
apfelmus == apfelmus [EMAIL PROTECTED] writes: apfelmus Colin Paul Adams wrote: Left? Right? Hardly descriptive terms. Sounds like a sinister language to me. apfelmus The mnemonics is that Right x is right in the sense of apfelmus correct. So, the error case

Re: [Haskell-cafe] Re: Doubting Haskell

2008-02-17 Thread Jonathan Cast
On 17 Feb 2008, at 1:12 AM, Colin Paul Adams wrote: apfelmus == apfelmus [EMAIL PROTECTED] writes: apfelmus Colin Paul Adams wrote: Left? Right? Hardly descriptive terms. Sounds like a sinister language to me. apfelmus The mnemonics is that Right x is right in the sense of

[Haskell-cafe] Re: Doubting Haskell

2008-02-17 Thread apfelmus
Alan Carter wrote: We now need to be able to do parallel with ease. Functional programming just got really important. While this is a reason to have a look at Haskell, I think it's not the best one. In fact, I think it's probably harmful to have parallelism as single goal for learning

Re: [Haskell-cafe] Doubting Haskell

2008-02-17 Thread Thomas Schilling
On 17 feb 2008, at 08.46, Anton van Straaten wrote: Colin Paul Adams wrote: Cale == Cale Gibbard [EMAIL PROTECTED] writes: Cale So, the first version: Cale import System.IO import Control.Exception (try) Cale main = do mfh - try (openFile myFile ReadMode) case mfh Cale of

Re: [Haskell-cafe] Arrows: definition of pure arr

2008-02-17 Thread Ross Paterson
On Sun, Feb 17, 2008 at 12:00:43AM -0800, Jonathan Cast wrote: arr = pure pure = arr [...] This example is admittedly kind of silly, but I'm sure someone has a passionate attachment to one or both names, so requiring definitions to use one or the other would be

[Haskell-cafe] ANN: winerror-0.1

2008-02-17 Thread Felix Martini
This is a small package for error handling when making foreign calls to the Windows API. The functions are similar to those in Foreign.C.Error, e.g. throwWinErrorIf corresponds to throwErrnoIf. Dynamic io errors are thrown with GHC so the catchWinError function can catch specific Windows error

Re: [Haskell-cafe] Stack overflow

2008-02-17 Thread Philip Armstrong
On Thu, Feb 14, 2008 at 04:56:39AM -0800, Grzegorz Chrupala wrote: I have a very simple program which reads a Data.Map from a file using Data.Binary and Data.ByteString.Lazy, which gives stack overflow with files over a certain size. Any ideas of what might be causing it? You can try it with

Re: [Haskell-cafe] Where does ~ come from?

2008-02-17 Thread Neil Mitchell
Hi 2) You would hope there is a quick way to search those symbols. But most search engines do not treate symbols friendly, often just ignore them. I typed ~ in Hoogle, it also returned nothing. 3) If the module defining the symbol is not in standard library, it is not possible to look up the

Re: [Haskell-cafe] Arrows: definition of pure arr

2008-02-17 Thread Peter Verswyvelen
I don't get why the name isn't arrow instead of arr... Arr reminds me of pirates, arrrhh ;-) I guess first was chosen because fst was already taken, but then it would be logical to choose arrow instead of arr ;-) Ross Paterson wrote: On Sun, Feb 17, 2008 at 12:00:43AM -0800, Jonathan

Re: [Haskell-cafe] Doubting Haskell

2008-02-17 Thread Philippa Cowderoy
On Sun, 17 Feb 2008, Anton van Straaten wrote: Is there a benefit to reusing a generic Either type for this sort of thing? For code comprehensibility, wouldn't it be better to use more specific names? If I want car and cdr, I know where to find it. It's Haskell's standard sum type, with a

Re: [Haskell-cafe] GHC + interactive input/output

2008-02-17 Thread Ian Lynagh
Hi Richard, On Mon, Feb 11, 2008 at 12:37:27PM +1300, Richard A. O'Keefe wrote: On 9 Feb 2008, at 2:29 pm, Philip Weaver wrote: GHC certain *could* do this, but it's arguably not the right thing to do. I have reminded the GHC maintainers before that the Haskell specification

Re: [Haskell-cafe] Working with multiple time zones

2008-02-17 Thread Bjorn Bringert
On Feb 17, 2008 12:13 AM, Dave Hinton [EMAIL PROTECTED] wrote: (This is a toy program to demonstrate only the part of my real program that I'm having trouble with.) Suppose I'm writing a program to print the current time in various time zones. The time zones are to be given symbolically on

Re: [Haskell-cafe] Working with multiple time zones

2008-02-17 Thread Daniel Fischer
Am Sonntag, 17. Februar 2008 16:09 schrieb Bjorn Bringert: Interesting, it works for me: $ ghc --make hsnow.hs -o hsnow [1 of 1] Compiling Main ( hsnow.hs, hsnow.o ) Linking hsnow ... $ ./hsnow Europe/Paris Europe/Moscow Europe/London Europe/Paris2008-02-17 16:07:43.009057

Re: [Haskell-cafe] Re: Doubting Haskell

2008-02-17 Thread Donn Cave
On Feb 17, 2008, at 1:12 AM, Colin Paul Adams wrote: And left is not the opposite of correct. That would be incorrect. Also, it is not clear to me that a failure to read a file (for instance) is incorrect behaviour. If the file doesn't exist, then I think it ought to be considered correct

Re: [Haskell-cafe] Working with multiple time zones

2008-02-17 Thread Brandon S. Allbery KF8NH
On Feb 17, 2008, at 13:22 , Daniel Fischer wrote: Am Sonntag, 17. Februar 2008 17:26 schrieb Daniel Fischer: Looking at the code in HsTime.c, it might be a difference between localtime and localtime_r. Indeed, mucking about a bit with HsTime.c, so that either a) localtime is called

Re: [Haskell-cafe] Working with multiple time zones

2008-02-17 Thread Daniel Fischer
Am Sonntag, 17. Februar 2008 17:26 schrieb Daniel Fischer: Looking at the code in HsTime.c, it might be a difference between localtime and localtime_r. Indeed, mucking about a bit with HsTime.c, so that either a) localtime is called instead of localtime_r or b) tzset() is done before

[Haskell-cafe] Re: Doubting Haskell

2008-02-17 Thread jerzy . karczmarczuk
Donn Cave writes: On Feb 17, 2008, at 1:12 AM, Colin Paul Adams wrote: And left is not the opposite of correct. That would be incorrect. ... If it's any consolation to those of the left handed persuasion, I guessed it wrong - I have used Either in this way, but Left was Success and Right

Re: [Haskell-cafe] Designing a Parser

2008-02-17 Thread Ryan Ingram
Writing a parsing library like this is a great learning experience; Graham Hutton wrote a paper you can follow along with entitled Monadic Parsing in Haskell at http://www.cs.nott.ac.uk/~gmh/bib.html#pearl But if you're just interested in writing a parser, and not in writing a parser generator, I

[Haskell-cafe] Re: Working with multiple time zones

2008-02-17 Thread Dave Hinton
Hurrah, I am now calling the C function tzset() from my Haskell code via FFI, and I'm getting the results I want. $ cat hsc2now.hs {-# LANGUAGE ForeignFunctionInterface #-} import Data.Time import Data.Time.LocalTime import System.Environment import System.Posix.Env foreign import ccall time.h

Re: [Haskell-cafe] Re: Working with multiple time zones

2008-02-17 Thread Don Stewart
beakerchu: Hurrah, I am now calling the C function tzset() from my Haskell code via FFI, and I'm getting the results I want. $ cat hsc2now.hs {-# LANGUAGE ForeignFunctionInterface #-} import Data.Time import Data.Time.LocalTime import System.Environment import System.Posix.Env foreign

Re: [Haskell-cafe] Stack overflow

2008-02-17 Thread Adrian Hey
Philip Armstrong wrote: Since no-one else has answered, I'll take a stab. Obiously, you have a stack leak due to laziness somewhere I wouldn't say that was obvious, though it is certainly a possibility. I'm never exactly clear what people mean by a stack leak. It seems some folk regard any

Re: [Haskell-cafe] Stack overflow

2008-02-17 Thread Bertram Felgenhauer
Adrian Hey wrote: Philip Armstrong wrote: In fact, a little experimentation has revealed that this: do [path] - getArgs m - liftM decode (BS.readFile path)::IO [((Int, Maybe String), Int)] putStrLn . show . findMax . fromAscList $ m will work just fine. No extra evaluation needed

[Haskell-cafe] More powerful error handling

2008-02-17 Thread Philippa Cowderoy
For a while I've been meaning to propose something along the lines of this class: class (MonadError m e, MonadError m' e') = MonadErrorRelated m e m' e' | m - e, m' - e', m e' - m' where catch' :: m a - (e - m' a) - m' a rethrow :: m a - (e - e') - m' a with an example instance

Re: [Haskell-cafe] Stack overflow

2008-02-17 Thread Adrian Hey
Bertram Felgenhauer wrote: I'm fairly certain that the stack overflow is (indirectly) caused by Data.Binary, not Data.Map. Yes, I think you are right. At least it seems clear that the stack overflow is not directly caused by fromDistinctAscList. The result of 'decode' is a list of known

[Haskell-cafe] Re: Designing DSL with explicit sharing [was: I love?purity, but it's killing me]

2008-02-17 Thread Chung-chieh Shan
Matthew Naylor [EMAIL PROTECTED] wrote in article [EMAIL PROTECTED] in gmane.comp.lang.haskell.cafe: sklansky f [] = [] sklansky f [x] = [x] sklansky f xs = left' ++ [ f (last left') r | r - right' ] where (left, right) = splitAt (length xs `div` 2) xs left' = sklansky f

Re: [Haskell-cafe] stream/bytestring questions

2008-02-17 Thread Brandon S. Allbery KF8NH
On Feb 17, 2008, at 18:53 , Chad Scherrer wrote: ByteStrings have given a real performance boost to a lot of Haskell applications, and I'm curious why some of the techniques aren't more abstracted and widely available. If it's because it's a big job, that's certainly understandable, but maybe

[Haskell-cafe] Rendering TTF fonts in Haskell and OpenGL

2008-02-17 Thread Jefferson Heard
In C and in Java, I can use truetype fonts in Haskell using select libraries, and I'd like to be able to do the same in Haskell. Are there any portable libraries out there for loading fonts into OpenGL geometry for Haskell? I can use the vector fonts from GLUT is absolutely neccessary, but I'd

[Haskell-cafe] stream/bytestring questions

2008-02-17 Thread Chad Scherrer
ByteStrings have given a real performance boost to a lot of Haskell applications, and I'm curious why some of the techniques aren't more abstracted and widely available. If it's because it's a big job, that's certainly understandable, but maybe there's something I'm overlooking that some of the

Re: [Haskell-cafe] Rendering TTF fonts in Haskell and OpenGL

2008-02-17 Thread Brandon S. Allbery KF8NH
On Feb 17, 2008, at 19:13 , Jefferson Heard wrote: In C and in Java, I can use truetype fonts in Haskell using select libraries, and I'd like to be able to do the same in Haskell. Are there any portable libraries out there for loading fonts into OpenGL geometry for Haskell? I can use the

Re: [Haskell-cafe] Doubting Haskell

2008-02-17 Thread Mads Lindstrøm
Hi Alan I can help but feeling curious. Did some of the answers actually help you? Are you still as doubtful about Haskell as when you wrote your email? Greetings, Mads Lindstrøm ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

Re: [Haskell-cafe] stream/bytestring questions

2008-02-17 Thread Chad Scherrer
On Feb 17, 2008 4:13 PM, Brandon S. Allbery KF8NH [EMAIL PROTECTED] wrote: Have you looked at the stream-fusion package on Hackage? http://hackage.haskell.org/cgi-bin/hackage-scripts/package/stream- fusion-0.1.1 Yeah, I've seen this. It's nice that this is separated, but a little unsatisfying

Re: [Haskell-cafe] stream/bytestring questions

2008-02-17 Thread Brandon S. Allbery KF8NH
On Feb 17, 2008, at 19:23 , Chad Scherrer wrote: On Feb 17, 2008 4:13 PM, Brandon S. Allbery KF8NH [EMAIL PROTECTED] wrote: Have you looked at the stream-fusion package on Hackage? http://hackage.haskell.org/cgi-bin/hackage-scripts/package/stream- fusion-0.1.1 Yeah, I've seen this. It's

Re: [Haskell-cafe] stream/bytestring questions

2008-02-17 Thread Don Stewart
chad.scherrer: ByteStrings have given a real performance boost to a lot of Haskell applications, and I'm curious why some of the techniques aren't more abstracted and widely available. If it's because it's a big job, that's certainly understandable, but maybe there's something I'm overlooking

Re: [Haskell-cafe] Doubting Haskell

2008-02-17 Thread John Meacham
On Sat, Feb 16, 2008 at 05:04:53PM -0800, Donn Cave wrote: But in Haskell, you cannot read a file line by line without writing an exception handler, because end of file is an exception! as if a file does not normally have an end where the authors of these library functions came from? Part of

Re: [Haskell-cafe] stream/bytestring questions

2008-02-17 Thread Don Stewart
chad.scherrer: On Feb 17, 2008 4:13 PM, Brandon S. Allbery KF8NH [EMAIL PROTECTED] wrote: Have you looked at the stream-fusion package on Hackage? http://hackage.haskell.org/cgi-bin/hackage-scripts/package/stream- fusion-0.1.1 Yeah, I've seen this. It's nice that this is separated, but

Re: [Haskell-cafe] Rendering TTF fonts in Haskell and OpenGL

2008-02-17 Thread Luke Palmer
On Feb 18, 2008 12:20 AM, Brandon S. Allbery KF8NH [EMAIL PROTECTED] wrote: On Feb 17, 2008, at 19:13 , Jefferson Heard wrote: In C and in Java, I can use truetype fonts in Haskell using select libraries, and I'd like to be able to do the same in Haskell. Are there any portable libraries

Re: [Haskell-cafe] stream/bytestring questions

2008-02-17 Thread Chad Scherrer
they currently use two different fusion systems. bytestring uses an older version of what is now stream fusion. at some point we'll switch bytestrings over to using the new stuff in the stream-fusion package, since its a lot better. Oh, that's pretty interesting. I had assumed bytestring had

Re: [Haskell-cafe] stream/bytestring questions

2008-02-17 Thread Don Stewart
chad.scherrer: they currently use two different fusion systems. bytestring uses an older version of what is now stream fusion. at some point we'll switch bytestrings over to using the new stuff in the stream-fusion package, since its a lot better. Oh, that's pretty interesting. I had

Re: [Haskell-cafe] Rendering TTF fonts in Haskell and OpenGL

2008-02-17 Thread Jefferson Heard
Thanks. that's certainly a thought... doesn't make the text 3d, though, does it? I'd ideally like to have something that turns the text into geometry, but this'll do in a pinch... On Sun, Feb 17, 2008 at 8:26 PM, Luke Palmer [EMAIL PROTECTED] wrote: On Feb 18, 2008 12:20 AM, Brandon S.

Re: [Haskell-cafe] stream/bytestring questions

2008-02-17 Thread Chad Scherrer
On Feb 17, 2008 5:01 PM, Don Stewart [EMAIL PROTECTED] wrote: yeah, with lists, as compared to bytestrings, there are: * more complex operations to fuse * allocation is much cheaper (lazy list cons nodes) * built in desugaring for build/foldr fusion interferes (enumerations,

Re: [Haskell-cafe] stream/bytestring questions

2008-02-17 Thread Derek Elkins
On Sun, 2008-02-17 at 18:02 -0800, Chad Scherrer wrote: On Feb 17, 2008 5:01 PM, Don Stewart [EMAIL PROTECTED] wrote: yeah, with lists, as compared to bytestrings, there are: * more complex operations to fuse * allocation is much cheaper (lazy list cons nodes) * built in

Re: [Haskell-cafe] Rendering TTF fonts in Haskell and OpenGL

2008-02-17 Thread Jeremy Shaw
At Mon, 18 Feb 2008 01:26:17 +, Luke Palmer wrote: I have an immature, but precise and picky implementation that renders text in a ttf font to an OpenGL texture (using SDL-ttf) here: http://svn.luqui.org/svn/misc/luke/work/code/haskell/frp/Fregl/Draw.hs (It may have some dependencies in

[Haskell-cafe] Arrow combinator names

2008-02-17 Thread Tom Davies
Are there generally accepted English language names for the arrow combinators? compose? pair? etc... ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Arrow combinator names

2008-02-17 Thread Derek Elkins
On Mon, 2008-02-18 at 03:37 +, Tom Davies wrote: Are there generally accepted English language names for the arrow combinators? compose? That's fine though ambiguous. pair? etc... The rest don't generally accepted readings. There are some examples of wordier names used (e.g. fork

[Haskell-cafe] naming a data structure for weighted random selection without replacement

2008-02-17 Thread Stuart Cook
A while ago I wrote a little data structure that allows weighted random selection-without-replacement from a collection of values in O(log n) time.[1] I'm now in the process of packaging it up for Hackage, but I'm looking for good names for both the type and its operations. The name I have at the