{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
module Text.Pandoc.Shared (
splitBy,
splitTextBy,
splitByIndices,
splitStringByIndices,
splitTextByIndices,
substitute,
ordNub,
findM,
ToString (..),
ToText (..),
tshow,
backslashEscapes,
escapeStringUsing,
elemText,
notElemText,
stripTrailingNewlines,
trim,
triml,
trimr,
trimMath,
stripFirstAndLast,
camelCaseToHyphenated,
camelCaseStrToHyphenated,
toRomanNumeral,
escapeURI,
tabFilter,
crFilter,
normalizeDate,
orderedListMarkers,
extractSpaces,
removeFormatting,
deNote,
deLink,
stringify,
capitalize,
compactify,
compactifyDL,
linesToPara,
makeSections,
uniqueIdent,
inlineListToIdentifier,
isHeaderBlock,
headerShift,
stripEmptyParagraphs,
onlySimpleTableCells,
isTightList,
taskListItemFromAscii,
taskListItemToAscii,
addMetaField,
makeMeta,
eastAsianLineBreakFilter,
underlineSpan,
htmlSpanLikeElements,
splitSentences,
filterIpynbOutput,
renderTags',
inDirectory,
collapseFilePath,
uriPathToPath,
filteredFilesFromArchive,
schemes,
isURI,
mapLeft,
blocksToInlines,
blocksToInlines',
blocksToInlinesWithSep,
defaultBlocksSeparator,
safeRead,
safeStrRead,
defaultUserDataDirs,
pandocVersion
) where
import Codec.Archive.Zip
import qualified Control.Exception as E
import Control.Monad (MonadPlus (..), msum, unless)
import qualified Control.Monad.State.Strict as S
import qualified Data.ByteString.Lazy as BL
import qualified Data.Bifunctor as Bifunctor
import Data.Char (isAlpha, isLower, isSpace, isUpper, toLower, isAlphaNum,
generalCategory, GeneralCategory(NonSpacingMark,
SpacingCombiningMark, EnclosingMark, ConnectorPunctuation))
import Data.List (find, intercalate, intersperse, stripPrefix, sortOn)
import qualified Data.Map as M
import Data.Maybe (mapMaybe, fromMaybe)
import Data.Monoid (Any (..))
import Data.Sequence (ViewL (..), ViewR (..), viewl, viewr)
import qualified Data.Set as Set
import qualified Data.Text as T
import Data.Version (showVersion)
import Network.URI (URI (uriScheme), escapeURIString, parseURI)
import Paths_pandoc (version)
import System.Directory
import System.FilePath (isPathSeparator, splitDirectories)
import qualified System.FilePath.Posix as Posix
import Text.HTML.TagSoup (RenderOptions (..), Tag (..), renderOptions,
renderTagsOptions)
import Text.Pandoc.Builder (Blocks, Inlines, ToMetaValue (..))
import qualified Text.Pandoc.Builder as B
import Data.Time
import Text.Pandoc.Asciify (toAsciiChar)
import Text.Pandoc.Definition
import Text.Pandoc.Extensions (Extensions, Extension(..), extensionEnabled)
import Text.Pandoc.Generic (bottomUp)
import Text.DocLayout (charWidth)
import Text.Pandoc.Walk
pandocVersion :: T.Text
pandocVersion = T.pack $ showVersion version
splitBy :: (a -> Bool) -> [a] -> [[a]]
splitBy _ [] = []
splitBy isSep lst =
let (first, rest) = break isSep lst
rest' = dropWhile isSep rest
in first:splitBy isSep rest'
splitTextBy :: (Char -> Bool) -> T.Text -> [T.Text]
splitTextBy isSep t
| T.null t = []
| otherwise = let (first, rest) = T.break isSep t
rest' = T.dropWhile isSep rest
in first : splitTextBy isSep rest'
splitByIndices :: [Int] -> [a] -> [[a]]
splitByIndices [] lst = [lst]
splitByIndices (x:xs) lst = first:splitByIndices (map (\y -> y - x) xs) rest
where (first, rest) = splitAt x lst
splitStringByIndices :: [Int] -> [Char] -> [[Char]]
splitStringByIndices [] lst = [lst]
splitStringByIndices (x:xs) lst =
let (first, rest) = splitAt' x lst in
first : splitStringByIndices (map (\y -> y - x) xs) rest
splitTextByIndices :: [Int] -> T.Text -> [T.Text]
splitTextByIndices ns = fmap T.pack . splitStringByIndices ns . T.unpack
splitAt' :: Int -> [Char] -> ([Char],[Char])
splitAt' _ [] = ([],[])
splitAt' n xs | n <= 0 = ([],xs)
splitAt' n (x:xs) = (x:ys,zs)
where (ys,zs) = splitAt' (n - charWidth x) xs
substitute :: (Eq a) => [a] -> [a] -> [a] -> [a]
substitute _ _ [] = []
substitute [] _ xs = xs
substitute target replacement lst@(x:xs) =
case stripPrefix target lst of
Just lst' -> replacement ++ substitute target replacement lst'
Nothing -> x : substitute target replacement xs
ordNub :: (Ord a) => [a] -> [a]
ordNub l = go Set.empty l
where
go _ [] = []
go s (x:xs) = if x `Set.member` s then go s xs
else x : go (Set.insert x s) xs
findM :: forall m t a. (Monad m, Foldable t) => (a -> m Bool) -> t a -> m (Maybe a)
findM p = foldr go (pure Nothing)
where
go :: a -> m (Maybe a) -> m (Maybe a)
go x acc = do
b <- p x
if b then pure (Just x) else acc
class ToString a where
toString :: a -> String
instance ToString String where
toString = id
instance ToString T.Text where
toString = T.unpack
class ToText a where
toText :: a -> T.Text
instance ToText String where
toText = T.pack
instance ToText T.Text where
toText = id
tshow :: Show a => a -> T.Text
tshow = T.pack . show
backslashEscapes :: [Char]
-> [(Char, T.Text)]
backslashEscapes = map (\ch -> (ch, T.pack ['\\',ch]))
escapeStringUsing :: [(Char, T.Text)] -> T.Text -> T.Text
escapeStringUsing tbl = T.concatMap $ \c -> fromMaybe (T.singleton c) $ lookup c tbl
elemText :: Char -> T.Text -> Bool
elemText c = T.any (== c)
notElemText :: Char -> T.Text -> Bool
notElemText c = T.all (/= c)
stripTrailingNewlines :: T.Text -> T.Text
stripTrailingNewlines = T.dropWhileEnd (== '\n')
trim :: T.Text -> T.Text
trim = T.dropAround (`elemText` " \r\n\t")
triml :: T.Text -> T.Text
triml = T.dropWhile (`elemText` " \r\n\t")
trimr :: T.Text -> T.Text
trimr = T.dropWhileEnd (`elemText` " \r\n\t")
trimMath :: T.Text -> T.Text
trimMath = triml . T.reverse . stripBeginSpace . T.reverse
where
stripBeginSpace t
| T.null pref = t
| Just ('\\', _) <- T.uncons suff = T.cons (T.last pref) suff
| otherwise = suff
where
(pref, suff) = T.span (`elemText` " \t\n\r") t
stripFirstAndLast :: T.Text -> T.Text
stripFirstAndLast t = case T.uncons t of
Just (_, t') -> case T.unsnoc t' of
Just (t'', _) -> t''
_ -> t'
_ -> ""
camelCaseToHyphenated :: T.Text -> T.Text
camelCaseToHyphenated = T.pack . camelCaseStrToHyphenated . T.unpack
camelCaseStrToHyphenated :: String -> String
camelCaseStrToHyphenated [] = ""
camelCaseStrToHyphenated (a:b:rest)
| isLower a
, isUpper b = a:'-':toLower b:camelCaseStrToHyphenated rest
camelCaseStrToHyphenated (a:b:c:rest)
| isUpper a
, isUpper b
, isLower c = toLower a:'-':toLower b:camelCaseStrToHyphenated (c:rest)
camelCaseStrToHyphenated (a:rest) = toLower a:camelCaseStrToHyphenated rest
toRomanNumeral :: Int -> T.Text
toRomanNumeral x
| x >= 4000 || x < 0 = "?"
| x >= 1000 = "M" <> toRomanNumeral (x - 1000)
| x >= 900 = "CM" <> toRomanNumeral (x - 900)
| x >= 500 = "D" <> toRomanNumeral (x - 500)
| x >= 400 = "CD" <> toRomanNumeral (x - 400)
| x >= 100 = "C" <> toRomanNumeral (x - 100)
| x >= 90 = "XC" <> toRomanNumeral (x - 90)
| x >= 50 = "L" <> toRomanNumeral (x - 50)
| x >= 40 = "XL" <> toRomanNumeral (x - 40)
| x >= 10 = "X" <> toRomanNumeral (x - 10)
| x == 9 = "IX"
| x >= 5 = "V" <> toRomanNumeral (x - 5)
| x == 4 = "IV"
| x >= 1 = "I" <> toRomanNumeral (x - 1)
| otherwise = ""
escapeURI :: T.Text -> T.Text
escapeURI = T.pack . escapeURIString (not . needsEscaping) . T.unpack
where needsEscaping c = isSpace c || c `elemText` "<>|\"{}[]^`"
tabFilter :: Int
-> T.Text
-> T.Text
tabFilter 0 = id
tabFilter tabStop = T.unlines . map go . T.lines
where go s =
let (s1, s2) = T.break (== '\t') s
in if T.null s2
then s1
else s1 <> T.replicate
(tabStop - (T.length s1 `mod` tabStop)) (T.pack " ")
<> go (T.drop 1 s2)
crFilter :: T.Text -> T.Text
crFilter = T.filter (/= '\r')
normalizeDate :: T.Text -> Maybe T.Text
normalizeDate = fmap T.pack . normalizeDate' . T.unpack
normalizeDate' :: String -> Maybe String
normalizeDate' s = fmap (formatTime defaultTimeLocale "%F")
(msum $ map (\fs -> parsetimeWith fs s >>= rejectBadYear) formats :: Maybe Day)
where rejectBadYear day = case toGregorian day of
(y, _, _) | y >= 1601 && y <= 9999 -> Just day
_ -> Nothing
parsetimeWith = parseTimeM True defaultTimeLocale
formats = ["%x","%m/%d/%Y", "%D","%F", "%d %b %Y",
"%e %B %Y", "%b. %e, %Y", "%B %e, %Y",
"%Y%m%d", "%Y%m", "%Y"]
orderedListMarkers :: (Int, ListNumberStyle, ListNumberDelim) -> [T.Text]
orderedListMarkers (start, numstyle, numdelim) =
let nums = case numstyle of
DefaultStyle -> map tshow [start..]
Example -> map tshow [start..]
Decimal -> map tshow [start..]
UpperAlpha -> drop (start - 1) $ cycle $
map T.singleton ['A'..'Z']
LowerAlpha -> drop (start - 1) $ cycle $
map T.singleton ['a'..'z']
UpperRoman -> map toRomanNumeral [start..]
LowerRoman -> map (T.toLower . toRomanNumeral) [start..]
inDelim str = case numdelim of
DefaultDelim -> str <> "."
Period -> str <> "."
OneParen -> str <> ")"
TwoParens -> "(" <> str <> ")"
in map inDelim nums
extractSpaces :: (Inlines -> Inlines) -> Inlines -> Inlines
extractSpaces f is =
let contents = B.unMany is
left = case viewl contents of
(Space :< _) -> B.space
(SoftBreak :< _) -> B.softbreak
_ -> mempty
right = case viewr contents of
(_ :> Space) -> B.space
(_ :> SoftBreak) -> B.softbreak
_ -> mempty in
(left <> f (B.trimInlines . B.Many $ contents) <> right)
removeFormatting :: Walkable Inline a => a -> [Inline]
removeFormatting = query go . walk (deNote . deQuote)
where go :: Inline -> [Inline]
go (Str xs) = [Str xs]
go Space = [Space]
go SoftBreak = [SoftBreak]
go (Code _ x) = [Str x]
go (Math _ x) = [Str x]
go LineBreak = [Space]
go _ = []
deNote :: Inline -> Inline
deNote (Note _) = Str ""
deNote x = x
deLink :: Inline -> Inline
deLink (Link _ ils _) = Span nullAttr ils
deLink x = x
deQuote :: Inline -> Inline
deQuote (Quoted SingleQuote xs) =
Span ("",[],[]) (Str "\8216" : xs ++ [Str "\8217"])
deQuote (Quoted DoubleQuote xs) =
Span ("",[],[]) (Str "\8220" : xs ++ [Str "\8221"])
deQuote x = x
stringify :: Walkable Inline a => a -> T.Text
stringify = query go . walk (deNote . deQuote)
where go :: Inline -> T.Text
go Space = " "
go SoftBreak = " "
go (Str x) = x
go (Code _ x) = x
go (Math _ x) = x
go (RawInline (Format "html") (T.unpack -> ('<':'b':'r':_)))
= " "
go LineBreak = " "
go _ = ""
capitalize :: Walkable Inline a => a -> a
capitalize = walk go
where go :: Inline -> Inline
go (Str s) = Str $ T.toUpper s
go x = x
compactify :: [Blocks]
-> [Blocks]
compactify [] = []
compactify items =
let (others, final) = (init items, last items)
in case reverse (B.toList final) of
(Para a:xs)
| null [Para x | Para x <- xs ++ concatMap B.toList others]
-> others ++ [B.fromList (reverse (Plain a : xs))]
_ | null [Para x | Para x <- concatMap B.toList items]
-> items
_ -> map (fmap plainToPara) items
plainToPara :: Block -> Block
plainToPara (Plain ils) = Para ils
plainToPara x = x
compactifyDL :: [(Inlines, [Blocks])] -> [(Inlines, [Blocks])]
compactifyDL items =
let defs = concatMap snd items
in case reverse (concatMap B.toList defs) of
(Para x:xs)
| not (any isPara xs) ->
let (t,ds) = last items
lastDef = B.toList $ last ds
ds' = init ds ++
if null lastDef
then [B.fromList lastDef]
else [B.fromList $ init lastDef ++ [Plain x]]
in init items ++ [(t, ds')]
| otherwise -> items
_ -> items
combineLines :: [[Inline]] -> [Inline]
combineLines = intercalate [LineBreak]
linesToPara :: [[Inline]] -> Block
linesToPara = Para . combineLines
isPara :: Block -> Bool
isPara (Para _) = True
isPara _ = False
inlineListToIdentifier :: Extensions -> [Inline] -> T.Text
inlineListToIdentifier exts =
dropNonLetter . filterAscii . toIdent . stringify . walk unEmojify
where
unEmojify :: [Inline] -> [Inline]
unEmojify
| extensionEnabled Ext_gfm_auto_identifiers exts ||
extensionEnabled Ext_ascii_identifiers exts = walk unEmoji
| otherwise = id
unEmoji (Span ("",["emoji"],[("data-emoji",ename)]) _) = Str ename
unEmoji x = x
dropNonLetter
| extensionEnabled Ext_gfm_auto_identifiers exts = id
| otherwise = T.dropWhile (not . isAlpha)
filterAscii
| extensionEnabled Ext_ascii_identifiers exts
= T.pack . mapMaybe toAsciiChar . T.unpack
| otherwise = id
toIdent
| extensionEnabled Ext_gfm_auto_identifiers exts =
filterPunct . spaceToDash . T.toLower
| otherwise = T.intercalate "-" . T.words . filterPunct . T.toLower
filterPunct = T.filter (\c -> isSpace c || isAlphaNum c || isAllowedPunct c)
isAllowedPunct c
| extensionEnabled Ext_gfm_auto_identifiers exts
= c == '-' || c == '_' ||
generalCategory c `elem` [NonSpacingMark, SpacingCombiningMark,
EnclosingMark, ConnectorPunctuation]
| otherwise = c == '_' || c == '-' || c == '.'
spaceToDash = T.map (\c -> if isSpace c then '-' else c)
makeSections :: Bool -> Maybe Int -> [Block] -> [Block]
makeSections numbering mbBaseLevel bs =
S.evalState (go bs) (mbBaseLevel, [])
where
go :: [Block] -> S.State (Maybe Int, [Int]) [Block]
go (Header level (ident,classes,kvs) title':xs) = do
(mbLevel, lastnum) <- S.get
let level' = fromMaybe level mbLevel
let lastnum' = take level' lastnum
let newnum =
if level' > 0
then case length lastnum' of
x | "unnumbered" `elem` classes -> []
| x >= level' -> init lastnum' ++ [last lastnum' + 1]
| otherwise -> lastnum ++
replicate (level' - length lastnum - 1) 0 ++ [1]
else []
unless (null newnum) $ S.modify $ \(mbl, _) -> (mbl, newnum)
let (sectionContents, rest) = break (headerLtEq level) xs
S.modify $ \(_, ln) -> (fmap (+ 1) mbLevel, ln)
sectionContents' <- go sectionContents
S.modify $ \(_, ln) -> (mbLevel, ln)
rest' <- go rest
let kvs' =
case lookup "number" kvs of
Nothing | numbering
, not ("unnumbered" `elem` classes) ->
("number", T.intercalate "." (map tshow newnum)) : kvs
_ -> kvs
let divattr = (ident, "section":classes, kvs')
let attr = ("",classes,kvs')
return $
Div divattr (Header level' attr title' : sectionContents') : rest'
go (Div divattr@(dident,dclasses,_) (Header level hattr title':ys) : xs)
| all (\case
Header level' _ _ -> level' > level
_ -> True) ys
, "column" `notElem` dclasses
, "columns" `notElem` dclasses = do
inner <- go (Header level hattr title':ys)
rest <- go xs
return $
case inner of
[Div divattr'@(dident',_,_) zs]
| T.null dident || T.null dident' || dident == dident'
-> Div (combineAttr divattr' divattr) zs : rest
_ -> Div divattr inner : rest
go (Div attr xs : rest) = do
xs' <- go xs
rest' <- go rest
return $ Div attr xs' : rest'
go (x:xs) = (x :) <$> go xs
go [] = return []
combineAttr :: Attr -> Attr -> Attr
combineAttr (id1, classes1, kvs1) (id2, classes2, kvs2) =
(if T.null id1 then id2 else id1,
ordNub (classes1 ++ classes2),
foldr (\(k,v) kvs -> case lookup k kvs of
Nothing -> (k,v):kvs
Just _ -> kvs) mempty (kvs1 ++ kvs2))
headerLtEq :: Int -> Block -> Bool
headerLtEq level (Header l _ _) = l <= level
headerLtEq level (Div _ (b:_)) = headerLtEq level b
headerLtEq _ _ = False
uniqueIdent :: Extensions -> [Inline] -> Set.Set T.Text -> T.Text
uniqueIdent exts title' usedIdents =
if baseIdent `Set.member` usedIdents
then case find (\x -> numIdent x `Set.notMember` usedIdents)
([1..60000] :: [Int]) of
Just x -> numIdent x
Nothing -> baseIdent
else baseIdent
where
baseIdent = case inlineListToIdentifier exts title' of
"" -> "section"
x -> x
numIdent n = baseIdent <> "-" <> tshow n
isHeaderBlock :: Block -> Bool
isHeaderBlock Header{} = True
isHeaderBlock _ = False
headerShift :: Int -> Pandoc -> Pandoc
headerShift n (Pandoc meta (Header m _ ils : bs))
| n < 0
, m + n == 0 = headerShift n $
B.setTitle (B.fromList ils) $ Pandoc meta bs
headerShift n (Pandoc meta bs) = Pandoc meta (walk shift bs)
where
shift :: Block -> Block
shift (Header level attr inner)
| level + n > 0 = Header (level + n) attr inner
| otherwise = Para inner
shift x = x
stripEmptyParagraphs :: Pandoc -> Pandoc
stripEmptyParagraphs = walk go
where go :: [Block] -> [Block]
go = filter (not . isEmptyParagraph)
isEmptyParagraph (Para []) = True
isEmptyParagraph _ = False
onlySimpleTableCells :: [[[Block]]] -> Bool
onlySimpleTableCells = all isSimpleCell . concat
where
isSimpleCell [Plain ils] = not (hasLineBreak ils)
isSimpleCell [Para ils ] = not (hasLineBreak ils)
isSimpleCell [] = True
isSimpleCell _ = False
hasLineBreak = getAny . query isLineBreak
isLineBreak LineBreak = Any True
isLineBreak _ = Any False
isTightList :: [[Block]] -> Bool
isTightList = all (\item -> firstIsPlain item || null item)
where firstIsPlain (Plain _ : _) = True
firstIsPlain _ = False
taskListItemFromAscii :: Extensions -> [Block] -> [Block]
taskListItemFromAscii = handleTaskListItem fromMd
where
fromMd (Str "[" : Space : Str "]" : Space : is) = Str "☐" : Space : is
fromMd (Str "[x]" : Space : is) = Str "☒" : Space : is
fromMd (Str "[X]" : Space : is) = Str "☒" : Space : is
fromMd is = is
taskListItemToAscii :: Extensions -> [Block] -> [Block]
taskListItemToAscii = handleTaskListItem toMd
where
toMd (Str "☐" : Space : is) = rawMd "[ ]" : Space : is
toMd (Str "☒" : Space : is) = rawMd "[x]" : Space : is
toMd is = is
rawMd = RawInline (Format "markdown")
handleTaskListItem :: ([Inline] -> [Inline]) -> Extensions -> [Block] -> [Block]
handleTaskListItem handleInlines exts bls =
if Ext_task_lists `extensionEnabled` exts
then handleItem bls
else bls
where
handleItem (Plain is : bs) = Plain (handleInlines is) : bs
handleItem (Para is : bs) = Para (handleInlines is) : bs
handleItem bs = bs
addMetaField :: ToMetaValue a
=> T.Text
-> a
-> Meta
-> Meta
addMetaField key val (Meta meta) =
Meta $ M.insertWith combine key (toMetaValue val) meta
where combine newval (MetaList xs) = MetaList (xs ++ tolist newval)
combine newval x = MetaList [x, newval]
tolist (MetaList ys) = ys
tolist y = [y]
makeMeta :: [Inline] -> [[Inline]] -> [Inline] -> Meta
makeMeta title authors date =
addMetaField "title" (B.fromList title)
$ addMetaField "author" (map B.fromList authors)
$ addMetaField "date" (B.fromList date) nullMeta
eastAsianLineBreakFilter :: Pandoc -> Pandoc
eastAsianLineBreakFilter = bottomUp go
where go (x:SoftBreak:y:zs)
| Just (_, b) <- T.unsnoc $ stringify x
, Just (c, _) <- T.uncons $ stringify y
, charWidth b == 2
, charWidth c == 2
= x:y:zs
| otherwise
= x:SoftBreak:y:zs
go xs
= xs
{-# DEPRECATED underlineSpan "Use Text.Pandoc.Builder.underline instead" #-}
underlineSpan :: Inlines -> Inlines
underlineSpan = B.underline
htmlSpanLikeElements :: Set.Set T.Text
htmlSpanLikeElements = Set.fromList ["kbd", "mark", "dfn"]
breakSentence :: [Inline] -> ([Inline], [Inline])
breakSentence [] = ([],[])
breakSentence xs =
let isSentenceEndInline (Str ys)
| Just (_, c) <- T.unsnoc ys = c == '.' || c == '?'
isSentenceEndInline LineBreak = True
isSentenceEndInline _ = False
(as, bs) = break isSentenceEndInline xs
in case bs of
[] -> (as, [])
[c] -> (as ++ [c], [])
(c:Space:cs) -> (as ++ [c], cs)
(c:SoftBreak:cs) -> (as ++ [c], cs)
(Str ".":Str s@(T.uncons -> Just (')',_)):cs)
-> (as ++ [Str ".", Str s], cs)
(x@(Str (T.stripPrefix ".)" -> Just _)):cs) -> (as ++ [x], cs)
(LineBreak:x@(Str (T.uncons -> Just ('.',_))):cs) -> (as ++[LineBreak], x:cs)
(c:cs) -> (as ++ [c] ++ ds, es)
where (ds, es) = breakSentence cs
splitSentences :: [Inline] -> [[Inline]]
splitSentences xs =
let (sent, rest) = breakSentence xs
in if null rest then [sent] else sent : splitSentences rest
filterIpynbOutput :: Maybe Format -> Pandoc -> Pandoc
filterIpynbOutput mode = walk go
where go (Div (ident, "output":os, kvs) bs) =
case mode of
Nothing -> Div (ident, "output":os, kvs) []
Just fmt
| fmt == Format "ipynb"
-> Div (ident, "output":os, kvs) bs
| otherwise -> Div (ident, "output":os, kvs) $
walk removeANSI $
take 1 $ sortOn rank bs
where
rank (RawBlock (Format "html") _)
| fmt == Format "html" = 1 :: Int
| fmt == Format "markdown" = 2
| otherwise = 3
rank (RawBlock (Format "latex") _)
| fmt == Format "latex" = 1
| fmt == Format "markdown" = 2
| otherwise = 3
rank (RawBlock f _)
| fmt == f = 1
| otherwise = 3
rank (Para [Image{}]) = 1
rank _ = 2
removeANSI (CodeBlock attr code) =
CodeBlock attr (removeANSIEscapes code)
removeANSI x = x
removeANSIEscapes t
| Just cs <- T.stripPrefix "\x1b[" t =
removeANSIEscapes $ T.drop 1 $ T.dropWhile (/='m') cs
| Just (c, cs) <- T.uncons t = T.cons c $ removeANSIEscapes cs
| otherwise = ""
go x = x
renderTags' :: [Tag T.Text] -> T.Text
renderTags' = renderTagsOptions
renderOptions{ optMinimize = matchTags ["hr", "br", "img",
"meta", "link", "col"]
, optRawTag = matchTags ["script", "style"] }
where matchTags tags = flip elem tags . T.toLower
inDirectory :: FilePath -> IO a -> IO a
inDirectory path action = E.bracket
getCurrentDirectory
setCurrentDirectory
(const $ setCurrentDirectory path >> action)
mapLeft :: (a -> b) -> Either a c -> Either b c
mapLeft = Bifunctor.first
collapseFilePath :: FilePath -> FilePath
collapseFilePath = Posix.joinPath . reverse . foldl go [] . splitDirectories
where
go rs "." = rs
go r@(p:rs) ".." = case p of
".." -> "..":r
(checkPathSeperator -> Just True) -> "..":r
_ -> rs
go _ (checkPathSeperator -> Just True) = [[Posix.pathSeparator]]
go rs x = x:rs
isSingleton [] = Nothing
isSingleton [x] = Just x
isSingleton _ = Nothing
checkPathSeperator = fmap isPathSeparator . isSingleton
uriPathToPath :: T.Text -> FilePath
uriPathToPath (T.unpack -> path) =
#ifdef _WINDOWS
case path of
'/':ps -> ps
ps -> ps
#else
path
#endif
filteredFilesFromArchive :: Archive -> (FilePath -> Bool) -> [(FilePath, BL.ByteString)]
filteredFilesFromArchive zf f =
mapMaybe (fileAndBinary zf) (filter f (filesInArchive zf))
where
fileAndBinary :: Archive -> FilePath -> Maybe (FilePath, BL.ByteString)
fileAndBinary a fp = findEntryByPath fp a >>= \e -> Just (fp, fromEntry e)
schemes :: Set.Set T.Text
schemes = Set.fromList
[ "aaa", "aaas", "about", "acap", "acct", "acr", "adiumxtra", "afp", "afs"
, "aim", "appdata", "apt", "attachment", "aw", "barion", "beshare", "bitcoin"
, "blob", "bolo", "browserext", "callto", "cap", "chrome", "chrome-extension"
, "cid", "coap", "coaps", "com-eventbrite-attendee", "content", "crid", "cvs"
, "data", "dav", "dict", "dis", "dlna-playcontainer", "dlna-playsingle"
, "dns", "dntp", "dtn", "dvb", "ed2k", "example", "facetime", "fax", "feed"
, "feedready", "file", "filesystem", "finger", "fish", "ftp", "geo", "gg"
, "git", "gizmoproject", "go", "gopher", "graph", "gtalk", "h323", "ham"
, "hcp", "http", "https", "hxxp", "hxxps", "hydrazone", "iax", "icap", "icon"
, "im", "imap", "info", "iotdisco", "ipn", "ipp", "ipps", "irc", "irc6"
, "ircs", "iris", "iris.beep", "iris.lwz", "iris.xpc", "iris.xpcs"
, "isostore", "itms", "jabber", "jar", "jms", "keyparc", "lastfm", "ldap"
, "ldaps", "lvlt", "magnet", "mailserver", "mailto", "maps", "market"
, "message", "mid", "mms", "modem", "mongodb", "moz", "ms-access"
, "ms-browser-extension", "ms-drive-to", "ms-enrollment", "ms-excel"
, "ms-gamebarservices", "ms-getoffice", "ms-help", "ms-infopath"
, "ms-media-stream-id", "ms-officeapp", "ms-project", "ms-powerpoint"
, "ms-publisher", "ms-search-repair", "ms-secondary-screen-controller"
, "ms-secondary-screen-setup", "ms-settings", "ms-settings-airplanemode"
, "ms-settings-bluetooth", "ms-settings-camera", "ms-settings-cellular"
, "ms-settings-cloudstorage", "ms-settings-connectabledevices"
, "ms-settings-displays-topology", "ms-settings-emailandaccounts"
, "ms-settings-language", "ms-settings-location", "ms-settings-lock"
, "ms-settings-nfctransactions", "ms-settings-notifications"
, "ms-settings-power", "ms-settings-privacy", "ms-settings-proximity"
, "ms-settings-screenrotation", "ms-settings-wifi", "ms-settings-workplace"
, "ms-spd", "ms-sttoverlay", "ms-transit-to", "ms-virtualtouchpad"
, "ms-visio", "ms-walk-to", "ms-whiteboard", "ms-whiteboard-cmd", "ms-word"
, "msnim", "msrp", "msrps", "mtqp", "mumble", "mupdate", "mvn", "news", "nfs"
, "ni", "nih", "nntp", "notes", "ocf", "oid", "onenote", "onenote-cmd"
, "opaquelocktoken", "pack", "palm", "paparazzi", "pkcs11", "platform", "pop"
, "pres", "prospero", "proxy", "pwid", "psyc", "qb", "query", "redis"
, "rediss", "reload", "res", "resource", "rmi", "rsync", "rtmfp", "rtmp"
, "rtsp", "rtsps", "rtspu", "secondlife", "service", "session", "sftp", "sgn"
, "shttp", "sieve", "sip", "sips", "skype", "smb", "sms", "smtp", "snews"
, "snmp", "soap.beep", "soap.beeps", "soldat", "spotify", "ssh", "steam"
, "stun", "stuns", "submit", "svn", "tag", "teamspeak", "tel", "teliaeid"
, "telnet", "tftp", "things", "thismessage", "tip", "tn3270", "tool", "turn"
, "turns", "tv", "udp", "unreal", "urn", "ut2004", "v-event", "vemmi"
, "ventrilo", "videotex", "vnc", "view-source", "wais", "webcal", "wpid"
, "ws", "wss", "wtai", "wyciwyg", "xcon", "xcon-userid", "xfire"
, "xmlrpc.beep", "xmlrpc.beeps", "xmpp", "xri", "ymsgr", "z39.50", "z39.50r"
, "z39.50s"
, "doi", "isbn", "javascript", "pmid"
]
isURI :: T.Text -> Bool
isURI = maybe False hasKnownScheme . parseURI . T.unpack
where
hasKnownScheme = (`Set.member` schemes) . T.toLower .
T.filter (/= ':') . T.pack . uriScheme
blockToInlines :: Block -> Inlines
blockToInlines (Plain ils) = B.fromList ils
blockToInlines (Para ils) = B.fromList ils
blockToInlines (LineBlock lns) = B.fromList $ combineLines lns
blockToInlines (CodeBlock attr str) = B.codeWith attr str
blockToInlines (RawBlock (Format fmt) str) = B.rawInline fmt str
blockToInlines (BlockQuote blks) = blocksToInlines' blks
blockToInlines (OrderedList _ blkslst) =
mconcat $ map blocksToInlines' blkslst
blockToInlines (BulletList blkslst) =
mconcat $ map blocksToInlines' blkslst
blockToInlines (DefinitionList pairslst) =
mconcat $ map f pairslst
where
f (ils, blkslst) = B.fromList ils <> B.str ":" <> B.space <>
mconcat (map blocksToInlines' blkslst)
blockToInlines (Header _ _ ils) = B.fromList ils
blockToInlines HorizontalRule = mempty
blockToInlines (Table _ _ _ (TableHead _ hbd) bodies (TableFoot _ fbd)) =
mconcat $ intersperse B.linebreak $
map (mconcat . map blocksToInlines') (plainRowBody <$> hbd <> unTableBodies bodies <> fbd)
where
plainRowBody (Row _ body) = cellBody <$> body
cellBody (Cell _ _ _ _ body) = body
unTableBody (TableBody _ _ hd bd) = hd <> bd
unTableBodies = concatMap unTableBody
blockToInlines (Div _ blks) = blocksToInlines' blks
blockToInlines Null = mempty
blocksToInlinesWithSep :: Inlines -> [Block] -> Inlines
blocksToInlinesWithSep sep =
mconcat . intersperse sep . map blockToInlines
blocksToInlines' :: [Block] -> Inlines
blocksToInlines' = blocksToInlinesWithSep defaultBlocksSeparator
blocksToInlines :: [Block] -> [Inline]
blocksToInlines = B.toList . blocksToInlines'
defaultBlocksSeparator :: Inlines
defaultBlocksSeparator =
B.space <> B.str "¶" <> B.space
safeRead :: (MonadPlus m, Read a) => T.Text -> m a
safeRead = safeStrRead . T.unpack
safeStrRead :: (MonadPlus m, Read a) => String -> m a
safeStrRead s = case reads s of
(d,x):_
| all isSpace x -> return d
_ -> mzero
defaultUserDataDirs :: IO [FilePath]
defaultUserDataDirs = E.catch (do
xdgDir <- getXdgDirectory XdgData "pandoc"
legacyDir <- getAppUserDataDirectory "pandoc"
return $ ordNub [xdgDir, legacyDir])
(\(_ :: E.SomeException) -> return [])