[Haskell-cafe] QuickCheck properties for Haskell98 Libraries?

2005-01-26 Thread John Meacham
I was curious if anyone had a collection of QuickCheck rules for testing the Haskell98 Prelude and libraries? It seems like it would be a useful thing to exist as a common resource. In particular, if there were overloaded rules for the various class properties then it would be easier to test wheth

Re: [Haskell-cafe] List manipulation

2005-01-26 Thread Sven Panne
Jules Bean wrote: [...] You rather want 'zipWith'. Documentation at: http://www.haskell.org/ghc/docs/latest/html/libraries/base/GHC.List.html ...along with lots of other funky list processing stuff. Just a small hint: Everything below "GHC" in the hierarchical libraries is, well, GHC-specific, mea

[Haskell-cafe] library documentation [was: File path programme]

2005-01-26 Thread Isaac Jones
"Georg Martius" <[EMAIL PROTECTED]> writes: > Hi, > > I think Isaac's idea is pretty nice, to have an easy way to add documentation > in a collaborative manner. > I have the following in mind: Well, I've added a much less glorious page than yours on the wiki: http://www.haskell.org/hawiki/Libra

[Haskell-cafe] fastest Fibonacci numbers in the West

2005-01-26 Thread William Lee Irwin III
Inspired by a discussion on freenode #haskell, I tried to write the fastest Fibonacci number function possible, i.e. given a natural number input n to compute F_n. mlton seems to enjoy substantially better speed despite equivalent algorithms; it may be enlightening to determine the causes of this,

Re: [Haskell-cafe] File path programme

2005-01-26 Thread Robert Dockins
Here is my first cut at this. The unix implementation mostly works, the windows one just has some datatypes sketched out, but it typechecks. -- module FilePath where import Data.Word (Word8) import Text.ParserCombinators.Parsec import Text.ParserCombinators.Parsec.Error import System (getArgs)

Re: [Haskell-cafe] File path programme

2005-01-26 Thread Robert Dockins
> I would say that all paths are relative to something, whether it's the > Unix root, or the current directory, or whatever. Therefore I would call > this something like PathStart, and add: > > | CurrentDirectory > | CurrentDirectoryOfWindowsDrive Char > | RootOfCurrentWindowsDrive

RE: [Haskell-cafe] using Map rather than FiniteMap

2005-01-26 Thread S. Alexander Jacobson
Ah, ok. So I ran the code with 10 items, 5 items, and 25000 items and got total memory in use of 28Mb, 15Mb, and 8Mb respectively. That comes to 260-280 bytes per record which is still an order of magnitude higher than the 20-30 bytes per record we would expect. On the other hand, I

Re: [Haskell-cafe] File path programme

2005-01-26 Thread John Meacham
On Wed, Jan 26, 2005 at 01:39:01PM -, Simon Marlow wrote: > On 25 January 2005 19:45, Duncan Coutts wrote: > > > On Tue, 2005-01-25 at 19:12 +, Ben Rudiak-Gould wrote: > >> My concern here is that someone will actually use the library once it > >> ships, with the following consequences: >

Re: [Haskell-cafe] What are the MonadPlus laws?

2005-01-26 Thread ajb
G'day all. Quoting Iavor Diatchki <[EMAIL PROTECTED]>: > This is not enough, at least in some cases. > Consider lists, and m being an infinite list, e.g. [1..] > Then we need that the inifinte concatenation of a empty lists > gives us the empty list which is not the case. It also doesn't work fo

Re: [Haskell-cafe] File path programme

2005-01-26 Thread Ben Rudiak-Gould
robert dockins wrote: > After the discussion about file paths over the last several days I went home and put together a quick trial implementation for unix file paths, with the idea of adding windows, SMB and maybe VMS (why not?) paths. This is great. Comments below. > data PathRoot >= UnixF

Re: [Haskell-cafe] File path programme

2005-01-26 Thread Georg Martius
Hi, I think Isaac's idea is pretty nice, to have an easy way to add documentation in a collaborative manner. I have the following in mind: A separate wiki which supports generating haddock documentation. Ideally one would see the haddock documentation as it is and would click to a function or typ

[Haskell-cafe] RE: Answers to Exercises in Craft of FP

2005-01-26 Thread Hamilton Richards
Dear Chris-- Many of us instructors who use (or have used) these textbooks (or others that have exercises) in university classes have found from experience that 1. Students learn best from exercises when they make a real effort to solve them before looking at the instructors' solutions. b. Stu

