{-# LANGUAGE CPP #-}
{-# LANGUAGE RecordWildCards, PatternGuards #-}
module Data.GI.GIR.Type
( parseType
, queryCType
, parseCType
, queryElementCType
, parseOptionalType
) where
#include "HsBaseConfig.h"
import Data.Maybe (catMaybes)
#if !MIN_VERSION_base(4,11,0)
import Data.Monoid ((<>))
#endif
import Data.Text (Text)
import qualified Data.Text as T
import Data.GI.GIR.BasicTypes (Type(..), BasicType(..))
import Data.GI.GIR.Parser
nameToBasicType :: Text -> Maybe BasicType
nameToBasicType :: ParseError -> Maybe BasicType
nameToBasicType ParseError
"gpointer" = BasicType -> Maybe BasicType
forall a. a -> Maybe a
Just BasicType
TPtr
nameToBasicType ParseError
"gboolean" = BasicType -> Maybe BasicType
forall a. a -> Maybe a
Just BasicType
TBoolean
nameToBasicType ParseError
"gchar" = BasicType -> Maybe BasicType
forall a. a -> Maybe a
Just BasicType
TInt8
nameToBasicType ParseError
"gint" = BasicType -> Maybe BasicType
forall a. a -> Maybe a
Just BasicType
TInt
nameToBasicType ParseError
"guint" = BasicType -> Maybe BasicType
forall a. a -> Maybe a
Just BasicType
TUInt
nameToBasicType ParseError
"glong" = BasicType -> Maybe BasicType
forall a. a -> Maybe a
Just BasicType
TLong
nameToBasicType ParseError
"gulong" = BasicType -> Maybe BasicType
forall a. a -> Maybe a
Just BasicType
TULong
nameToBasicType ParseError
"gint8" = BasicType -> Maybe BasicType
forall a. a -> Maybe a
Just BasicType
TInt8
nameToBasicType ParseError
"guint8" = BasicType -> Maybe BasicType
forall a. a -> Maybe a
Just BasicType
TUInt8
nameToBasicType ParseError
"gint16" = BasicType -> Maybe BasicType
forall a. a -> Maybe a
Just BasicType
TInt16
nameToBasicType ParseError
"guint16" = BasicType -> Maybe BasicType
forall a. a -> Maybe a
Just BasicType
TUInt16
nameToBasicType ParseError
"gint32" = BasicType -> Maybe BasicType
forall a. a -> Maybe a
Just BasicType
TInt32
nameToBasicType ParseError
"guint32" = BasicType -> Maybe BasicType
forall a. a -> Maybe a
Just BasicType
TUInt32
nameToBasicType ParseError
"gint64" = BasicType -> Maybe BasicType
forall a. a -> Maybe a
Just BasicType
TInt64
nameToBasicType ParseError
"guint64" = BasicType -> Maybe BasicType
forall a. a -> Maybe a
Just BasicType
TUInt64
nameToBasicType ParseError
"gfloat" = BasicType -> Maybe BasicType
forall a. a -> Maybe a
Just BasicType
TFloat
nameToBasicType ParseError
"gdouble" = BasicType -> Maybe BasicType
forall a. a -> Maybe a
Just BasicType
TDouble
nameToBasicType ParseError
"gunichar" = BasicType -> Maybe BasicType
forall a. a -> Maybe a
Just BasicType
TUniChar
nameToBasicType ParseError
"GType" = BasicType -> Maybe BasicType
forall a. a -> Maybe a
Just BasicType
TGType
nameToBasicType ParseError
"utf8" = BasicType -> Maybe BasicType
forall a. a -> Maybe a
Just BasicType
TUTF8
nameToBasicType ParseError
"filename" = BasicType -> Maybe BasicType
forall a. a -> Maybe a
Just BasicType
TFileName
nameToBasicType ParseError
"gintptr" = BasicType -> Maybe BasicType
forall a. a -> Maybe a
Just BasicType
TIntPtr
nameToBasicType ParseError
"guintptr" = BasicType -> Maybe BasicType
forall a. a -> Maybe a
Just BasicType
TUIntPtr
nameToBasicType ParseError
"gshort" = BasicType -> Maybe BasicType
forall a. a -> Maybe a
Just BasicType
TShort
nameToBasicType ParseError
"gushort" = BasicType -> Maybe BasicType
forall a. a -> Maybe a
Just BasicType
TUShort
nameToBasicType ParseError
"gssize" = BasicType -> Maybe BasicType
forall a. a -> Maybe a
Just BasicType
TSSize
nameToBasicType ParseError
"gsize" = BasicType -> Maybe BasicType
forall a. a -> Maybe a
Just BasicType
TSize
nameToBasicType ParseError
"time_t" = BasicType -> Maybe BasicType
forall a. a -> Maybe a
Just BasicType
Ttime_t
nameToBasicType ParseError
"off_t" = BasicType -> Maybe BasicType
forall a. a -> Maybe a
Just BasicType
Toff_t
nameToBasicType ParseError
"dev_t" = BasicType -> Maybe BasicType
forall a. a -> Maybe a
Just BasicType
Tdev_t
nameToBasicType ParseError
"gid_t" = BasicType -> Maybe BasicType
forall a. a -> Maybe a
Just BasicType
Tgid_t
nameToBasicType ParseError
"pid_t" = BasicType -> Maybe BasicType
forall a. a -> Maybe a
Just BasicType
Tpid_t
nameToBasicType ParseError
"socklen_t" = BasicType -> Maybe BasicType
forall a. a -> Maybe a
Just BasicType
Tsocklen_t
nameToBasicType ParseError
"uid_t" = BasicType -> Maybe BasicType
forall a. a -> Maybe a
Just BasicType
Tuid_t
nameToBasicType ParseError
_ = Maybe BasicType
forall a. Maybe a
Nothing
parseArrayInfo :: Parser Type
parseArrayInfo :: Parser Type
parseArrayInfo = Name -> Parser (Maybe ParseError)
queryAttr Name
"name" Parser (Maybe ParseError)
-> (Maybe ParseError -> Parser Type) -> Parser Type
forall a b.
ReaderT ParseContext (Except ParseError) a
-> (a -> ReaderT ParseContext (Except ParseError) b)
-> ReaderT ParseContext (Except ParseError) b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Just ParseError
"GLib.Array" -> Type -> Type
TGArray (Type -> Type) -> Parser Type -> Parser Type
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Type
parseType
Just ParseError
"GLib.PtrArray" -> Type -> Type
TPtrArray (Type -> Type) -> Parser Type -> Parser Type
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Type
parseType
Just ParseError
"GLib.ByteArray" -> Type -> Parser Type
forall a. a -> ReaderT ParseContext (Except ParseError) a
forall (m :: * -> *) a. Monad m => a -> m a
return Type
TByteArray
Just ParseError
other -> ParseError -> Parser Type
forall a. ParseError -> Parser a
parseError (ParseError -> Parser Type) -> ParseError -> Parser Type
forall a b. (a -> b) -> a -> b
$ ParseError
"Unsupported array type: \"" ParseError -> ParseError -> ParseError
forall a. Semigroup a => a -> a -> a
<> ParseError
other ParseError -> ParseError -> ParseError
forall a. Semigroup a => a -> a -> a
<> ParseError
"\""
Maybe ParseError
Nothing -> Parser Type
parseCArrayType
parseCArrayType :: Parser Type
parseCArrayType :: Parser Type
parseCArrayType = do
zeroTerminated <- Name -> Parser (Maybe ParseError)
queryAttr Name
"zero-terminated" Parser (Maybe ParseError)
-> (Maybe ParseError
-> ReaderT ParseContext (Except ParseError) Bool)
-> ReaderT ParseContext (Except ParseError) Bool
forall a b.
ReaderT ParseContext (Except ParseError) a
-> (a -> ReaderT ParseContext (Except ParseError) b)
-> ReaderT ParseContext (Except ParseError) b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Just ParseError
b -> ParseError -> ReaderT ParseContext (Except ParseError) Bool
parseBool ParseError
b
Maybe ParseError
Nothing -> Bool -> ReaderT ParseContext (Except ParseError) Bool
forall a. a -> ReaderT ParseContext (Except ParseError) a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True
length <- queryAttr "length" >>= \case
Just ParseError
l -> ParseError -> ReaderT ParseContext (Except ParseError) Int
forall a. Integral a => ParseError -> Parser a
parseIntegral ParseError
l
Maybe ParseError
Nothing -> Int -> ReaderT ParseContext (Except ParseError) Int
forall a. a -> ReaderT ParseContext (Except ParseError) a
forall (m :: * -> *) a. Monad m => a -> m a
return (-Int
1)
fixedSize <- queryAttr "fixed-size" >>= \case
Just ParseError
s -> ParseError -> ReaderT ParseContext (Except ParseError) Int
forall a. Integral a => ParseError -> Parser a
parseIntegral ParseError
s
Maybe ParseError
Nothing -> Int -> ReaderT ParseContext (Except ParseError) Int
forall a. a -> ReaderT ParseContext (Except ParseError) a
forall (m :: * -> *) a. Monad m => a -> m a
return (-Int
1)
elementType <- parseType
return $ TCArray zeroTerminated fixedSize length elementType
parseHashTable :: Parser Type
parseHashTable :: Parser Type
parseHashTable = Parser [Maybe Type]
parseTypeElements Parser [Maybe Type] -> ([Maybe Type] -> Parser Type) -> Parser Type
forall a b.
ReaderT ParseContext (Except ParseError) a
-> (a -> ReaderT ParseContext (Except ParseError) b)
-> ReaderT ParseContext (Except ParseError) b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
[] -> Type -> Parser Type
forall a. a -> ReaderT ParseContext (Except ParseError) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Type -> Parser Type) -> Type -> Parser Type
forall a b. (a -> b) -> a -> b
$ Type -> Type -> Type
TGHash (BasicType -> Type
TBasicType BasicType
TPtr) (BasicType -> Type
TBasicType BasicType
TPtr)
[Just Type
key, Just Type
value] -> Type -> Parser Type
forall a. a -> ReaderT ParseContext (Except ParseError) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Type -> Parser Type) -> Type -> Parser Type
forall a b. (a -> b) -> a -> b
$ Type -> Type -> Type
TGHash Type
key Type
value
[Maybe Type]
other -> ParseError -> Parser Type
forall a. ParseError -> Parser a
parseError (ParseError -> Parser Type) -> ParseError -> Parser Type
forall a b. (a -> b) -> a -> b
$ ParseError
"Unsupported hash type: "
ParseError -> ParseError -> ParseError
forall a. Semigroup a => a -> a -> a
<> String -> ParseError
T.pack ([Maybe Type] -> String
forall a. Show a => a -> String
show [Maybe Type]
other)
parseClosure :: Parser Type
parseClosure :: Parser Type
parseClosure = Name -> Parser (Maybe ParseError)
queryAttr Name
"closure-type" Parser (Maybe ParseError)
-> (Maybe ParseError -> Parser Type) -> Parser Type
forall a b.
ReaderT ParseContext (Except ParseError) a
-> (a -> ReaderT ParseContext (Except ParseError) b)
-> ReaderT ParseContext (Except ParseError) b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Just ParseError
t -> (Maybe Type -> Type
TGClosure (Maybe Type -> Type) -> (Type -> Maybe Type) -> Type -> Type
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Type -> Maybe Type
forall a. a -> Maybe a
Just) (Type -> Type) -> Parser Type -> Parser Type
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParseError -> Parser Type
parseTypeName ParseError
t
Maybe ParseError
Nothing -> Type -> Parser Type
forall a. a -> ReaderT ParseContext (Except ParseError) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Type -> Parser Type) -> Type -> Parser Type
forall a b. (a -> b) -> a -> b
$ Maybe Type -> Type
TGClosure Maybe Type
forall a. Maybe a
Nothing
parseListType :: Parser Type
parseListType :: Parser Type
parseListType = Parser (Maybe Type)
queryType Parser (Maybe Type) -> (Maybe Type -> Parser Type) -> Parser Type
forall a b.
ReaderT ParseContext (Except ParseError) a
-> (a -> ReaderT ParseContext (Except ParseError) b)
-> ReaderT ParseContext (Except ParseError) b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Just Type
t -> Type -> Parser Type
forall a. a -> ReaderT ParseContext (Except ParseError) a
forall (m :: * -> *) a. Monad m => a -> m a
return Type
t
Maybe Type
Nothing -> Type -> Parser Type
forall a. a -> ReaderT ParseContext (Except ParseError) a
forall (m :: * -> *) a. Monad m => a -> m a
return (BasicType -> Type
TBasicType BasicType
TPtr)
parseFundamentalType :: Text -> Text -> Parser Type
parseFundamentalType :: ParseError -> ParseError -> Parser Type
parseFundamentalType ParseError
"GLib" ParseError
"List" = Type -> Type
TGList (Type -> Type) -> Parser Type -> Parser Type
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Type
parseListType
parseFundamentalType ParseError
"GLib" ParseError
"SList" = Type -> Type
TGSList (Type -> Type) -> Parser Type -> Parser Type
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Type
parseListType
parseFundamentalType ParseError
"GLib" ParseError
"HashTable" = Parser Type
parseHashTable
parseFundamentalType ParseError
"GLib" ParseError
"Error" = Type -> Parser Type
forall a. a -> ReaderT ParseContext (Except ParseError) a
forall (m :: * -> *) a. Monad m => a -> m a
return Type
TError
parseFundamentalType ParseError
"GLib" ParseError
"Variant" = Type -> Parser Type
forall a. a -> ReaderT ParseContext (Except ParseError) a
forall (m :: * -> *) a. Monad m => a -> m a
return Type
TVariant
parseFundamentalType ParseError
"GObject" ParseError
"ParamSpec" = Type -> Parser Type
forall a. a -> ReaderT ParseContext (Except ParseError) a
forall (m :: * -> *) a. Monad m => a -> m a
return Type
TParamSpec
parseFundamentalType ParseError
"GObject" ParseError
"Value" = Type -> Parser Type
forall a. a -> ReaderT ParseContext (Except ParseError) a
forall (m :: * -> *) a. Monad m => a -> m a
return Type
TGValue
parseFundamentalType ParseError
"GLib" ParseError
"ObjectPath" = Type -> Parser Type
forall a. a -> ReaderT ParseContext (Except ParseError) a
forall (m :: * -> *) a. Monad m => a -> m a
return (BasicType -> Type
TBasicType BasicType
TUTF8)
parseFundamentalType ParseError
"GObject" ParseError
"Closure" = Parser Type
parseClosure
parseFundamentalType ParseError
ns ParseError
n = Name -> Parser Type
resolveQualifiedTypeName (ParseError -> ParseError -> Name
Name ParseError
ns ParseError
n)
parseTypeName :: Text -> Parser Type
parseTypeName :: ParseError -> Parser Type
parseTypeName ParseError
typeName = case ParseError -> Maybe BasicType
nameToBasicType ParseError
typeName of
Just BasicType
b -> Type -> Parser Type
forall a. a -> ReaderT ParseContext (Except ParseError) a
forall (m :: * -> *) a. Monad m => a -> m a
return (BasicType -> Type
TBasicType BasicType
b)
Maybe BasicType
Nothing -> case (Char -> Bool) -> ParseError -> [ParseError]
T.split (Char
'.' Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
==) ParseError
typeName of
[ParseError
ns, ParseError
n] -> ParseError -> ParseError -> Parser Type
parseFundamentalType ParseError
ns ParseError
n
[ParseError
n] -> do
ns <- Parser ParseError
currentNamespace
parseFundamentalType ns n
[ParseError]
_ -> ParseError -> Parser Type
forall a. ParseError -> Parser a
parseError (ParseError -> Parser Type) -> ParseError -> Parser Type
forall a b. (a -> b) -> a -> b
$ ParseError
"Unsupported type form: \""
ParseError -> ParseError -> ParseError
forall a. Semigroup a => a -> a -> a
<> ParseError
typeName ParseError -> ParseError -> ParseError
forall a. Semigroup a => a -> a -> a
<> ParseError
"\""
parseTypeInfo :: Parser (Maybe Type)
parseTypeInfo :: Parser (Maybe Type)
parseTypeInfo = do
typeName <- Name -> Parser ParseError
getAttr Name
"name"
if typeName == "none"
then return Nothing
else Just <$> parseTypeName typeName
parseTypeElements :: Parser [Maybe Type]
parseTypeElements :: Parser [Maybe Type]
parseTypeElements = do
types <- ParseError -> Parser (Maybe Type) -> Parser [Maybe Type]
forall a. ParseError -> Parser a -> Parser [a]
parseChildrenWithLocalName ParseError
"type" Parser (Maybe Type)
parseTypeInfo
arrays <- parseChildrenWithLocalName "array" parseArrayInfo
return (types ++ map Just arrays)
queryCType :: Parser (Maybe Text)
queryCType :: Parser (Maybe ParseError)
queryCType = GIRXMLNamespace -> Name -> Parser (Maybe ParseError)
queryAttrWithNamespace GIRXMLNamespace
CGIRNS Name
"type"
parseCType :: Parser Text
parseCType :: Parser ParseError
parseCType = GIRXMLNamespace -> Name -> Parser ParseError
getAttrWithNamespace GIRXMLNamespace
CGIRNS Name
"type"
parseCTypeNameElements :: Parser [Text]
parseCTypeNameElements :: Parser [ParseError]
parseCTypeNameElements = do
types <- ParseError
-> Parser (Maybe ParseError) -> Parser [Maybe ParseError]
forall a. ParseError -> Parser a -> Parser [a]
parseChildrenWithLocalName ParseError
"type" Parser (Maybe ParseError)
queryCType
arrays <- parseChildrenWithLocalName "array" queryCType
return (catMaybes (types ++ arrays))
queryType :: Parser (Maybe Type)
queryType :: Parser (Maybe Type)
queryType = Parser [Maybe Type]
parseTypeElements Parser [Maybe Type]
-> ([Maybe Type] -> Parser (Maybe Type)) -> Parser (Maybe Type)
forall a b.
ReaderT ParseContext (Except ParseError) a
-> (a -> ReaderT ParseContext (Except ParseError) b)
-> ReaderT ParseContext (Except ParseError) b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
[Just Type
e] -> Maybe Type -> Parser (Maybe Type)
forall a. a -> ReaderT ParseContext (Except ParseError) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Type -> Maybe Type
forall a. a -> Maybe a
Just Type
e)
[] -> Maybe Type -> Parser (Maybe Type)
forall a. a -> ReaderT ParseContext (Except ParseError) a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Type
forall a. Maybe a
Nothing
[Maybe Type
Nothing] -> ParseError -> Parser (Maybe Type)
forall a. ParseError -> Parser a
parseError (ParseError -> Parser (Maybe Type))
-> ParseError -> Parser (Maybe Type)
forall a b. (a -> b) -> a -> b
$ ParseError
"Unexpected \"none\" type."
[Maybe Type]
_ -> ParseError -> Parser (Maybe Type)
forall a. ParseError -> Parser a
parseError (ParseError -> Parser (Maybe Type))
-> ParseError -> Parser (Maybe Type)
forall a b. (a -> b) -> a -> b
$ ParseError
"Found more than one type for the element."
parseType :: Parser Type
parseType :: Parser Type
parseType = Parser [Maybe Type]
parseTypeElements Parser [Maybe Type] -> ([Maybe Type] -> Parser Type) -> Parser Type
forall a b.
ReaderT ParseContext (Except ParseError) a
-> (a -> ReaderT ParseContext (Except ParseError) b)
-> ReaderT ParseContext (Except ParseError) b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
[Just Type
e] -> Type -> Parser Type
forall a. a -> ReaderT ParseContext (Except ParseError) a
forall (m :: * -> *) a. Monad m => a -> m a
return Type
e
[] -> ParseError -> Parser Type
forall a. ParseError -> Parser a
parseError (ParseError -> Parser Type) -> ParseError -> Parser Type
forall a b. (a -> b) -> a -> b
$ ParseError
"Did not find a type for the element."
[Maybe Type
Nothing] -> ParseError -> Parser Type
forall a. ParseError -> Parser a
parseError (ParseError -> Parser Type) -> ParseError -> Parser Type
forall a b. (a -> b) -> a -> b
$ ParseError
"Unexpected \"none\" type."
[Maybe Type]
_ -> ParseError -> Parser Type
forall a. ParseError -> Parser a
parseError (ParseError -> Parser Type) -> ParseError -> Parser Type
forall a b. (a -> b) -> a -> b
$ ParseError
"Found more than one type for the element."
parseOptionalType :: Parser (Maybe Type)
parseOptionalType :: Parser (Maybe Type)
parseOptionalType =
Parser [Maybe Type]
parseTypeElements Parser [Maybe Type]
-> ([Maybe Type] -> Parser (Maybe Type)) -> Parser (Maybe Type)
forall a b.
ReaderT ParseContext (Except ParseError) a
-> (a -> ReaderT ParseContext (Except ParseError) b)
-> ReaderT ParseContext (Except ParseError) b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
[Maybe Type
e] -> Maybe Type -> Parser (Maybe Type)
forall a. a -> ReaderT ParseContext (Except ParseError) a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Type
e
[] -> ParseError -> Parser (Maybe Type)
forall a. ParseError -> Parser a
parseError (ParseError -> Parser (Maybe Type))
-> ParseError -> Parser (Maybe Type)
forall a b. (a -> b) -> a -> b
$ ParseError
"Did not find a type for the element."
[Maybe Type]
_ -> ParseError -> Parser (Maybe Type)
forall a. ParseError -> Parser a
parseError (ParseError -> Parser (Maybe Type))
-> ParseError -> Parser (Maybe Type)
forall a b. (a -> b) -> a -> b
$ ParseError
"Found more than one type for the element."
queryElementCType :: Parser (Maybe Text)
queryElementCType :: Parser (Maybe ParseError)
queryElementCType = Parser [ParseError]
parseCTypeNameElements Parser [ParseError]
-> ([ParseError] -> Parser (Maybe ParseError))
-> Parser (Maybe ParseError)
forall a b.
ReaderT ParseContext (Except ParseError) a
-> (a -> ReaderT ParseContext (Except ParseError) b)
-> ReaderT ParseContext (Except ParseError) b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
[ParseError
ctype] -> Maybe ParseError -> Parser (Maybe ParseError)
forall a. a -> ReaderT ParseContext (Except ParseError) a
forall (m :: * -> *) a. Monad m => a -> m a
return (ParseError -> Maybe ParseError
forall a. a -> Maybe a
Just ParseError
ctype)
[] -> Maybe ParseError -> Parser (Maybe ParseError)
forall a. a -> ReaderT ParseContext (Except ParseError) a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ParseError
forall a. Maybe a
Nothing
[ParseError]
_ -> ParseError -> Parser (Maybe ParseError)
forall a. ParseError -> Parser a
parseError (ParseError -> Parser (Maybe ParseError))
-> ParseError -> Parser (Maybe ParseError)
forall a b. (a -> b) -> a -> b
$ ParseError
"Found more than one type for the element."