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.  class and instance question (Walck, Scott)
   2. Re:  class and instance question (Lyndon Maydwell)
   3. Re:  class and instance question (Brent Yorgey)


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

Message: 1
Date: Thu, 20 May 2010 06:35:34 -0400
From: "Walck, Scott" <wa...@lvc.edu>
Subject: [Haskell-beginners] class and instance question
To: "beginners@haskell.org" <beginners@haskell.org>
Message-ID: <e6c639c7e135d846b5127945421a789f244bd7b...@lvc02.lvc.edu>
Content-Type: text/plain; charset="us-ascii"

Hi folks,

I'm trying to make doubles and triples act like vectors, as in

(3,4) <+> (7,8) ==> (10,12)
(3,2,1) <+> (9,8,7) ==> (12,10,8)
6 *> (1,2,3) ==> (6,12,18)

I thought I should make a type class so that I could use <+> for both double 
addition and triple addition,
and *> for both double and triple scalar multiplication.  (Some of this 
functionality is provided by
NumericPrelude, but I didn't need all of that, and I hoped this would be simple 
to write.)
The code below gives the error

NewVectorShort.hs:19:0:
    Type synonym `Vector2D' should have 1 argument, but has been given 0
    In the instance declaration for `BasicVector Vector2D'
Failed, modules loaded: none.

I don't understand how what I'm trying to do is different from, say, the Monad 
instance for Maybe.
(Maybe a) is a type, and (Vector2D a) is a type.

Thanks,

Scott



{-# LANGUAGE TypeSynonymInstances #-}

infixl 6 <+>
infixl 6 <->
infixl 7 *>
infixl 7 <*

class BasicVector v where
    (<+>) :: v a -> v a -> v a
    (<->) :: v a -> v a -> v a
    (*>)  :: Num a => a -> v a -> v a
    (<*)  :: Num a => v a -> a -> v a
    v1 <-> v2 = v1 <+> fromInteger (-1) *> v2
    v1 <* c = c *> v1
    c *> v1 = v1 <* c

type Vector2D a = (a,a)

instance BasicVector Vector2D where
    (ax,ay) <+> (bx,by) = (ax+bx,ay+by)
    c *> (ax,ay) = (c*ax,c*ay)







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

Message: 2
Date: Thu, 20 May 2010 18:49:22 +0800
From: Lyndon Maydwell <maydw...@gmail.com>
Subject: Re: [Haskell-beginners] class and instance question
To: "Walck, Scott" <wa...@lvc.edu>
Cc: "beginners@haskell.org" <beginners@haskell.org>
Message-ID:
        <aanlktim-bfpluu72bv4tvtkhqiq3yqgflmoln5rfe...@mail.gmail.com>
Content-Type: text/plain; charset=UTF-8

It looks like you've given the Vector2D type an argument, but not used
one for the BasicVector instance.

On Thu, May 20, 2010 at 6:35 PM, Walck, Scott <wa...@lvc.edu> wrote:
> Hi folks,
>
> I'm trying to make doubles and triples act like vectors, as in
>
> (3,4) <+> (7,8) ==> (10,12)
> (3,2,1) <+> (9,8,7) ==> (12,10,8)
> 6 *> (1,2,3) ==> (6,12,18)
>
> I thought I should make a type class so that I could use <+> for both double 
> addition and triple addition,
> and *> for both double and triple scalar multiplication.  (Some of this 
> functionality is provided by
> NumericPrelude, but I didn't need all of that, and I hoped this would be 
> simple to write.)
> The code below gives the error
>
> NewVectorShort.hs:19:0:
>    Type synonym `Vector2D' should have 1 argument, but has been given 0
>    In the instance declaration for `BasicVector Vector2D'
> Failed, modules loaded: none.
>
> I don't understand how what I'm trying to do is different from, say, the 
> Monad instance for Maybe.
> (Maybe a) is a type, and (Vector2D a) is a type.
>
> Thanks,
>
> Scott
>
>
>
> {-# LANGUAGE TypeSynonymInstances #-}
>
> infixl 6 <+>
> infixl 6 <->
> infixl 7 *>
> infixl 7 <*
>
> class BasicVector v where
>    (<+>) :: v a -> v a -> v a
>    (<->) :: v a -> v a -> v a
>    (*>)  :: Num a => a -> v a -> v a
>    (<*)  :: Num a => v a -> a -> v a
>    v1 <-> v2 = v1 <+> fromInteger (-1) *> v2
>    v1 <* c = c *> v1
>    c *> v1 = v1 <* c
>
> type Vector2D a = (a,a)
>
> instance BasicVector Vector2D where
>    (ax,ay) <+> (bx,by) = (ax+bx,ay+by)
>    c *> (ax,ay) = (c*ax,c*ay)
>
>
>
>
>
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>


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

Message: 3
Date: Thu, 20 May 2010 11:30:33 -0400
From: Brent Yorgey <byor...@seas.upenn.edu>
Subject: Re: [Haskell-beginners] class and instance question
To: beginners@haskell.org
Message-ID: <20100520153033.ga6...@seas.upenn.edu>
Content-Type: text/plain; charset=us-ascii

On Thu, May 20, 2010 at 06:35:34AM -0400, Walck, Scott wrote:
> Hi folks,
> 
> 
> NewVectorShort.hs:19:0:
>     Type synonym `Vector2D' should have 1 argument, but has been given 0
>     In the instance declaration for `BasicVector Vector2D'
> Failed, modules loaded: none.

The problem is simply that type synonyms must always be fully applied, so given

  type Vector2D a = (a,a)

you cannot declare an instance for Vector2D, since Vector2D is not
applied to an argument.  The solution is to make Vector2D a newtype:

  newtype Vector2D a = V2D (a,a)

Of course, this means you'll need to wrap and unwrap V2D constructors
in various places, which can be a bit annoying, but such is the price
of progress.

For another take on encoding vector stuff in Haskell, see the
vector-space package on Hackage.

-Brent

> 
> I don't understand how what I'm trying to do is different from, say, the 
> Monad instance for Maybe.
> (Maybe a) is a type, and (Vector2D a) is a type.
> 
> Thanks,
> 
> Scott
> 
> 
> 
> {-# LANGUAGE TypeSynonymInstances #-}
> 
> infixl 6 <+>
> infixl 6 <->
> infixl 7 *>
> infixl 7 <*
> 
> class BasicVector v where
>     (<+>) :: v a -> v a -> v a
>     (<->) :: v a -> v a -> v a
>     (*>)  :: Num a => a -> v a -> v a
>     (<*)  :: Num a => v a -> a -> v a
>     v1 <-> v2 = v1 <+> fromInteger (-1) *> v2
>     v1 <* c = c *> v1
>     c *> v1 = v1 <* c
> 
> type Vector2D a = (a,a)
> 
> instance BasicVector Vector2D where
>     (ax,ay) <+> (bx,by) = (ax+bx,ay+by)
>     c *> (ax,ay) = (c*ax,c*ay)
> 
> 
> 
> 
> 
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners


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

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


End of Beginners Digest, Vol 23, Issue 32
*****************************************

Reply via email to