Safe Haskell | None |
---|---|
Language | Haskell2010 |
- 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 Entities)
- 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)
- 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 :: *
- dmCreatedAt :: Lens' DirectMessage UTCTime
- dmSenderScreenName :: Lens' DirectMessage Text
- dmSender :: Lens' DirectMessage User
- dmText :: Lens' DirectMessage Text
- dmRecipientScreeName :: Lens' DirectMessage Text
- dmId :: Lens' DirectMessage StatusId
- dmRecipient :: Lens' DirectMessage User
- dmRecipientId :: Lens' DirectMessage UserId
- dmSenderId :: Lens' DirectMessage UserId
- dmCoordinates :: Lens' DirectMessage (Maybe Coordinates)
- 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
- 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 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 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
- 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
status_id :: Lens' s StatusId Source
geolocation :: Lens' s (Maybe Coordinates) Source
class HasCreatedAt a where Source
created_at :: Lens' a UTCTime Source
class AsImageSize a where Source
Status
data Status :: *
This type represents a Twitter tweet structure. See https://dev.twitter.com/docs/platform-objects/tweets.
Eq Status | |
Data Status | |
Show Status | |
Generic Status | |
ToJSON Status | |
FromJSON Status | |
HasCreatedAt Status Source | |
AsStatus Status Source | |
type Rep Status = D1 D1Status (C1 C1_0Status ((:*:) ((:*:) ((:*:) ((:*:) (S1 S1_0_0Status (Rec0 (Maybe [Contributor]))) ((:*:) (S1 S1_0_1Status (Rec0 (Maybe Coordinates))) (S1 S1_0_2Status (Rec0 UTCTime)))) ((:*:) ((:*:) (S1 S1_0_3Status (Rec0 (Maybe StatusId))) (S1 S1_0_4Status (Rec0 (Maybe Entities)))) ((:*:) (S1 S1_0_5Status (Rec0 (Maybe Entities))) (S1 S1_0_6Status (Rec0 Integer))))) ((:*:) ((:*:) (S1 S1_0_7Status (Rec0 (Maybe Bool))) ((:*:) (S1 S1_0_8Status (Rec0 (Maybe Text))) (S1 S1_0_9Status (Rec0 StatusId)))) ((:*:) ((:*:) (S1 S1_0_10Status (Rec0 (Maybe Text))) (S1 S1_0_11Status (Rec0 (Maybe StatusId)))) ((:*:) (S1 S1_0_12Status (Rec0 (Maybe UserId))) (S1 S1_0_13Status (Rec0 (Maybe LanguageCode))))))) ((:*:) ((:*:) ((:*:) (S1 S1_0_14Status (Rec0 (Maybe Place))) ((:*:) (S1 S1_0_15Status (Rec0 (Maybe Bool))) (S1 S1_0_16Status (Rec0 (Maybe Object))))) ((:*:) ((:*:) (S1 S1_0_17Status (Rec0 (Maybe StatusId))) (S1 S1_0_18Status (Rec0 (Maybe Status)))) ((:*:) (S1 S1_0_19Status (Rec0 Integer)) (S1 S1_0_20Status (Rec0 (Maybe Bool)))))) ((:*:) ((:*:) ((:*:) (S1 S1_0_21Status (Rec0 (Maybe Status))) (S1 S1_0_22Status (Rec0 Text))) ((:*:) (S1 S1_0_23Status (Rec0 Text)) (S1 S1_0_24Status (Rec0 Bool)))) ((:*:) ((:*:) (S1 S1_0_25Status (Rec0 User)) (S1 S1_0_26Status (Rec0 (Maybe Bool)))) ((:*:) (S1 S1_0_27Status (Rec0 (Maybe [Text]))) (S1 S1_0_28Status (Rec0 (Maybe Text))))))))) |
SearchResult
data SearchResult body :: * -> *
Eq body => Eq (SearchResult body) | |
Data body => Data (SearchResult body) | |
Show body => Show (SearchResult body) | |
Generic (SearchResult body) | |
ToJSON body => ToJSON (SearchResult body) | |
FromJSON body => FromJSON (SearchResult body) | |
type Rep (SearchResult body) = D1 D1SearchResult (C1 C1_0SearchResult ((:*:) (S1 S1_0_0SearchResult (Rec0 body)) (S1 S1_0_1SearchResult (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 :: *
Eq SearchStatus | |
Data SearchStatus | |
Show SearchStatus | |
Generic SearchStatus | |
ToJSON SearchStatus | |
FromJSON SearchStatus | |
HasCreatedAt SearchStatus Source | |
AsStatus SearchStatus Source | |
type Rep SearchStatus = D1 D1SearchStatus (C1 C1_0SearchStatus ((:*:) ((:*:) (S1 S1_0_0SearchStatus (Rec0 UTCTime)) ((:*:) (S1 S1_0_1SearchStatus (Rec0 StatusId)) (S1 S1_0_2SearchStatus (Rec0 Text)))) ((:*:) (S1 S1_0_3SearchStatus (Rec0 Text)) ((:*:) (S1 S1_0_4SearchStatus (Rec0 User)) (S1 S1_0_5SearchStatus (Rec0 (Maybe Coordinates))))))) |
SearchMetadata
data SearchMetadata :: *
Eq SearchMetadata | |
Data SearchMetadata | |
Show SearchMetadata | |
Generic SearchMetadata | |
ToJSON SearchMetadata | |
FromJSON SearchMetadata | |
type Rep SearchMetadata = D1 D1SearchMetadata (C1 C1_0SearchMetadata ((:*:) ((:*:) ((:*:) (S1 S1_0_0SearchMetadata (Rec0 StatusId)) (S1 S1_0_1SearchMetadata (Rec0 StatusId))) ((:*:) (S1 S1_0_2SearchMetadata (Rec0 URIString)) (S1 S1_0_3SearchMetadata (Rec0 (Maybe URIString))))) ((:*:) ((:*:) (S1 S1_0_4SearchMetadata (Rec0 Int)) (S1 S1_0_5SearchMetadata (Rec0 (Maybe Float)))) ((:*:) (S1 S1_0_6SearchMetadata (Rec0 String)) ((:*:) (S1 S1_0_7SearchMetadata (Rec0 String)) (S1 S1_0_8SearchMetadata (Rec0 String))))))) |
RetweetedStatus
data RetweetedStatus :: *
Eq RetweetedStatus | |
Data RetweetedStatus | |
Show RetweetedStatus | |
Generic RetweetedStatus | |
ToJSON RetweetedStatus | |
FromJSON RetweetedStatus | |
HasCreatedAt RetweetedStatus Source | |
AsStatus RetweetedStatus Source | |
type Rep RetweetedStatus = D1 D1RetweetedStatus (C1 C1_0RetweetedStatus ((:*:) ((:*:) ((:*:) (S1 S1_0_0RetweetedStatus (Rec0 UTCTime)) (S1 S1_0_1RetweetedStatus (Rec0 StatusId))) ((:*:) (S1 S1_0_2RetweetedStatus (Rec0 Text)) (S1 S1_0_3RetweetedStatus (Rec0 Text)))) ((:*:) ((:*:) (S1 S1_0_4RetweetedStatus (Rec0 Bool)) (S1 S1_0_5RetweetedStatus (Rec0 (Maybe Entities)))) ((:*:) (S1 S1_0_6RetweetedStatus (Rec0 User)) ((:*:) (S1 S1_0_7RetweetedStatus (Rec0 Status)) (S1 S1_0_8RetweetedStatus (Rec0 (Maybe Coordinates)))))))) |
DirectMessage
data DirectMessage :: *
Eq DirectMessage | |
Data DirectMessage | |
Show DirectMessage | |
Generic DirectMessage | |
ToJSON DirectMessage | |
FromJSON DirectMessage | |
HasCreatedAt DirectMessage Source | |
AsStatus DirectMessage Source | |
type Rep DirectMessage = D1 D1DirectMessage (C1 C1_0DirectMessage ((:*:) ((:*:) ((:*:) (S1 S1_0_0DirectMessage (Rec0 UTCTime)) (S1 S1_0_1DirectMessage (Rec0 Text))) ((:*:) (S1 S1_0_2DirectMessage (Rec0 User)) ((:*:) (S1 S1_0_3DirectMessage (Rec0 Text)) (S1 S1_0_4DirectMessage (Rec0 Text))))) ((:*:) ((:*:) (S1 S1_0_5DirectMessage (Rec0 StatusId)) (S1 S1_0_6DirectMessage (Rec0 User))) ((:*:) (S1 S1_0_7DirectMessage (Rec0 UserId)) ((:*:) (S1 S1_0_8DirectMessage (Rec0 UserId)) (S1 S1_0_9DirectMessage (Rec0 (Maybe Coordinates)))))))) |
Event
data Event :: *
Eq Event | |
Data Event | |
Show Event | |
Generic Event | |
ToJSON Event | |
FromJSON Event | |
type Rep Event = D1 D1Event (C1 C1_0Event ((:*:) ((:*:) (S1 S1_0_0Event (Rec0 UTCTime)) (S1 S1_0_1Event (Rec0 (Maybe EventTarget)))) ((:*:) (S1 S1_0_2Event (Rec0 Text)) ((:*:) (S1 S1_0_3Event (Rec0 EventTarget)) (S1 S1_0_4Event (Rec0 EventTarget)))))) |
Delete
data Delete :: *
User
data User :: *
This type represents the Twitter user. See https://dev.twitter.com/docs/platform-objects/users.
Eq User | |
Data User | |
Show User | |
Generic User | |
ToJSON User | |
FromJSON User | |
HasCreatedAt User Source | |
AsUser User Source | |
type Rep User = D1 D1User (C1 C1_0User ((:*:) ((:*:) ((:*:) ((:*:) ((:*:) (S1 S1_0_0User (Rec0 Bool)) (S1 S1_0_1User (Rec0 UTCTime))) ((:*:) (S1 S1_0_2User (Rec0 Bool)) ((:*:) (S1 S1_0_3User (Rec0 Bool)) (S1 S1_0_4User (Rec0 (Maybe Text)))))) ((:*:) ((:*:) (S1 S1_0_5User (Rec0 Int)) (S1 S1_0_6User (Rec0 (Maybe Bool)))) ((:*:) (S1 S1_0_7User (Rec0 (Maybe Bool))) ((:*:) (S1 S1_0_8User (Rec0 Int)) (S1 S1_0_9User (Rec0 Int)))))) ((:*:) ((:*:) ((:*:) (S1 S1_0_10User (Rec0 Bool)) (S1 S1_0_11User (Rec0 UserId))) ((:*:) (S1 S1_0_12User (Rec0 Bool)) ((:*:) (S1 S1_0_13User (Rec0 LanguageCode)) (S1 S1_0_14User (Rec0 Int))))) ((:*:) ((:*:) (S1 S1_0_15User (Rec0 (Maybe Text))) (S1 S1_0_16User (Rec0 Text))) ((:*:) (S1 S1_0_17User (Rec0 (Maybe Bool))) ((:*:) (S1 S1_0_18User (Rec0 (Maybe Text))) (S1 S1_0_19User (Rec0 (Maybe URIString)))))))) ((:*:) ((:*:) ((:*:) ((:*:) (S1 S1_0_20User (Rec0 (Maybe URIString))) (S1 S1_0_21User (Rec0 (Maybe Bool)))) ((:*:) (S1 S1_0_22User (Rec0 (Maybe URIString))) ((:*:) (S1 S1_0_23User (Rec0 (Maybe URIString))) (S1 S1_0_24User (Rec0 (Maybe URIString)))))) ((:*:) ((:*:) (S1 S1_0_25User (Rec0 Text)) (S1 S1_0_26User (Rec0 Text))) ((:*:) (S1 S1_0_27User (Rec0 Text)) ((:*:) (S1 S1_0_28User (Rec0 Text)) (S1 S1_0_29User (Rec0 Bool)))))) ((:*:) ((:*:) ((:*:) (S1 S1_0_30User (Rec0 Bool)) (S1 S1_0_31User (Rec0 Text))) ((:*:) (S1 S1_0_32User (Rec0 (Maybe Bool))) ((:*:) (S1 S1_0_33User (Rec0 Int)) (S1 S1_0_34User (Rec0 (Maybe Text)))))) ((:*:) ((:*:) (S1 S1_0_35User (Rec0 (Maybe URIString))) (S1 S1_0_36User (Rec0 (Maybe Int)))) ((:*:) (S1 S1_0_37User (Rec0 Bool)) ((:*:) (S1 S1_0_38User (Rec0 (Maybe [Text]))) (S1 S1_0_39User (Rec0 (Maybe Text)))))))))) |
List
data List :: *
Eq List | |
Data List | |
Show List | |
Generic List | |
ToJSON List | |
FromJSON List | |
type Rep List = D1 D1List (C1 C1_0List ((:*:) ((:*:) (S1 S1_0_0List (Rec0 Int)) ((:*:) (S1 S1_0_1List (Rec0 Text)) (S1 S1_0_2List (Rec0 Text)))) ((:*:) ((:*:) (S1 S1_0_3List (Rec0 Int)) (S1 S1_0_4List (Rec0 Int))) ((:*:) (S1 S1_0_5List (Rec0 Text)) (S1 S1_0_6List (Rec0 User)))))) |
Entities
data Entities :: *
Entity handling. See https://dev.twitter.com/docs/platform-objects/entities.
Eq Entities | |
Data Entities | |
Show Entities | |
Generic Entities | |
ToJSON Entities | |
FromJSON Entities | |
type Rep Entities = D1 D1Entities (C1 C1_0Entities ((:*:) ((:*:) (S1 S1_0_0Entities (Rec0 [Entity HashTagEntity])) (S1 S1_0_1Entities (Rec0 [Entity UserEntity]))) ((:*:) (S1 S1_0_2Entities (Rec0 [Entity URLEntity])) (S1 S1_0_3Entities (Rec0 [Entity MediaEntity]))))) |
Entity
data Entity a :: * -> *
Eq a => Eq (Entity a) | |
Data a => Data (Entity a) | |
Show a => Show (Entity a) | |
Generic (Entity a) | |
ToJSON a => ToJSON (Entity a) | |
FromJSON a => FromJSON (Entity a) | |
AsUser (Entity UserEntity) Source | |
type Rep (Entity a) = D1 D1Entity (C1 C1_0Entity ((:*:) (S1 S1_0_0Entity (Rec0 a)) (S1 S1_0_1Entity (Rec0 EntityIndices)))) |
entityBody :: forall a a. Lens (Entity a) (Entity a) a a Source
entityIndices :: forall a. Lens' (Entity a) EntityIndices Source
HashTagEntity
data HashTagEntity :: *
Hashtag entity. See https://dev.twitter.com/docs/platform-objects/entities#obj-hashtags.
Eq HashTagEntity | |
Data HashTagEntity | |
Show HashTagEntity | |
Generic HashTagEntity | |
ToJSON HashTagEntity | |
FromJSON HashTagEntity | |
type Rep HashTagEntity = D1 D1HashTagEntity (C1 C1_0HashTagEntity (S1 S1_0_0HashTagEntity (Rec0 Text))) |
UserEntity
data UserEntity :: *
User mention entity. See https://dev.twitter.com/docs/platform-objects/entities#obj-usermention.
Eq UserEntity | |
Data UserEntity | |
Show UserEntity | |
Generic UserEntity | |
ToJSON UserEntity | |
FromJSON UserEntity | |
AsUser UserEntity Source | |
AsUser (Entity UserEntity) Source | |
type Rep UserEntity = D1 D1UserEntity (C1 C1_0UserEntity ((:*:) (S1 S1_0_0UserEntity (Rec0 UserId)) ((:*:) (S1 S1_0_1UserEntity (Rec0 UserName)) (S1 S1_0_2UserEntity (Rec0 Text))))) |
URLEntity
data URLEntity :: *
URL entity. See https://dev.twitter.com/docs/platform-objects/entities#obj-url.
MediaEntity
data MediaEntity :: *
Eq MediaEntity | |
Data MediaEntity | |
Show MediaEntity | |
Generic MediaEntity | |
ToJSON MediaEntity | |
FromJSON MediaEntity | |
type Rep MediaEntity = D1 D1MediaEntity (C1 C1_0MediaEntity ((:*:) ((:*:) (S1 S1_0_0MediaEntity (Rec0 Text)) ((:*:) (S1 S1_0_1MediaEntity (Rec0 StatusId)) (S1 S1_0_2MediaEntity (Rec0 (HashMap Text MediaSize))))) ((:*:) (S1 S1_0_3MediaEntity (Rec0 URIString)) ((:*:) (S1 S1_0_4MediaEntity (Rec0 URIString)) (S1 S1_0_5MediaEntity (Rec0 URLEntity)))))) |
MediaSize
data MediaSize :: *
Size entity. See https://dev.twitter.com/docs/platform-objects/entities#obj-size.
Coordinates
data Coordinates :: *
Eq Coordinates | |
Data Coordinates | |
Show Coordinates | |
Generic Coordinates | |
ToJSON Coordinates | |
FromJSON Coordinates | |
type Rep Coordinates = D1 D1Coordinates (C1 C1_0Coordinates ((:*:) (S1 S1_0_0Coordinates (Rec0 [Double])) (S1 S1_0_1Coordinates (Rec0 Text)))) |
Place
data Place :: *
This type represents a place, named locations with corresponding geo coordinates. See https://dev.twitter.com/docs/platform-objects/places.
Eq Place | |
Data Place | |
Show Place | |
Generic Place | |
ToJSON Place | |
FromJSON Place | |
type Rep Place = D1 D1Place (C1 C1_0Place ((:*:) ((:*:) ((:*:) (S1 S1_0_0Place (Rec0 (HashMap Text Text))) (S1 S1_0_1Place (Rec0 (Maybe BoundingBox)))) ((:*:) (S1 S1_0_2Place (Rec0 Text)) (S1 S1_0_3Place (Rec0 Text)))) ((:*:) ((:*:) (S1 S1_0_4Place (Rec0 Text)) (S1 S1_0_5Place (Rec0 Text))) ((:*:) (S1 S1_0_6Place (Rec0 Text)) ((:*:) (S1 S1_0_7Place (Rec0 Text)) (S1 S1_0_8Place (Rec0 Text))))))) |
BoundingBox
data BoundingBox :: *
A bounding box of coordinates which encloses the place. See https://dev.twitter.com/docs/platform-objects/places#obj-boundingbox.
Eq BoundingBox | |
Data BoundingBox | |
Show BoundingBox | |
Generic BoundingBox | |
ToJSON BoundingBox | |
FromJSON BoundingBox | |
type Rep BoundingBox = D1 D1BoundingBox (C1 C1_0BoundingBox ((:*:) (S1 S1_0_0BoundingBox (Rec0 [[[Double]]])) (S1 S1_0_1BoundingBox (Rec0 Text)))) |
boundingBoxCoordinates :: Lens' BoundingBox [[[Double]]] Source
Contributor
data Contributor :: *
Eq Contributor | |
Data Contributor | |
Show Contributor | |
Generic Contributor | |
ToJSON Contributor | |
FromJSON Contributor | |
type Rep Contributor = D1 D1Contributor (C1 C1_0Contributor ((:*:) (S1 S1_0_0Contributor (Rec0 UserId)) (S1 S1_0_1Contributor (Rec0 (Maybe Text))))) |
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.
Eq UploadedMedia | |
Data UploadedMedia | |
Show UploadedMedia | |
Generic UploadedMedia | |
ToJSON UploadedMedia | |
FromJSON UploadedMedia | |
type Rep UploadedMedia = D1 D1UploadedMedia (C1 C1_0UploadedMedia ((:*:) (S1 S1_0_0UploadedMedia (Rec0 Integer)) ((:*:) (S1 S1_0_1UploadedMedia (Rec0 Integer)) (S1 S1_0_2UploadedMedia (Rec0 ImageSizeType))))) |
ImageSizeType
data ImageSizeType :: *
Image size type. This type is included in the API response of "/1.1/media/upload.json".
Eq ImageSizeType | |
Data ImageSizeType | |
Show ImageSizeType | |
Generic ImageSizeType | |
ToJSON ImageSizeType | |
FromJSON ImageSizeType | |
AsImageSize ImageSizeType Source | |
type Rep ImageSizeType = D1 D1ImageSizeType (C1 C1_0ImageSizeType ((:*:) (S1 S1_0_0ImageSizeType (Rec0 Int)) ((:*:) (S1 S1_0_1ImageSizeType (Rec0 Int)) (S1 S1_0_2ImageSizeType (Rec0 Text))))) |
Type aliases and sum types
type LanguageCode = String
data StreamingAPI :: *
SStatus Status | |
SRetweetedStatus RetweetedStatus | |
SEvent Event | |
SDelete Delete | |
SFriends Friends | SScrubGeo ScrubGeo |
SDirectMessage DirectMessage | |
SUnknown Value |
Eq StreamingAPI | |
Data StreamingAPI | |
Show StreamingAPI | |
Generic StreamingAPI | |
ToJSON StreamingAPI | |
FromJSON StreamingAPI | |
type Rep StreamingAPI = D1 D1StreamingAPI ((:+:) ((:+:) (C1 C1_0StreamingAPI (S1 NoSelector (Rec0 Status))) ((:+:) (C1 C1_1StreamingAPI (S1 NoSelector (Rec0 RetweetedStatus))) (C1 C1_2StreamingAPI (S1 NoSelector (Rec0 Event))))) ((:+:) ((:+:) (C1 C1_3StreamingAPI (S1 NoSelector (Rec0 Delete))) (C1 C1_4StreamingAPI (S1 NoSelector (Rec0 Friends)))) ((:+:) (C1 C1_5StreamingAPI (S1 NoSelector (Rec0 DirectMessage))) (C1 C1_6StreamingAPI (S1 NoSelector (Rec0 Value)))))) |
data EventTarget :: *
Eq EventTarget | |
Data EventTarget | |
Show EventTarget | |
Generic EventTarget | |
ToJSON EventTarget | |
FromJSON EventTarget | |
type Rep EventTarget = D1 D1EventTarget ((:+:) ((:+:) (C1 C1_0EventTarget (S1 NoSelector (Rec0 User))) (C1 C1_1EventTarget (S1 NoSelector (Rec0 Status)))) ((:+:) (C1 C1_2EventTarget (S1 NoSelector (Rec0 List))) (C1 C1_3EventTarget (S1 NoSelector (Rec0 Value))))) |
type EntityIndices = [Int]
The character positions the Entity was extracted from
This is experimental implementation. This may be replaced by more definite types.