[PATCH] Add Functor, Applicative, Monad instances for First, Last
Edward Kmett
ekmett at gmail.com
Sat Jun 28 18:00:50 UTC 2014
Looks good to me.
-Edward
On Sat, Jun 28, 2014 at 1:58 PM, Ben Gamari <bgamari.foss at gmail.com> wrote:
> This was proposed in 2011 [1] with no serious objections although wasn't
> implemented until it was again mentioned in 2014 [2].
>
> [1] http://www.haskell.org/pipermail/libraries/2011-January/015552.html
> [2] http://www.haskell.org/pipermail/libraries/2014-June/023228.html
> ---
> libraries/base/Control/Applicative.hs | 11 ++++++++++-
> libraries/base/Data/Monoid.hs | 14 ++++++++++++++
> 2 files changed, 24 insertions(+), 1 deletion(-)
>
> diff --git a/libraries/base/Control/Applicative.hs
> b/libraries/base/Control/Applicative.hs
> index 4e77479..81ce513 100644
> --- a/libraries/base/Control/Applicative.hs
> +++ b/libraries/base/Control/Applicative.hs
> @@ -54,7 +54,7 @@ import Control.Monad (liftM, ap, MonadPlus(..))
> import Control.Monad.ST.Safe (ST)
> import qualified Control.Monad.ST.Lazy.Safe as Lazy (ST)
> import Data.Functor ((<$>), (<$))
> -import Data.Monoid (Monoid(..))
> +import Data.Monoid (Monoid(..), First(..), Last(..))
> import Data.Proxy
>
> import Text.ParserCombinators.ReadP (ReadP)
> @@ -281,6 +281,15 @@ instance (ArrowZero a, ArrowPlus a) => Alternative
> (WrappedArrow a b) where
> empty = WrapArrow zeroArrow
> WrapArrow u <|> WrapArrow v = WrapArrow (u <+> v)
>
> +-- Added in base-4.8.0.0
> +instance Applicative First where
> + pure x = First (Just x)
> + First x <*> First y = First (x <*> y)
> +
> +instance Applicative Last where
> + pure x = Last (Just x)
> + Last x <*> Last y = Last (x <*> y)
> +
> -- | Lists, but with an 'Applicative' functor based on zipping, so that
> --
> -- @f '<$>' 'ZipList' xs1 '<*>' ... '<*>' 'ZipList' xsn = 'ZipList'
> (zipWithn f xs1 ... xsn)@
> diff --git a/libraries/base/Data/Monoid.hs b/libraries/base/Data/Monoid.hs
> index b71176b..bb87243 100644
> --- a/libraries/base/Data/Monoid.hs
> +++ b/libraries/base/Data/Monoid.hs
> @@ -251,6 +251,13 @@ instance Monoid (First a) where
> r@(First (Just _)) `mappend` _ = r
> First Nothing `mappend` r = r
>
> +instance Functor First where
> + fmap f (First x) = First (fmap f x)
> +
> +instance Monad First where
> + return x = First (Just x)
> + First x >>= m = First (x >>= getFirst . m)
> +
> -- | Maybe monoid returning the rightmost non-Nothing value.
> newtype Last a = Last { getLast :: Maybe a }
> deriving (Eq, Ord, Read, Show, Generic, Generic1)
> @@ -260,6 +267,13 @@ instance Monoid (Last a) where
> _ `mappend` r@(Last (Just _)) = r
> r `mappend` Last Nothing = r
>
> +instance Functor Last where
> + fmap f (Last x) = Last (fmap f x)
> +
> +instance Monad Last where
> + return x = Last (Just x)
> + Last x >>= m = Last (x >>= getLast . m)
> +
> {-
> {--------------------------------------------------------------------
> Testing
> --
> 1.9.1
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/libraries/attachments/20140628/5701a6a6/attachment.html>
More information about the Libraries
mailing list