[Haskell-cafe] Channel9 Interview: Software Composability andthe Future of Languages

Claus Reinke claus.reinke at talk21.com
Thu Feb 1 10:34:23 EST 2007


>>> while (hGetBuf h buf bufsize == bufsize)
>>>   crc := updateCrc crc buf bufsize
>>>   break if crc==0
>>>   print crc
> 
>>     inContT $ callCC $ \break -> do
>>         flip execStateT 0 $ do
>>             whileM (liftM (== bufsize) (hGetBuf h buf bufsize)) $ do
>>                 modifyM (updateCrc buf bufsize)
>>                 crc <- get
>>                 when (crc == 0) (lift (break crc))
>>                 print crc
> 
> first. it's longer than original. 

is it, though? what makes it longer are features that the original doesn't have,
I think. so how about a less ambitious translation, with crc in an MVar and a
while-loop that can be broken from the body as well as the condition:

    while (hGetBuf h buf bufzise .==. (return bufsize)) $ do
        crc =: updateCrc crc buf bufsize
        breakIf ((val crc) .==. (return 0)) `orElse` do
        printM (val crc)
        od

using definitions roughly like this

    while c b = do { r <- c; when r (b >>= flip when (while c b)) }
    continueIf c m = c >>= \b-> if b then od else m
    breakIf c m = c >>= \b-> if b then return False else m
    orElse = ($)
    od :: Monad m => m Bool
    od = return True

    x .==. y = liftM2 (==) x y
    printM x = x >>= print

    v =: x = do { rx <- x; swapMVar v rx }
    val = readMVar

not that I like that style;-)
Claus



More information about the Haskell-Cafe mailing list