#625: Incorrect handling of types
------------------------------------------+---------------------------------
 Reporter:  hjgtuyl (at) chello (dot) nl  |          Owner:         
     Type:  bug                           |         Status:  new    
 Priority:  normal                        |      Milestone:         
Component:  Compiler (Type checker)       |        Version:  6.4.1  
 Severity:  normal                        |       Keywords:         
       Os:  Windows                       |   Architecture:  Unknown
------------------------------------------+---------------------------------
The following program, taken from
 http://shootout.alioth.debian.org/benchmark.php?test=pidigits&lang=ghc&id=0
 compiles without a problem:

 -------------------------------------------------
 import System

 floor_ev (q, r, s, t) x = (q*x + r) `div` (s*x + t)
 comp (q,r,s,t) (q',r',s',t') = (q*q' + r*s', q*r' + r*t', s*q' + t*s',
 s*r' + t*t')
 next z = floor_ev z 3
 safe z n = n == floor_ev z 4
 prod z n = comp (10,-10 * n, 0, 1) z
 cons z k = let den = 2*k+1 in comp z (fromIntegral k, fromIntegral
 (2*den), 0, fromIntegral

 den)

 digit :: Int -> (Integer,Integer,Integer,Integer) -> Int -> Int -> Int ->
 IO ()
 digit k z 0 row col = putStrLn (take (10-col) "
 "++"\t:"++show (row+col))
 digit k z n row col =
   if safe z y
      then if col == 10
      then do let row' = row + 10
              putStr ("\t:"++show row'++"\n"++show y)
              digit k (prod z y) (n-1) row' 1
      else putStr (show y) >> digit k (prod z y) (n-1) row (col+1)
      else digit (k+1) (cons z k) n row col
   where y = next z

 main =
   do [n] <- getArgs
      digit 1 (1,0,0,1) (read n) 0 0
 -------------------------------------------------

 When substituting "safe z y" in the function "digits" with it's
 definition, we get:

 -------------------------------------------------
 import System

 floor_ev (q, r, s, t) x = (q*x + r) `div` (s*x + t)
 comp (q,r,s,t) (q',r',s',t') = (q*q' + r*s', q*r' + r*t', s*q' + t*s',
 s*r' + t*t')
 next z = floor_ev z 3
 safe z n = n == floor_ev z 4
 prod z n = comp (10,-10 * n, 0, 1) z
 cons z k = let den = 2*k+1 in comp z (fromIntegral k, fromIntegral
 (2*den), 0, fromIntegral

 den)

 digit :: Int -> (Integer,Integer,Integer,Integer) -> Int -> Int -> Int ->
 IO ()
 digit k z 0 row col = putStrLn (take (10-col) "
 "++"\t:"++show (row+col))
 digit k z n row col =
   if n == floor_ev z 4   -- safe z y
      then if col == 10
      then do let row' = row + 10
              putStr ("\t:"++show row'++"\n"++show y)
              digit k (prod z y) (n-1) row' 1
      else putStr (show y) >> digit k (prod z y) (n-1) row (col+1)
      else digit (k+1) (cons z k) n row col
   where y = next z

 main =
   do [n] <- getArgs
      digit 1 (1,0,0,1) (read n) 0 0
 -------------------------------------------------

 The compilation then fails with the message:

 Pidigits2.hs:13:19:
     Couldn't match `Int' against `Integer'
       Expected type: (Int, Int, Int, Int)
       Inferred type: (Integer, Integer, Integer, Integer)
     In the first argument of `floor_ev', namely `z'
     In the second argument of `(==)', namely `floor_ev z 4'

 I suppose this is a correct message, but then the first version should not
 have been compiled

 either.

-- 
Ticket URL: <http://cvs.haskell.org/trac/ghc/ticket/625>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to