Skip to content

Commit 16e923e

Browse files
committed
Introduce ANSI link support
The `Attr` constructor grows a field for a link target, which is just a `Maybe Text` for the time being. We deem nested links to be illegal, like HTML, and so the rendering state only has to keep track of one link at a time. When rendering to ANSI, we use OSC8 to include the link in the output. OSC8 links support an "id" parameter which tells terminals to treat discontiguous linked text spans as being "the same" link, for mouseover purposes. Our code could grow to support this.
1 parent 949d42f commit 16e923e

File tree

4 files changed

+61
-29
lines changed

4 files changed

+61
-29
lines changed

src/Text/DocLayout.hs

+37-15
Original file line numberDiff line numberDiff line change
@@ -70,6 +70,7 @@ module Text.DocLayout (
7070
, magenta
7171
, cyan
7272
, white
73+
, link
7374
, empty
7475
-- * Functions for concatenating documents
7576
, (<+>)
@@ -151,6 +152,7 @@ data Doc a = Text Int a -- ^ Text with specified width.
151152
| BlankLines Int -- ^ Ensure a number of blank lines.
152153
| Concat (Doc a) (Doc a) -- ^ Two documents concatenated.
153154
| Styled StyleReq (Doc a)
155+
| Linked Text (Doc a) -- ^ A hyperlink
154156
| Empty
155157
deriving (Show, Read, Eq, Ord, Functor, Foldable, Traversable,
156158
Data, Typeable, Generic)
@@ -263,6 +265,7 @@ data RenderState a = RenderState{
263265
, column :: Int
264266
, newlines :: Int -- ^ Number of preceding newlines
265267
, fontStack :: [Font]
268+
, linkTarget :: Maybe Text -- ^ Current link target
266269
}
267270

268271
peekFont :: RenderState a -> Font
@@ -276,9 +279,9 @@ newline = do
276279
let rawpref = prefix st'
277280
when (column st' == 0 && usePrefix st' && not (T.null rawpref)) $ do
278281
let pref = fromString $ T.unpack $ T.dropWhileEnd isSpace rawpref
279-
modify $ \st -> st{ output = Attr baseFont pref : output st
282+
modify $ \st -> st{ output = Attr Nothing baseFont pref : output st
280283
, column = column st + realLength pref }
281-
modify $ \st -> st { output = Attr baseFont "\n" : output st
284+
modify $ \st -> st { output = Attr Nothing baseFont "\n" : output st
282285
, column = 0
283286
, newlines = newlines st + 1
284287
}
@@ -289,9 +292,9 @@ outp off s = do -- offset >= 0 (0 might be combining char)
289292
let pref = if usePrefix st' then fromString $ T.unpack $ prefix st' else mempty
290293
let font = peekFont st'
291294
when (column st' == 0 && not (isNull pref && font == baseFont)) $
292-
modify $ \st -> st{ output = Attr baseFont pref : output st
295+
modify $ \st -> st{ output = Attr Nothing baseFont pref : output st
293296
, column = column st + realLength pref }
294-
modify $ \st -> st{ output = Attr font s : output st
297+
modify $ \st -> st{ output = Attr (linkTarget st) font s : output st
295298
, column = column st + off
296299
, newlines = 0 }
297300

@@ -302,22 +305,23 @@ render :: HasChars a => Maybe Int -> Doc a -> a
302305
render = renderPlain
303306

304307
renderANSI :: HasChars a => Maybe Int -> Doc a -> TL.Text
305-
renderANSI n d = B.toLazyText $ snd $ go $ prerender n d where
306-
go (Attributed s) = foldl attrRender (baseFont, B.fromText "") s
308+
renderANSI n d = B.toLazyText $ (\(_,_,o) -> o) $ go $ prerender n d where
309+
go (Attributed s) = foldl attrRender (Nothing, baseFont, B.fromText "") s
307310

308311
renderPlain :: HasChars a => Maybe Int -> Doc a -> a
309312
renderPlain n d = go $ prerender n d where
310313
go (Attributed s) = foldMap attrStrip s
311314

312315
attrStrip :: HasChars a => Attr a -> a
313-
attrStrip (Attr _ y) | isNull y = ""
314-
| otherwise = y
316+
attrStrip (Attr _ _ y) | isNull y = ""
317+
| otherwise = y
315318

316-
attrRender :: HasChars a => (Font, B.Builder) -> Attr a -> (Font, B.Builder)
317-
attrRender (f, acc) (Attr g y)
318-
| isNull y = (f, acc)
319-
| otherwise = (g, acc <> B.fromText newFont <> build y)
319+
attrRender :: HasChars a => (Link, Font, B.Builder) -> Attr a -> (Link, Font, B.Builder)
320+
attrRender (l, f, acc) (Attr m g y)
321+
| isNull y = (l, f, acc)
322+
| otherwise = (m, g, acc <> B.fromText newFont <> B.fromText newLink <> build y)
320323
where
324+
newLink = if l == m then mempty else renderOSC8 m
321325
newFont = if f == g then mempty else renderFont g
322326

323327
prerender :: HasChars a => Maybe Int -> Doc a -> Attributed a
@@ -330,7 +334,8 @@ prerender linelen doc = fromList . reverse . output $
330334
, lineLength = linelen
331335
, column = 0
332336
, newlines = 2
333-
, fontStack = [] }
337+
, fontStack = []
338+
, linkTarget = Nothing }
334339

335340
renderDoc :: HasChars a => Doc a -> DocState a
336341
renderDoc = renderList . normalize . unfoldD
@@ -393,7 +398,7 @@ renderList (CookedText off s : xs) = do
393398
let pref = if usePrefix st' then fromString $ T.unpack $ prefix st' else mempty
394399
let elems (Attributed x) = reverse $ toList x
395400
when (column st' == 0 && not (isNull pref)) $
396-
modify $ \st -> st{ output = Attr baseFont pref : output st
401+
modify $ \st -> st{ output = Attr Nothing baseFont pref : output st
397402
, column = column st + realLength pref }
398403
modify $ \st -> st{ output = elems s ++ output st
399404
, column = column st + off
@@ -409,6 +414,18 @@ renderList (Styled style doc : xs) = do
409414
modify $ \s -> s{ fontStack = fontStack st, output = output s }
410415
renderList xs
411416

417+
-- Nested links are nonsensical, we only handle the outermost and
418+
-- silently ignore any attempts to have a link inside a link
419+
renderList (Linked target doc : xs) = do
420+
st <- get
421+
case linkTarget st of
422+
Nothing -> do
423+
modify $ \s -> s{linkTarget = Just target}
424+
renderDoc doc
425+
modify $ \s -> s{linkTarget = Nothing}
426+
_ -> renderDoc doc
427+
renderList xs
428+
412429
renderList (Prefixed pref d : xs) = do
413430
st <- get
414431
let oldPref = prefix st
@@ -477,7 +494,7 @@ renderList (b : xs) | isBlock b = do
477494
heightOf _ = 1
478495
let maxheight = maximum $ map heightOf (b:bs)
479496
let toBlockSpec (Block w ls) = (w, ls)
480-
toBlockSpec (VFill w t) = (w, map (singleton . (Attr font)) (take maxheight $ repeat t))
497+
toBlockSpec (VFill w t) = (w, map (singleton . (Attr (linkTarget st) font)) (take maxheight $ repeat t))
481498
toBlockSpec _ = (0, [])
482499
let (_, lns') = foldl (mergeBlocks maxheight) (toBlockSpec b)
483500
(map toBlockSpec bs)
@@ -522,6 +539,7 @@ startsBlank (BlankLines _) = True
522539
startsBlank (Concat Empty y) = startsBlank y
523540
startsBlank (Concat x _) = startsBlank x
524541
startsBlank (Styled _ x) = startsBlank x
542+
startsBlank (Linked _ x) = startsBlank x
525543
startsBlank Empty = True
526544

527545
isBlock :: Doc a -> Bool
@@ -639,6 +657,7 @@ getOffset breakWhen (!l, !c) x =
639657
CookedText n _ -> (l, c + n)
640658
Empty -> (l, c)
641659
Styled _ d -> getOffset breakWhen (l, c) d
660+
Linked _ d -> getOffset breakWhen (l, c) d
642661
CarriageReturn -> (max l c, 0)
643662
NewLine -> (max l c, 0)
644663
BlankLines _ -> (max l c, 0)
@@ -805,6 +824,9 @@ cyan = Cyan
805824
white :: Color
806825
white = White
807826

827+
link :: HasChars a => Text -> Doc a -> Doc a
828+
link = Linked
829+
808830
-- | Returns width of a character in a monospace font: 0 for a combining
809831
-- character, 1 for a regular character, 2 for an East Asian wide character.
810832
-- Ambiguous characters are treated as width 1.

src/Text/DocLayout/ANSIFont.hs

+9-2
Original file line numberDiff line numberDiff line change
@@ -12,22 +12,25 @@ module Text.DocLayout.ANSIFont
1212
, Background(..)
1313
, (~>)
1414
, renderFont
15+
, renderOSC8
1516
) where
1617

1718
import Data.Data (Data)
1819
import Data.String
20+
import Data.Text (Text)
1921

2022
data Font = Font
2123
{ ftWeight :: Weight,
2224
ftShape :: Shape,
2325
ftUnderline :: Underline,
2426
ftForeground :: Foreground,
25-
ftBackground :: Background
27+
ftBackground :: Background,
28+
ftLink :: Maybe Text
2629
}
2730
deriving (Show, Eq, Read, Data, Ord)
2831

2932
baseFont :: Font
30-
baseFont = Font Normal Roman ULNone FGDefault BGDefault
33+
baseFont = Font Normal Roman ULNone FGDefault BGDefault Nothing
3134

3235
data Weight = Normal | Bold deriving (Show, Eq, Read, Data, Ord)
3336
data Shape = Roman | Italic deriving (Show, Eq, Read, Data, Ord)
@@ -84,3 +87,7 @@ renderFont f
8487
<> renderSGR (ftForeground f)
8588
<> renderSGR (ftBackground f)
8689
<> renderSGR (ftUnderline f)
90+
91+
renderOSC8 :: (Semigroup a, IsString a) => Maybe a -> a
92+
renderOSC8 Nothing = "\ESC]8;;\ESC\\"
93+
renderOSC8 (Just t) = "\ESC]8;;" <> t <> "\ESC\\"

src/Text/DocLayout/Attributed.hs

+9-6
Original file line numberDiff line numberDiff line change
@@ -2,7 +2,7 @@
22
{-# LANGUAGE DeriveTraversable #-}
33
{-# LANGUAGE DeriveDataTypeable #-}
44
{-# LANGUAGE FlexibleInstances #-}
5-
module Text.DocLayout.Attributed (Attributed(..), Attr(..), fromList, singleton)
5+
module Text.DocLayout.Attributed (Attributed(..), Attr(..), Link, fromList, singleton)
66
where
77

88
import Data.String
@@ -11,16 +11,19 @@ import Data.Data (Data, Typeable)
1111
import GHC.Generics
1212
import Data.Sequence ((><))
1313
import qualified Data.Sequence as S
14+
import Data.Text (Text)
1415

15-
data Attr a = Attr Font a
16+
type Link = Maybe Text
17+
18+
data Attr a = Attr Link Font a
1619
deriving (Show, Read, Eq, Ord, Functor, Foldable, Traversable,
1720
Data, Typeable, Generic)
1821

1922
instance Semigroup a => Semigroup (Attr a) where
20-
(<>) (Attr f x) (Attr _ y) = Attr f $ x <> y -- This is arbitrary
23+
(<>) (Attr l f x) (Attr _ _ y) = Attr l f $ x <> y -- This is arbitrary
2124

2225
instance (IsString a, Monoid a) => Monoid (Attr a) where
23-
mempty = Attr baseFont (fromString "")
26+
mempty = Attr Nothing baseFont (fromString "")
2427

2528
newtype Attributed a = Attributed (S.Seq (Attr a))
2629
deriving (Show, Read, Eq, Ord, Functor, Foldable, Traversable,
@@ -33,10 +36,10 @@ singleton :: Attr a -> Attributed a
3336
singleton = Attributed . S.singleton
3437

3538
instance IsString a => IsString (Attr a) where
36-
fromString x = Attr baseFont (fromString x)
39+
fromString x = Attr Nothing baseFont (fromString x)
3740

3841
instance IsString a => IsString (Attributed a) where
39-
fromString x = Attributed $ S.singleton $ Attr baseFont (fromString x)
42+
fromString x = Attributed $ S.singleton $ Attr Nothing baseFont (fromString x)
4043

4144
instance Semigroup a => Semigroup (Attributed a) where
4245
(<>) (Attributed a) (Attributed b) = Attributed $ a >< b

src/Text/DocLayout/HasChars.hs

+6-6
Original file line numberDiff line numberDiff line change
@@ -60,19 +60,19 @@ instance HasChars TL.Text where
6060
build = B.fromLazyText
6161

6262
instance HasChars a => HasChars (Attr a) where
63-
foldrChar f a (Attr _ x) = foldrChar f a x
64-
foldlChar f a (Attr _ x) = foldlChar f a x
65-
splitLines (Attr f x) = Attr f <$> splitLines x
66-
build (Attr _ x) = build x
63+
foldrChar f a (Attr _ _ x) = foldrChar f a x
64+
foldlChar f a (Attr _ _ x) = foldlChar f a x
65+
splitLines (Attr l f x) = Attr l f <$> splitLines x
66+
build (Attr _ _ x) = build x
6767

6868
instance (HasChars a) => HasChars (Attributed a) where
6969
foldrChar _ acc (Attributed S.Empty) = acc
70-
foldrChar f acc (Attributed (xs :|> (Attr _ x))) =
70+
foldrChar f acc (Attributed (xs :|> (Attr _ _ x))) =
7171
let l = foldrChar f acc x
7272
innerFold e a = foldrChar f a e
7373
in foldr innerFold l xs
7474
foldlChar _ acc (Attributed S.Empty) = acc
75-
foldlChar f acc (Attributed ((Attr _ x) :<| xs)) =
75+
foldlChar f acc (Attributed ((Attr _ _ x) :<| xs)) =
7676
let l = foldlChar f acc x
7777
innerFold e a = foldlChar f a e
7878
in foldr innerFold l xs

0 commit comments

Comments
 (0)