twitter-conduit-0.2.2.1: Twitter API package with conduit interface and Streaming API support.

Safe HaskellNone
LanguageHaskell98

Web.Twitter.Conduit.Lens

Contents

Synopsis

Response

data Response responseType Source #

Instances

Functor Response Source # 

Methods

fmap :: (a -> b) -> Response a -> Response b #

(<$) :: a -> Response b -> Response a #

Foldable Response Source # 

Methods

fold :: Monoid m => Response m -> m #

foldMap :: Monoid m => (a -> m) -> Response a -> m #

foldr :: (a -> b -> b) -> b -> Response a -> b #

foldr' :: (a -> b -> b) -> b -> Response a -> b #

foldl :: (b -> a -> b) -> b -> Response a -> b #

foldl' :: (b -> a -> b) -> b -> Response a -> b #

foldr1 :: (a -> a -> a) -> Response a -> a #

foldl1 :: (a -> a -> a) -> Response a -> a #

toList :: Response a -> [a] #

null :: Response a -> Bool #

length :: Response a -> Int #

elem :: Eq a => a -> Response a -> Bool #

maximum :: Ord a => Response a -> a #

minimum :: Ord a => Response a -> a #

sum :: Num a => Response a -> a #

product :: Num a => Response a -> a #

Traversable Response Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Response a -> f (Response b) #

sequenceA :: Applicative f => Response (f a) -> f (Response a) #

mapM :: Monad m => (a -> m b) -> Response a -> m (Response b) #

sequence :: Monad m => Response (m a) -> m (Response a) #

Eq responseType => Eq (Response responseType) Source # 

Methods

(==) :: Response responseType -> Response responseType -> Bool #

(/=) :: Response responseType -> Response responseType -> Bool #

Show responseType => Show (Response responseType) Source # 

Methods

showsPrec :: Int -> Response responseType -> ShowS #

show :: Response responseType -> String #

showList :: [Response responseType] -> ShowS #

responseStatus :: forall responseType. Lens' (Response responseType) Status Source #

responseBody :: forall a b. Lens (Response a) (Response b) a b Source #

responseHeaders :: forall responseType. Lens' (Response responseType) ResponseHeaders Source #

TwitterErrorMessage

data TwitterErrorMessage Source #

Twitter Error Messages

see detail: https://dev.twitter.com/docs/error-codes-responses

Instances

Enum TwitterErrorMessage Source # 
Eq TwitterErrorMessage Source # 
Data TwitterErrorMessage Source # 

Methods

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

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

toConstr :: TwitterErrorMessage -> Constr #

dataTypeOf :: TwitterErrorMessage -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord TwitterErrorMessage Source # 
Show TwitterErrorMessage Source # 
FromJSON TwitterErrorMessage Source # 

WithCursor

data WithCursor cursorKey wrapped Source #

A wrapper for API responses which have "next_cursor" field.

The first type parameter of WithCursor specifies the field name of contents.

>>> let Just res = decode "{\"previous_cursor\": 0, \"next_cursor\": 1234567890, \"ids\": [1111111111]}" :: Maybe (WithCursor IdsCursorKey UserId)
>>> nextCursor res
1234567890
>>> contents res
[1111111111]
>>> let Just res = decode "{\"previous_cursor\": 0, \"next_cursor\": 0, \"users\": [1000]}" :: Maybe (WithCursor UsersCursorKey UserId)
>>> nextCursor res
0
>>> contents res
[1000]

Instances

Show wrapped => Show (WithCursor cursorKey wrapped) Source # 

Methods

showsPrec :: Int -> WithCursor cursorKey wrapped -> ShowS #

show :: WithCursor cursorKey wrapped -> String #

showList :: [WithCursor cursorKey wrapped] -> ShowS #

(FromJSON wrapped, CursorKey c) => FromJSON (WithCursor c wrapped) Source # 

Methods

parseJSON :: Value -> Parser (WithCursor c wrapped) #

parseJSONList :: Value -> Parser [WithCursor c wrapped] #

previousCursor :: forall cursorKey wrapped. Lens' (WithCursor cursorKey wrapped) Integer Source #

nextCursor :: forall cursorKey wrapped. Lens' (WithCursor cursorKey wrapped) Integer Source #

contents :: forall cursorKey a b. Lens (WithCursor cursorKey a) (WithCursor cursorKey b) [a] [b] Source #

Re-exports

data IdsCursorKey Source #

Phantom type to specify the key which point out the content in the response.

data UsersCursorKey Source #

Phantom type to specify the key which point out the content in the response.

data ListsCursorKey Source #

Phantom type to specify the key which point out the content in the response.