[commit: ghc] wip/nfs-locking: Move Monoid (ReaderT Target Action a) instance to src/Target.hs. (95d2949)

git at git.haskell.org git at git.haskell.org
Fri Oct 27 00:05:23 UTC 2017


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

On branch  : wip/nfs-locking
Link       : http://ghc.haskell.org/trac/ghc/changeset/95d2949e9c255d525adfcc6af61f6a7711ae5dab/ghc

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

commit 95d2949e9c255d525adfcc6af61f6a7711ae5dab
Author: Andrey Mokhov <andrey.mokhov at gmail.com>
Date:   Fri Aug 21 16:10:44 2015 +0100

    Move Monoid (ReaderT Target Action a) instance to src/Target.hs.


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

95d2949e9c255d525adfcc6af61f6a7711ae5dab
 src/Target.hs | 14 ++++++++++++--
 1 file changed, 12 insertions(+), 2 deletions(-)

diff --git a/src/Target.hs b/src/Target.hs
index 2ce94bc..1717a87 100644
--- a/src/Target.hs
+++ b/src/Target.hs
@@ -1,6 +1,6 @@
-{-# LANGUAGE DeriveGeneric, TypeSynonymInstances #-}
+{-# LANGUAGE DeriveGeneric, FlexibleInstances #-}
 module Target (
-    Target (..), StageTarget (..), StagePackageTarget (..), FullTarget (..),
+    Target (..), StageTarget, StagePackageTarget, FullTarget,
     stageTarget, stagePackageTarget, fullTarget, fullTargetWithWay,
     ) where
 
@@ -10,6 +10,8 @@ import Stage
 import Package
 import Builder
 import GHC.Generics
+import Data.Monoid
+import Control.Monad.Reader
 
 -- Target captures all parameters relevant to the current build target:
 -- * Stage and Package being built,
@@ -28,6 +30,14 @@ data Target = Target
      }
      deriving (Show, Eq, Generic)
 
+-- If values of type 'a' form a Monoid then we can also derive a Monoid instance
+-- for values of type 'ReaderT Target Action a':
+-- * the empty computation returns the identity element of the underlying type
+-- * two computations can be combined by combining their results
+instance Monoid a => Monoid (ReaderT Target Action a) where
+    mempty  = return mempty
+    mappend = liftM2 mappend
+
 -- StageTarget is a partially constructed Target. Only stage is guaranteed to
 -- be assigned.
 type StageTarget = Target



More information about the ghc-commits mailing list