Cast.hs 7.61 KB
Newer Older
1 2 3 4 5 6 7 8 9 10 11 12 13 14 15 16 17 18 19 20 21 22 23 24 25 26 27 28 29 30 31
{- sv2v
 - Author: Zachary Snow <zach@zachjs.com>
 -
 - Conversion of elaborated type casts
 -
 - Much of the work of elaborating various casts into explicit integer vector
 - type casts happens in the TypeOf conversion, which contains the primary logic
 - for resolving the type and signedness of expressions. It also removes
 - redundant explicit casts to produce cleaner output.
 -
 - Type casts are defined as producing the result of the expression assigned to
 - a variable of the given type. In the general case, this conversion generates
 - a pass-through function which performs this assignment-based casting. This
 - allows for casts to be used anywhere expressions are used, including within
 - constant expressions.
 -
 - It is possible for the type in a cast to refer to localparams within a
 - procedure. Without evaluating the localparam itself, a function outside of
 - the procedure cannot refer to the size of the type in the cast. In these
 - scenarios, the cast is instead performed by adding a temporary parameter or
 - data declaration within the procedure and assigning the expression to that
 - declaration to perform the cast.
 -
 - A few common cases of casts on number literals are fully elaborated into
 - their corresponding resulting number literals to avoid excessive noise.
 -}

module Convert.Cast (convert) where

import Control.Monad.Writer.Strict
import Data.List (isPrefixOf)
32
import Data.Maybe (isJust)
33 34 35 36 37 38 39 40 41 42

import Convert.ExprUtils
import Convert.Scoper
import Convert.Traverse
import Language.SystemVerilog.AST

convert :: [AST] -> [AST]
convert = map $ traverseDescriptions convertDescription

convertDescription :: Description -> Description
43 44 45 46
convertDescription =
    traverseModuleItems dropDuplicateCaster . evalScoper . scopePart scoper
    where scoper = scopeModuleItem
            traverseDeclM traverseModuleItemM traverseGenItemM traverseStmtM
47

48
type SC = Scoper ()
49

50
traverseDeclM :: Decl -> SC Decl
51 52 53 54 55 56 57 58 59 60
traverseDeclM decl = do
    decl' <- case decl of
        Variable d t x a e -> do
            enterStmt
            e' <- traverseExprM e
            exitStmt
            details <- lookupLocalIdentM x
            if isPrefixOf "sv2v_cast_" x && details /= Nothing
                then return $ Variable Local t DuplicateTag [] Nil
                else do
61
                    insertElem x ()
62
                    return $ Variable d t x a e'
63 64 65 66
        Net d n s t x a e -> do
            enterStmt
            e' <- traverseExprM e
            exitStmt
67
            insertElem x ()
68
            return $ Net d n s t x a e'
69
        Param _ _ x _ ->
70
            insertElem x () >> return decl
71 72 73 74 75 76 77 78 79 80 81 82
        ParamType    _ _ _ -> return decl
        CommentDecl      _ -> return decl
    traverseDeclExprsM traverseExprM decl'

pattern DuplicateTag :: Identifier
pattern DuplicateTag = ":duplicate_cast_to_be_removed:"

dropDuplicateCaster :: ModuleItem -> ModuleItem
dropDuplicateCaster (MIPackageItem (Function _ _ DuplicateTag _ _)) =
    Generate []
dropDuplicateCaster other = other

83
traverseModuleItemM :: ModuleItem -> SC ModuleItem
84
traverseModuleItemM (Genvar x) =
85
    insertElem x () >> return (Genvar x)
86 87 88
traverseModuleItemM item =
    traverseExprsM traverseExprM item

89
traverseGenItemM :: GenItem -> SC GenItem
90 91
traverseGenItemM = traverseGenItemExprsM traverseExprM

92
traverseStmtM :: Stmt -> SC Stmt
93 94 95 96 97 98
traverseStmtM stmt = do
    enterStmt
    stmt' <- traverseStmtExprsM traverseExprM stmt
    exitStmt
    return stmt'

99
traverseExprM :: Expr -> SC Expr
100
traverseExprM (Cast (Left (IntegerVector kw sg rs)) value) | kw /= TBit = do
101
    value' <- fmap simplify $ traverseExprM value
102 103 104 105 106
    size' <- traverseExprM size
    convertCastM size' value' signed
    where
        signed = sg == Signed
        size = dimensionsSize rs
107 108 109
traverseExprM other =
    traverseSinglyNestedExprsM traverseExprM other

