module Feldspar.Compiler.Compiler where
import Data.List (partition)
import Data.Maybe (fromMaybe)
import Control.Applicative
import Feldspar.Transformation
import Feldspar.Core.Constructs (SyntacticFeld)
import Feldspar.Core.Interpretation (defaultFeldOpts)
import Feldspar.Compiler.Backend.C.Library
import Feldspar.Compiler.Backend.C.Options
import Feldspar.Compiler.Backend.C.Platforms
import Feldspar.Compiler.Backend.C.Plugin.Rule
import Feldspar.Compiler.Backend.C.CodeGeneration
import Feldspar.Compiler.Imperative.FromCore
import Feldspar.Compiler.Imperative.Plugin.IVars
data SplitModuleDescriptor = SplitModuleDescriptor
{ smdSource :: Module ()
, smdHeader :: Module ()
}
data SplitCompToCCoreResult = SplitCompToCCoreResult
{ sctccrSource :: CompToCCoreResult ()
, sctccrHeader :: CompToCCoreResult ()
}
data CompToCCoreResult t = CompToCCoreResult {
sourceCode :: String,
debugModule :: Module t
}
moduleSplitter :: Module () -> SplitModuleDescriptor
moduleSplitter m = SplitModuleDescriptor {
smdHeader = Module (hdr ++ createProcDecls (entities m)),
smdSource = Module body
} where
(hdr, body) = partition belongsToHeader (entities m)
belongsToHeader :: Entity () -> Bool
belongsToHeader StructDef{} = True
belongsToHeader Proc{..} | Nothing <- procBody = True
belongsToHeader _ = False
createProcDecls :: [Entity ()] -> [Entity ()]
createProcDecls = concatMap defToDecl
defToDecl :: Entity () -> [Entity ()]
defToDecl (Proc n inp outp _) = [Proc n inp outp Nothing]
defToDecl _ = []
moduleToCCore :: Options -> Module () -> CompToCCoreResult ()
moduleToCCore opts mdl = CompToCCoreResult { sourceCode = incls ++ res
, debugModule = mdl
}
where
res = compToCWithInfos opts mdl
incls = genIncludeLines opts Nothing
compileToCCore
:: SyntacticFeld c => String -> Options -> c -> SplitCompToCCoreResult
compileToCCore funSig coreOptions prg =
createSplit $ moduleToCCore coreOptions <$> separatedModules
where
separatedModules = moduleSeparator
$ executePluginChain funSig coreOptions prg
moduleSeparator modules = [header, source]
where (SplitModuleDescriptor header source) = moduleSplitter modules
createSplit [header, source] = SplitCompToCCoreResult header source
genIncludeLines :: Options -> Maybe String -> String
genIncludeLines opts mainHeader = concatMap include incs ++ "\n\n"
where
include [] = ""
include fname@('<':_) = "#include " ++ fname ++ "\n"
include fname = "#include \"" ++ fname ++ "\"\n"
incs = includes (platform opts) ++ [fromMaybe "" mainHeader]
defaultOptions :: Options
defaultOptions
= Options
{ platform = c99
, unroll = NoUnroll
, debug = NoDebug
, memoryInfoVisible = True
, printHeader = False
, rules = []
, frontendOpts = defaultFeldOpts
, nestSize = 2
}
c99PlatformOptions :: Options
c99PlatformOptions = defaultOptions
c99OpenMpPlatformOptions :: Options
c99OpenMpPlatformOptions = defaultOptions { platform = c99OpenMp }
tic64xPlatformOptions :: Options
tic64xPlatformOptions = defaultOptions { platform = tic64x }
unrollOptions :: Options
unrollOptions = defaultOptions { unroll = Unroll 8 }
noPrimitiveInstructionHandling :: Options
noPrimitiveInstructionHandling = defaultOptions { debug = NoPrimitiveInstructionHandling }
noMemoryInformation :: Options
noMemoryInformation = defaultOptions { memoryInfoVisible = False }
pluginChain :: ExternalInfoCollection -> Module () -> Module ()
pluginChain externalInfo
= executePlugin RulePlugin (ruleExternalInfo externalInfo)
. executePlugin RulePlugin (primitivesExternalInfo externalInfo)
. executePlugin IVarPlugin ()
data ExternalInfoCollection = ExternalInfoCollection
{ primitivesExternalInfo :: ExternalInfo RulePlugin
, ruleExternalInfo :: ExternalInfo RulePlugin
}
executePluginChain :: SyntacticFeld c
=> String -> Options -> c -> Module ()
executePluginChain originalFunctionName opt prg =
pluginChain ExternalInfoCollection
{ primitivesExternalInfo = opt{ rules = platformRules $ platform opt }
, ruleExternalInfo = opt
} $ fromCore opt (encodeFunctionName originalFunctionName) prg