Re: [Haskell-cafe] IO (Either a Error) question

2010-05-09 Thread Ivan Lazar Miljenovic
"Brandon S. Allbery KF8NH"  writes:
> I've always had the feeling that if I need catMaybes, I haven't
> thought through the data representation (or possibly manipulation)
> fully.

I've used catMaybes in several places: for example, in SourceGraph only
"interesting" analyses are reported (e.g. if there's only one connected
component, then don't bother mentioning it, as the big point is when
your module has more than one component); I indicate this by having each
separate analysis function returning a Maybe value and then applying
catMaybes.

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] IO (Either a Error) question

2010-05-09 Thread Brandon S. Allbery KF8NH

On May 9, 2010, at 06:18 , Ben Millwood wrote:
On Sun, May 9, 2010 at 7:27 AM, wren ng thornton   
wrote:


The only examples I can think of where we'd want 'fail'-able  
patterns are

entirely pedagogical (and are insignificantly altered by not using
'fail'-able patterns). I can't think of any real code where it would
actually help with clarity.


You're not a fan of e.g.

catMaybes xs = [x | Just x <- xs]


I've always had the feeling that if I need catMaybes, I haven't  
thought through the data representation (or possibly manipulation)  
fully.


--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allb...@kf8nh.com
system administrator [openafs,heimdal,too many hats] allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon universityKF8NH




PGP.sig
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] IO (Either a Error) question

2010-05-09 Thread Ben Millwood
On Sun, May 9, 2010 at 7:27 AM, wren ng thornton  wrote:
>
> The only examples I can think of where we'd want 'fail'-able patterns are
> entirely pedagogical (and are insignificantly altered by not using
> 'fail'-able patterns). I can't think of any real code where it would
> actually help with clarity.
>

You're not a fan of e.g.

catMaybes xs = [x | Just x <- xs]

or the do-notation form:

catMaybes xs = do
 Just x <- xs
 return x

then? (I actually prefer foldr (maybe id (:)) [] but that's probably just me :)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] IO (Either a Error) question

2010-05-08 Thread wren ng thornton

Brandon S. Allbery KF8NH wrote:
It's not a call, it's a definition as shown above.  The simpler 
translation is:


 > x <- y

becomes

 > y >>= \x ->

(note incomplete expression; the next line must complete it) and the 
refutable pattern match takes place in the lambda binding.  But because 
of the whole "fail" thing, instead of letting pattern match failure be 
caught by the lambda binding it gets handled specially beforehand, which 
is especially silly when in most cases fail is defined to do the same 
thing as the lambda binding would.


I'm suggesting (as is David, I think) that a saner definition would let 
the lambda binding randle refutable patterns, and for something like 
Maybe (>>=) can decide how to deal with it in the usual way.  Otherwise 
you're either using a default fail that duplicates the lambda binding, 
or if you want custom handling (as with Maybe and Either that propagate 
Nothing/Left _ respectively) you end up reimplementing part of (>>=) as 
fail, which is just dumb.


+1.

I've never understood what exactly the goal of 'fail'-able patterns was. 
It's a *solution* to the problem of pattern matching, but what is the 
*goal* of allowing pattern matching in the first place? What semantics 
is the solution trying to capture?


The vast majority of code I've written or seen uses plain variables as 
the binding pattern, in which case the definition of (>>=) should handle 
issues like this. And in the cases where we want more than just a plain 
variable, we usually want to handle the "exceptional" branch on a 
case-by-case basis, so the pattern gets boiled out of the <- syntax anyways.


The only examples I can think of where we'd want 'fail'-able patterns 
are entirely pedagogical (and are insignificantly altered by not using 
'fail'-able patterns). I can't think of any real code where it would 
actually help with clarity.


--
Live well,
~wren
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] IO (Either a Error) question

2010-05-08 Thread Ben Millwood
On Sat, May 8, 2010 at 3:26 AM, John Meacham  wrote:
>
> What counts as unfailable?
>
> (x,y) probably,  but what about
>
> data Foo = Foo x y
>
> If we don't allow it, we add 'magic' to tuples, which is a bad thing, if
> we do allow it, there are some odd consequences.
>
> adding another constructor to Foo will suddenly change the type of do
> notations involving it non locally. said constructor may not even be
> exported from the module defining Foo, its existence being an
> implementation detail.
>
> All in all, it is very hacky one way or another. Much more so than
> having 'fail' in Monad.
>

This is an interesting point, but I still disagree. A data type having
constructors added or changed *is* going to break code in clients
using it, or at least make GHC spit out a bunch of non-exhaustive
warnings. It's then a good idea, I think, that people are forced to
re-examine their use sites which don't obviously handle the new
failing case. Presumably if they were really really sure then just a
few well-placed ~s would make the problem go away.
(i.e. to answer your question, pattern matching against any
single-constructor data type should be unfailable in my opinion).

