]> Git — Sourcephile - haskell/symantic.git/blob - symantic-document/Symantic/Document/Sym.hs
document: remove Language. prefix in module names
[haskell/symantic.git] / symantic-document / Symantic / Document / Sym.hs
1 {-# LANGUAGE GeneralizedNewtypeDeriving #-}
2 module Symantic.Document.Sym where
3
4 import Data.Bool
5 import Data.Char (Char)
6 import Data.Eq (Eq(..))
7 import Data.Foldable (Foldable, foldr, foldr1)
8 import Data.Function ((.), ($))
9 import Data.Functor (Functor(..))
10 import Data.Int (Int)
11 import Data.Maybe (Maybe(..))
12 import Data.Monoid (Monoid(..))
13 import Data.Ord (Ord(..), Ordering(..))
14 import Data.Semigroup (Semigroup(..))
15 import Data.String (String, IsString)
16 import Prelude (Integer, fromIntegral, Num(..), pred, undefined, Integral, Real, Enum)
17 import Text.Show (Show(..))
18 import qualified Data.Foldable as Foldable
19 import qualified Data.List as List
20 import qualified Data.Text as Text
21 import qualified Data.Text.Lazy as TL
22
23 -- * Type 'Nat'
24 newtype Nat = Nat { unNat :: Integer }
25 deriving (Eq, Ord, Show, Integral, Real, Enum)
26 unLength :: Nat -> Integer
27 unLength (Nat i) = i
28 instance Num Nat where
29 fromInteger i | 0 <= i = Nat i
30 | otherwise = undefined
31 abs = Nat . abs . unLength
32 signum = signum . signum
33 Nat x + Nat y = Nat (x + y)
34 Nat x * Nat y = Nat (x * y)
35 Nat x - Nat y | x >= y = Nat (x - y)
36 | otherwise = undefined
37
38 -- * Class 'Lengthable'
39 class Lengthable a where
40 length :: a -> Nat
41 instance Lengthable Char where
42 length _ = Nat 1
43 instance Lengthable [a] where
44 length = Nat . fromIntegral . List.length
45 instance Lengthable Text.Text where
46 length = Nat . fromIntegral . Text.length
47 instance Lengthable TL.Text where
48 length = Nat . fromIntegral . TL.length
49
50 -- * Class 'Splitable'
51 class Monoid a => Splitable a where
52 null :: a -> Bool
53 tail :: a -> a
54 break :: (Char -> Bool) -> a -> (a, a)
55 lines :: a -> [a]
56 lines = splitOnChar (== '\n')
57 words :: a -> [a]
58 words = splitOnChar (== ' ')
59 splitOnChar :: (Char -> Bool) -> a -> [a]
60 splitOnChar c a =
61 if null a then []
62 else let (l,a') = break c a in
63 l : if null a' then []
64 else let a'' = tail a' in
65 if null a'' then [mempty] else splitOnChar c a''
66 instance Splitable String where
67 null = List.null
68 tail = List.tail
69 break = List.break
70 instance Splitable Text.Text where
71 null = Text.null
72 tail = Text.tail
73 break = Text.break
74 instance Splitable TL.Text where
75 null = TL.null
76 tail = TL.tail
77 break = TL.break
78
79 -- * Type 'Column'
80 type Column = Nat
81
82 -- ** Type 'Indent'
83 type Indent = Column
84
85 -- * Class 'Textable'
86 class (IsString d, Semigroup d) => Textable d where
87 empty :: d
88 charH :: Char -- ^ XXX: MUST NOT be '\n'
89 -> d
90 stringH :: String -- ^ XXX: MUST NOT contain '\n'
91 -> d
92 textH :: Text.Text -- ^ XXX: MUST NOT contain '\n'
93 -> d
94 ltextH :: TL.Text -- ^ XXX: MUST NOT contain '\n'
95 -> d
96 default empty :: Textable (ReprOf d) => Trans d => d
97 default charH :: Textable (ReprOf d) => Trans d => Char -> d
98 default stringH :: Textable (ReprOf d) => Trans d => String -> d
99 default textH :: Textable (ReprOf d) => Trans d => Text.Text -> d
100 default ltextH :: Textable (ReprOf d) => Trans d => TL.Text -> d
101 empty = trans empty
102 charH = trans . charH
103 stringH = trans . stringH
104 textH = trans . textH
105 ltextH = trans . ltextH
106
107 newline :: d
108 space :: d
109 -- | @x '<+>' y = x '<>' 'space' '<>' y@
110 (<+>) :: d -> d -> d
111 -- | @x '</>' y = x '<>' 'newline' '<>' y@
112 (</>) :: d -> d -> d
113 int :: Int -> d
114 integer :: Integer -> d
115 char :: Char -> d
116 string :: String -> d
117 text :: Text.Text -> d
118 ltext :: TL.Text -> d
119 catH :: Foldable f => f d -> d
120 catV :: Foldable f => f d -> d
121 unwords :: Foldable f => f d -> d
122 unlines :: Foldable f => f d -> d
123 foldrWith :: Foldable f => (d -> d -> d) -> f d -> d
124 foldWith :: Foldable f => (d -> d) -> f d -> d
125 intercalate :: Foldable f => d -> f d -> d
126 between :: d -> d -> d -> d
127 replicate :: Int -> d -> d
128
129 newline = "\n"
130 space = char ' '
131 x <+> y = x <> space <> y
132 x </> y = x <> newline <> y
133 int = stringH . show
134 integer = stringH . show
135 char = \case '\n' -> newline; c -> charH c
136 string = catV . fmap stringH . lines
137 text = catV . fmap textH . lines
138 ltext = catV . fmap ltextH . lines
139 catH = foldr (<>) empty
140 catV = foldrWith (\x y -> x<>newline<>y)
141 unwords = foldr (<>) space
142 unlines = foldr (\x y -> x<>newline<>y) empty
143 foldrWith f ds = if Foldable.null ds then empty else foldr1 f ds
144 foldWith f = foldrWith $ \a acc -> a <> f acc
145 intercalate sep = foldrWith (\x y -> x<>sep<>y)
146 between o c d = o<>d<>c
147 replicate cnt t | cnt <= 0 = empty
148 | otherwise = t <> replicate (pred cnt) t
149
150 -- * Class 'Indentable'
151 class Textable d => Indentable d where
152 -- | @('align' d)@ make @d@ uses current 'Column' as 'Indent' level.
153 align :: d -> d
154 default align :: Indentable (ReprOf d) => Trans d => d -> d
155 align = trans1 align
156 -- | @('incrIndent' ind d)@ make @d@ uses current 'Indent' plus @ind@ as 'Indent' level.
157 incrIndent :: Indent -> d -> d
158 default incrIndent :: Indentable (ReprOf d) => Trans d => Indent -> d -> d
159 incrIndent = trans1 . incrIndent
160 -- | @('withIndent' ind d)@ make @d@ uses @ind@ as 'Indent' level.
161 withIndent :: Indent -> d -> d
162 default withIndent :: Indentable (ReprOf d) => Trans d => Indent -> d -> d
163 withIndent = trans1 . withIndent
164 -- | @('withNewline' nl d)@ make @d@ uses @nl@ as 'newline'.
165 --
166 -- Useful values for @nl@ are: 'empty', 'newlineWithIndent', 'newlineWithoutIndent'.
167 withNewline :: d -> d -> d
168 newlineWithoutIndent :: d
169 newlineWithIndent :: d
170 default withNewline :: Indentable (ReprOf d) => Trans d => d -> d -> d
171 default newlineWithoutIndent :: Indentable (ReprOf d) => Trans d => d
172 default newlineWithIndent :: Indentable (ReprOf d) => Trans d => d
173 withNewline = trans2 withNewline
174 newlineWithoutIndent = trans newlineWithoutIndent
175 newlineWithIndent = trans newlineWithIndent
176 -- | @('column' f)@ write @f@ applied to the current 'Column'.
177 column :: (Column -> d) -> d
178 default column :: Indentable (ReprOf d) => Trans d => (Column -> d) -> d
179 column f = trans $ column (unTrans . f)
180 -- | @('indent' f)@ write @f@ applied to the current 'Indent'.
181 indent :: (Indent -> d) -> d
182 default indent :: Indentable (ReprOf d) => Trans d => (Indent -> d) -> d
183 indent f = trans $ indent (unTrans . f)
184
185 -- | @('hang' ind d)@ make @d@ uses current 'Column' plus @ind@ as 'Indent' level.
186 hang :: Indent -> d -> d
187 hang ind = align . incrIndent ind
188
189 -- | @('endToEndWidth' d f)@ write @d@ then
190 -- @f@ applied to the absolute value of the difference between
191 -- the end 'Column' and start 'Column' of @d@.
192 --
193 -- Note that @f@ is given the end-to-end width,
194 -- which is not necessarily the maximal width.
195 endToEndWidth :: d -> (Column -> d) -> d
196 endToEndWidth d f =
197 column $ \c1 ->
198 (d <>) $
199 column $ \c2 ->
200 f $ if c2 - c1 >= 0
201 then c2 - c1
202 else c1 - c2
203
204 -- | @'spaces' ind = 'replicate' ind 'space'@
205 spaces :: Indent -> d
206 spaces i = replicate (fromIntegral i) space
207
208 -- | @('fill' ind d)@ write @d@,
209 -- then if @d@ is not wider than @ind@,
210 -- write the difference with 'spaces'.
211 fill :: Indent -> d -> d
212 fill m d =
213 endToEndWidth d $ \w ->
214 case w`compare`m of
215 LT -> spaces $ m - w
216 _ -> empty
217
218 -- | @('breakableFill' ind d)@ write @d@,
219 -- then if @d@ is not wider than @ind@, write the difference with 'spaces'
220 -- otherwise write a 'newline' indented to to the start 'Column' of @d@ plus @ind@.
221 breakableFill :: Indent -> d -> d
222 breakableFill m d =
223 column $ \c ->
224 endToEndWidth d $ \w ->
225 case w`compare`m of
226 LT -> spaces (m - w)
227 EQ -> empty
228 GT -> withIndent (c + m) newline
229
230 -- * Class 'Breakable'
231 class (Textable d, Indentable d) => Breakable d where
232 -- | @('breakable' f)@ write @f@ applied to whether breaks are activated or not.
233 breakable :: (Maybe Column -> d) -> d
234 default breakable :: Breakable (ReprOf d) => Trans d => (Maybe Column -> d) -> d
235 breakable f = trans $ breakable (unTrans . f)
236 -- | @('withBreakable' b d)@ whether to active breaks or not within @d@.
237 withBreakable :: Maybe Column -> d -> d
238 default withBreakable :: Breakable (ReprOf d) => Trans d => Maybe Column -> d -> d
239 withBreakable = trans1 . withBreakable
240
241 -- | @('ifBreak' onWrap onNoWrap)@
242 -- write @onWrap@ if @onNoWrap@ leads to a 'Column'
243 -- greater or equal to the one sets with 'withBreakable',
244 -- otherwise write @onNoWrap@.
245 ifBreak :: d -> d -> d
246 default ifBreak :: Breakable (ReprOf d) => Trans d => d -> d -> d
247 ifBreak = trans2 ifBreak
248 -- | @('breakpoint' onNoBreak onBreak d)@
249 -- write @onNoBreak@ then @d@ if they fit,
250 -- @onBreak@ otherwise.
251 breakpoint :: d -> d -> d -> d
252 default breakpoint :: Breakable (ReprOf d) => Trans d => d -> d -> d -> d
253 breakpoint = trans3 breakpoint
254
255 -- | @('breakableEmpty' d)@ write @d@ if it fits, 'newline' then @d@ otherwise.
256 breakableEmpty :: d -> d
257 breakableEmpty = breakpoint empty newline
258
259 -- | @x '><' y = x '<>' 'breakableEmpty' y@
260 (><) :: d -> d -> d
261 x >< y = x <> breakableEmpty y
262
263 -- | @('breakableSpace' d)@ write 'space' then @d@ it they fit,
264 -- 'newline' then @d@ otherwise.
265 breakableSpace :: d -> d
266 breakableSpace = breakpoint space newline
267
268 -- | @x '>+<' y = x '<>' 'breakableSpace' y@
269 (>+<) :: d -> d -> d
270 x >+< y = x <> breakableSpace y
271
272 -- | @'breakableSpaces' ds@ intercalate a 'breakableSpace'
273 -- between items of @ds@.
274 breakableSpaces :: Foldable f => f d -> d
275 breakableSpaces = foldWith breakableSpace
276
277 -- | @('intercalateHorV' sep ds)@
278 -- write @ds@ with @sep@ intercalated if the whole fits,
279 -- otherwise write 'align' of @ds@ with 'newline' and @sep@ intercalated.
280 intercalateHorV :: Foldable f => d -> f d -> d
281 intercalateHorV sep xs =
282 ifBreak
283 (align $ foldWith ((newline <> sep) <>) xs)
284 (foldWith (sep <>) xs)
285
286 -- * Class 'Colorable'
287 class Colorable d where
288 -- | @('colorable' f)@ write @f@ applied to whether colors are activated or not.
289 colorable :: (Bool -> d) -> d
290 default colorable :: Colorable (ReprOf d) => Trans d => (Bool -> d) -> d
291 colorable f = trans $ colorable (unTrans . f)
292 -- | @('withColor' b d)@ whether to active colors or not within @d@.
293 withColorable :: Bool -> d -> d
294 default withColorable :: Colorable (ReprOf d) => Trans d => Bool -> d -> d
295 withColorable = trans1 . withColorable
296
297 reverse :: d -> d
298
299 -- Foreground colors
300 -- Dull
301 black :: d -> d
302 red :: d -> d
303 green :: d -> d
304 yellow :: d -> d
305 blue :: d -> d
306 magenta :: d -> d
307 cyan :: d -> d
308 white :: d -> d
309
310 -- Vivid
311 blacker :: d -> d
312 redder :: d -> d
313 greener :: d -> d
314 yellower :: d -> d
315 bluer :: d -> d
316 magentaer :: d -> d
317 cyaner :: d -> d
318 whiter :: d -> d
319
320 -- Background colors
321 -- Dull
322 onBlack :: d -> d
323 onRed :: d -> d
324 onGreen :: d -> d
325 onYellow :: d -> d
326 onBlue :: d -> d
327 onMagenta :: d -> d
328 onCyan :: d -> d
329 onWhite :: d -> d
330
331 -- Vivid
332 onBlacker :: d -> d
333 onRedder :: d -> d
334 onGreener :: d -> d
335 onYellower :: d -> d
336 onBluer :: d -> d
337 onMagentaer :: d -> d
338 onCyaner :: d -> d
339 onWhiter :: d -> d
340
341 default reverse :: Colorable (ReprOf d) => Trans d => d -> d
342 default black :: Colorable (ReprOf d) => Trans d => d -> d
343 default red :: Colorable (ReprOf d) => Trans d => d -> d
344 default green :: Colorable (ReprOf d) => Trans d => d -> d
345 default yellow :: Colorable (ReprOf d) => Trans d => d -> d
346 default blue :: Colorable (ReprOf d) => Trans d => d -> d
347 default magenta :: Colorable (ReprOf d) => Trans d => d -> d
348 default cyan :: Colorable (ReprOf d) => Trans d => d -> d
349 default white :: Colorable (ReprOf d) => Trans d => d -> d
350 default blacker :: Colorable (ReprOf d) => Trans d => d -> d
351 default redder :: Colorable (ReprOf d) => Trans d => d -> d
352 default greener :: Colorable (ReprOf d) => Trans d => d -> d
353 default yellower :: Colorable (ReprOf d) => Trans d => d -> d
354 default bluer :: Colorable (ReprOf d) => Trans d => d -> d
355 default magentaer :: Colorable (ReprOf d) => Trans d => d -> d
356 default cyaner :: Colorable (ReprOf d) => Trans d => d -> d
357 default whiter :: Colorable (ReprOf d) => Trans d => d -> d
358 default onBlack :: Colorable (ReprOf d) => Trans d => d -> d
359 default onRed :: Colorable (ReprOf d) => Trans d => d -> d
360 default onGreen :: Colorable (ReprOf d) => Trans d => d -> d
361 default onYellow :: Colorable (ReprOf d) => Trans d => d -> d
362 default onBlue :: Colorable (ReprOf d) => Trans d => d -> d
363 default onMagenta :: Colorable (ReprOf d) => Trans d => d -> d
364 default onCyan :: Colorable (ReprOf d) => Trans d => d -> d
365 default onWhite :: Colorable (ReprOf d) => Trans d => d -> d
366 default onBlacker :: Colorable (ReprOf d) => Trans d => d -> d
367 default onRedder :: Colorable (ReprOf d) => Trans d => d -> d
368 default onGreener :: Colorable (ReprOf d) => Trans d => d -> d
369 default onYellower :: Colorable (ReprOf d) => Trans d => d -> d
370 default onBluer :: Colorable (ReprOf d) => Trans d => d -> d
371 default onMagentaer :: Colorable (ReprOf d) => Trans d => d -> d
372 default onCyaner :: Colorable (ReprOf d) => Trans d => d -> d
373 default onWhiter :: Colorable (ReprOf d) => Trans d => d -> d
374
375 reverse = trans1 reverse
376 black = trans1 black
377 red = trans1 red
378 green = trans1 green
379 yellow = trans1 yellow
380 blue = trans1 blue
381 magenta = trans1 magenta
382 cyan = trans1 cyan
383 white = trans1 white
384 blacker = trans1 blacker
385 redder = trans1 redder
386 greener = trans1 greener
387 yellower = trans1 yellower
388 bluer = trans1 bluer
389 magentaer = trans1 magentaer
390 cyaner = trans1 cyaner
391 whiter = trans1 whiter
392 onBlack = trans1 onBlack
393 onRed = trans1 onRed
394 onGreen = trans1 onGreen
395 onYellow = trans1 onYellow
396 onBlue = trans1 onBlue
397 onMagenta = trans1 onMagenta
398 onCyan = trans1 onCyan
399 onWhite = trans1 onWhite
400 onBlacker = trans1 onBlacker
401 onRedder = trans1 onRedder
402 onGreener = trans1 onGreener
403 onYellower = trans1 onYellower
404 onBluer = trans1 onBluer
405 onMagentaer = trans1 onMagentaer
406 onCyaner = trans1 onCyaner
407 onWhiter = trans1 onWhiter
408
409 -- * Class 'Decorable'
410 class Decorable d where
411 -- | @('decorable' f)@ write @f@ applied to whether decorations are activated or not.
412 decorable :: (Bool -> d) -> d
413 default decorable :: Decorable (ReprOf d) => Trans d => (Bool -> d) -> d
414 decorable f = trans $ decorable (unTrans . f)
415 -- | @('withColor' b d)@ whether to active decorations or not within @d@.
416 withDecorable :: Bool -> d -> d
417 default withDecorable :: Decorable (ReprOf d) => Trans d => Bool -> d -> d
418 withDecorable = trans1 . withDecorable
419
420 bold :: d -> d
421 underline :: d -> d
422 italic :: d -> d
423 default bold :: Decorable (ReprOf d) => Trans d => d -> d
424 default underline :: Decorable (ReprOf d) => Trans d => d -> d
425 default italic :: Decorable (ReprOf d) => Trans d => d -> d
426 bold = trans1 bold
427 underline = trans1 underline
428 italic = trans1 italic
429
430 -- * Class 'Trans'
431 class Trans tr where
432 -- | Return the underlying @tr@ of the transformer.
433 type ReprOf tr :: *
434
435 -- | Lift a tr to the transformer's.
436 trans :: ReprOf tr -> tr
437 -- | Unlift a tr from the transformer's.
438 unTrans :: tr -> ReprOf tr
439
440 -- | Identity transformation for a unary symantic method.
441 trans1 :: (ReprOf tr -> ReprOf tr) -> (tr -> tr)
442 trans1 f = trans . f . unTrans
443
444 -- | Identity transformation for a binary symantic method.
445 trans2
446 :: (ReprOf tr -> ReprOf tr -> ReprOf tr)
447 -> (tr -> tr -> tr)
448 trans2 f t1 t2 = trans (f (unTrans t1) (unTrans t2))
449
450 -- | Identity transformation for a ternary symantic method.
451 trans3
452 :: (ReprOf tr -> ReprOf tr -> ReprOf tr -> ReprOf tr)
453 -> (tr -> tr -> tr -> tr)
454 trans3 f t1 t2 t3 = trans (f (unTrans t1) (unTrans t2) (unTrans t3))