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.  fonction in a typeclass that does not mention    the type
      variable (TP)
   2. Re:  cabal package haskore-vintage fails to build (Brent Yorgey)
   3. Re:  fonction in a typeclass that does not mention the type
      variable (Peter Hall)
   4. Re:  fonction in a typeclass that does not        mention the type
      variable (Peter Jones)
   5. Re:  fonction in a typeclass that does not        mention the type
      variable (Peter Jones)
   6. Re:  fonction in a typeclass that does not        mention the type
      variable (TP)
   7. Re:  fonction in a typeclass that does not        mention the type
      variable (TP)


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

Message: 1
Date: Wed, 21 Aug 2013 18:39:33 +0200
From: TP <paratribulati...@free.fr>
To: beginners@haskell.org
Subject: [Haskell-beginners] fonction in a typeclass that does not
        mention the type variable
Message-ID: <537fea-mm5.ln1@rama.universe>
Content-Type: text/plain; charset="ISO-8859-1"

Hi,

I have a simple test case containing a typeclass Foo with one type variable 
a. The goal is to write once and for all a function symbolToInfixLevel 
function that combines two other functions defined in the typeclass:

-----------------------
class Foo a where
    
    symbolToConstructor :: String -> ( a -> a -> a )
    infixLevel :: a -> Int

    symbolToInfixLevel :: String -> Int
    symbolToInfixLevel s = infixLevel $ (symbolToConstructor s) undefined 
undefined
-----------------------

This yields an error because there is no "a" in the type signature for 
symbolToInfixLevel:

$ runghc test_typeclass_without_typevariable.hs 
test_typeclass_without_typevariable.hs:1:1:
    The class method `symbolToInfixLevel'
    mentions none of the type variables of the class Foo a
    When checking the class method: symbolToInfixLevel :: String -> Int
    In the class declaration for `Foo'

Now, if I define symbolToInfixLevel out of the typeclass:

-----------------------
class Foo a where
    
    symbolToConstructor :: String -> ( a -> a -> a )
    infixLevel :: a -> Int

symbolToInfixLevel :: String -> Int
symbolToInfixLevel s = infixLevel $ (symbolToConstructor s) undefined 
undefined
-----------------------

Now, I obtain:

$ runghc test_typeclass_without_typevariable.hs 
test_typeclass_without_typevariable.hs:7:24:
    No instance for (Foo a0) arising from a use of `infixLevel'
    In the expression: infixLevel
    In the expression:
      infixLevel $ (symbolToConstructor s) undefined undefined
    In an equation for `symbolToInfixLevel':
        symbolToInfixLevel s
          = infixLevel $ (symbolToConstructor s) undefined undefined

How to get rid from this situation?

Thanks in advance,

TP




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

Message: 2
Date: Wed, 21 Aug 2013 13:01:01 -0400
From: Brent Yorgey <byor...@seas.upenn.edu>
To: beginners@haskell.org
Subject: Re: [Haskell-beginners] cabal package haskore-vintage fails
        to build
Message-ID: <20130821170101.ga8...@seas.upenn.edu>
Content-Type: text/plain; charset=iso-8859-1

It also uses the cached version of the tar file which is already on
your disk, if you have previously installed the package, so it does
not even need to download anything.

-Brent

On Wed, Aug 21, 2013 at 01:00:12PM +0200, Sylvain HENRY wrote:
> 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 ?
> >
> >
> 
> 
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
> 



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

Message: 3
Date: Wed, 21 Aug 2013 18:05:42 +0100
From: Peter Hall <peter.h...@memorphic.com>
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Subject: Re: [Haskell-beginners] fonction in a typeclass that does not
        mention the type variable
Message-ID:
        <CAA6hAk495VcVq2oSMfs6LhN4ARoSMAF=nokcnpnmkp28kgs...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

Maybe I don't fully understand what you are trying to achieve, but I don't
think what you are trying to do makes sense. infixLevel and
symbolToConstructor will have different implementations for each instance
of Foo, and the compiler cannot possibly know which implementations you
mean. If the implementation of symbolToInfixLevel is independent of the
implementations of infixLevel and symbolToConstructor then it shouldn't
need them in its definition.

