
I have a Data.Map.Map String -> (Layout, [String]) as follows: type Anagrams = [String] type Cell = (Layout, Anagrams) type WordMap = Map.Map String Cell exists str wmap = let a = Map.lookup (sort str) wmap in case a of Nothing -> False Just x -> case (find (== str) (snd x)) of Nothing -> False _ -> True the existence test looks ugly - any more compact way to write it? martin

On 2/4/07, Martin DeMello
I have a Data.Map.Map String -> (Layout, [String]) as follows:
type Anagrams = [String] type Cell = (Layout, Anagrams) type WordMap = Map.Map String Cell
exists str wmap = let a = Map.lookup (sort str) wmap in case a of Nothing -> False Just x -> case (find (== str) (snd x)) of Nothing -> False _ -> True
the existence test looks ugly - any more compact way to write it?
How about: exists str = fromMaybe False . fmap (elem str.snd) . Map.lookup (sort str) -- Cheers, Lemmih

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
/g
On 2/4/07, Martin DeMello
I have a Data.Map.Map String -> (Layout, [String]) as follows:
type Anagrams = [String] type Cell = (Layout, Anagrams) type WordMap = Map.Map String Cell
exists str wmap = let a = Map.lookup (sort str) wmap in case a of Nothing -> False Just x -> case (find (== str) (snd x)) of Nothing -> False _ -> True
the existence test looks ugly - any more compact way to write it?
martin _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- It is myself I have never met, whose face is pasted on the underside of my mind.

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.

J. Garrett Morris wrote:
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
Small improvement (Data.Maybe is underappreciated):
exists str wmap = isJust exists' where exists' = do x <- Map.lookup (sort str) wmap find (== str) (snd x)
and maybe another improvement, though this is dependent on your tastes:
exists s wmap = isJust $ Map.lookup (sort s) wmap >>= find (== s) . snd
-Udo -- Catproof is an oxymoron, childproof nearly so.

On 2/4/07, Udo Stenzel
J. Garrett Morris wrote: Small improvement (Data.Maybe is underappreciated):
exists str wmap = isJust exists' where exists' = do x <- Map.lookup (sort str) wmap find (== str) (snd x)
This is true. Some time ago I swore off the use of fromRight and fromLeft in favor of maybe, and have been forgetting about the other functions in Data.Maybe ever since.
and maybe another improvement, though this is dependent on your tastes:
exists s wmap = isJust $ Map.lookup (sort s) wmap >>= find (== s) . snd
If you're going to write it all on one line, I prefer to keep things going the same direction: exists s wmap = isJust $ find (==s) . snd =<< Map.lookup (sort s) wmap Normally, from there I would be tempted to look for a points-free implementation, but in this case I have a strong suspicion that would simply be unreadable. /g -- It is myself I have never met, whose face is pasted on the underside of my mind.

Hi
This is true. Some time ago I swore off the use of fromRight and fromLeft in favor of maybe, and have been forgetting about the other functions in Data.Maybe ever since.
I think you mean you swore off fromJust. Unfortunately when people started to debate adding fromLeft and fromRight they decided against logic and consistency, and chose not to add them... Thanks Neil

J. Garrett Morris wrote:
On 2/4/07, Udo Stenzel
wrote: exists s wmap = isJust $ Map.lookup (sort s) wmap >>= find (== s) . snd
If you're going to write it all on one line, I prefer to keep things going the same direction:
Hey, doing it this way saved me a full two keystrokes!!!1 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!
exists s wmap = isJust $ find (==s) . snd =<< Map.lookup (sort s) wmap
Normally, from there I would be tempted to look for a points-free implementation, but in this case I have a strong suspicion that would simply be unreadable.
Well, depends on whether we are allowed to define new combinators. I sometimes use -- Kleisli composition infixl 1 @@ (@@) :: Monad m => (a -> m b) -> (b -> m c) -> (a -> m c) f @@ g = join . liftM g . f and the resulting
exists s = Map.lookup (sort s) @@ find (== s) . snd >>> isJust
isn't all that bad. (To be read as: one can get used to it.) I also think, (@@) and (>>>) belong in the Prelude and (>>>) at type ((a->b) -> (b->c) -> (b->c)) should be known under a shorter name. Unfortunately, everything short but (?) is already taken... Of course, the remaining variable "s" could also be transformed away, but that's really pointless. -Udo -- "Never confuse motion with action." -- Ernest Hemingway

