Text.Pandoc.Class: add readStdinStrict method to PandocMonad.
[API change]
This commit is contained in:
parent
8ad22002cb
commit
c39ddeb8f8
5 changed files with 17 additions and 0 deletions
|
@ -30,6 +30,7 @@ module Text.Pandoc.Class.IO
|
|||
, openURL
|
||||
, readFileLazy
|
||||
, readFileStrict
|
||||
, readStdinStrict
|
||||
, extractMedia
|
||||
) where
|
||||
|
||||
|
@ -158,6 +159,11 @@ readFileLazy s = liftIOError BL.readFile s
|
|||
readFileStrict :: (PandocMonad m, MonadIO m) => FilePath -> m B.ByteString
|
||||
readFileStrict s = liftIOError B.readFile s
|
||||
|
||||
-- | Read the strict ByteString contents from stdin, raising
|
||||
-- an error on failure.
|
||||
readStdinStrict :: (PandocMonad m, MonadIO m) => m B.ByteString
|
||||
readStdinStrict = liftIOError (const B.getContents) "stdin"
|
||||
|
||||
-- | Return a list of paths that match a glob, relative to the working
|
||||
-- directory. See 'System.FilePath.Glob' for the glob syntax.
|
||||
glob :: (PandocMonad m, MonadIO m) => String -> m [FilePath]
|
||||
|
|
|
@ -62,6 +62,7 @@ instance PandocMonad PandocIO where
|
|||
openURL = IO.openURL
|
||||
readFileLazy = IO.readFileLazy
|
||||
readFileStrict = IO.readFileStrict
|
||||
readStdinStrict = IO.readStdinStrict
|
||||
|
||||
glob = IO.glob
|
||||
fileExists = IO.fileExists
|
||||
|
|
|
@ -117,6 +117,9 @@ class (Functor m, Applicative m, Monad m, MonadError PandocError m)
|
|||
-- | Read the strict ByteString contents from a file path,
|
||||
-- raising an error on failure.
|
||||
readFileStrict :: FilePath -> m B.ByteString
|
||||
-- | Read the contents of stdin as a strict ByteString, raising
|
||||
-- an error on failure.
|
||||
readStdinStrict :: m B.ByteString
|
||||
-- | Return a list of paths that match a glob, relative to
|
||||
-- the working directory. See 'System.FilePath.Glob' for
|
||||
-- the glob syntax.
|
||||
|
@ -674,6 +677,7 @@ instance (MonadTrans t, PandocMonad m, Functor (t m),
|
|||
openURL = lift . openURL
|
||||
readFileLazy = lift . readFileLazy
|
||||
readFileStrict = lift . readFileStrict
|
||||
readStdinStrict = lift readStdinStrict
|
||||
glob = lift . glob
|
||||
fileExists = lift . fileExists
|
||||
getDataFileName = lift . getDataFileName
|
||||
|
@ -691,6 +695,7 @@ instance {-# OVERLAPS #-} PandocMonad m => PandocMonad (ParsecT s st m) where
|
|||
openURL = lift . openURL
|
||||
readFileLazy = lift . readFileLazy
|
||||
readFileStrict = lift . readFileStrict
|
||||
readStdinStrict = lift readStdinStrict
|
||||
glob = lift . glob
|
||||
fileExists = lift . fileExists
|
||||
getDataFileName = lift . getDataFileName
|
||||
|
|
|
@ -64,6 +64,7 @@ data PureState = PureState
|
|||
, stReferencePptx :: Archive
|
||||
, stReferenceODT :: Archive
|
||||
, stFiles :: FileTree
|
||||
, stStdin :: B.ByteString
|
||||
, stUserDataFiles :: FileTree
|
||||
, stCabalDataFiles :: FileTree
|
||||
}
|
||||
|
@ -80,6 +81,7 @@ instance Default PureState where
|
|||
, stReferencePptx = emptyArchive
|
||||
, stReferenceODT = emptyArchive
|
||||
, stFiles = mempty
|
||||
, stStdin = mempty
|
||||
, stUserDataFiles = mempty
|
||||
, stCabalDataFiles = mempty
|
||||
}
|
||||
|
@ -193,6 +195,8 @@ instance PandocMonad PandocPure where
|
|||
Just bs -> return bs
|
||||
Nothing -> throwError $ PandocResourceNotFound $ T.pack fp
|
||||
|
||||
readStdinStrict = getsPureState stStdin
|
||||
|
||||
glob s = do
|
||||
FileTree ftmap <- getsPureState stFiles
|
||||
return $ filter (match (compile s)) $ M.keys ftmap
|
||||
|
|
|
@ -126,6 +126,7 @@ instance PandocMonad PandocLua where
|
|||
|
||||
readFileLazy = IO.readFileLazy
|
||||
readFileStrict = IO.readFileStrict
|
||||
readStdinStrict = IO.readStdinStrict
|
||||
|
||||
glob = IO.glob
|
||||
fileExists = IO.fileExists
|
||||
|
|
Loading…
Add table
Reference in a new issue