X-Git-Url: https://git.stderr.nl/gitweb?a=blobdiff_plain;f=VHDL.hs;h=f176b9eea6be2c9457280f7e720a678d4fe3f420;hb=059c20c7b953a21097939a47ecac7f6cad05541a;hp=b23e5f3117acc6481e37062d2816c28754365d46;hpb=20fbdf46508998bd11da03f3abd6e8725508b0a1;p=matthijs%2Fmaster-project%2Fc%CE%BBash.git diff --git a/VHDL.hs b/VHDL.hs index b23e5f3..f176b9e 100644 --- a/VHDL.hs +++ b/VHDL.hs @@ -4,10 +4,16 @@ module VHDL where import qualified Data.Foldable as Foldable +import qualified Data.List as List +import qualified Data.Map as Map import qualified Maybe import qualified Control.Monad as Monad +import qualified Control.Arrow as Arrow +import qualified Data.Traversable as Traversable +import qualified Data.Monoid as Monoid import qualified Type +import qualified TysWiredIn import qualified Name import qualified TyCon import Outputable ( showSDoc, ppr ) @@ -15,39 +21,60 @@ import Outputable ( showSDoc, ppr ) import qualified ForSyDe.Backend.VHDL.AST as AST import VHDLTypes +import Flatten import FlattenTypes import TranslatorTypes import Pretty +getDesignFiles :: [FuncData] -> [AST.DesignFile] +getDesignFiles funcs = + map (AST.DesignFile context) units + where + units = filter (not.null) $ map getLibraryUnits funcs + context = [ + AST.Library $ mkVHDLId "IEEE", + AST.Use $ (AST.NSimple $ mkVHDLId "IEEE.std_logic_1164") AST.:.: AST.All] + -- | Create an entity for a given function createEntity :: HsFunction -- | The function signature -> FuncData -- | The function data collected so far - -> VHDLState () + -> Maybe Entity -- | The resulting entity. Should return the existing + --- Entity for builtin functions. createEntity hsfunc fdata = - let func = flatFunc fdata in - case func of + case flatFunc fdata of -- Skip (builtin) functions without a FlatFunction - Nothing -> do return () + Nothing -> funcEntity fdata -- Create an entity for all other functions Just flatfunc -> - let sigs = flat_sigs flatfunc args = flat_args flatfunc res = flat_res flatfunc - args' = map (fmap (mkMap sigs)) args - res' = fmap (mkMap sigs) res + (ty_decls, args') = Traversable.traverse (Traversable.traverse (mkMap sigs)) args + (ty_decls', res') = Traversable.traverse (mkMap sigs) res + -- TODO: Unique ty_decls ent_decl' = createEntityAST hsfunc args' res' + pkg_id = mkVHDLId $ (AST.fromVHDLId entity_id) ++ "_types" + pkg_decl = if null ty_decls && null ty_decls' + then Nothing + else Just $ AST.PackageDec pkg_id (map AST.PDITD $ ty_decls ++ ty_decls') AST.EntityDec entity_id _ = ent_decl' - entity' = Entity entity_id args' res' (Just ent_decl') - in - setEntity hsfunc entity' + in + Just $ Entity entity_id args' res' (Just ent_decl') pkg_decl where - mkMap :: Eq id => [(id, SignalInfo)] -> id -> (AST.VHDLId, AST.TypeMark) + mkMap :: + [(SignalId, SignalInfo)] + -> SignalId + -> ([AST.TypeDec], Maybe (AST.VHDLId, AST.TypeMark)) mkMap sigmap id = - (mkVHDLId nm, vhdl_ty ty) + if isPortSigUse $ sigUse info + then + let (decs, type_mark) = vhdl_ty ty in + (decs, Just (mkVHDLId nm, type_mark)) + else + (Monoid.mempty, Nothing) where info = Maybe.fromMaybe (error $ "Signal not found in the name map? This should not happen!") @@ -57,7 +84,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 @@ -70,17 +97,25 @@ 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) + Maybe.catMaybes $ 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 :: 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 + -> Maybe (AST.VHDLId, AST.TypeMark) -- | The id and type for the port + -> Maybe AST.IfaceSigDec -- | The resulting port declaration -mkIfaceSigDec mode (id, ty) = AST.IfaceSigDec id mode ty +mkIfaceSigDec mode (Just (id, ty)) = Just $ AST.IfaceSigDec id mode ty +mkIfaceSigDec _ Nothing = Nothing -- | Generate a VHDL entity name for the given hsfunc mkEntityId hsfunc = @@ -89,86 +124,172 @@ mkEntityId hsfunc = -- | Create an architecture for a given function createArchitecture :: - HsFunction -- | The function signature - -> FuncData -- | The function data collected so far - -> VHDLState () + FuncMap -- ^ The functions in the current session + -> HsFunction -- ^ The function signature + -> FuncData -- ^ The function data collected so far + -> Maybe AST.ArchBody -- ^ The architecture for this function -createArchitecture hsfunc fdata = - let func = flatFunc fdata in - case func of +createArchitecture funcs hsfunc fdata = + case flatFunc fdata of -- Skip (builtin) functions without a FlatFunction - Nothing -> do return () + Nothing -> funcArch fdata -- 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 + Just flatfunc -> + let + sigs = flat_sigs flatfunc + args = flat_args flatfunc + res = flat_res flatfunc + defs = flat_defs flatfunc + 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 + -- Create signal declarations for all signals that are not in args and + -- res + (ty_decls, sig_decs) = Arrow.second Maybe.catMaybes $ Traversable.traverse (mkSigDec . snd) sigs + -- TODO: Unique ty_decls + -- TODO: Store ty_decls somewhere + -- Create concurrent statements for all signal definitions + statements = zipWith (mkConcSm funcs sigs) defs [0..] + procs = map mkStateProcSm (makeStatePairs flatfunc) + procs' = map AST.CSPSm procs + in + Just $ AST.ArchBody (mkVHDLId "structural") (AST.NSimple entity_id) (map AST.BDISD sig_decs) (statements ++ procs') + +-- | Looks up all pairs of old state, new state signals, together with +-- the state id they represent. +makeStatePairs :: FlatFunction -> [(StateId, SignalInfo, SignalInfo)] +makeStatePairs flatfunc = + [(Maybe.fromJust $ oldStateId $ sigUse old_info, old_info, new_info) + | old_info <- map snd (flat_sigs flatfunc) + , new_info <- map snd (flat_sigs flatfunc) + -- old_info must be an old state (and, because of the next equality, + -- new_info must be a new state). + , Maybe.isJust $ oldStateId $ sigUse old_info + -- And the state numbers must match + , (oldStateId $ sigUse old_info) == (newStateId $ sigUse new_info)] + + -- Replace the second tuple element with the corresponding SignalInfo + --args_states = map (Arrow.second $ signalInfo sigs) args +mkStateProcSm :: (StateId, 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.TypeDec], Maybe AST.SigDec) mkSigDec info = - AST.SigDec (mkVHDLId name) (vhdl_ty ty) Nothing + let use = sigUse info in + if isInternalSigUse use || isStateSigUse use then + let (ty_decls, type_mark) = vhdl_ty ty in + (ty_decls, Just $ AST.SigDec (getSignalId info) type_mark Nothing) + else + ([], 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 :: - [(UnnamedSignal, SignalInfo)] -- | The signals in the current architecture - -> FApp UnnamedSignal -- | The application to look at. - -> VHDLState AST.CompInsSm -- | The corresponding VHDL component instantiation. +-- | Transforms a signal definition into a VHDL concurrent statement +mkConcSm :: + FuncMap -- ^ The functions in the current session + -> [(SignalId, SignalInfo)] -- ^ The signals in the current architecture + -> SigDef -- ^ The signal definition + -> Int -- ^ A number that will be unique for all + -- concurrent statements in the architecture. + -> AST.ConcSm -- ^ The corresponding VHDL component instantiation. -mkCompInsSm sigs app = do - let hsfunc = appFunc app - fdata_maybe <- getFunc hsfunc - let fdata = Maybe.fromMaybe +mkConcSm funcs sigs (FApp hsfunc args res) num = + let + fdata_maybe = Map.lookup hsfunc funcs + fdata = Maybe.fromMaybe (error $ "Using function '" ++ (prettyShow hsfunc) ++ "' that is not in the session? This should not happen!") fdata_maybe - let entity = Maybe.fromMaybe + 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) + entity_id = ent_id entity + label = (AST.fromVHDLId entity_id) ++ "_" ++ (show num) + -- Add a clk port if we have state + clk_port = Maybe.fromJust $ mkAssocElem (Just $ mkVHDLId "clk") "clk" + portmaps = mkAssocElems sigs args res entity ++ (if hasState hsfunc then [clk_port] else []) + in + AST.CSISm $ AST.CompInsSm (mkVHDLId label) (AST.IUEntity (AST.NSimple entity_id)) (AST.PMapAspect portmaps) + +mkConcSm _ sigs (UncondDef src dst) _ = + let + src_expr = vhdl_expr src + src_wform = AST.Wform [AST.WformElem src_expr Nothing] + dst_name = AST.NSimple (getSignalId $ signalInfo sigs dst) + assign = dst_name AST.:<==: (AST.ConWforms [] src_wform Nothing) + in + AST.CSSASm assign + where + vhdl_expr (Left id) = mkIdExpr sigs id + vhdl_expr (Right expr) = + case expr of + (EqLit id lit) -> + (mkIdExpr sigs id) AST.:=: (AST.PrimLit lit) + (Literal lit) -> + AST.PrimLit lit + (Eq a b) -> + (mkIdExpr sigs a) AST.:=: (mkIdExpr sigs b) + +mkConcSm _ sigs (CondDef cond true false dst) _ = + let + cond_expr = mkIdExpr sigs cond + true_expr = mkIdExpr sigs true + false_expr = mkIdExpr sigs false + false_wform = AST.Wform [AST.WformElem false_expr Nothing] + true_wform = AST.Wform [AST.WformElem true_expr Nothing] + whenelse = AST.WhenElse true_wform cond_expr + dst_name = AST.NSimple (getSignalId $ signalInfo sigs dst) + assign = dst_name AST.:<==: (AST.ConWforms [whenelse] false_wform Nothing) + in + AST.CSSASm assign + +-- | Turn a SignalId into a VHDL Expr +mkIdExpr :: [(SignalId, SignalInfo)] -> SignalId -> AST.Expr +mkIdExpr sigs id = + let src_name = AST.NSimple (getSignalId $ signalInfo sigs id) in + AST.PrimName src_name mkAssocElems :: - [(UnnamedSignal, SignalInfo)] -- | The signals in the current architecture - -> FApp UnnamedSignal -- | The application to look at. + [(SignalId, SignalInfo)] -- | The signals in the current architecture + -> [SignalMap] -- | The signals that are applied to function + -> SignalMap -- | the signals in which to store the function result -> Entity -- | The entity to map against. -> [AST.AssocElem] -- | The resulting port maps -mkAssocElems sigmap app entity = +mkAssocElems sigmap args res entity = -- Create the actual AssocElems - zipWith mkAssocElem ports sigs + Maybe.catMaybes $ 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) + arg_sigs = (concat (map Foldable.toList args)) + res_sigs = Foldable.toList res -- Extract the id part from the (id, type) tuple - ports = (map fst (arg_ports ++ res_ports)) + ports = (map (fmap 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 :: [(SignalId, SignalInfo)] -> SignalId -> String lookupSigName sigs sig = name where info = Maybe.fromMaybe @@ -179,8 +300,9 @@ lookupSigName sigs sig = name (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))) +mkAssocElem :: Maybe AST.VHDLId -> String -> Maybe AST.AssocElem +mkAssocElem (Just port) signal = Just $ Just port AST.:=>: (AST.ADName (AST.NSimple (mkVHDLId signal))) +mkAssocElem Nothing _ = Nothing -- | Extracts the generated entity id from the given funcdata getEntityId :: FuncData -> Maybe AST.VHDLId @@ -192,42 +314,78 @@ getEntityId fdata = Just (AST.EntityDec id _) -> Just id getLibraryUnits :: - (HsFunction, FuncData) -- | A function from the session - -> [AST.LibraryUnit] -- | The library units it generates + FuncData -- | A function from the session + -> [AST.LibraryUnit] -- | The entity, architecture and optional package for the function -getLibraryUnits (hsfunc, fdata) = +getLibraryUnits fdata = case funcEntity fdata of Nothing -> [] - Just ent -> case ent_decl ent of + Just ent -> + case ent_decl ent of Nothing -> [] - Just decl -> [AST.LUEntity decl] - ++ - case funcArch fdata of - Nothing -> [] - Just arch -> [AST.LUArch arch] + Just decl -> + case funcArch fdata of + Nothing -> [] + Just arch -> + [AST.LUEntity decl, AST.LUArch arch] + ++ (Maybe.maybeToList (fmap AST.LUPackageDec $ ent_pkg_decl ent)) -- | The VHDL Bit type bit_ty :: AST.TypeMark bit_ty = AST.unsafeVHDLBasicId "Bit" +-- | The VHDL Boolean type +bool_ty :: AST.TypeMark +bool_ty = AST.unsafeVHDLBasicId "Boolean" + +-- | 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 :: Type.Type -> ([AST.TypeDec], AST.TypeMark) vhdl_ty ty = Maybe.fromMaybe (error $ "Unsupported Haskell type: " ++ (showSDoc $ ppr ty)) (vhdl_ty_maybe ty) --- Translate a Haskell type to a VHDL type -vhdl_ty_maybe :: Type.Type -> Maybe AST.TypeMark +-- Translate a Haskell type to a VHDL type, optionally generating a type +-- declaration for the type. +vhdl_ty_maybe :: Type.Type -> Maybe ([AST.TypeDec], AST.TypeMark) vhdl_ty_maybe ty = - case Type.splitTyConApp_maybe ty of - Just (tycon, args) -> - let name = TyCon.tyConName tycon in - -- TODO: Do something more robust than string matching - case Name.getOccString name of - "Bit" -> Just bit_ty - otherwise -> Nothing - otherwise -> Nothing + if Type.coreEqType ty TysWiredIn.boolTy + then + Just ([], bool_ty) + else + case Type.splitTyConApp_maybe ty of + Just (tycon, args) -> + let name = TyCon.tyConName tycon in + -- TODO: Do something more robust than string matching + case Name.getOccString name of + "Bit" -> Just ([], std_logic_ty) + "FSVec" -> + let + [len, el_ty] = args + -- TODO: Find actual number + ty_id = mkVHDLId ("vector_" ++ (show len)) + -- TODO: Use el_ty + range = AST.IndexConstraint [AST.ToRange (AST.PrimLit "0") (AST.PrimLit "16")] + ty_def = AST.TDA $ AST.ConsArrayDef range std_logic_ty + ty_dec = AST.TypeDec ty_id ty_def + in + Just ([ty_dec], ty_id) + otherwise -> Nothing + otherwise -> Nothing -- Shortcut mkVHDLId :: String -> AST.VHDLId -mkVHDLId = AST.unsafeVHDLBasicId +mkVHDLId s = + AST.unsafeVHDLBasicId $ (strip_multiscore . strip_invalid) s + where + -- Strip invalid characters. + strip_invalid = filter (`elem` ['A'..'Z'] ++ ['a'..'z'] ++ ['0'..'9'] ++ "_.") + -- Strip multiple adjacent underscores + strip_multiscore = concat . map (\cs -> + case cs of + ('_':_) -> "_" + _ -> cs + ) . List.group