#6029: GHC fails to stop at phase HCc
------------------------------+---------------------------------------------
 Reporter:  liuexp            |          Owner:                  
     Type:  bug               |         Status:  new             
 Priority:  normal            |      Component:  Compiler        
  Version:  7.4.1             |       Keywords:                  
       Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
  Failure:  Other             |       Testcase:                  
Blockedby:                    |       Blocking:                  
  Related:                    |  
------------------------------+---------------------------------------------
 I tried with several different haskell source code and all got the same
 error:

 [liuexp@liuexp pearls]$ ghc -C minfree.hs

 addFlag by -C on the commandline:
     Warning: The -fvia-C flag does nothing; it will be removed in a future
 GHC release
 ghc: panic! (the 'impossible' happened)
   (GHC version 7.4.1 for i386-unknown-linux):
         pipeLoop: at phase As but I wanted to stop at phase HCc



 here's minfree.hs for reference:

 [liuexp@liuexp pearls]$ cat minfree.hs
 {-# OPTIONS_GHC -O2 #-}
 module Pearls where
 import Data.List hiding (union)
 import Data.List.Ordered (minus,union)
 import Data.Map (Map)
 import Data.Set (Set)
 import qualified Data.Set as DS
 import qualified Data.Map as DM
 import Data.Sequence (Seq, (<|), (|>), (><))
 import qualified Data.Sequence as S
 import qualified Data.Foldable as F

 import Control.Monad
 import Control.Applicative

 --assuming no duplicates
 minfree xs = minfrom 0 (length xs,xs)
 minfrom a (n,xs)
         |n == 0 = a
         |m == b -a = minfrom b (n-m,vs)
         |otherwise = minfrom a (m,us)
         where   (us,vs)= partition (<b) xs
                 b = a + 1 + n `div` 2
                 m = length us

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