xml-lens-0.3: Lenses, traversals, and prisms for xml-conduit
Copyright(C) 2015 Fumiaki Kinoshita
LicenseBSD-style (see the file LICENSE)
MaintainerFumiaki Kinoshita <fumiexcel@gmail.com>
Stabilityprovisional
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Text.XML.Lens

Description

 
Synopsis

Lenses, traversals for Element

data Element #

Instances

Instances details
Eq Element 
Instance details

Defined in Text.XML

Methods

(==) :: Element -> Element -> Bool #

(/=) :: Element -> Element -> Bool #

Data Element 
Instance details

Defined in Text.XML

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Element -> c Element #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Element #

toConstr :: Element -> Constr #

dataTypeOf :: Element -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Element) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Element) #

gmapT :: (forall b. Data b => b -> b) -> Element -> Element #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Element -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Element -> r #

gmapQ :: (forall d. Data d => d -> u) -> Element -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Element -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Element -> m Element #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Element -> m Element #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Element -> m Element #

Ord Element 
Instance details

Defined in Text.XML

Show Element 
Instance details

Defined in Text.XML

ToMarkup Element

Note that the special element name {http:/www.snoyman.comxml2html}ie-cond with the single attribute cond is used to indicate an IE conditional comment.

Instance details

Defined in Text.XML

NFData Element 
Instance details

Defined in Text.XML

Methods

rnf :: Element -> () #

Plated Element Source #

plate traverses over its sub-elements.

Instance details

Defined in Text.XML.Lens

(...) :: forall k f c s t p (a :: k) b. (Applicative f, Plated c) => LensLike f s t c c -> Over p f c c a b -> Over p f s t a b infixr 9 #

Compose through a plate

Names

el :: Name -> Traversal' Element Element Source #

Deprecated: Use named instead

Traverse elements which has the specified name.

named :: CI Text -> Traversal' Element Element Source #

Traverse elements which has the specified *local* name (case-insensitive).

Attributes

Contents

text :: Traversal' Element Text Source #

Traverse all contents of the element.

comment :: Traversal' Element Text Source #

Traverse all comments of the element.

Children

Prisms for Node

data Node #

Instances

Instances details
Eq Node 
Instance details

Defined in Text.XML

Methods

(==) :: Node -> Node -> Bool #

(/=) :: Node -> Node -> Bool #

Data Node 
Instance details

Defined in Text.XML

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Node -> c Node #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Node #

toConstr :: Node -> Constr #

dataTypeOf :: Node -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Node) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Node) #

gmapT :: (forall b. Data b => b -> b) -> Node -> Node #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Node -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Node -> r #

gmapQ :: (forall d. Data d => d -> u) -> Node -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Node -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Node -> m Node #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Node -> m Node #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Node -> m Node #

Ord Node 
Instance details

Defined in Text.XML

Methods

compare :: Node -> Node -> Ordering #

(<) :: Node -> Node -> Bool #

(<=) :: Node -> Node -> Bool #

(>) :: Node -> Node -> Bool #

(>=) :: Node -> Node -> Bool #

max :: Node -> Node -> Node #

min :: Node -> Node -> Node #

Show Node 
Instance details

Defined in Text.XML

Methods

showsPrec :: Int -> Node -> ShowS #

show :: Node -> String #

showList :: [Node] -> ShowS #

ToMarkup Node 
Instance details

Defined in Text.XML

NFData Node 
Instance details

Defined in Text.XML

Methods

rnf :: Node -> () #

AsComment Node Source # 
Instance details

Defined in Text.XML.Lens

AsInstruction Node Source # 
Instance details

Defined in Text.XML.Lens

class AsInstruction t where Source #

Instances

Instances details
AsInstruction Node Source # 
Instance details

Defined in Text.XML.Lens

AsInstruction Miscellaneous Source # 
Instance details

Defined in Text.XML.Lens

class AsComment t where Source #

Instances

Instances details
AsComment Node Source # 
Instance details

Defined in Text.XML.Lens

AsComment Miscellaneous Source # 
Instance details

Defined in Text.XML.Lens

Lenses for Document

data Document #

Instances

Instances details
Eq Document 
Instance details

Defined in Text.XML

Data Document 
Instance details

Defined in Text.XML

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Document -> c Document #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Document #

toConstr :: Document -> Constr #

dataTypeOf :: Document -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Document) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Document) #

gmapT :: (forall b. Data b => b -> b) -> Document -> Document #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Document -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Document -> r #

