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

Commits:

9 changed files:

Changes:

  • compiler/GHC/Cmm.hs
    ... ... @@ -269,7 +269,6 @@ data SectionType
    269 269
       | FiniArray           -- .fini_array on ELF, .dtor on Windows
    
    270 270
       | CString
    
    271 271
       | IPE
    
    272
    -  | OtherSection String
    
    273 272
       deriving (Show)
    
    274 273
     
    
    275 274
     data SectionProtection
    
    ... ... @@ -290,7 +289,6 @@ sectionProtection (Section t _) = case t of
    290 289
         Data                    -> ReadWriteSection
    
    291 290
         UninitialisedData       -> ReadWriteSection
    
    292 291
         IPE                     -> ReadWriteSection
    
    293
    -    (OtherSection _)        -> ReadWriteSection
    
    294 292
     
    
    295 293
     {-
    
    296 294
     Note [Relocatable Read-Only Data]
    
    ... ... @@ -550,4 +548,3 @@ pprSectionType s = doubleQuotes $ case s of
    550 548
       FiniArray               -> text "finiarray"
    
    551 549
       CString                 -> text "cstring"
    
    552 550
       IPE                     -> text "ipe"
    553
    -  OtherSection s'         -> text s'

  • compiler/GHC/Cmm/Parser.y
    ... ... @@ -978,7 +978,7 @@ section "data" = Data
    978 978
     section "rodata"    = ReadOnlyData
    
    979 979
     section "relrodata" = RelocatableReadOnlyData
    
    980 980
     section "bss"       = UninitialisedData
    
    981
    -section s           = OtherSection s
    
    981
    +section s           = panic ("CmmParse: unknown section type: " ++ s)
    
    982 982
     
    
    983 983
     mkString :: String -> CmmStatic
    
    984 984
     mkString s = CmmString (BS8.pack s)
    

  • compiler/GHC/CmmToAsm/AArch64/Ppr.hs
    ... ... @@ -91,8 +91,6 @@ pprAlignForSection _platform _seg
    91 91
     --     .balign 8
    
    92 92
     --
    
    93 93
     pprSectionAlign :: IsDoc doc => NCGConfig -> Section -> doc
    
    94
    -pprSectionAlign _config (Section (OtherSection _) _) =
    
    95
    -     panic "AArch64.Ppr.pprSectionAlign: unknown section"
    
    96 94
     pprSectionAlign config sec@(Section seg _) =
    
    97 95
         line (pprSectionHeader config sec)
    
    98 96
         $$ pprAlignForSection (ncgPlatform config) seg
    

  • compiler/GHC/CmmToAsm/LA64/Ppr.hs
    ... ... @@ -108,8 +108,6 @@ pprAlignForSection _seg = pprAlign . mkAlignment $ 8
    108 108
     --     .balign 8
    
    109 109
     --
    
    110 110
     pprSectionAlign :: IsDoc doc => NCGConfig -> Section -> doc
    
    111
    -pprSectionAlign _config (Section (OtherSection _) _) =
    
    112
    -  panic "LA64.Ppr.pprSectionAlign: unknown section"
    
    113 111
     pprSectionAlign config sec@(Section seg _) =
    
    114 112
         line (pprSectionHeader config sec)
    
    115 113
         $$ pprAlignForSection seg
    

  • compiler/GHC/CmmToAsm/PPC/Ppr.hs
    ... ... @@ -302,7 +302,6 @@ pprAlignForSection platform seg = line $
    302 302
            CString
    
    303 303
             | ppc64          -> text ".align 3"
    
    304 304
             | otherwise      -> text ".align 2"
    
    305
    -       OtherSection _    -> panic "PprMach.pprSectionAlign: unknown section"
    
    306 305
     
    
    307 306
     pprDataItem :: IsDoc doc => Platform -> CmmLit -> doc
    
    308 307
     pprDataItem platform lit
    

  • compiler/GHC/CmmToAsm/Ppr.hs
    ... ... @@ -240,8 +240,6 @@ pprGNUSectionHeader config t suffix =
    240 240
             | OSMinGW32 <- platformOS platform
    
    241 241
                         -> text ".rdata"
    
    242 242
             | otherwise -> text ".ipe"
    
    243
    -      OtherSection _ ->
    
    244
    -        panic "PprBase.pprGNUSectionHeader: unknown section type"
    
    245 243
         flags = case t of
    
    246 244
           Text
    
    247 245
             | OSMinGW32 <- platformOS platform, splitSections
    
    ... ... @@ -286,6 +284,5 @@ pprDarwinSectionHeader t = case t of
    286 284
       FiniArray               -> panic "pprDarwinSectionHeader: fini not supported"
    
    287 285
       CString                 -> text ".section\t__TEXT,__cstring,cstring_literals"
    
    288 286
       IPE                     -> text ".const"
    
    289
    -  OtherSection _          -> panic "pprDarwinSectionHeader: unknown section type"
    
    290 287
     {-# SPECIALIZE pprDarwinSectionHeader :: SectionType -> SDoc #-}
    
    291 288
     {-# SPECIALIZE pprDarwinSectionHeader :: SectionType -> HLine #-} -- see Note [SPECIALIZE to HDoc] in GHC.Utils.Outputable

  • compiler/GHC/CmmToAsm/RV64/Ppr.hs
    ... ... @@ -99,8 +99,6 @@ pprAlignForSection _seg = pprAlign . mkAlignment $ 8
    99 99
     --     .section .text
    
    100 100
     --     .balign 8
    
    101 101
     pprSectionAlign :: (IsDoc doc) => NCGConfig -> Section -> doc
    
    102
    -pprSectionAlign _config (Section (OtherSection _) _) =
    
    103
    -  panic "RV64.Ppr.pprSectionAlign: unknown section"
    
    104 102
     pprSectionAlign config sec@(Section seg _) =
    
    105 103
       line (pprSectionHeader config sec)
    
    106 104
         $$ pprAlignForSection seg
    

  • compiler/GHC/CmmToAsm/X86/Ppr.hs
    ... ... @@ -526,8 +526,6 @@ pprAddr platform (AddrBaseIndex base index displacement)
    526 526
     
    
    527 527
     -- | Print section header and appropriate alignment for that section.
    
    528 528
     pprSectionAlign :: IsDoc doc => NCGConfig -> Section -> doc
    
    529
    -pprSectionAlign _config (Section (OtherSection _) _) =
    
    530
    -     panic "X86.Ppr.pprSectionAlign: unknown section"
    
    531 529
     pprSectionAlign config sec@(Section seg _) =
    
    532 530
         line (pprSectionHeader config sec) $$
    
    533 531
         pprAlignForSection (ncgPlatform config) seg
    

  • compiler/GHC/CmmToLlvm/Data.hs
    ... ... @@ -148,7 +148,6 @@ llvmSectionType p t = case t of
    148 148
         IPE                     -> fsLit ".ipe"
    
    149 149
         InitArray               -> panic "llvmSectionType: InitArray"
    
    150 150
         FiniArray               -> panic "llvmSectionType: FiniArray"
    
    151
    -    OtherSection _          -> panic "llvmSectionType: unknown section type"
    
    152 151
     
    
    153 152
     -- | Format a Cmm Section into a LLVM section name
    
    154 153
     llvmSection :: Section -> LlvmM LMSection