{-# OPTIONS_GHC -Wall #-} module Text.Pandoc.Z.Util( unwrapPandoc , readPandoc , readPandocExtensions , readPandocPlainExtensions , readPandocPhpMarkdownExtraExtensions , readPandocGithubMarkdownExtensions , readPandocMultimarkdownExtensions , readPandocStrictExtensions , readPandocDefaultExtensions , writePandoc , writePandocExtensions , writePandocPlainExtensions , writePandocPhpMarkdownExtraExtensions , writePandocGithubMarkdownExtensions , writePandocMultimarkdownExtensions , writePandocStrictExtensions , writePandocDefaultExtensions , (.~~) ) where import Control.Lens ( (&), view, (.~), set, _Wrapped, ASetter, Field1(_1) ) import Data.Default ( Default(def) ) import Data.Stringz(HasText(text)) import Data.Text as Text ( Text ) import Text.Pandoc.Class ( PandocPure(unPandocPure) ) import Text.Pandoc.Error ( PandocError ) import Text.Pandoc.Extensions ( getDefaultExtensions, githubMarkdownExtensions, multimarkdownExtensions, pandocExtensions, phpMarkdownExtraExtensions, plainExtensions, strictExtensions ) import Text.Pandoc.Z.Extensions ( HasExtensions(extensions) ) import Text.Pandoc.Z.ReaderOptions ( ReaderOptions, defaultReaderOptions ) import Text.Pandoc.Z.WriterOptions ( WriterOptions, defaultWriterOptions ) unwrapPandoc :: PandocPure a -> Either PandocError a unwrapPandoc :: forall a. PandocPure a -> Either PandocError a unwrapPandoc PandocPure a x = Getting (Either PandocError a) (Unwrapped (Identity ((Either PandocError a, CommonState), PureState))) (Either PandocError a) -> Unwrapped (Identity ((Either PandocError a, CommonState), PureState)) -> Either PandocError a forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a view (((Either PandocError a, CommonState) -> Const (Either PandocError a) (Either PandocError a, CommonState)) -> Unwrapped (Identity ((Either PandocError a, CommonState), PureState)) -> Const (Either PandocError a) (Unwrapped (Identity ((Either PandocError a, CommonState), PureState))) forall s t a b. Field1 s t a b => Lens s t a b Lens (Unwrapped (Identity ((Either PandocError a, CommonState), PureState))) (Unwrapped (Identity ((Either PandocError a, CommonState), PureState))) (Either PandocError a, CommonState) (Either PandocError a, CommonState) _1 (((Either PandocError a, CommonState) -> Const (Either PandocError a) (Either PandocError a, CommonState)) -> Unwrapped (Identity ((Either PandocError a, CommonState), PureState)) -> Const (Either PandocError a) (Unwrapped (Identity ((Either PandocError a, CommonState), PureState)))) -> ((Either PandocError a -> Const (Either PandocError a) (Either PandocError a)) -> (Either PandocError a, CommonState) -> Const (Either PandocError a) (Either PandocError a, CommonState)) -> Getting (Either PandocError a) (Unwrapped (Identity ((Either PandocError a, CommonState), PureState))) (Either PandocError a) forall b c a. (b -> c) -> (a -> b) -> a -> c . (Either PandocError a -> Const (Either PandocError a) (Either PandocError a)) -> (Either PandocError a, CommonState) -> Const (Either PandocError a) (Either PandocError a, CommonState) forall s t a b. Field1 s t a b => Lens s t a b Lens (Either PandocError a, CommonState) (Either PandocError a, CommonState) (Either PandocError a) (Either PandocError a) _1) (Getting (Unwrapped (Identity ((Either PandocError a, CommonState), PureState))) (Identity ((Either PandocError a, CommonState), PureState)) (Unwrapped (Identity ((Either PandocError a, CommonState), PureState))) -> Identity ((Either PandocError a, CommonState), PureState) -> Unwrapped (Identity ((Either PandocError a, CommonState), PureState)) forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a view Getting (Unwrapped (Identity ((Either PandocError a, CommonState), PureState))) (Identity ((Either PandocError a, CommonState), PureState)) (Unwrapped (Identity ((Either PandocError a, CommonState), PureState))) forall s t. Rewrapping s t => Iso s t (Unwrapped s) (Unwrapped t) Iso (Identity ((Either PandocError a, CommonState), PureState)) (Identity ((Either PandocError a, CommonState), PureState)) (Unwrapped (Identity ((Either PandocError a, CommonState), PureState))) (Unwrapped (Identity ((Either PandocError a, CommonState), PureState))) _Wrapped (Getting (PureState -> Identity ((Either PandocError a, CommonState), PureState)) (StateT PureState Identity (Either PandocError a, CommonState)) (PureState -> Identity ((Either PandocError a, CommonState), PureState)) -> StateT PureState Identity (Either PandocError a, CommonState) -> PureState -> Identity ((Either PandocError a, CommonState), PureState) forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a view (Unwrapped (StateT PureState Identity (Either PandocError a, CommonState)) -> Const (PureState -> Identity ((Either PandocError a, CommonState), PureState)) (Unwrapped (StateT PureState Identity (Either PandocError a, CommonState)))) -> StateT PureState Identity (Either PandocError a, CommonState) -> Const (PureState -> Identity ((Either PandocError a, CommonState), PureState)) (StateT PureState Identity (Either PandocError a, CommonState)) Getting (PureState -> Identity ((Either PandocError a, CommonState), PureState)) (StateT PureState Identity (Either PandocError a, CommonState)) (PureState -> Identity ((Either PandocError a, CommonState), PureState)) forall s t. Rewrapping s t => Iso s t (Unwrapped s) (Unwrapped t) Iso (StateT PureState Identity (Either PandocError a, CommonState)) (StateT PureState Identity (Either PandocError a, CommonState)) (Unwrapped (StateT PureState Identity (Either PandocError a, CommonState))) (Unwrapped (StateT PureState Identity (Either PandocError a, CommonState))) _Wrapped (Getting (CommonState -> StateT PureState Identity (Either PandocError a, CommonState)) (ExceptT PandocError (StateT CommonState (State PureState)) a) (CommonState -> StateT PureState Identity (Either PandocError a, CommonState)) -> ExceptT PandocError (StateT CommonState (State PureState)) a -> CommonState -> StateT PureState Identity (Either PandocError a, CommonState) forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a view ((Unwrapped (ExceptT PandocError (StateT CommonState (State PureState)) a) -> Const (CommonState -> StateT PureState Identity (Either PandocError a, CommonState)) (Unwrapped (ExceptT PandocError (StateT CommonState (State PureState)) a))) -> ExceptT PandocError (StateT CommonState (State PureState)) a -> Const (CommonState -> StateT PureState Identity (Either PandocError a, CommonState)) (ExceptT PandocError (StateT CommonState (State PureState)) a) forall s t. Rewrapping s t => Iso s t (Unwrapped s) (Unwrapped t) Iso (ExceptT PandocError (StateT CommonState (State PureState)) a) (ExceptT PandocError (StateT CommonState (State PureState)) a) (Unwrapped (ExceptT PandocError (StateT CommonState (State PureState)) a)) (Unwrapped (ExceptT PandocError (StateT CommonState (State PureState)) a)) _Wrapped ((Unwrapped (ExceptT PandocError (StateT CommonState (State PureState)) a) -> Const (CommonState -> StateT PureState Identity (Either PandocError a, CommonState)) (Unwrapped (ExceptT PandocError (StateT CommonState (State PureState)) a))) -> ExceptT PandocError (StateT CommonState (State PureState)) a -> Const (CommonState -> StateT PureState Identity (Either PandocError a, CommonState)) (ExceptT PandocError (StateT CommonState (State PureState)) a)) -> (((CommonState -> StateT PureState Identity (Either PandocError a, CommonState)) -> Const (CommonState -> StateT PureState Identity (Either PandocError a, CommonState)) (CommonState -> StateT PureState Identity (Either PandocError a, CommonState))) -> Unwrapped (ExceptT PandocError (StateT CommonState (State PureState)) a) -> Const (CommonState -> StateT PureState Identity (Either PandocError a, CommonState)) (Unwrapped (ExceptT PandocError (StateT CommonState (State PureState)) a))) -> Getting (CommonState -> StateT PureState Identity (Either PandocError a, CommonState)) (ExceptT PandocError (StateT CommonState (State PureState)) a) (CommonState -> StateT PureState Identity (Either PandocError a, CommonState)) forall b c a. (b -> c) -> (a -> b) -> a -> c . (Unwrapped (Unwrapped (ExceptT PandocError (StateT CommonState (State PureState)) a)) -> Const (CommonState -> StateT PureState Identity (Either PandocError a, CommonState)) (Unwrapped (Unwrapped (ExceptT PandocError (StateT CommonState (State PureState)) a)))) -> Unwrapped (ExceptT PandocError (StateT CommonState (State PureState)) a) -> Const (CommonState -> StateT PureState Identity (Either PandocError a, CommonState)) (Unwrapped (ExceptT PandocError (StateT CommonState (State PureState)) a)) ((CommonState -> StateT PureState Identity (Either PandocError a, CommonState)) -> Const (CommonState -> StateT PureState Identity (Either PandocError a, CommonState)) (CommonState -> StateT PureState Identity (Either PandocError a, CommonState))) -> Unwrapped (ExceptT PandocError (StateT CommonState (State PureState)) a) -> Const (CommonState -> StateT PureState Identity (Either PandocError a, CommonState)) (Unwrapped (ExceptT PandocError (StateT CommonState (State PureState)) a)) forall s t. Rewrapping s t => Iso s t (Unwrapped s) (Unwrapped t) Iso (Unwrapped (ExceptT PandocError (StateT CommonState (State PureState)) a)) (Unwrapped (ExceptT PandocError (StateT CommonState (State PureState)) a)) (Unwrapped (Unwrapped (ExceptT PandocError (StateT CommonState (State PureState)) a))) (Unwrapped (Unwrapped (ExceptT PandocError (StateT CommonState (State PureState)) a))) _Wrapped) (PandocPure a -> ExceptT PandocError (StateT CommonState (State PureState)) a forall a. PandocPure a -> ExceptT PandocError (StateT CommonState (State PureState)) a unPandocPure PandocPure a x) CommonState forall a. Default a => a def) PureState forall a. Default a => a def)) readPandoc :: HasText s => (ReaderOptions -> Text -> PandocPure a) -> s -> Either PandocError a readPandoc :: forall s a. HasText s => (ReaderOptions -> Text -> PandocPure a) -> s -> Either PandocError a readPandoc ReaderOptions -> Text -> PandocPure a f = PandocPure a -> Either PandocError a forall a. PandocPure a -> Either PandocError a unwrapPandoc (PandocPure a -> Either PandocError a) -> (s -> PandocPure a) -> s -> Either PandocError a forall b c a. (b -> c) -> (a -> b) -> a -> c . ReaderOptions -> Text -> PandocPure a f ReaderOptions defaultReaderOptions (Text -> PandocPure a) -> (s -> Text) -> s -> PandocPure a forall b c a. (b -> c) -> (a -> b) -> a -> c . Getting Text s Text -> s -> Text forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a view Getting Text s Text forall a. HasText a => Lens' a Text Lens' s Text text readPandocExtensions :: HasText s => (ReaderOptions -> Text -> PandocPure a) -> s -> Either PandocError a readPandocExtensions :: forall s a. HasText s => (ReaderOptions -> Text -> PandocPure a) -> s -> Either PandocError a readPandocExtensions ReaderOptions -> Text -> PandocPure a f = (ReaderOptions -> Text -> PandocPure a) -> s -> Either PandocError a forall s a. HasText s => (ReaderOptions -> Text -> PandocPure a) -> s -> Either PandocError a readPandoc (\ReaderOptions o -> ReaderOptions -> Text -> PandocPure a f (ReaderOptions o ReaderOptions -> (ReaderOptions -> ReaderOptions) -> ReaderOptions forall a b. a -> (a -> b) -> b & (Extensions -> Identity Extensions) -> ReaderOptions -> Identity ReaderOptions forall a. HasExtensions a => Lens' a Extensions Lens' ReaderOptions Extensions extensions ((Extensions -> Identity Extensions) -> ReaderOptions -> Identity ReaderOptions) -> Extensions -> ReaderOptions -> ReaderOptions forall s t a b. ASetter s t a b -> b -> s -> t .~ Extensions pandocExtensions)) readPandocPlainExtensions :: HasText s => (ReaderOptions -> Text -> PandocPure a) -> s -> Either PandocError a readPandocPlainExtensions :: forall s a. HasText s => (ReaderOptions -> Text -> PandocPure a) -> s -> Either PandocError a readPandocPlainExtensions ReaderOptions -> Text -> PandocPure a f = (ReaderOptions -> Text -> PandocPure a) -> s -> Either PandocError a forall s a. HasText s => (ReaderOptions -> Text -> PandocPure a) -> s -> Either PandocError a readPandoc (\ReaderOptions o -> ReaderOptions -> Text -> PandocPure a f (ReaderOptions o ReaderOptions -> (ReaderOptions -> ReaderOptions) -> ReaderOptions forall a b. a -> (a -> b) -> b & (Extensions -> Identity Extensions) -> ReaderOptions -> Identity ReaderOptions forall a. HasExtensions a => Lens' a Extensions Lens' ReaderOptions Extensions extensions ((Extensions -> Identity Extensions) -> ReaderOptions -> Identity ReaderOptions) -> Extensions -> ReaderOptions -> ReaderOptions forall s t a b. ASetter s t a b -> b -> s -> t .~ Extensions plainExtensions)) readPandocPhpMarkdownExtraExtensions :: HasText s => (ReaderOptions -> Text -> PandocPure a) -> s -> Either PandocError a readPandocPhpMarkdownExtraExtensions :: forall s a. HasText s => (ReaderOptions -> Text -> PandocPure a) -> s -> Either PandocError a readPandocPhpMarkdownExtraExtensions ReaderOptions -> Text -> PandocPure a f = (ReaderOptions -> Text -> PandocPure a) -> s -> Either PandocError a forall s a. HasText s => (ReaderOptions -> Text -> PandocPure a) -> s -> Either PandocError a readPandoc (\ReaderOptions o -> ReaderOptions -> Text -> PandocPure a f (ReaderOptions o ReaderOptions -> (ReaderOptions -> ReaderOptions) -> ReaderOptions forall a b. a -> (a -> b) -> b & (Extensions -> Identity Extensions) -> ReaderOptions -> Identity ReaderOptions forall a. HasExtensions a => Lens' a Extensions Lens' ReaderOptions Extensions extensions ((Extensions -> Identity Extensions) -> ReaderOptions -> Identity ReaderOptions) -> Extensions -> ReaderOptions -> ReaderOptions forall s t a b. ASetter s t a b -> b -> s -> t .~ Extensions phpMarkdownExtraExtensions)) readPandocGithubMarkdownExtensions :: HasText s => (ReaderOptions -> Text -> PandocPure a) -> s -> Either PandocError a readPandocGithubMarkdownExtensions :: forall s a. HasText s => (ReaderOptions -> Text -> PandocPure a) -> s -> Either PandocError a readPandocGithubMarkdownExtensions ReaderOptions -> Text -> PandocPure a f = (ReaderOptions -> Text -> PandocPure a) -> s -> Either PandocError a forall s a. HasText s => (ReaderOptions -> Text -> PandocPure a) -> s -> Either PandocError a readPandoc (\ReaderOptions o -> ReaderOptions -> Text -> PandocPure a f (ReaderOptions o ReaderOptions -> (ReaderOptions -> ReaderOptions) -> ReaderOptions forall a b. a -> (a -> b) -> b & (Extensions -> Identity Extensions) -> ReaderOptions -> Identity ReaderOptions forall a. HasExtensions a => Lens' a Extensions Lens' ReaderOptions Extensions extensions ((Extensions -> Identity Extensions) -> ReaderOptions -> Identity ReaderOptions) -> Extensions -> ReaderOptions -> ReaderOptions forall s t a b. ASetter s t a b -> b -> s -> t .~ Extensions githubMarkdownExtensions)) readPandocMultimarkdownExtensions :: HasText s => (ReaderOptions -> Text -> PandocPure a) -> s -> Either PandocError a readPandocMultimarkdownExtensions :: forall s a. HasText s => (ReaderOptions -> Text -> PandocPure a) -> s -> Either PandocError a readPandocMultimarkdownExtensions ReaderOptions -> Text -> PandocPure a f = (ReaderOptions -> Text -> PandocPure a) -> s -> Either PandocError a forall s a. HasText s => (ReaderOptions -> Text -> PandocPure a) -> s -> Either PandocError a readPandoc (\ReaderOptions o -> ReaderOptions -> Text -> PandocPure a f (ReaderOptions o ReaderOptions -> (ReaderOptions -> ReaderOptions) -> ReaderOptions forall a b. a -> (a -> b) -> b & (Extensions -> Identity Extensions) -> ReaderOptions -> Identity ReaderOptions forall a. HasExtensions a => Lens' a Extensions Lens' ReaderOptions Extensions extensions ((Extensions -> Identity Extensions) -> ReaderOptions -> Identity ReaderOptions) -> Extensions -> ReaderOptions -> ReaderOptions forall s t a b. ASetter s t a b -> b -> s -> t .~ Extensions multimarkdownExtensions)) readPandocStrictExtensions :: HasText s => (ReaderOptions -> Text -> PandocPure a) -> s -> Either PandocError a readPandocStrictExtensions :: forall s a. HasText s => (ReaderOptions -> Text -> PandocPure a) -> s -> Either PandocError a readPandocStrictExtensions ReaderOptions -> Text -> PandocPure a f = (ReaderOptions -> Text -> PandocPure a) -> s -> Either PandocError a forall s a. HasText s => (ReaderOptions -> Text -> PandocPure a) -> s -> Either PandocError a readPandoc (\ReaderOptions o -> ReaderOptions -> Text -> PandocPure a f (ReaderOptions o ReaderOptions -> (ReaderOptions -> ReaderOptions) -> ReaderOptions forall a b. a -> (a -> b) -> b & (Extensions -> Identity Extensions) -> ReaderOptions -> Identity ReaderOptions forall a. HasExtensions a => Lens' a Extensions Lens' ReaderOptions Extensions extensions ((Extensions -> Identity Extensions) -> ReaderOptions -> Identity ReaderOptions) -> Extensions -> ReaderOptions -> ReaderOptions forall s t a b. ASetter s t a b -> b -> s -> t .~ Extensions strictExtensions)) readPandocDefaultExtensions :: HasText s => Text -> (ReaderOptions -> Text -> PandocPure a) -> s -> Either PandocError a readPandocDefaultExtensions :: forall s a. HasText s => Text -> (ReaderOptions -> Text -> PandocPure a) -> s -> Either PandocError a readPandocDefaultExtensions Text t ReaderOptions -> Text -> PandocPure a f = (ReaderOptions -> Text -> PandocPure a) -> s -> Either PandocError a forall s a. HasText s => (ReaderOptions -> Text -> PandocPure a) -> s -> Either PandocError a readPandoc (\ReaderOptions o -> ReaderOptions -> Text -> PandocPure a f (ReaderOptions o ReaderOptions -> (ReaderOptions -> ReaderOptions) -> ReaderOptions forall a b. a -> (a -> b) -> b & (Extensions -> Identity Extensions) -> ReaderOptions -> Identity ReaderOptions forall a. HasExtensions a => Lens' a Extensions Lens' ReaderOptions Extensions extensions ((Extensions -> Identity Extensions) -> ReaderOptions -> Identity ReaderOptions) -> Extensions -> ReaderOptions -> ReaderOptions forall s t a b. ASetter s t a b -> b -> s -> t .~ Text -> Extensions getDefaultExtensions Text t)) writePandoc :: (WriterOptions -> b -> PandocPure a) -> b -> Either PandocError a writePandoc :: forall b a. (WriterOptions -> b -> PandocPure a) -> b -> Either PandocError a writePandoc WriterOptions -> b -> PandocPure a f = PandocPure a -> Either PandocError a forall a. PandocPure a -> Either PandocError a unwrapPandoc (PandocPure a -> Either PandocError a) -> (b -> PandocPure a) -> b -> Either PandocError a forall b c a. (b -> c) -> (a -> b) -> a -> c . WriterOptions -> b -> PandocPure a f WriterOptions defaultWriterOptions writePandocExtensions :: (WriterOptions -> b -> PandocPure a) -> b -> Either PandocError a writePandocExtensions :: forall b a. (WriterOptions -> b -> PandocPure a) -> b -> Either PandocError a writePandocExtensions WriterOptions -> b -> PandocPure a f = (WriterOptions -> b -> PandocPure a) -> b -> Either PandocError a forall b a. (WriterOptions -> b -> PandocPure a) -> b -> Either PandocError a writePandoc (\WriterOptions o -> WriterOptions -> b -> PandocPure a f (WriterOptions o WriterOptions -> (WriterOptions -> WriterOptions) -> WriterOptions forall a b. a -> (a -> b) -> b & (Extensions -> Identity Extensions) -> WriterOptions -> Identity WriterOptions forall a. HasExtensions a => Lens' a Extensions Lens' WriterOptions Extensions extensions ((Extensions -> Identity Extensions) -> WriterOptions -> Identity WriterOptions) -> Extensions -> WriterOptions -> WriterOptions forall s t a b. ASetter s t a b -> b -> s -> t .~ Extensions pandocExtensions)) writePandocPlainExtensions :: (WriterOptions -> b -> PandocPure a) -> b -> Either PandocError a writePandocPlainExtensions :: forall b a. (WriterOptions -> b -> PandocPure a) -> b -> Either PandocError a writePandocPlainExtensions WriterOptions -> b -> PandocPure a f = (WriterOptions -> b -> PandocPure a) -> b -> Either PandocError a forall b a. (WriterOptions -> b -> PandocPure a) -> b -> Either PandocError a writePandoc (\WriterOptions o -> WriterOptions -> b -> PandocPure a f (WriterOptions o WriterOptions -> (WriterOptions -> WriterOptions) -> WriterOptions forall a b. a -> (a -> b) -> b & (Extensions -> Identity Extensions) -> WriterOptions -> Identity WriterOptions forall a. HasExtensions a => Lens' a Extensions Lens' WriterOptions Extensions extensions ((Extensions -> Identity Extensions) -> WriterOptions -> Identity WriterOptions) -> Extensions -> WriterOptions -> WriterOptions forall s t a b. ASetter s t a b -> b -> s -> t .~ Extensions plainExtensions)) writePandocPhpMarkdownExtraExtensions :: (WriterOptions -> b -> PandocPure a) -> b -> Either PandocError a writePandocPhpMarkdownExtraExtensions :: forall b a. (WriterOptions -> b -> PandocPure a) -> b -> Either PandocError a writePandocPhpMarkdownExtraExtensions WriterOptions -> b -> PandocPure a f = (WriterOptions -> b -> PandocPure a) -> b -> Either PandocError a forall b a. (WriterOptions -> b -> PandocPure a) -> b -> Either PandocError a writePandoc (\WriterOptions o -> WriterOptions -> b -> PandocPure a f (WriterOptions o WriterOptions -> (WriterOptions -> WriterOptions) -> WriterOptions forall a b. a -> (a -> b) -> b & (Extensions -> Identity Extensions) -> WriterOptions -> Identity WriterOptions forall a. HasExtensions a => Lens' a Extensions Lens' WriterOptions Extensions extensions ((Extensions -> Identity Extensions) -> WriterOptions -> Identity WriterOptions) -> Extensions -> WriterOptions -> WriterOptions forall s t a b. ASetter s t a b -> b -> s -> t .~ Extensions phpMarkdownExtraExtensions)) writePandocGithubMarkdownExtensions :: (WriterOptions -> b -> PandocPure a) -> b -> Either PandocError a writePandocGithubMarkdownExtensions :: forall b a. (WriterOptions -> b -> PandocPure a) -> b -> Either PandocError a writePandocGithubMarkdownExtensions WriterOptions -> b -> PandocPure a f = (WriterOptions -> b -> PandocPure a) -> b -> Either PandocError a forall b a. (WriterOptions -> b -> PandocPure a) -> b -> Either PandocError a writePandoc (\WriterOptions o -> WriterOptions -> b -> PandocPure a f (WriterOptions o WriterOptions -> (WriterOptions -> WriterOptions) -> WriterOptions forall a b. a -> (a -> b) -> b & (Extensions -> Identity Extensions) -> WriterOptions -> Identity WriterOptions forall a. HasExtensions a => Lens' a Extensions Lens' WriterOptions Extensions extensions ((Extensions -> Identity Extensions) -> WriterOptions -> Identity WriterOptions) -> Extensions -> WriterOptions -> WriterOptions forall s t a b. ASetter s t a b -> b -> s -> t .~ Extensions githubMarkdownExtensions)) writePandocMultimarkdownExtensions :: (WriterOptions -> b -> PandocPure a) -> b -> Either PandocError a writePandocMultimarkdownExtensions :: forall b a. (WriterOptions -> b -> PandocPure a) -> b -> Either PandocError a writePandocMultimarkdownExtensions WriterOptions -> b -> PandocPure a f = (WriterOptions -> b -> PandocPure a) -> b -> Either PandocError a forall b a. (WriterOptions -> b -> PandocPure a) -> b -> Either PandocError a writePandoc (\WriterOptions o -> WriterOptions -> b -> PandocPure a f (WriterOptions o WriterOptions -> (WriterOptions -> WriterOptions) -> WriterOptions forall a b. a -> (a -> b) -> b & (Extensions -> Identity Extensions) -> WriterOptions -> Identity WriterOptions forall a. HasExtensions a => Lens' a Extensions Lens' WriterOptions Extensions extensions ((Extensions -> Identity Extensions) -> WriterOptions -> Identity WriterOptions) -> Extensions -> WriterOptions -> WriterOptions forall s t a b. ASetter s t a b -> b -> s -> t .~ Extensions multimarkdownExtensions)) writePandocStrictExtensions :: (WriterOptions -> b -> PandocPure a) -> b -> Either PandocError a writePandocStrictExtensions :: forall b a. (WriterOptions -> b -> PandocPure a) -> b -> Either PandocError a writePandocStrictExtensions WriterOptions -> b -> PandocPure a f = (WriterOptions -> b -> PandocPure a) -> b -> Either PandocError a forall b a. (WriterOptions -> b -> PandocPure a) -> b -> Either PandocError a writePandoc (\WriterOptions o -> WriterOptions -> b -> PandocPure a f (WriterOptions o WriterOptions -> (WriterOptions -> WriterOptions) -> WriterOptions forall a b. a -> (a -> b) -> b & (Extensions -> Identity Extensions) -> WriterOptions -> Identity WriterOptions forall a. HasExtensions a => Lens' a Extensions Lens' WriterOptions Extensions extensions ((Extensions -> Identity Extensions) -> WriterOptions -> Identity WriterOptions) -> Extensions -> WriterOptions -> WriterOptions forall s t a b. ASetter s t a b -> b -> s -> t .~ Extensions strictExtensions)) writePandocDefaultExtensions :: Text -> (WriterOptions -> b -> PandocPure a) -> b -> Either PandocError a writePandocDefaultExtensions :: forall b a. Text -> (WriterOptions -> b -> PandocPure a) -> b -> Either PandocError a writePandocDefaultExtensions Text t WriterOptions -> b -> PandocPure a f = (WriterOptions -> b -> PandocPure a) -> b -> Either PandocError a forall b a. (WriterOptions -> b -> PandocPure a) -> b -> Either PandocError a writePandoc (\WriterOptions o -> WriterOptions -> b -> PandocPure a f (WriterOptions o WriterOptions -> (WriterOptions -> WriterOptions) -> WriterOptions forall a b. a -> (a -> b) -> b & (Extensions -> Identity Extensions) -> WriterOptions -> Identity WriterOptions forall a. HasExtensions a => Lens' a Extensions Lens' WriterOptions Extensions extensions ((Extensions -> Identity Extensions) -> WriterOptions -> Identity WriterOptions) -> Extensions -> WriterOptions -> WriterOptions forall s t a b. ASetter s t a b -> b -> s -> t .~ Text -> Extensions getDefaultExtensions Text t)) (.~~) :: Monoid s => ASetter s t a b -> b -> t ASetter s t a b r .~~ :: forall s t a b. Monoid s => ASetter s t a b -> b -> t .~~ b x = ASetter s t a b -> b -> s -> t forall s t a b. ASetter s t a b -> b -> s -> t set ASetter s t a b r b x s forall a. Monoid a => a mempty infixr 4 .~~