On Sat, May 8, 2010 at 7:16 AM, Ivan Lazar Miljenovic
 wrote:
> As I said in another email: does not the "x <- Nothing" itself call fail
> as it expects x to be an actual value wrapped in Just?

No, the propagation of Nothings is done solely by the definition of
>>= for Monad, and doesn't need fail at all.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] IO (Either a Error) question

2010-05-07 Thread Brandon S. Allbery KF8NH

On May 8, 2010, at 02:16 , Ivan Lazar Miljenovic wrote:

David Menendez  writes:

That does not invoke fail.

Let's take a simpler example: do { x <- Nothing; stmt }. This  
translates to


let
   ok x = do { stmt }
   ok _ = fail "..."
in Nothing >>= ok

By the definition of (>>=) for Maybe, 'ok' is never called.


As I said in another email: does not the "x <- Nothing" itself call  
fail

as it expects x to be an actual value wrapped in Just?


It's not a call, it's a definition as shown above.  The simpler  
translation is:


> x <- y

becomes

> y >>= \x ->

(note incomplete expression; the next line must complete it) and the  
refutable pattern match takes place in the lambda binding.  But  
because of the whole "fail" thing, instead of letting pattern match  
failure be caught by the lambda binding it gets handled specially  
beforehand, which is especially silly when in most cases fail is  
defined to do the same thing as the lambda binding would.


I'm suggesting (as is David, I think) that a saner definition would  
let the lambda binding randle refutable patterns, and for something  
like Maybe (>>=) can decide how to deal with it in the usual way.   
Otherwise you're either using a default fail that duplicates the  
lambda binding, or if you want custom handling (as with Maybe and  
Either that propagate Nothing/Left _ respectively) you end up  
reimplementing part of (>>=) as fail, which is just dumb.


--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allb...@kf8nh.com
system administrator [openafs,heimdal,too many hats] allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon universityKF8NH




PGP.sig
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] IO (Either a Error) question

2010-05-07 Thread Ivan Lazar Miljenovic
David Menendez  writes:
> That does not invoke fail.
>
> Let's take a simpler example: do { x <- Nothing; stmt }. This translates to
>
> let
> ok x = do { stmt }
> ok _ = fail "..."
> in Nothing >>= ok
>
> By the definition of (>>=) for Maybe, 'ok' is never called.

As I said in another email: does not the "x <- Nothing" itself call fail
as it expects x to be an actual value wrapped in Just?

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] IO (Either a Error) question

2010-05-07 Thread David Menendez
On Sat, May 8, 2010 at 1:16 AM, Ivan Lazar Miljenovic
 wrote:
> David Menendez  writes:
>
>> On Sat, May 8, 2010 at 12:15 AM, Ivan Lazar Miljenovic
>>> Well, any time you have a do-block like this you're using failable
>>> patterns:
>>>
>>> maybeAdd       :: Maybe Int -> Maybe Int -> Maybe Int
>>> maybeAdd mx my = do x <- mx
>>>                    y <- my
>>>                    return $ x + y
>>
>> This is true in the sense that the translation for the do syntax in
>> the Haskell report uses fail.
>>
>> do { p <- e; stmts } =
>>     let ok p = do { stmts }
>>         ok _ = fail "..."
>>     in e >>= ok
>>
>> However, it's also true that the fails introduced by the translation
>> of maybeAdd will never be invoked, since the two patterns are
>> irrefutable.
>
> Huh?  What about "maybeAdd (Just 2) Nothing" ?

That does not invoke fail.

Let's take a simpler example: do { x <- Nothing; stmt }. This translates to

let
ok x = do { stmt }
ok _ = fail "..."
in Nothing >>= ok

By the definition of (>>=) for Maybe, 'ok' is never called.

>> That is, maybeAdd would work exactly the same if the do syntax
>> translation were changed to read:
>>
>> do { p <- e; stmts } = e >>= \p -> do { stmts }
>
> Wait, are you using "irrefutable" as "it will still work if we make do
> blocks work the way I want"?

I am using "irrefutable" to refer to patterns which always match. From
the Haskell Report, section 3.17.2:

> It is sometimes helpful to distinguish two kinds of patterns. Matching an
> irrefutable pattern is non-strict: the pattern matches even if the value to be
> matched is _|_. Matching a refutable pattern is strict: if the value to be
> matched is _|_ the match diverges. The irrefutable patterns are as follows:
> a variable, a wildcard, N apat where N is a constructor defined by newtype
> and apat is irrefutable (see Section 4.2.3), v...@apat where apat is 
> irrefutable,
> or of the form ~apat (whether or not apat is irrefutable). All other patterns
> are refutable.

