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:  Cabal: Upgrading to the latest version of    library
      (Yucheng Zhang)
   2. Re:  Haskell wants the type,      but I only know the class.
      (Antoine Latter)
   3. Re:  Haskell wants the type,      but I only know the class.
      (Amy de Buitl?ir)
   4. Re:  Haskell wants the type,      but I only know the class.
      (Antoine Latter)
   5. Re:  Haskell wants the type,      but I only know the class.
      (aditya siram)
   6. Re:  Haskell wants the type,      but I only know the class.
      (Amy de Buitl?ir)
   7. Re:  Haskell wants the type,      but I only know the class.
      (Amy de Buitl?ir)
   8. Re:  Haskell wants the type, but I only know the class.
      (Brent Yorgey)


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

Message: 1
Date: Fri, 4 Nov 2011 19:13:24 +0800
From: Yucheng Zhang <yczhan...@gmail.com>
Subject: Re: [Haskell-beginners] Cabal: Upgrading to the latest
        version of      library
To: beginners@haskell.org
Message-ID:
        <CANgDTog2=Hk3M1bkE4nPbCN-rGKVsV5GGGb-=fyjrntgdws...@mail.gmail.com>
Content-Type: text/plain; charset=UTF-8

On Fri, Nov 4, 2011 at 6:30 PM, Giovanni Tirloni <gtirl...@sysdroid.com> wrote:
> On Wed, Nov 2, 2011 at 1:05 AM, Rustom Mody <rustompm...@gmail.com> wrote:
>>
>> I wonder if you could throw some light on this?
>> Say you just have to use the 'sub-optimal' solution and cabal install some
>> package foo.
>> Later it appears in the rpm list and you can yum install it.
>> How do you now cabal uninstall foo?
>
> I don't know if this is the "right way" but it seems to work:
> ghc-pkg unregister <package>
> rm ?the contents from $HOME/.cabal/package/hackage.haskell.org/<package>

Maybe 'cab' on Hackage is the right thing to try.

--
Yucheng Zhang



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

Message: 2
Date: Fri, 4 Nov 2011 07:06:43 -0500
From: Antoine Latter <aslat...@gmail.com>
Subject: Re: [Haskell-beginners] Haskell wants the type,        but I only
        know the class.
To: Amy de Buitl?ir <a...@nualeargais.ie>
Cc: beginners@haskell.org
Message-ID:
        <CAKjSnQG4Hf1EMdCF=x7hsvkcn-dnwxyia5uutnt3ndzm94e...@mail.gmail.com>
Content-Type: text/plain; charset=UTF-8

On Fri, Nov 4, 2011 at 4:40 AM, Amy de Buitl?ir <a...@nualeargais.ie> wrote:
> 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



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

Message: 3
Date: Fri, 4 Nov 2011 12:51:23 +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.20111104t132648-...@post.gmane.org>
Content-Type: text/plain; charset=us-ascii

Antoine Latter <aslatter <at> gmail.com> 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.





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

Message: 4
Date: Fri, 4 Nov 2011 08:26:08 -0500
From: Antoine Latter <aslat...@gmail.com>
Subject: Re: [Haskell-beginners] Haskell wants the type,        but I only
        know the class.
To: Amy de Buitl?ir <a...@nualeargais.ie>
Cc: beginners@haskell.org
Message-ID:
        <cakjsnqgix-emad9o7xlxpewwpiynf6cyr01tdpapi2zjs5e...@mail.gmail.com>
Content-Type: text/plain; charset=UTF-8

On Fri, Nov 4, 2011 at 7:51 AM, Amy de Buitl?ir <a...@nualeargais.ie> wrote:
> Antoine Latter <aslatter <at> gmail.com> 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



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

Message: 5
Date: Fri, 4 Nov 2011 08:52:36 -0500
From: aditya siram <aditya.si...@gmail.com>
Subject: Re: [Haskell-beginners] Haskell wants the type,        but I only
        know the class.
To: Antoine Latter <aslat...@gmail.com>
Cc: Amy de Buitl?ir <a...@nualeargais.ie>,      beginners@haskell.org
Message-ID:
        <CAJrReyirWkF7K4=1gvttnipocgahljgmduggwfuxz2pwo1w...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

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 <aslat...@gmail.com> wrote:

> On Fri, Nov 4, 2011 at 7:51 AM, Amy de Buitl?ir <a...@nualeargais.ie>
> wrote:
> > Antoine Latter <aslatter <at> gmail.com> 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
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20111104/9fe21d62/attachment-0001.htm>

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

Message: 6
Date: Fri, 4 Nov 2011 13:56:12 +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.20111104t144942-...@post.gmane.org>
Content-Type: text/plain; charset=us-ascii

Antoine Latter <aslatter <at> gmail.com> writes:
> 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.




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

Message: 7
Date: Fri, 4 Nov 2011 13:58:35 +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.20111104t145648-...@post.gmane.org>
Content-Type: text/plain; charset=us-ascii

aditya siram <aditya.siram <at> gmail.com> writes:

> Perhaps this is what you're looking for:

Thank you! I think that's what I'm looking for.





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

Message: 8
Date: Fri, 4 Nov 2011 12:22:23 -0400
From: Brent Yorgey <byor...@seas.upenn.edu>
Subject: Re: [Haskell-beginners] Haskell wants the type, but I only
        know the class.
To: beginners@haskell.org
Message-ID: <20111104162223.ga11...@seas.upenn.edu>
Content-Type: text/plain; charset=us-ascii

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


End of Beginners Digest, Vol 41, Issue 5
****************************************

Reply via email to