Re: [Haskell-cafe] RE: Answers to Exercises in Craft of FP

2005-01-26 Thread Christian Hofer
Maybe I am too much rooted in the German university system, where the students' autonomy is held high (against all evidence). But I never understood, why we - who have to learn the interesting stuff completely on our own, because bad luck supplies us only with Java teachers (although other prof

Re: [Haskell-cafe] Problem with Hyperlinking Haddock-documentation

2005-01-26 Thread Daniel Fischer
Am Mittwoch, 26. Januar 2005 21:49 schrieben Sie: > On Wed, 26 Jan 2005, Daniel Fischer wrote: > > Maybe somebody can enlighten me. > > > > When I run haddock and put the html files e.g. in directory ~/bar/foo, > > any references to things defined in the Prelude or the libraries are > > linked to,

Re: [Haskell-cafe] Problem with Hyperlinking Haddock-documentation

2005-01-26 Thread Henning Thielemann
On Wed, 26 Jan 2005, Daniel Fischer wrote: > Maybe somebody can enlighten me. > > When I run haddock and put the html files e.g. in directory ~/bar/foo, any > references to things defined in the Prelude or the libraries are linked to, > say ~/bar/foo/Prelude.html#t%3AFractional, which of course d

[Haskell-cafe] Looking for these libraries...

2005-01-26 Thread John Goerzen
Hi, I'm looking for libraries / interfaces to these systems from Haskell: LDAP ncurses zlib (the one in darcs doesn't suit my needs) bz2lib Thanks, John ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/ha

[Haskell-cafe] Problem with Hyperlinking Haddock-documentation

2005-01-26 Thread Daniel Fischer
Maybe somebody can enlighten me. When I run haddock and put the html files e.g. in directory ~/bar/foo, any references to things defined in the Prelude or the libraries are linked to, say ~/bar/foo/Prelude.html#t%3AFractional, which of course does not exist, because the documentation for the Pr

Re: [Haskell-cafe] Converting from Int to Double

2005-01-26 Thread Jorge Adriano Aires
> >> How can I convert an Int into a Double? > > > > You don't convert to, you convert from :-) > > The function 'fromIntegral' is probably what you want. > > And what function can I use to convert from Double to Int (the inverse of > fromIntegral) ? Use the functions in the RealFrac class. http:

Re: [Haskell-cafe] Converting from Int to Double

2005-01-26 Thread Stefan Holdermans
Dmitri, And what function can I use to convert from Double to Int (the inverse of fromIntegral) ? You should really have a look at the Prelude and the Standard Libraries. Well, it depends on *how* you want to convert. truncate :: (RealFrac a, Integral b) => a -> b round :: (RealFrac a, Integral b)

Re: [Haskell-cafe] Converting from Int to Double

2005-01-26 Thread Dmitri Pissarenko
How can I convert an Int into a Double? You don't convert to, you convert from :-) The function 'fromIntegral' is probably what you want. And what function can I use to convert from Double to Int (the inverse of fromIntegral) ? TIA Dmitri Pissarenko -- Dmitri Pissarenko Software Engineer http://dap

[Haskell-cafe] Non-blocking I/O (was: Re: Hugs vs GHC)

2005-01-26 Thread Marcin 'Qrczak' Kowalczyk
Glynn Clements <[EMAIL PROTECTED]> writes: >> > The point is that the Unix documentation does not consider the short >> > pause as data is read off your hard drive to be blocking. So that's why >> > select will always report that data is available when you use it with a >> > file handle. >> >> Is

Re: [Haskell-cafe] List manipulation

2005-01-26 Thread Dmitri Pissarenko
Thanks all for the help! -- Dmitri Pissarenko Software Engineer http://dapissarenko.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] What are the MonadPlus laws?

2005-01-26 Thread Iavor Diatchki
Hello, On Tue, 25 Jan 2005 22:49:06 -0500, Paul Hudak <[EMAIL PROTECTED]> wrote: > Good point; I suppose the constraint m /= _|_ > should be added to the law. This is not enough, at least in some cases. Consider lists, and m being an infinite list, e.g. [1..] Then we need that the inifinte concat

Re: [Haskell-cafe] RE: Answers to Exercises in Craft of FP

2005-01-26 Thread Gour
Paul Hudak ([EMAIL PROTECTED]) wrote: > I'm not sure how Simon Thompson feels, or other instructors using his or > my book, but a downside of posting all of the solutions is that the > problems cannot be assigned for homework. That's true. Being a self-learner I forgot that your books are use

