never executed always true always false
    1 -- All extensions should be enabled explicitly due to doctest in this module.
    2 {-# LANGUAGE DuplicateRecordFields #-}
    3 {-# LANGUAGE FlexibleContexts #-}
    4 {-# LANGUAGE FlexibleInstances #-}
    5 {-# LANGUAGE ImportQualifiedPost #-}
    6 {-# LANGUAGE LambdaCase #-}
    7 {-# LANGUAGE MultiParamTypeClasses #-}
    8 {-# LANGUAGE NamedFieldPuns #-}
    9 {-# LANGUAGE OverloadedStrings #-}
   10 {-# LANGUAGE QuasiQuotes #-}
   11 {-# LANGUAGE RecordWildCards #-}
   12 {-# LANGUAGE ScopedTypeVariables #-}
   13 {-# LANGUAGE StandaloneDeriving #-}
   14 {-# LANGUAGE TypeFamilies #-}
   15 {-# LANGUAGE UndecidableInstances #-}
   16 
   17 -- TODO: A promising direction for the improvement is the implementation of the
   18 -- accumulator into it. It allows multiplying an arbitrary number of arguments,
   19 -- which will reduce the number of data transactions on the bus when multiplying
   20 -- more than two variables by one function.
   21 
   22 -- TODO: Add assertion, which checks that all synthesis decision compliant
   23 -- available options.
   24 
   25 {- |
   26 Module      : NITTA.Model.ProcessorUnits.Multiplier
   27 Description :
   28 Copyright   : (c) Aleksandr Penskoi, 2020
   29 License     : BSD3
   30 Maintainer  : aleksandr.penskoi@gmail.com
   31 Stability   : experimental
   32 
   33 = Processor unit
   34 
   35 A processor unit (PU) can be used for:
   36 
   37 - data storage and processing;
   38 - interaction with the periphery (IO);
   39 - control of a NITTA processor (special case).
   40 
   41 There are characterized by complicated behavior with:
   42 
   43 - multifunctionality;
   44 - internal parallelism;
   45 - superscalar;
   46 - pipelining;
   47 - availability of internal resources.
   48 
   49 The multiplier PU is one of the simplest processors because it realizes only
   50 one function with sequence evaluation
   51 ('NITTA.Intermediate.Functions.Multiply'). Processor behavior in a specific
   52 application is determined by the applied algorithm
   53 ('NITTA.Intermediate.DataFlow').
   54 
   55 Any PU may include three components:
   56 
   57 - hardware - set of prepared or automatically generated hardware descriptions
   58   (@\/hdl\/multiplier@);
   59 
   60 - software - set of binary files that determine:
   61 
   62     - initial state and setting ;
   63 
   64     - a control program;
   65 
   66 - PU model - CAD component that implements PU support (hardware and software
   67   generation, instance generation, computation process scheduling, testing
   68   environment, etc.).
   69 
   70 All three components are hardly related to each other and needed to comply
   71 with each other strictly. For a deeper understanding, a PU developer should
   72 understand all of its components. The multiplier model will be described
   73 above.
   74 
   75 == Processor unit model
   76 
   77 A model purpose is "teaching" CAD how to work with the PU:
   78 
   79 - Which functions can be evaluated by PU? (see
   80   'NITTA.Model.ProcessorUnits.Types.ProcessorUnit')?
   81 
   82 - How to control PU for evaluating specific functions (see
   83   'NITTA.Model.ProcessorUnits.Types.ProcessorUnit',
   84   'NITTA.Model.ProcessorUnits.Types.Controllable')?
   85 
   86 - How to translating instructions to microcode (see
   87   'NITTA.Model.ProcessorUnits.Types.UnambiguouslyDecode')?
   88 
   89 - What are the options of PU synthesis decision available? (see
   90   'NITTA.Model.Problems.Types.ProcessorUnit',
   91   'NITTA.Model.Problems.Types.EndpointDT'):
   92 
   93     - push variable to the PU ('NITTA.Model.Problems.Endpoint.Target');
   94 
   95     - pull at least one variable from the PU ('NITTA.Model.Problems.Endpoint.Source').
   96 
   97 The basis of a PU model is a data structure that represents:
   98 
   99 - PU state during computation process scheduling;
  100 
  101 - process description (full or fragment), which can be translated to microcode.
  102 
  103 Exactly around this data structure, all algorithmic part of the PU model is
  104 developed. The types of the following variables parametrize the data structure:
  105 
  106 - @v@ - variable id (usually 'String');
  107 
  108 - @x@ - a type of processed value (see 'NITTA.Intermediate.Value.Val');
  109 
  110 - @t@ - time moment id (usually 'Int').
  111 
  112 = Multiplier processor unit
  113 
  114 The multiplier processor unit can evaluate the following function type:
  115 
  116 - 'NITTA.Intermediate.Functions.Multiply'.
  117 
  118 Only one function can be processed in one moment, and its execution cannot be
  119 interrupted.
  120 
  121 This module should be considered as a tutorial for the development of other
  122 models of processor units. Its source code is written almost in literature
  123 style, so we recommend to continue reading within the source code.
  124 
  125 == Interaction with multiplier processor unit
  126 
  127 We will consider the example of the computation process scheduling for one
  128 function. To do this, we need to start GHCi interpreter by executing `stack
  129 repl` command from the project directory. After that:
  130 
  131 @
  132 > :l NITTA.Model.ProcessorUnits.Multiplier
  133 [ 1 of 30] Compiling NITTA.Intermediate.Value ( UserspenskoiDocumentsnitta-corpnittasrcNITTAIntermediate/Value.hs, interpreted )
  134 [ 2 of 30] Compiling NITTA.Intermediate.Variable ( UserspenskoiDocumentsnitta-corpnittasrcNITTAIntermediate/Variable.hs, interpreted )
  135 [ 3 of 30] Compiling NITTA.Intermediate.Types ( UserspenskoiDocumentsnitta-corpnittasrcNITTAIntermediate/Types.hs, interpreted )
  136 [ 4 of 30] Compiling NITTA.Model.Problems.Binding ( UserspenskoiDocumentsnitta-corpnittasrcNITTAModelProblemsBinding.hs, interpreted )
  137 [ 5 of 30] Compiling NITTA.Model.Types ( UserspenskoiDocumentsnitta-corpnittasrcNITTAModel/Types.hs, interpreted )
  138 [ 6 of 30] Compiling NITTA.Model.Problems.Endpoint ( UserspenskoiDocumentsnitta-corpnittasrcNITTAModelProblemsEndpoint.hs, interpreted )
  139 [ 7 of 30] Compiling NITTA.Model.Problems.Dataflow ( UserspenskoiDocumentsnitta-corpnittasrcNITTAModelProblemsDataflow.hs, interpreted )
  140 [ 8 of 30] Compiling NITTA.Project.Types ( UserspenskoiDocumentsnitta-corpnittasrcNITTAProject/Types.hs, interpreted )
  141 [ 9 of 30] Compiling NITTA.Utils.Base ( UserspenskoiDocumentsnitta-corpnittasrcNITTAUtils/Base.hs, interpreted )
  142 [10 of 30] Compiling NITTA.Intermediate.Functions.Accum ( UserspenskoiDocumentsnitta-corpnittasrcNITTAIntermediateFunctionsAccum.hs, interpreted )
  143 [11 of 30] Compiling NITTA.Intermediate.Functions ( UserspenskoiDocumentsnitta-corpnittasrcNITTAIntermediate/Functions.hs, interpreted )
  144 [12 of 30] Compiling NITTA.Model.Problems.Refactor ( UserspenskoiDocumentsnitta-corpnittasrcNITTAModelProblemsRefactor.hs, interpreted )
  145 [13 of 30] Compiling NITTA.Model.Problems.Whole ( UserspenskoiDocumentsnitta-corpnittasrcNITTAModelProblemsWhole.hs, interpreted )
  146 [14 of 30] Compiling NITTA.Model.Problems ( UserspenskoiDocumentsnitta-corpnittasrcNITTAModel/Problems.hs, interpreted )
  147 [15 of 30] Compiling NITTA.Utils.CodeFormat ( UserspenskoiDocumentsnitta-corpnittasrcNITTAUtils/CodeFormat.hs, interpreted )
  148 [16 of 30] Compiling NITTA.Model.ProcessorUnits.Types ( UserspenskoiDocumentsnitta-corpnittasrcNITTAModelProcessorUnitsTypes.hs, interpreted )
  149 [17 of 30] Compiling NITTA.Utils      ( UserspenskoiDocumentsnitta-corpnittasrcNITTAUtils.hs, interpreted )
  150 [18 of 30] Compiling NITTA.Project.VerilogSnippets ( UserspenskoiDocumentsnitta-corpnittasrcNITTAProject/Snippets.hs, interpreted )
  151 [19 of 30] Compiling NITTA.Project.Implementation ( UserspenskoiDocumentsnitta-corpnittasrcNITTAProject/Implementation.hs, interpreted )
  152 [20 of 30] Compiling NITTA.Project.Parts.Utils ( UserspenskoiDocumentsnitta-corpnittasrcNITTAProjectPartsUtils.hs, interpreted )
  153 [21 of 30] Compiling NITTA.Project.TestBench ( UserspenskoiDocumentsnitta-corpnittasrcNITTAProjectPartsTestBench.hs, interpreted )
  154 [22 of 30] Compiling NITTA.Project.Parts.TargetSystem ( UserspenskoiDocumentsnitta-corpnittasrcNITTAProjectPartsTargetSystem.hs, interpreted )
  155 [23 of 30] Compiling NITTA.Project.Parts.Icarus ( UserspenskoiDocumentsnitta-corpnittasrcNITTAProjectPartsIcarus.hs, interpreted )
  156 [24 of 30] Compiling NITTA.Model.Networks.Types ( UserspenskoiDocumentsnitta-corpnittasrcNITTAModelNetworksTypes.hs, interpreted )
  157 [25 of 30] Compiling NITTA.Utils.ProcessDescription ( UserspenskoiDocumentsnitta-corpnittasrcNITTAUtils/ProcessDescription.hs, interpreted )
  158 [26 of 30] Compiling NITTA.Model.Networks.Bus ( UserspenskoiDocumentsnitta-corpnittasrcNITTAModelNetworksBus.hs, interpreted )
  159 [27 of 30] Compiling NITTA.Project.Parts.Quartus ( UserspenskoiDocumentsnitta-corpnittasrcNITTAProjectPartsQuartus.hs, interpreted )
  160 [28 of 30] Compiling NITTA.Project.Utils ( UserspenskoiDocumentsnitta-corpnittasrcNITTAProject/Utils.hs, interpreted )
  161 [29 of 30] Compiling NITTA.Project    ( UserspenskoiDocumentsnitta-corpnittasrcNITTAProject.hs, interpreted )
  162 [30 of 30] Compiling NITTA.Model.ProcessorUnits.Multiplier ( UserspenskoiDocumentsnitta-corpnittasrcNITTAModelProcessorUnitsMultiplier.hs, interpreted )
  163 Ok, 30 modules loaded.
  164 > :module +NITTA.Model.ProcessorUnits.Types NITTA.Intermediate.Functions Numeric.Interval.NonEmpty Data.Set Prettyprinter.Render.Text
  165 > :set prompt "ESC[34mλ> ESC[m"
  166 @
  167 
  168 Now create the function and multiplier model initial state. Unfortunately, it
  169 is not enough information for GHC deduction of its type, so let's define its
  170 implicitly.
  171 
  172 >>> :module +Prettyprinter.Render.Text
  173 >>> let f = F.multiply "a" "b" ["c", "d"] :: F String Int
  174 >>> f
  175 a * b = c = d
  176 >>> let st0 = multiplier True :: Multiplier String Int Int
  177 >>> putDoc $ pretty st0
  178 Multiplier:
  179     remain: []
  180     targets: []
  181     sources: []
  182     currentWork: Nothing
  183     isMocked: True
  184     Process:
  185         steps:
  186         relations:
  187         nextTick: 0
  188         nextUid: 0
  189 >>> endpointOptions st0
  190 []
  191 
  192 Bind a function to the multiplier unit. This operation could be executed at
  193 any time of working with a model, including when a computation process is
  194 fully scheduled (new work can be added). The main rules are: 1) if work is
  195 fully scheduled, then it is necessary to perform it, and any part of it
  196 cannot be "lost" inside the model; 2) if a unit has its internal resources,
  197 there should be enough to finish schedule, even it is inefficient.
  198 
  199 >>> let Right st1 = tryBind f st0
  200 >>> putDoc $ pretty st1
  201 Multiplier:
  202     remain: [a * b = c = d]
  203     targets: []
  204     sources: []
  205     currentWork: Nothing
  206     isMocked: True
  207     Process:
  208         steps:
  209         relations:
  210         nextTick: 0
  211         nextUid: 0
  212 >>> endpointOptions st1
  213 [?Target a@(0..INF /P 1..INF),?Target b@(0..INF /P 1..INF)]
  214 
  215 As we can see, after binding, we have two different options of computational
  216 process scheduling that match different argument loading sequences: @a@ or
  217 @b@. We can see that they are similar from an execution sequence point of
  218 view: loading can be started from 0 tick or after an arbitrary delay; for
  219 loading of one argument needed only one tick, but it can continue for an
  220 arbitrary time. Choose the variant.
  221 
  222 >>> let st2 = endpointDecision st1 $ EndpointSt (Target "a") (0...2)
  223 >>> putDoc $ pretty st2
  224 Multiplier:
  225     remain: []
  226     targets: ["b"]
  227     sources: ["c","d"]
  228     currentWork: Just a * b = c = d
  229     isMocked: True
  230     Process:
  231         steps:
  232             0) Step {pID = 0, pInterval = 0 ... 2, pDesc = Endpoint: Target a}
  233             1) Step {pID = 1, pInterval = 0 ... 2, pDesc = Instruction: Load}
  234         relations:
  235             0) Vertical {vUp = 0, vDown = 1}
  236         nextTick: 3
  237         nextUid: 2
  238 >>> mapM_ print $ endpointOptions st2
  239 ?Target b@(3..INF /P 1..INF)
  240 >>> let st3 = endpointDecision st2 $ EndpointSt (Target "b") (3...3)
  241 >>> putDoc $ pretty st3
  242 Multiplier:
  243     remain: []
  244     targets: []
  245     sources: ["c","d"]
  246     currentWork: Just a * b = c = d
  247     isMocked: True
  248     Process:
  249         steps:
  250             0) Step {pID = 0, pInterval = 0 ... 2, pDesc = Endpoint: Target a}
  251             1) Step {pID = 1, pInterval = 0 ... 2, pDesc = Instruction: Load}
  252             2) Step {pID = 2, pInterval = 3 ... 3, pDesc = Endpoint: Target b}
  253             3) Step {pID = 3, pInterval = 3 ... 3, pDesc = Instruction: Load}
  254         relations:
  255             0) Vertical {vUp = 2, vDown = 3}
  256             1) Vertical {vUp = 0, vDown = 1}
  257         nextTick: 4
  258         nextUid: 4
  259 >>> mapM_ print $ endpointOptions st3
  260 ?Source c,d@(6..INF /P 1..INF)
  261 
  262 After loading both arguments, we can see that the next option is unloading
  263 @c@ and @d@ variables. Note, these variables can be unloaded either
  264 concurrently or sequentially (for details, see how the multiplier works
  265 inside). Consider the second option:
  266 
  267 >>> let st4 = endpointDecision st3 $ EndpointSt (Source $ S.fromList ["c"]) (6...6)
  268 >>> putDoc $ pretty st4
  269 Multiplier:
  270     remain: []
  271     targets: []
  272     sources: ["d"]
  273     currentWork: Just a * b = c = d
  274     isMocked: True
  275     Process:
  276         steps:
  277             0) Step {pID = 0, pInterval = 0 ... 2, pDesc = Endpoint: Target a}
  278             1) Step {pID = 1, pInterval = 0 ... 2, pDesc = Instruction: Load}
  279             2) Step {pID = 2, pInterval = 3 ... 3, pDesc = Endpoint: Target b}
  280             3) Step {pID = 3, pInterval = 3 ... 3, pDesc = Instruction: Load}
  281             4) Step {pID = 4, pInterval = 6 ... 6, pDesc = Endpoint: Source c}
  282             5) Step {pID = 5, pInterval = 6 ... 6, pDesc = Instruction: Out}
  283         relations:
  284             0) Vertical {vUp = 4, vDown = 5}
  285             1) Vertical {vUp = 2, vDown = 3}
  286             2) Vertical {vUp = 0, vDown = 1}
  287         nextTick: 7
  288         nextUid: 6
  289 >>> mapM_ print $ endpointOptions st4
  290 ?Source d@(7..INF /P 1..INF)
  291 >>> let st5 = endpointDecision st4 $ EndpointSt (Source $ S.fromList ["d"]) (7...7)
  292 >>> putDoc $ pretty st5
  293 Multiplier:
  294     remain: []
  295     targets: []
  296     sources: []
  297     currentWork: Nothing
  298     isMocked: True
  299     Process:
  300         steps:
  301             0) Step {pID = 0, pInterval = 0 ... 2, pDesc = Endpoint: Target a}
  302             1) Step {pID = 1, pInterval = 0 ... 2, pDesc = Instruction: Load}
  303             2) Step {pID = 2, pInterval = 3 ... 3, pDesc = Endpoint: Target b}
  304             3) Step {pID = 3, pInterval = 3 ... 3, pDesc = Instruction: Load}
  305             4) Step {pID = 4, pInterval = 6 ... 6, pDesc = Endpoint: Source c}
  306             5) Step {pID = 5, pInterval = 6 ... 6, pDesc = Instruction: Out}
  307             6) Step {pID = 6, pInterval = 7 ... 7, pDesc = Endpoint: Source d}
  308             7) Step {pID = 7, pInterval = 7 ... 7, pDesc = Instruction: Out}
  309             8) Step {pID = 8, pInterval = 0 ... 7, pDesc = Intermediate: a * b = c = d}
  310         relations:
  311             0) Vertical {vUp = 8, vDown = 6}
  312             1) Vertical {vUp = 8, vDown = 4}
  313             2) Vertical {vUp = 8, vDown = 2}
  314             3) Vertical {vUp = 8, vDown = 0}
  315             4) Vertical {vUp = 6, vDown = 7}
  316             5) Vertical {vUp = 4, vDown = 5}
  317             6) Vertical {vUp = 2, vDown = 3}
  318             7) Vertical {vUp = 0, vDown = 1}
  319         nextTick: 8
  320         nextUid: 9
  321 >>> endpointOptions st5
  322 []
  323 
  324 All options of computing process scheduling are run out. All bound functions
  325 are planned. Further microcode can be generated, which can be organizing the
  326 described computational process on the multiplier.
  327 -}
  328 module NITTA.Model.ProcessorUnits.Multiplier (
  329     multiplier,
  330     Multiplier,
  331     Ports (..),
  332     IOPorts (..),
  333 ) where
  334 
  335 import Control.Monad (when)
  336 import Data.Default
  337 import Data.List (find, partition, (\\))
  338 import Data.Maybe
  339 import Data.Set qualified as S
  340 import Data.String.Interpolate
  341 import Data.String.ToString
  342 import NITTA.Intermediate.Functions qualified as F
  343 import NITTA.Intermediate.Types
  344 import NITTA.Model.Problems
  345 import NITTA.Model.ProcessorUnits.Types
  346 import NITTA.Model.Time
  347 import NITTA.Project
  348 import NITTA.Utils
  349 import NITTA.Utils.ProcessDescription
  350 import Numeric.Interval.NonEmpty (inf, sup, (...))
  351 import Prettyprinter
  352 
  353 {- | It is a PU model state representation, which describes each state of
  354 synthesis model for that PU.
  355 -}
  356 data Multiplier v x t = Multiplier
  357     { remain :: [F v x]
  358     -- ^ List of the assigned but not processed functions. To execute a
  359     --  function:
  360     --
  361     --  - removing the function from this list;
  362     --
  363     --  - transfering information from function to 'targets' and 'sources'
  364     --    fields.
  365     --
  366     --  An assigned function can be executed in random order.
  367     , targets :: [v]
  368     -- ^ List of variables, which is needed to push to the PU for current
  369     --  function evaluation.
  370     , sources :: [v]
  371     -- ^ List of variables, which is needed to pull from PU for current
  372     --  function evaluation. Pull order is arbitrary. All pulled variables
  373     --  correspond to the same value (same result).
  374     , currentWork :: Maybe (F v x)
  375     -- ^ Current work, if some function is executed.
  376     , process_ :: Process t (StepInfo v x t)
  377     -- ^ Description of scheduled computation process
  378     --  ('NITTA.Model.ProcessorUnits.Types').
  379     , isMocked :: Bool
  380     -- ^ HDL implementation of PU contains a multiplier IP core from Altera.
  381     --  Icarus Verilog can not simulate it. If `isMocked` is set, a target
  382     --  system will be contained non-synthesizable implementation of that
  383     --  IP-core.
  384     }
  385 
  386 instance VarValTime v x t => Pretty (Multiplier v x t) where
  387     pretty Multiplier{remain, targets, sources, currentWork, process_, isMocked} =
  388         [__i|
  389             Multiplier:
  390                 remain: #{ remain }
  391                 targets: #{ map toString targets }
  392                 sources: #{ map toString sources }
  393                 currentWork: #{ currentWork }
  394                 isMocked: #{ isMocked }
  395                 #{ nest 4 $ pretty process_ }
  396             |]
  397 
  398 {- | Multiplier PU model constructor. Argument defines the computation unit's
  399 internal organization: using multiplier IP kernel (False) or mock (True). For
  400 more information, look hardware function in 'TargetSystemComponent' class.
  401 -}
  402 multiplier mock =
  403     Multiplier
  404         { remain = []
  405         , targets = []
  406         , sources = []
  407         , currentWork = Nothing
  408         , process_ = def
  409         , isMocked = mock
  410         }
  411 
  412 -- | Default initial state of multiplier PU model.
  413 instance Time t => Default (Multiplier v x t) where
  414     def = multiplier True
  415 
  416 instance Default x => DefaultX (Multiplier v x t) x
  417 
  418 {- | This class is allowed to extract all bound functions. It has a very simple
  419 implementation: we take process description (all planned functions), and
  420 function in progress, if it is.
  421 -}
  422 instance Ord t => WithFunctions (Multiplier v x t) (F v x) where
  423     functions Multiplier{process_, remain, currentWork} =
  424         functions process_
  425             ++ remain
  426             ++ maybeToList currentWork
  427 
  428 {- | Tracking internal dependencies on the processed variables. It includes:
  429 
  430 - dependencies between inputs and outputs of currently evaluated function;
  431 
  432 - dependencies of all remain functions from the currently evaluated function
  433   (if it is).
  434 -}
  435 instance Var v => Locks (Multiplier v x t) v where
  436     locks Multiplier{remain, sources, targets} =
  437         [ Lock{lockBy, locked}
  438         | locked <- sources
  439         , lockBy <- targets
  440         ]
  441             ++ [ Lock{lockBy, locked}
  442                | locked <- concatMap (S.elems . variables) remain
  443                , lockBy <- sources ++ targets
  444                ]
  445             ++ concatMap locks remain
  446 
  447 {- | That type classes ('BreakLoopProblem', 'OptimizeAccumProblem',
  448 'ResolveDeadlockProblem', 'ConstantFoldingProblem') describes the possibility of PU to modify an
  449 algorithm. Empty implementation means that multiplier PU doesn't have such
  450 possibilities.
  451 -}
  452 instance BreakLoopProblem (Multiplier v x t) v x
  453 
  454 instance ConstantFoldingProblem (Multiplier v x t) v x
  455 instance OptimizeAccumProblem (Multiplier v x t) v x
  456 instance ResolveDeadlockProblem (Multiplier v x t) v x
  457 
  458 {- | This type class specifies how to bind functions to the PU. If it is
  459 possible, @tryBind@ function will return @Right@ value with a new PU model
  460 state. If not, @Left@ value with reason description. And also specify how to
  461 get computation process description.
  462 
  463 From the CAD point of view, bind looks like:
  464 
  465 - CAD asks PU models: "Who can evaluate this function?" and get the list of
  466   possible bindings.
  467 
  468 - CAD, based on the different metrics (see 'NITTA.Synthesis'), the best variant
  469   is chosen.
  470 
  471 Binding can be done either gradually due synthesis process at the start.
  472 -}
  473 instance VarValTime v x t => ProcessorUnit (Multiplier v x t) v x t where
  474     tryBind f pu@Multiplier{remain}
  475         | Just F.Multiply{} <- castF f = Right pu{remain = f : remain}
  476         | otherwise = Left $ "The function is unsupported by Multiplier: " ++ show f
  477 
  478     -- Unified interface for getting computation process description.
  479     process = process_
  480 
  481 -- | Execute function (set as current and remove from remain).
  482 execution pu@Multiplier{targets = [], sources = [], remain} f
  483     | Just (F.Multiply (I a) (I b) (O c)) <- castF f =
  484         pu
  485             { targets = [a, b]
  486             , currentWork = Just f
  487             , sources = S.elems c
  488             , remain = remain \\ [f]
  489             }
  490 execution _ _ = error "Multiplier: internal execution error."
  491 
  492 {- | A computational process of PU from a hardware architectural perspective can
  493 be described as a sequence of pushing and pulling values. From a synthesis
  494 perspective, it is represented by 'EndpointProblem', which describes when PU
  495 is a 'Source' or 'Target' of data transfers.
  496 
  497 Work with endpoint problem implemented by only two functions:
  498 
  499 __endpointOptions__ define what the possible synthesis decision is. It
  500 includes three cases:
  501 
  502 - Not a function is executed. That means that we have options to push any
  503   input variables of remain functions.
  504 
  505 - The function is executed, and not all arguments are received. We have
  506   options to push remain variables.
  507 
  508 - The function is executed, and all arguments are received. We have options
  509   to pull the result from the multiplier, which can include several
  510   variables. These variables can be got one by one or all at once because the
  511   value will be written to the bus and read by several processor units on the
  512   hardware level.
  513 
  514 Note: an option don't specify moment for action but specify an available
  515 interval ('NITTA.Model.Types.TimeConstraint'). That describes the interval for
  516 action start and restriction on process duration.
  517 
  518 __endpointDecision__ defines how to apply synthesis decision to the PU model.
  519 It includes three cases:
  520 
  521 - Push an input variable of the executed function. We need to schedule
  522   instruction for endpoint action and modify the model state.
  523 
  524 - Pull an output variable or variables of the executed function. We need to
  525   schedule instruction for endpoint action and modify the model state.
  526 
  527 - Push an input variable of a not executed function. In this case, we need to
  528   find the selected function, 'execute' it, and do a recursive call with the
  529   same decision.
  530 -}
  531 instance VarValTime v x t => EndpointProblem (Multiplier v x t) v t where
  532     endpointOptions pu@Multiplier{targets}
  533         | not $ null targets =
  534             let at = nextTick pu ... maxBound
  535                 duration = 1 ... maxBound
  536              in map (\v -> EndpointSt (Target v) $ TimeConstraint at duration) targets
  537     endpointOptions Multiplier{sources, currentWork = Just f, process_}
  538         | not $ null sources =
  539             let doneAt = inputsPushedAt process_ f + 3
  540                 at = max doneAt (nextTick process_) ... maxBound
  541                 duration = 1 ... maxBound
  542              in [EndpointSt (Source $ S.fromList sources) $ TimeConstraint at duration]
  543     endpointOptions pu@Multiplier{remain} = concatMap (endpointOptions . execution pu) remain
  544 
  545     endpointDecision pu@Multiplier{targets} d@EndpointSt{epRole = Target v, epAt}
  546         | not $ null targets
  547         , ([_], targets') <- partition (== v) targets
  548         , --  Computation process planning is carried out.
  549           let process_' = execSchedule pu $ do
  550                 -- this is required for correct work of automatically generated tests,
  551                 -- that takes information about time from Process
  552                 scheduleEndpoint d $ scheduleInstructionUnsafe epAt Load =
  553             pu
  554                 { process_ = process_'
  555                 , -- The remainder of the work is saved for the next loop
  556                   targets = targets'
  557                 }
  558     endpointDecision pu@Multiplier{targets = [], sources, currentWork = Just f, process_} d@EndpointSt{epRole = Source v, epAt}
  559         | not $ null sources
  560         , let sources' = sources \\ S.elems v
  561         , sources' /= sources
  562         , let a = inf $ stepsInterval $ relatedEndpoints process_ $ variables f
  563         , -- Compututation process planning is carring on.
  564           let process_' = execSchedule pu $ do
  565                 endpoints <- scheduleEndpoint d $ scheduleInstructionUnsafe epAt Out
  566                 when (null sources') $ do
  567                     -- Set up the vertical relantions between functional unit
  568                     -- and related to that data sending.
  569 
  570                     -- FIXME: here ([]) you can see the source of error.
  571                     -- Function don't connected to bind step. It should be fixed.
  572                     scheduleFunctionFinish_ [] f $ a ... sup epAt
  573                 -- this is needed to correct work of automatically generated tests
  574                 -- that takes time about time from Process
  575                 return endpoints =
  576             pu
  577                 { process_ = process_'
  578                 , -- In case if not all variables what asked - remaining are saved.
  579                   sources = sources'
  580                 , -- if all of works is done, then time when result is ready,
  581                   -- current work and data transfering, what is done is the current function is reset.
  582                   currentWork = if null sources' then Nothing else Just f
  583                 }
  584     endpointDecision pu@Multiplier{targets = [], sources = [], remain} d
  585         | let v = oneOf $ variables d
  586         , Just f <- find (\f -> v `S.member` variables f) remain =
  587             endpointDecision (execution pu f) d
  588     -- If something went wrong.
  589     endpointDecision pu d = error [i|incorrect decision #{ d } for #{ pretty pu }|]
  590 
  591 {- | For each PU, we can specify the instruction set and microcode, which allows
  592 us to control the PU at the hardware level.
  593 
  594 - instructions set describes a computation process from a programmer point of
  595   view;
  596 
  597 - microcode describes the structure of processors that controls signals.
  598 
  599 The implementation had the internal register, which allows us to simply push the
  600 data in the unit, without any specification of argument position. It will be
  601 always a sequence of the first and second arguments.
  602 -}
  603 instance Controllable (Multiplier v x t) where
  604     data Instruction (Multiplier v x t)
  605         = Load
  606         | Out
  607         deriving (Show)
  608 
  609     data Microcode (Multiplier v x t) = Microcode
  610         { -- \| Write to mUnit signal.
  611           wrSignal :: Bool
  612         , -- \| Downloading from mUnit signal.
  613           oeSignal :: Bool
  614         }
  615         deriving (Show, Eq, Ord)
  616 
  617     zipSignalTagsAndValues MultiplierPorts{..} Microcode{..} =
  618         [ (wr, Bool wrSignal)
  619         , (oe, Bool oeSignal)
  620         ]
  621 
  622     usedPortTags MultiplierPorts{wr, oe} = [wr, oe]
  623 
  624     takePortTags (wr : oe : _) _ = MultiplierPorts wr oe
  625     takePortTags _ _ = error "can not take port tags, tags are over"
  626 
  627 {- | Default microcode state should be equal to @nop@ function, which should be a
  628 safe way to do nothing (not take a bus, not change internal PU state, etc.).
  629 -}
  630 instance Default (Microcode (Multiplier v x t)) where
  631     def =
  632         Microcode
  633             { wrSignal = False
  634             , oeSignal = False
  635             }
  636 
  637 {- | Instruction and microcode should have exact matching, which allows us to
  638 translate PU instructions to microcode value.
  639 -}
  640 instance UnambiguouslyDecode (Multiplier v x t) where
  641     decodeInstruction Load = def{wrSignal = True}
  642     decodeInstruction Out = def{oeSignal = True}
  643 
  644 {- | Processor unit control signal ports. In
  645 'NITTA.Model.Networks.Bus.BusNetwork', these ports are directly connecting to
  646 @ControlUnit@.
  647 -}
  648 instance Connected (Multiplier v x t) where
  649     data Ports (Multiplier v x t) = MultiplierPorts
  650         { -- \|get data from the bus (data_in)
  651           wr :: SignalTag
  652         , -- \|send result to the bus
  653           oe :: SignalTag
  654         }
  655         deriving (Show)
  656 
  657 instance IOConnected (Multiplier v x t) where
  658     data IOPorts (Multiplier v x t) = MultiplierIO
  659         deriving (Show)
  660 
  661 {- | Usage of PU requires some artifacts of a synthesis process:
  662 
  663 - Hardware implementation, which depends from 'isMocked' value:
  664 
  665 - Software (not needed for the multiplier because it does not have any
  666   configuration and is controlled from the network level).
  667 
  668 - Hardware instance in the upper structure element.
  669 -}
  670 instance VarValTime v x t => TargetSystemComponent (Multiplier v x t) where
  671     moduleName _title _pu = "pu_multiplier"
  672 
  673     hardware _tag Multiplier{isMocked} =
  674         Aggregate
  675             Nothing
  676             [ if isMocked
  677                 then FromLibrary "multiplier/mult_mock.v"
  678                 else FromLibrary "multiplier/mult_inner.v"
  679             , FromLibrary "multiplier/pu_multiplier.v"
  680             ]
  681 
  682     software _ _ = Empty
  683 
  684     hardwareInstance
  685         tag
  686         _pu
  687         UnitEnv
  688             { sigClk
  689             , sigRst
  690             , ctrlPorts = Just MultiplierPorts{..}
  691             , valueIn = Just (dataIn, attrIn)
  692             , valueOut = Just (dataOut, attrOut)
  693             } =
  694             [__i|
  695                 pu_multiplier \#
  696                         ( .DATA_WIDTH( #{ dataWidth (def :: x) } )
  697                         , .ATTR_WIDTH( #{ attrWidth (def :: x) } )
  698                         , .SCALING_FACTOR_POWER( #{ fractionalBitSize (def :: x) } )
  699                         , .INVALID( 0 )
  700                         ) #{ tag }
  701                     ( .clk( #{ sigClk } )
  702                     , .rst( #{ sigRst } )
  703                     , .signal_wr( #{ wr } )
  704                     , .data_in( #{ dataIn } )
  705                     , .attr_in( #{ attrIn } )
  706                     , .signal_oe( #{ oe } )
  707                     , .data_out( #{ dataOut } )
  708                     , .attr_out( #{ attrOut } )
  709                     );
  710             |]
  711     hardwareInstance _title _pu _env = error "internal error"
  712 
  713 {- | Empty implementation of 'NITTA.Project.TestBench.IOTestBench' class
  714 means that multiplier, as expected, doesn't have any IO.
  715 -}
  716 instance IOTestBench (Multiplier v x t) v x
  717 
  718 {- | The main purpose of this class is to generate autotests for PU. It allows to
  719 generate testbench for the PU according to its model and scheduled computational
  720 process. You can see tests in @test/Spec.hs@. Testbench contains:
  721 
  722 - The sequence of control signals that implement the already scheduled process.
  723 
  724 - The sequence of bus state checks in which we compare actual values with the
  725   results of the functional simulation.
  726 -}
  727 instance VarValTime v x t => Testable (Multiplier v x t) v x where
  728     testBenchImplementation prj@Project{pName, pUnit} =
  729         Immediate (toString $ moduleName pName pUnit <> "_tb.v") $
  730             snippetTestBench
  731                 prj
  732                 SnippetTestBenchConf
  733                     { -- List of control signals. It is needed to initialize
  734                       -- registers with the same names.
  735                       tbcSignals = ["oe", "wr"]
  736                     , -- A processor unit connects to the environment by signal
  737                       -- lines. In 'NITTA.Project.TestBench.tbcPorts'
  738                       -- describes IDs signal lines of testbench. In
  739                       -- 'NITTA.Project.TestBench.tbcSignalConnect' how
  740                       -- abstract numbers are translate to source code.
  741                       tbcPorts =
  742                         MultiplierPorts
  743                             { oe = SignalTag "oe"
  744                             , wr = SignalTag "wr"
  745                             }
  746                     , -- Map microcode to registers in the testbench.
  747                       tbcMC2verilogLiteral = \Microcode{oeSignal, wrSignal} ->
  748                         [i|oe <= #{bool2verilog oeSignal};|]
  749                             <> [i| wr <= #{bool2verilog wrSignal};|]
  750                     }