[Haskell-cafe] Maybe use advice

Maciej Piechotka uzytkownik2 at gmail.com
Mon Jun 6 22:14:59 CEST 2011


On Tue, 2011-06-07 at 04:09 +0800, Lyndon Maydwell wrote:
> (missed including cafe)
> 
> f :: [Modification] -> Maybe [Modification]
> and
> f _ = Just $ f ...
> are incompatible
> 


My bad:

f ... = let cs' = (Rotate (x+x') : fromMaybe cs (f cs))
        in fromMaybe cs (f cs)

Or refactoring it:

g l = fromMaybe l (f l)

f (Rotate    x   : Rotate    x'    : cs) = g (Rotate (x+x') : g cs)

Regards

> I managed to get the behaviour I'm after with the use of Either, but
> this really is messy:
> 
> 
> -- Sets of changes
> o (Modifier (Changes [])  i) = Just $ i
> o (Modifier (Changes [c]) i) = Just $ Modifier c i
> o (Modifier (Changes l)   i) = g (f (Left l))
>   where
>     g (Right l) = Just $ Modifier (Changes l) i
>     g (Left  l) = Nothing
> 
>     f (Left  (Scale     x y : Scale     x' y' : l)) =
>         f $ Right $ Scale     (x*x') (y*y') : h (f $ Left l)
>     f (Left  (Translate x y : Translate x' y' : l)) =
>         f $ Right $ Translate (x+x') (y+y') : h (f $ Left l)
>     f (Left  (Rotate    x   : Rotate    x'    : l)) =
>         f $ Right $ Rotate    (x+x')        : h (f $ Left l)
>     f x = x
> 
>     h (Left  l) = l
>     h (Right l) = l
> 
> 
> On Tue, Jun 7, 2011 at 3:11 AM, Maciej Marcin Piechotka
> <uzytkownik2 at gmail.com> wrote:
> > On Mon, 2011-06-06 at 23:38 +0800, Lyndon Maydwell wrote:
> >> I'm writing an optimisation routine using Uniplate. Unfortunately, a
> >> sub-function I'm writing is getting caught in an infinite loop because
> >> it doesn't return Nothing when there are no optimisations left.
> >>
> >> I'd like a way to move the last Just into f, but this makes recursion
> >> very messy. I was wondering if there was a nice way to use something
> >> like the Monad or Applicative instance to help here.
> >>
> >> -- Sets of changes
> >> o (Modifier (Changes [])  i) = Just $ i
> >> o (Modifier (Changes [c]) i) = Just $ Modifier c i
> >> o (Modifier (Changes l)   i) = Just $ Modifier (Changes (f l)) i
> >>   where
> >>     f (Scale     x y : Scale     x' y' : l) = f $ Scale     (x*x') (y*y') : f l
> >>     f (Translate x y : Translate x' y' : l) = f $ Translate (x+x') (y+y') : f l
> >>     f (Rotate    x   : Rotate    x'    : l) = f $ Rotate    (x+x')        : f l
> >>     f l = l
> >>
> >>
> >> Any ideas?
> >
> > Something like:
> >
> > ...
> > f (Rotate    x   : Rotate    x'    : l)
> >    = Just $ f (Rotate (x+x') : fromMaybe l (f l))
> > f l = Nothing -- As far as I understend
> >
> > Regards
> >
> > _______________________________________________
> > Haskell-Cafe mailing list
> > Haskell-Cafe at haskell.org
> > http://www.haskell.org/mailman/listinfo/haskell-cafe
> >
> >


-------------- next part --------------
A non-text attachment was scrubbed...
Name: not available
Type: application/pgp-signature
Size: 836 bytes
Desc: This is a digitally signed message part
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20110606/87509ffa/attachment.pgp>


More information about the Haskell-Cafe mailing list