summaryrefslogtreecommitdiff
path: root/Codec
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 /Codec
parentf907d986330ac5f88f9e921bdd6c0572d4691003 (diff)
Separate ASCII armor codec into its own package, change license to ISC, and change API toward Stephen Paul Weber's proposal.
Diffstat (limited to 'Codec')
-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
4 files changed, 43 insertions, 24 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)