From 4b29933ce947acb9da6fb1d3a61aae186e235843 Mon Sep 17 00:00:00 2001 From: Yann Herklotz Date: Mon, 31 Dec 2018 19:17:04 +0100 Subject: Remove sep and fromList in favour of fold --- src/Test/VeriFuzz/Graph/CodeGen.hs | 8 ++++---- src/Test/VeriFuzz/Internal/Shared.hs | 19 ------------------- src/Test/VeriFuzz/Verilog/CodeGen.hs | 6 +++--- 3 files changed, 7 insertions(+), 26 deletions(-) (limited to 'src') diff --git a/src/Test/VeriFuzz/Graph/CodeGen.hs b/src/Test/VeriFuzz/Graph/CodeGen.hs index eaa109e..5d3232c 100644 --- a/src/Test/VeriFuzz/Graph/CodeGen.hs +++ b/src/Test/VeriFuzz/Graph/CodeGen.hs @@ -30,7 +30,7 @@ toOperator Xor = " ^ " statList :: Gate -> [Node] -> Maybe Text statList g n = toStr <$> safe tail n where - toStr = fromList . fmap ((<> toOperator g) . fromNode) + toStr = fold . fmap ((<> toOperator g) . fromNode) lastEl :: [Node] -> Maybe Text lastEl n = fromNode <$> safe head n @@ -45,10 +45,10 @@ toStmnt graph (n, g) = generate :: (Graph gr) => gr Gate e -> Text generate graph = "module generated_module(\n" - <> fromList (imap " input wire " ",\n" inp) - <> sep ",\n" (imap " output wire " "" out) + <> fold (imap " input wire " ",\n" inp) + <> T.intercalate ",\n" (imap " output wire " "" out) <> ");\n" - <> fromList (toStmnt graph <$> labNodes graph) + <> fold (toStmnt graph <$> labNodes graph) <> "endmodule\n\nmodule main;\n initial\n begin\n " <> "$display(\"Hello, world\");\n $finish;\n " <> "end\nendmodule" diff --git a/src/Test/VeriFuzz/Internal/Shared.hs b/src/Test/VeriFuzz/Internal/Shared.hs index bf96509..54abb53 100644 --- a/src/Test/VeriFuzz/Internal/Shared.hs +++ b/src/Test/VeriFuzz/Internal/Shared.hs @@ -12,25 +12,6 @@ Shared high level code used in the other modules internally. module Test.VeriFuzz.Internal.Shared where -import Data.Maybe (fromMaybe) - --- | Fold up a list of Monoids using mappend and mempty as the first --- element. -fromList :: (Foldable t, Monoid a) => t a -> a -fromList = foldl mappend mempty - --- | Combine the Monoid elements of a list and insert the seperation symbol in --- between each element except the last one. -sep :: (Monoid a) => a -> [a] -> a -sep el l = fromMaybe mempty $ - (fromList . fmap (<>el) <$> safe init l) <> safe last l - --- | Alternative sep which returns the pattern if the list is empty. -sep_ :: (Monoid a) => a -> [a] -> a -sep_ el l - | null l = mempty - | otherwise = el <> sep el l - -- | Converts unsafe list functions in the Prelude to a safe version. safe :: ([a] -> b) -> [a] -> Maybe b safe _ [] = Nothing diff --git a/src/Test/VeriFuzz/Verilog/CodeGen.hs b/src/Test/VeriFuzz/Verilog/CodeGen.hs index 9e99f70..4fecaec 100644 --- a/src/Test/VeriFuzz/Verilog/CodeGen.hs +++ b/src/Test/VeriFuzz/Verilog/CodeGen.hs @@ -33,7 +33,7 @@ defMap stat = fromMaybe ";\n" $ genStmnt <$> stat -- | Convert the 'VerilogSrc' type to 'Text' so that it can be rendered. genVerilogSrc :: VerilogSrc -> Text genVerilogSrc source = - fromList $ genDescription <$> source ^. getVerilogSrc + fold $ genDescription <$> source ^. getVerilogSrc -- | Generate the 'Description' to 'Text'. genDescription :: Description -> Text @@ -51,7 +51,7 @@ genModuleDecl mod = ports | noIn && noOut = "" | otherwise = "(" <> (comma $ genModPort <$> outIn) <> ")" - modItems = fromList $ genModuleItem <$> mod ^. moduleItems + modItems = fold $ genModuleItem <$> mod ^. moduleItems noOut = null $ mod ^. modOutPorts noIn = null $ mod ^. modInPorts outIn = (mod ^. modOutPorts) ++ (mod ^. modInPorts) @@ -182,7 +182,7 @@ genStmnt :: Stmnt -> Text genStmnt (TimeCtrl d stat) = genDelay d <> " " <> defMap stat genStmnt (EventCtrl e stat) = genEvent e <> " " <> defMap stat genStmnt (SeqBlock s) = - "begin\n" <> fromList (genStmnt <$> s) <> "end\n" + "begin\n" <> fold (genStmnt <$> s) <> "end\n" genStmnt (BlockAssign a) = genAssign " = " a <> ";\n" genStmnt (NonBlockAssign a) = genAssign " <= " a <> ";\n" genStmnt (StatCA a) = genContAssign a -- cgit