Skip to content

Instantly share code, notes, and snippets.

@CristhianMotoche
Created December 12, 2018 03:07
Show Gist options
  • Save CristhianMotoche/894812f18b076efdaeb28cb7f02bb6fb to your computer and use it in GitHub Desktop.
Save CristhianMotoche/894812f18b076efdaeb28cb7f02bb6fb to your computer and use it in GitHub Desktop.
Example of Tasty Golden Tests
:set -package tasty-golden
:set -package blaze-html
{-# LANGUAGE RecordWildCards #-}
module TastyGoldenEx (main) where
import Test.Tasty (defaultMain, TestTree, testGroup)
import Test.Tasty.Golden (goldenVsFile)
import Text.Blaze.Html5 (Html)
import qualified Text.Blaze.Html5 as H
import qualified Text.Blaze.Html.Renderer.String as H
-- Types
newtype Type =
Type { mkType :: String } deriving Show
data Attack =
Attack
{ aName :: String
, aDamage :: Int
} deriving Show
data Pokemon =
Pokemon
{ name :: String
, type_ :: Type
, attacks :: [Attack]
} deriving Show
-- View
view :: Pokemon -> Html
view Pokemon{..} =
H.div $ do
H.h1 $
H.toHtml name
H.h4 $
H.toHtml (mkType type_)
-- H.ul $
-- mapM_ viewAttack attacks
mapM_ viewAttack attacks
viewAttack :: Attack -> Html
viewAttack Attack{..} = do
H.li $ H.toHtml aName
H.li $ H.toHtml aDamage
-- Test
pikachu :: Pokemon
pikachu =
Pokemon
"Pikachu"
(Type "Electric")
[ Attack "Quick Attack" 100
, Attack "Electric Shock" 200
]
test :: TestTree
test =
testGroup "YamlToJson golden tests"
[ let outputFilename = "actual.pokemon.txt"
in goldenVsFile
"view Pokemon"
"golden.pokemon.txt"
outputFilename
(writeFile outputFilename (H.renderHtml $ view pikachu))
]
-- Main
main :: IO ()
main = do
putStrLn $ H.renderHtml (view pikachu)
defaultMain test
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment