module FriendFeed.Updates where

import FriendFeed.Types
import FriendFeed.Types.Import ()
import FriendFeed.Monad

upd_base :: URLString
upd_base = "http://chan.friendfeed.com/api/updates/"

upd_base2 :: URLString
upd_base2 = "http://chan.friendfeed.com/api/updates"

getUpdateInfo :: FFm UpdateInfo
getUpdateInfo = withBase upd_base2 $ authCall $
  ffeedTranslateSub "update" $ 
    ffeedCall [""] []

-- | Returns updates to the users home feed.
getUpdatesHome :: UpdateToken -> Maybe Int -> FFm [Entry]
getUpdatesHome tok mbT = withBase upd_base $ authCall $
  ffeedTranslateLs "entries" $ 
    ffeedCall ["home"] 
              (mbArg2 "timeout" (fmap show mbT) $
	       mbArg2 "token"   (Just tok) [])

-- | Returns updates to a user's friends. 
getUpdatesFriends :: UserName -> UpdateToken -> Maybe Int -> FFm [Entry]
getUpdatesFriends u tok mbT = withBase upd_base $ authCall $
   ffeedTranslateLs "entries" $
    ffeedCall ["user",u,"home"] 
              (mbArg2 "timeout" (fmap show mbT) $
	       mbArg2 "token"   (Just tok) [])

-- | Returns updates to the authenticated user's list with the given nickname.
getUpdatesList :: ListName -> UpdateToken -> Maybe Int -> FFm [Entry]
getUpdatesList l tok mbT = withBase upd_base $ authCall $
   ffeedTranslateLs "entries" $
    ffeedCall ["list",l] 
              (mbArg2 "timeout" (fmap show mbT) $
	       mbArg2 "token"   (Just tok) [])

-- | Returns updates to the room with the given nickname. 
getUpdatesRoom :: RoomName -> UpdateToken -> Maybe Int -> FFm [Entry]
getUpdatesRoom r tok mbT = withBase upd_base $ authCall $
   ffeedTranslateLs "entries" $
    ffeedCall ["room",r] 
              (mbArg2 "timeout" (fmap show mbT) $
	       mbArg2 "token"   (Just tok) [])