110
convertCastM :: Expr -> Expr -> Bool -> SC Expr
111 112 113 114 115 116
convertCastM (Number size) _ _
    | maybeInt == Nothing = illegal "an integer"
    | int <= 0            = illegal "a positive integer"
    where
        maybeInt = numberToInteger size
        Just int = maybeInt
117 118
        illegal = scopedErrorM . msg
        msg s = "size cast width " ++ show size ++ " is not " ++ s
119 120
convertCastM (Number size) (Number value) signed =
    return $ Number $
121 122
        numberCast signed (fromIntegral size') value
    where Just size' = numberToInteger size
123 124
convertCastM size@Number{} (String str) signed =
    convertCastM size (stringToNumber str) signed
125
convertCastM size value signed = do
126 127 128
    sizeUsesLocalVars <- embedScopes usesLocalVars size
    inProcedure <- withinProcedureM
    if not sizeUsesLocalVars || not inProcedure then do
129
        let name = castFnName size signed
130 131 132 133 134 135 136 137
        let item = castFn name size signed
        if sizeUsesLocalVars
            then do
                details <- lookupLocalIdentM name
                when (details == Nothing) (injectItem item)
            else do
                details <- lookupElemM name
                when (details == Nothing) (injectTopItem item)
138
        return $ Call (Ident name) (Args [value] [])
139 140
    else do
        name <- castDeclName 0
141
        insertElem name ()
142
        useVar <- withinStmt
143
        injectDecl $ castDecl useVar name value size signed
144 145
        return $ Ident name

146 147 148 149
-- checks if a cast size references any vars not defined at the top level scope
usesLocalVars :: Scopes a -> Expr -> Bool
usesLocalVars scopes =
    getAny . execWriter . collectNestedExprsM collectLocalVarsM
150
    where
151 152 153 154 155 156 157 158
        collectLocalVarsM :: Expr -> Writer Any ()
        collectLocalVarsM expr@(Ident x) =
            if isLoopVar scopes x
                then tell $ Any True
                else resolve expr
        collectLocalVarsM expr = resolve expr
        resolve :: Expr -> Writer Any ()
        resolve expr =
159 160 161 162 163 164 165 166 167 168 169 170 171 172 173 174 175 176 177 178 179 180 181 182 183 184
            case lookupElem scopes expr of
                Nothing -> return ()
                Just ([_, _], _, _) -> return ()
                Just (_, _, _) -> tell $ Any True

castType :: Expr -> Bool -> Type
castType size signed =
    IntegerVector TLogic sg [r]
    where
        r = (simplify $ BinOp Sub size (RawNum 1), RawNum 0)
        sg = if signed then Signed else Unspecified

castFn :: Identifier -> Expr -> Bool -> ModuleItem
castFn name size signed =
    MIPackageItem $ Function Automatic t name [decl] [stmt]
    where
        inp = "inp"
        t = castType size signed
        decl = Variable Input t inp [] Nil
        stmt = Asgn AsgnOpEq Nothing (LHSIdent name) (Ident inp)

castFnName :: Expr -> Bool -> String
castFnName size signed =
    "sv2v_cast_" ++ sizeStr ++ suffix
    where
        sizeStr = case size of
185 186
            Number n -> show v
                where Just v = numberToInteger n
187 188 189 190 191 192 193 194 195 196
            _ -> shortHash size
        suffix = if signed then "_signed" else ""

castDecl :: Bool -> Identifier -> Expr -> Expr -> Bool -> Decl
castDecl useVar name value size signed =
    if useVar
        then Variable Local t name [] value
        else Param Localparam t name value
    where t = castType size signed

197
castDeclName :: Int -> SC String
198 199 200 201 202 203 204 205 206 207 208 209
castDeclName counter = do
    details <- lookupElemM name
    if details == Nothing
        then return name
        else castDeclName (counter + 1)
    where
        name = if counter == 0
            then prefix
            else prefix ++ '_' : show counter
        prefix = "sv2v_tmp_cast"

-- track whether procedural casts should use variables
210 211 212 213 214
withinStmtKey :: Identifier
withinStmtKey = ":within_stmt:"
withinStmt :: SC Bool
withinStmt = fmap isJust $ lookupElemM withinStmtKey
enterStmt :: SC ()
215 216
enterStmt = do
    inProcedure <- withinProcedureM
217 218
    when inProcedure $ insertElem withinStmtKey ()
exitStmt :: SC ()
219 220
exitStmt = do
    inProcedure <- withinProcedureM
221
    when inProcedure $ removeElem withinStmtKey