module Highlighter.Highlighter where import Data.Text import Common import System.Console.ANSI (Color(..), Underlining(..), SGR(..), setSGRCode) import DiffRender.DiffRender -- Mostly for use with highlighting and not actual token parsing. -- This represent any tokens we want to show in editors with highlighting. class Highlightable a where getTokenLoc :: a -> Location highlight :: (StyledText, Maybe a) -> StyledText pairWithTokens :: [a] -> Int -> Text -> ([(Text, Maybe a)], [a]) -- ^ Associate token type with their text sources -- First arg is stack of tokens at current location -- Second arg is the text offset at current location -- Third arg is the text at the current location -- -- This is so that in an editor, a line of text can break at somewhere in the -- middle of a single token. So an editor cannot display tokenwise without more -- complex tracking of current offset in source text. instance Highlightable Text where highlight (x, _) = x pairWithTokens _ _ t = ([(t, Nothing)], []) getTokenLoc = error "No token location for text" underlineText :: Text -> Text underlineText t = let startCode = (setSGRCode [SetUnderlining SingleUnderline]) endCode = setSGRCode [] in (pack startCode) <> t <> (pack endCode) colorText :: Color -> Color -> Text -> StyledText colorText fg bg t = StyledText (FgBg fg bg) [Plain t] colorTextFg :: Color -> Text -> StyledText colorTextFg fg t = StyledText (Fg fg) [Plain t]