Write id for code block to label attr in latex when listing is used

The code:

    ~~~{#test}
    asdf
    ~~~

gets compiled to html:

    <pre id="test">
    asdf
    </pre>

So it is possible to link to the identifier `test`

But this doesn't happen on latex

When using the listings package (`--listings`) it is possible to set the
identifier using the `label=test` property:

    \begin{lstlisting}[label=id]
    hi
    \end{lstlisting}

And this is exactly what this patch is doing.

Modified LaTeX Reader/Writer and added tests for this.
This commit is contained in:
Florian Eitel 2013-08-22 20:15:36 +02:00
parent f7c14eddd8
commit 5f09cf7ff0
4 changed files with 22 additions and 3 deletions

View file

@ -47,6 +47,7 @@ import Text.Pandoc.Builder
import Data.Char (isLetter) import Data.Char (isLetter)
import Control.Applicative import Control.Applicative
import Data.Monoid import Data.Monoid
import Data.Maybe (fromMaybe)
import System.Environment (getEnv) import System.Environment (getEnv)
import System.FilePath (replaceExtension, (</>)) import System.FilePath (replaceExtension, (</>))
import Data.List (intercalate, intersperse) import Data.List (intercalate, intersperse)
@ -901,7 +902,7 @@ environments = M.fromList
lookup "numbers" options == Just "left" ] lookup "numbers" options == Just "left" ]
++ maybe [] (:[]) (lookup "language" options ++ maybe [] (:[]) (lookup "language" options
>>= fromListingsLanguage) >>= fromListingsLanguage)
let attr = ("",classes,kvs) let attr = (fromMaybe "" (lookup "label" options),classes,kvs)
codeBlockWith attr <$> (verbEnv "lstlisting")) codeBlockWith attr <$> (verbEnv "lstlisting"))
, ("minted", do options <- option [] keyvals , ("minted", do options <- option [] keyvals
lang <- grouped (many1 $ satisfy (/='}')) lang <- grouped (many1 $ satisfy (/='}'))

View file

@ -313,7 +313,7 @@ blockToLaTeX (BlockQuote lst) = do
_ -> do _ -> do
contents <- blockListToLaTeX lst contents <- blockListToLaTeX lst
return $ "\\begin{quote}" $$ contents $$ "\\end{quote}" return $ "\\begin{quote}" $$ contents $$ "\\end{quote}"
blockToLaTeX (CodeBlock (_,classes,keyvalAttr) str) = do blockToLaTeX (CodeBlock (identifier,classes,keyvalAttr) str) = do
opts <- gets stOptions opts <- gets stOptions
case () of case () of
_ | isEnabled Ext_literate_haskell opts && "haskell" `elem` classes && _ | isEnabled Ext_literate_haskell opts && "haskell" `elem` classes &&
@ -344,7 +344,11 @@ blockToLaTeX (CodeBlock (_,classes,keyvalAttr) str) = do
[ (if key == "startFrom" [ (if key == "startFrom"
then "firstnumber" then "firstnumber"
else key) ++ "=" ++ attr | else key) ++ "=" ++ attr |
(key,attr) <- keyvalAttr ] (key,attr) <- keyvalAttr ] ++
(if identifier == ""
then []
else [ "label=" ++ identifier ])
else [] else []
printParams printParams
| null params = empty | null params = empty

View file

@ -55,6 +55,13 @@ tests = [ testGroup "basic"
"hi % this is a comment\nthere\n" =?> para "hi there" "hi % this is a comment\nthere\n" =?> para "hi there"
] ]
, testGroup "code blocks"
[ "identifier" =:
"\\begin{lstlisting}[label=test]\\end{lstlisting}" =?> codeBlockWith ("test", [], [("label","test")]) ""
, "no identifier" =:
"\\begin{lstlisting}\\end{lstlisting}" =?> codeBlock ""
]
, testGroup "citations" , testGroup "citations"
[ natbibCitations [ natbibCitations
, biblatexCitations , biblatexCitations

View file

@ -10,6 +10,9 @@ import Tests.Arbitrary()
latex :: (ToString a, ToPandoc a) => a -> String latex :: (ToString a, ToPandoc a) => a -> String
latex = writeLaTeX def . toPandoc latex = writeLaTeX def . toPandoc
latexListing :: (ToString a, ToPandoc a) => a -> String
latexListing = writeLaTeX def{ writerListings = True } . toPandoc
{- {-
"my test" =: X =?> Y "my test" =: X =?> Y
@ -31,6 +34,10 @@ tests :: [Test]
tests = [ testGroup "code blocks" tests = [ testGroup "code blocks"
[ "in footnotes" =: note (para "hi" <> codeBlock "hi") =?> [ "in footnotes" =: note (para "hi" <> codeBlock "hi") =?>
"\\footnote{hi\n\n\\begin{Verbatim}\nhi\n\\end{Verbatim}\n}" "\\footnote{hi\n\n\\begin{Verbatim}\nhi\n\\end{Verbatim}\n}"
, test latexListing "identifier" $ codeBlockWith ("id",[],[]) "hi" =?>
("\\begin{lstlisting}[label=id]\nhi\n\\end{lstlisting}" :: String)
, test latexListing "no identifier" $ codeBlock "hi" =?>
("\\begin{lstlisting}\nhi\n\\end{lstlisting}" :: String)
] ]
, testGroup "math" , testGroup "math"
[ "escape |" =: para (math "\\sigma|_{\\{x\\}}") =?> [ "escape |" =: para (math "\\sigma|_{\\{x\\}}") =?>