[Pkg-haskell-commits] darcs: haskell-clientsession: New upstream version 0.7.0.

clint at debian.org clint at debian.org
Sat Sep 10 13:22:53 UTC 2011


Sat Sep 10 13:22:17 UTC 2011  clint at debian.org
  * New upstream version 0.7.0.
  Ignore-this: f8680806bfe80ffe96e400f0bac6a4bb

    M ./changelog +6
    M ./control +20
    M ./copyright -1 +1
    A ./patches/
    A ./patches/debian-changes-0.7.0-1
    A ./patches/series

Sat Sep 10 13:22:17 UTC 2011  clint at debian.org
  * New upstream version 0.7.0.
  Ignore-this: f8680806bfe80ffe96e400f0bac6a4bb
diff -rN -u old-haskell-clientsession//changelog new-haskell-clientsession//changelog
--- old-haskell-clientsession//changelog	2011-09-10 13:22:53.145211172 +0000
+++ new-haskell-clientsession//changelog	2011-09-10 13:22:53.145211172 +0000
@@ -1,3 +1,9 @@
+haskell-clientsession (0.7.0-1) unstable; urgency=low
+
+  * New upstream version.
+
+ -- Clint Adams <clint at debian.org>  Sat, 10 Sep 2011 08:58:53 -0400
+
 haskell-clientsession (0.6.0-1) unstable; urgency=low
 
   * New upstream release.
diff -rN -u old-haskell-clientsession//control new-haskell-clientsession//control
--- old-haskell-clientsession//control	2011-09-10 13:22:53.129158656 +0000
+++ new-haskell-clientsession//control	2011-09-10 13:22:53.145211172 +0000
@@ -9,7 +9,27 @@
   , ghc
   , ghc-prof
   , ghc-ghci
+  , libghc-base64-bytestring-dev (>> 0.1.0.3)
+  , libghc-base64-bytestring-dev (<< 0.2)
+  , libghc-base64-bytestring-prof
+  , libghc-cereal-dev (>> 0.3)
+  , libghc-cereal-dev (<< 0.4)
+  , libghc-cereal-prof
+  , libghc-crypto-api-dev (>> 0.6.4)
+  , libghc-crypto-api-dev (<< 0.7)
+  , libghc-crypto-api-prof
+  , libghc-cryptocipher-dev (>> 0.2.5)
+  , libghc-cryptocipher-dev (<< 0.3)
+  , libghc-cryptocipher-prof
+  , libghc-cryptohash-dev (>> 0.7.1)
+  , libghc-cryptohash-dev (<< 0.8)
+  , libghc-cryptohash-prof
 Build-Depends-Indep: ghc-doc
+  , libghc-base64-bytestring-doc
+  , libghc-cereal-doc
+  , libghc-crypto-api-doc
+  , libghc-cryptocipher-doc
+  , libghc-cryptohash-doc
 Standards-Version: 3.9.2
 Homepage: http://hackage.haskell.org/package/clientsession
 Vcs-Darcs: http://darcs.debian.org/pkg-haskell/haskell-clientsession
diff -rN -u old-haskell-clientsession//copyright new-haskell-clientsession//copyright
--- old-haskell-clientsession//copyright	2011-09-10 13:22:53.129158656 +0000
+++ new-haskell-clientsession//copyright	2011-09-10 13:22:53.149172433 +0000
@@ -8,7 +8,7 @@
 
     Michael Snoyman <michael at snoyman.com>
 
-Copyright: 
+Copyright:
 
     2008  Michael Snoyman
 
