never executed always true always false
    1 {-# LANGUAGE FlexibleInstances #-}
    2 {-# LANGUAGE QuasiQuotes #-}
    3 {-# LANGUAGE RecordWildCards #-}
    4 {-# LANGUAGE TypeFamilies #-}
    5 {-# LANGUAGE ViewPatterns #-}
    6 
    7 module NITTA.Model.ProcessorUnits.Multiplexer (
    8     Multiplexer,
    9     multiplexer,
   10     IOPorts (..),
   11 ) where
   12 
   13 import Control.Monad (when)
   14 import Data.Default
   15 import Data.List (find, (\\))
   16 import Data.Maybe (maybeToList)
   17 import Data.Set qualified as S
   18 import Data.String.Interpolate
   19 import Data.String.ToString
   20 import Data.Text qualified as T
   21 import NITTA.Intermediate.Functions qualified as F
   22 import NITTA.Intermediate.Types
   23 import NITTA.Model.Problems
   24 import NITTA.Model.ProcessorUnits.Types
   25 import NITTA.Model.Time
   26 import NITTA.Project
   27 import NITTA.Utils
   28 import NITTA.Utils.ProcessDescription
   29 import Numeric.Interval.NonEmpty hiding (elem, notElem)
   30 import Prettyprinter
   31 
   32 data Multiplexer v x t = Multiplexer
   33     { remain :: [F v x]
   34     , sources :: [v]
   35     , muxSels :: [v]
   36     , targets :: [v]
   37     , currentWork :: Maybe (F v x)
   38     , process_ :: Process t (StepInfo v x t)
   39     }
   40 
   41 instance Default x => DefaultX (Multiplexer v x t) x
   42 
   43 instance Time t => Default (Multiplexer v x t) where
   44     def = multiplexer
   45 
   46 instance VarValTime v x t => Pretty (Multiplexer v x t) where
   47     pretty Multiplexer{remain, targets, sources, currentWork, process_, muxSels} =
   48         [__i|
   49             Multiplexer:
   50                 remain: #{ remain }
   51                 targets: #{ map toString targets }
   52                 muxSels: #{ map toString muxSels }
   53                 sources: #{ map toString sources }
   54                 currentWork: #{ currentWork }
   55                 #{ nest 4 $ pretty process_ }
   56             |]
   57 
   58 multiplexer :: Time t => Multiplexer v x t
   59 multiplexer =
   60     Multiplexer
   61         { remain = []
   62         , sources = []
   63         , muxSels = []
   64         , targets = []
   65         , currentWork = Nothing
   66         , process_ = def
   67         }
   68 
   69 selWidth :: Int
   70 selWidth = 4
   71 instance VarValTime v x t => ProcessorUnit (Multiplexer v x t) v x t where
   72     tryBind f pu@Multiplexer{remain}
   73         | Just F.Mux{} <- castF f =
   74             Right
   75                 pu
   76                     { remain = f : remain
   77                     }
   78         | otherwise = Left "Unsupported function type for Multiplexer"
   79 
   80     process = process_
   81 
   82 instance Connected (Multiplexer v x t) where
   83     data Ports (Multiplexer v x t) = MultiplexerPorts
   84         { dataInPort :: SignalTag
   85         , selPort :: SignalTag
   86         , outPort :: SignalTag
   87         }
   88 
   89 instance Controllable (Multiplexer v x t) where
   90     data Instruction (Multiplexer v x t)
   91         = LoadInput
   92         | LoadSel
   93         | Out
   94         deriving (Show, Eq)
   95 
   96     data Microcode (Multiplexer v x t) = MuxMicrocode
   97         { dataInActive :: Bool
   98         , selActive :: Bool
   99         , outActive :: Bool
  100         }
  101 
  102     zipSignalTagsAndValues MultiplexerPorts{..} MuxMicrocode{..} =
  103         [ (dataInPort, Bool dataInActive)
  104         , (selPort, Bool selActive)
  105         , (outPort, Bool outActive)
  106         ]
  107     usedPortTags MultiplexerPorts{..} = [dataInPort, selPort, outPort]
  108 
  109     takePortTags (oe : wr : sel : _) _ = MultiplexerPorts oe wr sel
  110     takePortTags _ _ = error "can not take port tags, tags are over"
  111 
  112 instance VarValTime v x t => EndpointProblem (Multiplexer v x t) v t where
  113     endpointOptions pu@Multiplexer{sources, muxSels, targets}
  114         | not (null targets) || not (null muxSels) =
  115             let at = nextTick pu ... maxBound
  116                 duration = 1 ... maxBound
  117              in [EndpointSt (Target $ head $ targets ++ muxSels) $ TimeConstraint at duration]
  118         | not $ null sources =
  119             let doneAt = nextTick (process_ pu) + 2
  120                 at = doneAt ... maxBound
  121                 duration = 1 ... maxBound
  122              in [EndpointSt (Source $ S.fromList sources) $ TimeConstraint at duration]
  123         | otherwise = concatMap (endpointOptions . execution pu) (remain pu)
  124 
  125     endpointDecision pu@Multiplexer{muxSels, targets} d@EndpointSt{epRole = Target v, epAt}
  126         | v `elem` targets =
  127             let process_' = execSchedule pu $ do
  128                     scheduleEndpoint d $ scheduleInstructionUnsafe epAt LoadInput
  129              in pu
  130                     { targets = filter (/= v) targets
  131                     , process_ = process_'
  132                     , muxSels = muxSels
  133                     }
  134         | v `elem` muxSels =
  135             let process_' = execSchedule pu $ do
  136                     scheduleEndpoint d $ scheduleInstructionUnsafe epAt LoadSel
  137              in pu
  138                     { muxSels = filter (/= v) muxSels
  139                     , process_ = process_'
  140                     , targets = targets
  141                     }
  142     endpointDecision pu@Multiplexer{sources, currentWork = Just f} d@EndpointSt{epRole = Source vs, epAt}
  143         | not $ null sources =
  144             let sources' = sources \\ S.elems vs
  145                 process_' = execSchedule pu $ do
  146                     _ <- scheduleEndpoint d $ scheduleInstructionUnsafe epAt Out
  147                     when (null sources') $ do
  148                         let a = inf $ stepsInterval $ relatedEndpoints (process_ pu) (variables f)
  149                         scheduleFunctionFinish_ [] f (a ... sup epAt)
  150              in pu
  151                     { sources = sources'
  152                     , process_ = process_'
  153                     , currentWork = if null sources' then Nothing else Just f
  154                     }
  155     endpointDecision pu@Multiplexer{targets = [], sources = [], muxSels = [], remain} d
  156         | let v = oneOf $ variables d
  157         , Just f <- find (\f -> v `S.member` variables f) remain =
  158             endpointDecision (execution pu f) d
  159     endpointDecision pu d = error [i|incorrect decision #{ d } for #{ pretty pu }|]
  160 
  161 execution pu@Multiplexer{targets = [], sources = [], muxSels = [], remain} f
  162     | Just (F.Mux a b (O c)) <- castF f =
  163         pu
  164             { sources = S.elems c
  165             , muxSels = [(\(I v) -> v) a]
  166             , targets = map (\(I v) -> v) b
  167             , remain = filter (/= f) remain
  168             , currentWork = Just f
  169             }
  170 execution _ f = error $ "Multiplexer execution error. Expected Mux, got: " ++ show f
  171 
  172 instance Var v => Locks (Multiplexer v x t) v where
  173     locks Multiplexer{targets, muxSels, sources} =
  174         [ Lock lockBy locked
  175         | locked <- sources
  176         , lockBy <- targets ++ muxSels
  177         ]
  178 instance VarValTime v x t => TargetSystemComponent (Multiplexer v x t) where
  179     moduleName _ _ = T.pack "pu_multiplexer"
  180 
  181     hardware _tag _pu = FromLibrary "pu_multiplexer.v"
  182     software _ _ = Empty
  183 
  184     hardwareInstance
  185         tag
  186         _pu
  187         UnitEnv
  188             { sigClk
  189             , sigRst
  190             , ctrlPorts = Just MultiplexerPorts{..}
  191             , valueIn = Just (dataIn, attrIn)
  192             , valueOut = Just (dataOut, attrOut)
  193             } =
  194             [__i|
  195         pu_multiplexer \#
  196                 ( .DATA_WIDTH( #{ dataWidth (def :: x) } )
  197                 , .ATTR_WIDTH( #{ attrWidth (def :: x) } )
  198                 , .SEL_WIDTH( #{ selWidth} )
  199                 ) #{ tag } (
  200             .clk(#{ sigClk }),
  201             .rst(#{ sigRst }),
  202             .signal_wr(#{ dataInPort }),
  203             .signal_sel(#{ selPort }),
  204             .signal_oe(#{ outPort }),
  205 
  206             .data_in( #{ dataIn } ),
  207             .attr_in( #{ attrIn } ),
  208             .data_out(#{ dataOut }),
  209             .attr_out(#{ attrOut })
  210         );|]
  211     hardwareInstance _title _pu _env = error "internal error"
  212 
  213 instance IOConnected (Multiplexer v x t) where
  214     data IOPorts (Multiplexer v x t) = MultiplexerIO
  215         deriving (Show)
  216 
  217 instance BreakLoopProblem (Multiplexer v x t) v x
  218 
  219 instance ConstantFoldingProblem (Multiplexer v x t) v x
  220 
  221 instance OptimizeAccumProblem (Multiplexer v x t) v x
  222 
  223 instance ResolveDeadlockProblem (Multiplexer v x t) v x
  224 
  225 instance IOTestBench (Multiplexer v x t) v x
  226 
  227 instance OptimizeLogicalUnitProblem (Multiplexer v x t) v x
  228 
  229 instance Default (Microcode (Multiplexer v x t)) where
  230     def =
  231         MuxMicrocode
  232             { dataInActive = False
  233             , selActive = False
  234             , outActive = False
  235             }
  236 
  237 instance UnambiguouslyDecode (Multiplexer v x t) where
  238     decodeInstruction Out = def{outActive = True, selActive = False, dataInActive = False}
  239     decodeInstruction LoadInput = def{dataInActive = True, outActive = False, selActive = False}
  240     decodeInstruction LoadSel = def{selActive = True, outActive = False, dataInActive = False}
  241 
  242 instance VarValTime v x t => WithFunctions (Multiplexer v x t) (F v x) where
  243     functions Multiplexer{process_, remain, currentWork} =
  244         functions process_ ++ remain ++ maybeToList currentWork
  245 
  246 instance VarValTime v x t => Testable (Multiplexer v x t) v x where
  247     testBenchImplementation prj@Project{pName, pUnit} =
  248         let tbcSignalsConst = map T.pack ["signal_wr", "signal_sel", "signal_oe"]
  249             showMicrocode MuxMicrocode{..} =
  250                 [i|signal_wr <= #{ bool2verilog dataInActive };|]
  251                     <> [i| signal_sel <= #{ bool2verilog selActive };|]
  252                     <> [i| signal_oe <= #{ bool2verilog outActive };|]
  253          in Immediate (toString $ moduleName pName pUnit <> T.pack "_tb.v") $
  254                 snippetTestBench
  255                     prj
  256                     SnippetTestBenchConf
  257                         { tbcSignals = tbcSignalsConst
  258                         , tbcPorts =
  259                             MultiplexerPorts
  260                                 { dataInPort = SignalTag (T.pack "signal_wr")
  261                                 , selPort = SignalTag (T.pack "signal_sel")
  262                                 , outPort = SignalTag (T.pack "signal_oe")
  263                                 }
  264                         , tbcMC2verilogLiteral = showMicrocode
  265                         }