From 2cda405afd09b9a9923526ffe49fa2ac2a5e1505 Mon Sep 17 00:00:00 2001 From: Yann Herklotz Date: Sat, 1 Dec 2018 17:53:13 +0000 Subject: Add all arbitrary instances and fix identifier --- src/Test/VeriFuzz/VerilogAST.hs | 80 +++++++++++++++++++++++++++++++++-------- 1 file changed, 65 insertions(+), 15 deletions(-) diff --git a/src/Test/VeriFuzz/VerilogAST.hs b/src/Test/VeriFuzz/VerilogAST.hs index 5fdb900..48d01a5 100644 --- a/src/Test/VeriFuzz/VerilogAST.hs +++ b/src/Test/VeriFuzz/VerilogAST.hs @@ -4,33 +4,29 @@ module Test.VeriFuzz.VerilogAST where import Control.Lens -import Data.Text as T -import Data.Text (Text) +import Data.Text as T +import Data.Text (Text) +import Test.QuickCheck as QC newtype Identifier = Identifier { _getIdentifier :: Text } deriving (Show) -makeLenses ''Identifier data Number = Number { _numSize :: Int , _numVal :: Int } deriving (Show) -makeLenses ''Number data BinaryOperator = BinAnd | BinOr | BinXor deriving (Show) -makeLenses ''BinaryOperator data UnaryOperator = UnNot | UnMinus deriving (Show) -makeLenses ''UnaryOperator data Primary = PrimNum Number | PrimId Identifier deriving (Show) -makeLenses ''Primary data Expression = PrimExpr Primary | UnPrimExpr { _exprUnOp :: UnaryOperator @@ -45,42 +41,96 @@ data Expression = PrimExpr Primary , _exprFalse :: Expression } deriving (Show) -makeLenses ''Expression data ContAssign = ContAssign { _contAssignNetLVal :: Identifier , _contAssignExpr :: Expression } deriving (Show) -makeLenses ''ContAssign data PortDir = Input | Output | InOut deriving (Show) -makeLenses ''PortDir data Port = Port { _portName :: Identifier , _portDir :: PortDir } deriving (Show) -makeLenses ''Port newtype ModuleItem = Assign ContAssign deriving (Show) -makeLenses ''ModuleItem -- | 'module' module_identifier [list_of_ports] ';' { module_item } 'end_module' data ModuleDecl = ModuleDecl { _moduleId :: Identifier , _modPorts :: [Port] , _moduleItems :: [ModuleItem] } deriving (Show) -makeLenses ''ModuleDecl newtype Description = Description { _getDescription :: ModuleDecl } deriving (Show) -makeLenses ''Description newtype SourceText = SourceText { _getSourceText :: [Description] } deriving (Show) + +-- Generate Arbitrary instances for the AST + +instance QC.Arbitrary Identifier where + arbitrary = Identifier . T.pack <$> + (QC.shuffle (['a'..'z'] <> ['A'..'Z']) >>= QC.sublistOf) + +instance QC.Arbitrary Number where + arbitrary = Number <$> QC.arbitrary <*> QC.arbitrary + +instance QC.Arbitrary BinaryOperator where + arbitrary = QC.elements [BinAnd, BinOr, BinXor] + +instance QC.Arbitrary UnaryOperator where + arbitrary = QC.elements [UnNot, UnMinus] + +instance QC.Arbitrary Primary where + arbitrary = PrimNum <$> QC.arbitrary + +instance QC.Arbitrary PortDir where + arbitrary = QC.elements [Input, Output, InOut] + +instance QC.Arbitrary Port where + arbitrary = Port <$> QC.arbitrary <*> QC.arbitrary + +instance QC.Arbitrary Expression where + arbitrary = QC.frequency [ (1, OpExpr <$> QC.arbitrary <*> QC.arbitrary <*> QC.arbitrary) + , (2, PrimExpr <$> arbitrary) + ] + +instance QC.Arbitrary ContAssign where + arbitrary = ContAssign <$> QC.arbitrary <*> QC.arbitrary + +instance QC.Arbitrary ModuleItem where + arbitrary = Assign <$> QC.arbitrary + +instance QC.Arbitrary ModuleDecl where + arbitrary = ModuleDecl <$> QC.arbitrary <*> QC.arbitrary <*> QC.arbitrary + +instance QC.Arbitrary Description where + arbitrary = Description <$> QC.arbitrary + +instance QC.Arbitrary SourceText where + arbitrary = SourceText <$> QC.arbitrary + +-- Create all the necessary lenses + +makeLenses ''Identifier +makeLenses ''Number makeLenses ''SourceText +makeLenses ''Description +makeLenses ''ModuleDecl +makeLenses ''ModuleItem +makeLenses ''Port +makeLenses ''PortDir +makeLenses ''BinaryOperator +makeLenses ''UnaryOperator +makeLenses ''Primary +makeLenses ''Expression +makeLenses ''ContAssign + +-- Helper functions for the AST numExpr :: Int -> Int -> Expression numExpr = ((PrimExpr . PrimNum) .) . Number @@ -92,4 +142,4 @@ setModName :: Text -> ModuleDecl -> ModuleDecl setModName str = moduleId .~ Identifier str addModPort :: Port -> ModuleDecl -> ModuleDecl -addModPort port = modPorts %~ ((:) port) +addModPort port = modPorts %~ (:) port -- cgit