{-# LANGUAGE OverloadedStrings #-}
module Text.Pandoc.Readers.Org.Shared
( cleanLinkText
, isImageFilename
, originalLang
, translateLang
, exportsCode
) where
import Data.Char (isAlphaNum)
import Data.Text (Text)
import qualified Data.Text as T
import System.FilePath (isValid, takeExtension)
import Text.Pandoc.Shared (elemText)
isImageFilename :: Text -> Bool
isImageFilename :: Text -> Bool
isImageFilename Text
fp = Bool
hasImageExtension Bool -> Bool -> Bool
&& (FilePath -> Bool
isValid (Text -> FilePath
T.unpack Text
fp) Bool -> Bool -> Bool
|| Bool
isKnownProtocolUri)
where
hasImageExtension :: Bool
hasImageExtension = FilePath -> FilePath
takeExtension (Text -> FilePath
T.unpack (Text -> FilePath) -> Text -> FilePath
forall a b. (a -> b) -> a -> b
$ Text -> Text
T.toLower Text
fp)
FilePath -> [FilePath] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [FilePath]
imageExtensions
isKnownProtocolUri :: Bool
isKnownProtocolUri = (Text -> Bool) -> [Text] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (\Text
x -> (Text
x Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"://") Text -> Text -> Bool
`T.isPrefixOf` Text
fp) [Text]
protocols
imageExtensions :: [FilePath]
imageExtensions = [ FilePath
".jpeg", FilePath
".jpg", FilePath
".png", FilePath
".gif", FilePath
".svg" ]
protocols :: [Text]
protocols = [ Text
"file", Text
"http", Text
"https" ]
cleanLinkText :: Text -> Maybe Text
cleanLinkText :: Text -> Maybe Text
cleanLinkText Text
s
| Just Text
_ <- Text -> Text -> Maybe Text
T.stripPrefix Text
"/" Text
s = Text -> Maybe Text
forall a. a -> Maybe a
Just (Text -> Maybe Text) -> Text -> Maybe Text
forall a b. (a -> b) -> a -> b
$ Text
"file://" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
s
| Just Text
_ <- Text -> Text -> Maybe Text
T.stripPrefix Text
"./" Text
s = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
s
| Just Text
_ <- Text -> Text -> Maybe Text
T.stripPrefix Text
"../" Text
s = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
s
| Just Text
s' <- Text -> Text -> Maybe Text
T.stripPrefix Text
"file:" Text
s = Text -> Maybe Text
forall a. a -> Maybe a
Just (Text -> Maybe Text) -> Text -> Maybe Text
forall a b. (a -> b) -> a -> b
$ if Text
"//" Text -> Text -> Bool
`T.isPrefixOf` Text
s' then Text
s else Text
s'
| Bool
otherwise = if Text -> Bool
isUrl Text
s then Text -> Maybe Text
forall a. a -> Maybe a
Just Text
s else Maybe Text
forall a. Maybe a
Nothing
where
isUrl :: Text -> Bool
isUrl :: Text -> Bool
isUrl Text
cs =
let (Text
scheme, Text
path) = (Char -> Bool) -> Text -> (Text, Text)
T.break (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
':') Text
cs
in (Char -> Bool) -> Text -> Bool
T.all (\Char
c -> Char -> Bool
isAlphaNum Char
c Bool -> Bool -> Bool
|| Char
c Char -> Text -> Bool
`elemText` Text
".-") Text
scheme
Bool -> Bool -> Bool
&& Bool -> Bool
not (Text -> Bool
T.null Text
path)
originalLang :: Text -> [(Text, Text)]
originalLang :: Text -> [(Text, Text)]
originalLang Text
lang =
let transLang :: Text
transLang = Text -> Text
translateLang Text
lang
in [(Text
"org-language", Text
lang) | Text
transLang Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
/= Text
lang]
translateLang :: Text -> Text
translateLang :: Text -> Text
translateLang Text
cs =
case Text
cs of
Text
"C" -> Text
"c"
Text
"C++" -> Text
"cpp"
Text
"emacs-lisp" -> Text
"commonlisp"
Text
"js" -> Text
"javascript"
Text
"lisp" -> Text
"commonlisp"
Text
"R" -> Text
"r"
Text
"sh" -> Text
"bash"
Text
"sqlite" -> Text
"sql"
Text
_ -> Text
cs
exportsCode :: [(Text, Text)] -> Bool
exportsCode :: [(Text, Text)] -> Bool
exportsCode = Bool -> (Text -> Bool) -> Maybe Text -> Bool
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Bool
True (Text -> [Text] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text
"code", Text
"both"]) (Maybe Text -> Bool)
-> ([(Text, Text)] -> Maybe Text) -> [(Text, Text)] -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [(Text, Text)] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"exports"