UnbasedUnsized.hs 11 KB
Newer Older
1
{-# LANGUAGE PatternSynonyms #-}
2 3 4 5 6
{- sv2v
 - Author: Zachary Snow <zach@zachjs.com>
 -
 - Conversion for unbased, unsized literals ('0, '1, 'z, 'x)
 -
7 8
 - 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
9
 - literals are repeated to match the context-determined size.
10
 -
11 12 13 14 15
 - 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.
16 17 18 19
 -}

module Convert.UnbasedUnsized (convert) where

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

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

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

33 34 35 36
data ExprContext
    = SelfDetermined
    | ContextDetermined Expr

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

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

convertModuleItem :: Parts -> ModuleItem -> ModuleItem
50 51 52 53 54 55 56 57
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']
58
    where
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 91
        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

92 93
convertModuleItem _ other = convertModuleItem' other

94 95 96 97
-- convert a port binding and produce a list of needed extension decls
convertBinding :: Identifier -> PortBinding -> (PortBinding, [Decl])
convertBinding blockName (portName, expr) =
    ((portName, exprPatched), portBits)
98
    where
99 100 101 102 103 104 105 106 107 108 109 110 111 112 113 114 115 116 117 118
        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
119
    where
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 165
        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
166 167 168

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

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

176 177 178 179 180 181 182 183
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)]
184

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

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

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

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

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

convertType :: Type -> Type
273
convertType (TypeOf e) = TypeOf $ convertExpr SelfDetermined e
274
convertType other = traverseTypeExprs (convertExpr SelfDetermined) other
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 302
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)