[Haskell-beginners] Help with TAP implemation in haskell

Krzysztof Skrzętnicki gtener at gmail.com
Tue Feb 24 21:07:09 EST 2009


On Wed, Feb 25, 2009 at 02:32, Patrick LeBoutillier
<patrick.leboutillier at gmail.com> wrote:
> I'm having problems implementing the equivalent of this function in
> haskell. Inside a do block, is there a way to terminate the function
> immediately and return a result ("return" in the imperative sense, not
> the Haskell sense)? If not, must one really use deeply nested
> if/then/else statements to treat these special cases? All I could come
> up was this, which I find quite ugly:

For complex control flow continuation monad can be quite useful. But
one must be careful not to abuse it. Code with heavy use of
continuations can be very hard to follow and hard to debug as well.
Here is an example:

module Main where
import Control.Monad.Cont

checkErrors :: Int -> Maybe String
checkErrors ident =
    (`runCont` id) $ do
      response <- callCC $ \exit -> do
                       when (ident == 1) (exit . Just $ "Error! 1!")
                       when (ident == 2) (exit . Just $ "Error! 2!")
                       when (ident == 3) (exit . Just $ "Error! 3!")
                       when (ident == 4) (exit . Just $ "Error! 4!")
                       when (ident == 5) (exit . Just $ "Error! 5!")
                       return Nothing
      return response

main = forever $ getLine >>= \n -> print (checkErrors (read n))

It runs :

$ ./callcc
0
Nothing
1
Just "Error! 1!"
5
Just "Error! 5!"
3
Just "Error! 3!"
2
Just "Error! 2!"
1
Just "Error! 1!"
9
Nothing
8
Nothing
^C

Please read documentation on Control.Monad.Cont. There are more
elaborate explanations there.

All best

Christopher Skrzętnicki


More information about the Beginners mailing list