Re: [Haskell-cafe] ANN: fixed-vector

2012-11-12 Thread Michael Orlitzky
On 11/12/12 07:05, Aleksey Khudyakov wrote:
>> I have a lot of one-off code where I've defined these myself. Is it
>> possible to e.g. define vectors in R^2 and R^3, and write the p-norm
>> functions only once?
>>
> 
> Yes. it's possible.
> 
>> {-# LANGUAGE TypeFamilies #-}
>> {-# LANGUAGE FlexibleInstances #-}
>> {-# LANGUAGE MultiParamTypeClasses #-}
>> import Data.Vector.Fixed as V
>> import Data.Vector.Fixed.Internal
>> -- ^^^ Needed for Fun /will be reexported from Data.Vector.Fixed
>> import Data.Vector.Fixed.Unboxed
> 
> First we need to define data types and instances. It's possible to use
> vectors from library
> 
> ...

Thanks, this looks like exactly what I need. I'll try to replace my R^2
and R^3 implementations the next time I do my homework before the last
minute.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN: fixed-vector

2012-11-12 Thread Michael Orlitzky
On 11/12/12 01:57, Carter Schonwald wrote:
> Michael, I think that calls for a type-class! 
> (though I imagine theres a slicker way of writing it)
> 

I'm already using typeclasses, but there's still a bit of boilerplate. I
could probably think of something more clever myself, but like I said,
these are just one-off experiments, and I'm lazy. So I'm hoping
fixed-vector will do it for me!


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN: fixed-vector

2012-11-12 Thread Aleksey Khudyakov
> I have a lot of one-off code where I've defined these myself. Is it
> possible to e.g. define vectors in R^2 and R^3, and write the p-norm
> functions only once?
>

Yes. it's possible.

> {-# LANGUAGE TypeFamilies #-}
> {-# LANGUAGE FlexibleInstances #-}
> {-# LANGUAGE MultiParamTypeClasses #-}
> import Data.Vector.Fixed as V
> import Data.Vector.Fixed.Internal
> -- ^^^ Needed for Fun /will be reexported from Data.Vector.Fixed
> import Data.Vector.Fixed.Unboxed

First we need to define data types and instances. It's possible to use
vectors from library

> data Vec2D a = Vec2D a a
>
> type instance Dim Vec2D = S (S Z)
>
> instance Vector Vec2D a where
>   inspect (Vec2D x y) (Fun f) = f x y
>   construct = Fun Vec2D
>
>
> data Vec3D a = Vec3D a a a
>
> type instance Dim Vec3D = S (S (S Z))
>
> instance Vector Vec3D a where
>   inspect (Vec3D x y z) (Fun f) = f x y z
>   construct = Fun Vec3D
>

Now we can define generic p-norm. Maybe you had something different in
mind but still it's function which will work with any vector of fixed
length.

> pNorm :: (Vector v a, Floating a) => a -> v a -> a
> pNorm p = (** recip p) . V.sum . V.map ((** p) . abs)

We will get folloiwng in GHCi:

*Main> pNorm 1 $ Vec2D 1 2 :: Double
3.0
*Main> pNorm 1 $ Vec3D 1 2 3 :: Double
6.0

It's possible to avoid defining data types and use generic vectors
from library. Vec2 is synonym to Data.Vector.Fixed.Unboxed.Vec (S (S Z))

*Main> pNorm 2 (vec $ con |> 1 |> 2 :: Vec2 Double)
2.23606797749979

At the moment their construction is a bit cumbersome
so used replicate to illustrate other vector sizes.

*Main> pNorm 1 (V.replicate 1 :: Vec2 Double)
2.0
*Main> pNorm 1 (V.replicate 1 :: Vec (S (S (S Z))) Double)
3.0
*Main> pNorm 1 (V.replicate 1 :: Vec (S (S (S (S Z Double)
4.0

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN: fixed-vector

2012-11-11 Thread Carter Schonwald
Michael, I think that calls for a type-class!
(though I imagine theres a slicker way of writing it)


On Sun, Nov 11, 2012 at 11:18 PM, Michael Orlitzky wrote:

> On 11/10/2012 06:59 AM, Aleksey Khudyakov wrote:
> > Hello cafe!
> >
> > I want to announce library for the small vectors of fixed length
> > fixed-vector[1]. Fixed means that vector's length is determined
> > by its type.
> >
> > Generic API can work with both ATD-based vector like complex or
> > Vec written below and array-based ones.
> >
> >> data Vec a = Vec a a a
> >
> > It's based on post by Roman Leschinsiy[2].
> >
> >
> > Library also provide array-based vectors with memory
> > representation similar to onves from vector package. It's more
> > compact though because there is no need to store lengh and and
> > offset to first element.
> >
> > [1] http://hackage.haskell.org/package/fixed-vector
> > [2]
> http://unlines.wordpress.com/2010/11/15/generics-for-small-fixed-size-vectors/
>
>
> I have a lot of one-off code where I've defined these myself. Is it
> possible to e.g. define vectors in R^2 and R^3, and write the p-norm
> functions only once?
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN: fixed-vector

2012-11-11 Thread Michael Orlitzky
On 11/10/2012 06:59 AM, Aleksey Khudyakov wrote:
> Hello cafe!
> 
> I want to announce library for the small vectors of fixed length
> fixed-vector[1]. Fixed means that vector's length is determined
> by its type.
> 
> Generic API can work with both ATD-based vector like complex or
> Vec written below and array-based ones.
> 
>> data Vec a = Vec a a a
> 
> It's based on post by Roman Leschinsiy[2].
> 
> 
> Library also provide array-based vectors with memory
> representation similar to onves from vector package. It's more
> compact though because there is no need to store lengh and and
> offset to first element.
> 
> [1] http://hackage.haskell.org/package/fixed-vector
> [2] 
> http://unlines.wordpress.com/2010/11/15/generics-for-small-fixed-size-vectors/


I have a lot of one-off code where I've defined these myself. Is it
possible to e.g. define vectors in R^2 and R^3, and write the p-norm
functions only once?

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe