aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--.travis.yml108
-rw-r--r--Makefile3
-rw-r--r--Setup.hs35
-rw-r--r--benchmark/benchmark-pandoc.hs11
-rw-r--r--make_travis_yml.hs210
-rw-r--r--pandoc.cabal4
-rw-r--r--src/Text/Pandoc/Readers/LaTeX.hs8
7 files changed, 311 insertions, 68 deletions
diff --git a/.travis.yml b/.travis.yml
index 4979593d0..7b91b71d9 100644
--- a/.travis.yml
+++ b/.travis.yml
@@ -1,39 +1,87 @@
-# NB: don't set `language: haskell` here
-
-# Ensures that sudo is disabled, so that containerized builds are allowed
+# This file has been generated -- see https://github.com/hvr/multi-ghc-travis
+language: c
sudo: false
-# The following enables several GHC versions to be tested; often it's enough to test only against the last release in a major GHC version. Feel free to omit lines listings versions you don't need/want testing for.
+cache:
+ directories:
+ - $HOME/.cabsnap
+ - $HOME/.cabal/packages
+
+before_cache:
+ - rm -fv $HOME/.cabal/packages/hackage.haskell.org/build-reports.log
+ - rm -fv $HOME/.cabal/packages/hackage.haskell.org/00-index.tar
+
matrix:
- include:
- - env: CABALVER=1.16 GHCVER=7.4.2 GHCOPTS="-Werror" JOPTS=""
- addons: {apt: {packages: [cabal-install-1.16, ghc-7.4.2], sources: [hvr-ghc]}}
- - env: CABALVER=1.18 GHCVER=7.6.3 GHCOPTS="-Werror" JOPTS="-j2"
- addons: {apt: {packages: [cabal-install-1.18, ghc-7.6.3], sources: [hvr-ghc]}}
- - env: CABALVER=1.18 GHCVER=7.8.4 GHCOPTS="-Werror" JOPTS="-j2"
- addons: {apt: {packages: [cabal-install-1.18, ghc-7.8.4], sources: [hvr-ghc]}}
- - env: CABALVER=head GHCVER=7.10.1 GHCOPTS="" JOPTS="-j2"
- addons: {apt: {packages: [cabal-install-head, ghc-7.10.1],sources: [hvr-ghc]}}
-# - env: CABALVER=head GHCVER=head GHCOPTS="-Werror" JOPTS="-j2"
-# addons: {apt: {packages: [cabal-install-head,ghc-head], sources: [hvr-ghc]}}
-
-# Note: the distinction between `before_install` and `install` is not important.
+ include:
+ - env: CABALVER=1.16 GHCVER=7.4.2 GHCOPTS=-Werror
+ compiler: ": #GHC 7.4.2"
+ addons: {apt: {packages: [cabal-install-1.16,ghc-7.4.2], sources: [hvr-ghc]}}
+ - env: CABALVER=1.16 GHCVER=7.6.3 GHCOPTS=-Werror
+ compiler: ": #GHC 7.6.3"
+ addons: {apt: {packages: [cabal-install-1.16,ghc-7.6.3], sources: [hvr-ghc]}}
+ - env: CABALVER=1.18 GHCVER=7.8.4 GHCOPTS=-Werror
+ compiler: ": #GHC 7.8.4"
+ addons: {apt: {packages: [cabal-install-1.18,ghc-7.8.4], sources: [hvr-ghc]}}
+ - env: CABALVER=1.22 GHCVER=7.10.2 GHCOPTS=
+ compiler: ": #GHC 7.10.2"
+ addons: {apt: {packages: [cabal-install-1.22,ghc-7.10.2], sources: [hvr-ghc]}}
+
before_install:
+ - unset CC
- export PATH=/opt/ghc/$GHCVER/bin:/opt/cabal/$CABALVER/bin:$PATH
install:
- - cabal-$CABALVER update
-# - git clone https://github.com/jgm/pandoc-types && cd pandoc-types && cabal-1.18 install && cd ..
- - cabal-$CABALVER install $JOPTS --only-dependencies --enable-tests
+ - cabal --version
+ - echo "$(ghc --version) [$(ghc --print-project-git-commit-id 2> /dev/null || echo '?')]"
+ - if [ -f $HOME/.cabal/packages/hackage.haskell.org/00-index.tar.gz ];
+ then
+ zcat $HOME/.cabal/packages/hackage.haskell.org/00-index.tar.gz >
+ $HOME/.cabal/packages/hackage.haskell.org/00-index.tar;
+ fi
+ - travis_retry cabal update -v
+ - sed -i 's/^jobs:/-- jobs:/' ${HOME}/.cabal/config
+ - cabal install --only-dependencies --enable-tests --enable-benchmarks --dry -v > installplan.txt
+ - sed -i -e '1,/^Resolving /d' installplan.txt; cat installplan.txt
-# Here starts the actual work to be performed for the package under test; any command which exits with a non-zero exit code causes the build to fail.
-script:
- - |
- if [ "${CABALVER}" != "1.16" ]; then
- cabal-$CABALVER sdist --output-directory=build
- cd build
+# check whether current requested install-plan matches cached package-db snapshot
+ - if diff -u installplan.txt $HOME/.cabsnap/installplan.txt;
+ then
+ echo "cabal build-cache HIT";
+ rm -rfv .ghc;
+ cp -a $HOME/.cabsnap/ghc $HOME/.ghc;
+ cp -a $HOME/.cabsnap/lib $HOME/.cabsnap/share $HOME/.cabsnap/bin $HOME/.cabal/;
+ else
+ echo "cabal build-cache MISS";
+ rm -rf $HOME/.cabsnap;
+ mkdir -p $HOME/.ghc $HOME/.cabal/lib $HOME/.cabal/share $HOME/.cabal/bin;
+ cabal install --only-dependencies --enable-tests --enable-benchmarks;
fi
- - cabal-$CABALVER configure --enable-tests -v2 # -v2 provides useful information for debugging
- - cabal-$CABALVER build $JOPTS --ghc-options=$GHCOPTS # this builds all libraries and executables (including tests/benchmarks)
- - cabal-$CABALVER test
- - cabal-$CABALVER check
+
+# snapshot package-db on cache miss
+ - if [ ! -d $HOME/.cabsnap ];
+ then
+ echo "snapshotting package-db to build-cache";
+ mkdir $HOME/.cabsnap;
+ cp -a $HOME/.ghc $HOME/.cabsnap/ghc;
+ cp -a $HOME/.cabal/lib $HOME/.cabal/share $HOME/.cabal/bin installplan.txt $HOME/.cabsnap/;
+ fi
+
+# Here starts the actual work to be performed for the package under test;
+# any command which exits with a non-zero exit code causes the build to fail.
+script:
+ - if [ -f configure.ac ]; then autoreconf -i; fi
+ - cabal configure --enable-tests --enable-benchmarks -v2 # -v2 provides useful information for debugging
+ - cabal build --ghc-options=$GHCOPTS # this builds all libraries and executables (including tests/benchmarks)
+ - cabal test
+ - cabal check
+# Test that a source-distribution can be generated
+# (with cabal >= 1.18 'cabal sdist' would work too):
+ - ./dist/setup/setup sdist
+
+# Check that the resulting source distribution can be built & installed.
+# If there are no other `.tar.gz` files in `dist`, this can be even simpler:
+# `cabal install --force-reinstalls dist/*-*.tar.gz`
+ - SRC_TGZ=$(cabal info . | awk '{print $2;exit}').tar.gz &&
+ (cd dist && cabal install --force-reinstalls "$SRC_TGZ")
+
+# EOF
diff --git a/Makefile b/Makefile
index a44085420..7c16418f8 100644
--- a/Makefile
+++ b/Makefile
@@ -34,6 +34,9 @@ dist: man/pandoc.1
cd pandoc-${version}
cabal configure ${CABALARGS} && cabal build && cabal test && cd .. && rm -rf "pandoc-${version}"
+.travis.yml: pandoc.cabal make_travis_yml.hs
+ runghc make_travis_yml.hs $< > $@
+
debpkg: man/pandoc.1
./make_deb.sh
diff --git a/Setup.hs b/Setup.hs
index 312e1cf47..e2e026014 100644
--- a/Setup.hs
+++ b/Setup.hs
@@ -20,17 +20,14 @@ import Distribution.Simple
import Distribution.Simple.PreProcess
import Distribution.Simple.Setup (ConfigFlags(..))
import Distribution.PackageDescription (PackageDescription(..), FlagName(..))
-import System.Process ( rawSystem )
-import System.FilePath ( (</>) )
-import System.Directory ( findExecutable )
+import Distribution.Simple.Utils ( rawSystemExitCode, findProgramVersion )
+import System.Exit
import Distribution.Verbosity ( Verbosity )
import Distribution.Simple.Utils (info, notice, installOrdinaryFiles)
import Distribution.Simple.Setup
import Distribution.Simple.Program (simpleProgram, Program(..))
import Distribution.Simple.LocalBuildInfo
import Data.Version
-import System.Process (readProcess)
-import Text.ParserCombinators.ReadP (readP_to_S, skipSpaces, eof)
import Control.Monad (when)
import qualified Control.Exception as E
@@ -39,23 +36,11 @@ main = defaultMainWithHooks $ simpleUserHooks {
-- enable hsb2hs preprocessor for .hsb files
hookedPreProcessors = [ppBlobSuffixHandler]
, hookedPrograms = [(simpleProgram "hsb2hs"){
- programFindVersion = findHsb2hsVersion }]
+ programFindVersion = \verbosity fp ->
+ findProgramVersion "--version" id verbosity fp }]
, postCopy = installManPage
}
-findHsb2hsVersion :: Verbosity -> FilePath -> IO (Maybe Version)
-findHsb2hsVersion verb fp = do
- let handleExitFailure :: IOError -> IO (Maybe Version)
- handleExitFailure _ = return Nothing
- E.handle handleExitFailure $ do
- outp <- readProcess fp ["--version"] ""
- case readP_to_S (do v <- parseVersion
- skipSpaces
- eof
- return v) outp of
- ((v,""):_) -> return (Just v)
- _ -> return Nothing
-
ppBlobSuffixHandler :: PPSuffixHandler
ppBlobSuffixHandler = ("hsb", \_ lbi ->
PreProcessor {
@@ -67,11 +52,11 @@ ppBlobSuffixHandler = ("hsb", \_ lbi ->
_ -> False
when embedData $
do info verbosity $ "Preprocessing " ++ infile ++ " to " ++ outfile
- hsb2hsPath <- findExecutable "hsb2hs"
- case hsb2hsPath of
- Just p -> rawSystem p [infile, infile, outfile]
- Nothing -> error "hsb2hs is needed to build this program: cabal install hsb2hs"
- return ()
+ ec <- rawSystemExitCode verbosity "hsb2hs"
+ [infile, infile, outfile]
+ case ec of
+ ExitSuccess -> return ()
+ ExitFailure _ -> error "hsb2hs is needed to build this program"
})
installManPage :: Args -> CopyFlags
@@ -80,6 +65,6 @@ installManPage _ flags pkg lbi = do
let verbosity = fromFlag (copyVerbosity flags)
let copydest = fromFlag (copyDest flags)
let mandest = mandir (absoluteInstallDirs pkg lbi copydest)
- </> "man1"
+ ++ "/man1"
notice verbosity $ "Copying man page to " ++ mandest
installOrdinaryFiles verbosity mandest [("man", "pandoc.1")]
diff --git a/benchmark/benchmark-pandoc.hs b/benchmark/benchmark-pandoc.hs
index 3fc70331f..d86d38f60 100644
--- a/benchmark/benchmark-pandoc.hs
+++ b/benchmark/benchmark-pandoc.hs
@@ -17,9 +17,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
-}
import Text.Pandoc
import Criterion.Main
-import Criterion.Config
-import System.Environment (getArgs)
-import Data.Monoid
+import Criterion.Types (Config(..))
import Data.Maybe (mapMaybe)
import Debug.Trace (trace)
import Text.Pandoc.Error
@@ -44,9 +42,6 @@ writerBench doc (name, writer) = bench (name ++ " writer") $ nf
main :: IO ()
main = do
- args <- getArgs
- (conf,_) <- parseArgs defaultConfig{ cfgSamples = Last $ Just 20 }
- defaultOptions args
inp <- readFile "tests/testsuite.txt"
let opts = def{ readerSmart = True }
let doc = handleError $ readMarkdown opts inp
@@ -56,5 +51,5 @@ main = do
let writers' = [(n,w) | (n, PureStringWriter w) <- writers]
let writerBs = map (writerBench doc)
$ writers'
- defaultMainWith conf (return ()) $
- writerBs ++ readerBs
+ defaultMainWith defaultConfig{ timeLimit = 6.0 }
+ (writerBs ++ readerBs)
diff --git a/make_travis_yml.hs b/make_travis_yml.hs
new file mode 100644
index 000000000..91916c499
--- /dev/null
+++ b/make_travis_yml.hs
@@ -0,0 +1,210 @@
+#!/usr/bin/env runghc
+
+-- NB: This code deliberately avoids relying on non-standard packages
+
+import Control.Monad
+import Data.List
+import Data.Version
+import System.Environment
+import System.Exit
+import System.IO
+
+import Distribution.PackageDescription.Parse (readPackageDescription)
+import Distribution.PackageDescription (packageDescription, testedWith)
+import Distribution.Compiler (CompilerFlavor(..))
+import Distribution.Version
+import Distribution.Text
+
+putStrLnErr :: String -> IO ()
+putStrLnErr m = hPutStrLn stderr ("*ERROR* " ++ m) >> exitFailure
+
+putStrLnWarn :: String -> IO ()
+putStrLnWarn m = hPutStrLn stderr ("*WARNING* " ++ m)
+
+putStrLnInfo :: String -> IO ()
+putStrLnInfo m = hPutStrLn stderr ("*INFO* " ++ m)
+
+main :: IO ()
+main = do
+ args <- getArgs
+ case args of
+ (cabfn:xpkgs) -> do genTravisFromCabalFile cabfn xpkgs
+ _ -> putStrLnErr (unlines $ [ "expected .cabal file as command-line argument"
+ , "Usage: make_travis_yml.hs <cabal-file> <extra-apt-packages...>"
+ , ""
+ , "Example: make_travis_yml.hs someProject.cabal alex-3.1.4 liblzma-dev > .travis.yml"
+ ])
+
+genTravisFromCabalFile :: FilePath -> [String] -> IO ()
+genTravisFromCabalFile fn xpkgs = do
+ gpd <- readPackageDescription maxBound fn
+
+ let compilers = testedWith $ packageDescription $ gpd
+
+ let unknownComps = nub [ c | (c,_) <- compilers, c /= GHC ]
+ ghcVerConstrs = [ vc | (GHC,vc) <- compilers ]
+ ghcVerConstrs' = simplifyVersionRange $ foldr unionVersionRanges noVersion ghcVerConstrs
+
+ when (null compilers) $ do
+ putStrLnErr "empty or missing 'tested-with:' definition in .cabal file"
+
+ unless (null unknownComps) $ do
+ putStrLnWarn $ "ignoring unsupported compilers mentioned in tested-with: " ++ show unknownComps
+
+ when (null ghcVerConstrs) $ do
+ putStrLnErr "'tested-with:' doesn't mention any 'GHC' version"
+
+ when (isNoVersion ghcVerConstrs') $ do
+ putStrLnErr "'tested-with:' describes an empty version range for 'GHC'"
+
+ when (isAnyVersion ghcVerConstrs') $ do
+ putStrLnErr "'tested-with:' allows /any/ 'GHC' version"
+
+ let testedGhcVersions = filter (`withinRange` ghcVerConstrs') knownGhcVersions
+
+ when (null testedGhcVersions) $ do
+ putStrLnErr "no known GHC version is allowed by the 'tested-with' specification"
+
+ putStrLnInfo $ "Generating Travis-CI config for testing for GHC versions: " ++ (unwords $ map disp' $ testedGhcVersions)
+
+ ----------------------------------------------------------------------------
+ -- travis.yml generation starts here
+
+ putStrLn "# This file has been generated -- see https://github.com/hvr/multi-ghc-travis"
+ putStrLn "language: c"
+ putStrLn "sudo: false"
+ putStrLn ""
+ putStrLn "cache:"
+ putStrLn " directories:"
+ putStrLn " - $HOME/.cabsnap"
+ putStrLn " - $HOME/.cabal/packages"
+ putStrLn ""
+ putStrLn "before_cache:"
+ putStrLn " - rm -fv $HOME/.cabal/packages/hackage.haskell.org/build-reports.log"
+ putStrLn " - rm -fv $HOME/.cabal/packages/hackage.haskell.org/00-index.tar"
+ putStrLn ""
+ putStrLn "matrix:"
+ putStrLn " include:"
+
+ forM_ testedGhcVersions $ \gv -> do
+ let cvs = disp' (lookupCabVer gv)
+ gvs = disp' gv
+ ghcopts = if gv >= Version [7,10,0] []
+ then ""
+ else "-Werror"
+
+ xpkgs' = concatMap (',':) xpkgs
+
+ putStrLn $ concat [ " - env: CABALVER=", cvs, " GHCVER=", gvs,
+ " GHCOPTS=", ghcopts]
+ putStrLn $ concat [ " compiler: \": #GHC ", gvs, "\"" ]
+ putStrLn $ concat [ " addons: {apt: {packages: [cabal-install-", cvs, ",ghc-", gvs, xpkgs'
+ , "], sources: [hvr-ghc]}}" ]
+ return ()
+
+ let headGhcVers = filter isHead testedGhcVersions
+
+ unless (null headGhcVers) $ do
+ putStrLn ""
+ putStrLn " allow_failures:"
+
+ forM_ headGhcVers $ \gv -> do
+ let cvs = disp' (lookupCabVer gv)
+ gvs = disp' gv
+ putStrLn $ concat [ " - env: CABALVER=", cvs, " GHCVER=", gvs ]
+
+ putStrLn ""
+ putStrLn "before_install:"
+ putStrLn " - unset CC"
+ putStrLn " - export PATH=/opt/ghc/$GHCVER/bin:/opt/cabal/$CABALVER/bin:$PATH"
+
+ putStrLn ""
+
+ putStr $ unlines
+ [ "install:"
+ , " - cabal --version"
+ , " - echo \"$(ghc --version) [$(ghc --print-project-git-commit-id 2> /dev/null || echo '?')]\""
+ , " - if [ -f $HOME/.cabal/packages/hackage.haskell.org/00-index.tar.gz ];"
+ , " then"
+ , " zcat $HOME/.cabal/packages/hackage.haskell.org/00-index.tar.gz >"
+ , " $HOME/.cabal/packages/hackage.haskell.org/00-index.tar;"
+ , " fi"
+ , " - travis_retry cabal update -v"
+ , " - sed -i 's/^jobs:/-- jobs:/' ${HOME}/.cabal/config"
+ , " - cabal install --only-dependencies --enable-tests --enable-benchmarks --dry -v > installplan.txt"
+ , " - sed -i -e '1,/^Resolving /d' installplan.txt; cat installplan.txt"
+ , ""
+ , "# check whether current requested install-plan matches cached package-db snapshot"
+ , " - if diff -u installplan.txt $HOME/.cabsnap/installplan.txt;"
+ , " then"
+ , " echo \"cabal build-cache HIT\";"
+ , " rm -rfv .ghc;"
+ , " cp -a $HOME/.cabsnap/ghc $HOME/.ghc;"
+ , " cp -a $HOME/.cabsnap/lib $HOME/.cabsnap/share $HOME/.cabsnap/bin $HOME/.cabal/;"
+ , " else"
+ , " echo \"cabal build-cache MISS\";"
+ , " rm -rf $HOME/.cabsnap;"
+ , " mkdir -p $HOME/.ghc $HOME/.cabal/lib $HOME/.cabal/share $HOME/.cabal/bin;"
+ , " cabal install --only-dependencies --enable-tests --enable-benchmarks;"
+ , " fi"
+ , " "
+ , "# snapshot package-db on cache miss"
+ , " - if [ ! -d $HOME/.cabsnap ];"
+ , " then"
+ , " echo \"snapshotting package-db to build-cache\";"
+ , " mkdir $HOME/.cabsnap;"
+ , " cp -a $HOME/.ghc $HOME/.cabsnap/ghc;"
+ , " cp -a $HOME/.cabal/lib $HOME/.cabal/share $HOME/.cabal/bin installplan.txt $HOME/.cabsnap/;"
+ , " fi"
+ , ""
+ , "# Here starts the actual work to be performed for the package under test;"
+ , "# any command which exits with a non-zero exit code causes the build to fail."
+ , "script:"
+ , " - if [ -f configure.ac ]; then autoreconf -i; fi"
+ , " - cabal configure --enable-tests --enable-benchmarks -v2 # -v2 provides useful information for debugging"
+ , " - cabal build --ghc-options=$GHCOPTS # this builds all libraries and executables (including tests/benchmarks)"
+ , " - cabal test"
+ , " - cabal check"
+ , "# Test that a source-distribution can be generated"
+ , "# (with cabal >= 1.18 'cabal sdist' would work too):"
+ , " - ./dist/setup/setup sdist"
+ , ""
+ , "# Check that the resulting source distribution can be built & installed."
+ , "# If there are no other `.tar.gz` files in `dist`, this can be even simpler:"
+ , "# `cabal install --force-reinstalls dist/*-*.tar.gz`"
+ , " - SRC_TGZ=$(cabal info . | awk '{print $2;exit}').tar.gz &&"
+ , " (cd dist && cabal install --force-reinstalls \"$SRC_TGZ\")"
+ , ""
+ , "# EOF"
+ ]
+
+ return ()
+ where
+ knownGhcVersions :: [Version]
+ knownGhcVersions = fmap (`Version` [])
+ [ [7,0,1], [7,0,2], [7,0,3], [7,0,4]
+ , [7,2,1], [7,2,2]
+ , [7,4,1], [7,4,2]
+ , [7,6,1], [7,6,2], [7,6,3]
+ , [7,8,1], [7,8,2], [7,8,3], [7,8,4]
+ , [7,10,1], [7,10,2]
+ , [7,11] -- HEAD
+ ]
+
+ lookupCabVer :: Version -> Version
+ lookupCabVer (Version (x:y:_) _) = maybe (error "internal error") id $ lookup (x,y) cabalVerMap
+ where
+ cabalVerMap = fmap (fmap (`Version` []))
+ [ ((7, 0), [1,16])
+ , ((7, 2), [1,16])
+ , ((7, 4), [1,16])
+ , ((7, 6), [1,16])
+ , ((7, 8), [1,18])
+ , ((7,10), [1,22])
+ , ((7,11), [1,23]) -- HEAD
+ ]
+
+ isHead (Version (_:y:_) _) = odd (y :: Int)
+
+ disp' v | isHead v = "head"
+ | otherwise = display v
diff --git a/pandoc.cabal b/pandoc.cabal
index c9db0406e..3818d0bf4 100644
--- a/pandoc.cabal
+++ b/pandoc.cabal
@@ -11,7 +11,7 @@ Bug-Reports: https://github.com/jgm/pandoc/issues
Stability: alpha
Homepage: http://pandoc.org
Category: Text
-Tested-With: GHC == 7.4.2, GHC == 7.6.3, GHC == 7.8.2
+Tested-With: GHC == 7.4.2, GHC == 7.6.3, GHC == 7.8.4, GHC == 7.10.2
Synopsis: Conversion between markup formats
Description: Pandoc is a Haskell library for converting from one markup
format to another, and a command-line tool that uses
@@ -500,6 +500,6 @@ benchmark benchmark-pandoc
Build-Depends: pandoc,
base >= 4.2 && < 5,
syb >= 0.1 && < 0.7,
- criterion >= 0.5 && < 1.2
+ criterion >= 1.0 && < 1.2
Ghc-Options: -rtsopts -Wall -fno-warn-unused-do-bind
Default-Language: Haskell98
diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs
index ed0291051..0e144dd0d 100644
--- a/src/Text/Pandoc/Readers/LaTeX.hs
+++ b/src/Text/Pandoc/Readers/LaTeX.hs
@@ -234,7 +234,9 @@ blocks = mconcat <$> many block
getRawCommand :: String -> LP String
getRawCommand name' = do
- rawargs <- withRaw (skipopts *> option "" dimenarg *> many braced)
+ rawargs <- withRaw (many (try (optional sp *> opt)) *>
+ option "" (try (optional sp *> dimenarg)) *>
+ many braced)
return $ '\\' : name' ++ snd rawargs
lookupListDefault :: (Ord k) => v -> [k] -> M.Map k v -> v
@@ -816,10 +818,10 @@ tok :: LP Inlines
tok = try $ grouped inline <|> inlineCommand <|> str <$> count 1 inlineChar
opt :: LP Inlines
-opt = bracketed inline <* optional sp
+opt = bracketed inline
skipopts :: LP ()
-skipopts = skipMany opt
+skipopts = skipMany (opt *> optional sp)
inlineText :: LP Inlines
inlineText = str <$> many1 inlineChar