X-Git-Url: https://git.stderr.nl/gitweb?a=blobdiff_plain;f=VHDL.hs;h=b23e5f3117acc6481e37062d2816c28754365d46;hb=72a84356f5507b73d4d5f84844aac9334ee17795;hp=efa14097adb09301b8a6f7a617fa3598b787f644;hpb=6fabab8e6243062ab74860ca90bb4b08f564ceff;p=matthijs%2Fmaster-project%2Fc%CE%BBash.git diff --git a/VHDL.hs b/VHDL.hs index efa1409..b23e5f3 100644 --- a/VHDL.hs +++ b/VHDL.hs @@ -3,8 +3,9 @@ -- module VHDL where -import Data.Traversable +import qualified Data.Foldable as Foldable import qualified Maybe +import qualified Control.Monad as Monad import qualified Type import qualified Name @@ -16,42 +17,45 @@ import qualified ForSyDe.Backend.VHDL.AST as AST import VHDLTypes import FlattenTypes import TranslatorTypes +import Pretty -- | Create an entity for a given function createEntity :: HsFunction -- | The function signature -> FuncData -- | The function data collected so far - -> FuncData -- | The modified function data + -> VHDLState () createEntity hsfunc fdata = let func = flatFunc fdata in case func of -- Skip (builtin) functions without a FlatFunction - Nothing -> fdata + Nothing -> do return () -- Create an entity for all other functions Just flatfunc -> let - s = sigs flatfunc - a = args flatfunc - r = res flatfunc - args' = map (fmap (mkMap s)) a - res' = fmap (mkMap s) r + sigs = flat_sigs flatfunc + args = flat_args flatfunc + res = flat_res flatfunc + args' = map (fmap (mkMap sigs)) args + res' = fmap (mkMap sigs) res ent_decl' = createEntityAST hsfunc args' res' - entity' = Entity args' res' (Just ent_decl') + AST.EntityDec entity_id _ = ent_decl' + entity' = Entity entity_id args' res' (Just ent_decl') in - fdata { entity = Just entity' } + setEntity hsfunc entity' where - mkMap :: Eq id => [(id, SignalInfo)] -> id -> AST.VHDLId + mkMap :: Eq id => [(id, SignalInfo)] -> id -> (AST.VHDLId, AST.TypeMark) mkMap sigmap id = - mkVHDLId nm + (mkVHDLId nm, vhdl_ty ty) where info = Maybe.fromMaybe (error $ "Signal not found in the name map? This should not happen!") (lookup id sigmap) nm = Maybe.fromMaybe (error $ "Signal not named? This should not happen!") - (name info) + (sigName info) + ty = sigTy info -- | Create the VHDL AST for an entity createEntityAST :: @@ -64,23 +68,143 @@ createEntityAST hsfunc args res = AST.EntityDec vhdl_id ports where vhdl_id = mkEntityId hsfunc - ports = [] + ports = concatMap (mapToPorts AST.In) args + ++ mapToPorts AST.Out res + mapToPorts :: AST.Mode -> VHDLSignalMap -> [AST.IfaceSigDec] + mapToPorts mode m = + map (mkIfaceSigDec mode) (Foldable.toList m) + +-- | Create a port declaration +mkIfaceSigDec :: + AST.Mode -- | The mode for the port (In / Out) + -> (AST.VHDLId, AST.TypeMark) -- | The id and type for the port + -> AST.IfaceSigDec -- | The resulting port declaration + +mkIfaceSigDec mode (id, ty) = AST.IfaceSigDec id mode ty -- | Generate a VHDL entity name for the given hsfunc mkEntityId hsfunc = -- TODO: This doesn't work for functions with multiple signatures! mkVHDLId $ hsFuncName hsfunc +-- | Create an architecture for a given function +createArchitecture :: + HsFunction -- | The function signature + -> FuncData -- | The function data collected so far + -> VHDLState () + +createArchitecture hsfunc fdata = + let func = flatFunc fdata in + case func of + -- Skip (builtin) functions without a FlatFunction + Nothing -> do return () + -- Create an architecture for all other functions + Just flatfunc -> do + let sigs = flat_sigs flatfunc + let args = flat_args flatfunc + let res = flat_res flatfunc + let apps = flat_apps flatfunc + let entity_id = Maybe.fromMaybe + (error $ "Building architecture without an entity? This should not happen!") + (getEntityId fdata) + -- Create signal declarations for all signals that are not in args and + -- res + let sig_decs = [mkSigDec info | (id, info) <- sigs, (all (id `Foldable.notElem`) (res:args)) ] + -- Create component instantiations for all function applications + insts <- mapM (mkCompInsSm sigs) apps + let insts' = map AST.CSISm insts + let arch = AST.ArchBody (mkVHDLId "structural") (AST.NSimple entity_id) (map AST.BDISD sig_decs) insts' + setArchitecture hsfunc arch + +mkSigDec :: SignalInfo -> AST.SigDec +mkSigDec info = + AST.SigDec (mkVHDLId name) (vhdl_ty ty) Nothing + where + name = Maybe.fromMaybe + (error $ "Unnamed signal? This should not happen!") + (sigName info) + ty = sigTy info + +-- | Transforms a flat function application to a VHDL component instantiation. +mkCompInsSm :: + [(UnnamedSignal, SignalInfo)] -- | The signals in the current architecture + -> FApp UnnamedSignal -- | The application to look at. + -> VHDLState AST.CompInsSm -- | The corresponding VHDL component instantiation. + +mkCompInsSm sigs app = do + let hsfunc = appFunc app + fdata_maybe <- getFunc hsfunc + let fdata = Maybe.fromMaybe + (error $ "Using function '" ++ (prettyShow hsfunc) ++ "' that is not in the session? This should not happen!") + fdata_maybe + let entity = Maybe.fromMaybe + (error $ "Using function '" ++ (prettyShow hsfunc) ++ "' without entity declaration? This should not happen!") + (funcEntity fdata) + let entity_id = ent_id entity + label <- uniqueName (AST.fromVHDLId entity_id) + let portmaps = mkAssocElems sigs app entity + return $ AST.CompInsSm (mkVHDLId label) (AST.IUEntity (AST.NSimple entity_id)) (AST.PMapAspect portmaps) + +mkAssocElems :: + [(UnnamedSignal, SignalInfo)] -- | The signals in the current architecture + -> FApp UnnamedSignal -- | The application to look at. + -> Entity -- | The entity to map against. + -> [AST.AssocElem] -- | The resulting port maps + +mkAssocElems sigmap app entity = + -- Create the actual AssocElems + zipWith mkAssocElem ports sigs + where + -- Turn the ports and signals from a map into a flat list. This works, + -- since the maps must have an identical form by definition. TODO: Check + -- the similar form? + arg_ports = concat (map Foldable.toList (ent_args entity)) + res_ports = Foldable.toList (ent_res entity) + arg_sigs = (concat (map Foldable.toList (appArgs app))) + res_sigs = Foldable.toList (appRes app) + -- Extract the id part from the (id, type) tuple + ports = (map fst (arg_ports ++ res_ports)) + -- Translate signal numbers into names + sigs = (map (lookupSigName sigmap) (arg_sigs ++ res_sigs)) + +-- | Look up a signal in the signal name map +lookupSigName :: [(UnnamedSignal, SignalInfo)] -> UnnamedSignal -> String +lookupSigName sigs sig = name + where + info = Maybe.fromMaybe + (error $ "Unknown signal " ++ (show sig) ++ " used? This should not happen!") + (lookup sig sigs) + name = Maybe.fromMaybe + (error $ "Unnamed signal " ++ (show sig) ++ " used? This should not happen!") + (sigName info) + +-- | Create an VHDL port -> signal association +mkAssocElem :: AST.VHDLId -> String -> AST.AssocElem +mkAssocElem port signal = Just port AST.:=>: (AST.ADName (AST.NSimple (mkVHDLId signal))) + +-- | Extracts the generated entity id from the given funcdata +getEntityId :: FuncData -> Maybe AST.VHDLId +getEntityId fdata = + case funcEntity fdata of + Nothing -> Nothing + Just e -> case ent_decl e of + Nothing -> Nothing + Just (AST.EntityDec id _) -> Just id + getLibraryUnits :: (HsFunction, FuncData) -- | A function from the session -> [AST.LibraryUnit] -- | The library units it generates getLibraryUnits (hsfunc, fdata) = - case entity fdata of + case funcEntity fdata of Nothing -> [] Just ent -> case ent_decl ent of Nothing -> [] Just decl -> [AST.LUEntity decl] + ++ + case funcArch fdata of + Nothing -> [] + Just arch -> [AST.LUArch arch] -- | The VHDL Bit type bit_ty :: AST.TypeMark