Re: [Haskell-cafe] two problems with Data.Binary and Data.ByteString

2008-08-12 Thread Ketil Malde
Don Stewart <[EMAIL PROTECTED]> writes: >> You really, really want to be using rnf for this job, instead of >> turning your brain into a pretzel shape. > The Pretzel being one of the lesser-known lazy, cyclic, functional data > structures. So "pretzel-brain" is actually a honorific, rather than

Re: [Haskell-cafe] "Prompt" Monad

2008-08-12 Thread Martin Hofmann
Thanks a lot. That is exactly what I have been looking for. Cheers, Martin On Tue, 2008-08-12 at 10:28 -0700, Ryan Ingram wrote: > Latest code is on hackage: > http://hackage.haskell.org/cgi-bin/hackage-scripts/package/MonadPrompt > > There is a "sample" file with lots of other monads impleme

Re: [Haskell-cafe] two problems with Data.Binary and Data.ByteString

2008-08-12 Thread Don Stewart
newsham: > >I'm starting to wonder if this isn't an issue with > >Data.ByteString.Lazy.Char8.{read,write}File. > > This simple test case fails: > > module Main where > import qualified Data.ByteString.Lazy.Char8 as B > main = do > print =<< B.readFile "xxx" > B.writeFile "xxx" =

Re: [Haskell-cafe] Cyclic Inclusions

2008-08-12 Thread ajb
G'day all. Quoting Henning Thielemann <[EMAIL PROTECTED]>: As far as I know the real difficulties come from mutually recursive class definitions. I wouldn't be surprised, because that's a more blatant instance of the same problem. With classes and instances, there is no way to specify whethe

Re: [Haskell-cafe] two problems with Data.Binary and Data.ByteString

2008-08-12 Thread Don Stewart
bos: > On Tue, Aug 12, 2008 at 6:01 PM, Tim Newsham <[EMAIL PROTECTED]> wrote: > > > (my keys are dates, which are Enum). This should look at > > every key in every inner map. Shouldn't that be sufficient to > > force the entire data set (or do I have to touch the fields in the > > data elements

Re: [Haskell-cafe] Cyclic Inclusions

2008-08-12 Thread ajb
G'day all. Quoting Thomas Davie <[EMAIL PROTECTED]>: Why is separate compilation important? I'm a little shocked that anyone on this list should have to ask this question. Two people have asked it now. The simplest answer is that unless your program fits in cache, it takes longer to compile

Re: [Haskell-cafe] two problems with Data.Binary and Data.ByteString

2008-08-12 Thread Tim Newsham
I'm starting to wonder if this isn't an issue with Data.ByteString.Lazy.Char8.{read,write}File. This simple test case fails: module Main where import qualified Data.ByteString.Lazy.Char8 as B main = do print =<< B.readFile "xxx" B.writeFile "xxx" =<< B.readFile "test.hs" If y

Re: [Haskell-cafe] two problems with Data.Binary and Data.ByteString

2008-08-12 Thread Tim Newsham
You might have to force the last value of the alist that the map gets flattened into, since otherwise there's no guarantee that it will be read. You really, really want to be using rnf for this job, instead of turning your brain into a pretzel shape. *nod* that's my eventual goal but I'd like t

Re: [Haskell-cafe] two problems with Data.Binary and Data.ByteString

2008-08-12 Thread Bryan O'Sullivan
On Tue, Aug 12, 2008 at 6:01 PM, Tim Newsham <[EMAIL PROTECTED]> wrote: > (my keys are dates, which are Enum). This should look at > every key in every inner map. Shouldn't that be sufficient to > force the entire data set (or do I have to touch the fields in the > data elements too?) You might

Re: [Haskell-cafe] Dealing with heterogeneously-typed lists?

2008-08-12 Thread Bryan O'Sullivan
2008/8/12 Leif Warner <[EMAIL PROTECTED]>: > I know in a language like Java or C++ I might do some sort of run-time type > identification, which would detect the type of each element in the list, and > output it appropriately. I think I've missed a step. Why do you want to break the fields of an

Re: [Haskell-cafe] two problems with Data.Binary and Data.ByteString

2008-08-12 Thread Tim Newsham
Doesn't Data.Map.size run in O(1) time? Maybe something like using different encodings for big maps in the default implementation would help? ugh, of course. Ok, so I fixed it to: loadState db = do d <- decode <$> B.readFile stateFile let force = sum $ map (sum . map fromEnum . M.keys)

Re: [Haskell-cafe] two problems with Data.Binary and Data.ByteString

