[Haskell-cafe] Monad transformers, design

2010-07-31 Thread Tony Morris
Hello I have a question regarding monad transformers and how to design
an API with a transformer. I have a narrowed code example of the
question. Please see the questions in the comments below.



import Data.Monoid
import Control.Monad

-- Suppose some data type
newtype Inter a = Inter (Int - a)

-- and a monad transformer for that data type.
newtype InterT m a = InterT (m (Inter a))

-- It's easy to implement this type-class
instance (Monoid a) = Monoid (Inter a) where
  mempty = Inter (const mempty)
  Inter a `mappend` Inter b = Inter (a `mappend` b)

-- and for the transformer too by lifting into the monad
instance (Monad m, Monoid a) = Monoid (InterT m a) where
  mempty = InterT (return mempty)
  InterT a `mappend` InterT b = InterT (liftM2 mappend a b)

-- But what about this type-class?
class Ints a where
  ints :: a - Int - Int

-- Seems easy enough
instance (Integral a) = Ints (Inter a) where
  ints (Inter a) n = fromIntegral (a n)

-- OH NO!
{-
instance (Monad m, Integral a) = Ints (InterT m a) where
  ints (InterT a) n = error OH NO!
-}

-- We could try this
class Copointed f where
  copoint :: f a - a

-- but it seems rather impractical
instance (Copointed m, Integral a) = Ints (InterT m a) where
  ints (InterT a) = ints (copoint a)

{-
So it seems that for some type-classes it is possible to implement
for both the data type and the transformer, but not all type-classes.

Is there a general approach to this problem?
-}



-- 
Tony Morris
http://tmorris.net/


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


Re: [Haskell-cafe] Monad transformers, design

2010-07-31 Thread Ross Paterson
On Sat, Jul 31, 2010 at 10:56:31PM +1000, Tony Morris wrote:
 -- Suppose some data type
 newtype Inter a = Inter (Int - a)
 
 -- and a monad transformer for that data type.
 newtype InterT m a = InterT (m (Inter a))

The monad transformer should be Inter (m a).
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monad transformers, design

2010-07-31 Thread Tony Morris
gah you're right, @mtl had confuzzled me.

Well that changes things then, thanks.

Ross Paterson wrote:
 On Sat, Jul 31, 2010 at 10:56:31PM +1000, Tony Morris wrote:
   
 -- Suppose some data type
 newtype Inter a = Inter (Int - a)

 -- and a monad transformer for that data type.
 newtype InterT m a = InterT (m (Inter a))
 

 The monad transformer should be Inter (m a).
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

   

-- 
Tony Morris
http://tmorris.net/


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


[Haskell-cafe] Monad transformers (was: Is my code too complicated?)

2010-07-03 Thread Roman Cheplyaka
* Andrew Coppin andrewcop...@btinternet.com [2010-07-03 14:20:14+0100]
 In my experience, using more than one monad transformer at once makes
 code utterly incomprehensible.

See X monad (xmonad) for an counterexample.

-- | The X monad, 'ReaderT' and 'StateT' transformers over 'IO'
-- encapsulating the window manager configuration and state,
-- respectively.
--
-- Dynamic components may be retrieved with 'get', static components
-- with 'ask'. With newtype deriving we get readers and state monads
-- instantiated on 'XConf' and 'XState' automatically.
--
newtype X a = X (ReaderT XConf (StateT XState IO) a)

-- 
Roman I. Cheplyaka :: http://ro-che.info/
Don't let school get in the way of your education. - Mark Twain
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monad transformers

2010-07-03 Thread Andrew Coppin

Roman Cheplyaka wrote:

* Andrew Coppin andrewcop...@btinternet.com [2010-07-03 14:20:14+0100]
  

In my experience, using more than one monad transformer at once makes
code utterly incomprehensible.



See X monad (xmonad) for an counterexample.

-- | The X monad, 'ReaderT' and 'StateT' transformers over 'IO'
-- encapsulating the window manager configuration and state,
-- respectively.
--
-- Dynamic components may be retrieved with 'get', static components
-- with 'ask'. With newtype deriving we get readers and state monads
-- instantiated on 'XConf' and 'XState' automatically.
--
newtype X a = X (ReaderT XConf (StateT XState IO) a)
  


