twitter-types-0.7.2.2: Twitter JSON parser and types

Safe HaskellNone
LanguageHaskell98

Web.Twitter.Types

Synopsis

Documentation

data StreamingAPI Source #

Instances

Eq StreamingAPI Source # 
Data StreamingAPI Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StreamingAPI -> c StreamingAPI #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c StreamingAPI #

toConstr :: StreamingAPI -> Constr #

dataTypeOf :: StreamingAPI -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c StreamingAPI) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c StreamingAPI) #

gmapT :: (forall b. Data b => b -> b) -> StreamingAPI -> StreamingAPI #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StreamingAPI -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StreamingAPI -> r #

gmapQ :: (forall d. Data d => d -> u) -> StreamingAPI -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StreamingAPI -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StreamingAPI -> m StreamingAPI #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StreamingAPI -> m StreamingAPI #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StreamingAPI -> m StreamingAPI #

Show StreamingAPI Source # 
Generic StreamingAPI Source # 

Associated Types

type Rep StreamingAPI :: * -> * #

ToJSON StreamingAPI Source # 
FromJSON StreamingAPI Source # 
type Rep StreamingAPI Source # 

data Status Source #

This type represents a Twitter tweet structure. See https://dev.twitter.com/docs/platform-objects/tweets.

Instances

Eq Status Source # 

Methods

(==) :: Status -> Status -> Bool #

(/=) :: Status -> Status -> Bool #

Data Status Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Status -> c Status #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Status #

toConstr :: Status -> Constr #

dataTypeOf :: Status -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Status) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Status) #

gmapT :: (forall b. Data b => b -> b) -> Status -> Status #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Status -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Status -> r #

gmapQ :: (forall d. Data d => d -> u) -> Status -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Status -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Status -> m Status #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Status -> m Status #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Status -> m Status #

Show Status Source # 
Generic Status Source # 

Associated Types

type Rep Status :: * -> * #

Methods

from :: Status -> Rep Status x #

to :: Rep Status x -> Status #

ToJSON Status Source # 
FromJSON Status Source # 
type Rep Status Source # 
type Rep Status = D1 (MetaData "Status" "Web.Twitter.Types" "twitter-types-0.7.2.2-LaMHofqEINq80FbVZtr9dc" False) (C1 (MetaCons "Status" PrefixI True) ((:*:) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "statusContributors") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe [Contributor]))) ((:*:) (S1 (MetaSel (Just Symbol "statusCoordinates") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Coordinates))) (S1 (MetaSel (Just Symbol "statusCreatedAt") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 UTCTime)))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "statusCurrentUserRetweet") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe StatusId))) (S1 (MetaSel (Just Symbol "statusEntities") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Entities)))) ((:*:) (S1 (MetaSel (Just Symbol "statusExtendedEntities") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Entities))) (S1 (MetaSel (Just Symbol "statusFavoriteCount") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Integer))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "statusFavorited") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Bool))) ((:*:) (S1 (MetaSel (Just Symbol "statusFilterLevel") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "statusId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 StatusId)))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "statusInReplyToScreenName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "statusInReplyToStatusId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe StatusId)))) ((:*:) (S1 (MetaSel (Just Symbol "statusInReplyToUserId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe UserId))) (S1 (MetaSel (Just Symbol "statusLang") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe LanguageCode))))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "statusPlace") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Place))) ((:*:) (S1 (MetaSel (Just Symbol "statusPossiblySensitive") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "statusScopes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Object))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "statusQuotedStatusId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe StatusId))) (S1 (MetaSel (Just Symbol "statusQuotedStatus") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Status)))) ((:*:) (S1 (MetaSel (Just Symbol "statusRetweetCount") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Integer)) (S1 (MetaSel (Just Symbol "statusRetweeted") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Bool)))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "statusRetweetedStatus") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Status))) (S1 (MetaSel (Just Symbol "statusSource") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text))) ((:*:) (S1 (MetaSel (Just Symbol "statusText") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) (S1 (MetaSel (Just Symbol "statusTruncated") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "statusUser") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 User)) (S1 (MetaSel (Just Symbol "statusWithheldCopyright") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Bool)))) ((:*:) (S1 (MetaSel (Just Symbol "statusWithheldInCountries") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe [Text]))) (S1 (MetaSel (Just Symbol "statusWithheldScope") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text)))))))))

data SearchResult body Source #

