soap-0.2.3.4: SOAP client tools

Safe HaskellNone
LanguageHaskell98

Network.SOAP.Parsing.Stream

Contents

Description

Collection of helpers to use with Text.XML.Stream.Parse parsers.

let sink = flaxTag "MethodNameResponse"
         $ flaxTag "MethodNameResult" $ do
             info <- flaxTag "Info" $ do
                         q <- readTag "quantity"
                         b <- readTag "balance"
                         return $ Info q b
             rc <- readTag "ResponseCode"
             return (rc, info)

Synopsis

Tags

laxTag :: MonadThrow m => Text -> Sink Event m a -> Sink Event m (Maybe a) Source #

Namespace- and attribute- ignorant tagNoAttr.

flaxTag :: MonadThrow m => Text -> Sink Event m a -> Sink Event m a Source #

Non-maybe version of laxTag/tagNoAttr.

Content

readContent :: (Read a, MonadThrow m) => Sink Event m a Source #

Unpack and read a current tag content.

readTag :: (Read a, MonadThrow m) => Text -> Sink Event m a Source #

Unpack and read tag content by local name.

Types to use in custom parser sinks

type Sink i = ConduitM i Void #

Consumes a stream of input values and produces a final result, without producing any output.

type Sink i m r = ConduitM i Void m r

Since 0.5.0

data Event :: * #

Some XML processing tools are incremental, and work in terms of events rather than node trees. The Event type allows a document to be fully specified as a sequence of events.

Event-based XML libraries include:

Instances

Eq Event 

Methods

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

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

Data Event 

Methods

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

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

toConstr :: Event -> Constr #

dataTypeOf :: Event -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Event 

Methods

compare :: Event -> Event -> Ordering #

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

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

(>) :: Event -> Event -> Bool #

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

max :: Event -> Event -> Event #

min :: Event -> Event -> Event #

Show Event 

Methods

showsPrec :: Int -> Event -> ShowS #

show :: Event -> String #

showList :: [Event] -> ShowS #

Generic Event 

Associated Types

type Rep Event :: * -> * #

Methods

from :: Event -> Rep Event x #

to :: Rep Event x -> Event #

NFData Event 

Methods

rnf :: Event -> () #

type Rep Event 
type Rep Event = D1 (MetaData "Event" "Data.XML.Types" "xml-types-0.3.6-1OA83qn4r7cCPFYWdkfYwO" False) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "EventBeginDocument" PrefixI False) U1) (C1 (MetaCons "EventEndDocument" PrefixI False) U1)) ((:+:) (C1 (MetaCons "EventBeginDoctype" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe ExternalID))))) ((:+:) (C1 (MetaCons "EventEndDoctype" PrefixI False) U1) (C1 (MetaCons "EventInstruction" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Instruction)))))) ((:+:) ((:+:) (C1 (MetaCons "EventBeginElement" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Name)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [(Name, [Content])])))) (C1 (MetaCons "EventEndElement" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Name)))) ((:+:) (C1 (MetaCons "EventContent" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Content))) ((:+:) (C1 (MetaCons "EventComment" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text))) (C1 (MetaCons "EventCDATA" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))))))