File: ParameterizedSite.hs

package info (click to toggle)
haskell-yesod-core 1.6.26.0-1
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 672 kB
  • sloc: haskell: 7,833; makefile: 5
file content (37 lines) | stat: -rw-r--r-- 1,392 bytes parent folder | download | duplicates (2)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
{-# LANGUAGE OverloadedStrings #-}
module YesodCoreTest.ParameterizedSite
    ( parameterizedSiteTest
    ) where

import Data.ByteString.Lazy (ByteString)
import Network.Wai.Test (runSession, request, defaultRequest, assertBodyContains)
import Test.Hspec (Spec, describe, it)
import Yesod.Core (YesodDispatch)
import Yesod.Core.Dispatch (toWaiApp)

import YesodCoreTest.ParameterizedSite.PolyAny (PolyAny (..))
import YesodCoreTest.ParameterizedSite.PolyShow (PolyShow (..))
import YesodCoreTest.ParameterizedSite.Compat (Compat (..))

-- These are actually tests for template haskell. So if it compiles, it works
parameterizedSiteTest :: Spec
parameterizedSiteTest = describe "Polymorphic Yesod sites" $ do
    it "Polymorphic unconstrained stub" $ runStub (PolyAny ())
    it "Polymorphic stub with Show" $ runStub' "1337" (PolyShow 1337)
    it "Polymorphic unconstrained stub, old-style" $ runStub (Compat () ())

runStub :: YesodDispatch a => a -> IO ()
runStub stub =
    let actions = do
            res <- request defaultRequest
            assertBodyContains "Stub" res
    in toWaiApp stub >>= runSession actions


runStub' :: YesodDispatch a => ByteString -> a -> IO ()
runStub' body stub =
    let actions = do
            res <- request defaultRequest
            assertBodyContains "Stub" res
            assertBodyContains body res
    in toWaiApp stub >>= runSession actions