-- 
Dave Menendez 

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] IO (Either a Error) question

2010-05-07 Thread Ivan Lazar Miljenovic
"Brandon S. Allbery KF8NH"  writes:

> On May 8, 2010, at 01:16 , Ivan Lazar Miljenovic wrote:
>> Huh?  What about "maybeAdd (Just 2) Nothing" ?
>
> Isn't that handled by the definition of (>>=) in Maybe, as opposed to
> by invoking fail?
>
>> instance Monad Maybe where
>>   -- ...
>>   Nothing >>= _ = Nothing
>>   (Just x) >>= f = f x

Yes, but isn't the "y <- Nothing" pattern failure handled by invoking
fail?

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] IO (Either a Error) question

2010-05-07 Thread Brandon S. Allbery KF8NH

On May 8, 2010, at 01:16 , Ivan Lazar Miljenovic wrote:

David Menendez  writes:

On Sat, May 8, 2010 at 12:15 AM, Ivan Lazar Miljenovic

Well, any time you have a do-block like this you're using failable
patterns:

maybeAdd   :: Maybe Int -> Maybe Int -> Maybe Int
maybeAdd mx my = do x <- mx
  y <- my
  return $ x + y


This is true in the sense that the translation for the do syntax in
the Haskell report uses fail.


Huh?  What about "maybeAdd (Just 2) Nothing" ?


Isn't that handled by the definition of (>>=) in Maybe, as opposed to  
by invoking fail?


> instance Monad Maybe where
>   -- ...
>   Nothing >>= _ = Nothing
>   (Just x) >>= f = f x

--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allb...@kf8nh.com
system administrator [openafs,heimdal,too many hats] allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon universityKF8NH




PGP.sig
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] IO (Either a Error) question

2010-05-07 Thread Ivan Lazar Miljenovic
David Menendez  writes:

> On Sat, May 8, 2010 at 12:15 AM, Ivan Lazar Miljenovic
>> Well, any time you have a do-block like this you're using failable
>> patterns:
>>
>> maybeAdd   :: Maybe Int -> Maybe Int -> Maybe Int
>> maybeAdd mx my = do x <- mx
>>y <- my
>>return $ x + y
>
> This is true in the sense that the translation for the do syntax in
> the Haskell report uses fail.
>
> do { p <- e; stmts } =
> let ok p = do { stmts }
> ok _ = fail "..."
> in e >>= ok
>
> However, it's also true that the fails introduced by the translation
> of maybeAdd will never be invoked, since the two patterns are
> irrefutable.

Huh?  What about "maybeAdd (Just 2) Nothing" ?

> That is, maybeAdd would work exactly the same if the do syntax
> translation were changed to read:
>
> do { p <- e; stmts } = e >>= \p -> do { stmts }

Wait, are you using "irrefutable" as "it will still work if we make do
blocks work the way I want"?

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] IO (Either a Error) question

2010-05-07 Thread David Menendez
On Sat, May 8, 2010 at 12:15 AM, Ivan Lazar Miljenovic
 wrote:
> David Menendez  writes:
>>
>> I wonder how often people rely on the use of fail in pattern matching.
>> Could we get by without fail or unfailable patterns?
>>
>> ensureCons :: MonadPlus m => [a] -> m [a]
>> ensureCons x@(_:_) = return x
>> ensureCons _ = mzero
>>
>> do ...
>>     x:xs <- ensureCons $ some_compuation
>>
>> This is more flexible than the current situation (you can easily adapt
>> it to throw custom exceptions in ErrorT), but gets cumbersome when
>> you're doing nested patterns. Also, it does the match twice, but
>> presumably the optimizer can be improved to catch that if the idiom
>> became popular.
>
> Well, any time you have a do-block like this you're using failable
> patterns:
>
> maybeAdd       :: Maybe Int -> Maybe Int -> Maybe Int
> maybeAdd mx my = do x <- mx
>                    y <- my
>                    return $ x + y

This is true in the sense that the translation for the do syntax in
the Haskell report uses fail.

do { p <- e; stmts } =
let ok p = do { stmts }
ok _ = fail "..."
in e >>= ok

However, it's also true that the fails introduced by the translation
of maybeAdd will never be invoked, since the two patterns are
irrefutable. That is, maybeAdd would work exactly the same if the do
syntax translation were changed to read:

do { p <- e; stmts } = e >>= \p -> do { stmts }


This would not be the case if refutable patterns were used.

viewM l = do { x:xs <- return l; return (x,xs) }

-- 
Dave Menendez 

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] IO (Either a Error) question

