summaryrefslogtreecommitdiff
path: root/tools/resolver-visualize/DotRender.hs
blob: 448c1a5aca5f4ae52a8855c4cbb5379bca998f5a (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
module DotRender(
                 writeDotRun
                ) where

import Data.List
import Data.Maybe
import Dot
import Resolver.Log
import Resolver.PrettyPrint
import Resolver.Types
import System.IO
import Text.Printf
import Types
import qualified Data.Set as Set


inBounds :: Params -> Integer -> Bool
inBounds params n = let first = maybe 0 id (firstStep params) in
                    n >= first && maybe True (\max -> n < first + max) (maxSteps params)

choiceText :: LinkChoice -> String
choiceText (LinkChoice (InstallVersion ver _ _)) = "Install " ++ pp ver
choiceText (LinkChoice (BreakSoftDep d)) = "Break " ++ pp d
choiceText Unknown = "(...)"

dotChoiceLabel :: LinkChoice -> String
dotChoiceLabel lc@(LinkChoice c) = choiceText lc
dotChoiceLabel Unknown           = ""

inferTargetFormat :: Params -> TargetFormat
inferTargetFormat (Params { targetFormat = fmt,
                            dotOutput    = output }) =
    case fmt of
      Nothing -> PS
      Just fmt' -> fmt'

cloudImage :: Params -> String
cloudImage params =
    case inferTargetFormat params of
      PS -> "cloud.eps"
      PNG -> "cloud.png"

dotStepNode :: Params -> ProcessingStep -> Node
dotStepNode params step = node (name $ printf "step%d" (stepOrder step))
                          <<< set "label" (printf "Step: %d\nScore: %d\nTier: %s"
                                           (stepOrder step)
                                           (solScore $ stepSol step)
                                           (show $ solTier $ stepSol step))
                          <<< Set.null (solBrokenDeps (stepSol step)) `thenDo`
                              set "style" "filled" `andAlso`
                              set "peripheries" "2" `andAlso`
                              set "fillColor" "lightgrey"

-- Generate nodes for any successors that were not processed in the
-- render.
dotUnprocessedSuccs :: Params -> ProcessingStep -> [Node]
dotUnprocessedSuccs params step = unprocessed ++ excluded
    where unprocessed = [ node (name $ printf "step%dunproc%d" (stepOrder step) stepNum)
                          <<< set "label" (printf "Unprocessed\nScore: %d\nTier: %s"
                                           (solScore succSol)
                                           (show $ solTier succSol))
                          <<< set "style" "dashed"
                          <<< Set.null (solBrokenDeps (stepSol step)) `thenDo`
                              set "style" "dashed,filled" `andAlso`
                              set "peripheries" "2" `andAlso`
                              set "fillcolor" "lightgrey"
                          | ((Unprocessed { successorChoice    = succChoice,
                                            successorSolution  = succSol }),
                             stepNum)
                          <- zip (stepSuccessors step) ([0..] :: [Integer]) ]
          excluded    = [ node (name $ printf "step%d" (stepOrder step))
                          <<< set "label" (printf "Step %d+\n%d nodes..." (stepOrder step) (stepBranchSize step))
                          <<< set "shape" "plaintext"
                          <<< set "image" (cloudImage params)
                          | (Successor { successorStep = step }) <- stepSuccessors step,
                            not $ inBounds params (stepOrder step) ]

-- | If the parent of the given step (or of one of its
-- backpropagations) was excluded from the render, build and return a
-- node for it.
--
-- TODO: should show links between excluded nodes, etc...that will
-- need a bit of an overhaul though.
dotExcludedIndices :: Params -> ProcessingStep -> [Integer]
dotExcludedIndices params step =
    (maybeToList $ do (ParentLink {parentLinkParent = parentStep}) <- stepPredecessor step
                      (if inBounds params $ stepOrder parentStep
                       then fail "Not an excluded step."
                       else return $ stepOrder parentStep))
    ++
    [ parentStepNum
      | Backpropagation {
          backpropagationStep =
              ProcessingStep {
                stepOrder = parentStepNum
          } } <- stepBackpropagations step,
        not $ inBounds params parentStepNum ]

dotExcludedParentNode :: Params -> Integer -> Node
dotExcludedParentNode params stepNum = node (name $ printf "step%d" stepNum)
                                       <<< set "label" (printf "Step %d" stepNum)
                                       <<< set "shape" "plaintext"
                                       <<< set "image" (cloudImage params)

dotPromotions params step =
    if not $ showPromotions params
    then []
    else [ node (name $ printf "step%dpromotion%d" (stepOrder step) promotionNum)
           <<< set "label" (makeLabel promotion)
           <<< set "shape" "oval"
           | (promotion, promotionNum) <- zip (Set.toList $ stepPromotions step) ([0..] :: [Integer]) ]
         ++
         [ node (name $ printf "step%dbackprop%d" (stepOrder step) backpropNum)
           <<< set "label" (makeLabel $ backpropagationPromotion backprop)
           <<< set "shape" "oval" 
           | (backprop, backpropNum) <- zip (stepBackpropagations step) ([0..] :: [Integer]) ]
    where makeLabel p = if Set.size (promotionChoices p) <= 5
                        then printf "%s\n%s"
                                 (show $ promotionTier p)
                                 (concat $ intersperse "\n"
                                             [pp c | c <- Set.toList $ promotionChoices p])
                        else printf "(T%s: %d choices)"
                                 (show $ promotionTier p)
                                 (Set.size $ promotionChoices p)

dotEdges params step = cutIncoming ++ processed ++ unprocessed ++ promotions ++ backprops
    where processed   = [ edge (node (name $ printf "step%d" (stepOrder step)))
                               (node (name $ printf "step%d" (stepOrder step')))
                          <<< set "label" (dotChoiceLabel succChoice)
                          <<< forced `thenDo`
                              -- This gives us an arrow drawn with two
                              -- parallel lines.
                              set "color" "black:black"
                          | Successor { successorStep   = step',
                                        successorChoice = succChoice,
                                        successorForced = forced } <- stepSuccessors step ]
          unprocessed = [ edge (node (name $ printf "step%d" (stepOrder step)))
                               (node (name $ printf "step%dunproc%d" (stepOrder step) stepNum))
                          <<< set "label" (dotChoiceLabel succChoice)
                          <<< forced `thenDo` set "color" "black:black"
                          | ((Unprocessed { successorChoice = succChoice,
                                            successorForced = forced  }), stepNum)
                              <- zip (stepSuccessors step) ([0..] :: [Integer]) ]
          promotions  = if (not $ showPromotions params) || (Set.null $ stepPromotions step)
                        then []
                        else [ edge (node (name $ printf "step%d" (stepOrder step)))
                                    (node (name $ printf "step%dpromotion%d" (stepOrder step) promotionNum))
                               | promotionNum <- [0..((Set.size $ stepPromotions step) - 1)] ]
          backprops   = let attrs = set "color" "red" `andAlso`
                                    set "style" "dashed" `andAlso`
                                    set "constraint" "false" in
                        if (not $ showPromotions params) || (null $ stepBackpropagations step)
                        then []
                        -- Temporal edges to backpropagations.
                        else [edge (node (name $ printf "step%d" (stepOrder step)))
                                   (node (name $ printf "step%dbackprop0" (stepOrder step)))
                              <<< attrs]
                             ++
                             [edge (node (name $ printf "step%dbackprop%d" (stepOrder step) backpropNum))
                                   (node (name $ printf "step%dbackprop%d" (stepOrder step) (backpropNum + 1)))
                              <<< attrs
                              | backpropNum <- [0..((length $ stepBackpropagations step) - 2)] ]
                             ++
                             -- Structural edges to backpropagations.
                             [ edge (node (name $ printf "step%d" (stepOrder $ backpropagationStep backprop)))
                                    (node (name $ printf "step%dbackprop%d" (stepOrder step) backpropNum))
                               | (backprop, backpropNum) <- zip (stepBackpropagations step) ([0..] :: [Integer]) ]

          cutIncoming = [ edge (node (name $ printf "step%d" (stepOrder parentStep)))
                               (node (name $ printf "step%d" (stepOrder step)))
                          <<< set "label" (dotChoiceLabel choice)
                          <<< forced `thenDo` set "color" "black:black"
                          | ParentLink { parentLinkAction = choice,
                                         parentLinkForced = forced,
                                         parentLinkParent = parentStep }
                              <- maybeToList $ stepPredecessor step,
                            not $ inBounds params $ stepOrder parentStep ]

dotOrderEdges steps =
    [ edge (node (name $ printf "step%d" (stepOrder step1)))
           (node (name $ printf "step%d" (stepOrder step2)))
      <<< set "constraint" "false"
      <<< set "style" "dotted"
      <<< set "color" "blue"
      | (step1, step2) <- zip steps (drop 1 steps) ]

renderDot :: Params -> [ProcessingStep] -> Digraph
renderDot params steps =
    let droppedSteps   = maybe steps (\n -> genericDrop n steps) (firstStep params)
        truncatedSteps = maybe droppedSteps (\n -> genericTake n droppedSteps) (maxSteps params) in
    if null truncatedSteps
    then error "No steps to render."
    else let stepNodes          = map (dotStepNode params) truncatedSteps
             unprocessed        = concat $ map (dotUnprocessedSuccs params) truncatedSteps
             excludedParentIndices = concat $ map (dotExcludedIndices params) truncatedSteps
             excludedParentIndicesUnique = Set.toList $ Set.fromList excludedParentIndices
             excludedParents    = map (dotExcludedParentNode params) excludedParentIndicesUnique
             promotions         = concat $ map (dotPromotions params) truncatedSteps
             stepEdges          = concat $ map (dotEdges params) truncatedSteps
             orderEdges         = dotOrderEdges truncatedSteps in
         digraph (stepNodes ++ excludedParents ++
                  unprocessed ++ promotions) (stepEdges ++ orderEdges)

writeDotRun params steps outputFile =
    do let dot = renderDot params steps
       withFile outputFile WriteMode $ \h ->
           hPutStrLn h (show dot)