Peter



On 21 August 2013 17:39, TP <paratribulati...@free.fr> wrote:

> Hi,
>
> I have a simple test case containing a typeclass Foo with one type variable
> a. The goal is to write once and for all a function symbolToInfixLevel
> function that combines two other functions defined in the typeclass:
>
> -----------------------
> class Foo a where
>
>     symbolToConstructor :: String -> ( a -> a -> a )
>     infixLevel :: a -> Int
>
>     symbolToInfixLevel :: String -> Int
>     symbolToInfixLevel s = infixLevel $ (symbolToConstructor s) undefined
> undefined
> -----------------------
>
> This yields an error because there is no "a" in the type signature for
> symbolToInfixLevel:
>
> $ runghc test_typeclass_without_typevariable.hs
> test_typeclass_without_typevariable.hs:1:1:
>     The class method `symbolToInfixLevel'
>     mentions none of the type variables of the class Foo a
>     When checking the class method: symbolToInfixLevel :: String -> Int
>     In the class declaration for `Foo'
>
> Now, if I define symbolToInfixLevel out of the typeclass:
>
> -----------------------
> class Foo a where
>
>     symbolToConstructor :: String -> ( a -> a -> a )
>     infixLevel :: a -> Int
>
> symbolToInfixLevel :: String -> Int
> symbolToInfixLevel s = infixLevel $ (symbolToConstructor s) undefined
> undefined
> -----------------------
>
> Now, I obtain:
>
> $ runghc test_typeclass_without_typevariable.hs
> test_typeclass_without_typevariable.hs:7:24:
>     No instance for (Foo a0) arising from a use of `infixLevel'
>     In the expression: infixLevel
>     In the expression:
>       infixLevel $ (symbolToConstructor s) undefined undefined
>     In an equation for `symbolToInfixLevel':
>         symbolToInfixLevel s
>           = infixLevel $ (symbolToConstructor s) undefined undefined
>
> How to get rid from this situation?
>
> Thanks in advance,
>
> TP
>
>
> _______________________________________________
> 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/2c4fbc2e/attachment-0001.html>

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

Message: 4
Date: Wed, 21 Aug 2013 11:20:30 -0600
From: Peter Jones <mli...@pmade.com>
To: beginners@haskell.org
Subject: Re: [Haskell-beginners] fonction in a typeclass that does not
        mention the type variable
Message-ID: <87y57vdkpt....@pmade.com>
Content-Type: text/plain

TP <paratribulati...@free.fr> writes:
> symbolToInfixLevel :: String -> Int
> symbolToInfixLevel s = infixLevel $ (symbolToConstructor s) undefined 
>
> Now, I obtain:
>
> $ runghc test_typeclass_without_typevariable.hs 
> test_typeclass_without_typevariable.hs:7:24:
>     No instance for (Foo a0) arising from a use of `infixLevel'
>     In the expression: infixLevel
>     In the expression:
>       infixLevel $ (symbolToConstructor s) undefined undefined
>     In an equation for `symbolToInfixLevel':
>         symbolToInfixLevel s
>           = infixLevel $ (symbolToConstructor s) undefined undefined
>
> How to get rid from this situation?

Your `symbolToConstructor' function is too specific for both cases you
describe.  You'd need to change the `String' argument to `a' and put it
back in the type class or write it like this:

symbolToInfixLevel :: (Foo a) => a -> Int
symbolToInfixLevel s = infixLevel $ (symbolToConstructor s) undefined 

-- 
Peter Jones, Founder, Devalot.com
Defending the honor of good code




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

Message: 5
Date: Wed, 21 Aug 2013 11:37:23 -0600
From: Peter Jones <mli...@pmade.com>
To: beginners@haskell.org
Subject: Re: [Haskell-beginners] fonction in a typeclass that does not
        mention the type variable
Message-ID: <87siy3djxo....@pmade.com>
Content-Type: text/plain

