Send Beginners mailing list submissions to
        beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
        http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
        beginners-requ...@haskell.org

You can reach the person managing the list at
        beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than "Re: Contents of Beginners digest..."


Today's Topics:

   1. Re:  Haskell wants the type,      but I only know the class.
      (Amy de Buitl?ir)


----------------------------------------------------------------------

Message: 1
Date: Mon, 26 Mar 2012 14:52:32 +0000 (UTC)
From: Amy de Buitl?ir <a...@nualeargais.ie>
Subject: Re: [Haskell-beginners] Haskell wants the type,        but I only
        know the class.
To: beginners@haskell.org
Message-ID: <loom.20120326t164833-...@post.gmane.org>
Content-Type: text/plain; charset=utf-8

Amy de Buitl?ir <amy <at> nualeargais.ie> writes:
> 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





------------------------------

_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners


End of Beginners Digest, Vol 45, Issue 33
*****************************************

Reply via email to