1 {-# LANGUAGE OverloadedStrings #-}
2 {-# LANGUAGE RecordWildCards #-}
3 {-# LANGUAGE ViewPatterns #-}
4 {-# OPTIONS_GHC -fno-warn-orphans #-}
5 -- | Render a TCT file in plain Text.
6 module Language.TCT.Write.Text where
8 import Control.Monad (Monad(..), mapM)
10 import Data.Eq (Eq(..))
11 import Data.Foldable (Foldable(..))
12 import Data.Function (($), (.))
13 import Data.Functor ((<$>))
15 import Data.Int (Int64)
16 import Data.Monoid (Monoid(..))
17 import Data.Ord (Ord(..))
18 import Data.Semigroup (Semigroup(..))
19 import Data.Sequence (ViewL(..))
20 import Data.String (String)
21 import Data.Text (Text)
22 import Prelude (Num(..), undefined, Integral(..))
23 import Text.Show (Show(..))
24 import qualified Control.Monad.Trans.State as S
25 import qualified Data.List as L
26 import qualified Data.Sequence as Seq
27 import qualified Data.Text as Text
28 import qualified Data.Text.Lazy as TL
30 import Language.TCT.Tree
31 import Language.TCT.Token
32 import Language.TCT.Elem hiding (trac,dbg)
34 import Debug.Trace (trace)
35 trac :: String -> a -> a
38 dbg :: Show a => String -> a -> a
39 dbg m x = trac (m <> ": " <> show x) x
44 -- * Type 'Config_Text'
47 { config_text_escape :: Bool
50 config_text :: Config_Text
53 { config_text_escape = True
56 text :: Config_Text -> Trees (Cell Key) (Cell Token) -> TL.Text
57 text cfg tct = foldMap (t_TreeCell cfg) (treePosLastCell tct)
59 treeRackUpLeft :: Tree (Cell k) (Cell a) -> Tree (Cell k) (Cell a)
60 treeRackUpLeft t = go t
63 rackUpLeft pos = (linePos pos - l0 + 1, columnPos pos - c0 + 1)
64 go :: Tree (Cell k) (Cell a) -> Tree (Cell k) (Cell a)
65 go (Tree0 (Cell pos posEnd c)) =
66 Tree0 $ Cell (rackUpLeft pos) (rackUpLeft posEnd) c
67 go (TreeN (Cell pos posEnd c) ts) =
69 (Cell (rackUpLeft pos) (rackUpLeft posEnd) c)
72 treePosLastCell :: Trees (Cell k) (Cell a) -> Trees (Pos,Cell k) (Pos,Cell a)
73 treePosLastCell t = S.evalState (go`mapM`t) (1,1)
75 go :: Tree (Cell k) (Cell a) ->
76 S.State (Int, Int) (Tree (Pos, Cell k) (Pos, Cell a))
79 S.put $ posEndCell cell
80 return $ Tree0 (lastPos,cell)
81 go (TreeN cell ts) = do
83 S.put $ posEndCell cell
85 return $ TreeN (lastPos,cell) ts'
87 t_Value :: Text -> TL.Text
90 int64 :: Integral i => i -> Int64
91 int64 = fromInteger . toInteger
93 t_TreeCell :: Config_Text -> Tree (Pos,Cell Key) (Pos,Cell Token) -> TL.Text
94 t_TreeCell cfg (TreeN c@(_, unCell -> KeySection lvl) ts) =
96 TL.replicate (int64 lvl) "#" <> " " <>
98 Tree0 (_,Cell posTitle _ title) :< _ -> t_IndentToken cfg posTitle title
100 foldMap (t_TreeCell cfg) (case Seq.viewl ts of {Tree0{} :< ts' -> ts'; _ -> ts})
101 t_TreeCell cfg (Tree0 c@(_,cell)) =
104 t_TreeCell cfg (TreeN c@(_,cell) cs) =
106 t_CellKey cfg cell cs
108 t_IndentCell :: (Pos,Cell a) -> TL.Text
109 t_IndentCell ((lineLast,colLast),posCell -> (line,col))
111 TL.replicate (int64 $ line - (lineLast+1)) "\n" <>
112 TL.replicate (int64 $ col - 1) " "
114 && colLast <= col = TL.replicate (int64 $ col - colLast) " "
115 | otherwise = undefined
117 t_CellKey :: Config_Text -> Cell Key -> Trees (Pos,Cell Key) (Pos,Cell Token) -> TL.Text
118 t_CellKey cfg (Cell _pos _posEnd key) cells = do
120 KeyColon n wh -> t_Key n wh ":"
121 KeyGreat n wh -> t_Key n wh ">"
122 KeyEqual n wh -> t_Key n wh "="
123 KeyBar n wh -> t_Key n wh "|"
124 KeyDash -> "- " <> foldMap (t_TreeCell cfg) cells
125 KeyLower name attrs ->
126 "<" <> tl name <> t_Attrs attrs <>
127 foldMap (t_TreeCell cfg) cells
128 KeySection{} -> undefined
130 t_Key :: Text -> White -> TL.Text -> TL.Text
131 t_Key name wh mark = tl name <> tl wh <> mark <> foldMap (t_TreeCell cfg) cells
133 t_CellToken :: Config_Text -> Cell Token -> TL.Text
134 t_CellToken cfg (Cell pos _posEnd tok) =
135 t_IndentToken cfg pos tok
137 t_IndentToken :: Config_Text -> Pos -> Token -> TL.Text
138 t_IndentToken cfg pos tok = go tok `S.evalState` linePos pos
140 indent = TL.replicate (int64 $ columnPos pos - 1) " "
141 go :: Token -> S.State Int TL.Text
142 go (TokenPlain txt) = do
144 let lines = Text.splitOn "\n" txt
145 S.put (lnum - 1 + L.length lines)
149 (l0:ls) -> tl l0 <> mconcat ((\l -> "\n"<>indent<>tl l)<$>ls)
150 go (TokenTag v) = return $ "#"<>tl v
153 if config_text_escape cfg
154 then tl $ Text.pack ['\\',c]
156 go (TokenLink lnk) = return $ tl lnk
157 go (TokenPair grp t) = do
159 return $ tl o<>t'<>tl c
160 where (o,c) = pairBorders grp t
163 return $ foldr (<>) mempty ts'
165 t_Attrs :: Attrs -> TL.Text
166 t_Attrs = foldMap t_Attr
168 t_Attr :: (Text,Attr) -> TL.Text
169 t_Attr (attr_white,Attr{..}) =
179 t_Token :: Token -> TL.Text
180 t_Token (TokenPlain txt) = tl txt
181 t_Token (TokenTag v) = "#"<>tl v
182 t_Token (TokenEscape c) = TL.singleton c -- tl $ Text.pack ['\\',c]
183 t_Token (TokenLink lnk) = tl lnk
184 t_Token (TokenPair grp t) = tl o<>t_Token t<>tl c
185 where (o,c) = pairBorders grp t
186 t_Token (Tokens ts) = foldMap t_Token ts