2010-05-07 Thread Ivan Lazar Miljenovic
David Menendez  writes:
>
> I wonder how often people rely on the use of fail in pattern matching.
> Could we get by without fail or unfailable patterns?
>
> ensureCons :: MonadPlus m => [a] -> m [a]
> ensureCons x@(_:_) = return x
> ensureCons _ = mzero
>
> do ...
> x:xs <- ensureCons $ some_compuation
>
> This is more flexible than the current situation (you can easily adapt
> it to throw custom exceptions in ErrorT), but gets cumbersome when
> you're doing nested patterns. Also, it does the match twice, but
> presumably the optimizer can be improved to catch that if the idiom
> became popular.

Well, any time you have a do-block like this you're using failable
patterns:

maybeAdd   :: Maybe Int -> Maybe Int -> Maybe Int
maybeAdd mx my = do x <- mx
y <- my
return $ x + y


-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] IO (Either a Error) question

2010-05-07 Thread Ivan Lazar Miljenovic
Limestraël  writes:

>> Personally I think fail is a terrible wart, and should be shunned.
>
> So do I.
> I can't understand its purpose since monads which can fail can be
> implemented through MonadPlus.

Polyparse uses it, and I believe Parsec does as well...

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] IO (Either a Error) question

2010-05-07 Thread David Menendez
On Fri, May 7, 2010 at 10:26 PM, John Meacham  wrote:
> On Fri, May 07, 2010 at 08:27:04PM -0400, Dan Doel wrote:
>> Personally, I don't really understand why unfailable patterns were canned
>> (they don't seem that complicated to me), so I'd vote to bring them back, and
>> get rid of fail. But hind sight is 20/20, I suppose (or perhaps there exist
>> cogent arguments that I haven't heard).
>
> What counts as unfailable?
>
> (x,y) probably,  but what about
>
> data Foo = Foo x y
>
> If we don't allow it, we add 'magic' to tuples, which is a bad thing, if
> we do allow it, there are some odd consequences.
>
> adding another constructor to Foo will suddenly change the type of do
> notations involving it non locally. said constructor may not even be
> exported from the module defining Foo, its existence being an
> implementation detail.
>
> All in all, it is very hacky one way or another. Much more so than
> having 'fail' in Monad.

I wonder how often people rely on the use of fail in pattern matching.
Could we get by without fail or unfailable patterns?

ensureCons :: MonadPlus m => [a] -> m [a]
ensureCons x@(_:_) = return x
ensureCons _ = mzero

do ...
x:xs <- ensureCons $ some_compuation

This is more flexible than the current situation (you can easily adapt
it to throw custom exceptions in ErrorT), but gets cumbersome when
you're doing nested patterns. Also, it does the match twice, but
presumably the optimizer can be improved to catch that if the idiom
became popular.

-- 
Dave Menendez 

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] IO (Either a Error) question

2010-05-07 Thread John Meacham
On Fri, May 07, 2010 at 08:27:04PM -0400, Dan Doel wrote:
> Personally, I don't really understand why unfailable patterns were canned
> (they don't seem that complicated to me), so I'd vote to bring them back, and
> get rid of fail. But hind sight is 20/20, I suppose (or perhaps there exist
> cogent arguments that I haven't heard).

What counts as unfailable?

(x,y) probably,  but what about

data Foo = Foo x y

If we don't allow it, we add 'magic' to tuples, which is a bad thing, if
we do allow it, there are some odd consequences.

adding another constructor to Foo will suddenly change the type of do
notations involving it non locally. said constructor may not even be
exported from the module defining Foo, its existence being an
implementation detail.

All in all, it is very hacky one way or another. Much more so than
having 'fail' in Monad.

John

-- 
John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] IO (Either a Error) question

2010-05-07 Thread Dan Doel
On Friday 07 May 2010 7:54:21 pm Limestraël wrote:
> > Personally I think fail is a terrible wart, and should be shunned.
> 
> So do I.
> I can't understand its purpose since monads which can fail can be
> implemented through MonadPlus.

Understanding why fail exists requires going back to before Haskell 98. Back 
then, there was a MonadZero, and when you did pattern matching in do syntax, a 
MonadZero constraint would be generated in most cases, like:

  do Just x <- m
 ...

*But*, there were cases where MonadZero wasn't required. This happened when 
you did a match like:

  do (x, y) <- m
 ...

In this case, there's no need to fail 'in the monad', because either the value 
in question *is* of the form (x, y), or it is bottom, in which case the whole 
expression should be bottom anyhow (because we're not supposed to be able to 
detect bottoms like that). Patterns like the above had a special distinction, 
called "unfailable". This is not the same as irrefutable, although the latter 
would be a special case of the former; unfailable patterns are those that can 
at most be refuted by a partially defined value, rather than refuted by a sum.

So, for reasons that I don't recall off the top of my head (perhaps pedagogy), 
it was decided that Haskell 98 should no longer have this additional notion of 
unfailable pattern. However, when you get rid of them, there's a fair amount 
of valid code with a context of Monad m that now needs MonadZero (or, Plus, 
since Zero is gone), and that's rather inconvenient. So, fail was introduced 
into Monad so that pattern matching can be desugared in any Monad, and you're 
once again allowed to write:

  foo :: Monad m => m (a,b) -> ...
  foo m = do (x, y) <- m
 ...

Which is always okay, even though other matches/etc. you can do with fail 
really isn't.

Personally, I don't really understand why unfailable patterns were canned 
(they don't seem that complicated to me), so I'd vote to bring them back, and 
get rid of fail. But hind sight is 20/20, I suppose (or perhaps there exist 
cogent arguments that I haven't heard).

-- Dan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] IO (Either a Error) question

2010-05-07 Thread Brandon S. Allbery KF8NH

On May 7, 2010, at 19:54 , Limestraël wrote:

> Personally I think fail is a terrible wart, and should be shunned.

So do I.
I can't understand its purpose since monads which can fail can be  
implemented through MonadPlus.



The translation of "do" syntax involves pattern matching ("do  
{ [x,y,z] <- something; ... }"), and needs to know what to do when the  
pattern bind fails, so what it does is invoke "fail".  This is  
arguably wrong but we're stuck with it now.  (I have to admit I don't  
see why we can't do exactly what the obvious (>>= \[x,y,z] -> ...)  
translation does, which is throw an exception.  "case", "let", and  
lambda binding don't invoke a special fail mechanism; why is "do"  
special?)


--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allb...@kf8nh.com
system administrator [openafs,heimdal,too many hats] allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon universityKF8NH




PGP.sig
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] IO (Either a Error) question

2010-05-07 Thread Ross Paterson
On Sat, May 08, 2010 at 01:54:21AM +0200, Limestraël wrote:
> > Personally I think fail is a terrible wart, and should be shunned.
> 
> So do I.
> I can't understand its purpose since monads which can fail can be implemented
> through MonadPlus.

It was introduced to implement pattern match failure in do-notation,
in Section 3.14 of the Haskell Report:

  do {p <- e; stmts} = let ok p = do {stmts}
   ok _ = fail "..."
   in e >>= ok
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] IO (Either a Error) question

2010-05-07 Thread Gregory Crosswhite

On May 7, 2010, at 4:54 PM, Limestraël wrote:

> > Personally I think fail is a terrible wart, and should be shunned.
> 
> So do I.
> I can't understand its purpose since monads which can fail can be implemented 
> through MonadPlus.

As far as I can tell, its purpose is to essentially allow you to catch pattern 
match errors in pure code and turn them into a value, since Haskell calls fail 
whenever there is a failed pattern match.  (I am not saying that this is a good 
idea, only that this is not something that you would simply get by using 
MonadPlus.)

Cheers,
Greg

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] IO (Either a Error) question

