-------------------------------------------------------------------- -- | -- Module : FriendFeed.Types -- Description : Types used in the FriendFeed API -- Copyright : (c) Sigbjorn Finne, 2008 -- License : BSD3 -- -- Maintainer: Sigbjorn Finne -- Stability : provisional -- Portability: portable -- -- Definition of types that the FriendFeed API uses in its -- responses. -- -------------------------------------------------------------------- module FriendFeed.Types where type UUID = String type URLString = String type DateString = String type UserName = String type ListName = String type RoomName = String type ServiceName = String type EntryID = UUID type CommentID = UUID type RoomID = UUID type ListID = UUID type ServiceID = UUID type UserID = UUID nullUUID :: UUID nullUUID = "" data Entry = Entry { entryId :: UUID , entryTitle :: String , entryLink :: URLString , entryPublished :: DateString , entryUpdated :: DateString , entryIsHidden :: Bool , entryIsAnon :: Bool , entryUser :: Resource User , entryService :: Service , entryLikes :: [Like] , entryComments :: [Comment] , entryMedia :: [Media] , entryVia :: Maybe Via , entryRoom :: Maybe (Resource Room) } type Via = (String, URLString) nullVia :: Via nullVia = ("","") nullEntry :: Entry nullEntry = Entry { entryId = nullUUID , entryTitle = "" , entryLink = "" , entryPublished = "" , entryUpdated = "" , entryIsHidden = False , entryIsAnon = False , entryUser = nullResource , entryService = nullService , entryLikes = [] , entryComments = [] , entryMedia = [] , entryVia = Nothing , entryRoom = Nothing } data User = User { userStatus :: String , userId :: UserID , userName :: UserName , userNickname :: UserName , userProfileURL :: URLString , userServices :: [Service] , userSubscriptions :: [Resource Subscription] , userRooms :: [Resource Room] , userLists :: [Resource List] } nullUser :: User nullUser = User { userStatus = "unsubscribed" , userId = nullUUID , userName = "" , userNickname = "" , userProfileURL = "" , userServices = [] , userSubscriptions = [] , userRooms = [] , userLists = [] } data Subscription = Subscription_ data Comment = Comment { commentDate :: DateString , commentUser :: [Resource User] , commentBody :: String } nullComment :: Comment nullComment = Comment { commentDate = "" , commentUser = [] , commentBody = "" } data Like = Like { likeDate :: DateString , likeUser :: Resource User } nullLike :: Like nullLike = Like { likeDate = "" , likeUser = nullResource } data Media = Media { mediaTitle :: Maybe String , mediaPlayer :: Maybe String , mediaLink :: URLString , mediaThumbs :: [Thumbnail] , mediaContent :: [Content] , mediaEnclosure :: [Enclosure] } nullMedia :: Media nullMedia = Media { mediaTitle = Nothing , mediaPlayer = Nothing , mediaLink = "" , mediaThumbs = [] , mediaContent = [] , mediaEnclosure = [] } data Thumbnail = Thumbnail { thumbUrl :: URLString , thumbWidth :: Int , thumbHeight :: Int } nullThumbnail :: Thumbnail nullThumbnail = Thumbnail { thumbUrl = "" , thumbWidth = 0 , thumbHeight = 0 } data Content = Content { contentUrl :: URLString , contentType :: String -- MIME , contentWidth :: Int , contentHeight :: Int } nullContent :: Content nullContent = Content { contentUrl = "" , contentType = "" , contentWidth = 0 , contentHeight = 0 } data Service = Service { serviceUrl :: URLString , serviceIconUrl :: URLString , serviceId :: ServiceID , serviceName :: String } nullService :: Service nullService = Service { serviceUrl = "" , serviceIconUrl = "" , serviceId = nullUUID , serviceName = "" } data Enclosure = Enclosure { enclosureUrl :: URLString , enclosureType :: String -- ^ MIME type , enclosureLength :: Integer } nullEnclosure :: Enclosure nullEnclosure = Enclosure { enclosureUrl = "" , enclosureType = "" , enclosureLength = 0 } data Resource a = Resource { resourceId :: UUID , resourceName :: String , resourceNickname :: String , resourceUrl :: URLString } nullResource :: Resource a nullResource = Resource { resourceId = nullUUID , resourceName = "" , resourceNickname = "" , resourceUrl = "" } data Room = Room { roomStatus :: String -- ^ static or public , roomDescription :: String , roomUrl :: URLString , roomAdmins :: [Resource User] , roomMember :: [Resource User] , roomId :: RoomID , roomName :: String , roomNickname :: String } nullRoom :: Room nullRoom = Room { roomStatus = "public" , roomDescription = "" , roomUrl = "" , roomAdmins = [] , roomMember = [] , roomId = nullUUID , roomName = "" , roomNickname = "" } data List = List { listId :: ListID , listName :: String , listNickname :: String , listURL :: URLString , listUsers :: [Resource User] , listRooms :: [Resource Room] } nullList :: List nullList = List { listId = "" , listName = "" , listNickname = "" , listURL = "" , listUsers = [] , listRooms = [] }