tests and better docs for jsLoader

This commit is contained in:
Greg Weber 2012-02-16 16:11:10 -08:00
parent 5b75d6758a
commit 9b8b20e058
5 changed files with 79 additions and 1 deletions

View File

@ -323,7 +323,10 @@ class RenderRoute a => Yesod a where
yepnopeJs _ = Nothing
-- | Where to Load sripts from. We recommend changing this to 'BottomOfBody'
-- Alternatively use the built in async yepnope loader: BottomOfHeadAsync (loadJsYepnope eyn)
-- Alternatively use the built in async yepnope loader:
--
-- > BottomOfHeadAsync $ loadJsYepnope $ Right $ StaticR js_modernizr_js
--
-- Or write your own async js loader: see 'loadJsYepnope'
jsLoader :: a -> ScriptLoadPosition a
jsLoader y = case yepnopeJs y of

View File

@ -10,6 +10,7 @@ import YesodCoreTest.InternalRequest
import YesodCoreTest.ErrorHandling
import YesodCoreTest.Cache
import qualified YesodCoreTest.Redirect as Redirect
import qualified YesodCoreTest.JsLoader as JsLoader
import Test.Hspec
@ -25,4 +26,5 @@ specs =
, errorHandlingTest
, cacheTest
, Redirect.specs
, JsLoader.specs
]

View File

@ -0,0 +1,40 @@
{-# LANGUAGE QuasiQuotes, TypeFamilies, TemplateHaskell, MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE FlexibleInstances #-}
module YesodCoreTest.JsLoader (specs) where
import YesodCoreTest.JsLoaderSites.HeadAsync (HA(..))
import YesodCoreTest.JsLoaderSites.Bottom (B(..))
import Test.Hspec
import Test.Hspec.HUnit ()
import Yesod.Core hiding (Request)
import Network.Wai.Test
data H = H
mkYesod "H" [parseRoutes|
/ HeadR GET
|]
instance Yesod H
getHeadR :: Handler RepHtml
getHeadR = defaultLayout $ addScriptRemote "load.js"
specs :: [Spec]
specs = describe "Test.Links" [
it "link from head" $ runner H $ do
res <- request defaultRequest
assertBody "<!DOCTYPE html>\n<html><head><title></title><script src=\"load.js\"></script></head><body></body></html>" res
, it "link from head async" $ runner HA $ do
res <- request defaultRequest
assertBody "<!DOCTYPE html>\n<html><head><title></title><script src=\"yepnope.js\"></script><script>yepnope({load:[\"load.js\"]});</script></head><body></body></html>" res
, it "link from bottom" $ runner B $ do
res <- request defaultRequest
assertBody "<!DOCTYPE html>\n<html><head><title></title></head><body><script src=\"load.js\"></script></body></html>" res
]
runner :: (YesodDispatch master master, Yesod master) => master -> Session () -> IO ()
runner app f = toWaiApp app >>= runSession f

View File

@ -0,0 +1,17 @@
{-# LANGUAGE QuasiQuotes, TypeFamilies, TemplateHaskell, MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE FlexibleInstances #-}
module YesodCoreTest.JsLoaderSites.Bottom (B(..)) where
import Yesod.Core
data B = B
mkYesod "B" [parseRoutes|
/ BottomR GET
|]
instance Yesod B where
jsLoader _ = BottomOfBody
getBottomR :: Handler RepHtml
getBottomR = defaultLayout $ addScriptRemote "load.js"

View File

@ -0,0 +1,16 @@
{-# LANGUAGE QuasiQuotes, TypeFamilies, TemplateHaskell, MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE FlexibleInstances #-}
module YesodCoreTest.JsLoaderSites.HeadAsync (HA(..)) where
import Yesod.Core
data HA = HA
mkYesod "HA" [parseRoutes|
/ HeadAsyncR GET
|]
instance Yesod HA where
jsLoader _ = BottomOfHeadAsync $ loadJsYepnope $ Left "yepnope.js"
getHeadAsyncR :: Handler RepHtml
getHeadAsyncR = defaultLayout $ addScriptRemote "load.js"