[Haskell-cafe] ANNOUNCE: abacate and chuchu

Marco Túlio Pimenta Gontijo marcotmarcot at gmail.com
Mon Aug 13 16:21:04 CEST 2012


Hi.

I'm pleased to announce the first release of Abacate and Chuchu.  Chuchu is
a port of Ruby's Cucumber to Haskell, and Abacate is a parser for the Gherkin
language, used by Cucumber.

According to their web site, "Cucumber lets software development teams describe
how software should behave in plain text. The text is written in a
business-readable domain-specific language and serves as documentation,
automated tests and development-aid - all rolled into one format."  For more
information on Cucumber: http://cukes.info/

Example of usage for a stack calculator:

calculator.feature:

    Feature: Division
      In order to avoid silly mistakes
      Cashiers must be able to calculate a fraction

      Scenario: Regular numbers
        Given that I have entered 3 into the calculator
        And that I have entered 2 into the calculator
        When I press divide
        Then the result should be 1.5 on the screen

calculator.hs:

    import Control.Applicative
    import Control.Monad.IO.Class
    import Control.Monad.Trans.State
    import Test.Chuchu
    import Test.HUnit

    type CalculatorT m = StateT [Double] m

    enterNumber :: Monad m => Double -> CalculatorT m ()
    enterNumber = modify . (:)

    getDisplay :: Monad m => CalculatorT m Double
    getDisplay
      = do
        ns <- get
        return $ head $ ns ++ [0]

    divide :: Monad m => CalculatorT m ()
    divide = do
      (n1:n2:ns) <- get
      put $ (n2 / n1) : ns

    defs :: Chuchu (CalculatorT IO)
    defs
      = do
        Given
          ("that I have entered"  *> number <*  "into the calculator")
          enterNumber
        When "I press divide" $ const divide
        Then ("the result should be"  *> number <*  "on the screen")
          $ \n
            -> do
              d <- getDisplay
              liftIO $ d @?= n

    main :: IO ()
    main = chuchuMain defs (`evalStateT` [])

Both packages are available at Hackage at

http://hackage.haskell.org/package/abacate
http://hackage.haskell.org/package/chuchu

I have written them after the specification from Felipe Almeida Lessa.

Any comments are welcome.


-- 
marcot
http://marcot.eti.br/



More information about the Haskell-Cafe mailing list