{-# LANGUAGE DeriveDataTypeable, FlexibleInstances, MultiParamTypeClasses, TypeFamilies #-} module Happstack.Facebook.Status where import Data.Generics (Data, Typeable) import qualified Data.Map as Map import Data.Maybe (catMaybes) import Happstack.Facebook.Common import Text.RJson -- ** Status data Set = Set String deriving (Data, Typeable, Eq, Ord, Read, Show) -- according to the docs, you only need uid *or* session_key, but -- never both. However, it did not work for me with out the session -- key. instance (HasSessionKey m) => FacebookMethod m Set where type FacebookResponse Set = String parseResponse _ = Right . id toParams (Set status) = do sessionKey <- askSessionKey return $ catMaybes $ [ Just ("method","Status.set") , Just ("status", status) , Just ("session_key", sessionKey) ]