From 969b7ddd86b69d2fc61b101961affcca0364749c Mon Sep 17 00:00:00 2001 From: Matthijs Kooijman Date: Thu, 25 Jun 2009 14:36:40 +0200 Subject: [PATCH] Restructure a lot of VHDL generating code. In particular: * The globalNameTable was moved into Generate. * A large part of mkConcSm was moved into Generate. * A BuiltinBuilder now accepts Either CoreBndr VHDLName and [Either CoreExpr AST.Expr], so we can reuse them even when we no longer have a CoreBndrs (this does not happen yet, though). --- Generate.hs | 130 +++++++++++++++++++++++++++++++++++++++------ GlobalNameTable.hs | 39 -------------- VHDL.hs | 50 +---------------- VHDLTools.hs | 39 +++++++++----- VHDLTypes.hs | 6 +-- 5 files changed, 144 insertions(+), 120 deletions(-) delete mode 100644 GlobalNameTable.hs diff --git a/Generate.hs b/Generate.hs index 7b8dcf0..5be8694 100644 --- a/Generate.hs +++ b/Generate.hs @@ -4,6 +4,7 @@ module Generate where import qualified Control.Monad as Monad import qualified Data.Map as Map import qualified Maybe +import qualified Data.Either as Either import Data.Accessor import Debug.Trace @@ -14,6 +15,7 @@ import qualified ForSyDe.Backend.VHDL.AST as AST import CoreSyn import Type import qualified Var +import qualified IdInfo -- Local imports import Constants @@ -22,60 +24,68 @@ import VHDLTools import CoreTools import Pretty +----------------------------------------------------------------------------- +-- Functions to generate VHDL for builtin functions +----------------------------------------------------------------------------- + -- | A function to wrap a builder-like function that expects its arguments to -- be expressions. genExprArgs :: (dst -> func -> [AST.Expr] -> res) - -> (dst -> func -> [CoreSyn.CoreExpr] -> res) + -> (dst -> func -> [Either CoreSyn.CoreExpr AST.Expr] -> res) genExprArgs wrap dst func args = wrap dst func args' - where args' = map (varToVHDLExpr.exprToVar) args + where args' = map (either (varToVHDLExpr.exprToVar) id) args -- | A function to wrap a builder-like function that expects its arguments to -- be variables. genVarArgs :: (dst -> func -> [Var.Var] -> res) - -> (dst -> func -> [CoreSyn.CoreExpr] -> res) + -> (dst -> func -> [Either CoreSyn.CoreExpr AST.Expr] -> res) genVarArgs wrap dst func args = wrap dst func args' - where args' = map exprToVar args + where + args' = map exprToVar exprargs + -- Check (rather crudely) that all arguments are CoreExprs + (exprargs, []) = Either.partitionEithers args -- | A function to wrap a builder-like function that produces an expression -- and expects it to be assigned to the destination. genExprRes :: - (CoreSyn.CoreBndr -> func -> [arg] -> VHDLSession AST.Expr) - -> (CoreSyn.CoreBndr -> func -> [arg] -> VHDLSession [AST.ConcSm]) + ((Either CoreSyn.CoreBndr AST.VHDLName) -> func -> [arg] -> VHDLSession AST.Expr) + -> ((Either CoreSyn.CoreBndr AST.VHDLName) -> func -> [arg] -> VHDLSession [AST.ConcSm]) genExprRes wrap dst func args = do expr <- wrap dst func args - return $ [mkUncondAssign (Left dst) expr] + return $ [mkUncondAssign dst expr] -- | Generate a binary operator application. The first argument should be a -- constructor from the AST.Expr type, e.g. AST.And. genOperator2 :: (AST.Expr -> AST.Expr -> AST.Expr) -> BuiltinBuilder genOperator2 op = genExprArgs $ genExprRes (genOperator2' op) -genOperator2' :: (AST.Expr -> AST.Expr -> AST.Expr) -> CoreSyn.CoreBndr -> CoreSyn.CoreBndr -> [AST.Expr] -> VHDLSession AST.Expr -genOperator2' op res f [arg1, arg2] = return $ op arg1 arg2 +genOperator2' :: (AST.Expr -> AST.Expr -> AST.Expr) -> dst -> CoreSyn.CoreBndr -> [AST.Expr] -> VHDLSession AST.Expr +genOperator2' op _ f [arg1, arg2] = return $ op arg1 arg2 -- | Generate a unary operator application genOperator1 :: (AST.Expr -> AST.Expr) -> BuiltinBuilder genOperator1 op = genExprArgs $ genExprRes (genOperator1' op) -genOperator1' :: (AST.Expr -> AST.Expr) -> CoreSyn.CoreBndr -> CoreSyn.CoreBndr -> [AST.Expr] -> VHDLSession AST.Expr -genOperator1' op res f [arg] = return $ op arg +genOperator1' :: (AST.Expr -> AST.Expr) -> dst -> CoreSyn.CoreBndr -> [AST.Expr] -> VHDLSession AST.Expr +genOperator1' op _ f [arg] = return $ op arg -- | Generate a function call from the destination binder, function name and a -- list of expressions (its arguments) genFCall :: BuiltinBuilder genFCall = genExprArgs $ genExprRes genFCall' -genFCall' :: CoreSyn.CoreBndr -> CoreSyn.CoreBndr -> [AST.Expr] -> VHDLSession AST.Expr -genFCall' res f args = do +genFCall' :: Either CoreSyn.CoreBndr AST.VHDLName -> CoreSyn.CoreBndr -> [AST.Expr] -> VHDLSession AST.Expr +genFCall' (Left res) f args = do let fname = varToString f let el_ty = (tfvec_elem . Var.varType) res id <- vectorFunId el_ty fname return $ AST.PrimFCall $ AST.FCall (AST.NSimple id) $ map (\exp -> Nothing AST.:=>: AST.ADExpr exp) args +genFCall' (Right name) _ _ = error $ "Cannot generate builtin function call assigned to a VHDLName: " ++ show name -- | Generate a generate statement for the builtin function "map" genMap :: BuiltinBuilder genMap = genVarArgs genMap' -genMap' res f [mapped_f, arg] = do +genMap' (Left res) f [mapped_f, arg] = do signatures <- getA vsSignatures let entity = Maybe.fromMaybe (error $ "Using function '" ++ (varToString mapped_f) ++ "' without signature? This should not happen!") @@ -83,6 +93,7 @@ genMap' res f [mapped_f, arg] = do let -- Setup the generate scheme len = (tfvec_len . Var.varType) res + -- TODO: Use something better than varToString label = mkVHDLExtId ("mapVector" ++ (varToString res)) nPar = AST.unsafeVHDLBasicId "n" range = AST.ToRange (AST.PrimLit "0") (AST.PrimLit $ show (len-1)) @@ -102,10 +113,12 @@ genMap' res f [mapped_f, arg] = do genSm = AST.CSGSm $ AST.GenerateSm label genScheme [] [compins] in return $ [genSm] +genMap' (Right name) _ _ = error $ "Cannot generate map function call assigned to a VHDLName: " ++ show name genZipWith :: BuiltinBuilder genZipWith = genVarArgs genZipWith' -genZipWith' res f args@[zipped_f, arg1, arg2] = do +genZipWith' :: (Either CoreSyn.CoreBndr AST.VHDLName) -> CoreSyn.CoreBndr -> [Var.Var] -> VHDLSession [AST.ConcSm] +genZipWith' (Left res) f args@[zipped_f, arg1, arg2] = do signatures <- getA vsSignatures let entity = Maybe.fromMaybe (error $ "Using function '" ++ (varToString zipped_f) ++ "' without signature? This should not happen!") @@ -113,6 +126,7 @@ genZipWith' res f args@[zipped_f, arg1, arg2] = do let -- Setup the generate scheme len = (tfvec_len . Var.varType) res + -- TODO: Use something better than varToString label = mkVHDLExtId ("zipWithVector" ++ (varToString res)) nPar = AST.unsafeVHDLBasicId "n" range = AST.ToRange (AST.PrimLit "0") (AST.PrimLit $ show (len-1)) @@ -133,7 +147,7 @@ genZipWith' res f args@[zipped_f, arg1, arg2] = do genSm = AST.CSGSm $ AST.GenerateSm label genScheme [] [compins] in return $ [genSm] - +{- genFoldl :: BuiltinBuilder genFoldl = genVarArgs genFoldl' genFoldl' resVal f [folded_f, startVal, inVec] = do @@ -221,7 +235,62 @@ genFoldl' resVal f [folded_f, startVal, inVec] = do (AST.NSimple tmpId) [AST.PrimLit $ show (len-1)]))) -- Return the generate functions cellGn = AST.GenerateSm cellLabel cellGenScheme [] [compins,assign] +-} +----------------------------------------------------------------------------- +-- Function to generate VHDL for applications +----------------------------------------------------------------------------- +genApplication :: + (Either CoreSyn.CoreBndr AST.VHDLName) -- ^ Where to store the result? + -> CoreSyn.CoreBndr -- ^ The function to apply + -> [Either CoreSyn.CoreExpr AST.Expr] -- ^ The arguments to apply + -> VHDLSession [AST.ConcSm] -- ^ The resulting concurrent statements +genApplication dst f args = + case Var.globalIdVarDetails f of + IdInfo.DataConWorkId dc -> case dst of + -- It's a datacon. Create a record from its arguments. + Left bndr -> do + -- We have the bndr, so we can get at the type + labels <- getFieldLabels (Var.varType bndr) + return $ zipWith mkassign labels $ map (either exprToVHDLExpr id) args + where + mkassign :: AST.VHDLId -> AST.Expr -> AST.ConcSm + mkassign label arg = + let sel_name = mkSelectedName ((either varToVHDLName id) dst) label in + mkUncondAssign (Right sel_name) arg + Right _ -> error $ "Generate.genApplication Can't generate dataconstructor application without an original binder" + IdInfo.VanillaGlobal -> do + -- It's a global value imported from elsewhere. These can be builtin + -- functions. Look up the function name in the name table and execute + -- the associated builder if there is any and the argument count matches + -- (this should always be the case if it typechecks, but just to be + -- sure...). + case (Map.lookup (varToString f) globalNameTable) of + Just (arg_count, builder) -> + if length args == arg_count then + builder dst f args + else + error $ "Generate.genApplication Incorrect number of arguments to builtin function: " ++ pprString f ++ " Args: " ++ show args + Nothing -> error $ "Using function from another module that is not a known builtin: " ++ pprString f + IdInfo.NotGlobalId -> do + signatures <- getA vsSignatures + -- This is a local id, so it should be a function whose definition we + -- have and which can be turned into a component instantiation. + let + signature = Maybe.fromMaybe + (error $ "Using function '" ++ (varToString f) ++ "' without signature? This should not happen!") + (Map.lookup f signatures) + entity_id = ent_id signature + -- TODO: Using show here isn't really pretty, but we'll need some + -- unique-ish value... + label = "comp_ins_" ++ (either show show) dst + portmaps = mkAssocElems (map (either exprToVHDLExpr id) args) ((either varToVHDLName id) dst) signature + in + return [mkComponentInst label entity_id portmaps] + details -> error $ "Calling unsupported function " ++ pprString f ++ " with GlobalIdDetails " ++ pprString details +----------------------------------------------------------------------------- +-- Functions to generate functions dealing with vectors. +----------------------------------------------------------------------------- -- Returns the VHDLId of the vector function with the given name for the given -- element type. Generates -- this function if needed. @@ -431,3 +500,32 @@ genUnconsVectorFuns elemTM vectorTM = (AST.PrimName $ AST.NSimple aPar)]) -- return res copyExpr = AST.ReturnSm (Just $ AST.PrimName $ AST.NSimple resId) + +----------------------------------------------------------------------------- +-- A table of builtin functions +----------------------------------------------------------------------------- + +-- | The builtin functions we support. Maps a name to an argument count and a +-- builder function. +globalNameTable :: NameTable +globalNameTable = Map.fromList + [ (exId , (2, genFCall ) ) + , (replaceId , (3, genFCall ) ) + , (headId , (1, genFCall ) ) + , (lastId , (1, genFCall ) ) + , (tailId , (1, genFCall ) ) + , (initId , (1, genFCall ) ) + , (takeId , (2, genFCall ) ) + , (dropId , (2, genFCall ) ) + , (plusgtId , (2, genFCall ) ) + , (mapId , (2, genMap ) ) + , (zipWithId , (3, genZipWith ) ) + --, (foldlId , (3, genFoldl ) ) + , (emptyId , (0, genFCall ) ) + , (singletonId , (1, genFCall ) ) + , (copyId , (2, genFCall ) ) + , (hwxorId , (2, genOperator2 AST.Xor ) ) + , (hwandId , (2, genOperator2 AST.And ) ) + , (hworId , (2, genOperator2 AST.Or ) ) + , (hwnotId , (1, genOperator1 AST.Not ) ) + ] diff --git a/GlobalNameTable.hs b/GlobalNameTable.hs deleted file mode 100644 index ab56574..0000000 --- a/GlobalNameTable.hs +++ /dev/null @@ -1,39 +0,0 @@ -{-# LANGUAGE TemplateHaskell #-} - -module GlobalNameTable (globalNameTable) where - -import Language.Haskell.TH -import qualified Data.Map as Map - -import qualified ForSyDe.Backend.VHDL.AST as AST -import qualified Data.Param.TFVec as V - -import VHDLTypes -import Constants -import Generate - -mkGlobalNameTable :: [(String, (Int, BuiltinBuilder) )] -> NameTable -mkGlobalNameTable = Map.fromList - -globalNameTable :: NameTable -globalNameTable = mkGlobalNameTable - [ (exId , (2, genFCall ) ) - , (replaceId , (3, genFCall ) ) - , (headId , (1, genFCall ) ) - , (lastId , (1, genFCall ) ) - , (tailId , (1, genFCall ) ) - , (initId , (1, genFCall ) ) - , (takeId , (2, genFCall ) ) - , (dropId , (2, genFCall ) ) - , (plusgtId , (2, genFCall ) ) - , (mapId , (2, genMap ) ) - , (zipWithId , (3, genZipWith ) ) - , (foldlId , (3, genFoldl ) ) - , (emptyId , (0, genFCall ) ) - , (singletonId , (1, genFCall ) ) - , (copyId , (2, genFCall ) ) - , (hwxorId , (2, genOperator2 AST.Xor ) ) - , (hwandId , (2, genOperator2 AST.And ) ) - , (hworId , (2, genOperator2 AST.Or ) ) - , (hwnotId , (1, genOperator1 AST.Not ) ) - ] diff --git a/VHDL.hs b/VHDL.hs index 4b69df5..c646f8b 100644 --- a/VHDL.hs +++ b/VHDL.hs @@ -37,7 +37,6 @@ import Pretty import CoreTools import Constants import Generate -import GlobalNameTable createDesignFiles :: [(CoreSyn.CoreBndr, CoreSyn.CoreExpr)] @@ -275,52 +274,7 @@ mkConcSm (bndr, app@(CoreSyn.App _ _))= do let (CoreSyn.Var f, args) = CoreSyn.collectArgs app let valargs' = filter isValArg args let valargs = filter (\(CoreSyn.Var bndr) -> not (Id.isDictId bndr)) valargs' - case Var.globalIdVarDetails f of - IdInfo.DataConWorkId dc -> - -- It's a datacon. Create a record from its arguments. - -- First, filter out type args. TODO: Is this the best way to do this? - -- The types should already have been taken into acocunt when creating - -- the signal, so this should probably work... - --let valargs = filter isValArg args in - if all is_var valargs then do - labels <- getFieldLabels (CoreUtils.exprType app) - return $ zipWith mkassign labels valargs - else - error $ "VHDL.mkConcSm Not in normal form: One ore more complex arguments: " ++ pprString args - where - mkassign :: AST.VHDLId -> CoreExpr -> AST.ConcSm - mkassign label (Var arg) = - let sel_name = mkSelectedName bndr label in - mkUncondAssign (Right sel_name) (varToVHDLExpr arg) - IdInfo.VanillaGlobal -> do - -- It's a global value imported from elsewhere. These can be builtin - -- functions. - signatures <- getA vsSignatures - case (Map.lookup (varToString f) globalNameTable) of - Just (arg_count, builder) -> - if length valargs == arg_count then - builder bndr f valargs - else - error $ "VHDL.mkConcSm Incorrect number of arguments to builtin function: " ++ pprString f ++ " Args: " ++ pprString valargs - Nothing -> error $ "Using function from another module that is not a known builtin: " ++ pprString f - IdInfo.NotGlobalId -> do - signatures <- getA vsSignatures - -- This is a local id, so it should be a function whose definition we - -- have and which can be turned into a component instantiation. - let - signature = Maybe.fromMaybe - (error $ "Using function '" ++ (varToString f) ++ "' without signature? This should not happen!") - (Map.lookup f signatures) - entity_id = ent_id signature - label = "comp_ins_" ++ varToString bndr - -- Add a clk port if we have state - --clk_port = Maybe.fromJust $ mkAssocElem (Just $ mkVHDLExtId "clk") "clk" - --clk_port = Maybe.fromJust $ mkAssocElem (Just $ mkVHDLExtId "clk") "clk" - --portmaps = mkAssocElems sigs args res signature ++ (if hasState hsfunc then [clk_port] else []) - portmaps = mkAssocElems args bndr signature - in - return [mkComponentInst label entity_id portmaps] - details -> error $ "Calling unsupported function " ++ pprString f ++ " with GlobalIdDetails " ++ pprString details + genApplication (Left bndr) f (map Left valargs) -- A single alt case must be a selector. This means thee scrutinee is a simple -- variable, the alternative is a dataalt with a single non-wild binder that @@ -332,7 +286,7 @@ mkConcSm (bndr, expr@(Case (Var scrut) b ty [alt])) = Just i -> do labels <- getFieldLabels (Id.idType scrut) let label = labels!!i - let sel_name = mkSelectedName scrut label + let sel_name = mkSelectedName (varToVHDLName scrut) label let sel_expr = AST.PrimName sel_name return [mkUncondAssign (Left bndr) sel_expr] Nothing -> error $ "VHDL.mkConcSM Not in normal form: Not a selector case:\n" ++ (pprString expr) diff --git a/VHDLTools.hs b/VHDLTools.hs index 178c743..d6034e7 100644 --- a/VHDLTools.hs +++ b/VHDLTools.hs @@ -76,8 +76,8 @@ mkAssign dst cond false_expr = AST.CSSASm assign mkAssocElems :: - [CoreSyn.CoreExpr] -- | The argument that are applied to function - -> CoreSyn.CoreBndr -- | The binder in which to store the result + [AST.Expr] -- | The argument that are applied to function + -> AST.VHDLName -- | The binder in which to store the result -> Entity -- | The entity to map against. -> [AST.AssocElem] -- | The resulting port maps mkAssocElems args res entity = @@ -92,11 +92,11 @@ mkAssocElems args res entity = -- Extract the id part from the (id, type) tuple ports = map (Monad.liftM fst) (res_port : arg_ports) -- Translate signal numbers into names - sigs = (varToString res : map (varToString.exprToVar) args) + sigs = (vhdlNameToVHDLExpr res : args) -- | Create an VHDL port -> signal association -mkAssocElem :: Maybe AST.VHDLId -> String -> Maybe AST.AssocElem -mkAssocElem (Just port) signal = Just $ Just port AST.:=>: (AST.ADName (AST.NSimple (mkVHDLExtId signal))) +mkAssocElem :: Maybe AST.VHDLId -> AST.Expr -> Maybe AST.AssocElem +mkAssocElem (Just port) signal = Just $ Just port AST.:=>: (AST.ADExpr signal) mkAssocElem Nothing _ = Nothing -- | Create an VHDL port -> signal association @@ -113,7 +113,7 @@ mkComponentInst :: mkComponentInst label entity_id portassigns = AST.CSISm compins where -- We always have a clock port, so no need to map it anywhere but here - clk_port = Maybe.fromJust $ mkAssocElem (Just $ mkVHDLExtId "clk") "clk" + clk_port = Maybe.fromJust $ mkAssocElem (Just $ mkVHDLExtId "clk") (idToVHDLExpr $ mkVHDLExtId "clk") compins = AST.CompInsSm (mkVHDLExtId label) (AST.IUEntity (AST.NSimple entity_id)) (AST.PMapAspect (portassigns ++ [clk_port])) ----------------------------------------------------------------------------- @@ -130,6 +130,15 @@ varToVHDLExpr var = -- local/global here as well? Nothing -> AST.PrimName $ AST.NSimple $ varToVHDLId var +-- Turn a VHDLName into an AST expression +vhdlNameToVHDLExpr = AST.PrimName + +-- Turn a VHDL Id into an AST expression +idToVHDLExpr = vhdlNameToVHDLExpr . AST.NSimple + +-- Turn a Core expression into an AST expression +exprToVHDLExpr = varToVHDLExpr . exprToVar + -- Turn a alternative constructor into an AST expression. For -- dataconstructors, this is only the constructor itself, not any arguments it -- has. Should not be called with a DEFAULT constructor. @@ -159,7 +168,13 @@ dataconToVHDLExpr dc = AST.PrimLit lit varToVHDLId :: CoreSyn.CoreBndr -> AST.VHDLId -varToVHDLId = mkVHDLExtId . OccName.occNameString . Name.nameOccName . Var.varName +varToVHDLId = mkVHDLExtId . varToString + +-- Creates a VHDL Name from a binder +varToVHDLName :: + CoreSyn.CoreBndr + -> AST.VHDLName +varToVHDLName = AST.NSimple . varToVHDLId -- Extracts the binder name as a String varToString :: @@ -209,13 +224,9 @@ mkVHDLExtId s = -- Create a record field selector that selects the given label from the record -- stored in the given binder. -mkSelectedName :: CoreBndr -> AST.VHDLId -> AST.VHDLName -mkSelectedName bndr label = - let - sel_prefix = AST.NSimple $ varToVHDLId bndr - sel_suffix = AST.SSimple $ label - in - AST.NSelected $ sel_prefix AST.:.: sel_suffix +mkSelectedName :: AST.VHDLName -> AST.VHDLId -> AST.VHDLName +mkSelectedName name label = + AST.NSelected $ name AST.:.: (AST.SSimple label) ----------------------------------------------------------------------------- -- Functions dealing with VHDL types diff --git a/VHDLTypes.hs b/VHDLTypes.hs index 79d7675..3e2ebe0 100644 --- a/VHDLTypes.hs +++ b/VHDLTypes.hs @@ -78,10 +78,10 @@ type TypeState = State.State TypeMap -- A function that generates VHDL for a builtin function type BuiltinBuilder = - CoreSyn.CoreBndr -- ^ The destination value + (Either CoreSyn.CoreBndr AST.VHDLName) -- ^ The destination signal and it's original type -> CoreSyn.CoreBndr -- ^ The function called - -> [CoreSyn.CoreExpr] -- ^ The value arguments passed (excluding type and - -- dictionary arguments). + -> [Either CoreSyn.CoreExpr AST.Expr] -- ^ The value arguments passed (excluding type and + -- dictionary arguments). -> VHDLSession [AST.ConcSm] -- ^ The resulting concurrent statements. -- A map of a builtin function to VHDL function builder -- 2.30.2