[Haskell-cafe] question - which monad to use?

Matthias Fischmann fis at wiwi.hu-berlin.de
Mon Oct 2 12:19:13 EDT 2006


On Mon, Oct 02, 2006 at 11:42:22AM -0400, Tamas K Papp wrote:
> To: haskell-cafe at haskell.org
> From: Tamas K Papp <tpapp at Princeton.EDU>
> Date: Mon, 2 Oct 2006 11:42:22 -0400
> Subject: Re: [Haskell-cafe] question - which monad to use?
> 
> On Mon, Oct 02, 2006 at 11:35:40AM -0400, Tamas K Papp wrote:
> > Matthias,
> > 
> > Sorry if I was not clear in stating the problem.  Your solution works

no problem, i like to be confused by missing facts.  (-: and you gave
enough input for a discussion.


> > type Failure = String
> > data Computation a = Computation (Either Failure a) [a]
> > 
> > instance Monad Computation where
> >     (Computation (Left e) h) >>= f = Computation (Left e) h -- do not proceed
> >     (Computation (Right a) h) >>= f = let r = f a -- result
> >                                           h' = case r of
> >                                                  Left e -> h
> >                                                  Right a' -> a':h
> >                                       in
> >                                         Computation r h'
> >     return (s,c) = Computation (Right (s,c)) [(s,c)]
> 
> sorry, I pasted an older version.  This line should be
> 
>     return a = Computation (Right a) [a]

yeah, that works.  the (>>=) part has two problems:

 (1) according to the Monad class, the type of f is (a -> m b), and
     the type of (a >>= f) is m b.  but in your definition, (a >>= f)
     has the same type as a, no matter what f.

 (2) the cases in the definition of h' shouldn't be of type (Either
     Failure a), but of type (Computation b).

the second one is easy to fix, just add the constructors to the case
switches.  the first is more of a conceptual problem: you want to have
elements of potentially different types in the computation history h.
this is unfortunate, given that you don't want make use of this
flexibility of the class type, but i don't see a quick way around
this.  

i have been meaning to read this for a while, perhaps that could help
you (but i sense it's somewhat of an overkill in your case): Oleg
Kiselyov, Ralf Laemmel, Keean Schupke: Strongly typed heterogeneous
collections, http://homepages.cwi.nl/~ralf/HList/.

donno...


matthias



> > Basically, I want the >>= operator to call f on the last result, if it
> > is not a failure, and append the new result to the list (if it didn't
> > fail).
> > 
> > However, I am getting the following error message:
> > 
> > /home/tpapp/doc/research/pricespread/Main.hs:62:58:
> >     Couldn't match the rigid variable `b' against the rigid variable `a'
> >       `b' is bound by the type signature for `>>='
> >       `a' is bound by the type signature for `>>='
> >       Expected type: [b]
> >       Inferred type: [a]
> >     In the second argument of `Computation', namely `h'
> >     In the definition of `>>=':
> > 	>>= (Computation (Left e) h) f = Computation (Left e) h
> > 
> > I don't know what the problem is.
> > 
> > Thanks,
> > 
> > Tamas
> > 
> > On Mon, Oct 02, 2006 at 03:54:23PM +0200, Matthias Fischmann wrote:
> > 
> > > hi, i don't fully understand your problem, but perhaps you could use
> > > iterate to produce a list or type [Result a], ie, of all computation
> > > steps, and then use this function to extract either result or error
> > > from the list:
> > > 
> > > 
> > > type Failmessage = Int
> > > data Result a = Root a | Failure Failmessage  deriving (Show)
> > > 
> > > f :: [Result a] -> Either a (Int, [Result a])
> > > f cs = f [] cs
> > >     where
> > >     f (Root r:_) [] = Left r
> > >     f l [Failure i] = Right (i, reverse l)
> > >     f l (x:xs)      = f (x:l) xs
> > > 
> > > cs = [Root 1.2, Root 1.4, Root 1.38, Root 1.39121]
> > > cs' = [Root 1.2, Root 1.4, Root 1.38, Failure 1]
> > > 
> > > -- f cs  ==> Left 1.39121
> > > -- f cs' ==> Right (1,[Root 1.2,Root 1.4,Root 1.38])
> > > 
> > > 
> > > (although this way you probably have the list still floating around
> > > somewhere if you process the error returned by f, so f should probably
> > > just drop the traversed part of the list.)
> > > 
> > > hth,
> > > matthias
> > > 
> > > 
> > > 
> > > On Sun, Oct 01, 2006 at 06:00:43PM -0400, Tamas K Papp wrote:
> > > > To: Haskell Cafe <haskell-cafe at haskell.org>
> > > > From: Tamas K Papp <tpapp at Princeton.EDU>
> > > > Date: Sun, 1 Oct 2006 18:00:43 -0400
> > > > Subject: [Haskell-cafe] question - which monad to use?
> > > > 
> > > > Hi,
> > > > 
> > > > I have a computation where a function is always applied to the
> > > > previous result.  However, this function may not return a value (it
> > > > involves finding a root numerically, and there may be no zero on the
> > > > interval).  The whole problem has a parameter c0, and the function is
> > > > also parametrized by the number of steps that have been taken
> > > > previously.
> > > > 
> > > > To make things concrete,
> > > > 
> > > > type Failmessage = Int          -- this might be something more complex
> > > > data Result a = Root a | Failure Failmessage -- guess I could use Either too
> > > > 
> > > > f :: Double -> Int -> Double 0 -> Result Double
> > > > f c0 0 _ = c0
> > > > f c0 j x = {- computation using x, parameters calculated from c0 and j -}
> > > > 
> > > > Then
> > > > 
> > > > c1 = f c0 0 c0
> > > > c2 = f c0 1 c1
> > > > c3 = f c0 2 c2
> > > > ...
> > > > 
> > > > up to cn.
> > > > 
> > > > I would like to
> > > > 
> > > > 1) stop the computation when a Failure occurs, and store that failure
> > > > 
> > > > 2) keep track of intermediate results up to the point of failure, ie
> > > > have a list [c1,c2,c3,...] at the end, which would go to cn in the
> > > > ideal case of no failure.
> > > > 
> > > > I think that a monad would be the cleanest way to do this.  I think I
> > > > could try writing one (it would be a good exercise, I haven't written
> > > > a monad before).  I would like to know if there is a predefined one
> > > > which would work.
> > > > 
> > > > Thank you,
> > > > 
> > > > Tamas


More information about the Haskell-Cafe mailing list