summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorClint Adams <clint@debian.org>2018-03-28 22:23:03 -0400
committerClint Adams <clint@debian.org>2018-03-28 22:23:03 -0400
commitf013f29b60a0549c300b0aab0c6e128cb28298e0 (patch)
tree10e67f7b9ddebea1910248e2bc371e17ff307191
parent55fa003d68c79ee928fbcdef0c922e333282afe9 (diff)
Switch from cereal to binary
-rw-r--r--Codec/Encryption/OpenPGP/ASCIIArmor/Decode.hs38
-rw-r--r--Codec/Encryption/OpenPGP/ASCIIArmor/Encode.hs6
-rw-r--r--openpgp-asciiarmor.cabal4
3 files changed, 24 insertions, 24 deletions
diff --git a/Codec/Encryption/OpenPGP/ASCIIArmor/Decode.hs b/Codec/Encryption/OpenPGP/ASCIIArmor/Decode.hs
index 98934a0..08a951b 100644
--- a/Codec/Encryption/OpenPGP/ASCIIArmor/Decode.hs
+++ b/Codec/Encryption/OpenPGP/ASCIIArmor/Decode.hs
@@ -1,6 +1,6 @@
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-2018 Clint Adams
4-- This software is released under the terms of the ISC 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
@@ -18,17 +18,17 @@ import qualified Data.Attoparsec.ByteString as AS
18import qualified Data.Attoparsec.ByteString.Lazy as AL 18import qualified Data.Attoparsec.ByteString.Lazy as AL
19import Data.Attoparsec.ByteString.Char8 (isDigit_w8, anyChar) 19import Data.Attoparsec.ByteString.Char8 (isDigit_w8, anyChar)
20import Data.Bits (shiftL) 20import Data.Bits (shiftL)
21import Data.ByteString (ByteString) 21import Data.ByteString.Lazy (ByteString)
22import qualified Data.ByteString as B 22import qualified Data.ByteString as B
23import qualified Data.ByteString.Lazy as BL 23import qualified Data.ByteString.Lazy as BL
24import qualified Data.ByteString.Char8 as BC8 24import qualified Data.ByteString.Char8 as BC8
25import qualified Data.ByteString.Base64 as Base64 25import qualified Data.ByteString.Base64 as Base64
26import Data.Digest.CRC24 (crc24) 26import Data.Digest.CRC24 (crc24)
27import Data.Serialize.Get (Get, runGet, getWord8) 27import Data.Binary.Get (Get, runGetOrFail, getWord8)
28import Data.String (IsString, fromString) 28import Data.String (IsString, fromString)
29import Data.Word (Word32) 29import Data.Word (Word32)
30 30
31decode :: IsString e => ByteString -> Either e [Armor] 31decode :: IsString e => B.ByteString -> Either e [Armor]
32decode bs = go (AS.parse parseArmors bs) 32decode bs = go (AS.parse parseArmors bs)
33 where 33 where
34 go (AS.Fail _ _ e) = Left (fromString e) 34 go (AS.Fail _ _ e) = Left (fromString e)
@@ -55,7 +55,7 @@ clearsigned = do
55 _ <- blankishLine <?> "blank line" 55 _ <- blankishLine <?> "blank line"
56 cleartext <- dashEscapedCleartext 56 cleartext <- dashEscapedCleartext
57 sig <- armor 57 sig <- armor
58 return $ ClearSigned headers (BL.fromChunks [cleartext]) sig 58 return $ ClearSigned headers cleartext sig
59 59
60armor :: Parser Armor 60armor :: Parser Armor
61armor = do 61armor = do
@@ -64,7 +64,7 @@ armor = do
64 _ <- blankishLine <?> "blank line" 64 _ <- blankishLine <?> "blank line"
65 payload <- base64Data <?> "base64 data" 65 payload <- base64Data <?> "base64 data"
66 _ <- endLine atype <?> "end line" 66 _ <- endLine atype <?> "end line"
67 return $ Armor atype headers (BL.fromChunks [payload]) 67 return $ Armor atype headers payload
68 68
69beginLine :: Parser ArmorType 69beginLine :: Parser ArmorType
70beginLine = do 70beginLine = do
@@ -88,7 +88,7 @@ beginLine = do
88 partsindef = ArmorSplitMessageIndefinite . BL.pack <$> num 88 partsindef = ArmorSplitMessageIndefinite . BL.pack <$> num
89 num = many1 (satisfy isDigit_w8) <?> "number" 89 num = many1 (satisfy isDigit_w8) <?> "number"
90 90
91lineEnding :: Parser ByteString 91lineEnding :: Parser B.ByteString
92lineEnding = string "\n" <|> string "\r\n" 92lineEnding = string "\n" <|> string "\r\n"
93 93
94armorHeaders :: Parser [(String, String)] 94armorHeaders :: Parser [(String, String)]
@@ -104,15 +104,15 @@ armorHeader = do
104 where 104 where
105 w8sToString = BC8.unpack . B.pack 105 w8sToString = BC8.unpack . B.pack
106 106
107blankishLine :: Parser ByteString 107blankishLine :: Parser B.ByteString
108blankishLine = many (satisfy (inClass " \t")) *> lineEnding 108blankishLine = many (satisfy (inClass " \t")) *> lineEnding
109 109
110endLine :: ArmorType -> Parser ByteString 110endLine :: ArmorType -> Parser B.ByteString
111endLine atype = do 111endLine atype = do
112 _ <- string $ "-----END PGP " `B.append` aType atype `B.append` "-----" 112 _ <- string $ "-----END PGP " `B.append` aType atype `B.append` "-----"
113 lineEnding 113 lineEnding
114 114
115aType :: ArmorType -> ByteString 115aType :: ArmorType -> B.ByteString
116aType (ArmorMessage) = BC8.pack "MESSAGE" 116aType (ArmorMessage) = BC8.pack "MESSAGE"
117aType (ArmorPublicKeyBlock) = BC8.pack "PUBLIC KEY BLOCK" 117aType (ArmorPublicKeyBlock) = BC8.pack "PUBLIC KEY BLOCK"
118aType (ArmorPrivateKeyBlock) = BC8.pack "PRIVATE KEY BLOCK" 118aType (ArmorPrivateKeyBlock) = BC8.pack "PRIVATE KEY BLOCK"
@@ -120,7 +120,7 @@ aType (ArmorSplitMessage x y) = BC8.pack "MESSAGE, PART " `B.append` l2s x `B.ap
120aType (ArmorSplitMessageIndefinite x) = BC8.pack "MESSAGE, PART " `B.append` l2s x 120aType (ArmorSplitMessageIndefinite x) = BC8.pack "MESSAGE, PART " `B.append` l2s x
121aType (ArmorSignature) = BC8.pack "SIGNATURE" 121aType (ArmorSignature) = BC8.pack "SIGNATURE"
122 122
123l2s :: BL.ByteString -> ByteString 123l2s :: BL.ByteString -> B.ByteString
124l2s = B.concat . BL.toChunks 124l2s = B.concat . BL.toChunks
125 125
126base64Data :: Parser ByteString 126base64Data :: Parser ByteString
@@ -129,11 +129,11 @@ base64Data = do
129 cksum <- checksumLine 129 cksum <- checksumLine
130 let payload = B.concat ls 130 let payload = B.concat ls
131 let ourcksum = crc24 payload 131 let ourcksum = crc24 payload
132 case runGet d24 cksum of 132 case runGetOrFail d24 (BL.fromStrict cksum) of
133 Left err -> fail err 133 Left (_,_,err) -> fail err
134 Right theircksum -> if theircksum == ourcksum then return payload else fail ("CRC24 mismatch: " ++ show (B.unpack cksum) ++ "/" ++ show theircksum ++ " vs. " ++ show ourcksum) 134 Right (_,_,theircksum) -> if theircksum == ourcksum then return (BL.fromStrict payload) else fail ("CRC24 mismatch: " ++ show (B.unpack cksum) ++ "/" ++ show theircksum ++ " vs. " ++ show ourcksum)
135 where 135 where
136 base64Line :: Parser ByteString 136 base64Line :: Parser B.ByteString
137 base64Line = do 137 base64Line = do
138 b64 <- many1 (satisfy (inClass "ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz0123456789+/")) 138 b64 <- many1 (satisfy (inClass "ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz0123456789+/"))
139 pad <- many (word8 (fromIntegral . fromEnum $ '=')) 139 pad <- many (word8 (fromIntegral . fromEnum $ '='))
@@ -142,7 +142,7 @@ base64Data = do
142 case Base64.decode line of 142 case Base64.decode line of
143 Left err -> fail err 143 Left err -> fail err
144 Right bs -> return bs 144 Right bs -> return bs
145 checksumLine :: Parser ByteString 145 checksumLine :: Parser B.ByteString
146 checksumLine = do 146 checksumLine = do
147 _ <- word8 (fromIntegral . fromEnum $ '=') 147 _ <- word8 (fromIntegral . fromEnum $ '=')
148 b64 <- many1 (satisfy (inClass "ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz0123456789+/")) 148 b64 <- many1 (satisfy (inClass "ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz0123456789+/"))
@@ -166,9 +166,9 @@ prefixed end = end <|> anyChar *> prefixed end
166dashEscapedCleartext :: Parser ByteString 166dashEscapedCleartext :: Parser ByteString
167dashEscapedCleartext = do 167dashEscapedCleartext = do
168 ls <- many1 ((deLine <|> unescapedLine) <* lineEnding) 168 ls <- many1 ((deLine <|> unescapedLine) <* lineEnding)
169 return $ crlfUnlines ls 169 return . BL.fromStrict $ crlfUnlines ls
170 where 170 where
171 deLine :: Parser ByteString 171 deLine :: Parser B.ByteString
172 deLine = B.pack <$> (string "- " *> many (satisfy (notInClass "\n\r"))) 172 deLine = B.pack <$> (string "- " *> many (satisfy (notInClass "\n\r")))
173 unescapedLine :: Parser ByteString 173 unescapedLine :: Parser B.ByteString
174 unescapedLine = maybe B.empty B.pack <$> optional ((:) <$> satisfy (notInClass "-\n\r") <*> many (satisfy (notInClass "\n\r"))) 174 unescapedLine = maybe B.empty B.pack <$> optional ((:) <$> satisfy (notInClass "-\n\r") <*> many (satisfy (notInClass "\n\r")))
diff --git a/Codec/Encryption/OpenPGP/ASCIIArmor/Encode.hs b/Codec/Encryption/OpenPGP/ASCIIArmor/Encode.hs
index c437439..fdb9961 100644
--- a/Codec/Encryption/OpenPGP/ASCIIArmor/Encode.hs
+++ b/Codec/Encryption/OpenPGP/ASCIIArmor/Encode.hs
@@ -1,5 +1,5 @@
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-2018 Clint Adams
3-- This software is released under the terms of the ISC 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
@@ -15,7 +15,7 @@ import qualified Data.ByteString.Lazy as BL
15import qualified Data.ByteString.Lazy.Char8 as BLC8 15import qualified Data.ByteString.Lazy.Char8 as BLC8
16import qualified Data.ByteString.Base64 as Base64 16import qualified Data.ByteString.Base64 as Base64
17import Data.Digest.CRC24 (crc24Lazy) 17import Data.Digest.CRC24 (crc24Lazy)
18import Data.Serialize.Put (runPutLazy, putWord32be) 18import Data.Binary.Put (runPut, putWord32be)
19 19
20encode :: [Armor] -> B.ByteString 20encode :: [Armor] -> B.ByteString
21encode = B.concat . BL.toChunks . encodeLazy 21encode = B.concat . BL.toChunks . encodeLazy
@@ -60,7 +60,7 @@ wordWrap lw bs
60 | otherwise = BL.take (fromIntegral lw) bs : wordWrap lw (BL.drop (fromIntegral lw) bs) 60 | otherwise = BL.take (fromIntegral lw) bs : wordWrap lw (BL.drop (fromIntegral lw) bs)
61 61
62armorChecksum :: ByteString -> ByteString 62armorChecksum :: ByteString -> ByteString
63armorChecksum = BLC8.cons '=' . armorData . BL.tail . runPutLazy . putWord32be . crc24Lazy 63armorChecksum = BLC8.cons '=' . armorData . BL.tail . runPut . putWord32be . crc24Lazy
64 64
65dashEscape :: ByteString -> ByteString 65dashEscape :: ByteString -> ByteString
66dashEscape = BLC8.unlines . map escapeLine . BLC8.lines 66dashEscape = BLC8.unlines . map escapeLine . BLC8.lines
diff --git a/openpgp-asciiarmor.cabal b/openpgp-asciiarmor.cabal
index 0feac1d..0e1f9ca 100644
--- a/openpgp-asciiarmor.cabal
+++ b/openpgp-asciiarmor.cabal
@@ -40,8 +40,8 @@ Library
40 Build-depends: attoparsec 40 Build-depends: attoparsec
41 , base > 4 && < 5 41 , base > 4 && < 5
42 , base64-bytestring 42 , base64-bytestring
43 , binary
43 , bytestring 44 , bytestring
44 , cereal
45 default-language: Haskell2010 45 default-language: Haskell2010
46 46
47 47
@@ -52,8 +52,8 @@ Test-Suite tests
52 Build-depends: attoparsec 52 Build-depends: attoparsec
53 , base > 4 && < 5 53 , base > 4 && < 5
54 , base64-bytestring 54 , base64-bytestring
55 , binary
55 , bytestring 56 , bytestring
56 , cereal
57 , tasty 57 , tasty
58 , tasty-hunit 58 , tasty-hunit
59 default-language: Haskell2010 59 default-language: Haskell2010