X-Git-Url: https://git.stderr.nl/gitweb?a=blobdiff_plain;f=c%CE%BBash%2FCLasH%2FVHDL%2FVHDLTools.hs;h=cff65a68606a0a508ff05d8e882dab2ac49a981a;hb=a09063e81d573bfa513d30ae97dba95485dc67e9;hp=eabb1b48f371a3a4e0f1c0515b91c97136f94756;hpb=4492bef13c85e9566eaeae496203f12f867e8326;p=matthijs%2Fmaster-project%2Fc%CE%BBash.git diff --git "a/c\316\273ash/CLasH/VHDL/VHDLTools.hs" "b/c\316\273ash/CLasH/VHDL/VHDLTools.hs" index eabb1b4..cff65a6 100644 --- "a/c\316\273ash/CLasH/VHDL/VHDLTools.hs" +++ "b/c\316\273ash/CLasH/VHDL/VHDLTools.hs" @@ -5,6 +5,7 @@ module CLasH.VHDL.VHDLTools where import qualified Maybe import qualified Data.Either as Either import qualified Data.List as List +import qualified Data.Char as Char import qualified Data.Map as Map import qualified Control.Monad as Monad import qualified Control.Arrow as Arrow @@ -88,20 +89,18 @@ mkAssocElems :: [AST.Expr] -- ^ The argument that are applied to function -> AST.VHDLName -- ^ The binder in which to store the result -> Entity -- ^ The entity to map against. - -> TranslatorSession [AST.AssocElem] -- ^ The resulting port maps + -> [AST.AssocElem] -- ^ The resulting port maps mkAssocElems args res entity = - -- Create the actual AssocElems - return $ zipWith mkAssocElem ports sigs + arg_maps ++ (Maybe.maybeToList res_map_maybe) 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 = ent_args entity - res_port = ent_res entity - -- Extract the id part from the (id, type) tuple - ports = map fst (res_port : arg_ports) - -- Translate signal numbers into names - sigs = (vhdlNameToVHDLExpr res : args) + res_port_maybe = ent_res entity + -- Create an expression of res to map against the output port + res_expr = vhdlNameToVHDLExpr res + -- Map each of the input ports + arg_maps = zipWith mkAssocElem (map fst arg_ports) args + -- Map the output port, if present + res_map_maybe = fmap (\port -> mkAssocElem (fst port) res_expr) res_port_maybe -- | Create an VHDL port -> signal association mkAssocElem :: AST.VHDLId -> AST.Expr -> AST.AssocElem @@ -120,7 +119,8 @@ mkComponentInst label entity_id portassigns = AST.CSISm compins where -- We always have a clock port, so no need to map it anywhere but here clk_port = mkAssocElem clockId (idToVHDLExpr clockId) - compins = AST.CompInsSm (mkVHDLExtId label) (AST.IUEntity (AST.NSimple entity_id)) (AST.PMapAspect (portassigns ++ [clk_port])) + resetn_port = mkAssocElem resetId (idToVHDLExpr resetId) + compins = AST.CompInsSm (mkVHDLExtId label) (AST.IUEntity (AST.NSimple entity_id)) (AST.PMapAspect (portassigns ++ [clk_port,resetn_port])) ----------------------------------------------------------------------------- -- Functions to generate VHDL Exprs @@ -185,7 +185,10 @@ dataconToVHDLExpr dc = AST.PrimLit lit varToVHDLId :: CoreSyn.CoreBndr -> AST.VHDLId -varToVHDLId = mkVHDLExtId . varToString +varToVHDLId var = mkVHDLExtId $ (varToString var ++ varToStringUniq var ++ (show $ lowers $ varToStringUniq var)) + where + lowers :: String -> Int + lowers xs = length [x | x <- xs, Char.isLower x] -- Creates a VHDL Name from a binder varToVHDLName :: @@ -236,7 +239,7 @@ mkVHDLExtId s = AST.unsafeVHDLExtId $ strip_invalid s where -- Allowed characters, taken from ForSyde's mkVHDLExtId - allowed = ['A'..'Z'] ++ ['a'..'z'] ++ ['0'..'9'] ++ " \"#&\\'()*+,./:;<=>_|!$%@?[]^`{}~-" + allowed = ['A'..'Z'] ++ ['a'..'z'] ++ ['0'..'9'] ++ " \"#&'()*+,./:;<=>_|!$%@?[]^`{}~-" strip_invalid = filter (`elem` allowed) -- Create a record field selector that selects the given label from the record @@ -287,7 +290,8 @@ vhdl_ty_either tything = Just ty -> vhdl_ty_either' ty vhdl_ty_either' :: Type.Type -> TypeSession (Either String (Maybe AST.TypeMark)) -vhdl_ty_either' ty = do +vhdl_ty_either' ty | ty_has_free_tyvars ty = return $ Left $ "VHDLTools.vhdl_ty_either': Cannot create type: type has free type variables: " ++ pprString ty + | otherwise = do typemap <- getA tsTypes htype_either <- mkHType ty case htype_either of @@ -434,9 +438,10 @@ mk_natural_ty :: -> TypeSession (Either String (Maybe (AST.TypeMark, Either AST.TypeDef AST.SubtypeIn))) -- ^ An error message or The typemark created. 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) + let bitsize = floor (logBase 2 (fromInteger (toInteger max_bound))) + let ty_id = mkVHDLExtId $ "natural_" ++ (show min_bound) ++ "_to_" ++ (show max_bound) + let range = AST.ConstraintIndex $ AST.IndexConstraint [AST.ToRange (AST.PrimLit $ show min_bound) (AST.PrimLit $ show bitsize)] + let ty_def = AST.SubtypeIn unsignedTM (Just range) return (Right $ Just (ty_id, Right ty_def)) mk_unsigned_ty :: @@ -447,8 +452,6 @@ mk_unsigned_ty ty = do let ty_id = mkVHDLExtId $ "unsigned_" ++ show (size - 1) let range = AST.ConstraintIndex $ AST.IndexConstraint [AST.ToRange (AST.PrimLit "0") (AST.PrimLit $ show (size - 1))] let ty_def = AST.SubtypeIn unsignedTM (Just range) - let unsignedshow = mkIntegerShow ty_id - modA tsTypeFuns $ Map.insert (OrdType ty, showIdString) (showId, unsignedshow) return (Right $ Just (ty_id, Right ty_def)) mk_signed_ty :: @@ -459,8 +462,6 @@ mk_signed_ty ty = do let ty_id = mkVHDLExtId $ "signed_" ++ show (size - 1) let range = AST.ConstraintIndex $ AST.IndexConstraint [AST.ToRange (AST.PrimLit "0") (AST.PrimLit $ show (size - 1))] let ty_def = AST.SubtypeIn signedTM (Just range) - let signedshow = mkIntegerShow ty_id - modA tsTypeFuns $ Map.insert (OrdType ty, showIdString) (showId, signedshow) return (Right $ Just (ty_id, Right ty_def)) -- Finds the field labels for VHDL type generated for the given Core type, @@ -678,26 +679,19 @@ mkVectorShow elemTM vectorTM = genExprFCall doShowId (AST.PrimName $ AST.NSimple vecPar) AST.:&: AST.PrimLit "'>'" ) -mkIntegerShow :: - AST.TypeMark -- ^ The specific signed - -> AST.SubProgBody -mkIntegerShow signedTM = AST.SubProgBody showSpec [] [showExpr] - where - signedPar = AST.unsafeVHDLBasicId "sint" - showSpec = AST.Function showId [AST.IfaceVarDec signedPar signedTM] stringTM - showExpr = AST.ReturnSm (Just $ - AST.PrimName $ AST.NAttribute $ AST.AttribName (AST.NSimple integerId) - (AST.NIndexed $ AST.IndexedName (AST.NSimple imageId) [signToInt]) Nothing ) - where - signToInt = genExprFCall (mkVHDLBasicId toIntegerId) (AST.PrimName $ AST.NSimple $ signedPar) - mkBuiltInShow :: [AST.SubProgBody] mkBuiltInShow = [ AST.SubProgBody showBitSpec [] [showBitExpr] , AST.SubProgBody showBoolSpec [] [showBoolExpr] + , AST.SubProgBody showSingedSpec [] [showSignedExpr] + , AST.SubProgBody showUnsignedSpec [] [showUnsignedExpr] + -- , AST.SubProgBody showNaturalSpec [] [showNaturalExpr] ] where - bitPar = AST.unsafeVHDLBasicId "s" - boolPar = AST.unsafeVHDLBasicId "b" + bitPar = AST.unsafeVHDLBasicId "s" + boolPar = AST.unsafeVHDLBasicId "b" + signedPar = AST.unsafeVHDLBasicId "sint" + unsignedPar = AST.unsafeVHDLBasicId "uint" + -- naturalPar = AST.unsafeVHDLBasicId "nat" showBitSpec = AST.Function showId [AST.IfaceVarDec bitPar std_logicTM] stringTM -- if s = '1' then return "'1'" else return "'0'" showBitExpr = AST.IfSm (AST.PrimName (AST.NSimple bitPar) AST.:=: AST.PrimLit "'1'") @@ -710,6 +704,23 @@ mkBuiltInShow = [ AST.SubProgBody showBitSpec [] [showBitExpr] [AST.ReturnSm (Just $ AST.PrimLit "\"True\"")] [] (Just $ AST.Else [AST.ReturnSm (Just $ AST.PrimLit "\"False\"")]) + showSingedSpec = AST.Function showId [AST.IfaceVarDec signedPar signedTM] stringTM + showSignedExpr = AST.ReturnSm (Just $ + AST.PrimName $ AST.NAttribute $ AST.AttribName (AST.NSimple integerId) + (AST.NIndexed $ AST.IndexedName (AST.NSimple imageId) [signToInt]) Nothing ) + where + signToInt = genExprFCall (mkVHDLBasicId toIntegerId) (AST.PrimName $ AST.NSimple $ signedPar) + showUnsignedSpec = AST.Function showId [AST.IfaceVarDec unsignedPar unsignedTM] stringTM + showUnsignedExpr = AST.ReturnSm (Just $ + AST.PrimName $ AST.NAttribute $ AST.AttribName (AST.NSimple integerId) + (AST.NIndexed $ AST.IndexedName (AST.NSimple imageId) [unsignToInt]) Nothing ) + where + unsignToInt = genExprFCall (mkVHDLBasicId toIntegerId) (AST.PrimName $ AST.NSimple $ unsignedPar) + -- showNaturalSpec = AST.Function showId [AST.IfaceVarDec naturalPar naturalTM] stringTM + -- showNaturalExpr = AST.ReturnSm (Just $ + -- AST.PrimName $ AST.NAttribute $ AST.AttribName (AST.NSimple integerId) + -- (AST.NIndexed $ AST.IndexedName (AST.NSimple imageId) [AST.PrimName $ AST.NSimple $ naturalPar]) Nothing ) + genExprFCall :: AST.VHDLId -> AST.Expr -> AST.Expr genExprFCall fName args = @@ -728,3 +739,8 @@ mkSigDec bndr = do case type_mark_maybe of Just type_mark -> return $ Just (AST.SigDec (varToVHDLId bndr) type_mark Nothing) Nothing -> return Nothing + +-- | Does the given thing have a non-empty type? +hasNonEmptyType :: (TypedThing t, Outputable.Outputable t) => + t -> TranslatorSession Bool +hasNonEmptyType thing = MonadState.lift tsType $ isJustM (vhdl_ty "hasNonEmptyType: Non representable type?" thing)