module Ganeti.Confd.Utils
( getClusterHmac
, parseSignedMessage
, parseRequest
, parseReply
, signMessage
, getCurrentTime
, extractJSONPath
) where
import qualified Data.Attoparsec.Text as P
import Prelude ()
import Ganeti.Prelude
import qualified Data.ByteString as B
import Data.Text (pack)
import qualified Text.JSON as J
import Ganeti.BasicTypes
import Ganeti.Confd.Types
import Ganeti.Hash
import qualified Ganeti.Constants as C
import qualified Ganeti.Path as Path
import Ganeti.JSON
import Ganeti.Utils
maxClockSkew :: Integer
maxClockSkew = fromIntegral C.confdMaxClockSkew
getClusterHmac :: IO HashKey
getClusterHmac = Path.confdHmacKey >>= fmap B.unpack . B.readFile
parseSignedMessage :: (J.JSON a) => HashKey -> String
-> Result (String, String, a)
parseSignedMessage key str = do
(SignedMessage hmac msg salt) <- fromJResult "parsing signed message"
$ J.decode str
parsedMsg <- if verifyMac key (Just salt) msg hmac
then fromJResult "parsing message" $ J.decode msg
else Bad "HMAC verification failed"
return (salt, msg, parsedMsg)
parseRequest :: HashKey -> String -> Integer
-> Result (String, ConfdRequest)
parseRequest hmac msg curtime = do
(salt, origmsg, request) <- parseSignedMessage hmac msg
ts <- tryRead "Parsing timestamp" salt::Result Integer
if abs (ts curtime) > maxClockSkew
then fail "Too old/too new timestamp or clock skew"
else return (origmsg, request)
parseReply :: HashKey -> String -> String -> Result (String, ConfdReply)
parseReply hmac msg expSalt = do
(salt, origmsg, reply) <- parseSignedMessage hmac msg
if salt /= expSalt
then fail "The received salt differs from the expected salt"
else return (origmsg, reply)
signMessage :: HashKey -> String -> String -> SignedMessage
signMessage key salt msg =
SignedMessage { signedMsgMsg = msg
, signedMsgSalt = salt
, signedMsgHmac = hmac
}
where hmac = computeMac key (Just salt) msg
data Pointer = Pointer [String]
deriving (Show, Eq)
readInteger :: String -> J.Result Int
readInteger = either J.Error J.Ok . P.parseOnly P.decimal . pack
pointerFromString :: String -> J.Result Pointer
pointerFromString s =
either J.Error J.Ok . P.parseOnly parser $ pack s
where
parser = do
_ <- P.char '/'
tokens <- token `P.sepBy1` P.char '/'
return $ Pointer tokens
token =
P.choice [P.many1 (P.choice [ escaped
, P.satisfy $ P.notInClass "~/"])
, P.endOfInput *> return ""]
escaped = P.choice [escapedSlash, escapedTilde]
escapedSlash = P.string (pack "~1") *> return '/'
escapedTilde = P.string (pack "~0") *> return '~'
extractValue :: J.JSON a => Pointer -> a -> J.Result J.JSValue
extractValue (Pointer l) json =
getJSValue l $ J.showJSON json
where
indexWithString x (J.JSObject object) = J.valFromObj x object
indexWithString x (J.JSArray list) = do
i <- readInteger x
if 0 <= i && i < length list
then return $ list !! i
else J.Error ("list index " ++ show i ++ " out of bounds")
indexWithString _ _ = J.Error "Atomic value was indexed"
getJSValue :: [String] -> J.JSValue -> J.Result J.JSValue
getJSValue [] js = J.Ok js
getJSValue (x:xs) js = do
value <- indexWithString x js
getJSValue xs value
extractJSONPath :: J.JSON a => String -> a -> J.Result J.JSValue
extractJSONPath path obj = do
pointer <- pointerFromString path
extractValue pointer obj