2008-08-12 Thread Don Stewart
bos: > On Tue, Aug 12, 2008 at 5:13 PM, Tim Newsham <[EMAIL PROTECTED]> wrote: > > > The data type I'm storing is a Map (of maps): > > > > type DailyDb = M.Map Date Daily > > type InstrsDb = M.Map String DailyDb > > > > What's going on here? > > The default marshalling scheme that Binary uses

Re: [Haskell-cafe] two problems with Data.Binary and Data.ByteString

2008-08-12 Thread Tim Newsham
Maybe it makes sense to have the streamble list instance in Binary as well, with some examples? A flexible format that doesn't sacrifice too much space efficiency would be to encode in chunks of up to 255 elements: Chunk = { length :: Word8 elems :: [Elem] -- 0..255 repetitions }

Re: [Haskell-cafe] two problems with Data.Binary and Data.ByteString

2008-08-12 Thread Tim Newsham
On Tue, 12 Aug 2008, Bryan O'Sullivan wrote: On Tue, Aug 12, 2008 at 5:34 PM, Tim Newsham <[EMAIL PROTECTED]> wrote: I tried to force the data with: loadState db = do d <- decode <$> B.readFile stateFile let force = sum $ M.elems $ M.size `fmap` d force `seq` atomicall

Re: [Haskell-cafe] two problems with Data.Binary and Data.ByteString

2008-08-12 Thread Felipe Lessa
On Tue, Aug 12, 2008 at 9:32 PM, Don Stewart <[EMAIL PROTECTED]> wrote: > Not hackery, just a different encoding. The default Binary encodings > don't work cover all use cases and all scales. To hit other sweet spots, > use your own instances. Doesn't Data.Map.size run in O(1) time? Maybe somethin

Re: [Haskell-cafe] two problems with Data.Binary and Data.ByteString

2008-08-12 Thread Bryan O'Sullivan
On Tue, Aug 12, 2008 at 5:34 PM, Tim Newsham <[EMAIL PROTECTED]> wrote: > I tried to force the data with: > >loadState db = do >d <- decode <$> B.readFile stateFile >let force = sum $ M.elems $ M.size `fmap` d >force `seq` atomically $ writeTVar db d > > and I get the s

Re: [Haskell-cafe] two problems with Data.Binary and Data.ByteString