u.stenzel:
J. Garrett Morris wrote:
On 2/4/07, Udo Stenzel
wrote: exists s wmap = isJust $ Map.lookup (sort s) wmap >>= find (== s) . snd
If you're going to write it all on one line, I prefer to keep things going the same direction:
Hey, doing it this way saved me a full two keystrokes!!!1
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!
exists s wmap = isJust $ find (==s) . snd =<< Map.lookup (sort s) wmap
Normally, from there I would be tempted to look for a points-free implementation, but in this case I have a strong suspicion that would simply be unreadable.
Well, depends on whether we are allowed to define new combinators. I sometimes use
-- Kleisli composition infixl 1 @@ (@@) :: Monad m => (a -> m b) -> (b -> m c) -> (a -> m c) f @@ g = join . liftM g . f
By the way, this is now in Control.Monad (in darcs). Though since we also want the flipped version, it becomes: -- | Left-to-right Kleisli composition of monads. (>=>) :: Monad m => (a -> m b) -> (b -> m c) -> (a -> m c) f >=> g = \x -> f x >>= g -- | Right-to-left Kleisli composition of monads. '(>=>)', with the arguments flipped (<=<) :: Monad m => (b -> m c) -> (a -> m b) -> (a -> m c) (<=<) = flip (>=>) Cheers, Don

On 2/4/07, Udo Stenzel
J. Garrett Morris wrote:
On 2/4/07, Udo Stenzel
wrote: Well, depends on whether we are allowed to define new combinators. I sometimes use -- Kleisli composition infixl 1 @@ (@@) :: Monad m => (a -> m b) -> (b -> m c) -> (a -> m c) f @@ g = join . liftM g . f
I was responding to this, but Dons beat me to it. Personally, I use this combinator quite a bit. (As much as I would rather use >>>, the Kleisli arrow is a bit verbose to use for my taste.)
and the resulting
exists s = Map.lookup (sort s) @@ find (== s) . snd >>> isJust
isn't all that bad. (To be read as: one can get used to it.) I also think, (@@) and (>>>) belong in the Prelude and (>>>) at type ((a->b) -> (b->c) -> (b->c)) should be known under a shorter name. Unfortunately, everything short but (?) is already taken...
Presumably you mean (a -> b) -> (b -> c) -> (a -> c)? I would personally be fine with Arrows being in the prelude (and, for instance, (.) defined as flip (>>>)). I'd support your shorter name idea if I could think of one... /g -- It is myself I have never met, whose face is pasted on the underside of my mind.

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

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

Udo Stenzel wrote:
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.
No? Your words: "everything flowing in the same direction". Of the two definitions (f . g) x = g (f x) vs. (f . g) x = f (g x) the first one (your prefered one) turns the natural applicative order around, while the second one preserves it. Note this is an objective argument and has nothing to do with how I feel about it.
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.
I'd say what 'feels natural' is in the eye of the beholder. One can get used to almost any form of convention, notational and otherwise, however inconsistent. For instance, the Haskell convention for (.) feels natural for me, because I have been doing math for a long time and mathematicians use the same convention. OTOH, the math convention also says that the type of a function is written (ArgType -> ResultType), although (ResultType <- ArgType) would have been more logical because consistent with the application order. I am used to it, so it feels natural to me, but does that make it the better choice? Cheers Ben

