[GHC] #10852: ghc 7.8.4 on arm - panic: Simplifier ticks exhausted
GHC
ghc-devs at haskell.org
Sun Nov 29 13:56:59 UTC 2015
#10852: ghc 7.8.4 on arm - panic: Simplifier ticks exhausted
---------------------------------------+------------------------------
Reporter: andrewufrank | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.10.2
Resolution: | Keywords: arm
Operating System: Linux | Architecture: arm
Type of failure: Compile-time crash | Test Case:
Blocked By: | Blocking:
Related Tickets: #5642, #9675 | Differential Rev(s):
Wiki Page: |
---------------------------------------+------------------------------
Comment (by andrewufrank):
the problem in pureMD5 seems to be in the part
{{{
#ifdef FastWordExtract
getNthWord n b = inlinePerformIO (unsafeUseAsCString b (flip peekElemOff n
. castPtr))
#else
getNthWord :: Int -> B.ByteString -> Word32
getNthWord n = right . G.runGet G.getWord32le . B.drop (n * sizeOf
(undefined :: Word32))
where
right x = case x of Right y -> y
#endif
-- {-# INLINE getNthWord #-}
}}}
i have removed the inline pragma and it compiles.
the armhf is not FastWordExtract (at least not set in the cabal) and thus
uses code which is typically for the intel processor not used.
i hope this helps to fix the problem.
thank you!
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/10852#comment:7>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list