From 4ecf423075f146ee0a1a452a5658e7a13f99aa9b Mon Sep 17 00:00:00 2001 From: Yann Herklotz Date: Mon, 13 May 2019 14:58:34 +0100 Subject: Use NonEmpty to represent concatenation --- src/VeriFuzz/Verilog/AST.hs | 24 ++++++++++++------------ src/VeriFuzz/Verilog/CodeGen.hs | 4 ++-- src/VeriFuzz/Verilog/Gen.hs | 4 ++-- 3 files changed, 16 insertions(+), 16 deletions(-) diff --git a/src/VeriFuzz/Verilog/AST.hs b/src/VeriFuzz/Verilog/AST.hs index 8adf58e..1957cb5 100644 --- a/src/VeriFuzz/Verilog/AST.hs +++ b/src/VeriFuzz/Verilog/AST.hs @@ -138,11 +138,11 @@ module VeriFuzz.Verilog.AST ) where -import Control.Lens +import Control.Lens hiding ((<|)) import Data.Data import Data.Data.Lens import Data.Functor.Foldable.TH (makeBaseFunctor) -import Data.List.NonEmpty (NonEmpty) +import Data.List.NonEmpty (NonEmpty (..), (<|)) import Data.String (IsString, fromString) import Data.Text (Text) import Data.Traversable (sequenceA) @@ -218,7 +218,7 @@ data Expr = Number {-# UNPACK #-} !BitVec | VecSelect {-# UNPACK #-} !Identifier !Expr | RangeSelect {-# UNPACK #-} !Identifier !Range -- ^ Symbols - | Concat ![Expr] + | Concat !(NonEmpty Expr) -- ^ Bit-wise concatenation of expressions represented by braces. | UnOp !UnaryOperator !Expr | BinOp !Expr !BinaryOperator !Expr @@ -238,12 +238,12 @@ instance Num Expr where 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] + (Concat a) <> b = Concat $ a <> (b :| []) + a <> (Concat b) = Concat $ a <| b + a <> b = Concat $ a <| b :| [] instance Monoid Expr where - mempty = Concat [] + mempty = Number 0 instance IsString Expr where fromString = Str . fromString @@ -254,7 +254,7 @@ instance Plated Expr where -- | Constant expression, which are known before simulation at compile time. data ConstExpr = ConstNum { _constNum :: {-# UNPACK #-} !BitVec } | ParamId { _constParamId :: {-# UNPACK #-} !Identifier } - | ConstConcat { _constConcat :: ![ConstExpr] } + | ConstConcat { _constConcat :: !(NonEmpty ConstExpr) } | ConstUnOp { _constUnOp :: !UnaryOperator , _constPrim :: !ConstExpr } @@ -299,12 +299,12 @@ instance Num ConstExpr where instance Semigroup ConstExpr where (ConstConcat a) <> (ConstConcat b) = ConstConcat $ a <> b - (ConstConcat a) <> b = ConstConcat $ a <> [b] - a <> (ConstConcat b) = ConstConcat $ a : b - a <> b = ConstConcat [a, b] + (ConstConcat a) <> b = ConstConcat $ a <> (b :| []) + a <> (ConstConcat b) = ConstConcat $ a <| b + a <> b = ConstConcat $ a <| b :| [] instance Monoid ConstExpr where - mempty = ConstConcat [] + mempty = ConstNum 0 instance IsString ConstExpr where fromString = ConstStr . fromString diff --git a/src/VeriFuzz/Verilog/CodeGen.hs b/src/VeriFuzz/Verilog/CodeGen.hs index 71ba162..3ff39d9 100644 --- a/src/VeriFuzz/Verilog/CodeGen.hs +++ b/src/VeriFuzz/Verilog/CodeGen.hs @@ -139,7 +139,7 @@ expr (Number b ) = showNum b expr (Id i ) = identifier i expr (VecSelect i e ) = hcat [identifier i, brackets $ expr e] expr (RangeSelect i r ) = hcat [identifier i, range r] -expr (Concat c ) = braces . nest 4 . sep $ punctuate comma (expr <$> c) +expr (Concat c ) = braces . nest 4 . sep . punctuate comma $ toList (expr <$> c) expr (UnOp u e ) = parens $ hcat [unaryOp u, expr e] expr (Cond l t f) = parens . nest 4 $ sep [expr l <+> "?", hsep [expr t, colon, expr f]] expr (Appl f e) = hcat [identifier f, parens $ expr e] @@ -155,7 +155,7 @@ showNum (BitVec s n) = constExpr :: ConstExpr -> Doc a constExpr (ConstNum b) = showNum b constExpr (ParamId i) = identifier i -constExpr (ConstConcat c) = braces . hsep $ punctuate comma (constExpr <$> c) +constExpr (ConstConcat c) = braces . hsep . punctuate comma $ toList (constExpr <$> c) constExpr (ConstUnOp u e) = parens $ hcat [unaryOp u, constExpr e] constExpr (ConstBinOp eRhs bin eLhs) = parens $ hsep [constExpr eRhs, binaryOp bin, constExpr eLhs] diff --git a/src/VeriFuzz/Verilog/Gen.hs b/src/VeriFuzz/Verilog/Gen.hs index 9a5b71d..630e3c0 100644 --- a/src/VeriFuzz/Verilog/Gen.hs +++ b/src/VeriFuzz/Verilog/Gen.hs @@ -174,7 +174,7 @@ constExprWithContext ps prob size , ( prob ^. probExprCond , ConstCond <$> subexpr 2 <*> subexpr 2 <*> subexpr 2 ) - , (prob ^. probExprConcat, ConstConcat <$> Hog.list (Hog.linear 1 10) (subexpr 2)) + , (prob ^. probExprConcat, ConstConcat <$> Hog.nonEmpty (Hog.linear 0 10) (subexpr 2)) ] | otherwise = constExprWithContext ps prob 0 where subexpr y = constExprWithContext ps prob $ size `div` y @@ -185,7 +185,7 @@ exprSafeList prob = [(prob ^. probExprNum, Number <$> genBitVec)] exprRecList :: ProbExpr -> (Hog.Size -> Gen Expr) -> [(Int, Gen Expr)] exprRecList prob subexpr = [ (prob ^. probExprNum , Number <$> genBitVec) - , (prob ^. probExprConcat , Concat <$> Hog.list (Hog.linear 1 10) (subexpr 2)) + , (prob ^. probExprConcat , Concat <$> Hog.nonEmpty (Hog.linear 0 10) (subexpr 2)) , (prob ^. probExprUnOp , UnOp <$> unOp <*> subexpr 2) , (prob ^. probExprStr, Str <$> Hog.text (Hog.linear 0 100) Hog.alphaNum) , (prob ^. probExprBinOp , BinOp <$> subexpr 2 <*> binOp <*> subexpr 2) -- cgit