Skip to content

Commit

Permalink
Merge pull request #6 from adinapoli/issue-1
Browse files Browse the repository at this point in the history
Issue 1, Encryption support
  • Loading branch information
adinapoli committed Dec 13, 2014
2 parents ca3e186 + 138779f commit 7ccd7ab
Show file tree
Hide file tree
Showing 9 changed files with 403 additions and 207 deletions.
1 change: 1 addition & 0 deletions .gitignore
Original file line number Diff line number Diff line change
Expand Up @@ -2,3 +2,4 @@ dist
.cabal-sandbox
cabal.sandbox.config
shell.nix
cabal.config
4 changes: 2 additions & 2 deletions example/StreamingDecrypter.hs
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
{-# LANGUAGE OverloadedStrings #-}
module Main where

import Crypto.RNCryptor.V3
import Crypto.RNCryptor.V3.Decrypt
import qualified System.IO.Streams as S
import System.Environment
import qualified Data.ByteString.Char8 as B
Expand All @@ -11,4 +11,4 @@ main = do
args <- getArgs
case args of
key:_ -> decryptStream (B.pack key) S.stdin S.stdout
_ -> putStrLn "usage: rncryptor-stream <key>"
_ -> putStrLn "usage: rncryptor-decrypt <key>"
14 changes: 14 additions & 0 deletions example/StreamingEncrypter.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,14 @@
{-# LANGUAGE OverloadedStrings #-}
module Main where

import Crypto.RNCryptor.V3.Encrypt
import qualified System.IO.Streams as S
import System.Environment
import qualified Data.ByteString.Char8 as B

main :: IO ()
main = do
args <- getArgs
case args of
key:_ -> encryptStream (B.pack key) S.stdin S.stdout
_ -> putStrLn "usage: rncryptor-encrypt <key>"
26 changes: 22 additions & 4 deletions rncryptor.cabal
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
name: rncryptor
version: 0.0.1.0
version: 0.0.2.0
synopsis: Haskell implementation of the RNCryptor file format
description: Pure Haskell implementation of the RNCrytor spec.
license: MIT
Expand All @@ -17,14 +17,17 @@ source-repository head

library
exposed-modules:
Crypto.RNCryptor.Padding
Crypto.RNCryptor.V3
Crypto.RNCryptor.V3.Encrypt
Crypto.RNCryptor.V3.Decrypt
Crypto.RNCryptor.Types
other-modules:
build-depends:
base >=4.6 && < 5
, bytestring >= 0.9.0
, mtl >= 2.1
, base64-bytestring >= 1.0.0.1
, random >= 1.0.0.1
, QuickCheck >= 2.6 && < 2.8
, io-streams >= 1.2.0.0
, cipher-aes >= 0.2.0
Expand Down Expand Up @@ -56,12 +59,11 @@ test-suite rncryptor-tests
, tasty-quickcheck
, tasty-hunit

executable rncryptor-stream
executable rncryptor-decrypt
build-depends:
base
, bytestring
, io-streams
, base64-bytestring
, cipher-aes
, rncryptor -any
hs-source-dirs:
Expand All @@ -70,5 +72,21 @@ executable rncryptor-stream
StreamingDecrypter.hs
default-language:
Haskell2010
ghc-options:
-funbox-strict-fields

executable rncryptor-encrypt
build-depends:
base
, bytestring
, io-streams
, cipher-aes
, rncryptor -any
hs-source-dirs:
example
main-is:
StreamingEncrypter.hs
default-language:
Haskell2010
ghc-options:
-funbox-strict-fields
19 changes: 19 additions & 0 deletions src/Crypto/RNCryptor/Padding.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,19 @@
module Crypto.RNCryptor.Padding
( pkcs7Padding ) where

import Data.ByteString (ByteString)
import qualified Data.ByteString as B


--------------------------------------------------------------------------------
-- | Computes the padding as per PKCS#7. The specification can be found
-- here: <http://tools.ietf.org/html/rfc5652#section-6.3>
pkcs7Padding :: Int
-- ^ The block size (e.g. 16 bytes)
-> Int
-- ^ The input size
-> ByteString
-- ^ The resulting padding
pkcs7Padding k l =
let octetsSize = k - (l `rem` k)
in B.pack $ replicate octetsSize (fromIntegral octetsSize)
51 changes: 48 additions & 3 deletions src/Crypto/RNCryptor/Types.hs
Original file line number Diff line number Diff line change
@@ -1,12 +1,20 @@

{-# LANGUAGE RecordWildCards #-}
module Crypto.RNCryptor.Types
( RNCryptorHeader(..)
, RNCryptorContext(ctxHeader, ctxCipher)
, newRNCryptorContext
, newRNCryptorHeader
, renderRNCryptorHeader
, blockSize
) where

import Data.ByteString (ByteString)
import Data.ByteString (cons, ByteString)
import qualified Data.ByteString.Char8 as C8
import Data.Word
import Data.Monoid
import System.Random
import Control.Applicative
import Control.Monad
import Crypto.Cipher.AES
import Crypto.PBKDF.ByteString

Expand All @@ -20,14 +28,51 @@ data RNCryptorHeader = RNCryptorHeader {
-- ^ iff option includes "uses password"
, rncHMACSalt :: !ByteString
-- ^ iff options includes "uses password"
, rncIV :: !AESIV
, rncIV :: !ByteString
-- ^ The initialisation vector
-- The ciphertext is variable and encrypted in CBC mode
, rncHMAC :: (ByteString -> ByteString)
-- ^ The HMAC (32 bytes). This field is a continuation
-- as the HMAC is at the end of the file.
}

--------------------------------------------------------------------------------
saltSize :: Int
saltSize = 8

--------------------------------------------------------------------------------
blockSize :: Int
blockSize = 16

--------------------------------------------------------------------------------
randomSaltIO :: Int -> IO ByteString
randomSaltIO sz = C8.pack <$> forM [1 .. sz] (const $ randomRIO ('\NUL', '\255'))

--------------------------------------------------------------------------------
-- | Generates a new 'RNCryptorHeader', suitable for encryption.
newRNCryptorHeader :: ByteString -> IO RNCryptorHeader
newRNCryptorHeader userKey = do
let version = toEnum 3
let options = toEnum 1
eSalt <- randomSaltIO saltSize
iv <- randomSaltIO blockSize
hmacSalt <- randomSaltIO saltSize
return RNCryptorHeader {
rncVersion = version
, rncOptions = options
, rncEncryptionSalt = eSalt
, rncHMACSalt = hmacSalt
, rncIV = iv
, rncHMAC = const $ sha1PBKDF2 userKey hmacSalt 10000 32
}

--------------------------------------------------------------------------------
-- | Concatenates this 'RNCryptorHeader' into a raw sequence of bytes, up to the
-- IV. This means you need to append the ciphertext plus the HMAC to finalise
-- the encrypted file.
renderRNCryptorHeader :: RNCryptorHeader -> ByteString
renderRNCryptorHeader RNCryptorHeader{..} =
rncVersion `cons` rncOptions `cons` (rncEncryptionSalt <> rncHMACSalt <> rncIV)

--------------------------------------------------------------------------------
-- A convenient datatype to avoid carrying around the AES cypher,
Expand Down
Loading

0 comments on commit 7ccd7ab

Please sign in to comment.