aboutsummaryrefslogtreecommitdiffstats
path: root/src/Test/VeriFuzz/CodeGen.hs
blob: 755f52f9ba7c0fe9ee4e8b0041248214407273e1 (plain)
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
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
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
91
92
93
94
95
96
97
98
99
{-|
Module      : Test.VeriFuzz.CodeGen
Description : Code generation for Verilog AST.
Copyright   : (c) Yann Herklotz Grave 2018
License     : GPL-3
Maintainer  : ymherklotz@gmail.com
Stability   : experimental
Portability : POSIX

This module generates the code from the Verilog AST defined in
"Test.VeriFuzz.VerilogAST".
-}

{-# LANGUAGE OverloadedStrings #-}

module Test.VeriFuzz.CodeGen where

import           Control.Lens
import           Data.Text                     (Text)
import qualified Data.Text                     as T
import qualified Data.Text.IO                  as T
import           Test.VeriFuzz.Internal.Shared
import           Test.VeriFuzz.VerilogAST

-- | Convert the 'SourceText' type to 'Text' so that it can be rendered.
genSourceText :: SourceText -> Text
genSourceText source =
  fromList $ genDescription <$> source ^. getSourceText

-- | Generate the 'Description' to 'Text'.
genDescription :: Description -> Text
genDescription desc =
  genModuleDecl $ desc ^. getDescription

-- | Generate the 'ModuleDecl' for a module and convert it to 'Text'.
genModuleDecl :: ModuleDecl -> Text
genModuleDecl mod =
  "module " <> mod ^. moduleId . getIdentifier
  <> "(\n" <> ports <> "\n);\n"
  <> modItems
  <> "endmodule\n"
  where
    ports = sep ",\n" $ genPort <$> mod ^. modPorts
    modItems = fromList $ genModuleItem <$> mod ^. moduleItems

-- | Generate the 'Port' description.
genPort :: Port -> Text
genPort port =
  "  " <> dir <> " " <> name
  where
    dir = genPortDir $ port ^. portDir
    name = port ^. portName . getIdentifier

-- | Convert the 'PortDir' type to 'Text'.
genPortDir :: PortDir -> Text
genPortDir Input  = "input"
genPortDir Output = "output"
genPortDir InOut  = "inout"

-- | Generate a 'ModuleItem'.
genModuleItem :: ModuleItem -> Text
genModuleItem (Assign assign) = genContAssign assign

-- | Generate the 'ContinuousAssignment' to 'Text'.
genContAssign :: ContAssign -> Text
genContAssign assign =
  "  assign " <> name <> " = " <> expr <> ";\n"
  where
    name = assign ^. contAssignNetLVal . getIdentifier
    expr = genExpr $ assign ^. contAssignExpr

-- | Generate 'Expression' to 'Text'.
genExpr :: Expression -> Text
genExpr (OpExpr exprRhs bin exprLhs) =
  genExpr exprRhs <> genBinaryOperator bin <> genExpr exprLhs
genExpr (PrimExpr prim) =
  genPrimary prim
genExpr _ = "TODO"

-- | Generate a 'PrimaryExpression' to 'Text'.
genPrimary :: Primary -> Text
genPrimary (PrimNum num) =
  neg <> sh (num ^. numSize) <> "'d" <> (sh . abs) n
  where
    sh = T.pack . show
    abs x = if x <= 0 then -x else x
    n = num ^. numVal
    neg = if n <= 0 then "-" else ""
genPrimary (PrimId ident) = ident ^. getIdentifier

-- | Convert 'BinaryOperator' to 'Text'.
genBinaryOperator :: BinaryOperator -> Text
genBinaryOperator BinAnd = " & "
genBinaryOperator BinOr  = " | "
genBinaryOperator BinXor = " ^ "

-- | Render the 'Text' to 'IO'. This is equivalent to 'putStrLn'.
render :: Text -> IO ()
render = T.putStrLn