Copyright | Copyright (C) 2016-2020 Jesse Rosenthal John MacFarlane |
---|---|
License | GNU GPL, version 2 or above |
Maintainer | Jesse Rosenthal <jrosenthal@jhu.edu> |
Stability | alpha |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
Text.Pandoc.Class
Description
This module defines a type class, PandocMonad
, for pandoc readers
and writers. A pure instance PandocPure
and an impure instance
PandocIO
are provided. This allows users of the library to choose
whether they want conversions to perform IO operations (such as
reading include files or images).
Synopsis
- data CommonState = CommonState {
- stLog :: [LogMessage]
- stUserDataDir :: Maybe FilePath
- stSourceURL :: Maybe Text
- stRequestHeaders :: [(Text, Text)]
- stNoCheckCertificate :: Bool
- stMediaBag :: MediaBag
- stTranslations :: Maybe (Lang, Maybe Translations)
- stInputFiles :: [FilePath]
- stOutputFile :: Maybe FilePath
- stResourcePath :: [FilePath]
- stVerbosity :: Verbosity
- stTrace :: Bool
- runIO :: PandocIO a -> IO (Either PandocError a)
- extractMedia :: (PandocMonad m, MonadIO m) => FilePath -> Pandoc -> m Pandoc
- runIOorExplode :: PandocIO a -> IO a
- newtype PandocIO a = PandocIO {
- unPandocIO :: ExceptT PandocError (StateT CommonState IO) a
- class (Functor m, Applicative m, Monad m, MonadError PandocError m) => PandocMonad (m :: Type -> Type) where
- lookupEnv :: Text -> m (Maybe Text)
- getCurrentTime :: m UTCTime
- getCurrentTimeZone :: m TimeZone
- newStdGen :: m StdGen
- newUniqueHash :: m Int
- openURL :: Text -> m (ByteString, Maybe MimeType)
- readFileLazy :: FilePath -> m ByteString
- readFileStrict :: FilePath -> m ByteString
- readStdinStrict :: m 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
- modifyCommonState :: (CommonState -> CommonState) -> m ()
- logOutput :: LogMessage -> m ()
- trace :: Text -> m ()
- report :: PandocMonad m => LogMessage -> m ()
- getPOSIXTime :: PandocMonad m => m POSIXTime
- getZonedTime :: PandocMonad m => m ZonedTime
- checkUserDataDir :: PandocMonad m => FilePath -> m (Maybe FilePath)
- getTimestamp :: PandocMonad m => m UTCTime
- getUserDataDir :: PandocMonad m => m (Maybe FilePath)
- makeCanonical :: FilePath -> FilePath
- insertMedia :: PandocMonad m => FilePath -> Maybe MimeType -> ByteString -> m ()
- findFileWithDataFallback :: PandocMonad m => FilePath -> FilePath -> m (Maybe FilePath)
- getVerbosity :: PandocMonad m => m Verbosity
- toTextM :: PandocMonad m => FilePath -> ByteString -> m Text
- getResourcePath :: PandocMonad m => m [FilePath]
- readFileFromDirs :: PandocMonad m => [FilePath] -> FilePath -> m (Maybe Text)
- setResourcePath :: PandocMonad m => [FilePath] -> m ()
- fetchItem :: PandocMonad m => Text -> m (ByteString, Maybe MimeType)
- getMediaBag :: PandocMonad m => m MediaBag
- toLang :: PandocMonad m => Maybe Text -> m (Maybe Lang)
- fillMediaBag :: PandocMonad m => Pandoc -> m Pandoc
- setVerbosity :: PandocMonad m => Verbosity -> m ()
- getInputFiles :: PandocMonad m => m [FilePath]
- setInputFiles :: PandocMonad m => [FilePath] -> m ()
- extractURIData :: String -> (ByteString, Maybe MimeType)
- setTrace :: PandocMonad m => Bool -> m ()
- setRequestHeader :: PandocMonad m => Text -> Text -> m ()
- setNoCheckCertificate :: PandocMonad m => Bool -> m ()
- getLog :: PandocMonad m => m [LogMessage]
- setMediaBag :: PandocMonad m => MediaBag -> m ()
- setUserDataDir :: PandocMonad m => Maybe FilePath -> m ()
- getOutputFile :: PandocMonad m => m (Maybe FilePath)
- setOutputFile :: PandocMonad m => Maybe FilePath -> m ()
- readMetadataFile :: PandocMonad m => FilePath -> m ByteString
- newtype PandocPure a = PandocPure {}
- runPure :: PandocPure a -> Either PandocError a
- data PureState = PureState {
- stStdGen :: StdGen
- stWord8Store :: [Word8]
- stUniqStore :: [Int]
- stEnv :: [(Text, Text)]
- stTime :: UTCTime
- stTimeZone :: TimeZone
- stReferenceDocx :: Archive
- stReferencePptx :: Archive
- stReferenceODT :: Archive
- stFiles :: FileTree
- stStdin :: ByteString
- stUserDataFiles :: FileTree
- stCabalDataFiles :: FileTree
- getPureState :: PandocPure PureState
- getsPureState :: (PureState -> a) -> PandocPure a
- putPureState :: PureState -> PandocPure ()
- modifyPureState :: (PureState -> PureState) -> PandocPure ()
- data FileTree
- data FileInfo = FileInfo {}
- addToFileTree :: FileTree -> FilePath -> IO FileTree
- insertInFileTree :: FilePath -> FileInfo -> FileTree -> FileTree
- sandbox :: (PandocMonad m, MonadIO m) => [FilePath] -> PandocPure a -> m a
- sandboxWithFileTree :: (PandocMonad m, MonadIO m) => FileTree -> PandocPure a -> m a
- data Translations
Documentation
data CommonState Source #
CommonState
represents state that is used by all
instances of PandocMonad
. Normally users should not
need to interact with it directly; instead, auxiliary
functions like setVerbosity
and withMediaBag
should be used.
Constructors
CommonState | |
Fields
|
Instances
Default CommonState Source # | |
Defined in Text.Pandoc.Class.CommonState Methods def :: CommonState # |
extractMedia :: (PandocMonad m, MonadIO m) => FilePath -> Pandoc -> m Pandoc Source #
Extract media from the mediabag into a directory.
runIOorExplode :: PandocIO a -> IO a Source #
Evaluate a PandocIO
operation, handling any errors
by exiting with an appropriate message and error status.
Constructors
PandocIO | |
Fields
|
Instances
class (Functor m, Applicative m, Monad m, MonadError PandocError m) => PandocMonad (m :: Type -> Type) where Source #
The PandocMonad typeclass contains all the potentially
IO-related functions used in pandoc's readers and writers.
Instances of this typeclass may implement these functions
in IO (as in PandocIO
) or using an internal state that
represents a file system, time, and so on (as in PandocPure
).
Minimal complete definition
lookupEnv, getCurrentTime, getCurrentTimeZone, newStdGen, newUniqueHash, openURL, readFileLazy, readFileStrict, readStdinStrict, glob, fileExists, getDataFileName, getModificationTime, getCommonState, putCommonState, logOutput
Methods
lookupEnv :: Text -> m (Maybe Text) Source #
Lookup an environment variable.
getCurrentTime :: m UTCTime Source #
Get the current (UTC) time.
getCurrentTimeZone :: m TimeZone Source #
Get the locale's time zone.
newStdGen :: m StdGen Source #
Return a new generator for random numbers.
newUniqueHash :: m Int Source #
Return a new unique integer.
openURL :: Text -> m (ByteString, Maybe MimeType) Source #
Retrieve contents and mime type from a URL, raising an error on failure.
readFileLazy :: FilePath -> m ByteString Source #
Read the lazy ByteString contents from a file path, raising an error on failure.
readFileStrict :: FilePath -> m ByteString Source #
Read the strict ByteString contents from a file path, raising an error on failure.
readStdinStrict :: m ByteString Source #
Read the contents of stdin as a strict ByteString, raising an error on failure.
glob :: String -> m [FilePath] Source #
Return a list of paths that match a glob, relative to
the working directory. See Glob
for
the glob syntax.
fileExists :: FilePath -> m Bool Source #
Returns True if file exists.
getDataFileName :: FilePath -> m FilePath Source #
Returns the path of data file.
getModificationTime :: FilePath -> m UTCTime Source #
Return the modification time of a file.
getCommonState :: m CommonState Source #
Get the value of the CommonState
used by all instances
of PandocMonad
.
putCommonState :: CommonState -> m () Source #
Set the value of the CommonState
used by all instances
of PandocMonad
.
| Get the value of a specific field of CommonState
.
getsCommonState :: (CommonState -> a) -> m a Source #
Get the value of a specific field of CommonState
.
modifyCommonState :: (CommonState -> CommonState) -> m () Source #
Modify the CommonState
.
logOutput :: LogMessage -> m () Source #
Output a log message.
trace :: Text -> m () Source #
Output a debug message to sterr, using trace
,
if tracing is enabled. Note: this writes to stderr even in
pure instances.
Instances
report :: PandocMonad m => LogMessage -> m () Source #
getPOSIXTime :: PandocMonad m => m POSIXTime Source #
Get the POSIX time. If SOURCE_DATE_EPOCH
is set to a unix time,
it is used instead of the current time.
getZonedTime :: PandocMonad m => m ZonedTime Source #
Get the zoned time. If SOURCE_DATE_EPOCH
is set to a unix time,
value (POSIX time), it is used instead of the current time.
checkUserDataDir :: PandocMonad m => FilePath -> m (Maybe FilePath) Source #
Returns possible user data directory if the file path refers to a file or subdirectory within it.
getTimestamp :: PandocMonad m => m UTCTime Source #
Get the current UTC time. If the SOURCE_DATE_EPOCH
environment
variable is set to a unix time (number of seconds since midnight
Jan 01 1970 UTC), it is used instead of the current time, to support
reproducible builds.
getUserDataDir :: PandocMonad m => m (Maybe FilePath) Source #
Get the user data directory from common state.
makeCanonical :: FilePath -> FilePath Source #
Canonicalizes a file path by removing redundant .
and ..
.
insertMedia :: PandocMonad m => FilePath -> Maybe MimeType -> ByteString -> m () Source #
Insert an item into the media bag.
findFileWithDataFallback Source #
Arguments
:: PandocMonad m | |
=> FilePath | subdir |
-> FilePath | fp |
-> m (Maybe FilePath) |
Returns fp
if the file exists in the current directory; otherwise
searches for the data file relative to subdir
. Returns Nothing
if neither file exists.
getVerbosity :: PandocMonad m => m Verbosity Source #
Get the verbosity level.
toTextM :: PandocMonad m => FilePath -> ByteString -> m Text Source #
A variant of Text.Pandoc.UTF8.toText that takes a FilePath as well as the file's contents as parameter, and traps UTF8 decoding errors so it can issue a more informative PandocUTF8DecodingError with source position.
getResourcePath :: PandocMonad m => m [FilePath] Source #
Retrieve the resource path searched by fetchItem
.
readFileFromDirs :: PandocMonad m => [FilePath] -> FilePath -> m (Maybe Text) Source #
Read file, checking in any number of directories.
setResourcePath :: PandocMonad m => [FilePath] -> m () Source #
Set the resource path searched by fetchItem
.
fetchItem :: PandocMonad m => Text -> m (ByteString, Maybe MimeType) Source #
Fetch an image or other item from the local filesystem or the net. Returns raw content and maybe mime type.
getMediaBag :: PandocMonad m => m MediaBag Source #
Retrieve the media bag.
toLang :: PandocMonad m => Maybe Text -> m (Maybe Lang) Source #
Convert BCP47 string to a Lang, issuing warning if there are problems.
fillMediaBag :: PandocMonad m => Pandoc -> m Pandoc Source #
Traverse tree, filling media bag for any images that aren't already in the media bag.
setVerbosity :: PandocMonad m => Verbosity -> m () Source #
Set the verbosity level.
getInputFiles :: PandocMonad m => m [FilePath] Source #
Retrieve the input filenames.
setInputFiles :: PandocMonad m => [FilePath] -> m () Source #
Set the input filenames.
extractURIData :: String -> (ByteString, Maybe MimeType) Source #
setTrace :: PandocMonad m => Bool -> m () Source #
Arguments
:: PandocMonad m | |
=> Text | Header name |
-> Text | Value |
-> m () |
Set request header to use in HTTP requests.
setNoCheckCertificate :: PandocMonad m => Bool -> m () Source #
Determine whether certificate validation is disabled
getLog :: PandocMonad m => m [LogMessage] Source #
Get the accumulated log messages (in temporal order).
setMediaBag :: PandocMonad m => MediaBag -> m () Source #
Initialize the media bag.
setUserDataDir :: PandocMonad m => Maybe FilePath -> m () Source #
Set the user data directory in common state.
getOutputFile :: PandocMonad m => m (Maybe FilePath) Source #
Retrieve the output filename.
setOutputFile :: PandocMonad m => Maybe FilePath -> m () Source #
Set the output filename.
readMetadataFile :: PandocMonad m => FilePath -> m ByteString Source #
Read metadata file from the working directory or, if not found there, from the metadata subdirectory of the user data directory.
newtype PandocPure a Source #
Constructors
PandocPure | |
Fields |
Instances
runPure :: PandocPure a -> Either PandocError a Source #
Run a PandocPure
operation.
The PureState
contains ersatz representations
of things that would normally be obtained through IO.
Constructors
PureState | |
Fields
|
getPureState :: PandocPure PureState Source #
Retrieve the underlying state of the
type.PandocPure
getsPureState :: (PureState -> a) -> PandocPure a Source #
Retrieve a value from the underlying state of the
type.PandocPure
putPureState :: PureState -> PandocPure () Source #
Set a new state for the
type.PandocPure
modifyPureState :: (PureState -> PureState) -> PandocPure () Source #
Modify the underlying state of the
type.PandocPure
Basis of the mock file system used by
.PandocPure
Captures all file-level information necessary for a
conforming mock file system.PandocMonad
Constructors
FileInfo | |
Fields |
addToFileTree :: FileTree -> FilePath -> IO FileTree Source #
Add the specified file to the FileTree. If file is a directory, add its contents recursively.
insertInFileTree :: FilePath -> FileInfo -> FileTree -> FileTree Source #
Insert an ersatz file into the FileTree
.
sandbox :: (PandocMonad m, MonadIO m) => [FilePath] -> PandocPure a -> m a Source #
Lift a PandocPure action into any instance of PandocMonad. The main computation is done purely, but CommonState is preserved continuously, and warnings are emitted after the action completes. The parameter is a list of FilePaths which will be added to the ersatz file system and be available for reading.
sandboxWithFileTree :: (PandocMonad m, MonadIO m) => FileTree -> PandocPure a -> m a Source #
Lift a PandocPure action into any instance of PandocMonad. The main computation is done purely, but CommonState is preserved continuously, and warnings are emitted after the action completes. The parameter is an ersatz file system which will be available for reading.
data Translations Source #