module Flickr.Photosets.Comments where
import Flickr.Monad
import Flickr.Types
import Flickr.Types.Import
addComment :: PhotosetID -> String -> FM CommentID
addComment psid c = withWritePerm $ postMethod $
  flickTranslate toCommentID $ 
    flickrCall "flickr.photosets.comments.addComment"
               [ ("photoset_id", psid)
	       , ("comment_text", c)
	       ]
deleteComment :: CommentID -> FM ()
deleteComment cid = withWritePerm $ postMethod $
    flickCall_ "flickr.photosets.comments.deleteComment"
               [ ("comment_id", cid)
	       ]
editComment :: CommentID -> String -> FM ()
editComment cid c = withWritePerm $ postMethod $
    flickCall_ "flickr.photosets.comments.editComment"
               [ ("comment_id", cid)
	       , ("comment_text", c)
	       ]
getList :: PhotosetID -> FM [Comment]
getList psid = 
  flickTranslate toCommentList $ 
    flickrCall "flickr.photosets.comments.getList"
               [ ("photoset_id", psid)
	       ]