-- taken from https://github.com/jaspervdj/blaze-html/blob/2c4513e30ce768517b8d7b7b154d438f55217006/src/Util/GenerateHtmlCombinators.hs -- Copyright Jasper Van der Jeugt 2010 -- All rights reserved. -- Redistribution and use in source and binary forms, with or without -- modification, are permitted provided that the following conditions are met: -- * Redistributions of source code must retain the above copyright -- notice, this list of conditions and the following disclaimer. -- * Redistributions in binary form must reproduce the above -- copyright notice, this list of conditions and the following -- disclaimer in the documentation and/or other materials provided -- with the distribution. -- * Neither the name of Jasper Van der Jeugt nor the names of other -- contributors may be used to endorse or promote products derived -- from this software without specific prior written permission. -- THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS -- "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT -- LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR -- A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT -- OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, -- SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT -- LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, -- DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY -- THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT -- (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE -- OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. {-# LANGUAGE CPP #-} #define DO_NOT_EDIT (doNotEdit __FILE__ __LINE__) -- | Generates code for HTML tags. -- module Util.GenerateHtmlCombinators where import Control.Arrow ((&&&)) import Data.List (sort, sortBy, intersperse, intercalate) import Data.Ord (comparing) import System.Directory (createDirectoryIfMissing) import System.FilePath ((>), (<.>)) import Data.Map (Map) import qualified Data.Map as M import Data.Char (toLower) import qualified Data.Set as S import Util.Sanitize (sanitize, prelude) -- | Datatype for an HTML variant. -- data HtmlVariant = HtmlVariant { version :: [String] , docType :: [String] , parents :: [String] , leafs :: [String] , attributes :: [String] , selfClosing :: Bool } deriving (Eq) instance Show HtmlVariant where show = map toLower . intercalate "-" . version -- | Get the full module name for an HTML variant. -- getModuleName :: HtmlVariant -> String getModuleName = ("Text.Blaze." ++) . intercalate "." . version -- | Get the attribute module name for an HTML variant. -- getAttributeModuleName :: HtmlVariant -> String getAttributeModuleName = (++ ".Attributes") . getModuleName -- | Check if a given name causes a name clash. -- isNameClash :: HtmlVariant -> String -> Bool isNameClash v t -- Both an element and an attribute | (t `elem` parents v || t `elem` leafs v) && t `elem` attributes v = True -- Already a prelude function | sanitize t `S.member` prelude = True | otherwise = False -- | Write an HTML variant. -- writeHtmlVariant :: HtmlVariant -> IO () writeHtmlVariant htmlVariant = do -- Make a directory. createDirectoryIfMissing True basePath let tags = zip parents' (repeat makeParent) ++ zip leafs' (repeat (makeLeaf $ selfClosing htmlVariant)) sortedTags = sortBy (comparing fst) tags appliedTags = map (\(x, f) -> f x) sortedTags -- Write the main module. writeFile' (basePath <.> "hs") $ removeTrailingNewlines $ unlines [ DO_NOT_EDIT , "{-# LANGUAGE OverloadedStrings #-}" , "-- | This module exports HTML combinators used to create documents." , "--" , exportList modulName $ "module Text.Blaze.Html" : "docType" : "docTypeHtml" : map (sanitize . fst) sortedTags , DO_NOT_EDIT , "import Prelude ((>>), (.))" , "" , "import Text.Blaze" , "import Text.Blaze.Internal" , "import Text.Blaze.Html" , "" , makeDocType $ docType htmlVariant , makeDocTypeHtml $ docType htmlVariant , unlines appliedTags ] let sortedAttributes = sort attributes' -- Write the attribute module. writeFile' (basePath > "Attributes.hs") $ removeTrailingNewlines $ unlines [ DO_NOT_EDIT , "-- | This module exports combinators that provide you with the" , "-- ability to set attributes on HTML elements." , "--" , "{-# LANGUAGE OverloadedStrings #-}" , exportList attributeModuleName $ map sanitize sortedAttributes , DO_NOT_EDIT , "import Prelude ()" , "" , "import Text.Blaze.Internal (Attribute, AttributeValue, attribute)" , "" , unlines (map makeAttribute sortedAttributes) ] where basePath = "src" > "Text" > "Blaze" > foldl1 (>) version' modulName = getModuleName htmlVariant attributeModuleName = getAttributeModuleName htmlVariant attributes' = attributes htmlVariant parents' = parents htmlVariant leafs' = leafs htmlVariant version' = version htmlVariant removeTrailingNewlines = reverse . drop 2 . reverse writeFile' file content = do putStrLn ("Generating " ++ file) writeFile file content -- | Create a string, consisting of @x@ spaces, where @x@ is the length of the -- argument. -- spaces :: String -> String spaces = flip replicate ' ' . length -- | Join blocks of code with a newline in between. -- unblocks :: [String] -> String unblocks = unlines . intersperse "\n" -- | A warning to not edit the generated code. -- doNotEdit :: FilePath -> Int -> String doNotEdit fileName lineNumber = init $ unlines [ "-- WARNING: The next block of code was automatically generated by" , "-- " ++ fileName ++ ":" ++ show lineNumber , "--" ] -- | Generate an export list for a Haskell module. -- exportList :: String -- ^ Module name. -> [String] -- ^ List of functions. -> String -- ^ Resulting string. exportList _ [] = error "exportList without functions." exportList name (f:functions) = unlines $ [ "module " ++ name , " ( " ++ f ] ++ map (" , " ++) functions ++ [ " ) where"] -- | Generate a function for a doctype. -- makeDocType :: [String] -> String makeDocType lines' = unlines [ DO_NOT_EDIT , "-- | Combinator for the document type. This should be placed at the top" , "-- of every HTML page." , "--" , "-- Example:" , "--" , "-- > docType" , "--" , "-- Result:" , "--" , unlines (map ("-- > " ++) lines') ++ "--" , "docType :: Html -- ^ The document type HTML." , "docType = preEscapedText " ++ show (unlines lines') , "{-# INLINE docType #-}" ] -- | Generate a function for the HTML tag (including the doctype). -- makeDocTypeHtml :: [String] -- ^ The doctype. -> String -- ^ Resulting combinator function. makeDocTypeHtml lines' = unlines [ DO_NOT_EDIT , "-- | Combinator for the @\\@ element. This combinator will also" , "-- insert the correct doctype." , "--" , "-- Example:" , "--" , "-- > docTypeHtml $ span $ toHtml \"foo\"" , "--" , "-- Result:" , "--" , unlines (map ("-- > " ++) lines') ++ "-- > foo" , "--" , "docTypeHtml :: Html -- ^ Inner HTML." , " -> Html -- ^ Resulting HTML." , "docTypeHtml inner = docType >> html inner" , "{-# INLINE docTypeHtml #-}" ] -- | Generate a function for an HTML tag that can be a parent. -- makeParent :: String -> String makeParent tag = unlines [ DO_NOT_EDIT , "-- | Combinator for the @\\<" ++ tag ++ ">@ element." , "--" , "-- Example:" , "--" , "-- > " ++ function ++ " $ span $ toHtml \"foo\"" , "--" , "-- Result:" , "--" , "-- > <" ++ tag ++ ">foo" ++ tag ++ ">" , "--" , function ++ " :: Html -- ^ Inner HTML." , spaces function ++ " -> Html -- ^ Resulting HTML." , function ++ " = Parent \"" ++ tag ++ "\" \"<" ++ tag ++ "\" \"" ++ tag ++ ">\"" ++ modifier , "{-# INLINE " ++ function ++ " #-}" ] where function = sanitize tag modifier = if tag `elem` ["style", "script"] then " . external" else "" -- | Generate a function for an HTML tag that must be a leaf. -- makeLeaf :: Bool -- ^ Make leaf tags self-closing -> String -- ^ Tag for the combinator -> String -- ^ Combinator code makeLeaf closing tag = unlines [ DO_NOT_EDIT , "-- | Combinator for the @\\<" ++ tag ++ " />@ element." , "--" , "-- Example:" , "--" , "-- > " ++ function , "--" , "-- Result:" , "--" , "-- > <" ++ tag ++ " />" , "--" , function ++ " :: Html -- ^ Resulting HTML." , function ++ " = Leaf \"" ++ tag ++ "\" \"<" ++ tag ++ "\" " ++ "\"" ++ (if closing then " /" else "") ++ ">\"" , "{-# INLINE " ++ function ++ " #-}" ] where function = sanitize tag -- | Generate a function for an HTML attribute. -- makeAttribute :: String -> String makeAttribute name = unlines [ DO_NOT_EDIT , "-- | Combinator for the @" ++ name ++ "@ attribute." , "--" , "-- Example:" , "--" , "-- > div ! " ++ function ++ " \"bar\" $ \"Hello.\"" , "--" , "-- Result:" , "--" , "-- >