{-# LANGUAGE AllowAmbiguousTypes #-} {-# LANGUAGE DataKinds #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeApplications #-} {-# LANGUAGE TypeFamilies #-} module BNFC.Backend.CommonInterface.Backend where import Control.Monad.Except import Control.Monad.Writer import Control.Monad.State import Options.Applicative ( Parser ) import System.FilePath import BNFC.CF import BNFC.Prelude import BNFC.Options.GlobalOptions import BNFC.Options.Target -- result generated by a backed: file paths and their contents. type Result = [(FilePath, String)] -- type used to log what the backends may print while generating files. type Log = Writer String -- output type, inclusive of the backend result and logging. type Output = WriterT Result Log () -- | Backend typeclass. class Backend (target :: TargetLanguage) where type BackendOptions target type BackendState target parseOpts :: Parser (BackendOptions target) initState :: LBNF -> GlobalOptions -> BackendOptions target -> Except String (BackendState target) abstractSyntax :: LBNF -> State (BackendState target) Result printer :: LBNF -> State (BackendState target) Result lexer :: LBNF -> State (BackendState target) Result parser :: LBNF -> State (BackendState target) Result parserTest :: LBNF -> State (BackendState target) Result makefile :: LBNF -> State (BackendState target) Result runBackend :: forall target. Backend target => GlobalOptions -> BackendOptions target -> LBNF -> Except String Result runBackend globalOpts backendOpts cf = do st <- initState @target cf globalOpts backendOpts return $ flip evalState st $ do lexSpec <- lexer @target cf parSpec <- parser @target cf parTest <- parserTest @target cf absSpec <- abstractSyntax @target cf printSpec <- printer @target cf mkfile <- if optMakeFile globalOpts then makefile @target cf else return [] return $ concat [lexSpec, parSpec, parTest, absSpec, printSpec, mkfile]