Safe Haskell | None |
---|---|
Language | Haskell2010 |
Defines types for zipping and iterating over HTML trees.
Synopsis
- data HTMLZipper
- type HTMLZipAction = HTMLZipper -> Maybe HTMLZipper
- data HTMLIter
- newtype HTMLZipPath = HTMLZipPath [Int]
- htmlZip :: HTMLNode -> HTMLZipper
- htmlZipM :: Monad m => HTMLNode -> m HTMLZipper
- htmlUnzip :: HTMLZipper -> HTMLNode
- htmlUnzipM :: Monad m => HTMLZipper -> m HTMLNode
- htmlZipNode :: HTMLZipper -> HTMLNode
- htmlZipNodeM :: Monad m => HTMLZipper -> m HTMLNode
- htmlZipRoot :: HTMLZipper -> HTMLZipper
- htmlZipRootM :: Monad m => HTMLZipper -> m HTMLZipper
- htmlZipUp :: HTMLZipper -> Maybe HTMLZipper
- htmlZipParent :: HTMLZipper -> Maybe HTMLZipper
- htmlZipFirst :: HTMLZipper -> Maybe HTMLZipper
- htmlZipLast :: HTMLZipper -> Maybe HTMLZipper
- htmlZipFind :: (HTMLNode -> Bool) -> HTMLZipper -> Maybe HTMLZipper
- htmlZipNext :: HTMLZipper -> Maybe HTMLZipper
- htmlZipPrev :: HTMLZipper -> Maybe HTMLZipper
- htmlZipGet :: Int -> HTMLZipper -> Maybe HTMLZipper
- htmlZipTest :: (HTMLZipper -> Bool) -> HTMLZipper -> Maybe HTMLZipper
- htmlZipTestNode :: (HTMLNode -> Bool) -> HTMLZipper -> Maybe HTMLZipper
- htmlZipTestName :: Text -> HTMLZipper -> Maybe HTMLZipper
- htmlZipTestFirst :: HTMLZipper -> Maybe HTMLZipper
- htmlZipTestLast :: HTMLZipper -> Maybe HTMLZipper
- htmlZipModify :: (HTMLNode -> HTMLNode) -> HTMLZipper -> HTMLZipper
- htmlZipModifyM :: Monad m => (HTMLNode -> HTMLNode) -> HTMLZipper -> m HTMLZipper
- htmlZipDelete :: HTMLZipper -> Maybe HTMLZipper
- htmlZipCollapse :: HTMLZipper -> Maybe HTMLZipper
- htmlZipInsertBefore :: HTMLNode -> HTMLZipper -> Maybe HTMLZipper
- htmlZipInsertAfter :: HTMLNode -> HTMLZipper -> Maybe HTMLZipper
- htmlZipContentBefore :: HTMLZipper -> [HTMLNode]
- htmlZipContentAfter :: HTMLZipper -> [HTMLNode]
- htmlZipContentLeft :: HTMLZipper -> [HTMLNode]
- htmlZipContentRight :: HTMLZipper -> [HTMLNode]
- htmlZipDropBefore :: HTMLZipper -> Maybe HTMLZipper
- htmlZipDropAfter :: HTMLZipper -> Maybe HTMLZipper
- htmlZipDropLeft :: HTMLZipper -> Maybe HTMLZipper
- htmlZipDropRight :: HTMLZipper -> Maybe HTMLZipper
- htmlZipPruneBefore :: HTMLZipper -> Maybe HTMLZipper
- htmlZipPruneAfter :: HTMLZipper -> Maybe HTMLZipper
- htmlZipPruneLeft :: HTMLZipper -> Maybe HTMLZipper
- htmlZipPruneRight :: HTMLZipper -> Maybe HTMLZipper
- htmlZipRepeat :: HTMLZipAction -> HTMLZipAction -> HTMLZipAction
- htmlZipStepNext :: HTMLZipper -> Maybe HTMLZipper
- htmlZipStepBack :: HTMLZipper -> Maybe HTMLZipper
- htmlZipSearch :: (HTMLZipper -> Maybe HTMLZipper) -> (HTMLZipper -> Bool) -> HTMLZipper -> Maybe HTMLZipper
- htmlZipIndex :: HTMLZipper -> Maybe Int
- htmlIter :: HTMLZipper -> HTMLIter
- htmlIterZipper :: HTMLIter -> HTMLZipper
- htmlIterSearch :: (HTMLIter -> Maybe HTMLIter) -> (HTMLZipper -> Bool) -> HTMLIter -> Maybe HTMLIter
- htmlIterModify :: (HTMLZipper -> HTMLZipper) -> HTMLIter -> HTMLIter
- htmlIterNext :: HTMLIter -> Maybe HTMLIter
- htmlIterBack :: HTMLIter -> Maybe HTMLIter
- htmlZipPath :: HTMLZipper -> HTMLZipPath
- htmlZipPathEmpty :: HTMLZipPath
- htmlZipPathFind :: HTMLZipPath -> HTMLZipper -> Maybe HTMLZipper
Documentation
data HTMLZipper Source #
The zipper type.
type HTMLZipAction = HTMLZipper -> Maybe HTMLZipper Source #
Defines an action on a zipper.
newtype HTMLZipPath Source #
Defines the type for a path.
Instances
Eq HTMLZipPath Source # | |
Defined in Zenacy.HTML.Internal.Zip (==) :: HTMLZipPath -> HTMLZipPath -> Bool # (/=) :: HTMLZipPath -> HTMLZipPath -> Bool # | |
Ord HTMLZipPath Source # | |
Defined in Zenacy.HTML.Internal.Zip compare :: HTMLZipPath -> HTMLZipPath -> Ordering # (<) :: HTMLZipPath -> HTMLZipPath -> Bool # (<=) :: HTMLZipPath -> HTMLZipPath -> Bool # (>) :: HTMLZipPath -> HTMLZipPath -> Bool # (>=) :: HTMLZipPath -> HTMLZipPath -> Bool # max :: HTMLZipPath -> HTMLZipPath -> HTMLZipPath # min :: HTMLZipPath -> HTMLZipPath -> HTMLZipPath # | |
Show HTMLZipPath Source # | |
Defined in Zenacy.HTML.Internal.Zip showsPrec :: Int -> HTMLZipPath -> ShowS # show :: HTMLZipPath -> String # showList :: [HTMLZipPath] -> ShowS # | |
Default HTMLZipPath Source # | Defaults for zip path. |
Defined in Zenacy.HTML.Internal.Zip def :: HTMLZipPath # |
htmlZip :: HTMLNode -> HTMLZipper Source #
Creates a zipper for a HTML node.
htmlZipM :: Monad m => HTMLNode -> m HTMLZipper Source #
Creates a zipper for a HTML node in a Monad.
htmlUnzip :: HTMLZipper -> HTMLNode Source #
Extracts the HTML node from a zipper.
htmlUnzipM :: Monad m => HTMLZipper -> m HTMLNode Source #
Extracts the HTML node from a zipper in a Monad.
htmlZipNode :: HTMLZipper -> HTMLNode Source #
Gets the current HTML node.
htmlZipNodeM :: Monad m => HTMLZipper -> m HTMLNode Source #
Gets the current HTML node in a Monad.
htmlZipRoot :: HTMLZipper -> HTMLZipper Source #
Moves the zipper to the root HTML node.
htmlZipRootM :: Monad m => HTMLZipper -> m HTMLZipper Source #
Moves the zipper to the root HTML node in a Monad.
htmlZipUp :: HTMLZipper -> Maybe HTMLZipper Source #
Moves the zipper to the parent node.
htmlZipParent :: HTMLZipper -> Maybe HTMLZipper Source #
Moves the zipper to the parent node.
htmlZipFirst :: HTMLZipper -> Maybe HTMLZipper Source #
Moves the zipper to the first child node.
htmlZipLast :: HTMLZipper -> Maybe HTMLZipper Source #
Moves the zipper to the last child node.
htmlZipFind :: (HTMLNode -> Bool) -> HTMLZipper -> Maybe HTMLZipper Source #
Moves the zipper to a named child element.
htmlZipNext :: HTMLZipper -> Maybe HTMLZipper Source #
Moves to the next sibling.
htmlZipPrev :: HTMLZipper -> Maybe HTMLZipper Source #
Moves to the previous sibling.
htmlZipGet :: Int -> HTMLZipper -> Maybe HTMLZipper Source #
Gets the child specified by an index.
htmlZipTest :: (HTMLZipper -> Bool) -> HTMLZipper -> Maybe HTMLZipper Source #
Continues a zipper if a test is passed.
htmlZipTestNode :: (HTMLNode -> Bool) -> HTMLZipper -> Maybe HTMLZipper Source #
Continues a zipper if a node test is passed.
htmlZipTestName :: Text -> HTMLZipper -> Maybe HTMLZipper Source #
Tests the current node for an element name.
htmlZipTestFirst :: HTMLZipper -> Maybe HTMLZipper Source #
Test whether the zipper is at the first child node.
htmlZipTestLast :: HTMLZipper -> Maybe HTMLZipper Source #
Test whether the zipper is at the last child node.
htmlZipModify :: (HTMLNode -> HTMLNode) -> HTMLZipper -> HTMLZipper Source #
Modifies the currently focused node.
htmlZipModifyM :: Monad m => (HTMLNode -> HTMLNode) -> HTMLZipper -> m HTMLZipper Source #
Modifies the currently focused node in a Monad.
htmlZipDelete :: HTMLZipper -> Maybe HTMLZipper Source #
Deletes the current node.
htmlZipCollapse :: HTMLZipper -> Maybe HTMLZipper Source #
Collapses the current node.
htmlZipInsertBefore :: HTMLNode -> HTMLZipper -> Maybe HTMLZipper Source #
Inserts a node before the current node.
htmlZipInsertAfter :: HTMLNode -> HTMLZipper -> Maybe HTMLZipper Source #
Inserts a node after the current node.
htmlZipContentBefore :: HTMLZipper -> [HTMLNode] Source #
Gets the siblings to the left of the current node.
htmlZipContentAfter :: HTMLZipper -> [HTMLNode] Source #
Gets the siblings to the right of the current node.
htmlZipContentLeft :: HTMLZipper -> [HTMLNode] Source #
Synonym for htmlZipContentBefore.
htmlZipContentRight :: HTMLZipper -> [HTMLNode] Source #
Synonym for htmlZipContentAfter.
htmlZipDropBefore :: HTMLZipper -> Maybe HTMLZipper Source #
Drops the siblings to the left of the current node.
htmlZipDropAfter :: HTMLZipper -> Maybe HTMLZipper Source #
Drops the siblings to the right of the current node.
htmlZipDropLeft :: HTMLZipper -> Maybe HTMLZipper Source #
Synonym for htmlZipDropBefore.
htmlZipDropRight :: HTMLZipper -> Maybe HTMLZipper Source #
Synonym for htmlZipDropAfter.
htmlZipPruneBefore :: HTMLZipper -> Maybe HTMLZipper Source #
Drops all of the branches to the left of the current node while moving up to and ending at the root.
htmlZipPruneAfter :: HTMLZipper -> Maybe HTMLZipper Source #
Drops all of the branches to the right of the current node while moving up to and ending at the root.
htmlZipPruneLeft :: HTMLZipper -> Maybe HTMLZipper Source #
Synonym for htmlZipPruneBefore.
htmlZipPruneRight :: HTMLZipper -> Maybe HTMLZipper Source #
Synonym for htmlZipPruneAfter.
htmlZipRepeat :: HTMLZipAction -> HTMLZipAction -> HTMLZipAction Source #
Repeats a zipper action until another zipper returns Nothing.
htmlZipStepNext :: HTMLZipper -> Maybe HTMLZipper Source #
Step a zipper forward one node.
htmlZipStepBack :: HTMLZipper -> Maybe HTMLZipper Source #
Step a zipper back one node.
htmlZipSearch :: (HTMLZipper -> Maybe HTMLZipper) -> (HTMLZipper -> Bool) -> HTMLZipper -> Maybe HTMLZipper Source #
Searches a zipper until a predicate is true.
htmlZipIndex :: HTMLZipper -> Maybe Int Source #
Gets the index for a node.
htmlIter :: HTMLZipper -> HTMLIter Source #
Returns an iterator for a zipper.
htmlIterZipper :: HTMLIter -> HTMLZipper Source #
Gets the iterator for a zipper.
htmlIterSearch :: (HTMLIter -> Maybe HTMLIter) -> (HTMLZipper -> Bool) -> HTMLIter -> Maybe HTMLIter Source #
Searches an iterator until a predicate is true.
htmlIterModify :: (HTMLZipper -> HTMLZipper) -> HTMLIter -> HTMLIter Source #
Modifies the zipper for an interator.
htmlZipPath :: HTMLZipper -> HTMLZipPath Source #
Gets the path for a node.
htmlZipPathEmpty :: HTMLZipPath Source #
Defines an empty path.
htmlZipPathFind :: HTMLZipPath -> HTMLZipper -> Maybe HTMLZipper Source #
Finds the zipper for a path starting from the current node.