diff --git a/src/NITTA/Intermediate/Types.hs b/src/NITTA/Intermediate/Types.hs index d4af7217d..effc52603 100644 --- a/src/NITTA/Intermediate/Types.hs +++ b/src/NITTA/Intermediate/Types.hs @@ -30,6 +30,7 @@ module NITTA.Intermediate.Types ( FView (..), packF, castF, + functionType, Function (..), Lock (..), Locks (..), @@ -194,6 +195,9 @@ data F v x where packF f = F{fun = f, funHistory = []} +functionType :: F v x -> TypeRep +functionType F{fun} = typeOf fun + instance Eq (F v x) where F{fun = a} == F{fun = b} | typeOf a == typeOf b = a == fromJust (cast b) diff --git a/src/NITTA/Model/Networks/Bus.hs b/src/NITTA/Model/Networks/Bus.hs index ccbedba98..ec1b76fc8 100644 --- a/src/NITTA/Model/Networks/Bus.hs +++ b/src/NITTA/Model/Networks/Bus.hs @@ -299,25 +299,116 @@ instance {-# OVERLAPS #-} ByTime (BusNetwork tag v x t) t where ---------------------------------------------------------------------- +cartesianProduct :: [[a]] -> [[a]] +cartesianProduct [] = [[]] +cartesianProduct (xs : xss) = [x : ys | x <- xs, ys <- cartesianProduct xss] + +{- | Not all bindings can be applied to unit a the same time. E.g.: + + - @b = reg(a)@ + - @c = reg(b)@ + + Can't be binded to same unit because it require self sending of data. + + In this case, we just throw away conflicted bindings. +-} +fixGroupBinding :: (UnitTag tag, VarValTime v x t) => BusNetwork tag v x t -> [(tag, F v x)] -> [(tag, F v x)] +fixGroupBinding _bn [] = [] +fixGroupBinding bn@BusNetwork{bnPus} (b@(uTag, f) : binds) + | Right _ <- tryBind f (bnPus M.! uTag) = b : fixGroupBinding (bindDecision bn $ SingleBind uTag f) binds + | otherwise = fixGroupBinding bn binds + +mergeFunctionWithSameType = True + +{- | GroupBindHash required to find equal from task point of view bindings. + E.g. (we have 2 units and 3 functions with the same type): + @u1 <- f1, f2, f3; u2 <- _ === u1 <- _; u2 <- f1, f2, f3@ because all + task will performing by one unit and it is not matter which one. + + Corner cases: + + - not all group binding are correct (e.g. self sending) + + - we can't wait that unit is empty + + - Combination like: `u1 <- f1, f2; u2 <- f3 !== u1 <- f1, f3; u2 <- f2` are not + equal because we don't take into accout their place in DFG. +-} +bindsHash :: UnitTag k => BusNetwork k v x t -> [(k, F v x)] -> S.Set (TypeRep, Int, S.Set String) +bindsHash BusNetwork{bnPus, bnBinded} binds = + let distribution = binds2bindGroup binds + in S.fromList + $ map + ( \(tag, fs) -> + let + u = bnPus M.! tag + binded = maybe 0 length $ bnBinded M.!? tag + fs' = + S.fromList $ + if mergeFunctionWithSameType + then -- TODO: merge only functions without + -- inputs, because they are equal from + -- scheduling point of view + + -- TODO: other way to reduce number of + -- combinations + map (show . (\lst -> (head lst, length lst))) (L.group $ map functionType fs) + else map show fs + in + (unitType u, binded, fs') + ) + $ M.assocs distribution + +nubNotObliviousBinds :: UnitTag k => BusNetwork k v x t -> [[(k, F v x)]] -> [[(k, F v x)]] +nubNotObliviousBinds bn bindss = + let hashed = map (\binds -> (bindsHash bn binds, binds)) bindss + in M.elems $ M.fromList hashed + instance (UnitTag tag, VarValTime v x t) => BindProblem (BusNetwork tag v x t) tag v x where - bindOptions BusNetwork{bnRemains, bnPus} = concatMap optionsFor bnRemains + bindOptions bn@BusNetwork{bnRemains, bnPus} = + let binds = map optionsFor bnRemains + + -- oblivious mean we have only one option to bind function + obliviousBinds = concat $ filter ((== 1) . length) binds + singleAssingmentBinds + | null obliviousBinds = [] + | otherwise = [GroupBind True $ binds2bindGroup obliviousBinds] + + notObliviousBinds :: [[(tag, F v x)]] + notObliviousBinds = filter ((> 1) . length) binds + -- TODO: split them on independent bindGroups. It should + -- significantly reduce complexity. + multiBinds :: [Bind tag v x] + multiBinds + | null notObliviousBinds = [] + | otherwise = + map (GroupBind False . binds2bindGroup) $ + filter ((> 1) . length) $ + map (fixGroupBinding bn) $ + nubNotObliviousBinds bn $ + cartesianProduct notObliviousBinds + + simpleBinds = concatMap (map $ uncurry SingleBind) binds + in singleAssingmentBinds <> multiBinds <> simpleBinds where optionsFor f = - [ Bind f puTitle - | (puTitle, pu) <- M.assocs bnPus + [ (tag, f) + | (tag, pu) <- M.assocs bnPus , allowToProcess f pu ] - bindDecision bn@BusNetwork{bnProcess, bnPus, bnBinded, bnRemains} (Bind f tag) = + bindDecision bn@BusNetwork{bnProcess, bnPus, bnBinded, bnRemains} (SingleBind tag f) = bn { bnPus = M.adjust (bind f) tag bnPus , bnBinded = registerBinding tag f bnBinded , bnProcess = execScheduleWithProcess bn bnProcess $ scheduleFunctionBind f , bnRemains = filter (/= f) bnRemains } + bindDecision bn@BusNetwork{} GroupBind{bindGroup} = + foldl bindDecision bn $ concatMap (\(tag, fs) -> map (SingleBind tag) fs) $ M.assocs bindGroup instance (UnitTag tag, VarValTime v x t) => BreakLoopProblem (BusNetwork tag v x t) v x where breakLoopOptions BusNetwork{bnPus} = concatMap breakLoopOptions $ M.elems bnPus diff --git a/src/NITTA/Model/Networks/Types.hs b/src/NITTA/Model/Networks/Types.hs index 32000a304..3ab0de837 100644 --- a/src/NITTA/Model/Networks/Types.hs +++ b/src/NITTA/Model/Networks/Types.hs @@ -12,6 +12,7 @@ Stability : experimental -} module NITTA.Model.Networks.Types ( PU (..), + unitType, PUClasses, IOSynchronization (..), PUPrototype (..), @@ -50,6 +51,7 @@ type PUClasses pu v x t = , Controllable pu , IOTestBench pu v x , Locks pu v + , Typeable pu ) -- | Existential container for a processor unit . @@ -62,6 +64,9 @@ data PU v x t where } -> PU v x t +unitType :: PU v x t -> TypeRep +unitType PU{unit} = typeOf unit + instance Ord v => EndpointProblem (PU v x t) v t where endpointOptions PU{diff, unit} = map (patch diff) $ endpointOptions unit diff --git a/src/NITTA/Model/Problems/Bind.hs b/src/NITTA/Model/Problems/Bind.hs index f5a734bd6..3d18ab1a8 100644 --- a/src/NITTA/Model/Problems/Bind.hs +++ b/src/NITTA/Model/Problems/Bind.hs @@ -12,22 +12,60 @@ Stability : experimental module NITTA.Model.Problems.Bind ( Bind (..), BindProblem (..), + binds2bindGroup, ) where +import Data.Map.Strict qualified as M import Data.String.ToString +import Data.String.Utils qualified as S import GHC.Generics import NITTA.Intermediate.Types +import NITTA.Model.ProcessorUnits.Types (UnitTag) +import NITTA.Utils.Base (unionsMap) data Bind tag v x - = Bind (F v x) tag + = SingleBind tag (F v x) + | GroupBind {isObliviousBinds :: Bool, bindGroup :: M.Map tag [F v x]} deriving (Generic, Eq) -instance ToString tag => Show (Bind tag v x) where - show (Bind f tag) = "Bind " <> show f <> " " <> toString tag +binds2bindGroup :: UnitTag tag => [(tag, F v x)] -> M.Map tag [F v x] +binds2bindGroup binds = + foldl + ( \st (tag, f) -> + M.alter + ( \case + (Just fs) -> Just $ f : fs + Nothing -> Just [f] + ) + tag + st + ) + M.empty + binds + +instance UnitTag tag => Show (Bind tag v x) where + show (SingleBind uTag f) = "Bind " <> showFAndTag (f, uTag) + show (GroupBind{isObliviousBinds, bindGroup}) = + concat + [ "Binds " + , if isObliviousBinds then "obliviousBinds " else "" + , S.join "; " (map showFsAndTag $ M.assocs bindGroup) + ] + +showFAndTag :: UnitTag tag => (F v x, tag) -> String +showFAndTag (f, tag) = toString tag <> " <- " <> show f + +showFsAndTag :: (ToString a1, Show a2) => (a1, [a2]) -> String +showFsAndTag (tag, fs) = toString tag <> " <- " <> S.join ", " (map show fs) class BindProblem u tag v x | u -> tag v x where bindOptions :: u -> [Bind tag v x] bindDecision :: u -> Bind tag v x -> u instance Var v => Variables (Bind tab v x) v where - variables (Bind f _tag) = variables f + variables (SingleBind _tag f) = variables f + variables GroupBind{bindGroup} = unionsMap variables $ concat $ M.elems bindGroup + +instance WithFunctions (Bind tag v x) (F v x) where + functions (SingleBind _tag f) = [f] + functions GroupBind{bindGroup} = concat $ M.elems bindGroup diff --git a/src/NITTA/Model/Problems/ViewHelper.hs b/src/NITTA/Model/Problems/ViewHelper.hs index f63b25985..f658a0454 100644 --- a/src/NITTA/Model/Problems/ViewHelper.hs +++ b/src/NITTA/Model/Problems/ViewHelper.hs @@ -10,7 +10,9 @@ module NITTA.Model.Problems.ViewHelper ( ) where import Data.Aeson -import Data.Bifunctor +import Data.Bifunctor (Bifunctor (bimap)) +import Data.HashMap.Strict qualified as HM +import Data.Map.Strict qualified as M import Data.Set qualified as S import Data.Text qualified as T import GHC.Generics @@ -31,10 +33,13 @@ instance ToJSON IntervalView data DecisionView = RootView - | BindDecisionView + | SingleBindView { function :: FView , pu :: T.Text } + | GroupBindView + { bindGroup :: HM.HashMap T.Text [FView] + } | AllocationView { networkTag :: T.Text , processUnitTag :: T.Text @@ -63,11 +68,12 @@ data DecisionView deriving (Generic) instance UnitTag tag => Viewable (Bind tag v x) DecisionView where - view (Bind f pu) = - BindDecisionView + view (SingleBind uTag f) = + SingleBindView { function = view f - , pu = toText pu + , pu = toText uTag } + view GroupBind{bindGroup} = GroupBindView $ HM.fromList $ map (bimap toText (map view)) $ M.assocs bindGroup instance UnitTag tag => Viewable (Allocation tag) DecisionView where view Allocation{networkTag, processUnitTag} = diff --git a/src/NITTA/Synthesis/Analysis.hs b/src/NITTA/Synthesis/Analysis.hs index 371cf863a..9baf5abaa 100644 --- a/src/NITTA/Synthesis/Analysis.hs +++ b/src/NITTA/Synthesis/Analysis.hs @@ -13,63 +13,82 @@ module NITTA.Synthesis.Analysis ( import Control.Concurrent.STM import Data.HashMap.Strict qualified as HM +import Data.Maybe (isJust) import GHC.Generics -import NITTA.Model.TargetSystem (processDuration) +import NITTA.Model.ProcessorUnits.Types (NextTick) +import NITTA.Model.TargetSystem (TargetSystem, processDuration) +import NITTA.Model.Time (VarValTime) import NITTA.Synthesis.Types -- | Metrics of synthesis tree process data TreeInfo = TreeInfo - { nodes :: !Int - , success :: !Int - , failed :: !Int - , notProcessed :: !Int - , durationSuccess :: HM.HashMap Int Int - , stepsSuccess :: HM.HashMap Int Int + { nodesVisited :: !Int + , nodesSuccess :: !Int + , nodesFailed :: !Int + , nodesNotProcessed :: !Int + , targetProcessDuration :: HM.HashMap Int Int + , synthesisStepsForSuccess :: HM.HashMap Int Int } deriving (Generic, Show) instance Semigroup TreeInfo where - (<>) synthesisInfo1 synthesisInfo2 = - let synthesisInfoList = [synthesisInfo1, synthesisInfo2] - durationSuccessList = map durationSuccess synthesisInfoList - stepsSuccessList = map stepsSuccess synthesisInfoList + a <> b = + let ab = [a, b] + durationSuccessList = map targetProcessDuration ab + stepsSuccessList = map synthesisStepsForSuccess ab in TreeInfo - { nodes = sum $ map nodes synthesisInfoList - , success = sum $ map success synthesisInfoList - , failed = sum $ map failed synthesisInfoList - , notProcessed = sum $ map notProcessed synthesisInfoList - , durationSuccess = if not $ null durationSuccessList then foldr1 (HM.unionWith (+)) durationSuccessList else HM.empty - , stepsSuccess = if not $ null stepsSuccessList then foldr1 (HM.unionWith (+)) stepsSuccessList else HM.empty + { nodesVisited = sum $ map nodesVisited ab + , nodesSuccess = sum $ map nodesSuccess ab + , nodesFailed = sum $ map nodesFailed ab + , nodesNotProcessed = sum $ map nodesNotProcessed ab + , targetProcessDuration = if not $ null durationSuccessList then foldr1 (HM.unionWith (+)) durationSuccessList else HM.empty + , synthesisStepsForSuccess = if not $ null stepsSuccessList then foldr1 (HM.unionWith (+)) stepsSuccessList else HM.empty } instance Monoid TreeInfo where mempty = TreeInfo - { nodes = 0 - , success = 0 - , failed = 0 - , notProcessed = 0 - , durationSuccess = HM.empty - , stepsSuccess = HM.empty + { nodesVisited = 0 + , nodesSuccess = 0 + , nodesFailed = 0 + , nodesNotProcessed = 0 + , targetProcessDuration = HM.empty + , synthesisStepsForSuccess = HM.empty } +getTreeInfo :: + (VarValTime v x t, NextTick u t) => + Tree (TargetSystem u tag v x t) tag v x t -> + IO TreeInfo getTreeInfo tree@Tree{sID = Sid sid, sSubForestVar} = do subForestM <- atomically $ tryReadTMVar sSubForestVar - subForestInfo <- maybe (return mempty) (fmap mconcat . mapM getTreeInfo) subForestM + let isProcessed = isJust subForestM + TreeInfo + { nodesVisited + , nodesSuccess + , nodesFailed + , targetProcessDuration + , synthesisStepsForSuccess + , nodesNotProcessed + } <- + maybe (return mempty) (fmap mconcat . mapM getTreeInfo) subForestM + let (isSuccess, isFail) | isLeaf tree = if isComplete tree then (True, False) else (False, True) | otherwise = (False, False) + let duration = fromEnum $ processDuration $ sTarget $ sState tree - let successDepends value field = - if not isSuccess - then field subForestInfo - else HM.alter (Just . maybe 1 (+ 1)) value $ field subForestInfo + + let registerIfSuccess stat value + | not isSuccess = stat + | otherwise = HM.alter (Just . maybe 1 (+ 1)) value stat + return $ TreeInfo - { nodes = 1 + nodes subForestInfo - , success = if isSuccess then 1 else 0 + success subForestInfo - , failed = if isFail then 1 else 0 + failed subForestInfo - , notProcessed = maybe 1 (const 0) subForestM + notProcessed subForestInfo - , durationSuccess = successDepends duration durationSuccess - , stepsSuccess = successDepends (length sid) stepsSuccess + { nodesVisited = nodesVisited + 1 + , nodesSuccess = nodesSuccess + if isSuccess then 1 else 0 + , nodesFailed = nodesFailed + if isFail then 1 else 0 + , nodesNotProcessed = nodesNotProcessed + if isProcessed then 0 else 1 + , targetProcessDuration = registerIfSuccess targetProcessDuration duration + , synthesisStepsForSuccess = registerIfSuccess synthesisStepsForSuccess $ length sid } diff --git a/src/NITTA/Synthesis/Explore.hs b/src/NITTA/Synthesis/Explore.hs index e0922077c..c1310db9d 100644 --- a/src/NITTA/Synthesis/Explore.hs +++ b/src/NITTA/Synthesis/Explore.hs @@ -169,15 +169,18 @@ nodeCtx parent nModel = , sOptimizeAccumOptions = optimizeAccumOptions nModel , bindingAlternative = foldl - (\st (Bind f tag) -> M.alter (return . maybe [tag] (tag :)) f st) + ( \st b -> case b of + (SingleBind uTag f) -> M.alter (return . maybe [uTag] (uTag :)) f st + _ -> st + ) M.empty sBindOptions , possibleDeadlockBinds = S.fromList [ f - | (Bind f tag) <- sBindOptions + | (SingleBind uTag f) <- sBindOptions , Lock{lockBy} <- locks f - , lockBy `S.member` unionsMap variables (bindedFunctions tag $ mUnit nModel) + , lockBy `S.member` unionsMap variables (bindedFunctions uTag $ mUnit nModel) ] , bindWaves = estimateVarWaves (S.elems (variables (mUnit nModel) S.\\ unionsMap variables sBindOptions)) fs , processWaves @@ -189,4 +192,13 @@ nodeCtx parent nModel = | (DataflowSt _ targets) <- sDataflowOptions , (_, ep) <- targets ] + , unitWorkloadInFunction = + let + BusNetwork{bnBinded, bnPus} = mUnit nModel + in + M.fromList + $ map + ( \uTag -> (uTag, maybe 0 length $ bnBinded M.!? uTag) + ) + $ M.keys bnPus } diff --git a/src/NITTA/Synthesis/Method.hs b/src/NITTA/Synthesis/Method.hs index 87bbd636d..8dfcabdc1 100644 --- a/src/NITTA/Synthesis/Method.hs +++ b/src/NITTA/Synthesis/Method.hs @@ -26,6 +26,7 @@ module NITTA.Synthesis.Method ( import Data.List qualified as L import Data.Typeable import Debug.Trace +import NITTA.Model.Networks.Bus (BusNetwork) import NITTA.Model.ProcessorUnits import NITTA.Model.TargetSystem import NITTA.Synthesis.Explore @@ -53,7 +54,8 @@ stateOfTheArtSynthesisIO () tree = do l2 <- smartBindSynthesisIO tree l3 <- bestThreadIO stepLimit tree l4 <- bestThreadIO stepLimit =<< allBindsAndRefsIO tree - return $ bestLeaf tree [l1, l2, l3, l4] + l5 <- obliviousGroupBindsIO tree >>= tryAllGroupBindsByIO (bestThreadIO stepLimit) + return $ bestLeaf tree [l1, l2, l3, l4, l5] -- | Schedule process by simple synthesis. simpleSynthesisIO :: (VarValTime v x t, UnitTag tag) => SynthesisMethod tag v x t @@ -83,14 +85,25 @@ bestStepIO tree = do [] -> error "all step is over" _ -> return $ maximumOn (defScore . sDecision) subForest +obliviousGroupBindsIO :: (VarValTime v x t, UnitTag tag) => SynthesisMethod tag v x t +obliviousGroupBindsIO tree = do + binds <- selectSubForestIO isObliviousMultiBind tree + maybe (return tree) obliviousGroupBindsIO $ bestDecision binds + +tryAllGroupBindsByIO :: (VarValTime v x t, UnitTag tag) => SynthesisMethod tag v x t -> SynthesisMethod tag v x t +tryAllGroupBindsByIO method tree = do + bindSubForest <- selectSubForestIO isMultiBind tree + leafs <- mapM method bindSubForest + return $ bestLeaf tree leafs + obviousBindThreadIO :: (VarValTime v x t, UnitTag tag) => SynthesisMethod tag v x t obviousBindThreadIO tree = do subForest <- positiveSubForestIO tree maybe (return tree) obviousBindThreadIO $ L.find ( ( \case - Just BindMetrics{pPossibleDeadlock = True} -> False - Just BindMetrics{pAlternative = 1} -> True + Just SingleBindMetrics{pPossibleDeadlock = True} -> False + Just SingleBindMetrics{pAlternative = 1} -> True _ -> False ) . cast @@ -101,12 +114,13 @@ obviousBindThreadIO tree = do allBindsAndRefsIO :: (VarValTime v x t, UnitTag tag) => SynthesisMethod tag v x t allBindsAndRefsIO tree = do subForest <- - filter ((\d -> isBind d || isRefactor d) . sDecision) + filter ((\d -> isSingleBind d || isRefactor d) . sDecision) <$> positiveSubForestIO tree case subForest of [] -> return tree _ -> allBindsAndRefsIO $ maximumOn (defScore . sDecision) subForest +refactorThreadIO :: (VarValTime v x t, UnitTag tag) => SynthesisMethod tag v x t refactorThreadIO tree = do subForest <- positiveSubForestIO tree maybe (return tree) refactorThreadIO $ @@ -115,7 +129,7 @@ refactorThreadIO tree = do smartBindThreadIO :: (VarValTime v x t, UnitTag tag) => SynthesisMethod tag v x t smartBindThreadIO tree = do subForest <- - filter ((\d -> isBind d || isRefactor d) . sDecision) + filter ((\d -> isSingleBind d || isRefactor d) . sDecision) <$> (positiveSubForestIO =<< refactorThreadIO tree) case subForest of [] -> return tree @@ -137,3 +151,20 @@ bestLeaf tree leafs = minimumOn (\Tree{sState = SynthesisState{sTarget}} -> (processDuration sTarget, puSize sTarget)) successLeafs + +-- * Helpers + +selectSubForestIO :: + ( UnitTag tag + , VarValTime v x t + , m ~ TargetSystem (BusNetwork tag v x t) tag v x t + , ctx ~ SynthesisState m tag v x t + ) => + (SynthesisDecision ctx m -> Bool) -> + DefTree tag v x t -> + IO [DefTree tag v x t] +selectSubForestIO p tree = filter (p . sDecision) <$> positiveSubForestIO tree + +bestDecision :: [DefTree tag v x t] -> Maybe (DefTree tag v x t) +bestDecision [] = Nothing +bestDecision xs = Just $ maximumOn (defScore . sDecision) xs diff --git a/src/NITTA/Synthesis/Steps/Bind.hs b/src/NITTA/Synthesis/Steps/Bind.hs index 7f4a33ce0..2230af07f 100644 --- a/src/NITTA/Synthesis/Steps/Bind.hs +++ b/src/NITTA/Synthesis/Steps/Bind.hs @@ -13,7 +13,9 @@ Stability : experimental -} module NITTA.Synthesis.Steps.Bind ( BindMetrics (..), - isBind, + isSingleBind, + isMultiBind, + isObliviousMultiBind, ) where import Data.Aeson (ToJSON) @@ -34,24 +36,39 @@ import NITTA.Synthesis.Types import NITTA.Utils import Numeric.Interval.NonEmpty (inf) -data BindMetrics = BindMetrics - { pCritical :: Bool - -- ^ Can this binding block another one (for example, one 'Loop' can - -- take the last free buffer)? - , pAlternative :: Float - -- ^ How many alternative binding we have? - , pRestless :: Float - -- ^ How many ticks requires for executing the function? - , pOutputNumber :: Float - , pAllowDataFlow :: Float - -- ^ How many transactions can be executed with this function? - , pPossibleDeadlock :: Bool - -- ^ May this binding cause deadlock? - , pNumberOfBindedFunctions :: Float - , pPercentOfBindedInputs :: Float - -- ^ number of binded input variables / number of all input variables - , pWave :: Maybe Float - } +data BindMetrics + = SingleBindMetrics + { pCritical :: Bool + -- ^ Can this binding block another one (for example, one 'Loop' can + -- take the last free buffer)? + , pAlternative :: Float + -- ^ How many alternative binding we have? + , pRestless :: Float + -- ^ How many ticks requires for executing the function? + , pOutputNumber :: Float + , pAllowDataFlow :: Float + -- ^ How many transactions can be executed with this function? + , pPossibleDeadlock :: Bool + -- ^ May this binding cause deadlock? + , pNumberOfBindedFunctions :: Float + , pPercentOfBindedInputs :: Float + -- ^ number of binded input variables / number of all input variables + , pWave :: Maybe Float + } + | GroupBindMetrics + { pOnlyObliviousBinds :: Bool + -- ^ We don't have alternatives for binding + , pFunctionPercentInBinds :: Float + -- ^ number of binded functions / number of all functions in DFG + , pAvgBinds :: Float + -- ^ average number of binds per unit + , pVarianceBinds :: Float + -- ^ variance of binds per unit + , pAvgUnitWorkload :: Float + -- ^ average number of variables after bind per unit + , pVarianceUnitWorkload :: Float + -- ^ variance of variables after bind per unit + } deriving (Generic) instance ToJSON BindMetrics @@ -74,9 +91,9 @@ instance , possibleDeadlockBinds , bindWaves } - (Bind f tag) + (SingleBind tag f) _ = - BindMetrics + SingleBindMetrics { pCritical = isInternalLockPossible f , pAlternative = fromIntegral $ length (bindingAlternative M.! f) , pAllowDataFlow = fromIntegral $ length $ unionsMap variables $ filter isTarget $ optionsAfterBind f tag sTarget @@ -96,20 +113,57 @@ instance waves | all isJust waves -> Just $ maximum $ catMaybes waves _ -> Nothing } + parameters SynthesisState{sTarget, unitWorkloadInFunction} binds@GroupBind{isObliviousBinds, bindGroup} _ = + let dfgFunCount = length $ functions $ mDataFlowGraph sTarget + bindFunCount = length $ functions binds + in GroupBindMetrics + { pOnlyObliviousBinds = isObliviousBinds + , pFunctionPercentInBinds = fromIntegral bindFunCount / fromIntegral dfgFunCount + , pAvgBinds = avg $ map (fromIntegral . length . snd) $ M.assocs bindGroup + , pVarianceBinds = stddev $ map (fromIntegral . length . snd) $ M.assocs bindGroup + , pAvgUnitWorkload = avg $ map unitWorkload $ M.keys bindGroup + , pVarianceUnitWorkload = stddev $ map unitWorkload $ M.keys bindGroup + } + where + unitWorkload = fromIntegral . (unitWorkloadInFunction M.!) + avg lst = sum lst / fromIntegral (length lst) + stddev lst = + let lstAvg = avg lst + in sqrt $ avg $ map (\x -> (x - lstAvg) ^ (2 :: Int)) lst - estimate _ctx _o _d BindMetrics{pPossibleDeadlock = True} = 500 - estimate _ctx _o _d BindMetrics{pCritical, pAlternative, pAllowDataFlow, pRestless, pNumberOfBindedFunctions, pWave, pPercentOfBindedInputs, pOutputNumber} = + estimate _ctx _o _d GroupBindMetrics{pOnlyObliviousBinds, pFunctionPercentInBinds, pVarianceBinds} = sum - [ 3000 - , pCritical 1000 - , (pAlternative == 1) 500 - , pAllowDataFlow * 10 - , pPercentOfBindedInputs * 50 - , -fromMaybe (-1) pWave * 50 - , -pNumberOfBindedFunctions * 10 - , -pRestless * 4 - , pOutputNumber * 2 + [ 4100 + , pOnlyObliviousBinds 1000 + , fromInteger $ round pFunctionPercentInBinds * 10 + , fromInteger $ round pVarianceBinds * (-20) ] + estimate _ctx _o _d SingleBindMetrics{pPossibleDeadlock = True} = 500 + estimate + _ctx + _o + _d + SingleBindMetrics + { pCritical + , pAlternative + , pAllowDataFlow + , pRestless + , pNumberOfBindedFunctions + , pWave + , pPercentOfBindedInputs + , pOutputNumber + } = + sum + [ 3000 + , pCritical 1000 + , (pAlternative == 1) 500 + , pAllowDataFlow * 10 + , pPercentOfBindedInputs * 50 + , -fromMaybe (-1) pWave * 50 + , -pNumberOfBindedFunctions * 10 + , -pRestless * 4 + , pOutputNumber * 2 + ] waitingTimeOfVariables net = [ (variable, inf $ tcAvailable constrain) @@ -125,6 +179,17 @@ optionsAfterBind f tag TargetSystem{mUnit = BusNetwork{bnPus}} = where act `optionOf` f' = not $ S.null (variables act `S.intersection` variables f') -isBind SynthesisDecision{metrics} - | isJust (cast metrics :: Maybe BindMetrics) = True -isBind _ = False +isSingleBind :: SynthesisDecision ctx m -> Bool +isSingleBind SynthesisDecision{metrics} + | Just SingleBindMetrics{} <- cast metrics :: Maybe BindMetrics = True +isSingleBind _ = False + +isMultiBind :: SynthesisDecision ctx m -> Bool +isMultiBind SynthesisDecision{metrics} + | Just GroupBindMetrics{} <- cast metrics :: Maybe BindMetrics = True +isMultiBind _ = False + +isObliviousMultiBind :: SynthesisDecision ctx m -> Bool +isObliviousMultiBind SynthesisDecision{metrics} + | Just GroupBindMetrics{pOnlyObliviousBinds = True} <- cast metrics :: Maybe BindMetrics = True +isObliviousMultiBind _ = False diff --git a/src/NITTA/Synthesis/Types.hs b/src/NITTA/Synthesis/Types.hs index 3e7442cff..5bd3ef1c0 100644 --- a/src/NITTA/Synthesis/Types.hs +++ b/src/NITTA/Synthesis/Types.hs @@ -132,6 +132,7 @@ data SynthesisDecision ctx m where {option :: o, decision :: d, metrics :: p, scores :: Map Text Float} -> SynthesisDecision ctx m +defScore :: SynthesisDecision ctx m -> Float defScore = (M.! "default") . scores class SynthesisDecisionCls ctx m o d p | ctx o -> m d p where @@ -169,6 +170,8 @@ data SynthesisState m tag v x t = SynthesisState , transferableVars :: S.Set v -- ^ a variable set, which can be transferred on the current -- synthesis step + , unitWorkloadInFunction :: M.Map tag Int + -- ^ dictionary with number of binded functions for each unit } -- * Utils diff --git a/src/NITTA/UIBackend/ViewHelper.hs b/src/NITTA/UIBackend/ViewHelper.hs index 2006b493d..97c170333 100644 --- a/src/NITTA/UIBackend/ViewHelper.hs +++ b/src/NITTA/UIBackend/ViewHelper.hs @@ -157,7 +157,8 @@ viewNodeTree tree@Tree{sID = sid, sDecision, sSubForestVar} = do Root{} -> "root" SynthesisDecision{metrics} | Just AllocationMetrics{} <- cast metrics -> "Allocation" - | Just BindMetrics{} <- cast metrics -> "Bind" + | Just SingleBindMetrics{} <- cast metrics -> "SingleBind" + | Just GroupBindMetrics{} <- cast metrics -> "GroupBind" | Just BreakLoopMetrics{} <- cast metrics -> "Refactor" | Just ConstantFoldingMetrics{} <- cast metrics -> "Refactor" | Just DataflowMetrics{} <- cast metrics -> "Transport" @@ -219,7 +220,7 @@ instance ToSample (NodeView tag v x t) where , duration = 0 , parameters = toJSON $ - BindMetrics + SingleBindMetrics { pCritical = False , pAlternative = 1 , pRestless = 0 @@ -230,7 +231,7 @@ instance ToSample (NodeView tag v x t) where , pPercentOfBindedInputs = 0.2 , pWave = Just 2 } - , decision = BindDecisionView (FView "buffer(a) = b = c" []) "pu" + , decision = SingleBindView (FView "buffer(a) = b = c" []) "pu" , score = 1032 } , NodeView diff --git a/test/NITTA/Model/ProcessorUnits/Tests/DSL.hs b/test/NITTA/Model/ProcessorUnits/Tests/DSL.hs index 19e978cb0..af8856c13 100644 --- a/test/NITTA/Model/ProcessorUnits/Tests/DSL.hs +++ b/test/NITTA/Model/ProcessorUnits/Tests/DSL.hs @@ -437,9 +437,9 @@ synthesis method = do put st{unit = sTarget $ sState leaf} doBind :: T.Text -> F T.Text x -> TSStatement x () -doBind tag f = do +doBind uTag f = do st@UnitTestState{unit = ts} <- get - let d = Bind f tag + let d = SingleBind uTag f opts = bindOptions ts unless (d `L.elem` opts) $ lift $ diff --git a/web/src/components/IntermediateView.tsx b/web/src/components/IntermediateView.tsx index 93a9f11ae..cd4bc969b 100644 --- a/web/src/components/IntermediateView.tsx +++ b/web/src/components/IntermediateView.tsx @@ -4,7 +4,7 @@ import { Graphviz } from "graphviz-react"; import { AppContext, IAppContext } from "app/AppContext"; import { GraphNode, GraphEdge } from "services/gen/types"; -import { api, IntermediateGraph, Dataflow, Bind, Node } from "services/HaskellApiService"; +import { api, IntermediateGraph, Dataflow, SingleBind, Node } from "services/HaskellApiService"; import { UnitEndpointsData, EndpointOptionData, EndpointDecision } from "services/HaskellApiService"; import { DownloadTextFile } from "utils/download"; @@ -162,8 +162,8 @@ function makeProcState(nodes: Node[]): ProcessState { procState.transferedVars.push(target[1].epRole.contents as string); }); } - if (n.decision.tag === "BindDecisionView") { - let d = n.decision as Bind; + if (n.decision.tag === "SingleBindView") { + let d = n.decision as SingleBind; procState.bindeFuns.push(d.function.fvFun, ...d.function.fvHistory); } }); diff --git a/web/src/components/SubforestTables.tsx b/web/src/components/SubforestTables.tsx index 5c2266b34..ce2040376 100644 --- a/web/src/components/SubforestTables.tsx +++ b/web/src/components/SubforestTables.tsx @@ -3,7 +3,7 @@ import ReactTable, { Column } from "react-table"; import { AppContext, IAppContext } from "app/AppContext"; import { Node, Dataflow } from "services/HaskellApiService"; -import { BindMetrics, AllocationMetrics, DataflowMetrics } from "services/gen/types"; +import { ISingleBindMetrics, IGroupBindMetrics, AllocationMetrics, DataflowMetrics } from "services/gen/types"; import { sidColumn, textColumn, @@ -26,8 +26,9 @@ export const SubforestTables: FC = ({ nodes }) => { }; let known = [ "RootView", + "GroupBindView", "AllocationView", - "BindDecisionView", + "SingleBindView", "DataflowDecisionView", "BreakLoopView", "ConstantFoldingView", @@ -45,40 +46,61 @@ export const SubforestTables: FC = ({ nodes }) => { return ( <> + ["GroupBindView"].includes(e.decision.tag))} + columns={[ + sidColumn(appContext.setSid), + objectiveColumn(scoresInfo), + textColumn("type", (e: Node) => e.decision.tag, 160), + textColumn("description", (e: Node) => showDecision(e.decision)), + + textColumn("oblivious", (e: Node) => String((e.parameters as IGroupBindMetrics).pOnlyObliviousBinds), 75), + textColumn("percent", (e: Node) => String((e.parameters as IGroupBindMetrics).pFunctionPercentInBinds), 75), + textColumn("avg", (e: Node) => String((e.parameters as IGroupBindMetrics).pAvgBinds), 50), + textColumn("variance", (e: Node) => String((e.parameters as IGroupBindMetrics).pVarianceBinds), 75), + textColumn("avgLoad", (e: Node) => String((e.parameters as IGroupBindMetrics).pAvgUnitWorkload), 75), + textColumn( + "varianceLoad", + (e: Node) => String((e.parameters as IGroupBindMetrics).pVarianceUnitWorkload), + 100 + ), + + detailColumn(), + ]} + />
e.decision.tag === "BindDecisionView")} + nodes={nodes.filter((e: Node) => e.decision.tag === "SingleBindView")} columns={[ sidColumn(appContext.setSid), objectiveColumn(scoresInfo), textColumn("description", (e: Node) => showDecision(e.decision)), - textColumn("crit", (e: Node) => String((e.parameters as BindMetrics).pCritical), 50), - textColumn("lock", (e: Node) => String((e.parameters as BindMetrics).pPossibleDeadlock), 50), + textColumn("crit", (e: Node) => String((e.parameters as ISingleBindMetrics).pCritical), 50), + textColumn("lock", (e: Node) => String((e.parameters as ISingleBindMetrics).pPossibleDeadlock), 50), textColumn( "wave", (e: Node) => { - let x = (e.parameters as BindMetrics).pWave; + let x = (e.parameters as ISingleBindMetrics).pWave; return x === undefined || x === null ? "null" : (x as number).toString(); }, 50 ), - textColumn("outputs", (e: Node) => (e.parameters as BindMetrics).pOutputNumber, 70), - textColumn("alt", (e: Node) => (e.parameters as BindMetrics).pAlternative, 50), - textColumn("rest", (e: Node) => (e.parameters as BindMetrics).pRestless, 50), + textColumn("outputs", (e: Node) => (e.parameters as ISingleBindMetrics).pOutputNumber, 70), + textColumn("alt", (e: Node) => (e.parameters as ISingleBindMetrics).pAlternative, 50), + textColumn("rest", (e: Node) => (e.parameters as ISingleBindMetrics).pRestless, 50), - textColumn("newDF", (e: Node) => (e.parameters as BindMetrics).pAllowDataFlow, 70), - textColumn("newBind", (e: Node) => (e.parameters as BindMetrics).pNumberOfBindedFunctions, 70), - textColumn("|inputs|", (e: Node) => (e.parameters as BindMetrics).pPercentOfBindedInputs, 70), + textColumn("newDF", (e: Node) => (e.parameters as ISingleBindMetrics).pAllowDataFlow, 70), + textColumn("newBind", (e: Node) => (e.parameters as ISingleBindMetrics).pNumberOfBindedFunctions, 70), + textColumn("|inputs|", (e: Node) => (e.parameters as ISingleBindMetrics).pPercentOfBindedInputs, 70), detailColumn(), ]} />
!["DataflowDecisionView", "BindDecisionView", "AllocationView"].includes(e.decision.tag) - )} + nodes={nodes.filter((e) => ["BreakLoopView", "ConstantFoldingView", "AllocationView"].includes(e.decision.tag))} columns={[ sidColumn(appContext.setSid), objectiveColumn(scoresInfo), diff --git a/web/src/components/SubforestTables/Columns.tsx b/web/src/components/SubforestTables/Columns.tsx index 0003f9d87..300951e21 100644 --- a/web/src/components/SubforestTables/Columns.tsx +++ b/web/src/components/SubforestTables/Columns.tsx @@ -5,12 +5,13 @@ import * as Icon from "react-bootstrap-icons"; import { Allocation, - Bind, + GroupBind, + SingleBind, Dataflow, BreakLoop, OptimizeAccum, ConstantFolding, - ResolveDeadlock + ResolveDeadlock, } from "services/HaskellApiService"; import { Node, sidSeparator, EndpointDecision, Target } from "services/HaskellApiService"; import { Interval, FView, DecisionView } from "services/gen/types"; @@ -141,7 +142,8 @@ export function objectiveColumn(scoresInfo: ScoresInfo): Column { } export function showDecision(decision: DecisionView): ReactElement { - if (decision.tag === "BindDecisionView") return showBind(decision); + if (decision.tag === "SingleBindView") return showBind(decision); + else if (decision.tag === "GroupBindView") return showBinds(decision); else if (decision.tag === "DataflowDecisionView") return showDataflow(decision); else if (decision.tag === "BreakLoopView") return showBreakLoop(decision); else if (decision.tag === "ConstantFoldingView") return showConstantFolding(decision); @@ -151,7 +153,24 @@ export function showDecision(decision: DecisionView): ReactElement { else throw new Error("Unkown decision type: " + decision.tag); } -export function showBind(decision: Bind): ReactElement { +export function showBinds(decision: GroupBind): ReactElement { + const binds = Object.keys(decision.bindGroup).map((uTag: string) => { + let fs = decision.bindGroup[uTag]!; + return ( +
+ {uTag} +
    + {fs.map((e) => ( +
  • {e.fvFun}
  • + ))} +
+
+ ); + }); + return
{binds}
; +} + +export function showBind(decision: SingleBind): ReactElement { return (
{decision.pu} {decision.function.fvFun} diff --git a/web/src/components/TreeInfoView.tsx b/web/src/components/TreeInfoView.tsx index dea90e887..a8a6ae9b3 100644 --- a/web/src/components/TreeInfoView.tsx +++ b/web/src/components/TreeInfoView.tsx @@ -31,22 +31,24 @@ export const TreeInfoView: FC = (props) => { resultRenderer={(result) => ( -
+ - - - - - + + + + + + + diff --git a/web/src/services/HaskellApiService.ts b/web/src/services/HaskellApiService.ts index 651d7aad2..7bd3e20ec 100644 --- a/web/src/services/HaskellApiService.ts +++ b/web/src/services/HaskellApiService.ts @@ -7,9 +7,12 @@ import { ShortNodeView, IBreakLoopView, IConstantFoldingView, + IDataflowDecisionView, IOptimizeAccumView, IResolveDeadlockView, NetworkDesc, + ISingleBindView, + IGroupBindView, UnitDesc, Relation, TimeConstraint, @@ -19,7 +22,7 @@ import { StepInfoView, IAllocationView, } from "services/gen/types"; -import { NodeView, DecisionView, IRootView, IBindDecisionView, IDataflowDecisionView } from "services/gen/types"; +import { NodeView, DecisionView, IRootView } from "services/gen/types"; import { UnitEndpoints, EndpointSt, @@ -40,7 +43,8 @@ export type Node = NodeView; export type Decision = DecisionView; export type Root = IRootView; -export type Bind = IBindDecisionView; +export type SingleBind = ISingleBindView; +export type GroupBind = IGroupBindView; export type Allocation = IAllocationView; export type Dataflow = IDataflowDecisionView;