Help with TAP implemation in haskell

Hi, As a learning exercise, I'm trying to make a Haskell module (my first) that implements a TAP library (http://testanything.org/). The library basically provides some functions to perform unit tests and keeps track of some state. It also performs quite a bit of IO as it goes a long. As a first step I'm loosely basing my code on a Java implementation. You can find the code here: http://svn.solucorp.qc.ca/repos/solucorp/JTap/trunk/JTap.java. I've setup my TapState data structure and a monad transformer to be able to keep state and do IO within the same functions: data TapState = TapState { planSet :: Bool, noPlan :: Bool, skipAll :: Bool, testDied :: Bool, expectedTests :: Int, executedTests :: Int, failedTests :: Int } deriving (Show) type TAP a = StateT TapState IO a In the Java version there is a function called cleanup that is called after all the tests are performed to determine the return code and print some diagnostics: private int cleanup(){ int rc = 0 ; if (! plan_set){ diag("Looks like your test died before it could output anything.") ; return rc ; } if (test_died){ diag("Looks like your test died just after " + executed_tests + ".") ; return rc ; } if ((! skip_all)&&(no_plan)){ print_plan(executed_tests) ; } if ((! no_plan)&&(expected_tests < executed_tests)) { diag("Looks like you planned " + expected_tests + " test" + (expected_tests > 1 ? "s" : "") + " but ran " + (executed_tests - expected_tests) + " extra.") ; rc = -1 ; } if ((! no_plan)&&(expected_tests > executed_tests)) { diag("Looks like you planned " + expected_tests + " test" + (expected_tests > 1 ? "s" : "") + " but only ran " + executed_tests + ".") ; } if (failed_tests > 0){ diag("Looks like you failed " + failed_tests + " test" + (failed_tests > 1 ? "s" : "") + " of " + executed_tests + ".") ; } return rc ; } 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: _cleanup :: Int -> TAP Int _cleanup rc = do ts <- get if (not $ planSet ts) then do diag "Looks like your test died before it could output anything." return rc else if (testDied ts) then do diag $ "Looks like your test died just after " ++ (show $ executedTests ts) return rc else ... Thanks a lot, Patrick Note: If it helps, you can find my Haskell code here: http://svn.solucorp.qc.ca/repos/solucorp/JTap/trunk/tap.hs -- ===================== Patrick LeBoutillier Rosemère, Québec, Canada

On Wed, Feb 25, 2009 at 02:32, Patrick LeBoutillier
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

On Tue, Feb 24, 2009 at 10:32 PM, Patrick LeBoutillier
_cleanup :: Int -> TAP Int _cleanup rc = do ts <- get if (not $ planSet ts) then do diag "Looks like your test died before it could output anything." return rc else if (testDied ts) then do diag $ "Looks like your test died just after " ++ (show $ executedTests ts) return rc else ...
_cleanup rc = do ts <- get let err | not (planSet ts) = diag "Looks like...anything." | testDied ts = diag $ "Looks like...after " ++ show (executedTests ts) | otherwise = return () -- assuming diag :: String -> TAP () err >> return rc or maybe _cleanup rc = get >>= showErrs >> return rc where showErrs ts | not (planSet ts) = diag "Looks like...anything." | testDied ts = diag $ "Looks like...after " ++ show (executedTests ts) | otherwise = return () HTH, -- Felipe.

On 2009 Feb 24, at 20:32, Patrick LeBoutillier 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
Take a look at MonadCont. But cleaner is to use Maybe (or MaybeT from Hackage):
-- you don't need to define this, it's in the Prelude instance Monad Maybe where return = Just Nothing >>= _ = Nothing (Just x) >>= f = f x
So if a test produces Nothing, you short-circuit past the remaining tests in the (>>=)-chain. But since you need to propagate the TAP state even when you are given Nothing, you want to wrap the Maybe in a StateT (and since you have IO at the bottom, you need MaybeT from Hackage):
type TAP a = StateT TAPState (MaybeT IO a)
withTAPplan myPlan $ do qTAP propertyOne -- Test.QuickCheck.quickCheck sTAP propertyTwo -- Test.SmallCheck.test sTAPToDepth 5 property3 -- Test.SmallCheck.smallCheck -- need wrappers because e.g. quickCheck won't expect a TAPState
BTW, are you integrating this with QuickCheck and/or SmallCheck? It might be nice to have passed in
-- or you could define (>>=) in your monad to DTRT
Also, in Haskell it is preferable to stay pure, perhaps especially while testing, so I would ditch the IO in the default case and provide a secondary function for tests that require IO. (hm, I sure hope I got this right, since my sinuses are trying to squeeze my brain out my ears...) -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH
participants (4)
-
Brandon S. Allbery KF8NH
-
Felipe Lessa
-
Krzysztof Skrzętnicki
-
Patrick LeBoutillier