I suppose there are plenty of flavors for such functions, and they are simple enough to write.

   One I've been using a bit is this one:

loopM :: Monad m => a -> (a -> m (Maybe a)) -> m ()
loopM start action = loop start
    where
    loop i =
        do  result <- action i
            case result of
                Nothing     -> return ()
                Just newval -> loop newval

   BTW: what is considered better? The above or this one:

loopM :: Monad m => a -> (a -> m (Maybe a)) -> m ()
loopM i action =
    do  result <- action i
        case result of
            Nothing     -> return ()
            Just newval -> loopM newval action

   Or is there no difference at all? Sorry for the non-sequitur here.

   Usage example:

streamToFile :: Storable a => [a] -> String -> IO ()
streamToFile list fname =
    do  let elementSize = sizeOf (head list)
        let numElements = (65535 + elementSize) `div` elementSize
        let bufferSize  = numElements * elementSize
        f <- openBinaryFile fname WriteMode
        allocaArray bufferSize $ \buf ->
            loopM list $ \list ->
                do  let (cur, next) = splitAt numElements list
                    pokeArray buf cur
                    hPutBuf f buf (length cur * elementSize)
                    case next of
                        []        -> return Nothing
                        otherwise -> return (Just next)
        hClose f

   (allows writing a lazy list to a binary file)

JCAB

On Wed, 21 Mar 2007 13:34:48 -0700, Dominic Steinitz <[EMAIL PROTECTED]> wrote:

These sort of things come up from time to time. Why not make a proposal?

http://www.haskell.org/pipermail/haskell-cafe/2006-February/014214.html

Dominic.

_______________________________________________
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

Reply via email to