
On Thu, Nov 3, 2011 at 11:55 AM, Amy de Buitléir
I'm trying to read something from a file, do something with it, and then write it out again. I don't know, or care about, the type of the object I'm reading, but I do know its class. Here's my code:
---------- import Data.Binary ( Binary, encode, decode ) import Data.ByteString.Lazy as B ( readFile, writeFile ) import Codec.Compression.GZip ( compress, decompress )
class ( Binary a, Show a, Eq a ) => Thing a where doSomething :: a -> IO a
From a quick read, your 'main' method never tells the compiler which instance of 'Thing' to use, so it is unable to look up the correct implementation of 'doSomething' (or the correct implementation of 'decode').
Antoine
readThing :: ( Thing a ) => FilePath -> IO a readThing f = return . decode . decompress =<< B.readFile f
writeThing :: ( Thing a ) => FilePath -> a -> IO () writeThing f = B.writeFile f . compress . encode
main = do a <- readThing "file1.txt" a' <- doSomething a writeThing "file2.txt" a' ----------
And here's the compiler error I get.
Amy.hs:18:3: Ambiguous type variable `a0' in the constraint: (Thing a0) arising from a use of `writeThing' Probable fix: add a type signature that fixes these type variable(s) In the expression: writeThing "file2.txt" a' In the expression: do { a <- readThing "file1.txt"; a' <- doSomething a; writeThing "file2.txt" a' } In an equation for `main': main = do { a <- readThing "file1.txt"; a' <- doSomething a; writeThing "file2.txt" a' }
Is there a way to fix my code? I tried adding a type signature, e.g.,
a <- readThing "file1.txt" :: (Thing t) => IO t a' <- doSomething a :: (Thing t) => IO t
but then it says...
Couldn't match type `t0' with `t' because type variable `t' would escape its scope This (rigid, skolem) type variable is bound by an expression type signature: Thing t => IO t The following variables have types that mention t0 a :: t0 (bound at Amy.hs:16:3) In a stmt of a 'do' expression: a' <- doSomething a :: Thing t => IO t In the expression: do { a <- readThing "file1.txt" :: Thing t => IO t; a' <- doSomething a :: Thing t => IO t; writeThing "file2.txt" a' } In an equation for `main': main = do { a <- readThing "file1.txt" :: Thing t => IO t; a' <- doSomething a :: Thing t => IO t; writeThing "file2.txt" a' }
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners