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

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] 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] 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

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] 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

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 ___

[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

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

2005-01-24 Thread Ketil Malde
Daniel Fischer <[EMAIL PROTECTED]> writes: >> 'everything matters' is wrong even for IO actions, because the >> actual value returned when the action is executed is completely >> irrelevant to the IO action's identity. > Now that I cannot swallow, that would mean > return 4 == return 5. I would

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

2005-01-24 Thread ajb
G'day all. Quoting Daniel Fischer <[EMAIL PROTECTED]>: > The sad truth is that IO actions in general aren't well defined entities > (unless we index them with the space-time-coordinates of their invocation). Not really. One of the ways that IO used to be implemented (still might be on some Hask

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

2005-01-24 Thread Jan-Willem Maessen
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 the question are driving me up the wall) that this simple equality holds in

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

2005-01-24 Thread Jorge Adriano Aires
(Sorry about the recurrent self answers) > Maybe (not sure) it is sensible to > sapecify return::(a -> IO a), as an action with no side effects such that > return x === return x iff x === x. return x === return y iff x === y<-- this is what I meant to write. But even that is not enough, s

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

2005-01-24 Thread Jorge Adriano Aires
> >This isn't obvious to me. So x is an action, and it does not always > > produces the same side effects when executed. But why should that make > > x/=x? It is the same action, it gets one line from the input, and then > > prints it... > > OK, but then the different side-effects could not be use

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

2005-01-24 Thread Daniel Fischer
Am Montag, 24. Januar 2005 22:59 schrieb Benjamin Franksen: > Both are wrong. 'just the result matters' is the correct POV for functions, > but not for IO actions. 'everything matters' is wrong even for IO actions, > because the actual value returned when the action is executed is completely > irre

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

2005-01-24 Thread Daniel Fischer
Am Dienstag, 25. Januar 2005 00:29 schrieb Jorge Adriano Aires: >> x = getLine >>= putStrLn >This isn't obvious to me. So x is an action, and it does not always produces >the same side effects when executed. But why should that make x/=x? It is the >same action, it gets one line from the input, a

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

2005-01-24 Thread Jorge Adriano Aires
> A constant c :: a is just morphism(function) c : 0 -> a, where 0 is the > initial object (empty set). --- Rant2 "correction" Opss I messed up here. Should be terminal should 1-> a (terminal object/unit set). At least that's how I usually think of constants in haskell 1 is ()... so I thin

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

2005-01-24 Thread Daniel Fischer
Am Montag, 24. Januar 2005 20:25 schrieb Keean Schupke: > I think the endofunctors are defined on the types, not the values > though. So the object of the category is the endofunctor (Type -> Type), > and unit and join are the identity and binary associative operator on > which a Monad is defined.

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

2005-01-24 Thread Jorge Adriano Aires
> 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, > consider > > x = getLine >>= putStrLn > > or anything similar --

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

2005-01-24 Thread Benjamin Franksen
On Monday 24 January 2005 21:23, Daniel Fischer wrote: > Am Montag, 24. Januar 2005 11:47 schrieb Jules Bean: > > > > Here are the three monad laws as written on the nomaware site: > > > > 1. (return x) >>= f == f x > > 2. m >>= return == m > > 3. (m >>= f) >>= g == m >>

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

2005-01-24 Thread Daniel Fischer
Am Montag, 24. Januar 2005 11:47 schrieb Jules Bean: > Here are the three monad laws as written on the nomaware site: > > 1. (return x) >>= f == f x > 2. m >>= return == m > 3. (m >>= f) >>= g == m >>= (\x -> f x >>= g) > > Taking rule 1, we do not simply mean that

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

2005-01-24 Thread Keean Schupke
Jules Bean wrote: I've lost track of what you mean by 'this case' and indeed of what you mean by 'join' (did you mean mplus? the word join is normally used for the operation of type m (m a) -> m a, which is not often used directly in haskell) However, even addressing your point about endofuncto

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

2005-01-24 Thread Jorge Adriano Aires
> Right, but we are dealing with the type system here. Remember Haskell > monoids are functors on types, not on values ... (ie the base objects the > 'category theory' is applied to are the types not the values)... > > Therefore we only consider the types when considering Monads. How so? Functors

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

2005-01-24 Thread Jules Bean
On 24 Jan 2005, at 18:18, Keean Schupke wrote: Ashley Yakeley wrote: If you remember your category theory, you'll recall that two morphisms are not necessarily the same just because they're between the same two objects. For instance, the objects may be sets, and the morphisms may be functions b

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

2005-01-24 Thread Keean Schupke
Ashley Yakeley wrote: If you remember your category theory, you'll recall that two morphisms are not necessarily the same just because they're between the same two objects. For instance, the objects may be sets, and the morphisms may be functions between sets: morphisms from A to B are the same

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

2005-01-24 Thread Ashley Yakeley
In article <[EMAIL PROTECTED]>, Keean Schupke <[EMAIL PROTECTED]> wrote: > Right, but we are dealing with the type system here. Remember Haskell > monoids are functors on types, not on values ... (ie the base objects the > 'category theory' is applied to are the types not the values)... > > Ther

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

2005-01-24 Thread Jules Bean
On 24 Jan 2005, at 10:32, Keean Schupke wrote: Right, but we are dealing with the type system here. Remember Haskell monoids are functors on types, not on values ... (ie the base objects the 'category theory' is applied to are the types not the values)... Therefore we only consider the types when

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

2005-01-24 Thread Keean Schupke
Ashley Yakeley wrote: I don't believe this represents a good understanding of IO actions as Haskell values. For instance, 'return ()' and 'putStrLn "Hello"' are the same type, but are clearly different actions and so are usually considered to be different values. That the latter prints out text

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

2005-01-24 Thread Ashley Yakeley
In article <[EMAIL PROTECTED]>, Keean Schupke <[EMAIL PROTECTED]> wrote: > Yes it is, side effects are quite clearly not counted. The value > of (putStrLn "Hello" >> mzero") is mzero. I don't believe this represents a good understanding of IO actions as Haskell values. For instance, 'return ()'

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

2005-01-24 Thread Keean Schupke
Just thinking about this, a monad is a Functor plus two natural-tranformations, Unit and Join. Is there an equivalent definition for MonadPlus... I am not sure I understand where MonadPlus comes from? Is it just a Functor and two different definitions of Unit and Join (from those chosen to be i

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

2005-01-24 Thread Jules Bean
On 24 Jan 2005, at 09:36, Keean Schupke wrote: Ashley Yakeley wrote: I disagree. Clearly (putStrLn "Hello" >> mzero) is not the same as mzero. Yes it is, side effects are quite clearly not counted. The value of (putStrLn "Hello" >> mzero") is mzero. This makes no sense to me at all. putStrLn "He

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

2005-01-24 Thread Keean Schupke
Ashley Yakeley wrote: I disagree. Clearly (putStrLn "Hello" >> mzero) is not the same as mzero. Yes it is, side effects are quite clearly not counted. The value of (putStrLn "Hello" >> mzero") is mzero. In reference to the idea of splitting MonadPlus, what category would you be operating in, if

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

2005-01-23 Thread Aaron Denney
On 2005-01-23, Keean Schupke <[EMAIL PROTECTED]> wrote: > Aaron Denney wrote: > >>You can, but the "other one" turns it into a copy of the Maybe Monad, so >>the current one is more useful. >> >> > So what does this mean in terms of Ashley's question: > > But only some instances (such as [])

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

2005-01-23 Thread Ashley Yakeley
In article <[EMAIL PROTECTED]>, Daniel Fischer <[EMAIL PROTECTED]> wrote: > from an earlier message of Keean: > > 1. |mzero >>= f == mzero| > > 2. |m >>= (\x -> mzero) == mzero| > > 3. |mzero `mplus` m == m| > > 4. |m `mplus` mzero == m| > > What exactly does 2. mean in the IO-case? > a) the

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

2005-01-23 Thread Ashley Yakeley
In article <[EMAIL PROTECTED]>, Jorge Adriano Aires <[EMAIL PROTECTED]> wrote: > I just checked the paper, > "A monadic Interpretation of Tatics", by Andrew Martin and Jeremy Gibbons > http://web.comlab.ox.ac.uk/oucl/work/jeremy.gibbons/publications/tactics.pdf > > And in deed, these are the lis

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

2005-01-23 Thread Ashley Yakeley
In article <[EMAIL PROTECTED]>, Marcin 'Qrczak' Kowalczyk <[EMAIL PROTECTED]> wrote: > > I think mplus should be separated into two functions. > > This would prevent using mplus in a single parser which - depending on > the underlying monad used - backtracks or not. Exactly. -- Ashley Yakeley

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

2005-01-23 Thread Jorge Adriano Aires
> Am Sonntag, 23. Januar 2005 15:58 schrieb Jorge Adriano Aires: > > I'm not arguing that definition would be "wrong". It is a monoid. This is > > the instance for (): > > > > instance MonadPlus() where > > mzero = () > > mplus a b = () > > Maybe I'm stupid, but: > > class Monad m => MonadPlus

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

2005-01-23 Thread Daniel Fischer
Am Sonntag, 23. Januar 2005 15:58 schrieb Jorge Adriano Aires: > > I'm not arguing that definition would be "wrong". It is a monoid. This is > the instance for (): > > instance MonadPlus() where > mzero = () > mplus a b = () > Maybe I'm stupid, but: class Monad m => MonadPlus m where mzero

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

2005-01-23 Thread Daniel Fischer
Am Sonntag, 23. Januar 2005 13:21 schrieb Keean Schupke: > Ashley Yakeley wrote: > > I think it would be helpful if all these classes came with their laws > > > >prominently attached in their Haddock documentation or wherever. The Definitely! > >trouble with MonadPlus is that the precise set of a

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

2005-01-23 Thread Jorge Adriano Aires
> I think it would be helpful if all these classes came with their laws > prominently attached in their Haddock documentation or wherever. Agree. > The trouble with MonadPlus is that the precise set of associated laws is > either unspecified or not the most useful (I assume there's a paper on >

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

2005-01-23 Thread Jorge Adriano Aires
> > One common example is using MonadPlus for some backtracking algorithm, > > then instantiatiating it to Maybe or List instance depending on wether > > you just want one solution or all of them. > > Backtracking only works with the first kind, even if you're only > interested in the first soluti

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

2005-01-23 Thread Jorge Adriano Aires
> >>What would happen if this was the definition? > >> > >>instance MonadPlus [] where > >> mzero = [] > >> mplus a b > >> > >> | a == [] = b > >> | otherwise = a > > Isn't the above a monoid as well? Yes. > Is there only on correct definition of a monad/monoid on lists - or does

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

2005-01-23 Thread Marcin 'Qrczak' Kowalczyk
Ashley Yakeley <[EMAIL PROTECTED]> writes: > But only some instances (such as []) satisfy this: > > (mplus a b) >>= c = mplus (a >>= c) (b >>= c) > > Other instances (IO, Maybe) satisfy this: > > mplus (return a) b = return a > > I think mplus should be separated into two functions. This woul

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

2005-01-23 Thread Keean Schupke
Ashley Yakeley wrote: I think it would be helpful if all these classes came with their laws prominently attached in their Haddock documentation or wherever. The trouble with MonadPlus is that the precise set of associated laws is either unspecified or not the most useful (I assume there's a paper

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

2005-01-23 Thread Ashley Yakeley
> I got the impression you > could define anthing you liked for mzero and mplus - providing the laws > are upheld? I agree that a law-based approach is the correct one. The "Monad laws" are well known, equivalent laws for Functor don't seem to be talked about so much but I doubt there'd be any

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

2005-01-23 Thread Ashley Yakeley
In article <[EMAIL PROTECTED]>, Jorge Adriano Aires <[EMAIL PROTECTED]> wrote: > One common example is using MonadPlus for some backtracking algorithm, then > instantiatiating it to Maybe or List instance depending on wether you just > want one solution or all of them. Backtracking only works

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

2005-01-23 Thread Keean Schupke
Aaron Denney wrote: You can, but the "other one" turns it into a copy of the Maybe Monad, so the current one is more useful. So what does this mean in terms of Ashley's question: But only some instances (such as []) satisfy this: (mplus a b) >>= c = mplus (a >>= c) (b >>=

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

2005-01-23 Thread Aaron Denney
On 2005-01-23, Keean Schupke <[EMAIL PROTECTED]> wrote: > Is there only on correct definition of a monad/monoid on lists - or does > anything that satisfies the monad laws count? I got the impression you > could define anthing you liked for mzero and mplus - providing the laws > are upheld? You

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

2005-01-23 Thread Ashley Yakeley
In article <[EMAIL PROTECTED]>, Jorge Adriano Aires <[EMAIL PROTECTED]> wrote: > How would we implement the first kind in the Maybe instance of MonadPlus? We wouldn't, they'd be in separate classes. -- Ashley Yakeley, Seattle WA ___ Haskell-Cafe mai

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

2005-01-23 Thread Keean Schupke
Jorge Adriano Aires wrote: On the list monad, I think of the mplus operation as the "union" two non-deterministic states. Mzero is the state that works as the identity (which is when you have no possible state at all). Okay... thats a definition of a monoid. What would happen if this was the

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

2005-01-22 Thread Jorge Adriano Aires
> >concat (map c (a ++ b)) = concat (map c a) ++ concat (Map c b), > > > >which is easily seen to be true (if applying c to an element of a causes > > an error, neither side will go past that). > > > >Daniel > > So do we consider [] to be fail?, Monad.hs defines: I will ignore "fail" if you don't

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

2005-01-22 Thread Jorge Adriano Aires
> Only the monoid Maybe a is not very nice (nor is the monoid IO a),since the > second argument of the composition is in general ignored. > So I think, rather than separating mplus, one should think about whether it > is sensible to make Maybe and IO instances of MonadPlus in the first place

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

2005-01-22 Thread Jorge Adriano Aires
> But only some instances (such as []) satisfy this: > > (mplus a b) >>= c = mplus (a >>= c) (b >>= c) > > Other instances (IO, Maybe) satisfy this: > > mplus (return a) b = return a > > I think mplus should be separated into two functions. How would we implement the first kind in the Maybe i

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

2005-01-22 Thread Keean Schupke
Daniel Fischer wrote: That's probably a misunderstanding due to the notation, in the [] monad, it's just concat (map c (a ++ b)) = concat (map c a) ++ concat (Map c b), which is easily seen to be true (if applying c to an element of a causes an error, neither side will go past that). Daniel

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

2005-01-22 Thread Daniel Fischer
Am Samstag, 22. Januar 2005 21:20 schrieb Keean Schupke: > Ashley Yakeley wrote: > >In article <[EMAIL PROTECTED]>, > > > > Keean Schupke <[EMAIL PROTECTED]> wrote: > >>This fits the above description, but I don't see how the following can > >>be true: > >> > >>(mplus a b) >>= c = mplus (a >>=

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

2005-01-22 Thread Keean Schupke
Ashley Yakeley wrote: In article <[EMAIL PROTECTED]>, Keean Schupke <[EMAIL PROTECTED]> wrote: This fits the above description, but I don't see how the following can be true: (mplus a b) >>= c = mplus (a >>= c) (b >>= c) Try it (and my test code) with [], which is an instance of MonadP

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

2005-01-22 Thread Daniel Fischer
Am Samstag, 22. Januar 2005 10:09 schrieb Ashley Yakeley: > In article <[EMAIL PROTECTED]>, > > Keean Schupke <[EMAIL PROTECTED]> wrote: > > This fits the above description, but I don't see how the following can > > be true: > > > > (mplus a b) >>= c = mplus (a >>= c) (b >>= c) > > Try it (and

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

2005-01-22 Thread Ashley Yakeley
In article <[EMAIL PROTECTED]>, Keean Schupke <[EMAIL PROTECTED]> wrote: > This fits the above description, but I don't see how the following can > be true: > > (mplus a b) >>= c = mplus (a >>= c) (b >>= c) Try it (and my test code) with [], which is an instance of MonadPlus. mplus is def

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

2005-01-22 Thread Keean Schupke
Ashley Yakeley wrote: In article <[EMAIL PROTECTED]>, "S. Alexander Jacobson" <[EMAIL PROTECTED]> wrote: I assume there is a standard name for this class/function: instance Foo [] where foo [] = mzero foo (x:_) = return x instance Foo (Maybe x) where foo Nothing = mzero foo

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

2005-01-21 Thread Ashley Yakeley
In article <[EMAIL PROTECTED]>, "S. Alexander Jacobson" <[EMAIL PROTECTED]> wrote: > I assume there is a standard name for this > class/function: > >instance Foo [] where > foo [] = mzero > foo (x:_) = return x > >instance Foo (Maybe x) where > foo Nothing = mzero >