{-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}
module Snap.Snaplet.Session.SecureCookie
( SecureCookie
, getSecureCookie
, setSecureCookie
, expireSecureCookie
, encodeSecureCookie
, decodeSecureCookie
, checkTimeout
) where
import Control.Monad
import Control.Monad.Trans
import Data.ByteString (ByteString)
import Data.Serialize
import Data.Time
import Data.Time.Clock.POSIX
import Snap.Core
import Web.ClientSession
#if !MIN_VERSION_base(4,8,0)
import Control.Applicative
#endif
type SecureCookie t = (UTCTime, t)
getSecureCookie :: (MonadSnap m, Serialize t)
=> ByteString
-> Key
-> Maybe Int
-> m (Maybe t)
getSecureCookie name key timeout = do
rqCookie <- getCookie name
rspCookie <- getResponseCookie name <$> getResponse
let ck = rspCookie `mplus` rqCookie
let val = fmap cookieValue ck >>= decodeSecureCookie key
case val of
Nothing -> return Nothing
Just (ts, t) -> do
to <- checkTimeout timeout ts
return $ case to of
True -> Nothing
False -> Just t
decodeSecureCookie :: Serialize a
=> Key
-> ByteString
-> Maybe (SecureCookie a)
decodeSecureCookie key value = do
cv <- decrypt key value
(i, val) <- either (const Nothing) Just $ decode cv
return $ (posixSecondsToUTCTime (fromInteger i), val)
setSecureCookie :: (MonadSnap m, Serialize t)
=> ByteString
-> Maybe ByteString
-> Key
-> Maybe Int
-> t
-> m ()
setSecureCookie name domain key to val = do
t <- liftIO getCurrentTime
val' <- encodeSecureCookie key (t, val)
let expire = to >>= Just . flip addUTCTime t . fromIntegral
let nc = Cookie name val' expire domain (Just "/") False True
modifyResponse $ addResponseCookie nc
encodeSecureCookie :: (MonadIO m, Serialize t)
=> Key
-> SecureCookie t
-> m ByteString
encodeSecureCookie key (t, val) =
liftIO $ encryptIO key . encode $ (seconds, val)
where
seconds = round (utcTimeToPOSIXSeconds t) :: Integer
expireSecureCookie :: MonadSnap m
=> ByteString
-> Maybe ByteString
-> m ()
expireSecureCookie name domain = expireCookie cookie
where
cookie = Cookie name "" Nothing domain (Just "/") False False
checkTimeout :: (MonadSnap m) => Maybe Int -> UTCTime -> m Bool
checkTimeout Nothing _ = return False
checkTimeout (Just x) t0 = do
t1 <- liftIO getCurrentTime
return $ t1 > addUTCTime (fromIntegral x) t0