[Haskell-cafe] testing for exceptions

Richard A. O'Keefe ok at cs.otago.ac.nz
Mon Nov 2 00:21:20 UTC 2015


Simplest hack:

    f2Maybe :: Integer -> Maybe Integer
    f2Maybe n = if n < 0 then Nothing else Just (g n)
      where g 0 = 1
            g n = if odd n then x*2 else x
                  where x = (g (n `div` 2))^2

There is no need to *keep* checking for a negative number in the
recursive code.
> 
> f2Maybe :: Integer -> Maybe Integer 
> f2Maybe n 
>    | n > 0  = Nothing 
>    | n == 0  = Just 1 
>    | even n = Just (f2Maybe ( n `div` 2) ^ 2)
>    | odd n  = Just ((f2Maybe ( n `div` 2) ^ 2) * 2) 

Let's try another tack.
The recursive calls (f2Maybe (n `div` 2))
give you a value of type Maybe Integer.
You want to transform the Integer part.
This is an instance of

 Monad m => m a -> (a -> b) -> m b.

There's something almost like that in Control.Monad:

  liftM :: (a -> b) -> m a -> m b

So what you want is

  liftM (\x -> x^2)   (f2Maybe (n `div` 2))
  liftM (\x -> x^2*2) (f2Maybe (n `div` 2))

So

  f2Maybe n | n < 0 = Nothing
  f2Maybe 0         = Just 1
  f2Maybe n         = liftM (if odd n then (\x -> x^2*2) else (\x -> x^2))
                            (f2Maybe (n `div` 2))

Or you could use 'do' notation:

    f2Maybe n | n < 0 = Nothing
    f2Maybe 0         = Just 1
    f2Maybe n         = do x <- f2Maybe (n `div` 2)
                           return (if odd n then x^2*2 else x^2)

Whatever you do, the key thing is that you HAVE a value
wrapped up in Just and you need to unwrap it, operate on the
value, and rewrap it.

So you could do something like

rewrap _ Nothing  = Nothing
rewrap f (Just x) = Just (f x)

and then

    f2Maybe n | n < 0 = Nothing
    f2Maybe 0         = Just 1
    f2Maybe n         = rewrap (\x -> if odd n then x^2*2 else x^2)
                               (f2Maybe (n `div` 2))

and presto, chango! we've just re-invented liftM under the name
'rewrap'.   





More information about the Haskell-Cafe mailing list