Instances

Eq body => Eq (SearchResult body) Source # 

Methods

(==) :: SearchResult body -> SearchResult body -> Bool #

(/=) :: SearchResult body -> SearchResult body -> Bool #

Data body => Data (SearchResult body) Source # 

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) Source # 

Methods

showsPrec :: Int -> SearchResult body -> ShowS #

show :: SearchResult body -> String #

showList :: [SearchResult body] -> ShowS #

Generic (SearchResult body) Source # 

Associated Types

type Rep (SearchResult body) :: * -> * #

Methods

from :: SearchResult body -> Rep (SearchResult body) x #

to :: Rep (SearchResult body) x -> SearchResult body #

ToJSON body => ToJSON (SearchResult body) Source # 
FromJSON body => FromJSON (SearchResult body) Source # 

Methods

parseJSON :: Value -> Parser (SearchResult body) #

type Rep (SearchResult body) Source # 
type Rep (SearchResult body) = D1 (MetaData "SearchResult" "Web.Twitter.Types" "twitter-types-0.7.2.2-LaMHofqEINq80FbVZtr9dc" False) (C1 (MetaCons "SearchResult" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "searchResultStatuses") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 body)) (S1 (MetaSel (Just Symbol "searchResultSearchMetadata") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SearchMetadata))))

data SearchStatus Source #

Instances

Eq SearchStatus Source # 
Data SearchStatus Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SearchStatus -> c SearchStatus #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SearchStatus #

toConstr :: SearchStatus -> Constr #

dataTypeOf :: SearchStatus -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SearchStatus) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SearchStatus) #

gmapT :: (forall b. Data b => b -> b) -> SearchStatus -> SearchStatus #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SearchStatus -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SearchStatus -> r #

gmapQ :: (forall d. Data d => d -> u) -> SearchStatus -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SearchStatus -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SearchStatus -> m SearchStatus #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SearchStatus -> m SearchStatus #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SearchStatus -> m SearchStatus #

Show SearchStatus Source # 
Generic SearchStatus Source # 

Associated Types

type Rep SearchStatus :: * -> * #

ToJSON SearchStatus Source # 
FromJSON SearchStatus Source # 
type Rep SearchStatus Source # 

data SearchMetadata Source #

Instances

Eq SearchMetadata Source # 
Data SearchMetadata Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SearchMetadata -> c SearchMetadata #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SearchMetadata #

toConstr :: SearchMetadata -> Constr #

dataTypeOf :: SearchMetadata -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SearchMetadata) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SearchMetadata) #

gmapT :: (forall b. Data b => b -> b) -> SearchMetadata -> SearchMetadata #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SearchMetadata -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SearchMetadata -> r #

gmapQ :: (forall d. Data d => d -> u) -> SearchMetadata -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SearchMetadata -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SearchMetadata -> m SearchMetadata #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SearchMetadata -> m SearchMetadata #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SearchMetadata -> m SearchMetadata #

Show SearchMetadata Source # 
Generic SearchMetadata Source # 

Associated Types

type Rep SearchMetadata :: * -> * #

ToJSON SearchMetadata Source # 
FromJSON SearchMetadata Source # 
type Rep SearchMetadata Source # 

data RetweetedStatus Source #

Instances

Eq RetweetedStatus Source # 
Data RetweetedStatus Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RetweetedStatus -> c RetweetedStatus #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RetweetedStatus #

toConstr :: RetweetedStatus -> Constr #

dataTypeOf :: RetweetedStatus -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c RetweetedStatus) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RetweetedStatus) #

gmapT :: (forall b. Data b => b -> b) -> RetweetedStatus -> RetweetedStatus #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RetweetedStatus -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RetweetedStatus -> r #

gmapQ :: (forall d. Data d => d -> u) -> RetweetedStatus -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RetweetedStatus -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RetweetedStatus -> m RetweetedStatus #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RetweetedStatus -> m RetweetedStatus #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RetweetedStatus -> m RetweetedStatus #

Show RetweetedStatus Source # 
Generic RetweetedStatus Source # 
ToJSON RetweetedStatus Source # 
FromJSON RetweetedStatus Source # 
type Rep RetweetedStatus Source # 

data DirectMessage Source #

Instances

Eq DirectMessage Source # 
Data DirectMessage Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DirectMessage -> c DirectMessage #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DirectMessage #