In my experience, defining a type representing several stacked monad 
transformers is the easy part. The hard part is figuring out how in the 
name of God to run the resulting computation, or how to access functions 
burried at various levels of the stack.


From what I've seen, it usually ends up being faster and easier to just 
define a custom monad that does exactly what you want, and then use that.


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


Re: [Haskell-cafe] Monad transformers

2010-07-03 Thread Roman Cheplyaka
* Andrew Coppin andrewcop...@btinternet.com [2010-07-03 15:07:17+0100]
 Roman Cheplyaka wrote:
 * Andrew Coppin andrewcop...@btinternet.com [2010-07-03 14:20:14+0100]
 In my experience, using more than one monad transformer at once makes
 code utterly incomprehensible.
 
 See X monad (xmonad) for an counterexample.
 
 -- | The X monad, 'ReaderT' and 'StateT' transformers over 'IO'
 -- encapsulating the window manager configuration and state,
 -- respectively.
 --
 -- Dynamic components may be retrieved with 'get', static components
 -- with 'ask'. With newtype deriving we get readers and state monads
 -- instantiated on 'XConf' and 'XState' automatically.
 --
 newtype X a = X (ReaderT XConf (StateT XState IO) a)
 
 In my experience, defining a type representing several stacked monad
 transformers is the easy part.

Of course it is. It wasn't my intention just to show you how easy it is
to define a newtype in Haskell :)

I just showed you a monad stack which is successfully used in xmonad --
and you really need to read the code a bit to get the taste of it.

 The hard part is figuring out how in
 the name of God to run the resulting computation

It is run just in the one place, so you don't need to think about it each
time you do some changes.

 or how to access functions burried at various levels of the stack.

See above:
-- Dynamic components may be retrieved with 'get', static components
-- with 'ask'.

So you use ask to get some configuration variable (reader monad is used
for configuration in xmonad) and get/put/modify to deal with dynamic
state of application. You use liftIO (abbreviated to 'io') to run IO
computations.

 From what I've seen, it usually ends up being faster and easier to
 just define a custom monad that does exactly what you want, and then
 use that.

In which way is it faster and easier? Can you show faster and easier
implementation of the X monad shown above?

-- 
Roman I. Cheplyaka :: http://ro-che.info/
Don't let school get in the way of your education. - Mark Twain
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monad transformers

2010-07-03 Thread Andrew Coppin

Roman Cheplyaka wrote:

* Andrew Coppin andrewcop...@btinternet.com [2010-07-03 15:07:17+0100]
  

In my experience, defining a type representing several stacked monad
transformers is the easy part.



Of course it is. It wasn't my intention just to show you how easy it is
to define a newtype in Haskell :)

I just showed you a monad stack which is successfully used in xmonad --
and you really need to read the code a bit to get the taste of it.
  


OK, fair enough then.


The hard part is figuring out how in
the name of God to run the resulting computation



It is run just in the one place, so you don't need to think about it each
time you do some changes.
  


As I say, every time I've tried to do this, I end up writing a function 
to run this stuff, and it typically takes a few hours to reach the 
point where it type-checks.



or how to access functions burried at various levels of the stack.



See above:
-- Dynamic components may be retrieved with 'get', static components
-- with 'ask'.

So you use ask to get some configuration variable (reader monad is used
for configuration in xmonad) and get/put/modify to deal with dynamic
state of application. You use liftIO (abbreviated to 'io') to run IO
computations.
  


In other words, somebody has written a combinatorial explosion of class 
instances to automate some of the lifting.



From what I've seen, it usually ends up being faster and easier to
just define a custom monad that does exactly what you want, and then
use that.



In which way is it faster and easier?


It's faster and easier to write the code because I don't have to spend 
multiple hours trying to work out how to make it type-check. Whether 
it's any faster at run-time, I have no idea...


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


Re: [Haskell-cafe] Monad transformers

2010-07-03 Thread Evan Laforge
 As I say, every time I've tried to do this, I end up writing a function to
 run this stuff, and it typically takes a few hours to reach the point
 where it type-checks.

It took me a while the first time, but then I just learned the pattern
and I do it that way every time.  Here's my pattern:

type SomethingStack m = Monad1T Args (Monad2T Args (Monad3T Args m))
newtype SomethingT m a = SomethingT (SomethingStack m a)
  deriving (Functor, Monad, MonadIO, MonadError MyError, KitchenSink)
