Safe Haskell | None |
---|---|
Language | Haskell2010 |
Web.Twitter.Types.Lens
Contents
- Type classes
Status
SearchResult
SearchStatus
SearchMetadata
RetweetedStatus
DirectMessage
Event
Delete
User
List
Entities
ExtendedEntities
ExtendedEntity
Entity
HashTagEntity
UserEntity
URLEntity
MediaEntity
MediaSize
Coordinates
Place
BoundingBox
Contributor
UploadedMedia
ImageSizeType
- Type aliases and sum types
StreamingAPI
EventTarget
Synopsis
- class AsStatus s where
- class AsUser u where
- class HasCreatedAt a where
- created_at :: Lens' a UTCTime
- class AsImageSize a where
- data Status
- statusContributors :: Lens' Status (Maybe [Contributor])
- statusCoordinates :: Lens' Status (Maybe Coordinates)
- statusCreatedAt :: Lens' Status UTCTime
- statusCurrentUserRetweet :: Lens' Status (Maybe StatusId)
- statusEntities :: Lens' Status (Maybe Entities)
- statusExtendedEntities :: Lens' Status (Maybe ExtendedEntities)
- statusFavoriteCount :: Lens' Status Integer
- statusFavorited :: Lens' Status (Maybe Bool)
- statusFilterLevel :: Lens' Status (Maybe Text)
- statusId :: Lens' Status StatusId
- statusInReplyToScreenName :: Lens' Status (Maybe Text)
- statusInReplyToStatusId :: Lens' Status (Maybe StatusId)
- statusInReplyToUserId :: Lens' Status (Maybe UserId)
- statusLang :: Lens' Status (Maybe LanguageCode)
- statusPlace :: Lens' Status (Maybe Place)
- statusPossiblySensitive :: Lens' Status (Maybe Bool)
- statusScopes :: Lens' Status (Maybe Object)
- statusQuotedStatusId :: Lens' Status (Maybe StatusId)
- statusQuotedStatus :: Lens' Status (Maybe Status)
- statusRetweetCount :: Lens' Status Integer
- statusRetweeted :: Lens' Status (Maybe Bool)
- statusRetweetedStatus :: Lens' Status (Maybe Status)
- statusSource :: Lens' Status Text
- statusText :: Lens' Status Text
- statusTruncated :: Lens' Status Bool
- statusUser :: Lens' Status User
- statusWithheldCopyright :: Lens' Status (Maybe Bool)
- statusWithheldInCountries :: Lens' Status (Maybe [Text])
- statusWithheldScope :: Lens' Status (Maybe Text)
- statusDisplayTextRange :: Lens' Status (Maybe DisplayTextRange)
- data SearchResult body
- searchResultStatuses :: forall body body. Lens (SearchResult body) (SearchResult body) body body
- searchResultSearchMetadata :: forall body. Lens' (SearchResult body) SearchMetadata
- data SearchStatus
- searchStatusCreatedAt :: Lens' SearchStatus UTCTime
- searchStatusId :: Lens' SearchStatus StatusId
- searchStatusText :: Lens' SearchStatus Text
- searchStatusSource :: Lens' SearchStatus Text
- searchStatusUser :: Lens' SearchStatus User
- searchStatusCoordinates :: Lens' SearchStatus (Maybe Coordinates)
- data SearchMetadata
- searchMetadataMaxId :: Lens' SearchMetadata StatusId
- searchMetadataSinceId :: Lens' SearchMetadata StatusId
- searchMetadataRefreshURL :: Lens' SearchMetadata URIString
- searchMetadataNextResults :: Lens' SearchMetadata (Maybe URIString)
- searchMetadataCount :: Lens' SearchMetadata Int
- searchMetadataCompletedIn :: Lens' SearchMetadata (Maybe Float)
- searchMetadataSinceIdStr :: Lens' SearchMetadata String
- searchMetadataQuery :: Lens' SearchMetadata String
- searchMetadataMaxIdStr :: Lens' SearchMetadata String
- data RetweetedStatus
- rsCreatedAt :: Lens' RetweetedStatus UTCTime
- rsId :: Lens' RetweetedStatus StatusId
- rsText :: Lens' RetweetedStatus Text
- rsSource :: Lens' RetweetedStatus Text
- rsTruncated :: Lens' RetweetedStatus Bool
- rsEntities :: Lens' RetweetedStatus (Maybe Entities)
- rsUser :: Lens' RetweetedStatus User
- rsRetweetedStatus :: Lens' RetweetedStatus Status
- rsCoordinates :: Lens' RetweetedStatus (Maybe Coordinates)
- data DirectMessage
- dmId :: Lens' DirectMessage EventId
- dmCreatedTimestamp :: Lens' DirectMessage UTCTime
- dmTargetRecipientId :: Lens' DirectMessage UserId
- dmSenderId :: Lens' DirectMessage UserId
- dmText :: Lens' DirectMessage Text
- dmEntities :: Lens' DirectMessage Entities
- data Event
- evCreatedAt :: Lens' Event UTCTime
- evTargetObject :: Lens' Event (Maybe EventTarget)
- evEvent :: Lens' Event Text
- evTarget :: Lens' Event EventTarget
- evSource :: Lens' Event EventTarget
- data Delete
- delId :: Lens' Delete StatusId
- delUserId :: Lens' Delete UserId
- data User
- userContributorsEnabled :: Lens' User Bool
- userCreatedAt :: Lens' User UTCTime
- userDefaultProfile :: Lens' User Bool
- userDefaultProfileImage :: Lens' User Bool
- userEmail :: Lens' User (Maybe Text)
- userDescription :: Lens' User (Maybe Text)
- userFavoritesCount :: Lens' User Int
- userFollowRequestSent :: Lens' User (Maybe Bool)
- userFollowing :: Lens' User (Maybe Bool)
- userFollowersCount :: Lens' User Int
- userFriendsCount :: Lens' User Int
- userGeoEnabled :: Lens' User Bool
- userId :: Lens' User UserId
- userIsTranslator :: Lens' User Bool
- userLang :: Lens' User (Maybe LanguageCode)
- userListedCount :: Lens' User Int
- userLocation :: Lens' User (Maybe Text)
- userName :: Lens' User Text
- userNotifications :: Lens' User (Maybe Bool)
- userProfileBackgroundColor :: Lens' User (Maybe Text)
- userProfileBackgroundImageURL :: Lens' User (Maybe URIString)
- userProfileBackgroundImageURLHttps :: Lens' User (Maybe URIString)
- userProfileBackgroundTile :: Lens' User (Maybe Bool)
- userProfileBannerURL :: Lens' User (Maybe URIString)
- userProfileImageURL :: Lens' User (Maybe URIString)
- userProfileImageURLHttps :: Lens' User (Maybe URIString)
- userProfileLinkColor :: Lens' User Text
- userProfileSidebarBorderColor :: Lens' User Text
- userProfileSidebarFillColor :: Lens' User Text
- userProfileTextColor :: Lens' User Text
- userProfileUseBackgroundImage :: Lens' User Bool
- userProtected :: Lens' User Bool
- userScreenName :: Lens' User Text
- userShowAllInlineMedia :: Lens' User (Maybe Bool)
- userStatusesCount :: Lens' User Int
- userTimeZone :: Lens' User (Maybe Text)
- userURL :: Lens' User (Maybe URIString)
- userUtcOffset :: Lens' User (Maybe Int)
- userVerified :: Lens' User Bool
- userWithheldInCountries :: Lens' User (Maybe [Text])
- userWithheldScope :: Lens' User (Maybe Text)
- data List
- listId :: Lens' List Int
- listName :: Lens' List Text
- listFullName :: Lens' List Text
- listMemberCount :: Lens' List Int
- listSubscriberCount :: Lens' List Int
- listMode :: Lens' List Text
- listUser :: Lens' List User
- data Entities
- enHashTags :: Lens' Entities [Entity HashTagEntity]
- enUserMentions :: Lens' Entities [Entity UserEntity]
- enURLs :: Lens' Entities [Entity URLEntity]
- enMedia :: Lens' Entities [Entity MediaEntity]
- data ExtendedEntities
- exeMedia :: Iso' ExtendedEntities [Entity ExtendedEntity]
- data ExtendedEntity
- exeID :: Lens' ExtendedEntity StatusId
- exeMediaUrl :: Lens' ExtendedEntity URIString
- exeMediaUrlHttps :: Lens' ExtendedEntity URIString
- exeURL :: Lens' ExtendedEntity URLEntity
- exeSizes :: Lens' ExtendedEntity (HashMap Text MediaSize)
- exeType :: Lens' ExtendedEntity Text
- exeDurationMillis :: Lens' ExtendedEntity (Maybe Double)
- exeExtAltText :: Lens' ExtendedEntity (Maybe String)
- data Entity a
- entityBody :: forall a a. Lens (Entity a) (Entity a) a a
- entityIndices :: forall a. Lens' (Entity a) EntityIndices
- data HashTagEntity
- hashTagText :: Iso' HashTagEntity Text
- data UserEntity
- userEntityUserId :: Lens' UserEntity UserId
- userEntityUserName :: Lens' UserEntity UserName
- userEntityUserScreenName :: Lens' UserEntity Text
- data URLEntity
- ueURL :: Lens' URLEntity URIString
- ueExpanded :: Lens' URLEntity URIString
- ueDisplay :: Lens' URLEntity Text
- data MediaEntity
- meType :: Lens' MediaEntity Text
- meId :: Lens' MediaEntity StatusId
- meSizes :: Lens' MediaEntity (HashMap Text MediaSize)
- meMediaURL :: Lens' MediaEntity URIString
- meMediaURLHttps :: Lens' MediaEntity URIString
- meURL :: Lens' MediaEntity URLEntity
- data MediaSize
- msWidth :: Lens' MediaSize Int
- msHeight :: Lens' MediaSize Int
- msResize :: Lens' MediaSize Text
- data Coordinates
- coordinates :: Lens' Coordinates [Double]
- coordinatesType :: Lens' Coordinates Text
- data Place
- placeAttributes :: Lens' Place (HashMap Text Text)
- placeBoundingBox :: Lens' Place (Maybe BoundingBox)
- placeCountry :: Lens' Place Text
- placeCountryCode :: Lens' Place Text
- placeFullName :: Lens' Place Text
- placeId :: Lens' Place Text
- placeName :: Lens' Place Text
- placeType :: Lens' Place Text
- placeURL :: Lens' Place Text
- data BoundingBox
- boundingBoxCoordinates :: Lens' BoundingBox [[[Double]]]
- boundingBoxType :: Lens' BoundingBox Text
- data Contributor
- contributorId :: Lens' Contributor UserId
- contributorScreenName :: Lens' Contributor (Maybe Text)
- data UploadedMedia
- uploadedMediaId :: Lens' UploadedMedia Integer
- uploadedMediaSize :: Lens' UploadedMedia Integer
- uploadedMediaImage :: Lens' UploadedMedia ImageSizeType
- data ImageSizeType
- imageSizeTypeWidth :: Lens' ImageSizeType Int
- imageSizeTypeHeight :: Lens' ImageSizeType Int
- imageSizeTypeType :: Lens' ImageSizeType Text
- data DisplayTextRange
- displayTextRangeStart :: Lens' DisplayTextRange Int
- displayTextRangeEnd :: Lens' DisplayTextRange Int
- type UserId = Integer
- type Friends = [UserId]
- type URIString = Text
- type UserName = Text
- type StatusId = Integer
- type LanguageCode = String
- data StreamingAPI
- data EventTarget
- type EntityIndices = [Int]
- _SStatus :: Prism' StreamingAPI Status
- _SRetweetedStatus :: Prism' StreamingAPI RetweetedStatus
- _SEvent :: Prism' StreamingAPI Event
- _SDelete :: Prism' StreamingAPI Delete
- _SFriends :: Prism' StreamingAPI Friends
- _SDirectMessage :: Prism' StreamingAPI DirectMessage
- _SUnknown :: Prism' StreamingAPI Value
- _ETUser :: Prism' EventTarget User
- _ETStatus :: Prism' EventTarget Status
- _ETList :: Prism' EventTarget List
- _ETUnknown :: Prism' EventTarget Value
Type classes
class AsStatus s where Source #
Instances
AsStatus Status Source # | |
AsStatus SearchStatus Source # | |
Defined in Web.Twitter.Types.Lens Methods status_id :: Lens' SearchStatus StatusId Source # text :: Lens' SearchStatus Text Source # user :: Lens' SearchStatus User Source # geolocation :: Lens' SearchStatus (Maybe Coordinates) Source # | |
AsStatus RetweetedStatus Source # | |
Defined in Web.Twitter.Types.Lens Methods status_id :: Lens' RetweetedStatus StatusId Source # text :: Lens' RetweetedStatus Text Source # user :: Lens' RetweetedStatus User Source # geolocation :: Lens' RetweetedStatus (Maybe Coordinates) Source # |
Methods
user_id :: Lens' u UserId Source #
name :: Lens' u UserName Source #
screen_name :: Lens' u Text Source #
Instances
AsUser User Source # | |
AsUser UserEntity Source # | |
Defined in Web.Twitter.Types.Lens | |
AsUser (Entity UserEntity) Source # | |
Defined in Web.Twitter.Types.Lens |
class HasCreatedAt a where Source #
Methods
created_at :: Lens' a UTCTime Source #
Instances
HasCreatedAt Status Source # | |
Defined in Web.Twitter.Types.Lens | |
HasCreatedAt SearchStatus Source # | |
Defined in Web.Twitter.Types.Lens Methods | |
HasCreatedAt RetweetedStatus Source # | |
Defined in Web.Twitter.Types.Lens Methods | |
HasCreatedAt DirectMessage Source # | |
Defined in Web.Twitter.Types.Lens Methods | |
HasCreatedAt User Source # | |
Defined in Web.Twitter.Types.Lens |
class AsImageSize a where Source #
Instances
AsImageSize MediaSize Source # | |
AsImageSize ImageSizeType Source # | |
Defined in Web.Twitter.Types.Lens |
Status
This type represents a Twitter tweet structure. See https://dev.twitter.com/docs/platform-objects/tweets.
Instances
statusContributors :: Lens' Status (Maybe [Contributor]) Source #
SearchResult
data SearchResult body #
Instances
Eq body => Eq (SearchResult body) | |
Defined in Web.Twitter.Types Methods (==) :: SearchResult body -> SearchResult body -> Bool # (/=) :: SearchResult body -> SearchResult body -> Bool # | |
Data body => Data (SearchResult body) | |
Defined in Web.Twitter.Types Methods 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 :: (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) | |
Defined in Web.Twitter.Types Methods showsPrec :: Int -> SearchResult body -> ShowS # show :: SearchResult body -> String # showList :: [SearchResult body] -> ShowS # | |
Generic (SearchResult body) | |
Defined in Web.Twitter.Types Associated Types type Rep (SearchResult body) :: Type -> Type # Methods from :: SearchResult body -> Rep (SearchResult body) x # to :: Rep (SearchResult body) x -> SearchResult body # | |
ToJSON body => ToJSON (SearchResult body) | |
Defined in Web.Twitter.Types Methods toJSON :: SearchResult body -> Value # toEncoding :: SearchResult body -> Encoding # toJSONList :: [SearchResult body] -> Value # toEncodingList :: [SearchResult body] -> Encoding # | |
FromJSON body => FromJSON (SearchResult body) | |
Defined in Web.Twitter.Types Methods parseJSON :: Value -> Parser (SearchResult body) # parseJSONList :: Value -> Parser [SearchResult body] # | |
type Rep (SearchResult body) | |
Defined in Web.Twitter.Types type Rep (SearchResult body) = D1 (MetaData "SearchResult" "Web.Twitter.Types" "twitter-types-0.10.0-H2tNb12e7goIbSMtsuemZ5" False) (C1 (MetaCons "SearchResult" PrefixI True) (S1 (MetaSel (Just "searchResultStatuses") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 body) :*: S1 (MetaSel (Just "searchResultSearchMetadata") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SearchMetadata))) |
searchResultStatuses :: forall body body. Lens (SearchResult body) (SearchResult body) body body Source #
searchResultSearchMetadata :: forall body. Lens' (SearchResult body) SearchMetadata Source #
SearchStatus
data SearchStatus #
Instances
SearchMetadata
data SearchMetadata #
Instances
RetweetedStatus
data RetweetedStatus #
Instances
DirectMessage
data DirectMessage #
Instances
dmId :: Lens' DirectMessage EventId Source #
Event
Instances
Eq Event | |
Data Event | |
Defined in Web.Twitter.Types Methods 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 :: (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 | |
Generic Event | |
ToJSON Event | |
Defined in Web.Twitter.Types | |
FromJSON Event | |
type Rep Event | |
Defined in Web.Twitter.Types type Rep Event = D1 (MetaData "Event" "Web.Twitter.Types" "twitter-types-0.10.0-H2tNb12e7goIbSMtsuemZ5" 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))))) |
Delete
Instances
Eq Delete | |
Data Delete | |
Defined in Web.Twitter.Types Methods 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 :: (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 | |
Generic Delete | |
ToJSON Delete | |
Defined in Web.Twitter.Types | |
FromJSON Delete | |
type Rep Delete | |
Defined in Web.Twitter.Types type Rep Delete = D1 (MetaData "Delete" "Web.Twitter.Types" "twitter-types-0.10.0-H2tNb12e7goIbSMtsuemZ5" False) (C1 (MetaCons "Delete" PrefixI True) (S1 (MetaSel (Just "delId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 StatusId) :*: S1 (MetaSel (Just "delUserId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 UserId))) |
User
This type represents the Twitter user. See https://dev.twitter.com/docs/platform-objects/users.
Instances
List
Instances
Eq List | |
Data List | |
Defined in Web.Twitter.Types Methods 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 :: (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 | |
Generic List | |
ToJSON List | |
Defined in Web.Twitter.Types | |
FromJSON List | |
type Rep List | |
Defined in Web.Twitter.Types type Rep List = D1 (MetaData "List" "Web.Twitter.Types" "twitter-types-0.10.0-H2tNb12e7goIbSMtsuemZ5" 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))))) |
Entities
Entity handling. See https://dev.twitter.com/docs/platform-objects/entities.
Instances
Eq Entities | |
Data Entities | |
Defined in Web.Twitter.Types Methods 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 :: (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 | |
Generic Entities | |
ToJSON Entities | |
Defined in Web.Twitter.Types | |
FromJSON Entities | |
type Rep Entities | |
Defined in Web.Twitter.Types type Rep Entities = D1 (MetaData "Entities" "Web.Twitter.Types" "twitter-types-0.10.0-H2tNb12e7goIbSMtsuemZ5" 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])))) |
ExtendedEntities
data ExtendedEntities #
Instances
ExtendedEntity
data ExtendedEntity #
Instances
Entity
Instances
Eq a => Eq (Entity a) | |
Data a => Data (Entity a) | |
Defined in Web.Twitter.Types Methods 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 :: (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) | |
Generic (Entity a) | |
ToJSON a => ToJSON (Entity a) | |
Defined in Web.Twitter.Types | |
FromJSON a => FromJSON (Entity a) | |
AsUser (Entity UserEntity) Source # | |
Defined in Web.Twitter.Types.Lens | |
type Rep (Entity a) | |
Defined in Web.Twitter.Types type Rep (Entity a) = D1 (MetaData "Entity" "Web.Twitter.Types" "twitter-types-0.10.0-H2tNb12e7goIbSMtsuemZ5" False) (C1 (MetaCons "Entity" PrefixI True) (S1 (MetaSel (Just "entityBody") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "entityIndices") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 EntityIndices))) |
entityIndices :: forall a. Lens' (Entity a) EntityIndices Source #
HashTagEntity
data HashTagEntity #
Hashtag entity. See https://dev.twitter.com/docs/platform-objects/entities#obj-hashtags.
Instances
UserEntity
data UserEntity #
User mention entity. See https://dev.twitter.com/docs/platform-objects/entities#obj-usermention.
Instances
URLEntity
URL entity. See https://dev.twitter.com/docs/platform-objects/entities#obj-url.
Instances
Eq URLEntity | |
Data URLEntity | |
Defined in Web.Twitter.Types Methods 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 :: (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 | |
Generic URLEntity | |
ToJSON URLEntity | |
Defined in Web.Twitter.Types | |
FromJSON URLEntity | |
type Rep URLEntity | |
Defined in Web.Twitter.Types type Rep URLEntity = D1 (MetaData "URLEntity" "Web.Twitter.Types" "twitter-types-0.10.0-H2tNb12e7goIbSMtsuemZ5" 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)))) |
MediaEntity
data MediaEntity #
Instances
MediaSize
Size entity. See https://dev.twitter.com/docs/platform-objects/entities#obj-size.
Instances
Eq MediaSize | |
Data MediaSize | |
Defined in Web.Twitter.Types Methods 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 :: (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 | |
Generic MediaSize | |
ToJSON MediaSize | |
Defined in Web.Twitter.Types | |
FromJSON MediaSize | |
AsImageSize MediaSize Source # | |
type Rep MediaSize | |
Defined in Web.Twitter.Types type Rep MediaSize = D1 (MetaData "MediaSize" "Web.Twitter.Types" "twitter-types-0.10.0-H2tNb12e7goIbSMtsuemZ5" 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)))) |
Coordinates
data Coordinates #
Instances
coordinates :: Lens' Coordinates [Double] Source #
Place
This type represents a place, named locations with corresponding geo coordinates. See https://dev.twitter.com/docs/platform-objects/places.
Instances
BoundingBox
data BoundingBox #
A bounding box of coordinates which encloses the place. See https://dev.twitter.com/docs/platform-objects/places#obj-boundingbox.
Instances
Eq BoundingBox | |
Defined in Web.Twitter.Types | |
Data BoundingBox | |
Defined in Web.Twitter.Types Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BoundingBox -> c BoundingBox # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BoundingBox # toConstr :: BoundingBox -> Constr # dataTypeOf :: BoundingBox -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c BoundingBox) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BoundingBox) # gmapT :: (forall b. Data b => b -> b) -> BoundingBox -> BoundingBox # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BoundingBox -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BoundingBox -> r # gmapQ :: (forall d. Data d => d -> u) -> BoundingBox -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> BoundingBox -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> BoundingBox -> m BoundingBox # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BoundingBox -> m BoundingBox # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BoundingBox -> m BoundingBox # | |
Show BoundingBox | |
Defined in Web.Twitter.Types Methods showsPrec :: Int -> BoundingBox -> ShowS # show :: BoundingBox -> String # showList :: [BoundingBox] -> ShowS # | |
Generic BoundingBox | |
Defined in Web.Twitter.Types Associated Types type Rep BoundingBox :: Type -> Type # | |
ToJSON BoundingBox | |
Defined in Web.Twitter.Types Methods toJSON :: BoundingBox -> Value # toEncoding :: BoundingBox -> Encoding # toJSONList :: [BoundingBox] -> Value # toEncodingList :: [BoundingBox] -> Encoding # | |
FromJSON BoundingBox | |
Defined in Web.Twitter.Types | |
type Rep BoundingBox | |
Defined in Web.Twitter.Types type Rep BoundingBox = D1 (MetaData "BoundingBox" "Web.Twitter.Types" "twitter-types-0.10.0-H2tNb12e7goIbSMtsuemZ5" False) (C1 (MetaCons "BoundingBox" PrefixI True) (S1 (MetaSel (Just "boundingBoxCoordinates") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [[[Double]]]) :*: S1 (MetaSel (Just "boundingBoxType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text))) |
boundingBoxCoordinates :: Lens' BoundingBox [[[Double]]] Source #
Contributor
data Contributor #
Instances
UploadedMedia
data UploadedMedia #
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
ImageSizeType
data ImageSizeType #
Image size type. This type is included in the API response of "/1.1/media/upload.json".
Instances
data DisplayTextRange #
unicode code point indices, identifying the inclusive start and exclusive end of the displayable content of the Tweet.
Instances
Type aliases and sum types
type LanguageCode = String #
data StreamingAPI #
Constructors
SStatus Status | |
SRetweetedStatus RetweetedStatus | |
SEvent Event | |
SDelete Delete | |
SFriends Friends | SScrubGeo ScrubGeo |
SDirectMessage DirectMessage | |
SUnknown Value |
Instances
data EventTarget #
Instances
type EntityIndices = [Int] #
The character positions the Entity was extracted from
This is experimental implementation. This may be replaced by more definite types.