toConstr :: DirectMessage -> Constr #

dataTypeOf :: DirectMessage -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c DirectMessage) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DirectMessage) #

gmapT :: (forall b. Data b => b -> b) -> DirectMessage -> DirectMessage #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DirectMessage -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DirectMessage -> r #

gmapQ :: (forall d. Data d => d -> u) -> DirectMessage -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DirectMessage -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DirectMessage -> m DirectMessage #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DirectMessage -> m DirectMessage #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DirectMessage -> m DirectMessage #

Show DirectMessage Source # 
Generic DirectMessage Source # 

Associated Types

type Rep DirectMessage :: * -> * #

ToJSON DirectMessage Source # 
FromJSON DirectMessage Source # 
type Rep DirectMessage Source # 

data EventTarget Source #

Instances

Eq EventTarget Source # 
Data EventTarget Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EventTarget -> c EventTarget #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EventTarget #

toConstr :: EventTarget -> Constr #

dataTypeOf :: EventTarget -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c EventTarget) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EventTarget) #

gmapT :: (forall b. Data b => b -> b) -> EventTarget -> EventTarget #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EventTarget -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EventTarget -> r #

gmapQ :: (forall d. Data d => d -> u) -> EventTarget -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> EventTarget -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> EventTarget -> m EventTarget #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EventTarget -> m EventTarget #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EventTarget -> m EventTarget #

Show EventTarget Source # 
Generic EventTarget Source # 

Associated Types

type Rep EventTarget :: * -> * #

ToJSON EventTarget Source # 
FromJSON EventTarget Source # 
type Rep EventTarget Source # 

data Event Source #

Instances

Eq Event Source # 

Methods

(==) :: Event -> Event -> Bool #

(/=) :: Event -> Event -> Bool #

Data Event Source # 

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 #

toConstr :: Event -> Constr #

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 Source # 

Methods

showsPrec :: Int -> Event -> ShowS #

show :: Event -> String #

showList :: [Event] -> ShowS #

Generic Event Source # 

Associated Types

type Rep Event :: * -> * #

Methods

from :: Event -> Rep Event x #

to :: Rep Event x -> Event #

ToJSON Event Source # 
FromJSON Event Source # 
type Rep Event Source # 

data Delete Source #

Constructors

Delete 

Instances

Eq Delete Source # 

Methods

(==) :: Delete -> Delete -> Bool #

(/=) :: Delete -> Delete -> Bool #

Data Delete Source # 

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 Source # 
Generic Delete Source # 

Associated Types

type Rep Delete :: * -> * #

Methods

from :: Delete -> Rep Delete x #

to :: Rep Delete x -> Delete #

ToJSON Delete Source # 
FromJSON Delete Source # 
type Rep Delete Source # 
type Rep Delete = D1 (MetaData "Delete" "Web.Twitter.Types" "twitter-types-0.7.2.2-LaMHofqEINq80FbVZtr9dc" False) (C1 (MetaCons "Delete" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "delId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 StatusId)) (S1 (MetaSel (Just Symbol "delUserId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 UserId))))

data User Source #

This type represents the Twitter user. See https://dev.twitter.com/docs/platform-objects/users.

Instances

Eq User Source # 

Methods

(==) :: User -> User -> Bool #

(/=) :: User -> User -> Bool #

Data User Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> User -> c User #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c User #

toConstr :: User -> Constr #

dataTypeOf :: User -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c User) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c User) #

gmapT :: (forall b. Data b => b -> b) -> User -> User #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> User -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> User -> r #

gmapQ :: (forall d. Data d => d -> u) -> User -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> User -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> User -> m User #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> User -> m User #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> User -> m User #

Show User Source # 

Methods

showsPrec :: Int -> User -> ShowS #

show :: User -> String #

showList :: [User] -> ShowS #

Generic User Source # 

Associated Types

type Rep User :: * -> * #

Methods

from :: User -> Rep User x #

to :: Rep User x -> User #

ToJSON User Source # 
FromJSON User Source # 

Methods

parseJSON :: Value -> Parser User #

