Haskell wants the type, but I only know the class.

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' }

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

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

Thank you, David and Antoine. I was planning to have files containing different types of objects, but where all of the types are instances of a particular class. Since the class definition ensures that whatever the types are, they implement the methods that I need, I hoped to be able to manipulate the files using those methods, without having to find out the class programmatically. Clearly I need to rethink this. I'm looking into existentially quantified data constructors now, maybe that will help.

On Thu, Nov 3, 2011 at 1:08 PM, Amy de Buitléir
Thank you, David and Antoine.
I was planning to have files containing different types of objects, but where all of the types are instances of a particular class. Since the class definition ensures that whatever the types are, they implement the methods that I need, I hoped to be able to manipulate the files using those methods, without having to find out the class programmatically.
Clearly I need to rethink this. I'm looking into existentially quantified data constructors now, maybe that will help.
You'll still need some way to build the existential data constructor at run-time - what information will you have at run-time to select the right instance? One thing to keep in mind is that GHC erases types during compilation, so there isn't any sort of run-time operator like 'getTypeByName :: String -> Type'. Some projects (acid-state, in particular) build up mappings from ByteString tags to existential constructor types which can be used to deserialize binary data. I'd be interested in knowing what other folks do for this sort of thing. Antoine
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

I think this is the exact use case that the new ConstraintKinds extension
was meant to address (http://hackage.haskell.org/trac/ghc/wiki/Status/Oct11).
But we have to wait for 7.4.
-deech
On Thu, Nov 3, 2011 at 1:08 PM, Amy de Buitléir
Thank you, David and Antoine.
I was planning to have files containing different types of objects, but where all of the types are instances of a particular class. Since the class definition ensures that whatever the types are, they implement the methods that I need, I hoped to be able to manipulate the files using those methods, without having to find out the class programmatically.
Clearly I need to rethink this. I'm looking into existentially quantified data constructors now, maybe that will help.
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

On Thu, Nov 3, 2011 at 2:24 PM, aditya siram
I think this is the exact use case that the new ConstraintKinds extension was meant to address (http://hackage.haskell.org/trac/ghc/wiki/Status/Oct11). But we have to wait for 7.4. -deech
I don't think so - we still need some we to tell GHC which class instance to select. But maybe I'm mis-understanding how ConstraintKinds works. Antoine

I could put a header in the file that tells me what the type of the object is. Then I would know at run-time (but not compile-time). Would that help?

On Fri, Nov 4, 2011 at 4:40 AM, Amy de Buitléir
I could put a header in the file that tells me what the type of the object is. Then I would know at run-time (but not compile-time). Would that help?
A really simple and common way to do this would be using a sum-type: data TypeOne = ... data TypeTwo = ... data TypeThree = ... data AllOfTheTypes = T1 TypeOne | T2 TypeTwo | T3 TypeThree instance Binary AllOfTheTypes where put (T1 x) = putWord8 0; put x put (T2 x) = putWord8 1; put x put (T3 x) = putWord8 2; put x get = do tag <- getWord8 case tag of 0 -> T1 <$> get 1 -> T2 <$> get 2 -> T3 <$> get Antoine

Antoine Latter
A really simple and common way to do this would be using a sum-type:
Here's what I'm trying to accomplish. I want to write a daemon that will cycle through the files, load each one in turn, and invoke the doSomething method. I would like to be able to allow people to use my daemon with any assortment of new types that they create, as long as that type implements the doSomething, readThing, and writeThing methods. I could make the sum-type approach work, but then users would have to modify the type. And there might be dozens of different types in use, some provided by me, and some provided by the user, so it would get messy. But I might have to go with that approach.

On Fri, Nov 4, 2011 at 7:51 AM, Amy de Buitléir
Antoine Latter
writes: A really simple and common way to do this would be using a sum-type:
Here's what I'm trying to accomplish. I want to write a daemon that will cycle through the files, load each one in turn, and invoke the doSomething method. I would like to be able to allow people to use my daemon with any assortment of new types that they create, as long as that type implements the doSomething, readThing, and writeThing methods.
I could make the sum-type approach work, but then users would have to modify the type. And there might be dozens of different types in use, some provided by me, and some provided by the user, so it would get messy. But I might have to go with that approach.
An executable, once compiled, cannot really learn about new types without dynamically loading new object code. Which is possible but often tricky. You'd have this problem in other languages, too, except Java and .Net have spent a lot of time working on the dynamic loading of new object code into a running process (but you would still need to get the .class file or .dll into a folder where the executable can read it). Maybe I'm mis-understanding your requirements, though. Antoine

Perhaps this is what you're looking for:
{-# LANGUAGE ExistentialQuantification #-}
import Data.Binary
import Data.ByteString.Lazy as B ( readFile, writeFile )
import Codec.Compression.GZip ( compress, decompress )
data Thing = forall a. (Binary a, Show a, Eq a) => Thing a
instance Binary Thing where
get = get
put (Thing a) = put a
instance Show Thing where
show (Thing a) = show a
readThing :: FilePath -> IO Thing
readThing f = return . decode . decompress =<< B.readFile
f
writeThing :: FilePath -> Thing -> IO ()
writeThing f = B.writeFile f . compress . encode
doSomething :: Thing -> m Thing
doSomething = undefined
main = do
a <- readThing "file1.txt"
a' <- doSomething a
writeThing "file2.txt" a'
It compiles on my machine (GHC 7.2.1) but I haven't tested it. It uses the
existential quantification extension to constrain a datatype to the
typeclasses you mention. The caveat is that the only functions you can run
on "a" or "a'" are those defined by the Eq, Show and Binary typeclasses.
-deech
On Fri, Nov 4, 2011 at 8:26 AM, Antoine Latter
On Fri, Nov 4, 2011 at 7:51 AM, Amy de Buitléir
wrote: Antoine Latter
writes: A really simple and common way to do this would be using a sum-type:
Here's what I'm trying to accomplish. I want to write a daemon that will cycle through the files, load each one in turn, and invoke the doSomething method. I would like to be able to allow people to use my daemon with any assortment of new types that they create, as long as that type implements the doSomething, readThing, and writeThing methods.
I could make the sum-type approach work, but then users would have to modify the type. And there might be dozens of different types in use, some provided by me, and some provided by the user, so it would get messy. But I might have to go with that approach.
An executable, once compiled, cannot really learn about new types without dynamically loading new object code. Which is possible but often tricky.
You'd have this problem in other languages, too, except Java and .Net have spent a lot of time working on the dynamic loading of new object code into a running process (but you would still need to get the .class file or .dll into a folder where the executable can read it).
Maybe I'm mis-understanding your requirements, though.
Antoine
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

On Fri, Nov 04, 2011 at 08:52:36AM -0500, aditya siram wrote:
Perhaps this is what you're looking for: {-# LANGUAGE ExistentialQuantification #-} import Data.Binary import Data.ByteString.Lazy as B ( readFile, writeFile ) import Codec.Compression.GZip ( compress, decompress )
data Thing = forall a. (Binary a, Show a, Eq a) => Thing a
instance Binary Thing where get = get put (Thing a) = put a
instance Show Thing where show (Thing a) = show a
readThing :: FilePath -> IO Thing readThing f = return . decode . decompress =<< B.readFile f
writeThing :: FilePath -> Thing -> IO () writeThing f = B.writeFile f . compress . encode
doSomething :: Thing -> m Thing doSomething = undefined
main = do a <- readThing "file1.txt" a' <- doSomething a writeThing "file2.txt" a'
It compiles on my machine (GHC 7.2.1) but I haven't tested it. It uses the
This will not work. The problem is that once you have a Thing you cannot do anything with it, because you have no information about what type is inside. In other words you cannot implement 'doSomething' to do anything interesting at all. I am actually surprised that 'readThing' type checks -- I am not sure what type it thinks the read thing has, or how it can guarantee that it satisfies the given constraints. I tried adding a Typeable constraint to Thing and using 'cast' to recover the type, but that doesn't really work either. You would really have to do something like changing the Binary instance for Thing so that it also serializes/deserializes a TypeRep along with the value, and then does some sort of unsafe cast after reading. You may want to take a look at how xmonad handles this problem -- it allows arbitrary user-extensible state and layouts, which it needs to serialize and deserialize when restarting itself. -Brent

Sorry for the misinformation. I should've ran the code.
-deech
On Fri, Nov 4, 2011 at 11:22 AM, Brent Yorgey
On Fri, Nov 04, 2011 at 08:52:36AM -0500, aditya siram wrote:
Perhaps this is what you're looking for: {-# LANGUAGE ExistentialQuantification #-} import Data.Binary import Data.ByteString.Lazy as B ( readFile, writeFile ) import Codec.Compression.GZip ( compress, decompress )
data Thing = forall a. (Binary a, Show a, Eq a) => Thing a
instance Binary Thing where get = get put (Thing a) = put a
instance Show Thing where show (Thing a) = show a
readThing :: FilePath -> IO Thing readThing f = return . decode . decompress =<< B.readFile f
writeThing :: FilePath -> Thing -> IO () writeThing f = B.writeFile f . compress . encode
doSomething :: Thing -> m Thing doSomething = undefined
main = do a <- readThing "file1.txt" a' <- doSomething a writeThing "file2.txt" a'
It compiles on my machine (GHC 7.2.1) but I haven't tested it. It uses the
This will not work. The problem is that once you have a Thing you cannot do anything with it, because you have no information about what type is inside. In other words you cannot implement 'doSomething' to do anything interesting at all. I am actually surprised that 'readThing' type checks -- I am not sure what type it thinks the read thing has, or how it can guarantee that it satisfies the given constraints.
I tried adding a Typeable constraint to Thing and using 'cast' to recover the type, but that doesn't really work either. You would really have to do something like changing the Binary instance for Thing so that it also serializes/deserializes a TypeRep along with the value, and then does some sort of unsafe cast after reading.
You may want to take a look at how xmonad handles this problem -- it allows arbitrary user-extensible state and layouts, which it needs to serialize and deserialize when restarting itself.
-Brent
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Antoine Latter
An executable, once compiled, cannot really learn about new types without dynamically loading new object code. Which is possible but often tricky.
I don't mind if the user has to re-compile the code to add in their new types. In addition to the daemon, I'm providing a library of functions that they can use when implementing new types, so they'd have to re-compile anyway.

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.
Apologies for resurrecting an old thread, but I wanted to share the solution I came up with, in case anyone else has a similar scenario. It's not as graceful as I'd like, but it minimises the amount of code that users of my library have to write. -----8<----- {-# LANGUAGE ExistentialQuantification #-} import Data.Binary ( Binary, encode, decode, put, get, Put, Get ) import Data.ByteString.Lazy as B ( readFile, writeFile ) import Codec.Compression.GZip ( compress, decompress ) class (Show a) => Thing a where doSomething :: a -> IO a label :: a -> String data ThingBox = forall a. Thing a => TB a putThing :: ThingBox -> Put putThing a = do put $ label a put $ show a getThing :: Get ThingBox getThing = do s <- get x <- get return $ readThingByLabel s x instance Binary ThingBox where put = putThing get = getThing instance Show ThingBox where show (TB a) = show a -- This trick allows me to treat ThingBoxes just like Things instance Thing ThingBox where doSomething (TB a) = do a' <- doSomething a return $ TB a' label (TB a) = label a readThing :: FilePath -> IO ThingBox readThing f = return . decode . decompress =<< B.readFile f writeThing :: FilePath -> ThingBox -> IO () writeThing f = B.writeFile f . compress . encode main = do let a = TB Thing1 _ <- doSomething a let b = TB Thing2 writeThing "file.txt" b b' <- readThing "file.txt" _ <- doSomething b return () -- Now my users can develop their own things data Thing1 = Thing1 deriving (Show, Read) instance Thing Thing1 where doSomething a = do putStrLn "In Thing1's doSomething" return a label _ = "Thing1" data Thing2 = Thing2 deriving (Show, Read) instance Thing Thing2 where doSomething a = do putStrLn "In Thing2's doSomething" return a label _ = "Thing2" -- And they'll need to write this too readThingByLabel :: String -> String -> ThingBox readThingByLabel "Thing1" x = TB z where z = read x :: Thing1 readThingByLabel "Thing2" x = TB z where z = read x :: Thing2 readThingByLabel s x = error $ "Unrecognised species: " ++ s
participants (5)
-
aditya siram
-
Amy de Buitléir
-
Antoine Latter
-
Brent Yorgey
-
David McBride