@@ -49,10 +49,10 @@ import System.IO (nativeNewline, stdout)
4949import qualified System.IO as IO (Newline (.. ))
5050import Text.Pandoc
5151import Text.Pandoc.Builder (setMeta )
52+ import qualified Text.Pandoc.Format.Input as Input
5253import Text.Pandoc.MediaBag (mediaItems )
5354import Text.Pandoc.MIME (getCharset , MimeType )
5455import Text.Pandoc.Image (svgToPng )
55- import Text.Pandoc.App.FormatHeuristics (formatFromFilePaths )
5656import Text.Pandoc.App.Opt (Opt (.. ), LineEnding (.. ), defaultOpts ,
5757 IpynbOutput (.. ))
5858import Text.Pandoc.App.CommandLineOptions (parseOptions , parseOptionsFromArgs ,
@@ -116,18 +116,19 @@ convertWithOpts opts = do
116116 setOutputFile (optOutputFile opts)
117117
118118 -- assign reader and writer based on options and filenames
119- readerName <- case optFrom opts of
120- Just f -> return f
121- Nothing -> case formatFromFilePaths sources of
122- Just f' -> return f'
123- Nothing | sources == [" -" ] -> return " markdown"
124- | any (isURI . T. pack) sources -> return " html"
125- | otherwise -> do
126- report $ CouldNotDeduceFormat
127- (map (T. pack . takeExtension) sources) " markdown"
128- return " markdown"
129-
130- let readerNameBase = T. takeWhile (\ c -> c /= ' +' && c /= ' -' ) readerName
119+ readerFormat <- case optFrom opts of
120+ Just spec -> Input. flavoredFromSpec spec
121+ Nothing ->
122+ let defFlavor = return . Input. defaultFlavor
123+ in case Input. flavoredFormatFromFilePaths sources of
124+ Just f' -> return f'
125+ Nothing
126+ | sources == [" -" ] -> defFlavor Input. Markdown
127+ | any (isURI . T. pack) sources -> defFlavor Input. HTML
128+ | otherwise -> do
129+ report $ CouldNotDeduceFormat
130+ (map (T. pack . takeExtension) sources) " markdown"
131+ defFlavor Input. Markdown
131132
132133 let makeSandboxed pureReader =
133134 let files = maybe id (:) (optReferenceDoc opts) .
@@ -142,14 +143,13 @@ convertWithOpts opts = do
142143 ByteStringReader r
143144 -> ByteStringReader $ \ o t -> sandbox files (r o t)
144145
145- (reader, readerExts) <-
146- if " .lua" `T.isSuffixOf` readerName
147- then return (TextReader (readCustom (T. unpack readerName)), mempty )
148- else if optSandbox opts
149- then case runPure (getReader readerName) of
150- Left e -> throwError e
151- Right (r, rexts) -> return (makeSandboxed r, rexts)
152- else getReader readerName
146+ (reader, readerExts) <- case readerFormat of
147+ Input. CustomFormat luaFilename ->
148+ return (TextReader (readCustom luaFilename), mempty )
149+ Input. KnownFormat infrmt exts -> return $
150+ if optSandbox opts
151+ then (makeSandboxed (readerForFormat infrmt), exts)
152+ else (readerForFormat infrmt, exts)
153153
154154 outputSettings <- optToOutputSettings opts
155155 let format = outputFormat outputSettings
@@ -169,7 +169,7 @@ convertWithOpts opts = do
169169 pdfOutput ||
170170 bibOutput
171171
172- when (pdfOutput && readerNameBase == " latex " ) $
172+ when (pdfOutput && readerFormat `Input.hasBase` Input. LaTeX ) $
173173 case optInputFiles opts of
174174 Just (inputFile: _) -> report $ UnusualConversion $ T. pack $
175175 " to convert a .tex file to PDF, you get better results by using pdflatex "
@@ -222,7 +222,7 @@ convertWithOpts opts = do
222222 -- If format is markdown or commonmark, use the enabled extensions,
223223 -- otherwise treat metadata as pandoc markdown (see #7926, #6832)
224224 let readerOptsMeta =
225- if readerNameBase == " markdown " || readerNameBase == " commonmark "
225+ if readerFormat `Input.hasBaseIn` [ Input. Markdown , Input. CommonMark ]
226226 then readerOpts
227227 else readerOpts{ readerExtensions = pandocExtensions }
228228 mconcat <$> mapM
@@ -243,7 +243,7 @@ convertWithOpts opts = do
243243 then (eastAsianLineBreakFilter : )
244244 else id ) .
245245 (case optIpynbOutput opts of
246- _ | readerNameBase /= " ipynb " -> id
246+ _ | not (readerFormat `Input.hasBase` Input. Ipynb ) -> id
247247 IpynbOutputAll -> id
248248 IpynbOutputNone -> (filterIpynbOutput Nothing : )
249249 IpynbOutputBest -> (filterIpynbOutput (Just $
@@ -257,14 +257,13 @@ convertWithOpts opts = do
257257 $ []
258258
259259 let convertTabs = tabFilter (if optPreserveTabs opts ||
260- readerNameBase == " t2t" ||
261- readerNameBase == " man" ||
262- readerNameBase == " tsv"
260+ readerFormat `Input.hasBaseIn`
261+ [Input. T2T , Input. Man , Input. TSV ]
263262 then 0
264263 else optTabStop opts)
265264
266265
267- when (readerNameBase == " markdown_github " ||
266+ when (readerFormat `Input.hasBase` Input. Markdown_GitHub ||
268267 writerNameBase == " markdown_github" ) $
269268 report $ Deprecated " markdown_github" " Use gfm instead."
270269
@@ -293,7 +292,7 @@ convertWithOpts opts = do
293292
294293 doc <- (case reader of
295294 TextReader r
296- | readerNameBase == " json " ->
295+ | readerFormat `Input.hasBase` Input. JSON ->
297296 mconcat <$>
298297 mapM (inputToText convertTabs
299298 >=> r readerOpts . (: [] )) inputs
0 commit comments