yesod/yesod-core/test/YesodCoreTest/Meta.hs
Isaac van Bakel b9fbdb3950 Add idempotent versions of setDescription API
`setDescription` and `setDescriptionI` present a similar API to
`setTitle` and `setTitleI`, but unlike those functions the description
functions are not idempotent - so calling them multiple times inserts
multiple `<meta/>` tags in HTML `<head/>`.

This adds explicitly idempotent versions of those functions which are
handled in a similar way to the title, so that calling them multiple
times has the effect of taking the final value specified.

Because the non-idempotent behaviour of setDescription is not obvious,
this also adds warnings for that behaviour to make it clear what the
effect of multiple calls will be. Unfortunately, setDescriptionIdemp
can't be made a drop-in replacement because developers may have defined
their own layouts which need to take pageDescription into account.
2022-04-20 12:54:23 +01:00

55 lines
1.5 KiB
Haskell

{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE ViewPatterns #-}
module YesodCoreTest.Meta
( metaTest
) where
import Test.Hspec
import Yesod.Core
import Network.Wai
import Network.Wai.Test
data App = App
mkYesod "App" [parseRoutes|
/title TitleR GET
/desc DescriptionR GET
|]
instance Yesod App where
getTitleR :: Handler Html
getTitleR = defaultLayout $ do
setTitle "First title"
setTitle "Second title"
getDescriptionR :: Handler Html
getDescriptionR = defaultLayout $ do
setDescriptionIdemp "First description"
setDescriptionIdemp "Second description"
metaTest :: Spec
metaTest = describe "Setting page metadata" $ do
describe "Yesod.Core.Widget.setTitle" $ do
it "is idempotent" $ runner $ do
res <- request defaultRequest
{ pathInfo = ["title"]
}
assertBody "<!DOCTYPE html>\n<html><head><title>Second title</title></head><body></body></html>" res
describe "Yesod.Core.Widget.setDescriptionIdemp" $ do
it "is idempotent" $ runner $ do
res <- request defaultRequest
{ pathInfo = ["desc"]
}
assertBody "<!DOCTYPE html>\n<html><head><title></title><meta type=\"description\" content=\"Second description\"></head><body></body></html>" res
runner :: Session () -> IO ()
runner f = toWaiAppPlain App >>= runSession f