exh-0.2.0: A library for crawling exhentai
Safe HaskellNone
LanguageHaskell2010

Web.Exhentai.API.MPV

Synopsis

Documentation

data DispatchRequest Source #

Constructors

DispatchRequest 

Instances

Instances details
Eq DispatchRequest Source # 
Instance details

Defined in Web.Exhentai.API.MPV

Show DispatchRequest Source # 
Instance details

Defined in Web.Exhentai.API.MPV

Generic DispatchRequest Source # 
Instance details

Defined in Web.Exhentai.API.MPV

Associated Types

type Rep DispatchRequest :: Type -> Type #

ToJSON DispatchRequest Source # 
Instance details

Defined in Web.Exhentai.API.MPV

type Rep DispatchRequest Source # 
Instance details

Defined in Web.Exhentai.API.MPV

data DispatchResult Source #

Constructors

DispatchResult 

Fields

Instances

Instances details
Eq DispatchResult Source # 
Instance details

Defined in Web.Exhentai.API.MPV

Show DispatchResult Source # 
Instance details

Defined in Web.Exhentai.API.MPV

Generic DispatchResult Source # 
Instance details

Defined in Web.Exhentai.API.MPV

Associated Types

type Rep DispatchResult :: Type -> Type #

FromJSON DispatchResult Source # 
Instance details

Defined in Web.Exhentai.API.MPV

type Rep DispatchResult Source # 
Instance details

Defined in Web.Exhentai.API.MPV

data Vars Source #

All the variables defined in the scripts that came with the MPV

Constructors

Vars 

Fields

Instances

Instances details
Eq Vars Source # 
Instance details

Defined in Web.Exhentai.Parsing.MPV

Methods

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

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

Show Vars Source # 
Instance details

Defined in Web.Exhentai.Parsing.MPV

Methods

showsPrec :: Int -> Vars -> ShowS #

show :: Vars -> String #

showList :: [Vars] -> ShowS #

Generic Vars Source # 
Instance details

Defined in Web.Exhentai.Parsing.MPV

Associated Types

type Rep Vars :: Type -> Type #

Methods

from :: Vars -> Rep Vars x #

to :: Rep Vars x -> Vars #

type Rep Vars Source # 
Instance details

Defined in Web.Exhentai.Parsing.MPV

data Server Source #

Constructors

HAtH Int 
Other Text 

Instances

Instances details
Eq Server Source # 
Instance details

Defined in Web.Exhentai.API.MPV

Methods

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

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

Show Server Source # 
Instance details

Defined in Web.Exhentai.API.MPV

Generic Server Source # 
Instance details

Defined in Web.Exhentai.API.MPV

Associated Types

type Rep Server :: Type -> Type #

Methods

from :: Server -> Rep Server x #

to :: Rep Server x -> Server #

ToJSON Server Source # 
Instance details

Defined in Web.Exhentai.API.MPV

FromJSON Server Source # 
Instance details

Defined in Web.Exhentai.API.MPV

type Rep Server Source # 
Instance details

Defined in Web.Exhentai.API.MPV

newtype Dim Source #

Constructors

Dim Int 

Instances

Instances details
Eq Dim Source # 
Instance details

Defined in Web.Exhentai.API.MPV

Methods

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

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

Show Dim Source # 
Instance details

Defined in Web.Exhentai.API.MPV

Methods

showsPrec :: Int -> Dim -> ShowS #

show :: Dim -> String #

showList :: [Dim] -> ShowS #

FromJSON Dim Source # 
Instance details

Defined in Web.Exhentai.API.MPV

fetchMpv :: (MonadHttpState m, MonadIO m) => Gallery -> m Vars Source #

Fetch the Vars from a Gallery's mpv page

toRequests :: Vars -> [DispatchRequest] Source #

Generate a list of requests from a Vars

imageDispatch :: MonadHttpState m => DispatchRequest -> m DispatchResult Source #

Calls the API to dispatch a image request to a H@H server

fetchImage' :: (MonadHttpState m, MonadIO n) => DispatchRequest -> m (Response (ConduitT i ByteString n ())) Source #

Like fetchImage, but the user is responsible of closing the response