X-Git-Url: https://git.stderr.nl/gitweb?a=blobdiff_plain;f=Translator.hs;h=cf2fb966876c5ffd612d00360dfe772a4adf2110;hb=0082f01a853476cdcec0e73bacf8c0d4508dbec0;hp=c037a1e24a0d30a8f97aeca69c815fa65ad9e97d;hpb=a3ea63eb2bd94867dae27a30aa900c9dfa9babb1;p=matthijs%2Fmaster-project%2Fc%CE%BBash.git diff --git a/Translator.hs b/Translator.hs index c037a1e..cf2fb96 100644 --- a/Translator.hs +++ b/Translator.hs @@ -1,5 +1,5 @@ module Translator where -import GHC +import GHC hiding (loadModule) import CoreSyn import qualified CoreUtils import qualified Var @@ -13,6 +13,7 @@ import Name import qualified Data.Map as Map import Data.Generics import NameEnv ( lookupNameEnv ) +import qualified HscTypes import HscTypes ( cm_binds, cm_types ) import MonadUtils ( liftIO ) import Outputable ( showSDoc, ppr ) @@ -40,28 +41,36 @@ import FlattenTypes import VHDLTypes import qualified VHDL -main = - do - defaultErrorHandler defaultDynFlags $ do - runGhc (Just libdir) $ do - dflags <- getSessionDynFlags - setSessionDynFlags dflags - --target <- guessTarget "adder.hs" Nothing - --liftIO (print (showSDoc (ppr (target)))) - --liftIO $ printTarget target - --setTargets [target] - --load LoadAllTargets - --core <- GHC.compileToCoreSimplified "Adders.hs" - core <- GHC.compileToCoreSimplified "Adders.hs" - --liftIO $ printBinds (cm_binds core) - let binds = Maybe.mapMaybe (findBind (cm_binds core)) ["dff"] - liftIO $ putStr $ prettyShow binds - -- Turn bind into VHDL - let (vhdl, sess) = State.runState (mkVHDL binds) (VHDLSession core 0 Map.empty) - liftIO $ putStr $ render $ ForSyDe.Backend.Ppr.ppr vhdl - liftIO $ ForSyDe.Backend.VHDL.FileIO.writeDesignFile vhdl "../vhdl/vhdl/output.vhdl" - liftIO $ putStr $ "\n\nFinal session:\n" ++ prettyShow sess ++ "\n\n" - return () +main = do + -- Load the module + core <- loadModule "Adders.hs" + -- Translate to VHDL + vhdl <- moduleToVHDL core ["shifter"] + -- Write VHDL to file + writeVHDL vhdl "../vhdl/vhdl/output.vhdl" + +-- | Show the core structure of the given binds in the given file. +listBind :: String -> String -> IO () +listBind filename name = do + core <- loadModule filename + let binds = findBinds core [name] + putStr "\n" + putStr $ prettyShow binds + putStr "\n\n" + +-- | Translate the binds with the given names from the given core module to +-- VHDL +moduleToVHDL :: HscTypes.CoreModule -> [String] -> IO AST.DesignFile +moduleToVHDL core names = do + --liftIO $ putStr $ prettyShow (cm_binds core) + let binds = findBinds core names + --putStr $ prettyShow binds + -- Turn bind into VHDL + let (vhdl, sess) = State.runState (mkVHDL binds) (VHDLSession core 0 Map.empty) + putStr $ render $ ForSyDe.Backend.Ppr.ppr vhdl + putStr $ "\n\nFinal session:\n" ++ prettyShow sess ++ "\n\n" + return vhdl + where -- Turns the given bind into VHDL mkVHDL binds = do @@ -72,14 +81,33 @@ main = modFuncs nameFlatFunction modFuncs VHDL.createEntity modFuncs VHDL.createArchitecture - -- Extract the library units generated from all the functions in the - -- session. - funcs <- getFuncs - let units = concat $ map VHDL.getLibraryUnits funcs - return $ AST.DesignFile - [] - units + VHDL.getDesignFile + +-- | Write the given design file to the given file +writeVHDL :: AST.DesignFile -> String -> IO () +writeVHDL = ForSyDe.Backend.VHDL.FileIO.writeDesignFile + +-- | Loads the given file and turns it into a core module. +loadModule :: String -> IO HscTypes.CoreModule +loadModule filename = + defaultErrorHandler defaultDynFlags $ do + runGhc (Just libdir) $ do + dflags <- getSessionDynFlags + setSessionDynFlags dflags + --target <- guessTarget "adder.hs" Nothing + --liftIO (print (showSDoc (ppr (target)))) + --liftIO $ printTarget target + --setTargets [target] + --load LoadAllTargets + --core <- GHC.compileToCoreSimplified "Adders.hs" + core <- GHC.compileToCoreSimplified filename + return core + +-- | Extracts the named binds from the given module. +findBinds :: HscTypes.CoreModule -> [String] -> [CoreBind] +findBinds core names = Maybe.mapMaybe (findBind (cm_binds core)) names +-- | Extract a named bind from the given list of binds findBind :: [CoreBind] -> String -> Maybe CoreBind findBind binds lookfor = -- This ignores Recs and compares the name of the bind with lookfor, @@ -117,7 +145,7 @@ flattenBind hsfunc bind@(NonRec var expr) = do let flatfunc = flattenFunction hsfunc bind addFunc hsfunc setFlatFunc hsfunc flatfunc - let used_hsfuncs = map appFunc (flat_apps flatfunc) + let used_hsfuncs = Maybe.mapMaybe usedHsFunc (flat_defs flatfunc) State.mapM resolvFunc used_hsfuncs return () @@ -215,7 +243,7 @@ data BuiltIn = BuiltIn String [PortMap] PortMap -- | Map a port specification of a builtin function to a VHDL Signal to put in -- a VHDLSignalMap toVHDLSignalMap :: HsValueMap (String, AST.TypeMark) -> VHDLSignalMap -toVHDLSignalMap = fmap (\(name, ty) -> (VHDL.mkVHDLId name, ty)) +toVHDLSignalMap = fmap (\(name, ty) -> Just (VHDL.mkVHDLId name, ty)) -- | Translate a concise representation of a builtin function to something -- that can be put into FuncMap directly.