[Haskell-cafe] Channel9 Interview: Software Composability and the
Future of Languages
Tomasz Zielonka
tomasz.zielonka at gmail.com
Thu Feb 1 05:15:39 EST 2007
On Wed, Jan 31, 2007 at 07:46:15PM +0300, Bulat Ziganshin wrote:
> Wednesday, January 31, 2007, 12:01:16 PM, you wrote:
>
> >> there are also many other similar issues, such as lack of good syntax
> >> for "for", "while", "break" and other well-known statements,
>
> > On the other hand you have an ability to define your own control
> > structures.
>
> i have a lot, but their features are limited, both in terms of
> automatic lifting and overall syntax. let's consider
>
> while (hGetBuf h buf bufsize == bufsize)
> crc := updateCrc crc buf bufsize
> break if crc==0
> print crc
A direct translation could look like this:
whileM c b = do { x <- c; when x (b >> whileM c b) }
f h buf =
flip runContT return $ do
callCC $ \break -> do
flip execStateT 0 $ do
whileM (liftIO (liftM (== bufsize) (hGetBuf h buf bufsize))) $ do
do crc <- get
crc' <- liftIO (updateCrc crc buf bufsize)
put crc'
crc <- get
when (crc == 0) (lift (break crc))
liftIO (print crc)
Which, admittedly, is much more lengthy. If we assume that hGetBuf,
updateCrc and print can work in any MonadIO, and we define
inContT x = flip runContT return x
then it becomes slightly shorter:
inContT $ callCC $ \break -> do
flip execStateT 0 $ do
whileM (liftM (== bufsize) (hGetBuf h buf bufsize)) $ do
do crc <- get
crc' <- updateCrc crc buf bufsize
put crc'
crc <- get
when (crc == 0) (lift (break crc))
Let's define:
modifyM f = do
x <- get
x' <- f x
put x'
and change the order of parametrs in updateCrc. We get:
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
> how this can be expressed in Haskell, without losing clarity?
I think it's quite clear what it does.
> > "inability" is an exaggeration - you can use the ContT monad
> > transformer, which even allows you to choose how "high" you
> > want to jump. But you probably already know this and just want to point
> > that it is cumbersome?
>
> don't know and don't want to use such a hard way.
I gave an example above. You can "break" with a return value, so it
seem it's what you want.
> there is a simpler solution, but it still requires to write more
> boilerplate code than C:
>
> res <- doSomething
> if isLeft res then return$ fromLeft res else do
> let (Right x) = res
> ...
Not simpler, but easier... and uglier. Somehow I don't like to solve
problems on the level of programming language syntax.
Best regards
Tomasz
More information about the Haskell-Cafe
mailing list