scalpel-0.5.0: A high level web scraping library for Haskell.

Safe HaskellNone
LanguageHaskell2010

Text.HTML.Scalpel

Contents

Description

Scalpel is a web scraping library inspired by libraries like parsec and Perl's Web::Scraper. Scalpel builds on top of Text.HTML.TagSoup to provide a declarative and monadic interface.

There are two general mechanisms provided by this library that are used to build web scrapers: Selectors and Scrapers.

Selectors describe a location within an HTML DOM tree. The simplest selector, that can be written is a simple string value. For example, the selector "div" matches every single div node in a DOM. Selectors can be combined using tag combinators. The // operator to define nested relationships within a DOM tree. For example, the selector "div" // "a" matches all anchor tags nested arbitrarily deep within a div tag.

In addition to describing the nested relationships between tags, selectors can also include predicates on the attributes of a tag. The @: operator creates a selector that matches a tag based on the name and various conditions on the tag's attributes. An attribute predicate is just a function that takes an attribute and returns a boolean indicating if the attribute matches a criteria. There are several attribute operators that can be used to generate common predicates. The @= operator creates a predicate that matches the name and value of an attribute exactly. For example, the selector "div" @: ["id" @= "article"] matches div tags where the id attribute is equal to "article".

Scrapers are values that are parameterized over a selector and produce a value from an HTML DOM tree. The Scraper type takes two type parameters. The first is the string like type that is used to store the text values within a DOM tree. Any string like type supported by Text.StringLike is valid. The second type is the type of value that the scraper produces.

There are several scraper primitives that take selectors and extract content from the DOM. Each primitive defined by this library comes in two variants: singular and plural. The singular variants extract the first instance matching the given selector, while the plural variants match every instance.

The following is an example that demonstrates most of the features provided by this library. Suppose you have the following hypothetical HTML located at "http:/example.comarticle.html" and you would like to extract a list of all of the comments.

<html>
  <body>
    <div class='comments'>
      <div class='comment container'>
        <span class='comment author'>Sally</span>
        <div class='comment text'>Woo hoo!</div>
      </div>
      <div class='comment container'>
        <span class='comment author'>Bill</span>
        <img class='comment image' src='http://example.com/cat.gif' />
      </div>
      <div class='comment container'>
        <span class='comment author'>Susan</span>
        <div class='comment text'>WTF!?!</div>
      </div>
    </div>
  </body>
</html>

The following snippet defines a function, allComments, that will download the web page, and extract all of the comments into a list:

type Author = String

data Comment
    = TextComment Author String
    | ImageComment Author URL
    deriving (Show, Eq)

allComments :: IO (Maybe [Comment])
allComments = scrapeURL "http://example.com/article.html" comments
   where
       comments :: Scraper String [Comment]
       comments = chroots ("div" @: [hasClass "container"]) comment

       comment :: Scraper String Comment
       comment = textComment <|> imageComment

       textComment :: Scraper String Comment
       textComment = do
           author      <- text $ "span" @: [hasClass "author"]
           commentText <- text $ "div"  @: [hasClass "text"]
           return $ TextComment author commentText

       imageComment :: Scraper String Comment
       imageComment = do
           author   <- text       $ "span" @: [hasClass "author"]
           imageURL <- attr "src" $ "img"  @: [hasClass "image"]
           return $ ImageComment author imageURL

Complete examples can be found in the examples folder in the scalpel git repository.

Synopsis

Selectors

data Selector :: * #

Selector defines a selection of an HTML DOM tree to be operated on by a web scraper. The selection includes the opening tag that matches the selection, all of the inner tags, and the corresponding closing tag.

Instances

data AttributePredicate :: * #

An AttributePredicate is a method that takes a Attribute and returns a Bool indicating if the given attribute matches a predicate.

data AttributeName :: * #

The AttributeName type can be used when creating Selectors to specify the name of an attribute of a tag.

data TagName :: * #

The TagName type is used when creating a Selector to specify the name of a tag.

Constructors

AnyTag 
TagString String 

Instances

