tagsoup-navigate-0.1.0.4: Tagsoup Navigate

Safe HaskellNone
LanguageHaskell2010

Text.HTML.TagSoup.Navigate.Types.TagTreePosState

Synopsis

Documentation

newtype TagTreePosStateT str f a Source #

Constructors

TagTreePosStateT (TagTreePos str -> f (Maybe (TagTreePos str, a))) 
Instances
MonadTrans (TagTreePosStateT str) Source # 
Instance details

Defined in Text.HTML.TagSoup.Navigate.Types.TagTreePosState

Methods

lift :: Monad m => m a -> TagTreePosStateT str m a #

MFunctor (TagTreePosStateT str :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Text.HTML.TagSoup.Navigate.Types.TagTreePosState

Methods

hoist :: Monad m => (forall a. m a -> n a) -> TagTreePosStateT str m b -> TagTreePosStateT str n b #

Monad f => MonadReader (TagTreePos str) (TagTreePosStateT str f) Source # 
Instance details

Defined in Text.HTML.TagSoup.Navigate.Types.TagTreePosState

Methods

ask :: TagTreePosStateT str f (TagTreePos str) #

local :: (TagTreePos str -> TagTreePos str) -> TagTreePosStateT str f a -> TagTreePosStateT str f a #

reader :: (TagTreePos str -> a) -> TagTreePosStateT str f a #

Monad f => MonadState (TagTreePos str) (TagTreePosStateT str f) Source # 
Instance details

Defined in Text.HTML.TagSoup.Navigate.Types.TagTreePosState

Methods

get :: TagTreePosStateT str f (TagTreePos str) #

put :: TagTreePos str -> TagTreePosStateT str f () #

state :: (TagTreePos str -> (a, TagTreePos str)) -> TagTreePosStateT str f a #

Monad f => Monad (TagTreePosStateT str f) Source # 
Instance details

Defined in Text.HTML.TagSoup.Navigate.Types.TagTreePosState

Methods

(>>=) :: TagTreePosStateT str f a -> (a -> TagTreePosStateT str f b) -> TagTreePosStateT str f b #

(>>) :: TagTreePosStateT str f a -> TagTreePosStateT str f b -> TagTreePosStateT str f b #

return :: a -> TagTreePosStateT str f a #

fail :: String -> TagTreePosStateT str f a #

Functor f => Functor (TagTreePosStateT str f) Source # 
Instance details

Defined in Text.HTML.TagSoup.Navigate.Types.TagTreePosState

Methods

fmap :: (a -> b) -> TagTreePosStateT str f a -> TagTreePosStateT str f b #

(<$) :: a -> TagTreePosStateT str f b -> TagTreePosStateT str f a #

Monad f => Applicative (TagTreePosStateT str f) Source # 
Instance details

Defined in Text.HTML.TagSoup.Navigate.Types.TagTreePosState

Methods

pure :: a -> TagTreePosStateT str f a #

(<*>) :: TagTreePosStateT str f (a -> b) -> TagTreePosStateT str f a -> TagTreePosStateT str f b #

liftA2 :: (a -> b -> c) -> TagTreePosStateT str f a -> TagTreePosStateT str f b -> TagTreePosStateT str f c #

(*>) :: TagTreePosStateT str f a -> TagTreePosStateT str f b -> TagTreePosStateT str f b #

(<*) :: TagTreePosStateT str f a -> TagTreePosStateT str f b -> TagTreePosStateT str f a #

MonadIO f => MonadIO (TagTreePosStateT str f) Source # 
Instance details

Defined in Text.HTML.TagSoup.Navigate.Types.TagTreePosState

Methods

liftIO :: IO a -> TagTreePosStateT str f a #

Monad f => Alternative (TagTreePosStateT str f) Source # 
Instance details

Defined in Text.HTML.TagSoup.Navigate.Types.TagTreePosState

Methods

empty :: TagTreePosStateT str f a #

(<|>) :: TagTreePosStateT str f a -> TagTreePosStateT str f a -> TagTreePosStateT str f a #

some :: TagTreePosStateT str f a -> TagTreePosStateT str f [a] #

many :: TagTreePosStateT str f a -> TagTreePosStateT str f [a] #

Monad f => Apply (TagTreePosStateT str f) Source # 
Instance details

Defined in Text.HTML.TagSoup.Navigate.Types.TagTreePosState

Methods

(<.>) :: TagTreePosStateT str f (a -> b) -> TagTreePosStateT str f a -> TagTreePosStateT str f b #

(.>) :: TagTreePosStateT str f a -> TagTreePosStateT str f b -> TagTreePosStateT str f b #

(<.) :: TagTreePosStateT str f a -> TagTreePosStateT str f b -> TagTreePosStateT str f a #

liftF2 :: (a -> b -> c) -> TagTreePosStateT str f a -> TagTreePosStateT str f b -> TagTreePosStateT str f c #

Monad f => Alt (TagTreePosStateT str f) Source # 
Instance details

Defined in Text.HTML.TagSoup.Navigate.Types.TagTreePosState

Methods

(<!>) :: TagTreePosStateT str f a -> TagTreePosStateT str f a -> TagTreePosStateT str f a #

some :: Applicative (TagTreePosStateT str f) => TagTreePosStateT str f a -> TagTreePosStateT str f [a] #

many :: Applicative (TagTreePosStateT str f) => TagTreePosStateT str f a -> TagTreePosStateT str f [a] #

Monad f => Bind (TagTreePosStateT str f) Source # 
Instance details

Defined in Text.HTML.TagSoup.Navigate.Types.TagTreePosState

Methods

(>>-) :: TagTreePosStateT str f a -> (a -> TagTreePosStateT str f b) -> TagTreePosStateT str f b #

join :: TagTreePosStateT str f (TagTreePosStateT str f a) -> TagTreePosStateT str f a #

(Monad f, Semigroup a) => Semigroup (TagTreePosStateT str f a) Source # 
Instance details

Defined in Text.HTML.TagSoup.Navigate.Types.TagTreePosState

Methods

(<>) :: TagTreePosStateT str f a -> TagTreePosStateT str f a -> TagTreePosStateT str f a #

sconcat :: NonEmpty (TagTreePosStateT str f a) -> TagTreePosStateT str f a #

stimes :: Integral b => b -> TagTreePosStateT str f a -> TagTreePosStateT str f a #

(Monad f, Monoid a) => Monoid (TagTreePosStateT str f a) Source # 
Instance details

Defined in Text.HTML.TagSoup.Navigate.Types.TagTreePosState

Methods

mempty :: TagTreePosStateT str f a #

mappend :: TagTreePosStateT str f a -> TagTreePosStateT str f a -> TagTreePosStateT str f a #

mconcat :: [TagTreePosStateT str f a] -> TagTreePosStateT str f a #

Wrapped (TagTreePosStateT str f a) Source # 
Instance details

Defined in Text.HTML.TagSoup.Navigate.Types.TagTreePosState

Associated Types

type Unwrapped (TagTreePosStateT str f a) :: Type #

Methods

_Wrapped' :: Iso' (TagTreePosStateT str f a) (Unwrapped (TagTreePosStateT str f a)) #

TagTreePosStateT str f a ~ t => Rewrapped (TagTreePosStateT str f' a') t Source # 
Instance details

Defined in Text.HTML.TagSoup.Navigate.Types.TagTreePosState

type Unwrapped (TagTreePosStateT str f a) Source # 
Instance details

Defined in Text.HTML.TagSoup.Navigate.Types.TagTreePosState

type Unwrapped (TagTreePosStateT str f a) = TagTreePos str -> f (Maybe (TagTreePos str, a))

opticContent :: ((a -> Const (First a) a) -> TagTree str -> Const (First a) (TagTree str)) -> TagTreePosState str a Source #

findTreeT :: Monad f => TagTreePosStateT str f a -> TagTreePosStateT str f b -> (TagTree str -> f Bool) -> TagTreePosStateT str f () Source #

findTree :: TagTreePosState str () -> TagTreePosState str () -> (TagTree str -> Bool) -> TagTreePosState str () Source #

tagBranchLeafText :: TagTreePosState a (a, a) Source #

produces `(x, t)` in `TagBranch x _ [TagLeaf (TagText t)]`