#5783: Data.Text.isPrefixOf fails to terminate
------------------------------------------+---------------------------------
  Reporter:  reinerp                      |          Owner:                
      Type:  bug                          |         Status:  closed        
  Priority:  highest                      |      Milestone:  7.4.1         
 Component:  Compiler                     |        Version:  7.4.1-rc1     
Resolution:  invalid                      |       Keywords:                
        Os:  MacOS X                      |   Architecture:  x86_64 (amd64)
   Failure:  Incorrect result at runtime  |     Difficulty:  Unknown       
  Testcase:                               |      Blockedby:                
  Blocking:                               |        Related:                
------------------------------------------+---------------------------------
Changes (by simonmar):

  * status:  new => closed
  * resolution:  => invalid


Comment:

 In `Data.Text` there is this:

 {{{
 -- | /O(n)/ The 'isPrefixOf' function takes two 'Text's and returns
 -- 'True' iff the first is a prefix of the second.  Subject to fusion.
 isPrefixOf :: Text -> Text -> Bool
 isPrefixOf a@(Text _ _ alen) b@(Text _ _ blen) =
     alen <= blen && S.isPrefixOf (stream a) (stream b)
 {-# INLINE [1] isPrefixOf #-}

 {-# RULES
 "TEXT isPrefixOf -> fused" [~1] forall s t.
     isPrefixOf s t = S.isPrefixOf (stream s) (stream t)
 "TEXT isPrefixOf -> unfused" [1] forall s t.
     S.isPrefixOf (stream s) (stream t) = isPrefixOf s t
   #-}
 }}}

 It looks to me like GHC has applied the second rewrite rule to end up with

 {{{
 isPrefixOf a@(Text _ _ alen) b@(Text _ _ blen) =
     alen <= blen && isPrefixOf a b
 }}}

 which is an infinite loop when `alen > blen`.

 So I don't think this is a bug, but the `text` package will need to be
 fixed. Maybe this is going wroing now because we're optimising INLINE
 functions after capturing their definitions, whereas we weren't before.

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