pandoc-2.8.0.1: Conversion between markup formats

CopyrightCopyright (C) 2016-17 Jesse Rosenthal John MacFarlane
LicenseGNU GPL, version 2 or above
MaintainerJesse Rosenthal <jrosenthal@jhu.edu>
Stabilityalpha
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

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

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).

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.

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 #

trace :: Text -> m () Source #

Instances
PandocMonad PandocPure Source # 
Instance details

Defined in Text.Pandoc.Class

PandocMonad PandocIO Source # 
Instance details

Defined in Text.Pandoc.Class

(MonadTrans t, PandocMonad m, Functor (t m), MonadError PandocError (t m), Monad (t m), Applicative (t m)) => PandocMonad (t m) Source # 
Instance details

Defined in Text.Pandoc.Class

PandocMonad m => PandocMonad (ParsecT s st m) Source # 
Instance details

Defined in Text.Pandoc.Class

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 # 
Instance details

Defined in Text.Pandoc.Class

Methods

def :: CommonState #

Peekable CommonState Source # 
Instance details

Defined in Text.Pandoc.Lua.Marshaling.CommonState

Pushable CommonState Source # 
Instance details

Defined in Text.Pandoc.Lua.Marshaling.CommonState

Methods

push :: CommonState -> Lua () #

data PureState Source #

The PureState contains ersatz representations of things that would normally be obtained through IO.

Instances
Default PureState Source # 
Instance details

Defined in Text.Pandoc.Class

Methods

def :: PureState #

readFileFromDirs :: PandocMonad m => [FilePath] -> FilePath -> m (Maybe Text) Source #

Read file, checking in any number of directories.

report :: PandocMonad m => LogMessage -> m () Source #

Log a message using logOutput. Note that logOutput is called only if the verbosity level exceeds the level of the message, but the message is added to the list of log messages that will be retrieved by getLog regardless of its verbosity level.

setTrace :: PandocMonad m => Bool -> m () Source #

Determine whether tracing is enabled. This affects the behavior of trace. If tracing is not enabled, trace does nothing.

setRequestHeader Source #

Arguments

:: PandocMonad m 
=> Text

Header name

-> Text

Value

-> m () 

Set request header to use in HTTP requests.

setVerbosity :: PandocMonad m => Verbosity -> m () Source #

Set the verbosity level.

getVerbosity :: PandocMonad m => m Verbosity Source #

Get the verbosity level.

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.

getUserDataDir :: PandocMonad m => m (Maybe FilePath) Source #

Get the user data directory from common state.

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.

newtype PandocIO a Source #

Instances
Monad PandocIO Source # 
Instance details

Defined in Text.Pandoc.Class

Methods

(>>=) :: PandocIO a -> (a -> PandocIO b) -> PandocIO b #

(>>) :: PandocIO a -> PandocIO b -> PandocIO b #

return :: a -> PandocIO a #

fail :: String -> PandocIO a #

Functor PandocIO Source # 
Instance details

Defined in Text.Pandoc.Class

Methods

fmap :: (a -> b) -> PandocIO a -> PandocIO b #

(<$) :: a -> PandocIO b -> PandocIO a #

Applicative PandocIO Source # 
Instance details

Defined in Text.Pandoc.Class

Methods

pure :: a -> PandocIO a #

(<*>) :: PandocIO (a -> b) -> PandocIO a -> PandocIO b #

liftA2 :: (a -> b -> c) -> PandocIO a -> PandocIO b -> PandocIO c #

(*>) :: PandocIO a -> PandocIO b -> PandocIO b #

(<*) :: PandocIO a -> PandocIO b -> PandocIO a #

MonadIO PandocIO Source # 
Instance details

Defined in Text.Pandoc.Class

Methods

liftIO :: IO a -> PandocIO a #

TemplateMonad PandocIO Source # 
Instance details

Defined in Text.Pandoc.Class

PandocMonad PandocIO Source # 
Instance details

Defined in Text.Pandoc.Class

MonadError PandocError PandocIO Source # 
Instance details

Defined in Text.Pandoc.Class

newtype PandocPure a Source #

Instances
Monad PandocPure Source # 
Instance details

Defined in Text.Pandoc.Class

Methods

(>>=) :: PandocPure a -> (a -> PandocPure b) -> PandocPure b #

(>>) :: PandocPure a -> PandocPure b -> PandocPure b #

return :: a -> PandocPure a #

fail :: String -> PandocPure a #

Functor PandocPure Source # 
Instance details

Defined in Text.Pandoc.Class

Methods

fmap :: (a -> b) -> PandocPure a -> PandocPure b #

(<$) :: a -> PandocPure b -> PandocPure a #

Applicative PandocPure Source # 
Instance details

Defined in Text.Pandoc.Class

Methods

pure :: a -> PandocPure a #

(<*>) :: PandocPure (a -> b) -> PandocPure a -> PandocPure b #

liftA2 :: (a -> b -> c) -> PandocPure a -> PandocPure b -> PandocPure c #

(*>) :: PandocPure a -> PandocPure b -> PandocPure b #

(<*) :: PandocPure a -> PandocPure b -> PandocPure a #

TemplateMonad PandocPure Source # 
Instance details

Defined in Text.Pandoc.Class

PandocMonad PandocPure Source # 
Instance details

Defined in Text.Pandoc.Class

MonadError PandocError PandocPure Source # 
Instance details

Defined in Text.Pandoc.Class

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.

runIO :: PandocIO a -> IO (Either PandocError a) Source #

Evaluate a PandocIO operation.

runIOorExplode :: PandocIO a -> IO a Source #

Evaluate a PandocIO operation, handling any errors by exiting with an appropriate message and error status.

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 => Text -> 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 Text -> 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 Text Source #

Get a translation from the current term map. Issue a warning if the term is not defined.