module Text.Pandoc.Class.CommonState
  ( CommonState(..)
  , defaultCommonState
  )
where
import Data.Default (Default (def))
import Data.Text (Text)
import Text.Collate.Lang (Lang)
import Text.Pandoc.MediaBag (MediaBag)
import Text.Pandoc.Logging (LogMessage, Verbosity (WARNING))
import Text.Pandoc.Translations (Translations)
data CommonState = CommonState
  { CommonState -> [LogMessage]
stLog          :: [LogMessage]
    
  , CommonState -> Maybe FilePath
stUserDataDir  :: Maybe FilePath
    
  , CommonState -> Maybe Text
stSourceURL    :: Maybe Text
    
  ,  :: [(Text, Text)]
    
  , CommonState -> Bool
stNoCheckCertificate :: Bool
    
  , CommonState -> MediaBag
stMediaBag     :: MediaBag
    
  , CommonState -> Maybe (Lang, Maybe Translations)
stTranslations :: Maybe (Lang, Maybe Translations)
    
  , CommonState -> [FilePath]
stInputFiles   :: [FilePath]
    
  , CommonState -> Maybe FilePath
stOutputFile   :: Maybe FilePath
    
  , CommonState -> [FilePath]
stResourcePath :: [FilePath]
    
    
  , CommonState -> Verbosity
stVerbosity    :: Verbosity
    
  , CommonState -> Bool
stTrace        :: Bool
    
    
  }
defaultCommonState :: CommonState
defaultCommonState :: CommonState
defaultCommonState = CommonState
  { stLog :: [LogMessage]
stLog = []
  , stUserDataDir :: Maybe FilePath
stUserDataDir = forall a. Maybe a
Nothing
  , stSourceURL :: Maybe Text
stSourceURL = forall a. Maybe a
Nothing
  , stRequestHeaders :: [(Text, Text)]
stRequestHeaders = []
  , stNoCheckCertificate :: Bool
stNoCheckCertificate = Bool
False
  , stMediaBag :: MediaBag
stMediaBag = forall a. Monoid a => a
mempty
  , stTranslations :: Maybe (Lang, Maybe Translations)
stTranslations = forall a. Maybe a
Nothing
  , stInputFiles :: [FilePath]
stInputFiles = []
  , stOutputFile :: Maybe FilePath
stOutputFile = forall a. Maybe a
Nothing
  , stResourcePath :: [FilePath]
stResourcePath = [FilePath
"."]
  , stVerbosity :: Verbosity
stVerbosity = Verbosity
WARNING
  , stTrace :: Bool
stTrace = Bool
False
  }
instance Default CommonState where
  def :: CommonState
def = CommonState
defaultCommonState