gmapQ :: (forall d. Data d => d -> u) -> Document -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Document -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Document -> m Document #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Document -> m Document #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Document -> m Document #

Show Document 
Instance details

Defined in Text.XML

ToMarkup Document 
Instance details

Defined in Text.XML

NFData Document 
Instance details

Defined in Text.XML

Methods

rnf :: Document -> () #

root :: Lens' Document Element Source #

The root element of the document.

Lenses for Name

data Name #

A fully qualified name.

Prefixes are not semantically important; they are included only to simplify pass-through parsing. When comparing names with Eq or Ord methods, prefixes are ignored.

The IsString instance supports Clark notation; see http://www.jclark.com/xml/xmlns.htm and http://infohost.nmt.edu/tcc/help/pubs/pylxml/etree-QName.html. Use the OverloadedStrings language extension for very simple Name construction:

myname :: Name
myname = "{http://example.com/ns/my-namespace}my-name"

Instances

Instances details
Eq Name 
Instance details

Defined in Data.XML.Types

Methods

(==) :: Name -> Name -> Bool #

(/=) :: Name -> Name -> Bool #

Data Name 
Instance details

Defined in Data.XML.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Name -> c Name #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Name #

toConstr :: Name -> Constr #

dataTypeOf :: Name -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Name) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Name) #

gmapT :: (forall b. Data b => b -> b) -> Name -> Name #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Name -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Name -> r #

gmapQ :: (forall d. Data d => d -> u) -> Name -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Name -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Name -> m Name #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Name -> m Name #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Name -> m Name #

Ord Name 
Instance details

Defined in Data.XML.Types

Methods

compare :: Name -> Name -> Ordering #

(<) :: Name -> Name -> Bool #

(<=) :: Name -> Name -> Bool #

(>) :: Name -> Name -> Bool #

(>=) :: Name -> Name -> Bool #

max :: Name -> Name -> Name #

min :: Name -> Name -> Name #

Show Name 
Instance details

Defined in Data.XML.Types

Methods

showsPrec :: Int -> Name -> ShowS #

show :: Name -> String #

showList :: [Name] -> ShowS #

IsString Name 
Instance details

Defined in Data.XML.Types

Methods

fromString :: String -> Name #

Generic Name 
Instance details

Defined in Data.XML.Types

Associated Types

type Rep Name :: Type -> Type #

Methods

from :: Name -> Rep Name x #

to :: Rep Name x -> Name #

NFData Name 
Instance details

Defined in Data.XML.Types

Methods

rnf :: Name -> () #

type Rep Name 
Instance details

Defined in Data.XML.Types

type Rep Name = D1 ('MetaData "Name" "Data.XML.Types" "xml-types-0.3.8-1FskkqwabAiJVamcx9xCWD" 'False) (C1 ('MetaCons "Name" 'PrefixI 'True) (S1 ('MetaSel ('Just "nameLocalName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: (S1 ('MetaSel ('Just "nameNamespace") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "namePrefix") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)))))

Lenses for Instruction

data Instruction #

Instances

Instances details
Eq Instruction 
Instance details

Defined in Data.XML.Types

Data Instruction 
Instance details

Defined in Data.XML.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Instruction -> c Instruction #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Instruction #

toConstr :: Instruction -> Constr #

dataTypeOf :: Instruction -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Instruction) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Instruction) #

gmapT :: (forall b. Data b => b -> b) -> Instruction -> Instruction #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Instruction -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Instruction -> r #

gmapQ :: (forall d. Data d => d -> u) -> Instruction -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Instruction -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Instruction -> m Instruction #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Instruction -> m Instruction #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Instruction -> m Instruction #

Ord Instruction 
Instance details

Defined in Data.XML.Types

Show Instruction 
Instance details

Defined in Data.XML.Types

Generic Instruction 
Instance details

Defined in Data.XML.Types

Associated Types

type Rep Instruction :: Type -> Type #

NFData Instruction 
Instance details

Defined in Data.XML.Types

Methods

rnf :: Instruction -> () #

type Rep Instruction 
Instance details

Defined in Data.XML.Types

type Rep Instruction = D1 ('MetaData "Instruction" "Data.XML.Types" "xml-types-0.3.8-1FskkqwabAiJVamcx9xCWD" 'False) (C1 ('MetaCons "Instruction" 'PrefixI 'True) (S1 ('MetaSel ('Just "instructionTarget") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "instructionData") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

Orphan instances

Plated Element Source #

plate traverses over its sub-elements.

Instance details