diff options
Diffstat (limited to 'src/Text/Pandoc/Writers/ConTeXt.hs')
| -rw-r--r-- | src/Text/Pandoc/Writers/ConTeXt.hs | 23 |
1 files changed, 12 insertions, 11 deletions
diff --git a/src/Text/Pandoc/Writers/ConTeXt.hs b/src/Text/Pandoc/Writers/ConTeXt.hs index ebdc4a3d3..1f8bbcdba 100644 --- a/src/Text/Pandoc/Writers/ConTeXt.hs +++ b/src/Text/Pandoc/Writers/ConTeXt.hs @@ -1,6 +1,6 @@ {-# LANGUAGE OverloadedStrings #-} {- -Copyright (C) 2007-2014 John MacFarlane <jgm@berkeley.edu> +Copyright (C) 2007-2015 John MacFarlane <jgm@berkeley.edu> This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by @@ -19,7 +19,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA {- | Module : Text.Pandoc.Writers.ConTeXt - Copyright : Copyright (C) 2007-2014 John MacFarlane + Copyright : Copyright (C) 2007-2015 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane <jgm@berkeley.edu> @@ -119,7 +119,7 @@ stringToConTeXt opts = concatMap (escapeCharForConTeXt opts) toLabel :: String -> String toLabel z = concatMap go z where go x - | elem x "\\#[]\",{}%()|=" = "ux" ++ printf "%x" (ord x) + | elem x ("\\#[]\",{}%()|=" :: String) = "ux" ++ printf "%x" (ord x) | otherwise = [x] -- | Convert Elements to ConTeXt @@ -151,7 +151,13 @@ blockToConTeXt (CodeBlock _ str) = -- blankline because \stoptyping can't have anything after it, inc. '}' blockToConTeXt (RawBlock "context" str) = return $ text str <> blankline blockToConTeXt (RawBlock _ _ ) = return empty -blockToConTeXt (Div _ bs) = blockListToConTeXt bs +blockToConTeXt (Div (ident,_,_) bs) = do + contents <- blockListToConTeXt bs + if null ident + then return contents + else return $ + ("\\reference" <> brackets (text $ toLabel ident) <> braces empty <> + "%") $$ contents blockToConTeXt (BulletList lst) = do contents <- mapM listItemToConTeXt lst return $ ("\\startitemize" <> if isTightList lst @@ -296,13 +302,8 @@ inlineToConTeXt (Link txt (('#' : ref), _)) = do opts <- gets stOptions contents <- inlineListToConTeXt txt let ref' = toLabel $ stringToConTeXt opts ref - return $ text "\\in" - <> braces (if writerNumberSections opts - then contents <+> text "(\\S" - else contents) -- prefix - <> braces (if writerNumberSections opts - then text ")" - else empty) -- suffix + return $ text "\\goto" + <> braces contents <> brackets (text ref') inlineToConTeXt (Link txt (src, _)) = do |
