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:  multi-parameter typeclass with default       implementation
      (Twan van Laarhoven)
   2.  cabal package haskore-vintage fails to build (Dimitri Hendriks)
   3. Re:  multi-parameter typeclass with default       implementation (TP)
   4. Re:  cabal package haskore-vintage fails to build (Stephen Tetley)
   5. Re:  cabal package haskore-vintage fails to build (Sylvain HENRY)
   6. Re:  cabal package haskore-vintage fails to build
      (Dimitri Hendriks)
   7. Re:  cabal package haskore-vintage fails to build (Sylvain HENRY)


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

Message: 1
Date: Tue, 20 Aug 2013 14:20:24 +0200
From: Twan van Laarhoven <twa...@gmail.com>
To: beginners@haskell.org
Subject: Re: [Haskell-beginners] multi-parameter typeclass with
        default implementation
Message-ID: <52135f08.9040...@gmail.com>
Content-Type: text/plain; charset=UTF-8; format=flowed

On 20/08/13 12:13, TP wrote:
> {-# LANGUAGE MultiParamTypeClasses #-}
>
> class Bar a where
>      bar :: a -> Int
>
> class FooBar a b where
>      foobar :: Bar a => a -> b -> Int
>      foobar avalue bvalue = bar avalue
>
> instance Bar Int where
>      bar i = 5
> instance FooBar Int Int
>
> main = do
>      print $ bar (4::Int)
>      print $ foobar (5::Int) (2::Int)

It might be better to make Bar a superclass of FooBar,

     class Bar a => FooBar a b where
       foobar :: a -> b -> Int
       foobar a b = bar a

Then the compiler knows that every instance of FooBar also requires an instance 
of Bar.


Twan



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

Message: 2
Date: Tue, 20 Aug 2013 21:02:17 +0200
From: Dimitri Hendriks <d...@xs4all.nl>
To: beginners@haskell.org
Subject: [Haskell-beginners] cabal package haskore-vintage fails to
        build
Message-ID: <1c957484-db86-43b2-8927-a012d4480...@xs4all.nl>
Content-Type: text/plain; charset=us-ascii

Hi all,

I'm new to this list, and know very little about haskell.
I am trying to install the package haskore-vintage 
on mac osx version 10.6.8, using cabal, but this fails;
see the log below.

I have ghc version 7.6.3, and cabal-install version 1.16.0.2.

------------------------------------------------------------------------------
$ cabal install haskore-vintage

Resolving dependencies...
Configuring haskore-vintage-0.1...
Building haskore-vintage-0.1...
Preprocessing library haskore-vintage-0.1...
[ 1 of 16] Compiling Haskore.Monads   ( src/Haskore/Monads.hs, 
dist/build/Haskore/Monads.o )
[ 2 of 16] Compiling Haskore.Utils    ( src/Haskore/Utils.hs, 
dist/build/Haskore/Utils.o )

src/Haskore/Utils.hs:87:23: Not in scope: `catch'

src/Haskore/Utils.hs:93:23: Not in scope: `catch'
Failed to install haskore-vintage-0.1
cabal: Error: some packages failed to install:
haskore-vintage-0.1 failed during the building phase. The exception was:
ExitFailure 1
$
------------------------------------------------------------------------------

Does anyone know how to resolve this?

Related problems I found:
https://code.google.com/p/leksah/issues/detail?id=272
(no solution given).

And here: https://github.com/haskell/cabal/issues/1137
it appears they think it is a combination of Cabal 1.10 / cabal-install 0.10 
and GHC 7.6 the causes the problem with "catch", but I use cabal 1.16.

Many thanks in advance,
Dimitri




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

Message: 3
Date: Tue, 20 Aug 2013 22:12:19 +0200
From: TP <paratribulati...@free.fr>
To: beginners@haskell.org
Subject: Re: [Haskell-beginners] multi-parameter typeclass with
        default implementation
Message-ID: <36vcea-pt.ln1@rama.universe>
Content-Type: text/plain; charset="ISO-8859-1"

Ben Gamari wrote:

>     {-# LANGUAGE MultiParamTypeClasses, DefaultSignatures #-}

In fact, we could try a solution using a simple parameter typeclass 
containing an implicit existential type b (I hope I am right):

-------------------------
class Foo a where

    bar :: a -> Int

    foobar :: Foo b => a -> b -> Int
    foobar avalue bvalue = bar avalue

instance Foo Int where
    bar i = 5
    foobar avalue bvalue = (bar avalue) + (bar bvalue)

main = do

print $ bar (4::Int)
print $ foobar (5::Int) (3::Int)
-------------------------

It works correctly:

$ runghc test_one_simple_parameter_typeclass.hs
5
10

But if we try to call a function external to the typeclass:

-------------------------
toto :: Int -> Int
toto i = 4

class Foo a where

    bar :: a -> Int

    foobar :: Foo b => a -> b -> Int
    foobar avalue bvalue = bar avalue

instance Foo Int where
    bar i = 5
    foobar avalue bvalue = (bar avalue)
                            + (bar bvalue)
                            + (toto bvalue)

main = do

print $ bar (4::Int)
print $ foobar (5::Int) (3::Int)
-------------------------

We get an error message (see below) meaning that when we call "toto" with 
"bvalue", there is not guarantee that "bvalue" is an "Int". So, in this 
situation, *are we compelled to use multiparameter typeclasses*?


PS: the error message yielded by the second example above:
$ runghc test_one_simple_parameter_typeclass_limitation.hs
test_one_simple_parameter_typeclass_limitation.hs:15:37:
    Could not deduce (b ~ Int)
    from the context (Foo b)
      bound by the type signature for foobar :: Foo b => Int -> b -> Int
      at test_one_simple_parameter_typeclass_limitation.hs:(13,5)-(15,43)
      `b' is a rigid type variable bound by
          the type signature for foobar :: Foo b => Int -> b -> Int
          at test_one_simple_parameter_typeclass_limitation.hs:13:5
    In the first argument of `toto', namely `bvalue'
    In the second argument of `(+)', namely `(toto bvalue)'
    In the expression: (bar avalue) + (bar bvalue) + (toto bvalue)




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

Message: 4
Date: Tue, 20 Aug 2013 22:55:23 +0100
From: Stephen Tetley <stephen.tet...@gmail.com>
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Subject: Re: [Haskell-beginners] cabal package haskore-vintage fails
        to build
Message-ID:
        <cab2tprbxujjhzctppp3+dxdt36ch9ofru7shi1f1vsh1u4u...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

Hi Dimitri

You should be able to get it to work by downloading the archive, gunzip and
untarring the source and changing Utils.hs to include this line after the
line "import Control.Monad":

import Control.Exception hiding  ( assert )


After that build with these commands from the top of the source tree:

runhaskell Setup.hs configure
runhaskell Setup.hs build
runhaskell Setup.hs install

The original problem is that `catch` is no longer export by Prelude in GHC
7.6
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20130820/15593e53/attachment-0001.html>

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

Message: 5
Date: Wed, 21 Aug 2013 09:49:52 +0200
From: Sylvain HENRY <hsy...@gmail.com>
To: beginners@haskell.org
Subject: Re: [Haskell-beginners] cabal package haskore-vintage fails
        to build
Message-ID: <52147120.9000...@gmail.com>
Content-Type: text/plain; charset="iso-8859-1"; Format="flowed"

Hi,

It is better to use "cabal unpack" to download and unpack the source.

Cheers
Sylvain

Le 20/08/2013 23:55, Stephen Tetley a ?crit :
> Hi Dimitri
>
> You should be able to get it to work by downloading the archive, 
> gunzip and untarring the source and changing Utils.hs to include this 
> line after the line "import Control.Monad":
>
> import Control.Exception hiding  ( assert )
>
>
> After that build with these commands from the top of the source tree:
>
> runhaskell Setup.hs configure
> runhaskell Setup.hs build
> runhaskell Setup.hs install
>
> The original problem is that `catch` is no longer export by Prelude in 
> GHC 7.6
>
>
>
>
>
>
> _______________________________________________
> 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/20130821/9a44c50b/attachment-0001.html>

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

Message: 6
Date: Wed, 21 Aug 2013 09:58:29 +0200
From: Dimitri Hendriks <d...@xs4all.nl>
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Subject: Re: [Haskell-beginners] cabal package haskore-vintage fails
        to build
Message-ID: <899939ef-27c7-4ac7-b953-8ba8ea966...@xs4all.nl>
Content-Type: text/plain; charset=us-ascii

Many thanks Stephen, works like a charm!

Finally, I can start composing music, can't wait!

@Sylvain: why is  cabal unpack better than  tar zxvf ?

Greetings,
Dimitri


On Aug 20, 2013, at 23:55 , Stephen Tetley wrote:

> Hi Dimitri
> 
> You should be able to get it to work by downloading the archive, gunzip and 
> untarring the source and changing Utils.hs to include this line after the 
> line "import Control.Monad":
> 
> import Control.Exception hiding  ( assert )
> 
> 
> After that build with these commands from the top of the source tree:
> 
> runhaskell Setup.hs configure
> runhaskell Setup.hs build 
> runhaskell Setup.hs install
> 
> The original problem is that `catch` is no longer export by Prelude in GHC 7.6
> 
> 
> 
> 
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners




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

Message: 7
Date: Wed, 21 Aug 2013 13:00:12 +0200
From: Sylvain HENRY <hsy...@gmail.com>
To: beginners@haskell.org
Subject: Re: [Haskell-beginners] cabal package haskore-vintage fails
        to build
Message-ID: <52149dbc.5030...@gmail.com>
Content-Type: text/plain; charset=ISO-8859-1; format=flowed

It may be a bit quicker as it downloads and unpacks the package 
automatically.

 > cabal unpack haskore-vintage
 > cd haskore-vintage-0.1
 > vim src/Haskore/Utils.hs
 > cabal install

Le 21/08/2013 09:58, Dimitri Hendriks a ?crit :
> @Sylvain: why is  cabal unpack better than  tar zxvf ?
>
>




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

Subject: Digest Footer

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


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

End of Beginners Digest, Vol 62, Issue 21
*****************************************

Reply via email to