diff -rN -u old-haskell-clientsession//patches/debian-changes-0.7.0-1 new-haskell-clientsession//patches/debian-changes-0.7.0-1
--- old-haskell-clientsession//patches/debian-changes-0.7.0-1	1970-01-01 00:00:00.000000000 +0000
+++ new-haskell-clientsession//patches/debian-changes-0.7.0-1	2011-09-10 13:22:53.149172433 +0000
@@ -0,0 +1,223 @@
+Description: Upstream changes introduced in version 0.7.0-1
+ This patch has been created by dpkg-source during the package build.
+ Here's the last changelog entry, hopefully it gives details on why
+ those changes were made:
+ .
+ haskell-clientsession (0.7.0-1) unstable; urgency=low
+ .
+   * New upstream version.
+ .
+ The person named in the Author field signed this changelog entry.
+Author: Clint Adams <clint at debian.org>
+
+---
+The information above should follow the Patch Tagging Guidelines, please
+checkout http://dep.debian.net/deps/dep3/ to learn about the format. Here
+are templates for supplementary fields that you might want to add:
+
+Origin: <vendor|upstream|other>, <url of original patch>
+Bug: <url in upstream bugtracker>
+Bug-Debian: http://bugs.debian.org/<bugnumber>
+Bug-Ubuntu: https://launchpad.net/bugs/<bugnumber>
+Forwarded: <no|not-needed|url proving that it has been forwarded>
+Reviewed-By: <name and email of someone who approved the patch>
+Last-Update: <YYYY-MM-DD>
+
+--- /dev/null
++++ haskell-clientsession-0.7.0/src/Web/ClientSession.hs
+@@ -0,0 +1,195 @@
++{-# LANGUAGE FlexibleContexts #-}
++{-# LANGUAGE ForeignFunctionInterface #-}
++{-# LANGUAGE TemplateHaskell #-}
++---------------------------------------------------------
++--
++-- |
++--
++-- Module        : Web.ClientSession
++-- Copyright     : Michael Snoyman
++-- License       : BSD3
++--
++-- Maintainer    : Michael Snoyman <michael at snoyman.com>
++-- Stability     : Stable
++-- Portability   : portable
++--
++-- Stores session data in a client cookie.  In order to do so,
++-- we:
++--
++-- * Encrypt the cookie data using AES in CBC mode.  This allows
++-- you to store sensitive information on the client side without
++-- worrying about eavesdropping.
++--
++-- * Sign the encrypted cookie data using HMAC-SHA256.  Besides
++-- detecting potential errors in storage or transmission of the
++-- cookies (integrity), the HMAC-SHA256 code also avoids
++-- malicious modifications of the cookie data by assuring you
++-- that the cookie data really was generated by this server
++-- (authentication).
++--
++-- * Encode everything using Base64.  Thus we avoid problems with
++-- non-printable characters by giving the browser a simple
++-- string.
++--
++-- Simple usage of the library involves just calling
++-- 'getDefaultKey' on the startup of your server, 'encryptIO'
++-- when serializing cookies and 'decrypt' when parsing then back.
++--
++---------------------------------------------------------
++module Web.ClientSession
++    ( -- * Automatic key generation
++      Key(..)
++    , IV
++    , randomIV
++    , mkIV
++    , getKey
++    , defaultKeyFile
++    , getDefaultKey
++    , initKey
++      -- * Actual encryption/decryption
++    , encrypt
++    , encryptIO
++    , decrypt
++    ) where
++
++import Control.Arrow (second)
++import Control.Monad (guard)
++import Data.Bits (xor)
++import System.Directory (doesFileExist)
++import qualified Data.ByteString as S
++import qualified Crypto.Cipher.AES as A
++import Crypto.Hash.SHA256 (SHA256)
++import Crypto.HMAC (MacKey(..), hmac')
++import qualified Data.ByteString.Base64 as B
++import Crypto.Random (newGenIO, genBytes, SystemRandom)
++import Data.Serialize (encode)
++
++-- | The keys used to store the cookies.  We have an AES key used
++-- to encrypt the cookie and a HMAC-SHA256 key used verify the
++-- authencity and integrity of the cookie.  The AES key needs to
++-- have exactly 32 bytes (256 bits).  The HMAC-SHA256 should have
++-- 64 bytes (512 bits), which is the block size of SHA256, but
++-- any size may be used.
++--
++-- See also 'getDefaultKey' and 'initKey'.
++data Key = Key { aesKey  :: A.Key
++               , hmacKey :: MacKey }
++         deriving (Eq, Show)
++
++-- | The initialization vector used by AES in CBC mode.  Should
++-- be exactly 16 bytes long.
++newtype IV = IV S.ByteString
++    deriving Show
++
++-- | Construct an initialization vector from a 'S.ByteString'.
++-- Fails if there isn't exactly 16 bytes.
++mkIV :: S.ByteString -> Maybe IV
++mkIV bs
++    | S.length bs == 16 = Just $ IV bs
++    | otherwise = Nothing
++
++-- | Randomly construct a fresh initialization vector.  You
++-- /should not/ reuse initialization vectors.
++randomIV :: IO IV
++randomIV = fmap IV $ randomBytes 16
++
++-- | The default key file.
++defaultKeyFile :: FilePath
++defaultKeyFile = "client_session_key.aes"
++
++-- | Simply calls 'getKey' 'defaultKeyFile'.
++getDefaultKey :: IO Key
++getDefaultKey = getKey defaultKeyFile
++
++-- | Get a key from the given text file.
++--
++-- If the file does not exist or is corrupted a random key will
++-- be generated and stored in that file.
++getKey :: FilePath     -- ^ File name where key is stored.
++       -> IO Key       -- ^ The actual key.
++getKey keyFile = do
++    exists <- doesFileExist keyFile
++    if exists
++        then S.readFile keyFile >>= either (const newKey) return . initKey
++        else newKey
++  where
++    newKey = do
++        (bs, key') <- randomKey
++        S.writeFile keyFile bs
++        return key'
++
++-- | Generate the given number of random bytes.
++randomBytes :: Int -> IO S.ByteString
++randomBytes len = do
++    g <- newGenIO
++    either (error . show) (return . fst) $ genBytes len (g :: SystemRandom)
++
++-- | Generate a random 'Key'.  Besides the 'Key', the
++-- 'ByteString' passed to 'initKey' is returned so that it can be
++-- saved for later use.
++randomKey :: IO (S.ByteString, Key)
++randomKey = do
++    bs <- randomBytes 64
++    case initKey bs of
++        Left e -> error $ "Web.ClientSession.randomKey: never here, " ++ e
++        Right key -> return (bs, key)
++
++-- | Initializes a 'Key' from a random 'S.ByteString'.  It's
++-- better to give a 'S.ByteString' with exactly 64 bytes, but
++-- anything with at least 32 bytes will work.
++initKey :: S.ByteString -> Either String Key
++initKey bs | S.length bs < 32 = Left $ "Web.ClientSession.initKey: length of " ++
++                                       show (S.length bs) ++ " too small."
++initKey bs = fmap mk $ A.initKey256 preAesKey
++    where
++      preAesKey | S.length bs >= 64 = S.pack $ uncurry (S.zipWith xor) $ S.splitAt 32 bs
++                | otherwise         = S.take 32 bs
++      mk k = Key { aesKey  = k
++                 , hmacKey = MacKey bs }
++                 -- It's okay to have a MacKey where bs doesn't
++                 -- have exactly 512 bits, the size of the block
++                 -- used in SHA-256.  hmac' already deals with it.
++
++-- | Same as 'encrypt', however randomly generates the
++-- initialization vector for you.
++encryptIO :: Key -> S.ByteString -> IO S.ByteString
++encryptIO key x = do
++    iv <- randomIV
++    return $ encrypt key iv x
++
++-- | Encrypt (AES-CBC), sign (HMAC-SHA256) and encode (Base64)
++-- the given cookie data.  The returned byte string is ready to
++-- be used in a response header.
++encrypt :: Key          -- ^ Key of the server.
++        -> IV           -- ^ New, random initialization vector (see 'randomIV').
++        -> S.ByteString -- ^ Serialized cookie data.
++        -> S.ByteString -- ^ Encoded cookie data to be given to
++                        -- the client browser.
++encrypt key (IV iv) x =
++    B.encode $ S.concat [iv, encode auth, encrypted]
++  where
++    toPad = 16 - S.length x `mod` 16
++    pad = S.replicate toPad $ fromIntegral toPad
++    y = pad `S.append` x
++    encrypted = A.encryptCBC (aesKey key) iv y
++    auth = hmac' (hmacKey key) encrypted :: SHA256
++
++-- | Decode (Base64), verify the integrity and authenticity
++-- (HMAC-SHA256) and decrypt (AES-CBC) the given encoded cookie
++-- data.  Returns the original serialized cookie data.  Fails if
++-- the data is corrupted.
++decrypt :: Key                -- ^ Key of the server.
++        -> S.ByteString       -- ^ Encoded cookie data given by the browser.
++        -> Maybe S.ByteString -- ^ Serialized cookie data.
++decrypt key dataBS64 = do
++    dataBS <- either (const Nothing) Just $ B.decode dataBS64
++    if S.length dataBS `mod` 16 /= 0 || S.length dataBS < 48
++        then Nothing
++        else do
++            let (iv, (auth, encrypted)) = second (S.splitAt 32) $ S.splitAt 16 dataBS
++                auth' = hmac' (hmacKey key) encrypted :: SHA256
++            guard (encode auth' == auth)
++            let x = A.decryptCBC (aesKey key) iv encrypted
++            (td, _) <- S.uncons x
++            guard (td > 0 && td <= 16)
++            return $ S.drop (fromIntegral td) x
diff -rN -u old-haskell-clientsession//patches/series new-haskell-clientsession//patches/series
--- old-haskell-clientsession//patches/series	1970-01-01 00:00:00.000000000 +0000
+++ new-haskell-clientsession//patches/series	2011-09-10 13:22:53.149172433 +0000
@@ -0,0 +1 @@
+debian-changes-0.7.0-1





More information about the Pkg-haskell-commits mailing list