Skip to content

Commit

Permalink
More work on typst formatter.
Browse files Browse the repository at this point in the history
  • Loading branch information
jgm committed Jan 7, 2025
1 parent b5105ed commit a70cc0e
Show file tree
Hide file tree
Showing 4 changed files with 130 additions and 115 deletions.
223 changes: 108 additions & 115 deletions skylighting-format-typst/src/Skylighting/Format/Typst.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,7 +8,6 @@ module Skylighting.Format.Typst (
) where

import Control.Monad (mplus)
import Data.Char (isSpace)
import Data.List (sort)
import qualified Data.Map as Map
import Data.Text (Text)
Expand All @@ -19,134 +18,128 @@ import Text.Printf
import Data.Semigroup
#endif

formatTypst :: Bool -> [SourceLine] -> Text
formatTypst inline = Text.intercalate (Text.singleton '\n')
. map (sourceLineToTypst inline)

-- | Formats tokens as Typst using custom commands inside
-- @|@ characters. Assumes that @|@ is defined as a short verbatim
-- command by the macros produced by 'styleToTypst'.
-- A @KeywordTok@ is rendered using @\\KeywordTok{..}@, and so on.
formatTypstInline :: FormatOptions -> [SourceLine] -> Text
formatTypstInline _opts ls = "\\VERB|" <> formatTypst True ls <> "|"

sourceLineToTypst :: Bool -> SourceLine -> Text
sourceLineToTypst inline = mconcat . map (tokenToTypst inline)

tokenToTypst :: Bool -> Token -> Text
tokenToTypst inline (NormalTok, txt)
| Text.all isSpace txt = escapeTypst inline txt
tokenToTypst inline (toktype, txt) = Text.cons '\\'
(Text.pack (show toktype) <> "{" <> escapeTypst inline txt <> "}")

escapeTypst :: Bool -> Text -> Text
escapeTypst inline = Text.concatMap escapeTypstChar
where escapeTypstChar c =
case c of
'\\' -> "\\textbackslash{}"
'{' -> "\\{"
'}' -> "\\}"
'|' | inline -> "\\VerbBar{}" -- used in inline verbatim
'_' -> "\\_"
'&' -> "\\&"
'%' -> "\\%"
'#' -> "\\#"
'`' -> "\\textasciigrave{}"
'\'' -> "\\textquotesingle{}"
'-' -> "{-}" -- prevent ligatures
'~' -> "\\textasciitilde{}"
'^' -> "\\^{}"
'>' -> "\\textgreater{}"
'<' -> "\\textless{}"
_ -> Text.singleton c
formatTypstInline _opts = Text.intercalate newline . map sourceLineToTypst

newline :: Text
newline = "#EndLine()\n"

sourceLineToTypst :: SourceLine -> Text
sourceLineToTypst = mconcat . map tokenToTypst

tokenToTypst :: Token -> Text
tokenToTypst (toktype, txt) =
"#" <> Text.pack (show toktype) <> "(" <> doubleQuoted txt <> ");"

doubleQuoted :: Text -> Text
doubleQuoted t = "\"" <> escape t <> "\""
where
escape = Text.concatMap escapeChar
escapeChar '\\' = "\\\\"
escapeChar '"' = "\\\""
escapeChar c = Text.singleton c

-- Typst

