module Network.RTorrent.CommandList 
  ( module Network.RTorrent.File
  , module Network.RTorrent.Peer
  , module Network.RTorrent.Priority
  , module Network.RTorrent.Torrent
  , module Network.RTorrent.Tracker
  
  , Global 
  , getUpRate 
  , getDownRate
  , getDirectory
  , getPid
  , getUploadRate
  , getDownloadRate
  , setUploadRate
  , setDownloadRate
  
  
  , loadTorrent
  , loadTorrentRaw
  , loadStartTorrent
  , loadStartTorrentRaw
  
  , commandSimple
  , commandArgs
  , commandInt
  , commandString
  
  , (<+>)
  , sequenceActions
  
  , (:*:)(..)
  , AnyCommand (..)
  , Command (Ret)
  )
  where
import Network.XmlRpc.Internals
import Control.Applicative
import Data.ByteString (ByteString)
import Network.RTorrent.Action
import Network.RTorrent.Command.Internals
import Network.RTorrent.File
import Network.RTorrent.Peer
import Network.RTorrent.Priority
import Network.RTorrent.Torrent
import Network.RTorrent.Tracker
commandSimple :: XmlRpcType a => String -> Global a
commandSimple cmd = commandArgs cmd []
commandArgs :: XmlRpcType a => String -> [Value] -> Global a
commandArgs = flip $ Global parseSingle
commandInt :: XmlRpcType a => String -> Int -> Global a
commandInt cmd i = commandArgs cmd [ValueInt i]
commandString :: XmlRpcType a => 
    String  
    -> String 
    -> Global a
commandString cmd s = commandArgs cmd [ValueString s]
getUpRate :: Global Int
getUpRate = commandSimple "get_up_rate"
getDownRate :: Global Int
getDownRate = commandSimple "get_down_rate"
getDirectory :: Global String
getDirectory = fmap decodeUtf8 $ commandSimple "get_directory"
getUploadRate :: Global Int
getUploadRate = commandSimple "get_upload_rate"
getDownloadRate :: Global Int
getDownloadRate = commandSimple "get_download_rate"
setUploadRate :: Int -> Global Int
setUploadRate = commandInt "set_upload_rate"
setDownloadRate :: Int -> Global Int
setDownloadRate = commandInt "set_download_rate"
getPid :: Global Int
getPid = commandSimple "system.pid"
loadTorrent :: String 
        -> Global Int
loadTorrent = commandString "load"
loadTorrentRaw :: ByteString 
        -> Global Int
loadTorrentRaw torrentData = commandArgs "load_raw" [ValueBase64 torrentData] 
loadStartTorrent :: String 
        -> Global Int
loadStartTorrent = commandString "load_start"
loadStartTorrentRaw :: ByteString 
        -> Global Int
loadStartTorrentRaw torrentData = commandArgs "load_raw_start" [ValueBase64 torrentData] 
    
data Global t = Global (forall m. (Monad m, Applicative m) => Value -> m t) [Value] String
instance Command (Global a) where
    type Ret (Global a) = a
    commandCall (Global _ args cmd) = mkRTMethodCall cmd args
    commandValue (Global parse _ _) = parse
instance Functor Global where
    fmap f (Global g args s) = Global (fmap f . g) args s