X-Git-Url: https://git.stderr.nl/gitweb?a=blobdiff_plain;f=Translator.hs;h=e375e457b171d85f2927691ed0900773e29ee508;hb=acb620510e3623e8dfd979a8b732babd19086a9b;hp=9ce7206c9df9bd841bd0c5a4e7cccabe1d392b3f;hpb=72a84356f5507b73d4d5f84844aac9334ee17795;p=matthijs%2Fmaster-project%2Fc%CE%BBash.git diff --git a/Translator.hs b/Translator.hs index 9ce7206..e375e45 100644 --- a/Translator.hs +++ b/Translator.hs @@ -1,5 +1,5 @@ module Translator where -import GHC +import GHC hiding (loadModule, sigName) 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,41 @@ 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)) ["sfull_adder"] - 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 + makeVHDL "Alu.hs" "register_bank" + +makeVHDL :: String -> String -> IO () +makeVHDL filename name = do + -- Load the module + core <- loadModule filename + -- Translate to VHDL + vhdl <- moduleToVHDL core [name] + -- 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 $ showSDoc $ ppr 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 +86,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 +150,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 () @@ -188,9 +221,16 @@ nameFlatFunction hsfunc fdata = -- Name the signals in all other functions Just flatfunc -> let s = flat_sigs flatfunc in - let s' = map (\(id, (SignalInfo Nothing use ty)) -> (id, SignalInfo (Just $ "sig_" ++ (show id)) use ty)) s in + let s' = map nameSignal s in let flatfunc' = flatfunc { flat_sigs = s' } in setFlatFunc hsfunc flatfunc' + where + nameSignal :: (SignalId, SignalInfo) -> (SignalId, SignalInfo) + nameSignal (id, info) = + let hints = nameHints info in + let parts = ("sig" : hints) ++ [show id] in + let name = concat $ List.intersperse "_" parts in + (id, info {sigName = Just name}) -- | Splits a tuple type into a list of element types, or Nothing if the type -- is not a tuple type. @@ -215,7 +255,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.