Skip to content

Commit

Permalink
started on the pretty print functions
Browse files Browse the repository at this point in the history
  • Loading branch information
sakari committed Sep 3, 2011
1 parent 8878914 commit 75ac35e
Show file tree
Hide file tree
Showing 5 changed files with 50 additions and 3 deletions.
2 changes: 2 additions & 0 deletions Language/Gherkin.hs
Expand Up @@ -2,8 +2,10 @@ module Language.Gherkin
(
module Language.Gherkin.AST
, module Language.Gherkin.Parser
, module Language.Gherkin.Pretty
)
where

import Language.Gherkin.AST
import Language.Gherkin.Parser
import Language.Gherkin.Pretty
16 changes: 16 additions & 0 deletions Language/Gherkin/Pretty.hs
@@ -0,0 +1,16 @@
{-# LANGUAGE NamedFieldPuns #-}

module Language.Gherkin.Pretty where

import Language.Gherkin.AST
import Text.PrettyPrint

pretty :: Feature -> Doc
pretty Feature { -- feature_tags
feature_name
, feature_description
-- , feature_background
-- , feature_scenarios
} = text "Feature:" <+> text feature_name $$ nest 4 featureBody
where
featureBody = text feature_description
7 changes: 5 additions & 2 deletions gherkin.cabal
Expand Up @@ -22,6 +22,7 @@ test-suite test
QuickCheck >= 2.4.0.0,
parsec >= 3.1.1,
gherkin >= 0.1,
pretty >= 1.0.2.1,
MissingH >= 1.1.0.3

Library
Expand All @@ -30,10 +31,12 @@ Library
exposed-modules:
Language.Gherkin,
Language.Gherkin.AST,
Language.Gherkin.Parser
Language.Gherkin.Parser,
Language.Gherkin.Pretty
build-depends:
base >= 4,
parsec >= 3.1.1
parsec >= 3.1.1,
pretty >= 1.0.2.1

-- Modules not exported by this package.
-- Other-modules:
Expand Down
15 changes: 15 additions & 0 deletions tests/Instances.hs
@@ -0,0 +1,15 @@
module Instances where
import Test.QuickCheck
import Language.Gherkin

newtype GF = GF Feature
deriving (Eq, Show)

instance Arbitrary GF where
arbitrary = return $ GF $ Feature {
feature_tags = []
, feature_name = "feature"
, feature_description = "description"
, feature_background = Nothing
, feature_scenarios = []
}
13 changes: 12 additions & 1 deletion tests/Main.hs
Expand Up @@ -4,10 +4,14 @@ import Test.Framework
import Test.Framework.Providers.QuickCheck2
import Text.Parsec
import Text.Parsec.String
import Instances
import Language.Gherkin
import Text.PrettyPrint

main :: IO ()
main = defaultMain [testGroup "Parsing tests" tests]
main = defaultMain [testGroup "Parsing tests" tests
, testGroup "Pretty roundtrip" prettyTests
]

feature :: Feature
feature = Feature { feature_tags = []
Expand All @@ -26,6 +30,13 @@ prop p str = case parse p "" str of
l =.= r | l /= r = error $ "Expected '" ++ show r ++ "'\nGot '" ++ show l
| otherwise = True


prettyTests :: [Test]
prettyTests = [
testProperty "" $ \(GF f) ->
prop parseFeature (render $ pretty f) =.= f
]

tests :: [Test]
tests = [
testProperty "parse table" $
Expand Down

0 comments on commit 75ac35e

Please sign in to comment.