module Network.Gitit.Util ( readFileUTF8
, inDir
, withTempDir
, orIfNull
, splitCategories
, trim
, yesOrNo
, parsePageType
, encUrl
)
where
import System.Directory
import Control.Exception (bracket)
import System.FilePath ((</>), (<.>))
import System.IO.Error (isAlreadyExistsError)
import Control.Monad.Trans (liftIO)
import Data.Char (toLower, isAscii)
import Network.Gitit.Types
import qualified Control.Exception as E
import qualified Text.Pandoc.UTF8 as UTF8
import Network.URL (encString)
readFileUTF8 :: FilePath -> IO String
readFileUTF8 = UTF8.readFile
inDir :: FilePath -> IO a -> IO a
inDir d action = do
w <- getCurrentDirectory
setCurrentDirectory d
result <- action
setCurrentDirectory w
return result
withTempDir :: FilePath -> (FilePath -> IO a) -> IO a
withTempDir baseName f = do
oldDir <- getCurrentDirectory
bracket (createTempDir 0 baseName)
(\tmp -> setCurrentDirectory oldDir >> removeDirectoryRecursive tmp)
f
createTempDir :: Integer -> FilePath -> IO FilePath
createTempDir num baseName = do
sysTempDir <- getTemporaryDirectory
let dirName = sysTempDir </> baseName <.> show num
liftIO $ E.catch (createDirectory dirName >> return dirName) $
\e -> if isAlreadyExistsError e
then createTempDir (num + 1) baseName
else ioError e
orIfNull :: [a] -> [a] -> [a]
orIfNull lst backup = if null lst then backup else lst
splitCategories :: String -> [String]
splitCategories = words . map puncToSpace . trim
where puncToSpace x | x `elem` ".,;:" = ' '
puncToSpace x = x
trim :: String -> String
trim = reverse . trimLeft . reverse . trimLeft
where trimLeft = dropWhile (`elem` " \t")
yesOrNo :: Bool -> String
yesOrNo True = "yes"
yesOrNo False = "no"
parsePageType :: String -> (PageType, Bool)
parsePageType s =
case map toLower s of
"markdown" -> (Markdown,False)
"markdown+lhs" -> (Markdown,True)
"commonmark" -> (CommonMark,False)
"rst" -> (RST,False)
"rst+lhs" -> (RST,True)
"html" -> (HTML,False)
"textile" -> (Textile,False)
"latex" -> (LaTeX,False)
"latex+lhs" -> (LaTeX,True)
"org" -> (Org,False)
"mediawiki" -> (MediaWiki,False)
x -> error $ "Unknown page type: " ++ x
encUrl :: String -> String
encUrl = encString True isAscii