never executed always true always false
    1 {-# LANGUAGE AllowAmbiguousTypes #-}
    2 {-# LANGUAGE ConstraintKinds #-}
    3 {-# LANGUAGE DataKinds #-}
    4 {-# LANGUAGE DuplicateRecordFields #-}
    5 {-# LANGUAGE OverloadedStrings #-}
    6 
    7 {-# OPTIONS -fno-warn-orphans #-}
    8 
    9 {- |
   10 Module      : NITTA.UIBackend.ViewHelper
   11 Description : Types for marshaling data for REST API
   12 Copyright   : (c) Aleksandr Penskoi, 2021
   13 License     : BSD3
   14 Maintainer  : aleksandr.penskoi@gmail.com
   15 Stability   : experimental
   16 
   17 We can not autogenerate ToJSON implementation for some types, so we add helper
   18 types for doing that automatically. Why do we need to generate `ToJSON`
   19 automatically? We don't want to achieve consistency between client and server
   20 manually.
   21 -}
   22 module NITTA.UIBackend.ViewHelper (
   23     module NITTA.UIBackend.ViewHelperCls,
   24     module NITTA.Model.Problems.ViewHelper,
   25     FView (..),
   26     Viewable (..),
   27     viewNodeTree,
   28     TreeView,
   29     ShortNodeView,
   30     NodeView,
   31     StepInfoView (..),
   32     VarValTimeJSON,
   33 ) where
   34 
   35 import Control.Concurrent.STM
   36 import Data.Aeson
   37 import Data.HashMap.Strict qualified as HM
   38 import Data.Maybe
   39 import Data.Set qualified as S
   40 import Data.Text qualified as T
   41 import Data.Typeable
   42 import GHC.Generics
   43 import NITTA.Intermediate.Types
   44 import NITTA.Model.Problems
   45 import NITTA.Model.Problems.ViewHelper
   46 import NITTA.Model.ProcessorUnits
   47 import NITTA.Model.TargetSystem
   48 import NITTA.Project.TestBench
   49 import NITTA.Synthesis.Analysis
   50 import NITTA.Synthesis.Steps
   51 import NITTA.Synthesis.Types
   52 import NITTA.UIBackend.ViewHelperCls
   53 import NITTA.Utils.Base
   54 import Numeric.Interval.NonEmpty
   55 import Servant.Docs
   56 
   57 -- Synthesis tree
   58 
   59 data TreeView a = TreeNodeView
   60     { rootLabel :: a
   61     , subForest :: [TreeView a]
   62     }
   63     deriving (Generic, Show)
   64 
   65 instance ToJSON a => ToJSON (TreeView a)
   66 
   67 instance ToSample (TreeView ShortNodeView) where
   68     toSamples _ =
   69         singleSample $
   70             TreeNodeView
   71                 { rootLabel =
   72                     ShortNodeView
   73                         { sid = showText $ Sid []
   74                         , isTerminal = False
   75                         , isFinish = False
   76                         , isProcessed = True
   77                         , duration = 0
   78                         , score = 0 / 0
   79                         , decsionType = "-"
   80                         }
   81                 , subForest =
   82                     [ TreeNodeView
   83                         { rootLabel =
   84                             ShortNodeView
   85                                 { sid = showText $ Sid [0]
   86                                 , isTerminal = False
   87                                 , isFinish = False
   88                                 , isProcessed = False
   89                                 , duration = 0
   90                                 , score = 4052
   91                                 , decsionType = "Bind"
   92                                 }
   93                         , subForest = []
   94                         }
   95                     , TreeNodeView
   96                         { rootLabel =
   97                             ShortNodeView
   98                                 { sid = showText $ Sid [1]
   99                                 , isTerminal = False
  100                                 , isFinish = False
  101                                 , isProcessed = False
  102                                 , duration = 0
  103                                 , score = 3021
  104                                 , decsionType = "Bind"
  105                                 }
  106                         , subForest = []
  107                         }
  108                     ]
  109                 }
  110 
  111 instance ToSample Integer where
  112     toSamples _ =
  113         singleSample 0
  114 
  115 data ShortNodeView = ShortNodeView
  116     { sid :: T.Text
  117     , isTerminal :: Bool
  118     , isFinish :: Bool
  119     , isProcessed :: Bool
  120     , duration :: Int
  121     , score :: Float
  122     , decsionType :: T.Text
  123     }
  124     deriving (Generic, Show)
  125 
  126 data NodeInfo = NodeInfo
  127     { sid :: String
  128     , isTerminal :: Bool
  129     , isProcessed :: Bool
  130     , duration :: Int
  131     , score :: Float
  132     , decsionType :: String
  133     }
  134     deriving (Generic, Show)
  135 
  136 instance ToJSON ShortNodeView
  137 instance ToJSON TreeInfo
  138 
  139 instance ToSample TreeInfo where
  140     toSamples _ =
  141         singleSample mempty
  142 
  143 viewNodeTree tree@Tree{sID = sid, sDecision, sSubForestVar} = do
  144     subForestM <- atomically $ tryReadTMVar sSubForestVar
  145     subForest <- maybe (return []) (mapM viewNodeTree) subForestM
  146     return
  147         TreeNodeView
  148             { rootLabel =
  149                 ShortNodeView
  150                     { sid = showText sid
  151                     , isTerminal = isLeaf tree
  152                     , isFinish = isComplete tree
  153                     , isProcessed = isJust subForestM
  154                     , duration = (fromEnum . processDuration . sTarget . sState) tree
  155                     , score = read "NaN" -- maybe (read "NaN") eObjectiveFunctionValue nOrigin
  156                     , decsionType = case sDecision of
  157                         Root{} -> "root"
  158                         SynthesisDecision{metrics}
  159                             | Just AllocationMetrics{} <- cast metrics -> "Allocation"
  160                             | Just SingleBindMetrics{} <- cast metrics -> "SingleBind"
  161                             | Just GroupBindMetrics{} <- cast metrics -> "GroupBind"
  162                             | Just BreakLoopMetrics{} <- cast metrics -> "Refactor"
  163                             | Just ConstantFoldingMetrics{} <- cast metrics -> "Refactor"
  164                             | Just DataflowMetrics{} <- cast metrics -> "Transport"
  165                             | Just OptimizeAccumMetrics{} <- cast metrics -> "Refactor"
  166                             | Just ResolveDeadlockMetrics{} <- cast metrics -> "Refactor"
  167                         _ -> "?"
  168                     }
  169             , subForest = subForest
  170             }
  171 
  172 data NodeView tag v x t = NodeView
  173     { sid :: T.Text
  174     , isTerminal :: Bool
  175     , isFinish :: Bool
  176     , duration :: Int
  177     , parameters :: Value
  178     , decision :: DecisionView
  179     , score :: Float
  180     , scores :: Value
  181     }
  182     deriving (Generic)
  183 
  184 instance (UnitTag tag, VarValTimeJSON v x t) => Viewable (DefTree tag v x t) (NodeView tag v x t) where
  185     view tree@Tree{sID, sDecision} =
  186         NodeView
  187             { sid = showText sID
  188             , isTerminal = isLeaf tree
  189             , isFinish = isComplete tree
  190             , duration = fromEnum $ processDuration $ sTarget $ sState tree
  191             , decision =
  192                 ( \case
  193                     SynthesisDecision{decision} -> view decision
  194                     _ -> RootView
  195                 )
  196                     sDecision
  197             , parameters =
  198                 ( \case
  199                     SynthesisDecision{metrics} -> toJSON metrics
  200                     _ -> String "root"
  201                 )
  202                     sDecision
  203             , score =
  204                 ( \case
  205                     -- TODO: add support for "scores" field in UI, remove that field (or rename to default_score/effective_score?)
  206                     sd@SynthesisDecision{} -> defScore sd
  207                     _ -> 0
  208                 )
  209                     sDecision
  210             , scores =
  211                 ( \case
  212                     SynthesisDecision{scores} -> toJSON scores
  213                     _ -> object ["default" .= (0 :: Float)]
  214                 )
  215                     sDecision
  216             }
  217 
  218 instance (VarValTimeJSON v x t, ToJSON tag) => ToJSON (NodeView tag v x t)
  219 
  220 instance ToSample (NodeView tag v x t) where
  221     toSamples _ =
  222         samples
  223             [ NodeView
  224                 { sid = showText $ Sid [0, 1, 3, 1]
  225                 , isTerminal = False
  226                 , isFinish = False
  227                 , duration = 0
  228                 , parameters =
  229                     toJSON $
  230                         SingleBindMetrics
  231                             { pCritical = False
  232                             , pAlternative = 1
  233                             , pRestless = 0
  234                             , pOutputNumber = 2
  235                             , pAllowDataFlow = 1
  236                             , pPossibleDeadlock = False
  237                             , pNumberOfBoundFunctions = 1
  238                             , pPercentOfBoundInputs = 0.2
  239                             , pWave = Just 2
  240                             }
  241                 , decision = SingleBindView (FView "buffer(a) = b = c" []) "pu"
  242                 , score = 1032
  243                 , scores = object ["default" .= (1032 :: Float)]
  244                 }
  245             , NodeView
  246                 { sid = showText $ Sid [0, 1, 3, 1, 5]
  247                 , isTerminal = False
  248                 , isFinish = False
  249                 , duration = 0
  250                 , parameters =
  251                     toJSON $
  252                         DataflowMetrics
  253                             { pWaitTime = 1
  254                             , pRestrictedTime = False
  255                             , pNotTransferableInputs = [0, 0]
  256                             , pFirstWaveOfTargetUse = 0
  257                             }
  258                 , decision =
  259                     DataflowDecisionView
  260                         { source = ("PU1", EndpointSt{epRole = Source $ S.fromList ["a1", "a2"], epAt = 1 ... 1})
  261                         , targets =
  262                             [("PU2", EndpointSt{epRole = Target "a2", epAt = 1 ... 1})]
  263                         }
  264                 , score = 1999
  265                 , scores = object ["default" .= (1999 :: Float)]
  266                 }
  267             , NodeView
  268                 { sid = showText $ Sid [0, 1, 3, 1, 6]
  269                 , isTerminal = False
  270                 , isFinish = False
  271                 , duration = 0
  272                 , parameters = toJSON BreakLoopMetrics
  273                 , decision = BreakLoopView{value = "12.5", outputs = ["a", "b"], input = "c"}
  274                 , score = 5000
  275                 , scores = object ["default" .= (5000 :: Float)]
  276                 }
  277             , NodeView
  278                 { sid = showText $ Sid [0, 1, 3, 1, 5]
  279                 , isTerminal = False
  280                 , isFinish = False
  281                 , duration = 0
  282                 , parameters = toJSON OptimizeAccumMetrics
  283                 , decision =
  284                     OptimizeAccumView
  285                         { old = [FView "a + b = c" [], FView "c + d = e" []]
  286                         , new = [FView "a + b + d = e" []]
  287                         }
  288                 , score = 1999
  289                 , scores = object ["default" .= (1999 :: Float)]
  290                 }
  291             , NodeView
  292                 { sid = showText $ Sid [0, 1, 3, 1, 5]
  293                 , isTerminal = False
  294                 , isFinish = False
  295                 , duration = 0
  296                 , parameters = toJSON ConstantFoldingMetrics
  297                 , decision =
  298                     ConstantFoldingView
  299                         { cRefOld = [FView "a = 1" [], FView "b = 2" [], FView "a + b = r" []]
  300                         , cRefNew = [FView "r = 3" []]
  301                         }
  302                 , score = 1999
  303                 , scores = object ["default" .= (1999 :: Float)]
  304                 }
  305             , NodeView
  306                 { sid = showText $ Sid [0, 1, 3, 1, 5]
  307                 , isTerminal = False
  308                 , isFinish = False
  309                 , duration = 0
  310                 , parameters =
  311                     toJSON $
  312                         ResolveDeadlockMetrics
  313                             { pNumberOfLockedVariables = 1
  314                             , pBufferCount = 0
  315                             , pNumberOfTransferableVariables = 0
  316                             }
  317                 , decision =
  318                     ResolveDeadlockView
  319                         { newBuffer = "buffer(x#0@buf) = x#0"
  320                         , changeset = "Changeset {changeI = fromList [], changeO = fromList [(\"x#0\",fromList [\"x#0@buf\"])]}"
  321                         }
  322                 , score = 1999
  323                 , scores = object ["default" .= (1999 :: Float)]
  324                 }
  325             ]
  326 
  327 newtype StepInfoView = StepInfoView T.Text
  328     deriving (Generic)
  329 
  330 instance (Var v, Time t) => Viewable (StepInfo v x t) StepInfoView where
  331     view = StepInfoView . showText
  332 
  333 instance ToJSON StepInfoView
  334 
  335 instance (Var v, Time t) => Viewable (Process t (StepInfo v x t)) (Process t StepInfoView) where
  336     view p@Process{steps} = p{steps = map (\s@Step{pDesc} -> s{pDesc = view pDesc}) steps}
  337 
  338 -- Testbench
  339 
  340 instance (ToJSONKey v, ToJSON v, ToJSON x) => ToJSON (TestbenchReport v x)
  341 
  342 instance ToSample (TestbenchReport String Int) where
  343     toSamples _ =
  344         singleSample
  345             TestbenchReport
  346                 { tbStatus = True
  347                 , tbCompilerDump = "stdout:\n" <> "stderr:\n"
  348                 , tbSimulationDump =
  349                     T.unlines
  350                         [ "stdout:"
  351                         , "VCD info: dumpfile web_ui_net_tb.vcd opened for output."
  352                         , "0:0\tactual: 0.000  0\t"
  353                         , "0:1\tactual: 0.000  0 \texpect: 0.000  0 \tvar: x#0\t"
  354                         , "0:2\tactual: 0.000  0\t"
  355                         , "0:3\tactual: 0.000  0\t"
  356                         , "0:4\tactual: 0.000  0 \texpect: 0.000  0 \tvar: tmp_0#0\t"
  357                         , "0:5\tactual: 0.000  0\t"
  358                         , "1:0\tactual: 0.000  0\t"
  359                         , "1:1\tactual: 0.000  0 \texpect: 0.000  0 \tvar: x#0\t"
  360                         , "1:2\tactual: 0.000  0\t"
  361                         , "1:3\tactual: 0.000  0\t"
  362                         , "1:4\tactual: 0.000  0 \texpect: 0.000  0 \tvar: tmp_0#0\t"
  363                         , "1:5\tactual: 0.000  0\t"
  364                         , "stderr:"
  365                         ]
  366                 , tbPath = "/Users/penskoi/Documents/nitta-corp/nitta/gen/web_ui"
  367                 , tbFiles =
  368                     [ "web_ui_net/web_ui_net.v"
  369                     , "lib/div/div_mock.v"
  370                     , "lib/div/pu_div.v"
  371                     , "lib/i2c/bounce_filter.v"
  372                     , "lib/i2c/buffer.v"
  373                     , "lib/multiplier/mult_mock.v"
  374                     , "lib/multiplier/pu_multiplier.v"
  375                     , "lib/spi/pu_slave_spi_driver.v"
  376                     , "lib/spi/spi_slave_driver.v"
  377                     , "lib/spi/i2n_splitter.v"
  378                     , "lib/spi/spi_master_driver.v"
  379                     , "lib/spi/n2i_splitter.v"
  380                     , "lib/spi/pu_slave_spi.v"
  381                     , "lib/spi/pu_master_spi.v"
  382                     , "lib/pu_accum.v"
  383                     , "lib/pu_fram.v"
  384                     , "lib/pu_shift.v"
  385                     , "lib/pu_simple_control.v"
  386                     , "web_ui_net_tb.v"
  387                     ]
  388                 , tbFunctions =
  389                     [ "buffer(x#0) = tmp_0#0"
  390                     , "LoopEnd (Loop (X 0.000000) (O [x#0]) (I tmp_0#0)) (I tmp_0#0)"
  391                     , "LoopBegin (Loop (X 0.000000) (O [x#0]) (I tmp_0#0)) (O [x#0])"
  392                     ]
  393                 , tbSynthesisSteps =
  394                     [ "Step {pID = 19, pInterval = 0 ... 0, pDesc = Nested fram2: Step {pID = 0, pInterval = 0 ... 0, pDesc = bind Loop (X 0.000000) (O [x#0]) (I tmp_0#0)}}"
  395                     , "Step {pID = 18, pInterval = 0 ... 0, pDesc = Nested fram2: Step {pID = 1, pInterval = 0 ... 0, pDesc = revoke Loop (X 0.000000) (O [x#0]) (I tmp_0#0)}}"
  396                     , "Step {pID = 17, pInterval = 0 ... 0, pDesc = Nested fram2: Step {pID = 2, pInterval = 0 ... 0, pDesc = bind LoopBegin (Loop (X 0.000000) (O [x#0]) (I tmp_0#0)) (O [x#0])}}"
  397                     , "Step {pID = 16, pInterval = 0 ... 0, pDesc = Nested fram2: Step {pID = 3, pInterval = 0 ... 0, pDesc = bind LoopEnd (Loop (X 0.000000) (O [x#0]) (I tmp_0#0)) (I tmp_0#0)}}"
  398                     , "Step {pID = 15, pInterval = 1 ... 1, pDesc = Nested fram2: Step {pID = 4, pInterval = 1 ... 1, pDesc = Source x#0}}"
  399                     , "Step {pID = 14, pInterval = 0 ... 0, pDesc = Nested fram2: Step {pID = 5, pInterval = 0 ... 0, pDesc = PrepareRead 0}}"
  400                     , "Step {pID = 13, pInterval = 0 ... 1, pDesc = Nested fram2: Step {pID = 6, pInterval = 0 ... 1, pDesc = LoopBegin (Loop (X 0.000000) (O [x#0]) (I tmp_0#0)) (O [x#0])}}"
  401                     , "Step {pID = 12, pInterval = 4 ... 4, pDesc = Nested fram2: Step {pID = 7, pInterval = 4 ... 4, pDesc = Target tmp_0#0}}"
  402                     , "Step {pID = 11, pInterval = 4 ... 4, pDesc = Nested fram2: Step {pID = 8, pInterval = 4 ... 4, pDesc = Write 0}}"
  403                     , "Step {pID = 10, pInterval = 4 ... 4, pDesc = Nested fram2: Step {pID = 9, pInterval = 4 ... 4, pDesc = LoopEnd (Loop (X 0.000000) (O [x#0]) (I tmp_0#0)) (I tmp_0#0)}}"
  404                     , "Step {pID = 9, pInterval = 0 ... 0, pDesc = Nested fram1: Step {pID = 0, pInterval = 0 ... 0, pDesc = bind buffer(x#0) = tmp_0#0}}"
  405                     , "Step {pID = 8, pInterval = 1 ... 1, pDesc = Nested fram1: Step {pID = 1, pInterval = 1 ... 1, pDesc = Target x#0}}"
  406                     , "Step {pID = 7, pInterval = 1 ... 1, pDesc = Nested fram1: Step {pID = 2, pInterval = 1 ... 1, pDesc = Write 0}}"
  407                     , "Step {pID = 6, pInterval = 4 ... 4, pDesc = Nested fram1: Step {pID = 3, pInterval = 4 ... 4, pDesc = Source tmp_0#0}}"
  408                     , "Step {pID = 5, pInterval = 3 ... 3, pDesc = Nested fram1: Step {pID = 4, pInterval = 3 ... 3, pDesc = PrepareRead 0}}"
  409                     , "Step {pID = 4, pInterval = 1 ... 4, pDesc = Nested fram1: Step {pID = 5, pInterval = 1 ... 4, pDesc = buffer(x#0) = tmp_0#0}}"
  410                     , "Step {pID = 3, pInterval = 4 ... 4, pDesc = Transport \"tmp_0#0\" \"fram1\" \"fram2\"}"
  411                     , "Step {pID = 2, pInterval = 1 ... 1, pDesc = Transport \"x#0\" \"fram2\" \"fram1\"}"
  412                     , "Step {pID = 1, pInterval = 0 ... 0, pDesc = bind reg(x#0) = tmp_0#0}"
  413                     , "Step {pID = 0, pInterval = 0 ... 0, pDesc = bind Loop (X 0.000000) (O [x#0]) (I tmp_0#0)}"
  414                     ]
  415                 , tbFunctionalSimulationLog =
  416                     replicate 2 $
  417                         HM.fromList
  418                             [ ("tmp_0#0", 0)
  419                             , ("u#0", 0)
  420                             , ("x#0", 0)
  421                             ]
  422                 , tbLogicalSimulationLog =
  423                     replicate 2 $
  424                         HM.fromList
  425                             [ ("tmp_0#0", 0)
  426                             , ("u#0", 0)
  427                             , ("x#0", 0)
  428                             ]
  429                 }