scotty-0.20.1: Haskell web framework inspired by Ruby's Sinatra, using WAI and Warp
Copyright(c) 2014 2015 Mārtiņš Mačs
(c) 2023 Marco Zocca
LicenseBSD-3-Clause
Maintainer
Stabilityexperimental
PortabilityGHC
Safe HaskellSafe-Inferred
LanguageHaskell2010

Web.Scotty.Cookie

Description

This module provides utilities for adding cookie support inside scotty applications. Most code has been adapted from 'scotty-cookie'.

Example

A simple hit counter that stores the number of page visits in a cookie:

{-# LANGUAGE OverloadedStrings #-}

import Control.Monad
import Data.Monoid
import Data.Maybe
import qualified Data.Text.Lazy as TL
import qualified Data.Text.Lazy.Read as TL (decimal)
import Web.Scotty (scotty, html)
import Web.Scotty.Cookie (getCookie, setSimpleCookie)

main :: IO ()
main = scotty 3000 $
    get "/" $ do
        hits <- liftM (fromMaybe "0") $ getCookie "hits"
        let hits' =
              case TL.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

Set cookie

setCookie :: MonadIO m => SetCookie -> ActionT m () Source #

Set a cookie, with full access to its options (see SetCookie)

setSimpleCookie Source #

Arguments

:: MonadIO m 
=> Text

name

-> Text

value

-> ActionT m () 

Get cookie(s)

getCookie Source #

Arguments

:: Monad m 
=> Text

name

-> ActionT m (Maybe Text) 

Lookup one cookie name

getCookies :: Monad m => ActionT m CookiesText Source #

Returns all cookies

Delete a cookie

deleteCookie Source #

Arguments

:: MonadIO m 
=> Text

name

-> ActionT m () 

Browsers don't directly delete a cookie, but setting its expiry to a past date (e.g. the UNIX epoch) ensures that the cookie will be invalidated (whether and when it will be actually deleted by the browser seems to be browser-dependent).

Helpers and advanced interface (re-exported from cookie)

type CookiesText = [(Text, Text)] #

makeSimpleCookie Source #

Arguments

:: Text

name

-> Text

value

-> SetCookie 

Construct a simple cookie (an UTF-8 string pair with default cookie options)

cookie configuration

data SetCookie #

Instances

Instances details
Show SetCookie 
Instance details

Defined in Web.Cookie

Default SetCookie 
Instance details

Defined in Web.Cookie

Methods

def :: SetCookie Source #

NFData SetCookie 
Instance details

Defined in Web.Cookie

Methods

rnf :: SetCookie -> () Source #

Eq SetCookie 
Instance details

Defined in Web.Cookie

data SameSiteOption #

Instances

Instances details
Show SameSiteOption 
Instance details

Defined in Web.Cookie

NFData SameSiteOption 
Instance details

Defined in Web.Cookie

Methods

rnf :: SameSiteOption -> () Source #

Eq SameSiteOption 
Instance details

Defined in Web.Cookie