twitter-conduit-0.6.1: Twitter API package with conduit interface and Streaming API support.
Safe HaskellNone
LanguageHaskell2010

Web.Twitter.Conduit.Cursor

Synopsis

Documentation

type IdsCursorKey = "ids" Source #

type UsersCursorKey = "users" Source #

type ListsCursorKey = "lists" Source #

type EventsCursorKey = "events" Source #

data WithCursor cursorType (cursorKey :: Symbol) 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 Integer "ids" UserId)
>>> nextCursor res
Just 1234567890
>>> contents res
[1111111111]
>>> let Just res = decode "{\"previous_cursor\": 0, \"next_cursor\": 0, \"users\": [1000]}" :: Maybe (WithCursor Integer "users" UserId)
>>> nextCursor res
Just 0
>>> contents res
[1000]
>>> let Just res = decode "{\"next_cursor\": \"hogehoge\", \"events\": [1000]}" :: Maybe (WithCursor Text "events" UserId)
>>> nextCursor res
Just "hogehoge"
>>> contents res
[1000]

Constructors

WithCursor 

Fields

Instances

Instances details
Generic1 (WithCursor cursorType cursorKey :: Type -> Type) Source # 
Instance details

Defined in Web.Twitter.Conduit.Cursor

Associated Types

type Rep1 (WithCursor cursorType cursorKey) :: k -> Type #

Methods

from1 :: forall (a :: k). WithCursor cursorType cursorKey a -> Rep1 (WithCursor cursorType cursorKey) a #

to1 :: forall (a :: k). Rep1 (WithCursor cursorType cursorKey) a -> WithCursor cursorType cursorKey a #

Functor (WithCursor cursorType cursorKey) Source # 
Instance details

Defined in Web.Twitter.Conduit.Cursor

Methods

fmap :: (a -> b) -> WithCursor cursorType cursorKey a -> WithCursor cursorType cursorKey b #

(<$) :: a -> WithCursor cursorType cursorKey b -> WithCursor cursorType cursorKey a #

Foldable (WithCursor cursorType cursorKey) Source # 
Instance details

Defined in Web.Twitter.Conduit.Cursor

Methods

fold :: Monoid m => WithCursor cursorType cursorKey m -> m #

foldMap :: Monoid m => (a -> m) -> WithCursor cursorType cursorKey a -> m #

foldMap' :: Monoid m => (a -> m) -> WithCursor cursorType cursorKey a -> m #

foldr :: (a -> b -> b) -> b -> WithCursor cursorType cursorKey a -> b #

foldr' :: (a -> b -> b) -> b -> WithCursor cursorType cursorKey a -> b #

foldl :: (b -> a -> b) -> b -> WithCursor cursorType cursorKey a -> b #

foldl' :: (b -> a -> b) -> b -> WithCursor cursorType cursorKey a -> b #

foldr1 :: (a -> a -> a) -> WithCursor cursorType cursorKey a -> a #

foldl1 :: (a -> a -> a) -> WithCursor cursorType cursorKey a -> a #

toList :: WithCursor cursorType cursorKey a -> [a] #

null :: WithCursor cursorType cursorKey a -> Bool #

length :: WithCursor cursorType cursorKey a -> Int #

elem :: Eq a => a -> WithCursor cursorType cursorKey a -> Bool #

maximum :: Ord a => WithCursor cursorType cursorKey a -> a #

minimum :: Ord a => WithCursor cursorType cursorKey a -> a #

sum :: Num a => WithCursor cursorType cursorKey a -> a #

product :: Num a => WithCursor cursorType cursorKey a -> a #

Traversable (WithCursor cursorType cursorKey) Source # 
Instance details

Defined in Web.Twitter.Conduit.Cursor

Methods

traverse :: Applicative f => (a -> f b) -> WithCursor cursorType cursorKey a -> f (WithCursor cursorType cursorKey b) #

sequenceA :: Applicative f => WithCursor cursorType cursorKey (f a) -> f (WithCursor cursorType cursorKey a) #

