module Network.XmlRpc.Internals (
MethodCall(..), MethodResponse(..),
Value(..), Type(..), XmlRpcType(..),
parseResponse, parseCall, getField, getFieldMaybe,
renderCall, renderResponse,
toXRValue, fromXRValue,
toXRMethodCall, fromXRMethodCall,
toXRMethodResponse, fromXRMethodResponse,
toXRParams, fromXRParams,
toXRMember, fromXRMember,
Err, maybeToM, handleError, ioErrorToErr
) where
import Control.Exception
import Control.Monad
import Control.Monad.Except
import Data.Char
import Data.List
import Data.Maybe
import Data.Time.Calendar
import Data.Time.Calendar.OrdinalDate (toOrdinalDate)
import Data.Time.Calendar.WeekDate (toWeekDate)
import Data.Time.Format
import Data.Time.LocalTime
import Numeric (showFFloat)
import Prelude hiding (showString, catch)
import System.IO.Unsafe (unsafePerformIO)
import System.Time (CalendarTime(..))
#if ! MIN_VERSION_time(1,5,0)
import System.Locale (defaultTimeLocale)
#endif
import Data.Text (Text)
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as BS (ByteString, pack, unpack)
import qualified Data.ByteString.Lazy.Char8 as BSL (ByteString, pack)
import qualified Network.XmlRpc.Base64 as Base64
import qualified Network.XmlRpc.DTD_XMLRPC as XR
import Network.XmlRpc.Pretty
import Text.XML.HaXml.XmlContent
replace :: Eq a =>
[a]
-> [a]
-> [a]
-> [a]
replace [] _ xs = xs
replace _ _ [] = []
replace ys zs xs@(x:xs')
| isPrefixOf ys xs = zs ++ replace ys zs (drop (length ys) xs)
| otherwise = x : replace ys zs xs'
maybeToM :: Monad m =>
String
-> Maybe a
-> m a
maybeToM err Nothing = fail err
maybeToM _ (Just x) = return x
eitherToM :: Monad m
=> String
-> Either String a
-> m a
eitherToM err (Left s) = fail (err ++ ": " ++ s)
eitherToM _ (Right x) = return x
xmlRpcDateFormat :: String
xmlRpcDateFormat = "%Y%m%dT%H:%M:%S"
type Err m a = ExceptT String m a
errorToErr :: (Show e, MonadError e m) => a -> Err m a
errorToErr x = unsafePerformIO (liftM return (evaluate x) `catch` handleErr)
where handleErr :: Monad m => SomeException -> IO (Err m a)
handleErr = return . throwError . show
ioErrorToErr :: IO a -> Err IO a
ioErrorToErr x = (liftIO x >>= return) `catchError` \e -> throwError (show e)
handleError :: Monad m => (String -> m a) -> Err m a -> m a
handleError h m = do
Right x <- runExceptT (catchError m (lift . h))
return x
errorRead :: (Monad m, Read a) =>
ReadS a
-> String
-> String
-> Err m a
errorRead r err s = case [x | (x,t) <- r s, ("","") <- lex t] of
[x] -> return x
_ -> fail (err ++ ": '" ++ s ++ "'")
data MethodCall = MethodCall String [Value]
deriving (Eq, Show)
data MethodResponse = Return Value
| Fault Int String
deriving (Eq, Show)
data Value =
ValueInt Int
| ValueBool Bool
| ValueString String
| ValueUnwrapped String
| ValueDouble Double
| ValueDateTime LocalTime
| ValueBase64 BS.ByteString
| ValueStruct [(String,Value)]
| ValueArray [Value]
deriving (Eq, Show)
data Type =
TInt
| TBool
| TString
| TDouble
| TDateTime
| TBase64
| TStruct
| TArray
| TUnknown
deriving (Eq)
instance Show Type where
show TInt = "int"
show TBool = "bool"
show TString = "string"
show TDouble = "double"
show TDateTime = "dateTime.iso8601"
show TBase64 = "base64"
show TStruct = "struct"
show TArray = "array"
show TUnknown = "unknown"
instance Read Type where
readsPrec _ s = case break isSpace (dropWhile isSpace s) of
("int",r) -> [(TInt,r)]
("bool",r) -> [(TBool,r)]
("string",r) -> [(TString,r)]
("double",r) -> [(TDouble,r)]
("dateTime.iso8601",r) -> [(TDateTime,r)]
("base64",r) -> [(TBase64,r)]
("struct",r) -> [(TStruct,r)]
("array",r) -> [(TArray,r)]
structGetValue :: Monad m => String -> Value -> Err m Value
structGetValue n (ValueStruct t) =
maybeToM ("Unknown member '" ++ n ++ "'") (lookup n t)
structGetValue _ _ = fail "Value is not a struct"
faultStruct :: Int -> String -> Value
faultStruct code str = ValueStruct [("faultCode",ValueInt code),
("faultString",ValueString str)]
onlyOneResult :: Monad m => [Value] -> Err m Value
onlyOneResult [] = fail "Method returned no result"
onlyOneResult [x] = return x
onlyOneResult _ = fail "Method returned more than one result"
class XmlRpcType a where
toValue :: a -> Value
fromValue :: Monad m => Value -> Err m a
getType :: a -> Type
typeError :: (XmlRpcType a, Monad m) => Value -> Err m a
typeError v = withType $ \t ->
fail ("Wanted: "
++ show (getType t)
++ "', got: '"
++ showXml False (toXRValue v) ++ "'") `asTypeOf` return t
withType :: (a -> Err m a) -> Err m a
withType f = f undefined
simpleFromValue :: (Monad m, XmlRpcType a) => (Value -> Maybe a)
-> Value -> Err m a
simpleFromValue f v =
maybe (typeError v) return (f v)
instance XmlRpcType Value where
toValue = id
fromValue = return . id
getType _ = TUnknown
instance XmlRpcType Int where
toValue = ValueInt
fromValue = simpleFromValue f
where f (ValueInt x) = Just x
f _ = Nothing
getType _ = TInt
instance XmlRpcType Bool where
toValue = ValueBool
fromValue = simpleFromValue f
where f (ValueBool x) = Just x
f _ = Nothing
getType _ = TBool
instance XmlRpcType String where
toValue = ValueString
fromValue = simpleFromValue f
where f (ValueString x) = Just x
f (ValueUnwrapped x) = Just x
f _ = Nothing
getType _ = TString
instance XmlRpcType Text where
toValue = ValueString . T.unpack
fromValue = (liftM T.pack) . fromValue
getType _ = TString
instance XmlRpcType BS.ByteString where
toValue = ValueBase64
fromValue = simpleFromValue f
where f (ValueBase64 x) = Just x
f _ = Nothing
getType _ = TBase64
instance XmlRpcType Double where
toValue = ValueDouble
fromValue = simpleFromValue f
where f (ValueDouble x) = Just x
f _ = Nothing
getType _ = TDouble
instance XmlRpcType LocalTime where
toValue = ValueDateTime
fromValue = simpleFromValue f
where f (ValueDateTime x) = Just x
f _ = Nothing
getType _ = TDateTime
instance XmlRpcType CalendarTime where
toValue = toValue . calendarTimeToLocalTime
fromValue = liftM localTimeToCalendarTime . fromValue
getType _ = TDateTime
instance XmlRpcType a => XmlRpcType [a] where
toValue = ValueArray . map toValue
fromValue v = case v of
ValueArray xs -> mapM fromValue xs
_ -> typeError v
getType _ = TArray
instance XmlRpcType a => XmlRpcType [(String,a)] where
toValue xs = ValueStruct [(n, toValue v) | (n,v) <- xs]
fromValue v = case v of
ValueStruct xs -> mapM (\ (n,v') -> liftM ((,) n) (fromValue v')) xs
_ -> typeError v
getType _ = TStruct
instance (XmlRpcType a, XmlRpcType b, XmlRpcType c, XmlRpcType d,
XmlRpcType e) =>
XmlRpcType (a,b,c,d,e) where
toValue (v,w,x,y,z) =
ValueArray [toValue v, toValue w, toValue x, toValue y, toValue z]
fromValue (ValueArray [v,w,x,y,z]) =
liftM5 (,,,,) (fromValue v) (fromValue w) (fromValue x)
(fromValue y) (fromValue z)
fromValue _ = throwError "Expected 5-element tuple!"
getType _ = TArray
instance (XmlRpcType a, XmlRpcType b, XmlRpcType c, XmlRpcType d) =>
XmlRpcType (a,b,c,d) where
toValue (w,x,y,z) = ValueArray [toValue w, toValue x, toValue y, toValue z]
fromValue (ValueArray [w,x,y,z]) =
liftM4 (,,,) (fromValue w) (fromValue x) (fromValue y) (fromValue z)
fromValue _ = throwError "Expected 4-element tuple!"
getType _ = TArray
instance (XmlRpcType a, XmlRpcType b, XmlRpcType c) => XmlRpcType (a,b,c) where
toValue (x,y,z) = ValueArray [toValue x, toValue y, toValue z]
fromValue (ValueArray [x,y,z]) =
liftM3 (,,) (fromValue x) (fromValue y) (fromValue z)
fromValue _ = throwError "Expected 3-element tuple!"
getType _ = TArray
instance (XmlRpcType a, XmlRpcType b) => XmlRpcType (a,b) where
toValue (x,y) = ValueArray [toValue x, toValue y]
fromValue (ValueArray [x,y]) = liftM2 (,) (fromValue x) (fromValue y)
fromValue _ = throwError "Expected 2-element tuple."
getType _ = TArray
getField :: (Monad m, XmlRpcType a) =>
String
-> [(String,Value)]
-> Err m a
getField x xs = maybeToM ("struct member " ++ show x ++ " not found")
(lookup x xs) >>= fromValue
getFieldMaybe :: (Monad m, XmlRpcType a) =>
String
-> [(String,Value)]
-> Err m (Maybe a)
getFieldMaybe x xs = case lookup x xs of
Nothing -> return Nothing
Just v -> liftM Just (fromValue v)
toXRValue :: Value -> XR.Value
toXRValue (ValueInt x) = XR.Value [XR.Value_AInt (XR.AInt (showInt x))]
toXRValue (ValueBool b) = XR.Value [XR.Value_Boolean (XR.Boolean (showBool b))]
toXRValue (ValueString s) = XR.Value [XR.Value_AString (XR.AString (showString s))]
toXRValue (ValueUnwrapped s) = XR.Value [XR.Value_Str s]
toXRValue (ValueDouble d) = XR.Value [XR.Value_ADouble (XR.ADouble (showDouble d))]
toXRValue (ValueDateTime t) =
XR.Value [ XR.Value_DateTime_iso8601 (XR.DateTime_iso8601 (showDateTime t))]
toXRValue (ValueBase64 s) = XR.Value [XR.Value_Base64 (XR.Base64 (showBase64 s))]
toXRValue (ValueStruct xs) = XR.Value [XR.Value_Struct (XR.Struct (map toXRMember xs))]
toXRValue (ValueArray xs) =
XR.Value [XR.Value_Array (XR.Array (XR.Data (map toXRValue xs)))]
showInt :: Int -> String
showInt = show
showBool :: Bool -> String
showBool b = if b then "1" else "0"
showString :: String -> String
showString = replace ">" ">" . replace "<" "<" . replace "&" "&"
showDouble :: Double -> String
showDouble d = showFFloat Nothing d ""
showDateTime :: LocalTime -> String
showDateTime t = formatTime defaultTimeLocale xmlRpcDateFormat t
showBase64 :: BS.ByteString -> String
showBase64 = BS.unpack . Base64.encode
toXRMethodCall :: MethodCall -> XR.MethodCall
toXRMethodCall (MethodCall name vs) =
XR.MethodCall (XR.MethodName name) (Just (toXRParams vs))
toXRMethodResponse :: MethodResponse -> XR.MethodResponse
toXRMethodResponse (Return val) = XR.MethodResponseParams (toXRParams [val])
toXRMethodResponse (Fault code str) =
XR.MethodResponseFault (XR.Fault (toXRValue (faultStruct code str)))
toXRParams :: [Value] -> XR.Params
toXRParams vs = XR.Params (map (XR.Param . toXRValue) vs)
toXRMember :: (String, Value) -> XR.Member
toXRMember (n, v) = XR.Member (XR.Name n) (toXRValue v)
fromXRValue :: Monad m => XR.Value -> Err m Value
fromXRValue (XR.Value vs)
= case (filter notstr vs) of
[] -> liftM (ValueUnwrapped . concat) (mapM (readString . unstr) vs)
(v:_) -> f v
where
notstr (XR.Value_Str _) = False
notstr _ = True
unstr (XR.Value_Str x) = x
f (XR.Value_I4 (XR.I4 x)) = liftM ValueInt (readInt x)
f (XR.Value_I8 (XR.I8 x)) = liftM ValueInt (readInt x)
f (XR.Value_AInt (XR.AInt x)) = liftM ValueInt (readInt x)
f (XR.Value_Boolean (XR.Boolean x)) = liftM ValueBool (readBool x)
f (XR.Value_ADouble (XR.ADouble x)) = liftM ValueDouble (readDouble x)
f (XR.Value_AString (XR.AString x)) = liftM ValueString (readString x)
f (XR.Value_DateTime_iso8601 (XR.DateTime_iso8601 x)) =
liftM ValueDateTime (readDateTime x)
f (XR.Value_Base64 (XR.Base64 x)) = liftM ValueBase64 (readBase64 x)
f (XR.Value_Struct (XR.Struct ms)) =
liftM ValueStruct (mapM fromXRMember ms)
f (XR.Value_Array (XR.Array (XR.Data xs))) =
liftM ValueArray (mapM fromXRValue xs)
fromXRMember :: Monad m => XR.Member -> Err m (String,Value)
fromXRMember (XR.Member (XR.Name n) xv) = liftM (\v -> (n,v)) (fromXRValue xv)
readInt :: Monad m => String -> Err m Int
readInt s = errorRead reads "Error parsing integer" s
readBool :: Monad m => String -> Err m Bool
readBool s = errorRead readsBool "Error parsing boolean" s
where readsBool "true" = [(True,"")]
readsBool "false" = [(False,"")]
readsBool "1" = [(True,"")]
readsBool "0" = [(False,"")]
readsBool _ = []
readString :: Monad m => String -> Err m String
readString = return . replace "&" "&" . replace "<" "<"
. replace ">" ">"
readDouble :: Monad m => String -> Err m Double
readDouble s = errorRead reads "Error parsing double" s
readDateTime :: Monad m => String -> Err m LocalTime
readDateTime dt =
maybe
(fail $ "Error parsing dateTime '" ++ dt ++ "'")
return
(parseTime defaultTimeLocale xmlRpcDateFormat dt)
localTimeToCalendarTime :: LocalTime -> CalendarTime
localTimeToCalendarTime l =
let (y,mo,d) = toGregorian (localDay l)
TimeOfDay { todHour = h, todMin = mi, todSec = s } = localTimeOfDay l
(_,_,wd) = toWeekDate (localDay l)
(_,yd) = toOrdinalDate (localDay l)
in CalendarTime {
ctYear = fromIntegral y,
ctMonth = toEnum (mo1),
ctDay = d,
ctHour = h,
ctMin = mi,
ctSec = truncate s,
ctPicosec = 0,
ctWDay = toEnum (wd `mod` 7),
ctYDay = yd,
ctTZName = "UTC",
ctTZ = 0,
ctIsDST = False
}
calendarTimeToLocalTime :: CalendarTime -> LocalTime
calendarTimeToLocalTime ct =
let (y,mo,d) = (ctYear ct, ctMonth ct, ctDay ct)
(h,mi,s) = (ctHour ct, ctMin ct, ctSec ct)
in LocalTime {
localDay = fromGregorian (fromIntegral y) (fromEnum mo + 1) d,
localTimeOfDay = TimeOfDay { todHour = h, todMin = mi, todSec = fromIntegral s }
}
readBase64 :: Monad m => String -> Err m BS.ByteString
readBase64 = return . Base64.decode . BS.pack
fromXRParams :: Monad m => XR.Params -> Err m [Value]
fromXRParams (XR.Params xps) = mapM (\(XR.Param v) -> fromXRValue v) xps
fromXRMethodCall :: Monad m => XR.MethodCall -> Err m MethodCall
fromXRMethodCall (XR.MethodCall (XR.MethodName name) params) =
liftM (MethodCall name) (fromXRParams (fromMaybe (XR.Params []) params))
fromXRMethodResponse :: Monad m => XR.MethodResponse -> Err m MethodResponse
fromXRMethodResponse (XR.MethodResponseParams xps) =
liftM Return (fromXRParams xps >>= onlyOneResult)
fromXRMethodResponse (XR.MethodResponseFault (XR.Fault v)) =
do
struct <- fromXRValue v
vcode <- structGetValue "faultCode" struct
code <- fromValue vcode
vstr <- structGetValue "faultString" struct
str <- fromValue vstr
return (Fault code str)
parseCall :: (Show e, MonadError e m) => String -> Err m MethodCall
parseCall c =
do
mxc <- errorToErr (readXml c)
xc <- eitherToM "Error parsing method call" mxc
fromXRMethodCall xc
parseResponse :: (Show e, MonadError e m) => String -> Err m MethodResponse
parseResponse c =
do
mxr <- errorToErr (readXml c)
xr <- eitherToM "Error parsing method response" mxr
fromXRMethodResponse xr
renderCall :: MethodCall -> BSL.ByteString
renderCall = showXml' False . toXRMethodCall
renderResponse :: MethodResponse -> BSL.ByteString
renderResponse = showXml' False . toXRMethodResponse
showXml' :: XmlContent a => Bool -> a -> BSL.ByteString
showXml' dtd x = case toContents x of
[CElem _ _] -> (document . toXml dtd) x
_ -> BSL.pack ""