show count of how often a cert has been temporarily trusted
[diohsc.git] / TextGemini.hs
blob5d210716c7893c97f43073e10366b91d17866e7a
1 -- This file is part of Diohsc
2 -- Copyright (C) 2020 Martin Bays <mbays@sdf.org>
3 --
4 -- This program is free software: you can redistribute it and/or modify
5 -- it under the terms of version 3 of the GNU General Public License as
6 -- published by the Free Software Foundation, or any later version.
7 --
8 -- You should have received a copy of the GNU General Public License
9 -- along with this program. If not, see http://www.gnu.org/licenses/.
11 {-# LANGUAGE CPP #-}
12 {-# LANGUAGE OverloadedStrings #-}
13 {-# LANGUAGE Safe #-}
15 module TextGemini where
17 import Control.Monad.State
18 import Data.Maybe (catMaybes, isJust, mapMaybe)
20 import ANSIColour
22 import qualified Data.Text.Lazy as T
23 import URI
25 data Link = Link { linkUri :: URIRef, linkDescription :: T.Text }
26 deriving (Eq,Ord,Show)
28 data GeminiLine
29 = TextLine T.Text
30 | LinkLine { linkLineIndex :: Int, linkLineLink :: Link }
31 | AltTextLine T.Text
32 | PreformatToggleLine
33 | PreformattedLine T.Text T.Text
34 | HeadingLine Int T.Text
35 | ItemLine T.Text
36 | QuoteLine T.Text
37 | ErrorLine T.Text
38 deriving (Eq,Ord,Show)
40 newtype GeminiDocument = GeminiDocument { geminiDocumentLines :: [GeminiLine] }
41 deriving (Eq,Ord,Show)
43 extractLinks :: GeminiDocument -> [Link]
44 extractLinks (GeminiDocument ls) = mapMaybe linkOfLine ls
45 where
46 linkOfLine (LinkLine _ link) = Just link
47 linkOfLine _ = Nothing
49 data PreOpt
50 = PreOptAlt
51 | PreOptPre
52 | PreOptBoth
53 deriving (Eq,Ord,Show)
55 showPreOpt :: PreOpt -> String
56 showPreOpt PreOptAlt = "alt"
57 showPreOpt PreOptPre = "pre"
58 showPreOpt PreOptBoth = "both"
60 data GemRenderOpts = GemRenderOpts
61 { grOptsAnsi :: Bool
62 , grOptsPre :: PreOpt
63 , grOptsWrapWidth :: Int
64 , grOptsLinkDescFirst :: Bool
65 } deriving (Eq,Ord,Show)
67 printGemDoc :: GemRenderOpts -> (URIRef -> T.Text) -> GeminiDocument -> [T.Text]
68 printGemDoc (GemRenderOpts ansi preOpt width linkDescFirst)
69 showUri (GeminiDocument doc) = concatMap printLine doc
70 where
71 printLine (TextLine line) = wrapWith "" False line
72 printLine (AltTextLine line)
73 | preOpt == PreOptPre || T.null line = []
74 | otherwise = (:[]) $ applyIf ansi withBoldStr "`` " <> line
76 printLine PreformatToggleLine = []
78 printLine (PreformattedLine alt line)
79 | preOpt == PreOptAlt && not (T.null alt) = []
80 | otherwise = (:[]) $ applyIf ansi ((resetCode <>) . withBoldStr) "` " <> line
81 printLine (HeadingLine level line) = (:[])
82 . ((T.take (fromIntegral level) (T.repeat '#') <> " ") <>)
83 . applyIf ansi
84 ( applyIf (level /= 2) withUnderlineStr
85 . applyIf (level < 3) withBoldStr )
86 $ line
87 printLine (ItemLine line) = wrapWith "* " False line
88 printLine (QuoteLine line) = wrapWith "> " True line
89 printLine (ErrorLine line) = (:[]) $ applyIf ansi (withColourStr Red)
90 "! Formatting error in text/gemini: " <> line
91 printLine (LinkLine n (Link uri desc)) =
92 wrapWith (T.pack $ '[' : show (n+1) ++ if n+1 < 10 then "] " else "] ") False
93 $ (if T.null desc then id
94 else (if linkDescFirst then id else flip) (\a b -> a <> " " <> b)
95 $ applyIf ansi (withColourStr Cyan) desc)
96 (showUri uri)
98 wrapWith :: T.Text -> Bool -> T.Text -> [T.Text]
99 wrapWith pre onAll line =
100 concat . zipWith prependHeader lineHeaders $ wrap (width - n) line
101 where
102 n = visibleLength pre
103 lineHeaders = (pre:) . repeat $
104 if onAll then pre else T.replicate (fromIntegral n) " "
105 splitWordHeader = if n > 0 then "|" <> T.replicate (fromIntegral n - 1) " " else ""
106 prependHeader header (l:ls) = header <> l : ((splitWordHeader <>) <$> ls)
107 prependHeader _ [] = []
109 wrap :: Int -> T.Text -> [[T.Text]]
110 wrap wrapWidth line = wrap' "" 0 $ T.words line
111 where
112 maxWCWidth = 2
113 ww = max maxWCWidth wrapWidth
114 wrap' l n ws | n > ww =
115 chunkVisible l : wrap' "" 0 ws
116 where
117 chunkVisible s | T.null s = []
118 chunkVisible s = let (a,b) = splitAtVisible ww s in a : chunkVisible b
119 wrap' l _ [] = [[l]]
120 wrap' l n (w:ws) =
121 let l' = if T.null l then w else l <> " " <> w
122 nw = visibleLength w
123 n' = n + nw + (if T.null l then 0 else 1)
124 in if n' > ww
125 then (if T.null l then id else ([l]:)) $ wrap' w nw ws
126 else wrap' l' n' ws
129 data GeminiParseState = GeminiParseState { numLinks :: Int, preformatted :: Maybe T.Text }
131 initialParseState :: GeminiParseState
132 initialParseState = GeminiParseState 0 Nothing
134 parseGemini :: T.Text -> GeminiDocument
135 parseGemini text = GeminiDocument . catMaybes $ evalState
136 (forM (T.lines text) (parseLine . stripTrailingCR)) initialParseState
137 where
138 stripTrailingCR = T.dropWhileEnd (== '\r')
139 parseLine :: T.Text -> State GeminiParseState (Maybe GeminiLine)
140 parseLine line = do
141 pre <- gets preformatted
142 case T.take 1 line of
143 "`" | T.take 3 line == "```", isJust pre -> do
144 modify $ \s -> s { preformatted = Nothing }
145 return $ case T.strip $ T.drop 3 line of
146 "" -> Nothing
147 _ -> Just . ErrorLine $ "Illegal non-empty text after closing '```'"
148 -- ^The spec says we MUST ignore any text on a "```" line closing a preformatted
149 -- block. This seems like a gaping extensibility hole to me, so I'm interpreting it
150 -- as not disallowing an error message.
151 "`" | T.take 3 line == "```" ->
152 let alt = T.strip $ T.drop 3 line in do
153 modify $ \s -> s { preformatted = Just alt }
154 return . Just . AltTextLine $ alt
155 _ | Just alt <- pre ->
156 return . Just $ PreformattedLine alt line
157 "=" | T.take 2 line == "=>" ->
158 case parseLink . T.dropWhile isGemWhitespace $ T.drop 2 line of
159 Nothing -> return . Just . ErrorLine $ "Unparseable link line: " <> line
160 Just link -> do
161 n <- gets numLinks
162 modify $ \s -> s { numLinks = n + 1 }
163 return . Just $ LinkLine n link
164 "#" | headers <- T.length . T.takeWhile (== '#') $ line,
165 headers > 0 && headers < 4 ->
166 return . Just . HeadingLine (fromIntegral headers) .
167 T.dropWhile isGemWhitespace . T.dropWhile (== '#') $ line
168 "*" | T.take 2 line == "* " ->
169 return . Just . ItemLine $ T.drop 2 line
170 ">" ->
171 return . Just . QuoteLine $ T.drop 1 line
172 _ ->
173 return . Just $ TextLine line
175 parseLink :: T.Text -> Maybe Link
176 parseLink linkInfo =
177 let uriText = T.takeWhile (not . isGemWhitespace) linkInfo
178 desc = T.dropWhile isGemWhitespace . T.dropWhile (not . isGemWhitespace) $ linkInfo
179 in (`Link` desc) <$> parseUriReference (
180 #ifdef IRILinks
181 escapeIRI $
182 #endif
183 T.unpack uriText)
185 isGemWhitespace :: Char -> Bool
186 isGemWhitespace = (`elem` (" \t"::String))