[commit: packages/containers] cleaned_bugfix394, master, merge-doc-target, merge-fixes-5.9, merge-restrict-fix-5.8, revert-408-bugfix_394: Define pattern synonyms only for GHC >=8 (98cb19f)

git at git.haskell.org git at git.haskell.org
Mon Apr 17 21:44:10 UTC 2017


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

On branches: cleaned_bugfix394,master,merge-doc-target,merge-fixes-5.9,merge-restrict-fix-5.8,revert-408-bugfix_394
Link       : http://git.haskell.org/packages/containers.git/commitdiff/98cb19f263aa0a064fb67161ef7f19039c28ae59

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

commit 98cb19f263aa0a064fb67161ef7f19039c28ae59
Author: David Feuer <David.Feuer at gmail.com>
Date:   Wed Jul 13 22:24:05 2016 -0400

    Define pattern synonyms only for GHC >=8
    
    The CPP required to support pattern synonyms with earlier GHC
    versions produces too much clutter. It's bad enough having to
    deal with exports with and without testing and with and without
    pattern synonyms. Having two different export mechanisms goes too
    far. If users demand support very strenuously, we can put some of
    it back. Until then, I don't want to commit to supporting it
    indefinitely.
    
    Fixes #297


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

98cb19f263aa0a064fb67161ef7f19039c28ae59
 Data/Sequence.hs | 37 +++----------------------------------
 1 file changed, 3 insertions(+), 34 deletions(-)

diff --git a/Data/Sequence.hs b/Data/Sequence.hs
index 374e2a2..1219ef6 100644
--- a/Data/Sequence.hs
+++ b/Data/Sequence.hs
@@ -1,6 +1,6 @@
 {-# LANGUAGE CPP #-}
 {-# LANGUAGE BangPatterns #-}
-#if __GLASGOW_HASKELL__ >= 708
+#if __GLASGOW_HASKELL__ >= 800
 #define DEFINE_PATTERN_SYNONYMS 1
 #endif
 #if __GLASGOW_HASKELL__
@@ -70,28 +70,16 @@
 module Data.Sequence (
 #if defined(TESTING)
     Elem(..), FingerTree(..), Node(..), Digit(..),
-#if __GLASGOW_HASKELL__ >= 800
+#if defined(DEFINE_PATTERN_SYNONYMS)
     Seq (.., Empty, (:<|), (:|>)),
 #else
     Seq (..),
-#if defined(DEFINE_PATTERN_SYNONYMS)
-    -- * Pattern synonyms
-    pattern Empty,  -- :: Seq a
-    pattern (:<|),  -- :: a -> Seq a -> Seq a
-    pattern (:|>),  -- :: Seq a -> a -> Seq a
-#endif
 #endif
 
-#elif __GLASGOW_HASKELL__ >= 800
+#elif defined(DEFINE_PATTERN_SYNONYMS)
     Seq (Empty, (:<|), (:|>)),
 #else
     Seq,
-#if defined(DEFINE_PATTERN_SYNONYMS)
-    -- * Pattern synonyms
-    pattern Empty,  -- :: Seq a
-    pattern (:<|),  -- :: a -> Seq a -> Seq a
-    pattern (:|>),  -- :: Seq a -> a -> Seq a
-#endif
 #endif
     -- * Construction
     empty,          -- :: Seq a
@@ -294,43 +282,24 @@ infixl 5 :|>
 -- pattern match warnings for pattern synonyms, we should be
 -- sure to take advantage of that.
 
--- Unfortunately, there's some extra noise here because
--- pattern synonyms could not have signatures until 7.10,
--- but 8.0 at least will warn if they're missing.
-
 -- | A pattern synonym matching an empty sequence.
-#if __GLASGOW_HASKELL__ >= 710
 pattern Empty :: Seq a
-#else
-#endif
 pattern Empty = Seq EmptyT
 
--- Non-trivial bidirectional pattern synonyms are only
--- available in GHC >= 7.10. In earlier versions, these
--- can be used to match, but not to construct.
-
 -- | A pattern synonym viewing the front of a non-empty
 -- sequence.
-#if __GLASGOW_HASKELL__ >= 710
 pattern (:<|) :: a -> Seq a -> Seq a
-#endif
 pattern x :<| xs <- (viewl -> x :< xs)
-#if __GLASGOW_HASKELL__ >= 710
   where
     x :<| xs = x <| xs
-#endif
 
 -- | A pattern synonym viewing the rear of a non-empty
 -- sequence.
-#if __GLASGOW_HASKELL__ >= 710
 pattern (:|>) :: Seq a -> a -> Seq a
-#endif
 pattern xs :|> x <- (viewr -> xs :> x)
-#if __GLASGOW_HASKELL__ >= 710
   where
     xs :|> x = xs |> x
 #endif
-#endif
 
 class Sized a where
     size :: a -> Int



More information about the ghc-commits mailing list