#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 simonpj):

 The whole approach in this ticket is a bit unsatisfactory (I know, I
 recommended it!) because it only works if the typechecker knows enough at
 the moment it encounters the literal.  The vaguaries of inference might
 mean it doesn't know enough, and it ''certainly'' won't know enough if you
 have constant in code that is subsequently specialised:
 {{{
 f :: Num a => a -> a
 f a = a + 0x9ddfea08eb382d69
 {-# SPECIALISE f :: Word64 -> Word64 #-}
 }}}
 The Right Thing is really for the optimiser to do the right constant-
 folding thing.  I can see two reasonable alternative approaches.

 The first is to treat big integer literals using a list of coefficients
 thus:
 {{{
 makeInteger :: [Int] -> Integer
 }}}
 (This would replace the chain of plus/multiply stuff at the moment.)  With
 the idea that
 {{{
 makeInteger [a,b,c] = a + 10000*(b + 10000*c)
 }}}
 (Actually 2**30 would probably be a better constant than 10000.)  Now you
 could sensibly have a rule
 {{{
 RULE "fromInteger/Float"
  fromInteger (makeInteger (a:as)) = a + 10000*fromInteger (makeInteger as)
 :: Word64
 }}}
 or something like that.  (This would allow out of range Word constants,
 which would just overflow.  I'd prefer a static error...)

 A second approach would be to make Core have a built-in, boxed, literal
 type `Integer`, not (visibly) represented with a data type.  It would
 directly support constant-folding etc just as `Int#` does.  Then in the
 back end it'd be expanded to a call to `makeInteger` or something like
 that.

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/5152#comment:7>
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