UnbasedUnsized.hs 11 KB
Newer Older
1 2 3 4 5
{- sv2v
 - Author: Zachary Snow <zach@zachjs.com>
 -
 - Conversion for unbased, unsized literals ('0, '1, 'z, 'x)
 -
6 7
 - The literals are given a binary base, a size of 1, and are made signed to
 - allow sign extension. For context-determined expressions, the converted
8
 - literals are repeated to match the context-determined size.
9
 -
10 11 12 13 14
 - When an unbased, unsized literal depends on the width a module port, the
 - constant portions of the instantiated module are inlined alongside synthetic
 - declarations matching the size of the port and filled with the desired bit.
 - This allows port widths to depend on functions or parameters while avoiding
 - creating hierarchical or generate-scoped references.
15 16 17 18
 -}

module Convert.UnbasedUnsized (convert) where

19
import Control.Monad.Writer.Strict
20 21
import Data.Either (isLeft)
import Data.Maybe (isNothing, mapMaybe)
22
import qualified Data.Map.Strict as Map
23

24
import Convert.Package (inject, prefixItems)
25 26 27
import Convert.Traverse
import Language.SystemVerilog.AST

28
type Part = [ModuleItem]
29
type Parts = Map.Map Identifier Part
30
type PortBit = (Identifier, Bit)
31

32 33 34 35
data ExprContext
    = SelfDetermined
    | ContextDetermined Expr

36
convert :: [AST] -> [AST]
37
convert files =
38
    map (traverseDescriptions convertDescription) files
39
    where
40 41
        parts = execWriter $ mapM (collectDescriptionsM collectPartsM) files
        convertDescription = traverseModuleItems $ convertModuleItem parts
42

43
collectPartsM :: Description -> Writer Parts ()
44 45
collectPartsM (Part _ _ _ _ name _ items) =
    tell $ Map.singleton name items
46 47 48
collectPartsM _ = return ()

