xml-conduit-decode-1.0.0.0: Historical cursors & decoding on top of xml-conduit.

Copyright(c) Ben Kolera
LicenseMIT
MaintainerBen Kolera
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Text.XML.Decode.HCursor

Description

The big issue with using a plain Cursor is that all you get when you fail to parse what you were after is an Empty list of cursors and no idea how you got there.

An HCursor, however, only allows you to traverse it using the combinators in this file, and each one of these combinators accumulates CursorHistory in the HCursor describing each navigation operation, so that if you ever get to a position where you have an empty HCursor (i.e. the elements you were looking for didn't exist) then you can use that history to describe where you went wrong in an error message.

There is a general pattern to the combinators in this file:

Prefixes:

  • % apply a shift to a HCursor
  • $ apply a shift to a Cursor
  • & apply a shift to another shift (composes them)

Suffixes:

  • / Applies the shift to the children of the current foci
  • // Applies the shift to all descendants of the current foci

Synopsis

Documentation

data Shift Source #

A shift moves the HCursor foci to another set of foci, collection cursor history in the new HCursor. If the shift could not find any elements from this movement, the cursor will be empty.

shift :: (Cursor -> [Cursor]) -> CursorOp -> Shift Source #

Construct a shift given a Cursor movement and a description of the movement

data HCursor Source #

An HCursor carries around the elements of the XML in focus (the cursors) and the history as to how we got these elements in focus.

Constructors

HCursor 

Instances

data CursorOp Source #

Describes the operations that got an HCursor into its state

Constructors

Choice

We had a choice, determined by the shifts. The shifts that we failed to match are recorded and our potential success is too.

Backtrack

This is brought by the ||| operator which backtracks to the next cursor if the first one fails

BacktrackSucceed CursorHistory

When the first choice of a backtrack succeeds

GenericOp Text

If you need to cheat and create your own Op with a text description

MoveAxis CursorAxis

Move the cursor from its current foci to a new set of foci based on the axis

LaxElement Text

Filter the current foci based on element name (case insensive, namespace free)

FilterPredicate Text

Filter the current foci based on a predicate (described by a string)

FailedCompose

We tried to do a Shift onto a HCursor that was empty.

data CursorAxis Source #

These describe the axis that we can move from one set of elements to another. Note, these MoveAxis operations are the only CursorOps that actually "move" the cursor and replace the current foci with another set of possibilities.

Every other operation is actually a filtering operation of the foci.

Constructors

Child

To just the immediate children of our elements

Descendant

To all descendants of the current elements

data Predicate Source #

A node filtering function with a textual description

Constructors

Predicate 

Fields

foldCursor Source #

Arguments

:: (CursorHistory -> a)

Failure: Gives the history leading to this failure

-> (NonEmpty Cursor -> CursorHistory -> a)

The foci and history

-> HCursor 
-> a 

Fold on whether the cursor is failed

failedCursor :: HCursor -> Bool Source #

Tests to see if this cursor has no foci left (has failed)

successfulCursor :: HCursor -> Bool Source #

Tests to see whether this cursor still has foci to traverse

withHistory :: (CursorHistory -> CursorHistory) -> HCursor -> HCursor Source #

Modify the history of a cursor

laxElement :: Text -> Shift Source #

Filter foci based on element name, ignoring case or namespaces

filterPred :: Predicate -> Shift Source #

Filter foci based on the predicate

shiftGeneric :: Text -> (Cursor -> [Cursor]) -> Shift Source #

Constructs a Generic Cheat Text shift operation

(|||) :: Shift -> Shift -> Shift Source #

Tries the first shift, and backtracks to try the second if the first fails

(***) :: Shift -> Int -> Shift Source #

Repeat a shift n times

(%/) :: HCursor -> Shift -> HCursor infixr 1 Source #

Apply this shift to the children of the current foci

(%//) :: HCursor -> Shift -> HCursor infixr 1 Source #

Apply this shift to all descendants of the current foci

($/) :: Cursor -> Shift -> HCursor infixr 1 Source #

Apply a shift to children elements of a raw Cursor

($//) :: Cursor -> Shift -> HCursor infixr 1 Source #

Apply a shift to descendant elements of a raw Cursor

(&/) :: Shift -> Shift -> Shift infixr 1 Source #

Compose a shift to another shift, apply the right to children foci following the first shift

(&//) :: Shift -> Shift -> Shift infixr 1 Source #

Compose a shift to another shift, apply the right all descendant foci following the first shift