module Network.XmlRpc.Client
(
remote, remoteWithHeaders,
call, callWithHeaders,
Remote
) where
import Network.XmlRpc.Internals
import Data.Functor ((<$>))
import Data.Maybe
import Data.Int
import Network.URI
import Text.Read.Compat (readMaybe)
import Network.Http.Client (Method (..), Request,
baselineContextSSL, buildRequest,
closeConnection, getStatusCode,
getStatusMessage, http, openConnection,
inputStreamBody, openConnectionSSL,
receiveResponse, sendRequest,
setAuthorizationBasic,
setContentType, setContentLength, setHeader)
import OpenSSL
import qualified System.IO.Streams as Streams
import qualified Data.ByteString.Char8 as BS
import qualified Data.ByteString.Lazy.Char8 as BSL (ByteString, fromChunks,
unpack, length)
import qualified Data.ByteString.Lazy.UTF8 as U
handleResponse :: Monad m => MethodResponse -> m Value
handleResponse (Return v) = return v
handleResponse (Fault code str) = fail ("Error " ++ show code ++ ": " ++ str)
type HeadersAList = [(BS.ByteString, BS.ByteString)]
doCall :: String -> HeadersAList -> MethodCall -> Err IO MethodResponse
doCall url headers mc =
do
let req = renderCall mc
resp <- ioErrorToErr $ post url headers req
parseResponse (BSL.unpack resp)
call :: String
-> String
-> [Value]
-> Err IO Value
call url method args = doCall url [] (MethodCall method args) >>= handleResponse
callWithHeaders :: String
-> String
-> HeadersAList
-> [Value]
-> Err IO Value
callWithHeaders url method headers args =
doCall url headers (MethodCall method args) >>= handleResponse
remote :: Remote a =>
String
-> String
-> a
remote u m = remote_ (\e -> "Error calling " ++ m ++ ": " ++ e) (call u m)
remoteWithHeaders :: Remote a =>
String
-> String
-> HeadersAList
-> a
remoteWithHeaders u m headers =
remote_ (\e -> "Error calling " ++ m ++ ": " ++ e)
(callWithHeaders u m headers)
class Remote a where
remote_ :: (String -> String)
-> ([Value] -> Err IO Value)
-> a
instance XmlRpcType a => Remote (IO a) where
remote_ h f = handleError (fail . h) $ f [] >>= fromValue
instance (XmlRpcType a, Remote b) => Remote (a -> b) where
remote_ h f x = remote_ h (\xs -> f (toValue x:xs))
userAgent :: BS.ByteString
userAgent = "Haskell XmlRpcClient/0.1"
post :: String -> HeadersAList -> BSL.ByteString -> IO U.ByteString
post url headers content = do
uri <- maybeFail ("Bad URI: '" ++ url ++ "'") (parseURI url)
let a = uriAuthority uri
auth <- maybeFail ("Bad URI authority: '" ++ show (fmap showAuth a) ++ "'") a
post_ uri auth headers content
where showAuth (URIAuth u r p) = "URIAuth "++u++" "++r++" "++p
post_ :: URI -> URIAuth -> HeadersAList -> BSL.ByteString -> IO U.ByteString
post_ uri auth headers content = withOpenSSL $ do
let hostname = BS.pack (uriRegName auth)
port base = fromMaybe base (readMaybe $ drop 1 $ uriPort auth)
c <- case init $ uriScheme uri of
"http" ->
openConnection hostname (port 80)
"https" -> do
ctx <- baselineContextSSL
openConnectionSSL ctx hostname (port 443)
x -> fail ("Unknown scheme: '" ++ x ++ "'!")
req <- request uri auth headers (BSL.length content)
body <- inputStreamBody <$> Streams.fromLazyByteString content
_ <- sendRequest c req body
s <- receiveResponse c $ \resp i -> do
case getStatusCode resp of
200 -> readLazyByteString i
_ -> fail (show (getStatusCode resp) ++ " " ++ BS.unpack (getStatusMessage resp))
closeConnection c
return s
readLazyByteString :: Streams.InputStream BS.ByteString -> IO U.ByteString
readLazyByteString i = BSL.fromChunks <$> go
where
go :: IO [BS.ByteString]
go = do
res <- Streams.read i
case res of
Nothing -> return []
Just bs -> (bs:) <$> go
request :: URI -> URIAuth -> [(BS.ByteString, BS.ByteString)] -> Int64 -> IO Request
request uri auth usrHeaders len = buildRequest $ do
http POST (BS.pack $ uriPath uri)
setContentType "text/xml"
setContentLength len
case parseUserInfo auth of
(Just user, Just pass) -> setAuthorizationBasic (BS.pack user) (BS.pack pass)
_ -> return ()
mapM_ (uncurry setHeader) usrHeaders
setHeader "User-Agent" userAgent
where
parseUserInfo info = let (u,pw) = break (==':') $ uriUserInfo info
in ( if null u then Nothing else Just u
, if null pw then Nothing else Just $ dropAtEnd $ tail pw )
maybeFail :: Monad m => String -> Maybe a -> m a
maybeFail msg = maybe (fail msg) return
dropAtEnd :: String -> String
dropAtEnd l = take (length l 1) l