#3902: Partial application gives type error
-------------------------------+--------------------------------------------
Reporter: moleculeColony | Owner:
Type: bug | Status: new
Priority: normal | Component: Compiler (Type checker)
Version: 6.10.4 | Keywords:
Os: Linux | Testcase:
Architecture: x86_64 (amd64) | Failure: GHC rejects valid program
-------------------------------+--------------------------------------------
I've tried to use the following line in my code (just to save some
typing):
fI = fromIntegral
However, in certain cases it gives a type error, whereas the following
version works:
fI x = fromIntegral x
Here a program that doesn't compile (with the error at the end):
{{{
import Graphics.UI.Gtk
import Graphics.UI.Gtk.Gdk.EventM
import Control.Monad.Reader
import System.Random
import Data.Array.MArray
import Data.Array.IO
import Data.Word
main = do
parr <- newArray ((1,1,1),(600,600,3)) 127 :: IO (IOUArray (Int,Int,Int)
Word8)
initGUI
win <- windowNew
brush <- pixbufNew ColorspaceRgb False 8 10 10
widgetShowAll win
dw <- widgetGetDrawWindow win
gc <- gcNew dw
timeoutAdd (draw parr dw gc brush) 1
on win deleteEvent $ tryEvent $ liftIO mainQuit
mainGUI
draw parr dw gc brush = do
x <- randomRIO (1,600)
y <- randomRIO (1,600)
rr <- randomRIO (0,255) :: IO Int
gr <- randomRIO (0,255) :: IO Int
br <- randomRIO (0,255) :: IO Int
rw <- readArray parr (x,y,1)
gw <- readArray parr (x,y,2)
bw <- readArray parr (x,y,3)
let (ro,go,bo) = (fI rw, fI gw, fI bw)
let cs = ro+go+bo
let rn = div cs 6 + div rr 2
let gn = div cs 6 + div gr 2
let bn = div cs 6 + div br 2
let (ra,ga,ba) = (fI rn,fI gn,fI bn)
writeArray parr (x,y,1) ra
writeArray parr (x,y,2) ga
writeArray parr (x,y,3) ba
pixbufFill brush ra ga ba 0
w <- randomRIO (1,10)
h <- randomRIO (1,10)
drawPixbuf dw gc brush 0 0 x y w h RgbDitherNone 0 0
return True
fI = fromIntegral
fitest.hs:39:19:
Couldn't match expected type `Word8' against inferred type `Int'
In the second argument of `pixbufFill', namely `ra'
In a stmt of a 'do' expression: pixbufFill brush ra ga ba 0
In the expression:
do x <- randomRIO (1, 600)
y <- randomRIO (1, 600)
rr <- randomRIO (0, 255) :: IO Int
gr <- randomRIO (0, 255) :: IO Int
....
}}}
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/3902>
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