
On 09.01 11:32, Simon Marlow wrote:
Sebastian Sylvan wrote:
It would be neat if the PackedString library contained functions such as hGetLine etc. It does have a function for reading from a buffer, but it won't stop at a newline... But yeah, fast string manipulation is difficult when using a linked-list representation...
My version of the packed string library does have an hGetLine. Don Stewart was merging my version with his fps at some point, Don - any news on that?
Getting a fast FastPackedString will solve the problems with many benchmarks. A similar thing for arrays would be nice - although this is more about inteface:
module Data.Array.UnsafeOps where
import Data.Array.Base hiding((!))
{-# INLINE (!) #-} (!) :: MArray a e m => a Int e -> Int -> m e (!) = unsafeRead
{-# INLINE set #-} set :: MArray a e m => a Int e -> Int -> e -> m () set = unsafeWrite
{-# INLINE swap #-} swap :: MArray a e m => a Int e -> Int -> Int -> m () swap arr x y = do xv <- arr ! x yv <- arr ! y set arr x yv set arr y xv
{-# INLINE combineTo #-} combineTo :: MArray a e m => a Int e -> Int -> (e -> e -> e) -> a Int e -> Int -> m () combineTo a0 i0 f a1 i1 = do v0 <- a0 ! i0 v1 <- a1 ! i1 set a0 i0 $! f v0 v1
and so forth. Usually imperative solutions have something like "a[i] += b[i]", which currently is quite tedious and ugly to translate to MArrays. Now it would become "combineTo a i (+) b i". - Einar Karttunen