module Data.Torrent.Progress
       ( 
         Progress (..)
         
       , left
       , uploaded
       , downloaded
         
       , startProgress
       , downloadedProgress
       , enqueuedProgress
       , uploadedProgress
       , dequeuedProgress
         
       , canDownload
       , canUpload
       ) where
import Control.Applicative
import Control.Lens hiding ((%=))
import Data.Aeson.TH
import Data.Default
import Data.List as L
import Data.Monoid
import Data.Serialize as S
import Data.Ratio
import Data.URLEncoded
import Data.Word
import Text.PrettyPrint as PP
import Text.PrettyPrint.Class
data Progress = Progress
  { _downloaded ::  !Word64 
  , _left       ::  !Word64 
  , _uploaded   ::  !Word64 
  } deriving (Show, Read, Eq)
$(makeLenses ''Progress)
$(deriveJSON L.tail ''Progress)
instance Serialize Progress where
  put Progress {..} = do
    putWord64be $ fromIntegral _downloaded
    putWord64be $ fromIntegral _left
    putWord64be $ fromIntegral _uploaded
  get = Progress
    <$> (fromIntegral <$> getWord64be)
    <*> (fromIntegral <$> getWord64be)
    <*> (fromIntegral <$> getWord64be)
instance Default Progress where
  def = Progress 0 0 0
  
instance Monoid Progress where
  mempty  = def
  
  mappend (Progress da la ua) (Progress db lb ub) = Progress
    { _downloaded = da + db
    , _left       = la + lb
    , _uploaded   = ua + ub
    }
  
instance URLShow Word64 where
  urlShow = show
  
instance URLEncode Progress where
  urlEncode Progress {..} = mconcat
    [ s "uploaded"   %=  _uploaded
    , s "left"       %=  _left
    , s "downloaded" %=  _downloaded
    ]
    where s :: String -> String;  s = id; 
instance Pretty Progress where
  pretty Progress {..} =
    "/\\"  <+> PP.text (show _uploaded)   $$
    "\\/"  <+> PP.text (show _downloaded) $$
    "left" <+> PP.text (show _left)
startProgress :: Integer -> Progress
startProgress = Progress 0 0 . fromIntegral
downloadedProgress :: Int -> Progress -> Progress
downloadedProgress (fromIntegral -> amount)
                 = (left         -~ amount)
                 . (downloaded   +~ amount)
uploadedProgress :: Int -> Progress -> Progress
uploadedProgress (fromIntegral -> amount) = uploaded +~ amount
enqueuedProgress :: Integer -> Progress -> Progress
enqueuedProgress amount = left +~ fromIntegral amount
dequeuedProgress :: Integer -> Progress -> Progress
dequeuedProgress amount = left -~ fromIntegral amount
ri2rw64 :: Ratio Int -> Ratio Word64
ri2rw64 x = fromIntegral (numerator x) % fromIntegral (denominator x)
canDownload :: Ratio Int -> Progress -> Bool
canDownload limit Progress {..} = _uploaded % _downloaded > ri2rw64 limit
canUpload :: Ratio Int -> Progress -> Bool
canUpload limit Progress {..} = _downloaded % _uploaded > ri2rw64 limit