run_something_t (SomethingT m) = m

run :: (Monad m) = SomethingT m a - m (a, MonadCrap, MonadCrap, ...)
run = Monad3T.run args . Monad2T.run args . Monad1T.run args . run_something_t

Or if you don't need the polymorphism, just stick a
'Identity.runIdentity' before Monad3T.run and make a

type Something = SomethingT Identity

The tricky bit is that you run them inside-out so the composition
looks like the stack backwards.  And sometimes mtl's 'run' functions
have an inconvenient arg order (e.g. StateT), so you have to flip
them.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monad transformers

2010-07-03 Thread Mike Dillon
begin Andrew Coppin quotation:
 Roman Cheplyaka wrote:
 See above:
 -- Dynamic components may be retrieved with 'get', static components
 -- with 'ask'.
 
 So you use ask to get some configuration variable (reader monad is used
 for configuration in xmonad) and get/put/modify to deal with dynamic
 state of application. You use liftIO (abbreviated to 'io') to run IO
 computations.
 
 In other words, somebody has written a combinatorial explosion of
 class instances to automate some of the lifting.

Well then you need to automate writing the instances too :)

The GeneralizedNewtypeDeriving extension can be used to get instances
for Monad, MonadReader XConf, MonadState XState, and MonadIO
automatically for a newtype like X that should suffice in most cases.

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


Re: [Haskell-cafe] Monad transformers [Stacking monads]

2008-10-07 Thread Dougal Stanton
On Mon, Oct 6, 2008 at 9:48 PM, Andrew Coppin
[EMAIL PROTECTED] wrote:
 Andrew Coppin wrote:

 I have some longwinded code that works, but I'm still thinking about how
 to do this more elegantly. It looks like what I really need is something
 like

  type M = StateT State (ResultSetT (ErrorT ErrorType Identity))

 Is that the correct ordering?

 If so, I guess that means I have to somehow construct ResultSetT. Is there
 an easy way to do that, given that I already have ResultSet? For example, if
 I put ResultSet into Traversable, would that let me do it?

 ...and again I'm talking to myself... :-/

 So after much experimentation, I have managed to piece together the
 following facts:

 - It appears that the outer-most monad transformer represents the inner-most
 monad. So StateT Foo ListT means a list of stateful computations, while
 ListT (StateT Foo) means a stateful list of computations.

Have you read Monad Transformers Step by Step [1] by Martin
Grabmueller? It's a fantastic introduction to these beasties, leading
the reader through a series of transformations from pure code to using
about 4 different monads/transformers for all sorts of extra features.

Seriously recommend it.

[]: http://uebb.cs.tu-berlin.de/~magr/pub/Transformers.pdf



Cheers,

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


Re: [Haskell-cafe] Monad transformers [Stacking monads]

2008-10-07 Thread Andrew Coppin
The good news: I managed to turn ResultSet into a monad transformer. 
Yay, me!


The bad news: It generates the entire result set before returning 
anything to the caller.


In other words, it works perfectly for finite result sets, and locks up 
forever on infinite result sets. Since the entire *point* of the monad 
is to handle infinite result sets correctly, that's kind-of a problem. 
And one that I see absolutely no way of fixing. :-(


Basically, the core code is something like

 raw_bind :: (Monad m) = [[x]] - (x - m (ResultSet y)) - m 
(ResultSet y)

 raw_bind [] f = return empty
 raw_bind (xs:xss) f = do
   rsYs - mapM f xs
   rsZ - raw_bind xss f
   return (foldr union (cost rsZ) rsYs)

As you can see, this generates all of rsZ before attempting to return 
anything to the caller. And I'm really struggling to see any way to 
avoid that.


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


Re: [Haskell-cafe] Monad transformers [Stacking monads]

2008-10-07 Thread Daniel Fischer
Am Dienstag, 7. Oktober 2008 20:27 schrieb Andrew Coppin:
 The good news: I managed to turn ResultSet into a monad transformer.
 Yay, me!

 The bad news: It generates the entire result set before returning
 anything to the caller.

 In other words, it works perfectly for finite result sets, and locks up
 forever on infinite result sets. Since the entire *point* of the monad
 is to handle infinite result sets correctly, that's kind-of a problem.
 And one that I see absolutely no way of fixing. :-(

 Basically, the core code is something like

   raw_bind :: (Monad m) = [[x]] - (x - m (ResultSet y)) - m
 (ResultSet y)
   raw_bind [] f = return empty
   raw_bind (xs:xss) f = do
 rsYs - mapM f xs
 rsZ - raw_bind xss f
 return (foldr union (cost rsZ) rsYs)

 As you can see, this generates all of rsZ before attempting to return
 anything to the caller. And I'm really struggling to see any way to
 avoid that.


Maybe it is as simple as

raw_bind (xs:xss) f = do
 rsYs - mapM f xs
 ~rsZ - raw_bind xss f
 return (foldr union (cost rsZ) rsYs)

then rsZ should only be evaluated when it's needed
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monad transformers [Stacking monads]

2008-10-07 Thread Daniel Fischer
Am Dienstag, 7. Oktober 2008 22:09 schrieb Andrew Coppin:
 Daniel Fischer wrote:
  Am Dienstag, 7. Oktober 2008 20:27 schrieb Andrew Coppin:
  Basically, the core code is something like
 
raw_bind :: (Monad m) = [[x]] - (x - m (ResultSet y)) - m
  (ResultSet y)
raw_bind [] f = return empty
raw_bind (xs:xss) f = do
  rsYs - mapM f xs
  rsZ - raw_bind xss f
  return (foldr union (cost rsZ) rsYs)
 
  As you can see, this generates all of rsZ before attempting to return
  anything to the caller. And I'm really struggling to see any way to
  avoid that.
 
  Maybe it is as simple as
 
  raw_bind (xs:xss) f = do
   rsYs - mapM f xs
   ~rsZ - raw_bind xss f
   return (foldr union (cost rsZ) rsYs)
 
  then rsZ should only be evaluated when it's needed

 Ooo... lazy pattern matching? Can somebody explain to me, _very
 slowy_, exactly what that means?

 If I'm doing this right, it seems that

   rsZ - raw_bind xss f
   ...

 desugards to

   raw_bind xss f = \rsZ - ...

 If I'm not mistaken, the rsZ variable shouldn't be evaluated until
 needed *anyway*, so what is lazy pattern matching buying me here?

That depends on how your Monad (and union) is implemented, it may or may not 
make a difference. I must admit that I didn't really look at the code you 
posted, so I don't know what would be the case here. It was just an easy 
thing to try which *might* help.
I will take a look, can't guarantee any result.


 Also, suppose I stack ResultSetT on top of IO. In that case, f is
 allowed to perform externally-visible I/O operations. If there really
 *is* a way to delay the execution of certain calls until the data is
 needed... well that doesn't look right somehow. In fact, it looks like
 what I'm trying to do *should* be impossible. :-/ Oh dear...

To delay computations in IO until needed, you can use unsafeInterleaveIO:


uiSeq :: [IO Int] - IO [Int]
uiSeq [] = do
putStrLn End of list
return []
uiSeq (a:as) = do
x - a
putStrLn $ got the value  ++ show x
xs - unsafeInterleaveIO $ uiSeq as
return (x:xs)

verbRet :: Int - IO Int
verbRet k = do
putStrLn $ Returning  ++ show k
return k

*Main fmap (take 3) $ uiSeq [verbRet k | k - [1 .. 10]]
Returning 1
got the value 1
[1Returning 2
got the value 2
,2Returning 3
got the value 3
,3]
*Main fmap (take 3) $ sequence [verbRet k | k - [1 .. 10]]
Returning 1
Returning 2
Returning 3
Returning 4
Returning 5
Returning 6
Returning 7
Returning 8
Returning 9
Returning 10
[1,2,3]

But unsafeInterleaveIO doesn't have its first six letters without a reason, so 
be careful when you want to use it (in general, don't).
And of course you can't use it in generic monad transformer code, you might 
however be able to use

class Monad m = LazyMonad m where
lazyBind :: m a - (a - m b) - m b
lazySequence :: [m a] - m [a]

instance LazyMonad IO where
lazyBind  ma f = do
a - unsafeInterleaveIO ma
f a
lazySequence [] = return []
lazySequence (a:as) = do
x - a
xs - unsafeInterleaveIO $ lazySequence as
return (x:xs)

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


Re: [Haskell-cafe] Monad transformers [Stacking monads]

2008-10-07 Thread David Menendez
On Tue, Oct 7, 2008 at 5:07 PM, Daniel Fischer [EMAIL PROTECTED] wrote:
 Am Dienstag, 7. Oktober 2008 22:09 schrieb Andrew Coppin:
 Daniel Fischer wrote:
  Maybe it is as simple as
 
  raw_bind (xs:xss) f = do
   rsYs - mapM f xs
   ~rsZ - raw_bind xss f
   return (foldr union (cost rsZ) rsYs)
 
  then rsZ should only be evaluated when it's needed

 Ooo... lazy pattern matching? Can somebody explain to me, _very
 slowy_, exactly what that means?
snip
 If I'm not mistaken, the rsZ variable shouldn't be evaluated until
 needed *anyway*, so what is lazy pattern matching buying me here?

 That depends on how your Monad (and union) is implemented, it may or may not
 make a difference. I must admit that I didn't really look at the code you
 posted, so I don't know what would be the case here. It was just an easy
 thing to try which *might* help.

Unless you're pattern matching against a constructor, which rsZ is
not, I think lazy pattern matching is no different from regular
pattern matching.

-- 
Dave Menendez [EMAIL PROTECTED]
http://www.eyrie.org/~zednenem/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monad transformers [Stacking monads]

2008-10-07 Thread David Menendez
On Mon, Oct 6, 2008 at 4:48 PM, Andrew Coppin
[EMAIL PROTECTED] wrote:
 Andrew Coppin wrote:

 I have some longwinded code that works, but I'm still thinking about how
 to do this more elegantly. It looks like what I really need is something
 like

  type M = StateT State (ResultSetT (ErrorT ErrorType Identity))

 Is that the correct ordering?

Pretty much.

 For reference, I humbly present ResultSet.hs:

There are actually several ways to make ResultSetT from ResultSet,
depending on how you want to handle the inner monad. There are two
popular ways to make a transformer variant of [], of which the easier
looks something like this:

newtype ListT m a = ListT { unListT :: m (Stream m a) }
data Stream m a = Nil | Cons a (m (Stream m a))

Using that and your code as a pattern, I've come up with the guts of a
similar transformer, included below. Like your code, it maintains a
list of answers at each depth. The effects of each depth are deferred
until some code (e.g., to_list) demands it, but the effects associated
with any answer at a given depth are linked. The resulting code, I
imagine, is not very efficient, but it shouldn't be too awful. I've
tried to keep things structurally similar to your code, to hopefully
make it clearer what is happening.

I also recommend trying alternatives like Oleg's FBackTrackT. In that
code, mplus corresponds to union.

http://okmij.org/ftp/Haskell/FBackTrackT.hs



import Control.Monad

newtype ResultSetT m a = Pack { unpack :: m (Stream m a) }

data Stream m a = Nil | Cons [a] (m (Stream m a))

-- this is just the important parts, the rest should be fairly straightforward.

raw_lift :: (Monad m) = m a - m (Stream m a)
raw_lift = liftM (\x - Cons [x] (return Nil))

raw_union :: (Monad m) = Stream m a - Stream m a - Stream m a
raw_union Nil yss = yss
raw_union xss Nil = xss
raw_union (Cons xs xss) (Cons ys yss) = Cons (xs ++ ys) (liftM2
raw_union xss yss)


raw_bind :: (Monad m) = m (Stream m a) - (a - m (Stream m b)) - m
(Stream m b)
raw_bind xss f = xss = work (return Nil)
where
work out Nil = out
work out (Cons xs xss) = do
yss - foldr (liftM2 raw_union) out $ map f xs
return undefined
case yss of
Nil - return $ Cons [] (xss = work (return Nil))
Cons ys yss - return $ Cons ys (xss = work yss)


from_list :: (Monad m) = [[a]] - ResultSetT m a
from_list = Pack . foldr (\xs xss - return $ Cons xs xss) (return Nil)

to_list :: (Monad m) = ResultSetT m a - m [[a]]
to_list (Pack m) = m = work
where
work Nil = return [[]]
work (Cons xs xss) = liftM (xs:) (xss = work)

limit :: (Monad m) = Int - ResultSetT m a - ResultSetT m a
limit n (Pack xss) = Pack (xss = work n)
where
work n (Cons xs xss) | n  0 = return $ Cons xs (xss = work (n-1))
work _ _ = return Nil

-- 
Dave Menendez [EMAIL PROTECTED]
http://www.eyrie.org/~zednenem/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monad transformers [Stacking monads]

2008-10-06 Thread Andrew Coppin

Andrew Coppin wrote:
I have some longwinded code that works, but I'm still thinking about 
how to do this more elegantly. It looks like what I really need is 
something like


 type M = StateT State (ResultSetT (ErrorT ErrorType Identity))

Is that the correct ordering?

If so, I guess that means I have to somehow construct ResultSetT. Is 
there an easy way to do that, given that I already have ResultSet? For 
example, if I put ResultSet into Traversable, would that let me do it?


...and again I'm talking to myself... :-/

So after much experimentation, I have managed to piece together the 
following facts:


- It appears that the outer-most monad transformer represents the 
inner-most monad. So StateT Foo ListT means a list of stateful 
computations, while ListT (StateT Foo) means a stateful list of 
computations.


- Each transformer seems to be defined as a newtype such that we have 
ListT :: m [x] - ListT m x and runListT :: ListT m x - m [x].


- By some magical process that I do not yet understand, I can wrap a 
StateT in 17 other transformers, and yet get and put do not require 
any lifting. (God only knows what happens if you were to use two StateTs 
in the same monad stack...)


What I haven't figured out yet is how to turn ResultSet into ResultSetT. 
I seem to just spend most of my time being frustrated by the type 
checker. A useful trick is to say things like


 :t lift (undefined :: ListT Int)

to figure out what type the various parts of a complex multi-monad 
expression have. (By now I'm seeing things like return . return . 
return, which is just far out.) But sometimes I find myself desperately 
wanting to take some block of code and say what type does *this* part 
of the expression have? or if I do x = y when y has *this* type, 
what type must x have? It can be very hard to work this out mentally, 
and unfortunately there isn't any tool I'm aware of that will help you 
in this matter.


After much testing, it appears that the utopian type definition at the 
very top of this message is in fact the thing I need. So if I can just 
figure out how to construct ResultSetT than I'm done. It looks like 
trying to build it from ResultSet is actually harder than just 
implementing it directly, so I'm going to try a direct transformer 
implementation instead. But it's seriously hard work!


For reference, I humbly present ResultSet.hs:



module Orphi.Kernel.ResultSet (ResultSet (), from_list, to_list, build, 
limit, cost, union) where


data ResultSet x = Pack {unpack :: [[x]]} deriving (Eq)

instance (Show x) = Show (ResultSet x) where
 show (Pack xss) = from_list  ++ show xss

instance Monad ResultSet where
 fail msg = Pack []
 return x = Pack [[x]]
 (Pack xss) = f = Pack $ raw_bind xss (unpack . f)

raw_bind :: [[x]] - (x - [[y]]) - [[y]]
raw_bind = work []
 where
   work out []   _ = out
   work out (xs:xss) f =
 let yss = foldr raw_union out (map f xs)
 in  if null yss
   then []   : work [] xss f
   else head yss : work (tail yss) xss f

raw_union :: [[x]] - [[x]] - [[x]]
raw_union []   yss  = yss
raw_union xss  []   = xss
raw_union (xs:xss) (ys:yss) = (xs ++ ys) : raw_union xss yss



from_list :: [[x]] - ResultSet x
from_list = Pack

to_list :: ResultSet x - [[x]]
to_list = unpack

build :: [x] - ResultSet x
build = from_list . map return

limit :: Int - ResultSet x - ResultSet x
limit n (Pack xss) = Pack (take n xss)

cost :: ResultSet x - ResultSet x
cost (Pack xss) = Pack ([]:xss)

union :: ResultSet x - ResultSet x - ResultSet x
union (Pack xss) (Pack yss) = Pack (raw_union xss yss)

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


Re: [Haskell-cafe] Monad transformers [Stacking monads]

2008-10-06 Thread Anton van Straaten

Andrew Coppin wrote:
If so, I guess that means I have to somehow construct ResultSetT. Is 
there an easy way to do that, given that I already have ResultSet? 


I haven't been following this thread closely, so forgive if this was 
already discussed, but my understanding is that the answer is no, in 
general.


In the paper Monad Transformers and Modular Interpreters[*], Section 8 
(Lifting Operations) touches on some of the issues.  That's from 1995 
- I don't know if any progress on this has been made since then, other 
than that a standard set of the most common monad transformers is now 
available.


Anton

[*] http://citeseerx.ist.psu.edu/viewdoc/summary?doi=10.1.1.17.268

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


Re: [Haskell-cafe] Monad transformers [Stacking monads]

2008-10-06 Thread Reid Barton
Hi Andrew,

On Mon, Oct 06, 2008 at 09:48:51PM +0100, Andrew Coppin wrote:
 data ResultSet x = Pack {unpack :: [[x]]} deriving (Eq)

Your ResultSet monad is roughly equivalent to

newtype Nat = Nat Int
instance Monoid Nat where
  mempty = Nat 0
  (Nat x) `mappend` (Nat y) = Nat (x+y)
type ResultSet' = WriterT Nat []
-- ResultSet' x = [(x, Nat)]

where unpack :: ResultSet' x - [[x]] gives a list whose nth element
is the list of alternatives whose cost (Nat data) is n (with
trailing [] lists removed).  Except that using [[x]] internally lets
you be lazy about handling items of high cost.  (This is kind of neat
actually.)

I'd therefore guess that if there is an associated monad transformer
ResultSetT, it's similarly equivalent to

ResultSetT' m x = WriterT Nat (ListT m x)

where ListT is some version of ListT done right.  But on the other
hand, as I understand ListT done right, you can think of ListT m x
as a list of xs where you have to perform an action in the m monad
to get each successive value in the list.  The equivalence converting
ResultSet' to ResultSet sort of tears up the list in a way I'm not
sure is compatible with inserting a monad like that.


Once again, all this high-falutin' nonsense corresponds to really
concrete questions about what you want your code to *actually do*.
Consider your original problem

  run :: State - Foo - Either ErrorType (ResultSet State)

  run_and :: State - Foo - Foo - Either ErrorType (ResultSet State)
  {- some Either-ified version of
 run_and :: State - Foo - Foo - ResultSet State
 run_and s0 x y = do
   s1 - run s0 x
   s2 - run s1 y
   return s2
  -}

Say run s0 x returns many different possibilities s1 (with varying
costs).  And suppose run s1 y is a (Left err) for some of these s1 and
a (Right whatever) for others.  When should the overall result of
run_and be a Left and when should it be a Right?  And *which error*
should you return if there's more than one Left?  Do you really want
to check whether every run s1 y is a (Right whatever)?  In that case
you are not gaining much from the laziness of ResultSet and might as
well use ResultSet'.  Until you decide the answer to questions of this
kind, you can't know how to best structure your code.

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


[Haskell-cafe] Monad transformers [Stacking monads]

2008-10-05 Thread Andrew Coppin

David Menendez wrote:

So it might be possible to rewrite your code along these lines:

type M = StateT State []

run :: Foo - M ()

runOr :: Foo - Foo - M ()
runOr x y = mplus (run x) (run y)

runAnd :: Foo - Foo - M ()
runAnd x y = run x  run y

The type StateT State [] alpha is isomorphic to State - [(alpha,
State)], which means that each of the computations in mplus gets its
own copy of the state.

There are a few ways to add exceptions to this, depending on how you
want the exceptions to interact with the non-determinism.
  
2. StateT State (NondetT (Either ErrorType)) alpha
  


I have some longwinded code that works, but I'm still thinking about how 
to do this more elegantly. It looks like what I really need is something 
like


 type M = StateT State (ResultSetT (ErrorT ErrorType Identity))

Is that the correct ordering?

If so, I guess that means I have to somehow construct ResultSetT. Is 
there an easy way to do that, given that I already have ResultSet? For 
example, if I put ResultSet into Traversable, would that let me do it?


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


Re: [Haskell-cafe] Monad transformers

2005-05-08 Thread Tomasz Zielonka
On Sun, May 08, 2005 at 07:54:43PM +0400, Max Vasin wrote:
 Hello!
 
 Suppose we have functions 
 
 f :: ReaderT env monad1 rtype
 g :: Reader env rtype
 
 and we need to call g from f.
 
 Currently I write something like
 
 f = do env - ask
let r = runReader g env
doSmth r
 
 I don't like doing it this way (I need to get environment and
 explicitly pass it). Is there another way to get things done?

How about:

toReaderT :: (Monad m) = Reader r a - ReaderT r m a
toReaderT (Reader f) = ReaderT (return . f)

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