Peter Jones <mli...@pmade.com> writes:
> Your `symbolToConstructor' function is too specific for both cases you
> describe.  You'd need to change the `String' argument to `a' and put it
> back in the type class or write it like this:
>
> symbolToInfixLevel :: (Foo a) => a -> Int
> symbolToInfixLevel s = infixLevel $ (symbolToConstructor s) undefined 

Actually, the problem is with your `symbolToConstructor' function.  It
needs to look like this:

symbolToConstructor :: (Foo a) => String -> a

Then symbolToInfixLevel can be:

symbolToInfixLevel :: String -> Int

-- 
Peter Jones, Founder, Devalot.com
Defending the honor of good code




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

Message: 6
Date: Wed, 21 Aug 2013 21:44:43 +0200
From: TP <paratribulati...@free.fr>
To: beginners@haskell.org
Subject: Re: [Haskell-beginners] fonction in a typeclass that does not
        mention the type variable
Message-ID: <buhfea-vh9.ln1@rama.universe>
Content-Type: text/plain; charset="ISO-8859-1"

Peter Hall wrote:

> Maybe I don't fully understand what you are trying to achieve, but I don't
> think what you are trying to do makes sense. infixLevel and
> symbolToConstructor will have different implementations for each instance
> of Foo, and the compiler cannot possibly know which implementations you
> mean.

Indeed, my question was stupid. This is obvious in the second implementation 
(which instance to choose?), and it is also true in the first one because 
even if symbolToInfixLevel of one considered instance uses infixLevel and 
symbolToConstructor of this same instance (what I am not sure of), at the 
location where I use this function the compiler cannot known which instance 
I mean.

> If the implementation of symbolToInfixLevel is independent of the
> implementations of infixLevel and symbolToConstructor then it shouldn't
> need them in its definition.

No, they are not independent: it is really a function that "composes" 
functions infixLevel and symbolToConstructor. See my proposition in my 
answer to Peter Jones.





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

Message: 7
Date: Wed, 21 Aug 2013 21:43:33 +0200
From: TP <paratribulati...@free.fr>
To: beginners@haskell.org
Subject: Re: [Haskell-beginners] fonction in a typeclass that does not
        mention the type variable
Message-ID: <5shfea-vh9.ln1@rama.universe>
Content-Type: text/plain; charset="ISO-8859-1"

Peter Jones wrote:

> Actually, the problem is with your `symbolToConstructor' function.  It
> needs to look like this:
> 
> symbolToConstructor :: (Foo a) => String -> a
> 
> Then symbolToInfixLevel can be:
> 
> symbolToInfixLevel :: String -> Int
> 

Sorry, I have not been able to write an example with your proposition. Might 
you give more informations?

In the meantime, I have been able to write a working example proposing two 
variants:

------------------------------
{-# LANGUAGE ScopedTypeVariables #-}

data Exp = Plus Exp Exp | Minus Exp Exp | Atom String
    deriving Show

class Foo a where

    symbolToConstructor :: String -> ( a -> a -> a )
    infixLevel :: a -> Int

    -- The second argument is only used to indicate the type of the
    -- intermediary result (i.e. the type of the result of
    -- symbolToConstructor).
    symbolToInfixLevel :: String -> a -> Int
    symbolToInfixLevel s u =
        infixLevel $ (((symbolToConstructor s) undefined undefined)::a)


instance Foo Exp where

    symbolToConstructor e = case e of
                "+" -> Plus
                "-" -> Minus
    infixLevel e = case e of
        Plus _ _ -> 6
        Minus _ _ -> 7

main = do

-- First variant
print $ infixLevel $ (((symbolToConstructor "+") undefined undefined)::Exp)
print $ infixLevel $ (((symbolToConstructor "-") undefined undefined)::Exp)
-- Second variant
print $ symbolToInfixLevel "+" (undefined::Exp)
print $ symbolToInfixLevel "-" (undefined::Exp)
------------------------------




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

Subject: Digest Footer

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


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

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

Reply via email to