[Haskell-cafe] Efficient M to N conversion on fusion?

iquiw iku.iwasa at gmail.com
Tue Feb 16 19:00:12 EST 2010


I'll try it, thanks!

iquiw

On Tue, Feb 16, 2010 at 11:12 PM, Felipe Lessa <felipe.lessa at gmail.com> wrote:
> On Tue, Feb 16, 2010 at 07:52:51PM +0900, iquiw wrote:
>> Is there any efficient way to convert M-length ByteString, Text or
>> Vector into N-length one?
>
> This is just a guess, but in vector at least it should be
> possible to use sized[1] to tell how much space should be
> allocated on the final vector.  For example, something like the
> following *untested* code:
>
> import qualified Data.Vector.Stream.Monadic as S
> import qualified Data.Vector.Generic as G
> import Control.Applicative
> import Data.Vector.Stream.Size
>
> -- | The size should be the size of each v b.
> concatMapSized :: (G.Vector v a, G.Vector v b) => Size -> (a -> v b) -> v a -> v b
> concatMapSized size_each f v =
>  let stream = G.stream v
>      size   = mult size_each (S.size stream)
>  in G.unstream . flip S.sized size . S.concatMap (G.stream . f) $ stream
>
> mult :: Size -> Size -> Size
> mult (Exact n) (Exact m) = Exact (n*m)
> mult x y = maybe Max Unknown $ (*) <$> upperBound x <*> upperBound y
>
> I really don't know if this would improve or worsen performance,
> you should check the core and do benchmarks :).
>
> [1] http://hackage.haskell.org/packages/archive/vector/0.5/doc/html/Data-Vector-Fusion-Stream.html#v%3Asized
>
> --
> Felipe.
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>


More information about the Haskell-Cafe mailing list