[Haskell-cafe] state and exception or types again...

Brian Hulley brianh at metamilk.com
Tue Aug 29 05:02:38 EDT 2006


Andrea Rossato wrote:
> Il Tue, Aug 29, 2006 at 07:45:46AM +0100, Brian Hulley ebbe a
> scrivere:
>> Andrea Rossato wrote:
>>> Il Mon, Aug 28, 2006 at 09:28:02PM +0100, Brian Hulley ebbe a
>>> scrivere:
>>>> where the 4th element of the tuple is True iff we can continue or
>>>> False iff an exception occurred.
>>>
>>> I'm starting to believe that the best method is just take the way
>>> StateT takes... without reinventing the wheel...
>>
>> The solution I gave was very close to being correct. I enclose a
>> tested example below - you'll need to adapt it to do evaluation but
>> it shows an exception being raised.
>
> I said I think that the StateT approach is the one to take only
> because I believe that the complexity of the definition of >>= is
> getting unmanageable, that is, as far as I understand, contrary to the
> spirit of haskell, and functional programming in general.

>
> so, start getting my hands dirty in monadic combinations is probably
> the best for improving my knowledge of haskell and functional
> programming.
> what do you think?

Hi -
Yes I agree the StateT/monad transformer approach is probably best in the 
long run, since by using the standard monad transformers, you will get code 
that will scale better to handle more complexities later, and has the 
advantage of being already tested so you can be sure the resulting monads 
will obey all the monad laws. Also, there are a lot of tutorials about how 
to use them to solve different problems.

Just for interest, I enclose another version of the SOIE implementation 
which I think is closer to what you originally intended. I've used two 
constructors for the result to avoid having to use (undefined), but the 
whole function is still wrapped inside a single constructor newtype:

module Test where

import Control.Monad

data Result a
    = Good a State Output
    | Bad State Output
    deriving Show

newtype Eval_SOI a = SOIE {runSOIE :: State -> Result a}

type State = Int
type Output = String

raise e = SOIE (\s -> Bad s e)

instance Monad Eval_SOI where
    return a = SOIE (\s -> Good a s "")

    m >>= f = SOIE $ \x ->
        case runSOIE m x of
            Good a y o1 ->
                case runSOIE (f a) y of
                    Good b z o2 -> Good b z (o1 ++ o2)
                    Bad z o2 -> Bad z (o1 ++ o2)
            Bad z o2 -> Bad z o2  -- (*)


display t = SOIE(\s -> Good () s t)

test = runSOIE (do
   display "hello"
   raise "Exception"
   display "Foo"
  ) 0

(*) This line is essential, because the (Bad z o2) on the lhs has type 
(Eval_SOI a) whereas the (Bad z o2) on the rhs has type (Eval_SOI b) (given 
(>>=) :: m a -> (a->m b) -> m b) so something like r@(Bad z o2) -> r would 
not work, though the hope is that the compiler would manage to optimize out 
the re-construction that's needed to satisfy the type checker.

I think monads can be quite difficult to understand until you see that they 
are just quite simple definitions of (return) and (>>=) as above, and 
understanding how the monad transformers are defined (by reading the source 
in ...\libraries\mtl\Control\Monad) means you'll be able to use them with 
absolute confidence rather than having a vague uneasiess that there is some 
"magic" involved.

Happy monadic explorations! :-)
Brian.
-- 
Logic empowers us and Love gives us purpose.
Yet still phantoms restless for eras long past,
congealed in the present in unthought forms,
strive mightily unseen to destroy us.

http://www.metamilk.com 



More information about the Haskell-Cafe mailing list