Muse reader: allow examples to be indented with tabs

This commit is contained in:
Alexander Krotov 2018-10-17 15:42:57 +03:00
parent 1071732719
commit 6fc812485e
2 changed files with 13 additions and 8 deletions

View file

@ -45,7 +45,7 @@ import Control.Monad.Reader
import Control.Monad.Except (throwError) import Control.Monad.Except (throwError)
import Data.Bifunctor import Data.Bifunctor
import Data.Default import Data.Default
import Data.List (intercalate) import Data.List (intercalate, transpose)
import Data.List.Split (splitOn) import Data.List.Split (splitOn)
import qualified Data.Map as M import qualified Data.Map as M
import qualified Data.Set as Set import qualified Data.Set as Set
@ -135,9 +135,6 @@ parseMuse = do
-- * Utility functions -- * Utility functions
commonPrefix :: String -> String -> String
commonPrefix xs ys = map fst $ takeWhile (uncurry (==)) $ zip xs ys
-- | Trim up to one newline from the beginning of the string. -- | Trim up to one newline from the beginning of the string.
lchop :: String -> String lchop :: String -> String
lchop ('\n':xs) = xs lchop ('\n':xs) = xs
@ -151,10 +148,10 @@ unindent :: String -> String
unindent = rchop . intercalate "\n" . dropSpacePrefix . splitOn "\n" . lchop unindent = rchop . intercalate "\n" . dropSpacePrefix . splitOn "\n" . lchop
dropSpacePrefix :: [String] -> [String] dropSpacePrefix :: [String] -> [String]
dropSpacePrefix lns = dropSpacePrefix lns = drop maxIndent <$> lns
map (drop maxIndent) lns where isSpaceChar c = c == ' ' || c == '\t'
where flns = filter (not . all (== ' ')) lns maxIndent = length $ takeWhile (isSpaceChar . head) $ takeWhile same $ transpose lns
maxIndent = if null flns then maximum (map length lns) else length $ takeWhile (== ' ') $ foldl1 commonPrefix flns same = and . (zipWith (==) <*> drop 1)
atStart :: PandocMonad m => MuseParser m () atStart :: PandocMonad m => MuseParser m ()
atStart = do atStart = do

View file

@ -465,6 +465,14 @@ tests =
, " }}}" , " }}}"
] =?> ] =?>
bulletList [ codeBlock "Example line" ] bulletList [ codeBlock "Example line" ]
, "Tabs" =:
T.unlines [ "{{{"
, "\t foo"
, "\t\t"
, "\t bar"
, "}}}"
] =?>
codeBlock " foo\n\t\n bar"
-- Amusewiki requires braces to be on separate line, -- Amusewiki requires braces to be on separate line,
-- this is an extension. -- this is an extension.
, "One line" =: , "One line" =: