#5152: GHC generates poor code for large 64-bit literals
---------------------------------+------------------------------------------
    Reporter:  bos               |        Owner:  igloo                  
        Type:  bug               |       Status:  new                    
    Priority:  normal            |    Milestone:  7.4.1                  
   Component:  Compiler          |      Version:  7.0.3                  
    Keywords:                    |     Testcase:                         
   Blockedby:                    |   Difficulty:                         
          Os:  Unknown/Multiple  |     Blocking:                         
Architecture:  Unknown/Multiple  |      Failure:  Runtime performance bug
---------------------------------+------------------------------------------

Comment(by thoughtpolice):

 I've fixed this in the `Word64` case at least. My branch with the fix is
 here:

 https://github.com/thoughtpolice/ghc/tree/trac-5152

 Relevant commit:

 
https://github.com/thoughtpolice/ghc/commit/18cf5ba840a7ecdf1860e54b8a6c8f3fcdf0441d

 With GHC 7.0.4, here are my results:

 {{{
 $ cat ghc_5152.hs
 module Main where

 import Data.Word (Word64)

 {-# NOINLINE a #-}
 a :: Word64
 a = 0x9ddfea08eb382d69

 main = print a
 }}}

 I get:

 {{{
 ghc -ddump-simpl -fforce-recomp ghc_5152.hs
 [1 of 1] Compiling Main             ( ghc_5152.hs, ghc_5152.o )

 ==================== Tidy Core ====================
 Main.a [InlPrag=NOINLINE] :: GHC.Word.Word64
 [GblId]
 Main.a =
   GHC.Num.fromInteger
     @ GHC.Word.Word64
     GHC.Word.$fNumWord64
     (GHC.Integer.plusInteger
        (GHC.Integer.smallInteger 2152696470933351786)
        (GHC.Integer.smallInteger 9223372036854775807))

 Main.main :: GHC.Types.IO ()
 [GblId]
 Main.main =
   System.IO.print @ GHC.Word.Word64 GHC.Word.$fShowWord64 Main.a

 :Main.main :: GHC.Types.IO ()
 [GblId]
 :Main.main = GHC.TopHandler.runMainIO @ () Main.main
 }}}

 With my patch, I get:

 {{{
 ~/code/ghc/inplace/bin/ghc-stage2 -ddump-simpl -fforce-recomp ghc_5152.hs
 [1 of 1] Compiling Main             ( ghc_5152.hs, ghc_5152.o )

 ==================== Tidy Core ====================
 Result size = 12

 Main.a [InlPrag=NOINLINE] :: GHC.Word.Word64
 [GblId, Caf=NoCafRefs]
 Main.a = GHC.Word.W# __word 11376068507788127593

 Main.main :: GHC.Types.IO ()
 [GblId]
 Main.main =
   System.IO.print @ GHC.Word.Word64 GHC.Word.$fShowWord64 Main.a

 :Main.main :: GHC.Types.IO ()
 [GblId]
 :Main.main = GHC.TopHandler.runMainIO @ () Main.main
 }}}

 Which should be exactly what you want, Bryan.

 I'm willing to extend this patch to handle other fixed-width types - I
 assume `Int64` probably needs handling among other things. If this is what
 should be done, I'm willing to assign this ticket to myself and add those
 cases.

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/5152#comment:3>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler

_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to