summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorClint Adams <clint@softwarefreedom.org>2012-04-25 16:38:48 -0400
committerClint Adams <clint@softwarefreedom.org>2012-04-25 16:38:48 -0400
commit5ed645493e10190f7cddd753bb058e8487037549 (patch)
tree7b80971ad747ff0d1e5e6651e1efe7fe29ec6db6
parentf907d986330ac5f88f9e921bdd6c0572d4691003 (diff)
Separate ASCII armor codec into its own package, change license to ISC, and change API toward Stephen Paul Weber's proposal.
-rw-r--r--Codec/Encryption/OpenPGP/ASCIIArmor.hs2
-rw-r--r--Codec/Encryption/OpenPGP/ASCIIArmor/Decode.hs17
-rw-r--r--Codec/Encryption/OpenPGP/ASCIIArmor/Encode.hs25
-rw-r--r--Codec/Encryption/OpenPGP/ASCIIArmor/Types.hs23
-rw-r--r--Data/Digest/CRC24.hs2
-rw-r--r--LICENSE30
-rw-r--r--openpgp-asciiarmor.cabal49
-rw-r--r--tests/data/msg1.asc7
-rw-r--r--tests/data/msg1.gpgbin0 -> 58 bytes
-rw-r--r--tests/suite.hs44
10 files changed, 157 insertions, 42 deletions
diff --git a/Codec/Encryption/OpenPGP/ASCIIArmor.hs b/Codec/Encryption/OpenPGP/ASCIIArmor.hs
index 62440ae..74c8c69 100644
--- a/Codec/Encryption/OpenPGP/ASCIIArmor.hs
+++ b/Codec/Encryption/OpenPGP/ASCIIArmor.hs
@@ -1,6 +1,6 @@
1-- ASCIIArmor.hs: OpenPGP (RFC4880) ASCII armor implementation 1-- ASCIIArmor.hs: OpenPGP (RFC4880) ASCII armor implementation
2-- Copyright Ⓒ 2012 Clint Adams 2-- Copyright Ⓒ 2012 Clint Adams
3-- This software is released under the terms of the Expat (MIT) license. 3-- This software is released under the terms of the ISC license.
4-- (See the LICENSE file). 4-- (See the LICENSE file).
5 5
6module Codec.Encryption.OpenPGP.ASCIIArmor ( 6module Codec.Encryption.OpenPGP.ASCIIArmor (
diff --git a/Codec/Encryption/OpenPGP/ASCIIArmor/Decode.hs b/Codec/Encryption/OpenPGP/ASCIIArmor/Decode.hs
index 64f7236..8c2a8a3 100644
--- a/Codec/Encryption/OpenPGP/ASCIIArmor/Decode.hs
+++ b/Codec/Encryption/OpenPGP/ASCIIArmor/Decode.hs
@@ -1,7 +1,7 @@
1{-# LANGUAGE OverloadedStrings #-} 1{-# LANGUAGE OverloadedStrings #-}
2-- ASCIIArmor/Decode.hs: OpenPGP (RFC4880) ASCII armor implementation 2-- ASCIIArmor/Decode.hs: OpenPGP (RFC4880) ASCII armor implementation
3-- Copyright Ⓒ 2012 Clint Adams 3-- Copyright Ⓒ 2012 Clint Adams
4-- This software is released under the terms of the Expat (MIT) license. 4-- This software is released under the terms of the ISC license.
5-- (See the LICENSE file). 5-- (See the LICENSE file).
6 6
7module Codec.Encryption.OpenPGP.ASCIIArmor.Decode ( 7module Codec.Encryption.OpenPGP.ASCIIArmor.Decode (
@@ -9,8 +9,7 @@ module Codec.Encryption.OpenPGP.ASCIIArmor.Decode (
9 , decodeArmor 9 , decodeArmor
10) where 10) where
11 11
12import Codec.Encryption.OpenPGP.Serialize () 12import Codec.Encryption.OpenPGP.ASCIIArmor.Types
13import Codec.Encryption.OpenPGP.Types
14import Control.Applicative (many, (<|>), (<$>)) 13import Control.Applicative (many, (<|>), (<$>))
15import Data.Attoparsec.ByteString (Parser, many1, string, inClass, notInClass, satisfy, word8, (<?>), parse, IResult(..)) 14import Data.Attoparsec.ByteString (Parser, many1, string, inClass, notInClass, satisfy, word8, (<?>), parse, IResult(..))
16import Data.Attoparsec.ByteString.Char8 (isDigit_w8) 15import Data.Attoparsec.ByteString.Char8 (isDigit_w8)
@@ -39,9 +38,7 @@ parseArmor = do
39 blankishLine <?> "blank line" 38 blankishLine <?> "blank line"
40 payload <- base64Data <?> "base64 data" 39 payload <- base64Data <?> "base64 data"
41 endLine atype <?> "end line" 40 endLine atype <?> "end line"
42 case runGet get payload of 41 return $ Armor atype headers payload
43 Left err -> fail err
44 Right packets -> return $ Armor atype headers (unBlock packets)
45 42
46beginLine :: (Integral a, Read a, Show a) => Parser (ArmorType a) 43beginLine :: (Integral a, Read a, Show a) => Parser (ArmorType a)
47beginLine = do 44beginLine = do
@@ -64,16 +61,18 @@ beginLine = do
64lineEnding :: Parser ByteString 61lineEnding :: Parser ByteString
65lineEnding = string "\n" <|> string "\r\n" 62lineEnding = string "\n" <|> string "\r\n"
66 63
67armorHeaders :: Parser [ArmorHeader] 64armorHeaders :: Parser [(String, String)]
68armorHeaders = many armorHeader 65armorHeaders = many armorHeader
69 66
70armorHeader :: Parser ArmorHeader 67armorHeader :: Parser (String, String)
71armorHeader = do 68armorHeader = do
72 key <- many1 (satisfy (inClass "ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz")) 69 key <- many1 (satisfy (inClass "ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz"))
73 string ": " 70 string ": "
74 val <- many1 (satisfy (notInClass "\n\r")) 71 val <- many1 (satisfy (notInClass "\n\r"))
75 lineEnding 72 lineEnding
76 return (B.pack key, B.pack val) 73 return (w8sToString key, w8sToString val)
74 where
75 w8sToString = BC8.unpack . B.pack
77 76
78blankishLine :: Parser ByteString 77blankishLine :: Parser ByteString
79blankishLine = many (satisfy (inClass " \t")) >> lineEnding 78blankishLine = many (satisfy (inClass " \t")) >> lineEnding
diff --git a/Codec/Encryption/OpenPGP/ASCIIArmor/Encode.hs b/Codec/Encryption/OpenPGP/ASCIIArmor/Encode.hs
index c9c9641..8853be3 100644
--- a/Codec/Encryption/OpenPGP/ASCIIArmor/Encode.hs
+++ b/Codec/Encryption/OpenPGP/ASCIIArmor/Encode.hs
@@ -1,14 +1,13 @@
1-- ASCIIArmor/Encode.hs: OpenPGP (RFC4880) ASCII armor implementation 1-- ASCIIArmor/Encode.hs: OpenPGP (RFC4880) ASCII armor implementation
2-- Copyright Ⓒ 2012 Clint Adams 2-- Copyright Ⓒ 2012 Clint Adams
3-- This software is released under the terms of the Expat (MIT) license. 3-- This software is released under the terms of the ISC license.
4-- (See the LICENSE file). 4-- (See the LICENSE file).
5 5
6module Codec.Encryption.OpenPGP.ASCIIArmor.Encode ( 6module Codec.Encryption.OpenPGP.ASCIIArmor.Encode (
7 armor 7 armor
8) where 8) where
9 9
10import Codec.Encryption.OpenPGP.Serialize () 10import Codec.Encryption.OpenPGP.ASCIIArmor.Types
11import Codec.Encryption.OpenPGP.Types
12import Data.ByteString (ByteString) 11import Data.ByteString (ByteString)
13import qualified Data.ByteString as B 12import qualified Data.ByteString as B
14import qualified Data.ByteString.Char8 as BC8 13import qualified Data.ByteString.Char8 as BC8
@@ -19,7 +18,7 @@ import Data.Serialize.Put (runPut, putWord32be)
19import Data.String (IsString, fromString) 18import Data.String (IsString, fromString)
20 19
21armor :: (Integral a, Show a) => Armor a -> ByteString 20armor :: (Integral a, Show a) => Armor a -> ByteString
22armor (Armor atype ahs ps) = beginLine atype `B.append` armorHeaders ahs `B.append` blankLine `B.append` armorData (opgpStream ps) `B.append` armorChecksum (opgpStream ps) `B.append` endLine atype 21armor (Armor atype ahs bs) = beginLine atype `B.append` armorHeaders ahs `B.append` blankLine `B.append` armorData bs `B.append` armorChecksum bs `B.append` endLine atype
23 22
24blankLine :: ByteString 23blankLine :: ByteString
25blankLine = BC8.singleton '\n' 24blankLine = BC8.singleton '\n'
@@ -38,22 +37,20 @@ aType (ArmorSplitMessage x y) = BC8.pack $ "MESSAGE, PART " ++ show x ++ "/" ++
38aType (ArmorSplitMessageIndefinite x) = BC8.pack $ "MESSAGE, PART " ++ show x 37aType (ArmorSplitMessageIndefinite x) = BC8.pack $ "MESSAGE, PART " ++ show x
39aType (ArmorSignature) = BC8.pack "SIGNATURE" 38aType (ArmorSignature) = BC8.pack "SIGNATURE"
40 39
41armorHeaders :: [ArmorHeader] -> ByteString 40armorHeaders :: [(String, String)] -> ByteString
42armorHeaders ahs = BC8.unlines . map armorHeader $ ahs 41armorHeaders ahs = BC8.unlines . map armorHeader $ ahs
43 where 42 where
44 armorHeader :: ArmorHeader -> ByteString 43 armorHeader :: (String, String) -> ByteString
45 armorHeader (k, v) = k `B.append` BC8.pack ": " `B.append` v 44 armorHeader (k, v) = BC8.pack k `B.append` BC8.pack ": " `B.append` BC8.pack v
46
47opgpStream :: [Packet] -> ByteString
48opgpStream = runPut . put . Block
49 45
50armorData :: ByteString -> ByteString 46armorData :: ByteString -> ByteString
51armorData = BC8.unlines . wrap76 . Base64.encode 47armorData = BC8.unlines . wordWrap 64 . Base64.encode
52 48
53wrap76 :: ByteString -> [ByteString] 49wordWrap :: Int -> ByteString -> [ByteString]
54wrap76 bs 50wordWrap lw bs
55 | B.null bs = [] 51 | B.null bs = []
56 | otherwise = B.take 76 bs : wrap76 (B.drop 76 bs) 52 | lw < 1 || lw > 76 = wordWrap 76 bs
53 | otherwise = B.take lw bs : wordWrap lw (B.drop lw bs)
57 54
58armorChecksum :: ByteString -> ByteString 55armorChecksum :: ByteString -> ByteString
59armorChecksum = BC8.cons '=' . armorData . B.tail . runPut . putWord32be . crc24 56armorChecksum = BC8.cons '=' . armorData . B.tail . runPut . putWord32be . crc24
diff --git a/Codec/Encryption/OpenPGP/ASCIIArmor/Types.hs b/Codec/Encryption/OpenPGP/ASCIIArmor/Types.hs
new file mode 100644
index 0000000..8c7ef6f
--- /dev/null
+++ b/Codec/Encryption/OpenPGP/ASCIIArmor/Types.hs
@@ -0,0 +1,23 @@
1-- ASCIIArmor/Decode.hs: OpenPGP (RFC4880) ASCII armor implementation
2-- Copyright Ⓒ 2012 Clint Adams
3-- This software is released under the terms of the ISC license.
4-- (See the LICENSE file).
5
6module Codec.Encryption.OpenPGP.ASCIIArmor.Types (
7 Armor(..)
8 , ArmorType(..)
9) where
10
11import Data.ByteString (ByteString)
12
13data Armor a = Armor (ArmorType a) [(String, String)] ByteString
14 | ClearSigned [(String, String)] String (Armor a)
15 deriving (Show, Eq)
16
17data ArmorType a = ArmorMessage
18 | ArmorPublicKeyBlock
19 | ArmorPrivateKeyBlock
20 | ArmorSplitMessage a a
21 | ArmorSplitMessageIndefinite a
22 | ArmorSignature
23 deriving (Show, Eq)
diff --git a/Data/Digest/CRC24.hs b/Data/Digest/CRC24.hs
index 5c8c27c..4637834 100644
--- a/Data/Digest/CRC24.hs
+++ b/Data/Digest/CRC24.hs
@@ -1,6 +1,6 @@
1-- CRC24.hs: OpenPGP (RFC4880) CRC24 implementation 1-- CRC24.hs: OpenPGP (RFC4880) CRC24 implementation
2-- Copyright Ⓒ 2012 Clint Adams 2-- Copyright Ⓒ 2012 Clint Adams
3-- This software is released under the terms of the Expat (MIT) license. 3-- This software is released under the terms of the ISC license.
4-- (See the LICENSE file). 4-- (See the LICENSE file).
5 5
6module Data.Digest.CRC24 ( 6module Data.Digest.CRC24 (
diff --git a/LICENSE b/LICENSE
index 02691d7..db7a166 100644
--- a/LICENSE
+++ b/LICENSE
@@ -1,19 +1,15 @@
1Copyright Ⓒ 2012 Clint Adams 1Copyright Ⓒ 2012 Clint Adams <clint@debian.org>
2 2
3Permission is hereby granted, free of charge, to any person obtaining a copy of 3Permission to use, copy, modify, and/or distribute this software
4this software and associated documentation files (the "Software"), to deal in 4for any purpose with or without fee is hereby granted, provided
5the Software without restriction, including without limitation the rights to 5that the above copyright notice and this permission notice appear
6use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies 6in all copies.
7of the Software, and to permit persons to whom the Software is furnished to do
8so, subject to the following conditions:
9 7
10The above copyright notice and this permission notice shall be included in all 8THE SOFTWARE IS PROVIDED "AS IS" AND THE AUTHOR DISCLAIMS ALL
11copies or substantial portions of the Software. 9WARRANTIES WITH REGARD TO THIS SOFTWARE INCLUDING ALL IMPLIED
12 10WARRANTIES OF MERCHANTABILITY AND FITNESS. IN NO EVENT SHALL THE
13THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR 11AUTHOR BE LIABLE FOR ANY SPECIAL, DIRECT, INDIRECT, OR
14IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, 12CONSEQUENTIAL DAMAGES OR ANY DAMAGES WHATSOEVER RESULTING FROM
15FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE 13LOSS OF USE, DATA OR PROFITS, WHETHER IN AN ACTION OF CONTRACT,
16AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER 14NEGLIGENCE OR OTHER TORTIOUS ACTION, ARISING OUT OF OR IN
17LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, 15CONNECTION WITH THE USE OR PERFORMANCE OF THIS SOFTWARE.
18OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE
19SOFTWARE.
diff --git a/openpgp-asciiarmor.cabal b/openpgp-asciiarmor.cabal
new file mode 100644
index 0000000..4b7e25d
--- /dev/null
+++ b/openpgp-asciiarmor.cabal
@@ -0,0 +1,49 @@
1Name: openpgp-asciiarmor
2Version: 0.0
3Synopsis: OpenPGP (RFC4880) ASCII Armor codec
4Description: OpenPGP (RFC4880) ASCII Armor codec
5Homepage: http://floss.scru.org/openpgp-asciiarmor
6License: OtherLicense
7License-file: LICENSE
8Author: Clint Adams
9Maintainer: Clint Adams <clint@debian.org>
10Copyright: 2012, Clint Adams
11Category: Codec, Data
12Build-type: Simple
13Extra-source-files: tests/suite.hs
14 , tests/data/msg1.asc
15 , tests/data/msg1.gpg
16
17Cabal-version: >= 1.10
18
19
20Library
21 Exposed-modules: Codec.Encryption.OpenPGP.ASCIIArmor
22 , Codec.Encryption.OpenPGP.ASCIIArmor.Decode
23 , Codec.Encryption.OpenPGP.ASCIIArmor.Encode
24 , Codec.Encryption.OpenPGP.ASCIIArmor.Types
25 Other-Modules: Data.Digest.CRC24
26 Build-depends: attoparsec
27 , base > 4 && < 5
28 , base64-bytestring
29 , bytestring
30 , cereal
31 default-language: Haskell98
32
33
34Test-Suite tests
35 type: exitcode-stdio-1.0
36 main-is: tests/suite.hs
37 Build-depends: attoparsec
38 , base > 4 && < 5
39 , base64-bytestring
40 , bytestring
41 , cereal
42 , HUnit
43 , test-framework
44 , test-framework-hunit
45 default-language: Haskell98
46
47source-repository head
48 type: git
49 location: git://git.debian.org/users/clint/openpgp-asciiarmor.git
diff --git a/tests/data/msg1.asc b/tests/data/msg1.asc
new file mode 100644
index 0000000..832d3bb
--- /dev/null
+++ b/tests/data/msg1.asc
@@ -0,0 +1,7 @@
1-----BEGIN PGP MESSAGE-----
2Version: OpenPrivacy 0.99
3
4yDgBO22WxBHv7O8X7O/jygAEzol56iUKiXmV+XmpCtmpqQUKiQrFqclFqUDBovzS
5vBSFjNSiVHsuAA==
6=njUN
7-----END PGP MESSAGE-----
diff --git a/tests/data/msg1.gpg b/tests/data/msg1.gpg
new file mode 100644
index 0000000..ddb79ea
--- /dev/null
+++ b/tests/data/msg1.gpg
Binary files differ
diff --git a/tests/suite.hs b/tests/suite.hs
new file mode 100644
index 0000000..272295a
--- /dev/null
+++ b/tests/suite.hs
@@ -0,0 +1,44 @@
1import Test.Framework (defaultMain, testGroup)
2import Test.Framework.Providers.HUnit
3
4import Test.HUnit
5
6import Codec.Encryption.OpenPGP.ASCIIArmor (armor, decodeArmor)
7import Codec.Encryption.OpenPGP.ASCIIArmor.Types
8
9import Data.ByteString (ByteString)
10import qualified Data.ByteString as B
11import qualified Data.ByteString.Char8 as BC8
12import Data.Digest.CRC24 (crc24)
13import Data.Word (Word32)
14
15testCRC24 :: ByteString -> Word32 -> Assertion
16testCRC24 bs crc = assertEqual "crc24" crc (crc24 bs)
17
18testArmorDecode :: FilePath -> FilePath -> Assertion
19testArmorDecode fp target = do
20 bs <- B.readFile $ "tests/data/" ++ fp
21 tbs <- B.readFile $ "tests/data/" ++ target
22 case decodeArmor bs of
23 Left e -> assertFailure $ "Decode failed (" ++ e ++ ") on " ++ fp
24 Right (Armor at hdrs pl) -> do assertEqual ("for " ++ fp) tbs pl
25
26testArmorEncode :: FilePath -> FilePath -> Assertion
27testArmorEncode fp target = do
28 bs <- B.readFile $ "tests/data/" ++ fp
29 tbs <- B.readFile $ "tests/data/" ++ target
30 assertEqual ("literaldata") (armor (Armor ArmorMessage [("Version","OpenPrivacy 0.99")] bs)) tbs
31
32tests = [
33 testGroup "CRC24" [
34 testCase "CRC24: A" (testCRC24 (BC8.pack "A") 16680698)
35 , testCase "CRC24: Haskell" (testCRC24 (BC8.pack "Haskell") 15612750)
36 , testCase "CRC24: hOpenPGP and friends" (testCRC24 (BC8.pack "hOpenPGP and friends") 11940960)
37 ]
38 , testGroup "ASCII armor" [
39 testCase "Decode sample armor" (testArmorDecode "msg1.asc" "msg1.gpg")
40 , testCase "Encode sample armor" (testArmorEncode "msg1.gpg" "msg1.asc")
41 ]
42 ]
43
44main = defaultMain tests