aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--changelog26
-rwxr-xr-xmake_osx_package.sh8
-rwxr-xr-xosx/osx-resources/InstallationCheck (renamed from osx-resources/InstallationCheck)0
-rw-r--r--osx/osx-resources/InstallationCheck.strings (renamed from osx-resources/InstallationCheck.strings)0
-rwxr-xr-xosx/uninstall-pandoc.pl79
-rw-r--r--pandoc.cabal9
-rw-r--r--src/Text/Pandoc.hs2
-rw-r--r--src/Text/Pandoc/Parsing.hs45
-rw-r--r--src/Text/Pandoc/Readers/LaTeX.hs9
-rw-r--r--src/Text/Pandoc/Readers/Markdown.hs23
-rw-r--r--src/Text/Pandoc/Readers/Org.hs66
-rw-r--r--src/Text/Pandoc/Shared.hs4
-rw-r--r--tests/Tests/Readers/Org.hs22
13 files changed, 244 insertions, 49 deletions
diff --git a/changelog b/changelog
index 5238e943f..e58f5516d 100644
--- a/changelog
+++ b/changelog
@@ -1,3 +1,29 @@
+pandoc (1.12.4.1)
+
+ * Require highlighting-kate >= 0.5.8. Fixes a performance regression.
+
+ * Shared: `addMetaValue` now behaves slightly differently:
+ if both the new and old values are lists, it concatenates their
+ contents to form a new list.
+
+ * LaTeX reader:
+
+ + Set `bibliography` in metadata from `\bibliography` or
+ `\addbibresource` command.
+ + Don't error on `%foo` with no trailing newline.
+
+ * Org reader:
+
+ + Support code block headers (`#+BEGIN_SRC ...`) (Albert Krewinkel).
+ + Fix parsing of blank lines within blocks (Albert Krewinkel).
+
+ * Updated copyright notices (Albert Krewinkel).
+
+ * Added default.icml to data files so it installs with the package.
+
+ * Moved OSX package materials to osx directory. Added uninstall
+ script (thanks to Daniel T. Staal).
+
pandoc (1.12.4)
* Made it possible to run filters that aren't executable (#1096).
diff --git a/make_osx_package.sh b/make_osx_package.sh
index 3119f140e..86ce784ed 100755
--- a/make_osx_package.sh
+++ b/make_osx_package.sh
@@ -6,7 +6,8 @@ VERSION=$(grep -e '^Version' pandoc.cabal | awk '{print $2}')
RESOURCES=$DIST/Resources
ROOT=$DIST/pandoc
DEST=$ROOT/usr/local
-SCRIPTS=osx-resources
+OSX=osx
+SCRIPTS=$OSX/osx-resources
BASE=pandoc-$VERSION
ME=$(whoami)
CODESIGNID="Developer ID Application: John Macfarlane"
@@ -28,8 +29,8 @@ echo Building pandoc...
cabal clean
# Use cpphs to avoid problems with clang cpp on ghc 7.8 osx:
cabal install cpphs alex happy hsb2hs
-cabal install --reinstall --flags="embed_data_files" --ghc-options '-pgmPcpphs -optP--cpp'
-cabal install --reinstall --flags="embed_data_files" pandoc-citeproc --ghc-options '-pgmPcpphs -optP--cpp'
+cabal install --ghc-options="-optl-mmacosx-version-min=10.6" --reinstall --flags="embed_data_files" --ghc-options '-pgmPcpphs -optP--cpp'
+cabal install --ghc-options="-optl-mmacosx-version-min=10.6" --reinstall --flags="embed_data_files" pandoc-citeproc --ghc-options '-pgmPcpphs -optP--cpp'
mkdir -p $DEST/bin
mkdir -p $DEST/share/man/man1
@@ -39,6 +40,7 @@ for f in $EXES; do
cp $SANDBOX/share/man/man1/$f.1 $DEST/share/man/man1/
done
cp $SANDBOX/share/man/man5/pandoc_markdown.5 $DEST/share/man/man5/
+cp $OSX/uninstall-pandoc.pl $DEST/bin/
chown -R $ME:staff $DIST
# gzip $DEST/share/man/man?/*.*
diff --git a/osx-resources/InstallationCheck b/osx/osx-resources/InstallationCheck
index 2bd691f5c..2bd691f5c 100755
--- a/osx-resources/InstallationCheck
+++ b/osx/osx-resources/InstallationCheck
diff --git a/osx-resources/InstallationCheck.strings b/osx/osx-resources/InstallationCheck.strings
index 6c8efe0d4..6c8efe0d4 100644
--- a/osx-resources/InstallationCheck.strings
+++ b/osx/osx-resources/InstallationCheck.strings
diff --git a/osx/uninstall-pandoc.pl b/osx/uninstall-pandoc.pl
new file mode 100755
index 000000000..a5194d9bd
--- /dev/null
+++ b/osx/uninstall-pandoc.pl
@@ -0,0 +1,79 @@
+#!/usr/bin/perl
+
+# Script to remove all files installed by the OSX pandoc installer
+# and unregister the package. Modified from a script contributed
+# by Daniel T. Staal.
+
+use warnings;
+use strict;
+
+use File::Spec;
+
+# The main info: this is the list of files to remove and the pkg_id.
+my $pkg_id = 'net.johnmacfarlane.pandoc';
+
+# Find which, if any, volume Pandoc is installed on.
+my $volume;
+
+# First check /, then other volumes on the box.
+my $cur_test = `pkgutil --pkgs=$pkg_id`;
+if ( $cur_test =~ m/$pkg_id/ ) {
+ $volume = '/';
+} else {
+ opendir( my $dh, '/Volumes' ) or die "Can't list Volumes: $!\n";
+ foreach my $dir ( readdir($dh) ) {
+ next if $dir =~ m/^\./; # Skip dotfiles.
+
+ my $path = File::Spec->rel2abs( $dir, '/Volumes' );
+ next if !( -d $path ); # Skip anything that isn't a directory.
+
+ my $cur_test = `pkgutil --pkgs=$pkg_id --volume '$path'`;
+ if ( $cur_test =~ m/$pkg_id/ ) {
+ $volume = $path;
+ last;
+ }
+ }
+}
+
+die "Pandoc not installed.\n" if !( defined($volume) );
+
+# Get the list of files to remove.
+my @pkg_files = `pkgutil --volume '$volume' --only-files --files '$pkg_id'`;
+@pkg_files = map { chomp; File::Spec->rel2abs($_, $volume) } @pkg_files;
+
+# Confirm uninistall with the user.
+print "The following files will be deleted:\n\n";
+print join("\n", @pkg_files);
+print "\n\n";
+print "Do you want to proceed and uninstall pandoc (Y/N)?";
+my $input = <STDIN>;
+
+if ($input =~ m/^[Yy]/) {
+
+ # Actually remove the files.
+ foreach my $file (@pkg_files) {
+ if ( -e $file ) {
+ if ( system( 'sudo', 'rm', $file ) == 0 ) {
+ warn "Deleted $file\n";
+ } else {
+ warn "Unable to delete $file: $?\n";
+ die "Aborting Uninstall.\n";
+ }
+ } else {
+ warn "File $file does not exist. Skipping.\n";
+ }
+ }
+
+ # Clean up the install.
+ if (system('sudo', 'pkgutil', '--forget', $pkg_id, '--volume', $volume) != 0) {
+ die "Unable to clean up install: $?\n";
+ }
+
+} else {
+
+ print "OK, aborting uninstall.\n";
+ exit;
+}
+
+print "Pandoc has been successfully uninstalled.\n";
+exit;
diff --git a/pandoc.cabal b/pandoc.cabal
index 63c748a47..f29ee8fb1 100644
--- a/pandoc.cabal
+++ b/pandoc.cabal
@@ -1,5 +1,5 @@
Name: pandoc
-Version: 1.12.4
+Version: 1.12.4.1
Cabal-Version: >= 1.10
Build-Type: Custom
License: GPL
@@ -45,6 +45,7 @@ Data-Files:
data/templates/default.docbook,
data/templates/default.beamer,
data/templates/default.opendocument,
+ data/templates/default.icml,
data/templates/default.opml,
data/templates/default.latex,
data/templates/default.context,
@@ -226,7 +227,7 @@ Library
tagsoup >= 0.13.1 && < 0.14,
base64-bytestring >= 0.1 && < 1.1,
zlib >= 0.5 && < 0.6,
- highlighting-kate >= 0.5.7 && < 0.6,
+ highlighting-kate >= 0.5.8 && < 0.6,
data-default >= 0.4 && < 0.6,
temporary >= 1.1 && < 1.3,
blaze-html >= 0.5 && < 0.8,
@@ -327,7 +328,7 @@ Executable pandoc
text >= 0.11 && < 1.2,
bytestring >= 0.9 && < 0.11,
extensible-exceptions >= 0.1 && < 0.2,
- highlighting-kate >= 0.5.7 && < 0.6,
+ highlighting-kate >= 0.5.8 && < 0.6,
aeson >= 0.7 && < 0.8,
yaml >= 0.8.8.2 && < 0.9,
containers >= 0.1 && < 0.6,
@@ -370,7 +371,7 @@ Test-Suite test-pandoc
directory >= 1 && < 1.3,
filepath >= 1.1 && < 1.4,
process >= 1 && < 1.3,
- highlighting-kate >= 0.5.7 && < 0.6,
+ highlighting-kate >= 0.5.8 && < 0.6,
Diff >= 0.2 && < 0.4,
test-framework >= 0.3 && < 0.9,
test-framework-hunit >= 0.2 && < 0.4,
diff --git a/src/Text/Pandoc.hs b/src/Text/Pandoc.hs
index dd5bc18f6..130338f0e 100644
--- a/src/Text/Pandoc.hs
+++ b/src/Text/Pandoc.hs
@@ -275,6 +275,7 @@ getDefaultExtensions "markdown_mmd" = multimarkdownExtensions
getDefaultExtensions "markdown_github" = githubMarkdownExtensions
getDefaultExtensions "markdown" = pandocExtensions
getDefaultExtensions "plain" = pandocExtensions
+getDefaultExtensions "org" = Set.fromList [Ext_citations]
getDefaultExtensions "textile" = Set.fromList [Ext_auto_identifiers, Ext_raw_tex]
getDefaultExtensions _ = Set.fromList [Ext_auto_identifiers]
@@ -319,4 +320,3 @@ readJSON _ = either error id . eitherDecode' . UTF8.fromStringLazy
writeJSON :: WriterOptions -> Pandoc -> String
writeJSON _ = UTF8.toStringLazy . encode
-
diff --git a/src/Text/Pandoc/Parsing.hs b/src/Text/Pandoc/Parsing.hs
index d1e55cbc4..4cd6591c0 100644
--- a/src/Text/Pandoc/Parsing.hs
+++ b/src/Text/Pandoc/Parsing.hs
@@ -54,7 +54,6 @@ module Text.Pandoc.Parsing ( (>>~),
withRaw,
escaped,
characterReference,
- updateLastStrPos,
anyOrderedListMarker,
orderedListMarker,
charRef,
@@ -66,11 +65,14 @@ module Text.Pandoc.Parsing ( (>>~),
testStringWith,
guardEnabled,
guardDisabled,
+ updateLastStrPos,
+ notAfterString,
ParserState (..),
HasReaderOptions (..),
HasHeaderMap (..),
HasIdentifierList (..),
HasMacros (..),
+ HasLastStrPosition (..),
defaultParserState,
HeaderType (..),
ParserContext (..),
@@ -92,6 +94,7 @@ module Text.Pandoc.Parsing ( (>>~),
apostrophe,
dash,
nested,
+ citeKey,
macro,
applyMacros',
Parser,
@@ -904,6 +907,14 @@ instance HasMacros ParserState where
extractMacros = stateMacros
updateMacros f st = st{ stateMacros = f $ stateMacros st }
+class HasLastStrPosition st where
+ setLastStrPos :: SourcePos -> st -> st
+ getLastStrPos :: st -> Maybe SourcePos
+
+instance HasLastStrPosition ParserState where
+ setLastStrPos pos st = st{ stateLastStrPos = Just pos }
+ getLastStrPos st = stateLastStrPos st
+
defaultParserState :: ParserState
defaultParserState =
ParserState { stateOptions = def,
@@ -938,6 +949,17 @@ guardEnabled ext = getOption readerExtensions >>= guard . Set.member ext
guardDisabled :: HasReaderOptions st => Extension -> Parser s st ()
guardDisabled ext = getOption readerExtensions >>= guard . not . Set.member ext
+-- | Update the position on which the last string ended.
+updateLastStrPos :: HasLastStrPosition st => Parser s st ()
+updateLastStrPos = getPosition >>= updateState . setLastStrPos
+
+-- | Whether we are right after the end of a string.
+notAfterString :: HasLastStrPosition st => Parser s st Bool
+notAfterString = do
+ pos <- getPosition
+ st <- getState
+ return $ getLastStrPos st /= Just pos
+
data HeaderType
= SingleHeader Char -- ^ Single line of characters underneath
| DoubleHeader Char -- ^ Lines of characters above and below
@@ -1049,17 +1071,11 @@ charOrRef cs =
guard (c `elem` cs)
return c)
-updateLastStrPos :: Parser [Char] ParserState ()
-updateLastStrPos = getPosition >>= \p ->
- updateState $ \s -> s{ stateLastStrPos = Just p }
-
singleQuoteStart :: Parser [Char] ParserState ()
singleQuoteStart = do
failIfInQuoteContext InSingleQuote
- pos <- getPosition
- st <- getState
-- single quote start can't be right after str
- guard $ stateLastStrPos st /= Just pos
+ guard =<< notAfterString
() <$ charOrRef "'\8216\145"
singleQuoteEnd :: Parser [Char] st ()
@@ -1129,6 +1145,18 @@ nested p = do
updateState $ \st -> st{ stateMaxNestingLevel = nestlevel }
return res
+citeKey :: HasLastStrPosition st => Parser [Char] st (Bool, String)
+citeKey = try $ do
+ guard =<< notAfterString
+ suppress_author <- option False (char '-' *> return True)
+ char '@'
+ firstChar <- letter <|> char '_'
+ let regchar = satisfy (\c -> isAlphaNum c || c == '_')
+ let internal p = try $ p <* lookAhead regchar
+ rest <- many $ regchar <|> internal (oneOf ":.#$%&-+?<>~/")
+ let key = firstChar:rest
+ return (suppress_author, key)
+
--
-- Macros
--
@@ -1156,4 +1184,3 @@ applyMacros' target = do
then do macros <- extractMacros `fmap` getState
return $ applyMacros macros target
else return target
-
diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs
index 8476c8636..6f870318f 100644
--- a/src/Text/Pandoc/Readers/LaTeX.hs
+++ b/src/Text/Pandoc/Readers/LaTeX.hs
@@ -307,6 +307,10 @@ blockCommands = M.fromList $
, ("caption", tok >>= setCaption)
, ("PandocStartInclude", startInclude)
, ("PandocEndInclude", endInclude)
+ , ("bibliography", mempty <$ (skipopts *> braced >>=
+ addMeta "bibliography" . splitBibs))
+ , ("addbibresource", mempty <$ (skipopts *> braced >>=
+ addMeta "bibliography" . splitBibs))
] ++ map ignoreBlocks
-- these commands will be ignored unless --parse-raw is specified,
-- in which case they will appear as raw latex blocks
@@ -314,7 +318,7 @@ blockCommands = M.fromList $
-- newcommand, etc. should be parsed by macro, but we need this
-- here so these aren't parsed as inline commands to ignore
, "special", "pdfannot", "pdfstringdef"
- , "bibliography", "bibliographystyle"
+ , "bibliographystyle"
, "maketitle", "makeindex", "makeglossary"
, "addcontentsline", "addtocontents", "addtocounter"
-- \ignore{} is used conventionally in literate haskell for definitions
@@ -329,6 +333,9 @@ addMeta :: ToMetaValue a => String -> a -> LP ()
addMeta field val = updateState $ \st ->
st{ stateMeta = addMetaField field val $ stateMeta st }
+splitBibs :: String -> [Inlines]
+splitBibs = map (str . flip replaceExtension "bib" . trim) . splitBy (==',')
+
setCaption :: Inlines -> LP Blocks
setCaption ils = do
updateState $ \st -> st{ stateCaption = Just ils }
diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs
index d1637b701..5129bc2e3 100644
--- a/src/Text/Pandoc/Readers/Markdown.hs
+++ b/src/Text/Pandoc/Readers/Markdown.hs
@@ -1474,9 +1474,7 @@ strongOrEmph = enclosure '*' <|> (checkIntraword >> enclosure '_')
where checkIntraword = do
exts <- getOption readerExtensions
when (Ext_intraword_underscores `Set.member` exts) $ do
- pos <- getPosition
- lastStrPos <- stateLastStrPos <$> getState
- guard $ lastStrPos /= Just pos
+ guard =<< notAfterString
-- | Parses a list of inlines between start and end delimiters.
inlinesBetween :: (Show b)
@@ -1518,8 +1516,7 @@ nonEndline = satisfy (/='\n')
str :: MarkdownParser (F Inlines)
str = do
result <- many1 alphaNum
- pos <- getPosition
- updateState $ \s -> s{ stateLastStrPos = Just pos }
+ updateLastStrPos
let spacesToNbr = map (\c -> if c == ' ' then '\160' else c)
isSmart <- getOption readerSmart
if isSmart
@@ -1817,22 +1814,6 @@ normalCite = try $ do
char ']'
return citations
-citeKey :: MarkdownParser (Bool, String)
-citeKey = try $ do
- -- make sure we're not right after an alphanumeric,
- -- since foo@bar.baz is probably an email address
- lastStrPos <- stateLastStrPos <$> getState
- pos <- getPosition
- guard $ lastStrPos /= Just pos
- suppress_author <- option False (char '-' >> return True)
- char '@'
- first <- letter <|> char '_'
- let regchar = satisfy (\c -> isAlphaNum c || c == '_')
- let internal p = try $ p >>~ lookAhead regchar
- rest <- many $ regchar <|> internal (oneOf ":.#$%&-+?<>~/")
- let key = first:rest
- return (suppress_author, key)
-
suffix :: MarkdownParser (F Inlines)
suffix = try $ do
hasSpace <- option False (notFollowedBy nonspaceChar >> return True)
diff --git a/src/Text/Pandoc/Readers/Org.hs b/src/Text/Pandoc/Readers/Org.hs
index 2e4a29beb..86dda2732 100644
--- a/src/Text/Pandoc/Readers/Org.hs
+++ b/src/Text/Pandoc/Readers/Org.hs
@@ -105,6 +105,10 @@ instance HasMeta OrgParserState where
deleteMeta field st =
st{ orgStateMeta = deleteMeta field $ orgStateMeta st }
+instance HasLastStrPosition OrgParserState where
+ getLastStrPos = orgStateLastStrPos
+ setLastStrPos pos st = st{ orgStateLastStrPos = Just pos }
+
instance Default OrgParserState where
def = defaultOrgParserState
@@ -865,6 +869,7 @@ inline :: OrgParser (F Inlines)
inline =
choice [ whitespace
, linebreak
+ , cite
, footnote
, linkOrImage
, anchor
@@ -929,6 +934,51 @@ endline = try $ do
updateLastPreCharPos
return . return $ B.space
+cite :: OrgParser (F Inlines)
+cite = try $ do
+ guardEnabled Ext_citations
+ (cs, raw) <- withRaw normalCite
+ return $ (flip B.cite (B.text raw)) <$> cs
+
+normalCite :: OrgParser (F [Citation])
+normalCite = try $ char '['
+ *> skipSpaces
+ *> citeList
+ <* skipSpaces
+ <* char ']'
+
+citeList :: OrgParser (F [Citation])
+citeList = sequence <$> sepBy1 citation (try $ char ';' *> skipSpaces)
+
+citation :: OrgParser (F Citation)
+citation = try $ do
+ pref <- prefix
+ (suppress_author, key) <- citeKey
+ suff <- suffix
+ return $ do
+ x <- pref
+ y <- suff
+ return $ Citation{ citationId = key
+ , citationPrefix = B.toList x
+ , citationSuffix = B.toList y
+ , citationMode = if suppress_author
+ then SuppressAuthor
+ else NormalCitation
+ , citationNoteNum = 0
+ , citationHash = 0
+ }
+ where
+ prefix = trimInlinesF . mconcat <$>
+ manyTill inline (char ']' <|> (']' <$ lookAhead citeKey))
+ suffix = try $ do
+ hasSpace <- option False (notFollowedBy nonspaceChar >> return True)
+ skipSpaces
+ rest <- trimInlinesF . mconcat <$>
+ many (notFollowedBy (oneOf ";]") *> inline)
+ return $ if hasSpace
+ then (B.space <>) <$> rest
+ else rest
+
footnote :: OrgParser (F Inlines)
footnote = try $ inlineNote <|> referencedNote
@@ -1003,7 +1053,7 @@ selfTarget :: OrgParser String
selfTarget = try $ char '[' *> linkTarget <* char ']'
linkTarget :: OrgParser String
-linkTarget = enclosed (char '[') (char ']') (noneOf "\n\r[]")
+linkTarget = enclosedByPair '[' ']' (noneOf "\n\r[]")
applyCustomLinkFormat :: String -> OrgParser (F String)
applyCustomLinkFormat link = do
@@ -1079,7 +1129,12 @@ inlineCodeBlock = try $ do
let attrClasses = [translateLang lang, rundocBlockClass]
let attrKeyVal = map toRundocAttrib (("language", lang) : opts)
returnF $ B.codeWith ("", attrClasses, attrKeyVal) inlineCode
- where enclosedByPair s e p = char s *> many1Till p (char e)
+
+enclosedByPair :: Char -- ^ opening char
+ -> Char -- ^ closing char
+ -> OrgParser a -- ^ parser
+ -> OrgParser [a]
+enclosedByPair s e p = char s *> many1Till p (char e)
emph :: OrgParser (F Inlines)
emph = fmap B.emph <$> emphasisBetween '/'
@@ -1274,13 +1329,6 @@ afterEmphasisPreChar = do
lastPrePos <- orgStateLastPreCharPos <$> getState
return . fromMaybe True $ (== pos) <$> lastPrePos
--- | Whether we are right after the end of a string
-notAfterString :: OrgParser Bool
-notAfterString = do
- pos <- getPosition
- lastStrPos <- orgStateLastStrPos <$> getState
- return $ lastStrPos /= Just pos
-
-- | Whether the parser is right after a forbidden border char
notAfterForbiddenBorderChar :: OrgParser Bool
notAfterForbiddenBorderChar = do
diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs
index 31c490af6..4f506b5a6 100644
--- a/src/Text/Pandoc/Shared.hs
+++ b/src/Text/Pandoc/Shared.hs
@@ -564,8 +564,10 @@ addMetaField :: ToMetaValue a
-> Meta
addMetaField key val (Meta meta) =
Meta $ M.insertWith combine key (toMetaValue val) meta
- where combine newval (MetaList xs) = MetaList (xs ++ [newval])
+ where combine newval (MetaList xs) = MetaList (xs ++ tolist newval)
combine newval x = MetaList [x, newval]
+ tolist (MetaList ys) = ys
+ tolist y = [y]
-- | Create 'Meta' from old-style title, authors, date. This is
-- provided to ease the transition from the old API.
diff --git a/tests/Tests/Readers/Org.hs b/tests/Tests/Readers/Org.hs
index 4ef7a7731..ca97ba348 100644
--- a/tests/Tests/Readers/Org.hs
+++ b/tests/Tests/Readers/Org.hs
@@ -225,6 +225,28 @@ tests =
]
)
"echo 'Hello, World'")
+
+ , "Citation" =:
+ "[@nonexistent]" =?>
+ let citation = Citation
+ { citationId = "nonexistent"
+ , citationPrefix = []
+ , citationSuffix = []
+ , citationMode = NormalCitation
+ , citationNoteNum = 0
+ , citationHash = 0}
+ in (para $ cite [citation] "[@nonexistent]")
+
+ , "Citation containing text" =:
+ "[see @item1 p. 34-35]" =?>
+ let citation = Citation
+ { citationId = "item1"
+ , citationPrefix = [Str "see"]
+ , citationSuffix = [Space ,Str "p.",Space,Str "34-35"]
+ , citationMode = NormalCitation
+ , citationNoteNum = 0
+ , citationHash = 0}
+ in (para $ cite [citation] "[see @item1 p. 34-35]")
]
, testGroup "Meta Information" $