Re: [Haskell-cafe] Re: nested maybes

2007-02-06 Thread Yitzchak Gale

J. Garrett Morris wrote:

Again, from the earlier example, I'm not sure how typing:

apply :: (MonadCont m, MonadState Blargh m, MonadError Fzzt m, MonadIO m) =
  Handle - Attribute a - m a

is simpler than

apply :: Handle - Attribute a - m a


Well, no, but it is at least no worse than

apply :: Handle - Attribute a -
 ContT (StateT Blargh (ErrorT Fzzt IO)) a

I find that in general, many functions do
not need all of the capabilities. If they do,
you can alias that also:

class (MonadCont m, MonadState Blargh m, MonadError Fzzt m, MonadIO m) =
 MyContext m
instance MyContext (ContT (StateT Blargh (ErrorT Fzzt IO)))

...

apply :: MyContext m = Handle - Attribute a - m a


 2. Use a type alias for the monad stack.

At least as of 6.4.2, GHC printed the expanded types, not the aliases,
in error messages.


Hmm, I'm not sure. I use a more recent GHC.
I know I have seen type aliases in error messages,
but I am not certain that they are always used.


(There are other big advantages of both of these.)

Those being?


OK, let's see...

You often need to make changes to the monad stack -
add or remove capabilities, reorder, etc. This way,
you only change the type in one place, and only
fix functions that use the particular capabilities that
were changed.

The usual advantages of polymorphism apply -
gives separation of concerns, encourages reuse,
eases maintenance and testing, better expresses
the meaning of the function by not mentioning
unneeded details.

Monad transformers are like Lego blocks. I find
that almost always, different parts of a system
need to use different combinations of common
monad stack fragments, assembled in different
ways. Polymorphism makes that a lot easier to do,
and results in functions that are much more
readable.

By the way, are you really doing CPS? If you are
only using ContT to get short-circuiting, you could
probably also simplify things by using ExitT
instead:

http://www.haskell.org/haskellwiki/New_monads#MonadExit

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


Re: [Haskell-cafe] Re: nested maybes

2007-02-06 Thread J. Garrett Morris

On 2/6/07, Yitzchak Gale [EMAIL PROTECTED] wrote:

J. Garrett Morris wrote:
Well, no, but it is at least no worse than

apply :: Handle - Attribute a -
  ContT (StateT Blargh (ErrorT Fzzt IO)) a

I find that in general, many functions do
not need all of the capabilities. If they do,
you can alias that also:


Well, in this case, the function looked more like:

apply :: Handle - Attribute a - S a

Part of the point here was that S was an abstraction.  Most functions
weren't accessing the state or the continuations directly - and their
interaction with the error type had an intermediary as well.  Instead,
they were using operations that, in turn, used the underlying pieces.


You often need to make changes to the monad stack -
add or remove capabilities, reorder, etc. This way,
you only change the type in one place, and only
fix functions that use the particular capabilities that
were changed.


This is the same with my newtype-deriving alias.


The usual advantages of polymorphism apply -
gives separation of concerns, encourages reuse,
eases maintenance and testing, better expresses
the meaning of the function by not mentioning
unneeded details.


Well, we accomplished this all by having an abstraction barrier
between a set of basic operations (which knew, at some level, about
the internals of S and had their own sets of unit tests) and things
built on top of S (which hypothetically could have gotten to its
internals, but didn't.  It would have been better practice to not
export the instances, but I didn't think of that at the time_.


By the way, are you really doing CPS? If you are
only using ContT to get short-circuiting, you could
probably also simplify things by using ExitT
instead:


We had a threading system which scheduled application threads to a
limited number of IO threads based on data-driven changing priorities.
This was first designed for GHC 6.2.2, when the threaded runtime
wasn't in the shipping versions yet.

I really think we're just talking about two approaches to the same
thing.  I prefer to encapsulate most of the MonadX operations as soon
as possible behind a domain-specific layer, and then write the rest of
my code in terms of that.  In that case, I get isolation of concerns
and testing and such from the fact that the internals of the monad
stack aren't exposed, and if they need to be changed it only affects
the DSL components, not the majority of the code.

/g

--
It is myself I have never met, whose face is pasted on the underside of my mind.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: nested maybes

2007-02-05 Thread Bulat Ziganshin
Hello Martin,

Monday, February 5, 2007, 2:47:33 AM, you wrote:

 main = do
minput - getInput
case minput of
  Nothing - printError
  Just input - do
mresult - processInput input
case mresult of
  Nothing - printError
  Just result - printResult result

main = do
  getInput = maybe printError $ \input - do
  ...

  


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] Re: nested maybes

