
Is there a built-in function that already does this? foo :: (a -> b) -> Maybe a -> Maybe b foo f m | isNothing m = Nothing | otherwise = Just (f (fromJust m)) *Main> foo (+2) (Just 3) Just 5 *Main> foo (+2) Nothing Nothing If so what is it? If not, what should I call it? Thanks -John

On Jan 25, 2007, at 9:15 , John Ky wrote:
Is there a built-in function that already does this?
foo :: (a -> b) -> Maybe a -> Maybe b foo f m | isNothing m = Nothing | otherwise = Just (f (fromJust m))
Nothing specific to Maybe, because the more general liftM (over monads) or fmap (over functors) already does it. -- brandon s. allbery [linux,solaris,freebsd,perl] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH

liftM (+2) (Just 3 Just 5
:t liftM
forall r (m :: * -> *) a1. (Monad m) => (a1 -> r) -> m a1 -> m r
liftM (+2) Nothing
Nothing
(Thanks to allbery_b for contributing to the discussion on #haskell)
On 1/25/07, John Ky
Is there a built-in function that already does this?
foo :: (a -> b) -> Maybe a -> Maybe b foo f m | isNothing m = Nothing | otherwise = Just (f (fromJust m))
*Main> foo (+2) (Just 3) Just 5 *Main> foo (+2) Nothing Nothing
If so what is it?
If not, what should I call it?
Thanks
-John
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

fmap. e.g.:
Prelude> fmap ('c':) (Just "a")
Just "ca"
Prelude> fmap ('c':) Nothing
Nothing
Prelude>
/g
On 1/25/07, John Ky
Is there a built-in function that already does this?
foo :: (a -> b) -> Maybe a -> Maybe b foo f m | isNothing m = Nothing | otherwise = Just (f (fromJust m))
*Main> foo (+2) (Just 3) Just 5 *Main> foo (+2) Nothing Nothing
If so what is it?
If not, what should I call it?
Thanks
-John
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- It is myself I have never met, whose face is pasted on the underside of my mind.

John Ky wrote:
Is there a built-in function that already does this?
Usually, when I have a question like this, I try Hoogle first: http://www.haskell.org/hoogle/?q=%28a+-%3E+b%29+-%3E+Maybe+a+-%3E+Maybe+b Unfortunatly, the right answer (fmap) is on the second page of results. (I am really excited for the new version of Hoogle, its supposed to be pretty close to release)
foo :: (a -> b) -> Maybe a -> Maybe b foo f m | isNothing m = Nothing | otherwise = Just (f (fromJust m))
*Main> foo (+2) (Just 3) Just 5 *Main> foo (+2) Nothing Nothing
Prelude> fmap (+2) (Just 2) Just 4 Prelude> fmap (+2) Nothing Nothing it works over all Functors, so list also works: Prelude> fmap (+2) [2,3] [4,5] Prelude> fmap (+2) [] [] and Map and so on. -- Alan Falloon

Hi Alan,
Usually, when I have a question like this, I try Hoogle first: http://www.haskell.org/hoogle/?q=%28a+-%3E+b%29+-%3E+Maybe+a+-%3E+Maybe+b
Unfortunatly, the right answer (fmap) is on the second page of results.
The reason for this is that Hoogle 3 doesn't understand higher-kinded type classes, i.e. Monad and Functor, which means that fmap doesn't match as closely as it should do. Hoogle 4 would give fmap as the first result, I'm pretty sure.
(I am really excited for the new version of Hoogle, its supposed to be pretty close to release)
Me too, but you'll probably have to wait a few more months yet - but the various components are coming together nicely. Thanks Neil
participants (6)
-
Al Falloon
-
Andrew Wagner
-
Brandon S. Allbery KF8NH
-
J. Garrett Morris
-
John Ky
-
Neil Mitchell