{-# LANGUAGE QuasiQuotes, OverloadedStrings, UnicodeSyntax, CPP #-} module Data.IndieWeb.AuthorshipSpec (spec) where #if !MIN_VERSION_base(4,8,0) import Control.Applicative #endif import Test.Hspec hiding (shouldBe) import Test.Hspec.Expectations.Pretty (shouldBe) import TestCommon import Network.URI import qualified Data.ByteString.Lazy as LB import Data.Functor.Identity import Data.Maybe import Data.Aeson.Lens import Control.Lens ((^?), _Just, _head) import Data.Microformats2.Parser import Data.IndieWeb.Authorship import Data.IndieWeb.MicroformatsUtil spec ∷ Spec spec = do describe "findAuthors" $ do let mockFetch ∷ URI → Identity (Maybe LB.ByteString) mockFetch "http://direct" = return $ Just [xml|

Author from Direct!|] mockFetch "http://link" = return $ Just [xml|
http://author/page|] mockFetch "http://link-relme" = return $ Just [xml|
http://author/page-relme|] mockFetch "http://link-only-url" = return $ Just [xml|
http://author/page-only-url|] mockFetch "http://link-not-only-url" = return $ Just [xml|
http://author/page-not-only-url|] mockFetch "http://rel" = return $ Just [xml|
|] mockFetch "http://author/page/link-relative" = return $ Just [xml|
/page|] mockFetch "http://feed" = return $ Just [xml|

Author from Feed!

|] mockFetch "http://feed/link" = return $ Just [xml|
http://author/page
|] mockFetch "http://author/page" = return $ Just [xml|

Author from Page!|] mockFetch "http://author/page-relme" = return $ Just [xml|

Author from Page-relme!|] mockFetch "http://author/page-only-url" = return $ Just [xml|