File: Json.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 (56 lines) | stat: -rw-r--r-- 1,535 bytes parent folder | download | duplicates (3)
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
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
{-# LANGUAGE OverloadedStrings, TemplateHaskell, QuasiQuotes, TypeFamilies, MultiParamTypeClasses, ViewPatterns #-}
module YesodCoreTest.Json
    ( specs
    , Widget
    , resourcesApp
    ) where

import Yesod.Core
import Test.Hspec
import qualified Data.Map as Map
import Network.Wai.Test
import Data.Text (Text)
import Data.ByteString.Lazy (ByteString)

data App = App

mkYesod "App" [parseRoutes|
/ HomeR GET
/has-multiple-pieces/#Int/#Int MultiplePiecesR GET
|]

instance Yesod App

getHomeR :: Handler RepPlain
getHomeR = do
    val <- requireInsecureJsonBody
    case Map.lookup ("foo" :: Text) val of
        Nothing -> invalidArgs ["foo not found"]
        Just foo -> return $ RepPlain $ toContent (foo :: Text)

getMultiplePiecesR :: Int -> Int -> Handler ()
getMultiplePiecesR _ _ = return ()

test :: String
     -> ByteString
     -> (SResponse -> Session ())
     -> Spec
test name rbody f = it name $ do
    app <- toWaiApp App
    flip runSession app $ do
        sres <- srequest SRequest
            { simpleRequest = defaultRequest
            , simpleRequestBody = rbody
            }
        f sres

specs :: Spec
specs = describe "Yesod.Json" $ do
    test "parses valid content" "{\"foo\":\"bar\"}" $ \sres -> do
        assertStatus 200 sres
        assertBody "bar" sres
    test "400 for bad JSON" "{\"foo\":\"bar\"" $ \sres -> do
        assertStatus 400 sres
    test "400 for bad structure" "{\"foo2\":\"bar\"}" $ \sres -> do
        assertStatus 400 sres
        assertBodyContains "foo not found" sres