aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Readers/Muse.hs
diff options
context:
space:
mode:
authorAlexander Krotov <ilabdsf@gmail.com>2018-10-17 15:42:57 +0300
committerAlexander Krotov <ilabdsf@gmail.com>2018-10-17 18:17:30 +0300
commit6fc812485e26f169bfe560b5f78c572378cbc53a (patch)
tree194297a66834d7172dcbef0a176f771be442693a /src/Text/Pandoc/Readers/Muse.hs
parent1071732719fa015b1dcc994e1d80146f291d3e17 (diff)
downloadpandoc-6fc812485e26f169bfe560b5f78c572378cbc53a.tar.gz
Muse reader: allow examples to be indented with tabs
Diffstat (limited to 'src/Text/Pandoc/Readers/Muse.hs')
-rw-r--r--src/Text/Pandoc/Readers/Muse.hs13
1 files changed, 5 insertions, 8 deletions
diff --git a/src/Text/Pandoc/Readers/Muse.hs b/src/Text/Pandoc/Readers/Muse.hs
index 5d417e717..3b64fe5ef 100644
--- a/src/Text/Pandoc/Readers/Muse.hs
+++ b/src/Text/Pandoc/Readers/Muse.hs
@@ -45,7 +45,7 @@ import Control.Monad.Reader
import Control.Monad.Except (throwError)
import Data.Bifunctor
import Data.Default
-import Data.List (intercalate)
+import Data.List (intercalate, transpose)
import Data.List.Split (splitOn)
import qualified Data.Map as M
import qualified Data.Set as Set
@@ -135,9 +135,6 @@ parseMuse = do
-- * 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.
lchop :: String -> String
lchop ('\n':xs) = xs
@@ -151,10 +148,10 @@ unindent :: String -> String
unindent = rchop . intercalate "\n" . dropSpacePrefix . splitOn "\n" . lchop
dropSpacePrefix :: [String] -> [String]
-dropSpacePrefix lns =
- map (drop maxIndent) lns
- where flns = filter (not . all (== ' ')) lns
- maxIndent = if null flns then maximum (map length lns) else length $ takeWhile (== ' ') $ foldl1 commonPrefix flns
+dropSpacePrefix lns = drop maxIndent <$> lns
+ where isSpaceChar c = c == ' ' || c == '\t'
+ maxIndent = length $ takeWhile (isSpaceChar . head) $ takeWhile same $ transpose lns
+ same = and . (zipWith (==) <*> drop 1)
atStart :: PandocMonad m => MuseParser m ()
atStart = do