From 4d3fb9ff1b58e07cbfaa5ba80505dbbb59cf74d7 Mon Sep 17 00:00:00 2001 From: BasicEC Date: Sun, 12 Jun 2022 17:51:43 +0300 Subject: [PATCH] Synthesis uarch automatically Related #157 --- README.md | 2 +- app/Main.hs | 33 ++++++- examples/microarch.toml | 49 +++++---- src/NITTA/Model/Microarchitecture/Config.hs | 99 ++++++++++++------- src/NITTA/Model/Networks/Bus.hs | 3 + src/NITTA/Model/ProcessorUnits/Types.hs | 4 + src/NITTA/Model/TargetSystem.hs | 1 + src/NITTA/Synthesis/Method.hs | 3 +- src/NITTA/Synthesis/Steps/Allocation.hs | 7 +- src/NITTA/Synthesis/Steps/Dataflow.hs | 50 +++++++--- src/NITTA/UIBackend/ViewHelper.hs | 1 + .../Model/ProcessorUnits/Tests/DSL/Tests.hs | 93 ++++++++++++----- web/src/components/SubforestTables.tsx | 1 + 13 files changed, 246 insertions(+), 100 deletions(-) diff --git a/README.md b/README.md index 4fef16679..b68ce8f9b 100644 --- a/README.md +++ b/README.md @@ -171,7 +171,7 @@ $ find src -name '*.hs' -exec grep -l '>>>' {} \; | xargs -t -L 1 -P 4 stack exe # | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ $ stack exec ghc-pkg unregister interpolate -- --force -# run formolu for all files +# run fourmolu for all files $ find . -name '*.hs' | xargs fourmolu -m inplace # show modules dependency diff --git a/app/Main.hs b/app/Main.hs index 4ea0db1ef..3813079a9 100644 --- a/app/Main.hs +++ b/app/Main.hs @@ -21,7 +21,6 @@ import Control.Exception import Control.Monad (when) import Data.ByteString.Lazy.Char8 qualified as BS import Data.Default (def) -import Data.Functor import Data.Maybe import Data.Proxy import Data.String.Utils qualified as S @@ -57,6 +56,7 @@ import Text.Regex data Nitta = Nitta { filename :: FilePath , uarch :: Maybe FilePath + , auto_uarch :: Bool , type_ :: Maybe String , io_sync :: Maybe IOSynchronization , port :: Int @@ -93,6 +93,11 @@ nittaArgs = &= explicit &= name "uarch" &= groupname "Target system configuration" + , auto_uarch = + False + &= help "Use empty microarchitecture and allocate PUs during synthesis process." + &= name "auto-uarch" + &= groupname "Target system configuration" , type_ = Nothing &= name "t" @@ -162,6 +167,7 @@ main = do ( Nitta filename uarch + auto_uarch type_ io_sync port @@ -180,7 +186,7 @@ main = do toml <- case uarch of Nothing -> return Nothing - Just path -> T.readFile path <&> (Just . getToml) + Just path -> Just . getToml <$> T.readFile path let fromConf s = getFromTomlSection s =<< toml let exactFrontendType = identifyFrontendType filename frontend_language @@ -194,7 +200,14 @@ main = do received = [("u#0", map (\i -> read $ show $ sin ((2 :: Double) * 3.14 * 50 * 0.001 * i)) [0 .. toEnum n])] ioSync = fromJust $ io_sync <|> fromConf "ioSync" <|> Just Sync confMa = toml >>= Just . mkMicroarchitecture ioSync - ma = fromJust $ confMa <|> Just (defMicroarch ioSync) :: BusNetwork T.Text T.Text (Attr (FX m b)) Int + ma + | auto_uarch && isJust confMa = + error $ + "auto_uarch flag means that an empty uarch with default prototypes will be used. " + <> "Remove uarch flag or specify prototypes list in config file and remove auto_uarch." + | auto_uarch = microarchWithProtos ioSync :: BusNetwork T.Text T.Text (Attr (FX m b)) Int + | isJust confMa = fromJust confMa + | otherwise = defMicroarch ioSync infoM "NITTA" $ "will trace: " <> S.join ", " (map (show . tvVar) frTrace) @@ -300,3 +313,17 @@ defMicroarch ioSync = defineNetwork "net1" ioSync $ do , slave_sclk = InputPortTag "sclk" , slave_cs = InputPortTag "cs" } + +microarchWithProtos ioSync = defineNetwork "net1" ioSync $ do + addCustomPrototype "fram{x}" (framWithSize 32) FramIO + addPrototype "shift{x}" ShiftIO + addPrototype "mul{x}" MultiplierIO + addPrototype "accum{x}" AccumIO + addPrototype "div{x}" DividerIO + add "spi" $ -- use addPrototype when https://github.com/ryukzak/nitta/issues/194 will be fixed + SPISlave + { slave_mosi = InputPortTag "mosi" + , slave_miso = OutputPortTag "miso" + , slave_sclk = InputPortTag "sclk" + , slave_cs = InputPortTag "cs" + } diff --git a/examples/microarch.toml b/examples/microarch.toml index ffb786c25..2e19d8746 100644 --- a/examples/microarch.toml +++ b/examples/microarch.toml @@ -4,44 +4,43 @@ ioSync = "Sync" [[networks]] name = "net1" -[[networks.pus]] -type = "Fram" -name = "fram1" -size = 16 +# Array of PUs [[networks.pus]] +type = "SPI" +name = "spi" +mosi = "mosi" +miso = "miso" +sclk = "sclk" +cs = "cs" +isSlave = true +bufferSize = 6 +bounceFilter = 0 + +# Array of PU prototypes + +[[networks.protos]] type = "Fram" -name = "fram2" +name = "fram{x}" # If you want a PU can be allocated only once, remove {x} from the PU name. size = 32 -[[networks.pus]] +[[networks.protos]] type = "Shift" -name = "shift" +name = "shift{x}" sRight = true -[[networks.pus]] +[[networks.protos]] type = "Multiplier" -name = "mul" +name = "mul{x}" mock = true -[[networks.pus]] +[[networks.protos]] type = "Accum" -name = "accum" +name = "accum{x}" isInt = true -[[networks.pus]] +[[networks.protos]] type = "Divider" -name = "div" +name = "div{x}" mock = true -pipeline = 4 - -[[networks.pus]] -type = "SPI" -name = "spi" -mosi = "mosi" -miso = "miso" -sclk = "sclk" -cs = "cs" -isSlave = true -bufferSize = 6 -bounceFilter = 0 +pipeline = 4 \ No newline at end of file diff --git a/src/NITTA/Model/Microarchitecture/Config.hs b/src/NITTA/Model/Microarchitecture/Config.hs index bbe04954c..bdc2b6f27 100644 --- a/src/NITTA/Model/Microarchitecture/Config.hs +++ b/src/NITTA/Model/Microarchitecture/Config.hs @@ -1,18 +1,41 @@ {-# LANGUAGE DuplicateRecordFields #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE PartialTypeSignatures #-} +{-# OPTIONS_GHC -Wno-unrecognised-pragmas #-} + +{-# HLINT ignore "Use forM_" #-} module NITTA.Model.Microarchitecture.Config ( mkMicroarchitecture, ) where -import Data.Aeson -import Data.Default +import Control.Monad.State (when) +import Data.Aeson ( + FromJSON (parseJSON), + Options (sumEncoding), + SumEncoding (TaggedObject, contentsFieldName, tagFieldName), + ToJSON (toJSON), + defaultOptions, + genericParseJSON, + genericToJSON, + ) +import Data.Default (Default (def)) +import Data.HashMap.Internal.Strict (HashMap) +import Data.Maybe (fromJust, isJust) import Data.Text qualified as T -import GHC.Generics -import NITTA.Model.Networks.Bus +import GHC.Generics (Generic) +import NITTA.Intermediate.Value (Val) +import NITTA.Intermediate.Variable (Var) +import NITTA.Model.Networks.Bus ( + BusNetwork, + addCustom, + addCustomPrototype, + busNetwork, + modifyNetwork, + ) +import NITTA.Model.Networks.Types (IOSynchronization) import NITTA.Model.ProcessorUnits qualified as PU -import NITTA.Utils +import NITTA.Utils (getFromToml) data PUConf = Accum @@ -58,34 +81,10 @@ instance ToJSON PUConf where instance FromJSON PUConf where parseJSON = genericParseJSON puConfJsonOptions -build NetworkConf{pus} = do mapM_ addPU pus - where - addPU Accum{name} = addCustom name def PU.AccumIO - addPU Divider{name, pipeline, mock} = addCustom name (PU.divider pipeline mock) PU.DividerIO - addPU Multiplier{name, mock} = addCustom name (PU.multiplier mock) PU.MultiplierIO - addPU Fram{name, size} = addCustom name (PU.framWithSize size) PU.FramIO - addPU Shift{name, sRight} = addCustom name (PU.shift $ Just False /= sRight) PU.ShiftIO - addPU SPI{name, mosi, miso, sclk, cs, isSlave, bounceFilter, bufferSize} = - addCustom name (PU.anySPI bounceFilter bufferSize) $ - if isSlave - then - PU.SPISlave - { slave_mosi = PU.InputPortTag mosi - , slave_miso = PU.OutputPortTag miso - , slave_sclk = PU.InputPortTag sclk - , slave_cs = PU.InputPortTag cs - } - else - PU.SPIMaster - { master_mosi = PU.OutputPortTag mosi - , master_miso = PU.InputPortTag miso - , master_sclk = PU.OutputPortTag sclk - , master_cs = PU.OutputPortTag cs - } - data NetworkConf = NetworkConf { name :: T.Text - , pus :: [PUConf] + , pus :: Maybe [PUConf] + , protos :: Maybe [PUConf] } deriving (Generic, Show) @@ -100,9 +99,39 @@ newtype MicroarchitectureConf = MicroarchitectureConf instance FromJSON MicroarchitectureConf instance ToJSON MicroarchitectureConf +mkMicroarchitecture :: (Val v, Var x, ToJSON a, ToJSON x) => IOSynchronization -> HashMap T.Text a -> BusNetwork T.Text x v Int mkMicroarchitecture ioSync toml = - let ns = networks (getFromToml toml :: MicroarchitectureConf) - mkNetwork net@NetworkConf{name} = defineNetwork name ioSync $ build net - in if length ns > 1 + let addPU proto + | proto = addCustomPrototype + | otherwise = addCustom + build NetworkConf{pus, protos} = do + when (isJust pus) $ mapM_ (configure False) $ fromJust pus + when (isJust protos) $ mapM_ (configure True) $ fromJust protos + where + configure proto Accum{name} = addPU proto name def PU.AccumIO + configure proto Divider{name, pipeline, mock} = addPU proto name (PU.divider pipeline mock) PU.DividerIO + configure proto Multiplier{name, mock} = addPU proto name (PU.multiplier mock) PU.MultiplierIO + configure proto Fram{name, size} = addPU proto name (PU.framWithSize size) PU.FramIO + configure proto Shift{name, sRight} = addPU proto name (PU.shift $ Just False /= sRight) PU.ShiftIO + configure proto SPI{name, mosi, miso, sclk, cs, isSlave, bounceFilter, bufferSize} = + addPU proto name (PU.anySPI bounceFilter bufferSize) $ + if isSlave + then + PU.SPISlave + { slave_mosi = PU.InputPortTag mosi + , slave_miso = PU.OutputPortTag miso + , slave_sclk = PU.InputPortTag sclk + , slave_cs = PU.InputPortTag cs + } + else + PU.SPIMaster + { master_mosi = PU.OutputPortTag mosi + , master_miso = PU.InputPortTag miso + , master_sclk = PU.OutputPortTag sclk + , master_cs = PU.OutputPortTag cs + } + nets = networks (getFromToml toml :: MicroarchitectureConf) + mkNetwork net@NetworkConf{name} = modifyNetwork (busNetwork name ioSync) (build net) + in if length nets > 1 then error "multi-networks are not currently supported" - else mkNetwork (head ns) + else mkNetwork (head nets) diff --git a/src/NITTA/Model/Networks/Bus.hs b/src/NITTA/Model/Networks/Bus.hs index f85007548..6f0547a3d 100644 --- a/src/NITTA/Model/Networks/Bus.hs +++ b/src/NITTA/Model/Networks/Bus.hs @@ -279,6 +279,8 @@ instance (UnitTag tag, VarValTime v x t) => ProcessorUnit (BusNetwork tag v x t) parallelismType _ = error " not support parallelismType for BusNetwork" + puSize BusNetwork{bnPus} = sum $ map puSize $ M.elems bnPus + instance Controllable (BusNetwork tag v x t) where data Instruction (BusNetwork tag v x t) = Transport v tag tag @@ -845,6 +847,7 @@ modifyNetwork net@BusNetwork{bnPus, bnPUPrototypes, bnSignalBusWidth, bnEnv} bui defineNetwork bnName ioSync builder = modifyNetwork (busNetwork bnName ioSync) builder +addCustom :: forall tag v x t m pu. (MonadState (BuilderSt tag v x t) m, PUClasses pu v x t, UnitTag tag) => tag -> pu -> IOPorts pu -> m () addCustom tag pu ioPorts = do st@BuilderSt{signalBusWidth, availSignals, pus} <- get let ctrlPorts = takePortTags availSignals pu diff --git a/src/NITTA/Model/ProcessorUnits/Types.hs b/src/NITTA/Model/ProcessorUnits/Types.hs index a67a78ae6..4fd952ce5 100644 --- a/src/NITTA/Model/ProcessorUnits/Types.hs +++ b/src/NITTA/Model/ProcessorUnits/Types.hs @@ -130,6 +130,10 @@ class (VarValTime v x t) => ProcessorUnit u v x t | u -> v x t where parallelismType :: u -> ParallelismType parallelismType _ = None + -- |Provide the processor unit size. At the moment it's just the number of subprocessors + puSize :: u -> Float + puSize _ = 1 + bind f pu = case tryBind f pu of Right pu' -> pu' Left err -> error $ "can't bind function: " <> err diff --git a/src/NITTA/Model/TargetSystem.hs b/src/NITTA/Model/TargetSystem.hs index 863e296b4..bcccda532 100644 --- a/src/NITTA/Model/TargetSystem.hs +++ b/src/NITTA/Model/TargetSystem.hs @@ -58,6 +58,7 @@ instance tryBind f ts@TargetSystem{mUnit} = (\u -> ts{mUnit = u}) <$> tryBind f mUnit process TargetSystem{mUnit} = process mUnit parallelismType TargetSystem{mUnit} = parallelismType mUnit + puSize TargetSystem{mUnit} = puSize mUnit instance (BindProblem u tag v x) => BindProblem (TargetSystem u tag v x t) tag v x where bindOptions TargetSystem{mUnit} = bindOptions mUnit diff --git a/src/NITTA/Synthesis/Method.hs b/src/NITTA/Synthesis/Method.hs index 233d89ab4..72ee8e71a 100644 --- a/src/NITTA/Synthesis/Method.hs +++ b/src/NITTA/Synthesis/Method.hs @@ -125,6 +125,7 @@ allBestThreadIO n tree = do bestLeaf :: (VarValTime v x t, UnitTag tag) => DefTree tag v x t -> [DefTree tag v x t] -> DefTree tag v x t bestLeaf tree leafs = let successLeafs = filter (\node -> isComplete node && isLeaf node) leafs + target = sTarget . sState in case successLeafs of - _ : _ -> minimumOn (processDuration . sTarget . sState) successLeafs + _ : _ -> minimumOn (\l -> (processDuration $ target l, puSize $ target l)) successLeafs [] -> headDef tree leafs diff --git a/src/NITTA/Synthesis/Steps/Allocation.hs b/src/NITTA/Synthesis/Steps/Allocation.hs index c35fd4da8..805b6650a 100644 --- a/src/NITTA/Synthesis/Steps/Allocation.hs +++ b/src/NITTA/Synthesis/Steps/Allocation.hs @@ -85,4 +85,9 @@ instance , mAvgParallels = (fromIntegral (sum fCountByWaves) :: Float) / (fromIntegral numberOfProcessWaves :: Float) } - estimate _ctx _o _d AllocationMetrics{} = -1 + estimate _ctx _o _d AllocationMetrics{mParallelism, mMinPusForRemains, mAvgParallels} + | mMinPusForRemains == 0 = 5000 + | mParallelism == Full = -1 + | mParallelism == Pipeline && (mAvgParallels / mMinPusForRemains >= 3) = 4900 + | mAvgParallels / mMinPusForRemains >= 2 = 4900 + | otherwise = -1 diff --git a/src/NITTA/Synthesis/Steps/Dataflow.hs b/src/NITTA/Synthesis/Steps/Dataflow.hs index 73c6117eb..2f7941676 100644 --- a/src/NITTA/Synthesis/Steps/Dataflow.hs +++ b/src/NITTA/Synthesis/Steps/Dataflow.hs @@ -17,15 +17,35 @@ module NITTA.Synthesis.Steps.Dataflow ( import Data.Aeson (ToJSON) import Data.Set qualified as S -import GHC.Generics -import NITTA.Intermediate.Types -import NITTA.Model.Networks.Bus -import NITTA.Model.Problems.Dataflow -import NITTA.Model.Problems.Endpoint -import NITTA.Model.ProcessorUnits -import NITTA.Model.TargetSystem -import NITTA.Synthesis.Types -import NITTA.Utils +import GHC.Generics (Generic) +import NITTA.Intermediate.Analysis (ProcessWave (..)) +import NITTA.Intermediate.Types ( + Function (inputs), + Variables (variables), + WithFunctions (functions), + ) +import NITTA.Model.Networks.Bus (BusNetwork) +import NITTA.Model.Problems.Dataflow ( + DataflowProblem (dataflowDecision), + DataflowSt (..), + dataflowOption2decision, + ) +import NITTA.Model.Problems.Endpoint (EndpointSt (epAt)) +import NITTA.Model.ProcessorUnits.Types (UnitTag) +import NITTA.Model.TargetSystem (TargetSystem (mUnit)) +import NITTA.Model.Time (TimeConstraint (..), VarValTime) +import NITTA.Synthesis.Types ( + SynthesisDecisionCls (..), + SynthesisState ( + SynthesisState, + numberOfDataflowOptions, + processWaves, + sTarget, + transferableVars + ), + (), + ) +import NITTA.Utils.Base (unionsMap) import Numeric.Interval.NonEmpty (Interval, inf, sup) data DataflowMetrics = DataflowMetrics @@ -34,6 +54,8 @@ data DataflowMetrics = DataflowMetrics , pNotTransferableInputs :: [Float] -- ^number of variables, which is not transferable for affected -- functions. + , pWaveOfUse :: Float + -- ^number of the first wave in which one of the target variables is used } deriving (Generic) @@ -50,20 +72,23 @@ instance where decisions SynthesisState{sTarget} o = let d = dataflowOption2decision o in [(d, dataflowDecision sTarget d)] - parameters SynthesisState{transferableVars, sTarget} DataflowSt{dfSource, dfTargets} _ = + parameters SynthesisState{transferableVars, sTarget, processWaves} DataflowSt{dfSource, dfTargets} _ = let TimeConstraint{tcAvailable, tcDuration} = epAt $ snd dfSource + vs = unionsMap (variables . snd) dfTargets + lvs = length vs + waveNum = length . takeWhile (\ProcessWave{pwFs} -> lvs == length (vs `S.difference` unionsMap inputs pwFs)) $ processWaves in DataflowMetrics { pWaitTime = fromIntegral (inf tcAvailable) , pRestrictedTime = fromEnum (sup tcDuration) /= maxBound , pNotTransferableInputs = let fs = functions $ mUnit sTarget - vs = unionsMap (variables . snd) dfTargets affectedFunctions = filter (\f -> not $ null (inputs f `S.intersection` vs)) fs notTransferableVars = map (\f -> inputs f S.\\ transferableVars) affectedFunctions in map (fromIntegral . length) notTransferableVars + , pWaveOfUse = fromIntegral waveNum :: Float } - estimate SynthesisState{numberOfDataflowOptions} _o _d DataflowMetrics{pWaitTime, pNotTransferableInputs, pRestrictedTime} = + estimate SynthesisState{numberOfDataflowOptions} _o _d DataflowMetrics{pWaitTime, pNotTransferableInputs, pRestrictedTime, pWaveOfUse} = 2000 + (numberOfDataflowOptions >= threshold) 1000 @@ -72,5 +97,6 @@ instance - sum pNotTransferableInputs * 5 - pWaitTime + - pWaveOfUse threshold = 20 diff --git a/src/NITTA/UIBackend/ViewHelper.hs b/src/NITTA/UIBackend/ViewHelper.hs index 0617d35b8..dc3390d36 100644 --- a/src/NITTA/UIBackend/ViewHelper.hs +++ b/src/NITTA/UIBackend/ViewHelper.hs @@ -243,6 +243,7 @@ instance ToSample (NodeView tag v x t) where { pWaitTime = 1 , pRestrictedTime = False , pNotTransferableInputs = [0, 0] + , pWaveOfUse = 0 } , decision = DataflowDecisionView diff --git a/test/NITTA/Model/ProcessorUnits/Tests/DSL/Tests.hs b/test/NITTA/Model/ProcessorUnits/Tests/DSL/Tests.hs index 91dc9728b..3c659d5da 100644 --- a/test/NITTA/Model/ProcessorUnits/Tests/DSL/Tests.hs +++ b/test/NITTA/Model/ProcessorUnits/Tests/DSL/Tests.hs @@ -294,28 +294,77 @@ tests = , Pull $ O $ S.fromList ["d^0#2"] ] ] - , unitTestCase "target system: manual synthesis, allocation works correctly" def $ do - setNetwork $ - Bus.defineNetwork "net1" ASync $ do - Bus.addPrototype "fram{x}" FramIO - Bus.addPrototype "accum" AccumIO - setBusType pInt - assignLua - [__i| - function sum(a) - local d = a + 1 - sum(d) - end - sum(0) - |] - doAllocation "net1" "accum" - doAllocation "net1" "fram{x}" - assertAllocation 1 =<< mkAllocation "net1" "fram{x}" - assertAllocation 1 =<< mkAllocation "net1" "accum" - assertAllocationOptions =<< mkAllocationOptions "net1" ["fram{x}"] - assertPU "net1_accum" (Proxy :: Proxy (Accum T.Text Int Int)) - assertPU "net1_fram1" (Proxy :: Proxy (Fram T.Text Int Int)) - synthesizeAndCoSim + , testGroup + "Allocation synthesis step" + [ unitTestCase "target system: manual synthesis, allocation works correctly" def $ do + setNetwork $ + Bus.defineNetwork "net1" ASync $ do + Bus.addPrototype "fram{x}" FramIO + Bus.addPrototype "accum" AccumIO + setBusType pInt + assignLua + [__i| + function sum(a) + local d = a + 1 + sum(d) + end + sum(0) + |] + doAllocation "net1" "accum" + doAllocation "net1" "fram{x}" + assertAllocation 1 =<< mkAllocation "net1" "fram{x}" + assertAllocation 1 =<< mkAllocation "net1" "accum" + assertAllocationOptions =<< mkAllocationOptions "net1" ["fram{x}"] + assertPU "net1_accum" (Proxy :: Proxy (Accum T.Text Int Int)) + assertPU "net1_fram1" (Proxy :: Proxy (Fram T.Text Int Int)) + synthesizeAndCoSim + , unitTestCase "target system: autosynthesis, allocate required PUs" def $ do + setNetwork $ + Bus.defineNetwork "net1" ASync $ do + Bus.addCustomPrototype "fram{x}" (framWithSize 32) FramIO + Bus.addPrototype "accum{x}" AccumIO + Bus.addPrototype "mul{x}" MultiplierIO + Bus.add "spi" $ -- use addPrototype when https://github.com/ryukzak/nitta/issues/194 will be fixed + SPISlave + { slave_mosi = InputPortTag "mosi" + , slave_miso = OutputPortTag "miso" + , slave_sclk = InputPortTag "sclk" + , slave_cs = InputPortTag "cs" + } + setBusType pInt + assignLua + [__i| + function counter(x1) + send(x1) + x2 = x1 + 1 + counter(x2) + end + counter(0) + |] + synthesizeAndCoSim + assertAllocation 1 =<< mkAllocation "net1" "fram{x}" + assertAllocation 1 =<< mkAllocation "net1" "accum{x}" + assertAllocation 0 =<< mkAllocation "net1" "mul{x}" + , unitTestCase "target system: autosynthesis, allocation comes after constant folding" def $ do + setNetwork $ + Bus.defineNetwork "net1" ASync $ do + Bus.addCustomPrototype "fram{x}" (framWithSize 32) FramIO + Bus.addPrototype "accum{x}" AccumIO + Bus.addPrototype "mul{x}" MultiplierIO + setBusType pInt + assignLua + [__i| + function mul3(x1) + x1 = (1 + 1 + 1) * x1 + mul3(x1) + end + mul3(1) + |] + synthesizeAndCoSim + assertAllocation 1 =<< mkAllocation "net1" "fram{x}" + assertAllocation 1 =<< mkAllocation "net1" "mul{x}" + assertAllocation 0 =<< mkAllocation "net1" "accum{x}" + ] ] , testGroup "BusNetwork negative tests" diff --git a/web/src/components/SubforestTables.tsx b/web/src/components/SubforestTables.tsx index 33ae6be11..a08f44055 100644 --- a/web/src/components/SubforestTables.tsx +++ b/web/src/components/SubforestTables.tsx @@ -120,6 +120,7 @@ export const SubforestTables: FC = ({ nodes }) => { 60 ), textColumn("restricted", (e: Node) => String((e.parameters as DataflowMetrics).pRestrictedTime), 60), + textColumn("wave of use", (e: Node) => String((e.parameters as DataflowMetrics).pWaveOfUse), 60), detailColumn(), ]} />