twitter-types-0.11.0/Web/0000755000000000000000000000000014144754426013353 5ustar0000000000000000twitter-types-0.11.0/Web/Twitter/0000755000000000000000000000000014144754426015015 5ustar0000000000000000twitter-types-0.11.0/tests/0000755000000000000000000000000014144754426014000 5ustar0000000000000000twitter-types-0.11.0/tests/fixtures/0000755000000000000000000000000014144754426015651 5ustar0000000000000000twitter-types-0.11.0/tests/fixtures/tweet-updates/0000755000000000000000000000000014144754426020444 5ustar0000000000000000twitter-types-0.11.0/Web/Twitter/Types.hs0000644000000000000000000011374114144754426016464 0ustar0000000000000000{-# LANGUAGE CPP #-} {-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE LambdaCase #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE RecordWildCards #-} module Web.Twitter.Types ( UserId, Friends, URIString, UserName, StatusId, LanguageCode, StreamingAPI (..), Status (..), SearchResult (..), SearchStatus (..), SearchMetadata (..), RetweetedStatus (..), DirectMessage (..), EventTarget (..), Event (..), Delete (..), User (..), List (..), Entities (..), EntityIndices, ExtendedEntities (..), Variant (..), VideoInfo (..), ExtendedEntity (..), Entity (..), HashTagEntity (..), UserEntity (..), URLEntity (..), MediaEntity (..), MediaSize (..), Coordinates (..), Place (..), BoundingBox (..), Contributor (..), UploadedMedia (..), ImageSizeType (..), DisplayTextRange (..), checkError, twitterTimeFormat, ) where import Control.Applicative import Control.Monad import Data.Aeson import Data.Aeson.Types (Parser) import Data.Data import Data.HashMap.Strict (HashMap) #if MIN_VERSION_aeson(2, 0, 0) import qualified Data.Aeson.KeyMap as KeyMap #else import qualified Data.HashMap.Strict as KeyMap #endif import Data.Int import Data.Ratio import Data.Text (Text, pack, unpack) import Data.Text.Read (decimal) import Data.Time import Data.Time.Clock.POSIX import GHC.Generics newtype TwitterTime = TwitterTime {fromTwitterTime :: UTCTime} type UserId = Integer type Friends = [UserId] type URIString = Text type UserName = Text type StatusId = Integer type LanguageCode = String data StreamingAPI = SStatus Status | SRetweetedStatus RetweetedStatus | SEvent Event | SDelete Delete | -- | SScrubGeo ScrubGeo SFriends Friends | SDirectMessage DirectMessage | SUnknown Value deriving (Show, Eq, Data, Typeable, Generic) checkError :: Object -> Parser () checkError o = do err <- o .:? "error" case err of Just msg -> fail msg Nothing -> return () twitterTimeFormat :: String twitterTimeFormat = "%a %b %d %T %z %Y" instance FromJSON TwitterTime where parseJSON = withText "TwitterTime" $ \t -> case parseTimeM True defaultTimeLocale twitterTimeFormat (unpack t) of Just d -> pure $ TwitterTime d Nothing -> fail $ "Could not parse twitter time. Text was: " ++ unpack t instance ToJSON TwitterTime where toJSON t = String $ pack $ formatTime defaultTimeLocale twitterTimeFormat $ fromTwitterTime t instance FromJSON StreamingAPI where parseJSON v@(Object o) = SRetweetedStatus <$> js <|> SStatus <$> js <|> SEvent <$> js <|> SDelete <$> js <|> SFriends <$> (o .: "friends") <|> SDirectMessage <$> (o .: "direct_message") <|> return (SUnknown v) where js :: FromJSON a => Parser a js = parseJSON v parseJSON v = fail $ "couldn't parse StreamingAPI from: " ++ show v instance ToJSON StreamingAPI where toJSON (SStatus s) = toJSON s toJSON (SRetweetedStatus s) = toJSON s toJSON (SEvent e) = toJSON e toJSON (SDelete d) = toJSON d toJSON (SFriends f) = toJSON f toJSON (SDirectMessage m) = toJSON m toJSON (SUnknown v) = v -- | This type represents a Twitter tweet structure. -- See . data Status = Status { statusContributors :: Maybe [Contributor] , statusCoordinates :: Maybe Coordinates , statusCreatedAt :: UTCTime , statusCurrentUserRetweet :: Maybe StatusId , statusEntities :: Maybe Entities , statusExtendedEntities :: Maybe ExtendedEntities , statusFavoriteCount :: Integer , statusFavorited :: Maybe Bool , statusFilterLevel :: Maybe Text , statusId :: StatusId , statusInReplyToScreenName :: Maybe Text , statusInReplyToStatusId :: Maybe StatusId , statusInReplyToUserId :: Maybe UserId , statusLang :: Maybe LanguageCode , statusPlace :: Maybe Place , statusPossiblySensitive :: Maybe Bool , statusScopes :: Maybe Object , statusQuotedStatusId :: Maybe StatusId , statusQuotedStatus :: Maybe Status , statusRetweetCount :: Integer , statusRetweeted :: Maybe Bool , statusRetweetedStatus :: Maybe Status , statusSource :: Text , statusText :: Text , statusTruncated :: Bool , statusUser :: User , statusWithheldCopyright :: Maybe Bool , statusWithheldInCountries :: Maybe [Text] , statusWithheldScope :: Maybe Text , statusDisplayTextRange :: Maybe DisplayTextRange } deriving (Show, Eq, Data, Typeable, Generic) instance FromJSON Status where parseJSON (Object o) = checkError o >> Status <$> o .:? "contributors" .!= Nothing <*> o .:? "coordinates" .!= Nothing <*> (o .: "created_at" >>= return . fromTwitterTime) <*> ((o .: "current_user_retweet" >>= (.: "id")) <|> return Nothing) <*> o .:? "entities" <*> o .:? "extended_entities" <*> o .:? "favorite_count" .!= 0 <*> o .:? "favorited" <*> o .:? "filter_level" <*> o .: "id" <*> o .:? "in_reply_to_screen_name" .!= Nothing <*> o .:? "in_reply_to_status_id" .!= Nothing <*> o .:? "in_reply_to_user_id" .!= Nothing <*> o .:? "lang" <*> o .:? "place" .!= Nothing <*> o .:? "possibly_sensitive" <*> o .:? "scopes" <*> o .:? "quoted_status_id" <*> o .:? "quoted_status" <*> o .:? "retweet_count" .!= 0 <*> o .:? "retweeted" <*> o .:? "retweeted_status" <*> o .: "source" <*> (o .: "full_text" <|> o .: "text") <*> o .: "truncated" <*> o .: "user" <*> o .:? "withheld_copyright" <*> o .:? "withheld_in_countries" <*> o .:? "withheld_scope" <*> o .:? "display_text_range" parseJSON v = fail $ "couldn't parse status from: " ++ show v instance ToJSON Status where toJSON Status {..} = object [ "contributors" .= statusContributors , "coordinates" .= statusCoordinates , "created_at" .= TwitterTime statusCreatedAt , "current_user_retweet" .= object [ "id" .= statusCurrentUserRetweet , "id_str" .= show statusCurrentUserRetweet ] , "entities" .= statusEntities , "extended_entities" .= statusExtendedEntities , "favorite_count" .= statusFavoriteCount , "favorited" .= statusFavorited , "filter_level" .= statusFilterLevel , "id" .= statusId , "in_reply_to_screen_name" .= statusInReplyToScreenName , "in_reply_to_status_id" .= statusInReplyToStatusId , "in_reply_to_user_id" .= statusInReplyToUserId , "lang" .= statusLang , "place" .= statusPlace , "possibly_sensitive" .= statusPossiblySensitive , "scopes" .= statusScopes , "quoted_status_id" .= statusQuotedStatusId , "quoted_status" .= statusQuotedStatus , "retweet_count" .= statusRetweetCount , "retweeted" .= statusRetweeted , "retweeted_status" .= statusRetweetedStatus , "source" .= statusSource , "text" .= statusText , "truncated" .= statusTruncated , "user" .= statusUser , "withheld_copyright" .= statusWithheldCopyright , "withheld_in_countries" .= statusWithheldInCountries , "withheld_scope" .= statusWithheldScope , "display_text_range" .= statusDisplayTextRange ] data SearchResult body = SearchResult { searchResultStatuses :: body , searchResultSearchMetadata :: SearchMetadata } deriving (Show, Eq, Data, Typeable, Generic) instance FromJSON body => FromJSON (SearchResult body) where parseJSON (Object o) = checkError o >> SearchResult <$> o .: "statuses" <*> o .: "search_metadata" parseJSON v = fail $ "couldn't parse search result from: " ++ show v instance ToJSON body => ToJSON (SearchResult body) where toJSON SearchResult {..} = object [ "statuses" .= searchResultStatuses , "search_metadata" .= searchResultSearchMetadata ] data SearchStatus = SearchStatus { searchStatusCreatedAt :: UTCTime , searchStatusId :: StatusId , searchStatusText :: Text , searchStatusSource :: Text , searchStatusUser :: User , searchStatusCoordinates :: Maybe Coordinates } deriving (Show, Eq, Data, Typeable, Generic) instance FromJSON SearchStatus where parseJSON (Object o) = checkError o >> SearchStatus <$> (o .: "created_at" >>= return . fromTwitterTime) <*> o .: "id" <*> o .: "text" <*> o .: "source" <*> o .: "user" <*> o .:? "coordinates" parseJSON v = fail $ "couldn't parse status search result from: " ++ show v instance ToJSON SearchStatus where toJSON SearchStatus {..} = object [ "created_at" .= TwitterTime searchStatusCreatedAt , "id" .= searchStatusId , "text" .= searchStatusText , "source" .= searchStatusSource , "user" .= searchStatusUser , "coordinates" .= searchStatusCoordinates ] data SearchMetadata = SearchMetadata { searchMetadataMaxId :: StatusId , searchMetadataSinceId :: StatusId , searchMetadataRefreshURL :: URIString , searchMetadataNextResults :: Maybe URIString , searchMetadataCount :: Int , searchMetadataCompletedIn :: Maybe Float , searchMetadataSinceIdStr :: String , searchMetadataQuery :: String , searchMetadataMaxIdStr :: String } deriving (Show, Eq, Data, Typeable, Generic) instance FromJSON SearchMetadata where parseJSON (Object o) = checkError o >> SearchMetadata <$> o .: "max_id" <*> o .: "since_id" <*> o .: "refresh_url" <*> o .:? "next_results" <*> o .: "count" <*> o .:? "completed_in" <*> o .: "since_id_str" <*> o .: "query" <*> o .: "max_id_str" parseJSON v = fail $ "couldn't parse search metadata from: " ++ show v instance ToJSON SearchMetadata where toJSON SearchMetadata {..} = object [ "max_id" .= searchMetadataMaxId , "since_id" .= searchMetadataSinceId , "refresh_url" .= searchMetadataRefreshURL , "next_results" .= searchMetadataNextResults , "count" .= searchMetadataCount , "completed_in" .= searchMetadataCompletedIn , "since_id_str" .= searchMetadataSinceIdStr , "query" .= searchMetadataQuery , "max_id_str" .= searchMetadataMaxIdStr ] data RetweetedStatus = RetweetedStatus { rsCreatedAt :: UTCTime , rsId :: StatusId , rsText :: Text , rsSource :: Text , rsTruncated :: Bool , rsEntities :: Maybe Entities , rsUser :: User , rsRetweetedStatus :: Status , rsCoordinates :: Maybe Coordinates } deriving (Show, Eq, Data, Typeable, Generic) instance FromJSON RetweetedStatus where parseJSON (Object o) = checkError o >> RetweetedStatus <$> (o .: "created_at" >>= return . fromTwitterTime) <*> o .: "id" <*> o .: "text" <*> o .: "source" <*> o .: "truncated" <*> o .:? "entities" <*> o .: "user" <*> o .: "retweeted_status" <*> o .:? "coordinates" parseJSON v = fail $ "couldn't parse retweeted status from: " ++ show v instance ToJSON RetweetedStatus where toJSON RetweetedStatus {..} = object [ "created_at" .= TwitterTime rsCreatedAt , "id" .= rsId , "text" .= rsText , "source" .= rsSource , "truncated" .= rsTruncated , "entities" .= rsEntities , "user" .= rsUser , "retweeted_status" .= rsRetweetedStatus , "coordinates" .= rsCoordinates ] type EventId = Integer data DirectMessage = DirectMessage { dmId :: EventId , dmCreatedTimestamp :: UTCTime , dmTargetRecipientId :: UserId , dmSenderId :: UserId , dmText :: Text , dmEntities :: Entities } deriving (Show, Eq, Data, Typeable, Generic) parseIntegral :: Integral a => Text -> Parser a parseIntegral v = either (\_ -> fail $ "couldn't parse stringized int: " ++ show v) (return . fst) $ decimal v epochMsToUTCTime :: Int64 -> UTCTime epochMsToUTCTime = posixSecondsToUTCTime . fromRational . (% 1000) . fromIntegral parseUnixTimeString :: Text -> Parser UTCTime parseUnixTimeString = fmap epochMsToUTCTime <$> parseIntegral unixTimeToEpochInt :: UTCTime -> Int unixTimeToEpochInt = floor . (* 1000) . utcTimeToPOSIXSeconds instance FromJSON DirectMessage where parseJSON (Object o) = do _ <- checkError o messageCreate <- o .: "message_create" messageData <- messageCreate .: "message_data" DirectMessage <$> (o .: "id" >>= parseIntegral) <*> (o .: "created_timestamp" >>= parseUnixTimeString) <*> (messageCreate .: "target" >>= (.: "recipient_id") >>= parseIntegral) <*> (messageCreate .: "sender_id" >>= parseIntegral) <*> messageData .: "text" <*> messageData .: "entities" parseJSON v = fail $ "couldn't parse direct message create event from: " ++ show v instance ToJSON DirectMessage where toJSON DirectMessage {..} = object [ "id" .= show dmId , "created_timestamp" .= show (unixTimeToEpochInt dmCreatedTimestamp) , "message_create" .= object [ "message_data" .= object ["text" .= dmText, "entities" .= dmEntities] , "target" .= object ["recipient_id" .= show dmTargetRecipientId] , "sender_id" .= show dmSenderId ] ] data EventType = Favorite | Unfavorite | ListCreated | ListUpdated | ListMemberAdded | UserUpdate | Block | Unblock | Follow deriving (Show, Eq, Data, Typeable, Generic) data EventTarget = ETUser User | ETStatus Status | ETList List | ETUnknown Value deriving (Show, Eq, Data, Typeable, Generic) instance FromJSON EventTarget where parseJSON v@(Object o) = checkError o >> ETUser <$> parseJSON v <|> ETStatus <$> parseJSON v <|> ETList <$> parseJSON v <|> return (ETUnknown v) parseJSON v = fail $ "couldn't parse event target from: " ++ show v instance ToJSON EventTarget where toJSON (ETUser u) = toJSON u toJSON (ETStatus s) = toJSON s toJSON (ETList l) = toJSON l toJSON (ETUnknown v) = v data Event = Event { evCreatedAt :: UTCTime , evTargetObject :: Maybe EventTarget , evEvent :: Text , evTarget :: EventTarget , evSource :: EventTarget } deriving (Show, Eq, Data, Typeable, Generic) instance FromJSON Event where parseJSON (Object o) = checkError o >> Event <$> (o .: "created_at" >>= return . fromTwitterTime) <*> o .:? "target_object" <*> o .: "event" <*> o .: "target" <*> o .: "source" parseJSON v = fail $ "couldn't parse event from: " ++ show v instance ToJSON Event where toJSON Event {..} = object [ "created_at" .= TwitterTime evCreatedAt , "target_object" .= evTargetObject , "event" .= evEvent , "target" .= evTarget , "source" .= evSource ] data Delete = Delete { delId :: StatusId , delUserId :: UserId } deriving (Show, Eq, Data, Typeable, Generic) instance FromJSON Delete where parseJSON (Object o) = checkError o >> do s <- o .: "delete" >>= (.: "status") Delete <$> s .: "id" <*> s .: "user_id" parseJSON v = fail $ "couldn't parse delete from: " ++ show v instance ToJSON Delete where toJSON Delete {..} = object [ "delete" .= object [ "status" .= object [ "id" .= delId , "user_id" .= delUserId ] ] ] -- | This type represents the Twitter user. -- See . data User = User { userContributorsEnabled :: Bool , userCreatedAt :: UTCTime , userDefaultProfile :: Bool , userDefaultProfileImage :: Bool , userDescription :: Maybe Text , userEmail :: Maybe Text , userFavoritesCount :: Int , userFollowRequestSent :: Maybe Bool , userFollowing :: Maybe Bool , userFollowersCount :: Int , userFriendsCount :: Int , userGeoEnabled :: Bool , userId :: UserId , userIsTranslator :: Bool , userLang :: Maybe LanguageCode , userListedCount :: Int , userLocation :: Maybe Text , userName :: Text , userNotifications :: Maybe Bool , userProfileBackgroundColor :: Maybe Text , userProfileBackgroundImageURL :: Maybe URIString , userProfileBackgroundImageURLHttps :: Maybe URIString , userProfileBackgroundTile :: Maybe Bool , userProfileBannerURL :: Maybe URIString , userProfileImageURL :: Maybe URIString , userProfileImageURLHttps :: Maybe URIString , userProfileLinkColor :: Text , userProfileSidebarBorderColor :: Text , userProfileSidebarFillColor :: Text , userProfileTextColor :: Text , userProfileUseBackgroundImage :: Bool , userProtected :: Bool , userScreenName :: Text , userShowAllInlineMedia :: Maybe Bool , userStatusesCount :: Int , userTimeZone :: Maybe Text , userURL :: Maybe URIString , userUtcOffset :: Maybe Int , userVerified :: Bool , userWithheldInCountries :: Maybe [Text] , userWithheldScope :: Maybe Text } deriving (Show, Eq, Data, Typeable, Generic) instance FromJSON User where parseJSON (Object o) = checkError o >> User <$> o .: "contributors_enabled" <*> (o .: "created_at" >>= return . fromTwitterTime) <*> o .: "default_profile" <*> o .: "default_profile_image" <*> o .:? "description" <*> fmap join (o .:? "email") -- The field can be a null value <*> o .: "favourites_count" <*> o .:? "follow_request_sent" .!= Nothing <*> o .:? "following" .!= Nothing <*> o .: "followers_count" <*> o .: "friends_count" <*> o .: "geo_enabled" <*> o .: "id" <*> o .: "is_translator" <*> o .: "lang" <*> o .: "listed_count" <*> o .:? "location" <*> o .: "name" <*> o .:? "notifications" .!= Nothing <*> o .:? "profile_background_color" <*> o .:? "profile_background_image_url" <*> o .:? "profile_background_image_url_https" <*> o .:? "profile_background_tile" <*> o .:? "profile_banner_url" <*> o .:? "profile_image_url" <*> o .:? "profile_image_url_https" <*> o .: "profile_link_color" <*> o .: "profile_sidebar_border_color" <*> o .: "profile_sidebar_fill_color" <*> o .: "profile_text_color" <*> o .: "profile_use_background_image" <*> o .: "protected" <*> o .: "screen_name" <*> o .:? "show_all_inline_media" <*> o .: "statuses_count" <*> o .:? "time_zone" <*> o .:? "url" .!= Nothing <*> o .:? "utc_offset" <*> o .: "verified" <*> o .:? "withheld_in_countries" <*> o .:? "withheld_scope" parseJSON v = fail $ "couldn't parse user from: " ++ show v instance ToJSON User where toJSON User {..} = object [ "contributors_enabled" .= userContributorsEnabled , "created_at" .= TwitterTime userCreatedAt , "default_profile" .= userDefaultProfile , "default_profile_image" .= userDefaultProfileImage , "description" .= userDescription , "email" .= userEmail , "favourites_count" .= userFavoritesCount , "follow_request_sent" .= userFollowRequestSent , "following" .= userFollowing , "followers_count" .= userFollowersCount , "friends_count" .= userFriendsCount , "geo_enabled" .= userGeoEnabled , "id" .= userId , "is_translator" .= userIsTranslator , "lang" .= userLang , "listed_count" .= userListedCount , "location" .= userLocation , "name" .= userName , "notifications" .= userNotifications , "profile_background_color" .= userProfileBackgroundColor , "profile_background_image_url" .= userProfileBackgroundImageURL , "profile_background_image_url_https" .= userProfileBackgroundImageURLHttps , "profile_background_tile" .= userProfileBackgroundTile , "profile_banner_url" .= userProfileBannerURL , "profile_image_url" .= userProfileImageURL , "profile_image_url_https" .= userProfileImageURLHttps , "profile_link_color" .= userProfileLinkColor , "profile_sidebar_border_color" .= userProfileSidebarBorderColor , "profile_sidebar_fill_color" .= userProfileSidebarFillColor , "profile_text_color" .= userProfileTextColor , "profile_use_background_image" .= userProfileUseBackgroundImage , "protected" .= userProtected , "screen_name" .= userScreenName , "show_all_inline_media" .= userShowAllInlineMedia , "statuses_count" .= userStatusesCount , "time_zone" .= userTimeZone , "url" .= userURL , "utc_offset" .= userUtcOffset , "verified" .= userVerified , "withheld_in_countries" .= userWithheldInCountries , "withheld_scope" .= userWithheldScope ] data List = List { listId :: Int , listName :: Text , listFullName :: Text , listMemberCount :: Int , listSubscriberCount :: Int , listMode :: Text , listUser :: User } deriving (Show, Eq, Data, Typeable, Generic) instance FromJSON List where parseJSON (Object o) = checkError o >> List <$> o .: "id" <*> o .: "name" <*> o .: "full_name" <*> o .: "member_count" <*> o .: "subscriber_count" <*> o .: "mode" <*> o .: "user" parseJSON v = fail $ "couldn't parse List from: " ++ show v instance ToJSON List where toJSON List {..} = object [ "id" .= listId , "name" .= listName , "full_name" .= listFullName , "member_count" .= listMemberCount , "subscriber_count" .= listSubscriberCount , "mode" .= listMode , "user" .= listUser ] -- | Hashtag entity. -- See . data HashTagEntity = HashTagEntity { -- | The Hashtag text hashTagText :: Text } deriving (Show, Eq, Data, Typeable, Generic) instance FromJSON HashTagEntity where parseJSON (Object o) = HashTagEntity <$> o .: "text" parseJSON v = fail $ "couldn't parse hashtag entity from: " ++ show v instance ToJSON HashTagEntity where toJSON HashTagEntity {..} = object ["text" .= hashTagText] -- | User mention entity. -- See . data UserEntity = UserEntity { userEntityUserId :: UserId , userEntityUserName :: UserName , userEntityUserScreenName :: Text } deriving (Show, Eq, Data, Typeable, Generic) instance FromJSON UserEntity where parseJSON (Object o) = UserEntity <$> o .: "id" <*> o .: "name" <*> o .: "screen_name" parseJSON v = fail $ "couldn't parse user entity from: " ++ show v instance ToJSON UserEntity where toJSON UserEntity {..} = object [ "id" .= userEntityUserId , "name" .= userEntityUserName , "screen_name" .= userEntityUserScreenName ] -- | URL entity. -- See . data URLEntity = URLEntity { -- | The URL that was extracted ueURL :: URIString , -- | The fully resolved URL (only for t.co links) ueExpanded :: URIString , -- | Not a URL but a string to display instead of the URL (only for t.co links) ueDisplay :: Text } deriving (Show, Eq, Data, Typeable, Generic) instance FromJSON URLEntity where parseJSON (Object o) = URLEntity <$> o .: "url" <*> o .: "expanded_url" <*> o .: "display_url" parseJSON v = fail $ "couldn't parse url entity from: " ++ show v instance ToJSON URLEntity where toJSON URLEntity {..} = object [ "url" .= ueURL , "expanded_url" .= ueExpanded , "display_url" .= ueDisplay ] data MediaEntity = MediaEntity { meType :: Text , meId :: StatusId , meSizes :: HashMap Text MediaSize , meMediaURL :: URIString , meMediaURLHttps :: URIString , meURL :: URLEntity } deriving (Show, Eq, Data, Typeable, Generic) instance FromJSON MediaEntity where parseJSON v@(Object o) = MediaEntity <$> o .: "type" <*> o .: "id" <*> o .: "sizes" <*> o .: "media_url" <*> o .: "media_url_https" <*> parseJSON v parseJSON v = fail $ "couldn't parse media entity from: " ++ show v instance ToJSON MediaEntity where toJSON MediaEntity {..} = object [ "type" .= meType , "id" .= meId , "sizes" .= meSizes , "media_url" .= meMediaURL , "media_url_https" .= meMediaURLHttps , "url" .= ueURL meURL , "expanded_url" .= ueExpanded meURL , "display_url" .= ueDisplay meURL ] -- | Size entity. -- See . data MediaSize = MediaSize { msWidth :: Int , msHeight :: Int , msResize :: Text } deriving (Show, Eq, Data, Typeable, Generic) instance FromJSON MediaSize where parseJSON (Object o) = MediaSize <$> o .: "w" <*> o .: "h" <*> o .: "resize" parseJSON v = fail $ "couldn't parse media size from: " ++ show v instance ToJSON MediaSize where toJSON MediaSize {..} = object [ "w" .= msWidth , "h" .= msHeight , "resize" .= msResize ] data Coordinates = Coordinates { coordinates :: [Double] , coordinatesType :: Text } deriving (Show, Eq, Data, Typeable, Generic) instance FromJSON Coordinates where parseJSON (Object o) = Coordinates <$> o .: "coordinates" <*> o .: "type" parseJSON v = fail $ "couldn't parse coordinates from: " ++ show v instance ToJSON Coordinates where toJSON Coordinates {..} = object [ "coordinates" .= coordinates , "type" .= coordinatesType ] -- | This type represents a place, named locations with corresponding geo coordinates. -- See . data Place = Place { placeAttributes :: HashMap Text Text , placeBoundingBox :: Maybe BoundingBox , placeCountry :: Text , placeCountryCode :: Text , placeFullName :: Text , placeId :: Text , placeName :: Text , placeType :: Text , placeURL :: Text } deriving (Show, Eq, Data, Typeable, Generic) instance FromJSON Place where parseJSON (Object o) = Place <$> o .: "attributes" <*> o .:? "bounding_box" <*> o .: "country" <*> o .: "country_code" <*> o .: "full_name" <*> o .: "id" <*> o .: "name" <*> o .: "place_type" <*> o .: "url" parseJSON v = fail $ "couldn't parse place from: " ++ show v instance ToJSON Place where toJSON Place {..} = object [ "attributes" .= placeAttributes , "bounding_box" .= placeBoundingBox , "country" .= placeCountry , "country_code" .= placeCountryCode , "full_name" .= placeFullName , "id" .= placeId , "name" .= placeName , "place_type" .= placeType , "url" .= placeURL ] -- | A bounding box of coordinates which encloses the place. -- See . data BoundingBox = BoundingBox { boundingBoxCoordinates :: [[[Double]]] , boundingBoxType :: Text } deriving (Show, Eq, Data, Typeable, Generic) instance FromJSON BoundingBox where parseJSON (Object o) = BoundingBox <$> o .: "coordinates" <*> o .: "type" parseJSON v = fail $ "couldn't parse bounding box from: " ++ show v instance ToJSON BoundingBox where toJSON BoundingBox {..} = object [ "coordinates" .= boundingBoxCoordinates , "type" .= boundingBoxType ] -- | Entity handling. -- See . data Entities = Entities { enHashTags :: [Entity HashTagEntity] , enUserMentions :: [Entity UserEntity] , enURLs :: [Entity URLEntity] , enMedia :: [Entity MediaEntity] } deriving (Show, Eq, Data, Typeable, Generic) instance FromJSON Entities where parseJSON (Object o) = Entities <$> o .:? "hashtags" .!= [] <*> o .:? "user_mentions" .!= [] <*> o .:? "urls" .!= [] <*> o .:? "media" .!= [] parseJSON v = fail $ "couldn't parse entities from: " ++ show v instance ToJSON Entities where toJSON Entities {..} = object [ "hashtags" .= enHashTags , "user_mentions" .= enUserMentions , "urls" .= enURLs , "media" .= enMedia ] -- | The character positions the Entity was extracted from -- -- This is experimental implementation. -- This may be replaced by more definite types. type EntityIndices = [Int] data Entity a = Entity { -- | The detail information of the specific entity types (HashTag, URL, User) entityBody :: a , -- | The character positions the Entity was extracted from entityIndices :: EntityIndices } deriving (Show, Eq, Data, Typeable, Generic, Generic1) instance FromJSON a => FromJSON (Entity a) where parseJSON v@(Object o) = Entity <$> parseJSON v <*> o .: "indices" parseJSON v = fail $ "couldn't parse entity wrapper from: " ++ show v instance ToJSON a => ToJSON (Entity a) where toJSON Entity {..} = case toJSON entityBody of (Object o) -> Object $ KeyMap.insert "indices" (toJSON entityIndices) o _ -> error "Entity body must produce an object." data ExtendedEntities = ExtendedEntities { exeMedia :: [Entity ExtendedEntity] } deriving (Show, Eq, Data, Typeable, Generic) instance FromJSON ExtendedEntities where parseJSON (Object o) = ExtendedEntities <$> o .:? "media" .!= [] parseJSON v = fail $ "couldn't parse extended entity from: " ++ show v instance ToJSON ExtendedEntities where toJSON ExtendedEntities {..} = object ["media" .= exeMedia] -- "video_info": { -- "aspect_ratio": [ -- 9, -- 16 -- ], -- "duration_millis": 10704, -- "variants": [ -- { -- "bitrate": 320000, -- "content_type": "video/mp4", -- "url": "https://video.twimg.com/ext_tw_video/869317980307415040/pu/vid/180x320/FMei8yCw7yc_Z7e-.mp4" -- }, -- { -- "bitrate": 2176000, -- "content_type": "video/mp4", -- "url": "https://video.twimg.com/ext_tw_video/869317980307415040/pu/vid/720x1280/octt5pFbISkef8RB.mp4" -- }, -- { -- "bitrate": 832000, -- "content_type": "video/mp4", -- "url": "https://video.twimg.com/ext_tw_video/869317980307415040/pu/vid/360x640/2OmqK74SQ9jNX8mZ.mp4" -- }, -- { -- "content_type": "application/x-mpegURL", -- "url": "https://video.twimg.com/ext_tw_video/869317980307415040/pu/pl/wcJQJ2nxiFU4ZZng.m3u8" -- } -- ] -- } data Variant = Variant { vBitrate :: Maybe Int , vContentType :: Text , vUrl :: URIString } deriving (Show, Eq, Data, Typeable, Generic) instance FromJSON Variant where parseJSON (Object o) = Variant <$> o .:? "bitrate" <*> o .: "content_type" <*> o .: "url" parseJSON v = fail $ "couldn't parse variant from:" ++ show v instance ToJSON Variant where toJSON Variant {..} = object [ "bitrate" .= vBitrate , "content_type" .= vContentType , "url" .= vUrl ] data VideoInfo = VideoInfo { vsAspectRatio :: [Int] , vsDurationMillis :: Maybe Int , vsVariants :: [Variant] } deriving (Show, Eq, Data, Typeable, Generic) instance FromJSON VideoInfo where parseJSON (Object o) = VideoInfo <$> o .: "aspect_ratio" .!= [] <*> o .:? "duration_millis" <*> o .: "variants" .!= [] parseJSON v = fail $ "couldn't parse video info from:" ++ show v instance ToJSON VideoInfo where toJSON VideoInfo {..} = object [ "aspect_ratio" .= vsAspectRatio , "duration_millis" .= vsDurationMillis , "variants" .= vsVariants ] -- Extended entities are like entities, but contain special media features like -- video or multiple photos data ExtendedEntity = ExtendedEntity { exeID :: StatusId , exeMediaUrl :: URIString , exeMediaUrlHttps :: URIString , exeSizes :: HashMap Text MediaSize , exeType :: Text , exeVideoInfo :: Maybe VideoInfo , exeDurationMillis :: Maybe Double , exeExtAltText :: Maybe String , exeURL :: URLEntity } deriving (Show, Eq, Data, Typeable, Generic) instance FromJSON ExtendedEntity where parseJSON v@(Object o) = ExtendedEntity <$> o .: "id" <*> o .: "media_url" <*> o .: "media_url_https" <*> o .: "sizes" <*> o .: "type" <*> o .:? "video_info" <*> o .:? "duration_millis" <*> o .:? "ext_alt_text" <*> parseJSON v parseJSON v = fail $ "couldn't parse extended entity from:" ++ show v instance ToJSON ExtendedEntity where toJSON ExtendedEntity {..} = object [ "id" .= exeID , "media_url" .= exeMediaUrl , "media_url_https" .= exeMediaUrlHttps , "sizes" .= exeSizes , "type" .= exeType , "video_info" .= exeVideoInfo , "duration_millis" .= exeDurationMillis , "ext_alt_text" .= exeExtAltText , "url" .= ueURL exeURL , "expanded_url" .= ueExpanded exeURL , "display_url" .= ueDisplay exeURL ] data Contributor = Contributor { contributorId :: UserId , contributorScreenName :: Maybe Text } deriving (Show, Eq, Data, Typeable, Generic) instance FromJSON Contributor where parseJSON (Object o) = Contributor <$> o .: "id" <*> o .:? "screen_name" parseJSON v@(Number _) = Contributor <$> parseJSON v <*> pure Nothing parseJSON v = fail $ "couldn't parse contributor from: " ++ show v instance ToJSON Contributor where toJSON Contributor {..} = object [ "id" .= contributorId , "screen_name" .= contributorScreenName ] -- | Image size type. This type is included in the API response of \"\/1.1\/media\/upload.json\". data ImageSizeType = ImageSizeType { imageSizeTypeWidth :: Int , imageSizeTypeHeight :: Int , imageSizeTypeType :: Text } deriving (Show, Eq, Data, Typeable, Generic) instance FromJSON ImageSizeType where parseJSON (Object o) = ImageSizeType <$> o .: "w" <*> o .: "h" <*> o .: "image_type" parseJSON v = fail $ "unknown value: " ++ show v instance ToJSON ImageSizeType where toJSON ImageSizeType {..} = object [ "w" .= imageSizeTypeWidth , "h" .= imageSizeTypeHeight , "image_type" .= imageSizeTypeType ] -- | This type is represents the API response of \"\/1.1\/media\/upload.json\". -- See . data UploadedMedia = UploadedMedia { uploadedMediaId :: Integer , uploadedMediaSize :: Integer , uploadedMediaImage :: ImageSizeType } deriving (Show, Eq, Data, Typeable, Generic) instance FromJSON UploadedMedia where parseJSON (Object o) = UploadedMedia <$> o .: "media_id" <*> o .: "size" <*> o .: "image" parseJSON v = fail $ "unknown value: " ++ show v instance ToJSON UploadedMedia where toJSON UploadedMedia {..} = object [ "media_id" .= uploadedMediaId , "size" .= uploadedMediaSize , "image" .= uploadedMediaImage ] -- | unicode code point indices, identifying the inclusive start and exclusive end of the displayable content of the Tweet. data DisplayTextRange = DisplayTextRange { displayTextRangeStart :: Int , -- | exclusive displayTextRangeEnd :: Int } deriving (Show, Eq, Ord, Data, Typeable, Generic) instance FromJSON DisplayTextRange where parseJSON v = do parseJSON v >>= \case [s, e] -> pure $ DisplayTextRange s e unexpected -> fail $ "parsing DisplayTextRange failed, expected [Int, Int], but got: " ++ show unexpected instance ToJSON DisplayTextRange where toJSON (DisplayTextRange s e) = toJSON [s, e] twitter-types-0.11.0/tests/spec_main.hs0000644000000000000000000000055614144754426016300 0ustar0000000000000000module Main where import qualified PropFromToJSONTest import qualified StatusTest import Test.Tasty import qualified TypesTest tests :: TestTree tests = testGroup "Tests" [ testGroup "Unit Test" [TypesTest.tests, StatusTest.tests] , testGroup "Property Test" [PropFromToJSONTest.tests] ] main :: IO () main = defaultMain tests twitter-types-0.11.0/tests/Fixtures.hs0000644000000000000000000000134514144754426016150 0ustar0000000000000000{-# LANGUAGE CPP #-} module Fixtures where import Data.Aeson import Data.ByteString as S import System.FilePath import Test.Tasty.HUnit fixturePath :: FilePath -> FilePath fixturePath filename = takeDirectory __FILE__ "fixtures" filename readFixtureFile :: FilePath -> IO ByteString readFixtureFile = S.readFile . fixturePath withFixtureJSON :: FromJSON a => FilePath -> (a -> Assertion) -> Assertion withFixtureJSON filename assertions = do body <- readFixtureFile filename withJSON body assertions withJSON :: FromJSON a => ByteString -> (a -> Assertion) -> Assertion withJSON body assertions = do case eitherDecodeStrict' body of Left err -> assertFailure $ err Right result -> assertions result twitter-types-0.11.0/tests/Instances.hs0000644000000000000000000001222714144754426016267 0ustar0000000000000000{-# LANGUAGE CPP #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TypeOperators #-} {-# OPTIONS_GHC -fno-warn-orphans #-} module Instances where import Control.Applicative import Data.Aeson #if MIN_VERSION_aeson(2, 0, 0) import Data.Aeson.KeyMap as KeyMap #else import Data.HashMap.Strict as KeyMap #endif import Data.HashMap.Strict as HashMap import Data.String import qualified Data.Text as T import Data.Time (UTCTime (..), defaultTimeLocale, fromGregorian, readTime) import Generic.Random import Test.Tasty.QuickCheck import Web.Twitter.Types instance IsString UTCTime where fromString = readTime defaultTimeLocale twitterTimeFormat instance Arbitrary UTCTime where arbitrary = do randomDay <- choose (1, 29) :: Gen Int randomMonth <- choose (1, 12) :: Gen Int randomYear <- choose (2001, 2002) :: Gen Integer randomTime <- choose (0, 86401) :: Gen Int return $ UTCTime (fromGregorian randomYear randomMonth randomDay) (fromIntegral randomTime) instance Arbitrary T.Text where arbitrary = T.pack <$> arbitrary instance Arbitrary Value where arbitrary = elements [ Object KeyMap.empty , Object (KeyMap.fromList [("test", Number 2), ("value", String "non empty")]) ] -- derive makeArbitrary ''StreamingAPI instance Arbitrary Status where arbitrary = do qt <- frequency [(5, Just <$> arbitrary), (95, pure Nothing)] :: Gen (Maybe Status) rt <- frequency [(5, Just <$> arbitrary), (95, pure Nothing)] :: Gen (Maybe Status) Status <$> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary <*> pure Nothing <*> pure (statusId <$> qt) <*> pure qt <*> arbitrary <*> arbitrary <*> pure rt <*> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary instance Arbitrary SearchStatus where arbitrary = genericArbitraryU instance Arbitrary SearchMetadata where arbitrary = genericArbitraryU instance Arbitrary RetweetedStatus where arbitrary = genericArbitraryU instance Arbitrary DirectMessage where arbitrary = genericArbitrarySingleG customGens where customGens :: Gen Integer :+ () customGens = (getNonNegative <$> arbitrary) :+ () instance Arbitrary EventTarget where arbitrary = genericArbitraryU instance Arbitrary Event where arbitrary = genericArbitraryU instance Arbitrary Delete where arbitrary = genericArbitraryU instance Arbitrary User where arbitrary = genericArbitraryU instance Arbitrary List where arbitrary = genericArbitraryU instance Arbitrary HashTagEntity where arbitrary = genericArbitraryU instance Arbitrary UserEntity where arbitrary = genericArbitraryU instance Arbitrary URLEntity where arbitrary = genericArbitraryU instance Arbitrary MediaEntity where arbitrary = do ms <- arbitrary MediaEntity <$> arbitrary <*> arbitrary <*> pure (HashMap.fromList [("medium", ms)]) <*> arbitrary <*> arbitrary <*> arbitrary instance Arbitrary MediaSize where arbitrary = genericArbitraryU instance Arbitrary Coordinates where arbitrary = genericArbitraryU instance Arbitrary Place where arbitrary = do Place HashMap.empty <$> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary instance Arbitrary BoundingBox where arbitrary = genericArbitraryU instance Arbitrary Entities where arbitrary = genericArbitraryU instance Arbitrary ExtendedEntities where arbitrary = genericArbitraryU instance Arbitrary Variant where arbitrary = genericArbitraryU instance Arbitrary VideoInfo where arbitrary = genericArbitraryU instance Arbitrary ExtendedEntity where arbitrary = do ms <- arbitrary ExtendedEntity <$> arbitrary <*> arbitrary <*> arbitrary <*> pure (HashMap.fromList [("medium", ms)]) <*> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary instance Arbitrary a => Arbitrary (Entity a) where arbitrary = do a <- arbitrary ind <- arbitrary return $ Entity a ind instance Arbitrary Contributor where arbitrary = genericArbitraryU instance Arbitrary ImageSizeType where arbitrary = genericArbitraryU instance Arbitrary UploadedMedia where arbitrary = genericArbitraryU instance Arbitrary DisplayTextRange where arbitrary = genericArbitraryU twitter-types-0.11.0/tests/PropFromToJSONTest.hs0000644000000000000000000000422514144754426017740 0ustar0000000000000000{-# LANGUAGE TemplateHaskell #-} module PropFromToJSONTest where import Data.Aeson import qualified Data.Aeson.Types as Aeson import Instances () import Test.Tasty import Test.Tasty.QuickCheck import Test.Tasty.TH import Web.Twitter.Types fromToJSON :: (Eq a, FromJSON a, ToJSON a) => a -> Bool fromToJSON obj = case fromJSON . toJSON $ obj of Aeson.Error _ -> False Aeson.Success a -> a == obj prop_fromToStatus :: Status -> Bool prop_fromToStatus = fromToJSON prop_fromToSearchStatus :: SearchStatus -> Bool prop_fromToSearchStatus = fromToJSON prop_fromToSearchMetadata :: SearchMetadata -> Bool prop_fromToSearchMetadata = fromToJSON prop_fromToRetweetedStatus :: RetweetedStatus -> Bool prop_fromToRetweetedStatus = fromToJSON prop_fromToDirectMessage :: DirectMessage -> Bool prop_fromToDirectMessage = fromToJSON prop_fromToEventTarget :: EventTarget -> Bool prop_fromToEventTarget = fromToJSON prop_fromToEvent :: Event -> Bool prop_fromToEvent = fromToJSON prop_fromToDelete :: Delete -> Bool prop_fromToDelete = fromToJSON prop_fromToUser :: User -> Bool prop_fromToUser = fromToJSON prop_fromToList :: List -> Bool prop_fromToList = fromToJSON prop_fromToHashTagEntity :: HashTagEntity -> Bool prop_fromToHashTagEntity = fromToJSON prop_fromToUserEntity :: UserEntity -> Bool prop_fromToUserEntity = fromToJSON prop_fromToURLEntity :: URLEntity -> Bool prop_fromToURLEntity = fromToJSON prop_fromToMediaEntity :: MediaEntity -> Bool prop_fromToMediaEntity = fromToJSON prop_fromToMediaSize :: MediaSize -> Bool prop_fromToMediaSize = fromToJSON prop_fromToCoordinates :: Coordinates -> Bool prop_fromToCoordinates = fromToJSON prop_fromToPlace :: Place -> Bool prop_fromToPlace = fromToJSON prop_fromToBoundingBox :: BoundingBox -> Bool prop_fromToBoundingBox = fromToJSON prop_fromToEntities :: Entities -> Bool prop_fromToEntities = fromToJSON prop_fromToContributor :: Contributor -> Bool prop_fromToContributor = fromToJSON prop_fromToImageSizeType :: ImageSizeType -> Bool prop_fromToImageSizeType = fromToJSON prop_fromToUploadedMedia :: UploadedMedia -> Bool prop_fromToUploadedMedia = fromToJSON tests :: TestTree tests = $(testGroupGenerator) twitter-types-0.11.0/tests/StatusTest.hs0000644000000000000000000003077014144754426016466 0ustar0000000000000000{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE TemplateHaskell #-} module StatusTest where import Data.Aeson import qualified Data.Aeson.Types as Aeson import qualified Data.HashMap.Strict as M import Data.Maybe import Fixtures import Instances () import Test.Tasty import Test.Tasty.HUnit import Test.Tasty.TH import Web.Twitter.Types example_compatibility_classic_13995 :: Status -> Assertion example_compatibility_classic_13995 obj = do statusCreatedAt obj @?= "Mon Mar 07 15:13:47 +0000 2016" statusId obj @?= 706860403981099008 statusText obj @?= "Peek-a-boo! https://t.co/R3P6waHxRa" statusSource obj @?= "OS X" statusTruncated obj @?= False statusEntities obj @?= Just ( Entities { enHashTags = [] , enUserMentions = [] , enURLs = [] , enMedia = [ Entity { entityBody = MediaEntity { meType = "photo" , meId = 706860403746181121 , meSizes = M.fromList [ ( "small" , MediaSize { msWidth = 340 , msHeight = 226 , msResize = "fit" } ) , ( "large" , MediaSize { msWidth = 1024 , msHeight = 680 , msResize = "fit" } ) , ( "medium" , MediaSize { msWidth = 600 , msHeight = 398 , msResize = "fit" } ) , ( "thumb" , MediaSize { msWidth = 150 , msHeight = 150 , msResize = "crop" } ) ] , meMediaURL = "http://pbs.twimg.com/media/Cc9FyscUkAEQaOw.jpg" , meMediaURLHttps = "https://pbs.twimg.com/media/Cc9FyscUkAEQaOw.jpg" , meURL = URLEntity { ueURL = "https://t.co/R3P6waHxRa" , ueExpanded = "http://twitter.com/jeremycloud/status/706860403981099008/photo/1" , ueDisplay = "pic.twitter.com/R3P6waHxRa" } } , entityIndices = [12, 35] } ] } ) statusExtendedEntities obj @?= Just ( ExtendedEntities { exeMedia = [ Entity { entityBody = ExtendedEntity { exeID = 706860403746181121 , exeMediaUrl = "http://pbs.twimg.com/media/Cc9FyscUkAEQaOw.jpg" , exeMediaUrlHttps = "https://pbs.twimg.com/media/Cc9FyscUkAEQaOw.jpg" , exeSizes = M.fromList [ ( "small" , MediaSize { msWidth = 340 , msHeight = 226 , msResize = "fit" } ) , ( "large" , MediaSize { msWidth = 1024 , msHeight = 680 , msResize = "fit" } ) , ( "medium" , MediaSize { msWidth = 600 , msHeight = 398 , msResize = "fit" } ) , ( "thumb" , MediaSize { msWidth = 150 , msHeight = 150 , msResize = "crop" } ) ] , exeType = "photo" , exeVideoInfo = Nothing , exeDurationMillis = Nothing , exeExtAltText = Nothing , exeURL = URLEntity { ueURL = "https://t.co/R3P6waHxRa" , ueExpanded = "http://twitter.com/jeremycloud/status/706860403981099008/photo/1" , ueDisplay = "pic.twitter.com/R3P6waHxRa" } } , entityIndices = [12, 35] } ] } ) statusInReplyToStatusId obj @?= Nothing statusInReplyToUserId obj @?= Nothing statusFavorited obj @?= Just False statusQuotedStatus obj @?= Nothing statusQuotedStatusId obj @?= Nothing statusRetweetCount obj @?= 0 (userScreenName . statusUser) obj @?= "jeremycloud" statusRetweetedStatus obj @?= Nothing statusPlace obj @?= Nothing statusFavoriteCount obj @?= 8 statusLang obj @?= Just "en" statusPossiblySensitive obj @?= Just False statusCoordinates obj @?= Nothing case_compatibility_classic_13995 :: Assertion case_compatibility_classic_13995 = do withFixtureJSON "tweet-updates/compatibility_classic_13995.json" $ example_compatibility_classic_13995 withFixtureJSON "tweet-updates/compatibility_classic_13995_extended.json" $ example_compatibility_classic_13995 -- case_compatibility_classic_hidden_13797 :: Assertion -- case_compatibility_classic_hidden_13797 = withFixtureJSON "tweet-updates/compatibility_classic_hidden_13797" $ \obj -> do -- case_compatibility_extended_13996 :: Assertion -- case_compatibility_extended_13996 = withFixtureJSON "tweet-updates/compatibility_extended_13996" $ \obj -> do -- case_compatibilityplus_classic_13994 :: Assertion -- case_compatibilityplus_classic_13994 = withFixtureJSON "tweet-updates/compatibilityplus_classic_13994" $ \obj -> do -- case_compatibilityplus_classic_hidden_13797 :: Assertion -- case_compatibilityplus_classic_hidden_13797 = withFixtureJSON "tweet-updates/compatibilityplus_classic_hidden_13797" $ \obj -> do -- case_compatibilityplus_extended_13997 :: Assertion -- case_compatibilityplus_extended_13997 = withFixtureJSON "tweet-updates/compatibilityplus_extended_13997" $ \obj -> do -- case_extended_classic_14002 :: Assertion -- case_extended_classic_14002 = withFixtureJSON "tweet-updates/extended_classic_14002" $ \obj -> do case_extended_classic_hidden_13761 :: Assertion case_extended_classic_hidden_13761 = withFixtureJSON "tweet-updates/extended_classic_hidden_13761.json" $ \obj -> do statusTruncated obj @?= False statusExtendedEntities obj @?= Just ( ExtendedEntities { exeMedia = [ Entity { entityBody = ExtendedEntity { exeID = 743479379079004160 , exeMediaUrl = "http://pbs.twimg.com/tweet_video_thumb/ClFejl_VAAAo9Xk.jpg" , exeMediaUrlHttps = "https://pbs.twimg.com/tweet_video_thumb/ClFejl_VAAAo9Xk.jpg" , exeSizes = M.fromList [ ( "small" , MediaSize { msWidth = 340 , msHeight = 190 , msResize = "fit" } ) , ( "large" , MediaSize { msWidth = 480 , msHeight = 268 , msResize = "fit" } ) , ( "medium" , MediaSize { msWidth = 480 , msHeight = 268 , msResize = "fit" } ) , ( "thumb" , MediaSize { msWidth = 150 , msHeight = 150 , msResize = "crop" } ) ] , exeType = "animated_gif" , exeVideoInfo = Just (VideoInfo {vsAspectRatio = [120, 67], vsDurationMillis = Nothing, vsVariants = [Variant {vBitrate = Just 0, vContentType = "video/mp4", vUrl = "https://pbs.twimg.com/tweet_video/ClFejl_VAAAo9Xk.mp4"}]}) , exeDurationMillis = Nothing , exeExtAltText = Nothing , exeURL = URLEntity {ueURL = "https://t.co/VnJMDg3cbS", ueExpanded = "http://twitter.com/beyond_oneforty/status/743479431658758145/photo/1", ueDisplay = "pic.twitter.com/VnJMDg3cbS"} } , entityIndices = [48, 71] } ] } ) case_extended_extended_14001 :: Assertion case_extended_extended_14001 = withFixtureJSON "tweet-updates/extended_extended_14001.json" $ \obj -> do statusText obj @?= "@twitter @twitterdev has more details about these changes at https://t.co/ZnXoRQy8mK. Thanks for making @twitter more expressive! https://t.co/AWmiH870F7" statusTruncated obj @?= False statusDisplayTextRange obj @?= Just (DisplayTextRange 9 130) tests :: TestTree tests = $(testGroupGenerator) twitter-types-0.11.0/tests/TypesTest.hs0000644000000000000000000003304214144754426016302 0ustar0000000000000000{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE TemplateHaskell #-} module TypesTest where import Data.Aeson import qualified Data.Aeson.Types as Aeson import qualified Data.HashMap.Strict as M import Data.Maybe import Data.Time.Clock.POSIX import Fixtures import Instances () import Test.Tasty import Test.Tasty.HUnit import Test.Tasty.TH import Web.Twitter.Types case_parseStatus :: Assertion case_parseStatus = withFixtureJSON "status01.json" $ \obj -> do statusCreatedAt obj @?= "Sat Sep 10 22:23:38 +0000 2011" statusId obj @?= 112652479837110273 statusText obj @?= "@twitter meets @seepicturely at #tcdisrupt cc.@boscomonkey @episod http://t.co/6J2EgYM" statusSource obj @?= "Instagram" statusTruncated obj @?= False statusEntities obj @?= Nothing statusExtendedEntities obj @?= Nothing statusInReplyToStatusId obj @?= Nothing statusInReplyToUserId obj @?= Just 783214 statusFavorited obj @?= Just False statusQuotedStatus obj @?= Nothing statusQuotedStatusId obj @?= Nothing statusRetweetCount obj @?= 0 (userScreenName . statusUser) obj @?= "imeoin" statusRetweetedStatus obj @?= Nothing statusPlace obj @?= Nothing statusFavoriteCount obj @?= 0 statusLang obj @?= Nothing statusPossiblySensitive obj @?= Just False statusCoordinates obj @?= Nothing case_parseStatusQuoted :: Assertion case_parseStatusQuoted = withFixtureJSON "status_quoted.json" $ \obj -> do statusId obj @?= 641660763770372100 statusText obj @?= "Wow! Congrats! https://t.co/EPMMldEcci" statusQuotedStatusId obj @?= Just 641653574284537900 let qs = fromJust $ statusQuotedStatus obj statusCreatedAt qs @?= "Wed Sep 09 16:45:08 +0000 2015" statusId qs @?= 641653574284537900 statusText qs @?= "Very happy to say that I'm joining @mesosphere as a Distributed Systems Engineer!" statusSource qs @?= "Twitter Web Client" let ent = fromJust $ statusEntities qs enURLs ent @?= [] enMedia ent @?= [] enHashTags ent @?= [] map (userEntityUserId . entityBody) (enUserMentions ent) @?= [1872399366] map (userEntityUserScreenName . entityBody) (enUserMentions ent) @?= ["mesosphere"] statusExtendedEntities qs @?= Nothing statusInReplyToStatusId qs @?= Nothing statusInReplyToUserId qs @?= Nothing statusFavorited qs @?= Just False statusQuotedStatus qs @?= Nothing statusQuotedStatusId qs @?= Nothing statusRetweetCount qs @?= 7 (userScreenName . statusUser) qs @?= "neil_conway" statusRetweeted qs @?= Just False statusRetweetedStatus qs @?= Nothing statusPlace qs @?= Nothing statusFavoriteCount qs @?= 63 statusLang qs @?= Just "en" statusPossiblySensitive qs @?= Nothing statusCoordinates qs @?= Nothing case_parseStatusWithPhoto :: Assertion case_parseStatusWithPhoto = withFixtureJSON "status_thimura_with_photo.json" $ \obj -> do statusId obj @?= 491143410770657280 statusText obj @?= "近所の海です http://t.co/FjSOU8dDoD" statusTruncated obj @?= False let ent = fromJust $ statusEntities obj enHashTags ent @?= [] enUserMentions ent @?= [] enURLs ent @?= [] length (enMedia ent) @?= 1 map (meMediaURLHttps . entityBody) (enMedia ent) @?= ["https://pbs.twimg.com/media/BtDkUVaCQAIpWBU.jpg"] let exents = fromJust $ statusExtendedEntities obj let media = exeMedia exents length media @?= 1 let exent = entityBody $ head media exeID exent @?= 491143397378244610 ueURL (exeURL exent) @?= "http://t.co/FjSOU8dDoD" statusInReplyToStatusId obj @?= Nothing statusInReplyToUserId obj @?= Nothing statusFavorited obj @?= Just False statusRetweetCount obj @?= 4 (userScreenName . statusUser) obj @?= "thimura" statusRetweetedStatus obj @?= Nothing statusPlace obj @?= Nothing statusFavoriteCount obj @?= 9 statusLang obj @?= Just "ja" statusPossiblySensitive obj @?= Just False statusCoordinates obj @?= Nothing case_parseStatusIncludeEntities :: Assertion case_parseStatusIncludeEntities = withFixtureJSON "status_with_entity.json" $ \obj -> do statusId obj @?= 112652479837110273 statusRetweetCount obj @?= 0 (userScreenName . statusUser) obj @?= "imeoin" let ent = fromMaybe (Entities [] [] [] []) $ statusEntities obj (map entityIndices . enHashTags) ent @?= [[32, 42]] (hashTagText . entityBody . head . enHashTags) ent @?= "tcdisrupt" case_parseSearchStatusMetadata :: Assertion case_parseSearchStatusMetadata = withFixtureJSON "search_haskell.json" $ \obj -> do let status = (searchResultStatuses obj) :: [Status] length status @?= 1 let metadata = searchResultSearchMetadata obj searchMetadataMaxId metadata @?= 495597397733433345 searchMetadataSinceId metadata @?= 0 searchMetadataRefreshURL metadata @?= "?since_id=495597397733433345&q=haskell&include_entities=1" searchMetadataNextResults metadata @?= Just "?max_id=495594369802440705&q=haskell&include_entities=1" searchMetadataCount metadata @?= 1 searchMetadataCompletedIn metadata @?= Just 0.043 searchMetadataSinceIdStr metadata @?= "0" searchMetadataQuery metadata @?= "haskell" searchMetadataMaxIdStr metadata @?= "495597397733433345" case_parseSearchStatusBodyStatus :: Assertion case_parseSearchStatusBodyStatus = withFixtureJSON "search_haskell.json" $ \obj -> do let status = (searchResultStatuses obj) :: [Status] length status @?= 1 statusText (head status) @?= "haskell" case_parseSearchStatusBodySearchStatus :: Assertion case_parseSearchStatusBodySearchStatus = withFixtureJSON "search_haskell.json" $ \obj -> do let status = (searchResultStatuses obj) :: [SearchStatus] length status @?= 1 searchStatusText (head status) @?= "haskell" data DMList = DMList { dmList :: [DirectMessage] } deriving (Show, Eq) instance FromJSON DMList where parseJSON = withObject "DMList" $ \obj -> DMList <$> obj .: "events" case_parseDirectMessageList :: Assertion case_parseDirectMessageList = withFixtureJSON "direct_message_event_list.json" $ \obj -> do dmList obj @?= [ DirectMessage { dmId = 123123123123123123 , dmCreatedTimestamp = read "2019-10-13 18:15:48.951 UTC" , dmTargetRecipientId = 186712193 , dmSenderId = 69179963 , dmText = "hello @thimura" , dmEntities = Entities { enHashTags = [] , enUserMentions = [ Entity { entityBody = UserEntity { userEntityUserId = 69179963 , userEntityUserName = "ちむら" , userEntityUserScreenName = "thimura" } , entityIndices = [6, 14] } ] , enURLs = [] , enMedia = [] } } , DirectMessage { dmId = 25252525252525 , dmCreatedTimestamp = read "2019-10-13 18:06:46.14 UTC" , dmTargetRecipientId = 186712193 , dmSenderId = 69179963 , dmText = "hello" , dmEntities = Entities {enHashTags = [], enUserMentions = [], enURLs = [], enMedia = []} } ] case_parseEventFavorite :: Assertion case_parseEventFavorite = withFixtureJSON "event_favorite_thimura.json" $ \obj -> do evCreatedAt obj @?= "Sat Aug 02 16:32:01 +0000 2014" evEvent obj @?= "favorite" let Just (ETStatus targetObj) = evTargetObject obj statusId targetObj @?= 495597326736449536 statusText targetObj @?= "haskell" let ETUser targetUser = evTarget obj userScreenName targetUser @?= "thimura" let ETUser sourceUser = evSource obj userScreenName sourceUser @?= "thimura_shinku" case_parseEventUnfavorite :: Assertion case_parseEventUnfavorite = withFixtureJSON "event_unfavorite_thimura.json" $ \obj -> do evCreatedAt obj @?= "Sat Aug 02 16:32:10 +0000 2014" evEvent obj @?= "unfavorite" let Just (ETStatus targetObj) = evTargetObject obj statusId targetObj @?= 495597326736449536 statusText targetObj @?= "haskell" let ETUser targetUser = evTarget obj userScreenName targetUser @?= "thimura" let ETUser sourceUser = evSource obj userScreenName sourceUser @?= "thimura_shinku" case_parseDelete :: Assertion case_parseDelete = withFixtureJSON "delete.json" $ \obj -> do delId obj @?= 495607981833064448 delUserId obj @?= 2566877347 case_parseErrorMsg :: Assertion case_parseErrorMsg = withFixtureJSON "error_not_authorized.json" $ \value -> case parseStatus value of Aeson.Error str -> "Not authorized" @=? str Aeson.Success _ -> assertFailure "errorMsgJson should be parsed as an error." where parseStatus :: Value -> Aeson.Result Status parseStatus = Aeson.parse parseJSON case_parseMediaEntity :: Assertion case_parseMediaEntity = withFixtureJSON "media_entity.json" $ \obj -> do let entities = statusEntities obj assertBool "entities should not empty" $ isJust entities let Just ent = entities media = enMedia ent length media @?= 1 let me = entityBody $ head media meType me @?= "photo" meId me @?= 114080493040967680 let sizes = meSizes me assertBool "sizes must contains \"thumb\"" $ M.member "thumb" sizes assertBool "sizes must contains \"large\"" $ M.member "large" sizes let Just mediaSize = M.lookup "large" sizes msWidth mediaSize @?= 226 msHeight mediaSize @?= 238 msResize mediaSize @?= "fit" ueURL (meURL me) @?= "http://t.co/rJC5Pxsu" meMediaURLHttps me @?= "https://pbs.twimg.com/media/AZVLmp-CIAAbkyy.jpg" case_parseEmptyEntity :: Assertion case_parseEmptyEntity = withJSON "{}" $ \entity -> do length (enHashTags entity) @?= 0 length (enUserMentions entity) @?= 0 length (enURLs entity) @?= 0 length (enMedia entity) @?= 0 case_parseEntityHashTag :: Assertion case_parseEntityHashTag = withFixtureJSON "entity01.json" $ \entity -> do length (enHashTags entity) @?= 1 length (enUserMentions entity) @?= 1 length (enURLs entity) @?= 1 length (enMedia entity) @?= 0 let urlEntity = entityBody . head . enURLs $ entity ueURL urlEntity @?= "http://t.co/IOwBrTZR" ueExpanded urlEntity @?= "http://www.youtube.com/watch?v=oHg5SJYRHA0" ueDisplay urlEntity @?= "youtube.com/watch?v=oHg5SJ\x2026" let mentionsUser = entityBody . head . enUserMentions $ entity userEntityUserName mentionsUser @?= "Twitter API" userEntityUserScreenName mentionsUser @?= "twitterapi" userEntityUserId mentionsUser @?= 6253282 let HashTagEntity hashtag = entityBody . head . enHashTags $ entity hashtag @?= "lol" case_parseExtendedEntities :: Assertion case_parseExtendedEntities = withFixtureJSON "media_extended_entity.json" $ \obj -> do let entities = statusExtendedEntities obj assertBool "entities should not empty" $ isJust entities let Just ent = entities media = exeMedia ent length media @?= 4 let me = entityBody $ head media ueURL (exeURL me) @?= "https://t.co/Qi316FhOwe" exeMediaUrl me @?= "http://pbs.twimg.com/media/Coju86fUIAEUcRC.jpg" exeExtAltText me @?= Just "A small tabby kitten" exeType me @?= "photo" case_parseUser :: Assertion case_parseUser = withFixtureJSON "user_thimura.json" $ \obj -> do userId obj @?= 69179963 userName obj @?= "ちむら" userScreenName obj @?= "thimura" userDescription obj @?= Just "真紅かわいい" userLocation obj @?= Just "State# Irotoridori.No.World" userProfileImageURL obj @?= Just "http://pbs.twimg.com/profile_images/414044387346116609/VNMfLpY7_normal.png" userURL obj @?= Just "http://t.co/TFUAsAffX0" userProtected obj @?= False userFollowersCount obj @?= 754 userFriendsCount obj @?= 780 userStatusesCount obj @?= 24709 userLang obj @?= Just "en" userCreatedAt obj @?= "Thu Aug 27 02:48:06 +0000 2009" userFavoritesCount obj @?= 17313 case_parseUserLangNull :: Assertion case_parseUserLangNull = withFixtureJSON "user_thimura_lang_null.json" $ \obj -> do userId obj @?= 69179963 userName obj @?= "ちむら" userScreenName obj @?= "thimura" userDescription obj @?= Just "真紅かわいい" userLocation obj @?= Just "State# Irotoridori.No.World" userProfileImageURL obj @?= Just "http://pbs.twimg.com/profile_images/414044387346116609/VNMfLpY7_normal.png" userURL obj @?= Just "http://t.co/TFUAsAffX0" userProtected obj @?= False userFollowersCount obj @?= 754 userFriendsCount obj @?= 780 userStatusesCount obj @?= 24709 -- N.B. the only difference between this one and case_parseUser is in lang userLang obj @?= Nothing userCreatedAt obj @?= "Thu Aug 27 02:48:06 +0000 2009" userFavoritesCount obj @?= 17313 case_parseList :: Assertion case_parseList = withFixtureJSON "list_thimura_haskell.json" $ \obj -> do listId obj @?= 20849097 listName obj @?= "haskell" listFullName obj @?= "@thimura/haskell" listMemberCount obj @?= 50 listSubscriberCount obj @?= 1 listMode obj @?= "public" (userScreenName . listUser) obj @?= "thimura" tests :: TestTree tests = $(testGroupGenerator) twitter-types-0.11.0/LICENSE0000644000000000000000000000245314144754426013647 0ustar0000000000000000Copyright (c)2011, Takahiro Himura All rights reserved. Redistribution and use in source and binary forms, with or without modification, are permitted provided that the following conditions are met: * Redistributions of source code must retain the above copyright notice, this list of conditions and the following disclaimer. * Redistributions in binary form must reproduce the above copyright notice, this list of conditions and the following disclaimer in the documentation and/or other materials provided with the distribution. THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. twitter-types-0.11.0/Setup.hs0000644000000000000000000000011214144754426014264 0ustar0000000000000000#!/usr/bin/env runhaskell import Distribution.Simple main = defaultMain twitter-types-0.11.0/twitter-types.cabal0000644000000000000000000000316714144754426016475 0ustar0000000000000000cabal-version: >=1.10 name: twitter-types version: 0.11.0 license: BSD3 license-file: LICENSE maintainer: Takahiro HIMURA author: Takahiro HIMURA stability: Experimental tested-with: ghc ==8.8.4 ghc ==8.10.4 ghc ==9.0.1 homepage: https://github.com/himura/twitter-types synopsis: Twitter JSON parser and types description: Please see the README on Github at category: Web build-type: Simple extra-source-files: README.md tests/fixtures/*.json tests/fixtures/tweet-updates/*.json source-repository head type: git location: git://github.com/himura/twitter-types.git library exposed-modules: Web.Twitter.Types default-language: Haskell2010 ghc-options: -Wall build-depends: base >=4.9 && <5, aeson >=0.3.2.2, text, time >=1.5, unordered-containers test-suite tests type: exitcode-stdio-1.0 main-is: spec_main.hs hs-source-dirs: tests other-modules: Fixtures Instances PropFromToJSONTest StatusTest TypesTest default-language: Haskell2010 ghc-options: -Wall build-depends: base >=4.9 && <5, twitter-types, aeson, attoparsec, bytestring, generic-random, directory, filepath, tasty >=0.7, tasty-hunit, tasty-quickcheck, tasty-th, text, time, unordered-containers twitter-types-0.11.0/README.md0000644000000000000000000000064614144754426014123 0ustar0000000000000000twitter-types ============= ![CI](https://github.com/himura/twitter-types/workflows/CI/badge.svg) [![Hackage](https://img.shields.io/hackage/v/twitter-types.svg?style=flat)](https://hackage.haskell.org/package/twitter-types) [![Hackage-Deps](https://img.shields.io/hackage-deps/v/twitter-types.svg)](http://packdeps.haskellers.com/feed?needle=twitter-types) This library treats the Twitter JSON API in the Haskell way. twitter-types-0.11.0/tests/fixtures/entity01.json0000644000000000000000000000054014144754426020220 0ustar0000000000000000{"symbols":[],"urls":[{"indices":[32,52], "url":"http://t.co/IOwBrTZR", "display_url":"youtube.com/watch?v=oHg5SJ\u2026", "expanded_url":"http://www.youtube.com/watch?v=oHg5SJYRHA0"}],"user_mentions":[{"name":"Twitter API", "indices":[4,15], "screen_name":"twitterapi", "id":6253282, "id_str":"6253282"}],"hashtags":[{"indices":[32,36],"text":"lol"}]} twitter-types-0.11.0/tests/fixtures/event_unfavorite_thimura.json0000644000000000000000000001160114144754426023657 0ustar0000000000000000{"event":"unfavorite","created_at":"Sat Aug 02 16:32:10 +0000 2014","source":{"id":2566877347,"id_str":"2566877347","name":"thimura shinku","screen_name":"thimura_shinku","location":null,"url":null,"description":"\u4e8c\u968e\u5802 \u771f\u7d05","protected":false,"followers_count":4,"friends_count":3,"listed_count":0,"created_at":"Sat Jun 14 10:15:19 +0000 2014","favourites_count":1,"utc_offset":32400,"time_zone":"Irkutsk","geo_enabled":false,"verified":false,"statuses_count":2,"lang":"ja","contributors_enabled":false,"is_translator":false,"is_translation_enabled":false,"profile_background_color":"C0DEED","profile_background_image_url":"http:\/\/abs.twimg.com\/images\/themes\/theme1\/bg.png","profile_background_image_url_https":"https:\/\/abs.twimg.com\/images\/themes\/theme1\/bg.png","profile_background_tile":false,"profile_image_url":"http:\/\/pbs.twimg.com\/profile_images\/477757821895704577\/rVwTwORU_normal.jpeg","profile_image_url_https":"https:\/\/pbs.twimg.com\/profile_images\/477757821895704577\/rVwTwORU_normal.jpeg","profile_banner_url":"https:\/\/pbs.twimg.com\/profile_banners\/2566877347\/1402741935","profile_link_color":"0084B4","profile_sidebar_border_color":"C0DEED","profile_sidebar_fill_color":"DDEEF6","profile_text_color":"333333","profile_use_background_image":true,"default_profile":true,"default_profile_image":false,"following":null,"follow_request_sent":null,"notifications":null},"target":{"id":69179963,"id_str":"69179963","name":"\u3061\u3080\u3089","screen_name":"thimura","location":"State# Irotoridori.No.World","url":"http:\/\/d.hatena.ne.jp\/thimura","description":"\u771f\u7d05\u304b\u308f\u3044\u3044","protected":false,"followers_count":755,"friends_count":781,"listed_count":102,"created_at":"Thu Aug 27 02:48:06 +0000 2009","favourites_count":17363,"utc_offset":32400,"time_zone":"Tokyo","geo_enabled":false,"verified":false,"statuses_count":24747,"lang":"en","contributors_enabled":false,"is_translator":false,"is_translation_enabled":false,"profile_background_color":"000000","profile_background_image_url":"http:\/\/pbs.twimg.com\/profile_background_images\/378800000154132099\/hn0DlU5i.png","profile_background_image_url_https":"https:\/\/pbs.twimg.com\/profile_background_images\/378800000154132099\/hn0DlU5i.png","profile_background_tile":true,"profile_image_url":"http:\/\/pbs.twimg.com\/profile_images\/414044387346116609\/VNMfLpY7_normal.png","profile_image_url_https":"https:\/\/pbs.twimg.com\/profile_images\/414044387346116609\/VNMfLpY7_normal.png","profile_banner_url":"https:\/\/pbs.twimg.com\/profile_banners\/69179963\/1402419439","profile_link_color":"00660F","profile_sidebar_border_color":"FFFFFF","profile_sidebar_fill_color":"BABDD1","profile_text_color":"333333","profile_use_background_image":true,"default_profile":false,"default_profile_image":false,"following":null,"follow_request_sent":null,"notifications":null},"target_object":{"created_at":"Sat Aug 02 15:49:45 +0000 2014","id":495597326736449536,"id_str":"495597326736449536","text":"haskell","source":"\u003ca href=\"http:\/\/twitter.com\" rel=\"nofollow\"\u003eTwitter Web Client\u003c\/a\u003e","truncated":false,"in_reply_to_status_id":null,"in_reply_to_status_id_str":null,"in_reply_to_user_id":null,"in_reply_to_user_id_str":null,"in_reply_to_screen_name":null,"user":{"id":69179963,"id_str":"69179963","name":"\u3061\u3080\u3089","screen_name":"thimura","location":"State# Irotoridori.No.World","url":"http:\/\/d.hatena.ne.jp\/thimura","description":"\u771f\u7d05\u304b\u308f\u3044\u3044","protected":false,"followers_count":755,"friends_count":781,"listed_count":102,"created_at":"Thu Aug 27 02:48:06 +0000 2009","favourites_count":17363,"utc_offset":32400,"time_zone":"Tokyo","geo_enabled":false,"verified":false,"statuses_count":24747,"lang":"en","contributors_enabled":false,"is_translator":false,"is_translation_enabled":false,"profile_background_color":"000000","profile_background_image_url":"http:\/\/pbs.twimg.com\/profile_background_images\/378800000154132099\/hn0DlU5i.png","profile_background_image_url_https":"https:\/\/pbs.twimg.com\/profile_background_images\/378800000154132099\/hn0DlU5i.png","profile_background_tile":true,"profile_image_url":"http:\/\/pbs.twimg.com\/profile_images\/414044387346116609\/VNMfLpY7_normal.png","profile_image_url_https":"https:\/\/pbs.twimg.com\/profile_images\/414044387346116609\/VNMfLpY7_normal.png","profile_banner_url":"https:\/\/pbs.twimg.com\/profile_banners\/69179963\/1402419439","profile_link_color":"00660F","profile_sidebar_border_color":"FFFFFF","profile_sidebar_fill_color":"BABDD1","profile_text_color":"333333","profile_use_background_image":true,"default_profile":false,"default_profile_image":false,"following":null,"follow_request_sent":null,"notifications":null},"geo":null,"coordinates":null,"place":null,"contributors":null,"retweet_count":1,"favorite_count":1,"entities":{"hashtags":[],"symbols":[],"urls":[],"user_mentions":[]},"favorited":false,"retweeted":false,"lang":"en"}} twitter-types-0.11.0/tests/fixtures/list_thimura_haskell.json0000644000000000000000000000351014144754426022752 0ustar0000000000000000{"id_str":"20849097","slug":"haskell","mode":"public","full_name":"@thimura/haskell","uri":"/thimura/haskell","following":true,"user":{"screen_name":"thimura","profile_banner_url":"https://pbs.twimg.com/profile_banners/69179963/1402419439","is_translation_enabled":false,"default_profile":false,"profile_image_url":"http://pbs.twimg.com/profile_images/414044387346116609/VNMfLpY7_normal.png","default_profile_image":false,"id_str":"69179963","profile_background_image_url_https":"https://pbs.twimg.com/profile_background_images/378800000154132099/hn0DlU5i.png","protected":false,"location":"State# Irotoridori.No.World","entities":{"url":{"urls":[{"expanded_url":"http://d.hatena.ne.jp/thimura","url":"http://t.co/TFUAsAffX0","indices":[0,22],"display_url":"d.hatena.ne.jp/thimura"}]},"description":{"urls":[]}},"profile_background_color":"000000","utc_offset":32400,"url":"http://t.co/TFUAsAffX0","profile_text_color":"333333","profile_image_url_https":"https://pbs.twimg.com/profile_images/414044387346116609/VNMfLpY7_normal.png","verified":false,"statuses_count":24734,"profile_background_tile":true,"following":false,"lang":"en","follow_request_sent":false,"profile_sidebar_fill_color":"BABDD1","time_zone":"Tokyo","name":"ちむら","profile_sidebar_border_color":"FFFFFF","geo_enabled":false,"listed_count":102,"contributors_enabled":false,"created_at":"Thu Aug 27 02:48:06 +0000 2009","id":69179963,"friends_count":781,"is_translator":false,"favourites_count":17345,"notifications":false,"profile_background_image_url":"http://pbs.twimg.com/profile_background_images/378800000154132099/hn0DlU5i.png","profile_use_background_image":true,"description":"真紅かわいい","profile_link_color":"00660F","followers_count":755},"member_count":50,"name":"haskell","created_at":"Sat Sep 04 11:48:02 +0000 2010","id":20849097,"subscriber_count":1,"description":""}twitter-types-0.11.0/tests/fixtures/delete.json0000644000000000000000000000017614144754426020012 0ustar0000000000000000{"delete":{"status":{"id":495607981833064448,"user_id":2566877347,"id_str":"495607981833064448","user_id_str":"2566877347"}}} twitter-types-0.11.0/tests/fixtures/status01.json0000644000000000000000000000363614144754426020240 0ustar0000000000000000{"created_at":"Sat Sep 10 22:23:38 +0000 2011","id":112652479837110273,"id_str":"112652479837110273","text":"@twitter meets @seepicturely at #tcdisrupt cc.@boscomonkey @episod http:\/\/t.co\/6J2EgYM","source":"\u003ca href=\"http:\/\/instagr.am\" rel=\"nofollow\"\u003eInstagram\u003c\/a\u003e","truncated":false,"in_reply_to_status_id":null,"in_reply_to_status_id_str":null,"in_reply_to_user_id":783214,"in_reply_to_user_id_str":"783214","in_reply_to_screen_name":"twitter","user":{"id":299862462,"id_str":"299862462","name":"Eoin McMillan ","screen_name":"imeoin","location":"Twitter","description":"Eoin's photography account. See @mceoin for tweets.","url":"http:\/\/www.eoin.me","protected":false,"followers_count":6,"friends_count":0,"listed_count":0,"created_at":"Mon May 16 20:07:59 +0000 2011","favourites_count":0,"utc_offset":null,"time_zone":null,"geo_enabled":false,"verified":false,"statuses_count":277,"lang":"en","contributors_enabled":false,"is_translator":false,"profile_background_color":"131516","profile_background_image_url":"http:\/\/a0.twimg.com\/images\/themes\/theme14\/bg.gif","profile_background_image_url_https":"https:\/\/si0.twimg.com\/images\/themes\/theme14\/bg.gif","profile_background_tile":true,"profile_image_url":"http:\/\/a0.twimg.com\/profile_images\/1380912173\/Screen_shot_2011-06-03_at_7.35.36_PM_normal.png","profile_image_url_https":"https:\/\/si0.twimg.com\/profile_images\/1380912173\/Screen_shot_2011-06-03_at_7.35.36_PM_normal.png","profile_link_color":"009999","profile_sidebar_border_color":"EEEEEE","profile_sidebar_fill_color":"EFEFEF","profile_text_color":"333333","profile_use_background_image":true,"show_all_inline_media":false,"default_profile":false,"default_profile_image":false,"following":null,"follow_request_sent":null,"notifications":null},"geo":null,"coordinates":null,"place":null,"contributors":null,"retweet_count":0,"favorited":false,"retweeted":false,"possibly_sensitive":false} twitter-types-0.11.0/tests/fixtures/status_thimura_with_photo.json0000644000000000000000000000654214144754426024073 0ustar0000000000000000{"in_reply_to_status_id":null,"id_str":"491143410770657280","truncated":false,"possibly_sensitive":false,"in_reply_to_screen_name":null,"extended_entities":{"media":[{"id_str":"491143397378244610","expanded_url":"http://twitter.com/thimura/status/491143410770657280/photo/1","url":"http://t.co/FjSOU8dDoD","media_url_https":"https://pbs.twimg.com/media/BtDkUVaCQAIpWBU.jpg","indices":[7,29],"id":491143397378244610,"media_url":"http://pbs.twimg.com/media/BtDkUVaCQAIpWBU.jpg","type":"photo","sizes":{"small":{"w":340,"resize":"fit","h":191},"large":{"w":1024,"resize":"fit","h":576},"medium":{"w":600,"resize":"fit","h":338},"thumb":{"w":150,"resize":"crop","h":150}},"display_url":"pic.twitter.com/FjSOU8dDoD"}]},"entities":{"symbols":[],"urls":[],"media":[{"id_str":"491143397378244610","expanded_url":"http://twitter.com/thimura/status/491143410770657280/photo/1","url":"http://t.co/FjSOU8dDoD","media_url_https":"https://pbs.twimg.com/media/BtDkUVaCQAIpWBU.jpg","indices":[7,29],"id":491143397378244610,"media_url":"http://pbs.twimg.com/media/BtDkUVaCQAIpWBU.jpg","type":"photo","sizes":{"small":{"w":340,"resize":"fit","h":191},"large":{"w":1024,"resize":"fit","h":576},"medium":{"w":600,"resize":"fit","h":338},"thumb":{"w":150,"resize":"crop","h":150}},"display_url":"pic.twitter.com/FjSOU8dDoD"}],"user_mentions":[],"hashtags":[]},"text":"近所の海です http://t.co/FjSOU8dDoD","in_reply_to_user_id_str":null,"favorited":false,"coordinates":null,"retweeted":false,"user":{"screen_name":"thimura","profile_banner_url":"https://pbs.twimg.com/profile_banners/69179963/1402419439","is_translation_enabled":false,"default_profile":false,"profile_image_url":"http://pbs.twimg.com/profile_images/414044387346116609/VNMfLpY7_normal.png","default_profile_image":false,"id_str":"69179963","profile_background_image_url_https":"https://pbs.twimg.com/profile_background_images/378800000154132099/hn0DlU5i.png","protected":false,"location":"State# Irotoridori.No.World","entities":{"url":{"urls":[{"expanded_url":"http://d.hatena.ne.jp/thimura","url":"http://t.co/TFUAsAffX0","indices":[0,22],"display_url":"d.hatena.ne.jp/thimura"}]},"description":{"urls":[]}},"profile_background_color":"000000","utc_offset":32400,"url":"http://t.co/TFUAsAffX0","profile_text_color":"333333","profile_image_url_https":"https://pbs.twimg.com/profile_images/414044387346116609/VNMfLpY7_normal.png","verified":false,"statuses_count":24734,"profile_background_tile":true,"following":false,"lang":"en","follow_request_sent":false,"profile_sidebar_fill_color":"BABDD1","time_zone":"Tokyo","name":"ちむら","profile_sidebar_border_color":"FFFFFF","geo_enabled":false,"listed_count":102,"contributors_enabled":false,"created_at":"Thu Aug 27 02:48:06 +0000 2009","id":69179963,"friends_count":781,"is_translator":false,"favourites_count":17345,"notifications":false,"profile_background_image_url":"http://pbs.twimg.com/profile_background_images/378800000154132099/hn0DlU5i.png","profile_use_background_image":true,"description":"真紅かわいい","profile_link_color":"00660F","followers_count":755},"lang":"ja","retweet_count":4,"in_reply_to_user_id":null,"created_at":"Mon Jul 21 08:51:28 +0000 2014","source":"\u003ca href=\"https://sites.google.com/site/wakamesoba98/sobacha\" rel=\"nofollow\"\u003eSobaCha\u003c/a\u003e","geo":null,"id":491143410770657280,"in_reply_to_status_id_str":null,"favorite_count":9,"contributors":null,"place":null}twitter-types-0.11.0/tests/fixtures/event_favorite_thimura.json0000644000000000000000000001157714144754426023330 0ustar0000000000000000{"event":"favorite","created_at":"Sat Aug 02 16:32:01 +0000 2014","source":{"id":2566877347,"id_str":"2566877347","name":"thimura shinku","screen_name":"thimura_shinku","location":null,"url":null,"description":"\u4e8c\u968e\u5802 \u771f\u7d05","protected":false,"followers_count":4,"friends_count":3,"listed_count":0,"created_at":"Sat Jun 14 10:15:19 +0000 2014","favourites_count":2,"utc_offset":32400,"time_zone":"Irkutsk","geo_enabled":false,"verified":false,"statuses_count":1,"lang":"ja","contributors_enabled":false,"is_translator":false,"is_translation_enabled":false,"profile_background_color":"C0DEED","profile_background_image_url":"http:\/\/abs.twimg.com\/images\/themes\/theme1\/bg.png","profile_background_image_url_https":"https:\/\/abs.twimg.com\/images\/themes\/theme1\/bg.png","profile_background_tile":false,"profile_image_url":"http:\/\/pbs.twimg.com\/profile_images\/477757821895704577\/rVwTwORU_normal.jpeg","profile_image_url_https":"https:\/\/pbs.twimg.com\/profile_images\/477757821895704577\/rVwTwORU_normal.jpeg","profile_banner_url":"https:\/\/pbs.twimg.com\/profile_banners\/2566877347\/1402741935","profile_link_color":"0084B4","profile_sidebar_border_color":"C0DEED","profile_sidebar_fill_color":"DDEEF6","profile_text_color":"333333","profile_use_background_image":true,"default_profile":true,"default_profile_image":false,"following":null,"follow_request_sent":null,"notifications":null},"target":{"id":69179963,"id_str":"69179963","name":"\u3061\u3080\u3089","screen_name":"thimura","location":"State# Irotoridori.No.World","url":"http:\/\/d.hatena.ne.jp\/thimura","description":"\u771f\u7d05\u304b\u308f\u3044\u3044","protected":false,"followers_count":755,"friends_count":781,"listed_count":102,"created_at":"Thu Aug 27 02:48:06 +0000 2009","favourites_count":17363,"utc_offset":32400,"time_zone":"Tokyo","geo_enabled":false,"verified":false,"statuses_count":24747,"lang":"en","contributors_enabled":false,"is_translator":false,"is_translation_enabled":false,"profile_background_color":"000000","profile_background_image_url":"http:\/\/pbs.twimg.com\/profile_background_images\/378800000154132099\/hn0DlU5i.png","profile_background_image_url_https":"https:\/\/pbs.twimg.com\/profile_background_images\/378800000154132099\/hn0DlU5i.png","profile_background_tile":true,"profile_image_url":"http:\/\/pbs.twimg.com\/profile_images\/414044387346116609\/VNMfLpY7_normal.png","profile_image_url_https":"https:\/\/pbs.twimg.com\/profile_images\/414044387346116609\/VNMfLpY7_normal.png","profile_banner_url":"https:\/\/pbs.twimg.com\/profile_banners\/69179963\/1402419439","profile_link_color":"00660F","profile_sidebar_border_color":"FFFFFF","profile_sidebar_fill_color":"BABDD1","profile_text_color":"333333","profile_use_background_image":true,"default_profile":false,"default_profile_image":false,"following":null,"follow_request_sent":null,"notifications":null},"target_object":{"created_at":"Sat Aug 02 15:49:45 +0000 2014","id":495597326736449536,"id_str":"495597326736449536","text":"haskell","source":"\u003ca href=\"http:\/\/twitter.com\" rel=\"nofollow\"\u003eTwitter Web Client\u003c\/a\u003e","truncated":false,"in_reply_to_status_id":null,"in_reply_to_status_id_str":null,"in_reply_to_user_id":null,"in_reply_to_user_id_str":null,"in_reply_to_screen_name":null,"user":{"id":69179963,"id_str":"69179963","name":"\u3061\u3080\u3089","screen_name":"thimura","location":"State# Irotoridori.No.World","url":"http:\/\/d.hatena.ne.jp\/thimura","description":"\u771f\u7d05\u304b\u308f\u3044\u3044","protected":false,"followers_count":755,"friends_count":781,"listed_count":102,"created_at":"Thu Aug 27 02:48:06 +0000 2009","favourites_count":17363,"utc_offset":32400,"time_zone":"Tokyo","geo_enabled":false,"verified":false,"statuses_count":24747,"lang":"en","contributors_enabled":false,"is_translator":false,"is_translation_enabled":false,"profile_background_color":"000000","profile_background_image_url":"http:\/\/pbs.twimg.com\/profile_background_images\/378800000154132099\/hn0DlU5i.png","profile_background_image_url_https":"https:\/\/pbs.twimg.com\/profile_background_images\/378800000154132099\/hn0DlU5i.png","profile_background_tile":true,"profile_image_url":"http:\/\/pbs.twimg.com\/profile_images\/414044387346116609\/VNMfLpY7_normal.png","profile_image_url_https":"https:\/\/pbs.twimg.com\/profile_images\/414044387346116609\/VNMfLpY7_normal.png","profile_banner_url":"https:\/\/pbs.twimg.com\/profile_banners\/69179963\/1402419439","profile_link_color":"00660F","profile_sidebar_border_color":"FFFFFF","profile_sidebar_fill_color":"BABDD1","profile_text_color":"333333","profile_use_background_image":true,"default_profile":false,"default_profile_image":false,"following":null,"follow_request_sent":null,"notifications":null},"geo":null,"coordinates":null,"place":null,"contributors":null,"retweet_count":0,"favorite_count":2,"entities":{"hashtags":[],"symbols":[],"urls":[],"user_mentions":[]},"favorited":false,"retweeted":false,"lang":"en"}} twitter-types-0.11.0/tests/fixtures/media_entity.json0000644000000000000000000000440314144754426021220 0ustar0000000000000000{"created_at":"Wed Sep 14 20:58:04 +0000 2011","id":114080493036773378,"id_str":"114080493036773378","text":"Hello America! http:\/\/t.co\/rJC5Pxsu","source":"web","truncated":false,"in_reply_to_status_id":null,"in_reply_to_status_id_str":null,"in_reply_to_user_id":null,"in_reply_to_user_id_str":null,"in_reply_to_screen_name":null,"user":{"id":373487136,"id_str":"373487136","name":"Y U No @rno?","screen_name":"yunorno","location":"Paris, France","url":"http:\/\/twitter.com\/rno","description":"Oui oui!","protected":false,"followers_count":32,"friends_count":3,"listed_count":2,"created_at":"Wed Sep 14 17:24:54 +0000 2011","favourites_count":0,"utc_offset":null,"time_zone":null,"geo_enabled":false,"verified":false,"statuses_count":27,"lang":"en","contributors_enabled":false,"is_translator":false,"profile_background_color":"C0DEED","profile_background_image_url":"http:\/\/a0.twimg.com\/images\/themes\/theme1\/bg.png","profile_background_image_url_https":"https:\/\/si0.twimg.com\/images\/themes\/theme1\/bg.png","profile_background_tile":false,"profile_image_url":"http:\/\/a0.twimg.com\/profile_images\/1542800106\/oui_normal.png","profile_image_url_https":"https:\/\/si0.twimg.com\/profile_images\/1542800106\/oui_normal.png","profile_link_color":"0084B4","profile_sidebar_border_color":"C0DEED","profile_sidebar_fill_color":"DDEEF6","profile_text_color":"333333","profile_use_background_image":true,"default_profile":true,"default_profile_image":false,"following":false,"follow_request_sent":false,"notifications":false},"geo":null,"coordinates":null,"place":null,"contributors":null,"retweet_count":4,"entities":{"hashtags":[],"urls":[],"user_mentions":[],"media":[{"id":114080493040967680,"id_str":"114080493040967680","indices":[15,35],"media_url":"http:\/\/pbs.twimg.com\/media\/AZVLmp-CIAAbkyy.jpg","media_url_https":"https:\/\/pbs.twimg.com\/media\/AZVLmp-CIAAbkyy.jpg","url":"http:\/\/t.co\/rJC5Pxsu","display_url":"pic.twitter.com\/rJC5Pxsu","expanded_url":"http:\/\/twitter.com\/yunorno\/status\/114080493036773378\/photo\/1","type":"photo","sizes":{"large":{"w":226,"h":238,"resize":"fit"},"thumb":{"w":150,"h":150,"resize":"crop"},"medium":{"w":226,"h":238,"resize":"fit"},"small":{"w":226,"h":238,"resize":"fit"}}}]},"favorited":false,"retweeted":false,"possibly_sensitive":false} twitter-types-0.11.0/tests/fixtures/direct_message_event_list.json0000644000000000000000000000306614144754426023763 0ustar0000000000000000{ "apps": { "258901": { "url": "http://twitter.com/download/android", "name": "Twitter for Android", "id": "258901" }, "3033300": { "url": "https://mobile.twitter.com", "name": "Twitter Web App", "id": "3033300" } }, "events": [ { "message_create": { "source_app_id": "3033300", "message_data": { "entities": { "symbols": [], "urls": [], "user_mentions": [ { "screen_name": "thimura", "id_str": "69179963", "name": "ちむら", "indices": [ 6, 14 ], "id": 69179963 } ], "hashtags": [] }, "text": "hello @thimura" }, "target": { "recipient_id": "186712193" }, "sender_id": "69179963" }, "created_timestamp": "1570990548951", "id": "123123123123123123", "type": "message_create" }, { "message_create": { "source_app_id": "4237790", "message_data": { "entities": { "symbols": [], "urls": [], "user_mentions": [], "hashtags": [] }, "text": "hello" }, "target": { "recipient_id": "186712193" }, "sender_id": "69179963" }, "created_timestamp": "1570990006140", "id": "25252525252525", "type": "message_create" } ] } twitter-types-0.11.0/tests/fixtures/status_quoted.json0000644000000000000000000001477314144754426021464 0ustar0000000000000000{ "created_at": "Wed Sep 09 17:13:42 +0000 2015", "id": 641660763770372100, "id_str": "641660763770372097", "text": "Wow! Congrats! https://t.co/EPMMldEcci", "source": "Twitter for iPhone", "truncated": false, "in_reply_to_status_id": null, "in_reply_to_status_id_str": null, "in_reply_to_user_id": null, "in_reply_to_user_id_str": null, "in_reply_to_screen_name": null, "user": { "id": 15232432, "id_str": "15232432", "name": "Dean Wampler", "screen_name": "deanwampler", "location": "Chicago", "description": "Minor irritant, major pedant, Big Data, IoT, and Scala poser. Lurks at Typesafe. O'Reilly author. Opinions are my own..", "url": "http://t.co/bzGTwCnmvO", "entities": { "url": { "urls": [ { "url": "http://t.co/bzGTwCnmvO", "expanded_url": "http://typesafe.com", "display_url": "typesafe.com", "indices": [ 0, 22 ] } ] }, "description": { "urls": [] } }, "protected": false, "followers_count": 7221, "friends_count": 811, "listed_count": 645, "created_at": "Wed Jun 25 15:24:31 +0000 2008", "favourites_count": 2841, "utc_offset": -18000, "time_zone": "Central Time (US & Canada)", "geo_enabled": true, "verified": false, "statuses_count": 13483, "lang": "en", "contributors_enabled": false, "is_translator": false, "is_translation_enabled": false, "profile_background_color": "9AE4E8", "profile_background_image_url": "http://pbs.twimg.com/profile_background_images/670120165/5514a5b016bf4d3d617ece5f117643d0.jpeg", "profile_background_image_url_https": "https://pbs.twimg.com/profile_background_images/670120165/5514a5b016bf4d3d617ece5f117643d0.jpeg", "profile_background_tile": true, "profile_image_url": "http://pbs.twimg.com/profile_images/639619926374748160/QhODNcWz_normal.jpg", "profile_image_url_https": "https://pbs.twimg.com/profile_images/639619926374748160/QhODNcWz_normal.jpg", "profile_banner_url": "https://pbs.twimg.com/profile_banners/15232432/1359038744", "profile_link_color": "0000FF", "profile_sidebar_border_color": "FFFFFF", "profile_sidebar_fill_color": "DFF8A0", "profile_text_color": "070708", "profile_use_background_image": true, "has_extended_profile": false, "default_profile": false, "default_profile_image": false, "following": false, "follow_request_sent": false, "notifications": false }, "geo": null, "coordinates": null, "place": null, "contributors": null, "quoted_status_id": 641653574284537900, "quoted_status_id_str": "641653574284537856", "quoted_status": { "created_at": "Wed Sep 09 16:45:08 +0000 2015", "id": 641653574284537900, "id_str": "641653574284537856", "text": "Very happy to say that I'm joining @mesosphere as a Distributed Systems Engineer!", "source": "Twitter Web Client", "truncated": false, "in_reply_to_status_id": null, "in_reply_to_status_id_str": null, "in_reply_to_user_id": null, "in_reply_to_user_id_str": null, "in_reply_to_screen_name": null, "user": { "id": 54129186, "id_str": "54129186", "name": "Neil Conway", "screen_name": "neil_conway", "location": "Oakland, CA", "description": "Large-scale data management and distributed systems.", "url": "http://t.co/grthxRo5Q1", "entities": { "url": { "urls": [ { "url": "http://t.co/grthxRo5Q1", "expanded_url": "http://neilconway.org", "display_url": "neilconway.org", "indices": [ 0, 22 ] } ] }, "description": { "urls": [] } }, "protected": false, "followers_count": 3380, "friends_count": 680, "listed_count": 202, "created_at": "Mon Jul 06 05:43:15 +0000 2009", "favourites_count": 611, "utc_offset": -25200, "time_zone": "Pacific Time (US & Canada)", "geo_enabled": true, "verified": false, "statuses_count": 3559, "lang": "en", "contributors_enabled": false, "is_translator": false, "is_translation_enabled": false, "profile_background_color": "FFFFFF", "profile_background_image_url": "http://pbs.twimg.com/profile_background_images/204823473/Untitled-2.jpg", "profile_background_image_url_https": "https://pbs.twimg.com/profile_background_images/204823473/Untitled-2.jpg", "profile_background_tile": true, "profile_image_url": "http://pbs.twimg.com/profile_images/299445365/3613789225_66f1cc848f_b_normal.jpg", "profile_image_url_https": "https://pbs.twimg.com/profile_images/299445365/3613789225_66f1cc848f_b_normal.jpg", "profile_link_color": "036E6E", "profile_sidebar_border_color": "B05607", "profile_sidebar_fill_color": "E8F0F0", "profile_text_color": "998308", "profile_use_background_image": true, "has_extended_profile": false, "default_profile": false, "default_profile_image": false, "following": true, "follow_request_sent": false, "notifications": false }, "geo": null, "coordinates": null, "place": null, "contributors": null, "is_quote_status": false, "retweet_count": 7, "favorite_count": 63, "entities": { "hashtags": [], "symbols": [], "user_mentions": [ { "screen_name": "mesosphere", "name": "Mesosphere", "id": 1872399366, "id_str": "1872399366", "indices": [ 35, 46 ] } ], "urls": [] }, "favorited": false, "retweeted": false, "lang": "en" }, "is_quote_status": true, "retweet_count": 0, "favorite_count": 1, "entities": { "hashtags": [], "symbols": [], "user_mentions": [], "urls": [ { "url": "https://t.co/EPMMldEcci", "expanded_url": "https://twitter.com/neil_conway/status/641653574284537856", "display_url": "twitter.com/neil_conway/st…", "indices": [ 15, 38 ] } ] }, "favorited": false, "retweeted": false, "possibly_sensitive": false, "possibly_sensitive_appealable": false, "lang": "en" } twitter-types-0.11.0/tests/fixtures/media_extended_entity.json0000644000000000000000000001153314144754426023102 0ustar0000000000000000{"created_at":"Fri Jul 29 20:14:40 +0000 2016","id":759119974329823200,"id_str":"759119974329823233","text":"look at all these cats tho https://t.co/Qi316FhOwe","truncated":false,"entities":{"hashtags":[],"symbols":[],"user_mentions":[],"urls":[],"media":[{"id":759119267472089100,"id_str":"759119267472089089","indices":[27,50],"media_url":"http://pbs.twimg.com/media/Coju86fUIAEUcRC.jpg","media_url_https":"https://pbs.twimg.com/media/Coju86fUIAEUcRC.jpg","url":"https://t.co/Qi316FhOwe","display_url":"pic.twitter.com/Qi316FhOwe","expanded_url":"http://twitter.com/PleaseCaption/status/759119974329823233/photo/1","type":"photo","sizes":{"large":{"w":300,"h":400,"resize":"fit"},"medium":{"w":300,"h":400,"resize":"fit"},"thumb":{"w":150,"h":150,"resize":"crop"},"small":{"w":300,"h":400,"resize":"fit"}}}]},"extended_entities":{"media":[{"id":759119267472089100,"id_str":"759119267472089089","indices":[27,50],"media_url":"http://pbs.twimg.com/media/Coju86fUIAEUcRC.jpg","media_url_https":"https://pbs.twimg.com/media/Coju86fUIAEUcRC.jpg","url":"https://t.co/Qi316FhOwe","display_url":"pic.twitter.com/Qi316FhOwe","expanded_url":"http://twitter.com/PleaseCaption/status/759119974329823233/photo/1","type":"photo","sizes":{"large":{"w":300,"h":400,"resize":"fit"},"medium":{"w":300,"h":400,"resize":"fit"},"thumb":{"w":150,"h":150,"resize":"crop"},"small":{"w":300,"h":400,"resize":"fit"}},"ext_alt_text":"A small tabby kitten"},{"id":759119396350505000,"id_str":"759119396350504960","indices":[27,50],"media_url":"http://pbs.twimg.com/media/CojvEamUsAARiX2.jpg","media_url_https":"https://pbs.twimg.com/media/CojvEamUsAARiX2.jpg","url":"https://t.co/Qi316FhOwe","display_url":"pic.twitter.com/Qi316FhOwe","expanded_url":"http://twitter.com/PleaseCaption/status/759119974329823233/photo/1","type":"photo","sizes":{"medium":{"w":500,"h":301,"resize":"fit"},"small":{"w":500,"h":301,"resize":"fit"},"thumb":{"w":150,"h":150,"resize":"crop"},"large":{"w":500,"h":301,"resize":"fit"}},"ext_alt_text":"four kittens sitting together"},{"id":759119476621086700,"id_str":"759119476621086720","indices":[27,50],"media_url":"http://pbs.twimg.com/media/CojvJFoUkAAoWIR.jpg","media_url_https":"https://pbs.twimg.com/media/CojvJFoUkAAoWIR.jpg","url":"https://t.co/Qi316FhOwe","display_url":"pic.twitter.com/Qi316FhOwe","expanded_url":"http://twitter.com/PleaseCaption/status/759119974329823233/photo/1","type":"photo","sizes":{"thumb":{"w":150,"h":150,"resize":"crop"},"large":{"w":500,"h":600,"resize":"fit"},"medium":{"w":500,"h":600,"resize":"fit"},"small":{"w":500,"h":600,"resize":"fit"}},"ext_alt_text":"a cute soft kitten with a red ornament"},{"id":759119583466758100,"id_str":"759119583466758145","indices":[27,50],"media_url":"http://pbs.twimg.com/media/CojvPTqUIAEYF7l.jpg","media_url_https":"https://pbs.twimg.com/media/CojvPTqUIAEYF7l.jpg","url":"https://t.co/Qi316FhOwe","display_url":"pic.twitter.com/Qi316FhOwe","expanded_url":"http://twitter.com/PleaseCaption/status/759119974329823233/photo/1","type":"photo","sizes":{"medium":{"w":650,"h":600,"resize":"fit"},"thumb":{"w":150,"h":150,"resize":"crop"},"small":{"w":650,"h":600,"resize":"fit"},"large":{"w":650,"h":600,"resize":"fit"}},"ext_alt_text":"a skeptical-looking tabby cat outside"}]},"source":"Twitter Web Client","in_reply_to_status_id":null,"in_reply_to_status_id_str":null,"in_reply_to_user_id":null,"in_reply_to_user_id_str":null,"in_reply_to_screen_name":null,"user":{"id":753372895682949100,"id_str":"753372895682949120","name":"Please Caption!","screen_name":"PleaseCaption","location":"","description":"","url":null,"entities":{"description":{"urls":[]}},"protected":false,"followers_count":0,"friends_count":1,"listed_count":0,"created_at":"Wed Jul 13 23:37:50 +0000 2016","favourites_count":0,"utc_offset":-25200,"time_zone":"Pacific Time (US & Canada)","geo_enabled":false,"verified":false,"statuses_count":7,"lang":"en-gb","contributors_enabled":false,"is_translator":false,"is_translation_enabled":false,"profile_background_color":"F5F8FA","profile_background_image_url":null,"profile_background_image_url_https":null,"profile_background_tile":false,"profile_image_url":"http://abs.twimg.com/sticky/default_profile_images/default_profile_5_normal.png","profile_image_url_https":"https://abs.twimg.com/sticky/default_profile_images/default_profile_5_normal.png","profile_link_color":"2B7BB9","profile_sidebar_border_color":"C0DEED","profile_sidebar_fill_color":"DDEEF6","profile_text_color":"333333","profile_use_background_image":true,"has_extended_profile":false,"default_profile":true,"default_profile_image":true,"following":false,"follow_request_sent":false,"notifications":false},"geo":null,"coordinates":null,"place":null,"contributors":null,"is_quote_status":false,"retweet_count":0,"favorite_count":0,"favorited":false,"retweeted":false,"possibly_sensitive":false,"possibly_sensitive_appealable":false,"lang":"en"} twitter-types-0.11.0/tests/fixtures/user_thimura.json0000644000000000000000000000433714144754426021262 0ustar0000000000000000{"screen_name":"thimura","profile_banner_url":"https://pbs.twimg.com/profile_banners/69179963/1402419439","status":{"in_reply_to_status_id":null,"id_str":"495192122836783104","truncated":false,"in_reply_to_screen_name":null,"entities":{"symbols":[],"urls":[],"user_mentions":[],"hashtags":[]},"text":"くそあつい","in_reply_to_user_id_str":null,"favorited":false,"coordinates":null,"retweeted":false,"lang":"ja","retweet_count":0,"in_reply_to_user_id":null,"created_at":"Fri Aug 01 12:59:36 +0000 2014","source":"\u003ca href=\"http://twitter.com\" rel=\"nofollow\"\u003eTwitter Web Client\u003c/a\u003e","geo":null,"id":495192122836783104,"in_reply_to_status_id_str":null,"favorite_count":0,"contributors":null,"place":null},"is_translation_enabled":false,"needs_phone_verification":false,"default_profile":false,"profile_image_url":"http://pbs.twimg.com/profile_images/414044387346116609/VNMfLpY7_normal.png","default_profile_image":false,"id_str":"69179963","profile_background_image_url_https":"https://pbs.twimg.com/profile_background_images/378800000154132099/hn0DlU5i.png","protected":false,"location":"State# Irotoridori.No.World","entities":{"url":{"urls":[{"expanded_url":"http://d.hatena.ne.jp/thimura","url":"http://t.co/TFUAsAffX0","indices":[0,22],"display_url":"d.hatena.ne.jp/thimura"}]},"description":{"urls":[]}},"profile_background_color":"000000","utc_offset":32400,"url":"http://t.co/TFUAsAffX0","profile_text_color":"333333","profile_image_url_https":"https://pbs.twimg.com/profile_images/414044387346116609/VNMfLpY7_normal.png","suspended":false,"verified":false,"statuses_count":24709,"profile_background_tile":true,"following":false,"lang":"en","follow_request_sent":false,"profile_sidebar_fill_color":"BABDD1","time_zone":"Tokyo","name":"ちむら","profile_sidebar_border_color":"FFFFFF","geo_enabled":false,"listed_count":102,"contributors_enabled":false,"created_at":"Thu Aug 27 02:48:06 +0000 2009","id":69179963,"friends_count":780,"is_translator":false,"favourites_count":17313,"notifications":false,"profile_background_image_url":"http://pbs.twimg.com/profile_background_images/378800000154132099/hn0DlU5i.png","profile_use_background_image":true,"description":"真紅かわいい","profile_link_color":"00660F","followers_count":754}twitter-types-0.11.0/tests/fixtures/user_thimura_lang_null.json0000644000000000000000000000434014144754426023307 0ustar0000000000000000{"screen_name":"thimura","profile_banner_url":"https://pbs.twimg.com/profile_banners/69179963/1402419439","status":{"in_reply_to_status_id":null,"id_str":"495192122836783104","truncated":false,"in_reply_to_screen_name":null,"entities":{"symbols":[],"urls":[],"user_mentions":[],"hashtags":[]},"text":"くそあつい","in_reply_to_user_id_str":null,"favorited":false,"coordinates":null,"retweeted":false,"lang":null,"retweet_count":0,"in_reply_to_user_id":null,"created_at":"Fri Aug 01 12:59:36 +0000 2014","source":"\u003ca href=\"http://twitter.com\" rel=\"nofollow\"\u003eTwitter Web Client\u003c/a\u003e","geo":null,"id":495192122836783104,"in_reply_to_status_id_str":null,"favorite_count":0,"contributors":null,"place":null},"is_translation_enabled":false,"needs_phone_verification":false,"default_profile":false,"profile_image_url":"http://pbs.twimg.com/profile_images/414044387346116609/VNMfLpY7_normal.png","default_profile_image":false,"id_str":"69179963","profile_background_image_url_https":"https://pbs.twimg.com/profile_background_images/378800000154132099/hn0DlU5i.png","protected":false,"location":"State# Irotoridori.No.World","entities":{"url":{"urls":[{"expanded_url":"http://d.hatena.ne.jp/thimura","url":"http://t.co/TFUAsAffX0","indices":[0,22],"display_url":"d.hatena.ne.jp/thimura"}]},"description":{"urls":[]}},"profile_background_color":"000000","utc_offset":32400,"url":"http://t.co/TFUAsAffX0","profile_text_color":"333333","profile_image_url_https":"https://pbs.twimg.com/profile_images/414044387346116609/VNMfLpY7_normal.png","suspended":false,"verified":false,"statuses_count":24709,"profile_background_tile":true,"following":false,"lang":null,"follow_request_sent":false,"profile_sidebar_fill_color":"BABDD1","time_zone":"Tokyo","name":"ちむら","profile_sidebar_border_color":"FFFFFF","geo_enabled":false,"listed_count":102,"contributors_enabled":false,"created_at":"Thu Aug 27 02:48:06 +0000 2009","id":69179963,"friends_count":780,"is_translator":false,"favourites_count":17313,"notifications":false,"profile_background_image_url":"http://pbs.twimg.com/profile_background_images/378800000154132099/hn0DlU5i.png","profile_use_background_image":true,"description":"真紅かわいい","profile_link_color":"00660F","followers_count":754} twitter-types-0.11.0/tests/fixtures/status_with_entity.json0000644000000000000000000000464614144754426022530 0ustar0000000000000000{"created_at":"Sat Sep 10 22:23:38 +0000 2011","id":112652479837110273,"id_str":"112652479837110273","text":"@twitter meets @seepicturely at #tcdisrupt cc.@boscomonkey @episod http:\/\/t.co\/6J2EgYM","source":"\u003ca href=\"http:\/\/instagr.am\" rel=\"nofollow\"\u003eInstagram\u003c\/a\u003e","truncated":false,"in_reply_to_status_id":null,"in_reply_to_status_id_str":null,"in_reply_to_user_id":783214,"in_reply_to_user_id_str":"783214","in_reply_to_screen_name":"twitter","user":{"id":299862462,"id_str":"299862462","name":"Eoin McMillan ","screen_name":"imeoin","location":"Twitter","description":"Eoin's photography account. See @mceoin for tweets.","url":"http:\/\/www.eoin.me","protected":false,"followers_count":6,"friends_count":0,"listed_count":0,"created_at":"Mon May 16 20:07:59 +0000 2011","favourites_count":0,"utc_offset":null,"time_zone":null,"geo_enabled":false,"verified":false,"statuses_count":277,"lang":"en","contributors_enabled":false,"is_translator":false,"profile_background_color":"131516","profile_background_image_url":"http:\/\/a0.twimg.com\/images\/themes\/theme14\/bg.gif","profile_background_image_url_https":"https:\/\/si0.twimg.com\/images\/themes\/theme14\/bg.gif","profile_background_tile":true,"profile_image_url":"http:\/\/a0.twimg.com\/profile_images\/1380912173\/Screen_shot_2011-06-03_at_7.35.36_PM_normal.png","profile_image_url_https":"https:\/\/si0.twimg.com\/profile_images\/1380912173\/Screen_shot_2011-06-03_at_7.35.36_PM_normal.png","profile_link_color":"009999","profile_sidebar_border_color":"EEEEEE","profile_sidebar_fill_color":"EFEFEF","profile_text_color":"333333","profile_use_background_image":true,"show_all_inline_media":false,"default_profile":false,"default_profile_image":false,"following":null,"follow_request_sent":null,"notifications":null},"geo":null,"coordinates":null,"place":null,"contributors":null,"retweet_count":0,"entities":{"hashtags":[{"text":"tcdisrupt","indices":[32,42]}],"urls":[{"url":"http:\/\/t.co\/6J2EgYM","expanded_url":"http:\/\/instagr.am\/p\/MuW67\/","display_url":"instagr.am\/p\/MuW67\/","indices":[67,86]}],"user_mentions":[{"screen_name":"twitter","name":"Twitter","id":783214,"id_str":"783214","indices":[0,8]},{"screen_name":"boscomonkey","name":"Bosco So","id":14792670,"id_str":"14792670","indices":[46,58]},{"screen_name":"episod","name":"Taylor Singletary","id":819797,"id_str":"819797","indices":[59,66]}]},"favorited":false,"retweeted":false,"possibly_sensitive":false} twitter-types-0.11.0/tests/fixtures/error_not_authorized.json0000644000000000000000000000011114144754426023004 0ustar0000000000000000{"request":"\/1\/statuses\/user_timeline.json","error":"Not authorized"} twitter-types-0.11.0/tests/fixtures/search_haskell.json0000644000000000000000000000504514144754426021520 0ustar0000000000000000{"search_metadata":{"next_results":"?max_id=495594369802440705&q=haskell&include_entities=1","since_id_str":"0","completed_in":0.043,"count":1,"refresh_url":"?since_id=495597397733433345&q=haskell&include_entities=1","max_id_str":"495597397733433345","query":"haskell","since_id":0,"max_id":495597397733433345},"statuses":[{"in_reply_to_status_id":null,"id_str":"495597326736449536","truncated":false,"in_reply_to_screen_name":null,"entities":{"symbols":[],"urls":[],"user_mentions":[],"hashtags":[]},"text":"haskell","in_reply_to_user_id_str":null,"favorited":false,"coordinates":null,"retweeted":false,"user":{"screen_name":"thimura","profile_banner_url":"https://pbs.twimg.com/profile_banners/69179963/1402419439","is_translation_enabled":false,"default_profile":false,"profile_image_url":"http://pbs.twimg.com/profile_images/414044387346116609/VNMfLpY7_normal.png","default_profile_image":false,"id_str":"69179963","profile_background_image_url_https":"https://pbs.twimg.com/profile_background_images/378800000154132099/hn0DlU5i.png","protected":false,"location":"State# Irotoridori.No.World","entities":{"url":{"urls":[{"expanded_url":"http://d.hatena.ne.jp/thimura","url":"http://t.co/TFUAsAffX0","indices":[0,22],"display_url":"d.hatena.ne.jp/thimura"}]},"description":{"urls":[]}},"profile_background_color":"000000","utc_offset":32400,"url":"http://t.co/TFUAsAffX0","profile_text_color":"333333","profile_image_url_https":"https://pbs.twimg.com/profile_images/414044387346116609/VNMfLpY7_normal.png","verified":false,"statuses_count":24747,"profile_background_tile":true,"following":false,"lang":"en","follow_request_sent":false,"profile_sidebar_fill_color":"BABDD1","time_zone":"Tokyo","name":"ちむら","profile_sidebar_border_color":"FFFFFF","geo_enabled":false,"listed_count":102,"contributors_enabled":false,"created_at":"Thu Aug 27 02:48:06 +0000 2009","id":69179963,"friends_count":781,"is_translator":false,"favourites_count":17362,"notifications":false,"profile_background_image_url":"http://pbs.twimg.com/profile_background_images/378800000154132099/hn0DlU5i.png","profile_use_background_image":true,"description":"真紅かわいい","profile_link_color":"00660F","followers_count":755},"lang":"et","retweet_count":0,"in_reply_to_user_id":null,"created_at":"Sat Aug 02 15:49:45 +0000 2014","metadata":{"result_type":"recent","iso_language_code":"et"},"source":"\u003ca href=\"http://twitter.com\" rel=\"nofollow\"\u003eTwitter Web Client\u003c/a\u003e","geo":null,"id":495597326736449536,"in_reply_to_status_id_str":null,"favorite_count":0,"contributors":null,"place":null}]} twitter-types-0.11.0/tests/fixtures/tweet-updates/compatibilityplus_classic_hidden_13797.json0000644000000000000000000002202614144754426030704 0ustar0000000000000000{ "created_at": "Mon Mar 28 14:39:13 +0000 2016", "id": 714461850188926976, "id_str": "714461850188926976", "text": "@jeremycloud It's neat to have owls and raccoons around until you realize that raccoons will eat the eggs from the … https://t.co/OY7qmdJQnO", "entities": { "hashtags": [], "symbols": [], "user_mentions": [ { "screen_name": "jeremycloud", "name": "/dev/cloud/jeremy", "id": 15062340, "id_str": "15062340", "indices": [ 0, 12 ] } ], "urls": [ { "url": "https://t.co/OY7qmdJQnO", "expanded_url": "https://twitter.com/i/web/status/714461850188926976", "display_url": "twitter.com/i/web/status/7…", "indices": [ 117, 140 ] } ] }, "truncated": true, "extended_tweet": { "full_text": "@jeremycloud It's neat to have owls and raccoons around until you realize that raccoons will eat the eggs from the owl's nest https://t.co/Q0pkaU4ORH", "display_text_range": [ 13, 125 ], "entities": { "hashtags": [], "symbols": [], "user_mentions": [ { "screen_name": "jeremycloud", "name": "/dev/cloud/jeremy", "id": 15062340, "id_str": "15062340", "indices": [ 0, 12 ] } ], "urls": [ { "url": "https://t.co/Q0pkaU4ORH", "expanded_url": "https://twitter.com/jeremycloud/status/704059336788606976", "display_url": "twitter.com/jeremycloud/st…", "indices": [ 126, 149 ] } ] } }, "source": "Twitter Web Client", "in_reply_to_status_id": 706860403981099008, "in_reply_to_status_id_str": "706860403981099008", "in_reply_to_user_id": 15062340, "in_reply_to_user_id_str": "15062340", "in_reply_to_screen_name": "jeremycloud", "user": { "id": 4449621923, "id_str": "4449621923", "name": "Mr Bones", "screen_name": "MrBonesDroid", "location": "", "profile_location": null, "description": "", "url": null, "entities": { "description": { "urls": [] } }, "protected": true, "followers_count": 5, "friends_count": 7, "listed_count": 0, "created_at": "Fri Dec 11 15:18:02 +0000 2015", "favourites_count": 7, "utc_offset": -25200, "time_zone": "Pacific Time (US & Canada)", "geo_enabled": false, "verified": false, "statuses_count": 35, "lang": "en-gb", "contributors_enabled": false, "is_translator": false, "is_translation_enabled": false, "profile_background_color": "F5F8FA", "profile_background_image_url": null, "profile_background_image_url_https": null, "profile_background_tile": false, "profile_image_url": "http://pbs.twimg.com/profile_images/677097663288860672/zZxWCPSI_normal.jpg", "profile_image_url_https": "https://pbs.twimg.com/profile_images/677097663288860672/zZxWCPSI_normal.jpg", "profile_link_color": "2B7BB9", "profile_sidebar_border_color": "C0DEED", "profile_sidebar_fill_color": "DDEEF6", "profile_text_color": "333333", "profile_use_background_image": true, "has_extended_profile": false, "default_profile": true, "default_profile_image": false, "following": true, "follow_request_sent": false, "notifications": false }, "geo": null, "coordinates": null, "place": null, "contributors": null, "quoted_status_id": 704059336788606976, "quoted_status_id_str": "704059336788606976", "quoted_status": { "created_at": "Sun Feb 28 21:43:21 +0000 2016", "id": 704059336788606976, "id_str": "704059336788606976", "text": "My favorite photographic subject, up closer than ever before. https://t.co/K958bKh9Sd", "entities": { "hashtags": [], "symbols": [], "user_mentions": [], "urls": [], "media": [ { "id": 704059330149031936, "id_str": "704059330149031936", "indices": [ 62, 85 ], "media_url": "http://pbs.twimg.com/media/CcVSOwJVIAAKwE6.jpg", "media_url_https": "https://pbs.twimg.com/media/CcVSOwJVIAAKwE6.jpg", "url": "https://t.co/K958bKh9Sd", "display_url": "pic.twitter.com/K958bKh9Sd", "expanded_url": "http://twitter.com/jeremycloud/status/704059336788606976/photo/1", "type": "photo", "sizes": { "medium": { "w": 600, "h": 600, "resize": "fit" }, "thumb": { "w": 150, "h": 150, "resize": "crop" }, "large": { "w": 871, "h": 871, "resize": "fit" }, "small": { "w": 340, "h": 340, "resize": "fit" } } } ] }, "extended_entities": { "media": [ { "id": 704059330149031936, "id_str": "704059330149031936", "indices": [ 62, 85 ], "media_url": "http://pbs.twimg.com/media/CcVSOwJVIAAKwE6.jpg", "media_url_https": "https://pbs.twimg.com/media/CcVSOwJVIAAKwE6.jpg", "url": "https://t.co/K958bKh9Sd", "display_url": "pic.twitter.com/K958bKh9Sd", "expanded_url": "http://twitter.com/jeremycloud/status/704059336788606976/photo/1", "type": "photo", "sizes": { "medium": { "w": 600, "h": 600, "resize": "fit" }, "thumb": { "w": 150, "h": 150, "resize": "crop" }, "large": { "w": 871, "h": 871, "resize": "fit" }, "small": { "w": 340, "h": 340, "resize": "fit" } } } ] }, "truncated": false, "source": "Twitter for iPhone", "in_reply_to_status_id": null, "in_reply_to_status_id_str": null, "in_reply_to_user_id": null, "in_reply_to_user_id_str": null, "in_reply_to_screen_name": null, "user": { "id": 15062340, "id_str": "15062340", "name": "/dev/cloud/jeremy", "screen_name": "jeremycloud", "location": "Madison, Wisconsin", "description": "Professional yak shaver. Amateur bike shedder.", "url": "https://t.co/FcYeBkOpVY", "entities": { "url": { "urls": [ { "url": "https://t.co/FcYeBkOpVY", "expanded_url": "http://about.me/jeremy.cloud", "display_url": "about.me/jeremy.cloud", "indices": [ 0, 23 ] } ] }, "description": { "urls": [] } }, "protected": false, "followers_count": 4324, "friends_count": 410, "listed_count": 103, "created_at": "Mon Jun 09 17:00:58 +0000 2008", "favourites_count": 815, "utc_offset": -18000, "time_zone": "Central Time (US & Canada)", "geo_enabled": true, "verified": false, "statuses_count": 2218, "lang": "en", "contributors_enabled": false, "is_translator": false, "is_translation_enabled": false, "profile_background_color": "000000", "profile_background_image_url": "http://abs.twimg.com/images/themes/theme1/bg.png", "profile_background_image_url_https": "https://abs.twimg.com/images/themes/theme1/bg.png", "profile_background_tile": false, "profile_image_url": "http://pbs.twimg.com/profile_images/436903139183054849/i_MbCcoW_normal.jpeg", "profile_image_url_https": "https://pbs.twimg.com/profile_images/436903139183054849/i_MbCcoW_normal.jpeg", "profile_banner_url": "https://pbs.twimg.com/profile_banners/15062340/1447451621", "profile_link_color": "4A913C", "profile_sidebar_border_color": "000000", "profile_sidebar_fill_color": "000000", "profile_text_color": "000000", "profile_use_background_image": false, "has_extended_profile": true, "default_profile": false, "default_profile_image": false, "following": true, "follow_request_sent": false, "notifications": false }, "geo": null, "coordinates": null, "place": null, "contributors": null, "is_quote_status": false, "retweet_count": 0, "favorite_count": 11, "favorited": false, "retweeted": false, "possibly_sensitive": false, "possibly_sensitive_appealable": false, "lang": "en" }, "is_quote_status": true, "retweet_count": 0, "favorite_count": 0, "favorited": false, "retweeted": false, "possibly_sensitive": false, "possibly_sensitive_appealable": false, "lang": "en" }twitter-types-0.11.0/tests/fixtures/tweet-updates/compatibility_classic_13995.json0000644000000000000000000001142314144754426026464 0ustar0000000000000000{ "created_at": "Mon Mar 07 15:13:47 +0000 2016", "id": 706860403981099008, "id_str": "706860403981099008", "text": "Peek-a-boo! https://t.co/R3P6waHxRa", "entities": { "hashtags": [], "symbols": [], "user_mentions": [], "urls": [], "media": [ { "id": 706860403746181121, "id_str": "706860403746181121", "indices": [ 12, 35 ], "media_url": "http://pbs.twimg.com/media/Cc9FyscUkAEQaOw.jpg", "media_url_https": "https://pbs.twimg.com/media/Cc9FyscUkAEQaOw.jpg", "url": "https://t.co/R3P6waHxRa", "display_url": "pic.twitter.com/R3P6waHxRa", "expanded_url": "http://twitter.com/jeremycloud/status/706860403981099008/photo/1", "type": "photo", "sizes": { "medium": { "w": 600, "h": 398, "resize": "fit" }, "small": { "w": 340, "h": 226, "resize": "fit" }, "thumb": { "w": 150, "h": 150, "resize": "crop" }, "large": { "w": 1024, "h": 680, "resize": "fit" } } } ] }, "extended_entities": { "media": [ { "id": 706860403746181121, "id_str": "706860403746181121", "indices": [ 12, 35 ], "media_url": "http://pbs.twimg.com/media/Cc9FyscUkAEQaOw.jpg", "media_url_https": "https://pbs.twimg.com/media/Cc9FyscUkAEQaOw.jpg", "url": "https://t.co/R3P6waHxRa", "display_url": "pic.twitter.com/R3P6waHxRa", "expanded_url": "http://twitter.com/jeremycloud/status/706860403981099008/photo/1", "type": "photo", "sizes": { "medium": { "w": 600, "h": 398, "resize": "fit" }, "small": { "w": 340, "h": 226, "resize": "fit" }, "thumb": { "w": 150, "h": 150, "resize": "crop" }, "large": { "w": 1024, "h": 680, "resize": "fit" } } } ] }, "truncated": false, "source": "OS X", "in_reply_to_status_id": null, "in_reply_to_status_id_str": null, "in_reply_to_user_id": null, "in_reply_to_user_id_str": null, "in_reply_to_screen_name": null, "user": { "id": 15062340, "id_str": "15062340", "name": "/dev/cloud/jeremy", "screen_name": "jeremycloud", "location": "Madison, Wisconsin", "description": "Professional yak shaver. Amateur bike shedder.", "url": "https://t.co/FcYeBkOpVY", "entities": { "url": { "urls": [ { "url": "https://t.co/FcYeBkOpVY", "expanded_url": "http://about.me/jeremy.cloud", "display_url": "about.me/jeremy.cloud", "indices": [ 0, 23 ] } ] }, "description": { "urls": [] } }, "protected": false, "followers_count": 4324, "friends_count": 410, "listed_count": 103, "created_at": "Mon Jun 09 17:00:58 +0000 2008", "favourites_count": 815, "utc_offset": -18000, "time_zone": "Central Time (US & Canada)", "geo_enabled": true, "verified": false, "statuses_count": 2218, "lang": "en", "contributors_enabled": false, "is_translator": false, "is_translation_enabled": false, "profile_background_color": "000000", "profile_background_image_url": "http://abs.twimg.com/images/themes/theme1/bg.png", "profile_background_image_url_https": "https://abs.twimg.com/images/themes/theme1/bg.png", "profile_background_tile": false, "profile_image_url": "http://pbs.twimg.com/profile_images/436903139183054849/i_MbCcoW_normal.jpeg", "profile_image_url_https": "https://pbs.twimg.com/profile_images/436903139183054849/i_MbCcoW_normal.jpeg", "profile_banner_url": "https://pbs.twimg.com/profile_banners/15062340/1447451621", "profile_link_color": "4A913C", "profile_sidebar_border_color": "000000", "profile_sidebar_fill_color": "000000", "profile_text_color": "000000", "profile_use_background_image": false, "has_extended_profile": true, "default_profile": false, "default_profile_image": false, "following": true, "follow_request_sent": false, "notifications": false }, "geo": null, "coordinates": null, "place": null, "contributors": null, "is_quote_status": false, "retweet_count": 0, "favorite_count": 8, "favorited": false, "retweeted": false, "possibly_sensitive": false, "possibly_sensitive_appealable": false, "lang": "en" } twitter-types-0.11.0/tests/fixtures/tweet-updates/extended_extended_14001.json0000644000000000000000000001330314144754426025544 0ustar0000000000000000{ "created_at": "Thu Jun 16 17:33:23 +0000 2016", "id": 743496707711733760, "id_str": "743496707711733760", "full_text": "@twitter @twitterdev has more details about these changes at https://t.co/ZnXoRQy8mK. Thanks for making @twitter more expressive! https://t.co/AWmiH870F7", "truncated": false, "display_text_range": [ 9, 130 ], "entities": { "hashtags": [], "symbols": [], "user_mentions": [ { "screen_name": "twitter", "name": "Twitter", "id": 783214, "id_str": "783214", "indices": [ 0, 8 ] }, { "screen_name": "TwitterDev", "name": "TwitterDev", "id": 2244994945, "id_str": "2244994945", "indices": [ 9, 20 ] }, { "screen_name": "twitter", "name": "Twitter", "id": 783214, "id_str": "783214", "indices": [ 105, 113 ] } ], "urls": [ { "url": "https://t.co/ZnXoRQy8mK", "expanded_url": "https://blog.twitter.com/2016/doing-more-with-140-characters", "display_url": "blog.twitter.com/2016/doing-mor…", "indices": [ 61, 84 ] } ], "media": [ { "id": 743495942192566272, "id_str": "743495942192566272", "indices": [ 131, 154 ], "media_url": "http://pbs.twimg.com/tweet_video_thumb/ClFtnsZVEAAE4oA.jpg", "media_url_https": "https://pbs.twimg.com/tweet_video_thumb/ClFtnsZVEAAE4oA.jpg", "url": "https://t.co/AWmiH870F7", "display_url": "pic.twitter.com/AWmiH870F7", "expanded_url": "http://twitter.com/beyond_oneforty/status/743496707711733760/photo/1", "type": "photo", "sizes": { "small": { "w": 340, "h": 255, "resize": "fit" }, "medium": { "w": 480, "h": 360, "resize": "fit" }, "thumb": { "w": 150, "h": 150, "resize": "crop" }, "large": { "w": 480, "h": 360, "resize": "fit" } } } ] }, "extended_entities": { "media": [ { "id": 743495942192566272, "id_str": "743495942192566272", "indices": [ 131, 154 ], "media_url": "http://pbs.twimg.com/tweet_video_thumb/ClFtnsZVEAAE4oA.jpg", "media_url_https": "https://pbs.twimg.com/tweet_video_thumb/ClFtnsZVEAAE4oA.jpg", "url": "https://t.co/AWmiH870F7", "display_url": "pic.twitter.com/AWmiH870F7", "expanded_url": "http://twitter.com/beyond_oneforty/status/743496707711733760/photo/1", "type": "animated_gif", "sizes": { "small": { "w": 340, "h": 255, "resize": "fit" }, "medium": { "w": 480, "h": 360, "resize": "fit" }, "thumb": { "w": 150, "h": 150, "resize": "crop" }, "large": { "w": 480, "h": 360, "resize": "fit" } }, "video_info": { "aspect_ratio": [ 4, 3 ], "variants": [ { "bitrate": 0, "content_type": "video/mp4", "url": "https://pbs.twimg.com/tweet_video/ClFtnsZVEAAE4oA.mp4" } ] } } ] }, "source": "<a href=\"http://twitter.com\" rel=\"nofollow\">Twitter Web Client</a>", "in_reply_to_status_id": 735108260718469121, "in_reply_to_status_id_str": "735108260718469121", "in_reply_to_user_id": 783214, "in_reply_to_user_id_str": "783214", "in_reply_to_screen_name": "twitter", "user": { "id": 3883872981, "id_str": "3883872981", "name": "Beyond 140", "screen_name": "beyond_oneforty", "location": "", "description": "", "url": null, "entities": { "description": { "urls": [] } }, "protected": true, "followers_count": 51, "friends_count": 2, "listed_count": 0, "created_at": "Tue Oct 06 21:08:37 +0000 2015", "favourites_count": 1, "utc_offset": null, "time_zone": null, "geo_enabled": false, "verified": false, "statuses_count": 11, "lang": "en", "contributors_enabled": false, "is_translator": false, "is_translation_enabled": false, "profile_background_color": "C0DEED", "profile_background_image_url": "http://abs.twimg.com/images/themes/theme1/bg.png", "profile_background_image_url_https": "https://abs.twimg.com/images/themes/theme1/bg.png", "profile_background_tile": false, "profile_image_url": "http://pbs.twimg.com/profile_images/743489433861685249/VOcKbH8Z_normal.jpg", "profile_image_url_https": "https://pbs.twimg.com/profile_images/743489433861685249/VOcKbH8Z_normal.jpg", "profile_link_color": "0084B4", "profile_sidebar_border_color": "C0DEED", "profile_sidebar_fill_color": "DDEEF6", "profile_text_color": "333333", "profile_use_background_image": true, "has_extended_profile": false, "default_profile": true, "default_profile_image": false, "following": false, "follow_request_sent": false, "notifications": false }, "geo": null, "coordinates": null, "place": null, "contributors": null, "is_quote_status": false, "retweet_count": 0, "favorite_count": 0, "favorited": false, "retweeted": false, "possibly_sensitive": false, "possibly_sensitive_appealable": false, "lang": "en" }twitter-types-0.11.0/tests/fixtures/tweet-updates/extended_classic_14002.json0000644000000000000000000000465714144754426025402 0ustar0000000000000000{ "created_at": "Thu Jun 16 15:57:14 +0000 2016", "id": 743472511740870657, "id_str": "743472511740870657", "full_text": "Just setting up my Twitter. #myfirstTweet", "truncated": false, "display_text_range": [ 0, 41 ], "entities": { "hashtags": [ { "text": "myfirstTweet", "indices": [ 28, 41 ] } ], "symbols": [], "user_mentions": [], "urls": [] }, "source": "<a href=\"http://twitter.com\" rel=\"nofollow\">Twitter Web Client</a>", "in_reply_to_status_id": null, "in_reply_to_status_id_str": null, "in_reply_to_user_id": null, "in_reply_to_user_id_str": null, "in_reply_to_screen_name": null, "user": { "id": 3883872981, "id_str": "3883872981", "name": "Beyond 140", "screen_name": "beyond_oneforty", "location": "", "description": "", "url": null, "entities": { "description": { "urls": [] } }, "protected": true, "followers_count": 51, "friends_count": 0, "listed_count": 0, "created_at": "Tue Oct 06 21:08:37 +0000 2015", "favourites_count": 1, "utc_offset": null, "time_zone": null, "geo_enabled": false, "verified": false, "statuses_count": 9, "lang": "en", "contributors_enabled": false, "is_translator": false, "is_translation_enabled": false, "profile_background_color": "C0DEED", "profile_background_image_url": "http://abs.twimg.com/images/themes/theme1/bg.png", "profile_background_image_url_https": "https://abs.twimg.com/images/themes/theme1/bg.png", "profile_background_tile": false, "profile_image_url": "http://pbs.twimg.com/profile_images/651506565225271296/PMEWfvS__normal.jpg", "profile_image_url_https": "https://pbs.twimg.com/profile_images/651506565225271296/PMEWfvS__normal.jpg", "profile_link_color": "0084B4", "profile_sidebar_border_color": "C0DEED", "profile_sidebar_fill_color": "DDEEF6", "profile_text_color": "333333", "profile_use_background_image": true, "has_extended_profile": false, "default_profile": true, "default_profile_image": false, "following": false, "follow_request_sent": false, "notifications": false }, "geo": null, "coordinates": null, "place": null, "contributors": null, "is_quote_status": false, "retweet_count": 0, "favorite_count": 1, "favorited": false, "retweeted": false, "lang": "en" }twitter-types-0.11.0/tests/fixtures/tweet-updates/compatibility_classic_13995_extended.json0000644000000000000000000001150514144754426030345 0ustar0000000000000000{ "created_at": "Mon Mar 07 15:13:47 +0000 2016", "id": 706860403981099008, "id_str": "706860403981099008", "full_text": "Peek-a-boo! https://t.co/R3P6waHxRa", "display_text_range": [ 0, 35 ], "entities": { "hashtags": [], "symbols": [], "user_mentions": [], "urls": [], "media": [ { "id": 706860403746181121, "id_str": "706860403746181121", "indices": [ 12, 35 ], "media_url": "http://pbs.twimg.com/media/Cc9FyscUkAEQaOw.jpg", "media_url_https": "https://pbs.twimg.com/media/Cc9FyscUkAEQaOw.jpg", "url": "https://t.co/R3P6waHxRa", "display_url": "pic.twitter.com/R3P6waHxRa", "expanded_url": "http://twitter.com/jeremycloud/status/706860403981099008/photo/1", "type": "photo", "sizes": { "medium": { "w": 600, "h": 398, "resize": "fit" }, "small": { "w": 340, "h": 226, "resize": "fit" }, "thumb": { "w": 150, "h": 150, "resize": "crop" }, "large": { "w": 1024, "h": 680, "resize": "fit" } } } ] }, "extended_entities": { "media": [ { "id": 706860403746181121, "id_str": "706860403746181121", "indices": [ 12, 35 ], "media_url": "http://pbs.twimg.com/media/Cc9FyscUkAEQaOw.jpg", "media_url_https": "https://pbs.twimg.com/media/Cc9FyscUkAEQaOw.jpg", "url": "https://t.co/R3P6waHxRa", "display_url": "pic.twitter.com/R3P6waHxRa", "expanded_url": "http://twitter.com/jeremycloud/status/706860403981099008/photo/1", "type": "photo", "sizes": { "medium": { "w": 600, "h": 398, "resize": "fit" }, "small": { "w": 340, "h": 226, "resize": "fit" }, "thumb": { "w": 150, "h": 150, "resize": "crop" }, "large": { "w": 1024, "h": 680, "resize": "fit" } } } ] }, "truncated": false, "source": "OS X", "in_reply_to_status_id": null, "in_reply_to_status_id_str": null, "in_reply_to_user_id": null, "in_reply_to_user_id_str": null, "in_reply_to_screen_name": null, "user": { "id": 15062340, "id_str": "15062340", "name": "/dev/cloud/jeremy", "screen_name": "jeremycloud", "location": "Madison, Wisconsin", "description": "Professional yak shaver. Amateur bike shedder.", "url": "https://t.co/FcYeBkOpVY", "entities": { "url": { "urls": [ { "url": "https://t.co/FcYeBkOpVY", "expanded_url": "http://about.me/jeremy.cloud", "display_url": "about.me/jeremy.cloud", "indices": [ 0, 23 ] } ] }, "description": { "urls": [] } }, "protected": false, "followers_count": 4324, "friends_count": 410, "listed_count": 103, "created_at": "Mon Jun 09 17:00:58 +0000 2008", "favourites_count": 815, "utc_offset": -18000, "time_zone": "Central Time (US & Canada)", "geo_enabled": true, "verified": false, "statuses_count": 2218, "lang": "en", "contributors_enabled": false, "is_translator": false, "is_translation_enabled": false, "profile_background_color": "000000", "profile_background_image_url": "http://abs.twimg.com/images/themes/theme1/bg.png", "profile_background_image_url_https": "https://abs.twimg.com/images/themes/theme1/bg.png", "profile_background_tile": false, "profile_image_url": "http://pbs.twimg.com/profile_images/436903139183054849/i_MbCcoW_normal.jpeg", "profile_image_url_https": "https://pbs.twimg.com/profile_images/436903139183054849/i_MbCcoW_normal.jpeg", "profile_banner_url": "https://pbs.twimg.com/profile_banners/15062340/1447451621", "profile_link_color": "4A913C", "profile_sidebar_border_color": "000000", "profile_sidebar_fill_color": "000000", "profile_text_color": "000000", "profile_use_background_image": false, "has_extended_profile": true, "default_profile": false, "default_profile_image": false, "following": true, "follow_request_sent": false, "notifications": false }, "geo": null, "coordinates": null, "place": null, "contributors": null, "is_quote_status": false, "retweet_count": 0, "favorite_count": 8, "favorited": false, "retweeted": false, "possibly_sensitive": false, "possibly_sensitive_appealable": false, "lang": "en" } twitter-types-0.11.0/tests/fixtures/tweet-updates/compatibility_classic_hidden_13797.json0000644000000000000000000002000314144754426027771 0ustar0000000000000000{ "created_at": "Thu Mar 10 23:12:12 +0000 2016", "id": 708067963060916224, "id_str": "708067963060916224", "text": "@jeremycloud Who would win in a battle between a Barred Owl and a Cooper's Hawk? https://t.co/FamikDro2h", "entities": { "hashtags": [], "symbols": [], "user_mentions": [ { "screen_name": "jeremycloud", "name": "/dev/cloud/jeremy", "id": 15062340, "id_str": "15062340", "indices": [ 0, 12 ] } ], "urls": [ { "url": "https://t.co/FamikDro2h", "expanded_url": "https://twitter.com/jeremycloud/status/703621193417379840", "display_url": "twitter.com/jeremycloud/st…", "indices": [ 81, 104 ] } ] }, "truncated": false, "source": "bonesTwurl", "in_reply_to_status_id": 704059336788606976, "in_reply_to_status_id_str": "704059336788606976", "in_reply_to_user_id": 15062340, "in_reply_to_user_id_str": "15062340", "in_reply_to_screen_name": "jeremycloud", "user": { "id": 4449621923, "id_str": "4449621923", "name": "Mr Bones", "screen_name": "MrBonesDroid", "location": "", "profile_location": null, "description": "", "url": null, "entities": { "description": { "urls": [] } }, "protected": true, "followers_count": 5, "friends_count": 7, "listed_count": 0, "created_at": "Fri Dec 11 15:18:02 +0000 2015", "favourites_count": 7, "utc_offset": -25200, "time_zone": "Pacific Time (US & Canada)", "geo_enabled": false, "verified": false, "statuses_count": 35, "lang": "en-gb", "contributors_enabled": false, "is_translator": false, "is_translation_enabled": false, "profile_background_color": "F5F8FA", "profile_background_image_url": null, "profile_background_image_url_https": null, "profile_background_tile": false, "profile_image_url": "http://pbs.twimg.com/profile_images/677097663288860672/zZxWCPSI_normal.jpg", "profile_image_url_https": "https://pbs.twimg.com/profile_images/677097663288860672/zZxWCPSI_normal.jpg", "profile_link_color": "2B7BB9", "profile_sidebar_border_color": "C0DEED", "profile_sidebar_fill_color": "DDEEF6", "profile_text_color": "333333", "profile_use_background_image": true, "has_extended_profile": false, "default_profile": true, "default_profile_image": false, "following": true, "follow_request_sent": false, "notifications": false }, "geo": null, "coordinates": null, "place": null, "contributors": null, "quoted_status_id": 703621193417379840, "quoted_status_id_str": "703621193417379840", "quoted_status": { "created_at": "Sat Feb 27 16:42:19 +0000 2016", "id": 703621193417379840, "id_str": "703621193417379840", "text": "Cooper’s Hawk https://t.co/nppuOGne9X", "entities": { "hashtags": [], "symbols": [], "user_mentions": [], "urls": [], "media": [ { "id": 703621193182502913, "id_str": "703621193182502913", "indices": [ 14, 37 ], "media_url": "http://pbs.twimg.com/media/CcPDv0wUYAE3D-2.jpg", "media_url_https": "https://pbs.twimg.com/media/CcPDv0wUYAE3D-2.jpg", "url": "https://t.co/nppuOGne9X", "display_url": "pic.twitter.com/nppuOGne9X", "expanded_url": "http://twitter.com/jeremycloud/status/703621193417379840/photo/1", "type": "photo", "sizes": { "medium": { "w": 600, "h": 398, "resize": "fit" }, "thumb": { "w": 150, "h": 150, "resize": "crop" }, "large": { "w": 1024, "h": 680, "resize": "fit" }, "small": { "w": 340, "h": 226, "resize": "fit" } } } ] }, "extended_entities": { "media": [ { "id": 703621193182502913, "id_str": "703621193182502913", "indices": [ 14, 37 ], "media_url": "http://pbs.twimg.com/media/CcPDv0wUYAE3D-2.jpg", "media_url_https": "https://pbs.twimg.com/media/CcPDv0wUYAE3D-2.jpg", "url": "https://t.co/nppuOGne9X", "display_url": "pic.twitter.com/nppuOGne9X", "expanded_url": "http://twitter.com/jeremycloud/status/703621193417379840/photo/1", "type": "photo", "sizes": { "medium": { "w": 600, "h": 398, "resize": "fit" }, "thumb": { "w": 150, "h": 150, "resize": "crop" }, "large": { "w": 1024, "h": 680, "resize": "fit" }, "small": { "w": 340, "h": 226, "resize": "fit" } } } ] }, "truncated": false, "source": "OS X", "in_reply_to_status_id": null, "in_reply_to_status_id_str": null, "in_reply_to_user_id": null, "in_reply_to_user_id_str": null, "in_reply_to_screen_name": null, "user": { "id": 15062340, "id_str": "15062340", "name": "/dev/cloud/jeremy", "screen_name": "jeremycloud", "location": "Madison, Wisconsin", "description": "Professional yak shaver. Amateur bike shedder.", "url": "https://t.co/FcYeBkOpVY", "entities": { "url": { "urls": [ { "url": "https://t.co/FcYeBkOpVY", "expanded_url": "http://about.me/jeremy.cloud", "display_url": "about.me/jeremy.cloud", "indices": [ 0, 23 ] } ] }, "description": { "urls": [] } }, "protected": false, "followers_count": 4329, "friends_count": 411, "listed_count": 103, "created_at": "Mon Jun 09 17:00:58 +0000 2008", "favourites_count": 803, "utc_offset": -21600, "time_zone": "Central Time (US & Canada)", "geo_enabled": true, "verified": false, "statuses_count": 2216, "lang": "en", "contributors_enabled": false, "is_translator": false, "is_translation_enabled": false, "profile_background_color": "000000", "profile_background_image_url": "http://abs.twimg.com/images/themes/theme1/bg.png", "profile_background_image_url_https": "https://abs.twimg.com/images/themes/theme1/bg.png", "profile_background_tile": false, "profile_image_url": "http://pbs.twimg.com/profile_images/436903139183054849/i_MbCcoW_normal.jpeg", "profile_image_url_https": "https://pbs.twimg.com/profile_images/436903139183054849/i_MbCcoW_normal.jpeg", "profile_banner_url": "https://pbs.twimg.com/profile_banners/15062340/1447451621", "profile_link_color": "4A913C", "profile_sidebar_border_color": "000000", "profile_sidebar_fill_color": "000000", "profile_text_color": "000000", "profile_use_background_image": false, "has_extended_profile": true, "default_profile": false, "default_profile_image": false, "following": true, "follow_request_sent": false, "notifications": false }, "geo": null, "coordinates": null, "place": null, "contributors": null, "is_quote_status": false, "retweet_count": 0, "favorite_count": 2, "favorited": false, "retweeted": false, "possibly_sensitive": false, "possibly_sensitive_appealable": false, "lang": "en" }, "is_quote_status": true, "retweet_count": 0, "favorite_count": 0, "favorited": false, "retweeted": false, "possibly_sensitive": false, "possibly_sensitive_appealable": false, "lang": "en" }twitter-types-0.11.0/tests/fixtures/tweet-updates/compatibilityplus_extended_13997.json0000644000000000000000000002043614144754426027555 0ustar0000000000000000{ "created_at": "Mon Mar 28 14:39:13 +0000 2016", "id": 714461850188926976, "id_str": "714461850188926976", "full_text": "@jeremycloud It's neat to have owls and raccoons around until you realize that raccoons will eat the eggs from the owl's nest https://t.co/Q0pkaU4ORH", "display_text_range": [ 13, 125 ], "entities": { "hashtags": [], "symbols": [], "user_mentions": [ { "screen_name": "jeremycloud", "name": "/dev/cloud/jeremy", "id": 15062340, "id_str": "15062340", "indices": [ 0, 12 ] } ], "urls": [ { "url": "https://t.co/Q0pkaU4ORH", "expanded_url": "https://twitter.com/jeremycloud/status/704059336788606976", "display_url": "twitter.com/jeremycloud/st…", "indices": [ 126, 149 ] } ] }, "truncated": false, "source": "Twitter Web Client", "in_reply_to_status_id": 706860403981099008, "in_reply_to_status_id_str": "706860403981099008", "in_reply_to_user_id": 15062340, "in_reply_to_user_id_str": "15062340", "in_reply_to_screen_name": "jeremycloud", "user": { "id": 4449621923, "id_str": "4449621923", "name": "Mr Bones", "screen_name": "MrBonesDroid", "location": "", "profile_location": null, "description": "", "url": null, "entities": { "description": { "urls": [] } }, "protected": true, "followers_count": 5, "friends_count": 7, "listed_count": 0, "created_at": "Fri Dec 11 15:18:02 +0000 2015", "favourites_count": 7, "utc_offset": -25200, "time_zone": "Pacific Time (US & Canada)", "geo_enabled": false, "verified": false, "statuses_count": 35, "lang": "en-gb", "contributors_enabled": false, "is_translator": false, "is_translation_enabled": false, "profile_background_color": "F5F8FA", "profile_background_image_url": null, "profile_background_image_url_https": null, "profile_background_tile": false, "profile_image_url": "http://pbs.twimg.com/profile_images/677097663288860672/zZxWCPSI_normal.jpg", "profile_image_url_https": "https://pbs.twimg.com/profile_images/677097663288860672/zZxWCPSI_normal.jpg", "profile_link_color": "2B7BB9", "profile_sidebar_border_color": "C0DEED", "profile_sidebar_fill_color": "DDEEF6", "profile_text_color": "333333", "profile_use_background_image": true, "has_extended_profile": false, "default_profile": true, "default_profile_image": false, "following": true, "follow_request_sent": false, "notifications": false }, "geo": null, "coordinates": null, "place": null, "contributors": null, "quoted_status_id": 704059336788606976, "quoted_status_id_str": "704059336788606976", "quoted_status": { "created_at": "Sun Feb 28 21:43:21 +0000 2016", "id": 704059336788606976, "id_str": "704059336788606976", "full_text": "My favorite photographic subject, up closer than ever before. https://t.co/K958bKh9Sd", "display_text_range": [ 0, 85 ], "entities": { "hashtags": [], "symbols": [], "user_mentions": [], "urls": [], "media": [ { "id": 704059330149031936, "id_str": "704059330149031936", "indices": [ 62, 85 ], "media_url": "http://pbs.twimg.com/media/CcVSOwJVIAAKwE6.jpg", "media_url_https": "https://pbs.twimg.com/media/CcVSOwJVIAAKwE6.jpg", "url": "https://t.co/K958bKh9Sd", "display_url": "pic.twitter.com/K958bKh9Sd", "expanded_url": "http://twitter.com/jeremycloud/status/704059336788606976/photo/1", "type": "photo", "sizes": { "medium": { "w": 600, "h": 600, "resize": "fit" }, "thumb": { "w": 150, "h": 150, "resize": "crop" }, "large": { "w": 871, "h": 871, "resize": "fit" }, "small": { "w": 340, "h": 340, "resize": "fit" } } } ] }, "extended_entities": { "media": [ { "id": 704059330149031936, "id_str": "704059330149031936", "indices": [ 62, 85 ], "media_url": "http://pbs.twimg.com/media/CcVSOwJVIAAKwE6.jpg", "media_url_https": "https://pbs.twimg.com/media/CcVSOwJVIAAKwE6.jpg", "url": "https://t.co/K958bKh9Sd", "display_url": "pic.twitter.com/K958bKh9Sd", "expanded_url": "http://twitter.com/jeremycloud/status/704059336788606976/photo/1", "type": "photo", "sizes": { "medium": { "w": 600, "h": 600, "resize": "fit" }, "thumb": { "w": 150, "h": 150, "resize": "crop" }, "large": { "w": 871, "h": 871, "resize": "fit" }, "small": { "w": 340, "h": 340, "resize": "fit" } } } ] }, "truncated": false, "source": "Twitter for iPhone", "in_reply_to_status_id": null, "in_reply_to_status_id_str": null, "in_reply_to_user_id": null, "in_reply_to_user_id_str": null, "in_reply_to_screen_name": null, "user": { "id": 15062340, "id_str": "15062340", "name": "/dev/cloud/jeremy", "screen_name": "jeremycloud", "location": "Madison, Wisconsin", "description": "Professional yak shaver. Amateur bike shedder.", "url": "https://t.co/FcYeBkOpVY", "entities": { "url": { "urls": [ { "url": "https://t.co/FcYeBkOpVY", "expanded_url": "http://about.me/jeremy.cloud", "display_url": "about.me/jeremy.cloud", "indices": [ 0, 23 ] } ] }, "description": { "urls": [] } }, "protected": false, "followers_count": 4324, "friends_count": 410, "listed_count": 103, "created_at": "Mon Jun 09 17:00:58 +0000 2008", "favourites_count": 815, "utc_offset": -18000, "time_zone": "Central Time (US & Canada)", "geo_enabled": true, "verified": false, "statuses_count": 2218, "lang": "en", "contributors_enabled": false, "is_translator": false, "is_translation_enabled": false, "profile_background_color": "000000", "profile_background_image_url": "http://abs.twimg.com/images/themes/theme1/bg.png", "profile_background_image_url_https": "https://abs.twimg.com/images/themes/theme1/bg.png", "profile_background_tile": false, "profile_image_url": "http://pbs.twimg.com/profile_images/436903139183054849/i_MbCcoW_normal.jpeg", "profile_image_url_https": "https://pbs.twimg.com/profile_images/436903139183054849/i_MbCcoW_normal.jpeg", "profile_banner_url": "https://pbs.twimg.com/profile_banners/15062340/1447451621", "profile_link_color": "4A913C", "profile_sidebar_border_color": "000000", "profile_sidebar_fill_color": "000000", "profile_text_color": "000000", "profile_use_background_image": false, "has_extended_profile": true, "default_profile": false, "default_profile_image": false, "following": true, "follow_request_sent": false, "notifications": false }, "geo": null, "coordinates": null, "place": null, "contributors": null, "is_quote_status": false, "retweet_count": 0, "favorite_count": 11, "favorited": false, "retweeted": false, "possibly_sensitive": false, "possibly_sensitive_appealable": false, "lang": "en" }, "is_quote_status": true, "retweet_count": 0, "favorite_count": 0, "favorited": false, "retweeted": false, "possibly_sensitive": false, "possibly_sensitive_appealable": false, "lang": "en" }twitter-types-0.11.0/tests/fixtures/tweet-updates/extended_classic_hidden_13761.json0000644000000000000000000001177014144754426026722 0ustar0000000000000000{ "created_at": "Thu Jun 16 16:24:44 +0000 2016", "id": 743479431658758145, "id_str": "743479431658758145", "full_text": "@TwitterDev I'm really excited for this change! https://t.co/VnJMDg3cbS", "truncated": false, "display_text_range": [ 12, 47 ], "entities": { "hashtags": [], "symbols": [], "user_mentions": [ { "screen_name": "TwitterDev", "name": "TwitterDev", "id": 2244994945, "id_str": "2244994945", "indices": [ 0, 11 ] } ], "urls": [], "media": [ { "id": 743479379079004160, "id_str": "743479379079004160", "indices": [ 48, 71 ], "media_url": "http://pbs.twimg.com/tweet_video_thumb/ClFejl_VAAAo9Xk.jpg", "media_url_https": "https://pbs.twimg.com/tweet_video_thumb/ClFejl_VAAAo9Xk.jpg", "url": "https://t.co/VnJMDg3cbS", "display_url": "pic.twitter.com/VnJMDg3cbS", "expanded_url": "http://twitter.com/beyond_oneforty/status/743479431658758145/photo/1", "type": "photo", "sizes": { "medium": { "w": 480, "h": 268, "resize": "fit" }, "thumb": { "w": 150, "h": 150, "resize": "crop" }, "large": { "w": 480, "h": 268, "resize": "fit" }, "small": { "w": 340, "h": 190, "resize": "fit" } } } ] }, "extended_entities": { "media": [ { "id": 743479379079004160, "id_str": "743479379079004160", "indices": [ 48, 71 ], "media_url": "http://pbs.twimg.com/tweet_video_thumb/ClFejl_VAAAo9Xk.jpg", "media_url_https": "https://pbs.twimg.com/tweet_video_thumb/ClFejl_VAAAo9Xk.jpg", "url": "https://t.co/VnJMDg3cbS", "display_url": "pic.twitter.com/VnJMDg3cbS", "expanded_url": "http://twitter.com/beyond_oneforty/status/743479431658758145/photo/1", "type": "animated_gif", "sizes": { "medium": { "w": 480, "h": 268, "resize": "fit" }, "thumb": { "w": 150, "h": 150, "resize": "crop" }, "large": { "w": 480, "h": 268, "resize": "fit" }, "small": { "w": 340, "h": 190, "resize": "fit" } }, "video_info": { "aspect_ratio": [ 120, 67 ], "variants": [ { "bitrate": 0, "content_type": "video/mp4", "url": "https://pbs.twimg.com/tweet_video/ClFejl_VAAAo9Xk.mp4" } ] } } ] }, "source": "<a href=\"http://twitter.com\" rel=\"nofollow\">Twitter Web Client</a>", "in_reply_to_status_id": 735111578660438017, "in_reply_to_status_id_str": "735111578660438017", "in_reply_to_user_id": 2244994945, "in_reply_to_user_id_str": "2244994945", "in_reply_to_screen_name": "TwitterDev", "user": { "id": 3883872981, "id_str": "3883872981", "name": "Beyond 140", "screen_name": "beyond_oneforty", "location": "", "description": "", "url": null, "entities": { "description": { "urls": [] } }, "protected": true, "followers_count": 51, "friends_count": 0, "listed_count": 0, "created_at": "Tue Oct 06 21:08:37 +0000 2015", "favourites_count": 1, "utc_offset": null, "time_zone": null, "geo_enabled": false, "verified": false, "statuses_count": 10, "lang": "en", "contributors_enabled": false, "is_translator": false, "is_translation_enabled": false, "profile_background_color": "C0DEED", "profile_background_image_url": "http://abs.twimg.com/images/themes/theme1/bg.png", "profile_background_image_url_https": "https://abs.twimg.com/images/themes/theme1/bg.png", "profile_background_tile": false, "profile_image_url": "http://pbs.twimg.com/profile_images/651506565225271296/PMEWfvS__normal.jpg", "profile_image_url_https": "https://pbs.twimg.com/profile_images/651506565225271296/PMEWfvS__normal.jpg", "profile_link_color": "0084B4", "profile_sidebar_border_color": "C0DEED", "profile_sidebar_fill_color": "DDEEF6", "profile_text_color": "333333", "profile_use_background_image": true, "has_extended_profile": false, "default_profile": true, "default_profile_image": false, "following": false, "follow_request_sent": false, "notifications": false }, "geo": null, "coordinates": null, "place": null, "contributors": null, "is_quote_status": false, "retweet_count": 0, "favorite_count": 1, "favorited": false, "retweeted": false, "possibly_sensitive": false, "possibly_sensitive_appealable": false, "lang": "en" }twitter-types-0.11.0/tests/fixtures/tweet-updates/compatibilityplus_classic_13994.json0000644000000000000000000002024614144754426027372 0ustar0000000000000000{ "created_at": "Mon Mar 28 14:39:13 +0000 2016", "id": 714461850188926976, "id_str": "714461850188926976", "text": "@jeremycloud It's neat to have owls and raccoons around until you realize that raccoons will eat the eggs from the … https://t.co/OY7qmdJQnO", "entities": { "hashtags": [], "symbols": [], "user_mentions": [ { "screen_name": "jeremycloud", "name": "/dev/cloud/jeremy", "id": 15062340, "id_str": "15062340", "indices": [ 0, 12 ] } ], "urls": [ { "url": "https://t.co/OY7qmdJQnO", "expanded_url": "https://twitter.com/i/web/status/714461850188926976", "display_url": "twitter.com/i/web/status/7…", "indices": [ 117, 140 ] } ] }, "truncated": true, "source": "Twitter Web Client", "in_reply_to_status_id": 706860403981099008, "in_reply_to_status_id_str": "706860403981099008", "in_reply_to_user_id": 15062340, "in_reply_to_user_id_str": "15062340", "in_reply_to_screen_name": "jeremycloud", "user": { "id": 4449621923, "id_str": "4449621923", "name": "Mr Bones", "screen_name": "MrBonesDroid", "location": "", "profile_location": null, "description": "", "url": null, "entities": { "description": { "urls": [] } }, "protected": true, "followers_count": 5, "friends_count": 7, "listed_count": 0, "created_at": "Fri Dec 11 15:18:02 +0000 2015", "favourites_count": 7, "utc_offset": -25200, "time_zone": "Pacific Time (US & Canada)", "geo_enabled": false, "verified": false, "statuses_count": 35, "lang": "en-gb", "contributors_enabled": false, "is_translator": false, "is_translation_enabled": false, "profile_background_color": "F5F8FA", "profile_background_image_url": null, "profile_background_image_url_https": null, "profile_background_tile": false, "profile_image_url": "http://pbs.twimg.com/profile_images/677097663288860672/zZxWCPSI_normal.jpg", "profile_image_url_https": "https://pbs.twimg.com/profile_images/677097663288860672/zZxWCPSI_normal.jpg", "profile_link_color": "2B7BB9", "profile_sidebar_border_color": "C0DEED", "profile_sidebar_fill_color": "DDEEF6", "profile_text_color": "333333", "profile_use_background_image": true, "has_extended_profile": false, "default_profile": true, "default_profile_image": false, "following": true, "follow_request_sent": false, "notifications": false }, "geo": null, "coordinates": null, "place": null, "contributors": null, "quoted_status_id": 704059336788606976, "quoted_status_id_str": "704059336788606976", "quoted_status": { "created_at": "Sun Feb 28 21:43:21 +0000 2016", "id": 704059336788606976, "id_str": "704059336788606976", "text": "My favorite photographic subject, up closer than ever before. https://t.co/K958bKh9Sd", "entities": { "hashtags": [], "symbols": [], "user_mentions": [], "urls": [], "media": [ { "id": 704059330149031936, "id_str": "704059330149031936", "indices": [ 62, 85 ], "media_url": "http://pbs.twimg.com/media/CcVSOwJVIAAKwE6.jpg", "media_url_https": "https://pbs.twimg.com/media/CcVSOwJVIAAKwE6.jpg", "url": "https://t.co/K958bKh9Sd", "display_url": "pic.twitter.com/K958bKh9Sd", "expanded_url": "http://twitter.com/jeremycloud/status/704059336788606976/photo/1", "type": "photo", "sizes": { "medium": { "w": 600, "h": 600, "resize": "fit" }, "thumb": { "w": 150, "h": 150, "resize": "crop" }, "large": { "w": 871, "h": 871, "resize": "fit" }, "small": { "w": 340, "h": 340, "resize": "fit" } } } ] }, "extended_entities": { "media": [ { "id": 704059330149031936, "id_str": "704059330149031936", "indices": [ 62, 85 ], "media_url": "http://pbs.twimg.com/media/CcVSOwJVIAAKwE6.jpg", "media_url_https": "https://pbs.twimg.com/media/CcVSOwJVIAAKwE6.jpg", "url": "https://t.co/K958bKh9Sd", "display_url": "pic.twitter.com/K958bKh9Sd", "expanded_url": "http://twitter.com/jeremycloud/status/704059336788606976/photo/1", "type": "photo", "sizes": { "medium": { "w": 600, "h": 600, "resize": "fit" }, "thumb": { "w": 150, "h": 150, "resize": "crop" }, "large": { "w": 871, "h": 871, "resize": "fit" }, "small": { "w": 340, "h": 340, "resize": "fit" } } } ] }, "truncated": false, "source": "Twitter for iPhone", "in_reply_to_status_id": null, "in_reply_to_status_id_str": null, "in_reply_to_user_id": null, "in_reply_to_user_id_str": null, "in_reply_to_screen_name": null, "user": { "id": 15062340, "id_str": "15062340", "name": "/dev/cloud/jeremy", "screen_name": "jeremycloud", "location": "Madison, Wisconsin", "description": "Professional yak shaver. Amateur bike shedder.", "url": "https://t.co/FcYeBkOpVY", "entities": { "url": { "urls": [ { "url": "https://t.co/FcYeBkOpVY", "expanded_url": "http://about.me/jeremy.cloud", "display_url": "about.me/jeremy.cloud", "indices": [ 0, 23 ] } ] }, "description": { "urls": [] } }, "protected": false, "followers_count": 4324, "friends_count": 410, "listed_count": 103, "created_at": "Mon Jun 09 17:00:58 +0000 2008", "favourites_count": 815, "utc_offset": -18000, "time_zone": "Central Time (US & Canada)", "geo_enabled": true, "verified": false, "statuses_count": 2218, "lang": "en", "contributors_enabled": false, "is_translator": false, "is_translation_enabled": false, "profile_background_color": "000000", "profile_background_image_url": "http://abs.twimg.com/images/themes/theme1/bg.png", "profile_background_image_url_https": "https://abs.twimg.com/images/themes/theme1/bg.png", "profile_background_tile": false, "profile_image_url": "http://pbs.twimg.com/profile_images/436903139183054849/i_MbCcoW_normal.jpeg", "profile_image_url_https": "https://pbs.twimg.com/profile_images/436903139183054849/i_MbCcoW_normal.jpeg", "profile_banner_url": "https://pbs.twimg.com/profile_banners/15062340/1447451621", "profile_link_color": "4A913C", "profile_sidebar_border_color": "000000", "profile_sidebar_fill_color": "000000", "profile_text_color": "000000", "profile_use_background_image": false, "has_extended_profile": true, "default_profile": false, "default_profile_image": false, "following": true, "follow_request_sent": false, "notifications": false }, "geo": null, "coordinates": null, "place": null, "contributors": null, "is_quote_status": false, "retweet_count": 0, "favorite_count": 11, "favorited": false, "retweeted": false, "possibly_sensitive": false, "possibly_sensitive_appealable": false, "lang": "en" }, "is_quote_status": true, "retweet_count": 0, "favorite_count": 0, "favorited": false, "retweeted": false, "possibly_sensitive": false, "possibly_sensitive_appealable": false, "lang": "en" }twitter-types-0.11.0/tests/fixtures/tweet-updates/compatibility_extended_13996.json0000644000000000000000000002016014144754426026642 0ustar0000000000000000{ "created_at": "Thu Mar 10 23:12:12 +0000 2016", "id": 708067963060916224, "id_str": "708067963060916224", "full_text": "@jeremycloud Who would win in a battle between a Barred Owl and a Cooper's Hawk? https://t.co/FamikDro2h", "display_text_range": [ 13, 80 ], "entities": { "hashtags": [], "symbols": [], "user_mentions": [ { "screen_name": "jeremycloud", "name": "/dev/cloud/jeremy", "id": 15062340, "id_str": "15062340", "indices": [ 0, 12 ] } ], "urls": [ { "url": "https://t.co/FamikDro2h", "expanded_url": "https://twitter.com/jeremycloud/status/703621193417379840", "display_url": "twitter.com/jeremycloud/st…", "indices": [ 81, 104 ] } ] }, "truncated": false, "source": "bonesTwurl", "in_reply_to_status_id": 704059336788606976, "in_reply_to_status_id_str": "704059336788606976", "in_reply_to_user_id": 15062340, "in_reply_to_user_id_str": "15062340", "in_reply_to_screen_name": "jeremycloud", "user": { "id": 4449621923, "id_str": "4449621923", "name": "Mr Bones", "screen_name": "MrBonesDroid", "location": "", "profile_location": null, "description": "", "url": null, "entities": { "description": { "urls": [] } }, "protected": true, "followers_count": 5, "friends_count": 7, "listed_count": 0, "created_at": "Fri Dec 11 15:18:02 +0000 2015", "favourites_count": 7, "utc_offset": -25200, "time_zone": "Pacific Time (US & Canada)", "geo_enabled": false, "verified": false, "statuses_count": 35, "lang": "en-gb", "contributors_enabled": false, "is_translator": false, "is_translation_enabled": false, "profile_background_color": "F5F8FA", "profile_background_image_url": null, "profile_background_image_url_https": null, "profile_background_tile": false, "profile_image_url": "http://pbs.twimg.com/profile_images/677097663288860672/zZxWCPSI_normal.jpg", "profile_image_url_https": "https://pbs.twimg.com/profile_images/677097663288860672/zZxWCPSI_normal.jpg", "profile_link_color": "2B7BB9", "profile_sidebar_border_color": "C0DEED", "profile_sidebar_fill_color": "DDEEF6", "profile_text_color": "333333", "profile_use_background_image": true, "has_extended_profile": false, "default_profile": true, "default_profile_image": false, "following": true, "follow_request_sent": false, "notifications": false }, "geo": null, "coordinates": null, "place": null, "contributors": null, "quoted_status_id": 703621193417379840, "quoted_status_id_str": "703621193417379840", "quoted_status": { "created_at": "Sat Feb 27 16:42:19 +0000 2016", "id": 703621193417379840, "id_str": "703621193417379840", "full_text": "Cooper’s Hawk https://t.co/nppuOGne9X", "display_text_range": [ 0, 37 ], "entities": { "hashtags": [], "symbols": [], "user_mentions": [], "urls": [], "media": [ { "id": 703621193182502913, "id_str": "703621193182502913", "indices": [ 14, 37 ], "media_url": "http://pbs.twimg.com/media/CcPDv0wUYAE3D-2.jpg", "media_url_https": "https://pbs.twimg.com/media/CcPDv0wUYAE3D-2.jpg", "url": "https://t.co/nppuOGne9X", "display_url": "pic.twitter.com/nppuOGne9X", "expanded_url": "http://twitter.com/jeremycloud/status/703621193417379840/photo/1", "type": "photo", "sizes": { "medium": { "w": 600, "h": 398, "resize": "fit" }, "thumb": { "w": 150, "h": 150, "resize": "crop" }, "large": { "w": 1024, "h": 680, "resize": "fit" }, "small": { "w": 340, "h": 226, "resize": "fit" } } } ] }, "extended_entities": { "media": [ { "id": 703621193182502913, "id_str": "703621193182502913", "indices": [ 14, 37 ], "media_url": "http://pbs.twimg.com/media/CcPDv0wUYAE3D-2.jpg", "media_url_https": "https://pbs.twimg.com/media/CcPDv0wUYAE3D-2.jpg", "url": "https://t.co/nppuOGne9X", "display_url": "pic.twitter.com/nppuOGne9X", "expanded_url": "http://twitter.com/jeremycloud/status/703621193417379840/photo/1", "type": "photo", "sizes": { "medium": { "w": 600, "h": 398, "resize": "fit" }, "thumb": { "w": 150, "h": 150, "resize": "crop" }, "large": { "w": 1024, "h": 680, "resize": "fit" }, "small": { "w": 340, "h": 226, "resize": "fit" } } } ] }, "truncated": false, "source": "OS X", "in_reply_to_status_id": null, "in_reply_to_status_id_str": null, "in_reply_to_user_id": null, "in_reply_to_user_id_str": null, "in_reply_to_screen_name": null, "user": { "id": 15062340, "id_str": "15062340", "name": "/dev/cloud/jeremy", "screen_name": "jeremycloud", "location": "Madison, Wisconsin", "description": "Professional yak shaver. Amateur bike shedder.", "url": "https://t.co/FcYeBkOpVY", "entities": { "url": { "urls": [ { "url": "https://t.co/FcYeBkOpVY", "expanded_url": "http://about.me/jeremy.cloud", "display_url": "about.me/jeremy.cloud", "indices": [ 0, 23 ] } ] }, "description": { "urls": [] } }, "protected": false, "followers_count": 4329, "friends_count": 411, "listed_count": 103, "created_at": "Mon Jun 09 17:00:58 +0000 2008", "favourites_count": 803, "utc_offset": -21600, "time_zone": "Central Time (US & Canada)", "geo_enabled": true, "verified": false, "statuses_count": 2216, "lang": "en", "contributors_enabled": false, "is_translator": false, "is_translation_enabled": false, "profile_background_color": "000000", "profile_background_image_url": "http://abs.twimg.com/images/themes/theme1/bg.png", "profile_background_image_url_https": "https://abs.twimg.com/images/themes/theme1/bg.png", "profile_background_tile": false, "profile_image_url": "http://pbs.twimg.com/profile_images/436903139183054849/i_MbCcoW_normal.jpeg", "profile_image_url_https": "https://pbs.twimg.com/profile_images/436903139183054849/i_MbCcoW_normal.jpeg", "profile_banner_url": "https://pbs.twimg.com/profile_banners/15062340/1447451621", "profile_link_color": "4A913C", "profile_sidebar_border_color": "000000", "profile_sidebar_fill_color": "000000", "profile_text_color": "000000", "profile_use_background_image": false, "has_extended_profile": true, "default_profile": false, "default_profile_image": false, "following": true, "follow_request_sent": false, "notifications": false }, "geo": null, "coordinates": null, "place": null, "contributors": null, "is_quote_status": false, "retweet_count": 0, "favorite_count": 2, "favorited": false, "retweeted": false, "possibly_sensitive": false, "possibly_sensitive_appealable": false, "lang": "en" }, "is_quote_status": true, "retweet_count": 0, "favorite_count": 0, "favorited": false, "retweeted": false, "possibly_sensitive": false, "possibly_sensitive_appealable": false, "lang": "en" }