Re: [Haskell-cafe] using Map rather than FiniteMap

2005-01-26 Thread S. Alexander Jacobson
On Tue, 25 Jan 2005, David Menendez wrote: Does having 'zipped' at the top level mean that the program is keeping the entire 100,000-element list in memory? I don't know, but I tested with zipped at the top, in the where, and it appears to make no performance or memory difference. Also, would pe

Re: [Haskell-cafe] List manipulation

2005-01-26 Thread Henning Thielemann
On Wed, 26 Jan 2005, Luca Marchetti wrote: > Hi > > why don't you try something like this: > > map (\(x,y) -> x+y) (zip [1,2,100] [2,3,500]) > > list comprehension would sum every element of the firs list with every > element of the second. If 'zipWith (+)' doesn't satisfy you, what about map

Re: [Haskell-cafe] List manipulation

2005-01-26 Thread Luca Marchetti
Hi why don't you try something like this: map (\(x,y) -> x+y) (zip [1,2,100] [2,3,500]) list comprehension would sum every element of the firs list with every element of the second. On Wed, 2005-01-26 at 17:39 +0100, Dmitri Pissarenko wrote: > Hello! > > I have two lists of Double with equal l

RE: [Haskell-cafe] using Map rather than FiniteMap

2005-01-26 Thread Simon Marlow
On 26 January 2005 16:42, S. Alexander Jacobson wrote: > On Wed, 26 Jan 2005, Simon Marlow wrote: >> When using the ordinary 2-generation collector, memory in use will >> tend to be 2-3 times larger than the actual residency, because this >> is a copying collector. > > Ok. Perhaps you want a diff

Re: [Haskell-cafe] List manipulation

2005-01-26 Thread Jules Bean
On 26 Jan 2005, at 16:39, Dmitri Pissarenko wrote: Hello! Hi Dmitri. Have a browse around the haskell wiki! There's loads of interesting information and example code there... add2Img summand1 summand2 = sum where sum = [ (x+y) | x <- summand1, y <- summand2 ] [3.0,4.0,501.0,4.0,5.0,502.0

Re: [Haskell-cafe] List manipulation

2005-01-26 Thread Stefan Holdermans
Dmitri, You're performing a point-wise addition Err ... what I meant was: you're *not* performing a point-wise addition, but instead ... Regards, Stefan ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haske

Re: [Haskell-cafe] List manipulation

