{-# LANGUAGE OverloadedStrings #-} module UriSpec where import Control.Lens import Data.Default import Test.Hspec import LuminescentDreams.Data.URI uriSpec :: Spec uriSpec = describe "verify parsing and generation of URIs" $ do it "should render an empty URI" $ renderURI def `shouldBe` "" it "should render a simple URI" $ let uri = (uriProtocol .~ "http") $ (uriFqdn .~ "localhost") $ (uriPathParts .~ PathParts ["web", "elsewhere"]) def in renderURI uri `shouldBe` "http://localhost/web/elsewhere" it "should render a simple URI with a port number" $ let uri = (uriProtocol .~ "http") $ (uriFqdn .~ "localhost") $ (uriPort .~ Just 8080) $ (uriPathParts .~ PathParts ["web", "elsewhere"]) def in renderURI uri `shouldBe` "http://localhost:8080/web/elsewhere" it "renders a URI using uriPath lens" $ let uri = (uriProtocol .~ "http") $ (uriFqdn .~ "localhost") $ (uriPort .~ Just 8080) $ (uriPath .~ "web/elsewhere") def in renderURI uri `shouldBe` "http://localhost:8080/web/elsewhere" it "renders a URI using uriPath lens and a leading /" $ let uri = (uriProtocol .~ "http") $ (uriFqdn .~ "localhost") $ (uriPort .~ Just 8080) $ (uriPath .~ "/web/elsewhere") def in renderURI uri `shouldBe` "http://localhost:8080/web/elsewhere" it "should parse a URI without a path" $ let uri = (uriProtocol .~ "http") $ (uriFqdn .~ "localhost") def in parseURI "http://localhost/" `shouldBe` Right uri it "should parse a simple URI" $ let uri = (uriProtocol .~ "http") $ (uriFqdn .~ "localhost") $ (uriPath .~ "/web/elsewhere") def in parseURI "http://localhost/web/elsewhere" `shouldBe` Right uri it "should parse a URI with a port number" $ let uri = (uriProtocol .~ "http") $ (uriFqdn .~ "localhost") $ (uriPort .~ Just 8080) $ (uriPath .~ "/web/elsewhere") def in parseURI "http://localhost:8080/web/elsewhere" `shouldBe` Right uri it "should parse a URI with a port number" $ let uri = (uriProtocol .~ "http") $ (uriFqdn .~ "localhost") $ (uriPort .~ Just 8080) $ (uriPathParts .~ PathParts ["web", "elsewhere"]) def in parseURI "http://localhost:8080/web/elsewhere" `shouldBe` Right uri spec :: Spec spec = uriSpec