convertModuleItem :: Parts -> ModuleItem -> ModuleItem
49 50 51 52 53 54 55 56
convertModuleItem parts (Instance moduleName params instanceName ds bindings) =
    if null extensionDecls || isNothing maybeModuleItems then
        convertModuleItem' $ instanceBase bindings
    else if hasTypeParams || not moduleIsResolved then
        instanceBase bindings
    else
        Generate $ map GenModuleItem $
            stubItems ++ [instanceBase bindings']
57
    where
58 59 60 61 62 63 64 65 66 67 68 69 70 71 72 73 74 75 76 77 78 79 80 81 82 83 84 85 86 87 88 89 90
        instanceBase = Instance moduleName params instanceName ds
        maybeModuleItems = Map.lookup moduleName parts
        Just moduleItems = maybeModuleItems

        -- checking whether we're ready to inline
        hasTypeParams = any (isLeft . snd) params
        moduleIsResolved = isEntirelyResolved selectedStubItems

        -- transform the existing bindings to reference extension declarations
        (bindings', extensionDeclLists) = unzip $
            map (convertBinding blockName) bindings
        extensionDecls = map (MIPackageItem . Decl) $ concat extensionDeclLists

        -- inline the necessary portions of the module alongside the selected
        -- extension declarations
        stubItems =
            map (traverseDecls overrideParam) $
            prefixItems blockName selectedStubItems
        selectedStubItems = inject rawStubItems extensionDecls
        rawStubItems = createModuleStub moduleItems
        blockName = "sv2v_uu_" ++ instanceName

        -- override a parameter value in the stub
        overrideParam :: Decl -> Decl
        overrideParam (Param Parameter t x e) =
            Param Localparam t x $
            case lookup xOrig params of
                Just val -> e'
                    where Right e' = val
                Nothing -> e
            where xOrig = drop (length blockName + 1) x
        overrideParam decl = decl

91 92
convertModuleItem _ other = convertModuleItem' other

93 94 95 96
-- convert a port binding and produce a list of needed extension decls
convertBinding :: Identifier -> PortBinding -> (PortBinding, [Decl])
convertBinding blockName (portName, expr) =
    ((portName, exprPatched), portBits)
97
    where
98 99 100 101 102 103 104 105 106 107 108 109 110 111 112 113 114 115 116 117
        exprRaw = convertExpr (ContextDetermined PortTag) expr
        (exprPatched, portBits) = runWriter $ traverseNestedExprsM
            (replaceBindingExpr blockName portName) exprRaw

-- identify and rewrite references to the width of the current port
replaceBindingExpr :: Identifier -> Identifier -> Expr -> Writer [Decl] Expr
replaceBindingExpr blockName portName (PortTaggedUU v k) = do
    tell [extensionDecl portBit]
    return $ Ident $ blockName ++ "_" ++ extensionDeclName portBit
    where portBit = (portName, bitForBased v k)
replaceBindingExpr _ _ other = return other

-- standardized name format for the synthetic declarations below
extensionDeclName :: PortBit -> Identifier
extensionDeclName (portName, bit) = "ext_" ++ portName ++ "_" ++ show bit

-- synthetic declaration with the type of the port filled with the given bit
extensionDecl :: PortBit -> Decl
extensionDecl portBit@(portName, bit) =
    Param Localparam t x e
118
    where
119 120 121 122 123 124 125 126 127 128 129 130 131 132 133 134 135 136 137 138 139 140 141 142 143 144 145 146 147 148 149 150 151 152 153 154 155 156 157 158 159 160 161 162 163 164
        t = Alias portName []
        x = extensionDeclName portBit
        e = literalFor bit

-- create an all-constant stub for an instantiated module
createModuleStub :: [ModuleItem] -> [PackageItem]
createModuleStub =
    mapMaybe stub
    where
        stub :: ModuleItem -> Maybe PackageItem
        stub (MIPackageItem (Decl decl)) = fmap Decl $ stubDecl decl
        stub (MIPackageItem item) = Just item
        stub _ = Nothing
        -- transform declarations into appropriate constants and type params
        stubDecl :: Decl -> Maybe Decl
        stubDecl (Variable d t x a _) = makePortType d t x a
        stubDecl (Net  d _ _ t x a _) = makePortType d t x a
        stubDecl decl = Just decl
        -- make a type parameter for each port declaration
        makePortType :: Direction -> Type -> Identifier -> [Range] -> Maybe Decl
        makePortType Input UnknownType x [] = Just $ ParamType Localparam x t
            where t = IntegerVector TLogic Unspecified []
        makePortType Input t x [] = Just $ ParamType Localparam x t
        makePortType _ _ _ _ = Nothing

-- ensure inlining the constants doesn't produce generate-scoped exprs or
-- expression type references
isEntirelyResolved :: [ModuleItem] -> Bool
isEntirelyResolved =
    not . getAny . execWriter .
    mapM (collectNestedModuleItemsM collectModuleItem)
    where
        collectModuleItem :: ModuleItem -> Writer Any ()
        collectModuleItem item =
            collectExprsM collectExpr item >>
            collectTypesM collectType item
        collectExpr :: Expr -> Writer Any ()
        collectExpr Dot{} = tell $ Any True
        collectExpr expr =
            collectExprTypesM collectType expr >>
            collectSinglyNestedExprsM collectExpr expr
        collectType :: Type -> Writer Any ()
        collectType TypeOf{} = tell $ Any True
        collectType typ =
            collectTypeExprsM collectExpr typ >>
            collectSinglyNestedTypesM collectType typ
165 166 167

convertModuleItem' :: ModuleItem -> ModuleItem
convertModuleItem' =
168
    traverseExprs (convertExpr SelfDetermined) .
169 170
    traverseTypes (traverseNestedTypes convertType) .
    traverseAsgns convertAsgn
171

172 173
literalFor :: Bit -> Expr
literalFor = Number . (uncurry $ Based 1 True Binary) . bitToVK
174

175 176 177 178 179 180 181 182
pattern PortTag :: Expr
pattern PortTag = Ident "~~uub~~"

-- a converted literal which depends on the current port's width
pattern PortTaggedUU :: Integer -> Integer -> Expr
pattern PortTaggedUU v k <- Repeat
    (DimsFn FnBits (Right PortTag))
    [Number (Based 1 True Binary v k)]
183

184 185 186 187 188
bitForBased :: Integer -> Integer -> Bit
bitForBased 0 0 = Bit0
bitForBased 1 0 = Bit1
bitForBased 0 1 = BitX
bitForBased _ _ = BitZ
189

190 191 192
sizedLiteralFor :: Expr -> Bit -> Expr
sizedLiteralFor expr bit =
    Repeat size [literalFor bit]
193 194
    where size = DimsFn FnBits $ Right expr

195
convertAsgn :: (LHS, Expr) -> (LHS, Expr)
196 197
convertAsgn (lhs, UU bit) =
    (lhs, literalFor bit)
198 199 200 201
convertAsgn (lhs, expr) =
    (lhs, convertExpr context expr)
    where context = ContextDetermined $ lhsToExpr lhs

202 203 204 205 206 207 208
convertExpr :: ExprContext -> Expr -> Expr
convertExpr _ (DimsFn fn (Right e)) =
    DimsFn fn $ Right $ convertExpr SelfDetermined e
convertExpr _ (Cast te e) =
    Cast te $ convertExpr SelfDetermined e
convertExpr _ (Concat exprs) =
    Concat $ map (convertExpr SelfDetermined) exprs
209
convertExpr context (Pattern [(Left UnknownType, e@UU{})]) =
210
    convertExpr context e
211 212 213 214
convertExpr _ (Pattern items) =
    Pattern $ zip
    (map fst items)
    (map (convertExpr SelfDetermined . snd) items)
215 216 217
convertExpr _ (Call expr (Args pnArgs [])) =
    Call expr $ Args pnArgs' []
    where pnArgs' = map (convertExpr SelfDetermined) pnArgs
218 219
convertExpr _ (Repeat count exprs) =
    Repeat count $ map (convertExpr SelfDetermined) exprs
220 221
convertExpr SelfDetermined (MuxA a cond e1@UU{} e2@UU{}) =
    MuxA a
222 223 224
    (convertExpr SelfDetermined cond)
    (convertExpr SelfDetermined e1)
    (convertExpr SelfDetermined e2)
225 226
convertExpr SelfDetermined (MuxA a cond e1 e2) =
    MuxA a
227 228 229
    (convertExpr SelfDetermined cond)
    (convertExpr (ContextDetermined e2) e1)
    (convertExpr (ContextDetermined e1) e2)
230 231
convertExpr (ContextDetermined expr) (MuxA a cond e1 e2) =
    MuxA a
232 233 234 235
    (convertExpr SelfDetermined cond)
    (convertExpr context e1)
    (convertExpr context e2)
    where context = ContextDetermined expr
236
convertExpr SelfDetermined (BinOpA op a e1 e2) =
237
    if isPeerSizedBinOp op || isParentSizedBinOp op
238
        then BinOpA op a
239 240
            (convertExpr (ContextDetermined e2) e1)
            (convertExpr (ContextDetermined e1) e2)
241
        else BinOpA op a
242 243
            (convertExpr SelfDetermined e1)
            (convertExpr SelfDetermined e2)
244
convertExpr (ContextDetermined expr) (BinOpA op a e1 e2) =
245
    if isPeerSizedBinOp op then
246
        BinOpA op a
247 248 249
            (convertExpr (ContextDetermined e2) e1)
            (convertExpr (ContextDetermined e1) e2)
    else if isParentSizedBinOp op then
250
        BinOpA op a
251 252 253
            (convertExpr context e1)
            (convertExpr context e2)
    else
254
        BinOpA op a
255 256 257
            (convertExpr SelfDetermined e1)
            (convertExpr SelfDetermined e2)
    where context = ContextDetermined expr
258
convertExpr context (UniOpA op a expr) =
259
    if isSizedUniOp op
260 261
        then UniOpA op a (convertExpr context expr)
        else UniOpA op a (convertExpr SelfDetermined expr)
262 263 264 265
convertExpr SelfDetermined (UU bit) =
    literalFor bit
convertExpr (ContextDetermined expr) (UU bit) =
    sizedLiteralFor expr bit
266 267
convertExpr _ other = other

268
pattern UU :: Bit -> Expr
269
pattern UU bit <- Number (UnbasedUnsized bit)
270 271

convertType :: Type -> Type
272
convertType (TypeOf e) = TypeOf $ convertExpr SelfDetermined e
273
convertType other = traverseTypeExprs (convertExpr SelfDetermined) other
274

275 276 277 278 279 280 281 282 283 284 285 286 287 288 289 290 291 292 293 294 295 296 297 298 299 300 301
isParentSizedBinOp :: BinOp -> Bool
isParentSizedBinOp BitAnd  = True
isParentSizedBinOp BitXor  = True
isParentSizedBinOp BitXnor = True
isParentSizedBinOp BitOr   = True
isParentSizedBinOp Mul     = True
isParentSizedBinOp Div     = True
isParentSizedBinOp Mod     = True
isParentSizedBinOp Add     = True
isParentSizedBinOp Sub     = True
isParentSizedBinOp _       = False

isPeerSizedBinOp :: BinOp -> Bool
isPeerSizedBinOp Eq      = True
isPeerSizedBinOp Ne      = True
isPeerSizedBinOp TEq     = True
isPeerSizedBinOp TNe     = True
isPeerSizedBinOp WEq     = True
isPeerSizedBinOp WNe     = True
isPeerSizedBinOp Lt      = True
isPeerSizedBinOp Le      = True
isPeerSizedBinOp Gt      = True
isPeerSizedBinOp Ge      = True
isPeerSizedBinOp _       = False

isSizedUniOp :: UniOp -> Bool
isSizedUniOp = (/= LogNot)