2005-01-26 Thread Stefan Holdermans
Dmitri, I have two lists of Double with equal length and want to create a third one, in which each element is the sum of the corresponding element of the first list and the second list. add2Img :: [Double] -> [Double] -> [Double] add2Img summand1 summand2 = sum where sum = [ (x+y) | x <

Re: [Haskell-cafe] List manipulation

2005-01-26 Thread Gracjan Polak
Dmitri Pissarenko wrote: > Hello! > > I have two lists of Double with equal length and want to create a third one, > in which each element is the sum of the corresponding element of the first > list and the second list. > > If list1 is [1, 2, 100] and list2 is [2, 3, 500], then the result of the

RE: [Haskell-cafe] using Map rather than FiniteMap

2005-01-26 Thread S. Alexander Jacobson
On Wed, 26 Jan 2005, Simon Marlow wrote: When using the ordinary 2-generation collector, memory in use will tend to be 2-3 times larger than the actual residency, because this is a copying collector. Ok. Perhaps you want a different name for this item in the reports? On the other hand, I found 10

[Haskell-cafe] List manipulation

2005-01-26 Thread Dmitri Pissarenko
Hello! I have two lists of Double with equal length and want to create a third one, in which each element is the sum of the corresponding element of the first list and the second list. If list1 is [1, 2, 100] and list2 is [2, 3, 500], then the result of the operation I desire is [3, 5, 600]. I w

Re: [Haskell-cafe] using Map rather than FiniteMap

2005-01-26 Thread Christian Maeder
S. Alexander Jacobson wrote: zipped =zip [1..] [1..10]::[(Int,Int)] untup f (x,y) = f x y produce = foldr (untup Map.insert) Map.empty zipped fm = length $ Map.keys produce main = print $ fm Has this profile: example +RTS -p -K5M -RTS total time =5.10 secs

RE: [Haskell-cafe] using Map rather than FiniteMap

2005-01-26 Thread Simon Marlow
On 26 January 2005 14:29, S. Alexander Jacobson wrote: > Ah, ok. So I ran the code with 10 items, > 5 items, and 25000 items and got total memory > in use of 28Mb, 15Mb, and 8Mb respectively. That > comes to 260-280 bytes per record which is still > an order of magnitude higher than the

Re: [Haskell-cafe] RE: Answers to Exercises in Craft of FP

2005-01-26 Thread Paul Hudak
I'm not sure how Simon Thompson feels, or other instructors using his or my book, but a downside of posting all of the solutions is that the problems cannot be assigned for homework. I have many of the solutions to SOE problems, and could post them, but am wondering if it would be better to ma

Re: [Haskell-cafe] File path programme

2005-01-26 Thread robert dockins
After the discussion about file paths over the last several days I went home and put together a quick trial implementation for unix file paths, with the idea of adding windows, SMB and maybe VMS (why not?) paths. It is based on a Path class. I'll post it later when I get home. However, I wil

Re: [Haskell-cafe] File path programme

2005-01-26 Thread David Roundy
On Wed, Jan 26, 2005 at 01:39:01PM -, Simon Marlow wrote: > We can't add libraries in a point release, because there's no way for > code to use conditional compilation to test the patchlevel version > number. On the other hand, darcs doesn't rely on version numbers when looking for libraries (

Re: [Haskell-cafe] File path programme

2005-01-26 Thread David Roundy
On Wed, Jan 26, 2005 at 01:34:39PM -, Simon Marlow wrote: > ... We can therefore: > > (a) make System.IO.FilePath be the new type, which is different from, > and incompatible with, IO.FilePath. Similarly for > System.IO.openFile, System.Directory.removeFile, and so on. > > (b) o

RE: [Haskell-cafe] File path programme

2005-01-26 Thread Simon Marlow
On 25 January 2005 19:45, Duncan Coutts wrote: > On Tue, 2005-01-25 at 19:12 +, Ben Rudiak-Gould wrote: >> My concern here is that someone will actually use the library once it >> ships, with the following consequences: >> >> 1. Programs using the library will have predictable >> (exploit

Re: [Haskell-cafe] what is a stack overflow?

2005-01-26 Thread Tomasz Zielonka
On Wed, Jan 26, 2005 at 01:04:29PM -, Simon Marlow wrote: > On 25 January 2005 16:04, S. Alexander Jacobson wrote: > > Is there a way to profile stack usage using GHCi > > (without compiling) to find the problem? > > +RTS -xt -RTS will include the stack in a heap profile. See > > http://ww

RE: [Haskell-cafe] File path programme

2005-01-26 Thread Simon Marlow
[ moving to [EMAIL PROTECTED] ] On 26 January 2005 12:22, Malcolm Wallace wrote: >> Could we just punt this library for this release. After all we can >> add libraries in a later point release (eg 6.4.1) you just can't >> change existing APIs. > > FWIW, I agree with Duncan, Ben, and Peter, that

RE: [Haskell-cafe] using Map rather than FiniteMap

2005-01-26 Thread Simon Marlow
On 25 January 2005 23:27, S. Alexander Jacobson wrote: > Oops. It pays to check your checking code before > making posts like this. > > After actually running the correct test, I am > still getting semi-ridiculous space behavior > (6k/pair)! > > import qualified Map > zipped =zip [1..]

Re: [Haskell-cafe] Converting from Int to Double

2005-01-26 Thread Ketil Malde
Dmitri Pissarenko <[EMAIL PROTECTED]> writes: > How can I convert an Int into a Double? You don't convert to, you convert from :-) The function 'fromIntegral' is probably what you want. -kzm -- If I haven't seen further, it is by standing in the footprints of giants ___

RE: [Haskell-cafe] what is a stack overflow?

2005-01-26 Thread Simon Marlow
On 25 January 2005 16:04, S. Alexander Jacobson wrote: > Ok. I guessed I was producing a big expression > of the form > >addToFM (addToFM (addToFM (addToFM (addToFM ...) > > I tried to solve it by doing > >(addToFM $! fm) key val > > But still got an error. I then tried the same > wi

Re: [Haskell-cafe] Converting from Int to Double

2005-01-26 Thread Stefan Holdermans
Dmitri, How can I convert an Int into a Double? fromIntegral :: (Integral a, Num b) => a -> b HTH, Stefan ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Converting from Int to Double

2005-01-26 Thread Dmitri Pissarenko
Zitat von Henning Thielemann <[EMAIL PROTECTED]>: On Wed, 26 Jan 2005, Dmitri Pissarenko wrote: How can I convert an Int into a Double? fromIntegral Thanks! -- Dmitri Pissarenko Software Engineer http://dapissarenko.com ___ Haskell-Cafe mailing list Haske

Re: [Haskell-cafe] Converting from Int to Double

2005-01-26 Thread Henning Thielemann
On Wed, 26 Jan 2005, Dmitri Pissarenko wrote: > How can I convert an Int into a Double? fromIntegral ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Re: What are the MonadPlus laws?

2005-01-26 Thread Jules Bean
On 26 Jan 2005, at 08:41, Keean Schupke wrote: I cannot find any reference to MonadPlus in category theory. At a guess I would say that it was the same as a Monad except the operators are id and co-product (or sum)... That would mean the 'laws' would be exactly the same as a Monad, just with (0,

[Haskell-cafe] Converting from Int to Double

2005-01-26 Thread Dmitri Pissarenko
Hello! I have a list of integer numbers (grayscale values from 0 to 255) and want to convert them to a list of double numbers, so that each number is 0 <= x <= 1, where 0 is completely black and 1 is completely white. Before I convert the numbers, I need to convert them to a list of double values

Re: [Haskell-cafe] File path programme

2005-01-26 Thread Malcolm Wallace
> Could we just punt this library for this release. After all we can add > libraries in a later point release (eg 6.4.1) you just can't change > existing APIs. FWIW, I agree with Duncan, Ben, and Peter, that the new System.FilePath interface is broken, and the implementation more so. It would be

RE: [Haskell-cafe] Re: Can't do basic time operations with System.Time

2005-01-26 Thread Simon Marlow
On 25 January 2005 17:17, John Goerzen wrote: > On Tue, Jan 25, 2005 at 03:15:38PM -, Simon Marlow wrote: >> normalizeTimeDiff (and TimeDiff in general) is wrong. I wouldn't >> recommend using it. There's the TimeExts library in the lang >> package, which might be useful to you. > > I'm cur

Re: [Haskell-cafe] Re: What are the MonadPlus laws?

2005-01-26 Thread Ralf Laemmel
Jules Bean wrote: Are there any interesting programming uses of MonadPlus apart from 'calculations returning multiple values'.. i.e. lists/sets/multisets/maybe? Just a minor point ... You mention Maybe in the list above but I would like to wonder whether it is fully appropriate to associate it wi

Re: [Haskell-cafe] Re: What are the MonadPlus laws?

2005-01-26 Thread Jules Bean
On 26 Jan 2005, at 05:57, David Menendez wrote: Philip Wadler listed those as the laws he "would usually insist on" in a 1997 message[1]. [1] He also mentions two other possible, but problematic, laws: m >>= \x -> mzero =

Re: [Haskell-cafe] Re: Visual Programming Languages

2005-01-26 Thread Keean Schupke
Hmm, can't resist commenting on this one! Bayley, Alistair wrote: This was odd... Some cherry-picked quotes from the manifesto: http://alarmingdevelopment.org/index.php?p=5 - Visual languages are not the solution: ... common idea is to replace AST structures with some form of graphical diagram. ..

Re: [Haskell-cafe] How to convert from "IO String" to String

2005-01-26 Thread Dmitri Pissarenko
Thanks for your response! Now it works! -- Dmitri Pissarenko Software Engineer http://dapissarenko.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Visual Programming Languages

2005-01-26 Thread Stijn De Saeger
> This was odd... > > Some cherry-picked quotes from the manifesto: > http://alarmingdevelopment.org/index.php?p=5 > > - Visual languages are not the solution: ... common idea is to replace AST > structures with some form of graphical diagram. ... > > - Programming is not Mathematics > > -

RE: [Haskell-cafe] Re: Visual Programming Languages

2005-01-26 Thread Bayley, Alistair
> From: Stijn De Saeger [mailto:[EMAIL PROTECTED] > > Don't know if this is exactly what you were thinking of, but you may > want to have a look at > www.subtextual.org > > if you do, make sure you watch the demo. This was odd... Some cherry-picked quotes from the manifesto: http://alarming

Re: [Haskell-cafe] Re: What are the MonadPlus laws?

2005-01-26 Thread Keean Schupke
David Menendez wrote: Philip Wadler listed those as the laws he "would usually insist on" in a 1997 message[1]. [1] He also mentions two other possible, but problematic, laws: m >>= \x -> mzero == mzero m >>= \x -> k x `mp