module Flowdock.MessageTypes where import Control.Applicative import Control.Monad import Data.Aeson import Data.Int import Data.Text (Text) -- ----------------------------------------------------------------------------- -- Deserialized Data Types data EventAction = AddPeople { people :: !Text } | Joined | Block { userId :: !Text } | Invite { emails :: !Text } | Decline { emails :: !Text } | Uninvite { emails :: !Text } | AddRssFeed { url :: !Text } | RemoveRssFeed { url :: !Text } | AddTwitterFollower { twitterUser :: !Text } | RemoveTwitterFollower { twitterFollower :: !Text } | AddTwitterSearch { twitterTerm :: !Text } | RemoveTwitterSearch { twitterTerm :: !Text } deriving (Eq, Show) instance FromJSON EventAction where parseJSON (Object o) = do actionType <- o .: "type" case (actionType :: Text) of "add_people" -> AddPeople <$> o .: "description" "join" -> return Joined "block" -> Block <$> o .: "description" "invite" -> Invite <$> o .: "descrption" "decline" -> Decline <$> o .: "description" "uninvite" -> Uninvite <$> o .: "description" "add_rss_feed" -> AddRssFeed <$> o .: "description" "remove_rss_feed" -> RemoveRssFeed <$> o .: "decription" "add_twitter_follower" -> AddTwitterFollower <$> o .: "description" "remove_twitter_follower" -> RemoveTwitterFollower <$> o .: "description" "add_twitter_search" -> AddTwitterSearch <$> o .: "description" "remove_twitter_search" -> RemoveTwitterSearch <$> o .: "description" _ -> mzero parseJSON _ = mzero data ImageDetails = ImageDetails { imageHeight :: !Int, imageWidth :: !Int } deriving (Eq, Show) instance FromJSON ImageDetails where parseJSON (Object o) = ImageDetails <$> o .: "height" <*> o .: "width" parseJSON _ = mzero data Thumbnail = Thumbnail { thumbnailHeight :: !Int, thumbnailWidth :: !Int, path :: !Text } deriving (Eq, Show) instance FromJSON Thumbnail where parseJSON (Object o) = Thumbnail <$> o .: "height" <*> o .: "width" <*> o .: "path" parseJSON _ = mzero data Attachment = Attachment { attachmentID :: !(Maybe Text) , attachmentContentType :: !Text , attachmentFileName :: !Text , attachmentFileSize :: !Int , attachmentFilePath :: !Text } deriving (Eq, Show) instance FromJSON Attachment where parseJSON (Object o) = do cid <- o .:? "content_id" ctype <- o .: "content_type" fname <- o .: "file_name" fsize <- o .: "file_size" fpath <- o .: "path" return $ Attachment cid ctype fname fsize fpath parseJSON _ = mzero data EventType = Message { content :: !Text } | Status { content :: !Text } | Comment { title :: !Text , text :: !Text } | Action !EventAction | TagChange { messageID :: !Int , addedTags :: ![Text] , removedTags :: ![Text] } | MessageEdit { messageID :: !Int , updatedContent :: !Text } | UserActivity { lastActivity :: !Int64 } | File { filePath :: !Text , fileName :: !Text , fileSize :: !Int , contentType :: !Text , imageDetails :: !(Maybe ImageDetails) , thumbnail :: !(Maybe Thumbnail) } deriving (Eq, Show) instance FromJSON EventType where parseJSON (Object o) = do eventType <- o .: "event" case (eventType :: Text) of "message" -> Message <$> o .: "content" "status" -> Status <$> o .: "content" "comment" -> do cnt <- o .: "content" Comment <$> cnt .: "title" <*> cnt .: "text" "action" -> do ob <- o .: "content" Action <$> parseJSON ob "tag-change" -> do cnt <- o .: "content" TagChange <$> cnt .: "message" <*> cnt .: "add" <*> cnt .: "remove" "message-edit" -> do cnt <- o .: "content" MessageEdit <$> cnt .: "message" <*> cnt .: "updated_content" "activity.user" -> do cnt <- o .: "content" UserActivity <$> cnt .: "last_activity" "file" -> do cnt <- o .: "content" File <$> cnt .: "path" <*> cnt .: "file_name" <*> cnt .: "file_size" <*> cnt .: "content_type" <*> cnt .:? "image" <*> cnt .:? "thumbnail" _ -> mzero parseJSON _ = error "4" data Event = Event { eventID :: !Int , eventApp :: !(Maybe Text) , eventTags :: ![Text] , eventUuid :: !(Maybe Text) , eventFlow :: !Text , eventSent :: !Int64 , eventAttachments :: ![Attachment] , eventUser :: !Text , eventType :: !EventType } deriving (Eq, Show) instance FromJSON Event where parseJSON obj@(Object o) = do eid <- o .: "id" app <- o .:? "app" tags <- o .: "tags" uuid <- o .:? "uuid" flow <- o .: "flow" att <- o .: "attachments" sent <- o .: "sent" user <- o .: "user" Event eid app tags uuid flow sent att user <$> parseJSON obj parseJSON _ = mzero