2010-05-07 Thread Limestraël
> Personally I think fail is a terrible wart, and should be shunned.

So do I.
I can't understand its purpose since monads which can fail can be
implemented through MonadPlus.


2010/5/8 Ross Paterson 

> On Sat, May 08, 2010 at 07:49:57AM +1000, Ivan Lazar Miljenovic wrote:
> > Limestraėl  writes:
> > > 2010/5/1 John Millikin 
> > >
> > >> You might want to make a local version of ErrorT in your library, to
> > >> avoid the silly 'Error' class restriction. This is pretty easy; just
> > >> copy it from the 'transformers' or 'mtl' package.
> > >>
> > > Yes, I wonder why mtl is not updated so as to remove this restriction.
> >
> > Presumably because its in "maintenance mode" (i.e. it only gets
> > changed/updated to reflect changes in GHC that might affect it and the
> > API is frozen).
>
> The API isn't frozen -- it can be changed with a library proposal,
> if you can get people to agree to it.
>
> As Ryan said, the Error constraint is there to support a definition of
> the fail method in the Monad instance for ErrorT.  (Personally I think
> fail is a terrible wart, and should be shunned.)
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] IO (Either a Error) question

2010-05-07 Thread Ross Paterson
On Sat, May 08, 2010 at 07:49:57AM +1000, Ivan Lazar Miljenovic wrote:
> Limestraël  writes:
> > 2010/5/1 John Millikin 
> >
> >> You might want to make a local version of ErrorT in your library, to
> >> avoid the silly 'Error' class restriction. This is pretty easy; just
> >> copy it from the 'transformers' or 'mtl' package.
> >>
> > Yes, I wonder why mtl is not updated so as to remove this restriction.
> 
> Presumably because its in "maintenance mode" (i.e. it only gets
> changed/updated to reflect changes in GHC that might affect it and the
> API is frozen).

The API isn't frozen -- it can be changed with a library proposal,
if you can get people to agree to it.