-- | Format tokens as a Typst @Highlighting@ environment inside a
-- @Shaded@ environment. @Highlighting@ and @Shaded@ are
-- defined by the macros produced by 'styleToTypst'. @Highlighting@
-- is a verbatim environment using @fancyvrb@; @\\@, @{@, and @}@
-- have their normal meanings inside this environment, so that
-- formatting commands work. @Shaded@ is either nothing
-- (if the style's background color is default) or a @snugshade@
-- environment from @framed@, providing a background color
-- for the whole code block, even if it spans multiple pages.
-- Skylighting block that can be styled. @Skylighting@ is
-- defined by the macros produced by 'styleToTypst'.
formatTypstBlock :: FormatOptions -> [SourceLine] -> Text
formatTypstBlock opts ls = Text.unlines
["\\begin{Shaded}"
,"\\begin{Highlighting}[" <>
(if numberLines opts
then "numbers=left," <>
(if startNumber opts == 1
then ""
else ",firstnumber=" <>
Text.pack (show (startNumber opts))) <> ","
else Text.empty) <> "]"
,formatTypst False ls
,"\\end{Highlighting}"
,"\\end{Shaded}"]
formatTypstBlock opts ls =
"#Skylighting(" <>
(if numberLines opts
then "number: true, start: " <> Text.pack (show (startNumber opts)) <> ")"
else ")") <>
"[" <> formatTypstInline opts ls <> "];"

-- | Converts a 'Style' to a set of Typst macro definitions,
-- which should be placed in the document's preamble.
-- Note: default Typst setup doesn't allow boldface typewriter font.
-- To make boldface work in styles, you need to use a different typewriter
-- font. This will work for computer modern:
--
-- > \DeclareFontShape{OT1}{cmtt}{bx}{n}{<5><6><7><8><9><10><10.95><12><14.4><17.28><20.74><24.88>cmttb10}{}
--
-- Or, with xelatex:
--
-- > \usepackage{fontspec}
-- > \setmainfont[SmallCapsFont={* Caps}]{Latin Modern Roman}
-- > \setsansfont{Latin Modern Sans}
-- > \setmonofont[SmallCapsFont={Latin Modern Mono Caps}]{Latin Modern Mono Light}
--
styleToTypst :: Style -> Text
styleToTypst f = Text.unlines $
[ "\\usepackage{color}"
, "\\usepackage{fancyvrb}"
, "\\newcommand{\\VerbBar}{|}"
, "\\newcommand{\\VERB}{\\Verb[commandchars=\\\\\\{\\}]}"
, "\\DefineVerbatimEnvironment{Highlighting}{Verbatim}{commandchars=\\\\\\{\\}}"
, "% Add ',fontsize=\\small' for more characters per line"
] ++
(case backgroundColor f of
Nothing -> ["\\newenvironment{Shaded}{}{}"]
Just (RGB r g b) -> ["\\usepackage{framed}"
,Text.pack
(printf "\\definecolor{shadecolor}{RGB}{%d,%d,%d}" r g b)
,"\\newenvironment{Shaded}{\\begin{snugshade}}{\\end{snugshade}}"])
++ sort (map (macrodef (defaultColor f) (Map.toList (tokenStyles f)))
(enumFromTo KeywordTok NormalTok))
styleToTypst f = "TODO"


-- #let Skylighting(body, number: false, start: 1) = body
-- #let EndLine() = raw("\n")
--
-- #let KeywordTok(s) = raw(s)
-- #let DataTypeTok(s) = raw(s)
-- #let DecValTok(s) = raw(s)
-- #let BaseNTok(s) = raw(s)
-- #let FloatTok(s) = raw(s)
-- #let ConstantTok(s) = raw(s)
-- #let CharTok(s) = raw(s)
-- #let SpecialCharTok(s) = raw(s)
-- #let StringTok(s) = raw(s)
-- #let VerbatimStringTok(s) = raw(s)
-- #let SpecialStringTok(s) = raw(s)
-- #let ImportTok(s) = raw(s)
-- #let CommentTok(s) = raw(s)
-- #let DocumentationTok(s) = raw(s)
-- #let AnnotationTok(s) = raw(s)
-- #let CommentVarTok(s) = raw(s)
-- #let OtherTok(s) = raw(s)
-- #let FunctionTok(s) = raw(s)
-- #let VariableTok(s) = raw(s)
-- #let ControlFlowTok(s) = raw(s)
-- #let OperatorTok(s) = raw(s)
-- #let BuiltInTok(s) = raw(s)
-- #let ExtensionTok(s) = raw(s)
-- #let PreprocessorTok(s) = raw(s)
-- #let AttributeTok(s) = raw(s)
-- #let RegionMarkerTok(s) = raw(s)
-- #let InformationTok(s) = raw(s)
-- #let WarningTok(s) = raw(s)
-- #let AlertTok(s) = raw(s)
-- #let ErrorTok(s) = raw(s)
-- #let NormalTok(s) = raw(s)


-- define Skylighting + all the token functions
-- (case backgroundColor f of
-- Nothing -> ["\\newenvironment{Shaded}{}{}"]
-- Just (RGB r g b) -> ["\\usepackage{framed}"
-- ,Text.pack
-- (printf "\\definecolor{shadecolor}{RGB}{%d,%d,%d}" r g b)
-- ,"\\newenvironment{Shaded}{\\begin{snugshade}}{\\end{snugshade}}"])
-- ++ sort (map (macrodef (defaultColor f) (Map.toList (tokenStyles f)))
-- (enumFromTo KeywordTok NormalTok))

-- also define EndLine
-- #raw(\"\\n\")"

macrodef :: Maybe Color -> [(TokenType, TokenStyle)] -> TokenType -> Text
macrodef defaultcol tokstyles tokt = "\\newcommand{\\"
<> Text.pack (show tokt)
<> "}[1]{"
<> Text.pack (co . ul . bf . it . bg $ "#1")
<> "}"
where tokf = case lookup tokt tokstyles of
Nothing -> defStyle
Just x -> x
ul x = if tokenUnderline tokf
then "\\underline{" <> x <> "}"
else x
it x = if tokenItalic tokf
then "\\textit{" <> x <> "}"
else x
bf x = if tokenBold tokf
then "\\textbf{" <> x <> "}"
else x
bcol = fromColor `fmap` tokenBackground tokf
:: Maybe (Double, Double, Double)
bg x = case bcol of
Nothing -> x
Just (r, g, b) ->
printf "\\colorbox[rgb]{%0.2f,%0.2f,%0.2f}{%s}" r g b x
col = fromColor `fmap` (tokenColor tokf `mplus` defaultcol)
:: Maybe (Double, Double, Double)
co x = case col of
Nothing -> x
Just (r, g, b) ->
printf "\\textcolor[rgb]{%0.2f,%0.2f,%0.2f}{%s}" r g b x
macrodef defaultcol tokstyles tokt = "TODO"
-- "\\newcommand{\\"
-- <> Text.pack (show tokt)
-- <> "}[1]{"
-- <> Text.pack (co . ul . bf . it . bg $ "#1")
-- <> "}"
-- where tokf = case lookup tokt tokstyles of
-- Nothing -> defStyle
-- Just x -> x
-- ul x = if tokenUnderline tokf
-- then "\\underline{" <> x <> "}"
-- else x
-- it x = if tokenItalic tokf
-- then "\\textit{" <> x <> "}"
-- else x
-- bf x = if tokenBold tokf
-- then "\\textbf{" <> x <> "}"
-- else x
-- bcol = fromColor `fmap` tokenBackground tokf
-- :: Maybe (Double, Double, Double)
-- bg x = case bcol of
-- Nothing -> x
-- Just (r, g, b) ->
-- printf "\\colorbox[rgb]{%0.2f,%0.2f,%0.2f}{%s}" r g b x
-- col = fromColor `fmap` (tokenColor tokf `mplus` defaultcol)
-- :: Maybe (Double, Double, Double)
-- co x = case col of
-- Nothing -> x
-- Just (r, g, b) ->
-- printf "\\textcolor[rgb]{%0.2f,%0.2f,%0.2f}{%s}" r g b x

18 changes: 18 additions & 0 deletions skylighting/bin/main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -45,6 +45,7 @@ data HighlightFormat = FormatANSI
| FormatConTeXt
| FormatHtml
| FormatLaTeX
| FormatTypst
| FormatNative
deriving (Eq, Show)

Expand Down Expand Up @@ -147,6 +148,7 @@ formatOf (Format s : _) = case map toLower s of
"context"-> return FormatConTeXt
"html" -> return FormatHtml
"latex" -> return FormatLaTeX
"typst" -> return FormatTypst
"native" -> return FormatNative
_ -> err $ "Unknown format: " ++ s
formatOf (_ : xs) = formatOf xs
Expand Down Expand Up @@ -249,6 +251,7 @@ main = do
FormatConTeXt-> hlConTeXt fragment fname highlightOpts style sourceLines
FormatHtml -> hlHtml fragment fname highlightOpts style sourceLines
FormatLaTeX -> hlLaTeX fragment fname highlightOpts style sourceLines
FormatTypst -> hlTypst fragment fname highlightOpts style sourceLines
FormatNative -> putStrLn $ ppShow sourceLines

hlANSI :: FormatOptions
Expand Down Expand Up @@ -298,6 +301,21 @@ hlLaTeX frag fname opts sty sourceLines =
macros = styleToLaTeX sty
pageTitle = "\\title{" <> Text.pack fname <> "}\n"

hlTypst :: Bool -- ^ Fragment
-> FilePath -- ^ Filename
-> FormatOptions
-> Style
-> [SourceLine]
-> IO ()
hlTypst frag fname opts sty sourceLines =
if frag
then Text.putStrLn fragment
else Text.putStrLn $ macros <> pageTitle <> fragment
where fragment = formatTypstBlock opts sourceLines
macros = styleToTypst sty
pageTitle = "== " <> Text.pack fname <> "\n"


hlConTeXt :: Bool -- ^ Fragment
-> FilePath -- ^ Filename
-> FormatOptions
Expand Down
2 changes: 2 additions & 0 deletions skylighting/skylighting.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -46,6 +46,7 @@ library
, skylighting-format-blaze-html:Skylighting.Format.HTML
, skylighting-format-context:Skylighting.Format.ConTeXt
, skylighting-format-latex:Skylighting.Format.LaTeX
, skylighting-format-typst:Skylighting.Format.Typst
other-modules:
Skylighting.Syntax.Abc
Skylighting.Syntax.Actionscript
Expand Down Expand Up @@ -217,6 +218,7 @@ library
skylighting-format-context >= 0.1 && < 0.2,
skylighting-format-latex >= 0.1 && < 0.2,
skylighting-format-blaze-html >= 0.1 && < 0.2,
skylighting-format-typst >= 0.1 && < 0.2,
containers,
binary
hs-source-dirs: src
Expand Down
2 changes: 2 additions & 0 deletions skylighting/src/Skylighting.hs
Original file line number Diff line number Diff line change
Expand Up @@ -17,6 +17,7 @@ module Skylighting
, module Skylighting.Format.ConTeXt
, module Skylighting.Format.HTML
, module Skylighting.Format.LaTeX
, module Skylighting.Format.Typst
, module Skylighting.Loader

)
Expand All @@ -27,6 +28,7 @@ import Skylighting.Format.ANSI
import Skylighting.Format.ConTeXt
import Skylighting.Format.HTML
import Skylighting.Format.LaTeX
import Skylighting.Format.Typst
import Skylighting.Parser
import Skylighting.Regex
import Skylighting.Styles
Expand Down

0 comments on commit a70cc0e

Please sign in to comment.