On Wed, 7 Feb 2007, Benjamin Franksen wrote:
Udo Stenzel wrote:
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.
No? Your words: "everything flowing in the same direction".
Of the two definitions
(f . g) x = g (f x)
vs.
(f . g) x = f (g x)
the first one (your prefered one) turns the natural applicative order around, while the second one preserves it. Note this is an objective argument and has nothing to do with how I feel about it.
I would guess that one thing lying at the bottom of this particular disagreement is whether everything is a function, or whether objects are some qualified class of their own. A way to categorify elements of objects in a cartesian closed category (such as that that sufficiently restricted Haskell takes place in) are to view entities of type A as maps () -> A. If this is the case, then with g::A -> B and f:: B -> C, we would want our composition to work the same way regardless of what we feed into it, and so we have two choices of notation: either x . g . f or f . g . x (where I'm using the fact that composition in a category is associative, as to not write the brackets everywhere) Now, here it is perfectly obvious why Udo's argument applies, and that inverting (.) and ($) would lead to (x f) meaning f applied to x. In a way, this is more in agreement with the actual maps we view, since x . g . f corresponds to a composition () -> A -> B -> C ==> () -> C However, if elements are to be viewed as something different entirely, not in any way acquainted with functions, then one could state that function composition should be by right action, and element application by left action, so as to mimic the unix shell situation. It seems a bit unnatural in purely functional languages though, and I believe that one'd lose important intuition that way around. -- Mikael Johansson | To see the world in a grain of sand mikael@johanssons.org | And heaven in a wild flower http://www.mikael.johanssons.org | To hold infinity in the palm of your hand | And eternity for an hour

A way to categorify elements of objects in a cartesian closed category (such as that that sufficiently restricted Haskell takes place in) are to view entities of type A as maps () -> A.Mikael Johansson wrote:
This rather inconveniently clashes with the fact that A and () -> A are two distinct types in Haskell. A is just the "curried" counterpart to () -> A, just as A -> B is the curried counterpart to OneTuple A -> B and A -> B -> C is the (fully) curried counterpart to (A,B) -> C I take it by your argument that curried and uncurried functions, being isomorphic, are represented by the same object in your category? Dan
On Wed, 7 Feb 2007, Benjamin Franksen wrote:
Udo Stenzel wrote:
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.
No? Your words: "everything flowing in the same direction".
Of the two definitions
(f . g) x = g (f x)
vs.
(f . g) x = f (g x)
the first one (your prefered one) turns the natural applicative order around, while the second one preserves it. Note this is an objective argument and has nothing to do with how I feel about it.
I would guess that one thing lying at the bottom of this particular disagreement is whether everything is a function, or whether objects are some qualified class of their own.
A way to categorify elements of objects in a cartesian closed category (such as that that sufficiently restricted Haskell takes place in) are to view entities of type A as maps () -> A. If this is the case, then with g::A -> B and f:: B -> C, we would want our composition to work the same way regardless of what we feed into it, and so we have two choices of notation: either x . g . f or f . g . x (where I'm using the fact that composition in a category is associative, as to not write the brackets everywhere)
Now, here it is perfectly obvious why Udo's argument applies, and that inverting (.) and ($) would lead to (x f) meaning f applied to x. In a way, this is more in agreement with the actual maps we view, since x . g . f corresponds to a composition () -> A -> B -> C ==> () -> C
However, if elements are to be viewed as something different entirely, not in any way acquainted with functions, then one could state that function composition should be by right action, and element application by left action, so as to mimic the unix shell situation. It seems a bit unnatural in purely functional languages though, and I believe that one'd lose important intuition that way around.

On Wed, 7 Feb 2007, Dan Weston wrote:
A way to categorify elements of objects in a cartesian closed category (such as that that sufficiently restricted Haskell takes place in) are to view entities of type A as maps () -> A.Mikael Johansson wrote:
This rather inconveniently clashes with the fact that A and () -> A are two distinct types in Haskell. A is just the "curried" counterpart to () -> A, just as A -> B is the curried counterpart to OneTuple A -> B and A B -> -> C is the (fully) curried counterpart to (A,B) -> C
I take it by your argument that curried and uncurried functions, being isomorphic, are represented by the same object in your category?
They probably would be -- which'd end up displaying the category (and thus the way I think about Haskell) as a quotient category of the Haskell98 category. I think though, still, that my argument carries content to the discussion: regardless of whether we handle currying or not (note that any function has a completely curried normal form) we still end up with the original argument separating things that doesn't necessarily make sense to separate -- in the argument 0-ary functions from n-ary functions.
Dan
-- Mikael Johansson | To see the world in a grain of sand mikael@johanssons.org | And heaven in a wild flower http://www.mikael.johanssons.org | To hold infinity in the palm of your hand | And eternity for an hour

Mikael Johansson wrote:
A way to categorify elements of objects in a cartesian closed category (such as that that sufficiently restricted Haskell takes place in) are to view entities of type A as maps () -> A.
Dan Weston wrote:
This rather inconveniently clashes with the fact that A and () -> A are two distinct types in Haskell.
Not really. It's just that in the terminology of category theory, there is no direct way to talk about "elements" of an object. In general, objects do not need to be sets, so there is no notion of an "element". In our case, where the objects - Haskell types - happen to be sets, we get our hands on "elements" of an object by using the trick of taking elements of the set of morphisms from () to the type. With functions, we have the opposite situation. Functions are first-class in Haskell. So for each function of type A -> B there are two representations in the category: as an "element" of the object A->B, and as an element of the set of morphisms from A to B.
I take it by your argument that curried and uncurried functions, being isomorphic, are represented by the same object in your category?
No. (A,B)->C and A->B->C are two different types, so they are two different objects in the category. The two objects are isomorphic via curry and uncurry. -Yitz

Hello J., Sunday, February 4, 2007, 11:46:57 PM, you wrote:
exists s wmap = isJust $ find (==s) . snd =<< Map.lookup (sort s) wmap
exists s wmap = Map.lookup (sort s) wmap >>== snd >>== find (==s) >>== isJust a>>==b = a>>=return.b -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

On 2/5/07, Bulat Ziganshin
Hello J.,
Sunday, February 4, 2007, 11:46:57 PM, you wrote:
exists s wmap = isJust $ find (==s) . snd =<< Map.lookup (sort s) wmap
exists s wmap = Map.lookup (sort s) wmap >>== snd >>== find (==s) >>== isJust
a>>==b = a>>=return.b
Very nice! Didn't know about >>==. Thanks to everyone else who responded too; I'm learning a lot from this thread. martin

Martin DeMello wrote:
On 2/5/07, Bulat Ziganshin
wrote: Hello J.,
Sunday, February 4, 2007, 11:46:57 PM, you wrote:
exists s wmap = isJust $ find (==s) . snd =<< Map.lookup (sort s) wmap
exists s wmap = Map.lookup (sort s) wmap >>== snd >>== find (==s) >>== isJust
a>>==b = a>>=return.b
Very nice! Didn't know about >>==. Thanks to everyone else who responded too; I'm learning a lot from this thread.
(>>==) is user-defined; that's what the last line is for :)

On Sun, 2007-02-04 at 19:54 +0530, Martin DeMello wrote:
I have a Data.Map.Map String -> (Layout, [String]) as follows:
type Anagrams = [String] type Cell = (Layout, Anagrams) type WordMap = Map.Map String Cell
exists str wmap = let a = Map.lookup (sort str) wmap in case a of Nothing -> False Just x -> case (find (== str) (snd x)) of Nothing -> False _ -> True
the existence test looks ugly - any more compact way to write it?
Using the Maybe Monad is one solution i think (as in: i _think_ this should work): findIt str wmap = do a <- Map.lookup (sort str) wmap return $ find (== str) (snd a) exists str wmap = case findIt str wmap of Nothing -> False Just _ -> True The Maybe monad is very nice for abstracting away all those case-expressions.

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.

On 2/4/07, 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:
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.

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

On 2/5/07, Yitzchak Gale
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.

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

On 2/5/07, Yitzchak Gale
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.

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

On 2/6/07, Yitzchak Gale
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.

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, Bulat mailto:Bulat.Ziganshin@gmail.com
participants (15)
-
Benjamin Franksen
-
Bryan Donlan
-
Bulat Ziganshin
-
Dan Weston
-
dons@cse.unsw.edu.au
-
J. Garrett Morris
-
Lemmih
-
Martin DeMello
-
Martin Huschenbett
-
Mattias Bengtsson
-
Max Vasin
-
Mikael Johansson
-
Neil Mitchell
-
Udo Stenzel
-
Yitzchak Gale