X-Git-Url: https://git.stderr.nl/gitweb?a=blobdiff_plain;f=VHDL.hs;h=ee61c500a6916f676fd75e1c7566d6d8bb868eab;hb=157dae90bdd7c45613c6ad6185383a1137b2323f;hp=8c0a2ec93835605f964ea0745159b86a59739fd2;hpb=f3f93a3ced1b73a8ea40ec065544504bb4fe87f5;p=matthijs%2Fmaster-project%2Fc%CE%BBash.git diff --git a/VHDL.hs b/VHDL.hs index 8c0a2ec..ee61c50 100644 --- a/VHDL.hs +++ b/VHDL.hs @@ -5,6 +5,7 @@ module VHDL where import qualified Data.Foldable as Foldable import qualified Maybe +import qualified Control.Monad as Monad import qualified Type import qualified Name @@ -14,8 +15,10 @@ import Outputable ( showSDoc, ppr ) import qualified ForSyDe.Backend.VHDL.AST as AST import VHDLTypes +import Flatten import FlattenTypes import TranslatorTypes +import Pretty -- | Create an entity for a given function createEntity :: @@ -38,7 +41,8 @@ createEntity hsfunc fdata = 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 setEntity hsfunc entity' where @@ -54,7 +58,7 @@ createEntity hsfunc fdata = (sigName info) ty = sigTy info --- | Create the VHDL AST for an entity + -- | Create the VHDL AST for an entity createEntityAST :: HsFunction -- | The signature of the function we're working with -> [VHDLSignalMap] -- | The entity's arguments @@ -67,9 +71,16 @@ createEntityAST hsfunc args res = vhdl_id = mkEntityId hsfunc ports = concatMap (mapToPorts AST.In) args ++ mapToPorts AST.Out res + ++ clk_port mapToPorts :: AST.Mode -> VHDLSignalMap -> [AST.IfaceSigDec] mapToPorts mode m = map (mkIfaceSigDec mode) (Foldable.toList m) + -- Add a clk port if we have state + clk_port = if hasState hsfunc + then + [AST.IfaceSigDec (mkVHDLId "clk") AST.In VHDL.std_logic_ty] + else + [] -- | Create a port declaration mkIfaceSigDec :: @@ -108,31 +119,95 @@ createArchitecture hsfunc fdata = -- 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 apps + insts <- mapM (mkCompInsSm sigs) apps + let procs = map mkStateProcSm (getOwnStates hsfunc flatfunc) let insts' = map AST.CSISm insts - let arch = AST.ArchBody (mkVHDLId "structural") (AST.NSimple entity_id) (map AST.BDISD sig_decs) insts' + let procs' = map AST.CSPSm procs + let arch = AST.ArchBody (mkVHDLId "structural") (AST.NSimple entity_id) (map AST.BDISD sig_decs) (insts' ++ procs') setArchitecture hsfunc arch +mkStateProcSm :: (Int, SignalInfo, SignalInfo) -> AST.ProcSm +mkStateProcSm (num, old, new) = + AST.ProcSm label [clk] [statement] + where + label = mkVHDLId $ "state_" ++ (show num) + clk = mkVHDLId "clk" + rising_edge = AST.NSimple $ mkVHDLId "rising_edge" + wform = AST.Wform [AST.WformElem (AST.PrimName $ AST.NSimple $ getSignalId new) Nothing] + assign = AST.SigAssign (AST.NSimple $ getSignalId old) wform + rising_edge_clk = AST.PrimFCall $ AST.FCall rising_edge [Nothing AST.:=>: (AST.ADName $ AST.NSimple clk)] + statement = AST.IfSm rising_edge_clk [assign] [] Nothing + mkSigDec :: SignalInfo -> AST.SigDec mkSigDec info = - AST.SigDec (mkVHDLId name) (vhdl_ty ty) Nothing + AST.SigDec (getSignalId info) (vhdl_ty ty) Nothing where - name = Maybe.fromMaybe + ty = sigTy info + +-- | Creates a VHDL Id from a named SignalInfo. Errors out if the SignalInfo +-- is not named. +getSignalId :: SignalInfo -> AST.VHDLId +getSignalId info = + mkVHDLId $ 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 :: - FApp UnnamedSignal -- | The application to look at. + [(UnnamedSignal, SignalInfo)] -- | The signals in the current architecture + -> FApp UnnamedSignal -- | The application to look at. -> VHDLState AST.CompInsSm -- | The corresponding VHDL component instantiation. -mkCompInsSm app = do - return $ AST.CompInsSm label (AST.IUEntity (AST.NSimple entity_id)) (AST.PMapAspect portmaps) +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 - entity_id = mkVHDLId "foo" - label = mkVHDLId "app" - portmaps = [] + -- 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 @@ -162,6 +237,10 @@ getLibraryUnits (hsfunc, fdata) = bit_ty :: AST.TypeMark bit_ty = AST.unsafeVHDLBasicId "Bit" +-- | The VHDL std_logic +std_logic_ty :: AST.TypeMark +std_logic_ty = AST.unsafeVHDLBasicId "std_logic" + -- Translate a Haskell type to a VHDL type vhdl_ty :: Type.Type -> AST.TypeMark vhdl_ty ty = Maybe.fromMaybe