RST writer: Use .. code:: language
for code blocks with language.
Closes #721. Also fixed whitespace in lhs tests.
This commit is contained in:
parent
2f50406c7f
commit
9d549ab683
11 changed files with 25 additions and 20 deletions
|
@ -177,7 +177,12 @@ blockToRST (CodeBlock (_,classes,_) str) = do
|
|||
if "haskell" `elem` classes && "literate" `elem` classes &&
|
||||
isEnabled Ext_literate_haskell opts
|
||||
then return $ prefixed "> " (text str) $$ blankline
|
||||
else return $ "::" $+$ nest tabstop (text str) $$ blankline
|
||||
else return $
|
||||
(case [c | c <- classes,
|
||||
c `notElem` ["sourceCode","literate","numberLines"]] of
|
||||
[] -> "::"
|
||||
(lang:_) -> ".. code:: " <> text lang)
|
||||
$+$ nest tabstop (text str) $$ blankline
|
||||
blockToRST (BlockQuote blocks) = do
|
||||
tabstop <- get >>= (return . writerTabStop . stOptions)
|
||||
contents <- blockListToRST blocks
|
||||
|
|
|
@ -1,6 +1,6 @@
|
|||
[Header 1 ("lhs-test",[],[]) [Str "lhs",Space,Str "test"]
|
||||
,Para [Code ("",[],[]) "unsplit",Space,Str "is",Space,Str "an",Space,Str "arrow",Space,Str "that",Space,Str "takes",Space,Str "a",Space,Str "pair",Space,Str "of",Space,Str "values",Space,Str "and",Space,Str "combines",Space,Str "them",Space,Str "to",Space,Str "return",Space,Str "a",Space,Str "single",Space,Str "value:"]
|
||||
,CodeBlock ("",["sourceCode","literate","haskell"],[]) "unsplit :: (Arrow a) => (b -> c -> d) -> a (b, c) d\nunsplit = arr . uncurry \n -- arr (\\op (x,y) -> x `op` y) "
|
||||
,CodeBlock ("",["sourceCode","literate","haskell"],[]) "unsplit :: (Arrow a) => (b -> c -> d) -> a (b, c) d\nunsplit = arr . uncurry\n -- arr (\\op (x,y) -> x `op` y)"
|
||||
,Para [Code ("",[],[]) "(***)",Space,Str "combines",Space,Str "two",Space,Str "arrows",Space,Str "into",Space,Str "a",Space,Str "new",Space,Str "arrow",Space,Str "by",Space,Str "running",Space,Str "the",Space,Str "two",Space,Str "arrows",Space,Str "on",Space,Str "a",Space,Str "pair",Space,Str "of",Space,Str "values",Space,Str "(one",Space,Str "arrow",Space,Str "on",Space,Str "the",Space,Str "first",Space,Str "item",Space,Str "of",Space,Str "the",Space,Str "pair",Space,Str "and",Space,Str "one",Space,Str "arrow",Space,Str "on",Space,Str "the",Space,Str "second",Space,Str "item",Space,Str "of",Space,Str "the",Space,Str "pair)."]
|
||||
,CodeBlock ("",[],[]) "f *** g = first f >>> second g"
|
||||
,Para [Str "Block",Space,Str "quote:"]
|
||||
|
|
|
@ -31,7 +31,7 @@ code > span.er { color: #ff0000; font-weight: bold; }
|
|||
<p><code>unsplit</code> is an arrow that takes a pair of values and combines them to return a single value:</p>
|
||||
<pre class="sourceCode literate haskell"><code class="sourceCode haskell"><span class="ot">unsplit ::</span> (<span class="dt">Arrow</span> a) <span class="ot">=></span> (b <span class="ot">-></span> c <span class="ot">-></span> d) <span class="ot">-></span> a (b, c) d
|
||||
unsplit <span class="fu">=</span> arr <span class="fu">.</span> <span class="fu">uncurry</span>
|
||||
<span class="co">-- arr (\op (x,y) -> x `op` y) </span></code></pre>
|
||||
<span class="co">-- arr (\op (x,y) -> x `op` y)</span></code></pre>
|
||||
<p><code>(***)</code> combines two arrows into a new arrow by running the two arrows on a pair of values (one arrow on the first item of the pair and one arrow on the second item of the pair).</p>
|
||||
<pre><code>f *** g = first f >>> second g</code></pre>
|
||||
<p>Block quote:</p>
|
||||
|
|
|
@ -31,7 +31,7 @@ code > span.er { color: #ff0000; font-weight: bold; }
|
|||
<p><code>unsplit</code> is an arrow that takes a pair of values and combines them to return a single value:</p>
|
||||
<pre class="sourceCode literate haskell"><code class="sourceCode haskell"><span class="fu">></span><span class="ot"> unsplit ::</span> (<span class="dt">Arrow</span> a) <span class="ot">=></span> (b <span class="ot">-></span> c <span class="ot">-></span> d) <span class="ot">-></span> a (b, c) d
|
||||
<span class="fu">></span> unsplit <span class="fu">=</span> arr <span class="fu">.</span> <span class="fu">uncurry</span>
|
||||
<span class="fu">></span> <span class="co">-- arr (\op (x,y) -> x `op` y) </span></code></pre>
|
||||
<span class="fu">></span> <span class="co">-- arr (\op (x,y) -> x `op` y)</span></code></pre>
|
||||
<p><code>(***)</code> combines two arrows into a new arrow by running the two arrows on a pair of values (one arrow on the first item of the pair and one arrow on the second item of the pair).</p>
|
||||
<pre><code>f *** g = first f >>> second g</code></pre>
|
||||
<p>Block quote:</p>
|
||||
|
|
|
@ -73,7 +73,7 @@ return a single value:
|
|||
\begin{Highlighting}[]
|
||||
\OtherTok{unsplit ::} \NormalTok{(}\DataTypeTok{Arrow} \NormalTok{a) }\OtherTok{=>} \NormalTok{(b }\OtherTok{->} \NormalTok{c }\OtherTok{->} \NormalTok{d) }\OtherTok{->} \NormalTok{a (b, c) d}
|
||||
\NormalTok{unsplit }\FunctionTok{=} \NormalTok{arr }\FunctionTok{.} \FunctionTok{uncurry}
|
||||
\CommentTok{-- arr (\textbackslash{}op (x,y) -> x `op` y) }
|
||||
\CommentTok{-- arr (\textbackslash{}op (x,y) -> x `op` y)}
|
||||
\end{Highlighting}
|
||||
\end{Shaded}
|
||||
|
||||
|
|
|
@ -1,6 +1,6 @@
|
|||
[Header 1 ("",[],[]) [Str "lhs",Space,Str "test"]
|
||||
,Para [Code ("",[],[]) "unsplit",Space,Str "is",Space,Str "an",Space,Str "arrow",Space,Str "that",Space,Str "takes",Space,Str "a",Space,Str "pair",Space,Str "of",Space,Str "values",Space,Str "and",Space,Str "combines",Space,Str "them",Space,Str "to",Space,Str "return",Space,Str "a",Space,Str "single",Space,Str "value:"]
|
||||
,CodeBlock ("",["sourceCode","literate","haskell"],[]) "unsplit :: (Arrow a) => (b -> c -> d) -> a (b, c) d\nunsplit = arr . uncurry \n -- arr (\\op (x,y) -> x `op` y) "
|
||||
,CodeBlock ("",["sourceCode","literate","haskell"],[]) "unsplit :: (Arrow a) => (b -> c -> d) -> a (b, c) d\nunsplit = arr . uncurry\n -- arr (\\op (x,y) -> x `op` y)"
|
||||
,Para [Code ("",[],[]) "(***)",Space,Str "combines",Space,Str "two",Space,Str "arrows",Space,Str "into",Space,Str "a",Space,Str "new",Space,Str "arrow",Space,Str "by",Space,Str "running",Space,Str "the",Space,Str "two",Space,Str "arrows",Space,Str "on",Space,Str "a",Space,Str "pair",Space,Str "of",Space,Str "values",Space,Str "(one",Space,Str "arrow",Space,Str "on",Space,Str "the",Space,Str "first",Space,Str "item",Space,Str "of",Space,Str "the",Space,Str "pair",Space,Str "and",Space,Str "one",Space,Str "arrow",Space,Str "on",Space,Str "the",Space,Str "second",Space,Str "item",Space,Str "of",Space,Str "the",Space,Str "pair)."]
|
||||
,CodeBlock ("",[],[]) "f *** g = first f >>> second g"
|
||||
,Para [Str "Block",Space,Str "quote:"]
|
||||
|
|
|
@ -4,7 +4,7 @@ lhs test
|
|||
``unsplit`` is an arrow that takes a pair of values and combines them to
|
||||
return a single value:
|
||||
|
||||
::
|
||||
.. code:: haskell
|
||||
|
||||
unsplit :: (Arrow a) => (b -> c -> d) -> a (b, c) d
|
||||
unsplit = arr . uncurry
|
||||
|
|
Loading…
Reference in a new issue