module Happstack.Server.Internal.Cookie
( Cookie(..)
, CookieLife(..)
, calcLife
, mkCookie
, mkCookieHeader
, getCookies
, getCookie
, getCookies'
, getCookie'
, parseCookies
, cookiesParser
)
where
import Control.Monad
import qualified Data.ByteString.Char8 as C
import Data.Char (chr, toLower)
import Data.Data (Data, Typeable)
import Data.List ((\\), intersperse)
import Data.Time.Clock (UTCTime, addUTCTime, diffUTCTime)
import Data.Time.Clock.POSIX (posixSecondsToUTCTime)
import Data.Time.Format (formatTime)
import Happstack.Server.Internal.Clock (getApproximateUTCTime)
import Text.ParserCombinators.Parsec hiding (token)
import System.Locale (defaultTimeLocale)
data Cookie = Cookie
{ cookieVersion :: String
, cookiePath :: String
, cookieDomain :: String
, cookieName :: String
, cookieValue :: String
, secure :: Bool
, httpOnly :: Bool
} deriving(Show,Eq,Read,Typeable,Data)
data CookieLife
= Session
| MaxAge Int
| Expires UTCTime
| Expired
deriving (Eq, Ord, Read, Show, Typeable)
calcLife :: CookieLife -> IO (Maybe (Int, UTCTime))
calcLife Session = return Nothing
calcLife (MaxAge s) =
do now <- getApproximateUTCTime
return (Just (s, addUTCTime (fromIntegral s) now))
calcLife (Expires expirationDate) =
do now <- getApproximateUTCTime
return $ Just (round $ expirationDate `diffUTCTime` now, expirationDate)
calcLife Expired =
return $ Just (0, posixSecondsToUTCTime 0)
mkCookie :: String
-> String
-> Cookie
mkCookie key val = Cookie "1" "/" "" key val False False
mkCookieHeader :: Maybe (Int, UTCTime) -> Cookie -> String
mkCookieHeader mLife cookie =
let l = [("Domain=", cookieDomain cookie)
,("Max-Age=", maybe "" (show . max 0 . fst) mLife)
,("expires=", maybe "" (formatTime defaultTimeLocale "%a, %d-%b-%Y %X GMT" . snd) mLife)
,("Path=", cookiePath cookie)
,("Version=", s cookieVersion)]
s f | f cookie == "" = ""
s f = '\"' : concatMap e (f cookie) ++ "\""
e c | fctl c || c == '"' = ['\\',c]
| otherwise = [c]
in concat $ intersperse ";" ((cookieName cookie++"="++s cookieValue):[ (k++v) | (k,v) <- l, "" /= v ] ++
(if secure cookie then ["Secure"] else []) ++
(if httpOnly cookie then ["HttpOnly"] else []))
fctl :: Char -> Bool
fctl ch = ch == chr 127 || ch <= chr 31
parseCookies :: String -> Either String [Cookie]
parseCookies str = either (Left . show) Right $ parse cookiesParser str str
cookiesParser :: GenParser Char st [Cookie]
cookiesParser = cookies
where
cookies = do
ws
ver<-option "" $ try (cookie_version >>= (\x -> cookieSep >> return x))
cookieList<-(cookie_value ver) `sepBy1` try cookieSep
ws
eof
return cookieList
cookie_value ver = do
name<-name_parser
cookieEq
val<-value
path<-option "" $ try (cookieSep >> cookie_path)
domain<-option "" $ try (cookieSep >> cookie_domain)
return $ Cookie ver path domain (low name) val False False
cookie_version = cookie_special "$Version"
cookie_path = cookie_special "$Path"
cookie_domain = cookie_special "$Domain"
cookie_special s = do
void $ string s
cookieEq
value
cookieSep = ws >> oneOf ",;" >> ws
cookieEq = ws >> char '=' >> ws
ws = spaces
value = word
word = try quoted_string <|> try incomp_token <|> return ""
quoted_string = do
void $ char '"'
r <-many ((try quotedPair) <|> (oneOf qdtext))
void $ char '"'
return r
incomp_token = many1 $ oneOf ((chars \\ ctl) \\ " \t\";")
name_parser = many1 $ oneOf ((chars \\ ctl) \\ "= ;,")
ctl = map chr (127:[0..31])
chars = map chr [0..127]
octet = map chr [0..255]
text = octet \\ ctl
qdtext = text \\ "\""
quotedPair = char '\\' >> anyChar
getCookies :: Monad m => C.ByteString -> m [Cookie]
getCookies h = getCookies' h >>= either (fail. ("Cookie parsing failed!"++)) return
getCookie :: Monad m => String -> C.ByteString -> m Cookie
getCookie s h = getCookie' s h >>= either (const $ fail ("getCookie: " ++ show s)) return
getCookies' :: Monad m => C.ByteString -> m (Either String [Cookie])
getCookies' header | C.null header = return $ Right []
| otherwise = return $ parseCookies (C.unpack header)
getCookie' :: Monad m => String -> C.ByteString -> m (Either String Cookie)
getCookie' s h = do
cs <- getCookies' h
return $ do
cooks <- cs
case filter (\x->(==) (low s) (cookieName x) ) cooks of
[] -> fail "No cookie found"
f -> return $ head f
low :: String -> String
low = map toLower