diff options
Diffstat (limited to 'haddock-library/fixtures')
27 files changed, 561 insertions, 0 deletions
diff --git a/haddock-library/fixtures/Fixtures.hs b/haddock-library/fixtures/Fixtures.hs new file mode 100644 index 00000000..a4e4321f --- /dev/null +++ b/haddock-library/fixtures/Fixtures.hs @@ -0,0 +1,165 @@ +{-# LANGUAGE DeriveGeneric, StandaloneDeriving #-} +{-# OPTIONS_GHC -fno-warn-orphans #-} +module Main (main) where + +import Control.Applicative ((<|>)) +import Control.Exception (IOException, catch) +import Control.Monad (when) +import Data.Foldable (traverse_) +import Data.List (foldl') +import Data.Traversable (for) +import GHC.Generics (Generic) +import Prelude () +import Prelude.Compat +import System.Directory (getDirectoryContents) +import System.Exit (exitFailure) +import System.FilePath +import System.IO + +import Data.TreeDiff +import Data.TreeDiff.Golden + +import qualified Options.Applicative as O + +import Documentation.Haddock.Types +import qualified Documentation.Haddock.Parser as Parse + +type Doc id = DocH () id + +data Fixture = Fixture + { fixtureName :: FilePath + , fixtureOutput :: FilePath + } + deriving Show + +data Result = Result + { _resultSuccess :: !Int + , _resultTotal :: !Int + } + deriving Show + +combineResults :: Result -> Result -> Result +combineResults (Result s t) (Result s' t') = Result (s + s') (t + t') + +readFixtures :: IO [Fixture] +readFixtures = do + let dir = "fixtures/examples" + files <- getDirectoryContents dir + let inputs = filter (\fp -> takeExtension fp == ".input") files + return $ flip map inputs $ \fp -> Fixture + { fixtureName = dir </> fp + , fixtureOutput = dir </> fp -<.> "parsed" + } + +goldenFixture + :: String + -> IO Expr + -> IO Expr + -> (Expr -> Expr -> IO (Maybe String)) + -> (Expr -> IO ()) + -> IO Result +goldenFixture name expect actual cmp wrt = do + putStrLn $ "running " ++ name + a <- actual + e <- expect `catch` handler a + mres <- cmp e a + case mres of + Nothing -> return (Result 1 1) + Just str -> do + putStrLn str + return (Result 0 1) + where + handler :: Expr -> IOException -> IO Expr + handler a exc = do + putStrLn $ "Caught " ++ show exc + putStrLn "Accepting the test" + wrt a + return a + +runFixtures :: [Fixture] -> IO () +runFixtures fixtures = do + results <- for fixtures $ \(Fixture i o) -> do + let name = takeBaseName i + let readDoc = do + input <- readFile i + return (parseString input) + ediffGolden goldenFixture name o readDoc + case foldl' combineResults (Result 0 0) results of + Result s t -> do + putStrLn $ "Fixtures: success " ++ show s ++ "; total " ++ show t + when (s /= t) exitFailure + +listFixtures :: [Fixture] -> IO () +listFixtures = traverse_ $ \(Fixture i _) -> do + let name = takeBaseName i + putStrLn name + +acceptFixtures :: [Fixture] -> IO () +acceptFixtures = traverse_ $ \(Fixture i o) -> do + input <- readFile i + let doc = parseString input + let actual = show (prettyExpr $ toExpr doc) ++ "\n" + writeFile o actual + +parseString :: String -> Doc String +parseString = Parse.toRegular . _doc . Parse.parseParas Nothing + +data Cmd = CmdRun | CmdAccept | CmdList + +main :: IO () +main = do + hSetBuffering stdout NoBuffering -- For interleaved output when debugging + runCmd =<< O.execParser opts + where + opts = O.info (O.helper <*> cmdParser) O.fullDesc + + cmdParser :: O.Parser Cmd + cmdParser = cmdRun <|> cmdAccept <|> cmdList <|> pure CmdRun + + cmdRun = O.flag' CmdRun $ mconcat + [ O.long "run" + , O.help "Run parser fixtures" + ] + + cmdAccept = O.flag' CmdAccept $ mconcat + [ O.long "accept" + , O.help "Run & accept parser fixtures" + ] + + cmdList = O.flag' CmdList $ mconcat + [ O.long "list" + , O.help "List fixtures" + ] + +runCmd :: Cmd -> IO () +runCmd CmdRun = readFixtures >>= runFixtures +runCmd CmdList = readFixtures >>= listFixtures +runCmd CmdAccept = readFixtures >>= acceptFixtures + +------------------------------------------------------------------------------- +-- Orphans +------------------------------------------------------------------------------- + +deriving instance Generic (DocH mod id) +instance (ToExpr mod, ToExpr id) => ToExpr (DocH mod id) + +deriving instance Generic (Header id) +instance ToExpr id => ToExpr (Header id) + +deriving instance Generic Hyperlink +instance ToExpr Hyperlink + +deriving instance Generic Picture +instance ToExpr Picture + +deriving instance Generic Example +instance ToExpr Example + +deriving instance Generic (Table id) +instance ToExpr id => ToExpr (Table id) + +deriving instance Generic (TableRow id) +instance ToExpr id => ToExpr (TableRow id) + +deriving instance Generic (TableCell id) +instance ToExpr id => ToExpr (TableCell id) diff --git a/haddock-library/fixtures/examples/definitionList.input b/haddock-library/fixtures/examples/definitionList.input new file mode 100644 index 00000000..e1bffb21 --- /dev/null +++ b/haddock-library/fixtures/examples/definitionList.input @@ -0,0 +1 @@ +[foo]: bar diff --git a/haddock-library/fixtures/examples/definitionList.parsed b/haddock-library/fixtures/examples/definitionList.parsed new file mode 100644 index 00000000..048aa141 --- /dev/null +++ b/haddock-library/fixtures/examples/definitionList.parsed @@ -0,0 +1 @@ +DocDefList [_×_ (DocString "foo") (DocString "bar")] diff --git a/haddock-library/fixtures/examples/identifier.input b/haddock-library/fixtures/examples/identifier.input new file mode 100644 index 00000000..c2c4af01 --- /dev/null +++ b/haddock-library/fixtures/examples/identifier.input @@ -0,0 +1 @@ +'foo' diff --git a/haddock-library/fixtures/examples/identifier.parsed b/haddock-library/fixtures/examples/identifier.parsed new file mode 100644 index 00000000..3405a5c9 --- /dev/null +++ b/haddock-library/fixtures/examples/identifier.parsed @@ -0,0 +1 @@ +DocParagraph (DocIdentifier "foo") diff --git a/haddock-library/fixtures/examples/identifierBackticks.input b/haddock-library/fixtures/examples/identifierBackticks.input new file mode 100644 index 00000000..347253a0 --- /dev/null +++ b/haddock-library/fixtures/examples/identifierBackticks.input @@ -0,0 +1 @@ +`foo` diff --git a/haddock-library/fixtures/examples/identifierBackticks.parsed b/haddock-library/fixtures/examples/identifierBackticks.parsed new file mode 100644 index 00000000..3405a5c9 --- /dev/null +++ b/haddock-library/fixtures/examples/identifierBackticks.parsed @@ -0,0 +1 @@ +DocParagraph (DocIdentifier "foo") diff --git a/haddock-library/fixtures/examples/link.input b/haddock-library/fixtures/examples/link.input new file mode 100644 index 00000000..a55c05a6 --- /dev/null +++ b/haddock-library/fixtures/examples/link.input @@ -0,0 +1 @@ +[link](http://example.com) diff --git a/haddock-library/fixtures/examples/link.parsed b/haddock-library/fixtures/examples/link.parsed new file mode 100644 index 00000000..0e85338c --- /dev/null +++ b/haddock-library/fixtures/examples/link.parsed @@ -0,0 +1,5 @@ +DocParagraph + (DocHyperlink + Hyperlink + {hyperlinkLabel = Just "link", + hyperlinkUrl = "http://example.com"}) diff --git a/haddock-library/fixtures/examples/linkInline.input b/haddock-library/fixtures/examples/linkInline.input new file mode 100644 index 00000000..eeca5a07 --- /dev/null +++ b/haddock-library/fixtures/examples/linkInline.input @@ -0,0 +1 @@ +Bla [link](http://example.com) diff --git a/haddock-library/fixtures/examples/linkInline.parsed b/haddock-library/fixtures/examples/linkInline.parsed new file mode 100644 index 00000000..43470d7b --- /dev/null +++ b/haddock-library/fixtures/examples/linkInline.parsed @@ -0,0 +1,6 @@ +DocParagraph + (DocAppend + (DocString "Bla ") + (DocHyperlink + Hyperlink + {hyperlinkLabel = Just "link", hyperlinkUrl = "http://example.com"})) diff --git a/haddock-library/fixtures/examples/table-simple.input b/haddock-library/fixtures/examples/table-simple.input new file mode 100644 index 00000000..d9c49f87 --- /dev/null +++ b/haddock-library/fixtures/examples/table-simple.input @@ -0,0 +1,7 @@ ++------+--------------+------------------------------------------+ +| code | message | description | ++======+==============+==========================================+ +| 200 | @OK@ | operation successful | ++------+--------------+------------------------------------------+ +| 204 | @No Content@ | operation successful, no body returned | ++------+--------------+------------------------------------------+ diff --git a/haddock-library/fixtures/examples/table-simple.parsed b/haddock-library/fixtures/examples/table-simple.parsed new file mode 100644 index 00000000..b5e62453 --- /dev/null +++ b/haddock-library/fixtures/examples/table-simple.parsed @@ -0,0 +1,52 @@ +DocTable + Table + {tableBodyRows = [TableRow + [TableCell + {tableCellColspan = 1, + tableCellContents = DocString " 200 ", + tableCellRowspan = 1}, + TableCell + {tableCellColspan = 1, + tableCellContents = DocAppend + (DocString " ") + (DocAppend + (DocMonospaced (DocString "OK")) + (DocString " ")), + tableCellRowspan = 1}, + TableCell + {tableCellColspan = 1, + tableCellContents = DocString + " operation successful ", + tableCellRowspan = 1}], + TableRow + [TableCell + {tableCellColspan = 1, + tableCellContents = DocString " 204 ", + tableCellRowspan = 1}, + TableCell + {tableCellColspan = 1, + tableCellContents = DocAppend + (DocString " ") + (DocAppend + (DocMonospaced (DocString "No Content")) + (DocString " ")), + tableCellRowspan = 1}, + TableCell + {tableCellColspan = 1, + tableCellContents = DocString + " operation successful, no body returned ", + tableCellRowspan = 1}]], + tableHeaderRows = [TableRow + [TableCell + {tableCellColspan = 1, + tableCellContents = DocString " code ", + tableCellRowspan = 1}, + TableCell + {tableCellColspan = 1, + tableCellContents = DocString " message ", + tableCellRowspan = 1}, + TableCell + {tableCellColspan = 1, + tableCellContents = DocString + " description ", + tableCellRowspan = 1}]]} diff --git a/haddock-library/fixtures/examples/table1.input b/haddock-library/fixtures/examples/table1.input new file mode 100644 index 00000000..a007020c --- /dev/null +++ b/haddock-library/fixtures/examples/table1.input @@ -0,0 +1,12 @@ ++------------------------+------------+----------+----------+ +| Header row, column 1 | Header 2 | Header 3 | Header 4 | +| (header rows optional) | | | | ++========================+============+==========+==========+ +| body row 1, column 1 | column 2 | column 3 | column 4 | ++------------------------+------------+----------+----------+ +| body row 2 | Cells may span columns. | ++------------------------+------------+---------------------+ +| body row 3 | Cells may | \[ | ++------------------------+ span rows. | f(n) = \sum_{i=1} | +| body row 4 | | \] | ++------------------------+------------+---------------------+ diff --git a/haddock-library/fixtures/examples/table1.parsed b/haddock-library/fixtures/examples/table1.parsed new file mode 100644 index 00000000..2fa58fd8 --- /dev/null +++ b/haddock-library/fixtures/examples/table1.parsed @@ -0,0 +1,81 @@ +DocTable + Table + {tableBodyRows = [TableRow + [TableCell + {tableCellColspan = 1, + tableCellContents = DocString " body row 1, column 1 ", + tableCellRowspan = 1}, + TableCell + {tableCellColspan = 1, + tableCellContents = DocString " column 2 ", + tableCellRowspan = 1}, + TableCell + {tableCellColspan = 1, + tableCellContents = DocString " column 3 ", + tableCellRowspan = 1}, + TableCell + {tableCellColspan = 1, + tableCellContents = DocString " column 4 ", + tableCellRowspan = 1}], + TableRow + [TableCell + {tableCellColspan = 1, + tableCellContents = DocString " body row 2 ", + tableCellRowspan = 1}, + TableCell + {tableCellColspan = 3, + tableCellContents = DocString " Cells may span columns. ", + tableCellRowspan = 1}], + TableRow + [TableCell + {tableCellColspan = 1, + tableCellContents = DocString " body row 3 ", + tableCellRowspan = 1}, + TableCell + {tableCellColspan = 1, + tableCellContents = DocString + (concat + [" Cells may \n", + " span rows. \n", + " "]), + tableCellRowspan = 2}, + TableCell + {tableCellColspan = 2, + tableCellContents = DocAppend + (DocString " ") + (DocAppend + (DocMathDisplay + (concat + [" \n", + " f(n) = \\sum_{i=1} \n", + " "])) + (DocString " ")), + tableCellRowspan = 2}], + TableRow + [TableCell + {tableCellColspan = 1, + tableCellContents = DocString " body row 4 ", + tableCellRowspan = 1}]], + tableHeaderRows = [TableRow + [TableCell + {tableCellColspan = 1, + tableCellContents = DocString + (concat + [" Header row, column 1 \n", + " (header rows optional) "]), + tableCellRowspan = 1}, + TableCell + {tableCellColspan = 1, + tableCellContents = DocString + (concat [" Header 2 \n", " "]), + tableCellRowspan = 1}, + TableCell + {tableCellColspan = 1, + tableCellContents = DocString + (concat [" Header 3 \n", " "]), + tableCellRowspan = 1}, + TableCell + {tableCellColspan = 1, + tableCellContents = DocString + (concat [" Header 4 \n", " "]), + tableCellRowspan = 1}]]} diff --git a/haddock-library/fixtures/examples/table2.input b/haddock-library/fixtures/examples/table2.input new file mode 100644 index 00000000..aa5d0862 --- /dev/null +++ b/haddock-library/fixtures/examples/table2.input @@ -0,0 +1,7 @@ ++--------------+----------+-----------+-----------+ +| row 1, col 1 | column 2 | column 3 | column 4 | ++--------------+----------+-----------+-----------+ +| row 2 | | ++--------------+----------+-----------+-----------+ +| row 3 | | | | ++--------------+----------+-----------+-----------+ diff --git a/haddock-library/fixtures/examples/table2.parsed b/haddock-library/fixtures/examples/table2.parsed new file mode 100644 index 00000000..e3dbf0b4 --- /dev/null +++ b/haddock-library/fixtures/examples/table2.parsed @@ -0,0 +1,46 @@ +DocTable + Table + {tableBodyRows = [TableRow + [TableCell + {tableCellColspan = 1, + tableCellContents = DocString " row 1, col 1 ", + tableCellRowspan = 1}, + TableCell + {tableCellColspan = 1, + tableCellContents = DocString " column 2 ", + tableCellRowspan = 1}, + TableCell + {tableCellColspan = 1, + tableCellContents = DocString " column 3 ", + tableCellRowspan = 1}, + TableCell + {tableCellColspan = 1, + tableCellContents = DocString " column 4 ", + tableCellRowspan = 1}], + TableRow + [TableCell + {tableCellColspan = 1, + tableCellContents = DocString " row 2 ", + tableCellRowspan = 1}, + TableCell + {tableCellColspan = 3, + tableCellContents = DocString " ", + tableCellRowspan = 1}], + TableRow + [TableCell + {tableCellColspan = 1, + tableCellContents = DocString " row 3 ", + tableCellRowspan = 1}, + TableCell + {tableCellColspan = 1, + tableCellContents = DocString " ", + tableCellRowspan = 1}, + TableCell + {tableCellColspan = 1, + tableCellContents = DocString " ", + tableCellRowspan = 1}, + TableCell + {tableCellColspan = 1, + tableCellContents = DocString " ", + tableCellRowspan = 1}]], + tableHeaderRows = []} diff --git a/haddock-library/fixtures/examples/table3.input b/haddock-library/fixtures/examples/table3.input new file mode 100644 index 00000000..a6ca84ca --- /dev/null +++ b/haddock-library/fixtures/examples/table3.input @@ -0,0 +1,7 @@ ++--------------+----------+-----------+-----------+ +| row 1, col 1 | column 2 | column 3 | column 4 | ++--------------+----------+-----------+-----------+ +| row 2 | Use the command ``ls | more``. | ++--------------+----------+-----------+-----------+ +| row 3 | | | | ++--------------+----------+-----------+-----------+ diff --git a/haddock-library/fixtures/examples/table3.parsed b/haddock-library/fixtures/examples/table3.parsed new file mode 100644 index 00000000..cabff9cb --- /dev/null +++ b/haddock-library/fixtures/examples/table3.parsed @@ -0,0 +1,50 @@ +DocTable + Table + {tableBodyRows = [TableRow + [TableCell + {tableCellColspan = 1, + tableCellContents = DocString " row 1, col 1 ", + tableCellRowspan = 1}, + TableCell + {tableCellColspan = 1, + tableCellContents = DocString " column 2 ", + tableCellRowspan = 1}, + TableCell + {tableCellColspan = 1, + tableCellContents = DocString " column 3 ", + tableCellRowspan = 1}, + TableCell + {tableCellColspan = 1, + tableCellContents = DocString " column 4 ", + tableCellRowspan = 1}], + TableRow + [TableCell + {tableCellColspan = 1, + tableCellContents = DocString " row 2 ", + tableCellRowspan = 1}, + TableCell + {tableCellColspan = 2, + tableCellContents = DocString " Use the command ``ls ", + tableCellRowspan = 1}, + TableCell + {tableCellColspan = 1, + tableCellContents = DocString " more``. ", + tableCellRowspan = 1}], + TableRow + [TableCell + {tableCellColspan = 1, + tableCellContents = DocString " row 3 ", + tableCellRowspan = 1}, + TableCell + {tableCellColspan = 1, + tableCellContents = DocString " ", + tableCellRowspan = 1}, + TableCell + {tableCellColspan = 1, + tableCellContents = DocString " ", + tableCellRowspan = 1}, + TableCell + {tableCellColspan = 1, + tableCellContents = DocString " ", + tableCellRowspan = 1}]], + tableHeaderRows = []} diff --git a/haddock-library/fixtures/examples/table4.input b/haddock-library/fixtures/examples/table4.input new file mode 100644 index 00000000..2c5611c8 --- /dev/null +++ b/haddock-library/fixtures/examples/table4.input @@ -0,0 +1,17 @@ +Single outer cell: + ++-------------+ +| outer | +| | ++-------+ | +| inner | | ++-------+-----+ + +Broken (only inner cell is rendered): + ++-------+-----+ +| inner | | ++-------+ | +| | +| outer | ++-------------+ diff --git a/haddock-library/fixtures/examples/table4.parsed b/haddock-library/fixtures/examples/table4.parsed new file mode 100644 index 00000000..cfdd6f0f --- /dev/null +++ b/haddock-library/fixtures/examples/table4.parsed @@ -0,0 +1,26 @@ +DocAppend + (DocParagraph (DocString "Single outer cell:")) + (DocAppend + (DocTable + Table + {tableBodyRows = [TableRow + [TableCell + {tableCellColspan = 1, + tableCellContents = DocString + (concat + [" outer \n", + " \n", + "-------+ \n", + " inner | "]), + tableCellRowspan = 1}]], + tableHeaderRows = []}) + (DocAppend + (DocParagraph (DocString "Broken (only inner cell is rendered):")) + (DocTable + Table + {tableBodyRows = [TableRow + [TableCell + {tableCellColspan = 1, + tableCellContents = DocString " inner ", + tableCellRowspan = 1}]], + tableHeaderRows = []}))) diff --git a/haddock-library/fixtures/examples/table5.input b/haddock-library/fixtures/examples/table5.input new file mode 100644 index 00000000..7cf26512 --- /dev/null +++ b/haddock-library/fixtures/examples/table5.input @@ -0,0 +1,8 @@ ++--------------+----------+-----------+-----------+ +| row 1, col 1 | column 2 | column 3 | column 4 | ++==============+==========+===========+===========+ +| row 2 | Use the command @ls | more@. | +| | | +| +----------+-----------+-----------+ +| row 3 | | | | ++--------------+----------+-----------+-----------+ diff --git a/haddock-library/fixtures/examples/table5.parsed b/haddock-library/fixtures/examples/table5.parsed new file mode 100644 index 00000000..9a547ad3 --- /dev/null +++ b/haddock-library/fixtures/examples/table5.parsed @@ -0,0 +1,53 @@ +DocTable + Table + {tableBodyRows = [TableRow + [TableCell + {tableCellColspan = 1, + tableCellContents = DocString + (concat + [" row 2 \n", + " \n", + " \n", + " row 3 "]), + tableCellRowspan = 2}, + TableCell + {tableCellColspan = 3, + tableCellContents = DocAppend + (DocString " Use the command ") + (DocAppend + (DocMonospaced (DocString "ls | more")) + (DocString + (concat + [". \n", + " "]))), + tableCellRowspan = 1}], + TableRow + [TableCell + {tableCellColspan = 1, + tableCellContents = DocString " ", + tableCellRowspan = 1}, + TableCell + {tableCellColspan = 1, + tableCellContents = DocString " ", + tableCellRowspan = 1}, + TableCell + {tableCellColspan = 1, + tableCellContents = DocString " ", + tableCellRowspan = 1}]], + tableHeaderRows = [TableRow + [TableCell + {tableCellColspan = 1, + tableCellContents = DocString " row 1, col 1 ", + tableCellRowspan = 1}, + TableCell + {tableCellColspan = 1, + tableCellContents = DocString " column 2 ", + tableCellRowspan = 1}, + TableCell + {tableCellColspan = 1, + tableCellContents = DocString " column 3 ", + tableCellRowspan = 1}, + TableCell + {tableCellColspan = 1, + tableCellContents = DocString " column 4 ", + tableCellRowspan = 1}]]} diff --git a/haddock-library/fixtures/examples/url.input b/haddock-library/fixtures/examples/url.input new file mode 100644 index 00000000..5bfed0a1 --- /dev/null +++ b/haddock-library/fixtures/examples/url.input @@ -0,0 +1 @@ +<http://example.com/> diff --git a/haddock-library/fixtures/examples/url.parsed b/haddock-library/fixtures/examples/url.parsed new file mode 100644 index 00000000..0fbbbb30 --- /dev/null +++ b/haddock-library/fixtures/examples/url.parsed @@ -0,0 +1,4 @@ +DocParagraph + (DocHyperlink + Hyperlink + {hyperlinkLabel = Nothing, hyperlinkUrl = "http://example.com/"}) diff --git a/haddock-library/fixtures/examples/urlLabel.input b/haddock-library/fixtures/examples/urlLabel.input new file mode 100644 index 00000000..729812e8 --- /dev/null +++ b/haddock-library/fixtures/examples/urlLabel.input @@ -0,0 +1 @@ +<http://example.com/ some link> diff --git a/haddock-library/fixtures/examples/urlLabel.parsed b/haddock-library/fixtures/examples/urlLabel.parsed new file mode 100644 index 00000000..d7e3a76c --- /dev/null +++ b/haddock-library/fixtures/examples/urlLabel.parsed @@ -0,0 +1,5 @@ +DocParagraph + (DocHyperlink + Hyperlink + {hyperlinkLabel = Just "some link", + hyperlinkUrl = "http://example.com/"}) |