pandoc-3.0.1: Conversion between markup formats
CopyrightCopyright (C) 2016-2020 Jesse Rosenthal John MacFarlane
LicenseGNU GPL, version 2 or above
MaintainerJesse Rosenthal <jrosenthal@jhu.edu>
Stabilityalpha
Portabilityportable
Safe HaskellSafe-Inferred
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

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

Instances details
Default CommonState Source # 
Instance details

Defined in Text.Pandoc.Class.CommonState

Methods

def :: CommonState #

newtype PandocIO a Source #

Instances

Instances details
MonadIO PandocIO Source # 
Instance details

Defined in Text.Pandoc.Class.PandocIO

Methods

liftIO :: IO a -> PandocIO a #

Applicative PandocIO Source # 
Instance details

Defined in Text.Pandoc.Class.PandocIO

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 #

Functor PandocIO Source # 
Instance details

Defined in Text.Pandoc.Class.PandocIO

Methods

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

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

Monad PandocIO Source # 
Instance details

Defined in Text.Pandoc.Class.PandocIO

Methods

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

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

return :: a -> PandocIO a #

MonadCatch PandocIO Source # 
Instance details

Defined in Text.Pandoc.Class.PandocIO

Methods

catch :: Exception e => PandocIO a -> (e -> PandocIO a) -> PandocIO a #

MonadMask PandocIO Source # 
Instance details

Defined in Text.Pandoc.Class.PandocIO

Methods

mask :: ((forall a. PandocIO a -> PandocIO a) -> PandocIO b) -> PandocIO b #

uninterruptibleMask :: ((forall a. PandocIO a -> PandocIO a) -> PandocIO b) -> PandocIO b #

generalBracket :: PandocIO a -> (a -> ExitCase b -> PandocIO c) -> (a -> PandocIO b) -> PandocIO (b, c) #

MonadThrow PandocIO Source # 
Instance details

Defined in Text.Pandoc.Class.PandocIO

Methods

throwM :: Exception e => e -> PandocIO a #

PandocMonad PandocIO Source # 
Instance details

Defined in Text.Pandoc.Class.PandocIO

MonadError PandocError PandocIO Source # 
Instance details

Defined in Text.Pandoc.Class.PandocIO

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.

extractMedia :: (PandocMonad m, MonadIO m) => FilePath -> Pandoc -> m Pandoc Source #

Extract media from the mediabag into a directory.

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.

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

Instances details
PandocMonad PandocIO Source # 
Instance details

Defined in Text.Pandoc.Class.PandocIO

PandocMonad PandocPure Source # 
Instance details

Defined in Text.Pandoc.Class.PandocPure

(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

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

Defined in Text.Pandoc.Class.PandocMonad

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.

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.

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.

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

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 #

Retrieve the media bag.

setMediaBag :: PandocMonad m => MediaBag -> m () Source #

Initialize the media bag.

insertMedia :: PandocMonad m => FilePath -> Maybe MimeType -> ByteString -> m () Source #

Insert an item into 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.

getInputFiles :: PandocMonad m => m [FilePath] Source #

Retrieve the input filenames.

setInputFiles :: PandocMonad m => [FilePath] -> m () Source #

Set the input filenames.

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

Retrieve the output filename.

setOutputFile :: PandocMonad m => Maybe FilePath -> m () Source #

Set the output filename.

setResourcePath :: PandocMonad m => [FilePath] -> m () Source #

Set the resource path searched by fetchItem.

getResourcePath :: PandocMonad m => m [FilePath] Source #

Retrieve the resource path searched by fetchItem.

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.

fillMediaBag :: PandocMonad m => Pandoc -> m Pandoc Source #

Traverse tree, filling media bag for any images that aren't already in the media bag.

toLang :: PandocMonad m => Maybe Text -> m (Maybe Lang) Source #

Convert BCP47 string to a Lang, issuing warning if there are problems.

makeCanonical :: FilePath -> FilePath Source #

Canonicalizes a file path by removing redundant . and ...

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.

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.

data PureState Source #

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

Constructors

PureState 

Fields

Instances

Instances details
Default PureState Source # 
Instance details

Defined in Text.Pandoc.Class.PandocPure

Methods

def :: PureState #

getPureState :: PandocPure PureState Source #

Retrieve the underlying state of the PandocPure type.

getsPureState :: (PureState -> a) -> PandocPure a Source #

Retrieve a value from the underlying state of the PandocPure type.

putPureState :: PureState -> PandocPure () Source #

Set a new state for the PandocPure type.

modifyPureState :: (PureState -> PureState) -> PandocPure () Source #

Modify the underlying state of the PandocPure type.

newtype PandocPure a Source #

Instances

Instances details
Applicative PandocPure Source # 
Instance details

Defined in Text.Pandoc.Class.PandocPure

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 #

Functor PandocPure Source # 
Instance details

Defined in Text.Pandoc.Class.PandocPure

Methods

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

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

Monad PandocPure Source # 
Instance details

Defined in Text.Pandoc.Class.PandocPure

Methods

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

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

return :: a -> PandocPure a #

PandocMonad PandocPure Source # 
Instance details

Defined in Text.Pandoc.Class.PandocPure

MonadError PandocError PandocPure Source # 
Instance details

Defined in Text.Pandoc.Class.PandocPure

data FileTree Source #

Basis of the mock file system used by PandocPure.

Instances

Instances details
Monoid FileTree Source # 
Instance details

Defined in Text.Pandoc.Class.PandocPure

Semigroup FileTree Source # 
Instance details

Defined in Text.Pandoc.Class.PandocPure

data FileInfo Source #

Captures all file-level information necessary for a PandocMonad conforming mock file system.

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.

data Translations Source #

Instances

Instances details
Monoid Translations Source # 
Instance details

Defined in Text.Pandoc.Translations.Types

Semigroup Translations Source # 
Instance details

Defined in Text.Pandoc.Translations.Types

Generic Translations Source # 
Instance details

Defined in Text.Pandoc.Translations.Types

Associated Types

type Rep Translations :: Type -> Type #

Show Translations Source # 
Instance details

Defined in Text.Pandoc.Translations.Types

FromJSON Translations Source # 
Instance details

Defined in Text.Pandoc.Translations.Types

Methods

parseJSON :: Value -> Parser Translations

parseJSONList :: Value -> Parser [Translations]

type Rep Translations Source # 
Instance details

Defined in Text.Pandoc.Translations.Types

type Rep Translations = D1 ('MetaData "Translations" "Text.Pandoc.Translations.Types" "pandoc-3.0.1-inplace" 'True) (C1 ('MetaCons "Translations" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map Term Text))))