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.ResolveDeadlock
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.ResolveDeadlock (
15 ResolveDeadlockMetrics (..),
16 ) where
17
18 import Data.Aeson (ToJSON)
19 import Data.Set qualified as S
20 import GHC.Generics
21 import NITTA.Intermediate.Types
22 import NITTA.Model.Networks.Bus
23 import NITTA.Model.Problems.Refactor
24 import NITTA.Model.ProcessorUnits
25 import NITTA.Model.TargetSystem
26 import NITTA.Synthesis.Types
27
28 data ResolveDeadlockMetrics = ResolveDeadlockMetrics
29 { pNumberOfLockedVariables :: Float
30 , pBufferCount :: Float
31 , pNumberOfTransferableVariables :: Float
32 }
33 deriving (Generic)
34
35 instance ToJSON ResolveDeadlockMetrics
36
37 instance
38 (UnitTag tag, VarValTime v x t) =>
39 SynthesisDecisionCls
40 (SynthesisState (TargetSystem (BusNetwork tag v x t) tag v x t) tag v x t)
41 (TargetSystem (BusNetwork tag v x t) tag v x t)
42 (ResolveDeadlock v x)
43 (ResolveDeadlock v x)
44 ResolveDeadlockMetrics
45 where
46 decisions SynthesisState{sTarget} o = [(o, resolveDeadlockDecision sTarget o)]
47
48 parameters SynthesisState{transferableVars} ResolveDeadlock{newBuffer} _ =
49 let buffered = outputs newBuffer
50 in ResolveDeadlockMetrics
51 { pNumberOfLockedVariables = fromIntegral $ S.size buffered
52 , pBufferCount = fromIntegral $ sum $ map countSuffix $ S.elems buffered
53 , pNumberOfTransferableVariables = fromIntegral (S.size $ buffered `S.intersection` transferableVars)
54 }
55
56 estimate SynthesisState{sParent} _o d _ | 0 < decisionRepeats d sParent = -2
57 estimate SynthesisState{} _o _d ResolveDeadlockMetrics{pNumberOfLockedVariables, pBufferCount, pNumberOfTransferableVariables} =
58 1000
59 + pNumberOfLockedVariables
60 - pBufferCount * 1000
61 - 20 * pNumberOfTransferableVariables
62
63 decisionRepeats d parent =
64 let ds = toRootDecisionStrings parent
65 in length $ takeWhile (== show d) ds
66
67 toRootDecisionStrings parent =
68 map
69 ( ( \case
70 SynthesisDecision{decision} -> show decision
71 _ -> ""
72 )
73 . sDecision
74 )
75 $ toRoot parent
76
77 toRoot (Just tree@Tree{sState = SynthesisState{sParent}}) = tree : toRoot sParent
78 toRoot _ = []