{-# LANGUAGE CPP #-}
module Network.Gitit.Page ( stringToPage
, pageToString
, readCategories
)
where
import Network.Gitit.Types
import Network.Gitit.Util (trim, splitCategories, parsePageType)
import Text.ParserCombinators.Parsec
import Data.Char (toLower)
import Data.List (intercalate)
import Data.Maybe (fromMaybe)
import Data.ByteString.UTF8 (toString)
import qualified Data.ByteString as B
import qualified Data.ByteString.Char8 as BC
import System.IO (withFile, Handle, IOMode(..))
import qualified Control.Exception as E
import System.IO.Error (isEOFError)
parseMetadata :: String -> ([(String, String)], String)
parseMetadata raw =
case parse pMetadataBlock "" raw of
Left _ -> ([], raw)
Right (ls, rest) -> (ls, rest)
pMetadataBlock :: GenParser Char st ([(String, String)], String)
pMetadataBlock = try $ do
_ <- string "---"
_ <- pBlankline
ls <- manyTill pMetadataLine pMetaEnd
skipMany pBlankline
rest <- getInput
return (ls, rest)
pMetaEnd :: GenParser Char st Char
pMetaEnd = try $ do
string "..." <|> string "---"
pBlankline
pBlankline :: GenParser Char st Char
pBlankline = try $ many (oneOf " \t") >> newline
pMetadataLine :: GenParser Char st (String, String)
pMetadataLine = try $ do
first <- letter
rest <- many (letter <|> digit <|> oneOf "-_")
let ident = first:rest
skipMany (oneOf " \t")
_ <- char ':'
rawval <- many $ noneOf "\n\r"
<|> (try $ newline >> notFollowedBy pBlankline >>
skipMany1 (oneOf " \t") >> return ' ')
_ <- newline
return (ident, trim rawval)
stringToPage :: Config -> String -> String -> Page
stringToPage conf pagename raw =
let (ls, rest) = parseMetadata raw
page' = Page { pageName = pagename
, pageFormat = defaultPageType conf
, pageLHS = defaultLHS conf
, pageTOC = tableOfContents conf
, pageTitle = pagename
, pageCategories = []
, pageText = filter (/= '\r') rest
, pageMeta = ls }
in foldr adjustPage page' ls
adjustPage :: (String, String) -> Page -> Page
adjustPage ("title", val) page' = page' { pageTitle = val }
adjustPage ("format", val) page' = page' { pageFormat = pt, pageLHS = lhs }
where (pt, lhs) = parsePageType val
adjustPage ("toc", val) page' = page' {
pageTOC = map toLower val `elem` ["yes","true"] }
adjustPage ("categories", val) page' =
page' { pageCategories = splitCategories val ++ pageCategories page' }
adjustPage (_, _) page' = page'
pageToString :: Config -> Page -> String
pageToString conf page' =
let pagename = pageName page'
pagetitle = pageTitle page'
pageformat = pageFormat page'
pagelhs = pageLHS page'
pagetoc = pageTOC page'
pagecats = pageCategories page'
metadata = filter
(\(k, _) -> not (k `elem`
["title", "format", "toc", "categories"]))
(pageMeta page')
metadata' = (if pagename /= pagetitle
then "title: " ++ pagetitle ++ "\n"
else "") ++
(if pageformat /= defaultPageType conf ||
pagelhs /= defaultLHS conf
then "format: " ++
map toLower (show pageformat) ++
if pagelhs then "+lhs\n" else "\n"
else "") ++
(if pagetoc /= tableOfContents conf
then "toc: " ++
(if pagetoc then "yes" else "no") ++ "\n"
else "") ++
(if not (null pagecats)
then "categories: " ++ intercalate ", " pagecats ++ "\n"
else "") ++
(unlines (map (\(k, v) -> k ++ ": " ++ v) metadata))
in (if null metadata' then "" else "---\n" ++ metadata' ++ "...\n\n")
++ pageText page'
readCategories :: FilePath -> IO [String]
readCategories f =
withFile f ReadMode $ \h ->
E.catch (do fl <- B.hGetLine h
if dashline fl
then do
rest <- hGetLinesTill h dotOrDashline
let (md,_) = parseMetadata $ unlines $ "---":rest
return $ splitCategories $ fromMaybe ""
$ lookup "categories" md
else return [])
(\e -> if isEOFError e then return [] else E.throwIO e)
dashline :: B.ByteString -> Bool
dashline x =
case BC.unpack x of
('-':'-':'-':xs) | all (==' ') xs -> True
_ -> False
dotOrDashline :: B.ByteString -> Bool
dotOrDashline x =
case BC.unpack x of
('-':'-':'-':xs) | all (==' ') xs -> True
('.':'.':'.':xs) | all (==' ') xs -> True
_ -> False
hGetLinesTill :: Handle -> (B.ByteString -> Bool) -> IO [String]
hGetLinesTill h end = do
next <- B.hGetLine h
if end next
then return [toString next]
else do
rest <- hGetLinesTill h end
return (toString next:rest)