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.
      (Antoine Latter)
   2. Re:  Haskell wants the type,      but I only know the class.
      (Amy de Buitl?ir)
   3. Re:  Haskell wants the type,      but I only know the class.
      (Antoine Latter)
   4. Re:  Haskell wants the type,      but I only know the class.
      (aditya siram)
   5. Re:  Haskell wants the type,      but I only know the class.
      (Antoine Latter)
   6. Re:  Selecting single result of function application to list
      (Hugo Ferreira)
   7. Re:  Haskell wants the type,      but I only know the class.
      (Amy de Buitl?ir)
   8. Re:  Cabal: Upgrading to the latest version of    library
      (Giovanni Tirloni)


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

Message: 1
Date: Thu, 3 Nov 2011 12:48:55 -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:
        <CAKjSnQFiUHV9QsR4-m7Te4=mvej-cxugaskac5a9k+bg+n3...@mail.gmail.com>
Content-Type: text/plain; charset=UTF-8

On Thu, Nov 3, 2011 at 11:55 AM, Amy de Buitl?ir <a...@nualeargais.ie> wrote:
> 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
>



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

Message: 2
Date: Thu, 3 Nov 2011 18:08:14 +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.20111103t185737-...@post.gmane.org>
Content-Type: text/plain; charset=us-ascii

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.





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

Message: 3
Date: Thu, 3 Nov 2011 14:21:36 -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:
        <CAKjSnQECx1Yrqh8-J3AhOUq-=ar_qseeq+ghkmw_uxgsbo+...@mail.gmail.com>
Content-Type: text/plain; charset=UTF-8

On Thu, Nov 3, 2011 at 1:08 PM, Amy de Buitl?ir <a...@nualeargais.ie> wrote:
> 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
>



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

Message: 4
Date: Thu, 3 Nov 2011 14:24:09 -0500
From: aditya siram <aditya.si...@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:
        <cajrreyjmubsny1qg3xfa682dtzuifnaul9smonhhon88ru7...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

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 <a...@nualeargais.ie> wrote:

> 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
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20111103/4b385828/attachment-0001.htm>

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

Message: 5
Date: Thu, 3 Nov 2011 15:33:54 -0500
From: Antoine Latter <aslat...@gmail.com>
Subject: Re: [Haskell-beginners] Haskell wants the type,        but I only
        know the class.
To: aditya siram <aditya.si...@gmail.com>
Cc: Amy de Buitl?ir <a...@nualeargais.ie>,      beginners@haskell.org
Message-ID:
        <cakjsnqe6xvo_ae5hmx30opcgwwnxrzechz9ceaieksrk5qo...@mail.gmail.com>
Content-Type: text/plain; charset=UTF-8

On Thu, Nov 3, 2011 at 2:24 PM, aditya siram <aditya.si...@gmail.com> wrote:
> 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



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

Message: 6
Date: Fri, 04 Nov 2011 08:05:30 +0000
From: Hugo Ferreira <h...@inescporto.pt>
Subject: Re: [Haskell-beginners] Selecting single result of function
        application to list
To: Markus L?ll <markus.l...@gmail.com>
Cc: beginners@haskell.org, Daniel Fischer
        <daniel.is.fisc...@googlemail.com>
Message-ID: <4eb39cca.5000...@inescporto.pt>
Content-Type: text/plain; charset=ISO-8859-1; format=flowed

Thanks to Daniel Fischer, Daniel Schoepe and
Markus Lall for the answers.

Will have to look this over more carefully.

Rgds,
Hugo F.


On 11/03/2011 05:27 PM, Markus L?ll wrote:
> There's also newtype First wraping a Maybe in Data.Monoid, in which
> you can wrap your Maybes, mconcat them and get the first Just value.
> Like:
>
>> mconcat $ map First [Nothing, Just "first", Nohing, Just "last", Nothing]
> First {getFirst = Just "first"}
>
>
> On Thu, Nov 3, 2011 at 6:07 PM, Hugo Ferreira<h...@inescporto.pt>  wrote:
>> Hello,
>>
>> Apologies the simpleton question but I would like to
>> know how it is done in Haskell. I have a list of values,
>> and I am applying a function to each of these elements.
>> The result is a Maybe. I would like to return the first
>> occurrence which is not a Nothing.
>>
>> I am considering something like:
>>
>> selectOne f = take 1 . filter (\e ->  case e of
>>                                        Just _ ->  True
>>                                        _ ->  False ) . map f
>>
>> I this how it is done?
>>
>> TIA,
>> Hugo F.
>>
>>
>>
>> _______________________________________________
>> Beginners mailing list
>> Beginners@haskell.org
>> http://www.haskell.org/mailman/listinfo/beginners
>>
>
>
>




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

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

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?




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

Message: 8
Date: Fri, 4 Nov 2011 08:30:56 -0200
From: Giovanni Tirloni <gtirl...@sysdroid.com>
Subject: Re: [Haskell-beginners] Cabal: Upgrading to the latest
        version of      library
To: Rustom Mody <rustompm...@gmail.com>
Cc: beginners@haskell.org
Message-ID:
        <caj9aok9l-zsltgdusoic-8smdsptpq57qmay07v3do6wtsd...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

On Wed, Nov 2, 2011 at 1:05 AM, Rustom Mody <rustompm...@gmail.com> wrote:

>
>
> On Wed, Nov 2, 2011 at 1:31 AM, Giovanni Tirloni <gtirl...@sysdroid.com>wrote:
>
>> On Tue, Nov 1, 2011 at 2:04 PM, Hugo Ferreira <h...@inescporto.pt> wrote:
>>>
>>> I have used Ocaml + the GODI "package manager" and it seems work ok.
>>> GODI allows one to identify newer packages, select those we want to
>>> upgrade and recompiles any dependencies automatically.
>>>
>>>
>> As a newcommer, I feel that this subject has already been discussed at
>> length by the Haskell community and progress is being made.
>>
>> Two articles that I have been referred to in order to understand it
>> better:
>>
>> http://www.vex.net/~trebla/haskell/sicp.xhtml#unsafeInterleave
>>
>> http://ivanmiljenovic.wordpress.com/2010/03/15/repeat-after-me-cabal-is-not-a-package-manager/
>>
>>
> Thanks for those links.
>
>
>>  As a Fedora user, I'm relying on the Haskell SIG work and using the
>> ghc-* RPM packages. When a given Hackage package has not been packaged in
>> Fedora yet, I'm using cabal to supplement but I think that's sub-optimal
>> (from a sysadmin perspective). I'm looking at ways to actually build my own
>> RPMs following their standards. As it's mentioned in one of the article,
>> someone has had the trouble to figure out which packages work best together.
>>
>
> 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>

-- 
Giovanni
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20111104/bcd87563/attachment.htm>

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

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


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

Reply via email to