#5688: instance Read Integer/Rational/Double readsPrec out of memory and crash 
due
to exponential notation
---------------------------------+------------------------------------------
    Reporter:  gracjan           |       Owner:                  
        Type:  bug               |      Status:  patch           
    Priority:  highest           |   Milestone:  7.4.1           
   Component:  libraries/base    |     Version:  6.12.3          
    Keywords:                    |          Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  |     Failure:  Runtime crash   
  Difficulty:  Unknown           |    Testcase:                  
   Blockedby:                    |    Blocking:                  
     Related:                    |  
---------------------------------+------------------------------------------

Comment(by gracjan):

 To chime in: parsing Float and Double also kills programs because this
 goes through Rational.

 Text.JSON is self guilty. Here is the relevant snippet from json-0.5.
 File Text/JSON/String.hs:189

 {{{
    exponent' n (c:cs)
     | c == 'e' || c == 'E' = (n*) <$> exp_num cs
    exponent' n cs = setInput cs >> return n

    exp_num          :: String -> GetJSON Rational
    exp_num ('+':cs)  = exp_digs cs
    exp_num ('-':cs)  = recip <$> exp_digs cs
    exp_num cs        = exp_digs cs

    exp_digs :: String -> GetJSON Rational
    exp_digs cs = case readDec cs of
        [(a,ds)] -> do setInput ds
                       return (fromIntegral ((10::Integer) ^ (a::Integer)))
        _        -> fail $ "Unable to parse JSON exponential: " ++ context
 cs

 }}}

 Same with aeson because of attoparsec: Data.Attoparsec.Text:

 {{{
 number :: Parser Number
 number = floaty $ \real frac fracDenom ->
          if frac == 0 && fracDenom == 0
          then I real
          else D (asDouble real frac fracDenom)

 ...
   let n = if fracDigits == 0
           then if power == 0
                then fromIntegral real
                else fromIntegral real * (10 ^^ power)
           else if power == 0
                then f real fraction (10 ^ fracDigits)
                else f real fraction (10 ^ fracDigits) * (10 ^^ power)
 }}}

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