X-Git-Url: https://git.stderr.nl/gitweb?a=blobdiff_plain;f=VHDL.hs;h=9cea6fe74c333910ef8fd1b9919d61e8e5f9694f;hb=7a5b4eb318626f327dd6b0d69e99a8247f56399c;hp=192714778d5605c40efd37dc2cc85dc1540890f4;hpb=85ee6f8e10f7dcc73db62a55a07d924bc002f216;p=matthijs%2Fmaster-project%2Fc%CE%BBash.git diff --git a/VHDL.hs b/VHDL.hs index 1927147..9cea6fe 100644 --- a/VHDL.hs +++ b/VHDL.hs @@ -4,6 +4,7 @@ module VHDL where import Data.Traversable +import qualified Data.Foldable as Foldable import qualified Maybe import qualified Type @@ -42,9 +43,9 @@ createEntity hsfunc fdata = in fdata { entity = Just 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!") @@ -52,6 +53,7 @@ createEntity hsfunc fdata = nm = Maybe.fromMaybe (error $ "Signal not named? This should not happen!") (sigName info) + ty = sigTy info -- | Create the VHDL AST for an entity createEntityAST :: @@ -64,13 +66,68 @@ 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 + -> FuncData -- | The modified function data + +createArchitecture hsfunc fdata = + let func = flatFunc fdata in + case func of + -- Skip (builtin) functions without a FlatFunction + Nothing -> fdata + -- Create an architecture for all other functions + Just flatfunc -> + let + s = sigs flatfunc + a = args flatfunc + r = res flatfunc + entity_id = Maybe.fromMaybe + (error $ "Building architecture without an entity? This should not happen!") + (getEntityId fdata) + sig_decs = [mkSigDec info | (id, info) <- s, (all (id `Foldable.notElem`) (r:a)) ] + arch = AST.ArchBody (mkVHDLId "structural") (AST.NSimple entity_id) (map AST.BDISD sig_decs) [] + in + fdata { funcArch = Just 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 + +-- | Extracts the generated entity id from the given funcdata +getEntityId :: FuncData -> Maybe AST.VHDLId +getEntityId fdata = + case entity 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 @@ -81,6 +138,10 @@ getLibraryUnits (hsfunc, fdata) = 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