pandoc/test/Tests/Shared.hs
Albert Krewinkel 37a82b0b11 Add missing copyright notices and remove license boilerplate (#5112)
Quite a few modules were missing copyright notices.

This commit adds copyright notices everywhere via haddock module
headers.  The old license boilerplate comment is redundant with this and has
been removed.

Update copyright years to 2019.

Closes #4592.
2019-02-04 13:52:31 -08:00

52 lines
2.4 KiB
Haskell

{-# LANGUAGE NoImplicitPrelude #-}
{- |
Module : Tests.Shared
Copyright : © 2006-2019 John MacFarlane
License : GNU GPL, version 2 or above
Maintainer : John MacFarlane <jgm@berkeley@edu>
Stability : alpha
Portability : portable
Tests for functions used in many parts of the library.
-}
module Tests.Shared (tests) where
import Prelude
import System.FilePath.Posix (joinPath)
import Test.Tasty
import Test.Tasty.HUnit (assertBool, testCase, (@?=))
import Text.Pandoc.Arbitrary ()
import Text.Pandoc.Builder
import Text.Pandoc.Shared
tests :: [TestTree]
tests = [ testGroup "compactifyDL"
[ testCase "compactifyDL with empty def" $
assertBool "compactifyDL"
(let x = [(str "word", [para (str "def"), mempty])]
in compactifyDL x == x)
]
, testGroup "collapseFilePath" testCollapse
]
testCollapse :: [TestTree]
testCollapse = map (testCase "collapse")
[ collapseFilePath (joinPath [ ""]) @?= (joinPath [ ""])
, collapseFilePath (joinPath [ ".","foo"]) @?= (joinPath [ "foo"])
, collapseFilePath (joinPath [ ".",".","..","foo"]) @?= (joinPath [ joinPath ["..", "foo"]])
, collapseFilePath (joinPath [ "..","foo"]) @?= (joinPath [ "..","foo"])
, collapseFilePath (joinPath [ "","bar","..","baz"]) @?= (joinPath [ "","baz"])
, collapseFilePath (joinPath [ "","..","baz"]) @?= (joinPath [ "","..","baz"])
, collapseFilePath (joinPath [ ".","foo","..",".","bar","..",".",".","baz"]) @?= (joinPath [ "baz"])
, collapseFilePath (joinPath [ ".",""]) @?= (joinPath [ ""])
, collapseFilePath (joinPath [ ".",".",""]) @?= (joinPath [ ""])
, collapseFilePath (joinPath [ "..",""]) @?= (joinPath [ ".."])
, collapseFilePath (joinPath [ "..",".",""]) @?= (joinPath [ ".."])
, collapseFilePath (joinPath [ ".","..",""]) @?= (joinPath [ ".."])
, collapseFilePath (joinPath [ "..","..",""]) @?= (joinPath [ "..",".."])
, collapseFilePath (joinPath [ "parent","foo","baz","..","bar"]) @?= (joinPath [ "parent","foo","bar"])
, collapseFilePath (joinPath [ "parent","foo","baz","..","..","bar"]) @?= (joinPath [ "parent","bar"])
, collapseFilePath (joinPath [ "parent","foo",".."]) @?= (joinPath [ "parent"])
, collapseFilePath (joinPath [ "","parent","foo","..","..","bar"]) @?= (joinPath [ "","bar"])
, collapseFilePath (joinPath [ "",".","parent","foo"]) @?= (joinPath [ "","parent","foo"])]