[Git][ghc/ghc][master] haddock: Remove compatibility shims for GHC < 8.4 from haddock-library

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Fri May 24 11:55:08 UTC 2024



Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC


Commits:
27c430f3 by David Binder at 2024-05-24T07:52:38-04:00
haddock: Remove compatibility shims for GHC < 8.4 from haddock-library

- - - - -


6 changed files:

- utils/haddock/haddock-library/haddock-library.cabal
- − utils/haddock/haddock-library/src/CompatPrelude.hs
- utils/haddock/haddock-library/src/Documentation/Haddock/Parser/Identifier.hs
- utils/haddock/haddock-library/src/Documentation/Haddock/Parser/Monad.hs
- utils/haddock/haddock-library/src/Documentation/Haddock/Types.hs
- utils/haddock/haddock.cabal


Changes:

=====================================
utils/haddock/haddock-library/haddock-library.cabal
=====================================
@@ -17,13 +17,7 @@ maintainer:           Alec Theriault <alec.theriault at gmail.com>, Alex Biehl <ale
 homepage:             http://www.haskell.org/haddock/
 bug-reports:          https://github.com/haskell/haddock/issues
 category:             Documentation
-tested-with:          GHC == 7.4.2
-                    , GHC == 7.6.3
-                    , GHC == 7.8.4
-                    , GHC == 7.10.3
-                    , GHC == 8.0.2
-                    , GHC == 8.2.2
-                    , GHC == 8.4.4
+tested-with:          GHC == 8.4.4
                     , GHC == 8.6.5
                     , GHC == 8.8.3
                     , GHC == 8.10.1
@@ -41,14 +35,15 @@ common lib-defaults
   default-language: Haskell2010
 
   build-depends:
-    , base         >= 4.5     && < 4.20
+    , base         >= 4.10     && < 4.20
     , containers   ^>= 0.4.2.1 || ^>= 0.5.0.0 || ^>= 0.6.0.1 || ^>= 0.7
     , text         ^>= 1.2.3.0 || ^>= 2.0 || ^>= 2.1
     , parsec       ^>= 3.1.13.0
 
-  ghc-options: -funbox-strict-fields -Wall
-  if impl(ghc >= 8.0)
-    ghc-options: -Wcompat -Wnoncanonical-monad-instances
+  ghc-options: -funbox-strict-fields
+               -Wall
+               -Wcompat
+               -Wnoncanonical-monad-instances
 
 library
   import: lib-defaults
@@ -62,7 +57,6 @@ library
     Documentation.Haddock.Types
 
   other-modules:
-    CompatPrelude
     Documentation.Haddock.Parser.Util
     Documentation.Haddock.Parser.Monad
     Documentation.Haddock.Parser.Identifier
@@ -76,7 +70,6 @@ test-suite spec
     src
 
   other-modules:
-    CompatPrelude
     Documentation.Haddock.Doc
     Documentation.Haddock.Markup
     Documentation.Haddock.Parser


=====================================
utils/haddock/haddock-library/src/CompatPrelude.hs deleted
=====================================
@@ -1,52 +0,0 @@
-{-# LANGUAGE CPP #-}
-
-#ifdef __HLINT__
-#elif !MIN_VERSION_base(4,5,0)
-# error This module doesn't provide compat-shims for versions prior to base-4.5
-#endif
-
--- | Bridge impedance mismatch of different @base@ versions back till @base-4.5@ (GHC 7.4.2)
-module CompatPrelude
-  ( ($>)
-  , isSymbolChar
-  ) where
-
-#if MIN_VERSION_base(4,7,0)
-import           Data.Functor                ( ($>) )
-#else
-import           Data.Functor                ( (<$) )
-#endif
-
-#if MIN_VERSION_base(4,9,0)
-import           Text.Read.Lex                      (isSymbolChar)
-#else
-import           Data.Char (GeneralCategory(..), generalCategory)
-#endif
-
-#if !MIN_VERSION_base(4,7,0)
-infixl 4 $>
-
--- | Flipped version of '<$'.
---
--- @since 4.7.0.0
-($>) :: Functor f => f a -> b -> f b
-($>) = flip (<$)
-#endif
-
-#if !MIN_VERSION_base(4,9,0)
--- inlined from base-4.10.0.0
-isSymbolChar :: Char -> Bool
-isSymbolChar c = not (isPuncChar c) && case generalCategory c of
-    MathSymbol           -> True
-    CurrencySymbol       -> True
-    ModifierSymbol       -> True
-    OtherSymbol          -> True
-    DashPunctuation      -> True
-    OtherPunctuation     -> c `notElem` "'\""
-    ConnectorPunctuation -> c /= '_'
-    _                    -> False
-  where
-    -- | The @special@ character class as defined in the Haskell Report.
-    isPuncChar :: Char -> Bool
-    isPuncChar = (`elem` (",;()[]{}`" :: String))
-#endif


=====================================
utils/haddock/haddock-library/src/Documentation/Haddock/Parser/Identifier.hs
=====================================
@@ -24,11 +24,12 @@ import Text.Parsec
   )
 import qualified Text.Parsec as Parsec
 import Text.Parsec.Pos (updatePosChar)
