tagsoup-navigate-0.1.0.7: Tagsoup Navigate

Safe HaskellNone
LanguageHaskell2010

Text.HTML.TagSoup.Navigate.Types.Attribute

Synopsis

Documentation

data Attribute str Source #

Constructors

Attribute str str 
Instances
Monad Attribute Source # 
Instance details

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

Methods

(>>=) :: Attribute a -> (a -> Attribute b) -> Attribute b #

(>>) :: Attribute a -> Attribute b -> Attribute b #

return :: a -> Attribute a #

fail :: String -> Attribute a #

Functor Attribute Source # 
Instance details

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

Methods

fmap :: (a -> b) -> Attribute a -> Attribute b #

(<$) :: a -> Attribute b -> Attribute a #

Applicative Attribute Source # 
Instance details

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

Methods

pure :: a -> Attribute a #

(<*>) :: Attribute (a -> b) -> Attribute a -> Attribute b #

liftA2 :: (a -> b -> c) -> Attribute a -> Attribute b -> Attribute c #

(*>) :: Attribute a -> Attribute b -> Attribute b #

(<*) :: Attribute a -> Attribute b -> Attribute a #

Foldable Attribute Source # 
Instance details

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

Methods

fold :: Monoid m => Attribute m -> m #

foldMap :: Monoid m => (a -> m) -> Attribute a -> m #

foldr :: (a -> b -> b) -> b -> Attribute a -> b #

foldr' :: (a -> b -> b) -> b -> Attribute a -> b #

foldl :: (b -> a -> b) -> b -> Attribute a -> b #

foldl' :: (b -> a -> b) -> b -> Attribute a -> b #

foldr1 :: (a -> a -> a) -> Attribute a -> a #

foldl1 :: (a -> a -> a) -> Attribute a -> a #

toList :: Attribute a -> [a] #

null :: Attribute a -> Bool #

length :: Attribute a -> Int #

elem :: Eq a => a -> Attribute a -> Bool #

maximum :: Ord a => Attribute a -> a #

minimum :: Ord a => Attribute a -> a #

sum :: Num a => Attribute a -> a #

product :: Num a => Attribute a -> a #

Traversable Attribute Source # 
Instance details

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

Methods

traverse :: Applicative f => (a -> f b) -> Attribute a -> f (Attribute b) #

sequenceA :: Applicative f => Attribute (f a) -> f (Attribute a) #

mapM :: Monad m => (a -> m b) -> Attribute a -> m (Attribute b) #

sequence :: Monad m => Attribute (m a) -> m (Attribute a) #

Eq1 Attribute Source # 
Instance details

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

Methods

liftEq :: (a -> b -> Bool) -> Attribute a -> Attribute b -> Bool #

Ord1 Attribute Source # 
Instance details

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

Methods

liftCompare :: (a -> b -> Ordering) -> Attribute a -> Attribute b -> Ordering #

Show1 Attribute Source # 
Instance details

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

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Attribute a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Attribute a] -> ShowS #

MonadZip Attribute Source # 
Instance details

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

Methods

mzip :: Attribute a -> Attribute b -> Attribute (a, b) #

mzipWith :: (a -> b -> c) -> Attribute a -> Attribute b -> Attribute c #

munzip :: Attribute (a, b) -> (Attribute a, Attribute b) #

Apply Attribute Source # 
Instance details

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

Methods

(<.>) :: Attribute (a -> b) -> Attribute a -> Attribute b #

(.>) :: Attribute a -> Attribute b -> Attribute b #

(<.) :: Attribute a -> Attribute b -> Attribute a #

liftF2 :: (a -> b -> c) -> Attribute a -> Attribute b -> Attribute c #

Traversable1 Attribute Source # 
Instance details

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

Methods

traverse1 :: Apply f => (a -> f b) -> Attribute a -> f (Attribute b) #

sequence1 :: Apply f => Attribute (f b) -> f (Attribute b) #

