[delete all HaXml example code Malcolm.Wallace@cs.york.ac.uk**20070123153526] { hunk ./examples/AlbumDTD.hs 1 -module AlbumDTD where - -import Text.XML.HaXml.XmlContent -import Text.XML.HaXml.OneOfN - - -{-Type decls-} - -data Album = Album Title Artist (Maybe Recording) Coverart - [Catalogno] Personnel [Track] Notes - deriving (Eq,Show) -newtype Title = Title String deriving (Eq,Show) -newtype Artist = Artist String deriving (Eq,Show) -data Recording = Recording - { recordingDate :: (Maybe String) - , recordingPlace :: (Maybe String) - } deriving (Eq,Show) -data Coverart = Coverart Coverart_Attrs (Maybe Location) - deriving (Eq,Show) -data Coverart_Attrs = Coverart_Attrs - { coverartStyle :: String - } deriving (Eq,Show) -data Location = Location - { locationThumbnail :: (Maybe String) - , locationFullsize :: (Maybe String) - } deriving (Eq,Show) -data Catalogno = Catalogno - { catalognoLabel :: String - , catalognoNumber :: String - , catalognoFormat :: (Maybe Catalogno_Format) - , catalognoReleasedate :: (Maybe String) - , catalognoCountry :: (Maybe String) - } deriving (Eq,Show) -data Catalogno_Format = Catalogno_Format_CD | Catalogno_Format_LP - | Catalogno_Format_MiniDisc - deriving (Eq,Show) -newtype Personnel = Personnel [Player] deriving (Eq,Show) -data Player = Player - { playerName :: String - , playerInstrument :: String - } deriving (Eq,Show) -data Track = Track - { trackTitle :: String - , trackCredit :: (Maybe String) - , trackTiming :: (Maybe String) - } deriving (Eq,Show) -data Notes = Notes Notes_Attrs [Notes_] - deriving (Eq,Show) -data Notes_Attrs = Notes_Attrs - { notesAuthor :: (Maybe String) - } deriving (Eq,Show) -data Notes_ = Notes_Str String - | Notes_Albumref Albumref - | Notes_Trackref Trackref - deriving (Eq,Show) -data Albumref = Albumref Albumref_Attrs String - deriving (Eq,Show) -data Albumref_Attrs = Albumref_Attrs - { albumrefLink :: String - } deriving (Eq,Show) -data Trackref = Trackref Trackref_Attrs String - deriving (Eq,Show) -data Trackref_Attrs = Trackref_Attrs - { trackrefLink :: (Maybe String) - } deriving (Eq,Show) - - -{-Instance decls-} - -instance XmlContent Album where - fromElem (CElem (Elem "album" [] c0):rest) = - (\(a,ca)-> - (\(b,cb)-> - (\(c,cc)-> - (\(d,cd)-> - (\(e,ce)-> - (\(f,cf)-> - (\(g,cg)-> - (\(h,ch)-> - (Just (Album a b c d e f g h), rest)) - (definite fromElem "" "album" cg)) - (many fromElem cf)) - (definite fromElem "" "album" ce)) - (many fromElem cd)) - (definite fromElem "" "album" cc)) - (fromElem cb)) - (definite fromElem "" "album" ca)) - (definite fromElem "" "album" c0) - fromElem (CMisc _:rest) = fromElem rest - fromElem rest = (Nothing, rest) - toElem (Album a b c d e f g h) = - [CElem (Elem "album" [] (toElem a ++ toElem b ++ maybe [] toElem c - ++ toElem d ++ concatMap toElem e ++ toElem f ++ concatMap toElem g - ++ toElem h))] -instance XmlContent Title where - fromElem (CElem (Elem "title" [] c0):rest) = - (\(a,ca)-> - (Just (Title a), rest)) - (definite fromText "text" "title" c0) - fromElem (CMisc _:rest) = fromElem rest - fromElem rest = (Nothing, rest) - toElem (Title a) = - [CElem (Elem "title" [] (toText a))] -instance XmlContent Artist where - fromElem (CElem (Elem "artist" [] c0):rest) = - (\(a,ca)-> - (Just (Artist a), rest)) - (definite fromText "text" "artist" c0) - fromElem (CMisc _:rest) = fromElem rest - fromElem rest = (Nothing, rest) - toElem (Artist a) = - [CElem (Elem "artist" [] (toText a))] -instance XmlContent Recording where - fromElem (CElem (Elem "recording" as []):rest) = - (Just (fromAttrs as), rest) - fromElem (CMisc _:rest) = fromElem rest - fromElem rest = (Nothing, rest) - toElem as = - [CElem (Elem "recording" (toAttrs as) [])] -instance XmlAttributes Recording where - fromAttrs as = - Recording - { recordingDate = possibleA fromAttrToStr "date" as - , recordingPlace = possibleA fromAttrToStr "place" as - } - toAttrs v = catMaybes - [ maybeToAttr toAttrFrStr "date" (recordingDate v) - , maybeToAttr toAttrFrStr "place" (recordingPlace v) - ] -instance XmlContent Coverart where - fromElem (CElem (Elem "coverart" as c0):rest) = - (\(a,ca)-> - (Just (Coverart (fromAttrs as) a), rest)) - (fromElem c0) - fromElem (CMisc _:rest) = fromElem rest - fromElem rest = (Nothing, rest) - toElem (Coverart as a) = - [CElem (Elem "coverart" (toAttrs as) (maybe [] toElem a))] -instance XmlAttributes Coverart_Attrs where - fromAttrs as = - Coverart_Attrs - { coverartStyle = definiteA fromAttrToStr "coverart" "style" as - } - toAttrs v = catMaybes - [ toAttrFrStr "style" (coverartStyle v) - ] -instance XmlContent Location where - fromElem (CElem (Elem "location" as []):rest) = - (Just (fromAttrs as), rest) - fromElem (CMisc _:rest) = fromElem rest - fromElem rest = (Nothing, rest) - toElem as = - [CElem (Elem "location" (toAttrs as) [])] -instance XmlAttributes Location where - fromAttrs as = - Location - { locationThumbnail = possibleA fromAttrToStr "thumbnail" as - , locationFullsize = possibleA fromAttrToStr "fullsize" as - } - toAttrs v = catMaybes - [ maybeToAttr toAttrFrStr "thumbnail" (locationThumbnail v) - , maybeToAttr toAttrFrStr "fullsize" (locationFullsize v) - ] -instance XmlContent Catalogno where - fromElem (CElem (Elem "catalogno" as []):rest) = - (Just (fromAttrs as), rest) - fromElem (CMisc _:rest) = fromElem rest - fromElem rest = (Nothing, rest) - toElem as = - [CElem (Elem "catalogno" (toAttrs as) [])] -instance XmlAttributes Catalogno where - fromAttrs as = - Catalogno - { catalognoLabel = definiteA fromAttrToStr "catalogno" "label" as - , catalognoNumber = definiteA fromAttrToStr "catalogno" "number" as - , catalognoFormat = possibleA fromAttrToTyp "format" as - , catalognoReleasedate = possibleA fromAttrToStr "releasedate" as - , catalognoCountry = possibleA fromAttrToStr "country" as - } - toAttrs v = catMaybes - [ toAttrFrStr "label" (catalognoLabel v) - , toAttrFrStr "number" (catalognoNumber v) - , maybeToAttr toAttrFrTyp "format" (catalognoFormat v) - , maybeToAttr toAttrFrStr "releasedate" (catalognoReleasedate v) - , maybeToAttr toAttrFrStr "country" (catalognoCountry v) - ] -instance XmlAttrType Catalogno_Format where - fromAttrToTyp n (n',v) - | n==n' = translate (attr2str v) - | otherwise = Nothing - where translate "CD" = Just Catalogno_Format_CD - translate "LP" = Just Catalogno_Format_LP - translate "MiniDisc" = Just Catalogno_Format_MiniDisc - translate _ = Nothing - toAttrFrTyp n Catalogno_Format_CD = Just (n, str2attr "CD") - toAttrFrTyp n Catalogno_Format_LP = Just (n, str2attr "LP") - toAttrFrTyp n Catalogno_Format_MiniDisc = Just (n, str2attr "MiniDisc") -instance XmlContent Personnel where - fromElem (CElem (Elem "personnel" [] c0):rest) = - (\(a,ca)-> - (Just (Personnel a), rest)) - (many fromElem c0) - fromElem (CMisc _:rest) = fromElem rest - fromElem rest = (Nothing, rest) - toElem (Personnel a) = - [CElem (Elem "personnel" [] (concatMap toElem a))] -instance XmlContent Player where - fromElem (CElem (Elem "player" as []):rest) = - (Just (fromAttrs as), rest) - fromElem (CMisc _:rest) = fromElem rest - fromElem rest = (Nothing, rest) - toElem as = - [CElem (Elem "player" (toAttrs as) [])] -instance XmlAttributes Player where - fromAttrs as = - Player - { playerName = definiteA fromAttrToStr "player" "name" as - , playerInstrument = definiteA fromAttrToStr "player" "instrument" as - } - toAttrs v = catMaybes - [ toAttrFrStr "name" (playerName v) - , toAttrFrStr "instrument" (playerInstrument v) - ] -instance XmlContent Track where - fromElem (CElem (Elem "track" as []):rest) = - (Just (fromAttrs as), rest) - fromElem (CMisc _:rest) = fromElem rest - fromElem rest = (Nothing, rest) - toElem as = - [CElem (Elem "track" (toAttrs as) [])] -instance XmlAttributes Track where - fromAttrs as = - Track - { trackTitle = definiteA fromAttrToStr "track" "title" as - , trackCredit = possibleA fromAttrToStr "credit" as - , trackTiming = possibleA fromAttrToStr "timing" as - } - toAttrs v = catMaybes - [ toAttrFrStr "title" (trackTitle v) - , maybeToAttr toAttrFrStr "credit" (trackCredit v) - , maybeToAttr toAttrFrStr "timing" (trackTiming v) - ] -instance XmlContent Notes where - fromElem (CElem (Elem "notes" as c0):rest) = - (\(a,ca)-> - (Just (Notes (fromAttrs as) a), rest)) - (many fromElem c0) - fromElem (CMisc _:rest) = fromElem rest - fromElem rest = (Nothing, rest) - toElem (Notes as a) = - [CElem (Elem "notes" (toAttrs as) (concatMap toElem a))] -instance XmlAttributes Notes_Attrs where - fromAttrs as = - Notes_Attrs - { notesAuthor = possibleA fromAttrToStr "author" as - } - toAttrs v = catMaybes - [ maybeToAttr toAttrFrStr "author" (notesAuthor v) - ] -instance XmlContent Notes_ where - fromElem c0 = - case (fromText c0) of - (Just a,rest) -> (Just (Notes_Str a), rest) - (Nothing,_) -> - case (fromElem c0) of - (Just a,rest) -> (Just (Notes_Albumref a), rest) - (Nothing,_) -> - case (fromElem c0) of - (Just a,rest) -> (Just (Notes_Trackref a), rest) - (Nothing,_) -> - (Nothing, c0) - fromElem (CMisc _:rest) = fromElem rest - fromElem rest = (Nothing, rest) - toElem (Notes_Str a) = toText a - toElem (Notes_Albumref a) = toElem a - toElem (Notes_Trackref a) = toElem a -instance XmlContent Albumref where - fromElem (CElem (Elem "albumref" as c0):rest) = - (\(a,ca)-> - (Just (Albumref (fromAttrs as) a), rest)) - (definite fromText "text" "albumref" c0) - fromElem (CMisc _:rest) = fromElem rest - fromElem rest = (Nothing, rest) - toElem (Albumref as a) = - [CElem (Elem "albumref" (toAttrs as) (toText a))] -instance XmlAttributes Albumref_Attrs where - fromAttrs as = - Albumref_Attrs - { albumrefLink = definiteA fromAttrToStr "albumref" "link" as - } - toAttrs v = catMaybes - [ toAttrFrStr "link" (albumrefLink v) - ] -instance XmlContent Trackref where - fromElem (CElem (Elem "trackref" as c0):rest) = - (\(a,ca)-> - (Just (Trackref (fromAttrs as) a), rest)) - (definite fromText "text" "trackref" c0) - fromElem (CMisc _:rest) = fromElem rest - fromElem rest = (Nothing, rest) - toElem (Trackref as a) = - [CElem (Elem "trackref" (toAttrs as) (toText a))] -instance XmlAttributes Trackref_Attrs where - fromAttrs as = - Trackref_Attrs - { trackrefLink = possibleA fromAttrToStr "link" as - } - toAttrs v = catMaybes - [ maybeToAttr toAttrFrStr "link" (trackrefLink v) - ] - - -{-Done-} rmfile ./examples/AlbumDTD.hs hunk ./examples/App.hs 1 -module Main where - -import System (getArgs) -import IO - -import Text.XML.HaXml.Wrappers (fix2Args) -import Text.XML.HaXml.XmlContent (fReadXml, fWriteXml) -import AlbumDTD - -main = - fix2Args >>= \(infile,outfile)-> - do putStrLn ("reading "++infile) - value <- fReadXml infile - putStrLn ("checking value's type and album title") - putStrLn (let (Album title _ _ _ _ _ _ _) = value in - if title==(Title "Time Out") then "ok" else "failed") - putStrLn ("writing "++outfile) - v <- (let (Album _ b c d e f g h) = value in - return (Album (Title "unknown") b c d e f g h)) - fWriteXml outfile v - putStrLn ("Done.") - rmfile ./examples/App.hs hunk ./examples/DTDpp.hs 1 -module Main where - -import System (getArgs) -import IO -import Maybe -import List (isSuffixOf) - -import Text.XML.HaXml.Types (DocTypeDecl(..)) -import Text.XML.HaXml.Parse (dtdParse) -import Text.XML.HaXml.Pretty (markupdecl) -import Text.XML.HaXml.Wrappers (fix2Args) -import Text.PrettyPrint.HughesPJ (render,vcat) - --- This is another trivial application that reads an XML DTD from --- a file (or stdin) and writes it back to another file (or stdout). --- It should deal with the external subset fully, collecting and --- in-lining all the individual files associated with the DTD. --- Note that PE references used in definitions are also expanded --- fully in the output. - -main = - fix2Args >>= \(inf,outf)-> - ( if inf=="-" then getContents - else readFile inf ) >>= \content-> - ( if outf=="-" then return stdout - else openFile outf WriteMode ) >>= \o-> - ( hPutStrLn o . render . vcat . map markupdecl . fromDTD . dtdParse inf) - content - -fromDTD Nothing = error "no DTD found" -fromDTD (Just (DTD _ _ ds)) = ds - rmfile ./examples/DTDpp.hs hunk ./examples/DTypes.hs 1 -{- Generated by DrIFT (Automatic class derivations for Haskell) -} -{-# LINE 1 "DTypes.hs" #-} -module DTypes where - -import Text.XML.HaXml.XmlContent hiding (Name) - --- data types for a simple test program - -data Person = Person Name Email [Rating] Version {-! derive : XmlContent !-} - -newtype Name = Name String {-! derive : XmlContent !-} -newtype Email = Email String {-! derive : XmlContent !-} -newtype Version = Version Int {-! derive : XmlContent !-} - -data Rating = Rating SubjectID Interest Skill {-! derive : XmlContent !-} - -newtype SubjectID = SubjectID Int {-! derive : XmlContent !-} -newtype Interest = Interest Score {-! derive : XmlContent !-} -newtype Skill = Skill Score {-! derive : XmlContent !-} - -data Score = ScoreNone | ScoreLow | ScoreMedium | ScoreHigh {-! derive : XmlContent !-} - -{-* Generated by DrIFT : Look, but Don't Touch. *-} -instance Haskell2XmlNew Person where - toHType v = - Defined "Person" [] - [Constr "Person" [] [toHType aa,toHType ab,toHType ac,toHType ad]] - where - (Person aa ab ac ad) = v - parseContents = do - { e@(Elem t _ _) <- element ["Person"] - ; case t of - _ | "Person" `isPrefixOf` t -> interior e $ - do { aa <- parseContents - ; ab <- parseContents - ; ac <- parseContents - ; ad <- parseContents - ; return (Person aa ab ac ad) - } - } - toContents v@(Person aa ab ac ad) = - [mkElemC (showConstr 0 (toHType v)) (concat [toContents aa, - toContents ab,toContents ac,toContents ad])] - -instance Haskell2XmlNew Name where - toHType v = - Defined "Name" [] [Constr "Name" [] [toHType aa]] - where - (Name aa) = v - parseContents = do - { e@(Elem t _ _) <- element ["Name"] - ; case t of - _ | "Name" `isPrefixOf` t -> interior e $ fmap Name parseContents - } - toContents v@(Name aa) = - [mkElemC (showConstr 0 (toHType v)) (toContents aa)] - -instance Haskell2XmlNew Email where - toHType v = - Defined "Email" [] [Constr "Email" [] [toHType aa]] - where - (Email aa) = v - parseContents = do - { e@(Elem t _ _) <- element ["Email"] - ; case t of - _ | "Email" `isPrefixOf` t -> interior e $ fmap Email parseContents - } - toContents v@(Email aa) = - [mkElemC (showConstr 0 (toHType v)) (toContents aa)] - -instance Haskell2XmlNew Version where - toHType v = - Defined "Version" [] [Constr "Version" [] [toHType aa]] - where - (Version aa) = v - parseContents = do - { e@(Elem t _ _) <- element ["Version"] - ; case t of - _ | "Version" `isPrefixOf` t -> interior e $ fmap Version parseContents - } - toContents v@(Version aa) = - [mkElemC (showConstr 0 (toHType v)) (toContents aa)] - -instance Haskell2XmlNew Rating where - toHType v = - Defined "Rating" [] - [Constr "Rating" [] [toHType aa,toHType ab,toHType ac]] - where - (Rating aa ab ac) = v - parseContents = do - { e@(Elem t _ _) <- element ["Rating"] - ; case t of - _ | "Rating" `isPrefixOf` t -> interior e $ - do { aa <- parseContents - ; ab <- parseContents - ; ac <- parseContents - ; return (Rating aa ab ac) - } - } - toContents v@(Rating aa ab ac) = - [mkElemC (showConstr 0 (toHType v)) (concat [toContents aa, - toContents ab,toContents ac])] - -instance Haskell2XmlNew SubjectID where - toHType v = - Defined "SubjectID" [] [Constr "SubjectID" [] [toHType aa]] - where - (SubjectID aa) = v - parseContents = do - { e@(Elem t _ _) <- element ["SubjectID"] - ; case t of - _ | "SubjectID" `isPrefixOf` t -> interior e $ fmap SubjectID parseContents - } - toContents v@(SubjectID aa) = - [mkElemC (showConstr 0 (toHType v)) (toContents aa)] - -instance Haskell2XmlNew Interest where - toHType v = - Defined "Interest" [] [Constr "Interest" [] [toHType aa]] - where - (Interest aa) = v - parseContents = do - { e@(Elem t _ _) <- element ["Interest"] - ; case t of - _ | "Interest" `isPrefixOf` t -> interior e $ fmap Interest parseContents - } - toContents v@(Interest aa) = - [mkElemC (showConstr 0 (toHType v)) (toContents aa)] - -instance Haskell2XmlNew Skill where - toHType v = - Defined "Skill" [] [Constr "Skill" [] [toHType aa]] - where - (Skill aa) = v - parseContents = do - { e@(Elem t _ _) <- element ["Skill"] - ; case t of - _ | "Skill" `isPrefixOf` t -> interior e $ fmap Skill parseContents - } - toContents v@(Skill aa) = - [mkElemC (showConstr 0 (toHType v)) (toContents aa)] - -instance Haskell2XmlNew Score where - toHType v = - Defined "Score" [] - [Constr "ScoreNone" [] [],Constr "ScoreLow" [] [], - Constr "ScoreMedium" [] [],Constr "ScoreHigh" [] []] - parseContents = do - { e@(Elem t _ _) <- element ["ScoreNone","ScoreLow","ScoreMedium","ScoreHigh"] - ; case t of - _ | "ScoreNone" `isPrefixOf` t -> interior e $ return ScoreNone - | "ScoreMedium" `isPrefixOf` t -> interior e $ return ScoreMedium - | "ScoreLow" `isPrefixOf` t -> interior e $ return ScoreLow - | "ScoreHigh" `isPrefixOf` t -> interior e $ return ScoreHigh - } - toContents v@ScoreNone = - [mkElemC (showConstr 0 (toHType v)) []] - toContents v@ScoreLow = - [mkElemC (showConstr 1 (toHType v)) []] - toContents v@ScoreMedium = - [mkElemC (showConstr 2 (toHType v)) []] - toContents v@ScoreHigh = - [mkElemC (showConstr 3 (toHType v)) []] - --- Imported from other files :- rmfile ./examples/DTypes.hs hunk ./examples/DebugLex.hs 1 -module Main where - -import System (getArgs) -import IO - -import Text.XML.HaXml.Lex (xmlLex) -import Text.XML.HaXml.Wrappers (fix2Args) - --- Debug the HaXml library by showing what the lexer generates. -main = - fix2Args >>= \(inf,outf)-> - ( if inf=="-" then getContents - else readFile inf ) >>= \content-> - ( if outf=="-" then return stdout - else openFile outf WriteMode ) >>= \o-> - mapM_ ( hPutStrLn o . show ) (xmlLex inf content) - rmfile ./examples/DebugLex.hs hunk ./examples/Example.hs 1 -module Main where - -import IO -import Text.XML.HaXml.XmlContent (fWriteXml) -import DTypes - -rjn = Person (Name "Rob Noble") (Email "rjn") [ - Rating (SubjectID 1) (Interest ScoreNone) (Skill ScoreLow), - Rating (SubjectID 2) (Interest ScoreMedium) (Skill ScoreHigh)] - (Version 1) - -main :: IO () -main = - fWriteXml "subjdb.xml" rjn rmfile ./examples/Example.hs hunk ./examples/OpenOffice.org/Blocklist.dtd 1 -<!-- - $Id: Blocklist.dtd,v 1.1 2003/05/13 13:07:49 malcolm Exp $ - - The Contents of this file are made available subject to the terms of - either of the following licenses - - - GNU Lesser General Public License Version 2.1 - - Sun Industry Standards Source License Version 1.1 - - Sun Microsystems Inc., October, 2000 - - GNU Lesser General Public License Version 2.1 - ============================================= - Copyright 2000 by Sun Microsystems, Inc. - 901 San Antonio Road, Palo Alto, CA 94303, USA - - This library is free software; you can redistribute it and/or - modify it under the terms of the GNU Lesser General Public - License version 2.1, as published by the Free Software Foundation. - - This library is distributed in the hope that it will be useful, - but WITHOUT ANY WARRANTY; without even the implied warranty of - MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU - Lesser General Public License for more details. - - You should have received a copy of the GNU Lesser General Public - License along with this library; if not, write to the Free Software - Foundation, Inc., 59 Temple Place, Suite 330, Boston, - MA 02111-1307 USA - - - Sun Industry Standards Source License Version 1.1 - ================================================= - The contents of this file are subject to the Sun Industry Standards - Source License Version 1.1 (the "License"); You may not use this file - except in compliance with the License. You may obtain a copy of the - License at http://www.openoffice.org/license.html. - - Software provided under this License is provided on an "AS IS" basis, - WITHOUT WARRANTY OF ANY KIND, EITHER EXPRESS OR IMPLIED, INCLUDING, - WITHOUT LIMITATION, WARRANTIES THAT THE SOFTWARE IS FREE OF DEFECTS, - MERCHANTABLE, FIT FOR A PARTICULAR PURPOSE, OR NON-INFRINGING. - See the License for the specific provisions governing your rights and - obligations concerning the Software. - - The Initial Developer of the Original Code is: Sun Microsystems, Inc. - - Copyright: 2000 by Sun Microsystems, Inc. - - All Rights Reserved. - - Contributor(s): Martin Gallwey (gallwey@Sun.COM) - ---> -<!ELEMENT block-list:block-list (block-list:block*) > -<!ATTLIST block-list:block-list - block-list:list-name CDATA #REQUIRED> -<!ELEMENT block-list:block EMPTY> -<!ATTLIST block-list:block - block-list:abbreviated-name CDATA #REQUIRED - block-list:package-name CDATA #REQUIRED - block-list:name CDATA #REQUIRED> rmfile ./examples/OpenOffice.org/Blocklist.dtd hunk ./examples/OpenOffice.org/chart.mod 1 -<!-- - $Id: chart.mod,v 1.1 2003/05/13 13:07:49 malcolm Exp $ - - The Contents of this file are made available subject to the terms of - either of the following licenses - - - GNU Lesser General Public License Version 2.1 - - Sun Industry Standards Source License Version 1.1 - - Sun Microsystems Inc., October, 2000 - - GNU Lesser General Public License Version 2.1 - ============================================= - Copyright 2000 by Sun Microsystems, Inc. - 901 San Antonio Road, Palo Alto, CA 94303, USA - - This library is free software; you can redistribute it and/or - modify it under the terms of the GNU Lesser General Public - License version 2.1, as published by the Free Software Foundation. - - This library is distributed in the hope that it will be useful, - but WITHOUT ANY WARRANTY; without even the implied warranty of - MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU - Lesser General Public License for more details. - - You should have received a copy of the GNU Lesser General Public - License along with this library; if not, write to the Free Software - Foundation, Inc., 59 Temple Place, Suite 330, Boston, - MA 02111-1307 USA - - - Sun Industry Standards Source License Version 1.1 - ================================================= - The contents of this file are subject to the Sun Industry Standards - Source License Version 1.1 (the "License"); You may not use this file - except in compliance with the License. You may obtain a copy of the - License at http://www.openoffice.org/license.html. - - Software provided under this License is provided on an "AS IS" basis, - WITHOUT WARRANTY OF ANY KIND, EITHER EXPRESS OR IMPLIED, INCLUDING, - WITHOUT LIMITATION, WARRANTIES THAT THE SOFTWARE IS FREE OF DEFECTS, - MERCHANTABLE, FIT FOR A PARTICULAR PURPOSE, OR NON-INFRINGING. - See the License for the specific provisions governing your rights and - obligations concerning the Software. - - The Initial Developer of the Original Code is: Sun Microsystems, Inc. - - Copyright: 2000 by Sun Microsystems, Inc. - - All Rights Reserved. - - Contributor(s): _______________________________________ - ---> - - -<!ENTITY % chart-class "(line|area|circle|ring|scatter|radar|bar|stock|add-in)"> -<!ENTITY % chart-solid-type "(cuboid|cylinder|cone|pyramid)"> - -<!-- Chart element --> -<!ELEMENT chart:chart ( chart:title?, chart:subtitle?, chart:legend?, - chart:plot-area, - table:table? )> -<!ATTLIST chart:chart - chart:class %chart-class; #REQUIRED - chart:add-in-name %string; #IMPLIED - chart:table-number-list %string; #IMPLIED - draw:name %string; #IMPLIED - %draw-position; - %draw-size; - %draw-style-name; - chart:column-mapping %string; #IMPLIED - chart:row-mapping %string; #IMPLIED - chart:style-name %styleName; #IMPLIED> - -<!ATTLIST chart:chart %presentation-class; > -<!ATTLIST chart:chart %zindex;> -<!ATTLIST chart:chart %draw-end-position; > -<!ATTLIST chart:chart draw:id %draw-shape-id; > -<!ATTLIST chart:chart draw:layer %layerName; #IMPLIED> - -<!ATTLIST style:properties - chart:scale-text %boolean; "true" - chart:stock-updown-bars %boolean; "false" - chart:stock-with-volume %boolean; "false" - chart:three-dimensional %boolean; "false" - chart:deep %boolean; "false" - chart:lines %boolean; "false" - chart:percentage %boolean; "false" - chart:solid-type %chart-solid-type; "cuboid" - chart:splines %nonNegativeInteger; "0" - chart:stacked %boolean; "false" - chart:symbol %integer; "-1" - chart:vertical %boolean; "false" - chart:lines-used %nonNegativeInteger; "0" - chart:connect-bars %boolean; "false" - chart:spline-order %nonNegativeInteger; "2" - chart:spline-resolution %nonNegativeInteger; "20" - chart:pie-offset %nonNegativeInteger; "0"> - -<!-- Main/Sub Title --> -<!-- the cell-address attribute is currently not supported for titles --> -<!ELEMENT chart:title (text:p)?> -<!ATTLIST chart:title - table:cell-range %cell-address; #IMPLIED - svg:x %coordinate; #IMPLIED - svg:y %coordinate; #IMPLIED - chart:style-name %styleName; #IMPLIED > - -<!ELEMENT chart:subtitle (text:p)?> -<!ATTLIST chart:subtitle - table:cell-range %cell-address; #IMPLIED - svg:x %coordinate; #IMPLIED - svg:y %coordinate; #IMPLIED - chart:style-name %styleName; #IMPLIED > - -<!-- you must specify either a legend-position or both, x and y coordinates --> -<!ELEMENT chart:legend EMPTY> -<!ATTLIST chart:legend - chart:legend-position (top|left|bottom|right) "right" - svg:x %coordinate; #IMPLIED - svg:y %coordinate; #IMPLIED - chart:style-name %styleName; #IMPLIED > - -<!-- Plot-Area specification --> - -<!ELEMENT chart:plot-area (dr3d:light*, - chart:axis*, - chart:categories?, - chart:series*, - chart:stock-gain-marker?, - chart:stock-loss-marker?, - chart:stock-range-line?, - chart:wall?, - chart:floor?) > - -<!ATTLIST chart:plot-area - svg:x %coordinate; #IMPLIED - svg:y %coordinate; #IMPLIED - svg:width %length; #IMPLIED - svg:height %length; #IMPLIED - chart:style-name %styleName; #IMPLIED - table:cell-range-address %cell-range-address; #IMPLIED - chart:table-number-list %string; #IMPLIED - chart:data-source-has-labels (none|row|column|both) "none" > - -<!-- 3d scene attributes on plot-area --> -<!ATTLIST chart:plot-area - dr3d:vrp %vector3D; #IMPLIED - dr3d:vpn %vector3D; #IMPLIED - dr3d:vup %vector3D; #IMPLIED - dr3d:projection (parallel|perspective) #IMPLIED - dr3d:transform CDATA #IMPLIED - dr3d:distance %length; #IMPLIED - dr3d:focal-length %length; #IMPLIED - dr3d:shadow-slant %nonNegativeInteger; #IMPLIED - dr3d:shade-mode (flat|phong|gouraud|draft) #IMPLIED - dr3d:ambient-color %color; #IMPLIED - dr3d:lighting-mode %boolean; #IMPLIED > - -<!ATTLIST style:properties - chart:series-source (columns|rows) "columns" > - -<!ELEMENT chart:wall EMPTY> -<!ATTLIST chart:wall - svg:width %length; #IMPLIED - chart:style-name %styleName; #IMPLIED > - -<!ELEMENT chart:floor EMPTY> -<!ATTLIST chart:floor - svg:width %length; #IMPLIED - chart:style-name %styleName; #IMPLIED > - -<!-- Stock chart elements --> - -<!ELEMENT chart:stock-gain-marker EMPTY> -<!ATTLIST chart:stock-gain-marker - chart:style-name %styleName; #IMPLIED > - -<!ELEMENT chart:stock-loss-marker EMPTY> -<!ATTLIST chart:stock-loss-marker - chart:style-name %styleName; #IMPLIED > - -<!ELEMENT chart:stock-range-line EMPTY> -<!ATTLIST chart:stock-range-line - chart:style-name %styleName; #IMPLIED > - -<!-- Axis --> - -<!ELEMENT chart:axis (chart:title?, chart:grid*)> -<!ATTLIST chart:axis - chart:class (category|value|series|domain) #REQUIRED - chart:name %string; #IMPLIED - chart:style-name %styleName; #IMPLIED > - -<!ATTLIST style:properties - chart:tick-marks-major-inner %boolean; "false" - chart:tick-marks-major-outer %boolean; "true" - chart:tick-marks-minor-inner %boolean; "false" - chart:tick-marks-minor-outer %boolean; "false" - chart:logarithmic %boolean; "false" - chart:maximum %float; #IMPLIED - chart:minimum %float; #IMPLIED - chart:origin %float; #IMPLIED - chart:interval-major %float; #IMPLIED - chart:interval-minor %float; #IMPLIED - chart:gap-width %integer; #IMPLIED - chart:overlap %integer; #IMPLIED - text:line-break %boolean; "true" - chart:display-label %boolean; "true" - chart:label-arrangement (side-by-side|stagger-even|stagger-odd) "side-by-side" - chart:text-overlap %boolean; "false" - chart:visible %boolean; "true" - chart:link-data-style-to-source %boolean; "true" > - -<!ELEMENT chart:grid EMPTY> -<!ATTLIST chart:grid - chart:class (major|minor) "major" - chart:style-name %styleName; #IMPLIED > - - -<!ELEMENT chart:categories EMPTY> -<!ATTLIST chart:categories - table:cell-range-address %cell-range-address; #IMPLIED > - -<!-- - each series element must have an cell-range-address element that points - to the underlying table data. - Impl. Note: Internally all href elements are merged to one table range - that represents the data for the whole chart ---> -<!ELEMENT chart:series ( chart:domain*, - chart:mean-value?, - chart:regression-curve?, - chart:error-indicator?, - chart:data-point* )> -<!ATTLIST chart:series - chart:values-cell-range-address %cell-range-address; #IMPLIED - chart:label-cell-address %cell-address; #IMPLIED - chart:class %chart-class; #IMPLIED - chart:attached-axis %string; #IMPLIED - chart:style-name %styleName; #IMPLIED > - -<!ELEMENT chart:domain EMPTY> -<!ATTLIST chart:domain - table:cell-range-address %cell-range-address; #IMPLIED > - -<!ELEMENT chart:data-point EMPTY> -<!ATTLIST chart:data-point - chart:repeated %nonNegativeInteger; #IMPLIED - chart:style-name %styleName; #IMPLIED > - -<!-- statistical properties --> - -<!ELEMENT chart:mean-value EMPTY> -<!ELEMENT chart:regression-curve EMPTY > -<!ELEMENT chart:error-indicator EMPTY > -<!ATTLIST chart:mean-value chart:style-name %styleName; #IMPLIED > -<!ATTLIST chart:regression-curve chart:style-name %styleName; #IMPLIED > -<!ATTLIST chart:error-indicator chart:style-name %styleName; #IMPLIED > - -<!ATTLIST style:properties - chart:mean-value %boolean; #IMPLIED - chart:error-category (none|variance|standard-deviation|percentage|error-margin|constant) "none" - chart:error-percentage %float; #IMPLIED - chart:error-margin %float; #IMPLIED - chart:error-lower-limit %float; #IMPLIED - chart:error-upper-limit %float; #IMPLIED - chart:error-upper-indicator %boolean; #IMPLIED - chart:error-lower-indicator %boolean; #IMPLIED - chart:regression-type (none|linear|logarithmic|exponential|power) "none" > - -<!-- data label properties --> - -<!ATTLIST style:properties - chart:data-label-number (none|value|percentage) "none" - chart:data-label-text %boolean; "false" - chart:data-label-symbol %boolean; "false" > - -<!-- general text properties --> - -<!ATTLIST style:properties - text:rotation-angle %integer; "0" > - -<!-- symbol properties --> - -<!ATTLIST style:properties - chart:symbol-width %nonNegativeLength; #IMPLIED - chart:symbol-height %nonNegativeLength; #IMPLIED - chart:symbol-image-name %string; #IMPLIED > rmfile ./examples/OpenOffice.org/chart.mod hunk ./examples/OpenOffice.org/datastyl.mod 1 -<!-- - - $Id: datastyl.mod,v 1.1 2003/05/13 13:07:49 malcolm Exp $ - - The Contents of this file are made available subject to the terms of - either of the following licenses - - - GNU Lesser General Public License Version 2.1 - - Sun Industry Standards Source License Version 1.1 - - Sun Microsystems Inc., October, 2000 - - GNU Lesser General Public License Version 2.1 - ============================================= - Copyright 2000 by Sun Microsystems, Inc. - 901 San Antonio Road, Palo Alto, CA 94303, USA - - This library is free software; you can redistribute it and/or - modify it under the terms of the GNU Lesser General Public - License version 2.1, as published by the Free Software Foundation. - - This library is distributed in the hope that it will be useful, - but WITHOUT ANY WARRANTY; without even the implied warranty of - MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU - Lesser General Public License for more details. - - You should have received a copy of the GNU Lesser General Public - License along with this library; if not, write to the Free Software - Foundation, Inc., 59 Temple Place, Suite 330, Boston, - MA 02111-1307 USA - - - Sun Industry Standards Source License Version 1.1 - ================================================= - The contents of this file are subject to the Sun Industry Standards - Source License Version 1.1 (the "License"); You may not use this file - except in compliance with the License. You may obtain a copy of the - License at http://www.openoffice.org/license.html. - - Software provided under this License is provided on an "AS IS" basis, - WITHOUT WARRANTY OF ANY KIND, EITHER EXPRESS OR IMPLIED, INCLUDING, - WITHOUT LIMITATION, WARRANTIES THAT THE SOFTWARE IS FREE OF DEFECTS, - MERCHANTABLE, FIT FOR A PARTICULAR PURPOSE, OR NON-INFRINGING. - See the License for the specific provisions governing your rights and - obligations concerning the Software. - - The Initial Developer of the Original Code is: Sun Microsystems, Inc. - - Copyright: 2000 by Sun Microsystems, Inc. - - All Rights Reserved. - - Contributor(s): _______________________________________ - ---> - -<!-- data styles --> -<!ENTITY % any-number "( number:number | number:scientific-number | number:fraction )"> -<!ENTITY % number-style-content "( (number:text,(%any-number;,number:text?)?) | (%any-number;,number:text?) )"> -<!ELEMENT number:number-style ( style:properties?, %number-style-content;, style:map* )> -<!ELEMENT number:number ( number:embedded-text* )> -<!ELEMENT number:scientific-number EMPTY> -<!ELEMENT number:fraction EMPTY> - -<!ELEMENT number:embedded-text (#PCDATA)> -<!ATTLIST number:embedded-text number:position %integer; #REQUIRED> - -<!ENTITY % currency-symbol-and-text "number:currency-symbol,number:text?"> -<!ENTITY % number-and-text "number:number,number:text?"> -<!ENTITY % currency-symbol-and-number "((%number-and-text;),(%currency-symbol-and-text;)?) | ((%currency-symbol-and-text;),(%number-and-text;)?)"> -<!ENTITY % currency-style-content "number:text?, (%currency-symbol-and-number;)?"> - -<!ELEMENT number:currency-style ( style:properties?, (%currency-style-content;), style:map* )> -<!ELEMENT number:currency-symbol (#PCDATA)> -<!ATTLIST number:currency-symbol number:language CDATA #IMPLIED> -<!ATTLIST number:currency-symbol number:country CDATA #IMPLIED> - -<!ENTITY % percentage-style-content "( (number:text,(%number-and-text;)?) | (%number-and-text;) )"> -<!ELEMENT number:percentage-style ( style:properties?, %percentage-style-content;, style:map* )> - -<!ENTITY % any-date "( number:day | number:month | number:year | number:era | number:day-of-week | number:week-of-year | number:quarter| number:hours | number:am-pm | number:minutes | number:seconds )"> -<!ENTITY % date-style-content "( (number:text,(%any-date;,number:text?)+) | (%any-date;,number:text?)+ )"> -<!ELEMENT number:date-style ( style:properties?, %date-style-content;, style:map* )> -<!ELEMENT number:day EMPTY> -<!ATTLIST number:day number:style (short|long) "short"> -<!ATTLIST number:day number:calendar CDATA #IMPLIED> -<!ELEMENT number:month EMPTY> -<!ATTLIST number:month number:textual %boolean; "false"> -<!ATTLIST number:month number:style (short|long) "short"> -<!ATTLIST number:month number:calendar CDATA #IMPLIED> -<!ELEMENT number:year EMPTY> -<!ATTLIST number:year number:style (short|long) "short"> -<!ATTLIST number:year number:calendar CDATA #IMPLIED> -<!ELEMENT number:era EMPTY> -<!ATTLIST number:era number:style (short|long) "short"> -<!ATTLIST number:era number:calendar CDATA #IMPLIED> -<!ELEMENT number:day-of-week EMPTY> -<!ATTLIST number:day-of-week number:style (short|long) "short"> -<!ATTLIST number:day-of-week number:calendar CDATA #IMPLIED> -<!ELEMENT number:week-of-year EMPTY> -<!ATTLIST number:week-of-year number:calendar CDATA #IMPLIED> -<!ELEMENT number:quarter EMPTY> -<!ATTLIST number:quarter number:style (short|long) "short"> -<!ATTLIST number:quarter number:calendar CDATA #IMPLIED> - -<!ENTITY % any-time "( number:hours | number:am-pm | number:minutes | number:seconds )"> -<!ENTITY % time-style-content "( (number:text,(%any-time;,number:text?)+) | (%any-time;,number:text?)+)"> -<!ELEMENT number:time-style ( style:properties?, %time-style-content;, style:map* )> -<!ELEMENT number:hours EMPTY> -<!ATTLIST number:hours number:style (short|long) "short"> -<!ELEMENT number:minutes EMPTY> -<!ATTLIST number:minutes number:style (short|long) "short"> -<!ELEMENT number:seconds EMPTY> -<!ATTLIST number:seconds number:style (short|long) "short"> -<!ATTLIST number:seconds number:decimal-places %integer; "0"> -<!ELEMENT number:am-pm EMPTY> - -<!ENTITY % boolean-style-content "( (number:text,(number:boolean,number:text?)?) | (number:boolean,number:text?) )"> -<!ELEMENT number:boolean-style ( style:properties?,%boolean-style-content;, style:map* )> -<!ELEMENT number:boolean EMPTY> - -<!ENTITY % text-style-content "( (number:text,(number:text-content,number:text?)?) | (number:text-content,number:text?) )"> -<!ELEMENT number:text-style ( style:properties?,%text-style-content;, style:map* )> -<!ELEMENT number:text (#PCDATA)> -<!ELEMENT number:text-content EMPTY> - -<!ATTLIST number:number-style style:name %styleName; #REQUIRED> -<!ATTLIST number:currency-style style:name %styleName; #REQUIRED> -<!ATTLIST number:percentage-style style:name %styleName; #REQUIRED> -<!ATTLIST number:date-style style:name %styleName; #REQUIRED> -<!ATTLIST number:time-style style:name %styleName; #REQUIRED> -<!ATTLIST number:boolean-style style:name %styleName; #REQUIRED> -<!ATTLIST number:text-style style:name %styleName; #REQUIRED> - -<!ATTLIST number:number-style style:family CDATA #REQUIRED> -<!ATTLIST number:currency-style style:family CDATA #REQUIRED> -<!ATTLIST number:percentage-style style:family CDATA #REQUIRED> -<!ATTLIST number:date-style style:family CDATA #REQUIRED> -<!ATTLIST number:time-style style:family CDATA #REQUIRED> -<!ATTLIST number:boolean-style style:family CDATA #REQUIRED> -<!ATTLIST number:text-style style:family CDATA #REQUIRED> - -<!ATTLIST number:number-style number:language CDATA #IMPLIED> -<!ATTLIST number:currency-style number:language CDATA #IMPLIED> -<!ATTLIST number:percentage-style number:language CDATA #IMPLIED> -<!ATTLIST number:date-style number:language CDATA #IMPLIED> -<!ATTLIST number:time-style number:language CDATA #IMPLIED> -<!ATTLIST number:boolean-style number:language CDATA #IMPLIED> -<!ATTLIST number:text-style number:language CDATA #IMPLIED> - -<!ATTLIST number:number-style number:country CDATA #IMPLIED> -<!ATTLIST number:currency-style number:country CDATA #IMPLIED> -<!ATTLIST number:percentage-style number:country CDATA #IMPLIED> -<!ATTLIST number:date-style number:country CDATA #IMPLIED> -<!ATTLIST number:time-style number:country CDATA #IMPLIED> -<!ATTLIST number:boolean-style number:country CDATA #IMPLIED> -<!ATTLIST number:text-style number:country CDATA #IMPLIED> - -<!ATTLIST number:number-style number:title CDATA #IMPLIED> -<!ATTLIST number:currency-style number:title CDATA #IMPLIED> -<!ATTLIST number:percentage-style number:title CDATA #IMPLIED> -<!ATTLIST number:date-style number:title CDATA #IMPLIED> -<!ATTLIST number:time-style number:title CDATA #IMPLIED> -<!ATTLIST number:boolean-style number:title CDATA #IMPLIED> -<!ATTLIST number:text-style number:title CDATA #IMPLIED> - -<!ATTLIST number:number-style style:volatile %boolean; #IMPLIED> -<!ATTLIST number:currency-style style:volatile %boolean; #IMPLIED> -<!ATTLIST number:percentage-style style:volatile %boolean; #IMPLIED> -<!ATTLIST number:date-style style:volatile %boolean; #IMPLIED> -<!ATTLIST number:time-style style:volatile %boolean; #IMPLIED> -<!ATTLIST number:boolean-style style:volatile %boolean; #IMPLIED> -<!ATTLIST number:text-style style:volatile %boolean; #IMPLIED> - -<!ATTLIST number:number-style number:transliteration-format CDATA "1"> -<!ATTLIST number:currency-style number:transliteration-format CDATA "1"> -<!ATTLIST number:percentage-style number:transliteration-format CDATA "1"> -<!ATTLIST number:date-style number:transliteration-format CDATA "1"> -<!ATTLIST number:time-style number:transliteration-format CDATA "1"> -<!ATTLIST number:boolean-style number:transliteration-format CDATA "1"> -<!ATTLIST number:text-style number:transliteration-format CDATA "1"> - -<!ATTLIST number:number-style number:transliteration-language CDATA #IMPLIED> -<!ATTLIST number:currency-style number:transliteration-language CDATA #IMPLIED> -<!ATTLIST number:percentage-style number:transliteration-language CDATA #IMPLIED> -<!ATTLIST number:date-style number:transliteration-language CDATA #IMPLIED> -<!ATTLIST number:time-style number:transliteration-language CDATA #IMPLIED> -<!ATTLIST number:boolean-style number:transliteration-language CDATA #IMPLIED> -<!ATTLIST number:text-style number:transliteration-language CDATA #IMPLIED> - -<!ATTLIST number:number-style number:transliteration-country CDATA #IMPLIED> -<!ATTLIST number:currency-style number:transliteration-country CDATA #IMPLIED> -<!ATTLIST number:percentage-style number:transliteration-country CDATA #IMPLIED> -<!ATTLIST number:date-style number:transliteration-country CDATA #IMPLIED> -<!ATTLIST number:time-style number:transliteration-country CDATA #IMPLIED> -<!ATTLIST number:boolean-style number:transliteration-country CDATA #IMPLIED> -<!ATTLIST number:text-style number:transliteration-country CDATA #IMPLIED> - -<!ATTLIST number:number-style number:transliteration-style (short|medium|long) "short"> -<!ATTLIST number:currency-style number:transliteration-style (short|medium|long) "short"> -<!ATTLIST number:percentage-style number:transliteration-style (short|medium|long) "short"> -<!ATTLIST number:date-style number:transliteration-style (short|medium|long) "short"> -<!ATTLIST number:time-style number:transliteration-style (short|medium|long) "short"> -<!ATTLIST number:boolean-style number:transliteration-style (short|medium|long) "short"> -<!ATTLIST number:text-style number:transliteration-style (short|medium|long) "short"> - -<!ATTLIST number:currency-style number:automatic-order %boolean; "false"> -<!ATTLIST number:date-style number:automatic-order %boolean; "false"> - -<!ATTLIST number:date-style number:format-source (fixed|language) "fixed"> -<!ATTLIST number:time-style number:format-source (fixed|language) "fixed"> - -<!ATTLIST number:time-style number:truncate-on-overflow %boolean; "true"> - -<!ATTLIST number:number number:decimal-places %integer; #IMPLIED> -<!ATTLIST number:scientific-number number:decimal-places %integer; #IMPLIED> - -<!ATTLIST number:number number:min-integer-digits %integer; #IMPLIED> -<!ATTLIST number:scientific-number number:min-integer-digits %integer; #IMPLIED> -<!ATTLIST number:fraction number:min-integer-digits %integer; #IMPLIED> - -<!ATTLIST number:number number:grouping %boolean; "false"> -<!ATTLIST number:scientific-number number:grouping %boolean; "false"> -<!ATTLIST number:fraction number:grouping %boolean; "false"> - -<!ATTLIST number:number number:decimal-replacement CDATA #IMPLIED> - -<!ATTLIST number:number number:display-factor %float; "1"> - -<!ATTLIST number:scientific-number number:min-exponent-digits %integer; #IMPLIED> - -<!ATTLIST number:fraction number:min-numerator-digits %integer; #IMPLIED> - -<!ATTLIST number:fraction number:min-denominator-digits %integer; #IMPLIED> rmfile ./examples/OpenOffice.org/datastyl.mod hunk ./examples/OpenOffice.org/defs.mod 1 -<!-- - $Id: defs.mod,v 1.1 2003/05/13 13:07:51 malcolm Exp $ - - The Contents of this file are made available subject to the terms of - either of the following licenses - - - GNU Lesser General Public License Version 2.1 - - Sun Industry Standards Source License Version 1.1 - - Sun Microsystems Inc., October, 2000 - - GNU Lesser General Public License Version 2.1 - ============================================= - Copyright 2000 by Sun Microsystems, Inc. - 901 San Antonio Road, Palo Alto, CA 94303, USA - - This library is free software; you can redistribute it and/or - modify it under the terms of the GNU Lesser General Public - License version 2.1, as published by the Free Software Foundation. - - This library is distributed in the hope that it will be useful, - but WITHOUT ANY WARRANTY; without even the implied warranty of - MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU - Lesser General Public License for more details. - - You should have received a copy of the GNU Lesser General Public - License along with this library; if not, write to the Free Software - Foundation, Inc., 59 Temple Place, Suite 330, Boston, - MA 02111-1307 USA - - - Sun Industry Standards Source License Version 1.1 - ================================================= - The contents of this file are subject to the Sun Industry Standards - Source License Version 1.1 (the "License"); You may not use this file - except in compliance with the License. You may obtain a copy of the - License at http://www.openoffice.org/license.html. - - Software provided under this License is provided on an "AS IS" basis, - WITHOUT WARRANTY OF ANY KIND, EITHER EXPRESS OR IMPLIED, INCLUDING, - WITHOUT LIMITATION, WARRANTIES THAT THE SOFTWARE IS FREE OF DEFECTS, - MERCHANTABLE, FIT FOR A PARTICULAR PURPOSE, OR NON-INFRINGING. - See the License for the specific provisions governing your rights and - obligations concerning the Software. - - The Initial Developer of the Original Code is: Sun Microsystems, Inc. - - Copyright: 2000 by Sun Microsystems, Inc. - - All Rights Reserved. - - Contributor(s): _______________________________________ - ---> - -<!-- This module should contain entities intended for content definitions - in several other modules. Putting all of them here should remove - (some) order dependencies of the other module files ---> - - -<!-- text marks for tracking changes; usually used inside of paragraphs --> -<!ENTITY % change-marks "text:change | text:change-start | text:change-end"> - -<!-- (optional) text declarations; used before the first paragraph --> -<!ENTITY % text-decls "text:variable-decls?, text:sequence-decls?, - text:user-field-decls?, text:dde-connection-decls?, - text:alphabetical-index-auto-mark-file?" > - -<!-- define the types of text which may occur inside of sections --> -<!ENTITY % sectionText "(text:h|text:p|text:ordered-list| - text:unordered-list|table:table|text:section| - text:table-of-content|text:illustration-index| - text:table-index|text:object-index|text:user-index| - text:alphabetical-index|text:bibliography| - text:index-title|%change-marks;)*"> - -<!ENTITY % headerText "(%text-decls;, (text:h|text:p|text:ordered-list| - text:unordered-list|table:table|text:section| - text:table-of-content|text:illustration-index| - text:table-index|text:object-index|text:user-index| - text:alphabetical-index|text:bibliography| - text:index-title|%change-marks;)* )"> - rmfile ./examples/OpenOffice.org/defs.mod hunk ./examples/OpenOffice.org/drawing.mod 1 -<!-- - $Id: drawing.mod,v 1.1 2003/05/13 13:07:51 malcolm Exp $ - - The Contents of this file are made available subject to the terms of - either of the following licenses - - - GNU Lesser General Public License Version 2.1 - - Sun Industry Standards Source License Version 1.1 - - Sun Microsystems Inc., October, 2000 - - GNU Lesser General Public License Version 2.1 - ============================================= - Copyright 2000 by Sun Microsystems, Inc. - 901 San Antonio Road, Palo Alto, CA 94303, USA - - This library is free software; you can redistribute it and/or - modify it under the terms of the GNU Lesser General Public - License version 2.1, as published by the Free Software Foundation. - - This library is distributed in the hope that it will be useful, - but WITHOUT ANY WARRANTY; without even the implied warranty of - MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU - Lesser General Public License for more details. - - You should have received a copy of the GNU Lesser General Public - License along with this library; if not, write to the Free Software - Foundation, Inc., 59 Temple Place, Suite 330, Boston, - MA 02111-1307 USA - - - Sun Industry Standards Source License Version 1.1 - ================================================= - The contents of this file are subject to the Sun Industry Standards - Source License Version 1.1 (the "License"); You may not use this file - except in compliance with the License. You may obtain a copy of the - License at http://www.openoffice.org/license.html. - - Software provided under this License is provided on an "AS IS" basis, - WITHOUT WARRANTY OF ANY KIND, EITHER EXPRESS OR IMPLIED, INCLUDING, - WITHOUT LIMITATION, WARRANTIES THAT THE SOFTWARE IS FREE OF DEFECTS, - MERCHANTABLE, FIT FOR A PARTICULAR PURPOSE, OR NON-INFRINGING. - See the License for the specific provisions governing your rights and - obligations concerning the Software. - - The Initial Developer of the Original Code is: Sun Microsystems, Inc. - - Copyright: 2000 by Sun Microsystems, Inc. - - All Rights Reserved. - - Contributor(s): _______________________________________ - ---> - -<!ENTITY % points "CDATA" > -<!ENTITY % pathData "CDATA" > -<!ENTITY % gradient-style "(linear|axial|radial|ellipsoid|square|rectangular)" > -<!ENTITY % draw-position "svg:x %coordinate; #IMPLIED svg:y %coordinate; #IMPLIED"> -<!ENTITY % draw-end-position "table:end-cell-address %cell-address; #IMPLIED table:end-x %coordinate; #IMPLIED table:end-y %coordinate; #IMPLIED"> -<!ENTITY % draw-size "svg:width %coordinate; #IMPLIED svg:height %coordinate; #IMPLIED"> -<!ENTITY % draw-transform "draw:transform CDATA #IMPLIED"> -<!ENTITY % draw-viewbox "svg:viewBox CDATA #REQUIRED"> -<!ENTITY % draw-style-name "draw:style-name %styleName; #IMPLIED presentation:style-name %styleName; #IMPLIED draw:text-style-name %styleName; #IMPLIED"> -<!ENTITY % draw-shape-id "CDATA #IMPLIED" > -<!ENTITY % draw-text "(text:p|text:unordered-list|text:ordered-list)*"> -<!ENTITY % zindex "draw:z-index %nonNegativeInteger; #IMPLIED"> -<!ENTITY % distance "CDATA"> -<!ENTITY % rectanglePoint "(top-left|top|top-right|left|center|right|bottom-left|bottom|bottom-right)"> -<!ENTITY % vector3D "CDATA"> -<!ENTITY % text-anchor "text:anchor-type %anchorType; #IMPLIED text:anchor-page-number %positiveInteger; #IMPLIED"> -<!ENTITY % layerName "CDATA"> -<!ENTITY % table-background "table:table-background (true | false) #IMPLIED"> - -<!-- commont presentation shape attributes --> -<!ENTITY % presentation-style-name "presentation:style-name %styleName; #IMPLIED"> -<!ENTITY % presentation-classes "(title|outline|subtitle|text|graphic|object|chart|table|orgchart|page|notes)" > -<!-- ENTITY % presentation-class "presentation:class %presentation-classes; #IMPLIED" --> -<!ENTITY % presentation-class "presentation:class %presentation-classes; #IMPLIED presentation:placeholder (true|false) #IMPLIED presentation:user-transformed (true|false) #IMPLIED"> -<!ENTITY % presentationEffects "(none|fade|move|stripes|open|close|dissolve|wavyline|random|lines|laser|appear|hide|move-short|checkerboard|rotate|stretch)" > -<!ENTITY % presentationEffectDirections "(none|from-left|from-top|from-right|from-bottom|from-center|from-upper-left|from-upper-right|from-lower-left|from-lower-right|to-left|to-top|to-right|to-bottom|to-upper-left|to-upper-right|to-lower-right|to-lower-left|path|spiral-inward-left|spiral-inward-right|spiral-outward-left|spiral-outward-right|vertical|horizontal|to-center|clockwise|counter-clockwise)" > -<!ENTITY % presentationSpeeds "(slow|medium|fast)" > - -<!-- Drawing shapes --> -<!ELEMENT draw:rect ( office:events?, %draw-text; )> -<!ATTLIST draw:rect %draw-position; > -<!ATTLIST draw:rect %draw-end-position; > -<!ATTLIST draw:rect %table-background; > -<!ATTLIST draw:rect %draw-size; > -<!ATTLIST draw:rect %draw-style-name; > -<!ATTLIST draw:rect %draw-transform; > -<!ATTLIST draw:rect draw:corner-radius %nonNegativeLength; #IMPLIED> -<!ATTLIST draw:rect %zindex;> -<!ATTLIST draw:rect draw:id %draw-shape-id;> -<!ATTLIST draw:rect %text-anchor;> -<!ATTLIST draw:rect draw:layer %layerName; #IMPLIED> - -<!ELEMENT draw:line ( office:events?, %draw-text; )> -<!ATTLIST draw:line svg:x1 %length; #IMPLIED> -<!ATTLIST draw:line svg:y1 %length; #IMPLIED> -<!ATTLIST draw:line svg:x2 %length; #REQUIRED> -<!ATTLIST draw:line svg:y2 %length; #REQUIRED> -<!ATTLIST draw:line svg:y %coordinate; #IMPLIED> -<!ATTLIST draw:line %draw-style-name; > -<!ATTLIST draw:line %draw-transform; > -<!ATTLIST draw:line %zindex;> -<!ATTLIST draw:line %draw-end-position; > -<!ATTLIST draw:line %table-background; > -<!ATTLIST draw:line draw:id %draw-shape-id;> -<!ATTLIST draw:line %text-anchor;> -<!ATTLIST draw:line draw:layer %layerName; #IMPLIED> - -<!ELEMENT draw:polyline ( office:events?, %draw-text; )> -<!ATTLIST draw:polyline %draw-position; > -<!ATTLIST draw:polyline %draw-size; > -<!ATTLIST draw:polyline %draw-viewbox; > -<!ATTLIST draw:polyline draw:points %points; #REQUIRED> -<!ATTLIST draw:polyline %draw-style-name; > -<!ATTLIST draw:polyline %draw-transform; > -<!ATTLIST draw:polyline %zindex;> -<!ATTLIST draw:polyline %draw-end-position; > -<!ATTLIST draw:polyline %table-background; > -<!ATTLIST draw:polyline draw:id %draw-shape-id;> -<!ATTLIST draw:polyline %text-anchor;> -<!ATTLIST draw:polyline draw:layer %layerName; #IMPLIED> - -<!ELEMENT draw:polygon ( office:events?, %draw-text; )> -<!ATTLIST draw:polygon %draw-position; > -<!ATTLIST draw:polygon %draw-end-position; > -<!ATTLIST draw:polygon %table-background; > -<!ATTLIST draw:polygon %draw-size; > -<!ATTLIST draw:polygon %draw-viewbox; > -<!ATTLIST draw:polygon draw:points %points; #REQUIRED > -<!ATTLIST draw:polygon %draw-style-name; > -<!ATTLIST draw:polygon %draw-transform; > -<!ATTLIST draw:polygon %zindex;> -<!ATTLIST draw:polygon draw:id %draw-shape-id;> -<!ATTLIST draw:polygon %text-anchor;> -<!ATTLIST draw:polygon draw:layer %layerName; #IMPLIED> - -<!ELEMENT draw:path ( office:events?, %draw-text; )> -<!ATTLIST draw:path %draw-position;> -<!ATTLIST draw:path %draw-end-position; > -<!ATTLIST draw:path %table-background; > -<!ATTLIST draw:path %draw-size; > -<!ATTLIST draw:path %draw-viewbox; > -<!ATTLIST draw:path svg:d %pathData; #REQUIRED > -<!ATTLIST draw:path %draw-style-name; > -<!ATTLIST draw:path %draw-transform; > -<!ATTLIST draw:path %zindex;> -<!ATTLIST draw:path draw:id %draw-shape-id;> -<!ATTLIST draw:path %text-anchor;> -<!ATTLIST draw:path draw:layer %layerName; #IMPLIED> - -<!ELEMENT draw:circle ( office:events?, %draw-text; )> -<!ATTLIST draw:circle %draw-position; > -<!ATTLIST draw:circle %draw-size; > -<!ATTLIST draw:circle %draw-style-name; > -<!ATTLIST draw:circle %draw-transform; > -<!ATTLIST draw:circle %zindex;> -<!ATTLIST draw:circle %draw-end-position; > -<!ATTLIST draw:circle %table-background; > -<!ATTLIST draw:circle draw:id %draw-shape-id;> -<!ATTLIST draw:circle draw:kind (full|section|cut|arc) "full"> -<!ATTLIST draw:circle draw:start-angle %nonNegativeInteger; #IMPLIED> -<!ATTLIST draw:circle draw:end-angle %nonNegativeInteger; #IMPLIED> -<!ATTLIST draw:circle %text-anchor;> -<!ATTLIST draw:circle draw:layer %layerName; #IMPLIED> - -<!ELEMENT draw:ellipse ( office:events?, %draw-text; )> -<!ATTLIST draw:ellipse %draw-position; > -<!ATTLIST draw:ellipse %draw-size; > -<!ATTLIST draw:ellipse %draw-style-name; > -<!ATTLIST draw:ellipse %draw-transform; > -<!ATTLIST draw:ellipse %zindex;> -<!ATTLIST draw:ellipse %draw-end-position; > -<!ATTLIST draw:ellipse %table-background; > -<!ATTLIST draw:ellipse draw:id %draw-shape-id;> -<!ATTLIST draw:ellipse draw:kind (full|section|cut|arc) "full"> -<!ATTLIST draw:ellipse draw:start-angle %nonNegativeInteger; #IMPLIED> -<!ATTLIST draw:ellipse draw:end-angle %nonNegativeInteger; #IMPLIED> -<!ATTLIST draw:ellipse %text-anchor;> -<!ATTLIST draw:ellipse draw:layer %layerName; #IMPLIED> - -<!ELEMENT draw:connector ( office:events?, %draw-text;)> -<!ATTLIST draw:connector draw:type (standard|lines|line|curve) "standard"> -<!ATTLIST draw:connector draw:line-skew CDATA #IMPLIED> -<!ATTLIST draw:connector %draw-style-name;> -<!ATTLIST draw:connector svg:x1 %coordinate; #REQUIRED> -<!ATTLIST draw:connector svg:y1 %coordinate; #REQUIRED> -<!ATTLIST draw:connector svg:x2 %coordinate; #REQUIRED> -<!ATTLIST draw:connector svg:y2 %coordinate; #REQUIRED> -<!ATTLIST draw:connector draw:start-shape %draw-shape-id;> -<!ATTLIST draw:connector draw:start-glue-point %integer; #IMPLIED> -<!ATTLIST draw:connector draw:end-shape %draw-shape-id;> -<!ATTLIST draw:connector draw:end-glue-point %integer; #IMPLIED> -<!ATTLIST draw:connector %zindex;> -<!ATTLIST draw:connector %draw-end-position; > -<!ATTLIST draw:connector %table-background; > -<!ATTLIST draw:connector draw:id %draw-shape-id;> -<!ATTLIST draw:connector %text-anchor;> -<!ATTLIST draw:connector draw:layer %layerName; #IMPLIED> - -<!ELEMENT draw:control EMPTY> -<!ATTLIST draw:control %draw-style-name;> -<!ATTLIST draw:control %draw-position; > -<!ATTLIST draw:control %draw-size; > -<!ATTLIST draw:control %control-id; > -<!ATTLIST draw:control %zindex;> -<!ATTLIST draw:control %draw-end-position; > -<!ATTLIST draw:control %table-background; > -<!ATTLIST draw:control draw:id %draw-shape-id;> -<!ATTLIST draw:control %text-anchor;> -<!ATTLIST draw:control draw:layer %layerName; #IMPLIED> - -<!ELEMENT draw:g ( office:events?, (%shapes;)* ) > -<!ATTLIST draw:g svg:y %coordinate; #IMPLIED> -<!ATTLIST draw:g %draw-transform; > -<!ATTLIST draw:g draw:name %string; #IMPLIED> -<!ATTLIST draw:g %draw-style-name; > -<!ATTLIST draw:g %zindex;> -<!ATTLIST draw:g %draw-end-position; > -<!ATTLIST draw:g %table-background; > -<!ATTLIST draw:g draw:id %draw-shape-id;> -<!ATTLIST draw:g %text-anchor;> -<!ATTLIST draw:g draw:layer %layerName; #IMPLIED> - -<!ELEMENT draw:page-thumbnail EMPTY> -<!ATTLIST draw:page-thumbnail draw:page-number %positiveInteger; #IMPLIED> -<!ATTLIST draw:page-thumbnail %draw-position; > -<!ATTLIST draw:page-thumbnail %draw-size; > -<!ATTLIST draw:page-thumbnail %draw-style-name; > -<!ATTLIST draw:page-thumbnail %presentation-class; > -<!ATTLIST draw:page-thumbnail %zindex;> -<!ATTLIST draw:page-thumbnail %draw-end-position; > -<!ATTLIST draw:page-thumbnail %table-background; > -<!ATTLIST draw:page-thumbnail draw:id %draw-shape-id;> -<!ATTLIST draw:page-thumbnail %text-anchor;> -<!ATTLIST draw:page-thumbnail draw:layer %layerName; #IMPLIED> - -<!ELEMENT draw:caption ( office:events?, %draw-text;)> -<!ATTLIST draw:caption %draw-position; > -<!ATTLIST draw:caption %draw-end-position; > -<!ATTLIST draw:caption %table-background; > -<!ATTLIST draw:caption %draw-size; > -<!ATTLIST draw:caption %draw-style-name; > -<!ATTLIST draw:caption %draw-transform; > -<!ATTLIST draw:caption draw:caption-point-x %coordinate; #IMPLIED> -<!ATTLIST draw:caption draw:caption-point-y %coordinate; #IMPLIED> -<!ATTLIST draw:caption %zindex;> -<!ATTLIST draw:caption draw:id %draw-shape-id;> -<!ATTLIST draw:caption %text-anchor;> -<!ATTLIST draw:caption draw:layer %layerName; #IMPLIED> -<!ATTLIST draw:caption draw:corner-radius %nonNegativeLength; #IMPLIED> - -<!ELEMENT draw:measure ( office:events?, %draw-text;)> -<!ATTLIST draw:measure svg:x1 %coordinate; #REQUIRED> -<!ATTLIST draw:measure svg:y1 %coordinate; #REQUIRED> -<!ATTLIST draw:measure svg:x2 %coordinate; #REQUIRED> -<!ATTLIST draw:measure svg:y2 %coordinate; #REQUIRED> -<!ATTLIST draw:measure %draw-end-position; > -<!ATTLIST draw:measure %table-background; > -<!ATTLIST draw:measure %draw-style-name; > -<!ATTLIST draw:measure %draw-transform; > -<!ATTLIST draw:measure %zindex;> -<!ATTLIST draw:measure draw:id %draw-shape-id;> -<!ATTLIST draw:measure %text-anchor;> -<!ATTLIST draw:measure draw:layer %layerName; #IMPLIED> - -<!-- graphic style elements --> -<!ELEMENT draw:gradient EMPTY > -<!ATTLIST draw:gradient draw:name %styleName; #REQUIRED> -<!ATTLIST draw:gradient draw:style %gradient-style; #REQUIRED> -<!ATTLIST draw:gradient draw:cx %coordinate; #IMPLIED> -<!ATTLIST draw:gradient draw:cy %coordinate; #IMPLIED> -<!ATTLIST draw:gradient draw:start-color %color; #IMPLIED> -<!ATTLIST draw:gradient draw:end-color %color; #IMPLIED> -<!ATTLIST draw:gradient draw:start-intensity %percentage; #IMPLIED> -<!ATTLIST draw:gradient draw:end-intensity %percentage; #IMPLIED> -<!ATTLIST draw:gradient draw:angle %integer; #IMPLIED> -<!ATTLIST draw:gradient draw:border %percentage; #IMPLIED> - -<!ELEMENT draw:hatch EMPTY > -<!ATTLIST draw:hatch draw:name %styleName; #REQUIRED> -<!ATTLIST draw:hatch draw:style (single|double|triple) #REQUIRED > -<!ATTLIST draw:hatch draw:color %color; #IMPLIED> -<!ATTLIST draw:hatch draw:distance %length; #IMPLIED> -<!ATTLIST draw:hatch draw:rotation %integer; #IMPLIED> - - -<!ELEMENT draw:fill-image EMPTY > -<!ATTLIST draw:fill-image draw:name %styleName; #REQUIRED> -<!ATTLIST draw:fill-image xlink:href %uriReference; #REQUIRED> -<!ATTLIST draw:fill-image xlink:type (simple) #IMPLIED> -<!ATTLIST draw:fill-image xlink:show (embed) #IMPLIED> -<!ATTLIST draw:fill-image xlink:actuate (onLoad) #IMPLIED> -<!ATTLIST draw:fill-image svg:width %length; #IMPLIED> -<!ATTLIST draw:fill-image svg:height %length; #IMPLIED> - -<!ELEMENT draw:transparency EMPTY> -<!ATTLIST draw:transparency draw:name %styleName; #REQUIRED> -<!ATTLIST draw:transparency draw:style %gradient-style; #REQUIRED> -<!ATTLIST draw:transparency draw:cx %coordinate; #IMPLIED> -<!ATTLIST draw:transparency draw:cy %coordinate; #IMPLIED> -<!ATTLIST draw:transparency draw:start %percentage; #IMPLIED> -<!ATTLIST draw:transparency draw:end %percentage; #IMPLIED> -<!ATTLIST draw:transparency draw:angle %integer; #IMPLIED> -<!ATTLIST draw:transparency draw:border %percentage; #IMPLIED> - -<!ELEMENT draw:marker EMPTY> -<!ATTLIST draw:marker draw:name %styleName; #REQUIRED> -<!ATTLIST draw:marker %draw-viewbox; > -<!ATTLIST draw:marker svg:d %pathData; #REQUIRED> - -<!ELEMENT draw:stroke-dash EMPTY> -<!ATTLIST draw:stroke-dash draw:name %styleName; #REQUIRED> -<!ATTLIST draw:stroke-dash draw:style (rect|round) #IMPLIED> -<!ATTLIST draw:stroke-dash draw:dots1 %integer; #IMPLIED> -<!ATTLIST draw:stroke-dash draw:dots1-length %length; #IMPLIED> -<!ATTLIST draw:stroke-dash draw:dots2 %integer; #IMPLIED> -<!ATTLIST draw:stroke-dash draw:dots2-length %length; #IMPLIED> -<!ATTLIST draw:stroke-dash draw:distance %length; #IMPLIED> - -<!-- stroke attributes --> -<!ATTLIST style:properties draw:stroke (none|dash|solid) #IMPLIED> -<!ATTLIST style:properties draw:stroke-dash CDATA #IMPLIED> -<!ATTLIST style:properties svg:stroke-width %length; #IMPLIED> -<!ATTLIST style:properties svg:stroke-color %color; #IMPLIED> -<!ATTLIST style:properties draw:marker-start %styleName; #IMPLIED> -<!ATTLIST style:properties draw:marker-end %styleName; #IMPLIED> -<!ATTLIST style:properties draw:marker-start-width %length; #IMPLIED> -<!ATTLIST style:properties draw:marker-end-width %length; #IMPLIED> -<!ATTLIST style:properties draw:marker-start-center %boolean; #IMPLIED> -<!ATTLIST style:properties draw:marker-end-center %boolean; #IMPLIED> -<!ATTLIST style:properties svg:stroke-opacity %floatOrPercentage; #IMPLIED> -<!ATTLIST style:properties svg:stroke-linejoin (miter|round|bevel|middle|none|inherit) #IMPLIED> - -<!-- text attributes --> -<!ATTLIST style:properties draw:auto-grow-width %boolean; #IMPLIED> -<!ATTLIST style:properties draw:auto-grow-height %boolean; #IMPLIED> -<!ATTLIST style:properties draw:fit-to-size %boolean; #IMPLIED> -<!ATTLIST style:properties draw:fit-to-contour %boolean; #IMPLIED> -<!ATTLIST style:properties draw:textarea-horizontal-align ( left | center | right | justify ) #IMPLIED> -<!ATTLIST style:properties draw:textarea-vertical-align ( top | middle | bottom | justify ) #IMPLIED> -<!ATTLIST style:properties draw:writing-mode (lr-tb|tb-rl) "lr-tb"> - -<!-- fill attributes --> -<!ATTLIST style:properties draw:fill (none|solid|bitmap|gradient|hatch) #IMPLIED> -<!ATTLIST style:properties draw:fill-color %color; #IMPLIED> -<!ATTLIST style:properties draw:fill-gradient-name %styleName; #IMPLIED> -<!ATTLIST style:properties draw:gradient-step-count CDATA #IMPLIED> -<!ATTLIST style:properties draw:fill-hatch-name %styleName; #IMPLIED> -<!ATTLIST style:properties draw:fill-hatch-solid %boolean; #IMPLIED> -<!ATTLIST style:properties draw:fill-image-name %styleName; #IMPLIED> -<!ATTLIST style:properties style:repeat (no-repeat|repeat|stretch) #IMPLIED> -<!ATTLIST style:properties draw:fill-image-width %lengthOrPercentage; #IMPLIED> -<!ATTLIST style:properties draw:fill-image-height %lengthOrPercentage; #IMPLIED> -<!ATTLIST style:properties draw:fill-image-ref-point-x %percentage; #IMPLIED> -<!ATTLIST style:properties draw:fill-image-ref-point-y %percentage; #IMPLIED> -<!ATTLIST style:properties draw:fill-image-ref-point %rectanglePoint; #IMPLIED> -<!ATTLIST style:properties draw:tile-repeat-offset CDATA #IMPLIED> -<!ATTLIST style:properties draw:transparency %percentage; #IMPLIED> -<!ATTLIST style:properties draw:transparency-name %styleName; #IMPLIED> - -<!-- graphic attributes --> -<!ATTLIST style:properties draw:color-mode (greyscale|mono|watermark|standard) #IMPLIED> -<!ATTLIST style:properties draw:luminance %percentage; #IMPLIED> -<!ATTLIST style:properties draw:contrast %percentage; #IMPLIED> -<!ATTLIST style:properties draw:gamma %percentage; #IMPLIED> -<!ATTLIST style:properties draw:red %percentage; #IMPLIED> -<!ATTLIST style:properties draw:green %percentage; #IMPLIED> -<!ATTLIST style:properties draw:blue %percentage; #IMPLIED> -<!ATTLIST style:properties draw:color-inversion %boolean; #IMPLIED> -<!ATTLIST style:properties draw:mirror %boolean; #IMPLIED> - -<!-- shadow attributes --> -<!ATTLIST style:properties draw:shadow (visible|hidden) #IMPLIED> -<!ATTLIST style:properties draw:shadow-offset-x %length; #IMPLIED> -<!ATTLIST style:properties draw:shadow-offset-y %length; #IMPLIED> -<!ATTLIST style:properties draw:shadow-color %color; #IMPLIED> -<!ATTLIST style:properties draw:shadow-transparency CDATA #IMPLIED> - -<!-- connector attributes --> -<!ATTLIST style:properties draw:start-line-spacing-horizontal %distance; #IMPLIED> -<!ATTLIST style:properties draw:start-line-spacing-vertical %distance; #IMPLIED> -<!ATTLIST style:properties draw:end-line-spacing-horizontal %distance; #IMPLIED> -<!ATTLIST style:properties draw:end-line-spacing-vertical %distance; #IMPLIED> - -<!-- measure attributes --> -<!ATTLIST style:properties draw:line-distance %distance; #IMPLIED> -<!ATTLIST style:properties draw:guide-overhang %distance; #IMPLIED> -<!ATTLIST style:properties draw:guide-distance %distance; #IMPLIED> -<!ATTLIST style:properties draw:start-guide %distance; #IMPLIED> -<!ATTLIST style:properties draw:end-guide %distance; #IMPLIED> -<!ATTLIST style:properties draw:measure-align (automatic|left-outside|inside|right-outside) #IMPLIED> -<!ATTLIST style:properties draw:measure-vertical-align (automatic|above|below|center) #IMPLIED> -<!ATTLIST style:properties draw:unit (automatic|mm|cm|m|km|pt|pc|inch|ft|mi) #IMPLIED> -<!ATTLIST style:properties draw:show-unit %boolean; #IMPLIED> -<!ATTLIST style:properties draw:placing (below|above) #IMPLIED> -<!ATTLIST style:properties draw:parallel %boolean; #IMPLIED> -<!ATTLIST style:properties draw:decimal-places %nonNegativeLength; #IMPLIED> - -<!-- frame attributes --> -<!ATTLIST style:properties draw:frame-display-scrollbar %boolean; #IMPLIED> -<!ATTLIST style:properties draw:frame-display-border %boolean; #IMPLIED> -<!ATTLIST style:properties draw:frame-margin-horizontal %nonNegativePixelLength; #IMPLIED> -<!ATTLIST style:properties draw:frame-margin-vertical %nonNegativePixelLength; #IMPLIED> -<!ATTLIST style:properties draw:size-protect %boolean; #IMPLIED> -<!ATTLIST style:properties draw:move-protect %boolean; #IMPLIED> - -<!-- ole object attributes --> -<!ATTLIST style:properties draw:visible-area-left %nonNegativeLength; #IMPLIED> -<!ATTLIST style:properties draw:visible-area-top %nonNegativeLength; #IMPLIED> -<!ATTLIST style:properties draw:visible-area-width %positiveLength; #IMPLIED> -<!ATTLIST style:properties draw:visible-area-height %positiveLength; #IMPLIED> - -<!-- fontwork attributes --> -<!ATTLIST style:properties draw:fontwork-style (rotate|upright|slant-x|slant-y|none) #IMPLIED> -<!ATTLIST style:properties draw:fontwork-adjust (left|right|autosize|center) #IMPLIED> -<!ATTLIST style:properties draw:fontwork-distance %distance; #IMPLIED> -<!ATTLIST style:properties draw:fontwork-start %distance; #IMPLIED> -<!ATTLIST style:properties draw:fontwork-mirror %boolean; #IMPLIED> -<!ATTLIST style:properties draw:fontwork-outline %boolean; #IMPLIED> -<!ATTLIST style:properties draw:fontwork-shadow (normal|slant|none) #IMPLIED> -<!ATTLIST style:properties draw:fontwork-shadow-color %color; #IMPLIED> -<!ATTLIST style:properties draw:fontwork-shadow-offset-x %distance; #IMPLIED> -<!ATTLIST style:properties draw:fontwork-shadow-offset-y %distance; #IMPLIED> -<!ATTLIST style:properties draw:fontwork-form (none|top-circle|bottom-circle|left-circle|right-circle|top-arc|bottom-arc|left-arc|right-arc|button1|button2|button3|button4) #IMPLIED> -<!ATTLIST style:properties draw:fontwork-hide-form %boolean; #IMPLIED> -<!ATTLIST style:properties draw:fontwork-shadow-transparence %percentage; #IMPLIED> - -<!-- caption attributes --> -<!ATTLIST style:properties draw:caption-type (straight-line|angled-line|angled-connector-line) #IMPLIED> -<!ATTLIST style:properties draw:caption-angle-type (fixed|free) #IMPLIED> -<!ATTLIST style:properties draw:caption-angle %nonNegativeInteger; #IMPLIED> -<!ATTLIST style:properties draw:caption-gap %distance; #IMPLIED> -<!ATTLIST style:properties draw:caption-escape-direction (horizontal|vertical|auto) #IMPLIED> -<!ATTLIST style:properties draw:caption-escape %lengthOrPercentage; #IMPLIED> -<!ATTLIST style:properties draw:caption-line-length %distance; #IMPLIED> -<!ATTLIST style:properties draw:caption-fit-line-length %boolean; #IMPLIED> - -<!-- Animations --> -<!ELEMENT presentation:sound EMPTY> -<!ATTLIST presentation:sound xlink:href %uriReference; #REQUIRED> -<!ATTLIST presentation:sound xlink:type (simple) #FIXED "simple"> -<!ATTLIST presentation:sound xlink:show (new|replace) #IMPLIED> -<!ATTLIST presentation:sound xlink:actuate (onRequest) "onRequest"> -<!ATTLIST presentation:sound presentation:play-full %boolean; #IMPLIED> - -<!ELEMENT presentation:show-shape (presentation:sound)?> -<!ATTLIST presentation:show-shape draw:shape-id CDATA #REQUIRED> -<!ATTLIST presentation:show-shape presentation:effect %presentationEffects; "none"> -<!ATTLIST presentation:show-shape presentation:direction %presentationEffectDirections; "none"> -<!ATTLIST presentation:show-shape presentation:speed %presentationSpeeds; "medium"> -<!ATTLIST presentation:show-shape presentation:start-scale %percentage; "100%"> -<!ATTLIST presentation:show-shape presentation:path-id CDATA #IMPLIED > - -<!ELEMENT presentation:show-text (presentation:sound)?> -<!ATTLIST presentation:show-text draw:shape-id CDATA #REQUIRED> -<!ATTLIST presentation:show-text presentation:effect %presentationEffects; "none"> -<!ATTLIST presentation:show-text presentation:direction %presentationEffectDirections; "none"> -<!ATTLIST presentation:show-text presentation:speed %presentationSpeeds; "medium"> -<!ATTLIST presentation:show-text presentation:start-scale %percentage; "100%"> -<!ATTLIST presentation:show-text presentation:path-id CDATA #IMPLIED > - -<!ELEMENT presentation:hide-shape (presentation:sound)?> -<!ATTLIST presentation:hide-shape draw:shape-id CDATA #REQUIRED> -<!ATTLIST presentation:hide-shape presentation:effect %presentationEffects; "none"> -<!ATTLIST presentation:hide-shape presentation:direction %presentationEffectDirections; "none"> -<!ATTLIST presentation:hide-shape presentation:speed %presentationSpeeds; "medium"> -<!ATTLIST presentation:hide-shape presentation:start-scale %percentage; "100%"> -<!ATTLIST presentation:hide-shape presentation:path-id CDATA #IMPLIED > - -<!ELEMENT presentation:hide-text (presentation:sound)?> -<!ATTLIST presentation:hide-text draw:shape-id CDATA #REQUIRED> -<!ATTLIST presentation:hide-text presentation:effect %presentationEffects; "none"> -<!ATTLIST presentation:hide-text presentation:direction %presentationEffectDirections; "none"> -<!ATTLIST presentation:hide-text presentation:speed %presentationSpeeds; "medium"> -<!ATTLIST presentation:hide-text presentation:start-scale %percentage; "100%"> -<!ATTLIST presentation:hide-text presentation:path-id CDATA #IMPLIED > - -<!ELEMENT presentation:dim (presentation:sound)?> -<!ATTLIST presentation:dim draw:shape-id CDATA #REQUIRED> -<!ATTLIST presentation:dim draw:color %color; #REQUIRED> - -<!ELEMENT presentation:play EMPTY> -<!ATTLIST presentation:play draw:shape-id CDATA #REQUIRED> -<!ATTLIST presentation:play presentation:speed %presentationSpeeds; "medium"> - -<!ELEMENT presentation:animations (presentation:show-shape|presentation:show-text|presentation:hide-shape|presentation:hide-text|presentation:dim|presentation:play)*> - -<!ELEMENT presentation:show EMPTY> -<!ATTLIST presentation:show presentation:name %styleName; #REQUIRED> -<!ATTLIST presentation:show presentation:pages CDATA #REQUIRED> - -<!ELEMENT presentation:settings (presentation:show)*> -<!ATTLIST presentation:settings presentation:start-page %styleName; #IMPLIED> -<!ATTLIST presentation:settings presentation:show %styleName; #IMPLIED> -<!ATTLIST presentation:settings presentation:full-screen %boolean; "true"> -<!ATTLIST presentation:settings presentation:endless %boolean; "false"> -<!ATTLIST presentation:settings presentation:pause %timeDuration; #IMPLIED> -<!ATTLIST presentation:settings presentation:show-logo %boolean; "false"> -<!ATTLIST presentation:settings presentation:force-manual %boolean; "false"> -<!ATTLIST presentation:settings presentation:mouse-visible %boolean; "true"> -<!ATTLIST presentation:settings presentation:mouse-as-pen %boolean; "false"> -<!ATTLIST presentation:settings presentation:start-with-navigator %boolean; "false"> -<!ATTLIST presentation:settings presentation:animations (enabled|disabled) "enabled"> -<!ATTLIST presentation:settings presentation:stay-on-top %boolean; "false"> -<!ATTLIST presentation:settings presentation:transition-on-click (enabled|disabled) "enabled"> - -<!-- Drawing page --> -<!ELEMENT draw:page (office:forms?,(%shapes;)*,presentation:animations?,presentation:notes?)> -<!ATTLIST draw:page draw:name %string; #IMPLIED> -<!ATTLIST draw:page draw:style-name %styleName; #IMPLIED> -<!ATTLIST draw:page draw:master-page-name %styleName; #REQUIRED> -<!ATTLIST draw:page presentation:presentation-page-layout-name %styleName; #IMPLIED> -<!ATTLIST draw:page draw:id %nonNegativeInteger; #IMPLIED> -<!ATTLIST draw:page xlink:href %uriReference; #IMPLIED> -<!ATTLIST draw:page xlink:type (simple) #IMPLIED> -<!ATTLIST draw:page xlink:show (replace) #IMPLIED> -<!ATTLIST draw:page xlink:actuate (onRequest) #IMPLIED> - -<!-- Presentation notes --> -<!ELEMENT presentation:notes (%shapes;)*> -<!ATTLIST presentation:notes style:page-master-name %styleName; #IMPLIED> - -<!-- presentation page layouts --> -<!ELEMENT style:presentation-page-layout (presentation:placeholder)* > -<!ATTLIST style:presentation-page-layout style:name %styleName; #REQUIRED> -<!ELEMENT presentation:placeholder EMPTY > -<!ATTLIST presentation:placeholder presentation:object (title|outline|subtitle|text|graphic|object|chart|orgchart|page|notes|handout) #REQUIRED> -<!ATTLIST presentation:placeholder svg:x %coordinateOrPercentage; #REQUIRED> -<!ATTLIST presentation:placeholder svg:y %coordinateOrPercentage; #REQUIRED> -<!ATTLIST presentation:placeholder svg:width %lengthOrPercentage; #REQUIRED> -<!ATTLIST presentation:placeholder svg:height %lengthOrPercentage; #REQUIRED> - -<!-- presentation page attributes --> -<!ATTLIST style:properties presentation:transition-type (manual|automatic|semi-automatic) #IMPLIED > -<!ATTLIST style:properties presentation:transition-style (none|fade-from-left|fade-from-top|fade-from-right|fade-from-bottom|fade-to-center|fade-from-center|move-from-left|move-from-top|move-from-right|move-from-bottom|roll-from-top|roll-from-left|roll-from-right|roll-from-bottom|vertical-stripes|horizontal-stripes|clockwise|counterclockwise|fade-from-upperleft|fade-from-upperright|fade-from-lowerleft|fade-from-lowerright|close-vertical|close-horizontal|open-vertical|open-horizontal|spiralin-left|spiralin-right|spiralout-left|spiralout-right|dissolve|wavyline-from-left|wavyline-from-top|wavyline-from-right|wavyline-from-bottom|random|stretch-from-left|stretch-from-top|stretch-from-right|stretch-from-bottom|vertical-lines|horizontal-lines) #IMPLIED > -<!ATTLIST style:properties presentation:transition-speed %presentationSpeeds; #IMPLIED > -<!ATTLIST style:properties presentation:duration %timeDuration; #IMPLIED> -<!ATTLIST style:properties presentation:visibility (visible|hidden) #IMPLIED> -<!ATTLIST style:properties draw:background-size (full|border) #IMPLIED> -<!ATTLIST style:properties presentation:background-objects-visible %boolean; #IMPLIED> -<!ATTLIST style:properties presentation:background-visible %boolean; #IMPLIED> - - -<!-- text boxes --> -<!ELEMENT draw:text-box (office:events?,draw:image-map?, - %sectionText;)> -<!ATTLIST draw:text-box %draw-style-name;> -<!ATTLIST draw:text-box %draw-transform; > -<!ATTLIST draw:text-box draw:name %string; #IMPLIED> -<!ATTLIST draw:text-box draw:chain-next-name %string; #IMPLIED> - -<!ATTLIST draw:text-box %text-anchor;> -<!ATTLIST draw:text-box %draw-position;> -<!ATTLIST draw:text-box %draw-end-position; > -<!ATTLIST draw:text-box %table-background; > -<!ATTLIST draw:text-box svg:width %lengthOrPercentage; #IMPLIED> -<!ATTLIST draw:text-box svg:height %lengthOrPercentage; #IMPLIED> -<!ATTLIST draw:text-box style:rel-width %percentage; #IMPLIED> -<!ATTLIST draw:text-box style:rel-height %percentage; #IMPLIED> -<!ATTLIST draw:text-box fo:min-height %lengthOrPercentage; #IMPLIED> -<!ATTLIST draw:text-box %zindex;> -<!ATTLIST draw:text-box %presentation-class; > -<!ATTLIST draw:text-box draw:id %draw-shape-id;> -<!ATTLIST draw:text-box draw:layer %layerName; #IMPLIED> -<!ATTLIST draw:text-box draw:corner-radius %nonNegativeLength; #IMPLIED> - -<!-- image --> -<!ELEMENT draw:image (office:binary-data?,office:events?,draw:image-map?,svg:desc?,(draw:contour-polygon|draw:contour-path)?)> -<!ATTLIST draw:image %draw-transform; > -<!ATTLIST draw:image %draw-style-name;> -<!ATTLIST draw:image draw:name %string; #IMPLIED> -<!ATTLIST draw:image xlink:href %uriReference; #IMPLIED> -<!ATTLIST draw:image xlink:type (simple) #IMPLIED> -<!ATTLIST draw:image xlink:show (embed) #IMPLIED> -<!ATTLIST draw:image xlink:actuate (onLoad) #IMPLIED> -<!ATTLIST draw:image draw:filter-name %string; #IMPLIED> -<!ATTLIST draw:image %text-anchor;> -<!ATTLIST draw:image %draw-position;> -<!ATTLIST draw:image %draw-end-position; > -<!ATTLIST draw:image %table-background; > -<!ATTLIST draw:image svg:width %lengthOrPercentage; #IMPLIED> -<!ATTLIST draw:image svg:height %lengthOrPercentage; #IMPLIED> -<!ATTLIST draw:image %presentation-class; > -<!ATTLIST draw:image %zindex;> -<!ATTLIST draw:image draw:id %draw-shape-id;> -<!ATTLIST draw:image draw:layer %layerName; #IMPLIED> -<!ATTLIST draw:image style:rel-width %percentage; #IMPLIED> -<!ATTLIST draw:image style:rel-height %percentage; #IMPLIED> - -<!-- objects --> -<!ELEMENT draw:thumbnail EMPTY> -<!ATTLIST draw:thumbnail xlink:href %uriReference; #REQUIRED> -<!ATTLIST draw:thumbnail xlink:type (simple) #IMPLIED> -<!ATTLIST draw:thumbnail xlink:show (embed) #IMPLIED> -<!ATTLIST draw:thumbnail xlink:actuate (onLoad) #IMPLIED> - -<!ELEMENT math:math ANY> <!-- dummy (we have no MathML DTD currently)--> -<!ELEMENT draw:object (draw:thumbnail?,(office:document|math:math)?,office:events?, draw:image-map?, svg:desc?,(draw:contour-polygon|draw:contour-path)?)> -<!ATTLIST draw:object %draw-style-name;> -<!ATTLIST draw:object draw:name %string; #IMPLIED> -<!ATTLIST draw:object xlink:href %uriReference; #IMPLIED> -<!ATTLIST draw:object xlink:type (simple) #IMPLIED> -<!ATTLIST draw:object xlink:show (embed) #IMPLIED> -<!ATTLIST draw:object xlink:actuate (onLoad) #IMPLIED> -<!ATTLIST draw:object %text-anchor;> -<!ATTLIST draw:object %draw-position;> -<!ATTLIST draw:object %draw-end-position; > -<!ATTLIST draw:object %table-background; > -<!ATTLIST draw:object svg:width %lengthOrPercentage; #IMPLIED> -<!ATTLIST draw:object svg:height %lengthOrPercentage; #IMPLIED> -<!ATTLIST draw:object %presentation-class; > -<!ATTLIST draw:object %zindex;> -<!ATTLIST draw:object draw:id %draw-shape-id;> -<!ATTLIST draw:object draw:layer %layerName; #IMPLIED> -<!ATTLIST draw:object draw:notify-on-update-of-ranges %string; #IMPLIED> -<!ATTLIST draw:object style:rel-width %percentage; #IMPLIED> -<!ATTLIST draw:object style:rel-height %percentage; #IMPLIED> - -<!ELEMENT draw:object-ole (office:binary-data?|office:events?|draw:image-map?|svg:desc?|draw:contour-polygon?|draw:contour-path?|draw:thumbnail?)> -<!ATTLIST draw:object-ole draw:class-id CDATA #IMPLIED> -<!ATTLIST draw:object-ole %draw-style-name;> -<!ATTLIST draw:object-ole draw:name %string; #IMPLIED> -<!ATTLIST draw:object-ole xlink:href %uriReference; #IMPLIED> -<!ATTLIST draw:object-ole xlink:type (simple) #IMPLIED> -<!ATTLIST draw:object-ole xlink:show (embed) #IMPLIED> -<!ATTLIST draw:object-ole xlink:actuate (onLoad) #IMPLIED> -<!ATTLIST draw:object-ole %text-anchor;> -<!ATTLIST draw:object-ole %draw-position;> -<!ATTLIST draw:object-ole %draw-end-position; > -<!ATTLIST draw:object-ole %table-background; > -<!ATTLIST draw:object-ole svg:width %lengthOrPercentage; #IMPLIED> -<!ATTLIST draw:object-ole svg:height %lengthOrPercentage; #IMPLIED> -<!ATTLIST draw:object-ole %presentation-class; > -<!ATTLIST draw:object-ole %zindex;> -<!ATTLIST draw:object-ole draw:id %draw-shape-id;> -<!ATTLIST draw:object-ole draw:layer %layerName; #IMPLIED> -<!ATTLIST draw:object-ole style:rel-width %percentage; #IMPLIED> -<!ATTLIST draw:object-ole style:rel-height %percentage; #IMPLIED> - -<!ELEMENT svg:desc (#PCDATA)> - -<!ELEMENT draw:contour-polygon EMPTY> -<!ATTLIST draw:contour-polygon svg:width %coordinate; #REQUIRED> -<!ATTLIST draw:contour-polygon svg:height %coordinate; #REQUIRED> -<!ATTLIST draw:contour-polygon %draw-viewbox;> -<!ATTLIST draw:contour-polygon draw:points %points; #REQUIRED> -<!ATTLIST draw:contour-polygon draw:recreate-on-edit %boolean; #IMPLIED> - -<!ELEMENT draw:contour-path EMPTY> -<!ATTLIST draw:contour-path svg:width %coordinate; #REQUIRED> -<!ATTLIST draw:contour-path svg:height %coordinate; #REQUIRED> -<!ATTLIST draw:contour-path %draw-viewbox;> -<!ATTLIST draw:contour-path svg:d %pathData; #REQUIRED> -<!ATTLIST draw:contour-path draw:recreate-on-edit %boolean; #IMPLIED> - -<!-- hyperlink --> -<!ELEMENT draw:a (draw:image|draw:text-box)> -<!ATTLIST draw:a xlink:href %uriReference; #REQUIRED> -<!ATTLIST draw:a xlink:type (simple) #FIXED "simple"> -<!ATTLIST draw:a xlink:show (new|replace) #IMPLIED> -<!ATTLIST draw:a xlink:actuate (onRequest) "onRequest"> -<!ATTLIST draw:a office:name %string; #IMPLIED> -<!ATTLIST draw:a office:target-frame-name %string; #IMPLIED> -<!ATTLIST draw:a office:server-map %boolean; "false"> - -<!-- 3d properties --> -<!ATTLIST style:properties dr3d:horizontal-segments %nonNegativeInteger; #IMPLIED> -<!ATTLIST style:properties dr3d:vertical-segments %nonNegativeInteger; #IMPLIED> -<!ATTLIST style:properties dr3d:edge-rounding %percentage; #IMPLIED> -<!ATTLIST style:properties dr3d:edge-rounding-mode (correct|attractive) #IMPLIED> -<!ATTLIST style:properties dr3d:back-scale %percentage; #IMPLIED> -<!ATTLIST style:properties dr3d:end-angle %nonNegativeInteger; #IMPLIED> -<!ATTLIST style:properties dr3d:depth %length; #IMPLIED> -<!ATTLIST style:properties dr3d:backface-culling (enabled|disabled) #IMPLIED> -<!ATTLIST style:properties dr3d:lighting-mode (standard|double-sided) #IMPLIED> -<!ATTLIST style:properties dr3d:normals-kind (object|flat|sphere) #IMPLIED> -<!ATTLIST style:properties dr3d:normals-direction (normal|inverse) #IMPLIED> -<!ATTLIST style:properties dr3d:texture-generation-mode-x (object|parallel|sphere) #IMPLIED> -<!ATTLIST style:properties dr3d:texture-generation-mode-y (object|parallel|sphere) #IMPLIED> -<!ATTLIST style:properties dr3d:texture-kind (luminance|intesity|color) #IMPLIED> -<!ATTLIST style:properties dr3d:texture-filter (enabled|disabled) #IMPLIED> -<!ATTLIST style:properties dr3d:texture-mode (replace|modulate|blend) #IMPLIED> -<!ATTLIST style:properties dr3d:ambient-color %color; #IMPLIED> -<!ATTLIST style:properties dr3d:emissive-color %color; #IMPLIED> -<!ATTLIST style:properties dr3d:specular-color %color; #IMPLIED> -<!ATTLIST style:properties dr3d:diffuse-color %color; #IMPLIED> -<!ATTLIST style:properties dr3d:shininess %percentage; #IMPLIED> -<!ATTLIST style:properties dr3d:shadow (visible|hidden) #IMPLIED> -<!ATTLIST style:properties dr3d:close-front %boolean; #IMPLIED> -<!ATTLIST style:properties dr3d:close-back %boolean; #IMPLIED> - -<!ELEMENT dr3d:light EMPTY> -<!ATTLIST dr3d:light dr3d:diffuse-color %color; #IMPLIED> -<!ATTLIST dr3d:light dr3d:direction %vector3D; #REQUIRED> -<!ATTLIST dr3d:light dr3d:enabled %boolean; #IMPLIED> -<!ATTLIST dr3d:light dr3d:specular %boolean; #IMPLIED> - -<!ENTITY % shapes3d "(dr3d:scene|dr3d:extrude|dr3d:sphere|dr3d:rotate|dr3d:cube)"> - -<!ELEMENT dr3d:cube EMPTY> -<!ATTLIST dr3d:cube dr3d:transform CDATA #IMPLIED> -<!ATTLIST dr3d:cube dr3d:min-edge %vector3D; #IMPLIED> -<!ATTLIST dr3d:cube dr3d:max-edge %vector3D; #IMPLIED> -<!ATTLIST dr3d:cube %zindex;> -<!ATTLIST dr3d:cube draw:id %draw-shape-id;> -<!ATTLIST dr3d:cube %draw-end-position; > -<!ATTLIST dr3d:cube %table-background; > -<!ATTLIST dr3d:cube %draw-style-name; > -<!ATTLIST dr3d:cube draw:layer %layerName; #IMPLIED> - -<!ELEMENT dr3d:sphere EMPTY> -<!ATTLIST dr3d:sphere dr3d:transform CDATA #IMPLIED> -<!ATTLIST dr3d:sphere dr3d:center %vector3D; #IMPLIED> -<!ATTLIST dr3d:sphere dr3d:size %vector3D; #IMPLIED> -<!ATTLIST dr3d:sphere %zindex;> -<!ATTLIST dr3d:sphere draw:id %draw-shape-id;> -<!ATTLIST dr3d:sphere %draw-end-position; > -<!ATTLIST dr3d:sphere %table-background; > -<!ATTLIST dr3d:sphere %draw-style-name; > -<!ATTLIST dr3d:sphere draw:layer %layerName; #IMPLIED> - -<!ELEMENT dr3d:extrude EMPTY> -<!ATTLIST dr3d:extrude dr3d:transform CDATA #IMPLIED> -<!ATTLIST dr3d:extrude %draw-viewbox;> -<!ATTLIST dr3d:extrude svg:d %pathData; #REQUIRED > -<!ATTLIST dr3d:extrude %zindex;> -<!ATTLIST dr3d:extrude draw:id %draw-shape-id;> -<!ATTLIST dr3d:extrude %draw-end-position; > -<!ATTLIST dr3d:extrude %table-background; > -<!ATTLIST dr3d:extrude %draw-style-name; > -<!ATTLIST dr3d:extrude draw:layer %layerName; #IMPLIED> - -<!ELEMENT dr3d:rotate EMPTY> -<!ATTLIST dr3d:rotate dr3d:transform CDATA #IMPLIED> -<!ATTLIST dr3d:rotate %draw-viewbox;> -<!ATTLIST dr3d:rotate svg:d %pathData; #REQUIRED > -<!ATTLIST dr3d:rotate %zindex;> -<!ATTLIST dr3d:rotate draw:id %draw-shape-id;> -<!ATTLIST dr3d:rotate %draw-end-position; > -<!ATTLIST dr3d:rotate %table-background; > -<!ATTLIST dr3d:rotate %draw-style-name; > -<!ATTLIST dr3d:rotate draw:layer %layerName; #IMPLIED> - -<!ELEMENT dr3d:scene (dr3d:light*,(%shapes3d;)*)> -<!ATTLIST dr3d:scene %draw-style-name; > -<!ATTLIST dr3d:scene svg:x %coordinate; #IMPLIED> -<!ATTLIST dr3d:scene svg:y %coordinate; #IMPLIED> -<!ATTLIST dr3d:scene svg:width %length; #IMPLIED> -<!ATTLIST dr3d:scene svg:height %length; #IMPLIED> -<!ATTLIST dr3d:scene dr3d:vrp %vector3D; #IMPLIED> -<!ATTLIST dr3d:scene dr3d:vpn %vector3D; #IMPLIED> -<!ATTLIST dr3d:scene dr3d:vup %vector3D; #IMPLIED> -<!ATTLIST dr3d:scene dr3d:projection (parallel|perspective) #IMPLIED> -<!ATTLIST dr3d:scene dr3d:transform CDATA #IMPLIED> -<!ATTLIST dr3d:scene dr3d:distance %length; #IMPLIED> -<!ATTLIST dr3d:scene dr3d:focal-length %length; #IMPLIED> -<!ATTLIST dr3d:scene dr3d:shadow-slant %nonNegativeInteger; #IMPLIED> -<!ATTLIST dr3d:scene dr3d:shade-mode (flat|phong|gouraud|draft) #IMPLIED> -<!ATTLIST dr3d:scene dr3d:ambient-color %color; #IMPLIED> -<!ATTLIST dr3d:scene dr3d:lighting-mode %boolean; #IMPLIED> -<!ATTLIST dr3d:scene %zindex;> -<!ATTLIST dr3d:scene draw:id %draw-shape-id;> -<!ATTLIST dr3d:scene %draw-end-position; > -<!ATTLIST dr3d:scene %table-background; > - -<!-- layer --> - -<!ELEMENT draw:layer-set (draw:layer*)> - -<!ELEMENT draw:layer EMPTY> -<!ATTLIST draw:layer draw:name %layerName; #REQUIRED> - -<!-- events --> -<!ELEMENT presentation:event (presentation:sound)?> -<!ATTLIST presentation:event %event-name;> -<!ATTLIST presentation:event presentation:action (none|previous-page|next-page|first-page|last-page|hide|stop|execute|show|verb|fade-out|sound) #REQUIRED> -<!ATTLIST presentation:event presentation:effect %presentationEffects; "none"> -<!ATTLIST presentation:event presentation:direction %presentationEffectDirections; "none"> -<!ATTLIST presentation:event presentation:speed %presentationSpeeds; "medium"> -<!ATTLIST presentation:event presentation:start-scale %percentage; "100%"> -<!ATTLIST presentation:event xlink:href %uriReference; #IMPLIED> -<!ATTLIST presentation:event xlink:type (simple) #IMPLIED> -<!ATTLIST presentation:event xlink:show (embed) #IMPLIED> -<!ATTLIST presentation:event xlink:actuate (onRequest) #IMPLIED> -<!ATTLIST presentation:event presentation:verb %nonNegativeInteger; #IMPLIED> - -<!-- applets --> -<!ELEMENT draw:applet (draw:thumbnail?, draw:param*, svg:desc?)> -<!ATTLIST draw:applet xlink:href %uriReference; #IMPLIED> -<!ATTLIST draw:applet xlink:type (simple) #IMPLIED> -<!ATTLIST draw:applet xlink:show (embed) #IMPLIED> -<!ATTLIST draw:applet xlink:actuate (onLoad) #IMPLIED> -<!ATTLIST draw:applet draw:code CDATA #REQUIRED> -<!ATTLIST draw:applet draw:object CDATA #IMPLIED> -<!ATTLIST draw:applet draw:archive CDATA #IMPLIED> -<!ATTLIST draw:applet draw:may-script %boolean; "false"> -<!ATTLIST draw:applet draw:name CDATA #IMPLIED> -<!ATTLIST draw:applet %draw-style-name;> -<!ATTLIST draw:applet svg:width %lengthOrPercentage; #IMPLIED> -<!ATTLIST draw:applet svg:height %lengthOrPercentage; #IMPLIED> -<!ATTLIST draw:applet %zindex;> -<!ATTLIST draw:applet draw:layer %layerName; #IMPLIED> -<!ATTLIST draw:applet %draw-position;> -<!ATTLIST draw:applet %draw-end-position; > - -<!-- plugins --> -<!ELEMENT draw:plugin (draw:thumbnail?, draw:param*, svg:desc?)> -<!ATTLIST draw:plugin xlink:href %uriReference; #IMPLIED> -<!ATTLIST draw:plugin xlink:type (simple) #IMPLIED> -<!ATTLIST draw:plugin xlink:show (embed) #IMPLIED> -<!ATTLIST draw:plugin xlink:actuate (onLoad) #IMPLIED> -<!ATTLIST draw:plugin draw:mime-type CDATA #IMPLIED> -<!ATTLIST draw:plugin draw:name CDATA #IMPLIED> -<!ATTLIST draw:plugin %draw-style-name;> -<!ATTLIST draw:plugin svg:width %lengthOrPercentage; #IMPLIED> -<!ATTLIST draw:plugin svg:height %lengthOrPercentage; #IMPLIED> -<!ATTLIST draw:plugin %zindex;> -<!ATTLIST draw:plugin draw:layer %layerName; #IMPLIED> -<!ATTLIST draw:plugin %draw-position;> -<!ATTLIST draw:plugin %draw-end-position; > - -<!-- Paramaters --> -<!ELEMENT draw:param EMPTY> -<!ATTLIST draw:param draw:name CDATA #IMPLIED> -<!ATTLIST draw:param draw:value CDATA #IMPLIED> - -<!-- Floating Frames --> -<!ELEMENT draw:floating-frame (draw:thumbnail?, svg:desc?)> -<!ATTLIST draw:floating-frame xlink:href %uriReference; #IMPLIED> -<!ATTLIST draw:floating-frame xlink:type (simple) #IMPLIED> -<!ATTLIST draw:floating-frame xlink:show (embed) #IMPLIED> -<!ATTLIST draw:floating-frame xlink:actuate (onLoad) #IMPLIED> -<!ATTLIST draw:floating-frame draw:name CDATA #IMPLIED> -<!ATTLIST draw:floating-frame draw:frame-name CDATA #IMPLIED> -<!ATTLIST draw:floating-frame %draw-style-name;> -<!ATTLIST draw:floating-frame svg:width %lengthOrPercentage; #IMPLIED> -<!ATTLIST draw:floating-frame svg:height %lengthOrPercentage; #IMPLIED> -<!ATTLIST draw:floating-frame %zindex;> -<!ATTLIST draw:floating-frame draw:layer %layerName; #IMPLIED> -<!ATTLIST draw:floating-frame %draw-position;> -<!ATTLIST draw:floating-frame %draw-end-position; > - -<!-- Image Maps --> -<!ELEMENT draw:image-map - (draw:area-rectangle|draw:area-circle|draw:area-polygon)*> - -<!ELEMENT draw:area-rectangle (svg:desc?,office:events?)> -<!ATTLIST draw:area-rectangle xlink:href %uriReference; #IMPLIED> -<!ATTLIST draw:area-rectangle xlink:type (simple) #IMPLIED> -<!ATTLIST draw:area-rectangle office:target-frame-name CDATA #IMPLIED> -<!ATTLIST draw:area-rectangle xlink:show (new|replace) #IMPLIED> -<!ATTLIST draw:area-rectangle office:name CDATA #IMPLIED> -<!ATTLIST draw:area-rectangle draw:nohref (nohref) #IMPLIED> -<!ATTLIST draw:area-rectangle svg:x %coordinate; #REQUIRED> -<!ATTLIST draw:area-rectangle svg:y %coordinate; #REQUIRED> -<!ATTLIST draw:area-rectangle svg:width %coordinate; #REQUIRED> -<!ATTLIST draw:area-rectangle svg:height %coordinate; #REQUIRED> - -<!ELEMENT draw:area-circle (svg:desc?,office:events?)> -<!ATTLIST draw:area-circle xlink:href %uriReference; #IMPLIED> -<!ATTLIST draw:area-circle xlink:type (simple) #IMPLIED> -<!ATTLIST draw:area-circle office:target-frame-name CDATA #IMPLIED> -<!ATTLIST draw:area-circle xlink:show (new|replace) #IMPLIED> -<!ATTLIST draw:area-circle office:name CDATA #IMPLIED> -<!ATTLIST draw:area-circle draw:nohref (nohref) #IMPLIED> -<!ATTLIST draw:area-circle svg:cx %coordinate; #REQUIRED> -<!ATTLIST draw:area-circle svg:cy %coordinate; #REQUIRED> -<!ATTLIST draw:area-circle svg:r %coordinate; #REQUIRED> - -<!ELEMENT draw:area-polygon (svg:desc?,office:events?)> -<!ATTLIST draw:area-polygon xlink:href %uriReference; #IMPLIED> -<!ATTLIST draw:area-polygon xlink:type (simple) #IMPLIED> -<!ATTLIST draw:area-polygon office:target-frame-name CDATA #IMPLIED> -<!ATTLIST draw:area-polygon xlink:show (new|replace) #IMPLIED> -<!ATTLIST draw:area-polygon office:name CDATA #IMPLIED> -<!ATTLIST draw:area-polygon draw:nohref (nohref) #IMPLIED> -<!ATTLIST draw:area-polygon svg:x %coordinate; #REQUIRED> -<!ATTLIST draw:area-polygon svg:y %coordinate; #REQUIRED> -<!ATTLIST draw:area-polygon svg:width %coordinate; #REQUIRED> -<!ATTLIST draw:area-polygon svg:height %coordinate; #REQUIRED> -<!ATTLIST draw:area-polygon svg:points %points; #REQUIRED> -<!ATTLIST draw:area-polygon svg:viewBox CDATA #REQUIRED> rmfile ./examples/OpenOffice.org/drawing.mod hunk ./examples/OpenOffice.org/dtypes.mod 1 -<!-- - $Id: dtypes.mod,v 1.1 2003/05/13 13:07:51 malcolm Exp $ - - The Contents of this file are made available subject to the terms of - either of the following licenses - - - GNU Lesser General Public License Version 2.1 - - Sun Industry Standards Source License Version 1.1 - - Sun Microsystems Inc., October, 2000 - - GNU Lesser General Public License Version 2.1 - ============================================= - Copyright 2000 by Sun Microsystems, Inc. - 901 San Antonio Road, Palo Alto, CA 94303, USA - - This library is free software; you can redistribute it and/or - modify it under the terms of the GNU Lesser General Public - License version 2.1, as published by the Free Software Foundation. - - This library is distributed in the hope that it will be useful, - but WITHOUT ANY WARRANTY; without even the implied warranty of - MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU - Lesser General Public License for more details. - - You should have received a copy of the GNU Lesser General Public - License along with this library; if not, write to the Free Software - Foundation, Inc., 59 Temple Place, Suite 330, Boston, - MA 02111-1307 USA - - - Sun Industry Standards Source License Version 1.1 - ================================================= - The contents of this file are subject to the Sun Industry Standards - Source License Version 1.1 (the "License"); You may not use this file - except in compliance with the License. You may obtain a copy of the - License at http://www.openoffice.org/license.html. - - Software provided under this License is provided on an "AS IS" basis, - WITHOUT WARRANTY OF ANY KIND, EITHER EXPRESS OR IMPLIED, INCLUDING, - WITHOUT LIMITATION, WARRANTIES THAT THE SOFTWARE IS FREE OF DEFECTS, - MERCHANTABLE, FIT FOR A PARTICULAR PURPOSE, OR NON-INFRINGING. - See the License for the specific provisions governing your rights and - obligations concerning the Software. - - The Initial Developer of the Original Code is: Sun Microsystems, Inc. - - Copyright: 2000 by Sun Microsystems, Inc. - - All Rights Reserved. - - Contributor(s): _______________________________________ - ---> - -<!-- datatypes corresponding to XML Schema Part 2 W3C Working draft of --> -<!-- 07 April 2000 --> - -<!-- string --> -<!ENTITY % string "CDATA"> -<!ENTITY % cString "#PCDATA"> - -<!-- boolean (values are "true" and "false" --> -<!ENTITY % boolean "CDATA"> - -<!-- integer ( ..., -2, -1, 0, 1, 2, ...) --> -<!ENTITY % integer "CDATA"> - -<!-- non negative integer ( 0, 1, 2, ...) --> -<!ENTITY % nonNegativeInteger "CDATA"> - -<!-- positive integer ( 1, 2, ...) --> -<!ENTITY % positiveInteger "CDATA"> -<!ENTITY % cPositiveInteger "#PCDATA"> - -<!ENTITY % positiveNumberOrDefault "CDATA"> - -<!-- time duration as specified by ISO8601, section 5.5.3.2 --> -<!ENTITY % timeDuration "CDATA"> -<!ENTITY % cTimeDuration "#PCDATA"> - -<!-- time instance as specified by ISO8601, section 5.4 --> -<!ENTITY % timeInstance "CDATA"> -<!ENTITY % cTimeInstance "#PCDATA"> - -<!-- date instance as specified by ISO8601, section 5.2.1.1, extended format--> -<!ENTITY % date "CDATA"> -<!ENTITY % cDate "#PCDATA"> - -<!-- date duration, like timDuration but truncated to full dates --> -<!ENTITY % dateDuration "CDATA"> -<!ENTITY % cDateDuration "#PCDATA"> - -<!-- URI reference --> -<!ENTITY % uriReference "CDATA"> - -<!-- language code as specified by RFC1766 --> -<!ENTITY % language "CDATA"> -<!ENTITY % cLanguage "#PCDATA"> - -<!-- float --> -<!ENTITY % float "CDATA"> - -<!-- Some other common used data types --> - -<!-- a single UNICODE character --> -<!ENTITY % character "CDATA"> - -<!-- a style name --> -<!ENTITY % styleName "CDATA"> - -<!-- a target frame mame --> -<!ENTITY % targetFrameName "CDATA"> - -<!-- a language without a country as specified by ISO639 --> -<!ENTITY % languageOnly "CDATA"> - -<!-- a country as specified by ISO3166 --> -<!ENTITY % country "CDATA"> - -<!-- a color value having the format #rrggbb --> -<!ENTITY % color "CDATA"> -<!-- a color value having the format #rrggbb or "transparent" --> -<!ENTITY % transparentOrColor "CDATA"> - -<!-- a percentage --> -<!ENTITY % percentage "CDATA"> - -<!-- a length (i.e. 1cm or .6inch) --> -<!ENTITY % length "CDATA"> -<!ENTITY % positiveLength "CDATA"> -<!ENTITY % nonNegativeLength "CDATA"> -<!ENTITY % lengthOrNoLimit "CDATA"> - -<!-- a length or a percentage --> -<!ENTITY % lengthOrPercentage "CDATA"> -<!ENTITY % positiveLengthOrPercentage "CDATA"> - -<!-- a pixel length (i.e. 2px) --> -<!ENTITY % nonNegativePixelLength "CDATA"> - -<!-- a float or a percentage --> -<!ENTITY % floatOrPercentage "CDATA"> - -<!-- a text encoding --> -<!ENTITY % textEncoding "CDATA"> - -<!-- cell address and cell range address --> -<!ENTITY % cell-address "CDATA"> -<!ENTITY % cell-range-address "CDATA"> -<!ENTITY % cell-range-address-list "CDATA"> - -<!-- value types --> -<!ENTITY % valueType "(float|time|date|percentage|currency|boolean|string)"> - -<!-- an svg coordinate in different distance formats --> -<!ENTITY % coordinate "CDATA"> - -<!ENTITY % coordinateOrPercentage "CDATA"> - -<!ENTITY % shape "draw:rect|draw:line|draw:polyline|draw:polygon|draw:path| - draw:circle|draw:ellipse|draw:g|draw:page-thumbnail| - draw:text-box|draw:image|draw:object|draw:object-ole| - draw:applet|draw:floating-frame|draw:plugin| - draw:measure|draw:caption|draw:connector|chart:chart| - dr3d:scene|draw:control" > -<!ENTITY % shapes "(%shape;)" > - -<!ENTITY % anchorType "(page|frame|paragraph|char|as-char)"> - -<!ENTITY % control-id "form:id CDATA #REQUIRED"> rmfile ./examples/OpenOffice.org/dtypes.mod hunk ./examples/OpenOffice.org/form.mod 1 -<!-- - $Id: form.mod,v 1.1 2003/05/13 13:07:51 malcolm Exp $ - - The Contents of this file are made available subject to the terms of - either of the following licenses - - - GNU Lesser General Public License Version 2.1 - - Sun Industry Standards Source License Version 1.1 - - Sun Microsystems Inc., October, 2000 - - GNU Lesser General Public License Version 2.1 - ============================================= - Copyright 2000 by Sun Microsystems, Inc. - 901 San Antonio Road, Palo Alto, CA 94303, USA - - This library is free software; you can redistribute it and/or - modify it under the terms of the GNU Lesser General Public - License version 2.1, as published by the Free Software Foundation. - - This library is distributed in the hope that it will be useful, - but WITHOUT ANY WARRANTY; without even the implied warranty of - MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU - Lesser General Public License for more details. - - You should have received a copy of the GNU Lesser General Public - License along with this library; if not, write to the Free Software - Foundation, Inc., 59 Temple Place, Suite 330, Boston, - MA 02111-1307 USA - - - Sun Industry Standards Source License Version 1.1 - ================================================= - The contents of this file are subject to the Sun Industry Standards - Source License Version 1.1 (the "License"); You may not use this file - except in compliance with the License. You may obtain a copy of the - License at http://www.openoffice.org/license.html. - - Software provided under this License is provided on an "AS IS" basis, - WITHOUT WARRANTY OF ANY KIND, EITHER EXPRESS OR IMPLIED, INCLUDING, - WITHOUT LIMITATION, WARRANTIES THAT THE SOFTWARE IS FREE OF DEFECTS, - MERCHANTABLE, FIT FOR A PARTICULAR PURPOSE, OR NON-INFRINGING. - See the License for the specific provisions governing your rights and - obligations concerning the Software. - - The Initial Developer of the Original Code is: Sun Microsystems, Inc. - - Copyright: 2000 by Sun Microsystems, Inc. - - All Rights Reserved. - - Contributor(s): _______________________________________ - ---> - -<!ENTITY % controls "form:text|form:textarea|form:fixed-text|form:file| - form:password|form:formatted-text|form:button|form:image| - form:checkbox|form:radio|form:listbox|form:combobox|form:frame| - form:hidden|form:image-frame|form:grid|form:generic-control"> - -<!ENTITY % name "form:name CDATA #IMPLIED"> -<!ENTITY % service-name "form:service-name CDATA #IMPLIED"> - -<!ENTITY % navigation "(none|current|parent)"> -<!ENTITY % cycles "(records|current|page)"> -<!ENTITY % url "CDATA"> - - -<!ENTITY % types "(submit|reset|push|url)"> -<!ENTITY % button-type "form:button-type %types; 'push'"> -<!ENTITY % current-selected "form:current-selected %boolean; 'false'"> -<!ENTITY % current-value "form:current-value CDATA #IMPLIED"> -<!ENTITY % value "form:value CDATA #IMPLIED"> -<!ENTITY % disabled "form:disabled %boolean; 'false'"> -<!ENTITY % dropdown "form:dropdown %boolean; 'false'"> -<!ENTITY % for "form:for CDATA #IMPLIED"> -<!ENTITY % image-data "form:image-data %url; #IMPLIED"> -<!ENTITY % label "form:label CDATA #IMPLIED"> -<!ENTITY % max-length "form:max-length CDATA #IMPLIED"> -<!ENTITY % printable "form:printable %boolean; 'true'"> -<!ENTITY % readonly "form:readonly %boolean; 'false'"> -<!ENTITY % size "form:size CDATA #IMPLIED"> -<!ENTITY % selected "form:selected %boolean; 'false'"> -<!ENTITY % size "form:size CDATA #IMPLIED"> -<!ENTITY % tab-index "form:tab-index CDATA #IMPLIED"> -<!ENTITY % target-frame "office:target-frame CDATA '_blank'"> -<!ENTITY % target-location "xlink:href %url; #IMPLIED"> -<!ENTITY % tab-stop "form:tab-stop %boolean; 'true'"> -<!ENTITY % title "form:title CDATA #IMPLIED"> -<!ENTITY % default-value "form:default-value CDATA #IMPLIED"> -<!ENTITY % bound-column "form:bound-column CDATA #IMPLIED"> -<!ENTITY % convert-empty "form:convert-empty-to-null %boolean; 'false'"> -<!ENTITY % data-field "form:data-field CDATA #IMPLIED"> -<!ENTITY % list-source "form:list-source CDATA #IMPLIED"> -<!ENTITY % list-source-types "(table|query|sql|sql-pass-through|value-list|table-fields)"> -<!ENTITY % list-source-type "form:list-source-type %list-source-types; #IMPLIED"> -<!ENTITY % column-style-name "form:column-style-name %styleName; #IMPLIED"> - - -<!ELEMENT form:control (%controls;)+> -<!ATTLIST form:control %name; - %service-name; - %control-id;> - -<!ELEMENT form:form (form:properties?, office:events?, (form:control|form:form)*)> -<!ATTLIST form:form %name; %service-name;> -<!ATTLIST form:form xlink:href %url; #IMPLIED> -<!ATTLIST form:form form:enctype CDATA "application/x-www-form-urlencoded"> -<!ATTLIST form:form form:method CDATA "get"> -<!ATTLIST form:form office:target-frame CDATA "_blank"> -<!ATTLIST form:form form:allow-deletes %boolean; "true"> -<!ATTLIST form:form form:allow-inserts %boolean; "true"> -<!ATTLIST form:form form:allow-updates %boolean; "true"> -<!ATTLIST form:form form:apply-filter %boolean; "false"> -<!ATTLIST form:form form:command CDATA #IMPLIED> -<!ATTLIST form:form form:command-type (table|query|command) "command"> -<!ATTLIST form:form form:datasource CDATA #IMPLIED> -<!ATTLIST form:form form:detail-fields CDATA #IMPLIED> -<!ATTLIST form:form form:escape-processing %boolean; "true"> -<!ATTLIST form:form form:filter CDATA #IMPLIED> -<!ATTLIST form:form form:ignore-result %boolean; "false"> -<!ATTLIST form:form form:master-fields CDATA #IMPLIED> -<!ATTLIST form:form form:navigation-mode %navigation; #IMPLIED> -<!ATTLIST form:form form:order CDATA #IMPLIED> -<!ATTLIST form:form form:tab-cycle %cycles; #IMPLIED> - -<!ELEMENT office:forms (form:form*)> -<!ATTLIST office:forms form:automatic-focus %boolean; "false"> -<!ATTLIST office:forms form:apply-design-mode %boolean; "true"> - -<!ELEMENT form:text (form:properties?, office:events?)> -<!ATTLIST form:text %current-value; - %disabled; - %max-length; - %printable; - %readonly; - %tab-index; - %tab-stop; - %title; - %value; - %convert-empty; - %data-field;> - -<!ELEMENT form:textarea (form:properties?, office:events?)> -<!ATTLIST form:textarea %current-value; - %disabled; - %max-length; - %printable; - %readonly; - %tab-index; - %tab-stop; - %title; - %value; - %convert-empty; - %data-field;> - -<!ELEMENT form:password (form:properties?, office:events?)> -<!ATTLIST form:password %disabled; - %max-length; - %printable; - %tab-index; - %tab-stop; - %title; - %value; - %convert-empty;> - -<!ATTLIST form:password form:echo-char CDATA "*"> - -<!ELEMENT form:file (form:properties?, office:events?)> -<!ATTLIST form:file %current-value; - %disabled; - %max-length; - %printable; - %readonly; - %tab-index; - %tab-stop; - %title; - %value;> - -<!ELEMENT form:formatted-text (form:properties?, office:events?)> -<!ATTLIST form:formatted-text %current-value; - %disabled; - %max-length; - %printable; - %readonly; - %tab-index; - %tab-stop; - %title; - %value; - %convert-empty; - %data-field;> -<!ATTLIST form:formatted-text form:max-value CDATA #IMPLIED> -<!ATTLIST form:formatted-text form:min-value CDATA #IMPLIED> -<!ATTLIST form:formatted-text form:validation %boolean; "false"> - -<!ELEMENT form:fixed-text (form:properties?, office:events?)> -<!ATTLIST form:fixed-text %for; - %disabled; - %label; - %printable; - %title;> -<!ATTLIST form:fixed-text form:multi-line %boolean; "false"> - -<!ELEMENT form:combobox (form:properties?, office:events?, form:item*)> -<!ATTLIST form:combobox %current-value; - %disabled; - %dropdown; - %max-length; - %printable; - %readonly; - %size; - %tab-index; - %tab-stop; - %title; - %value; - %convert-empty; - %data-field; - %list-source; - %list-source-type;> -<!ATTLIST form:combobox form:auto-complete %boolean; #IMPLIED> - -<!ELEMENT form:item (#PCDATA)> -<!ATTLIST form:item %label;> - -<!ELEMENT form:listbox (form:properties?, office:events?, form:option*)> -<!ATTLIST form:listbox %disabled; - %dropdown; - %printable; - %size; - %tab-index; - %tab-stop; - %title; - %bound-column; - %data-field; - %list-source; - %list-source-type;> -<!ATTLIST form:listbox form:multiple %boolean; "false"> - -<!ELEMENT form:option (#PCDATA)> -<!ATTLIST form:option %current-selected; - %selected; - %label; - %value;> - -<!ELEMENT form:button (form:properties?, office:events?)> -<!ATTLIST form:button %button-type; - %disabled; - %label; - %image-data; - %printable; - %tab-index; - %tab-stop; - %target-frame; - %target-location; - %title; - %value;> -<!ATTLIST form:button form:default-button %boolean; "false"> - -<!ELEMENT form:image (form:properties?, office:events?)> -<!ATTLIST form:image %button-type; - %disabled; - %image-data; - %printable; - %tab-index; - %tab-stop; - %target-frame; - %target-location; - %title; - %value;> - -<!ELEMENT form:checkbox (form:properties?, office:events?)> -<!ATTLIST form:checkbox %disabled; - %label; - %printable; - %tab-index; - %tab-stop; - %title; - %value; - %data-field;> -<!ENTITY % states "(unchecked|checked|unknown)"> -<!ATTLIST form:checkbox form:current-state %states; #IMPLIED> -<!ATTLIST form:checkbox form:is-tristate %boolean; "false"> -<!ATTLIST form:checkbox form:state %states; "unchecked"> - -<!ELEMENT form:radio (form:properties?, office:events?)> -<!ATTLIST form:radio %current-selected; - %disabled; - %label; - %printable; - %selected; - %tab-index; - %tab-stop; - %title; - %value; - %data-field;> - -<!ELEMENT form:frame (form:properties?, office:events?)> -<!ATTLIST form:frame %disabled; - %for; - %label; - %printable; - %title;> - -<!ELEMENT form:image-frame (form:properties?, office:events?)> -<!ATTLIST form:image-frame %disabled; - %image-data; - %printable; - %readonly; - %title; - %data-field;> - -<!ELEMENT form:hidden (form:properties?, office:events?)> -<!ATTLIST form:hidden %name; - %service-name; - %value;> - -<!ELEMENT form:grid (form:properties?, office:events?, form:column*)> -<!ATTLIST form:grid %disabled; - %printable; - %tab-index; - %tab-stop; - %title;> - -<!ENTITY % column-type "form:text| form:textarea| form:formatted-text|form:checkbox| form:listbox| form:combobox"> -<!ELEMENT form:column (%column-type;)+> -<!ATTLIST form:column %name; - %service-name; - %label; - %column-style-name;> - -<!ELEMENT form:generic-control (form:properties?, office:events?)> - - -<!ELEMENT form:properties (form:property+)> -<!ELEMENT form:property (form:property-value*)> -<!ATTLIST form:property form:property-is-list %boolean; #IMPLIED> -<!ATTLIST form:property form:property-name CDATA #REQUIRED> -<!ATTLIST form:property form:property-type (boolean|short|int|long|double|string) #REQUIRED> -<!ELEMENT form:property-value (#PCDATA)> -<!ATTLIST form:property-value form:property-is-void %boolean; #IMPLIED> rmfile ./examples/OpenOffice.org/form.mod hunk ./examples/OpenOffice.org/meta.mod 1 -<!-- - $Id: meta.mod,v 1.1 2003/05/13 13:07:51 malcolm Exp $ - - The Contents of this file are made available subject to the terms of - either of the following licenses - - - GNU Lesser General Public License Version 2.1 - - Sun Industry Standards Source License Version 1.1 - - Sun Microsystems Inc., October, 2000 - - GNU Lesser General Public License Version 2.1 - ============================================= - Copyright 2000 by Sun Microsystems, Inc. - 901 San Antonio Road, Palo Alto, CA 94303, USA - - This library is free software; you can redistribute it and/or - modify it under the terms of the GNU Lesser General Public - License version 2.1, as published by the Free Software Foundation. - - This library is distributed in the hope that it will be useful, - but WITHOUT ANY WARRANTY; without even the implied warranty of - MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU - Lesser General Public License for more details. - - You should have received a copy of the GNU Lesser General Public - License along with this library; if not, write to the Free Software - Foundation, Inc., 59 Temple Place, Suite 330, Boston, - MA 02111-1307 USA - - - Sun Industry Standards Source License Version 1.1 - ================================================= - The contents of this file are subject to the Sun Industry Standards - Source License Version 1.1 (the "License"); You may not use this file - except in compliance with the License. You may obtain a copy of the - License at http://www.openoffice.org/license.html. - - Software provided under this License is provided on an "AS IS" basis, - WITHOUT WARRANTY OF ANY KIND, EITHER EXPRESS OR IMPLIED, INCLUDING, - WITHOUT LIMITATION, WARRANTIES THAT THE SOFTWARE IS FREE OF DEFECTS, - MERCHANTABLE, FIT FOR A PARTICULAR PURPOSE, OR NON-INFRINGING. - See the License for the specific provisions governing your rights and - obligations concerning the Software. - - The Initial Developer of the Original Code is: Sun Microsystems, Inc. - - Copyright: 2000 by Sun Microsystems, Inc. - - All Rights Reserved. - - Contributor(s): _______________________________________ - ---> - - -<!ELEMENT meta:generator (%cString;)> - -<!ELEMENT dc:title (%cString;)> - -<!ELEMENT dc:description (%cString;)> - -<!ELEMENT dc:subject (%cString;)> - -<!ELEMENT meta:keywords (meta:keyword)*> -<!ELEMENT meta:keyword (%cString;)> - -<!ELEMENT meta:initial-creator (%cString;)> - -<!ELEMENT dc:creator (%cString;)> - -<!ELEMENT meta:printed-by (%cString;)> - -<!ELEMENT meta:creation-date (%cTimeInstance;)> - -<!ELEMENT dc:date (%cTimeInstance;)> - -<!ELEMENT meta:print-date (%cTimeInstance;)> - -<!ELEMENT meta:template EMPTY> -<!ATTLIST meta:template xlink:type (simple) #FIXED "simple"> -<!ATTLIST meta:template xlink:actuate (onRequest) "onRequest"> -<!ATTLIST meta:template xlink:href %uriReference; #REQUIRED> -<!ATTLIST meta:template xlink:title %string; #IMPLIED> -<!ATTLIST meta:template meta:date %timeInstance; #IMPLIED> - -<!ELEMENT meta:auto-reload EMPTY> -<!ATTLIST meta:auto-reload xlink:type (simple) #IMPLIED> -<!ATTLIST meta:auto-reload xlink:show (replace) #IMPLIED> -<!ATTLIST meta:auto-reload xlink:actuate (onLoad) #IMPLIED> -<!ATTLIST meta:auto-reload xlink:href %uriReference; #IMPLIED> -<!ATTLIST meta:auto-reload meta:delay %timeDuration; "P0S"> - -<!ELEMENT meta:hyperlink-behaviour EMPTY> -<!ATTLIST meta:hyperlink-behaviour office:target-frame-name %targetFrameName; #IMPLIED> -<!ATTLIST meta:hyperlink-behaviour xlink:show (new|replace) #IMPLIED> - -<!ELEMENT dc:language (%cLanguage;)> - -<!ELEMENT meta:editing-cycles (%cPositiveInteger;)> - -<!ELEMENT meta:editing-duration (%cTimeDuration;)> - -<!ELEMENT meta:user-defined (%cString;)> -<!ATTLIST meta:user-defined meta:name %string; #REQUIRED> - -<!ELEMENT meta:document-statistic EMPTY> -<!ATTLIST meta:document-statistic meta:page-count %positiveInteger; #IMPLIED - meta:table-count %nonNegativeInteger; #IMPLIED - meta:draw-count %nonNegativeInteger; #IMPLIED - meta:image-count %nonNegativeInteger; #IMPLIED - meta:ole-object-count %nonNegativeInteger; #IMPLIED - meta:paragraph-count %nonNegativeInteger; #IMPLIED - meta:word-count %nonNegativeInteger; #IMPLIED - meta:character-count %nonNegativeInteger; #IMPLIED - meta:row-count %nonNegativeInteger; #IMPLIED - meta:cell-count %nonNegativeInteger; #IMPLIED - meta:object-count %positiveInteger; #IMPLIED> rmfile ./examples/OpenOffice.org/meta.mod hunk ./examples/OpenOffice.org/nmspace.mod 1 -<!-- - $Id: nmspace.mod,v 1.1 2003/05/13 13:07:51 malcolm Exp $ - - The Contents of this file are made available subject to the terms of - either of the following licenses - - - GNU Lesser General Public License Version 2.1 - - Sun Industry Standards Source License Version 1.1 - - Sun Microsystems Inc., October, 2000 - - GNU Lesser General Public License Version 2.1 - ============================================= - Copyright 2000 by Sun Microsystems, Inc. - 901 San Antonio Road, Palo Alto, CA 94303, USA - - This library is free software; you can redistribute it and/or - modify it under the terms of the GNU Lesser General Public - License version 2.1, as published by the Free Software Foundation. - - This library is distributed in the hope that it will be useful, - but WITHOUT ANY WARRANTY; without even the implied warranty of - MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU - Lesser General Public License for more details. - - You should have received a copy of the GNU Lesser General Public - License along with this library; if not, write to the Free Software - Foundation, Inc., 59 Temple Place, Suite 330, Boston, - MA 02111-1307 USA - - - Sun Industry Standards Source License Version 1.1 - ================================================= - The contents of this file are subject to the Sun Industry Standards - Source License Version 1.1 (the "License"); You may not use this file - except in compliance with the License. You may obtain a copy of the - License at http://www.openoffice.org/license.html. - - Software provided under this License is provided on an "AS IS" basis, - WITHOUT WARRANTY OF ANY KIND, EITHER EXPRESS OR IMPLIED, INCLUDING, - WITHOUT LIMITATION, WARRANTIES THAT THE SOFTWARE IS FREE OF DEFECTS, - MERCHANTABLE, FIT FOR A PARTICULAR PURPOSE, OR NON-INFRINGING. - See the License for the specific provisions governing your rights and - obligations concerning the Software. - - The Initial Developer of the Original Code is: Sun Microsystems, Inc. - - Copyright: 2000 by Sun Microsystems, Inc. - - All Rights Reserved. - - Contributor(s): _______________________________________ - ---> - -<!ENTITY nFO "http://www.w3.org/1999/XSL/Format"> -<!ENTITY nXLink "http://www.w3.org/1999/xlink"> -<!ENTITY nSVG "http://www.w3.org/2000/svg"> -<!ENTITY nMath "http://www.w3.org/1998/Math/MathML"> - -<!-- StarOffice namespace names and prefixes --> - -<!ENTITY nOpenOffice "http://openoffice.org/2000"> -<!ENTITY nOpenOffice2001 "http://openoffice.org/2001"> - -<!ENTITY nOffice "&nOpenOffice;/office"> -<!ENTITY nStyle "&nOpenOffice;/style"> -<!ENTITY nText "&nOpenOffice;/text"> -<!ENTITY nTable "&nOpenOffice;/table"> -<!ENTITY nMeta "&nOpenOffice;/meta"> -<!ENTITY nScript "&nOpenOffice;/script"> -<!ENTITY nDraw "&nOpenOffice;/drawing"> -<!ENTITY nChart "&nOpenOffice;/chart"> -<!ENTITY nNumber "&nOpenOffice;/datastyle"> -<!ENTITY nDr3D "&nOpenOffice;/dr3d"> -<!ENTITY nForm "&nOpenOffice;/form"> -<!ENTITY nConfig "&nOpenOffice2001;/config"> - -<!-- dublin core namespace name and prefic --> -<!ENTITY nDC "http://purl.org/dc/elements/1.1/"> rmfile ./examples/OpenOffice.org/nmspace.mod hunk ./examples/OpenOffice.org/office.dtd 1 -<?xml version="1.0" encoding="UTF-8"?> -<!-- - $Id: office.dtd,v 1.1 2003/05/13 13:07:51 malcolm Exp $ - - The Contents of this file are made available subject to the terms of - either of the following licenses - - - GNU Lesser General Public License Version 2.1 - - Sun Industry Standards Source License Version 1.1 - - Sun Microsystems Inc., October, 2000 - - GNU Lesser General Public License Version 2.1 - ============================================= - Copyright 2000 by Sun Microsystems, Inc. - 901 San Antonio Road, Palo Alto, CA 94303, USA - - This library is free software; you can redistribute it and/or - modify it under the terms of the GNU Lesser General Public - License version 2.1, as published by the Free Software Foundation. - - This library is distributed in the hope that it will be useful, - but WITHOUT ANY WARRANTY; without even the implied warranty of - MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU - Lesser General Public License for more details. - - You should have received a copy of the GNU Lesser General Public - License along with this library; if not, write to the Free Software - Foundation, Inc., 59 Temple Place, Suite 330, Boston, - MA 02111-1307 USA - - - Sun Industry Standards Source License Version 1.1 - ================================================= - The contents of this file are subject to the Sun Industry Standards - Source License Version 1.1 (the "License"); You may not use this file - except in compliance with the License. You may obtain a copy of the - License at http://www.openoffice.org/license.html. - - Software provided under this License is provided on an "AS IS" basis, - WITHOUT WARRANTY OF ANY KIND, EITHER EXPRESS OR IMPLIED, INCLUDING, - WITHOUT LIMITATION, WARRANTIES THAT THE SOFTWARE IS FREE OF DEFECTS, - MERCHANTABLE, FIT FOR A PARTICULAR PURPOSE, OR NON-INFRINGING. - See the License for the specific provisions governing your rights and - obligations concerning the Software. - - The Initial Developer of the Original Code is: Sun Microsystems, Inc. - - Copyright: 2000 by Sun Microsystems, Inc. - - All Rights Reserved. - - Contributor(s): _______________________________________ - ---> -<!ENTITY % dtypes-mod SYSTEM "dtypes.mod"> -%dtypes-mod; -<!ENTITY % nmspace-mod SYSTEM "nmspace.mod"> -%nmspace-mod; -<!ENTITY % defs-mod SYSTEM "defs.mod"> -%defs-mod; -<!ENTITY % office-mod SYSTEM "office.mod"> -%office-mod; -<!ENTITY % style-mod SYSTEM "style.mod"> -%style-mod; -<!ENTITY % meta-mod SYSTEM "meta.mod"> -%meta-mod; -<!ENTITY % script-mod SYSTEM "script.mod"> -%script-mod; -<!ENTITY % drawing-mod SYSTEM "drawing.mod"> -%drawing-mod; -<!ENTITY % text-mod SYSTEM "text.mod"> -%text-mod; -<!ENTITY % table-mod SYSTEM "table.mod"> -%table-mod; -<!ENTITY % chart-mod SYSTEM "chart.mod"> -%chart-mod; -<!ENTITY % datastyl-mod SYSTEM "datastyl.mod"> -%datastyl-mod; -<!ENTITY % form-mod SYSTEM "form.mod"> -%form-mod; -<!ENTITY % settings-mod SYSTEM "settings.mod"> -%settings-mod; rmfile ./examples/OpenOffice.org/office.dtd hunk ./examples/OpenOffice.org/office.mod 1 -<!-- - $Id: office.mod,v 1.1 2003/05/13 13:07:51 malcolm Exp $ - - The Contents of this file are made available subject to the terms of - either of the following licenses - - - GNU Lesser General Public License Version 2.1 - - Sun Industry Standards Source License Version 1.1 - - Sun Microsystems Inc., October, 2000 - - GNU Lesser General Public License Version 2.1 - ============================================= - Copyright 2000 by Sun Microsystems, Inc. - 901 San Antonio Road, Palo Alto, CA 94303, USA - - This library is free software; you can redistribute it and/or - modify it under the terms of the GNU Lesser General Public - License version 2.1, as published by the Free Software Foundation. - - This library is distributed in the hope that it will be useful, - but WITHOUT ANY WARRANTY; without even the implied warranty of - MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU - Lesser General Public License for more details. - - You should have received a copy of the GNU Lesser General Public - License along with this library; if not, write to the Free Software - Foundation, Inc., 59 Temple Place, Suite 330, Boston, - MA 02111-1307 USA - - - Sun Industry Standards Source License Version 1.1 - ================================================= - The contents of this file are subject to the Sun Industry Standards - Source License Version 1.1 (the "License"); You may not use this file - except in compliance with the License. You may obtain a copy of the - License at http://www.openoffice.org/license.html. - - Software provided under this License is provided on an "AS IS" basis, - WITHOUT WARRANTY OF ANY KIND, EITHER EXPRESS OR IMPLIED, INCLUDING, - WITHOUT LIMITATION, WARRANTIES THAT THE SOFTWARE IS FREE OF DEFECTS, - MERCHANTABLE, FIT FOR A PARTICULAR PURPOSE, OR NON-INFRINGING. - See the License for the specific provisions governing your rights and - obligations concerning the Software. - - The Initial Developer of the Original Code is: Sun Microsystems, Inc. - - Copyright: 2000 by Sun Microsystems, Inc. - - All Rights Reserved. - - Contributor(s): _______________________________________ - ---> - -<!ELEMENT office:document ( office:meta?, - office:settings?, - office:script?, - office:font-decls?, - office:styles?, - office:automatic-styles?, - office:master-styles?, - office:body ) > - -<!ATTLIST office:document xmlns:office CDATA #FIXED "&nOffice;"> -<!ATTLIST office:document xmlns:meta CDATA #FIXED "&nMeta;"> -<!ATTLIST office:document xmlns:script CDATA #FIXED "&nScript;"> -<!ATTLIST office:document xmlns:style CDATA #FIXED "&nStyle;"> -<!ATTLIST office:document xmlns:text CDATA #FIXED "&nText;"> -<!ATTLIST office:document xmlns:table CDATA #FIXED "&nTable;"> -<!ATTLIST office:document xmlns:draw CDATA #FIXED "&nDraw;"> -<!ATTLIST office:document xmlns:chart CDATA #FIXED "&nChart;"> -<!ATTLIST office:document xmlns:number CDATA #FIXED "&nNumber;"> -<!ATTLIST office:document xmlns:fo CDATA #FIXED "&nFO;"> -<!ATTLIST office:document xmlns:xlink CDATA #FIXED "&nXLink;"> -<!ATTLIST office:document xmlns:svg CDATA #FIXED "&nSVG;"> -<!ATTLIST office:document xmlns:dc CDATA #FIXED "&nDC;"> -<!ATTLIST office:document xmlns:dr3d CDATA #FIXED "&nDr3D;"> -<!ATTLIST office:document xmlns:math CDATA #FIXED "&nMath;"> -<!ATTLIST office:document xmlns:form CDATA #FIXED "&nForm;"> -<!ATTLIST office:document xmlns:config CDATA #FIXED "&nConfig;"> - -<!ATTLIST office:document office:class - (text|text-global| - drawing|presentation| - spreadsheet|chart) #REQUIRED> - -<!ATTLIST office:document office:version %string; #IMPLIED> - -<!-- document-styles --> -<!ELEMENT office:document-styles ( - office:font-decls?, - office:styles?, - office:automatic-styles?, - office:master-styles? ) > - -<!ATTLIST office:document-styles xmlns:office CDATA #FIXED "&nOffice;"> -<!ATTLIST office:document-styles xmlns:meta CDATA #FIXED "&nMeta;"> -<!ATTLIST office:document-styles xmlns:script CDATA #FIXED "&nScript;"> -<!ATTLIST office:document-styles xmlns:style CDATA #FIXED "&nStyle;"> -<!ATTLIST office:document-styles xmlns:text CDATA #FIXED "&nText;"> -<!ATTLIST office:document-styles xmlns:table CDATA #FIXED "&nTable;"> -<!ATTLIST office:document-styles xmlns:draw CDATA #FIXED "&nDraw;"> -<!ATTLIST office:document-styles xmlns:chart CDATA #FIXED "&nChart;"> -<!ATTLIST office:document-styles xmlns:number CDATA #FIXED "&nNumber;"> -<!ATTLIST office:document-styles xmlns:fo CDATA #FIXED "&nFO;"> -<!ATTLIST office:document-styles xmlns:xlink CDATA #FIXED "&nXLink;"> -<!ATTLIST office:document-styles xmlns:svg CDATA #FIXED "&nSVG;"> -<!ATTLIST office:document-styles xmlns:dc CDATA #FIXED "&nDC;"> -<!ATTLIST office:document-styles xmlns:dr3d CDATA #FIXED "&nDr3D;"> -<!ATTLIST office:document-styles xmlns:math CDATA #FIXED "&nMath;"> -<!ATTLIST office:document-styles xmlns:form CDATA #FIXED "&nForm;"> - -<!ATTLIST office:document-styles office:version %string; #IMPLIED> - -<!-- document-content --> - -<!ELEMENT office:document-content ( - office:script?, - office:font-decls?, - office:automatic-styles?, - office:body ) > - -<!ATTLIST office:document-content xmlns:office CDATA #FIXED "&nOffice;"> -<!ATTLIST office:document-content xmlns:meta CDATA #FIXED "&nMeta;"> -<!ATTLIST office:document-content xmlns:script CDATA #FIXED "&nScript;"> -<!ATTLIST office:document-content xmlns:style CDATA #FIXED "&nStyle;"> -<!ATTLIST office:document-content xmlns:text CDATA #FIXED "&nText;"> -<!ATTLIST office:document-content xmlns:table CDATA #FIXED "&nTable;"> -<!ATTLIST office:document-content xmlns:draw CDATA #FIXED "&nDraw;"> -<!ATTLIST office:document-content xmlns:chart CDATA #FIXED "&nChart;"> -<!ATTLIST office:document-content xmlns:number CDATA #FIXED "&nNumber;"> -<!ATTLIST office:document-content xmlns:fo CDATA #FIXED "&nFO;"> -<!ATTLIST office:document-content xmlns:xlink CDATA #FIXED "&nXLink;"> -<!ATTLIST office:document-content xmlns:svg CDATA #FIXED "&nSVG;"> -<!ATTLIST office:document-content xmlns:dc CDATA #FIXED "&nDC;"> -<!ATTLIST office:document-content xmlns:dr3d CDATA #FIXED "&nDr3D;"> -<!ATTLIST office:document-content xmlns:math CDATA #FIXED "&nMath;"> -<!ATTLIST office:document-content xmlns:form CDATA #FIXED "&nForm;"> - -<!ATTLIST office:document-content office:class - (text|text-global| - drawing|presentation| - spreadsheet|chart) #REQUIRED> - -<!ATTLIST office:document-content office:version %string; #IMPLIED> - -<!-- document-content --> - -<!ELEMENT office:document-meta ( office:meta? ) > - -<!ATTLIST office:document-meta xmlns:office CDATA #FIXED "&nOffice;"> -<!ATTLIST office:document-meta xmlns:meta CDATA #FIXED "&nMeta;"> -<!ATTLIST office:document-meta xmlns:script CDATA #FIXED "&nScript;"> -<!ATTLIST office:document-meta xmlns:style CDATA #FIXED "&nStyle;"> -<!ATTLIST office:document-meta xmlns:text CDATA #FIXED "&nText;"> -<!ATTLIST office:document-meta xmlns:table CDATA #FIXED "&nTable;"> -<!ATTLIST office:document-meta xmlns:draw CDATA #FIXED "&nDraw;"> -<!ATTLIST office:document-meta xmlns:chart CDATA #FIXED "&nChart;"> -<!ATTLIST office:document-meta xmlns:number CDATA #FIXED "&nNumber;"> -<!ATTLIST office:document-meta xmlns:fo CDATA #FIXED "&nFO;"> -<!ATTLIST office:document-meta xmlns:xlink CDATA #FIXED "&nXLink;"> -<!ATTLIST office:document-meta xmlns:svg CDATA #FIXED "&nSVG;"> -<!ATTLIST office:document-meta xmlns:dc CDATA #FIXED "&nDC;"> -<!ATTLIST office:document-meta xmlns:dr3d CDATA #FIXED "&nDr3D;"> -<!ATTLIST office:document-meta xmlns:math CDATA #FIXED "&nMath;"> -<!ATTLIST office:document-meta xmlns:form CDATA #FIXED "&nForm;"> - -<!ATTLIST office:document-meta office:version %string; #IMPLIED> - -<!ELEMENT office:document-settings (office:settings) > -<!ATTLIST office:document-settings xmlns:office CDATA #FIXED "&nOffice;"> -<!ATTLIST office:document-settings xmlns:xlink CDATA #FIXED "&nXLink;"> -<!ATTLIST office:document-settings xmlns:config CDATA #FIXED "&nConfig;"> - -<!ATTLIST office:document-settings office:version %string; #IMPLIED> - -<!ENTITY % meta "(meta:generator?, - dc:title?, - dc:description?, - dc:subject?, - meta:initial-creator?, - meta:creation-date?, - dc:creator?, - dc:date?, - meta:printed-by?, - meta:print-date?, - meta:keywords?, - dc:language?, - meta:editing-cycles?, - meta:editing-duration?, - meta:hyperlink-behaviour?, - meta:auto-reload?, - meta:template?, - meta:user-defined*, - meta:document-statistic?)"> -<!ELEMENT office:meta %meta;> - -<!ENTITY % script "(script:library-embedded | - script:library-linked)*,office:events?"> -<!ELEMENT office:script (%script;)> - -<!ELEMENT office:font-decls (style:font-decl)*> - -<!ENTITY % styles "(style:default-style|style:style|text:list-style| - number:number-style|number:currency-style|number:percentage-style| - number:date-style|number:time-style|number:boolean-style| - number:text-style| - draw:gradient|draw:hatch|draw:fill-image|draw:marker|draw:stroke-dash| - style:presentation-page-layout|draw:transparency)"> - -<!-- Validity constraint: The elements - text:outline-style, - text:footnotes-configuration, - text:endnotes-configuration, - text:bibliography-configuration and - text:linenumbering-configuration - may appear only once! - Unfortunatetly, this constraint cannot be easily specified in the DTD. ---> -<!ELEMENT office:styles (%styles;|text:outline-style| - text:footnotes-configuration|text:endnotes-configuration| - text:bibliography-configuration|text:linenumbering-configuration)*> - -<!ELEMENT office:automatic-styles (%styles;|style:page-master)*> - -<!ELEMENT office:master-styles (draw:layer-set?,style:handout-master?,style:master-page*) > - - -<!ENTITY % body "(office:forms?,(text:tracked-changes|table:tracked-changes)?,%text-decls;,table:calculation-settings?,table:content-validations?,table:label-ranges?, - (text:h|text:p|text:ordered-list| - text:unordered-list|table:table|draw:page| - draw:a|%shape;|text:section|text:table-of-content| - text:illustration-index|text:table-index|text:object-index| - text:user-index|text:alphabetical-index|text:bibliography| - %change-marks;)*, - table:named-expressions?, - table:database-ranges?,table:data-pilot-tables?, - table:consolidation?, - table:dde-links?, - presentation:settings?)"> -<!ELEMENT office:body %body;> -<!ATTLIST office:body table:structure-protected %boolean; "false" - table:protection-key CDATA #IMPLIED> - -<!ELEMENT office:events (script:event|presentation:event)*> - -<!-- DDE source: for text sections and tables --> -<!ELEMENT office:dde-source EMPTY> -<!ATTLIST office:dde-source office:dde-application CDATA #IMPLIED> -<!ATTLIST office:dde-source office:dde-topic CDATA #IMPLIED> -<!ATTLIST office:dde-source office:dde-item CDATA #IMPLIED> -<!ATTLIST office:dde-source office:automatic-update %boolean; "false"> -<!ATTLIST office:dde-source office:name CDATA #IMPLIED> -<!ATTLIST office:dde-source table:conversion-mode (into-default-style-data-style|into-english-number|let-text) "into-default-style-data-style" > - -<!-- annotations --> -<!-- limitation: in the current implementation, only plain text inside of - paragraphs is supported --> -<!ELEMENT office:annotation (text:p)*> -<!ATTLIST office:annotation office:author %string; #IMPLIED> -<!ATTLIST office:annotation office:create-date %date; #IMPLIED> -<!ATTLIST office:annotation office:create-date-string %string; #IMPLIED> -<!ATTLIST office:annotation office:display %boolean; "false"> - -<!ELEMENT office:change-info (text:p)*> -<!ATTLIST office:change-info office:chg-author %string; #REQUIRED> -<!ATTLIST office:change-info office:chg-date-time %timeInstance; #REQUIRED> - -<!ELEMENT office:binary-data (#PCDATA)> rmfile ./examples/OpenOffice.org/office.mod hunk ./examples/OpenOffice.org/office2.dtd 1 -<?xml version="1.0" encoding="UTF-8"?> -<!-- - $Id: office2.dtd,v 1.1 2003/05/13 13:07:51 malcolm Exp $ - - The Contents of this file are made available subject to the terms of - either of the following licenses - - - GNU Lesser General Public License Version 2.1 - - Sun Industry Standards Source License Version 1.1 - - Sun Microsystems Inc., October, 2000 - - GNU Lesser General Public License Version 2.1 - ============================================= - Copyright 2000 by Sun Microsystems, Inc. - 901 San Antonio Road, Palo Alto, CA 94303, USA - - This library is free software; you can redistribute it and/or - modify it under the terms of the GNU Lesser General Public - License version 2.1, as published by the Free Software Foundation. - - This library is distributed in the hope that it will be useful, - but WITHOUT ANY WARRANTY; without even the implied warranty of - MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU - Lesser General Public License for more details. - - You should have received a copy of the GNU Lesser General Public - License along with this library; if not, write to the Free Software - Foundation, Inc., 59 Temple Place, Suite 330, Boston, - MA 02111-1307 USA - - - Sun Industry Standards Source License Version 1.1 - ================================================= - The contents of this file are subject to the Sun Industry Standards - Source License Version 1.1 (the "License"); You may not use this file - except in compliance with the License. You may obtain a copy of the - License at http://www.openoffice.org/license.html. - - Software provided under this License is provided on an "AS IS" basis, - WITHOUT WARRANTY OF ANY KIND, EITHER EXPRESS OR IMPLIED, INCLUDING, - WITHOUT LIMITATION, WARRANTIES THAT THE SOFTWARE IS FREE OF DEFECTS, - MERCHANTABLE, FIT FOR A PARTICULAR PURPOSE, OR NON-INFRINGING. - See the License for the specific provisions governing your rights and - obligations concerning the Software. - - The Initial Developer of the Original Code is: Sun Microsystems, Inc. - - Copyright: 2000 by Sun Microsystems, Inc. - - All Rights Reserved. - - Contributor(s): _______________________________________ - ---> - -<!-- string --> -<!ENTITY % string "CDATA"> -<!ENTITY % cString "#PCDATA"> - -<!-- boolean (values are "true" and "false" --> -<!ENTITY % boolean "CDATA"> - -<!-- integer ( ..., -2, -1, 0, 1, 2, ...) --> -<!ENTITY % integer "CDATA"> - -<!-- non negative integer ( 0, 1, 2, ...) --> -<!ENTITY % nonNegativeInteger "CDATA"> - -<!-- positive integer ( 1, 2, ...) --> -<!ENTITY % positiveInteger "CDATA"> -<!ENTITY % cPositiveInteger "#PCDATA"> - -<!ENTITY % positiveNumberOrDefault "CDATA"> - -<!-- time duration as specified by ISO8601, section 5.5.3.2 --> -<!ENTITY % timeDuration "CDATA"> -<!ENTITY % cTimeDuration "#PCDATA"> - -<!-- time instance as specified by ISO8601, section 5.4 --> -<!ENTITY % timeInstance "CDATA"> -<!ENTITY % cTimeInstance "#PCDATA"> - -<!-- date instance as specified by ISO8601, section 5.2.1.1, extended format--> -<!ENTITY % date "CDATA"> -<!ENTITY % cDate "#PCDATA"> - -<!-- date duration, like timDuration but truncated to full dates --> -<!ENTITY % dateDuration "CDATA"> -<!ENTITY % cDateDuration "#PCDATA"> - -<!-- URI reference --> -<!ENTITY % uriReference "CDATA"> - -<!-- language code as specified by RFC1766 --> -<!ENTITY % language "CDATA"> -<!ENTITY % cLanguage "#PCDATA"> - -<!-- float --> -<!ENTITY % float "CDATA"> - -<!-- Some other common used data types --> - -<!-- a single UNICODE character --> -<!ENTITY % character "CDATA"> - -<!-- a style name --> -<!ENTITY % styleName "CDATA"> - -<!-- a target frame mame --> -<!ENTITY % targetFrameName "CDATA"> - -<!-- a language without a country as specified by ISO639 --> -<!ENTITY % languageOnly "CDATA"> - -<!-- a country as specified by ISO3166 --> -<!ENTITY % country "CDATA"> - -<!-- a color value having the format #rrggbb --> -<!ENTITY % color "CDATA"> -<!-- a color value having the format #rrggbb or "transparent" --> -<!ENTITY % transparentOrColor "CDATA"> - -<!-- a percentage --> -<!ENTITY % percentage "CDATA"> - -<!-- a length (i.e. 1cm or .6inch) --> -<!ENTITY % length "CDATA"> -<!ENTITY % positiveLength "CDATA"> -<!ENTITY % nonNegativeLength "CDATA"> -<!ENTITY % lengthOrNoLimit "CDATA"> - -<!-- a length or a percentage --> -<!ENTITY % lengthOrPercentage "CDATA"> -<!ENTITY % positiveLengthOrPercentage "CDATA"> - -<!-- a pixel length (i.e. 2px) --> -<!ENTITY % nonNegativePixelLength "CDATA"> - -<!-- a float or a percentage --> -<!ENTITY % floatOrPercentage "CDATA"> - -<!-- a text encoding --> -<!ENTITY % textEncoding "CDATA"> - -<!-- cell address and cell range address --> -<!ENTITY % cell-address "CDATA"> -<!ENTITY % cell-range-address "CDATA"> -<!ENTITY % cell-range-address-list "CDATA"> - -<!-- value types --> -<!ENTITY % valueType "(float|time|date|percentage|currency|boolean|string)"> - -<!-- an svg coordinate in different distance formats --> -<!ENTITY % coordinate "CDATA"> - -<!ENTITY % coordinateOrPercentage "CDATA"> - -<!ENTITY % shape "draw:rect|draw:line|draw:polyline|draw:polygon|draw:path| - draw:circle|draw:ellipse|draw:g|draw:page-thumbnail| - draw:text-box|draw:image|draw:object|draw:object-ole| - draw:applet|draw:floating-frame|draw:plugin| - draw:measure|draw:caption|draw:connector|chart:chart| - dr3d:scene|draw:control" > -<!ENTITY % shapes "(%shape;)" > - -<!ENTITY % anchorType "(page|frame|paragraph|char|as-char)"> - -<!ENTITY % control-id "form:id CDATA #REQUIRED"> - -<!ENTITY nFO "http://www.w3.org/1999/XSL/Format"> -<!ENTITY nXLink "http://www.w3.org/1999/xlink"> -<!ENTITY nSVG "http://www.w3.org/2000/svg"> -<!ENTITY nMath "http://www.w3.org/1998/Math/MathML"> - -<!-- StarOffice namespace names and prefixes --> - -<!ENTITY nOpenOffice "http://openoffice.org/2000"> -<!ENTITY nOpenOffice2001 "http://openoffice.org/2001"> - -<!ENTITY nOffice "&nOpenOffice;/office"> -<!ENTITY nStyle "&nOpenOffice;/style"> -<!ENTITY nText "&nOpenOffice;/text"> -<!ENTITY nTable "&nOpenOffice;/table"> -<!ENTITY nMeta "&nOpenOffice;/meta"> -<!ENTITY nScript "&nOpenOffice;/script"> -<!ENTITY nDraw "&nOpenOffice;/drawing"> -<!ENTITY nChart "&nOpenOffice;/chart"> -<!ENTITY nNumber "&nOpenOffice;/datastyle"> -<!ENTITY nDr3D "&nOpenOffice;/dr3d"> -<!ENTITY nForm "&nOpenOffice;/form"> -<!ENTITY nConfig "&nOpenOffice2001;/config"> - -<!-- dublin core namespace name and prefic --> -<!ENTITY nDC "http://purl.org/dc/elements/1.1/"> - -<!-- text marks for tracking changes; usually used inside of paragraphs --> -<!ENTITY % change-marks "text:change | text:change-start | text:change-end"> - -<!-- (optional) text declarations; used before the first paragraph --> -<!ENTITY % text-decls "text:variable-decls?, text:sequence-decls?, - text:user-field-decls?, text:dde-connection-decls?, - text:alphabetical-index-auto-mark-file?" > - -<!-- define the types of text which may occur inside of sections --> -<!ENTITY % sectionText "(text:h|text:p|text:ordered-list| - text:unordered-list|table:table|text:section| - text:table-of-content|text:illustration-index| - text:table-index|text:object-index|text:user-index| - text:alphabetical-index|text:bibliography| - text:index-title|%change-marks;)*"> - -<!ENTITY % headerText "(%text-decls;, (text:h|text:p|text:ordered-list| - text:unordered-list|table:table|text:section| - text:table-of-content|text:illustration-index| - text:table-index|text:object-index|text:user-index| - text:alphabetical-index|text:bibliography| - text:index-title|%change-marks;)* )"> - - -<!ELEMENT office:document ( office:meta?, - office:settings?, - office:script?, - office:font-decls?, - office:styles?, - office:automatic-styles?, - office:master-styles?, - office:body ) > - -<!ATTLIST office:document xmlns:office CDATA #FIXED "&nOffice;"> -<!ATTLIST office:document xmlns:meta CDATA #FIXED "&nMeta;"> -<!ATTLIST office:document xmlns:script CDATA #FIXED "&nScript;"> -<!ATTLIST office:document xmlns:style CDATA #FIXED "&nStyle;"> -<!ATTLIST office:document xmlns:text CDATA #FIXED "&nText;"> -<!ATTLIST office:document xmlns:table CDATA #FIXED "&nTable;"> -<!ATTLIST office:document xmlns:draw CDATA #FIXED "&nDraw;"> -<!ATTLIST office:document xmlns:chart CDATA #FIXED "&nChart;"> -<!ATTLIST office:document xmlns:number CDATA #FIXED "&nNumber;"> -<!ATTLIST office:document xmlns:fo CDATA #FIXED "&nFO;"> -<!ATTLIST office:document xmlns:xlink CDATA #FIXED "&nXLink;"> -<!ATTLIST office:document xmlns:svg CDATA #FIXED "&nSVG;"> -<!ATTLIST office:document xmlns:dc CDATA #FIXED "&nDC;"> -<!ATTLIST office:document xmlns:dr3d CDATA #FIXED "&nDr3D;"> -<!ATTLIST office:document xmlns:math CDATA #FIXED "&nMath;"> -<!ATTLIST office:document xmlns:form CDATA #FIXED "&nForm;"> - -<!ATTLIST office:document office:class - (text|text-global| - drawing|presentation| - spreadsheet|chart) #REQUIRED> - -<!ATTLIST office:document office:version %string; #IMPLIED> - -<!-- document-styles --> -<!ELEMENT office:document-styles ( - office:font-decls?, - office:styles?, - office:automatic-styles?, - office:master-styles? ) > - -<!ATTLIST office:document-styles xmlns:office CDATA #FIXED "&nOffice;"> -<!ATTLIST office:document-styles xmlns:meta CDATA #FIXED "&nMeta;"> -<!ATTLIST office:document-styles xmlns:script CDATA #FIXED "&nScript;"> -<!ATTLIST office:document-styles xmlns:style CDATA #FIXED "&nStyle;"> -<!ATTLIST office:document-styles xmlns:text CDATA #FIXED "&nText;"> -<!ATTLIST office:document-styles xmlns:table CDATA #FIXED "&nTable;"> -<!ATTLIST office:document-styles xmlns:draw CDATA #FIXED "&nDraw;"> -<!ATTLIST office:document-styles xmlns:chart CDATA #FIXED "&nChart;"> -<!ATTLIST office:document-styles xmlns:number CDATA #FIXED "&nNumber;"> -<!ATTLIST office:document-styles xmlns:fo CDATA #FIXED "&nFO;"> -<!ATTLIST office:document-styles xmlns:xlink CDATA #FIXED "&nXLink;"> -<!ATTLIST office:document-styles xmlns:svg CDATA #FIXED "&nSVG;"> -<!ATTLIST office:document-styles xmlns:dc CDATA #FIXED "&nDC;"> -<!ATTLIST office:document-styles xmlns:dr3d CDATA #FIXED "&nDr3D;"> -<!ATTLIST office:document-styles xmlns:math CDATA #FIXED "&nMath;"> -<!ATTLIST office:document-styles xmlns:form CDATA #FIXED "&nForm;"> - -<!ATTLIST office:document-styles office:version %string; #IMPLIED> - -<!-- document-content --> - -<!ELEMENT office:document-content ( - office:script?, - office:font-decls?, - office:automatic-styles?, - office:body ) > - -<!ATTLIST office:document-content xmlns:office CDATA #FIXED "&nOffice;"> -<!ATTLIST office:document-content xmlns:meta CDATA #FIXED "&nMeta;"> -<!ATTLIST office:document-content xmlns:script CDATA #FIXED "&nScript;"> -<!ATTLIST office:document-content xmlns:style CDATA #FIXED "&nStyle;"> -<!ATTLIST office:document-content xmlns:text CDATA #FIXED "&nText;"> -<!ATTLIST office:document-content xmlns:table CDATA #FIXED "&nTable;"> -<!ATTLIST office:document-content xmlns:draw CDATA #FIXED "&nDraw;"> -<!ATTLIST office:document-content xmlns:chart CDATA #FIXED "&nChart;"> -<!ATTLIST office:document-content xmlns:number CDATA #FIXED "&nNumber;"> -<!ATTLIST office:document-content xmlns:fo CDATA #FIXED "&nFO;"> -<!ATTLIST office:document-content xmlns:xlink CDATA #FIXED "&nXLink;"> -<!ATTLIST office:document-content xmlns:svg CDATA #FIXED "&nSVG;"> -<!ATTLIST office:document-content xmlns:dc CDATA #FIXED "&nDC;"> -<!ATTLIST office:document-content xmlns:dr3d CDATA #FIXED "&nDr3D;"> -<!ATTLIST office:document-content xmlns:math CDATA #FIXED "&nMath;"> -<!ATTLIST office:document-content xmlns:form CDATA #FIXED "&nForm;"> - -<!ATTLIST office:document-content office:class - (text|text-global| - drawing|presentation| - spreadsheet|chart) #REQUIRED> - -<!ATTLIST office:document-content office:version %string; #IMPLIED> - -<!-- document-content --> - -<!ELEMENT office:document-meta ( office:meta? ) > - -<!ATTLIST office:document-meta xmlns:office CDATA #FIXED "&nOffice;"> -<!ATTLIST office:document-meta xmlns:meta CDATA #FIXED "&nMeta;"> -<!ATTLIST office:document-meta xmlns:script CDATA #FIXED "&nScript;"> -<!ATTLIST office:document-meta xmlns:style CDATA #FIXED "&nStyle;"> -<!ATTLIST office:document-meta xmlns:text CDATA #FIXED "&nText;"> -<!ATTLIST office:document-meta xmlns:table CDATA #FIXED "&nTable;"> -<!ATTLIST office:document-meta xmlns:draw CDATA #FIXED "&nDraw;"> -<!ATTLIST office:document-meta xmlns:chart CDATA #FIXED "&nChart;"> -<!ATTLIST office:document-meta xmlns:number CDATA #FIXED "&nNumber;"> -<!ATTLIST office:document-meta xmlns:fo CDATA #FIXED "&nFO;"> -<!ATTLIST office:document-meta xmlns:xlink CDATA #FIXED "&nXLink;"> -<!ATTLIST office:document-meta xmlns:svg CDATA #FIXED "&nSVG;"> -<!ATTLIST office:document-meta xmlns:dc CDATA #FIXED "&nDC;"> -<!ATTLIST office:document-meta xmlns:dr3d CDATA #FIXED "&nDr3D;"> -<!ATTLIST office:document-meta xmlns:math CDATA #FIXED "&nMath;"> -<!ATTLIST office:document-meta xmlns:form CDATA #FIXED "&nForm;"> - -<!ATTLIST office:document-meta office:version %string; #IMPLIED> - -<!ELEMENT office:document-settings (office:settings) > -<!ATTLIST office:document-settings xmlns:office CDATA #FIXED "&nOffice;"> -<!ATTLIST office:document-settings xmlns:xlink CDATA #FIXED "&nXLink;"> -<!ATTLIST office:document-settings xmlns:config CDATA #FIXED "&nConfig;"> - -<!ATTLIST office:document-settings office:version %string; #IMPLIED> - -<!ENTITY % meta "(meta:generator?, - dc:title?, - dc:description?, - dc:subject?, - meta:initial-creator?, - meta:creation-date?, - dc:creator?, - dc:date?, - meta:printed-by?, - meta:print-date?, - meta:keywords?, - dc:language?, - meta:editing-cycles?, - meta:editing-duration?, - meta:hyperlink-behaviour?, - meta:auto-reload?, - meta:template?, - meta:user-defined*, - meta:document-statistic?)"> -<!ELEMENT office:meta %meta;> - -<!ENTITY % script "(script:library-embedded | - script:library-linked)*,office:events?"> -<!ELEMENT office:script (%script;)> - -<!ELEMENT office:font-decls (style:font-decl)*> - -<!ENTITY % styles "(style:default-style|style:style|text:list-style| - number:number-style|number:currency-style|number:percentage-style| - number:date-style|number:time-style|number:boolean-style| - number:text-style| - draw:gradient|draw:hatch|draw:fill-image|draw:marker|draw:stroke-dash| - style:presentation-page-layout|draw:transparency)"> - -<!-- Validity constraint: The elements - text:outline-style, - text:footnotes-configuration, - text:endnotes-configuration, - text:bibliography-configuration and - text:linenumbering-configuration - may appear only once! - Unfortunatetly, this constraint cannot be easily specified in the DTD. ---> -<!ELEMENT office:styles (%styles;|text:outline-style| - text:footnotes-configuration|text:endnotes-configuration| - text:bibliography-configuration|text:linenumbering-configuration)*> - -<!ELEMENT office:automatic-styles (%styles;|style:page-master)*> - -<!ELEMENT office:master-styles (draw:layer-set?,style:handout-master?,style:master-page*) > - - -<!ENTITY % body "(office:forms?,(text:tracked-changes|table:tracked-changes)?,%text-decls;,table:calculation-settings?,table:content-validations?,table:label-ranges?, - (text:h|text:p|text:ordered-list| - text:unordered-list|table:table|draw:page| - draw:a|%shape;|text:section|text:table-of-content| - text:illustration-index|text:table-index|text:object-index| - text:user-index|text:alphabetical-index|text:bibliography| - %change-marks;)*, - table:named-expressions?, - table:database-ranges?,table:data-pilot-tables?, - table:consolidation?, - table:dde-links?, - presentation:settings?)"> -<!ELEMENT office:body %body;> -<!ATTLIST office:body table:structure-protected %boolean; "false" - table:protection-key CDATA #IMPLIED> - -<!ELEMENT office:events (script:event|presentation:event)*> - -<!-- DDE source: for text sections and tables --> -<!ELEMENT office:dde-source EMPTY> -<!ATTLIST office:dde-source office:dde-application CDATA #IMPLIED> -<!ATTLIST office:dde-source office:dde-topic CDATA #IMPLIED> -<!ATTLIST office:dde-source office:dde-item CDATA #IMPLIED> -<!ATTLIST office:dde-source office:automatic-update %boolean; "false"> -<!ATTLIST office:dde-source office:name CDATA #IMPLIED> -<!ATTLIST office:dde-source table:conversion-mode (into-default-style-data-style|into-english-number|let-text) "into-default-style-data-style" > - -<!-- annotations --> -<!-- limitation: in the current implementation, only plain text inside of - paragraphs is supported --> -<!ELEMENT office:annotation (text:p)*> -<!ATTLIST office:annotation office:author %string; #IMPLIED> -<!ATTLIST office:annotation office:create-date %date; #IMPLIED> -<!ATTLIST office:annotation office:create-date-string %string; #IMPLIED> -<!ATTLIST office:annotation office:display %boolean; "false"> - -<!ELEMENT office:change-info (text:p)*> -<!ATTLIST office:change-info office:chg-author %string; #REQUIRED> -<!ATTLIST office:change-info office:chg-date-time %timeInstance; #REQUIRED> - -<!ELEMENT office:binary-data (#PCDATA)> - -<!ELEMENT style:font-decl EMPTY> -<!ATTLIST style:font-decl style:name %string; #REQUIRED> -<!ATTLIST style:font-decl fo:font-family %string; #REQUIRED> -<!ATTLIST style:font-decl style:font-style-name %string; #IMPLIED> -<!ENTITY % fontFamilyGeneric "(roman|swiss|modern|decorative|script|system)"> -<!ATTLIST style:font-decl style:font-family-generic %fontFamilyGeneric; - #IMPLIED> -<!ENTITY % fontPitch "(fixed|variable)"> -<!ATTLIST style:font-decl style:font-pitch %fontPitch; #IMPLIED> -<!ATTLIST style:font-decl style:font-charset %textEncoding; #IMPLIED> - -<!ELEMENT style:style ( style:properties?,office:events?,style:map*)> - -<!ATTLIST style:style style:name %styleName; #REQUIRED> - -<!ENTITY % styleFamily "(paragraph|text|section| - table|table-column|table-row|table-cell|table-page|chart|graphics|default|drawing-page|presentation|control|ruby)"> -<!ATTLIST style:style style:family %styleFamily; #REQUIRED> - -<!ATTLIST style:style style:parent-style-name %styleName; #IMPLIED> -<!ATTLIST style:style style:master-page-name %styleName; #IMPLIED> -<!ATTLIST style:style style:next-style-name %styleName; #IMPLIED> -<!ATTLIST style:style style:list-style-name %styleName; #IMPLIED> -<!ATTLIST style:style style:data-style-name %styleName; #IMPLIED> - -<!ATTLIST style:style style:auto-update %boolean; "false"> - -<!ATTLIST style:style style:class %string; #IMPLIED> - -<!ELEMENT style:default-style (style:properties?)> -<!ATTLIST style:default-style style:family %styleFamily; #REQUIRED> - -<!ELEMENT style:map EMPTY> - -<!ATTLIST style:map style:condition %string; #REQUIRED> -<!ATTLIST style:map style:apply-style-name %styleName; #REQUIRED> -<!ATTLIST style:map style:base-cell-address %cell-address; #IMPLIED> - -<!ELEMENT style:properties ANY> - -<!-- number format properties --> -<!ATTLIST style:properties style:num-prefix %string; #IMPLIED> -<!ATTLIST style:properties style:num-suffix %string; #IMPLIED> -<!ATTLIST style:properties style:num-format %string; #IMPLIED> -<!ATTLIST style:properties style:num-letter-sync %boolean; #IMPLIED> - -<!-- frame properties --> -<!ATTLIST style:properties fo:width %positiveLength; #IMPLIED> -<!ATTLIST style:properties fo:height %positiveLength; #IMPLIED> -<!ATTLIST style:properties style:vertical-pos (top|middle|bottom|from-top|below) #IMPLIED> -<!ATTLIST style:properties style:vertical-rel (page|page-content| - frame|frame-content| - paragraph|paragraph-content|char| - line|baseline|text) #IMPLIED> -<!ATTLIST style:properties style:horizontal-pos (left|center|right|from-left|inside|outside|from-inside) #IMPLIED> -<!ATTLIST style:properties style:horizontal-rel (page|page-content| - page-start-margin|page-end-margin| - frame|frame-content| - frame-start-margin|frame-end-margin| - paragraph|paragraph-content| - paragraph-start-margin|paragraph-end-margin| - char) #IMPLIED> -<!ATTLIST style:properties svg:width %lengthOrPercentage; #IMPLIED> -<!ATTLIST style:properties svg:height %lengthOrPercentage; #IMPLIED> -<!ATTLIST style:properties fo:min-height %lengthOrPercentage; #IMPLIED> -<!ATTLIST style:properties fo:min-width %lengthOrPercentage; #IMPLIED> -<!ATTLIST style:properties fo:max-height %lengthOrPercentage; #IMPLIED> -<!ATTLIST style:properties fo:max-width %lengthOrPercentage; #IMPLIED> -<!ATTLIST style:properties text:anchor-type %anchorType; #IMPLIED> -<!ATTLIST style:properties text:anchor-page-number %positiveInteger; #IMPLIED> -<!ATTLIST style:properties svg:x %coordinate; #IMPLIED> -<!ATTLIST style:properties svg:y %coordinate; #IMPLIED> -<!ATTLIST style:properties style:print-content %boolean; #IMPLIED> -<!ATTLIST style:properties style:protect %boolean; #IMPLIED> -<!ATTLIST style:properties style:wrap (none|left|right|parallel|dynamic|run-through) #IMPLIED> -<!ENTITY % noLimitOrPositiveInteger "CDATA"> -<!ATTLIST style:properties style:number-wrapped-paragraphs %noLimitOrPositiveInteger; #IMPLIED> -<!ATTLIST style:properties style:wrap-contour %boolean; #IMPLIED> -<!ATTLIST style:properties style:wrap-contour-mode (full|outside) #IMPLIED> -<!ATTLIST style:properties style:run-through (foreground|background) #IMPLIED> -<!ATTLIST style:properties style:editable %boolean; #IMPLIED> -<!ATTLIST style:properties style:mirror CDATA #IMPLIED> -<!ATTLIST style:properties fo:clip CDATA #IMPLIED> -<!ATTLIST style:properties text:animation (none|scroll|alternate|slide) #IMPLIED> -<!ATTLIST style:properties text:animation-direction (left|right|up|down) #IMPLIED> -<!ATTLIST style:properties text:animation-start-inside %boolean; #IMPLIED> -<!ATTLIST style:properties text:animation-stop-inside %boolean; #IMPLIED> -<!ATTLIST style:properties text:animation-repeat %integer; #IMPLIED> -<!ATTLIST style:properties text:animation-delay %timeDuration; #IMPLIED> -<!ATTLIST style:properties text:animation-steps %length; #IMPLIED> - -<!-- text properties --> -<!ATTLIST style:properties fo:font-variant (normal|small-caps) #IMPLIED> -<!ATTLIST style:properties fo:text-transform (none|lowercase| - uppercase|capitalize) #IMPLIED> -<!ATTLIST style:properties fo:color %color; #IMPLIED> -<!ATTLIST style:properties style:use-window-font-color %boolean; #IMPLIED> -<!ATTLIST style:properties style:text-outline %boolean; #IMPLIED> -<!ATTLIST style:properties style:text-crossing-out - (none|single-line|double-line|thick-line|slash|X) - #IMPLIED> -<!ATTLIST style:properties style:text-position CDATA #IMPLIED> -<!ATTLIST style:properties style:text-align (left|right|start|center|end|justify|justified) #IMPLIED> - -<!ATTLIST style:properties style:font-name %string; #IMPLIED> -<!ATTLIST style:properties fo:font-family %string; #IMPLIED> -<!ATTLIST style:properties style:font-family-generic %fontFamilyGeneric; - #IMPLIED> -<!ATTLIST style:properties style:font-style-name %string; #IMPLIED> -<!ATTLIST style:properties style:font-pitch %fontPitch; #IMPLIED> -<!ATTLIST style:properties style:font-charset %textEncoding; #IMPLIED> -<!ATTLIST style:properties style:font-name-asian %string; #IMPLIED> -<!ATTLIST style:properties style:font-family-asian %string; #IMPLIED> -<!ATTLIST style:properties style:font-family-generic-asian %fontFamilyGeneric; - #IMPLIED> -<!ATTLIST style:properties style:font-style-name-asian %string; #IMPLIED> -<!ATTLIST style:properties style:font-pitch-asian %fontPitch; #IMPLIED> -<!ATTLIST style:properties style:font-charset-asian %textEncoding; #IMPLIED> -<!ATTLIST style:properties style:font-name-complex %string; #IMPLIED> -<!ATTLIST style:properties style:font-family-complex %string; #IMPLIED> -<!ATTLIST style:properties style:font-family-generic-complex %fontFamilyGeneric; - #IMPLIED> -<!ATTLIST style:properties style:font-style-name-complex %string; #IMPLIED> -<!ATTLIST style:properties style:font-pitch-complex %fontPitch; #IMPLIED> -<!ATTLIST style:properties style:font-charset-complex %textEncoding; #IMPLIED> - -<!ATTLIST style:properties fo:font-size %positiveLengthOrPercentage; #IMPLIED> -<!ATTLIST style:properties style:font-size-rel %length; #IMPLIED> -<!ATTLIST style:properties style:font-size-asian %positiveLengthOrPercentage; #IMPLIED> -<!ATTLIST style:properties style:font-size-rel-asian %length; #IMPLIED> -<!ATTLIST style:properties style:font-size-complex %positiveLengthOrPercentage; #IMPLIED> -<!ATTLIST style:properties style:font-size-rel-complex %length; #IMPLIED> -<!ENTITY % normalOrLength "CDATA"> -<!ATTLIST style:properties fo:letter-spacing %normalOrLength; #IMPLIED> -<!ATTLIST style:properties fo:language %languageOnly; #IMPLIED> -<!ATTLIST style:properties style:language-asian %languageOnly; #IMPLIED> -<!ATTLIST style:properties style:language-complex %languageOnly; #IMPLIED> -<!ATTLIST style:properties fo:country %country; #IMPLIED> -<!ATTLIST style:properties style:country-asian %country; #IMPLIED> -<!ATTLIST style:properties style:country-complex %country; #IMPLIED> -<!ENTITY % fontStyle "(normal|italic|oblique)"> -<!ATTLIST style:properties fo:font-style %fontStyle; #IMPLIED> -<!ATTLIST style:properties style:font-style-asian %fontStyle; #IMPLIED> -<!ATTLIST style:properties style:font-style-complex %fontStyle; #IMPLIED> -<!ENTITY % fontRelief "(none|embossed|engraved)"> -<!ATTLIST style:properties style:font-relief %fontRelief; #IMPLIED> -<!ATTLIST style:properties fo:text-shadow CDATA #IMPLIED> -<!ATTLIST style:properties style:text-underline - (none|single|double|dotted|dash|long-dash|dot-dash| - dot-dot-dash|wave|bold|bold-dotted|bold-dash| - bold-long-dash|bold-dot-dash|bold-dot-dot-dash| - bold-wave|double-wave|small-wave) #IMPLIED> -<!ATTLIST style:properties style:text-autospace (none | ideograph-alpha) #IMPLIED> -<!ATTLIST style:properties style:punctuation-wrap (simple | hanging) #IMPLIED> -<!ATTLIST style:properties style:line-break (normal | strict) #IMPLIED> -<!ENTITY % fontColorOrColor "CDATA"> -<!ATTLIST style:properties style:text-underline-color %fontColorOrColor; - #IMPLIED> -<!ATTLIST style:properties fo:font-weight CDATA #IMPLIED> -<!ATTLIST style:properties style:font-weight-asian CDATA #IMPLIED> -<!ATTLIST style:properties style:font-weight-complex CDATA #IMPLIED> -<!ATTLIST style:properties fo:score-spaces %boolean; #IMPLIED> -<!ATTLIST style:properties style:letter-kerning %boolean; #IMPLIED> -<!ATTLIST style:properties style:text-blinking %boolean; #IMPLIED> -<!ATTLIST style:properties style:text-background-color %transparentOrColor; - #IMPLIED> - -<!ATTLIST style:properties style:text-combine (none|letters|lines) #IMPLIED> -<!ATTLIST style:properties style:text-combine-start-char %character; #IMPLIED> -<!ATTLIST style:properties style:text-combine-end-char %character; #IMPLIED> -<!ATTLIST style:properties style:text-emphasize CDATA #IMPLIED> -<!ATTLIST style:properties style:text-scale %percentage; #IMPLIED> -<!ATTLIST style:properties style:text-rotation-angle %integer; #IMPLIED> -<!ATTLIST style:properties style:text-rotation-scale (fixed|line-height) #IMPLIED> - -<!-- paragraph properties --> -<!ENTITY % nonNegativeLengthOrPercentageOrNormal "CDATA"> -<!ATTLIST style:properties fo:line-height - %nonNegativeLengthOrPercentageOrNormal; #IMPLIED> -<!ATTLIST style:properties style:line-height-at-least %nonNegativeLength; - #IMPLIED> -<!ATTLIST style:properties style:line-spacing %length; #IMPLIED> -<!ATTLIST style:properties fo:text-align (start|end|center|justify) #IMPLIED> -<!ATTLIST style:properties fo:text-align-last (start|center|justify) #IMPLIED> -<!ATTLIST style:properties style:text-align-source (fix|value-type) #IMPLIED> -<!ATTLIST style:properties style:justify-single-word %boolean; #IMPLIED> -<!ATTLIST style:properties style:break-inside (auto|avoid) #IMPLIED> -<!ATTLIST style:properties fo:widows %nonNegativeInteger; #IMPLIED> -<!ATTLIST style:properties fo:orphans %nonNegativeInteger; #IMPLIED> - -<!ATTLIST style:properties fo:hyphenate %boolean; #IMPLIED> -<!ATTLIST style:properties fo:hyphenate-keep (none|page) #IMPLIED> -<!ATTLIST style:properties fo:hyphenation-remain-char-count %positiveInteger; - #IMPLIED> -<!ATTLIST style:properties fo:hyphenation-push-char-count %positiveInteger; - #IMPLIED> -<!ATTLIST style:properties fo:hyphenation-ladder-count - %noLimitOrPositiveInteger; #IMPLIED> -<!ATTLIST style:properties style:page-number %positiveInteger; #IMPLIED> - -<!ELEMENT style:tab-stops (style:tab-stop)*> -<!ELEMENT style:tab-stop EMPTY> -<!ATTLIST style:tab-stop style:position %nonNegativeLength; #REQUIRED> -<!ATTLIST style:tab-stop style:type (left|center|right|char|default) "left"> -<!ATTLIST style:tab-stop style:char %character; #IMPLIED> -<!ATTLIST style:tab-stop style:leader-char %character; " "> - -<!ELEMENT style:drop-cap EMPTY> -<!ENTITY % wordOrPositiveInteger "CDATA"> -<!ATTLIST style:drop-cap style:length %wordOrPositiveInteger; "1"> -<!ATTLIST style:drop-cap style:lines %positiveInteger; "1"> -<!ATTLIST style:drop-cap style:distance %length; "0cm"> -<!ATTLIST style:drop-cap style:style-name %styleName; #IMPLIED> - -<!ATTLIST style:properties style:register-true %boolean; #IMPLIED> -<!ATTLIST style:properties style:register-truth-ref-style-name %styleName; #IMPLIED> -<!ATTLIST style:properties fo:margin-left %positiveLengthOrPercentage; #IMPLIED> -<!ATTLIST style:properties fo:margin-right %positiveLengthOrPercentage; - #IMPLIED> -<!ATTLIST style:properties fo:text-indent %lengthOrPercentage; #IMPLIED> -<!ATTLIST style:properties style:auto-text-indent %boolean; #IMPLIED> -<!ATTLIST style:properties fo:margin-top %positiveLengthOrPercentage; #IMPLIED> -<!ATTLIST style:properties fo:margin-bottom %positiveLengthOrPercentage; #IMPLIED> -<!ATTLIST style:properties fo:break-before (auto|column|page) #IMPLIED> -<!ATTLIST style:properties fo:break-after (auto|column|page) #IMPLIED> -<!ATTLIST style:properties fo:background-color %transparentOrColor; #IMPLIED> -<!ATTLIST style:properties style:background-transparency %percentage; #IMPLIED> -<!ATTLIST style:properties style:dynamic-spacing %boolean; #IMPLIED> - -<!ELEMENT style:background-image (office:binary-data?)> -<!ATTLIST style:background-image xlink:type (simple) #IMPLIED> -<!ATTLIST style:background-image xlink:href %uriReference; #IMPLIED> -<!ATTLIST style:background-image xlink:show (embed) #IMPLIED> -<!ATTLIST style:background-image xlink:actuate (onLoad) #IMPLIED> -<!ATTLIST style:background-image style:repeat (no-repeat|repeat|stretch) - "repeat"> -<!ATTLIST style:background-image style:position CDATA "center"> -<!ATTLIST style:background-image style:filter-name %string; #IMPLIED> -<!ATTLIST style:background-image draw:transparency %percentage; #IMPLIED> - -<!ELEMENT style:symbol-image (office:binary-data?)> -<!ATTLIST style:symbol-image xlink:type (simple) #IMPLIED> -<!ATTLIST style:symbol-image xlink:href %uriReference; #IMPLIED> -<!ATTLIST style:symbol-image xlink:show (embed) #IMPLIED> -<!ATTLIST style:symbol-image xlink:actuate (onLoad) #IMPLIED> - -<!ATTLIST style:properties fo:border CDATA #IMPLIED> -<!ATTLIST style:properties fo:border-top CDATA #IMPLIED> -<!ATTLIST style:properties fo:border-bottom CDATA #IMPLIED> -<!ATTLIST style:properties fo:border-left CDATA #IMPLIED> -<!ATTLIST style:properties fo:border-right CDATA #IMPLIED> -<!ATTLIST style:properties style:border-line-width CDATA #IMPLIED> -<!ATTLIST style:properties style:border-line-width-top CDATA #IMPLIED> -<!ATTLIST style:properties style:border-line-width-bottom CDATA #IMPLIED> -<!ATTLIST style:properties style:border-line-width-left CDATA #IMPLIED> -<!ATTLIST style:properties style:border-line-width-right CDATA #IMPLIED> -<!ATTLIST style:properties fo:padding %nonNegativeLength; #IMPLIED> -<!ATTLIST style:properties fo:padding-top %nonNegativeLength; #IMPLIED> -<!ATTLIST style:properties fo:padding-bottom %nonNegativeLength; #IMPLIED> -<!ATTLIST style:properties fo:padding-left %nonNegativeLength; #IMPLIED> -<!ATTLIST style:properties fo:padding-right %nonNegativeLength; #IMPLIED> -<!ATTLIST style:properties style:shadow CDATA #IMPLIED> -<!ATTLIST style:properties fo:keep-with-next %boolean; #IMPLIED> - -<!ATTLIST style:properties text:number-lines %boolean; "false"> -<!ATTLIST style:properties text:line-number %nonNegativeInteger; #IMPLIED> - -<!ATTLIST style:properties style:decimal-places %nonNegativeInteger; #IMPLIED> -<!ATTLIST style:properties style:tab-stop-distance %nonNegativeLength; #IMPLIED> - -<!-- section properties --> -<!ATTLIST style:properties text:dont-balance-text-columns %boolean; #IMPLIED> - -<!-- ruby properties --> -<!ATTLIST style:properties style:ruby-align (left|center|right|distribute-letter|distribute-space) #IMPLIED> -<!ATTLIST style:properties style:ruby-position (above|below) #IMPLIED> - - -<!-- table properties --> -<!ATTLIST style:properties style:width %positiveLength; #IMPLIED> -<!ATTLIST style:properties style:rel-width %percentage; #IMPLIED> -<!ATTLIST style:properties style:may-break-between-rows %boolean; #IMPLIED> -<!ATTLIST style:properties table:page-style-name %styleName; #IMPLIED> -<!ATTLIST style:properties table:display %boolean; #IMPLIED> - -<!-- table column properties --> -<!ATTLIST style:properties style:column-width %positiveLength; #IMPLIED> -<!ENTITY % relWidth "CDATA"> -<!ATTLIST style:properties style:rel-column-width %relWidth; #IMPLIED> -<!ATTLIST style:properties style:use-optimal-column-width %boolean; #IMPLIED> - -<!-- table row properties --> -<!ATTLIST style:properties style:row-height %positiveLength; #IMPLIED> -<!ATTLIST style:properties style:min-row-height %nonNegativeLength; #IMPLIED> -<!ATTLIST style:properties style:use-optimal-row-height %boolean; #IMPLIED> - -<!-- table cell properties --> -<!ATTLIST style:properties - table:align (left | center | right | margins) #IMPLIED - table:border-model (collapsing | separating) #IMPLIED - fo:vertical-align (top | middle | bottom | automatic) #IMPLIED - fo:direction (ltr | ttb) #IMPLIED - style:glyph-orientation-vertical (auto | 0) #IMPLIED - style:rotation-angle %nonNegativeInteger; #IMPLIED - style:rotation-align (none | bottom | top | center) #IMPLIED - style:cell-protect CDATA #IMPLIED - fo:wrap-option (no-wrap | wrap) #IMPLIED -> -<!ELEMENT style:columns (style:column-sep?,style:column*)> -<!ATTLIST style:columns fo:column-count %nonNegativeInteger; #IMPLIED> -<!ATTLIST style:columns fo:column-gap %positiveLength; #IMPLIED> - -<!ELEMENT style:column EMPTY> -<!ATTLIST style:column style:rel-width CDATA #IMPLIED> -<!ATTLIST style:column fo:margin-left %positiveLength; #IMPLIED> -<!ATTLIST style:column fo:margin-right %positiveLength; #IMPLIED> - -<!ELEMENT style:column-sep EMPTY> -<!ATTLIST style:column-sep style:style (none|solid|dotted|dashed|dot-dashed) - "solid"> -<!ATTLIST style:column-sep style:width %length; #REQUIRED> -<!ATTLIST style:column-sep style:height %percentage; "100%"> -<!ATTLIST style:column-sep style:vertical-align (top|middle|bottom) "top"> -<!ATTLIST style:column-sep style:color %color; "#000000"> - -<!-- page master properties --> -<!ELEMENT style:page-master (style:properties?, style:header-style?, style:footer-style?)> -<!ATTLIST style:page-master style:name %styleName; #REQUIRED> -<!ATTLIST style:page-master style:page-usage (all|left|right|mirrored) "all"> - -<!ELEMENT style:header-style (style:properties?)> -<!ELEMENT style:footer-style (style:properties?)> - -<!ATTLIST style:properties fo:page-width %length; #IMPLIED> -<!ATTLIST style:properties fo:page-height %length; #IMPLIED> -<!ATTLIST style:properties style:paper-tray-name %string; #IMPLIED> -<!ATTLIST style:properties style:print-orientation (portrait|landscape) #IMPLIED> -<!ATTLIST style:properties style:print CDATA #IMPLIED> -<!ATTLIST style:properties style:print-page-order (ttb|ltr) #IMPLIED> -<!ATTLIST style:properties style:first-page-number %positiveInteger; #IMPLIED> -<!ATTLIST style:properties style:scale-to %percentage; #IMPLIED> -<!ATTLIST style:properties style:scale-to-pages %positiveInteger; #IMPLIED> -<!ATTLIST style:properties style:table-centering (horizontal | vertical | both | none) #IMPLIED> - -<!ATTLIST style:properties style:footnote-max-height %lengthOrNoLimit; #IMPLIED> -<!ATTLIST style:properties style:vertical-align (top|bottom|middle|basline|auto) #IMPLIED> -<!ATTLIST style:properties style:writing-mode (lr-tb|rl-tb|tb-rl|tb-lr|lr|rl|tb|page) "lr-tb"> -<!ATTLIST style:properties style:layout-grid-mode (none|line|both) #IMPLIED> -<!ATTLIST style:properties style:layout-grid-base-height %length; #IMPLIED> -<!ATTLIST style:properties style:layout-grid-ruby-height %length; #IMPLIED> -<!ATTLIST style:properties style:layout-grid-lines %positiveInteger; #IMPLIED> -<!ATTLIST style:properties style:layout-grid-color %color; #IMPLIED> -<!ATTLIST style:properties style:layout-grid-ruby-below %boolean; #IMPLIED> -<!ATTLIST style:properties style:layout-grid-print %boolean; #IMPLIED> -<!ATTLIST style:properties style:layout-grid-display %boolean; #IMPLIED> -<!ATTLIST style:properties style:snap-to-layout-grid %boolean; #IMPLIED> - -<!ELEMENT style:footnote-sep EMPTY> -<!ATTLIST style:footnote-sep style:width %length; #IMPLIED> -<!ATTLIST style:footnote-sep style:rel-width %percentage; #IMPLIED> -<!ATTLIST style:footnote-sep style:color %color; #IMPLIED> -<!ATTLIST style:footnote-sep style:adjustment (left|center|right) "left"> -<!ATTLIST style:footnote-sep style:distance-before-sep %length; #IMPLIED> -<!ATTLIST style:footnote-sep style:distance-after-sep %length; #IMPLIED> - -<!-- master page --> -<!ELEMENT style:master-page ( (style:header, style:header-left?)?, (style:footer, style:footer-left?)?, - office:forms?,style:style*, (%shapes;)*, presentation:notes? )> -<!ATTLIST style:master-page style:name %styleName; #REQUIRED> -<!ATTLIST style:master-page style:page-master-name %styleName; #REQUIRED> -<!ATTLIST style:master-page style:next-style-name %styleName; #IMPLIED> -<!ATTLIST style:master-page draw:style-name %styleName; #IMPLIED> - -<!-- handout master --> -<!ELEMENT style:handout-master (%shapes;)*> -<!ATTLIST style:handout-master presentation:presentation-page-layout-name %styleName; #IMPLIED> -<!ATTLIST style:handout-master style:page-master-name %styleName; #IMPLIED> - - -<!ENTITY % hd-ft-content "( %headerText; | (style:region-left?, style:region-center?, style:region-right?) )"> -<!ELEMENT style:header %hd-ft-content;> -<!ATTLIST style:header style:display %boolean; "true"> -<!ELEMENT style:footer %hd-ft-content;> -<!ATTLIST style:footer style:display %boolean; "true"> -<!ELEMENT style:header-left %hd-ft-content;> -<!ATTLIST style:header-left style:display %boolean; "true"> -<!ELEMENT style:footer-left %hd-ft-content;> -<!ATTLIST style:footer-left style:display %boolean; "true"> - -<!ENTITY % region-content "(text:p*)"> -<!ELEMENT style:region-left %region-content;> -<!ELEMENT style:region-center %region-content;> -<!ELEMENT style:region-right %region-content;> - -<!ELEMENT meta:generator (%cString;)> - -<!ELEMENT dc:title (%cString;)> - -<!ELEMENT dc:description (%cString;)> - -<!ELEMENT dc:subject (%cString;)> - -<!ELEMENT meta:keywords (meta:keyword)*> -<!ELEMENT meta:keyword (%cString;)> - -<!ELEMENT meta:initial-creator (%cString;)> - -<!ELEMENT dc:creator (%cString;)> - -<!ELEMENT meta:printed-by (%cString;)> - -<!ELEMENT meta:creation-date (%cTimeInstance;)> - -<!ELEMENT dc:date (%cTimeInstance;)> - -<!ELEMENT meta:print-date (%cTimeInstance;)> - -<!ELEMENT meta:template EMPTY> -<!ATTLIST meta:template xlink:type (simple) #FIXED "simple"> -<!ATTLIST meta:template xlink:actuate (onRequest) "onRequest"> -<!ATTLIST meta:template xlink:href %uriReference; #REQUIRED> -<!ATTLIST meta:template xlink:title %string; #IMPLIED> -<!ATTLIST meta:template meta:date %timeInstance; #IMPLIED> - -<!ELEMENT meta:auto-reload EMPTY> -<!ATTLIST meta:auto-reload xlink:type (simple) #IMPLIED> -<!ATTLIST meta:auto-reload xlink:show (replace) #IMPLIED> -<!ATTLIST meta:auto-reload xlink:actuate (onLoad) #IMPLIED> -<!ATTLIST meta:auto-reload xlink:href %uriReference; #IMPLIED> -<!ATTLIST meta:auto-reload meta:delay %timeDuration; "P0S"> - -<!ELEMENT meta:hyperlink-behaviour EMPTY> -<!ATTLIST meta:hyperlink-behaviour office:target-frame-name %targetFrameName; #IMPLIED> -<!ATTLIST meta:hyperlink-behaviour xlink:show (new|replace) #IMPLIED> - -<!ELEMENT dc:language (%cLanguage;)> - -<!ELEMENT meta:editing-cycles (%cPositiveInteger;)> - -<!ELEMENT meta:editing-duration (%cTimeDuration;)> - -<!ELEMENT meta:user-defined (%cString;)> -<!ATTLIST meta:user-defined meta:name %string; #REQUIRED> - -<!ELEMENT meta:document-statistic EMPTY> -<!ATTLIST meta:document-statistic meta:page-count %positiveInteger; #IMPLIED - meta:table-count %nonNegativeInteger; #IMPLIED - meta:draw-count %nonNegativeInteger; #IMPLIED - meta:image-count %nonNegativeInteger; #IMPLIED - meta:ole-object-count %nonNegativeInteger; #IMPLIED - meta:paragraph-count %nonNegativeInteger; #IMPLIED - meta:word-count %nonNegativeInteger; #IMPLIED - meta:character-count %nonNegativeInteger; #IMPLIED - meta:row-count %nonNegativeInteger; #IMPLIED - meta:cell-count %nonNegativeInteger; #IMPLIED - meta:object-count %positiveInteger; #IMPLIED> - -<!ELEMENT script:library-embedded (script:module*)> -<!ATTLIST script:library-embedded script:name %string; #REQUIRED> -<!ATTLIST script:library-embedded script:password %string; #IMPLIED> - -<!ELEMENT script:library-linked EMPTY> -<!ATTLIST script:library-linked script:name %string; #REQUIRED> -<!ATTLIST script:library-linked xlink:href %string; #REQUIRED> -<!ATTLIST script:library-linked xlink:type (simple) #FIXED "simple"> - -<!ELEMENT script:module (#PCDATA)> -<!ATTLIST script:module script:name %string; #REQUIRED> -<!ATTLIST script:module script:language %string; #IMPLIED> - - -<!ENTITY % script-language "script:language %string; #REQUIRED"> -<!ENTITY % event-name "script:event-name %string; #REQUIRED"> -<!ENTITY % location "script:location (document|application) #REQUIRED"> -<!ENTITY % macro-name "script:macro-name %string; #REQUIRED"> - -<!ELEMENT script:event (#PCDATA)> -<!ATTLIST script:event %script-language; - %event-name; - %location; - %macro-name;> - -<!ENTITY % points "CDATA" > -<!ENTITY % pathData "CDATA" > -<!ENTITY % gradient-style "(linear|axial|radial|ellipsoid|square|rectangular)" > -<!ENTITY % draw-position "svg:x %coordinate; #IMPLIED svg:y %coordinate; #IMPLIED"> -<!ENTITY % draw-end-position "table:end-cell-address %cell-address; #IMPLIED table:end-x %coordinate; #IMPLIED table:end-y %coordinate; #IMPLIED"> -<!ENTITY % draw-size "svg:width %coordinate; #IMPLIED svg:height %coordinate; #IMPLIED"> -<!ENTITY % draw-transform "draw:transform CDATA #IMPLIED"> -<!ENTITY % draw-viewbox "svg:viewBox CDATA #REQUIRED"> -<!ENTITY % draw-style-name "draw:style-name %styleName; #IMPLIED presentation:style-name %styleName; #IMPLIED draw:text-style-name %styleName; #IMPLIED"> -<!ENTITY % draw-shape-id "CDATA #IMPLIED" > -<!ENTITY % draw-text "(text:p|text:unordered-list|text:ordered-list)*"> -<!ENTITY % zindex "draw:z-index %nonNegativeInteger; #IMPLIED"> -<!ENTITY % distance "CDATA"> -<!ENTITY % rectanglePoint "(top-left|top|top-right|left|center|right|bottom-left|bottom|bottom-right)"> -<!ENTITY % vector3D "CDATA"> -<!ENTITY % text-anchor "text:anchor-type %anchorType; #IMPLIED text:anchor-page-number %positiveInteger; #IMPLIED"> -<!ENTITY % layerName "CDATA"> -<!ENTITY % table-background "table:table-background (true | false) #IMPLIED"> - -<!-- commont presentation shape attributes --> -<!ENTITY % presentation-style-name "presentation:style-name %styleName; #IMPLIED"> -<!ENTITY % presentation-classes "(title|outline|subtitle|text|graphic|object|chart|table|orgchart|page|notes)" > -<!-- ENTITY % presentation-class "presentation:class %presentation-classes; #IMPLIED" --> -<!ENTITY % presentation-class "presentation:class %presentation-classes; #IMPLIED presentation:placeholder (true|false) #IMPLIED presentation:user-transformed (true|false) #IMPLIED"> -<!ENTITY % presentationEffects "(none|fade|move|stripes|open|close|dissolve|wavyline|random|lines|laser|appear|hide|move-short|checkerboard|rotate|stretch)" > -<!ENTITY % presentationEffectDirections "(none|from-left|from-top|from-right|from-bottom|from-center|from-upper-left|from-upper-right|from-lower-left|from-lower-right|to-left|to-top|to-right|to-bottom|to-upper-left|to-upper-right|to-lower-right|to-lower-left|path|spiral-inward-left|spiral-inward-right|spiral-outward-left|spiral-outward-right|vertical|horizontal|to-center|clockwise|counter-clockwise)" > -<!ENTITY % presentationSpeeds "(slow|medium|fast)" > - -<!-- Drawing shapes --> -<!ELEMENT draw:rect ( office:events?, %draw-text; )> -<!ATTLIST draw:rect %draw-position; > -<!ATTLIST draw:rect %draw-end-position; > -<!ATTLIST draw:rect %table-background; > -<!ATTLIST draw:rect %draw-size; > -<!ATTLIST draw:rect %draw-style-name; > -<!ATTLIST draw:rect %draw-transform; > -<!ATTLIST draw:rect draw:corner-radius %nonNegativeLength; #IMPLIED> -<!ATTLIST draw:rect %zindex;> -<!ATTLIST draw:rect draw:id %draw-shape-id;> -<!ATTLIST draw:rect %text-anchor;> -<!ATTLIST draw:rect draw:layer %layerName; #IMPLIED> - -<!ELEMENT draw:line ( office:events?, %draw-text; )> -<!ATTLIST draw:line svg:x1 %length; #IMPLIED> -<!ATTLIST draw:line svg:y1 %length; #IMPLIED> -<!ATTLIST draw:line svg:x2 %length; #REQUIRED> -<!ATTLIST draw:line svg:y2 %length; #REQUIRED> -<!ATTLIST draw:line svg:y %coordinate; #IMPLIED> -<!ATTLIST draw:line %draw-style-name; > -<!ATTLIST draw:line %draw-transform; > -<!ATTLIST draw:line %zindex;> -<!ATTLIST draw:line %draw-end-position; > -<!ATTLIST draw:line %table-background; > -<!ATTLIST draw:line draw:id %draw-shape-id;> -<!ATTLIST draw:line %text-anchor;> -<!ATTLIST draw:line draw:layer %layerName; #IMPLIED> - -<!ELEMENT draw:polyline ( office:events?, %draw-text; )> -<!ATTLIST draw:polyline %draw-position; > -<!ATTLIST draw:polyline %draw-size; > -<!ATTLIST draw:polyline %draw-viewbox; > -<!ATTLIST draw:polyline draw:points %points; #REQUIRED> -<!ATTLIST draw:polyline %draw-style-name; > -<!ATTLIST draw:polyline %draw-transform; > -<!ATTLIST draw:polyline %zindex;> -<!ATTLIST draw:polyline %draw-end-position; > -<!ATTLIST draw:polyline %table-background; > -<!ATTLIST draw:polyline draw:id %draw-shape-id;> -<!ATTLIST draw:polyline %text-anchor;> -<!ATTLIST draw:polyline draw:layer %layerName; #IMPLIED> - -<!ELEMENT draw:polygon ( office:events?, %draw-text; )> -<!ATTLIST draw:polygon %draw-position; > -<!ATTLIST draw:polygon %draw-end-position; > -<!ATTLIST draw:polygon %table-background; > -<!ATTLIST draw:polygon %draw-size; > -<!ATTLIST draw:polygon %draw-viewbox; > -<!ATTLIST draw:polygon draw:points %points; #REQUIRED > -<!ATTLIST draw:polygon %draw-style-name; > -<!ATTLIST draw:polygon %draw-transform; > -<!ATTLIST draw:polygon %zindex;> -<!ATTLIST draw:polygon draw:id %draw-shape-id;> -<!ATTLIST draw:polygon %text-anchor;> -<!ATTLIST draw:polygon draw:layer %layerName; #IMPLIED> - -<!ELEMENT draw:path ( office:events?, %draw-text; )> -<!ATTLIST draw:path %draw-position;> -<!ATTLIST draw:path %draw-end-position; > -<!ATTLIST draw:path %table-background; > -<!ATTLIST draw:path %draw-size; > -<!ATTLIST draw:path %draw-viewbox; > -<!ATTLIST draw:path svg:d %pathData; #REQUIRED > -<!ATTLIST draw:path %draw-style-name; > -<!ATTLIST draw:path %draw-transform; > -<!ATTLIST draw:path %zindex;> -<!ATTLIST draw:path draw:id %draw-shape-id;> -<!ATTLIST draw:path %text-anchor;> -<!ATTLIST draw:path draw:layer %layerName; #IMPLIED> - -<!ELEMENT draw:circle ( office:events?, %draw-text; )> -<!ATTLIST draw:circle %draw-position; > -<!ATTLIST draw:circle %draw-size; > -<!ATTLIST draw:circle %draw-style-name; > -<!ATTLIST draw:circle %draw-transform; > -<!ATTLIST draw:circle %zindex;> -<!ATTLIST draw:circle %draw-end-position; > -<!ATTLIST draw:circle %table-background; > -<!ATTLIST draw:circle draw:id %draw-shape-id;> -<!ATTLIST draw:circle draw:kind (full|section|cut|arc) "full"> -<!ATTLIST draw:circle draw:start-angle %nonNegativeInteger; #IMPLIED> -<!ATTLIST draw:circle draw:end-angle %nonNegativeInteger; #IMPLIED> -<!ATTLIST draw:circle %text-anchor;> -<!ATTLIST draw:circle draw:layer %layerName; #IMPLIED> - -<!ELEMENT draw:ellipse ( office:events?, %draw-text; )> -<!ATTLIST draw:ellipse %draw-position; > -<!ATTLIST draw:ellipse %draw-size; > -<!ATTLIST draw:ellipse %draw-style-name; > -<!ATTLIST draw:ellipse %draw-transform; > -<!ATTLIST draw:ellipse %zindex;> -<!ATTLIST draw:ellipse %draw-end-position; > -<!ATTLIST draw:ellipse %table-background; > -<!ATTLIST draw:ellipse draw:id %draw-shape-id;> -<!ATTLIST draw:ellipse draw:kind (full|section|cut|arc) "full"> -<!ATTLIST draw:ellipse draw:start-angle %nonNegativeInteger; #IMPLIED> -<!ATTLIST draw:ellipse draw:end-angle %nonNegativeInteger; #IMPLIED> -<!ATTLIST draw:ellipse %text-anchor;> -<!ATTLIST draw:ellipse draw:layer %layerName; #IMPLIED> - -<!ELEMENT draw:connector ( office:events?, %draw-text;)> -<!ATTLIST draw:connector draw:type (standard|lines|line|curve) "standard"> -<!ATTLIST draw:connector draw:line-skew CDATA #IMPLIED> -<!ATTLIST draw:connector %draw-style-name;> -<!ATTLIST draw:connector svg:x1 %coordinate; #REQUIRED> -<!ATTLIST draw:connector svg:y1 %coordinate; #REQUIRED> -<!ATTLIST draw:connector svg:x2 %coordinate; #REQUIRED> -<!ATTLIST draw:connector svg:y2 %coordinate; #REQUIRED> -<!ATTLIST draw:connector draw:start-shape %draw-shape-id;> -<!ATTLIST draw:connector draw:start-glue-point %integer; #IMPLIED> -<!ATTLIST draw:connector draw:end-shape %draw-shape-id;> -<!ATTLIST draw:connector draw:end-glue-point %integer; #IMPLIED> -<!ATTLIST draw:connector %zindex;> -<!ATTLIST draw:connector %draw-end-position; > -<!ATTLIST draw:connector %table-background; > -<!ATTLIST draw:connector draw:id %draw-shape-id;> -<!ATTLIST draw:connector %text-anchor;> -<!ATTLIST draw:connector draw:layer %layerName; #IMPLIED> - -<!ELEMENT draw:control EMPTY> -<!ATTLIST draw:control %draw-style-name;> -<!ATTLIST draw:control %draw-position; > -<!ATTLIST draw:control %draw-size; > -<!ATTLIST draw:control %control-id; > -<!ATTLIST draw:control %zindex;> -<!ATTLIST draw:control %draw-end-position; > -<!ATTLIST draw:control %table-background; > -<!ATTLIST draw:control draw:id %draw-shape-id;> -<!ATTLIST draw:control %text-anchor;> -<!ATTLIST draw:control draw:layer %layerName; #IMPLIED> - -<!ELEMENT draw:g ( office:events?, (%shapes;)* ) > -<!ATTLIST draw:g svg:y %coordinate; #IMPLIED> -<!ATTLIST draw:g %draw-transform; > -<!ATTLIST draw:g draw:name %string; #IMPLIED> -<!ATTLIST draw:g %draw-style-name; > -<!ATTLIST draw:g %zindex;> -<!ATTLIST draw:g %draw-end-position; > -<!ATTLIST draw:g %table-background; > -<!ATTLIST draw:g draw:id %draw-shape-id;> -<!ATTLIST draw:g %text-anchor;> -<!ATTLIST draw:g draw:layer %layerName; #IMPLIED> - -<!ELEMENT draw:page-thumbnail EMPTY> -<!ATTLIST draw:page-thumbnail draw:page-number %positiveInteger; #IMPLIED> -<!ATTLIST draw:page-thumbnail %draw-position; > -<!ATTLIST draw:page-thumbnail %draw-size; > -<!ATTLIST draw:page-thumbnail %draw-style-name; > -<!ATTLIST draw:page-thumbnail %presentation-class; > -<!ATTLIST draw:page-thumbnail %zindex;> -<!ATTLIST draw:page-thumbnail %draw-end-position; > -<!ATTLIST draw:page-thumbnail %table-background; > -<!ATTLIST draw:page-thumbnail draw:id %draw-shape-id;> -<!ATTLIST draw:page-thumbnail %text-anchor;> -<!ATTLIST draw:page-thumbnail draw:layer %layerName; #IMPLIED> - -<!ELEMENT draw:caption ( office:events?, %draw-text;)> -<!ATTLIST draw:caption %draw-position; > -<!ATTLIST draw:caption %draw-end-position; > -<!ATTLIST draw:caption %table-background; > -<!ATTLIST draw:caption %draw-size; > -<!ATTLIST draw:caption %draw-style-name; > -<!ATTLIST draw:caption %draw-transform; > -<!ATTLIST draw:caption draw:caption-point-x %coordinate; #IMPLIED> -<!ATTLIST draw:caption draw:caption-point-y %coordinate; #IMPLIED> -<!ATTLIST draw:caption %zindex;> -<!ATTLIST draw:caption draw:id %draw-shape-id;> -<!ATTLIST draw:caption %text-anchor;> -<!ATTLIST draw:caption draw:layer %layerName; #IMPLIED> -<!ATTLIST draw:caption draw:corner-radius %nonNegativeLength; #IMPLIED> - -<!ELEMENT draw:measure ( office:events?, %draw-text;)> -<!ATTLIST draw:measure svg:x1 %coordinate; #REQUIRED> -<!ATTLIST draw:measure svg:y1 %coordinate; #REQUIRED> -<!ATTLIST draw:measure svg:x2 %coordinate; #REQUIRED> -<!ATTLIST draw:measure svg:y2 %coordinate; #REQUIRED> -<!ATTLIST draw:measure %draw-end-position; > -<!ATTLIST draw:measure %table-background; > -<!ATTLIST draw:measure %draw-style-name; > -<!ATTLIST draw:measure %draw-transform; > -<!ATTLIST draw:measure %zindex;> -<!ATTLIST draw:measure draw:id %draw-shape-id;> -<!ATTLIST draw:measure %text-anchor;> -<!ATTLIST draw:measure draw:layer %layerName; #IMPLIED> - -<!-- graphic style elements --> -<!ELEMENT draw:gradient EMPTY > -<!ATTLIST draw:gradient draw:name %styleName; #REQUIRED> -<!ATTLIST draw:gradient draw:style %gradient-style; #REQUIRED> -<!ATTLIST draw:gradient draw:cx %coordinate; #IMPLIED> -<!ATTLIST draw:gradient draw:cy %coordinate; #IMPLIED> -<!ATTLIST draw:gradient draw:start-color %color; #IMPLIED> -<!ATTLIST draw:gradient draw:end-color %color; #IMPLIED> -<!ATTLIST draw:gradient draw:start-intensity %percentage; #IMPLIED> -<!ATTLIST draw:gradient draw:end-intensity %percentage; #IMPLIED> -<!ATTLIST draw:gradient draw:angle %integer; #IMPLIED> -<!ATTLIST draw:gradient draw:border %percentage; #IMPLIED> - -<!ELEMENT draw:hatch EMPTY > -<!ATTLIST draw:hatch draw:name %styleName; #REQUIRED> -<!ATTLIST draw:hatch draw:style (single|double|triple) #REQUIRED > -<!ATTLIST draw:hatch draw:color %color; #IMPLIED> -<!ATTLIST draw:hatch draw:distance %length; #IMPLIED> -<!ATTLIST draw:hatch draw:rotation %integer; #IMPLIED> - - -<!ELEMENT draw:fill-image EMPTY > -<!ATTLIST draw:fill-image draw:name %styleName; #REQUIRED> -<!ATTLIST draw:fill-image xlink:href %uriReference; #REQUIRED> -<!ATTLIST draw:fill-image xlink:type (simple) #IMPLIED> -<!ATTLIST draw:fill-image xlink:show (embed) #IMPLIED> -<!ATTLIST draw:fill-image xlink:actuate (onLoad) #IMPLIED> -<!ATTLIST draw:fill-image svg:width %length; #IMPLIED> -<!ATTLIST draw:fill-image svg:height %length; #IMPLIED> - -<!ELEMENT draw:transparency EMPTY> -<!ATTLIST draw:transparency draw:name %styleName; #REQUIRED> -<!ATTLIST draw:transparency draw:style %gradient-style; #REQUIRED> -<!ATTLIST draw:transparency draw:cx %coordinate; #IMPLIED> -<!ATTLIST draw:transparency draw:cy %coordinate; #IMPLIED> -<!ATTLIST draw:transparency draw:start %percentage; #IMPLIED> -<!ATTLIST draw:transparency draw:end %percentage; #IMPLIED> -<!ATTLIST draw:transparency draw:angle %integer; #IMPLIED> -<!ATTLIST draw:transparency draw:border %percentage; #IMPLIED> - -<!ELEMENT draw:marker EMPTY> -<!ATTLIST draw:marker draw:name %styleName; #REQUIRED> -<!ATTLIST draw:marker %draw-viewbox; > -<!ATTLIST draw:marker svg:d %pathData; #REQUIRED> - -<!ELEMENT draw:stroke-dash EMPTY> -<!ATTLIST draw:stroke-dash draw:name %styleName; #REQUIRED> -<!ATTLIST draw:stroke-dash draw:style (rect|round) #IMPLIED> -<!ATTLIST draw:stroke-dash draw:dots1 %integer; #IMPLIED> -<!ATTLIST draw:stroke-dash draw:dots1-length %length; #IMPLIED> -<!ATTLIST draw:stroke-dash draw:dots2 %integer; #IMPLIED> -<!ATTLIST draw:stroke-dash draw:dots2-length %length; #IMPLIED> -<!ATTLIST draw:stroke-dash draw:distance %length; #IMPLIED> - -<!-- stroke attributes --> -<!ATTLIST style:properties draw:stroke (none|dash|solid) #IMPLIED> -<!ATTLIST style:properties draw:stroke-dash CDATA #IMPLIED> -<!ATTLIST style:properties svg:stroke-width %length; #IMPLIED> -<!ATTLIST style:properties svg:stroke-color %color; #IMPLIED> -<!ATTLIST style:properties draw:marker-start %styleName; #IMPLIED> -<!ATTLIST style:properties draw:marker-end %styleName; #IMPLIED> -<!ATTLIST style:properties draw:marker-start-width %length; #IMPLIED> -<!ATTLIST style:properties draw:marker-end-width %length; #IMPLIED> -<!ATTLIST style:properties draw:marker-start-center %boolean; #IMPLIED> -<!ATTLIST style:properties draw:marker-end-center %boolean; #IMPLIED> -<!ATTLIST style:properties svg:stroke-opacity %floatOrPercentage; #IMPLIED> -<!ATTLIST style:properties svg:stroke-linejoin (miter|round|bevel|middle|none|inherit) #IMPLIED> - -<!-- text attributes --> -<!ATTLIST style:properties draw:auto-grow-width %boolean; #IMPLIED> -<!ATTLIST style:properties draw:auto-grow-height %boolean; #IMPLIED> -<!ATTLIST style:properties draw:fit-to-size %boolean; #IMPLIED> -<!ATTLIST style:properties draw:fit-to-contour %boolean; #IMPLIED> -<!ATTLIST style:properties draw:textarea-horizontal-align ( left | center | right | justify ) #IMPLIED> -<!ATTLIST style:properties draw:textarea-vertical-align ( top | middle | bottom | justify ) #IMPLIED> -<!ATTLIST style:properties draw:writing-mode (lr-tb|tb-rl) "lr-tb"> - -<!-- fill attributes --> -<!ATTLIST style:properties draw:fill (none|solid|bitmap|gradient|hatch) #IMPLIED> -<!ATTLIST style:properties draw:fill-color %color; #IMPLIED> -<!ATTLIST style:properties draw:fill-gradient-name %styleName; #IMPLIED> -<!ATTLIST style:properties draw:gradient-step-count CDATA #IMPLIED> -<!ATTLIST style:properties draw:fill-hatch-name %styleName; #IMPLIED> -<!ATTLIST style:properties draw:fill-hatch-solid %boolean; #IMPLIED> -<!ATTLIST style:properties draw:fill-image-name %styleName; #IMPLIED> -<!ATTLIST style:properties style:repeat (no-repeat|repeat|stretch) #IMPLIED> -<!ATTLIST style:properties draw:fill-image-width %lengthOrPercentage; #IMPLIED> -<!ATTLIST style:properties draw:fill-image-height %lengthOrPercentage; #IMPLIED> -<!ATTLIST style:properties draw:fill-image-ref-point-x %percentage; #IMPLIED> -<!ATTLIST style:properties draw:fill-image-ref-point-y %percentage; #IMPLIED> -<!ATTLIST style:properties draw:fill-image-ref-point %rectanglePoint; #IMPLIED> -<!ATTLIST style:properties draw:tile-repeat-offset CDATA #IMPLIED> -<!ATTLIST style:properties draw:transparency %percentage; #IMPLIED> -<!ATTLIST style:properties draw:transparency-name %styleName; #IMPLIED> - -<!-- graphic attributes --> -<!ATTLIST style:properties draw:color-mode (greyscale|mono|watermark|standard) #IMPLIED> -<!ATTLIST style:properties draw:luminance %percentage; #IMPLIED> -<!ATTLIST style:properties draw:contrast %percentage; #IMPLIED> -<!ATTLIST style:properties draw:gamma %percentage; #IMPLIED> -<!ATTLIST style:properties draw:red %percentage; #IMPLIED> -<!ATTLIST style:properties draw:green %percentage; #IMPLIED> -<!ATTLIST style:properties draw:blue %percentage; #IMPLIED> -<!ATTLIST style:properties draw:color-inversion %boolean; #IMPLIED> -<!ATTLIST style:properties draw:mirror %boolean; #IMPLIED> - -<!-- shadow attributes --> -<!ATTLIST style:properties draw:shadow (visible|hidden) #IMPLIED> -<!ATTLIST style:properties draw:shadow-offset-x %length; #IMPLIED> -<!ATTLIST style:properties draw:shadow-offset-y %length; #IMPLIED> -<!ATTLIST style:properties draw:shadow-color %color; #IMPLIED> -<!ATTLIST style:properties draw:shadow-transparency CDATA #IMPLIED> - -<!-- connector attributes --> -<!ATTLIST style:properties draw:start-line-spacing-horizontal %distance; #IMPLIED> -<!ATTLIST style:properties draw:start-line-spacing-vertical %distance; #IMPLIED> -<!ATTLIST style:properties draw:end-line-spacing-horizontal %distance; #IMPLIED> -<!ATTLIST style:properties draw:end-line-spacing-vertical %distance; #IMPLIED> - -<!-- measure attributes --> -<!ATTLIST style:properties draw:line-distance %distance; #IMPLIED> -<!ATTLIST style:properties draw:guide-overhang %distance; #IMPLIED> -<!ATTLIST style:properties draw:guide-distance %distance; #IMPLIED> -<!ATTLIST style:properties draw:start-guide %distance; #IMPLIED> -<!ATTLIST style:properties draw:end-guide %distance; #IMPLIED> -<!ATTLIST style:properties draw:measure-align (automatic|left-outside|inside|right-outside) #IMPLIED> -<!ATTLIST style:properties draw:measure-vertical-align (automatic|above|below|center) #IMPLIED> -<!ATTLIST style:properties draw:unit (automatic|mm|cm|m|km|pt|pc|inch|ft|mi) #IMPLIED> -<!ATTLIST style:properties draw:show-unit %boolean; #IMPLIED> -<!ATTLIST style:properties draw:placing (below|above) #IMPLIED> -<!ATTLIST style:properties draw:parallel %boolean; #IMPLIED> -<!ATTLIST style:properties draw:decimal-places %nonNegativeLength; #IMPLIED> - -<!-- frame attributes --> -<!ATTLIST style:properties draw:frame-display-scrollbar %boolean; #IMPLIED> -<!ATTLIST style:properties draw:frame-display-border %boolean; #IMPLIED> -<!ATTLIST style:properties draw:frame-margin-horizontal %nonNegativePixelLength; #IMPLIED> -<!ATTLIST style:properties draw:frame-margin-vertical %nonNegativePixelLength; #IMPLIED> -<!ATTLIST style:properties draw:size-protect %boolean; #IMPLIED> -<!ATTLIST style:properties draw:move-protect %boolean; #IMPLIED> - -<!-- ole object attributes --> -<!ATTLIST style:properties draw:visible-area-left %nonNegativeLength; #IMPLIED> -<!ATTLIST style:properties draw:visible-area-top %nonNegativeLength; #IMPLIED> -<!ATTLIST style:properties draw:visible-area-width %positiveLength; #IMPLIED> -<!ATTLIST style:properties draw:visible-area-height %positiveLength; #IMPLIED> - -<!-- fontwork attributes --> -<!ATTLIST style:properties draw:fontwork-style (rotate|upright|slant-x|slant-y|none) #IMPLIED> -<!ATTLIST style:properties draw:fontwork-adjust (left|right|autosize|center) #IMPLIED> -<!ATTLIST style:properties draw:fontwork-distance %distance; #IMPLIED> -<!ATTLIST style:properties draw:fontwork-start %distance; #IMPLIED> -<!ATTLIST style:properties draw:fontwork-mirror %boolean; #IMPLIED> -<!ATTLIST style:properties draw:fontwork-outline %boolean; #IMPLIED> -<!ATTLIST style:properties draw:fontwork-shadow (normal|slant|none) #IMPLIED> -<!ATTLIST style:properties draw:fontwork-shadow-color %color; #IMPLIED> -<!ATTLIST style:properties draw:fontwork-shadow-offset-x %distance; #IMPLIED> -<!ATTLIST style:properties draw:fontwork-shadow-offset-y %distance; #IMPLIED> -<!ATTLIST style:properties draw:fontwork-form (none|top-circle|bottom-circle|left-circle|right-circle|top-arc|bottom-arc|left-arc|right-arc|button1|button2|button3|button4) #IMPLIED> -<!ATTLIST style:properties draw:fontwork-hide-form %boolean; #IMPLIED> -<!ATTLIST style:properties draw:fontwork-shadow-transparence %percentage; #IMPLIED> - -<!-- caption attributes --> -<!ATTLIST style:properties draw:caption-type (straight-line|angled-line|angled-connector-line) #IMPLIED> -<!ATTLIST style:properties draw:caption-angle-type (fixed|free) #IMPLIED> -<!ATTLIST style:properties draw:caption-angle %nonNegativeInteger; #IMPLIED> -<!ATTLIST style:properties draw:caption-gap %distance; #IMPLIED> -<!ATTLIST style:properties draw:caption-escape-direction (horizontal|vertical|auto) #IMPLIED> -<!ATTLIST style:properties draw:caption-escape %lengthOrPercentage; #IMPLIED> -<!ATTLIST style:properties draw:caption-line-length %distance; #IMPLIED> -<!ATTLIST style:properties draw:caption-fit-line-length %boolean; #IMPLIED> - -<!-- Animations --> -<!ELEMENT presentation:sound EMPTY> -<!ATTLIST presentation:sound xlink:href %uriReference; #REQUIRED> -<!ATTLIST presentation:sound xlink:type (simple) #FIXED "simple"> -<!ATTLIST presentation:sound xlink:show (new|replace) #IMPLIED> -<!ATTLIST presentation:sound xlink:actuate (onRequest) "onRequest"> -<!ATTLIST presentation:sound presentation:play-full %boolean; #IMPLIED> - -<!ELEMENT presentation:show-shape (presentation:sound)?> -<!ATTLIST presentation:show-shape draw:shape-id CDATA #REQUIRED> -<!ATTLIST presentation:show-shape presentation:effect %presentationEffects; "none"> -<!ATTLIST presentation:show-shape presentation:direction %presentationEffectDirections; "none"> -<!ATTLIST presentation:show-shape presentation:speed %presentationSpeeds; "medium"> -<!ATTLIST presentation:show-shape presentation:start-scale %percentage; "100%"> -<!ATTLIST presentation:show-shape presentation:path-id CDATA #IMPLIED > - -<!ELEMENT presentation:show-text (presentation:sound)?> -<!ATTLIST presentation:show-text draw:shape-id CDATA #REQUIRED> -<!ATTLIST presentation:show-text presentation:effect %presentationEffects; "none"> -<!ATTLIST presentation:show-text presentation:direction %presentationEffectDirections; "none"> -<!ATTLIST presentation:show-text presentation:speed %presentationSpeeds; "medium"> -<!ATTLIST presentation:show-text presentation:start-scale %percentage; "100%"> -<!ATTLIST presentation:show-text presentation:path-id CDATA #IMPLIED > - -<!ELEMENT presentation:hide-shape (presentation:sound)?> -<!ATTLIST presentation:hide-shape draw:shape-id CDATA #REQUIRED> -<!ATTLIST presentation:hide-shape presentation:effect %presentationEffects; "none"> -<!ATTLIST presentation:hide-shape presentation:direction %presentationEffectDirections; "none"> -<!ATTLIST presentation:hide-shape presentation:speed %presentationSpeeds; "medium"> -<!ATTLIST presentation:hide-shape presentation:start-scale %percentage; "100%"> -<!ATTLIST presentation:hide-shape presentation:path-id CDATA #IMPLIED > - -<!ELEMENT presentation:hide-text (presentation:sound)?> -<!ATTLIST presentation:hide-text draw:shape-id CDATA #REQUIRED> -<!ATTLIST presentation:hide-text presentation:effect %presentationEffects; "none"> -<!ATTLIST presentation:hide-text presentation:direction %presentationEffectDirections; "none"> -<!ATTLIST presentation:hide-text presentation:speed %presentationSpeeds; "medium"> -<!ATTLIST presentation:hide-text presentation:start-scale %percentage; "100%"> -<!ATTLIST presentation:hide-text presentation:path-id CDATA #IMPLIED > - -<!ELEMENT presentation:dim (presentation:sound)?> -<!ATTLIST presentation:dim draw:shape-id CDATA #REQUIRED> -<!ATTLIST presentation:dim draw:color %color; #REQUIRED> - -<!ELEMENT presentation:play EMPTY> -<!ATTLIST presentation:play draw:shape-id CDATA #REQUIRED> -<!ATTLIST presentation:play presentation:speed %presentationSpeeds; "medium"> - -<!ELEMENT presentation:animations (presentation:show-shape|presentation:show-text|presentation:hide-shape|presentation:hide-text|presentation:dim|presentation:play)*> - -<!ELEMENT presentation:show EMPTY> -<!ATTLIST presentation:show presentation:name %styleName; #REQUIRED> -<!ATTLIST presentation:show presentation:pages CDATA #REQUIRED> - -<!ELEMENT presentation:settings (presentation:show)*> -<!ATTLIST presentation:settings presentation:start-page %styleName; #IMPLIED> -<!ATTLIST presentation:settings presentation:show %styleName; #IMPLIED> -<!ATTLIST presentation:settings presentation:full-screen %boolean; "true"> -<!ATTLIST presentation:settings presentation:endless %boolean; "false"> -<!ATTLIST presentation:settings presentation:pause %timeDuration; #IMPLIED> -<!ATTLIST presentation:settings presentation:show-logo %boolean; "false"> -<!ATTLIST presentation:settings presentation:force-manual %boolean; "false"> -<!ATTLIST presentation:settings presentation:mouse-visible %boolean; "true"> -<!ATTLIST presentation:settings presentation:mouse-as-pen %boolean; "false"> -<!ATTLIST presentation:settings presentation:start-with-navigator %boolean; "false"> -<!ATTLIST presentation:settings presentation:animations (enabled|disabled) "enabled"> -<!ATTLIST presentation:settings presentation:stay-on-top %boolean; "false"> -<!ATTLIST presentation:settings presentation:transition-on-click (enabled|disabled) "enabled"> - -<!-- Drawing page --> -<!ELEMENT draw:page (office:forms?,(%shapes;)*,presentation:animations?,presentation:notes?)> -<!ATTLIST draw:page draw:name %string; #IMPLIED> -<!ATTLIST draw:page draw:style-name %styleName; #IMPLIED> -<!ATTLIST draw:page draw:master-page-name %styleName; #REQUIRED> -<!ATTLIST draw:page presentation:presentation-page-layout-name %styleName; #IMPLIED> -<!ATTLIST draw:page draw:id %nonNegativeInteger; #IMPLIED> -<!ATTLIST draw:page xlink:href %uriReference; #IMPLIED> -<!ATTLIST draw:page xlink:type (simple) #IMPLIED> -<!ATTLIST draw:page xlink:show (replace) #IMPLIED> -<!ATTLIST draw:page xlink:actuate (onRequest) #IMPLIED> - -<!-- Presentation notes --> -<!ELEMENT presentation:notes (%shapes;)*> -<!ATTLIST presentation:notes style:page-master-name %styleName; #IMPLIED> - -<!-- presentation page layouts --> -<!ELEMENT style:presentation-page-layout (presentation:placeholder)* > -<!ATTLIST style:presentation-page-layout style:name %styleName; #REQUIRED> -<!ELEMENT presentation:placeholder EMPTY > -<!ATTLIST presentation:placeholder presentation:object (title|outline|subtitle|text|graphic|object|chart|orgchart|page|notes|handout) #REQUIRED> -<!ATTLIST presentation:placeholder svg:x %coordinateOrPercentage; #REQUIRED> -<!ATTLIST presentation:placeholder svg:y %coordinateOrPercentage; #REQUIRED> -<!ATTLIST presentation:placeholder svg:width %lengthOrPercentage; #REQUIRED> -<!ATTLIST presentation:placeholder svg:height %lengthOrPercentage; #REQUIRED> - -<!-- presentation page attributes --> -<!ATTLIST style:properties presentation:transition-type (manual|automatic|semi-automatic) #IMPLIED > -<!ATTLIST style:properties presentation:transition-style (none|fade-from-left|fade-from-top|fade-from-right|fade-from-bottom|fade-to-center|fade-from-center|move-from-left|move-from-top|move-from-right|move-from-bottom|roll-from-top|roll-from-left|roll-from-right|roll-from-bottom|vertical-stripes|horizontal-stripes|clockwise|counterclockwise|fade-from-upperleft|fade-from-upperright|fade-from-lowerleft|fade-from-lowerright|close-vertical|close-horizontal|open-vertical|open-horizontal|spiralin-left|spiralin-right|spiralout-left|spiralout-right|dissolve|wavyline-from-left|wavyline-from-top|wavyline-from-right|wavyline-from-bottom|random|stretch-from-left|stretch-from-top|stretch-from-right|stretch-from-bottom|vertical-lines|horizontal-lines) #IMPLIED > -<!ATTLIST style:properties presentation:transition-speed %presentationSpeeds; #IMPLIED > -<!ATTLIST style:properties presentation:duration %timeDuration; #IMPLIED> -<!ATTLIST style:properties presentation:visibility (visible|hidden) #IMPLIED> -<!ATTLIST style:properties draw:background-size (full|border) #IMPLIED> -<!ATTLIST style:properties presentation:background-objects-visible %boolean; #IMPLIED> -<!ATTLIST style:properties presentation:background-visible %boolean; #IMPLIED> - - -<!-- text boxes --> -<!ELEMENT draw:text-box (office:events?,draw:image-map?, - %sectionText;)> -<!ATTLIST draw:text-box %draw-style-name;> -<!ATTLIST draw:text-box %draw-transform; > -<!ATTLIST draw:text-box draw:name %string; #IMPLIED> -<!ATTLIST draw:text-box draw:chain-next-name %string; #IMPLIED> - -<!ATTLIST draw:text-box %text-anchor;> -<!ATTLIST draw:text-box %draw-position;> -<!ATTLIST draw:text-box %draw-end-position; > -<!ATTLIST draw:text-box %table-background; > -<!ATTLIST draw:text-box svg:width %lengthOrPercentage; #IMPLIED> -<!ATTLIST draw:text-box svg:height %lengthOrPercentage; #IMPLIED> -<!ATTLIST draw:text-box style:rel-width %percentage; #IMPLIED> -<!ATTLIST draw:text-box style:rel-height %percentage; #IMPLIED> -<!ATTLIST draw:text-box fo:min-height %lengthOrPercentage; #IMPLIED> -<!ATTLIST draw:text-box %zindex;> -<!ATTLIST draw:text-box %presentation-class; > -<!ATTLIST draw:text-box draw:id %draw-shape-id;> -<!ATTLIST draw:text-box draw:layer %layerName; #IMPLIED> -<!ATTLIST draw:text-box draw:corner-radius %nonNegativeLength; #IMPLIED> - -<!-- image --> -<!ELEMENT draw:image (office:binary-data?,office:events?,draw:image-map?,svg:desc?,(draw:contour-polygon|draw:contour-path)?)> -<!ATTLIST draw:image %draw-transform; > -<!ATTLIST draw:image %draw-style-name;> -<!ATTLIST draw:image draw:name %string; #IMPLIED> -<!ATTLIST draw:image xlink:href %uriReference; #IMPLIED> -<!ATTLIST draw:image xlink:type (simple) #IMPLIED> -<!ATTLIST draw:image xlink:show (embed) #IMPLIED> -<!ATTLIST draw:image xlink:actuate (onLoad) #IMPLIED> -<!ATTLIST draw:image draw:filter-name %string; #IMPLIED> -<!ATTLIST draw:image %text-anchor;> -<!ATTLIST draw:image %draw-position;> -<!ATTLIST draw:image %draw-end-position; > -<!ATTLIST draw:image %table-background; > -<!ATTLIST draw:image svg:width %lengthOrPercentage; #IMPLIED> -<!ATTLIST draw:image svg:height %lengthOrPercentage; #IMPLIED> -<!ATTLIST draw:image %presentation-class; > -<!ATTLIST draw:image %zindex;> -<!ATTLIST draw:image draw:id %draw-shape-id;> -<!ATTLIST draw:image draw:layer %layerName; #IMPLIED> -<!ATTLIST draw:image style:rel-width %percentage; #IMPLIED> -<!ATTLIST draw:image style:rel-height %percentage; #IMPLIED> - -<!-- objects --> -<!ELEMENT draw:thumbnail EMPTY> -<!ATTLIST draw:thumbnail xlink:href %uriReference; #REQUIRED> -<!ATTLIST draw:thumbnail xlink:type (simple) #IMPLIED> -<!ATTLIST draw:thumbnail xlink:show (embed) #IMPLIED> -<!ATTLIST draw:thumbnail xlink:actuate (onLoad) #IMPLIED> - -<!ELEMENT math:math ANY> <!-- dummy (we have no MathML DTD currently)--> -<!ELEMENT draw:object (draw:thumbnail?,(office:document|math:math)?,office:events?, draw:image-map?, svg:desc?,(draw:contour-polygon|draw:contour-path)?)> -<!ATTLIST draw:object %draw-style-name;> -<!ATTLIST draw:object draw:name %string; #IMPLIED> -<!ATTLIST draw:object xlink:href %uriReference; #IMPLIED> -<!ATTLIST draw:object xlink:type (simple) #IMPLIED> -<!ATTLIST draw:object xlink:show (embed) #IMPLIED> -<!ATTLIST draw:object xlink:actuate (onLoad) #IMPLIED> -<!ATTLIST draw:object %text-anchor;> -<!ATTLIST draw:object %draw-position;> -<!ATTLIST draw:object %draw-end-position; > -<!ATTLIST draw:object %table-background; > -<!ATTLIST draw:object svg:width %lengthOrPercentage; #IMPLIED> -<!ATTLIST draw:object svg:height %lengthOrPercentage; #IMPLIED> -<!ATTLIST draw:object %presentation-class; > -<!ATTLIST draw:object %zindex;> -<!ATTLIST draw:object draw:id %draw-shape-id;> -<!ATTLIST draw:object draw:layer %layerName; #IMPLIED> -<!ATTLIST draw:object draw:notify-on-update-of-ranges %string; #IMPLIED> -<!ATTLIST draw:object style:rel-width %percentage; #IMPLIED> -<!ATTLIST draw:object style:rel-height %percentage; #IMPLIED> - -<!ELEMENT draw:object-ole (office:binary-data?|office:events?|draw:image-map?|svg:desc?|draw:contour-polygon?|draw:contour-path?|draw:thumbnail?)> -<!ATTLIST draw:object-ole draw:class-id CDATA #IMPLIED> -<!ATTLIST draw:object-ole %draw-style-name;> -<!ATTLIST draw:object-ole draw:name %string; #IMPLIED> -<!ATTLIST draw:object-ole xlink:href %uriReference; #IMPLIED> -<!ATTLIST draw:object-ole xlink:type (simple) #IMPLIED> -<!ATTLIST draw:object-ole xlink:show (embed) #IMPLIED> -<!ATTLIST draw:object-ole xlink:actuate (onLoad) #IMPLIED> -<!ATTLIST draw:object-ole %text-anchor;> -<!ATTLIST draw:object-ole %draw-position;> -<!ATTLIST draw:object-ole %draw-end-position; > -<!ATTLIST draw:object-ole %table-background; > -<!ATTLIST draw:object-ole svg:width %lengthOrPercentage; #IMPLIED> -<!ATTLIST draw:object-ole svg:height %lengthOrPercentage; #IMPLIED> -<!ATTLIST draw:object-ole %presentation-class; > -<!ATTLIST draw:object-ole %zindex;> -<!ATTLIST draw:object-ole draw:id %draw-shape-id;> -<!ATTLIST draw:object-ole draw:layer %layerName; #IMPLIED> -<!ATTLIST draw:object-ole style:rel-width %percentage; #IMPLIED> -<!ATTLIST draw:object-ole style:rel-height %percentage; #IMPLIED> - -<!ELEMENT svg:desc (#PCDATA)> - -<!ELEMENT draw:contour-polygon EMPTY> -<!ATTLIST draw:contour-polygon svg:width %coordinate; #REQUIRED> -<!ATTLIST draw:contour-polygon svg:height %coordinate; #REQUIRED> -<!ATTLIST draw:contour-polygon %draw-viewbox;> -<!ATTLIST draw:contour-polygon draw:points %points; #REQUIRED> -<!ATTLIST draw:contour-polygon draw:recreate-on-edit %boolean; #IMPLIED> - -<!ELEMENT draw:contour-path EMPTY> -<!ATTLIST draw:contour-path svg:width %coordinate; #REQUIRED> -<!ATTLIST draw:contour-path svg:height %coordinate; #REQUIRED> -<!ATTLIST draw:contour-path %draw-viewbox;> -<!ATTLIST draw:contour-path svg:d %pathData; #REQUIRED> -<!ATTLIST draw:contour-path draw:recreate-on-edit %boolean; #IMPLIED> - -<!-- hyperlink --> -<!ELEMENT draw:a (draw:image|draw:text-box)> -<!ATTLIST draw:a xlink:href %uriReference; #REQUIRED> -<!ATTLIST draw:a xlink:type (simple) #FIXED "simple"> -<!ATTLIST draw:a xlink:show (new|replace) #IMPLIED> -<!ATTLIST draw:a xlink:actuate (onRequest) "onRequest"> -<!ATTLIST draw:a office:name %string; #IMPLIED> -<!ATTLIST draw:a office:target-frame-name %string; #IMPLIED> -<!ATTLIST draw:a office:server-map %boolean; "false"> - -<!-- 3d properties --> -<!ATTLIST style:properties dr3d:horizontal-segments %nonNegativeInteger; #IMPLIED> -<!ATTLIST style:properties dr3d:vertical-segments %nonNegativeInteger; #IMPLIED> -<!ATTLIST style:properties dr3d:edge-rounding %percentage; #IMPLIED> -<!ATTLIST style:properties dr3d:edge-rounding-mode (correct|attractive) #IMPLIED> -<!ATTLIST style:properties dr3d:back-scale %percentage; #IMPLIED> -<!ATTLIST style:properties dr3d:end-angle %nonNegativeInteger; #IMPLIED> -<!ATTLIST style:properties dr3d:depth %length; #IMPLIED> -<!ATTLIST style:properties dr3d:backface-culling (enabled|disabled) #IMPLIED> -<!ATTLIST style:properties dr3d:lighting-mode (standard|double-sided) #IMPLIED> -<!ATTLIST style:properties dr3d:normals-kind (object|flat|sphere) #IMPLIED> -<!ATTLIST style:properties dr3d:normals-direction (normal|inverse) #IMPLIED> -<!ATTLIST style:properties dr3d:texture-generation-mode-x (object|parallel|sphere) #IMPLIED> -<!ATTLIST style:properties dr3d:texture-generation-mode-y (object|parallel|sphere) #IMPLIED> -<!ATTLIST style:properties dr3d:texture-kind (luminance|intesity|color) #IMPLIED> -<!ATTLIST style:properties dr3d:texture-filter (enabled|disabled) #IMPLIED> -<!ATTLIST style:properties dr3d:texture-mode (replace|modulate|blend) #IMPLIED> -<!ATTLIST style:properties dr3d:ambient-color %color; #IMPLIED> -<!ATTLIST style:properties dr3d:emissive-color %color; #IMPLIED> -<!ATTLIST style:properties dr3d:specular-color %color; #IMPLIED> -<!ATTLIST style:properties dr3d:diffuse-color %color; #IMPLIED> -<!ATTLIST style:properties dr3d:shininess %percentage; #IMPLIED> -<!ATTLIST style:properties dr3d:shadow (visible|hidden) #IMPLIED> - -<!ELEMENT dr3d:light EMPTY> -<!ATTLIST dr3d:light dr3d:diffuse-color %color; #IMPLIED> -<!ATTLIST dr3d:light dr3d:direction %vector3D; #REQUIRED> -<!ATTLIST dr3d:light dr3d:enabled %boolean; #IMPLIED> -<!ATTLIST dr3d:light dr3d:specular %boolean; #IMPLIED> - -<!ENTITY % shapes3d "(dr3d:scene|dr3d:extrude|dr3d:sphere|dr3d:rotate|dr3d:cube)"> - -<!ELEMENT dr3d:cube EMPTY> -<!ATTLIST dr3d:cube dr3d:transform CDATA #IMPLIED> -<!ATTLIST dr3d:cube dr3d:min-edge %vector3D; #IMPLIED> -<!ATTLIST dr3d:cube dr3d:max-edge %vector3D; #IMPLIED> -<!ATTLIST dr3d:cube %zindex;> -<!ATTLIST dr3d:cube draw:id %draw-shape-id;> -<!ATTLIST dr3d:cube %draw-end-position; > -<!ATTLIST dr3d:cube %table-background; > -<!ATTLIST dr3d:cube %draw-style-name; > -<!ATTLIST dr3d:cube draw:layer %layerName; #IMPLIED> - -<!ELEMENT dr3d:sphere EMPTY> -<!ATTLIST dr3d:sphere dr3d:transform CDATA #IMPLIED> -<!ATTLIST dr3d:sphere dr3d:center %vector3D; #IMPLIED> -<!ATTLIST dr3d:sphere dr3d:size %vector3D; #IMPLIED> -<!ATTLIST dr3d:sphere %zindex;> -<!ATTLIST dr3d:sphere draw:id %draw-shape-id;> -<!ATTLIST dr3d:sphere %draw-end-position; > -<!ATTLIST dr3d:sphere %table-background; > -<!ATTLIST dr3d:sphere %draw-style-name; > -<!ATTLIST dr3d:sphere draw:layer %layerName; #IMPLIED> - -<!ELEMENT dr3d:extrude EMPTY> -<!ATTLIST dr3d:extrude dr3d:transform CDATA #IMPLIED> -<!ATTLIST dr3d:extrude %draw-viewbox;> -<!ATTLIST dr3d:extrude svg:d %pathData; #REQUIRED > -<!ATTLIST dr3d:extrude %zindex;> -<!ATTLIST dr3d:extrude draw:id %draw-shape-id;> -<!ATTLIST dr3d:extrude %draw-end-position; > -<!ATTLIST dr3d:extrude %table-background; > -<!ATTLIST dr3d:extrude %draw-style-name; > -<!ATTLIST dr3d:extrude draw:layer %layerName; #IMPLIED> - -<!ELEMENT dr3d:rotate EMPTY> -<!ATTLIST dr3d:rotate dr3d:transform CDATA #IMPLIED> -<!ATTLIST dr3d:rotate %draw-viewbox;> -<!ATTLIST dr3d:rotate svg:d %pathData; #REQUIRED > -<!ATTLIST dr3d:rotate %zindex;> -<!ATTLIST dr3d:rotate draw:id %draw-shape-id;> -<!ATTLIST dr3d:rotate %draw-end-position; > -<!ATTLIST dr3d:rotate %table-background; > -<!ATTLIST dr3d:rotate %draw-style-name; > -<!ATTLIST dr3d:rotate draw:layer %layerName; #IMPLIED> - -<!ELEMENT dr3d:scene (dr3d:light*,(%shapes3d;)*)> -<!ATTLIST dr3d:scene %draw-style-name; > -<!ATTLIST dr3d:scene svg:x %coordinate; #IMPLIED> -<!ATTLIST dr3d:scene svg:y %coordinate; #IMPLIED> -<!ATTLIST dr3d:scene svg:width %length; #IMPLIED> -<!ATTLIST dr3d:scene svg:height %length; #IMPLIED> -<!ATTLIST dr3d:scene dr3d:vrp %vector3D; #IMPLIED> -<!ATTLIST dr3d:scene dr3d:vpn %vector3D; #IMPLIED> -<!ATTLIST dr3d:scene dr3d:vup %vector3D; #IMPLIED> -<!ATTLIST dr3d:scene dr3d:projection (parallel|perspective) #IMPLIED> -<!ATTLIST dr3d:scene dr3d:transform CDATA #IMPLIED> -<!ATTLIST dr3d:scene dr3d:distance %length; #IMPLIED> -<!ATTLIST dr3d:scene dr3d:focal-length %length; #IMPLIED> -<!ATTLIST dr3d:scene dr3d:shadow-slant %nonNegativeInteger; #IMPLIED> -<!ATTLIST dr3d:scene dr3d:shade-mode (flat|phong|gouraud|draft) #IMPLIED> -<!ATTLIST dr3d:scene dr3d:ambient-color %color; #IMPLIED> -<!ATTLIST dr3d:scene dr3d:lighting-mode %boolean; #IMPLIED> -<!ATTLIST dr3d:scene %zindex;> -<!ATTLIST dr3d:scene draw:id %draw-shape-id;> -<!ATTLIST dr3d:scene %draw-end-position; > -<!ATTLIST dr3d:scene %table-background; > - -<!-- layer --> - -<!ELEMENT draw:layer-set (draw:layer*)> - -<!ELEMENT draw:layer EMPTY> -<!ATTLIST draw:layer draw:name %layerName; #REQUIRED> - -<!-- events --> -<!ELEMENT presentation:event (presentation:sound)?> -<!ATTLIST presentation:event %event-name;> -<!ATTLIST presentation:event presentation:action (none|previous-page|next-page|first-page|last-page|hide|stop|execute|show|verb|fade-out|sound) #REQUIRED> -<!ATTLIST presentation:event presentation:effect %presentationEffects; "none"> -<!ATTLIST presentation:event presentation:direction %presentationEffectDirections; "none"> -<!ATTLIST presentation:event presentation:speed %presentationSpeeds; "medium"> -<!ATTLIST presentation:event presentation:start-scale %percentage; "100%"> -<!ATTLIST presentation:event xlink:href %uriReference; #IMPLIED> -<!ATTLIST presentation:event xlink:type (simple) #IMPLIED> -<!ATTLIST presentation:event xlink:show (embed) #IMPLIED> -<!ATTLIST presentation:event xlink:actuate (onRequest) #IMPLIED> -<!ATTLIST presentation:event presentation:verb %nonNegativeInteger; #IMPLIED> - -<!-- applets --> -<!ELEMENT draw:applet (draw:thumbnail?, draw:param*, svg:desc?)> -<!ATTLIST draw:applet xlink:href %uriReference; #IMPLIED> -<!ATTLIST draw:applet xlink:type (simple) #IMPLIED> -<!ATTLIST draw:applet xlink:show (embed) #IMPLIED> -<!ATTLIST draw:applet xlink:actuate (onLoad) #IMPLIED> -<!ATTLIST draw:applet draw:code CDATA #REQUIRED> -<!ATTLIST draw:applet draw:object CDATA #IMPLIED> -<!ATTLIST draw:applet draw:archive CDATA #IMPLIED> -<!ATTLIST draw:applet draw:may-script %boolean; "false"> -<!ATTLIST draw:applet draw:name CDATA #IMPLIED> -<!ATTLIST draw:applet %draw-style-name;> -<!ATTLIST draw:applet svg:width %lengthOrPercentage; #IMPLIED> -<!ATTLIST draw:applet svg:height %lengthOrPercentage; #IMPLIED> -<!ATTLIST draw:applet %zindex;> -<!ATTLIST draw:applet draw:layer %layerName; #IMPLIED> -<!ATTLIST draw:applet %draw-position;> -<!ATTLIST draw:applet %draw-end-position; > - -<!-- plugins --> -<!ELEMENT draw:plugin (draw:thumbnail?, draw:param*, svg:desc?)> -<!ATTLIST draw:plugin xlink:href %uriReference; #IMPLIED> -<!ATTLIST draw:plugin xlink:type (simple) #IMPLIED> -<!ATTLIST draw:plugin xlink:show (embed) #IMPLIED> -<!ATTLIST draw:plugin xlink:actuate (onLoad) #IMPLIED> -<!ATTLIST draw:plugin draw:mime-type CDATA #IMPLIED> -<!ATTLIST draw:plugin draw:name CDATA #IMPLIED> -<!ATTLIST draw:plugin %draw-style-name;> -<!ATTLIST draw:plugin svg:width %lengthOrPercentage; #IMPLIED> -<!ATTLIST draw:plugin svg:height %lengthOrPercentage; #IMPLIED> -<!ATTLIST draw:plugin %zindex;> -<!ATTLIST draw:plugin draw:layer %layerName; #IMPLIED> -<!ATTLIST draw:plugin %draw-position;> -<!ATTLIST draw:plugin %draw-end-position; > - -<!-- Paramaters --> -<!ELEMENT draw:param EMPTY> -<!ATTLIST draw:param draw:name CDATA #IMPLIED> -<!ATTLIST draw:param draw:value CDATA #IMPLIED> - -<!-- Floating Frames --> -<!ELEMENT draw:floating-frame (draw:thumbnail?, svg:desc?)> -<!ATTLIST draw:floating-frame xlink:href %uriReference; #IMPLIED> -<!ATTLIST draw:floating-frame xlink:type (simple) #IMPLIED> -<!ATTLIST draw:floating-frame xlink:show (embed) #IMPLIED> -<!ATTLIST draw:floating-frame xlink:actuate (onLoad) #IMPLIED> -<!ATTLIST draw:floating-frame draw:name CDATA #IMPLIED> -<!ATTLIST draw:floating-frame draw:frame-name CDATA #IMPLIED> -<!ATTLIST draw:floating-frame %draw-style-name;> -<!ATTLIST draw:floating-frame svg:width %lengthOrPercentage; #IMPLIED> -<!ATTLIST draw:floating-frame svg:height %lengthOrPercentage; #IMPLIED> -<!ATTLIST draw:floating-frame %zindex;> -<!ATTLIST draw:floating-frame draw:layer %layerName; #IMPLIED> -<!ATTLIST draw:floating-frame %draw-position;> -<!ATTLIST draw:floating-frame %draw-end-position; > - -<!-- Image Maps --> -<!ELEMENT draw:image-map - (draw:area-rectangle|draw:area-circle|draw:area-polygon)*> - -<!ELEMENT draw:area-rectangle (svg:desc?,office:events?)> -<!ATTLIST draw:area-rectangle xlink:href %uriReference; #IMPLIED> -<!ATTLIST draw:area-rectangle xlink:type (simple) #IMPLIED> -<!ATTLIST draw:area-rectangle office:target-frame-name CDATA #IMPLIED> -<!ATTLIST draw:area-rectangle xlink:show (new|replace) #IMPLIED> -<!ATTLIST draw:area-rectangle office:name CDATA #IMPLIED> -<!ATTLIST draw:area-rectangle draw:nohref (nohref) #IMPLIED> -<!ATTLIST draw:area-rectangle svg:x %coordinate; #REQUIRED> -<!ATTLIST draw:area-rectangle svg:y %coordinate; #REQUIRED> -<!ATTLIST draw:area-rectangle svg:width %coordinate; #REQUIRED> -<!ATTLIST draw:area-rectangle svg:height %coordinate; #REQUIRED> - -<!ELEMENT draw:area-circle (svg:desc?,office:events?)> -<!ATTLIST draw:area-circle xlink:href %uriReference; #IMPLIED> -<!ATTLIST draw:area-circle xlink:type (simple) #IMPLIED> -<!ATTLIST draw:area-circle office:target-frame-name CDATA #IMPLIED> -<!ATTLIST draw:area-circle xlink:show (new|replace) #IMPLIED> -<!ATTLIST draw:area-circle office:name CDATA #IMPLIED> -<!ATTLIST draw:area-circle draw:nohref (nohref) #IMPLIED> -<!ATTLIST draw:area-circle svg:cx %coordinate; #REQUIRED> -<!ATTLIST draw:area-circle svg:cy %coordinate; #REQUIRED> -<!ATTLIST draw:area-circle svg:r %coordinate; #REQUIRED> - -<!ELEMENT draw:area-polygon (svg:desc?,office:events?)> -<!ATTLIST draw:area-polygon xlink:href %uriReference; #IMPLIED> -<!ATTLIST draw:area-polygon xlink:type (simple) #IMPLIED> -<!ATTLIST draw:area-polygon office:target-frame-name CDATA #IMPLIED> -<!ATTLIST draw:area-polygon xlink:show (new|replace) #IMPLIED> -<!ATTLIST draw:area-polygon office:name CDATA #IMPLIED> -<!ATTLIST draw:area-polygon draw:nohref (nohref) #IMPLIED> -<!ATTLIST draw:area-polygon svg:x %coordinate; #REQUIRED> -<!ATTLIST draw:area-polygon svg:y %coordinate; #REQUIRED> -<!ATTLIST draw:area-polygon svg:width %coordinate; #REQUIRED> -<!ATTLIST draw:area-polygon svg:height %coordinate; #REQUIRED> -<!ATTLIST draw:area-polygon svg:points %points; #REQUIRED> -<!ATTLIST draw:area-polygon svg:viewBox CDATA #REQUIRED> - -<!ENTITY % fields "text:date | - text:time | - text:page-number | - text:page-continuation | - text:sender-firstname | - text:sender-lastname | - text:sender-initials | - text:sender-title | - text:sender-position | - text:sender-email | - text:sender-phone-private | - text:sender-fax | - text:sender-company | - text:sender-phone-work | - text:sender-street | - text:sender-city | - text:sender-postal-code | - text:sender-country | - text:sender-state-or-province | - text:author-name | - text:author-initials | - text:placeholder | - text:variable-set | - text:variable-get | - text:variable-input | - text:user-field-get | - text:user-field-input | - text:sequence | - text:expression | - text:text-input | - text:database-display | - text:database-next | - text:database-row-select | - text:database-row-number | - text:database-name | - text:initial-creator | - text:creation-date | - text:creation-time | - text:description | - text:user-defined | - text:print-time | - text:print-date | - text:printed-by | - text:title | - text:subject | - text:keywords | - text:editing-cycles | - text:editing-duration | - text:modification-time | - text:modification-date | - text:creator | - text:conditional-text | - text:hidden-text | - text:hidden-paragraph | - text:chapter | - text:file-name | - text:template-name | - text:page-variable-set | - text:page-variable-get | - text:execute-macro | - text:dde-connection | - text:reference-ref | - text:sequence-ref | - text:bookmark-ref | - text:footnote-ref | - text:endnote-ref | - text:sheet-name | - text:bibliography-mark | - text:page-count | - text:paragraph-count | - text:word-count | - text:character-count | - text:table-count | - text:image-count | - text:object-count | - office:annotation | - text:script | - text:measure" > - -<!ENTITY % inline-text-elements " - text:span|text:tab-stop|text:s|text:line-break| - text:footnote|text:endnote|text:a| - text:bookmark|text:bookmark-start|text:bookmark-end| - text:reference-mark|text:reference-mark-start| - text:reference-mark-end|%fields;|%shape;| - text:toc-mark-start | text:toc-mark-end | - text:toc-mark | text:user-index-mark-start | - text:user-index-mark-end | text:user-index-mark | - text:alphabetical-index-mark-start | - text:alphabetical-index-mark-end | - text:alphabetical-index-mark | - %change-marks; | draw:a | text:ruby"> - -<!ENTITY % inline-text "( #PCDATA | %inline-text-elements; )*"> - -<!ELEMENT text:p %inline-text;> -<!ELEMENT text:h %inline-text;> - -<!ATTLIST text:p text:style-name %styleName; #IMPLIED> -<!ATTLIST text:p text:cond-style-name %styleName; #IMPLIED> - -<!ATTLIST text:h text:style-name %styleName; #IMPLIED> -<!ATTLIST text:h text:cond-style-name %styleName; #IMPLIED> -<!ATTLIST text:h text:level %positiveInteger; "1"> - -<!ELEMENT text:span %inline-text;> -<!ATTLIST text:span text:style-name %styleName; #REQUIRED> - -<!ELEMENT text:a (#PCDATA | office:events | %inline-text-elements;)*> -<!ATTLIST text:a xlink:href %uriReference; #REQUIRED> -<!ATTLIST text:a xlink:type (simple) #FIXED "simple"> -<!ATTLIST text:a xlink:actuate (onRequest) "onRequest"> -<!ATTLIST text:a xlink:show (new|replace) "replace"> -<!ATTLIST text:a office:name %string; #IMPLIED> -<!ATTLIST text:a office:target-frame-name %string; #IMPLIED> -<!ATTLIST text:a text:style-name %styleName; #IMPLIED> -<!ATTLIST text:a text:visited-style-name %styleName; #IMPLIED> - - -<!ELEMENT text:s EMPTY> -<!ATTLIST text:s text:c %positiveInteger; "1"> - -<!ELEMENT text:tab-stop EMPTY> - -<!ELEMENT text:line-break EMPTY> - - -<!ENTITY % list-items "((text:list-header,text:list-item*)|text:list-item+)"> -<!ELEMENT text:ordered-list %list-items;> -<!ELEMENT text:unordered-list %list-items;> - - -<!ATTLIST text:ordered-list text:style-name %styleName; #IMPLIED> -<!ATTLIST text:unordered-list text:style-name %styleName; #IMPLIED> - -<!ATTLIST text:ordered-list text:continue-numbering %boolean; "false"> - -<!ELEMENT text:list-header (text:p|text:h)+> -<!ELEMENT text:list-item (text:p|text:h|text:ordered-list|text:unordered-list)+> - -<!ATTLIST text:list-item text:restart-numbering %boolean; "false"> -<!ATTLIST text:list-item text:start-value %positiveInteger; #IMPLIED> - -<!ELEMENT text:list-style (text:list-level-style-number| - text:list-level-style-bullet| - text:list-level-style-image)+> - -<!ATTLIST text:list-style style:name %styleName; #IMPLIED> - -<!ATTLIST text:list-style text:consecutive-numbering %boolean; "false"> - - -<!ELEMENT text:list-level-style-number (style:properties?)> - -<!ATTLIST text:list-level-style-number text:level %positiveInteger; - #REQUIRED> -<!ATTLIST text:list-level-style-number text:style-name %styleName; #IMPLIED> - -<!ATTLIST text:list-level-style-number style:num-format %string; #REQUIRED> -<!ATTLIST text:list-level-style-number style:num-prefix %string; #IMPLIED> -<!ATTLIST text:list-level-style-number style:num-suffix %string; #IMPLIED> -<!ATTLIST text:list-level-style-number style:num-letter-sync %boolean; - "false"> -<!ATTLIST text:list-level-style-number text:display-levels %positiveInteger; - "1"> -<!ATTLIST text:list-level-style-number text:start-value %positiveInteger; - "1"> -<!ELEMENT text:list-level-style-bullet (style:properties?)> - -<!ATTLIST text:list-level-style-bullet text:level %positiveInteger; #REQUIRED> -<!ATTLIST text:list-level-style-bullet text:style-name %styleName; #IMPLIED> -<!ATTLIST text:list-level-style-bullet text:bullet-char %character; #REQUIRED> -<!ATTLIST text:list-level-style-bullet style:num-prefix %string; #IMPLIED> -<!ATTLIST text:list-level-style-bullet style:num-suffix %string; #IMPLIED> - -<!ELEMENT text:list-level-style-image (style:properties?,office:binary-data?)> - -<!ATTLIST text:list-level-style-image text:level %positiveInteger; #REQUIRED> -<!ATTLIST text:list-level-style-image xlink:type (simple) #IMPLIED> -<!ATTLIST text:list-level-style-image xlink:href %uriReference; #IMPLIED> -<!ATTLIST text:list-level-style-image xlink:actuate (onLoad) #IMPLIED> -<!ATTLIST text:list-level-style-image xlink:show (embed) #IMPLIED> - - -<!-- list properties --> -<!ATTLIST style:properties text:space-before %nonNegativeLength; #IMPLIED> -<!ATTLIST style:properties text:min-label-width %nonNegativeLength; #IMPLIED> -<!ATTLIST style:properties text:min-label-distance %nonNegativeLength; #IMPLIED> -<!ATTLIST style:properties text:enable-numbering %boolean; #IMPLIED> -<!ATTLIST style:properties style:list-style-name %styleName; #IMPLIED> - -<!ELEMENT text:outline-style (text:outline-level-style)+> - -<!ELEMENT text:outline-level-style (style:properties?)> - -<!ATTLIST text:outline-level-style text:level %positiveInteger; - #REQUIRED> -<!ATTLIST text:outline-level-style text:style-name %styleName; #IMPLIED> - -<!ATTLIST text:outline-level-style style:num-format %string; #REQUIRED> -<!ATTLIST text:outline-level-style style:num-prefix %string; #IMPLIED> -<!ATTLIST text:outline-level-style style:num-suffix %string; #IMPLIED> -<!ATTLIST text:outline-level-style style:num-letter-sync %boolean; - "false"> -<!ATTLIST text:outline-level-style text:display-levels %positiveInteger; - "1"> -<!ATTLIST text:outline-level-style text:start-value %positiveInteger; - "1"> - -<!ENTITY % field-declarations "text:variable-decls?, - text:user-field-decls?, - text:sequence-decls?"> - -<!ENTITY % variableName "CDATA"> - -<!ENTITY % formula "CDATA"> - -<!ENTITY % valueAttr "text:value-type %valueType; #IMPLIED - text:currency CDATA #IMPLIED" > - -<!ENTITY % valueAndTypeAttr "%valueAttr; - text:value %float; #IMPLIED - text:date-value %date; #IMPLIED - text:time-value %timeInstance; #IMPLIED - text:boolean-value %boolean; #IMPLIED - text:string-value %string; #IMPLIED" > - -<!ENTITY % numFormat 'style:num-format CDATA #IMPLIED - style:num-letter-sync %boolean; "false"'> - - -<!ELEMENT text:date (#PCDATA)> -<!ATTLIST text:date text:date-value %timeInstance; #IMPLIED> -<!ATTLIST text:date text:date-adjust %dateDuration; #IMPLIED> -<!ATTLIST text:date text:fixed %boolean; "false"> -<!ATTLIST text:date style:data-style-name %styleName; #IMPLIED> - -<!ELEMENT text:time (#PCDATA)> -<!ATTLIST text:time text:time-value %timeInstance; #IMPLIED> -<!ATTLIST text:time text:time-adjust %timeDuration; #IMPLIED> -<!ATTLIST text:time text:fixed %boolean; "false"> -<!ATTLIST text:time style:data-style-name %styleName; #IMPLIED> - -<!ELEMENT text:page-number (#PCDATA)> -<!ATTLIST text:page-number text:page-adjust %positiveInteger; #IMPLIED> -<!ATTLIST text:page-number text:select-page (previous|current|next) "current"> -<!ATTLIST text:page-number %numFormat;> - -<!ELEMENT text:page-continuation (#PCDATA)> -<!ATTLIST text:page-continuation text:select-page (previous|next) #REQUIRED> -<!ATTLIST text:page-continuation text:string-value %string; #IMPLIED> - -<!ELEMENT text:sender-firstname (#PCDATA)> -<!ATTLIST text:sender-firstname text:fixed %boolean; "true"> - -<!ELEMENT text:sender-lastname (#PCDATA)> -<!ATTLIST text:sender-lastname text:fixed %boolean; "true"> - -<!ELEMENT text:sender-initials (#PCDATA)> -<!ATTLIST text:sender-initials text:fixed %boolean; "true"> - -<!ELEMENT text:sender-title (#PCDATA)> -<!ATTLIST text:sender-title text:fixed %boolean; "true"> - -<!ELEMENT text:sender-position (#PCDATA)> -<!ATTLIST text:sender-position text:fixed %boolean; "true"> - -<!ELEMENT text:sender-email (#PCDATA)> -<!ATTLIST text:sender-email text:fixed %boolean; "true"> - -<!ELEMENT text:sender-phone-private (#PCDATA)> -<!ATTLIST text:sender-phone-private text:fixed %boolean; "true"> - -<!ELEMENT text:sender-fax (#PCDATA)> -<!ATTLIST text:sender-fax text:fixed %boolean; "true"> - -<!ELEMENT text:sender-company (#PCDATA)> -<!ATTLIST text:sender-company text:fixed %boolean; "true"> - -<!ELEMENT text:sender-phone-work (#PCDATA)> -<!ATTLIST text:sender-phone-work text:fixed %boolean; "true"> - -<!ELEMENT text:sender-street (#PCDATA)> -<!ATTLIST text:sender-street text:fixed %boolean; "true"> - -<!ELEMENT text:sender-city (#PCDATA)> -<!ATTLIST text:sender-city text:fixed %boolean; "true"> - -<!ELEMENT text:sender-postal-code (#PCDATA)> -<!ATTLIST text:sender-postal-code text:fixed %boolean; "true"> - -<!ELEMENT text:sender-country (#PCDATA)> -<!ATTLIST text:sender-country text:fixed %boolean; "true"> - -<!ELEMENT text:sender-state-or-province (#PCDATA)> -<!ATTLIST text:sender-state-or-province text:fixed %boolean; "true"> - -<!ELEMENT text:author-name (#PCDATA)> -<!ATTLIST text:author-name text:fixed %boolean; "true"> - -<!ELEMENT text:author-initials (#PCDATA)> -<!ATTLIST text:author-initials text:fixed %boolean; "true"> - -<!ELEMENT text:placeholder (#PCDATA)> -<!ATTLIST text:placeholder text:placeholder-type (text|table|text-box|image|object) #REQUIRED> -<!ATTLIST text:placeholder text:description %string; #IMPLIED> - -<!ELEMENT text:variable-decls (text:variable-decl)*> - -<!ELEMENT text:variable-decl EMPTY> -<!ATTLIST text:variable-decl text:name %variableName; #REQUIRED> -<!ATTLIST text:variable-decl %valueAndTypeAttr;> - -<!ELEMENT text:variable-set (#PCDATA)> -<!ATTLIST text:variable-set text:name %variableName; #REQUIRED> -<!ATTLIST text:variable-set text:formula %formula; #IMPLIED> -<!ATTLIST text:variable-set %valueAndTypeAttr;> -<!ATTLIST text:variable-set text:display (value|none) "value"> -<!ATTLIST text:variable-set style:data-style-name %styleName; #IMPLIED> - -<!ELEMENT text:variable-get (#PCDATA)> -<!ATTLIST text:variable-get text:name %variableName; #REQUIRED> -<!ATTLIST text:variable-get text:display (value|formula) "value"> -<!ATTLIST text:variable-get style:data-style-name %styleName; #IMPLIED> -<!ATTLIST text:variable-get %valueAttr;> - -<!ELEMENT text:variable-input (#PCDATA)> -<!ATTLIST text:variable-input text:name %variableName; #REQUIRED> -<!ATTLIST text:variable-input text:description %string; #IMPLIED> -<!ATTLIST text:variable-input %valueAndTypeAttr;> -<!ATTLIST text:variable-input text:display (value|none) "value"> -<!ATTLIST text:variable-input style:data-style-name %styleName; #IMPLIED> - -<!ELEMENT text:user-field-decls (text:user-field-decl)*> - -<!ELEMENT text:user-field-decl EMPTY> -<!ATTLIST text:user-field-decl text:name %variableName; #REQUIRED> -<!ATTLIST text:user-field-decl text:formula %formula; #IMPLIED> -<!ATTLIST text:user-field-decl %valueAndTypeAttr;> - -<!ELEMENT text:user-field-get (#PCDATA)> -<!ATTLIST text:user-field-get text:name %variableName; #REQUIRED> -<!ATTLIST text:user-field-get text:display (value|formula|none) "value"> -<!ATTLIST text:user-field-get style:data-style-name %styleName; #IMPLIED> - -<!ELEMENT text:user-field-input (#PCDATA)> -<!ATTLIST text:user-field-input text:name %variableName; #REQUIRED> -<!ATTLIST text:user-field-input text:description %string; #IMPLIED> -<!ATTLIST text:user-field-input style:data-style-name %styleName; #IMPLIED> - -<!ELEMENT text:sequence-decls (text:sequence-decl)*> - -<!ELEMENT text:sequence-decl EMPTY> -<!ATTLIST text:sequence-decl text:name %variableName; #REQUIRED> -<!ATTLIST text:sequence-decl text:display-outline-level %positiveInteger; "0"> -<!ATTLIST text:sequence-decl text:separation-character %character; "."> - -<!ELEMENT text:sequence (#PCDATA)> -<!ATTLIST text:sequence text:name %variableName; #REQUIRED> -<!ATTLIST text:sequence text:formula %formula; #IMPLIED> -<!ATTLIST text:sequence %numFormat;> -<!ATTLIST text:sequence text:ref-name ID #IMPLIED> - -<!ELEMENT text:expression (#PCDATA)> -<!ATTLIST text:expression text:formula %formula; #IMPLIED> -<!ATTLIST text:expression text:display (value|formula ) "value"> -<!ATTLIST text:expression %valueAndTypeAttr;> -<!ATTLIST text:expression style:data-style-name %styleName; #IMPLIED> - -<!ELEMENT text:text-input (#PCDATA)> -<!ATTLIST text:text-input text:description %string; #IMPLIED> - -<!ENTITY % database-table "text:database-name CDATA #REQUIRED - text:table-name CDATA #REQUIRED - text:table-type (table|query|command) #IMPLIED"> - -<!ELEMENT text:database-display (#PCDATA)> -<!ATTLIST text:database-display %database-table;> -<!ATTLIST text:database-display text:column-name %string; #REQUIRED> -<!ATTLIST text:database-display style:data-style-name %styleName; #IMPLIED> - -<!ELEMENT text:database-next (#PCDATA)> -<!ATTLIST text:database-next %database-table;> -<!ATTLIST text:database-next text:condition %formula; #IMPLIED> - -<!ELEMENT text:database-row-select (#PCDATA)> -<!ATTLIST text:database-row-select %database-table;> -<!ATTLIST text:database-row-select text:condition %formula; #IMPLIED> -<!ATTLIST text:database-row-select text:row-number %integer; #REQUIRED> - -<!ELEMENT text:database-row-number (#PCDATA)> -<!ATTLIST text:database-row-number %database-table;> -<!ATTLIST text:database-row-number %numFormat;> -<!ATTLIST text:database-row-number text:value %integer; #IMPLIED> - -<!ELEMENT text:database-name (#PCDATA)> -<!ATTLIST text:database-name %database-table;> - -<!ELEMENT text:initial-creator (#PCDATA)> -<!ATTLIST text:initial-creator text:fixed %boolean; "false"> - -<!ELEMENT text:creation-date (#PCDATA)> -<!ATTLIST text:creation-date text:fixed %boolean; "false"> -<!ATTLIST text:creation-date text:date-value %date; #IMPLIED> -<!ATTLIST text:creation-date style:data-style-name %styleName; #IMPLIED> - -<!ELEMENT text:creation-time (#PCDATA)> -<!ATTLIST text:creation-time text:fixed %boolean; "false"> -<!ATTLIST text:creation-time text:time-value %timeInstance; #IMPLIED> -<!ATTLIST text:creation-time style:data-style-name %styleName; #IMPLIED> - -<!ELEMENT text:description (#PCDATA)> -<!ATTLIST text:description text:fixed %boolean; "false"> - -<!ELEMENT text:user-defined (#PCDATA)> -<!ATTLIST text:user-defined text:fixed %boolean; "false"> -<!ATTLIST text:user-defined text:name %string; #REQUIRED> - -<!ELEMENT text:print-time (#PCDATA)> -<!ATTLIST text:print-time text:fixed %boolean; "false"> -<!ATTLIST text:print-time text:time-value %timeInstance; #IMPLIED> -<!ATTLIST text:print-time style:data-style-name %styleName; #IMPLIED> - -<!ELEMENT text:print-date (#PCDATA)> -<!ATTLIST text:print-date text:fixed %boolean; "false"> -<!ATTLIST text:print-date text:date-value %date; #IMPLIED> -<!ATTLIST text:print-date style:data-style-name %styleName; #IMPLIED> - -<!ELEMENT text:printed-by (#PCDATA)> -<!ATTLIST text:printed-by text:fixed %boolean; "false"> - -<!ELEMENT text:title (#PCDATA)> -<!ATTLIST text:title text:fixed %boolean; "false"> - -<!ELEMENT text:subject (#PCDATA)> -<!ATTLIST text:subject text:fixed %boolean; "false"> - -<!ELEMENT text:keywords (#PCDATA)> -<!ATTLIST text:keywords text:fixed %boolean; "false"> - -<!ELEMENT text:editing-cycles (#PCDATA)> -<!ATTLIST text:editing-cycles text:fixed %boolean; "false"> - -<!ELEMENT text:editing-duration (#PCDATA)> -<!ATTLIST text:editing-duration text:fixed %boolean; "false"> -<!ATTLIST text:editing-duration text:duration %timeDuration; #IMPLIED> -<!ATTLIST text:editing-duration style:data-style-name %styleName; #IMPLIED> - -<!ELEMENT text:modification-time (#PCDATA)> -<!ATTLIST text:modification-time text:fixed %boolean; "false"> -<!ATTLIST text:modification-time text:time-value %timeInstance; #IMPLIED> -<!ATTLIST text:modification-time style:data-style-name %styleName; #IMPLIED> - -<!ELEMENT text:modification-date (#PCDATA)> -<!ATTLIST text:modification-date text:fixed %boolean; "false"> -<!ATTLIST text:modification-date text:date-value %date; #IMPLIED> -<!ATTLIST text:modification-date style:data-style-name %styleName; #IMPLIED> - -<!ELEMENT text:creator (#PCDATA)> -<!ATTLIST text:creator text:fixed %boolean; "false"> - -<!ELEMENT text:conditional-text (#PCDATA)> -<!ATTLIST text:conditional-text text:condition %formula; #REQUIRED> -<!ATTLIST text:conditional-text text:string-value-if-false %string; #REQUIRED> -<!ATTLIST text:conditional-text text:string-value-if-true %string; #REQUIRED> -<!ATTLIST text:conditional-text text:current-value %boolean; "false"> - -<!ELEMENT text:hidden-text (#PCDATA)> -<!ATTLIST text:hidden-text text:condition %formula; #REQUIRED> -<!ATTLIST text:hidden-text text:string-value %string; #REQUIRED> -<!ATTLIST text:hidden-text text:is-hidden %boolean; "false"> - -<!ELEMENT text:hidden-paragraph EMPTY> -<!ATTLIST text:hidden-paragraph text:condition %formula; #REQUIRED> -<!ATTLIST text:hidden-paragraph text:is-hidden %boolean; "false"> - -<!ELEMENT text:chapter (#PCDATA)> -<!ATTLIST text:chapter text:display (name|number|number-and-name| - plain-number-and-name|plain-number) - "number-and-name"> -<!ATTLIST text:chapter text:outline-level %integer; "1"> - -<!ELEMENT text:file-name (#PCDATA)> -<!ATTLIST text:file-name text:display (full|path|name|name-and-extension) - "full"> -<!ATTLIST text:file-name text:fixed %boolean; "false"> - -<!ELEMENT text:template-name (#PCDATA)> -<!ATTLIST text:template-name text:display (full|path|name|name-and-extension| - area|title) "full"> - -<!ELEMENT text:page-variable-set EMPTY> -<!ATTLIST text:page-variable-set text:active %boolean; "true"> -<!ATTLIST text:page-variable-set text:page-adjust %integer; "0"> - -<!ELEMENT text:page-variable-get (#PCDATA)> -<!ATTLIST text:page-variable-get %numFormat;> - -<!ELEMENT text:execute-macro (#PCDATA|office:events)* > -<!ATTLIST text:execute-macro text:description %string; #IMPLIED> - - -<!ELEMENT text:dde-connection-decls (text:dde-connection-decl)*> - -<!ELEMENT text:dde-connection-decl EMPTY> -<!ATTLIST text:dde-connection-decl text:name %string; #REQUIRED> -<!ATTLIST text:dde-connection-decl office:dde-application %string; #REQUIRED> -<!ATTLIST text:dde-connection-decl office:dde-topic %string; #REQUIRED> -<!ATTLIST text:dde-connection-decl office:dde-item %string; #REQUIRED> -<!ATTLIST text:dde-connection-decl office:automatic-update %boolean; "false"> - -<!ELEMENT text:dde-connection (#PCDATA)> -<!ATTLIST text:dde-connection text:connection-name %string; #REQUIRED> - -<!ELEMENT text:reference-ref (#PCDATA)> -<!ATTLIST text:reference-ref text:ref-name %string; #REQUIRED> -<!ATTLIST text:reference-ref text:reference-format (page|chapter|text|direction) #IMPLIED> - -<!ELEMENT text:sequence-ref (#PCDATA)> -<!ATTLIST text:sequence-ref text:ref-name %string; #REQUIRED> -<!ATTLIST text:sequence-ref text:reference-format (page|chapter|text|direction|category-and-value|caption|value) #IMPLIED> - -<!ELEMENT text:bookmark-ref (#PCDATA)> -<!ATTLIST text:bookmark-ref text:ref-name %string; #REQUIRED> -<!ATTLIST text:bookmark-ref text:reference-format (page|chapter|text|direction) #IMPLIED> - -<!ELEMENT text:footnote-ref (#PCDATA)> -<!ATTLIST text:footnote-ref text:ref-name %string; #REQUIRED> -<!ATTLIST text:footnote-ref text:reference-format (page|chapter|text|direction) #IMPLIED> - -<!ELEMENT text:endnote-ref (#PCDATA)> -<!ATTLIST text:endnote-ref text:ref-name %string; #REQUIRED> -<!ATTLIST text:endnote-ref text:reference-format (page|chapter|text|direction) #IMPLIED> - -<!ELEMENT text:sheet-name (#PCDATA)> - -<!ELEMENT text:page-count (#PCDATA)> -<!ATTLIST text:page-count style:num-format %string; #IMPLIED> -<!ATTLIST text:page-count style:num-letter-sync %boolean; "false"> - -<!ELEMENT text:paragraph-count (#PCDATA)> -<!ATTLIST text:paragraph-count style:num-format %string; #IMPLIED> -<!ATTLIST text:paragraph-count style:num-letter-sync %boolean; "false"> - -<!ELEMENT text:word-count (#PCDATA)> -<!ATTLIST text:word-count style:num-format %string; #IMPLIED> -<!ATTLIST text:word-count style:num-letter-sync %boolean; "false"> - -<!ELEMENT text:character-count (#PCDATA)> -<!ATTLIST text:character-count style:num-format %string; #IMPLIED> -<!ATTLIST text:character-count style:num-letter-sync %boolean; "false"> - -<!ELEMENT text:table-count (#PCDATA)> -<!ATTLIST text:table-count style:num-format %string; #IMPLIED> -<!ATTLIST text:table-count style:num-letter-sync %boolean; "false"> - -<!ELEMENT text:image-count (#PCDATA)> -<!ATTLIST text:image-count style:num-format %string; #IMPLIED> -<!ATTLIST text:image-count style:num-letter-sync %boolean; "false"> - -<!ELEMENT text:object-count (#PCDATA)> -<!ATTLIST text:object-count style:num-format %string; #IMPLIED> -<!ATTLIST text:object-count style:num-letter-sync %boolean; "false"> - -<!ELEMENT text:bibliography-mark (#PCDATA)> -<!ATTLIST text:bibliography-mark text:bibliography-type - ( article | book | booklet | conference | custom1 | custom2 | custom3 | - custom4 | custom5 | email | inbook | incollection | inproceedings | - journal | manual | mastersthesis | misc | phdthesis | proceedings | - techreport | unpublished | www ) #REQUIRED > -<!ATTLIST text:bibliography-mark text:identifier CDATA #IMPLIED> -<!ATTLIST text:bibliography-mark text:address CDATA #IMPLIED> -<!ATTLIST text:bibliography-mark text:annote CDATA #IMPLIED> -<!ATTLIST text:bibliography-mark text:author CDATA #IMPLIED> -<!ATTLIST text:bibliography-mark text:booktitle CDATA #IMPLIED> -<!ATTLIST text:bibliography-mark text:chapter CDATA #IMPLIED> -<!ATTLIST text:bibliography-mark text:edition CDATA #IMPLIED> -<!ATTLIST text:bibliography-mark text:editor CDATA #IMPLIED> -<!ATTLIST text:bibliography-mark text:howpublished CDATA #IMPLIED> -<!ATTLIST text:bibliography-mark text:institution CDATA #IMPLIED> -<!ATTLIST text:bibliography-mark text:journal CDATA #IMPLIED> -<!ATTLIST text:bibliography-mark text:month CDATA #IMPLIED> -<!ATTLIST text:bibliography-mark text:note CDATA #IMPLIED> -<!ATTLIST text:bibliography-mark text:number CDATA #IMPLIED> -<!ATTLIST text:bibliography-mark text:organizations CDATA #IMPLIED> -<!ATTLIST text:bibliography-mark text:pages CDATA #IMPLIED> -<!ATTLIST text:bibliography-mark text:publisher CDATA #IMPLIED> -<!ATTLIST text:bibliography-mark text:school CDATA #IMPLIED> -<!ATTLIST text:bibliography-mark text:series CDATA #IMPLIED> -<!ATTLIST text:bibliography-mark text:title CDATA #IMPLIED> -<!ATTLIST text:bibliography-mark text:report-type CDATA #IMPLIED> -<!ATTLIST text:bibliography-mark text:volume CDATA #IMPLIED> -<!ATTLIST text:bibliography-mark text:year CDATA #IMPLIED> -<!ATTLIST text:bibliography-mark text:url CDATA #IMPLIED> -<!ATTLIST text:bibliography-mark text:custom1 CDATA #IMPLIED> -<!ATTLIST text:bibliography-mark text:custom2 CDATA #IMPLIED> -<!ATTLIST text:bibliography-mark text:custom3 CDATA #IMPLIED> -<!ATTLIST text:bibliography-mark text:custom4 CDATA #IMPLIED> -<!ATTLIST text:bibliography-mark text:custom5 CDATA #IMPLIED> -<!ATTLIST text:bibliography-mark text:isbn CDATA #IMPLIED> - - -<!ELEMENT text:bookmark EMPTY> -<!ATTLIST text:bookmark text:name CDATA #REQUIRED> - -<!ELEMENT text:bookmark-start EMPTY> -<!ATTLIST text:bookmark-start text:name CDATA #REQUIRED> - -<!ELEMENT text:bookmark-end EMPTY> -<!ATTLIST text:bookmark-end text:name CDATA #REQUIRED> - -<!ELEMENT text:reference-mark EMPTY> -<!ATTLIST text:reference-mark text:name CDATA #REQUIRED> - -<!ELEMENT text:reference-mark-start EMPTY> -<!ATTLIST text:reference-mark-start text:name CDATA #REQUIRED> - -<!ELEMENT text:reference-mark-end EMPTY> -<!ATTLIST text:reference-mark-end text:name CDATA #REQUIRED> - -<!ELEMENT text:footnotes-configuration (text:footnote-continuation-notice-forward?,text:footnote-continuation-notice-backward?)> -<!ATTLIST text:footnotes-configuration style:num-prefix %string; #IMPLIED> -<!ATTLIST text:footnotes-configuration style:num-suffix %string; #IMPLIED> -<!ATTLIST text:footnotes-configuration style:num-format %string; #IMPLIED> -<!ATTLIST text:footnotes-configuration style:num-letter-sync %string; #IMPLIED> -<!ATTLIST text:footnotes-configuration text:citation-body-style-name %styleName; #IMPLIED> -<!ATTLIST text:footnotes-configuration text:citation-style-name %styleName; #IMPLIED> -<!ATTLIST text:footnotes-configuration text:default-style-name %styleName; #IMPLIED> -<!ATTLIST text:footnotes-configuration text:master-page-name %styleName; #IMPLIED> -<!ATTLIST text:footnotes-configuration text:start-value %integer; #IMPLIED> -<!ATTLIST text:footnotes-configuration text:footnotes-position (document|page) "page"> -<!ATTLIST text:footnotes-configuration text:start-numbering-at (document|chapter|page) "document"> - -<!ELEMENT text:footnote-continuation-notice-forward (#PCDATA)> -<!ELEMENT text:footnote-continuation-notice-backward (#PCDATA)> - -<!ELEMENT text:endnotes-configuration EMPTY> -<!ATTLIST text:endnotes-configuration style:num-prefix %string; #IMPLIED> -<!ATTLIST text:endnotes-configuration style:num-suffix %string; #IMPLIED> -<!ATTLIST text:endnotes-configuration style:num-format %string; #IMPLIED> -<!ATTLIST text:endnotes-configuration style:num-letter-sync %string; #IMPLIED> -<!ATTLIST text:endnotes-configuration text:start-value %integer; #IMPLIED> -<!ATTLIST text:endnotes-configuration text:citation-style-name %styleName; #IMPLIED> -<!ATTLIST text:endnotes-configuration text:citation-body-style-name %styleName; #IMPLIED> -<!ATTLIST text:endnotes-configuration text:default-style-name %styleName; #IMPLIED> -<!ATTLIST text:endnotes-configuration text:master-page-name %styleName; #IMPLIED> - -<!-- Validity constraint: text:footnote and text:endnote elements may not - contain other text:footnote or text:endnote elements, even though the DTD - allows this (via the %text; in the foot-/endnote-body). - Unfortunatetly, this constraint cannot be easily specified in the DTD. ---> -<!ELEMENT text:footnote (text:footnote-citation, text:footnote-body)> -<!ATTLIST text:footnote text:id ID #IMPLIED> - -<!ELEMENT text:footnote-citation (#PCDATA)> -<!ATTLIST text:footnote-citation text:label %string; #IMPLIED> - -<!ELEMENT text:footnote-body (text:h|text:p| - text:ordered-list|text:unordered-list)*> - -<!ELEMENT text:endnote (text:endnote-citation, text:endnote-body)> -<!ATTLIST text:endnote text:id ID #IMPLIED> - -<!ELEMENT text:endnote-citation (#PCDATA)> -<!ATTLIST text:endnote-citation text:label %string; #IMPLIED> - -<!ELEMENT text:endnote-body (text:h|text:p| - text:ordered-list|text:unordered-list)*> - -<!ENTITY % sectionAttr "text:name CDATA #REQUIRED - text:style-name %styleName; #IMPLIED - text:protected %boolean; 'false' "> - - -<!ELEMENT text:section ((text:section-source|office:dde-source)?, - %sectionText;) > - -<!ATTLIST text:section %sectionAttr;> -<!ATTLIST text:section text:display (true|none|condition) "true"> -<!ATTLIST text:section text:condition %formula; #IMPLIED> -<!ATTLIST text:section text:protection-key CDATA #IMPLIED> -<!ATTLIST text:section text:is-hidden %boolean; #IMPLIED> - -<!ELEMENT text:section-source EMPTY> -<!ATTLIST text:section-source xlink:href %string; #IMPLIED> -<!ATTLIST text:section-source xlink:type (simple) #FIXED "simple"> -<!ATTLIST text:section-source xlink:show (embed) #FIXED "embed"> -<!ATTLIST text:section-source text:section-name %string; #IMPLIED> -<!ATTLIST text:section-source text:filter-name %string; #IMPLIED> - -<!ELEMENT text:table-of-content (text:table-of-content-source, - text:index-body) > -<!ATTLIST text:table-of-content %sectionAttr;> - -<!ELEMENT text:table-of-content-source (text:index-title-template? , - text:table-of-content-entry-template*, - text:index-source-styles* ) > -<!ATTLIST text:table-of-content-source text:outline-level %integer; #IMPLIED> -<!ATTLIST text:table-of-content-source text:use-index-marks %boolean; "true"> -<!ATTLIST text:table-of-content-source text:use-index-source-styles - %boolean; "false"> -<!ATTLIST text:table-of-content-source text:index-scope (document|chapter) - "document"> -<!ATTLIST text:table-of-content-source text:relative-tab-stop-position - %boolean; "true"> -<!ATTLIST text:table-of-content-source fo:language %string; #IMPLIED> -<!ATTLIST text:table-of-content-source fo:country %string; #IMPLIED> -<!ATTLIST text:table-of-content-source text:sort-algorithm %string; #IMPLIED> - -<!ELEMENT text:table-of-content-entry-template (text:index-entry-chapter-number | - text:index-entry-page-number | - text:index-entry-text | - text:index-entry-span | - text:index-entry-tab-stop | - text:index-entry-link-start | - text:index-entry-link-end)* > -<!ATTLIST text:table-of-content-entry-template text:outline-level - %integer; #REQUIRED> -<!ATTLIST text:table-of-content-entry-template text:style-name - %styleName; #REQUIRED> - -<!ELEMENT text:illustration-index - (text:illustration-index-source, text:index-body)> -<!ATTLIST text:illustration-index %sectionAttr;> - -<!ELEMENT text:illustration-index-source (text:index-title-template?, - text:illustration-index-entry-template?) > -<!ATTLIST text:illustration-index-source text:index-scope - (document|chapter) "document"> -<!ATTLIST text:illustration-index-source text:relative-tab-stop-position - %boolean; "true"> -<!ATTLIST text:illustration-index-source text:use-caption %boolean; "true"> -<!ATTLIST text:illustration-index-source text:caption-sequence-name - %string; #IMPLIED> -<!ATTLIST text:illustration-index-source text:caption-sequence-format - (text|category-and-value|caption) "text"> -<!ATTLIST text:illustration-index-source fo:language %string; #IMPLIED> -<!ATTLIST text:illustration-index-source fo:country %string; #IMPLIED> -<!ATTLIST text:illustration-index-source text:sort-algorithm %string; #IMPLIED> - -<!ELEMENT text:illustration-index-entry-template - ( text:index-entry-page-number | - text:index-entry-text | - text:index-entry-span | - text:index-entry-tab-stop )* > -<!ATTLIST text:illustration-index-entry-template text:style-name - %styleName; #REQUIRED> - -<!ELEMENT text:table-index (text:table-index-source, text:index-body)> -<!ATTLIST text:table-index %sectionAttr;> - -<!ELEMENT text:table-index-source (text:index-title-template?, - text:table-index-entry-template?) > -<!ATTLIST text:table-index-source text:index-scope - (document|chapter) "document"> -<!ATTLIST text:table-index-source text:relative-tab-stop-position - %boolean; "true"> -<!ATTLIST text:table-index-source text:use-caption %boolean; "true"> -<!ATTLIST text:table-index-source text:caption-sequence-name - %string; #IMPLIED> -<!ATTLIST text:table-index-source text:caption-sequence-format - (text|category-and-value|caption) "text"> -<!ATTLIST text:table-index-source fo:language %string; #IMPLIED> -<!ATTLIST text:table-index-source fo:country %string; #IMPLIED> -<!ATTLIST text:table-index-source text:sort-algorithm %string; #IMPLIED> - -<!ELEMENT text:table-index-entry-template ( text:index-entry-page-number | - text:index-entry-text | - text:index-entry-span | - text:index-entry-tab-stop )* > -<!ATTLIST text:table-index-entry-template text:style-name - %styleName; #REQUIRED> - -<!ELEMENT text:object-index ( text:object-index-source, text:index-body ) > -<!ATTLIST text:object-index %sectionAttr;> - -<!ELEMENT text:object-index-source ( text:index-title-template?, - text:object-index-entry-template? ) > -<!ATTLIST text:object-index-source text:index-scope - (document|chapter) "document"> -<!ATTLIST text:object-index-source text:relative-tab-stop-position - %boolean; "true"> -<!ATTLIST text:object-index-source text:use-spreadsheet-objects - %boolean; "false"> -<!ATTLIST text:object-index-source text:use-draw-objects %boolean; "false"> -<!ATTLIST text:object-index-source text:use-chart-objects %boolean; "false"> -<!ATTLIST text:object-index-source text:use-other-objects %boolean; "false"> -<!ATTLIST text:object-index-source text:use-math-objects %boolean; "false"> -<!ATTLIST text:object-index-source fo:language %string; #IMPLIED> -<!ATTLIST text:object-index-source fo:country %string; #IMPLIED> -<!ATTLIST text:object-index-source text:sort-algorithm %string; #IMPLIED> - -<!ELEMENT text:object-index-entry-template ( text:index-entry-page-number | - text:index-entry-text | - text:index-entry-span | - text:index-entry-tab-stop )* > -<!ATTLIST text:object-index-entry-template text:style-name - %styleName; #REQUIRED > - -<!ELEMENT text:user-index (text:user-index-source, text:index-body) > -<!ATTLIST text:user-index %sectionAttr;> - -<!ELEMENT text:user-index-source ( text:index-title-template?, - text:user-index-entry-template*, - text:index-source-styles* ) > -<!ATTLIST text:user-index-source text:index-scope - (document|chapter) "document"> -<!ATTLIST text:user-index-source text:relative-tab-stop-position - %boolean; "true"> -<!ATTLIST text:user-index-source text:use-index-marks %boolean; "false"> -<!ATTLIST text:user-index-source text:use-graphics %boolean; "false"> -<!ATTLIST text:user-index-source text:use-tables %boolean; "false"> -<!ATTLIST text:user-index-source text:use-floating-frames %boolean; "false"> -<!ATTLIST text:user-index-source text:use-objects %boolean; "false"> -<!ATTLIST text:user-index-source text:use-index-source-styles - %boolean; "false"> -<!ATTLIST text:user-index-source text:copy-outline-levels %boolean; "false"> -<!ATTLIST text:user-index-source fo:language %string; #IMPLIED> -<!ATTLIST text:user-index-source fo:country %string; #IMPLIED> -<!ATTLIST text:user-index-source text:sort-algorithm %string; #IMPLIED> -<!ATTLIST text:user-index-source text:index-name %string; #IMPLIED> - -<!ELEMENT text:user-index-entry-template ( text:index-entry-chapter | - text:index-entry-page-number | - text:index-entry-text | - text:index-entry-span | - text:index-entry-tab-stop )* > -<!ATTLIST text:user-index-entry-template text:outline-level %integer; #REQUIRED> -<!ATTLIST text:user-index-entry-template text:style-name %styleName; #REQUIRED> - -<!ELEMENT text:alphabetical-index (text:alphabetical-index-source, - text:index-body)> -<!ATTLIST text:alphabetical-index %sectionAttr;> - -<!ELEMENT text:alphabetical-index-source ( text:index-title-template?, - text:alphabetical-index-entry-template* ) > -<!ATTLIST text:alphabetical-index-source text:index-scope - (document|chapter) "document"> -<!ATTLIST text:alphabetical-index-source text:relative-tab-stop-position - %boolean; "true"> -<!ATTLIST text:alphabetical-index-source text:ignore-case %boolean; "false"> -<!ATTLIST text:alphabetical-index-source text:main-entry-style-name - %styleName; #IMPLIED> -<!ATTLIST text:alphabetical-index-source text:alphabetical-separators - %boolean; "false"> -<!ATTLIST text:alphabetical-index-source text:combine-entries - %boolean; "true"> -<!ATTLIST text:alphabetical-index-source text:combine-entries-with-dash - %boolean; "false"> -<!ATTLIST text:alphabetical-index-source text:combine-entries-with-pp - %boolean; "true"> -<!ATTLIST text:alphabetical-index-source text:use-keys-as-entries - %boolean; "false"> -<!ATTLIST text:alphabetical-index-source text:capitalize-entries - %boolean; "false"> -<!ATTLIST text:alphabetical-index-source text:comma-separated - %boolean; "false"> -<!ATTLIST text:alphabetical-index-source fo:language %string; #IMPLIED> -<!ATTLIST text:alphabetical-index-source fo:country %string; #IMPLIED> -<!ATTLIST text:alphabetical-index-source text:sort-algorithm %string; #IMPLIED> - -<!ELEMENT text:alphabetical-index-entry-template ( text:index-entry-chapter | - text:index-entry-page-number | - text:index-entry-text | - text:index-entry-span | - text:index-entry-tab-stop )* > -<!ATTLIST text:alphabetical-index-entry-template text:outline-level - (1|2|3|separator) #REQUIRED> -<!ATTLIST text:alphabetical-index-entry-template text:style-name - %styleName; #REQUIRED> - -<!ELEMENT text:alphabetical-index-auto-mark-file EMPTY> -<!ATTLIST text:alphabetical-index-auto-mark-file xlink:href CDATA #IMPLIED> -<!ATTLIST text:alphabetical-index-auto-mark-file xlink:type (simple) #FIXED "simple"> - -<!ELEMENT text:bibliography (text:bibliography-source, text:index-body) > -<!ATTLIST text:bibliography %sectionAttr;> - -<!ELEMENT text:bibliography-source ( text:index-title-template?, - text:bibliography-entry-template* ) > - -<!ELEMENT text:bibliography-entry-template ( text:index-entry-span | - text:index-entry-tab-stop | - text:index-entry-bibliography )* > -<!ATTLIST text:bibliography-entry-template text:bibliography-type - ( article | book | booklet | conference | custom1 | custom2 | - custom3 | custom4 | custom5 | email | inbook | incollection | - inproceedings | journal | manual | mastersthesis | misc | - phdthesis | proceedings | techreport | unpublished | www ) - #REQUIRED > -<!ATTLIST text:bibliography-entry-template text:style-name - %styleName; #REQUIRED> - -<!ELEMENT text:index-body %sectionText; > - -<!-- -Validity constraint: text:index-title elements may appear only in -indices, and there may be only one text:index-title element. ---> -<!ELEMENT text:index-title %sectionText; > -<!ATTLIST text:index-title text:style-name %styleName; #IMPLIED> -<!ATTLIST text:index-title text:name %string; #IMPLIED> - -<!ELEMENT text:index-title-template (#PCDATA)> -<!ATTLIST text:index-title-template text:style-name %styleName; #IMPLIED> - -<!ELEMENT text:index-entry-chapter-number EMPTY> -<!ATTLIST text:index-entry-chapter-number text:style-name %styleName; #IMPLIED> - -<!ELEMENT text:index-entry-chapter EMPTY> -<!ATTLIST text:index-entry-chapter text:style-name %styleName; #IMPLIED> -<!ATTLIST text:index-entry-chapter text:display (name|number|number-and-name) - "number-and-name" > - -<!ELEMENT text:index-entry-text EMPTY> -<!ATTLIST text:index-entry-text text:style-name %styleName; #IMPLIED> - -<!ELEMENT text:index-entry-page-number EMPTY> -<!ATTLIST text:index-entry-page-number text:style-name %styleName; #IMPLIED> - -<!ELEMENT text:index-entry-span (#PCDATA)> -<!ATTLIST text:index-entry-span text:style-name %styleName; #IMPLIED> - -<!ELEMENT text:index-entry-bibliography EMPTY> -<!ATTLIST text:index-entry-bibliography text:style-name %styleName; #IMPLIED> -<!ATTLIST text:index-entry-bibliography text:bibliography-data-field - ( address | annote | author | bibliography-type | - booktitle | chapter | custom1 | custom2 | - custom3 | custom4 | custom5 | edition | editor | - howpublished | identifier | institution | isbn | - journal | month | note | number | organizations | - pages | publisher | report-type | school | - series | title | url | volume | year ) #REQUIRED> - - -<!ELEMENT text:index-entry-tab-stop EMPTY> -<!ATTLIST text:index-entry-tab-stop text:style-name %styleName; #IMPLIED> -<!ATTLIST text:index-entry-tab-stop style:leader-char %character; " "> -<!ATTLIST text:index-entry-tab-stop style:type (left|right) "left"> -<!ATTLIST text:index-entry-tab-stop style:position %length; #IMPLIED> - -<!ELEMENT text:index-entry-link-start EMPTY> -<!ATTLIST text:index-entry-link-start text:style-name %styleName; #IMPLIED> - -<!ELEMENT text:index-entry-link-end EMPTY> -<!ATTLIST text:index-entry-link-end text:style-name %styleName; #IMPLIED> - -<!ELEMENT text:index-source-styles (text:index-source-style)*> -<!ATTLIST text:index-source-styles text:outline-level %integer; #REQUIRED> - -<!ELEMENT text:index-source-style EMPTY> -<!ATTLIST text:index-source-style text:style-name %styleName; #REQUIRED> - -<!ELEMENT text:toc-mark-start EMPTY> -<!ATTLIST text:toc-mark-start text:id %string; #REQUIRED> -<!ATTLIST text:toc-mark-start text:outline-level %integer; #IMPLIED> - -<!ELEMENT text:toc-mark-end EMPTY> -<!ATTLIST text:toc-mark-end text:id %string; #REQUIRED> - -<!ELEMENT text:toc-mark EMPTY> -<!ATTLIST text:toc-mark text:string-value %string; #REQUIRED> -<!ATTLIST text:toc-mark text:outline-level %integer; #IMPLIED> - -<!ELEMENT text:user-index-mark-start EMPTY> -<!ATTLIST text:user-index-mark-start text:id %string; #REQUIRED> -<!ATTLIST text:user-index-mark-start text:outline-level %integer; #IMPLIED> -<!ATTLIST text:user-index-mark-start text:index-name %string; #IMPLIED> - -<!ELEMENT text:user-index-mark-end EMPTY> -<!ATTLIST text:user-index-mark-end text:id %string; #REQUIRED> - -<!ELEMENT text:user-index-mark EMPTY> -<!ATTLIST text:user-index-mark text:string-value %string; #REQUIRED> -<!ATTLIST text:user-index-mark text:outline-level %integer; #IMPLIED> -<!ATTLIST text:user-index-mark text:index-name %string; #IMPLIED> - -<!ELEMENT text:alphabetical-index-mark-start EMPTY> -<!ATTLIST text:alphabetical-index-mark-start text:id %string; #REQUIRED> -<!ATTLIST text:alphabetical-index-mark-start text:key1 %string; #IMPLIED> -<!ATTLIST text:alphabetical-index-mark-start text:key2 %string; #IMPLIED> -<!ATTLIST text:alphabetical-index-mark-start text:main-etry %boolean; "false"> - -<!ELEMENT text:alphabetical-index-mark-end EMPTY> -<!ATTLIST text:alphabetical-index-mark-end text:id %string; #REQUIRED> - -<!ELEMENT text:alphabetical-index-mark EMPTY> -<!ATTLIST text:alphabetical-index-mark text:string-value %string; #REQUIRED> -<!ATTLIST text:alphabetical-index-mark text:key1 %string; #IMPLIED> -<!ATTLIST text:alphabetical-index-mark text:key2 %string; #IMPLIED> -<!ATTLIST text:alphabetical-index-mark text:main-etry %boolean; "false"> - -<!ELEMENT text:bibliography-configuration (text:sort-key)*> -<!ATTLIST text:bibliography-configuration text:prefix %string; #IMPLIED> -<!ATTLIST text:bibliography-configuration text:suffix %string; #IMPLIED> -<!ATTLIST text:bibliography-configuration text:sort-by-position %boolean; "true"> -<!ATTLIST text:bibliography-configuration text:numbered-entries %boolean; "false"> -<!ATTLIST text:bibliography-configuration fo:language %string; #IMPLIED> -<!ATTLIST text:bibliography-configuration fo:country %string; #IMPLIED> -<!ATTLIST text:bibliography-configuration text:sort-algorithm %string; #IMPLIED> - -<!ELEMENT text:sort-key EMPTY> -<!ATTLIST text:sort-key text:key ( address | annote | author | - bibliography-type | booktitle | chapter | custom1 | custom2 | - custom3 | custom4 | custom5 | edition | editor | howpublished | - identifier | institution | isbn | journal | month | note | number | - organizations | pages | publisher | report-type | school | series | - title | url | volume | year ) #REQUIRED> -<!ATTLIST text:sort-key text:sort-ascending %boolean; "true"> - -<!ELEMENT text:linenumbering-configuration (text:linenumbering-separator?)> -<!ATTLIST text:linenumbering-configuration text:style-name %styleName; #IMPLIED> -<!ATTLIST text:linenumbering-configuration text:number-lines %boolean; "true"> -<!ATTLIST text:linenumbering-configuration text:count-empty-lines %boolean; "true"> -<!ATTLIST text:linenumbering-configuration text:count-in-floating-frames %boolean; "false"> -<!ATTLIST text:linenumbering-configuration text:restart-numbering %boolean; "false"> -<!ATTLIST text:linenumbering-configuration text:offset %nonNegativeLength; #IMPLIED> -<!ATTLIST text:linenumbering-configuration style:num-format (1|a|A|i|I) "1"> -<!ATTLIST text:linenumbering-configuration style:num-letter-sync %boolean; "false"> -<!ATTLIST text:linenumbering-configuration text:number-position (left|rigth|inner|outer) "left"> -<!ATTLIST text:linenumbering-configuration text:increment %nonNegativeInteger; #IMPLIED> - -<!ELEMENT text:linenumbering-separator (#PCDATA)> -<!ATTLIST text:linenumbering-separator text:increment %nonNegativeInteger; #IMPLIED> - -<!ELEMENT text:script (#PCDATA)> -<!ATTLIST text:script script:language CDATA #REQUIRED> -<!ATTLIST text:script xlink:href CDATA #IMPLIED> -<!ATTLIST text:script xlink:type (simple) #FIXED "simple"> - -<!ELEMENT text:measure (#PCDATA)> -<!ATTLIST text:measure text:kind (value|unit|gap) #REQUIRED> - -<!ELEMENT text:ruby (text:ruby-base, text:ruby-text)> -<!ATTLIST text:ruby text:style-name %styleName; #IMPLIED> - -<!ELEMENT text:ruby-base %inline-text;> - -<!ELEMENT text:ruby-text (#PCDATA)> -<!ATTLIST text:ruby-text text:style-name %styleName; #IMPLIED> - -<!-- elements for change tracking --> - -<!ELEMENT text:change EMPTY> -<!ATTLIST text:change text:change-id CDATA #REQUIRED> - -<!ELEMENT text:change-start EMPTY> -<!ATTLIST text:change-start text:change-id CDATA #REQUIRED> - -<!ELEMENT text:change-end EMPTY> -<!ATTLIST text:change-end text:change-id CDATA #REQUIRED> - -<!ELEMENT text:tracked-changes (text:changed-region)*> -<!ATTLIST text:tracked-changes text:track-changes %boolean; "true"> -<!ATTLIST text:tracked-changes text:protection-key CDATA #IMPLIED> - -<!ELEMENT text:changed-region (text:insertion | - (text:deletion, text:insertion?) | - text:format-change) > -<!ATTLIST text:changed-region text:id ID #REQUIRED> -<!ATTLIST text:changed-region text:merge-last-paragraph %boolean; "true"> - -<!ELEMENT text:insertion (office:change-info, %sectionText;)> -<!ELEMENT text:deletion (office:change-info, %sectionText;)> -<!ELEMENT text:format-change (office:change-info)> - - - -<!ELEMENT table:calculation-settings (table:null-date?, table:iteration?)> -<!ATTLIST table:calculation-settings - table:case-sensitive %boolean; "true" - table:precision-as-shown %boolean; "false" - table:search-criteria-must-apply-to-whole-cell %boolean; "true" - table:automatic-find-labels %boolean; "true" - table:use-regular-expressions %boolean; "true" - table:null-year %positiveInteger; "1930" -> -<!ELEMENT table:null-date EMPTY> -<!ATTLIST table:null-date - table:value-type %valueType; #FIXED "date" - table:date-value %date; "1899-12-30" -> -<!ELEMENT table:iteration EMPTY> -<!ATTLIST table:iteration - table:status (enable | disable) "disable" - table:steps %positiveInteger; "100" - table:maximum-difference %float; "0.001" -> - -<!ELEMENT table:tracked-changes (table:cell-content-change | table:insertion | table:deletion | table:movement | table:rejection)*> -<!ATTLIST table:tracked-changes table:track-changes %boolean; "true" - table:protected %boolean; "false" - table:protection-key CDATA #IMPLIED -> - -<!ELEMENT table:dependences (table:dependence)+> -<!ELEMENT table:dependence EMPTY> -<!ATTLIST table:dependence - table:id CDATA #REQUIRED -> -<!ELEMENT table:deletions (table:cell-content-deletion | table:change-deletion)+> -<!ELEMENT table:cell-content-deletion (table:cell-address?, table:change-track-table-cell?)> -<!ATTLIST table:cell-content-deletion - table:id CDATA #IMPLIED -> -<!ELEMENT table:change-deletion EMPTY> -<!ATTLIST table:change-deletion - table:id CDATA #IMPLIED -> -<!ELEMENT table:insertion (office:change-info, table:dependences?, table:deletions?)> -<!ATTLIST table:insertion - table:id CDATA #REQUIRED - table:acceptance-state (accepted | rejected | pending) "pending" - table:rejecting-change-id %positiveInteger; #IMPLIED - table:type (row | column | table) #REQUIRED - table:position %integer; #REQUIRED - table:count %positiveInteger; "1" - table:table %integer; #IMPLIED -> -<!ELEMENT table:deletion (office:change-info, table:dependences?, table:deletions?, table:cut-offs?)> -<!ATTLIST table:deletion - table:id CDATA #REQUIRED - table:acceptance-state (accepted | rejected | pending) "pending" - table:rejecting-change-id %positiveInteger; #IMPLIED - table:type (row | column | table) #REQUIRED - table:position %integer; #REQUIRED - table:count %positiveInteger; "1" - table:table %integer; #IMPLIED - table:multi-deletion-spanned %integer; #IMPLIED -> -<!ELEMENT table:cut-offs (table:movement-cut-off+ | (table:insertion-cut-off, table:movement-cut-off*))> -<!ELEMENT table:insertion-cut-off EMPTY> -<!ATTLIST table:insertion-cut-off - table:id CDATA #REQUIRED - table:position %integer; #REQUIRED -> -<!ELEMENT table:movement-cut-off EMPTY> -<!ATTLIST table:movement-cut-off - table:id CDATA #REQUIRED - table:start-position %integer; #IMPLIED - table:end-position %integer; #IMPLIED - table:position %integer; #IMPLIED -> -<!ELEMENT table:movement (table:source-range-address, table:target-range-address, office:change-info, table:dependences?, table:deletions?)> -<!ATTLIST table:movement - table:id CDATA #REQUIRED - table:acceptance-state (accepted | rejected | pending) "pending" - table:rejecting-change-id %positiveInteger; #IMPLIED -> -<!ELEMENT table:target-range-address EMPTY> -<!ATTLIST table:target-range-address - table:column %integer; #IMPLIED - table:row %integer; #IMPLIED - table:table %integer; #IMPLIED - table:start-column %integer; #IMPLIED - table:start-row %integer; #IMPLIED - table:start-table %integer; #IMPLIED - table:end-column %integer; #IMPLIED - table:end-row %integer; #IMPLIED - table:end-table %integer; #IMPLIED -> -<!ELEMENT table:source-range-address EMPTY> -<!ATTLIST table:source-range-address - table:column %integer; #IMPLIED - table:row %integer; #IMPLIED - table:table %integer; #IMPLIED - table:start-column %integer; #IMPLIED - table:start-row %integer; #IMPLIED - table:start-table %integer; #IMPLIED - table:end-column %integer; #IMPLIED - table:end-row %integer; #IMPLIED - table:end-table %integer; #IMPLIED -> -<!ELEMENT table:change-track-table-cell (text:p*)> -<!ATTLIST table:change-track-table-cell - table:cell-address %cell-address; #IMPLIED - table:matrix-covered (true | false) "false" - table:formula %string; #IMPLIED - table:number-matrix-rows-spanned %positiveInteger; #IMPLIED - table:number-matrix-columns-spanned %positiveInteger; #IMPLIED - table:value-type %valueType; "string" - table:value %float; #IMPLIED - table:date-value %date; #IMPLIED - table:time-value %timeInstance; #IMPLIED - table:string-value %string; #IMPLIED -> -<!ELEMENT table:cell-content-change (table:cell-address, office:change-info, table:dependences?, table:deletions?, table:previous)> -<!ATTLIST table:cell-content-change - table:id CDATA #REQUIRED - table:acceptance-state (accepted | rejected | pending) "pending" - table:rejecting-change-id %positiveInteger; #IMPLIED -> -<!ELEMENT table:cell-address EMPTY> -<!ATTLIST table:cell-address - table:column %integer; #IMPLIED - table:row %integer; #IMPLIED - table:table %integer; #IMPLIED -> -<!ELEMENT table:previous (table:change-track-table-cell)> -<!ATTLIST table:previous - table:id CDATA #IMPLIED -> -<!ELEMENT table:rejection (office:change-info, table:dependences?, table:deletions?)> -<!ATTLIST table:rejection - table:id CDATA #REQUIRED - table:acceptance-state (accepted | rejected | pending) "pending" - table:rejecting-change-id %positiveInteger; #IMPLIED -> - -<!ENTITY % table-columns "table:table-columns | ( table:table-column | table:table-column-group )+"> -<!ENTITY % table-header-columns "table:table-header-columns"> -<!ENTITY % table-rows "table:table-rows | ( table:table-row | table:table-row-group )+"> -<!ENTITY % table-header-rows "table:table-header-rows"> -<!ENTITY % table-column-groups "((%table-columns;),(%table-header-columns;,(%table-columns;)?)?) | (%table-header-columns;,(%table-columns;)?)"> -<!ENTITY % table-row-groups "((%table-rows;),(%table-header-rows;,(%table-rows;)?)?) | (%table-header-rows;,(%table-rows;)?)"> -<!ELEMENT table:table (table:table-source?, table:scenario?, office:forms?, table:shapes?, (%table-column-groups;), (%table-row-groups;))> -<!ATTLIST table:table - table:name %string; #IMPLIED - table:style-name %styleName; #IMPLIED - table:protected %boolean; "false" - table:protection-key CDATA #IMPLIED - table:print-ranges %cell-range-address-list; #IMPLIED -> -<!ELEMENT table:table-source EMPTY> -<!ATTLIST table:table-source - table:mode (copy-all | copy-results-only) "copy-all" - xlink:type (simple) #FIXED "simple" - xlink:actuate (onRequest) "onRequest" - xlink:href %uriReference; #REQUIRED - table:filter-name CDATA #IMPLIED - table:table-name CDATA #IMPLIED - table:filter-options CDATA #IMPLIED - table:refresh-delay %timeDuration; #IMPLIED -> -<!ELEMENT table:scenario EMPTY> -<!ATTLIST table:scenario - table:display-border %boolean; "true" - table:border-color %color; #IMPLIED - table:copy-back %boolean; "true" - table:copy-styles %boolean; "true" - table:copy-formulas %boolean; "true" - table:is-active %boolean; #REQUIRED - table:scenario-ranges %cell-range-address-list; #REQUIRED - table:comment CDATA #IMPLIED -> -<!ELEMENT table:shapes %shapes;> -<!ELEMENT table:table-column-group (table:table-header-columns | table:table-column | table:table-column-group)+> -<!ATTLIST table:table-column-group - table:display %boolean; "true" -> -<!ELEMENT table:table-header-columns (table:table-column | table:table-column-group)+> -<!ELEMENT table:table-columns (table:table-column | table:table-column-group)+> -<!ELEMENT table:table-column EMPTY> -<!ATTLIST table:table-column - table:number-columns-repeated %positiveInteger; "1" - table:style-name %styleName; #IMPLIED - table:visibility (visible | collapse | filter) "visible" - table:default-cell-style-name %styleName; #IMPLIED -> -<!ELEMENT table:table-row-group (table:table-header-rows | table:table-row | table:table-row-group)+> -<!ATTLIST table:table-row-group - table:display %boolean; "true" -> -<!ELEMENT table:table-header-rows (table:table-row | table:table-row-group)+> -<!ELEMENT table:table-rows (table:table-row | table:table-row-group)+> -<!ENTITY % table-cells "(table:table-cell|table:covered-table-cell)+"> -<!ELEMENT table:table-row %table-cells;> -<!ATTLIST table:table-row - table:number-rows-repeated %positiveInteger; "1" - table:style-name %styleName; #IMPLIED - table:visibility (visible | collapse | filter) "visible" - table:default-cell-style-name %styleName; #IMPLIED -> - -<!ENTITY % text-wo-table "(text:h|text:p|text:ordered-list|text:unordered-list|%shapes;)*"> -<!ENTITY % cell-content "(table:cell-range-source?,office:annotation?,table:detective?,(table:sub-table|%text-wo-table;))"> -<!ELEMENT table:table-cell %cell-content;> -<!ELEMENT table:covered-table-cell %cell-content;> -<!ATTLIST table:table-cell - table:number-columns-repeated %positiveInteger; "1" - table:number-rows-spanned %positiveInteger; "1" - table:number-columns-spanned %positiveInteger; "1" - table:style-name %styleName; #IMPLIED - table:validation-name CDATA #IMPLIED - table:formula %string; #IMPLIED - table:number-matrix-rows-spanned %positiveInteger; #IMPLIED - table:number-matrix-columns-spanned %positiveInteger; #IMPLIED - table:value-type %valueType; "string" - table:value %float; #IMPLIED - table:date-value %date; #IMPLIED - table:time-value %timeInstance; #IMPLIED - table:boolean-value %boolean; #IMPLIED - table:string-value %string; #IMPLIED - table:currency %string; #IMPLIED -> -<!ATTLIST table:covered-table-cell - table:number-columns-repeated %positiveInteger; "1" - table:style-name %styleName; #IMPLIED - table:validation-name CDATA #IMPLIED - table:formula %string; #IMPLIED - table:number-matrix-rows-spanned %positiveInteger; #IMPLIED - table:number-matrix-columns-spanned %positiveInteger; #IMPLIED - table:value-type %valueType; "string" - table:value %float; #IMPLIED - table:date-value %date; #IMPLIED - table:time-value %timeInstance; #IMPLIED - table:boolean-value %boolean; #IMPLIED - table:string-value %string; #IMPLIED - table:currency %string; #IMPLIED -> -<!-- cell protection in writer: cell attribute; calc uses format --> -<!ATTLIST table:table-cell table:protected %boolean; "false"> - -<!ELEMENT table:cell-range-source EMPTY> -<!ATTLIST table:cell-range-source - table:name %string; #REQUIRED - xlink:type (simple) #FIXED "simple" - xlink:actuate (onRequest) #FIXED "onRequest" - xlink:href %uriReference; #REQUIRED - table:filter-name %string; #REQUIRED - table:filter-options %string; #IMPLIED - table:last-column-spanned %positiveInteger; #REQUIRED - table:last-row-spanned %positiveInteger; #REQUIRED - table:refresh-delay %timeDuration; #IMPLIED -> - -<!ELEMENT table:detective (table:highlighted-range*, table:operation*)> -<!ELEMENT table:highlighted-range EMPTY> -<!ATTLIST table:highlighted-range - table:cell-range-address %cell-range-address; #IMPLIED - table:direction (from-another-table | to-another-table | from-same-table | to-same-table) #IMPLIED - table:contains-error %boolean; #IMPLIED - table:marked-invalid %boolean; #IMPLIED -> -<!ELEMENT table:operation EMPTY> -<!ATTLIST table:operation - table:name (trace-dependents | remove-dependents | trace-precedents | remove-precedents | trace-errors) #REQUIRED - table:index %nonNegativeInteger; #REQUIRED -> - -<!ELEMENT table:content-validations (table:content-validation)+> -<!ELEMENT table:content-validation (table:help-message?, (table:error-message | (table:error-macro, office:events?))?)> -<!ATTLIST table:content-validation - table:name CDATA #REQUIRED - table:condition CDATA #IMPLIED - table:base-cell-address %cell-address; #IMPLIED - table:allow-empty-cell %boolean; #IMPLIED -> -<!ELEMENT table:help-message (text:p*)> -<!ATTLIST table:help-message - table:title CDATA #IMPLIED - table:display %boolean; #IMPLIED -> -<!ELEMENT table:error-message (text:p*)> -<!ATTLIST table:error-message - table:title CDATA #IMPLIED - table:message-type (stop | warning | information) #IMPLIED - table:display %boolean; #IMPLIED -> -<!ELEMENT table:error-macro EMPTY> -<!ATTLIST table:error-macro - table:name CDATA #IMPLIED - table:execute %boolean; #IMPLIED -> - -<!ELEMENT table:sub-table ((%table-column-groups;) , (%table-row-groups;))> - -<!ELEMENT table:label-ranges (table:label-range)*> -<!ELEMENT table:label-range EMPTY> -<!ATTLIST table:label-range - table:label-cell-range-address %cell-range-address; #REQUIRED - table:data-cell-range-address %cell-range-address; #REQUIRED - table:orientation (column | row) #REQUIRED -> - -<!ELEMENT table:named-expressions (table:named-range | table:named-expression)*> -<!ELEMENT table:named-range EMPTY> -<!ATTLIST table:named-range - table:name CDATA #REQUIRED - table:cell-range-address %cell-range-address; #REQUIRED - table:base-cell-address %cell-address; #IMPLIED - table:range-usable-as CDATA "none" -> -<!ELEMENT table:named-expression EMPTY> -<!ATTLIST table:named-expression - table:name CDATA #REQUIRED - table:expression CDATA #REQUIRED - table:base-cell-address %cell-address; #IMPLIED -> - -<!ELEMENT table:filter (table:filter-condition | table:filter-and | table:filter-or)> -<!ATTLIST table:filter - table:target-range-address %cell-range-address; #IMPLIED - table:condition-source-range-address %cell-range-address; #IMPLIED - table:condition-source (self | cell-range) "self" - table:display-duplicates %boolean; "true" -> -<!ELEMENT table:filter-and (table:filter-or | table:filter-condition)+> -<!ELEMENT table:filter-or (table:filter-and | table:filter-condition)+> -<!ELEMENT table:filter-condition EMPTY> -<!ATTLIST table:filter-condition - table:field-number %nonNegativeInteger; #REQUIRED - table:case-sensitive %boolean; "false" - table:data-type (text | number) "text" - table:value CDATA #REQUIRED - table:operator CDATA #REQUIRED -> - -<!ELEMENT table:database-ranges (table:database-range)*> -<!ELEMENT table:database-range ((table:database-source-sql | table:database-source-table | table:database-source-query)?, table:filter?, table:sort?, table:subtotal-rules?)> -<!ATTLIST table:database-range - table:name CDATA #IMPLIED - table:is-selection %boolean; "false" - table:on-update-keep-styles %boolean; "false" - table:on-update-keep-size %boolean; "true" - table:has-persistant-data %boolean; "true" - table:orientation (row | column) "row" - table:contains-header %boolean; "true" - table:display-filter-buttons %boolean; "false" - table:target-range-address %cell-range-address; #REQUIRED - table:refresh-delay %timeDuration; #IMPLIED -> -<!ELEMENT table:database-source-sql EMPTY> -<!ATTLIST table:database-source-sql - table:database-name CDATA #REQUIRED - table:sql-statement CDATA #REQUIRED - table:parse-sql-statements %boolean; "false" -> -<!ELEMENT table:database-source-table EMPTY> -<!ATTLIST table:database-source-table - table:database-name CDATA #REQUIRED - table:table-name CDATA #REQUIRED -> -<!ELEMENT table:database-source-query EMPTY> -<!ATTLIST table:database-source-query - table:database-name CDATA #REQUIRED - table:query-name CDATA #REQUIRED -> - -<!ELEMENT table:sort (table:sort-by)+> -<!ATTLIST table:sort - table:bind-styles-to-content %boolean; "true" - table:target-range-address %cell-range-address; #IMPLIED - table:case-sensitive %boolean; "false" - table:language CDATA #IMPLIED - table:country CDATA #IMPLIED - table:algorithm CDATA #IMPLIED -> -<!ELEMENT table:sort-by EMPTY> -<!ATTLIST table:sort-by - table:field-number %nonNegativeInteger; #REQUIRED - table:data-type CDATA "automatic" - table:order (ascending | descending) "ascending" -> - -<!ELEMENT table:subtotal-rules (table:sort-groups? | table:subtotal-rule*)?> -<!ATTLIST table:subtotal-rules - table:bind-styles-to-content %boolean; "true" - table:case-sensitive %boolean; "false" - table:page-breaks-on-group-change %boolean; "false" -> -<!ELEMENT table:sort-groups EMPTY> -<!ATTLIST table:sort-groups - table:data-type CDATA "automatic" - table:order (ascending | descending) "ascending" -> -<!ELEMENT table:subtotal-rule (table:subtotal-field)*> -<!ATTLIST table:subtotal-rule - table:group-by-field-number %nonNegativeInteger; #REQUIRED -> -<!ELEMENT table:subtotal-field EMPTY> -<!ATTLIST table:subtotal-field - table:field-number %nonNegativeInteger; #REQUIRED - table:function CDATA #REQUIRED -> - -<!ELEMENT table:data-pilot-tables (table:data-pilot-table)*> -<!ELEMENT table:data-pilot-table ((table:database-source-sql | table:database-source-table | table:database-source-query | table:source-service | table:source-cell-range)?, table:data-pilot-field+)> -<!ATTLIST table:data-pilot-table - table:name CDATA #REQUIRED - table:application-data CDATA #IMPLIED - table:grand-total (none | row | column | both) "both" - table:ignore-empty-rows %boolean; "false" - table:identify-categories %boolean; "false" - table:target-range-address %cell-range-address; #REQUIRED - table:buttons %cell-range-address-list; #REQUIRED -> -<!ELEMENT table:source-service EMPTY> -<!ATTLIST table:source-service - table:name CDATA #REQUIRED - table:source-name CDATA #REQUIRED - table:object-name CDATA #REQUIRED - table:username CDATA #IMPLIED - table:password CDATA #IMPLIED -> -<!ELEMENT table:source-cell-range (table:filter)?> -<!ATTLIST table:source-cell-range - table:cell-range-address %cell-range-address; #REQUIRED -> -<!ELEMENT table:data-pilot-field (table:data-pilot-level)?> -<!ATTLIST table:data-pilot-field - table:source-field-name CDATA #REQUIRED - table:is-data-layout-field %boolean; "false" - table:function CDATA #REQUIRED - table:orientation (row | column | data | page | hidden) #REQUIRED - table:used-hierarchy %positiveInteger; "1" -> -<!ELEMENT table:data-pilot-level (table:data-pilot-subtotals?, table:data-pilot-members?)> -<!ATTLIST table:data-pilot-level - table:display-empty %boolean; #IMPLIED -> -<!ELEMENT table:data-pilot-subtotals (table:data-pilot-subtotal)*> -<!ELEMENT table:data-pilot-subtotal EMPTY> -<!ATTLIST table:data-pilot-subtotal - table:function CDATA #REQUIRED -> -<!ELEMENT table:data-pilot-members (table:data-pilot-member)*> -<!ELEMENT table:data-pilot-member EMPTY> -<!ATTLIST table:data-pilot-member - table:name CDATA #REQUIRED - table:display %boolean; #IMPLIED - table:display-details %boolean; #IMPLIED -> - -<!ELEMENT table:consolidation EMPTY> -<!ATTLIST table:consolidation - table:function CDATA #REQUIRED - table:source-cell-range-addresses %cell-range-address-list; #REQUIRED - table:target-cell-address %cell-address; #REQUIRED - table:use-label (none | column | row | both) "none" - table:link-to-source-data %boolean; "false" -> - -<!ELEMENT table:dde-links (table:dde-link)+> -<!ELEMENT table:dde-link (office:dde-source, table:table)> - - -<!ENTITY % chart-class "(line|area|circle|ring|scatter|radar|bar|stock|add-in)"> -<!ENTITY % chart-solid-type "(cuboid|cylinder|cone|pyramid)"> - -<!-- Chart element --> -<!ELEMENT chart:chart ( chart:title?, chart:subtitle?, chart:legend?, - chart:plot-area, - table:table? )> -<!ATTLIST chart:chart - chart:class %chart-class; #REQUIRED - chart:add-in-name %string; #IMPLIED - chart:table-number-list %string; #IMPLIED - draw:name %string; #IMPLIED - %draw-position; - %draw-size; - %draw-style-name; - chart:column-mapping %string; #IMPLIED - chart:row-mapping %string; #IMPLIED - chart:style-name %styleName; #IMPLIED> - -<!ATTLIST chart:chart %presentation-class; > -<!ATTLIST chart:chart %zindex;> -<!ATTLIST chart:chart %draw-end-position; > -<!ATTLIST chart:chart draw:id %draw-shape-id; > -<!ATTLIST chart:chart draw:layer %layerName; #IMPLIED> - -<!ATTLIST style:properties - chart:scale-text %boolean; "true" - chart:stock-updown-bars %boolean; "false" - chart:stock-with-volume %boolean; "false" - chart:three-dimensional %boolean; "false" - chart:deep %boolean; "false" - chart:lines %boolean; "false" - chart:percentage %boolean; "false" - chart:solid-type %chart-solid-type; "cuboid" - chart:splines %nonNegativeInteger; "0" - chart:stacked %boolean; "false" - chart:symbol %integer; "-1" - chart:vertical %boolean; "false" - chart:lines-used %nonNegativeInteger; "0" - chart:connect-bars %boolean; "false" - chart:spline-order %nonNegativeInteger; "2" - chart:spline-resolution %nonNegativeInteger; "20" - chart:pie-offset %nonNegativeInteger; "0"> - -<!-- Main/Sub Title --> -<!-- the cell-address attribute is currently not supported for titles --> -<!ELEMENT chart:title (text:p)?> -<!ATTLIST chart:title - table:cell-range %cell-address; #IMPLIED - svg:x %coordinate; #IMPLIED - svg:y %coordinate; #IMPLIED - chart:style-name %styleName; #IMPLIED > - -<!ELEMENT chart:subtitle (text:p)?> -<!ATTLIST chart:subtitle - table:cell-range %cell-address; #IMPLIED - svg:x %coordinate; #IMPLIED - svg:y %coordinate; #IMPLIED - chart:style-name %styleName; #IMPLIED > - -<!-- you must specify either a legend-position or both, x and y coordinates --> -<!ELEMENT chart:legend EMPTY> -<!ATTLIST chart:legend - chart:legend-position (top|left|bottom|right) "right" - svg:x %coordinate; #IMPLIED - svg:y %coordinate; #IMPLIED - chart:style-name %styleName; #IMPLIED > - -<!-- Plot-Area specification --> - -<!ELEMENT chart:plot-area (dr3d:light*, - chart:axis*, - chart:categories?, - chart:series*, - chart:stock-gain-marker?, - chart:stock-loss-marker?, - chart:stock-range-line?, - chart:wall?, - chart:floor?) > - -<!ATTLIST chart:plot-area - svg:x %coordinate; #IMPLIED - svg:y %coordinate; #IMPLIED - svg:width %length; #IMPLIED - svg:height %length; #IMPLIED - chart:style-name %styleName; #IMPLIED - table:cell-range-address %cell-range-address; #IMPLIED - chart:table-number-list %string; #IMPLIED - chart:data-source-has-labels (none|row|column|both) "none" > - -<!-- 3d scene attributes on plot-area --> -<!ATTLIST chart:plot-area - dr3d:vrp %vector3D; #IMPLIED - dr3d:vpn %vector3D; #IMPLIED - dr3d:vup %vector3D; #IMPLIED - dr3d:projection (parallel|perspective) #IMPLIED - dr3d:transform CDATA #IMPLIED - dr3d:distance %length; #IMPLIED - dr3d:focal-length %length; #IMPLIED - dr3d:shadow-slant %nonNegativeInteger; #IMPLIED - dr3d:shade-mode (flat|phong|gouraud|draft) #IMPLIED - dr3d:ambient-color %color; #IMPLIED - dr3d:lighting-mode %boolean; #IMPLIED > - -<!ATTLIST style:properties - chart:series-source (columns|rows) "columns" > - -<!ELEMENT chart:wall EMPTY> -<!ATTLIST chart:wall - svg:width %length; #IMPLIED - chart:style-name %styleName; #IMPLIED > - -<!ELEMENT chart:floor EMPTY> -<!ATTLIST chart:floor - svg:width %length; #IMPLIED - chart:style-name %styleName; #IMPLIED > - -<!-- Stock chart elements --> - -<!ELEMENT chart:stock-gain-marker EMPTY> -<!ATTLIST chart:stock-gain-marker - chart:style-name %styleName; #IMPLIED > - -<!ELEMENT chart:stock-loss-marker EMPTY> -<!ATTLIST chart:stock-loss-marker - chart:style-name %styleName; #IMPLIED > - -<!ELEMENT chart:stock-range-line EMPTY> -<!ATTLIST chart:stock-range-line - chart:style-name %styleName; #IMPLIED > - -<!-- Axis --> - -<!ELEMENT chart:axis (chart:title?, chart:grid*)> -<!ATTLIST chart:axis - chart:class (category|value|series|domain) #REQUIRED - chart:name %string; #IMPLIED - chart:style-name %styleName; #IMPLIED > - -<!ATTLIST style:properties - chart:tick-marks-major-inner %boolean; "false" - chart:tick-marks-major-outer %boolean; "true" - chart:tick-marks-minor-inner %boolean; "false" - chart:tick-marks-minor-outer %boolean; "false" - chart:logarithmic %boolean; "false" - chart:maximum %float; #IMPLIED - chart:minimum %float; #IMPLIED - chart:origin %float; #IMPLIED - chart:interval-major %float; #IMPLIED - chart:interval-minor %float; #IMPLIED - chart:gap-width %integer; #IMPLIED - chart:overlap %integer; #IMPLIED - text:line-break %boolean; "true" - chart:display-label %boolean; "true" - chart:label-arrangement (side-by-side|stagger-even|stagger-odd) "side-by-side" - chart:text-overlap %boolean; "false" - chart:visible %boolean; "true" - chart:link-data-style-to-source %boolean; "true" > - -<!ELEMENT chart:grid EMPTY> -<!ATTLIST chart:grid - chart:class (major|minor) "major" - chart:style-name %styleName; #IMPLIED > - - -<!ELEMENT chart:categories EMPTY> -<!ATTLIST chart:categories - table:cell-range-address %cell-range-address; #IMPLIED > - -<!-- - each series element must have an cell-range-address element that points - to the underlying table data. - Impl. Note: Internally all href elements are merged to one table range - that represents the data for the whole chart ---> -<!ELEMENT chart:series ( chart:domain*, - chart:mean-value?, - chart:regression-curve?, - chart:error-indicator?, - chart:data-point* )> -<!ATTLIST chart:series - chart:values-cell-range-address %cell-range-address; #IMPLIED - chart:label-cell-address %cell-address; #IMPLIED - chart:class %chart-class; #IMPLIED - chart:attached-axis %string; #IMPLIED - chart:style-name %styleName; #IMPLIED > - -<!ELEMENT chart:domain EMPTY> -<!ATTLIST chart:domain - table:cell-range-address %cell-range-address; #IMPLIED > - -<!ELEMENT chart:data-point EMPTY> -<!ATTLIST chart:data-point - chart:repeated %nonNegativeInteger; #IMPLIED - chart:style-name %styleName; #IMPLIED > - -<!-- statistical properties --> - -<!ELEMENT chart:mean-value EMPTY> -<!ELEMENT chart:regression-curve EMPTY > -<!ELEMENT chart:error-indicator EMPTY > -<!ATTLIST chart:mean-value chart:style-name %styleName; #IMPLIED > -<!ATTLIST chart:regression-curve chart:style-name %styleName; #IMPLIED > -<!ATTLIST chart:error-indicator chart:style-name %styleName; #IMPLIED > - -<!ATTLIST style:properties - chart:mean-value %boolean; #IMPLIED - chart:error-category (none|variance|standard-deviation|percentage|error-margin|constant) "none" - chart:error-percentage %float; #IMPLIED - chart:error-margin %float; #IMPLIED - chart:error-lower-limit %float; #IMPLIED - chart:error-upper-limit %float; #IMPLIED - chart:error-upper-indicator %boolean; #IMPLIED - chart:error-lower-indicator %boolean; #IMPLIED - chart:regression-type (none|linear|logarithmic|exponential|power) "none" > - -<!-- data label properties --> - -<!ATTLIST style:properties - chart:data-label-number (none|value|percentage) "none" - chart:data-label-text %boolean; "false" - chart:data-label-symbol %boolean; "false" > - -<!-- general text properties --> - -<!ATTLIST style:properties - text:rotation-angle %integer; "0" > - -<!-- symbol properties --> - -<!ATTLIST style:properties - chart:symbol-width %nonNegativeLength; #IMPLIED - chart:symbol-height %nonNegativeLength; #IMPLIED - chart:symbol-image-name %string; #IMPLIED > - -<!-- data styles --> -<!ENTITY % any-number "( number:number | number:scientific-number | number:fraction )"> -<!ENTITY % number-style-content "( (number:text,(%any-number;,number:text?)?) | (%any-number;,number:text?) )"> -<!ELEMENT number:number-style ( style:properties?, %number-style-content;, style:map* )> -<!ELEMENT number:number ( number:embedded-text* )> -<!ELEMENT number:scientific-number EMPTY> -<!ELEMENT number:fraction EMPTY> - -<!ELEMENT number:embedded-text (#PCDATA)> -<!ATTLIST number:embedded-text number:position %integer; #REQUIRED> - -<!ENTITY % currency-symbol-and-text "number:currency-symbol,number:text?"> -<!ENTITY % number-and-text "number:number,number:text?"> -<!ENTITY % currency-symbol-and-number "((%number-and-text;),(%currency-symbol-and-text;)?) | ((%currency-symbol-and-text;),(%number-and-text;)?)"> -<!ENTITY % currency-style-content "number:text?, (%currency-symbol-and-number;)?"> - -<!ELEMENT number:currency-style ( style:properties?, (%currency-style-content;), style:map* )> -<!ELEMENT number:currency-symbol (#PCDATA)> -<!ATTLIST number:currency-symbol number:language CDATA #IMPLIED> -<!ATTLIST number:currency-symbol number:country CDATA #IMPLIED> - -<!ENTITY % percentage-style-content "( (number:text,(%number-and-text;)?) | (%number-and-text;) )"> -<!ELEMENT number:percentage-style ( style:properties?, %percentage-style-content;, style:map* )> - -<!ENTITY % any-date "( number:day | number:month | number:year | number:era | number:day-of-week | number:week-of-year | number:quarter| number:hours | number:am-pm | number:minutes | number:seconds )"> -<!ENTITY % date-style-content "( (number:text,(%any-date;,number:text?)+) | (%any-date;,number:text?)+ )"> -<!ELEMENT number:date-style ( style:properties?, %date-style-content;, style:map* )> -<!ELEMENT number:day EMPTY> -<!ATTLIST number:day number:style (short|long) "short"> -<!ATTLIST number:day number:calendar CDATA #IMPLIED> -<!ELEMENT number:month EMPTY> -<!ATTLIST number:month number:textual %boolean; "false"> -<!ATTLIST number:month number:style (short|long) "short"> -<!ATTLIST number:month number:calendar CDATA #IMPLIED> -<!ELEMENT number:year EMPTY> -<!ATTLIST number:year number:style (short|long) "short"> -<!ATTLIST number:year number:calendar CDATA #IMPLIED> -<!ELEMENT number:era EMPTY> -<!ATTLIST number:era number:style (short|long) "short"> -<!ATTLIST number:era number:calendar CDATA #IMPLIED> -<!ELEMENT number:day-of-week EMPTY> -<!ATTLIST number:day-of-week number:style (short|long) "short"> -<!ATTLIST number:day-of-week number:calendar CDATA #IMPLIED> -<!ELEMENT number:week-of-year EMPTY> -<!ATTLIST number:week-of-year number:calendar CDATA #IMPLIED> -<!ELEMENT number:quarter EMPTY> -<!ATTLIST number:quarter number:style (short|long) "short"> -<!ATTLIST number:quarter number:calendar CDATA #IMPLIED> - -<!ENTITY % any-time "( number:hours | number:am-pm | number:minutes | number:seconds )"> -<!ENTITY % time-style-content "( (number:text,(%any-time;,number:text?)+) | (%any-time;,number:text?)+)"> -<!ELEMENT number:time-style ( style:properties?, %time-style-content;, style:map* )> -<!ELEMENT number:hours EMPTY> -<!ATTLIST number:hours number:style (short|long) "short"> -<!ELEMENT number:minutes EMPTY> -<!ATTLIST number:minutes number:style (short|long) "short"> -<!ELEMENT number:seconds EMPTY> -<!ATTLIST number:seconds number:style (short|long) "short"> -<!ATTLIST number:seconds number:decimal-places %integer; "0"> -<!ELEMENT number:am-pm EMPTY> - -<!ENTITY % boolean-style-content "( (number:text,(number:boolean,number:text?)?) | (number:boolean,number:text?) )"> -<!ELEMENT number:boolean-style ( style:properties?,%boolean-style-content;, style:map* )> -<!ELEMENT number:boolean EMPTY> - -<!ENTITY % text-style-content "( (number:text,(number:text-content,number:text?)?) | (number:text-content,number:text?) )"> -<!ELEMENT number:text-style ( style:properties?,%text-style-content;, style:map* )> -<!ELEMENT number:text (#PCDATA)> -<!ELEMENT number:text-content EMPTY> - -<!ATTLIST number:number-style style:name %styleName; #REQUIRED> -<!ATTLIST number:currency-style style:name %styleName; #REQUIRED> -<!ATTLIST number:percentage-style style:name %styleName; #REQUIRED> -<!ATTLIST number:date-style style:name %styleName; #REQUIRED> -<!ATTLIST number:time-style style:name %styleName; #REQUIRED> -<!ATTLIST number:boolean-style style:name %styleName; #REQUIRED> -<!ATTLIST number:text-style style:name %styleName; #REQUIRED> - -<!ATTLIST number:number-style style:family CDATA #REQUIRED> -<!ATTLIST number:currency-style style:family CDATA #REQUIRED> -<!ATTLIST number:percentage-style style:family CDATA #REQUIRED> -<!ATTLIST number:date-style style:family CDATA #REQUIRED> -<!ATTLIST number:time-style style:family CDATA #REQUIRED> -<!ATTLIST number:boolean-style style:family CDATA #REQUIRED> -<!ATTLIST number:text-style style:family CDATA #REQUIRED> - -<!ATTLIST number:number-style number:language CDATA #IMPLIED> -<!ATTLIST number:currency-style number:language CDATA #IMPLIED> -<!ATTLIST number:percentage-style number:language CDATA #IMPLIED> -<!ATTLIST number:date-style number:language CDATA #IMPLIED> -<!ATTLIST number:time-style number:language CDATA #IMPLIED> -<!ATTLIST number:boolean-style number:language CDATA #IMPLIED> -<!ATTLIST number:text-style number:language CDATA #IMPLIED> - -<!ATTLIST number:number-style number:country CDATA #IMPLIED> -<!ATTLIST number:currency-style number:country CDATA #IMPLIED> -<!ATTLIST number:percentage-style number:country CDATA #IMPLIED> -<!ATTLIST number:date-style number:country CDATA #IMPLIED> -<!ATTLIST number:time-style number:country CDATA #IMPLIED> -<!ATTLIST number:boolean-style number:country CDATA #IMPLIED> -<!ATTLIST number:text-style number:country CDATA #IMPLIED> - -<!ATTLIST number:number-style number:title CDATA #IMPLIED> -<!ATTLIST number:currency-style number:title CDATA #IMPLIED> -<!ATTLIST number:percentage-style number:title CDATA #IMPLIED> -<!ATTLIST number:date-style number:title CDATA #IMPLIED> -<!ATTLIST number:time-style number:title CDATA #IMPLIED> -<!ATTLIST number:boolean-style number:title CDATA #IMPLIED> -<!ATTLIST number:text-style number:title CDATA #IMPLIED> - -<!ATTLIST number:number-style style:volatile %boolean; #IMPLIED> -<!ATTLIST number:currency-style style:volatile %boolean; #IMPLIED> -<!ATTLIST number:percentage-style style:volatile %boolean; #IMPLIED> -<!ATTLIST number:date-style style:volatile %boolean; #IMPLIED> -<!ATTLIST number:time-style style:volatile %boolean; #IMPLIED> -<!ATTLIST number:boolean-style style:volatile %boolean; #IMPLIED> -<!ATTLIST number:text-style style:volatile %boolean; #IMPLIED> - -<!ATTLIST number:number-style number:transliteration-format CDATA "1"> -<!ATTLIST number:currency-style number:transliteration-format CDATA "1"> -<!ATTLIST number:percentage-style number:transliteration-format CDATA "1"> -<!ATTLIST number:date-style number:transliteration-format CDATA "1"> -<!ATTLIST number:time-style number:transliteration-format CDATA "1"> -<!ATTLIST number:boolean-style number:transliteration-format CDATA "1"> -<!ATTLIST number:text-style number:transliteration-format CDATA "1"> - -<!ATTLIST number:number-style number:transliteration-language CDATA #IMPLIED> -<!ATTLIST number:currency-style number:transliteration-language CDATA #IMPLIED> -<!ATTLIST number:percentage-style number:transliteration-language CDATA #IMPLIED> -<!ATTLIST number:date-style number:transliteration-language CDATA #IMPLIED> -<!ATTLIST number:time-style number:transliteration-language CDATA #IMPLIED> -<!ATTLIST number:boolean-style number:transliteration-language CDATA #IMPLIED> -<!ATTLIST number:text-style number:transliteration-language CDATA #IMPLIED> - -<!ATTLIST number:number-style number:transliteration-country CDATA #IMPLIED> -<!ATTLIST number:currency-style number:transliteration-country CDATA #IMPLIED> -<!ATTLIST number:percentage-style number:transliteration-country CDATA #IMPLIED> -<!ATTLIST number:date-style number:transliteration-country CDATA #IMPLIED> -<!ATTLIST number:time-style number:transliteration-country CDATA #IMPLIED> -<!ATTLIST number:boolean-style number:transliteration-country CDATA #IMPLIED> -<!ATTLIST number:text-style number:transliteration-country CDATA #IMPLIED> - -<!ATTLIST number:number-style number:transliteration-style (short|medium|long) "short"> -<!ATTLIST number:currency-style number:transliteration-style (short|medium|long) "short"> -<!ATTLIST number:percentage-style number:transliteration-style (short|medium|long) "short"> -<!ATTLIST number:date-style number:transliteration-style (short|medium|long) "short"> -<!ATTLIST number:time-style number:transliteration-style (short|medium|long) "short"> -<!ATTLIST number:boolean-style number:transliteration-style (short|medium|long) "short"> -<!ATTLIST number:text-style number:transliteration-style (short|medium|long) "short"> - -<!ATTLIST number:currency-style number:automatic-order %boolean; "false"> -<!ATTLIST number:date-style number:automatic-order %boolean; "false"> - -<!ATTLIST number:date-style number:format-source (fixed|language) "fixed"> -<!ATTLIST number:time-style number:format-source (fixed|language) "fixed"> - -<!ATTLIST number:time-style number:truncate-on-overflow %boolean; "true"> - -<!ATTLIST number:number number:decimal-places %integer; #IMPLIED> -<!ATTLIST number:scientific-number number:decimal-places %integer; #IMPLIED> - -<!ATTLIST number:number number:min-integer-digits %integer; #IMPLIED> -<!ATTLIST number:scientific-number number:min-integer-digits %integer; #IMPLIED> -<!ATTLIST number:fraction number:min-integer-digits %integer; #IMPLIED> - -<!ATTLIST number:number number:grouping %boolean; "false"> -<!ATTLIST number:scientific-number number:grouping %boolean; "false"> -<!ATTLIST number:fraction number:grouping %boolean; "false"> - -<!ATTLIST number:number number:decimal-replacement CDATA #IMPLIED> - -<!ATTLIST number:number number:display-factor %float; "1"> - -<!ATTLIST number:scientific-number number:min-exponent-digits %integer; #IMPLIED> - -<!ATTLIST number:fraction number:min-numerator-digits %integer; #IMPLIED> - -<!ATTLIST number:fraction number:min-denominator-digits %integer; #IMPLIED> - - -<!ENTITY % controls "form:text|form:textarea|form:fixed-text|form:file| - form:password|form:formatted-text|form:button|form:image| - form:checkbox|form:radio|form:listbox|form:combobox|form:frame| - form:hidden|form:image-frame|form:grid|form:generic-control"> - -<!ENTITY % name "form:name CDATA #IMPLIED"> -<!ENTITY % service-name "form:service-name CDATA #IMPLIED"> - -<!ENTITY % navigation "(none|current|parent)"> -<!ENTITY % cycles "(records|current|page)"> -<!ENTITY % url "CDATA"> - - -<!ENTITY % types "(submit|reset|push|url)"> -<!ENTITY % button-type "form:button-type %types; 'push'"> -<!ENTITY % current-selected "form:current-selected %boolean; 'false'"> -<!ENTITY % current-value "form:current-value CDATA #IMPLIED"> -<!ENTITY % value "form:value CDATA #IMPLIED"> -<!ENTITY % disabled "form:disabled %boolean; 'false'"> -<!ENTITY % dropdown "form:dropdown %boolean; 'false'"> -<!ENTITY % for "form:for CDATA #IMPLIED"> -<!ENTITY % image-data "form:image-data %url; #IMPLIED"> -<!ENTITY % label "form:label CDATA #IMPLIED"> -<!ENTITY % max-length "form:max-length CDATA #IMPLIED"> -<!ENTITY % printable "form:printable %boolean; 'true'"> -<!ENTITY % readonly "form:readonly %boolean; 'false'"> -<!ENTITY % size "form:size CDATA #IMPLIED"> -<!ENTITY % selected "form:selected %boolean; 'false'"> -<!ENTITY % size "form:size CDATA #IMPLIED"> -<!ENTITY % tab-index "form:tab-index CDATA #IMPLIED"> -<!ENTITY % target-frame "office:target-frame CDATA '_blank'"> -<!ENTITY % target-location "xlink:href %url; #IMPLIED"> -<!ENTITY % tab-stop "form:tab-stop %boolean; 'true'"> -<!ENTITY % title "form:title CDATA #IMPLIED"> -<!ENTITY % default-value "form:default-value CDATA #IMPLIED"> -<!ENTITY % bound-column "form:bound-column CDATA #IMPLIED"> -<!ENTITY % convert-empty "form:convert-empty-to-null %boolean; 'false'"> -<!ENTITY % data-field "form:data-field CDATA #IMPLIED"> -<!ENTITY % list-source "form:list-source CDATA #IMPLIED"> -<!ENTITY % list-source-types "(table|query|sql|sql-pass-through|value-list|table-fields)"> -<!ENTITY % list-source-type "form:list-source-type %list-source-types; #IMPLIED"> -<!ENTITY % column-style-name "form:column-style-name %styleName; #IMPLIED"> - - -<!ELEMENT form:control (%controls;)+> -<!ATTLIST form:control %name; - %service-name; - %control-id;> - -<!ELEMENT form:form (form:properties?, office:events?, (form:control|form:form)*)> -<!ATTLIST form:form %name; %service-name;> -<!ATTLIST form:form xlink:href %url; #IMPLIED> -<!ATTLIST form:form form:enctype CDATA "application/x-www-form-urlencoded"> -<!ATTLIST form:form form:method CDATA "get"> -<!ATTLIST form:form office:target-frame CDATA "_blank"> -<!ATTLIST form:form form:allow-deletes %boolean; "true"> -<!ATTLIST form:form form:allow-inserts %boolean; "true"> -<!ATTLIST form:form form:allow-updates %boolean; "true"> -<!ATTLIST form:form form:apply-filter %boolean; "false"> -<!ATTLIST form:form form:command CDATA #IMPLIED> -<!ATTLIST form:form form:command-type (table|query|command) "command"> -<!ATTLIST form:form form:datasource CDATA #IMPLIED> -<!ATTLIST form:form form:detail-fields CDATA #IMPLIED> -<!ATTLIST form:form form:escape-processing %boolean; "true"> -<!ATTLIST form:form form:filter CDATA #IMPLIED> -<!ATTLIST form:form form:ignore-result %boolean; "false"> -<!ATTLIST form:form form:master-fields CDATA #IMPLIED> -<!ATTLIST form:form form:navigation-mode %navigation; #IMPLIED> -<!ATTLIST form:form form:order CDATA #IMPLIED> -<!ATTLIST form:form form:tab-cycle %cycles; #IMPLIED> - -<!ELEMENT office:forms (form:form*)> -<!ATTLIST office:forms form:automatic-focus %boolean; "false"> -<!ATTLIST office:forms form:apply-design-mode %boolean; "true"> - -<!ELEMENT form:text (form:properties?, office:events?)> -<!ATTLIST form:text %current-value; - %disabled; - %max-length; - %printable; - %readonly; - %tab-index; - %tab-stop; - %title; - %value; - %convert-empty; - %data-field;> - -<!ELEMENT form:textarea (form:properties?, office:events?)> -<!ATTLIST form:textarea %current-value; - %disabled; - %max-length; - %printable; - %readonly; - %tab-index; - %tab-stop; - %title; - %value; - %convert-empty; - %data-field;> - -<!ELEMENT form:password (form:properties?, office:events?)> -<!ATTLIST form:password %disabled; - %max-length; - %printable; - %tab-index; - %tab-stop; - %title; - %value; - %convert-empty;> - -<!ATTLIST form:password form:echo-char CDATA "*"> - -<!ELEMENT form:file (form:properties?, office:events?)> -<!ATTLIST form:file %current-value; - %disabled; - %max-length; - %printable; - %readonly; - %tab-index; - %tab-stop; - %title; - %value;> - -<!ELEMENT form:formatted-text (form:properties?, office:events?)> -<!ATTLIST form:formatted-text %current-value; - %disabled; - %max-length; - %printable; - %readonly; - %tab-index; - %tab-stop; - %title; - %value; - %convert-empty; - %data-field;> -<!ATTLIST form:formatted-text form:max-value CDATA #IMPLIED> -<!ATTLIST form:formatted-text form:min-value CDATA #IMPLIED> -<!ATTLIST form:formatted-text form:validation %boolean; "false"> - -<!ELEMENT form:fixed-text (form:properties?, office:events?)> -<!ATTLIST form:fixed-text %for; - %disabled; - %label; - %printable; - %title;> -<!ATTLIST form:fixed-text form:multi-line %boolean; "false"> - -<!ELEMENT form:combobox (form:properties?, office:events?, form:item*)> -<!ATTLIST form:combobox %current-value; - %disabled; - %dropdown; - %max-length; - %printable; - %readonly; - %size; - %tab-index; - %tab-stop; - %title; - %value; - %convert-empty; - %data-field; - %list-source; - %list-source-type;> -<!ATTLIST form:combobox form:auto-complete %boolean; #IMPLIED> - -<!ELEMENT form:item (#PCDATA)> -<!ATTLIST form:item %label;> - -<!ELEMENT form:listbox (form:properties?, office:events?, form:option*)> -<!ATTLIST form:listbox %disabled; - %dropdown; - %printable; - %size; - %tab-index; - %tab-stop; - %title; - %bound-column; - %data-field; - %list-source; - %list-source-type;> -<!ATTLIST form:listbox form:multiple %boolean; "false"> - -<!ELEMENT form:option (#PCDATA)> -<!ATTLIST form:option %current-selected; - %selected; - %label; - %value;> - -<!ELEMENT form:button (form:properties?, office:events?)> -<!ATTLIST form:button %button-type; - %disabled; - %label; - %image-data; - %printable; - %tab-index; - %tab-stop; - %target-frame; - %target-location; - %title; - %value;> -<!ATTLIST form:button form:default-button %boolean; "false"> - -<!ELEMENT form:image (form:properties?, office:events?)> -<!ATTLIST form:image %button-type; - %disabled; - %image-data; - %printable; - %tab-index; - %tab-stop; - %target-frame; - %target-location; - %title; - %value;> - -<!ELEMENT form:checkbox (form:properties?, office:events?)> -<!ATTLIST form:checkbox %disabled; - %label; - %printable; - %tab-index; - %tab-stop; - %title; - %value; - %data-field;> -<!ENTITY % states "(unchecked|checked|unknown)"> -<!ATTLIST form:checkbox form:current-state %states; #IMPLIED> -<!ATTLIST form:checkbox form:is-tristate %boolean; "false"> -<!ATTLIST form:checkbox form:state %states; "unchecked"> - -<!ELEMENT form:radio (form:properties?, office:events?)> -<!ATTLIST form:radio %current-selected; - %disabled; - %label; - %printable; - %selected; - %tab-index; - %tab-stop; - %title; - %value; - %data-field;> - -<!ELEMENT form:frame (form:properties?, office:events?)> -<!ATTLIST form:frame %disabled; - %for; - %label; - %printable; - %title;> - -<!ELEMENT form:image-frame (form:properties?, office:events?)> -<!ATTLIST form:image-frame %disabled; - %image-data; - %printable; - %readonly; - %title; - %data-field;> - -<!ELEMENT form:hidden (form:properties?, office:events?)> -<!ATTLIST form:hidden %name; - %service-name; - %value;> - -<!ELEMENT form:grid (form:properties?, office:events?, form:column*)> -<!ATTLIST form:grid %disabled; - %printable; - %tab-index; - %tab-stop; - %title;> - -<!ENTITY % column-type "form:text| form:textarea| form:formatted-text|form:checkbox| form:listbox| form:combobox"> -<!ELEMENT form:column (%column-type;)+> -<!ATTLIST form:column %name; - %service-name; - %label; - %column-style-name;> - -<!ELEMENT form:generic-control (form:properties?, office:events?)> - - -<!ELEMENT form:properties (form:property+)> -<!ELEMENT form:property (form:property-value*)> -<!ATTLIST form:property form:property-is-list %boolean; #IMPLIED> -<!ATTLIST form:property form:property-name CDATA #REQUIRED> -<!ATTLIST form:property form:property-type (boolean|short|int|long|double|string) #REQUIRED> -<!ELEMENT form:property-value (#PCDATA)> -<!ATTLIST form:property-value form:property-is-void %boolean; #IMPLIED> - - -<!ELEMENT office:settings (config:config-item-set+)> - -<!ENTITY % items "(config:config-item | - config:config-item-set | - config:config-item-map-named | - config:config-item-map-indexed)+"> - -<!ELEMENT config:config-item-set %items;> -<!ATTLIST config:config-item-set config:name CDATA #REQUIRED> - -<!ELEMENT config:config-item (#PCDATA)> -<!ATTLIST config:config-item config:name CDATA #REQUIRED - config:type (boolean | short | int | long | double | string | datetime | base64Binary) #REQUIRED> - -<!ELEMENT config:config-item-map-named (config:config-item-map-entry)+> -<!ATTLIST config:config-item-map-named config:name CDATA #REQUIRED> - -<!ELEMENT config:config-item-map-indexed (config:config-item-map-entry)+> -<!ATTLIST config:config-item-map-indexed config:name CDATA #REQUIRED> - -<!ELEMENT config:config-item-map-entry %items;> -<!ATTLIST config:config-item-map-entry config:name CDATA #IMPLIED> - rmfile ./examples/OpenOffice.org/office2.dtd hunk ./examples/OpenOffice.org/script.mod 1 -<!-- - $Id: script.mod,v 1.1 2003/05/13 13:07:54 malcolm Exp $ - - The Contents of this file are made available subject to the terms of - either of the following licenses - - - GNU Lesser General Public License Version 2.1 - - Sun Industry Standards Source License Version 1.1 - - Sun Microsystems Inc., October, 2000 - - GNU Lesser General Public License Version 2.1 - ============================================= - Copyright 2000 by Sun Microsystems, Inc. - 901 San Antonio Road, Palo Alto, CA 94303, USA - - This library is free software; you can redistribute it and/or - modify it under the terms of the GNU Lesser General Public - License version 2.1, as published by the Free Software Foundation. - - This library is distributed in the hope that it will be useful, - but WITHOUT ANY WARRANTY; without even the implied warranty of - MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU - Lesser General Public License for more details. - - You should have received a copy of the GNU Lesser General Public - License along with this library; if not, write to the Free Software - Foundation, Inc., 59 Temple Place, Suite 330, Boston, - MA 02111-1307 USA - - - Sun Industry Standards Source License Version 1.1 - ================================================= - The contents of this file are subject to the Sun Industry Standards - Source License Version 1.1 (the "License"); You may not use this file - except in compliance with the License. You may obtain a copy of the - License at http://www.openoffice.org/license.html. - - Software provided under this License is provided on an "AS IS" basis, - WITHOUT WARRANTY OF ANY KIND, EITHER EXPRESS OR IMPLIED, INCLUDING, - WITHOUT LIMITATION, WARRANTIES THAT THE SOFTWARE IS FREE OF DEFECTS, - MERCHANTABLE, FIT FOR A PARTICULAR PURPOSE, OR NON-INFRINGING. - See the License for the specific provisions governing your rights and - obligations concerning the Software. - - The Initial Developer of the Original Code is: Sun Microsystems, Inc. - - Copyright: 2000 by Sun Microsystems, Inc. - - All Rights Reserved. - - Contributor(s): _______________________________________ - ---> - -<!ELEMENT script:library-embedded (script:module*)> -<!ATTLIST script:library-embedded script:name %string; #REQUIRED> -<!ATTLIST script:library-embedded script:password %string; #IMPLIED> - -<!ELEMENT script:library-linked EMPTY> -<!ATTLIST script:library-linked script:name %string; #REQUIRED> -<!ATTLIST script:library-linked xlink:href %string; #REQUIRED> -<!ATTLIST script:library-linked xlink:type (simple) #FIXED "simple"> - -<!ELEMENT script:module (#PCDATA)> -<!ATTLIST script:module script:name %string; #REQUIRED> -<!ATTLIST script:module script:language %string; #IMPLIED> - - -<!ENTITY % script-language "script:language %string; #REQUIRED"> -<!ENTITY % event-name "script:event-name %string; #REQUIRED"> -<!ENTITY % location "script:location (document|application) #REQUIRED"> -<!ENTITY % macro-name "script:macro-name %string; #REQUIRED"> - -<!ELEMENT script:event (#PCDATA)> -<!ATTLIST script:event %script-language; - %event-name; - %location; - %macro-name;> rmfile ./examples/OpenOffice.org/script.mod hunk ./examples/OpenOffice.org/settings.mod 1 -<!-- - $Id: settings.mod,v 1.1 2003/05/13 13:07:54 malcolm Exp $ - - The Contents of this file are made available subject to the terms of - either of the following licenses - - - GNU Lesser General Public License Version 2.1 - - Sun Industry Standards Source License Version 1.1 - - Sun Microsystems Inc., October, 2000 - - GNU Lesser General Public License Version 2.1 - ============================================= - Copyright 2000 by Sun Microsystems, Inc. - 901 San Antonio Road, Palo Alto, CA 94303, USA - - This library is free software; you can redistribute it and/or - modify it under the terms of the GNU Lesser General Public - License version 2.1, as published by the Free Software Foundation. - - This library is distributed in the hope that it will be useful, - but WITHOUT ANY WARRANTY; without even the implied warranty of - MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU - Lesser General Public License for more details. - - You should have received a copy of the GNU Lesser General Public - License along with this library; if not, write to the Free Software - Foundation, Inc., 59 Temple Place, Suite 330, Boston, - MA 02111-1307 USA - - - Sun Industry Standards Source License Version 1.1 - ================================================= - The contents of this file are subject to the Sun Industry Standards - Source License Version 1.1 (the "License"); You may not use this file - except in compliance with the License. You may obtain a copy of the - License at http://www.openoffice.org/license.html. - - Software provided under this License is provided on an "AS IS" basis, - WITHOUT WARRANTY OF ANY KIND, EITHER EXPRESS OR IMPLIED, INCLUDING, - WITHOUT LIMITATION, WARRANTIES THAT THE SOFTWARE IS FREE OF DEFECTS, - MERCHANTABLE, FIT FOR A PARTICULAR PURPOSE, OR NON-INFRINGING. - See the License for the specific provisions governing your rights and - obligations concerning the Software. - - The Initial Developer of the Original Code is: Sun Microsystems, Inc. - - Copyright: 2000 by Sun Microsystems, Inc. - - All Rights Reserved. - - Contributor(s): _______________________________________ - ---> - -<!ELEMENT office:settings (config:config-item-set+)> - -<!ENTITY % items "(config:config-item | - config:config-item-set | - config:config-item-map-named | - config:config-item-map-indexed)+"> - -<!ELEMENT config:config-item-set %items;> -<!ATTLIST config:config-item-set config:name CDATA #REQUIRED> - -<!ELEMENT config:config-item (#PCDATA)> -<!ATTLIST config:config-item config:name CDATA #REQUIRED - config:type (boolean | short | int | long | double | string | datetime | base64Binary) #REQUIRED> - -<!ELEMENT config:config-item-map-named (config:config-item-map-entry)+> -<!ATTLIST config:config-item-map-named config:name CDATA #REQUIRED> - -<!ELEMENT config:config-item-map-indexed (config:config-item-map-entry)+> -<!ATTLIST config:config-item-map-indexed config:name CDATA #REQUIRED> - -<!ELEMENT config:config-item-map-entry %items;> -<!ATTLIST config:config-item-map-entry config:name CDATA #IMPLIED> rmfile ./examples/OpenOffice.org/settings.mod hunk ./examples/OpenOffice.org/style.mod 1 -<!-- - $Id: style.mod,v 1.1 2003/05/13 13:07:54 malcolm Exp $ - - The Contents of this file are made available subject to the terms of - either of the following licenses - - - GNU Lesser General Public License Version 2.1 - - Sun Industry Standards Source License Version 1.1 - - Sun Microsystems Inc., October, 2000 - - GNU Lesser General Public License Version 2.1 - ============================================= - Copyright 2000 by Sun Microsystems, Inc. - 901 San Antonio Road, Palo Alto, CA 94303, USA - - This library is free software; you can redistribute it and/or - modify it under the terms of the GNU Lesser General Public - License version 2.1, as published by the Free Software Foundation. - - This library is distributed in the hope that it will be useful, - but WITHOUT ANY WARRANTY; without even the implied warranty of - MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU - Lesser General Public License for more details. - - You should have received a copy of the GNU Lesser General Public - License along with this library; if not, write to the Free Software - Foundation, Inc., 59 Temple Place, Suite 330, Boston, - MA 02111-1307 USA - - - Sun Industry Standards Source License Version 1.1 - ================================================= - The contents of this file are subject to the Sun Industry Standards - Source License Version 1.1 (the "License"); You may not use this file - except in compliance with the License. You may obtain a copy of the - License at http://www.openoffice.org/license.html. - - Software provided under this License is provided on an "AS IS" basis, - WITHOUT WARRANTY OF ANY KIND, EITHER EXPRESS OR IMPLIED, INCLUDING, - WITHOUT LIMITATION, WARRANTIES THAT THE SOFTWARE IS FREE OF DEFECTS, - MERCHANTABLE, FIT FOR A PARTICULAR PURPOSE, OR NON-INFRINGING. - See the License for the specific provisions governing your rights and - obligations concerning the Software. - - The Initial Developer of the Original Code is: Sun Microsystems, Inc. - - Copyright: 2000 by Sun Microsystems, Inc. - - All Rights Reserved. - - Contributor(s): _______________________________________ - ---> - -<!ELEMENT style:font-decl EMPTY> -<!ATTLIST style:font-decl style:name %string; #REQUIRED> -<!ATTLIST style:font-decl fo:font-family %string; #REQUIRED> -<!ATTLIST style:font-decl style:font-style-name %string; #IMPLIED> -<!ENTITY % fontFamilyGeneric "(roman|swiss|modern|decorative|script|system)"> -<!ATTLIST style:font-decl style:font-family-generic %fontFamilyGeneric; - #IMPLIED> -<!ENTITY % fontPitch "(fixed|variable)"> -<!ATTLIST style:font-decl style:font-pitch %fontPitch; #IMPLIED> -<!ATTLIST style:font-decl style:font-charset %textEncoding; #IMPLIED> - -<!ELEMENT style:style ( style:properties?,office:events?,style:map*)> - -<!ATTLIST style:style style:name %styleName; #REQUIRED> - -<!ENTITY % styleFamily "(paragraph|text|section| - table|table-column|table-row|table-cell|table-page|chart|graphics|default|drawing-page|presentation|control|ruby)"> -<!ATTLIST style:style style:family %styleFamily; #REQUIRED> - -<!ATTLIST style:style style:parent-style-name %styleName; #IMPLIED> -<!ATTLIST style:style style:master-page-name %styleName; #IMPLIED> -<!ATTLIST style:style style:next-style-name %styleName; #IMPLIED> -<!ATTLIST style:style style:list-style-name %styleName; #IMPLIED> -<!ATTLIST style:style style:data-style-name %styleName; #IMPLIED> - -<!ATTLIST style:style style:auto-update %boolean; "false"> - -<!ATTLIST style:style style:class %string; #IMPLIED> - -<!ELEMENT style:default-style (style:properties?)> -<!ATTLIST style:default-style style:family %styleFamily; #REQUIRED> - -<!ELEMENT style:map EMPTY> - -<!ATTLIST style:map style:condition %string; #REQUIRED> -<!ATTLIST style:map style:apply-style-name %styleName; #REQUIRED> -<!ATTLIST style:map style:base-cell-address %cell-address; #IMPLIED> - -<!ELEMENT style:properties ANY> - -<!-- number format properties --> -<!ATTLIST style:properties style:num-prefix %string; #IMPLIED> -<!ATTLIST style:properties style:num-suffix %string; #IMPLIED> -<!ATTLIST style:properties style:num-format %string; #IMPLIED> -<!ATTLIST style:properties style:num-letter-sync %boolean; #IMPLIED> - -<!-- frame properties --> -<!ATTLIST style:properties fo:width %positiveLength; #IMPLIED> -<!ATTLIST style:properties fo:height %positiveLength; #IMPLIED> -<!ATTLIST style:properties style:vertical-pos (top|middle|bottom|from-top|below) #IMPLIED> -<!ATTLIST style:properties style:vertical-rel (page|page-content| - frame|frame-content| - paragraph|paragraph-content|char| - line|baseline|text) #IMPLIED> -<!ATTLIST style:properties style:horizontal-pos (left|center|right|from-left|inside|outside|from-inside) #IMPLIED> -<!ATTLIST style:properties style:horizontal-rel (page|page-content| - page-start-margin|page-end-margin| - frame|frame-content| - frame-start-margin|frame-end-margin| - paragraph|paragraph-content| - paragraph-start-margin|paragraph-end-margin| - char) #IMPLIED> -<!ATTLIST style:properties svg:width %lengthOrPercentage; #IMPLIED> -<!ATTLIST style:properties svg:height %lengthOrPercentage; #IMPLIED> -<!ATTLIST style:properties fo:min-height %lengthOrPercentage; #IMPLIED> -<!ATTLIST style:properties fo:min-width %lengthOrPercentage; #IMPLIED> -<!ATTLIST style:properties fo:max-height %lengthOrPercentage; #IMPLIED> -<!ATTLIST style:properties fo:max-width %lengthOrPercentage; #IMPLIED> -<!ATTLIST style:properties text:anchor-type %anchorType; #IMPLIED> -<!ATTLIST style:properties text:anchor-page-number %positiveInteger; #IMPLIED> -<!ATTLIST style:properties svg:x %coordinate; #IMPLIED> -<!ATTLIST style:properties svg:y %coordinate; #IMPLIED> -<!ATTLIST style:properties style:print-content %boolean; #IMPLIED> -<!ATTLIST style:properties style:protect %boolean; #IMPLIED> -<!ATTLIST style:properties style:wrap (none|left|right|parallel|dynamic|run-through) #IMPLIED> -<!ENTITY % noLimitOrPositiveInteger "CDATA"> -<!ATTLIST style:properties style:number-wrapped-paragraphs %noLimitOrPositiveInteger; #IMPLIED> -<!ATTLIST style:properties style:wrap-contour %boolean; #IMPLIED> -<!ATTLIST style:properties style:wrap-contour-mode (full|outside) #IMPLIED> -<!ATTLIST style:properties style:run-through (foreground|background) #IMPLIED> -<!ATTLIST style:properties style:editable %boolean; #IMPLIED> -<!ATTLIST style:properties style:mirror CDATA #IMPLIED> -<!ATTLIST style:properties fo:clip CDATA #IMPLIED> -<!ATTLIST style:properties text:animation (none|scroll|alternate|slide) #IMPLIED> -<!ATTLIST style:properties text:animation-direction (left|right|up|down) #IMPLIED> -<!ATTLIST style:properties text:animation-start-inside %boolean; #IMPLIED> -<!ATTLIST style:properties text:animation-stop-inside %boolean; #IMPLIED> -<!ATTLIST style:properties text:animation-repeat %integer; #IMPLIED> -<!ATTLIST style:properties text:animation-delay %timeDuration; #IMPLIED> -<!ATTLIST style:properties text:animation-steps %length; #IMPLIED> - -<!-- text properties --> -<!ATTLIST style:properties fo:font-variant (normal|small-caps) #IMPLIED> -<!ATTLIST style:properties fo:text-transform (none|lowercase| - uppercase|capitalize) #IMPLIED> -<!ATTLIST style:properties fo:color %color; #IMPLIED> -<!ATTLIST style:properties style:use-window-font-color %boolean; #IMPLIED> -<!ATTLIST style:properties style:text-outline %boolean; #IMPLIED> -<!ATTLIST style:properties style:text-crossing-out - (none|single-line|double-line|thick-line|slash|X) - #IMPLIED> -<!ATTLIST style:properties style:text-position CDATA #IMPLIED> -<!ATTLIST style:properties style:text-align (left|right|start|center|end|justify|justified) #IMPLIED> - -<!ATTLIST style:properties style:font-name %string; #IMPLIED> -<!ATTLIST style:properties fo:font-family %string; #IMPLIED> -<!ATTLIST style:properties style:font-family-generic %fontFamilyGeneric; - #IMPLIED> -<!ATTLIST style:properties style:font-style-name %string; #IMPLIED> -<!ATTLIST style:properties style:font-pitch %fontPitch; #IMPLIED> -<!ATTLIST style:properties style:font-charset %textEncoding; #IMPLIED> -<!ATTLIST style:properties style:font-name-asian %string; #IMPLIED> -<!ATTLIST style:properties style:font-family-asian %string; #IMPLIED> -<!ATTLIST style:properties style:font-family-generic-asian %fontFamilyGeneric; - #IMPLIED> -<!ATTLIST style:properties style:font-style-name-asian %string; #IMPLIED> -<!ATTLIST style:properties style:font-pitch-asian %fontPitch; #IMPLIED> -<!ATTLIST style:properties style:font-charset-asian %textEncoding; #IMPLIED> -<!ATTLIST style:properties style:font-name-complex %string; #IMPLIED> -<!ATTLIST style:properties style:font-family-complex %string; #IMPLIED> -<!ATTLIST style:properties style:font-family-generic-complex %fontFamilyGeneric; - #IMPLIED> -<!ATTLIST style:properties style:font-style-name-complex %string; #IMPLIED> -<!ATTLIST style:properties style:font-pitch-complex %fontPitch; #IMPLIED> -<!ATTLIST style:properties style:font-charset-complex %textEncoding; #IMPLIED> - -<!ATTLIST style:properties fo:font-size %positiveLengthOrPercentage; #IMPLIED> -<!ATTLIST style:properties style:font-size-rel %length; #IMPLIED> -<!ATTLIST style:properties style:font-size-asian %positiveLengthOrPercentage; #IMPLIED> -<!ATTLIST style:properties style:font-size-rel-asian %length; #IMPLIED> -<!ATTLIST style:properties style:font-size-complex %positiveLengthOrPercentage; #IMPLIED> -<!ATTLIST style:properties style:font-size-rel-complex %length; #IMPLIED> -<!ENTITY % normalOrLength "CDATA"> -<!ATTLIST style:properties fo:letter-spacing %normalOrLength; #IMPLIED> -<!ATTLIST style:properties fo:language %languageOnly; #IMPLIED> -<!ATTLIST style:properties style:language-asian %languageOnly; #IMPLIED> -<!ATTLIST style:properties style:language-complex %languageOnly; #IMPLIED> -<!ATTLIST style:properties fo:country %country; #IMPLIED> -<!ATTLIST style:properties style:country-asian %country; #IMPLIED> -<!ATTLIST style:properties style:country-complex %country; #IMPLIED> -<!ENTITY % fontStyle "(normal|italic|oblique)"> -<!ATTLIST style:properties fo:font-style %fontStyle; #IMPLIED> -<!ATTLIST style:properties style:font-style-asian %fontStyle; #IMPLIED> -<!ATTLIST style:properties style:font-style-complex %fontStyle; #IMPLIED> -<!ENTITY % fontRelief "(none|embossed|engraved)"> -<!ATTLIST style:properties style:font-relief %fontRelief; #IMPLIED> -<!ATTLIST style:properties fo:text-shadow CDATA #IMPLIED> -<!ATTLIST style:properties style:text-underline - (none|single|double|dotted|dash|long-dash|dot-dash| - dot-dot-dash|wave|bold|bold-dotted|bold-dash| - bold-long-dash|bold-dot-dash|bold-dot-dot-dash| - bold-wave|double-wave|small-wave) #IMPLIED> -<!ATTLIST style:properties style:text-autospace (none | ideograph-alpha) #IMPLIED> -<!ATTLIST style:properties style:punctuation-wrap (simple | hanging) #IMPLIED> -<!ATTLIST style:properties style:line-break (normal | strict) #IMPLIED> -<!ENTITY % fontColorOrColor "CDATA"> -<!ATTLIST style:properties style:text-underline-color %fontColorOrColor; - #IMPLIED> -<!ATTLIST style:properties fo:font-weight CDATA #IMPLIED> -<!ATTLIST style:properties style:font-weight-asian CDATA #IMPLIED> -<!ATTLIST style:properties style:font-weight-complex CDATA #IMPLIED> -<!ATTLIST style:properties fo:score-spaces %boolean; #IMPLIED> -<!ATTLIST style:properties style:letter-kerning %boolean; #IMPLIED> -<!ATTLIST style:properties style:text-blinking %boolean; #IMPLIED> -<!ATTLIST style:properties style:text-background-color %transparentOrColor; - #IMPLIED> - -<!ATTLIST style:properties style:text-combine (none|letters|lines) #IMPLIED> -<!ATTLIST style:properties style:text-combine-start-char %character; #IMPLIED> -<!ATTLIST style:properties style:text-combine-end-char %character; #IMPLIED> -<!ATTLIST style:properties style:text-emphasize CDATA #IMPLIED> -<!ATTLIST style:properties style:text-scale %percentage; #IMPLIED> -<!ATTLIST style:properties style:text-rotation-angle %integer; #IMPLIED> -<!ATTLIST style:properties style:text-rotation-scale (fixed|line-height) #IMPLIED> - -<!-- paragraph properties --> -<!ENTITY % nonNegativeLengthOrPercentageOrNormal "CDATA"> -<!ATTLIST style:properties fo:line-height - %nonNegativeLengthOrPercentageOrNormal; #IMPLIED> -<!ATTLIST style:properties style:line-height-at-least %nonNegativeLength; - #IMPLIED> -<!ATTLIST style:properties style:line-spacing %length; #IMPLIED> -<!ATTLIST style:properties fo:text-align (start|end|center|justify) #IMPLIED> -<!ATTLIST style:properties fo:text-align-last (start|center|justify) #IMPLIED> -<!ATTLIST style:properties style:text-align-source (fix|value-type) #IMPLIED> -<!ATTLIST style:properties style:justify-single-word %boolean; #IMPLIED> -<!ATTLIST style:properties style:break-inside (auto|avoid) #IMPLIED> -<!ATTLIST style:properties fo:widows %nonNegativeInteger; #IMPLIED> -<!ATTLIST style:properties fo:orphans %nonNegativeInteger; #IMPLIED> - -<!ATTLIST style:properties fo:hyphenate %boolean; #IMPLIED> -<!ATTLIST style:properties fo:hyphenate-keep (none|page) #IMPLIED> -<!ATTLIST style:properties fo:hyphenation-remain-char-count %positiveInteger; - #IMPLIED> -<!ATTLIST style:properties fo:hyphenation-push-char-count %positiveInteger; - #IMPLIED> -<!ATTLIST style:properties fo:hyphenation-ladder-count - %noLimitOrPositiveInteger; #IMPLIED> -<!ATTLIST style:properties style:page-number %positiveInteger; #IMPLIED> - -<!ELEMENT style:tab-stops (style:tab-stop)*> -<!ELEMENT style:tab-stop EMPTY> -<!ATTLIST style:tab-stop style:position %nonNegativeLength; #REQUIRED> -<!ATTLIST style:tab-stop style:type (left|center|right|char|default) "left"> -<!ATTLIST style:tab-stop style:char %character; #IMPLIED> -<!ATTLIST style:tab-stop style:leader-char %character; " "> - -<!ELEMENT style:drop-cap EMPTY> -<!ENTITY % wordOrPositiveInteger "CDATA"> -<!ATTLIST style:drop-cap style:length %wordOrPositiveInteger; "1"> -<!ATTLIST style:drop-cap style:lines %positiveInteger; "1"> -<!ATTLIST style:drop-cap style:distance %length; "0cm"> -<!ATTLIST style:drop-cap style:style-name %styleName; #IMPLIED> - -<!ATTLIST style:properties style:register-true %boolean; #IMPLIED> -<!ATTLIST style:properties style:register-truth-ref-style-name %styleName; #IMPLIED> -<!ATTLIST style:properties fo:margin-left %positiveLengthOrPercentage; #IMPLIED> -<!ATTLIST style:properties fo:margin-right %positiveLengthOrPercentage; - #IMPLIED> -<!ATTLIST style:properties fo:text-indent %lengthOrPercentage; #IMPLIED> -<!ATTLIST style:properties style:auto-text-indent %boolean; #IMPLIED> -<!ATTLIST style:properties fo:margin-top %positiveLengthOrPercentage; #IMPLIED> -<!ATTLIST style:properties fo:margin-bottom %positiveLengthOrPercentage; #IMPLIED> -<!ATTLIST style:properties fo:break-before (auto|column|page) #IMPLIED> -<!ATTLIST style:properties fo:break-after (auto|column|page) #IMPLIED> -<!ATTLIST style:properties fo:background-color %transparentOrColor; #IMPLIED> -<!ATTLIST style:properties style:background-transparency %percentage; #IMPLIED> -<!ATTLIST style:properties style:dynamic-spacing %boolean; #IMPLIED> - -<!ELEMENT style:background-image (office:binary-data?)> -<!ATTLIST style:background-image xlink:type (simple) #IMPLIED> -<!ATTLIST style:background-image xlink:href %uriReference; #IMPLIED> -<!ATTLIST style:background-image xlink:show (embed) #IMPLIED> -<!ATTLIST style:background-image xlink:actuate (onLoad) #IMPLIED> -<!ATTLIST style:background-image style:repeat (no-repeat|repeat|stretch) - "repeat"> -<!ATTLIST style:background-image style:position CDATA "center"> -<!ATTLIST style:background-image style:filter-name %string; #IMPLIED> -<!ATTLIST style:background-image draw:transparency %percentage; #IMPLIED> - -<!ELEMENT style:symbol-image (office:binary-data?)> -<!ATTLIST style:symbol-image xlink:type (simple) #IMPLIED> -<!ATTLIST style:symbol-image xlink:href %uriReference; #IMPLIED> -<!ATTLIST style:symbol-image xlink:show (embed) #IMPLIED> -<!ATTLIST style:symbol-image xlink:actuate (onLoad) #IMPLIED> - -<!ATTLIST style:properties fo:border CDATA #IMPLIED> -<!ATTLIST style:properties fo:border-top CDATA #IMPLIED> -<!ATTLIST style:properties fo:border-bottom CDATA #IMPLIED> -<!ATTLIST style:properties fo:border-left CDATA #IMPLIED> -<!ATTLIST style:properties fo:border-right CDATA #IMPLIED> -<!ATTLIST style:properties style:border-line-width CDATA #IMPLIED> -<!ATTLIST style:properties style:border-line-width-top CDATA #IMPLIED> -<!ATTLIST style:properties style:border-line-width-bottom CDATA #IMPLIED> -<!ATTLIST style:properties style:border-line-width-left CDATA #IMPLIED> -<!ATTLIST style:properties style:border-line-width-right CDATA #IMPLIED> -<!ATTLIST style:properties fo:padding %nonNegativeLength; #IMPLIED> -<!ATTLIST style:properties fo:padding-top %nonNegativeLength; #IMPLIED> -<!ATTLIST style:properties fo:padding-bottom %nonNegativeLength; #IMPLIED> -<!ATTLIST style:properties fo:padding-left %nonNegativeLength; #IMPLIED> -<!ATTLIST style:properties fo:padding-right %nonNegativeLength; #IMPLIED> -<!ATTLIST style:properties style:shadow CDATA #IMPLIED> -<!ATTLIST style:properties fo:keep-with-next %boolean; #IMPLIED> - -<!ATTLIST style:properties text:number-lines %boolean; "false"> -<!ATTLIST style:properties text:line-number %nonNegativeInteger; #IMPLIED> - -<!ATTLIST style:properties style:decimal-places %nonNegativeInteger; #IMPLIED> -<!ATTLIST style:properties style:tab-stop-distance %nonNegativeLength; #IMPLIED> - -<!-- section properties --> -<!ATTLIST style:properties text:dont-balance-text-columns %boolean; #IMPLIED> - -<!-- ruby properties --> -<!ATTLIST style:properties style:ruby-align (left|center|right|distribute-letter|distribute-space) #IMPLIED> -<!ATTLIST style:properties style:ruby-position (above|below) #IMPLIED> - - -<!-- table properties --> -<!ATTLIST style:properties style:width %positiveLength; #IMPLIED> -<!ATTLIST style:properties style:rel-width %percentage; #IMPLIED> -<!ATTLIST style:properties style:may-break-between-rows %boolean; #IMPLIED> -<!ATTLIST style:properties table:page-style-name %styleName; #IMPLIED> -<!ATTLIST style:properties table:display %boolean; #IMPLIED> - -<!-- table column properties --> -<!ATTLIST style:properties style:column-width %positiveLength; #IMPLIED> -<!ENTITY % relWidth "CDATA"> -<!ATTLIST style:properties style:rel-column-width %relWidth; #IMPLIED> -<!ATTLIST style:properties style:use-optimal-column-width %boolean; #IMPLIED> - -<!-- table row properties --> -<!ATTLIST style:properties style:row-height %positiveLength; #IMPLIED> -<!ATTLIST style:properties style:min-row-height %nonNegativeLength; #IMPLIED> -<!ATTLIST style:properties style:use-optimal-row-height %boolean; #IMPLIED> - -<!-- table cell properties --> -<!ATTLIST style:properties - table:align (left | center | right | margins) #IMPLIED - table:border-model (collapsing | separating) #IMPLIED - fo:vertical-align (top | middle | bottom | automatic) #IMPLIED - fo:direction (ltr | ttb) #IMPLIED - style:glyph-orientation-vertical (auto | 0) #IMPLIED - style:rotation-angle %nonNegativeInteger; #IMPLIED - style:rotation-align (none | bottom | top | center) #IMPLIED - style:cell-protect CDATA #IMPLIED - fo:wrap-option (no-wrap | wrap) #IMPLIED -> -<!ELEMENT style:columns (style:column-sep?,style:column*)> -<!ATTLIST style:columns fo:column-count %nonNegativeInteger; #IMPLIED> -<!ATTLIST style:columns fo:column-gap %positiveLength; #IMPLIED> - -<!ELEMENT style:column EMPTY> -<!ATTLIST style:column style:rel-width CDATA #IMPLIED> -<!ATTLIST style:column fo:margin-left %positiveLength; #IMPLIED> -<!ATTLIST style:column fo:margin-right %positiveLength; #IMPLIED> - -<!ELEMENT style:column-sep EMPTY> -<!ATTLIST style:column-sep style:style (none|solid|dotted|dashed|dot-dashed) - "solid"> -<!ATTLIST style:column-sep style:width %length; #REQUIRED> -<!ATTLIST style:column-sep style:height %percentage; "100%"> -<!ATTLIST style:column-sep style:vertical-align (top|middle|bottom) "top"> -<!ATTLIST style:column-sep style:color %color; "#000000"> - -<!-- page master properties --> -<!ELEMENT style:page-master (style:properties?, style:header-style?, style:footer-style?)> -<!ATTLIST style:page-master style:name %styleName; #REQUIRED> -<!ATTLIST style:page-master style:page-usage (all|left|right|mirrored) "all"> - -<!ELEMENT style:header-style (style:properties?)> -<!ELEMENT style:footer-style (style:properties?)> - -<!ATTLIST style:properties fo:page-width %length; #IMPLIED> -<!ATTLIST style:properties fo:page-height %length; #IMPLIED> -<!ATTLIST style:properties style:paper-tray-name %string; #IMPLIED> -<!ATTLIST style:properties style:print-orientation (portrait|landscape) #IMPLIED> -<!ATTLIST style:properties style:print CDATA #IMPLIED> -<!ATTLIST style:properties style:print-page-order (ttb|ltr) #IMPLIED> -<!ATTLIST style:properties style:first-page-number %positiveInteger; #IMPLIED> -<!ATTLIST style:properties style:scale-to %percentage; #IMPLIED> -<!ATTLIST style:properties style:scale-to-pages %positiveInteger; #IMPLIED> -<!ATTLIST style:properties style:table-centering (horizontal | vertical | both | none) #IMPLIED> - -<!ATTLIST style:properties style:footnote-max-height %lengthOrNoLimit; #IMPLIED> -<!ATTLIST style:properties style:vertical-align (top|bottom|middle|basline|auto) #IMPLIED> -<!ATTLIST style:properties style:writing-mode (lr-tb|rl-tb|tb-rl|tb-lr|lr|rl|tb|page) "lr-tb"> -<!ATTLIST style:properties style:layout-grid-mode (none|line|both) #IMPLIED> -<!ATTLIST style:properties style:layout-grid-base-height %length; #IMPLIED> -<!ATTLIST style:properties style:layout-grid-ruby-height %length; #IMPLIED> -<!ATTLIST style:properties style:layout-grid-lines %positiveInteger; #IMPLIED> -<!ATTLIST style:properties style:layout-grid-color %color; #IMPLIED> -<!ATTLIST style:properties style:layout-grid-ruby-below %boolean; #IMPLIED> -<!ATTLIST style:properties style:layout-grid-print %boolean; #IMPLIED> -<!ATTLIST style:properties style:layout-grid-display %boolean; #IMPLIED> -<!ATTLIST style:properties style:snap-to-layout-grid %boolean; #IMPLIED> - -<!ELEMENT style:footnote-sep EMPTY> -<!ATTLIST style:footnote-sep style:width %length; #IMPLIED> -<!ATTLIST style:footnote-sep style:rel-width %percentage; #IMPLIED> -<!ATTLIST style:footnote-sep style:color %color; #IMPLIED> -<!ATTLIST style:footnote-sep style:adjustment (left|center|right) "left"> -<!ATTLIST style:footnote-sep style:distance-before-sep %length; #IMPLIED> -<!ATTLIST style:footnote-sep style:distance-after-sep %length; #IMPLIED> - -<!-- master page --> -<!ELEMENT style:master-page ( (style:header, style:header-left?)?, (style:footer, style:footer-left?)?, - office:forms?,style:style*, (%shapes;)*, presentation:notes? )> -<!ATTLIST style:master-page style:name %styleName; #REQUIRED> -<!ATTLIST style:master-page style:page-master-name %styleName; #REQUIRED> -<!ATTLIST style:master-page style:next-style-name %styleName; #IMPLIED> -<!ATTLIST style:master-page draw:style-name %styleName; #IMPLIED> - -<!-- handout master --> -<!ELEMENT style:handout-master (%shapes;)*> -<!ATTLIST style:handout-master presentation:presentation-page-layout-name %styleName; #IMPLIED> -<!ATTLIST style:handout-master style:page-master-name %styleName; #IMPLIED> - - -<!ENTITY % hd-ft-content "( %headerText; | (style:region-left?, style:region-center?, style:region-right?) )"> -<!ELEMENT style:header %hd-ft-content;> -<!ATTLIST style:header style:display %boolean; "true"> -<!ELEMENT style:footer %hd-ft-content;> -<!ATTLIST style:footer style:display %boolean; "true"> -<!ELEMENT style:header-left %hd-ft-content;> -<!ATTLIST style:header-left style:display %boolean; "true"> -<!ELEMENT style:footer-left %hd-ft-content;> -<!ATTLIST style:footer-left style:display %boolean; "true"> - -<!ENTITY % region-content "(text:p*)"> -<!ELEMENT style:region-left %region-content;> -<!ELEMENT style:region-center %region-content;> -<!ELEMENT style:region-right %region-content;> rmfile ./examples/OpenOffice.org/style.mod hunk ./examples/OpenOffice.org/table.mod 1 -<!-- - $Id: table.mod,v 1.1 2003/05/13 13:07:54 malcolm Exp $ - - The Contents of this file are made available subject to the terms of - either of the following licenses - - - GNU Lesser General Public License Version 2.1 - - Sun Industry Standards Source License Version 1.1 - - Sun Microsystems Inc., October, 2000 - - GNU Lesser General Public License Version 2.1 - ============================================= - Copyright 2000 by Sun Microsystems, Inc. - 901 San Antonio Road, Palo Alto, CA 94303, USA - - This library is free software; you can redistribute it and/or - modify it under the terms of the GNU Lesser General Public - License version 2.1, as published by the Free Software Foundation. - - This library is distributed in the hope that it will be useful, - but WITHOUT ANY WARRANTY; without even the implied warranty of - MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU - Lesser General Public License for more details. - - You should have received a copy of the GNU Lesser General Public - License along with this library; if not, write to the Free Software - Foundation, Inc., 59 Temple Place, Suite 330, Boston, - MA 02111-1307 USA - - - Sun Industry Standards Source License Version 1.1 - ================================================= - The contents of this file are subject to the Sun Industry Standards - Source License Version 1.1 (the "License"); You may not use this file - except in compliance with the License. You may obtain a copy of the - License at http://www.openoffice.org/license.html. - - Software provided under this License is provided on an "AS IS" basis, - WITHOUT WARRANTY OF ANY KIND, EITHER EXPRESS OR IMPLIED, INCLUDING, - WITHOUT LIMITATION, WARRANTIES THAT THE SOFTWARE IS FREE OF DEFECTS, - MERCHANTABLE, FIT FOR A PARTICULAR PURPOSE, OR NON-INFRINGING. - See the License for the specific provisions governing your rights and - obligations concerning the Software. - - The Initial Developer of the Original Code is: Sun Microsystems, Inc. - - Copyright: 2000 by Sun Microsystems, Inc. - - All Rights Reserved. - - Contributor(s): _______________________________________ - ---> - -<!ELEMENT table:calculation-settings (table:null-date?, table:iteration?)> -<!ATTLIST table:calculation-settings - table:case-sensitive %boolean; "true" - table:precision-as-shown %boolean; "false" - table:search-criteria-must-apply-to-whole-cell %boolean; "true" - table:automatic-find-labels %boolean; "true" - table:use-regular-expressions %boolean; "true" - table:null-year %positiveInteger; "1930" -> -<!ELEMENT table:null-date EMPTY> -<!ATTLIST table:null-date - table:value-type %valueType; #FIXED "date" - table:date-value %date; "1899-12-30" -> -<!ELEMENT table:iteration EMPTY> -<!ATTLIST table:iteration - table:status (enable | disable) "disable" - table:steps %positiveInteger; "100" - table:maximum-difference %float; "0.001" -> - -<!ELEMENT table:tracked-changes (table:cell-content-change | table:insertion | table:deletion | table:movement | table:rejection)*> -<!ATTLIST table:tracked-changes table:track-changes %boolean; "true" - table:protected %boolean; "false" - table:protection-key CDATA #IMPLIED -> - -<!ELEMENT table:dependences (table:dependence)+> -<!ELEMENT table:dependence EMPTY> -<!ATTLIST table:dependence - table:id CDATA #REQUIRED -> -<!ELEMENT table:deletions (table:cell-content-deletion | table:change-deletion)+> -<!ELEMENT table:cell-content-deletion (table:cell-address?, table:change-track-table-cell?)> -<!ATTLIST table:cell-content-deletion - table:id CDATA #IMPLIED -> -<!ELEMENT table:change-deletion EMPTY> -<!ATTLIST table:change-deletion - table:id CDATA #IMPLIED -> -<!ELEMENT table:insertion (office:change-info, table:dependences?, table:deletions?)> -<!ATTLIST table:insertion - table:id CDATA #REQUIRED - table:acceptance-state (accepted | rejected | pending) "pending" - table:rejecting-change-id %positiveInteger; #IMPLIED - table:type (row | column | table) #REQUIRED - table:position %integer; #REQUIRED - table:count %positiveInteger; "1" - table:table %integer; #IMPLIED -> -<!ELEMENT table:deletion (office:change-info, table:dependences?, table:deletions?, table:cut-offs?)> -<!ATTLIST table:deletion - table:id CDATA #REQUIRED - table:acceptance-state (accepted | rejected | pending) "pending" - table:rejecting-change-id %positiveInteger; #IMPLIED - table:type (row | column | table) #REQUIRED - table:position %integer; #REQUIRED - table:count %positiveInteger; "1" - table:table %integer; #IMPLIED - table:multi-deletion-spanned %integer; #IMPLIED -> -<!ELEMENT table:cut-offs (table:movement-cut-off+ | (table:insertion-cut-off, table:movement-cut-off*))> -<!ELEMENT table:insertion-cut-off EMPTY> -<!ATTLIST table:insertion-cut-off - table:id CDATA #REQUIRED - table:position %integer; #REQUIRED -> -<!ELEMENT table:movement-cut-off EMPTY> -<!ATTLIST table:movement-cut-off - table:id CDATA #REQUIRED - table:start-position %integer; #IMPLIED - table:end-position %integer; #IMPLIED - table:position %integer; #IMPLIED -> -<!ELEMENT table:movement (table:source-range-address, table:target-range-address, office:change-info, table:dependences?, table:deletions?)> -<!ATTLIST table:movement - table:id CDATA #REQUIRED - table:acceptance-state (accepted | rejected | pending) "pending" - table:rejecting-change-id %positiveInteger; #IMPLIED -> -<!ELEMENT table:target-range-address EMPTY> -<!ATTLIST table:target-range-address - table:column %integer; #IMPLIED - table:row %integer; #IMPLIED - table:table %integer; #IMPLIED - table:start-column %integer; #IMPLIED - table:start-row %integer; #IMPLIED - table:start-table %integer; #IMPLIED - table:end-column %integer; #IMPLIED - table:end-row %integer; #IMPLIED - table:end-table %integer; #IMPLIED -> -<!ELEMENT table:source-range-address EMPTY> -<!ATTLIST table:source-range-address - table:column %integer; #IMPLIED - table:row %integer; #IMPLIED - table:table %integer; #IMPLIED - table:start-column %integer; #IMPLIED - table:start-row %integer; #IMPLIED - table:start-table %integer; #IMPLIED - table:end-column %integer; #IMPLIED - table:end-row %integer; #IMPLIED - table:end-table %integer; #IMPLIED -> -<!ELEMENT table:change-track-table-cell (text:p*)> -<!ATTLIST table:change-track-table-cell - table:cell-address %cell-address; #IMPLIED - table:matrix-covered (true | false) "false" - table:formula %string; #IMPLIED - table:number-matrix-rows-spanned %positiveInteger; #IMPLIED - table:number-matrix-columns-spanned %positiveInteger; #IMPLIED - table:value-type %valueType; "string" - table:value %float; #IMPLIED - table:date-value %date; #IMPLIED - table:time-value %timeInstance; #IMPLIED - table:string-value %string; #IMPLIED -> -<!ELEMENT table:cell-content-change (table:cell-address, office:change-info, table:dependences?, table:deletions?, table:previous)> -<!ATTLIST table:cell-content-change - table:id CDATA #REQUIRED - table:acceptance-state (accepted | rejected | pending) "pending" - table:rejecting-change-id %positiveInteger; #IMPLIED -> -<!ELEMENT table:cell-address EMPTY> -<!ATTLIST table:cell-address - table:column %integer; #IMPLIED - table:row %integer; #IMPLIED - table:table %integer; #IMPLIED -> -<!ELEMENT table:previous (table:change-track-table-cell)> -<!ATTLIST table:previous - table:id CDATA #IMPLIED -> -<!ELEMENT table:rejection (office:change-info, table:dependences?, table:deletions?)> -<!ATTLIST table:rejection - table:id CDATA #REQUIRED - table:acceptance-state (accepted | rejected | pending) "pending" - table:rejecting-change-id %positiveInteger; #IMPLIED -> - -<!ENTITY % table-columns "table:table-columns | ( table:table-column | table:table-column-group )+"> -<!ENTITY % table-header-columns "table:table-header-columns"> -<!ENTITY % table-rows "table:table-rows | ( table:table-row | table:table-row-group )+"> -<!ENTITY % table-header-rows "table:table-header-rows"> -<!ENTITY % table-column-groups "((%table-columns;),(%table-header-columns;,(%table-columns;)?)?) | (%table-header-columns;,(%table-columns;)?)"> -<!ENTITY % table-row-groups "((%table-rows;),(%table-header-rows;,(%table-rows;)?)?) | (%table-header-rows;,(%table-rows;)?)"> -<!ELEMENT table:table (table:table-source?, table:scenario?, office:forms?, table:shapes?, (%table-column-groups;), (%table-row-groups;))> -<!ATTLIST table:table - table:name %string; #IMPLIED - table:style-name %styleName; #IMPLIED - table:protected %boolean; "false" - table:protection-key CDATA #IMPLIED - table:print-ranges %cell-range-address-list; #IMPLIED -> -<!ELEMENT table:table-source EMPTY> -<!ATTLIST table:table-source - table:mode (copy-all | copy-results-only) "copy-all" - xlink:type (simple) #FIXED "simple" - xlink:actuate (onRequest) "onRequest" - xlink:href %uriReference; #REQUIRED - table:filter-name CDATA #IMPLIED - table:table-name CDATA #IMPLIED - table:filter-options CDATA #IMPLIED - table:refresh-delay %timeDuration; #IMPLIED -> -<!ELEMENT table:scenario EMPTY> -<!ATTLIST table:scenario - table:display-border %boolean; "true" - table:border-color %color; #IMPLIED - table:copy-back %boolean; "true" - table:copy-styles %boolean; "true" - table:copy-formulas %boolean; "true" - table:is-active %boolean; #REQUIRED - table:scenario-ranges %cell-range-address-list; #REQUIRED - table:comment CDATA #IMPLIED -> -<!ELEMENT table:shapes %shapes;> -<!ELEMENT table:table-column-group (table:table-header-columns | table:table-column | table:table-column-group)+> -<!ATTLIST table:table-column-group - table:display %boolean; "true" -> -<!ELEMENT table:table-header-columns (table:table-column | table:table-column-group)+> -<!ELEMENT table:table-columns (table:table-column | table:table-column-group)+> -<!ELEMENT table:table-column EMPTY> -<!ATTLIST table:table-column - table:number-columns-repeated %positiveInteger; "1" - table:style-name %styleName; #IMPLIED - table:visibility (visible | collapse | filter) "visible" - table:default-cell-style-name %styleName; #IMPLIED -> -<!ELEMENT table:table-row-group (table:table-header-rows | table:table-row | table:table-row-group)+> -<!ATTLIST table:table-row-group - table:display %boolean; "true" -> -<!ELEMENT table:table-header-rows (table:table-row | table:table-row-group)+> -<!ELEMENT table:table-rows (table:table-row | table:table-row-group)+> -<!ENTITY % table-cells "(table:table-cell|table:covered-table-cell)+"> -<!ELEMENT table:table-row %table-cells;> -<!ATTLIST table:table-row - table:number-rows-repeated %positiveInteger; "1" - table:style-name %styleName; #IMPLIED - table:visibility (visible | collapse | filter) "visible" - table:default-cell-style-name %styleName; #IMPLIED -> - -<!ENTITY % text-wo-table "(text:h|text:p|text:ordered-list|text:unordered-list|%shapes;)*"> -<!ENTITY % cell-content "(table:cell-range-source?,office:annotation?,table:detective?,(table:sub-table|%text-wo-table;))"> -<!ELEMENT table:table-cell %cell-content;> -<!ELEMENT table:covered-table-cell %cell-content;> -<!ATTLIST table:table-cell - table:number-columns-repeated %positiveInteger; "1" - table:number-rows-spanned %positiveInteger; "1" - table:number-columns-spanned %positiveInteger; "1" - table:style-name %styleName; #IMPLIED - table:validation-name CDATA #IMPLIED - table:formula %string; #IMPLIED - table:number-matrix-rows-spanned %positiveInteger; #IMPLIED - table:number-matrix-columns-spanned %positiveInteger; #IMPLIED - table:value-type %valueType; "string" - table:value %float; #IMPLIED - table:date-value %date; #IMPLIED - table:time-value %timeInstance; #IMPLIED - table:boolean-value %boolean; #IMPLIED - table:string-value %string; #IMPLIED - table:currency %string; #IMPLIED -> -<!ATTLIST table:covered-table-cell - table:number-columns-repeated %positiveInteger; "1" - table:style-name %styleName; #IMPLIED - table:validation-name CDATA #IMPLIED - table:formula %string; #IMPLIED - table:number-matrix-rows-spanned %positiveInteger; #IMPLIED - table:number-matrix-columns-spanned %positiveInteger; #IMPLIED - table:value-type %valueType; "string" - table:value %float; #IMPLIED - table:date-value %date; #IMPLIED - table:time-value %timeInstance; #IMPLIED - table:boolean-value %boolean; #IMPLIED - table:string-value %string; #IMPLIED - table:currency %string; #IMPLIED -> -<!-- cell protection in writer: cell attribute; calc uses format --> -<!ATTLIST table:table-cell table:protected %boolean; "false"> - -<!ELEMENT table:cell-range-source EMPTY> -<!ATTLIST table:cell-range-source - table:name %string; #REQUIRED - xlink:type (simple) #FIXED "simple" - xlink:actuate (onRequest) #FIXED "onRequest" - xlink:href %uriReference; #REQUIRED - table:filter-name %string; #REQUIRED - table:filter-options %string; #IMPLIED - table:last-column-spanned %positiveInteger; #REQUIRED - table:last-row-spanned %positiveInteger; #REQUIRED - table:refresh-delay %timeDuration; #IMPLIED -> - -<!ELEMENT table:detective (table:highlighted-range*, table:operation*)> -<!ELEMENT table:highlighted-range EMPTY> -<!ATTLIST table:highlighted-range - table:cell-range-address %cell-range-address; #IMPLIED - table:direction (from-another-table | to-another-table | from-same-table | to-same-table) #IMPLIED - table:contains-error %boolean; #IMPLIED - table:marked-invalid %boolean; #IMPLIED -> -<!ELEMENT table:operation EMPTY> -<!ATTLIST table:operation - table:name (trace-dependents | remove-dependents | trace-precedents | remove-precedents | trace-errors) #REQUIRED - table:index %nonNegativeInteger; #REQUIRED -> - -<!ELEMENT table:content-validations (table:content-validation)+> -<!ELEMENT table:content-validation (table:help-message?, (table:error-message | (table:error-macro, office:events?))?)> -<!ATTLIST table:content-validation - table:name CDATA #REQUIRED - table:condition CDATA #IMPLIED - table:base-cell-address %cell-address; #IMPLIED - table:allow-empty-cell %boolean; #IMPLIED -> -<!ELEMENT table:help-message (text:p*)> -<!ATTLIST table:help-message - table:title CDATA #IMPLIED - table:display %boolean; #IMPLIED -> -<!ELEMENT table:error-message (text:p*)> -<!ATTLIST table:error-message - table:title CDATA #IMPLIED - table:message-type (stop | warning | information) #IMPLIED - table:display %boolean; #IMPLIED -> -<!ELEMENT table:error-macro EMPTY> -<!ATTLIST table:error-macro - table:name CDATA #IMPLIED - table:execute %boolean; #IMPLIED -> - -<!ELEMENT table:sub-table ((%table-column-groups;) , (%table-row-groups;))> - -<!ELEMENT table:label-ranges (table:label-range)*> -<!ELEMENT table:label-range EMPTY> -<!ATTLIST table:label-range - table:label-cell-range-address %cell-range-address; #REQUIRED - table:data-cell-range-address %cell-range-address; #REQUIRED - table:orientation (column | row) #REQUIRED -> - -<!ELEMENT table:named-expressions (table:named-range | table:named-expression)*> -<!ELEMENT table:named-range EMPTY> -<!ATTLIST table:named-range - table:name CDATA #REQUIRED - table:cell-range-address %cell-range-address; #REQUIRED - table:base-cell-address %cell-address; #IMPLIED - table:range-usable-as CDATA "none" -> -<!ELEMENT table:named-expression EMPTY> -<!ATTLIST table:named-expression - table:name CDATA #REQUIRED - table:expression CDATA #REQUIRED - table:base-cell-address %cell-address; #IMPLIED -> - -<!ELEMENT table:filter (table:filter-condition | table:filter-and | table:filter-or)> -<!ATTLIST table:filter - table:target-range-address %cell-range-address; #IMPLIED - table:condition-source-range-address %cell-range-address; #IMPLIED - table:condition-source (self | cell-range) "self" - table:display-duplicates %boolean; "true" -> -<!ELEMENT table:filter-and (table:filter-or | table:filter-condition)+> -<!ELEMENT table:filter-or (table:filter-and | table:filter-condition)+> -<!ELEMENT table:filter-condition EMPTY> -<!ATTLIST table:filter-condition - table:field-number %nonNegativeInteger; #REQUIRED - table:case-sensitive %boolean; "false" - table:data-type (text | number) "text" - table:value CDATA #REQUIRED - table:operator CDATA #REQUIRED -> - -<!ELEMENT table:database-ranges (table:database-range)*> -<!ELEMENT table:database-range ((table:database-source-sql | table:database-source-table | table:database-source-query)?, table:filter?, table:sort?, table:subtotal-rules?)> -<!ATTLIST table:database-range - table:name CDATA #IMPLIED - table:is-selection %boolean; "false" - table:on-update-keep-styles %boolean; "false" - table:on-update-keep-size %boolean; "true" - table:has-persistant-data %boolean; "true" - table:orientation (row | column) "row" - table:contains-header %boolean; "true" - table:display-filter-buttons %boolean; "false" - table:target-range-address %cell-range-address; #REQUIRED - table:refresh-delay %timeDuration; #IMPLIED -> -<!ELEMENT table:database-source-sql EMPTY> -<!ATTLIST table:database-source-sql - table:database-name CDATA #REQUIRED - table:sql-statement CDATA #REQUIRED - table:parse-sql-statements %boolean; "false" -> -<!ELEMENT table:database-source-table EMPTY> -<!ATTLIST table:database-source-table - table:database-name CDATA #REQUIRED - table:table-name CDATA #REQUIRED -> -<!ELEMENT table:database-source-query EMPTY> -<!ATTLIST table:database-source-query - table:database-name CDATA #REQUIRED - table:query-name CDATA #REQUIRED -> - -<!ELEMENT table:sort (table:sort-by)+> -<!ATTLIST table:sort - table:bind-styles-to-content %boolean; "true" - table:target-range-address %cell-range-address; #IMPLIED - table:case-sensitive %boolean; "false" - table:language CDATA #IMPLIED - table:country CDATA #IMPLIED - table:algorithm CDATA #IMPLIED -> -<!ELEMENT table:sort-by EMPTY> -<!ATTLIST table:sort-by - table:field-number %nonNegativeInteger; #REQUIRED - table:data-type CDATA "automatic" - table:order (ascending | descending) "ascending" -> - -<!ELEMENT table:subtotal-rules (table:sort-groups? | table:subtotal-rule*)?> -<!ATTLIST table:subtotal-rules - table:bind-styles-to-content %boolean; "true" - table:case-sensitive %boolean; "false" - table:page-breaks-on-group-change %boolean; "false" -> -<!ELEMENT table:sort-groups EMPTY> -<!ATTLIST table:sort-groups - table:data-type CDATA "automatic" - table:order (ascending | descending) "ascending" -> -<!ELEMENT table:subtotal-rule (table:subtotal-field)*> -<!ATTLIST table:subtotal-rule - table:group-by-field-number %nonNegativeInteger; #REQUIRED -> -<!ELEMENT table:subtotal-field EMPTY> -<!ATTLIST table:subtotal-field - table:field-number %nonNegativeInteger; #REQUIRED - table:function CDATA #REQUIRED -> - -<!ELEMENT table:data-pilot-tables (table:data-pilot-table)*> -<!ELEMENT table:data-pilot-table ((table:database-source-sql | table:database-source-table | table:database-source-query | table:source-service | table:source-cell-range)?, table:data-pilot-field+)> -<!ATTLIST table:data-pilot-table - table:name CDATA #REQUIRED - table:application-data CDATA #IMPLIED - table:grand-total (none | row | column | both) "both" - table:ignore-empty-rows %boolean; "false" - table:identify-categories %boolean; "false" - table:target-range-address %cell-range-address; #REQUIRED - table:buttons %cell-range-address-list; #REQUIRED -> -<!ELEMENT table:source-service EMPTY> -<!ATTLIST table:source-service - table:name CDATA #REQUIRED - table:source-name CDATA #REQUIRED - table:object-name CDATA #REQUIRED - table:username CDATA #IMPLIED - table:password CDATA #IMPLIED -> -<!ELEMENT table:source-cell-range (table:filter)?> -<!ATTLIST table:source-cell-range - table:cell-range-address %cell-range-address; #REQUIRED -> -<!ELEMENT table:data-pilot-field (table:data-pilot-level)?> -<!ATTLIST table:data-pilot-field - table:source-field-name CDATA #REQUIRED - table:is-data-layout-field %boolean; "false" - table:function CDATA #REQUIRED - table:orientation (row | column | data | page | hidden) #REQUIRED - table:used-hierarchy %positiveInteger; "1" -> -<!ELEMENT table:data-pilot-level (table:data-pilot-subtotals?, table:data-pilot-members?)> -<!ATTLIST table:data-pilot-level - table:display-empty %boolean; #IMPLIED -> -<!ELEMENT table:data-pilot-subtotals (table:data-pilot-subtotal)*> -<!ELEMENT table:data-pilot-subtotal EMPTY> -<!ATTLIST table:data-pilot-subtotal - table:function CDATA #REQUIRED -> -<!ELEMENT table:data-pilot-members (table:data-pilot-member)*> -<!ELEMENT table:data-pilot-member EMPTY> -<!ATTLIST table:data-pilot-member - table:name CDATA #REQUIRED - table:display %boolean; #IMPLIED - table:display-details %boolean; #IMPLIED -> - -<!ELEMENT table:consolidation EMPTY> -<!ATTLIST table:consolidation - table:function CDATA #REQUIRED - table:source-cell-range-addresses %cell-range-address-list; #REQUIRED - table:target-cell-address %cell-address; #REQUIRED - table:use-label (none | column | row | both) "none" - table:link-to-source-data %boolean; "false" -> - -<!ELEMENT table:dde-links (table:dde-link)+> -<!ELEMENT table:dde-link (office:dde-source, table:table)> rmfile ./examples/OpenOffice.org/table.mod hunk ./examples/OpenOffice.org/text.mod 1 -<!-- - $Id: text.mod,v 1.1 2003/05/13 13:07:54 malcolm Exp $ - - The Contents of this file are made available subject to the terms of - either of the following licenses - - - GNU Lesser General Public License Version 2.1 - - Sun Industry Standards Source License Version 1.1 - - Sun Microsystems Inc., October, 2000 - - GNU Lesser General Public License Version 2.1 - ============================================= - Copyright 2000 by Sun Microsystems, Inc. - 901 San Antonio Road, Palo Alto, CA 94303, USA - - This library is free software; you can redistribute it and/or - modify it under the terms of the GNU Lesser General Public - License version 2.1, as published by the Free Software Foundation. - - This library is distributed in the hope that it will be useful, - but WITHOUT ANY WARRANTY; without even the implied warranty of - MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU - Lesser General Public License for more details. - - You should have received a copy of the GNU Lesser General Public - License along with this library; if not, write to the Free Software - Foundation, Inc., 59 Temple Place, Suite 330, Boston, - MA 02111-1307 USA - - - Sun Industry Standards Source License Version 1.1 - ================================================= - The contents of this file are subject to the Sun Industry Standards - Source License Version 1.1 (the "License"); You may not use this file - except in compliance with the License. You may obtain a copy of the - License at http://www.openoffice.org/license.html. - - Software provided under this License is provided on an "AS IS" basis, - WITHOUT WARRANTY OF ANY KIND, EITHER EXPRESS OR IMPLIED, INCLUDING, - WITHOUT LIMITATION, WARRANTIES THAT THE SOFTWARE IS FREE OF DEFECTS, - MERCHANTABLE, FIT FOR A PARTICULAR PURPOSE, OR NON-INFRINGING. - See the License for the specific provisions governing your rights and - obligations concerning the Software. - - The Initial Developer of the Original Code is: Sun Microsystems, Inc. - - Copyright: 2000 by Sun Microsystems, Inc. - - All Rights Reserved. - - Contributor(s): _______________________________________ - ---> - -<!ENTITY % fields "text:date | - text:time | - text:page-number | - text:page-continuation | - text:sender-firstname | - text:sender-lastname | - text:sender-initials | - text:sender-title | - text:sender-position | - text:sender-email | - text:sender-phone-private | - text:sender-fax | - text:sender-company | - text:sender-phone-work | - text:sender-street | - text:sender-city | - text:sender-postal-code | - text:sender-country | - text:sender-state-or-province | - text:author-name | - text:author-initials | - text:placeholder | - text:variable-set | - text:variable-get | - text:variable-input | - text:user-field-get | - text:user-field-input | - text:sequence | - text:expression | - text:text-input | - text:database-display | - text:database-next | - text:database-select | - text:database-row-number | - text:database-name | - text:initial-creator | - text:creation-date | - text:creation-time | - text:description | - text:user-defined | - text:print-time | - text:print-date | - text:printed-by | - text:title | - text:subject | - text:keywords | - text:editing-cycles | - text:editing-duration | - text:modification-time | - text:modification-date | - text:creator | - text:conditional-text | - text:hidden-text | - text:hidden-paragraph | - text:chapter | - text:file-name | - text:template-name | - text:page-variable-set | - text:page-variable-get | - text:execute-macro | - text:dde-connection | - text:reference-ref | - text:sequence-ref | - text:bookmark-ref | - text:footnote-ref | - text:endnote-ref | - text:sheet-name | - text:bibliography-mark | - text:page-count | - text:paragraph-count | - text:word-count | - text:character-count | - text:table-count | - text:image-count | - text:object-count | - office:annotation | - text:script | - text:measure" > - -<!ENTITY % inline-text-elements " - text:span|text:tab-stop|text:s|text:line-break| - text:footnote|text:endnote|text:a| - text:bookmark|text:bookmark-start|text:bookmark-end| - text:reference-mark|text:reference-mark-start| - text:reference-mark-end|%fields;|%shape;| - text:toc-mark-start | text:toc-mark-end | - text:toc-mark | text:user-index-mark-start | - text:user-index-mark-end | text:user-index-mark | - text:alphabetical-index-mark-start | - text:alphabetical-index-mark-end | - text:alphabetical-index-mark | - %change-marks; | draw:a | text:ruby"> - -<!ENTITY % inline-text "( #PCDATA | %inline-text-elements; )*"> - -<!ELEMENT text:p %inline-text;> -<!ELEMENT text:h %inline-text;> - -<!ATTLIST text:p text:style-name %styleName; #IMPLIED> -<!ATTLIST text:p text:cond-style-name %styleName; #IMPLIED> - -<!ATTLIST text:h text:style-name %styleName; #IMPLIED> -<!ATTLIST text:h text:cond-style-name %styleName; #IMPLIED> -<!ATTLIST text:h text:level %positiveInteger; "1"> - -<!ELEMENT text:span %inline-text;> -<!ATTLIST text:span text:style-name %styleName; #REQUIRED> - -<!ELEMENT text:a (#PCDATA | office:events | %inline-text-elements;)*> -<!ATTLIST text:a xlink:href %uriReference; #REQUIRED> -<!ATTLIST text:a xlink:type (simple) #FIXED "simple"> -<!ATTLIST text:a xlink:actuate (onRequest) "onRequest"> -<!ATTLIST text:a xlink:show (new|replace) "replace"> -<!ATTLIST text:a office:name %string; #IMPLIED> -<!ATTLIST text:a office:target-frame-name %string; #IMPLIED> -<!ATTLIST text:a text:style-name %styleName; #IMPLIED> -<!ATTLIST text:a text:visited-style-name %styleName; #IMPLIED> - - -<!ELEMENT text:s EMPTY> -<!ATTLIST text:s text:c %positiveInteger; "1"> - -<!ELEMENT text:tab-stop EMPTY> - -<!ELEMENT text:line-break EMPTY> - - -<!ENTITY % list-items "((text:list-header,text:list-item*)|text:list-item+)"> -<!ELEMENT text:ordered-list %list-items;> -<!ELEMENT text:unordered-list %list-items;> - - -<!ATTLIST text:ordered-list text:style-name %styleName; #IMPLIED> -<!ATTLIST text:unordered-list text:style-name %styleName; #IMPLIED> - -<!ATTLIST text:ordered-list text:continue-numbering %boolean; "false"> - -<!ELEMENT text:list-header (text:p|text:h)+> -<!ELEMENT text:list-item (text:p|text:h|text:ordered-list|text:unordered-list)+> - -<!ATTLIST text:list-item text:restart-numbering %boolean; "false"> -<!ATTLIST text:list-item text:start-value %positiveInteger; #IMPLIED> - -<!ELEMENT text:list-style (text:list-level-style-number| - text:list-level-style-bullet| - text:list-level-style-image)+> - -<!ATTLIST text:list-style style:name %styleName; #IMPLIED> - -<!ATTLIST text:list-style text:consecutive-numbering %boolean; "false"> - - -<!ELEMENT text:list-level-style-number (style:properties?)> - -<!ATTLIST text:list-level-style-number text:level %positiveInteger; - #REQUIRED> -<!ATTLIST text:list-level-style-number text:style-name %styleName; #IMPLIED> - -<!ATTLIST text:list-level-style-number style:num-format %string; #REQUIRED> -<!ATTLIST text:list-level-style-number style:num-prefix %string; #IMPLIED> -<!ATTLIST text:list-level-style-number style:num-suffix %string; #IMPLIED> -<!ATTLIST text:list-level-style-number style:num-letter-sync %boolean; - "false"> -<!ATTLIST text:list-level-style-number text:display-levels %positiveInteger; - "1"> -<!ATTLIST text:list-level-style-number text:start-value %positiveInteger; - "1"> -<!ELEMENT text:list-level-style-bullet (style:properties?)> - -<!ATTLIST text:list-level-style-bullet text:level %positiveInteger; #REQUIRED> -<!ATTLIST text:list-level-style-bullet text:style-name %styleName; #IMPLIED> -<!ATTLIST text:list-level-style-bullet text:bullet-char %character; #REQUIRED> -<!ATTLIST text:list-level-style-bullet style:num-prefix %string; #IMPLIED> -<!ATTLIST text:list-level-style-bullet style:num-suffix %string; #IMPLIED> - -<!ELEMENT text:list-level-style-image (style:properties?,office:binary-data?)> - -<!ATTLIST text:list-level-style-image text:level %positiveInteger; #REQUIRED> -<!ATTLIST text:list-level-style-image xlink:type (simple) #IMPLIED> -<!ATTLIST text:list-level-style-image xlink:href %uriReference; #IMPLIED> -<!ATTLIST text:list-level-style-image xlink:actuate (onLoad) #IMPLIED> -<!ATTLIST text:list-level-style-image xlink:show (embed) #IMPLIED> - - -<!-- list properties --> -<!ATTLIST style:properties text:space-before %nonNegativeLength; #IMPLIED> -<!ATTLIST style:properties text:min-label-width %nonNegativeLength; #IMPLIED> -<!ATTLIST style:properties text:min-label-distance %nonNegativeLength; #IMPLIED> -<!ATTLIST style:properties text:enable-numbering %boolean; #IMPLIED> -<!ATTLIST style:properties style:list-style-name %styleName; #IMPLIED> - -<!ELEMENT text:outline-style (text:outline-level-style)+> - -<!ELEMENT text:outline-level-style (style:properties?)> - -<!ATTLIST text:outline-level-style text:level %positiveInteger; - #REQUIRED> -<!ATTLIST text:outline-level-style text:style-name %styleName; #IMPLIED> - -<!ATTLIST text:outline-level-style style:num-format %string; #REQUIRED> -<!ATTLIST text:outline-level-style style:num-prefix %string; #IMPLIED> -<!ATTLIST text:outline-level-style style:num-suffix %string; #IMPLIED> -<!ATTLIST text:outline-level-style style:num-letter-sync %boolean; - "false"> -<!ATTLIST text:outline-level-style text:display-levels %positiveInteger; - "1"> -<!ATTLIST text:outline-level-style text:start-value %positiveInteger; - "1"> - -<!ENTITY % field-declarations "text:variable-decls?, - text:user-field-decls?, - text:sequence-decls?"> - -<!ENTITY % variableName "CDATA"> - -<!ENTITY % formula "CDATA"> - -<!ENTITY % valueAttr "text:value-type %valueType; #IMPLIED - text:currency CDATA #IMPLIED" > - -<!ENTITY % valueAndTypeAttr "%valueAttr; - text:value %float; #IMPLIED - text:date-value %date; #IMPLIED - text:time-value %timeInstance; #IMPLIED - text:boolean-value %boolean; #IMPLIED - text:string-value %string; #IMPLIED" > - -<!ENTITY % numFormat 'style:num-format CDATA #IMPLIED - style:num-letter-sync %boolean; "false"'> - - -<!ELEMENT text:date (#PCDATA)> -<!ATTLIST text:date text:date-value %timeInstance; #IMPLIED> -<!ATTLIST text:date text:date-adjust %dateDuration; #IMPLIED> -<!ATTLIST text:date text:fixed %boolean; "false"> -<!ATTLIST text:date style:data-style-name %styleName; #IMPLIED> - -<!ELEMENT text:time (#PCDATA)> -<!ATTLIST text:time text:time-value %timeInstance; #IMPLIED> -<!ATTLIST text:time text:time-adjust %timeDuration; #IMPLIED> -<!ATTLIST text:time text:fixed %boolean; "false"> -<!ATTLIST text:time style:data-style-name %styleName; #IMPLIED> - -<!ELEMENT text:page-number (#PCDATA)> -<!ATTLIST text:page-number text:page-adjust %positiveInteger; #IMPLIED> -<!ATTLIST text:page-number text:select-page (previous|current|next) "current"> -<!ATTLIST text:page-number %numFormat;> - -<!ELEMENT text:page-continuation (#PCDATA)> -<!ATTLIST text:page-continuation text:select-page (previous|next) #REQUIRED> -<!ATTLIST text:page-continuation text:string-value %string; #IMPLIED> - -<!ELEMENT text:sender-firstname (#PCDATA)> -<!ATTLIST text:sender-firstname text:fixed %boolean; "true"> - -<!ELEMENT text:sender-lastname (#PCDATA)> -<!ATTLIST text:sender-lastname text:fixed %boolean; "true"> - -<!ELEMENT text:sender-initials (#PCDATA)> -<!ATTLIST text:sender-initials text:fixed %boolean; "true"> - -<!ELEMENT text:sender-title (#PCDATA)> -<!ATTLIST text:sender-title text:fixed %boolean; "true"> - -<!ELEMENT text:sender-position (#PCDATA)> -<!ATTLIST text:sender-position text:fixed %boolean; "true"> - -<!ELEMENT text:sender-email (#PCDATA)> -<!ATTLIST text:sender-email text:fixed %boolean; "true"> - -<!ELEMENT text:sender-phone-private (#PCDATA)> -<!ATTLIST text:sender-phone-private text:fixed %boolean; "true"> - -<!ELEMENT text:sender-fax (#PCDATA)> -<!ATTLIST text:sender-fax text:fixed %boolean; "true"> - -<!ELEMENT text:sender-company (#PCDATA)> -<!ATTLIST text:sender-company text:fixed %boolean; "true"> - -<!ELEMENT text:sender-phone-work (#PCDATA)> -<!ATTLIST text:sender-phone-work text:fixed %boolean; "true"> - -<!ELEMENT text:sender-street (#PCDATA)> -<!ATTLIST text:sender-street text:fixed %boolean; "true"> - -<!ELEMENT text:sender-city (#PCDATA)> -<!ATTLIST text:sender-city text:fixed %boolean; "true"> - -<!ELEMENT text:sender-postal-code (#PCDATA)> -<!ATTLIST text:sender-postal-code text:fixed %boolean; "true"> - -<!ELEMENT text:sender-country (#PCDATA)> -<!ATTLIST text:sender-country text:fixed %boolean; "true"> - -<!ELEMENT text:sender-state-or-province (#PCDATA)> -<!ATTLIST text:sender-state-or-province text:fixed %boolean; "true"> - -<!ELEMENT text:author-name (#PCDATA)> -<!ATTLIST text:author-name text:fixed %boolean; "true"> - -<!ELEMENT text:author-initials (#PCDATA)> -<!ATTLIST text:author-initials text:fixed %boolean; "true"> - -<!ELEMENT text:placeholder (#PCDATA)> -<!ATTLIST text:placeholder text:placeholder-type (text|table|text-box|image|object) #REQUIRED> -<!ATTLIST text:placeholder text:description %string; #IMPLIED> - -<!ELEMENT text:variable-decls (text:variable-decl)*> - -<!ELEMENT text:variable-decl EMPTY> -<!ATTLIST text:variable-decl text:name %variableName; #REQUIRED> -<!ATTLIST text:variable-decl %valueAndTypeAttr;> - -<!ELEMENT text:variable-set (#PCDATA)> -<!ATTLIST text:variable-set text:name %variableName; #REQUIRED> -<!ATTLIST text:variable-set text:formula %formula; #IMPLIED> -<!ATTLIST text:variable-set %valueAndTypeAttr;> -<!ATTLIST text:variable-set text:display (value|none) "value"> -<!ATTLIST text:variable-set style:data-style-name %styleName; #IMPLIED> - -<!ELEMENT text:variable-get (#PCDATA)> -<!ATTLIST text:variable-get text:name %variableName; #REQUIRED> -<!ATTLIST text:variable-get text:display (value|formula) "value"> -<!ATTLIST text:variable-get style:data-style-name %styleName; #IMPLIED> -<!ATTLIST text:variable-get %valueAttr;> - -<!ELEMENT text:variable-input (#PCDATA)> -<!ATTLIST text:variable-input text:name %variableName; #REQUIRED> -<!ATTLIST text:variable-input text:description %string; #IMPLIED> -<!ATTLIST text:variable-input %valueAndTypeAttr;> -<!ATTLIST text:variable-input text:display (value|none) "value"> -<!ATTLIST text:variable-input style:data-style-name %styleName; #IMPLIED> - -<!ELEMENT text:user-field-decls (text:user-field-decl)*> - -<!ELEMENT text:user-field-decl EMPTY> -<!ATTLIST text:user-field-decl text:name %variableName; #REQUIRED> -<!ATTLIST text:user-field-decl text:formula %formula; #IMPLIED> -<!ATTLIST text:user-field-decl %valueAndTypeAttr;> - -<!ELEMENT text:user-field-get (#PCDATA)> -<!ATTLIST text:user-field-get text:name %variableName; #REQUIRED> -<!ATTLIST text:user-field-get text:display (value|formula|none) "value"> -<!ATTLIST text:user-field-get style:data-style-name %styleName; #IMPLIED> - -<!ELEMENT text:user-field-input (#PCDATA)> -<!ATTLIST text:user-field-input text:name %variableName; #REQUIRED> -<!ATTLIST text:user-field-input text:description %string; #IMPLIED> -<!ATTLIST text:user-field-input style:data-style-name %styleName; #IMPLIED> - -<!ELEMENT text:sequence-decls (text:sequence-decl)*> - -<!ELEMENT text:sequence-decl EMPTY> -<!ATTLIST text:sequence-decl text:name %variableName; #REQUIRED> -<!ATTLIST text:sequence-decl text:display-outline-level %positiveInteger; "0"> -<!ATTLIST text:sequence-decl text:separation-character %character; "."> - -<!ELEMENT text:sequence (#PCDATA)> -<!ATTLIST text:sequence text:name %variableName; #REQUIRED> -<!ATTLIST text:sequence text:formula %formula; #IMPLIED> -<!ATTLIST text:sequence %numFormat;> -<!ATTLIST text:sequence text:ref-name ID #IMPLIED> - -<!ELEMENT text:expression (#PCDATA)> -<!ATTLIST text:expression text:formula %formula; #IMPLIED> -<!ATTLIST text:expression text:display (value|formula ) "value"> -<!ATTLIST text:expression %valueAndTypeAttr;> -<!ATTLIST text:expression style:data-style-name %styleName; #IMPLIED> - -<!ELEMENT text:text-input (#PCDATA)> -<!ATTLIST text:text-input text:description %string; #IMPLIED> - -<!ENTITY % database-table "text:database-name CDATA #REQUIRED - text:table-name CDATA #REQUIRED - text:table-type (table|query|command) #IMPLIED"> - -<!ELEMENT text:database-display (#PCDATA)> -<!ATTLIST text:database-display %database-table;> -<!ATTLIST text:database-display text:column-name %string; #REQUIRED> -<!ATTLIST text:database-display style:data-style-name %styleName; #IMPLIED> -<!ATTLIST text:database-display text:display (none|value) #IMPLIED> - -<!ELEMENT text:database-next (#PCDATA)> -<!ATTLIST text:database-next %database-table;> -<!ATTLIST text:database-next text:condition %formula; #IMPLIED> - -<!ELEMENT text:database-select (#PCDATA)> -<!ATTLIST text:database-select %database-table;> -<!ATTLIST text:database-select text:condition %formula; #IMPLIED> -<!ATTLIST text:database-select text:row-number %integer; #REQUIRED> - -<!ELEMENT text:database-row-number (#PCDATA)> -<!ATTLIST text:database-row-number %database-table;> -<!ATTLIST text:database-row-number %numFormat;> -<!ATTLIST text:database-row-number text:value %integer; #IMPLIED> -<!ATTLIST text:database-row-number text:display (none|value) #IMPLIED> - -<!ELEMENT text:database-name (#PCDATA)> -<!ATTLIST text:database-name %database-table;> -<!ATTLIST text:database-name text:display (none|value) #IMPLIED> - -<!ELEMENT text:initial-creator (#PCDATA)> -<!ATTLIST text:initial-creator text:fixed %boolean; "false"> - -<!ELEMENT text:creation-date (#PCDATA)> -<!ATTLIST text:creation-date text:fixed %boolean; "false"> -<!ATTLIST text:creation-date text:date-value %date; #IMPLIED> -<!ATTLIST text:creation-date style:data-style-name %styleName; #IMPLIED> - -<!ELEMENT text:creation-time (#PCDATA)> -<!ATTLIST text:creation-time text:fixed %boolean; "false"> -<!ATTLIST text:creation-time text:time-value %timeInstance; #IMPLIED> -<!ATTLIST text:creation-time style:data-style-name %styleName; #IMPLIED> - -<!ELEMENT text:description (#PCDATA)> -<!ATTLIST text:description text:fixed %boolean; "false"> - -<!ELEMENT text:user-defined (#PCDATA)> -<!ATTLIST text:user-defined text:fixed %boolean; "false"> -<!ATTLIST text:user-defined text:name %string; #REQUIRED> - -<!ELEMENT text:print-time (#PCDATA)> -<!ATTLIST text:print-time text:fixed %boolean; "false"> -<!ATTLIST text:print-time text:time-value %timeInstance; #IMPLIED> -<!ATTLIST text:print-time style:data-style-name %styleName; #IMPLIED> - -<!ELEMENT text:print-date (#PCDATA)> -<!ATTLIST text:print-date text:fixed %boolean; "false"> -<!ATTLIST text:print-date text:date-value %date; #IMPLIED> -<!ATTLIST text:print-date style:data-style-name %styleName; #IMPLIED> - -<!ELEMENT text:printed-by (#PCDATA)> -<!ATTLIST text:printed-by text:fixed %boolean; "false"> - -<!ELEMENT text:title (#PCDATA)> -<!ATTLIST text:title text:fixed %boolean; "false"> - -<!ELEMENT text:subject (#PCDATA)> -<!ATTLIST text:subject text:fixed %boolean; "false"> - -<!ELEMENT text:keywords (#PCDATA)> -<!ATTLIST text:keywords text:fixed %boolean; "false"> - -<!ELEMENT text:editing-cycles (#PCDATA)> -<!ATTLIST text:editing-cycles text:fixed %boolean; "false"> - -<!ELEMENT text:editing-duration (#PCDATA)> -<!ATTLIST text:editing-duration text:fixed %boolean; "false"> -<!ATTLIST text:editing-duration text:duration %timeDuration; #IMPLIED> -<!ATTLIST text:editing-duration style:data-style-name %styleName; #IMPLIED> - -<!ELEMENT text:modification-time (#PCDATA)> -<!ATTLIST text:modification-time text:fixed %boolean; "false"> -<!ATTLIST text:modification-time text:time-value %timeInstance; #IMPLIED> -<!ATTLIST text:modification-time style:data-style-name %styleName; #IMPLIED> - -<!ELEMENT text:modification-date (#PCDATA)> -<!ATTLIST text:modification-date text:fixed %boolean; "false"> -<!ATTLIST text:modification-date text:date-value %date; #IMPLIED> -<!ATTLIST text:modification-date style:data-style-name %styleName; #IMPLIED> - -<!ELEMENT text:creator (#PCDATA)> -<!ATTLIST text:creator text:fixed %boolean; "false"> - -<!ELEMENT text:conditional-text (#PCDATA)> -<!ATTLIST text:conditional-text text:condition %formula; #REQUIRED> -<!ATTLIST text:conditional-text text:string-value-if-false %string; #REQUIRED> -<!ATTLIST text:conditional-text text:string-value-if-true %string; #REQUIRED> -<!ATTLIST text:conditional-text text:current-value %boolean; "false"> - -<!ELEMENT text:hidden-text (#PCDATA)> -<!ATTLIST text:hidden-text text:condition %formula; #REQUIRED> -<!ATTLIST text:hidden-text text:string-value %string; #REQUIRED> -<!ATTLIST text:hidden-text text:is-hidden %boolean; "false"> - -<!ELEMENT text:hidden-paragraph EMPTY> -<!ATTLIST text:hidden-paragraph text:condition %formula; #REQUIRED> -<!ATTLIST text:hidden-paragraph text:is-hidden %boolean; "false"> - -<!ELEMENT text:chapter (#PCDATA)> -<!ATTLIST text:chapter text:display (name|number|number-and-name| - plain-number-and-name|plain-number) - "number-and-name"> -<!ATTLIST text:chapter text:outline-level %integer; "1"> - -<!ELEMENT text:file-name (#PCDATA)> -<!ATTLIST text:file-name text:display (full|path|name|name-and-extension) - "full"> -<!ATTLIST text:file-name text:fixed %boolean; "false"> - -<!ELEMENT text:template-name (#PCDATA)> -<!ATTLIST text:template-name text:display (full|path|name|name-and-extension| - area|title) "full"> - -<!ELEMENT text:page-variable-set EMPTY> -<!ATTLIST text:page-variable-set text:active %boolean; "true"> -<!ATTLIST text:page-variable-set text:page-adjust %integer; "0"> - -<!ELEMENT text:page-variable-get (#PCDATA)> -<!ATTLIST text:page-variable-get %numFormat;> - -<!ELEMENT text:execute-macro (#PCDATA|office:events)* > -<!ATTLIST text:execute-macro text:description %string; #IMPLIED> - - -<!ELEMENT text:dde-connection-decls (text:dde-connection-decl)*> - -<!ELEMENT text:dde-connection-decl EMPTY> -<!ATTLIST text:dde-connection-decl text:name %string; #REQUIRED> -<!ATTLIST text:dde-connection-decl office:dde-application %string; #REQUIRED> -<!ATTLIST text:dde-connection-decl office:dde-topic %string; #REQUIRED> -<!ATTLIST text:dde-connection-decl office:dde-item %string; #REQUIRED> -<!ATTLIST text:dde-connection-decl office:automatic-update %boolean; "false"> - -<!ELEMENT text:dde-connection (#PCDATA)> -<!ATTLIST text:dde-connection text:connection-name %string; #REQUIRED> - -<!ELEMENT text:reference-ref (#PCDATA)> -<!ATTLIST text:reference-ref text:ref-name %string; #REQUIRED> -<!ATTLIST text:reference-ref text:reference-format (page|chapter|text|direction) #IMPLIED> - -<!ELEMENT text:sequence-ref (#PCDATA)> -<!ATTLIST text:sequence-ref text:ref-name %string; #REQUIRED> -<!ATTLIST text:sequence-ref text:reference-format (page|chapter|text|direction|category-and-value|caption|value) #IMPLIED> - -<!ELEMENT text:bookmark-ref (#PCDATA)> -<!ATTLIST text:bookmark-ref text:ref-name %string; #REQUIRED> -<!ATTLIST text:bookmark-ref text:reference-format (page|chapter|text|direction) #IMPLIED> - -<!ELEMENT text:footnote-ref (#PCDATA)> -<!ATTLIST text:footnote-ref text:ref-name %string; #REQUIRED> -<!ATTLIST text:footnote-ref text:reference-format (page|chapter|text|direction) #IMPLIED> - -<!ELEMENT text:endnote-ref (#PCDATA)> -<!ATTLIST text:endnote-ref text:ref-name %string; #REQUIRED> -<!ATTLIST text:endnote-ref text:reference-format (page|chapter|text|direction) #IMPLIED> - -<!ELEMENT text:sheet-name (#PCDATA)> - -<!ELEMENT text:page-count (#PCDATA)> -<!ATTLIST text:page-count style:num-format %string; #IMPLIED> -<!ATTLIST text:page-count style:num-letter-sync %boolean; "false"> - -<!ELEMENT text:paragraph-count (#PCDATA)> -<!ATTLIST text:paragraph-count style:num-format %string; #IMPLIED> -<!ATTLIST text:paragraph-count style:num-letter-sync %boolean; "false"> - -<!ELEMENT text:word-count (#PCDATA)> -<!ATTLIST text:word-count style:num-format %string; #IMPLIED> -<!ATTLIST text:word-count style:num-letter-sync %boolean; "false"> - -<!ELEMENT text:character-count (#PCDATA)> -<!ATTLIST text:character-count style:num-format %string; #IMPLIED> -<!ATTLIST text:character-count style:num-letter-sync %boolean; "false"> - -<!ELEMENT text:table-count (#PCDATA)> -<!ATTLIST text:table-count style:num-format %string; #IMPLIED> -<!ATTLIST text:table-count style:num-letter-sync %boolean; "false"> - -<!ELEMENT text:image-count (#PCDATA)> -<!ATTLIST text:image-count style:num-format %string; #IMPLIED> -<!ATTLIST text:image-count style:num-letter-sync %boolean; "false"> - -<!ELEMENT text:object-count (#PCDATA)> -<!ATTLIST text:object-count style:num-format %string; #IMPLIED> -<!ATTLIST text:object-count style:num-letter-sync %boolean; "false"> - -<!ELEMENT text:bibliography-mark (#PCDATA)> -<!ATTLIST text:bibliography-mark text:bibliography-type - ( article | book | booklet | conference | custom1 | custom2 | custom3 | - custom4 | custom5 | email | inbook | incollection | inproceedings | - journal | manual | mastersthesis | misc | phdthesis | proceedings | - techreport | unpublished | www ) #REQUIRED > -<!ATTLIST text:bibliography-mark text:identifier CDATA #IMPLIED> -<!ATTLIST text:bibliography-mark text:address CDATA #IMPLIED> -<!ATTLIST text:bibliography-mark text:annote CDATA #IMPLIED> -<!ATTLIST text:bibliography-mark text:author CDATA #IMPLIED> -<!ATTLIST text:bibliography-mark text:booktitle CDATA #IMPLIED> -<!ATTLIST text:bibliography-mark text:chapter CDATA #IMPLIED> -<!ATTLIST text:bibliography-mark text:edition CDATA #IMPLIED> -<!ATTLIST text:bibliography-mark text:editor CDATA #IMPLIED> -<!ATTLIST text:bibliography-mark text:howpublished CDATA #IMPLIED> -<!ATTLIST text:bibliography-mark text:institution CDATA #IMPLIED> -<!ATTLIST text:bibliography-mark text:journal CDATA #IMPLIED> -<!ATTLIST text:bibliography-mark text:month CDATA #IMPLIED> -<!ATTLIST text:bibliography-mark text:note CDATA #IMPLIED> -<!ATTLIST text:bibliography-mark text:number CDATA #IMPLIED> -<!ATTLIST text:bibliography-mark text:organizations CDATA #IMPLIED> -<!ATTLIST text:bibliography-mark text:pages CDATA #IMPLIED> -<!ATTLIST text:bibliography-mark text:publisher CDATA #IMPLIED> -<!ATTLIST text:bibliography-mark text:school CDATA #IMPLIED> -<!ATTLIST text:bibliography-mark text:series CDATA #IMPLIED> -<!ATTLIST text:bibliography-mark text:title CDATA #IMPLIED> -<!ATTLIST text:bibliography-mark text:report-type CDATA #IMPLIED> -<!ATTLIST text:bibliography-mark text:volume CDATA #IMPLIED> -<!ATTLIST text:bibliography-mark text:year CDATA #IMPLIED> -<!ATTLIST text:bibliography-mark text:url CDATA #IMPLIED> -<!ATTLIST text:bibliography-mark text:custom1 CDATA #IMPLIED> -<!ATTLIST text:bibliography-mark text:custom2 CDATA #IMPLIED> -<!ATTLIST text:bibliography-mark text:custom3 CDATA #IMPLIED> -<!ATTLIST text:bibliography-mark text:custom4 CDATA #IMPLIED> -<!ATTLIST text:bibliography-mark text:custom5 CDATA #IMPLIED> -<!ATTLIST text:bibliography-mark text:isbn CDATA #IMPLIED> - - -<!ELEMENT text:bookmark EMPTY> -<!ATTLIST text:bookmark text:name CDATA #REQUIRED> - -<!ELEMENT text:bookmark-start EMPTY> -<!ATTLIST text:bookmark-start text:name CDATA #REQUIRED> - -<!ELEMENT text:bookmark-end EMPTY> -<!ATTLIST text:bookmark-end text:name CDATA #REQUIRED> - -<!ELEMENT text:reference-mark EMPTY> -<!ATTLIST text:reference-mark text:name CDATA #REQUIRED> - -<!ELEMENT text:reference-mark-start EMPTY> -<!ATTLIST text:reference-mark-start text:name CDATA #REQUIRED> - -<!ELEMENT text:reference-mark-end EMPTY> -<!ATTLIST text:reference-mark-end text:name CDATA #REQUIRED> - -<!ELEMENT text:footnotes-configuration (text:footnote-continuation-notice-forward?,text:footnote-continuation-notice-backward?)> -<!ATTLIST text:footnotes-configuration style:num-prefix %string; #IMPLIED> -<!ATTLIST text:footnotes-configuration style:num-suffix %string; #IMPLIED> -<!ATTLIST text:footnotes-configuration style:num-format %string; #IMPLIED> -<!ATTLIST text:footnotes-configuration style:num-letter-sync %string; #IMPLIED> -<!ATTLIST text:footnotes-configuration text:citation-body-style-name %styleName; #IMPLIED> -<!ATTLIST text:footnotes-configuration text:citation-style-name %styleName; #IMPLIED> -<!ATTLIST text:footnotes-configuration text:default-style-name %styleName; #IMPLIED> -<!ATTLIST text:footnotes-configuration text:master-page-name %styleName; #IMPLIED> -<!ATTLIST text:footnotes-configuration text:start-value %integer; #IMPLIED> -<!ATTLIST text:footnotes-configuration text:footnotes-position (document|page) "page"> -<!ATTLIST text:footnotes-configuration text:start-numbering-at (document|chapter|page) "document"> - -<!ELEMENT text:footnote-continuation-notice-forward (#PCDATA)> -<!ELEMENT text:footnote-continuation-notice-backward (#PCDATA)> - -<!ELEMENT text:endnotes-configuration EMPTY> -<!ATTLIST text:endnotes-configuration style:num-prefix %string; #IMPLIED> -<!ATTLIST text:endnotes-configuration style:num-suffix %string; #IMPLIED> -<!ATTLIST text:endnotes-configuration style:num-format %string; #IMPLIED> -<!ATTLIST text:endnotes-configuration style:num-letter-sync %string; #IMPLIED> -<!ATTLIST text:endnotes-configuration text:start-value %integer; #IMPLIED> -<!ATTLIST text:endnotes-configuration text:citation-style-name %styleName; #IMPLIED> -<!ATTLIST text:endnotes-configuration text:citation-body-style-name %styleName; #IMPLIED> -<!ATTLIST text:endnotes-configuration text:default-style-name %styleName; #IMPLIED> -<!ATTLIST text:endnotes-configuration text:master-page-name %styleName; #IMPLIED> - -<!-- Validity constraint: text:footnote and text:endnote elements may not - contain other text:footnote or text:endnote elements, even though the DTD - allows this (via the %text; in the foot-/endnote-body). - Unfortunatetly, this constraint cannot be easily specified in the DTD. ---> -<!ELEMENT text:footnote (text:footnote-citation, text:footnote-body)> -<!ATTLIST text:footnote text:id ID #IMPLIED> - -<!ELEMENT text:footnote-citation (#PCDATA)> -<!ATTLIST text:footnote-citation text:label %string; #IMPLIED> - -<!ELEMENT text:footnote-body (text:h|text:p| - text:ordered-list|text:unordered-list)*> - -<!ELEMENT text:endnote (text:endnote-citation, text:endnote-body)> -<!ATTLIST text:endnote text:id ID #IMPLIED> - -<!ELEMENT text:endnote-citation (#PCDATA)> -<!ATTLIST text:endnote-citation text:label %string; #IMPLIED> - -<!ELEMENT text:endnote-body (text:h|text:p| - text:ordered-list|text:unordered-list)*> - -<!ENTITY % sectionAttr "text:name CDATA #REQUIRED - text:style-name %styleName; #IMPLIED - text:protected %boolean; 'false' "> - - -<!ELEMENT text:section ((text:section-source|office:dde-source)?, - %sectionText;) > - -<!ATTLIST text:section %sectionAttr;> -<!ATTLIST text:section text:display (true|none|condition) "true"> -<!ATTLIST text:section text:condition %formula; #IMPLIED> -<!ATTLIST text:section text:protection-key CDATA #IMPLIED> -<!ATTLIST text:section text:is-hidden %boolean; #IMPLIED> - -<!ELEMENT text:section-source EMPTY> -<!ATTLIST text:section-source xlink:href %string; #IMPLIED> -<!ATTLIST text:section-source xlink:type (simple) #FIXED "simple"> -<!ATTLIST text:section-source xlink:show (embed) #FIXED "embed"> -<!ATTLIST text:section-source text:section-name %string; #IMPLIED> -<!ATTLIST text:section-source text:filter-name %string; #IMPLIED> - -<!ELEMENT text:table-of-content (text:table-of-content-source, - text:index-body) > -<!ATTLIST text:table-of-content %sectionAttr;> - -<!ELEMENT text:table-of-content-source (text:index-title-template? , - text:table-of-content-entry-template*, - text:index-source-styles* ) > -<!ATTLIST text:table-of-content-source text:outline-level %integer; #IMPLIED> -<!ATTLIST text:table-of-content-source text:use-outline-level %boolean; "true"> -<!ATTLIST text:table-of-content-source text:use-index-marks %boolean; "true"> -<!ATTLIST text:table-of-content-source text:use-index-source-styles - %boolean; "false"> -<!ATTLIST text:table-of-content-source text:index-scope (document|chapter) - "document"> -<!ATTLIST text:table-of-content-source text:relative-tab-stop-position - %boolean; "true"> -<!ATTLIST text:table-of-content-source fo:language %string; #IMPLIED> -<!ATTLIST text:table-of-content-source fo:country %string; #IMPLIED> -<!ATTLIST text:table-of-content-source text:sort-algorithm %string; #IMPLIED> - -<!ELEMENT text:table-of-content-entry-template (text:index-entry-chapter-number | - text:index-entry-page-number | - text:index-entry-text | - text:index-entry-span | - text:index-entry-tab-stop | - text:index-entry-link-start | - text:index-entry-link-end)* > -<!ATTLIST text:table-of-content-entry-template text:outline-level - %integer; #REQUIRED> -<!ATTLIST text:table-of-content-entry-template text:style-name - %styleName; #REQUIRED> - -<!ELEMENT text:illustration-index - (text:illustration-index-source, text:index-body)> -<!ATTLIST text:illustration-index %sectionAttr;> - -<!ELEMENT text:illustration-index-source (text:index-title-template?, - text:illustration-index-entry-template?) > -<!ATTLIST text:illustration-index-source text:index-scope - (document|chapter) "document"> -<!ATTLIST text:illustration-index-source text:relative-tab-stop-position - %boolean; "true"> -<!ATTLIST text:illustration-index-source text:use-caption %boolean; "true"> -<!ATTLIST text:illustration-index-source text:caption-sequence-name - %string; #IMPLIED> -<!ATTLIST text:illustration-index-source text:caption-sequence-format - (text|category-and-value|caption) "text"> -<!ATTLIST text:illustration-index-source fo:language %string; #IMPLIED> -<!ATTLIST text:illustration-index-source fo:country %string; #IMPLIED> -<!ATTLIST text:illustration-index-source text:sort-algorithm %string; #IMPLIED> - -<!ELEMENT text:illustration-index-entry-template - ( text:index-entry-page-number | - text:index-entry-text | - text:index-entry-span | - text:index-entry-tab-stop )* > -<!ATTLIST text:illustration-index-entry-template text:style-name - %styleName; #REQUIRED> - -<!ELEMENT text:table-index (text:table-index-source, text:index-body)> -<!ATTLIST text:table-index %sectionAttr;> - -<!ELEMENT text:table-index-source (text:index-title-template?, - text:table-index-entry-template?) > -<!ATTLIST text:table-index-source text:index-scope - (document|chapter) "document"> -<!ATTLIST text:table-index-source text:relative-tab-stop-position - %boolean; "true"> -<!ATTLIST text:table-index-source text:use-caption %boolean; "true"> -<!ATTLIST text:table-index-source text:caption-sequence-name - %string; #IMPLIED> -<!ATTLIST text:table-index-source text:caption-sequence-format - (text|category-and-value|caption) "text"> -<!ATTLIST text:table-index-source fo:language %string; #IMPLIED> -<!ATTLIST text:table-index-source fo:country %string; #IMPLIED> -<!ATTLIST text:table-index-source text:sort-algorithm %string; #IMPLIED> - -<!ELEMENT text:table-index-entry-template ( text:index-entry-page-number | - text:index-entry-text | - text:index-entry-span | - text:index-entry-tab-stop )* > -<!ATTLIST text:table-index-entry-template text:style-name - %styleName; #REQUIRED> - -<!ELEMENT text:object-index ( text:object-index-source, text:index-body ) > -<!ATTLIST text:object-index %sectionAttr;> - -<!ELEMENT text:object-index-source ( text:index-title-template?, - text:object-index-entry-template? ) > -<!ATTLIST text:object-index-source text:index-scope - (document|chapter) "document"> -<!ATTLIST text:object-index-source text:relative-tab-stop-position - %boolean; "true"> -<!ATTLIST text:object-index-source text:use-spreadsheet-objects - %boolean; "false"> -<!ATTLIST text:object-index-source text:use-draw-objects %boolean; "false"> -<!ATTLIST text:object-index-source text:use-chart-objects %boolean; "false"> -<!ATTLIST text:object-index-source text:use-other-objects %boolean; "false"> -<!ATTLIST text:object-index-source text:use-math-objects %boolean; "false"> -<!ATTLIST text:object-index-source fo:language %string; #IMPLIED> -<!ATTLIST text:object-index-source fo:country %string; #IMPLIED> -<!ATTLIST text:object-index-source text:sort-algorithm %string; #IMPLIED> - -<!ELEMENT text:object-index-entry-template ( text:index-entry-page-number | - text:index-entry-text | - text:index-entry-span | - text:index-entry-tab-stop )* > -<!ATTLIST text:object-index-entry-template text:style-name - %styleName; #REQUIRED > - -<!ELEMENT text:user-index (text:user-index-source, text:index-body) > -<!ATTLIST text:user-index %sectionAttr;> - -<!ELEMENT text:user-index-source ( text:index-title-template?, - text:user-index-entry-template*, - text:index-source-styles* ) > -<!ATTLIST text:user-index-source text:index-scope - (document|chapter) "document"> -<!ATTLIST text:user-index-source text:relative-tab-stop-position - %boolean; "true"> -<!ATTLIST text:user-index-source text:use-index-marks %boolean; "false"> -<!ATTLIST text:user-index-source text:use-graphics %boolean; "false"> -<!ATTLIST text:user-index-source text:use-tables %boolean; "false"> -<!ATTLIST text:user-index-source text:use-floating-frames %boolean; "false"> -<!ATTLIST text:user-index-source text:use-objects %boolean; "false"> -<!ATTLIST text:user-index-source text:use-index-source-styles - %boolean; "false"> -<!ATTLIST text:user-index-source text:copy-outline-levels %boolean; "false"> -<!ATTLIST text:user-index-source fo:language %string; #IMPLIED> -<!ATTLIST text:user-index-source fo:country %string; #IMPLIED> -<!ATTLIST text:user-index-source text:sort-algorithm %string; #IMPLIED> -<!ATTLIST text:user-index-source text:index-name %string; #IMPLIED> - -<!ELEMENT text:user-index-entry-template ( text:index-entry-chapter | - text:index-entry-page-number | - text:index-entry-text | - text:index-entry-span | - text:index-entry-tab-stop )* > -<!ATTLIST text:user-index-entry-template text:outline-level %integer; #REQUIRED> -<!ATTLIST text:user-index-entry-template text:style-name %styleName; #REQUIRED> - -<!ELEMENT text:alphabetical-index (text:alphabetical-index-source, - text:index-body)> -<!ATTLIST text:alphabetical-index %sectionAttr;> - -<!ELEMENT text:alphabetical-index-source ( text:index-title-template?, - text:alphabetical-index-entry-template* ) > -<!ATTLIST text:alphabetical-index-source text:index-scope - (document|chapter) "document"> -<!ATTLIST text:alphabetical-index-source text:relative-tab-stop-position - %boolean; "true"> -<!ATTLIST text:alphabetical-index-source text:ignore-case %boolean; "false"> -<!ATTLIST text:alphabetical-index-source text:main-entry-style-name - %styleName; #IMPLIED> -<!ATTLIST text:alphabetical-index-source text:alphabetical-separators - %boolean; "false"> -<!ATTLIST text:alphabetical-index-source text:combine-entries - %boolean; "true"> -<!ATTLIST text:alphabetical-index-source text:combine-entries-with-dash - %boolean; "false"> -<!ATTLIST text:alphabetical-index-source text:combine-entries-with-pp - %boolean; "true"> -<!ATTLIST text:alphabetical-index-source text:use-keys-as-entries - %boolean; "false"> -<!ATTLIST text:alphabetical-index-source text:capitalize-entries - %boolean; "false"> -<!ATTLIST text:alphabetical-index-source text:comma-separated - %boolean; "false"> -<!ATTLIST text:alphabetical-index-source fo:language %string; #IMPLIED> -<!ATTLIST text:alphabetical-index-source fo:country %string; #IMPLIED> -<!ATTLIST text:alphabetical-index-source text:sort-algorithm %string; #IMPLIED> - -<!ELEMENT text:alphabetical-index-entry-template ( text:index-entry-chapter | - text:index-entry-page-number | - text:index-entry-text | - text:index-entry-span | - text:index-entry-tab-stop )* > -<!ATTLIST text:alphabetical-index-entry-template text:outline-level - (1|2|3|separator) #REQUIRED> -<!ATTLIST text:alphabetical-index-entry-template text:style-name - %styleName; #REQUIRED> - -<!ELEMENT text:alphabetical-index-auto-mark-file EMPTY> -<!ATTLIST text:alphabetical-index-auto-mark-file xlink:href CDATA #IMPLIED> -<!ATTLIST text:alphabetical-index-auto-mark-file xlink:type (simple) #FIXED "simple"> - -<!ELEMENT text:bibliography (text:bibliography-source, text:index-body) > -<!ATTLIST text:bibliography %sectionAttr;> - -<!ELEMENT text:bibliography-source ( text:index-title-template?, - text:bibliography-entry-template* ) > - -<!ELEMENT text:bibliography-entry-template ( text:index-entry-span | - text:index-entry-tab-stop | - text:index-entry-bibliography )* > -<!ATTLIST text:bibliography-entry-template text:bibliography-type - ( article | book | booklet | conference | custom1 | custom2 | - custom3 | custom4 | custom5 | email | inbook | incollection | - inproceedings | journal | manual | mastersthesis | misc | - phdthesis | proceedings | techreport | unpublished | www ) - #REQUIRED > -<!ATTLIST text:bibliography-entry-template text:style-name - %styleName; #REQUIRED> - -<!ELEMENT text:index-body %sectionText; > - -<!-- -Validity constraint: text:index-title elements may appear only in -indices, and there may be only one text:index-title element. ---> -<!ELEMENT text:index-title %sectionText; > -<!ATTLIST text:index-title text:style-name %styleName; #IMPLIED> -<!ATTLIST text:index-title text:name %string; #IMPLIED> - -<!ELEMENT text:index-title-template (#PCDATA)> -<!ATTLIST text:index-title-template text:style-name %styleName; #IMPLIED> - -<!ELEMENT text:index-entry-chapter-number EMPTY> -<!ATTLIST text:index-entry-chapter-number text:style-name %styleName; #IMPLIED> - -<!ELEMENT text:index-entry-chapter EMPTY> -<!ATTLIST text:index-entry-chapter text:style-name %styleName; #IMPLIED> -<!ATTLIST text:index-entry-chapter text:display (name|number|number-and-name) - "number-and-name" > - -<!ELEMENT text:index-entry-text EMPTY> -<!ATTLIST text:index-entry-text text:style-name %styleName; #IMPLIED> - -<!ELEMENT text:index-entry-page-number EMPTY> -<!ATTLIST text:index-entry-page-number text:style-name %styleName; #IMPLIED> - -<!ELEMENT text:index-entry-span (#PCDATA)> -<!ATTLIST text:index-entry-span text:style-name %styleName; #IMPLIED> - -<!ELEMENT text:index-entry-bibliography EMPTY> -<!ATTLIST text:index-entry-bibliography text:style-name %styleName; #IMPLIED> -<!ATTLIST text:index-entry-bibliography text:bibliography-data-field - ( address | annote | author | bibliography-type | - booktitle | chapter | custom1 | custom2 | - custom3 | custom4 | custom5 | edition | editor | - howpublished | identifier | institution | isbn | - journal | month | note | number | organizations | - pages | publisher | report-type | school | - series | title | url | volume | year ) #REQUIRED> - - -<!ELEMENT text:index-entry-tab-stop EMPTY> -<!ATTLIST text:index-entry-tab-stop text:style-name %styleName; #IMPLIED> -<!ATTLIST text:index-entry-tab-stop style:leader-char %character; " "> -<!ATTLIST text:index-entry-tab-stop style:type (left|right) "left"> -<!ATTLIST text:index-entry-tab-stop style:position %length; #IMPLIED> - -<!ELEMENT text:index-entry-link-start EMPTY> -<!ATTLIST text:index-entry-link-start text:style-name %styleName; #IMPLIED> - -<!ELEMENT text:index-entry-link-end EMPTY> -<!ATTLIST text:index-entry-link-end text:style-name %styleName; #IMPLIED> - -<!ELEMENT text:index-source-styles (text:index-source-style)*> -<!ATTLIST text:index-source-styles text:outline-level %integer; #REQUIRED> - -<!ELEMENT text:index-source-style EMPTY> -<!ATTLIST text:index-source-style text:style-name %styleName; #REQUIRED> - -<!ELEMENT text:toc-mark-start EMPTY> -<!ATTLIST text:toc-mark-start text:id %string; #REQUIRED> -<!ATTLIST text:toc-mark-start text:outline-level %integer; #IMPLIED> - -<!ELEMENT text:toc-mark-end EMPTY> -<!ATTLIST text:toc-mark-end text:id %string; #REQUIRED> - -<!ELEMENT text:toc-mark EMPTY> -<!ATTLIST text:toc-mark text:string-value %string; #REQUIRED> -<!ATTLIST text:toc-mark text:outline-level %integer; #IMPLIED> - -<!ELEMENT text:user-index-mark-start EMPTY> -<!ATTLIST text:user-index-mark-start text:id %string; #REQUIRED> -<!ATTLIST text:user-index-mark-start text:outline-level %integer; #IMPLIED> -<!ATTLIST text:user-index-mark-start text:index-name %string; #IMPLIED> - -<!ELEMENT text:user-index-mark-end EMPTY> -<!ATTLIST text:user-index-mark-end text:id %string; #REQUIRED> - -<!ELEMENT text:user-index-mark EMPTY> -<!ATTLIST text:user-index-mark text:string-value %string; #REQUIRED> -<!ATTLIST text:user-index-mark text:outline-level %integer; #IMPLIED> -<!ATTLIST text:user-index-mark text:index-name %string; #IMPLIED> - -<!ELEMENT text:alphabetical-index-mark-start EMPTY> -<!ATTLIST text:alphabetical-index-mark-start text:id %string; #REQUIRED> -<!ATTLIST text:alphabetical-index-mark-start text:key1 %string; #IMPLIED> -<!ATTLIST text:alphabetical-index-mark-start text:key2 %string; #IMPLIED> -<!ATTLIST text:alphabetical-index-mark-start text:main-etry %boolean; "false"> - -<!ELEMENT text:alphabetical-index-mark-end EMPTY> -<!ATTLIST text:alphabetical-index-mark-end text:id %string; #REQUIRED> - -<!ELEMENT text:alphabetical-index-mark EMPTY> -<!ATTLIST text:alphabetical-index-mark text:string-value %string; #REQUIRED> -<!ATTLIST text:alphabetical-index-mark text:key1 %string; #IMPLIED> -<!ATTLIST text:alphabetical-index-mark text:key2 %string; #IMPLIED> -<!ATTLIST text:alphabetical-index-mark text:main-etry %boolean; "false"> - -<!ELEMENT text:bibliography-configuration (text:sort-key)*> -<!ATTLIST text:bibliography-configuration text:prefix %string; #IMPLIED> -<!ATTLIST text:bibliography-configuration text:suffix %string; #IMPLIED> -<!ATTLIST text:bibliography-configuration text:sort-by-position %boolean; "true"> -<!ATTLIST text:bibliography-configuration text:numbered-entries %boolean; "false"> -<!ATTLIST text:bibliography-configuration fo:language %string; #IMPLIED> -<!ATTLIST text:bibliography-configuration fo:country %string; #IMPLIED> -<!ATTLIST text:bibliography-configuration text:sort-algorithm %string; #IMPLIED> - -<!ELEMENT text:sort-key EMPTY> -<!ATTLIST text:sort-key text:key ( address | annote | author | - bibliography-type | booktitle | chapter | custom1 | custom2 | - custom3 | custom4 | custom5 | edition | editor | howpublished | - identifier | institution | isbn | journal | month | note | number | - organizations | pages | publisher | report-type | school | series | - title | url | volume | year ) #REQUIRED> -<!ATTLIST text:sort-key text:sort-ascending %boolean; "true"> - -<!ELEMENT text:linenumbering-configuration (text:linenumbering-separator?)> -<!ATTLIST text:linenumbering-configuration text:style-name %styleName; #IMPLIED> -<!ATTLIST text:linenumbering-configuration text:number-lines %boolean; "true"> -<!ATTLIST text:linenumbering-configuration text:count-empty-lines %boolean; "true"> -<!ATTLIST text:linenumbering-configuration text:count-in-floating-frames %boolean; "false"> -<!ATTLIST text:linenumbering-configuration text:restart-numbering %boolean; "false"> -<!ATTLIST text:linenumbering-configuration text:offset %nonNegativeLength; #IMPLIED> -<!ATTLIST text:linenumbering-configuration style:num-format (1|a|A|i|I) "1"> -<!ATTLIST text:linenumbering-configuration style:num-letter-sync %boolean; "false"> -<!ATTLIST text:linenumbering-configuration text:number-position (left|rigth|inner|outer) "left"> -<!ATTLIST text:linenumbering-configuration text:increment %nonNegativeInteger; #IMPLIED> - -<!ELEMENT text:linenumbering-separator (#PCDATA)> -<!ATTLIST text:linenumbering-separator text:increment %nonNegativeInteger; #IMPLIED> - -<!ELEMENT text:script (#PCDATA)> -<!ATTLIST text:script script:language CDATA #REQUIRED> -<!ATTLIST text:script xlink:href CDATA #IMPLIED> -<!ATTLIST text:script xlink:type (simple) #FIXED "simple"> - -<!ELEMENT text:measure (#PCDATA)> -<!ATTLIST text:measure text:kind (value|unit|gap) #REQUIRED> - -<!ELEMENT text:ruby (text:ruby-base, text:ruby-text)> -<!ATTLIST text:ruby text:style-name %styleName; #IMPLIED> - -<!ELEMENT text:ruby-base %inline-text;> - -<!ELEMENT text:ruby-text (#PCDATA)> -<!ATTLIST text:ruby-text text:style-name %styleName; #IMPLIED> - -<!-- elements for change tracking --> - -<!ELEMENT text:change EMPTY> -<!ATTLIST text:change text:change-id CDATA #REQUIRED> - -<!ELEMENT text:change-start EMPTY> -<!ATTLIST text:change-start text:change-id CDATA #REQUIRED> - -<!ELEMENT text:change-end EMPTY> -<!ATTLIST text:change-end text:change-id CDATA #REQUIRED> - -<!ELEMENT text:tracked-changes (text:changed-region)*> -<!ATTLIST text:tracked-changes text:track-changes %boolean; "true"> -<!ATTLIST text:tracked-changes text:protection-key CDATA #IMPLIED> - -<!ELEMENT text:changed-region (text:insertion | - (text:deletion, text:insertion?) | - text:format-change) > -<!ATTLIST text:changed-region text:id ID #REQUIRED> -<!ATTLIST text:changed-region text:merge-last-paragraph %boolean; "true"> - -<!ELEMENT text:insertion (office:change-info, %sectionText;)> -<!ELEMENT text:deletion (office:change-info, %sectionText;)> -<!ELEMENT text:format-change (office:change-info)> - rmfile ./examples/OpenOffice.org/text.mod rmdir ./examples/OpenOffice.org hunk ./examples/README 1 -Please note: -The example code in this directory may not always work with the -current version of the the HaXml libraries. What little time I have -for maintenance goes into the main HaXml facilites, not into testing -these small demonstration exercises. Sorry. - - -Parse/Pretty-Print example (Canonicalise.hs) --------------------------- -To demonstrate parsing and pretty-printing, I wrote a simple in-out -application: - $ hmake Canonicalise -I../lib -Test it on some XML documents: - $ ./Canonicalise album.xml -You will notice that it changes some parts of the document, for instance in - $ ./Canonicalise subjdb.xml -all parameter entities are replaced with their expansion. - - -Xml2Haskell example (album.dtd, AlbumDTD.hs, album.xml) -------------------- -In this example, I did the following: - -Convert the XML DTD for an album into a Haskell module: - $ DtdToHaskell album.dtd AlbumDtd.hs - -Edit the generated file (just to change the module name to match!) - $ vi AlbumDtd.hs - -Wrote the test application (App.hs) using AlbumDTD.hs, and compiled it: - $ hmake App -I../lib - -Running the test displays some progress messages, and outputs the original -document again, only with the album title changed. - $ ./App album.xml new.xml - -And that's it. - - -Haskell2Xml example (Types.hs, DTypes.hs, Example.hs, subjdb.xml) -------------------- -The file Types.hs defines some data types for a mini-database. -Derive the Haskell2Xml apparatus using DrIFT: - $ DrIFT Types.hs >DTypes.hs - -The example program in Example.hs just writes some Haskell data to -an XML file. - $ hmake Example -I../lib - $ ./Example - $ less subjdb.xml - -I hope that's reasonably clear. - - -Bigger DtdToHaskell example ---------------------------- -In directory SMIL, do - $ DtdToHaskell SMIL20.dtd DTD_SMIL20.hs -and have a look at the resulting Haskell file. This is a large -multi-part DTD for the Synchronised Multimedia Integration Language, -defined by the W3C. As of 2000-11-16, our XML parser has been extended -to deal with the external subset as fully as possible. - -DTDpp ------ -This little program is just a pretty-printer for an XML DTD - it -inlines any included files and expands all PE references. Its main -use is to check that the HaXml parser can read a complicated DTD -without errors. - -DebugLex --------- -Another little debugging program to help find errors in HaXml - -this time in the lexer. It prints a stream of lexed tokens (and -their source positions) to stdout, so you can examine whether -some complicated piece of syntax has confused the lexer. - rmfile ./examples/README hunk ./examples/SMIL/DTD_SMIL20.hs 1 -module DTD_SMIL20 where - -import Text.XML.HaXml.Xml2Haskell -import Text.XML.HaXml.OneOfN - - -{-Type decls-} - -data Smil = Smil - { smilId :: (Maybe String) - , smilClass :: (Maybe String) - , smilTitle :: (Maybe String) - , smilXml'lang :: (Maybe String) - , smilXmlns :: (Defaultable String) - } deriving (Eq,Show) -data Head = Head - { headId :: (Maybe String) - , headClass :: (Maybe String) - , headTitle :: (Maybe String) - , headXml'lang :: (Maybe String) - } deriving (Eq,Show) -data Body = Body - { bodyId :: (Maybe String) - , bodyClass :: (Maybe String) - , bodyTitle :: (Maybe String) - , bodyXml'lang :: (Maybe String) - } deriving (Eq,Show) -data Animate = Animate - { animateId :: (Maybe String) - , animateClass :: (Maybe String) - , animateTitle :: (Maybe String) - , animateXml'lang :: (Maybe String) - , animateCustomTest :: (Maybe String) - , animateSystemBitrate :: (Maybe String) - , animateSystemCaptions :: (Maybe Animate_SystemCaptions) - , animateSystemLanguage :: (Maybe String) - , animateSystemOverdubOrSubtitle :: (Maybe Animate_SystemOverdubOrSubtitle) - , animateSystemRequired :: (Maybe String) - , animateSystemScreenSize :: (Maybe String) - , animateSystemScreenDepth :: (Maybe String) - , animateSystemAudioDesc :: (Maybe Animate_SystemAudioDesc) - , animateSystemOperatingSystem :: (Maybe String) - , animateSystemCPU :: (Maybe String) - , animateSystemComponent :: (Maybe String) - , animateSystem_bitrate :: (Maybe String) - , animateSystem_captions :: (Maybe Animate_System_captions) - , animateSystem_language :: (Maybe String) - , animateSystem_overdub_or_caption :: (Maybe Animate_System_overdub_or_caption) - , animateSystem_required :: (Maybe String) - , animateSystem_screen_size :: (Maybe String) - , animateSystem_screen_depth :: (Maybe String) - , animateDur :: (Maybe String) - , animateRepeatCount :: (Maybe String) - , animateRepeatDur :: (Maybe String) - , animateBegin :: (Maybe String) - , animateEnd :: (Maybe String) - , animateAttributeName :: String - , animateAttributeType :: (Maybe String) - , animateValues :: (Maybe String) - , animateFrom :: (Maybe String) - , animateTo :: (Maybe String) - , animateBy :: (Maybe String) - , animateCalcMode :: (Defaultable Animate_CalcMode) - , animateAdditive :: (Defaultable Animate_Additive) - , animateAccumulate :: (Defaultable Animate_Accumulate) - } deriving (Eq,Show) -data Animate_SystemCaptions = Animate_SystemCaptions_On | - Animate_SystemCaptions_Off - deriving (Eq,Show) -data Animate_SystemOverdubOrSubtitle = Animate_SystemOverdubOrSubtitle_Overdub - | Animate_SystemOverdubOrSubtitle_Subtitle - deriving (Eq,Show) -data Animate_SystemAudioDesc = Animate_SystemAudioDesc_On | - Animate_SystemAudioDesc_Off - deriving (Eq,Show) -data Animate_System_captions = Animate_System_captions_On | - Animate_System_captions_Off - deriving (Eq,Show) -data Animate_System_overdub_or_caption = Animate_System_overdub_or_caption_Overdub - | Animate_System_overdub_or_caption_Caption - deriving (Eq,Show) -data Animate_CalcMode = Animate_CalcMode_Discrete | - Animate_CalcMode_Linear | Animate_CalcMode_Paced - deriving (Eq,Show) -data Animate_Additive = Animate_Additive_Replace | - Animate_Additive_Sum - deriving (Eq,Show) -data Animate_Accumulate = Animate_Accumulate_None | - Animate_Accumulate_Sum - deriving (Eq,Show) -data Set = Set - { setId :: (Maybe String) - , setClass :: (Maybe String) - , setTitle :: (Maybe String) - , setXml'lang :: (Maybe String) - , setCustomTest :: (Maybe String) - , setSystemBitrate :: (Maybe String) - , setSystemCaptions :: (Maybe Set_SystemCaptions) - , setSystemLanguage :: (Maybe String) - , setSystemOverdubOrSubtitle :: (Maybe Set_SystemOverdubOrSubtitle) - , setSystemRequired :: (Maybe String) - , setSystemScreenSize :: (Maybe String) - , setSystemScreenDepth :: (Maybe String) - , setSystemAudioDesc :: (Maybe Set_SystemAudioDesc) - , setSystemOperatingSystem :: (Maybe String) - , setSystemCPU :: (Maybe String) - , setSystemComponent :: (Maybe String) - , setSystem_bitrate :: (Maybe String) - , setSystem_captions :: (Maybe Set_System_captions) - , setSystem_language :: (Maybe String) - , setSystem_overdub_or_caption :: (Maybe Set_System_overdub_or_caption) - , setSystem_required :: (Maybe String) - , setSystem_screen_size :: (Maybe String) - , setSystem_screen_depth :: (Maybe String) - , setDur :: (Maybe String) - , setRepeatCount :: (Maybe String) - , setRepeatDur :: (Maybe String) - , setBegin :: (Maybe String) - , setEnd :: (Maybe String) - , setAttributeName :: String - , setAttributeType :: (Maybe String) - , setTo :: (Maybe String) - } deriving (Eq,Show) -data Set_SystemCaptions = Set_SystemCaptions_On | - Set_SystemCaptions_Off - deriving (Eq,Show) -data Set_SystemOverdubOrSubtitle = Set_SystemOverdubOrSubtitle_Overdub - | Set_SystemOverdubOrSubtitle_Subtitle - deriving (Eq,Show) -data Set_SystemAudioDesc = Set_SystemAudioDesc_On | - Set_SystemAudioDesc_Off - deriving (Eq,Show) -data Set_System_captions = Set_System_captions_On | - Set_System_captions_Off - deriving (Eq,Show) -data Set_System_overdub_or_caption = Set_System_overdub_or_caption_Overdub - | Set_System_overdub_or_caption_Caption - deriving (Eq,Show) -data AnimateMotion = AnimateMotion - { animateMotionId :: (Maybe String) - , animateMotionClass :: (Maybe String) - , animateMotionTitle :: (Maybe String) - , animateMotionXml'lang :: (Maybe String) - , animateMotionCustomTest :: (Maybe String) - , animateMotionSystemBitrate :: (Maybe String) - , animateMotionSystemCaptions :: (Maybe AnimateMotion_SystemCaptions) - , animateMotionSystemLanguage :: (Maybe String) - , animateMotionSystemOverdubOrSubtitle :: (Maybe AnimateMotion_SystemOverdubOrSubtitle) - , animateMotionSystemRequired :: (Maybe String) - , animateMotionSystemScreenSize :: (Maybe String) - , animateMotionSystemScreenDepth :: (Maybe String) - , animateMotionSystemAudioDesc :: (Maybe AnimateMotion_SystemAudioDesc) - , animateMotionSystemOperatingSystem :: (Maybe String) - , animateMotionSystemCPU :: (Maybe String) - , animateMotionSystemComponent :: (Maybe String) - , animateMotionSystem_bitrate :: (Maybe String) - , animateMotionSystem_captions :: (Maybe AnimateMotion_System_captions) - , animateMotionSystem_language :: (Maybe String) - , animateMotionSystem_overdub_or_caption :: (Maybe AnimateMotion_System_overdub_or_caption) - , animateMotionSystem_required :: (Maybe String) - , animateMotionSystem_screen_size :: (Maybe String) - , animateMotionSystem_screen_depth :: (Maybe String) - , animateMotionDur :: (Maybe String) - , animateMotionRepeatCount :: (Maybe String) - , animateMotionRepeatDur :: (Maybe String) - , animateMotionBegin :: (Maybe String) - , animateMotionEnd :: (Maybe String) - , animateMotionValues :: (Maybe String) - , animateMotionFrom :: (Maybe String) - , animateMotionTo :: (Maybe String) - , animateMotionBy :: (Maybe String) - , animateMotionCalcMode :: (Defaultable AnimateMotion_CalcMode) - , animateMotionAdditive :: (Defaultable AnimateMotion_Additive) - , animateMotionAccumulate :: (Defaultable AnimateMotion_Accumulate) - , animateMotionOrigin :: (Defaultable AnimateMotion_Origin) - } deriving (Eq,Show) -data AnimateMotion_SystemCaptions = AnimateMotion_SystemCaptions_On - | AnimateMotion_SystemCaptions_Off - deriving (Eq,Show) -data AnimateMotion_SystemOverdubOrSubtitle = AnimateMotion_SystemOverdubOrSubtitle_Overdub - | AnimateMotion_SystemOverdubOrSubtitle_Subtitle - deriving (Eq,Show) -data AnimateMotion_SystemAudioDesc = AnimateMotion_SystemAudioDesc_On - | AnimateMotion_SystemAudioDesc_Off - deriving (Eq,Show) -data AnimateMotion_System_captions = AnimateMotion_System_captions_On - | AnimateMotion_System_captions_Off - deriving (Eq,Show) -data AnimateMotion_System_overdub_or_caption = AnimateMotion_System_overdub_or_caption_Overdub - | AnimateMotion_System_overdub_or_caption_Caption - deriving (Eq,Show) -data AnimateMotion_CalcMode = AnimateMotion_CalcMode_Discrete | - AnimateMotion_CalcMode_Linear | AnimateMotion_CalcMode_Paced - deriving (Eq,Show) -data AnimateMotion_Additive = AnimateMotion_Additive_Replace | - AnimateMotion_Additive_Sum - deriving (Eq,Show) -data AnimateMotion_Accumulate = AnimateMotion_Accumulate_None | - AnimateMotion_Accumulate_Sum - deriving (Eq,Show) -data AnimateMotion_Origin = AnimateMotion_Origin_Default - deriving (Eq,Show) -data AnimateColor = AnimateColor - { animateColorId :: (Maybe String) - , animateColorClass :: (Maybe String) - , animateColorTitle :: (Maybe String) - , animateColorXml'lang :: (Maybe String) - , animateColorCustomTest :: (Maybe String) - , animateColorSystemBitrate :: (Maybe String) - , animateColorSystemCaptions :: (Maybe AnimateColor_SystemCaptions) - , animateColorSystemLanguage :: (Maybe String) - , animateColorSystemOverdubOrSubtitle :: (Maybe AnimateColor_SystemOverdubOrSubtitle) - , animateColorSystemRequired :: (Maybe String) - , animateColorSystemScreenSize :: (Maybe String) - , animateColorSystemScreenDepth :: (Maybe String) - , animateColorSystemAudioDesc :: (Maybe AnimateColor_SystemAudioDesc) - , animateColorSystemOperatingSystem :: (Maybe String) - , animateColorSystemCPU :: (Maybe String) - , animateColorSystemComponent :: (Maybe String) - , animateColorSystem_bitrate :: (Maybe String) - , animateColorSystem_captions :: (Maybe AnimateColor_System_captions) - , animateColorSystem_language :: (Maybe String) - , animateColorSystem_overdub_or_caption :: (Maybe AnimateColor_System_overdub_or_caption) - , animateColorSystem_required :: (Maybe String) - , animateColorSystem_screen_size :: (Maybe String) - , animateColorSystem_screen_depth :: (Maybe String) - , animateColorDur :: (Maybe String) - , animateColorRepeatCount :: (Maybe String) - , animateColorRepeatDur :: (Maybe String) - , animateColorBegin :: (Maybe String) - , animateColorEnd :: (Maybe String) - , animateColorAttributeName :: String - , animateColorAttributeType :: (Maybe String) - , animateColorValues :: (Maybe String) - , animateColorFrom :: (Maybe String) - , animateColorTo :: (Maybe String) - , animateColorBy :: (Maybe String) - , animateColorCalcMode :: (Defaultable AnimateColor_CalcMode) - , animateColorAdditive :: (Defaultable AnimateColor_Additive) - , animateColorAccumulate :: (Defaultable AnimateColor_Accumulate) - } deriving (Eq,Show) -data AnimateColor_SystemCaptions = AnimateColor_SystemCaptions_On - | AnimateColor_SystemCaptions_Off - deriving (Eq,Show) -data AnimateColor_SystemOverdubOrSubtitle = AnimateColor_SystemOverdubOrSubtitle_Overdub - | AnimateColor_SystemOverdubOrSubtitle_Subtitle - deriving (Eq,Show) -data AnimateColor_SystemAudioDesc = AnimateColor_SystemAudioDesc_On - | AnimateColor_SystemAudioDesc_Off - deriving (Eq,Show) -data AnimateColor_System_captions = AnimateColor_System_captions_On - | AnimateColor_System_captions_Off - deriving (Eq,Show) -data AnimateColor_System_overdub_or_caption = AnimateColor_System_overdub_or_caption_Overdub - | AnimateColor_System_overdub_or_caption_Caption - deriving (Eq,Show) -data AnimateColor_CalcMode = AnimateColor_CalcMode_Discrete | - AnimateColor_CalcMode_Linear | AnimateColor_CalcMode_Paced - deriving (Eq,Show) -data AnimateColor_Additive = AnimateColor_Additive_Replace | - AnimateColor_Additive_Sum - deriving (Eq,Show) -data AnimateColor_Accumulate = AnimateColor_Accumulate_None | - AnimateColor_Accumulate_Sum - deriving (Eq,Show) -data Switch = Switch - { switchId :: (Maybe String) - , switchClass :: (Maybe String) - , switchTitle :: (Maybe String) - , switchXml'lang :: (Maybe String) - } deriving (Eq,Show) -data Meta = Meta - { metaContent :: (Maybe String) - , metaName :: String - } deriving (Eq,Show) -data Metadata = Metadata - { metadataId :: (Maybe String) - , metadataClass :: (Maybe String) - , metadataTitle :: (Maybe String) - , metadataXml'lang :: (Maybe String) - } deriving (Eq,Show) -data Layout = Layout - { layoutId :: (Maybe String) - , layoutClass :: (Maybe String) - , layoutTitle :: (Maybe String) - , layoutXml'lang :: (Maybe String) - , layoutType :: (Defaultable String) - } deriving (Eq,Show) -data Region = Region - { regionId :: (Maybe String) - , regionClass :: (Maybe String) - , regionTitle :: (Maybe String) - , regionXml'lang :: (Maybe String) - , regionHeight :: (Defaultable String) - , regionWidth :: (Defaultable String) - , regionClose :: (Defaultable Region_Close) - , regionOpen :: (Defaultable Region_Open) - , regionBackgroundColor :: (Maybe String) - , regionBackground_color :: (Maybe String) - , regionBottom :: (Defaultable String) - , regionLeft :: (Defaultable String) - , regionRight :: (Defaultable String) - , regionTop :: (Defaultable String) - , regionZ_index :: (Maybe String) - , regionShowBackground :: (Defaultable Region_ShowBackground) - , regionFit :: (Defaultable Region_Fit) - } deriving (Eq,Show) -data Region_Close = Region_Close_Never | - Region_Close_WhenNotActive - deriving (Eq,Show) -data Region_Open = Region_Open_Always | Region_Open_WhenActive - deriving (Eq,Show) -data Region_ShowBackground = Region_ShowBackground_Always | - Region_ShowBackground_WhenActive - deriving (Eq,Show) -data Region_Fit = Region_Fit_Hidden | Region_Fit_Fill | - Region_Fit_Meet | Region_Fit_Scroll | Region_Fit_Slice - deriving (Eq,Show) -data Root_layout = Root_layout - { root_layoutId :: (Maybe String) - , root_layoutClass :: (Maybe String) - , root_layoutTitle :: (Maybe String) - , root_layoutXml'lang :: (Maybe String) - , root_layoutHeight :: (Defaultable String) - , root_layoutWidth :: (Defaultable String) - , root_layoutClose :: (Defaultable Root_layout_Close) - , root_layoutOpen :: (Defaultable Root_layout_Open) - , root_layoutBackgroundColor :: (Maybe String) - , root_layoutBackground_color :: (Maybe String) - } deriving (Eq,Show) -data Root_layout_Close = Root_layout_Close_Never | - Root_layout_Close_WhenNotActive - deriving (Eq,Show) -data Root_layout_Open = Root_layout_Open_Always | - Root_layout_Open_WhenActive - deriving (Eq,Show) -data Ref = Ref - { refId :: (Maybe String) - , refClass :: (Maybe String) - , refTitle :: (Maybe String) - , refXml'lang :: (Maybe String) - } deriving (Eq,Show) -data Audio = Audio - { audioId :: (Maybe String) - , audioClass :: (Maybe String) - , audioTitle :: (Maybe String) - , audioXml'lang :: (Maybe String) - } deriving (Eq,Show) -data Img = Img - { imgId :: (Maybe String) - , imgClass :: (Maybe String) - , imgTitle :: (Maybe String) - , imgXml'lang :: (Maybe String) - } deriving (Eq,Show) -data Video = Video - { videoId :: (Maybe String) - , videoClass :: (Maybe String) - , videoTitle :: (Maybe String) - , videoXml'lang :: (Maybe String) - } deriving (Eq,Show) -data Text = Text - { textId :: (Maybe String) - , textClass :: (Maybe String) - , textTitle :: (Maybe String) - , textXml'lang :: (Maybe String) - } deriving (Eq,Show) -data Textstream = Textstream - { textstreamId :: (Maybe String) - , textstreamClass :: (Maybe String) - , textstreamTitle :: (Maybe String) - , textstreamXml'lang :: (Maybe String) - } deriving (Eq,Show) -data Animation = Animation - { animationId :: (Maybe String) - , animationClass :: (Maybe String) - , animationTitle :: (Maybe String) - , animationXml'lang :: (Maybe String) - } deriving (Eq,Show) -data Transition = Transition - { transitionId :: (Maybe String) - , transitionClass :: (Maybe String) - , transitionTitle :: (Maybe String) - , transitionXml'lang :: (Maybe String) - , transitionType :: (Maybe Transition_Type) - , transitionSubtype :: (Maybe Transition_Subtype) - , transitionHorzRepeat :: (Defaultable String) - , transitionVertRepeat :: (Defaultable String) - , transitionBorderWidth :: (Defaultable String) - , transitionBorderColor :: (Defaultable String) - , transitionFadeColor :: (Defaultable String) - , transitionCoordinated :: (Defaultable Transition_Coordinated) - , transitionClibBoundary :: (Defaultable Transition_ClibBoundary) - , transitionDur :: (Maybe String) - , transitionStartProgress :: (Defaultable String) - , transitionEndProgress :: (Defaultable String) - , transitionDirection :: (Defaultable Transition_Direction) - } deriving (Eq,Show) -data Transition_Type = Transition_Type_BarWipe | - Transition_Type_BoxWipe | Transition_Type_FourBoxWipe | - Transition_Type_BarnDoorWipe | Transition_Type_DiagonalWipe | - Transition_Type_BowTieWipe | Transition_Type_MiscDiagonalWipe | - Transition_Type_VeeWipe | Transition_Type_BarnVeeWipe | - Transition_Type_ZigZagWipe | Transition_Type_BarnZigZagWipe | - Transition_Type_MiscShapeWipe | Transition_Type_TriangleWipe | - Transition_Type_ArrowHeadWipe | Transition_Type_PentagonWipe | - Transition_Type_HexagonWipe | Transition_Type_EllipseWipe | - Transition_Type_EyeWipe | Transition_Type_RoundRectWipe | - Transition_Type_StarWipe | Transition_Type_ClockWipe | - Transition_Type_PinWheelWipe | Transition_Type_SingleSweepWipe - | Transition_Type_FanWipe | Transition_Type_DoubleFanWipe | - Transition_Type_DoubleSweepWipe | Transition_Type_SaloonDoorWipe - | Transition_Type_WindshieldWipe | Transition_Type_SnakeWipe - | Transition_Type_SpiralWipe | - Transition_Type_ParallelSnakesWipe | - Transition_Type_BoxSnakesWipe | Transition_Type_WaterfallWipe | - Transition_Type_PushWipe | Transition_Type_SlideWipe | - Transition_Type_Fade - deriving (Eq,Show) -data Transition_Subtype = Transition_Subtype_Bottom | - Transition_Subtype_BottomCenter | Transition_Subtype_BottomLeft - | Transition_Subtype_BottomLeftClockwise | - Transition_Subtype_BottomLeftCounterClockwise | - Transition_Subtype_BottomLeftDiagonal | - Transition_Subtype_BottomRight | - Transition_Subtype_BottomRightClockwise | - Transition_Subtype_BottomRightCounterClockwise | - Transition_Subtype_BottomRightDiagonal | - Transition_Subtype_CenterRight | Transition_Subtype_CenterTop | - Transition_Subtype_Circle | Transition_Subtype_ClockwiseBottom - | Transition_Subtype_ClockwiseBottomRight | - Transition_Subtype_ClockwiseLeft | - Transition_Subtype_ClockwiseNine | - Transition_Subtype_ClockwiseRight | - Transition_Subtype_ClockwiseSix | - Transition_Subtype_ClockwiseThree | - Transition_Subtype_ClockwiseTop | - Transition_Subtype_ClockwiseTopLeft | - Transition_Subtype_ClockwiseTwelve | Transition_Subtype_CornersIn - | Transition_Subtype_CornersOut | - Transition_Subtype_CounterClockwiseBottomLeft | - Transition_Subtype_CounterClockwiseTopRight | - Transition_Subtype_Crossfade | - Transition_Subtype_DiagonalBottomLeft | - Transition_Subtype_DiagonalBottomLeftOpposite | - Transition_Subtype_DiagonalTopLeft | - Transition_Subtype_DiagonalTopLeftOpposite | - Transition_Subtype_Diamond | Transition_Subtype_DoubleBarnDoor - | Transition_Subtype_DoubleDiamond | Transition_Subtype_Down - | Transition_Subtype_FadeFromColor | - Transition_Subtype_FadeToColor | - Transition_Subtype_FanInHorizontal | - Transition_Subtype_FanInVertical | - Transition_Subtype_FanOutHorizontal | - Transition_Subtype_FanOutVertical | Transition_Subtype_FivePoint - | Transition_Subtype_FourBlade | - Transition_Subtype_FourBoxHorizontal | - Transition_Subtype_FourBoxVertical | Transition_Subtype_FourPoint - | Transition_Subtype_FromBottom | Transition_Subtype_FromLeft - | Transition_Subtype_FromRight | Transition_Subtype_FromTop | - Transition_Subtype_Heart | Transition_Subtype_Horizontal | - Transition_Subtype_HorizontalLeft | - Transition_Subtype_HorizontalLeftSame | - Transition_Subtype_HorizontalRight | - Transition_Subtype_HorizontalRightSame | - Transition_Subtype_HorizontalTopLeftOpposite | - Transition_Subtype_HorizontalTopRightOpposite | - Transition_Subtype_Keyhole | Transition_Subtype_Left | - Transition_Subtype_LeftCenter | Transition_Subtype_LeftToRight - | Transition_Subtype_OppositeHorizontal | - Transition_Subtype_OppositeVertical | - Transition_Subtype_ParallelDiagonal | - Transition_Subtype_ParallelDiagonalBottomLeft | - Transition_Subtype_ParallelDiagonalTopLeft | - Transition_Subtype_ParallelVertical | - Transition_Subtype_Rectangle | Transition_Subtype_Right | - Transition_Subtype_RightCenter | Transition_Subtype_SixPoint | - Transition_Subtype_Top | Transition_Subtype_TopCenter | - Transition_Subtype_TopLeft | Transition_Subtype_TopLeftClockwise - | Transition_Subtype_TopLeftCounterClockwise | - Transition_Subtype_TopLeftDiagonal | - Transition_Subtype_TopLeftHorizontal | - Transition_Subtype_TopLeftVertical | Transition_Subtype_TopRight - | Transition_Subtype_TopRightClockwise | - Transition_Subtype_TopRightCounterClockwise | - Transition_Subtype_TopRightDiagonal | - Transition_Subtype_TopToBottom | - Transition_Subtype_TwoBladeHorizontal | - Transition_Subtype_TwoBladeVertical | - Transition_Subtype_TwoBoxBottom | Transition_Subtype_TwoBoxLeft - | Transition_Subtype_TwoBoxRight | Transition_Subtype_TwoBoxTop - | Transition_Subtype_Up | Transition_Subtype_Vertical | - Transition_Subtype_VerticalBottomLeftOpposite | - Transition_Subtype_VerticalBottomSame | - Transition_Subtype_VerticalLeft | - Transition_Subtype_VerticalRight | - Transition_Subtype_VerticalTopLeftOpposite | - Transition_Subtype_VerticalTopSame - deriving (Eq,Show) -data Transition_Coordinated = Transition_Coordinated_True | - Transition_Coordinated_False - deriving (Eq,Show) -data Transition_ClibBoundary = Transition_ClibBoundary_Parent | - Transition_ClibBoundary_Children - deriving (Eq,Show) -data Transition_Direction = Transition_Direction_Forward | - Transition_Direction_Reverse - deriving (Eq,Show) -data TransitionFilter = TransitionFilter - { transitionFilterId :: (Maybe String) - , transitionFilterClass :: (Maybe String) - , transitionFilterTitle :: (Maybe String) - , transitionFilterXml'lang :: (Maybe String) - , transitionFilterType :: (Maybe TransitionFilter_Type) - , transitionFilterSubtype :: (Maybe TransitionFilter_Subtype) - , transitionFilterHorzRepeat :: (Defaultable String) - , transitionFilterVertRepeat :: (Defaultable String) - , transitionFilterBorderWidth :: (Defaultable String) - , transitionFilterBorderColor :: (Defaultable String) - , transitionFilterFadeColor :: (Defaultable String) - , transitionFilterCoordinated :: (Defaultable TransitionFilter_Coordinated) - , transitionFilterClibBoundary :: (Defaultable TransitionFilter_ClibBoundary) - , transitionFilterDur :: (Maybe String) - , transitionFilterRepeatCount :: (Maybe String) - , transitionFilterRepeatDur :: (Maybe String) - , transitionFilterBegin :: (Maybe String) - , transitionFilterEnd :: (Maybe String) - , transitionFilterValues :: (Maybe String) - , transitionFilterFrom :: (Maybe String) - , transitionFilterTo :: (Maybe String) - , transitionFilterBy :: (Maybe String) - , transitionFilterCalcMode :: (Defaultable TransitionFilter_CalcMode) - } deriving (Eq,Show) -data TransitionFilter_Type = TransitionFilter_Type_BarWipe | - TransitionFilter_Type_BoxWipe | TransitionFilter_Type_FourBoxWipe - | TransitionFilter_Type_BarnDoorWipe | - TransitionFilter_Type_DiagonalWipe | - TransitionFilter_Type_BowTieWipe | - TransitionFilter_Type_MiscDiagonalWipe | - TransitionFilter_Type_VeeWipe | TransitionFilter_Type_BarnVeeWipe - | TransitionFilter_Type_ZigZagWipe | - TransitionFilter_Type_BarnZigZagWipe | - TransitionFilter_Type_MiscShapeWipe | - TransitionFilter_Type_TriangleWipe | - TransitionFilter_Type_ArrowHeadWipe | - TransitionFilter_Type_PentagonWipe | - TransitionFilter_Type_HexagonWipe | - TransitionFilter_Type_EllipseWipe | TransitionFilter_Type_EyeWipe - | TransitionFilter_Type_RoundRectWipe | - TransitionFilter_Type_StarWipe | TransitionFilter_Type_ClockWipe - | TransitionFilter_Type_PinWheelWipe | - TransitionFilter_Type_SingleSweepWipe | - TransitionFilter_Type_FanWipe | - TransitionFilter_Type_DoubleFanWipe | - TransitionFilter_Type_DoubleSweepWipe | - TransitionFilter_Type_SaloonDoorWipe | - TransitionFilter_Type_WindshieldWipe | - TransitionFilter_Type_SnakeWipe | - TransitionFilter_Type_SpiralWipe | - TransitionFilter_Type_ParallelSnakesWipe | - TransitionFilter_Type_BoxSnakesWipe | - TransitionFilter_Type_WaterfallWipe | - TransitionFilter_Type_PushWipe | TransitionFilter_Type_SlideWipe - | TransitionFilter_Type_Fade - deriving (Eq,Show) -data TransitionFilter_Subtype = TransitionFilter_Subtype_Bottom | - TransitionFilter_Subtype_BottomCenter | - TransitionFilter_Subtype_BottomLeft | - TransitionFilter_Subtype_BottomLeftClockwise | - TransitionFilter_Subtype_BottomLeftCounterClockwise | - TransitionFilter_Subtype_BottomLeftDiagonal | - TransitionFilter_Subtype_BottomRight | - TransitionFilter_Subtype_BottomRightClockwise | - TransitionFilter_Subtype_BottomRightCounterClockwise | - TransitionFilter_Subtype_BottomRightDiagonal | - TransitionFilter_Subtype_CenterRight | - TransitionFilter_Subtype_CenterTop | - TransitionFilter_Subtype_Circle | - TransitionFilter_Subtype_ClockwiseBottom | - TransitionFilter_Subtype_ClockwiseBottomRight | - TransitionFilter_Subtype_ClockwiseLeft | - TransitionFilter_Subtype_ClockwiseNine | - TransitionFilter_Subtype_ClockwiseRight | - TransitionFilter_Subtype_ClockwiseSix | - TransitionFilter_Subtype_ClockwiseThree | - TransitionFilter_Subtype_ClockwiseTop | - TransitionFilter_Subtype_ClockwiseTopLeft | - TransitionFilter_Subtype_ClockwiseTwelve | - TransitionFilter_Subtype_CornersIn | - TransitionFilter_Subtype_CornersOut | - TransitionFilter_Subtype_CounterClockwiseBottomLeft | - TransitionFilter_Subtype_CounterClockwiseTopRight | - TransitionFilter_Subtype_Crossfade | - TransitionFilter_Subtype_DiagonalBottomLeft | - TransitionFilter_Subtype_DiagonalBottomLeftOpposite | - TransitionFilter_Subtype_DiagonalTopLeft | - TransitionFilter_Subtype_DiagonalTopLeftOpposite | - TransitionFilter_Subtype_Diamond | - TransitionFilter_Subtype_DoubleBarnDoor | - TransitionFilter_Subtype_DoubleDiamond | - TransitionFilter_Subtype_Down | - TransitionFilter_Subtype_FadeFromColor | - TransitionFilter_Subtype_FadeToColor | - TransitionFilter_Subtype_FanInHorizontal | - TransitionFilter_Subtype_FanInVertical | - TransitionFilter_Subtype_FanOutHorizontal | - TransitionFilter_Subtype_FanOutVertical | - TransitionFilter_Subtype_FivePoint | - TransitionFilter_Subtype_FourBlade | - TransitionFilter_Subtype_FourBoxHorizontal | - TransitionFilter_Subtype_FourBoxVertical | - TransitionFilter_Subtype_FourPoint | - TransitionFilter_Subtype_FromBottom | - TransitionFilter_Subtype_FromLeft | - TransitionFilter_Subtype_FromRight | - TransitionFilter_Subtype_FromTop | TransitionFilter_Subtype_Heart - | TransitionFilter_Subtype_Horizontal | - TransitionFilter_Subtype_HorizontalLeft | - TransitionFilter_Subtype_HorizontalLeftSame | - TransitionFilter_Subtype_HorizontalRight | - TransitionFilter_Subtype_HorizontalRightSame | - TransitionFilter_Subtype_HorizontalTopLeftOpposite | - TransitionFilter_Subtype_HorizontalTopRightOpposite | - TransitionFilter_Subtype_Keyhole | TransitionFilter_Subtype_Left - | TransitionFilter_Subtype_LeftCenter | - TransitionFilter_Subtype_LeftToRight | - TransitionFilter_Subtype_OppositeHorizontal | - TransitionFilter_Subtype_OppositeVertical | - TransitionFilter_Subtype_ParallelDiagonal | - TransitionFilter_Subtype_ParallelDiagonalBottomLeft | - TransitionFilter_Subtype_ParallelDiagonalTopLeft | - TransitionFilter_Subtype_ParallelVertical | - TransitionFilter_Subtype_Rectangle | - TransitionFilter_Subtype_Right | - TransitionFilter_Subtype_RightCenter | - TransitionFilter_Subtype_SixPoint | TransitionFilter_Subtype_Top - | TransitionFilter_Subtype_TopCenter | - TransitionFilter_Subtype_TopLeft | - TransitionFilter_Subtype_TopLeftClockwise | - TransitionFilter_Subtype_TopLeftCounterClockwise | - TransitionFilter_Subtype_TopLeftDiagonal | - TransitionFilter_Subtype_TopLeftHorizontal | - TransitionFilter_Subtype_TopLeftVertical | - TransitionFilter_Subtype_TopRight | - TransitionFilter_Subtype_TopRightClockwise | - TransitionFilter_Subtype_TopRightCounterClockwise | - TransitionFilter_Subtype_TopRightDiagonal | - TransitionFilter_Subtype_TopToBottom | - TransitionFilter_Subtype_TwoBladeHorizontal | - TransitionFilter_Subtype_TwoBladeVertical | - TransitionFilter_Subtype_TwoBoxBottom | - TransitionFilter_Subtype_TwoBoxLeft | - TransitionFilter_Subtype_TwoBoxRight | - TransitionFilter_Subtype_TwoBoxTop | TransitionFilter_Subtype_Up - | TransitionFilter_Subtype_Vertical | - TransitionFilter_Subtype_VerticalBottomLeftOpposite | - TransitionFilter_Subtype_VerticalBottomSame | - TransitionFilter_Subtype_VerticalLeft | - TransitionFilter_Subtype_VerticalRight | - TransitionFilter_Subtype_VerticalTopLeftOpposite | - TransitionFilter_Subtype_VerticalTopSame - deriving (Eq,Show) -data TransitionFilter_Coordinated = TransitionFilter_Coordinated_True - | TransitionFilter_Coordinated_False - deriving (Eq,Show) -data TransitionFilter_ClibBoundary = TransitionFilter_ClibBoundary_Parent - | TransitionFilter_ClibBoundary_Children - deriving (Eq,Show) -data TransitionFilter_CalcMode = TransitionFilter_CalcMode_Discrete - | TransitionFilter_CalcMode_Linear | - TransitionFilter_CalcMode_Paced - deriving (Eq,Show) - - -{-Instance decls-} - -instance XmlContent Smil where - fromElem (CElem (Elem "smil" as []):rest) = - (Just (fromAttrs as), rest) - fromElem (CMisc _:rest) = fromElem rest - fromElem rest = (Nothing, rest) - toElem as = - [CElem (Elem "smil" (toAttrs as) [])] -instance XmlAttributes Smil where - fromAttrs as = - Smil - { smilId = possibleA fromAttrToStr "id" as - , smilClass = possibleA fromAttrToStr "class" as - , smilTitle = possibleA fromAttrToStr "title" as - , smilXml'lang = possibleA fromAttrToStr "xml:lang" as - , smilXmlns = defaultA fromAttrToStr "http://www.w3.org/TR/REC-smil/SMIL20" "xmlns" as - } - toAttrs v = catMaybes - [ maybeToAttr toAttrFrStr "id" (smilId v) - , maybeToAttr toAttrFrStr "class" (smilClass v) - , maybeToAttr toAttrFrStr "title" (smilTitle v) - , maybeToAttr toAttrFrStr "xml:lang" (smilXml'lang v) - , defaultToAttr toAttrFrStr "xmlns" (smilXmlns v) - ] -instance XmlContent Head where - fromElem (CElem (Elem "head" as []):rest) = - (Just (fromAttrs as), rest) - fromElem (CMisc _:rest) = fromElem rest - fromElem rest = (Nothing, rest) - toElem as = - [CElem (Elem "head" (toAttrs as) [])] -instance XmlAttributes Head where - fromAttrs as = - Head - { headId = possibleA fromAttrToStr "id" as - , headClass = possibleA fromAttrToStr "class" as - , headTitle = possibleA fromAttrToStr "title" as - , headXml'lang = possibleA fromAttrToStr "xml:lang" as - } - toAttrs v = catMaybes - [ maybeToAttr toAttrFrStr "id" (headId v) - , maybeToAttr toAttrFrStr "class" (headClass v) - , maybeToAttr toAttrFrStr "title" (headTitle v) - , maybeToAttr toAttrFrStr "xml:lang" (headXml'lang v) - ] -instance XmlContent Body where - fromElem (CElem (Elem "body" as []):rest) = - (Just (fromAttrs as), rest) - fromElem (CMisc _:rest) = fromElem rest - fromElem rest = (Nothing, rest) - toElem as = - [CElem (Elem "body" (toAttrs as) [])] -instance XmlAttributes Body where - fromAttrs as = - Body - { bodyId = possibleA fromAttrToStr "id" as - , bodyClass = possibleA fromAttrToStr "class" as - , bodyTitle = possibleA fromAttrToStr "title" as - , bodyXml'lang = possibleA fromAttrToStr "xml:lang" as - } - toAttrs v = catMaybes - [ maybeToAttr toAttrFrStr "id" (bodyId v) - , maybeToAttr toAttrFrStr "class" (bodyClass v) - , maybeToAttr toAttrFrStr "title" (bodyTitle v) - , maybeToAttr toAttrFrStr "xml:lang" (bodyXml'lang v) - ] -instance XmlContent Animate where - fromElem (CElem (Elem "animate" as []):rest) = - (Just (fromAttrs as), rest) - fromElem (CMisc _:rest) = fromElem rest - fromElem rest = (Nothing, rest) - toElem as = - [CElem (Elem "animate" (toAttrs as) [])] -instance XmlAttributes Animate where - fromAttrs as = - Animate - { animateId = possibleA fromAttrToStr "id" as - , animateClass = possibleA fromAttrToStr "class" as - , animateTitle = possibleA fromAttrToStr "title" as - , animateXml'lang = possibleA fromAttrToStr "xml:lang" as - , animateCustomTest = possibleA fromAttrToStr "customTest" as - , animateSystemBitrate = possibleA fromAttrToStr "systemBitrate" as - , animateSystemCaptions = possibleA fromAttrToTyp "systemCaptions" as - , animateSystemLanguage = possibleA fromAttrToStr "systemLanguage" as - , animateSystemOverdubOrSubtitle = possibleA fromAttrToTyp "systemOverdubOrSubtitle" as - , animateSystemRequired = possibleA fromAttrToStr "systemRequired" as - , animateSystemScreenSize = possibleA fromAttrToStr "systemScreenSize" as - , animateSystemScreenDepth = possibleA fromAttrToStr "systemScreenDepth" as - , animateSystemAudioDesc = possibleA fromAttrToTyp "systemAudioDesc" as - , animateSystemOperatingSystem = possibleA fromAttrToStr "systemOperatingSystem" as - , animateSystemCPU = possibleA fromAttrToStr "systemCPU" as - , animateSystemComponent = possibleA fromAttrToStr "systemComponent" as - , animateSystem_bitrate = possibleA fromAttrToStr "system-bitrate" as - , animateSystem_captions = possibleA fromAttrToTyp "system-captions" as - , animateSystem_language = possibleA fromAttrToStr "system-language" as - , animateSystem_overdub_or_caption = possibleA fromAttrToTyp "system-overdub-or-caption" as - , animateSystem_required = possibleA fromAttrToStr "system-required" as - , animateSystem_screen_size = possibleA fromAttrToStr "system-screen-size" as - , animateSystem_screen_depth = possibleA fromAttrToStr "system-screen-depth" as - , animateDur = possibleA fromAttrToStr "dur" as - , animateRepeatCount = possibleA fromAttrToStr "repeatCount" as - , animateRepeatDur = possibleA fromAttrToStr "repeatDur" as - , animateBegin = possibleA fromAttrToStr "begin" as - , animateEnd = possibleA fromAttrToStr "end" as - , animateAttributeName = definiteA fromAttrToStr "animate" "attributeName" as - , animateAttributeType = possibleA fromAttrToStr "attributeType" as - , animateValues = possibleA fromAttrToStr "values" as - , animateFrom = possibleA fromAttrToStr "from" as - , animateTo = possibleA fromAttrToStr "to" as - , animateBy = possibleA fromAttrToStr "by" as - , animateCalcMode = defaultA fromAttrToTyp Animate_CalcMode_Linear "calcMode" as - , animateAdditive = defaultA fromAttrToTyp Animate_Additive_Replace "additive" as - , animateAccumulate = defaultA fromAttrToTyp Animate_Accumulate_None "accumulate" as - } - toAttrs v = catMaybes - [ maybeToAttr toAttrFrStr "id" (animateId v) - , maybeToAttr toAttrFrStr "class" (animateClass v) - , maybeToAttr toAttrFrStr "title" (animateTitle v) - , maybeToAttr toAttrFrStr "xml:lang" (animateXml'lang v) - , maybeToAttr toAttrFrStr "customTest" (animateCustomTest v) - , maybeToAttr toAttrFrStr "systemBitrate" (animateSystemBitrate v) - , maybeToAttr toAttrFrTyp "systemCaptions" (animateSystemCaptions v) - , maybeToAttr toAttrFrStr "systemLanguage" (animateSystemLanguage v) - , maybeToAttr toAttrFrTyp "systemOverdubOrSubtitle" (animateSystemOverdubOrSubtitle v) - , maybeToAttr toAttrFrStr "systemRequired" (animateSystemRequired v) - , maybeToAttr toAttrFrStr "systemScreenSize" (animateSystemScreenSize v) - , maybeToAttr toAttrFrStr "systemScreenDepth" (animateSystemScreenDepth v) - , maybeToAttr toAttrFrTyp "systemAudioDesc" (animateSystemAudioDesc v) - , maybeToAttr toAttrFrStr "systemOperatingSystem" (animateSystemOperatingSystem v) - , maybeToAttr toAttrFrStr "systemCPU" (animateSystemCPU v) - , maybeToAttr toAttrFrStr "systemComponent" (animateSystemComponent v) - , maybeToAttr toAttrFrStr "system-bitrate" (animateSystem_bitrate v) - , maybeToAttr toAttrFrTyp "system-captions" (animateSystem_captions v) - , maybeToAttr toAttrFrStr "system-language" (animateSystem_language v) - , maybeToAttr toAttrFrTyp "system-overdub-or-caption" (animateSystem_overdub_or_caption v) - , maybeToAttr toAttrFrStr "system-required" (animateSystem_required v) - , maybeToAttr toAttrFrStr "system-screen-size" (animateSystem_screen_size v) - , maybeToAttr toAttrFrStr "system-screen-depth" (animateSystem_screen_depth v) - , maybeToAttr toAttrFrStr "dur" (animateDur v) - , maybeToAttr toAttrFrStr "repeatCount" (animateRepeatCount v) - , maybeToAttr toAttrFrStr "repeatDur" (animateRepeatDur v) - , maybeToAttr toAttrFrStr "begin" (animateBegin v) - , maybeToAttr toAttrFrStr "end" (animateEnd v) - , toAttrFrStr "attributeName" (animateAttributeName v) - , maybeToAttr toAttrFrStr "attributeType" (animateAttributeType v) - , maybeToAttr toAttrFrStr "values" (animateValues v) - , maybeToAttr toAttrFrStr "from" (animateFrom v) - , maybeToAttr toAttrFrStr "to" (animateTo v) - , maybeToAttr toAttrFrStr "by" (animateBy v) - , defaultToAttr toAttrFrTyp "calcMode" (animateCalcMode v) - , defaultToAttr toAttrFrTyp "additive" (animateAdditive v) - , defaultToAttr toAttrFrTyp "accumulate" (animateAccumulate v) - ] -instance XmlAttrType Animate_SystemCaptions where - fromAttrToTyp n (n',v) - | n==n' = translate (attr2str v) - | otherwise = Nothing - where translate "on" = Just Animate_SystemCaptions_On - translate "off" = Just Animate_SystemCaptions_Off - translate _ = Nothing - toAttrFrTyp n Animate_SystemCaptions_On = Just (n, str2attr "on") - toAttrFrTyp n Animate_SystemCaptions_Off = Just (n, str2attr "off") -instance XmlAttrType Animate_SystemOverdubOrSubtitle where - fromAttrToTyp n (n',v) - | n==n' = translate (attr2str v) - | otherwise = Nothing - where translate "overdub" = Just Animate_SystemOverdubOrSubtitle_Overdub - translate "subtitle" = Just Animate_SystemOverdubOrSubtitle_Subtitle - translate _ = Nothing - toAttrFrTyp n Animate_SystemOverdubOrSubtitle_Overdub = Just (n, str2attr "overdub") - toAttrFrTyp n Animate_SystemOverdubOrSubtitle_Subtitle = Just (n, str2attr "subtitle") -instance XmlAttrType Animate_SystemAudioDesc where - fromAttrToTyp n (n',v) - | n==n' = translate (attr2str v) - | otherwise = Nothing - where translate "on" = Just Animate_SystemAudioDesc_On - translate "off" = Just Animate_SystemAudioDesc_Off - translate _ = Nothing - toAttrFrTyp n Animate_SystemAudioDesc_On = Just (n, str2attr "on") - toAttrFrTyp n Animate_SystemAudioDesc_Off = Just (n, str2attr "off") -instance XmlAttrType Animate_System_captions where - fromAttrToTyp n (n',v) - | n==n' = translate (attr2str v) - | otherwise = Nothing - where translate "on" = Just Animate_System_captions_On - translate "off" = Just Animate_System_captions_Off - translate _ = Nothing - toAttrFrTyp n Animate_System_captions_On = Just (n, str2attr "on") - toAttrFrTyp n Animate_System_captions_Off = Just (n, str2attr "off") -instance XmlAttrType Animate_System_overdub_or_caption where - fromAttrToTyp n (n',v) - | n==n' = translate (attr2str v) - | otherwise = Nothing - where translate "overdub" = Just Animate_System_overdub_or_caption_Overdub - translate "caption" = Just Animate_System_overdub_or_caption_Caption - translate _ = Nothing - toAttrFrTyp n Animate_System_overdub_or_caption_Overdub = Just (n, str2attr "overdub") - toAttrFrTyp n Animate_System_overdub_or_caption_Caption = Just (n, str2attr "caption") -instance XmlAttrType Animate_CalcMode where - fromAttrToTyp n (n',v) - | n==n' = translate (attr2str v) - | otherwise = Nothing - where translate "discrete" = Just Animate_CalcMode_Discrete - translate "linear" = Just Animate_CalcMode_Linear - translate "paced" = Just Animate_CalcMode_Paced - translate _ = Nothing - toAttrFrTyp n Animate_CalcMode_Discrete = Just (n, str2attr "discrete") - toAttrFrTyp n Animate_CalcMode_Linear = Just (n, str2attr "linear") - toAttrFrTyp n Animate_CalcMode_Paced = Just (n, str2attr "paced") -instance XmlAttrType Animate_Additive where - fromAttrToTyp n (n',v) - | n==n' = translate (attr2str v) - | otherwise = Nothing - where translate "replace" = Just Animate_Additive_Replace - translate "sum" = Just Animate_Additive_Sum - translate _ = Nothing - toAttrFrTyp n Animate_Additive_Replace = Just (n, str2attr "replace") - toAttrFrTyp n Animate_Additive_Sum = Just (n, str2attr "sum") -instance XmlAttrType Animate_Accumulate where - fromAttrToTyp n (n',v) - | n==n' = translate (attr2str v) - | otherwise = Nothing - where translate "none" = Just Animate_Accumulate_None - translate "sum" = Just Animate_Accumulate_Sum - translate _ = Nothing - toAttrFrTyp n Animate_Accumulate_None = Just (n, str2attr "none") - toAttrFrTyp n Animate_Accumulate_Sum = Just (n, str2attr "sum") -instance XmlContent Set where - fromElem (CElem (Elem "set" as []):rest) = - (Just (fromAttrs as), rest) - fromElem (CMisc _:rest) = fromElem rest - fromElem rest = (Nothing, rest) - toElem as = - [CElem (Elem "set" (toAttrs as) [])] -instance XmlAttributes Set where - fromAttrs as = - Set - { setId = possibleA fromAttrToStr "id" as - , setClass = possibleA fromAttrToStr "class" as - , setTitle = possibleA fromAttrToStr "title" as - , setXml'lang = possibleA fromAttrToStr "xml:lang" as - , setCustomTest = possibleA fromAttrToStr "customTest" as - , setSystemBitrate = possibleA fromAttrToStr "systemBitrate" as - , setSystemCaptions = possibleA fromAttrToTyp "systemCaptions" as - , setSystemLanguage = possibleA fromAttrToStr "systemLanguage" as - , setSystemOverdubOrSubtitle = possibleA fromAttrToTyp "systemOverdubOrSubtitle" as - , setSystemRequired = possibleA fromAttrToStr "systemRequired" as - , setSystemScreenSize = possibleA fromAttrToStr "systemScreenSize" as - , setSystemScreenDepth = possibleA fromAttrToStr "systemScreenDepth" as - , setSystemAudioDesc = possibleA fromAttrToTyp "systemAudioDesc" as - , setSystemOperatingSystem = possibleA fromAttrToStr "systemOperatingSystem" as - , setSystemCPU = possibleA fromAttrToStr "systemCPU" as - , setSystemComponent = possibleA fromAttrToStr "systemComponent" as - , setSystem_bitrate = possibleA fromAttrToStr "system-bitrate" as - , setSystem_captions = possibleA fromAttrToTyp "system-captions" as - , setSystem_language = possibleA fromAttrToStr "system-language" as - , setSystem_overdub_or_caption = possibleA fromAttrToTyp "system-overdub-or-caption" as - , setSystem_required = possibleA fromAttrToStr "system-required" as - , setSystem_screen_size = possibleA fromAttrToStr "system-screen-size" as - , setSystem_screen_depth = possibleA fromAttrToStr "system-screen-depth" as - , setDur = possibleA fromAttrToStr "dur" as - , setRepeatCount = possibleA fromAttrToStr "repeatCount" as - , setRepeatDur = possibleA fromAttrToStr "repeatDur" as - , setBegin = possibleA fromAttrToStr "begin" as - , setEnd = possibleA fromAttrToStr "end" as - , setAttributeName = definiteA fromAttrToStr "set" "attributeName" as - , setAttributeType = possibleA fromAttrToStr "attributeType" as - , setTo = possibleA fromAttrToStr "to" as - } - toAttrs v = catMaybes - [ maybeToAttr toAttrFrStr "id" (setId v) - , maybeToAttr toAttrFrStr "class" (setClass v) - , maybeToAttr toAttrFrStr "title" (setTitle v) - , maybeToAttr toAttrFrStr "xml:lang" (setXml'lang v) - , maybeToAttr toAttrFrStr "customTest" (setCustomTest v) - , maybeToAttr toAttrFrStr "systemBitrate" (setSystemBitrate v) - , maybeToAttr toAttrFrTyp "systemCaptions" (setSystemCaptions v) - , maybeToAttr toAttrFrStr "systemLanguage" (setSystemLanguage v) - , maybeToAttr toAttrFrTyp "systemOverdubOrSubtitle" (setSystemOverdubOrSubtitle v) - , maybeToAttr toAttrFrStr "systemRequired" (setSystemRequired v) - , maybeToAttr toAttrFrStr "systemScreenSize" (setSystemScreenSize v) - , maybeToAttr toAttrFrStr "systemScreenDepth" (setSystemScreenDepth v) - , maybeToAttr toAttrFrTyp "systemAudioDesc" (setSystemAudioDesc v) - , maybeToAttr toAttrFrStr "systemOperatingSystem" (setSystemOperatingSystem v) - , maybeToAttr toAttrFrStr "systemCPU" (setSystemCPU v) - , maybeToAttr toAttrFrStr "systemComponent" (setSystemComponent v) - , maybeToAttr toAttrFrStr "system-bitrate" (setSystem_bitrate v) - , maybeToAttr toAttrFrTyp "system-captions" (setSystem_captions v) - , maybeToAttr toAttrFrStr "system-language" (setSystem_language v) - , maybeToAttr toAttrFrTyp "system-overdub-or-caption" (setSystem_overdub_or_caption v) - , maybeToAttr toAttrFrStr "system-required" (setSystem_required v) - , maybeToAttr toAttrFrStr "system-screen-size" (setSystem_screen_size v) - , maybeToAttr toAttrFrStr "system-screen-depth" (setSystem_screen_depth v) - , maybeToAttr toAttrFrStr "dur" (setDur v) - , maybeToAttr toAttrFrStr "repeatCount" (setRepeatCount v) - , maybeToAttr toAttrFrStr "repeatDur" (setRepeatDur v) - , maybeToAttr toAttrFrStr "begin" (setBegin v) - , maybeToAttr toAttrFrStr "end" (setEnd v) - , toAttrFrStr "attributeName" (setAttributeName v) - , maybeToAttr toAttrFrStr "attributeType" (setAttributeType v) - , maybeToAttr toAttrFrStr "to" (setTo v) - ] -instance XmlAttrType Set_SystemCaptions where - fromAttrToTyp n (n',v) - | n==n' = translate (attr2str v) - | otherwise = Nothing - where translate "on" = Just Set_SystemCaptions_On - translate "off" = Just Set_SystemCaptions_Off - translate _ = Nothing - toAttrFrTyp n Set_SystemCaptions_On = Just (n, str2attr "on") - toAttrFrTyp n Set_SystemCaptions_Off = Just (n, str2attr "off") -instance XmlAttrType Set_SystemOverdubOrSubtitle where - fromAttrToTyp n (n',v) - | n==n' = translate (attr2str v) - | otherwise = Nothing - where translate "overdub" = Just Set_SystemOverdubOrSubtitle_Overdub - translate "subtitle" = Just Set_SystemOverdubOrSubtitle_Subtitle - translate _ = Nothing - toAttrFrTyp n Set_SystemOverdubOrSubtitle_Overdub = Just (n, str2attr "overdub") - toAttrFrTyp n Set_SystemOverdubOrSubtitle_Subtitle = Just (n, str2attr "subtitle") -instance XmlAttrType Set_SystemAudioDesc where - fromAttrToTyp n (n',v) - | n==n' = translate (attr2str v) - | otherwise = Nothing - where translate "on" = Just Set_SystemAudioDesc_On - translate "off" = Just Set_SystemAudioDesc_Off - translate _ = Nothing - toAttrFrTyp n Set_SystemAudioDesc_On = Just (n, str2attr "on") - toAttrFrTyp n Set_SystemAudioDesc_Off = Just (n, str2attr "off") -instance XmlAttrType Set_System_captions where - fromAttrToTyp n (n',v) - | n==n' = translate (attr2str v) - | otherwise = Nothing - where translate "on" = Just Set_System_captions_On - translate "off" = Just Set_System_captions_Off - translate _ = Nothing - toAttrFrTyp n Set_System_captions_On = Just (n, str2attr "on") - toAttrFrTyp n Set_System_captions_Off = Just (n, str2attr "off") -instance XmlAttrType Set_System_overdub_or_caption where - fromAttrToTyp n (n',v) - | n==n' = translate (attr2str v) - | otherwise = Nothing - where translate "overdub" = Just Set_System_overdub_or_caption_Overdub - translate "caption" = Just Set_System_overdub_or_caption_Caption - translate _ = Nothing - toAttrFrTyp n Set_System_overdub_or_caption_Overdub = Just (n, str2attr "overdub") - toAttrFrTyp n Set_System_overdub_or_caption_Caption = Just (n, str2attr "caption") -instance XmlContent AnimateMotion where - fromElem (CElem (Elem "animateMotion" as []):rest) = - (Just (fromAttrs as), rest) - fromElem (CMisc _:rest) = fromElem rest - fromElem rest = (Nothing, rest) - toElem as = - [CElem (Elem "animateMotion" (toAttrs as) [])] -instance XmlAttributes AnimateMotion where - fromAttrs as = - AnimateMotion - { animateMotionId = possibleA fromAttrToStr "id" as - , animateMotionClass = possibleA fromAttrToStr "class" as - , animateMotionTitle = possibleA fromAttrToStr "title" as - , animateMotionXml'lang = possibleA fromAttrToStr "xml:lang" as - , animateMotionCustomTest = possibleA fromAttrToStr "customTest" as - , animateMotionSystemBitrate = possibleA fromAttrToStr "systemBitrate" as - , animateMotionSystemCaptions = possibleA fromAttrToTyp "systemCaptions" as - , animateMotionSystemLanguage = possibleA fromAttrToStr "systemLanguage" as - , animateMotionSystemOverdubOrSubtitle = possibleA fromAttrToTyp "systemOverdubOrSubtitle" as - , animateMotionSystemRequired = possibleA fromAttrToStr "systemRequired" as - , animateMotionSystemScreenSize = possibleA fromAttrToStr "systemScreenSize" as - , animateMotionSystemScreenDepth = possibleA fromAttrToStr "systemScreenDepth" as - , animateMotionSystemAudioDesc = possibleA fromAttrToTyp "systemAudioDesc" as - , animateMotionSystemOperatingSystem = possibleA fromAttrToStr "systemOperatingSystem" as - , animateMotionSystemCPU = possibleA fromAttrToStr "systemCPU" as - , animateMotionSystemComponent = possibleA fromAttrToStr "systemComponent" as - , animateMotionSystem_bitrate = possibleA fromAttrToStr "system-bitrate" as - , animateMotionSystem_captions = possibleA fromAttrToTyp "system-captions" as - , animateMotionSystem_language = possibleA fromAttrToStr "system-language" as - , animateMotionSystem_overdub_or_caption = possibleA fromAttrToTyp "system-overdub-or-caption" as - , animateMotionSystem_required = possibleA fromAttrToStr "system-required" as - , animateMotionSystem_screen_size = possibleA fromAttrToStr "system-screen-size" as - , animateMotionSystem_screen_depth = possibleA fromAttrToStr "system-screen-depth" as - , animateMotionDur = possibleA fromAttrToStr "dur" as - , animateMotionRepeatCount = possibleA fromAttrToStr "repeatCount" as - , animateMotionRepeatDur = possibleA fromAttrToStr "repeatDur" as - , animateMotionBegin = possibleA fromAttrToStr "begin" as - , animateMotionEnd = possibleA fromAttrToStr "end" as - , animateMotionValues = possibleA fromAttrToStr "values" as - , animateMotionFrom = possibleA fromAttrToStr "from" as - , animateMotionTo = possibleA fromAttrToStr "to" as - , animateMotionBy = possibleA fromAttrToStr "by" as - , animateMotionCalcMode = defaultA fromAttrToTyp AnimateMotion_CalcMode_Linear "calcMode" as - , animateMotionAdditive = defaultA fromAttrToTyp AnimateMotion_Additive_Replace "additive" as - , animateMotionAccumulate = defaultA fromAttrToTyp AnimateMotion_Accumulate_None "accumulate" as - , animateMotionOrigin = defaultA fromAttrToTyp AnimateMotion_Origin_Default "origin" as - } - toAttrs v = catMaybes - [ maybeToAttr toAttrFrStr "id" (animateMotionId v) - , maybeToAttr toAttrFrStr "class" (animateMotionClass v) - , maybeToAttr toAttrFrStr "title" (animateMotionTitle v) - , maybeToAttr toAttrFrStr "xml:lang" (animateMotionXml'lang v) - , maybeToAttr toAttrFrStr "customTest" (animateMotionCustomTest v) - , maybeToAttr toAttrFrStr "systemBitrate" (animateMotionSystemBitrate v) - , maybeToAttr toAttrFrTyp "systemCaptions" (animateMotionSystemCaptions v) - , maybeToAttr toAttrFrStr "systemLanguage" (animateMotionSystemLanguage v) - , maybeToAttr toAttrFrTyp "systemOverdubOrSubtitle" (animateMotionSystemOverdubOrSubtitle v) - , maybeToAttr toAttrFrStr "systemRequired" (animateMotionSystemRequired v) - , maybeToAttr toAttrFrStr "systemScreenSize" (animateMotionSystemScreenSize v) - , maybeToAttr toAttrFrStr "systemScreenDepth" (animateMotionSystemScreenDepth v) - , maybeToAttr toAttrFrTyp "systemAudioDesc" (animateMotionSystemAudioDesc v) - , maybeToAttr toAttrFrStr "systemOperatingSystem" (animateMotionSystemOperatingSystem v) - , maybeToAttr toAttrFrStr "systemCPU" (animateMotionSystemCPU v) - , maybeToAttr toAttrFrStr "systemComponent" (animateMotionSystemComponent v) - , maybeToAttr toAttrFrStr "system-bitrate" (animateMotionSystem_bitrate v) - , maybeToAttr toAttrFrTyp "system-captions" (animateMotionSystem_captions v) - , maybeToAttr toAttrFrStr "system-language" (animateMotionSystem_language v) - , maybeToAttr toAttrFrTyp "system-overdub-or-caption" (animateMotionSystem_overdub_or_caption v) - , maybeToAttr toAttrFrStr "system-required" (animateMotionSystem_required v) - , maybeToAttr toAttrFrStr "system-screen-size" (animateMotionSystem_screen_size v) - , maybeToAttr toAttrFrStr "system-screen-depth" (animateMotionSystem_screen_depth v) - , maybeToAttr toAttrFrStr "dur" (animateMotionDur v) - , maybeToAttr toAttrFrStr "repeatCount" (animateMotionRepeatCount v) - , maybeToAttr toAttrFrStr "repeatDur" (animateMotionRepeatDur v) - , maybeToAttr toAttrFrStr "begin" (animateMotionBegin v) - , maybeToAttr toAttrFrStr "end" (animateMotionEnd v) - , maybeToAttr toAttrFrStr "values" (animateMotionValues v) - , maybeToAttr toAttrFrStr "from" (animateMotionFrom v) - , maybeToAttr toAttrFrStr "to" (animateMotionTo v) - , maybeToAttr toAttrFrStr "by" (animateMotionBy v) - , defaultToAttr toAttrFrTyp "calcMode" (animateMotionCalcMode v) - , defaultToAttr toAttrFrTyp "additive" (animateMotionAdditive v) - , defaultToAttr toAttrFrTyp "accumulate" (animateMotionAccumulate v) - , defaultToAttr toAttrFrTyp "origin" (animateMotionOrigin v) - ] -instance XmlAttrType AnimateMotion_SystemCaptions where - fromAttrToTyp n (n',v) - | n==n' = translate (attr2str v) - | otherwise = Nothing - where translate "on" = Just AnimateMotion_SystemCaptions_On - translate "off" = Just AnimateMotion_SystemCaptions_Off - translate _ = Nothing - toAttrFrTyp n AnimateMotion_SystemCaptions_On = Just (n, str2attr "on") - toAttrFrTyp n AnimateMotion_SystemCaptions_Off = Just (n, str2attr "off") -instance XmlAttrType AnimateMotion_SystemOverdubOrSubtitle where - fromAttrToTyp n (n',v) - | n==n' = translate (attr2str v) - | otherwise = Nothing - where translate "overdub" = Just AnimateMotion_SystemOverdubOrSubtitle_Overdub - translate "subtitle" = Just AnimateMotion_SystemOverdubOrSubtitle_Subtitle - translate _ = Nothing - toAttrFrTyp n AnimateMotion_SystemOverdubOrSubtitle_Overdub = Just (n, str2attr "overdub") - toAttrFrTyp n AnimateMotion_SystemOverdubOrSubtitle_Subtitle = Just (n, str2attr "subtitle") -instance XmlAttrType AnimateMotion_SystemAudioDesc where - fromAttrToTyp n (n',v) - | n==n' = translate (attr2str v) - | otherwise = Nothing - where translate "on" = Just AnimateMotion_SystemAudioDesc_On - translate "off" = Just AnimateMotion_SystemAudioDesc_Off - translate _ = Nothing - toAttrFrTyp n AnimateMotion_SystemAudioDesc_On = Just (n, str2attr "on") - toAttrFrTyp n AnimateMotion_SystemAudioDesc_Off = Just (n, str2attr "off") -instance XmlAttrType AnimateMotion_System_captions where - fromAttrToTyp n (n',v) - | n==n' = translate (attr2str v) - | otherwise = Nothing - where translate "on" = Just AnimateMotion_System_captions_On - translate "off" = Just AnimateMotion_System_captions_Off - translate _ = Nothing - toAttrFrTyp n AnimateMotion_System_captions_On = Just (n, str2attr "on") - toAttrFrTyp n AnimateMotion_System_captions_Off = Just (n, str2attr "off") -instance XmlAttrType AnimateMotion_System_overdub_or_caption where - fromAttrToTyp n (n',v) - | n==n' = translate (attr2str v) - | otherwise = Nothing - where translate "overdub" = Just AnimateMotion_System_overdub_or_caption_Overdub - translate "caption" = Just AnimateMotion_System_overdub_or_caption_Caption - translate _ = Nothing - toAttrFrTyp n AnimateMotion_System_overdub_or_caption_Overdub = Just (n, str2attr "overdub") - toAttrFrTyp n AnimateMotion_System_overdub_or_caption_Caption = Just (n, str2attr "caption") -instance XmlAttrType AnimateMotion_CalcMode where - fromAttrToTyp n (n',v) - | n==n' = translate (attr2str v) - | otherwise = Nothing - where translate "discrete" = Just AnimateMotion_CalcMode_Discrete - translate "linear" = Just AnimateMotion_CalcMode_Linear - translate "paced" = Just AnimateMotion_CalcMode_Paced - translate _ = Nothing - toAttrFrTyp n AnimateMotion_CalcMode_Discrete = Just (n, str2attr "discrete") - toAttrFrTyp n AnimateMotion_CalcMode_Linear = Just (n, str2attr "linear") - toAttrFrTyp n AnimateMotion_CalcMode_Paced = Just (n, str2attr "paced") -instance XmlAttrType AnimateMotion_Additive where - fromAttrToTyp n (n',v) - | n==n' = translate (attr2str v) - | otherwise = Nothing - where translate "replace" = Just AnimateMotion_Additive_Replace - translate "sum" = Just AnimateMotion_Additive_Sum - translate _ = Nothing - toAttrFrTyp n AnimateMotion_Additive_Replace = Just (n, str2attr "replace") - toAttrFrTyp n AnimateMotion_Additive_Sum = Just (n, str2attr "sum") -instance XmlAttrType AnimateMotion_Accumulate where - fromAttrToTyp n (n',v) - | n==n' = translate (attr2str v) - | otherwise = Nothing - where translate "none" = Just AnimateMotion_Accumulate_None - translate "sum" = Just AnimateMotion_Accumulate_Sum - translate _ = Nothing - toAttrFrTyp n AnimateMotion_Accumulate_None = Just (n, str2attr "none") - toAttrFrTyp n AnimateMotion_Accumulate_Sum = Just (n, str2attr "sum") -instance XmlAttrType AnimateMotion_Origin where - fromAttrToTyp n (n',v) - | n==n' = translate (attr2str v) - | otherwise = Nothing - where translate "default" = Just AnimateMotion_Origin_Default - translate _ = Nothing - toAttrFrTyp n AnimateMotion_Origin_Default = Just (n, str2attr "default") -instance XmlContent AnimateColor where - fromElem (CElem (Elem "animateColor" as []):rest) = - (Just (fromAttrs as), rest) - fromElem (CMisc _:rest) = fromElem rest - fromElem rest = (Nothing, rest) - toElem as = - [CElem (Elem "animateColor" (toAttrs as) [])] -instance XmlAttributes AnimateColor where - fromAttrs as = - AnimateColor - { animateColorId = possibleA fromAttrToStr "id" as - , animateColorClass = possibleA fromAttrToStr "class" as - , animateColorTitle = possibleA fromAttrToStr "title" as - , animateColorXml'lang = possibleA fromAttrToStr "xml:lang" as - , animateColorCustomTest = possibleA fromAttrToStr "customTest" as - , animateColorSystemBitrate = possibleA fromAttrToStr "systemBitrate" as - , animateColorSystemCaptions = possibleA fromAttrToTyp "systemCaptions" as - , animateColorSystemLanguage = possibleA fromAttrToStr "systemLanguage" as - , animateColorSystemOverdubOrSubtitle = possibleA fromAttrToTyp "systemOverdubOrSubtitle" as - , animateColorSystemRequired = possibleA fromAttrToStr "systemRequired" as - , animateColorSystemScreenSize = possibleA fromAttrToStr "systemScreenSize" as - , animateColorSystemScreenDepth = possibleA fromAttrToStr "systemScreenDepth" as - , animateColorSystemAudioDesc = possibleA fromAttrToTyp "systemAudioDesc" as - , animateColorSystemOperatingSystem = possibleA fromAttrToStr "systemOperatingSystem" as - , animateColorSystemCPU = possibleA fromAttrToStr "systemCPU" as - , animateColorSystemComponent = possibleA fromAttrToStr "systemComponent" as - , animateColorSystem_bitrate = possibleA fromAttrToStr "system-bitrate" as - , animateColorSystem_captions = possibleA fromAttrToTyp "system-captions" as - , animateColorSystem_language = possibleA fromAttrToStr "system-language" as - , animateColorSystem_overdub_or_caption = possibleA fromAttrToTyp "system-overdub-or-caption" as - , animateColorSystem_required = possibleA fromAttrToStr "system-required" as - , animateColorSystem_screen_size = possibleA fromAttrToStr "system-screen-size" as - , animateColorSystem_screen_depth = possibleA fromAttrToStr "system-screen-depth" as - , animateColorDur = possibleA fromAttrToStr "dur" as - , animateColorRepeatCount = possibleA fromAttrToStr "repeatCount" as - , animateColorRepeatDur = possibleA fromAttrToStr "repeatDur" as - , animateColorBegin = possibleA fromAttrToStr "begin" as - , animateColorEnd = possibleA fromAttrToStr "end" as - , animateColorAttributeName = definiteA fromAttrToStr "animateColor" "attributeName" as - , animateColorAttributeType = possibleA fromAttrToStr "attributeType" as - , animateColorValues = possibleA fromAttrToStr "values" as - , animateColorFrom = possibleA fromAttrToStr "from" as - , animateColorTo = possibleA fromAttrToStr "to" as - , animateColorBy = possibleA fromAttrToStr "by" as - , animateColorCalcMode = defaultA fromAttrToTyp AnimateColor_CalcMode_Linear "calcMode" as - , animateColorAdditive = defaultA fromAttrToTyp AnimateColor_Additive_Replace "additive" as - , animateColorAccumulate = defaultA fromAttrToTyp AnimateColor_Accumulate_None "accumulate" as - } - toAttrs v = catMaybes - [ maybeToAttr toAttrFrStr "id" (animateColorId v) - , maybeToAttr toAttrFrStr "class" (animateColorClass v) - , maybeToAttr toAttrFrStr "title" (animateColorTitle v) - , maybeToAttr toAttrFrStr "xml:lang" (animateColorXml'lang v) - , maybeToAttr toAttrFrStr "customTest" (animateColorCustomTest v) - , maybeToAttr toAttrFrStr "systemBitrate" (animateColorSystemBitrate v) - , maybeToAttr toAttrFrTyp "systemCaptions" (animateColorSystemCaptions v) - , maybeToAttr toAttrFrStr "systemLanguage" (animateColorSystemLanguage v) - , maybeToAttr toAttrFrTyp "systemOverdubOrSubtitle" (animateColorSystemOverdubOrSubtitle v) - , maybeToAttr toAttrFrStr "systemRequired" (animateColorSystemRequired v) - , maybeToAttr toAttrFrStr "systemScreenSize" (animateColorSystemScreenSize v) - , maybeToAttr toAttrFrStr "systemScreenDepth" (animateColorSystemScreenDepth v) - , maybeToAttr toAttrFrTyp "systemAudioDesc" (animateColorSystemAudioDesc v) - , maybeToAttr toAttrFrStr "systemOperatingSystem" (animateColorSystemOperatingSystem v) - , maybeToAttr toAttrFrStr "systemCPU" (animateColorSystemCPU v) - , maybeToAttr toAttrFrStr "systemComponent" (animateColorSystemComponent v) - , maybeToAttr toAttrFrStr "system-bitrate" (animateColorSystem_bitrate v) - , maybeToAttr toAttrFrTyp "system-captions" (animateColorSystem_captions v) - , maybeToAttr toAttrFrStr "system-language" (animateColorSystem_language v) - , maybeToAttr toAttrFrTyp "system-overdub-or-caption" (animateColorSystem_overdub_or_caption v) - , maybeToAttr toAttrFrStr "system-required" (animateColorSystem_required v) - , maybeToAttr toAttrFrStr "system-screen-size" (animateColorSystem_screen_size v) - , maybeToAttr toAttrFrStr "system-screen-depth" (animateColorSystem_screen_depth v) - , maybeToAttr toAttrFrStr "dur" (animateColorDur v) - , maybeToAttr toAttrFrStr "repeatCount" (animateColorRepeatCount v) - , maybeToAttr toAttrFrStr "repeatDur" (animateColorRepeatDur v) - , maybeToAttr toAttrFrStr "begin" (animateColorBegin v) - , maybeToAttr toAttrFrStr "end" (animateColorEnd v) - , toAttrFrStr "attributeName" (animateColorAttributeName v) - , maybeToAttr toAttrFrStr "attributeType" (animateColorAttributeType v) - , maybeToAttr toAttrFrStr "values" (animateColorValues v) - , maybeToAttr toAttrFrStr "from" (animateColorFrom v) - , maybeToAttr toAttrFrStr "to" (animateColorTo v) - , maybeToAttr toAttrFrStr "by" (animateColorBy v) - , defaultToAttr toAttrFrTyp "calcMode" (animateColorCalcMode v) - , defaultToAttr toAttrFrTyp "additive" (animateColorAdditive v) - , defaultToAttr toAttrFrTyp "accumulate" (animateColorAccumulate v) - ] -instance XmlAttrType AnimateColor_SystemCaptions where - fromAttrToTyp n (n',v) - | n==n' = translate (attr2str v) - | otherwise = Nothing - where translate "on" = Just AnimateColor_SystemCaptions_On - translate "off" = Just AnimateColor_SystemCaptions_Off - translate _ = Nothing - toAttrFrTyp n AnimateColor_SystemCaptions_On = Just (n, str2attr "on") - toAttrFrTyp n AnimateColor_SystemCaptions_Off = Just (n, str2attr "off") -instance XmlAttrType AnimateColor_SystemOverdubOrSubtitle where - fromAttrToTyp n (n',v) - | n==n' = translate (attr2str v) - | otherwise = Nothing - where translate "overdub" = Just AnimateColor_SystemOverdubOrSubtitle_Overdub - translate "subtitle" = Just AnimateColor_SystemOverdubOrSubtitle_Subtitle - translate _ = Nothing - toAttrFrTyp n AnimateColor_SystemOverdubOrSubtitle_Overdub = Just (n, str2attr "overdub") - toAttrFrTyp n AnimateColor_SystemOverdubOrSubtitle_Subtitle = Just (n, str2attr "subtitle") -instance XmlAttrType AnimateColor_SystemAudioDesc where - fromAttrToTyp n (n',v) - | n==n' = translate (attr2str v) - | otherwise = Nothing - where translate "on" = Just AnimateColor_SystemAudioDesc_On - translate "off" = Just AnimateColor_SystemAudioDesc_Off - translate _ = Nothing - toAttrFrTyp n AnimateColor_SystemAudioDesc_On = Just (n, str2attr "on") - toAttrFrTyp n AnimateColor_SystemAudioDesc_Off = Just (n, str2attr "off") -instance XmlAttrType AnimateColor_System_captions where - fromAttrToTyp n (n',v) - | n==n' = translate (attr2str v) - | otherwise = Nothing - where translate "on" = Just AnimateColor_System_captions_On - translate "off" = Just AnimateColor_System_captions_Off - translate _ = Nothing - toAttrFrTyp n AnimateColor_System_captions_On = Just (n, str2attr "on") - toAttrFrTyp n AnimateColor_System_captions_Off = Just (n, str2attr "off") -instance XmlAttrType AnimateColor_System_overdub_or_caption where - fromAttrToTyp n (n',v) - | n==n' = translate (attr2str v) - | otherwise = Nothing - where translate "overdub" = Just AnimateColor_System_overdub_or_caption_Overdub - translate "caption" = Just AnimateColor_System_overdub_or_caption_Caption - translate _ = Nothing - toAttrFrTyp n AnimateColor_System_overdub_or_caption_Overdub = Just (n, str2attr "overdub") - toAttrFrTyp n AnimateColor_System_overdub_or_caption_Caption = Just (n, str2attr "caption") -instance XmlAttrType AnimateColor_CalcMode where - fromAttrToTyp n (n',v) - | n==n' = translate (attr2str v) - | otherwise = Nothing - where translate "discrete" = Just AnimateColor_CalcMode_Discrete - translate "linear" = Just AnimateColor_CalcMode_Linear - translate "paced" = Just AnimateColor_CalcMode_Paced - translate _ = Nothing - toAttrFrTyp n AnimateColor_CalcMode_Discrete = Just (n, str2attr "discrete") - toAttrFrTyp n AnimateColor_CalcMode_Linear = Just (n, str2attr "linear") - toAttrFrTyp n AnimateColor_CalcMode_Paced = Just (n, str2attr "paced") -instance XmlAttrType AnimateColor_Additive where - fromAttrToTyp n (n',v) - | n==n' = translate (attr2str v) - | otherwise = Nothing - where translate "replace" = Just AnimateColor_Additive_Replace - translate "sum" = Just AnimateColor_Additive_Sum - translate _ = Nothing - toAttrFrTyp n AnimateColor_Additive_Replace = Just (n, str2attr "replace") - toAttrFrTyp n AnimateColor_Additive_Sum = Just (n, str2attr "sum") -instance XmlAttrType AnimateColor_Accumulate where - fromAttrToTyp n (n',v) - | n==n' = translate (attr2str v) - | otherwise = Nothing - where translate "none" = Just AnimateColor_Accumulate_None - translate "sum" = Just AnimateColor_Accumulate_Sum - translate _ = Nothing - toAttrFrTyp n AnimateColor_Accumulate_None = Just (n, str2attr "none") - toAttrFrTyp n AnimateColor_Accumulate_Sum = Just (n, str2attr "sum") -instance XmlContent Switch where - fromElem (CElem (Elem "switch" as []):rest) = - (Just (fromAttrs as), rest) - fromElem (CMisc _:rest) = fromElem rest - fromElem rest = (Nothing, rest) - toElem as = - [CElem (Elem "switch" (toAttrs as) [])] -instance XmlAttributes Switch where - fromAttrs as = - Switch - { switchId = possibleA fromAttrToStr "id" as - , switchClass = possibleA fromAttrToStr "class" as - , switchTitle = possibleA fromAttrToStr "title" as - , switchXml'lang = possibleA fromAttrToStr "xml:lang" as - } - toAttrs v = catMaybes - [ maybeToAttr toAttrFrStr "id" (switchId v) - , maybeToAttr toAttrFrStr "class" (switchClass v) - , maybeToAttr toAttrFrStr "title" (switchTitle v) - , maybeToAttr toAttrFrStr "xml:lang" (switchXml'lang v) - ] -instance XmlContent Meta where - fromElem (CElem (Elem "meta" as []):rest) = - (Just (fromAttrs as), rest) - fromElem (CMisc _:rest) = fromElem rest - fromElem rest = (Nothing, rest) - toElem as = - [CElem (Elem "meta" (toAttrs as) [])] -instance XmlAttributes Meta where - fromAttrs as = - Meta - { metaContent = possibleA fromAttrToStr "content" as - , metaName = definiteA fromAttrToStr "meta" "name" as - } - toAttrs v = catMaybes - [ maybeToAttr toAttrFrStr "content" (metaContent v) - , toAttrFrStr "name" (metaName v) - ] -instance XmlContent Metadata where - fromElem (CElem (Elem "metadata" as []):rest) = - (Just (fromAttrs as), rest) - fromElem (CMisc _:rest) = fromElem rest - fromElem rest = (Nothing, rest) - toElem as = - [CElem (Elem "metadata" (toAttrs as) [])] -instance XmlAttributes Metadata where - fromAttrs as = - Metadata - { metadataId = possibleA fromAttrToStr "id" as - , metadataClass = possibleA fromAttrToStr "class" as - , metadataTitle = possibleA fromAttrToStr "title" as - , metadataXml'lang = possibleA fromAttrToStr "xml:lang" as - } - toAttrs v = catMaybes - [ maybeToAttr toAttrFrStr "id" (metadataId v) - , maybeToAttr toAttrFrStr "class" (metadataClass v) - , maybeToAttr toAttrFrStr "title" (metadataTitle v) - , maybeToAttr toAttrFrStr "xml:lang" (metadataXml'lang v) - ] -instance XmlContent Layout where - fromElem (CElem (Elem "layout" as []):rest) = - (Just (fromAttrs as), rest) - fromElem (CMisc _:rest) = fromElem rest - fromElem rest = (Nothing, rest) - toElem as = - [CElem (Elem "layout" (toAttrs as) [])] -instance XmlAttributes Layout where - fromAttrs as = - Layout - { layoutId = possibleA fromAttrToStr "id" as - , layoutClass = possibleA fromAttrToStr "class" as - , layoutTitle = possibleA fromAttrToStr "title" as - , layoutXml'lang = possibleA fromAttrToStr "xml:lang" as - , layoutType = defaultA fromAttrToStr "text/smil-basic-layout" "type" as - } - toAttrs v = catMaybes - [ maybeToAttr toAttrFrStr "id" (layoutId v) - , maybeToAttr toAttrFrStr "class" (layoutClass v) - , maybeToAttr toAttrFrStr "title" (layoutTitle v) - , maybeToAttr toAttrFrStr "xml:lang" (layoutXml'lang v) - , defaultToAttr toAttrFrStr "type" (layoutType v) - ] -instance XmlContent Region where - fromElem (CElem (Elem "region" as []):rest) = - (Just (fromAttrs as), rest) - fromElem (CMisc _:rest) = fromElem rest - fromElem rest = (Nothing, rest) - toElem as = - [CElem (Elem "region" (toAttrs as) [])] -instance XmlAttributes Region where - fromAttrs as = - Region - { regionId = possibleA fromAttrToStr "id" as - , regionClass = possibleA fromAttrToStr "class" as - , regionTitle = possibleA fromAttrToStr "title" as - , regionXml'lang = possibleA fromAttrToStr "xml:lang" as - , regionHeight = defaultA fromAttrToStr "auto" "height" as - , regionWidth = defaultA fromAttrToStr "auto" "width" as - , regionClose = defaultA fromAttrToTyp Region_Close_Never "close" as - , regionOpen = defaultA fromAttrToTyp Region_Open_Always "open" as - , regionBackgroundColor = possibleA fromAttrToStr "backgroundColor" as - , regionBackground_color = possibleA fromAttrToStr "background-color" as - , regionBottom = defaultA fromAttrToStr "auto" "bottom" as - , regionLeft = defaultA fromAttrToStr "auto" "left" as - , regionRight = defaultA fromAttrToStr "auto" "right" as - , regionTop = defaultA fromAttrToStr "auto" "top" as - , regionZ_index = possibleA fromAttrToStr "z-index" as - , regionShowBackground = defaultA fromAttrToTyp Region_ShowBackground_Always "showBackground" as - , regionFit = defaultA fromAttrToTyp Region_Fit_Hidden "fit" as - } - toAttrs v = catMaybes - [ maybeToAttr toAttrFrStr "id" (regionId v) - , maybeToAttr toAttrFrStr "class" (regionClass v) - , maybeToAttr toAttrFrStr "title" (regionTitle v) - , maybeToAttr toAttrFrStr "xml:lang" (regionXml'lang v) - , defaultToAttr toAttrFrStr "height" (regionHeight v) - , defaultToAttr toAttrFrStr "width" (regionWidth v) - , defaultToAttr toAttrFrTyp "close" (regionClose v) - , defaultToAttr toAttrFrTyp "open" (regionOpen v) - , maybeToAttr toAttrFrStr "backgroundColor" (regionBackgroundColor v) - , maybeToAttr toAttrFrStr "background-color" (regionBackground_color v) - , defaultToAttr toAttrFrStr "bottom" (regionBottom v) - , defaultToAttr toAttrFrStr "left" (regionLeft v) - , defaultToAttr toAttrFrStr "right" (regionRight v) - , defaultToAttr toAttrFrStr "top" (regionTop v) - , maybeToAttr toAttrFrStr "z-index" (regionZ_index v) - , defaultToAttr toAttrFrTyp "showBackground" (regionShowBackground v) - , defaultToAttr toAttrFrTyp "fit" (regionFit v) - ] -instance XmlAttrType Region_Close where - fromAttrToTyp n (n',v) - | n==n' = translate (attr2str v) - | otherwise = Nothing - where translate "never" = Just Region_Close_Never - translate "whenNotActive" = Just Region_Close_WhenNotActive - translate _ = Nothing - toAttrFrTyp n Region_Close_Never = Just (n, str2attr "never") - toAttrFrTyp n Region_Close_WhenNotActive = Just (n, str2attr "whenNotActive") -instance XmlAttrType Region_Open where - fromAttrToTyp n (n',v) - | n==n' = translate (attr2str v) - | otherwise = Nothing - where translate "always" = Just Region_Open_Always - translate "whenActive" = Just Region_Open_WhenActive - translate _ = Nothing - toAttrFrTyp n Region_Open_Always = Just (n, str2attr "always") - toAttrFrTyp n Region_Open_WhenActive = Just (n, str2attr "whenActive") -instance XmlAttrType Region_ShowBackground where - fromAttrToTyp n (n',v) - | n==n' = translate (attr2str v) - | otherwise = Nothing - where translate "always" = Just Region_ShowBackground_Always - translate "whenActive" = Just Region_ShowBackground_WhenActive - translate _ = Nothing - toAttrFrTyp n Region_ShowBackground_Always = Just (n, str2attr "always") - toAttrFrTyp n Region_ShowBackground_WhenActive = Just (n, str2attr "whenActive") -instance XmlAttrType Region_Fit where - fromAttrToTyp n (n',v) - | n==n' = translate (attr2str v) - | otherwise = Nothing - where translate "hidden" = Just Region_Fit_Hidden - translate "fill" = Just Region_Fit_Fill - translate "meet" = Just Region_Fit_Meet - translate "scroll" = Just Region_Fit_Scroll - translate "slice" = Just Region_Fit_Slice - translate _ = Nothing - toAttrFrTyp n Region_Fit_Hidden = Just (n, str2attr "hidden") - toAttrFrTyp n Region_Fit_Fill = Just (n, str2attr "fill") - toAttrFrTyp n Region_Fit_Meet = Just (n, str2attr "meet") - toAttrFrTyp n Region_Fit_Scroll = Just (n, str2attr "scroll") - toAttrFrTyp n Region_Fit_Slice = Just (n, str2attr "slice") -instance XmlContent Root_layout where - fromElem (CElem (Elem "root-layout" as []):rest) = - (Just (fromAttrs as), rest) - fromElem (CMisc _:rest) = fromElem rest - fromElem rest = (Nothing, rest) - toElem as = - [CElem (Elem "root-layout" (toAttrs as) [])] -instance XmlAttributes Root_layout where - fromAttrs as = - Root_layout - { root_layoutId = possibleA fromAttrToStr "id" as - , root_layoutClass = possibleA fromAttrToStr "class" as - , root_layoutTitle = possibleA fromAttrToStr "title" as - , root_layoutXml'lang = possibleA fromAttrToStr "xml:lang" as - , root_layoutHeight = defaultA fromAttrToStr "auto" "height" as - , root_layoutWidth = defaultA fromAttrToStr "auto" "width" as - , root_layoutClose = defaultA fromAttrToTyp Root_layout_Close_Never "close" as - , root_layoutOpen = defaultA fromAttrToTyp Root_layout_Open_Always "open" as - , root_layoutBackgroundColor = possibleA fromAttrToStr "backgroundColor" as - , root_layoutBackground_color = possibleA fromAttrToStr "background-color" as - } - toAttrs v = catMaybes - [ maybeToAttr toAttrFrStr "id" (root_layoutId v) - , maybeToAttr toAttrFrStr "class" (root_layoutClass v) - , maybeToAttr toAttrFrStr "title" (root_layoutTitle v) - , maybeToAttr toAttrFrStr "xml:lang" (root_layoutXml'lang v) - , defaultToAttr toAttrFrStr "height" (root_layoutHeight v) - , defaultToAttr toAttrFrStr "width" (root_layoutWidth v) - , defaultToAttr toAttrFrTyp "close" (root_layoutClose v) - , defaultToAttr toAttrFrTyp "open" (root_layoutOpen v) - , maybeToAttr toAttrFrStr "backgroundColor" (root_layoutBackgroundColor v) - , maybeToAttr toAttrFrStr "background-color" (root_layoutBackground_color v) - ] -instance XmlAttrType Root_layout_Close where - fromAttrToTyp n (n',v) - | n==n' = translate (attr2str v) - | otherwise = Nothing - where translate "never" = Just Root_layout_Close_Never - translate "whenNotActive" = Just Root_layout_Close_WhenNotActive - translate _ = Nothing - toAttrFrTyp n Root_layout_Close_Never = Just (n, str2attr "never") - toAttrFrTyp n Root_layout_Close_WhenNotActive = Just (n, str2attr "whenNotActive") -instance XmlAttrType Root_layout_Open where - fromAttrToTyp n (n',v) - | n==n' = translate (attr2str v) - | otherwise = Nothing - where translate "always" = Just Root_layout_Open_Always - translate "whenActive" = Just Root_layout_Open_WhenActive - translate _ = Nothing - toAttrFrTyp n Root_layout_Open_Always = Just (n, str2attr "always") - toAttrFrTyp n Root_layout_Open_WhenActive = Just (n, str2attr "whenActive") -instance XmlContent Ref where - fromElem (CElem (Elem "ref" as []):rest) = - (Just (fromAttrs as), rest) - fromElem (CMisc _:rest) = fromElem rest - fromElem rest = (Nothing, rest) - toElem as = - [CElem (Elem "ref" (toAttrs as) [])] -instance XmlAttributes Ref where - fromAttrs as = - Ref - { refId = possibleA fromAttrToStr "id" as - , refClass = possibleA fromAttrToStr "class" as - , refTitle = possibleA fromAttrToStr "title" as - , refXml'lang = possibleA fromAttrToStr "xml:lang" as - } - toAttrs v = catMaybes - [ maybeToAttr toAttrFrStr "id" (refId v) - , maybeToAttr toAttrFrStr "class" (refClass v) - , maybeToAttr toAttrFrStr "title" (refTitle v) - , maybeToAttr toAttrFrStr "xml:lang" (refXml'lang v) - ] -instance XmlContent Audio where - fromElem (CElem (Elem "audio" as []):rest) = - (Just (fromAttrs as), rest) - fromElem (CMisc _:rest) = fromElem rest - fromElem rest = (Nothing, rest) - toElem as = - [CElem (Elem "audio" (toAttrs as) [])] -instance XmlAttributes Audio where - fromAttrs as = - Audio - { audioId = possibleA fromAttrToStr "id" as - , audioClass = possibleA fromAttrToStr "class" as - , audioTitle = possibleA fromAttrToStr "title" as - , audioXml'lang = possibleA fromAttrToStr "xml:lang" as - } - toAttrs v = catMaybes - [ maybeToAttr toAttrFrStr "id" (audioId v) - , maybeToAttr toAttrFrStr "class" (audioClass v) - , maybeToAttr toAttrFrStr "title" (audioTitle v) - , maybeToAttr toAttrFrStr "xml:lang" (audioXml'lang v) - ] -instance XmlContent Img where - fromElem (CElem (Elem "img" as []):rest) = - (Just (fromAttrs as), rest) - fromElem (CMisc _:rest) = fromElem rest - fromElem rest = (Nothing, rest) - toElem as = - [CElem (Elem "img" (toAttrs as) [])] -instance XmlAttributes Img where - fromAttrs as = - Img - { imgId = possibleA fromAttrToStr "id" as - , imgClass = possibleA fromAttrToStr "class" as - , imgTitle = possibleA fromAttrToStr "title" as - , imgXml'lang = possibleA fromAttrToStr "xml:lang" as - } - toAttrs v = catMaybes - [ maybeToAttr toAttrFrStr "id" (imgId v) - , maybeToAttr toAttrFrStr "class" (imgClass v) - , maybeToAttr toAttrFrStr "title" (imgTitle v) - , maybeToAttr toAttrFrStr "xml:lang" (imgXml'lang v) - ] -instance XmlContent Video where - fromElem (CElem (Elem "video" as []):rest) = - (Just (fromAttrs as), rest) - fromElem (CMisc _:rest) = fromElem rest - fromElem rest = (Nothing, rest) - toElem as = - [CElem (Elem "video" (toAttrs as) [])] -instance XmlAttributes Video where - fromAttrs as = - Video - { videoId = possibleA fromAttrToStr "id" as - , videoClass = possibleA fromAttrToStr "class" as - , videoTitle = possibleA fromAttrToStr "title" as - , videoXml'lang = possibleA fromAttrToStr "xml:lang" as - } - toAttrs v = catMaybes - [ maybeToAttr toAttrFrStr "id" (videoId v) - , maybeToAttr toAttrFrStr "class" (videoClass v) - , maybeToAttr toAttrFrStr "title" (videoTitle v) - , maybeToAttr toAttrFrStr "xml:lang" (videoXml'lang v) - ] -instance XmlContent Text where - fromElem (CElem (Elem "text" as []):rest) = - (Just (fromAttrs as), rest) - fromElem (CMisc _:rest) = fromElem rest - fromElem rest = (Nothing, rest) - toElem as = - [CElem (Elem "text" (toAttrs as) [])] -instance XmlAttributes Text where - fromAttrs as = - Text - { textId = possibleA fromAttrToStr "id" as - , textClass = possibleA fromAttrToStr "class" as - , textTitle = possibleA fromAttrToStr "title" as - , textXml'lang = possibleA fromAttrToStr "xml:lang" as - } - toAttrs v = catMaybes - [ maybeToAttr toAttrFrStr "id" (textId v) - , maybeToAttr toAttrFrStr "class" (textClass v) - , maybeToAttr toAttrFrStr "title" (textTitle v) - , maybeToAttr toAttrFrStr "xml:lang" (textXml'lang v) - ] -instance XmlContent Textstream where - fromElem (CElem (Elem "textstream" as []):rest) = - (Just (fromAttrs as), rest) - fromElem (CMisc _:rest) = fromElem rest - fromElem rest = (Nothing, rest) - toElem as = - [CElem (Elem "textstream" (toAttrs as) [])] -instance XmlAttributes Textstream where - fromAttrs as = - Textstream - { textstreamId = possibleA fromAttrToStr "id" as - , textstreamClass = possibleA fromAttrToStr "class" as - , textstreamTitle = possibleA fromAttrToStr "title" as - , textstreamXml'lang = possibleA fromAttrToStr "xml:lang" as - } - toAttrs v = catMaybes - [ maybeToAttr toAttrFrStr "id" (textstreamId v) - , maybeToAttr toAttrFrStr "class" (textstreamClass v) - , maybeToAttr toAttrFrStr "title" (textstreamTitle v) - , maybeToAttr toAttrFrStr "xml:lang" (textstreamXml'lang v) - ] -instance XmlContent Animation where - fromElem (CElem (Elem "animation" as []):rest) = - (Just (fromAttrs as), rest) - fromElem (CMisc _:rest) = fromElem rest - fromElem rest = (Nothing, rest) - toElem as = - [CElem (Elem "animation" (toAttrs as) [])] -instance XmlAttributes Animation where - fromAttrs as = - Animation - { animationId = possibleA fromAttrToStr "id" as - , animationClass = possibleA fromAttrToStr "class" as - , animationTitle = possibleA fromAttrToStr "title" as - , animationXml'lang = possibleA fromAttrToStr "xml:lang" as - } - toAttrs v = catMaybes - [ maybeToAttr toAttrFrStr "id" (animationId v) - , maybeToAttr toAttrFrStr "class" (animationClass v) - , maybeToAttr toAttrFrStr "title" (animationTitle v) - , maybeToAttr toAttrFrStr "xml:lang" (animationXml'lang v) - ] -instance XmlContent Transition where - fromElem (CElem (Elem "transition" as []):rest) = - (Just (fromAttrs as), rest) - fromElem (CMisc _:rest) = fromElem rest - fromElem rest = (Nothing, rest) - toElem as = - [CElem (Elem "transition" (toAttrs as) [])] -instance XmlAttributes Transition where - fromAttrs as = - Transition - { transitionId = possibleA fromAttrToStr "id" as - , transitionClass = possibleA fromAttrToStr "class" as - , transitionTitle = possibleA fromAttrToStr "title" as - , transitionXml'lang = possibleA fromAttrToStr "xml:lang" as - , transitionType = possibleA fromAttrToTyp "type" as - , transitionSubtype = possibleA fromAttrToTyp "subtype" as - , transitionHorzRepeat = defaultA fromAttrToStr "0" "horzRepeat" as - , transitionVertRepeat = defaultA fromAttrToStr "0" "vertRepeat" as - , transitionBorderWidth = defaultA fromAttrToStr "0" "borderWidth" as - , transitionBorderColor = defaultA fromAttrToStr "black" "borderColor" as - , transitionFadeColor = defaultA fromAttrToStr "black" "fadeColor" as - , transitionCoordinated = defaultA fromAttrToTyp Transition_Coordinated_False "coordinated" as - , transitionClibBoundary = defaultA fromAttrToTyp Transition_ClibBoundary_Children "clibBoundary" as - , transitionDur = possibleA fromAttrToStr "dur" as - , transitionStartProgress = defaultA fromAttrToStr "0.0" "startProgress" as - , transitionEndProgress = defaultA fromAttrToStr "1.0" "endProgress" as - , transitionDirection = defaultA fromAttrToTyp Transition_Direction_Forward "direction" as - } - toAttrs v = catMaybes - [ maybeToAttr toAttrFrStr "id" (transitionId v) - , maybeToAttr toAttrFrStr "class" (transitionClass v) - , maybeToAttr toAttrFrStr "title" (transitionTitle v) - , maybeToAttr toAttrFrStr "xml:lang" (transitionXml'lang v) - , maybeToAttr toAttrFrTyp "type" (transitionType v) - , maybeToAttr toAttrFrTyp "subtype" (transitionSubtype v) - , defaultToAttr toAttrFrStr "horzRepeat" (transitionHorzRepeat v) - , defaultToAttr toAttrFrStr "vertRepeat" (transitionVertRepeat v) - , defaultToAttr toAttrFrStr "borderWidth" (transitionBorderWidth v) - , defaultToAttr toAttrFrStr "borderColor" (transitionBorderColor v) - , defaultToAttr toAttrFrStr "fadeColor" (transitionFadeColor v) - , defaultToAttr toAttrFrTyp "coordinated" (transitionCoordinated v) - , defaultToAttr toAttrFrTyp "clibBoundary" (transitionClibBoundary v) - , maybeToAttr toAttrFrStr "dur" (transitionDur v) - , defaultToAttr toAttrFrStr "startProgress" (transitionStartProgress v) - , defaultToAttr toAttrFrStr "endProgress" (transitionEndProgress v) - , defaultToAttr toAttrFrTyp "direction" (transitionDirection v) - ] -instance XmlAttrType Transition_Type where - fromAttrToTyp n (n',v) - | n==n' = translate (attr2str v) - | otherwise = Nothing - where translate "barWipe" = Just Transition_Type_BarWipe - translate "boxWipe" = Just Transition_Type_BoxWipe - translate "fourBoxWipe" = Just Transition_Type_FourBoxWipe - translate "barnDoorWipe" = Just Transition_Type_BarnDoorWipe - translate "diagonalWipe" = Just Transition_Type_DiagonalWipe - translate "bowTieWipe" = Just Transition_Type_BowTieWipe - translate "miscDiagonalWipe" = Just Transition_Type_MiscDiagonalWipe - translate "veeWipe" = Just Transition_Type_VeeWipe - translate "barnVeeWipe" = Just Transition_Type_BarnVeeWipe - translate "zigZagWipe" = Just Transition_Type_ZigZagWipe - translate "barnZigZagWipe" = Just Transition_Type_BarnZigZagWipe - translate "miscShapeWipe" = Just Transition_Type_MiscShapeWipe - translate "triangleWipe" = Just Transition_Type_TriangleWipe - translate "arrowHeadWipe" = Just Transition_Type_ArrowHeadWipe - translate "pentagonWipe" = Just Transition_Type_PentagonWipe - translate "hexagonWipe" = Just Transition_Type_HexagonWipe - translate "ellipseWipe" = Just Transition_Type_EllipseWipe - translate "eyeWipe" = Just Transition_Type_EyeWipe - translate "roundRectWipe" = Just Transition_Type_RoundRectWipe - translate "starWipe" = Just Transition_Type_StarWipe - translate "clockWipe" = Just Transition_Type_ClockWipe - translate "pinWheelWipe" = Just Transition_Type_PinWheelWipe - translate "singleSweepWipe" = Just Transition_Type_SingleSweepWipe - translate "fanWipe" = Just Transition_Type_FanWipe - translate "doubleFanWipe" = Just Transition_Type_DoubleFanWipe - translate "doubleSweepWipe" = Just Transition_Type_DoubleSweepWipe - translate "saloonDoorWipe" = Just Transition_Type_SaloonDoorWipe - translate "windshieldWipe" = Just Transition_Type_WindshieldWipe - translate "snakeWipe" = Just Transition_Type_SnakeWipe - translate "spiralWipe" = Just Transition_Type_SpiralWipe - translate "parallelSnakesWipe" = Just Transition_Type_ParallelSnakesWipe - translate "boxSnakesWipe" = Just Transition_Type_BoxSnakesWipe - translate "waterfallWipe" = Just Transition_Type_WaterfallWipe - translate "pushWipe" = Just Transition_Type_PushWipe - translate "slideWipe" = Just Transition_Type_SlideWipe - translate "fade" = Just Transition_Type_Fade - translate _ = Nothing - toAttrFrTyp n Transition_Type_BarWipe = Just (n, str2attr "barWipe") - toAttrFrTyp n Transition_Type_BoxWipe = Just (n, str2attr "boxWipe") - toAttrFrTyp n Transition_Type_FourBoxWipe = Just (n, str2attr "fourBoxWipe") - toAttrFrTyp n Transition_Type_BarnDoorWipe = Just (n, str2attr "barnDoorWipe") - toAttrFrTyp n Transition_Type_DiagonalWipe = Just (n, str2attr "diagonalWipe") - toAttrFrTyp n Transition_Type_BowTieWipe = Just (n, str2attr "bowTieWipe") - toAttrFrTyp n Transition_Type_MiscDiagonalWipe = Just (n, str2attr "miscDiagonalWipe") - toAttrFrTyp n Transition_Type_VeeWipe = Just (n, str2attr "veeWipe") - toAttrFrTyp n Transition_Type_BarnVeeWipe = Just (n, str2attr "barnVeeWipe") - toAttrFrTyp n Transition_Type_ZigZagWipe = Just (n, str2attr "zigZagWipe") - toAttrFrTyp n Transition_Type_BarnZigZagWipe = Just (n, str2attr "barnZigZagWipe") - toAttrFrTyp n Transition_Type_MiscShapeWipe = Just (n, str2attr "miscShapeWipe") - toAttrFrTyp n Transition_Type_TriangleWipe = Just (n, str2attr "triangleWipe") - toAttrFrTyp n Transition_Type_ArrowHeadWipe = Just (n, str2attr "arrowHeadWipe") - toAttrFrTyp n Transition_Type_PentagonWipe = Just (n, str2attr "pentagonWipe") - toAttrFrTyp n Transition_Type_HexagonWipe = Just (n, str2attr "hexagonWipe") - toAttrFrTyp n Transition_Type_EllipseWipe = Just (n, str2attr "ellipseWipe") - toAttrFrTyp n Transition_Type_EyeWipe = Just (n, str2attr "eyeWipe") - toAttrFrTyp n Transition_Type_RoundRectWipe = Just (n, str2attr "roundRectWipe") - toAttrFrTyp n Transition_Type_StarWipe = Just (n, str2attr "starWipe") - toAttrFrTyp n Transition_Type_ClockWipe = Just (n, str2attr "clockWipe") - toAttrFrTyp n Transition_Type_PinWheelWipe = Just (n, str2attr "pinWheelWipe") - toAttrFrTyp n Transition_Type_SingleSweepWipe = Just (n, str2attr "singleSweepWipe") - toAttrFrTyp n Transition_Type_FanWipe = Just (n, str2attr "fanWipe") - toAttrFrTyp n Transition_Type_DoubleFanWipe = Just (n, str2attr "doubleFanWipe") - toAttrFrTyp n Transition_Type_DoubleSweepWipe = Just (n, str2attr "doubleSweepWipe") - toAttrFrTyp n Transition_Type_SaloonDoorWipe = Just (n, str2attr "saloonDoorWipe") - toAttrFrTyp n Transition_Type_WindshieldWipe = Just (n, str2attr "windshieldWipe") - toAttrFrTyp n Transition_Type_SnakeWipe = Just (n, str2attr "snakeWipe") - toAttrFrTyp n Transition_Type_SpiralWipe = Just (n, str2attr "spiralWipe") - toAttrFrTyp n Transition_Type_ParallelSnakesWipe = Just (n, str2attr "parallelSnakesWipe") - toAttrFrTyp n Transition_Type_BoxSnakesWipe = Just (n, str2attr "boxSnakesWipe") - toAttrFrTyp n Transition_Type_WaterfallWipe = Just (n, str2attr "waterfallWipe") - toAttrFrTyp n Transition_Type_PushWipe = Just (n, str2attr "pushWipe") - toAttrFrTyp n Transition_Type_SlideWipe = Just (n, str2attr "slideWipe") - toAttrFrTyp n Transition_Type_Fade = Just (n, str2attr "fade") -instance XmlAttrType Transition_Subtype where - fromAttrToTyp n (n',v) - | n==n' = translate (attr2str v) - | otherwise = Nothing - where translate "bottom" = Just Transition_Subtype_Bottom - translate "bottomCenter" = Just Transition_Subtype_BottomCenter - translate "bottomLeft" = Just Transition_Subtype_BottomLeft - translate "bottomLeftClockwise" = Just Transition_Subtype_BottomLeftClockwise - translate "bottomLeftCounterClockwise" = Just Transition_Subtype_BottomLeftCounterClockwise - translate "bottomLeftDiagonal" = Just Transition_Subtype_BottomLeftDiagonal - translate "bottomRight" = Just Transition_Subtype_BottomRight - translate "bottomRightClockwise" = Just Transition_Subtype_BottomRightClockwise - translate "bottomRightCounterClockwise" = Just Transition_Subtype_BottomRightCounterClockwise - translate "bottomRightDiagonal" = Just Transition_Subtype_BottomRightDiagonal - translate "centerRight" = Just Transition_Subtype_CenterRight - translate "centerTop" = Just Transition_Subtype_CenterTop - translate "circle" = Just Transition_Subtype_Circle - translate "clockwiseBottom" = Just Transition_Subtype_ClockwiseBottom - translate "clockwiseBottomRight" = Just Transition_Subtype_ClockwiseBottomRight - translate "clockwiseLeft" = Just Transition_Subtype_ClockwiseLeft - translate "clockwiseNine" = Just Transition_Subtype_ClockwiseNine - translate "clockwiseRight" = Just Transition_Subtype_ClockwiseRight - translate "clockwiseSix" = Just Transition_Subtype_ClockwiseSix - translate "clockwiseThree" = Just Transition_Subtype_ClockwiseThree - translate "clockwiseTop" = Just Transition_Subtype_ClockwiseTop - translate "clockwiseTopLeft" = Just Transition_Subtype_ClockwiseTopLeft - translate "clockwiseTwelve" = Just Transition_Subtype_ClockwiseTwelve - translate "cornersIn" = Just Transition_Subtype_CornersIn - translate "cornersOut" = Just Transition_Subtype_CornersOut - translate "counterClockwiseBottomLeft" = Just Transition_Subtype_CounterClockwiseBottomLeft - translate "counterClockwiseTopRight" = Just Transition_Subtype_CounterClockwiseTopRight - translate "crossfade" = Just Transition_Subtype_Crossfade - translate "diagonalBottomLeft" = Just Transition_Subtype_DiagonalBottomLeft - translate "diagonalBottomLeftOpposite" = Just Transition_Subtype_DiagonalBottomLeftOpposite - translate "diagonalTopLeft" = Just Transition_Subtype_DiagonalTopLeft - translate "diagonalTopLeftOpposite" = Just Transition_Subtype_DiagonalTopLeftOpposite - translate "diamond" = Just Transition_Subtype_Diamond - translate "doubleBarnDoor" = Just Transition_Subtype_DoubleBarnDoor - translate "doubleDiamond" = Just Transition_Subtype_DoubleDiamond - translate "down" = Just Transition_Subtype_Down - translate "fadeFromColor" = Just Transition_Subtype_FadeFromColor - translate "fadeToColor" = Just Transition_Subtype_FadeToColor - translate "fanInHorizontal" = Just Transition_Subtype_FanInHorizontal - translate "fanInVertical" = Just Transition_Subtype_FanInVertical - translate "fanOutHorizontal" = Just Transition_Subtype_FanOutHorizontal - translate "fanOutVertical" = Just Transition_Subtype_FanOutVertical - translate "fivePoint" = Just Transition_Subtype_FivePoint - translate "fourBlade" = Just Transition_Subtype_FourBlade - translate "fourBoxHorizontal" = Just Transition_Subtype_FourBoxHorizontal - translate "fourBoxVertical" = Just Transition_Subtype_FourBoxVertical - translate "fourPoint" = Just Transition_Subtype_FourPoint - translate "fromBottom" = Just Transition_Subtype_FromBottom - translate "fromLeft" = Just Transition_Subtype_FromLeft - translate "fromRight" = Just Transition_Subtype_FromRight - translate "fromTop" = Just Transition_Subtype_FromTop - translate "heart" = Just Transition_Subtype_Heart - translate "horizontal" = Just Transition_Subtype_Horizontal - translate "horizontalLeft" = Just Transition_Subtype_HorizontalLeft - translate "horizontalLeftSame" = Just Transition_Subtype_HorizontalLeftSame - translate "horizontalRight" = Just Transition_Subtype_HorizontalRight - translate "horizontalRightSame" = Just Transition_Subtype_HorizontalRightSame - translate "horizontalTopLeftOpposite" = Just Transition_Subtype_HorizontalTopLeftOpposite - translate "horizontalTopRightOpposite" = Just Transition_Subtype_HorizontalTopRightOpposite - translate "keyhole" = Just Transition_Subtype_Keyhole - translate "left" = Just Transition_Subtype_Left - translate "leftCenter" = Just Transition_Subtype_LeftCenter - translate "leftToRight" = Just Transition_Subtype_LeftToRight - translate "oppositeHorizontal" = Just Transition_Subtype_OppositeHorizontal - translate "oppositeVertical" = Just Transition_Subtype_OppositeVertical - translate "parallelDiagonal" = Just Transition_Subtype_ParallelDiagonal - translate "parallelDiagonalBottomLeft" = Just Transition_Subtype_ParallelDiagonalBottomLeft - translate "parallelDiagonalTopLeft" = Just Transition_Subtype_ParallelDiagonalTopLeft - translate "parallelVertical" = Just Transition_Subtype_ParallelVertical - translate "rectangle" = Just Transition_Subtype_Rectangle - translate "right" = Just Transition_Subtype_Right - translate "rightCenter" = Just Transition_Subtype_RightCenter - translate "sixPoint" = Just Transition_Subtype_SixPoint - translate "top" = Just Transition_Subtype_Top - translate "topCenter" = Just Transition_Subtype_TopCenter - translate "topLeft" = Just Transition_Subtype_TopLeft - translate "topLeftClockwise" = Just Transition_Subtype_TopLeftClockwise - translate "topLeftCounterClockwise" = Just Transition_Subtype_TopLeftCounterClockwise - translate "topLeftDiagonal" = Just Transition_Subtype_TopLeftDiagonal - translate "topLeftHorizontal" = Just Transition_Subtype_TopLeftHorizontal - translate "topLeftVertical" = Just Transition_Subtype_TopLeftVertical - translate "topRight" = Just Transition_Subtype_TopRight - translate "topRightClockwise" = Just Transition_Subtype_TopRightClockwise - translate "topRightCounterClockwise" = Just Transition_Subtype_TopRightCounterClockwise - translate "topRightDiagonal" = Just Transition_Subtype_TopRightDiagonal - translate "topToBottom" = Just Transition_Subtype_TopToBottom - translate "twoBladeHorizontal" = Just Transition_Subtype_TwoBladeHorizontal - translate "twoBladeVertical" = Just Transition_Subtype_TwoBladeVertical - translate "twoBoxBottom" = Just Transition_Subtype_TwoBoxBottom - translate "twoBoxLeft" = Just Transition_Subtype_TwoBoxLeft - translate "twoBoxRight" = Just Transition_Subtype_TwoBoxRight - translate "twoBoxTop" = Just Transition_Subtype_TwoBoxTop - translate "up" = Just Transition_Subtype_Up - translate "vertical" = Just Transition_Subtype_Vertical - translate "verticalBottomLeftOpposite" = Just Transition_Subtype_VerticalBottomLeftOpposite - translate "verticalBottomSame" = Just Transition_Subtype_VerticalBottomSame - translate "verticalLeft" = Just Transition_Subtype_VerticalLeft - translate "verticalRight" = Just Transition_Subtype_VerticalRight - translate "verticalTopLeftOpposite" = Just Transition_Subtype_VerticalTopLeftOpposite - translate "verticalTopSame" = Just Transition_Subtype_VerticalTopSame - translate _ = Nothing - toAttrFrTyp n Transition_Subtype_Bottom = Just (n, str2attr "bottom") - toAttrFrTyp n Transition_Subtype_BottomCenter = Just (n, str2attr "bottomCenter") - toAttrFrTyp n Transition_Subtype_BottomLeft = Just (n, str2attr "bottomLeft") - toAttrFrTyp n Transition_Subtype_BottomLeftClockwise = Just (n, str2attr "bottomLeftClockwise") - toAttrFrTyp n Transition_Subtype_BottomLeftCounterClockwise = Just (n, str2attr "bottomLeftCounterClockwise") - toAttrFrTyp n Transition_Subtype_BottomLeftDiagonal = Just (n, str2attr "bottomLeftDiagonal") - toAttrFrTyp n Transition_Subtype_BottomRight = Just (n, str2attr "bottomRight") - toAttrFrTyp n Transition_Subtype_BottomRightClockwise = Just (n, str2attr "bottomRightClockwise") - toAttrFrTyp n Transition_Subtype_BottomRightCounterClockwise = Just (n, str2attr "bottomRightCounterClockwise") - toAttrFrTyp n Transition_Subtype_BottomRightDiagonal = Just (n, str2attr "bottomRightDiagonal") - toAttrFrTyp n Transition_Subtype_CenterRight = Just (n, str2attr "centerRight") - toAttrFrTyp n Transition_Subtype_CenterTop = Just (n, str2attr "centerTop") - toAttrFrTyp n Transition_Subtype_Circle = Just (n, str2attr "circle") - toAttrFrTyp n Transition_Subtype_ClockwiseBottom = Just (n, str2attr "clockwiseBottom") - toAttrFrTyp n Transition_Subtype_ClockwiseBottomRight = Just (n, str2attr "clockwiseBottomRight") - toAttrFrTyp n Transition_Subtype_ClockwiseLeft = Just (n, str2attr "clockwiseLeft") - toAttrFrTyp n Transition_Subtype_ClockwiseNine = Just (n, str2attr "clockwiseNine") - toAttrFrTyp n Transition_Subtype_ClockwiseRight = Just (n, str2attr "clockwiseRight") - toAttrFrTyp n Transition_Subtype_ClockwiseSix = Just (n, str2attr "clockwiseSix") - toAttrFrTyp n Transition_Subtype_ClockwiseThree = Just (n, str2attr "clockwiseThree") - toAttrFrTyp n Transition_Subtype_ClockwiseTop = Just (n, str2attr "clockwiseTop") - toAttrFrTyp n Transition_Subtype_ClockwiseTopLeft = Just (n, str2attr "clockwiseTopLeft") - toAttrFrTyp n Transition_Subtype_ClockwiseTwelve = Just (n, str2attr "clockwiseTwelve") - toAttrFrTyp n Transition_Subtype_CornersIn = Just (n, str2attr "cornersIn") - toAttrFrTyp n Transition_Subtype_CornersOut = Just (n, str2attr "cornersOut") - toAttrFrTyp n Transition_Subtype_CounterClockwiseBottomLeft = Just (n, str2attr "counterClockwiseBottomLeft") - toAttrFrTyp n Transition_Subtype_CounterClockwiseTopRight = Just (n, str2attr "counterClockwiseTopRight") - toAttrFrTyp n Transition_Subtype_Crossfade = Just (n, str2attr "crossfade") - toAttrFrTyp n Transition_Subtype_DiagonalBottomLeft = Just (n, str2attr "diagonalBottomLeft") - toAttrFrTyp n Transition_Subtype_DiagonalBottomLeftOpposite = Just (n, str2attr "diagonalBottomLeftOpposite") - toAttrFrTyp n Transition_Subtype_DiagonalTopLeft = Just (n, str2attr "diagonalTopLeft") - toAttrFrTyp n Transition_Subtype_DiagonalTopLeftOpposite = Just (n, str2attr "diagonalTopLeftOpposite") - toAttrFrTyp n Transition_Subtype_Diamond = Just (n, str2attr "diamond") - toAttrFrTyp n Transition_Subtype_DoubleBarnDoor = Just (n, str2attr "doubleBarnDoor") - toAttrFrTyp n Transition_Subtype_DoubleDiamond = Just (n, str2attr "doubleDiamond") - toAttrFrTyp n Transition_Subtype_Down = Just (n, str2attr "down") - toAttrFrTyp n Transition_Subtype_FadeFromColor = Just (n, str2attr "fadeFromColor") - toAttrFrTyp n Transition_Subtype_FadeToColor = Just (n, str2attr "fadeToColor") - toAttrFrTyp n Transition_Subtype_FanInHorizontal = Just (n, str2attr "fanInHorizontal") - toAttrFrTyp n Transition_Subtype_FanInVertical = Just (n, str2attr "fanInVertical") - toAttrFrTyp n Transition_Subtype_FanOutHorizontal = Just (n, str2attr "fanOutHorizontal") - toAttrFrTyp n Transition_Subtype_FanOutVertical = Just (n, str2attr "fanOutVertical") - toAttrFrTyp n Transition_Subtype_FivePoint = Just (n, str2attr "fivePoint") - toAttrFrTyp n Transition_Subtype_FourBlade = Just (n, str2attr "fourBlade") - toAttrFrTyp n Transition_Subtype_FourBoxHorizontal = Just (n, str2attr "fourBoxHorizontal") - toAttrFrTyp n Transition_Subtype_FourBoxVertical = Just (n, str2attr "fourBoxVertical") - toAttrFrTyp n Transition_Subtype_FourPoint = Just (n, str2attr "fourPoint") - toAttrFrTyp n Transition_Subtype_FromBottom = Just (n, str2attr "fromBottom") - toAttrFrTyp n Transition_Subtype_FromLeft = Just (n, str2attr "fromLeft") - toAttrFrTyp n Transition_Subtype_FromRight = Just (n, str2attr "fromRight") - toAttrFrTyp n Transition_Subtype_FromTop = Just (n, str2attr "fromTop") - toAttrFrTyp n Transition_Subtype_Heart = Just (n, str2attr "heart") - toAttrFrTyp n Transition_Subtype_Horizontal = Just (n, str2attr "horizontal") - toAttrFrTyp n Transition_Subtype_HorizontalLeft = Just (n, str2attr "horizontalLeft") - toAttrFrTyp n Transition_Subtype_HorizontalLeftSame = Just (n, str2attr "horizontalLeftSame") - toAttrFrTyp n Transition_Subtype_HorizontalRight = Just (n, str2attr "horizontalRight") - toAttrFrTyp n Transition_Subtype_HorizontalRightSame = Just (n, str2attr "horizontalRightSame") - toAttrFrTyp n Transition_Subtype_HorizontalTopLeftOpposite = Just (n, str2attr "horizontalTopLeftOpposite") - toAttrFrTyp n Transition_Subtype_HorizontalTopRightOpposite = Just (n, str2attr "horizontalTopRightOpposite") - toAttrFrTyp n Transition_Subtype_Keyhole = Just (n, str2attr "keyhole") - toAttrFrTyp n Transition_Subtype_Left = Just (n, str2attr "left") - toAttrFrTyp n Transition_Subtype_LeftCenter = Just (n, str2attr "leftCenter") - toAttrFrTyp n Transition_Subtype_LeftToRight = Just (n, str2attr "leftToRight") - toAttrFrTyp n Transition_Subtype_OppositeHorizontal = Just (n, str2attr "oppositeHorizontal") - toAttrFrTyp n Transition_Subtype_OppositeVertical = Just (n, str2attr "oppositeVertical") - toAttrFrTyp n Transition_Subtype_ParallelDiagonal = Just (n, str2attr "parallelDiagonal") - toAttrFrTyp n Transition_Subtype_ParallelDiagonalBottomLeft = Just (n, str2attr "parallelDiagonalBottomLeft") - toAttrFrTyp n Transition_Subtype_ParallelDiagonalTopLeft = Just (n, str2attr "parallelDiagonalTopLeft") - toAttrFrTyp n Transition_Subtype_ParallelVertical = Just (n, str2attr "parallelVertical") - toAttrFrTyp n Transition_Subtype_Rectangle = Just (n, str2attr "rectangle") - toAttrFrTyp n Transition_Subtype_Right = Just (n, str2attr "right") - toAttrFrTyp n Transition_Subtype_RightCenter = Just (n, str2attr "rightCenter") - toAttrFrTyp n Transition_Subtype_SixPoint = Just (n, str2attr "sixPoint") - toAttrFrTyp n Transition_Subtype_Top = Just (n, str2attr "top") - toAttrFrTyp n Transition_Subtype_TopCenter = Just (n, str2attr "topCenter") - toAttrFrTyp n Transition_Subtype_TopLeft = Just (n, str2attr "topLeft") - toAttrFrTyp n Transition_Subtype_TopLeftClockwise = Just (n, str2attr "topLeftClockwise") - toAttrFrTyp n Transition_Subtype_TopLeftCounterClockwise = Just (n, str2attr "topLeftCounterClockwise") - toAttrFrTyp n Transition_Subtype_TopLeftDiagonal = Just (n, str2attr "topLeftDiagonal") - toAttrFrTyp n Transition_Subtype_TopLeftHorizontal = Just (n, str2attr "topLeftHorizontal") - toAttrFrTyp n Transition_Subtype_TopLeftVertical = Just (n, str2attr "topLeftVertical") - toAttrFrTyp n Transition_Subtype_TopRight = Just (n, str2attr "topRight") - toAttrFrTyp n Transition_Subtype_TopRightClockwise = Just (n, str2attr "topRightClockwise") - toAttrFrTyp n Transition_Subtype_TopRightCounterClockwise = Just (n, str2attr "topRightCounterClockwise") - toAttrFrTyp n Transition_Subtype_TopRightDiagonal = Just (n, str2attr "topRightDiagonal") - toAttrFrTyp n Transition_Subtype_TopToBottom = Just (n, str2attr "topToBottom") - toAttrFrTyp n Transition_Subtype_TwoBladeHorizontal = Just (n, str2attr "twoBladeHorizontal") - toAttrFrTyp n Transition_Subtype_TwoBladeVertical = Just (n, str2attr "twoBladeVertical") - toAttrFrTyp n Transition_Subtype_TwoBoxBottom = Just (n, str2attr "twoBoxBottom") - toAttrFrTyp n Transition_Subtype_TwoBoxLeft = Just (n, str2attr "twoBoxLeft") - toAttrFrTyp n Transition_Subtype_TwoBoxRight = Just (n, str2attr "twoBoxRight") - toAttrFrTyp n Transition_Subtype_TwoBoxTop = Just (n, str2attr "twoBoxTop") - toAttrFrTyp n Transition_Subtype_Up = Just (n, str2attr "up") - toAttrFrTyp n Transition_Subtype_Vertical = Just (n, str2attr "vertical") - toAttrFrTyp n Transition_Subtype_VerticalBottomLeftOpposite = Just (n, str2attr "verticalBottomLeftOpposite") - toAttrFrTyp n Transition_Subtype_VerticalBottomSame = Just (n, str2attr "verticalBottomSame") - toAttrFrTyp n Transition_Subtype_VerticalLeft = Just (n, str2attr "verticalLeft") - toAttrFrTyp n Transition_Subtype_VerticalRight = Just (n, str2attr "verticalRight") - toAttrFrTyp n Transition_Subtype_VerticalTopLeftOpposite = Just (n, str2attr "verticalTopLeftOpposite") - toAttrFrTyp n Transition_Subtype_VerticalTopSame = Just (n, str2attr "verticalTopSame") -instance XmlAttrType Transition_Coordinated where - fromAttrToTyp n (n',v) - | n==n' = translate (attr2str v) - | otherwise = Nothing - where translate "true" = Just Transition_Coordinated_True - translate "false" = Just Transition_Coordinated_False - translate _ = Nothing - toAttrFrTyp n Transition_Coordinated_True = Just (n, str2attr "true") - toAttrFrTyp n Transition_Coordinated_False = Just (n, str2attr "false") -instance XmlAttrType Transition_ClibBoundary where - fromAttrToTyp n (n',v) - | n==n' = translate (attr2str v) - | otherwise = Nothing - where translate "parent" = Just Transition_ClibBoundary_Parent - translate "children" = Just Transition_ClibBoundary_Children - translate _ = Nothing - toAttrFrTyp n Transition_ClibBoundary_Parent = Just (n, str2attr "parent") - toAttrFrTyp n Transition_ClibBoundary_Children = Just (n, str2attr "children") -instance XmlAttrType Transition_Direction where - fromAttrToTyp n (n',v) - | n==n' = translate (attr2str v) - | otherwise = Nothing - where translate "forward" = Just Transition_Direction_Forward - translate "reverse" = Just Transition_Direction_Reverse - translate _ = Nothing - toAttrFrTyp n Transition_Direction_Forward = Just (n, str2attr "forward") - toAttrFrTyp n Transition_Direction_Reverse = Just (n, str2attr "reverse") -instance XmlContent TransitionFilter where - fromElem (CElem (Elem "transitionFilter" as []):rest) = - (Just (fromAttrs as), rest) - fromElem (CMisc _:rest) = fromElem rest - fromElem rest = (Nothing, rest) - toElem as = - [CElem (Elem "transitionFilter" (toAttrs as) [])] -instance XmlAttributes TransitionFilter where - fromAttrs as = - TransitionFilter - { transitionFilterId = possibleA fromAttrToStr "id" as - , transitionFilterClass = possibleA fromAttrToStr "class" as - , transitionFilterTitle = possibleA fromAttrToStr "title" as - , transitionFilterXml'lang = possibleA fromAttrToStr "xml:lang" as - , transitionFilterType = possibleA fromAttrToTyp "type" as - , transitionFilterSubtype = possibleA fromAttrToTyp "subtype" as - , transitionFilterHorzRepeat = defaultA fromAttrToStr "0" "horzRepeat" as - , transitionFilterVertRepeat = defaultA fromAttrToStr "0" "vertRepeat" as - , transitionFilterBorderWidth = defaultA fromAttrToStr "0" "borderWidth" as - , transitionFilterBorderColor = defaultA fromAttrToStr "black" "borderColor" as - , transitionFilterFadeColor = defaultA fromAttrToStr "black" "fadeColor" as - , transitionFilterCoordinated = defaultA fromAttrToTyp TransitionFilter_Coordinated_False "coordinated" as - , transitionFilterClibBoundary = defaultA fromAttrToTyp TransitionFilter_ClibBoundary_Children "clibBoundary" as - , transitionFilterDur = possibleA fromAttrToStr "dur" as - , transitionFilterRepeatCount = possibleA fromAttrToStr "repeatCount" as - , transitionFilterRepeatDur = possibleA fromAttrToStr "repeatDur" as - , transitionFilterBegin = possibleA fromAttrToStr "begin" as - , transitionFilterEnd = possibleA fromAttrToStr "end" as - , transitionFilterValues = possibleA fromAttrToStr "values" as - , transitionFilterFrom = possibleA fromAttrToStr "from" as - , transitionFilterTo = possibleA fromAttrToStr "to" as - , transitionFilterBy = possibleA fromAttrToStr "by" as - , transitionFilterCalcMode = defaultA fromAttrToTyp TransitionFilter_CalcMode_Linear "calcMode" as - } - toAttrs v = catMaybes - [ maybeToAttr toAttrFrStr "id" (transitionFilterId v) - , maybeToAttr toAttrFrStr "class" (transitionFilterClass v) - , maybeToAttr toAttrFrStr "title" (transitionFilterTitle v) - , maybeToAttr toAttrFrStr "xml:lang" (transitionFilterXml'lang v) - , maybeToAttr toAttrFrTyp "type" (transitionFilterType v) - , maybeToAttr toAttrFrTyp "subtype" (transitionFilterSubtype v) - , defaultToAttr toAttrFrStr "horzRepeat" (transitionFilterHorzRepeat v) - , defaultToAttr toAttrFrStr "vertRepeat" (transitionFilterVertRepeat v) - , defaultToAttr toAttrFrStr "borderWidth" (transitionFilterBorderWidth v) - , defaultToAttr toAttrFrStr "borderColor" (transitionFilterBorderColor v) - , defaultToAttr toAttrFrStr "fadeColor" (transitionFilterFadeColor v) - , defaultToAttr toAttrFrTyp "coordinated" (transitionFilterCoordinated v) - , defaultToAttr toAttrFrTyp "clibBoundary" (transitionFilterClibBoundary v) - , maybeToAttr toAttrFrStr "dur" (transitionFilterDur v) - , maybeToAttr toAttrFrStr "repeatCount" (transitionFilterRepeatCount v) - , maybeToAttr toAttrFrStr "repeatDur" (transitionFilterRepeatDur v) - , maybeToAttr toAttrFrStr "begin" (transitionFilterBegin v) - , maybeToAttr toAttrFrStr "end" (transitionFilterEnd v) - , maybeToAttr toAttrFrStr "values" (transitionFilterValues v) - , maybeToAttr toAttrFrStr "from" (transitionFilterFrom v) - , maybeToAttr toAttrFrStr "to" (transitionFilterTo v) - , maybeToAttr toAttrFrStr "by" (transitionFilterBy v) - , defaultToAttr toAttrFrTyp "calcMode" (transitionFilterCalcMode v) - ] -instance XmlAttrType TransitionFilter_Type where - fromAttrToTyp n (n',v) - | n==n' = translate (attr2str v) - | otherwise = Nothing - where translate "barWipe" = Just TransitionFilter_Type_BarWipe - translate "boxWipe" = Just TransitionFilter_Type_BoxWipe - translate "fourBoxWipe" = Just TransitionFilter_Type_FourBoxWipe - translate "barnDoorWipe" = Just TransitionFilter_Type_BarnDoorWipe - translate "diagonalWipe" = Just TransitionFilter_Type_DiagonalWipe - translate "bowTieWipe" = Just TransitionFilter_Type_BowTieWipe - translate "miscDiagonalWipe" = Just TransitionFilter_Type_MiscDiagonalWipe - translate "veeWipe" = Just TransitionFilter_Type_VeeWipe - translate "barnVeeWipe" = Just TransitionFilter_Type_BarnVeeWipe - translate "zigZagWipe" = Just TransitionFilter_Type_ZigZagWipe - translate "barnZigZagWipe" = Just TransitionFilter_Type_BarnZigZagWipe - translate "miscShapeWipe" = Just TransitionFilter_Type_MiscShapeWipe - translate "triangleWipe" = Just TransitionFilter_Type_TriangleWipe - translate "arrowHeadWipe" = Just TransitionFilter_Type_ArrowHeadWipe - translate "pentagonWipe" = Just TransitionFilter_Type_PentagonWipe - translate "hexagonWipe" = Just TransitionFilter_Type_HexagonWipe - translate "ellipseWipe" = Just TransitionFilter_Type_EllipseWipe - translate "eyeWipe" = Just TransitionFilter_Type_EyeWipe - translate "roundRectWipe" = Just TransitionFilter_Type_RoundRectWipe - translate "starWipe" = Just TransitionFilter_Type_StarWipe - translate "clockWipe" = Just TransitionFilter_Type_ClockWipe - translate "pinWheelWipe" = Just TransitionFilter_Type_PinWheelWipe - translate "singleSweepWipe" = Just TransitionFilter_Type_SingleSweepWipe - translate "fanWipe" = Just TransitionFilter_Type_FanWipe - translate "doubleFanWipe" = Just TransitionFilter_Type_DoubleFanWipe - translate "doubleSweepWipe" = Just TransitionFilter_Type_DoubleSweepWipe - translate "saloonDoorWipe" = Just TransitionFilter_Type_SaloonDoorWipe - translate "windshieldWipe" = Just TransitionFilter_Type_WindshieldWipe - translate "snakeWipe" = Just TransitionFilter_Type_SnakeWipe - translate "spiralWipe" = Just TransitionFilter_Type_SpiralWipe - translate "parallelSnakesWipe" = Just TransitionFilter_Type_ParallelSnakesWipe - translate "boxSnakesWipe" = Just TransitionFilter_Type_BoxSnakesWipe - translate "waterfallWipe" = Just TransitionFilter_Type_WaterfallWipe - translate "pushWipe" = Just TransitionFilter_Type_PushWipe - translate "slideWipe" = Just TransitionFilter_Type_SlideWipe - translate "fade" = Just TransitionFilter_Type_Fade - translate _ = Nothing - toAttrFrTyp n TransitionFilter_Type_BarWipe = Just (n, str2attr "barWipe") - toAttrFrTyp n TransitionFilter_Type_BoxWipe = Just (n, str2attr "boxWipe") - toAttrFrTyp n TransitionFilter_Type_FourBoxWipe = Just (n, str2attr "fourBoxWipe") - toAttrFrTyp n TransitionFilter_Type_BarnDoorWipe = Just (n, str2attr "barnDoorWipe") - toAttrFrTyp n TransitionFilter_Type_DiagonalWipe = Just (n, str2attr "diagonalWipe") - toAttrFrTyp n TransitionFilter_Type_BowTieWipe = Just (n, str2attr "bowTieWipe") - toAttrFrTyp n TransitionFilter_Type_MiscDiagonalWipe = Just (n, str2attr "miscDiagonalWipe") - toAttrFrTyp n TransitionFilter_Type_VeeWipe = Just (n, str2attr "veeWipe") - toAttrFrTyp n TransitionFilter_Type_BarnVeeWipe = Just (n, str2attr "barnVeeWipe") - toAttrFrTyp n TransitionFilter_Type_ZigZagWipe = Just (n, str2attr "zigZagWipe") - toAttrFrTyp n TransitionFilter_Type_BarnZigZagWipe = Just (n, str2attr "barnZigZagWipe") - toAttrFrTyp n TransitionFilter_Type_MiscShapeWipe = Just (n, str2attr "miscShapeWipe") - toAttrFrTyp n TransitionFilter_Type_TriangleWipe = Just (n, str2attr "triangleWipe") - toAttrFrTyp n TransitionFilter_Type_ArrowHeadWipe = Just (n, str2attr "arrowHeadWipe") - toAttrFrTyp n TransitionFilter_Type_PentagonWipe = Just (n, str2attr "pentagonWipe") - toAttrFrTyp n TransitionFilter_Type_HexagonWipe = Just (n, str2attr "hexagonWipe") - toAttrFrTyp n TransitionFilter_Type_EllipseWipe = Just (n, str2attr "ellipseWipe") - toAttrFrTyp n TransitionFilter_Type_EyeWipe = Just (n, str2attr "eyeWipe") - toAttrFrTyp n TransitionFilter_Type_RoundRectWipe = Just (n, str2attr "roundRectWipe") - toAttrFrTyp n TransitionFilter_Type_StarWipe = Just (n, str2attr "starWipe") - toAttrFrTyp n TransitionFilter_Type_ClockWipe = Just (n, str2attr "clockWipe") - toAttrFrTyp n TransitionFilter_Type_PinWheelWipe = Just (n, str2attr "pinWheelWipe") - toAttrFrTyp n TransitionFilter_Type_SingleSweepWipe = Just (n, str2attr "singleSweepWipe") - toAttrFrTyp n TransitionFilter_Type_FanWipe = Just (n, str2attr "fanWipe") - toAttrFrTyp n TransitionFilter_Type_DoubleFanWipe = Just (n, str2attr "doubleFanWipe") - toAttrFrTyp n TransitionFilter_Type_DoubleSweepWipe = Just (n, str2attr "doubleSweepWipe") - toAttrFrTyp n TransitionFilter_Type_SaloonDoorWipe = Just (n, str2attr "saloonDoorWipe") - toAttrFrTyp n TransitionFilter_Type_WindshieldWipe = Just (n, str2attr "windshieldWipe") - toAttrFrTyp n TransitionFilter_Type_SnakeWipe = Just (n, str2attr "snakeWipe") - toAttrFrTyp n TransitionFilter_Type_SpiralWipe = Just (n, str2attr "spiralWipe") - toAttrFrTyp n TransitionFilter_Type_ParallelSnakesWipe = Just (n, str2attr "parallelSnakesWipe") - toAttrFrTyp n TransitionFilter_Type_BoxSnakesWipe = Just (n, str2attr "boxSnakesWipe") - toAttrFrTyp n TransitionFilter_Type_WaterfallWipe = Just (n, str2attr "waterfallWipe") - toAttrFrTyp n TransitionFilter_Type_PushWipe = Just (n, str2attr "pushWipe") - toAttrFrTyp n TransitionFilter_Type_SlideWipe = Just (n, str2attr "slideWipe") - toAttrFrTyp n TransitionFilter_Type_Fade = Just (n, str2attr "fade") -instance XmlAttrType TransitionFilter_Subtype where - fromAttrToTyp n (n',v) - | n==n' = translate (attr2str v) - | otherwise = Nothing - where translate "bottom" = Just TransitionFilter_Subtype_Bottom - translate "bottomCenter" = Just TransitionFilter_Subtype_BottomCenter - translate "bottomLeft" = Just TransitionFilter_Subtype_BottomLeft - translate "bottomLeftClockwise" = Just TransitionFilter_Subtype_BottomLeftClockwise - translate "bottomLeftCounterClockwise" = Just TransitionFilter_Subtype_BottomLeftCounterClockwise - translate "bottomLeftDiagonal" = Just TransitionFilter_Subtype_BottomLeftDiagonal - translate "bottomRight" = Just TransitionFilter_Subtype_BottomRight - translate "bottomRightClockwise" = Just TransitionFilter_Subtype_BottomRightClockwise - translate "bottomRightCounterClockwise" = Just TransitionFilter_Subtype_BottomRightCounterClockwise - translate "bottomRightDiagonal" = Just TransitionFilter_Subtype_BottomRightDiagonal - translate "centerRight" = Just TransitionFilter_Subtype_CenterRight - translate "centerTop" = Just TransitionFilter_Subtype_CenterTop - translate "circle" = Just TransitionFilter_Subtype_Circle - translate "clockwiseBottom" = Just TransitionFilter_Subtype_ClockwiseBottom - translate "clockwiseBottomRight" = Just TransitionFilter_Subtype_ClockwiseBottomRight - translate "clockwiseLeft" = Just TransitionFilter_Subtype_ClockwiseLeft - translate "clockwiseNine" = Just TransitionFilter_Subtype_ClockwiseNine - translate "clockwiseRight" = Just TransitionFilter_Subtype_ClockwiseRight - translate "clockwiseSix" = Just TransitionFilter_Subtype_ClockwiseSix - translate "clockwiseThree" = Just TransitionFilter_Subtype_ClockwiseThree - translate "clockwiseTop" = Just TransitionFilter_Subtype_ClockwiseTop - translate "clockwiseTopLeft" = Just TransitionFilter_Subtype_ClockwiseTopLeft - translate "clockwiseTwelve" = Just TransitionFilter_Subtype_ClockwiseTwelve - translate "cornersIn" = Just TransitionFilter_Subtype_CornersIn - translate "cornersOut" = Just TransitionFilter_Subtype_CornersOut - translate "counterClockwiseBottomLeft" = Just TransitionFilter_Subtype_CounterClockwiseBottomLeft - translate "counterClockwiseTopRight" = Just TransitionFilter_Subtype_CounterClockwiseTopRight - translate "crossfade" = Just TransitionFilter_Subtype_Crossfade - translate "diagonalBottomLeft" = Just TransitionFilter_Subtype_DiagonalBottomLeft - translate "diagonalBottomLeftOpposite" = Just TransitionFilter_Subtype_DiagonalBottomLeftOpposite - translate "diagonalTopLeft" = Just TransitionFilter_Subtype_DiagonalTopLeft - translate "diagonalTopLeftOpposite" = Just TransitionFilter_Subtype_DiagonalTopLeftOpposite - translate "diamond" = Just TransitionFilter_Subtype_Diamond - translate "doubleBarnDoor" = Just TransitionFilter_Subtype_DoubleBarnDoor - translate "doubleDiamond" = Just TransitionFilter_Subtype_DoubleDiamond - translate "down" = Just TransitionFilter_Subtype_Down - translate "fadeFromColor" = Just TransitionFilter_Subtype_FadeFromColor - translate "fadeToColor" = Just TransitionFilter_Subtype_FadeToColor - translate "fanInHorizontal" = Just TransitionFilter_Subtype_FanInHorizontal - translate "fanInVertical" = Just TransitionFilter_Subtype_FanInVertical - translate "fanOutHorizontal" = Just TransitionFilter_Subtype_FanOutHorizontal - translate "fanOutVertical" = Just TransitionFilter_Subtype_FanOutVertical - translate "fivePoint" = Just TransitionFilter_Subtype_FivePoint - translate "fourBlade" = Just TransitionFilter_Subtype_FourBlade - translate "fourBoxHorizontal" = Just TransitionFilter_Subtype_FourBoxHorizontal - translate "fourBoxVertical" = Just TransitionFilter_Subtype_FourBoxVertical - translate "fourPoint" = Just TransitionFilter_Subtype_FourPoint - translate "fromBottom" = Just TransitionFilter_Subtype_FromBottom - translate "fromLeft" = Just TransitionFilter_Subtype_FromLeft - translate "fromRight" = Just TransitionFilter_Subtype_FromRight - translate "fromTop" = Just TransitionFilter_Subtype_FromTop - translate "heart" = Just TransitionFilter_Subtype_Heart - translate "horizontal" = Just TransitionFilter_Subtype_Horizontal - translate "horizontalLeft" = Just TransitionFilter_Subtype_HorizontalLeft - translate "horizontalLeftSame" = Just TransitionFilter_Subtype_HorizontalLeftSame - translate "horizontalRight" = Just TransitionFilter_Subtype_HorizontalRight - translate "horizontalRightSame" = Just TransitionFilter_Subtype_HorizontalRightSame - translate "horizontalTopLeftOpposite" = Just TransitionFilter_Subtype_HorizontalTopLeftOpposite - translate "horizontalTopRightOpposite" = Just TransitionFilter_Subtype_HorizontalTopRightOpposite - translate "keyhole" = Just TransitionFilter_Subtype_Keyhole - translate "left" = Just TransitionFilter_Subtype_Left - translate "leftCenter" = Just TransitionFilter_Subtype_LeftCenter - translate "leftToRight" = Just TransitionFilter_Subtype_LeftToRight - translate "oppositeHorizontal" = Just TransitionFilter_Subtype_OppositeHorizontal - translate "oppositeVertical" = Just TransitionFilter_Subtype_OppositeVertical - translate "parallelDiagonal" = Just TransitionFilter_Subtype_ParallelDiagonal - translate "parallelDiagonalBottomLeft" = Just TransitionFilter_Subtype_ParallelDiagonalBottomLeft - translate "parallelDiagonalTopLeft" = Just TransitionFilter_Subtype_ParallelDiagonalTopLeft - translate "parallelVertical" = Just TransitionFilter_Subtype_ParallelVertical - translate "rectangle" = Just TransitionFilter_Subtype_Rectangle - translate "right" = Just TransitionFilter_Subtype_Right - translate "rightCenter" = Just TransitionFilter_Subtype_RightCenter - translate "sixPoint" = Just TransitionFilter_Subtype_SixPoint - translate "top" = Just TransitionFilter_Subtype_Top - translate "topCenter" = Just TransitionFilter_Subtype_TopCenter - translate "topLeft" = Just TransitionFilter_Subtype_TopLeft - translate "topLeftClockwise" = Just TransitionFilter_Subtype_TopLeftClockwise - translate "topLeftCounterClockwise" = Just TransitionFilter_Subtype_TopLeftCounterClockwise - translate "topLeftDiagonal" = Just TransitionFilter_Subtype_TopLeftDiagonal - translate "topLeftHorizontal" = Just TransitionFilter_Subtype_TopLeftHorizontal - translate "topLeftVertical" = Just TransitionFilter_Subtype_TopLeftVertical - translate "topRight" = Just TransitionFilter_Subtype_TopRight - translate "topRightClockwise" = Just TransitionFilter_Subtype_TopRightClockwise - translate "topRightCounterClockwise" = Just TransitionFilter_Subtype_TopRightCounterClockwise - translate "topRightDiagonal" = Just TransitionFilter_Subtype_TopRightDiagonal - translate "topToBottom" = Just TransitionFilter_Subtype_TopToBottom - translate "twoBladeHorizontal" = Just TransitionFilter_Subtype_TwoBladeHorizontal - translate "twoBladeVertical" = Just TransitionFilter_Subtype_TwoBladeVertical - translate "twoBoxBottom" = Just TransitionFilter_Subtype_TwoBoxBottom - translate "twoBoxLeft" = Just TransitionFilter_Subtype_TwoBoxLeft - translate "twoBoxRight" = Just TransitionFilter_Subtype_TwoBoxRight - translate "twoBoxTop" = Just TransitionFilter_Subtype_TwoBoxTop - translate "up" = Just TransitionFilter_Subtype_Up - translate "vertical" = Just TransitionFilter_Subtype_Vertical - translate "verticalBottomLeftOpposite" = Just TransitionFilter_Subtype_VerticalBottomLeftOpposite - translate "verticalBottomSame" = Just TransitionFilter_Subtype_VerticalBottomSame - translate "verticalLeft" = Just TransitionFilter_Subtype_VerticalLeft - translate "verticalRight" = Just TransitionFilter_Subtype_VerticalRight - translate "verticalTopLeftOpposite" = Just TransitionFilter_Subtype_VerticalTopLeftOpposite - translate "verticalTopSame" = Just TransitionFilter_Subtype_VerticalTopSame - translate _ = Nothing - toAttrFrTyp n TransitionFilter_Subtype_Bottom = Just (n, str2attr "bottom") - toAttrFrTyp n TransitionFilter_Subtype_BottomCenter = Just (n, str2attr "bottomCenter") - toAttrFrTyp n TransitionFilter_Subtype_BottomLeft = Just (n, str2attr "bottomLeft") - toAttrFrTyp n TransitionFilter_Subtype_BottomLeftClockwise = Just (n, str2attr "bottomLeftClockwise") - toAttrFrTyp n TransitionFilter_Subtype_BottomLeftCounterClockwise = Just (n, str2attr "bottomLeftCounterClockwise") - toAttrFrTyp n TransitionFilter_Subtype_BottomLeftDiagonal = Just (n, str2attr "bottomLeftDiagonal") - toAttrFrTyp n TransitionFilter_Subtype_BottomRight = Just (n, str2attr "bottomRight") - toAttrFrTyp n TransitionFilter_Subtype_BottomRightClockwise = Just (n, str2attr "bottomRightClockwise") - toAttrFrTyp n TransitionFilter_Subtype_BottomRightCounterClockwise = Just (n, str2attr "bottomRightCounterClockwise") - toAttrFrTyp n TransitionFilter_Subtype_BottomRightDiagonal = Just (n, str2attr "bottomRightDiagonal") - toAttrFrTyp n TransitionFilter_Subtype_CenterRight = Just (n, str2attr "centerRight") - toAttrFrTyp n TransitionFilter_Subtype_CenterTop = Just (n, str2attr "centerTop") - toAttrFrTyp n TransitionFilter_Subtype_Circle = Just (n, str2attr "circle") - toAttrFrTyp n TransitionFilter_Subtype_ClockwiseBottom = Just (n, str2attr "clockwiseBottom") - toAttrFrTyp n TransitionFilter_Subtype_ClockwiseBottomRight = Just (n, str2attr "clockwiseBottomRight") - toAttrFrTyp n TransitionFilter_Subtype_ClockwiseLeft = Just (n, str2attr "clockwiseLeft") - toAttrFrTyp n TransitionFilter_Subtype_ClockwiseNine = Just (n, str2attr "clockwiseNine") - toAttrFrTyp n TransitionFilter_Subtype_ClockwiseRight = Just (n, str2attr "clockwiseRight") - toAttrFrTyp n TransitionFilter_Subtype_ClockwiseSix = Just (n, str2attr "clockwiseSix") - toAttrFrTyp n TransitionFilter_Subtype_ClockwiseThree = Just (n, str2attr "clockwiseThree") - toAttrFrTyp n TransitionFilter_Subtype_ClockwiseTop = Just (n, str2attr "clockwiseTop") - toAttrFrTyp n TransitionFilter_Subtype_ClockwiseTopLeft = Just (n, str2attr "clockwiseTopLeft") - toAttrFrTyp n TransitionFilter_Subtype_ClockwiseTwelve = Just (n, str2attr "clockwiseTwelve") - toAttrFrTyp n TransitionFilter_Subtype_CornersIn = Just (n, str2attr "cornersIn") - toAttrFrTyp n TransitionFilter_Subtype_CornersOut = Just (n, str2attr "cornersOut") - toAttrFrTyp n TransitionFilter_Subtype_CounterClockwiseBottomLeft = Just (n, str2attr "counterClockwiseBottomLeft") - toAttrFrTyp n TransitionFilter_Subtype_CounterClockwiseTopRight = Just (n, str2attr "counterClockwiseTopRight") - toAttrFrTyp n TransitionFilter_Subtype_Crossfade = Just (n, str2attr "crossfade") - toAttrFrTyp n TransitionFilter_Subtype_DiagonalBottomLeft = Just (n, str2attr "diagonalBottomLeft") - toAttrFrTyp n TransitionFilter_Subtype_DiagonalBottomLeftOpposite = Just (n, str2attr "diagonalBottomLeftOpposite") - toAttrFrTyp n TransitionFilter_Subtype_DiagonalTopLeft = Just (n, str2attr "diagonalTopLeft") - toAttrFrTyp n TransitionFilter_Subtype_DiagonalTopLeftOpposite = Just (n, str2attr "diagonalTopLeftOpposite") - toAttrFrTyp n TransitionFilter_Subtype_Diamond = Just (n, str2attr "diamond") - toAttrFrTyp n TransitionFilter_Subtype_DoubleBarnDoor = Just (n, str2attr "doubleBarnDoor") - toAttrFrTyp n TransitionFilter_Subtype_DoubleDiamond = Just (n, str2attr "doubleDiamond") - toAttrFrTyp n TransitionFilter_Subtype_Down = Just (n, str2attr "down") - toAttrFrTyp n TransitionFilter_Subtype_FadeFromColor = Just (n, str2attr "fadeFromColor") - toAttrFrTyp n TransitionFilter_Subtype_FadeToColor = Just (n, str2attr "fadeToColor") - toAttrFrTyp n TransitionFilter_Subtype_FanInHorizontal = Just (n, str2attr "fanInHorizontal") - toAttrFrTyp n TransitionFilter_Subtype_FanInVertical = Just (n, str2attr "fanInVertical") - toAttrFrTyp n TransitionFilter_Subtype_FanOutHorizontal = Just (n, str2attr "fanOutHorizontal") - toAttrFrTyp n TransitionFilter_Subtype_FanOutVertical = Just (n, str2attr "fanOutVertical") - toAttrFrTyp n TransitionFilter_Subtype_FivePoint = Just (n, str2attr "fivePoint") - toAttrFrTyp n TransitionFilter_Subtype_FourBlade = Just (n, str2attr "fourBlade") - toAttrFrTyp n TransitionFilter_Subtype_FourBoxHorizontal = Just (n, str2attr "fourBoxHorizontal") - toAttrFrTyp n TransitionFilter_Subtype_FourBoxVertical = Just (n, str2attr "fourBoxVertical") - toAttrFrTyp n TransitionFilter_Subtype_FourPoint = Just (n, str2attr "fourPoint") - toAttrFrTyp n TransitionFilter_Subtype_FromBottom = Just (n, str2attr "fromBottom") - toAttrFrTyp n TransitionFilter_Subtype_FromLeft = Just (n, str2attr "fromLeft") - toAttrFrTyp n TransitionFilter_Subtype_FromRight = Just (n, str2attr "fromRight") - toAttrFrTyp n TransitionFilter_Subtype_FromTop = Just (n, str2attr "fromTop") - toAttrFrTyp n TransitionFilter_Subtype_Heart = Just (n, str2attr "heart") - toAttrFrTyp n TransitionFilter_Subtype_Horizontal = Just (n, str2attr "horizontal") - toAttrFrTyp n TransitionFilter_Subtype_HorizontalLeft = Just (n, str2attr "horizontalLeft") - toAttrFrTyp n TransitionFilter_Subtype_HorizontalLeftSame = Just (n, str2attr "horizontalLeftSame") - toAttrFrTyp n TransitionFilter_Subtype_HorizontalRight = Just (n, str2attr "horizontalRight") - toAttrFrTyp n TransitionFilter_Subtype_HorizontalRightSame = Just (n, str2attr "horizontalRightSame") - toAttrFrTyp n TransitionFilter_Subtype_HorizontalTopLeftOpposite = Just (n, str2attr "horizontalTopLeftOpposite") - toAttrFrTyp n TransitionFilter_Subtype_HorizontalTopRightOpposite = Just (n, str2attr "horizontalTopRightOpposite") - toAttrFrTyp n TransitionFilter_Subtype_Keyhole = Just (n, str2attr "keyhole") - toAttrFrTyp n TransitionFilter_Subtype_Left = Just (n, str2attr "left") - toAttrFrTyp n TransitionFilter_Subtype_LeftCenter = Just (n, str2attr "leftCenter") - toAttrFrTyp n TransitionFilter_Subtype_LeftToRight = Just (n, str2attr "leftToRight") - toAttrFrTyp n TransitionFilter_Subtype_OppositeHorizontal = Just (n, str2attr "oppositeHorizontal") - toAttrFrTyp n TransitionFilter_Subtype_OppositeVertical = Just (n, str2attr "oppositeVertical") - toAttrFrTyp n TransitionFilter_Subtype_ParallelDiagonal = Just (n, str2attr "parallelDiagonal") - toAttrFrTyp n TransitionFilter_Subtype_ParallelDiagonalBottomLeft = Just (n, str2attr "parallelDiagonalBottomLeft") - toAttrFrTyp n TransitionFilter_Subtype_ParallelDiagonalTopLeft = Just (n, str2attr "parallelDiagonalTopLeft") - toAttrFrTyp n TransitionFilter_Subtype_ParallelVertical = Just (n, str2attr "parallelVertical") - toAttrFrTyp n TransitionFilter_Subtype_Rectangle = Just (n, str2attr "rectangle") - toAttrFrTyp n TransitionFilter_Subtype_Right = Just (n, str2attr "right") - toAttrFrTyp n TransitionFilter_Subtype_RightCenter = Just (n, str2attr "rightCenter") - toAttrFrTyp n TransitionFilter_Subtype_SixPoint = Just (n, str2attr "sixPoint") - toAttrFrTyp n TransitionFilter_Subtype_Top = Just (n, str2attr "top") - toAttrFrTyp n TransitionFilter_Subtype_TopCenter = Just (n, str2attr "topCenter") - toAttrFrTyp n TransitionFilter_Subtype_TopLeft = Just (n, str2attr "topLeft") - toAttrFrTyp n TransitionFilter_Subtype_TopLeftClockwise = Just (n, str2attr "topLeftClockwise") - toAttrFrTyp n TransitionFilter_Subtype_TopLeftCounterClockwise = Just (n, str2attr "topLeftCounterClockwise") - toAttrFrTyp n TransitionFilter_Subtype_TopLeftDiagonal = Just (n, str2attr "topLeftDiagonal") - toAttrFrTyp n TransitionFilter_Subtype_TopLeftHorizontal = Just (n, str2attr "topLeftHorizontal") - toAttrFrTyp n TransitionFilter_Subtype_TopLeftVertical = Just (n, str2attr "topLeftVertical") - toAttrFrTyp n TransitionFilter_Subtype_TopRight = Just (n, str2attr "topRight") - toAttrFrTyp n TransitionFilter_Subtype_TopRightClockwise = Just (n, str2attr "topRightClockwise") - toAttrFrTyp n TransitionFilter_Subtype_TopRightCounterClockwise = Just (n, str2attr "topRightCounterClockwise") - toAttrFrTyp n TransitionFilter_Subtype_TopRightDiagonal = Just (n, str2attr "topRightDiagonal") - toAttrFrTyp n TransitionFilter_Subtype_TopToBottom = Just (n, str2attr "topToBottom") - toAttrFrTyp n TransitionFilter_Subtype_TwoBladeHorizontal = Just (n, str2attr "twoBladeHorizontal") - toAttrFrTyp n TransitionFilter_Subtype_TwoBladeVertical = Just (n, str2attr "twoBladeVertical") - toAttrFrTyp n TransitionFilter_Subtype_TwoBoxBottom = Just (n, str2attr "twoBoxBottom") - toAttrFrTyp n TransitionFilter_Subtype_TwoBoxLeft = Just (n, str2attr "twoBoxLeft") - toAttrFrTyp n TransitionFilter_Subtype_TwoBoxRight = Just (n, str2attr "twoBoxRight") - toAttrFrTyp n TransitionFilter_Subtype_TwoBoxTop = Just (n, str2attr "twoBoxTop") - toAttrFrTyp n TransitionFilter_Subtype_Up = Just (n, str2attr "up") - toAttrFrTyp n TransitionFilter_Subtype_Vertical = Just (n, str2attr "vertical") - toAttrFrTyp n TransitionFilter_Subtype_VerticalBottomLeftOpposite = Just (n, str2attr "verticalBottomLeftOpposite") - toAttrFrTyp n TransitionFilter_Subtype_VerticalBottomSame = Just (n, str2attr "verticalBottomSame") - toAttrFrTyp n TransitionFilter_Subtype_VerticalLeft = Just (n, str2attr "verticalLeft") - toAttrFrTyp n TransitionFilter_Subtype_VerticalRight = Just (n, str2attr "verticalRight") - toAttrFrTyp n TransitionFilter_Subtype_VerticalTopLeftOpposite = Just (n, str2attr "verticalTopLeftOpposite") - toAttrFrTyp n TransitionFilter_Subtype_VerticalTopSame = Just (n, str2attr "verticalTopSame") -instance XmlAttrType TransitionFilter_Coordinated where - fromAttrToTyp n (n',v) - | n==n' = translate (attr2str v) - | otherwise = Nothing - where translate "true" = Just TransitionFilter_Coordinated_True - translate "false" = Just TransitionFilter_Coordinated_False - translate _ = Nothing - toAttrFrTyp n TransitionFilter_Coordinated_True = Just (n, str2attr "true") - toAttrFrTyp n TransitionFilter_Coordinated_False = Just (n, str2attr "false") -instance XmlAttrType TransitionFilter_ClibBoundary where - fromAttrToTyp n (n',v) - | n==n' = translate (attr2str v) - | otherwise = Nothing - where translate "parent" = Just TransitionFilter_ClibBoundary_Parent - translate "children" = Just TransitionFilter_ClibBoundary_Children - translate _ = Nothing - toAttrFrTyp n TransitionFilter_ClibBoundary_Parent = Just (n, str2attr "parent") - toAttrFrTyp n TransitionFilter_ClibBoundary_Children = Just (n, str2attr "children") -instance XmlAttrType TransitionFilter_CalcMode where - fromAttrToTyp n (n',v) - | n==n' = translate (attr2str v) - | otherwise = Nothing - where translate "discrete" = Just TransitionFilter_CalcMode_Discrete - translate "linear" = Just TransitionFilter_CalcMode_Linear - translate "paced" = Just TransitionFilter_CalcMode_Paced - translate _ = Nothing - toAttrFrTyp n TransitionFilter_CalcMode_Discrete = Just (n, str2attr "discrete") - toAttrFrTyp n TransitionFilter_CalcMode_Linear = Just (n, str2attr "linear") - toAttrFrTyp n TransitionFilter_CalcMode_Paced = Just (n, str2attr "paced") - - -{-Done-} rmfile ./examples/SMIL/DTD_SMIL20.hs hunk ./examples/SMIL/SMIL-anim.mod 1 -<!-- ======================================================================= --> -<!-- SMIL Animation Module ================================================ --> -<!-- file: SMIL-anim.mod - - This is SMIL 2.0. - Copyright 2000 W3C (MIT, INRIA, Keio), All Rights Reserved. - - Author: Patrick Schmitz, Ken Day, Jacco van Ossenbruggen - Revision: $Id: SMIL-anim.mod,v 1.1.1.1 2002/03/19 12:29:23 malcolm Exp $ - - This DTD module is identified by the PUBLIC and SYSTEM identifiers: - - PUBLIC "-//W3C//ELEMENTS SMIL 2.0 Animation//EN" - SYSTEM "SMIL-anim.mod" - - ======================================================================= --> - - -<!-- ============================= Dependencies ============================ --> -<!-- The integrating profile is expected to define the following entities, - Unless the defaults provided are sufficient. - --> - -<!-- SplineAnimation.module entity: Define as "INCLUDE" if the integrating - profile includes the SMIL 2.0 SplineAnimation Module, "IGNORE" if not. - The default is "IGNORE", i.e. by default SplineAnimation is not included - in the integrating language profile. - --> -<!ENTITY % SplineAnimation.module "IGNORE"> - -<!-- Animation depends on SMIL Timing, importing the attributes listed - in the AnimationTime.attrib entity. If the integrating profile does - include the MinMaxTiming.module, its default value includes the - attributes defined in BasicInlineTiming.attrib and inMaxTiming.attrib. - Otherwise, it is defaulted to BasicInlineTiming.attrib, which is the - minimum requirement. - - Note that the profile can override these defaults by redefining - AnimationTime.attrib. The profile is also expected to define - Fill.attrib. - --> -<!ENTITY % MinMaxTiming.module "IGNORE"> -<![%MinMaxTiming.module;[ - <!ENTITY % AnimationTime.attrib " - %BasicInlineTiming.attrib; - %MinMaxTiming.attrib; - "> -]]> -<!ENTITY % AnimationTime.attrib "%BasicInlineTiming.attrib;"> -<!ENTITY % Fill.attrib ""> - -<!ENTITY % animTimingAttrs " - %AnimationTime.attrib; - %Fill.attrib; -"> - -<!-- Language Designer chooses to integrate targetElement or xlink attributes. - To integrate the targetElement attribute, define the entity - animation-targetElement as "INCLUDE"; to integrate the XLink attributes, - define animation-XLinkTarget as "INCLUDE". - - One or the other MUST be defined. It is strongly recommended that only one - of the two be defined. ---> - -<!ENTITY % animation-targetElement "IGNORE"> -<![%animation-targetElement;[ - <!ENTITY % animTargetElementAttr - "targetElement IDREF #IMPLIED" - > -]]> -<!ENTITY % animTargetElementAttr ""> - -<!ENTITY % animation-XLinkTarget "IGNORE"> -<![%animation-XLinkTarget;[ - <!ENTITY % animTargetElementXLink " - actuate (onRequest|onLoad) 'onLoad' - href %URI; #IMPLIED - show (new | embed | replace) #FIXED 'embed' - type (simple | extended | locator | arc) #FIXED 'simple' -"> -]]> -<!ENTITY % animTargetElementXLink ""> - - -<!-- ========================== Attribute Groups =========================== --> - -<!-- All animation elements include these attributes --> -<!ENTITY % animAttrsCommon - "%Core.attrib; - %I18n.attrib; - %System.attrib; - %animTimingAttrs; - %animTargetElementAttr; - %animTargetElementXLink;" -> - -<!-- All except animateMotion need an identified target attribute --> -<!ENTITY % animAttrsNamedTarget - "%animAttrsCommon; - attributeName CDATA #REQUIRED - attributeType CDATA #IMPLIED" -> - -<!-- All except set support the full animation-function specification, - additive and cumulative animation. - SplineAnimation adds the attributes keyTimes, keySplines and path, - and the calcMode value "spline", to those of BasicAnimation. - --> -<![%SplineAnimation.module;[ - <!ENTITY % splineAnimCalcModeValues "| spline"> - <!ENTITY % splineAnimValueAttrs - "keyTimes CDATA #IMPLIED - keySplines CDATA #IMPLIED" - > - <!ENTITY % splineAnimPathAttr - "path CDATA #IMPLIED" - > -]]> -<!ENTITY % splineAnimCalcModeValues ""> -<!ENTITY % splineAnimValueAttrs ""> -<!ENTITY % splineAnimPathAttr ""> - -<!ENTITY % animValueAttrs " - %BasicAnimation.attrib; - calcMode (discrete|linear|paced %splineAnimCalcModeValues;) 'linear' - %splineAnimValueAttrs; - additive (replace | sum) 'replace' - accumulate (none | sum) 'none'" -> - - -<!-- ========================== Animation Elements ========================= --> - -<!ENTITY % animate.attrib ""> -<!ENTITY % animate.content "EMPTY"> -<!ENTITY % animate.qname "animate"> -<!ELEMENT %animate.qname; %animate.content;> -<!ATTLIST %animate.qname; %animate.attrib; - %animAttrsNamedTarget; - %animValueAttrs; -> - -<!ENTITY % set.attrib ""> -<!ENTITY % set.content "EMPTY"> -<!ENTITY % set.qname "set"> -<!ELEMENT %set.qname; %set.content;> -<!ATTLIST %set.qname; %set.attrib; - %animAttrsNamedTarget; - to CDATA #IMPLIED -> - -<!ENTITY % animateMotion.attrib ""> -<!ENTITY % animateMotion.content "EMPTY"> -<!ENTITY % animateMotion.qname "animateMotion"> -<!ELEMENT %animateMotion.qname; %animateMotion.content;> -<!ATTLIST %animateMotion.qname; %animateMotion.attrib; - %animAttrsCommon; - %animValueAttrs; - %splineAnimPathAttr; - origin (default) "default" -> - - -<!ENTITY % animateColor.attrib ""> -<!ENTITY % animateColor.content "EMPTY"> -<!ENTITY % animateColor.qname "animateColor"> -<!ELEMENT %animateColor.qname; %animateColor.content;> -<!ATTLIST %animateColor.qname; %animateColor.attrib; - %animAttrsNamedTarget; - %animValueAttrs; -> - -<!-- ========================== End Animation ============================= --> -<!-- end of SMIL-anim.mod --> rmfile ./examples/SMIL/SMIL-anim.mod hunk ./examples/SMIL/SMIL-control.mod 1 -<!-- ================================================================= --> -<!-- SMIL Content Control Module ==================================== --> -<!-- file: SMIL-control.mod - - This is SMIL 2.0. - Copyright 2000 W3C (MIT, INRIA, Keio), All Rights Reserved. - - Author: Jacco van Ossenbruggen, Aaron Cohen - Revision: $Id: SMIL-control.mod,v 1.1.1.1 2002/03/19 12:29:23 malcolm Exp $ - - This DTD module is identified by the PUBLIC and SYSTEM identifiers: - - PUBLIC "-//W3C//ELEMENTS SMIL 2.0 Content Control//EN" - SYSTEM "SMIL-control.mod" - - ================================================================= --> - -<!ENTITY % BasicContentControl.module "INCLUDE"> -<![%BasicContentControl.module;[ - <!ENTITY % switch.attrib ""> - <!ENTITY % switch.content "EMPTY"> - <!ENTITY % switch.qname "switch"> - - <!ELEMENT %switch.qname; %switch.content;> - <!ATTLIST %switch.qname; %switch.attrib; - %Core.attrib; - %I18n.attrib; - > -]]> - -<!-- ========================= CustomTest Elements ========================= --> -<!ENTITY % CustomTestAttributes.module "IGNORE"> -<![%CustomTestAttributes.module;[ - - <!ENTITY % customTest.attrib ""> - <!ENTITY % customTest.qname "customTest"> - <!ENTITY % customTest.content "EMPTY"> - <!ELEMENT %customTest.qname; %customTest.content;> - <!ATTLIST %customTest.qname; %customTest.attrib; - defaultState (true|false) 'false' - override (allowed|not-allowed) 'not-allowed' - uid %URI; #IMPLIED - %Core.attrib; - %I18n.attrib; - > - <!ENTITY % customAttributes.attrib ""> - <!ENTITY % customAttributes.qname "customAttributes"> - <!ENTITY % customAttributes.content "EMPTY"> - <!ELEMENT %customAttributes.qname; %customAttributes.content;> - <!ATTLIST %customAttributes.qname; %customAttributes.attrib; - %Core.attrib; - %I18n.attrib; - > - -]]> <!-- end of CustomTestAttributes --> - -<!-- ========================= PrefetchControl Elements ==================== --> -<!ENTITY % PrefetchControl.module "IGNORE"> -<![%PrefetchControl.module;[ - <!ENTITY % prefetch.attrib ""> - <!ENTITY % prefetch.qname "prefetch"> - <!ENTITY % prefetch.content "EMPTY"> - <!ELEMENT %prefetch.qname; %prefetch.content;> - <!ATTLIST %prefetch.qname; %prefetch.attrib; - mediaSize CDATA #IMPLIED - mediaTime CDATA #IMPLIED - bandwidth CDATA #IMPLIED - %Core.attrib; - %I18n.attrib; - > -]]> rmfile ./examples/SMIL/SMIL-control.mod hunk ./examples/SMIL/SMIL-layout.mod 1 -<!-- ======================================================================= --> -<!-- SMIL 2.0 Layout Modules =============================================== --> -<!-- file: SMIL-layout.mod - - This is SMIL 2.0. - Copyright 2000 W3C (MIT, INRIA, Keio), All Rights Reserved. - - Authors: Jacco van Ossenbruggen, Aaron Cohen - Revision: $Id: SMIL-layout.mod,v 1.1.1.1 2002/03/19 12:29:24 malcolm Exp $ - - This DTD module is identified by the PUBLIC and SYSTEM identifiers: - - PUBLIC "-//W3C//ELEMENTS SMIL 2.0 Layout//EN" - SYSTEM "SMIL-layout.mod" - - ==================================================================== --> - -<!-- ================== BasicLayout ======================================== --> -<!-- ================== BasicLayout Profiling Entities ===================== --> -<!ENTITY % layout.attrib ""> -<!ENTITY % region.attrib ""> -<!ENTITY % rootlayout.attrib ""> -<!ENTITY % layout.content "EMPTY"> -<!ENTITY % region.content "EMPTY"> -<!ENTITY % rootlayout.content "EMPTY"> - -<!-- ================== BasicLayout Entities =============================== --> -<!ENTITY % viewport-attrs " - height CDATA 'auto' - width CDATA 'auto' - close (never|whenNotActive) 'never' - open (always|whenActive) 'always' - %BackgroundColor.attrib; - %BackgroundColor-deprecated.attrib; -"> - -<!ENTITY % region-attrs " - bottom CDATA 'auto' - left CDATA 'auto' - right CDATA 'auto' - top CDATA 'auto' - z-index CDATA #IMPLIED - showBackground (always|whenActive) 'always' - %Fit.attrib; -"> - -<!-- ================== BasicLayout Elements =============================== --> -<!-- - Layout contains the region and root-layout elements defined by - smil-basic-layout or other elements defined an external layout - mechanism. ---> - -<!ENTITY % layout.qname "layout"> -<!ELEMENT %layout.qname; %layout.content;> -<!ATTLIST %layout.qname; %layout.attrib; - %Core.attrib; - %I18n.attrib; - type CDATA 'text/smil-basic-layout' -> - -<!-- ================== Region Element ======================================--> -<!ENTITY % region.qname "region"> -<!ELEMENT %region.qname; %region.content;> -<!ATTLIST %region.qname; %region.attrib; - %Core.attrib; - %I18n.attrib; - %viewport-attrs; - %region-attrs; -> - -<!-- ================== Root-layout Element =================================--> -<!ENTITY % root-layout.qname "root-layout"> -<!ELEMENT %root-layout.qname; %rootlayout.content; > -<!ATTLIST %root-layout.qname; %rootlayout.attrib; - %Core.attrib; - %I18n.attrib; - %viewport-attrs; -> - - -<!-- ================== AudioLayout ======================================== --> -<!ENTITY % AudioLayout.module "IGNORE"> -<![%AudioLayout.module;[ - <!-- ================== AudioLayout Entities ============================= --> - <!ENTITY % audio-attrs " - soundLevel CDATA '100%' - "> - - <!-- ================ AudioLayout Elements =============================== --> - <!-- ================ Add soundLevel to region element =================== --> - <!ATTLIST %region.qname; %audio-attrs;> -]]> <!-- end AudioLayout.module --> - - -<!-- ================ MultiWindowLayout ==================================== --> -<!ENTITY % MultiWindowLayout.module "IGNORE"> -<![%MultiWindowLayout.module;[ - <!-- ============== MultiWindowLayout Profiling Entities ================= --> - <!ENTITY % viewport.attrib ""> - <!ENTITY % viewport.content "EMPTY"> - - <!-- ============== MultiWindowLayout Elements =========================== --> - <!--================= viewport element =================================== --> - <!ENTITY % viewport.qname "viewport"> - <!ELEMENT %viewport.qname; %viewport.content;> - <!ATTLIST %viewport.qname; %viewport.attrib; - %Core.attrib; - %I18n.attrib; - %viewport-attrs; - > -]]> <!-- end MultiWindowLayout.module --> - - -<!-- ====================== HierarchicalLayout ============================= --> -<!ENTITY % HierarchicalLayout.module "IGNORE"> -<![%HierarchicalLayout.module;[ - <!-- ========== HierarchicalLayout Profiling Entities ==================== --> - <!ENTITY % regPoint.attrib ""> - <!ENTITY % regPoint.content "EMPTY"> - - <!-- ============ HierarchicalLayout Elements ============================ --> - <!ENTITY % regPoint.qname "regPoint"> - <!ELEMENT %regPoint.qname; %regPoint.content;> - <!ATTLIST %regPoint.qname; %regPoint.attrib; - %Core.attrib; - %I18n.attrib; - %Sub-region.attrib; - %RegistrationPoint.attrib; - > -]]> <!-- end HierarchicalLayout.module --> - - -<!-- end of SMIL-layout.mod --> rmfile ./examples/SMIL/SMIL-layout.mod hunk ./examples/SMIL/SMIL-link.mod 1 -<!-- ======================================================================= --> -<!-- SMIL Linking Module ================================================== --> -<!-- file: SMIL-link.mod - - This is SMIL 2.0. - Copyright 2000 W3C (MIT, INRIA, Keio), All Rights Reserved. - - Author: Jacco van Ossenbruggen, Lloyd Rutledge, Aaron Cohen - Revision: $Id: SMIL-link.mod,v 1.1.1.1 2002/03/19 12:29:24 malcolm Exp $ - - This DTD module is identified by the PUBLIC and SYSTEM identifiers: - - PUBLIC "-//W3C//ELEMENTS SMIL 2.0 Linking//EN" - SYSTEM "SMIL-link.mod" - - ======================================================================= --> - -<!-- ======================== LinkingAttributes Entities =================== --> -<!ENTITY % linking-attrs " - sourceLevel CDATA '100%' - destinationLevel CDATA '100%' - sourcePlaystate (play|pause|stop) #IMPLIED - destinationPlaystate (play|pause|stop) 'play' - show (new|pause|replace) 'replace' - accesskey CDATA #IMPLIED - tabindex CDATA #IMPLIED - target CDATA #IMPLIED - external (true|false) 'false' - actuate (onRequest|onLoad) 'onRequest' -"> - - - -<!-- ========================= BasicLinking Elements ======================= --> -<!ENTITY % BasicLinking.module "IGNORE"> -<![%BasicLinking.module;[ - - <!-- ======================= BasicLinking Entities ======================= --> - <!ENTITY % Shape "(rect|circle|poly|default)"> - <!ENTITY % Coords "CDATA"> - <!-- comma separated list of lengths --> - - <!ENTITY % a.attrib ""> - <!ENTITY % a.content "EMPTY"> - <!ENTITY % a.qname "a"> - <!ELEMENT %a.qname; %a.content;> - <!ATTLIST %a.qname; %a.attrib; - %linking-attrs; - href %URI; #IMPLIED - %Core.attrib; - %I18n.attrib; - > - - <!ENTITY % area.attrib ""> - <!ENTITY % area.content "EMPTY"> - <!ENTITY % area.qname "area"> - <!ELEMENT %area.qname; %area.content;> - <!ATTLIST %area.qname; %area.attrib; - %linking-attrs; - shape %Shape; 'rect' - coords %Coords; #IMPLIED - href %URI; #IMPLIED - nohref (nohref) #IMPLIED - alt %Text; #IMPLIED - %Core.attrib; - %I18n.attrib; - > - - <!ENTITY % anchor.attrib ""> - <!ENTITY % anchor.content "EMPTY"> - <!ENTITY % anchor.qname "anchor"> - <!ELEMENT %anchor.qname; %anchor.content;> - <!ATTLIST %anchor.qname; %area.attrib; - %linking-attrs; - shape %Shape; 'rect' - coords %Coords; #IMPLIED - href %URI; #IMPLIED - nohref (nohref) #IMPLIED - alt %Text; #IMPLIED - %Core.attrib; - %I18n.attrib; - > -]]> <!-- end of BasicLinking --> - -<!-- ======================== ObjectLinking ================================ --> -<!ENTITY % ObjectLinking.module "IGNORE"> -<![%ObjectLinking.module;[ - - <!ENTITY % Fragment " - fragment CDATA #IMPLIED - "> - - <!-- ====================== ObjectLinking Elements ======================= --> - <!-- add fragment attribute to area, and anchor elements --> - <!ATTLIST %area.qname; - %Fragment; - > - - <!ATTLIST %anchor.qname; - %Fragment; - > -]]> -<!-- ======================== End ObjectLinking ============================ --> - -<!-- end of SMIL-link.mod --> rmfile ./examples/SMIL/SMIL-link.mod hunk ./examples/SMIL/SMIL-media.mod 1 -<!-- ======================================================================= --> -<!-- SMIL 2.0 Media Objects Modules ======================================== --> -<!-- file: SMIL-media.mod - - This is SMIL 2.0. - Copyright 2000 W3C (MIT, INRIA, Keio), All Rights Reserved. - - Author: Rob Lanphier, Jacco van Ossenbruggen - Revision: $Id: SMIL-media.mod,v 1.1.1.1 2002/03/19 12:29:24 malcolm Exp $ - - This DTD module is identified by the PUBLIC and SYSTEM identifiers: - - PUBLIC "-//W3C//ELEMENTS SMIL 2.0 Media Objects//EN" - SYSTEM "SMIL-media.mod" - - ======================================================================= --> - -<!-- ================== Profiling Entities ================================= --> - -<!ENTITY % BasicMedia.module "INCLUDE"> -<![%BasicMedia.module;[ - <!ENTITY % media-object.content "EMPTY"> - <!ENTITY % media-object.attrib ""> - - <!-- ================ Media Objects Entities ============================= --> - - <!ENTITY % mo-attributes-BasicMedia " - abstract CDATA #IMPLIED - alt CDATA #IMPLIED - author CDATA #IMPLIED - copyright CDATA #IMPLIED - longdesc CDATA #IMPLIED - src CDATA #IMPLIED - type CDATA #IMPLIED - "> -]]> -<!ENTITY % mo-attributes-BasicMedia ""> - - -<!ENTITY % MediaClipping.module "IGNORE"> -<![%MediaClipping.module;[ - <!ENTITY % mo-attributes-MediaClipping " - clipBegin CDATA #IMPLIED - clipEnd CDATA #IMPLIED - "> -]]> -<!ENTITY % mo-attributes-MediaClipping ""> - -<!ENTITY % MediaClipping.deprecated.module "IGNORE"> -<![%MediaClipping.module;[ - <!ENTITY % mo-attributes-MediaClipping-deprecated " - clip-begin CDATA #IMPLIED - clip-end CDATA #IMPLIED - "> - ]]> -<!ENTITY % mo-attributes-MediaClipping-deprecated ""> - -<!ENTITY % MediaParam.module "IGNORE"> -<![%MediaParam.module;[ - <!ENTITY % mo-attributes-MediaParam " - erase (whenDone|never) 'whenDone' - mediaRepeat (preserve|strip) 'preserve' - "> -]]> -<!ENTITY % mo-attributes-MediaParam ""> - -<!ENTITY % MediaAccessibility.module "IGNORE"> -<![%MediaAccessibility.module;[ - <!ENTITY % mo-attributes-MediaAccessibility " - readIndex CDATA #IMPLIED - "> -]]> -<!ENTITY % mo-attributes-MediaAccessibility ""> - - -<!ENTITY % mo-attributes " - %Core.attrib; - %I18n.attrib; - %mo-attributes-BasicMedia; - %mo-attributes-MediaParam; - %mo-attributes-MediaAccessibility; - %media-object.attrib; -"> - -<!-- - Most info is in the attributes, media objects are empty or - have children defined at the language integration level: ---> - -<!ENTITY % mo-content "%media-object.content;"> - -<!-- ================== Media Objects Elements ============================= --> -<!-- BasicMedia --> -<!ENTITY % ref.qname "ref"> -<!ENTITY % audio.qname "audio"> -<!ENTITY % img.qname "img"> -<!ENTITY % video.qname "video"> -<!ENTITY % text.qname "text"> -<!ENTITY % textstream.qname "textstream"> -<!ENTITY % animation.qname "animation"> - -<!ENTITY % ref.content "%mo-content;"> -<!ENTITY % audio.content "%mo-content;"> -<!ENTITY % img.content "%mo-content;"> -<!ENTITY % video.content "%mo-content;"> -<!ENTITY % text.content "%mo-content;"> -<!ENTITY % textstream.content "%mo-content;"> -<!ENTITY % animation.content "%mo-content;"> - -<!ELEMENT %ref.qname; %ref.content;> -<!ELEMENT %audio.qname; %audio.content;> -<!ELEMENT %img.qname; %img.content;> -<!ELEMENT %video.qname; %video.content;> -<!ELEMENT %text.qname; %text.content;> -<!ELEMENT %textstream.qname; %textstream.content;> -<!ELEMENT %animation.qname; %animation.content;> - -<!ATTLIST %img.qname; - %mo-attributes; -> -<!ATTLIST %text.qname; - %mo-attributes; -> -<!ATTLIST %ref.qname; - %mo-attributes-MediaClipping; - %mo-attributes-MediaClipping-deprecated; - %mo-attributes; -> -<!ATTLIST %audio.qname; - %mo-attributes-MediaClipping; - %mo-attributes-MediaClipping-deprecated; - %mo-attributes; -> -<!ATTLIST %video.qname; - %mo-attributes-MediaClipping; - %mo-attributes-MediaClipping-deprecated; - %mo-attributes; -> -<!ATTLIST %textstream.qname; - %mo-attributes-MediaClipping; - %mo-attributes-MediaClipping-deprecated; - %mo-attributes; -> -<!ATTLIST %animation.qname; - %mo-attributes-MediaClipping; - %mo-attributes-MediaClipping-deprecated; - %mo-attributes; -> - -<!-- MediaParam --> -<![%MediaParam.module;[ - - <!ENTITY % param.qname "param"> - <!ELEMENT %param.qname; EMPTY> - - <!ATTLIST %param.qname; - %Core.attrib; - %I18n.attrib; - name CDATA #IMPLIED - value CDATA #IMPLIED - valuetype (data|ref|object) "data" - type %ContentType; #IMPLIED - > -]]> - -<!-- BrushMedia --> -<!ENTITY % BrushMedia.module "IGNORE"> -<![%BrushMedia.module;[ - <!ENTITY % brush.attrib ""> - <!ENTITY % brush.content "%mo-content;"> - <!ENTITY % brush.qname "brush"> - <!ELEMENT %brush.qname; %brush.content;> - <!ATTLIST %brush.qname; %brush.attrib; - %mo-attributes; - color CDATA #IMPLIED - > -]]> - -<!-- end of SMIL-media.mod --> rmfile ./examples/SMIL/SMIL-media.mod hunk ./examples/SMIL/SMIL-metainformation.mod 1 -<!-- ================================================================ --> -<!-- SMIL Metainformation Module =================================== --> -<!-- file: SMIL-metainformation.mod - - This is SMIL 2.0. - Copyright 2000 W3C (MIT, INRIA, Keio), All Rights Reserved. - - This module declares the meta and metadata elements types and - its attributes, used to provide declarative document metainformation. - - Author: Thierry Michel, Jacco van Ossenbruggen - Revision: $Id: SMIL-metainformation.mod,v 1.1.1.1 2002/03/19 12:29:24 malcolm Exp $ - - This DTD module is identified by the PUBLIC and SYSTEM identifiers: - - PUBLIC "-//W3C//ELEMENTS SMIL 2.0 Document Metadata//EN" - SYSTEM "SMIL-metainformation.mod" - - ================================================================ --> - - -<!-- ================== Profiling Entities ========================== --> - -<!ENTITY % meta.content "EMPTY"> -<!ENTITY % meta.attrib ""> -<!ENTITY % meta.qname "meta"> - -<!ENTITY % metadata.content "EMPTY"> -<!ENTITY % metadata.attrib ""> -<!ENTITY % metadata.qname "metadata"> - -<!-- ================== meta element ================================ --> - -<!ELEMENT %meta.qname; %meta.content;> -<!ATTLIST %meta.qname; %meta.attrib; - content CDATA #IMPLIED - name CDATA #REQUIRED - > - -<!-- ================== metadata element ============================ --> - -<!ELEMENT %metadata.qname; %metadata.content;> -<!ATTLIST %metadata.qname; %metadata.attrib; - %Core.attrib; - %I18n.attrib; -> - -<!-- end of SMIL-metadata.mod --> rmfile ./examples/SMIL/SMIL-metainformation.mod hunk ./examples/SMIL/SMIL-struct.mod 1 -<!-- ====================================================================== --> -<!-- SMIL Structure Module =============================================== --> -<!-- file: SMIL-struct.mod - - This is SMIL 2.0. - Copyright 2000 W3C (MIT, INRIA, Keio), All Rights Reserved. - - This DTD module is identified by the PUBLIC and SYSTEM identifiers: - - PUBLIC "-//W3C//ELEMENTS SMIL 2.0 Document Structure//EN" - SYSTEM "SMIL-struct.mod" - - Author: Warner ten Kate, Jacco van Ossenbruggen - Revision: $Id: SMIL-struct.mod,v 1.1.1.1 2002/03/19 12:29:24 malcolm Exp $ - - ===================================================================== --> - -<!-- ================== SMIL Document Root =============================== --> -<!ENTITY % smil.attrib "" > -<!ENTITY % smil.content "EMPTY" > -<!ENTITY % smil.qname "smil" > - -<!ELEMENT %smil.qname; %smil.content;> -<!ATTLIST %smil.qname; %smil.attrib; - %Core.attrib; - %I18n.attrib; - xmlns %URI; #FIXED %SMIL.ns; -> - -<!-- ================== The Document Head ================================ --> -<!ENTITY % head.content "EMPTY" > -<!ENTITY % head.attrib "" > -<!ENTITY % head.qname "head" > - -<!ELEMENT %head.qname; %head.content;> -<!ATTLIST %head.qname; %head.attrib; - %Core.attrib; - %I18n.attrib; -> - -<!--=================== The Document Body - Timing Root ================== --> -<!ENTITY % body.content "EMPTY" > -<!ENTITY % body.attrib "" > -<!ENTITY % body.qname "body" > - -<!ELEMENT %body.qname; %body.content;> -<!ATTLIST %body.qname; %body.attrib; - %Core.attrib; - %I18n.attrib; -> -<!-- end of SMIL-struct.mod --> rmfile ./examples/SMIL/SMIL-struct.mod hunk ./examples/SMIL/SMIL-timing.mod 1 -<!-- ================================================================= --> -<!-- SMIL Timing and Synchronization Modules ========================= --> -<!-- file: SMIL-timing.mod - - This is SMIL 2.0. - Copyright 2000 W3C (MIT, INRIA, Keio), All Rights Reserved. - - Author: Jacco van Ossenbruggen. - Revision: $Id: SMIL-timing.mod,v 1.1.1.1 2002/03/19 12:29:24 malcolm Exp $ - - This DTD module is identified by the PUBLIC and SYSTEM identifiers: - - PUBLIC "-//W3C//ELEMENTS SMIL 2.0 Timing//EN" - SYSTEM "SMIL-timing.mod" - - ================================================================= --> - - -<!-- ================== Timing Elements ============================== --> - -<!ENTITY % BasicTimeContainers.module "IGNORE"> -<![%BasicTimeContainers.module;[ - <!ENTITY % par.content "EMPTY"> - <!ENTITY % seq.content "EMPTY"> - <!ENTITY % par.attrib ""> - <!ENTITY % seq.attrib ""> - <!ENTITY % seq.qname "seq"> - <!ENTITY % par.qname "par"> - - <!ENTITY % description.attrib " - abstract CDATA #IMPLIED - author CDATA #IMPLIED - copyright CDATA #IMPLIED - "> - - <!ELEMENT %seq.qname; %seq.content;> - <!ATTLIST %seq.qname; %seq.attrib; - %Core.attrib; - %I18n.attrib; - %description.attrib; - > - - <!ELEMENT %par.qname; %par.content;> - <!ATTLIST %par.qname; %par.attrib; - %Core.attrib; - %I18n.attrib; - %description.attrib; - > -]]> <!-- End of BasicTimeContainers.module --> - - -<!ENTITY % ExclTimeContainers.module "IGNORE"> -<![%ExclTimeContainers.module;[ - <!ENTITY % excl.content "EMPTY"> - <!ENTITY % priorityClass.content "EMPTY"> - <!ENTITY % excl.attrib ""> - <!ENTITY % priorityClass.attrib ""> - <!ENTITY % excl.qname "excl"> - <!ENTITY % priorityClass.qname "priorityClass"> - - <!ELEMENT %excl.qname; %excl.content;> - <!ATTLIST %excl.qname; %excl.attrib; - %Core.attrib; - %I18n.attrib; - %description.attrib; - > - - <!ELEMENT %priorityClass.qname; %priorityClass.content;> - <!ATTLIST %priorityClass.qname; %priorityClass.attrib; - peers (stop|pause|defer|never) "stop" - higher (stop|pause) "pause" - lower (defer|never) "defer" - pauseDisplay (disable|hide|show ) "show" - %description.attrib; - %Core.attrib; - %I18n.attrib; - > -]]> <!-- End of ExclTimeContainers.module --> - -<!-- end of SMIL-timing.mod --> rmfile ./examples/SMIL/SMIL-timing.mod hunk ./examples/SMIL/SMIL-transition.mod 1 -<!-- ====================================================================== --> -<!-- SMIL Transition Module ============================================== --> -<!-- file: SMIL-transition.mod - - This is SMIL 2.0 - Copyright 2000 W3C (MIT, INRIA, Keio), All Rights Reserved. - - Revision: $Id: SMIL-transition.mod,v 1.1.1.1 2002/03/19 12:29:24 malcolm Exp $ - - This DTD module is identified by the PUBLIC and SYSTEM identifiers: - - PUBLIC "-//W3C//ELEMENTS SMIL 2.0 Transition//EN" - SYSTEM "SMIL-transition.mod" - - - - ====================================================================== --> - -<!ENTITY % transition-types "(barWipe|boxWipe|fourBoxWipe|barnDoorWipe| -diagonalWipe|bowTieWipe|miscDiagonalWipe|veeWipe|barnVeeWipe|zigZagWipe| -barnZigZagWipe|miscShapeWipe|triangleWipe|arrowHeadWipe|pentagonWipe| -hexagonWipe|ellipseWipe|eyeWipe|roundRectWipe|starWipe|clockWipe| -pinWheelWipe|singleSweepWipe|fanWipe|doubleFanWipe|doubleSweepWipe| -saloonDoorWipe|windshieldWipe|snakeWipe|spiralWipe|parallelSnakesWipe| -boxSnakesWipe|waterfallWipe|pushWipe|slideWipe|fade)" -> - -<!ENTITY % transition-subtypes "(bottom -|bottomCenter|bottomLeft|bottomLeftClockwise|bottomLeftCounterClockwise| -bottomLeftDiagonal|bottomRight|bottomRightClockwise| -bottomRightCounterClockwise|bottomRightDiagonal|centerRight|centerTop| -circle|clockwiseBottom|clockwiseBottomRight|clockwiseLeft|clockwiseNine| -clockwiseRight|clockwiseSix|clockwiseThree|clockwiseTop|clockwiseTopLeft| -clockwiseTwelve|cornersIn|cornersOut|counterClockwiseBottomLeft| -counterClockwiseTopRight|crossfade|diagonalBottomLeft| -diagonalBottomLeftOpposite|diagonalTopLeft|diagonalTopLeftOpposite| -diamond|doubleBarnDoor|doubleDiamond|down|fadeFromColor|fadeToColor| -fanInHorizontal|fanInVertical|fanOutHorizontal|fanOutVertical|fivePoint| -fourBlade|fourBoxHorizontal|fourBoxVertical|fourPoint|fromBottom|fromLeft| -fromRight|fromTop|heart|horizontal|horizontalLeft|horizontalLeftSame| -horizontalRight|horizontalRightSame|horizontalTopLeftOpposite| -horizontalTopRightOpposite|keyhole|left|leftCenter|leftToRight| -oppositeHorizontal|oppositeVertical|parallelDiagonal| -parallelDiagonalBottomLeft|parallelDiagonalTopLeft| -parallelVertical|rectangle|right|rightCenter|sixPoint|top|topCenter| -topLeft|topLeftClockwise|topLeftCounterClockwise|topLeftDiagonal| -topLeftHorizontal|topLeftVertical|topRight|topRightClockwise| -topRightCounterClockwise|topRightDiagonal|topToBottom|twoBladeHorizontal| -twoBladeVertical|twoBoxBottom|twoBoxLeft|twoBoxRight|twoBoxTop|up| -vertical|verticalBottomLeftOpposite|verticalBottomSame|verticalLeft| -verticalRight|verticalTopLeftOpposite|verticalTopSame)" -> - - -<!ENTITY % transition-attrs ' - type %transition-types; #IMPLIED - subtype %transition-subtypes; #IMPLIED - horzRepeat CDATA "0" - vertRepeat CDATA "0" - borderWidth CDATA "0" - borderColor CDATA "black" - fadeColor CDATA "black" - coordinated (true|false) "false" - clibBoundary (parent|children) "children" -'> - -<!ENTITY % transition.attrib ""> -<!ENTITY % transition.content "EMPTY"> -<!ENTITY % transition.qname "transition"> -<!ELEMENT %transition.qname; %transition.content;> -<!ATTLIST %transition.qname; %transition.attrib; - %Core.attrib; - %I18n.attrib; - %transition-attrs; - dur CDATA #IMPLIED - startProgress CDATA "0.0" - endProgress CDATA "1.0" - direction (forward|reverse) "forward" -> - -<!ENTITY % transitionFilter.attrib ""> -<!ENTITY % transitionFilter.content "EMPTY"> -<!ENTITY % transitionFilter.qname "transitionFilter"> -<!ELEMENT %transitionFilter.qname; %transitionFilter.content;> -<!ATTLIST %transitionFilter.qname; %transitionFilter.attrib; - %Core.attrib; - %I18n.attrib; - %transition-attrs; - %BasicInlineTiming.attrib; - %BasicAnimation.attrib; - calcMode (discrete|linear|paced) 'linear' -> - -<!-- end of SMIL-transition.mod --> rmfile ./examples/SMIL/SMIL-transition.mod hunk ./examples/SMIL/SMIL20.dtd 1 -<!-- ....................................................................... --> -<!-- SMIL 2.0 DTD ......................................................... --> -<!-- file: SMIL20.dtd ---> -<!-- SMIL 2.0 DTD - - This is SMIL 2.0. - - Copyright 1998-2000 World Wide Web Consortium - (Massachusetts Institute of Technology, Institut National de - Recherche en Informatique et en Automatique, Keio University). - All Rights Reserved. - - Permission to use, copy, modify and distribute the SMIL 2.0 DTD and - its accompanying documentation for any purpose and without fee is - hereby granted in perpetuity, provided that the above copyright notice - and this paragraph appear in all copies. The copyright holders make - no representation about the suitability of the DTD for any purpose. - - It is provided "as is" without expressed or implied warranty. - - Author: Jacco van Ossenbruggen - Revision: $Id: SMIL20.dtd,v 1.1.1.1 2002/03/19 12:29:24 malcolm Exp $ - ---> -<!-- This is the driver file for the SMIL 2.0 DTD. - - Please use this formal public identifier to identify it: - - "-//W3C//DTD SMIL 2.0//EN" ---> - -<!ENTITY % NS.prefixed "IGNORE" > -<!ENTITY % SMIL.prefix "" > - -<!-- Define the Content Model --> -<!ENTITY % smil-model.mod - PUBLIC "-//W3C//ENTITIES SMIL 2.0 Document Model 1.0//EN" - "smil-model-1.mod" > - -<!-- Modular Framework Module ................................... --> -<!ENTITY % smil-framework.module "INCLUDE" > -<![%smil-framework.module;[ -<!ENTITY % smil-framework.mod - PUBLIC "-//W3C//ENTITIES SMIL 2.0 Modular Framework 1.0//EN" - "smil-framework-1.mod" > -%smil-framework.mod;]]> - -<!-- The SMIL 2.0 Profile includes the following sections: - C. The SMIL Animation Module - D. The SMIL Content Control Module - G. The SMIL Layout Module - H. The SMIL Linking Module - I. The SMIL Media Object Module - J. The SMIL Metainformation Module - K. The SMIL Structure Module - L. The SMIL Timing and Synchronization Module - M. Integrating SMIL Timing into other XML-Based Languages - P. The SMIL Transition effects Module - - The SMIL Streaming Media Object Module is optional. ---> - -<!ENTITY % streamingmedia.model "IGNORE"> -<![%streamingmedia.model;[ - <!ENTITY % streaming-mod - PUBLIC "-//W3C//ELEMENTS SMIL 2.0 Streaming Media Objects//EN" - "SMIL-streamingmedia.mod"> - %streaming-mod; -]]> - -<!ENTITY % anim-mod - PUBLIC "-//W3C//ELEMENTS SMIL 2.0 Animation//EN" - "SMIL-anim.mod"> -<!ENTITY % control-mod - PUBLIC "-//W3C//ELEMENTS SMIL 2.0 Content Control//EN" - "SMIL-control.mod"> -<!ENTITY % layout-mod - PUBLIC "-//W3C//ELEMENTS SMIL 2.0 Layout//EN" - "SMIL-layout.mod"> -<!ENTITY % link-mod - PUBLIC "-//W3C//ELEMENTS SMIL 2.0 Linking//EN" - "SMIL-link.mod"> -<!ENTITY % media-mod - PUBLIC "-//W3C//ELEMENTS SMIL 2.0 Media Objects//EN" - "SMIL-media.mod"> -<!ENTITY % meta-mod - PUBLIC "-//W3C//ELEMENTS SMIL 2.0 Document Metainformation//EN" - "SMIL-metainformation.mod"> -<!ENTITY % struct-mod - PUBLIC "-//W3C//ELEMENTS SMIL 2.0 Document Structure//EN" - "SMIL-struct.mod"> -<!ENTITY % timing-mod - PUBLIC "-//W3C//ELEMENTS SMIL 2.0 Timing//EN" - "SMIL-timing.mod"> -<!ENTITY % transition-mod - PUBLIC "-//W3C//ELEMENTS SMIL 2.0 Transition//EN" - "SMIL-transition.mod"> - -%struct-mod; -%anim-mod; -%control-mod; -%meta-mod; -%layout-mod; -%link-mod; -%media-mod; -%timing-mod; -%transition-mod; rmfile ./examples/SMIL/SMIL20.dtd hunk ./examples/SMIL/smil-attribs-1.mod 1 -<!-- ...................................................................... --> -<!-- SMIL 2.0 Common Attributes Module ................................... --> -<!-- file: smil-attribs-1.mod - - This is SMIL 2.0. - Copyright 1998-2000 W3C (MIT, INRIA, Keio), All Rights Reserved. - Revision: $Id: smil-attribs-1.mod,v 1.1.1.1 2002/03/19 12:29:24 malcolm Exp $ - - This DTD module is identified by the PUBLIC and SYSTEM identifiers: - - PUBLIC "-//W3C//ENTITIES SMIL 2.0 Common Attributes 1.0//EN" - SYSTEM "smil-attribs-1.mod" - - ...................................................................... --> - -<!-- Common Attributes - - This module declares the common attributes for the SMIL DTD Modules. ---> - -<!ENTITY % SMIL.pfx ""> - -<!ENTITY % Id.attrib - "%SMIL.pfx;id ID #IMPLIED" -> - -<!ENTITY % Class.attrib - "%SMIL.pfx;class CDATA #IMPLIED" -> - -<!ENTITY % Title.attrib - "%SMIL.pfx;title %Text; #IMPLIED" -> - -<!ENTITY % Core.extra.attrib "" > - -<!ENTITY % Core.attrib - "%Id.attrib; - %Class.attrib; - %Title.attrib; - %Core.extra.attrib;" -> - -<!ENTITY % I18n.extra.attrib "" > -<!ENTITY % I18n.attrib " - xml:lang %LanguageCode; #IMPLIED - %I18n.extra.attrib;" -> - -<!-- ================== BasicLayout ======================================= --> -<!ENTITY % Region.attrib " - %SMIL.pfx;region CDATA #IMPLIED -"> - -<!ENTITY % Fill.attrib " - %SMIL.pfx;fill (remove|freeze|hold|transition) #IMPLIED -"> - -<!-- ================== HierarchicalLayout ======================================= --> -<!ENTITY % BackgroundColor.attrib " - %SMIL.pfx;backgroundColor CDATA #IMPLIED -"> -<!ENTITY % BackgroundColor-deprecated.attrib " - %SMIL.pfx;background-color CDATA #IMPLIED -"> - -<!ENTITY % Sub-region.attrib " - %SMIL.pfx;top CDATA 'auto' - %SMIL.pfx;bottom CDATA 'auto' - %SMIL.pfx;left CDATA 'auto' - %SMIL.pfx;right CDATA 'auto' -"> - -<!ENTITY % Fit.attrib " - %SMIL.pfx;fit (hidden|fill|meet|scroll|slice) 'hidden' -"> - -<!-- ================ Registration Point attribute for media elements ============ --> -<!-- integrating language using HierarchicalLayout must include regPoint --> -<!-- attribute on media elements for regPoint elements to be useful --> - -<!ENTITY % RegistrationPoint.attrib " - %SMIL.pfx;regPoint CDATA #IMPLIED - %SMIL.pfx;regAlign (topLeft|topMid|topRight|midLeft|center| - midRight|bottomLeft|bottomMid|bottomRight) #IMPLIED -"> - -<!--=================== Content Control =======================--> -<!-- customTest Attribute --> -<!ENTITY % CustomTest.attrib " - %SMIL.pfx;customTest IDREF #IMPLIED -"> - -<!-- ========================= SkipContentControl Module ========================= --> -<!ENTITY % skipContent.attrib " - %SMIL.pfx;skip-content (true|false) 'true' -"> - -<!-- Switch Parameter Attributes --> - -<!ENTITY % System.attrib " - %CustomTest.attrib; - %SMIL.pfx;systemBitrate CDATA #IMPLIED - %SMIL.pfx;systemCaptions (on|off) #IMPLIED - %SMIL.pfx;systemLanguage CDATA #IMPLIED - %SMIL.pfx;systemOverdubOrSubtitle (overdub|subtitle) #IMPLIED - %SMIL.pfx;systemRequired NMTOKEN #IMPLIED - %SMIL.pfx;systemScreenSize CDATA #IMPLIED - %SMIL.pfx;systemScreenDepth CDATA #IMPLIED - %SMIL.pfx;systemAudioDesc (on|off) #IMPLIED - %SMIL.pfx;systemOperatingSystem NMTOKEN #IMPLIED - %SMIL.pfx;systemCPU NMTOKEN #IMPLIED - %SMIL.pfx;systemComponent CDATA #IMPLIED - - %SMIL.pfx;system-bitrate CDATA #IMPLIED - %SMIL.pfx;system-captions (on|off) #IMPLIED - %SMIL.pfx;system-language CDATA #IMPLIED - %SMIL.pfx;system-overdub-or-caption (overdub|caption) #IMPLIED - %SMIL.pfx;system-required NMTOKEN #IMPLIED - %SMIL.pfx;system-screen-size CDATA #IMPLIED - %SMIL.pfx;system-screen-depth CDATA #IMPLIED -"> - -<!-- SMIL Animation Module ================================================ --> -<!ENTITY % BasicAnimation.attrib " - %SMIL.pfx;values CDATA #IMPLIED - %SMIL.pfx;from CDATA #IMPLIED - %SMIL.pfx;to CDATA #IMPLIED - %SMIL.pfx;by CDATA #IMPLIED -"> - -<!-- SMIL Timing Module =================================================== --> -<!ENTITY % BasicInlineTiming.attrib " - %SMIL.pfx;dur %TimeValue; #IMPLIED - %SMIL.pfx;repeatCount %TimeValue; #IMPLIED - %SMIL.pfx;repeatDur %TimeValue; #IMPLIED - %SMIL.pfx;begin %TimeValue; #IMPLIED - %SMIL.pfx;end %TimeValue; #IMPLIED -"> - -<!ENTITY % MinMaxTiming.attrib " - %SMIL.pfx;min %TimeValue; #IMPLIED - %SMIL.pfx;max %TimeValue; #IMPLIED -"> - -<!ENTITY % BasicInlineTiming-deprecated.attrib " - %SMIL.pfx;repeat %TimeValue; #IMPLIED -"> - -<!ENTITY % BasicTimeContainers.attrib " - %SMIL.pfx;endsync (first|last|all|IDREF) 'last' - %Fill.attrib; -"> - -<!ENTITY % TimeContainerAttributes.attrib " - %SMIL.pfx;timeAction CDATA #IMPLIED - %SMIL.pfx;timeContainer CDATA #IMPLIED -"> - -<!ENTITY % RestartTiming.attrib " - %SMIL.pfx;restart (always|whenNotActive|never) 'always' -"> - -<!ENTITY % RestartDefaultTiming.attrib " - %SMIL.pfx;restartDefault (inherit|always|never|whenNotActive) 'always' -"> - -<!ENTITY % SyncBehavior.attrib " - %SMIL.pfx;syncBehavior (canSlip|locked|independent) #IMPLIED - %SMIL.pfx;syncTolerence %TimeValue; #IMPLIED -"> - -<!ENTITY % SyncBehaviorDefault.attrib " - %SMIL.pfx;syncBehaviorDefault (canSlip|locked|independent) #IMPLIED - %SMIL.pfx;syncToleranceDefault %TimeValue; #IMPLIED -"> - -<!ENTITY % SyncMaster.attrib " - %SMIL.pfx;syncMaster (true|false) 'false' -"> - -<!-- ================== Time Manipulations ================================= --> -<!ENTITY % TimeManipulations.attrib " - %SMIL.pfx;accelerate %Number; '0' - %SMIL.pfx;decelerate %Number; '0' - %SMIL.pfx;autoReverse (true|false) 'false' - %SMIL.pfx;speed %Number; '1.0' -"> - -<!-- ================== Streaming Media ==================================== --> -<!ENTITY % Streaming-media.attrib " - %SMIL.pfx;port CDATA #IMPLIED - %SMIL.pfx;rtpformat CDATA #IMPLIED - %SMIL.pfx;transport CDATA #IMPLIED -"> - -<!ENTITY % Streaming-timecontainer.attrib " - %SMIL.pfx;control CDATA #IMPLIED -"> - -<!-- ================== Transitions Media ================================== --> -<!ENTITY % Transition.attrib " - %SMIL.pfx;transIn IDREF #IMPLIED - %SMIL.pfx;transOut IDREF #IMPLIED -"> rmfile ./examples/SMIL/smil-attribs-1.mod hunk ./examples/SMIL/smil-datatypes-1.mod 1 -<!-- ...................................................................... --> -<!-- SMIL 2.0 Datatypes Module ........................................... --> -<!-- file: smil-datatypes-1.mod - - This is SMIL 2.0. - Copyright 1998-2000 W3C (MIT, INRIA, Keio), All Rights Reserved. - Revision: $Id: smil-datatypes-1.mod,v 1.1.1.1 2002/03/19 12:29:24 malcolm Exp $ - - This DTD module is identified by the PUBLIC and SYSTEM identifiers: - - PUBLIC "-//W3C//ENTITIES SMIL 2.0 Datatypes 1.0//EN" - SYSTEM "smil-datatypes-1.mod" - - ....................................................................... --> - -<!-- Datatypes - - defines containers for the following datatypes, many of - these imported from other specifications and standards. ---> - -<!ENTITY % Character "CDATA"> - <!-- a single character from [ISO10646] --> -<!ENTITY % ContentType "CDATA"> - <!-- media type, as per [RFC2045] --> -<!ENTITY % LanguageCode "NMTOKEN"> - <!-- a language code, as per [RFC1766] --> -<!ENTITY % LanguageCodes "CDATA"> - <!-- comma-separated list of language codes, as per [RFC1766] --> -<!ENTITY % Number "CDATA"> - <!-- one or more digits --> -<!ENTITY % Script "CDATA"> - <!-- script expression --> -<!ENTITY % Text "CDATA"> - <!-- used for titles etc. --> -<!ENTITY % TimeValue "CDATA"> - <!-- a Number, possibly with its dimension, or a reserved - word like 'indefinite' --> -<!ENTITY % URI.datatype "CDATA" > -<!ENTITY % URI "CDATA" > - <!-- used for URI references --> rmfile ./examples/SMIL/smil-datatypes-1.mod hunk ./examples/SMIL/smil-framework-1.mod 1 -<!-- ...................................................................... --> -<!-- SMIL 2.0 Modular Framework Module ................................... --> -<!-- file: smil-framework-1.mod - - This is SMIL 2.0. - Copyright 1998-2000 W3C (MIT, INRIA, Keio), All Rights Reserved. - - This DTD module is identified by the PUBLIC and SYSTEM identifiers: - - PUBLIC "-//W3C//ENTITIES SMIL 2.0 Modular Framework 1.0//EN" - SYSTEM "smil-framework-1.mod" - - Revision: $Id: smil-framework-1.mod,v 1.1.1.1 2002/03/19 12:29:24 malcolm Exp $ - ....................................................................... --> - -<!-- Modular Framework - - This required module instantiates the modules needed - to support the SMIL 2.0 modularization model, including: - - + datatypes - + namespace-qualified names - + common attributes - + document model - - The Intrinsic Events module is ignored by default but - occurs in this module because it must be instantiated - prior to Attributes but after Datatypes. ---> - -<!-- The (still to be determined) SMIL namespace: --> -<!ENTITY % SMIL.ns "'http://www.w3.org/TR/REC-smil/SMIL20'"> - -<!ENTITY % smil-datatypes.module "INCLUDE" > -<![%smil-datatypes.module;[ -<!ENTITY % smil-datatypes.mod - PUBLIC "-//W3C//ENTITIES SMIL 2.0 Datatypes 1.0//EN" - "smil-datatypes-1.mod" > -%smil-datatypes.mod;]]> - -<!ENTITY % smil-qname.module "INCLUDE" > -<![%smil-qname.module;[ -<!ENTITY % smil-qname.mod - PUBLIC "-//W3C//ENTITIES SMIL 2.0 Qualified Names 1.0//EN" - "smil-qname-1.mod" > -%smil-qname.mod;]]> - -<!ENTITY % smil-events.module "IGNORE" > -<![%smil-events.module;[ -<!ENTITY % smil-events.mod - PUBLIC "-//W3C//ENTITIES SMIL 2.0 Intrinsic Events 1.0//EN" - "smil-events-1.mod" > -%smil-events.mod;]]> - -<!ENTITY % smil-attribs.module "INCLUDE" > -<![%smil-attribs.module;[ -<!ENTITY % smil-attribs.mod - PUBLIC "-//W3C//ENTITIES SMIL 2.0 Common Attributes 1.0//EN" - "smil-attribs-1.mod" > -%smil-attribs.mod;]]> - -<!ENTITY % smil-model.module "INCLUDE" > -<![%smil-model.module;[ -<!-- A content model MUST be defined by the driver file --> -%smil-model.mod;]]> - -<!-- end of smil-framework-1.mod --> rmfile ./examples/SMIL/smil-framework-1.mod hunk ./examples/SMIL/smil-model-1.mod 1 -<!-- .................................................................... --> -<!-- SMIL 2.0 Document Model Module ..................................... --> -<!-- file: smil-model-1.mod - - This is SMIL 2.0. - Copyright 1998-2000 W3C (MIT, INRIA, Keio), All Rights Reserved. - - This DTD module is identified by the PUBLIC and SYSTEM identifiers: - - PUBLIC "-//W3C//ENTITIES SMIL 2.0 Document Model 1.0//EN" - SYSTEM "smil-model-1.mod" - - Author: Warner ten Kate, Jacco van Ossenbruggen, Aaron Cohen - Revision: $Id: smil-model-1.mod,v 1.1.1.1 2002/03/19 12:29:24 malcolm Exp $ - ....................................................................... --> - -<!-- - This file defines the SMIL 2.0 Language Document Model. - All attributes and content models are defined in the second - half of this file. We first start with some utility definitions. - These are mainly used to simplify the use of Modules in the - second part of the file. - ---> -<!-- ================== Util: Head ========================================= --> -<!ENTITY % head-meta.content "metadata?,meta*"> -<!ENTITY % head-layout.content "layout|switch"> -<!ENTITY % head-control.content "customAttributes"> -<!ENTITY % head-transition.content "transition+, meta*"> - -<!--=================== Util: Body - Content Control ======================= --> -<!ENTITY % content-control "switch|prefetch"> - -<!--=================== Util: Body - Animation ========================= --> -<!ENTITY % animation.elements "animate|set|animateMotion|animateColor"> - -<!--=================== Util: Body - Media ========================= --> - -<!ENTITY % media-object "audio|video|animation|text|img|textstream|ref|brush - |%animation.elements;"> - -<!--=================== Util: Body - Timing ================================ --> -<!ENTITY % BasicTimeContainers.class "par|seq"> -<!ENTITY % ExclTimeContainers.class "excl"> -<!ENTITY % timecontainer.class - "%BasicTimeContainers.class;|%ExclTimeContainers.class;"> -<!ENTITY % timecontainer.content - "%timecontainer.class;|%media-object;|%content-control;|a"> - -<!ENTITY % smil-time.attrib " - %BasicInlineTiming.attrib; - %MinMaxTiming.attrib; - %RestartTiming.attrib; - %SyncBehavior.attrib; - %SyncBehaviorDefault.attrib; - %BasicInlineTiming-deprecated.attrib; - %Fill.attrib; -"> - -<!ENTITY % timecontainer.attrib " - %BasicInlineTiming.attrib; - %MinMaxTiming.attrib; - %BasicTimeContainers.attrib; - %RestartTiming.attrib; - %SyncBehavior.attrib; - %SyncBehaviorDefault.attrib; - %BasicInlineTiming-deprecated.attrib; - %System.attrib; -"> - -<!-- ====================================================================== --> -<!-- ====================================================================== --> -<!-- ====================================================================== --> - -<!-- - The actual content model and attribute definitions for each module - sections follow below. ---> - -<!-- ================== Content Control =================================== --> -<!ENTITY % BasicContentControl.module "INCLUDE"> -<!ENTITY % CustomTestAttributes.module "INCLUDE"> -<!ENTITY % PrefetchControl.module "INCLUDE"> -<!ENTITY % SkipContentControl.module "INCLUDE"> - -<!ENTITY % switch.content "(layout|%timecontainer.class;|%media-object;| - %content-control;|a)*"> -<!ENTITY % prefetch.content "%switch.content;"> -<!ENTITY % customAttributes.content "(customTest)+"> - -<!ENTITY % switch.attrib "%System.attrib; %skipContent.attrib;"> -<!ENTITY % prefetch.attrib "%timecontainer.attrib; %skipContent.attrib; "> -<!ENTITY % customAttributes.attrib "%skipContent.attrib;"> -<!ENTITY % customTest.attrib "%skipContent.attrib;"> - -<!-- ================== Animation ========================================= --> -<!ENTITY % BasicAnimation.module "INCLUDE"> - -<!-- choose targetElement or XLink: --> -<!ENTITY % animation-targetElement "INCLUDE"> -<!ENTITY % animation-XLinkTarget "IGNORE"> - -<!ENTITY % animate.content "EMPTY"> -<!ENTITY % animateColor.content "EMPTY"> -<!ENTITY % animateMotion.content "EMPTY"> -<!ENTITY % set.content "EMPTY"> - -<!ENTITY % animate.attrib "%skipContent.attrib;"> -<!ENTITY % animateColor.attrib "%skipContent.attrib;"> -<!ENTITY % animateMotion.attrib "%skipContent.attrib;"> -<!ENTITY % set.attrib "%skipContent.attrib;"> - -<!-- ================== Layout ============================================ --> -<!ENTITY % BasicLayout.module "INCLUDE"> -<!ENTITY % AudioLayout.module "INCLUDE"> -<!ENTITY % MultiWindowLayout.module "INCLUDE"> -<!ENTITY % HierarchicalLayout.module "INCLUDE"> - -<!ENTITY % layout.content "(region|viewport|root-layout|regPoint)*"> -<!ENTITY % region.content "(region)*"> -<!ENTITY % rootlayout.content "(region)*"> -<!ENTITY % viewport.content "(region)*"> -<!ENTITY % regPoint.content "EMPTY"> - -<!ENTITY % rootlayout.attrib "%skipContent.attrib;"> -<!ENTITY % viewport.attrib "%skipContent.attrib;"> -<!ENTITY % region.attrib "%skipContent.attrib;"> -<!ENTITY % regPoint.attrib "%skipContent.attrib;"> - -<!-- ================== Linking =========================================== --> -<!ENTITY % LinkingAttributes.module "INCLUDE"> -<!ENTITY % BasicLinking.module "INCLUDE"> -<!ENTITY % ObjectLinking.module "INCLUDE"> - -<!ENTITY % a.content "(%timecontainer.class;|%media-object;| - %content-control;)*"> -<!ENTITY % area.content "EMPTY"> -<!ENTITY % anchor.content "EMPTY"> - -<!ENTITY % a.attrib "%smil-time.attrib;"> -<!ENTITY % area.attrib "%smil-time.attrib; %skipContent.attrib;"> -<!ENTITY % anchor.attrib "%smil-time.attrib; %skipContent.attrib;"> - -<!-- ================== Media ============================================ --> -<!ENTITY % BasicMedia.module "INCLUDE"> -<!ENTITY % MediaClipping.module "INCLUDE"> -<!ENTITY % MediaClipping.deperecated.module "INCLUDE"> -<!ENTITY % MediaClipMarkers.module "INCLUDE"> -<!ENTITY % MediaParam.module "INCLUDE"> -<!ENTITY % BrushMedia.module "INCLUDE"> -<!ENTITY % MediaAccessibility.module "INCLUDE"> - -<!ENTITY % media-object.content "(%animation.elements;|anchor|area - |transitionFilter|param)*"> -<!ENTITY % media-object.attrib " - %smil-time.attrib; - %System.attrib; - %Region.attrib; - %Transition.attrib; - %BackgroundColor.attrib; - %BackgroundColor-deprecated.attrib; - %Sub-region.attrib; - %RegistrationPoint.attrib; - %Fit.attrib; -"> - -<!ENTITY % brush.attrib "%skipContent.attrib;"> - -<!-- ================== Metadata ========================================== --> -<!ENTITY % meta.content "EMPTY"> -<!ENTITY % meta.attrib "%skipContent.attrib;"> - -<!ENTITY % metadata.content "EMPTY"> -<!ENTITY % metadata.attrib "%skipContent.attrib;"> - -<!-- ================== Structure ========================================= --> -<!ENTITY % Structure.module "INCLUDE"> -<!ENTITY % smil.content "(head?,body?)"> -<!ENTITY % head.content " - ((%head-meta.content;)?, - ((%head-layout.content;),meta*)?, - (%head-transition.content;)?, - ((%head-control.content;),meta*)?)"> -<!ENTITY % body.content "(%timecontainer.class;|%media-object;| - %content-control;|a)*"> - -<!ENTITY % body.attrib "%timecontainer.attrib; %Region.attrib;"> - -<!-- ================== Transitions ======================================= --> -<!ENTITY % BasicTransitions.module "INCLUDE"> -<!ENTITY % MultiElementTransitions.module "INCLUDE"> - -<!ENTITY % transition.content "(transitionFilter*)"> -<!ENTITY % transition.attrib "%skipContent.attrib;"> -<!ENTITY % transitionFilter.attrib "%skipContent.attrib;"> - -<!-- ================== Timing ============================================ --> -<!ENTITY % BasicInlineTiming.module "INCLUDE"> -<!ENTITY % SyncbaseTiming.module "INCLUDE"> -<!ENTITY % EventTiming.module "INCLUDE"> -<!ENTITY % WallclockTiming.module "INCLUDE"> -<!ENTITY % MultiSyncArcTiming.module "INCLUDE"> -<!ENTITY % MediaMarkerTiming.module "INCLUDE"> -<!ENTITY % MinMaxTiming.module "INCLUDE"> -<!ENTITY % BasicTimeContainers.module "INCLUDE"> -<!ENTITY % ExclTimeContainers.module "INCLUDE"> -<!ENTITY % PrevTiming.module "INCLUDE"> -<!ENTITY % RestartTiming.module "INCLUDE"> -<!ENTITY % SyncBehavior.module "INCLUDE"> -<!ENTITY % SyncBehaviorDefault.module "INCLUDE"> -<!ENTITY % RestartDefault.module "INCLUDE"> -<!ENTITY % FillDefault.module "INCLUDE"> - -<!ENTITY % par.attrib "%timecontainer.attrib; %Region.attrib;"> -<!ENTITY % seq.attrib "%timecontainer.attrib; %Region.attrib;"> -<!ENTITY % excl.attrib "%timecontainer.attrib; %Region.attrib; %skipContent.attrib;"> - -<!ENTITY % par.content "(%timecontainer.content;)*"> -<!ENTITY % seq.content "(%timecontainer.content;)*"> -<!ENTITY % excl.content "((%timecontainer.content;)*|priorityClass+)"> - -<!ENTITY % priorityClass.attrib "%skipContent.attrib;"> -<!ENTITY % priorityClass.content "((%timecontainer.content;)*|priorityClass+)"> rmfile ./examples/SMIL/smil-model-1.mod hunk ./examples/SMIL/smil-qname-1.mod 1 -<!-- ....................................................................... --> -<!-- SMIL Qualified Names Module .......................................... --> -<!-- file: smil-qname-1.mod - - This is SMIL. - Copyright 1998-2000 W3C (MIT, INRIA, Keio), All Rights Reserved. - Revision: $Id: smil-qname-1.mod,v 1.1.1.1 2002/03/19 12:29:24 malcolm Exp $ SMI - - This DTD module is identified by the PUBLIC and SYSTEM identifiers: - - PUBLIC "-//W3C//ENTITIES SMIL Qualified Names 1.0//EN" - SYSTEM "smil-qname-1.mod" - - ....................................................................... --> - -<!-- SMIL Qualified Names - - This module is contained in two parts, labeled Section 'A' and 'B': - - Section A declares parameter entities to support namespace- - qualified names, namespace declarations, and name prefixing - for SMIL and extensions. - - Section B declares parameter entities used to provide - namespace-qualified names for all SMIL element types: - - %animation.qname; the xmlns-qualified name for <animation> - %video.qname; the xmlns-qualified name for <video> - ... - - SMIL extensions would create a module similar to this one, - using the '%smil-qname-extra.mod;' parameter entity to insert - it within Section A. A template module suitable for this purpose - ('template-qname-1.mod') is included in the XHTML distribution. ---> - -<!-- Section A: SMIL XML Namespace Framework :::::::::::::::::::: --> - -<!-- 1. Declare the two parameter entities used to support XLink, - first the parameter entity container for the URI used to - identify the XLink namespace: ---> -<!ENTITY % XLINK.xmlns "http://www.w3.org/1999/xlink" > - -<!-- This contains the XLink namespace declaration attribute. ---> -<!ENTITY % XLINK.xmlns.attrib - "xmlns:xlink %URI.datatype; #FIXED '%XLINK.xmlns;'" -> - -<!-- 2. Declare parameter entities (eg., %SMIL.xmlns;) containing - the namespace URI for the SMIL namespace, and any namespaces - included by SMIL: ---> - -<!ENTITY % SMIL.xmlns "http://www.w3.org/TR/REC-smil/SMIL20" > - -<!-- 3. Declare parameter entities (eg., %SMIL.prefix;) containing - the default namespace prefix string(s) to use when prefixing - is enabled. This may be overridden in the DTD driver or the - internal subset of an document instance. - - NOTE: As specified in [XMLNAMES], the namespace prefix serves - as a proxy for the URI reference, and is not in itself significant. ---> -<!ENTITY % SMIL.prefix "" > - -<!-- 4. Declare a %SMIL.prefixed; conditional section keyword, used - to activate namespace prefixing. The default value should - inherit '%NS.prefixed;' from the DTD driver, so that unless - overridden, the default behaviour follows the overall DTD - prefixing scheme. ---> -<!ENTITY % NS.prefixed "IGNORE" > -<!ENTITY % SMIL.prefixed "%NS.prefixed;" > - -<!-- 5. Declare parameter entities (eg., %SMIL.pfx;) containing the - colonized prefix(es) (eg., '%SMIL.prefix;:') used when - prefixing is active, an empty string when it is not. ---> -<![%SMIL.prefixed;[ -<!ENTITY % SMIL.pfx "%SMIL.prefix;:" > -]]> -<!ENTITY % SMIL.pfx "" > - - -<!-- declare qualified name extensions here --> -<!ENTITY % smil-qname-extra.mod "" > -%smil-qname-extra.mod; - -<!-- 6. The parameter entity %SMIL.xmlns.extra.attrib; may be - redeclared to contain any non-SMIL namespace declaration - attributes for namespaces embedded in SMIL. The default - is an empty string. XLink should be included here if used - in the DTD and not already included by a previously-declared - %*.xmlns.extra.attrib;. ---> -<!ENTITY % SMIL.xmlns.extra.attrib "" > - -<!-- 7. The parameter entity %NS.prefixed.attrib; is defined to be - the prefix for SMIL elements if any and whatever is in - SMIL.xmlns.extra.attrib. ---> -<![%SMIL.prefixed;[ -<!ENTITY % NS.prefixed.attrib - "xmlns:%SMIL.prefix; %URI.datatype; #FIXED '%SMIL.xmlns;' - %SMIL.xmlns.extra.attrib; " > -]]> -<!ENTITY % NS.prefixed.attrib "%SMIL.xmlns.extra.attrib;" > - - -<!-- Section B: SMIL Qualified Names ::::::::::::::::::::::::::::: --> - -<!-- This section declares parameter entities used to provide - namespace-qualified names for all SMIL element types. ---> - -<!ENTITY % animate.qname "%SMIL.pfx;animate" > -<!ENTITY % set.qname "%SMIL.pfx;set" > -<!ENTITY % animateMotion.qname "%SMIL.pfx;animateMotion" > -<!ENTITY % animateColor.qname "%SMIL.pfx;animateColor" > - -<!ENTITY % switch.qname "%SMIL.pfx;switch" > -<!ENTITY % customTest.qname "%SMIL.pfx;customTest" > -<!ENTITY % customAttributes.qname "%SMIL.pfx;customAttributes" > -<!ENTITY % prefetch.qname "%SMIL.pfx;prefetch" > - -<!ENTITY % layout.qname "%SMIL.pfx;layout" > -<!ENTITY % region.qname "%SMIL.pfx;region" > -<!ENTITY % root-layout.qname "%SMIL.pfx;root-layout" > -<!ENTITY % viewport.qname "%SMIL.pfx;viewport" > -<!ENTITY % regPoint.qname "%SMIL.pfx;regPoint" > - -<!ENTITY % a.qname "%SMIL.pfx;a" > -<!ENTITY % area.qname "%SMIL.pfx;area" > -<!ENTITY % anchor.qname "%SMIL.pfx;anchor" > - -<!ENTITY % ref.qname "%SMIL.pfx;ref" > -<!ENTITY % audio.qname "%SMIL.pfx;audio" > -<!ENTITY % img.qname "%SMIL.pfx;img" > -<!ENTITY % video.qname "%SMIL.pfx;video" > -<!ENTITY % text.qname "%SMIL.pfx;text" > -<!ENTITY % textstream.qname "%SMIL.pfx;textstream" > -<!ENTITY % animation.qname "%SMIL.pfx;animation" > -<!ENTITY % param.qname "%SMIL.pfx;param" > -<!ENTITY % brush.qname "%SMIL.pfx;brush" > - -<!ENTITY % meta.qname "%SMIL.pfx;meta" > -<!ENTITY % metadata.qname "%SMIL.pfx;metadata" > - -<!ENTITY % rtpmap.qname "%SMIL.pfx;rtpmap" > - -<!ENTITY % smil.qname "%SMIL.pfx;smil" > -<!ENTITY % head.qname "%SMIL.pfx;head" > -<!ENTITY % body.qname "%SMIL.pfx;body" > - -<!ENTITY % seq.qname "%SMIL.pfx;seq" > -<!ENTITY % par.qname "%SMIL.pfx;par" > -<!ENTITY % excl.qname "%SMIL.pfx;excl" > - -<!ENTITY % transition.qname "%SMIL.pfx;transition" > -<!ENTITY % transitionFilter.qname "%SMIL.pfx;transitionFilter" > - -<!-- end of smil-qname-1.mod --> rmfile ./examples/SMIL/smil-qname-1.mod rmdir ./examples/SMIL hunk ./examples/SimpleTest.hs 1 -module Main where - -import List (isPrefixOf) -import Text.XML.HaXml.XmlContent -import Text.XML.HaXml.Types -import Text.PrettyPrint.HughesPJ (render) -import Text.XML.HaXml.Pretty (document) - --- Test stuff -value1 :: ([(Bool,Int)],(String,Maybe Char)) -value1 = ([(True,42),(False,0)],("Hello World",Just 'x')) - -data MyType a = ConsA Int a - | ConsB String deriving Eq - {-! derive : Haskell2Xml !-} - - -instance Haskell2Xml a => Haskell2Xml (MyType a) where - toHType v = Defined "MyType" [toHType a] - [Constr "ConsA" [toHType a] [Prim "Int" "int", toHType a] - ,Constr "ConsB" [] [String] - ] - where (ConsA _ a) = v - toContents v@(ConsA n a) = [mkElemC (showConstr 0 (toHType v)) - (concat [toContents n, toContents a])] - toContents v@(ConsB s) = [mkElemC (showConstr 1 (toHType v)) (toContents s)] - fromContents (CElem (Elem constr [] cs) : etc) - | "ConsA-" `isPrefixOf` constr = - (\(i,cs')-> (\(a,_) -> (ConsA i a,etc)) - (fromContents cs')) (fromContents cs) - | "ConsB" `isPrefixOf` constr = - (\(s,_)-> (ConsB s, etc)) (fromContents cs) - - -value2 :: (MyType [Int], MyType ()) -value2 = (ConsA 2 [42,0], ConsB "hello world") - ---main = do (putStrLn . render . document . toXml) value2 - -main = putStrLn - (if value2 == (fst . fromContents . toContents) value2 then "success" - else "failure") - rmfile ./examples/SimpleTest.hs hunk ./examples/SimpleTestBool.hs 1 -module Main where - -import List (isPrefixOf) -import Text.XML.HaXml.XmlContent -import Text.XML.HaXml.Types -import Text.PrettyPrint.HughesPJ (render) -import Text.XML.HaXml.Pretty (document) - --- Test stuff ---value1 :: ([(Bool,Int)],(String,Maybe Char)) -value1 = True - ---main = do (putStrLn . render . document . toXml) value2 - -main = fWriteXml "/dev/tty" value1 - rmfile ./examples/SimpleTestBool.hs hunk ./examples/SimpleTestD.hs 1 -module Main where - -import IO -import System (getArgs) ---import List (isPrefixOf) - -import Text.XML.HaXml.XmlContent - --- Test stuff -data MyType a = ConsA Int a - | ConsB String - {-! derive : XmlContent !-} - -instance Eq a => Eq (MyType a) where - (ConsA a b) == (ConsA c d) = a==c && b==d - (ConsB e) == (ConsB f) = e `isPrefixOf` f || f `isPrefixOf` e - _ == _ = False - -{- --- Hand-written example of preferred instance declaration. -instance Haskell2Xml a => Haskell2Xml (MyType a) where - toHType v = Defined "MyType" [toHType a] - [Constr "ConsA" [toHType a] [Prim "Int" "int", toHType a] - ,Constr "ConsB" [] [String] - ] - where (ConsA _ a) = v - toContents v@(ConsA n a) = [mkElemC (showConstr 0 (toHType v)) - (concat [toContents n, toContents a])] - toContents v@(ConsB s) = [mkElemC (showConstr 1 (toHType v)) (toContents s)] - fromContents (CElem (Elem constr [] cs) : etc) - | "ConsA-" `isPrefixOf` constr = - (\(i,cs')-> (\(a,_) -> (ConsA i a,etc)) - (fromContents cs')) (fromContents cs) - | "ConsB" `isPrefixOf` constr = - (\(s,_)-> (ConsB s, etc)) (fromContents cs) --} - -value1 :: Maybe ([(Bool,Int)],(String,Maybe Char)) -value1 = Just ([(True,42),(False,0)],("Hello World",Nothing)) - -value2 :: (MyType [Int], MyType ()) -value2 = (ConsA 2 [42,0], ConsB "hello world") - -value3 :: MyType [Int] -value3 = ConsA 2 [42,0] - --- Main wrapper -main = - getArgs >>= \args-> - if length args /= 3 then - putStrLn "Usage: <app> [1|2|3] [-w|-r] <xmlfile>" - else - let (arg0:arg1:arg2:_) = args in - ( case arg1 of - "-w"-> return (stdout,WriteMode) - "-r"-> return (stdin,ReadMode) - _ -> fail ("Usage: <app> [-r|-w] <xmlfile>") ) >>= \(std,mode)-> - ( if arg2=="-" then return std - else openFile arg2 mode ) >>= \f-> - ( case arg0 of - "1" -> checkValue f mode value1 - "2" -> checkValue f mode value2 - "3" -> checkValue f mode value3 - _ -> fail ("Usage: <app> [-r|-w] <xmlfile>") ) - -checkValue f mode value = - case mode of - WriteMode-> hPutXml f value - ReadMode -> do ivalue <- hGetXml f - putStrLn (if ivalue==value then "success" else "failure") - --- WriteMode-> (hPutStrLn f . render . document . toXml) value1 --- ReadMode -> hGetContents f >>= \content -> --- let ivalue = (fromXml . xmlParse) content in --- (putStrLn . render . document . toXml) (ivalue `asTypeOf` value1) >> --- putStrLn (if ivalue == value1 then "success" else "failure") - - --- Machine generated stuff -{-* Generated by DrIFT-v1.0 : Look, but Don't Touch. *-} -instance (Haskell2Xml a) => Haskell2Xml (MyType a) where - toHType v = - Defined "MyType" [a] - [Constr "ConsA" [a] [toHType aa,toHType ab], - Constr "ConsB" [] [toHType ac]] - where - (ConsA aa ab) = v - (ConsB ac) = v - (a) = toHType ab - fromContents (CElem (Elem constr [] cs):etc) - | "ConsA" `isPrefixOf` constr = - (\(aa,cs00)-> (\(ab,_)-> (ConsA aa ab, etc)) (fromContents cs00)) - (fromContents cs) - | "ConsB" `isPrefixOf` constr = - (\(ac,_)-> (ConsB ac, etc)) (fromContents cs) - fromContents (CElem (Elem constr _ _):etc) = - error ("expected ConsA or ConsB, got "++constr) - toContents v@(ConsA aa ab) = - [mkElemC (showConstr 0 (toHType v)) (concat [toContents aa, - toContents ab])] - toContents v@(ConsB ac) = - [mkElemC (showConstr 1 (toHType v)) (toContents ac)] - rmfile ./examples/SimpleTestD.hs hunk ./examples/Types.hs 1 -module DTypes where - -import Text.XML.HaXml.XmlContent hiding (Name) - --- data types for a simple test program - -data Person = Person Name Email [Rating] Version {-! derive : XmlContent !-} - -newtype Name = Name String {-! derive : XmlContent !-} -newtype Email = Email String {-! derive : XmlContent !-} -newtype Version = Version Int {-! derive : XmlContent !-} - -data Rating = Rating SubjectID Interest Skill {-! derive : XmlContent !-} - -newtype SubjectID = SubjectID Int {-! derive : XmlContent !-} -newtype Interest = Interest Score {-! derive : XmlContent !-} -newtype Skill = Skill Score {-! derive : XmlContent !-} - -data Score = ScoreNone | ScoreLow | ScoreMedium | ScoreHigh {-! derive : XmlContent !-} - rmfile ./examples/Types.hs hunk ./examples/album.dtd 1 -<!DOCTYPE album [ -<!ELEMENT album (title, artist, recording?, coverart, catalogno*, - personnel, track*, notes) > -<!ELEMENT title (#PCDATA) > -<!ELEMENT artist (#PCDATA) > -<!ELEMENT recording EMPTY> - <!ATTLIST recording date CDATA #IMPLIED - place CDATA #IMPLIED> -<!ELEMENT coverart (location)? > - <!ATTLIST coverart style CDATA #REQUIRED> -<!ELEMENT location EMPTY > - <!ATTLIST location thumbnail CDATA #IMPLIED - fullsize CDATA #IMPLIED> -<!ELEMENT catalogno EMPTY > - <!ATTLIST catalogno label CDATA #REQUIRED - number CDATA #REQUIRED - format (CD | LP | MiniDisc) #IMPLIED - releasedate CDATA #IMPLIED - country CDATA #IMPLIED> -<!ELEMENT personnel (player)+ > -<!ELEMENT player EMPTY > - <!ATTLIST player name CDATA #REQUIRED - instrument CDATA #REQUIRED> -<!ELEMENT track EMPTY> - <!ATTLIST track title CDATA #REQUIRED - credit CDATA #IMPLIED - timing CDATA #IMPLIED> -<!ELEMENT notes (#PCDATA | albumref | trackref)* > - <!ATTLIST notes author CDATA #IMPLIED> -<!ELEMENT albumref (#PCDATA)> - <!ATTLIST albumref link CDATA #REQUIRED> -<!ELEMENT trackref (#PCDATA)> - <!ATTLIST trackref link CDATA #IMPLIED> -]> rmfile ./examples/album.dtd hunk ./examples/album.xml 1 -<?xml version='1.0'?> -<!DOCTYPE album SYSTEM "album.dtd"> -<album - ><title>Time OutDave Brubeck QuartetPossibly the DBQ's most famous album, this contains - Take Five, the most famous jazz track - of that period. These experiments in different time signatures are - what Dave Brubeck is most remembered for. Recorded Jun-Aug 1959 in - NYC. See also the sequel, - Time Further Out. - rmfile ./examples/album.xml hunk ./examples/subjdb.xml 1 - - - - - - - - - - - - - - - - - - - - - - - - - - -]> -Rob Noblerjn rmfile ./examples/subjdb.xml }