summaryrefslogtreecommitdiff
path: root/KnownHosts.hs
blob: e04ad907cbfb9382746f30fdd9e5db7e0c758053 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
{-# LANGUAGE OverloadedStrings #-}
module KnownHosts where

import qualified Data.ByteString.Lazy.Char8 as L
import Data.Char
import Data.List
import qualified SSHKey as SSH

data KnownHostsEntry = KnownHostsEntry
    { eLineno :: Int
    , eSp :: [L.ByteString]
    , eComment :: L.ByteString
    , eKeyBlob :: L.ByteString
    , eKey :: Maybe SSH.Key
    , eKeyHeader :: L.ByteString
    , eHosts :: [L.ByteString]
    }
 deriving (Eq,Show)

serializeLine :: KnownHostsEntry -> L.ByteString
serializeLine (KnownHostsEntry { eSp = sp
                               , eComment = comment
                               , eKeyHeader = hdr
                               , eKeyBlob = blob
                               , eKey = _
                               , eHosts = hosts
                               })
    = L.concat $ zipWith L.append [host,hdr,blob] (take 3 sp) ++ [comment]
    -- = L.concat $ zipWith L.append [host,hdr,keyblob] (take 3 sp) ++ [comment]
 where
    host = L.intercalate "," hosts
    -- keyblob = L.dropWhile isSpace $ L.dropWhile (not . isSpace) $ SSH.keyblob key
    

parseLine :: Int -> L.ByteString -> KnownHostsEntry
parseLine num str = KnownHostsEntry
    { eLineno = num
    , eSp = sp
    , eComment = comment
    , eKeyHeader = hdr
    , eKeyBlob = blob
    , eKey = key
    , eHosts = hosts
    }
 where
    gs = L.groupBy (\a b -> isSpace a==isSpace b) str
    (sp,ns) = partition (\x -> isSpace (L.head x)) gs
    hosts = do
        h <- take 1 ns
        let hs = L.groupBy (\_ b -> b/=',') h
            hs' = map L.tail $ drop 1 hs
        h0 <- take 1 hs
        h0 : hs'
    hdr = L.concat $ take 1 (drop 1 ns)
    blob = L.concat $ take 1 (drop 2 ns)
    key = SSH.blobkey $ L.concat $ hdr:" ":blob:[]
    comment = L.concat $ zipWith L.append (drop 3 ns) (drop 3 sp ++ repeat "")

data KnownHosts = KnownHosts
    { khcount :: Int
    , khentries :: [KnownHostsEntry]
    }

decode :: L.ByteString -> KnownHosts
decode input = renum $ foldr grok (KnownHosts 0 []) ls
 where
    ls = L.lines input
    grok x (KnownHosts cnt es) =
        KnownHosts (cnt+1) (parseLine 0 x:es)
    renum kh = kh { khentries = zipWith setnum [1..] (khentries kh) }
        where setnum n e = e { eLineno=n }

encode :: KnownHosts -> L.ByteString
encode kh = L.unlines $ map serializeLine (khentries kh)