[Haskell-cafe] Colored Haskell Listings in LaTeX

Oleg Grenrus oleg.grenrus at iki.fi
Thu Jun 21 17:22:26 UTC 2018


Hi Artem,

I answer with inline lhs2Tex file. Hopefully it helps in your typed-code
type-settings!

cheers, Oleg.

\documentclass{article}
%include polycode.fmt

\usepackage{hyperref}
\hypersetup{pdfborder={0 0 0}}

% in lhs2TeX.style there are
%
% \newcommand{\Conid}[1]{{\mathit #1}}
% \newcommand{\Varid}[1]{{\mathit #1}}
% \newcommand{\anonymous}{\_}
%
% We can renew these

\usepackage{xcolor}
\definecolor{darkred}{rgb}{.5,0,0}
\definecolor{darkgreen}{rgb}{0,0.5,0}
\definecolor{darkblue}{rgb}{0,0,.5}
\definecolor{color4}{rgb}{0,.4,.4}
\definecolor{color5}{rgb}{.4,.4,0}

\renewcommand{\Conid}[1]{{\color{darkblue}\mathit #1}}

% however types and constructors look the same, we can differentiate
them though

%format Foo = "{\color{darkred}\mathit Foo}"
%format MkFoo = "{\color{darkgreen}\mathit Foo}"

% Note how I "cheat" making MkFoo render as Foo!

% We can also highlight operators
%format + = "\mathbin{\color{color4}+}"

% or symbols (note I also make thing look prettier)"
%format plusFoo = "{\color{color5}\mathit plus_{Foo}}"
%format ColorsInLhs2TeX = "{\text{Colors in lhs2\TeX}}"

\begin{document}

An example of colorful lhs2\TeX\ file.
See the source at
\url{https://github.com/phadej/gists/blob/master/posts/2018-06-21-colors-in-lhs2tex.tex}%
\footnote{It's named tex to trick \emph{Pandoc} in my blog setup},
and the result PDF at
\url{https://github.com/phadej/gists/blob/master/pdf/ColorsInLhs2TeX.pdf}

\begin{code}
module ColorsInLhs2TeX where

newtype Foo = MkFoo Int

plusFoo :: Foo -> Foo -> Int
plusFoo (MkFoo n) (MkFoo m) = n + m
\end{code}
\end{document}


On 21.06.2018 18:29, Artem Pelenitsyn wrote:
> Dear Cafe,
>
> In his recent Stitch manuscript,
> https://cs.brynmawr.edu/~rae/papers/2018/stitch/stitch.pdf
> <https://cs.brynmawr.edu/%7Erae/papers/2018/stitch/stitch.pdf>
> Richard Eisenberg mentions that he uses lhs2TeX to typeset Haskell
> listings, but I'm not aware of the support for colors in lhs2TeX. Can
> anyone suggest how to get such a nice code highlighting (presumably
> with lhs2TeX).
>
> --
> Best wishes,
> Artem
>
>
> _______________________________________________
> Haskell-Cafe mailing list
> To (un)subscribe, modify options or view archives go to:
> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
> Only members subscribed via the mailman list are allowed to post.



More information about the Haskell-Cafe mailing list