Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell98 |
Text.XML.HaXml.XmlContent.Parser
Description
The class XmlContent
is a kind of replacement for Read and Show:
it provides conversions between a generic XML tree representation
and your own more specialised typeful Haskell data trees.
If you are starting with a set of Haskell datatypes, use DrIFT to derive instances of this class for you: http://repetae.net/john/computer/haskell/DrIFT If you are starting with an XML DTD, use HaXml's tool DtdToHaskell to generate both the Haskell types and the corresponding instances.
This unified class interface replaces two previous (somewhat similar) classes: Haskell2Xml and Xml2Haskell. There was no real reason to have separate classes depending on how you originally defined your datatypes. However, some instances for basic types like lists will depend on which direction you are using. See Text.XML.HaXml.XmlContent and Text.XML.HaXml.XmlContent.Haskell.
Synopsis
- data Document i = Document Prolog (SymTab EntityDef) (Element i) [Misc]
- data Element i = Elem QName [Attribute] [Content i]
- data ElemTag = ElemTag QName [Attribute]
- data Content i
- type Attribute = (QName, AttValue)
- data AttValue = AttValue [Either String Reference]
- data Prolog = Prolog (Maybe XMLDecl) [Misc] (Maybe DocTypeDecl) [Misc]
- data Reference
- class HTypeable a => XmlContent a where
- parseContents :: XMLParser a
- toContents :: a -> [Content ()]
- xToChar :: a -> Char
- xFromChar :: Char -> a
- class XmlAttributes a where
- class XmlAttrType a where
- fromAttrToTyp :: String -> Attribute -> Maybe a
- toAttrFrTyp :: String -> a -> Maybe Attribute
- class Applicative f => Alternative (f :: Type -> Type) where
- newtype Parser t a = P ([t] -> Result [t] a)
- bracket :: PolyParse p => p bra -> p ket -> p a -> p a
- (<$>) :: Functor f => (a -> b) -> f a -> f b
- class Functor f => Applicative (f :: Type -> Type) where
- (<$) :: Functor f => a -> f b -> f a
- (<**>) :: Applicative f => f a -> f (a -> b) -> f b
- liftA :: Applicative f => (a -> b) -> f a -> f b
- liftA3 :: Applicative f => (a -> b -> c -> d) -> f a -> f b -> f c -> f d
- asum :: (Foldable t, Alternative f) => t (f a) -> f a
- newtype Const a (b :: k) = Const {
- getConst :: a
- next :: Parser t t
- satisfy :: (t -> Bool) -> Parser t t
- onFail :: Parser t a -> Parser t a -> Parser t a
- apply :: PolyParse p => p (a -> b) -> p a -> p b
- discard :: PolyParse p => p a -> p b -> p a
- class Commitment (p :: Type -> Type) where
- class (Functor p, Monad p, MonadFail p, Applicative p, Alternative p, Commitment p) => PolyParse (p :: Type -> Type)
- adjustErrBad :: PolyParse p => p a -> (String -> String) -> p a
- bracketSep :: PolyParse p => p bra -> p sep -> p ket -> p a -> p [a]
- exactly :: PolyParse p => Int -> p a -> p [a]
- failBad :: PolyParse p => String -> p a
- indent :: Int -> String -> String
- many1 :: PolyParse p => p a -> p [a]
- manyFinally :: PolyParse p => p a -> p z -> p [a]
- manyFinally' :: (PolyParse p, Show a) => p a -> p z -> p [a]
- oneOf :: PolyParse p => [p a] -> p a
- sepBy :: PolyParse p => p a -> p sep -> p [a]
- sepBy1 :: PolyParse p => p a -> p sep -> p [a]
- upto :: PolyParse p => Int -> p a -> p [a]
- eof :: Parser t ()
- reparse :: [t] -> Parser t ()
- satisfyMsg :: Show t => (t -> Bool) -> String -> Parser t t
- runParser :: Parser t a -> [t] -> (Either String a, [t])
- data Result z a
- optional :: Alternative f => f a -> f (Maybe a)
- newtype WrappedArrow (a :: Type -> Type -> Type) b c = WrapArrow {
- unwrapArrow :: a b c
- newtype WrappedMonad (m :: Type -> Type) a = WrapMonad {
- unwrapMonad :: m a
- newtype ZipList a = ZipList {
- getZipList :: [a]
- type XMLParser a = Parser (Content Posn) a
- content :: String -> XMLParser (Content Posn)
- posnElement :: [String] -> XMLParser (Posn, Element Posn)
- element :: [String] -> XMLParser (Element Posn)
- interior :: Element Posn -> XMLParser a -> XMLParser a
- inElement :: String -> XMLParser a -> XMLParser a
- text :: XMLParser String
- attributes :: XmlAttributes a => Element Posn -> XMLParser a
- posnElementWith :: (String -> String -> Bool) -> [String] -> XMLParser (Posn, Element Posn)
- elementWith :: (String -> String -> Bool) -> [String] -> XMLParser (Element Posn)
- inElementWith :: (String -> String -> Bool) -> String -> XMLParser a -> XMLParser a
- choice :: XmlContent a => (a -> b) -> XMLParser b -> XMLParser b
- definite :: XmlContent a => XMLParser a -> String -> String -> XMLParser a
- mkElem :: XmlContent a => a -> [Content ()] -> Content ()
- mkElemC :: String -> [Content ()] -> Content ()
- mkAttr :: String -> String -> Attribute
- toText :: String -> [Content ()]
- toCData :: String -> [Content ()]
- maybeToAttr :: (String -> a -> Maybe Attribute) -> String -> Maybe a -> Maybe Attribute
- defaultToAttr :: (String -> a -> Maybe Attribute) -> String -> Defaultable a -> Maybe Attribute
- definiteA :: (String -> Attribute -> Maybe a) -> String -> String -> [Attribute] -> a
- defaultA :: (String -> Attribute -> Maybe a) -> a -> String -> [Attribute] -> Defaultable a
- possibleA :: (String -> Attribute -> Maybe a) -> String -> [Attribute] -> Maybe a
- fromAttrToStr :: String -> Attribute -> Maybe String
- toAttrFrStr :: String -> String -> Maybe Attribute
- data Defaultable a
- = Default a
- | NonDefault a
- str2attr :: String -> AttValue
- attr2str :: AttValue -> String
- attval :: Read a => Element i -> a
- catMaybes :: [Maybe a] -> [a]
- module Text.XML.HaXml.TypeMapping
- data List1 a = NonEmpty [a]
- data ANYContent
- = (XmlContent a, Show a) => ANYContent a
- | UnConverted [Content Posn]
Re-export the relevant set of generic XML document type definitions
The symbol table stored in a document holds all its general entity reference definitions.
Constructors
CElem (Element i) i | |
CString Bool CharData i | bool is whether whitespace is significant |
CRef Reference i | |
CMisc Misc i |
Constructors
Prolog (Maybe XMLDecl) [Misc] (Maybe DocTypeDecl) [Misc] |
The enabling classes, that define parsing/unparsing between Haskell
class HTypeable a => XmlContent a where Source #
The XmlContent
class promises that an XML Content element can be
converted to and from a Haskell value.
Minimal complete definition
Methods
parseContents :: XMLParser a Source #
Convert from XML to Haskell
toContents :: a -> [Content ()] Source #
Convert from Haskell to XML
Dummy functions (for most types): used only in the Char instance for coercing lists of Char into String.
Instances
class XmlAttributes a where Source #
The XmlAttributes
class promises that a list of XML tag attributes
can be converted to and from a Haskell value.
class XmlAttrType a where Source #
The XmlAttrType
class promises that an attribute taking an XML
enumerated type can be converted to and from a Haskell value.
Methods
fromAttrToTyp :: String -> Attribute -> Maybe a Source #
toAttrFrTyp :: String -> a -> Maybe Attribute Source #
Auxiliaries for writing parsers in the XmlContent class
class Applicative f => Alternative (f :: Type -> Type) where #
Instances
Instances
MonadFail (Parser t) | |
Defined in Text.ParserCombinators.Poly.Parser | |
Alternative (Parser t) | |
Applicative (Parser t) | |
Functor (Parser t) | |
Monad (Parser t) | |
Commitment (Parser t) | |
PolyParse (Parser t) | |
Defined in Text.ParserCombinators.Poly.Parser |
class Functor f => Applicative (f :: Type -> Type) where #
Instances
Applicative ZipList | |
Applicative Complex | |
Applicative Identity | |
Applicative First | |
Applicative Last | |
Applicative Down | |
Applicative First | |
Applicative Last | |
Applicative Max | |
Applicative Min | |
Applicative NonEmpty | |
Applicative STM | |
Applicative NoIO | |
Applicative Par1 | |
Applicative P | |
Applicative ReadP | |
Applicative ReadPrec | |
Applicative Put | |
Applicative Seq | |
Applicative Tree | |
Applicative IO | |
Applicative Parser | |
Applicative Parser | |
Applicative Parser | |
Applicative Parser | |
Applicative Maybe | |
Applicative Solo | |
Applicative [] | |
Monad m => Applicative (WrappedMonad m) | |
Defined in Control.Applicative Methods pure :: a -> WrappedMonad m a # (<*>) :: WrappedMonad m (a -> b) -> WrappedMonad m a -> WrappedMonad m b # liftA2 :: (a -> b -> c) -> WrappedMonad m a -> WrappedMonad m b -> WrappedMonad m c # (*>) :: WrappedMonad m a -> WrappedMonad m b -> WrappedMonad m b # (<*) :: WrappedMonad m a -> WrappedMonad m b -> WrappedMonad m a # | |
Arrow a => Applicative (ArrowMonad a) | |
Defined in Control.Arrow Methods pure :: a0 -> ArrowMonad a a0 # (<*>) :: ArrowMonad a (a0 -> b) -> ArrowMonad a a0 -> ArrowMonad a b # liftA2 :: (a0 -> b -> c) -> ArrowMonad a a0 -> ArrowMonad a b -> ArrowMonad a c # (*>) :: ArrowMonad a a0 -> ArrowMonad a b -> ArrowMonad a b # (<*) :: ArrowMonad a a0 -> ArrowMonad a b -> ArrowMonad a a0 # | |
Applicative (Either e) | |
Applicative (Proxy :: Type -> Type) | |
Applicative (U1 :: Type -> Type) | |
Applicative (ST s) | |
Applicative (SetM s) | |
Applicative (Parser t) | |
Applicative (Parser t) | |
Applicative (Parser t) | |
Applicative (Parser s) | |
Defined in Text.ParserCombinators.Poly.StateText | |
Monoid a => Applicative ((,) a) | |
Arrow a => Applicative (WrappedArrow a b) | |
Defined in Control.Applicative Methods pure :: a0 -> WrappedArrow a b a0 # (<*>) :: WrappedArrow a b (a0 -> b0) -> WrappedArrow a b a0 -> WrappedArrow a b b0 # liftA2 :: (a0 -> b0 -> c) -> WrappedArrow a b a0 -> WrappedArrow a b b0 -> WrappedArrow a b c # (*>) :: WrappedArrow a b a0 -> WrappedArrow a b b0 -> WrappedArrow a b b0 # (<*) :: WrappedArrow a b a0 -> WrappedArrow a b b0 -> WrappedArrow a b a0 # | |
Applicative m => Applicative (Kleisli m a) | |
Defined in Control.Arrow | |
Monoid m => Applicative (Const m :: Type -> Type) | |
Applicative f => Applicative (Ap f) | |
(Generic1 f, Applicative (Rep1 f)) => Applicative (Generically1 f) | |
Defined in GHC.Generics Methods pure :: a -> Generically1 f a # (<*>) :: Generically1 f (a -> b) -> Generically1 f a -> Generically1 f b # liftA2 :: (a -> b -> c) -> Generically1 f a -> Generically1 f b -> Generically1 f c # (*>) :: Generically1 f a -> Generically1 f b -> Generically1 f b # (<*) :: Generically1 f a -> Generically1 f b -> Generically1 f a # | |
Applicative f => Applicative (Rec1 f) | |
(Applicative f, Monad f) => Applicative (WhenMissing f x) | |
Defined in Data.IntMap.Internal Methods pure :: a -> WhenMissing f x a # (<*>) :: WhenMissing f x (a -> b) -> WhenMissing f x a -> WhenMissing f x b # liftA2 :: (a -> b -> c) -> WhenMissing f x a -> WhenMissing f x b -> WhenMissing f x c # (*>) :: WhenMissing f x a -> WhenMissing f x b -> WhenMissing f x b # (<*) :: WhenMissing f x a -> WhenMissing f x b -> WhenMissing f x a # | |
Applicative (Parser s t) | |
Defined in Text.ParserCombinators.Poly.StateLazy | |
Applicative (Parser s t) | |
Defined in Text.ParserCombinators.Poly.StateParser | |
(Monoid a, Monoid b) => Applicative ((,,) a b) | |
(Applicative f, Applicative g) => Applicative (Product f g) | |
Defined in Data.Functor.Product | |
(Applicative f, Applicative g) => Applicative (f :*: g) | |
Monoid c => Applicative (K1 i c :: Type -> Type) | |
(Monad f, Applicative f) => Applicative (WhenMatched f x y) | |
Defined in Data.IntMap.Internal Methods pure :: a -> WhenMatched f x y a # (<*>) :: WhenMatched f x y (a -> b) -> WhenMatched f x y a -> WhenMatched f x y b # liftA2 :: (a -> b -> c) -> WhenMatched f x y a -> WhenMatched f x y b -> WhenMatched f x y c # (*>) :: WhenMatched f x y a -> WhenMatched f x y b -> WhenMatched f x y b # (<*) :: WhenMatched f x y a -> WhenMatched f x y b -> WhenMatched f x y a # | |
(Applicative f, Monad f) => Applicative (WhenMissing f k x) | |
Defined in Data.Map.Internal Methods pure :: a -> WhenMissing f k x a # (<*>) :: WhenMissing f k x (a -> b) -> WhenMissing f k x a -> WhenMissing f k x b # liftA2 :: (a -> b -> c) -> WhenMissing f k x a -> WhenMissing f k x b -> WhenMissing f k x c # (*>) :: WhenMissing f k x a -> WhenMissing f k x b -> WhenMissing f k x b # (<*) :: WhenMissing f k x a -> WhenMissing f k x b -> WhenMissing f k x a # | |
Applicative (Parser s t e) | |
Defined in Text.ParserCombinators.HuttonMeijerWallace | |
(Monoid a, Monoid b, Monoid c) => Applicative ((,,,) a b c) | |
Defined in GHC.Base | |
Applicative ((->) r) | |
(Applicative f, Applicative g) => Applicative (Compose f g) | |
Defined in Data.Functor.Compose | |
(Applicative f, Applicative g) => Applicative (f :.: g) | |
Applicative f => Applicative (M1 i c f) | |
(Monad f, Applicative f) => Applicative (WhenMatched f k x y) | |
Defined in Data.Map.Internal Methods pure :: a -> WhenMatched f k x y a # (<*>) :: WhenMatched f k x y (a -> b) -> WhenMatched f k x y a -> WhenMatched f k x y b # liftA2 :: (a -> b -> c) -> WhenMatched f k x y a -> WhenMatched f k x y b -> WhenMatched f k x y c # (*>) :: WhenMatched f k x y a -> WhenMatched f k x y b -> WhenMatched f k x y b # (<*) :: WhenMatched f k x y a -> WhenMatched f k x y b -> WhenMatched f k x y a # |
(<**>) :: Applicative f => f a -> f (a -> b) -> f b #
liftA :: Applicative f => (a -> b) -> f a -> f b #
liftA3 :: Applicative f => (a -> b -> c -> d) -> f a -> f b -> f c -> f d #
asum :: (Foldable t, Alternative f) => t (f a) -> f a #
Instances
Generic1 (Const a :: k -> Type) | |||||
Defined in Data.Functor.Const Associated Types
| |||||
Bifoldable (Const :: Type -> Type -> Type) | |||||
Bifoldable1 (Const :: Type -> Type -> Type) | |||||
Defined in Data.Bifoldable1 Methods bifold1 :: Semigroup m => Const m m -> m bifoldMap1 :: Semigroup m => (a -> m) -> (b -> m) -> Const a b -> m | |||||
Bifunctor (Const :: Type -> Type -> Type) | |||||
Bitraversable (Const :: Type -> Type -> Type) | |||||
Defined in Data.Bitraversable Methods bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> Const a b -> f (Const c d) | |||||
Eq2 (Const :: Type -> Type -> Type) | |||||
Defined in Data.Functor.Classes | |||||
Ord2 (Const :: Type -> Type -> Type) | |||||
Defined in Data.Functor.Classes Methods liftCompare2 :: (a -> b -> Ordering) -> (c -> d -> Ordering) -> Const a c -> Const b d -> Ordering | |||||
Read2 (Const :: Type -> Type -> Type) | |||||
Defined in Data.Functor.Classes Methods liftReadsPrec2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> Int -> ReadS (Const a b) liftReadList2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [Const a b] liftReadPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (Const a b) liftReadListPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec [Const a b] | |||||
Show2 (Const :: Type -> Type -> Type) | |||||
Defined in Data.Functor.Classes Methods liftShowsPrec2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> Int -> Const a b -> ShowS liftShowList2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> [Const a b] -> ShowS | |||||
Foldable (Const m :: Type -> Type) | |||||
Defined in Data.Functor.Const Methods fold :: Monoid m0 => Const m m0 -> m0 foldMap :: Monoid m0 => (a -> m0) -> Const m a -> m0 foldMap' :: Monoid m0 => (a -> m0) -> Const m a -> m0 foldr :: (a -> b -> b) -> b -> Const m a -> b foldr' :: (a -> b -> b) -> b -> Const m a -> b foldl :: (b -> a -> b) -> b -> Const m a -> b foldl' :: (b -> a -> b) -> b -> Const m a -> b foldr1 :: (a -> a -> a) -> Const m a -> a foldl1 :: (a -> a -> a) -> Const m a -> a elem :: Eq a => a -> Const m a -> Bool maximum :: Ord a => Const m a -> a minimum :: Ord a => Const m a -> a | |||||
Eq a => Eq1 (Const a :: Type -> Type) | |||||
Defined in Data.Functor.Classes | |||||
Ord a => Ord1 (Const a :: Type -> Type) | |||||
Defined in Data.Functor.Classes Methods liftCompare :: (a0 -> b -> Ordering) -> Const a a0 -> Const a b -> Ordering | |||||
Read a => Read1 (Const a :: Type -> Type) | |||||
Defined in Data.Functor.Classes Methods liftReadsPrec :: (Int -> ReadS a0) -> ReadS [a0] -> Int -> ReadS (Const a a0) liftReadList :: (Int -> ReadS a0) -> ReadS [a0] -> ReadS [Const a a0] liftReadPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec (Const a a0) liftReadListPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec [Const a a0] | |||||
Show a => Show1 (Const a :: Type -> Type) | |||||
Defined in Data.Functor.Classes Methods liftShowsPrec :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> Int -> Const a a0 -> ShowS liftShowList :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> [Const a a0] -> ShowS | |||||
Contravariant (Const a :: Type -> Type) | |||||
Traversable (Const m :: Type -> Type) | |||||
Defined in Data.Traversable | |||||
Monoid m => Applicative (Const m :: Type -> Type) | |||||
Functor (Const m :: Type -> Type) | |||||
(Typeable k, Data a, Typeable b) => Data (Const a b) | |||||
Defined in Data.Data Methods gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> Const a b -> c (Const a b) gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Const a b) toConstr :: Const a b -> Constr dataTypeOf :: Const a b -> DataType dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Const a b)) dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Const a b)) gmapT :: (forall b0. Data b0 => b0 -> b0) -> Const a b -> Const a b gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Const a b -> r gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Const a b -> r gmapQ :: (forall d. Data d => d -> u) -> Const a b -> [u] gmapQi :: Int -> (forall d. Data d => d -> u) -> Const a b -> u gmapM :: Monad m => (forall d. Data d => d -> m d) -> Const a b -> m (Const a b) gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Const a b -> m (Const a b) gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Const a b -> m (Const a b) | |||||
IsString a => IsString (Const a b) | |||||
Defined in Data.String Methods fromString :: String -> Const a b | |||||
Storable a => Storable (Const a b) | |||||
Defined in Data.Functor.Const Methods peekElemOff :: Ptr (Const a b) -> Int -> IO (Const a b) pokeElemOff :: Ptr (Const a b) -> Int -> Const a b -> IO () peekByteOff :: Ptr b0 -> Int -> IO (Const a b) pokeByteOff :: Ptr b0 -> Int -> Const a b -> IO () | |||||
Monoid a => Monoid (Const a b) | |||||
Semigroup a => Semigroup (Const a b) | |||||
Bits a => Bits (Const a b) | |||||
Defined in Data.Functor.Const Methods (.&.) :: Const a b -> Const a b -> Const a b (.|.) :: Const a b -> Const a b -> Const a b xor :: Const a b -> Const a b -> Const a b complement :: Const a b -> Const a b shift :: Const a b -> Int -> Const a b rotate :: Const a b -> Int -> Const a b setBit :: Const a b -> Int -> Const a b clearBit :: Const a b -> Int -> Const a b complementBit :: Const a b -> Int -> Const a b testBit :: Const a b -> Int -> Bool bitSizeMaybe :: Const a b -> Maybe Int shiftL :: Const a b -> Int -> Const a b unsafeShiftL :: Const a b -> Int -> Const a b shiftR :: Const a b -> Int -> Const a b unsafeShiftR :: Const a b -> Int -> Const a b rotateL :: Const a b -> Int -> Const a b | |||||
FiniteBits a => FiniteBits (Const a b) | |||||
Defined in Data.Functor.Const Methods finiteBitSize :: Const a b -> Int countLeadingZeros :: Const a b -> Int countTrailingZeros :: Const a b -> Int | |||||
Bounded a => Bounded (Const a b) | |||||
Defined in Data.Functor.Const | |||||
Enum a => Enum (Const a b) | |||||
Defined in Data.Functor.Const | |||||
Floating a => Floating (Const a b) | |||||
Defined in Data.Functor.Const Methods sqrt :: Const a b -> Const a b (**) :: Const a b -> Const a b -> Const a b logBase :: Const a b -> Const a b -> Const a b asin :: Const a b -> Const a b acos :: Const a b -> Const a b atan :: Const a b -> Const a b sinh :: Const a b -> Const a b cosh :: Const a b -> Const a b tanh :: Const a b -> Const a b asinh :: Const a b -> Const a b acosh :: Const a b -> Const a b atanh :: Const a b -> Const a b log1p :: Const a b -> Const a b expm1 :: Const a b -> Const a b | |||||
RealFloat a => RealFloat (Const a b) | |||||
Defined in Data.Functor.Const Methods floatRadix :: Const a b -> Integer floatDigits :: Const a b -> Int floatRange :: Const a b -> (Int, Int) decodeFloat :: Const a b -> (Integer, Int) encodeFloat :: Integer -> Int -> Const a b significand :: Const a b -> Const a b scaleFloat :: Int -> Const a b -> Const a b isInfinite :: Const a b -> Bool isDenormalized :: Const a b -> Bool isNegativeZero :: Const a b -> Bool | |||||
Generic (Const a b) | |||||
Defined in Data.Functor.Const Associated Types
| |||||
Ix a => Ix (Const a b) | |||||
Defined in Data.Functor.Const Methods range :: (Const a b, Const a b) -> [Const a b] index :: (Const a b, Const a b) -> Const a b -> Int unsafeIndex :: (Const a b, Const a b) -> Const a b -> Int inRange :: (Const a b, Const a b) -> Const a b -> Bool rangeSize :: (Const a b, Const a b) -> Int unsafeRangeSize :: (Const a b, Const a b) -> Int | |||||
Num a => Num (Const a b) | |||||
Read a => Read (Const a b) | |||||
Defined in Data.Functor.Const | |||||
Fractional a => Fractional (Const a b) | |||||
Defined in Data.Functor.Const | |||||
Integral a => Integral (Const a b) | |||||
Defined in Data.Functor.Const | |||||
Real a => Real (Const a b) | |||||
Defined in Data.Functor.Const Methods toRational :: Const a b -> Rational | |||||
RealFrac a => RealFrac (Const a b) | |||||
Show a => Show (Const a b) | |||||
Eq a => Eq (Const a b) | |||||
Ord a => Ord (Const a b) | |||||
Defined in Data.Functor.Const | |||||
type Rep1 (Const a :: k -> Type) | |||||
Defined in Data.Functor.Const type Rep1 (Const a :: k -> Type) = D1 ('MetaData "Const" "Data.Functor.Const" "base" 'True) (C1 ('MetaCons "Const" 'PrefixI 'True) (S1 ('MetaSel ('Just "getConst") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a))) | |||||
type Rep (Const a b) | |||||
Defined in Data.Functor.Const type Rep (Const a b) = D1 ('MetaData "Const" "Data.Functor.Const" "base" 'True) (C1 ('MetaCons "Const" 'PrefixI 'True) (S1 ('MetaSel ('Just "getConst") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a))) |
class Commitment (p :: Type -> Type) where #
Instances
Commitment Parser | |
Commitment Parser | |
Commitment Parser | |
Commitment (Parser t) | |
Commitment (Parser t) | |
Commitment (Parser t) | |
Commitment (Parser s) | |
Commitment (Parser s t) | |
Commitment (Parser s t) | |
class (Functor p, Monad p, MonadFail p, Applicative p, Alternative p, Commitment p) => PolyParse (p :: Type -> Type) #
Instances
PolyParse Parser | |
Defined in Text.ParserCombinators.Poly.ByteString | |
PolyParse Parser | |
Defined in Text.ParserCombinators.Poly.ByteStringChar | |
PolyParse Parser | |
Defined in Text.ParserCombinators.Poly.Text | |
PolyParse (Parser t) | |
Defined in Text.ParserCombinators.Poly.Lazy | |
PolyParse (Parser t) | |
Defined in Text.ParserCombinators.Poly.Lex | |
PolyParse (Parser t) | |
Defined in Text.ParserCombinators.Poly.Parser | |
PolyParse (Parser s) | |
Defined in Text.ParserCombinators.Poly.StateText | |
PolyParse (Parser s t) | |
Defined in Text.ParserCombinators.Poly.StateLazy | |
PolyParse (Parser s t) | |
Defined in Text.ParserCombinators.Poly.StateParser |
adjustErrBad :: PolyParse p => p a -> (String -> String) -> p a #
bracketSep :: PolyParse p => p bra -> p sep -> p ket -> p a -> p [a] #
manyFinally :: PolyParse p => p a -> p z -> p [a] #
manyFinally' :: (PolyParse p, Show a) => p a -> p z -> p [a] #
satisfyMsg :: Show t => (t -> Bool) -> String -> Parser t t #
optional :: Alternative f => f a -> f (Maybe a) #
newtype WrappedArrow (a :: Type -> Type -> Type) b c #
Constructors
WrapArrow | |
Fields
|
Instances
Generic1 (WrappedArrow a b :: Type -> Type) | |||||
Defined in Control.Applicative Associated Types
Methods from1 :: WrappedArrow a b a0 -> Rep1 (WrappedArrow a b) a0 to1 :: Rep1 (WrappedArrow a b) a0 -> WrappedArrow a b a0 | |||||
(ArrowZero a, ArrowPlus a) => Alternative (WrappedArrow a b) | |||||
Defined in Control.Applicative Methods empty :: WrappedArrow a b a0 # (<|>) :: WrappedArrow a b a0 -> WrappedArrow a b a0 -> WrappedArrow a b a0 # some :: WrappedArrow a b a0 -> WrappedArrow a b [a0] # many :: WrappedArrow a b a0 -> WrappedArrow a b [a0] # | |||||
Arrow a => Applicative (WrappedArrow a b) | |||||
Defined in Control.Applicative Methods pure :: a0 -> WrappedArrow a b a0 # (<*>) :: WrappedArrow a b (a0 -> b0) -> WrappedArrow a b a0 -> WrappedArrow a b b0 # liftA2 :: (a0 -> b0 -> c) -> WrappedArrow a b a0 -> WrappedArrow a b b0 -> WrappedArrow a b c # (*>) :: WrappedArrow a b a0 -> WrappedArrow a b b0 -> WrappedArrow a b b0 # (<*) :: WrappedArrow a b a0 -> WrappedArrow a b b0 -> WrappedArrow a b a0 # | |||||
Arrow a => Functor (WrappedArrow a b) | |||||
Defined in Control.Applicative Methods fmap :: (a0 -> b0) -> WrappedArrow a b a0 -> WrappedArrow a b b0 (<$) :: a0 -> WrappedArrow a b b0 -> WrappedArrow a b a0 # | |||||
(Typeable a, Typeable b, Typeable c, Data (a b c)) => Data (WrappedArrow a b c) | |||||
Defined in Data.Data Methods gfoldl :: (forall d b0. Data d => c0 (d -> b0) -> d -> c0 b0) -> (forall g. g -> c0 g) -> WrappedArrow a b c -> c0 (WrappedArrow a b c) gunfold :: (forall b0 r. Data b0 => c0 (b0 -> r) -> c0 r) -> (forall r. r -> c0 r) -> Constr -> c0 (WrappedArrow a b c) toConstr :: WrappedArrow a b c -> Constr dataTypeOf :: WrappedArrow a b c -> DataType dataCast1 :: Typeable t => (forall d. Data d => c0 (t d)) -> Maybe (c0 (WrappedArrow a b c)) dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c0 (t d e)) -> Maybe (c0 (WrappedArrow a b c)) gmapT :: (forall b0. Data b0 => b0 -> b0) -> WrappedArrow a b c -> WrappedArrow a b c gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WrappedArrow a b c -> r gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WrappedArrow a b c -> r gmapQ :: (forall d. Data d => d -> u) -> WrappedArrow a b c -> [u] gmapQi :: Int -> (forall d. Data d => d -> u) -> WrappedArrow a b c -> u gmapM :: Monad m => (forall d. Data d => d -> m d) -> WrappedArrow a b c -> m (WrappedArrow a b c) gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WrappedArrow a b c -> m (WrappedArrow a b c) gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WrappedArrow a b c -> m (WrappedArrow a b c) | |||||
Generic (WrappedArrow a b c) | |||||
Defined in Control.Applicative Associated Types
Methods from :: WrappedArrow a b c -> Rep (WrappedArrow a b c) x to :: Rep (WrappedArrow a b c) x -> WrappedArrow a b c | |||||
type Rep1 (WrappedArrow a b :: Type -> Type) | |||||
Defined in Control.Applicative type Rep1 (WrappedArrow a b :: Type -> Type) = D1 ('MetaData "WrappedArrow" "Control.Applicative" "base" 'True) (C1 ('MetaCons "WrapArrow" 'PrefixI 'True) (S1 ('MetaSel ('Just "unwrapArrow") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 (a b)))) | |||||
type Rep (WrappedArrow a b c) | |||||
Defined in Control.Applicative type Rep (WrappedArrow a b c) = D1 ('MetaData "WrappedArrow" "Control.Applicative" "base" 'True) (C1 ('MetaCons "WrapArrow" 'PrefixI 'True) (S1 ('MetaSel ('Just "unwrapArrow") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (a b c)))) |
newtype WrappedMonad (m :: Type -> Type) a #
Constructors
WrapMonad | |
Fields
|
Instances
Generic1 (WrappedMonad m :: Type -> Type) | |||||
Defined in Control.Applicative Associated Types
Methods from1 :: WrappedMonad m a -> Rep1 (WrappedMonad m) a to1 :: Rep1 (WrappedMonad m) a -> WrappedMonad m a | |||||
MonadPlus m => Alternative (WrappedMonad m) | |||||
Defined in Control.Applicative Methods empty :: WrappedMonad m a # (<|>) :: WrappedMonad m a -> WrappedMonad m a -> WrappedMonad m a # some :: WrappedMonad m a -> WrappedMonad m [a] # many :: WrappedMonad m a -> WrappedMonad m [a] # | |||||
Monad m => Applicative (WrappedMonad m) | |||||
Defined in Control.Applicative Methods pure :: a -> WrappedMonad m a # (<*>) :: WrappedMonad m (a -> b) -> WrappedMonad m a -> WrappedMonad m b # liftA2 :: (a -> b -> c) -> WrappedMonad m a -> WrappedMonad m b -> WrappedMonad m c # (*>) :: WrappedMonad m a -> WrappedMonad m b -> WrappedMonad m b # (<*) :: WrappedMonad m a -> WrappedMonad m b -> WrappedMonad m a # | |||||
Monad m => Functor (WrappedMonad m) | |||||
Defined in Control.Applicative Methods fmap :: (a -> b) -> WrappedMonad m a -> WrappedMonad m b (<$) :: a -> WrappedMonad m b -> WrappedMonad m a # | |||||
Monad m => Monad (WrappedMonad m) | |||||
Defined in Control.Applicative Methods (>>=) :: WrappedMonad m a -> (a -> WrappedMonad m b) -> WrappedMonad m b (>>) :: WrappedMonad m a -> WrappedMonad m b -> WrappedMonad m b return :: a -> WrappedMonad m a | |||||
(Typeable m, Typeable a, Data (m a)) => Data (WrappedMonad m a) | |||||
Defined in Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> WrappedMonad m a -> c (WrappedMonad m a) gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (WrappedMonad m a) toConstr :: WrappedMonad m a -> Constr dataTypeOf :: WrappedMonad m a -> DataType dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (WrappedMonad m a)) dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (WrappedMonad m a)) gmapT :: (forall b. Data b => b -> b) -> WrappedMonad m a -> WrappedMonad m a gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WrappedMonad m a -> r gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WrappedMonad m a -> r gmapQ :: (forall d. Data d => d -> u) -> WrappedMonad m a -> [u] gmapQi :: Int -> (forall d. Data d => d -> u) -> WrappedMonad m a -> u gmapM :: Monad m0 => (forall d. Data d => d -> m0 d) -> WrappedMonad m a -> m0 (WrappedMonad m a) gmapMp :: MonadPlus m0 => (forall d. Data d => d -> m0 d) -> WrappedMonad m a -> m0 (WrappedMonad m a) gmapMo :: MonadPlus m0 => (forall d. Data d => d -> m0 d) -> WrappedMonad m a -> m0 (WrappedMonad m a) | |||||
Generic (WrappedMonad m a) | |||||
Defined in Control.Applicative Associated Types
Methods from :: WrappedMonad m a -> Rep (WrappedMonad m a) x to :: Rep (WrappedMonad m a) x -> WrappedMonad m a | |||||
type Rep1 (WrappedMonad m :: Type -> Type) | |||||
Defined in Control.Applicative type Rep1 (WrappedMonad m :: Type -> Type) = D1 ('MetaData "WrappedMonad" "Control.Applicative" "base" 'True) (C1 ('MetaCons "WrapMonad" 'PrefixI 'True) (S1 ('MetaSel ('Just "unwrapMonad") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 m))) | |||||
type Rep (WrappedMonad m a) | |||||
Defined in Control.Applicative type Rep (WrappedMonad m a) = D1 ('MetaData "WrappedMonad" "Control.Applicative" "base" 'True) (C1 ('MetaCons "WrapMonad" 'PrefixI 'True) (S1 ('MetaSel ('Just "unwrapMonad") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (m a)))) |
Constructors
ZipList | |
Fields
|
Instances
Foldable ZipList | |||||
Defined in Control.Applicative Methods fold :: Monoid m => ZipList m -> m foldMap :: Monoid m => (a -> m) -> ZipList a -> m foldMap' :: Monoid m => (a -> m) -> ZipList a -> m foldr :: (a -> b -> b) -> b -> ZipList a -> b foldr' :: (a -> b -> b) -> b -> ZipList a -> b foldl :: (b -> a -> b) -> b -> ZipList a -> b foldl' :: (b -> a -> b) -> b -> ZipList a -> b foldr1 :: (a -> a -> a) -> ZipList a -> a foldl1 :: (a -> a -> a) -> ZipList a -> a elem :: Eq a => a -> ZipList a -> Bool maximum :: Ord a => ZipList a -> a minimum :: Ord a => ZipList a -> a | |||||
Traversable ZipList | |||||
Defined in Data.Traversable | |||||
Alternative ZipList | |||||
Applicative ZipList | |||||
Functor ZipList | |||||
Generic1 ZipList | |||||
Defined in Control.Applicative Associated Types
| |||||
Data a => Data (ZipList a) | |||||
Defined in Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ZipList a -> c (ZipList a) gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ZipList a) toConstr :: ZipList a -> Constr dataTypeOf :: ZipList a -> DataType dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ZipList a)) dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ZipList a)) gmapT :: (forall b. Data b => b -> b) -> ZipList a -> ZipList a gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ZipList a -> r gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ZipList a -> r gmapQ :: (forall d. Data d => d -> u) -> ZipList a -> [u] gmapQi :: Int -> (forall d. Data d => d -> u) -> ZipList a -> u gmapM :: Monad m => (forall d. Data d => d -> m d) -> ZipList a -> m (ZipList a) gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ZipList a -> m (ZipList a) gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ZipList a -> m (ZipList a) | |||||
Generic (ZipList a) | |||||
Defined in Control.Applicative Associated Types
| |||||
IsList (ZipList a) | |||||
Read a => Read (ZipList a) | |||||
Defined in Control.Applicative | |||||
Show a => Show (ZipList a) | |||||
Eq a => Eq (ZipList a) | |||||
Ord a => Ord (ZipList a) | |||||
Defined in Control.Applicative | |||||
type Rep1 ZipList | |||||
Defined in Control.Applicative type Rep1 ZipList = D1 ('MetaData "ZipList" "Control.Applicative" "base" 'True) (C1 ('MetaCons "ZipList" 'PrefixI 'True) (S1 ('MetaSel ('Just "getZipList") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 []))) | |||||
type Rep (ZipList a) | |||||
Defined in Control.Applicative type Rep (ZipList a) = D1 ('MetaData "ZipList" "Control.Applicative" "base" 'True) (C1 ('MetaCons "ZipList" 'PrefixI 'True) (S1 ('MetaSel ('Just "getZipList") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [a]))) | |||||
type Item (ZipList a) | |||||
Defined in GHC.IsList type Item (ZipList a) = a |
type XMLParser a = Parser (Content Posn) a Source #
We need a parsing monad for reading generic XML Content into specific datatypes. This is a specialisation of the Text.ParserCombinators.Poly ones, where the input token type is fixed as XML Content.
content :: String -> XMLParser (Content Posn) Source #
The most primitive combinator for XMLParser - get one content item.
posnElement :: [String] -> XMLParser (Posn, Element Posn) Source #
A specialisation of posnElementWith (==)
.
element :: [String] -> XMLParser (Element Posn) Source #
Get the next content element, checking that it has one of the required tags. (Skips over comments and whitespace, rejects text and refs.)
interior :: Element Posn -> XMLParser a -> XMLParser a Source #
Run an XMLParser on the contents of the given element (i.e. not on the current monadic content sequence), checking that the contents are exhausted, before returning the calculated value within the current parser context.
attributes :: XmlAttributes a => Element Posn -> XMLParser a Source #
Do some parsing of the attributes of the given element
posnElementWith :: (String -> String -> Bool) -> [String] -> XMLParser (Posn, Element Posn) Source #
Get the next content element, checking that it has one of the required tags, using the given matching function. (Skips over comments and whitespace, rejects text and refs. Also returns position of element.)
elementWith :: (String -> String -> Bool) -> [String] -> XMLParser (Element Posn) Source #
Like element, only permits a more flexible match against the tagname.
inElementWith :: (String -> String -> Bool) -> String -> XMLParser a -> XMLParser a Source #
A combination of elementWith + interior.
choice :: XmlContent a => (a -> b) -> XMLParser b -> XMLParser b Source #
'choice f p' means if parseContents succeeds, apply f to the result, otherwise use the continuation parser.
definite :: XmlContent a => XMLParser a -> String -> String -> XMLParser a Source #
not sure this is needed now. 'definite p' previously ensured that an element was definitely present. Now I think the monad might take care of that for us.
Auxiliaries for generating in the XmlContent class
mkElem :: XmlContent a => a -> [Content ()] -> Content () Source #
Generate an element with no attributes, named for its HType.
mkElemC :: String -> [Content ()] -> Content () Source #
Generate an element with no attributes, named directly.
toCData :: String -> [Content ()] Source #
Turn a string into an XML CDATA section.
(i.e. special characters like &
are preserved without interpretation.)
Auxiliaries for the attribute-related classes
maybeToAttr :: (String -> a -> Maybe Attribute) -> String -> Maybe a -> Maybe Attribute Source #
defaultToAttr :: (String -> a -> Maybe Attribute) -> String -> Defaultable a -> Maybe Attribute Source #
defaultA :: (String -> Attribute -> Maybe a) -> a -> String -> [Attribute] -> Defaultable a Source #
fromAttrToStr :: String -> Attribute -> Maybe String Source #
toAttrFrStr :: String -> String -> Maybe Attribute Source #
data Defaultable a Source #
If an attribute is defaultable, then it either takes the default value (which is omitted from the output), or a non-default value (which obviously must be printed).
Constructors
Default a | |
NonDefault a |
Instances
Show a => Show (Defaultable a) Source # | |
Defined in Text.XML.HaXml.XmlContent.Parser Methods showsPrec :: Int -> Defaultable a -> ShowS show :: Defaultable a -> String showList :: [Defaultable a] -> ShowS | |
Eq a => Eq (Defaultable a) Source # | |
Defined in Text.XML.HaXml.XmlContent.Parser |
Explicit representation of Haskell datatype information
module Text.XML.HaXml.TypeMapping
Types useful for some content models
The List1 type represents lists with at least one element. It is required for DTD content models that use + as a modifier.
Constructors
NonEmpty [a] |
data ANYContent Source #
A type corresponding to XML's ANY contentspec.
It is either a list of unconverted xml Content
or some XmlContent
-able value.
Parsing functions (e.g. parseContents
) will always produce UnConverted
.
Note: The Show instance for UnConverted
uses verbatim
.
Constructors
(XmlContent a, Show a) => ANYContent a | |
UnConverted [Content Posn] |
Instances
HTypeable ANYContent Source # | |
Defined in Text.XML.HaXml.XmlContent.Parser Methods toHType :: ANYContent -> HType Source # | |
XmlContent ANYContent Source # | |
Defined in Text.XML.HaXml.XmlContent.Parser Methods parseContents :: XMLParser ANYContent Source # toContents :: ANYContent -> [Content ()] Source # xToChar :: ANYContent -> Char Source # xFromChar :: Char -> ANYContent Source # | |
Show ANYContent Source # | |
Defined in Text.XML.HaXml.XmlContent.Parser Methods showsPrec :: Int -> ANYContent -> ShowS show :: ANYContent -> String showList :: [ANYContent] -> ShowS | |
Eq ANYContent Source # | |
Defined in Text.XML.HaXml.XmlContent.Parser |