1 {-# LANGUAGE FlexibleInstances #-}
2 {-# LANGUAGE OverloadedStrings #-}
3 {-# OPTIONS_GHC -fno-warn-orphans #-}
4 module Hdoc.DTC.Write.XML where
6 import Control.Monad (forM_)
8 import Data.Foldable (Foldable(..))
9 import Data.Function (($), (.))
10 import Data.Functor ((<$>))
11 import Data.Maybe (Maybe(..))
12 import Data.Monoid (Monoid(..))
13 import Data.Sequence (Seq)
14 import Data.TreeSeq.Strict (Tree(..))
15 import Text.Blaze ((!))
16 import Text.Blaze.Utils
17 import Text.Blaze.XML (XML)
18 import qualified Data.Function as Fun
19 import qualified Data.Text.Lazy as TL
20 import qualified Text.Blaze as B
21 import qualified Text.Blaze.DTC as XML
22 import qualified Text.Blaze.DTC.Attributes as XA
23 import qualified Text.Blaze.Internal as B
26 import Hdoc.DTC.Index (plainifyWords)
27 import Hdoc.DTC.Document as DTC
29 writeXML :: Locales ls => LocaleIn ls -> Document -> XML
30 writeXML _loc Document{..} = do
31 XML.xmlModel "./schema/dtc.rnc"
33 let lang = Text.takeWhile Char.isAlphaNum $ textLocales Map.! loc
34 XML.xmlStylesheet $ "./xsl/document.html5."<>lang<>".xsl"
35 XML.html5Stylesheet $ "./xsl/document.html5."<>lang<>".xsl"
36 XML.atomStylesheet $ "./xsl/document.atom."<>lang<>".xsl"
46 instance Xmlify TL.Text where
48 instance Xmlify Head where
51 instance Xmlify (Tree BodyNode) where
54 BodyBlock b -> xmlify b
55 BodySection Section{..} ->
56 xmlCommonAttrs attrs $
61 instance Xmlify Block where
63 BlockPara para -> xmlify para
65 xmlCommonAttrs attrs $
68 xmlCommonAttrs attrs $
70 !?? mayAttr XA.depth depth
72 xmlCommonAttrs attrs $
78 xmlCommonAttrs attrs $
81 forM_ terms $ \aliases ->
85 plainifyWords <$> aliases
87 xmlCommonAttrs attrs $
91 xmlCommonAttrs attrs $
93 ! XA.type_ (attrify type_) $ do
96 BlockReferences{..} ->
97 xmlCommonAttrs attrs $
98 XML.references $ xmlify refs
99 instance Xmlify Para where
101 ParaItem{..} -> xmlify item
102 ParaItems{..} -> xmlCommonAttrs attrs $ XML.para $ xmlify items
103 instance Xmlify ParaItem where
105 ParaPlain p -> XML.p $ xmlify p
107 XML.comment $ TL.toStrict c
110 ! XA.type_ (attrify type_) $ do
114 ! XA.type_ (attrify type_) $ do
116 ParaOL items -> XML.ol $ forM_ items xmlify
117 ParaUL items -> XML.ul $ forM_ items $ XML.li . xmlify
118 ParaJudgment j -> xmlify j
119 instance Xmlify Judgment where
123 ! XA.judges (attrify judges)
124 ! XA.grades (attrify grades) $
126 -- TODO: xmlify choices
127 instance Xmlify ListItem where
128 xmlify ListItem{..} =
129 XML.li ! XA.name (attrify name) $ xmlify paras
130 instance Xmlify (Tree PlainNode) where
133 PlainText t -> xmlify t
135 PlainGroup -> xmlify ts
136 PlainB -> XML.b $ xmlify ts
137 PlainCode -> XML.code $ xmlify ts
138 PlainDel -> XML.del $ xmlify ts
139 PlainI -> XML.i $ xmlify ts
140 PlainNote{..} -> XML.note $ xmlify note
141 PlainQ -> XML.q $ xmlify ts
142 PlainSpan{..} -> xmlCommonAttrs attrs $ XML.span $ xmlify ts
143 PlainSC -> XML.sc $ xmlify ts
144 PlainSub -> XML.sub $ xmlify ts
145 PlainSup -> XML.sup $ xmlify ts
146 PlainU -> XML.u $ xmlify ts
147 PlainEref to -> XML.eref ! XA.to (attrify to) $ xmlify ts
148 PlainIref{..} -> XML.iref ! XA.term (attrify $ plainifyWords term) $ xmlify ts
149 PlainTag{..} -> XML.tag $ xmlify ts
150 PlainRref{..} -> XML.rref ! XA.to (attrify $ unIdent to) $ xmlify ts
152 instance Xmlify About where
153 xmlify About{..} = do
155 !?? mayAttr XA.url url
161 forM_ tags $ XML.tag . xmlify
164 instance Xmlify Include where
167 ! XA.href (attrify href)
168 instance Xmlify Date where
171 ! XA.year (attrify year)
172 !?? mayAttr XA.month month
173 !?? mayAttr XA.day day
174 instance Xmlify Link where
177 !?? mayAttr XA.name name
178 !?? mayAttr XA.rel rel
179 !?? mayAttr XA.href href
181 instance Xmlify Entity where
184 !?? mayAttr XA.name name
185 !?? mayAttr XA.street street
186 !?? mayAttr XA.zipcode zipcode
187 !?? mayAttr XA.city city
188 !?? mayAttr XA.region region
189 !?? mayAttr XA.country country
190 !?? mayAttr XA.email email
191 !?? mayAttr XA.tel tel
192 !?? mayAttr XA.fax fax
193 instance Xmlify Title where
194 xmlify (Title t) = XML.title $ xmlify t
195 instance Xmlify Alias where
196 xmlify Alias{..} = XML.alias $ xmlify title
197 instance Xmlify Reference where
198 xmlify Reference{..} = XML.reference mempty -- TODO: to be coded
200 instance Xmlify a => Xmlify (Maybe a) where
201 xmlify = foldMap xmlify
202 instance Xmlify a => Xmlify [a] where
203 xmlify = foldMap xmlify
204 instance Xmlify a => Xmlify (Seq a) where
205 xmlify = foldMap xmlify
207 xmlId :: Ident -> B.Attribute
208 xmlId (Ident i) = XA.id $ attrify i
210 xmlCommonAttrs :: CommonAttrs -> XML -> XML
211 xmlCommonAttrs CommonAttrs{id=ident, ..} =
215 B.AddCustomAttribute "id" $
216 B.String $ TL.unpack i) .
220 B.AddCustomAttribute "class" $
221 B.String $ TL.unpack $ TL.unwords classes