]> Git — Sourcephile - haskell/symantic.git/blob - symantic-document/Language/Symantic/Document/Term/IO.hs
Fix writeSGR on/off.
[haskell/symantic.git] / symantic-document / Language / Symantic / Document / Term / IO.hs
1 module Language.Symantic.Document.Term.IO
2 ( module Language.Symantic.Document.Sym
3 , module Language.Symantic.Document.Term.IO
4 ) where
5
6 import Control.Applicative (Applicative(..))
7 import Data.Bool
8 import Data.Function (($), (.), id)
9 import Data.Monoid (Monoid(..))
10 import Data.Ord (Ord(..))
11 import Data.Semigroup (Semigroup(..))
12 import Data.String (IsString(..))
13 import GHC.Exts (IsList(..))
14 import Prelude (pred, fromIntegral, Num(..))
15 import System.Console.ANSI
16 import System.IO (IO)
17 import Text.Show (Show(..))
18 import qualified Data.List as List
19 import qualified Data.Text.IO as Text
20 import qualified Data.Text.Lazy.IO as TL
21 import qualified System.IO as IO
22
23 import Language.Symantic.Document.Sym
24
25 -- * Type 'Reader'
26 data Reader
27 = Reader
28 { reader_indent :: !Indent -- ^ Current indentation level, used by 'newline'.
29 , reader_newline :: TermIO -- ^ How to display 'newline'.
30 , reader_wrap_column :: !Column -- ^ 'Column' after which 'wrap' breaks on a 'breakpoint' or 'breakspace'.
31 , reader_sgr :: ![SGR] -- ^ Active ANSI codes.
32 , reader_handle :: !IO.Handle -- ^ Where to write.
33 , reader_colorable :: !Bool -- ^ Whether colors are activated or not.
34 , reader_decorable :: !Bool -- ^ Whether decorations are activated or not.
35 }
36
37 -- | Default 'Reader'.
38 defReader :: Reader
39 defReader = Reader
40 { reader_indent = 0
41 , reader_newline = newlineWithIndent
42 , reader_wrap_column = Nat 80
43 , reader_sgr = []
44 , reader_handle = IO.stdout
45 , reader_colorable = True
46 , reader_decorable = True
47 }
48
49 -- * Type 'State'
50 type State = Column
51
52 -- | Default 'State'.
53 defState :: State
54 defState = 0
55
56 -- * Type 'TermIO'
57 newtype TermIO
58 = TermIO
59 { unTermIO :: Reader -> State ->
60 (State -> IO () -> IO ()) -> -- normal continuation
61 (State -> IO () -> IO ()) -> -- should-wrap continuation
62 IO () }
63
64 -- | Write a 'TermIO'.
65 runTermIO :: IO.Handle -> TermIO -> IO ()
66 runTermIO h (TermIO p) = p defReader{reader_handle=h} defState oko oko
67 where oko _st = id
68
69 instance IsList TermIO where
70 type Item TermIO = TermIO
71 fromList = mconcat
72 toList = pure
73 instance Semigroup TermIO where
74 x <> y = TermIO $ \ro st ok ko ->
75 unTermIO x ro st
76 (\sx tx -> unTermIO y ro sx
77 (\sy ty -> ok sy (tx<>ty))
78 (\sy ty -> ko sy (tx<>ty)))
79 (\sx tx -> unTermIO y ro sx
80 (\sy ty -> ko sy (tx<>ty))
81 (\sy ty -> ko sy (tx<>ty)))
82 instance Monoid TermIO where
83 mempty = empty
84 mappend = (<>)
85 instance IsString TermIO where
86 fromString = string
87
88 writeH :: Column -> (IO.Handle -> IO ()) -> TermIO
89 writeH len t =
90 TermIO $ \ro st ok ko ->
91 let newCol = st + len in
92 (if newCol <= reader_wrap_column ro then ok else ko)
93 newCol (t (reader_handle ro))
94
95 instance Textable TermIO where
96 empty = TermIO $ \_ro st ok _ko -> ok st mempty
97 charH t = writeH 1 (`IO.hPutChar` t)
98 stringH t = writeH (length t) (`IO.hPutStr` t)
99 textH t = writeH (length t) (`Text.hPutStr` t)
100 ltextH t = writeH (length t) (`TL.hPutStr` t)
101 int = stringH . show
102 integer = stringH . show
103 replicate cnt p | cnt <= 0 = empty
104 | otherwise = p <> replicate (pred cnt) p
105 newline = TermIO $ \ro -> unTermIO (reader_newline ro) ro
106 instance Alignable TermIO where
107 align p = TermIO $ \ro st -> unTermIO p ro{reader_indent=st} st
108 withNewline nl p = TermIO $ \ro -> unTermIO p ro{reader_newline=nl}
109 withIndent ind p = TermIO $ \ro -> unTermIO p ro{reader_indent=ind}
110 incrIndent ind p = TermIO $ \ro -> unTermIO p ro{reader_indent=reader_indent ro + ind}
111 column f = TermIO $ \ro st -> unTermIO (f st) ro st
112 newlineWithoutIndent = TermIO $ \ro _st ok _ko ->
113 ok 0 $ IO.hPutChar (reader_handle ro) '\n'
114 newlineWithIndent = TermIO $ \ro@Reader{reader_handle=h} _st ok _ko ->
115 ok (reader_indent ro) $ do
116 IO.hPutChar h '\n'
117 IO.hPutStr h $ List.replicate (fromIntegral $ reader_indent ro) ' '
118 instance Wrapable TermIO where
119 ifWrap y x = TermIO $ \ro st ok ko ->
120 unTermIO x ro st ok (\_sx _tx -> unTermIO y ro st ok ko)
121 breakpoint onNoBreak onBreak p = TermIO $ \ro st ok ko ->
122 unTermIO (onNoBreak <> p) ro st ok
123 (\_sp _tp -> unTermIO (onBreak <> p) ro st ok ko)
124 withWrapColumn col p = TermIO $ \ro -> unTermIO p ro{reader_wrap_column=col}
125
126 writeSGR :: (Reader -> Bool) -> SGR -> TermIO -> TermIO
127 writeSGR isOn s (TermIO t) =
128 TermIO $ \ro ->
129 if isOn ro
130 then unTermIO (o <> m <> c) ro
131 else t ro
132 where
133 o = TermIO $ \ro st ok _ko -> ok st $ hSetSGR (reader_handle ro) [s]
134 m = TermIO $ \ro -> t ro{reader_sgr=s:reader_sgr ro}
135 c = TermIO $ \ro st ok _ko -> ok st $ hSetSGR (reader_handle ro) $ Reset:List.reverse (reader_sgr ro)
136
137 instance Colorable TermIO where
138 colorable f = TermIO $ \ro -> unTermIO (f (reader_colorable ro)) ro
139 withColorable b t = TermIO $ \ro -> unTermIO t ro{reader_colorable=b}
140 reverse = writeSGR reader_colorable $ SetSwapForegroundBackground True
141 black = writeSGR reader_colorable $ SetColor Foreground Dull Black
142 red = writeSGR reader_colorable $ SetColor Foreground Dull Red
143 green = writeSGR reader_colorable $ SetColor Foreground Dull Green
144 yellow = writeSGR reader_colorable $ SetColor Foreground Dull Yellow
145 blue = writeSGR reader_colorable $ SetColor Foreground Dull Blue
146 magenta = writeSGR reader_colorable $ SetColor Foreground Dull Magenta
147 cyan = writeSGR reader_colorable $ SetColor Foreground Dull Cyan
148 white = writeSGR reader_colorable $ SetColor Foreground Dull White
149 blacker = writeSGR reader_colorable $ SetColor Foreground Vivid Black
150 redder = writeSGR reader_colorable $ SetColor Foreground Vivid Red
151 greener = writeSGR reader_colorable $ SetColor Foreground Vivid Green
152 yellower = writeSGR reader_colorable $ SetColor Foreground Vivid Yellow
153 bluer = writeSGR reader_colorable $ SetColor Foreground Vivid Blue
154 magentaer = writeSGR reader_colorable $ SetColor Foreground Vivid Magenta
155 cyaner = writeSGR reader_colorable $ SetColor Foreground Vivid Cyan
156 whiter = writeSGR reader_colorable $ SetColor Foreground Vivid White
157 onBlack = writeSGR reader_colorable $ SetColor Background Dull Black
158 onRed = writeSGR reader_colorable $ SetColor Background Dull Red
159 onGreen = writeSGR reader_colorable $ SetColor Background Dull Green
160 onYellow = writeSGR reader_colorable $ SetColor Background Dull Yellow
161 onBlue = writeSGR reader_colorable $ SetColor Background Dull Blue
162 onMagenta = writeSGR reader_colorable $ SetColor Background Dull Magenta
163 onCyan = writeSGR reader_colorable $ SetColor Background Dull Cyan
164 onWhite = writeSGR reader_colorable $ SetColor Background Dull White
165 onBlacker = writeSGR reader_colorable $ SetColor Background Vivid Black
166 onRedder = writeSGR reader_colorable $ SetColor Background Vivid Red
167 onGreener = writeSGR reader_colorable $ SetColor Background Vivid Green
168 onYellower = writeSGR reader_colorable $ SetColor Background Vivid Yellow
169 onBluer = writeSGR reader_colorable $ SetColor Background Vivid Blue
170 onMagentaer = writeSGR reader_colorable $ SetColor Background Vivid Magenta
171 onCyaner = writeSGR reader_colorable $ SetColor Background Vivid Cyan
172 onWhiter = writeSGR reader_colorable $ SetColor Background Vivid White
173 instance Decorable TermIO where
174 decorable f = TermIO $ \ro -> unTermIO (f (reader_decorable ro)) ro
175 withDecorable b t = TermIO $ \ro -> unTermIO t ro{reader_decorable=b}
176 bold = writeSGR reader_decorable $ SetConsoleIntensity BoldIntensity
177 underline = writeSGR reader_decorable $ SetUnderlining SingleUnderline
178 italic = writeSGR reader_decorable $ SetItalicized True