1 {-# LANGUAGE OverloadedStrings #-}
2 {-# OPTIONS_GHC -fno-warn-orphans #-}
3 module Language.DTC.Write.XML where
5 import Control.Monad (forM_, mapM_)
7 import Data.Function (($), (.))
8 import Data.Functor ((<$>))
9 import Data.Maybe (Maybe(..))
10 import Data.Monoid (Monoid(..))
11 import Data.Semigroup (Semigroup(..))
12 import Data.Text (Text)
13 import Text.Blaze ((!))
14 import Text.Blaze.Utils
15 import Text.Blaze.XML (XML)
16 import Data.TreeSeq.Strict (Tree(..))
17 import qualified Data.Char as Char
18 import qualified Data.Map.Strict as Map
19 import qualified Data.Text as Text
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 Language.DTC.Document (MayText(..), whenMayText)
27 import Language.DTC.Anchor (plainifyWords)
28 import qualified Language.DTC.Document as DTC
30 xmlText :: Text -> XML
33 xmlDocument :: Locales ls => LocaleIn ls -> DTC.Document -> XML
34 xmlDocument loc DTC.Document{..} = do
35 let lang = Text.takeWhile Char.isAlphaNum $ textLocales Map.! loc
36 XML.xmlModel "./schema/dtc.rnc"
37 XML.xmlStylesheet $ "./xsl/document.html5."<>lang<>".xsl"
38 XML.html5Stylesheet $ "./xsl/document.html5."<>lang<>".xsl"
39 XML.atomStylesheet $ "./xsl/document.atom."<>lang<>".xsl"
44 xmlHead :: DTC.Head -> XML
45 xmlHead DTC.Head{..} =
46 XML.about $ xmlAbout about
48 xmlBody :: DTC.Body -> XML
49 xmlBody = mapM_ $ \case
50 TreeN k ts -> xmlBodyKey k $ xmlBody ts
51 Tree0 v -> xmlBodyValue v
53 xmlBodyKey :: DTC.BodyKey -> XML -> XML
54 xmlBodyKey k body = case k of
56 xmlCommonAttrs attrs $
59 forM_ aliases xmlAlias
62 xmlBodyValue :: DTC.BodyValue -> XML
65 xmlCommonAttrs attrs $
67 !?? mayAttr XA.depth depth
69 xmlCommonAttrs attrs $
75 xmlCommonAttrs attrs $
78 forM_ terms $ \aliases ->
82 plainifyWords <$> aliases
84 xmlCommonAttrs attrs $
86 ! XA.type_ (attrify type_) $ do
90 xmlCommonAttrs attrs $
91 XML.references $ forM_ refs $ xmlReference
92 DTC.Block v -> xmlBlock v
94 xmlAbout :: DTC.About -> XML
95 xmlAbout DTC.About{..} = do
96 forM_ titles $ xmlTitle
97 forM_ authors $ xmlEntity
98 forM_ editor $ xmlEntity
100 whenMayText version xmlVersion
101 forM_ keywords $ xmlKeyword
102 forM_ links $ xmlLink
103 forM_ includes $ xmlInclude
105 xmlInclude :: DTC.Include -> XML
106 xmlInclude DTC.Include{..} =
108 ! XA.href (attrify href)
110 xmlKeyword :: Text -> XML
111 xmlKeyword = XML.keyword . xmlText
113 xmlVersion :: MayText -> XML
114 xmlVersion (MayText t) = XML.version $ xmlText t
116 xmlDate :: DTC.Date -> XML
117 xmlDate DTC.Date{..} =
119 ! XA.year (attrify year)
120 !?? mayAttr XA.month month
121 !?? mayAttr XA.day day
123 xmlLink :: DTC.Link -> XML
124 xmlLink DTC.Link{..} =
126 !?? mayAttr XA.name name
127 !?? mayAttr XA.rel rel
128 !?? mayAttr XA.href href
131 xmlEntity :: DTC.Entity -> XML
132 xmlEntity DTC.Entity{..} =
134 !?? mayAttr XA.name name
135 !?? mayAttr XA.street street
136 !?? mayAttr XA.zipcode zipcode
137 !?? mayAttr XA.city city
138 !?? mayAttr XA.region region
139 !?? mayAttr XA.country country
140 !?? mayAttr XA.email email
141 !?? mayAttr XA.tel tel
142 !?? mayAttr XA.fax fax
144 xmlTitle :: DTC.Title -> XML
145 xmlTitle (DTC.Title t) = XML.title $ xmlPara t
147 xmlAlias :: DTC.Alias -> XML
148 xmlAlias DTC.Alias{..} = XML.alias !?? mayAttr XA.id id
150 xmlId :: DTC.Ident -> B.Attribute
151 xmlId (DTC.Ident i) = XA.id $ attrify i
153 xmlBlocks :: DTC.Blocks -> XML
154 xmlBlocks = (`forM_` xmlBlock)
156 xmlCommonAttrs :: DTC.CommonAttrs -> XML -> XML
157 xmlCommonAttrs DTC.CommonAttrs{id=ident, ..} =
160 Just (DTC.Ident i) -> B.AddCustomAttribute "id" (B.Text i)) .
163 _ -> B.AddCustomAttribute "class" (B.Text $ Text.unwords classes)
165 xmlBlock :: DTC.Block -> XML
168 xmlCommonAttrs attrs $
169 XML.para $ xmlPara para
171 xmlCommonAttrs attrs $
172 XML.ol $ forM_ items $ XML.li . xmlBlocks
174 xmlCommonAttrs attrs $
175 XML.ul $ forM_ items $ XML.li . xmlBlocks
179 xmlCommonAttrs attrs $
182 xmlPara :: DTC.Para -> XML
183 xmlPara = (`forM_` xmlLine)
185 xmlLine :: Tree DTC.LineKey DTC.LineValue -> XML
189 DTC.Plain p -> B.toMarkup p
193 DTC.B -> XML.b $ xmlPara ls
194 DTC.Code -> XML.code $ xmlPara ls
195 DTC.Del -> XML.del $ xmlPara ls
196 DTC.I -> XML.i $ xmlPara ls
197 DTC.Note{..} -> XML.note $ xmlPara ls
198 DTC.Q -> XML.q $ xmlPara ls
199 DTC.SC -> XML.sc $ xmlPara ls
200 DTC.Sub -> XML.sub $ xmlPara ls
201 DTC.Sup -> XML.sup $ xmlPara ls
202 DTC.U -> XML.u $ xmlPara ls
203 DTC.Eref to -> XML.eref ! XA.to (attrify to) $ xmlPara ls
204 DTC.Iref{..} -> XML.iref ! XA.term (attrify $ plainifyWords term) $ xmlPara ls
205 DTC.Ref to -> XML.ref ! XA.to (attrify to) $ xmlPara ls
206 DTC.Rref{..} -> XML.rref ! XA.to (attrify to) $ xmlPara ls
208 xmlReference :: DTC.Reference -> XML
209 xmlReference DTC.Reference{..} =