{-# LANGUAGE DeriveDataTypeable, FlexibleInstances, MultiParamTypeClasses, TypeFamilies #-}
module Happstack.Facebook.Photos where

import Data.Generics (Data, Typeable)
import Data.Maybe (catMaybes)
import Happstack.Facebook.Common
import Text.RJson

-- ** Photos
-- <http://wiki.developers.facebook.com/index.php/Photos.get>

data Get
    = Get
      { subj_id :: Maybe User -- perhaps this should be a Bool?
      , album   :: Maybe AlbumId
      , photos  :: Maybe [PhotoId]
      }
      deriving (Data, Typeable, Read, Show, Eq, Ord)

instance RequiresSession Get

instance (HasSessionKey m) => FacebookMethod m Get where
    type FacebookResponse Get = String
    parseResponse _ jstr = Right jstr
{-
        case fromJsonString [] jstr of
          Left e -> error $ "Photos.get: " ++ show e
          Right str -> str
-}
    toParams (Get mSubjId mAlbum mPhotos) =
        do sessionKey <- askSessionKey
           return $ catMaybes $ 
                      [ Just ("method", "Photos.get")
                      , Just ("session_key", sessionKey)
                      , fmap (\subj -> ("subj_id", show (uid subj))) mSubjId
                      , fmap (\albumId  -> ("aid",  show (aid albumId))) mAlbum
                      , fmap (\pids -> ("pids", toCommaList $ map (show . pid) pids)) mPhotos
                      ]

-- get :: Maybe User -> Maybe AlbumId -> Maybe [PhotoId] -> Facebook (Either FacebookError String)
-- get mUser mAlbum mPhotos = callMethodE (Get mUser mAlbum mPhotos)