{-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE OverloadedStrings #-} import Control.Monad import Control.Monad.Trans.Resource import Data.Char import Data.Conduit import Data.Conduit.List import Data.Default import Data.Functor.Identity import Data.Monoid import Data.MonoTraversable import Data.NonNull import Data.Text as Text import Data.Text.Encoding as Text import Data.Time.Clock import Data.XML.Types import Lens.Simple import qualified Language.Haskell.HLint as HLint (hlint) import Test.QuickCheck.Instances import Test.Tasty import Test.Tasty.HUnit import Test.Tasty.QuickCheck import Text.Atom.Conduit.Parse as Parser import Text.Atom.Conduit.Render as Renderer import Text.Atom.Lens import Text.Atom.Types import Text.Parser.Combinators import qualified Text.XML.Stream.Parse as XML import URI.ByteString main :: IO () main = defaultMain $ testGroup "Tests" [ unitTests -- , properties , hlint ] unitTests :: TestTree unitTests = testGroup "Unit tests" [ linkCase , personCase , generatorCase , sourceCase , textConstructCase , simpleCase ] properties :: TestTree properties = testGroup "Properties" [ roundtripAtomTextProperty , roundtripAtomPersonProperty , roundtripAtomCategoryProperty , roundtripAtomLinkProperty , roundtripAtomGeneratorProperty , roundtripAtomSourceProperty , roundtripAtomContentProperty -- , roundtripAtomEntryProperty -- , roundtripAtomFeedProperty ] linkCase :: TestTree linkCase = testCase "Link element" $ do result <- runResourceT . runConduit $ sourceList input =$= XML.parseText' def =$= XML.force "Invalid " atomLink result ^. linkHrefL @?= AtomURI (RelativeRef Nothing "/feed" (Query []) Nothing) (result ^. linkRelL) @?= "self" where input = [""] personCase :: TestTree personCase = testCase "Person construct" $ do result <- runResourceT . runConduit $ sourceList input =$= XML.parseText' def =$= XML.force "Invalid " (atomPerson "author") toNullable (result ^. personNameL) @?= "John Doe" result ^. personEmailL @?= "JohnDoe@example.com" result ^. personUriL @?= Just (AtomURI $ URI (Scheme "http") (Just $ Authority Nothing (Host "example.com") Nothing) "/~johndoe" (Query []) Nothing) where input = [ "" , "John Doe" , "JohnDoe@example.com" , "http://example.com/~johndoe" , "" ] generatorCase :: TestTree generatorCase = testCase "Generator element" $ do result <- runResourceT . runConduit $ sourceList input =$= XML.parseText' def =$= XML.force "Invalid " atomGenerator result ^. generatorUriL @?= Just (AtomURI $ RelativeRef Nothing "/myblog.php" (Query []) Nothing) (result ^. generatorVersionL) @?= "1.0" toNullable (result ^. generatorContentL) @?= "Example Toolkit" where input = [ "" , "Example Toolkit" , "" ] sourceCase :: TestTree sourceCase = testCase "Source element" $ do result <- runResourceT . runConduit $ sourceList input =$= XML.parseText' def =$= XML.force "Invalid " atomSource (result ^. sourceIdL) @?= "http://example.org/" (result ^. sourceTitleL) @?= Just (AtomPlainText TypeText "Fourty-Two") show <$> (result ^. sourceUpdatedL) @?= Just "2003-12-13 18:30:02 UTC" (result ^. sourceRightsL) @?= Just (AtomPlainText TypeText "© 2005 Example, Inc.") where input = [ "" , "http://example.org/" , "Fourty-Two" , "2003-12-13T18:30:02Z" , "© 2005 Example, Inc." , "" ] textConstructCase :: TestTree textConstructCase = testCase "Text construct" $ do a:b:c:_ <- runResourceT . runConduit $ sourceList input =$= XML.parseText' def =$= XML.many (atomText "title") a @?= AtomPlainText TypeText "AT&T bought by SBC!" b @?= AtomPlainText TypeHTML "AT&T bought by SBC!" c @?= AtomXHTMLText "AT&T bought by SBC!" where input = [ "AT&T bought by SBC!" , "" , "AT&amp;T bought <b>by SBC</b>!" , "" , "" , "<div xmlns=\"http://www.w3.org/1999/xhtml\">" , "AT&T bought <b><em>by SBC</em></b>!" , "</div>" , "" ] simpleCase :: TestTree simpleCase = testCase "Simple case" $ do result <- runResourceT . runConduit $ sourceList input =$= XML.parseText' def =$= XML.force "Invalid " atomFeed return () where input = [ "" , "" , "<em>Example</em> Feed" , "" , "2003-12-13T18:30:02Z" , "" , "John Doe" , "" , "urn:uuid:60a76c80-d399-11d9-b93C-0003939e0af6" , "" , "Atom-Powered Robots Run Amok" , "" , "urn:uuid:1225c695-cfb8-4ebb-aaaa-80da344efa6a" , "2003-12-13T18:30:02Z" , "Some text." , "" , "" ] hlint :: TestTree hlint = testCase "HLint check" $ do result <- HLint.hlint [ "test/", "Text/" ] Prelude.null result @?= True roundtripAtomTextProperty :: TestTree roundtripAtomTextProperty = testProperty "parse . render = id (AtomText)" $ \i -> either (const False) (Just i ==) (runConduit $ renderAtomText "test" i =$= atomText "test") roundtripAtomPersonProperty :: TestTree roundtripAtomPersonProperty = testProperty "parse . render = id (AtomPerson)" $ \i -> either (const False) (i ==) (runConduit $ renderAtomPerson "test" i =$= XML.force "Invalid " (atomPerson "test")) roundtripAtomCategoryProperty :: TestTree roundtripAtomCategoryProperty = testProperty "parse . render = id (AtomCategory)" $ \i -> either (const False) (i ==) (runConduit $ renderAtomCategory i =$= XML.force "Invalid " atomCategory) roundtripAtomLinkProperty :: TestTree roundtripAtomLinkProperty = testProperty "parse . render = id (AtomLink)" $ \i -> either (const False) (i ==) (runConduit $ renderAtomLink i =$= XML.force "Invalid " atomLink) roundtripAtomGeneratorProperty :: TestTree roundtripAtomGeneratorProperty = testProperty "parse . render = id (AtomGenerator)" $ \i -> either (const False) (i ==) (runConduit $ renderAtomGenerator i =$= XML.force "Invalid " atomGenerator) roundtripAtomSourceProperty :: TestTree roundtripAtomSourceProperty = testProperty "parse . render = id (AtomSource)" $ \i -> either (const False) (i ==) (runConduit $ renderAtomSource i =$= XML.force "Invalid " atomSource) roundtripAtomContentProperty :: TestTree roundtripAtomContentProperty = testProperty "parse . render = id (AtomContent)" $ \i -> either (const False) (i ==) (runConduit $ renderAtomContent i =$= XML.force "Invalid content" atomContent) roundtripAtomFeedProperty :: TestTree roundtripAtomFeedProperty = testProperty "parse . render = id (AtomFeed)" $ \i -> either (const False) (i ==) (runConduit $ renderAtomFeed i =$= XML.force "Invalid " atomFeed) roundtripAtomEntryProperty :: TestTree roundtripAtomEntryProperty = testProperty "parse . render = id (AtomEntry)" $ \i -> either (const False) (i ==) (runConduit $ renderAtomEntry i =$= XML.force "Invalid " atomEntry) letter = choose ('a', 'z') digit = arbitrary `suchThat` isDigit alphaNum = oneof [letter, digit] instance (MonoFoldable a, Arbitrary a) => Arbitrary (NonNull a) where arbitrary = impureNonNull <$> arbitrary `suchThat` (not . onull) instance Arbitrary Scheme where arbitrary = do a <- letter b <- listOf $ oneof [letter, digit, pure '+', pure '-', pure '.'] return $ Scheme $ encodeUtf8 $ pack (a:b) instance Arbitrary Authority where arbitrary = Authority <$> arbitrary <*> arbitrary <*> arbitrary shrink = genericShrink instance Arbitrary UserInfo where arbitrary = UserInfo <$> (encodeUtf8 . pack <$> listOf1 alphaNum) <*> (encodeUtf8 . pack <$> listOf1 alphaNum) instance Arbitrary Host where arbitrary = Host <$> (encodeUtf8 . pack <$> listOf1 alphaNum) instance Arbitrary Port where arbitrary = Port <$> (getPositive <$> arbitrary) instance Arbitrary Query where arbitrary = Query <$> listOf ((,) <$> (encodeUtf8 . pack <$> listOf1 alphaNum) <*> (encodeUtf8 . pack <$> listOf1 alphaNum)) instance Arbitrary URI where arbitrary = URI <$> arbitrary <*> arbitrary <*> (encodeUtf8 . pack . ('/' :) <$> listOf1 alphaNum) <*> arbitrary <*> oneof [pure Nothing, Just <$> (encodeUtf8 . pack <$> listOf1 alphaNum)] instance Arbitrary AtomURI where arbitrary = oneof [AtomURI <$> (arbitrary :: Gen (URIRef Absolute)), AtomURI <$> (arbitrary :: Gen (URIRef Relative))] instance Arbitrary RelativeRef where arbitrary = RelativeRef <$> arbitrary <*> (encodeUtf8 . pack . ('/' :) <$> listOf1 alphaNum) <*> arbitrary <*> oneof [pure Nothing, Just <$> (encodeUtf8 . pack <$> listOf1 alphaNum)] instance Arbitrary TextType where arbitrary = elements [TypeText, TypeHTML] instance Arbitrary AtomText where arbitrary = oneof [ AtomPlainText <$> arbitrary <*> (pack <$> listOf1 alphaNum) , AtomXHTMLText <$> (pack <$> listOf1 alphaNum) ] shrink = genericShrink instance Arbitrary AtomPerson where arbitrary = AtomPerson <$> arbitrary <*> arbitrary <*> arbitrary instance Arbitrary AtomCategory where arbitrary = AtomCategory <$> arbitrary <*> arbitrary <*> arbitrary instance Arbitrary AtomLink where arbitrary = AtomLink <$> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary instance Arbitrary AtomGenerator where arbitrary = do Just content <- fromNullable . pack <$> listOf1 alphaNum AtomGenerator <$> arbitrary <*> arbitrary <*> pure content shrink = genericShrink instance Arbitrary AtomSource where arbitrary = do updated <- oneof [return Nothing, Just <$> genUtcTime] AtomSource <$> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary <*> pure updated instance Arbitrary AtomContent where arbitrary = oneof [ AtomContentInlineText <$> arbitrary <*> arbitrary , AtomContentInlineXHTML <$> arbitrary , AtomContentInlineOther <$> arbitrary <*> arbitrary , AtomContentOutOfLine <$> arbitrary <*> arbitrary ] instance Arbitrary AtomEntry where arbitrary = do published <- oneof [return Nothing, Just <$> genUtcTime] AtomEntry <$> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary <*> pure published <*> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary <*> genUtcTime instance Arbitrary AtomFeed where arbitrary = AtomFeed <$> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary <*> genUtcTime -- | Generates 'UTCTime' with rounded seconds. genUtcTime = do (UTCTime d s) <- arbitrary return $ UTCTime d (fromIntegral (round s :: Int))