X-Git-Url: https://git.stderr.nl/gitweb?a=blobdiff_plain;f=VHDL.hs;h=f838cbafcf5a4f9ee30a1ec73673543e84800c56;hb=91914df9b344ccf0bc3242dc28ce74a8d6721944;hp=319b5b7ef900062f9a6c809f3645ba3fae18f08f;hpb=ff9a8487475aa90d2f212fd24169503993a4a27d;p=matthijs%2Fmaster-project%2Fc%CE%BBash.git diff --git a/VHDL.hs b/VHDL.hs index 319b5b7..f838cba 100644 --- a/VHDL.hs +++ b/VHDL.hs @@ -22,12 +22,13 @@ import Debug.Trace import qualified ForSyDe.Backend.VHDL.AST as AST -- GHC API +import CoreSyn import qualified Type import qualified Name import qualified OccName import qualified Var import qualified TyCon -import qualified CoreSyn +import qualified DataCon import Outputable ( showSDoc, ppr ) -- Local imports @@ -47,14 +48,16 @@ createDesignFiles :: -> [(AST.VHDLId, AST.DesignFile)] createDesignFiles binds = - (mkVHDLBasicId "types", AST.DesignFile ieee_context [type_package]) : + (mkVHDLBasicId "types", AST.DesignFile ieee_context [type_package_dec, type_package_body]) : map (Arrow.second $ AST.DesignFile full_context) units where - init_session = VHDLSession Map.empty Map.empty builtin_funcs globalNameTable + init_session = VHDLSession Map.empty Map.empty Map.empty builtin_funcs globalNameTable (units, final_session) = State.runState (createLibraryUnits binds) init_session ty_decls = Map.elems (final_session ^. vsTypes) + subty_decls = Map.elems (final_session ^. vsSubTypes) + tyfun_decls = Map.elems (final_session ^.vsTypeFuns) ieee_context = [ AST.Library $ mkVHDLBasicId "IEEE", mkUseAll ["IEEE", "std_logic_1164"], @@ -63,7 +66,12 @@ createDesignFiles binds = full_context = mkUseAll ["work", "types"] : ieee_context - type_package = AST.LUPackageDec $ AST.PackageDec (mkVHDLBasicId "types") (map (AST.PDITD . snd) ty_decls) + type_package_dec = AST.LUPackageDec $ AST.PackageDec (mkVHDLBasicId "types") (packageTypeDecs ++ packageSubtypeDecs ++ subProgSpecs) + type_package_body = AST.LUPackageBody $ AST.PackageBody typesId (concat tyfun_decls) + packageTypeDecs = map (AST.PDITD . snd) ty_decls + packageSubtypeDecs = map (AST.PDISD . snd) subty_decls + subProgSpecs = concat (map subProgSpec tyfun_decls) + subProgSpec = map (\(AST.SubProgBody spec _ _) -> AST.PDISS spec) -- Create a use foo.bar.all statement. Takes a list of components in the used -- name. Must contain at least two components @@ -278,6 +286,50 @@ mkConcSm (bndr, app@(CoreSyn.App _ _))= do -- least compile for now. mkConcSm (bndr, CoreSyn.Var _) = return $ AST.CSPSm $ AST.ProcSm (mkVHDLBasicId "unused") [] [] +-- A single alt case must be a selector +mkConcSm (bndr, (Case (Var scrut) b ty [alt])) = error "Single case alt not supported yet" + +-- Multiple case alt are be conditional assignments and have only wild +-- binders in the alts and only variables in the case values and a variable +-- for a scrutinee. We check the constructor of the second alt, since the +-- 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) + true_expr = (varToVHDLExpr true) + false_expr = (varToVHDLExpr 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 (bndrToVHDLId bndr) + assign = dst_name AST.:<==: (AST.ConWforms [whenelse] false_wform Nothing) + in + return $ AST.CSSASm assign +mkConcSm (_, (Case (Var _) _ _ alts)) = error "VHDL.mkConcSm Not in normal form: Case statement with more than two alternatives" +mkConcSm (_, Case _ _ _ _) = error "VHDL.mkConcSm Not in normal form: Case statement has does not have a simple variable as scrutinee" + +-- 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 + where + tycon = DataCon.dataConTyCon dc + tyname = TyCon.tyConName tycon + dcname = DataCon.dataConName dc + lit = case Name.getOccString tyname of + -- 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!" + + + {- mkConcSm sigs (UncondDef src dst) _ = do src_expr <- vhdl_expr src @@ -398,6 +450,7 @@ vhdl_ty ty = do case name of "TFVec" -> Just $ mk_vector_ty (tfvec_len ty) ty "SizedWord" -> Just $ mk_vector_ty (sized_word_len ty) ty + "RangedWord" -> Just $ mk_natural_ty 0 (ranged_word_bound ty) ty otherwise -> Nothing -- Return new_ty when a new type was successfully created Maybe.fromMaybe @@ -423,6 +476,18 @@ mk_vector_ty len ty = do modA vsTypeFuns (Map.insert (OrdType ty) (genUnconsVectorFuns std_logic_ty ty_id)) return ty_id +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 -- The typemark created. +mk_natural_ty min_bound max_bound ty = do + let ty_id = mkVHDLExtId $ "nat_" ++ (show min_bound) ++ "_to_" ++ (show max_bound) + let ty_def = AST.SubtypeIn naturalTM (Nothing) + let ty_dec = AST.SubtypeDec ty_id ty_def + modA vsSubTypes (Map.insert (OrdType ty) (ty_id, ty_dec)) + return ty_id + builtin_types = Map.fromList [