Re: [Haskell-cafe] Array, Vector, Bytestring

2013-06-03 Thread silvio

   write :: MVector a -> Int -> a -> ST s a


This should have been:
write :: MVector s a -> Int -> a -> ST s a

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


Re: [Haskell-cafe] Array, Vector, Bytestring

2013-06-03 Thread Artyom Kazak
silvio  писал(а) в своём письме Mon, 03 Jun 2013  
22:16:08 +0300:



Hi everyone,

Every time I want to use an array in Haskell, I find myself having to  
look up in the doc how they are used, which exactly are the modules I  
have to import ... and I am a bit tired of staring at type signatures  
for 10 minutes to figure out how these arrays work every time I use them  
(It's even worse when you have to write the signatures). I wonder how  
other people perceive this issue and what possible solutions could be.


Recently I’ve started to perceive this issue as “hooray, we have lenses  
now, a generic interface for all the different messy stuff we have”. But  
yes, the inability to have One Common API for All Data Structures is  
bothering me as well.


Why do we need so many different implementations of the same thing? In  
the ghc libraries alone we have a vector, array and bytestring package  
all of which do the same thing, as demonstrated for instance by the  
vector-bytestring package. To make matters worse, the haskell 2010  
standard has includes a watered down version of array.


Indeed. What we need is `text` for strings (and stop using `bytestring`)  
and reworked `vector` for arrays (with added code from `StorableVector` —  
basically a lazy ByteString-like chunked array).



# Index

I don't really see a reason for having an index of a type other than Int  
and that starts somewhere else than at 0.


It’s a bad idea. I, for one, don’t really see how writing `Vector (Vector  
(Vector Int))` can be considered even remotely satisfying by anyone. And  
if you’re considering 3D arrays “a corner case”, then I’m afraid I can’t  
agree with you.


Also, arrays which allow negative indexing can save a lot of headache and  
prevent mistakes which generally occur when a programmer is forced to  
constantly keep in mind that index 2000 is actually 0 and 0 is −2000.



# Storable vs Unboxed

Is there really a difference between Storable and Unboxed arrays and if  
so can't this be fixed in the complier rather than having to expose this  
problem to the programmer?


Storable seems to be mainly for marshalling, and most people who need it  
are (probably) library writers. I don’t know for sure, though, but it  
doesn’t appear to be a big issue.



# ST s vs IO

This is probably the hardest to resolve issue. The easiest solution is  
probably to just have a module for each of them as in the array package.

I find the PrimState a bit complicated and circuitous.

The ideal solution would be to have

   type IO a = ST RealWorld# a

in the next haskell standard.


Sure, except that IO is actually *not* ST+Realworld, and only happens to  
be implemented like that in GHC (not in JHC, for instance). It has been  
discussed before:  
http://haskell.1045720.n5.nabble.com/IO-ST-RealWorld-td3190075.html . (Not  
to mention people attempting to rewrite RealWorld# values and create havoc  
and fire missiles everywhere expecting them to disappear the very moment  
they smile knowingly and `put` the original RealWorld# back.)


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


Re: [Haskell-cafe] Array, Vector, Bytestring

2013-06-03 Thread Ben Gamari
Artyom Kazak  writes:

> silvio  писал(а) в своём письме Mon, 03 Jun 2013  
> 22:16:08 +0300:
>
>> Hi everyone,
>>
>> Every time I want to use an array in Haskell, I find myself having to  
>> look up in the doc how they are used, which exactly are the modules I  
>> have to import ... and I am a bit tired of staring at type signatures  
>> for 10 minutes to figure out how these arrays work every time I use them  
>> (It's even worse when you have to write the signatures). I wonder how  
>> other people perceive this issue and what possible solutions could be.
>
> Recently I’ve started to perceive this issue as “hooray, we have lenses  
> now, a generic interface for all the different messy stuff we have”. But  
> yes, the inability to have One Common API for All Data Structures is  
> bothering me as well.
>
>> Why do we need so many different implementations of the same thing? In  
>> the ghc libraries alone we have a vector, array and bytestring package  
>> all of which do the same thing, as demonstrated for instance by the  
>> vector-bytestring package. To make matters worse, the haskell 2010  
>> standard has includes a watered down version of array.
>
> Indeed. What we need is `text` for strings (and stop using `bytestring`)  
> and reworked `vector` for arrays (with added code from `StorableVector` —  
> basically a lazy ByteString-like chunked array).
>
To be perfectly clear, ByteString and Text target much different
use-cases and are hardly interchangeable. While ByteString is, as the
name suggests, a string of bytes, Text is a string of characters in a
Unicode encoding. When you are talking about unstructured binary data,
you should most certainly be using ByteString.

Cheers,

- Ben

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


Re: [Haskell-cafe] Array, Vector, Bytestring

2013-06-03 Thread briand
On Mon, 03 Jun 2013 19:16:08 +
silvio  wrote:

> Hi everyone,
> 
> Every time I want to use an array in Haskell, I find myself having to 
> look up in the doc how they are used, which exactly are the modules I 
> have to import ... and I am a bit tired of staring at type signatures 
> for 10 minutes to figure out how these arrays work every time I use them 
> (It's even worse when you have to write the signatures). I wonder how 
> other people perceive this issue and what possible solutions could be.

My opinion, it's every bit as bad you say it is...
Not a clue as to what can be done about it.

Probably yet another vector module.





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


Re: [Haskell-cafe] Array, Vector, Bytestring

2013-06-03 Thread Clark Gaebel
How is this a problem?

If you're representing text, use 'text'.
If you're representing a string of bytes, use 'bytestring'.
If you want an "array" of values, think c++ and use 'vector'.
If you want to mutate arrays, first, make sure you do. You probably don't.
If you're sure, use MVector.

Don't use String, except to interface with legacy code. You probably want
'text'.
Don't use Array. Anything it can be used for, can be done with 'vector'.

  - Clark

This covers all the use-cases that I can think of.

On Monday, June 3, 2013, wrote:

> On Mon, 03 Jun 2013 19:16:08 +
> silvio > wrote:
>
> > Hi everyone,
> >
> > Every time I want to use an array in Haskell, I find myself having to
> > look up in the doc how they are used, which exactly are the modules I
> > have to import ... and I am a bit tired of staring at type signatures
> > for 10 minutes to figure out how these arrays work every time I use them
> > (It's even worse when you have to write the signatures). I wonder how
> > other people perceive this issue and what possible solutions could be.
>
> My opinion, it's every bit as bad you say it is...
> Not a clue as to what can be done about it.
>
> Probably yet another vector module.
>
>
>
>
>
> ___
> 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] Array, Vector, Bytestring

2013-06-03 Thread Jason Dagit
On Mon, Jun 3, 2013 at 7:45 PM, Clark Gaebel  wrote:
> How is this a problem?
>
> If you're representing text, use 'text'.
> If you're representing a string of bytes, use 'bytestring'.
> If you want an "array" of values, think c++ and use 'vector'.
> If you want to mutate arrays, first, make sure you do. You probably don't.
> If you're sure, use MVector.
>
> Don't use String, except to interface with legacy code. You probably want
> 'text'.
> Don't use Array. Anything it can be used for, can be done with 'vector'.

You have to build multidimensional accessors for vector yourself.
Array supports them out of the box. I still prefer vector, but it's
only fair to note that multidimensional data is a weak spot of vector.

Jason

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


Re: [Haskell-cafe] Array, Vector, Bytestring

2013-06-03 Thread Clark Gaebel
That's absolutely true. Wrappers around vector for your multidimensional
access is probably best, but Vectors of Vectors are usually easier.

But again, you're right. Multidimensional access is a pain. If it's a
"matrix" of numerical values, you could take a look at 'hmatrix'.

  - Clark

On Monday, June 3, 2013, Jason Dagit wrote:

> On Mon, Jun 3, 2013 at 7:45 PM, Clark Gaebel 
> >
> wrote:
> > How is this a problem?
> >
> > If you're representing text, use 'text'.
> > If you're representing a string of bytes, use 'bytestring'.
> > If you want an "array" of values, think c++ and use 'vector'.
> > If you want to mutate arrays, first, make sure you do. You probably
> don't.
> > If you're sure, use MVector.
> >
> > Don't use String, except to interface with legacy code. You probably want
> > 'text'.
> > Don't use Array. Anything it can be used for, can be done with 'vector'.
>
> You have to build multidimensional accessors for vector yourself.
> Array supports them out of the box. I still prefer vector, but it's
> only fair to note that multidimensional data is a weak spot of vector.
>
> Jason
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Array, Vector, Bytestring

2013-06-03 Thread briand
On Mon, 3 Jun 2013 23:19:38 -0400
Clark Gaebel  wrote:

> That's absolutely true. Wrappers around vector for your multidimensional
> access is probably best, but Vectors of Vectors are usually easier.
> 
> But again, you're right. Multidimensional access is a pain. If it's a
> "matrix" of numerical values, you could take a look at 'hmatrix'.

or repa


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


Re: [Haskell-cafe] Array, Vector, Bytestring

2013-06-04 Thread Artyom Kazak

Oops.

Ben Gamari  писал(а) в своём письме Tue, 04 Jun
2013 04:41:53 +0300:


To be perfectly clear, ByteString and Text target much different
use-cases and are hardly interchangeable. While ByteString is, as the
name suggests, a string of bytes, Text is a string of characters in a
Unicode encoding. When you are talking about unstructured binary data,
you should most certainly be using ByteString.


Why create a special case? Right now you should use ByteString, yes, but I
wish I could just use a generic array of Word8.

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


Re: [Haskell-cafe] Array, Vector, Bytestring

2013-06-04 Thread Peter Simons
Hi Clark,

 > How is this a problem?
 >
 > If you're representing text, use 'text'.
 > If you're representing a string of bytes, use 'bytestring'.
 > If you want an "array" of values, think c++ and use 'vector'.

the problem is that all those packages implement the exact same data
type from scratch, instead of re-using an implementation of a
general-purpose array internally. That is hardly desirable, nor is it
necessary.

Take care,
Peter


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


Re: [Haskell-cafe] Array, Vector, Bytestring

2013-06-04 Thread Tom Ellis
On Tue, Jun 04, 2013 at 04:01:37PM +0200, Peter Simons wrote:
>  > How is this a problem?
>  >
>  > If you're representing text, use 'text'.
>  > If you're representing a string of bytes, use 'bytestring'.
>  > If you want an "array" of values, think c++ and use 'vector'.
> 
> the problem is that all those packages implement the exact same data
> type from scratch, instead of re-using an implementation of a
> general-purpose array internally. That is hardly desirable, nor is it
> necessary.

Just to clarify for those on the sidelines, the issue is duplication of
implementation details, rather than duplication of functionality?

Tom

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


Re: [Haskell-cafe] Array, Vector, Bytestring

2013-06-04 Thread silvio

Just to clarify for those on the sidelines, the issue is duplication of
implementation details, rather than duplication of functionality?


Well to me, that is not the main issue. The main issue is that you have 
to study all of them and depending on which libraries you want to use 
have to convert between them, which could be expensive and is definitely 
annoying.


I made a few simple benchmarks comparing the three libraries you can 
find the code attached.


this is compiled with -O2

# simple sum of 100 Word8 elements

Unboxed Vector   1.114060 ms
Storable Vector  795.1207 us
Primitive Vector 1.116145 ms

ByteString   9.076256 ms

array library has no fold or sum function

# simple sum of 100 more or less randomly chosen elements

Unboxed Vector (unsafe)33.74364 ms
Storable Vector (unsafe)   50.27273 ms
Storable Vector (safe) 67.01634 ms
Primitive Vector (unsafe)  56.29919 ms

ByteString (unsafe)19.29611 ms
ByteString (safe)  18.29065 ms

UArray (safe)  46.88719 ms
unsafe does not exist for array

So Unboxed can be better than Storable but doesn't need to be.
Also, which implementation is faster depends very much on the problem at 
hand. And array is just missing half the needed features.


Silvio
import Criterion.Main
import Criterion.Config

import Data.Word
import Data.Bits
import System.Random

import qualified Data.Vector.Unboxed as UVec
import qualified Data.Vector.Storable as SVec
import qualified Data.Vector.Primitive as PVec

import qualified Data.ByteString as BStr
import qualified Data.ByteString.Unsafe as BStr

import qualified Data.Array.Unboxed as UArr
import qualified Data.Array.Storable as SArr

num = 100 :: Int
logNum = floor $ logBase 2 (fromIntegral num)
maskNum = 2^logNum-1

gen = mkStdGen 4653

randomList = take num $ randoms gen

-- PREPARE ARRAYS
uvec = UVec.fromList randomList :: UVec.Vector Word8
svec = SVec.fromList randomList :: SVec.Vector Word8
pvec = PVec.fromList randomList :: PVec.Vector Word8
bstr = BStr.pack randomList :: BStr.ByteString
uarr = UArr.listArray (0,num-1) randomList :: UArr.UArray Int Word8

-- FOR SECOND TEST
randomAccessSum :: (Int -> Word8) -> Word8
randomAccessSum f = go (num-1) 0 0 where
go 0 _ result = result
go n index oldResult = let result = f index + oldResult in
seq result go (n-1) ((index + 38634329) .&. maskNum) result

-- myConfig = defaultConfig { cfgVerbosity = ljust Quiet }
myConfig = defaultConfig

main = do
uvec `seq` svec `seq` pvec `seq` bstr `seq` return ()
defaultMainWith myConfig (return ())
[ bgroup "sum"
[ bench "Unboxed Vector: sum"   $ whnf UVec.sum uvec
--, bench "Unboxed Vector: foldl1' (+)"   $ whnf (UVec.foldl1' (+)) uvec
, bench "Storable Vector: sum"  $ whnf SVec.sum svec
, bench "Storable Vector: foldl1' (+)"  $ whnf (SVec.foldl1' (+)) svec
--, bench "Storable Vector: sum . toList" $ whnf (sum . SVec.toList) svec
, bench "Primitive Vector: sum" $ whnf PVec.sum pvec
, bench "ByteString: foldl1' (+)"   $ whnf (BStr.foldl1' (+)) bstr
, bench "ByteString: foldl1 (+)"  $ whnf (BStr.foldl1 (+)) bstr
]
, bgroup "random access sum"
[ bench "Unboxed Vector: unsafeIndex"   $ whnf randomAccessSum (UVec.unsafeIndex uvec)
, bench "Storable Vector: unsafeIndex"  $ whnf randomAccessSum (SVec.unsafeIndex svec)
, bench "Storable Vector: safe (!)" $ whnf randomAccessSum ((SVec.!) svec)
, bench "Primitive Vector: unsafeIndex" $ whnf randomAccessSum (PVec.unsafeIndex pvec)
, bench "ByteString: unsafeIndex"   $ whnf randomAccessSum (BStr.unsafeIndex bstr)
, bench "ByteString: safe index"$ whnf randomAccessSum ((BStr.index) bstr)
, bench "UArray: safe (!)"  $ whnf randomAccessSum ((UVec.!) uvec)
]
]

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


Re: [Haskell-cafe] Array, Vector, Bytestring

2013-06-04 Thread Carter Schonwald
I really don't understand this concern.

These libraries are tuned for wildly different workloads and use cases, so
these sorts of micro benchmarks are an Apples to Frogs comparisons.
(even aside from the fact that you'll get very different perf if you used
-fllvm and set things up so the array indexing and associated loop code get
inlined and fused together!)

what is the actual concern? Strawman micro benchmarks that don't even
compare the respective libraries for their intended use cases seeems
weird.






On Tue, Jun 4, 2013 at 12:49 PM, silvio  wrote:

> Just to clarify for those on the sidelines, the issue is duplication of
>> implementation details, rather than duplication of functionality?
>>
>
> Well to me, that is not the main issue. The main issue is that you have to
> study all of them and depending on which libraries you want to use have to
> convert between them, which could be expensive and is definitely annoying.
>
> I made a few simple benchmarks comparing the three libraries you can find
> the code attached.
>
> this is compiled with -O2
>
> # simple sum of 100 Word8 elements
>
> Unboxed Vector   1.114060 ms
> Storable Vector  795.1207 us
> Primitive Vector 1.116145 ms
>
> ByteString   9.076256 ms
>
> array library has no fold or sum function
>
> # simple sum of 100 more or less randomly chosen elements
>
> Unboxed Vector (unsafe)33.74364 ms
> Storable Vector (unsafe)   50.27273 ms
> Storable Vector (safe) 67.01634 ms
> Primitive Vector (unsafe)  56.29919 ms
>
> ByteString (unsafe)19.29611 ms
> ByteString (safe)  18.29065 ms
>
> UArray (safe)  46.88719 ms
> unsafe does not exist for array
>
> So Unboxed can be better than Storable but doesn't need to be.
> Also, which implementation is faster depends very much on the problem at
> hand. And array is just missing half the needed features.
>
> Silvio
>
> ___
> 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] Array, Vector, Bytestring

2013-06-04 Thread Mike Ledger

On 05/06/13 02:49, silvio wrote:

Just to clarify for those on the sidelines, the issue is duplication of
implementation details, rather than duplication of functionality?


Well to me, that is not the main issue. The main issue is that you 
have to study all of them and depending on which libraries you want to 
use have to convert between them, which could be expensive and is 
definitely annoying.


I made a few simple benchmarks comparing the three libraries you can 
find the code attached.


this is compiled with -O2

# simple sum of 100 Word8 elements

Unboxed Vector   1.114060 ms
Storable Vector  795.1207 us
Primitive Vector 1.116145 ms

ByteString   9.076256 ms

array library has no fold or sum function

# simple sum of 100 more or less randomly chosen elements

Unboxed Vector (unsafe)33.74364 ms
Storable Vector (unsafe)   50.27273 ms
Storable Vector (safe) 67.01634 ms
Primitive Vector (unsafe)  56.29919 ms

ByteString (unsafe)19.29611 ms
ByteString (safe)  18.29065 ms

UArray (safe)  46.88719 ms
unsafe does not exist for array

So Unboxed can be better than Storable but doesn't need to be.
Also, which implementation is faster depends very much on the problem 
at hand. And array is just missing half the needed features.


Silvio


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
array does provide folding functions, found in its Foldable and 
Traversable instances.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Array, Vector, Bytestring

2013-06-04 Thread silvio

array does provide folding functions, found in its Foldable and
Traversable instances.


Where can I find this? I can neither in the array package nor with 
google nor with hoogle.


Silvio

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


Re: [Haskell-cafe] Array, Vector, Bytestring

2013-06-04 Thread Mike Ledger

On 05/06/13 07:01, silvio wrote:

array does provide folding functions, found in its Foldable and
Traversable instances.


Where can I find this? I can neither in the array package nor with 
google nor with hoogle.


Silvio

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
Data.Foldable and Data.Traversable, if you hoogle "Foldable" or 
"Traversable" you'll find their modules' docs.


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


Re: [Haskell-cafe] Array, Vector, Bytestring

2013-06-04 Thread silvio

These libraries are tuned for wildly different workloads and use cases,
so these sorts of micro benchmarks are an Apples to Frogs comparisons.


You can argue that for any benchmark, but sometimes the choice is 
between Apples and Frogs. If you have some more extensive benchmarks I'm 
happy to have a look at them.



(even aside from the fact that you'll get very different perf if you
used -fllvm and set things up so the array indexing and associated loop
code get inlined and fused together!)


I think llvm should be default by now. In any case, if you write code, 
it is important to know how well something works out of box without you 
having to spend hours optimizing it.



what is the actual concern? Strawman micro benchmarks that don't even
compare the respective libraries for their intended use cases seeems
weird.


Perhaps i should have explained that better.

If one library was clearly superior to the others, that would have made 
it easier to choose.


Also I wanted to check if Unboxed was usually better than Storable as 
they are semantically the same (correct me if i'm wrong). Which it is in 
one example. Still I think Storable could be done so we don't need 
Unboxed, too.


I would have said that sum/fold (i.e. consecutive access of the 
elements) is a reasonable use case for how we typically use bytestring 
and the random access sum is a reasonable you use case for how we 
typically use array/vector. Interestingly enough the performance was 
exactly opposed to these reasonable use cases.


Silvio

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


Re: [Haskell-cafe] Array, Vector, Bytestring

2013-06-04 Thread Peter Simons
Hi Tom,

 > On Tue, Jun 04, 2013 at 04:01:37PM +0200, Peter Simons wrote:
 >>  > How is this a problem?
 >>  >
 >>  > If you're representing text, use 'text'.
 >>  > If you're representing a string of bytes, use 'bytestring'.
 >>  > If you want an "array" of values, think c++ and use 'vector'.
 >>
 >> the problem is that all those packages implement the exact same data
 >> type from scratch, instead of re-using an implementation of a
 >> general-purpose array internally. That is hardly desirable, nor is it
 >> necessary.
 >
 > Just to clarify for those on the sidelines, the issue is duplication of
 > implementation details, rather than duplication of functionality?

I am not sure what the terms "duplication of implementation details" and
"duplication of functionality" mean in this context. Could you please
explain how these two concepts differ in your opinion?

Take care,
Peter


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


Re: [Haskell-cafe] Array, Vector, Bytestring

2013-06-04 Thread Tom Ellis
On Tue, Jun 04, 2013 at 11:23:16PM +0200, Peter Simons wrote:
>  > On Tue, Jun 04, 2013 at 04:01:37PM +0200, Peter Simons wrote:
>  >>  > If you're representing text, use 'text'.
>  >>  > If you're representing a string of bytes, use 'bytestring'.
>  >>  > If you want an "array" of values, think c++ and use 'vector'.
>  >>
>  >> the problem is that all those packages implement the exact same data
>  >> type from scratch, instead of re-using an implementation of a
>  >> general-purpose array internally. That is hardly desirable, nor is it
>  >> necessary.
>  >
>  > Just to clarify for those on the sidelines, the issue is duplication of
>  > implementation details, rather than duplication of functionality?
> 
> I am not sure what the terms "duplication of implementation details" and
> "duplication of functionality" mean in this context. Could you please
> explain how these two concepts differ in your opinion?

Hi Peter,

When I say "duplication of implementation details" I believe I mean
something like your implementing "the exact same data type from scratch".

By "duplication of functionality", on the other hand, I mean providing two
libraries with similar APIs which essentially serve the same purpose.

I believe you are suggesting that there is redundancy in the implementation
details of these libraries, not in the APIs they expose.  Then again, I was
just trying to understand the discussion at hand.  I don't have an opinion
on it.

Tom

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


Re: [Haskell-cafe] Array, Vector, Bytestring

2013-06-05 Thread Peter Simons
Hi Tom,

thank you for the explanation.

 > I believe you are suggesting that there is redundancy in the
 > implementation details of these libraries, not in the APIs they
 > expose.

I meant to say that there is redundancy in *both*. The libraries
mentioned in this thread re-implement the same type internally and
expose APIs to the user that are largely identical.

Take care,
Peter


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


Re: [Haskell-cafe] Array, Vector, Bytestring

2013-06-05 Thread Bas van Dijk
On 5 June 2013 11:50, Peter Simons  wrote:
> I meant to say that there is redundancy in *both*. The libraries
> mentioned in this thread re-implement the same type internally and
> expose APIs to the user that are largely identical.

I agree. I hope that ByteStrings will be replaced by a Storable.Vector
of Word8 at some point in the future.

To make the transition easier I have an experimental library which
defines a ByteString as a type synonym of a Storable.Vector of Word8
and provides the same interface as the bytestring package:

https://github.com/basvandijk/vector-bytestring

It includes a comprehensive benchmark suite which compares it to
bytestring. IIRC some functions are way faster in vector than their
bytestring equivalents and they have the potential to fuse. However
some functions are still way slower so more work has to be done in
vector to beat bytestring completely.

Bas

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


Re: [Haskell-cafe] Array, Vector, Bytestring

2013-07-10 Thread Alfredo Di Napoli
> To make the transition easier I have an experimental library which
> defines a ByteString as a type synonym of a Storable.Vector of Word8
> and provides the same interface as the bytestring package:
>
> https://github.com/basvandijk/vector-bytestring


That's interesting Bas. What bothers me about ByteStrings is that they need
to be "pinned" inside the heap,
preventing the GC from collecting them. This is more than an issue, I
think, if a program uses them massively
and they needs to be allocated persistently (example: a long-life
constant). I know is still a marginal case, but
knowing that a part of my heap is pinned makes my sleep quality degrade :(
I assume that working with vector remove the problem, correct?

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


Re: [Haskell-cafe] Array, Vector, Bytestring

2013-07-10 Thread Bas van Dijk
On 10 July 2013 08:57, Alfredo Di Napoli  wrote:
>
>> To make the transition easier I have an experimental library which
>> defines a ByteString as a type synonym of a Storable.Vector of Word8
>> and provides the same interface as the bytestring package:
>>
>> https://github.com/basvandijk/vector-bytestring
>
>
> That's interesting Bas. What bothers me about ByteStrings is that they need
> to be "pinned" inside the heap,
> preventing the GC from collecting them.

Being "pinned" doesn't prevent an object from being garbage collected.
It just means that the GC won't move the object around so that foreign
code can reliably reference the object while the GC is running:

http://ghc.haskell.org/trac/ghc/wiki/Commentary/Rts/Storage/GC/Pinned

> I assume that working with vector remove the problem, correct?

There wasn't a problem in the first but note that a Storable Vector is
implemented in the same way as a ByteString: a ForeignPtr and a
length*

I hope I have now improved your sleep quality ;-)

Cheers,

Bas

* A ByteString also contains an offset but vector modifies the pointer
in the ForeignPtr instead so we safe an Int there.

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


Re: [Haskell-cafe] Array, Vector, Bytestring

2013-07-10 Thread Alfredo Di Napoli
Hello Bas,

sorry for being unclear. What you say is correct, I was referring (and I
realised this after posting :D ) that the real
annoying thing is fragmentation in memory. Due to the fact the GC can't
move those objects, if we have long running
processes our memory will become more and more fragmented, correct? :(

A.


On 10 July 2013 08:25, Bas van Dijk  wrote:

> On 10 July 2013 08:57, Alfredo Di Napoli 
> wrote:
> >
> >> To make the transition easier I have an experimental library which
> >> defines a ByteString as a type synonym of a Storable.Vector of Word8
> >> and provides the same interface as the bytestring package:
> >>
> >> https://github.com/basvandijk/vector-bytestring
> >
> >
> > That's interesting Bas. What bothers me about ByteStrings is that they
> need
> > to be "pinned" inside the heap,
> > preventing the GC from collecting them.
>
> Being "pinned" doesn't prevent an object from being garbage collected.
> It just means that the GC won't move the object around so that foreign
> code can reliably reference the object while the GC is running:
>
> http://ghc.haskell.org/trac/ghc/wiki/Commentary/Rts/Storage/GC/Pinned
>
> > I assume that working with vector remove the problem, correct?
>
> There wasn't a problem in the first but note that a Storable Vector is
> implemented in the same way as a ByteString: a ForeignPtr and a
> length*
>
> I hope I have now improved your sleep quality ;-)
>
> Cheers,
>
> Bas
>
> * A ByteString also contains an offset but vector modifies the pointer
> in the ForeignPtr instead so we safe an Int there.
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe