From 1067284cc1f6ca8ba646545c5b8d0a79cc2e41ad Mon Sep 17 00:00:00 2001 From: Yann Herklotz Date: Fri, 1 Feb 2019 19:39:52 +0000 Subject: More restructuring --- src/VeriFuzz/AST.hs | 564 ++++++++++++++++++++++++++++++++++++++ src/VeriFuzz/ASTGen.hs | 82 ++++++ src/VeriFuzz/Circuit/ASTGen.hs | 82 ------ src/VeriFuzz/Circuit/CodeGen.hs | 62 ----- src/VeriFuzz/Circuit/Random.hs | 54 ---- src/VeriFuzz/Circuit/RandomAlt.hs | 25 -- src/VeriFuzz/CodeGen.hs | 276 +++++++++++++++++++ src/VeriFuzz/Env.hs | 26 ++ src/VeriFuzz/General.hs | 70 +++++ src/VeriFuzz/Helpers.hs | 72 +++++ src/VeriFuzz/Icarus.hs | 63 +++++ src/VeriFuzz/Mutate.hs | 169 ++++++++++++ src/VeriFuzz/Random.hs | 54 ++++ src/VeriFuzz/RandomAlt.hs | 25 ++ src/VeriFuzz/Simulator.hs | 41 --- src/VeriFuzz/Simulator/General.hs | 70 ----- src/VeriFuzz/Simulator/Icarus.hs | 63 ----- src/VeriFuzz/Simulator/Xst.hs | 57 ---- src/VeriFuzz/Simulator/Yosys.hs | 81 ------ src/VeriFuzz/Verilog.hs | 27 -- src/VeriFuzz/Verilog/AST.hs | 564 -------------------------------------- src/VeriFuzz/Verilog/CodeGen.hs | 276 ------------------- src/VeriFuzz/Verilog/Helpers.hs | 72 ----- src/VeriFuzz/Verilog/Mutate.hs | 169 ------------ src/VeriFuzz/Xst.hs | 57 ++++ src/VeriFuzz/Yosys.hs | 81 ++++++ 26 files changed, 1539 insertions(+), 1643 deletions(-) create mode 100644 src/VeriFuzz/AST.hs create mode 100644 src/VeriFuzz/ASTGen.hs delete mode 100644 src/VeriFuzz/Circuit/ASTGen.hs delete mode 100644 src/VeriFuzz/Circuit/CodeGen.hs delete mode 100644 src/VeriFuzz/Circuit/Random.hs delete mode 100644 src/VeriFuzz/Circuit/RandomAlt.hs create mode 100644 src/VeriFuzz/CodeGen.hs create mode 100644 src/VeriFuzz/Env.hs create mode 100644 src/VeriFuzz/General.hs create mode 100644 src/VeriFuzz/Helpers.hs create mode 100644 src/VeriFuzz/Icarus.hs create mode 100644 src/VeriFuzz/Mutate.hs create mode 100644 src/VeriFuzz/Random.hs create mode 100644 src/VeriFuzz/RandomAlt.hs delete mode 100644 src/VeriFuzz/Simulator.hs delete mode 100644 src/VeriFuzz/Simulator/General.hs delete mode 100644 src/VeriFuzz/Simulator/Icarus.hs delete mode 100644 src/VeriFuzz/Simulator/Xst.hs delete mode 100644 src/VeriFuzz/Simulator/Yosys.hs delete mode 100644 src/VeriFuzz/Verilog.hs delete mode 100644 src/VeriFuzz/Verilog/AST.hs delete mode 100644 src/VeriFuzz/Verilog/CodeGen.hs delete mode 100644 src/VeriFuzz/Verilog/Helpers.hs delete mode 100644 src/VeriFuzz/Verilog/Mutate.hs create mode 100644 src/VeriFuzz/Xst.hs create mode 100644 src/VeriFuzz/Yosys.hs (limited to 'src') diff --git a/src/VeriFuzz/AST.hs b/src/VeriFuzz/AST.hs new file mode 100644 index 0000000..0f24c49 --- /dev/null +++ b/src/VeriFuzz/AST.hs @@ -0,0 +1,564 @@ +{-| +Module : VeriFuzz.Verilog.AST +Description : Definition of the Verilog AST types. +Copyright : (c) 2018-2019, Yann Herklotz Grave +License : BSD-3 +Maintainer : ymherklotz [at] gmail [dot] com +Stability : experimental +Poratbility : POSIX + +Defines the types to build a Verilog AST. +-} + +{-# LANGUAGE GeneralizedNewtypeDeriving #-} +{-# LANGUAGE TemplateHaskell #-} + +module VeriFuzz.Verilog.AST + ( -- * Top level types + VerilogSrc(..) + , getVerilogSrc + , Description(..) + , getDescription + -- * Primitives + -- ** Identifier + , Identifier(..) + , getIdentifier + -- ** Control + , Delay(..) + , getDelay + , Event(..) + -- ** Operators + , BinaryOperator(..) + , UnaryOperator(..) + -- ** Task + , Task(..) + , taskName + , taskExpr + -- ** Left hand side value + , LVal(..) + , regId + , regExprId + , regExpr + , regSizeId + , regSizeMSB + , regSizeLSB + , regConc + -- ** Ports + , PortDir(..) + , PortType(..) + , regSigned + , Port(..) + , portType + , portSize + , portName + -- * Expression + , Expr(..) + , exprSize + , exprVal + , exprId + , exprConcat + , exprUnOp + , exprPrim + , exprLhs + , exprBinOp + , exprRhs + , exprCond + , exprTrue + , exprFalse + , exprFunc + , exprBody + , exprStr + , exprWithContext + , traverseExpr + , ConstExpr(..) + , constNum + , Function (..) + -- * Assignment + , Assign(..) + , assignReg + , assignDelay + , assignExpr + , ContAssign(..) + , contAssignNetLVal + , contAssignExpr + -- * Statment + , Stmnt(..) + , statDelay + , statDStat + , statEvent + , statEStat + , statements + , stmntBA + , stmntNBA + , stmntCA + , stmntTask + , stmntSysTask + -- * Module + , ModDecl(..) + , modId + , modOutPorts + , modInPorts + , modItems + , ModItem(..) + , _ModCA + , modInstId + , modInstName + , modInstConns + , declDir + , declPort + , ModConn(..) + , modConn + , modConnName + , modExpr + ) +where + +import Control.Lens (makeLenses, makePrisms) +import Control.Monad (replicateM) +import Data.String (IsString, fromString) +import Data.Text (Text) +import qualified Data.Text as T +import Data.Traversable (sequenceA) +import qualified Test.QuickCheck as QC + +positiveArb :: (QC.Arbitrary a, Ord a, Num a) => QC.Gen a +positiveArb = QC.suchThat QC.arbitrary (> 0) + +-- | Identifier in Verilog. This is just a string of characters that can either +-- be lowercase and uppercase for now. This might change in the future though, +-- as Verilog supports many more characters in Identifiers. +newtype Identifier = Identifier { _getIdentifier :: Text } + deriving (Eq, Show, IsString, Semigroup, Monoid) + +makeLenses ''Identifier + +instance QC.Arbitrary Identifier where + arbitrary = do + l <- QC.choose (2, 10) + Identifier . T.pack <$> replicateM l (QC.elements ['a'..'z']) + +-- | Verilog syntax for adding a delay, which is represented as @#num@. +newtype Delay = Delay { _getDelay :: Int } + deriving (Eq, Show, Num) + +makeLenses ''Delay + +instance QC.Arbitrary Delay where + arbitrary = Delay <$> positiveArb + +-- | Verilog syntax for an event, such as @\@x@, which is used for always blocks +data Event = EId Identifier + | EExpr Expr + | EAll + | EPosEdge Identifier + | ENegEdge Identifier + deriving (Eq, Show) + +instance QC.Arbitrary Event where + arbitrary = EId <$> QC.arbitrary + +-- | Binary operators that are currently supported in the verilog generation. +data BinaryOperator = BinPlus -- ^ @+@ + | BinMinus -- ^ @-@ + | BinTimes -- ^ @*@ + | BinDiv -- ^ @/@ + | BinMod -- ^ @%@ + | BinEq -- ^ @==@ + | BinNEq -- ^ @!=@ + | BinCEq -- ^ @===@ + | BinCNEq -- ^ @!==@ + | BinLAnd -- ^ @&&@ + | BinLOr -- ^ @||@ + | BinLT -- ^ @<@ + | BinLEq -- ^ @<=@ + | BinGT -- ^ @>@ + | BinGEq -- ^ @>=@ + | BinAnd -- ^ @&@ + | BinOr -- ^ @|@ + | BinXor -- ^ @^@ + | BinXNor -- ^ @^~@ + | BinXNorInv -- ^ @~^@ + | BinPower -- ^ @**@ + | BinLSL -- ^ @<<@ + | BinLSR -- ^ @>>@ + | BinASL -- ^ @<<<@ + | BinASR -- ^ @>>>@ + deriving (Eq, Show) + +instance QC.Arbitrary BinaryOperator where + arbitrary = QC.elements + [ BinPlus + , BinMinus + , BinTimes + , BinDiv + , BinMod + , BinEq + , BinNEq + , BinCEq + , BinCNEq + , BinLAnd + , BinLOr + , BinLT + , BinLEq + , BinGT + , BinGEq + , BinAnd + , BinOr + , BinXor + , BinXNor + , BinXNorInv + , BinPower + , BinLSL + , BinLSR + , BinASL + , BinASR + ] + +-- | Unary operators that are currently supported by the generator. +data UnaryOperator = UnPlus -- ^ @+@ + | UnMinus -- ^ @-@ + | UnNot -- ^ @!@ + | UnAnd -- ^ @&@ + | UnNand -- ^ @~&@ + | UnOr -- ^ @|@ + | UnNor -- ^ @~|@ + | UnXor -- ^ @^@ + | UnNxor -- ^ @~^@ + | UnNxorInv -- ^ @^~@ + deriving (Eq, Show) + +instance QC.Arbitrary UnaryOperator where + arbitrary = QC.elements + [ UnPlus + , UnMinus + , UnNot + , UnAnd + , UnNand + , UnOr + , UnNor + , UnXor + , UnNxor + , UnNxorInv + ] + +data Function = SignedFunc + | UnSignedFunc + deriving (Eq, Show) + +instance QC.Arbitrary Function where + arbitrary = QC.elements + [ SignedFunc + , UnSignedFunc + ] + +-- | Verilog expression, which can either be a primary expression, unary +-- expression, binary operator expression or a conditional expression. +data Expr = Number { _exprSize :: Int + , _exprVal :: Integer + } + | Id { _exprId :: Identifier } + | Concat { _exprConcat :: [Expr] } + | UnOp { _exprUnOp :: UnaryOperator + , _exprPrim :: Expr + } + | BinOp { _exprLhs :: Expr + , _exprBinOp :: BinaryOperator + , _exprRhs :: Expr + } + | Cond { _exprCond :: Expr + , _exprTrue :: Expr + , _exprFalse :: Expr + } + | Func { _exprFunc :: Function + , _exprBody :: Expr + } + | Str { _exprStr :: Text } + deriving (Eq, Show) + +instance Num Expr where + a + b = BinOp a BinPlus b + a - b = BinOp a BinMinus b + a * b = BinOp a BinTimes b + negate = UnOp UnMinus + abs = undefined + signum = undefined + fromInteger = Number 32 . fromInteger + +instance Semigroup Expr where + (Concat a) <> (Concat b) = Concat $ a <> b + (Concat a) <> b = Concat $ a <> [b] + a <> (Concat b) = Concat $ a : b + a <> b = Concat [a, b] + +instance Monoid Expr where + mempty = Concat [] + +instance IsString Expr where + fromString = Str . fromString + +exprSafeList :: [QC.Gen Expr] +exprSafeList = + [ Number <$> positiveArb <*> QC.arbitrary + -- , Str <$> QC.arbitrary + ] + +exprRecList :: (Int -> QC.Gen Expr) -> [QC.Gen Expr] +exprRecList subexpr = + [ Number <$> positiveArb <*> QC.arbitrary + , Concat <$> QC.listOf1 (subexpr 8) + , UnOp + <$> QC.arbitrary + <*> subexpr 2 + -- , Str <$> QC.arbitrary + , BinOp <$> subexpr 2 <*> QC.arbitrary <*> subexpr 2 + , Cond <$> subexpr 3 <*> subexpr 3 <*> subexpr 3 + , Func <$> QC.arbitrary <*> subexpr 2 + ] + +expr :: Int -> QC.Gen Expr +expr n + | n == 0 = QC.oneof $ (Id <$> QC.arbitrary) : exprSafeList + | n > 0 = QC.oneof $ (Id <$> QC.arbitrary) : exprRecList subexpr + | otherwise = expr 0 + where subexpr y = expr (n `div` y) + +exprWithContext :: [Identifier] -> Int -> QC.Gen Expr +exprWithContext l n + | n == 0 = QC.oneof $ (Id <$> QC.elements l) : exprSafeList + | n > 0 = QC.oneof $ (Id <$> QC.elements l) : exprRecList subexpr + | otherwise = exprWithContext l 0 + where subexpr y = exprWithContext l (n `div` y) + +instance QC.Arbitrary Expr where + arbitrary = QC.sized expr + +traverseExpr :: (Applicative f) => (Expr -> f Expr) -> Expr -> f Expr +traverseExpr f (Concat e ) = Concat <$> sequenceA (f <$> e) +traverseExpr f (UnOp un e ) = UnOp un <$> f e +traverseExpr f (BinOp l op r) = BinOp <$> f l <*> pure op <*> f r +traverseExpr f (Cond c l r) = Cond <$> f c <*> f l <*> f r +traverseExpr f (Func fn e ) = Func fn <$> f e +traverseExpr _ e = pure e + +makeLenses ''Expr + +-- | Constant expression, which are known before simulation at compilation time. +newtype ConstExpr = ConstExpr { _constNum :: Int } + deriving (Eq, Show, Num, QC.Arbitrary) + +makeLenses ''ConstExpr + +data Task = Task { _taskName :: Identifier + , _taskExpr :: [Expr] + } deriving (Eq, Show) + +makeLenses ''Task + +instance QC.Arbitrary Task where + arbitrary = Task <$> QC.arbitrary <*> QC.arbitrary + +-- | Type that represents the left hand side of an assignment, which can be a +-- concatenation such as in: +-- +-- @ +-- {a, b, c} = 32'h94238; +-- @ +data LVal = RegId { _regId :: Identifier} + | RegExpr { _regExprId :: Identifier + , _regExpr :: Expr + } + | RegSize { _regSizeId :: Identifier + , _regSizeMSB :: ConstExpr + , _regSizeLSB :: ConstExpr + } + | RegConcat { _regConc :: [Expr] } + deriving (Eq, Show) + +makeLenses ''LVal + +instance QC.Arbitrary LVal where + arbitrary = QC.oneof [ RegId <$> QC.arbitrary + , RegExpr <$> QC.arbitrary <*> QC.arbitrary + , RegSize <$> QC.arbitrary <*> QC.arbitrary <*> QC.arbitrary + ] + +instance IsString LVal where + fromString = RegId . fromString + +-- | Different port direction that are supported in Verilog. +data PortDir = PortIn -- ^ Input direction for port (@input@). + | PortOut -- ^ Output direction for port (@output@). + | PortInOut -- ^ Inout direction for port (@inout@). + deriving (Eq, Show) + +instance QC.Arbitrary PortDir where + arbitrary = QC.elements [PortIn, PortOut, PortInOut] + +-- | Currently, only @wire@ and @reg@ are supported, as the other net types are +-- not that common and not a priority. +data PortType = Wire + | Reg { _regSigned :: Bool } + deriving (Eq, Show) + +instance QC.Arbitrary PortType where + arbitrary = QC.oneof [pure Wire, Reg <$> QC.arbitrary] + +makeLenses ''PortType + +-- | Port declaration. It contains information about the type of the port, the +-- size, and the port name. It used to also contain information about if it was +-- an input or output port. However, this is not always necessary and was more +-- cumbersome than useful, as a lot of ports can be declared without input and +-- output port. +-- +-- This is now implemented inside 'ModDecl' itself, which uses a list of output +-- and input ports. +data Port = Port { _portType :: PortType + , _portSize :: Int + , _portName :: Identifier + } deriving (Eq, Show) + +makeLenses ''Port + +instance QC.Arbitrary Port where + arbitrary = Port <$> QC.arbitrary <*> positiveArb <*> QC.arbitrary + +-- | This is currently a type because direct module declaration should also be +-- added: +-- +-- @ +-- mod a(.y(y1), .x1(x11), .x2(x22)); +-- @ +data ModConn = ModConn { _modConn :: Expr } + | ModConnNamed { _modConnName :: Identifier + , _modExpr :: Expr + } + deriving (Eq, Show) + +makeLenses ''ModConn + +instance QC.Arbitrary ModConn where + arbitrary = ModConn <$> QC.arbitrary + +data Assign = Assign { _assignReg :: LVal + , _assignDelay :: Maybe Delay + , _assignExpr :: Expr + } deriving (Eq, Show) + +makeLenses ''Assign + +instance QC.Arbitrary Assign where + arbitrary = Assign <$> QC.arbitrary <*> QC.arbitrary <*> QC.arbitrary + +data ContAssign = ContAssign { _contAssignNetLVal :: Identifier + , _contAssignExpr :: Expr + } deriving (Eq, Show) + +makeLenses ''ContAssign + +instance QC.Arbitrary ContAssign where + arbitrary = ContAssign <$> QC.arbitrary <*> QC.arbitrary + +-- | Statements in Verilog. +data Stmnt = TimeCtrl { _statDelay :: Delay + , _statDStat :: Maybe Stmnt + } -- ^ Time control (@#NUM@) + | EventCtrl { _statEvent :: Event + , _statEStat :: Maybe Stmnt + } + | SeqBlock { _statements :: [Stmnt] } -- ^ Sequential block (@begin ... end@) + | BlockAssign { _stmntBA :: Assign } -- ^ blocking assignment (@=@) + | NonBlockAssign { _stmntNBA :: Assign } -- ^ Non blocking assignment (@<=@) + | StatCA { _stmntCA :: ContAssign } -- ^ Stmnt continuous assignment. May not be correct. + | TaskEnable { _stmntTask :: Task} + | SysTaskEnable { _stmntSysTask :: Task} + deriving (Eq, Show) + +makeLenses ''Stmnt + +instance Semigroup Stmnt where + (SeqBlock a) <> (SeqBlock b) = SeqBlock $ a <> b + (SeqBlock a) <> b = SeqBlock $ a <> [b] + a <> (SeqBlock b) = SeqBlock $ a : b + a <> b = SeqBlock [a, b] + +instance Monoid Stmnt where + mempty = SeqBlock [] + +statement :: Int -> QC.Gen Stmnt +statement n + | n == 0 = QC.oneof + [ BlockAssign <$> QC.arbitrary + , NonBlockAssign <$> QC.arbitrary + -- , StatCA <$> QC.arbitrary + , TaskEnable <$> QC.arbitrary + , SysTaskEnable <$> QC.arbitrary + ] + | n > 0 = QC.oneof + [ TimeCtrl <$> QC.arbitrary <*> (Just <$> substat 2) + , SeqBlock <$> QC.listOf1 (substat 4) + , BlockAssign <$> QC.arbitrary + , NonBlockAssign <$> QC.arbitrary + -- , StatCA <$> QC.arbitrary + , TaskEnable <$> QC.arbitrary + , SysTaskEnable <$> QC.arbitrary + ] + | otherwise = statement 0 + where substat y = statement (n `div` y) + +instance QC.Arbitrary Stmnt where + arbitrary = QC.sized statement + +-- | Module item which is the body of the module expression. +data ModItem = ModCA ContAssign + | ModInst { _modInstId :: Identifier + , _modInstName :: Identifier + , _modInstConns :: [ModConn] + } + | Initial Stmnt + | Always Stmnt + | Decl { _declDir :: Maybe PortDir + , _declPort :: Port + } + deriving (Eq, Show) + +makeLenses ''ModItem +makePrisms ''ModItem + +instance QC.Arbitrary ModItem where + arbitrary = QC.oneof [ ModCA <$> QC.arbitrary + , ModInst <$> QC.arbitrary <*> QC.arbitrary <*> QC.arbitrary + , Initial <$> QC.arbitrary + , Always <$> (EventCtrl <$> QC.arbitrary <*> QC.arbitrary) + , Decl <$> pure Nothing <*> QC.arbitrary + ] + +-- | 'module' module_identifier [list_of_ports] ';' { module_item } 'end_module' +data ModDecl = ModDecl { _modId :: Identifier + , _modOutPorts :: [Port] + , _modInPorts :: [Port] + , _modItems :: [ModItem] + } deriving (Eq, Show) + +makeLenses ''ModDecl + +modPortGen :: QC.Gen Port +modPortGen = QC.oneof + [ Port Wire <$> positiveArb <*> QC.arbitrary + , Port <$> (Reg <$> QC.arbitrary) <*> positiveArb <*> QC.arbitrary + ] + +instance QC.Arbitrary ModDecl where + arbitrary = ModDecl <$> QC.arbitrary <*> QC.arbitrary <*> QC.listOf1 modPortGen <*> QC.arbitrary + +-- | Description of the Verilog module. +newtype Description = Description { _getDescription :: ModDecl } + deriving (Eq, Show, QC.Arbitrary) + +makeLenses ''Description + +-- | The complete sourcetext for the Verilog module. +newtype VerilogSrc = VerilogSrc { _getVerilogSrc :: [Description] } + deriving (Eq, Show, QC.Arbitrary, Semigroup, Monoid) + +makeLenses ''VerilogSrc diff --git a/src/VeriFuzz/ASTGen.hs b/src/VeriFuzz/ASTGen.hs new file mode 100644 index 0000000..41f905d --- /dev/null +++ b/src/VeriFuzz/ASTGen.hs @@ -0,0 +1,82 @@ +{-| +Module : VeriFuzz.Circuit.ASTGen +Description : Generates the AST from the graph directly. +Copyright : (c) 2018-2019, Yann Herklotz Grave +License : BSD-3 +Maintainer : ymherklotz [at] gmail [dot] com +Stability : experimental +Portability : POSIX + +Generates the AST from the graph directly. +-} + +module VeriFuzz.Circuit.ASTGen where + +import Control.Lens ((^..)) +import Data.Foldable (fold) +import Data.Graph.Inductive (LNode, Node) +import qualified Data.Graph.Inductive as G +import Data.Maybe (catMaybes) +import VeriFuzz.Circuit +import VeriFuzz.Internal.Gen +import VeriFuzz.Verilog.AST +import VeriFuzz.Verilog.Helpers + +-- | Converts a 'CNode' to an 'Identifier'. +frNode :: Node -> Identifier +frNode = Identifier . fromNode + +-- | Converts a 'Gate' to a 'BinaryOperator', which should be a bijective +-- mapping. +fromGate :: Gate -> BinaryOperator +fromGate And = BinAnd +fromGate Or = BinOr +fromGate Xor = BinXor + +inputsC :: Circuit -> [Node] +inputsC c = inputs (getCircuit c) + +outputsC :: Circuit -> [Node] +outputsC c = outputs (getCircuit c) + +genPortsAST :: (Circuit -> [Node]) -> Circuit -> [Port] +genPortsAST f c = port . frNode <$> f c where port = Port Wire 4 + +-- | Generates the nested expression AST, so that it can then generate the +-- assignment expressions. +genAssignExpr :: Gate -> [Node] -> Maybe Expr +genAssignExpr _ [] = Nothing +genAssignExpr _ [n ] = Just . Id $ frNode n +genAssignExpr g (n : ns) = BinOp wire op <$> genAssignExpr g ns + where + wire = Id $ frNode n + op = fromGate g + +-- | Generate the continuous assignment AST for a particular node. If it does +-- not have any nodes that link to it then return 'Nothing', as that means that +-- the assignment will just be empty. +genContAssignAST :: Circuit -> LNode Gate -> Maybe ModItem +genContAssignAST c (n, g) = ModCA . ContAssign name <$> genAssignExpr g nodes + where + gr = getCircuit c + nodes = G.pre gr n + name = frNode n + +genAssignAST :: Circuit -> [ModItem] +genAssignAST c = catMaybes $ genContAssignAST c <$> nodes + where + gr = getCircuit c + nodes = G.labNodes gr + +genModuleDeclAST :: Circuit -> ModDecl +genModuleDeclAST c = ModDecl i output ports items + where + i = Identifier "gen_module" + ports = genPortsAST inputsC c + output = [Port Wire 90 "y"] + a = genAssignAST c + items = a ++ [ModCA . ContAssign "y" . fold $ Id <$> assigns] + assigns = a ^.. traverse . _ModCA . contAssignNetLVal + +generateAST :: Circuit -> VerilogSrc +generateAST c = VerilogSrc [Description $ genModuleDeclAST c] diff --git a/src/VeriFuzz/Circuit/ASTGen.hs b/src/VeriFuzz/Circuit/ASTGen.hs deleted file mode 100644 index 41f905d..0000000 --- a/src/VeriFuzz/Circuit/ASTGen.hs +++ /dev/null @@ -1,82 +0,0 @@ -{-| -Module : VeriFuzz.Circuit.ASTGen -Description : Generates the AST from the graph directly. -Copyright : (c) 2018-2019, Yann Herklotz Grave -License : BSD-3 -Maintainer : ymherklotz [at] gmail [dot] com -Stability : experimental -Portability : POSIX - -Generates the AST from the graph directly. --} - -module VeriFuzz.Circuit.ASTGen where - -import Control.Lens ((^..)) -import Data.Foldable (fold) -import Data.Graph.Inductive (LNode, Node) -import qualified Data.Graph.Inductive as G -import Data.Maybe (catMaybes) -import VeriFuzz.Circuit -import VeriFuzz.Internal.Gen -import VeriFuzz.Verilog.AST -import VeriFuzz.Verilog.Helpers - --- | Converts a 'CNode' to an 'Identifier'. -frNode :: Node -> Identifier -frNode = Identifier . fromNode - --- | Converts a 'Gate' to a 'BinaryOperator', which should be a bijective --- mapping. -fromGate :: Gate -> BinaryOperator -fromGate And = BinAnd -fromGate Or = BinOr -fromGate Xor = BinXor - -inputsC :: Circuit -> [Node] -inputsC c = inputs (getCircuit c) - -outputsC :: Circuit -> [Node] -outputsC c = outputs (getCircuit c) - -genPortsAST :: (Circuit -> [Node]) -> Circuit -> [Port] -genPortsAST f c = port . frNode <$> f c where port = Port Wire 4 - --- | Generates the nested expression AST, so that it can then generate the --- assignment expressions. -genAssignExpr :: Gate -> [Node] -> Maybe Expr -genAssignExpr _ [] = Nothing -genAssignExpr _ [n ] = Just . Id $ frNode n -genAssignExpr g (n : ns) = BinOp wire op <$> genAssignExpr g ns - where - wire = Id $ frNode n - op = fromGate g - --- | Generate the continuous assignment AST for a particular node. If it does --- not have any nodes that link to it then return 'Nothing', as that means that --- the assignment will just be empty. -genContAssignAST :: Circuit -> LNode Gate -> Maybe ModItem -genContAssignAST c (n, g) = ModCA . ContAssign name <$> genAssignExpr g nodes - where - gr = getCircuit c - nodes = G.pre gr n - name = frNode n - -genAssignAST :: Circuit -> [ModItem] -genAssignAST c = catMaybes $ genContAssignAST c <$> nodes - where - gr = getCircuit c - nodes = G.labNodes gr - -genModuleDeclAST :: Circuit -> ModDecl -genModuleDeclAST c = ModDecl i output ports items - where - i = Identifier "gen_module" - ports = genPortsAST inputsC c - output = [Port Wire 90 "y"] - a = genAssignAST c - items = a ++ [ModCA . ContAssign "y" . fold $ Id <$> assigns] - assigns = a ^.. traverse . _ModCA . contAssignNetLVal - -generateAST :: Circuit -> VerilogSrc -generateAST c = VerilogSrc [Description $ genModuleDeclAST c] diff --git a/src/VeriFuzz/Circuit/CodeGen.hs b/src/VeriFuzz/Circuit/CodeGen.hs deleted file mode 100644 index 91da48c..0000000 --- a/src/VeriFuzz/Circuit/CodeGen.hs +++ /dev/null @@ -1,62 +0,0 @@ -{-| -Module : VeriFuzz.Circuit.Random -Description : Code generation directly from DAG. -Copyright : (c) 2018-2019, Yann Herklotz Grave -License : BSD-3 -Maintainer : ymherklotz [at] gmail [dot] com -Stability : experimental -Portability : POSIX - -Define the code generation directly from the random DAG. --} - -module VeriFuzz.Circuit.CodeGen - ( generate - ) -where - -import Data.Foldable (fold) -import Data.Graph.Inductive (Graph, LNode, Node, labNodes, pre) -import Data.Maybe (fromMaybe) -import Data.Text (Text) -import qualified Data.Text as T -import VeriFuzz.Circuit -import VeriFuzz.Internal.Gen -import VeriFuzz.Internal.Shared - -toOperator :: Gate -> Text -toOperator And = " & " -toOperator Or = " | " -toOperator Xor = " ^ " - -statList :: Gate -> [Node] -> Maybe Text -statList g n = toStr <$> safe tail n where toStr = fold . fmap ((<> toOperator g) . fromNode) - -lastEl :: [Node] -> Maybe Text -lastEl n = fromNode <$> safe head n - -toStmnt :: (Graph gr) => gr Gate e -> LNode Gate -> Text -toStmnt graph (n, g) = - fromMaybe T.empty - $ Just " assign " - <> Just (fromNode n) - <> Just " = " - <> statList g nodeL - <> lastEl nodeL - <> Just ";\n" - where nodeL = pre graph n - -generate :: (Graph gr) => gr Gate e -> Text -generate graph = - "module generated_module(\n" - <> fold (imap " input wire " ",\n" inp) - <> T.intercalate ",\n" (imap " output wire " "" out) - <> ");\n" - <> fold (toStmnt graph <$> labNodes graph) - <> "endmodule\n\nmodule main;\n initial\n begin\n " - <> "$display(\"Hello, world\");\n $finish;\n " - <> "end\nendmodule" - where - inp = inputs graph - out = outputs graph - imap b e = fmap ((\s -> b <> s <> e) . fromNode) diff --git a/src/VeriFuzz/Circuit/Random.hs b/src/VeriFuzz/Circuit/Random.hs deleted file mode 100644 index 7989b49..0000000 --- a/src/VeriFuzz/Circuit/Random.hs +++ /dev/null @@ -1,54 +0,0 @@ -{-| -Module : VeriFuzz.Circuit.Random -Description : Random generation for DAG -Copyright : (c) 2018-2019, Yann Herklotz Grave -License : BSD-3 -Maintainer : ymherklotz [at] gmail [dot] com -Stability : experimental -Portability : POSIX - -Define the random generation for the directed acyclic graph. --} - -module VeriFuzz.Circuit.Random where - -import Data.Graph.Inductive (Context, LEdge) -import qualified Data.Graph.Inductive as G -import Data.Graph.Inductive.PatriciaTree (Gr) -import Data.List (nub) -import Test.QuickCheck (Arbitrary, Gen) -import qualified Test.QuickCheck as QC - -dupFolder :: (Eq a, Eq b) => Context a b -> [Context a b] -> [Context a b] -dupFolder cont ns = unique cont : ns - where unique (a, b, c, d) = (nub a, b, c, nub d) - --- | Remove duplicates. -rDups :: (Eq a, Eq b) => Gr a b -> Gr a b -rDups g = G.buildGr $ G.ufold dupFolder [] g - --- | Gen instance to create an arbitrary edge, where the edges are limited by --- `n` that is passed to it. -arbitraryEdge :: (Arbitrary e) => Int -> Gen (LEdge e) -arbitraryEdge n = do - x <- with $ \a -> a < n && a > 0 && a /= n - 1 - y <- with $ \a -> x < a && a < n && a > 0 - z <- QC.arbitrary - return (x, y, z) - where - with = QC.suchThat $ QC.resize n QC.arbitrary - --- | Gen instance for a random acyclic DAG. -randomDAG :: (Arbitrary l, Arbitrary e, Eq l, Eq e) => Gen (Gr l e) -- ^ The generated graph. It uses Arbitrary to - -- generate random instances of each node -randomDAG = do - list <- QC.infiniteListOf QC.arbitrary - l <- QC.infiniteListOf aE - QC.sized (\n -> return . G.mkGraph (nodes list n) $ take (10 * n) l) - where - nodes l n = zip [0 .. n] $ take n l - aE = QC.sized arbitraryEdge - --- | Generate a random acyclic DAG with an IO instance. -genRandomDAG :: (Arbitrary l, Arbitrary e, Eq l, Eq e) => IO (Gr l e) -genRandomDAG = QC.generate randomDAG diff --git a/src/VeriFuzz/Circuit/RandomAlt.hs b/src/VeriFuzz/Circuit/RandomAlt.hs deleted file mode 100644 index 93a50e9..0000000 --- a/src/VeriFuzz/Circuit/RandomAlt.hs +++ /dev/null @@ -1,25 +0,0 @@ -{-|p -Module : VeriFuzz.Circuit.RandomAlt -Description : RandomAlt generation for DAG -Copyright : (c) 2018-2019, Yann Herklotz Grave -License : BSD-3 -Maintainer : ymherklotz [at] gmail [dot] com -Stability : experimental -Portability : POSIX - -Define the random generation for the directed acyclic graph. --} - -module VeriFuzz.Circuit.RandomAlt where - -import qualified Data.Graph.Inductive.Arbitrary as G -import Data.Graph.Inductive.PatriciaTree (Gr) -import Test.QuickCheck (Arbitrary, Gen) -import qualified Test.QuickCheck as QC - -randomDAG :: (Arbitrary l, Arbitrary e) => Gen (Gr l e) -randomDAG = G.looplessGraph <$> QC.arbitrary - --- | Generate a random acyclic DAG with an IO instance. -genRandomDAG :: (Arbitrary l, Arbitrary e) => IO (Gr l e) -genRandomDAG = QC.generate randomDAG diff --git a/src/VeriFuzz/CodeGen.hs b/src/VeriFuzz/CodeGen.hs new file mode 100644 index 0000000..3253f86 --- /dev/null +++ b/src/VeriFuzz/CodeGen.hs @@ -0,0 +1,276 @@ +{-| +Module : VeriFuzz.Verilog.CodeGen +Description : Code generation for Verilog AST. +Copyright : (c) 2018-2019, Yann Herklotz Grave +License : BSD-3 +Maintainer : ymherklotz [at] gmail [dot] com +Stability : experimental +Portability : POSIX + +This module generates the code from the Verilog AST defined in +"VeriFuzz.Verilog.AST". +-} + +{-# LANGUAGE FlexibleInstances #-} + +module VeriFuzz.Verilog.CodeGen where + +import Control.Lens (view, (^.)) +import Data.Foldable (fold) +import Data.Text (Text) +import qualified Data.Text as T +import qualified Data.Text.IO as T +import Numeric (showHex) +import Test.QuickCheck (Arbitrary, arbitrary) +import VeriFuzz.Verilog.AST + +-- | 'Source' class which determines that source code is able to be generated +-- from the data structure using 'genSource'. This will be stored in 'Text' and +-- can then be processed further. +class Source a where + genSource :: a -> Text + +-- | Inserts commas between '[Text]' and except the last one. +comma :: [Text] -> Text +comma = T.intercalate ", " + +-- | Show function for 'Text' +showT :: (Show a) => a -> Text +showT = T.pack . show + +-- | Map a 'Maybe Stmnt' to 'Text'. If it is 'Just stmnt', the generated +-- statements are returned. If it is 'Nothing', then @;\n@ is returned. +defMap :: Maybe Stmnt -> Text +defMap = maybe ";\n" genStmnt + +-- | Convert the 'VerilogSrc' type to 'Text' so that it can be rendered. +genVerilogSrc :: VerilogSrc -> Text +genVerilogSrc source = fold $ genDescription <$> source ^. getVerilogSrc + +-- | Generate the 'Description' to 'Text'. +genDescription :: Description -> Text +genDescription desc = genModuleDecl $ desc ^. getDescription + +-- | Generate the 'ModDecl' for a module and convert it to 'Text'. +genModuleDecl :: ModDecl -> Text +genModuleDecl m = + "module " <> m ^. modId . getIdentifier <> ports <> ";\n" <> modI <> "endmodule\n" + where + ports | noIn && noOut = "" + | otherwise = "(" <> comma (genModPort <$> outIn) <> ")" + modI = fold $ genModuleItem <$> m ^. modItems + noOut = null $ m ^. modOutPorts + noIn = null $ m ^. modInPorts + outIn = (m ^. modOutPorts) ++ (m ^. modInPorts) + +-- | Conversts 'Port' to 'Text' for the module list, which means it only +-- generates a list of identifiers. +genModPort :: Port -> Text +genModPort port = port ^. portName . getIdentifier + +-- | Generate the 'Port' description. +genPort :: Port -> Text +genPort port = t <> size <> name + where + t = (<> " ") . genPortType $ port ^. portType + size | port ^. portSize > 1 = "[" <> showT (port ^. portSize - 1) <> ":0] " + | otherwise = "" + name = port ^. portName . getIdentifier + +-- | Convert the 'PortDir' type to 'Text'. +genPortDir :: PortDir -> Text +genPortDir PortIn = "input" +genPortDir PortOut = "output" +genPortDir PortInOut = "inout" + +-- | Generate a 'ModItem'. +genModuleItem :: ModItem -> Text +genModuleItem (ModCA ca) = genContAssign ca +genModuleItem (ModInst (Identifier i) (Identifier name) conn) = + i <> " " <> name <> "(" <> comma (genModConn <$> conn) <> ")" <> ";\n" +genModuleItem (Initial stat ) = "initial " <> genStmnt stat +genModuleItem (Always stat ) = "always " <> genStmnt stat +genModuleItem (Decl dir port) = maybe "" makePort dir <> genPort port <> ";\n" + where makePort = (<> " ") . genPortDir + +genModConn :: ModConn -> Text +genModConn (ModConn c) = + genExpr c +genModConn (ModConnNamed n c) = + "." <> n ^. getIdentifier <> "(" <> genExpr c <> ")" + +-- | Generate continuous assignment +genContAssign :: ContAssign -> Text +genContAssign (ContAssign val e) = "assign " <> name <> " = " <> expr <> ";\n" + where + name = val ^. getIdentifier + expr = genExpr e + +-- | Generate 'Function' to 'Text' +genFunc :: Function -> Text +genFunc SignedFunc = "$signed" +genFunc UnSignedFunc = "$unsigned" + +-- | Generate 'Expr' to 'Text'. +genExpr :: Expr -> Text +genExpr (BinOp eRhs bin eLhs) = "(" <> genExpr eRhs <> genBinaryOperator bin <> genExpr eLhs <> ")" +genExpr (Number s n ) = minus <> showT s <> "'h" <> T.pack (showHex (abs n) "") + where minus | signum n > 0 = "" | otherwise = "-" +genExpr (Id i ) = i ^. getIdentifier +genExpr (Concat c ) = "{" <> comma (genExpr <$> c) <> "}" +genExpr (UnOp u e ) = "(" <> genUnaryOperator u <> genExpr e <> ")" +genExpr (Cond l t f ) = "(" <> genExpr l <> " ? " <> genExpr t <> " : " <> genExpr f <> ")" +genExpr (Func f e ) = genFunc f <> "(" <> genExpr e <> ")" +genExpr (Str t ) = "\"" <> t <> "\"" + +-- | Convert 'BinaryOperator' to 'Text'. +genBinaryOperator :: BinaryOperator -> Text +genBinaryOperator BinPlus = " + " +genBinaryOperator BinMinus = " - " +genBinaryOperator BinTimes = " * " +genBinaryOperator BinDiv = " / " +genBinaryOperator BinMod = " % " +genBinaryOperator BinEq = " == " +genBinaryOperator BinNEq = " != " +genBinaryOperator BinCEq = " === " +genBinaryOperator BinCNEq = " !== " +genBinaryOperator BinLAnd = " && " +genBinaryOperator BinLOr = " || " +genBinaryOperator BinLT = " < " +genBinaryOperator BinLEq = " <= " +genBinaryOperator BinGT = " > " +genBinaryOperator BinGEq = " >= " +genBinaryOperator BinAnd = " & " +genBinaryOperator BinOr = " | " +genBinaryOperator BinXor = " ^ " +genBinaryOperator BinXNor = " ^~ " +genBinaryOperator BinXNorInv = " ~^ " +genBinaryOperator BinPower = " ** " +genBinaryOperator BinLSL = " << " +genBinaryOperator BinLSR = " >> " +genBinaryOperator BinASL = " <<< " +genBinaryOperator BinASR = " >>> " + +-- | Convert 'UnaryOperator' to 'Text'. +genUnaryOperator :: UnaryOperator -> Text +genUnaryOperator UnPlus = "+" +genUnaryOperator UnMinus = "-" +genUnaryOperator UnNot = "!" +genUnaryOperator UnAnd = "&" +genUnaryOperator UnNand = "~&" +genUnaryOperator UnOr = "|" +genUnaryOperator UnNor = "~|" +genUnaryOperator UnXor = "^" +genUnaryOperator UnNxor = "~^" +genUnaryOperator UnNxorInv = "^~" + +-- | Generate verilog code for an 'Event'. +genEvent :: Event -> Text +genEvent (EId i ) = "@(" <> i ^. getIdentifier <> ")" +genEvent (EExpr expr) = "@(" <> genExpr expr <> ")" +genEvent EAll = "@*" +genEvent (EPosEdge i) = "@(posedge " <> i ^. getIdentifier <> ")" +genEvent (ENegEdge i) = "@(negedge " <> i ^. getIdentifier <> ")" + +-- | Generates verilog code for a 'Delay'. +genDelay :: Delay -> Text +genDelay (Delay i) = "#" <> showT i + +-- | Generate the verilog code for an 'LVal'. +genLVal :: LVal -> Text +genLVal (RegId i ) = i ^. getIdentifier +genLVal (RegExpr i expr) = i ^. getIdentifier <> " [" <> genExpr expr <> "]" +genLVal (RegSize i msb lsb) = + i ^. getIdentifier <> " [" <> genConstExpr msb <> ":" <> genConstExpr lsb <> "]" +genLVal (RegConcat e) = "{" <> comma (genExpr <$> e) <> "}" + +genConstExpr :: ConstExpr -> Text +genConstExpr (ConstExpr num) = showT num + +genPortType :: PortType -> Text +genPortType Wire = "wire" +genPortType (Reg signed) | signed = "reg signed" + | otherwise = "reg" + +genAssign :: Text -> Assign -> Text +genAssign op (Assign r d e) = genLVal r <> op <> maybe "" genDelay d <> genExpr e + +genStmnt :: Stmnt -> Text +genStmnt (TimeCtrl d stat ) = genDelay d <> " " <> defMap stat +genStmnt (EventCtrl e stat ) = genEvent e <> " " <> defMap stat +genStmnt (SeqBlock s ) = "begin\n" <> fold (genStmnt <$> s) <> "end\n" +genStmnt (BlockAssign a ) = genAssign " = " a <> ";\n" +genStmnt (NonBlockAssign a ) = genAssign " <= " a <> ";\n" +genStmnt (StatCA a ) = genContAssign a +genStmnt (TaskEnable task) = genTask task <> ";\n" +genStmnt (SysTaskEnable task) = "$" <> genTask task <> ";\n" + +genTask :: Task -> Text +genTask (Task name expr) | null expr = i + | otherwise = i <> "(" <> comma (genExpr <$> expr) <> ")" + where i = name ^. getIdentifier + +-- | Render the 'Text' to 'IO'. This is equivalent to 'putStrLn'. +render :: (Source a) => a -> IO () +render = T.putStrLn . genSource + +-- Instances + +instance Source Identifier where + genSource = view getIdentifier + +instance Source Task where + genSource = genTask + +instance Source Stmnt where + genSource = genStmnt + +instance Source PortType where + genSource = genPortType + +instance Source ConstExpr where + genSource = genConstExpr + +instance Source LVal where + genSource = genLVal + +instance Source Delay where + genSource = genDelay + +instance Source Event where + genSource = genEvent + +instance Source UnaryOperator where + genSource = genUnaryOperator + +instance Source Expr where + genSource = genExpr + +instance Source ContAssign where + genSource = genContAssign + +instance Source ModItem where + genSource = genModuleItem + +instance Source PortDir where + genSource = genPortDir + +instance Source Port where + genSource = genPort + +instance Source ModDecl where + genSource = genModuleDecl + +instance Source Description where + genSource = genDescription + +instance Source VerilogSrc where + genSource = genVerilogSrc + +newtype GenVerilog a = GenVerilog { unGenVerilog :: a } + +instance (Source a) => Show (GenVerilog a) where + show = T.unpack . genSource . unGenVerilog + +instance (Arbitrary a) => Arbitrary (GenVerilog a) where + arbitrary = GenVerilog <$> arbitrary diff --git a/src/VeriFuzz/Env.hs b/src/VeriFuzz/Env.hs new file mode 100644 index 0000000..85c761e --- /dev/null +++ b/src/VeriFuzz/Env.hs @@ -0,0 +1,26 @@ +{-| +Module : VeriFuzz.Env +Description : Environment to run the simulator and synthesisers in a matrix. +Copyright : (c) 2019, Yann Herklotz Grave +License : GPL-3 +Maintainer : ymherklotz [at] gmail [dot] com +Stability : experimental +Portability : POSIX + +Environment to run the simulator and synthesisers in a matrix. +-} + +module VeriFuzz.Env where + +-- | Environment used to run the main +data SimMatrix = SimMatrix { yosys :: Yosys + , xst :: Maybe Xst + , icarus :: Maybe Icarus + } + +type SimEnv = ReaderT SimMatrix IO + +runAll :: SimEnv () +runAll = do + val <- asks xst + shelly $ run_ "echo" ["Hello World"] diff --git a/src/VeriFuzz/General.hs b/src/VeriFuzz/General.hs new file mode 100644 index 0000000..dbd1da0 --- /dev/null +++ b/src/VeriFuzz/General.hs @@ -0,0 +1,70 @@ +{-| +Module : VeriFuzz.Simulator.General +Description : Class of the simulator. +Copyright : (c) 2018-2019, Yann Herklotz Grave +License : BSD-3 +Maintainer : ymherklotz [at] gmail [dot] com +Stability : experimental +Portability : POSIX + +Class of the simulator and the synthesize tool. +-} + +module VeriFuzz.Simulator.General where + +import Data.Bits (shiftL) +import Data.ByteString (ByteString) +import qualified Data.ByteString as B +import Data.Text (Text) +import qualified Data.Text as T +import Prelude hiding (FilePath) +import Shelly +import System.FilePath.Posix (takeBaseName) +import VeriFuzz.Verilog.AST + +-- | Simulator class. +class Simulator a where + toText :: a -> Text + +-- | Simulation type class. +class (Simulator a) => Simulate a where + runSim :: a -- ^ Simulator instance + -> ModDecl -- ^ Module to simulate + -> [ByteString] -- ^ Inputs to simulate + -> Sh Int -- ^ Returns the value of the hash at the output of the testbench. + +-- | Synthesize type class. +class (Simulator a) => Synthesize a where + runSynth :: a -- ^ Synthesize tool instance + -> ModDecl -- ^ Module to synthesize + -> FilePath -- ^ Output verilog file for the module + -> Sh () -- ^ does not return any values + +rootPath :: Sh FilePath +rootPath = do + current <- pwd + maybe current fromText <$> get_env "VERIFUZZ_ROOT" + +timeout :: FilePath -> [Text] -> Sh Text +timeout = command1 "timeout" ["180"] . toTextIgnore +{-# INLINE timeout #-} + +timeout_ :: FilePath -> [Text] -> Sh () +timeout_ = command1_ "timeout" ["180"] . toTextIgnore +{-# INLINE timeout_ #-} + +-- | Helper function to convert bytestrings to integers +bsToI :: ByteString -> Integer +bsToI = B.foldl' (\i b -> (i `shiftL` 8) + fromIntegral b) 0 +{-# INLINE bsToI #-} + +noPrint :: Sh a -> Sh a +noPrint = + print_stdout False . print_stderr False + +echoP :: Text -> Sh () +echoP t = do + fn <- pwd + echo $ bname fn <> " :: " <> t + where + bname = T.pack . takeBaseName . T.unpack . toTextIgnore diff --git a/src/VeriFuzz/Helpers.hs b/src/VeriFuzz/Helpers.hs new file mode 100644 index 0000000..99e5f38 --- /dev/null +++ b/src/VeriFuzz/Helpers.hs @@ -0,0 +1,72 @@ +{-| +Module : VeriFuzz.Verilog.Helpers +Description : Defaults and common functions. +Copyright : (c) 2018-2019, Yann Herklotz Grave +License : BSD-3 +Maintainer : ymherklotz [at] gmail [dot] com +Stability : experimental +Portability : POSIX + +Defaults and common functions. +-} + +module VeriFuzz.Verilog.Helpers where + +import Control.Lens +import Data.Text (Text) +import VeriFuzz.Verilog.AST + +regDecl :: Identifier -> ModItem +regDecl = Decl Nothing . Port (Reg False) 1 + +wireDecl :: Identifier -> ModItem +wireDecl = Decl Nothing . Port Wire 1 + +-- | Create an empty module. +emptyMod :: ModDecl +emptyMod = ModDecl "" [] [] [] + +-- | Set a module name for a module declaration. +setModName :: Text -> ModDecl -> ModDecl +setModName str = modId .~ Identifier str + +-- | Add a input port to the module declaration. +addModPort :: Port -> ModDecl -> ModDecl +addModPort port = modInPorts %~ (:) port + +addDescription :: Description -> VerilogSrc -> VerilogSrc +addDescription desc = getVerilogSrc %~ (:) desc + +testBench :: ModDecl +testBench = ModDecl + "main" + [] + [] + [ regDecl "a" + , regDecl "b" + , wireDecl "c" + , ModInst "and" "and_gate" [ModConn $ Id "c", ModConn $ Id "a", ModConn $ Id "b"] + , Initial $ SeqBlock + [ BlockAssign . Assign (RegId "a") Nothing $ Number 1 1 + , BlockAssign . Assign (RegId "b") Nothing $ Number 1 1 + -- , TimeCtrl (Delay 1) . Just . SysTaskEnable $ Task "display" + -- [ Str "%d & %d = %d" + -- , PrimExpr $ PrimId "a" + -- , PrimExpr $ PrimId "b" + -- , PrimExpr $ PrimId "c" + -- ] + -- , SysTaskEnable $ Task "finish" [] + ] + ] + +addTestBench :: VerilogSrc -> VerilogSrc +addTestBench = addDescription $ Description testBench + +defaultPort :: Identifier -> Port +defaultPort = Port Wire 1 + +portToExpr :: Port -> Expr +portToExpr (Port _ _ i) = Id i + +modName :: ModDecl -> Text +modName = view $ modId . getIdentifier diff --git a/src/VeriFuzz/Icarus.hs b/src/VeriFuzz/Icarus.hs new file mode 100644 index 0000000..527322a --- /dev/null +++ b/src/VeriFuzz/Icarus.hs @@ -0,0 +1,63 @@ +{-| +Module : VeriFuzz.Simulator.Icarus +Description : Icarus verilog module. +Copyright : (c) 2018-2019, Yann Herklotz Grave +License : BSD-3 +Maintainer : ymherklotz [at] gmail [dot] com +Stability : experimental +Portability : POSIX + +Icarus verilog module. +-} + +module VeriFuzz.Simulator.Icarus where + +import Control.Lens +import Data.ByteString (ByteString) +import qualified Data.ByteString as B +import Data.Foldable (fold) +import Data.Hashable +import Data.List (transpose) +import Prelude hiding (FilePath) +import Shelly +import VeriFuzz.Simulator.General +import VeriFuzz.Verilog + +data Icarus = Icarus { icarusPath :: FilePath + , vvpPath :: FilePath + } + +instance Simulator Icarus where + toText _ = "iverilog" + +instance Simulate Icarus where + runSim = runSimIcarus + +defaultIcarus :: Icarus +defaultIcarus = Icarus "iverilog" "vvp" + +addDisplay :: [Stmnt] -> [Stmnt] +addDisplay s = concat $ transpose + [s, replicate l $ TimeCtrl 1 Nothing, replicate l . SysTaskEnable $ Task "display" ["%h", Id "y"]] + where l = length s + +assignFunc :: [Port] -> ByteString -> Stmnt +assignFunc inp bs = NonBlockAssign . Assign conc Nothing . Number (B.length bs * 4) $ bsToI bs + where conc = RegConcat (portToExpr <$> inp) + +runSimIcarus :: Icarus -> ModDecl -> [ByteString] -> Sh Int +runSimIcarus sim m bss = do + let tb = ModDecl + "main" + [] + [] + [ Initial + $ fold (addDisplay $ assignFunc (m ^. modInPorts) <$> bss) + <> (SysTaskEnable $ Task "finish" []) + ] + let newtb = instantiateMod m tb + let modWithTb = VerilogSrc $ Description <$> [newtb, m] + writefile "main.v" $ genSource modWithTb + echoP "Run icarus" + noPrint $ run_ (icarusPath sim) ["-o", "main", "main.v"] + hash <$> run (vvpPath sim) ["main"] diff --git a/src/VeriFuzz/Mutate.hs b/src/VeriFuzz/Mutate.hs new file mode 100644 index 0000000..3e03a02 --- /dev/null +++ b/src/VeriFuzz/Mutate.hs @@ -0,0 +1,169 @@ +{-| +Module : VeriFuzz.Verilog.Mutation +Description : Functions to mutate the Verilog AST. +Copyright : (c) 2018-2019, Yann Herklotz Grave +License : BSD-3 +Maintainer : ymherklotz [at] gmail [dot] com +Stability : experimental +Portability : POSIX + +Functions to mutate the Verilog AST from "VeriFuzz.Verilog.AST" to generate more +random patterns, such as nesting wires instead of creating new ones. +-} + +module VeriFuzz.Verilog.Mutate where + +import Control.Lens +import Data.Maybe (catMaybes, fromMaybe) +import Data.Text (Text) +import qualified Data.Text as T +import VeriFuzz.Internal.Gen +import VeriFuzz.Internal.Shared +import VeriFuzz.Verilog.AST +import VeriFuzz.Verilog.CodeGen + +-- | Return if the 'Identifier' is in a 'ModDecl'. +inPort :: Identifier -> ModDecl -> Bool +inPort i m = inInput + where inInput = any (\a -> a ^. portName == i) $ + m ^. modInPorts ++ m ^. modOutPorts + +-- | Find the last assignment of a specific wire/reg to an expression, and +-- returns that expression. +findAssign :: Identifier -> [ModItem] -> Maybe Expr +findAssign i items = safe last . catMaybes $ isAssign <$> items + where + isAssign (ModCA (ContAssign val expr)) + | val == i = Just expr + | otherwise = Nothing + isAssign _ = Nothing + +-- | Transforms an expression by replacing an Identifier with an +-- expression. This is used inside 'transformOf' and 'traverseExpr' to replace +-- the 'Identifier' recursively. +idTrans :: Identifier -> Expr -> Expr -> Expr +idTrans i expr (Id id') | id' == i = expr + | otherwise = Id id' +idTrans _ _ e = e + +-- | Replaces the identifier recursively in an expression. +replace :: Identifier -> Expr -> Expr -> Expr +replace = (transformOf traverseExpr .) . idTrans + +-- | Nest expressions for a specific 'Identifier'. If the 'Identifier' is not +-- found, the AST is not changed. +-- +-- This could be improved by instead of only using the last assignment to the +-- wire that one finds, to use the assignment to the wire before the current +-- expression. This would require a different approach though. +nestId :: Identifier -> ModDecl -> ModDecl +nestId i m + | not $ inPort i m + = let expr = fromMaybe def . findAssign i $ m ^. modItems in m & get %~ replace i expr + | otherwise + = m + where + get = modItems . traverse . _ModCA . contAssignExpr + def = Id i + +-- | Replaces an identifier by a expression in all the module declaration. +nestSource :: Identifier -> VerilogSrc -> VerilogSrc +nestSource i src = src & getVerilogSrc . traverse . getDescription %~ nestId i + +-- | Nest variables in the format @w[0-9]*@ up to a certain number. +nestUpTo :: Int -> VerilogSrc -> VerilogSrc +nestUpTo i src = foldl (flip nestSource) src $ Identifier . fromNode <$> [1 .. i] + +allVars :: ModDecl -> [Identifier] +allVars m = (m ^.. modOutPorts . traverse . portName) ++ (m ^.. modInPorts . traverse . portName) +-- $setup +-- >>> let m = (ModDecl (Identifier "m") [Port Wire 5 (Identifier "y")] [Port Wire 5 "x"] []) +-- >>> let main = (ModDecl "main" [] [] []) + +-- | Add a Module Instantiation using 'ModInst' from the first module passed to +-- it to the body of the second module. It first has to make all the inputs into +-- @reg@. +-- +-- >>> render $ instantiateMod m main +-- module main; +-- wire [4:0] y; +-- reg [4:0] x; +-- m m1(y, x); +-- endmodule +-- +instantiateMod :: ModDecl -> ModDecl -> ModDecl +instantiateMod m main = main & modItems %~ ((out ++ regIn ++ [inst]) ++) + where + out = Decl Nothing <$> m ^. modOutPorts + regIn = Decl Nothing <$> (m ^. modInPorts & traverse . portType .~ Reg False) + inst = ModInst (m ^. modId) (m ^. modId <> (Identifier . showT $ count + 1)) conns + count = length . filter (== m ^. modId) $ main ^.. modItems . traverse . modInstId + conns = ModConn . Id <$> allVars m + +-- | Instantiate without adding wire declarations. It also does not count the +-- current instantiations of the same module. +-- +-- >>> render $ instantiateMod_ m +-- m m(y, x); +-- +instantiateMod_ :: ModDecl -> ModItem +instantiateMod_ m = ModInst (m ^. modId) (m ^. modId) conns + where + conns = + ModConn + . Id + <$> (m ^.. modOutPorts . traverse . portName) + ++ (m ^.. modInPorts . traverse . portName) + +-- | Instantiate without adding wire declarations. It also does not count the +-- current instantiations of the same module. +-- +-- >>> render $ instantiateModSpec_ "_" m +-- m m(.y(y), .x(x)); +-- +instantiateModSpec_ :: Text -> ModDecl -> ModItem +instantiateModSpec_ outChar m = ModInst (m ^. modId) (m ^. modId) conns + where + conns = + zipWith ModConnNamed ids (Id <$> instIds) + ids = (filterChar outChar $ name modOutPorts) ++ (name modInPorts) + instIds = (name modOutPorts) ++ (name modInPorts) + name v = m ^.. v . traverse . portName + +filterChar :: Text -> [Identifier] -> [Identifier] +filterChar t ids = + ids & traverse . getIdentifier %~ (\x -> fromMaybe x . safe head $ T.splitOn t x) + +-- | Initialise all the inputs and outputs to a module. +-- +-- >>> render $ initMod m +-- module m(y, x); +-- output wire [4:0] y; +-- input wire [4:0] x; +-- endmodule +-- +initMod :: ModDecl -> ModDecl +initMod m = m & modItems %~ ((out ++ inp) ++) + where + out = Decl (Just PortOut) <$> (m ^. modOutPorts) + inp = Decl (Just PortIn) <$> (m ^. modInPorts) + +makeIdFrom :: (Show a) => a -> Identifier -> Identifier +makeIdFrom a i = (i <>) . Identifier . ("_" <>) $ showT a + +-- | Make top level module for equivalence verification. Also takes in how many +-- modules to instantiate. +makeTop :: Int -> ModDecl -> ModDecl +makeTop i m = ModDecl (m ^. modId) ys (m ^. modInPorts) modIt + where + ys = Port Wire 90 . flip makeIdFrom "y" <$> [1 .. i] + modIt = instantiateModSpec_ "_" . modN <$> [1 .. i] + modN n = m & modId %~ makeIdFrom n & modOutPorts .~ [Port Wire 90 (makeIdFrom n "y")] + +makeTopAssert :: ModDecl -> ModDecl +makeTopAssert = (modItems %~ (++ [assert])) . (modInPorts %~ addClk) . makeTop 2 + where + assert = Always . EventCtrl e . Just $ SeqBlock + [TaskEnable $ Task "assert" [BinOp (Id "y_1") BinEq (Id "y_2")]] + e = EPosEdge "clk" + addClk = ((Port Wire 1 "clk") :) diff --git a/src/VeriFuzz/Random.hs b/src/VeriFuzz/Random.hs new file mode 100644 index 0000000..7989b49 --- /dev/null +++ b/src/VeriFuzz/Random.hs @@ -0,0 +1,54 @@ +{-| +Module : VeriFuzz.Circuit.Random +Description : Random generation for DAG +Copyright : (c) 2018-2019, Yann Herklotz Grave +License : BSD-3 +Maintainer : ymherklotz [at] gmail [dot] com +Stability : experimental +Portability : POSIX + +Define the random generation for the directed acyclic graph. +-} + +module VeriFuzz.Circuit.Random where + +import Data.Graph.Inductive (Context, LEdge) +import qualified Data.Graph.Inductive as G +import Data.Graph.Inductive.PatriciaTree (Gr) +import Data.List (nub) +import Test.QuickCheck (Arbitrary, Gen) +import qualified Test.QuickCheck as QC + +dupFolder :: (Eq a, Eq b) => Context a b -> [Context a b] -> [Context a b] +dupFolder cont ns = unique cont : ns + where unique (a, b, c, d) = (nub a, b, c, nub d) + +-- | Remove duplicates. +rDups :: (Eq a, Eq b) => Gr a b -> Gr a b +rDups g = G.buildGr $ G.ufold dupFolder [] g + +-- | Gen instance to create an arbitrary edge, where the edges are limited by +-- `n` that is passed to it. +arbitraryEdge :: (Arbitrary e) => Int -> Gen (LEdge e) +arbitraryEdge n = do + x <- with $ \a -> a < n && a > 0 && a /= n - 1 + y <- with $ \a -> x < a && a < n && a > 0 + z <- QC.arbitrary + return (x, y, z) + where + with = QC.suchThat $ QC.resize n QC.arbitrary + +-- | Gen instance for a random acyclic DAG. +randomDAG :: (Arbitrary l, Arbitrary e, Eq l, Eq e) => Gen (Gr l e) -- ^ The generated graph. It uses Arbitrary to + -- generate random instances of each node +randomDAG = do + list <- QC.infiniteListOf QC.arbitrary + l <- QC.infiniteListOf aE + QC.sized (\n -> return . G.mkGraph (nodes list n) $ take (10 * n) l) + where + nodes l n = zip [0 .. n] $ take n l + aE = QC.sized arbitraryEdge + +-- | Generate a random acyclic DAG with an IO instance. +genRandomDAG :: (Arbitrary l, Arbitrary e, Eq l, Eq e) => IO (Gr l e) +genRandomDAG = QC.generate randomDAG diff --git a/src/VeriFuzz/RandomAlt.hs b/src/VeriFuzz/RandomAlt.hs new file mode 100644 index 0000000..93a50e9 --- /dev/null +++ b/src/VeriFuzz/RandomAlt.hs @@ -0,0 +1,25 @@ +{-|p +Module : VeriFuzz.Circuit.RandomAlt +Description : RandomAlt generation for DAG +Copyright : (c) 2018-2019, Yann Herklotz Grave +License : BSD-3 +Maintainer : ymherklotz [at] gmail [dot] com +Stability : experimental +Portability : POSIX + +Define the random generation for the directed acyclic graph. +-} + +module VeriFuzz.Circuit.RandomAlt where + +import qualified Data.Graph.Inductive.Arbitrary as G +import Data.Graph.Inductive.PatriciaTree (Gr) +import Test.QuickCheck (Arbitrary, Gen) +import qualified Test.QuickCheck as QC + +randomDAG :: (Arbitrary l, Arbitrary e) => Gen (Gr l e) +randomDAG = G.looplessGraph <$> QC.arbitrary + +-- | Generate a random acyclic DAG with an IO instance. +genRandomDAG :: (Arbitrary l, Arbitrary e) => IO (Gr l e) +genRandomDAG = QC.generate randomDAG diff --git a/src/VeriFuzz/Simulator.hs b/src/VeriFuzz/Simulator.hs deleted file mode 100644 index a84cd5f..0000000 --- a/src/VeriFuzz/Simulator.hs +++ /dev/null @@ -1,41 +0,0 @@ -{-| -Module : VeriFuzz.Simulator -Description : Simulator module. -Copyright : (c) 2018-2019, Yann Herklotz Grave -License : BSD-3 -Maintainer : ymherklotz [at] gmail [dot] com -Stability : experimental -Portability : POSIX - -Simulator module. --} - -module VeriFuzz.Simulator - ( SimMatrix - , module VeriFuzz.Simulator.General - , module VeriFuzz.Simulator.Yosys - , module VeriFuzz.Simulator.Xst - , module VeriFuzz.Simulator.Icarus - ) -where - -import Control.Monad.Trans.Reader -import Prelude hiding (FilePath) -import Shelly -import VeriFuzz.Simulator.General -import VeriFuzz.Simulator.Icarus -import VeriFuzz.Simulator.Xst -import VeriFuzz.Simulator.Yosys - --- | Environment used to run the main -data SimMatrix = SimMatrix { yosys :: Yosys - , xst :: Maybe Xst - , icarus :: Maybe Icarus - } - -type SimEnv = ReaderT SimMatrix IO - -runAll :: SimEnv () -runAll = do - val <- asks xst - shelly $ run_ "echo" ["Hello World"] diff --git a/src/VeriFuzz/Simulator/General.hs b/src/VeriFuzz/Simulator/General.hs deleted file mode 100644 index dbd1da0..0000000 --- a/src/VeriFuzz/Simulator/General.hs +++ /dev/null @@ -1,70 +0,0 @@ -{-| -Module : VeriFuzz.Simulator.General -Description : Class of the simulator. -Copyright : (c) 2018-2019, Yann Herklotz Grave -License : BSD-3 -Maintainer : ymherklotz [at] gmail [dot] com -Stability : experimental -Portability : POSIX - -Class of the simulator and the synthesize tool. --} - -module VeriFuzz.Simulator.General where - -import Data.Bits (shiftL) -import Data.ByteString (ByteString) -import qualified Data.ByteString as B -import Data.Text (Text) -import qualified Data.Text as T -import Prelude hiding (FilePath) -import Shelly -import System.FilePath.Posix (takeBaseName) -import VeriFuzz.Verilog.AST - --- | Simulator class. -class Simulator a where - toText :: a -> Text - --- | Simulation type class. -class (Simulator a) => Simulate a where - runSim :: a -- ^ Simulator instance - -> ModDecl -- ^ Module to simulate - -> [ByteString] -- ^ Inputs to simulate - -> Sh Int -- ^ Returns the value of the hash at the output of the testbench. - --- | Synthesize type class. -class (Simulator a) => Synthesize a where - runSynth :: a -- ^ Synthesize tool instance - -> ModDecl -- ^ Module to synthesize - -> FilePath -- ^ Output verilog file for the module - -> Sh () -- ^ does not return any values - -rootPath :: Sh FilePath -rootPath = do - current <- pwd - maybe current fromText <$> get_env "VERIFUZZ_ROOT" - -timeout :: FilePath -> [Text] -> Sh Text -timeout = command1 "timeout" ["180"] . toTextIgnore -{-# INLINE timeout #-} - -timeout_ :: FilePath -> [Text] -> Sh () -timeout_ = command1_ "timeout" ["180"] . toTextIgnore -{-# INLINE timeout_ #-} - --- | Helper function to convert bytestrings to integers -bsToI :: ByteString -> Integer -bsToI = B.foldl' (\i b -> (i `shiftL` 8) + fromIntegral b) 0 -{-# INLINE bsToI #-} - -noPrint :: Sh a -> Sh a -noPrint = - print_stdout False . print_stderr False - -echoP :: Text -> Sh () -echoP t = do - fn <- pwd - echo $ bname fn <> " :: " <> t - where - bname = T.pack . takeBaseName . T.unpack . toTextIgnore diff --git a/src/VeriFuzz/Simulator/Icarus.hs b/src/VeriFuzz/Simulator/Icarus.hs deleted file mode 100644 index 527322a..0000000 --- a/src/VeriFuzz/Simulator/Icarus.hs +++ /dev/null @@ -1,63 +0,0 @@ -{-| -Module : VeriFuzz.Simulator.Icarus -Description : Icarus verilog module. -Copyright : (c) 2018-2019, Yann Herklotz Grave -License : BSD-3 -Maintainer : ymherklotz [at] gmail [dot] com -Stability : experimental -Portability : POSIX - -Icarus verilog module. --} - -module VeriFuzz.Simulator.Icarus where - -import Control.Lens -import Data.ByteString (ByteString) -import qualified Data.ByteString as B -import Data.Foldable (fold) -import Data.Hashable -import Data.List (transpose) -import Prelude hiding (FilePath) -import Shelly -import VeriFuzz.Simulator.General -import VeriFuzz.Verilog - -data Icarus = Icarus { icarusPath :: FilePath - , vvpPath :: FilePath - } - -instance Simulator Icarus where - toText _ = "iverilog" - -instance Simulate Icarus where - runSim = runSimIcarus - -defaultIcarus :: Icarus -defaultIcarus = Icarus "iverilog" "vvp" - -addDisplay :: [Stmnt] -> [Stmnt] -addDisplay s = concat $ transpose - [s, replicate l $ TimeCtrl 1 Nothing, replicate l . SysTaskEnable $ Task "display" ["%h", Id "y"]] - where l = length s - -assignFunc :: [Port] -> ByteString -> Stmnt -assignFunc inp bs = NonBlockAssign . Assign conc Nothing . Number (B.length bs * 4) $ bsToI bs - where conc = RegConcat (portToExpr <$> inp) - -runSimIcarus :: Icarus -> ModDecl -> [ByteString] -> Sh Int -runSimIcarus sim m bss = do - let tb = ModDecl - "main" - [] - [] - [ Initial - $ fold (addDisplay $ assignFunc (m ^. modInPorts) <$> bss) - <> (SysTaskEnable $ Task "finish" []) - ] - let newtb = instantiateMod m tb - let modWithTb = VerilogSrc $ Description <$> [newtb, m] - writefile "main.v" $ genSource modWithTb - echoP "Run icarus" - noPrint $ run_ (icarusPath sim) ["-o", "main", "main.v"] - hash <$> run (vvpPath sim) ["main"] diff --git a/src/VeriFuzz/Simulator/Xst.hs b/src/VeriFuzz/Simulator/Xst.hs deleted file mode 100644 index 52272c3..0000000 --- a/src/VeriFuzz/Simulator/Xst.hs +++ /dev/null @@ -1,57 +0,0 @@ -{-| -Module : VeriFuzz.Simulator.Xst -Description : Xst (ise) simulator implementation. -Copyright : (c) 2018-2019, Yann Herklotz Grave -License : BSD-3 -Maintainer : ymherklotz [at] gmail [dot] com -Stability : experimental -Portability : POSIX - -Xst (ise) simulator implementation. --} - -{-# LANGUAGE QuasiQuotes #-} - -module VeriFuzz.Simulator.Xst where - -import Control.Lens hiding ((<.>)) -import qualified Data.Text as T -import Prelude hiding (FilePath) -import Shelly -import System.FilePath.Posix (takeBaseName) -import Text.Shakespeare.Text (st) -import VeriFuzz.Simulator.General -import VeriFuzz.Simulator.Internal.Template -import VeriFuzz.Verilog -import VeriFuzz.Verilog - -data Xst = Xst { xstPath :: FilePath - , netgenPath :: FilePath - } - -instance Simulator Xst where - toText _ = "xst" - -instance Synthesize Xst where - runSynth = runSynthXst - -defaultXst :: Xst -defaultXst = - Xst "/opt/Xilinx/14.7/ISE_DS/ISE/bin/lin64/xst" "/opt/Xilinx/14.7/ISE_DS/ISE/bin/lin64/netgen" - -runSynthXst :: Xst -> ModDecl -> FilePath -> Sh () -runSynthXst sim m outf = do - writefile xstFile $ xstSynthConfig m - writefile prjFile [st|verilog work "rtl.v"|] - writefile "rtl.v" $ genSource m - echoP "Run xst" - noPrint $ timeout_ (xstPath sim) ["-ifn", toTextIgnore xstFile] - echoP "Run netgen" - noPrint $ run_ (netgenPath sim) - ["-w", "-ofmt", "verilog", toTextIgnore $ modFile <.> "ngc", toTextIgnore outf] - echoP "Clean synthesized file" - noPrint $ run_ "sed" ["-i", "/^`ifndef/,/^`endif/ d; s/ *Timestamp: .*//;", toTextIgnore outf] - where - modFile = fromText $ modName m - xstFile = modFile <.> "xst" - prjFile = modFile <.> "prj" diff --git a/src/VeriFuzz/Simulator/Yosys.hs b/src/VeriFuzz/Simulator/Yosys.hs deleted file mode 100644 index e18de5a..0000000 --- a/src/VeriFuzz/Simulator/Yosys.hs +++ /dev/null @@ -1,81 +0,0 @@ -{-| -Module : VeriFuzz.Simulator.Yosys -Description : Yosys simulator implementation. -Copyright : (c) 2018-2019, Yann Herklotz Grave -License : BSD-3 -Maintainer : ymherklotz [at] gmail [dot] com -Stability : experimental -Portability : POSIX - -Yosys simulator implementation. --} - -{-# LANGUAGE QuasiQuotes #-} - -module VeriFuzz.Simulator.Yosys where - -import Data.Maybe (fromMaybe) -import Data.Text (Text) -import qualified Data.Text as T -import Prelude hiding (FilePath) -import Shelly -import Text.Shakespeare.Text (st) -import VeriFuzz.Simulator.General -import VeriFuzz.Simulator.Internal.Template -import VeriFuzz.Verilog - -newtype Yosys = Yosys { yosysPath :: FilePath } - -instance Simulator Yosys where - toText _ = "yosys" - -instance Synthesize Yosys where - runSynth = runSynthYosys - -defaultYosys :: Yosys -defaultYosys = Yosys "/usr/bin/yosys" - -writeSimFile - :: Yosys -- ^ Simulator instance - -> ModDecl -- ^ Current module - -> FilePath -- ^ Output sim file - -> Sh () -writeSimFile _ m file = do - writefile "rtl.v" $ genSource m - writefile file yosysSimConfig - -runSynthYosys :: Yosys -> ModDecl -> FilePath -> Sh () -runSynthYosys sim m outf = do - writefile inpf $ genSource m - echoP "Run yosim" - noPrint $ run_ (yosysPath sim) ["-q", "-b", "verilog -noattr", "-o", out, "-S", inp] - where - inpf = "rtl.v" - inp = toTextIgnore inpf - out = toTextIgnore outf - -- ids = T.intercalate "," $ allVars m ^.. traverse . getIdentifier - -runMaybeSynth :: (Synthesize a) => Maybe a -> ModDecl -> Sh () -runMaybeSynth (Just sim) m = runSynth sim m $ fromText [st|syn_#{toText sim}.v|] -runMaybeSynth Nothing m = writefile "syn_rtl.v" $ genSource m - -runEquivYosys :: (Synthesize a, Synthesize b) => Yosys -> a -> Maybe b -> ModDecl -> Sh () -runEquivYosys yosys sim1 sim2 m = do - writefile "top.v" . genSource . initMod $ makeTop 2 m - writefile checkFile $ yosysSatConfig sim1 sim2 m - runSynth sim1 m $ fromText [st|syn_#{toText sim1}.v|] - runMaybeSynth sim2 m - echoP "Run yosys" - noPrint $ run_ (yosysPath yosys) [toTextIgnore checkFile] - where - checkFile = fromText [st|test.#{toText sim1}.#{maybe "rtl" toText sim2}.ys|] - -runEquiv :: (Synthesize a, Synthesize b) => Yosys -> a -> Maybe b -> ModDecl -> Sh () -runEquiv yosys sim1 sim2 m = do - root <- rootPath - writefile "top.v" . genSource . initMod $ makeTopAssert m - writefile "test.sby" $ sbyConfig root sim1 sim2 m - runSynth sim1 m $ fromText [st|syn_#{toText sim1}.v|] - runMaybeSynth sim2 m - echoP "Run SymbiYosys" - noPrint $ run_ "sby" ["test.sby"] diff --git a/src/VeriFuzz/Verilog.hs b/src/VeriFuzz/Verilog.hs deleted file mode 100644 index 6b6a13f..0000000 --- a/src/VeriFuzz/Verilog.hs +++ /dev/null @@ -1,27 +0,0 @@ -{-| -Module : VeriFuzz.Verilog -Description : The main verilog module with the syntax and code generation. -Copyright : (c) 2018-2019, Yann Herklotz Grave -License : BSD-3 -Maintainer : ymherklotz [at] gmail [dot] com -Stability : experimental -Portability : POSIX - -The main verilog module with the syntax and code generation. --} - -module VeriFuzz.Verilog - ( -- * AST - module VeriFuzz.Verilog.AST - -- * Code Generation - , module VeriFuzz.Verilog.CodeGen - -- * Verilog mutations - , module VeriFuzz.Verilog.Mutate - , module VeriFuzz.Verilog.Helpers - ) -where - -import VeriFuzz.Verilog.AST -import VeriFuzz.Verilog.CodeGen -import VeriFuzz.Verilog.Helpers -import VeriFuzz.Verilog.Mutate diff --git a/src/VeriFuzz/Verilog/AST.hs b/src/VeriFuzz/Verilog/AST.hs deleted file mode 100644 index 0f24c49..0000000 --- a/src/VeriFuzz/Verilog/AST.hs +++ /dev/null @@ -1,564 +0,0 @@ -{-| -Module : VeriFuzz.Verilog.AST -Description : Definition of the Verilog AST types. -Copyright : (c) 2018-2019, Yann Herklotz Grave -License : BSD-3 -Maintainer : ymherklotz [at] gmail [dot] com -Stability : experimental -Poratbility : POSIX - -Defines the types to build a Verilog AST. --} - -{-# LANGUAGE GeneralizedNewtypeDeriving #-} -{-# LANGUAGE TemplateHaskell #-} - -module VeriFuzz.Verilog.AST - ( -- * Top level types - VerilogSrc(..) - , getVerilogSrc - , Description(..) - , getDescription - -- * Primitives - -- ** Identifier - , Identifier(..) - , getIdentifier - -- ** Control - , Delay(..) - , getDelay - , Event(..) - -- ** Operators - , BinaryOperator(..) - , UnaryOperator(..) - -- ** Task - , Task(..) - , taskName - , taskExpr - -- ** Left hand side value - , LVal(..) - , regId - , regExprId - , regExpr - , regSizeId - , regSizeMSB - , regSizeLSB - , regConc - -- ** Ports - , PortDir(..) - , PortType(..) - , regSigned - , Port(..) - , portType - , portSize - , portName - -- * Expression - , Expr(..) - , exprSize - , exprVal - , exprId - , exprConcat - , exprUnOp - , exprPrim - , exprLhs - , exprBinOp - , exprRhs - , exprCond - , exprTrue - , exprFalse - , exprFunc - , exprBody - , exprStr - , exprWithContext - , traverseExpr - , ConstExpr(..) - , constNum - , Function (..) - -- * Assignment - , Assign(..) - , assignReg - , assignDelay - , assignExpr - , ContAssign(..) - , contAssignNetLVal - , contAssignExpr - -- * Statment - , Stmnt(..) - , statDelay - , statDStat - , statEvent - , statEStat - , statements - , stmntBA - , stmntNBA - , stmntCA - , stmntTask - , stmntSysTask - -- * Module - , ModDecl(..) - , modId - , modOutPorts - , modInPorts - , modItems - , ModItem(..) - , _ModCA - , modInstId - , modInstName - , modInstConns - , declDir - , declPort - , ModConn(..) - , modConn - , modConnName - , modExpr - ) -where - -import Control.Lens (makeLenses, makePrisms) -import Control.Monad (replicateM) -import Data.String (IsString, fromString) -import Data.Text (Text) -import qualified Data.Text as T -import Data.Traversable (sequenceA) -import qualified Test.QuickCheck as QC - -positiveArb :: (QC.Arbitrary a, Ord a, Num a) => QC.Gen a -positiveArb = QC.suchThat QC.arbitrary (> 0) - --- | Identifier in Verilog. This is just a string of characters that can either --- be lowercase and uppercase for now. This might change in the future though, --- as Verilog supports many more characters in Identifiers. -newtype Identifier = Identifier { _getIdentifier :: Text } - deriving (Eq, Show, IsString, Semigroup, Monoid) - -makeLenses ''Identifier - -instance QC.Arbitrary Identifier where - arbitrary = do - l <- QC.choose (2, 10) - Identifier . T.pack <$> replicateM l (QC.elements ['a'..'z']) - --- | Verilog syntax for adding a delay, which is represented as @#num@. -newtype Delay = Delay { _getDelay :: Int } - deriving (Eq, Show, Num) - -makeLenses ''Delay - -instance QC.Arbitrary Delay where - arbitrary = Delay <$> positiveArb - --- | Verilog syntax for an event, such as @\@x@, which is used for always blocks -data Event = EId Identifier - | EExpr Expr - | EAll - | EPosEdge Identifier - | ENegEdge Identifier - deriving (Eq, Show) - -instance QC.Arbitrary Event where - arbitrary = EId <$> QC.arbitrary - --- | Binary operators that are currently supported in the verilog generation. -data BinaryOperator = BinPlus -- ^ @+@ - | BinMinus -- ^ @-@ - | BinTimes -- ^ @*@ - | BinDiv -- ^ @/@ - | BinMod -- ^ @%@ - | BinEq -- ^ @==@ - | BinNEq -- ^ @!=@ - | BinCEq -- ^ @===@ - | BinCNEq -- ^ @!==@ - | BinLAnd -- ^ @&&@ - | BinLOr -- ^ @||@ - | BinLT -- ^ @<@ - | BinLEq -- ^ @<=@ - | BinGT -- ^ @>@ - | BinGEq -- ^ @>=@ - | BinAnd -- ^ @&@ - | BinOr -- ^ @|@ - | BinXor -- ^ @^@ - | BinXNor -- ^ @^~@ - | BinXNorInv -- ^ @~^@ - | BinPower -- ^ @**@ - | BinLSL -- ^ @<<@ - | BinLSR -- ^ @>>@ - | BinASL -- ^ @<<<@ - | BinASR -- ^ @>>>@ - deriving (Eq, Show) - -instance QC.Arbitrary BinaryOperator where - arbitrary = QC.elements - [ BinPlus - , BinMinus - , BinTimes - , BinDiv - , BinMod - , BinEq - , BinNEq - , BinCEq - , BinCNEq - , BinLAnd - , BinLOr - , BinLT - , BinLEq - , BinGT - , BinGEq - , BinAnd - , BinOr - , BinXor - , BinXNor - , BinXNorInv - , BinPower - , BinLSL - , BinLSR - , BinASL - , BinASR - ] - --- | Unary operators that are currently supported by the generator. -data UnaryOperator = UnPlus -- ^ @+@ - | UnMinus -- ^ @-@ - | UnNot -- ^ @!@ - | UnAnd -- ^ @&@ - | UnNand -- ^ @~&@ - | UnOr -- ^ @|@ - | UnNor -- ^ @~|@ - | UnXor -- ^ @^@ - | UnNxor -- ^ @~^@ - | UnNxorInv -- ^ @^~@ - deriving (Eq, Show) - -instance QC.Arbitrary UnaryOperator where - arbitrary = QC.elements - [ UnPlus - , UnMinus - , UnNot - , UnAnd - , UnNand - , UnOr - , UnNor - , UnXor - , UnNxor - , UnNxorInv - ] - -data Function = SignedFunc - | UnSignedFunc - deriving (Eq, Show) - -instance QC.Arbitrary Function where - arbitrary = QC.elements - [ SignedFunc - , UnSignedFunc - ] - --- | Verilog expression, which can either be a primary expression, unary --- expression, binary operator expression or a conditional expression. -data Expr = Number { _exprSize :: Int - , _exprVal :: Integer - } - | Id { _exprId :: Identifier } - | Concat { _exprConcat :: [Expr] } - | UnOp { _exprUnOp :: UnaryOperator - , _exprPrim :: Expr - } - | BinOp { _exprLhs :: Expr - , _exprBinOp :: BinaryOperator - , _exprRhs :: Expr - } - | Cond { _exprCond :: Expr - , _exprTrue :: Expr - , _exprFalse :: Expr - } - | Func { _exprFunc :: Function - , _exprBody :: Expr - } - | Str { _exprStr :: Text } - deriving (Eq, Show) - -instance Num Expr where - a + b = BinOp a BinPlus b - a - b = BinOp a BinMinus b - a * b = BinOp a BinTimes b - negate = UnOp UnMinus - abs = undefined - signum = undefined - fromInteger = Number 32 . fromInteger - -instance Semigroup Expr where - (Concat a) <> (Concat b) = Concat $ a <> b - (Concat a) <> b = Concat $ a <> [b] - a <> (Concat b) = Concat $ a : b - a <> b = Concat [a, b] - -instance Monoid Expr where - mempty = Concat [] - -instance IsString Expr where - fromString = Str . fromString - -exprSafeList :: [QC.Gen Expr] -exprSafeList = - [ Number <$> positiveArb <*> QC.arbitrary - -- , Str <$> QC.arbitrary - ] - -exprRecList :: (Int -> QC.Gen Expr) -> [QC.Gen Expr] -exprRecList subexpr = - [ Number <$> positiveArb <*> QC.arbitrary - , Concat <$> QC.listOf1 (subexpr 8) - , UnOp - <$> QC.arbitrary - <*> subexpr 2 - -- , Str <$> QC.arbitrary - , BinOp <$> subexpr 2 <*> QC.arbitrary <*> subexpr 2 - , Cond <$> subexpr 3 <*> subexpr 3 <*> subexpr 3 - , Func <$> QC.arbitrary <*> subexpr 2 - ] - -expr :: Int -> QC.Gen Expr -expr n - | n == 0 = QC.oneof $ (Id <$> QC.arbitrary) : exprSafeList - | n > 0 = QC.oneof $ (Id <$> QC.arbitrary) : exprRecList subexpr - | otherwise = expr 0 - where subexpr y = expr (n `div` y) - -exprWithContext :: [Identifier] -> Int -> QC.Gen Expr -exprWithContext l n - | n == 0 = QC.oneof $ (Id <$> QC.elements l) : exprSafeList - | n > 0 = QC.oneof $ (Id <$> QC.elements l) : exprRecList subexpr - | otherwise = exprWithContext l 0 - where subexpr y = exprWithContext l (n `div` y) - -instance QC.Arbitrary Expr where - arbitrary = QC.sized expr - -traverseExpr :: (Applicative f) => (Expr -> f Expr) -> Expr -> f Expr -traverseExpr f (Concat e ) = Concat <$> sequenceA (f <$> e) -traverseExpr f (UnOp un e ) = UnOp un <$> f e -traverseExpr f (BinOp l op r) = BinOp <$> f l <*> pure op <*> f r -traverseExpr f (Cond c l r) = Cond <$> f c <*> f l <*> f r -traverseExpr f (Func fn e ) = Func fn <$> f e -traverseExpr _ e = pure e - -makeLenses ''Expr - --- | Constant expression, which are known before simulation at compilation time. -newtype ConstExpr = ConstExpr { _constNum :: Int } - deriving (Eq, Show, Num, QC.Arbitrary) - -makeLenses ''ConstExpr - -data Task = Task { _taskName :: Identifier - , _taskExpr :: [Expr] - } deriving (Eq, Show) - -makeLenses ''Task - -instance QC.Arbitrary Task where - arbitrary = Task <$> QC.arbitrary <*> QC.arbitrary - --- | Type that represents the left hand side of an assignment, which can be a --- concatenation such as in: --- --- @ --- {a, b, c} = 32'h94238; --- @ -data LVal = RegId { _regId :: Identifier} - | RegExpr { _regExprId :: Identifier - , _regExpr :: Expr - } - | RegSize { _regSizeId :: Identifier - , _regSizeMSB :: ConstExpr - , _regSizeLSB :: ConstExpr - } - | RegConcat { _regConc :: [Expr] } - deriving (Eq, Show) - -makeLenses ''LVal - -instance QC.Arbitrary LVal where - arbitrary = QC.oneof [ RegId <$> QC.arbitrary - , RegExpr <$> QC.arbitrary <*> QC.arbitrary - , RegSize <$> QC.arbitrary <*> QC.arbitrary <*> QC.arbitrary - ] - -instance IsString LVal where - fromString = RegId . fromString - --- | Different port direction that are supported in Verilog. -data PortDir = PortIn -- ^ Input direction for port (@input@). - | PortOut -- ^ Output direction for port (@output@). - | PortInOut -- ^ Inout direction for port (@inout@). - deriving (Eq, Show) - -instance QC.Arbitrary PortDir where - arbitrary = QC.elements [PortIn, PortOut, PortInOut] - --- | Currently, only @wire@ and @reg@ are supported, as the other net types are --- not that common and not a priority. -data PortType = Wire - | Reg { _regSigned :: Bool } - deriving (Eq, Show) - -instance QC.Arbitrary PortType where - arbitrary = QC.oneof [pure Wire, Reg <$> QC.arbitrary] - -makeLenses ''PortType - --- | Port declaration. It contains information about the type of the port, the --- size, and the port name. It used to also contain information about if it was --- an input or output port. However, this is not always necessary and was more --- cumbersome than useful, as a lot of ports can be declared without input and --- output port. --- --- This is now implemented inside 'ModDecl' itself, which uses a list of output --- and input ports. -data Port = Port { _portType :: PortType - , _portSize :: Int - , _portName :: Identifier - } deriving (Eq, Show) - -makeLenses ''Port - -instance QC.Arbitrary Port where - arbitrary = Port <$> QC.arbitrary <*> positiveArb <*> QC.arbitrary - --- | This is currently a type because direct module declaration should also be --- added: --- --- @ --- mod a(.y(y1), .x1(x11), .x2(x22)); --- @ -data ModConn = ModConn { _modConn :: Expr } - | ModConnNamed { _modConnName :: Identifier - , _modExpr :: Expr - } - deriving (Eq, Show) - -makeLenses ''ModConn - -instance QC.Arbitrary ModConn where - arbitrary = ModConn <$> QC.arbitrary - -data Assign = Assign { _assignReg :: LVal - , _assignDelay :: Maybe Delay - , _assignExpr :: Expr - } deriving (Eq, Show) - -makeLenses ''Assign - -instance QC.Arbitrary Assign where - arbitrary = Assign <$> QC.arbitrary <*> QC.arbitrary <*> QC.arbitrary - -data ContAssign = ContAssign { _contAssignNetLVal :: Identifier - , _contAssignExpr :: Expr - } deriving (Eq, Show) - -makeLenses ''ContAssign - -instance QC.Arbitrary ContAssign where - arbitrary = ContAssign <$> QC.arbitrary <*> QC.arbitrary - --- | Statements in Verilog. -data Stmnt = TimeCtrl { _statDelay :: Delay - , _statDStat :: Maybe Stmnt - } -- ^ Time control (@#NUM@) - | EventCtrl { _statEvent :: Event - , _statEStat :: Maybe Stmnt - } - | SeqBlock { _statements :: [Stmnt] } -- ^ Sequential block (@begin ... end@) - | BlockAssign { _stmntBA :: Assign } -- ^ blocking assignment (@=@) - | NonBlockAssign { _stmntNBA :: Assign } -- ^ Non blocking assignment (@<=@) - | StatCA { _stmntCA :: ContAssign } -- ^ Stmnt continuous assignment. May not be correct. - | TaskEnable { _stmntTask :: Task} - | SysTaskEnable { _stmntSysTask :: Task} - deriving (Eq, Show) - -makeLenses ''Stmnt - -instance Semigroup Stmnt where - (SeqBlock a) <> (SeqBlock b) = SeqBlock $ a <> b - (SeqBlock a) <> b = SeqBlock $ a <> [b] - a <> (SeqBlock b) = SeqBlock $ a : b - a <> b = SeqBlock [a, b] - -instance Monoid Stmnt where - mempty = SeqBlock [] - -statement :: Int -> QC.Gen Stmnt -statement n - | n == 0 = QC.oneof - [ BlockAssign <$> QC.arbitrary - , NonBlockAssign <$> QC.arbitrary - -- , StatCA <$> QC.arbitrary - , TaskEnable <$> QC.arbitrary - , SysTaskEnable <$> QC.arbitrary - ] - | n > 0 = QC.oneof - [ TimeCtrl <$> QC.arbitrary <*> (Just <$> substat 2) - , SeqBlock <$> QC.listOf1 (substat 4) - , BlockAssign <$> QC.arbitrary - , NonBlockAssign <$> QC.arbitrary - -- , StatCA <$> QC.arbitrary - , TaskEnable <$> QC.arbitrary - , SysTaskEnable <$> QC.arbitrary - ] - | otherwise = statement 0 - where substat y = statement (n `div` y) - -instance QC.Arbitrary Stmnt where - arbitrary = QC.sized statement - --- | Module item which is the body of the module expression. -data ModItem = ModCA ContAssign - | ModInst { _modInstId :: Identifier - , _modInstName :: Identifier - , _modInstConns :: [ModConn] - } - | Initial Stmnt - | Always Stmnt - | Decl { _declDir :: Maybe PortDir - , _declPort :: Port - } - deriving (Eq, Show) - -makeLenses ''ModItem -makePrisms ''ModItem - -instance QC.Arbitrary ModItem where - arbitrary = QC.oneof [ ModCA <$> QC.arbitrary - , ModInst <$> QC.arbitrary <*> QC.arbitrary <*> QC.arbitrary - , Initial <$> QC.arbitrary - , Always <$> (EventCtrl <$> QC.arbitrary <*> QC.arbitrary) - , Decl <$> pure Nothing <*> QC.arbitrary - ] - --- | 'module' module_identifier [list_of_ports] ';' { module_item } 'end_module' -data ModDecl = ModDecl { _modId :: Identifier - , _modOutPorts :: [Port] - , _modInPorts :: [Port] - , _modItems :: [ModItem] - } deriving (Eq, Show) - -makeLenses ''ModDecl - -modPortGen :: QC.Gen Port -modPortGen = QC.oneof - [ Port Wire <$> positiveArb <*> QC.arbitrary - , Port <$> (Reg <$> QC.arbitrary) <*> positiveArb <*> QC.arbitrary - ] - -instance QC.Arbitrary ModDecl where - arbitrary = ModDecl <$> QC.arbitrary <*> QC.arbitrary <*> QC.listOf1 modPortGen <*> QC.arbitrary - --- | Description of the Verilog module. -newtype Description = Description { _getDescription :: ModDecl } - deriving (Eq, Show, QC.Arbitrary) - -makeLenses ''Description - --- | The complete sourcetext for the Verilog module. -newtype VerilogSrc = VerilogSrc { _getVerilogSrc :: [Description] } - deriving (Eq, Show, QC.Arbitrary, Semigroup, Monoid) - -makeLenses ''VerilogSrc diff --git a/src/VeriFuzz/Verilog/CodeGen.hs b/src/VeriFuzz/Verilog/CodeGen.hs deleted file mode 100644 index 3253f86..0000000 --- a/src/VeriFuzz/Verilog/CodeGen.hs +++ /dev/null @@ -1,276 +0,0 @@ -{-| -Module : VeriFuzz.Verilog.CodeGen -Description : Code generation for Verilog AST. -Copyright : (c) 2018-2019, Yann Herklotz Grave -License : BSD-3 -Maintainer : ymherklotz [at] gmail [dot] com -Stability : experimental -Portability : POSIX - -This module generates the code from the Verilog AST defined in -"VeriFuzz.Verilog.AST". --} - -{-# LANGUAGE FlexibleInstances #-} - -module VeriFuzz.Verilog.CodeGen where - -import Control.Lens (view, (^.)) -import Data.Foldable (fold) -import Data.Text (Text) -import qualified Data.Text as T -import qualified Data.Text.IO as T -import Numeric (showHex) -import Test.QuickCheck (Arbitrary, arbitrary) -import VeriFuzz.Verilog.AST - --- | 'Source' class which determines that source code is able to be generated --- from the data structure using 'genSource'. This will be stored in 'Text' and --- can then be processed further. -class Source a where - genSource :: a -> Text - --- | Inserts commas between '[Text]' and except the last one. -comma :: [Text] -> Text -comma = T.intercalate ", " - --- | Show function for 'Text' -showT :: (Show a) => a -> Text -showT = T.pack . show - --- | Map a 'Maybe Stmnt' to 'Text'. If it is 'Just stmnt', the generated --- statements are returned. If it is 'Nothing', then @;\n@ is returned. -defMap :: Maybe Stmnt -> Text -defMap = maybe ";\n" genStmnt - --- | Convert the 'VerilogSrc' type to 'Text' so that it can be rendered. -genVerilogSrc :: VerilogSrc -> Text -genVerilogSrc source = fold $ genDescription <$> source ^. getVerilogSrc - --- | Generate the 'Description' to 'Text'. -genDescription :: Description -> Text -genDescription desc = genModuleDecl $ desc ^. getDescription - --- | Generate the 'ModDecl' for a module and convert it to 'Text'. -genModuleDecl :: ModDecl -> Text -genModuleDecl m = - "module " <> m ^. modId . getIdentifier <> ports <> ";\n" <> modI <> "endmodule\n" - where - ports | noIn && noOut = "" - | otherwise = "(" <> comma (genModPort <$> outIn) <> ")" - modI = fold $ genModuleItem <$> m ^. modItems - noOut = null $ m ^. modOutPorts - noIn = null $ m ^. modInPorts - outIn = (m ^. modOutPorts) ++ (m ^. modInPorts) - --- | Conversts 'Port' to 'Text' for the module list, which means it only --- generates a list of identifiers. -genModPort :: Port -> Text -genModPort port = port ^. portName . getIdentifier - --- | Generate the 'Port' description. -genPort :: Port -> Text -genPort port = t <> size <> name - where - t = (<> " ") . genPortType $ port ^. portType - size | port ^. portSize > 1 = "[" <> showT (port ^. portSize - 1) <> ":0] " - | otherwise = "" - name = port ^. portName . getIdentifier - --- | Convert the 'PortDir' type to 'Text'. -genPortDir :: PortDir -> Text -genPortDir PortIn = "input" -genPortDir PortOut = "output" -genPortDir PortInOut = "inout" - --- | Generate a 'ModItem'. -genModuleItem :: ModItem -> Text -genModuleItem (ModCA ca) = genContAssign ca -genModuleItem (ModInst (Identifier i) (Identifier name) conn) = - i <> " " <> name <> "(" <> comma (genModConn <$> conn) <> ")" <> ";\n" -genModuleItem (Initial stat ) = "initial " <> genStmnt stat -genModuleItem (Always stat ) = "always " <> genStmnt stat -genModuleItem (Decl dir port) = maybe "" makePort dir <> genPort port <> ";\n" - where makePort = (<> " ") . genPortDir - -genModConn :: ModConn -> Text -genModConn (ModConn c) = - genExpr c -genModConn (ModConnNamed n c) = - "." <> n ^. getIdentifier <> "(" <> genExpr c <> ")" - --- | Generate continuous assignment -genContAssign :: ContAssign -> Text -genContAssign (ContAssign val e) = "assign " <> name <> " = " <> expr <> ";\n" - where - name = val ^. getIdentifier - expr = genExpr e - --- | Generate 'Function' to 'Text' -genFunc :: Function -> Text -genFunc SignedFunc = "$signed" -genFunc UnSignedFunc = "$unsigned" - --- | Generate 'Expr' to 'Text'. -genExpr :: Expr -> Text -genExpr (BinOp eRhs bin eLhs) = "(" <> genExpr eRhs <> genBinaryOperator bin <> genExpr eLhs <> ")" -genExpr (Number s n ) = minus <> showT s <> "'h" <> T.pack (showHex (abs n) "") - where minus | signum n > 0 = "" | otherwise = "-" -genExpr (Id i ) = i ^. getIdentifier -genExpr (Concat c ) = "{" <> comma (genExpr <$> c) <> "}" -genExpr (UnOp u e ) = "(" <> genUnaryOperator u <> genExpr e <> ")" -genExpr (Cond l t f ) = "(" <> genExpr l <> " ? " <> genExpr t <> " : " <> genExpr f <> ")" -genExpr (Func f e ) = genFunc f <> "(" <> genExpr e <> ")" -genExpr (Str t ) = "\"" <> t <> "\"" - --- | Convert 'BinaryOperator' to 'Text'. -genBinaryOperator :: BinaryOperator -> Text -genBinaryOperator BinPlus = " + " -genBinaryOperator BinMinus = " - " -genBinaryOperator BinTimes = " * " -genBinaryOperator BinDiv = " / " -genBinaryOperator BinMod = " % " -genBinaryOperator BinEq = " == " -genBinaryOperator BinNEq = " != " -genBinaryOperator BinCEq = " === " -genBinaryOperator BinCNEq = " !== " -genBinaryOperator BinLAnd = " && " -genBinaryOperator BinLOr = " || " -genBinaryOperator BinLT = " < " -genBinaryOperator BinLEq = " <= " -genBinaryOperator BinGT = " > " -genBinaryOperator BinGEq = " >= " -genBinaryOperator BinAnd = " & " -genBinaryOperator BinOr = " | " -genBinaryOperator BinXor = " ^ " -genBinaryOperator BinXNor = " ^~ " -genBinaryOperator BinXNorInv = " ~^ " -genBinaryOperator BinPower = " ** " -genBinaryOperator BinLSL = " << " -genBinaryOperator BinLSR = " >> " -genBinaryOperator BinASL = " <<< " -genBinaryOperator BinASR = " >>> " - --- | Convert 'UnaryOperator' to 'Text'. -genUnaryOperator :: UnaryOperator -> Text -genUnaryOperator UnPlus = "+" -genUnaryOperator UnMinus = "-" -genUnaryOperator UnNot = "!" -genUnaryOperator UnAnd = "&" -genUnaryOperator UnNand = "~&" -genUnaryOperator UnOr = "|" -genUnaryOperator UnNor = "~|" -genUnaryOperator UnXor = "^" -genUnaryOperator UnNxor = "~^" -genUnaryOperator UnNxorInv = "^~" - --- | Generate verilog code for an 'Event'. -genEvent :: Event -> Text -genEvent (EId i ) = "@(" <> i ^. getIdentifier <> ")" -genEvent (EExpr expr) = "@(" <> genExpr expr <> ")" -genEvent EAll = "@*" -genEvent (EPosEdge i) = "@(posedge " <> i ^. getIdentifier <> ")" -genEvent (ENegEdge i) = "@(negedge " <> i ^. getIdentifier <> ")" - --- | Generates verilog code for a 'Delay'. -genDelay :: Delay -> Text -genDelay (Delay i) = "#" <> showT i - --- | Generate the verilog code for an 'LVal'. -genLVal :: LVal -> Text -genLVal (RegId i ) = i ^. getIdentifier -genLVal (RegExpr i expr) = i ^. getIdentifier <> " [" <> genExpr expr <> "]" -genLVal (RegSize i msb lsb) = - i ^. getIdentifier <> " [" <> genConstExpr msb <> ":" <> genConstExpr lsb <> "]" -genLVal (RegConcat e) = "{" <> comma (genExpr <$> e) <> "}" - -genConstExpr :: ConstExpr -> Text -genConstExpr (ConstExpr num) = showT num - -genPortType :: PortType -> Text -genPortType Wire = "wire" -genPortType (Reg signed) | signed = "reg signed" - | otherwise = "reg" - -genAssign :: Text -> Assign -> Text -genAssign op (Assign r d e) = genLVal r <> op <> maybe "" genDelay d <> genExpr e - -genStmnt :: Stmnt -> Text -genStmnt (TimeCtrl d stat ) = genDelay d <> " " <> defMap stat -genStmnt (EventCtrl e stat ) = genEvent e <> " " <> defMap stat -genStmnt (SeqBlock s ) = "begin\n" <> fold (genStmnt <$> s) <> "end\n" -genStmnt (BlockAssign a ) = genAssign " = " a <> ";\n" -genStmnt (NonBlockAssign a ) = genAssign " <= " a <> ";\n" -genStmnt (StatCA a ) = genContAssign a -genStmnt (TaskEnable task) = genTask task <> ";\n" -genStmnt (SysTaskEnable task) = "$" <> genTask task <> ";\n" - -genTask :: Task -> Text -genTask (Task name expr) | null expr = i - | otherwise = i <> "(" <> comma (genExpr <$> expr) <> ")" - where i = name ^. getIdentifier - --- | Render the 'Text' to 'IO'. This is equivalent to 'putStrLn'. -render :: (Source a) => a -> IO () -render = T.putStrLn . genSource - --- Instances - -instance Source Identifier where - genSource = view getIdentifier - -instance Source Task where - genSource = genTask - -instance Source Stmnt where - genSource = genStmnt - -instance Source PortType where - genSource = genPortType - -instance Source ConstExpr where - genSource = genConstExpr - -instance Source LVal where - genSource = genLVal - -instance Source Delay where - genSource = genDelay - -instance Source Event where - genSource = genEvent - -instance Source UnaryOperator where - genSource = genUnaryOperator - -instance Source Expr where - genSource = genExpr - -instance Source ContAssign where - genSource = genContAssign - -instance Source ModItem where - genSource = genModuleItem - -instance Source PortDir where - genSource = genPortDir - -instance Source Port where - genSource = genPort - -instance Source ModDecl where - genSource = genModuleDecl - -instance Source Description where - genSource = genDescription - -instance Source VerilogSrc where - genSource = genVerilogSrc - -newtype GenVerilog a = GenVerilog { unGenVerilog :: a } - -instance (Source a) => Show (GenVerilog a) where - show = T.unpack . genSource . unGenVerilog - -instance (Arbitrary a) => Arbitrary (GenVerilog a) where - arbitrary = GenVerilog <$> arbitrary diff --git a/src/VeriFuzz/Verilog/Helpers.hs b/src/VeriFuzz/Verilog/Helpers.hs deleted file mode 100644 index 99e5f38..0000000 --- a/src/VeriFuzz/Verilog/Helpers.hs +++ /dev/null @@ -1,72 +0,0 @@ -{-| -Module : VeriFuzz.Verilog.Helpers -Description : Defaults and common functions. -Copyright : (c) 2018-2019, Yann Herklotz Grave -License : BSD-3 -Maintainer : ymherklotz [at] gmail [dot] com -Stability : experimental -Portability : POSIX - -Defaults and common functions. --} - -module VeriFuzz.Verilog.Helpers where - -import Control.Lens -import Data.Text (Text) -import VeriFuzz.Verilog.AST - -regDecl :: Identifier -> ModItem -regDecl = Decl Nothing . Port (Reg False) 1 - -wireDecl :: Identifier -> ModItem -wireDecl = Decl Nothing . Port Wire 1 - --- | Create an empty module. -emptyMod :: ModDecl -emptyMod = ModDecl "" [] [] [] - --- | Set a module name for a module declaration. -setModName :: Text -> ModDecl -> ModDecl -setModName str = modId .~ Identifier str - --- | Add a input port to the module declaration. -addModPort :: Port -> ModDecl -> ModDecl -addModPort port = modInPorts %~ (:) port - -addDescription :: Description -> VerilogSrc -> VerilogSrc -addDescription desc = getVerilogSrc %~ (:) desc - -testBench :: ModDecl -testBench = ModDecl - "main" - [] - [] - [ regDecl "a" - , regDecl "b" - , wireDecl "c" - , ModInst "and" "and_gate" [ModConn $ Id "c", ModConn $ Id "a", ModConn $ Id "b"] - , Initial $ SeqBlock - [ BlockAssign . Assign (RegId "a") Nothing $ Number 1 1 - , BlockAssign . Assign (RegId "b") Nothing $ Number 1 1 - -- , TimeCtrl (Delay 1) . Just . SysTaskEnable $ Task "display" - -- [ Str "%d & %d = %d" - -- , PrimExpr $ PrimId "a" - -- , PrimExpr $ PrimId "b" - -- , PrimExpr $ PrimId "c" - -- ] - -- , SysTaskEnable $ Task "finish" [] - ] - ] - -addTestBench :: VerilogSrc -> VerilogSrc -addTestBench = addDescription $ Description testBench - -defaultPort :: Identifier -> Port -defaultPort = Port Wire 1 - -portToExpr :: Port -> Expr -portToExpr (Port _ _ i) = Id i - -modName :: ModDecl -> Text -modName = view $ modId . getIdentifier diff --git a/src/VeriFuzz/Verilog/Mutate.hs b/src/VeriFuzz/Verilog/Mutate.hs deleted file mode 100644 index 3e03a02..0000000 --- a/src/VeriFuzz/Verilog/Mutate.hs +++ /dev/null @@ -1,169 +0,0 @@ -{-| -Module : VeriFuzz.Verilog.Mutation -Description : Functions to mutate the Verilog AST. -Copyright : (c) 2018-2019, Yann Herklotz Grave -License : BSD-3 -Maintainer : ymherklotz [at] gmail [dot] com -Stability : experimental -Portability : POSIX - -Functions to mutate the Verilog AST from "VeriFuzz.Verilog.AST" to generate more -random patterns, such as nesting wires instead of creating new ones. --} - -module VeriFuzz.Verilog.Mutate where - -import Control.Lens -import Data.Maybe (catMaybes, fromMaybe) -import Data.Text (Text) -import qualified Data.Text as T -import VeriFuzz.Internal.Gen -import VeriFuzz.Internal.Shared -import VeriFuzz.Verilog.AST -import VeriFuzz.Verilog.CodeGen - --- | Return if the 'Identifier' is in a 'ModDecl'. -inPort :: Identifier -> ModDecl -> Bool -inPort i m = inInput - where inInput = any (\a -> a ^. portName == i) $ - m ^. modInPorts ++ m ^. modOutPorts - --- | Find the last assignment of a specific wire/reg to an expression, and --- returns that expression. -findAssign :: Identifier -> [ModItem] -> Maybe Expr -findAssign i items = safe last . catMaybes $ isAssign <$> items - where - isAssign (ModCA (ContAssign val expr)) - | val == i = Just expr - | otherwise = Nothing - isAssign _ = Nothing - --- | Transforms an expression by replacing an Identifier with an --- expression. This is used inside 'transformOf' and 'traverseExpr' to replace --- the 'Identifier' recursively. -idTrans :: Identifier -> Expr -> Expr -> Expr -idTrans i expr (Id id') | id' == i = expr - | otherwise = Id id' -idTrans _ _ e = e - --- | Replaces the identifier recursively in an expression. -replace :: Identifier -> Expr -> Expr -> Expr -replace = (transformOf traverseExpr .) . idTrans - --- | Nest expressions for a specific 'Identifier'. If the 'Identifier' is not --- found, the AST is not changed. --- --- This could be improved by instead of only using the last assignment to the --- wire that one finds, to use the assignment to the wire before the current --- expression. This would require a different approach though. -nestId :: Identifier -> ModDecl -> ModDecl -nestId i m - | not $ inPort i m - = let expr = fromMaybe def . findAssign i $ m ^. modItems in m & get %~ replace i expr - | otherwise - = m - where - get = modItems . traverse . _ModCA . contAssignExpr - def = Id i - --- | Replaces an identifier by a expression in all the module declaration. -nestSource :: Identifier -> VerilogSrc -> VerilogSrc -nestSource i src = src & getVerilogSrc . traverse . getDescription %~ nestId i - --- | Nest variables in the format @w[0-9]*@ up to a certain number. -nestUpTo :: Int -> VerilogSrc -> VerilogSrc -nestUpTo i src = foldl (flip nestSource) src $ Identifier . fromNode <$> [1 .. i] - -allVars :: ModDecl -> [Identifier] -allVars m = (m ^.. modOutPorts . traverse . portName) ++ (m ^.. modInPorts . traverse . portName) --- $setup --- >>> let m = (ModDecl (Identifier "m") [Port Wire 5 (Identifier "y")] [Port Wire 5 "x"] []) --- >>> let main = (ModDecl "main" [] [] []) - --- | Add a Module Instantiation using 'ModInst' from the first module passed to --- it to the body of the second module. It first has to make all the inputs into --- @reg@. --- --- >>> render $ instantiateMod m main --- module main; --- wire [4:0] y; --- reg [4:0] x; --- m m1(y, x); --- endmodule --- -instantiateMod :: ModDecl -> ModDecl -> ModDecl -instantiateMod m main = main & modItems %~ ((out ++ regIn ++ [inst]) ++) - where - out = Decl Nothing <$> m ^. modOutPorts - regIn = Decl Nothing <$> (m ^. modInPorts & traverse . portType .~ Reg False) - inst = ModInst (m ^. modId) (m ^. modId <> (Identifier . showT $ count + 1)) conns - count = length . filter (== m ^. modId) $ main ^.. modItems . traverse . modInstId - conns = ModConn . Id <$> allVars m - --- | Instantiate without adding wire declarations. It also does not count the --- current instantiations of the same module. --- --- >>> render $ instantiateMod_ m --- m m(y, x); --- -instantiateMod_ :: ModDecl -> ModItem -instantiateMod_ m = ModInst (m ^. modId) (m ^. modId) conns - where - conns = - ModConn - . Id - <$> (m ^.. modOutPorts . traverse . portName) - ++ (m ^.. modInPorts . traverse . portName) - --- | Instantiate without adding wire declarations. It also does not count the --- current instantiations of the same module. --- --- >>> render $ instantiateModSpec_ "_" m --- m m(.y(y), .x(x)); --- -instantiateModSpec_ :: Text -> ModDecl -> ModItem -instantiateModSpec_ outChar m = ModInst (m ^. modId) (m ^. modId) conns - where - conns = - zipWith ModConnNamed ids (Id <$> instIds) - ids = (filterChar outChar $ name modOutPorts) ++ (name modInPorts) - instIds = (name modOutPorts) ++ (name modInPorts) - name v = m ^.. v . traverse . portName - -filterChar :: Text -> [Identifier] -> [Identifier] -filterChar t ids = - ids & traverse . getIdentifier %~ (\x -> fromMaybe x . safe head $ T.splitOn t x) - --- | Initialise all the inputs and outputs to a module. --- --- >>> render $ initMod m --- module m(y, x); --- output wire [4:0] y; --- input wire [4:0] x; --- endmodule --- -initMod :: ModDecl -> ModDecl -initMod m = m & modItems %~ ((out ++ inp) ++) - where - out = Decl (Just PortOut) <$> (m ^. modOutPorts) - inp = Decl (Just PortIn) <$> (m ^. modInPorts) - -makeIdFrom :: (Show a) => a -> Identifier -> Identifier -makeIdFrom a i = (i <>) . Identifier . ("_" <>) $ showT a - --- | Make top level module for equivalence verification. Also takes in how many --- modules to instantiate. -makeTop :: Int -> ModDecl -> ModDecl -makeTop i m = ModDecl (m ^. modId) ys (m ^. modInPorts) modIt - where - ys = Port Wire 90 . flip makeIdFrom "y" <$> [1 .. i] - modIt = instantiateModSpec_ "_" . modN <$> [1 .. i] - modN n = m & modId %~ makeIdFrom n & modOutPorts .~ [Port Wire 90 (makeIdFrom n "y")] - -makeTopAssert :: ModDecl -> ModDecl -makeTopAssert = (modItems %~ (++ [assert])) . (modInPorts %~ addClk) . makeTop 2 - where - assert = Always . EventCtrl e . Just $ SeqBlock - [TaskEnable $ Task "assert" [BinOp (Id "y_1") BinEq (Id "y_2")]] - e = EPosEdge "clk" - addClk = ((Port Wire 1 "clk") :) diff --git a/src/VeriFuzz/Xst.hs b/src/VeriFuzz/Xst.hs new file mode 100644 index 0000000..52272c3 --- /dev/null +++ b/src/VeriFuzz/Xst.hs @@ -0,0 +1,57 @@ +{-| +Module : VeriFuzz.Simulator.Xst +Description : Xst (ise) simulator implementation. +Copyright : (c) 2018-2019, Yann Herklotz Grave +License : BSD-3 +Maintainer : ymherklotz [at] gmail [dot] com +Stability : experimental +Portability : POSIX + +Xst (ise) simulator implementation. +-} + +{-# LANGUAGE QuasiQuotes #-} + +module VeriFuzz.Simulator.Xst where + +import Control.Lens hiding ((<.>)) +import qualified Data.Text as T +import Prelude hiding (FilePath) +import Shelly +import System.FilePath.Posix (takeBaseName) +import Text.Shakespeare.Text (st) +import VeriFuzz.Simulator.General +import VeriFuzz.Simulator.Internal.Template +import VeriFuzz.Verilog +import VeriFuzz.Verilog + +data Xst = Xst { xstPath :: FilePath + , netgenPath :: FilePath + } + +instance Simulator Xst where + toText _ = "xst" + +instance Synthesize Xst where + runSynth = runSynthXst + +defaultXst :: Xst +defaultXst = + Xst "/opt/Xilinx/14.7/ISE_DS/ISE/bin/lin64/xst" "/opt/Xilinx/14.7/ISE_DS/ISE/bin/lin64/netgen" + +runSynthXst :: Xst -> ModDecl -> FilePath -> Sh () +runSynthXst sim m outf = do + writefile xstFile $ xstSynthConfig m + writefile prjFile [st|verilog work "rtl.v"|] + writefile "rtl.v" $ genSource m + echoP "Run xst" + noPrint $ timeout_ (xstPath sim) ["-ifn", toTextIgnore xstFile] + echoP "Run netgen" + noPrint $ run_ (netgenPath sim) + ["-w", "-ofmt", "verilog", toTextIgnore $ modFile <.> "ngc", toTextIgnore outf] + echoP "Clean synthesized file" + noPrint $ run_ "sed" ["-i", "/^`ifndef/,/^`endif/ d; s/ *Timestamp: .*//;", toTextIgnore outf] + where + modFile = fromText $ modName m + xstFile = modFile <.> "xst" + prjFile = modFile <.> "prj" diff --git a/src/VeriFuzz/Yosys.hs b/src/VeriFuzz/Yosys.hs new file mode 100644 index 0000000..e18de5a --- /dev/null +++ b/src/VeriFuzz/Yosys.hs @@ -0,0 +1,81 @@ +{-| +Module : VeriFuzz.Simulator.Yosys +Description : Yosys simulator implementation. +Copyright : (c) 2018-2019, Yann Herklotz Grave +License : BSD-3 +Maintainer : ymherklotz [at] gmail [dot] com +Stability : experimental +Portability : POSIX + +Yosys simulator implementation. +-} + +{-# LANGUAGE QuasiQuotes #-} + +module VeriFuzz.Simulator.Yosys where + +import Data.Maybe (fromMaybe) +import Data.Text (Text) +import qualified Data.Text as T +import Prelude hiding (FilePath) +import Shelly +import Text.Shakespeare.Text (st) +import VeriFuzz.Simulator.General +import VeriFuzz.Simulator.Internal.Template +import VeriFuzz.Verilog + +newtype Yosys = Yosys { yosysPath :: FilePath } + +instance Simulator Yosys where + toText _ = "yosys" + +instance Synthesize Yosys where + runSynth = runSynthYosys + +defaultYosys :: Yosys +defaultYosys = Yosys "/usr/bin/yosys" + +writeSimFile + :: Yosys -- ^ Simulator instance + -> ModDecl -- ^ Current module + -> FilePath -- ^ Output sim file + -> Sh () +writeSimFile _ m file = do + writefile "rtl.v" $ genSource m + writefile file yosysSimConfig + +runSynthYosys :: Yosys -> ModDecl -> FilePath -> Sh () +runSynthYosys sim m outf = do + writefile inpf $ genSource m + echoP "Run yosim" + noPrint $ run_ (yosysPath sim) ["-q", "-b", "verilog -noattr", "-o", out, "-S", inp] + where + inpf = "rtl.v" + inp = toTextIgnore inpf + out = toTextIgnore outf + -- ids = T.intercalate "," $ allVars m ^.. traverse . getIdentifier + +runMaybeSynth :: (Synthesize a) => Maybe a -> ModDecl -> Sh () +runMaybeSynth (Just sim) m = runSynth sim m $ fromText [st|syn_#{toText sim}.v|] +runMaybeSynth Nothing m = writefile "syn_rtl.v" $ genSource m + +runEquivYosys :: (Synthesize a, Synthesize b) => Yosys -> a -> Maybe b -> ModDecl -> Sh () +runEquivYosys yosys sim1 sim2 m = do + writefile "top.v" . genSource . initMod $ makeTop 2 m + writefile checkFile $ yosysSatConfig sim1 sim2 m + runSynth sim1 m $ fromText [st|syn_#{toText sim1}.v|] + runMaybeSynth sim2 m + echoP "Run yosys" + noPrint $ run_ (yosysPath yosys) [toTextIgnore checkFile] + where + checkFile = fromText [st|test.#{toText sim1}.#{maybe "rtl" toText sim2}.ys|] + +runEquiv :: (Synthesize a, Synthesize b) => Yosys -> a -> Maybe b -> ModDecl -> Sh () +runEquiv yosys sim1 sim2 m = do + root <- rootPath + writefile "top.v" . genSource . initMod $ makeTopAssert m + writefile "test.sby" $ sbyConfig root sim1 sim2 m + runSynth sim1 m $ fromText [st|syn_#{toText sim1}.v|] + runMaybeSynth sim2 m + echoP "Run SymbiYosys" + noPrint $ run_ "sby" ["test.sby"] -- cgit