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

2005-01-25 Thread David Menendez
Ashley Yakeley writes: > In article <[EMAIL PROTECTED]>, > Jules Bean <[EMAIL PROTECTED]> wrote: > > > So, anyone? What are the laws that MonadPlus is supposed to satisfy? > > These are what I think they should be: > > mplus mzero a = a > mplus a mzero = a > mplus (mplus a b) c = mplus a

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

2005-01-25 Thread Ashley Yakeley
In article <[EMAIL PROTECTED]>, Jules Bean <[EMAIL PROTECTED]> wrote: > So, anyone? What are the laws that MonadPlus is supposed to satisfy? These are what I think they should be: mplus mzero a = a mplus a mzero = a mplus (mplus a b) c = mplus a (mplus b c) mzero >>= a = mzero (mplus

[Haskell-cafe] Re: Visual Programming Languages

2005-01-25 Thread Stijn De Saeger
Hi, 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. cheers, stijn. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mail

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

2005-01-25 Thread David Menendez
S. Alexander Jacobson writes: > After actually running the correct test, I am > still getting semi-ridiculous space behavior > (6k/pair)! > > import qualified Map > zipped =zip [1..] [1..10]::[(Int,Int)] > untup f (x,y) = f x y > produce = foldr (untup Map.insert) Map.empty

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

2005-01-25 Thread Paul Hudak
Good point; I suppose the constraint m /= _|_ should be added to the law. [EMAIL PROTECTED] wrote: The problem is this "law": m >>= \k -> mzero === mzero I think this "law" is untrue for _all_ MonadPlus instances, and you can trivially check this by setting m to bottom. Cheers, Andrew Bromage _

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

2005-01-25 Thread ajb
G'day all. Quoting Jules Bean <[EMAIL PROTECTED]>: > So, anyone? What are the laws that MonadPlus is supposed to satisfy? The problem is this "law": m >>= \k -> mzero === mzero I think this "law" is untrue for _all_ MonadPlus instances, and you can trivially check this by setting m to bott

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

2005-01-25 Thread S. Alexander Jacobson
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..] [1..10]::[(Int,Int)] untup f (x,y) = f x y produce = foldr (unt

Re: [Haskell-cafe] Re: [Haskell] Newbie : How come that cyclic recursive lists areefficient ?

2005-01-25 Thread Benjamin Franksen
On Tuesday 25 January 2005 14:11, David Barton wrote: > Benjamin Fransen writes: > > There *is no* difference between the two if one views them as pure > > mathematical values. Questions of run time speed or memory usage, i.e. > > efficiency (which your original question was about) are clearly outs

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

2005-01-25 Thread Alistair Bayley
Try > l = [ 0, 255, 255, 255, 255, 0, 255, 255, 255, 255 > , 0, 255, 255, 255, 255, 0] > testConvertToList01 = TestCase $ do > img <- readImage "../data-test/diagonalImage.pgm" > assertEqual "" l (convertToList img) A TestCase is just an IO action (take a look at the HUnit source code). Ali

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

2005-01-25 Thread Jorge Adriano Aires
> Just did a search after my last post and learned > that FiniteMap is bad. Discoverd that Data.Map is > the intended replacement. Downloaded it and > modified it to work with 6.2. Blazingly fast! > > Yay. Hi, just curious, How much trouble was getting it to work with ghc 6.2 and adapting you

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

2005-01-25 Thread S. Alexander Jacobson
I didn't find any such information. I just decided to look at the FiniteMap source code in CVS and discovered in the comments that it was deprecated in favor of Data.Map. So I downloaded the new Data.Map and Data.Set and ran the code I posted before. I executed basically instantly and used

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

2005-01-25 Thread Ketil Malde
"S. Alexander Jacobson" <[EMAIL PROTECTED]> writes: > Just did a search after my last post and learned that FiniteMap is > bad. Discoverd that Data.Map is the intended replacement. Downloaded > it and modified it to work with 6.2. Blazingly fast! Oh? I was aware that Data.Map was supposed to

Re: [Haskell-cafe] File path programme

2005-01-25 Thread Isaac Jones
Mark Carroll <[EMAIL PROTECTED]> writes: > On Tue, 25 Jan 2005, Marcin 'Qrczak' Kowalczyk wrote: > (snip) >> If problems are in the implementation but the interface is right, then >> the module should be provided. It can be fixed later. > (snip) > > A lot of the Haskell libraries are sufficiently

Re: [Haskell-cafe] wxFruit examples

2005-01-25 Thread Mark Carroll
On Tue, 25 Jan 2005, John Peterson wrote: > The wxFruit effort was a senior project that focused pretty much > exclusively on the paddleball game. It didn't really create any > software that we intend to maintain and distribute. Still, is wxFruit the best shot we have at being The Way Forward fo

Re: [Haskell-cafe] File path programme

2005-01-25 Thread Mark Carroll
On Tue, 25 Jan 2005, Marcin 'Qrczak' Kowalczyk wrote: (snip) > If problems are in the implementation but the interface is right, then > the module should be provided. It can be fixed later. (snip) A lot of the Haskell libraries are sufficiently poorly documented that I work out what they do by exp

Re: [Haskell-cafe] Visual Functional Languages

2005-01-25 Thread Hamilton Richards
At 6:32 PM + 2005/1/25, José Miguel Vilaça wrote: Hi I'm searching for Visual Functional Languages, i.e. languages in which the programmer does diagrams instead of writing textual code. The only language I have found until now is VFPE of Joel Kelso's PhD thesis

[Haskell-cafe] using Map rather than FiniteMap

2005-01-25 Thread S. Alexander Jacobson
Just did a search after my last post and learned that FiniteMap is bad. Discoverd that Data.Map is the intended replacement. Downloaded it and modified it to work with 6.2. Blazingly fast! Yay. Please ignore the prior message. -Alex- __

Re: [Haskell-cafe] wxFruit examples

2005-01-25 Thread John Peterson
Hi there! The wxFruit effort was a senior project that focused pretty much exclusively on the paddleball game. It didn't really create any software that we intend to maintain and distribute. I have a couple of students working on a continuation of this but I don't expect to release anything for

Re: [Haskell-cafe] File path programme

2005-01-25 Thread Duncan Coutts
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 (exploitable) > bugs in pathname handling. > > 2. It will

[Haskell-cafe] wxFruit examples

2005-01-25 Thread Dmitri Pissarenko
Hello! I want to learn to program with wxFruit UI framework. http://zoo.cs.yale.edu/classes/cs490/03-04b/bartholomew.robinson/ Does someone know about any examples apart from paddle ball game? I would like to start with a simple application, which takes a the name of an image file as a command-

Re: [Haskell-cafe] File path programme

2005-01-25 Thread Ben Rudiak-Gould
Jules Bean wrote: > [...] it is an extension of the notion that "/foo/" and "/foo" > refer to the same directory. (Except, apparently, in the presence > of symbolic links... or so I have some vague memory) Yes, "/foo/" is equivalent to "/foo/.", which is not always the same as "/foo". If "/foo" is

[Haskell-cafe] Re: File path programme

2005-01-25 Thread Peter Simons
Ben Rudiak-Gould writes: > 1. Programs using the library will have predictable > (exploitable) bugs in pathname handling. > 2. It will never be possible to change the current weird > behavior, because it might break legacy code. I completely agree. Handling file path specifications

Re: [Haskell-cafe] File path programme

2005-01-25 Thread Marcin 'Qrczak' Kowalczyk
Ben Rudiak-Gould <[EMAIL PROTECTED]> writes: > >Doing a reasonable job on System.FilePath, even if it isn't > >perfect, will help prevent lots of applications from falling into > >common traps, and help make more code portable. > > But the library code itself falls into the same traps! It's a g

Re: [Haskell-cafe] Newbie Monad question

2005-01-25 Thread Henning Thielemann
On Tue, 25 Jan 2005, [iso-8859-1] Simon Ulfsbäcker wrote: > Hi, > > I'm a functional programming newbie trying to get the hang of the concept of > Monads, but one thing about bind puzzles me. Let's take an IO Monad-example: > > readLn >>= \i -> readLn >>= \j -> return (i + j) > > I fail to see ho

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

2005-01-25 Thread Dmitri Pissarenko
Hello! Thanks for your answer! You probably want something like... l = [0, 255, 255, 255, 255, 0, 255, 255, 255, 255, 0, 255, 255, 255, 255, 0] testConvertToList01 = do img <- readImage "../data-test/diagonalImage.pgm" return $ TestCase $ assertEqual "" l (convertToList im

[Haskell-cafe] Newbie Monad question

2005-01-25 Thread Simon Ulfsbäcker
Hi, I'm a functional programming newbie trying to get the hang of the concept of Monads, but one thing about bind puzzles me. Let's take an IO Monad-example: readLn >>= \i -> readLn >>= \j -> return (i + j) I fail to see how (\j -> return (i + j)) can know about the value of i. Isn't just the value

Re: [Haskell-cafe] File path programme

2005-01-25 Thread Ben Rudiak-Gould
Simon Marlow wrote: >Doing a reasonable job on System.FilePath, even if it isn't perfect, >will help prevent lots of applications from falling into common traps, >and help make more code portable. But the library code itself falls into the same traps! It's a great example of the kind of code we sh

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

2005-01-25 Thread Paul Hudak
I believe that these are the relevant laws of class MonadPlus: m >>= (\x -> mzero) = mzero mzero >>= m = mzero m `mplus` mzero = m mzero `mplus` m = m You can get some intuition for this by thinking of mplus as +, mzero as 0, and >>= as multiplication. I haven't follow much at all

Re: [Haskell-cafe] Visual Functional Languages

2005-01-25 Thread Shae Matijs Erisson
"Josà Miguel VilaÃa" <[EMAIL PROTECTED]> writes: > I'm searching for Visual Functional Languages, i.e. languages in which the > programmer does diagrams instead of writing textual code. > The only language I have found until now is VFPE of Joel Kelso's PhD thesis > http://www.csse.uwa.edu.au/~joel

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

2005-01-25 Thread Dmitri Pissarenko
Hello! I have a function, which reads the contents of a file into a string: readImage :: String -> IO String readImage filename = do fileContent <- readFile filename return fileContent The result of this function is fed into another function, which converts the string content o

[Haskell-cafe] Visual Functional Languages

2005-01-25 Thread José Miguel Vilaça
Hi   I’m searching for Visual Functional Languages, i.e. languages in which the programmer does diagrams instead of writing textual code.   The only language I have found until now is VFPE of Joel Kelso's PhD thesis http://www.csse.uwa.edu.au/~joel/vfpe/     Does anyone know other l

[Haskell-cafe] What are the MonadPlus laws?

2005-01-25 Thread Jules Bean
So, anyone? What are the laws that MonadPlus is supposed to satisfy? The obvious ones are that if MonadPlus m then for all types a, (m a) should be a monoid. But, what about the others, because IO does not appear to satisfy a >> mzero == mzero Jules __

Re: [Haskell-cafe] Haskell programs in C

2005-01-25 Thread Jérémy Bobbio
On Tuesday 25 January 2005 14:48, Dmitri Pissarenko wrote: > Imagine I wrote a program in Haskell and want to use it on a > microcontroller device. You should take a look at Malcolm Wallace's thesis : ftp://ftp.cs.york.ac.uk/pub/malcolm/thesis.html He worked on using Haskell in embedded computer

[Haskell-cafe] ~1k memory per elem for FiniteMap!!!?

2005-01-25 Thread S. Alexander Jacobson
Is it possible/reasonable that Data.FiniteMap takes around 1k per element? I just profiled this code: import Data.FiniteMap zipped =zip [1..] [1..5] addFMItem (index,item) fm = (addToFM $! fm) item index produce = foldr addFMItem emptyFM zipped fm = take 1 $ keysFM produce

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

2005-01-25 Thread John Goerzen
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 curious about that package. It's in my ghc source tree but

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

2005-01-25 Thread S. Alexander Jacobson
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 with the wrapper code, but still got the error. Is there a way to profile stack us

Re: [Haskell-cafe] Hugs for Zaurus

2005-01-25 Thread Graham Klyne
At 11:31 24/01/05 -0600, John Goerzen wrote: On Mon, Jan 24, 2005 at 04:48:49PM +, Graham Klyne wrote: > At 20:15 21/01/05 +, John Goerzen wrote: > >I have built a fixed Hugs for the Zaurus PDA running the OpenZaurus > >distribution. Download here: > >http://quux.org/devel/zaurus/hugs_hugs

Re: [Haskell-cafe] "Parsing" a string

2005-01-25 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 is a stack overflow?

2005-01-25 Thread S. Alexander Jacobson
Also, how do I get the profiler to tell me whether I am consuming heap or stack? -Alex- On Mon, 24 Jan 2005, Iavor Diatchki wrote: hi, it may happen for different reasons, but a common one is when you have a foldl pattern (programming with an accumulator), for example like this: sumList1 [] accum

Re: [Haskell-cafe] Re: what is inverse of mzero and return?

2005-01-25 Thread Jorge Adriano Aires
> Jules Bean wrote: > > It's in Control.Monad.Error. Not documented though. > > > > Jules > > Ahh, so it is: > > instance MonadPlus IO where > mzero = ioError (userError "mzero") > m `mplus` n = m `catch` \_ -> n > > So, the author of this obviously subscribed to the view tha

[Haskell-cafe] Recantation and updated views

2005-01-25 Thread Daniel Fischer
Okay, I was stupid, having ignored my own advice to always look at the sources. I stupidly assumed IO a was not a function-type. On retrospect, I can't imagine, how that came to me. I've looked it up now, and for ghc, I found newtype IO a = IO (State# RealWorld -> (# State# RealWorld, a #)) whi

RE: [Haskell-cafe] File path programme

2005-01-25 Thread Simon Marlow
On 24 January 2005 22:11, Ben Rudiak-Gould wrote: > Please, let's not ship this with the hierarchical libraries. It's not > ready for prime time. We decided to provide this library for purely pragmatic reasons. It's better than nothing. http://www.haskell.org/pipermail/libraries/2004-October/

Re: [Haskell-cafe] Haskell programs in C

2005-01-25 Thread Peter G. Hancock
> Ben Rudiak-Gould wrote (on Tue, 25 Jan 2005 at 14:49): > Mark Carroll wrote: >> Wasn't there someone mentioning here a little while ago >> some project where they strip most of System.* from the libraries and get >> something that might be suitable for embedded applications?

RE: [Haskell-cafe] can't 'make install-docs'

2005-01-25 Thread Simon Marlow
On 21 January 2005 23:24, Daniel Fischer wrote: > I've just installed ghc-6.2.2, but couldn't get the docs made. > I got the following: > Text/Regex.raw-hs Text/Regex/Posix.raw-hs Text/Show.raw-hs > Text/Show/Functions.raw-hs \ > --package=base \ > --dump-interface=base.haddock \ >

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

2005-01-25 Thread Simon Marlow
On 21 January 2005 21:50, John Goerzen wrote: > On 2005-01-21, Peter Simons <[EMAIL PROTECTED]> wrote: >>> 24 * ((fromIntegral $ tdDay td) + >>> 30 * ((fromIntegral $ tdMonth td) + >>> 365 * (fromIntegral $ tdYear td) >> >> I w

Re: [Haskell-cafe] Haskell programs in C

2005-01-25 Thread Ben Rudiak-Gould
Mark Carroll wrote: >Wasn't there someone mentioning here a little while ago >some project where they strip most of System.* from the libraries and get >something that might be suitable for embedded applications? What was that >called? Anyone remember? hOp: http://www.macs.hw.ac.uk/~sebc/hOp/ --

Re: [Haskell-cafe] Re: what is inverse of mzero and return?

2005-01-25 Thread Keean Schupke
Jules Bean wrote: It's in Control.Monad.Error. Not documented though. Jules Ahh, so it is: instance MonadPlus IO where mzero = ioError (userError "mzero") m `mplus` n = m `catch` \_ -> n So, the author of this obviously subscribed to the view that side-effects are not counted w

Re: [Haskell-cafe] "Parsing" a string

2005-01-25 Thread Mark Carroll
On Tue, 25 Jan 2005, Dmitri Pissarenko wrote: (snip) > I need to read the height and width, then "cut" them from the string, create > an array (or finite map) of Int's (for this I need to know the height and > width), and then recursively process the pixel values (i. e. put them into the > array).

Re: [Haskell-cafe] Re: what is inverse of mzero and return?

2005-01-25 Thread Jules Bean
On 25 Jan 2005, at 13:20, Keean Schupke wrote: f = getChar >>= (\a -> if a == "F" then mzero else return a) In this case if the LHS returns "F" the LHS should not have been run... this contradicts itself, so this is a non option I guess. Good paradox. That is what is upsetting me, too.

Re: [Haskell-cafe] Haskell programs in C

2005-01-25 Thread Mark Carroll
On Tue, 25 Jan 2005, Dmitri Pissarenko wrote: > Is it possible (at least theoretically) to write a program in Haskell, then > convert it into C and then compile the C program into an executable, which is > optimized for the microcontroller? I would guess so. Wasn't there someone mentioning here a

Re: [Haskell-cafe] "Parsing" a string

2005-01-25 Thread Henning Thielemann
On Tue, 25 Jan 2005, Dmitri Pissarenko wrote: > The string is structured as follows: > > > P2 > # comment > # comment > 320243255 > 130 130 130 130 130 > 130 130 130 130 130 > What about preprocessing with 'lines' ? ___ Haskell-Cafe mailing list Has

[Haskell-cafe] Haskell programs in C

2005-01-25 Thread Dmitri Pissarenko
Hello! Imagine I wrote a program in Haskell and want to use it on a microcontroller device. AFAIK, Haskell programs are first converted to C code and then compiled by gcc. Is it possible (at least theoretically) to write a program in Haskell, then convert it into C and then compile the C program

[Haskell-cafe] "Parsing" a string

2005-01-25 Thread Dmitri Pissarenko
Hello! I have to read a PGM image and transform it into a list of Int values. I read the image (this is an ASCII PGM format) using the readFile function and get a string with the contents of the file. This string contains height and widht of the image at the beginning, and then the pixel values

[Haskell-cafe] Haskell and palm pilots.

2005-01-25 Thread Matthew Roberts
There was work done on haskell for the palmos done my Tony Sloane and Matt Tarnawski at Macquarie University. In the end, Matt mangaged to demonstrate a working palm runtime (based on nhc I believe) but in the process discovered all kinds of reasons trying to get a haskell interpreter on a palm

Re: [Haskell-cafe] Re: what is inverse of mzero and return?

2005-01-25 Thread Keean Schupke
Jules Bean wrote: Well, mzero isn't a return value in the IO monad, it's an exception. But yes, I agree with you that the (plausible) laws I have seen for MonadPlus seem to say that mzero should ignore the actions. But this in practice is not how IO behaves. Jules I can see three possible solu

Re: [Haskell-cafe] Re: what is inverse of mzero and return?

2005-01-25 Thread Jorge Adriano Aires
On Tuesday 25 January 2005 02:25, Jan-Willem Maessen wrote: > On Jan 24, 2005, at 8:53 PM, Jorge Adriano Aires wrote: > > And it would say nothing about things like: > > return 4 >> return 5 ==?== return 5 > > I can live with it. > > I feel obliged to point out (because the repeated references to

[Haskell-cafe] Re: [Haskell] Newbie : How come that cyclic recursive lists areefficient ?

2005-01-25 Thread David Barton
Benjamin Fransen writes: > There *is no* difference between the two if one views them as pure > mathematical values. Questions of run time speed or memory usage, i.e. > efficiency (which your original question was about) are clearly outside the > realm of pure values, and thus we may perceive them

[Haskell-cafe] Re: File path programme

2005-01-25 Thread Krasimir Angelov
On Tue, 25 Jan 2005 13:32:29 +0200, Krasimir Angelov <[EMAIL PROTECTED]> wrote: > >> What about splitFileExt "foo.bar."? ("foo", "bar.") or ("foo.bar.", "")? > > > > The latter makes more sense to me, as an extension of the first case > > you give and splitting "foo.tar.gz" to ("foo.tar", "gz"). >

Re: [Haskell-cafe] Re: what is inverse of mzero and return?

2005-01-25 Thread Jules Bean
On 25 Jan 2005, at 12:22, Jules Bean wrote: The concrete example for [] is: concat . (map concat) should be the same (on all values of all types [a]) as concat . concat ..tiny correction, sorry. 'On all values of all types [[[a]]]'. ___ Haskell-Cafe maili

Re: [Haskell-cafe] Re: what is inverse of mzero and return?

2005-01-25 Thread Jules Bean
On 25 Jan 2005, at 11:56, Keean Schupke wrote: I guess I am trying to understand how the Monad laws are derived from category theory... I can only find referneces to associativity being required. Associativity and left and right unit laws. Monads are defined on functors, so the associativity just

Re: [Haskell-cafe] Re: what is inverse of mzero and return?

2005-01-25 Thread Ross Paterson
On Mon, Jan 24, 2005 at 09:23:29PM +0100, Daniel Fischer wrote: | We face a severe problem here, not only that IO a is not an instance of Eq, | which takes this whole discussion outside the realm of Haskell, on top of that | we find the horrible fact that x /= x may be true in the IO Monad, conside

Re: [Haskell-cafe] Re: what is inverse of mzero and return?

2005-01-25 Thread Jules Bean
On 25 Jan 2005, at 11:49, Keean Schupke wrote: Jules Bean wrote: A monad T is a (endo)functor T : * -> * where * is the category of types, together with a multiplication mu and a unit eta. So, * is the category of Types, and functions on type (which map values to values), and T is an endofunctor

Re: [Haskell-cafe] Re: what is inverse of mzero and return?

2005-01-25 Thread Keean Schupke
Ashley Yakeley wrote: Every morphism in any category has a "from" object and a "to" object: it is a morphism from object to object. In the "Haskell category", a function of type 'A -> B' is a morphism from object (type) A to object B. But in category theory, just because two morphisms are both f

Re: [Haskell-cafe] File path programme

2005-01-25 Thread David Roundy
On Tue, Jan 25, 2005 at 01:32:29PM +0200, Krasimir Angelov wrote: > > splitFileName "/foo/bar" ==> ("/foo","bar") > > splitFileName "/foo//bar" ==> ("/foo/","bar") > >(definitely a bug) > > Is "/foo//bar" valid file path and what does "//" mean? "//" means the same thing as "/". In unix yo

Re: [Haskell-cafe] File path programme

2005-01-25 Thread Jules Bean
On 25 Jan 2005, at 11:32, Krasimir Angelov wrote: splitFileName "/foo/bar" ==> ("/foo","bar") splitFileName "/foo//bar" ==> ("/foo/","bar") (definitely a bug) Is "/foo//bar" valid file path and what does "//" mean? pathParents "/foo///bar" ==> ["/","/foo","/foo","/foo","/foo/bar"] Again what

Re: [Haskell-cafe] Re: what is inverse of mzero and return?

2005-01-25 Thread Keean Schupke
Jules Bean wrote: No. Well: they are functions 'on' types, but functions 'on' types map values to values. Analogy: In the category of sets and functions, the objects are sets and the morphisms are functions. The functions --- from sets to sets --- take objects in one set to objects in another s

[Haskell-cafe] Re: what is inverse of mzero and return?

2005-01-25 Thread Ashley Yakeley
In article <[EMAIL PROTECTED]>, Keean Schupke <[EMAIL PROTECTED]> wrote: > I think I see, but if the objects are types, arn't the morphisms functions > on types not values? Every morphism in any category has a "from" object and a "to" object: it is a morphism from object to object. In the "Hask

[Haskell-cafe] File path programme

2005-01-25 Thread Krasimir Angelov
Hello, Guys The System.FilePath might not be perfect and might not handle some unusual cases very well. Most of functions in this module are collected from Cabal/Alex/Happy/Haddock. Some of these tools already use their own functions for file path handling. Special care was taken to make them more

Re: [Haskell-cafe] Re: what is inverse of mzero and return?

2005-01-25 Thread Jules Bean
On 25 Jan 2005, at 10:32, Keean Schupke wrote: I think I see, but if the objects are types, arn't the morphisms functions on types not values? No. Well: they are functions 'on' types, but functions 'on' types map values to values. Analogy: In the category of sets and functions, the objects are

Re: [Haskell-cafe] Re: what is inverse of mzero and return?

2005-01-25 Thread Keean Schupke
I think I see, but if the objects are types, arn't the morphisms functions on types not values? Keean. Ashley Yakeley wrote: In article <[EMAIL PROTECTED]>, Keean Schupke <[EMAIL PROTECTED]> wrote: I am sure monads in Haskell (and other functional languages like ML) are defined on types not

[Haskell-cafe] Re: what is inverse of mzero and return?

2005-01-25 Thread Ashley Yakeley
In article <[EMAIL PROTECTED]>, Keean Schupke <[EMAIL PROTECTED]> wrote: > I am sure monads in Haskell (and other functional languages like ML) are > defined on types not values. The objects of the category are types. The morphisms on the category are functions. Two functions are the same if t

Re: [Haskell-cafe] Re: what is inverse of mzero and return?

2005-01-25 Thread Keean Schupke
Daniel Fischer wrote: I think, 1. should be acceptable to everybody, and 2. as a principle too, only the question of which effects are relevant needs to be answered. It's plain that not all measurable effects are relevant. My inclination to ignore the side-effects stemmed from the (irrational) d

Re: [Haskell-cafe] Re: what is inverse of mzero and return?

2005-01-25 Thread Jules Bean
On 25 Jan 2005, at 09:30, Daniel Fischer wrote: putStrLn "hello" >>= (\_ -> mzero) === (\_ -> mzero) () ...no. That last identity holds for 'return ()' but not for 'putStrLn "hello"'. The monad law is a law for 'return' not for arbitrary things. Jules ___

Re: [Haskell-cafe] what is inverse of mzero and return?

2005-01-25 Thread Daniel Fischer
Am Dienstag, 25. Januar 2005 10:17 schrieben Sie: > Or rather: > getChar :: (?x :: RealWorld) -> (Char,RealWorld) > > Which is the whole point of IO, no? So yes, that's the essence. > > > if you insist on getChar being of > > pure type IO Char, I still have a problem. > > Not if "pure typ

[Haskell-cafe] Re: what is inverse of mzero and return?

2005-01-25 Thread Daniel Fischer
Am Dienstag, 25. Januar 2005 03:25 schrieb Jan-Willem Maessen: > I feel obliged to point out (because the repeated references to the > question are driving me up the wall) that this simple equality holds in > every monad: > > return 4 >> return 5 > > === (definition of >>) > > return 4 >>= \_ -> re

Re: [Haskell-cafe] Re: what is inverse of mzero and return?

2005-01-25 Thread Ketil Malde
Daniel Fischer <[EMAIL PROTECTED]> writes: >> getChar = 'the action that, when executed, reads a character from stdin and >> returns it' > I still say, getChar is not a well defined value of IO Char. By this line of reasoning, I think any imperative, real-world interacting program is ill-defined

Re: [Haskell-cafe] Re: what is inverse of mzero and return?

2005-01-25 Thread Jules Bean
On 25 Jan 2005, at 08:53, Daniel Fischer wrote: Am Montag, 24. Januar 2005 22:59 schrieb Benjamin Franksen: getChar = 'the action that, when executed, reads a character from stdin and returns it' and that holds whether we just consider the values returned by an IO action or take the action perfor

[Haskell-cafe] Re: what is inverse of mzero and return?

2005-01-25 Thread Daniel Fischer
Am Montag, 24. Januar 2005 22:59 schrieb Benjamin Franksen: > I wonder how you derive at this strange conclusion. Of course, getChar == > getChar is always true. Now we clearly have to say what we mean by this > kind of equality. Well, there is an operational model of the program inside > its envir