type Rep User Source # 
type Rep User = D1 (MetaData "User" "Web.Twitter.Types" "twitter-types-0.7.2.2-LaMHofqEINq80FbVZtr9dc" False) (C1 (MetaCons "User" PrefixI True) ((:*:) ((:*:) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "userContributorsEnabled") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) (S1 (MetaSel (Just Symbol "userCreatedAt") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 UTCTime))) ((:*:) (S1 (MetaSel (Just Symbol "userDefaultProfile") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) ((:*:) (S1 (MetaSel (Just Symbol "userDefaultProfileImage") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) (S1 (MetaSel (Just Symbol "userDescription") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "userFavoritesCount") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) (S1 (MetaSel (Just Symbol "userFollowRequestSent") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Bool)))) ((:*:) (S1 (MetaSel (Just Symbol "userFollowing") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Bool))) ((:*:) (S1 (MetaSel (Just Symbol "userFollowersCount") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) (S1 (MetaSel (Just Symbol "userFriendsCount") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "userGeoEnabled") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) (S1 (MetaSel (Just Symbol "userId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 UserId))) ((:*:) (S1 (MetaSel (Just Symbol "userIsTranslator") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) ((:*:) (S1 (MetaSel (Just Symbol "userLang") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 LanguageCode)) (S1 (MetaSel (Just Symbol "userListedCount") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "userLocation") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "userName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text))) ((:*:) (S1 (MetaSel (Just Symbol "userNotifications") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Bool))) ((:*:) (S1 (MetaSel (Just Symbol "userProfileBackgroundColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "userProfileBackgroundImageURL") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe URIString)))))))) ((:*:) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "userProfileBackgroundImageURLHttps") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe URIString))) (S1 (MetaSel (Just Symbol "userProfileBackgroundTile") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Bool)))) ((:*:) (S1 (MetaSel (Just Symbol "userProfileBannerURL") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe URIString))) ((:*:) (S1 (MetaSel (Just Symbol "userProfileImageURL") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe URIString))) (S1 (MetaSel (Just Symbol "userProfileImageURLHttps") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe URIString)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "userProfileLinkColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) (S1 (MetaSel (Just Symbol "userProfileSidebarBorderColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text))) ((:*:) (S1 (MetaSel (Just Symbol "userProfileSidebarFillColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) ((:*:) (S1 (MetaSel (Just Symbol "userProfileTextColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) (S1 (MetaSel (Just Symbol "userProfileUseBackgroundImage") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "userProtected") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) (S1 (MetaSel (Just Symbol "userScreenName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text))) ((:*:) (S1 (MetaSel (Just Symbol "userShowAllInlineMedia") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Bool))) ((:*:) (S1 (MetaSel (Just Symbol "userStatusesCount") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) (S1 (MetaSel (Just Symbol "userTimeZone") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "userURL") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe URIString))) (S1 (MetaSel (Just Symbol "userUtcOffset") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Int)))) ((:*:) (S1 (MetaSel (Just Symbol "userVerified") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) ((:*:) (S1 (MetaSel (Just Symbol "userWithheldInCountries") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe [Text]))) (S1 (MetaSel (Just Symbol "userWithheldScope") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text))))))))))

data List Source #

Instances

Eq List Source # 

Methods

(==) :: List -> List -> Bool #

(/=) :: List -> List -> Bool #

Data List Source # 

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 #

toConstr :: List -> Constr #

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 Source # 

Methods

showsPrec :: Int -> List -> ShowS #

show :: List -> String #

showList :: [List] -> ShowS #

Generic List Source # 

Associated Types

type Rep List :: * -> * #

Methods

from :: List -> Rep List x #

to :: Rep List x -> List #

ToJSON List Source # 
FromJSON List Source # 

Methods

parseJSON :: Value -> Parser List #

type Rep List Source # 

data Entities Source #

Instances

Eq Entities Source # 
Data Entities Source # 

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 Source # 
Generic Entities Source # 

Associated Types

type Rep Entities :: * -> * #

Methods

from :: Entities -> Rep Entities x #

to :: Rep Entities x -> Entities #

ToJSON Entities Source # 
FromJSON Entities Source # 
type Rep Entities Source # 

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 Entity a Source #

Constructors

Entity 

Fields

Instances

Eq a => Eq (Entity a) Source # 

Methods

(==) :: Entity a -> Entity a -> Bool #

(/=) :: Entity a -> Entity a -> Bool #

Data a => Data (Entity a) Source # 

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) Source # 

Methods

showsPrec :: Int -> Entity a -> ShowS #

show :: Entity a -> String #

showList :: [Entity a] -> ShowS #

Generic (Entity a) Source # 

Associated Types

type Rep (Entity a) :: * -> * #

Methods

from :: Entity a -> Rep (Entity a) x #

to :: Rep (Entity a) x -> Entity a #

ToJSON a => ToJSON (Entity a) Source # 

Methods

toJSON :: Entity a -> Value #

toEncoding :: Entity a -> Encoding #

FromJSON a => FromJSON (Entity a) Source # 

Methods

parseJSON :: Value -> Parser (Entity a) #

type Rep (Entity a) Source # 
type Rep (Entity a) = D1 (MetaData "Entity" "Web.Twitter.Types" "twitter-types-0.7.2.2-LaMHofqEINq80FbVZtr9dc" False) (C1 (MetaCons "Entity" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "entityBody") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)) (S1 (MetaSel (Just Symbol "entityIndices") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 EntityIndices))))

