Hi,

Sigbjorn Finne (Intl Vendor) wrote:

>> PS: I ever thought that such file operations are quite usual. 
>> Why don't they appear in the standard prelude?
> Who knows, but a concrete proposal of what operations you'd like
> to see supported here would be more than welcome.

Just an idea:

class Storable s where
  hWrite :: Handle -> s -> IO ()
  hRead ::  Handle -> IO s
  ...

some examples:

1.
instance Storable (ByteArray ix) where
  hWrite h ba = do
      (size,ba') <- toByteArray ba     -- convertion to ByteArray
      hPutStrLn h (show size)          -- first write the size of the ByteArray
      hPutBufBA h ba' size             -- does this operation append the
information
                                       -- to a file?
  hRead h = do
      size <- liftM read (hGetLine h)
      mba <- stToIO $ newCharArray (0,size-1)
      ba <- stToIO $ freezeCharArray mba   -- though, somehow strange ;^)
      s' <- hFillBufBA ba size
      when (s'<size) (error "...")
      return $ unsafeCoerce# ba        -- Is this coercion ok?


2.
instance (Storable a, Storable b) => Storable (a,b) where
  hWrite h (x,y) = do
      hWrite h x
      hWrite h y
  hRead h = do
      x <- hRead h
      y <- hRead h
      return (x,y)


3. 
data Tree a = Empty | Node a (Tree a) (Tree a)

Assuming that String is an instance of Storable, we can define (with 2.)

instance (Storable [a]) => Storable (Tree a) where
    hWrite h t = hWrite (structure t "", nodeValues t [])
       where structure :: Tree a -> String -> String    -- describing the Tree
             structure Empty s = 'e':s
             structure (Node _ tl tr) = structure tl 'n':(structure tr)
             
             nodeValues :: Tree a -> [a]                -- the Values of the
Tree
             ...

    hRead h = do
        (st,vs) <- hRead h
        (t,st',vs') <- return $ getTree st vals
        when ((st'/="")||(vs'/=[])) (error "...")
        return t
            where getTree :: String -> [a] -> (Tree a,String,[a])
                  getTree ('e':st) vs = (Empty,st,v)
                  getTree ('n':st) (v:vs) = (Node v tl tr,st',vs')
                      where ...



Providing instances of some basic data structures (like lists, tupels) in the
Prelude, one could easily define hWrite and hRead for arbitrary algebraic data
types like Tree.

Martin Stein

Reply via email to