mapM :: Monad m => (a -> m b) -> WithCursor cursorType cursorKey a -> m (WithCursor cursorType cursorKey b) #

sequence :: Monad m => WithCursor cursorType cursorKey (m a) -> m (WithCursor cursorType cursorKey a) #

(KnownSymbol cursorKey, FromJSON cursorType) => FromJSON1 (WithCursor cursorType cursorKey) Source # 
Instance details

Defined in Web.Twitter.Conduit.Cursor

Methods

liftParseJSON :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (WithCursor cursorType cursorKey a) #

liftParseJSONList :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser [WithCursor cursorType cursorKey a] #

(Eq cursorType, Eq wrapped) => Eq (WithCursor cursorType cursorKey wrapped) Source # 
Instance details

Defined in Web.Twitter.Conduit.Cursor

Methods

(==) :: WithCursor cursorType cursorKey wrapped -> WithCursor cursorType cursorKey wrapped -> Bool #

(/=) :: WithCursor cursorType cursorKey wrapped -> WithCursor cursorType cursorKey wrapped -> Bool #

(Show cursorType, Show wrapped) => Show (WithCursor cursorType cursorKey wrapped) Source # 
Instance details

Defined in Web.Twitter.Conduit.Cursor

Methods

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

show :: WithCursor cursorType cursorKey wrapped -> String #

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

Generic (WithCursor cursorType cursorKey wrapped) Source # 
Instance details

Defined in Web.Twitter.Conduit.Cursor

Associated Types

type Rep (WithCursor cursorType cursorKey wrapped) :: Type -> Type #

Methods

from :: WithCursor cursorType cursorKey wrapped -> Rep (WithCursor cursorType cursorKey wrapped) x #

to :: Rep (WithCursor cursorType cursorKey wrapped) x -> WithCursor cursorType cursorKey wrapped #

(KnownSymbol cursorKey, FromJSON cursorType, FromJSON wrapped) => FromJSON (WithCursor cursorType cursorKey wrapped) Source # 
Instance details

Defined in Web.Twitter.Conduit.Cursor

Methods

parseJSON :: Value -> Parser (WithCursor cursorType cursorKey wrapped) #

parseJSONList :: Value -> Parser [WithCursor cursorType cursorKey wrapped] #

(NFData cursorType, NFData wrapped) => NFData (WithCursor cursorType cursorKey wrapped) Source # 
Instance details

Defined in Web.Twitter.Conduit.Cursor

Methods

rnf :: WithCursor cursorType cursorKey wrapped -> () #

type Rep1 (WithCursor cursorType cursorKey :: Type -> Type) Source # 
Instance details

Defined in Web.Twitter.Conduit.Cursor

type Rep1 (WithCursor cursorType cursorKey :: Type -> Type) = D1 ('MetaData "WithCursor" "Web.Twitter.Conduit.Cursor" "twitter-conduit-0.6.1-KL9Tg1TP85945tCvDZ6jzE" 'False) (C1 ('MetaCons "WithCursor" 'PrefixI 'True) (S1 ('MetaSel ('Just "previousCursor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe cursorType)) :*: (S1 ('MetaSel ('Just "nextCursor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe cursorType)) :*: S1 ('MetaSel ('Just "contents") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 []))))
type Rep (WithCursor cursorType cursorKey wrapped) Source # 
Instance details

Defined in Web.Twitter.Conduit.Cursor

type Rep (WithCursor cursorType cursorKey wrapped) = D1 ('MetaData "WithCursor" "Web.Twitter.Conduit.Cursor" "twitter-conduit-0.6.1-KL9Tg1TP85945tCvDZ6jzE" 'False) (C1 ('MetaCons "WithCursor" 'PrefixI 'True) (S1 ('MetaSel ('Just "previousCursor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe cursorType)) :*: (S1 ('MetaSel ('Just "nextCursor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe cursorType)) :*: S1 ('MetaSel ('Just "contents") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [wrapped]))))