{-# LANGUAGE OverloadedStrings #-} module BNFC.Backend.Agda.Makefile where import BNFC.Prelude import Control.Monad.State import Data.List (intersperse) import Prettyprinter import Prettyprinter.Render.String import System.FilePath (dropExtension, takeBaseName, (), (<.>)) import BNFC.Backend.CommonInterface.Backend ( Result ) import BNFC.Backend.Agda.Options import BNFC.Backend.Agda.State import BNFC.Backend.Common.Makefile import BNFC.Backend.Common.Utils as Utils import BNFC.Backend.Common.StringUtils import BNFC.Backend.Haskell.Utilities.Utils import BNFC.CF import BNFC.Options.GlobalOptions agdaMakefile :: LBNF -> State AgdaBackendState Result agdaMakefile lbnf = do st <- get let opts = agdaOpts st force = optForce $ globalOpt st cfName = takeBaseName $ optInput $ globalOpt st pathToGrammar = optInput $ globalOpt st outDir = optOutDir $ globalOpt st return [("Makefile", cf2makefile lbnf opts force cfName outDir pathToGrammar)] cf2makefile :: LBNF -> AgdaBackendOptions -> Bool -> String -> Maybe FilePath -> FilePath -> String cf2makefile lbnf agdaOpts force cfName outDir pathToGrammar = renderString . layoutSmart defaultLayoutOptions $ makefileDoc lbnf agdaOpts force cfName outDir pathToGrammar makefileDoc :: LBNF -> AgdaBackendOptions -> Bool -> String -> Maybe FilePath -> FilePath -> Doc () makefileDoc lbnf agdaOpts force cfName outDir pathToGrammar = vsep . intersperse emptyDoc $ [ header , phonyRule , defaultRule , "# Rules for building the parser." ] ++ Utils.when (isNothing outDir) [ bnfcRule ] ++ [ happyRule , alexRule , testParserRule , mainRule , "# Rules for cleaning generated files." , cleanRule , distClean , "# EOF" ] where inDirectory :: Bool inDirectory = inDir agdaOpts nSpace :: Maybe String nSpace = nameSpace agdaOpts header :: Doc () header = vsep [ "# Makefile for building the parser and test program." , emptyDoc , "AGDA = agda" , "GHC = ghc" , "GHC_OPTS = -package containers -package prettyprinter -package prettyprinter-ansi-terminal" , "HAPPY = happy" , "HAPPY_OPTS = --array --info --ghc --coerce" , "ALEX = alex" , "ALEX_OPTS = --ghc" ] phonyRule :: Doc () phonyRule = vsep [ "# List of goals not corresponding to file names." , emptyDoc , mkRule ".PHONY" [ "all", "clean", "distclean" ] [] ] defaultRule :: Doc () defaultRule = vsep [ "# Default goal." , emptyDoc , mkRule "all" dependencies [] ] where dependencies = [ mkDir inDirectory nSpace cfName "Test", "Main" ] bnfcRule :: Doc () bnfcRule = mkRule target [ pathToGrammar ] recipe where target = unwords [ absSintax, lexerSpec, parserSpec, parserTest , printer ] recipe = "bnfc " ++ (if force then "-f " else "") ++ pathToGrammar ++ " agda" ++ printAgdaOptions agdaOpts -- | Rule to invoke @happy@. happyRule :: Doc () happyRule = mkRule "%.hs" [ "%.y" ] "${HAPPY} ${HAPPY_OPTS} $<" -- | Rule to invoke @alex@. alexRule :: Doc () alexRule = mkRule "%.hs" [ "%.x" ] "${ALEX} ${ALEX_OPTS} $<" -- | Rule to build Haskell test parser. testParserRule :: Doc () testParserRule = mkRule targets dependencies "${GHC} ${GHC_OPTS} $@" where targets :: String targets = mkDir inDirectory nSpace cfName "Test" dependencies :: [String] dependencies = [ absSintax ] ++ Utils.when (layoutsAreUsed lbnf) [ layout ] ++ [ lexer , parserSpec , parser , printer , parserTest ] -- | Rule to compile Agda files. mainRule :: Doc () mainRule = mkRule "Main" dependencies recipe where dependencies :: [String] dependencies = [ main , ast , agdaParser , ioLib ] ++ Utils.when (layoutsAreUsed lbnf) [ layout ] ++ [ lexer , parser , printer ] recipe :: String recipe = "${AGDA} --no-libraries --ghc --ghc-flag=-Wwarn $<" cleanRule :: Doc () cleanRule = mkRule "clean" [] recipe where recipe = "-rm " ++ filesToClean ++ "\n\t" ++ "-rm -rf MAlonzo" filesToClean | inDirectory = if isJust nSpace then unwords $ executable : agdaMainExecutable : map ((fromJust nSpace fstCharUpper cfName "*") <>) genHs else unwords $ executable : agdaMainExecutable : map ((fstCharUpper cfName "*") <>) genHs | isJust nSpace = unwords $ executable : map ((fromJust nSpace "*") <>) genHs | otherwise = unwords $ executable : agdaMainExecutable : map ("*" <>) genHs genHs = [ ".agdai", ".hi", ".o" ] distClean :: Doc () distClean = mkRule "distclean" ["clean"] recipe where recipe = "-rm " ++ unwords [ absSintax , lexerSpec , lexer , parserSpec , parser , parserTest , printer , template , ast , ioLib , main , agdaParser , absSintax <.> "bak" , lexerSpec <.> "bak" , lexer <.> "bak" , parserSpec <.> "bak" , parser <.> "bak" , parserTest <.> "bak" , printer <.> "bak" , template <.> "bak" , ast <.> "bak" , ioLib <.> "bak" , main <.> "bak" , agdaParser <.> "bak" , parserInfo , "Makefile" , "Makefile.bak" , unwords (Utils.when (layoutsAreUsed lbnf) [layout, layout <.> "bak"]) ] ++ rmdir inDirectory nSpace rmdir :: Bool -> Maybe String -> String rmdir True Nothing = "\n\t" ++ "-rmdir " ++ fstCharUpper cfName rmdir False Nothing = "" rmdir True (Just s) = "\n\t" ++ "-rmdir -p " ++ fstCharUpper s fstCharUpper cfName rmdir False (Just s) = "\n\t" ++ "-rmdir " ++ fstCharUpper s -- Paths to Haskell generated components. absSintax = mkFilePath inDirectory nSpace cfName "Abs" "hs" layout = mkFilePath inDirectory nSpace cfName "Layout" "hs" lexerSpec = mkFilePath inDirectory nSpace cfName "Lex" "x" lexer = mkFilePath inDirectory nSpace cfName "Lex" "hs" parserSpec = mkFilePath inDirectory nSpace cfName "Par" "y" parser = mkFilePath inDirectory nSpace cfName "Par" "hs" parserInfo = mkFilePath inDirectory nSpace cfName "Par" "info" parserTest = mkFilePath inDirectory nSpace cfName "Test" "hs" printer = mkFilePath inDirectory nSpace cfName "Print" "hs" template = mkFilePath inDirectory nSpace cfName "Skel" "hs" -- Paths to Agda generated components. ast = mkFilePath inDirectory nSpace cfName "AST" "agda" ioLib = mkFilePath inDirectory nSpace cfName "IOLib" "agda" main = mkFilePath inDirectory nSpace cfName "Main" "agda" agdaParser = mkFilePath inDirectory nSpace cfName "Parser" "agda" -- Parser test executable. executable = dropExtension parserTest -- Agda main executable. agdaMainExecutable = "Main"