summaryrefslogtreecommitdiff
path: root/Data/OpenPGP
diff options
context:
space:
mode:
authorJoe Crayne <joe@jerkface.net>2019-07-03 03:47:22 -0400
committerJoe Crayne <joe@jerkface.net>2019-07-03 03:47:22 -0400
commita35b7f7517b6d4c351d95acba3b87aa786c90f05 (patch)
tree8428daf69832da7457e9e05b9beefcacee9f1adb /Data/OpenPGP
parent660d5f111fee62ded78ffb622b063e4818c32928 (diff)
More big-num changes.
Diffstat (limited to 'Data/OpenPGP')
-rw-r--r--Data/OpenPGP/Internal.hs55
-rw-r--r--Data/OpenPGP/Util.hs2
2 files changed, 54 insertions, 3 deletions
diff --git a/Data/OpenPGP/Internal.hs b/Data/OpenPGP/Internal.hs
index b2bd506..24330f1 100644
--- a/Data/OpenPGP/Internal.hs
+++ b/Data/OpenPGP/Internal.hs
@@ -1,7 +1,16 @@
1{-# LANGUAGE BangPatterns #-}
1module Data.OpenPGP.Internal where 2module Data.OpenPGP.Internal where
2 3
3import Data.Word 4import Data.Bits
4import Data.Bits 5import qualified Data.ByteString as BS
6import qualified Data.ByteString.Internal as BS
7import Data.Word
8import Foreign.ForeignPtr
9import Foreign.Ptr
10import Foreign.Storable
11import System.Endian
12import System.IO.Unsafe
13
5 14
6decode_s2k_count :: Word8 -> Word32 15decode_s2k_count :: Word8 -> Word32
7decode_s2k_count c = (16 + (fromIntegral c .&. 15)) `shiftL` 16decode_s2k_count c = (16 + (fromIntegral c .&. 15)) `shiftL`
@@ -18,3 +27,45 @@ encode_s2k_count iterations
18 encode_s2k_count' count c 27 encode_s2k_count' count c
19 | count < 32 = (count, c) 28 | count < 32 = (count, c)
20 | otherwise = encode_s2k_count' (count `shiftR` 1) (c+1) 29 | otherwise = encode_s2k_count' (count `shiftR` 1) (c+1)
30
31getBigNum :: BS.ByteString -> Integer
32getBigNum bytes = unsafeDupablePerformIO $
33 let (fptr,offset,len) = BS.toForeignPtr bytes
34 in withForeignPtr fptr $ \ptr -> do
35 let p = ptr `plusPtr` offset :: Ptr Word64
36 e = p `plusPtr` (len .&. complement 7)
37 e2 = e `plusPtr` (len .&. 7)
38 go !p !a
39 | p==e = return a
40 | otherwise = do
41 w64 <- fromBE64 <$> peek p
42 let a' = (a `shiftL` 64) + fromIntegral w64
43 go (p `plusPtr` 8) a'
44 go2 !p !a
45 | p==e2 = return a
46 | otherwise = do
47 w8 <- peek p
48 let a' = a * 256 + fromIntegral w8
49 go2 (p `plusPtr` 1) a'
50 a <- go p 0
51 go2 (castPtr e :: Ptr Word8) a
52
53{-
54unchunk :: L.ByteString -> BS.ByteString
55unchunk b = L.toStrict $ foldr reappend L.empty $ L.toChunks b
56
57reappend :: BS.ByteString -> BS.ByteString -> Maybe BS.ByteString
58reappend a b =
59 let (ap,ao,al) = BS.toForeignPtr a
60 (bp,bo,bl) = BS.toForeignPtr b
61 in if ap == bp && ao+al == bo
62 then Just $ BS.PS ap ao (al+bl)
63 else Nothing
64
65reconsChunk :: S.ByteString -> L.ByteString -> L.ByteString
66reconsChunk b bs = case L.toChunks bs of
67 (c:cs) -> case reappend b c of
68 Just x -> L.fromChunks (x:cs)
69 Nothing -> L.fromChunks (b:c:cs)
70 _ -> L.fromChunks [b]
71-}
diff --git a/Data/OpenPGP/Util.hs b/Data/OpenPGP/Util.hs
index 6b1ebb1..1f9277d 100644
--- a/Data/OpenPGP/Util.hs
+++ b/Data/OpenPGP/Util.hs
@@ -1,4 +1,4 @@
1module Data.OpenPGP.Util 1module Data.OpenPGP.Util
2 ( fingerprint 2 ( fingerprint
3 , decryptSecretKey 3 , decryptSecretKey
4 , encryptSecretKey 4 , encryptSecretKey