| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
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>"
]
- makeSimpleCookie :: Text -> Text -> SetCookie
- setCookie :: (Monad m, ScottyError e) => SetCookie -> ActionT e m ()
- setSimpleCookie :: (Monad m, ScottyError e) => Text -> Text -> ActionT e m ()
- getCookie :: (Monad m, ScottyError e) => Text -> ActionT e m (Maybe Text)
- getCookies :: (Monad m, ScottyError e) => ActionT e m (Map Text Text)
- deleteCookie :: (Monad m, ScottyError e) => Text -> ActionT e m ()
Documentation
Arguments
| :: (Monad m, ScottyError e) | |
| => Text | name |
| -> Text | value |
| -> ActionT e m () |
makeSimpleCookie and setCookie combined.
getCookies :: (Monad m, ScottyError e) => ActionT e m (Map Text Text) Source
Returns all cookies
Arguments
| :: (Monad m, ScottyError e) | |
| => Text | name |
| -> ActionT e m () |