happstack-server-7.5.1.3: Web related tools and services.

Safe HaskellNone
LanguageHaskell2010

Happstack.Server.Cookie

Description

Functions for creating, adding, and expiring cookies. To lookup cookie values see Happstack.Server.RqData.

Synopsis

Documentation

data Cookie Source #

a type for HTTP cookies. Usually created using mkCookie.

Instances
Eq Cookie Source # 
Instance details

Defined in Happstack.Server.Internal.Cookie

Methods

(==) :: Cookie -> Cookie -> Bool #

(/=) :: Cookie -> Cookie -> Bool #

Data Cookie Source # 
Instance details

Defined in Happstack.Server.Internal.Cookie

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Cookie -> c Cookie #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Cookie #

toConstr :: Cookie -> Constr #

dataTypeOf :: Cookie -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Cookie) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Cookie) #

gmapT :: (forall b. Data b => b -> b) -> Cookie -> Cookie #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Cookie -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Cookie -> r #

gmapQ :: (forall d. Data d => d -> u) -> Cookie -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Cookie -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Cookie -> m Cookie #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Cookie -> m Cookie #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Cookie -> m Cookie #

Read Cookie Source # 
Instance details

Defined in Happstack.Server.Internal.Cookie

Show Cookie Source # 
Instance details

Defined in Happstack.Server.Internal.Cookie

MonadReader RqEnv RqData Source # 
Instance details

Defined in Happstack.Server.RqData

Methods

ask :: RqData RqEnv #

local :: (RqEnv -> RqEnv) -> RqData a -> RqData a #

reader :: (RqEnv -> a) -> RqData a #

data CookieLife Source #

Specify the lifetime of a cookie.

Note that we always set the max-age and expires headers because internet explorer does not honor max-age. You can specific MaxAge or Expires and the other will be calculated for you. Choose which ever one makes your life easiest.

Constructors

Session

session cookie - expires when browser is closed

MaxAge Int

life time of cookie in seconds

Expires UTCTime

cookie expiration date

Expired

cookie already expired

mkCookie Source #

Arguments

:: String

cookie name

-> String

cookie value

-> Cookie 

Creates a cookie with a default version of 1, empty domain, a path of "/", secure == False and httpOnly == False

see also: addCookie

addCookie :: (MonadIO m, FilterMonad Response m) => CookieLife -> Cookie -> m () Source #

Add the Cookie to Response.

example

main = simpleHTTP nullConf $
  do addCookie Session (mkCookie "name" "value")
     ok $ "You now have a session cookie."

see also: addCookies

addCookies :: (MonadIO m, FilterMonad Response m) => [(CookieLife, Cookie)] -> m () Source #

Add the list Cookie to the Response.

see also: addCookie

expireCookie :: (MonadIO m, FilterMonad Response m) => String -> m () Source #

Expire the named cookie immediately and set the cookie value to ""

main = simpleHTTP nullConf $
  do expireCookie "name"
     ok $ "The cookie has been expired."