As Ryan said, the Error constraint is there to support a definition of
the fail method in the Monad instance for ErrorT.  (Personally I think
fail is a terrible wart, and should be shunned.)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] IO (Either a Error) question

2010-05-07 Thread Ivan Lazar Miljenovic
Limestraël  writes:
> 2010/5/1 John Millikin 
>
>> You might want to make a local version of ErrorT in your library, to
>> avoid the silly 'Error' class restriction. This is pretty easy; just
>> copy it from the 'transformers' or 'mtl' package.
>>
> Yes, I wonder why mtl is not updated so as to remove this restriction.

Presumably because its in "maintenance mode" (i.e. it only gets
changed/updated to reflect changes in GHC that might affect it and the
API is frozen).

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] IO (Either a Error) question

2010-05-07 Thread Limestraël
Yes, I wonder why mtl is not updated so as to remove this restriction.


2010/5/1 John Millikin 

> You might want to make a local version of ErrorT in your library, to
> avoid the silly 'Error' class restriction. This is pretty easy; just
> copy it from the 'transformers' or 'mtl' package.
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] IO (Either a Error) question

2010-05-06 Thread David Virebayre
By the way, I didn't exactly reply your question :

> [...] Basically, i don't understand what does "ErrorT ::" means - it
> should name the function - but it starts with capital letter?

It's a type signature, it describes the type of ErrorT:

Prelude> import Control.Monad.Error
Prelude Control.Monad.Error> :t ErrorT
ErrorT :: m (Either e a) -> ErrorT e m a

So that says, ErrorT is a value constructor that takes a value of type
m (Either e a) and makes a value of type ErrorT e m a.

Notice that the type constructor and the value constructor have both
the same name ErrorT, I used to get confused by this when I began
learning.

If you type under ghci

Prelude Control.Monad.Error> :k ErrorT
ErrorT :: * -> (* -> *) -> * -> *

That tells you that ErrorT is a type constructor that takes a type, a
unary type constructor, and a type; and with all this defines a new
type (ErrorT e m a).

David.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] IO (Either a Error) question

2010-05-06 Thread Eugene Dzhurinsky
On Thu, May 06, 2010 at 10:05:05AM +0200, David Virebayre wrote:
> A constructor can be seen as a function that takes some parameters and
> produces a value
> 
> for example with the type Maybe a, which has 2 constructors ; Just and 
> Nothing :
> 
> Prelude> :t Just
> Just :: a -> Maybe a
> 
> the constructor Just is a function that takes a value of type a and
> makes a value of type Maybe a.
> 
> Prelude> :t Just
> Just :: a -> Maybe a

Ouch, that makes things clear. Thanks for the explanation!

-- 
Eugene N Dzhurinsky


pgpmfW4Cj0L7U.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] IO (Either a Error) question

2010-05-06 Thread David Virebayre
On Thu, May 6, 2010 at 9:56 AM, Eugene Dzhurinsky  wrote:
> On Wed, May 05, 2010 at 02:54:27PM -0700, Ryan Ingram wrote:
>> ErrorT is just a newtype wrapper, changing the order/application of
>> the type variables.
>>
>> newtype ErrorT e m a = ErrorT (m (Either e a))
>> runErrorT (ErrorT action) = action
>>
>> This gives the bijection:
>>
>> ErrorT :: m (Either e a) -> ErrorT e m a
>> runErrorT :: ErrorT e m a -> m (Either e a)
>
> That syntax is not clear for me - so ErrorT is some sort of function
> (calculation), which takes a monad with type (Either e a) and produces type
> ErrorT e m a ? Basically, i don't understand what does "ErrorT ::" means - it
> should name the function - but it starts with capital letter?

A constructor can be seen as a function that takes some parameters and
produces a value

for example with the type Maybe a, which has 2 constructors ; Just and Nothing :

Prelude> :t Just
Just :: a -> Maybe a

the constructor Just is a function that takes a value of type a and
makes a value of type Maybe a.

Prelude> :t Just
Just :: a -> Maybe a

David.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] IO (Either a Error) question

2010-05-06 Thread Eugene Dzhurinsky
On Wed, May 05, 2010 at 02:54:27PM -0700, Ryan Ingram wrote:
> ErrorT is just a newtype wrapper, changing the order/application of
> the type variables.
> 
> newtype ErrorT e m a = ErrorT (m (Either e a))
> runErrorT (ErrorT action) = action
> 
> This gives the bijection:
> 
> ErrorT :: m (Either e a) -> ErrorT e m a
> runErrorT :: ErrorT e m a -> m (Either e a)

That syntax is not clear for me - so ErrorT is some sort of function
(calculation), which takes a monad with type (Either e a) and produces type
ErrorT e m a ? Basically, i don't understand what does "ErrorT ::" means - it
should name the function - but it starts with capital letter?

