{-# LANGUAGE OverloadedStrings #-}
module Text.Pandoc.App.FormatHeuristics
( formatFromFilePaths
) where
import Data.Char (toLower)
import Data.Foldable (asum)
import Data.Text (Text)
import System.FilePath (takeExtension)
formatFromFilePaths :: [FilePath] -> Maybe Text
formatFromFilePaths :: [FilePath] -> Maybe Text
formatFromFilePaths = [Maybe Text] -> Maybe Text
forall (t :: * -> *) (f :: * -> *) a.
(Foldable t, Alternative f) =>
t (f a) -> f a
asum ([Maybe Text] -> Maybe Text)
-> ([FilePath] -> [Maybe Text]) -> [FilePath] -> Maybe Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FilePath -> Maybe Text) -> [FilePath] -> [Maybe Text]
forall a b. (a -> b) -> [a] -> [b]
map FilePath -> Maybe Text
formatFromFilePath
formatFromFilePath :: FilePath -> Maybe Text
formatFromFilePath :: FilePath -> Maybe Text
formatFromFilePath FilePath
x =
case FilePath -> FilePath
takeExtension ((Char -> Char) -> FilePath -> FilePath
forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
toLower FilePath
x) of
FilePath
".adoc" -> Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"asciidoc"
FilePath
".asciidoc" -> Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"asciidoc"
FilePath
".context" -> Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"context"
FilePath
".ctx" -> Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"context"
FilePath
".db" -> Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"docbook"
FilePath
".doc" -> Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"doc"
FilePath
".docx" -> Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"docx"
FilePath
".dokuwiki" -> Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"dokuwiki"
FilePath
".epub" -> Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"epub"
FilePath
".fb2" -> Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"fb2"
FilePath
".htm" -> Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"html"
FilePath
".html" -> Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"html"
FilePath
".icml" -> Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"icml"
FilePath
".json" -> Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"json"
FilePath
".latex" -> Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"latex"
FilePath
".lhs" -> Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"markdown+lhs"
FilePath
".ltx" -> Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"latex"
FilePath
".markdown" -> Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"markdown"
FilePath
".mkdn" -> Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"markdown"
FilePath
".mkd" -> Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"markdown"
FilePath
".mdwn" -> Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"markdown"
FilePath
".mdown" -> Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"markdown"
FilePath
".Rmd" -> Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"markdown"
FilePath
".md" -> Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"markdown"
FilePath
".ms" -> Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"ms"
FilePath
".muse" -> Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"muse"
FilePath
".native" -> Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"native"
FilePath
".odt" -> Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"odt"
FilePath
".opml" -> Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"opml"
FilePath
".org" -> Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"org"
FilePath
".pdf" -> Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"pdf"
FilePath
".pptx" -> Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"pptx"
FilePath
".roff" -> Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"ms"
FilePath
".rst" -> Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"rst"
FilePath
".rtf" -> Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"rtf"
FilePath
".s5" -> Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"s5"
FilePath
".t2t" -> Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"t2t"
FilePath
".tei" -> Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"tei"
FilePath
".tei.xml" -> Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"tei"
FilePath
".tex" -> Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"latex"
FilePath
".texi" -> Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"texinfo"
FilePath
".texinfo" -> Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"texinfo"
FilePath
".text" -> Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"markdown"
FilePath
".textile" -> Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"textile"
FilePath
".txt" -> Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"markdown"
FilePath
".wiki" -> Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"mediawiki"
FilePath
".xhtml" -> Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"html"
FilePath
".ipynb" -> Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"ipynb"
FilePath
".csv" -> Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"csv"
FilePath
".bib" -> Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"biblatex"
[Char
'.',Char
y] | Char
y Char -> FilePath -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Char
'1'..Char
'9'] -> Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"man"
FilePath
_ -> Maybe Text
forall a. Maybe a
Nothing