never executed always true always false
    1 {-# LANGUAGE GADTs #-}
    2 {-# LANGUAGE NoMonomorphismRestriction #-}
    3 
    4 {-# OPTIONS -fno-warn-orphans #-}
    5 
    6 {- |
    7 Module      : NITTA.Synthesis.Steps.Bind
    8 Description :
    9 Copyright   : (c) Aleksandr Penskoi, 2021
   10 License     : BSD3
   11 Maintainer  : aleksandr.penskoi@gmail.com
   12 Stability   : experimental
   13 -}
   14 module NITTA.Synthesis.Steps.Bind (
   15     BindMetrics (..),
   16     isSingleBind,
   17     isMultiBind,
   18     isObviousMultiBind,
   19 ) where
   20 
   21 import Data.Aeson (ToJSON)
   22 import Data.List qualified as L
   23 import Data.Map.Strict qualified as M
   24 import Data.Maybe
   25 import Data.Set qualified as S
   26 import Data.Typeable
   27 import GHC.Generics
   28 import NITTA.Intermediate.Types
   29 import NITTA.Model.Networks.Bus
   30 import NITTA.Model.Problems.Bind
   31 import NITTA.Model.Problems.Dataflow
   32 import NITTA.Model.Problems.Endpoint
   33 import NITTA.Model.ProcessorUnits
   34 import NITTA.Model.TargetSystem
   35 import NITTA.Synthesis.Types
   36 import NITTA.Utils
   37 import Numeric.Interval.NonEmpty (inf)
   38 
   39 data BindMetrics
   40     = SingleBindMetrics
   41         { pCritical :: Bool
   42         -- ^ Can this binding block another one (for example, one 'Loop' can
   43         --  take the last free buffer)?
   44         , pAlternative :: Float
   45         -- ^ How many alternative binding we have?
   46         , pRestless :: Float
   47         -- ^ How many ticks requires for executing the function?
   48         , pOutputNumber :: Float
   49         , pAllowDataFlow :: Float
   50         -- ^ How many transactions can be executed with this function?
   51         , pPossibleDeadlock :: Bool
   52         -- ^ May this binding cause deadlock?
   53         , pNumberOfBoundFunctions :: Float
   54         , pPercentOfBoundInputs :: Float
   55         -- ^ number of bound input variables / number of all input variables
   56         , pWave :: Maybe Float
   57         }
   58     | GroupBindMetrics
   59         { pOnlyObviousBinds :: Bool
   60         -- ^ We don't have alternatives for binding
   61         , pFunctionPercentInBinds :: Float
   62         -- ^ number of bound functions / number of all functions in DFG
   63         , pAvgBinds :: Float
   64         -- ^ average number of binds per unit
   65         , pVarianceBinds :: Float
   66         -- ^ variance of binds per unit
   67         , pAvgUnitWorkload :: Float
   68         -- ^ average number of variables after bind per unit
   69         , pVarianceUnitWorkload :: Float
   70         -- ^ variance of variables after bind per unit
   71         }
   72     deriving (Generic)
   73 
   74 instance ToJSON BindMetrics
   75 
   76 instance
   77     (UnitTag tag, VarValTime v x t) =>
   78     SynthesisDecisionCls
   79         (SynthesisState (TargetSystem (BusNetwork tag v x t) tag v x t) tag v x t)
   80         (TargetSystem (BusNetwork tag v x t) tag v x t)
   81         (Bind tag v x)
   82         (Bind tag v x)
   83         BindMetrics
   84     where
   85     decisions SynthesisState{sTarget} o = [(o, bindDecision sTarget o)]
   86 
   87     parameters
   88         SynthesisState
   89             { bindingAlternative
   90             , sTarget = sTarget@TargetSystem{mUnit}
   91             , possibleDeadlockBinds
   92             , bindWaves
   93             }
   94         (SingleBind tag f)
   95         _ =
   96             SingleBindMetrics
   97                 { pCritical = isInternalLockPossible f
   98                 , pAlternative = fromIntegral $ length (bindingAlternative M.! f)
   99                 , pAllowDataFlow = fromIntegral $ length $ unionsMap variables $ filter isTarget $ optionsAfterBind f tag sTarget
  100                 , pRestless = fromMaybe 0 $ do
  101                     (_var, tcFrom) <- L.find (\(v, _) -> v `elem` variables f) $ waitingTimeOfVariables sTarget
  102                     return $ fromIntegral tcFrom
  103                 , pOutputNumber = fromIntegral $ length $ S.elems $ outputs f
  104                 , pPossibleDeadlock = f `S.member` possibleDeadlockBinds
  105                 , pNumberOfBoundFunctions = fromIntegral $ length $ boundFunctions tag mUnit
  106                 , pPercentOfBoundInputs =
  107                     let is = inputs f
  108                         n = fromIntegral $ length $ S.intersection is $ variables mUnit
  109                         nAll = fromIntegral $ length is
  110                      in if nAll == 0 then 1 else n / nAll
  111                 , pWave = fmap fromIntegral $ case map (bindWaves M.!?) $ S.elems $ inputs f of
  112                     [] -> Just 0
  113                     waves | all isJust waves -> Just $ maximum $ catMaybes waves
  114                     _ -> Nothing
  115                 }
  116     parameters SynthesisState{sTarget, unitWorkloadInFunction} binds@GroupBind{isObviousBinds, bindGroup} _ =
  117         let dfgFunCount = length $ functions $ mDataFlowGraph sTarget
  118             bindFunCount = length $ functions binds
  119          in GroupBindMetrics
  120                 { pOnlyObviousBinds = isObviousBinds
  121                 , pFunctionPercentInBinds = fromIntegral bindFunCount / fromIntegral dfgFunCount
  122                 , pAvgBinds = avg $ map (fromIntegral . length . snd) $ M.assocs bindGroup
  123                 , pVarianceBinds = stddev $ map (fromIntegral . length . snd) $ M.assocs bindGroup
  124                 , pAvgUnitWorkload = avg $ map unitWorkload $ M.keys bindGroup
  125                 , pVarianceUnitWorkload = stddev $ map unitWorkload $ M.keys bindGroup
  126                 }
  127         where
  128             unitWorkload = fromIntegral . (unitWorkloadInFunction M.!)
  129             avg lst = sum lst / fromIntegral (length lst)
  130             stddev lst =
  131                 let lstAvg = avg lst
  132                  in sqrt $ avg $ map (\x -> (x - lstAvg) ^ (2 :: Int)) lst
  133 
  134     estimate _ctx _o _d GroupBindMetrics{pOnlyObviousBinds, pFunctionPercentInBinds, pVarianceBinds} =
  135         sum
  136             [ 4100
  137             , pOnlyObviousBinds <?> 1000
  138             , fromInteger $ round pFunctionPercentInBinds * 10
  139             , fromInteger $ round pVarianceBinds * (-20)
  140             ]
  141     estimate _ctx _o _d SingleBindMetrics{pPossibleDeadlock = True} = 500
  142     estimate
  143         _ctx
  144         _o
  145         _d
  146         SingleBindMetrics
  147             { pCritical
  148             , pAlternative
  149             , pAllowDataFlow
  150             , pRestless
  151             , pNumberOfBoundFunctions
  152             , pWave
  153             , pPercentOfBoundInputs
  154             , pOutputNumber
  155             } =
  156             sum
  157                 [ 3000
  158                 , pCritical <?> 1000
  159                 , (pAlternative == 1) <?> 500
  160                 , pAllowDataFlow * 10
  161                 , pPercentOfBoundInputs * 50
  162                 , -fromMaybe (-1) pWave * 50
  163                 , -pNumberOfBoundFunctions * 10
  164                 , -pRestless * 4
  165                 , pOutputNumber * 2
  166                 ]
  167 
  168 waitingTimeOfVariables net =
  169     [ (variable, inf $ tcAvailable constrain)
  170     | DataflowSt{dfSource = (_, srcEp), dfTargets} <- dataflowOptions net
  171     , let constrain = epAt srcEp
  172     , variable <- S.elems (variables srcEp S.\\ unionsMap (variables . snd) dfTargets)
  173     ]
  174 
  175 optionsAfterBind f tag TargetSystem{mUnit = BusNetwork{bnPus}} =
  176     case tryBind f (bnPus M.! tag) of
  177         Right pu' -> filter (\(EndpointSt act _) -> act `optionOf` f) $ endpointOptions pu'
  178         _ -> []
  179     where
  180         act `optionOf` f' = not $ S.null (variables act `S.intersection` variables f')
  181 
  182 isSingleBind :: SynthesisDecision ctx m -> Bool
  183 isSingleBind SynthesisDecision{metrics}
  184     | Just SingleBindMetrics{} <- cast metrics :: Maybe BindMetrics = True
  185 isSingleBind _ = False
  186 
  187 isMultiBind :: SynthesisDecision ctx m -> Bool
  188 isMultiBind SynthesisDecision{metrics}
  189     | Just GroupBindMetrics{} <- cast metrics :: Maybe BindMetrics = True
  190 isMultiBind _ = False
  191 
  192 isObviousMultiBind :: SynthesisDecision ctx m -> Bool
  193 isObviousMultiBind SynthesisDecision{metrics}
  194     | Just GroupBindMetrics{pOnlyObviousBinds = True} <- cast metrics :: Maybe BindMetrics = True
  195 isObviousMultiBind _ = False