| Stability | experimental |
|---|---|
| Maintainer | fuuzetsu@fuuzetsu.co.uk |
| Safe Haskell | Safe-Inferred |
HBooru.Types
Description
Module definining types used by the library.
- type Tag = String
- class DataFormat a
- data XML = XML
- data JSON = JSON
- class Response r => CoerceResponse x r | x -> r, r -> x where
- toResponse :: x -> String -> r
- fromResponse :: r -> x
- class (Site s, DataFormat r) => PostParser s r where
- type ImageTy s r
- parseResponse :: CoerceResponse r r' => s -> r' -> [ImageTy s r]
- class (Site s, DataFormat r) => Counted s r where
- parseCount :: CoerceResponse r r' => s -> r' -> Integer
- class (Site s, DataFormat r) => Postable s r where
- class Site s
- data Rating
- = Safe
- | Questionable
- | Explicit
- data Limit
- data XMLResponse = XMLResponse String
- data JSONResponse = JSONResponse String
- class Response r where
- getResponse :: r -> String
- class Post a where
- height :: a -> Integer
- score :: a -> Integer
- file_url :: a -> String
- parent_id :: a -> Maybe Integer
- sample_url :: a -> String
- sample_width :: a -> Integer
- sample_height :: a -> Integer
- preview_url :: a -> String
- rating :: a -> Rating
- tags :: a -> [String]
- id :: a -> Integer
- width :: a -> Integer
- change :: a -> String
- md5 :: a -> String
- creator_id :: a -> Integer
- has_children :: a -> Maybe Bool
- created_at :: a -> String
- status :: a -> String
- source :: a -> String
- has_notes :: a -> Maybe Bool
- has_comments :: a -> Maybe Bool
- preview_width :: a -> Integer
- preview_height :: a -> Integer
- betweenPosts :: Post b => a -> PostConstructor b -> b
- type PostConstructor b = Integer -> Integer -> String -> Maybe Integer -> String -> Integer -> Integer -> String -> Rating -> [String] -> Integer -> Integer -> String -> String -> Integer -> Maybe Bool -> String -> String -> String -> Maybe Bool -> Maybe Bool -> Integer -> Integer -> b
Documentation
Tags used for searching in sites. No special escaping is done. Note that many sites would treat a tag like "striped panties" as two separate tags and you wouldn't get the results you were after.
class DataFormat a Source
Data format used by various Sites. See instances for currently used
formats.
Instances
Used as one of the data formats.
Constructors
| XML |
Instances
class Response r => CoerceResponse x r | x -> r, r -> x whereSource
Thanks to this class, we're able to provide instances converting
from a DataFormat to Response. This is useful if we need a DataFormat
while we only have a type that's an instance of Response. Note that the
functional dependency currently requires that there is only one way to coerce
between two types.
Methods
toResponse :: x -> String -> rSource
Given something and a String, we get the appropriate Response.
For example with instance :
CoerceResponse XML XMLResponse
>>>toResponse XML "<SomeXML></SomeXML>"XMLReponse "<SomeXML></SomeXML>"
fromResponse :: r -> xSource
Given some kind of Response, we get the appropriate value back,
depending on the class instance.
For example with instance :
CoerceResponse XML XMLResponse
>>>fromResponse $ XMLReponse "<SomeXML></SomeXML>"XML
class (Site s, DataFormat r) => PostParser s r whereSource
Class specifying a parser that can fetch posts. A post usually consists of
links to the image, samples, and some meta-data. See
GenericPost for the kind of thing we usually
get out. The reason for this class is that sometimes we might get different
information based on the DataFormat we use so we use type families to
denote this rather than forcing the library user to make do with our best
guess on what goes into the post. It also allows us to use different post
types for sites that provide different information.
Methods
parseResponse :: CoerceResponse r r' => s -> r' -> [ImageTy s r]Source
Given a parser working with DataFormat specified by an instance of
this class, we require through CoerceResponse that it is able to parse
responses in the format so what we actually pass into this function is
the Site this parser works with (so that we can pick the appropriate data
type for the posts) and a Response matching the DataFormat (through a
class instance). For PostParser instance, example use
might go like
Gelbooru XML
do fc <-XMLResponse$readFile"gelbooruResponse.xml" -- the type of images is actually inferred for us let images ∷ [GelbooruPost] images = parseResponseGelboorufc return images
The cool thing is that we can't feed anything but XMLResponse to an
XML parser.
class (Site s, DataFormat r) => Counted s r whereSource
Describes whether a response from a Site in given DataFormat
allows us to get the information about total number of posts matching our
query. Some sites don't provide this information.
Methods
parseCount :: CoerceResponse r r' => s -> r' -> IntegerSource
class (Site s, DataFormat r) => Postable s r whereSource
If we can make an API request to Site in a specific DataFormat, we can
use instances of this class to pass in
Methods
postUrl :: s -> r -> [Tag] -> StringSource
Given a Site, a DataFormat and a list of Tags, an instance of this
class should be able to return a String at which we can find data in
DataFormat format that honours our tags. This is effectively a URL
builder for POST requests.
Provides information about whether there's a hard limit on the amount of
posts we can fetch from the site at once. The reason for this function here
rather than in Site is that we might be parsing data without an API we
can post to at all and we're getting our data through other means.
Describes a site for a parser. The reason why this isn't a simple data type is to allow us to write additional parsers in the future without modifying this library if we wish to do so.
Rating used on *booru sites.
Constructors
| Safe | |
| Questionable | |
| Explicit |
Denotes whethere there's a hard limit on the number of posts
we can fetch at a time from a site. NoLimit implies that we can fetch
everything at once and not that we don't know. See Counted for a way to
potentially retrieve number of posts present on the site.
data XMLResponse Source
One of the formats we can receive responses from sites in. For things
like parsers parametrisation, use XML instead and use methods in
CoerceResponse if you need to.
Constructors
| XMLResponse String |
data JSONResponse Source
One of the formats we can receive responses from sites in. For things
like parsers parametrisation, use JSON instead and use methods in
CoerceResponse if you need to.
Constructors
| JSONResponse String |
Specifies what is considered a response. You'll almost certainly also
want new DataFormat and CoerceResponse instances if you're adding some
here. This class assumes that all responses carry the response in a string we
can extract. Note that this is not for use as network response if you're
scraping, only for putting data into after you have done all the error
checking and whatnot.
Instances
Class representing a best-case scenario post. We use this to convert between different posts for each site while providing uniform access. The methods are just the attributes of posts seen on Gelbooru-like sites.
Methods
parent_id :: a -> Maybe IntegerSource
sample_url :: a -> StringSource
sample_width :: a -> IntegerSource
sample_height :: a -> IntegerSource
preview_url :: a -> StringSource
creator_id :: a -> IntegerSource
has_children :: a -> Maybe BoolSource
created_at :: a -> StringSource
has_notes :: a -> Maybe BoolSource
has_comments :: a -> Maybe BoolSource
preview_width :: a -> IntegerSource
preview_height :: a -> IntegerSource
betweenPosts :: Post b => a -> PostConstructor b -> bSource
type PostConstructor b = Integer -> Integer -> String -> Maybe Integer -> String -> Integer -> Integer -> String -> Rating -> [String] -> Integer -> Integer -> String -> String -> Integer -> Maybe Bool -> String -> String -> String -> Maybe Bool -> Maybe Bool -> Integer -> Integer -> bSource
A cludge for use with betweenPosts