data HashTagEntity Source #

Constructors

HashTagEntity 

Fields

Instances

Eq HashTagEntity Source # 
Data HashTagEntity Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HashTagEntity -> c HashTagEntity #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HashTagEntity #

toConstr :: HashTagEntity -> Constr #

dataTypeOf :: HashTagEntity -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c HashTagEntity) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HashTagEntity) #

gmapT :: (forall b. Data b => b -> b) -> HashTagEntity -> HashTagEntity #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HashTagEntity -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HashTagEntity -> r #

gmapQ :: (forall d. Data d => d -> u) -> HashTagEntity -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HashTagEntity -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HashTagEntity -> m HashTagEntity #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HashTagEntity -> m HashTagEntity #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HashTagEntity -> m HashTagEntity #

Show HashTagEntity Source # 
Generic HashTagEntity Source # 

Associated Types

type Rep HashTagEntity :: * -> * #

ToJSON HashTagEntity Source # 
FromJSON HashTagEntity Source # 
type Rep HashTagEntity Source # 
type Rep HashTagEntity = D1 (MetaData "HashTagEntity" "Web.Twitter.Types" "twitter-types-0.7.2.2-LaMHofqEINq80FbVZtr9dc" False) (C1 (MetaCons "HashTagEntity" PrefixI True) (S1 (MetaSel (Just Symbol "hashTagText") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

data UserEntity Source #

Instances

Eq UserEntity Source # 
Data UserEntity Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UserEntity -> c UserEntity #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UserEntity #

toConstr :: UserEntity -> Constr #

dataTypeOf :: UserEntity -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c UserEntity) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UserEntity) #

gmapT :: (forall b. Data b => b -> b) -> UserEntity -> UserEntity #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UserEntity -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UserEntity -> r #

gmapQ :: (forall d. Data d => d -> u) -> UserEntity -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> UserEntity -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> UserEntity -> m UserEntity #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UserEntity -> m UserEntity #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UserEntity -> m UserEntity #

Show UserEntity Source # 
Generic UserEntity Source # 

Associated Types

type Rep UserEntity :: * -> * #

ToJSON UserEntity Source # 
FromJSON UserEntity Source # 
type Rep UserEntity Source # 
type Rep UserEntity = D1 (MetaData "UserEntity" "Web.Twitter.Types" "twitter-types-0.7.2.2-LaMHofqEINq80FbVZtr9dc" False) (C1 (MetaCons "UserEntity" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "userEntityUserId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 UserId)) ((:*:) (S1 (MetaSel (Just Symbol "userEntityUserName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 UserName)) (S1 (MetaSel (Just Symbol "userEntityUserScreenName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))))

data URLEntity Source #

Constructors

URLEntity 

Fields

Instances

Eq URLEntity Source # 
Data URLEntity Source # 

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 Source # 
Generic URLEntity Source # 

Associated Types

type Rep URLEntity :: * -> * #

ToJSON URLEntity Source # 
FromJSON URLEntity Source # 
type Rep URLEntity Source # 
type Rep URLEntity = D1 (MetaData "URLEntity" "Web.Twitter.Types" "twitter-types-0.7.2.2-LaMHofqEINq80FbVZtr9dc" False) (C1 (MetaCons "URLEntity" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "ueURL") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 URIString)) ((:*:) (S1 (MetaSel (Just Symbol "ueExpanded") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 URIString)) (S1 (MetaSel (Just Symbol "ueDisplay") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))))

data MediaEntity Source #

Instances

Eq MediaEntity Source # 
Data MediaEntity Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MediaEntity -> c MediaEntity #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MediaEntity #

toConstr :: MediaEntity -> Constr #

dataTypeOf :: MediaEntity -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c MediaEntity) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MediaEntity) #

