Teo Camarasu pushed to branch wip/T26217 at Glasgow Haskell Compiler / GHC

Commits:

4 changed files:

Changes:

  • compiler/GHC/Builtin/Names/TH.hs
    ... ... @@ -30,7 +30,7 @@ templateHaskellNames :: [Name]
    30 30
     -- Should stay in sync with the import list of GHC.HsToCore.Quote
    
    31 31
     
    
    32 32
     templateHaskellNames = [
    
    33
    -    returnQName, bindQName, sequenceQName, newNameName, liftName, liftTypedName,
    
    33
    +    sequenceQName, newNameName, liftName, liftTypedName,
    
    34 34
         mkNameName, mkNameG_vName, mkNameG_dName, mkNameG_tcName, mkNameG_fldName,
    
    35 35
         mkNameLName,
    
    36 36
         mkNameSName, mkNameQName,
    
    ... ... @@ -240,12 +240,10 @@ overlapTyConName = thTc (fsLit "Overlap") overlapTyConKey
    240 240
     modNameTyConName       = thTc (fsLit "ModName")        modNameTyConKey
    
    241 241
     quasiQuoterTyConName   = mk_known_key_name tcName qqLib (fsLit "QuasiQuoter") quasiQuoterTyConKey
    
    242 242
     
    
    243
    -returnQName, bindQName, sequenceQName, newNameName, liftName,
    
    243
    +sequenceQName, newNameName, liftName,
    
    244 244
         mkNameName, mkNameG_vName, mkNameG_fldName, mkNameG_dName, mkNameG_tcName,
    
    245 245
         mkNameLName, mkNameSName, liftStringName, unTypeName, unTypeCodeName,
    
    246 246
         unsafeCodeCoerceName, liftTypedName, mkModNameName, mkNameQName :: Name
    
    247
    -returnQName    = thFun (fsLit "returnQ")   returnQIdKey
    
    248
    -bindQName      = thFun (fsLit "bindQ")     bindQIdKey
    
    249 247
     sequenceQName  = thMonadFun (fsLit "sequenceQ") sequenceQIdKey
    
    250 248
     newNameName    = thMonadFun (fsLit "newName")   newNameIdKey
    
    251 249
     mkNameName     = thFun (fsLit "mkName")     mkNameIdKey
    
    ... ... @@ -812,12 +810,10 @@ dataNamespaceSpecifierDataConKey = mkPreludeDataConUnique 215
    812 810
     -- IdUniques available: 200-499
    
    813 811
     -- If you want to change this, make sure you check in GHC.Builtin.Names
    
    814 812
     
    
    815
    -returnQIdKey, bindQIdKey, sequenceQIdKey, liftIdKey, newNameIdKey,
    
    813
    +sequenceQIdKey, liftIdKey, newNameIdKey,
    
    816 814
         mkNameIdKey, mkNameG_vIdKey, mkNameG_fldIdKey, mkNameG_dIdKey, mkNameG_tcIdKey,
    
    817 815
         mkNameLIdKey, mkNameSIdKey, unTypeIdKey, unTypeCodeIdKey,
    
    818 816
         unsafeCodeCoerceIdKey, liftTypedIdKey, mkModNameIdKey, mkNameQIdKey :: Unique
    
    819
    -returnQIdKey        = mkPreludeMiscIdUnique 200
    
    820
    -bindQIdKey          = mkPreludeMiscIdUnique 201
    
    821 817
     sequenceQIdKey      = mkPreludeMiscIdUnique 202
    
    822 818
     liftIdKey           = mkPreludeMiscIdUnique 203
    
    823 819
     newNameIdKey         = mkPreludeMiscIdUnique 204
    

  • compiler/GHC/HsToCore/Quote.hs
    ... ... @@ -245,14 +245,14 @@ first generate a polymorphic definition and then just apply the wrapper at the e
    245 245
     
    
    246 246
       [| \x -> x |]
    
    247 247
     ====>
    
    248
    -  gensym (unpackString "x"#) `bindQ` \ x1::String ->
    
    249
    -  lam (pvar x1) (var x1)
    
    248
    +  newName (unpackString "x"#) >>= \ x1::Name ->
    
    249
    +  lamE (varP x1) (varE x1)
    
    250 250
     
    
    251 251
     
    
    252 252
       [| \x -> $(f [| x |]) |]
    
    253 253
     ====>
    
    254
    -  gensym (unpackString "x"#) `bindQ` \ x1::String ->
    
    255
    -  lam (pvar x1) (f (var x1))
    
    254
    +  newName (unpackString "x"#) >>= \ x1::Name ->
    
    255
    +  lamE (varP x1) (f (varE x1))
    
    256 256
     -}
    
    257 257
     
    
    258 258
     
    

  • libraries/ghc-internal/src/GHC/Internal/Data/Data.hs
    ... ... @@ -143,6 +143,7 @@ import GHC.Internal.Arr -- So we can give Data instance for Array
    143 143
     import qualified GHC.Internal.Generics as Generics (Fixity(..))
    
    144 144
     import GHC.Internal.Generics hiding (Fixity(..))
    
    145 145
                                  -- So we can give Data instance for U1, V1, ...
    
    146
    +import qualified GHC.Internal.TH.Syntax as TH
    
    146 147
     
    
    147 148
     ------------------------------------------------------------------------------
    
    148 149
     --
    
    ... ... @@ -1353,3 +1354,63 @@ deriving instance Data DecidedStrictness
    1353 1354
     
    
    1354 1355
     -- | @since base-4.12.0.0
    
    1355 1356
     deriving instance Data a => Data (Down a)
    
    1357
    +
    
    1358
    +----------------------------------------------------------------------------
    
    1359
    +-- Data instances for GHC.Internal.TH.Syntax
    
    1360
    +
    
    1361
    +deriving instance Data TH.AnnLookup
    
    1362
    +deriving instance Data TH.AnnTarget
    
    1363
    +deriving instance Data TH.Bang
    
    1364
    +deriving instance Data TH.BndrVis
    
    1365
    +deriving instance Data TH.Body
    
    1366
    +deriving instance Data TH.Bytes
    
    1367
    +deriving instance Data TH.Callconv
    
    1368
    +deriving instance Data TH.Clause
    
    1369
    +deriving instance Data TH.Con
    
    1370
    +deriving instance Data TH.Dec
    
    1371
    +deriving instance Data TH.DecidedStrictness
    
    1372
    +deriving instance Data TH.DerivClause
    
    1373
    +deriving instance Data TH.DerivStrategy
    
    1374
    +deriving instance Data TH.DocLoc
    
    1375
    +deriving instance Data TH.Exp
    
    1376
    +deriving instance Data TH.FamilyResultSig
    
    1377
    +deriving instance Data TH.Fixity
    
    1378
    +deriving instance Data TH.FixityDirection
    
    1379
    +deriving instance Data TH.Foreign
    
    1380
    +deriving instance Data TH.FunDep
    
    1381
    +deriving instance Data TH.Guard
    
    1382
    +deriving instance Data TH.Info
    
    1383
    +deriving instance Data TH.InjectivityAnn
    
    1384
    +deriving instance Data TH.Inline
    
    1385
    +deriving instance Data TH.Lit
    
    1386
    +deriving instance Data TH.Loc
    
    1387
    +deriving instance Data TH.Match
    
    1388
    +deriving instance Data TH.ModName
    
    1389
    +deriving instance Data TH.Module
    
    1390
    +deriving instance Data TH.ModuleInfo
    
    1391
    +deriving instance Data TH.Name
    
    1392
    +deriving instance Data TH.NameFlavour
    
    1393
    +deriving instance Data TH.NameSpace
    
    1394
    +deriving instance Data TH.NamespaceSpecifier
    
    1395
    +deriving instance Data TH.OccName
    
    1396
    +deriving instance Data TH.Overlap
    
    1397
    +deriving instance Data TH.Pat
    
    1398
    +deriving instance Data TH.PatSynArgs
    
    1399
    +deriving instance Data TH.PatSynDir
    
    1400
    +deriving instance Data TH.Phases
    
    1401
    +deriving instance Data TH.PkgName
    
    1402
    +deriving instance Data TH.Pragma
    
    1403
    +deriving instance Data TH.Range
    
    1404
    +deriving instance Data TH.Role
    
    1405
    +deriving instance Data TH.RuleBndr
    
    1406
    +deriving instance Data TH.RuleMatch
    
    1407
    +deriving instance Data TH.Safety
    
    1408
    +deriving instance Data TH.SourceStrictness
    
    1409
    +deriving instance Data TH.SourceUnpackedness
    
    1410
    +deriving instance Data TH.Specificity
    
    1411
    +deriving instance Data TH.Stmt
    
    1412
    +deriving instance Data TH.TyLit
    
    1413
    +deriving instance Data TH.TySynEqn
    
    1414
    +deriving instance Data TH.Type
    
    1415
    +deriving instance Data TH.TypeFamilyHead
    
    1416
    +deriving instance Data flag => Data (TH.TyVarBndr flag)

  • libraries/ghc-internal/src/GHC/Internal/TH/Syntax.hs
    1 1
     {-# OPTIONS_HADDOCK not-home #-} -- we want users to import Language.Haskell.TH.Syntax instead
    
    2
    -{-# LANGUAGE CPP, DeriveDataTypeable,
    
    3
    -             DeriveGeneric, FlexibleInstances, DefaultSignatures,
    
    4
    -             RankNTypes, RoleAnnotations, ScopedTypeVariables,
    
    5
    -             MagicHash, KindSignatures, PolyKinds, TypeApplications, DataKinds,
    
    6
    -             GADTs, UnboxedTuples, UnboxedSums, TypeOperators,
    
    7
    -             Trustworthy, DeriveFunctor, DeriveTraversable,
    
    8
    -             BangPatterns, RecordWildCards, ImplicitParams #-}
    
    9
    -
    
    10
    -{-# LANGUAGE TemplateHaskellQuotes #-}
    
    11
    -{-# LANGUAGE StandaloneKindSignatures #-}
    
    2
    +{-# LANGUAGE CPP #-}
    
    3
    +{-# LANGUAGE DataKinds #-}
    
    4
    +{-# LANGUAGE DeriveGeneric #-}
    
    5
    +{-# LANGUAGE DeriveTraversable #-}
    
    6
    +{-# LANGUAGE FlexibleInstances #-}
    
    7
    +{-# LANGUAGE GADTs #-}
    
    8
    +{-# LANGUAGE PolyKinds #-}
    
    9
    +{-# LANGUAGE RankNTypes #-}
    
    10
    +{-# LANGUAGE RoleAnnotations #-}
    
    11
    +{-# LANGUAGE ScopedTypeVariables #-}
    
    12
    +{-# LANGUAGE Safe #-}
    
    13
    +{-# LANGUAGE UnboxedTuples #-}
    
    12 14
     
    
    13 15
     -- | This module is used internally in GHC's integration with Template Haskell
    
    14 16
     -- and defines the abstract syntax of Template Haskell.
    
    ... ... @@ -26,7 +28,6 @@ module GHC.Internal.TH.Syntax
    26 28
     
    
    27 29
     #ifdef BOOTSTRAP_TH
    
    28 30
     import Prelude
    
    29
    -import Data.Data hiding (Fixity(..))
    
    30 31
     import System.IO.Unsafe ( unsafePerformIO )
    
    31 32
     import Data.Char        ( isAlpha, isAlphaNum, isUpper )
    
    32 33
     import Data.List.NonEmpty ( NonEmpty(..) )
    
    ... ... @@ -38,7 +39,6 @@ import GHC.Ptr ( Ptr, plusPtr )
    38 39
     import GHC.Generics     ( Generic )
    
    39 40
     #else
    
    40 41
     import GHC.Internal.Base hiding (NonEmpty(..),Type, Module, sequence)
    
    41
    -import GHC.Internal.Data.Data hiding (Fixity(..))
    
    42 42
     import GHC.Internal.Data.NonEmpty (NonEmpty(..))
    
    43 43
     import GHC.Internal.Data.Traversable
    
    44 44
     import GHC.Internal.Word
    
    ... ... @@ -72,19 +72,19 @@ manyName = mkNameG DataName "ghc-internal" "GHC.Internal.Types" "Many"
    72 72
     
    
    73 73
     -- | The name of a module.
    
    74 74
     newtype ModName = ModName String        -- Module name
    
    75
    - deriving (Show,Eq,Ord,Data,Generic)
    
    75
    + deriving (Show,Eq,Ord,Generic)
    
    76 76
     
    
    77 77
     -- | The name of a package.
    
    78 78
     newtype PkgName = PkgName String        -- package name
    
    79
    - deriving (Show,Eq,Ord,Data,Generic)
    
    79
    + deriving (Show,Eq,Ord,Generic)
    
    80 80
     
    
    81 81
     -- | Obtained from 'reifyModule' and 'Language.Haskell.TH.Lib.thisModule'.
    
    82 82
     data Module = Module PkgName ModName -- package qualified module name
    
    83
    - deriving (Show,Eq,Ord,Data,Generic)
    
    83
    + deriving (Show,Eq,Ord,Generic)
    
    84 84
     
    
    85 85
     -- | An "Occurence Name".
    
    86 86
     newtype OccName = OccName String
    
    87
    - deriving (Show,Eq,Ord,Data,Generic)
    
    87
    + deriving (Show,Eq,Ord,Generic)
    
    88 88
     
    
    89 89
     -- | Smart constructor for 'ModName'
    
    90 90
     mkModName :: String -> ModName
    
    ... ... @@ -200,7 +200,7 @@ Names constructed using @newName@ and @mkName@ may be used in bindings
    200 200
     (such as @let x = ...@ or @\x -> ...@), but names constructed using
    
    201 201
     @lookupValueName@, @lookupTypeName@, @'f@, @''T@ may not.
    
    202 202
     -}
    
    203
    -data Name = Name OccName NameFlavour deriving (Data, Eq, Generic)
    
    203
    +data Name = Name OccName NameFlavour deriving (Eq, Generic)
    
    204 204
     
    
    205 205
     instance Ord Name where
    
    206 206
         -- check if unique is different before looking at strings
    
    ... ... @@ -216,7 +216,7 @@ data NameFlavour
    216 216
                     -- An original name (occurrences only, not binders)
    
    217 217
                     -- Need the namespace too to be sure which
    
    218 218
                     -- thing we are naming
    
    219
    -  deriving ( Data, Eq, Ord, Show, Generic )
    
    219
    +  deriving ( Eq, Ord, Show, Generic )
    
    220 220
     
    
    221 221
     data NameSpace = VarName        -- ^ Variables
    
    222 222
                    | DataName       -- ^ Data constructors
    
    ... ... @@ -230,7 +230,7 @@ data NameSpace = VarName -- ^ Variables
    230 230
                        --     of the datatype (regardless of whether this constructor has this field).
    
    231 231
                        --   - For a field of a pattern synonym, this is the name of the pattern synonym.
    
    232 232
                      }
    
    233
    -               deriving( Eq, Ord, Show, Data, Generic )
    
    233
    +               deriving( Eq, Ord, Show, Generic )
    
    234 234
     
    
    235 235
     -- | @Uniq@ is used by GHC to distinguish names from each other.
    
    236 236
     type Uniq = Integer
    
    ... ... @@ -532,7 +532,7 @@ data Loc
    532 532
             , loc_module   :: String
    
    533 533
             , loc_start    :: CharPos
    
    534 534
             , loc_end      :: CharPos }
    
    535
    -   deriving( Show, Eq, Ord, Data, Generic )
    
    535
    +   deriving( Show, Eq, Ord, Generic )
    
    536 536
     
    
    537 537
     type CharPos = (Int, Int)       -- ^ Line and character position
    
    538 538
     
    
    ... ... @@ -615,13 +615,13 @@ data Info
    615 615
       | TyVarI      -- Scoped type variable
    
    616 616
             Name
    
    617 617
             Type    -- What it is bound to
    
    618
    -  deriving( Show, Eq, Ord, Data, Generic )
    
    618
    +  deriving( Show, Eq, Ord, Generic )
    
    619 619
     
    
    620 620
     -- | Obtained from 'reifyModule' in the 'Q' Monad.
    
    621 621
     data ModuleInfo =
    
    622 622
       -- | Contains the import list of the module.
    
    623 623
       ModuleInfo [Module]
    
    624
    -  deriving( Show, Eq, Ord, Data, Generic )
    
    624
    +  deriving( Show, Eq, Ord, Generic )
    
    625 625
     
    
    626 626
     {- |
    
    627 627
     In 'ClassOpI' and 'DataConI', name of the parent class or type
    
    ... ... @@ -659,11 +659,11 @@ type InstanceDec = Dec
    659 659
     
    
    660 660
     -- | Fixity, as specified in a @infix[lr] n@ declaration.
    
    661 661
     data Fixity          = Fixity Int FixityDirection
    
    662
    -    deriving( Eq, Ord, Show, Data, Generic )
    
    662
    +    deriving( Eq, Ord, Show, Generic )
    
    663 663
     
    
    664 664
     -- | The associativity of an operator, as in an @infix@ declaration.
    
    665 665
     data FixityDirection = InfixL | InfixR | InfixN
    
    666
    -    deriving( Eq, Ord, Show, Data, Generic )
    
    666
    +    deriving( Eq, Ord, Show, Generic )
    
    667 667
     
    
    668 668
     -- | Highest allowed operator precedence for 'Fixity' constructor (answer: 9)
    
    669 669
     maxPrecedence :: Int
    
    ... ... @@ -696,7 +696,7 @@ data Lit = CharL Char -- ^ @\'c\'@
    696 696
              | StringPrimL [Word8]  -- ^ @"string"#@. A primitive C-style string, type 'Addr#'
    
    697 697
              | BytesPrimL Bytes     -- ^ Some raw bytes, type 'Addr#':
    
    698 698
              | CharPrimL Char       -- ^ @\'c\'#@
    
    699
    -    deriving( Show, Eq, Ord, Data, Generic )
    
    699
    +    deriving( Show, Eq, Ord, Generic )
    
    700 700
     
    
    701 701
         -- We could add Int, Float, Double etc, as we do in HsLit,
    
    702 702
         -- but that could complicate the
    
    ... ... @@ -718,7 +718,7 @@ data Bytes = Bytes
    718 718
        -- , bytesInitialized :: Bool -- ^ False: only use `bytesSize` to allocate
    
    719 719
        --                            --   an uninitialized region
    
    720 720
        }
    
    721
    -   deriving (Data,Generic)
    
    721
    +   deriving (Generic)
    
    722 722
     
    
    723 723
     -- We can't derive Show instance for Bytes because we don't want to show the
    
    724 724
     -- pointer value but the actual bytes (similarly to what ByteString does). See
    
    ... ... @@ -785,14 +785,14 @@ data Pat
    785 785
       | TypeP Type                      -- ^ @{ type p }@
    
    786 786
       | InvisP Type                     -- ^ @{ @p }@
    
    787 787
       | OrP (NonEmpty Pat)              -- ^ @{ p1; p2 }@
    
    788
    -  deriving( Show, Eq, Ord, Data, Generic )
    
    788
    +  deriving( Show, Eq, Ord, Generic )
    
    789 789
     
    
    790 790
     -- | A (field name, pattern) pair. See 'RecP'.
    
    791 791
     type FieldPat = (Name,Pat)
    
    792 792
     
    
    793 793
     -- | A @case@-alternative
    
    794 794
     data Match = Match Pat Body [Dec] -- ^ @case e of { pat -> body where decs }@
    
    795
    -    deriving( Show, Eq, Ord, Data, Generic )
    
    795
    +    deriving( Show, Eq, Ord, Generic )
    
    796 796
     
    
    797 797
     -- | A clause consists of patterns, guards, a body expression, and a list of
    
    798 798
     -- declarations under a @where@. Clauses are seen in equations for function
    
    ... ... @@ -800,7 +800,7 @@ data Match = Match Pat Body [Dec] -- ^ @case e of { pat -> body where decs }@
    800 800
     -- etc.
    
    801 801
     data Clause = Clause [Pat] Body [Dec]
    
    802 802
                                       -- ^ @f { p1 p2 = body where decs }@
    
    803
    -    deriving( Show, Eq, Ord, Data, Generic )
    
    803
    +    deriving( Show, Eq, Ord, Generic )
    
    804 804
     
    
    805 805
     -- | A Haskell expression.
    
    806 806
     data Exp
    
    ... ... @@ -895,7 +895,7 @@ data Exp
    895 895
       | ForallE [TyVarBndr Specificity] Exp -- ^ @forall \<vars\>. \<expr\>@
    
    896 896
       | ForallVisE [TyVarBndr ()] Exp      -- ^ @forall \<vars\> -> \<expr\>@
    
    897 897
       | ConstrainedE [Exp] Exp             -- ^ @\<ctxt\> => \<expr\>@
    
    898
    -  deriving( Show, Eq, Ord, Data, Generic )
    
    898
    +  deriving( Show, Eq, Ord, Generic )
    
    899 899
     
    
    900 900
     -- | A (field name, expression) pair. See 'RecConE' and 'RecUpdE'.
    
    901 901
     type FieldExp = (Name,Exp)
    
    ... ... @@ -909,13 +909,13 @@ data Body
    909 909
                                      --      | e3 = e4 }
    
    910 910
                                      -- where ds@
    
    911 911
       | NormalB Exp              -- ^ @f p { = e } where ds@
    
    912
    -  deriving( Show, Eq, Ord, Data, Generic )
    
    912
    +  deriving( Show, Eq, Ord, Generic )
    
    913 913
     
    
    914 914
     -- | A single guard.
    
    915 915
     data Guard
    
    916 916
       = NormalG Exp -- ^ @f x { | odd x } = x@
    
    917 917
       | PatG [Stmt] -- ^ @f x { | Just y <- x, Just z <- y } = z@
    
    918
    -  deriving( Show, Eq, Ord, Data, Generic )
    
    918
    +  deriving( Show, Eq, Ord, Generic )
    
    919 919
     
    
    920 920
     -- | A single statement, as in @do@-notation.
    
    921 921
     data Stmt
    
    ... ... @@ -924,14 +924,14 @@ data Stmt
    924 924
       | NoBindS Exp   -- ^ @e@
    
    925 925
       | ParS [[Stmt]] -- ^ @x <- e1 | s2, s3 | s4@ (in 'CompE')
    
    926 926
       | RecS [Stmt]   -- ^ @rec { s1; s2 }@
    
    927
    -  deriving( Show, Eq, Ord, Data, Generic )
    
    927
    +  deriving( Show, Eq, Ord, Generic )
    
    928 928
     
    
    929 929
     -- | A list/enum range expression.
    
    930 930
     data Range = FromR Exp               -- ^ @[n ..]@
    
    931 931
                | FromThenR Exp Exp       -- ^ @[n, m ..]@
    
    932 932
                | FromToR Exp Exp         -- ^ @[n .. m]@
    
    933 933
                | FromThenToR Exp Exp Exp -- ^ @[n, m .. k]@
    
    934
    -           deriving( Show, Eq, Ord, Data, Generic )
    
    934
    +           deriving( Show, Eq, Ord, Generic )
    
    935 935
     
    
    936 936
     -- | A single declaration.
    
    937 937
     data Dec
    
    ... ... @@ -1018,7 +1018,7 @@ data Dec
    1018 1018
           --
    
    1019 1019
           -- Implicit parameter binding declaration. Can only be used in let
    
    1020 1020
           -- and where clauses which consist entirely of implicit bindings.
    
    1021
    -  deriving( Show, Eq, Ord, Data, Generic )
    
    1021
    +  deriving( Show, Eq, Ord, Generic )
    
    1022 1022
     
    
    1023 1023
     -- | A way to specify a namespace to look in when GHC needs to find
    
    1024 1024
     --   a name's source
    
    ... ... @@ -1030,7 +1030,7 @@ data NamespaceSpecifier
    1030 1030
                                --   or type variable
    
    1031 1031
       | DataNamespaceSpecifier -- ^ Name should be a term-level entity, such as a
    
    1032 1032
                                --   function, data constructor, or pattern synonym
    
    1033
    -  deriving( Show, Eq, Ord, Data, Generic )
    
    1033
    +  deriving( Show, Eq, Ord, Generic )
    
    1034 1034
     
    
    1035 1035
     -- | Varieties of allowed instance overlap.
    
    1036 1036
     data Overlap = Overlappable   -- ^ May be overlapped by more specific instances
    
    ... ... @@ -1039,12 +1039,12 @@ data Overlap = Overlappable -- ^ May be overlapped by more specific instances
    1039 1039
                  | Incoherent     -- ^ Both 'Overlapping' and 'Overlappable', and
    
    1040 1040
                                   -- pick an arbitrary one if multiple choices are
    
    1041 1041
                                   -- available.
    
    1042
    -  deriving( Show, Eq, Ord, Data, Generic )
    
    1042
    +  deriving( Show, Eq, Ord, Generic )
    
    1043 1043
     
    
    1044 1044
     -- | A single @deriving@ clause at the end of a datatype declaration.
    
    1045 1045
     data DerivClause = DerivClause (Maybe DerivStrategy) Cxt
    
    1046 1046
         -- ^ @{ deriving stock (Eq, Ord) }@
    
    1047
    -  deriving( Show, Eq, Ord, Data, Generic )
    
    1047
    +  deriving( Show, Eq, Ord, Generic )
    
    1048 1048
     
    
    1049 1049
     -- | What the user explicitly requests when deriving an instance with
    
    1050 1050
     -- @-XDerivingStrategies@.
    
    ... ... @@ -1052,7 +1052,7 @@ data DerivStrategy = StockStrategy -- ^ @deriving {stock} C@
    1052 1052
                        | AnyclassStrategy -- ^ @deriving {anyclass} C@, @-XDeriveAnyClass@
    
    1053 1053
                        | NewtypeStrategy  -- ^ @deriving {newtype} C@, @-XGeneralizedNewtypeDeriving@
    
    1054 1054
                        | ViaStrategy Type -- ^ @deriving C {via T}@, @-XDerivingVia@
    
    1055
    -  deriving( Show, Eq, Ord, Data, Generic )
    
    1055
    +  deriving( Show, Eq, Ord, Generic )
    
    1056 1056
     
    
    1057 1057
     -- | A pattern synonym's type. Note that a pattern synonym's /fully/
    
    1058 1058
     -- specified type has a peculiar shape coming with two forall
    
    ... ... @@ -1108,7 +1108,7 @@ type PatSynType = Type
    1108 1108
     -- between @type family@ and @where@.
    
    1109 1109
     data TypeFamilyHead =
    
    1110 1110
       TypeFamilyHead Name [TyVarBndr BndrVis] FamilyResultSig (Maybe InjectivityAnn)
    
    1111
    -  deriving( Show, Eq, Ord, Data, Generic )
    
    1111
    +  deriving( Show, Eq, Ord, Generic )
    
    1112 1112
     
    
    1113 1113
     -- | One equation of a type family instance or closed type family. The
    
    1114 1114
     -- arguments are the left-hand-side type and the right-hand-side result.
    
    ... ... @@ -1128,28 +1128,28 @@ data TypeFamilyHead =
    1128 1128
     --            ('VarT' a)
    
    1129 1129
     -- @
    
    1130 1130
     data TySynEqn = TySynEqn (Maybe [TyVarBndr ()]) Type Type
    
    1131
    -  deriving( Show, Eq, Ord, Data, Generic )
    
    1131
    +  deriving( Show, Eq, Ord, Generic )
    
    1132 1132
     
    
    1133 1133
     -- | [Functional dependency](https://ghc.gitlab.haskell.org/ghc/doc/users_guide/exts/functional_dependencies.html)
    
    1134 1134
     -- syntax, as in a class declaration.
    
    1135 1135
     data FunDep = FunDep [Name] [Name] -- ^ @class C a b {| a -> b}@
    
    1136
    -  deriving( Show, Eq, Ord, Data, Generic )
    
    1136
    +  deriving( Show, Eq, Ord, Generic )
    
    1137 1137
     
    
    1138 1138
     -- | A @foreign@ declaration.
    
    1139 1139
     data Foreign = ImportF Callconv Safety String Name Type
    
    1140 1140
                  -- ^ @foreign import callconv safety "foreign_name" haskellName :: type@
    
    1141 1141
                  | ExportF Callconv        String Name Type
    
    1142 1142
                  -- ^ @foreign export callconv "foreign_name" haskellName :: type@
    
    1143
    -         deriving( Show, Eq, Ord, Data, Generic )
    
    1143
    +         deriving( Show, Eq, Ord, Generic )
    
    1144 1144
     
    
    1145 1145
     -- keep Callconv in sync with module ForeignCall in ghc/compiler/GHC/Types/ForeignCall.hs
    
    1146 1146
     -- | A calling convention identifier, as in a 'Foreign' declaration.
    
    1147 1147
     data Callconv = CCall | StdCall | CApi | Prim | JavaScript
    
    1148
    -          deriving( Show, Eq, Ord, Data, Generic )
    
    1148
    +          deriving( Show, Eq, Ord, Generic )
    
    1149 1149
     
    
    1150 1150
     -- | A safety level, as in a 'Foreign' declaration.
    
    1151 1151
     data Safety = Unsafe | Safe | Interruptible
    
    1152
    -        deriving( Show, Eq, Ord, Data, Generic )
    
    1152
    +        deriving( Show, Eq, Ord, Generic )
    
    1153 1153
     
    
    1154 1154
     data Pragma = InlineP         Name Inline RuleMatch Phases
    
    1155 1155
                 -- ^ @{ {\-\# [inline] [rule match] [phases] [phases] name #-} }@. See
    
    ... ... @@ -1174,7 +1174,7 @@ data Pragma = InlineP Name Inline RuleMatch Phases
    1174 1174
                     -- ^ @{ {\-\# COMPLETE C_1, ..., C_i [ :: T ] \#-} }@
    
    1175 1175
                 | SCCP            Name (Maybe String)
    
    1176 1176
                     -- ^ @{ {\-\# SCC fun "optional_name" \#-} }@
    
    1177
    -        deriving( Show, Eq, Ord, Data, Generic )
    
    1177
    +        deriving( Show, Eq, Ord, Generic )
    
    1178 1178
     
    
    1179 1179
     -- | An inline pragma.
    
    1180 1180
     data Inline = NoInline
    
    ... ... @@ -1183,7 +1183,7 @@ data Inline = NoInline
    1183 1183
                 -- ^ @{ {\-\# INLINE ... #-} }@
    
    1184 1184
                 | Inlinable
    
    1185 1185
                 -- ^ @{ {\-\# INLINABLE ... #-} }@
    
    1186
    -            deriving (Show, Eq, Ord, Data, Generic)
    
    1186
    +            deriving (Show, Eq, Ord, Generic)
    
    1187 1187
     
    
    1188 1188
     -- | A @CONLIKE@ modifier, as in one of the various inline pragmas, or lack
    
    1189 1189
     -- thereof ('FunLike').
    
    ... ... @@ -1191,7 +1191,7 @@ data RuleMatch = ConLike
    1191 1191
                    -- ^ @{ {\-\# CONLIKE [inline] ... #-} }@
    
    1192 1192
                    | FunLike
    
    1193 1193
                    -- ^ @{ {\-\# [inline] ... #-} }@
    
    1194
    -               deriving (Show, Eq, Ord, Data, Generic)
    
    1194
    +               deriving (Show, Eq, Ord, Generic)
    
    1195 1195
     
    
    1196 1196
     -- | Phase control syntax.
    
    1197 1197
     data Phases = AllPhases
    
    ... ... @@ -1200,14 +1200,14 @@ data Phases = AllPhases
    1200 1200
                 -- ^ @[n]@
    
    1201 1201
                 | BeforePhase Int
    
    1202 1202
                 -- ^ @[~n]@
    
    1203
    -            deriving (Show, Eq, Ord, Data, Generic)
    
    1203
    +            deriving (Show, Eq, Ord, Generic)
    
    1204 1204
     
    
    1205 1205
     -- | A binder found in the @forall@ of a @RULES@ pragma.
    
    1206 1206
     data RuleBndr = RuleVar Name
    
    1207 1207
                   -- ^ @forall {a} ... .@
    
    1208 1208
                   | TypedRuleVar Name Type
    
    1209 1209
                   -- ^ @forall {(a :: t)} ... .@
    
    1210
    -              deriving (Show, Eq, Ord, Data, Generic)
    
    1210
    +              deriving (Show, Eq, Ord, Generic)
    
    1211 1211
     
    
    1212 1212
     -- | The target of an @ANN@ pragma
    
    1213 1213
     data AnnTarget = ModuleAnnotation
    
    ... ... @@ -1216,7 +1216,7 @@ data AnnTarget = ModuleAnnotation
    1216 1216
                    -- ^ @{\-\# ANN type {name} ... #-}@
    
    1217 1217
                    | ValueAnnotation Name
    
    1218 1218
                    -- ^ @{\-\# ANN {name} ... #-}@
    
    1219
    -              deriving (Show, Eq, Ord, Data, Generic)
    
    1219
    +              deriving (Show, Eq, Ord, Generic)
    
    1220 1220
     
    
    1221 1221
     -- | A context, as found on the left side of a @=>@ in a type.
    
    1222 1222
     type Cxt = [Pred]                 -- ^ @(Eq a, Ord b)@
    
    ... ... @@ -1234,7 +1234,7 @@ data SourceUnpackedness
    1234 1234
       = NoSourceUnpackedness -- ^ @C a@
    
    1235 1235
       | SourceNoUnpack       -- ^ @C { {\-\# NOUNPACK \#-\} } a@
    
    1236 1236
       | SourceUnpack         -- ^ @C { {\-\# UNPACK \#-\} } a@
    
    1237
    -        deriving (Show, Eq, Ord, Data, Generic)
    
    1237
    +        deriving (Show, Eq, Ord, Generic)
    
    1238 1238
     
    
    1239 1239
     -- | 'SourceStrictness' corresponds to strictness annotations found in the source code.
    
    1240 1240
     --
    
    ... ... @@ -1243,7 +1243,7 @@ data SourceUnpackedness
    1243 1243
     data SourceStrictness = NoSourceStrictness    -- ^ @C a@
    
    1244 1244
                           | SourceLazy            -- ^ @C {~}a@
    
    1245 1245
                           | SourceStrict          -- ^ @C {!}a@
    
    1246
    -        deriving (Show, Eq, Ord, Data, Generic)
    
    1246
    +        deriving (Show, Eq, Ord, Generic)
    
    1247 1247
     
    
    1248 1248
     -- | Unlike 'SourceStrictness' and 'SourceUnpackedness', 'DecidedStrictness'
    
    1249 1249
     -- refers to the strictness annotations that the compiler chooses for a data constructor
    
    ... ... @@ -1256,7 +1256,7 @@ data SourceStrictness = NoSourceStrictness -- ^ @C a@
    1256 1256
     data DecidedStrictness = DecidedLazy -- ^ Field inferred to not have a bang.
    
    1257 1257
                            | DecidedStrict -- ^ Field inferred to have a bang.
    
    1258 1258
                            | DecidedUnpack -- ^ Field inferred to be unpacked.
    
    1259
    -        deriving (Show, Eq, Ord, Data, Generic)
    
    1259
    +        deriving (Show, Eq, Ord, Generic)
    
    1260 1260
     
    
    1261 1261
     -- | A data constructor.
    
    1262 1262
     --
    
    ... ... @@ -1321,7 +1321,7 @@ data Con =
    1321 1321
                  -- Invariant: the list must be non-empty.
    
    1322 1322
                  [VarBangType] -- ^ The constructor arguments
    
    1323 1323
                  Type -- ^ See Note [GADT return type]
    
    1324
    -        deriving (Show, Eq, Ord, Data, Generic)
    
    1324
    +        deriving (Show, Eq, Ord, Generic)
    
    1325 1325
     
    
    1326 1326
     -- Note [GADT return type]
    
    1327 1327
     -- ~~~~~~~~~~~~~~~~~~~~~~~
    
    ... ... @@ -1353,7 +1353,7 @@ data Con =
    1353 1353
     -- | Strictness information in a data constructor's argument.
    
    1354 1354
     data Bang = Bang SourceUnpackedness SourceStrictness
    
    1355 1355
              -- ^ @C { {\-\# UNPACK \#-\} !}a@
    
    1356
    -        deriving (Show, Eq, Ord, Data, Generic)
    
    1356
    +        deriving (Show, Eq, Ord, Generic)
    
    1357 1357
     
    
    1358 1358
     -- | A type with a strictness annotation, as in data constructors. See 'Con'.
    
    1359 1359
     type BangType    = (Bang, Type)
    
    ... ... @@ -1377,14 +1377,14 @@ data PatSynDir
    1377 1377
       = Unidir             -- ^ @pattern P x {<-} p@
    
    1378 1378
       | ImplBidir          -- ^ @pattern P x {=} p@
    
    1379 1379
       | ExplBidir [Clause] -- ^ @pattern P x {<-} p where P x = e@
    
    1380
    -  deriving( Show, Eq, Ord, Data, Generic )
    
    1380
    +  deriving( Show, Eq, Ord, Generic )
    
    1381 1381
     
    
    1382 1382
     -- | A pattern synonym's argument type.
    
    1383 1383
     data PatSynArgs
    
    1384 1384
       = PrefixPatSyn [Name]        -- ^ @pattern P {x y z} = p@
    
    1385 1385
       | InfixPatSyn Name Name      -- ^ @pattern {x P y} = p@
    
    1386 1386
       | RecordPatSyn [Name]        -- ^ @pattern P { {x,y,z} } = p@
    
    1387
    -  deriving( Show, Eq, Ord, Data, Generic )
    
    1387
    +  deriving( Show, Eq, Ord, Generic )
    
    1388 1388
     
    
    1389 1389
     -- | A Haskell type.
    
    1390 1390
     data Type = ForallT [TyVarBndr Specificity] Cxt Type -- ^ @forall \<vars\>. \<ctxt\> => \<type\>@
    
    ... ... @@ -1423,12 +1423,12 @@ data Type = ForallT [TyVarBndr Specificity] Cxt Type -- ^ @forall \<vars\>. \<ct
    1423 1423
               | LitT TyLit                     -- ^ @0@, @1@, @2@, etc.
    
    1424 1424
               | WildCardT                      -- ^ @_@
    
    1425 1425
               | ImplicitParamT String Type     -- ^ @?x :: t@
    
    1426
    -      deriving( Show, Eq, Ord, Data, Generic )
    
    1426
    +      deriving( Show, Eq, Ord, Generic )
    
    1427 1427
     
    
    1428 1428
     -- | The specificity of a type variable in a @forall ...@.
    
    1429 1429
     data Specificity = SpecifiedSpec          -- ^ @a@
    
    1430 1430
                      | InferredSpec           -- ^ @{a}@
    
    1431
    -      deriving( Show, Eq, Ord, Data, Generic )
    
    1431
    +      deriving( Show, Eq, Ord, Generic )
    
    1432 1432
     
    
    1433 1433
     -- | The @flag@ type parameter is instantiated to one of the following types:
    
    1434 1434
     --
    
    ... ... @@ -1438,40 +1438,40 @@ data Specificity = SpecifiedSpec -- ^ @a@
    1438 1438
     --
    
    1439 1439
     data TyVarBndr flag = PlainTV  Name flag      -- ^ @a@
    
    1440 1440
                         | KindedTV Name flag Kind -- ^ @(a :: k)@
    
    1441
    -      deriving( Show, Eq, Ord, Data, Generic, Functor, Foldable, Traversable )
    
    1441
    +      deriving( Show, Eq, Ord, Generic, Functor, Foldable, Traversable )
    
    1442 1442
     
    
    1443 1443
     -- | Visibility of a type variable. See [Inferred vs. specified type variables](https://ghc.gitlab.haskell.org/ghc/doc/users_guide/exts/type_applications.html#inferred-vs-specified-type-variables).
    
    1444 1444
     data BndrVis = BndrReq                    -- ^ @a@
    
    1445 1445
                  | BndrInvis                  -- ^ @\@a@
    
    1446
    -      deriving( Show, Eq, Ord, Data, Generic )
    
    1446
    +      deriving( Show, Eq, Ord, Generic )
    
    1447 1447
     
    
    1448 1448
     -- | Type family result signature
    
    1449 1449
     data FamilyResultSig = NoSig              -- ^ no signature
    
    1450 1450
                          | KindSig  Kind      -- ^ @k@
    
    1451 1451
                          | TyVarSig (TyVarBndr ()) -- ^ @= r, = (r :: k)@
    
    1452
    -      deriving( Show, Eq, Ord, Data, Generic )
    
    1452
    +      deriving( Show, Eq, Ord, Generic )
    
    1453 1453
     
    
    1454 1454
     -- | Injectivity annotation as in an [injective type family](https://ghc.gitlab.haskell.org/ghc/doc/users_guide/exts/type_families.html)
    
    1455 1455
     data InjectivityAnn = InjectivityAnn Name [Name]
    
    1456
    -  deriving ( Show, Eq, Ord, Data, Generic )
    
    1456
    +  deriving ( Show, Eq, Ord, Generic )
    
    1457 1457
     
    
    1458 1458
     -- | Type-level literals.
    
    1459 1459
     data TyLit = NumTyLit Integer             -- ^ @2@
    
    1460 1460
                | StrTyLit String              -- ^ @\"Hello\"@
    
    1461 1461
                | CharTyLit Char               -- ^ @\'C\'@, @since 4.16.0.0
    
    1462
    -  deriving ( Show, Eq, Ord, Data, Generic )
    
    1462
    +  deriving ( Show, Eq, Ord, Generic )
    
    1463 1463
     
    
    1464 1464
     -- | Role annotations
    
    1465 1465
     data Role = NominalR            -- ^ @nominal@
    
    1466 1466
               | RepresentationalR   -- ^ @representational@
    
    1467 1467
               | PhantomR            -- ^ @phantom@
    
    1468 1468
               | InferR              -- ^ @_@
    
    1469
    -  deriving( Show, Eq, Ord, Data, Generic )
    
    1469
    +  deriving( Show, Eq, Ord, Generic )
    
    1470 1470
     
    
    1471 1471
     -- | Annotation target for reifyAnnotations
    
    1472 1472
     data AnnLookup = AnnLookupModule Module
    
    1473 1473
                    | AnnLookupName Name
    
    1474
    -               deriving( Show, Eq, Ord, Data, Generic )
    
    1474
    +               deriving( Show, Eq, Ord, Generic )
    
    1475 1475
     
    
    1476 1476
     -- | To avoid duplication between kinds and types, they
    
    1477 1477
     -- are defined to be the same. Naturally, you would never
    
    ... ... @@ -1522,7 +1522,7 @@ data DocLoc
    1522 1522
       | ArgDoc Name Int   -- ^ At a specific argument of a function, indexed by its
    
    1523 1523
                           -- position.
    
    1524 1524
       | InstDoc Type      -- ^ At a class or family instance.
    
    1525
    -  deriving ( Show, Eq, Ord, Data, Generic )
    
    1525
    +  deriving ( Show, Eq, Ord, Generic )
    
    1526 1526
     
    
    1527 1527
     -----------------------------------------------------
    
    1528 1528
     --              Internal helper functions