Copyright | Copyright (C) 2016-17 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 |
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
- 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 (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 :: String -> m ()
- 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
- data PureState = PureState {
- stStdGen :: StdGen
- stWord8Store :: [Word8]
- stUniqStore :: [Int]
- stEnv :: [(String, String)]
- 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 ()
- getPOSIXTime :: PandocMonad m => m POSIXTime
- getZonedTime :: PandocMonad m => m ZonedTime
- readFileFromDirs :: PandocMonad m => [FilePath] -> FilePath -> m (Maybe String)
- report :: PandocMonad m => LogMessage -> m ()
- setTrace :: PandocMonad m => Bool -> m ()
- setRequestHeader :: PandocMonad m => String -> String -> 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 => String -> 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
- newtype PandocPure a = PandocPure {}
- data FileTree
- data FileInfo = FileInfo {}
- addToFileTree :: FileTree -> FilePath -> IO FileTree
- insertInFileTree :: FilePath -> FileInfo -> FileTree -> FileTree
- runIO :: PandocIO a -> IO (Either PandocError a)
- runIOorExplode :: PandocIO a -> IO a
- runPure :: PandocPure a -> Either PandocError a
- readDefaultDataFile :: PandocMonad m => FilePath -> m ByteString
- readDataFile :: PandocMonad m => FilePath -> m ByteString
- fetchMediaResource :: PandocMonad m => String -> m (FilePath, Maybe MimeType, ByteString)
- fillMediaBag :: PandocMonad m => Pandoc -> m Pandoc
- extractMedia :: FilePath -> Pandoc -> PandocIO Pandoc
- toLang :: PandocMonad m => Maybe String -> m (Maybe Lang)
- setTranslations :: PandocMonad m => Lang -> m ()
- translateTerm :: PandocMonad m => Term -> m String
- data Translations
Documentation
class (Functor m, Applicative m, Monad m, MonadError PandocError m) => PandocMonad m 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
).
lookupEnv, getCurrentTime, getCurrentTimeZone, newStdGen, newUniqueHash, openURL, readFileLazy, readFileStrict, glob, fileExists, getDataFileName, getModificationTime, getCommonState, putCommonState, logOutput
lookupEnv :: String -> m (Maybe String) 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 :: String -> 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.
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 #
Instances
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.
CommonState | |
|
Instances
Default CommonState Source # | |
Defined in Text.Pandoc.Class def :: CommonState # | |
Peekable CommonState Source # | |
Defined in Text.Pandoc.Lua.StackInstances peek :: StackIndex -> Lua CommonState # | |
Pushable CommonState Source # | |
Defined in Text.Pandoc.Lua.StackInstances push :: CommonState -> Lua () # |
The PureState
contains ersatz representations
of things that would normally be obtained through IO.
PureState | |
|
getsPureState :: (PureState -> a) -> PandocPure a Source #
putPureState :: PureState -> PandocPure () Source #
modifyPureState :: (PureState -> PureState) -> PandocPure () Source #
getPOSIXTime :: PandocMonad m => m POSIXTime Source #
getZonedTime :: PandocMonad m => m ZonedTime Source #
readFileFromDirs :: PandocMonad m => [FilePath] -> FilePath -> m (Maybe String) Source #
Read file, checking in any number of directories.
report :: PandocMonad m => LogMessage -> m () Source #
setTrace :: PandocMonad m => Bool -> m () Source #
:: PandocMonad m | |
=> String | Header name |
-> String | Value |
-> m () |
Set request header to use in HTTP requests.
getLog :: PandocMonad m => m [LogMessage] Source #
setVerbosity :: PandocMonad m => Verbosity -> m () Source #
Set the verbosity level.
getVerbosity :: PandocMonad m => m Verbosity Source #
Get the verbosity level.
getMediaBag :: PandocMonad m => m MediaBag Source #
setMediaBag :: PandocMonad m => MediaBag -> m () Source #
Initialize the media bag.
insertMedia :: PandocMonad m => FilePath -> Maybe MimeType -> ByteString -> m () Source #
setUserDataDir :: PandocMonad m => Maybe FilePath -> m () Source #
Set the user data directory in common state.
getUserDataDir :: PandocMonad m => m (Maybe FilePath) Source #
Get the user data directory from common state.
fetchItem :: PandocMonad m => String -> 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.
getInputFiles :: PandocMonad m => m [FilePath] Source #
setInputFiles :: PandocMonad m => [FilePath] -> m () Source #
getOutputFile :: PandocMonad m => m (Maybe FilePath) Source #
setOutputFile :: PandocMonad m => Maybe FilePath -> m () Source #
setResourcePath :: PandocMonad m => [FilePath] -> m () Source #
getResourcePath :: PandocMonad m => m [FilePath] Source #
Instances
newtype PandocPure a Source #
Instances
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
.
runIOorExplode :: PandocIO a -> IO a Source #
Evaluate a PandocIO
operation, handling any errors
by exiting with an appropriate message and error status.
runPure :: PandocPure a -> Either PandocError a Source #
readDefaultDataFile :: PandocMonad m => FilePath -> m ByteString Source #
Read file from from Cabal data directory.
readDataFile :: PandocMonad m => FilePath -> m ByteString Source #
Read file from user data directory or, if not found there, from Cabal data directory.
fetchMediaResource :: PandocMonad m => String -> m (FilePath, Maybe MimeType, ByteString) Source #
Fetch local or remote resource (like an image) and provide data suitable for adding it to the MediaBag.
fillMediaBag :: PandocMonad m => Pandoc -> m Pandoc Source #
Traverse tree, filling media bag for any images that aren't already in the media bag.
extractMedia :: FilePath -> Pandoc -> PandocIO Pandoc Source #
Extract media from the mediabag into a directory.
toLang :: PandocMonad m => Maybe String -> m (Maybe Lang) Source #
Convert BCP47 string to a Lang, issuing warning if there are problems.
setTranslations :: PandocMonad m => Lang -> m () Source #
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 String Source #
Get a translation from the current term map. Issue a warning if the term is not defined.
data Translations Source #