Foldable1 Attribute Source # 
Instance details

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

Methods

fold1 :: Semigroup m => Attribute m -> m #

foldMap1 :: Semigroup m => (a -> m) -> Attribute a -> m #

toNonEmpty :: Attribute a -> NonEmpty a #

Bind Attribute Source # 
Instance details

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

Methods

(>>-) :: Attribute a -> (a -> Attribute b) -> Attribute b #

join :: Attribute (Attribute a) -> Attribute a #

Eq str => Eq (Attribute str) Source # 
Instance details

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

Methods

(==) :: Attribute str -> Attribute str -> Bool #

(/=) :: Attribute str -> Attribute str -> Bool #

Ord str => Ord (Attribute str) Source # 
Instance details

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

Methods

compare :: Attribute str -> Attribute str -> Ordering #

(<) :: Attribute str -> Attribute str -> Bool #

(<=) :: Attribute str -> Attribute str -> Bool #

(>) :: Attribute str -> Attribute str -> Bool #

(>=) :: Attribute str -> Attribute str -> Bool #

max :: Attribute str -> Attribute str -> Attribute str #

min :: Attribute str -> Attribute str -> Attribute str #

Show str => Show (Attribute str) Source # 
Instance details

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

Methods

showsPrec :: Int -> Attribute str -> ShowS #

show :: Attribute str -> String #

showList :: [Attribute str] -> ShowS #

Semigroup str => Semigroup (Attribute str) Source # 
Instance details

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

Methods

(<>) :: Attribute str -> Attribute str -> Attribute str #

sconcat :: NonEmpty (Attribute str) -> Attribute str #

stimes :: Integral b => b -> Attribute str -> Attribute str #

Monoid str => Monoid (Attribute str) Source # 
Instance details

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

Methods

mempty :: Attribute str #

mappend :: Attribute str -> Attribute str -> Attribute str #

mconcat :: [Attribute str] -> Attribute str #

Wrapped (Attribute str) Source # 
Instance details

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

Associated Types

type Unwrapped (Attribute str) :: Type #

Methods

_Wrapped' :: Iso' (Attribute str) (Unwrapped (Attribute str)) #

Reversing (Attribute str) Source # 
Instance details

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

Methods

reversing :: Attribute str -> Attribute str #

Attribute s ~ str => Rewrapped (Attribute x) str Source # 
Instance details

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

HasAttribute (Attribute str) str Source # 
Instance details

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

AsAttribute (Attribute str) str Source # 
Instance details

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

Each (Attribute str) (Attribute str) str str Source # 
Instance details

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

Methods

each :: Traversal (Attribute str) (Attribute str) str str #

Field1 (Attribute str) (Attribute str) str str Source # 
Instance details

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

Methods

_1 :: Lens (Attribute str) (Attribute str) str str #

Field2 (Attribute str) (Attribute str) str str Source # 
Instance details

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

Methods

_2 :: Lens (Attribute str) (Attribute str) str str #

type Unwrapped (Attribute str) Source # 
Instance details

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

type Unwrapped (Attribute str) = (str, str)

class AsAttribute s str | s -> str where Source #

Methods

_Attribute :: Prism' s (Attribute str) Source #

Instances
AsAttribute (Attribute str) str Source # 
Instance details

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

AsAttribute (str, str) str Source # 
Instance details

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

Methods

_Attribute :: Prism' (str, str) (Attribute str) Source #

class HasAttribute s str | s -> str where Source #

Minimal complete definition

attribute

Instances
HasAttribute (Attribute str) str Source # 
Instance details

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

HasAttribute (str, str) str Source # 
Instance details

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

Methods

attribute :: Lens' (str, str) (Attribute str) Source #

attributeName :: Lens' (str, str) str Source #

attributeValue :: Lens' (str, str) str Source #

type Row = Int #

The row/line of a position, starting at 1

type Column = Int #

The column of a position, starting at 1