[commit: ghc] master: Add new `Data.Bifunctor` module (re #9682) (0a290ca)

git at git.haskell.org git at git.haskell.org
Sun Oct 26 08:45:49 UTC 2014


Repository : ssh://git@git.haskell.org/ghc

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/0a290ca0ad599e40ca15a60cc988640f1cfcb4c2/ghc

>---------------------------------------------------------------

commit 0a290ca0ad599e40ca15a60cc988640f1cfcb4c2
Author: Herbert Valerio Riedel <hvr at gnu.org>
Date:   Sun Oct 26 08:49:38 2014 +0100

    Add new `Data.Bifunctor` module (re #9682)
    
    This adds the module `Data.Bifunctor` providing the
    `Bifunctor(bimap,first,second)` class and a couple of instances
    
    This module and the class were previously exported by the `bifunctors`
    package.  In contrast to the original module all `INLINE` pragmas have
    been removed.
    
    Reviewed By: ekmett, austin, dolio
    
    Differential Revision: https://phabricator.haskell.org/D336


>---------------------------------------------------------------

0a290ca0ad599e40ca15a60cc988640f1cfcb4c2
 libraries/base/Data/Bifunctor.hs | 103 +++++++++++++++++++++++++++++++++++++++
 libraries/base/base.cabal        |   1 +
 libraries/base/changelog.md      |   3 ++
 3 files changed, 107 insertions(+)

diff --git a/libraries/base/Data/Bifunctor.hs b/libraries/base/Data/Bifunctor.hs
new file mode 100644
index 0000000..4c84f1c
--- /dev/null
+++ b/libraries/base/Data/Bifunctor.hs
@@ -0,0 +1,103 @@
+{-# LANGUAGE CPP #-}
+{-# LANGUAGE NoImplicitPrelude #-}
+
+-----------------------------------------------------------------------------
+-- |
+-- Module      :  Data.Bifunctor
+-- Copyright   :  (C) 2008-2014 Edward Kmett,
+-- License     :  BSD-style (see the file LICENSE)
+--
+-- Maintainer  :  libraries at haskell.org
+-- Stability   :  provisional
+-- Portability :  portable
+--
+-- /Since: 4.8.0.0/
+----------------------------------------------------------------------------
+module Data.Bifunctor
+  ( Bifunctor(..)
+  ) where
+
+import Control.Applicative  ( Const(..) )
+import Data.Either          ( Either(..) )
+import GHC.Base             ( (.), id )
+
+-- | Formally, the class 'Bifunctor' represents a bifunctor
+-- from @Hask@ -> @Hask at .
+--
+-- Intuitively it is a bifunctor where both the first and second
+-- arguments are covariant.
+--
+-- You can define a 'Bifunctor' by either defining 'bimap' or by
+-- defining both 'first' and 'second'.
+--
+-- If you supply 'bimap', you should ensure that:
+--
+-- @'bimap' 'id' 'id' ≡ 'id'@
+--
+-- If you supply 'first' and 'second', ensure:
+--
+-- @
+-- 'first' 'id' ≡ 'id'
+-- 'second' 'id' ≡ 'id'
+-- @
+--
+-- If you supply both, you should also ensure:
+--
+-- @'bimap' f g ≡ 'first' f '.' 'second' g@
+--
+-- These ensure by parametricity:
+--
+-- @
+-- 'bimap'  (f '.' g) (h '.' i) ≡ 'bimap' f h '.' 'bimap' g i
+-- 'first'  (f '.' g) ≡ 'first'  f '.' 'first'  g
+-- 'second' (f '.' g) ≡ 'second' f '.' 'second' g
+-- @
+--
+-- /Since: 4.8.0.0/
+class Bifunctor p where
+    {-# MINIMAL bimap | first, second #-}
+
+    -- | Map over both arguments at the same time.
+    --
+    -- @'bimap' f g ≡ 'first' f '.' 'second' g@
+    bimap :: (a -> b) -> (c -> d) -> p a c -> p b d
+    bimap f g = first f . second g
+
+    -- | Map covariantly over the first argument.
+    --
+    -- @'first' f ≡ 'bimap' f 'id'@
+    first :: (a -> b) -> p a c -> p b c
+    first f = bimap f id
+
+    -- | Map covariantly over the second argument.
+    --
+    -- @'second' ≡ 'bimap' 'id'@
+    second :: (b -> c) -> p a b -> p a c
+    second = bimap id
+
+
+instance Bifunctor (,) where
+    bimap f g ~(a, b) = (f a, g b)
+
+instance Bifunctor ((,,) x1) where
+    bimap f g ~(x1, a, b) = (x1, f a, g b)
+
+instance Bifunctor ((,,,) x1 x2) where
+    bimap f g ~(x1, x2, a, b) = (x1, x2, f a, g b)
+
+instance Bifunctor ((,,,,) x1 x2 x3) where
+    bimap f g ~(x1, x2, x3, a, b) = (x1, x2, x3, f a, g b)
+
+instance Bifunctor ((,,,,,) x1 x2 x3 x4) where
+    bimap f g ~(x1, x2, x3, x4, a, b) = (x1, x2, x3, x4, f a, g b)
+
+instance Bifunctor ((,,,,,,) x1 x2 x3 x4 x5) where
+    bimap f g ~(x1, x2, x3, x4, x5, a, b) = (x1, x2, x3, x4, x5, f a, g b)
+
+
+instance Bifunctor Either where
+    bimap f _ (Left a) = Left (f a)
+    bimap _ g (Right b) = Right (g b)
+
+instance Bifunctor Const where
+    bimap f _ (Const a) = Const (f a)
diff --git a/libraries/base/base.cabal b/libraries/base/base.cabal
index 45e674f..957053d 100644
--- a/libraries/base/base.cabal
+++ b/libraries/base/base.cabal
@@ -117,6 +117,7 @@ Library
         Control.Monad.ST.Strict
         Control.Monad.ST.Unsafe
         Control.Monad.Zip
+        Data.Bifunctor
         Data.Bits
         Data.Bool
         Data.Char
diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md
index ed93b46..76fe87a 100644
--- a/libraries/base/changelog.md
+++ b/libraries/base/changelog.md
@@ -84,6 +84,9 @@
 
   * Remove deprecated `Data.OldTypeable` (#9639)
 
+  * New module `Data.Bifunctor` providing the `Bifunctor(bimap,first,second)`
+    class (previously defined in `bifunctors` package) (#9682)
+
 ## 4.7.0.1  *Jul 2014*
 
   * Bundled with GHC 7.8.3



More information about the ghc-commits mailing list