{-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE CPP #-} module Text.Hamlet.Parse ( Result (..) , Content (..) , Doc (..) , parseDoc , HamletSettings (..) , defaultHamletSettings , xhtmlHamletSettings , debugHamletSettings , CloseStyle (..) #if HAMLET6TO7 , parseLines , Line (..) #endif ) where import Text.Shakespeare import Control.Applicative ((<$>), Applicative (..)) import Control.Monad import Control.Arrow import Data.Data import Data.List (intercalate) import Text.ParserCombinators.Parsec hiding (Line) import Data.Set (Set) import qualified Data.Set as Set data Result v = Error String | Ok v deriving (Show, Eq, Read, Data, Typeable) instance Monad Result where return = Ok Error s >>= _ = Error s Ok v >>= f = f v fail = Error instance Functor Result where fmap = liftM instance Applicative Result where pure = return (<*>) = ap data Content = ContentRaw String | ContentVar Deref | ContentUrl Bool Deref -- ^ bool: does it include params? | ContentEmbed Deref deriving (Show, Eq, Read, Data, Typeable) data Line = LineForall Deref Ident | LineIf Deref | LineElseIf Deref | LineElse | LineMaybe Deref Ident | LineNothing | LineTag { _lineTagName :: String , _lineAttr :: [(Maybe Deref, String, [Content])] , _lineContent :: [Content] , _lineClasses :: [[Content]] } | LineContent [Content] deriving (Eq, Show, Read) parseLines :: HamletSettings -> String -> Result [(Int, Line)] parseLines set s = case parse (many $ parseLine set) s s of Left e -> Error $ show e Right x -> Ok x parseLine :: HamletSettings -> Parser (Int, Line) parseLine set = do ss <- fmap sum $ many ((char ' ' >> return 1) <|> (char '\t' >> return 4)) x <- doctype <|> comment <|> htmlComment <|> backslash <|> controlIf <|> controlElseIf <|> (try (string "$else") >> many (oneOf " \t") >> eol >> return LineElse) <|> controlMaybe <|> (try (string "$nothing") >> many (oneOf " \t") >> eol >> return LineNothing) <|> controlForall <|> angle <|> (eol' >> return (LineContent [])) <|> (do cs <- content InContent isEof <- (eof >> return True) <|> return False if null cs && ss == 0 && isEof then fail "End of Hamlet template" else return $ LineContent cs) return (ss, x) where eol' = (char '\n' >> return ()) <|> (string "\r\n" >> return ()) eol = eof <|> eol' doctype = do try $ string "!!!" >> eol return $ LineContent [ContentRaw $ hamletDoctype set ++ "\n"] comment = do _ <- try $ string "$#" _ <- many $ noneOf "\r\n" eol return $ LineContent [] htmlComment = do _ <- try $ string "