Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- type UserId = Integer
- type Friends = [UserId]
- type URIString = Text
- type UserName = Text
- type StatusId = Integer
- type LanguageCode = String
- data StreamingAPI
- 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
- data SearchResult body = SearchResult {}
- data SearchStatus = SearchStatus {}
- data SearchMetadata = SearchMetadata {
- searchMetadataMaxId :: StatusId
- searchMetadataSinceId :: StatusId
- searchMetadataRefreshURL :: URIString
- searchMetadataNextResults :: Maybe URIString
- searchMetadataCount :: Int
- searchMetadataCompletedIn :: Maybe Float
- searchMetadataSinceIdStr :: String
- searchMetadataQuery :: String
- searchMetadataMaxIdStr :: String
- data RetweetedStatus = RetweetedStatus {
- rsCreatedAt :: UTCTime
- rsId :: StatusId
- rsText :: Text
- rsSource :: Text
- rsTruncated :: Bool
- rsEntities :: Maybe Entities
- rsUser :: User
- rsRetweetedStatus :: Status
- rsCoordinates :: Maybe Coordinates
- data DirectMessage = DirectMessage {
- dmId :: EventId
- dmCreatedTimestamp :: UTCTime
- dmTargetRecipientId :: UserId
- dmSenderId :: UserId
- dmText :: Text
- dmEntities :: Entities
- data EventTarget
- data Event = Event {}
- data Delete = Delete {}
- 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
- data List = List {
- listId :: Int
- listName :: Text
- listFullName :: Text
- listMemberCount :: Int
- listSubscriberCount :: Int
- listMode :: Text
- listUser :: User
- data Entities = Entities {
- enHashTags :: [Entity HashTagEntity]
- enUserMentions :: [Entity UserEntity]
- enURLs :: [Entity URLEntity]
- enMedia :: [Entity MediaEntity]
- type EntityIndices = [Int]
- data ExtendedEntities = ExtendedEntities {
- exeMedia :: [Entity ExtendedEntity]
- data Variant = Variant {}
- data VideoInfo = VideoInfo {
- vsAspectRatio :: [Int]
- vsDurationMillis :: Maybe Int
- vsVariants :: [Variant]
- data ExtendedEntity = ExtendedEntity {}
- data Entity a = Entity {
- entityBody :: a
- entityIndices :: EntityIndices
- data HashTagEntity = HashTagEntity {
- hashTagText :: Text
- data UserEntity = UserEntity {}
- data URLEntity = URLEntity {}
- data MediaEntity = MediaEntity {}
- data MediaSize = MediaSize {}
- data Coordinates = Coordinates {
- coordinates :: [Double]
- coordinatesType :: Text
- data Place = Place {}
- data BoundingBox = BoundingBox {
- boundingBoxCoordinates :: [[[Double]]]
- boundingBoxType :: Text
- data Contributor = Contributor {}
- data UploadedMedia = UploadedMedia {}
- data ImageSizeType = ImageSizeType {}
- data DisplayTextRange = DisplayTextRange {}
- checkError :: Object -> Parser ()
- twitterTimeFormat :: String
Documentation
type LanguageCode = String Source #
data StreamingAPI Source #
SStatus Status | |
SRetweetedStatus RetweetedStatus | |
SEvent Event | |
SDelete Delete | |
SFriends Friends | SScrubGeo ScrubGeo |
SDirectMessage DirectMessage | |
SUnknown Value |
Instances
This type represents a Twitter tweet structure. See https://dev.twitter.com/docs/platform-objects/tweets.
Instances
data SearchResult body Source #
Instances
Eq body => Eq (SearchResult body) Source # | |
Defined in Web.Twitter.Types (==) :: SearchResult body -> SearchResult body -> Bool # (/=) :: SearchResult body -> SearchResult body -> Bool # | |
Data body => Data (SearchResult body) Source # | |
Defined in Web.Twitter.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SearchResult body -> c (SearchResult body) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (SearchResult body) # toConstr :: SearchResult body -> Constr # dataTypeOf :: SearchResult body -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (SearchResult body)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (SearchResult body)) # gmapT :: (forall b. Data b => b -> b) -> SearchResult body -> SearchResult body # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SearchResult body -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SearchResult body -> r # gmapQ :: (forall d. Data d => d -> u) -> SearchResult body -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SearchResult body -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SearchResult body -> m (SearchResult body) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SearchResult body -> m (SearchResult body) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SearchResult body -> m (SearchResult body) # | |
Show body => Show (SearchResult body) Source # | |
Defined in Web.Twitter.Types showsPrec :: Int -> SearchResult body -> ShowS # show :: SearchResult body -> String # showList :: [SearchResult body] -> ShowS # | |
Generic (SearchResult body) Source # | |
Defined in Web.Twitter.Types type Rep (SearchResult body) :: Type -> Type # from :: SearchResult body -> Rep (SearchResult body) x # to :: Rep (SearchResult body) x -> SearchResult body # | |
ToJSON body => ToJSON (SearchResult body) Source # | |
Defined in Web.Twitter.Types toJSON :: SearchResult body -> Value # toEncoding :: SearchResult body -> Encoding # toJSONList :: [SearchResult body] -> Value # toEncodingList :: [SearchResult body] -> Encoding # | |
FromJSON body => FromJSON (SearchResult body) Source # | |
Defined in Web.Twitter.Types parseJSON :: Value -> Parser (SearchResult body) # parseJSONList :: Value -> Parser [SearchResult body] # | |
type Rep (SearchResult body) Source # | |
Defined in Web.Twitter.Types type Rep (SearchResult body) = D1 ('MetaData "SearchResult" "Web.Twitter.Types" "twitter-types-0.11.0-90zWHEClew8EZD9y3vRrZQ" 'False) (C1 ('MetaCons "SearchResult" 'PrefixI 'True) (S1 ('MetaSel ('Just "searchResultStatuses") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 body) :*: S1 ('MetaSel ('Just "searchResultSearchMetadata") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SearchMetadata))) |
data SearchStatus Source #
Instances
data SearchMetadata Source #
Instances
data RetweetedStatus Source #
RetweetedStatus | |
|
Instances
data DirectMessage Source #
DirectMessage | |
|
Instances
data EventTarget Source #
Instances
Event | |
|
Instances
Eq Event Source # | |
Data Event Source # | |
Defined in Web.Twitter.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Event -> c Event # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Event # dataTypeOf :: Event -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Event) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Event) # gmapT :: (forall b. Data b => b -> b) -> Event -> Event # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Event -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Event -> r # gmapQ :: (forall d. Data d => d -> u) -> Event -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Event -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Event -> m Event # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Event -> m Event # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Event -> m Event # | |
Show Event Source # | |
Generic Event Source # | |
ToJSON Event Source # | |
Defined in Web.Twitter.Types | |
FromJSON Event Source # | |
type Rep Event Source # | |
Defined in Web.Twitter.Types type Rep Event = D1 ('MetaData "Event" "Web.Twitter.Types" "twitter-types-0.11.0-90zWHEClew8EZD9y3vRrZQ" 'False) (C1 ('MetaCons "Event" 'PrefixI 'True) ((S1 ('MetaSel ('Just "evCreatedAt") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UTCTime) :*: S1 ('MetaSel ('Just "evTargetObject") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe EventTarget))) :*: (S1 ('MetaSel ('Just "evEvent") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: (S1 ('MetaSel ('Just "evTarget") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 EventTarget) :*: S1 ('MetaSel ('Just "evSource") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 EventTarget))))) |
Instances
Eq Delete Source # | |
Data Delete Source # | |
Defined in Web.Twitter.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Delete -> c Delete # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Delete # toConstr :: Delete -> Constr # dataTypeOf :: Delete -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Delete) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Delete) # gmapT :: (forall b. Data b => b -> b) -> Delete -> Delete # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Delete -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Delete -> r # gmapQ :: (forall d. Data d => d -> u) -> Delete -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Delete -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Delete -> m Delete # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Delete -> m Delete # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Delete -> m Delete # | |
Show Delete Source # | |
Generic Delete Source # | |
ToJSON Delete Source # | |
Defined in Web.Twitter.Types | |
FromJSON Delete Source # | |
type Rep Delete Source # | |
Defined in Web.Twitter.Types type Rep Delete = D1 ('MetaData "Delete" "Web.Twitter.Types" "twitter-types-0.11.0-90zWHEClew8EZD9y3vRrZQ" 'False) (C1 ('MetaCons "Delete" 'PrefixI 'True) (S1 ('MetaSel ('Just "delId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 StatusId) :*: S1 ('MetaSel ('Just "delUserId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UserId))) |
This type represents the Twitter user. See https://dev.twitter.com/docs/platform-objects/users.
Instances
List | |
|
Instances
Eq List Source # | |
Data List Source # | |
Defined in Web.Twitter.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> List -> c List # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c List # dataTypeOf :: List -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c List) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c List) # gmapT :: (forall b. Data b => b -> b) -> List -> List # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> List -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> List -> r # gmapQ :: (forall d. Data d => d -> u) -> List -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> List -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> List -> m List # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> List -> m List # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> List -> m List # | |
Show List Source # | |
Generic List Source # | |
ToJSON List Source # | |
Defined in Web.Twitter.Types | |
FromJSON List Source # | |
type Rep List Source # | |
Defined in Web.Twitter.Types type Rep List = D1 ('MetaData "List" "Web.Twitter.Types" "twitter-types-0.11.0-90zWHEClew8EZD9y3vRrZQ" 'False) (C1 ('MetaCons "List" 'PrefixI 'True) ((S1 ('MetaSel ('Just "listId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: (S1 ('MetaSel ('Just "listName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "listFullName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) :*: ((S1 ('MetaSel ('Just "listMemberCount") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "listSubscriberCount") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :*: (S1 ('MetaSel ('Just "listMode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "listUser") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 User))))) |
Entity handling. See https://dev.twitter.com/docs/platform-objects/entities.
Entities | |
|
Instances
Eq Entities Source # | |
Data Entities Source # | |
Defined in Web.Twitter.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Entities -> c Entities # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Entities # toConstr :: Entities -> Constr # dataTypeOf :: Entities -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Entities) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Entities) # gmapT :: (forall b. Data b => b -> b) -> Entities -> Entities # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Entities -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Entities -> r # gmapQ :: (forall d. Data d => d -> u) -> Entities -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Entities -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Entities -> m Entities # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Entities -> m Entities # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Entities -> m Entities # | |
Show Entities Source # | |
Generic Entities Source # | |
ToJSON Entities Source # | |
Defined in Web.Twitter.Types | |
FromJSON Entities Source # | |
type Rep Entities Source # | |
Defined in Web.Twitter.Types type Rep Entities = D1 ('MetaData "Entities" "Web.Twitter.Types" "twitter-types-0.11.0-90zWHEClew8EZD9y3vRrZQ" 'False) (C1 ('MetaCons "Entities" 'PrefixI 'True) ((S1 ('MetaSel ('Just "enHashTags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Entity HashTagEntity]) :*: S1 ('MetaSel ('Just "enUserMentions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Entity UserEntity])) :*: (S1 ('MetaSel ('Just "enURLs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Entity URLEntity]) :*: S1 ('MetaSel ('Just "enMedia") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Entity MediaEntity])))) |
type EntityIndices = [Int] Source #
The character positions the Entity was extracted from
This is experimental implementation. This may be replaced by more definite types.
data ExtendedEntities Source #
Instances
Instances
Eq Variant Source # | |
Data Variant Source # | |
Defined in Web.Twitter.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Variant -> c Variant # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Variant # toConstr :: Variant -> Constr # dataTypeOf :: Variant -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Variant) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Variant) # gmapT :: (forall b. Data b => b -> b) -> Variant -> Variant # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Variant -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Variant -> r # gmapQ :: (forall d. Data d => d -> u) -> Variant -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Variant -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Variant -> m Variant # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Variant -> m Variant # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Variant -> m Variant # | |
Show Variant Source # | |
Generic Variant Source # | |
ToJSON Variant Source # | |
Defined in Web.Twitter.Types | |
FromJSON Variant Source # | |
type Rep Variant Source # | |
Defined in Web.Twitter.Types type Rep Variant = D1 ('MetaData "Variant" "Web.Twitter.Types" "twitter-types-0.11.0-90zWHEClew8EZD9y3vRrZQ" 'False) (C1 ('MetaCons "Variant" 'PrefixI 'True) (S1 ('MetaSel ('Just "vBitrate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)) :*: (S1 ('MetaSel ('Just "vContentType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "vUrl") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 URIString)))) |
VideoInfo | |
|
Instances
Eq VideoInfo Source # | |
Data VideoInfo Source # | |
Defined in Web.Twitter.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VideoInfo -> c VideoInfo # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VideoInfo # toConstr :: VideoInfo -> Constr # dataTypeOf :: VideoInfo -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c VideoInfo) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VideoInfo) # gmapT :: (forall b. Data b => b -> b) -> VideoInfo -> VideoInfo # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VideoInfo -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VideoInfo -> r # gmapQ :: (forall d. Data d => d -> u) -> VideoInfo -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> VideoInfo -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> VideoInfo -> m VideoInfo # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VideoInfo -> m VideoInfo # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VideoInfo -> m VideoInfo # | |
Show VideoInfo Source # | |
Generic VideoInfo Source # | |
ToJSON VideoInfo Source # | |
Defined in Web.Twitter.Types | |
FromJSON VideoInfo Source # | |
type Rep VideoInfo Source # | |
Defined in Web.Twitter.Types type Rep VideoInfo = D1 ('MetaData "VideoInfo" "Web.Twitter.Types" "twitter-types-0.11.0-90zWHEClew8EZD9y3vRrZQ" 'False) (C1 ('MetaCons "VideoInfo" 'PrefixI 'True) (S1 ('MetaSel ('Just "vsAspectRatio") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Int]) :*: (S1 ('MetaSel ('Just "vsDurationMillis") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)) :*: S1 ('MetaSel ('Just "vsVariants") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Variant])))) |
data ExtendedEntity Source #
Instances
Entity | |
|
Instances
Eq a => Eq (Entity a) Source # | |
Data a => Data (Entity a) Source # | |
Defined in Web.Twitter.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Entity a -> c (Entity a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Entity a) # toConstr :: Entity a -> Constr # dataTypeOf :: Entity a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Entity a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Entity a)) # gmapT :: (forall b. Data b => b -> b) -> Entity a -> Entity a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Entity a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Entity a -> r # gmapQ :: (forall d. Data d => d -> u) -> Entity a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Entity a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Entity a -> m (Entity a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Entity a -> m (Entity a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Entity a -> m (Entity a) # | |
Show a => Show (Entity a) Source # | |
Generic (Entity a) Source # | |
ToJSON a => ToJSON (Entity a) Source # | |
Defined in Web.Twitter.Types | |
FromJSON a => FromJSON (Entity a) Source # | |
Generic1 Entity Source # | |
type Rep (Entity a) Source # | |
Defined in Web.Twitter.Types type Rep (Entity a) = D1 ('MetaData "Entity" "Web.Twitter.Types" "twitter-types-0.11.0-90zWHEClew8EZD9y3vRrZQ" 'False) (C1 ('MetaCons "Entity" 'PrefixI 'True) (S1 ('MetaSel ('Just "entityBody") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "entityIndices") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 EntityIndices))) | |
type Rep1 Entity Source # | |
Defined in Web.Twitter.Types type Rep1 Entity = D1 ('MetaData "Entity" "Web.Twitter.Types" "twitter-types-0.11.0-90zWHEClew8EZD9y3vRrZQ" 'False) (C1 ('MetaCons "Entity" 'PrefixI 'True) (S1 ('MetaSel ('Just "entityBody") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Just "entityIndices") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 EntityIndices))) |
data HashTagEntity Source #
Hashtag entity. See https://dev.twitter.com/docs/platform-objects/entities#obj-hashtags.
HashTagEntity | |
|
Instances
data UserEntity Source #
User mention entity. See https://dev.twitter.com/docs/platform-objects/entities#obj-usermention.
Instances
URL entity. See https://dev.twitter.com/docs/platform-objects/entities#obj-url.
Instances
Eq URLEntity Source # | |
Data URLEntity Source # | |
Defined in Web.Twitter.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> URLEntity -> c URLEntity # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c URLEntity # toConstr :: URLEntity -> Constr # dataTypeOf :: URLEntity -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c URLEntity) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c URLEntity) # gmapT :: (forall b. Data b => b -> b) -> URLEntity -> URLEntity # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> URLEntity -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> URLEntity -> r # gmapQ :: (forall d. Data d => d -> u) -> URLEntity -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> URLEntity -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> URLEntity -> m URLEntity # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> URLEntity -> m URLEntity # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> URLEntity -> m URLEntity # | |
Show URLEntity Source # | |
Generic URLEntity Source # | |
ToJSON URLEntity Source # | |
Defined in Web.Twitter.Types | |
FromJSON URLEntity Source # | |
type Rep URLEntity Source # | |
Defined in Web.Twitter.Types type Rep URLEntity = D1 ('MetaData "URLEntity" "Web.Twitter.Types" "twitter-types-0.11.0-90zWHEClew8EZD9y3vRrZQ" 'False) (C1 ('MetaCons "URLEntity" 'PrefixI 'True) (S1 ('MetaSel ('Just "ueURL") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 URIString) :*: (S1 ('MetaSel ('Just "ueExpanded") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 URIString) :*: S1 ('MetaSel ('Just "ueDisplay") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))) |
data MediaEntity Source #
Instances
Size entity. See https://dev.twitter.com/docs/platform-objects/entities#obj-size.
Instances
Eq MediaSize Source # | |
Data MediaSize Source # | |
Defined in Web.Twitter.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MediaSize -> c MediaSize # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MediaSize # toConstr :: MediaSize -> Constr # dataTypeOf :: MediaSize -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c MediaSize) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MediaSize) # gmapT :: (forall b. Data b => b -> b) -> MediaSize -> MediaSize # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MediaSize -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MediaSize -> r # gmapQ :: (forall d. Data d => d -> u) -> MediaSize -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> MediaSize -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> MediaSize -> m MediaSize # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MediaSize -> m MediaSize # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MediaSize -> m MediaSize # | |
Show MediaSize Source # | |
Generic MediaSize Source # | |
ToJSON MediaSize Source # | |
Defined in Web.Twitter.Types | |
FromJSON MediaSize Source # | |
type Rep MediaSize Source # | |
Defined in Web.Twitter.Types type Rep MediaSize = D1 ('MetaData "MediaSize" "Web.Twitter.Types" "twitter-types-0.11.0-90zWHEClew8EZD9y3vRrZQ" 'False) (C1 ('MetaCons "MediaSize" 'PrefixI 'True) (S1 ('MetaSel ('Just "msWidth") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: (S1 ('MetaSel ('Just "msHeight") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "msResize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))) |
data Coordinates Source #
Coordinates | |
|
Instances
This type represents a place, named locations with corresponding geo coordinates. See https://dev.twitter.com/docs/platform-objects/places.
Place | |
|
Instances
data BoundingBox Source #
A bounding box of coordinates which encloses the place. See https://dev.twitter.com/docs/platform-objects/places#obj-boundingbox.
BoundingBox | |
|
Instances
data Contributor Source #
Instances
data UploadedMedia Source #
This type is represents the API response of "/1.1/media/upload.json". See https://dev.twitter.com/docs/api/multiple-media-extended-entities.
Instances
data ImageSizeType Source #
Image size type. This type is included in the API response of "/1.1/media/upload.json".
Instances
data DisplayTextRange Source #
unicode code point indices, identifying the inclusive start and exclusive end of the displayable content of the Tweet.
DisplayTextRange | |
|
Instances
checkError :: Object -> Parser () Source #