[Haskell-cafe] reversing big list with constant heap space used

2007-05-16 Thread Sergey Perminov
How to solve task of reversing big list with constant heap space used? Amount of heap space used grows exponentially in following examples: 1: main = putStrLn.show.head $reverse [1..1000] 2 (GHC): import Data.List main = putStrLn.show.head $foldl' (flip (:)) [] [1..1000] 3 (GHC): impor

Re: [Haskell-cafe] Re: The danger of Monad ((->) r)

2007-05-16 Thread Tomasz Zielonka
On Tue, May 15, 2007 at 06:55:11AM -0700, Conal Elliott wrote: > You could also use mappend instead of concatStmts and keep the Database -> > IO () representation.- Conal You mean using the (Monoid b) => Monoid (a -> b) instance ? I can see that IO () makes a perfect Monoid, but there doesn't

[Haskell-cafe] Re: Type class help please

2007-05-16 Thread oleg
Adrian Hey wrote: > -- Instances of GT are instances of Eq -- > instance (GT map key, Eq a) => Eq (map a) where > map1 == map2 = assocsAscending map1 == assocsAscending map2 > ... > Overlapping instances for Eq [(key, a)] >arising from use of `==' at Test.hs:10:16-59 > Matching

Re: [Haskell-cafe] Converting CTime -> Int

2007-05-16 Thread Tomasz Zielonka
On Wed, May 16, 2007 at 12:38:55AM -0400, Brandon S. Allbery KF8NH wrote: > On May 16, 2007, at 0:35 , Rob Hoelz wrote: > > >wrapping returns time_t. I see that this maps to CTime in > >Foreign.C.Types, but I can't figure out how to convert it to an Int > >(or > >any other useful Haskell type,

Re: [Haskell-cafe] Re: The danger of Monad ((->) r)

2007-05-16 Thread Jules Bean
Tomasz Zielonka wrote: On Tue, May 15, 2007 at 06:55:11AM -0700, Conal Elliott wrote: You could also use mappend instead of concatStmts and keep the Database -> IO () representation.- Conal You mean using the (Monoid b) => Monoid (a -> b) instance ? I can see that IO () makes a per

Re: [Haskell-cafe] Re: The danger of Monad ((->) r)

2007-05-16 Thread Tomasz Zielonka
On Wed, May 16, 2007 at 09:28:31AM +0100, Jules Bean wrote: > Tomasz Zielonka wrote: > >You mean using the (Monoid b) => Monoid (a -> b) instance ? > >I can see that IO () makes a perfect Monoid, but there doesn't seem to > >be a standard instance for that. > > Indeed, all Monads are Monoids (that

Re: [Haskell-cafe] Re: The danger of Monad ((->) r)

2007-05-16 Thread Jules Bean
Tomasz Zielonka wrote: On Wed, May 16, 2007 at 09:28:31AM +0100, Jules Bean wrote: Tomasz Zielonka wrote: You mean using the (Monoid b) => Monoid (a -> b) instance ? I can see that IO () makes a perfect Monoid, but there doesn't seem to be a standard instance for that. Indeed, al

Re: [Haskell-cafe] Type class help please

2007-05-16 Thread Adrian Hey
Brandon S. Allbery KF8NH wrote: On May 16, 2007, at 0:57 , Adrian Hey wrote: -- GT class -- class Ord key => GT map key | map -> key where assocsAscending :: map a -> [(key,a)] -- Just 1 of many methods -- Instances of GT are instances of Eq -- Instances of Ord are instances of Eq, so defi

[Haskell-cafe] Re: Type class help please

2007-05-16 Thread Adrian Hey
[EMAIL PROTECTED] wrote: Adrian Hey wrote: -- Instances of GT are instances of Eq -- instance (GT map key, Eq a) => Eq (map a) where map1 == map2 = assocsAscending map1 == assocsAscending map2 ... Overlapping instances for Eq [(key, a)] arising from use of `==' at Test.hs:10:16-59

Re: [Haskell-cafe] Re: Type class help please

