h-booru-0.1.0.0: Haskell library for retrieving data from various booru image sites

Stabilityexperimental
Maintainerfuuzetsu@fuuzetsu.co.uk
Safe HaskellSafe-Inferred

HBooru.Types

Description

Module definining types used by the library.

Synopsis

Documentation

type Tag = StringSource

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.

data JSON Source

Used as one of the data formats.

Constructors

JSON 

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.

Associated Types

type ImageTy s r Source

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 Gelbooru XML instance, example use might go like

 do fc <- XMLResponse $ readFile "gelbooruResponse.xml"
    -- the type of images is actually inferred for us
    let images ∷ [GelbooruPost]
        images = parseResponse Gelbooru fc
    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.

hardLimit :: s -> LimitSource

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.

class Site s Source

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.

data Rating Source

Rating used on *booru sites.

Constructors

Safe 
Questionable 
Explicit 

Instances

data Limit Source

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.

Constructors

NoLimit 
Limit Integer 

Instances

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 

class Response r whereSource

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.

Methods

getResponse :: r -> StringSource

Extract the response string.

class Post a whereSource

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.

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