I feel like I missed something when learning type system and syntax of Haskell
:(

-- 
Eugene N Dzhurinsky


pgp58bWRrrwfP.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] IO (Either a Error) question

2010-05-05 Thread Ryan Ingram
ErrorT is just a newtype wrapper, changing the order/application of
the type variables.

newtype ErrorT e m a = ErrorT (m (Either e a))
runErrorT (ErrorT action) = action

This gives the bijection:

ErrorT :: m (Either e a) -> ErrorT e m a
runErrorT :: ErrorT e m a -> m (Either e a)

We can now redefine >>= for this new type to handle plumbing the error:

instance (Error e, Monad m) => Monad (ErrorT e m) where
return a = ErrorT (return (Right a))
m >>= f = ErrorT $ do
ea <- runErrorT m
case ea of
Left e -> return (Left e)
Right a -> runErrorT (f a)
fail s = ErrorT (return $ Left $ strMsg s)

On Sun, May 2, 2010 at 1:50 AM, Eugene Dzhurinsky  wrote:
>> > :t ErrorT
>> ErrorT :: m (Either e a) -> ErrorT e m a
>
> At this point I am lost. I'm not sure that I do understand this type
> transformation correctly. So we have some sort of monadic type m, error type e
> and resut of type a. If m = IO, e - Error, a - String, than
>
> ErrorT :: IO (Either Error String) -> ErrorT Error IO String

Yep.

> I can think that can be written as
>
> ErrorT :: IO (Either Error String) -> ErrorT Error (IO String)
>
> Am I correct?

Nope.

At the type level:

ErrorT :: * -> (* -> *) -> * -> *
That is, the to make the ErrorT concrete (kind *), you need
   a concrete type (e :: *)
   a type that takes a parameter (m :: * -> *)
   and finally, a parameter (a :: *)

(IO String) :: *
whereas
IO :: * -> *
String :: *

The reason for this is because ErrorT is inserting "Either" in the proper place:
   ErrorT :: m (Either e a) -> ErrorT e m a

There's no way for ErrorT to do anything at the type level with (IO
String).  (Although if you go into crazy type system extensions, you
could use GADTs to make a type that worked like that.  Probably not
useful, though!)

Now we have (ErrorT e m) :: * -> *
which means it is eligible to be an instance of Monad, Functor, etc.

>> So, if you can make your Error type an instance of this class, you can do 
>> this:
>> runCalc = runErrorT (ErrorT (func1 p) >>= ErrorT . func2)
>
> Sorry, I don't understand how does it work. Can you please explain the type
> transformations involved here?

Sorry, I typoed a bit here.
runCalc p = runErrorT (ErrorT (func1 p) >>= ErrorT . func2)

Lets just do some inference:

func1 :: Int -> IO (Either Error String)
p :: Int
func1 p :: IO (Either Error String)
ErrorT (func1 p) :: ErrorT Error IO String

func2 :: String -> IO (Either Error [String])
(ErrorT . func2) :: String -> ErrorT Error IO String

(>>=) :: forall m a b. Monad m => m a -> (a -> m b) -> m b
IO is an instance of Monad
If you make Error into an instance of Control.Monad.Error.Error
then (ErrorT Error IO) is an instance of Monad

So one instance of the type of (>>=):
(>>=) :: ErrorT Error IO String -> (String -> ErrorT Error IO
[String]) -> ErrorT Error IO [String]
(func1 p >>= ErrorT . func2) :: ErrorT Error IO [String]

runErrorT (func1 p >>= ErrorT . func2) :: IO (Either Error [String])

And finally:
runCalc :: Int -> IO (Either Error [String])

  -- ryan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] IO (Either a Error) question

2010-05-02 Thread Miguel Mitrofanov

ErrorT :: IO (Either Error String) -> ErrorT Error IO String

I can think that can be written as

ErrorT :: IO (Either Error String) -> ErrorT Error (IO String)

Am I correct?


No, you're not. Similar to function application, type application is  
also left-associative, so it can (but shouldn't) be written as


ErrorT :: IO ((Either Error) String) -> ((ErrorT Error) IO) String

In reality, ErrorT (or EitherT, for that matters) is just a disguise  
(meaning, newtype):


newtype ErrorT e m a = ErrorT {runErrorT :: m (Eigher e a)}
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] IO (Either a Error) question

2010-05-02 Thread Eugene Dzhurinsky
On Sat, May 01, 2010 at 02:42:26PM -0700, Ryan Ingram wrote:
> Check out ErrorT in Control.Monad.Error
> 
> > :t ErrorT
> ErrorT :: m (Either e a) -> ErrorT e m a

At this point I am lost. I'm not sure that I do understand this type
transformation correctly. So we have some sort of monadic type m, error type e
and resut of type a. If m = IO, e - Error, a - String, than

