
Thing a means a could be anything, but by the time your program
compiles, a must be something. readThing "file1.txt" returns
something that is a Thing, but what? Int? String? doSomething could
do wildly different things depending what a is, and so you have to
tell it what you want it to be, or it has to infer it by the way it is
being used. Unfortunately, it can't tell what a was supposed to be by
the way you used it so it said it was ambiguous. So, find what data
types are instances of Thing, choose whichever is most appropriate and
then:
a <- readThing "file1.txt" :: IO Whichever
a' <- doSomething a
where Whichever is your chosen instance of Thing.
On Thu, Nov 3, 2011 at 12:55 PM, 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
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