#4497: hmatrix-0.10.0.0 fails to build with GHC 7.0.1 (worked with 
7.0.0.20101111)
---------------------------------------------------------+------------------
    Reporter:  luite                                     |        Owner:        
      
        Type:  bug                                       |       Status:  new   
      
    Priority:  normal                                    |    Milestone:        
      
   Component:  Compiler                                  |      Version:  7.0.1 
      
    Keywords:  hmatrix context reduction stack overflow  |     Testcase:        
      
   Blockedby:                                            |   Difficulty:        
      
          Os:  Windows                                   |     Blocking:        
      
Architecture:  Unknown/Multiple                          |      Failure:  
None/Unknown
---------------------------------------------------------+------------------

Comment(by simonpj):

 OK here's a tiny program with no dependencies that demonstrates the bug.
 {{{
 {-# LANGUAGE FlexibleContexts, MultiParamTypeClasses, TypeFamilies #-}
 module T4497 where

 norm2PropR a = twiddle (norm2 a) a

 twiddle :: Normed a => a -> a -> Double
 twiddle a b = undefined

 norm2 :: e -> RealOf e
 norm2 = undefined

 class (Num (RealOf t)) => Normed t

 type family RealOf x
 }}}
 Great.  Dimitrios and I know what's happening. Patch coming.

 Simon

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