X-Git-Url: https://git.stderr.nl/gitweb?a=blobdiff_plain;f=VHDL.hs;h=72b0a925ec8554753109ff04946eb667a6581c04;hb=dfdf88c20bacf8f8e7863cf7a41c86c869735f6f;hp=4f8d1055af2e0df5a9db8b82ad7a709505a4e216;hpb=b4b8def2facb3d3bf92ee02a499405efdf986324;p=matthijs%2Fmaster-project%2Fc%CE%BBash.git diff --git a/VHDL.hs b/VHDL.hs index 4f8d105..72b0a92 100644 --- a/VHDL.hs +++ b/VHDL.hs @@ -63,6 +63,9 @@ createDesignFiles binds = tyfun_decls = Map.elems (final_session ^.vsTypeFuns) ty_decls = map mktydecl $ Map.elems (final_session ^. vsTypes) vec_decls = map (\(v_id, v_def) -> AST.PDITD $ AST.TypeDec v_id v_def) (Map.elems (final_session ^. vsElemTypes)) + tfvec_index_decl = AST.PDISD $ AST.SubtypeDec tfvec_indexTM tfvec_index_def + tfvec_range = AST.ConstraintRange $ AST.SubTypeRange (AST.PrimLit "-1") (AST.PrimName $ AST.NAttribute $ AST.AttribName (AST.NSimple integerTM) highId Nothing) + tfvec_index_def = AST.SubtypeIn integerTM (Just tfvec_range) ieee_context = [ AST.Library $ mkVHDLBasicId "IEEE", mkUseAll ["IEEE", "std_logic_1164"], @@ -71,7 +74,7 @@ createDesignFiles binds = full_context = mkUseAll ["work", "types"] : ieee_context - type_package_dec = AST.LUPackageDec $ AST.PackageDec (mkVHDLBasicId "types") (vec_decls ++ ty_decls ++ subProgSpecs) + type_package_dec = AST.LUPackageDec $ AST.PackageDec (mkVHDLBasicId "types") ([tfvec_index_decl] ++ vec_decls ++ ty_decls ++ subProgSpecs) type_package_body = AST.LUPackageBody $ AST.PackageBody typesId (concat tyfun_decls) subProgSpecs = concat (map subProgSpec tyfun_decls) subProgSpec = map (\(AST.SubProgBody spec _ _) -> AST.PDISS spec) @@ -261,6 +264,17 @@ mkConcSm :: (CoreSyn.CoreBndr, CoreSyn.CoreExpr) -- ^ The binding to process -> VHDLState [AST.ConcSm] -- ^ The corresponding VHDL component instantiations. + +-- Ignore Cast expressions, they should not longer have any meaning as long as +-- the type works out. +mkConcSm (bndr, Cast expr ty) = mkConcSm (bndr, expr) + +-- For simple a = b assignments, just generate an unconditional signal +-- assignment. This should only happen for dataconstructors without arguments. +-- TODO: Integrate this with the below code for application (essentially this +-- is an application without arguments) +mkConcSm (bndr, Var v) = return $ [mkUncondAssign (Left bndr) (varToVHDLExpr v)] + mkConcSm (bndr, app@(CoreSyn.App _ _))= do let (CoreSyn.Var f, args) = CoreSyn.collectArgs app let valargs' = filter isValArg args @@ -286,18 +300,32 @@ mkConcSm (bndr, app@(CoreSyn.App _ _))= do -- It's a global value imported from elsewhere. These can be builtin -- functions. funSignatures <- getA vsNameTable + signatures <- getA vsSignatures case (Map.lookup (bndrToString f) funSignatures) of Just (arg_count, builder) -> if length valargs == arg_count then - let - sigs = map (bndrToString.varBndr) valargs - sigsNames = map (\signal -> (AST.PrimName (AST.NSimple (mkVHDLExtId signal)))) sigs - func = builder sigsNames - src_wform = AST.Wform [AST.WformElem func Nothing] - dst_name = AST.NSimple (mkVHDLExtId (bndrToString bndr)) - assign = dst_name AST.:<==: (AST.ConWforms [] src_wform Nothing) - in - return [AST.CSSASm assign] + case builder of + Left funBuilder -> + let + sigs = map (varToVHDLExpr.varBndr) valargs + func = funBuilder sigs + src_wform = AST.Wform [AST.WformElem func Nothing] + dst_name = AST.NSimple (mkVHDLExtId (bndrToString bndr)) + assign = dst_name AST.:<==: (AST.ConWforms [] src_wform Nothing) + in + return [AST.CSSASm assign] + Right genBuilder -> + let + ty = Var.varType bndr + len = tfvec_len ty + sigs = map varBndr valargs + signature = Maybe.fromMaybe + (error $ "Using function '" ++ (bndrToString (head sigs)) ++ "' without signature? This should not happen!") + (Map.lookup (head sigs) signatures) + arg_names = map (mkVHDLExtId . bndrToString) (tail sigs) + dst_name = mkVHDLExtId (bndrToString bndr) + genSm = genBuilder len signature (arg_names ++ [dst_name]) + in return [AST.CSGSm genSm] 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 @@ -343,7 +371,7 @@ mkConcSm (bndr, expr@(Case (Var scrut) b ty [alt])) = -- first is the default case, if there is any. mkConcSm (bndr, (Case (Var scrut) b ty [(_, _, Var false), (con, _, Var true)])) = let - cond_expr = (varToVHDLExpr scrut) AST.:=: (conToVHDLExpr con) + cond_expr = (varToVHDLExpr scrut) AST.:=: (altconToVHDLExpr con) true_expr = (varToVHDLExpr true) false_expr = (varToVHDLExpr false) in @@ -419,13 +447,26 @@ getFieldLabels ty = do -- Turn a variable reference into a AST expression varToVHDLExpr :: Var.Var -> AST.Expr -varToVHDLExpr var = AST.PrimName $ AST.NSimple $ bndrToVHDLId var - --- Turn a 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. -conToVHDLExpr :: CoreSyn.AltCon -> AST.Expr -conToVHDLExpr (DataAlt dc) = AST.PrimLit lit +varToVHDLExpr var = + case Id.isDataConWorkId_maybe var of + Just dc -> dataconToVHDLExpr dc + -- This is a dataconstructor. + -- Not a datacon, just another signal. Perhaps we should check for + -- local/global here as well? + Nothing -> AST.PrimName $ AST.NSimple $ bndrToVHDLId var + +-- 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. +altconToVHDLExpr :: CoreSyn.AltCon -> AST.Expr +altconToVHDLExpr (DataAlt dc) = dataconToVHDLExpr dc + +altconToVHDLExpr (LitAlt _) = error "VHDL.conToVHDLExpr Literals not support in case alternatives yet" +altconToVHDLExpr DEFAULT = error "VHDL.conToVHDLExpr DEFAULT alternative should not occur here!" + +-- Turn a datacon (without arguments!) into a VHDL expression. +dataconToVHDLExpr :: DataCon.DataCon -> AST.Expr +dataconToVHDLExpr dc = AST.PrimLit lit where tycon = DataCon.dataConTyCon dc tyname = TyCon.tyConName tycon @@ -434,9 +475,6 @@ conToVHDLExpr (DataAlt dc) = AST.PrimLit lit -- TODO: Do something more robust than string matching "Bit" -> case Name.getOccString dcname of "High" -> "'1'"; "Low" -> "'0'" "Bool" -> case Name.getOccString dcname of "True" -> "true"; "False" -> "false" -conToVHDLExpr (LitAlt _) = error "VHDL.conToVHDLExpr Literals not support in case alternatives yet" -conToVHDLExpr DEFAULT = error "VHDL.conToVHDLExpr DEFAULT alternative should not occur here!" - {- @@ -568,13 +606,13 @@ construct_vhdl_ty ty = do let name = Name.getOccString (TyCon.tyConName tycon) case name of "TFVec" -> do - res <- mk_vector_ty (tfvec_len ty) (tfvec_elem ty) ty + res <- mk_vector_ty (tfvec_len ty) (tfvec_elem ty) return $ Just $ (Arrow.second Right) res -- "SizedWord" -> do -- res <- mk_vector_ty (sized_word_len ty) ty -- return $ Just $ (Arrow.second Left) res "RangedWord" -> do - res <- mk_natural_ty 0 (ranged_word_bound ty) ty + res <- mk_natural_ty 0 (ranged_word_bound ty) return $ Just $ (Arrow.second Right) res -- Create a custom type from this tycon otherwise -> mk_tycon_ty tycon args @@ -613,10 +651,9 @@ mk_tycon_ty tycon args = mk_vector_ty :: Int -- ^ The length of the vector -> Type.Type -- ^ The Haskell element type of the Vector - -> Type.Type -- ^ The Haskell type to create a VHDL type for -> VHDLState (AST.TypeMark, AST.SubtypeIn) -- The typemark created. -mk_vector_ty len el_ty ty = do +mk_vector_ty len el_ty = do elem_types_map <- getA vsElemTypes el_ty_tm <- vhdl_ty el_ty let ty_id = mkVHDLExtId $ "vector-"++ (AST.fromVHDLId el_ty_tm) ++ "-0_to_" ++ (show len) @@ -628,24 +665,22 @@ mk_vector_ty len el_ty ty = do return (ty_id, ty_def) Nothing -> do let vec_id = mkVHDLExtId $ "vector_" ++ (AST.fromVHDLId el_ty_tm) - let vec_def = AST.TDA $ AST.UnconsArrayDef [naturalTM] el_ty_tm + let vec_def = AST.TDA $ AST.UnconsArrayDef [tfvec_indexTM] el_ty_tm modA vsElemTypes (Map.insert (OrdType el_ty) (vec_id, vec_def)) - modA vsTypeFuns (Map.insert (OrdType ty) (genUnconsVectorFuns el_ty_tm vec_id)) + modA vsTypeFuns (Map.insert (OrdType el_ty) (genUnconsVectorFuns el_ty_tm vec_id)) let ty_def = AST.SubtypeIn vec_id (Just range) return (ty_id, ty_def) mk_natural_ty :: Int -- ^ The minimum bound (> 0) -> Int -- ^ The maximum bound (> minimum bound) - -> Type.Type -- ^ The Haskell type to create a VHDL type for -> VHDLState (AST.TypeMark, AST.SubtypeIn) -- The typemark created. -mk_natural_ty min_bound max_bound ty = do +mk_natural_ty min_bound max_bound = do let ty_id = mkVHDLExtId $ "nat_" ++ (show min_bound) ++ "_to_" ++ (show max_bound) let range = AST.ConstraintRange $ AST.SubTypeRange (AST.PrimLit $ (show min_bound)) (AST.PrimLit $ (show max_bound)) let ty_def = AST.SubtypeIn naturalTM (Just range) return (ty_id, ty_def) - - + builtin_types = Map.fromList [ ("Bit", std_logic_ty),