1 {-# LANGUAGE FlexibleInstances #-}
2 {-# LANGUAGE OverloadedStrings #-}
3 {-# LANGUAGE ViewPatterns #-}
4 module Language.TCT.Write.HTML5 where
6 import Control.Monad (Monad(..), forM_, mapM_, when)
8 import Data.Char (Char)
9 import Data.Default.Class (Default(..))
10 import Data.Eq (Eq(..))
11 import Data.Foldable (Foldable(..))
12 import Data.Function (($), (.))
13 import Data.Functor.Compose (Compose(..))
14 import Data.Maybe (Maybe(..))
15 import Data.Monoid (Monoid(..))
16 import Data.Ord (Ord(..), Ordering(..))
17 import Data.Semigroup (Semigroup(..))
18 import Data.Sequence (ViewL(..))
19 import Data.String (String, IsString(..))
20 import Prelude (Num(..), undefined, error)
21 import Text.Blaze ((!))
22 import Text.Blaze.Html (Html)
23 import Text.Show (Show(..))
24 import qualified Control.Monad.Trans.State as S
25 import qualified Data.List as List
26 import qualified Data.Sequence as Seq
27 import qualified Data.Text.Lazy as TL
28 import qualified Text.Blaze.Html5 as H
29 import qualified Text.Blaze.Html5.Attributes as HA
32 -- import Language.TCT.Debug
33 import Language.TCT.Utils
34 import Text.Blaze.Utils
35 import qualified Language.TCT.Write.Plain as Plain
37 html5Document :: Trees (Cell Node) -> Html
38 html5Document body = do
42 H.meta ! HA.httpEquiv "Content-Type"
43 ! HA.content "text/html; charset=UTF-8"
44 whenJust (titleFrom body) $ \t ->
46 H.toMarkup $ Plain.text def t
47 -- link ! rel "Chapter" ! title "SomeTitle">
48 H.link ! HA.rel "stylesheet"
50 ! HA.href "style/tct-html5.css"
51 let (html5Body, State{}) =
55 H.a ! HA.id ("line-1") $ return ()
58 titleFrom :: Roots -> Maybe Root
61 Tree (unCell -> NodeHeader HeaderSection{}) _ts -> True
64 Tree (unCell -> NodeHeader (HeaderSection _lvl))
65 (Seq.viewl -> title:<_) -> Just title
69 type Html5 = StateMarkup State ()
71 instance IsString Html5 where
72 fromString = mapM_ html5ify
74 html5 :: H.ToMarkup a => a -> Html5
75 html5 = Compose . return . H.toMarkup
81 , state_indent :: Html5
82 , state_italic :: Bool
83 } -- deriving (Eq, Show)
84 instance Default State where
88 , state_italic = False
90 -- instance Pretty State
93 class Html5ify a where
94 html5ify :: a -> Html5
95 instance Html5ify () where
97 instance Html5ify Char where
100 s@State{state_pos=Pos line _col, ..} <- liftStateMarkup S.get
101 liftStateMarkup $ S.put s{state_pos=Pos (line + 1) 1}
103 H.a ! HA.id ("line-"<>attrify (line + 1)) $$ return ()
106 liftStateMarkup $ S.modify' $ \s@State{state_pos=Pos line col} ->
107 s{state_pos=Pos line (col + 1)}
109 instance Html5ify String where
110 html5ify = mapM_ html5ify
111 instance Html5ify TL.Text where
115 let (h,ts) = TL.span (/='\n') t in
118 liftStateMarkup $ S.modify' $ \s@State{state_pos=Pos line col} ->
119 s{state_pos=Pos line $ col + int (TL.length h)}
123 -- NOTE: useless to increment the pos_column for h,
124 -- since the following '\n' will reset the pos_column.
127 instance Html5ify Pos where
128 html5ify new@(Pos lineNew colNew) = do
130 { state_pos=old@(Pos lineOld colOld)
132 } <- liftStateMarkup S.get
133 case lineOld`compare`lineNew of
135 forM_ [lineOld+1..lineNew] $ \lnum -> do
137 H.a ! HA.id ("line-"<>attrify lnum) $$ return ()
138 liftStateMarkup $ S.put s{state_pos=Pos lineNew 1}
140 Pos _lineMid colMid <- liftStateMarkup $ S.gets state_pos
141 html5 $ List.replicate (colNew - colMid) ' '
142 liftStateMarkup $ S.put s{state_pos=new}
143 EQ | colOld <= colNew -> do
144 liftStateMarkup $ S.put s{state_pos=new}
145 html5 $ List.replicate (colNew - colOld) ' '
146 _ -> error $ "html5ify: non-ascending Pos:"
147 <> "\n old: " <> show old
148 <> "\n new: " <> show new
149 instance Html5ify Roots where
150 html5ify = mapM_ html5ify
151 instance Html5ify Root where
152 html5ify (Tree (Cell bp _ep nod) ts) = do
155 ----------------------
156 NodeGroup -> html5ify ts
157 ----------------------
158 NodeLower name attrs -> do
159 H.span ! HA.class_ (mconcat ["header header-lower"," header-name-",attrify name]) $$ do
160 H.span ! HA.class_ "header-mark" $$ html5ify '<'
161 H.span ! HA.class_ "header-name" $$ html5ify name
164 ----------------------
167 HeaderGreat n wh -> html5HeaderRepeated "" "" n wh ">" "" "great"
168 HeaderBar n wh -> html5HeaderRepeated "" "" n wh "|" "" "bar"
169 HeaderColon n wh -> html5Header "" "" n wh ":" "" "colon"
170 HeaderEqual n wh -> html5Header "" "" n wh "=" "" "equal"
171 HeaderDot n -> html5Header "" "" n "" "." "" "dot"
172 HeaderDotSlash n -> html5Header "./" "" (fromString n) "" "" "" "dotslash"
173 HeaderDash -> html5Header "" "" "" "" "-" " " "dash"
174 HeaderDashDash -> html5Header "" "" "" "" "--" " " "dashdash"
175 HeaderBrackets n -> html5Header "[" "" n "" "]" "" "dashdash"
176 HeaderSection lvl -> do
178 H.span ! HA.class_ "section-title" $$ do
179 H.span ! HA.class_ "section-mark" $$ do
180 html5ify $ List.replicate lvl '#'
182 title :< _ -> h lvl $$ html5ify title
195 h n | n > 6 = H.span ! HA.class_ ("h h"<>attrify n)
198 html5Head :: Name -> White -> Name -> White -> TL.Text -> White -> H.AttributeValue -> Html5
199 html5Head markBegin whmb name whn markEnd whme cl = do
200 H.span ! HA.class_ (mconcat $ ["header header-",cl] <>
201 if TL.null name then [] else [" header-name-",attrify name]) $$ do
202 when (markBegin/="") $
203 H.span ! HA.class_ "header-mark" $$ html5ify markBegin
206 H.span ! HA.class_ "header-name" $$ html5ify name
209 H.span ! HA.class_ "header-mark" $$ html5ify markEnd
211 html5Header markBegin whmb name whn markEnd whme cl = do
212 html5Head markBegin whmb name whn markEnd whme cl
213 H.span ! HA.class_ "header-value" $$
215 html5HeaderRepeated :: Name -> White -> Name -> White -> TL.Text -> White -> H.AttributeValue -> Html5
216 html5HeaderRepeated markBegin whmb name whn markEnd whme cl = do
217 State{state_indent} <- liftStateMarkup S.get
218 liftStateMarkup $ S.modify' $ \s ->
221 Pos _lineMid colMid <- liftStateMarkup $ S.gets state_pos
222 html5ify $ List.replicate (pos_column bp - colMid) ' '
223 html5Head markBegin whmb name whn markEnd whme cl
225 r <- html5Header markBegin whmb name whn markEnd whme cl
226 liftStateMarkup $ S.modify' $ \s -> s{state_indent}
228 ----------------------
230 State{state_indent} <- liftStateMarkup S.get
231 liftStateMarkup $ S.modify' $ \s ->
234 Pos _lineMid colMid <- liftStateMarkup $ S.gets state_pos
235 html5ify $ List.replicate (pos_column bp - colMid) ' '
238 liftStateMarkup $ S.modify' $ \s -> s{state_indent}
240 ----------------------
242 State{state_indent} <- liftStateMarkup S.get
243 liftStateMarkup $ S.modify' $ \s ->
246 Pos _lineMid colMid <- liftStateMarkup $ S.gets state_pos
247 html5ify $ List.replicate (pos_column bp - colMid) ' '
250 liftStateMarkup $ S.modify' $ \s -> s{state_indent}
252 ----------------------
253 NodeToken t -> html5ify t <> html5ify ts
254 ----------------------
257 PairElem name attrs -> do
258 H.span ! HA.class_ ("pair-PairElem" <> " pair-elem-"<>attrify name) $$ do
259 H.span ! HA.class_ "pair-open" $$ o
260 when (not $ null ts) $ do
261 H.span ! HA.class_ "pair-content" $$ html5ify ts
262 H.span ! HA.class_ "pair-close" $$ c
265 H.span ! HA.class_ "elem-name" $$
270 ( "<"<>html5Name<>html5ify attrs<>"/>"
273 ( "<"<>html5Name<>html5ify attrs<>">"
274 , "</"<>html5Name<>">" )
276 H.span ! HA.class_ ("pair-"<>fromString (show pair)) $$ do
277 let (o,c) = pairBorders pair ts
278 H.span ! HA.class_ "pair-open" $$ html5ify o
279 H.span ! HA.class_ "pair-content" $$ em $ html5ify ts
280 H.span ! HA.class_ "pair-close" $$ html5ify c
286 || p == PairFrenchquote
287 || p == PairDoublequote -> do
288 State{..} <- liftStateMarkup $ S.get
289 liftStateMarkup $ S.modify' $ \s -> s{state_italic = not state_italic}
290 r <- H.em ! HA.class_ (if state_italic then "even" else "odd") $$ h
291 liftStateMarkup $ S.modify' $ \s -> s{state_italic}
294 instance Html5ify Token where
297 TokenText t -> html5ify t
299 H.span ! HA.class_ "tag" $$ do
300 H.span ! HA.class_ "tag-open" $$
303 TokenEscape c -> html5ify ['\\', c]
305 H.a ! HA.href (attrify l) $$
307 instance Html5ify ElemAttrs where
308 html5ify = mapM_ html5ify
309 instance Html5ify (White,ElemAttr) where
310 html5ify (elemAttr_white,ElemAttr{..}) = do
311 html5ify elemAttr_white
312 H.span ! HA.class_ "attr-name" $$
313 html5ify elemAttr_name
314 html5ify elemAttr_open
315 H.span ! HA.class_ "attr-value" $$
316 html5ify elemAttr_value
317 html5ify elemAttr_close