summaryrefslogtreecommitdiff
path: root/lib
diff options
context:
space:
mode:
Diffstat (limited to 'lib')
-rw-r--r--lib/Base58.hs70
-rw-r--r--lib/CommandLine.hs559
-rw-r--r--lib/Compat.hs58
-rw-r--r--lib/ControlMaybe.hs29
-rw-r--r--lib/CryptoCoins.hs70
-rw-r--r--lib/DotLock.hs45
-rw-r--r--lib/FunctorToMaybe.hs69
-rw-r--r--lib/Hosts.hs314
-rw-r--r--lib/KeyRing.hs3583
-rw-r--r--lib/Numeric/Interval.hs754
-rw-r--r--lib/Numeric/Interval/Bounded.hs9
-rw-r--r--lib/PEM.hs34
-rw-r--r--lib/ProcessUtils.hs45
-rw-r--r--lib/ScanningParser.hs74
-rw-r--r--lib/SuperOrd.hs23
-rw-r--r--lib/TimeUtil.hs128
-rw-r--r--lib/dotlock.c1303
-rw-r--r--lib/dotlock.h112
18 files changed, 7279 insertions, 0 deletions
diff --git a/lib/Base58.hs b/lib/Base58.hs
new file mode 100644
index 0000000..3c1a113
--- /dev/null
+++ b/lib/Base58.hs
@@ -0,0 +1,70 @@
1{-# LANGUAGE CPP #-}
2module Base58 where
3
4#if !defined(VERSION_cryptonite)
5import qualified Crypto.Hash.SHA256 as SHA256
6#else
7import Crypto.Hash
8import Data.ByteArray (convert)
9#endif
10import qualified Data.ByteString as S
11import Data.Maybe
12import Data.List
13import Data.Word ( Word8 )
14import Control.Monad
15
16base58chars :: [Char]
17base58chars = "123456789ABCDEFGHJKLMNPQRSTUVWXYZabcdefghijkmnopqrstuvwxyz"
18
19base58digits :: [Char] -> Maybe [Int]
20base58digits str = sequence mbs
21 where
22 mbs = map (flip elemIndex base58chars) str
23
24-- 5HueCGU8rMjxEXxiPuD5BDku4MkFqeZyd4dZ1jvhTVqvbTLvyTJ
25base58_decode :: [Char] -> Maybe (Word8,[Word8])
26base58_decode str = do
27 ds <- base58digits str
28 let n = foldl' (\a b-> a*58 + b) 0 $ ( map fromIntegral ds :: [Integer] )
29 rbytes = unfoldr getbyte n
30 getbyte d = do
31 guard (d/=0)
32 let (q,b) = d `divMod` 256
33 return (fromIntegral b,q)
34
35 let (rcksum,rpayload) = splitAt 4 $ rbytes
36 a_payload = reverse rpayload
37#if !defined(VERSION_cryptonite)
38 hash_result = S.take 4 . SHA256.hash . SHA256.hash . S.pack $ a_payload
39#else
40 hash_result = S.take 4 . convert $ digest
41 where digest = hash (S.pack a_payload) :: Digest SHA256
42#endif
43 expected_hash = S.pack $ reverse rcksum
44 (network_id,payload) = splitAt 1 a_payload
45
46 network_id <- listToMaybe network_id
47 guard (hash_result==expected_hash)
48 return (network_id,payload)
49
50base58_encode :: S.ByteString -> String
51base58_encode hsh = replicate zcount '1' ++ map (base58chars !!) (reverse rdigits)
52 where
53 zcount = S.length . S.takeWhile (==0) $ hsh
54#if !defined(VERSION_cryptonite)
55 cksum = S.take 4 . SHA256.hash . SHA256.hash $ hsh
56#else
57 cksum = S.take 4 (convert digest2 :: S.ByteString)
58 where digest2 = hash ( convert digest1 :: S.ByteString) :: Digest SHA256
59 digest1 = hash hsh :: Digest SHA256
60#endif
61 n = foldl' (\a b->a*256+b) 0 . map asInteger $ concatMap S.unpack [hsh, cksum]
62 asInteger x = fromIntegral x :: Integer
63 rdigits = unfoldr getdigit n
64 where
65 getdigit d = do
66 guard (d/=0)
67 let (q,b) = d `divMod` 58
68 return (fromIntegral b,q)
69
70
diff --git a/lib/CommandLine.hs b/lib/CommandLine.hs
new file mode 100644
index 0000000..dfc16f9
--- /dev/null
+++ b/lib/CommandLine.hs
@@ -0,0 +1,559 @@
1{-# LANGUAGE DeriveFunctor #-}
2{-# LANGUAGE CPP #-}
3-- {-# LANGUAGE RankNTypes #-}
4{-# LANGUAGE BangPatterns #-}
5{-# LANGUAGE GADTs #-}
6{-# LANGUAGE StandaloneDeriving #-}
7{-# LANGUAGE PatternGuards #-}
8module CommandLine
9 ( Args
10 , UsageError(..)
11 , usageErrorMessage
12 , parseInvocation
13 , runArgs
14 , arg
15 , param
16 , params
17 , label
18 ) where
19
20import Control.Applicative
21import Control.Arrow
22import Control.Monad
23import Data.Bits
24import Data.Either
25import Data.Function
26import Data.List
27import Data.Maybe
28import Data.Ord
29import Data.Map.Strict (Map)
30import qualified Data.Map.Strict as Map
31import Data.IntMap.Strict (IntMap)
32import qualified Data.IntMap.Strict as IntMap
33import Debug.Trace
34import Numeric.Interval (Interval(..), singleton, (...), inf, sup, hull)
35import qualified Numeric.Interval as I
36import Numeric.Interval.Bounded
37import SuperOrd
38
39-- trace :: String -> a -> a
40-- trace _ x = x
41
42-- type CompF a = [String] -> [String] -> a
43
44type MergeData = [(Int,Ordering)]
45
46-- | Expr a
47--
48data Expr a where
49 -- | Prim
50 --
51 -- Takes a function from the option arguments and unamed arguments repsectively to
52 -- a value of type a, usually IO (), and gives you an expression tree. As one
53 -- traverses down the tree only the 'interesting' option arguments are passed
54 -- to this function, but all of the unnamed arguments are passed regardless of
55 -- where we are in the tree.
56 --
57 Prim :: ([[String]] -> [String] -> a) -> Interval (SuperOrd Int) -> Expr a
58 -- | Star
59 -- Applicative '<*>'
60 Star :: MergeData -> Expr (b -> a) -> (Expr b) -> Expr a
61 -- | Or
62 -- Alternative '<|>'
63 Or :: MergeData -> Expr a -> Expr a -> Expr a
64 -- | Empty
65 -- Alternative empty
66 Empty :: Expr a
67
68deriving instance Functor Expr
69
70-- | Args
71--
72-- Applicative Functor for interpretting command line arguments.
73data Args a = Args
74 { expr :: Expr a
75 -- ^ Expression tree
76 , accepts :: [String]
77 -- ^ sorted list of acceptable short and long option names (non positional arguments)
78 -- The names include hyphens.
79 }
80 deriving Functor
81
82instance Applicative Args where
83 pure x = Args { expr = Prim (\_ _ -> x) (singleton $ exactly 0), accepts = [] }
84 f <*> b = Args
85 { expr = Star d (expr f) (expr b)
86 , accepts = m
87 }
88 where d = mergeData compare (accepts f) (accepts b)
89 m = mergeLists d const (accepts f) (accepts b)
90
91instance Alternative Args where
92 empty = Args Empty []
93 f <|> g = Args
94 { expr = Or d (expr f) (expr g)
95 , accepts = m
96 }
97 where d = mergeData compare (accepts f) (accepts g)
98 m = mergeLists d const (accepts f) (accepts g)
99
100
101{- dead code?
102unpackBits :: Integer -> [Bool]
103unpackBits 0 = [False]
104unpackBits 1 = [True]
105unpackBits n = ( r /= 0 ) : unpackBits q
106 where
107 (q,r) = divMod n 2
108
109-- requires finite list
110packBits :: [Bool] -> Integer
111packBits bs = sum $ zipWith (\b n -> if b then n else 0) bs $ iterate (*2) 1
112 -}
113
114
115-- | mergeData
116--
117-- > mergeData compare [1,3,5] [2,2,4,6] ==> [(1,LT),(2,GT),(1,LT),(1,GT),(1,LT),(1,GT)]
118--
119-- Given a comparison function and two sorted lists, 'mergeData' will return
120-- a RLE compressed (run-length encoded) list of the comparison results
121-- encountered while merging the lists.
122--
123-- This data is enough information to perform the merge without doing the
124-- comparisons or to reverse a merged list back to two sorted lists.
125--
126-- When one list is exausted, the length of the remaining list is returned as
127-- a run-length for LT or GT depending on whether the left list or the right
128-- list has elements.
129mergeData :: (a -> a -> Ordering) -> [a] -> [a] -> [(Int,Ordering)]
130mergeData comp (x:xs) (y:ys)
131 | comp x y == LT = case mergeData comp xs (y:ys) of
132 (n,LT):ys -> let n'=n+1 in n' `seq` (n',LT):ys
133 ys -> (1,LT):ys
134 | comp x y == EQ = case mergeData comp xs ys of
135 (n,EQ):ys -> let n'=n+1 in n' `seq` (n',EQ):ys
136 ys -> (1,EQ):ys
137 | comp x y == GT = case mergeData comp (x:xs) ys of
138 (n,GT):ys -> let n'=n+1 in n' `seq` (n',GT):ys
139 ys -> (1,GT):ys
140mergeData comp [] [] = []
141mergeData comp [] ys = (length ys, GT) : []
142mergeData comp xs [] = (length xs, LT) : []
143
144mergeLists :: [(Int,Ordering)] -> (a -> a -> a) -> [a] -> [a] -> [a]
145mergeLists ((n,LT):os) f xs ys = ls ++ mergeLists os f xs' ys
146 where
147 (ls,xs') = splitAt n xs
148mergeLists ((n,EQ):os) f xs ys = es ++ mergeLists os f xs' ys'
149 where
150 (les,xs') = splitAt n xs
151 (res,ys') = splitAt n ys
152 es = zipWith f les res
153mergeLists ((n,GT):os) f xs ys = gs ++ mergeLists os f xs ys'
154 where
155 (gs,ys') = splitAt n ys
156mergeLists [] f [] ys = ys
157mergeLists [] f xs [] = xs
158mergeLists [] f xs ys = error "xs ++ ys"
159
160{-
161computeMask :: Int -> Ordering -> Ordering -> [(Int,Ordering)] -> Integer
162computeMask k w t [] = 0
163computeMask k w t ((n,v):os)
164 = if w==v then r .|. shiftL (bit n - 1) k
165 else r
166 where r = computeMask (k+n') w t os
167 n' | v==t = n
168 | otherwise = 0
169
170-- WRONG, one-blocks are not spaced the same in input and output, need shifts
171mergeIntegers :: [(Int,Ordering)] -> (Integer -> Integer -> Integer) -> Integer -> Integer -> Integer
172mergeIntegers os f x y = (leftmask .&. x) .|. (rightmask .&. y) .|. (f (leqmask .&. x) (reqmask .&. y))
173 where
174 leftmask = computeMask 0 LT EQ os
175 leqmask = computeMask 0 EQ LT os
176 reqmask = computeMask 0 EQ GT os
177 rightmask = computeMask 0 GT EQ os
178-}
179{- kinda dead code
180mergeIntegers ((n,LT):os) f !x !y = v `seq` m `seq` m .|. v
181 where
182 m = x .&. (bit n - 1)
183 r = mergeIntegers os f (shiftR x n) y
184 v = r `seq` shiftL r n
185mergeIntegers ((n,EQ):os) f !x !y = mm `seq` v `seq` mm .|. v
186 where
187 mm = f mx my
188 mx = x .&. (bit n - 1)
189 my = y .&. (bit n - 1)
190 r = mergeIntegers os f (shiftR x n) (shiftR y n)
191 v = r `seq` shiftL r n
192mergeIntegers ((n,GT):os) f !x !y = v `seq` m `seq` m .|. v
193 where
194 m = y .&. (bit n - 1)
195 r = mergeIntegers os f x (shiftR y n)
196 v = r `seq` shiftL r n
197mergeIntegers [] f !0 !y = y
198mergeIntegers [] f !x !0 = x
199mergeIntegers [] f !x !y = error "x .|. y"
200-}
201
202splitLists :: [(Int,Ordering)] -> [a] -> ([a],[a])
203splitLists ((n,LT):os) xs = (ls ++ lls, rrs)
204 where
205 (ls,xs') = splitAt n xs
206 (lls,rrs) = splitLists os xs'
207splitLists ((n,EQ):os) xs = (es ++ lls, es ++ rrs)
208 where
209 (es,xs') = splitAt n xs
210 (lls,rrs) = splitLists os xs'
211splitLists ((n,GT):os) xs = (lls, rs ++ rrs)
212 where
213 (rs,xs') = splitAt n xs
214 (lls,rrs) = splitLists os xs'
215splitLists [] xs = (xs,xs)
216
217{-
218mergeBy :: Show a => (a -> a -> Ordering) -> [a] -> [a]
219 -> ( (Integer -> Integer -> Integer) -> Integer -> Integer -> Integer
220 , (b -> b -> b) -> [b] -> [b] -> [b]
221 , [b] -> ([b], [b]))
222mergeBy comp xs ys = trace (unlines ["xs="++show xs,"ys="++show ys,"mergeData="++show d]) (mergeIntegers d, mergeLists d, splitLists d)
223 where
224 d = mergeData comp xs ys
225-}
226
227
228param :: Int -> Args String
229param n = Args (Prim (\_ us -> us!!n) (singleton $ exactly (n+1))) []
230
231arg :: String -> Args String
232arg optname = Args (Prim (\opts _ -> head $ concat $ take 1 opts)
233 (singleton $ exactly 0))
234 [optname]
235
236params :: Args [String]
237params = Args (Prim (\_ args -> args) (exactly 0 ... PositiveInfinity)) []
238
239
240label :: String -> Args a -> Args a
241label _ = id
242
243data ArgsStyle = ArgsStyle
244 { parseInvocation :: String -> [String] -> ([(String,[String])], [String])
245 }
246
247-- | Phase 1. This function accepts a list of command line arguments in its
248-- second argument that will be parsed to obtain a pair of lists: named
249-- argument-value pairs and unnamed arguments values.
250--
251-- The first argument indicates which short options will be treated as on/off
252-- flags and given a dummy value of \"\". Hyphen-prefixed options not in this
253-- list are given their imeediately following string as a value.
254--
255-- The \"--\" convention is implemented to indicate all remaining arguments are
256-- unnamed argument values.
257--
258-- The results of this function are intended to be used as input to 'runArgs'.
259vanilla :: ArgsStyle
260vanilla = ArgsStyle { parseInvocation = parse }
261 where
262 parse flags cli = (opts, concat nons ++ nondashed ++ drop 1 trailing)
263 where
264 (as, trailing) = span (/= "--") cli
265 (nons,bs) = span ((==[True]) . map (not . isPrefixOf "-") . take 1) $ groupBy (const $ not . isPrefixOf "-") as
266 (ds, nondashed) = second concat $ unzip $ map splitParams bs
267 opts = map ((first concat) . splitAt 1) (ds :: [[String]])
268
269 splitParams (('-':[x]):xs) | x `elem` flags = (['-':[x]],xs)
270 splitParams xs = splitAt 2 xs
271
272-- | Information about how the user failed to satisfy a specified usage.
273data UsageError
274 = TooManyParameters Int
275 -- ^ The given number of excessive unnamed arguments occured.
276 | InsufficientParameters Int
277 -- ^ Not enough unnamed arguments. The number indicates how many are
278 -- total are expected.
279 | TooManyOf String [String]
280 -- ^ An option was supplied too many times. The list is a set of values
281 -- associated with the repeated instances.
282 | Missing [String]
283 -- ^ A list of required options that the user failed to specify.
284 | ChooseOne [[String]]
285 -- ^ The user failed to choose one of the given set of option combinations.
286 | Misunderstood [String]
287 -- ^ A list of unrecognized options.
288 | Incompatible [[String]]
289 -- ^ A list of supplied options that may not be used together.
290
291 | NamedFailure String UsageError
292 -- ^ Extra context provided via the 'label' primitive.
293
294 deriving (Eq,Show)
295
296-- | Obtain a description of a usage error that can be reported to the user.
297usageErrorMessage :: UsageError -> String
298usageErrorMessage (NamedFailure _ e) = usageErrorMessage e
299usageErrorMessage (TooManyParameters _) = "too many arguments"
300usageErrorMessage (InsufficientParameters c) = "insufficient arguments (need "++show c++")"
301usageErrorMessage (TooManyOf n xs) = n ++" can be specified only once"
302usageErrorMessage (Missing ns) = "missing: "++intercalate ", " ns
303usageErrorMessage (ChooseOne nss) = "choose one of: "++intercalate ", " (map (intercalate " ") nss)
304usageErrorMessage (Misunderstood ns) = "unrecognized: "++intercalate ", " ns
305usageErrorMessage (Incompatible nss) = intercalate " and " (map (intercalate " ") nss) ++ " cannot be used together"
306
307{-
308rankError :: UsageError -> Int
309rankError (NamedFailure _ e) = rankError e
310rankError (TooManyParameters _) = 0
311rankError (InsufficientParameters _) = 1
312rankError (TooManyOf _ xs) = 1
313rankError (Missing _) = 2
314rankError (ChooseOne _) = 2
315rankError (Misunderstood xs) = 2 + length xs
316rankError (Incompatible ys) = 2 + length ys
317
318tagError :: UsageError -> Int
319tagError (NamedFailure _ _) = 0
320tagError (TooManyParameters _) = 1
321tagError (InsufficientParameters _) = 2
322tagError (TooManyOf _ _) = 3
323tagError (Missing _) = 4
324tagError (ChooseOne _) = 5
325tagError (Misunderstood _) = 6
326tagError (Incompatible _) = 7
327
328missingWhat :: UsageError -> [[String]]
329missingWhat (Missing xs) = [xs]
330missingWhat (ChooseOne ys) = ys
331missingWhat (NamedFailure _ e) = missingWhat e
332missingWhat _ = []
333
334misunderstoodWhat :: UsageError -> [String]
335misunderstoodWhat (Misunderstood xs) = xs
336misunderstoodWhat (Incompatible yss) = concatMap (take 1) yss
337misunderstoodWhat (NamedFailure _ e) = misunderstoodWhat e
338misunderstoodWhat _ = []
339-}
340
341{- dead code
342tryCompute :: [(String,String)] -> [String] -> Computation a -> Either UsageError a
343tryCompute os us c@(Computation { compLabel = lbl })
344 | null lbl = tryCompute' os us c
345 | otherwise = either (Left . NamedFailure lbl) Right $ tryCompute' os us c
346 where
347 tryCompute' os us c
348 | not (null unused_os) = Left $ Misunderstood $ map fst unused_os
349 | not (null missing) = Left $ Missing missing
350 | not (null repss) = Left $ TooManyOf (fst $ head $ head repss) (map snd $ head repss)
351 | ulen < clen = Left $ InsufficientParameters clen
352 | ulen > clen = Left $ TooManyParameters (ulen - clen)
353 | otherwise = Right $ compute c os us
354 where
355 (found, missing) = partition (\k -> k `elem` map fst os) $ consumedOptions c
356 (used_os, unused_os) = partition (\(k,v) -> k `elem` consumedOptions c) os
357 ulen = length us
358 repss = filter (not . null . tail) $ groupBy ((==) `on` fst) $ sortBy (comparing fst) used_os
359 clen = case consumedParameters c of
360 -1 -> ulen
361 num -> num
362-}
363
364#if defined(VERSION_base)
365#if !MIN_VERSION_base(4,8,0)
366sortOn :: Ord b => (a -> b) -> [a] -> [a]
367sortOn f =
368 map snd . sortBy (comparing fst) . map (\x -> let y = f x in y `seq` (y, x))
369#endif
370#endif
371
372removeIntersection (x:xs) (y:ys)
373 | x == y = removeIntersection xs ys
374 | x < y = first (x :) $ removeIntersection xs (y:ys)
375 | x > y = second (y :) $ removeIntersection (x:xs) ys
376removeIntersection [] ys = ([],ys)
377removeIntersection xs [] = (xs,[])
378
379
380-- ordinary sorted list merge.
381mergeL :: Ord a => [a] -> [a] -> [a]
382mergeL as bs = mergeLists (mergeData compare as bs) const as bs
383
384-- | runArgs
385--
386-- (os,us) - named arguments(options, name-value pairs), and unnamed arguments
387-- c - expression tree (applicative functor)
388--
389-- returns either a UsageError or a computed result (perhaps IO ())
390--
391-- Evaluate the given set of named and unnamed values and return
392-- the computed result or else indicate bad usage.
393--
394-- 'parseInvocation' may be used on the results of 'System.Environment.getArgs'
395-- to obtain suitable input for this function.
396runArgs :: ([(String,[String])], [String]) -> Args a -> Either UsageError a
397runArgs (os,us) c
398 | not (null bads) = Left $ Misunderstood $ map fst bads
399 | not (null dups) = Left $ TooManyOf (fst $ head dups) (concat $ take 1 $ snd $ head dups) -- only reports first dup.
400 | otherwise = makeError $ compute (expr c) (zipWith const [0..] (accepts c)) us
401 where
402 os' = sortOn fst os
403 dups = mapMaybe notSingle $ groupBy ((==) `on` fst) (os' :: [(String,[String])])
404 where notSingle [x] = Nothing
405 notSingle ((k,v):xs) = Just (k,v : map snd xs)
406 getbit = let r = Map.fromList $ zip (accepts c) [0..] in trace ("getbit = "++show r) r
407 goods :: [(Int,[String])]
408 (bads,goods) = let r = partitionEithers $ map f os' in trace ("(bads,goods)="++show r) r
409 where f (k,v) = case Map.lookup k getbit of
410 Just b -> Right (b,v)
411 Nothing -> Left (k,v)
412
413 valmap = IntMap.fromList goods
414 namemap = IntMap.fromList $ zip [0..] (accepts c)
415
416 vals = map snd goods
417 ulen = length us
418
419 makeError (_,Left e) = Left $ makeError' e
420 where
421 makeError' (Left xss) = Incompatible $ map (map (namemap IntMap.!)) xss
422 makeError' (Right [xs]) = Missing $ map (namemap IntMap.!) xs
423 makeError' (Right xss) = ChooseOne $ map (map (namemap IntMap.!)) xss
424 makeError (i,Right v)
425 | exactly ulen > sup i = Left $ TooManyParameters (ulen - superApprox (sup i))
426 | exactly ulen < inf i = Left $ InsufficientParameters (superApprox (inf i))
427 | otherwise = Right v
428
429
430 -- On success, returns Right, otherwise:
431 --
432 -- * @ Left (Right xss) @ - xss indicates unspecified required named-options.
433 --
434 -- * @ Left (Left xss) @ - xss is a list of mutually-exclusive sets of specified options.
435 --
436 compute :: Expr a -> [Int] -> [String] -> (Interval (SuperOrd Int), Either (Either [[Int]] [[Int]]) a)
437 compute (Prim f i) opts us
438 | null es = (i, Right $ f vals us )
439 | otherwise = (i, Left $ Right [es])
440 where
441 (es,vals) = partitionEithers
442 $ map (\k -> maybe (Left k) Right (k `IntMap.lookup` valmap)) opts
443 compute (Star d f b) opts us = (max (inf fi) (inf bi) ... max (sup fi) (sup bi), r)
444 where
445 r = case (fres,bres) of
446 (Right ff , Right bb) -> Right $ ff bb
447 (Left e , Right _) -> Left e
448 (Right _ , Left e) -> Left e
449 (Left (Right ls) , Left (Right rs)) -> Left $ Right [ mergeL l r | l <- ls, r <- rs ]
450 (Left (Left ls) , Left (Left rs)) -> Left $ Left (ls ++ rs)
451 (Left e , Left (Right _)) -> Left e
452 (Left (Right _) , Left e ) -> Left e
453 (fopts,bopts) = splitLists d opts
454 (fi,fres) = compute f fopts us
455 (bi,bres) = compute b bopts us
456 compute (Or d f g) opts us
457 = case () of
458 () | null fonly
459 , null gonly
460 , Left (Right fms) <- fr
461 , Left (Right gms) <- gr -> (hi, Left $ Right $ fms ++ gms)
462
463 () | Left (Left fss) <- fr
464 , Left (Left gss) <- gr -> (hi, Left (Left (fss ++ gss)))
465
466 () | null gonly, Left _ <- gr -> (fi,fr)
467 () | null fonly, Left _ <- fr -> (gi,gr)
468
469 () | null gonly, Right _ <- fr -> (fi,fr)
470 () | null fonly, Right _ <- gr -> (gi,gr)
471
472 () | Left (Left fss) <- fr -> (hi, Left (Left ( filter (not . null) (gonly : map (filter (not . (`elem` gopts))) fss))))
473 () | Left (Left gss) <- gr -> (hi, Left (Left ( filter (not . null) (fonly : map (filter (not . (`elem` fopts))) gss))))
474 () -> (hi, Left (Left [fonly,gonly]))
475
476 where
477 (fopts,gopts) = splitLists d opts
478 (fonly,gonly) = (filterPresent *** filterPresent) $ removeIntersection fopts gopts
479 filterPresent = filter (`IntMap.member` valmap)
480 (fi,fr) = compute f fopts us
481 (gi,gr) = compute g gopts us
482 hi = hull fi gi
483 compute Empty _ _ = error "CommandLine: empty evaluation"
484
485{-
486-- | Phase 2. Evaluate the given set of named and unnamed values and return
487-- the computed result or else indicate bad usage.
488--
489-- 'parseInvocation' may be used on the results of 'System.Environment.getArgs'
490-- to obtain suitable input for this function.
491runArgsOlder :: ([(String,String)], [String]) -> ArgsOlder a -> Either UsageError a
492runArgsOlder (os,us) (ArgsOlder alts)
493 | not (null rs) = Right $ head rs
494 | not (null ls) = Left $ chooseError ls
495 | otherwise = Right $ error $ show (length alts,ls)
496 where
497 recs = map (tryCompute os us) alts
498 rs = rights recs
499 ls = lefts recs
500-}
501
502{-
503chooseError :: [UsageError] -> UsageError
504chooseError ls = case span ((==2) . rankError) $ sortOn rankError ls of
505 ([e],_) -> e
506 (e:es,_)
507 | overlap -> em
508 | otherwise -> -- trace ("ms="++show ms) $
509 case findPartition ms of
510 Just (xs@(_:_:_)) -> ChooseOne $ map return xs
511 _ -> em
512 where
513 em:ems = sortBy (comparing (maximum . map length . missingWhat)) (e:es)
514 ms = concatMap missingWhat (em:ems)
515 mi = foldr1 intersect ms
516 overlap = any null $ map (\\ mi) ms
517 (_,e:es) -> case takeWhile ((>2) . rankError) (e:es) of
518 [f] -> f
519 f:fs -> -- trace ("ws="++show (w:ws))
520 case u of
521 [_] -> f
522 _ -> Incompatible u
523 where u = foldr1 union $ w : takeWhile ((==wlen) . length) ws
524 w:ws = map misunderstoodWhat (f:fs)
525 wlen = length w
526 [] -> e
527-}
528
529
530{-
531-- Given a collection of sets, return a list of unique reprasentative members.
532findPartition :: Eq x => [[x]] -> Maybe [x]
533findPartition yss =
534 case sortBy (comparing length) yss of
535 []:_ -> Nothing
536 zss | not (null ds) -> Nothing
537 | otherwise -> _findPartition ps es xss3
538 where
539 (pss,xss0) = span isSingle zss
540 isSingle [x] = True
541 isSingle _ = False
542 ps = foldr union [] pss
543 xss1 = map (partition (`elem` ps)) xss0
544 (xss2,bs) = partition (null . fst) xss1
545 (cs,ds) = partition (null . drop 1 . fst) bs
546 es = foldr union [] $ map snd cs
547 xss3 = map snd xss2
548
549
550_findPartition :: Eq x => [x] -> [x] -> [[x]] -> Maybe [x]
551_findPartition ps qs [] = Just ps
552_findPartition ps qs (xs:xss)
553 | null cs = Nothing
554 | otherwise = listToMaybe ss
555 where
556 cs = filter (not . flip elem qs) xs
557 ts = init $ zipWith (\as (b:bs) -> (b,as++bs)) (inits cs) (tails cs)
558 ss = mapMaybe (\(t,tqs) -> _findPartition (t:ps) (tqs++qs) (filter (not . elem t) xss)) ts
559-}
diff --git a/lib/Compat.hs b/lib/Compat.hs
new file mode 100644
index 0000000..3b77851
--- /dev/null
+++ b/lib/Compat.hs
@@ -0,0 +1,58 @@
1{-# LANGUAGE CPP #-}
2module Compat where
3
4import Data.Bits
5import Data.Word
6import Data.ASN1.Types
7import Data.ASN1.Encoding
8import Data.ASN1.BinaryEncoding
9import Crypto.PubKey.RSA as RSA
10
11#if defined(VERSION_cryptonite)
12
13instance ASN1Object PublicKey where
14 toASN1 pubKey = \xs -> Start Sequence
15 : IntVal (public_n pubKey)
16 : IntVal (public_e pubKey)
17 : End Sequence
18 : xs
19 fromASN1 (Start Sequence:IntVal smodulus:IntVal pubexp:End Sequence:xs) =
20 Right (PublicKey { public_size = calculate_modulus modulus 1
21 , public_n = modulus
22 , public_e = pubexp
23 }
24 , xs)
25 where calculate_modulus n i = if (2 ^ (i * 8)) > n then i else calculate_modulus n (i+1)
26 -- some bad implementation will not serialize ASN.1 integer properly, leading
27 -- to negative modulus. if that's the case, we correct it.
28 modulus = toPositive smodulus
29 fromASN1 ( Start Sequence
30 : IntVal 0
31 : Start Sequence
32 : OID [1, 2, 840, 113549, 1, 1, 1]
33 : Null
34 : End Sequence
35 : OctetString bs
36 : xs
37 ) = let inner = either strError fromASN1 $ decodeASN1' BER bs
38 strError = Left .
39 ("fromASN1: RSA.PublicKey: " ++) . show
40 in either Left (\(k, _) -> Right (k, xs)) inner
41 fromASN1 _ =
42 Left "fromASN1: RSA.PublicKey: unexpected format"
43
44#endif
45
46toPositive :: Integer -> Integer
47toPositive int
48 | int < 0 = uintOfBytes $ bytesOfInt int
49 | otherwise = int
50 where uintOfBytes = foldl (\acc n -> (acc `shiftL` 8) + fromIntegral n) 0
51 bytesOfInt :: Integer -> [Word8]
52 bytesOfInt n = if testBit (head nints) 7 then nints else 0xff : nints
53 where nints = reverse $ plusOne $ reverse $ map complement $ bytesOfUInt (abs n)
54 plusOne [] = [1]
55 plusOne (x:xs) = if x == 0xff then 0 : plusOne xs else (x+1) : xs
56 bytesOfUInt x = reverse (list x)
57 where list i = if i <= 0xff then [fromIntegral i] else (fromIntegral i .&. 0xff) : list (i `shiftR` 8)
58
diff --git a/lib/ControlMaybe.hs b/lib/ControlMaybe.hs
new file mode 100644
index 0000000..659dab7
--- /dev/null
+++ b/lib/ControlMaybe.hs
@@ -0,0 +1,29 @@
1{-# LANGUAGE ScopedTypeVariables #-}
2module ControlMaybe where
3
4-- import GHC.IO.Exception (IOException(..))
5import Control.Exception as Exception (IOException(..),catch)
6
7
8withJust :: Monad m => Maybe x -> (x -> m ()) -> m ()
9withJust (Just x) f = f x
10withJust Nothing f = return ()
11
12whenJust :: Monad m => m (Maybe x) -> (x -> m ()) -> m ()
13whenJust acn f = do
14 x <- acn
15 withJust x f
16
17
18catchIO_ :: IO a -> IO a -> IO a
19catchIO_ a h = Exception.catch a (\(_ :: IOException) -> h)
20
21catchIO :: IO a -> (IOException -> IO a) -> IO a
22catchIO body handler = Exception.catch body handler
23
24handleIO_ :: IO a -> IO a -> IO a
25handleIO_ = flip catchIO_
26
27
28handleIO :: (IOException -> IO a) -> IO a -> IO a
29handleIO = flip catchIO
diff --git a/lib/CryptoCoins.hs b/lib/CryptoCoins.hs
new file mode 100644
index 0000000..f417036
--- /dev/null
+++ b/lib/CryptoCoins.hs
@@ -0,0 +1,70 @@
1{-# LANGUAGE ViewPatterns #-}
2module CryptoCoins where
3
4import Numeric
5import Data.Word
6import Data.Maybe
7
8data CoinNetwork = CoinNetwork
9 { network_name :: String
10 , public_byte_id :: Word8
11 , private_byte_id :: Word8
12 , source_code_uri :: String
13 }
14 deriving (Show,Read)
15
16-- For forks of bitcoin, grep sources for PUBKEY_ADDRESS
17-- That value + 0x80 will be the private_byte_id.
18-- information source: https://raw.github.com/zamgo/PHPCoinAddress/master/README.md
19coin_networks :: [CoinNetwork]
20coin_networks =
21 [ CoinNetwork "bitcoin" 0x00 0x80 "https://github.com/bitcoin/bitcoin"
22 , CoinNetwork "litecoin" 0x30 0xB0 "https://github.com/litecoin-project/litecoin"
23 , CoinNetwork "peercoin" 0x37 0xB7 "https://github.com/ppcoin/ppcoin" -- AKA: ppcoin
24 , CoinNetwork "namecoin" 0x34 0xB4 "https://github.com/namecoin/namecoin"
25 , CoinNetwork "bbqcoin" 0x05 0xD5 "https://github.com/overware/BBQCoin"
26 , CoinNetwork "bitbar" 0x19 0x99 "https://github.com/aLQ/bitbar"
27 , CoinNetwork "bytecoin" 0x12 0x80 "https://github.com/bryan-mills/bytecoin"
28 , CoinNetwork "chncoin" 0x1C 0x9C "https://github.com/CHNCoin/CHNCoin"
29 , CoinNetwork "devcoin" 0x00 0x80 "http://sourceforge.net/projects/galacticmilieu/files/DeVCoin"
30 , CoinNetwork "feathercoin" 0x0E 0x8E "https://github.com/FeatherCoin/FeatherCoin"
31 , CoinNetwork "freicoin" 0x00 0x80 "https://github.com/freicoin/freicoin"
32 , CoinNetwork "junkcoin" 0x10 0x90 "https://github.com/js2082/JKC"
33 , CoinNetwork "mincoin" 0x32 0xB2 "https://github.com/SandyCohen/mincoin"
34 , CoinNetwork "novacoin" 0x08 0x88 "https://github.com/CryptoManiac/novacoin"
35 , CoinNetwork "onecoin" 0x73 0xF3 "https://github.com/cre8r/onecoin"
36 , CoinNetwork "smallchange" 0x3E 0xBE "https://github.com/bfroemel/smallchange"
37 , CoinNetwork "terracoin" 0x00 0x80 "https://github.com/terracoin/terracoin"
38 , CoinNetwork "yacoin" 0x4D 0xCD "https://github.com/pocopoco/yacoin"
39 , CoinNetwork "bitcoin-t" 0x6F 0xEF ""
40 , CoinNetwork "bbqcoin-t" 0x19 0x99 ""
41 , CoinNetwork "bitbar-t" 0x73 0xF3 ""
42 ]
43 -- fairbrix - - https://github.com/coblee/Fairbrix
44 -- ixcoin - - https://github.com/ixcoin/ixcoin
45 -- royalcoin - - http://sourceforge.net/projects/royalcoin/
46
47lookupNetwork :: Eq a => (CoinNetwork -> a) -> a -> Maybe CoinNetwork
48lookupNetwork f b = listToMaybe $ filter (\n->f n==b) coin_networks
49
50nameFromSecretByte :: Word8 -> String
51nameFromSecretByte b = maybe (defaultName b) network_name (lookupNetwork private_byte_id b)
52 where
53 defaultName b = "?coin?"++hexit b
54 where
55 hexit b = pad0 $ showHex b ""
56 where pad0 [c] = '0':c:[]
57 pad0 cs = take 2 cs
58
59publicByteFromName :: String -> Word8
60publicByteFromName n = maybe (secretByteFromName n - 0x80)
61 -- exceptions to the above: bbqcoin, bytecoin
62 public_byte_id
63 (lookupNetwork network_name n)
64
65secretByteFromName :: String -> Word8
66secretByteFromName n = maybe (defaultID n) private_byte_id (lookupNetwork network_name n)
67 where
68 defaultID ('?':'c':'o':'i':'n':'?':(readHex->((x,_):_)))
69 = x
70 defaultID _ = 0x00
diff --git a/lib/DotLock.hs b/lib/DotLock.hs
new file mode 100644
index 0000000..af05f5d
--- /dev/null
+++ b/lib/DotLock.hs
@@ -0,0 +1,45 @@
1{-# LANGUAGE ForeignFunctionInterface #-}
2module DotLock
3 ( DotLock
4 , Flags
5 , dotlock_init
6 , dotlock_create
7 , dotlock_take
8 , dotlock_release
9 , dotlock_destroy
10 , dotlock_remove_lockfiles
11 , dotlock_set_fd
12 , dotlock_get_fd
13 , dotlock_disable
14 ) where
15
16import System.Posix.Types (Fd(..))
17import Foreign.C.String
18import Foreign.C.Types
19import Foreign.Ptr
20
21newtype DotLock = DotLockPtr (Ptr ())
22type Flags = Int
23
24foreign import ccall "dotlock_create" _dotlock_create_ptr :: Ptr Char -> Flags -> IO (Ptr ())
25
26foreign import ccall "dotlock_create" _dotlock_create :: CString -> Flags -> IO (Ptr ())
27
28dotlock_init :: IO ()
29dotlock_init = do
30 null_ptr <- _dotlock_create_ptr nullPtr 0
31 return ()
32
33dotlock_create :: FilePath -> Flags -> IO (Maybe DotLock)
34dotlock_create file flags = do
35 ptr <- withCString file (flip _dotlock_create flags)
36 if ptr == nullPtr then return Nothing else return (Just $ DotLockPtr ptr)
37
38
39foreign import ccall "dotlock_take" dotlock_take :: DotLock -> CLong -> IO CInt
40foreign import ccall "dotlock_release" dotlock_release :: DotLock -> IO CInt
41foreign import ccall "dotlock_destroy" dotlock_destroy :: DotLock -> IO ()
42foreign import ccall "dotlock_remove_lockfiles" dotlock_remove_lockfiles ::DotLock -> IO ()
43foreign import ccall "dotlock_set_fd" dotlock_set_fd :: DotLock -> Fd -> IO ()
44foreign import ccall "dotlock_get_fd" dotlock_get_fd :: DotLock -> IO Fd
45foreign import ccall "dotlock_disable" dotlock_disable :: IO ()
diff --git a/lib/FunctorToMaybe.hs b/lib/FunctorToMaybe.hs
new file mode 100644
index 0000000..658b024
--- /dev/null
+++ b/lib/FunctorToMaybe.hs
@@ -0,0 +1,69 @@
1---------------------------------------------------------------------------
2-- |
3-- Module : FunctorToMaybe
4--
5-- Maintainer : joe@jerkface.net
6-- Stability : experimental
7--
8-- Motivation: When parsing a stream of events, it is often desirable to
9-- let certain control events pass-through to the output stream without
10-- interrupting the parse. For example, the conduit package uses
11-- <http://hackage.haskell.org/package/conduit-1.0.13.1/docs/Data-Conduit.html#t:Flush Flush>
12-- which adds a special command to a stream and the blaze-builder-conduit
13-- package has <http://hackage.haskell.org/package/blaze-builder-conduit-1.0.0/docs/Data-Conduit-Blaze.html#g:2 conduits> that treat the nullary constructor with special significance.
14--
15-- But for other intermediary conduits, the nullary @Flush@ constructor may
16-- be noise that they should politely preserve in case it is meaningul downstream.
17-- If <http://hackage.haskell.org/package/conduit-1.0.13.1/docs/Data-Conduit.html#t:Flush Flush>
18-- implemented the 'FunctorToMaybe' type class, then 'functorToEither' could be used to
19-- seperate the noise from the work-product.
20--
21{-# LANGUAGE CPP #-}
22module FunctorToMaybe where
23
24#if MIN_VERSION_base(4,6,0)
25#else
26import Control.Monad.Instances()
27#endif
28
29-- | The 'FunctorToMaybe' class genaralizes 'Maybe' in that the
30-- there may be multiple null elements.
31--
32-- Instances of 'FunctorToMaybe' should satisfy the following laws:
33--
34-- > functorToMaybe (fmap f g) == fmap f (functorToMaybe g)
35--
36class Functor g => FunctorToMaybe g where
37 functorToMaybe :: g a -> Maybe a
38
39
40instance FunctorToMaybe Maybe where
41 functorToMaybe = id
42instance FunctorToMaybe (Either a) where
43 functorToMaybe (Right x) = Just x
44 functorToMaybe _ = Nothing
45
46
47-- | 'functorToEither' is a null-preserving cast.
48--
49-- If @functorToMaybe g == Nothing@, then a casted value is returned with Left.
50-- If @functorToMaybe g == Just a@, then @Right a@ is returned.
51--
52-- Returning to our <http://hackage.haskell.org/package/conduit-1.0.13.1/docs/Data-Conduit.html#t:Flush Flush>
53-- example, if we define
54--
55-- > instance Flush where
56-- > functorToMaybe Flush = Nothing
57-- > functorToMaybe (Chunk a) = Just a
58--
59-- Now stream processors can use 'functorToEither' to transform any nullary constructors while
60-- while doing its work to transform the data before forwarding it into
61-- <http://hackage.haskell.org/package/blaze-builder-conduit-1.0.0/docs/Data-Conduit-Blaze.html#v:builderToByteStringFlush builderToByteStringFlush>.
62--
63functorToEither :: FunctorToMaybe f => f a -> Either (f b) a
64functorToEither ga =
65 maybe (Left $ uncast ga)
66 Right
67 (functorToMaybe ga)
68 where
69 uncast = fmap (error "bad FunctorToMaybe instance")
diff --git a/lib/Hosts.hs b/lib/Hosts.hs
new file mode 100644
index 0000000..5f09de1
--- /dev/null
+++ b/lib/Hosts.hs
@@ -0,0 +1,314 @@
1{-# LANGUAGE CPP #-}
2{-# LANGUAGE ScopedTypeVariables #-}
3{-# LANGUAGE OverloadedStrings #-}
4#if ! MIN_VERSION_network(2,4,0)
5{-# LANGUAGE StandaloneDeriving #-}
6#endif
7module Hosts
8 ( Hosts
9 , assignName
10 , assignName'
11 , assignNewName
12 , removeName
13 , inet_pton
14 , inet_ntop
15 , empty
16 , hasName
17 , hasAddr
18 , encode
19 , decode
20 , diff
21 , plus
22 , filterAddrs
23 , namesForAddress
24 ) where
25
26import Data.Maybe
27import Data.Monoid ( (<>) )
28import Data.List as List (foldl', (\\) )
29import Data.Ord
30import Data.Char (isSpace)
31import qualified Data.Map as Map
32import Data.Map (Map)
33import qualified Data.ByteString.Lazy.Char8 as L
34import System.IO.Unsafe (unsafePerformIO)
35import Control.Applicative ( (<$>), (<*>) )
36import Control.Monad (mplus)
37import Network.Socket
38import ControlMaybe ( handleIO_ )
39
40#if ! MIN_VERSION_network(2,4,0)
41deriving instance Ord SockAddr
42#endif
43
44inet_pton :: String -> Maybe SockAddr
45inet_pton p = n
46 where
47 n = unsafePerformIO $ do
48 handleIO_ (return Nothing) $ do
49 info <- getAddrInfo safe_hints (Just p) Nothing
50 return $ fmap addrAddress $ listToMaybe info
51 safe_hints = Just $ defaultHints { addrFlags=[AI_NUMERICHOST] }
52
53inet_ntop :: SockAddr -> String
54inet_ntop n = p
55 where
56 p = case show n of
57 '[':xs -> fst $ break (==']') xs
58 xs -> fst $ break (==':') xs
59
60
61data Hosts = Hosts
62 { lineCount :: Int
63 , numline :: Map Int L.ByteString
64 , namenum :: Map L.ByteString [Int]
65 , addrnum :: Map SockAddr Int
66 }
67
68instance Show Hosts where
69 show = L.unpack . encode
70
71encode :: Hosts -> L.ByteString
72encode = L.unlines . map snd . Map.assocs . numline
73
74parseLine :: L.ByteString -> (Maybe SockAddr, [L.ByteString])
75parseLine s = (addr,names)
76 where
77 (addr0,names) = splitAt 1 $ L.words (uncom s)
78 addr = do
79 a <- fmap L.unpack $ listToMaybe addr0
80 n <- inet_pton a
81 return $ n -- inet_ntop n
82
83 uncom s = fst $ L.break (=='#') s
84
85empty :: Hosts
86empty = Hosts { lineCount = 0
87 , numline = Map.empty
88 , addrnum = Map.empty
89 , namenum = Map.empty
90 }
91
92{-
93parseHosts fname = do
94 input <- L.readFile fname
95 return $ decode input
96-}
97
98decode :: L.ByteString -> Hosts
99decode input =
100 let ls = L.lines input
101 ans = map (\l->(parseLine l,l)) ls
102 hosts = foldl' upd empty ans
103 upd hosts ((addr,names),line) = hosts
104 { lineCount = count
105 , numline = Map.insert count line (numline hosts)
106 , addrnum = maybeInsert (addrnum hosts) addr
107 , namenum = foldl' (\m x->Map.alter (cons count) x m)
108 (namenum hosts)
109 names
110 }
111 where count = lineCount hosts + 1
112 cons v xs = Just $ maybe [v] (v:) xs
113 maybeInsert m x = maybe m
114 (\x->Map.insert x count m)
115 x
116 in hosts
117
118
119hasName :: L.ByteString -> Hosts -> Bool
120hasName name hosts = Map.member name $ namenum hosts
121
122hasAddr :: SockAddr -> Hosts -> Bool
123hasAddr addr hosts = Map.member addr $ addrnum hosts
124
125scrubName ::
126 ([L.ByteString] -> [L.ByteString]) -> L.ByteString -> L.ByteString
127scrubName f line = line'
128 where
129 (x,ign) = L.break (=='#') line
130 ws = L.groupBy ( (==EQ) `oo` comparing isSpace) x
131 where oo = (.) . (.)
132 (a,ws') = splitAt 2 ws
133 ws'' = f ws'
134 line' = if null ws''
135 then if length a==2 then "" -- "# " <> L.concat a <> ign
136 else line
137 else if length a==2
138 then L.concat (a ++ ws'') <> ign
139 else let vs = L.groupBy ( (==EQ) `oo` comparing isSpace) $ L.dropWhile isSpace
140 $ L.tail ign
141 where oo = (.) . (.)
142 (a',vs') = splitAt 2 vs
143 vs'' = L.concat vs'
144 vs''' = if L.take 1 vs'' `elem` ["#",""]
145 then vs''
146 else "# " <> vs''
147 in L.concat (a'++ws'') <> vs'''
148
149assignName :: SockAddr -> L.ByteString -> Hosts -> Hosts
150assignName addr name hosts = assignName' False addr name hosts
151
152chaddr :: Int -> SockAddr -> Hosts -> Hosts
153chaddr n addr hosts =
154 hosts { addrnum = Map.insert addr n (addrnum hosts)
155 , numline = Map.adjust re n (numline hosts) }
156 where
157 re line = if length a==2
158 then L.pack (inet_ntop addr) <> " " <> L.concat ws' <> ign
159 else line
160 where (x,ign) = L.break (=='#') line
161 ws = L.groupBy ( (==EQ) `oo` comparing isSpace) x
162 where oo = (.) . (.)
163 (a,ws') = splitAt 2 ws
164
165isLonerName line = length ws' <= 2
166 where (x,_) = L.break (=='#') line
167 ws = L.groupBy ( (==EQ) `oo` comparing isSpace) x
168 where oo = (.) . (.)
169 (_,ws') = splitAt 2 ws
170
171scrubTrailingEmpties :: Hosts -> Hosts
172scrubTrailingEmpties hosts =
173 hosts { lineCount = cnt'
174 , numline = foldl' (flip Map.delete) (numline hosts) es
175 }
176 where
177 cnt = lineCount hosts
178 es = takeWhile (\n -> Map.lookup n (numline hosts) == Just "")
179 $ [cnt,cnt-1..]
180 cnt' = cnt - length es
181
182cannonizeName :: L.ByteString -> L.ByteString -> L.ByteString
183cannonizeName name line = scrubName f line
184 where
185 f ws = [name," "] ++ pre ++ drop 2 rst
186 where
187 (pre,rst) = break (==name) ws
188
189removeName name hosts = hosts'
190 where
191 hosts' = scrubTrailingEmpties (maybe hosts (removeName0 name hosts) ns)
192 ns = Map.lookup name (namenum hosts)
193
194
195removeName0 name hosts nums = hosts
196 { namenum = Map.delete name (namenum hosts)
197 , numline = foldl' scrub (numline hosts) nums
198 }
199 where scrub m num = Map.adjust (scrubName $ filter (/=name)) num m
200
201assignName' :: Bool -> SockAddr -> L.ByteString -> Hosts -> Hosts
202assignName' iscannon addr name hosts = hosts'
203 where
204 ns = Map.lookup name (namenum hosts)
205 a = Map.lookup addr (addrnum hosts)
206 canonize numline n = Map.adjust (cannonizeName name) n numline
207 hosts' = do
208 if (== Just True) $ elem <$> a <*> ns
209 then if not iscannon then hosts -- address already has name, nothing to do
210 else hosts { numline = foldl' canonize (numline hosts) $ fromJust ns}
211 else
212 let hosts0 = -- remove name if it's present
213 scrubTrailingEmpties $ maybe hosts (removeName0 name hosts) ns
214 ns' = fmap (filter $
215 isLonerName
216 . fromJust
217 . (\n -> Map.lookup n (numline hosts)))
218 ns
219 >>= listToMaybe
220 hosts1 = -- insert name, or add new line
221 maybe (maybe (newLine hosts0)
222 (\n -> chaddr n addr $ appendName iscannon name hosts0 n)
223 ns')
224 (appendName iscannon name hosts0)
225 a
226 in hosts1
227 newLine hosts = hosts
228 { lineCount = cnt
229 , numline = Map.insert cnt line $ numline hosts
230 , addrnum = Map.insert addr cnt $ addrnum hosts
231 , namenum = Map.alter (cons cnt) name $ namenum hosts
232 }
233 where cnt = lineCount hosts + 1
234 line = L.pack (inet_ntop addr) <> " " <> name
235 cons v xs = Just $ maybe [v] (v:) xs
236
237assignNewName :: SockAddr -> L.ByteString -> Hosts -> Hosts
238assignNewName addr name hosts =
239 if hasName name hosts then hosts
240 else assignName' True addr name hosts
241
242appendName :: Bool -> L.ByteString -> Hosts -> Int -> Hosts
243appendName iscannon name hosts num = hosts
244 { numline = Map.adjust (scrubName f) num (numline hosts)
245 , namenum = Map.alter (cons num) name (namenum hosts)
246 }
247 where f ws = if iscannon
248 then [name, " "] ++ ws
249 else let rs = reverse ws
250 (sp,rs') = span (L.any isSpace) rs
251 in reverse $ sp ++ [name," "] ++ rs'
252 cons v xs = Just $ maybe [v] (v:) xs
253
254-- Returns a list of bytestrings intended to show the
255-- differences between the two host databases. It is
256-- assumed that no lines are deleted, only altered or
257-- appended.
258diff :: Hosts -> Hosts -> [L.ByteString]
259diff as bs = cs
260 where
261 [as',bs'] = map (L.lines . Hosts.encode) [as,bs]
262 ext xs = map Just xs ++ repeat Nothing
263 ds = takeWhile (isJust . uncurry mplus) $ zip (ext as') (ext bs')
264 es = filter (uncurry (/=)) ds
265 cs = do
266 (a,b) <- es
267 [a,b] <- return $ map maybeToList [a,b]
268 fmap ("- " <>) a ++ fmap ("+ " <>) b
269
270namesForAddress :: SockAddr -> Hosts -> [L.ByteString]
271namesForAddress addr hosts = snd $ _namesForAddress addr hosts
272
273_namesForAddress :: SockAddr -> Hosts -> (Int, [L.ByteString])
274_namesForAddress addr (Hosts {numline=numline, addrnum=addrnum}) = ns
275 where
276 ns = maybe (-1,[]) id $ do
277 n <- Map.lookup addr addrnum
278 line <- Map.lookup n numline
279 return (n, snd $ parseLine line)
280
281
282plus :: Hosts -> Hosts -> Hosts
283plus a b = Map.foldlWithKey' mergeAddr a (addrnum b)
284 where
285 mergeAddr a addr bnum = a'
286 where
287 (anum,ns) = _namesForAddress addr a
288 bs = maybe [] (List.\\ ns) $ do
289 line <- Map.lookup bnum (numline b)
290 return . snd $ parseLine line
291 a' = if anum/=(-1) then foldl' app a $ reverse bs
292 else newLine a
293 app a b = appendName True b a anum -- True to allow b to reassign cannonical name
294 newLine hosts = hosts
295 { lineCount = cnt
296 , numline = Map.insert cnt line $ numline hosts
297 , addrnum = Map.insert addr cnt $ addrnum hosts
298 , namenum = foldl' updnamenum (namenum hosts) bs
299 }
300 where cnt = lineCount hosts + 1
301 line = L.pack (inet_ntop addr) <> " " <> L.intercalate " " bs
302 cons v xs = Just $ maybe [v] (v:) xs
303 updnamenum m name = Map.alter (cons cnt) name m
304
305filterAddrs :: (SockAddr -> Bool) -> Hosts -> Hosts
306filterAddrs pred hosts = hosts'
307 where
308 als = Map.toList (addrnum hosts)
309 nl = foldl' f (numline hosts) als
310 f m (addr,num) = if pred addr
311 then m
312 else Map.adjust (scrubName $ const []) num m
313 lines = L.unlines . Map.elems $ nl
314 hosts' = decode lines
diff --git a/lib/KeyRing.hs b/lib/KeyRing.hs
new file mode 100644
index 0000000..1c6dea8
--- /dev/null
+++ b/lib/KeyRing.hs
@@ -0,0 +1,3583 @@
1---------------------------------------------------------------------------
2-- |
3-- Module : KeyRing
4--
5-- Maintainer : joe@jerkface.net
6-- Stability : experimental
7--
8-- kiki is a command-line utility for manipulating GnuPG's keyring files. This
9-- module is the programmer-facing API it uses to do that.
10--
11-- Note: This is *not* a public facing API. I (the author) consider this
12-- library to be internal to kiki and subject to change at my whim.
13--
14-- Typically, a client to this module would prepare a 'KeyRingOperation'
15-- describing what he wants done, and then invoke 'runKeyRing' to make it
16-- happen.
17{-# LANGUAGE CPP #-}
18{-# LANGUAGE TupleSections #-}
19{-# LANGUAGE ViewPatterns #-}
20{-# LANGUAGE OverloadedStrings #-}
21{-# LANGUAGE DeriveFunctor #-}
22{-# LANGUAGE DoAndIfThenElse #-}
23{-# LANGUAGE NoPatternGuards #-}
24{-# LANGUAGE ForeignFunctionInterface #-}
25module KeyRing
26 (
27 -- * Error Handling
28 KikiResult(..)
29 , KikiCondition(..)
30 , KikiReportAction(..)
31 , errorString
32 , reportString
33 -- * Manipulating Keyrings
34 , runKeyRing
35 , KeyRingOperation(..)
36 , PassphraseSpec(..)
37 , Transform(..)
38 -- , PacketUpdate(..)
39 -- , guardAuthentic
40 -- * Describing File Operations
41 , StreamInfo(..)
42 , Access(..)
43 , FileType(..)
44 , InputFile(..)
45 , Initializer(..)
46 , KeyFilter(..)
47 -- * Results of a KeyRing Operation
48 , KeyRingRuntime(..)
49 , MappedPacket(..)
50 , KeyDB
51 , KeyData(..)
52 , SubKey(..)
53 , keyflags
54 -- * Miscelaneous Utilities
55 , isKey
56 , derRSA
57 , derToBase32
58 , backsig
59 , filterMatches
60 , flattenKeys
61 , flattenTop
62 , Hosts.Hosts
63 , isCryptoCoinKey
64 , matchpr
65 , parseSpec
66 , parseUID
67 , UserIDRecord(..)
68 , pkcs8
69 , RSAPublicKey(..)
70 , PKCS8_RSAPublicKey(..)
71 , rsaKeyFromPacket
72 , secretToPublic
73 , selectPublicKey
74 , selectSecretKey
75 , usage
76 , usageString
77 , walletImportFormat
78 , writePEM
79 , getBindings
80 , accBindings
81 , isSubkeySignature
82 , torhash
83 , ParsedCert(..)
84 , parseCertBlob
85 , packetFromPublicRSAKey
86 , decodeBlob
87 , selectPublicKeyAndSigs
88 , x509cert
89 , getHomeDir
90 , unconditionally
91 , SecretPEMData(..)
92 , readSecretPEMFile
93 , writeInputFileL
94 , InputFileContext(..)
95 , onionNameForContact
96 , keykey
97 , keyPacket
98 , KeySpec(..)
99 , getHostnames
100 , secretPemFromPacket
101 , getCrossSignedSubkeys
102 ) where
103
104import System.Environment
105import Control.Monad
106import Data.Maybe
107import Data.Either
108import Data.Char
109import Data.Ord
110import Data.List
111import Data.OpenPGP
112import Data.Functor
113import Data.Monoid
114import Data.Tuple ( swap )
115import Data.Bits ( (.|.), (.&.) )
116import Control.Applicative ( Applicative, pure, liftA2, (<*>) )
117import System.Directory ( getHomeDirectory, doesFileExist, createDirectoryIfMissing )
118import Control.Arrow ( first, second )
119import Data.OpenPGP.Util (verify,fingerprint,decryptSecretKey,pgpSign, generateKey, GenerateKeyParams(..))
120import Data.ByteString.Lazy ( ByteString )
121import Text.Show.Pretty as PP ( ppShow )
122import Data.Binary {- decode, decodeOrFail -}
123import ControlMaybe ( handleIO_ )
124import Data.ASN1.Types ( toASN1, ASN1Object, fromASN1
125 , ASN1(Start,End,IntVal,OID,BitString,Null), ASN1ConstructionType(Sequence) )
126import Data.ASN1.BitArray ( BitArray(..), toBitArray )
127import Data.ASN1.Encoding ( encodeASN1, encodeASN1', decodeASN1, decodeASN1' )
128import Data.ASN1.BinaryEncoding ( DER(..) )
129import Data.Time.Clock.POSIX ( POSIXTime, utcTimeToPOSIXSeconds )
130import Data.Time.Clock ( UTCTime )
131import Data.Bits ( Bits, shiftR )
132import Data.Text.Encoding ( encodeUtf8 )
133import qualified Data.Map as Map
134import qualified Data.ByteString.Lazy as L ( unpack, null, readFile, writeFile
135 , ByteString, toChunks, hGetContents, hPut, concat, fromChunks, splitAt
136 , index, break, pack )
137import qualified Data.ByteString as S ( ByteString, unpack, splitAt, concat, cons, spanEnd, hGetContents, readFile, breakSubstring, drop, length, null, hPutStr, singleton, unfoldr, reverse )
138import qualified Codec.Binary.Base32 as Base32
139import qualified Codec.Binary.Base64 as Base64
140#if !defined(VERSION_cryptonite)
141import qualified Crypto.Hash.SHA1 as SHA1
142import qualified Crypto.Types.PubKey.ECC as ECC
143#else
144import qualified Crypto.Hash as Vincent
145import Data.ByteArray (convert)
146import qualified Crypto.PubKey.ECC.Types as ECC
147#endif
148import qualified Data.X509 as X509
149import qualified Crypto.PubKey.RSA as RSA
150import qualified Codec.Compression.GZip as GZip
151import qualified Data.Text as T ( Text, unpack, pack,
152 strip, reverse, drop, break, dropAround, length )
153import qualified System.Posix.Types as Posix
154import System.Posix.Files ( modificationTime, getFileStatus, getFdStatus
155 , setFileCreationMask, setFileTimes )
156#if MIN_VERSION_x509(1,5,0)
157import Data.Hourglass.Types
158import Data.Hourglass
159#endif
160#if MIN_VERSION_unix(2,7,0)
161import System.Posix.Files ( setFdTimesHiRes )
162import Foreign.C.Types ( CTime(..), CLong, CInt(..) )
163#else
164import Foreign.C.Types ( CTime(..), CLong, CInt(..) )
165import Foreign.Marshal.Array ( withArray )
166import Foreign.Ptr
167import Foreign.C.Error ( throwErrnoIfMinus1_ )
168import Foreign.Storable
169#endif
170import System.FilePath ( takeDirectory )
171import System.IO (hPutStrLn,withFile,IOMode(..), Handle, hPutStr, stderr)
172import Data.IORef
173import System.Posix.IO ( fdToHandle )
174import qualified Data.Traversable as Traversable
175import Data.Traversable ( sequenceA )
176#if ! MIN_VERSION_base(4,6,0)
177import GHC.Exts ( Down(..) )
178#endif
179#if MIN_VERSION_binary(0,7,0)
180import Debug.Trace
181#endif
182import Network.Socket -- (SockAddr)
183import qualified Data.ByteString.Lazy.Char8 as Char8
184import Compat
185
186import TimeUtil
187import PEM
188import ScanningParser
189import qualified Hosts
190import qualified CryptoCoins
191import Base58
192import FunctorToMaybe
193import DotLock
194import ProcessUtils (systemEnv, ExitCode(ExitFailure, ExitSuccess) )
195
196-- DER-encoded elliptic curve ids
197-- nistp256_id = 0x2a8648ce3d030107
198secp256k1_id :: Integer
199secp256k1_id = 0x2b8104000a
200-- "\x2a\x86\x48\xce\x3d\x03\x01\x07"
201{- OID Curve description Curve name
202 ----------------------------------------------------------------
203 1.2.840.10045.3.1.7 NIST Curve P-256 [FIPS 186-2] "NIST P-256"
204 1.3.132.0.34 NIST Curve P-384 [FIPS 186-2] "NIST P-384"
205 1.3.132.0.35 NIST Curve P-521 [FIPS 186-2] "NIST P-521"
206
207 Implementations MUST implement "NIST P-256", "NIST P-384" and "NIST
208 P-521". The hexadecimal representation used in the public and
209 private key encodings are:
210
211 Curve Name Len Hexadecimal representation of the OID
212 ----------------------------------------------------------------
213 "NIST P-256" 8 0x2A, 0x86, 0x48, 0xCE, 0x3D, 0x03, 0x01, 0x07
214 "NIST P-384" 6 0x05, 0x2B, 0x81, 0x04, 0x00, 0x22
215 "NIST P-521" 6 0x05, 0x2B, 0x81, 0x04, 0x00, 0x23
216-}
217
218data HomeDir =
219 HomeDir { homevar :: String
220 , appdir :: String
221 , optfile_alts :: [String]
222 }
223
224home :: HomeDir
225home = HomeDir
226 { homevar = "GNUPGHOME"
227 , appdir = ".gnupg"
228 , optfile_alts = ["keys.conf","gpg.conf-2","gpg.conf"]
229 }
230
231data InputFile = HomeSec
232 -- ^ A file named secring.gpg located in the home directory.
233 -- See 'opHome'.
234 | HomePub
235 -- ^ A file named pubring.gpg located in the home directory.
236 -- See 'opHome'.
237 | ArgFile FilePath
238 -- ^ Contents will be read or written from the specified path.
239 | FileDesc Posix.Fd
240 -- ^ Contents will be read or written from the specified file
241 -- descriptor.
242 | Pipe Posix.Fd Posix.Fd
243 -- ^ Contents will be read from the first descriptor and updated
244 -- content will be writen to the second. Note: Don't use Pipe
245 -- for 'Wallet' files. (TODO: Wallet support)
246 | Generate Int GenerateKeyParams
247 -- ^ New key packets will be generated if there is no
248 -- matching content already in the key pool. The integer is
249 -- a unique id number so that multiple generations can be
250 -- inserted into 'opFiles'
251 deriving (Eq,Ord,Show)
252
253-- type UsageTag = String
254data Initializer = NoCreate | Internal GenerateKeyParams | External String
255 deriving (Eq,Ord,Show)
256
257data FileType = KeyRingFile
258 | PEMFile
259 | WalletFile
260 | DNSPresentation
261 | Hosts
262 deriving (Eq,Ord,Enum,Show)
263
264-- | Use this type to indicate whether a file of type 'KeyRingFile' is expected
265-- to contain secret or public PGP key packets. Note that it is not supported
266-- to mix both in the same file and that the secret key packets include all of
267-- the information contained in their corresponding public key packets.
268data Access = AutoAccess -- ^ secret or public as appropriate based on existing content.
269 -- (see 'rtRingAccess')
270 | Sec -- ^ secret information
271 | Pub -- ^ public information
272 deriving (Eq,Ord,Show)
273
274-- | Note that the documentation here is intended for when this value is
275-- assigned to 'fill'. For other usage, see 'spill'.
276data KeyFilter = KF_None -- ^ No keys will be imported.
277 | KF_Match String -- ^ Only the key that matches the spec will be imported.
278 | KF_Subkeys -- ^ Subkeys will be imported if their owner key is
279 -- already in the ring. TODO: Even if their signatures
280 -- are bad?
281 | KF_Authentic -- ^ Keys are imported if they belong to an authenticated
282 -- identity (signed or self-authenticating).
283 | KF_All -- ^ All keys will be imported.
284 deriving (Eq,Ord,Show)
285
286-- | This type describes how 'runKeyRing' will treat a file.
287data StreamInfo = StreamInfo
288 { access :: Access
289 -- ^ Indicates whether the file is allowed to contain secret information.
290 , typ :: FileType
291 -- ^ Indicates the format and content type of the file.
292 , fill :: KeyFilter
293 -- ^ This filter controls what packets will be inserted into a file.
294 , spill :: KeyFilter
295 --
296 -- ^ Use this to indicate whether or not a file's contents should be
297 -- available for updating other files. Note that although its type is
298 -- 'KeyFilter', it is usually interpretted as a boolean flag. Details
299 -- depend on 'typ' and are as follows:
300 --
301 -- 'KeyRingFile':
302 --
303 -- * 'KF_None' - The file's contents will not be shared.
304 --
305 -- * otherwise - The file's contents will be shared.
306 --
307 -- 'PEMFile':
308 --
309 -- * 'KF_None' - The file's contents will not be shared.
310 --
311 -- * 'KF_Match' - The file's key will be shared with the specified owner
312 -- key and usage tag. If 'fill' is also a 'KF_Match', then it must be
313 -- equal to this value; changing the usage or owner of a key is not
314 -- supported via the fill/spill mechanism.
315 --
316 -- * otherwise - Unspecified. Do not use.
317 --
318 -- 'WalletFile':
319 --
320 -- * The 'spill' setting is ignored and the file's contents are shared.
321 -- (TODO)
322 --
323 -- 'Hosts':
324 --
325 -- * The 'spill' setting is ignored and the file's contents are shared.
326 -- (TODO)
327 --
328 , initializer :: Initializer
329 -- ^ If 'typ' is 'PEMFile' and an 'External' 'initializer' string is set,
330 -- then it is interpretted as a shell command that may be used to create
331 -- the key if it does not exist.
332 , transforms :: [Transform]
333 -- ^ Per-file transformations that occur before the contents of a file are
334 -- spilled into the common pool.
335 }
336 deriving (Eq,Show)
337
338
339spillable :: StreamInfo -> Bool
340spillable (spill -> KF_None) = False
341spillable _ = True
342
343isMutable :: StreamInfo -> Bool
344isMutable (fill -> KF_None) = False
345isMutable _ = True
346
347isring :: FileType -> Bool
348isring (KeyRingFile {}) = True
349isring _ = False
350
351isSecretKeyFile :: FileType -> Bool
352isSecretKeyFile PEMFile = True
353isSecretKeyFile DNSPresentation = True
354isSecretKeyFile _ = False
355
356{-
357pwfile :: FileType -> Maybe InputFile
358pwfile (KeyRingFile f) = f
359pwfile _ = Nothing
360-}
361
362iswallet :: FileType -> Bool
363iswallet (WalletFile {}) = True
364iswallet _ = False
365
366usageFromFilter :: MonadPlus m => KeyFilter -> m String
367usageFromFilter (KF_Match usage) = return usage
368usageFromFilter _ = mzero
369
370data KeyRingRuntime = KeyRingRuntime
371 { rtPubring :: FilePath
372 -- ^ Path to the file represented by 'HomePub'
373 , rtSecring :: FilePath
374 -- ^ Path to the file represented by 'HomeSec'
375 , rtGrip :: Maybe String
376 -- ^ Fingerprint or portion of a fingerprint used
377 -- to identify the working GnuPG identity used to
378 -- make signatures.
379 , rtWorkingKey :: Maybe Packet
380 -- ^ The master key of the working GnuPG identity.
381 , rtKeyDB :: KeyDB
382 -- ^ The common information pool where files spilled
383 -- their content and from which they received new
384 -- content.
385 , rtRingAccess :: Map.Map InputFile Access
386 -- ^ The 'Access' values used for files of type
387 -- 'KeyRingFile'. If 'AutoAccess' was specified
388 -- for a file, this 'Map.Map' will indicate the
389 -- detected value that was used by the algorithm.
390 , rtPassphrases :: MappedPacket -> IO (KikiCondition Packet)
391 }
392
393-- | Roster-entry level actions
394data PacketUpdate = InducerSignature String [SignatureSubpacket]
395 | SubKeyDeletion KeyKey KeyKey
396
397-- | This type is used to indicate where to obtain passphrases.
398data PassphraseSpec = PassphraseSpec
399 { passSpecRingFile :: Maybe FilePath
400 -- ^ If not Nothing, the passphrase is to be used for packets
401 -- from this file.
402 , passSpecKeySpec :: Maybe String
403 -- ^ Non-Nothing value reserved for future use.
404 -- (TODO: Use this to implement per-key passphrase associations).
405 , passSpecPassFile :: InputFile
406 -- ^ The passphrase will be read from this file or file descriptor.
407 }
408 -- | Use this to carry pasphrases from a previous run.
409 | PassphraseMemoizer (MappedPacket -> IO (KikiCondition Packet))
410
411instance Show PassphraseSpec where
412 show (PassphraseSpec a b c) = "PassphraseSpec "++show (a,b,c)
413 show (PassphraseMemoizer _) = "PassphraseMemoizer"
414instance Eq PassphraseSpec where
415 PassphraseSpec a b c == PassphraseSpec d e f
416 = and [a==d,b==e,c==f]
417 _ == _
418 = False
419
420
421
422data Transform =
423 Autosign
424 -- ^ This operation will make signatures for any tor-style UID
425 -- that matches a tor subkey and thus can be authenticated without
426 -- requring the judgement of a human user.
427 --
428 -- A tor-style UID is one of the following form:
429 --
430 -- > Anonymous <root@HOSTNAME.onion>
431 | DeleteSubKey String
432 -- ^ Delete the subkey specified by the given fingerprint and any
433 -- associated signatures on that key.
434 deriving (Eq,Ord,Show)
435
436-- | This type describes an idempotent transformation (merge or import) on a
437-- set of GnuPG keyrings and other key files.
438data KeyRingOperation = KeyRingOperation
439 { opFiles :: Map.Map InputFile StreamInfo
440 -- ^ Indicates files to be read or updated.
441 , opPassphrases :: [PassphraseSpec]
442 -- ^ Indicates files or file descriptors where passphrases can be found.
443 , opTransforms :: [Transform]
444 -- ^ Transformations to be performed on the key pool after all files have
445 -- been read and before any have been written.
446 , opHome :: Maybe FilePath
447 -- ^ If provided, this is the directory where the 'HomeSec' and 'HomePub'
448 -- files reside. Otherwise, the evironment variable $GNUPGHOME is consulted
449 -- and if that is not set, it falls back to $HOME/.gnupg.
450 }
451 deriving (Eq,Show)
452
453resolveInputFile :: InputFileContext -> InputFile -> [FilePath]
454resolveInputFile ctx = resolve
455 where
456 resolve HomeSec = return (homesecPath ctx)
457 resolve HomePub = return (homepubPath ctx)
458 resolve (ArgFile f) = return f
459 resolve _ = []
460
461resolveForReport :: Maybe InputFileContext -> InputFile -> FilePath
462resolveForReport mctx (Pipe fdr fdw) = resolveForReport mctx (ArgFile str)
463 where str = case (fdr,fdw) of
464 (0,1) -> "-"
465 _ -> "&pipe" ++ show (fdr,fdw)
466resolveForReport mctx (FileDesc fd) = resolveForReport mctx (ArgFile str)
467 where str = "&" ++ show fd
468resolveForReport mctx f = concat $ resolveInputFile ctx f
469 where ctx = fromMaybe (InputFileContext "&secret" "&public") mctx
470
471filesToLock ::
472 KeyRingOperation -> InputFileContext -> [FilePath]
473filesToLock k ctx = do
474 (f,stream) <- Map.toList (opFiles k)
475 case fill stream of
476 KF_None -> []
477 _ -> resolveInputFile ctx f
478
479
480-- kret :: a -> KeyRingOperation a
481-- kret x = KeyRingOperation Map.empty Nothing (KeyRingAction x)
482
483data RSAPublicKey = RSAKey MPI MPI deriving (Eq,Show)
484data PKCS8_RSAPublicKey = RSAKey8 MPI MPI deriving Show
485
486pkcs8 :: RSAPublicKey -> PKCS8_RSAPublicKey
487pkcs8 (RSAKey n e) = RSAKey8 n e
488
489instance ASN1Object RSAPublicKey where
490 -- PKCS #1 RSA Public Key
491 toASN1 (RSAKey (MPI n) (MPI e))
492 = \xs -> Start Sequence
493 : IntVal n
494 : IntVal e
495 : End Sequence
496 : xs
497 fromASN1 (Start Sequence:IntVal n:IntVal e:End Sequence:xs) =
498 Right (RSAKey (MPI n) (MPI e), xs)
499
500 fromASN1 _ =
501 Left "fromASN1: RSAPublicKey: unexpected format"
502
503instance ASN1Object PKCS8_RSAPublicKey where
504
505 -- PKCS #8 Public key data
506 toASN1 (RSAKey8 (MPI n) (MPI e))
507 = \xs -> Start Sequence
508 : Start Sequence
509 : OID [1,2,840,113549,1,1,1]
510 : Null -- Doesn't seem to be neccessary, but i'm adding it
511 -- to match PEM files I see in the wild.
512 : End Sequence
513 : BitString (toBitArray bs 0)
514 : End Sequence
515 : xs
516 where
517 pubkey = [ Start Sequence, IntVal n, IntVal e, End Sequence ]
518 bs = encodeASN1' DER pubkey
519
520 fromASN1 (Start Sequence:IntVal modulus:IntVal pubexp:End Sequence:xs) =
521 Right (RSAKey8 (MPI modulus) (MPI pubexp) , xs)
522 fromASN1 (Start Sequence:Start Sequence:OID [1,2,840,113549,1,1,1]:Null:End Sequence:BitString b:End Sequence:xs) =
523 case decodeASN1' DER bs of
524 Right as -> fromASN1 as
525 Left e -> Left ("fromASN1: RSAPublicKey: "++show e)
526 where
527 BitArray _ bs = b
528 fromASN1 (Start Sequence:Start Sequence:OID [1,2,840,113549,1,1,1]:End Sequence:BitString b:End Sequence:xs) =
529 case decodeASN1' DER bs of
530 Right as -> fromASN1 as
531 Left e -> Left ("fromASN1: RSAPublicKey: "++show e)
532 where
533 BitArray _ bs = b
534
535 fromASN1 _ =
536 Left "fromASN1: RSAPublicKey: unexpected format"
537
538{-
539RSAPrivateKey ::= SEQUENCE {
540 version Version,
541 modulus INTEGER, -- n
542 publicExponent INTEGER, -- e
543 privateExponent INTEGER, -- d
544 prime1 INTEGER, -- p
545 prime2 INTEGER, -- q
546 exponent1 INTEGER, -- d mod (p1) -- ?? d mod (p-1)
547 exponent2 INTEGER, -- d mod (q-1)
548 coefficient INTEGER, -- (inverse of q) mod p
549 otherPrimeInfos OtherPrimeInfos OPTIONAL
550 }
551-}
552data RSAPrivateKey = RSAPrivateKey
553 { rsaN :: MPI
554 , rsaE :: MPI
555 , rsaD :: MPI
556 , rsaP :: MPI
557 , rsaQ :: MPI
558 , rsaDmodP1 :: MPI
559 , rsaDmodQminus1 :: MPI
560 , rsaCoefficient :: MPI
561 }
562 deriving Show
563
564instance ASN1Object RSAPrivateKey where
565 toASN1 rsa@(RSAPrivateKey {})
566 = \xs -> Start Sequence
567 : IntVal 0
568 : mpiVal rsaN
569 : mpiVal rsaE
570 : mpiVal rsaD
571 : mpiVal rsaP
572 : mpiVal rsaQ
573 : mpiVal rsaDmodP1
574 : mpiVal rsaDmodQminus1
575 : mpiVal rsaCoefficient
576 : End Sequence
577 : xs
578 where mpiVal f = IntVal x where MPI x = f rsa
579
580 fromASN1 ( Start Sequence
581 : IntVal _ -- version
582 : IntVal n
583 : IntVal e
584 : IntVal d
585 : IntVal p
586 : IntVal q
587 : IntVal dmodp1
588 : IntVal dmodqminus1
589 : IntVal coefficient
590 : ys) =
591 Right ( privkey, tail $ dropWhile notend ys)
592 where
593 notend (End Sequence) = False
594 notend _ = True
595 privkey = RSAPrivateKey
596 { rsaN = MPI n
597 , rsaE = MPI e
598 , rsaD = MPI d
599 , rsaP = MPI p
600 , rsaQ = MPI q
601 , rsaDmodP1 = MPI dmodp1
602 , rsaDmodQminus1 = MPI dmodqminus1
603 , rsaCoefficient = MPI coefficient
604 }
605 fromASN1 _ =
606 Left "fromASN1: RSAPrivateKey: unexpected format"
607
608
609
610-- | This type is used to indicate success or failure
611-- and in the case of success, return the computed object.
612-- The 'FunctorToMaybe' class is implemented to facilitate
613-- branching on failture.
614data KikiCondition a = KikiSuccess a
615 | FailedToLock [FilePath]
616 | BadPassphrase
617 | FailedToMakeSignature
618 | CantFindHome
619 | AmbiguousKeySpec FilePath
620 | CannotImportMasterKey
621 | NoWorkingKey
622 deriving ( Functor, Show )
623
624instance FunctorToMaybe KikiCondition where
625 functorToMaybe (KikiSuccess a) = Just a
626 functorToMaybe _ = Nothing
627
628instance Applicative KikiCondition where
629 pure a = KikiSuccess a
630 f <*> a =
631 case functorToEither f of
632 Right f -> case functorToEither a of
633 Right a -> pure (f a)
634 Left err -> err
635 Left err -> err
636
637-- | This type is used to describe events triggered by 'runKeyRing'. In
638-- addition to normal feedback (e.g. 'NewPacket'), it also may indicate
639-- non-fatal IO exceptions (e.g. 'FailedExternal'). Because a
640-- 'KeyRingOperation' may describe a very intricate multifaceted algorithm with
641-- many inputs and outputs, an operation may be partially (or even mostly)
642-- successful even when I/O failures occured. In this situation, the files may
643-- not have all the information they were intended to store, but they will be
644-- in a valid format for GnuPG or kiki to operate on in the future.
645data KikiReportAction =
646 NewPacket String
647 | MissingPacket String
648 | ExportedSubkey
649 | GeneratedSubkeyFile
650 | NewWalletKey String
651 | YieldSignature
652 | YieldSecretKeyPacket String
653 | UnableToUpdateExpiredSignature
654 | WarnFailedToMakeSignature
655 | FailedExternal Int
656 | ExternallyGeneratedFile
657 | UnableToExport KeyAlgorithm String
658 | FailedFileWrite
659 | HostsDiff ByteString
660 | DeletedPacket String
661 deriving Show
662
663uncamel :: String -> String
664uncamel str = unwords $ firstWord ++ (toLower .: otherWords) ++ args
665 where
666 (.:) = fmap . fmap
667 ( firstWord ,
668 otherWords ) = splitAt 1 ws
669 ws = camel >>= groupBy (\_ c -> isLower c)
670 ( camel, args) = splitAt 1 $ words str
671
672reportString :: KikiReportAction -> String
673reportString x = uncamel $ show x
674
675errorString :: KikiCondition a -> String
676errorString (KikiSuccess {}) = "success"
677errorString e = uncamel . show $ fmap (const ()) e
678
679-- | Errors in kiki are indicated by the returning of this record.
680data KikiResult a = KikiResult
681 { kikiCondition :: KikiCondition a
682 -- ^ The result or a fatal error condition.
683 , kikiReport :: KikiReport
684 -- ^ A list of non-fatal warnings and informational messages
685 -- along with the files that triggered them.
686 }
687
688type KikiReport = [ (FilePath, KikiReportAction) ]
689
690keyPacket :: KeyData -> Packet
691keyPacket (KeyData k _ _ _) = packet k
692
693subkeyMappedPacket :: SubKey -> MappedPacket
694subkeyMappedPacket (SubKey k _ ) = k
695
696
697usage :: SignatureSubpacket -> Maybe String
698usage (NotationDataPacket
699 { human_readable = True
700 , notation_name = "usage@"
701 , notation_value = u
702 }) = Just u
703usage _ = Nothing
704
705x509cert :: SignatureSubpacket -> Maybe Char8.ByteString
706x509cert (NotationDataPacket
707 { human_readable = False
708 , notation_name = "x509cert@"
709 , notation_value = u
710 }) = Just (Char8.pack u)
711x509cert _ = Nothing
712
713makeInducerSig
714 :: Packet
715 -> Packet -> Packet -> [SignatureSubpacket] -> SignatureOver
716-- torsig g topk wkun uid timestamp extras = todo
717makeInducerSig topk wkun uid extras
718 = CertificationSignature (secretToPublic topk)
719 uid
720 (sigpackets 0x13
721 subpackets
722 subpackets_unh)
723 where
724 subpackets = -- implicit: [ SignatureCreationTimePacket (fromIntegral timestamp) ]
725 tsign
726 ++ extras
727 subpackets_unh = [IssuerPacket (fingerprint wkun)]
728 tsign = if keykey wkun == keykey topk
729 then [] -- tsign doesnt make sense for self-signatures
730 else [ TrustSignaturePacket 1 120
731 , RegularExpressionPacket regex]
732 -- <[^>]+[@.]asdf\.nowhere>$
733 regex = "<[^>]+[@.]"++hostname++">$"
734 -- regex = username ++ "@" ++ hostname
735 -- username = "[a-zA-Z0-9.][-a-zA-Z0-9.]*\\$?" :: String
736 hostname = subdomain' pu ++ "\\." ++ topdomain' pu
737 pu = parseUID uidstr where UserIDPacket uidstr = uid
738 subdomain' = escape . T.unpack . uid_subdomain
739 topdomain' = escape . T.unpack . uid_topdomain
740 escape s = concatMap echar s
741 where
742 echar '|' = "\\|"
743 echar '*' = "\\*"
744 echar '+' = "\\+"
745 echar '?' = "\\?"
746 echar '.' = "\\."
747 echar '^' = "\\^"
748 echar '$' = "\\$"
749 echar '\\' = "\\\\"
750 echar '[' = "\\["
751 echar ']' = "\\]"
752 echar c = [c]
753
754
755keyflags :: SignatureSubpacket -> Maybe PGPKeyFlags
756keyflags flgs@(KeyFlagsPacket {}) =
757 Just . toEnum $
758 ( bit 0x1 certify_keys
759 .|. bit 0x2 sign_data
760 .|. bit 0x4 encrypt_communication
761 .|. bit 0x8 encrypt_storage ) :: Maybe PGPKeyFlags
762 -- other flags:
763 -- split_key
764 -- authentication (ssh-client)
765 -- group_key
766 where
767 bit v f = if f flgs then v else 0
768keyflags _ = Nothing
769
770
771data PGPKeyFlags =
772 Special
773 | Vouch -- Signkey
774 | Sign
775 | VouchSign
776 | Communication
777 | VouchCommunication
778 | SignCommunication
779 | VouchSignCommunication
780 | Storage
781 | VouchStorage
782 | SignStorage
783 | VouchSignStorage
784 | Encrypt
785 | VouchEncrypt
786 | SignEncrypt
787 | VouchSignEncrypt
788 deriving (Eq,Show,Read,Enum)
789
790
791usageString :: PGPKeyFlags -> String
792usageString flgs =
793 case flgs of
794 Special -> "special"
795 Vouch -> "vouch" -- signkey
796 Sign -> "sign"
797 VouchSign -> "vouch-sign"
798 Communication -> "communication"
799 VouchCommunication -> "vouch-communication"
800 SignCommunication -> "sign-communication"
801 VouchSignCommunication -> "vouch-sign-communication"
802 Storage -> "storage"
803 VouchStorage -> "vouch-storage"
804 SignStorage -> "sign-storage"
805 VouchSignStorage -> "vouch-sign-storage"
806 Encrypt -> "encrypt"
807 VouchEncrypt -> "vouch-encrypt"
808 SignEncrypt -> "sign-encrypt"
809 VouchSignEncrypt -> "vouch-sign-encrypt"
810
811
812
813
814-- matchpr computes the fingerprint of the given key truncated to
815-- be the same lenght as the given fingerprint for comparison.
816matchpr :: String -> Packet -> String
817matchpr fp k = reverse $ zipWith const (reverse (fingerprint k)) fp
818
819keyFlags :: t -> [Packet] -> [SignatureSubpacket]
820keyFlags wkun uids = keyFlags0 wkun (filter isSignaturePacket uids)
821
822keyFlags0 :: t -> [Packet] -> [SignatureSubpacket]
823keyFlags0 wkun uidsigs = concat
824 [ keyflags
825 , preferredsym
826 , preferredhash
827 , preferredcomp
828 , features ]
829
830 where
831 subs = concatMap hashed_subpackets uidsigs
832 keyflags = filterOr isflags subs $
833 KeyFlagsPacket { certify_keys = True
834 , sign_data = True
835 , encrypt_communication = False
836 , encrypt_storage = False
837 , split_key = False
838 , authentication = False
839 , group_key = False
840 }
841 preferredsym = filterOr ispreferedsym subs $
842 PreferredSymmetricAlgorithmsPacket
843 [ AES256
844 , AES192
845 , AES128
846 , CAST5
847 , TripleDES
848 ]
849 preferredhash = filterOr ispreferedhash subs $
850 PreferredHashAlgorithmsPacket
851 [ SHA256
852 , SHA1
853 , SHA384
854 , SHA512
855 , SHA224
856 ]
857 preferredcomp = filterOr ispreferedcomp subs $
858 PreferredCompressionAlgorithmsPacket
859 [ ZLIB
860 , BZip2
861 , ZIP
862 ]
863 features = filterOr isfeatures subs $
864 FeaturesPacket { supports_mdc = True
865 }
866
867 filterOr pred xs def = if null rs then [def] else rs where rs=filter pred xs
868
869 isflags (KeyFlagsPacket {}) = True
870 isflags _ = False
871 ispreferedsym (PreferredSymmetricAlgorithmsPacket {}) = True
872 ispreferedsym _ = False
873 ispreferedhash (PreferredHashAlgorithmsPacket {}) = True
874 ispreferedhash _ = False
875 ispreferedcomp (PreferredCompressionAlgorithmsPacket {}) = True
876 ispreferedcomp _ = False
877 isfeatures (FeaturesPacket {}) = True
878 isfeatures _ = False
879
880
881matchSpec :: KeySpec -> KeyData -> Bool
882matchSpec (KeyGrip grip) (KeyData p _ _ _)
883 | matchpr grip (packet p)==grip = True
884 | otherwise = False
885
886matchSpec (KeyTag key tag) (KeyData _ sigs _ _) = not . null $ filter match ps
887 where
888 ps = map (packet .fst) sigs
889 match p = isSignaturePacket p
890 && has_tag tag p
891 && has_issuer key p
892 has_issuer key p = isJust $ do
893 issuer <- signature_issuer p
894 guard $ matchpr issuer key == issuer
895 has_tag tag p = tag `elem` mapMaybe usage (hashed_subpackets p)
896 || tag `elem` map usageString (mapMaybe keyflags (hashed_subpackets p))
897
898matchSpec (KeyUidMatch pat) (KeyData _ _ uids _) = not $ null us
899 where
900 us = filter (isInfixOf pat) $ Map.keys uids
901
902data UserIDRecord = UserIDRecord {
903 uid_full :: String,
904 uid_realname :: T.Text,
905 uid_user :: T.Text,
906 uid_subdomain :: T.Text,
907 uid_topdomain :: T.Text
908}
909 deriving Show
910
911parseUID :: String -> UserIDRecord
912parseUID str = UserIDRecord {
913 uid_full = str,
914 uid_realname = realname,
915 uid_user = user,
916 uid_subdomain = subdomain,
917 uid_topdomain = topdomain
918 }
919 where
920 text = T.pack str
921 (T.strip-> realname, T.dropAround isBracket-> email)
922 = T.break (=='<') text
923 (user, T.drop 1-> hostname) = T.break (=='@') email
924 ( T.reverse -> topdomain,
925 T.reverse . T.drop 1 -> subdomain)
926 = T.break (=='.') . T.reverse $ hostname
927isBracket :: Char -> Bool
928isBracket '<' = True
929isBracket '>' = True
930isBracket _ = False
931
932
933
934
935data KeySpec =
936 KeyGrip String -- fp:
937 | KeyTag Packet String -- fp:????/t:
938 | KeyUidMatch String -- u:
939 deriving Show
940
941data MatchingField = UserIDField | KeyTypeField deriving (Show,Eq,Ord,Enum)
942data SingleKeySpec = FingerprintMatch String
943 | SubstringMatch (Maybe MatchingField) String
944 | EmptyMatch
945 | AnyMatch
946 | WorkingKeyMatch
947 deriving (Show,Eq,Ord)
948
949-- A pair of specs. The first specifies an identity and the second
950-- specifies a specific key (possibly master) associated with that
951-- identity.
952--
953-- When no slash is specified, context will decide whether the SingleKeySpec
954-- is specifying an identity or a key belonging to the working identity.
955type Spec = (SingleKeySpec,SingleKeySpec)
956
957parseSingleSpec :: String -> SingleKeySpec
958parseSingleSpec "*" = AnyMatch
959parseSingleSpec "-" = WorkingKeyMatch
960parseSingleSpec "" = EmptyMatch
961parseSingleSpec ('t':':':tag) = SubstringMatch (Just KeyTypeField) tag
962parseSingleSpec ('u':':':tag) = SubstringMatch (Just UserIDField) tag
963parseSingleSpec ('f':'p':':':fp) = FingerprintMatch fp
964parseSingleSpec str
965 | is40digitHex str = FingerprintMatch str
966 | otherwise = SubstringMatch Nothing str
967
968is40digitHex xs = ys == xs && length ys==40
969 where
970 ys = filter ishex xs
971 ishex c | '0' <= c && c <= '9' = True
972 | 'A' <= c && c <= 'F' = True
973 | 'a' <= c && c <= 'f' = True
974 ishex c = False
975
976
977 -- t:tor -- (FingerprintMatch "", SubstringMatch "tor")
978 -- u:joe -- (SubstringMatch "joe", FingerprintMatch "")
979 -- u:joe/ -- (SubstringMatch "joe", FingerprintMatch "!")
980 -- fp:4A39F/tor -- (FingerprintMatch "4A39F", SubstringMatch "tor")
981 -- u:joe/tor -- (SubstringMatch "joe", SubstringMatch "tor")
982 -- u:joe/t:tor -- (SubstringMatch "joe", SubstringMatch "tor")
983 -- u:joe/fp:4abf30 -- (SubstringMatch "joe", FingerprintMatch "4abf30")
984 -- joe/tor -- (SubstringMatch "joe", SubstringMatch "tor")
985
986-- | Parse a key specification.
987-- The first argument is a grip for the default working key.
988parseSpec :: String -> String -> (KeySpec,Maybe String)
989parseSpec wkgrip spec =
990 if not slashed
991 then
992 case prespec of
993 AnyMatch -> (KeyGrip "", Nothing)
994 EmptyMatch -> error "Bad key spec."
995 WorkingKeyMatch -> (KeyGrip wkgrip, Nothing)
996 SubstringMatch (Just KeyTypeField) tag -> (KeyGrip wkgrip, Just tag)
997 SubstringMatch Nothing str -> (KeyGrip wkgrip, Just str)
998 SubstringMatch (Just UserIDField) ustr -> (KeyUidMatch ustr, Nothing)
999 FingerprintMatch fp -> (KeyGrip fp, Nothing)
1000 else
1001 case (prespec,postspec) of
1002 (FingerprintMatch fp, SubstringMatch st t)
1003 | st /= Just UserIDField -> (KeyGrip fp, Just t)
1004 (SubstringMatch mt u, _)
1005 | postspec `elem` [AnyMatch,EmptyMatch]
1006 && mt /= Just KeyTypeField -> (KeyUidMatch u, Nothing)
1007 (SubstringMatch mt u, SubstringMatch st t)
1008 | mt /= Just KeyTypeField
1009 && st /= Just UserIDField -> (KeyUidMatch u, Just t)
1010 (FingerprintMatch _,FingerprintMatch _) -> error "todo: support fp:/fp: spec"
1011 (_,FingerprintMatch fp) -> error "todo: support /fp: spec"
1012 (FingerprintMatch fp,_) -> error "todo: support fp:/ spec"
1013 _ -> error "Bad key spec."
1014 where
1015 (preslash,slashon) = break (=='/') spec
1016 slashed = not $ null $ take 1 slashon
1017 postslash = drop 1 slashon
1018
1019 prespec = parseSingleSpec preslash
1020 postspec = parseSingleSpec postslash
1021
1022{-
1023 - BUGGY
1024parseSpec grip spec = (topspec,subspec)
1025 where
1026 (topspec0,subspec0) = unprefix '/' spec
1027 (toptyp,top) = unprefix ':' topspec0
1028 (subtyp,sub) = unprefix ':' subspec0
1029 topspec = case () of
1030 _ | null top && or [ subtyp=="fp"
1031 , null subtyp && is40digitHex sub
1032 ]
1033 -> KeyGrip sub
1034 _ | null top && null grip -> KeyUidMatch sub
1035 _ | null top -> KeyGrip grip
1036 _ | toptyp=="fp" || (null toptyp && is40digitHex top)
1037 -> KeyGrip top
1038 _ | toptyp=="u" -> KeyUidMatch top
1039 _ -> KeyUidMatch top
1040 subspec = case subtyp of
1041 "t" -> Just sub
1042 "fp" | top=="" -> Nothing
1043 "" | top=="" && is40digitHex sub -> Nothing
1044 "" -> listToMaybe sub >> Just sub
1045 _ -> Nothing
1046
1047 is40digitHex xs = ys == xs && length ys==40
1048 where
1049 ys = filter ishex xs
1050 ishex c | '0' <= c && c <= '9' = True
1051 | 'A' <= c && c <= 'F' = True
1052 | 'a' <= c && c <= 'f' = True
1053 ishex c = False
1054
1055 -- | Split a string into two at the first occurance of the given
1056 -- delimiter. If the delimeter does not occur, then the first
1057 -- item of the returned pair is empty and the second item is the
1058 -- input string.
1059 unprefix c spec = if null (snd p) then swap p else (fst p, tail (snd p))
1060 where p = break (==c) spec
1061-}
1062
1063
1064filterMatches :: KeySpec -> [(KeyKey,KeyData)] -> [(KeyKey,KeyData)]
1065filterMatches spec ks = filter (matchSpec spec . snd) ks
1066
1067filterNewSubs :: FilePath -> (KeySpec,Maybe String) -> KeyData -> KeyData
1068filterNewSubs fname spec (KeyData p sigs uids subs) = KeyData p sigs uids subs'
1069 where
1070 matchAll = KeyGrip ""
1071
1072 subkeySpec (KeyGrip grip,Nothing) = (matchAll, KeyGrip grip)
1073 subkeySpec (topspec,Just mtag) = (topspec , KeyTag (packet p) mtag)
1074
1075 match spec mps
1076 = not . null
1077 . snd
1078 . seek_key spec
1079 . map packet
1080 $ mps
1081
1082 old sub = isJust (Map.lookup fname $ locations $ subkeyMappedPacket sub)
1083
1084 oldOrMatch spec sub = old sub
1085 || match spec (flattenSub "" True sub)
1086
1087 subs' = Map.filter (if match topspec $ flattenTop "" True (KeyData p sigs uids Map.empty)
1088 then oldOrMatch subspec
1089 else old)
1090 subs
1091 where
1092 (topspec,subspec) = subkeySpec spec
1093
1094selectSecretKey :: (KeySpec,Maybe String) -> KeyDB -> Maybe Packet
1095selectSecretKey (spec,mtag) db = selectKey0 False (spec,mtag) db
1096
1097selectPublicKey :: (KeySpec,Maybe String) -> KeyDB -> Maybe Packet
1098selectPublicKey (spec,mtag) db = selectKey0 True (spec,mtag) db
1099
1100selectPublicKeyAndSigs :: (KeySpec,Maybe String) -> KeyDB -> [(KeyKey,Packet,[Packet])]
1101selectPublicKeyAndSigs (spec,mtag) db =
1102 case mtag of
1103 Nothing -> do
1104 (kk,r) <- Map.toList $ fmap (findbyspec spec) db
1105 (sub,sigs) <- r
1106 return (kk,sub,sigs)
1107 Just tag -> Map.toList (Map.filter (matchSpec spec) db) >>= findsubs tag
1108 where
1109 topresult kd = (keyPacket kd, map (packet .fst) $ keySigAndTrusts kd)
1110
1111 findbyspec (KeyGrip g) kd = do
1112 filter ismatch $
1113 topresult kd
1114 : map (\(SubKey sub sigs)-> (packet sub, map (packet . fst) sigs))
1115 (Map.elems $ keySubKeys kd)
1116 where
1117 ismatch (p,sigs) = matchpr g p ==g
1118 findbyspec spec kd = if matchSpec spec kd then [topresult kd] else []
1119
1120 findsubs tag (kk, KeyData topk _ _ subs) = Map.elems subs >>= gettag
1121 where
1122 gettag (SubKey sub sigs) = do
1123 let (_,mb,_) = findTag [mkUsage tag] (packet topk) (packet sub) sigs
1124 (hastag,_) <- maybeToList mb
1125 guard hastag
1126 return $ (kk, packet sub, map (packet . fst) sigs)
1127
1128selectKey0 :: Bool -> (KeySpec,Maybe String) -> KeyDB -> Maybe Packet
1129selectKey0 wantPublic (spec,mtag) db = do
1130 let Message ps = flattenKeys wantPublic db
1131 ys = snd $ seek_key spec ps
1132 flip (maybe (listToMaybe ys)) mtag $ \tag -> do
1133 case ys of
1134 y:ys1 -> listToMaybe $ snd $ seek_key (KeyTag y tag) ys1
1135 [] -> Nothing
1136
1137{-
1138selectAll :: Bool -> (KeySpec,Maybe String) -> KeyDB -> [(Packet,Maybe Packet)]
1139selectAll wantPublic (spec,mtag) db = do
1140 let Message ps = flattenKeys wantPublic db
1141 ys = snd $ seek_key spec ps
1142 y <- take 1 ys
1143 case mtag of
1144 Nothing -> return (y,Nothing)
1145 Just tag ->
1146 let search ys1 = do
1147 let zs = snd $ seek_key (KeyTag y tag) ys1
1148 z <- take 1 zs
1149 (y,Just z):search (drop 1 zs)
1150 in search (drop 1 ys)
1151-}
1152
1153seek_key :: KeySpec -> [Packet] -> ([Packet],[Packet])
1154seek_key (KeyGrip grip) sec = (pre, subs)
1155 where
1156 (pre,subs) = break pred sec
1157 pred p@(SecretKeyPacket {}) = matchpr grip p == grip
1158 pred p@(PublicKeyPacket {}) = matchpr grip p == grip
1159 pred _ = False
1160
1161seek_key (KeyTag key tag) ps
1162 | null bs = (ps, [])
1163 | null qs =
1164 let (as', bs') = seek_key (KeyTag key tag) (tail bs) in
1165 (as ++ (head bs : as'), bs')
1166 | otherwise = (reverse (tail qs), head qs : reverse rs ++ bs)
1167 where
1168 (as,bs) = break (\p -> isSignaturePacket p
1169 && has_tag tag p
1170 && isJust (signature_issuer p)
1171 && matchpr (fromJust $ signature_issuer p) key == fromJust (signature_issuer p) )
1172 ps
1173 (rs,qs) = break isKey (reverse as)
1174
1175 has_tag tag p = tag `elem` mapMaybe usage (hashed_subpackets p)
1176 || tag `elem` map usageString (mapMaybe keyflags (hashed_subpackets p))
1177
1178seek_key (KeyUidMatch pat) ps
1179 | null bs = (ps, [])
1180 | null qs = let (as', bs') = seek_key (KeyUidMatch pat) (tail bs) in
1181 (as ++ (head bs : as'), bs')
1182 | otherwise = (reverse (tail qs), head qs : reverse rs ++ bs)
1183 where
1184 (as,bs) = break (isInfixOf pat . uidStr) ps
1185 (rs,qs) = break isKey (reverse as)
1186
1187 uidStr (UserIDPacket s) = s
1188 uidStr _ = ""
1189
1190
1191data InputFileContext = InputFileContext
1192 { homesecPath :: FilePath
1193 , homepubPath :: FilePath
1194 }
1195
1196readInputFileS :: InputFileContext -> InputFile -> IO S.ByteString
1197readInputFileS ctx (Pipe fd _) = fdToHandle fd >>= S.hGetContents
1198readInputFileS ctx (FileDesc fd) = fdToHandle fd >>= S.hGetContents
1199readInputFileS ctx inp = do
1200 let fname = resolveInputFile ctx inp
1201 fmap S.concat $ mapM S.readFile fname
1202
1203readInputFileL :: InputFileContext -> InputFile -> IO L.ByteString
1204readInputFileL ctx (Pipe fd _) = fdToHandle fd >>= L.hGetContents
1205readInputFileL ctx (FileDesc fd) = fdToHandle fd >>= L.hGetContents
1206readInputFileL ctx inp = do
1207 let fname = resolveInputFile ctx inp
1208 fmap L.concat $ mapM L.readFile fname
1209
1210
1211writeInputFileL ctx (Pipe _ fd) bs = fdToHandle fd >>= (`L.hPut` bs)
1212writeInputFileL ctx (FileDesc fd) bs = fdToHandle fd >>= (`L.hPut` bs)
1213writeInputFileL ctx inp bs = do
1214 let fname = resolveInputFile ctx inp
1215 mapM_ (`L.writeFile` bs) fname
1216
1217-- writeStamped0 :: InputFileContext -> InputFile -> Posix.EpochTime -> L.ByteString -> IO ()
1218-- writeStamped0 :: InputFileContext -> InputFile
1219
1220getWriteFD :: InputFile -> Maybe Posix.Fd
1221getWriteFD (Pipe _ fd) = Just fd
1222getWriteFD (FileDesc fd) = Just fd
1223getWriteFD _ = Nothing
1224
1225writeStamped0 :: InputFileContext
1226 -> InputFile
1227 -> Posix.EpochTime
1228 -> (Either Handle FilePath -> t -> IO ())
1229 -> t
1230 -> IO ()
1231writeStamped0 ctx (getWriteFD -> Just fd) stamp dowrite bs = do
1232 h <- fdToHandle fd
1233 dowrite (Left h) bs
1234 handleIO_ (return ())
1235 $ setFdTimesHiRes fd (realToFrac stamp) (realToFrac stamp)
1236writeStamped0 ctx inp stamp dowrite bs = do
1237 let fname = resolveInputFile ctx inp
1238 forM_ fname $ \fname -> do
1239 createDirectoryIfMissing True $ takeDirectory fname
1240 dowrite (Right fname) bs
1241 setFileTimes fname stamp stamp
1242
1243{- This may be useful later. Commented for now, as it is not used.
1244 -
1245writeStampedL :: InputFileContext -> InputFile -> Posix.EpochTime -> L.ByteString -> IO ()
1246writeStampedL ctx f stamp bs = writeStamped0 ctx f stamp (either L.hPut L.writeFile) bs
1247-}
1248
1249writeStamped :: InputFileContext -> InputFile -> Posix.EpochTime -> String -> IO ()
1250writeStamped ctx f stamp str = writeStamped0 ctx f stamp (either hPutStr writeFile) str
1251
1252getInputFileTime :: InputFileContext -> InputFile -> IO CTime
1253getInputFileTime ctx (Pipe fdr fdw) = do
1254 mt <- handleIO_ (return Nothing) $ Just <$> modificationTime <$> getFdStatus fdr
1255 maybe tryw return mt
1256 where
1257 tryw = do
1258 handleIO_ (error $ (resolveForReport Nothing $ Pipe fdr fdw) ++": modificaiton time?")
1259 $ modificationTime <$> getFdStatus fdw
1260getInputFileTime ctx (FileDesc fd) = do
1261 handleIO_ (error $ "&"++show fd++": modificaiton time?") $
1262 modificationTime <$> getFdStatus fd
1263getInputFileTime ctx (resolveInputFile ctx -> [fname]) = do
1264 handleIO_ (error $ fname++": modificaiton time?") $
1265 modificationTime <$> getFileStatus fname
1266
1267{-
1268 - This may be useful later. Commented for now as it is not used.
1269 -
1270doesInputFileExist :: InputFileContext -> InputFile -> IO Bool
1271doesInputFileExist ctx f = do
1272 case resolveInputFile ctx f of
1273 [n] -> doesFileExist n
1274 _ -> return True
1275-}
1276
1277
1278cachedContents :: Maybe S.ByteString -> InputFileContext -> InputFile -> IO (IO S.ByteString)
1279cachedContents maybePrompt ctx fd = do
1280 ref <- newIORef Nothing
1281 return $ get maybePrompt ref fd
1282 where
1283 trimCR bs = fst $ S.spanEnd (\x -> x==10 || x==13) bs
1284
1285 get maybePrompt ref fd = do
1286 pw <- readIORef ref
1287 flip (flip maybe return) pw $ do
1288 if fd == FileDesc 0 then case maybePrompt of
1289 Just prompt -> S.hPutStr stderr prompt
1290 Nothing -> return ()
1291 else return ()
1292 pw <- fmap trimCR $ readInputFileS ctx fd
1293 writeIORef ref (Just pw)
1294 return pw
1295
1296generateSubkey ::
1297 (MappedPacket -> IO (KikiCondition Packet)) -- decrypt[
1298 -> KikiCondition (KeyData, [(FilePath, KikiReportAction)]) -- db
1299 -> (GenerateKeyParams, StreamInfo)
1300 -> IO (KikiCondition (KeyData, [(FilePath, KikiReportAction)]))
1301generateSubkey doDecrypt kd' (genparam,StreamInfo { spill = KF_Match tag }) = do
1302 try kd' $ \(kd,report0) -> do
1303 let subs = do
1304 SubKey p sigs <- Map.elems $ keySubKeys kd
1305 filter (has_tag tag) $ map (packet . fst) sigs
1306 if null subs
1307 then do
1308 newkey <- generateKey genparam
1309 kdr <- insertSubkey doDecrypt (keykey (keyPacket kd)) kd [mkUsage tag] "" newkey
1310 try kdr $ \(newkd,report) -> do
1311 return $ KikiSuccess (newkd, report ++ [("", NewPacket $ showPacket newkey)])
1312 else do
1313 return $ KikiSuccess (kd,report0)
1314generateSubkey _ kd _ = return kd
1315
1316importSecretKey ::
1317 (MappedPacket -> IO (KikiCondition Packet))
1318 -> KikiCondition
1319 (Map.Map KeyKey KeyData, [(FilePath, KikiReportAction)])
1320 -> (FilePath, Maybe [Char], [KeyKey], StreamInfo, t)
1321 -> IO (KikiCondition (Map.Map KeyKey KeyData, [(FilePath, KikiReportAction)]))
1322importSecretKey doDecrypt db' tup = do
1323 try db' $ \(db',report0) -> do
1324 r <- doImport doDecrypt
1325 db'
1326 tup
1327 try r $ \(db'',report) -> do
1328 return $ KikiSuccess (db'', report0 ++ report)
1329
1330
1331mergeHostFiles :: KeyRingOperation -> KeyDB -> InputFileContext
1332 -> IO
1333 (KikiCondition
1334 ( ( Map.Map [Char8.ByteString] KeyData
1335 , ( [Hosts.Hosts]
1336 , [Hosts.Hosts]
1337 , Hosts.Hosts
1338 , [(SockAddr, ([Char8.ByteString], [Char8.ByteString]))]
1339 , [SockAddr]))
1340 , [(FilePath,KikiReportAction)]))
1341mergeHostFiles krd db ctx = do
1342 let hns = files ishosts
1343 ishosts Hosts = True
1344 ishosts _ = False
1345 files istyp = do
1346 (f,stream) <- Map.toList (opFiles krd)
1347 guard (istyp $ typ stream)
1348 return f
1349
1350 hostdbs0 <- mapM (fmap Hosts.decode . readInputFileL ctx) hns
1351
1352 let gpgnames = map getHostnames $ Map.elems db
1353 os = do
1354 (addr,(ns,_)) <- gpgnames
1355 n <- ns
1356 return (addr,n)
1357 setOnions hosts = foldl' (flip $ uncurry Hosts.assignName) hosts os
1358 -- we ensure .onion names are set properly
1359 hostdbs = map setOnions hostdbs0
1360 outgoing_names = do
1361 (addr,(_,gns)) <- gpgnames
1362 guard . not $ null gns
1363 guard $ all (null . Hosts.namesForAddress addr) hostdbs0
1364 return addr
1365 -- putStrLn $ "hostdbs = " ++ show hostdbs
1366
1367 -- 1. let U = union all the host dbs
1368 -- preserving whitespace and comments of the first
1369 let u0 = foldl' Hosts.plus Hosts.empty hostdbs
1370 -- we filter U to be only finger-dresses
1371 u1 = Hosts.filterAddrs (hasFingerDress db) u0
1372
1373 -- let nf h = map Char8.unpack $ Hosts.namesForAddress (fromJust $ Hosts.inet_pton "fdf4:ed98:29c7:6226:9bde:a5b4:d564:3321") h
1374 {-
1375 putStrLn $ "_ = {\n" ++ show (head hostdbs) ++ "}"
1376 putStrLn $ "--> " ++ show (nf (head hostdbs))
1377 putStrLn $ "u0 = {\n" ++ show u0 ++ "}"
1378 putStrLn $ "--> " ++ show (nf u0)
1379 putStrLn $ "u1 = {\n" ++ show u1 ++ "}"
1380 putStrLn $ "--> " ++ show (nf u1)
1381 -}
1382
1383 -- 2. replace gpg annotations with those in U
1384 -- forM use_db
1385 db' <- Traversable.mapM (setHostnames (`notElem` outgoing_names) u1) db
1386
1387 return $ KikiSuccess ((db',(hostdbs0,hostdbs,u1,gpgnames,outgoing_names)),[])
1388
1389writeHostsFiles
1390 :: KeyRingOperation -> InputFileContext
1391 -> ([Hosts.Hosts],
1392 [Hosts.Hosts],
1393 Hosts.Hosts,
1394 [(SockAddr, (t1, [Char8.ByteString]))],
1395 [SockAddr])
1396 -> IO [(FilePath, KikiReportAction)]
1397writeHostsFiles krd ctx (hostdbs0,hostdbs,u1,gpgnames,outgoing_names) = do
1398 let hns = files isMutableHosts
1399 isMutableHosts (fill -> KF_None) = False
1400 isMutableHosts (typ -> Hosts) = True
1401 isMutableHosts _ = False
1402 files istyp = do
1403 (f,stream) <- Map.toList (opFiles krd)
1404 guard (istyp stream)
1405 return f -- resolveInputFile ctx f
1406
1407 -- 3. add hostnames from gpg for addresses not in U
1408 let u = foldl' f u1 ans
1409 ans = reverse $ do
1410 (addr,(_,ns)) <- gpgnames
1411 guard $ addr `elem` outgoing_names -- . null $ Hosts.namesForAddress addr u0
1412 n <- ns
1413 return (addr,n)
1414 f h (addr,n) = Hosts.assignNewName addr n h
1415
1416 -- 4. for each host db H, union H with U and write it out as H'
1417 -- only if there is a non-empty diff
1418 rss <- forM (zip hns $ zip hostdbs0 hostdbs) $ \(fname,(h0,h1)) -> do
1419 let h = h1 `Hosts.plus` u
1420 d = Hosts.diff h0 h
1421 rs = map ((fname,) . HostsDiff) d
1422 unless (null d) $ writeInputFileL ctx fname $ Hosts.encode h
1423 return $ map (first $ resolveForReport $ Just ctx) rs
1424 return $ concat rss
1425
1426isSecretKey :: Packet -> Bool
1427isSecretKey (SecretKeyPacket {}) = True
1428isSecretKey _ = False
1429
1430buildKeyDB :: InputFileContext -> Maybe String -> KeyRingOperation
1431 -> IO (KikiCondition ((KeyDB
1432 ,Maybe String
1433 ,Maybe MappedPacket
1434 ,([Hosts.Hosts],
1435 [Hosts.Hosts],
1436 Hosts.Hosts,
1437 [(SockAddr, (KeyKey, KeyKey))],
1438 [SockAddr])
1439 ,Map.Map InputFile Access
1440 ,MappedPacket -> IO (KikiCondition Packet)
1441 ,Map.Map InputFile Message
1442 )
1443 ,[(FilePath,KikiReportAction)]))
1444buildKeyDB ctx grip0 keyring = do
1445 let
1446 files istyp = do
1447 (f,stream) <- Map.toList (opFiles keyring)
1448 guard (istyp $ typ stream)
1449 resolveInputFile ctx f
1450
1451 ringMap0 = Map.filter (isring . typ) $ opFiles keyring
1452 (genMap,ringMap) = Map.partitionWithKey isgen ringMap0
1453 where
1454 isgen (Generate _ _) _ = True
1455 isgen _ _ = False
1456
1457 readp f stream = fmap readp0 $ readPacketsFromFile ctx f
1458 where
1459 readp0 ps = (stream { access = acc' }, ps)
1460 where acc' = case access stream of
1461 AutoAccess ->
1462 case ps of
1463 Message ((PublicKeyPacket {}):_) -> Pub
1464 Message ((SecretKeyPacket {}):_) -> Sec
1465 _ -> AutoAccess
1466 acc -> acc
1467
1468 readw wk n = fmap (n,) (readPacketsFromWallet wk (ArgFile n))
1469
1470 -- KeyRings (todo: KikiCondition reporting?)
1471 (spilled,mwk,grip,accs,keys,unspilled) <- do
1472#if MIN_VERSION_containers(0,5,0)
1473 ringPackets <- Map.traverseWithKey readp ringMap
1474#else
1475 ringPackets <- Traversable.traverse (uncurry readp) $ Map.mapWithKey (,) ringMap
1476#endif
1477 let _ = ringPackets :: Map.Map InputFile (StreamInfo, Message)
1478
1479 let grip = grip0 `mplus` (fingerprint <$> fstkey)
1480 where
1481 fstkey = do
1482 (_,Message ps) <- Map.lookup HomeSec ringPackets
1483 listToMaybe ps
1484 (spilled,unspilled) = Map.partition (spillable . fst) ringPackets
1485 keys :: Map.Map KeyKey MappedPacket
1486 keys = Map.foldl slurpkeys Map.empty
1487 $ Map.mapWithKey filterSecrets ringPackets
1488 where
1489 filterSecrets f (_,Message ps) =
1490 filter (isSecretKey . packet)
1491 $ zipWith (mappedPacketWithHint fname) ps [1..]
1492 where fname = resolveForReport (Just ctx) f
1493 slurpkeys m ps = m `Map.union` Map.fromList ps'
1494 where ps' = zip (map (keykey . packet) ps) ps
1495 wk = listToMaybe $ do
1496 fp <- maybeToList grip
1497 let matchfp mp = not (is_subkey p) && matchpr fp p == fp
1498 where p = packet mp
1499 Map.elems $ Map.filter matchfp keys
1500 accs = fmap (access . fst) ringPackets
1501 return (spilled,wk,grip,accs,keys,fmap snd unspilled)
1502
1503 doDecrypt <- makeMemoizingDecrypter keyring ctx keys
1504
1505 let wk = fmap packet mwk
1506 rt0 = KeyRingRuntime { rtPubring = homepubPath ctx
1507 , rtSecring = homesecPath ctx
1508 , rtGrip = grip
1509 , rtWorkingKey = wk
1510 , rtRingAccess = accs
1511 , rtKeyDB = Map.empty
1512 , rtPassphrases = doDecrypt
1513 }
1514 transformed0 <-
1515 let trans f (info,ps) = do
1516 let manip = combineTransforms (transforms info)
1517 rt1 = rt0 { rtKeyDB = merge Map.empty f ps }
1518 acc = Just Sec /= Map.lookup f accs
1519 r <- performManipulations doDecrypt rt1 mwk manip
1520 try r $ \(rt2,report) -> do
1521 return $ KikiSuccess (report,(info,flattenKeys acc $ rtKeyDB rt2))
1522#if MIN_VERSION_containers(0,5,0)
1523 in fmap sequenceA $ Map.traverseWithKey trans spilled
1524#else
1525 in fmap sequenceA $ Traversable.traverse (uncurry trans) $ Map.mapWithKey (,) spilled
1526#endif
1527 try transformed0 $ \transformed -> do
1528 let db_rings = Map.foldlWithKey' mergeIt Map.empty transformed
1529 where
1530 mergeIt db f (_,(info,ps)) = merge db f ps
1531 reportTrans = concat $ Map.elems $ fmap fst transformed
1532
1533 -- Wallets
1534 let importWalletKey wk db' (top,fname,sub,tag) = do
1535 try db' $ \(db',report0) -> do
1536 r <- doImportG doDecrypt
1537 db'
1538 (fmap keykey $ maybeToList wk)
1539 [mkUsage tag]
1540 fname
1541 sub
1542 try r $ \(db'',report) -> do
1543 return $ KikiSuccess (db'', report0 ++ report)
1544
1545 wms <- mapM (readw wk) (files iswallet)
1546 let wallet_keys = do
1547 maybeToList wk
1548 (fname,xs) <- wms
1549 (_,sub,(_,m)) <- xs
1550 (tag,top) <- Map.toList m
1551 return (top,fname,sub,tag)
1552 db <- foldM (importWalletKey wk) (KikiSuccess (db_rings,[])) wallet_keys
1553 try db $ \(db,reportWallets) -> do
1554
1555 -- PEM files
1556 let pems = do
1557 (n,stream) <- Map.toList $ opFiles keyring
1558 grip <- maybeToList grip
1559 n <- resolveInputFile ctx n
1560 guard $ spillable stream && isSecretKeyFile (typ stream)
1561 let us = mapMaybe usageFromFilter [fill stream,spill stream]
1562 usage <- take 1 us
1563 guard $ all (==usage) $ drop 1 us
1564 -- TODO: KikiCondition reporting for spill/fill usage mismatch?
1565 let (topspec,subspec) = parseSpec grip usage
1566 ms = map fst $ filterMatches topspec (Map.toList db)
1567 cmd = initializer stream
1568 return (n,subspec,ms,stream, cmd)
1569 imports <- filterM (\(n,_,_,_,_) -> doesFileExist n) pems
1570 db <- foldM (importSecretKey doDecrypt) (KikiSuccess (db,[])) imports
1571 try db $ \(db,reportPEMs) -> do
1572
1573 -- generate keys
1574 let gens = mapMaybe g $ Map.toList genMap
1575 where g (Generate _ params,v) = Just (params,v)
1576 g _ = Nothing
1577
1578 db <- generateInternals doDecrypt mwk db gens
1579 try db $ \(db,reportGens) -> do
1580
1581 r <- mergeHostFiles keyring db ctx
1582 try r $ \((db,hs),reportHosts) -> do
1583
1584 return $ KikiSuccess ( (db, grip, mwk, hs, accs, doDecrypt, unspilled)
1585 , reportTrans ++ reportWallets ++ reportPEMs ++ reportGens ++ reportHosts )
1586
1587generateInternals ::
1588 (MappedPacket -> IO (KikiCondition Packet))
1589 -> Maybe MappedPacket
1590 -> Map.Map KeyKey KeyData
1591 -> [(GenerateKeyParams,StreamInfo)]
1592 -> IO (KikiCondition (Map.Map KeyKey KeyData, [(FilePath, KikiReportAction)]))
1593generateInternals doDecrypt mwk db gens = do
1594 case fmap packet mwk >>= \wk -> Map.lookup (keykey wk) db of
1595 Just kd0 -> do
1596 kd <- foldM (generateSubkey doDecrypt) (KikiSuccess (kd0,[])) gens
1597 try kd $ \(kd,reportGens) -> do
1598 let kk = keykey $ packet $ fromJust mwk
1599 return $ KikiSuccess (Map.insert kk kd db,reportGens)
1600 Nothing -> return $ KikiSuccess (db,[])
1601
1602torhash :: Packet -> String
1603torhash key = fromMaybe "" $ derToBase32 <$> derRSA key
1604
1605derToBase32 :: ByteString -> String
1606#if !defined(VERSION_cryptonite)
1607derToBase32 = map toLower . Base32.encode . S.unpack . SHA1.hashlazy
1608#else
1609derToBase32 = map toLower . Base32.encode . S.unpack . sha1
1610 where
1611 sha1 :: L.ByteString -> S.ByteString
1612 sha1 x = convert (Vincent.hashlazy x :: Vincent.Digest Vincent.SHA1)
1613#endif
1614
1615derRSA :: Packet -> Maybe ByteString
1616derRSA rsa = do
1617 k <- rsaKeyFromPacket rsa
1618 return $ encodeASN1 DER (toASN1 k [])
1619
1620unconditionally :: IO (KikiCondition a) -> IO a
1621unconditionally action = do
1622 r <- action
1623 case r of
1624 KikiSuccess x -> return x
1625 e -> error $ errorString e
1626
1627try :: Monad m => KikiCondition a -> (a -> m (KikiCondition b)) -> m (KikiCondition b)
1628try x body =
1629 case functorToEither x of
1630 Left e -> return e
1631 Right x -> body x
1632
1633
1634data ParsedCert = ParsedCert
1635 { pcertKey :: Packet
1636 , pcertTimestamp :: UTCTime
1637 , pcertBlob :: L.ByteString
1638 }
1639 deriving (Show,Eq)
1640data SecretPEMData = PEMPacket Packet | PEMCertificate ParsedCert
1641 deriving (Show,Eq)
1642
1643spemPacket (PEMPacket p) = Just p
1644spemPacket _ = Nothing
1645
1646spemCert (PEMCertificate p) = Just p
1647spemCert _ = Nothing
1648
1649toStrict :: L.ByteString -> S.ByteString
1650toStrict = foldr1 (<>) . L.toChunks
1651
1652-- No instance for (ASN1Object RSA.PublicKey)
1653
1654parseCertBlob comp bs = do
1655 asn1 <- either (const Nothing) Just
1656 $ decodeASN1 DER bs
1657 let asn1' = drop 2 asn1
1658 cert <- either (const Nothing) (Just . fst) (fromASN1 asn1')
1659 let _ = cert :: X509.Certificate
1660 notBefore :: UTCTime
1661#if MIN_VERSION_x509(1,5,0)
1662 notBefore = toUTC ( timeFromElapsedP (timeGetElapsedP vincentTime) :: CTime) -- nanoToUTCTime nano
1663 where (vincentTime,_) = X509.certValidity cert
1664#else
1665 (notBefore,_) = X509.certValidity cert
1666#endif
1667 case X509.certPubKey cert of
1668 X509.PubKeyRSA key -> do
1669 let withoutkey =
1670 let ekey = toStrict $ encodeASN1 DER (toASN1 key [])
1671 (pre,post) = S.breakSubstring ekey $ toStrict bs
1672 post' = S.drop (S.length ekey) post
1673 len :: Word16
1674 len = if S.null post then maxBound
1675 else fromIntegral $ S.length pre
1676 in if len < 4096
1677 then encode len <> GZip.compress (Char8.fromChunks [pre,post'])
1678 else bs
1679 return
1680 ParsedCert { pcertKey = packetFromPublicRSAKey notBefore
1681 (MPI $ RSA.public_n key)
1682 (MPI $ RSA.public_e key)
1683 , pcertTimestamp = notBefore
1684 , pcertBlob = if comp then withoutkey
1685 else bs
1686 }
1687 _ -> Nothing
1688
1689packetFromPublicRSAKey notBefore n e =
1690 PublicKeyPacket { version = 4
1691 , timestamp = round $ utcTimeToPOSIXSeconds notBefore
1692 , key_algorithm = RSA
1693 , key = [('n',n),('e',e)]
1694 , is_subkey = True
1695 , v3_days_of_validity = Nothing
1696 }
1697
1698decodeBlob cert =
1699 if 0 /= (bs `L.index` 0) .&. 0x10
1700 then bs
1701 else let (keypos0,bs') = L.splitAt 2 bs
1702 keypos :: Word16
1703 keypos = decode keypos0
1704 ds = GZip.decompress bs'
1705 (prekey,postkey) = L.splitAt (fromIntegral keypos) ds
1706 in prekey <> key <> postkey
1707 where
1708 bs = pcertBlob cert
1709 key = maybe "" (encodeASN1 DER . flip toASN1 []) $ rsaKeyFromPacket $ pcertKey cert
1710
1711extractRSAKeyFields :: [(ByteString,ByteString)] -> Maybe RSAPrivateKey
1712extractRSAKeyFields kvs = do
1713 let kvs' = mapMaybe (\(k,v) -> (k,) <$> parseField v) kvs
1714 n <- lookup "Modulus" kvs'
1715 e <- lookup "PublicExponent" kvs'
1716 d <- lookup "PrivateExponent" kvs'
1717 p <- lookup "Prime1" kvs' -- p
1718 q <- lookup "Prime2" kvs' -- q
1719 dmodp1 <- lookup "Exponent1" kvs' -- dP = d `mod` (p - 1)
1720 dmodqminus1 <- lookup "Exponent2" kvs' -- dQ = d `mod` (q - 1)
1721 u <- lookup "Coefficient" kvs'
1722 {-
1723 case (d,p,dmodp1) of
1724 (MPI dd, MPI pp, MPI x) | x == dd `mod` (pp-1) -> return ()
1725 _ -> error "dmodp fail!"
1726 case (d,q,dmodqminus1) of
1727 (MPI dd, MPI qq, MPI x) | x == dd `mod` (qq-1) -> return ()
1728 _ -> error "dmodq fail!"
1729 -}
1730 return $ RSAPrivateKey
1731 { rsaN = n
1732 , rsaE = e
1733 , rsaD = d
1734 , rsaP = p
1735 , rsaQ = q
1736 , rsaDmodP1 = dmodp1
1737 , rsaDmodQminus1 = dmodqminus1
1738 , rsaCoefficient = u }
1739 where
1740 parseField blob = MPI <$> m
1741 where m = bigendian <$> Base64.decode (Char8.unpack blob)
1742
1743 bigendian bs = snd $ foldl' (\(c,a) w8 -> (c-1, a + 256^c * fromIntegral w8)) (nlen-1,0) bs
1744 where
1745 nlen = length bs
1746
1747rsaToPGP stamp rsa = SecretKeyPacket
1748 { version = 4
1749 , timestamp = fromTime stamp -- toEnum (fromEnum stamp)
1750 , key_algorithm = RSA
1751 , key = [ -- public fields...
1752 ('n',rsaN rsa)
1753 ,('e',rsaE rsa)
1754 -- secret fields
1755 ,('d',rsaD rsa)
1756 ,('p',rsaQ rsa) -- Note: p & q swapped
1757 ,('q',rsaP rsa) -- Note: p & q swapped
1758 ,('u',rsaCoefficient rsa)
1759 ]
1760 -- , ecc_curve = def
1761 , s2k_useage = 0
1762 , s2k = S2K 100 ""
1763 , symmetric_algorithm = Unencrypted
1764 , encrypted_data = ""
1765 , is_subkey = True
1766 }
1767
1768readSecretDNSFile :: InputFile -> IO Packet
1769readSecretDNSFile fname = do
1770 let ctx = InputFileContext "" ""
1771 stamp <- getInputFileTime ctx fname
1772 input <- readInputFileL ctx fname
1773 let kvs = map ( second (Char8.dropWhile isSpace . Char8.drop 1)
1774 . Char8.break (==':'))
1775 $ Char8.lines input
1776 alg = maybe RSA parseAlg $ lookup "Algorithm" kvs
1777 parseAlg spec = case Char8.words spec of
1778 nstr:_ -> case read (Char8.unpack nstr) :: Int of
1779 2 -> DH
1780 3 -> DSA -- SHA1
1781 5 -> RSA -- SHA1
1782 6 -> DSA -- NSEC3-SHA1 (RFC5155)
1783 7 -> RSA -- RSASHA1-NSEC3-SHA1 (RFC5155)
1784 8 -> RSA -- SHA256
1785 10 -> RSA -- SHA512 (RFC5702)
1786 -- 12 -> GOST
1787 13 -> ECDSA -- P-256 SHA256 (RFC6605)
1788 14 -> ECDSA -- P-384 SHA384 (RFC6605)
1789 _ -> RSA
1790 case alg of
1791 RSA -> return $ rsaToPGP stamp $ fromJust $ extractRSAKeyFields kvs
1792
1793
1794readSecretPEMFile :: InputFile -> IO [SecretPEMData]
1795readSecretPEMFile fname = do
1796 -- warn $ fname ++ ": reading ..."
1797 let ctx = InputFileContext "" ""
1798 -- Note: The key's timestamp is included in it's fingerprint.
1799 -- Therefore, we should attempt to preserve it.
1800 stamp <- getInputFileTime ctx fname
1801 input <- readInputFileL ctx fname
1802 let edta = scanAndParse (fmap Left dateParser <> fmap Right (pkcs1 <> cert)) $ Char8.lines input
1803 pkcs1 = fmap (parseRSAPrivateKey . pemBlob)
1804 $ pemParser $ Just "RSA PRIVATE KEY"
1805 cert = fmap (fmap PEMCertificate . parseCertBlob False . pemBlob)
1806 $ pemParser $ Just "CERTIFICATE"
1807 parseRSAPrivateKey dta = do
1808 let e = decodeASN1 DER dta
1809 asn1 <- either (const $ mzero) return e
1810 rsa <- either (const mzero) (return . fst) (fromASN1 asn1)
1811 let _ = rsa :: RSAPrivateKey
1812 return $ PEMPacket $ rsaToPGP stamp rsa
1813 dta = catMaybes $ map snd $ scanl mergeDate (stamp,Nothing) edta
1814 mergeDate (_,obj) (Left tm) = (fromTime tm,obj)
1815 mergeDate (tm,_) (Right (Just (PEMPacket key))) = (tm,Just $ PEMPacket key')
1816 where key' = if tm < fromTime (timestamp key)
1817 then key { timestamp = fromTime tm }
1818 else key
1819 mergeDate (tm,_) (Right mb) = (tm,mb)
1820 return $ dta
1821
1822doImport
1823 :: (MappedPacket -> IO (KikiCondition Packet))
1824 -> Map.Map KeyKey KeyData
1825 -> (FilePath, Maybe [Char], [KeyKey], StreamInfo, t)
1826 -> IO (KikiCondition (Map.Map KeyKey KeyData, [(FilePath,KikiReportAction)]))
1827doImport doDecrypt db (fname,subspec,ms,typ -> typ,_) = do
1828 flip (maybe $ return CannotImportMasterKey)
1829 subspec $ \tag -> do
1830 (certs,keys) <- case typ of
1831 PEMFile -> do
1832 ps <- readSecretPEMFile (ArgFile fname)
1833 let (mapMaybe spemCert -> certs,mapMaybe spemPacket-> keys)
1834 = partition (isJust . spemCert) ps
1835 return (certs,keys)
1836 DNSPresentation -> do
1837 p <- readSecretDNSFile (ArgFile fname)
1838 return ([],[p])
1839 -- TODO Probably we need to move to a new design where signature
1840 -- packets are merged into the database in one phase with null
1841 -- signatures, and then the signatures are made in the next phase.
1842 -- This would let us merge annotations (like certificates) from
1843 -- seperate files.
1844 foldM (importKey tag certs) (KikiSuccess (db,[])) keys
1845 where
1846 importKey tag certs prior key = do
1847 try prior $ \(db,report) -> do
1848 let (m0,tailms) = splitAt 1 ms
1849 if (not (null tailms) || null m0)
1850 then return $ AmbiguousKeySpec fname
1851 else do
1852 let kk = keykey key
1853 cs = filter (\c -> kk==keykey (pcertKey c)) certs
1854 blobs = map mkCertNotation $ nub $ map pcertBlob cs
1855 mkCertNotation bs = NotationDataPacket
1856 { human_readable = False
1857 , notation_name = "x509cert@"
1858 , notation_value = Char8.unpack bs }
1859 datedKey = key { timestamp = fromTime $ minimum dates }
1860 dates = fromTime (timestamp key) : map pcertTimestamp certs
1861 r <- doImportG doDecrypt db m0 (mkUsage tag:blobs) fname datedKey
1862 try r $ \(db',report') -> do
1863 return $ KikiSuccess (db',report++report')
1864
1865doImportG
1866 :: (MappedPacket -> IO (KikiCondition Packet))
1867 -> Map.Map KeyKey KeyData
1868 -> [KeyKey] -- m0, only head is used
1869 -> [SignatureSubpacket] -- tags
1870 -> FilePath
1871 -> Packet
1872 -> IO (KikiCondition (Map.Map KeyKey KeyData, [(FilePath,KikiReportAction)]))
1873doImportG doDecrypt db m0 tags fname key = do
1874 let kk = head m0
1875 Just kd@(KeyData top topsigs uids subs) = Map.lookup kk db
1876 kdr <- insertSubkey doDecrypt kk kd tags fname key
1877 try kdr $ \(kd',rrs) -> return $ KikiSuccess (Map.insert kk kd' db, rrs)
1878
1879insertSubkey doDecrypt kk (KeyData top topsigs uids subs) tags fname key = do
1880 let subkk = keykey key
1881 (is_new, subkey) = maybe (True, SubKey (mappedPacket fname key)
1882 [])
1883 ( (False,) . addOrigin )
1884 (Map.lookup subkk subs)
1885 where
1886 addOrigin (SubKey mp sigs) =
1887 let mp' = mp
1888 { locations = Map.insert fname
1889 (origin (packet mp) (-1))
1890 (locations mp) }
1891 in SubKey mp' sigs
1892 subs' = Map.insert subkk subkey subs
1893
1894 istor = do
1895 guard ("tor" `elem` mapMaybe usage tags)
1896 return $ "Anonymous <root@" ++ take 16 (torhash key) ++ ".onion>"
1897
1898 uids' <- flip (maybe $ return $ KikiSuccess (uids,[])) istor $ \idstr -> do
1899 let has_torid = do
1900 -- TODO: check for omitted real name field
1901 (sigtrusts,om) <- Map.lookup idstr uids
1902 listToMaybe $ do
1903 s <- (signatures $ Message (packet top:UserIDPacket idstr:map (packet . fst) sigtrusts))
1904 signatures_over $ verify (Message [packet top]) s
1905 flip (flip maybe $ const $ return $ KikiSuccess (uids,[])) has_torid $ do
1906 wkun <- doDecrypt top
1907
1908 try wkun $ \wkun -> do
1909
1910 let keyflags = keyFlags wkun (map packet $ flattenAllUids fname True uids)
1911 uid = UserIDPacket idstr
1912 -- sig_ov = fst $ torsig g (packet top) wkun uid timestamp keyflags
1913 tor_ov = makeInducerSig (packet top) wkun uid keyflags
1914 sig_ov <- pgpSign (Message [wkun])
1915 tor_ov
1916 SHA1
1917 (fingerprint wkun)
1918 flip (maybe $ return $ KikiSuccess (uids,[(fname, WarnFailedToMakeSignature)]))
1919 (sig_ov >>= listToMaybe . signatures_over)
1920 $ \sig -> do
1921 let om = Map.singleton fname (origin sig (-1))
1922 trust = Map.empty
1923 return $ KikiSuccess
1924 ( Map.insert idstr ([( (mappedPacket fname sig) {locations=om}
1925 , trust)],om) uids
1926 , [] )
1927
1928 try uids' $ \(uids',report) -> do
1929
1930 let SubKey subkey_p subsigs = subkey
1931 wk = packet top
1932 (xs',minsig,ys') = findTag tags wk key subsigs
1933 doInsert mbsig = do
1934 -- NEW SUBKEY BINDING SIGNATURE
1935 sig' <- makeSig doDecrypt top fname subkey_p tags mbsig
1936 try sig' $ \(sig',report) -> do
1937 report <- return $ fmap (fname,) report ++ [(fname, YieldSignature)]
1938 let subs' = Map.insert subkk
1939 (SubKey subkey_p $ xs'++[sig']++ys')
1940 subs
1941 return $ KikiSuccess ( KeyData top topsigs uids' subs'
1942 , report )
1943
1944 report <- let f = if is_new then (++[(fname,YieldSecretKeyPacket s)])
1945 else id
1946 s = show (fmap fst minsig,fingerprint key)
1947 in return (f report)
1948
1949 case minsig of
1950 Nothing -> doInsert Nothing -- we need to create a new sig
1951 Just (True,sig) -> -- we can deduce is_new == False
1952 -- we may need to add a tor id
1953 return $ KikiSuccess ( KeyData top topsigs uids' subs'
1954 , report )
1955 Just (False,sig) -> doInsert (Just sig) -- We have a sig, but is missing usage@ tag
1956
1957isCryptoCoinKey :: Packet -> Bool
1958isCryptoCoinKey p =
1959 and [ isKey p
1960 , key_algorithm p == ECDSA
1961 , lookup 'c' (key p) == Just (MPI secp256k1_id)
1962 ]
1963
1964getCryptoCoinTag :: Packet -> Maybe CryptoCoins.CoinNetwork
1965getCryptoCoinTag p | isSignaturePacket p = do
1966 -- CryptoCoins.secret
1967 let sps = hashed_subpackets p ++ unhashed_subpackets p
1968 u <- listToMaybe $ mapMaybe usage sps
1969 CryptoCoins.lookupNetwork CryptoCoins.network_name u
1970getCryptoCoinTag _ = Nothing
1971
1972
1973coinKeysOwnedBy :: KeyDB -> Maybe Packet -> [(CryptoCoins.CoinNetwork,MappedPacket)]
1974coinKeysOwnedBy db wk = do
1975 wk <- maybeToList wk
1976 let kk = keykey wk
1977 KeyData top topsigs uids subs <- maybeToList $ Map.lookup kk db
1978 (subkk,SubKey mp sigs) <- Map.toList subs
1979 let sub = packet mp
1980 guard $ isCryptoCoinKey sub
1981 tag <- take 1 $ mapMaybe (getCryptoCoinTag . packet . fst) sigs
1982 return (tag,mp)
1983
1984walletImportFormat :: Word8 -> Packet -> String
1985walletImportFormat idbyte k = secret_base58_foo
1986 where
1987 -- isSecret (SecretKeyPacket {}) = True
1988 -- isSecret _ = False
1989 secret_base58_foo = base58_encode seckey
1990 Just d = lookup 'd' (key k)
1991 (_,bigendian) = S.splitAt 2 (S.concat $ L.toChunks $ encode d)
1992 seckey = S.cons idbyte bigendian
1993
1994writeWalletKeys :: KeyRingOperation -> KeyDB -> Maybe Packet -> IO (KikiCondition [(FilePath,KikiReportAction)])
1995writeWalletKeys krd db wk = do
1996 let cs = db `coinKeysOwnedBy` wk
1997 -- export wallet keys
1998 isMutableWallet (fill -> KF_None) = False
1999 isMutableWallet (typ -> WalletFile {}) = True
2000 isMutableWallet _ = False
2001 files pred = do
2002 (f,stream) <- Map.toList (opFiles krd)
2003 guard (pred stream)
2004 resolveInputFile (InputFileContext "" "") f
2005 let writeWallet report n = do
2006 let cs' = do
2007 (nw,mp) <- cs
2008 -- let fns = Map.keys (locations mp)
2009 -- trace ("COIN KEY: "++show fns) $ return ()
2010 guard . not $ Map.member n (locations mp)
2011 let wip = walletImportFormat (CryptoCoins.private_byte_id nw) (packet mp)
2012 return (CryptoCoins.network_name nw,wip)
2013 handleIO_ (return report) $ do
2014 -- TODO: This AppendMode stratagy is not easy to adapt from FilePath-based
2015 -- to InputFile-based.
2016 withFile n AppendMode $ \fh -> do
2017 rs <- forM cs' $ \(net,wip) -> do
2018 hPutStrLn fh wip
2019 return (n, NewWalletKey net)
2020 return (report ++ rs)
2021 report <- foldM writeWallet [] (files isMutableWallet)
2022 return $ KikiSuccess report
2023
2024ifSecret :: Packet -> t -> t -> t
2025ifSecret (SecretKeyPacket {}) t f = t
2026ifSecret _ t f = f
2027
2028showPacket :: Packet -> String
2029showPacket p | isKey p = (if is_subkey p
2030 then showPacket0 p
2031 else ifSecret p "----Secret-----" "----Public-----")
2032 ++ " "++show (key_algorithm p)++" "++fingerprint p
2033 | isUserID p = showPacket0 p ++ " " ++ show (uidkey p)
2034 | otherwise = showPacket0 p
2035showPacket0 p = concat . take 1 $ words (show p)
2036
2037
2038-- | returns Just True so as to indicate that
2039-- the public portions of keys will be imported
2040importPublic :: Maybe Bool
2041importPublic = Just True
2042
2043-- | returns False True so as to indicate that
2044-- the public portions of keys will be imported
2045importSecret :: Maybe Bool
2046importSecret = Just False
2047
2048
2049-- TODO: Do we need to memoize this?
2050guardAuthentic :: KeyRingRuntime -> KeyData -> Maybe ()
2051guardAuthentic rt keydata = guard (isauth rt keydata)
2052
2053isauth :: KeyRingRuntime -> KeyData -> Bool
2054isauth rt keydata = dont_have keydata && maybe False (`has_good_sig` keydata) wk
2055 where wk = workingKey (rtGrip rt) (rtKeyDB rt)
2056 dont_have (KeyData p _ _ _) = not . Map.member (rtPubring rt)
2057 $ locations p
2058 has_good_sig wk (KeyData k sigs uids subs) = any goodsig $ Map.toList uids
2059 where
2060 goodsig (uidstr,(sigs,_)) = not . null $ do
2061 sig0 <- fmap (packet . fst) sigs
2062 pre_ov <- signatures (Message [packet k, UserIDPacket uidstr, sig0])
2063 signatures_over $ verify (Message [wk]) pre_ov
2064
2065 workingKey grip use_db = listToMaybe $ do
2066 fp <- maybeToList grip
2067 elm <- Map.elems use_db
2068 guard $ matchSpec (KeyGrip fp) elm
2069 return $ keyPacket elm
2070
2071writeRingKeys :: KeyRingOperation -> KeyRingRuntime -> Map.Map InputFile Message
2072 -> [(FilePath,KikiReportAction)]
2073 {-
2074 -> KeyDB -> Maybe Packet
2075 -> FilePath -> FilePath
2076 -}
2077 -> IO (KikiCondition [(FilePath,KikiReportAction)])
2078writeRingKeys krd rt {- db wk secring pubring -} unspilled report_manips = do
2079 let isring (KeyRingFile {}) = True
2080 isring _ = False
2081 db = rtKeyDB rt
2082 secring = rtSecring rt
2083 pubring = rtPubring rt
2084 ctx = InputFileContext secring pubring
2085 let s = do
2086 (f,f0,stream) <- do
2087 (f0,stream) <- Map.toList (opFiles krd)
2088 guard (isring $ typ stream)
2089 f <- resolveInputFile ctx f0
2090 return (f,f0,stream)
2091 let db' = fromMaybe db $ do
2092 msg <- Map.lookup f0 unspilled
2093 return $ merge db f0 msg
2094 x = do
2095 let wantedForFill :: Access -> KeyFilter -> KeyData -> Maybe Bool
2096 wantedForFill acc KF_None = importByExistingMaster
2097 -- Note the KF_None case is almost irrelevent as it will be
2098 -- filtered later when isMutable returns False.
2099 -- We use importByExistingMaster in order to generate
2100 -- MissingPacket warnings. To disable those warnings, use
2101 -- const Nothing instead.
2102 wantedForFill acc (KF_Match {}) = importByExistingMaster
2103 wantedForFill acc KF_Subkeys = importByExistingMaster
2104 wantedForFill acc KF_Authentic = \kd -> do guardAuthentic rt kd
2105 importByAccess acc kd
2106 wantedForFill acc KF_All = importByAccess acc
2107 importByAccess Pub kd = importPublic
2108 importByAccess Sec kd = importSecret
2109 importByAccess AutoAccess kd =
2110 mplus (importByExistingMaster kd)
2111 (error $ f ++ ": write public or secret key to file?")
2112 importByExistingMaster kd@(KeyData p _ _ _) =
2113 fmap originallyPublic $ Map.lookup f $ locations p
2114 d <- sortByHint f keyMappedPacket (Map.elems db')
2115 acc <- maybeToList $ Map.lookup f0 (rtRingAccess rt)
2116 only_public <- maybeToList $ wantedForFill acc (fill stream) d
2117 guard $ only_public || isSecretKey (keyPacket d)
2118 case fill stream of
2119 KF_Match usage -> do grip <- maybeToList $ rtGrip rt
2120 flattenTop f only_public
2121 $ filterNewSubs f (parseSpec grip usage) d
2122 _ -> flattenTop f only_public d
2123 new_packets = filter isnew x
2124 where isnew p = isNothing (Map.lookup (resolveForReport Nothing f0) $ locations p)
2125 -- TODO: We depend on an exact string match between the reported
2126 -- file origin of the deleted packet and the path of the file we are
2127 -- writing. Verify that this is a safe assumption.
2128 isdeleted (f',DeletedPacket _) = f'==f
2129 isdeleted _ = False
2130 guard (not (null new_packets) || any isdeleted report_manips)
2131 return ((f0,isMutable stream),(new_packets,x))
2132 let (towrites,report) = (\f -> foldl f ([],[]) s) $
2133 \(ws,report) ((f,mutable),(new_packets,x)) ->
2134 if mutable
2135 then
2136 let rs = flip map new_packets
2137 $ \c -> (concat $ resolveInputFile ctx f, NewPacket $ showPacket (packet c))
2138 in (ws++[(f,x)],report++rs)
2139 else
2140 let rs = flip map new_packets
2141 $ \c -> (concat $ resolveInputFile ctx f,MissingPacket (showPacket (packet c)))
2142 in (ws,report++rs)
2143 forM_ towrites $ \(f,x) -> do
2144 let m = Message $ map packet x
2145 -- warn $ "writing "++f
2146 writeInputFileL ctx f (encode m)
2147 return $ KikiSuccess report
2148
2149
2150{-
2151getSubkeysForExport kk subspec db = do
2152 kd <- maybeToList $ Map.lookup kk db
2153 subkeysForExport subspec kd
2154-}
2155
2156-- | If provided Nothing for the first argument, this function returns the
2157-- master key of the given identity. Otherwise, it returns all the subkeys of
2158-- the given identity which have a usage tag that matches the first argument.
2159subkeysForExport :: Maybe String -> KeyData -> [MappedPacket]
2160subkeysForExport subspec (KeyData key _ _ subkeys) = do
2161 let subs tag = do
2162 e <- Map.elems subkeys
2163 guard $ doSearch key tag e
2164 return $ subkeyMappedPacket e
2165 maybe [key] subs subspec
2166 where
2167 doSearch key tag (SubKey sub_mp sigtrusts) =
2168 let (_,v,_) = findTag [mkUsage tag]
2169 (packet key)
2170 (packet sub_mp)
2171 sigtrusts
2172 in fmap fst v==Just True
2173
2174writePEM :: String -> String -> String
2175writePEM typ dta = pem
2176 where
2177 pem = unlines . concat $
2178 [ ["-----BEGIN " <> typ <> "-----"]
2179 , split64s dta
2180 , ["-----END " <> typ <> "-----"] ]
2181 split64s :: String -> [String]
2182 split64s "" = []
2183 split64s dta = line : split64s rest where (line,rest) = splitAt 64 dta
2184
2185 -- 64 byte lines
2186
2187rsaPrivateKeyFromPacket :: Packet -> Maybe RSAPrivateKey
2188rsaPrivateKeyFromPacket pkt@(SecretKeyPacket {}) = do
2189 -- public fields...
2190 n <- lookup 'n' $ key pkt
2191 e <- lookup 'e' $ key pkt
2192 -- secret fields
2193 MPI d <- lookup 'd' $ key pkt
2194 MPI q <- lookup 'p' $ key pkt -- Note: p & q swapped
2195 MPI p <- lookup 'q' $ key pkt -- Note: p & q swapped
2196
2197 -- Note: Here we fail if 'u' key is missing.
2198 -- Ideally, it would be better to compute (inverse q) mod p
2199 -- see Algebra.Structures.EuclideanDomain.extendedEuclidAlg
2200 -- (package constructive-algebra)
2201 coefficient <- lookup 'u' $ key pkt
2202
2203 let dmodp1 = MPI $ d `mod` (p - 1)
2204 dmodqminus1 = MPI $ d `mod` (q - 1)
2205 return $ RSAPrivateKey
2206 { rsaN = n
2207 , rsaE = e
2208 , rsaD = MPI d
2209 , rsaP = MPI p
2210 , rsaQ = MPI q
2211 , rsaDmodP1 = dmodp1
2212 , rsaDmodQminus1 = dmodqminus1
2213 , rsaCoefficient = coefficient }
2214rsaPrivateKeyFromPacket _ = Nothing
2215
2216secretPemFromPacket packet = pemFromPacket Sec packet
2217
2218pemFromPacket Sec packet =
2219 case key_algorithm packet of
2220 RSA -> do
2221 rsa <- rsaPrivateKeyFromPacket packet -- RSAPrivateKey
2222 let asn1 = toASN1 rsa []
2223 bs = encodeASN1 DER asn1
2224 dta = Base64.encode (L.unpack bs)
2225 output = writePEM "RSA PRIVATE KEY" dta
2226 Just output
2227 algo -> Nothing
2228pemFromPacket Pub packet =
2229 case key_algorithm packet of
2230 RSA -> do
2231 rsa <- rsaKeyFromPacket packet
2232 let asn1 = toASN1 (pkcs8 rsa) []
2233 bs = encodeASN1 DER asn1
2234 dta = Base64.encode (L.unpack bs)
2235 output = writePEM "PUBLIC KEY" dta
2236 Just output
2237 algo -> Nothing
2238pemFromPacket AutoAccess p@(PublicKeyPacket {}) = pemFromPacket Pub p
2239pemFromPacket AutoAccess p@(SecretKeyPacket {}) = pemFromPacket Sec p
2240pemFromPacket AutoAccess _ = Nothing
2241
2242writeKeyToFile ::
2243 Bool -> StreamInfo -> InputFile -> Packet -> IO [(InputFile, KikiReportAction)]
2244writeKeyToFile False stream@(StreamInfo { typ = PEMFile }) fname packet = do
2245 case pemFromPacket (access stream) packet of
2246 Just output -> do
2247 let stamp = toEnum . fromEnum $ timestamp packet
2248 handleIO_ (return [(fname, FailedFileWrite)]) $ do
2249 saved_mask <- setFileCreationMask 0o077
2250 -- Note: The key's timestamp is included in it's fingerprint.
2251 -- Therefore, we should attempt to preserve it.
2252 writeStamped (InputFileContext "" "") fname stamp output
2253 setFileCreationMask saved_mask
2254 return [(fname, ExportedSubkey)]
2255 Nothing -> return [(fname, UnableToExport (key_algorithm packet) $ fingerprint packet)]
2256
2257writeKeyToFile False StreamInfo { typ = DNSPresentation } fname packet = do
2258 case key_algorithm packet of
2259 RSA -> do
2260 flip (maybe (return []))
2261 (rsaPrivateKeyFromPacket packet) -- RSAPrivateKey
2262 $ \rsa -> do
2263 let -- asn1 = toASN1 rsa []
2264 -- bs = encodeASN1 DER asn1
2265 -- dta = Base64.encode (L.unpack bs)
2266 b64 ac rsa = Base64.encode (S.unpack $ i2bs_unsized i)
2267 where
2268 MPI i = ac rsa
2269 i2bs_unsized :: Integer -> S.ByteString
2270 i2bs_unsized 0 = S.singleton 0
2271 i2bs_unsized i = S.reverse $ S.unfoldr go i
2272 where go i' = if i' <= 0 then Nothing
2273 else Just (fromIntegral i', (i' `shiftR` 8))
2274 output = unlines
2275 [ "Private-key-format: v1.2"
2276 , "Algorithm: 8 (RSASHA256)"
2277 , "Modulus: " ++ b64 rsaN rsa
2278 , "PublicExponent: " ++ b64 rsaE rsa
2279 , "PrivateExponent: " ++ b64 rsaD rsa
2280 , "Prime1: " ++ b64 rsaP rsa
2281 , "Prime2: " ++ b64 rsaQ rsa
2282 , "Exponent1: " ++ b64 rsaDmodP1 rsa
2283 , "Exponent2: " ++ b64 rsaDmodQminus1 rsa
2284 , "Coefficient: " ++ b64 rsaCoefficient rsa
2285 ]
2286 stamp = toEnum . fromEnum $ timestamp packet
2287 handleIO_ (return [(fname, FailedFileWrite)]) $ do
2288 saved_mask <- setFileCreationMask 0o077
2289 -- Note: The key's timestamp is included in it's fingerprint.
2290 -- Therefore, we should attempt to preserve it.
2291 writeStamped (InputFileContext "" "") fname stamp output
2292 setFileCreationMask saved_mask
2293 return [(fname, ExportedSubkey)]
2294 algo -> return [(fname, UnableToExport algo $ fingerprint packet)]
2295
2296writePEMKeys :: (MappedPacket -> IO (KikiCondition Packet))
2297 -> KeyDB
2298 -> [(FilePath,Maybe String,[MappedPacket],StreamInfo)]
2299 -> IO (KikiCondition [(FilePath,KikiReportAction)])
2300writePEMKeys doDecrypt db exports = do
2301 ds <- mapM decryptKeys exports
2302 let ds' = map functorToEither ds
2303 if null (lefts ds')
2304 then do
2305 rs <- mapM (\(f,stream,p) -> writeKeyToFile False stream (ArgFile f) p)
2306 (rights ds')
2307 return $ KikiSuccess (map (first $ resolveForReport Nothing) $ concat rs)
2308 else do
2309 return (head $ lefts ds')
2310 where
2311 decryptKeys (fname,subspec,[p],stream@(StreamInfo { access=Pub }))
2312 = return $ KikiSuccess (fname,stream,packet p) -- public keys are never encrypted.
2313 decryptKeys (fname,subspec,[p],stream) = do
2314 pun <- doDecrypt p
2315 try pun $ \pun -> do
2316 return $ KikiSuccess (fname,stream,pun)
2317
2318makeMemoizingDecrypter :: KeyRingOperation -> InputFileContext
2319 -> Map.Map KeyKey MappedPacket
2320 -> IO (MappedPacket -> IO (KikiCondition Packet))
2321makeMemoizingDecrypter operation ctx keys =
2322 if null chains then do
2323 -- (*) Notice we do not pass ctx to resolveForReport.
2324 -- This is because the merge function does not currently use a context
2325 -- and the pws map keys must match the MappedPacket locations.
2326 -- TODO: Perhaps these should both be of type InputFile rather than
2327 -- FilePath?
2328 -- pws :: Map.Map FilePath (IO S.ByteString)
2329 {-
2330 pws <-
2331 Traversable.mapM (cachedContents ctx . fromJust . pwfile . typ)
2332 (Map.mapKeys (resolveForReport Nothing) -- see note (*) note above
2333 $ Map.filter (isJust . pwfile . typ) $ opFiles operation)
2334 -}
2335 let prompt = Just "Enter possibly multi-line passphrase (Press CTRL-D when finished):\n"
2336 pws2 <-
2337 Traversable.mapM (cachedContents prompt ctx)
2338 $ Map.fromList $ mapMaybe
2339 (\spec -> (,passSpecPassFile spec) `fmap` do
2340 guard $ isNothing $ passSpecKeySpec spec
2341 passSpecRingFile spec)
2342 passspecs
2343 defpw <- do
2344 Traversable.mapM (cachedContents prompt ctx . passSpecPassFile)
2345 $ listToMaybe $ filter (\sp -> isNothing (passSpecRingFile sp)
2346 && isNothing (passSpecKeySpec sp))
2347 $ opPassphrases operation
2348 unkeysRef <- newIORef (Map.empty :: Map.Map KeyKey Packet)
2349 return $ doDecrypt unkeysRef ({- pws `Map.union` -} pws2) defpw
2350 else let PassphraseMemoizer f = head chains
2351 in return f
2352 where
2353 (chains,passspecs) = partition isChain $ opPassphrases operation
2354 where isChain (PassphraseMemoizer {}) = True
2355 isChain _ = False
2356 doDecrypt :: IORef (Map.Map KeyKey Packet)
2357 -> Map.Map FilePath (IO S.ByteString)
2358 -> Maybe (IO S.ByteString)
2359 -> MappedPacket
2360 -> IO (KikiCondition Packet)
2361 doDecrypt unkeysRef pws defpw mp0 = do
2362 unkeys <- readIORef unkeysRef
2363 let mp = fromMaybe mp0 $ do
2364 k <- Map.lookup kk keys
2365 return $ mergeKeyPacket "decrypt" mp0 k
2366 wk = packet mp0
2367 kk = keykey wk
2368 fs = Map.keys $ locations mp
2369
2370 decryptIt [] = return BadPassphrase
2371 decryptIt (getpw:getpws) = do
2372 -- TODO: This function should use mergeKeyPacket to
2373 -- combine the packet with it's unspilled version before
2374 -- attempting to decrypt it.
2375 pw <- getpw
2376 let wkun = fromMaybe wk $ decryptSecretKey pw (packet mp)
2377 case symmetric_algorithm wkun of
2378 Unencrypted -> do
2379 writeIORef unkeysRef (Map.insert kk wkun unkeys)
2380 return $ KikiSuccess wkun
2381 _ -> decryptIt getpws
2382
2383 getpws = mapMaybe (`Map.lookup` pws) fs ++ maybeToList defpw
2384
2385 case symmetric_algorithm wk of
2386 Unencrypted -> return (KikiSuccess wk)
2387 _ -> maybe (decryptIt getpws)
2388 (return . KikiSuccess)
2389 $ Map.lookup kk unkeys
2390
2391performManipulations ::
2392 (MappedPacket -> IO (KikiCondition Packet))
2393 -> KeyRingRuntime
2394 -> Maybe MappedPacket
2395 -> (KeyRingRuntime -> KeyData -> [PacketUpdate])
2396 -> IO (KikiCondition (KeyRingRuntime,KikiReport))
2397performManipulations doDecrypt rt wk manip = do
2398 let db = rtKeyDB rt
2399 performAll kd = foldM perform (KikiSuccess (kd,[])) $ manip rt kd
2400 r <- Traversable.mapM performAll db
2401 try (sequenceA r) $ \db -> do
2402 return $ KikiSuccess (rt { rtKeyDB = fmap fst db }, concatMap snd $ Map.elems db)
2403 where
2404 perform :: KikiCondition (KeyData,KikiReport) -> PacketUpdate -> IO (KikiCondition (KeyData,KikiReport))
2405 perform kd (InducerSignature uid subpaks) = do
2406 try kd $ \(kd,report) -> do
2407 flip (maybe $ return NoWorkingKey) wk $ \wk' -> do
2408 wkun' <- doDecrypt wk'
2409 try wkun' $ \wkun -> do
2410 let flgs = if keykey (keyPacket kd) == keykey wkun
2411 then keyFlags0 (keyPacket kd) (map (\(x,_,_)->x) selfsigs)
2412 else []
2413 sigOver = makeInducerSig (keyPacket kd)
2414 wkun
2415 (UserIDPacket uid)
2416 $ flgs ++ subpaks
2417 om = Map.singleton "--autosign" (origin p (-1)) where p = UserIDPacket uid
2418 toMappedPacket om p = (mappedPacket "" p) {locations=om}
2419 selfsigs = filter (\(sig,v,whosign) -> isJust (v >> Just wkun >>= guard
2420 . (== keykey whosign)
2421 . keykey)) vs
2422 keys = map keyPacket $ Map.elems (rtKeyDB rt)
2423 overs sig = signatures $ Message (keys++[keyPacket kd,UserIDPacket uid,sig])
2424 vs :: [ ( Packet -- signature
2425 , Maybe SignatureOver -- Nothing means non-verified
2426 , Packet ) -- key who signed
2427 ]
2428 vs = do
2429 x <- maybeToList $ Map.lookup uid (keyUids kd)
2430 sig <- map (packet . fst) (fst x)
2431 o <- overs sig
2432 k <- keys
2433 let ov = verify (Message [k]) $ o
2434 signatures_over ov
2435 return (sig,Just ov,k)
2436 additional new_sig = do
2437 new_sig <- maybeToList new_sig
2438 guard (null $ selfsigs)
2439 signatures_over new_sig
2440 sigr <- pgpSign (Message [wkun]) sigOver SHA1 (fingerprint wkun)
2441 let f ::([SigAndTrust],OriginMap) -> ([SigAndTrust],OriginMap)
2442 f x = ( map ( (,Map.empty) . toMappedPacket om) (additional sigr) ++ fst x
2443 , om `Map.union` snd x )
2444 -- XXX: Shouldn't this signature generation show up in the KikiReport ?
2445 return $ KikiSuccess $ ( kd { keyUids = Map.adjust f uid (keyUids kd) }, report )
2446
2447 perform kd (SubKeyDeletion topk subk) = do
2448 try kd $ \(kd,report) -> do
2449 let kk = keykey $ packet $ keyMappedPacket kd
2450 kd' | kk /= topk = kd
2451 | otherwise = kd { keySubKeys = Map.filterWithKey pred $ keySubKeys kd }
2452 pred k _ = k /= subk
2453 ps = concat $ maybeToList $ do
2454 SubKey mp sigs <- Map.lookup subk (keySubKeys kd)
2455 return $ packet mp : concatMap (\(p,ts) -> packet p : Map.elems ts) sigs
2456 ctx = InputFileContext (rtSecring rt) (rtPubring rt)
2457 rings = [HomeSec, HomePub] >>= resolveInputFile ctx
2458 return $ KikiSuccess (kd' , report ++ [ (f,DeletedPacket $ showPacket p) | f <- rings, p <- ps ])
2459
2460initializeMissingPEMFiles ::
2461 KeyRingOperation
2462 -> InputFileContext
2463 -> Maybe String
2464 -> Maybe MappedPacket
2465 -> (MappedPacket -> IO (KikiCondition Packet))
2466 -> KeyDB
2467 -> IO (KikiCondition ( (KeyDB,[( FilePath
2468 , Maybe String
2469 , [MappedPacket]
2470 , StreamInfo )])
2471 , [(FilePath,KikiReportAction)]))
2472initializeMissingPEMFiles operation ctx grip mwk decrypt db = do
2473 nonexistents <-
2474 filterM (fmap not . doesFileExist . fst)
2475 $ do (f,t) <- Map.toList (opFiles operation)
2476 f <- resolveInputFile ctx f
2477 return (f,t)
2478
2479 let (missing,notmissing) = partition (\(_,_,ns,_)->null (ns >>= snd)) $ do
2480 (fname,stream) <- nonexistents
2481 let internalInitializer StreamInfo
2482 { initializer = Internal _
2483 , spill = KF_Match tag } = Just tag
2484 internalInitializer _ = Nothing
2485 mutableTag
2486 | isMutable stream = usageFromFilter (fill stream)
2487 | otherwise = Nothing
2488 usage <- maybeToList $ internalInitializer stream `mplus` mutableTag
2489 -- TODO: Report error if generating without specifying usage tag.
2490 let (topspec,subspec) = parseSpec (fromMaybe "" grip) usage
2491 -- ms will contain duplicates if a top key has multiple matching
2492 -- subkeys. This is intentional.
2493 -- ms = map (keykey . fst) $ selectAll True (topspec,subspec) db
2494 -- ms = filterMatches topspec $ Map.toList db
2495 ns = do
2496 (kk,kd) <- filterMatches topspec $ Map.toList db
2497 return (kk , subkeysForExport subspec kd)
2498 return (fname,subspec,ns,stream)
2499 (exports0,ambiguous) = partition (\(_,_,ns,_)->null $ drop 1 $ (ns>>=snd))
2500 notmissing
2501 exports = map (\(f,subspec,ns,stream) -> (f,subspec,ns >>= snd,stream)) exports0
2502
2503 ambiguity (f,topspec,subspec,_) = do
2504 return $ AmbiguousKeySpec f
2505
2506 ifnotnull (x:xs) f g = f x
2507 ifnotnull _ f g = g
2508
2509 ifnotnull ambiguous ambiguity $ do
2510
2511 -- create nonexistent files via external commands
2512 do
2513 let cmds = mapMaybe getcmd missing
2514 where
2515 getcmd (fname,subspec,ms,stream) = do
2516 cmd <- case initializer stream of
2517 External str -> Just str
2518 _ -> Nothing
2519 return (fname,subspec,ms,stream,cmd)
2520 rs <- forM cmds $ \tup@(fname,subspec,ms,stream,cmd) -> do
2521 e <- systemEnv [ ("file",fname)
2522 , ("usage",fromMaybe "" subspec) ]
2523 cmd
2524 case e of
2525 ExitFailure num -> return (tup,FailedExternal num)
2526 ExitSuccess -> return (tup,ExternallyGeneratedFile)
2527
2528 v <- foldM (importSecretKey decrypt)
2529 (KikiSuccess (db,[])) $ do
2530 ((f,subspec,ms,stream,cmd),r) <- rs
2531 guard $ case r of
2532 ExternallyGeneratedFile -> True
2533 _ -> False
2534 return (f,subspec,map fst ms,stream,cmd)
2535
2536 try v $ \(db,import_rs) -> do
2537
2538 -- generateInternals
2539 let internals = mapMaybe getParams missing
2540 where
2541 getParams (fname,subspec,ms,stream) =
2542 case initializer stream of
2543 Internal p -> Just (p, stream)
2544 _ -> Nothing
2545 v <- generateInternals decrypt mwk db internals
2546
2547 try v $ \(db,internals_rs) -> do
2548
2549 return $ KikiSuccess ((db,exports), map (\((f,_,_,_,_),r)->(f,r)) rs
2550 ++ import_rs ++ internals_rs)
2551{-
2552interpretManip :: KeyData -> KeyRingAddress PacketUpdate -> IO KeyData
2553interpretManip kd (KeyRingAddress kk sk (InducerSignature ps)) = error "todo"
2554interpretManip kd manip = return kd
2555-}
2556
2557combineTransforms :: [Transform] -> KeyRingRuntime -> KeyData -> [PacketUpdate]
2558combineTransforms trans rt kd = updates
2559 where
2560 updates = -- kManip operation rt kd ++
2561 concatMap (\t -> resolveTransform t rt kd) sanitized
2562 sanitized = group (sort trans) >>= take 1
2563
2564isSubkeySignature (SubkeySignature {}) = True
2565isSubkeySignature _ = False
2566
2567-- Returned data is simmilar to getBindings but the Word8 codes
2568-- are ORed together.
2569accBindings ::
2570 Bits t =>
2571 [(t, (Packet, Packet), [a], [a1], [a2])]
2572 -> [(t, (Packet, Packet), [a], [a1], [a2])]
2573accBindings bs = as
2574 where
2575 gs = groupBy samePair . sortBy (comparing bindingPair) $ bs
2576 as = map (foldl1 combine) gs
2577 bindingPair (_,p,_,_,_) = pub2 p
2578 where
2579 pub2 (a,b) = (pub a, pub b)
2580 pub a = fingerprint_material a
2581 samePair a b = bindingPair a == bindingPair b
2582 combine (ac,p,akind,ahashed,aclaimaints)
2583 (bc,_,bkind,bhashed,bclaimaints)
2584 = (ac .|. bc,p,akind++bkind,ahashed++bhashed,aclaimaints++bclaimaints)
2585
2586
2587
2588verifyBindings keys nonkeys = (top ++ filter isSubkeySignature embedded,othersigs)
2589 where
2590 verified = do
2591 sig <- signatures (Message nonkeys)
2592 let v = verify (Message keys) sig
2593 guard (not . null $ signatures_over v)
2594 return v
2595 (top,othersigs) = partition isSubkeySignature verified
2596 embedded = do
2597 sub <- top
2598 let sigover = signatures_over sub
2599 unhashed = sigover >>= unhashed_subpackets
2600 subsigs = mapMaybe backsig unhashed
2601 -- This should consist only of 0x19 values
2602 -- subtypes = map signature_type subsigs
2603 -- trace ("subtypes = "++show subtypes) (return ())
2604 -- trace ("issuers: "++show (map signature_issuer subsigs)) (return ())
2605 sig <- signatures (Message ([topkey sub,subkey sub]++subsigs))
2606 let v = verify (Message [subkey sub]) sig
2607 guard (not . null $ signatures_over v)
2608 return v
2609
2610smallpr k = drop 24 $ fingerprint k
2611
2612disjoint_fp ks = {- concatMap group2 $ -} transpose grouped
2613 where
2614 grouped = groupBy samepr . sortBy (comparing smallpr) $ ks
2615 samepr a b = smallpr a == smallpr b
2616
2617 {-
2618 -- useful for testing
2619 group2 :: [a] -> [[a]]
2620 group2 (x:y:ys) = [x,y]:group2 ys
2621 group2 [x] = [[x]]
2622 group2 [] = []
2623 -}
2624
2625
2626getBindings ::
2627 [Packet]
2628 ->
2629 ( [([Packet],[SignatureOver])] -- other signatures with key sets
2630 -- that were used for the verifications
2631 , [(Word8,
2632 (Packet, Packet), -- (topkey,subkey)
2633 [String], -- usage flags
2634 [SignatureSubpacket], -- hashed data
2635 [Packet])] -- binding signatures
2636 )
2637getBindings pkts = (sigs,bindings)
2638 where
2639 (sigs,concat->bindings) = unzip $ do
2640 let (keys,_) = partition isKey pkts
2641 keys <- disjoint_fp keys
2642 let (bs,sigs) = verifyBindings keys pkts
2643 return . ((keys,sigs),) $ do
2644 b <- bs -- trace ("sigs = "++show (map (map signature_issuer . signatures_over) sigs)) bs
2645 i <- map signature_issuer (signatures_over b)
2646 i <- maybeToList i
2647 who <- maybeToList $ find_key fingerprint (Message keys) i
2648 let (code,claimants) =
2649 case () of
2650 _ | who == topkey b -> (1,[])
2651 _ | who == subkey b -> (2,[])
2652 _ -> (0,[who])
2653 let hashed = signatures_over b >>= hashed_subpackets
2654 kind = guard (code==1) >> hashed >>= maybeToList . usage
2655 return (code,(topkey b,subkey b), kind, hashed,claimants)
2656
2657resolveTransform :: Transform -> KeyRingRuntime -> KeyData -> [PacketUpdate]
2658resolveTransform Autosign rt kd@(KeyData k ksigs umap submap) = ops
2659 where
2660 ops = map (\u -> InducerSignature u []) us
2661 us = filter torStyle $ Map.keys umap
2662 torStyle str = and [ uid_topdomain parsed == "onion"
2663 , uid_realname parsed `elem` ["","Anonymous"]
2664 , uid_user parsed == "root"
2665 , fmap (match . fst) (lookup (packet k) torbindings)
2666 == Just True ]
2667 where parsed = parseUID str
2668 match = (==subdom) . take (fromIntegral len)
2669 subdom0 = L.fromChunks [encodeUtf8 (uid_subdomain parsed)]
2670 subdom = Char8.unpack subdom0
2671 len = T.length (uid_subdomain parsed)
2672 torbindings = getTorKeys (map packet $ flattenTop "" True kd)
2673 getTorKeys pub = do
2674 xs <- groupBindings pub
2675 (_,(top,sub),us,_,_) <- xs
2676 guard ("tor" `elem` us)
2677 let torhash = fromMaybe "" $ derToBase32 <$> derRSA sub
2678 return (top,(torhash,sub))
2679
2680 groupBindings pub = gs
2681 where (_,bindings) = getBindings pub
2682 bindings' = accBindings bindings
2683 code (c,(m,s),_,_,_) = (fingerprint_material m,-c)
2684 ownerkey (_,(a,_),_,_,_) = a
2685 sameMaster (ownerkey->a) (ownerkey->b)
2686 = fingerprint_material a==fingerprint_material b
2687 gs = groupBy sameMaster (sortBy (comparing code) bindings')
2688
2689
2690resolveTransform (DeleteSubKey fp) rt kd@(KeyData k ksigs umap submap) = fmap (SubKeyDeletion topk) subk
2691 where
2692 topk = keykey $ packet k -- key to master of key to be deleted
2693 subk = do
2694 (k,sub) <- Map.toList submap
2695 guard (map toUpper fp == fingerprint (packet (subkeyMappedPacket sub)))
2696 return k
2697
2698
2699-- | Load and update key files according to the specified 'KeyRingOperation'.
2700runKeyRing :: KeyRingOperation -> IO (KikiResult KeyRingRuntime)
2701runKeyRing operation = do
2702 homedir <- getHomeDir (opHome operation)
2703 let try' :: KikiCondition a -> (a -> IO (KikiResult b)) -> IO (KikiResult b)
2704 -- FIXME: try' should probably accept a list of KikiReportActions.
2705 -- This would be useful for reporting on disk writes that have already
2706 -- succeded prior to this termination.
2707 try' v body =
2708 case functorToEither v of
2709 Left e -> return $ KikiResult e []
2710 Right wkun -> body wkun
2711 try' homedir $ \(homedir,secring,pubring,grip0) -> do
2712 let ctx = InputFileContext secring pubring
2713 tolocks = filesToLock operation ctx
2714 secring <- return Nothing
2715 pubring <- return Nothing
2716 lks <- forM tolocks $ \f -> do
2717 lk <- dotlock_create f 0
2718 v <- flip (maybe $ return Nothing) lk $ \lk -> do
2719 e <- dotlock_take lk (-1)
2720 if e==0 then return $ Just lk
2721 else dotlock_destroy lk >> return Nothing
2722 return (v,f)
2723 let (lked, map snd -> failed_locks) = partition (isJust . fst) lks
2724 ret <-
2725 if not $ null failed_locks
2726 then return $ KikiResult (FailedToLock failed_locks) []
2727 else do
2728
2729 -- merge all keyrings, PEM files, and wallets
2730 bresult <- buildKeyDB ctx grip0 operation
2731 try' bresult $ \((db,grip,wk,hs,accs,decrypt,unspilled),report_imports) -> do
2732
2733 externals_ret <- initializeMissingPEMFiles operation
2734 ctx
2735 grip
2736 wk
2737 decrypt
2738 db
2739 try' externals_ret $ \((db,exports),report_externals) -> do
2740
2741 let rt = KeyRingRuntime
2742 { rtPubring = homepubPath ctx
2743 , rtSecring = homesecPath ctx
2744 , rtGrip = grip
2745 , rtWorkingKey = fmap packet wk
2746 , rtKeyDB = db
2747 , rtRingAccess = accs
2748 , rtPassphrases = decrypt
2749 }
2750
2751 r <- performManipulations decrypt
2752 rt
2753 wk
2754 (combineTransforms $ opTransforms operation)
2755 try' r $ \(rt,report_manips) -> do
2756
2757 r <- writeWalletKeys operation (rtKeyDB rt) (fmap packet wk)
2758 try' r $ \report_wallets -> do
2759
2760 r <- writeRingKeys operation rt unspilled report_manips
2761 try' r $ \report_rings -> do
2762
2763 r <- writePEMKeys decrypt (rtKeyDB rt) exports
2764 try' r $ \report_pems -> do
2765
2766 import_hosts <- writeHostsFiles operation ctx hs
2767
2768 return $ KikiResult (KikiSuccess rt)
2769 $ concat [ report_imports
2770 , report_externals
2771 , report_manips
2772 , report_wallets
2773 , report_rings
2774 , report_pems ]
2775
2776 forM_ lked $ \(Just lk, fname) -> dotlock_release lk
2777
2778 return ret
2779
2780parseOptionFile :: FilePath -> IO [String]
2781parseOptionFile fname = do
2782 xs <- fmap lines (readFile fname)
2783 let ys = filter notComment xs
2784 notComment ('#':_) = False
2785 notComment cs = not (all isSpace cs)
2786 return ys
2787
2788-- | returns ( home directory
2789-- , path to secret ring
2790-- , path to public ring
2791-- , fingerprint of working key
2792-- )
2793getHomeDir :: Maybe FilePath -> IO (KikiCondition (FilePath,FilePath,FilePath,Maybe String))
2794getHomeDir protohome = do
2795 homedir <- envhomedir protohome
2796 flip (maybe (return CantFindHome))
2797 homedir $ \homedir -> do
2798 -- putStrLn $ "homedir = " ++show homedir
2799 let secring = homedir ++ "/" ++ "secring.gpg"
2800 pubring = homedir ++ "/" ++ "pubring.gpg"
2801 -- putStrLn $ "secring = " ++ show secring
2802 workingkey <- getWorkingKey homedir
2803 return $ KikiSuccess (homedir,secring,pubring,workingkey)
2804 where
2805 envhomedir opt = do
2806 gnupghome <- fmap (mfilter (/="")) $ lookupEnv (homevar home)
2807 homed <- fmap (mfilter (/="") . Just) getHomeDirectory
2808 let homegnupg = (++('/':(appdir home))) <$> homed
2809 let val = (opt `mplus` gnupghome `mplus` homegnupg)
2810 return $ val
2811
2812 -- TODO: rename this to getGrip
2813 getWorkingKey homedir = do
2814 let o = Nothing
2815 h = Just homedir
2816 ofile <- fmap listToMaybe . flip (maybe (return [])) h $ \h ->
2817 let optfiles = map (second ((h++"/")++))
2818 (maybe optfile_alts' (:[]) o')
2819 optfile_alts' = zip (False:repeat True) (optfile_alts home)
2820 o' = fmap (False,) o
2821 in filterM (doesFileExist . snd) optfiles
2822 args <- flip (maybe $ return []) ofile $
2823 \(forgive,fname) -> parseOptionFile fname
2824 let config = map (topair . words) args
2825 where topair (x:xs) = (x,xs)
2826 return $ lookup "default-key" config >>= listToMaybe
2827
2828#if MIN_VERSION_base(4,6,0)
2829#else
2830lookupEnv :: String -> IO (Maybe String)
2831lookupEnv var =
2832 handleIO_ (return Nothing) $ fmap Just (getEnv var)
2833#endif
2834
2835isKey :: Packet -> Bool
2836isKey (PublicKeyPacket {}) = True
2837isKey (SecretKeyPacket {}) = True
2838isKey _ = False
2839
2840isUserID :: Packet -> Bool
2841isUserID (UserIDPacket {}) = True
2842isUserID _ = False
2843
2844isTrust :: Packet -> Bool
2845isTrust (TrustPacket {}) = True
2846isTrust _ = False
2847
2848sigpackets ::
2849 Monad m =>
2850 Word8 -> [SignatureSubpacket] -> [SignatureSubpacket] -> m Packet
2851sigpackets typ hashed unhashed = return $
2852 signaturePacket
2853 4 -- version
2854 typ -- 0x18 subkey binding sig, or 0x19 back-signature
2855 RSA
2856 SHA1
2857 hashed
2858 unhashed
2859 0 -- Word16 -- Left 16 bits of the signed hash value
2860 [] -- [MPI]
2861
2862secretToPublic :: Packet -> Packet
2863secretToPublic pkt@(SecretKeyPacket {}) =
2864 PublicKeyPacket { version = version pkt
2865 , timestamp = timestamp pkt
2866 , key_algorithm = key_algorithm pkt
2867 -- , ecc_curve = ecc_curve pkt
2868 , key = let seckey = key pkt
2869 pubs = public_key_fields (key_algorithm pkt)
2870 in filter (\(k,v) -> k `elem` pubs) seckey
2871 , is_subkey = is_subkey pkt
2872 , v3_days_of_validity = Nothing
2873 }
2874secretToPublic pkt = pkt
2875
2876
2877
2878slurpWIPKeys :: Posix.EpochTime -> L.ByteString -> ( [(Word8,Packet)], [L.ByteString])
2879slurpWIPKeys stamp "" = ([],[])
2880slurpWIPKeys stamp cs =
2881 let (b58,xs) = Char8.span (`elem` base58chars) cs
2882 mb = decode_btc_key stamp (Char8.unpack b58)
2883 in if L.null b58
2884 then let (ys,xs') = Char8.break (`elem` base58chars) cs
2885 (ks,js) = slurpWIPKeys stamp xs'
2886 in (ks,ys:js)
2887 else let (ks,js) = slurpWIPKeys stamp xs
2888 in maybe (ks,b58:js) (\(net,Message [k])->((net,k):ks,js)) mb
2889
2890
2891decode_btc_key ::
2892 Enum timestamp => timestamp -> String -> Maybe (Word8, Message)
2893decode_btc_key timestamp str = do
2894 (network_id,us) <- base58_decode str
2895 return . (network_id,) $ Message $ do
2896 let d = foldl' (\a b->a*256+b) 0 (map fromIntegral us :: [Integer])
2897 {-
2898 xy = secp256k1_G `pmul` d
2899 x = getx xy
2900 y = gety xy
2901 -- y² = x³ + 7 (mod p)
2902 y' = sqrtModP' (applyCurve secp256k1_curve x) (getp secp256k1_curve)
2903 y'' = sqrtModPList (applyCurve secp256k1_curve x) (getp secp256k1_curve)
2904 -}
2905 secp256k1 = ECC.getCurveByName ECC.SEC_p256k1
2906 ECC.Point x y = ECC.ecc_g $ ECC.common_curve secp256k1
2907 -- pub = cannonical_eckey x y
2908 -- hash = S.cons network_id . RIPEMD160.hash . SHA256.hash . S.pack $ pub
2909 -- address = base58_encode hash
2910 -- pubstr = concatMap (printf "%02x") $ pub
2911 -- _ = pubstr :: String
2912 return $ {- trace (unlines ["pub="++show pubstr
2913 ,"add="++show address
2914 ,"y ="++show y
2915 ,"y' ="++show y'
2916 ,"y''="++show y'']) -}
2917 SecretKeyPacket
2918 { version = 4
2919 , timestamp = toEnum (fromEnum timestamp)
2920 , key_algorithm = ECDSA
2921 , key = [ -- public fields...
2922 ('c',MPI secp256k1_id) -- secp256k1 (bitcoin curve)
2923 ,('l',MPI 256)
2924 ,('x',MPI x)
2925 ,('y',MPI y)
2926 -- secret fields
2927 ,('d',MPI d)
2928 ]
2929 , s2k_useage = 0
2930 , s2k = S2K 100 ""
2931 , symmetric_algorithm = Unencrypted
2932 , encrypted_data = ""
2933 , is_subkey = True
2934 }
2935
2936rsaKeyFromPacket :: Packet -> Maybe RSAPublicKey
2937rsaKeyFromPacket p | isKey p = do
2938 n <- lookup 'n' $ key p
2939 e <- lookup 'e' $ key p
2940 return $ RSAKey n e
2941
2942rsaKeyFromPacket _ = Nothing
2943
2944
2945readPacketsFromWallet ::
2946 Maybe Packet
2947 -> InputFile
2948 -> IO [(Packet,Packet,(Packet,Map.Map FilePath Packet))]
2949readPacketsFromWallet wk fname = do
2950 let ctx = InputFileContext "" ""
2951 timestamp <- getInputFileTime ctx fname
2952 input <- readInputFileL ctx fname
2953 let (ks,_) = slurpWIPKeys timestamp input
2954 unless (null ks) $ do
2955 -- decrypt wk
2956 -- create sigs
2957 -- return key/sig pairs
2958 return ()
2959 return $ do
2960 wk <- maybeToList wk
2961 guard (not $ null ks)
2962 let prep (tagbyte,k) = (wk,k,(k,Map.singleton tag wk))
2963 where tag = CryptoCoins.nameFromSecretByte tagbyte
2964 (wk,MarkerPacket,(MarkerPacket,Map.empty))
2965 :map prep ks
2966
2967readPacketsFromFile :: InputFileContext -> InputFile -> IO Message
2968readPacketsFromFile ctx fname = do
2969 -- warn $ fname ++ ": reading..."
2970 input <- readInputFileL ctx fname
2971#if MIN_VERSION_binary(0,7,0)
2972 return $
2973 case decodeOrFail input of
2974 Right (_,_,msg ) -> msg
2975 Left (_,_,_) ->
2976 -- FIXME
2977 -- trace (fname++": read fail") $
2978 Message []
2979#else
2980 return $ decode input
2981#endif
2982
2983-- | Get the time stamp of a signature.
2984--
2985-- Warning: This function checks unhashed_subpackets if no timestamp occurs in
2986-- the hashed section. TODO: change this?
2987--
2988signature_time :: SignatureOver -> Word32
2989signature_time ov = case (if null cs then ds else cs) of
2990 [] -> minBound
2991 xs -> maximum xs
2992 where
2993 ps = signatures_over ov
2994 ss = filter isSignaturePacket ps
2995 cs = concatMap (concatMap creationTime . hashed_subpackets) ss
2996 ds = concatMap (concatMap creationTime . unhashed_subpackets) ss
2997 creationTime (SignatureCreationTimePacket t) = [t]
2998 creationTime _ = []
2999
3000splitAtMinBy :: (t -> t -> Ordering) -> [t] -> ([t], [t])
3001splitAtMinBy comp xs = minimumBy comp' xxs
3002 where
3003 xxs = zip (inits xs) (tails xs)
3004 comp' (_,as) (_,bs) = compM (listToMaybe as) (listToMaybe bs)
3005 compM (Just a) (Just b) = comp a b
3006 compM Nothing mb = GT
3007 compM _ _ = LT
3008
3009
3010
3011-- | Given list of subpackets, a master key, one of its subkeys and a
3012-- list of signatures on that subkey, yields:
3013--
3014-- * preceding list of signatures
3015--
3016-- * The most recent valid signature made by the master key along with a
3017-- flag that indicates whether or not all of the supplied subpackets occur in
3018-- it or, if no valid signature from the working key is present, Nothing.
3019--
3020-- * following list of signatures
3021--
3022findTag ::
3023 [SignatureSubpacket]
3024 -> Packet
3025 -> Packet
3026 -> [(MappedPacket, b)]
3027 -> ([(MappedPacket, b)],
3028 Maybe (Bool, (MappedPacket, b)),
3029 [(MappedPacket, b)])
3030findTag tag topk subkey subsigs = (xs',minsig,ys')
3031 where
3032 vs = map (\sig ->
3033 (sig, do
3034 sig <- Just (packet . fst $ sig)
3035 guard (isSignaturePacket sig)
3036 guard $ flip isSuffixOf
3037 (fingerprint topk)
3038 . fromMaybe "%bad%"
3039 . signature_issuer
3040 $ sig
3041 listToMaybe $
3042 map (signature_time . verify (Message [topk]))
3043 (signatures $ Message [topk,subkey,sig])))
3044 subsigs
3045 (xs,ys) = splitAtMinBy (comparing (Down . snd)) vs
3046 xs' = map fst xs
3047 ys' = map fst $ if isNothing minsig then ys else drop 1 ys
3048 minsig = do
3049 (sig,ov) <- listToMaybe ys
3050 ov
3051 let hshed = hashed_subpackets $ packet $ fst sig
3052 return ( null $ tag \\ hshed, sig)
3053
3054mkUsage :: String -> SignatureSubpacket
3055mkUsage tag = NotationDataPacket
3056 { human_readable = True
3057 , notation_name = "usage@"
3058 , notation_value = tag
3059 }
3060
3061makeSig ::
3062 (MappedPacket -> IO (KikiCondition Packet))
3063 -> MappedPacket
3064 -> [Char]
3065 -> MappedPacket
3066 -> [SignatureSubpacket]
3067 -> Maybe (MappedPacket, Map.Map k a)
3068 -> IO (KikiCondition ((MappedPacket, Map.Map k a), [KikiReportAction]))
3069makeSig doDecrypt top fname subkey_p tags mbsig = do
3070 let wk = packet top
3071 wkun <- doDecrypt top
3072 try wkun $ \wkun -> do
3073 let grip = fingerprint wk
3074 addOrigin new_sig =
3075 flip (maybe $ return FailedToMakeSignature)
3076 (new_sig >>= listToMaybe . signatures_over)
3077 $ \new_sig -> do
3078 let mp' = mappedPacket fname new_sig
3079 return $ KikiSuccess (mp', Map.empty)
3080 parsedkey = [packet subkey_p]
3081 hashed0 = KeyFlagsPacket
3082 { certify_keys = False
3083 , sign_data = False
3084 , encrypt_communication = False
3085 , encrypt_storage = False
3086 , split_key = False
3087 , authentication = True
3088 , group_key = False }
3089 : tags
3090 -- implicitly added:
3091 -- , SignatureCreationTimePacket (fromIntegral timestamp)
3092 subgrip = fingerprint (head parsedkey)
3093
3094 back_sig <- pgpSign (Message parsedkey)
3095 (SubkeySignature wk
3096 (head parsedkey)
3097 (sigpackets 0x19
3098 hashed0
3099 [IssuerPacket subgrip]))
3100 (if key_algorithm (head parsedkey)==ECDSA
3101 then SHA256
3102 else SHA1)
3103 subgrip
3104 let iss = IssuerPacket (fingerprint wk)
3105 cons_iss back_sig = iss : map EmbeddedSignaturePacket (signatures_over back_sig)
3106 unhashed0 = maybe [iss] cons_iss back_sig
3107
3108 new_sig <- pgpSign (Message [wkun])
3109 (SubkeySignature wk
3110 (head parsedkey)
3111 (sigpackets 0x18
3112 hashed0
3113 unhashed0))
3114 SHA1
3115 grip
3116 let newSig = do
3117 r <- addOrigin new_sig
3118 return $ fmap (,[]) r
3119 flip (maybe newSig) mbsig $ \(mp,trustmap) -> do
3120 let sig = packet mp
3121 isCreation (SignatureCreationTimePacket {}) = True
3122 isCreation _ = False
3123 isExpiration (SignatureExpirationTimePacket {}) = True
3124 isExpiration _ = False
3125 (cs,ps) = partition isCreation (hashed_subpackets sig)
3126 (es,qs) = partition isExpiration ps
3127 stamp = listToMaybe . sortBy (comparing Down) $
3128 map unwrap cs where unwrap (SignatureCreationTimePacket x) = x
3129 exp = listToMaybe $ sort $
3130 map unwrap es where unwrap (SignatureExpirationTimePacket x) = x
3131 expires = liftA2 (+) stamp exp
3132 timestamp <- now
3133 if fmap ( (< timestamp) . fromIntegral) expires == Just True then
3134 return $ KikiSuccess ((mp,trustmap), [ UnableToUpdateExpiredSignature ] )
3135 else do
3136 let times = (:) (SignatureExpirationTimePacket (fromIntegral timestamp))
3137 $ maybeToList $ do
3138 e <- expires
3139 return $ SignatureExpirationTimePacket (e - fromIntegral timestamp)
3140 sig' = sig { hashed_subpackets = times ++ (qs `union` tags) }
3141 new_sig <- pgpSign (Message [wkun])
3142 (SubkeySignature wk
3143 (packet subkey_p)
3144 [sig'] )
3145 SHA1
3146 (fingerprint wk)
3147 newsig <- addOrigin new_sig
3148 return $ fmap (,[]) newsig
3149
3150
3151
3152data OriginFlags = OriginFlags {
3153 originallyPublic :: Bool,
3154 originalNum :: Int
3155 }
3156 deriving Show
3157type OriginMap = Map.Map FilePath OriginFlags
3158data MappedPacket = MappedPacket
3159 { packet :: Packet
3160 , locations :: OriginMap
3161 } deriving Show
3162
3163type TrustMap = Map.Map FilePath Packet
3164type SigAndTrust = ( MappedPacket
3165 , TrustMap ) -- trust packets
3166
3167type KeyKey = [ByteString]
3168data SubKey = SubKey MappedPacket [SigAndTrust] deriving Show
3169
3170-- | This is a GPG Identity which includes a master key and all its UIDs and
3171-- subkeys and associated signatures.
3172data KeyData = KeyData { keyMappedPacket :: MappedPacket -- main key
3173 , keySigAndTrusts :: [SigAndTrust] -- sigs on main key
3174 , keyUids :: (Map.Map String ([SigAndTrust],OriginMap)) -- uids
3175 , keySubKeys :: (Map.Map KeyKey SubKey) -- subkeys
3176 } deriving Show
3177
3178type KeyDB = Map.Map KeyKey KeyData
3179
3180origin :: Packet -> Int -> OriginFlags
3181origin p n = OriginFlags ispub n
3182 where
3183 ispub = case p of
3184 SecretKeyPacket {} -> False
3185 _ -> True
3186
3187mappedPacket :: FilePath -> Packet -> MappedPacket
3188mappedPacket filename p = MappedPacket
3189 { packet = p
3190 , locations = Map.singleton filename (origin p (-1))
3191 }
3192
3193mappedPacketWithHint :: FilePath -> Packet -> Int -> MappedPacket
3194mappedPacketWithHint filename p hint = MappedPacket
3195 { packet = p
3196 , locations = Map.singleton filename (origin p hint)
3197 }
3198
3199keykey :: Packet -> KeyKey
3200keykey key =
3201 -- Note: The key's timestamp is normally included in it's fingerprint.
3202 -- This is undesirable for kiki because it causes the same
3203 -- key to be imported multiple times and show as apparently
3204 -- distinct keys with different fingerprints.
3205 -- Thus, we will remove the timestamp.
3206 fingerprint_material (key {timestamp=0}) -- TODO: smaller key?
3207
3208uidkey :: Packet -> String
3209uidkey (UserIDPacket str) = str
3210
3211merge :: KeyDB -> InputFile -> Message -> KeyDB
3212merge db inputfile (Message ps) = merge_ db filename qs
3213 where
3214 filename = resolveForReport Nothing inputfile
3215
3216 qs = scanPackets filename ps
3217
3218 scanPackets :: FilePath -> [Packet] -> [(Packet,Packet,(Packet,Map.Map FilePath Packet))]
3219 scanPackets filename [] = []
3220 scanPackets filename (p:ps) = scanl doit (doit (MarkerPacket,MarkerPacket,ret MarkerPacket) p) ps
3221 where
3222 ret p = (p,Map.empty)
3223 doit (top,sub,prev) p =
3224 case p of
3225 _ | isKey p && not (is_subkey p) -> (p,MarkerPacket,ret p)
3226 _ | isKey p && is_subkey p -> (top,p,ret p)
3227 _ | isUserID p -> (top,p,ret p)
3228 _ | isTrust p -> (top,sub,updateTrust top sub prev p)
3229 _ -> (top,sub,ret p)
3230
3231 updateTrust top (PublicKeyPacket {}) (pre,t) p = (pre,Map.insert filename p t) -- public
3232 updateTrust (PublicKeyPacket {}) _ (pre,t) p = (pre,Map.insert filename p t) -- public
3233 updateTrust _ _ (pre,t) p = (pre,Map.insert filename p t) -- secret
3234
3235
3236{-
3237onionName :: KeyData -> (SockAddr,L.ByteString)
3238onionName kd = (addr,name)
3239 where
3240 (addr,(name:_,_)) = getHostnames kd
3241-}
3242keyCompare :: String -> Packet -> Packet -> Ordering
3243keyCompare what (SecretKeyPacket {}) (PublicKeyPacket {}) = LT
3244keyCompare what (PublicKeyPacket {}) (SecretKeyPacket {}) = GT
3245keyCompare what a b | keykey a==keykey b = EQ
3246keyCompare what a b = error $ unlines ["Unable to merge "++what++":"
3247 , fingerprint a
3248 , PP.ppShow a
3249 , fingerprint b
3250 , PP.ppShow b
3251 ]
3252
3253mergeKeyPacket :: String -> MappedPacket -> MappedPacket -> MappedPacket
3254mergeKeyPacket what key p =
3255 key { packet = minimumBy (keyCompare what) [packet key,packet p]
3256 , locations = Map.union (locations key) (locations p)
3257 }
3258
3259
3260merge_ :: KeyDB -> FilePath -> [(Packet,Packet,(Packet,Map.Map FilePath Packet))]
3261 -> KeyDB
3262merge_ db filename qs = foldl mergeit db (zip [0..] qs)
3263 where
3264 asMapped n p = mappedPacketWithHint filename p n
3265 asSigAndTrust n (p,tm) = (asMapped n p,tm)
3266 emptyUids = Map.empty
3267 -- mergeit db (_,_,TrustPacket {}) = db -- Filter TrustPackets
3268 mergeit :: KeyDB -> (Int,(Packet,Packet,(Packet,Map.Map FilePath Packet))) -> KeyDB
3269 mergeit db (n,(top,sub,ptt@(p,trustmap))) | isKey top = Map.alter update (keykey top) db
3270 where
3271 -- NOTE:
3272 -- if a keyring file has both a public key packet and a secret key packet
3273 -- for the same key, then only one of them will survive, which ever is
3274 -- later in the file.
3275 --
3276 -- This is due to the use of statements like
3277 -- (Map.insert filename (origin p n) (locations key))
3278 --
3279 update :: Maybe KeyData -> Maybe KeyData
3280 update v | isKey p && not (is_subkey p)
3281 = case v of
3282 Nothing -> Just $ KeyData (asMapped n p) [] emptyUids Map.empty
3283 Just (KeyData key sigs uids subkeys) | keykey (packet key) == keykey p
3284 -> Just $ KeyData (mergeKeyPacket "master keys" key $ asMapped n p)
3285 sigs
3286 uids
3287 subkeys
3288 _ -> error . concat $ ["Unexpected master key merge error: "
3289 ,show (fingerprint top, fingerprint p)]
3290 update (Just (KeyData key sigs uids subkeys)) | isKey p && is_subkey p
3291 = Just $ KeyData key sigs uids (Map.alter (mergeSubkey n p) (keykey p) subkeys)
3292 update (Just (KeyData key sigs uids subkeys)) | isUserID p
3293 = Just $ KeyData key sigs (Map.alter (mergeUid n ptt) (uidkey p) uids)
3294 subkeys
3295 update (Just (KeyData key sigs uids subkeys))
3296 = case sub of
3297 MarkerPacket -> Just $ KeyData key (mergeSig n ptt sigs) uids subkeys
3298 UserIDPacket {} -> Just $ KeyData key
3299 sigs
3300 (Map.alter (mergeUidSig n ptt) (uidkey sub) uids)
3301 subkeys
3302 _ | isKey sub -> Just $ KeyData key
3303 sigs
3304 uids
3305 (Map.alter (mergeSubSig n ptt) (keykey sub) subkeys)
3306 _ -> error $ "Unexpected PGP packet 1: "++(words (show p) >>= take 1)
3307 update _ = error $ "Unexpected PGP packet 2: "++(words (show p) >>= take 1)
3308
3309 mergeit _ (_,(_,_,p)) = error $ "Unexpected PGP packet 3: "++whatP p
3310
3311 mergeSubkey :: Int -> Packet -> Maybe SubKey -> Maybe SubKey
3312 mergeSubkey n p Nothing = Just $ SubKey (asMapped n p) []
3313 mergeSubkey n p (Just (SubKey key sigs)) = Just $
3314 SubKey (mergeKeyPacket "subs" key $ asMapped n p)
3315 sigs
3316
3317 mergeUid :: Int ->(Packet,a) -> Maybe ([SigAndTrust],OriginMap) -> Maybe ([SigAndTrust],OriginMap)
3318 mergeUid n (UserIDPacket s,_) Nothing = Just ([],Map.singleton filename (origin MarkerPacket n))
3319 mergeUid n (UserIDPacket s,_) (Just (sigs,m)) = Just (sigs, Map.insert filename (origin MarkerPacket n) m)
3320 mergeUid n p _ = error $ "Unable to merge into UID record: " ++whatP p
3321
3322 whatP (a,_) = concat . take 1 . words . show $ a
3323
3324
3325 mergeSig :: Int -> (Packet,TrustMap) -> [SigAndTrust] -> [SigAndTrust]
3326 mergeSig n sig sigs =
3327 let (xs,ys) = break (isSameSig sig) sigs
3328 in if null ys
3329 then sigs++[first (asMapped n) sig]
3330 else let y:ys'=ys
3331 in xs ++ (mergeSameSig n sig y : ys')
3332 where
3333 isSameSig (a,_) (MappedPacket {packet=b},_) | isSignaturePacket a && isSignaturePacket b =
3334 a { unhashed_subpackets=[] } == b { unhashed_subpackets = [] }
3335 isSameSig (a,_) (MappedPacket {packet=b},_) = a==b
3336
3337 mergeSameSig :: Int -> (Packet,TrustMap) -> (MappedPacket,TrustMap) -> (MappedPacket, TrustMap)
3338 mergeSameSig n (a,ta) (m@(MappedPacket{packet=b,locations=locs}),tb)
3339 | isSignaturePacket a && isSignaturePacket b =
3340 ( m { packet = b { unhashed_subpackets =
3341 union (unhashed_subpackets b) (unhashed_subpackets a)
3342 }
3343 , locations = Map.insert filename (origin a n) locs }
3344 -- TODO: when merging items, we should delete invalidated origins
3345 -- from the orgin map.
3346 , tb `Map.union` ta )
3347
3348 mergeSameSig n a b = b -- trace ("discarding dup "++show a) b
3349
3350 mergeUidSig n sig (Just (sigs,m)) = Just (mergeSig n sig sigs, m)
3351 mergeUidSig n sig Nothing = Just ([asSigAndTrust n sig],Map.empty)
3352
3353 mergeSubSig n sig (Just (SubKey key sigs)) = Just $ SubKey key (mergeSig n sig sigs)
3354 mergeSubSig n sig Nothing = error $
3355 "Unable to merge subkey signature: "++(words (show sig) >>= take 1)
3356
3357unsig :: FilePath -> Bool -> SigAndTrust -> [MappedPacket]
3358unsig fname isPublic (sig,trustmap) =
3359 sig : map (asMapped (-1)) ( take 1 . Map.elems $ Map.filterWithKey f trustmap)
3360 where
3361 f n _ = n==fname -- && trace ("fname=n="++show n) True
3362 asMapped n p = let m = mappedPacket fname p
3363 in m { locations = fmap (\x->x {originalNum=n}) (locations m) }
3364
3365concatSort ::
3366 FilePath -> ([a] -> MappedPacket) -> (b -> [a]) -> [b] -> [a]
3367concatSort fname getp f = concat . sortByHint fname getp . map f
3368
3369sortByHint :: FilePath -> (a -> MappedPacket) -> [a] -> [a]
3370sortByHint fname f = sortBy (comparing gethint)
3371 where
3372 gethint = maybe defnum originalNum . Map.lookup fname . locations . f
3373 defnum = -1
3374
3375flattenKeys :: Bool -> KeyDB -> Message
3376flattenKeys isPublic db = Message $ concatMap (map packet . flattenTop "" isPublic . snd) (prefilter . Map.assocs $ db)
3377 where
3378 prefilter = if isPublic then id else filter isSecret
3379 where
3380 isSecret (_,(KeyData
3381 (MappedPacket { packet=(SecretKeyPacket {})})
3382 _
3383 _
3384 _)) = True
3385 isSecret _ = False
3386
3387
3388flattenTop :: FilePath -> Bool -> KeyData -> [MappedPacket]
3389flattenTop fname ispub (KeyData key sigs uids subkeys) =
3390 unk ispub key :
3391 ( flattenAllUids fname ispub uids
3392 ++ concatSort fname head (flattenSub fname ispub) (Map.elems subkeys))
3393
3394flattenSub :: FilePath -> Bool -> SubKey -> [MappedPacket]
3395flattenSub fname ispub (SubKey key sigs) = unk ispub key: concatSort fname head (unsig fname ispub) sigs
3396
3397unk :: Bool -> MappedPacket -> MappedPacket
3398unk isPublic = if isPublic then toPacket secretToPublic else id
3399 where toPacket f mp@(MappedPacket {packet=p}) = mp {packet=(f p)}
3400
3401flattenAllUids :: FilePath -> Bool -> Map.Map String ([SigAndTrust],OriginMap) -> [MappedPacket]
3402flattenAllUids fname ispub uids =
3403 concatSort fname head (flattenUid fname ispub) (Map.assocs uids)
3404
3405flattenUid :: FilePath -> Bool -> (String,([SigAndTrust],OriginMap)) -> [MappedPacket]
3406flattenUid fname ispub (str,(sigs,om)) =
3407 (mappedPacket "" $ UserIDPacket str) {locations=om} : concatSort fname head (unsig fname ispub) sigs
3408
3409getCrossSignedSubkeys :: Packet -> Map.Map KeyKey SubKey -> String -> [Packet]
3410getCrossSignedSubkeys topk subs tag = do
3411 SubKey k sigs <- Map.elems subs
3412 let subk = packet k
3413 let sigs' = do
3414 torsig <- filter (has_tag tag) $ map (packet . fst) sigs
3415 sig <- (signatures $ Message [topk,subk,torsig])
3416 let v = verify (Message [topk]) sig
3417 -- Require parent's signature
3418 guard (not . null $ signatures_over v)
3419 let unhashed = unhashed_subpackets torsig
3420 subsigs = mapMaybe backsig unhashed
3421 -- This should consist only of 0x19 values
3422 -- subtypes = map signature_type subsigs
3423 sig' <- signatures . Message $ [topk,subk]++subsigs
3424 let v' = verify (Message [subk]) sig'
3425 -- Require subkey's signature
3426 guard . not . null $ signatures_over v'
3427 return torsig
3428 guard (not $ null sigs')
3429 return subk
3430
3431has_tag tag p = isSignaturePacket p
3432 && or [ tag `elem` mapMaybe usage (hashed_subpackets p)
3433 , tag `elem` map usageString (mapMaybe keyflags (hashed_subpackets p)) ]
3434
3435
3436-- |
3437-- Returns (ip6 fingerprint address,(onion names,other host names))
3438--
3439-- Requires a validly cross-signed tor key for each onion name returned.
3440-- (Signature checks are performed.)
3441getHostnames :: KeyData -> (SockAddr, ([L.ByteString],[L.ByteString]))
3442getHostnames (KeyData topmp _ uids subs) = (addr,(onames,othernames))
3443 where
3444 othernames = do
3445 mp <- flattenAllUids "" True uids
3446 let p = packet mp
3447 guard $ isSignaturePacket p
3448 uh <- unhashed_subpackets p
3449 case uh of
3450 NotationDataPacket True "hostname@" v
3451 -> return $ Char8.pack v
3452 _ -> mzero
3453
3454 addr = fingerdress topk
3455 -- name = fromMaybe "" $ listToMaybe onames -- TODO: more than one tor key?
3456 topk = packet topmp
3457 torkeys = getCrossSignedSubkeys topk subs "tor"
3458
3459 -- subkeyPacket (SubKey k _ ) = k
3460 onames :: [L.ByteString]
3461 onames = map ( (<> ".onion")
3462 . Char8.pack
3463 . take 16
3464 . torhash )
3465 torkeys
3466
3467hasFingerDress :: KeyDB -> SockAddr -> Bool
3468hasFingerDress db addr | socketFamily addr/=AF_INET6 = False
3469hasFingerDress db addr = pre=="fd" && isJust (selectPublicKey (KeyGrip g',Nothing) db)
3470 where
3471 (pre,g) = splitAt 2 $ filter (/=':') $ Hosts.inet_ntop addr
3472 g' = map toUpper g
3473
3474-- We return into IO in case we want to make a signature here.
3475setHostnames :: (SockAddr -> Bool) -> Hosts.Hosts -> KeyData -> IO KeyData
3476setHostnames pred hosts kd@(KeyData topmp topsigs uids subs) =
3477 -- TODO: we are removing the origin from the UID OriginMap,
3478 -- when we should be removing origins from the locations
3479 -- field of the sig's MappedPacket records.
3480 -- Call getHostnames and compare to see if no-op.
3481 if not (pred addr) || names0 == names \\ onions
3482 then {- trace (unlines [ "setHostnames NO-OP: gpg: "++show (map Char8.unpack onions, map Char8.unpack names0)
3483 , " file: "++show (map Char8.unpack names)
3484 , " pred: "++show (pred addr)]) -}
3485 (return kd)
3486 else do
3487 -- We should be sure to remove origins so that the data is written
3488 -- (but only if something changed).
3489 -- Filter all hostnames present in uids
3490 -- Write notations into first uid
3491 {-
3492 trace (unlines [ "setHostnames ACTION: gpg: "++show (map Char8.unpack onions, map Char8.unpack names0)
3493 , " file: "++show (map Char8.unpack names) ]) $ do
3494 -}
3495 return $ KeyData topmp topsigs uids1 subs
3496 where
3497 topk = packet topmp
3498 addr = fingerdress topk
3499 names :: [Char8.ByteString]
3500 names = Hosts.namesForAddress addr hosts
3501 (_,(onions,names0)) = getHostnames kd
3502 notations = map (NotationDataPacket True "hostname@" . Char8.unpack) (names \\ onions)
3503 isName (NotationDataPacket True "hostname@" _) = True
3504 isName _ = False
3505 uids0 = fmap zapIfHasName uids
3506 fstuid = head $ do
3507 p <- map packet $ flattenAllUids "" True uids
3508 guard $ isUserID p
3509 return $ uidkey p
3510 uids1 = Map.adjust addnames fstuid uids0
3511 addnames (sigs,om) = (fmap f ss ++ ts, om ) -- XXX: removed om=Map.empty, preserve UserId origin
3512 where
3513 (ss,ts) = splitAt 1 sigs
3514 f (sig,tm) = if isSignaturePacket (packet sig) then (sig { packet = p', locations=Map.empty }, tm)
3515 else (sig, tm)
3516 where p' = (packet sig) { unhashed_subpackets=uh }
3517 uh = unhashed_subpackets (packet sig) ++ notations
3518 zapIfHasName (sigs,om) = if or bs then (sigs',om) -- XXX: removed om=Map.empty to preserve UserID origin
3519 else (sigs,om)
3520 where
3521 (bs, sigs') = unzip $ map unhash sigs
3522
3523 unhash (sig,tm) = ( not (null ns)
3524 , ( sig { packet = p', locations = Map.empty }
3525 , tm ) )
3526 where
3527 psig = packet sig
3528 p' = if isSignaturePacket psig then psig { unhashed_subpackets = ps }
3529 else psig
3530 uh = unhashed_subpackets psig
3531 (ns,ps) = partition isName uh
3532
3533fingerdress :: Packet -> SockAddr
3534fingerdress topk = fromMaybe zero $ Hosts.inet_pton addr_str
3535 where
3536 zero = SockAddrInet 0 0
3537 addr_str = colons $ "fd" ++ drop 10 (map toLower $ fingerprint topk)
3538 colons (a:b:c:d:xs@(_:_)) = [a,b,c,d,':'] ++ colons xs
3539 colons xs = xs
3540
3541backsig :: SignatureSubpacket -> Maybe Packet
3542backsig (EmbeddedSignaturePacket s) = Just s
3543backsig _ = Nothing
3544
3545socketFamily :: SockAddr -> Family
3546socketFamily (SockAddrInet _ _) = AF_INET
3547socketFamily (SockAddrInet6 {}) = AF_INET6
3548socketFamily (SockAddrUnix _) = AF_UNIX
3549
3550#if ! MIN_VERSION_unix(2,7,0)
3551setFdTimesHiRes :: Posix.Fd -> POSIXTime -> POSIXTime -> IO ()
3552setFdTimesHiRes (Posix.Fd fd) atime mtime =
3553 withArray [toCTimeSpec atime, toCTimeSpec mtime] $ \times ->
3554 throwErrnoIfMinus1_ "setFdTimesHiRes" (c_futimens fd times)
3555
3556data CTimeSpec = CTimeSpec Posix.EpochTime CLong
3557instance Storable CTimeSpec where
3558 sizeOf _ = (16)
3559 alignment _ = alignment (undefined :: CInt)
3560 poke p (CTimeSpec sec nsec) = do
3561 ((\hsc_ptr -> pokeByteOff hsc_ptr 0)) p sec
3562 ((\hsc_ptr -> pokeByteOff hsc_ptr 8)) p nsec
3563 peek p = do
3564 sec <- (\hsc_ptr -> peekByteOff hsc_ptr 0) p
3565 nsec <- (\hsc_ptr -> peekByteOff hsc_ptr 8) p
3566 return $ CTimeSpec sec nsec
3567
3568toCTimeSpec :: POSIXTime -> CTimeSpec
3569toCTimeSpec t = CTimeSpec (CTime sec) (truncate $ 10^(9::Int) * frac)
3570 where
3571 (sec, frac) = if (frac' < 0) then (sec' - 1, frac' + 1) else (sec', frac')
3572 (sec', frac') = properFraction $ toRational t
3573
3574foreign import ccall unsafe "futimens"
3575 c_futimens :: CInt -> Ptr CTimeSpec -> IO CInt
3576#endif
3577
3578onionNameForContact :: KeyKey -> KeyDB -> Maybe String
3579onionNameForContact kk db = do
3580 contact <- Map.lookup kk db
3581 case getHostnames contact of
3582 (_,(name:_,_)) -> Just $ Char8.unpack name
3583 _ -> Nothing
diff --git a/lib/Numeric/Interval.hs b/lib/Numeric/Interval.hs
new file mode 100644
index 0000000..df4bc33
--- /dev/null
+++ b/lib/Numeric/Interval.hs
@@ -0,0 +1,754 @@
1{-# LANGUAGE CPP #-}
2{-# LANGUAGE Rank2Types #-}
3{-# LANGUAGE DeriveDataTypeable #-}
4#if defined(__GLASGOW_HASKELL) && __GLASGOW_HASKELL__ >= 704
5{-# LANGUAGE DeriveGeneric #-}
6#endif
7-----------------------------------------------------------------------------
8-- |
9-- Module : Numeric.Interval
10-- Copyright : (c) Edward Kmett 2010-2013
11-- License : BSD3
12-- Maintainer : ekmett@gmail.com
13-- Stability : experimental
14-- Portability : DeriveDataTypeable
15-- Version : intervals-0.4.2 (minus distributive instance)
16--
17-- Interval arithmetic
18--
19-----------------------------------------------------------------------------
20
21module Numeric.Interval
22 ( Interval(..)
23 , (...)
24 , whole
25 , empty
26 , null
27 , singleton
28 , elem
29 , notElem
30 , inf
31 , sup
32 , singular
33 , width
34 , midpoint
35 , intersection
36 , hull
37 , bisection
38 , magnitude
39 , mignitude
40 , contains
41 , isSubsetOf
42 , certainly, (<!), (<=!), (==!), (>=!), (>!)
43 , possibly, (<?), (<=?), (==?), (>=?), (>?)
44 , clamp
45 , idouble
46 , ifloat
47 ) where
48
49import Control.Applicative hiding (empty)
50import Data.Data
51#ifdef VERSION_distributive
52import Data.Distributive
53#endif
54import Data.Foldable hiding (minimum, maximum, elem, notElem, null)
55import Data.Function (on)
56import Data.Monoid
57import Data.Traversable
58#if defined(__GLASGOW_HASKELL) && __GLASGOW_HASKELL__ >= 704
59import GHC.Generics
60#endif
61import Prelude hiding (null, elem, notElem)
62
63-- $setup
64
65data Interval a = I !a !a deriving
66 ( Data
67 , Typeable
68#if defined(__GLASGOW_HASKELL) && __GLASGOW_HASKELL__ >= 704
69 , Generic
70#if __GLASGOW_HASKELL__ >= 706
71 , Generic1
72#endif
73#endif
74 )
75
76instance Functor Interval where
77 fmap f (I a b) = I (f a) (f b)
78 {-# INLINE fmap #-}
79
80instance Foldable Interval where
81 foldMap f (I a b) = f a `mappend` f b
82 {-# INLINE foldMap #-}
83
84instance Traversable Interval where
85 traverse f (I a b) = I <$> f a <*> f b
86 {-# INLINE traverse #-}
87
88instance Applicative Interval where
89 pure a = I a a
90 {-# INLINE pure #-}
91 I f g <*> I a b = I (f a) (g b)
92 {-# INLINE (<*>) #-}
93
94instance Monad Interval where
95 return a = I a a
96 {-# INLINE return #-}
97 I a b >>= f = I a' b' where
98 I a' _ = f a
99 I _ b' = f b
100 {-# INLINE (>>=) #-}
101
102#ifdef VERSION_distributive
103instance Distributive Interval where
104 distribute f = fmap inf f ... fmap sup f
105 {-# INLINE distribute #-}
106#endif
107
108infix 3 ...
109
110negInfinity :: Fractional a => a
111negInfinity = (-1)/0
112{-# INLINE negInfinity #-}
113
114posInfinity :: Fractional a => a
115posInfinity = 1/0
116{-# INLINE posInfinity #-}
117
118nan :: Fractional a => a
119nan = 0/0
120
121fmod :: RealFrac a => a -> a -> a
122fmod a b = a - q*b where
123 q = realToFrac (truncate $ a / b :: Integer)
124{-# INLINE fmod #-}
125
126-- | The rule of thumb is you should only use this to construct using values
127-- that you took out of the interval. Otherwise, use I, to force rounding
128(...) :: a -> a -> Interval a
129(...) = I
130{-# INLINE (...) #-}
131
132-- | The whole real number line
133--
134-- >>> whole
135-- -Infinity ... Infinity
136whole :: Fractional a => Interval a
137whole = negInfinity ... posInfinity
138{-# INLINE whole #-}
139
140-- | An empty interval
141--
142-- >>> empty
143-- NaN ... NaN
144empty :: Fractional a => Interval a
145empty = nan ... nan
146{-# INLINE empty #-}
147
148-- | negation handles NaN properly
149--
150-- >>> null (1 ... 5)
151-- False
152--
153-- >>> null (1 ... 1)
154-- False
155--
156-- >>> null empty
157-- True
158null :: Ord a => Interval a -> Bool
159null x = not (inf x <= sup x)
160{-# INLINE null #-}
161
162-- | A singleton point
163--
164-- >>> singleton 1
165-- 1 ... 1
166singleton :: a -> Interval a
167singleton a = a ... a
168{-# INLINE singleton #-}
169
170-- | The infinumum (lower bound) of an interval
171--
172-- >>> inf (1 ... 20)
173-- 1
174inf :: Interval a -> a
175inf (I a _) = a
176{-# INLINE inf #-}
177
178-- | The supremum (upper bound) of an interval
179--
180-- >>> sup (1 ... 20)
181-- 20
182sup :: Interval a -> a
183sup (I _ b) = b
184{-# INLINE sup #-}
185
186-- | Is the interval a singleton point?
187-- N.B. This is fairly fragile and likely will not hold after
188-- even a few operations that only involve singletons
189--
190-- >>> singular (singleton 1)
191-- True
192--
193-- >>> singular (1.0 ... 20.0)
194-- False
195singular :: Ord a => Interval a -> Bool
196singular x = not (null x) && inf x == sup x
197{-# INLINE singular #-}
198
199instance Eq a => Eq (Interval a) where
200 (==) = (==!)
201 {-# INLINE (==) #-}
202
203instance Show a => Show (Interval a) where
204 showsPrec n (I a b) =
205 showParen (n > 3) $
206 showsPrec 3 a .
207 showString " ... " .
208 showsPrec 3 b
209
210-- | Calculate the width of an interval.
211--
212-- >>> width (1 ... 20)
213-- 19
214--
215-- >>> width (singleton 1)
216-- 0
217--
218-- >>> width empty
219-- NaN
220width :: Num a => Interval a -> a
221width (I a b) = b - a
222{-# INLINE width #-}
223
224-- | Magnitude
225--
226-- >>> magnitude (1 ... 20)
227-- 20
228--
229-- >>> magnitude (-20 ... 10)
230-- 20
231--
232-- >>> magnitude (singleton 5)
233-- 5
234magnitude :: (Num a, Ord a) => Interval a -> a
235magnitude x = (max `on` abs) (inf x) (sup x)
236{-# INLINE magnitude #-}
237
238-- | \"mignitude\"
239--
240-- >>> mignitude (1 ... 20)
241-- 1
242--
243-- >>> mignitude (-20 ... 10)
244-- 10
245--
246-- >>> mignitude (singleton 5)
247-- 5
248mignitude :: (Num a, Ord a) => Interval a -> a
249mignitude x = (min `on` abs) (inf x) (sup x)
250{-# INLINE mignitude #-}
251
252instance (Num a, Ord a) => Num (Interval a) where
253 I a b + I a' b' = (a + a') ... (b + b')
254 {-# INLINE (+) #-}
255 I a b - I a' b' = (a - b') ... (b - a')
256 {-# INLINE (-) #-}
257 I a b * I a' b' =
258 minimum [a * a', a * b', b * a', b * b']
259 ...
260 maximum [a * a', a * b', b * a', b * b']
261 {-# INLINE (*) #-}
262 abs x@(I a b)
263 | a >= 0 = x
264 | b <= 0 = negate x
265 | otherwise = 0 ... max (- a) b
266 {-# INLINE abs #-}
267
268 signum = increasing signum
269 {-# INLINE signum #-}
270
271 fromInteger i = singleton (fromInteger i)
272 {-# INLINE fromInteger #-}
273
274-- | Bisect an interval at its midpoint.
275--
276-- >>> bisection (10.0 ... 20.0)
277-- (10.0 ... 15.0,15.0 ... 20.0)
278--
279-- >>> bisection (singleton 5.0)
280-- (5.0 ... 5.0,5.0 ... 5.0)
281--
282-- >>> bisection empty
283-- (NaN ... NaN,NaN ... NaN)
284bisection :: Fractional a => Interval a -> (Interval a, Interval a)
285bisection x = (inf x ... m, m ... sup x)
286 where m = midpoint x
287{-# INLINE bisection #-}
288
289-- | Nearest point to the midpoint of the interval.
290--
291-- >>> midpoint (10.0 ... 20.0)
292-- 15.0
293--
294-- >>> midpoint (singleton 5.0)
295-- 5.0
296--
297-- >>> midpoint empty
298-- NaN
299midpoint :: Fractional a => Interval a -> a
300midpoint x = inf x + (sup x - inf x) / 2
301{-# INLINE midpoint #-}
302
303-- | Determine if a point is in the interval.
304--
305-- >>> elem 3.2 (1.0 ... 5.0)
306-- True
307--
308-- >>> elem 5 (1.0 ... 5.0)
309-- True
310--
311-- >>> elem 1 (1.0 ... 5.0)
312-- True
313--
314-- >>> elem 8 (1.0 ... 5.0)
315-- False
316--
317-- >>> elem 5 empty
318-- False
319--
320elem :: Ord a => a -> Interval a -> Bool
321elem x xs = x >= inf xs && x <= sup xs
322{-# INLINE elem #-}
323
324-- | Determine if a point is not included in the interval
325--
326-- >>> notElem 8 (1.0 ... 5.0)
327-- True
328--
329-- >>> notElem 1.4 (1.0 ... 5.0)
330-- False
331--
332-- And of course, nothing is a member of the empty interval.
333--
334-- >>> notElem 5 empty
335-- True
336notElem :: Ord a => a -> Interval a -> Bool
337notElem x xs = not (elem x xs)
338{-# INLINE notElem #-}
339
340-- | 'realToFrac' will use the midpoint
341instance Real a => Real (Interval a) where
342 toRational x
343 | null x = nan
344 | otherwise = a + (b - a) / 2
345 where
346 a = toRational (inf x)
347 b = toRational (sup x)
348 {-# INLINE toRational #-}
349
350instance Ord a => Ord (Interval a) where
351 compare x y
352 | sup x < inf y = LT
353 | inf x > sup y = GT
354 | sup x == inf y && inf x == sup y = EQ
355 | otherwise = error "Numeric.Interval.compare: ambiguous comparison"
356 {-# INLINE compare #-}
357
358 max (I a b) (I a' b') = max a a' ... max b b'
359 {-# INLINE max #-}
360
361 min (I a b) (I a' b') = min a a' ... min b b'
362 {-# INLINE min #-}
363
364-- @'divNonZero' X Y@ assumes @0 `'notElem'` Y@
365divNonZero :: (Fractional a, Ord a) => Interval a -> Interval a -> Interval a
366divNonZero (I a b) (I a' b') =
367 minimum [a / a', a / b', b / a', b / b']
368 ...
369 maximum [a / a', a / b', b / a', b / b']
370
371-- @'divPositive' X y@ assumes y > 0, and divides @X@ by [0 ... y]
372divPositive :: (Fractional a, Ord a) => Interval a -> a -> Interval a
373divPositive x@(I a b) y
374 | a == 0 && b == 0 = x
375 -- b < 0 || isNegativeZero b = negInfinity ... ( b / y)
376 | b < 0 = negInfinity ... ( b / y)
377 | a < 0 = whole
378 | otherwise = (a / y) ... posInfinity
379{-# INLINE divPositive #-}
380
381-- divNegative assumes y < 0 and divides the interval @X@ by [y ... 0]
382divNegative :: (Fractional a, Ord a) => Interval a -> a -> Interval a
383divNegative x@(I a b) y
384 | a == 0 && b == 0 = - x -- flip negative zeros
385 -- b < 0 || isNegativeZero b = (b / y) ... posInfinity
386 | b < 0 = (b / y) ... posInfinity
387 | a < 0 = whole
388 | otherwise = negInfinity ... (a / y)
389{-# INLINE divNegative #-}
390
391divZero :: (Fractional a, Ord a) => Interval a -> Interval a
392divZero x
393 | inf x == 0 && sup x == 0 = x
394 | otherwise = whole
395{-# INLINE divZero #-}
396
397instance (Fractional a, Ord a) => Fractional (Interval a) where
398 -- TODO: check isNegativeZero properly
399 x / y
400 | 0 `notElem` y = divNonZero x y
401 | iz && sz = empty -- division by 0
402 | iz = divPositive x (inf y)
403 | sz = divNegative x (sup y)
404 | otherwise = divZero x
405 where
406 iz = inf y == 0
407 sz = sup y == 0
408 recip (I a b) = on min recip a b ... on max recip a b
409 {-# INLINE recip #-}
410 fromRational r = let r' = fromRational r in r' ... r'
411 {-# INLINE fromRational #-}
412
413instance RealFrac a => RealFrac (Interval a) where
414 properFraction x = (b, x - fromIntegral b)
415 where
416 b = truncate (midpoint x)
417 {-# INLINE properFraction #-}
418 ceiling x = ceiling (sup x)
419 {-# INLINE ceiling #-}
420 floor x = floor (inf x)
421 {-# INLINE floor #-}
422 round x = round (midpoint x)
423 {-# INLINE round #-}
424 truncate x = truncate (midpoint x)
425 {-# INLINE truncate #-}
426
427instance (RealFloat a, Ord a) => Floating (Interval a) where
428 pi = singleton pi
429 {-# INLINE pi #-}
430 exp = increasing exp
431 {-# INLINE exp #-}
432 log (I a b) = (if a > 0 then log a else negInfinity) ... log b
433 {-# INLINE log #-}
434 cos x
435 | null x = empty
436 | width t >= pi = (-1) ... 1
437 | inf t >= pi = - cos (t - pi)
438 | sup t <= pi = decreasing cos t
439 | sup t <= 2 * pi = (-1) ... cos ((pi * 2 - sup t) `min` inf t)
440 | otherwise = (-1) ... 1
441 where
442 t = fmod x (pi * 2)
443 {-# INLINE cos #-}
444 sin x
445 | null x = empty
446 | otherwise = cos (x - pi / 2)
447 {-# INLINE sin #-}
448 tan x
449 | null x = empty
450 | inf t' <= - pi / 2 || sup t' >= pi / 2 = whole
451 | otherwise = increasing tan x
452 where
453 t = x `fmod` pi
454 t' | t >= pi / 2 = t - pi
455 | otherwise = t
456 {-# INLINE tan #-}
457 asin x@(I a b)
458 | null x || b < -1 || a > 1 = empty
459 | otherwise =
460 (if a <= -1 then -halfPi else asin a)
461 ...
462 (if b >= 1 then halfPi else asin b)
463 where
464 halfPi = pi / 2
465 {-# INLINE asin #-}
466 acos x@(I a b)
467 | null x || b < -1 || a > 1 = empty
468 | otherwise =
469 (if b >= 1 then 0 else acos b)
470 ...
471 (if a < -1 then pi else acos a)
472 {-# INLINE acos #-}
473 atan = increasing atan
474 {-# INLINE atan #-}
475 sinh = increasing sinh
476 {-# INLINE sinh #-}
477 cosh x@(I a b)
478 | null x = empty
479 | b < 0 = decreasing cosh x
480 | a >= 0 = increasing cosh x
481 | otherwise = I 0 $ cosh $ if - a > b
482 then a
483 else b
484 {-# INLINE cosh #-}
485 tanh = increasing tanh
486 {-# INLINE tanh #-}
487 asinh = increasing asinh
488 {-# INLINE asinh #-}
489 acosh x@(I a b)
490 | null x || b < 1 = empty
491 | otherwise = I lo $ acosh b
492 where lo | a <= 1 = 0
493 | otherwise = acosh a
494 {-# INLINE acosh #-}
495 atanh x@(I a b)
496 | null x || b < -1 || a > 1 = empty
497 | otherwise =
498 (if a <= - 1 then negInfinity else atanh a)
499 ...
500 (if b >= 1 then posInfinity else atanh b)
501 {-# INLINE atanh #-}
502
503-- | lift a monotone increasing function over a given interval
504increasing :: (a -> b) -> Interval a -> Interval b
505increasing f (I a b) = f a ... f b
506
507-- | lift a monotone decreasing function over a given interval
508decreasing :: (a -> b) -> Interval a -> Interval b
509decreasing f (I a b) = f b ... f a
510
511-- | We have to play some semantic games to make these methods make sense.
512-- Most compute with the midpoint of the interval.
513instance RealFloat a => RealFloat (Interval a) where
514 floatRadix = floatRadix . midpoint
515
516 floatDigits = floatDigits . midpoint
517 floatRange = floatRange . midpoint
518 decodeFloat = decodeFloat . midpoint
519 encodeFloat m e = singleton (encodeFloat m e)
520 exponent = exponent . midpoint
521 significand x = min a b ... max a b
522 where
523 (_ ,em) = decodeFloat (midpoint x)
524 (mi,ei) = decodeFloat (inf x)
525 (ms,es) = decodeFloat (sup x)
526 a = encodeFloat mi (ei - em - floatDigits x)
527 b = encodeFloat ms (es - em - floatDigits x)
528 scaleFloat n x = scaleFloat n (inf x) ... scaleFloat n (sup x)
529 isNaN x = isNaN (inf x) || isNaN (sup x)
530 isInfinite x = isInfinite (inf x) || isInfinite (sup x)
531 isDenormalized x = isDenormalized (inf x) || isDenormalized (sup x)
532 -- contains negative zero
533 isNegativeZero x = not (inf x > 0)
534 && not (sup x < 0)
535 && ( (sup x == 0 && (inf x < 0 || isNegativeZero (inf x)))
536 || (inf x == 0 && isNegativeZero (inf x))
537 || (inf x < 0 && sup x >= 0))
538 isIEEE x = isIEEE (inf x) && isIEEE (sup x)
539 atan2 = error "unimplemented"
540
541-- TODO: (^), (^^) to give tighter bounds
542
543-- | Calculate the intersection of two intervals.
544--
545-- >>> intersection (1 ... 10 :: Interval Double) (5 ... 15 :: Interval Double)
546-- 5.0 ... 10.0
547intersection :: (Fractional a, Ord a) => Interval a -> Interval a -> Interval a
548intersection x@(I a b) y@(I a' b')
549 | x /=! y = empty
550 | otherwise = max a a' ... min b b'
551{-# INLINE intersection #-}
552
553-- | Calculate the convex hull of two intervals
554--
555-- >>> hull (0 ... 10 :: Interval Double) (5 ... 15 :: Interval Double)
556-- 0.0 ... 15.0
557--
558-- >>> hull (15 ... 85 :: Interval Double) (0 ... 10 :: Interval Double)
559-- 0.0 ... 85.0
560hull :: Ord a => Interval a -> Interval a -> Interval a
561hull x@(I a b) y@(I a' b')
562 | null x = y
563 | null y = x
564 | otherwise = min a a' ... max b b'
565{-# INLINE hull #-}
566
567-- | For all @x@ in @X@, @y@ in @Y@. @x '<' y@
568--
569-- >>> (5 ... 10 :: Interval Double) <! (20 ... 30 :: Interval Double)
570-- True
571--
572-- >>> (5 ... 10 :: Interval Double) <! (10 ... 30 :: Interval Double)
573-- False
574--
575-- >>> (20 ... 30 :: Interval Double) <! (5 ... 10 :: Interval Double)
576-- False
577(<!) :: Ord a => Interval a -> Interval a -> Bool
578x <! y = sup x < inf y
579{-# INLINE (<!) #-}
580
581-- | For all @x@ in @X@, @y@ in @Y@. @x '<=' y@
582--
583-- >>> (5 ... 10 :: Interval Double) <=! (20 ... 30 :: Interval Double)
584-- True
585--
586-- >>> (5 ... 10 :: Interval Double) <=! (10 ... 30 :: Interval Double)
587-- True
588--
589-- >>> (20 ... 30 :: Interval Double) <=! (5 ... 10 :: Interval Double)
590-- False
591(<=!) :: Ord a => Interval a -> Interval a -> Bool
592x <=! y = sup x <= inf y
593{-# INLINE (<=!) #-}
594
595-- | For all @x@ in @X@, @y@ in @Y@. @x '==' y@
596--
597-- Only singleton intervals return true
598--
599-- >>> (singleton 5 :: Interval Double) ==! (singleton 5 :: Interval Double)
600-- True
601--
602-- >>> (5 ... 10 :: Interval Double) ==! (5 ... 10 :: Interval Double)
603-- False
604(==!) :: Eq a => Interval a -> Interval a -> Bool
605x ==! y = sup x == inf y && inf x == sup y
606{-# INLINE (==!) #-}
607
608-- | For all @x@ in @X@, @y@ in @Y@. @x '/=' y@
609--
610-- >>> (5 ... 15 :: Interval Double) /=! (20 ... 40 :: Interval Double)
611-- True
612--
613-- >>> (5 ... 15 :: Interval Double) /=! (15 ... 40 :: Interval Double)
614-- False
615(/=!) :: Ord a => Interval a -> Interval a -> Bool
616x /=! y = sup x < inf y || inf x > sup y
617{-# INLINE (/=!) #-}
618
619-- | For all @x@ in @X@, @y@ in @Y@. @x '>' y@
620--
621-- >>> (20 ... 40 :: Interval Double) >! (10 ... 19 :: Interval Double)
622-- True
623--
624-- >>> (5 ... 20 :: Interval Double) >! (15 ... 40 :: Interval Double)
625-- False
626(>!) :: Ord a => Interval a -> Interval a -> Bool
627x >! y = inf x > sup y
628{-# INLINE (>!) #-}
629
630-- | For all @x@ in @X@, @y@ in @Y@. @x '>=' y@
631--
632-- >>> (20 ... 40 :: Interval Double) >=! (10 ... 20 :: Interval Double)
633-- True
634--
635-- >>> (5 ... 20 :: Interval Double) >=! (15 ... 40 :: Interval Double)
636-- False
637(>=!) :: Ord a => Interval a -> Interval a -> Bool
638x >=! y = inf x >= sup y
639{-# INLINE (>=!) #-}
640
641-- | For all @x@ in @X@, @y@ in @Y@. @x `op` y@
642--
643--
644certainly :: Ord a => (forall b. Ord b => b -> b -> Bool) -> Interval a -> Interval a -> Bool
645certainly cmp l r
646 | lt && eq && gt = True
647 | lt && eq = l <=! r
648 | lt && gt = l /=! r
649 | lt = l <! r
650 | eq && gt = l >=! r
651 | eq = l ==! r
652 | gt = l >! r
653 | otherwise = False
654 where
655 lt = cmp LT EQ
656 eq = cmp EQ EQ
657 gt = cmp GT EQ
658{-# INLINE certainly #-}
659
660-- | Check if interval @X@ totally contains interval @Y@
661--
662-- >>> (20 ... 40 :: Interval Double) `contains` (25 ... 35 :: Interval Double)
663-- True
664--
665-- >>> (20 ... 40 :: Interval Double) `contains` (15 ... 35 :: Interval Double)
666-- False
667contains :: Ord a => Interval a -> Interval a -> Bool
668contains x y = null y
669 || (not (null x) && inf x <= inf y && sup y <= sup x)
670{-# INLINE contains #-}
671
672-- | Flipped version of `contains`. Check if interval @X@ a subset of interval @Y@
673--
674-- >>> (25 ... 35 :: Interval Double) `isSubsetOf` (20 ... 40 :: Interval Double)
675-- True
676--
677-- >>> (20 ... 40 :: Interval Double) `isSubsetOf` (15 ... 35 :: Interval Double)
678-- False
679isSubsetOf :: Ord a => Interval a -> Interval a -> Bool
680isSubsetOf = flip contains
681{-# INLINE isSubsetOf #-}
682
683-- | Does there exist an @x@ in @X@, @y@ in @Y@ such that @x '<' y@?
684(<?) :: Ord a => Interval a -> Interval a -> Bool
685x <? y = inf x < sup y
686{-# INLINE (<?) #-}
687
688-- | Does there exist an @x@ in @X@, @y@ in @Y@ such that @x '<=' y@?
689(<=?) :: Ord a => Interval a -> Interval a -> Bool
690x <=? y = inf x <= sup y
691{-# INLINE (<=?) #-}
692
693-- | Does there exist an @x@ in @X@, @y@ in @Y@ such that @x '==' y@?
694(==?) :: Ord a => Interval a -> Interval a -> Bool
695x ==? y = inf x <= sup y && sup x >= inf y
696{-# INLINE (==?) #-}
697
698-- | Does there exist an @x@ in @X@, @y@ in @Y@ such that @x '/=' y@?
699(/=?) :: Eq a => Interval a -> Interval a -> Bool
700x /=? y = inf x /= sup y || sup x /= inf y
701{-# INLINE (/=?) #-}
702
703-- | Does there exist an @x@ in @X@, @y@ in @Y@ such that @x '>' y@?
704(>?) :: Ord a => Interval a -> Interval a -> Bool
705x >? y = sup x > inf y
706{-# INLINE (>?) #-}
707
708-- | Does there exist an @x@ in @X@, @y@ in @Y@ such that @x '>=' y@?
709(>=?) :: Ord a => Interval a -> Interval a -> Bool
710x >=? y = sup x >= inf y
711{-# INLINE (>=?) #-}
712
713-- | Does there exist an @x@ in @X@, @y@ in @Y@ such that @x `op` y@?
714possibly :: Ord a => (forall b. Ord b => b -> b -> Bool) -> Interval a -> Interval a -> Bool
715possibly cmp l r
716 | lt && eq && gt = True
717 | lt && eq = l <=? r
718 | lt && gt = l /=? r
719 | lt = l <? r
720 | eq && gt = l >=? r
721 | eq = l ==? r
722 | gt = l >? r
723 | otherwise = False
724 where
725 lt = cmp LT EQ
726 eq = cmp EQ EQ
727 gt = cmp GT EQ
728{-# INLINE possibly #-}
729
730-- | The nearest value to that supplied which is contained in the interval.
731clamp :: Ord a => Interval a -> a -> a
732clamp (I a b) x | x < a = a
733 | x > b = b
734 | otherwise = x
735
736-- | id function. Useful for type specification
737--
738-- >>> :t idouble (1 ... 3)
739-- idouble (1 ... 3) :: Interval Double
740idouble :: Interval Double -> Interval Double
741idouble = id
742
743-- | id function. Useful for type specification
744--
745-- >>> :t ifloat (1 ... 3)
746-- ifloat (1 ... 3) :: Interval Float
747ifloat :: Interval Float -> Interval Float
748ifloat = id
749
750-- Bugs:
751-- sin 1 :: Interval Double
752
753
754default (Integer,Double)
diff --git a/lib/Numeric/Interval/Bounded.hs b/lib/Numeric/Interval/Bounded.hs
new file mode 100644
index 0000000..2dd4d7b
--- /dev/null
+++ b/lib/Numeric/Interval/Bounded.hs
@@ -0,0 +1,9 @@
1module Numeric.Interval.Bounded where
2
3import Numeric.Interval
4
5whole' :: Bounded a => Interval a
6whole' = ( minBound ... maxBound )
7
8empty' :: Bounded a => Interval a
9empty' = ( maxBound ... minBound )
diff --git a/lib/PEM.hs b/lib/PEM.hs
new file mode 100644
index 0000000..e07b3d4
--- /dev/null
+++ b/lib/PEM.hs
@@ -0,0 +1,34 @@
1{-# LANGUAGE OverloadedStrings #-}
2module PEM where
3
4import Data.Monoid
5import qualified Data.ByteString.Lazy as LW
6import qualified Data.ByteString.Lazy.Char8 as L
7import Control.Monad
8import Control.Applicative
9import qualified Codec.Binary.Base64 as Base64
10import ScanningParser
11
12data PEMBlob = PEMBlob { pemType :: L.ByteString
13 , pemBlob :: L.ByteString
14 }
15 deriving (Eq,Show)
16
17pemParser mtyp = ScanningParser (maybe fndany fndtyp mtyp) pbdy
18 where
19 hdr typ = "-----BEGIN " <> typ <> "-----"
20 fndtyp typ bs = if bs==hdr typ then Just typ else Nothing
21 fndany bs = do
22 guard $ "-----BEGIN " `L.isPrefixOf` bs
23 let x0 = L.drop 11 bs
24 guard $ "-----" `LW.isSuffixOf` x0
25 let typ = L.take (L.length x0 - 5) x0
26 return typ
27
28 pbdy typ xs = (mblob, drop 1 rs)
29 where
30 (ys,rs) = span (/="-----END " <> typ <> "-----") xs
31 mblob = PEMBlob typ <$> LW.pack <$> Base64.decode (L.unpack dta)
32 dta = case ys of
33 [] -> ""
34 dta_lines -> L.concat dta_lines
diff --git a/lib/ProcessUtils.hs b/lib/ProcessUtils.hs
new file mode 100644
index 0000000..4e3ac38
--- /dev/null
+++ b/lib/ProcessUtils.hs
@@ -0,0 +1,45 @@
1module ProcessUtils
2 ( ExitCode(ExitFailure,ExitSuccess)
3 , systemEnv
4 ) where
5
6import GHC.IO.Exception ( ioException, IOErrorType(..) )
7import System.Process
8import System.Posix.Signals
9import System.Process.Internals (runGenProcess_,defaultSignal)
10import System.Environment
11import Data.Maybe ( isNothing )
12import System.IO.Error ( mkIOError, ioeSetErrorString )
13import System.Exit ( ExitCode(..) )
14
15
16-- | systemEnv
17-- This is like System.Process.system except that it lets you set
18-- some environment variables.
19systemEnv :: [(String, String)] -> String -> IO ExitCode
20systemEnv _ "" =
21 ioException (ioeSetErrorString (mkIOError InvalidArgument "system" Nothing Nothing) "null command")
22systemEnv vars cmd = do
23 env0 <- getEnvironment
24 let env1 = filter (isNothing . flip lookup vars . fst) env0
25 env = vars ++ env1
26 syncProcess "system" $ (shell cmd) {env=Just env}
27 where
28 -- This is a non-exported function from System.Process
29 syncProcess fun c = do
30 -- The POSIX version of system needs to do some manipulation of signal
31 -- handlers. Since we're going to be synchronously waiting for the child,
32 -- we want to ignore ^C in the parent, but handle it the default way
33 -- in the child (using SIG_DFL isn't really correct, it should be the
34 -- original signal handler, but the GHC RTS will have already set up
35 -- its own handler and we don't want to use that).
36 old_int <- installHandler sigINT Ignore Nothing
37 old_quit <- installHandler sigQUIT Ignore Nothing
38 (_,_,_,p) <- runGenProcess_ fun c
39 (Just defaultSignal) (Just defaultSignal)
40 r <- waitForProcess p
41 _ <- installHandler sigINT old_int Nothing
42 _ <- installHandler sigQUIT old_quit Nothing
43 return r
44
45
diff --git a/lib/ScanningParser.hs b/lib/ScanningParser.hs
new file mode 100644
index 0000000..f99e120
--- /dev/null
+++ b/lib/ScanningParser.hs
@@ -0,0 +1,74 @@
1{-# LANGUAGE RankNTypes #-}
2{-# LANGUAGE ExistentialQuantification #-}
3module ScanningParser
4 ( ScanningParser(..)
5 , scanAndParse
6 , scanAndParse1
7 ) where
8
9import Data.Maybe
10import Data.List
11import Control.Applicative
12import Control.Monad
13import Data.Monoid
14
15-- | This type provides the means to parse a stream of 'tok' and extract all
16-- the 'obj' parses that occur.
17--
18-- Use Functor and Monoid interfaces to combine parsers. For example,
19--
20-- > parserAorB = fmap Left parserA <> fmap Right parserB
21--
22data ScanningParser tok obj = forall partial. ScanningParser
23 { findFirst :: tok -> Maybe partial
24 -- ^ If the token starts an object, returns a partial parse.
25 , parseBody :: partial -> [tok] -> (Maybe obj,[tok])
26 -- ^ Given a partial parse and the stream of tokens that follow, attempt to
27 -- parse an object and return the unconsumed tokens.
28 }
29
30instance Functor (ScanningParser a) where
31 fmap f (ScanningParser ffst pbody)
32 = ScanningParser ffst (\b -> first (fmap f) . pbody b)
33 where
34 first f (x,y) = (f x, y)
35
36
37instance Monoid (ScanningParser a b) where
38 mempty = ScanningParser (const Nothing) (const $ const (Nothing,[]))
39 mappend (ScanningParser ffstA pbdyA)
40 (ScanningParser ffstB pbdyB)
41 = ScanningParser ffst pbody
42 where
43 ffst x = mplus (Left <$> ffstA x)
44 (Right <$> ffstB x)
45 pbody (Left apart) = pbdyA apart
46 pbody (Right bpart) = pbdyB bpart
47
48
49-- | Apply a 'ScanningParser' to a list of tokens, yielding a list of parsed
50-- objects.
51scanAndParse :: ScanningParser a c -> [a] -> [c]
52scanAndParse psr [] = []
53scanAndParse psr@(ScanningParser ffst pbdy) ts = do
54 (b,xs) <- take 1 $ mapMaybe findfst' tss
55 let (mc,ts') = pbdy b xs
56 rec = scanAndParse psr ts'
57 maybe rec (:rec) mc
58 where
59 tss = tails ts
60 findfst' ts = do
61 x <- listToMaybe ts
62 b <- ffst x
63 return (b,drop 1 ts)
64
65scanAndParse1 :: ScanningParser a c -> [a] -> (Maybe c, [a])
66scanAndParse1 psr@(ScanningParser ffst pbdy) ts =
67 maybe (Nothing,[]) (uncurry pbdy) mb
68 where
69 mb = listToMaybe $ mapMaybe findfst' tss
70 tss = tails ts
71 findfst' ts = do
72 x <- listToMaybe ts
73 b <- ffst x
74 return (b,drop 1 ts)
diff --git a/lib/SuperOrd.hs b/lib/SuperOrd.hs
new file mode 100644
index 0000000..258a823
--- /dev/null
+++ b/lib/SuperOrd.hs
@@ -0,0 +1,23 @@
1module SuperOrd where
2
3data SuperOrd a
4 = NegativeInfinity
5 | SuperOrd { superApprox :: !a
6 , superCompareApprox :: !Ordering
7 }
8 | PositiveInfinity
9 deriving (Eq, Ord, Show)
10
11instance Bounded (SuperOrd a) where
12 minBound = NegativeInfinity
13 maxBound = PositiveInfinity
14
15exactly :: a -> SuperOrd a
16exactly a = SuperOrd a EQ
17
18lessThan :: a -> SuperOrd a
19lessThan a = SuperOrd a LT
20
21greaterThan :: a -> SuperOrd a
22greaterThan a = SuperOrd a GT
23
diff --git a/lib/TimeUtil.hs b/lib/TimeUtil.hs
new file mode 100644
index 0000000..879bc32
--- /dev/null
+++ b/lib/TimeUtil.hs
@@ -0,0 +1,128 @@
1{-# LANGUAGE OverloadedStrings #-}
2{-# LANGUAGE ViewPatterns #-}
3{-# LANGUAGE CPP #-}
4module TimeUtil
5 ( now
6 , IsTime(..)
7 , fromTime
8 , toUTC
9 , parseRFC2822
10 , printRFC2822
11 , dateParser
12 ) where
13
14import Data.Time.LocalTime
15import Data.Time.Format
16import Data.Time.Clock
17import Data.Time.Clock.POSIX
18#if !MIN_VERSION_time(1,5,0)
19import System.Locale (defaultTimeLocale)
20#endif
21import Data.String
22import Control.Applicative
23import Data.Maybe
24import Data.Char
25import qualified Data.ByteString.Char8 as S
26import qualified Data.ByteString.Lazy.Char8 as L
27import Foreign.C.Types ( CTime(..) )
28import Data.Word ( Word32 )
29
30import ScanningParser
31
32class IsTime a where
33 fromZonedTime :: ZonedTime -> a
34 toZonedTime :: a -> IO ZonedTime
35
36instance IsTime ZonedTime where
37 fromZonedTime x = x
38 toZonedTime x = return x
39
40instance IsTime UTCTime where
41 toZonedTime t = utcToLocalZonedTime t
42 fromZonedTime zt = zonedTimeToUTC zt
43
44instance IsTime Integer where
45 toZonedTime t = utcToLocalZonedTime utime
46 where
47 utime = posixSecondsToUTCTime (fromIntegral t)
48 fromZonedTime zt = round $ utcTimeToPOSIXSeconds utime
49 where
50 utime = zonedTimeToUTC zt
51
52printRFC2822 :: (IsString b, IsTime a) => a -> IO b
53printRFC2822 tm = do
54 zt@(ZonedTime lt z) <- toZonedTime tm
55 let rfc2822 = formatTime defaultTimeLocale "%a, %0e %b %Y %T" zt ++ printZone
56 timeZoneStr = timeZoneOffsetString z
57 printZone = " " ++ timeZoneStr ++ " (" ++ fromString (show z) ++ ")"
58 return $ fromString $ rfc2822
59
60parseRFC2822 :: IsTime b => S.ByteString -> Maybe b
61parseRFC2822 str =
62 case mapMaybe (\f->parseTime defaultTimeLocale f str') formatRFC2822 of
63 [] -> Nothing
64 (zt:_) -> Just $ fromZonedTime zt
65 where
66 str' = S.unpack stripped
67 stripped = strip $ str
68 strip bs = bs3
69 where
70 (_,bs0) = S.span isSpace bs
71 (bs1,_) = S.spanEnd isSpace bs0
72 (bs2,cp) = S.spanEnd (==')') bs1
73 bs3 = if S.null cp
74 then bs2
75 else let (op,_) = S.spanEnd (/='(') bs2
76 in fst $ S.spanEnd isSpace $ S.init op
77 formatRFC2822 = [ "%a, %e %b %Y %T GMT"
78 , "%a, %e %b %Y %T %z"
79 , "%e %b %Y %T GMT"
80 , "%e %b %Y %T %z"
81 , "%a, %e %b %Y %R GMT"
82 , "%a, %e %b %Y %R %z"
83 , "%e %b %Y %R GMT"
84 , "%e %b %Y %R %z"
85 ]
86
87now :: IO Integer
88now = floor <$> Data.Time.Clock.POSIX.getPOSIXTime
89
90dateParser :: ScanningParser L.ByteString UTCTime
91dateParser = ScanningParser ffst pbdy
92 where
93 ffst bs = do
94 let (h,bs') = L.splitAt 6 bs
95 if h=="Date: "
96 then return $ parseRFC2822 $ foldr1 S.append $ L.toChunks bs'
97 else Nothing
98 pbdy date xs = (date,xs)
99
100class IsUTC a where
101 fromUTC :: UTCTime -> a
102 toUTC :: a -> UTCTime
103
104fromTime :: ( IsUTC a, IsUTC b ) => a -> b
105fromTime = fromUTC . toUTC
106
107instance IsUTC UTCTime where
108 fromUTC = id
109 toUTC = id
110
111instance IsUTC CTime where
112 fromUTC utc = CTime (round $ utcTimeToPOSIXSeconds utc)
113 toUTC (CTime t) = posixSecondsToUTCTime (realToFrac t)
114
115instance IsUTC Word32 where
116 fromUTC utc = round $ utcTimeToPOSIXSeconds utc
117 toUTC t = posixSecondsToUTCTime (realToFrac t)
118
119{-
120main = do
121 nowtime <- now
122 printRFC2822 nowtime >>= putStrLn
123 let test1 = "Thu, 08 May 2014 23:24:47 -0400"
124 test2 = " Thu, 08 May 2014 23:24:47 -0400 (EDT) "
125 putStrLn $ show (parseRFC2822 test1 :: Maybe Integer)
126 putStrLn $ show (parseRFC2822 test2 :: Maybe Integer)
127 return ()
128-}
diff --git a/lib/dotlock.c b/lib/dotlock.c
new file mode 100644
index 0000000..c111159
--- /dev/null
+++ b/lib/dotlock.c
@@ -0,0 +1,1303 @@
1/* dotlock.c - dotfile locking
2 * Copyright (C) 1998, 2000, 2001, 2003, 2004,
3 * 2005, 2006, 2008, 2010, 2011 Free Software Foundation, Inc.
4 *
5 * This file is part of JNLIB, which is a subsystem of GnuPG.
6 *
7 * JNLIB is free software; you can redistribute it and/or modify it
8 * under the terms of either
9 *
10 * - the GNU Lesser General Public License as published by the Free
11 * Software Foundation; either version 3 of the License, or (at
12 * your option) any later version.
13 *
14 * or
15 *
16 * - the GNU General Public License as published by the Free
17 * Software Foundation; either version 2 of the License, or (at
18 * your option) any later version.
19 *
20 * or both in parallel, as here.
21 *
22 * JNLIB is distributed in the hope that it will be useful, but
23 * WITHOUT ANY WARRANTY; without even the implied warranty of
24 * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
25 * General Public License for more details.
26 *
27 * You should have received a copies of the GNU General Public License
28 * and the GNU Lesser General Public License along with this program;
29 * if not, see <http://www.gnu.org/licenses/>.
30 *
31 * ALTERNATIVELY, this file may be distributed under the terms of the
32 * following license, in which case the provisions of this license are
33 * required INSTEAD OF the GNU Lesser General License or the GNU
34 * General Public License. If you wish to allow use of your version of
35 * this file only under the terms of the GNU Lesser General License or
36 * the GNU General Public License, and not to allow others to use your
37 * version of this file under the terms of the following license,
38 * indicate your decision by deleting this paragraph and the license
39 * below.
40 *
41 * Redistribution and use in source and binary forms, with or without
42 * modification, are permitted provided that the following conditions
43 * are met:
44 *
45 * 1. Redistributions of source code must retain the above copyright
46 * notice, and the entire permission notice in its entirety,
47 * including the disclaimer of warranties.
48 * 2. Redistributions in binary form must reproduce the above copyright
49 * notice, this list of conditions and the following disclaimer in the
50 * documentation and/or other materials provided with the distribution.
51 * 3. The name of the author may not be used to endorse or promote
52 * products derived from this software without specific prior
53 * written permission.
54 *
55 * THIS SOFTWARE IS PROVIDED "AS IS" AND ANY EXPRESS OR IMPLIED
56 * WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES
57 * OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE
58 * DISCLAIMED. IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR ANY DIRECT,
59 * INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES
60 * (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR
61 * SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
62 * HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT,
63 * STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE)
64 * ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED
65 * OF THE POSSIBILITY OF SUCH DAMAGE.
66 */
67
68/*
69 Overview:
70 =========
71
72 This module implements advisory file locking in a portable way.
73 Due to the problems with POSIX fcntl locking a separate lock file
74 is used. It would be possible to use fcntl locking on this lock
75 file and thus avoid the weird auto unlock bug of POSIX while still
76 having an unproved better performance of fcntl locking. However
77 there are still problems left, thus we resort to use a hardlink
78 which has the well defined property that a link call will fail if
79 the target file already exists.
80
81 Given that hardlinks are also available on NTFS file systems since
82 Windows XP; it will be possible to enhance this module to use
83 hardlinks even on Windows and thus allow Windows and Posix clients
84 to use locking on the same directory. This is not yet implemented;
85 instead we use a lockfile on Windows along with W32 style file
86 locking.
87
88 On FAT file systems hardlinks are not supported. Thus this method
89 does not work. Our solution is to use a O_EXCL locking instead.
90 Querying the type of the file system is not easy to do in a
91 portable way (e.g. Linux has a statfs, BSDs have a the same call
92 but using different structures and constants). What we do instead
93 is to check at runtime whether link(2) works for a specific lock
94 file.
95
96
97 How to use:
98 ===========
99
100 At program initialization time, the module should be explicitly
101 initialized:
102
103 dotlock_create (NULL, 0);
104
105 This installs an atexit handler and may also initialize mutex etc.
106 It is optional for non-threaded applications. Only the first call
107 has an effect. This needs to be done before any extra threads are
108 started.
109
110 To create a lock file (which prepares it but does not take the
111 lock) you do:
112
113 dotlock_t h
114
115 h = dotlock_create (fname, 0);
116 if (!h)
117 error ("error creating lock file: %s\n", strerror (errno));
118
119 It is important to handle the error. For example on a read-only
120 file system a lock can't be created (but is usually not needed).
121 FNAME is the file you want to lock; the actual lockfile is that
122 name with the suffix ".lock" appended. On success a handle to be
123 used with the other functions is returned or NULL on error. Note
124 that the handle shall only be used by one thread at a time. This
125 function creates a unique file temporary file (".#lk*") in the same
126 directory as FNAME and returns a handle for further operations.
127 The module keeps track of theses unique files so that they will be
128 unlinked using the atexit handler. If you don't need the lock file
129 anymore, you may also explicitly remove it with a call to:
130
131 dotlock_destroy (h);
132
133 To actually lock the file, you use:
134
135 if (dotlock_take (h, -1))
136 error ("error taking lock: %s\n", strerror (errno));
137
138 This function will wait until the lock is acquired. If an
139 unexpected error occurs if will return non-zero and set ERRNO. If
140 you pass (0) instead of (-1) the function does not wait in case the
141 file is already locked but returns -1 and sets ERRNO to EACCES.
142 Any other positive value for the second parameter is considered a
143 timeout valuie in milliseconds.
144
145 To release the lock you call:
146
147 if (dotlock_release (h))
148 error ("error releasing lock: %s\n", strerror (errno));
149
150 or, if the lock file is not anymore needed, you may just call
151 dotlock_destroy. However dotlock_release does some extra checks
152 before releasing the lock and prints diagnostics to help detecting
153 bugs.
154
155 If you want to explicitly destroy all lock files you may call
156
157 dotlock_remove_lockfiles ();
158
159 which is the core of the installed atexit handler. In case your
160 application wants to disable locking completely it may call
161
162 disable_locking ()
163
164 before any locks are created.
165
166 There are two convenience functions to store an integer (e.g. a
167 file descriptor) value with the handle:
168
169 void dotlock_set_fd (dotlock_t h, int fd);
170 int dotlock_get_fd (dotlock_t h);
171
172 If nothing has been stored dotlock_get_fd returns -1.
173
174
175
176 How to build:
177 =============
178
179 This module was originally developed for GnuPG but later changed to
180 allow its use without any GnuPG dependency. If you want to use it
181 with you application you may simply use it and it should figure out
182 most things automagically.
183
184 You may use the common config.h file to pass macros, but take care
185 to pass -DHAVE_CONFIG_H to the compiler. Macros used by this
186 module are:
187
188 DOTLOCK_USE_PTHREAD - Define if POSIX threads are in use.
189
190 DOTLOCK_GLIB_LOGGING - Define this to use Glib logging functions.
191
192 DOTLOCK_EXT_SYM_PREFIX - Prefix all external symbols with the
193 string to which this macro evaluates.
194
195 GNUPG_MAJOR_VERSION - Defined when used by GnuPG.
196
197 HAVE_DOSISH_SYSTEM - Defined for Windows etc. Will be
198 automatically defined if a the target is
199 Windows.
200
201 HAVE_POSIX_SYSTEM - Internally defined to !HAVE_DOSISH_SYSTEM.
202
203 HAVE_SIGNAL_H - Should be defined on Posix systems. If config.h
204 is not used defaults to defined.
205
206 DIRSEP_C - Separation character for file name parts.
207 Usually not redefined.
208
209 EXTSEP_S - Separation string for file name suffixes.
210 Usually not redefined.
211
212 HAVE_W32CE_SYSTEM - Currently only used by GnuPG.
213
214 Note that there is a test program t-dotlock which has compile
215 instructions at its end. At least for SMBFS and CIFS it is
216 important that 64 bit versions of stat are used; most programming
217 environments do this these days, just in case you want to compile
218 it on the command line, remember to pass -D_FILE_OFFSET_BITS=64
219
220
221 Bugs:
222 =====
223
224 On Windows this module is not yet thread-safe.
225
226
227 Miscellaneous notes:
228 ====================
229
230 On hardlinks:
231 - Hardlinks are supported under Windows with NTFS since XP/Server2003.
232 - In Linux 2.6.33 both SMBFS and CIFS seem to support hardlinks.
233 - NFS supports hard links. But there are solvable problems.
234 - FAT does not support links
235
236 On the file locking API:
237 - CIFS on Linux 2.6.33 supports several locking methods.
238 SMBFS seems not to support locking. No closer checks done.
239 - NFS supports Posix locks. flock is emulated in the server.
240 However there are a couple of problems; see below.
241 - FAT does not support locks.
242 - An advantage of fcntl locking is that R/W locks can be
243 implemented which is not easy with a straight lock file.
244
245 On O_EXCL:
246 - Does not work reliable on NFS
247 - Should work on CIFS and SMBFS but how can we delete lockfiles?
248
249 On NFS problems:
250 - Locks vanish if the server crashes and reboots.
251 - Client crashes keep the lock in the server until the client
252 re-connects.
253 - Communication problems may return unreliable error codes. The
254 MUA Postfix's workaround is to compare the link count after
255 seeing an error for link. However that gives a race. If using a
256 unique file to link to a lockfile and using stat to check the
257 link count instead of looking at the error return of link(2) is
258 the best solution.
259 - O_EXCL seems to have a race and may re-create a file anyway.
260
261*/
262
263#ifdef HAVE_CONFIG_H
264# include <config.h>
265#endif
266
267/* Some quick replacements for stuff we usually expect to be defined
268 in config.h. Define HAVE_POSIX_SYSTEM for better readability. */
269#if !defined (HAVE_DOSISH_SYSTEM) && defined(_WIN32)
270# define HAVE_DOSISH_SYSTEM 1
271#endif
272#if !defined (HAVE_DOSISH_SYSTEM) && !defined (HAVE_POSIX_SYSTEM)
273# define HAVE_POSIX_SYSTEM 1
274#endif
275
276/* With no config.h assume that we have sitgnal.h. */
277#if !defined (HAVE_CONFIG_H) && defined (HAVE_POSIX_SYSTEM)
278# define HAVE_SIGNAL_H 1
279#endif
280
281/* Standard headers. */
282#include <stdlib.h>
283#include <stdio.h>
284#include <string.h>
285#include <errno.h>
286#include <ctype.h>
287#include <errno.h>
288#include <unistd.h>
289#ifdef HAVE_DOSISH_SYSTEM
290# define WIN32_LEAN_AND_MEAN /* We only need the OS core stuff. */
291# include <windows.h>
292#else
293# include <sys/types.h>
294# include <sys/stat.h>
295# include <sys/utsname.h>
296#endif
297#include <sys/types.h>
298#include <sys/time.h>
299#include <sys/stat.h>
300#include <fcntl.h>
301#ifdef HAVE_SIGNAL_H
302# include <signal.h>
303#endif
304#ifdef DOTLOCK_USE_PTHREAD
305# include <pthread.h>
306#endif
307
308#ifdef DOTLOCK_GLIB_LOGGING
309# include <glib.h>
310#endif
311
312#ifdef GNUPG_MAJOR_VERSION
313# include "libjnlib-config.h"
314#endif
315#ifdef HAVE_W32CE_SYSTEM
316# include "utf8conv.h" /* WindowsCE requires filename conversion. */
317#endif
318
319#include "dotlock.h"
320
321
322/* Define constants for file name construction. */
323#if !defined(DIRSEP_C) && !defined(EXTSEP_S)
324# ifdef HAVE_DOSISH_SYSTEM
325# define DIRSEP_C '\\'
326# define EXTSEP_S "."
327#else
328# define DIRSEP_C '/'
329# define EXTSEP_S "."
330# endif
331#endif
332
333/* In GnuPG we use wrappers around the malloc fucntions. If they are
334 not defined we assume that this code is used outside of GnuPG and
335 fall back to the regular malloc functions. */
336#ifndef jnlib_malloc
337# define jnlib_malloc(a) malloc ((a))
338# define jnlib_calloc(a,b) calloc ((a), (b))
339# define jnlib_free(a) free ((a))
340#endif
341
342/* Wrapper to set ERRNO. */
343#ifndef jnlib_set_errno
344# ifdef HAVE_W32CE_SYSTEM
345# define jnlib_set_errno(e) gpg_err_set_errno ((e))
346# else
347# define jnlib_set_errno(e) do { errno = (e); } while (0)
348# endif
349#endif
350
351/* Gettext macro replacement. */
352#ifndef _
353# define _(a) (a)
354#endif
355
356#ifdef GNUPG_MAJOR_VERSION
357# define my_info_0(a) log_info ((a))
358# define my_info_1(a,b) log_info ((a), (b))
359# define my_info_2(a,b,c) log_info ((a), (b), (c))
360# define my_info_3(a,b,c,d) log_info ((a), (b), (c), (d))
361# define my_error_0(a) log_error ((a))
362# define my_error_1(a,b) log_error ((a), (b))
363# define my_error_2(a,b,c) log_error ((a), (b), (c))
364# define my_debug_1(a,b) log_debug ((a), (b))
365# define my_fatal_0(a) log_fatal ((a))
366#elif defined (DOTLOCK_GLIB_LOGGING)
367# define my_info_0(a) g_message ((a))
368# define my_info_1(a,b) g_message ((a), (b))
369# define my_info_2(a,b,c) g_message ((a), (b), (c))
370# define my_info_3(a,b,c,d) g_message ((a), (b), (c), (d))
371# define my_error_0(a) g_warning ((a))
372# define my_error_1(a,b) g_warning ((a), (b))
373# define my_error_2(a,b,c) g_warning ((a), (b), (c))
374# define my_debug_1(a,b) g_debug ((a), (b))
375# define my_fatal_0(a) g_error ((a))
376#else
377# define my_info_0(a) fprintf (stderr, (a))
378# define my_info_1(a,b) fprintf (stderr, (a), (b))
379# define my_info_2(a,b,c) fprintf (stderr, (a), (b), (c))
380# define my_info_3(a,b,c,d) fprintf (stderr, (a), (b), (c), (d))
381# define my_error_0(a) fprintf (stderr, (a))
382# define my_error_1(a,b) fprintf (stderr, (a), (b))
383# define my_error_2(a,b,c) fprintf (stderr, (a), (b), (c))
384# define my_debug_1(a,b) fprintf (stderr, (a), (b))
385# define my_fatal_0(a) do { fprintf (stderr,(a)); fflush (stderr); \
386 abort (); } while (0)
387#endif
388
389
390
391
392
393/* The object describing a lock. */
394struct dotlock_handle
395{
396 struct dotlock_handle *next;
397 char *lockname; /* Name of the actual lockfile. */
398 unsigned int locked:1; /* Lock status. */
399 unsigned int disable:1; /* If true, locking is disabled. */
400 unsigned int use_o_excl:1; /* Use open (O_EXCL) for locking. */
401
402 int extra_fd; /* A place for the caller to store an FD. */
403
404#ifdef HAVE_DOSISH_SYSTEM
405 HANDLE lockhd; /* The W32 handle of the lock file. */
406#else /*!HAVE_DOSISH_SYSTEM */
407 char *tname; /* Name of the lockfile template. */
408 size_t nodename_off; /* Offset in TNAME of the nodename part. */
409 size_t nodename_len; /* Length of the nodename part. */
410#endif /*!HAVE_DOSISH_SYSTEM */
411};
412
413
414/* A list of of all lock handles. The volatile attribute might help
415 if used in an atexit handler. */
416static volatile dotlock_t all_lockfiles;
417#ifdef DOTLOCK_USE_PTHREAD
418static pthread_mutex_t all_lockfiles_mutex = PTHREAD_MUTEX_INITIALIZER;
419# define LOCK_all_lockfiles() do { \
420 if (pthread_mutex_lock (&all_lockfiles_mutex)) \
421 my_fatal_0 ("locking all_lockfiles_mutex failed\n"); \
422 } while (0)
423# define UNLOCK_all_lockfiles() do { \
424 if (pthread_mutex_unlock (&all_lockfiles_mutex)) \
425 my_fatal_0 ("unlocking all_lockfiles_mutex failed\n"); \
426 } while (0)
427#else /*!DOTLOCK_USE_PTHREAD*/
428# define LOCK_all_lockfiles() do { } while (0)
429# define UNLOCK_all_lockfiles() do { } while (0)
430#endif /*!DOTLOCK_USE_PTHREAD*/
431
432/* If this has the value true all locking is disabled. */
433static int never_lock;
434
435
436
437
438
439/* Entirely disable all locking. This function should be called
440 before any locking is done. It may be called right at startup of
441 the process as it only sets a global value. */
442void
443dotlock_disable (void)
444{
445 never_lock = 1;
446}
447
448
449#ifdef HAVE_POSIX_SYSTEM
450static int
451maybe_deadlock (dotlock_t h)
452{
453 dotlock_t r;
454 int res = 0;
455
456 LOCK_all_lockfiles ();
457 for (r=all_lockfiles; r; r = r->next)
458 {
459 if ( r != h && r->locked )
460 {
461 res = 1;
462 break;
463 }
464 }
465 UNLOCK_all_lockfiles ();
466 return res;
467}
468#endif /*HAVE_POSIX_SYSTEM*/
469
470
471/* Read the lock file and return the pid, returns -1 on error. True
472 will be stored in the integer at address SAME_NODE if the lock file
473 has been created on the same node. */
474#ifdef HAVE_POSIX_SYSTEM
475static int
476read_lockfile (dotlock_t h, int *same_node )
477{
478 char buffer_space[10+1+70+1]; /* 70 is just an estimated value; node
479 names are usually shorter. */
480 int fd;
481 int pid = -1;
482 char *buffer, *p;
483 size_t expected_len;
484 int res, nread;
485
486 *same_node = 0;
487 expected_len = 10 + 1 + h->nodename_len + 1;
488 if ( expected_len >= sizeof buffer_space)
489 {
490 buffer = jnlib_malloc (expected_len);
491 if (!buffer)
492 return -1;
493 }
494 else
495 buffer = buffer_space;
496
497 if ( (fd = open (h->lockname, O_RDONLY)) == -1 )
498 {
499 int e = errno;
500 my_info_2 ("error opening lockfile '%s': %s\n",
501 h->lockname, strerror(errno) );
502 if (buffer != buffer_space)
503 jnlib_free (buffer);
504 jnlib_set_errno (e); /* Need to return ERRNO here. */
505 return -1;
506 }
507
508 p = buffer;
509 nread = 0;
510 do
511 {
512 res = read (fd, p, expected_len - nread);
513 if (res == -1 && errno == EINTR)
514 continue;
515 if (res < 0)
516 {
517 my_info_1 ("error reading lockfile '%s'\n", h->lockname );
518 close (fd);
519 if (buffer != buffer_space)
520 jnlib_free (buffer);
521 jnlib_set_errno (0); /* Do not return an inappropriate ERRNO. */
522 return -1;
523 }
524 p += res;
525 nread += res;
526 }
527 while (res && nread != expected_len);
528 close(fd);
529
530 if (nread < 11)
531 {
532 my_info_1 ("invalid size of lockfile '%s'\n", h->lockname);
533 if (buffer != buffer_space)
534 jnlib_free (buffer);
535 jnlib_set_errno (0); /* Better don't return an inappropriate ERRNO. */
536 return -1;
537 }
538
539 if (buffer[10] != '\n'
540 || (buffer[10] = 0, pid = atoi (buffer)) == -1
541 || !pid )
542 {
543 my_error_2 ("invalid pid %d in lockfile '%s'\n", pid, h->lockname);
544 if (buffer != buffer_space)
545 jnlib_free (buffer);
546 jnlib_set_errno (0);
547 return -1;
548 }
549
550 if (nread == expected_len
551 && !memcmp (h->tname+h->nodename_off, buffer+11, h->nodename_len)
552 && buffer[11+h->nodename_len] == '\n')
553 *same_node = 1;
554
555 if (buffer != buffer_space)
556 jnlib_free (buffer);
557 return pid;
558}
559#endif /*HAVE_POSIX_SYSTEM */
560
561
562/* Check whether the file system which stores TNAME supports
563 hardlinks. Instead of using the non-portable statsfs call which
564 differs between various Unix versions, we do a runtime test.
565 Returns: 0 supports hardlinks; 1 no hardlink support, -1 unknown
566 (test error). */
567#ifdef HAVE_POSIX_SYSTEM
568static int
569use_hardlinks_p (const char *tname)
570{
571 char *lname;
572 struct stat sb;
573 unsigned int nlink;
574 int res;
575
576 if (stat (tname, &sb))
577 return -1;
578 nlink = (unsigned int)sb.st_nlink;
579
580 lname = jnlib_malloc (strlen (tname) + 1 + 1);
581 if (!lname)
582 return -1;
583 strcpy (lname, tname);
584 strcat (lname, "x");
585
586 /* We ignore the return value of link() because it is unreliable. */
587 (void) link (tname, lname);
588
589 if (stat (tname, &sb))
590 res = -1; /* Ooops. */
591 else if (sb.st_nlink == nlink + 1)
592 res = 0; /* Yeah, hardlinks are supported. */
593 else
594 res = 1; /* No hardlink support. */
595
596 unlink (lname);
597 jnlib_free (lname);
598 return res;
599}
600#endif /*HAVE_POSIX_SYSTEM */
601
602
603
604#ifdef HAVE_POSIX_SYSTEM
605/* Locking core for Unix. It used a temporary file and the link
606 system call to make locking an atomic operation. */
607static dotlock_t
608dotlock_create_unix (dotlock_t h, const char *file_to_lock)
609{
610 int fd = -1;
611 char pidstr[16];
612 const char *nodename;
613 const char *dirpart;
614 int dirpartlen;
615 struct utsname utsbuf;
616 size_t tnamelen;
617
618 snprintf (pidstr, sizeof pidstr, "%10d\n", (int)getpid() );
619
620 /* Create a temporary file. */
621 if ( uname ( &utsbuf ) )
622 nodename = "unknown";
623 else
624 nodename = utsbuf.nodename;
625
626 if ( !(dirpart = strrchr (file_to_lock, DIRSEP_C)) )
627 {
628 dirpart = EXTSEP_S;
629 dirpartlen = 1;
630 }
631 else
632 {
633 dirpartlen = dirpart - file_to_lock;
634 dirpart = file_to_lock;
635 }
636
637 LOCK_all_lockfiles ();
638 h->next = all_lockfiles;
639 all_lockfiles = h;
640
641 tnamelen = dirpartlen + 6 + 30 + strlen(nodename) + 10 + 1;
642 h->tname = jnlib_malloc (tnamelen + 1);
643 if (!h->tname)
644 {
645 all_lockfiles = h->next;
646 UNLOCK_all_lockfiles ();
647 jnlib_free (h);
648 return NULL;
649 }
650 h->nodename_len = strlen (nodename);
651
652 snprintf (h->tname, tnamelen, "%.*s/.#lk%p.", dirpartlen, dirpart, h );
653 h->nodename_off = strlen (h->tname);
654 snprintf (h->tname+h->nodename_off, tnamelen - h->nodename_off,
655 "%s.%d", nodename, (int)getpid ());
656
657 do
658 {
659 jnlib_set_errno (0);
660 fd = open (h->tname, O_WRONLY|O_CREAT|O_EXCL,
661 S_IRUSR|S_IRGRP|S_IROTH|S_IWUSR );
662 }
663 while (fd == -1 && errno == EINTR);
664
665 if ( fd == -1 )
666 {
667 all_lockfiles = h->next;
668 UNLOCK_all_lockfiles ();
669 my_error_2 (_("failed to create temporary file '%s': %s\n"),
670 h->tname, strerror(errno));
671 jnlib_free (h->tname);
672 jnlib_free (h);
673 return NULL;
674 }
675 if ( write (fd, pidstr, 11 ) != 11 )
676 goto write_failed;
677 if ( write (fd, nodename, strlen (nodename) ) != strlen (nodename) )
678 goto write_failed;
679 if ( write (fd, "\n", 1 ) != 1 )
680 goto write_failed;
681 if ( close (fd) )
682 goto write_failed;
683
684 /* Check whether we support hard links. */
685 switch (use_hardlinks_p (h->tname))
686 {
687 case 0: /* Yes. */
688 break;
689 case 1: /* No. */
690 unlink (h->tname);
691 h->use_o_excl = 1;
692 break;
693 default:
694 my_error_2 ("can't check whether hardlinks are supported for '%s': %s\n",
695 h->tname, strerror(errno));
696 goto write_failed;
697 }
698
699 h->lockname = jnlib_malloc (strlen (file_to_lock) + 6 );
700 if (!h->lockname)
701 {
702 all_lockfiles = h->next;
703 UNLOCK_all_lockfiles ();
704 unlink (h->tname);
705 jnlib_free (h->tname);
706 jnlib_free (h);
707 return NULL;
708 }
709 strcpy (stpcpy (h->lockname, file_to_lock), EXTSEP_S "lock");
710 UNLOCK_all_lockfiles ();
711 if (h->use_o_excl)
712 my_debug_1 ("locking for '%s' done via O_EXCL\n", h->lockname);
713
714 return h;
715
716 write_failed:
717 all_lockfiles = h->next;
718 UNLOCK_all_lockfiles ();
719 my_error_2 (_("error writing to '%s': %s\n"), h->tname, strerror (errno));
720 close (fd);
721 unlink (h->tname);
722 jnlib_free (h->tname);
723 jnlib_free (h);
724 return NULL;
725}
726#endif /*HAVE_POSIX_SYSTEM*/
727
728
729#ifdef HAVE_DOSISH_SYSTEM
730/* Locking core for Windows. This version does not need a temporary
731 file but uses the plain lock file along with record locking. We
732 create this file here so that we later only need to do the file
733 locking. For error reporting it is useful to keep the name of the
734 file in the handle. */
735static dotlock_t
736dotlock_create_w32 (dotlock_t h, const char *file_to_lock)
737{
738 LOCK_all_lockfiles ();
739 h->next = all_lockfiles;
740 all_lockfiles = h;
741
742 h->lockname = jnlib_malloc ( strlen (file_to_lock) + 6 );
743 if (!h->lockname)
744 {
745 all_lockfiles = h->next;
746 UNLOCK_all_lockfiles ();
747 jnlib_free (h);
748 return NULL;
749 }
750 strcpy (stpcpy(h->lockname, file_to_lock), EXTSEP_S "lock");
751
752 /* If would be nice if we would use the FILE_FLAG_DELETE_ON_CLOSE
753 along with FILE_SHARE_DELETE but that does not work due to a race
754 condition: Despite the OPEN_ALWAYS flag CreateFile may return an
755 error and we can't reliable create/open the lock file unless we
756 would wait here until it works - however there are other valid
757 reasons why a lock file can't be created and thus the process
758 would not stop as expected but spin until Windows crashes. Our
759 solution is to keep the lock file open; that does not harm. */
760 {
761#ifdef HAVE_W32CE_SYSTEM
762 wchar_t *wname = utf8_to_wchar (h->lockname);
763
764 if (wname)
765 h->lockhd = CreateFile (wname,
766 GENERIC_READ|GENERIC_WRITE,
767 FILE_SHARE_READ|FILE_SHARE_WRITE,
768 NULL, OPEN_ALWAYS, 0, NULL);
769 else
770 h->lockhd = INVALID_HANDLE_VALUE;
771 jnlib_free (wname);
772#else
773 h->lockhd = CreateFile (h->lockname,
774 GENERIC_READ|GENERIC_WRITE,
775 FILE_SHARE_READ|FILE_SHARE_WRITE,
776 NULL, OPEN_ALWAYS, 0, NULL);
777#endif
778 }
779 if (h->lockhd == INVALID_HANDLE_VALUE)
780 {
781 all_lockfiles = h->next;
782 UNLOCK_all_lockfiles ();
783 my_error_2 (_("can't create '%s': %s\n"), h->lockname, w32_strerror (-1));
784 jnlib_free (h->lockname);
785 jnlib_free (h);
786 return NULL;
787 }
788 return h;
789}
790#endif /*HAVE_DOSISH_SYSTEM*/
791
792
793/* Create a lockfile for a file name FILE_TO_LOCK and returns an
794 object of type dotlock_t which may be used later to actually acquire
795 the lock. A cleanup routine gets installed to cleanup left over
796 locks or other files used internally by the lock mechanism.
797
798 Calling this function with NULL does only install the atexit
799 handler and may thus be used to assure that the cleanup is called
800 after all other atexit handlers.
801
802 This function creates a lock file in the same directory as
803 FILE_TO_LOCK using that name and a suffix of ".lock". Note that on
804 POSIX systems a temporary file ".#lk.<hostname>.pid[.threadid] is
805 used.
806
807 FLAGS must be 0.
808
809 The function returns an new handle which needs to be released using
810 destroy_dotlock but gets also released at the termination of the
811 process. On error NULL is returned.
812 */
813
814dotlock_t
815dotlock_create (const char *file_to_lock, unsigned int flags)
816{
817 static int initialized;
818 dotlock_t h;
819
820 if ( !initialized )
821 {
822 atexit (dotlock_remove_lockfiles);
823 initialized = 1;
824 }
825
826 if ( !file_to_lock )
827 return NULL; /* Only initialization was requested. */
828
829 if (flags)
830 {
831 jnlib_set_errno (EINVAL);
832 return NULL;
833 }
834
835 h = jnlib_calloc (1, sizeof *h);
836 if (!h)
837 return NULL;
838 h->extra_fd = -1;
839
840 if (never_lock)
841 {
842 h->disable = 1;
843 LOCK_all_lockfiles ();
844 h->next = all_lockfiles;
845 all_lockfiles = h;
846 UNLOCK_all_lockfiles ();
847 return h;
848 }
849
850#ifdef HAVE_DOSISH_SYSTEM
851 return dotlock_create_w32 (h, file_to_lock);
852#else /*!HAVE_DOSISH_SYSTEM */
853 return dotlock_create_unix (h, file_to_lock);
854#endif /*!HAVE_DOSISH_SYSTEM*/
855}
856
857
858
859/* Convenience function to store a file descriptor (or any any other
860 integer value) in the context of handle H. */
861void
862dotlock_set_fd (dotlock_t h, int fd)
863{
864 h->extra_fd = fd;
865}
866
867/* Convenience function to retrieve a file descriptor (or any any other
868 integer value) stored in the context of handle H. */
869int
870dotlock_get_fd (dotlock_t h)
871{
872 return h->extra_fd;
873}
874
875
876
877#ifdef HAVE_POSIX_SYSTEM
878/* Unix specific code of destroy_dotlock. */
879static void
880dotlock_destroy_unix (dotlock_t h)
881{
882 if (h->locked && h->lockname)
883 unlink (h->lockname);
884 if (h->tname && !h->use_o_excl)
885 unlink (h->tname);
886 jnlib_free (h->tname);
887}
888#endif /*HAVE_POSIX_SYSTEM*/
889
890
891#ifdef HAVE_DOSISH_SYSTEM
892/* Windows specific code of destroy_dotlock. */
893static void
894dotlock_destroy_w32 (dotlock_t h)
895{
896 if (h->locked)
897 {
898 OVERLAPPED ovl;
899
900 memset (&ovl, 0, sizeof ovl);
901 UnlockFileEx (h->lockhd, 0, 1, 0, &ovl);
902 }
903 CloseHandle (h->lockhd);
904}
905#endif /*HAVE_DOSISH_SYSTEM*/
906
907
908/* Destroy the locck handle H and release the lock. */
909void
910dotlock_destroy (dotlock_t h)
911{
912 dotlock_t hprev, htmp;
913
914 if ( !h )
915 return;
916
917 /* First remove the handle from our global list of all locks. */
918 LOCK_all_lockfiles ();
919 for (hprev=NULL, htmp=all_lockfiles; htmp; hprev=htmp, htmp=htmp->next)
920 if (htmp == h)
921 {
922 if (hprev)
923 hprev->next = htmp->next;
924 else
925 all_lockfiles = htmp->next;
926 h->next = NULL;
927 break;
928 }
929 UNLOCK_all_lockfiles ();
930
931 /* Then destroy the lock. */
932 if (!h->disable)
933 {
934#ifdef HAVE_DOSISH_SYSTEM
935 dotlock_destroy_w32 (h);
936#else /* !HAVE_DOSISH_SYSTEM */
937 dotlock_destroy_unix (h);
938#endif /* HAVE_DOSISH_SYSTEM */
939 jnlib_free (h->lockname);
940 }
941 jnlib_free(h);
942}
943
944
945
946#ifdef HAVE_POSIX_SYSTEM
947/* Unix specific code of make_dotlock. Returns 0 on success and -1 on
948 error. */
949static int
950dotlock_take_unix (dotlock_t h, long timeout)
951{
952 int wtime = 0;
953 int sumtime = 0;
954 int pid;
955 int lastpid = -1;
956 int ownerchanged;
957 const char *maybe_dead="";
958 int same_node;
959
960 again:
961 if (h->use_o_excl)
962 {
963 /* No hardlink support - use open(O_EXCL). */
964 int fd;
965
966 do
967 {
968 jnlib_set_errno (0);
969 fd = open (h->lockname, O_WRONLY|O_CREAT|O_EXCL,
970 S_IRUSR|S_IRGRP|S_IROTH|S_IWUSR );
971 }
972 while (fd == -1 && errno == EINTR);
973
974 if (fd == -1 && errno == EEXIST)
975 ; /* Lock held by another process. */
976 else if (fd == -1)
977 {
978 my_error_2 ("lock not made: open(O_EXCL) of '%s' failed: %s\n",
979 h->lockname, strerror (errno));
980 return -1;
981 }
982 else
983 {
984 char pidstr[16];
985
986 snprintf (pidstr, sizeof pidstr, "%10d\n", (int)getpid());
987 if (write (fd, pidstr, 11 ) == 11
988 && write (fd, h->tname + h->nodename_off,h->nodename_len)
989 == h->nodename_len
990 && write (fd, "\n", 1) == 1
991 && !close (fd))
992 {
993 h->locked = 1;
994 return 0;
995 }
996 /* Write error. */
997 my_error_2 ("lock not made: writing to '%s' failed: %s\n",
998 h->lockname, strerror (errno));
999 close (fd);
1000 unlink (h->lockname);
1001 return -1;
1002 }
1003 }
1004 else /* Standard method: Use hardlinks. */
1005 {
1006 struct stat sb;
1007
1008 /* We ignore the return value of link() because it is unreliable. */
1009 (void) link (h->tname, h->lockname);
1010
1011 if (stat (h->tname, &sb))
1012 {
1013 my_error_1 ("lock not made: Oops: stat of tmp file failed: %s\n",
1014 strerror (errno));
1015 /* In theory this might be a severe error: It is possible
1016 that link succeeded but stat failed due to changed
1017 permissions. We can't do anything about it, though. */
1018 return -1;
1019 }
1020
1021 if (sb.st_nlink == 2)
1022 {
1023 h->locked = 1;
1024 return 0; /* Okay. */
1025 }
1026 }
1027
1028 /* Check for stale lock files. */
1029 if ( (pid = read_lockfile (h, &same_node)) == -1 )
1030 {
1031 if ( errno != ENOENT )
1032 {
1033 my_info_0 ("cannot read lockfile\n");
1034 return -1;
1035 }
1036 my_info_0 ("lockfile disappeared\n");
1037 goto again;
1038 }
1039 else if ( pid == getpid() && same_node )
1040 {
1041 my_info_0 ("Oops: lock already held by us\n");
1042 h->locked = 1;
1043 return 0; /* okay */
1044 }
1045 else if ( same_node && kill (pid, 0) && errno == ESRCH )
1046 {
1047 /* Note: It is unlikley that we get a race here unless a pid is
1048 reused too fast or a new process with the same pid as the one
1049 of the stale file tries to lock right at the same time as we. */
1050 my_info_1 (_("removing stale lockfile (created by %d)\n"), pid);
1051 unlink (h->lockname);
1052 goto again;
1053 }
1054
1055 if (lastpid == -1)
1056 lastpid = pid;
1057 ownerchanged = (pid != lastpid);
1058
1059 if (timeout)
1060 {
1061 struct timeval tv;
1062
1063 /* Wait until lock has been released. We use increasing retry
1064 intervals of 50ms, 100ms, 200ms, 400ms, 800ms, 2s, 4s and 8s
1065 but reset it if the lock owner meanwhile changed. */
1066 if (!wtime || ownerchanged)
1067 wtime = 50;
1068 else if (wtime < 800)
1069 wtime *= 2;
1070 else if (wtime == 800)
1071 wtime = 2000;
1072 else if (wtime < 8000)
1073 wtime *= 2;
1074
1075 if (timeout > 0)
1076 {
1077 if (wtime > timeout)
1078 wtime = timeout;
1079 timeout -= wtime;
1080 }
1081
1082 sumtime += wtime;
1083 if (sumtime >= 1500)
1084 {
1085 sumtime = 0;
1086 my_info_3 (_("waiting for lock (held by %d%s) %s...\n"),
1087 pid, maybe_dead, maybe_deadlock(h)? _("(deadlock?) "):"");
1088 }
1089
1090
1091 tv.tv_sec = wtime / 1000;
1092 tv.tv_usec = (wtime % 1000) * 1000;
1093 select (0, NULL, NULL, NULL, &tv);
1094 goto again;
1095 }
1096
1097 jnlib_set_errno (EACCES);
1098 return -1;
1099}
1100#endif /*HAVE_POSIX_SYSTEM*/
1101
1102
1103#ifdef HAVE_DOSISH_SYSTEM
1104/* Windows specific code of make_dotlock. Returns 0 on success and -1 on
1105 error. */
1106static int
1107dotlock_take_w32 (dotlock_t h, long timeout)
1108{
1109 int wtime = 0;
1110 int w32err;
1111 OVERLAPPED ovl;
1112
1113 again:
1114 /* Lock one byte at offset 0. The offset is given by OVL. */
1115 memset (&ovl, 0, sizeof ovl);
1116 if (LockFileEx (h->lockhd, (LOCKFILE_EXCLUSIVE_LOCK
1117 | LOCKFILE_FAIL_IMMEDIATELY), 0, 1, 0, &ovl))
1118 {
1119 h->locked = 1;
1120 return 0; /* okay */
1121 }
1122
1123 w32err = GetLastError ();
1124 if (w32err != ERROR_LOCK_VIOLATION)
1125 {
1126 my_error_2 (_("lock '%s' not made: %s\n"),
1127 h->lockname, w32_strerror (w32err));
1128 return -1;
1129 }
1130
1131 if (timeout)
1132 {
1133 /* Wait until lock has been released. We use retry intervals of
1134 50ms, 100ms, 200ms, 400ms, 800ms, 2s, 4s and 8s. */
1135 if (!wtime)
1136 wtime = 50;
1137 else if (wtime < 800)
1138 wtime *= 2;
1139 else if (wtime == 800)
1140 wtime = 2000;
1141 else if (wtime < 8000)
1142 wtime *= 2;
1143
1144 if (timeout > 0)
1145 {
1146 if (wtime > timeout)
1147 wtime = timeout;
1148 timeout -= wtime;
1149 }
1150
1151 if (wtime >= 800)
1152 my_info_1 (_("waiting for lock %s...\n"), h->lockname);
1153
1154 Sleep (wtime);
1155 goto again;
1156 }
1157
1158 return -1;
1159}
1160#endif /*HAVE_DOSISH_SYSTEM*/
1161
1162
1163/* Take a lock on H. A value of 0 for TIMEOUT returns immediately if
1164 the lock can't be taked, -1 waits forever (hopefully not), other
1165 values wait for TIMEOUT milliseconds. Returns: 0 on success */
1166int
1167dotlock_take (dotlock_t h, long timeout)
1168{
1169 int ret;
1170
1171 if ( h->disable )
1172 return 0; /* Locks are completely disabled. Return success. */
1173
1174 if ( h->locked )
1175 {
1176 my_debug_1 ("Oops, '%s' is already locked\n", h->lockname);
1177 return 0;
1178 }
1179
1180#ifdef HAVE_DOSISH_SYSTEM
1181 ret = dotlock_take_w32 (h, timeout);
1182#else /*!HAVE_DOSISH_SYSTEM*/
1183 ret = dotlock_take_unix (h, timeout);
1184#endif /*!HAVE_DOSISH_SYSTEM*/
1185
1186 return ret;
1187}
1188
1189
1190
1191#ifdef HAVE_POSIX_SYSTEM
1192/* Unix specific code of release_dotlock. */
1193static int
1194dotlock_release_unix (dotlock_t h)
1195{
1196 int pid, same_node;
1197
1198 pid = read_lockfile (h, &same_node);
1199 if ( pid == -1 )
1200 {
1201 my_error_0 ("release_dotlock: lockfile error\n");
1202 return -1;
1203 }
1204 if ( pid != getpid() || !same_node )
1205 {
1206 my_error_1 ("release_dotlock: not our lock (pid=%d)\n", pid);
1207 return -1;
1208 }
1209
1210 if ( unlink( h->lockname ) )
1211 {
1212 my_error_1 ("release_dotlock: error removing lockfile '%s'\n",
1213 h->lockname);
1214 return -1;
1215 }
1216 /* Fixme: As an extra check we could check whether the link count is
1217 now really at 1. */
1218 return 0;
1219}
1220#endif /*HAVE_POSIX_SYSTEM */
1221
1222
1223#ifdef HAVE_DOSISH_SYSTEM
1224/* Windows specific code of release_dotlock. */
1225static int
1226dotlock_release_w32 (dotlock_t h)
1227{
1228 OVERLAPPED ovl;
1229
1230 memset (&ovl, 0, sizeof ovl);
1231 if (!UnlockFileEx (h->lockhd, 0, 1, 0, &ovl))
1232 {
1233 my_error_2 ("release_dotlock: error removing lockfile '%s': %s\n",
1234 h->lockname, w32_strerror (-1));
1235 return -1;
1236 }
1237
1238 return 0;
1239}
1240#endif /*HAVE_DOSISH_SYSTEM */
1241
1242
1243/* Release a lock. Returns 0 on success. */
1244int
1245dotlock_release (dotlock_t h)
1246{
1247 int ret;
1248
1249 /* To avoid atexit race conditions we first check whether there are
1250 any locks left. It might happen that another atexit handler
1251 tries to release the lock while the atexit handler of this module
1252 already ran and thus H is undefined. */
1253 LOCK_all_lockfiles ();
1254 ret = !all_lockfiles;
1255 UNLOCK_all_lockfiles ();
1256 if (ret)
1257 return 0;
1258
1259 if ( h->disable )
1260 return 0;
1261
1262 if ( !h->locked )
1263 {
1264 my_debug_1 ("Oops, '%s' is not locked\n", h->lockname);
1265 return 0;
1266 }
1267
1268#ifdef HAVE_DOSISH_SYSTEM
1269 ret = dotlock_release_w32 (h);
1270#else
1271 ret = dotlock_release_unix (h);
1272#endif
1273
1274 if (!ret)
1275 h->locked = 0;
1276 return ret;
1277}
1278
1279
1280
1281/* Remove all lockfiles. This is called by the atexit handler
1282 installed by this module but may also be called by other
1283 termination handlers. */
1284void
1285dotlock_remove_lockfiles (void)
1286{
1287 dotlock_t h, h2;
1288
1289 /* First set the lockfiles list to NULL so that for example
1290 dotlock_release is ware that this fucntion is currently
1291 running. */
1292 LOCK_all_lockfiles ();
1293 h = all_lockfiles;
1294 all_lockfiles = NULL;
1295 UNLOCK_all_lockfiles ();
1296
1297 while ( h )
1298 {
1299 h2 = h->next;
1300 dotlock_destroy (h);
1301 h = h2;
1302 }
1303}
diff --git a/lib/dotlock.h b/lib/dotlock.h
new file mode 100644
index 0000000..3fb9bcb
--- /dev/null
+++ b/lib/dotlock.h
@@ -0,0 +1,112 @@
1/* dotlock.h - dotfile locking declarations
2 * Copyright (C) 2000, 2001, 2006, 2011 Free Software Foundation, Inc.
3 *
4 * This file is part of JNLIB, which is a subsystem of GnuPG.
5 *
6 * JNLIB is free software; you can redistribute it and/or modify it
7 * under the terms of either
8 *
9 * - the GNU Lesser General Public License as published by the Free
10 * Software Foundation; either version 3 of the License, or (at
11 * your option) any later version.
12 *
13 * or
14 *
15 * - the GNU General Public License as published by the Free
16 * Software Foundation; either version 2 of the License, or (at
17 * your option) any later version.
18 *
19 * or both in parallel, as here.
20 *
21 * JNLIB is distributed in the hope that it will be useful, but
22 * WITHOUT ANY WARRANTY; without even the implied warranty of
23 * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
24 * General Public License for more details.
25 *
26 * You should have received a copies of the GNU General Public License
27 * and the GNU Lesser General Public License along with this program;
28 * if not, see <http://www.gnu.org/licenses/>.
29 *
30 * ALTERNATIVELY, this file may be distributed under the terms of the
31 * following license, in which case the provisions of this license are
32 * required INSTEAD OF the GNU Lesser General License or the GNU
33 * General Public License. If you wish to allow use of your version of
34 * this file only under the terms of the GNU Lesser General License or
35 * the GNU General Public License, and not to allow others to use your
36 * version of this file under the terms of the following license,
37 * indicate your decision by deleting this paragraph and the license
38 * below.
39 *
40 * Redistribution and use in source and binary forms, with or without
41 * modification, are permitted provided that the following conditions
42 * are met:
43 *
44 * 1. Redistributions of source code must retain the above copyright
45 * notice, and the entire permission notice in its entirety,
46 * including the disclaimer of warranties.
47 * 2. Redistributions in binary form must reproduce the above copyright
48 * notice, this list of conditions and the following disclaimer in the
49 * documentation and/or other materials provided with the distribution.
50 * 3. The name of the author may not be used to endorse or promote
51 * products derived from this software without specific prior
52 * written permission.
53 *
54 * THIS SOFTWARE IS PROVIDED "AS IS" AND ANY EXPRESS OR IMPLIED
55 * WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES
56 * OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE
57 * DISCLAIMED. IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR ANY DIRECT,
58 * INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES
59 * (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR
60 * SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
61 * HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT,
62 * STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE)
63 * ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED
64 * OF THE POSSIBILITY OF SUCH DAMAGE.
65 */
66
67#ifndef LIBJNLIB_DOTLOCK_H
68#define LIBJNLIB_DOTLOCK_H
69
70/* See dotlock.c for a description. */
71
72#ifdef DOTLOCK_EXT_SYM_PREFIX
73# ifndef _DOTLOCK_PREFIX
74# define _DOTLOCK_PREFIX1(x,y) x ## y
75# define _DOTLOCK_PREFIX2(x,y) _DOTLOCK_PREFIX1(x,y)
76# define _DOTLOCK_PREFIX(x) _DOTLOCK_PREFIX2(DOTLOCK_EXT_SYM_PREFIX,x)
77# endif /*_DOTLOCK_PREFIX*/
78# define dotlock_disable _DOTLOCK_PREFIX(dotlock_disable)
79# define dotlock_create _DOTLOCK_PREFIX(dotlock_create)
80# define dotlock_set_fd _DOTLOCK_PREFIX(dotlock_set_fd)
81# define dotlock_get_fd _DOTLOCK_PREFIX(dotlock_get_fd)
82# define dotlock_destroy _DOTLOCK_PREFIX(dotlock_destroy)
83# define dotlock_take _DOTLOCK_PREFIX(dotlock_take)
84# define dotlock_release _DOTLOCK_PREFIX(dotlock_release)
85# define dotlock_remove_lockfiles _DOTLOCK_PREFIX(dotlock_remove_lockfiles)
86#endif /*DOTLOCK_EXT_SYM_PREFIX*/
87
88#ifdef __cplusplus
89extern "C"
90{
91#if 0
92}
93#endif
94#endif
95
96
97struct dotlock_handle;
98typedef struct dotlock_handle *dotlock_t;
99
100void dotlock_disable (void);
101dotlock_t dotlock_create (const char *file_to_lock, unsigned int flags);
102void dotlock_set_fd (dotlock_t h, int fd);
103int dotlock_get_fd (dotlock_t h);
104void dotlock_destroy (dotlock_t h);
105int dotlock_take (dotlock_t h, long timeout);
106int dotlock_release (dotlock_t h);
107void dotlock_remove_lockfiles (void);
108
109#ifdef __cplusplus
110}
111#endif
112#endif /*LIBJNLIB_DOTLOCK_H*/