gmapT :: (forall b. Data b => b -> b) -> MediaEntity -> MediaEntity #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MediaEntity -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MediaEntity -> r #

gmapQ :: (forall d. Data d => d -> u) -> MediaEntity -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MediaEntity -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MediaEntity -> m MediaEntity #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MediaEntity -> m MediaEntity #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MediaEntity -> m MediaEntity #

Show MediaEntity Source # 
Generic MediaEntity Source # 

Associated Types

type Rep MediaEntity :: * -> * #

ToJSON MediaEntity Source # 
FromJSON MediaEntity Source # 
type Rep MediaEntity Source # 

data MediaSize Source #

Constructors

MediaSize 

Fields

Instances

Eq MediaSize Source # 
Data MediaSize Source # 

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 Source # 
Generic MediaSize Source # 

Associated Types

type Rep MediaSize :: * -> * #

ToJSON MediaSize Source # 
FromJSON MediaSize Source # 
type Rep MediaSize Source # 
type Rep MediaSize = D1 (MetaData "MediaSize" "Web.Twitter.Types" "twitter-types-0.7.2.2-LaMHofqEINq80FbVZtr9dc" False) (C1 (MetaCons "MediaSize" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "msWidth") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) ((:*:) (S1 (MetaSel (Just Symbol "msHeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) (S1 (MetaSel (Just Symbol "msResize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))))

data Coordinates Source #

Constructors

Coordinates 

Instances

Eq Coordinates Source # 
Data Coordinates Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Coordinates -> c Coordinates #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Coordinates #

toConstr :: Coordinates -> Constr #

dataTypeOf :: Coordinates -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Coordinates) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Coordinates) #

gmapT :: (forall b. Data b => b -> b) -> Coordinates -> Coordinates #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Coordinates -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Coordinates -> r #

gmapQ :: (forall d. Data d => d -> u) -> Coordinates -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Coordinates -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Coordinates -> m Coordinates #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Coordinates -> m Coordinates #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Coordinates -> m Coordinates #

Show Coordinates Source # 
Generic Coordinates Source # 

Associated Types

type Rep Coordinates :: * -> * #

ToJSON Coordinates Source # 
FromJSON Coordinates Source # 
type Rep Coordinates Source # 
type Rep Coordinates = D1 (MetaData "Coordinates" "Web.Twitter.Types" "twitter-types-0.7.2.2-LaMHofqEINq80FbVZtr9dc" False) (C1 (MetaCons "Coordinates" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "coordinates") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Double])) (S1 (MetaSel (Just Symbol "coordinatesType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text))))

data Place Source #

This type represents a place, named locations with corresponding geo coordinates. See https://dev.twitter.com/docs/platform-objects/places.

Instances

Eq Place Source # 

Methods

(==) :: Place -> Place -> Bool #

(/=) :: Place -> Place -> Bool #

Data Place Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Place -> c Place #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Place #

toConstr :: Place -> Constr #

dataTypeOf :: Place -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Place) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Place) #

gmapT :: (forall b. Data b => b -> b) -> Place -> Place #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Place -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Place -> r #

gmapQ :: (forall d. Data d => d -> u) -> Place -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Place -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Place -> m Place #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Place -> m Place #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Place -> m Place #

Show Place Source # 

Methods

showsPrec :: Int -> Place -> ShowS #

show :: Place -> String #

showList :: [Place] -> ShowS #

Generic Place Source # 

Associated Types

type Rep Place :: * -> * #

Methods

from :: Place -> Rep Place x #

to :: Rep Place x -> Place #

ToJSON Place Source # 
FromJSON Place Source # 
type Rep Place Source # 

data BoundingBox Source #

A bounding box of coordinates which encloses the place. See https://dev.twitter.com/docs/platform-objects/places#obj-boundingbox.

Instances

Eq BoundingBox Source # 
Data BoundingBox Source # 

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 Source # 
Generic BoundingBox Source # 

Associated Types

type Rep BoundingBox :: * -> * #

ToJSON BoundingBox Source # 
FromJSON BoundingBox Source # 
type Rep BoundingBox Source # 
type Rep BoundingBox = D1 (MetaData "BoundingBox" "Web.Twitter.Types" "twitter-types-0.7.2.2-LaMHofqEINq80FbVZtr9dc" False) (C1 (MetaCons "BoundingBox" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "boundingBoxCoordinates") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [[[Double]]])) (S1 (MetaSel (Just Symbol "boundingBoxType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text))))

data Contributor Source #

Instances

Eq Contributor Source # 
Data Contributor Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Contributor -> c Contributor #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Contributor #

toConstr :: Contributor -> Constr #

dataTypeOf :: Contributor -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Contributor) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Contributor) #

gmapT :: (forall b. Data b => b -> b) -> Contributor -> Contributor #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Contributor -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Contributor -> r #

gmapQ :: (forall d. Data d => d -> u) -> Contributor -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Contributor -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Contributor -> m Contributor #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Contributor -> m Contributor #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Contributor -> m Contributor #

Show Contributor Source # 
Generic Contributor Source # 

Associated Types

type Rep Contributor :: * -> * #

ToJSON Contributor Source # 
FromJSON Contributor Source # 
type Rep Contributor Source # 
type Rep Contributor = D1 (MetaData "Contributor" "Web.Twitter.Types" "twitter-types-0.7.2.2-LaMHofqEINq80FbVZtr9dc" False) (C1 (MetaCons "Contributor" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "contributorId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 UserId)) (S1 (MetaSel (Just Symbol "contributorScreenName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text)))))

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

