{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE CPP #-}
{-# OPTIONS_HADDOCK hide #-}
module Text.HTML.Scalpel.Internal.Scrape (
Scraper
, ScraperT (..)
, scrape
, scrapeT
, attr
, attrs
, html
, htmls
, innerHTML
, innerHTMLs
, text
, texts
, chroot
, chroots
, matches
, position
) where
import Text.HTML.Scalpel.Internal.Select
import Text.HTML.Scalpel.Internal.Select.Types
import Control.Applicative
import Control.Monad
import Control.Monad.Except (MonadError)
import Control.Monad.Cont (MonadCont)
import Control.Monad.Reader
import Control.Monad.State (MonadState)
import Control.Monad.Trans.Maybe
import Control.Monad.Writer (MonadWriter)
import Control.Monad.Fix
import Data.Functor.Identity
import Data.Maybe
import qualified Control.Monad.Fail as Fail
import qualified Data.Vector as Vector
import qualified Text.HTML.TagSoup as TagSoup
import qualified Text.StringLike as TagSoup
newtype ScraperT str m a = MkScraper (ReaderT (TagSpec str) (MaybeT m) a)
deriving (forall a b. a -> ScraperT str m b -> ScraperT str m a
forall a b. (a -> b) -> ScraperT str m a -> ScraperT str m b
forall str (m :: * -> *) a b.
Functor m =>
a -> ScraperT str m b -> ScraperT str m a
forall str (m :: * -> *) a b.
Functor m =>
(a -> b) -> ScraperT str m a -> ScraperT str m b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: forall a b. a -> ScraperT str m b -> ScraperT str m a
$c<$ :: forall str (m :: * -> *) a b.
Functor m =>
a -> ScraperT str m b -> ScraperT str m a
fmap :: forall a b. (a -> b) -> ScraperT str m a -> ScraperT str m b
$cfmap :: forall str (m :: * -> *) a b.
Functor m =>
(a -> b) -> ScraperT str m a -> ScraperT str m b
Functor, forall a. a -> ScraperT str m a
forall a b.
ScraperT str m a -> ScraperT str m b -> ScraperT str m a
forall a b.
ScraperT str m a -> ScraperT str m b -> ScraperT str m b
forall a b.
ScraperT str m (a -> b) -> ScraperT str m a -> ScraperT str m b
forall a b c.
(a -> b -> c)
-> ScraperT str m a -> ScraperT str m b -> ScraperT str m c
forall {str} {m :: * -> *}. Monad m => Functor (ScraperT str m)
forall str (m :: * -> *) a. Monad m => a -> ScraperT str m a
forall str (m :: * -> *) a b.
Monad m =>
ScraperT str m a -> ScraperT str m b -> ScraperT str m a
forall str (m :: * -> *) a b.
Monad m =>
ScraperT str m a -> ScraperT str m b -> ScraperT str m b
forall str (m :: * -> *) a b.
Monad m =>
ScraperT str m (a -> b) -> ScraperT str m a -> ScraperT str m b
forall str (m :: * -> *) a b c.
Monad m =>
(a -> b -> c)
-> ScraperT str m a -> ScraperT str m b -> ScraperT str m c
forall (f :: * -> *).
Functor f
-> (forall a. a -> f a)
-> (forall a b. f (a -> b) -> f a -> f b)
-> (forall a b c. (a -> b -> c) -> f a -> f b -> f c)
-> (forall a b. f a -> f b -> f b)
-> (forall a b. f a -> f b -> f a)
-> Applicative f
<* :: forall a b.
ScraperT str m a -> ScraperT str m b -> ScraperT str m a
$c<* :: forall str (m :: * -> *) a b.
Monad m =>
ScraperT str m a -> ScraperT str m b -> ScraperT str m a
*> :: forall a b.
ScraperT str m a -> ScraperT str m b -> ScraperT str m b
$c*> :: forall str (m :: * -> *) a b.
Monad m =>
ScraperT str m a -> ScraperT str m b -> ScraperT str m b
liftA2 :: forall a b c.
(a -> b -> c)
-> ScraperT str m a -> ScraperT str m b -> ScraperT str m c
$cliftA2 :: forall str (m :: * -> *) a b c.
Monad m =>
(a -> b -> c)
-> ScraperT str m a -> ScraperT str m b -> ScraperT str m c
<*> :: forall a b.
ScraperT str m (a -> b) -> ScraperT str m a -> ScraperT str m b
$c<*> :: forall str (m :: * -> *) a b.
Monad m =>
ScraperT str m (a -> b) -> ScraperT str m a -> ScraperT str m b
pure :: forall a. a -> ScraperT str m a
$cpure :: forall str (m :: * -> *) a. Monad m => a -> ScraperT str m a
Applicative, forall a. ScraperT str m a
forall a. ScraperT str m a -> ScraperT str m [a]
forall a. ScraperT str m a -> ScraperT str m a -> ScraperT str m a
forall str (m :: * -> *). Monad m => Applicative (ScraperT str m)
forall str (m :: * -> *) a. Monad m => ScraperT str m a
forall str (m :: * -> *) a.
Monad m =>
ScraperT str m a -> ScraperT str m [a]
forall str (m :: * -> *) a.
Monad m =>
ScraperT str m a -> ScraperT str m a -> ScraperT str m a
forall (f :: * -> *).
Applicative f
-> (forall a. f a)
-> (forall a. f a -> f a -> f a)
-> (forall a. f a -> f [a])
-> (forall a. f a -> f [a])
-> Alternative f
many :: forall a. ScraperT str m a -> ScraperT str m [a]
$cmany :: forall str (m :: * -> *) a.
Monad m =>
ScraperT str m a -> ScraperT str m [a]
some :: forall a. ScraperT str m a -> ScraperT str m [a]
$csome :: forall str (m :: * -> *) a.
Monad m =>
ScraperT str m a -> ScraperT str m [a]
<|> :: forall a. ScraperT str m a -> ScraperT str m a -> ScraperT str m a
$c<|> :: forall str (m :: * -> *) a.
Monad m =>
ScraperT str m a -> ScraperT str m a -> ScraperT str m a
empty :: forall a. ScraperT str m a
$cempty :: forall str (m :: * -> *) a. Monad m => ScraperT str m a
Alternative, forall a. a -> ScraperT str m a
forall a b.
ScraperT str m a -> ScraperT str m b -> ScraperT str m b
forall a b.
ScraperT str m a -> (a -> ScraperT str m b) -> ScraperT str m b
forall str (m :: * -> *). Monad m => Applicative (ScraperT str m)
forall str (m :: * -> *) a. Monad m => a -> ScraperT str m a
forall str (m :: * -> *) a b.
Monad m =>
ScraperT str m a -> ScraperT str m b -> ScraperT str m b
forall str (m :: * -> *) a b.
Monad m =>
ScraperT str m a -> (a -> ScraperT str m b) -> ScraperT str m b
forall (m :: * -> *).
Applicative m
-> (forall a b. m a -> (a -> m b) -> m b)
-> (forall a b. m a -> m b -> m b)
-> (forall a. a -> m a)
-> Monad m
return :: forall a. a -> ScraperT str m a
$creturn :: forall str (m :: * -> *) a. Monad m => a -> ScraperT str m a
>> :: forall a b.
ScraperT str m a -> ScraperT str m b -> ScraperT str m b
$c>> :: forall str (m :: * -> *) a b.
Monad m =>
ScraperT str m a -> ScraperT str m b -> ScraperT str m b
>>= :: forall a b.
ScraperT str m a -> (a -> ScraperT str m b) -> ScraperT str m b
$c>>= :: forall str (m :: * -> *) a b.
Monad m =>
ScraperT str m a -> (a -> ScraperT str m b) -> ScraperT str m b
Monad, forall a. ScraperT str m a
forall a. ScraperT str m a -> ScraperT str m a -> ScraperT str m a
forall str (m :: * -> *). Monad m => Monad (ScraperT str m)
forall str (m :: * -> *). Monad m => Alternative (ScraperT str m)
forall str (m :: * -> *) a. Monad m => ScraperT str m a
forall str (m :: * -> *) a.
Monad m =>
ScraperT str m a -> ScraperT str m a -> ScraperT str m a
forall (m :: * -> *).
Alternative m
-> Monad m
-> (forall a. m a)
-> (forall a. m a -> m a -> m a)
-> MonadPlus m
mplus :: forall a. ScraperT str m a -> ScraperT str m a -> ScraperT str m a
$cmplus :: forall str (m :: * -> *) a.
Monad m =>
ScraperT str m a -> ScraperT str m a -> ScraperT str m a
mzero :: forall a. ScraperT str m a
$cmzero :: forall str (m :: * -> *) a. Monad m => ScraperT str m a
MonadPlus, forall a. (a -> ScraperT str m a) -> ScraperT str m a
forall {str} {m :: * -> *}. MonadFix m => Monad (ScraperT str m)
forall str (m :: * -> *) a.
MonadFix m =>
(a -> ScraperT str m a) -> ScraperT str m a
forall (m :: * -> *).
Monad m -> (forall a. (a -> m a) -> m a) -> MonadFix m
mfix :: forall a. (a -> ScraperT str m a) -> ScraperT str m a
$cmfix :: forall str (m :: * -> *) a.
MonadFix m =>
(a -> ScraperT str m a) -> ScraperT str m a
MonadFix,
forall a. IO a -> ScraperT str m a
forall {str} {m :: * -> *}. MonadIO m => Monad (ScraperT str m)
forall str (m :: * -> *) a. MonadIO m => IO a -> ScraperT str m a
forall (m :: * -> *).
Monad m -> (forall a. IO a -> m a) -> MonadIO m
liftIO :: forall a. IO a -> ScraperT str m a
$cliftIO :: forall str (m :: * -> *) a. MonadIO m => IO a -> ScraperT str m a
MonadIO, forall a b.
((a -> ScraperT str m b) -> ScraperT str m a) -> ScraperT str m a
forall {str} {m :: * -> *}. MonadCont m => Monad (ScraperT str m)
forall str (m :: * -> *) a b.
MonadCont m =>
((a -> ScraperT str m b) -> ScraperT str m a) -> ScraperT str m a
forall (m :: * -> *).
Monad m -> (forall a b. ((a -> m b) -> m a) -> m a) -> MonadCont m
callCC :: forall a b.
((a -> ScraperT str m b) -> ScraperT str m a) -> ScraperT str m a
$ccallCC :: forall str (m :: * -> *) a b.
MonadCont m =>
((a -> ScraperT str m b) -> ScraperT str m a) -> ScraperT str m a
MonadCont, MonadError e, MonadState s, MonadWriter w)
#if MIN_VERSION_base(4,9,0)
deriving instance Monad m => Fail.MonadFail (ScraperT str m)
#else
instance Fail.MonadFail m => Fail.MonadFail (ScraperT str m) where
fail = lift . Fail.fail
#endif
instance MonadTrans (ScraperT str) where
lift :: forall (m :: * -> *) a. Monad m => m a -> ScraperT str m a
lift m a
op = forall str (m :: * -> *) a.
ReaderT (TagSpec str) (MaybeT m) a -> ScraperT str m a
MkScraper forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ m a
op
instance MonadReader s m => MonadReader s (ScraperT str m) where
ask :: ScraperT str m s
ask = forall str (m :: * -> *) a.
ReaderT (TagSpec str) (MaybeT m) a -> ScraperT str m a
MkScraper (forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall r (m :: * -> *). MonadReader r m => m r
ask)
local :: forall a. (s -> s) -> ScraperT str m a -> ScraperT str m a
local s -> s
f (MkScraper ReaderT (TagSpec str) (MaybeT m) a
op) = (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall str (m :: * -> *) a.
ReaderT (TagSpec str) (MaybeT m) a -> ScraperT str m a
MkScraper forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) a (n :: * -> *) b r.
(m a -> n b) -> ReaderT r m a -> ReaderT r n b
mapReaderT forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall r (m :: * -> *) a. MonadReader r m => (r -> r) -> m a -> m a
local) s -> s
f ReaderT (TagSpec str) (MaybeT m) a
op
type Scraper str = ScraperT str Identity
scrapeTagSpec :: ScraperT str m a -> TagSpec str -> m (Maybe a)
scrapeTagSpec :: forall str (m :: * -> *) a.
ScraperT str m a -> TagSpec str -> m (Maybe a)
scrapeTagSpec (MkScraper ReaderT (TagSpec str) (MaybeT m) a
r) = forall (m :: * -> *) a. MaybeT m a -> m (Maybe a)
runMaybeT forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT ReaderT (TagSpec str) (MaybeT m) a
r
scrapeT :: (TagSoup.StringLike str)
=> ScraperT str m a -> [TagSoup.Tag str] -> m (Maybe a)
scrapeT :: forall str (m :: * -> *) a.
StringLike str =>
ScraperT str m a -> [Tag str] -> m (Maybe a)
scrapeT ScraperT str m a
s = forall str (m :: * -> *) a.
ScraperT str m a -> TagSpec str -> m (Maybe a)
scrapeTagSpec ScraperT str m a
s forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall str. StringLike str => [Tag str] -> TagSpec str
tagsToSpec forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall str. StringLike str => [Tag str] -> [Tag str]
TagSoup.canonicalizeTags
scrape :: (TagSoup.StringLike str)
=> Scraper str a -> [TagSoup.Tag str] -> Maybe a
scrape :: forall str a.
StringLike str =>
Scraper str a -> [Tag str] -> Maybe a
scrape = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Identity a -> a
runIdentity forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall str (m :: * -> *) a.
StringLike str =>
ScraperT str m a -> [Tag str] -> m (Maybe a)
scrapeT
chroot :: (TagSoup.StringLike str, Monad m)
=> Selector -> ScraperT str m a -> ScraperT str m a
chroot :: forall str (m :: * -> *) a.
(StringLike str, Monad m) =>
Selector -> ScraperT str m a -> ScraperT str m a
chroot Selector
selector ScraperT str m a
inner = do
Maybe a
maybeResult <- forall a. [a] -> Maybe a
listToMaybe forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall str (m :: * -> *) a.
(StringLike str, Monad m) =>
Selector -> ScraperT str m a -> ScraperT str m [a]
chroots Selector
selector ScraperT str m a
inner
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (forall a. Maybe a -> Bool
isJust Maybe a
maybeResult)
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a. HasCallStack => Maybe a -> a
fromJust Maybe a
maybeResult
chroots :: (TagSoup.StringLike str, Monad m)
=> Selector -> ScraperT str m a -> ScraperT str m [a]
chroots :: forall str (m :: * -> *) a.
(StringLike str, Monad m) =>
Selector -> ScraperT str m a -> ScraperT str m [a]
chroots Selector
selector (MkScraper (ReaderT TagSpec str -> MaybeT m a
inner)) =
forall str (m :: * -> *) a.
ReaderT (TagSpec str) (MaybeT m) a -> ScraperT str m a
MkScraper forall a b. (a -> b) -> a -> b
$ forall r (m :: * -> *) a. (r -> m a) -> ReaderT r m a
ReaderT forall a b. (a -> b) -> a -> b
$ \TagSpec str
tags -> forall (m :: * -> *) a. m (Maybe a) -> MaybeT m a
MaybeT forall a b. (a -> b) -> a -> b
$ do
[Maybe a]
mvalues <- forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM (forall str.
StringLike str =>
Selector -> TagSpec str -> [TagSpec str]
select Selector
selector TagSpec str
tags) (forall (m :: * -> *) a. MaybeT m a -> m (Maybe a)
runMaybeT forall b c a. (b -> c) -> (a -> b) -> a -> c
. TagSpec str -> MaybeT m a
inner)
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall a. [Maybe a] -> [a]
catMaybes [Maybe a]
mvalues
matches :: (TagSoup.StringLike str, Monad m) => Selector -> ScraperT str m ()
matches :: forall str (m :: * -> *).
(StringLike str, Monad m) =>
Selector -> ScraperT str m ()
matches Selector
s = forall str (m :: * -> *) a.
ReaderT (TagSpec str) (MaybeT m) a -> ScraperT str m a
MkScraper forall a b. (a -> b) -> a -> b
$ (forall (f :: * -> *). Alternative f => Bool -> f ()
guard forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. Foldable t => t a -> Bool
null) forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
reader (forall str.
StringLike str =>
Selector -> TagSpec str -> [TagSpec str]
select Selector
s)
text :: (TagSoup.StringLike str, Monad m) => Selector -> ScraperT str m str
text :: forall str (m :: * -> *).
(StringLike str, Monad m) =>
Selector -> ScraperT str m str
text Selector
s = forall str (m :: * -> *) a.
ReaderT (TagSpec str) (MaybeT m) a -> ScraperT str m a
MkScraper forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a b str.
Monad m =>
(a -> b) -> [a] -> ReaderT (TagSpec str) (MaybeT m) b
withHead forall str. StringLike str => TagSpec str -> str
tagsToText forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
reader (forall str.
StringLike str =>
Selector -> TagSpec str -> [TagSpec str]
select Selector
s)
texts :: (TagSoup.StringLike str, Monad m)
=> Selector -> ScraperT str m [str]
texts :: forall str (m :: * -> *).
(StringLike str, Monad m) =>
Selector -> ScraperT str m [str]
texts Selector
s = forall str (m :: * -> *) a.
ReaderT (TagSpec str) (MaybeT m) a -> ScraperT str m a
MkScraper forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a b str.
Monad m =>
(a -> b) -> [a] -> ReaderT (TagSpec str) (MaybeT m) [b]
withAll forall str. StringLike str => TagSpec str -> str
tagsToText forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
reader (forall str.
StringLike str =>
Selector -> TagSpec str -> [TagSpec str]
select Selector
s)
html :: (TagSoup.StringLike str, Monad m) => Selector -> ScraperT str m str
html :: forall str (m :: * -> *).
(StringLike str, Monad m) =>
Selector -> ScraperT str m str
html Selector
s = forall str (m :: * -> *) a.
ReaderT (TagSpec str) (MaybeT m) a -> ScraperT str m a
MkScraper forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a b str.
Monad m =>
(a -> b) -> [a] -> ReaderT (TagSpec str) (MaybeT m) b
withHead forall str. StringLike str => TagSpec str -> str
tagsToHTML forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
reader (forall str.
StringLike str =>
Selector -> TagSpec str -> [TagSpec str]
select Selector
s)
htmls :: (TagSoup.StringLike str, Monad m)
=> Selector -> ScraperT str m [str]
htmls :: forall str (m :: * -> *).
(StringLike str, Monad m) =>
Selector -> ScraperT str m [str]
htmls Selector
s = forall str (m :: * -> *) a.
ReaderT (TagSpec str) (MaybeT m) a -> ScraperT str m a
MkScraper forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a b str.
Monad m =>
(a -> b) -> [a] -> ReaderT (TagSpec str) (MaybeT m) [b]
withAll forall str. StringLike str => TagSpec str -> str
tagsToHTML forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
reader (forall str.
StringLike str =>
Selector -> TagSpec str -> [TagSpec str]
select Selector
s)
innerHTML :: (TagSoup.StringLike str, Monad m)
=> Selector -> ScraperT str m str
innerHTML :: forall str (m :: * -> *).
(StringLike str, Monad m) =>
Selector -> ScraperT str m str
innerHTML Selector
s = forall str (m :: * -> *) a.
ReaderT (TagSpec str) (MaybeT m) a -> ScraperT str m a
MkScraper forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a b str.
Monad m =>
(a -> b) -> [a] -> ReaderT (TagSpec str) (MaybeT m) b
withHead forall str. StringLike str => TagSpec str -> str
tagsToInnerHTML forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
reader (forall str.
StringLike str =>
Selector -> TagSpec str -> [TagSpec str]
select Selector
s)
innerHTMLs :: (TagSoup.StringLike str, Monad m)
=> Selector -> ScraperT str m [str]
innerHTMLs :: forall str (m :: * -> *).
(StringLike str, Monad m) =>
Selector -> ScraperT str m [str]
innerHTMLs Selector
s = forall str (m :: * -> *) a.
ReaderT (TagSpec str) (MaybeT m) a -> ScraperT str m a
MkScraper forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a b str.
Monad m =>
(a -> b) -> [a] -> ReaderT (TagSpec str) (MaybeT m) [b]
withAll forall str. StringLike str => TagSpec str -> str
tagsToInnerHTML forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
reader (forall str.
StringLike str =>
Selector -> TagSpec str -> [TagSpec str]
select Selector
s)
attr :: (Show str, TagSoup.StringLike str, Monad m)
=> String -> Selector -> ScraperT str m str
attr :: forall str (m :: * -> *).
(Show str, StringLike str, Monad m) =>
String -> Selector -> ScraperT str m str
attr String
name Selector
s = forall str (m :: * -> *) a.
ReaderT (TagSpec str) (MaybeT m) a -> ScraperT str m a
MkScraper forall a b. (a -> b) -> a -> b
$ forall r (m :: * -> *) a. (r -> m a) -> ReaderT r m a
ReaderT forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. m (Maybe a) -> MaybeT m a
MaybeT
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) a. Monad m => a -> m a
return forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> Maybe a
listToMaybe forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [Maybe a] -> [a]
catMaybes
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall str.
(Show str, StringLike str) =>
str -> TagSpec str -> Maybe str
tagsToAttr forall a b. (a -> b) -> a -> b
$ forall a b. (StringLike a, StringLike b) => a -> b
TagSoup.castString String
name) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall str.
StringLike str =>
Selector -> TagSpec str -> [TagSpec str]
select Selector
s
attrs :: (Show str, TagSoup.StringLike str, Monad m)
=> String -> Selector -> ScraperT str m [str]
attrs :: forall str (m :: * -> *).
(Show str, StringLike str, Monad m) =>
String -> Selector -> ScraperT str m [str]
attrs String
name Selector
s = forall str (m :: * -> *) a.
ReaderT (TagSpec str) (MaybeT m) a -> ScraperT str m a
MkScraper forall a b. (a -> b) -> a -> b
$ forall r (m :: * -> *) a. (r -> m a) -> ReaderT r m a
ReaderT forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. m (Maybe a) -> MaybeT m a
MaybeT
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) a. Monad m => a -> m a
return forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. a -> Maybe a
Just forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [Maybe a] -> [a]
catMaybes
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall str.
(Show str, StringLike str) =>
str -> TagSpec str -> Maybe str
tagsToAttr str
nameStr) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall str.
StringLike str =>
Selector -> TagSpec str -> [TagSpec str]
select Selector
s
where nameStr :: str
nameStr = forall a b. (StringLike a, StringLike b) => a -> b
TagSoup.castString String
name
position :: (TagSoup.StringLike str, Monad m) => ScraperT str m Int
position :: forall str (m :: * -> *).
(StringLike str, Monad m) =>
ScraperT str m Int
position = forall str (m :: * -> *) a.
ReaderT (TagSpec str) (MaybeT m) a -> ScraperT str m a
MkScraper forall a b. (a -> b) -> a -> b
$ forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
reader forall str. TagSpec str -> Int
tagsToPosition
withHead :: Monad m => (a -> b) -> [a] -> ReaderT (TagSpec str) (MaybeT m) b
withHead :: forall (m :: * -> *) a b str.
Monad m =>
(a -> b) -> [a] -> ReaderT (TagSpec str) (MaybeT m) b
withHead a -> b
_ [] = forall (f :: * -> *) a. Alternative f => f a
empty
withHead a -> b
f (a
x:[a]
_) = forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ a -> b
f a
x
withAll :: Monad m => (a -> b) -> [a] -> ReaderT (TagSpec str) (MaybeT m) [b]
withAll :: forall (m :: * -> *) a b str.
Monad m =>
(a -> b) -> [a] -> ReaderT (TagSpec str) (MaybeT m) [b]
withAll a -> b
f [a]
xs = forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map a -> b
f [a]
xs
foldSpec :: TagSoup.StringLike str
=> (TagSoup.Tag str -> str -> str) -> TagSpec str -> str
foldSpec :: forall str.
StringLike str =>
(Tag str -> str -> str) -> TagSpec str -> str
foldSpec Tag str -> str -> str
f = forall a b. (a -> b -> b) -> b -> Vector a -> b
Vector.foldr' (Tag str -> str -> str
f forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall str. TagInfo str -> Tag str
infoTag) forall a. StringLike a => a
TagSoup.empty forall b c a. (b -> c) -> (a -> b) -> a -> c
. (\(Vector (TagInfo str)
a, TagForest
_, SelectContext
_) -> Vector (TagInfo str)
a)
tagsToText :: TagSoup.StringLike str => TagSpec str -> str
tagsToText :: forall str. StringLike str => TagSpec str -> str
tagsToText = forall str.
StringLike str =>
(Tag str -> str -> str) -> TagSpec str -> str
foldSpec forall {a}. StringLike a => Tag a -> a -> a
f
where
f :: Tag a -> a -> a
f (TagSoup.TagText a
str) a
s = a
str forall a. StringLike a => a -> a -> a
`TagSoup.append` a
s
f Tag a
_ a
s = a
s
tagsToHTML :: TagSoup.StringLike str => TagSpec str -> str
tagsToHTML :: forall str. StringLike str => TagSpec str -> str
tagsToHTML = forall str.
StringLike str =>
(Tag str -> str -> str) -> TagSpec str -> str
foldSpec (\Tag str
tag str
s -> forall str. StringLike str => [Tag str] -> str
TagSoup.renderTags [Tag str
tag] forall a. StringLike a => a -> a -> a
`TagSoup.append` str
s)
tagsToInnerHTML :: TagSoup.StringLike str => TagSpec str -> str
tagsToInnerHTML :: forall str. StringLike str => TagSpec str -> str
tagsToInnerHTML (TagVector str
tags, TagForest
tree, SelectContext
ctx)
| Int
len forall a. Ord a => a -> a -> Bool
< Int
2 = forall a. StringLike a => a
TagSoup.empty
| Bool
otherwise = forall str. StringLike str => TagSpec str -> str
tagsToHTML (forall a. Int -> Int -> Vector a -> Vector a
Vector.slice Int
1 (Int
len forall a. Num a => a -> a -> a
- Int
2) TagVector str
tags, TagForest
tree, SelectContext
ctx)
where len :: Int
len = forall a. Vector a -> Int
Vector.length TagVector str
tags
tagsToAttr :: (Show str, TagSoup.StringLike str)
=> str -> TagSpec str -> Maybe str
tagsToAttr :: forall str.
(Show str, StringLike str) =>
str -> TagSpec str -> Maybe str
tagsToAttr str
tagName (TagVector str
tags, TagForest
_, SelectContext
_) = do
forall (f :: * -> *). Alternative f => Bool -> f ()
guard forall a b. (a -> b) -> a -> b
$ Int
0 forall a. Ord a => a -> a -> Bool
< forall a. Vector a -> Int
Vector.length TagVector str
tags
let tag :: Tag str
tag = forall str. TagInfo str -> Tag str
infoTag forall a b. (a -> b) -> a -> b
$ TagVector str
tags forall a. Vector a -> Int -> a
Vector.! Int
0
forall (f :: * -> *). Alternative f => Bool -> f ()
guard forall a b. (a -> b) -> a -> b
$ forall str. Tag str -> Bool
TagSoup.isTagOpen Tag str
tag
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall str.
(Show str, Eq str, StringLike str) =>
str -> Tag str -> str
TagSoup.fromAttrib str
tagName Tag str
tag
tagsToPosition :: TagSpec str -> Int
tagsToPosition :: forall str. TagSpec str -> Int
tagsToPosition (TagVector str
_, TagForest
_, SelectContext
ctx) = SelectContext -> Int
ctxPosition SelectContext
ctx