aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc')
-rw-r--r--src/Text/Pandoc/App.hs58
-rw-r--r--src/Text/Pandoc/App/FormatHeuristics.hs94
-rw-r--r--src/Text/Pandoc/App/OutputSettings.hs52
-rw-r--r--src/Text/Pandoc/Writers/Texinfo.hs3
4 files changed, 102 insertions, 105 deletions
diff --git a/src/Text/Pandoc/App.hs b/src/Text/Pandoc/App.hs
index 809165c2e..a14e4e017 100644
--- a/src/Text/Pandoc/App.hs
+++ b/src/Text/Pandoc/App.hs
@@ -62,6 +62,7 @@ import System.FilePath
import System.IO (nativeNewline, stdout)
import qualified System.IO as IO (Newline (..))
import Text.Pandoc
+import Text.Pandoc.App.FormatHeuristics (formatFromFilePaths)
import Text.Pandoc.App.Opt (Opt (..), LineEnding (..), defaultOpts)
import Text.Pandoc.App.CommandLineOptions (parseOptions, options)
import Text.Pandoc.App.OutputSettings (OutputSettings (..), optToOutputSettings)
@@ -337,63 +338,6 @@ readMetaValue s = case YAML.decodeStrict (UTF8.fromString s) of
-> MetaBool b
_ -> MetaString s
--- Determine default reader based on source file extensions.
-formatFromFilePaths :: String -> [FilePath] -> String
-formatFromFilePaths fallback [] = fallback
-formatFromFilePaths fallback (x:xs) =
- case formatFromFilePath x of
- Just f -> f
- Nothing -> formatFromFilePaths fallback xs
-
--- Determine format based on file extension
-formatFromFilePath :: FilePath -> Maybe String
-formatFromFilePath x =
- case takeExtension (map toLower x) of
- ".adoc" -> Just "asciidoc"
- ".asciidoc" -> Just "asciidoc"
- ".context" -> Just "context"
- ".ctx" -> Just "context"
- ".db" -> Just "docbook"
- ".doc" -> Just "doc" -- so we get an "unknown reader" error
- ".docx" -> Just "docx"
- ".dokuwiki" -> Just "dokuwiki"
- ".epub" -> Just "epub"
- ".fb2" -> Just "fb2"
- ".htm" -> Just "html"
- ".html" -> Just "html"
- ".icml" -> Just "icml"
- ".json" -> Just "json"
- ".latex" -> Just "latex"
- ".lhs" -> Just "markdown+lhs"
- ".ltx" -> Just "latex"
- ".markdown" -> Just "markdown"
- ".md" -> Just "markdown"
- ".ms" -> Just "ms"
- ".muse" -> Just "muse"
- ".native" -> Just "native"
- ".odt" -> Just "odt"
- ".opml" -> Just "opml"
- ".org" -> Just "org"
- ".pdf" -> Just "pdf" -- so we get an "unknown reader" error
- ".pptx" -> Just "pptx"
- ".roff" -> Just "ms"
- ".rst" -> Just "rst"
- ".rtf" -> Just "rtf"
- ".s5" -> Just "s5"
- ".t2t" -> Just "t2t"
- ".tei" -> Just "tei"
- ".tei.xml" -> Just "tei"
- ".tex" -> Just "latex"
- ".texi" -> Just "texinfo"
- ".texinfo" -> Just "texinfo"
- ".text" -> Just "markdown"
- ".textile" -> Just "textile"
- ".txt" -> Just "markdown"
- ".wiki" -> Just "mediawiki"
- ".xhtml" -> Just "html"
- ['.',y] | y `elem` ['1'..'9'] -> Just "man"
- _ -> Nothing
-
-- Transformations of a Pandoc document post-parsing:
applyTransforms :: Monad m => [Transform] -> Pandoc -> m Pandoc
diff --git a/src/Text/Pandoc/App/FormatHeuristics.hs b/src/Text/Pandoc/App/FormatHeuristics.hs
new file mode 100644
index 000000000..c8dbcd645
--- /dev/null
+++ b/src/Text/Pandoc/App/FormatHeuristics.hs
@@ -0,0 +1,94 @@
+{-# LANGUAGE NoImplicitPrelude #-}
+{-
+Copyright (C) 2006-2018 John MacFarlane <jgm@berkeley.edu>
+
+This program is free software; you can redistribute it and/or modify
+it under the terms of the GNU General Public License as published by
+the Free Software Foundation; either version 2 of the License, or
+(at your option) any later version.
+
+This program is distributed in the hope that it will be useful,
+but WITHOUT ANY WARRANTY; without even the implied warranty of
+MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
+GNU General Public License for more details.
+
+You should have received a copy of the GNU General Public License
+along with this program; if not, write to the Free Software
+Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
+-}
+
+{- |
+ Module : Text.Pandoc.App.FormatHeuristics
+ Copyright : Copyright (C) 2006-2018 John MacFarlane
+ License : GNU GPL, version 2 or above
+
+ Maintainer : John MacFarlane <jgm@berkeley@edu>
+ Stability : alpha
+ Portability : portable
+
+Guess the format of a file from its name.
+-}
+module Text.Pandoc.App.FormatHeuristics
+ ( formatFromFilePaths
+ ) where
+
+import Prelude
+import Data.Char (toLower)
+import System.FilePath (takeExtension)
+
+-- Determine default reader based on source file extensions.
+formatFromFilePaths :: String -> [FilePath] -> String
+formatFromFilePaths fallback [] = fallback
+formatFromFilePaths fallback (x:xs) =
+ case formatFromFilePath x of
+ Just f -> f
+ Nothing -> formatFromFilePaths fallback xs
+
+-- Determine format based on file extension
+formatFromFilePath :: FilePath -> Maybe String
+formatFromFilePath x =
+ case takeExtension (map toLower x) of
+ ".adoc" -> Just "asciidoc"
+ ".asciidoc" -> Just "asciidoc"
+ ".context" -> Just "context"
+ ".ctx" -> Just "context"
+ ".db" -> Just "docbook"
+ ".doc" -> Just "doc" -- so we get an "unknown reader" error
+ ".docx" -> Just "docx"
+ ".dokuwiki" -> Just "dokuwiki"
+ ".epub" -> Just "epub"
+ ".fb2" -> Just "fb2"
+ ".htm" -> Just "html"
+ ".html" -> Just "html"
+ ".icml" -> Just "icml"
+ ".json" -> Just "json"
+ ".latex" -> Just "latex"
+ ".lhs" -> Just "markdown+lhs"
+ ".ltx" -> Just "latex"
+ ".markdown" -> Just "markdown"
+ ".md" -> Just "markdown"
+ ".ms" -> Just "ms"
+ ".muse" -> Just "muse"
+ ".native" -> Just "native"
+ ".odt" -> Just "odt"
+ ".opml" -> Just "opml"
+ ".org" -> Just "org"
+ ".pdf" -> Just "pdf" -- so we get an "unknown reader" error
+ ".pptx" -> Just "pptx"
+ ".roff" -> Just "ms"
+ ".rst" -> Just "rst"
+ ".rtf" -> Just "rtf"
+ ".s5" -> Just "s5"
+ ".t2t" -> Just "t2t"
+ ".tei" -> Just "tei"
+ ".tei.xml" -> Just "tei"
+ ".tex" -> Just "latex"
+ ".texi" -> Just "texinfo"
+ ".texinfo" -> Just "texinfo"
+ ".text" -> Just "markdown"
+ ".textile" -> Just "textile"
+ ".txt" -> Just "markdown"
+ ".wiki" -> Just "mediawiki"
+ ".xhtml" -> Just "html"
+ ['.',y] | y `elem` ['1'..'9'] -> Just "man"
+ _ -> Nothing
diff --git a/src/Text/Pandoc/App/OutputSettings.hs b/src/Text/Pandoc/App/OutputSettings.hs
index 654e240d4..3788af7bf 100644
--- a/src/Text/Pandoc/App/OutputSettings.hs
+++ b/src/Text/Pandoc/App/OutputSettings.hs
@@ -50,6 +50,7 @@ import System.Exit (exitSuccess)
import System.FilePath
import System.IO (stdout)
import Text.Pandoc
+import Text.Pandoc.App.FormatHeuristics (formatFromFilePaths)
import Text.Pandoc.App.Opt (Opt (..))
import Text.Pandoc.App.CommandLineOptions (engines)
import Text.Pandoc.BCP47 (Lang (..), parseBCP47)
@@ -81,14 +82,14 @@ optToOutputSettings opts = do
Nothing -> return Nothing
Just fp -> Just <$> readUtf8File fp
- let nonPdfWriterName Nothing = defaultWriterName outputFile
- nonPdfWriterName (Just x) = x
-
let pdfOutput = map toLower (takeExtension outputFile) == ".pdf"
(writerName, maybePdfProg) <-
if pdfOutput
then liftIO $ pdfWriterAndProg (optWriter opts) (optPdfEngine opts)
- else return (nonPdfWriterName $ optWriter opts, Nothing)
+ else case optWriter opts of
+ Nothing ->
+ return (formatFromFilePaths "html" [outputFile], Nothing)
+ Just f -> return (f, Nothing)
let format = map toLower $ baseWriterName
$ takeFileName writerName -- in case path to lua script
@@ -232,49 +233,6 @@ optToOutputSettings opts = do
, outputPdfProgram = maybePdfProg
}
--- Determine default writer based on output file extension
-defaultWriterName :: FilePath -> String
-defaultWriterName "-" = "html" -- no output file
-defaultWriterName x =
- case takeExtension (map toLower x) of
- "" -> "markdown" -- empty extension
- ".tex" -> "latex"
- ".latex" -> "latex"
- ".ltx" -> "latex"
- ".context" -> "context"
- ".ctx" -> "context"
- ".rtf" -> "rtf"
- ".rst" -> "rst"
- ".s5" -> "s5"
- ".native" -> "native"
- ".json" -> "json"
- ".txt" -> "markdown"
- ".text" -> "markdown"
- ".md" -> "markdown"
- ".muse" -> "muse"
- ".markdown" -> "markdown"
- ".textile" -> "textile"
- ".lhs" -> "markdown+lhs"
- ".texi" -> "texinfo"
- ".texinfo" -> "texinfo"
- ".db" -> "docbook"
- ".odt" -> "odt"
- ".docx" -> "docx"
- ".epub" -> "epub"
- ".org" -> "org"
- ".asciidoc" -> "asciidoc"
- ".adoc" -> "asciidoc"
- ".fb2" -> "fb2"
- ".opml" -> "opml"
- ".icml" -> "icml"
- ".tei.xml" -> "tei"
- ".tei" -> "tei"
- ".ms" -> "ms"
- ".roff" -> "ms"
- ".pptx" -> "pptx"
- ['.',y] | y `elem` ['1'..'9'] -> "man"
- _ -> "html"
-
baseWriterName :: String -> String
baseWriterName = takeWhile (\c -> c /= '+' && c /= '-')
diff --git a/src/Text/Pandoc/Writers/Texinfo.hs b/src/Text/Pandoc/Writers/Texinfo.hs
index 21d1f4eca..4a4dde461 100644
--- a/src/Text/Pandoc/Writers/Texinfo.hs
+++ b/src/Text/Pandoc/Writers/Texinfo.hs
@@ -328,7 +328,8 @@ blockListToTexinfo (x:xs) = do
lines' <- mapM makeMenuLine menu
let menu' = if null lines'
then empty
- else text "@menu" $$
+ else blankline $$
+ text "@menu" $$
vcat lines' $$
text "@end menu"
after' <- blockListToTexinfo after