never executed always true always false
    1 {-# LANGUAGE TypeFamilies #-}
    2 
    3 {- |
    4 Module      : NITTA.Model.TargetSystem
    5 Description : Model of target system for synthesis and so on.
    6 Copyright   : (c) Aleksandr Penskoi, 2021
    7 License     : BSD3
    8 Maintainer  : aleksandr.penskoi@gmail.com
    9 Stability   : experimental
   10 -}
   11 module NITTA.Model.TargetSystem (
   12     TargetSystem (..),
   13     processDuration,
   14     isSynthesisComplete,
   15 ) where
   16 
   17 import Control.Exception (assert)
   18 import Data.Default
   19 import Data.Set qualified as S
   20 import GHC.Generics
   21 import NITTA.Intermediate.DataFlow
   22 import NITTA.Intermediate.Types
   23 import NITTA.Model.Problems
   24 import NITTA.Model.ProcessorUnits
   25 import NITTA.Utils
   26 
   27 {- | Model of target unit, which is a main subject of synthesis process and
   28 synthesis graph.
   29 -}
   30 data TargetSystem u tag v x t = TargetSystem
   31     { mUnit :: u
   32     -- ^ model of target unit
   33     , mDataFlowGraph :: DataFlowGraph v x
   34     -- ^ whole application algorithm
   35     }
   36     deriving (Generic)
   37 
   38 instance Default u => Default (TargetSystem u tag v x t) where
   39     def = TargetSystem def def
   40 
   41 instance WithFunctions u (F v x) => WithFunctions (TargetSystem u tag v x t) (F v x) where
   42     functions TargetSystem{mUnit, mDataFlowGraph} =
   43         assert (S.fromList (functions mUnit) == S.fromList (functions mDataFlowGraph)) $ -- inconsistent TargetSystem
   44             functions mUnit
   45 
   46 processDuration TargetSystem{mUnit} = nextTick mUnit - 1
   47 
   48 isSynthesisComplete :: ProcessorUnit u v x t => TargetSystem u tag v x t -> Bool
   49 isSynthesisComplete TargetSystem{mUnit, mDataFlowGraph} =
   50     transferred mUnit == variables mDataFlowGraph
   51 
   52 instance ProcessorUnit u v x t => ProcessorUnit (TargetSystem u tag v x t) v x t where
   53     tryBind f ts@TargetSystem{mUnit} = (\u -> ts{mUnit = u}) <$> tryBind f mUnit
   54     process TargetSystem{mUnit} = process mUnit
   55     parallelismType TargetSystem{mUnit} = parallelismType mUnit
   56     puSize TargetSystem{mUnit} = puSize mUnit
   57 
   58 instance BindProblem u tag v x => BindProblem (TargetSystem u tag v x t) tag v x where
   59     bindOptions TargetSystem{mUnit} = bindOptions mUnit
   60 
   61     bindDecision ts@TargetSystem{mUnit} d = ts{mUnit = bindDecision mUnit d}
   62 
   63 instance DataflowProblem u tag v t => DataflowProblem (TargetSystem u tag v x t) tag v t where
   64     dataflowOptions TargetSystem{mUnit} = dataflowOptions mUnit
   65 
   66     dataflowDecision f@TargetSystem{mUnit} d = f{mUnit = dataflowDecision mUnit d}
   67 
   68 instance
   69     (Var v, Val x, BreakLoopProblem u v x) =>
   70     BreakLoopProblem (TargetSystem u tag v x t) v x
   71     where
   72     breakLoopOptions TargetSystem{mUnit} = breakLoopOptions mUnit
   73 
   74     breakLoopDecision TargetSystem{mUnit, mDataFlowGraph} d =
   75         TargetSystem
   76             { mDataFlowGraph = breakLoopDecision mDataFlowGraph d
   77             , mUnit = breakLoopDecision mUnit d
   78             }
   79 
   80 instance
   81     (Var v, Val x, OptimizeAccumProblem u v x) =>
   82     OptimizeAccumProblem (TargetSystem u tag v x t) v x
   83     where
   84     optimizeAccumOptions TargetSystem{mUnit} = optimizeAccumOptions mUnit
   85 
   86     optimizeAccumDecision TargetSystem{mUnit, mDataFlowGraph} d =
   87         TargetSystem
   88             { mDataFlowGraph = optimizeAccumDecision mDataFlowGraph d
   89             , mUnit = optimizeAccumDecision mUnit d
   90             }
   91 
   92 instance (Var v, Val x, ConstantFoldingProblem u v x) => ConstantFoldingProblem (TargetSystem u tag v x t) v x where
   93     constantFoldingOptions TargetSystem{mUnit} = constantFoldingOptions mUnit
   94 
   95     constantFoldingDecision TargetSystem{mUnit, mDataFlowGraph} d =
   96         TargetSystem
   97             { mDataFlowGraph = constantFoldingDecision mDataFlowGraph d
   98             , mUnit = constantFoldingDecision mUnit d
   99             }
  100 
  101 instance (Var v, ResolveDeadlockProblem u v x) => ResolveDeadlockProblem (TargetSystem u tag v x t) v x where
  102     resolveDeadlockOptions TargetSystem{mUnit} = resolveDeadlockOptions mUnit
  103 
  104     resolveDeadlockDecision TargetSystem{mUnit, mDataFlowGraph} d =
  105         TargetSystem
  106             { mDataFlowGraph = resolveDeadlockDecision mDataFlowGraph d
  107             , mUnit = resolveDeadlockDecision mUnit d
  108             }
  109 
  110 instance AllocationProblem u tag => AllocationProblem (TargetSystem u tag v x t) tag where
  111     allocationOptions TargetSystem{mUnit} = allocationOptions mUnit
  112 
  113     allocationDecision f@TargetSystem{mUnit} d = f{mUnit = allocationDecision mUnit d}