+import Text.Read.Lex (isSymbolChar)
 
+import Data.Functor (($>))
 import Data.Text (Text)
 import qualified Data.Text as T
 
-import CompatPrelude
 import Control.Monad (guard)
 import Data.Char (isAlpha, isAlphaNum)
 import Data.Maybe


=====================================
utils/haddock/haddock-library/src/Documentation/Haddock/Parser/Monad.hs
=====================================
@@ -24,9 +24,9 @@ import Text.Parsec
   , setParserState
   )
 import qualified Text.Parsec as Parsec
-import qualified Text.Parsec.Char as Parsec
 import Text.Parsec.Pos (updatePosChar)
 
+import Data.Functor (($>))
 import Data.Text (Text)
 import qualified Data.Text as T
 
@@ -39,7 +39,6 @@ import Data.String (IsString (..))
 
 import Documentation.Haddock.Types (MetaSince (..))
 
-import CompatPrelude
 import Prelude hiding (takeWhile)
 
 -- | The only bit of information we really care about trudging along with us


=====================================
utils/haddock/haddock-library/src/Documentation/Haddock/Types.hs
=====================================
@@ -1,4 +1,3 @@
-{-# LANGUAGE CPP #-}
 {-# LANGUAGE DeriveTraversable #-}
 
 -- |
@@ -15,21 +14,10 @@
 -- Exposes documentation data types used for (some) of Haddock.
 module Documentation.Haddock.Types where
 
-#if !MIN_VERSION_base(4,8,0)
-import Control.Applicative
-import Data.Foldable
-import Data.Traversable
-#endif
-
-#if MIN_VERSION_base(4,8,0)
 import Control.Arrow ((***))
-import Data.Bifunctor
-#endif
-
-#if MIN_VERSION_base(4,10,0)
 import Data.Bifoldable
+import Data.Bifunctor
 import Data.Bitraversable
-#endif
 
 -- | A @\@since@ declaration.
 data MetaSince = MetaSince
@@ -54,21 +42,14 @@ data MetaDoc mod id = MetaDoc
   }
   deriving (Eq, Show, Functor, Foldable, Traversable)
 
-#if MIN_VERSION_base(4,8,0)
--- | __NOTE__: Only defined for @base >= 4.8.0@
 instance Bifunctor MetaDoc where
   bimap f g (MetaDoc m d) = MetaDoc m (bimap f g d)
-#endif
 
-#if MIN_VERSION_base(4,10,0)
--- | __NOTE__: Only defined for @base >= 4.10.0@
 instance Bifoldable MetaDoc where
   bifoldr f g z d = bifoldr f g z (_doc d)
 
--- | __NOTE__: Only defined for @base >= 4.10.0@
 instance Bitraversable MetaDoc where
   bitraverse f g (MetaDoc m d) = MetaDoc m <$> bitraverse f g d
-#endif
 
 overDoc :: (DocH a b -> DocH c d) -> MetaDoc a b -> MetaDoc c d
 overDoc f d = d{_doc = f $ _doc d}
@@ -159,8 +140,6 @@ data DocH mod id
   | DocTable (Table (DocH mod id))
   deriving (Eq, Show, Functor, Foldable, Traversable)
 
-#if MIN_VERSION_base(4,8,0)
--- | __NOTE__: Only defined for @base >= 4.8.0@
 instance Bifunctor DocH where
   bimap _ _ DocEmpty = DocEmpty
   bimap f g (DocAppend docA docB) = DocAppend (bimap f g docA) (bimap f g docB)
@@ -186,10 +165,7 @@ instance Bifunctor DocH where
   bimap _ _ (DocExamples examples) = DocExamples examples
   bimap f g (DocHeader (Header level title)) = DocHeader (Header level (bimap f g title))
   bimap f g (DocTable (Table header body)) = DocTable (Table (map (fmap (bimap f g)) header) (map (fmap (bimap f g)) body))
-#endif
 
-#if MIN_VERSION_base(4,10,0)
--- | __NOTE__: Only defined for @base >= 4.10.0@
 instance Bifoldable DocH where
   bifoldr f g z (DocAppend docA docB) = bifoldr f g (bifoldr f g z docA) docB
   bifoldr f g z (DocParagraph doc) = bifoldr f g z doc
@@ -207,7 +183,6 @@ instance Bifoldable DocH where
   bifoldr f g z (DocTable (Table header body)) = foldr (\r acc -> foldr (flip (bifoldr f g)) acc r) (foldr (\r acc -> foldr (flip (bifoldr f g)) acc r) z body) header
   bifoldr _ _ z _ = z
 
--- | __NOTE__: Only defined for @base >= 4.10.0@
 instance Bitraversable DocH where
   bitraverse _ _ DocEmpty = pure DocEmpty
   bitraverse f g (DocAppend docA docB) = DocAppend <$> bitraverse f g docA <*> bitraverse f g docB
@@ -222,7 +197,8 @@ instance Bitraversable DocH where
   bitraverse f g (DocBold doc) = DocBold <$> bitraverse f g doc
   bitraverse f g (DocUnorderedList docs) = DocUnorderedList <$> traverse (bitraverse f g) docs
   bitraverse f g (DocOrderedList docs) = DocOrderedList <$> traverseSnd (bitraverse f g) docs
-    where traverseSnd f' = traverse (\(x, a) -> (\b -> (x, b)) <$> f' a)
+    where
+      traverseSnd f' = traverse (\(x, a) -> (\b -> (x, b)) <$> f' a)
   bitraverse f g (DocDefList docs) = DocDefList <$> traverse (bitraverse (bitraverse f g) (bitraverse f g)) docs
   bitraverse f g (DocCodeBlock doc) = DocCodeBlock <$> bitraverse f g doc
   bitraverse f g (DocHyperlink (Hyperlink url lbl)) = DocHyperlink <$> (Hyperlink url <$> traverse (bitraverse f g) lbl)
@@ -234,7 +210,6 @@ instance Bitraversable DocH where
   bitraverse _ _ (DocExamples examples) = pure (DocExamples examples)
   bitraverse f g (DocHeader (Header level title)) = (DocHeader . Header level) <$> bitraverse f g title
   bitraverse f g (DocTable (Table header body)) = (\h b -> DocTable (Table h b)) <$> traverse (traverse (bitraverse f g)) header <*> traverse (traverse (bitraverse f g)) body
-#endif
 
 -- | The namespace qualification for an identifier.
 data Namespace = Value | Type | None deriving (Eq, Ord, Enum, Show)


=====================================
utils/haddock/haddock.cabal
=====================================
@@ -91,7 +91,6 @@ executable haddock
       mtl
 
     other-modules:
-      CompatPrelude
       Documentation.Haddock.Parser
       Documentation.Haddock.Parser.Monad
       Documentation.Haddock.Parser.Identifier



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/27c430f39a759cf1a95005cd3f7737f7697a5207

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/27c430f39a759cf1a95005cd3f7737f7697a5207
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20240524/b7eef01e/attachment-0001.html>


More information about the ghc-commits mailing list