module Network.XmlRpc.Server 
    (
     XmlRpcMethod, ServerResult,
     fun,
     handleCall, methods, cgiXmlRpcServer,
    ) where
import Network.XmlRpc.Internals
import Data.Maybe
import Control.Monad.Error
import Control.Exception
import qualified Codec.Binary.UTF8.String as U
import System.IO
serverName = "Haskell XmlRpcServer/0.1"
type ServerResult = Err IO MethodResponse
type Signature = ([Type], Type)
type XmlRpcMethod = (MethodCall -> ServerResult, Signature)
showException :: Exception -> String
showException ex = fromMaybe (show ex) (userErrors ex)
handleIO :: IO a -> Err IO a
handleIO io = lift (try io) >>= either (fail . showException) return
fun :: XmlRpcFun a => a -> XmlRpcMethod
fun f = (toFun f, sig f)
class XmlRpcFun a where
    toFun :: a -> MethodCall -> ServerResult
    sig :: a -> Signature
instance XmlRpcType a => XmlRpcFun (IO a) where
    toFun x (MethodCall _ []) = do
			      v <- handleIO x
			      return (Return (toValue v))
    toFun _ _ = fail "Too many arguments"
    sig x = ([], getType (mType x))
instance (XmlRpcType a, XmlRpcFun b) => XmlRpcFun (a -> b) where
    toFun f (MethodCall n (x:xs)) = do
				  v <- fromValue x
				  toFun (f v) (MethodCall n xs)
    toFun _ _ = fail "Too few arguments"
    sig f = let (a,b) = funType f
                (as, r) = sig b
             in (getType a : as, r)
mType :: m a -> a
mType _ = undefined
funType :: (a -> b) -> (a, b)
funType _ = (undefined, undefined)
errorToResponse :: ServerResult -> IO MethodResponse
errorToResponse = handleError (return . Fault 0)
handleCall :: (MethodCall -> ServerResult) -> String -> IO String
handleCall f str = do
		       resp <- errorToResponse (parseCall str >>= f)
		       return (renderResponse resp)
methods :: [(String,XmlRpcMethod)] -> MethodCall -> ServerResult
methods t c@(MethodCall name _) = 
    do
    (method,_) <- maybeToM ("Unknown method: " ++ name) (lookup name t)
    method c
server :: [(String,XmlRpcMethod)] -> String -> IO String
server t = handleCall (methods (addIntrospection t))
addIntrospection :: [(String,XmlRpcMethod)] -> [(String,XmlRpcMethod)]
addIntrospection t = t' 
	where t' = ("system.listMethods", fun (listMethods t')) : 
		   ("system.methodSignature", fun (methodSignature t')) :
		   ("system.methodHelp", fun (methodHelp t')) : t
listMethods :: [(String,XmlRpcMethod)] -> IO [String]
listMethods t = return (fst (unzip t))
methodSignature :: [(String,XmlRpcMethod)] -> String -> IO [[String]]
methodSignature t name = 
    do
    (_,(as,r)) <- maybeToM ("Unknown method: " ++ name) (lookup name t)
    return [map show (r:as)]
methodHelp :: [(String,XmlRpcMethod)] -> String -> IO String
methodHelp t name =
    do
    method <- maybeToM ("Unknown method: " ++ name) (lookup name t)
    return (help method)
help :: XmlRpcMethod -> String
help m = ""
cgiXmlRpcServer :: [(String,XmlRpcMethod)] -> IO ()
cgiXmlRpcServer ms = 
    do
    hSetBinaryMode stdin True
    hSetBinaryMode stdout True
    input <- U.decodeString `fmap` getContents
    output <- U.encodeString `fmap` server ms input
    putStr ("Server: " ++ serverName ++ crlf)
    putStr ("Content-Type: text/xml" ++ crlf)
    putStr ("Content-Length: " ++ show (length output) ++ crlf)
    putStr crlf
    putStr output
	where crlf = "\r\n"