ErrorT :: IO (Either Error String) -> ErrorT Error IO String

I can think that can be written as 

ErrorT :: IO (Either Error String) -> ErrorT Error (IO String)

Am I correct?

> So, if you can make your Error type an instance of this class, you can do 
> this:
> runCalc = runErrorT (ErrorT (func1 p) >>= ErrorT . func2)

Sorry, I don't understand how does it work. Can you please explain the type
transformations involved here?

Thank you in advance!

-- 
Eugene N Dzhurinsky


pgpogj49pOZL5.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] IO (Either a Error) question

2010-05-01 Thread Miguel Mitrofanov

It's called "monad transformers"

func1' :: Int -> EitherT Error IO String
func1' n = EitherT $ func1 n
func2' :: Int -> EitherT Error IO String
func2' s = EitherT $ func2 n
runCalc' :: Int -> EitherT Error IO [String]
runCalc' param = func1' param >>= func2'
runCalc :: Int -> IO (Either Error [String])
runCalc param = runEitherT $ runCalc param

(EitherT is on Hackage)

On 2 May 2010, at 01:37, Eugeny N Dzhurinsky wrote:


Hello!

I have some sort of strange question:

assume that there are 2 functions

func1 :: Int -> IO (Either Error String)
func2 :: String -> IO (Either Error [String])

in case if there will be no IO involved, I could use
Control.Monad.Either and write something like

runCalc :: Int -> IO (Either Error [String])
runCalc param = func1 param >>= func2

but with that IO stuff I can't simply do in this way. Can somebody  
please

suggest, how to combine IO and Either monads, if that's even possible?

Thank you in advance!

--
Eugene Dzhurinsky
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] IO (Either a Error) question

2010-05-01 Thread John Millikin
You might want to make a local version of ErrorT in your library, to
avoid the silly 'Error' class restriction. This is pretty easy; just
copy it from the 'transformers' or 'mtl' package.

On Sat, May 1, 2010 at 14:42, Ryan Ingram  wrote:
> Check out ErrorT in Control.Monad.Error
>
>> :t ErrorT
> ErrorT :: m (Either e a) -> ErrorT e m a
>
>> :info ErrorT
> instance (Monad m, Error e) => Monad (ErrorT e m)
>
>> :info Error
> class Error e where
>    noMsg :: e
>    strMsg :: String -> e
>
> So, if you can make your Error type an instance of this class, you can do 
> this:
>
> runCalc = runErrorT (ErrorT (func1 p) >>= ErrorT . func2)
>
> The restriction to the typeclass Error is to allow implementation of
> the "fail" method in Monad.
>
>  -- ryan
>
>
> 2010/5/1 Eugeny N Dzhurinsky :
>> Hello!
>>
>> I have some sort of strange question:
>>
>> assume that there are 2 functions
>>
>> func1 :: Int -> IO (Either Error String)
>> func2 :: String -> IO (Either Error [String])
>>
>> in case if there will be no IO involved, I could use
>> Control.Monad.Either and write something like
>>
>> runCalc :: Int -> IO (Either Error [String])
>> runCalc param = func1 param >>= func2
>>
>> but with that IO stuff I can't simply do in this way. Can somebody please
>> suggest, how to combine IO and Either monads, if that's even possible?
>>
>> Thank you in advance!
>>
>> --
>> Eugene Dzhurinsky
>>
>> ___
>> Haskell-Cafe mailing list
>> Haskell-Cafe@haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>>
>>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] IO (Either a Error) question

2010-05-01 Thread Ryan Ingram
Check out ErrorT in Control.Monad.Error

> :t ErrorT
ErrorT :: m (Either e a) -> ErrorT e m a

> :info ErrorT
instance (Monad m, Error e) => Monad (ErrorT e m)

> :info Error
class Error e where
noMsg :: e
strMsg :: String -> e

So, if you can make your Error type an instance of this class, you can do this:

runCalc = runErrorT (ErrorT (func1 p) >>= ErrorT . func2)

The restriction to the typeclass Error is to allow implementation of
the "fail" method in Monad.

  -- ryan


2010/5/1 Eugeny N Dzhurinsky :
> Hello!
>
> I have some sort of strange question:
>
> assume that there are 2 functions
>
> func1 :: Int -> IO (Either Error String)
> func2 :: String -> IO (Either Error [String])
>
> in case if there will be no IO involved, I could use
> Control.Monad.Either and write something like
>
> runCalc :: Int -> IO (Either Error [String])
> runCalc param = func1 param >>= func2
>
> but with that IO stuff I can't simply do in this way. Can somebody please
> suggest, how to combine IO and Either monads, if that's even possible?
>
> Thank you in advance!
>
> --
> Eugene Dzhurinsky
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe