UnpackedArray.hs 3.7 KB
Newer Older
1 2 3 4
{- sv2v
 - Author: Zachary Snow <zach@zachjs.com>
 -
 - Conversion for any unpacked array which must be packed because it is: A) a
5
 - port; B) is bound to a port; C) is assigned a value in a single assignment;
6
 - or D) is assigned to an unpacked array which itself must be packed.
7 8
 -
 - The scoped nature of declarations makes this challenging. While scoping is
9 10 11 12
 - obeyed in general, if any of a set of *equivalent* declarations within a
 - module is packed, all of the declarations are packed. This is because we only
 - record the declaration that needs to be packed when a relevant usage is
 - encountered.
13 14 15 16 17 18 19
 -}

module Convert.UnpackedArray (convert) where

import Control.Monad.State
import qualified Data.Set as Set

20
import Convert.Scoper
21 22 23
import Convert.Traverse
import Language.SystemVerilog.AST

24 25 26
type Location = [Identifier]
type Locations = Set.Set Location
type ST = ScoperT Decl (State Locations)
27 28 29 30 31

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

convertDescription :: Description -> Description
32 33
convertDescription (description @ (Part _ _ Module _ _ _ _)) =
    evalState (operation description) Set.empty
34
    where
35 36 37 38 39
        operation =
            partScoperT traverseDeclM traverseModuleItemM noop traverseStmtM >=>
            partScoperT rewriteDeclM noop noop noop
        noop = return
convertDescription other = other
40

41
-- tracks multi-dimensional unpacked array declarations
42
traverseDeclM :: Decl -> ST Decl
43 44 45 46 47
traverseDeclM (decl @ (Variable _ _ _ [] _)) = return decl
traverseDeclM (decl @ (Variable dir _ x _ e)) = do
    insertElem x decl
    if dir /= Local || e /= Nil
        then flatUsageM x
48
        else return ()
49
    return decl
50
traverseDeclM other = return other
51

52 53 54 55 56 57 58 59 60 61
-- pack decls marked for packing
rewriteDeclM :: Decl -> ST Decl
rewriteDeclM (decl @ (Variable _ _ _ [] _)) = return decl
rewriteDeclM (decl @ (Variable d t x a e)) = do
    insertElem x decl
    details <- lookupElemM x
    let Just (accesses, _, _) = details
    let location = map accessName accesses
    usedAsPacked <- lift $ gets $ Set.member location
    if usedAsPacked
62 63 64
        then do
            let (tf, rs) = typeRanges t
            let t' = tf $ a ++ rs
65 66 67
            return $ Variable d t' x [] e
        else return decl
rewriteDeclM other = return other
68 69

traverseModuleItemM :: ModuleItem -> ST ModuleItem
70 71 72 73 74
traverseModuleItemM =
    traverseModuleItemM'
    >=> traverseLHSsM  traverseLHSM
    >=> traverseExprsM traverseExprM
    >=> traverseAsgnsM traverseAsgnM
75 76 77 78 79 80 81

traverseModuleItemM' :: ModuleItem -> ST ModuleItem
traverseModuleItemM' (Instance a b c d bindings) = do
    bindings' <- mapM collectBinding bindings
    return $ Instance a b c d bindings'
    where
        collectBinding :: PortBinding -> ST PortBinding
82
        collectBinding (y, x) = do
83
            flatUsageM x
84
            return (y, x)
85 86 87
traverseModuleItemM' other = return other

traverseStmtM :: Stmt -> ST Stmt
88 89 90
traverseStmtM =
    traverseStmtLHSsM  traverseLHSM  >=>
    traverseStmtExprsM traverseExprM >=>
91
    traverseStmtAsgnsM traverseAsgnM
92 93

traverseExprM :: Expr -> ST Expr
94 95
traverseExprM (Range x mode i) =
    flatUsageM x >> return (Range x mode i)
96
traverseExprM other = return other
97 98

traverseLHSM :: LHS -> ST LHS
99
traverseLHSM x = flatUsageM x >> return x
100

101
traverseAsgnM :: (LHS, Expr) -> ST (LHS, Expr)
102
traverseAsgnM (x, Mux cond y z) = do
103 104 105
    flatUsageM x
    flatUsageM y
    flatUsageM z
106 107
    return (x, Mux cond y z)
traverseAsgnM (x, y) = do
108 109
    flatUsageM x
    flatUsageM y
110
    return (x, y)
111

112
flatUsageM :: ScopeKey e => e -> ST ()
113
flatUsageM x = do
114 115 116 117 118
    details <- lookupElemM x
    case details of
        Just (accesses, _, _) -> do
            let location = map accessName accesses
            lift $ modify $ Set.insert location
119
        Nothing -> return ()