Eq UploadedMedia Source # 
Data UploadedMedia Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UploadedMedia -> c UploadedMedia #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UploadedMedia #

toConstr :: UploadedMedia -> Constr #

dataTypeOf :: UploadedMedia -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c UploadedMedia) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UploadedMedia) #

gmapT :: (forall b. Data b => b -> b) -> UploadedMedia -> UploadedMedia #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UploadedMedia -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UploadedMedia -> r #

gmapQ :: (forall d. Data d => d -> u) -> UploadedMedia -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> UploadedMedia -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> UploadedMedia -> m UploadedMedia #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UploadedMedia -> m UploadedMedia #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UploadedMedia -> m UploadedMedia #

Show UploadedMedia Source # 
Generic UploadedMedia Source # 

Associated Types

type Rep UploadedMedia :: * -> * #

ToJSON UploadedMedia Source # 
FromJSON UploadedMedia Source # 
type Rep UploadedMedia Source # 
type Rep UploadedMedia = D1 (MetaData "UploadedMedia" "Web.Twitter.Types" "twitter-types-0.7.2.2-LaMHofqEINq80FbVZtr9dc" False) (C1 (MetaCons "UploadedMedia" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "uploadedMediaId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Integer)) ((:*:) (S1 (MetaSel (Just Symbol "uploadedMediaSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Integer)) (S1 (MetaSel (Just Symbol "uploadedMediaImage") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ImageSizeType)))))

data ImageSizeType Source #

Image size type. This type is included in the API response of "/1.1/media/upload.json".

Instances

Eq ImageSizeType Source # 
Data ImageSizeType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ImageSizeType -> c ImageSizeType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ImageSizeType #

toConstr :: ImageSizeType -> Constr #

dataTypeOf :: ImageSizeType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ImageSizeType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ImageSizeType) #

gmapT :: (forall b. Data b => b -> b) -> ImageSizeType -> ImageSizeType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ImageSizeType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ImageSizeType -> r #

gmapQ :: (forall d. Data d => d -> u) -> ImageSizeType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ImageSizeType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ImageSizeType -> m ImageSizeType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ImageSizeType -> m ImageSizeType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ImageSizeType -> m ImageSizeType #

Show ImageSizeType Source # 
Generic ImageSizeType Source # 

Associated Types

type Rep ImageSizeType :: * -> * #

ToJSON ImageSizeType Source # 
FromJSON ImageSizeType Source # 
type Rep ImageSizeType Source # 
type Rep ImageSizeType = D1 (MetaData "ImageSizeType" "Web.Twitter.Types" "twitter-types-0.7.2.2-LaMHofqEINq80FbVZtr9dc" False) (C1 (MetaCons "ImageSizeType" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "imageSizeTypeWidth") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) ((:*:) (S1 (MetaSel (Just Symbol "imageSizeTypeHeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) (S1 (MetaSel (Just Symbol "imageSizeTypeType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))))