module Flowdock.REST.Invitation ( -- * Types Invitation(..) , Invitations(..) , InvitationState(..) , ImportAddressMessage(..) , ImportAddressResponse(..) , CreateInvitation(..) -- * API , listInvitations , getInvitation , createInvitation , importAddressList , deleteInvitation ) where import Control.Monad import Data.Aeson import Data.Aeson.TH import Data.Aeson.Types import Data.Text (Text, pack) import Data.Vector (toList) import Network.Http.Client (Method(..)) import Flowdock.Internal import Flowdock.REST import Flowdock.REST.User -- ----------------------------------------------------------------------------- -- Deserialized Types data InvitationState = Pending | Accepted deriving (Eq, Show) instance FromJSON InvitationState where parseJSON (String s) = case s of "pending" -> return Pending "accepted" -> return Accepted _ -> mzero parseJSON _ = mzero data Invitation = Invitation { invitationID :: !Int , invitationState :: !InvitationState , invitationEmail :: !Text , flowResource :: !Text , invitationURL :: !Text } deriving (Eq, Show) instance FromJSON Invitation where parseJSON (Object o) = do iid <- o .: "id" state <- o .: "state" email <- o .: "email" flow <- o .: "flow" url <- o .: "url" return $ Invitation iid state email flow url parseJSON _ = mzero newtype Invitations = Invitations { invitations :: [Invitation] } deriving (Show, Eq) instance FromJSON Invitations where parseJSON (Array as) = do invitations <- mapM parseJSON $ toList as :: Parser [Invitation] return $ Invitations invitations parseJSON _ = mzero data ImportAddressResponse = ImportAddressResponse { importInvitations :: ![Invitation] , importAddedUsers :: ![User] , importErroneousEmails :: ![Object] } deriving (Eq, Show) instance FromJSON ImportAddressResponse where parseJSON (Object o) = do invitations <- o .: "invitations" addedUsers <- o .: "added_users" erroneousEmails <- o .: "erroneous_emails" return $ ImportAddressResponse invitations addedUsers erroneousEmails parseJSON _ = mzero -- ----------------------------------------------------------------------------- -- Serialized Types data CreateInvitation = CreateInvitation { targetEmail :: !Text , targetMessage :: !Text } deriving (Eq, Show) $(deriveToJSON defaultOptions{fieldLabelModifier = underscoreCase . drop 6} ''CreateInvitation) data ImportAddressMessage = ImportAddressMessage { addressList :: !Text , addressMessage :: !Text } deriving (Eq, Show) $(deriveToJSON defaultOptions{fieldLabelModifier = underscoreCase . drop 7} ''ImportAddressMessage) -- ----------------------------------------------------------------------------- -- API Calls listInvitations :: Text -- ^ Organization parmaterized name -> Text -- ^ Flow paramaterized name -> RestAPI (Either Error Invitations) listInvitations organization flow = request GET ["flows", organization, flow, "invitations"] [] Nothing getInvitation :: Text -- ^ Organization parmaterized name -> Text -- ^ Flow paramaterized name -> Int -- ^ Invitation ID -> RestAPI (Either Error Invitation) getInvitation organization flow iid = request GET ["flows", organization, flow, "invitations", pack $ show iid] [] Nothing createInvitation :: Text -- ^ Organization parmaterized name -> Text -- ^ Flow paramaterized name -> CreateInvitation -> RestAPI (Either Error Invitation) createInvitation organization flow cinv = request POST ["flows", organization, flow, "invitations"] [] (Just $ encode cinv) importAddressList :: Text -- ^ Organization parmaterized name -> Text -- ^ Flow paramaterized name -> ImportAddressMessage -- ^ The import message -> RestAPI (Either Error ImportAddressResponse) importAddressList organization flow iam = request POST ["flows", organization, flow, "invitations", "import"] [] (Just $ encode iam) deleteInvitation :: Text -- ^ Organization parmaterized name -> Text -- ^ Flow paramaterized name -> Int -- ^ Invitation ID -> RestAPI (Either Error Success) deleteInvitation organization flow iid = request DELETE ["flows", organization, flow, "invitations", pack $ show iid] [] Nothing