{- - generated by DtdToHaskell (from HaXml 1.13.3) - altered to fix ambiguities and build errors - (why is this the "preferred" HaXml version, anyway?) -} module Data.PropertyList.Xml.Dtd_1_13 where import Text.XML.HaXml.Xml2Haskell import Text.XML.HaXml.OneOfN import Data.Char (isSpace) import Prelude (Eq, Show, String, Maybe(..), all, concatMap, (++)) {-Type decls-} -- |DtdToHaskell-generated type representing XML trees that match the PropertyList-1.0 dtd. -- This is an opaque representation of a structurally-sound property list -- which might still contain invalid data. End users should never need to -- use this type, but if they do, it can be manipulated with the constructors -- and deconstructors in "Data.PropertyList.Algebra". data Plist = PlistArray Plist_Attrs Array | PlistData Plist_Attrs Data | PlistDate Plist_Attrs Date | PlistDict Plist_Attrs Dict | PlistAReal Plist_Attrs AReal | PlistAInteger Plist_Attrs AInteger | PlistAString Plist_Attrs AString | PlistTrue Plist_Attrs True | PlistFalse Plist_Attrs False deriving (Eq,Show) data Plist_Attrs = Plist_Attrs { plistVersion :: (Defaultable String) } deriving (Eq,Show) newtype Array = Array [(OneOf9 Array Data Date Dict AReal AInteger AString True False)] deriving (Eq,Show) newtype Dict = Dict [Dict_] deriving (Eq,Show) data Dict_ = Dict_ Key (OneOf9 Array Data Date Dict AReal AInteger AString True False) deriving (Eq,Show) newtype Key = Key String deriving (Eq,Show) newtype AString = AString String deriving (Eq,Show) newtype Data = Data String deriving (Eq,Show) newtype Date = Date String deriving (Eq,Show) data True = True deriving (Eq,Show) data False = False deriving (Eq,Show) newtype AReal = AReal String deriving (Eq,Show) newtype AInteger = AInteger String deriving (Eq,Show) {-Instance decls-} instance XmlContent Plist where fromElem (CElem (Elem "plist" as c0):rest) = case (fromElem c0) of (Just a,_) -> (Just (PlistArray (fromAttrs as) a), rest) (_,_) -> case (fromElem c0) of (Just a,_) -> (Just (PlistData (fromAttrs as) a), rest) (_,_) -> case (fromElem c0) of (Just a,_) -> (Just (PlistDate (fromAttrs as) a), rest) (_,_) -> case (fromElem c0) of (Just a,_) -> (Just (PlistDict (fromAttrs as) a), rest) (_,_) -> case (fromElem c0) of (Just a,_) -> (Just (PlistAReal (fromAttrs as) a), rest) (_,_) -> case (fromElem c0) of (Just a,_) -> (Just (PlistAInteger (fromAttrs as) a), rest) (_,_) -> case (fromElem c0) of (Just a,_) -> (Just (PlistAString (fromAttrs as) a), rest) (_,_) -> case (fromElem c0) of (Just a,_) -> (Just (PlistTrue (fromAttrs as) a), rest) (_,_) -> case (fromElem c0) of (Just a,_) -> (Just (PlistFalse (fromAttrs as) a), rest) (_,_) -> (Nothing, c0) fromElem (CMisc _:rest) = fromElem rest fromElem (CString _ s:rest) | all isSpace s = fromElem rest fromElem rest = (Nothing, rest) toElem (PlistArray as a) = [CElem (Elem "plist" (toAttrs as) (toElem a) )] toElem (PlistData as a) = [CElem (Elem "plist" (toAttrs as) (toElem a) )] toElem (PlistDate as a) = [CElem (Elem "plist" (toAttrs as) (toElem a) )] toElem (PlistDict as a) = [CElem (Elem "plist" (toAttrs as) (toElem a) )] toElem (PlistAReal as a) = [CElem (Elem "plist" (toAttrs as) (toElem a) )] toElem (PlistAInteger as a) = [CElem (Elem "plist" (toAttrs as) (toElem a) )] toElem (PlistAString as a) = [CElem (Elem "plist" (toAttrs as) (toElem a) )] toElem (PlistTrue as a) = [CElem (Elem "plist" (toAttrs as) (toElem a) )] toElem (PlistFalse as a) = [CElem (Elem "plist" (toAttrs as) (toElem a) )] instance XmlAttributes Plist_Attrs where fromAttrs as = Plist_Attrs { plistVersion = defaultA fromAttrToStr "1.0" "version" as } toAttrs v = catMaybes [ defaultToAttr toAttrFrStr "version" (plistVersion v) ] instance XmlContent Array where fromElem (CElem (Elem "array" [] c0):rest) = (\(a,ca)-> (Just (Array a), rest)) (many fromElem c0) fromElem (CMisc _:rest) = fromElem rest fromElem (CString _ s:rest) | all isSpace s = fromElem rest fromElem rest = (Nothing, rest) toElem (Array a) = [CElem (Elem "array" [] (concatMap toElem a))] instance XmlContent Dict where fromElem (CElem (Elem "dict" [] c0):rest) = (\(a,ca)-> (Just (Dict a), rest)) (many fromElem c0) fromElem (CMisc _:rest) = fromElem rest fromElem (CString _ s:rest) | all isSpace s = fromElem rest fromElem rest = (Nothing, rest) toElem (Dict a) = [CElem (Elem "dict" [] (concatMap toElem a))] instance XmlContent Dict_ where fromElem c0 = case (\(a,ca)-> (\(b,cb)-> (a,b,cb)) (fromElem ca)) (fromElem c0) of (Just a,Just b,rest) -> (Just (Dict_ a b), rest) (_,_,_) -> (Nothing, c0) toElem (Dict_ a b) = (toElem a ++ toElem b) instance XmlContent Key where fromElem (CElem (Elem "key" [] c0):rest) = (\(a,ca)-> (Just (Key a), rest)) (definite fromText "text" "key" c0) fromElem (CMisc _:rest) = fromElem rest fromElem (CString _ s:rest) | all isSpace s = fromElem rest fromElem rest = (Nothing, rest) toElem (Key a) = [CElem (Elem "key" [] (toText a))] instance XmlContent AString where fromElem (CElem (Elem "string" [] c0):rest) = (\(a,ca)-> (Just (AString a), rest)) (definite fromText "text" "string" c0) fromElem (CMisc _:rest) = fromElem rest fromElem (CString _ s:rest) | all isSpace s = fromElem rest fromElem rest = (Nothing, rest) toElem (AString a) = [CElem (Elem "string" [] (toText a))] instance XmlContent Data where fromElem (CElem (Elem "data" [] c0):rest) = (\(a,ca)-> (Just (Data a), rest)) (definite fromText "text" "data" c0) fromElem (CMisc _:rest) = fromElem rest fromElem (CString _ s:rest) | all isSpace s = fromElem rest fromElem rest = (Nothing, rest) toElem (Data a) = [CElem (Elem "data" [] (toText a))] instance XmlContent Date where fromElem (CElem (Elem "date" [] c0):rest) = (\(a,ca)-> (Just (Date a), rest)) (definite fromText "text" "date" c0) fromElem (CMisc _:rest) = fromElem rest fromElem (CString _ s:rest) | all isSpace s = fromElem rest fromElem rest = (Nothing, rest) toElem (Date a) = [CElem (Elem "date" [] (toText a))] instance XmlContent True where fromElem (CElem (Elem "true" [] []):rest) = (Just True, rest) fromElem (CMisc _:rest) = fromElem rest fromElem (CString _ s:rest) | all isSpace s = fromElem rest fromElem rest = (Nothing, rest) toElem True = [CElem (Elem "true" [] [])] instance XmlContent False where fromElem (CElem (Elem "false" [] []):rest) = (Just False, rest) fromElem (CMisc _:rest) = fromElem rest fromElem (CString _ s:rest) | all isSpace s = fromElem rest fromElem rest = (Nothing, rest) toElem False = [CElem (Elem "false" [] [])] instance XmlContent AReal where fromElem (CElem (Elem "real" [] c0):rest) = (\(a,ca)-> (Just (AReal a), rest)) (definite fromText "text" "real" c0) fromElem (CMisc _:rest) = fromElem rest fromElem (CString _ s:rest) | all isSpace s = fromElem rest fromElem rest = (Nothing, rest) toElem (AReal a) = [CElem (Elem "real" [] (toText a))] instance XmlContent AInteger where fromElem (CElem (Elem "integer" [] c0):rest) = (\(a,ca)-> (Just (AInteger a), rest)) (definite fromText "text" "integer" c0) fromElem (CMisc _:rest) = fromElem rest fromElem (CString _ s:rest) | all isSpace s = fromElem rest fromElem rest = (Nothing, rest) toElem (AInteger a) = [CElem (Elem "integer" [] (toText a))] {-Done-}