2008-08-12 Thread Bryan O'Sullivan
On Tue, Aug 12, 2008 at 5:13 PM, Tim Newsham <[EMAIL PROTECTED]> wrote: > The data type I'm storing is a Map (of maps): > > type DailyDb = M.Map Date Daily > type InstrsDb = M.Map String DailyDb > > What's going on here? The default marshalling scheme that Binary uses for lists and maps (whic

Re: [Haskell-cafe] two problems with Data.Binary and Data.ByteString

2008-08-12 Thread Don Stewart
newsham: > >so that fromAscList's the result of parsing the map as a list, via, > > > > instance Binary a => Binary [a] where > > put l = put (length l) >> mapM_ put l > > get= do n <- get :: Get Int > > replicateM n get > > > >so that's a length-prefixed list,

Re: [Haskell-cafe] two problems with Data.Binary and Data.ByteString

2008-08-12 Thread Tim Newsham
Log: savedState.bin: openFile: resource busy (file is locked) this does not occur if the program wasnt loaded. My best guess here is that B.readFile isnt completing and closing the file for some reason. Is there a good way to force this? Lazy IO. So force the result to be evaluated, and the

Re: [Haskell-cafe] two problems with Data.Binary and Data.ByteString

2008-08-12 Thread Tim Newsham
so that fromAscList's the result of parsing the map as a list, via, instance Binary a => Binary [a] where put l = put (length l) >> mapM_ put l get= do n <- get :: Get Int replicateM n get so that's a length-prefixed list, strictly. Which is possibly wher

Re: [Haskell-cafe] two problems with Data.Binary and Data.ByteString

2008-08-12 Thread Don Stewart
newsham: > I have a program that read in and populated a large data structure and > then saved it out with Data.Binary and Data.ByteString.Lazy.Char8: > >saveState db = B.writeFile stateFile =<< >encode <$> atomically (readTVar db) > > when I go to read this in later I get a stack ove

[Haskell-cafe] two problems with Data.Binary and Data.ByteString

2008-08-12 Thread Tim Newsham
I have a program that read in and populated a large data structure and then saved it out with Data.Binary and Data.ByteString.Lazy.Char8: saveState db = B.writeFile stateFile =<< encode <$> atomically (readTVar db) when I go to read this in later I get a stack overflow: loadState db =

[Haskell-cafe] Dealing with heterogeneously-typed lists?

2008-08-12 Thread Leif Warner
Hi all, I'm dealing with some datatype, say: data Invoice = Invoice { invoiceNum:: String, dollarAmt :: Currency, printDate :: Date, dueDate :: Date, vendorNum :: Int,

Re: [Haskell-cafe] GLfloat on a Mac

2008-08-12 Thread Thomas Davie
On 12 Aug 2008, at 16:55, Conor McBride wrote: On 12 Aug 2008, at 11:27, Conor McBride wrote: On 12 Aug 2008, at 11:19, Jules Bean wrote: FWIW, I use ghc on my G4 and I got it by compiling from MacPorts. It took the best part of day, but the resulting binary works. I'm not sure whirl

Re: [Haskell-cafe] Cyclic Inclusions

2008-08-12 Thread Isaac Dupree
C.M.Brown wrote: I don't really see this as being any kind of real issue at all. Surely all GHC needs to do is to concatenate all the modules together, alpha-reduce the import/export relations and do a compile/type check over the concatenated module. FWIW, I agree (in principle -- I haven't loo

Re: [Haskell-cafe] Cyclic Inclusions

2008-08-12 Thread C.M.Brown
> The problem is not mutually recursive modules. Plenty of statically > typed languages support mutually recursive modules. > > The problem is that it's impossible in general to say what the > "interface" of a module is by examining the module alone. This is a > very unusual property as real-worl

Re: [Haskell-cafe] "Prompt" Monad

2008-08-12 Thread Ryan Ingram
Latest code is on hackage: http://hackage.haskell.org/cgi-bin/hackage-scripts/package/MonadPrompt There is a "sample" file with lots of other monads implemented in terms of Prompt included, along with some links to other samples; I seem to recall there being a "guess a number" game on paste.lisp.o

Re: [Haskell-cafe] GLfloat on a Mac

2008-08-12 Thread Jules Bean
Conor McBride wrote: After a very long time, it fell over with a large error message that I don't understand. Somehow, I'll get over it. I can't help thinking that this stuff shouldn't be hard. And yet it is. Sorry to anyone for whom this is just spam, and much gratitude to clued in people who

Re: [Haskell-cafe] GLfloat on a Mac

2008-08-12 Thread Conor McBride
On 12 Aug 2008, at 11:27, Conor McBride wrote: On 12 Aug 2008, at 11:19, Jules Bean wrote: FWIW, I use ghc on my G4 and I got it by compiling from MacPorts. It took the best part of day, but the resulting binary works. I'm not sure whirl is the right word, but I'll give it one anyway.

Re: [Haskell-cafe] Cyclic Inclusions

2008-08-12 Thread Thomas Davie
On 12 Aug 2008, at 16:01, [EMAIL PROTECTED] wrote: G'day all. Quoting Thomas Davie <[EMAIL PROTECTED]>: I'm not sure that it does make a lot of sense -- we allow (mutually) recursive functions, even though they come with an efficiency penalty. Why should we not allow (mutually) recursive m

Re: [Haskell-cafe] Cyclic Inclusions

2008-08-12 Thread Henning Thielemann
On Tue, 12 Aug 2008, [EMAIL PROTECTED] wrote: G'day all. Quoting Thomas Davie <[EMAIL PROTECTED]>: I'm not sure that it does make a lot of sense -- we allow (mutually) recursive functions, even though they come with an efficiency penalty. Why should we not allow (mutually) recursive modules,

Re: [Haskell-cafe] Cyclic Inclusions

2008-08-12 Thread ajb
G'day all. Quoting Thomas Davie <[EMAIL PROTECTED]>: I'm not sure that it does make a lot of sense -- we allow (mutually) recursive functions, even though they come with an efficiency penalty. Why should we not allow (mutually) recursive modules, even though they too come with an efficiency pen

Re: [Haskell-cafe] Cyclic Inclusions

2008-08-12 Thread C.M.Brown
> I'm not sure that it does make a lot of sense -- we allow (mutually) > recursive functions, even though they come with an efficiency > penalty. Why should we not allow (mutually) recursive modules, even > though they too come with an efficiency penalty. This is even an > example where the effic

Re: [Haskell-cafe] Cyclic Inclusions

2008-08-12 Thread Thomas Davie
On 12 Aug 2008, at 11:59, C.M.Brown wrote: Andrew, Thanks very much for your reponse. It was very helpful; this makes a lot of sense! And yes, some people think that this is a bug in the specification. I'm not sure that it does make a lot of sense -- we allow (mutually) recursive fun

[Haskell-cafe] "Prompt" Monad

2008-08-12 Thread Martin Hofmann
I just came across last year's thread about Ryan Ingram's "Prompt" monad ( http://www.mail-archive.com/haskell-cafe@haskell.org/msg33040.html ) and wondered if it might be useful for debugging and program analysis purposes. In particular, I thought about enforcing program decisions interactively. C

Re: [Haskell-cafe] GLfloat on a Mac

2008-08-12 Thread Conor McBride
On 12 Aug 2008, at 11:19, Jules Bean wrote: Conor McBride wrote: This sounds like bad news to me. I wonder how broken this G5 ghc is for a G4. Perhaps it should be labelled G5 rather than PowerPC in the large print. I'm quite scared about trying to build ghc: I worry that it may involve confro

Re: [Haskell-cafe] GLfloat on a Mac

2008-08-12 Thread Jules Bean
Conor McBride wrote: This sounds like bad news to me. I wonder how broken this G5 ghc is for a G4. Perhaps it should be labelled G5 rather than PowerPC in the large print. I'm quite scared about trying to build ghc: I worry that it may involve confronting large areas of my ignorance. I'm running

Re: [Haskell-cafe] Cyclic Inclusions

2008-08-12 Thread C.M.Brown
Andrew, Thanks very much for your reponse. It was very helpful; this makes a lot of sense! Regards, Chris. On Mon, 11 Aug 2008 [EMAIL PROTECTED] wrote: > G'day all. > > Quoting "C.M.Brown" <[EMAIL PROTECTED]>: > > > Yes, I saw that, thanks! I guess this is because it's hard to compile a > > mut

Re: [Haskell-cafe] GLfloat on a Mac

2008-08-12 Thread Conor McBride
Hi Thanks for the quick response. On 12 Aug 2008, at 10:18, Brandon S. Allbery KF8NH wrote: On 2008 Aug 12, at 5:11, Conor McBride wrote: $ ghc -package GLUT HelloWorld.lhs -o HelloWorld Illegal instruction I'm using ghc 6.8.3 on a Mac PowerBook G4. Googling "OpenGL illegal instruction" pr

Re: [Haskell-cafe] GLfloat on a Mac

2008-08-12 Thread Thomas Davie
On 12 Aug 2008, at 11:11, Conor McBride wrote: Hi folks I thought I'd try a bit of OpenGL. Perhaps I should send this to the more specific list, but perhaps other people are, like me, trying out a variety of UI technology. I thought I'd give OpenGL a go, because I saw the name whizz by when I u

Re: [Haskell-cafe] GLfloat on a Mac

2008-08-12 Thread Malcolm Wallace
$ ghc -package GLUT HelloWorld.lhs -o HelloWorld Illegal instruction I'm using ghc 6.8.3 on a Mac PowerBook G4. Googling "OpenGL illegal instruction" produced an unending choice of horror stories. Not much help, but it compiles fine for me using ghc-6.8.3 on an iBook G4. I'm running MacOS 10

Re: [Haskell-cafe] GLfloat on a Mac

2008-08-12 Thread Brandon S. Allbery KF8NH
On 2008 Aug 12, at 5:11, Conor McBride wrote: $ ghc -package GLUT HelloWorld.lhs -o HelloWorld Illegal instruction I'm using ghc 6.8.3 on a Mac PowerBook G4. Googling "OpenGL illegal instruction" produced an unending choice of horror stories. What message am I not getting? Is there some cruci

[Haskell-cafe] GLfloat on a Mac

2008-08-12 Thread Conor McBride
Hi folks I thought I'd try a bit of OpenGL. Perhaps I should send this to the more specific list, but perhaps other people are, like me, trying out a variety of UI technology. I thought I'd give OpenGL a go, because I saw the name whizz by when I upgraded to 6.8.3. I found the tutorial and got co

Re: [Haskell-cafe] Recommended Haskell Books

2008-08-12 Thread haskell
Also the Beta Version of "Real World Haskell" looks promising: http://book.realworldhaskell.org/beta/index.html >On Sun, Aug 10, 2008 at 1:29 PM, Warren Aldred <[EMAIL PROTECTED]> wrote: >> I'm new to Haskell and looking for recommendations on introductory Haskell >> books. Online or offline. An