#if MIN_VERSION_base(4,8,0)
#else
#endif
module Text.Pandoc.Class ( PandocMonad(..)
, CommonState(..)
, PureState(..)
, getPureState
, getsPureState
, putPureState
, modifyPureState
, getPOSIXTime
, getZonedTime
, readFileFromDirs
, report
, setTrace
, setRequestHeader
, getLog
, setVerbosity
, getVerbosity
, getMediaBag
, setMediaBag
, insertMedia
, setUserDataDir
, getUserDataDir
, fetchItem
, getInputFiles
, setInputFiles
, getOutputFile
, setOutputFile
, setResourcePath
, getResourcePath
, PandocIO(..)
, PandocPure(..)
, FileTree(..)
, FileInfo(..)
, addToFileTree
, runIO
, runIOorExplode
, runPure
, readDefaultDataFile
, readDataFile
, fetchMediaResource
, fillMediaBag
, extractMedia
, toLang
, setTranslations
, translateTerm
, Translations
) where
import Prelude hiding (readFile)
import System.Random (StdGen, next, mkStdGen)
import qualified System.Random as IO (newStdGen)
import Codec.Archive.Zip
import qualified Data.CaseInsensitive as CI
import Data.Unique (hashUnique)
import Data.List (stripPrefix)
import qualified Data.Unique as IO (newUnique)
import qualified Text.Pandoc.UTF8 as UTF8
import qualified System.Directory as Directory
import Text.Pandoc.Compat.Time (UTCTime)
import Text.Pandoc.Logging
import Text.Parsec (ParsecT, getPosition, sourceLine, sourceName)
import qualified Text.Pandoc.Compat.Time as IO (getCurrentTime)
import Text.Pandoc.MIME (MimeType, getMimeType, extensionFromMimeType)
import Text.Pandoc.Definition
import Data.Digest.Pure.SHA (sha1, showDigest)
import Data.Maybe (fromMaybe)
import Data.Time.Clock.POSIX ( utcTimeToPOSIXSeconds
, posixSecondsToUTCTime
, POSIXTime )
import Data.Time.LocalTime (TimeZone, ZonedTime, utcToZonedTime, utc)
import Data.ByteString.Base64 (decodeLenient)
import Network.URI ( escapeURIString, nonStrictRelativeTo,
unEscapeString, parseURIReference, isAllowedInURI,
parseURI, URI(..) )
import Network.HTTP.Client
(httpLbs, responseBody, responseHeaders,
Request(port, host, requestHeaders), parseRequest, newManager)
import Network.HTTP.Client.Internal (addProxy)
import Network.HTTP.Client.TLS (tlsManagerSettings)
import System.Environment (getEnv)
import Network.HTTP.Types.Header ( hContentType )
import Network (withSocketsDo)
import Data.ByteString.Lazy (toChunks)
import qualified Control.Exception as E
import qualified Data.Time.LocalTime as IO (getCurrentTimeZone)
import Text.Pandoc.MediaBag (MediaBag, lookupMedia, mediaDirectory)
import Text.Pandoc.Walk (walkM, walk)
import qualified Text.Pandoc.MediaBag as MB
import qualified Data.ByteString as B
import qualified Data.ByteString.Lazy as BL
import qualified System.Environment as IO (lookupEnv)
import System.FilePath.Glob (match, compile)
import System.Directory (createDirectoryIfMissing, getDirectoryContents,
doesDirectoryExist)
import System.FilePath ((</>), (<.>), takeDirectory,
takeExtension, dropExtension, isRelative, normalise)
import qualified System.FilePath.Glob as IO (glob)
import qualified System.Directory as IO (getModificationTime)
import Control.Monad as M (fail)
import Control.Monad.State.Strict
import Control.Monad.Except
import Data.Word (Word8)
import Data.Default
import System.IO.Error
import System.IO (stderr)
import qualified Data.Map as M
import Text.Pandoc.Error
import Text.Pandoc.BCP47 (Lang(..), parseBCP47, renderLang)
import Text.Pandoc.Translations (Term(..), Translations, lookupTerm,
readTranslations)
import qualified Debug.Trace
#ifdef EMBED_DATA_FILES
import Text.Pandoc.Data (dataFiles)
import qualified System.FilePath.Posix as Posix
import System.FilePath (splitDirectories)
#else
import qualified Paths_pandoc as Paths
#endif
class (Functor m, Applicative m, Monad m, MonadError PandocError m)
=> PandocMonad m where
lookupEnv :: String -> m (Maybe String)
getCurrentTime :: m UTCTime
getCurrentTimeZone :: m TimeZone
newStdGen :: m StdGen
newUniqueHash :: m Int
openURL :: String -> m (B.ByteString, Maybe MimeType)
readFileLazy :: FilePath -> m BL.ByteString
readFileStrict :: FilePath -> m B.ByteString
glob :: String -> m [FilePath]
fileExists :: FilePath -> m Bool
getDataFileName :: FilePath -> m FilePath
getModificationTime :: FilePath -> m UTCTime
getCommonState :: m CommonState
putCommonState :: CommonState -> m ()
getsCommonState :: (CommonState -> a) -> m a
getsCommonState f = f <$> getCommonState
modifyCommonState :: (CommonState -> CommonState) -> m ()
modifyCommonState f = getCommonState >>= putCommonState . f
logOutput :: LogMessage -> m ()
trace :: String -> m ()
trace msg = do
tracing <- getsCommonState stTrace
when tracing $ Debug.Trace.trace ("[trace] " ++ msg) (return ())
setVerbosity :: PandocMonad m => Verbosity -> m ()
setVerbosity verbosity =
modifyCommonState $ \st -> st{ stVerbosity = verbosity }
getVerbosity :: PandocMonad m => m Verbosity
getVerbosity = getsCommonState stVerbosity
getLog :: PandocMonad m => m [LogMessage]
getLog = reverse <$> getsCommonState stLog
report :: PandocMonad m => LogMessage -> m ()
report msg = do
verbosity <- getsCommonState stVerbosity
let level = messageVerbosity msg
when (level <= verbosity) $ logOutput msg
modifyCommonState $ \st -> st{ stLog = msg : stLog st }
setTrace :: PandocMonad m => Bool -> m ()
setTrace useTracing = modifyCommonState $ \st -> st{stTrace = useTracing}
setRequestHeader :: PandocMonad m
=> String
-> String
-> m ()
setRequestHeader name val = modifyCommonState $ \st ->
st{ stRequestHeaders =
(name, val) : filter (\(n,_) -> n /= name) (stRequestHeaders st) }
setMediaBag :: PandocMonad m => MediaBag -> m ()
setMediaBag mb = modifyCommonState $ \st -> st{stMediaBag = mb}
getMediaBag :: PandocMonad m => m MediaBag
getMediaBag = getsCommonState stMediaBag
insertMedia :: PandocMonad m => FilePath -> Maybe MimeType -> BL.ByteString -> m ()
insertMedia fp mime bs = do
mb <- getMediaBag
let mb' = MB.insertMedia fp mime bs mb
setMediaBag mb'
getInputFiles :: PandocMonad m => m [FilePath]
getInputFiles = getsCommonState stInputFiles
setInputFiles :: PandocMonad m => [FilePath] -> m ()
setInputFiles fs = do
let sourceURL = case fs of
[] -> Nothing
(x:_) -> case parseURI x of
Just u
| uriScheme u `elem` ["http:","https:"] ->
Just $ show u{ uriQuery = "",
uriFragment = "" }
_ -> Nothing
modifyCommonState $ \st -> st{ stInputFiles = fs
, stSourceURL = sourceURL }
getOutputFile :: PandocMonad m => m (Maybe FilePath)
getOutputFile = getsCommonState stOutputFile
setOutputFile :: PandocMonad m => Maybe FilePath -> m ()
setOutputFile mbf = modifyCommonState $ \st -> st{ stOutputFile = mbf }
getResourcePath :: PandocMonad m => m [FilePath]
getResourcePath = getsCommonState stResourcePath
setResourcePath :: PandocMonad m => [FilePath] -> m ()
setResourcePath ps = modifyCommonState $ \st -> st{stResourcePath = ps}
getPOSIXTime :: PandocMonad m => m POSIXTime
getPOSIXTime = utcTimeToPOSIXSeconds <$> getCurrentTime
getZonedTime :: PandocMonad m => m ZonedTime
getZonedTime = do
t <- getCurrentTime
tz <- getCurrentTimeZone
return $ utcToZonedTime tz t
readFileFromDirs :: PandocMonad m => [FilePath] -> FilePath -> m (Maybe String)
readFileFromDirs [] _ = return Nothing
readFileFromDirs (d:ds) f = catchError
((Just . UTF8.toStringLazy) <$> readFileLazy (d </> f))
(\_ -> readFileFromDirs ds f)
data CommonState = CommonState { stLog :: [LogMessage]
, stUserDataDir :: Maybe FilePath
, stSourceURL :: Maybe String
, stRequestHeaders :: [(String, String)]
, stMediaBag :: MediaBag
, stTranslations :: Maybe
(Lang, Maybe Translations)
, stInputFiles :: [FilePath]
, stOutputFile :: Maybe FilePath
, stResourcePath :: [FilePath]
, stVerbosity :: Verbosity
, stTrace :: Bool
}
instance Default CommonState where
def = CommonState { stLog = []
, stUserDataDir = Nothing
, stSourceURL = Nothing
, stRequestHeaders = []
, stMediaBag = mempty
, stTranslations = Nothing
, stInputFiles = []
, stOutputFile = Nothing
, stResourcePath = ["."]
, stVerbosity = WARNING
, stTrace = False
}
toLang :: PandocMonad m => Maybe String -> m (Maybe Lang)
toLang Nothing = return Nothing
toLang (Just s) =
case parseBCP47 s of
Left _ -> do
report $ InvalidLang s
return Nothing
Right l -> return (Just l)
setTranslations :: PandocMonad m => Lang -> m ()
setTranslations lang =
modifyCommonState $ \st -> st{ stTranslations = Just (lang, Nothing) }
getTranslations :: PandocMonad m => m Translations
getTranslations = do
mbtrans <- getsCommonState stTranslations
case mbtrans of
Nothing -> return mempty
Just (_, Just t) -> return t
Just (lang, Nothing) -> do
let translationFile = "translations/" ++ renderLang lang ++ ".yaml"
let fallbackFile = "translations/" ++ langLanguage lang ++ ".yaml"
let getTrans fp = do
bs <- readDataFile fp
case readTranslations (UTF8.toString bs) of
Left e -> do
report $ CouldNotLoadTranslations (renderLang lang)
(fp ++ ": " ++ e)
modifyCommonState $ \st ->
st{ stTranslations = Nothing }
return mempty
Right t -> do
modifyCommonState $ \st ->
st{ stTranslations = Just (lang, Just t) }
return t
catchError (getTrans translationFile)
(\_ ->
catchError (getTrans fallbackFile)
(\e -> do
report $ CouldNotLoadTranslations (renderLang lang)
$ case e of
PandocCouldNotFindDataFileError _ ->
"data file " ++ fallbackFile ++ " not found"
_ -> ""
modifyCommonState $ \st -> st{ stTranslations = Nothing }
return mempty))
translateTerm :: PandocMonad m => Term -> m String
translateTerm term = do
translations <- getTranslations
case lookupTerm term translations of
Just s -> return s
Nothing -> do
report $ NoTranslation (show term)
return ""
runIO :: PandocIO a -> IO (Either PandocError a)
runIO ma = flip evalStateT def $ runExceptT $ unPandocIO ma
runIOorExplode :: PandocIO a -> IO a
runIOorExplode ma = runIO ma >>= handleError
newtype PandocIO a = PandocIO {
unPandocIO :: ExceptT PandocError (StateT CommonState IO) a
} deriving ( MonadIO
, Functor
, Applicative
, Monad
, MonadError PandocError
)
liftIOError :: (String -> IO a) -> String -> PandocIO a
liftIOError f u = do
res <- liftIO $ tryIOError $ f u
case res of
Left e -> throwError $ PandocIOError u e
Right r -> return r
instance PandocMonad PandocIO where
lookupEnv = liftIO . IO.lookupEnv
getCurrentTime = liftIO IO.getCurrentTime
getCurrentTimeZone = liftIO IO.getCurrentTimeZone
newStdGen = liftIO IO.newStdGen
newUniqueHash = hashUnique <$> liftIO IO.newUnique
openURL u
| Just u'' <- stripPrefix "data:" u = do
let mime = takeWhile (/=',') u''
let contents = UTF8.fromString $
unEscapeString $ drop 1 $ dropWhile (/=',') u''
return (decodeLenient contents, Just mime)
| otherwise = do
let toReqHeader (n, v) = (CI.mk (UTF8.fromString n), UTF8.fromString v)
customHeaders <- map toReqHeader <$> getsCommonState stRequestHeaders
report $ Fetching u
res <- liftIO $ E.try $ withSocketsDo $ do
let parseReq = parseRequest
proxy <- tryIOError (getEnv "http_proxy")
let addProxy' x = case proxy of
Left _ -> return x
Right pr -> parseReq pr >>= \r ->
return (addProxy (host r) (port r) x)
req <- parseReq u >>= addProxy'
let req' = req{requestHeaders = customHeaders ++ requestHeaders req}
resp <- newManager tlsManagerSettings >>= httpLbs req'
return (B.concat $ toChunks $ responseBody resp,
UTF8.toString `fmap` lookup hContentType (responseHeaders resp))
case res of
Right r -> return r
Left e -> throwError $ PandocHttpError u e
readFileLazy s = liftIOError BL.readFile s
readFileStrict s = liftIOError B.readFile s
glob = liftIOError IO.glob
fileExists = liftIOError Directory.doesFileExist
#ifdef EMBED_DATA_FILES
getDataFileName = return
#else
getDataFileName = liftIOError Paths.getDataFileName
#endif
getModificationTime = liftIOError IO.getModificationTime
getCommonState = PandocIO $ lift get
putCommonState x = PandocIO $ lift $ put x
logOutput msg = liftIO $ do
UTF8.hPutStr stderr $
"[" ++ show (messageVerbosity msg) ++ "] "
alertIndent $ lines $ showLogMessage msg
alertIndent :: [String] -> IO ()
alertIndent [] = return ()
alertIndent (l:ls) = do
UTF8.hPutStrLn stderr l
mapM_ go ls
where go l' = do UTF8.hPutStr stderr " "
UTF8.hPutStrLn stderr l'
parseURIReference' :: String -> Maybe URI
parseURIReference' s =
case parseURIReference s of
Just u
| length (uriScheme u) > 2 -> Just u
| null (uriScheme u) -> Just u
_ -> Nothing
setUserDataDir :: PandocMonad m
=> Maybe FilePath
-> m ()
setUserDataDir mbfp = modifyCommonState $ \st -> st{ stUserDataDir = mbfp }
getUserDataDir :: PandocMonad m
=> m (Maybe FilePath)
getUserDataDir = getsCommonState stUserDataDir
fetchItem :: PandocMonad m
=> String
-> m (B.ByteString, Maybe MimeType)
fetchItem s = do
mediabag <- getMediaBag
case lookupMedia s mediabag of
Just (mime, bs) -> return (BL.toStrict bs, Just mime)
Nothing -> downloadOrRead s
downloadOrRead :: PandocMonad m
=> String
-> m (B.ByteString, Maybe MimeType)
downloadOrRead s = do
sourceURL <- getsCommonState stSourceURL
case (sourceURL >>= parseURIReference' .
ensureEscaped, ensureEscaped s) of
(Just u, s') ->
case parseURIReference' s' of
Just u' -> openURL $ show $ u' `nonStrictRelativeTo` u
Nothing -> openURL s'
(Nothing, s'@('/':'/':_)) ->
case parseURIReference' s' of
Just u' -> openURL $ show $ u' `nonStrictRelativeTo` httpcolon
Nothing -> openURL s'
(Nothing, s') ->
case parseURI s' of
Just u' | length (uriScheme u') > 2 -> openURL (show u')
Just u' | uriScheme u' == "file:" ->
readLocalFile $ dropWhile (=='/') (uriPath u')
_ -> readLocalFile fp
where readLocalFile f = do
resourcePath <- getResourcePath
cont <- if isRelative f
then withPaths resourcePath readFileStrict f
else readFileStrict f
return (cont, mime)
httpcolon = URI{ uriScheme = "http:",
uriAuthority = Nothing,
uriPath = "",
uriQuery = "",
uriFragment = "" }
dropFragmentAndQuery = takeWhile (\c -> c /= '?' && c /= '#')
fp = unEscapeString $ dropFragmentAndQuery s
mime = case takeExtension fp of
".gz" -> getMimeType $ dropExtension fp
".svgz" -> getMimeType $ dropExtension fp ++ ".svg"
x -> getMimeType x
ensureEscaped = escapeURIString isAllowedInURI . map convertSlash
convertSlash '\\' = '/'
convertSlash x = x
getDefaultReferenceDocx :: PandocMonad m => m Archive
getDefaultReferenceDocx = do
let paths = ["[Content_Types].xml",
"_rels/.rels",
"docProps/app.xml",
"docProps/core.xml",
"word/document.xml",
"word/fontTable.xml",
"word/footnotes.xml",
"word/numbering.xml",
"word/settings.xml",
"word/webSettings.xml",
"word/styles.xml",
"word/_rels/document.xml.rels",
"word/_rels/footnotes.xml.rels",
"word/theme/theme1.xml"]
let toLazy = BL.fromChunks . (:[])
let pathToEntry path = do
epochtime <- (floor . utcTimeToPOSIXSeconds) <$> getCurrentTime
contents <- toLazy <$> readDataFile ("docx/" ++ path)
return $ toEntry path epochtime contents
datadir <- getUserDataDir
mbArchive <- case datadir of
Nothing -> return Nothing
Just d -> do
exists <- fileExists (d </> "reference.docx")
if exists
then return (Just (d </> "reference.docx"))
else return Nothing
case mbArchive of
Just arch -> toArchive <$> readFileLazy arch
Nothing -> foldr addEntryToArchive emptyArchive <$>
mapM pathToEntry paths
getDefaultReferenceODT :: PandocMonad m => m Archive
getDefaultReferenceODT = do
let paths = ["mimetype",
"manifest.rdf",
"styles.xml",
"content.xml",
"meta.xml",
"settings.xml",
"Configurations2/accelerator/current.xml",
"Thumbnails/thumbnail.png",
"META-INF/manifest.xml"]
let pathToEntry path = do epochtime <- floor `fmap` getPOSIXTime
contents <- (BL.fromChunks . (:[])) `fmap`
readDataFile ("odt/" ++ path)
return $ toEntry path epochtime contents
datadir <- getUserDataDir
mbArchive <- case datadir of
Nothing -> return Nothing
Just d -> do
exists <- fileExists (d </> "reference.odt")
if exists
then return (Just (d </> "reference.odt"))
else return Nothing
case mbArchive of
Just arch -> toArchive <$> readFileLazy arch
Nothing -> foldr addEntryToArchive emptyArchive <$>
mapM pathToEntry paths
readDataFile :: PandocMonad m => FilePath -> m B.ByteString
readDataFile fname = do
datadir <- getUserDataDir
case datadir of
Nothing -> readDefaultDataFile fname
Just userDir -> do
exists <- fileExists (userDir </> fname)
if exists
then readFileStrict (userDir </> fname)
else readDefaultDataFile fname
readDefaultDataFile :: PandocMonad m => FilePath -> m B.ByteString
readDefaultDataFile "reference.docx" =
(B.concat . BL.toChunks . fromArchive) <$> getDefaultReferenceDocx
readDefaultDataFile "reference.odt" =
(B.concat . BL.toChunks . fromArchive) <$> getDefaultReferenceODT
readDefaultDataFile fname =
#ifdef EMBED_DATA_FILES
case lookup (makeCanonical fname) dataFiles of
Nothing -> throwError $ PandocCouldNotFindDataFileError fname
Just contents -> return contents
where makeCanonical = Posix.joinPath . transformPathParts . splitDirectories
transformPathParts = reverse . foldl go []
go as "." = as
go (_:as) ".." = as
go as x = x : as
#else
getDataFileName fname' >>= checkExistence >>= readFileStrict
where fname' = if fname == "MANUAL.txt" then fname else "data" </> fname
checkExistence :: PandocMonad m => FilePath -> m FilePath
checkExistence fn = do
exists <- fileExists fn
if exists
then return fn
else throwError $ PandocCouldNotFindDataFileError fn
#endif
withPaths :: PandocMonad m => [FilePath] -> (FilePath -> m a) -> FilePath -> m a
withPaths [] _ fp = throwError $ PandocResourceNotFound fp
withPaths (p:ps) action fp =
catchError (action (p </> fp))
(\_ -> withPaths ps action fp)
fetchMediaResource :: PandocMonad m
=> String -> m (FilePath, Maybe MimeType, BL.ByteString)
fetchMediaResource src = do
(bs, mt) <- downloadOrRead src
let ext = fromMaybe (takeExtension src)
(mt >>= extensionFromMimeType)
let bs' = BL.fromChunks [bs]
let basename = showDigest $ sha1 bs'
let fname = basename <.> ext
return (fname, mt, bs')
fillMediaBag :: PandocMonad m => Pandoc -> m Pandoc
fillMediaBag d = walkM handleImage d
where handleImage :: PandocMonad m => Inline -> m Inline
handleImage (Image attr lab (src, tit)) = catchError
(do mediabag <- getMediaBag
case lookupMedia src mediabag of
Just (_, _) -> return $ Image attr lab (src, tit)
Nothing -> do
(fname, mt, bs) <- fetchMediaResource src
insertMedia fname mt bs
return $ Image attr lab (fname, tit))
(\e ->
case e of
PandocResourceNotFound _ -> do
report $ CouldNotFetchResource src
"replacing image with description"
return $ Span ("",["image"],[]) lab
PandocHttpError u er -> do
report $ CouldNotFetchResource u
(show er ++ "\rReplacing image with description.")
return $ Span ("",["image"],[]) lab
_ -> throwError e)
handleImage x = return x
extractMedia :: FilePath -> Pandoc -> PandocIO Pandoc
extractMedia dir d = do
media <- getMediaBag
case [fp | (fp, _, _) <- mediaDirectory media] of
[] -> return d
fps -> do
mapM_ (writeMedia dir media) fps
return $ walk (adjustImagePath dir fps) d
writeMedia :: FilePath -> MediaBag -> FilePath -> PandocIO ()
writeMedia dir mediabag subpath = do
let fullpath = dir </> normalise subpath
let mbcontents = lookupMedia subpath mediabag
case mbcontents of
Nothing -> throwError $ PandocResourceNotFound subpath
Just (_, bs) -> do
report $ Extracting fullpath
liftIOError (createDirectoryIfMissing True) (takeDirectory fullpath)
liftIOError (\p -> BL.writeFile p bs) fullpath
adjustImagePath :: FilePath -> [FilePath] -> Inline -> Inline
adjustImagePath dir paths (Image attr lab (src, tit))
| src `elem` paths = Image attr lab (dir ++ "/" ++ src, tit)
adjustImagePath _ _ x = x
data PureState = PureState { stStdGen :: StdGen
, stWord8Store :: [Word8]
, stUniqStore :: [Int]
, stEnv :: [(String, String)]
, stTime :: UTCTime
, stTimeZone :: TimeZone
, stReferenceDocx :: Archive
, stReferenceODT :: Archive
, stFiles :: FileTree
, stUserDataFiles :: FileTree
, stCabalDataFiles :: FileTree
}
instance Default PureState where
def = PureState { stStdGen = mkStdGen 1848
, stWord8Store = [1..]
, stUniqStore = [1..]
, stEnv = [("USER", "pandoc-user")]
, stTime = posixSecondsToUTCTime 0
, stTimeZone = utc
, stReferenceDocx = emptyArchive
, stReferenceODT = emptyArchive
, stFiles = mempty
, stUserDataFiles = mempty
, stCabalDataFiles = mempty
}
getPureState :: PandocPure PureState
getPureState = PandocPure $ lift $ lift get
getsPureState :: (PureState -> a) -> PandocPure a
getsPureState f = f <$> getPureState
putPureState :: PureState -> PandocPure ()
putPureState ps= PandocPure $ lift $ lift $ put ps
modifyPureState :: (PureState -> PureState) -> PandocPure ()
modifyPureState f = PandocPure $ lift $ lift $ modify f
data FileInfo = FileInfo { infoFileMTime :: UTCTime
, infoFileContents :: B.ByteString
}
newtype FileTree = FileTree {unFileTree :: M.Map FilePath FileInfo}
deriving (Monoid)
getFileInfo :: FilePath -> FileTree -> Maybe FileInfo
getFileInfo fp tree = M.lookup fp $ unFileTree tree
addToFileTree :: FileTree -> FilePath -> IO FileTree
addToFileTree (FileTree treemap) fp = do
isdir <- doesDirectoryExist fp
if isdir
then do
let isSpecial ".." = True
isSpecial "." = True
isSpecial _ = False
fs <- (map (fp </>) . filter (not . isSpecial)) <$> getDirectoryContents fp
foldM addToFileTree (FileTree treemap) fs
else do
contents <- B.readFile fp
mtime <- IO.getModificationTime fp
return $ FileTree $
M.insert fp FileInfo{ infoFileMTime = mtime
, infoFileContents = contents } treemap
newtype PandocPure a = PandocPure {
unPandocPure :: ExceptT PandocError
(StateT CommonState (State PureState)) a
} deriving ( Functor
, Applicative
, Monad
, MonadError PandocError
)
runPure :: PandocPure a -> Either PandocError a
runPure x = flip evalState def $
flip evalStateT def $
runExceptT $
unPandocPure x
instance PandocMonad PandocPure where
lookupEnv s = do
env <- getsPureState stEnv
return (lookup s env)
getCurrentTime = getsPureState stTime
getCurrentTimeZone = getsPureState stTimeZone
newStdGen = do
g <- getsPureState stStdGen
let (_, nxtGen) = next g
modifyPureState $ \st -> st { stStdGen = nxtGen }
return g
newUniqueHash = do
uniqs <- getsPureState stUniqStore
case uniqs of
u : us -> do
modifyPureState $ \st -> st { stUniqStore = us }
return u
_ -> M.fail "uniq store ran out of elements"
openURL u = throwError $ PandocResourceNotFound u
readFileLazy fp = do
fps <- getsPureState stFiles
case infoFileContents <$> getFileInfo fp fps of
Just bs -> return (BL.fromStrict bs)
Nothing -> throwError $ PandocResourceNotFound fp
readFileStrict fp = do
fps <- getsPureState stFiles
case infoFileContents <$> getFileInfo fp fps of
Just bs -> return bs
Nothing -> throwError $ PandocResourceNotFound fp
glob s = do
FileTree ftmap <- getsPureState stFiles
return $ filter (match (compile s)) $ M.keys ftmap
fileExists fp = do
fps <- getsPureState stFiles
case getFileInfo fp fps of
Nothing -> return False
Just _ -> return True
getDataFileName fp = return $ "data/" ++ fp
getModificationTime fp = do
fps <- getsPureState stFiles
case infoFileMTime <$> getFileInfo fp fps of
Just tm -> return tm
Nothing -> throwError $ PandocIOError fp
(userError "Can't get modification time")
getCommonState = PandocPure $ lift get
putCommonState x = PandocPure $ lift $ put x
logOutput _msg = return ()
instance (MonadTrans t, PandocMonad m, Functor (t m),
MonadError PandocError (t m), Monad (t m),
Applicative (t m)) => PandocMonad (t m) where
lookupEnv = lift . lookupEnv
getCurrentTime = lift getCurrentTime
getCurrentTimeZone = lift getCurrentTimeZone
newStdGen = lift newStdGen
newUniqueHash = lift newUniqueHash
openURL = lift . openURL
readFileLazy = lift . readFileLazy
readFileStrict = lift . readFileStrict
glob = lift . glob
fileExists = lift . fileExists
getDataFileName = lift . getDataFileName
getModificationTime = lift . getModificationTime
getCommonState = lift getCommonState
putCommonState = lift . putCommonState
logOutput = lift . logOutput
#if MIN_VERSION_base(4,8,0)
instance PandocMonad m => PandocMonad (ParsecT s st m) where
#else
instance PandocMonad m => PandocMonad (ParsecT s st m) where
#endif
lookupEnv = lift . lookupEnv
getCurrentTime = lift getCurrentTime
getCurrentTimeZone = lift getCurrentTimeZone
newStdGen = lift newStdGen
newUniqueHash = lift newUniqueHash
openURL = lift . openURL
readFileLazy = lift . readFileLazy
readFileStrict = lift . readFileStrict
glob = lift . glob
fileExists = lift . fileExists
getDataFileName = lift . getDataFileName
getModificationTime = lift . getModificationTime
getCommonState = lift getCommonState
putCommonState = lift . putCommonState
trace msg = do
tracing <- getsCommonState stTrace
when tracing $ do
pos <- getPosition
Debug.Trace.trace
("[trace] Parsed " ++ msg ++ " at line " ++
show (sourceLine pos) ++
if sourceName pos == "chunk"
then " of chunk"
else "")
(return ())
logOutput = lift . logOutput