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