| Copyright | (c) 2014 2015 Mārtiņš Mačs (c) 2023 Marco Zocca |
|---|---|
| License | BSD-3-Clause |
| Maintainer | |
| Stability | experimental |
| Portability | GHC |
| Safe Haskell | Safe-Inferred |
| Language | Haskell2010 |
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
- setCookie :: MonadIO m => SetCookie -> ActionT m ()
- setSimpleCookie :: MonadIO m => Text -> Text -> ActionT m ()
- getCookie :: Monad m => Text -> ActionT m (Maybe Text)
- getCookies :: Monad m => ActionT m CookiesText
- deleteCookie :: MonadIO m => Text -> ActionT m ()
- type CookiesText = [(Text, Text)]
- makeSimpleCookie :: Text -> Text -> SetCookie
- data SetCookie
- defaultSetCookie :: SetCookie
- setCookieName :: SetCookie -> ByteString
- setCookieValue :: SetCookie -> ByteString
- setCookiePath :: SetCookie -> Maybe ByteString
- setCookieExpires :: SetCookie -> Maybe UTCTime
- setCookieMaxAge :: SetCookie -> Maybe DiffTime
- setCookieDomain :: SetCookie -> Maybe ByteString
- setCookieHttpOnly :: SetCookie -> Bool
- setCookieSecure :: SetCookie -> Bool
- setCookieSameSite :: SetCookie -> Maybe SameSiteOption
- data SameSiteOption
- sameSiteNone :: SameSiteOption
- sameSiteLax :: SameSiteOption
- sameSiteStrict :: SameSiteOption
Set cookie
setCookie :: MonadIO m => SetCookie -> ActionT m () Source #
Set a cookie, with full access to its options (see SetCookie)
makeSimpleCookie and setCookie combined.
Get cookie(s)
getCookies :: Monad m => ActionT m CookiesText Source #
Returns all cookies
Delete a cookie
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)] #
Textual cookies. Functions assume UTF8 encoding.
Construct a simple cookie (an UTF-8 string pair with default cookie options)
cookie configuration
Data type representing the key-value pair to use for a cookie, as well as configuration options for it.
Creating a SetCookie
SetCookie does not export a constructor; instead, use defaultSetCookie and override values (see http://www.yesodweb.com/book/settings-types for details):
import Web.Cookie :set -XOverloadedStrings let cookie =defaultSetCookie{setCookieName= "cookieName",setCookieValue= "cookieValue" }
Cookie Configuration
Cookies have several configuration options; a brief summary of each option is given below. For more information, see RFC 6265 or Wikipedia.
Instances
| Show SetCookie | |
| Default SetCookie |
|
Defined in Web.Cookie | |
| NFData SetCookie | |
Defined in Web.Cookie | |
| Eq SetCookie | |
defaultSetCookie :: SetCookie #
A minimal SetCookie. All fields are Nothing or False except and setCookieName = "name". You need this to construct a setCookieValue = "value"SetCookie, because it does not export a constructor. Equivalently, you may use def.
Since: cookie-0.4.2.2
setCookieName :: SetCookie -> ByteString #
The name of the cookie. Default value: "name"
setCookieValue :: SetCookie -> ByteString #
The value of the cookie. Default value: "value"
setCookiePath :: SetCookie -> Maybe ByteString #
The URL path for which the cookie should be sent. Default value: Nothing (The browser defaults to the path of the request that sets the cookie).
setCookieExpires :: SetCookie -> Maybe UTCTime #
The time at which to expire the cookie. Default value: Nothing (The browser will default to expiring a cookie when the browser is closed).
setCookieMaxAge :: SetCookie -> Maybe DiffTime #
The maximum time to keep the cookie, in seconds. Default value: Nothing (The browser defaults to expiring a cookie when the browser is closed).
setCookieDomain :: SetCookie -> Maybe ByteString #
The domain for which the cookie should be sent. Default value: Nothing (The browser defaults to the current domain).
setCookieHttpOnly :: SetCookie -> Bool #
Marks the cookie as "HTTP only", i.e. not accessible from Javascript. Default value: False
setCookieSecure :: SetCookie -> Bool #
Instructs the browser to only send the cookie over HTTPS. Default value: False
setCookieSameSite :: SetCookie -> Maybe SameSiteOption #
The "same site" policy of the cookie, i.e. whether it should be sent with cross-site requests. Default value: Nothing
data SameSiteOption #
Data type representing the options for a SameSite cookie
Instances
| Show SameSiteOption | |
Defined in Web.Cookie Methods showsPrec :: Int -> SameSiteOption -> ShowS # show :: SameSiteOption -> String # showList :: [SameSiteOption] -> ShowS # | |
| NFData SameSiteOption | |
Defined in Web.Cookie Methods rnf :: SameSiteOption -> () # | |
| Eq SameSiteOption | |
Defined in Web.Cookie Methods (==) :: SameSiteOption -> SameSiteOption -> Bool # (/=) :: SameSiteOption -> SameSiteOption -> Bool # | |
sameSiteNone :: SameSiteOption #
Directs the browser to send the cookie for cross-site requests.
Since: cookie-0.4.5
sameSiteLax :: SameSiteOption #
Directs the browser to send the cookie for safe requests (e.g. GET), but not for unsafe ones (e.g. POST)
sameSiteStrict :: SameSiteOption #
Directs the browser to not send the cookie for any cross-site request, including e.g. a user clicking a link in their email to open a page on your site.