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)]
- stMediaBag :: MediaBag
- stTranslations :: Maybe (Lang, Maybe Translations)
- stInputFiles :: [FilePath]
- stOutputFile :: Maybe FilePath
- stResourcePath :: [FilePath]
- stVerbosity :: Verbosity
- stTrace :: Bool
- getPOSIXTime :: PandocMonad m => m POSIXTime
- getZonedTime :: PandocMonad m => m ZonedTime
- readFileFromDirs :: PandocMonad m => [FilePath] -> FilePath -> m (Maybe Text)
- report :: PandocMonad m => LogMessage -> m ()
- setTrace :: PandocMonad m => Bool -> m ()
- setRequestHeader :: PandocMonad m => Text -> Text -> m ()
- getLog :: PandocMonad m => m [LogMessage]
- setVerbosity :: PandocMonad m => Verbosity -> m ()
- getVerbosity :: PandocMonad m => m Verbosity
- getMediaBag :: PandocMonad m => m MediaBag
- setMediaBag :: PandocMonad m => MediaBag -> m ()
- insertMedia :: PandocMonad m => FilePath -> Maybe MimeType -> ByteString -> m ()
- setUserDataDir :: PandocMonad m => Maybe FilePath -> m ()
- getUserDataDir :: PandocMonad m => m (Maybe FilePath)
- fetchItem :: PandocMonad m => Text -> m (ByteString, Maybe MimeType)
- getInputFiles :: PandocMonad m => m [FilePath]
- setInputFiles :: PandocMonad m => [FilePath] -> m ()
- getOutputFile :: PandocMonad m => m (Maybe FilePath)
- setOutputFile :: PandocMonad m => Maybe FilePath -> m ()
- setResourcePath :: PandocMonad m => [FilePath] -> m ()
- getResourcePath :: PandocMonad m => m [FilePath]
- newtype PandocIO a = PandocIO {
- unPandocIO :: ExceptT PandocError (StateT CommonState IO) a
- runIO :: PandocIO a -> IO (Either PandocError a)
- runIOorExplode :: PandocIO a -> IO a
- extractMedia :: FilePath -> Pandoc -> PandocIO Pandoc
- class (Functor m, Applicative m, Monad m, MonadError PandocError m) => PandocMonad m 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
- 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 ()
- getPOSIXTime :: PandocMonad m => m POSIXTime
- getZonedTime :: PandocMonad m => m ZonedTime
- readFileFromDirs :: PandocMonad m => [FilePath] -> FilePath -> m (Maybe Text)
- report :: PandocMonad m => LogMessage -> m ()
- setTrace :: PandocMonad m => Bool -> m ()
- setRequestHeader :: PandocMonad m => Text -> Text -> m ()
- getLog :: PandocMonad m => m [LogMessage]
- setVerbosity :: PandocMonad m => Verbosity -> m ()
- getVerbosity :: PandocMonad m => m Verbosity
- getMediaBag :: PandocMonad m => m MediaBag
- setMediaBag :: PandocMonad m => MediaBag -> m ()
- insertMedia :: PandocMonad m => FilePath -> Maybe MimeType -> ByteString -> m ()
- setUserDataDir :: PandocMonad m => Maybe FilePath -> m ()
- getUserDataDir :: PandocMonad m => m (Maybe FilePath)
- fetchItem :: PandocMonad m => Text -> m (ByteString, Maybe MimeType)
- fetchMediaResource :: PandocMonad m => Text -> m (FilePath, Maybe MimeType, ByteString)
- getInputFiles :: PandocMonad m => m [FilePath]
- setInputFiles :: PandocMonad m => [FilePath] -> m ()
- getOutputFile :: PandocMonad m => m (Maybe FilePath)
- setOutputFile :: PandocMonad m => Maybe FilePath -> m ()
- setResourcePath :: PandocMonad m => [FilePath] -> m ()
- getResourcePath :: PandocMonad m => m [FilePath]
- readDefaultDataFile :: PandocMonad m => FilePath -> m ByteString
- readDataFile :: PandocMonad m => FilePath -> m ByteString
- fillMediaBag :: PandocMonad m => Pandoc -> m Pandoc
- toLang :: PandocMonad m => Maybe Text -> m (Maybe Lang)
- setTranslations :: PandocMonad m => Lang -> m ()
- translateTerm :: PandocMonad m => Term -> m Text
- makeCanonical :: FilePath -> FilePath
- data PureState = PureState {
- stStdGen :: StdGen
- stWord8Store :: [Word8]
- stUniqStore :: [Int]
- stEnv :: [(Text, Text)]
- stTime :: UTCTime
- stTimeZone :: TimeZone
- stReferenceDocx :: Archive
- stReferencePptx :: Archive
- stReferenceODT :: Archive
- stFiles :: FileTree
- stUserDataFiles :: FileTree
- stCabalDataFiles :: FileTree
- getPureState :: PandocPure PureState
- getsPureState :: (PureState -> a) -> PandocPure a
- putPureState :: PureState -> PandocPure ()
- modifyPureState :: (PureState -> PureState) -> PandocPure ()
- newtype PandocPure a = PandocPure {
- unPandocPure :: ExceptT PandocError (StateT CommonState (State PureState)) a
- data FileTree
- data FileInfo = FileInfo {
- infoFileMTime :: UTCTime
- infoFileContents :: ByteString
- addToFileTree :: FileTree -> FilePath -> IO FileTree
- insertInFileTree :: FilePath -> FileInfo -> FileTree -> FileTree
- runPure :: PandocPure a -> Either PandocError a
- data Translations
Documentation
data CommonState #
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
Peekable CommonState | |
Defined in Text.Pandoc.Lua.Marshaling.CommonState Methods peek :: StackIndex -> Lua CommonState | |
Pushable CommonState | |
Defined in Text.Pandoc.Lua.Marshaling.CommonState Methods push :: CommonState -> Lua () | |
Default CommonState # | |
Defined in Text.Pandoc.Class.CommonState Methods def :: CommonState # |
getPOSIXTime :: PandocMonad m => m POSIXTime #
Get the POSIX time.
getZonedTime :: PandocMonad m => m ZonedTime #
Get the zoned time.
readFileFromDirs :: PandocMonad m => [FilePath] -> FilePath -> m (Maybe Text) #
Read file, checking in any number of directories.
report :: PandocMonad m => LogMessage -> m () #
setTrace :: PandocMonad m => Bool -> m () #
Arguments
:: PandocMonad m | |
=> Text | Header name |
-> Text | Value |
-> m () |
Set request header to use in HTTP requests.
getLog :: PandocMonad m => m [LogMessage] #
Get the accomulated log messages (in temporal order).
setVerbosity :: PandocMonad m => Verbosity -> m () #
Set the verbosity level.
getVerbosity :: PandocMonad m => m Verbosity #
Get the verbosity level.
getMediaBag :: PandocMonad m => m MediaBag #
Retrieve the media bag.
setMediaBag :: PandocMonad m => MediaBag -> m () #
Initialize the media bag.
insertMedia :: PandocMonad m => FilePath -> Maybe MimeType -> ByteString -> m () #
Insert an item into the media bag.
setUserDataDir :: PandocMonad m => Maybe FilePath -> m () #
Set the user data directory in common state.
getUserDataDir :: PandocMonad m => m (Maybe FilePath) #
Get the user data directory from common state.
fetchItem :: PandocMonad m => Text -> m (ByteString, Maybe MimeType) #
Fetch an image or other item from the local filesystem or the net. Returns raw content and maybe mime type.
getInputFiles :: PandocMonad m => m [FilePath] #
Retrieve the input filenames.
setInputFiles :: PandocMonad m => [FilePath] -> m () #
Set the input filenames.
getOutputFile :: PandocMonad m => m (Maybe FilePath) #
Retrieve the output filename.
setOutputFile :: PandocMonad m => Maybe FilePath -> m () #
Set the output filename.
setResourcePath :: PandocMonad m => [FilePath] -> m () #
Set the resource path searched by fetchItem
.
getResourcePath :: PandocMonad m => m [FilePath] #
Retrieve the resource path searched by fetchItem
.
Constructors
PandocIO | |
Fields
|
Instances
runIOorExplode :: PandocIO a -> IO a #
Evaluate a PandocIO
operation, handling any errors
by exiting with an appropriate message and error status.
extractMedia :: FilePath -> Pandoc -> PandocIO Pandoc #
Extract media from the mediabag into a directory.
class (Functor m, Applicative m, Monad m, MonadError PandocError m) => PandocMonad m where #
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, glob, fileExists, getDataFileName, getModificationTime, getCommonState, putCommonState, logOutput
Methods
lookupEnv :: Text -> m (Maybe Text) #
Lookup an environment variable.
getCurrentTime :: m UTCTime #
Get the current (UTC) time.
getCurrentTimeZone :: m TimeZone #
Get the locale's time zone.
Return a new generator for random numbers.
newUniqueHash :: m Int #
Return a new unique integer.
openURL :: Text -> m (ByteString, Maybe MimeType) #
Retrieve contents and mime type from a URL, raising an error on failure.
readFileLazy :: FilePath -> m ByteString #
Read the lazy ByteString contents from a file path, raising an error on failure.
readFileStrict :: FilePath -> m ByteString #
Read the strict ByteString contents from a file path, raising an error on failure.
glob :: String -> m [FilePath] #
Return a list of paths that match a glob, relative to
the working directory. See Glob
for
the glob syntax.
fileExists :: FilePath -> m Bool #
Returns True if file exists.
getDataFileName :: FilePath -> m FilePath #
Returns the path of data file.
getModificationTime :: FilePath -> m UTCTime #
Return the modification time of a file.
getCommonState :: m CommonState #
Get the value of the CommonState
used by all instances
of PandocMonad
.
putCommonState :: CommonState -> m () #
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 #
Get the value of a specific field of CommonState
.
modifyCommonState :: (CommonState -> CommonState) -> m () #
Modify the CommonState
.
logOutput :: LogMessage -> m () #
Output a log message.
Output a debug message to sterr, using trace
,
if tracing is enabled. Note: this writes to stderr even in
pure instances.
Instances
getPOSIXTime :: PandocMonad m => m POSIXTime #
Get the POSIX time.
getZonedTime :: PandocMonad m => m ZonedTime #
Get the zoned time.
readFileFromDirs :: PandocMonad m => [FilePath] -> FilePath -> m (Maybe Text) #
Read file, checking in any number of directories.
report :: PandocMonad m => LogMessage -> m () #
setTrace :: PandocMonad m => Bool -> m () #
Arguments
:: PandocMonad m | |
=> Text | Header name |
-> Text | Value |
-> m () |
Set request header to use in HTTP requests.
getLog :: PandocMonad m => m [LogMessage] #
Get the accomulated log messages (in temporal order).
setVerbosity :: PandocMonad m => Verbosity -> m () #
Set the verbosity level.
getVerbosity :: PandocMonad m => m Verbosity #
Get the verbosity level.
getMediaBag :: PandocMonad m => m MediaBag #
Retrieve the media bag.
setMediaBag :: PandocMonad m => MediaBag -> m () #
Initialize the media bag.
insertMedia :: PandocMonad m => FilePath -> Maybe MimeType -> ByteString -> m () #
Insert an item into the media bag.
setUserDataDir :: PandocMonad m => Maybe FilePath -> m () #
Set the user data directory in common state.
getUserDataDir :: PandocMonad m => m (Maybe FilePath) #
Get the user data directory from common state.
fetchItem :: PandocMonad m => Text -> m (ByteString, Maybe MimeType) #
Fetch an image or other item from the local filesystem or the net. Returns raw content and maybe mime type.
fetchMediaResource :: PandocMonad m => Text -> m (FilePath, Maybe MimeType, ByteString) #
Fetch local or remote resource (like an image) and provide data suitable for adding it to the MediaBag.
getInputFiles :: PandocMonad m => m [FilePath] #
Retrieve the input filenames.
setInputFiles :: PandocMonad m => [FilePath] -> m () #
Set the input filenames.
getOutputFile :: PandocMonad m => m (Maybe FilePath) #
Retrieve the output filename.
setOutputFile :: PandocMonad m => Maybe FilePath -> m () #
Set the output filename.
setResourcePath :: PandocMonad m => [FilePath] -> m () #
Set the resource path searched by fetchItem
.
getResourcePath :: PandocMonad m => m [FilePath] #
Retrieve the resource path searched by fetchItem
.
readDefaultDataFile :: PandocMonad m => FilePath -> m ByteString #
Read file from from Cabal data directory.
readDataFile :: PandocMonad m => FilePath -> m ByteString #
Read file from user data directory or, if not found there, from Cabal data directory.
fillMediaBag :: PandocMonad m => Pandoc -> m Pandoc #
Traverse tree, filling media bag for any images that aren't already in the media bag.
toLang :: PandocMonad m => Maybe Text -> m (Maybe Lang) #
Convert BCP47 string to a Lang, issuing warning if there are problems.
setTranslations :: PandocMonad m => Lang -> m () #
Select the language to use with translateTerm
.
Note that this does not read a translation file;
that is only done the first time translateTerm
is
used.
translateTerm :: PandocMonad m => Term -> m Text #
Get a translation from the current term map. Issue a warning if the term is not defined.
makeCanonical :: FilePath -> FilePath #
Canonicalizes a file path by removing redundant .
and ..
.
The PureState
contains ersatz representations
of things that would normally be obtained through IO.
Constructors
PureState | |
Fields
|
getPureState :: PandocPure PureState #
Retrieve the underlying state of the
type.PandocPure
getsPureState :: (PureState -> a) -> PandocPure a #
Retrieve a value from the underlying state of the
type.PandocPure
putPureState :: PureState -> PandocPure () #
Set a new state for the
type.PandocPure
modifyPureState :: (PureState -> PureState) -> PandocPure () #
Modify the underlying state of the
type.PandocPure
newtype PandocPure a #
Constructors
PandocPure | |
Fields
|
Instances
Captures all file-level information necessary for a
conforming mock file system.PandocMonad
Constructors
FileInfo | |
Fields
|
addToFileTree :: FileTree -> FilePath -> IO FileTree #
Add the specified file to the FileTree. If file is a directory, add its contents recursively.
insertInFileTree :: FilePath -> FileInfo -> FileTree -> FileTree #
Insert an ersatz file into the FileTree
.
runPure :: PandocPure a -> Either PandocError a #
Run a PandocPure
operation.
data Translations #
Instances
Show Translations # | |
Defined in Text.Pandoc.Translations Methods showsPrec :: Int -> Translations -> ShowS # show :: Translations -> String # showList :: [Translations] -> ShowS # | |
Generic Translations # | |
Defined in Text.Pandoc.Translations Associated Types type Rep Translations :: Type -> Type # | |
Semigroup Translations # | |
Defined in Text.Pandoc.Translations Methods (<>) :: Translations -> Translations -> Translations # sconcat :: NonEmpty Translations -> Translations # stimes :: Integral b => b -> Translations -> Translations # | |
Monoid Translations # | |
Defined in Text.Pandoc.Translations Methods mempty :: Translations # mappend :: Translations -> Translations -> Translations # mconcat :: [Translations] -> Translations # | |
FromYAML Translations # | |
Defined in Text.Pandoc.Translations | |
FromJSON Translations # | |
Defined in Text.Pandoc.Translations | |
type Rep Translations # | |
Defined in Text.Pandoc.Translations |