[commit: ghc] master: Fix Windows build following D2588 (e39589e)
git at git.haskell.org
git at git.haskell.org
Sat Oct 15 02:30:44 UTC 2016
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/e39589e2e4f788565c4a7f02cb85802214a95757/ghc
>---------------------------------------------------------------
commit e39589e2e4f788565c4a7f02cb85802214a95757
Author: Ryan Scott <ryan.gl.scott at gmail.com>
Date: Fri Oct 14 22:28:29 2016 -0400
Fix Windows build following D2588
Commit 8c6a3d68c0301bb985aa2a462936bbcf7584ae9c inadvertently broke the build
on Windows. This restores Windows compatibility.
>---------------------------------------------------------------
e39589e2e4f788565c4a7f02cb85802214a95757
libraries/base/Data/Semigroup.hs | 7 ++++++-
1 file changed, 6 insertions(+), 1 deletion(-)
diff --git a/libraries/base/Data/Semigroup.hs b/libraries/base/Data/Semigroup.hs
index 2cb1bb7..1c3d9da 100644
--- a/libraries/base/Data/Semigroup.hs
+++ b/libraries/base/Data/Semigroup.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE CPP #-}
{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
@@ -83,7 +84,9 @@ import Data.Monoid (All (..), Any (..), Dual (..), Endo (..),
import Data.Monoid (Alt (..))
import qualified Data.Monoid as Monoid
import Data.Void
-import GHC.Event (Event, Lifetime (..))
+#ifndef mingw32_HOST_OS
+import GHC.Event (Event, Lifetime)
+#endif
import GHC.Generics
infixr 6 <>
@@ -711,6 +714,7 @@ instance Semigroup (Proxy s) where
instance Semigroup a => Semigroup (IO a) where
(<>) = liftA2 (<>)
+#ifndef mingw32_HOST_OS
-- | @since 4.10.0.0
instance Semigroup Event where
(<>) = mappend
@@ -720,3 +724,4 @@ instance Semigroup Event where
instance Semigroup Lifetime where
(<>) = mappend
stimes = stimesMonoid
+#endif
More information about the ghc-commits
mailing list