2007-02-05 Thread Yitzchak Gale

J. Garrett Morris wrote:

This is where my favorite part of the mtl steps in: monad transformers.


I agree, the Error monad is very helpful here.


First, we'll create a transformed version of the IO monad,


Why go to the trouble of creating a new monad?
The existing ones are fine.

(While writing this, I just saw Bulat's posts. Nice!)

It would be nicest if we had MaybeT available, as in
http://www.haskell.org/haskellwiki/New_monads/MaybeT

Then you could just write:

import Control.Monad.Maybe

main = runMaybeT $ doIt `mplus` liftIO printError
where
  doIt = do
input - MaybeT getInput
result - MaybeT $ processInput input
liftIO $ printResult result

You could simplify things if you
change the types from IO (Maybe a) to
MaybeT IO a. Then you would have:

main = runMaybeT $ doIt `mplus` liftIO printError
where
  doIt = do
input - getInput
result - processInput input
liftIO $ printResult result

But you might want to do something more
robust with the error reporting. Then you
would do this:

import Control.Monad.Error

data MyError = InputError | OutputError | Unknown String
instance Error MyError where
 noMsg = Unknown Oops
 strMsg x = Unknown x

Then make the type of printError
printError :: MyError - IO ()

and we have:

main = runErrorT $ doIt `catchError` (liftIO . printError)
where
  doIt = do
input - liftIO getInput = maybe (throwError InputError) return
result - liftIO (processInput input) = maybe (throwError
OutputError return
liftIO $ printResult result

Again, you can simplify things if you do
change the types, using ErrorT MyError IO a
in place of IO (Maybe a), etc., and put the
throwError calls inside the functions.

main = runErrorT $ doIt `catchError` (liftIO . printError)
where
  doIt = do
input - getInput
result - processInput input
liftIO $ printResult result

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


Re: [Haskell-cafe] Re: nested maybes

2007-02-05 Thread J. Garrett Morris

On 2/5/07, Yitzchak Gale [EMAIL PROTECTED] wrote:

J. Garrett Morris wrote:
 First, we'll create a transformed version of the IO monad,

Why go to the trouble of creating a new monad?
The existing ones are fine.


Mainly to keep the type error messages simpler.  A project I was
working on started with

type S = StateT Blargh (ErrorT Fizzt IO)

which was fine and dandy, although it produced somewhat verbose error
messages.  But then we added ContT to the stack, and the end result
was that error messages tended to take more time giving the
transformers than the errors.  On the other hand, using a newtype the
error messages were much easier to read.

/g

--
It is myself I have never met, whose face is pasted on the underside of my mind.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: nested maybes

2007-02-05 Thread Yitzchak Gale

I wrote:

Why go to the trouble of creating a new monad?
The existing ones are fine.


J. Garrett Morris wrote:

Mainly to keep the type error messages simpler.


There are two ways to get around that problem:

1. Make your functions polymorphic, using
MonadState, MonadError, etc. Each function
mentions only the capabilities that it needs,
without having the whole monad stack in its type.

2. Use a type alias for the monad stack.

(There are other big advantages of both of these.)

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


Re: [Haskell-cafe] Re: nested maybes

2007-02-05 Thread J. Garrett Morris

On 2/5/07, Yitzchak Gale [EMAIL PROTECTED] wrote:

J. Garrett Morris wrote:
 Mainly to keep the type error messages simpler.

There are two ways to get around that problem:

1. Make your functions polymorphic, using
MonadState, MonadError, etc. Each function
mentions only the capabilities that it needs,
without having the whole monad stack in its type.


Again, from the earlier example, I'm not sure how typing:

apply :: (MonadCont m, MonadState Blargh m, MonadError Fzzt m, MonadIO m) =
 Handle - Attribute a - m a

is simpler than

apply :: Handle - Attribute a - m a

especially when almost every function in the project would have
required the same constraint list.


2. Use a type alias for the monad stack.


At least as of 6.4.2, GHC printed the expanded types, not the aliases,
in error messages.


(There are other big advantages of both of these.)


Those being?

/g

--
It is myself I have never met, whose face is pasted on the underside of my mind.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: nested maybes

2007-02-05 Thread Benjamin Franksen
Udo Stenzel wrote:
 Sure, you're right, everything flowing in the same direction is usually
 nicer, and in central Europe, that order is from the left to the right.
 What a shame that the Haskell gods chose to give the arguments to (.)
 and ($) the wrong order!

But then application is in the wrong order, too. Do you really want to write
(x f) for f applied to x?

Ben

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


Re: [Haskell-cafe] Re: nested maybes

2007-02-05 Thread Udo Stenzel
Benjamin Franksen wrote:
 Udo Stenzel wrote:
  Sure, you're right, everything flowing in the same direction is usually
  nicer, and in central Europe, that order is from the left to the right.
  What a shame that the Haskell gods chose to give the arguments to (.)
  and ($) the wrong order!
 
 But then application is in the wrong order, too. Do you really want to write
 (x f) for f applied to x?

No, doesn't follow.  Unix pipes also read from left to right, even
though programs receive their arguments to the right of the program
namen, and that feels totally natural.


-Udo


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


[Haskell-cafe] Re: nested maybes

2007-02-04 Thread Max Vasin

 Maybe has a Monad instance, so you can write this as follows (untested):

 exists str wmap = boolFromMaybe exists'
   where exists' =
 do x - Map.lookup (sort str) wmap
find (== str) (snd x)
 boolFromMaybe (Just _) = True
 boolFromMaybe Nothing  = False

import isJust
boolFromMaybe = isJust

-- 
WBR,
Max Vasin.

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


[Haskell-cafe] Re: nested maybes

2007-02-04 Thread Martin Huschenbett

Hi,

I've often got the same pattern with nested Maybes but inside the IO 
monad (sure this could be every other monad too). Assuming that I've got 
functions:


getInput :: IO (Maybe Input)
processInput :: Input - IO (Maybe Result)
printError :: IO ()
printResult :: Result - IO ()

I observed me writing something like

main :: IO ()
main = do
  minput - getInput
  case minput of
Nothing - printError
Just input - do
  mresult - processInput input
  case mresult of
Nothing - printError
Just result - printResult result

several times. But to my mind this looks very imperative and I hope it 
can be done more functional. If there is any way, please let me know.


Regards,

Martin.

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


Re: [Haskell-cafe] Re: nested maybes

2007-02-04 Thread J. Garrett Morris

On 2/4/07, Martin Huschenbett [EMAIL PROTECTED] wrote:

Hi,

I've often got the same pattern with nested Maybes but inside the IO
monad (sure this could be every other monad too). Assuming that I've got
functions:


This is where my favorite part of the mtl steps in: monad transformers.

First, we'll create a transformed version of the IO monad, which
encompasses the idea of failure.  I've made the failures somewhat more
general by allowing String typed error messages, but you can replace
String with whatever type you'd like (including () if you really don't
want any such information).


newtype MyIO a = MyIO { runMyIO :: ErrorT String IO a }
deriving (Functor, Monad, MonadError String)


This uses GHC's newtype deriving mechanism, and thus requires
-fglasgow-exts.  The same effect can be achieved in Haskell 98 by
using a type synonym instead of a newtype.

Then, we need to have your operations produce their results in MyIO a
instead of IO (Maybe a):


getInput :: MyIO Input
processInput :: Input - MyIO Result
printError :: String - MyIO ()
printResult :: Result - MyIO ()


Finally, we can rewrite your main function without the case statements:


main = runErrorT . runMyIO $
(do input - getInput
result - processInput input
printResult result)
`catchError` printError


However, in this case you don't really need do notation at all.  You
have a very nice pipeline of operations, and we can express it that
way:


main' = runErrorT . runMyIO $ (getInput = processInput = printResult)
  `catchError` printError


which should remove the last vestiges of imperative-feeling code.

/g

--
It is myself I have never met, whose face is pasted on the underside of my mind.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe