{-# LANGUAGE FlexibleInstances #-} -- | Backend base module. -- -- Defines the type of the backend and some useful functions. module BNFC.Backend.Base ( Backend , MkFiles , GeneratedFile(..) , MakeComment , execBackend , mkfile , liftIO , writeFiles ) where import Control.Arrow ( (&&&) ) import Control.Monad.Writer import Data.Char ( isSpace ) import Data.Function ( on ) import qualified Data.List as List import System.Directory ( createDirectoryIfMissing ) import System.FilePath ( dropFileName, takeExtension, () ) import BNFC.Options ( versionString ) import BNFC.PrettyPrint import BNFC.Utils ( writeFileRep ) -- | Stamp BNFC puts in the header of each generated file. msgGenerated :: String msgGenerated = "File generated by the BNF Converter (bnfc " ++ versionString ++ ")." -- | Define the type of the backend functions. For more purity, instead of -- having each backend writing the generated files to disk, they return a list -- of pairs containing the (relative) file path and the file content. This -- allow for 1) easier testing, 2) implement common options like changing the -- output dir or providing a diff instead of overwritting the files on a -- highter level and 3) more purity. -- -- The writer monad provides a more convenient API to generate the list. Note -- that we still use the `IO` monad for now because some backends insist on -- printing stuff to the screen while generating the files. type MkFiles a = WriterT [GeneratedFile] IO a type Backend = MkFiles () -- | A result file of a backend. data GeneratedFile = GeneratedFile { fileName :: FilePath -- ^ Name of the file to write. , makeComment :: MakeComment -- ^ Function to generate a comment. -- Used to prefix the file with a stamp ("Generated by BNFC"). , fileContent :: String -- ^ Content of the file to write. } -- quick-and-dirty instances for HSpec test-suite instance Show GeneratedFile where show (GeneratedFile x _ y) = unwords [ "GeneratedFile", show x, "_", show y ] instance Eq GeneratedFile where (==) = (==) `on` fileName &&& fileContent -- | Type of comment-generating functions. type MakeComment = String -> String -- | Named after execWriter, this function execute the given backend -- and returns the generated file paths and contents. execBackend :: MkFiles () -> IO [GeneratedFile] execBackend = execWriterT -- | A specialized version of `tell` that adds a file and its content to the -- list of generated files. mkfile :: FileContent c => FilePath -> MakeComment -> c -> MkFiles () mkfile path f content = tell [GeneratedFile path f (fileContentToString content)] -- | While we are moving to generating `Text.PrettyPrint.Doc` instead of `String`, -- it is nice to be able to use both as argument to 'mkfile'. -- So we do some typeclass magic. class FileContent a where fileContentToString :: a -> String instance FileContent [Char] where fileContentToString = deleteTrailingWhiteSpace instance FileContent Doc where fileContentToString = deleteTrailingWhiteSpace . render deleteTrailingWhiteSpace :: String -> String deleteTrailingWhiteSpace = unlines . map (List.dropWhileEnd isSpace) . lines -- | Write a set of files to disk. the first argument is the root directory -- inside which all the generated files will be written. This root directory -- and sub-directories will be created as needed (ex: if the files contains a -- @a\/b\/file.txt@, `writeFiles` will create the directories @$ROOT\/a@ and -- @$ROOT\/a\/b@) writeFiles :: FilePath -> MkFiles () -> IO () writeFiles root fw = do -- First we check that the directory exists. fb <- execBackend fw createDirectoryIfMissing True root forM_ fb $ \ (GeneratedFile path mkComment content) -> do createDirectoryIfMissing True (root dropFileName path) -- Then we write the files, adding the BNFC stamp as header. writeFileRep (root path) $ -- TODO: the following is a hack, make this more systematic: if takeExtension path == ".txt" then -- Sign at the end since e.g. txt2tags cannot handle comments at beginning of file. unlines [ content, mkComment msgGenerated ] else -- Sign at the beginning (JFlex cannot handle comments in general, only at beginning). mkComment msgGenerated ++ "\n\n" ++ content