{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE TypeSynonymInstances #-}
module Text.Pandoc.Shared (
splitBy,
splitByIndices,
splitStringByIndices,
substitute,
ordNub,
ToString (..),
backslashEscapes,
escapeStringUsing,
stripTrailingNewlines,
trim,
triml,
trimr,
trimMath,
stripFirstAndLast,
camelCaseToHyphenated,
toRomanNumeral,
escapeURI,
tabFilter,
crFilter,
normalizeDate,
orderedListMarkers,
extractSpaces,
removeFormatting,
deNote,
stringify,
capitalize,
compactify,
compactifyDL,
linesToPara,
Element (..),
hierarchicalize,
uniqueIdent,
inlineListToIdentifier,
isHeaderBlock,
headerShift,
stripEmptyParagraphs,
isTightList,
addMetaField,
makeMeta,
eastAsianLineBreakFilter,
underlineSpan,
splitSentences,
renderTags',
inDirectory,
collapseFilePath,
uriPathToPath,
filteredFilesFromArchive,
schemes,
isURI,
mapLeft,
blocksToInlines,
blocksToInlines',
blocksToInlinesWithSep,
defaultBlocksSeparator,
safeRead,
withTempDir,
pandocVersion
) where
import Prelude
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, isDigit, isLetter, isLower, isSpace, isUpper,
toLower)
import Data.Data (Data, Typeable)
import Data.List (find, intercalate, intersperse, stripPrefix)
import qualified Data.Map as M
import Data.Maybe (mapMaybe)
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 System.IO.Temp
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.Definition
import Text.Pandoc.Generic (bottomUp)
import Text.Pandoc.Pretty (charWidth)
import Text.Pandoc.Walk
pandocVersion :: String
pandocVersion = 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'
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
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
class ToString a where
toString :: a -> String
instance ToString String where
toString = id
instance ToString T.Text where
toString = T.unpack
backslashEscapes :: [Char]
-> [(Char, String)]
backslashEscapes = map (\ch -> (ch, ['\\',ch]))
escapeStringUsing :: [(Char, String)] -> String -> String
escapeStringUsing _ [] = ""
escapeStringUsing escapeTable (x:xs) =
case lookup x escapeTable of
Just str -> str ++ rest
Nothing -> x:rest
where rest = escapeStringUsing escapeTable xs
stripTrailingNewlines :: String -> String
stripTrailingNewlines = reverse . dropWhile (== '\n') . reverse
trim :: String -> String
trim = triml . trimr
triml :: String -> String
triml = dropWhile (`elem` " \r\n\t")
trimr :: String -> String
trimr = reverse . triml . reverse
trimMath :: String -> String
trimMath = triml . reverse . stripspace . reverse
where
stripspace (c1:c2:cs)
| c1 `elem` [' ','\t','\n','\r']
, c2 /= '\\' = stripspace (c2:cs)
stripspace cs = cs
stripFirstAndLast :: String -> String
stripFirstAndLast str =
drop 1 $ take (length str - 1) str
camelCaseToHyphenated :: String -> String
camelCaseToHyphenated [] = ""
camelCaseToHyphenated (a:b:rest) | isLower a && isUpper b =
a:'-':toLower b:camelCaseToHyphenated rest
camelCaseToHyphenated (a:rest) = toLower a:camelCaseToHyphenated rest
toRomanNumeral :: Int -> String
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 :: String -> String
escapeURI = escapeURIString (not . needsEscaping)
where needsEscaping c = isSpace c || c `elem`
['<','>','|','"','{','}','[',']','^', '`']
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 :: 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) -> [String]
orderedListMarkers (start, numstyle, numdelim) =
let singleton c = [c]
nums = case numstyle of
DefaultStyle -> map show [start..]
Example -> map show [start..]
Decimal -> map show [start..]
UpperAlpha -> drop (start - 1) $ cycle $
map singleton ['A'..'Z']
LowerAlpha -> drop (start - 1) $ cycle $
map singleton ['a'..'z']
UpperRoman -> map toRomanNumeral [start..]
LowerRoman -> map (map 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
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 -> String
stringify = query go . walk (deNote . deQuote)
where go :: Inline -> [Char]
go Space = " "
go SoftBreak = " "
go (Str x) = x
go (Code _ x) = x
go (Math _ x) = x
go (RawInline (Format "html") ('<':'b':'r':_)) = " "
go LineBreak = " "
go _ = ""
capitalize :: Walkable Inline a => a -> a
capitalize = walk go
where go :: Inline -> Inline
go (Str s) = Str (T.unpack $ T.toUpper $ T.pack 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) -> case [Para x | Para x <- concatMap B.toList items] of
[_] -> others ++ [B.fromList (reverse $ Plain a : xs)]
_ -> items
_ -> items
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
data Element = Blk Block
| Sec Int [Int] Attr [Inline] [Element]
deriving (Eq, Read, Show, Typeable, Data)
instance Walkable Inline Element where
walk f (Blk x) = Blk (walk f x)
walk f (Sec lev nums attr ils elts) = Sec lev nums attr (walk f ils) (walk f elts)
walkM f (Blk x) = Blk `fmap` walkM f x
walkM f (Sec lev nums attr ils elts) = do
ils' <- walkM f ils
elts' <- walkM f elts
return $ Sec lev nums attr ils' elts'
query f (Blk x) = query f x
query f (Sec _ _ _ ils elts) = query f ils `mappend` query f elts
instance Walkable Block Element where
walk f (Blk x) = Blk (walk f x)
walk f (Sec lev nums attr ils elts) = Sec lev nums attr (walk f ils) (walk f elts)
walkM f (Blk x) = Blk `fmap` walkM f x
walkM f (Sec lev nums attr ils elts) = do
ils' <- walkM f ils
elts' <- walkM f elts
return $ Sec lev nums attr ils' elts'
query f (Blk x) = query f x
query f (Sec _ _ _ ils elts) = query f ils `mappend` query f elts
inlineListToIdentifier :: [Inline] -> String
inlineListToIdentifier =
dropWhile (not . isAlpha) . intercalate "-" . words .
map (nbspToSp . toLower) .
filter (\c -> isLetter c || isDigit c || c `elem` "_-. ") .
stringify
where nbspToSp '\160' = ' '
nbspToSp x = x
hierarchicalize :: [Block] -> [Element]
hierarchicalize blocks = S.evalState (hierarchicalizeWithIds blocks) []
hierarchicalizeWithIds :: [Block] -> S.State [Int] [Element]
hierarchicalizeWithIds [] = return []
hierarchicalizeWithIds (Header level attr@(_,classes,_) title':xs) = do
lastnum <- S.get
let lastnum' = take level lastnum
let newnum = case length lastnum' of
x | "unnumbered" `elem` classes -> []
| x >= level -> init lastnum' ++ [last lastnum' + 1]
| otherwise -> lastnum ++
replicate (level - length lastnum - 1) 0 ++ [1]
unless (null newnum) $ S.put newnum
let (sectionContents, rest) = break (headerLtEq level) xs
sectionContents' <- hierarchicalizeWithIds sectionContents
rest' <- hierarchicalizeWithIds rest
return $ Sec level newnum attr title' sectionContents' : rest'
hierarchicalizeWithIds (Div ("",["references"],[])
(Header level (ident,classes,kvs) title' : xs):ys) =
hierarchicalizeWithIds (Header level (ident,"references":classes,kvs)
title' : (xs ++ ys))
hierarchicalizeWithIds (x:rest) = do
rest' <- hierarchicalizeWithIds rest
return $ Blk x : rest'
headerLtEq :: Int -> Block -> Bool
headerLtEq level (Header l _ _) = l <= level
headerLtEq level (Div ("",["references"],[]) (Header l _ _ : _)) = l <= level
headerLtEq _ _ = False
uniqueIdent :: [Inline] -> Set.Set String -> String
uniqueIdent title' usedIdents
= let baseIdent = case inlineListToIdentifier title' of
"" -> "section"
x -> x
numIdent n = baseIdent ++ "-" ++ show n
in if baseIdent `Set.member` usedIdents
then case find (\x -> not $ numIdent x `Set.member` usedIdents) ([1..60000] :: [Int]) of
Just x -> numIdent x
Nothing -> baseIdent
else baseIdent
isHeaderBlock :: Block -> Bool
isHeaderBlock Header{} = True
isHeaderBlock _ = False
headerShift :: Int -> Pandoc -> Pandoc
headerShift n = walk shift
where shift :: Block -> Block
shift (Header level attr inner) = Header (level + n) attr inner
shift x = x
stripEmptyParagraphs :: Pandoc -> Pandoc
stripEmptyParagraphs = walk go
where go :: [Block] -> [Block]
go = filter (not . isEmptyParagraph)
isEmptyParagraph (Para []) = True
isEmptyParagraph _ = False
isTightList :: [[Block]] -> Bool
isTightList = all firstIsPlain
where firstIsPlain (Plain _ : _) = True
firstIsPlain _ = False
addMetaField :: ToMetaValue a
=> String
-> 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) =
case (stringify x, stringify y) of
(xs@(_:_), c:_)
| charWidth (last xs) == 2 && charWidth c == 2 -> x:y:zs
_ -> x:SoftBreak:y:zs
go xs = xs
underlineSpan :: Inlines -> Inlines
underlineSpan = B.spanWith ("", ["underline"], [])
breakSentence :: [Inline] -> ([Inline], [Inline])
breakSentence [] = ([],[])
breakSentence xs =
let isSentenceEndInline (Str ys@(_:_)) | last ys == '.' = True
isSentenceEndInline (Str ys@(_:_)) | last ys == '?' = True
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 (')':ys):cs) -> (as ++ [Str ".", Str (')':ys)], cs)
(x@(Str ('.':')':_)):cs) -> (as ++ [x], cs)
(LineBreak:x@(Str ('.':_)):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
renderTags' :: [Tag String] -> String
renderTags' = renderTagsOptions
renderOptions{ optMinimize = matchTags ["hr", "br", "img",
"meta", "link"]
, optRawTag = matchTags ["script", "style"] }
where matchTags tags = flip elem tags . map 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 :: String -> FilePath
uriPathToPath 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 String
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 :: String -> Bool
isURI = maybe False hasKnownScheme . parseURI
where
hasKnownScheme = (`Set.member` schemes) . map toLower .
filter (/= ':') . 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 _ _ _ headers rows) =
mconcat $ intersperse B.linebreak $
map (mconcat . map blocksToInlines') (headers:rows)
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) => String -> m a
safeRead s = case reads s of
(d,x):_
| all isSpace x -> return d
_ -> mzero
withTempDir :: String -> (FilePath -> IO a) -> IO a
withTempDir =
#ifdef _WINDOWS
withTempDirectory "."
#else
withSystemTempDirectory
#endif