2007-05-16 Thread Adrian Hey
Adrian Hey wrote: [EMAIL PROTECTED] wrote: Adrian Hey wrote: -- Instances of GT are instances of Eq -- instance (GT map key, Eq a) => Eq (map a) where map1 == map2 = assocsAscending map1 == assocsAscending map2 ... Overlapping instances for Eq [(key, a)] arising from use of `==' a

[Haskell-cafe] Re: ANNOUNCE: Harpy -- run-time code generation library

2007-05-16 Thread apfelmus
Dirk Kleeblatt wrote: > apfelmus wrote: >> Dirk Kleeblatt wrote: >>> apfelmus wrote: I also think that having liftIO in the CodeGen-monad is plain wrong. I mean, CodeGen is a monad that generates code without any execution >>> >>> note that runCodeGen runs the code _generation_, executing

Re: [Haskell-cafe] reversing big list with constant heap space used

2007-05-16 Thread Henning Thielemann
On Wed, 16 May 2007, Sergey Perminov wrote: > How to solve task of reversing big list with constant heap space used? By avoiding 'reverse'? > Amount of heap space used grows exponentially in following examples: > > 1: > main = putStrLn.show.head $reverse [1..1000] Data.List.last I think

[Haskell-cafe] quiry

2007-05-16 Thread ashutosh dimri
how to convert a hexadecimal into base 10 integer using haskell . I have written a code but its not working for large values , please help ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: quiry

2007-05-16 Thread Stephane Bortzmeyer
On Wed, May 16, 2007 at 06:34:53PM +0530, ashutosh dimri <[EMAIL PROTECTED]> wrote a message of 34 lines which said: > how to convert a hexadecimal into base 10 integer using haskell . I > have written a code but its not working for large values , please > help Not showing the code you wrote w

Re: [Haskell-cafe] quiry

2007-05-16 Thread Pixel
"ashutosh dimri" <[EMAIL PROTECTED]> writes: > how to convert a hexadecimal into base 10 integer using haskell . I have > written a code but its not working for large values , please help from http://pleac.sourceforge.net/pleac_haskell/numbers.html#AEN118 : -- "read" handles both octal and hexa

[Haskell-cafe] Re: problem with implicit parameter

2007-05-16 Thread Grzegorz
Eric ukfsn.org> writes: > > Hi there, > > I've written the following program > > putchr = putChar ?d > > main = do > { c <- getChar > ; putchr with ?d = c} > I think you're supposed to use a let binding, like this: putchr :: (?d::Char) => IO () putchr = putChar ?d main = do c

[Haskell-cafe] Tail Recursion within the IO Monad

2007-05-16 Thread Rob Hoelz
Hello everyone, You may have seen my message about how I'm writing a binding to a C library. This is another question related to that. So, let's say I have a linked list implemented in C. Here's what its definition looks like: struct __linked_list { void *data; struct __linked_list *ne

Re: [Haskell-cafe] Tail Recursion within the IO Monad

2007-05-16 Thread Brandon S. Allbery KF8NH
On May 16, 2007, at 12:23 , Rob Hoelz wrote: And as long as I'm asking, is there some kind of monadic function composition operator? I'd like to clean up the above with something like peekCString . peek . linked_list_getdata... (=<<)? -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell

Re: [Haskell-cafe] Tail Recursion within the IO Monad

2007-05-16 Thread Rob Hoelz
"Brandon S. Allbery KF8NH" <[EMAIL PROTECTED]> wrote: > > On May 16, 2007, at 12:23 , Rob Hoelz wrote: > > > And as long as I'm asking, is there some kind of monadic function > > composition operator? I'd like to clean up the above with something > > like peekCString . peek . linked_list_getdat

Re: [Haskell-cafe] reversing big list with constant heap space used

2007-05-16 Thread David House
On 16/05/07, Sergey Perminov <[EMAIL PROTECTED]> wrote: How to solve task of reversing big list with constant heap space used? I think that as lists are singly-linked in Haskell, reversing a list will always be O(n) space. -- -David House, [EMAIL PROTECTED]

[Haskell-cafe] Books on Haskell

2007-05-16 Thread PR Stanley
Hi, Is Graham Hutton's book on Haskell Programming a good text for FP beginners? Paul ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Books on Haskell

2007-05-16 Thread Neil Mitchell
Hi Is Graham Hutton's book on Haskell Programming a good text for FP beginners? Yes. There is a review in The Monad Reader: http://www.haskell.org/sitewiki/images/0/03/TMR-Issue7.pdf From the abstract: "Do we need another introductory Haskell book? Is there anything new to be said or a b

Re: [Haskell-cafe] quiry

2007-05-16 Thread Albert Y. C. Lai
Pixel wrote: from http://pleac.sourceforge.net/pleac_haskell/numbers.html#AEN118 : -- "read" handles both octal and hexadecimal when prefixed with 0x or 0o -- here are versions adding the prefix and calling "read" hex s = read ("0x" ++ s) :: Integer oct s = read ("0o" ++ s) :: Integer -- hex "45

Re: [Haskell-cafe] Converting CTime -> Int

2007-05-16 Thread John Meacham
On Wed, May 16, 2007 at 12:38:55AM -0400, Brandon S. Allbery KF8NH wrote: > > On May 16, 2007, at 0:35 , Rob Hoelz wrote: > > >wrapping returns time_t. I see that this maps to CTime in > >Foreign.C.Types, but I can't figure out how to convert it to an Int > >(or > >any other useful Haskell typ

Re: [Haskell-cafe] reversing big list with constant heap space used

2007-05-16 Thread Jules Bean
David House wrote: On 16/05/07, Sergey Perminov <[EMAIL PROTECTED]> wrote: How to solve task of reversing big list with constant heap space used? I think that as lists are singly-linked in Haskell, reversing a list will always be O(n) space. You can do it in O(n^2) time and constant space,

Re: [Haskell-cafe] Tail Recursion within the IO Monad

2007-05-16 Thread Jules Bean
Rob Hoelz wrote: item <- linked_list_getdata listPtr next <- linked_list_next listPtr cStr <- peek item hStr <- peekCString cStr t <- linkedListToStringList next return (hStr : t) item <- linked_list_getdata listPtr next <-

Re: [Haskell-cafe] reversing big list with constant heap space used

2007-05-16 Thread Evan Laforge
I think that in every particular case you have to find out how to avoid 'reverse'. Especially if you have two 'reverse's like in reverse . dropWhile p . reverse there are more efficient solutions. Just from curiosity, what *is* an efficient way to do rDropWhile? Here's something which at lea

[Haskell-cafe] Imagining a G-machine

2007-05-16 Thread Albert Y. C. Lai
A native G-machine --- physical, or chemical, or biological, but not a repressed simulation over the imperative cpu-memory architecture --- is the dream of every lazy-functional programmer of great devotion. If only it became the dominant computing architecture! People would say, Haskell is hig

Re: [Haskell-cafe] Imagining a G-machine

2007-05-16 Thread John Meacham
I look forward to the day when the OS will notice that a binary was compiled from haskell, and therefore is provably not buggy due to haskells strong type system. So it happily turns off all memory protection and lets it run on the bare hardware at full speed. :) This is not entirely unreasonable,

Re: [Haskell-cafe] Imagining a G-machine

2007-05-16 Thread Stefan O'Rear
On Wed, May 16, 2007 at 03:41:30PM -0700, John Meacham wrote: > I look forward to the day when the OS will notice that a binary was > compiled from haskell, and therefore is provably not buggy due to > haskells strong type system. So it happily turns off all > memory protection and lets it run on t

Re: [Haskell-cafe] Imagining a G-machine

2007-05-16 Thread John Meacham
On Wed, May 16, 2007 at 03:47:07PM -0700, Stefan O'Rear wrote: > On Wed, May 16, 2007 at 03:41:30PM -0700, John Meacham wrote: > > I look forward to the day when the OS will notice that a binary was > > compiled from haskell, and therefore is provably not buggy due to > > haskells strong type syste

Re: [Haskell-cafe] Imagining a G-machine

2007-05-16 Thread Neil Mitchell
Hi It is worded as biotech but may as well be molecular computing or nanotech. biotech machines tend to be inaccurate, but highly parallel. Unfortunately the G machine is very un-parallel and requires 100% precision. Things like speculative evaluation may be more interesting. To add garbage

Re: [Haskell-cafe] Imagining a G-machine

2007-05-16 Thread Derek Elkins
Albert Y. C. Lai wrote: A native G-machine --- physical, or chemical, or biological, but not a repressed simulation over the imperative cpu-memory architecture --- is the dream of every lazy-functional programmer of great devotion. If only it became the dominant computing architecture! People w

Re: [Haskell-cafe] CUFP website

2007-05-16 Thread Donald Bruce Stewart
cyril.schmidt: > I noticed recently that the website of CUFP conference (Commercial Uses of > Function Programming), which used to be at http://www.galois.com/cufp, > is not accessible anymore. > > Does anybody know where it moved? Try http://cufp.galois.com/ -- Don _

[Haskell-cafe] ANNOUNCE: Dimensional 0.4 -- Statically checked physical dimensions

2007-05-16 Thread Björn Buckwalter
Dear all, I am pleased to announce version 0.4 of Dimensional (working name). Dimensional is a library providing data types for performing arithmetic with physical quantities and units. Information about the physical dimensions of the quantities/units is embedded in their types and the validity

[Haskell-cafe] Re: Type class help please

2007-05-16 Thread oleg
> Also, I suspect I'm still missing something important here, for > example I don't understand why, if it overlaps for [], it doesn't > overlap with other instances (like Maybe for example). Or am I > just not getting the error for Maybe because ghc stops after > the first error? One may think of