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:  class and instance question
      (Stephen Blackheath [to Haskell-Beginners])
   2.  Bit Manipulation (Daniel Rozycki)
   3. Re:  Bit Manipulation (Ron Leisti)
   4. Re:  Bit Manipulation (Yitzchak Gale)


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

Message: 1
Date: Fri, 21 May 2010 07:21:26 +1200
From: "Stephen Blackheath [to Haskell-Beginners]"
        <mutilating.cauliflowers.step...@blacksapphire.com>
Subject: Re: [Haskell-beginners] class and instance question
To: beginners@haskell.org
Message-ID: <4bf58bb6.4020...@blacksapphire.com>
Content-Type: text/plain; charset=UTF-8

Scott,

Here's a type families solution (see below).

*Main> ((2,3) :: (Int, Int)) <+> (10,10)
(12,13)
*Main>

I think TypeSynonymInstances are best avoided if possible, otherwise the
two types are not really interchangeable.  It's certainly not needed for
this, anyway.


Steve

{-# LANGUAGE TypeFamilies, FlexibleInstances, FlexibleContexts #-}


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


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


type Vector2D a = (a,a)


instance Num a => BasicVector (a, a) where
    type Elt (a, a) = a
    (ax,ay) <+> (bx,by) = (ax+bx,ay+by)
    c *> (ax,ay) = (c*ax,c*ay)


On 21/05/10 03:30, Brent Yorgey wrote:
> 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
> 


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

Message: 2
Date: Thu, 20 May 2010 15:36:02 -0400
From: Daniel Rozycki <daniel.rozy...@yale.edu>
Subject: [Haskell-beginners] Bit Manipulation
To: beginners@haskell.org
Message-ID:
        <aanlktinjfo8rjeg0knfixknwcntzjepadsxhw4csf...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

Hi all,

I am a newcomer to Haskell trying to manipulate data at the bit level. More
specifically, I am trying to calculate a seven-bit value and a nine-bit
value, concatenate the two values as a Word16, and put the result using
putWord16. I know that this sounds weird (because it totally is), but it is
required by the standard of a networking protocol that I am implementing.
The byte seems to be the atomic unit in Haskell, but I need to go subatomic.
Currently, I am storing the two values each as Word16s, bitshifting one of
them left by nine (using shift in the Data.Bits module), and then adding the
two. Is there a simpler and/or more elegant way of achieving this result?

Thanks,
Dan Rozycki
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20100520/fa6d9fda/attachment-0001.html

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

Message: 3
Date: Thu, 20 May 2010 15:45:24 -0400
From: Ron Leisti <ron.lei...@gmail.com>
Subject: Re: [Haskell-beginners] Bit Manipulation
To: Daniel Rozycki <daniel.rozy...@yale.edu>
Cc: beginners@haskell.org
Message-ID:
        <aanlktil-hj4vsmz37uzdbeodxz7nwvxz0ac5b7ihd...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

Disclaimer: I'm a beginner too.

That's essentially what I've resorted to as well.  It would be nice to
see standard functions that pull out specific bits of a word, or join
them together; I've been doing them with shifts and ORs as well.  I'd
also be interested in knowing if there's a more respected way of doing
this.

As an aside, the Crypto library on Hackage has an embedded library
called Data.LargeWord, which offers Word64, Word128 and Word256
variants in case you need them (though there is (currently) a bug with
right-shifts on these larger words).

On Thu, May 20, 2010 at 3:36 PM, Daniel Rozycki <daniel.rozy...@yale.edu> wrote:
> Hi all,
> I am a newcomer to Haskell trying to manipulate data at the bit level. More
> specifically, I am trying to calculate a seven-bit value and a nine-bit
> value, concatenate the two values as a Word16, and put the result using
> putWord16. I know that this sounds weird (because it totally is), but it is
> required by the standard of a networking protocol that I am implementing.
> The byte seems to be the atomic unit in Haskell, but I need to go subatomic.
> Currently, I am storing the two values each as Word16s, bitshifting one of
> them left by nine (using shift in the Data.Bits module), and then adding the
> two. Is there a simpler and/or more elegant way of achieving this result?
> Thanks,
> Dan Rozycki
>
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>
>


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

Message: 4
Date: Fri, 21 May 2010 15:44:24 +0300
From: Yitzchak Gale <g...@sefer.org>
Subject: Re: [Haskell-beginners] Bit Manipulation
To: Daniel Rozycki <daniel.rozy...@yale.edu>
Cc: beginners@haskell.org
Message-ID:
        <aanlktinj4frppnd4jo_gafrbnoj1yw76rc11j1d6s...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

Hi Daniel,

Daniel Rozycki wrote:
> Currently, I am storing the two values each as Word16s, bitshifting one of
> them left by nine (using shift in the Data.Bits module), and then adding the
> two. Is there a simpler and/or more elegant way of achieving this result?

That's about what I would do in C. What's wrong with doing it that
way in Haskell? GHC should be smart enough to do pretty well
with those kinds of combinations.

If you do this sort of thing all the time and there are some combinators
that would make it more convenient for you - go ahead and make a
library out of them. And upload it to Hackage!

Regards.
Yitz


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

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


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

Reply via email to