Safe Haskell | None |
---|---|
Language | Haskell2010 |
Functions for creating, adding, and expiring cookies. To lookup cookie values see Happstack.Server.RqData.
Synopsis
- data Cookie = Cookie {
- cookieVersion :: String
- cookiePath :: String
- cookieDomain :: String
- cookieName :: String
- cookieValue :: String
- secure :: Bool
- httpOnly :: Bool
- data CookieLife
- mkCookie :: String -> String -> Cookie
- addCookie :: (MonadIO m, FilterMonad Response m) => CookieLife -> Cookie -> m ()
- addCookies :: (MonadIO m, FilterMonad Response m) => [(CookieLife, Cookie)] -> m ()
- expireCookie :: (MonadIO m, FilterMonad Response m) => String -> m ()
Documentation
a type for HTTP cookies. Usually created using mkCookie
.
Cookie | |
|
Instances
Eq Cookie Source # | |
Data Cookie Source # | |
Defined in Happstack.Server.Internal.Cookie 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 # | |
Show Cookie Source # | |
MonadReader RqEnv RqData Source # | |
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.
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 |
Instances
Eq CookieLife Source # | |
Defined in Happstack.Server.Internal.Cookie (==) :: CookieLife -> CookieLife -> Bool # (/=) :: CookieLife -> CookieLife -> Bool # | |
Ord CookieLife Source # | |
Defined in Happstack.Server.Internal.Cookie compare :: CookieLife -> CookieLife -> Ordering # (<) :: CookieLife -> CookieLife -> Bool # (<=) :: CookieLife -> CookieLife -> Bool # (>) :: CookieLife -> CookieLife -> Bool # (>=) :: CookieLife -> CookieLife -> Bool # max :: CookieLife -> CookieLife -> CookieLife # min :: CookieLife -> CookieLife -> CookieLife # | |
Read CookieLife Source # | |
Defined in Happstack.Server.Internal.Cookie readsPrec :: Int -> ReadS CookieLife # readList :: ReadS [CookieLife] # readPrec :: ReadPrec CookieLife # readListPrec :: ReadPrec [CookieLife] # | |
Show CookieLife Source # | |
Defined in Happstack.Server.Internal.Cookie showsPrec :: Int -> CookieLife -> ShowS # show :: CookieLife -> String # showList :: [CookieLife] -> ShowS # |
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 #
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 #
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."