scotty-cookie-0.1.0.3: Cookie management helper functions for Scotty framework

Safe HaskellNone
LanguageHaskell2010

Web.Scotty.Cookie

Description

Usage example: simple hit counter

{-# LANGUAGE OverloadedStrings #-}

import Control.Monad
import Data.Monoid
import Data.Maybe
import Data.Text.Read
import qualified Data.Text.Lazy as TL

import Web.Scotty
import Web.Scotty.Cookie

main :: IO ()
main = scotty 3000 $
    get "/" $ do
        hits <- liftM (fromMaybe "0") $ getCookie "hits"
        let hits' = case decimal hits of
                        Right n -> TL.pack . show . (+1) $ (fst n :: Integer)
                        Left _  -> "1"
        setSimpleCookie "hits" $ TL.toStrict hits'
        html $ mconcat [ "<html><body>"
                       , hits'
                       , "</body></html>"
                       ]

Synopsis

Documentation

makeSimpleCookie Source

Arguments

:: Text

name

-> Text

value

-> SetCookie 

setSimpleCookie Source

Arguments

:: (Monad m, ScottyError e) 
=> Text

name

-> Text

value

-> ActionT e m () 

getCookie Source

Arguments

:: (Monad m, ScottyError e) 
=> Text

name

-> ActionT e m (Maybe Text) 

getCookies :: (Monad m, ScottyError e) => ActionT e m (Map Text Text) Source

Returns all cookies

deleteCookie Source

Arguments

:: (Monad m, ScottyError e) 
=> Text

name

-> ActionT e m ()