{-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE QuasiQuotes #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TypeFamilies #-} module YesodCoreTest.JsAttributes ( specs -- To avoid unused warning , Widget , resourcesApp ) where import Test.Hspec import Yesod.Core import Network.Wai.Test data App = App mkYesod "App" [parseRoutes| / HeadR GET |] instance Yesod App where jsAttributes _ = [("attr0", "a")] getHeadR :: Handler Html getHeadR = defaultLayout $ do addScriptRemote "load.js" toWidget [julius|/*body*/|] toWidgetHead [julius|/*head*/|] specs :: Spec specs = describe "Test.JsAttributes" $ do it "script in body gets attributes" $ runner App $ do res <- request defaultRequest assertBody "\n