[Haskell-cafe] Stream processors
MR K P SCHUPKE
k.schupke at imperial.ac.uk
Thu Oct 21 11:44:57 EDT 2004
This is the interface I came up with (and its fairly efficient):
data IList a i e = ICons i i (a i e) (IList a i e) | INil
class List l e where
nil :: l e
null :: l e -> Bool
head :: l e -> e
tail :: l e -> l e
(+:) :: e -> l e -> l e
class List (l a i) e => ListPlus l a i e where
(++:) :: a i e -> l a i e -> l a i e
part :: a i e -> i -> l a i e -> l a i e
Here's the instance for a normal list:
instance List [] e where
nil = []
null (_:_) = False
null _ = True
head (a:_) = a
head _ = error "head: empty list"
tail (_:l) = l
tail _ = error "tail: empty list"
a +: l = a:l
Here's the instance for a list made of UArray buffers:
instance (IArray a e,Ix i,Num i) => List (IList a i) e where
nil = INil
null INil = True
null _ = False
head (ICons i _ a _) = a!i
head _ = error "head: empty list"
tail (ICons i j a l)
| i < j = ICons (i+1) j a l
| otherwise = l
tail _ = error "tail: empty list"
a +: l = ICons 0 0 (array (0,0) [(0,a)]) l
instance (IArray a e,Ix i,Num i) => ListPlus IList a i e where
a ++: l
| e >= s = ICons s e a l
| otherwise = l
where ~(s,e) = bounds a
part a i l
| e >= i = ICons s i a l
| otherwise = l
where ~(s,e) = bounds a
Here's a feeder reading from a file:
hGetIList :: ListPlus l UArray Int Word8 => Int -> Handle -> IO (l UArray Int Word8)
hGetIList bufSize h = do
mt <- newArray_ (0,bufSize-1)
ioLoop mt
where
ioLoop mt = unsafeInterleaveIO $ do
sz <- hGetArray h mt bufSize
hd <- freeze mt
case sz of
0 -> return nil
n | n < bufSize -> do
return (part hd (n-1) nil)
| otherwise -> do
tl <- ioLoop mt
return (hd ++: tl)
And here's an example consumer:
wc :: List l Word8 => l Word8 -> Char -> Int -> Int -> Int -> (Int,Int,Int)
wc l p i j k
| p `seq` i `seq` j `seq` k `seq` False = undefined
| not $ Main.null l, h <- (toEnum . fromEnum . Main.head) l, t <- Main.tail l = case isSpace h of
False -> wc t h (i + 1) (j + if isSpace p then 1 else 0) k
_ -> wc t h (i + 1) j (k + if h == '\n' then 1 else 0)
| otherwise = (i,j,k)
Keean.
More information about the Haskell-Cafe
mailing list