Wildcards

anySelector :: Selector #

A selector which will match all tags

Tag combinators

(//) :: Selector -> Selector -> Selector infixl 5 #

The // operator creates an Selector by nesting one Selector in another. For example, "div" // "a" will create a Selector that matches anchor tags that are nested arbitrarily deep within a div tag.

Attribute predicates

(@:) :: TagName -> [AttributePredicate] -> Selector infixl 9 #

The @: operator creates a Selector by combining a TagName with a list of AttributePredicates.

(@=) :: AttributeName -> String -> AttributePredicate infixl 6 #

The @= operator creates an AttributePredicate that will match attributes with the given name and value.

If you are attempting to match a specific class of a tag with potentially multiple classes, you should use the hasClass utility function.

(@=~) :: RegexLike re String => AttributeName -> re -> AttributePredicate infixl 6 #

The @=~ operator creates an AttributePredicate that will match attributes with the given name and whose value matches the given regular expression.

hasClass :: String -> AttributePredicate #

The classes of a tag are defined in HTML as a space separated list given by the class attribute. The hasClass function will match a class attribute if the given class appears anywhere in the space separated list of classes.

match :: (String -> String -> Bool) -> AttributePredicate #

The match function allows for the creation of arbitrary AttributePredicates. The argument is a function that takes the attribute key followed by the attribute value and returns a boolean indicating if the attribute satisfies the predicate.

Scrapers

data Scraper str a :: * -> * -> * #

A value of Scraper a defines a web scraper that is capable of consuming a list of Tags and optionally producing a value of type a.

Instances

Monad (Scraper str) 

Methods

(>>=) :: Scraper str a -> (a -> Scraper str b) -> Scraper str b #

(>>) :: Scraper str a -> Scraper str b -> Scraper str b #

return :: a -> Scraper str a #

fail :: String -> Scraper str a #

Functor (Scraper str) 

Methods

fmap :: (a -> b) -> Scraper str a -> Scraper str b #

(<$) :: a -> Scraper str b -> Scraper str a #

MonadFail (Scraper str) 

Methods

fail :: String -> Scraper str a #

Applicative (Scraper str) 

Methods

pure :: a -> Scraper str a #

(<*>) :: Scraper str (a -> b) -> Scraper str a -> Scraper str b #

(*>) :: Scraper str a -> Scraper str b -> Scraper str b #

(<*) :: Scraper str a -> Scraper str b -> Scraper str a #

Alternative (Scraper str) 

Methods

empty :: Scraper str a #

(<|>) :: Scraper str a -> Scraper str a -> Scraper str a #

some :: Scraper str a -> Scraper str [a] #

many :: Scraper str a -> Scraper str [a] #

MonadPlus (Scraper str) 

Methods

mzero :: Scraper str a #

mplus :: Scraper str a -> Scraper str a -> Scraper str a #

Primitives

attr :: (Ord str, Show str, StringLike str) => String -> Selector -> Scraper str str #

The attr function takes an attribute name and a selector and returns the value of the attribute of the given name for the first opening tag that matches the given selector.

This function will match only the opening tag matching the selector, to match every tag, use attrs.

attrs :: (Ord str, Show str, StringLike str) => String -> Selector -> Scraper str [str] #

The attrs function takes an attribute name and a selector and returns the value of the attribute of the given name for every opening tag that matches the given selector.

html :: (Ord str, StringLike str) => Selector -> Scraper str str #

The html function takes a selector and returns the html string from the set of tags described by the given selector.

This function will match only the first set of tags matching the selector, to match every set of tags, use htmls.

htmls :: (Ord str, StringLike str) => Selector -> Scraper str [str] #

The htmls function takes a selector and returns the html string from every set of tags matching the given selector.

innerHTML :: (Ord str, StringLike str) => Selector -> Scraper str str #

The innerHTML function takes a selector and returns the inner html string from the set of tags described by the given selector. Inner html here meaning the html within but not including the selected tags.

This function will match only the first set of tags matching the selector, to match every set of tags, use innerHTMLs.

innerHTMLs :: (Ord str, StringLike str) => Selector -> Scraper str [str] #

The innerHTMLs function takes a selector and returns the inner html string from every set of tags matching the given selector.

text :: (Ord str, StringLike str) => Selector -> Scraper str str #

The text function takes a selector and returns the inner text from the set of tags described by the given selector.

This function will match only the first set of tags matching the selector, to match every set of tags, use texts.

texts :: (Ord str, StringLike str) => Selector -> Scraper str [str] #

The texts function takes a selector and returns the inner text from every set of tags matching the given selector.

chroot :: (Ord str, StringLike str) => Selector -> Scraper str a -> Scraper str a #

The chroot function takes a selector and an inner scraper and executes the inner scraper as if it were scraping a document that consists solely of the tags corresponding to the selector.

This function will match only the first set of tags matching the selector, to match every set of tags, use chroots.

chroots :: (Ord str, StringLike str) => Selector -> Scraper str a -> Scraper str [a] #

The chroots function takes a selector and an inner scraper and executes the inner scraper as if it were scraping a document that consists solely of the tags corresponding to the selector. The inner scraper is executed for each set of tags matching the given selector.

position :: (Ord str, StringLike str) => Scraper str Int #

The position function is intended to be used within the do-block of a chroots call. Within the do-block position will return the index of the current sub-tree within the list of all sub-trees matched by the selector passed to chroots.

For example, consider the following HTML:

<article>
 <p> First paragraph. </p>
 <p> Second paragraph. </p>
 <p> Third paragraph. </p>
</article>

The position function can be used to determine the index of each <p> tag within the article tag by doing the following.

chroots "article" // "p" $ do
  index   <- position
  content <- text "p"
  return (index, content)

Which will evaluate to the list:

[
  (0, "First paragraph.")
, (1, "Second paragraph.")
, (2, "Third paragraph.")
]

Executing scrapers

scrape :: (Ord str, StringLike str) => Scraper str a -> [Tag str] -> Maybe a #

The scrape function executes a Scraper on a list of Tags and produces an optional value.

scrapeStringLike :: (Ord str, StringLike str) => str -> Scraper str a -> Maybe a #

The scrapeStringLike function parses a StringLike value into a list of tags and executes a Scraper on it.

scrapeURL :: (Ord str, StringLike str) => URL -> Scraper str a -> IO (Maybe a) Source #

The scrapeURL function downloads the contents of the given URL and executes a Scraper on it.

scrapeURL makes use of curl to make HTTP requests. The dependency on curl may be too heavyweight for some use cases. In which case users who do not require inbuilt networking support can depend on scalpel-core for a lightweight subset of this library that does not depend on curl.

scrapeURLWithOpts :: (Ord str, StringLike str) => [CurlOption] -> URL -> Scraper str a -> IO (Maybe a) Source #

The scrapeURLWithOpts function take a list of curl options and downloads the contents of the given URL and executes a Scraper on it.

scrapeURLWithConfig :: (Ord str, StringLike str) => Config str -> URL -> Scraper str a -> IO (Maybe a) Source #

The scrapeURLWithConfig function takes a Config record type and downloads the contents of the given URL and executes a Scraper on it.

data Config str Source #

A record type that determines how scrapeUrlWithConfig interacts with the HTTP server and interprets the results.

Constructors

Config 

Fields

Instances

StringLike str => Default (Config str) Source # 

Methods

def :: Config str #

type Decoder str = CurlResponse_ [(String, String)] ByteString -> str Source #

A method that takes a HTTP response as raw bytes and returns the body as a string type.

defaultDecoder :: StringLike str => Decoder str Source #

The default response decoder. This decoder attempts to infer the character set of the HTTP response body from the `Content-Type` header. If this header is not present, then the character set is assumed to be `ISO-8859-1`.

utf8Decoder :: StringLike str => Decoder str Source #

A decoder that will always decode using `UTF-8`.

iso88591Decoder :: StringLike str => Decoder str Source #

A decoder that will always decode using `ISO-8859-1`.