1 {-# LANGUAGE OverloadedStrings #-}
2 {-# LANGUAGE RecordWildCards #-}
3 {-# LANGUAGE ViewPatterns #-}
4 {-# OPTIONS_GHC -fno-warn-orphans #-}
5 -- | Render a TCT file in DTC.
6 module Language.TCT.Write.DTC where
8 import Control.Arrow (first)
9 import Control.Monad (Monad(..), (=<<), forM_, when)
11 import Data.Eq (Eq(..))
12 import Data.Foldable (foldr, null, foldMap, foldl', any)
13 import Data.Function (($), (.), flip, id)
14 import Data.Functor (Functor(..), (<$>))
15 import Data.Map.Strict (Map)
16 import Data.Maybe (Maybe(..))
17 import Data.Monoid (Monoid(..))
18 import Data.Semigroup (Semigroup(..))
19 import Data.Sequence (ViewL(..), ViewR(..), (<|), (|>))
20 import Data.String (String)
21 import Data.Text (Text)
22 import GHC.Exts (toList)
23 import Text.Blaze ((!))
24 import Text.Show (Show(..))
25 import qualified Data.Char as Char
26 import qualified Data.Map.Strict as Map
27 import qualified Data.Sequence as Seq
28 import qualified Data.Text as Text
29 import qualified Data.Text.Lazy as TL
30 import qualified Text.Blaze as B
31 import qualified Text.Blaze.Internal as B
33 import Language.TCT.Tree
34 import Language.TCT.Token
35 import Language.TCT.Elem hiding (trac,dbg)
36 import qualified Language.TCT.Write.Text as Write
37 import Text.Blaze.Utils
38 import Text.Blaze.DTC (DTC)
39 import qualified Text.Blaze.DTC as D
40 import qualified Text.Blaze.DTC.Attributes as DA
42 import Debug.Trace (trace)
43 trac :: String -> a -> a
45 -- trac m x = trace m x
46 dbg :: Show a => String -> a -> a
47 dbg m x = trac (m <> ": " <> show x) x
52 { inh_dtc_para :: DTC -> DTC
53 , inh_dtc_figure :: Bool
58 , inh_dtc_figure = False
61 mimetype :: Text -> Maybe Text
62 mimetype "sh" = Just "text/x-shellscript"
63 mimetype "shell" = Just "text/x-shellscript"
64 mimetype "shellscript" = Just "text/x-shellscript"
67 dtc :: Trees Key Tokens -> DTC
70 D.xmlModel "./schema/dtc.rnc"
71 D.xmlStylesheet $ "./xsl/document.html5."<>lang<>".xsl"
72 D.html5Stylesheet $ "./xsl/document.html5."<>lang<>".xsl"
73 D.atomStylesheet $ "./xsl/document.atom."<>lang<>".xsl"
77 (Seq.viewl -> Tree0 (Write.t_Tokens -> TL.toStrict -> title) :< head)
79 d_Trees inh_dtc (mangleHead title head)
81 inh_dtc { inh_dtc_figure = True }
85 inh_dtc { inh_dtc_figure = True }
92 mangleHead title head =
94 (`Seq.findIndexL` head) $ \case
95 TreeN (KeyColon "about" _) _ -> True
99 TreeN (KeyColon "about" "")
102 Just i -> Seq.adjust f i head
104 f (TreeN c about) = TreeN c $ Seq.fromList names <> about
107 names = name <$> Text.splitOn "\n" title
109 TreeN (KeyColon "name" "") .
110 Seq.singleton . Tree0 .
113 d_Trees :: Inh_DTC -> Trees Key Tokens -> DTC
116 TreeN (KeyBar n _) _ :< _
117 | (content,ts') <- gatherBar n ts -> do
118 D.artwork !?? (mimetype n, DA.type_ . attrValue) $
119 d_Trees inh{inh_dtc_para=id} content
122 TreeN key@(KeyColon n _) cs :< ts'
123 | (cs',ts'') <- gatherColon n ts'
125 d_Trees inh $ TreeN key (cs<>cs') <| ts''
127 _ | (ul,ts') <- gatherLI (==KeyDash) ts, not (null ul) -> do
128 D.ul ! DA.style "format —" $ forM_ ul $ d_Tree inh
131 _ | (ol,ts') <- gatherLI (\case KeyDot{} -> True; _ -> False) ts, not (null ol) -> do
132 D.ol $ forM_ ol $ d_Tree inh
136 _ | inh_dtc_figure inh
137 , Just (name,head,content,ts') <- gatherColon ts -> do
138 D.figure ! DA.type_ (attrValue name) $ do
139 D.name $ d_Tokens head
151 gatherBar :: Name -> Trees Key Tokens -> (Trees Key Tokens, Trees Key Tokens)
152 gatherBar name = first unKeyBar . spanBar
154 unKeyBar :: Trees Key Tokens -> Trees Key Tokens
155 unKeyBar = (=<<) $ \case
156 TreeN KeyBar{} ts -> ts
160 TreeN (KeyBar n _) _ | n == name -> True
163 gatherColon :: Name -> Trees Key Tokens -> (Trees Key Tokens, Trees Key Tokens)
166 TreeN (KeyBar n _) _ -> n == name
167 TreeN (KeyGreat n _) _ -> n == name
171 gatherColon :: Trees Key Tokens -> Maybe (Name, Tokens, Trees Key Tokens, Trees Key Tokens)
174 TreeN (KeyColon name _) (toList -> [Tree0 head]) :< (spanBar name -> (body,ts')) ->
175 Just (name,head,body,ts')
180 TreeN (KeyBar n _) _ | n == name -> True
187 (Trees Key Tokens, Trees Key Tokens)
189 let (lis, ts') = spanLIs ts in
190 foldl' accumLIs (mempty,ts') lis
192 spanLIs = Seq.spanl $ \case
193 TreeN (liKey -> True) _ -> True
194 Tree0 (Tokens toks) ->
196 TokenPair (PairElem "li" _) _ -> True
199 accumLIs acc@(oks,kos) t =
201 TreeN (liKey -> True) _ -> (oks|>t,kos)
202 Tree0 (Tokens toks) ->
203 let mk = Tree0 . Tokens in
205 (`Seq.spanl` toks) $ \case
206 TokenPair (PairElem "li" _) _ -> True
207 TokenPlain txt -> Char.isSpace`Text.all`txt
209 ( if null ok then oks else oks|>mk (rmTokenPlain ok)
210 , if null ko then kos else mk ko<|kos )
214 TokenPlain{} -> False
219 (Name, Tokens, Attributes, Trees Key Tokens)
220 gatherName ts = dbg "gatherName" $
221 case Seq.viewl children of
222 Tree0 (toList -> [TokenPlain name]) :< body ->
223 case Text.splitOn "\n" name of
224 n:[] -> (n,mempty,attrs,body)
225 n:ns -> (n,tokens [TokenPlain $ Text.intercalate "\n" ns],attrs,body)
226 [] -> (name,mempty,attrs,body)
227 Tree0 name :< body -> ("",name,attrs,body)
228 _ -> ("",mempty,attrs,children)
230 (attrs,children) = partitionAttributesChildren ts
232 d_Tree :: Inh_DTC -> Tree Key Tokens -> DTC
233 d_Tree inh (TreeN KeySection{} ts) =
235 { inh_dtc_para = D.para
237 case gatherName ts of
238 ("",Tokens (null->True),attrs,body) ->
240 D.section $ d_Trees inh' body
241 ("",names,attrs,body) ->
242 d_Attributes (setAttrId (TL.toStrict $ Write.t_Tokens names) attrs) $
244 D.name $ d_Tokens names
246 (name,names,attrs,body) ->
247 d_Attributes (setAttrId name attrs) $
248 D.section ! DA.name (attrValue name) $ do
249 when (not $ null $ unTokens names) $
250 D.name $ d_Tokens names
252 d_Tree inh (TreeN key@(KeyColon typ _) ts) =
253 if inh_dtc_figure inh
255 case gatherName ts of
256 ("",names,attrs,body) ->
258 D.figure ! DA.type_ (attrValue typ) $ do
259 when (not $ null $ unTokens names) $
260 D.name $ d_Tokens names
262 (name,names,attrs,body) ->
264 D.figure ! DA.type_ (attrValue typ)
265 ! DA.name (attrValue name) $ do
266 when (not $ null $ unTokens names) $
267 D.name $ d_Tokens names
270 let (attrs,body) = partitionAttributesChildren ts in
273 d_Tree path (TreeN key ts) = d_Key path key ts
274 d_Tree inh (Tree0 ts) =
276 (toList -> [TokenPair PairElem{} _ts]) -> d_Tokens ts
277 _ -> inh_dtc_para inh $ d_Tokens ts
279 setAttrId :: Text -> Attributes -> Attributes
280 setAttrId = Map.insertWith (\_new old -> old) "id"
282 d_Key :: Inh_DTC -> Key -> Trees Key Tokens -> DTC
283 d_Key inh key ts = do
285 KeyColon n _wh -> d_key n
286 KeyGreat n _wh -> d_key n
287 KeyEqual n _wh -> d_key n
288 KeyBar n _wh -> d_key n
289 KeyDot _n -> D.li $ d_Trees inh ts
290 KeyDash -> D.li $ d_Trees inh ts
291 KeyDashDash -> B.Comment (B.Text $ TL.toStrict com) ()
294 Write.text Write.config_text $
295 mapTreeKey cell1 (\_path -> cell1) <$> ts
297 D.artwork $ d_Trees inh{inh_dtc_para = id} ts
300 d_key name | null ts =
301 B.CustomLeaf (B.Text name) True mempty
303 B.CustomParent (B.Text name) $
306 d_Tokens :: Tokens -> DTC
307 d_Tokens tok = goTokens tok
309 -- indent = Text.replicate (columnPos pos - 1) " "
311 go (TokenPlain t) = B.toMarkup t
312 go (TokenTag t) = D.ref mempty ! DA.to (attrValue t)
313 go (TokenEscape c) = B.toMarkup c
314 go (TokenLink lnk) = D.eref (B.toMarkup lnk) ! DA.to (attrValue lnk)
315 go (TokenPair PairSlash ts) = D.i $ goTokens ts
316 go (TokenPair PairBackquote ts) = D.code $ goTokens ts
317 go (TokenPair PairFrenchquote toks@(Tokens ts)) =
320 (Seq.viewl -> TokenPlain l :< ls) ->
324 TokenPlain (Text.dropWhile Char.isSpace l)
325 <|(m|>TokenPlain (Text.dropWhileEnd Char.isSpace r))
328 TokenPlain (Text.dropAround Char.isSpace l) <| ls
329 (Seq.viewr -> rs :> TokenPlain r) ->
331 rs |> TokenPlain (Text.dropAround Char.isSpace r)
333 go (TokenPair PairHash (toList -> [TokenPlain ts])) =
334 D.ref mempty ! DA.to (attrValue ts)
335 go (TokenPair (PairElem name attrs) ts) =
338 Tokens s | Seq.null s ->
339 B.CustomLeaf (B.Text name) True mempty
340 _ -> B.CustomParent (B.Text name) $ goTokens ts
341 go (TokenPair p ts) = do
342 let (o,c) = pairBorders p ts
346 goTokens :: Tokens -> DTC
347 goTokens (Tokens ts) = foldMap go ts
349 d_Attrs :: Attrs -> DTC -> DTC
350 d_Attrs = flip $ foldl' d_Attr
352 d_Attr :: DTC -> (Text,Attr) -> DTC
353 d_Attr acc (_,Attr{..}) =
359 -- attr_id :: Text -> [(Text,Text)] -> [(Text,Text)]
360 -- attr_id title = ("id",title)
362 -- * Type 'Attributes'
363 type Attributes = Map Name Text
365 d_Attributes :: Attributes -> DTC -> DTC
366 d_Attributes = flip $ Map.foldrWithKey $ \n v ->
367 B.AddCustomAttribute (B.Text n) (B.Text v)
369 partitionAttributesChildren ::
371 (Attributes, Trees Key Tokens)
372 partitionAttributesChildren ts = (attrs,children)
379 TreeN (KeyEqual n _wh) a -> Map.insert n v acc
382 Write.text Write.config_text{Write.config_text_escape = False} $
383 mapTreeKey cell1 (\_path -> cell1) <$> a
384 -- Write.treeRackUpLeft <$> a
387 children = Seq.filter (\t ->
390 TreeN KeyEqual{} _cs -> False