KWArgs.hs 2.24 KB
Newer Older
1 2 3 4
{- sv2v
 - Author: Zachary Snow <zach@zachjs.com>
 -
 - Conversion for named function and task arguments
5 6 7
 -
 - This conversion takes the named arguments and moves them into their
 - corresponding position in the argument list, with names removed.
8 9 10 11 12
 -}

module Convert.KWArgs (convert) where

import Data.List (elemIndex, sortOn)
13
import Control.Monad.Writer.Strict
14 15 16 17 18 19 20
import qualified Data.Map.Strict as Map

import Convert.Traverse
import Language.SystemVerilog.AST

type TFs = Map.Map Identifier [Identifier]

21 22
convert :: [AST] -> [AST]
convert = map $ traverseDescriptions convertDescription
23 24 25

convertDescription :: Description -> Description
convertDescription description =
26 27 28 29 30 31
    traverseModuleItems (convertModuleItem tfs) description
    where tfs = execWriter $ collectModuleItemsM collectTF description

convertModuleItem :: TFs -> ModuleItem -> ModuleItem
convertModuleItem tfs =
    (traverseExprs $ traverseNestedExprs $ convertExpr tfs) .
32
    (traverseStmts $ traverseNestedStmts $ convertStmt tfs)
33 34 35 36 37 38 39 40

collectTF :: ModuleItem -> Writer TFs ()
collectTF (MIPackageItem (Function _ _ f decls _)) = collectTFDecls f decls
collectTF (MIPackageItem (Task     _   f decls _)) = collectTFDecls f decls
collectTF _ = return ()

collectTFDecls :: Identifier -> [Decl] -> Writer TFs ()
collectTFDecls name decls =
Zachary Snow committed
41
    tell $ Map.singleton name $ filter (not . null) $ map getInput decls
42
    where
Zachary Snow committed
43 44 45
        getInput :: Decl -> Identifier
        getInput (Variable Input _ ident _ _) = ident
        getInput _ = ""
46 47

convertExpr :: TFs -> Expr -> Expr
48 49 50 51 52 53 54 55 56 57
convertExpr tfs (Call expr args) =
    convertInvoke tfs Call expr args
convertExpr _ other = other

convertStmt :: TFs -> Stmt -> Stmt
convertStmt tfs (Subroutine expr args) =
    convertInvoke tfs Subroutine expr args
convertStmt _ other = other

convertInvoke :: TFs -> (Expr -> Args -> a) -> Expr -> Args -> a
58
convertInvoke tfs constructor (Ident func) (Args pnArgs kwArgs@(_ : _)) =
59
    case tfs Map.!? func of
60 61
        Nothing -> constructor (Ident func) (Args pnArgs kwArgs)
        Just ordered -> constructor (Ident func) (Args args [])
62 63 64
            where
                args = pnArgs ++ (map snd $ sortOn position kwArgs)
                position (x, _) = elemIndex x ordered
65 66
convertInvoke _ constructor expr args =
    constructor expr args