!AColorSelectorMorph commentStamp: ''! ColorComponentSelector showing an alpha gradient over a hatched background.! !AColorSelectorMorph methodsFor: 'accessing' stamp: '4/26/2024 09:28'! color: aColor "Set the gradient colors." super color: aColor beOpaque. self fillStyle: self defaultFillStyle! ! !AColorSelectorMorph methodsFor: 'protocol' stamp: '4/26/2024 09:28'! defaultFillStyle "Answer the hue gradient." ^(GradientFillStyle colors: {self color alpha: 0. self color}) origin: self topLeft; direction: (self bounds isWide ifTrue: [self width@0] ifFalse: [0@self height])! ! !AColorSelectorMorph methodsFor: '*Athens-Morphic' stamp: '4/26/2024 09:28'! drawOnAthensCanvas: anAthensCanvas anAthensCanvas setPaint: (InfiniteForm with: self hatchForm). anAthensCanvas drawShape: self innerBounds. super drawOnAthensCanvas: anAthensCanvas! ! !AColorSelectorMorph methodsFor: 'initialization' stamp: '4/26/2024 09:28'! initialize "Initialize the receiver." super initialize. self value: 1.0; color: Color black! ! !AColorSelectorMorph methodsFor: 'private' stamp: '4/26/2024 09:28'! hatchForm "Answer a form showing a grid hatch pattern." ^ColorPresenterMorph hatchForm! ! !AColorSelectorMorph methodsFor: 'drawing' stamp: '4/26/2024 09:28'! drawOn: aCanvas "Draw a hatch pattern first." aCanvas fillRectangle: self innerBounds fillStyle: (InfiniteForm with: self hatchForm). super drawOn: aCanvas! ! !AColorSelectorMorph methodsFor: 'visual properties' stamp: '4/26/2024 09:28'! fillStyle: fillStyle "If it is a color then override with gradient." fillStyle isColor ifTrue: [self color: fillStyle] ifFalse: [super fillStyle: fillStyle]! ! !AIAstar commentStamp: ''! A* is a graph traversal and path search algorithm, which is used in many fields of computer science due to its completeness, optimality, and optimal efficiency. One major practical drawback is its O(b^d) space complexity, as it stores all generated nodes in memory. Thus, in practical travel-routing systems, it is generally outperformed by algorithms that can pre-process the graph to attain better performance, as well as memory-bounded approaches; however, A* is still the best solution in many cases. (source: Wikipedia) Pseudocode and implementation for the approach is taken from: https://github.com/tatut/aoc2021-smalltalk/blob/main/src/AoC2021/AStar.class.st ! !AIAstar methodsFor: 'private' stamp: '4/26/2024 09:29'! updateDistance: newDistance of: aNode previousNode: previousNode aNode previousNode: previousNode. aNode pathDistance: newDistance! ! !AIAstar methodsFor: 'accessing' stamp: '4/26/2024 09:29'! start: startModel start := self findNode: startModel. start pathDistance: 0! ! !AIAstar methodsFor: 'configuration' stamp: '4/26/2024 09:29'! edgeClass ^ AIWeightedEdge! ! !AIAstar methodsFor: 'configuration' stamp: '4/26/2024 09:29'! nodeClass ^ AIPathDistanceNode! ! !AIAstar methodsFor: 'running' stamp: '4/26/2024 09:29'! heuristicFrom: startModel to: endModel "We are using a version of dijkstra algorithm here with all weights the for every node (value 1). So it has the same time complexity as BFS and takes into account the number of nodes in between intermediate and goal as a heuristic function. Edge weight can be increased to add more weight to heuristic part of Astar." | dijkstra addEdges pathD use | addEdges := OrderedCollection new. edges do: [ :edge | | efrom eto eval array | efrom := edge from model. eto := edge to model. eval := edge weight. array := OrderedCollection new. array add: efrom. array add: eto. array add: eval. addEdges add: array asArray "Transcript show: array;cr." ]. addEdges := addEdges asArray. end ifNil: [ ^ 0 ]. endModel ifNil: [ ^ 0 ]. dijkstra := AIDijkstra new. dijkstra nodes: (nodes first model to: nodes last model). dijkstra edges: addEdges from: [ :each | each first ] to: [ :each | each second ] weight: [ :each | each third ]. use := OrderedCollection new. use add: startModel model. use add: endModel model. dijkstra start: use first. dijkstra end: use second. dijkstra run. pathD := (dijkstra findNode: endModel model) pathDistance. ^ pathD! ! !AIAstar methodsFor: 'accessing' stamp: '4/26/2024 09:29'! start ^ start! ! !AIAstar methodsFor: 'accessing' stamp: '4/26/2024 09:29'! end: endModel end := self findNode: endModel! ! !AIAstar methodsFor: 'initialization' stamp: '4/26/2024 09:29'! reset self nodes do: [ :node | node pathDistance: Float infinity; visited: false; previousNode: nil ]! ! !AIAstar methodsFor: 'running' stamp: '4/26/2024 09:29'! runFrom: startModel to: endModel self start: startModel. self end: endModel. ^ self run! ! !AIAstar methodsFor: 'actions' stamp: '4/26/2024 09:29'! newPriorityQueue "We use the Heap object defined in the SequenceableCollections package." ^ Heap new! ! !AIAstar methodsFor: 'backtracking' stamp: '4/26/2024 09:29'! reconstructPath | path previous | "If no path exists between the start and the end node" end pathDistance = Float infinity ifTrue: [ ^ #( ) ]. path := LinkedList empty. previous := end. path addFirst: end model. [ previous = start ] whileFalse: [ previous := previous previousNode. path addFirst: previous model ]. ^ path! ! !AIAstar methodsFor: 'actions' stamp: '4/26/2024 09:29'! removeMostPromisingPair: aPriorityQueue ^ aPriorityQueue removeFirst! ! !AIAstar methodsFor: 'running' stamp: '4/26/2024 09:29'! run | pq cameFrom gScore fScore gs fs | cameFrom := Dictionary new. gScore := Dictionary new. gScore at: start put: 0. fScore := Dictionary new. fScore at: start put: (self heuristicFrom: start to: end). gs := [ :p | gScore at: p ifAbsent: Float infinity ]. fs := [ :p | fScore at: p ifAbsent: Float infinity ]. pq := SortedCollection sortUsing: [ :a :b | (fs value: a) < (fs value: b) ]. pq add: start. [ pq isEmpty ] whileFalse: [ | current | current := pq removeFirst. current = end ifTrue: [ | path prev | path := OrderedCollection with: current. prev := cameFrom at: current ifAbsent: nil. [ prev isNotNil ] whileTrue: [ path addFirst: prev. prev := cameFrom at: prev ifAbsent: nil. ]. "^ path." ] ifFalse: [ current outgoingEdges do: [ :edge | | tentative_gScore | tentative_gScore := (gs value: current) + (edge weight). tentative_gScore < (gs value: (edge to)) ifTrue: [ "This path to neighbor is better than any previous one. Record it!!" self updateDistance: tentative_gScore of: edge to previousNode: current. cameFrom at: (edge to) put: current. gScore at: (edge to) put: tentative_gScore. fScore at: (edge to) put: tentative_gScore + (self heuristicFrom: (edge to) to: end). (pq includes: (edge to)) ifFalse: [ pq add: (edge to) ]. ] ]. ]. ]! ! !AIAstar methodsFor: 'accessing' stamp: '4/26/2024 09:29'! end ^ end! ! !AIAstar methodsFor: 'running' stamp: '4/26/2024 09:29'! runFrom: startModel self start: startModel. self run! ! !AIAstar methodsFor: 'running' stamp: '4/26/2024 09:29'! pathDistance "Needs to be editted" ^ self end pathDistance! ! !AIAstarTest methodsFor: 'running' stamp: '4/26/2024 09:29'! setUp super setUp. astar := AIAstar new! ! !AIAstarTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testComplexWeightedGraph2 |graphType graph | graphType := AICyclicWeightedComplexFixture new. graph :=graphType complexWeightedGraph2. astar nodes: graph nodes. astar edges: graph edges from: #first to: #second weight: #third. astar runFrom: 0. self assert: (astar findNode: 1) pathDistance equals: 4. self assert: (astar findNode: 2) pathDistance equals: 1. self assert: (astar findNode: 3) pathDistance equals: 7. self assert: (astar findNode: 4) pathDistance equals: 9. self assert: (astar findNode: 5) pathDistance equals: 10! ! !AIAstarTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testAseBasicCircuit |graphType graph | graphType := AICyclicWeightedSimpleFixture new. graph :=graphType aseCircuitWeightedGraph. astar nodes: graph nodes. astar edges: graph edges from: #first to: #second weight: #third. astar runFrom: $a. self assert: 1 equals: (astar findNode: $b) pathDistance. self assert: 3 equals: (astar findNode: $e) pathDistance. self assert: 5 equals: (astar findNode: $h) pathDistance. astar reset. astar runFrom: $c. self assert: 2 equals: (astar findNode: $b) pathDistance. astar reset. astar runFrom: $h. self assert: Float infinity equals: (astar findNode: $a) pathDistance! ! !AIAstarTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testComplexWeightedGraph3Backtracking | shortestPath graphType graph | graphType := AICyclicWeightedComplexFixture new. graph :=graphType complexWeightedGraph3. astar nodes: graph nodes. astar edges: graph edges from: #first to: #second weight: #third. shortestPath := astar runFrom: $a to: $b; reconstructPath. self assertCollection: shortestPath hasSameElements: #( $a $d $b ). astar reset. shortestPath := astar runFrom: $a to: $c; reconstructPath. self assertCollection: shortestPath hasSameElements: #( $a $d $e $c ). astar reset. shortestPath := astar runFrom: $a to: $d; reconstructPath. self assertCollection: shortestPath hasSameElements: #( $a $d ). astar reset. shortestPath := astar runFrom: $a to: $e; reconstructPath. self assertCollection: shortestPath hasSameElements: #( $a $d $e ). astar reset! ! !AIAstarTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testSimpleWeightedGraph |graphType graph | graphType := AICyclicWeightedSimpleFixture new. graph :=graphType simpleWeightedGraph. astar nodes: graph nodes. astar edges: graph edges from: #first to: #second weight: #third. astar runFrom: 1. self assert: (astar findNode: 2) pathDistance equals: 5. self assert: (astar findNode: 3) pathDistance equals: 4. self assert: (astar findNode: 4) pathDistance equals: 8. self assert: (astar findNode: 5) pathDistance equals: 3! ! !AIAstarTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testComplexWeightedGraph2BackTracking | shortestPath graphType graph | graphType := AICyclicWeightedComplexFixture new. graph :=graphType complexWeightedGraph2. astar nodes: graph nodes. astar edges: graph edges from: #first to: #second weight: #third. shortestPath := astar runFrom: 0 to: 1; reconstructPath. self assertCollection: shortestPath hasSameElements: #( 0 2 1 ). astar reset. shortestPath := astar runFrom: 0 to: 2; reconstructPath. self assertCollection: shortestPath hasSameElements: #( 0 2 ). astar reset. shortestPath := astar runFrom: 0 to: 3; reconstructPath. self assertCollection: shortestPath hasSameElements: #( 0 2 1 3 ). astar reset. shortestPath := astar runFrom: 0 to: 4; reconstructPath. self assertCollection: shortestPath hasSameElements: #( 0 2 1 3 4 ). astar reset. shortestPath := astar runFrom: 0 to: 5; reconstructPath. self assertCollection: shortestPath hasSameElements: #( 0 2 1 3 4 5 ). astar reset! ! !AIAstarTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testAseBasicCircuitBacktrack |graphType graph | graphType := AICyclicWeightedSimpleFixture new. graph :=graphType aseCircuitWeightedGraph. astar nodes: graph nodes. astar edges: graph edges from: #first to: #second weight: #third. self assert: (#( $a $b ) hasEqualElements: (astar runFrom: $a to: $b; reconstructPath)). astar reset. self assert: (#( $a $b $d $e ) hasEqualElements: (astar runFrom: $a to: $e; reconstructPath)). astar reset. self assert: (#( $c $d $b ) hasEqualElements: (astar runFrom: $c to: $b; reconstructPath)). astar reset. self assert: (#( $a $b $c $f $g $h ) hasEqualElements: (astar runFrom: $a to: $h; reconstructPath)). astar reset. self assert: (#( ) hasEqualElements: (astar runFrom: $h to: $a; reconstructPath))! ! !AIAstarTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testSimpleWeightedGraphBacktracking | shortestPath graphType graph | graphType := AICyclicWeightedSimpleFixture new. graph :=graphType simpleWeightedGraph. astar nodes: graph nodes. astar edges: graph edges from: #first to: #second weight: #third. shortestPath := astar runFrom: 1 to: 2; reconstructPath. self assertCollection: shortestPath hasSameElements: #( 1 2 ). astar reset. shortestPath := astar runFrom: 1 to: 3; reconstructPath. self assertCollection: shortestPath hasSameElements: #( 1 3 ). astar reset. shortestPath := astar runFrom: 1 to: 4; reconstructPath. self assertCollection: shortestPath hasSameElements: #( 1 2 4 ). astar reset. shortestPath := astar runFrom: 1 to: 5; reconstructPath. self assertCollection: shortestPath hasSameElements: #( 1 5 ). astar reset! ! !AIAstarTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testComplexWeightedGraph3 |graphType graph | graphType := AICyclicWeightedComplexFixture new. graph :=graphType complexWeightedGraph3. astar nodes: graph nodes. astar edges: graph edges from: #first to: #second weight: #third. astar runFrom: $a. self assert: (astar findNode: $b) pathDistance equals: 3. self assert: (astar findNode: $c) pathDistance equals: 7. self assert: (astar findNode: $d) pathDistance equals: 1. self assert: (astar findNode: $e) pathDistance equals: 2! ! !AIBFS commentStamp: ''! Breadth-first search (BFS) is an algorithm for traversing or searching tree or graph data structures. It starts at the tree root (or some arbitrary node of a graph, sometimes referred to as a `search key') and explores the neighbor nodes first, before moving to the next level neighbours. (source: Wikipedia) The `queue` instance variable uses a LinkedList. This is because the linked list has constant access times. The `removeFist`, `#add:`, `#addLast:` takes a constant time to operate. See my test class examples of how to use me, but in a nutshell: ``` bfs := AIBFS new nodes: #( 1 2 3 4); edges: { (1 -> 4) . (1 -> 2) . (2 -> 3) . (3 -> 4)} from: #key to: #value; yourself. shortestPath := bfs runFrom: 1 to: 4 ``` This will return `#( 1 4 )`.! !AIBFS methodsFor: 'accessing' stamp: '4/26/2024 09:29'! start: startModel start := self findNode: startModel! ! !AIBFS methodsFor: 'configuration' stamp: '4/26/2024 09:29'! nodeClass ^ AIBFSNode! ! !AIBFS methodsFor: 'accessing' stamp: '4/26/2024 09:29'! start ^ start! ! !AIBFS methodsFor: 'accessing' stamp: '4/26/2024 09:29'! end: endModel end := self findNode: endModel! ! !AIBFS methodsFor: 'running' stamp: '4/26/2024 09:29'! runFrom: startModel to: endModel self runFrom: startModel. self end: endModel. ^ self reconstructPath! ! !AIBFS methodsFor: 'actions' stamp: '4/26/2024 09:29'! resetValues nodes do: [ :aNode | aNode visited: false; previousNode: nil; distance: nil ]! ! !AIBFS methodsFor: 'actions' stamp: '4/26/2024 09:29'! reconstructPath | path previous | "If no path exists between the start and the end node" end previousNode ifNil: [ ^ #( ) ]. path := LinkedList empty. previous := end. path addFirst: end model. [ previous = start ] whileFalse: [ previous := previous previousNode. path addFirst: previous model ]. ^ path! ! !AIBFS methodsFor: 'running' stamp: '4/26/2024 09:29'! run | node neighbours | self resetValues. queue := LinkedList with: start. start visited: true. start distance: 0. [ queue isNotEmpty ] whileTrue: [ node := queue removeFirst. neighbours := node adjacentNodes. neighbours do: [ :next | next visited ifFalse: [ queue addLast: next. next visited: true. next distance: node distance + 1. next previousNode: node ] ] ]! ! !AIBFS methodsFor: 'accessing' stamp: '4/26/2024 09:29'! end ^ end! ! !AIBFS methodsFor: 'running' stamp: '4/26/2024 09:29'! runFrom: startModel self start: startModel. self run! ! !AIBFSNode commentStamp: ''! I am a node that is used in the BFS algorithm defined in the `AIBFS` class. I have an instance variable `previousNode` to track from which node I have been called and also an instance variable visited to see if I were visited or not.! !AIBFSNode methodsFor: 'initialization' stamp: '4/26/2024 09:29'! visited ^ visited! ! !AIBFSNode methodsFor: 'initialization' stamp: '4/26/2024 09:29'! visited: aBoolean visited := aBoolean! ! !AIBFSNode methodsFor: 'accessing' stamp: '4/26/2024 09:29'! previousNode ^ previousNode! ! !AIBFSNode methodsFor: 'initialization' stamp: '4/26/2024 09:29'! initialize super initialize. visited := false! ! !AIBFSNode methodsFor: 'accessing' stamp: '4/26/2024 09:29'! previousNode: aNode previousNode := aNode! ! !AIBFSNode methodsFor: 'accessing' stamp: '4/26/2024 09:29'! distance ^ distance! ! !AIBFSNode methodsFor: 'accessing' stamp: '4/26/2024 09:29'! distance: anObject distance := anObject! ! !AIBFSNode methodsFor: 'accessing' stamp: '4/26/2024 09:29'! label ^ 'BFS: '! ! !AIBFSTest methodsFor: 'running' stamp: '4/26/2024 09:29'! setUp super setUp. bfsp := AIBFS new! ! !AIBFSTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testAseSccGraph |graph graphType| graphType := AICyclicNonWeightedSimpleFixture new. graph := graphType aseCircuitGraph. bfsp nodes: graph nodes. bfsp edges: graph edges from: #first to: #second. self assert: (#( $a $b $d $e ) hasEqualElements: (bfsp runFrom: $a to: $e)). self assert: (#( $b $d ) hasEqualElements: (bfsp runFrom: $b to: $d)). self assert: (#( $a $b $d ) hasEqualElements: (bfsp runFrom: $a to: $d))! ! !AIBFSTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testComplexUndirectedGraph |graph graphType| graphType := AICyclicNonWeightedComplexFixture new. graph := graphType complexUndirectedGraph. bfsp nodes: graph nodes. bfsp edges: graph edges from: #first to: #second. self assert: (#( 10 8 0 7 3 ) hasEqualElements: (bfsp runFrom: 10 to: 3)). self assert: (bfsp runFrom: 10 to: 12) size equals: 4. self assert: (#( 10 8 0 11 ) hasEqualElements: (bfsp runFrom: 10 to: 11)). self assert: (#( 5 6 7 0 ) hasEqualElements: (bfsp runFrom: 5 to: 0)). self assert: (#( 8 0 7 3 ) hasEqualElements: (bfsp runFrom: 8 to: 3)). self assert: (#( 6 7 0 8 10 ) hasEqualElements: (bfsp runFrom: 6 to: 10)). self assert: (#( 4 3 2 12 9 ) hasEqualElements: (bfsp runFrom: 4 to: 9))! ! !AIBFSTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testAseGraph |graph graphType| graphType := AICyclicNonWeightedSimpleFixture new. graph := graphType aseCircuitGraph. bfsp nodes: graph nodes. bfsp edges: graph edges from: #first to: #second. self assert: (#( $a $b $c ) hasEqualElements: (bfsp runFrom: $a to: $c)). self assert: (#( $d $b $c ) hasEqualElements: (bfsp runFrom: $d to: $c)). self assert: (#( $e $a ) hasEqualElements: (bfsp runFrom: $e to: $a)). self assert: (#( $a $b $c $f $g $h ) hasEqualElements: (bfsp runFrom: $a to: $h)). self assert: (#( $a $b $d $e ) hasEqualElements: (bfsp runFrom: $a to: $e)). self assert: (#( $a $b $d ) hasEqualElements: (bfsp runFrom: $a to: $d)). self assert: (#( $d $b $c $f ) hasEqualElements: (bfsp runFrom: $d to: $f)). "Empty list means path doesn't exist" self assert: (#() hasEqualElements: (bfsp runFrom: $f to: $a))! ! !AIBFSTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testSimpleGraph |graph graphType| graphType := AINonWeightedDAGFixture new. graph := graphType simpleGraph. bfsp nodes: graph nodes. bfsp edges: graph edges from: #first to: #second. self assert: (#( $a $b $c ) hasEqualElements: (bfsp runFrom: $a to: $c)). self assert: (#( $d $c ) hasEqualElements: (bfsp runFrom: $d to: $c))! ! !AIBFSTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testWithoutCyclesComplexGraph |graph graphType| graphType := AINonWeightedDAGFixture new. graph := graphType withoutCyclesComplexGraph. bfsp nodes: graph nodes. bfsp edges: graph edges from: #first to: #second. self assert: (#( $b $c $o $p $s ) hasEqualElements: (bfsp runFrom: $b to: $s)). self assert: (#( $b $h $d $i $r ) hasEqualElements: (bfsp runFrom: $b to: $r))! ! !AIBellmanFord commentStamp: ''! The Bellman Ford algorithm calculates the shortest path in any kind of graph. The graph edges can have negative weights and this algo hanldes negative cycles. If a negative cycle is detected, the path distance of that node is set to negative infinity! !AIBellmanFord methodsFor: 'running' stamp: '4/26/2024 09:29'! relaxEdges | anEdgeHasBeenRelaxed | "Relax the edges V-1 times at worst case" nodes size - 1 timesRepeat: [ anEdgeHasBeenRelaxed := false. edges do: [ :edge | edge from pathDistance + edge weight < edge to pathDistance ifTrue: [ edge to pathDistance: edge from pathDistance + edge weight. edge to previousNode: edge from. anEdgeHasBeenRelaxed := true ] ]. "If no edge has been relaxed means that we can stop the iteration before V-1 times" anEdgeHasBeenRelaxed ifFalse: [ ^ self ] ]! ! !AIBellmanFord methodsFor: 'accessing' stamp: '4/26/2024 09:29'! start: aModel start := (self findNode: aModel). start pathDistance: 0! ! !AIBellmanFord methodsFor: 'configuration' stamp: '4/26/2024 09:29'! edgeClass ^ AIWeightedEdge! ! !AIBellmanFord methodsFor: 'configuration' stamp: '4/26/2024 09:29'! nodeClass ^ AIPathDistanceNode! ! !AIBellmanFord methodsFor: 'accessing' stamp: '4/26/2024 09:29'! end: aModel end := (self findNode: aModel)! ! !AIBellmanFord methodsFor: 'actions' stamp: '4/26/2024 09:29'! reset self nodes do: [ :node | node pathDistance: Float infinity; previousNode: nil ]! ! !AIBellmanFord methodsFor: 'running' stamp: '4/26/2024 09:29'! runFrom: startModel to: endModel self runFrom: startModel. self end: endModel. ^ self reconstructPath! ! !AIBellmanFord methodsFor: 'actions' stamp: '4/26/2024 09:29'! reconstructPath | path previous | "If no path exists between the start and the end node" end pathDistance = Float infinity ifTrue: [ ^ #( ) ]. "If the end node is part of a negative cycle" end pathDistance = Float negativeInfinity ifTrue: [ ^ #( ) ]. path := LinkedList empty. previous := end. path addFirst: end model. [ previous = start ] whileFalse: [ previous := previous previousNode. path addFirst: previous model ]. ^ path! ! !AIBellmanFord methodsFor: 'running' stamp: '4/26/2024 09:29'! run start pathDistance: 0. self relaxEdges. "Run the algorithm one more time to detect if there is any negative cycles. The variation is if we can relax one more time an edge, means that the edge is part of a negative cycle. So, we put negative infinity as the path distance" self relaxEdgesToNegativeInfinity! ! !AIBellmanFord methodsFor: 'running' stamp: '4/26/2024 09:29'! runFrom: startModel self start: startModel. self run! ! !AIBellmanFord methodsFor: 'running' stamp: '4/26/2024 09:29'! relaxEdgesToNegativeInfinity "This method is called after a first relaxation has ocurred already. The algorithm is the same as the previous one but with the only difference that now if an edge can be relaxed we set the path distance as negative infinity because means that the edge is part of a negative cycle." | anEdgeHasBeenRelaxed | "Relax the edges V-1 times at worst case" nodes size - 1 timesRepeat: [ anEdgeHasBeenRelaxed := false. edges do: [ :edge | edge from pathDistance + edge weight < edge to pathDistance ifTrue: [ edge to pathDistance: Float negativeInfinity. anEdgeHasBeenRelaxed := true ] ]. "If no edge has been relaxed means that we can stop the iteration before V-1 times" anEdgeHasBeenRelaxed ifFalse: [ ^ self ] ]! ! !AIBellmanFordTest commentStamp: ''! An AIBellmanFordTest is a test class for testing the behavior of AIBellmanFord! !AIBellmanFordTest methodsFor: 'running' stamp: '4/26/2024 09:29'! setUp super setUp. bellmanFord := AIBellmanFord new! ! !AIBellmanFordTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testNegativeUnconnectedWeightedGraph |graphType graph | graphType := AICyclicWeightedSimpleFixture new. graph :=graphType negativeUnconnectedWeightedGraph. bellmanFord nodes: graph nodes. bellmanFord edges: graph edges from: #first to: #second weight: #third. bellmanFord start: 0. bellmanFord run. self assert: (bellmanFord findNode: 1) pathDistance equals: 5. self assert: (bellmanFord findNode: 2) pathDistance equals: Float negativeInfinity. self assert: (bellmanFord findNode: 3) pathDistance equals: Float negativeInfinity. self assert: (bellmanFord findNode: 4) pathDistance equals: Float negativeInfinity. self assert: (bellmanFord findNode: 5) pathDistance equals: 35. self assert: (bellmanFord findNode: 6) pathDistance equals: 40. self assert: (bellmanFord findNode: 7) pathDistance equals: -10. "No possible path between 0 and 8" self assert: (bellmanFord findNode: 8) pathDistance equals: Float infinity. self assert: (bellmanFord findNode: 9) pathDistance equals: Float negativeInfinity! ! !AIBellmanFordTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testNegativeWeightedGraph |graphType graph | graphType := AICyclicWeightedSimpleFixture new. graph :=graphType negativeWeightedGraph. bellmanFord nodes: graph nodes. bellmanFord edges: graph edges from: #first to: #second weight: #third. bellmanFord start: 0. bellmanFord run. self assert: (bellmanFord findNode: 1) pathDistance equals: 5. self assert: (bellmanFord findNode: 2) pathDistance equals: Float negativeInfinity. self assert: (bellmanFord findNode: 3) pathDistance equals: Float negativeInfinity. self assert: (bellmanFord findNode: 4) pathDistance equals: Float negativeInfinity. self assert: (bellmanFord findNode: 5) pathDistance equals: 35. self assert: (bellmanFord findNode: 6) pathDistance equals: 40. self assert: (bellmanFord findNode: 7) pathDistance equals: -10. self assert: (bellmanFord findNode: 8) pathDistance equals: -20. self assert: (bellmanFord findNode: 9) pathDistance equals: Float negativeInfinity! ! !AIBellmanFordTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testNegativeWeightedGraphReconstrucPath |graphType graph | graphType := AICyclicWeightedSimpleFixture new. graph :=graphType negativeWeightedGraph. bellmanFord nodes: graph nodes. bellmanFord edges: graph edges from: #first to: #second weight: #third. bellmanFord runFrom: 0 to: 8. self assertCollection: bellmanFord reconstructPath asArray equals: #( 0 1 5 6 7 8). bellmanFord reset. bellmanFord runFrom: 0 to: 7. self assertCollection: bellmanFord reconstructPath asArray equals: #( 0 1 5 6 7 )! ! !AIBellmanFordTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testNegativeWeightedGraph2 |graphType graph | graphType := AICyclicWeightedSimpleFixture new. graph :=graphType negativeWeightedGraph2. bellmanFord nodes: graph nodes. bellmanFord edges: graph edges from: #first to: #second weight: #third. bellmanFord start: 0. bellmanFord run. self assert: (bellmanFord findNode: 1) pathDistance equals: 5. self assert: (bellmanFord findNode: 2) pathDistance equals: Float negativeInfinity. self assert: (bellmanFord findNode: 3) pathDistance equals: Float negativeInfinity. self assert: (bellmanFord findNode: 4) pathDistance equals: Float negativeInfinity. self assert: (bellmanFord findNode: 5) pathDistance equals: 35. self assert: (bellmanFord findNode: 6) pathDistance equals: 40. self assert: (bellmanFord findNode: 7) pathDistance equals: -10. "No possible path between 0 and 8" self assert: (bellmanFord findNode: 8) pathDistance equals: Float infinity. self assert: (bellmanFord findNode: 9) pathDistance equals: Float negativeInfinity! ! !AICyclicNonWeightedComplexFixture commentStamp: ''! Graph Class: 1. Cyclic 2. Non-Weighted 3. 1 UnDirected, rest Directed graphs 4. Complex Graphs! !AICyclicNonWeightedComplexFixture methodsFor: 'fixtures' stamp: '4/26/2024 09:29'! complexCycleGraph "https://i.imgur.com/4trPCcb.jpeg" | nodes edges graph| nodes := $a to: $h. edges := #( #( $a $b ) #( $a $c ) #( $a $g ) #( $b $e ) #( $c $b ) #( $c $d ) #( $d $f ) #( $f $c ) #( $g $h ) #( $g $d ) #( $h $g ) ). graph:= AIGraphNonWeightedFixtureStructure new. graph nodes: nodes. graph edges: edges. ^graph! ! !AICyclicNonWeightedComplexFixture methodsFor: 'fixtures' stamp: '4/26/2024 09:29'! stronglyConnectedGraph: graphBuilder withObjects: objects "This is the exact same graph as #stronglyConnectedGraph: but using a custom object" | edges | edges := { { objects at: 1. objects at: 2 }. { objects at: 1. objects at: 3 }. { objects at: 2. objects at: 1 }. { objects at: 2. objects at: 4 }. { objects at: 3. objects at: 1 }. { objects at: 3. objects at: 4 }. { objects at: 4. objects at: 5 }. { objects at: 5. objects at: 4 }. { objects at: 6. objects at: 2 }. { objects at: 6. objects at: 5 }. { objects at: 6. objects at: 8 }. { objects at: 7. objects at: 6 }. { objects at: 8. objects at: 5 }. { objects at: 8. objects at: 7 }. { objects at: 9. objects at: 7 }. { objects at: 9. objects at: 8 }. { objects at: 9. objects at: 9 } }. graphBuilder nodes: objects. graphBuilder edges: edges from: #first to: #second. ^ graphBuilder! ! !AICyclicNonWeightedComplexFixture methodsFor: 'fixtures' stamp: '4/26/2024 09:29'! complexUndirectedGraph "https://i.imgur.com/qK2zsYb.png" | nodes edges graph| nodes := 0 to: 12. edges := #( #( 0 7 ) #( 0 11 ) #( 0 8 ) #( 1 9 ) #( 1 10 ) #( 2 3 ) #( 2 12 ) #( 3 2 ) #( 3 4 ) #( 3 7 ) #( 4 3 ) #( 5 6 ) #( 6 7 ) #( 6 5 ) #( 7 3 ) #( 7 0 ) #( 7 11 ) #( 7 6 ) #( 8 9 ) #( 8 10 ) #( 8 0 ) #( 9 1 ) #( 9 8 ) #( 9 12 ) #( 10 1 ) #( 10 8 ) #( 11 7 ) #( 11 0 ) #( 12 2 ) #( 12 9 ) ). graph:= AIGraphNonWeightedFixtureStructure new. graph nodes: nodes. graph edges: edges. ^graph! ! !AICyclicNonWeightedComplexFixture methodsFor: 'fixtures' stamp: '4/26/2024 09:29'! stronglyConnectedGraph "This a graph for 4 strongly connected components " "https://i.imgur.com/NA87YUP.png" | nodes edges graph| nodes := $a to: $i. edges := #( #( $a $b ) #( $a $c ) #( $b $a ) #( $b $d ) #( $c $a ) #( $c $d ) #( $d $e ) #( $e $d ) #( $f $b ) #( $f $e ) #( $f $h ) #( $g $f ) #( $h $e ) #( $h $g ) #( $i $g ) #( $i $h ) #( $i $i ) ). graph:= AIGraphNonWeightedFixtureStructure new. graph nodes: nodes. graph edges: edges. ^graph! ! !AICyclicNonWeightedComplexFixture methodsFor: 'initialization' stamp: '4/26/2024 09:29'! initialize |persons| super initialize . complexCycleGraph := self complexCycleGraph . complexCycleGraph2 := self complexCycleGraph2 . complexUndirectedGraph := self complexUndirectedGraph . stronglyConnectedGraph := self stronglyConnectedGraph . persons := DummyTestingPerson generateNinePersonArray. stronglyConnectedGraphWithObjects := self stronglyConnectedGraph: persons.! ! !AICyclicNonWeightedComplexFixture methodsFor: 'fixtures' stamp: '4/26/2024 09:29'! complexCycleGraph2 | nodes edges graph| nodes := $a to: $i. edges := #( #($a $b) #($a $f) #($b $e) #($b $f) #($c $b) #($c $a) #($c $e) #($c $f) #($c $g) #($c $d) #($d $b) #($e $b) #($e $d) #($e $h) #($f $b) #($f $e) #($f $d) #($g $b) #($g $a) #($g $e) #($g $f) #($g $d) #($g $i) ). graph:= AIGraphNonWeightedFixtureStructure new. graph nodes: nodes. graph edges: edges. ^graph! ! !AICyclicNonWeightedComplexFixture methodsFor: 'fixtures' stamp: '4/26/2024 09:29'! stronglyConnectedGraph: objects "This is the exact same graph as #stronglyConnectedGraph: but using a custom object" | edges graph| edges := { { objects at: 1. objects at: 2 }. { objects at: 1. objects at: 3 }. { objects at: 2. objects at: 1 }. { objects at: 2. objects at: 4 }. { objects at: 3. objects at: 1 }. { objects at: 3. objects at: 4 }. { objects at: 4. objects at: 5 }. { objects at: 5. objects at: 4 }. { objects at: 6. objects at: 2 }. { objects at: 6. objects at: 5 }. { objects at: 6. objects at: 8 }. { objects at: 7. objects at: 6 }. { objects at: 8. objects at: 5 }. { objects at: 8. objects at: 7 }. { objects at: 9. objects at: 7 }. { objects at: 9. objects at: 8 }. { objects at: 9. objects at: 9 } }. graph:= AIGraphNonWeightedFixtureStructure new. graph nodes: objects . graph edges: edges. ^graph! ! !AICyclicNonWeightedSimpleFixture commentStamp: ''! Graph Class: 1. Cyclic 2. Non-Weighted 3. 1 UnDirected, rest Directed graphs 4. Simple Graphs! !AICyclicNonWeightedSimpleFixture methodsFor: 'fixtures' stamp: '4/26/2024 09:29'! dependencyGraph | nodes edges graph| nodes := $a to: $k. edges := #( #( $a $b ) #( $a $c ) #( $c $a ) #( $c $k ) #( $d $e ) #( $d $g ) #( $d $i ) #( $e $c ) #( $e $f ) #( $f $j ) #( $g $f ) #( $g $h ) #( $g $i ) #( $h $j ) ). graph:= AIGraphNonWeightedFixtureStructure new. graph nodes: nodes. graph edges: edges. ^graph! ! !AICyclicNonWeightedSimpleFixture methodsFor: 'fixtures' stamp: '4/26/2024 09:29'! nestedCycleGraph "https://i.imgur.com/6lk0pmR.jpeg" | nodes edges graph| nodes := $a to: $i. edges := #( #( $a $b ) #( $b $c ) #( $c $d ) #( $d $e ) #( $e $a ) #( $b $e ) #( $e $b ) #( $e $f ) #( $f $g ) #( $g $h ) #( $h $f ) #( $g $i ) #( $i $g ) ). graph:= AIGraphNonWeightedFixtureStructure new. graph nodes: nodes. graph edges: edges. ^graph! ! !AICyclicNonWeightedSimpleFixture methodsFor: 'fixtures' stamp: '4/26/2024 09:29'! simpleGraphForHits "https://i.imgur.com/FvqrFbf.png" "Note that the socres (auth and hub) obtained by the hits algorithm will difer the scores from the image. This because the scores of the image were rounded several times in each iteartion to be obtained. But the scores must be similar" | nodes edges graph| nodes := #( 'N1' 'N2' 'N3' 'N4' ). edges := #( #( 'N1' 'N2' ) #( 'N1' 'N3' ) #( 'N1' 'N4' ) #( 'N2' 'N3' ) #( 'N2' 'N4' ) #( 'N3' 'N1' ) #( 'N3' 'N4' ) #( 'N4' 'N4' ) ). graph:= AIGraphNonWeightedFixtureStructure new. graph nodes: nodes. graph edges: edges. ^graph! ! !AICyclicNonWeightedSimpleFixture methodsFor: 'fixtures' stamp: '4/26/2024 09:29'! cycleGraph "https://i.imgur.com/MNtwA56.jpeg" | nodes edges graph| nodes := $a to: $d. edges := #( #( $a $b ) #( $b $c ) #( $c $a ) #( $d $c ) ). graph:= AIGraphNonWeightedFixtureStructure new. graph nodes: nodes. graph edges: edges. ^graph! ! !AICyclicNonWeightedSimpleFixture methodsFor: 'initialization' stamp: '4/26/2024 09:29'! initialize super initialize . aseCircuitGraph := self aseCircuitGraph . aseSccGraph := self aseSccGraph . cycleGraph := self cycleGraph . dependencyGraph := self dependencyGraph . moduleGraph := self moduleGraph . nestedCycleGraph := self nestedCycleGraph . simpleGraphForHits := self simpleGraphForHits .! ! !AICyclicNonWeightedSimpleFixture methodsFor: 'fixtures' stamp: '4/26/2024 09:29'! aseCircuitGraph "https://i.imgur.com/t1S6dG4.jpeg" | nodes edges graph| nodes := $a to: $h. edges := #( #( $a $b ) #( $b $a ) #( $b $c ) #( $b $d ) #( $c $d ) #( $c $f ) #( $d $b ) #( $d $e ) #( $e $a ) #( $f $g ) #( $g $h ) #( $h $g ) ). graph:= AIGraphNonWeightedFixtureStructure new. graph nodes: nodes. graph edges: edges. ^graph! ! !AICyclicNonWeightedSimpleFixture methodsFor: 'fixtures' stamp: '4/26/2024 09:29'! moduleGraph | nodes edges graph | nodes := #('v1' 'v2' 'v3' 'v4' 'v5' 'v6' 'v7' 'v8' 'v9' 'v10' 'v11'). edges := #( ('v1' 'v2') ('v1' 'v3') ('v1' 'v4') ('v2' 'v4') ('v2' 'v5') ('v2' 'v6') ('v2' 'v7') ('v3' 'v4') ('v3' 'v5') ('v3' 'v6') ('v3' 'v7') ('v4' 'v2') ('v4' 'v3') ('v4' 'v5') ('v4' 'v6') ('v4' 'v7') ('v5' 'v6') ('v5' 'v7') ('v6' 'v8') ('v6' 'v9') ('v6' 'v10') ('v6' 'v11') ('v7' 'v8') ('v7' 'v9') ('v7' 'v10') ('v7' 'v11') ('v8' 'v9') ('v8' 'v10') ('v8' 'v11') ('v9' 'v10') ('v9' 'v11')). graph:= AIGraphNonWeightedFixtureStructure new. graph nodes: nodes. graph edges: edges. ^graph! ! !AICyclicNonWeightedSimpleFixture methodsFor: 'fixtures' stamp: '4/26/2024 09:29'! aseSccGraph | nodes edges graph| nodes := $a to: $e. edges := #( #( $a $b ) #( $b $a ) #( $b $c ) #( $b $d ) #( $c $d ) #( $d $b ) #( $d $e ) #( $e $a ) ). graph:= AIGraphNonWeightedFixtureStructure new. graph nodes: nodes. graph edges: edges. ^graph! ! !AICyclicWeightedComplexFixture commentStamp: ''! Graph Class: 1. Cyclic 2. 3 negative Weighted, rest positive 3. Directed graphs 4. Complex Graphs! !AICyclicWeightedComplexFixture methodsFor: 'fixtures' stamp: '4/26/2024 09:29'! complexWeightedGraph4 "https://imgur.com/Szd19hW" | nodes edges graph | nodes := 1 to: 12. edges := #( #( 1 2 1 ) #( 1 4 25 ) #( 2 1 1 ) #( 2 3 26 ) #( 3 2 26 ) #( 3 4 17 ) #( 3 5 6 ) #( 3 6 20 ) #( 4 1 25 ) #( 4 3 17 ) #( 4 6 15 ) #( 4 7 8 ) #( 5 3 6 ) #( 5 6 18 ) #( 5 9 16 ) #( 5 12 23 ) #( 6 3 20 ) #( 6 4 15 ) #( 6 5 18 ) #( 6 7 6 ) #( 6 8 16 ) #( 6 9 16 ) #( 7 4 8 ) #( 7 6 6 ) #( 7 8 20 ) #( 8 6 16 ) #( 8 7 20 ) #( 8 9 7 ) #( 8 10 9 ) #( 9 5 16 ) #( 9 6 16 ) #( 9 8 7 ) #( 9 11 24 ) #( 9 12 9 ) #( 10 8 9 ) #( 10 11 9 ) #( 11 9 24 ) #( 11 10 9 ) #( 11 12 16 ) #( 12 5 23 ) #( 12 9 9 ) #( 12 11 16 ) ). graph:= AIGraphWeightedFixtureStructure new. graph nodes: nodes. graph edges: edges. ^graph! ! !AICyclicWeightedComplexFixture methodsFor: 'fixtures' stamp: '4/26/2024 09:29'! complexWeightedGraph "https://i.imgur.com/LAy4W3Z.jpeg" | nodes edges graph | nodes := $a to: $s. edges := #( #( $a $b 30 ) #( $b $s 1 ) #( $b $p 4 ) #( $b $c 30 ) #( $d $e 30 ) #( $d $f 20 ) #( $d $j 10 ) #( $e $a 15 ) #( $f $m 8 ) #( $g $h 20 ) #( $g $r 3 ) #( $i $a 14 ) #( $i $k 4 ) #( $i $d 3 ) #( $j $q 5 ) #( $k $l 10 ) #( $k $g 5 ) #( $m $n 7 ) #( $m $o 6 ) #( $n $c 5 ) #( $p $b 5 ) #( $q $i 4 ) ). graph:= AIGraphWeightedFixtureStructure new. graph nodes: nodes. graph edges: edges. ^graph! ! !AICyclicWeightedComplexFixture methodsFor: 'fixtures' stamp: '4/26/2024 09:29'! complexWeightedGraph2 "https://i.imgur.com/Syyd7YI.png" | nodes edges graph | nodes := 0 to: 5. edges := #( #( 0 1 5 ) #( 0 2 1 ) #( 1 2 2 ) #( 1 4 20 ) #( 1 3 3 ) #( 2 1 3 ) #( 2 4 12 ) #( 3 2 3 ) #( 3 4 2 ) #( 3 5 6 ) #( 4 5 1 ) ). graph:= AIGraphWeightedFixtureStructure new. graph nodes: nodes. graph edges: edges. ^graph! ! !AICyclicWeightedComplexFixture methodsFor: 'fixtures' stamp: '4/26/2024 09:29'! complexWeightedGraph3 "https://i.imgur.com/0kgPUQM.png" | nodes edges graph | nodes := $a to: $e. edges := #( #( $a $b 6 ) #( $a $d 1 ) #( $b $a 6 ) #( $b $c 5 ) #( $b $d 2 ) #( $b $e 2 ) #( $c $b 5 ) #( $c $e 5 ) #( $d $a 1 ) #( $d $b 2 ) #( $d $e 1 ) #( $e $b 2 ) #( $e $c 5 ) #( $e $d 1 ) ). graph:= AIGraphWeightedFixtureStructure new. graph nodes: nodes. graph edges: edges. ^graph! ! !AICyclicWeightedComplexFixture methodsFor: 'initialization' stamp: '4/26/2024 09:29'! initialize super initialize . complexWeightedGraph := self complexWeightedGraph . complexWeightedGraph2 := self complexWeightedGraph2 . complexWeightedGraph3 := self complexWeightedGraph3 . complexWeightedGraph4 := self complexWeightedGraph4 .! ! !AICyclicWeightedSimpleFixture commentStamp: ''! Graph Class: 1. Cyclic 2. 3 negative Weighted, rest positive 3. Directed graphs 4. Simple Graphs! !AICyclicWeightedSimpleFixture methodsFor: 'fixtures' stamp: '4/26/2024 09:29'! negativeWeightedGraph2 "https://i.imgur.com/R3EV1pl.png" | nodes edges graph | nodes := 0 to: 9. edges := #( #( 0 1 5 ) #( 1 2 20 ) #( 1 6 60 ) #( 1 5 30 ) #( 2 3 10 ) #( 2 4 75 ) #( 3 2 -15 ) #( 4 9 100 ) #( 5 4 25 ) #( 5 6 5 ) #( 6 7 -50 ) #( 8 7 -18 ) ). graph:= AIGraphWeightedFixtureStructure new. graph nodes: nodes. graph edges: edges. ^graph! ! !AICyclicWeightedSimpleFixture methodsFor: 'fixtures' stamp: '4/26/2024 09:29'! aseWeightedCircuitGraph | nodes edges graph | nodes := $a to: $h. edges := #( #( $a $b 1 ) #( $b $a 1 ) #( $b $c 1 ) #( $b $d 1 ) #( $c $d 1 ) #( $c $f 1 ) #( $d $b 1 ) #( $d $e 1 ) #( $e $a 1 ) #( $f $g 1 ) #( $g $h 1 ) #( $h $g 1 ) ). graph:= AIGraphWeightedFixtureStructure new. graph nodes: nodes. graph edges: edges. ^graph! ! !AICyclicWeightedSimpleFixture methodsFor: 'fixtures' stamp: '4/26/2024 09:29'! simpleWeightedGraph "https://i.imgur.com/AQTX2hz.jpeg" | nodes edges graph | nodes := 1 to: 5. edges := #( #( 1 2 5 ) #( 1 3 4 ) #( 2 3 2 ) #( 3 4 5 ) #( 2 4 3 ) #( 4 5 1 ) #( 5 1 2 ) #( 1 5 3 ) ). graph:= AIGraphWeightedFixtureStructure new. graph nodes: nodes. graph edges: edges. ^graph! ! !AICyclicWeightedSimpleFixture methodsFor: 'fixtures' stamp: '4/26/2024 09:29'! negativeUnconnectedWeightedGraph "https://i.imgur.com/EKPxvx7.png" | nodes edges graph | nodes := 0 to: 9. edges := #( #( 0 1 5 ) #( 1 2 20 ) #( 1 6 60 ) #( 1 5 30 ) #( 2 3 10 ) #( 2 4 75 ) #( 3 2 -15 ) #( 4 9 100 ) #( 5 4 25 ) #( 5 6 5 ) #( 6 7 -50 ) ). graph:= AIGraphWeightedFixtureStructure new. graph nodes: nodes. graph edges: edges. ^graph! ! !AICyclicWeightedSimpleFixture methodsFor: 'initialization' stamp: '4/26/2024 09:29'! initialize super initialize . aseCircuitWeightedGraph := self aseCircuitWeightedGraph . aseWeightedCircuitGraph := self aseWeightedCircuitGraph . negativeUnconnectedWeightedGraph := self negativeUnconnectedWeightedGraph . negativeWeightedGraph := self negativeWeightedGraph . negativeWeightedGraph2 := self negativeWeightedGraph2 . simpleWeightedGraph := self simpleWeightedGraph . simpleWeightedGraph2 := self simpleWeightedGraph2 .! ! !AICyclicWeightedSimpleFixture methodsFor: 'fixtures' stamp: '4/26/2024 09:29'! simpleWeightedGraph2 "https://imgur.com/6Mjdngn" | nodes edges graph | nodes := 1 to: 5. edges := #( #( 1 2 3 ) #( 1 4 7 ) #( 1 5 8 ) #( 2 1 3 ) #( 2 3 1 ) #( 2 4 4 ) #( 3 2 1 ) #( 3 4 2 ) #( 4 1 7 ) #( 4 2 4 ) #( 4 3 2 ) #( 4 5 3 ) #( 5 1 8 ) #( 5 4 3 ) ). graph:= AIGraphWeightedFixtureStructure new. graph nodes: nodes. graph edges: edges. ^graph! ! !AICyclicWeightedSimpleFixture methodsFor: 'fixtures' stamp: '4/26/2024 09:29'! aseCircuitWeightedGraph "This is the same graph, but with weights of 1 to all edges" "https://i.imgur.com/t1S6dG4.jpeg" | nodes edges graph | nodes := $a to: $h. edges := #( #( $a $b 1 ) #( $b $a 1 ) #( $b $c 1 ) #( $b $d 1 ) #( $c $d 1 ) #( $c $f 1 ) #( $d $b 1 ) #( $d $e 1 ) #( $e $a 1 ) #( $f $g 1 ) #( $g $h 1 ) #( $h $g 1 ) ). graph:= AIGraphWeightedFixtureStructure new. graph nodes: nodes. graph edges: edges. ^graph! ! !AICyclicWeightedSimpleFixture methodsFor: 'fixtures' stamp: '4/26/2024 09:29'! negativeWeightedGraph "https://i.imgur.com/GsnrKtx.png" | nodes edges graph | nodes := 0 to: 9. edges := #( #( 0 1 5 ) #( 1 2 20 ) #( 1 6 60 ) #( 1 5 30 ) #( 2 3 10 ) #( 2 4 75 ) #( 3 2 -15 ) #( 4 9 100 ) #( 5 4 25 ) #( 5 6 5 ) #( 5 8 50 ) #( 6 7 -50 ) #( 7 8 -10 ) ). graph:= AIGraphWeightedFixtureStructure new. graph nodes: nodes. graph edges: edges. ^graph! ! !AIDijkstra commentStamp: ''! Dijkstra's algorithm is an algorithm for finding the shortest paths between nodes in a graph, which may represent, for example, road networks. It was conceived by computer scientist Edsger W. Dijkstra in 1956 and published in 1959. The algorithm exists in many variants; Dijkstra's original variant found the shortest path between two nodes, but a more common variant fixes a single node as the "source" node and finds shortest paths from the source to all other nodes in the graph, producing a shortest path tree. (source: Wikipedia). The current implementation of this algo is the naive one. To improve it, Implement the data structure "priority queue" is needed. That is the key to improve the time complexity. Now, the priority queue is implemented as a list and the method `removeMostPromisingPair:` does a iteration to the list O(N) to retrieve the most promising pair. We can implement the priority queue as heap for example.! !AIDijkstra methodsFor: 'private' stamp: '4/26/2024 09:29'! updateDistance: newDistance of: aNode previousNode: previousNode aNode previousNode: previousNode. aNode pathDistance: newDistance! ! !AIDijkstra methodsFor: 'accessing' stamp: '4/26/2024 09:29'! start: startModel start := (self findNode: startModel). start pathDistance: 0! ! !AIDijkstra methodsFor: 'configuration' stamp: '4/26/2024 09:29'! edgeClass ^ AIWeightedEdge! ! !AIDijkstra methodsFor: 'configuration' stamp: '4/26/2024 09:29'! nodeClass ^ AIPathDistanceNode! ! !AIDijkstra methodsFor: 'accessing' stamp: '4/26/2024 09:29'! start ^ start! ! !AIDijkstra methodsFor: 'accessing' stamp: '4/26/2024 09:29'! end: endModel end := (self findNode: endModel)! ! !AIDijkstra methodsFor: 'initialization' stamp: '4/26/2024 09:29'! reset self nodes do: [ :node | node pathDistance: Float infinity; visited: false; previousNode: nil ]! ! !AIDijkstra methodsFor: 'running' stamp: '4/26/2024 09:29'! runFrom: startModel to: endModel self runFrom: startModel. self end: endModel. ^ self reconstructPath! ! !AIDijkstra methodsFor: 'backtracking' stamp: '4/26/2024 09:29'! reconstructPath | path previous | "If no path exists between the start and the end node" end pathDistance = Float infinity ifTrue: [ ^ #( ) ]. path := LinkedList empty. previous := end. path addFirst: end model. [ previous = start ] whileFalse: [ previous := previous previousNode. path addFirst: previous model ]. ^ path! ! !AIDijkstra methodsFor: 'actions' stamp: '4/26/2024 09:29'! removeMostPromisingPair: aPriorityQueue ^ aPriorityQueue removeFirst! ! !AIDijkstra methodsFor: 'running' stamp: '4/26/2024 09:29'! run | pq | pq := Heap new. pq sortBlock: [ :element1 :element2 | (element1 priority ) <= (element2 priority )]. start priority: 0. pq add: start. [ pq isNotEmpty ] whileTrue: [ | node minWeight | node := self removeMostPromisingPair: pq. minWeight := node priority. node visited: true. "Skip if the path weight is less than the one obtained from the pq. This is an optimization for not processing unnecessary nodes." node pathDistance < minWeight ifFalse: [ node outgoingEdges do: [ :edge | edge to visited ifFalse: [ | newDistance | newDistance := node pathDistance + edge weight. newDistance < edge to pathDistance ifTrue: [ self updateDistance: newDistance of: edge to previousNode: node. edge to priority: newDistance. pq add: edge to] ] ] ] ]! ! !AIDijkstra methodsFor: 'accessing' stamp: '4/26/2024 09:29'! end ^ end! ! !AIDijkstra methodsFor: 'running' stamp: '4/26/2024 09:29'! runFrom: startModel self start: startModel. self run! ! !AIDijkstra methodsFor: 'running' stamp: '4/26/2024 09:29'! pathDistance ^ self end pathDistance! ! !AIDijkstraTest methodsFor: 'running' stamp: '4/26/2024 09:29'! setUp super setUp. dijkstra := AIDijkstra new! ! !AIDijkstraTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testComplexWeightedGraph2 |graphType graph | graphType := AICyclicWeightedComplexFixture new. graph :=graphType complexWeightedGraph2. dijkstra nodes: graph nodes. dijkstra edges: graph edges from: #first to: #second weight: #third. dijkstra runFrom: 0. self assert: (dijkstra findNode: 1) pathDistance equals: 4. self assert: (dijkstra findNode: 2) pathDistance equals: 1. self assert: (dijkstra findNode: 3) pathDistance equals: 7. self assert: (dijkstra findNode: 4) pathDistance equals: 9. self assert: (dijkstra findNode: 5) pathDistance equals: 10! ! !AIDijkstraTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testAseBasicCircuit |graphType graph | graphType := AICyclicWeightedSimpleFixture new. graph :=graphType aseCircuitWeightedGraph. dijkstra nodes: graph nodes. dijkstra edges: graph edges from: #first to: #second weight: #third. dijkstra runFrom: $a. self assert: 1 equals: (dijkstra findNode: $b) pathDistance. self assert: 3 equals: (dijkstra findNode: $e) pathDistance. self assert: 5 equals: (dijkstra findNode: $h) pathDistance. dijkstra reset. dijkstra runFrom: $c. self assert: 2 equals: (dijkstra findNode: $b) pathDistance. dijkstra reset. dijkstra runFrom: $h. self assert: Float infinity equals: (dijkstra findNode: $a) pathDistance! ! !AIDijkstraTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testComplexWeightedGraph3Backtracking | shortestPath graphType graph | graphType := AICyclicWeightedComplexFixture new. graph :=graphType complexWeightedGraph3. dijkstra nodes: graph nodes. dijkstra edges: graph edges from: #first to: #second weight: #third. shortestPath := dijkstra runFrom: $a to: $b; reconstructPath. self assertCollection: shortestPath hasSameElements: #( $a $d $b ). dijkstra reset. shortestPath := dijkstra runFrom: $a to: $c; reconstructPath. self assertCollection: shortestPath hasSameElements: #( $a $d $e $c ). dijkstra reset. shortestPath := dijkstra runFrom: $a to: $d; reconstructPath. self assertCollection: shortestPath hasSameElements: #( $a $d ). dijkstra reset. shortestPath := dijkstra runFrom: $a to: $e; reconstructPath. self assertCollection: shortestPath hasSameElements: #( $a $d $e ). dijkstra reset! ! !AIDijkstraTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testSimpleWeightedGraph |graphType graph | graphType := AICyclicWeightedSimpleFixture new. graph :=graphType simpleWeightedGraph. dijkstra nodes: graph nodes. dijkstra edges: graph edges from: #first to: #second weight: #third. dijkstra runFrom: 1. self assert: (dijkstra findNode: 2) pathDistance equals: 5. self assert: (dijkstra findNode: 3) pathDistance equals: 4. self assert: (dijkstra findNode: 4) pathDistance equals: 8. self assert: (dijkstra findNode: 5) pathDistance equals: 3! ! !AIDijkstraTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testComplexWeightedGraph2BackTracking | shortestPath graphType graph | graphType := AICyclicWeightedComplexFixture new. graph :=graphType complexWeightedGraph2. dijkstra nodes: graph nodes. dijkstra edges: graph edges from: #first to: #second weight: #third. shortestPath := dijkstra runFrom: 0 to: 1; reconstructPath. self assertCollection: shortestPath hasSameElements: #( 0 2 1 ). dijkstra reset. shortestPath := dijkstra runFrom: 0 to: 2; reconstructPath. self assertCollection: shortestPath hasSameElements: #( 0 2 ). dijkstra reset. shortestPath := dijkstra runFrom: 0 to: 3; reconstructPath. self assertCollection: shortestPath hasSameElements: #( 0 2 1 3 ). dijkstra reset. shortestPath := dijkstra runFrom: 0 to: 4; reconstructPath. self assertCollection: shortestPath hasSameElements: #( 0 2 1 3 4 ). dijkstra reset. shortestPath := dijkstra runFrom: 0 to: 5; reconstructPath. self assertCollection: shortestPath hasSameElements: #( 0 2 1 3 4 5 ). dijkstra reset! ! !AIDijkstraTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testAseBasicCircuitBacktrack |graphType graph | graphType := AICyclicWeightedSimpleFixture new. graph :=graphType aseCircuitWeightedGraph. dijkstra nodes: graph nodes. dijkstra edges: graph edges from: #first to: #second weight: #third. self assert: (#( $a $b ) hasEqualElements: (dijkstra runFrom: $a to: $b; reconstructPath)). dijkstra reset. self assert: (#( $a $b $d $e ) hasEqualElements: (dijkstra runFrom: $a to: $e; reconstructPath)). dijkstra reset. self assert: (#( $c $d $b ) hasEqualElements: (dijkstra runFrom: $c to: $b; reconstructPath)). dijkstra reset. self assert: (#( $a $b $c $f $g $h ) hasEqualElements: (dijkstra runFrom: $a to: $h; reconstructPath)). dijkstra reset. self assert: (#( ) hasEqualElements: (dijkstra runFrom: $h to: $a; reconstructPath))! ! !AIDijkstraTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testSimpleWeightedGraphBacktracking | shortestPath graphType graph | graphType := AICyclicWeightedSimpleFixture new. graph :=graphType simpleWeightedGraph. dijkstra nodes: graph nodes. dijkstra edges: graph edges from: #first to: #second weight: #third. shortestPath := dijkstra runFrom: 1 to: 2; reconstructPath. self assertCollection: shortestPath hasSameElements: #( 1 2 ). dijkstra reset. shortestPath := dijkstra runFrom: 1 to: 3; reconstructPath. self assertCollection: shortestPath hasSameElements: #( 1 3 ). dijkstra reset. shortestPath := dijkstra runFrom: 1 to: 4; reconstructPath. self assertCollection: shortestPath hasSameElements: #( 1 2 4 ). dijkstra reset. shortestPath := dijkstra runFrom: 1 to: 5; reconstructPath. self assertCollection: shortestPath hasSameElements: #( 1 5 ). dijkstra reset! ! !AIDijkstraTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testComplexWeightedGraph3 | graphType graph | graphType := AICyclicWeightedComplexFixture new. graph :=graphType complexWeightedGraph3. dijkstra nodes: graph nodes. dijkstra edges: graph edges from: #first to: #second weight: #third. dijkstra runFrom: $a. self assert: (dijkstra findNode: $b) pathDistance equals: 3. self assert: (dijkstra findNode: $c) pathDistance equals: 7. self assert: (dijkstra findNode: $d) pathDistance equals: 1. self assert: (dijkstra findNode: $e) pathDistance equals: 2! ! !AIDinic commentStamp: ''! Dinic's algorithm is a graph algorithm used to solve the maximum flow problem efficiently. It is an improvement over the Ford-Fulkerson algorithm and is based on the concept of layering in the residual graph. Here's a summary of Dinic's algorithm: - Start with an initial flow of zero and create the residual graph from the given network. - Construct a level graph using breadth-first search (BFS) on the residual graph. The level graph assigns levels or distances to each vertex, indicating the shortest path from the source. - While there exists an augmenting path (a path from the source to the sink in the level graph), do the following steps: a. Use depth-first search (DFS) to find a blocking flow along the augmenting path. This flow is the maximum amount of flow that can be sent through the path. b. Update the residual graph by subtracting the blocking flow from forward edges and adding it to backward edges. - Finally, the maximum flow is obtained by summing up the flows on all outgoing edges from the source. Dinic's algorithm is efficient due to the concept of layering. The algorithm increases the flow in the network by finding multiple disjoint augmenting paths in each iteration, resulting in faster convergence compared to the Ford-Fulkerson algorithm. The time complexity of Dinic's algorithm is O(V^2E), where V is the number of vertices and E is the number of edges. However, with the use of advanced data structures like dynamic trees, the time complexity can be improved to O(V^2E log(V)). Overall, Dinic's algorithm is a powerful method for solving the maximum flow problem, particularly for large-scale networks. Here's an example code snippet to run the Dinic's Algorithm: |nodes edges dinic value| nodes := #( $1 $2 $3 $4 $5 $6 ). edges := #( #( $1 $2 10 ) #( $1 $3 10 ) #( $2 $3 2 ) #( $2 $4 4 ) #( $2 $5 8 ) #( $3 $5 9 ) #( $4 $6 10 ) #( $5 $4 6 ) #( $5 $6 10 )). dinic := AIDinic new. dinic nodes: nodes. dinic edges: edges from: [ :each | each first ] to: [ :each | each second ] capacity: [ :each | each third ]. dinic setStartNode: (dinic findNode: $1) sinkNode: (dinic findNode: $6). value:= dinic run. value.! !AIDinic methodsFor: 'configuration' stamp: '4/26/2024 09:29'! currentIndexSetup self nodes do: [ :n | n currentIndex: 1 ]! ! !AIDinic methodsFor: 'configuration' stamp: '4/26/2024 09:29'! edgeClass ^ AINetworkFlowEdge! ! !AIDinic methodsFor: 'configuration' stamp: '4/26/2024 09:29'! nodeClass ^ AIDinicNode! ! !AIDinic methodsFor: 'building - graph' stamp: '4/26/2024 09:29'! edges: aCollection from: source to: target capacity: capacityFunction | edge edgeRev| aCollection do: [ :eModel | edge := self addEdge: eModel from: source to: target. edge ifNotNil: [ edge capacity: (capacityFunction value: eModel) ]. edgeRev := self addEdge: eModel from: target to: source. edgeRev ifNotNil: [ edgeRev capacity:0 ].]! ! !AIDinic methodsFor: 'utilities' stamp: '4/26/2024 09:29'! reverseEdge: fromNode to: toNode | e | (adjList at: fromNode) do: [ :i | e := edges at: i. e to == toNode & (e capacity = 0) ifTrue: [ ^ e ] ]! ! !AIDinic methodsFor: 'accessing' stamp: '4/26/2024 09:29'! adjList ^ adjList! ! !AIDinic methodsFor: 'initialization' stamp: '4/26/2024 09:29'! initialize super initialize. adjList := Dictionary new. queue := LinkedList new! ! !AIDinic methodsFor: 'backtracking' stamp: '4/26/2024 09:29'! bfs "This method uses bfs on the residual graph to construct a level graph. The level graph assigns levels or distances to each node, indicating the shortest path from the source. The returnBool boolean indicates if there exists and augmenting path(path from source to sink) in the residual level graph." | node ind returnBool | [ queue isNotEmpty ] whileTrue: [ node := queue removeFirst. ind := adjList at: node. ind do: [ :i | | e n | e := edges at: i. n := e to. e capacity - e flow >= 1 & (n level = -1) ifTrue: [ n level: node level + 1. queue addLast: n ] ] ]. returnBool := sink level == -1. ^ returnBool! ! !AIDinic methodsFor: 'configuration' stamp: '4/26/2024 09:29'! levelSetup self nodes do: [ :n | n level: -1 ]! ! !AIDinic methodsFor: 'running' stamp: '4/26/2024 09:29'! run | finalFlow pushed breakLoop | self addAdjList. finalFlow := 0. breakLoop := true. self initializeBfs ifTrue: [ ^ 0 ]. [ breakLoop ] whileTrue: [ pushed := self dfs: start pushed: SmallInteger maxVal. [ pushed = 0 ] whileFalse: [ finalFlow := finalFlow + pushed. pushed := self dfs: start pushed: SmallInteger maxVal ]. self initializeBfs ifTrue: [ breakLoop := false ] ]. ^ finalFlow! ! !AIDinic methodsFor: 'configuration' stamp: '4/26/2024 09:29'! initializeBfs "This method - Initialises all the levels and current index of the nodes - Runs the bfs method to get the level graph - Returns a boolean based on whether the there exists an augmenting path or not." self levelSetup. self currentIndexSetup. start level: 0. queue addLast: start. ^ self bfs! ! !AIDinic methodsFor: 'configuration' stamp: '4/26/2024 09:29'! addAdjList | arr fromNode | self nodes do: [ :n | adjList at: n put: OrderedCollection new ]. self edges doWithIndex: [ :e :i | fromNode := e from. arr := adjList at: fromNode. arr add: i ]! ! !AIDinic methodsFor: 'utilities' stamp: '4/26/2024 09:29'! minimumValue: firstNumber compare: secondNumber firstNumber > secondNumber ifTrue: [ ^ secondNumber ]. ^ firstNumber! ! !AIDinic methodsFor: 'backtracking' stamp: '4/26/2024 09:29'! dfs: fromNode pushed: p "This method uses DFS-style algorithm to find a blocking flow (A blocking flow is a flow that saturates all the edges on the path, preventing any further flow) along the augmenting path. This performs a series of depth-first searches on the residual graph, exploring the edges with positive residual capacity." | arr cid edg reverseEdg toNode tr min | p = 0 ifTrue: [ ^ 0 ]. fromNode == sink ifTrue: [ ^ p ]. arr := adjList at: fromNode. cid := fromNode currentIndex. tr := 0. [ cid <= arr size ] whileTrue: [ edg := edges at: (arr at: cid). toNode := edg to. "Checking if the TO NODE is one level greater than FROM NODE, and for positive residual capacity" fromNode level + 1 = toNode level & (edg capacity - edg flow >= 1) ifTrue: [ fromNode currentIndex: cid. "Calculating the minimum value between the current positive residual capacity and the pushed value from previous iterations" min := self minimumValue: edg capacity - edg flow compare: p. "The recursive call of DFS" tr := self dfs: toNode pushed: min ]. tr = 0 ifFalse: [ edg flow: edg flow + tr. reverseEdg := self reverseEdge: toNode to: fromNode. reverseEdg flow: reverseEdg flow - tr. ^ tr ]. cid := cid + 1. fromNode currentIndex: cid ]. ^ 0! ! !AIDinic methodsFor: 'initialization' stamp: '4/26/2024 09:29'! setStartNode: startNode sinkNode: sinkNode start := startNode. sink := sinkNode! ! !AIDinicNode commentStamp: ''! This class represents a node in the Dinic's algorithm. Each node has a level and a currentIndex property.! !AIDinicNode methodsFor: 'setter' stamp: '4/26/2024 09:29'! level: aValue level := aValue! ! !AIDinicNode methodsFor: 'initialization' stamp: '4/26/2024 09:29'! initialize super initialize. level := -1. currentIndex := 1.! ! !AIDinicNode methodsFor: 'accessing' stamp: '4/26/2024 09:29'! level ^ level! ! !AIDinicNode methodsFor: 'accessing' stamp: '4/26/2024 09:29'! currentIndex ^ currentIndex! ! !AIDinicNode methodsFor: 'setter' stamp: '4/26/2024 09:29'! currentIndex: aValue currentIndex := aValue! ! !AIDinicNode methodsFor: 'accessing' stamp: '4/26/2024 09:29'! label ^ 'Dinic: '! ! !AIDinicTest methodsFor: 'running' stamp: '4/26/2024 09:29'! setUp super setUp. dinic := AIDinic new.! ! !AIDinicTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testComplexFlow | graphType graph value | graphType := AIWeightedDAGFixture new. graph := graphType withoutCyclesComplexWeightedGraph. dinic nodes: graph nodes. dinic edges: graph edges from: [ :each | each first ] to: [ :each | each second ] capacity: [ :each | each third ]. dinic setStartNode: (dinic findNode: $b) sinkNode: (dinic findNode: $r). value := dinic run. self assert: value equals: 2.! ! !AIDinicTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testSimpleFlow | graphType graph value | graphType := AIWeightedDAGFixture new. graph := graphType weightedDAG. dinic nodes: graph nodes. dinic edges: graph edges from: [ :each | each first ] to: [ :each | each second ] capacity: [ :each | each third ]. dinic setStartNode: (dinic findNode: $B) sinkNode: (dinic findNode: $E). value := dinic run. self assert: value equals: 17.! ! !AIDisjointSetNode commentStamp: ''! From wikipedia: A disjoint-set data structure, also called a union–find data structure or merge–find set, is a data structure that stores a collection of disjoint (non-overlapping) sets. Equivalently, it stores a partition of a set into disjoint subsets. It provides operations for adding new sets, merging sets (replacing them by their union), and finding a representative member of a set. The last operation allows to find out efficiently if any two elements are in the same or different sets. I have this time complexities for my operations: Space: O(n) Search: O(α(n) Merge: O(α(n)) α = amortized time complexity But, when you call the method `find` I path compress the nodes to make all the nodes in the same component point to the same parent. That means that the find and union operations will eventually take a time complexity of O(1). I am used by the Kruskal's algorithm to find cycles in a graph with a constant time.! !AIDisjointSetNode methodsFor: 'accessing' stamp: '4/26/2024 09:29'! makeSet parent := self! ! !AIDisjointSetNode methodsFor: 'private - accessing' stamp: '4/26/2024 09:29'! parent: anObject parent := anObject! ! !AIDisjointSetNode methodsFor: 'accessing' stamp: '4/26/2024 09:29'! union: aDSNode | root1 root2 | root1 := aDSNode find. root2 := self find. "The nodes already belong to the same component" root1 = root2 ifTrue: [ ^ self ]. root1 parent: root2! ! !AIDisjointSetNode methodsFor: 'accessing' stamp: '4/26/2024 09:29'! find | root next node | "Find the root of the component" node := self. root := node. [ root = root parent ] whileFalse: [ root := root parent ]. "Compress the path leading back to the root. This is the path compression operation that gives the linear amortized time complexity" [ node = root ] whileFalse: [ next := node parent. node parent: root. node := next ]. "Return the root of the component" ^ root! ! !AIDisjointSetNode methodsFor: 'initialization' stamp: '4/26/2024 09:29'! initialize super initialize. self makeSet! ! !AIDisjointSetNode methodsFor: 'accessing' stamp: '4/26/2024 09:29'! label ^ 'DSN '! ! !AIDisjointSetNode methodsFor: 'private - accessing' stamp: '4/26/2024 09:29'! parent ^ parent! ! !AIGraphAlgorithm commentStamp: ''! I'm the common superclass for all graphs related algorithms. I store edges and nodes and provides convenience methods to add, access and find nodes or edges. Once configured, send the run message to execute the algorithm.! !AIGraphAlgorithm methodsFor: 'building - graph' stamp: '4/26/2024 09:29'! addNodesFrom: model childrenBlock: childrenBlock "recursively add nodes from the model" | parent | model ifNil: [ ^ self ]. self findNode: model ifFound: [ ^ self "Prevent cycles. Do not add a node already added." ]. parent := self addNodeFor: model. (childrenBlock value: model) do: [ :child | self addNodesFrom: child childrenBlock: childrenBlock. self addEdge: { parent model. child } from: [ :each | each first ] to: [ :each | each second ] ]! ! !AIGraphAlgorithm methodsFor: 'building - graph' stamp: '4/26/2024 09:29'! edges: aCollection from: source toAll: targets aCollection do: [ :eModel | (targets value: eModel) do: [ :target | self addEdge: { (source value: eModel). target } from: [ :each | each first ] to: [ :each | each second ] ] ]! ! !AIGraphAlgorithm methodsFor: 'accessing' stamp: '4/26/2024 09:29'! findNode: aModel ifFound: aBlock "^ nodes findBinary: (self findBinaryBlock: aModel) do: aBlock ifNone: [ ]" "^ nodes detect: [ :aNode | aNode model = aModel ] ifFound: aBlock" ^nodeDictionary at: aModel ifPresent: aBlock.! ! !AIGraphAlgorithm methodsFor: 'building - graph' stamp: '4/26/2024 09:29'! rawNodes: aRawNodeList nodes := aRawNodeList! ! !AIGraphAlgorithm methodsFor: 'configuration' stamp: '4/26/2024 09:29'! edgeClass ^ nil! ! !AIGraphAlgorithm methodsFor: 'configuration' stamp: '4/26/2024 09:29'! nodeClass ^ AIGraphNode! ! !AIGraphAlgorithm methodsFor: 'accessing' stamp: '4/26/2024 09:29'! nodes ^ nodes! ! !AIGraphAlgorithm methodsFor: 'accessing' stamp: '4/26/2024 09:29'! edges ^ edges! ! !AIGraphAlgorithm methodsFor: 'accessing' stamp: '4/26/2024 09:29'! findNode: aModel ifAbsent: aBlock "^ nodes findBinary: (self findBinaryBlock: aModel) ifNone: aBlock" "^ nodes detect: [ :node | node model = aModel ] ifNone: aBlock" ^nodeDictionary at: aModel ifAbsent: aBlock.! ! !AIGraphAlgorithm methodsFor: 'building - graph' stamp: '4/26/2024 09:29'! edgesByPair: aCollection " aCollection must be a collection where the incoming edge has to be in the first position and the outgoing esge has to be in the second position. You can use this method instead of doing edge: aCollection from: #first to: #second" aCollection do: [ :eModel | self addEdge: eModel from: [ :each | each first ] to: [ :each | each second ] ]! ! !AIGraphAlgorithm methodsFor: 'initialization' stamp: '4/26/2024 09:29'! initialize sortingBlock := [ :a :b | a model hash <= b model hash ]. nodes := SortedCollection sortUsing: sortingBlock. edges := SortedCollection sortUsing: sortingBlock. nodeDictionary := Dictionary new.! ! !AIGraphAlgorithm methodsFor: 'accessing' stamp: '4/26/2024 09:29'! findEdge: aModel "^ edges findBinary: (self findBinaryBlock: aModel)" ^ edges detect: [ :edge | edge model = aModel ]! ! !AIGraphAlgorithm methodsFor: 'private' stamp: '4/26/2024 09:29'! addEdge: edgeModel from: sourceBlock to: targetBlock | edge sourceNode targetNode | sourceNode := self findNode: (sourceBlock value: edgeModel) ifAbsent: [ ^ nil ]. targetNode := self findNode: (targetBlock value: edgeModel) ifAbsent: [ ^ nil ]. ^ self edgeClass ifNil: [ sourceNode to: targetNode. targetNode from: sourceNode. nil ] ifNotNil: [ edge := self edgeClass with: edgeModel. sourceNode to: targetNode edge: edge. targetNode from: sourceNode edge: edge. edge from: sourceNode. edge to: targetNode. self edges add: edge. edge ]! ! !AIGraphAlgorithm methodsFor: 'building - graph' stamp: '4/26/2024 09:29'! edges: aCollection from: source to: target aCollection do: [ :eModel | self addEdge: eModel from: source to: target ]! ! !AIGraphAlgorithm methodsFor: 'building - graph' stamp: '4/26/2024 09:29'! emptyGraph edges := edges copyEmpty. nodes := nodes copyEmpty! ! !AIGraphAlgorithm methodsFor: 'accessing' stamp: '4/26/2024 09:29'! findNode: aModel "^ nodes findBinary: (self findBinaryBlock: aModel)." "^ nodes detect: [ :node | node model = aModel ]" (nodeDictionary includesKey: aModel) ifTrue: [ ^ nodeDictionary at: aModel ]. Error signal: ('No Element in Graph : ',(aModel asString) ). ! ! !AIGraphAlgorithm methodsFor: 'building - graph' stamp: '4/26/2024 09:29'! nodes: aNodeList aNodeList do: [ :model | self addNodeFor: model ]! ! !AIGraphAlgorithm methodsFor: 'building - graph' stamp: '4/26/2024 09:29'! addNodeFor: aModel | newNode | ^ self findNode: aModel ifAbsent: [ newNode := (self nodeClass with: aModel). nodes add: newNode . nodeDictionary at: aModel put: newNode . ]! ! !AIGraphAlgorithm methodsFor: 'accessing' stamp: '4/26/2024 09:29'! graph ^ { nodes. edges }! ! !AIGraphAlgorithm methodsFor: 'running' stamp: '4/26/2024 09:29'! run self subclassResponsibility! ! !AIGraphAlgorithm methodsFor: 'building - graph' stamp: '4/26/2024 09:29'! addNodesFromDifferentGraph: aNodeList "Adds nodes from another graph. This is useful for example when you want to add all the nodes, and its adjacencies, from one graph to another. For example, first running a graph reducing algo and then do a topological sort. First create the graph reduced graph and then add its nodes to a topological sort graph. " aNodeList do: [ :node | self addNodeFor: node model ]. aNodeList do: [ :node | node adjacentNodes do: [ :next | self addEdge: node model -> next model from: [ :each | each key ] to: [ :each | each value ] ] ]! ! !AIGraphAlgorithm methodsFor: 'private' stamp: '4/26/2024 09:29'! findBinaryBlock: aModel "New implementation of the algos to have better performances to find nodes. The nodes and edges are sorted from low to high according to their has number." ^ [ :aNode | aModel hash - aNode model hash ]! ! !AIGraphAlgorithm methodsFor: 'building - graph' stamp: '4/26/2024 09:29'! edges: aCollection from: source to: target weight: weightFunction | edge | aCollection do: [ :eModel | edge := self addEdge: eModel from: source to: target. edge ifNotNil: [ edge weight: (weightFunction value: eModel) ] ]! ! !AIGraphAlgorithm class methodsFor: 'testing' stamp: '4/26/2024 09:29'! isAbstract ^ self = AIGraphAlgorithm! ! !AIGraphAlgorithmTest commentStamp: ''! A MalGraphAlgorithmTest is a test class for testing the behavior of MalGraphAlgorithm! !AIGraphAlgorithmTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testingFindingNodes |graphType graph dijkstra| graphType := AICyclicWeightedSimpleFixture new. graph :=graphType aseCircuitWeightedGraph. dijkstra := AIDijkstra new. dijkstra nodes: graph nodes. dijkstra edges: graph edges from: #first to: #second weight: #third. self assert: Float infinity equals: (dijkstra findNode: $g) pathDistance.! ! !AIGraphAlgorithmTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testAddNodesFromChildrenBlock | builder | builder := AIGraphReducer new. builder addNodesFrom: String childrenBlock: [ :parent | parent subclasses ]. self assert: builder nodes size equals: 6. self assertCollection: (builder nodes collect: [ :each | each model ]) hasSameElements: (String allSubclasses copyWith: String). self assertCollection: ((builder findNode: Symbol) adjacentNodes collect: [ :each | each model ]) hasSameElements: { ByteSymbol. WideSymbol }. self assert: (builder findNode: ByteSymbol) adjacentNodes isEmpty! ! !AIGraphAlgorithmTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testingAddingNodes |graphType graph dijkstra| graphType := AICyclicWeightedSimpleFixture new. graph :=graphType aseCircuitWeightedGraph. dijkstra := AIDijkstra new. dijkstra nodes: graph nodes. dijkstra edges: graph edges from: #first to: #second weight: #third. self assert: 8 equals: (dijkstra nodes) size. dijkstra addNodeFor: $i. self assert: 9 equals: (dijkstra nodes) size. self assert: Float infinity equals: (dijkstra findNode: $i) pathDistance. ! ! !AIGraphAlgorithmTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testingNodeDictionary |graphType graph dijkstra| graphType := AICyclicWeightedSimpleFixture new. graph :=graphType aseCircuitWeightedGraph. dijkstra := AIDijkstra new. dijkstra nodes: graph nodes. dijkstra edges: graph edges from: #first to: #second weight: #third. dijkstra runFrom: $a. self assert: 1 equals: (dijkstra findNode: $b) pathDistance. self assert: 8 equals: (dijkstra nodes) size. dijkstra addNodeFor: $i. self assert: 9 equals: (dijkstra nodes) size. self assert: Float infinity equals: (dijkstra findNode: $i) pathDistance. dijkstra reset. dijkstra runFrom: $c. self assert: 2 equals: (dijkstra findNode: $b) pathDistance. dijkstra reset. dijkstra runFrom: $h. self assert: Float infinity equals: (dijkstra findNode: $a) pathDistance! ! !AIGraphEdge commentStamp: ''! I represent an edge in a graph. I'm part of the edges of a AIGraphAlgorithm and I link two AINode together. Public API and Key Messages - from - to - model Instance Variables from: to: model: ! !AIGraphEdge methodsFor: 'accessing' stamp: '4/26/2024 09:29'! model: aModel model := aModel! ! !AIGraphEdge methodsFor: 'accessing' stamp: '4/26/2024 09:29'! model ^ model! ! !AIGraphEdge methodsFor: 'accessing' stamp: '4/26/2024 09:29'! from: anObject from := anObject! ! !AIGraphEdge methodsFor: 'accessing' stamp: '4/26/2024 09:29'! to: anObject to := anObject! ! !AIGraphEdge methodsFor: 'accessing' stamp: '4/26/2024 09:29'! from ^ from! ! !AIGraphEdge methodsFor: 'accessing' stamp: '4/26/2024 09:29'! asTuple ^ {from model . to model}! ! !AIGraphEdge methodsFor: 'printing' stamp: '4/26/2024 09:29'! printOn: aStream self from printOn: aStream. aStream nextPutAll: ' -> '. self to printOn: aStream! ! !AIGraphEdge methodsFor: 'accessing' stamp: '4/26/2024 09:29'! to ^ to! ! !AIGraphEdge class methodsFor: 'instance creation' stamp: '4/26/2024 09:29'! with: aModel from: srcNode to: dstNode | edge | edge := self new. edge model: aModel. edge from: srcNode. edge to: dstNode. ^ edge! ! !AIGraphEdge class methodsFor: 'instance creation' stamp: '4/26/2024 09:29'! with: aModel ^ self new model: aModel! ! !AIGraphNode commentStamp: ''! Default representation of a graph vertex (node).! !AIGraphNode methodsFor: 'accessing' stamp: '4/26/2024 09:29'! model: aModel model := aModel! ! !AIGraphNode methodsFor: 'accessing' stamp: '4/26/2024 09:29'! to: targetNode edge: anEdge! ! !AIGraphNode methodsFor: 'initialization' stamp: '4/26/2024 09:29'! initialize super initialize. adjacentNodes := OrderedCollection new! ! !AIGraphNode methodsFor: 'accessing' stamp: '4/26/2024 09:29'! adjacentNodes ^ adjacentNodes! ! !AIGraphNode methodsFor: 'accessing' stamp: '4/26/2024 09:29'! from: sourceNode! ! !AIGraphNode methodsFor: 'accessing' stamp: '4/26/2024 09:29'! adjacentNodes: aNodeList adjacentNodes := aNodeList! ! !AIGraphNode methodsFor: 'accessing' stamp: '4/26/2024 09:29'! model ^ model! ! !AIGraphNode methodsFor: 'accessing' stamp: '4/26/2024 09:29'! to: targetNode adjacentNodes add: targetNode! ! !AIGraphNode methodsFor: 'accessing' stamp: '4/26/2024 09:29'! label ^ 'Node: '! ! !AIGraphNode methodsFor: 'printing' stamp: '4/26/2024 09:29'! printOn: stream stream nextPutAll: self label. model printOn: stream! ! !AIGraphNode methodsFor: 'accessing' stamp: '4/26/2024 09:29'! from: sourceNode edge: anEdge! ! !AIGraphNode class methodsFor: 'instance creation' stamp: '4/26/2024 09:29'! with: aModel ^ self new model: aModel! ! !AIGraphNonWeightedFixtureStructure commentStamp: ''! Structure of Non Weighted Graphs - nodes - edges! !AIGraphNonWeightedFixtureStructure methodsFor: 'drawing - roassal' stamp: '4/26/2024 09:29'! buildGraphCanvas | canvas | canvas := RSCanvas new. canvas addAll: (self nodesAsRoassalShapes). canvas nodes @ RSDraggable new. canvas @ RSCanvasController new. RSLineBuilder arrowedLine color: Color black; withBorderAttachPoint; shapes: canvas nodes; useAssociations: (edges collect: [ :each | each first -> each last ]). RSCircleLayout on: canvas nodes. ^ canvas! ! !AIGraphReducer commentStamp: ''! The reduced graph of G is the graph G where each strongly connected components was merged into one vertice / node. circuitsNodes instance variable will collect all nodes created by merging nodes in a circuit. This algorithm is not merging the weights of the graph. However, reducing a weighted graphs needs an specific way of doing it according to the use case.! !AIGraphReducer methodsFor: 'reducing' stamp: '4/26/2024 09:29'! replaceReferencesToMergedNode: aReducedNode "Replace the adjacencies of aReducedNode to merged nodes to reference the reduced node instead. For example, is aReducedNode has an an adjacency to node A, but node A has been reduced to node R, replace the adjacency of A with R." | newAdjacencies adjacenciesToRemove | newAdjacencies := OrderedCollection empty. adjacenciesToRemove := OrderedCollection empty. aReducedNode adjacentNodes do: [ :anAdjacentNode | "Iterate through all the circuitNodes to see if the adjacent node was merged. If that is the case (if we found the adjacent node merged), then we need to remove the reference to that node and reference to the new merged node instead. " collapsedNodes do: [ :aNode | (aNode mergedNodes includes: anAdjacentNode) ifTrue: [ newAdjacencies add: aNode. adjacenciesToRemove add: anAdjacentNode ] ] ]. aReducedNode adjacentNodes removeAllFoundIn: adjacenciesToRemove; "We use a set to avoid referencing multiple times to the same reduced node" addAll: newAdjacencies asSet! ! !AIGraphReducer methodsFor: 'configuration' stamp: '4/26/2024 09:29'! nodeClass ^ AIReducedGraphNode! ! !AIGraphReducer methodsFor: 'actions' stamp: '4/26/2024 09:29'! adjacenciesFor: aMergedNodeList "Obtains the adjacent nodes of the merged nodes. Then removes the references to the same merged nodes (to avoid referencing a merged node). Because all the merged nodes are now a same 'reduced' node" ^ ((aMergedNodeList flatCollect: [ :each | each adjacentNodes ] as: Set) difference: aMergedNodeList) asOrderedCollection! ! !AIGraphReducer methodsFor: 'initialization' stamp: '4/26/2024 09:29'! initialize super initialize. collapsedNodes := OrderedCollection new. circuits := OrderedCollection new! ! !AIGraphReducer methodsFor: 'reducing' stamp: '4/26/2024 09:29'! reduceGraph circuits do: [ :each | self reduceNodesInCircuit: each ]. self removeMergedNodes. self addCollapsedNodes. self replaceReferencesToMergedNodes! ! !AIGraphReducer methodsFor: 'reducing' stamp: '4/26/2024 09:29'! reduceNodesInCircuit: aCircuit "This method created a reduced node (called circuit node) that contains all the nodes that are inside a circuit inside a strongly connected component that the Tarjan algorithm found." collapsedNodes add: (self nodeClass new mergedNodes: aCircuit; model: (aCircuit collect: [ :each | each model ]); adjacentNodes: (self adjacenciesFor: aCircuit); yourself)! ! !AIGraphReducer methodsFor: 'updating' stamp: '4/26/2024 09:29'! addCollapsedNodes nodes addAll: collapsedNodes! ! !AIGraphReducer methodsFor: 'running' stamp: '4/26/2024 09:29'! run self findCircuits. self reduceGraph. ^ nodes! ! !AIGraphReducer methodsFor: 'updating' stamp: '4/26/2024 09:29'! removeMergedNodes nodes removeAll: (collapsedNodes flatCollect: [ :each | each mergedNodes ])! ! !AIGraphReducer methodsFor: 'running' stamp: '4/26/2024 09:29'! findCircuits | tarjanCircuits | tarjanCircuits := AITarjan new addNodesFromDifferentGraph: nodes; run; circuits. circuits := tarjanCircuits collect: [ :circuit | circuit collect: [ :each | self findNode: each ] ]! ! !AIGraphReducer methodsFor: 'reducing' stamp: '4/26/2024 09:29'! replaceReferencesToMergedNodes nodes do: [ :reducedNode | self replaceReferencesToMergedNode: reducedNode ]! ! !AIGraphReducerTest methodsFor: 'running' stamp: '4/26/2024 09:29'! setUp super setUp. graphReducer := AIGraphReducer new! ! !AIGraphReducerTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testMergedNodesNotReferencedInNextNodesC2 | graphType graph| graphType := AICyclicNonWeightedComplexFixture new. graph := graphType complexCycleGraph2. graphReducer nodes: graph nodes. graphReducer edges: graph edges from: #first to: #second. graphReducer run. self assertNodes: (graphReducer nodes flatCollect: #adjacentNodes) doesNotInclude: (self mergedNodesIn: graphReducer nodes)! ! !AIGraphReducerTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testComplexCycle | mergedNodes graphType graph| graphType := AICyclicNonWeightedComplexFixture new. graph := graphType complexCycleGraph. graphReducer nodes: graph nodes. graphReducer edges: graph edges from: #first to: #second. graphReducer run. self assert: graphReducer nodes size equals: 5. self assert: (graphReducer nodes anySatisfy: [ :each | each model = $a ]). self assert: (graphReducer nodes anySatisfy: [ :each | each model = $b ]). self assert: (graphReducer nodes anySatisfy: [ :each | each model = $e ]). mergedNodes := graphReducer nodes select: [ :each | each mergedNodes isNotNil ] thenCollect: #model. self assert: (mergedNodes anySatisfy: [ :collapsedNode | collapsedNode includesAll: #( $g $h ) ]). self assert: (mergedNodes anySatisfy: [ :collapsedNode | collapsedNode includesAll: #( $c $d $f ) ])! ! !AIGraphReducerTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testMergedNodesNotReferencedInNextNodes | graphType graph| graphType := AICyclicNonWeightedComplexFixture new. graph := graphType complexCycleGraph. graphReducer nodes: graph nodes. graphReducer edges: graph edges from: #first to: #second. graphReducer run. self assertNodes: (graphReducer nodes flatCollect: #adjacentNodes) doesNotInclude: (self mergedNodesIn: graphReducer nodes)! ! !AIGraphReducerTest methodsFor: 'helpers' stamp: '4/26/2024 09:29'! assertNodes: aNodeList doesNotInclude: anotherNodeList aNodeList collect: [ :each | each model ] thenDo: [ :model | self deny: ((anotherNodeList collect: [ :each | each model ]) includes: model) description: model asString , ' should not be referenced!!' ]! ! !AIGraphReducerTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testComplexCycle2 | graphType graph| graphType := AICyclicNonWeightedComplexFixture new. graph := graphType complexCycleGraph2. graphReducer nodes: graph nodes. graphReducer edges: graph edges from: #first to: #second. graphReducer run. self assert: graphReducer nodes size equals: 6. self assert: (graphReducer nodes at: 6) mergedNodes size equals: 4! ! !AIGraphReducerTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testMergedNodesNotReferencedInNextNodesForSCG | graphType graph| graphType := AICyclicNonWeightedComplexFixture new. graph := graphType stronglyConnectedGraph. graphReducer nodes: graph nodes. graphReducer edges: graph edges from: #first to: #second. graphReducer run. self assertNodes: (graphReducer nodes flatCollect: #adjacentNodes) doesNotInclude: (self mergedNodesIn: graphReducer nodes)! ! !AIGraphReducerTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testStronglyConnectedGraphReferences | reducedNodeI mergedNodes reducedNodeABC reducedNodeDE reducedNodeFGH graphType graph| graphType := AICyclicNonWeightedComplexFixture new. graph := graphType stronglyConnectedGraph. graphReducer nodes: graph nodes. graphReducer edges: graph edges from: #first to: #second. graphReducer run. reducedNodeI := (graphReducer nodes select: [ :each | each model = $i ]) first. mergedNodes := graphReducer nodes select: [ :each | each model isCollection ]. reducedNodeABC := (mergedNodes select: [ :each | each model includesAll: #( $a $b $c ) ]) first. reducedNodeDE := (mergedNodes select: [ :each | each model includesAll: #( $d $e ) ]) first. reducedNodeFGH := (mergedNodes select: [ :each | each model includesAll: #( $f $g $h ) ]) first. self assertCollection: reducedNodeI adjacentNodes hasSameElements: { reducedNodeI. reducedNodeFGH }. "See is there is no duplicated adjacencies" self assert: reducedNodeI adjacentNodes size equals: 2. self assertCollection: reducedNodeABC adjacentNodes hasSameElements: { reducedNodeDE }. "See is there is no duplicated adjacencies" self assert: reducedNodeABC adjacentNodes size equals: 1. self assertCollection: reducedNodeFGH adjacentNodes hasSameElements: { reducedNodeDE. reducedNodeABC }. "See is there is no duplicated adjacencies" self assert: reducedNodeFGH adjacentNodes size equals: 2. self assert: reducedNodeDE adjacentNodes isEmpty! ! !AIGraphReducerTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testGraphReducingWhenNoCycleReferences | reducedNodeA reducedNodeB reducedNodeC reducedNodeD graphType graph| graphType := AINonWeightedDAGFixture new. graph := graphType simpleGraph. graphReducer nodes: graph nodes. graphReducer edges: graph edges from: #first to: #second. graphReducer run. reducedNodeA := (graphReducer nodes select: [ :each | each model = $a ]) first. reducedNodeB := (graphReducer nodes select: [ :each | each model = $b ]) first. reducedNodeC := (graphReducer nodes select: [ :each | each model = $c ]) first. reducedNodeD := (graphReducer nodes select: [ :each | each model = $d ]) first. self assertCollection: reducedNodeA adjacentNodes hasSameElements: { reducedNodeB }. self assertCollection: reducedNodeB adjacentNodes hasSameElements: { reducedNodeC }. self assertCollection: reducedNodeD adjacentNodes hasSameElements: { reducedNodeC }. self assert: reducedNodeC adjacentNodes isEmpty! ! !AIGraphReducerTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testNoCycle | graphType graph| graphType := AICyclicNonWeightedComplexFixture new. graph := graphType complexCycleGraph2. graphReducer nodes: graph nodes. graphReducer edges: graph edges from: #first to: #second. graphReducer run. graphReducer nodes do: [ :node | self deny: (node adjacentNodes includes: node) description: node asString , ' node is in cycle!!' ]! ! !AIGraphReducerTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testAdjacenciesFor | nodes graphType graph| graphType := AICyclicNonWeightedComplexFixture new. graph := graphType complexCycleGraph2. graphReducer nodes: graph nodes. graphReducer edges: graph edges from: #first to: #second. nodes := { (graphReducer findNode: $f). (graphReducer findNode: $g) }. self assert: ((graphReducer adjacenciesFor: nodes) collect: #model as: SortedCollection) asArray equals: #( $a $b $d $e $i )! ! !AIGraphReducerTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testComplexCycleReferences | mergedNodes reducedNodeA reducedNodeB reducedNodeE reducedNodeCDF reducedNodeGH graphType graph| graphType := AICyclicNonWeightedComplexFixture new. graph := graphType complexCycleGraph. graphReducer nodes: graph nodes. graphReducer edges: graph edges from: #first to: #second. graphReducer run. reducedNodeA := (graphReducer nodes select: [ :each | each model = $a ]) first. reducedNodeB := (graphReducer nodes select: [ :each | each model = $b ]) first. reducedNodeE := (graphReducer nodes select: [ :each | each model = $e ]) first. mergedNodes := graphReducer nodes select: [ :each | each model isCollection ]. reducedNodeCDF := (mergedNodes select: [ :each | each model includesAll: #( $d $f $c ) ]) first. reducedNodeGH := (mergedNodes select: [ :each | each model includesAll: #( $g $h ) ]) first. self assertCollection: reducedNodeA adjacentNodes hasSameElements: { reducedNodeB. reducedNodeGH. reducedNodeCDF }. "See is there is no duplicated adjacencies" self assert: reducedNodeA adjacentNodes size equals: 3. self assertCollection: reducedNodeB adjacentNodes hasSameElements: { reducedNodeE }. "See is there is no duplicated adjacencies" self assert: reducedNodeB adjacentNodes size equals: 1. self assert: reducedNodeE adjacentNodes isEmpty. self assertCollection: reducedNodeGH adjacentNodes hasSameElements: { reducedNodeCDF }. "See is there is no duplicated adjacencies" self assert: reducedNodeGH adjacentNodes size equals: 1. self assertCollection: reducedNodeCDF adjacentNodes hasSameElements: { reducedNodeB }. "See is there is no duplicated adjacencies" self assert: reducedNodeCDF adjacentNodes size equals: 1! ! !AIGraphReducerTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testGraphReducingWhenNoCycle | initialGraph graphType graph| graphType := AINonWeightedDAGFixture new. graph := graphType simpleGraph. graphReducer nodes: graph nodes. graphReducer edges: graph edges from: #first to: #second. initialGraph := graphReducer graph copy. graphReducer run. self assert: initialGraph equals: graphReducer graph! ! !AIGraphReducerTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testStronglyConnectedGraph | nodeModels nodeModelsCollection graphType graph| graphType := AICyclicNonWeightedComplexFixture new. graph := graphType stronglyConnectedGraph. graphReducer nodes: graph nodes. graphReducer edges: graph edges from: #first to: #second. graphReducer run. nodeModels := graphReducer nodes collect: #model. nodeModelsCollection := nodeModels select: [ :e | e isCollection ]. self assert: graphReducer nodes size equals: 4. self assert: (nodeModels includes: $i). self assert: (nodeModelsCollection anySatisfy: [ :aNodeModel | aNodeModel includesAll: #( $e $d ) ]). self assert: (nodeModelsCollection anySatisfy: [ :aNodeModel | aNodeModel includesAll: #( $a $b $c ) ]). self assert: (nodeModelsCollection anySatisfy: [ :aNodeModel | aNodeModel includesAll: #( $f $g $h ) ])! ! !AIGraphReducerTest methodsFor: 'helpers' stamp: '4/26/2024 09:29'! mergedNodesIn: aNodeList ^ (aNodeList select: [ :node | node mergedNodes isNotNil ]) flatCollect: #mergedNodes! ! !AIGraphTestFixtureStructure methodsFor: 'inspector' stamp: '4/26/2024 09:29'! inspectGraphContext: aContext aContext withoutEvaluator! ! !AIGraphTestFixtureStructure methodsFor: 'inspector' stamp: '4/26/2024 09:29'! inspectGraph | c | c := self buildGraphCanvas. ^ SpRoassal3InspectorPresenter new canvas: c; yourself! ! !AIGraphTestFixtureStructure methodsFor: 'accessing' stamp: '4/26/2024 09:29'! nodes ^ nodes! ! !AIGraphTestFixtureStructure methodsFor: 'accessing' stamp: '4/26/2024 09:29'! edges ^ edges! ! !AIGraphTestFixtureStructure methodsFor: 'accessing' stamp: '4/26/2024 09:29'! edges: anObject edges := anObject! ! !AIGraphTestFixtureStructure methodsFor: 'accessing' stamp: '4/26/2024 09:29'! nodes: asObject nodes := asObject! ! !AIGraphTestFixtureStructure methodsFor: 'drawing - roassal' stamp: '4/26/2024 09:29'! buildGraphCanvas ^ self subclassResponsibility! ! !AIGraphTestFixtureStructure methodsFor: 'drawing - roassal' stamp: '4/26/2024 09:29'! nodesAsRoassalShapes |nodesAsRoassalShapes | nodesAsRoassalShapes := RSComposite models: nodes forEach: [ :shape :model | | box label | label := RSLabel new text: model asString; color: Color black; yourself. box := RSCircle new extent: label extent y @ label extent y; color: Color white; borderColor: Color black. shape add: box; add: label; yourself ]. ^ nodesAsRoassalShapes! ! !AIGraphWeightedFixtureStructure commentStamp: ''! Structure of Weighted Graphs - nodes - edges - weight! !AIGraphWeightedFixtureStructure methodsFor: 'drawing - roassal' stamp: '4/26/2024 09:29'! buildGraphCanvas | canvas arrowHeight marker attachedPoint interaction | canvas := RSCanvas new. canvas addAll: (self nodesAsRoassalShapes). canvas nodes @ RSDraggable new. canvas @ RSCanvasController new. arrowHeight := 10. marker := RSShapeFactory arrow size: arrowHeight. marker := marker asMarker. marker offset: arrowHeight / 2. attachedPoint := RSBorderAttachPoint new endOffset: arrowHeight / 2; yourself. edges do: [ :edge | canvas add: (RSLine new markerEnd: marker; attachPoint: attachedPoint; color: Color black; from: (canvas nodes shapeFromModel: edge first) children second; to: (canvas nodes shapeFromModel: edge second) children second; model: edge third; yourself) ]. canvas lines pushBack. interaction := RSLabeled new. interaction text: [ :edgeModel | edgeModel asString ]. interaction location inner; middle. interaction shapeBuilder labelShape color: Color black; fontSize: 8. canvas lines @ interaction. RSForceBasedLayout new charge: -200; on: canvas nodes. ^ canvas! ! !AIHits commentStamp: ''! From wikipedia: Hyperlink-Induced Topic Search (HITS; also known as hubs and authorities) is a link analysis algorithm that rates Web pages, developed by Jon Kleinberg. The idea behind Hubs and Authorities stemmed from a particular insight into the creation of web pages when the Internet was originally forming; that is, certain web pages, known as hubs, served as large directories that were not actually authoritative in the information that they held, but were used as compilations of a broad catalog of information that led users direct to other authoritative pages. In other words, a good hub represents a page that pointed to many other pages, while a good authority represents a page that is linked by many different hubs.! !AIHits methodsFor: 'configuration' stamp: '4/26/2024 09:29'! k: aNumberOfIterations k := aNumberOfIterations! ! !AIHits methodsFor: 'configuration' stamp: '4/26/2024 09:29'! k "Number of iterations" ^ k! ! !AIHits methodsFor: 'configuration' stamp: '4/26/2024 09:29'! nodeClass ^ AIHitsNode! ! !AIHits methodsFor: 'running' stamp: '4/26/2024 09:29'! computeHubsFor: aNode aNode hub: (aNode adjacentNodes inject: 0 into: [ :sum :node | sum + node auth ])! ! !AIHits methodsFor: 'running' stamp: '4/26/2024 09:29'! normalizeScores | authNorm hubNorm | authNorm := 0. hubNorm := 0. nodes do: [ :node | authNorm := authNorm + node auth squared. hubNorm := hubNorm + node hub squared ]. authNorm := authNorm sqrt. hubNorm := hubNorm sqrt. "To avoid dividing by 0" authNorm = 0 ifTrue: [ authNorm := 1.0 ]. hubNorm = 0 ifTrue: [ hubNorm := 1.0 ]. nodes do: [ :n | n auth: n auth / authNorm. n hub: n hub / hubNorm ]! ! !AIHits methodsFor: 'running' stamp: '4/26/2024 09:29'! computeAuthoritiesFor: aNode aNode auth: (aNode incomingNodes inject: 0 into: [ :sum :node | sum + node hub ])! ! !AIHits methodsFor: 'initialization' stamp: '4/26/2024 09:29'! initialize super initialize. k := 20! ! !AIHits methodsFor: 'running' stamp: '4/26/2024 09:29'! run self initializeNodes. k timesRepeat: [ nodes do: [ :node | self computeAuthoritiesFor: node ]. nodes do: [ :node | self computeHubsFor: node ]. self normalizeScores ]. ^ nodes! ! !AIHits methodsFor: 'running' stamp: '4/26/2024 09:29'! initializeNodes nodes do: [ :n | n auth: 1.0. n hub: 1.0 ]! ! !AIHitsNode commentStamp: ''! I am a node used for the Hits algorithm! !AIHitsNode methodsFor: 'accessing' stamp: '4/26/2024 09:29'! auth: anObject auth := anObject! ! !AIHitsNode methodsFor: 'accessing' stamp: '4/26/2024 09:29'! hub ^ hub! ! !AIHitsNode methodsFor: 'accessing' stamp: '4/26/2024 09:29'! hub: anObject hub := anObject! ! !AIHitsNode methodsFor: 'initialization' stamp: '4/26/2024 09:29'! initialize super initialize. auth := 1. hub := 1! ! !AIHitsNode methodsFor: 'accessing' stamp: '4/26/2024 09:29'! auth ^ auth! ! !AIHitsNode methodsFor: 'accessing' stamp: '4/26/2024 09:29'! label ^ 'H '! ! !AIHitsNode methodsFor: 'printing' stamp: '4/26/2024 09:29'! printOn: aStream aStream nextPut: $(. self model printOn: aStream. aStream space. aStream << 'auth: '. self auth printOn: aStream showingDecimalPlaces: 2. aStream space. aStream << 'hub: '. self hub printOn: aStream showingDecimalPlaces: 2. aStream nextPutAll: ')'! ! !AIHitsTest methodsFor: 'running' stamp: '4/26/2024 09:29'! setUp super setUp. hits := AIHits new! ! !AIHitsTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testNestedCycle | graphType graph| graphType := AICyclicNonWeightedSimpleFixture new. graph := graphType nestedCycleGraph. hits nodes: graph nodes. hits edges: graph edges from: #first to: #second. hits run. hits nodes do: [ :node | self deny: node hub equals: 1. self deny: node auth equals: 1 ]! ! !AIHitsTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testComplexCycle | graphType graph| graphType := AICyclicNonWeightedComplexFixture new. graph := graphType complexCycleGraph. hits nodes: graph nodes. hits edges: graph edges from: #first to: #second. hits run. hits nodes do: [ :node | self deny: node hub equals: 1. self deny: node auth equals: 1 ]! ! !AIHitsTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testCycle | graphType graph| graphType := AICyclicNonWeightedSimpleFixture new. graph := graphType cycleGraph. hits nodes: graph nodes. hits edges: graph edges from: #first to: #second. hits run. hits nodes do: [ :node | self deny: node hub equals: 1. self deny: node auth equals: 1 ]! ! !AIHitsTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testSimple | graphType graph| graphType := AINonWeightedDAGFixture new. graph := graphType simpleGraph. hits nodes: graph nodes. hits edges: graph edges from: #first to: #second. hits run. hits nodes do: [ :node | self deny: node hub equals: 1. self deny: node auth equals: 1 ]! ! !AIHitsTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testSimpleW | graphType graph| graphType := AICyclicWeightedSimpleFixture new. graph := graphType simpleWeightedGraph. hits nodes: graph nodes. hits edges: graph edges from: #first to: #second weight: #third. hits run. hits nodes do: [ :node | self deny: node hub equals: 1. self deny: node auth equals: 1 ]! ! !AIHitsTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testComplexWCycle | graphType graph | graphType := AICyclicWeightedComplexFixture new. graph :=graphType complexWeightedGraph. hits nodes: graph nodes. hits edges: graph edges from: #first to: #second weight: #third. hits run. hits nodes do: [ :node | self deny: node hub equals: 1. self deny: node auth equals: 1 ]! ! !AIHitsTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testGraphForHits | graphType graph| graphType := AICyclicNonWeightedSimpleFixture new. graph := graphType simpleGraphForHits. hits nodes: graph nodes. hits edges: graph edges from: #first to: #second. hits k: 3. hits run. hits nodes do: [ :node | self deny: node hub equals: 0. self deny: node auth equals: 0 ]! ! !AIKruskal commentStamp: ''! Kruskal's algorithm is a greedy algorithm in graph theory that finds a minimum spanning tree for a connected weighted graph. This means it finds a subset of the edges that forms a tree that includes every vertex, where the total weight of all the edges in the tree is minimized. If the graph is not connected, then it finds a minimum spanning forest (a minimum spanning tree for each connected component). See https://en.wikipedia.org/wiki/Kruskal%27s_algorithm For having the time complexity of O(E log E) this algorithm uses the disjoint-set data structure. See the node class of this algorithm for more information about that data structure. Uses the disjoint-set to check, in linear time, if a cycle will be formed when joining two edges.! !AIKruskal methodsFor: 'configuration' stamp: '4/26/2024 09:29'! edgeClass ^ AIWeightedEdge! ! !AIKruskal methodsFor: 'configuration' stamp: '4/26/2024 09:29'! nodeClass ^ AIDisjointSetNode! ! !AIKruskal methodsFor: 'initialization' stamp: '4/26/2024 09:29'! initialize super initialize. self minSpanningTree! ! !AIKruskal methodsFor: 'running' stamp: '4/26/2024 09:29'! run | treeEdges sortedEdges | treeEdges := OrderedCollection new. nodes do: [ :each | each makeSet ]. sortedEdges := edges asSortedCollection: sortBlock. sortedEdges reject: [ :edge | "Only join the two nodes if they don't belong to the same component" edge from find = edge to find ] thenDo: [ :edge | edge from union: edge to. treeEdges add: edge ]. ^ treeEdges! ! !AIKruskal methodsFor: 'configuration' stamp: '4/26/2024 09:29'! maxSpanningTree sortBlock := [ :e1 :e2 | e1 weight > e2 weight ]! ! !AIKruskal methodsFor: 'configuration' stamp: '4/26/2024 09:29'! minSpanningTree sortBlock := [ :e1 :e2 | e1 weight < e2 weight ]! ! !AIKruskalTest methodsFor: 'running' stamp: '4/26/2024 09:29'! setUp super setUp. kruskal := AIKruskal new. nodes := OrderedCollection new. nodes add: AIDisjointSetNode new. nodes add: AIDisjointSetNode new. nodes add: AIDisjointSetNode new. nodes add: AIDisjointSetNode new! ! !AIKruskalTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testMinSpanningTreeSimple | tree expectedEdges graphType graph | graphType := AICyclicWeightedSimpleFixture new. graph :=graphType simpleWeightedGraph. kruskal nodes: graph nodes. kruskal edges: graph edges from: #first to: #second weight: #third. tree := kruskal run collect: [ :e | e asTuple ]. expectedEdges := #( #( 4 5 1 ) #( 5 1 2 ) #( 2 3 2 ) #( 2 4 3 ) ). self assertCollection: tree hasSameElements: expectedEdges. self assert: (tree inject: 0 into: [ :sum :edge | sum + edge third ]) equals: 8! ! !AIKruskalTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testMaxSpanningTreeSimple | tree expectedEdges graphType graph | graphType := AICyclicWeightedSimpleFixture new. graph :=graphType simpleWeightedGraph. kruskal nodes: graph nodes. kruskal edges: graph edges from: #first to: #second weight: #third. kruskal maxSpanningTree. tree := kruskal run collect: [ :e | e asTuple ]. expectedEdges := #( #( 1 2 5 ) #( 3 4 5 ) #( 1 3 4 ) #( 1 5 3 ) ). self assertCollection: tree hasSameElements: expectedEdges. self assert: (tree inject: 0 into: [ :sum :edge | sum + edge third ]) equals: 17! ! !AIKruskalTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testMaxSpanningTreeComplex | tree expectedEdges graphType graph | graphType := AICyclicWeightedComplexFixture new. graph :=graphType complexWeightedGraph. kruskal nodes: graph nodes. kruskal edges: graph edges from: #first to: #second weight: #third. kruskal maxSpanningTree. tree := kruskal run collect: [ :e | e asTuple ]. expectedEdges := #( #( $a $b 30 ) #( $b $s 1 ) #( $b $c 30 ) #( $d $e 30 ) #( $d $f 20 ) #( $d $j 10 ) #( $e $a 15 ) #( $f $m 8 ) #( $g $h 20 ) #( $g $r 3 ) #( $i $a 14 ) #( $i $k 4 ) #( $j $q 5 ) #( $k $l 10 ) #( $k $g 5 ) #( $m $n 7 ) #( $m $o 6 ) #( $p $b 5 ) ). self assertCollection: tree hasSameElements: expectedEdges. self assert: (tree inject: 0 into: [ :sum :edge | sum + edge third ]) equals: 223! ! !AIKruskalTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testMinSpanningTreeComplex | tree graphType graph | graphType := AICyclicWeightedComplexFixture new. graph :=graphType complexWeightedGraph. kruskal nodes: graph nodes. kruskal edges: graph edges from: #first to: #second weight: #third. tree := kruskal run collect: [ :e | e asTuple ]. self assert: tree size equals: kruskal nodes size - 1. self assert: (tree inject: 0 into: [ :sum :edge | sum + edge third ]) equals: 164! ! !AIKruskalTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testMinSpanningTreeComplexDisconnected | tree graphType graph | graphType := AIWeightedDAGFixture new. graph :=graphType withoutCyclesComplexWeightedGraph. kruskal nodes: graph nodes. kruskal edges: graph edges from: #first to: #second weight: #third. tree := kruskal run collect: [ :e | e asTuple ]. "The result is 2 trees. One with a total weight of 20 and the other with a total weight of 75" self assert: (tree inject: 0 into: [ :sum :edge | sum + edge third ]) equals: 95! ! !AILongestPathInDAG commentStamp: ''! This algorithm works only in weighted DAG (Directed Acyclic graph). The algorithm is simple and it has a complexity of O(V + E). You have to define a start node. Then, for obtaining the longest path from the start node to another node, you have to define an end node and the call the `AILongestPathInDAG>>#reconstructPath` method. See the test class for more examples. The algorithm is: 1) Initialize the initial distance to every node to be infinity and the distance of the start node to be 0. 2) Create a topological order of all nodes. 3) For every node u in topological order: - Do following for every adjacent node v of u - IF (v pathWeight > u pathWeight + (-1)*weight(u, v)) THEN v pathWeight: u pathWeight + weight(u, v) ! !AILongestPathInDAG methodsFor: 'accessing' stamp: '4/26/2024 09:29'! start: aModel start := self findNode: aModel! ! !AILongestPathInDAG methodsFor: 'configuration' stamp: '4/26/2024 09:29'! edgeClass ^ AIWeightedEdge! ! !AILongestPathInDAG methodsFor: 'configuration' stamp: '4/26/2024 09:29'! nodeClass ^ AIPathDistanceNode! ! !AILongestPathInDAG methodsFor: 'accessing' stamp: '4/26/2024 09:29'! start ^ start! ! !AILongestPathInDAG methodsFor: 'accessing' stamp: '4/26/2024 09:29'! end: aModel end := self findNode: aModel! ! !AILongestPathInDAG methodsFor: 'running' stamp: '4/26/2024 09:29'! initializePathWeights nodes do: [ :node | node pathDistance: Float infinity ]. start pathDistance: 0! ! !AILongestPathInDAG methodsFor: 'running' stamp: '4/26/2024 09:29'! runFrom: startModel to: endModel self runFrom: startModel. self end: endModel. ^ self reconstructPath! ! !AILongestPathInDAG methodsFor: 'running' stamp: '4/26/2024 09:29'! reconstructPath | path previous | "If no path exists between the start and the end node" end previousNode ifNil: [ ^ #( ) ]. path := LinkedList empty. previous := end. path addFirst: end model. [ previous = start ] whileFalse: [ previous := previous previousNode. path addFirst: previous model ]. ^ path! ! !AILongestPathInDAG methodsFor: 'running' stamp: '4/26/2024 09:29'! run | stack sortedNode | self initializePathWeights. stack := self topologicalSortedNodes. [ stack isNotEmpty ] whileTrue: [ sortedNode := self findNode: stack removeFirst. sortedNode outgoingEdges do: [ :nextEdge | nextEdge to pathDistance > (sortedNode pathDistance + (-1 * nextEdge weight)) ifTrue: [ self updatePathDistance: nextEdge previousNode: sortedNode ] ] ]! ! !AILongestPathInDAG methodsFor: 'accessing' stamp: '4/26/2024 09:29'! end ^ end! ! !AILongestPathInDAG methodsFor: 'running' stamp: '4/26/2024 09:29'! runFrom: startModel self start: startModel. self run! ! !AILongestPathInDAG methodsFor: 'running' stamp: '4/26/2024 09:29'! topologicalSortedNodes | topSorter | topSorter := AITopologicalSorting new addNodesFromDifferentGraph: nodes; yourself. topSorter run. ^ topSorter topologicalSortedElements! ! !AILongestPathInDAG methodsFor: 'running' stamp: '4/26/2024 09:29'! updatePathDistance: edge previousNode: previousNode edge to pathDistance: previousNode pathDistance + edge weight. edge to previousNode: previousNode! ! !AILongestPathInDAGTest methodsFor: 'running' stamp: '4/26/2024 09:29'! setUp super setUp. longestPathAlgo := AILongestPathInDAG new! ! !AILongestPathInDAGTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testWeightedDAG | longestPath graphType graph | graphType := AIWeightedDAGFixture new. graph :=graphType weightedDAG. longestPathAlgo nodes: graph nodes. longestPathAlgo edges: graph edges from: #first to: #second weight: #third. longestPathAlgo start: $A; end: $F; run. longestPath := longestPathAlgo reconstructPath. self assert: (longestPathAlgo findNode: $F) pathDistance equals: 22. self assert: longestPath asArray equals: #( $A $B $D $E $F ). longestPathAlgo end: $E. longestPath := longestPathAlgo reconstructPath. self assert: (longestPathAlgo findNode: $E) pathDistance equals: 15. self assert: longestPath asArray equals: #( $A $B $D $E ). longestPathAlgo runFrom: $B to: $F. longestPath := longestPathAlgo reconstructPath. self assert: (longestPathAlgo findNode: $F) pathDistance equals: 21. self assert: longestPath asArray equals: #( $B $D $E $F ). longestPathAlgo end: $G. longestPath := longestPathAlgo reconstructPath. self assert: (longestPathAlgo findNode: $G) pathDistance equals: Float infinity. self assert: longestPath asArray equals: #( )! ! !AILongestPathInDAGTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testWithoutCyclesComplexWeightedGraph | longestPath graphType graph | graphType := AIWeightedDAGFixture new. graph :=graphType withoutCyclesComplexWeightedGraph. longestPathAlgo nodes: graph nodes. longestPathAlgo edges: graph edges from: #first to: #second weight: #third. longestPathAlgo start: $b; end: $s; run. longestPath := longestPathAlgo reconstructPath. self assert: (longestPathAlgo findNode: $s) pathDistance equals: 10. self assert: longestPath asArray equals: #( $b $c $q $p $s )! ! !AILongestPathInDCG commentStamp: ''! A variation of Bellman Ford algorithm that calculates the longest path in any kind of graph (including Directed Cyclic Graphs (DCG)). The graph edges can have negative weights and this algo hanldes negative cycles. If a negative cycle is detected, the path distance of that node is set to negative infinity.! !AILongestPathInDCG methodsFor: 'running' stamp: '4/26/2024 09:29'! relaxEdges | anEdgeHasBeenRelaxed | "Relax the edges V-1 times at worst case" nodes size - 1 timesRepeat: [ anEdgeHasBeenRelaxed := false. edges do: [ :edge | edge from pathDistance + (-1 * edge weight) < edge to pathDistance ifTrue: [ edge to pathDistance: edge from pathDistance + (-1 * edge weight). edge to previousNode: edge from. anEdgeHasBeenRelaxed := true ] ]. "If no edge has been relaxed means that we can stop the iteration before V-1 times" anEdgeHasBeenRelaxed ifFalse: [ ^ self ] ]! ! !AILongestPathInDCG methodsFor: 'accessing' stamp: '4/26/2024 09:29'! start: aModel start := self findNode: aModel. start pathDistance: 0! ! !AILongestPathInDCG methodsFor: 'configuration' stamp: '4/26/2024 09:29'! edgeClass ^ AIWeightedEdge! ! !AILongestPathInDCG methodsFor: 'configuration' stamp: '4/26/2024 09:29'! nodeClass ^ AIPathDistanceNode! ! !AILongestPathInDCG methodsFor: 'accessing' stamp: '4/26/2024 09:29'! end: aModel end := (self findNode: aModel)! ! !AILongestPathInDCG methodsFor: 'actions' stamp: '4/26/2024 09:29'! reset self nodes do: [ :node | node pathDistance: Float infinity; previousNode: nil ]! ! !AILongestPathInDCG methodsFor: 'running' stamp: '4/26/2024 09:29'! runFrom: startModel to: endModel self runFrom: startModel. self end: endModel. ^ self reconstructPath! ! !AILongestPathInDCG methodsFor: 'actions' stamp: '4/26/2024 09:29'! reconstructPath | path previous | "If no path exists between the start and the end node" end pathDistance = Float infinity ifTrue: [ ^ #( ) ]. "If the end node is part of a negative cycle" end pathDistance = Float negativeInfinity ifTrue: [ ^ #( ) ]. path := LinkedList empty. previous := end. path addFirst: end model. [ previous = start ] whileFalse: [ previous := previous previousNode. path addFirst: previous model ]. ^ path! ! !AILongestPathInDCG methodsFor: 'actions' stamp: '4/26/2024 09:29'! pathPositive self nodes do: [ :node | node pathDistance: -1 * node pathDistance ]! ! !AILongestPathInDCG methodsFor: 'running' stamp: '4/26/2024 09:29'! run self reset. start pathDistance: 0. self relaxEdges. "Run the algorithm one more time to detect if there is any negative cycles. The variation is if we can relax one more time an edge, means that the edge is part of a negative cycle. So, we put negative infinity as the path distance" self relaxEdgesToNegativeInfinity. self pathPositive! ! !AILongestPathInDCG methodsFor: 'running' stamp: '4/26/2024 09:29'! runFrom: startModel self start: startModel. self run! ! !AILongestPathInDCG methodsFor: 'running' stamp: '4/26/2024 09:29'! relaxEdgesToNegativeInfinity "This method is called after a first relaxation has ocurred already. The algorithm is the same as the previous one but with the only difference that now if an edge can be relaxed we set the path distance as negative infinity because means that the edge is part of a negative cycle." | anEdgeHasBeenRelaxed | "Relax the edges V-1 times at worst case" nodes size - 1 timesRepeat: [ anEdgeHasBeenRelaxed := false. edges do: [ :edge | edge from pathDistance + (-1 * edge weight) < edge to pathDistance ifTrue: [ edge to pathDistance: Float negativeInfinity. anEdgeHasBeenRelaxed := true ] ]. "If no edge has been relaxed means that we can stop the iteration before V-1 times" anEdgeHasBeenRelaxed ifFalse: [ ^ self ] ]! ! !AILongestPathInDCGTest methodsFor: 'running' stamp: '4/26/2024 09:29'! setUp super setUp. longestPathAlgo := AILongestPathInDCG new! ! !AILongestPathInDCGTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testNegativeUnconnectedWeightedGraph |graphType graph | graphType := AICyclicWeightedSimpleFixture new. graph :=graphType negativeUnconnectedWeightedGraph. longestPathAlgo nodes: graph nodes. longestPathAlgo edges: graph edges from: #first to: #second weight: #third. longestPathAlgo start: 0. longestPathAlgo run. self assert: (longestPathAlgo findNode: 1) pathDistance equals: 5. self assert: (longestPathAlgo findNode: 2) pathDistance equals: 25. self assert: (longestPathAlgo findNode: 3) pathDistance equals: 35. self assert: (longestPathAlgo findNode: 4) pathDistance equals: 100. self assert: (longestPathAlgo findNode: 5) pathDistance equals: 35. self assert: (longestPathAlgo findNode: 6) pathDistance equals: 65. self assert: (longestPathAlgo findNode: 7) pathDistance equals: 15. "No possible path between 0 and 8" self assert: (longestPathAlgo findNode: 8) pathDistance equals: Float infinity negated. self assert: (longestPathAlgo findNode: 9) pathDistance equals: 200! ! !AILongestPathInDCGTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testNegativeWeightedGraph |graphType graph | graphType := AICyclicWeightedSimpleFixture new. graph :=graphType negativeWeightedGraph. longestPathAlgo nodes: graph nodes. longestPathAlgo edges: graph edges from: #first to: #second weight: #third. longestPathAlgo start: 0. longestPathAlgo run. self assert: (longestPathAlgo findNode: 1) pathDistance equals: 5. self assert: (longestPathAlgo findNode: 2) pathDistance equals: 25. self assert: (longestPathAlgo findNode: 3) pathDistance equals: 35. self assert: (longestPathAlgo findNode: 4) pathDistance equals: 100. self assert: (longestPathAlgo findNode: 5) pathDistance equals: 35. self assert: (longestPathAlgo findNode: 6) pathDistance equals: 65. self assert: (longestPathAlgo findNode: 7) pathDistance equals: 15. self assert: (longestPathAlgo findNode: 8) pathDistance equals: 85. self assert: (longestPathAlgo findNode: 9) pathDistance equals: 200! ! !AILongestPathInDCGTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testNegativeWeightedGraphReconstrucPath |graphType graph | graphType := AICyclicWeightedSimpleFixture new. graph :=graphType negativeWeightedGraph. longestPathAlgo nodes: graph nodes. longestPathAlgo edges: graph edges from: #first to: #second weight: #third. longestPathAlgo runFrom: 0 to: 8. self assertCollection: longestPathAlgo reconstructPath asArray equals: #( 0 1 5 8). longestPathAlgo reset. longestPathAlgo runFrom: 0 to: 7. self assertCollection: longestPathAlgo reconstructPath asArray equals: #( 0 1 6 7 )! ! !AILongestPathInDCGTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testNegativeWeightedGraph2 |graphType graph | graphType := AICyclicWeightedSimpleFixture new. graph :=graphType negativeWeightedGraph2. longestPathAlgo nodes: graph nodes. longestPathAlgo edges: graph edges from: #first to: #second weight: #third. longestPathAlgo start: 0. longestPathAlgo run. self assert: (longestPathAlgo findNode: 1) pathDistance equals: 5. self assert: (longestPathAlgo findNode: 2) pathDistance equals: 25. self assert: (longestPathAlgo findNode: 3) pathDistance equals: 35. self assert: (longestPathAlgo findNode: 4) pathDistance equals: 100. self assert: (longestPathAlgo findNode: 5) pathDistance equals: 35. self assert: (longestPathAlgo findNode: 6) pathDistance equals: 65. self assert: (longestPathAlgo findNode: 7) pathDistance equals: 15. "No possible path between 0 and 8" self assert: (longestPathAlgo findNode: 8) pathDistance equals: Float infinity negated. self assert: (longestPathAlgo findNode: 9) pathDistance equals: 200! ! !AINetworkFlowEdge commentStamp: ''! This class represents an edge in the Dinic's Algorithm. Each edge has a capacity and a flow property.! !AINetworkFlowEdge methodsFor: 'accessing' stamp: '4/26/2024 09:29'! capacity: aValue capacity := aValue! ! !AINetworkFlowEdge methodsFor: 'accessing' stamp: '4/26/2024 09:29'! capacity ^capacity! ! !AINetworkFlowEdge methodsFor: 'accessing' stamp: '4/26/2024 09:29'! flow ^flow ! ! !AINetworkFlowEdge methodsFor: 'initialization' stamp: '4/26/2024 09:29'! initialize flow:=0! ! !AINetworkFlowEdge methodsFor: 'accessing' stamp: '4/26/2024 09:29'! asTuple ^{from model. to model. capacity. flow}! ! !AINetworkFlowEdge methodsFor: 'accessing' stamp: '4/26/2024 09:29'! flow: anObject flow:=anObject ! ! !AINodeWithPrevious commentStamp: ''! A basic node able to host the model and to represent edges with no additional class. Edges are navigable in both way through the nextNodes and prevousNodes instances variables.! !AINodeWithPrevious methodsFor: 'testing' stamp: '4/26/2024 09:29'! isRoot ^ incomingNodes isEmpty! ! !AINodeWithPrevious methodsFor: 'initialization' stamp: '4/26/2024 09:29'! initialize super initialize. incomingNodes := OrderedCollection new! ! !AINodeWithPrevious methodsFor: 'accessing' stamp: '4/26/2024 09:29'! incomingNodes ^ incomingNodes! ! !AINodeWithPrevious methodsFor: 'accessing' stamp: '4/26/2024 09:29'! from: sourceNode incomingNodes add: sourceNode! ! !AINodeWithPrevious methodsFor: 'setting' stamp: '4/26/2024 09:29'! incomingNodes: aNodeList incomingNodes := aNodeList! ! !AINodeWithPrevious methodsFor: 'testing' stamp: '4/26/2024 09:29'! isLeaf ^ incomingNodes isEmpty! ! !AINonWeightedDAGFixture commentStamp: ''! Graph Class: 1. Acyclic 2. Non-Weighted 3. Directed graphs! !AINonWeightedDAGFixture methodsFor: 'fixtures' stamp: '4/26/2024 09:29'! withoutCyclesMediumGraph "for longest path algo" "https://i.imgur.com/Vx3QwZF.jpeg" | nodes edges graph| nodes := #( $a $b $c $d $e $f $g $h ). edges := #( #( $a $e ) #( $a $g ) #( $b $c ) #( $b $h ) #( $d $f ) #( $g $f ) #( $h $d ) ). graph:= AIGraphNonWeightedFixtureStructure new. graph nodes: nodes. graph edges: edges. ^graph! ! !AINonWeightedDAGFixture methodsFor: 'fixtures' stamp: '4/26/2024 09:29'! withoutCyclesComplexGraph "for longest path algo" "This is a disconnected graph" "https://i.imgur.com/yTLwTVA.jpeg" | nodes edges graph| nodes := #( $a $b $c $d $e $f $g $h $i $j $k $l $m $n $o $p $q $r $s ). edges := #( #( $a $e ) #( $a $g ) #( $b $c ) #( $b $h ) #( $c $o ) #( $c $q ) #( $d $f ) #( $d $i ) #( $f $i ) #( $g $f ) #( $h $d ) #( $i $r ) #( $j $k ) #( $j $l ) #( $l $m ) #( $l $n ) #( $o $p ) #( $q $p ) #( $p $s ) #( $r $s ) ). graph:= AIGraphNonWeightedFixtureStructure new. graph nodes: nodes. graph edges: edges. ^graph! ! !AINonWeightedDAGFixture methodsFor: 'fixtures' stamp: '4/26/2024 09:29'! moduleGraph2 "sample graph from Habib et al for modular decomposition" | nodes edges graph| nodes := #( $u $w $v $z $a $b $c $d ). edges := #( #( $u $w ) #( $w $a ) #( $w $b ) #( $w $c ) #( $w $d ) #( $w $v ) #( $v $b ) #( $v $d ) #( $v $z ) #( $z $b ) #( $a $d ) #( $c $v ) #( $c $z ) #( $d $b ) #( $d $z ) ). graph:= AIGraphNonWeightedFixtureStructure new. graph nodes: nodes. graph edges: edges. ^graph! ! !AINonWeightedDAGFixture methodsFor: 'initialization' stamp: '4/26/2024 09:29'! initialize super initialize . moduleGraph2 := self moduleGraph2 . simpleGraph := self simpleGraph . withoutCyclesComplexGraph := self withoutCyclesComplexGraph . withoutCyclesMediumGraph := self withoutCyclesMediumGraph .! ! !AINonWeightedDAGFixture methodsFor: 'fixtures' stamp: '4/26/2024 09:29'! simpleGraph "https://i.imgur.com/uJwu5xS.jpeg" | nodes edges graph| nodes := $a to: $d. edges := #( #( $a $b ) #( $b $c ) #( $d $c ) ). graph:= AIGraphNonWeightedFixtureStructure new. graph nodes: nodes. graph edges: edges. ^graph! ! !AINotADAG commentStamp: ''! I am raised when an algorithm should have run on a DAG but the collection was not a DAG.! !AINotADAG methodsFor: 'accessing' stamp: '4/26/2024 09:29'! messageText ^ messageText ifNil: [ messageText := 'Not a DAG (Directed Acyclic Graph)' ]! ! !AIPathDistanceNode commentStamp: ''! I am a node that is used in the Dijkstra algorithm! !AIPathDistanceNode methodsFor: 'accessing' stamp: '4/26/2024 09:29'! visited ^ visited! ! !AIPathDistanceNode methodsFor: 'accessing' stamp: '4/26/2024 09:29'! visited: anObject visited := anObject! ! !AIPathDistanceNode methodsFor: 'accessing' stamp: '4/26/2024 09:29'! previousNode ^ previousNode! ! !AIPathDistanceNode methodsFor: 'accessing' stamp: '4/26/2024 09:29'! to: aNode edge: anEdge outgoingEdges add: anEdge. adjacentNodes add: aNode! ! !AIPathDistanceNode methodsFor: 'accessing' stamp: '4/26/2024 09:29'! priority ^ priority ! ! !AIPathDistanceNode methodsFor: 'accessing' stamp: '4/26/2024 09:29'! pathDistance: anObject pathDistance := anObject! ! !AIPathDistanceNode methodsFor: 'initialization' stamp: '4/26/2024 09:29'! initialize super initialize. outgoingEdges := OrderedCollection new. pathDistance := Float infinity. visited := false. priority := Float infinity. ! ! !AIPathDistanceNode methodsFor: 'accessing' stamp: '4/26/2024 09:29'! previousNode: aNode previousNode := aNode! ! !AIPathDistanceNode methodsFor: 'accessing' stamp: '4/26/2024 09:29'! priority: anInteger priority := anInteger.! ! !AIPathDistanceNode methodsFor: 'accessing' stamp: '4/26/2024 09:29'! pathDistance ^ pathDistance! ! !AIPathDistanceNode methodsFor: 'accessing' stamp: '4/26/2024 09:29'! outgoingEdges ^ outgoingEdges! ! !AIPathDistanceNode methodsFor: 'printing' stamp: '4/26/2024 09:29'! printOn: aStream super printOn: aStream. aStream nextPutAll: ' weight: '; nextPutAll: pathDistance asString! ! !AIPrim commentStamp: ''! Prim's algorithm (also known as Jarník's algorithm) is a greedy algorithm that finds a minimum spanning tree for a weighted undirected graph. This means it finds a subset of the edges that forms a tree that includes every vertex, where the total weight of all the edges in the tree is minimized. The algorithm operates by building this tree one vertex at a time, from an arbitrary starting vertex, at each step adding the cheapest possible connection from the tree to another vertex. For more, see: https://en.wikipedia.org/wiki/Prim%27s_algorithm! !AIPrim methodsFor: 'configuration' stamp: '4/26/2024 09:29'! edgeClass ^ AIWeightedEdge! ! !AIPrim methodsFor: 'configuration' stamp: '4/26/2024 09:29'! nodeClass ^ AIBFSNode! ! !AIPrim methodsFor: 'initialization' stamp: '4/26/2024 09:29'! initialize super initialize! ! !AIPrim methodsFor: 'running' stamp: '4/26/2024 09:29'! run | curNode curEdge treeEdges fromNode toNode primEdge | nodes do: [ :each | each distance: Float infinity ]. treeEdges := OrderedCollection new. nodes first distance: 0; previousNode: nil. nodes size timesRepeat: [ curNode := self minNode. curNode visited: true. curNode previousNode ifNotNil: [ primEdge := { curNode previousNode model. curNode model. curNode distance }. treeEdges add: (self findEdge: primEdge) ]. edges do: [ :edge | curEdge := edge asTuple. fromNode := self findNode: curEdge first. toNode := self findNode: curEdge second. fromNode == curNode & (curEdge third < toNode distance) & toNode visited not ifTrue: [ toNode previousNode: curNode. toNode distance: curEdge third ] ] ]. ^ treeEdges! ! !AIPrim methodsFor: 'accessing' stamp: '4/26/2024 09:29'! minNode | lowNode lowKey | lowKey := Float infinity. nodes do: [ :each | each distance < lowKey & each visited not ifTrue: [ lowKey := each distance. lowNode := each ] ]. ^ lowNode! ! !AIPrimTest methodsFor: 'running' stamp: '4/26/2024 09:29'! setUp super setUp. prim := AIPrim new.! ! !AIPrimTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testMinimumSpanningTreeSimple | tree expectedEdges graphType graph | graphType := AICyclicWeightedSimpleFixture new. graph :=graphType simpleWeightedGraph2. prim nodes: graph nodes. prim edges: graph edges from: #first to: #second weight: #third. tree := prim run collect: [ :e | e asTuple ]. expectedEdges := #( #( 1 2 3 ) #( 2 3 1 ) #( 3 4 2 ) #( 4 5 3 ) ). self assertCollection: tree hasSameElements: expectedEdges. self assert: (tree inject: 0 into: [ :sum :edge | sum + edge third ]) equals: 9! ! !AIPrimTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testMinSpanningTreeComplex2 | tree graphType graph | graphType := AICyclicWeightedComplexFixture new. graph :=graphType complexWeightedGraph4. prim nodes: graph nodes. prim edges: graph edges from: #first to: #second weight: #third. tree := prim run collect: [ :e | e asTuple ]. self assert: tree size equals: 11. self assert: (tree inject: 0 into: [ :sum :edge | sum + edge third ]) equals: 112! ! !AIPrimTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testMinimumSpanningTreeComplex | tree expectedEdges graphType graph | graphType := AICyclicWeightedComplexFixture new. graph :=graphType complexWeightedGraph3. prim nodes: graph nodes. prim edges: graph edges from: #first to: #second weight: #third. tree := prim run collect: [ :e | e asTuple ]. expectedEdges := #( #( $a $d 1 ) #( $d $e 1 ) #( $d $b 2 ) #( $e $c 5 ) ). self assertCollection: tree hasSameElements: expectedEdges. self assert: (tree inject: 0 into: [ :sum :edge | sum + edge third ]) equals: 9! ! !AIReducedGraphNode commentStamp: ''! Node used by the MalReducedGraph algorithm. It has an additional instance variable to track merged nodes.! !AIReducedGraphNode methodsFor: 'accessing' stamp: '4/26/2024 09:29'! mergedNodes ^ mergedNodes! ! !AIReducedGraphNode methodsFor: 'setting' stamp: '4/26/2024 09:29'! mergedNodes: aNodeList mergedNodes := aNodeList! ! !AIReducedGraphNode methodsFor: 'accessing' stamp: '4/26/2024 09:29'! label ^ 'Merged nodes: '! ! !AIReducedGraphNode methodsFor: 'printing' stamp: '4/26/2024 09:29'! printOn: stream stream nextPutAll: self label. model isCollection ifTrue: [ model do: [ :node | node printOn: stream ] separatedBy: [ stream << ', ' ] ] ifFalse: [ model printOn: stream ]! ! !AIShortestPathInDAG commentStamp: ''! This algorithm works only in weighted DAG (Directed Acyclic graph). The algorithm is simple and it has a complexity of O(V + E). You have to define a start node. Then, for obtaining the shortest path from the start node to another node, you have to define an end node and the call the `AIShortestPathInDAG>>#reconstructPath` method. See the test class for more examples. The algorithm is: 1) Initialize the initial distance to every node to be infinity and the distance of the start node to be 0. 2) Create a topological order of all nodes. 3) For every node u in topological order: - Do following for every adjacent node v of u - IF (v pathWeight > u pathWeight + weight(u, v)) THEN v pathWeight: u pathWeight + weight(u, v) ! !AIShortestPathInDAG methodsFor: 'accessing' stamp: '4/26/2024 09:29'! start: aModel start := self findNode: aModel! ! !AIShortestPathInDAG methodsFor: 'configuration' stamp: '4/26/2024 09:29'! edgeClass ^ AIWeightedEdge! ! !AIShortestPathInDAG methodsFor: 'configuration' stamp: '4/26/2024 09:29'! nodeClass ^ AIPathDistanceNode! ! !AIShortestPathInDAG methodsFor: 'accessing' stamp: '4/26/2024 09:29'! start ^ start! ! !AIShortestPathInDAG methodsFor: 'accessing' stamp: '4/26/2024 09:29'! end: aModel end := self findNode: aModel! ! !AIShortestPathInDAG methodsFor: 'running' stamp: '4/26/2024 09:29'! initializePathWeights nodes do: [ :node | node pathDistance: Float infinity ]. start pathDistance: 0! ! !AIShortestPathInDAG methodsFor: 'running' stamp: '4/26/2024 09:29'! runFrom: startModel to: endModel self runFrom: startModel. self end: endModel. ^ self reconstructPath! ! !AIShortestPathInDAG methodsFor: 'running' stamp: '4/26/2024 09:29'! reconstructPath | path previous | "If no path exists between the start and the end node" end previousNode ifNil: [ ^ #( ) ]. path := LinkedList empty. previous := end. path addFirst: end model. [ previous = start ] whileFalse: [ previous := previous previousNode. path addFirst: previous model ]. ^ path! ! !AIShortestPathInDAG methodsFor: 'running' stamp: '4/26/2024 09:29'! run | stack sortedNode | self initializePathWeights. stack := self topologicalSortedNodes. [ stack isNotEmpty ] whileTrue: [ sortedNode := self findNode: stack removeFirst. sortedNode outgoingEdges do: [ :nextEdge | nextEdge to pathDistance > (sortedNode pathDistance + nextEdge weight) ifTrue: [ self updatePathDistance: nextEdge previousNode: sortedNode ] ] ]! ! !AIShortestPathInDAG methodsFor: 'accessing' stamp: '4/26/2024 09:29'! end ^ end! ! !AIShortestPathInDAG methodsFor: 'running' stamp: '4/26/2024 09:29'! runFrom: startModel self start: startModel. self run! ! !AIShortestPathInDAG methodsFor: 'running' stamp: '4/26/2024 09:29'! topologicalSortedNodes | topSorter | topSorter := AITopologicalSorting new addNodesFromDifferentGraph: nodes; yourself. topSorter run. ^ topSorter topologicalSortedElements! ! !AIShortestPathInDAG methodsFor: 'running' stamp: '4/26/2024 09:29'! updatePathDistance: edge previousNode: previousNode edge to pathDistance: previousNode pathDistance + edge weight. edge to previousNode: previousNode! ! !AIShortestPathInDAGTest commentStamp: ''! An AIShortestPathInDAGTest is a test class for testing the behavior of AIShortestPathInDAG! !AIShortestPathInDAGTest methodsFor: 'running' stamp: '4/26/2024 09:29'! setUp super setUp. shortestPathAlgo := AIShortestPathInDAG new! ! !AIShortestPathInDAGTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testWeightedDAG | shortestPath graphType graph | graphType := AIWeightedDAGFixture new. graph :=graphType weightedDAG. shortestPathAlgo nodes: graph nodes. shortestPathAlgo edges: graph edges from: #first to: #second weight: #third. shortestPathAlgo start: $A; end: $F; run. shortestPath := shortestPathAlgo reconstructPath. self assert: (shortestPathAlgo findNode: $F) pathDistance equals: 19. self assert: shortestPath asArray equals: #( $A $B $E $F ). shortestPathAlgo end: $E. shortestPath := shortestPathAlgo reconstructPath. self assert: (shortestPathAlgo findNode: $E) pathDistance equals: 12. self assert: shortestPath asArray equals: #( $A $B $E ). shortestPathAlgo runFrom: $B to: $F. shortestPath := shortestPathAlgo reconstructPath. self assert: (shortestPathAlgo findNode: $F) pathDistance equals: 18. self assert: shortestPath asArray equals: #( $B $E $F ). shortestPathAlgo end: $G. shortestPath := shortestPathAlgo reconstructPath. self assert: (shortestPathAlgo findNode: $G) pathDistance equals: Float infinity. self assert: shortestPath asArray equals: #( )! ! !AIShortestPathInDAGTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testWithoutCyclesComplexWeightedGraph | shortestPath graphType graph | graphType := AIWeightedDAGFixture new. graph :=graphType withoutCyclesComplexWeightedGraph. shortestPathAlgo nodes: graph nodes. shortestPathAlgo edges: graph edges from: #first to: #second weight: #third. shortestPathAlgo start: $b; end: $s; run. shortestPath := shortestPathAlgo reconstructPath. self assert: (shortestPathAlgo findNode: $s) pathDistance equals: 10. self assert: shortestPath asArray equals: #( $b $c $q $p $s )! ! !AITarjan commentStamp: ''! I implement the well known Tarjan's algorithm. My purpose is to find the strongly connected components (aka circuits /cycles) of a graph in O(m+n). See https://en.wikipedia.org/wiki/Tarjan%27s_strongly_connected_components_algorithm for more details. Instance variable `sccs` means strongly connected components. It is an array with all the strngly connected components that the algorithm found. The method `#stronglyConnectedComponents` will return a collection with all the strongly connected components of the graph. See in my test class examples of how to use me. But in a nutshell: ``` tarjan := AITarjan new nodes: #( 1 2 3 ); edges: { (1 -> 2) . (1 -> 3) . (2 -> 3) } from: #key to: #value; yourself. tarjan run. tarjan stronglyConnectedComponents ``` ! !AITarjan methodsFor: 'testing' stamp: '4/26/2024 09:29'! isRootNode: aTarjanNode "Finding a 'root' node means that we found a strongly connected component. The 'root' node represents the beginning of that strongly connected component" ^ aTarjanNode tarjanIndex = aTarjanNode tarjanLowlink! ! !AITarjan methodsFor: 'running' stamp: '4/26/2024 09:29'! traverse: aTarjanNode aTarjanNode tarjanIndex: runningIndex. aTarjanNode tarjanLowlink: runningIndex. runningIndex := runningIndex + 1. self putOnStack: aTarjanNode. aTarjanNode adjacentNodes do: [ :adjacentNode | adjacentNode isTarjanUndefined ifTrue: [ self traverse: adjacentNode. aTarjanNode tarjanLowlink: (aTarjanNode tarjanLowlink min: adjacentNode tarjanLowlink) ] ifFalse: [ adjacentNode inStack ifTrue: [ aTarjanNode tarjanLowlink: (aTarjanNode tarjanLowlink min: adjacentNode tarjanIndex) ] ] ]. (self isRootNode: aTarjanNode) ifTrue: [ self addNewSccForNode: aTarjanNode ]! ! !AITarjan methodsFor: 'running' stamp: '4/26/2024 09:29'! addNewSccForNode: aTarjanNode | currentNode stronglyConnectedComponent | stronglyConnectedComponent := OrderedCollection empty. [ currentNode := stack pop. currentNode popped. stronglyConnectedComponent add: currentNode ] doWhileFalse: [ currentNode = aTarjanNode ]. sccs add: stronglyConnectedComponent. stronglyConnectedComponent do: [ :each | each cycleNodes: stronglyConnectedComponent ]! ! !AITarjan methodsFor: 'configuration' stamp: '4/26/2024 09:29'! nodeClass ^ AITarjanNode! ! !AITarjan methodsFor: 'accessing' stamp: '4/26/2024 09:29'! circuits ^ self stronglyConnectedComponents select: [ :each | each size > 1 ]! ! !AITarjan methodsFor: '*Tool-DependencyAnalyser' stamp: '4/26/2024 09:29'! runOnDAPackageRelationGraph: aRelationGraph | dependencies | "Construct the internal structure of Tarjan from a DAPackageRelation" dependencies := (aRelationGraph packages collect: [ :each | each dependencies ]) flattened. self nodes: aRelationGraph packages. self edges: dependencies from: [ :each | each source ] to: [ :each | each target ]. self run. "Convert the strongly connected components to a DAPackageRelation" ^ self stronglyConnectedComponents collect: [ :packages | DAPackageRelationGraph onPackages: packages ]! ! !AITarjan methodsFor: 'running' stamp: '4/26/2024 09:29'! run sccs := OrderedCollection new. stack := Stack new. runningIndex := 0. self nodes do: [ :node | node isTarjanUndefined ifTrue: [ self traverse: node ] ]. ^ self stronglyConnectedComponents! ! !AITarjan methodsFor: 'running' stamp: '4/26/2024 09:29'! putOnStack: aTarjanNode stack push: aTarjanNode. aTarjanNode inStack: true! ! !AITarjan methodsFor: 'accessing' stamp: '4/26/2024 09:29'! stronglyConnectedComponents sccs ifNil: [ self run ]. ^ sccs collect: [ :component | component collect: [ :each | each model ] ]! ! !AITarjanNode commentStamp: ''! Node type used by the Tarjan algorithm. We just keep a list of next nodes (neighbours). I also have variables to track the lowest my link value and the tarjan index. I have an instance variable `inStack` to check if I am or not in the stack of the Tarjan algorithm. Tha instance variable `cycleNodes` is a list that contains all the other nodes that are in my same strongly connected component. If I am the only node in the strongly connected component the list will be empty. ! !AITarjanNode methodsFor: 'setting' stamp: '4/26/2024 09:29'! tarjanIndex: anInteger index := anInteger! ! !AITarjanNode methodsFor: 'testing' stamp: '4/26/2024 09:29'! isTarjanUndefined ^ index = -1! ! !AITarjanNode methodsFor: 'actions' stamp: '4/26/2024 09:29'! popped inStack := false! ! !AITarjanNode methodsFor: 'setting' stamp: '4/26/2024 09:29'! inStack: aBoolean inStack := aBoolean! ! !AITarjanNode methodsFor: 'setting' stamp: '4/26/2024 09:29'! cycleNodes: anObject cycleNodes := anObject copy. cycleNodes remove: self! ! !AITarjanNode methodsFor: 'setting' stamp: '4/26/2024 09:29'! tarjanLowlink: anInteger lowlink := anInteger! ! !AITarjanNode methodsFor: 'accessing' stamp: '4/26/2024 09:29'! tarjanLowlink ^ lowlink! ! !AITarjanNode methodsFor: 'accessing' stamp: '4/26/2024 09:29'! cycleNodes ^ cycleNodes! ! !AITarjanNode methodsFor: 'initialization' stamp: '4/26/2024 09:29'! initialize super initialize. adjacentNodes := Set new. index := -1. inStack := false! ! !AITarjanNode methodsFor: 'accessing' stamp: '4/26/2024 09:29'! inStack ^ inStack! ! !AITarjanNode methodsFor: 'accessing' stamp: '4/26/2024 09:29'! label ^ 'Tarjan Node: '! ! !AITarjanNode methodsFor: 'accessing' stamp: '4/26/2024 09:29'! tarjanIndex ^ index! ! !AITarjanNode methodsFor: 'testing' stamp: '4/26/2024 09:29'! isInCycle ^ self cycleNodes isNotEmpty! ! !AITarjanTest methodsFor: 'running' stamp: '4/26/2024 09:29'! setUp super setUp. tarjan := AITarjan new! ! !AITarjanTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testNestedCycle | a b c cycleNodesOfC d f e g h cycleNodesOfI i graphType graph| graphType := AICyclicNonWeightedSimpleFixture new. graph := graphType nestedCycleGraph. tarjan nodes: graph nodes. tarjan edges: graph edges from: #first to: #second. tarjan run. a := tarjan findNode: $a. b := tarjan findNode: $b. c := tarjan findNode: $c. d := tarjan findNode: $d. e := tarjan findNode: $e. f := tarjan findNode: $f. g := tarjan findNode: $g. h := tarjan findNode: $h. i := tarjan findNode: $i. cycleNodesOfC := Set with: a with: b with: d with: e. cycleNodesOfI := Set with: f with: g with: h. self assert: tarjan stronglyConnectedComponents size equals: 2. self assert: tarjan circuits size equals: 2. tarjan nodes do: [ :n | self assert: n isInCycle ]. self assert: (c cycleNodes includesAll: cycleNodesOfC). self assert: (i cycleNodes includesAll: cycleNodesOfI)! ! !AITarjanTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testComplexCycle | a b c d f e g h graphType graph| graphType := AICyclicNonWeightedComplexFixture new. graph := graphType complexCycleGraph. tarjan nodes: graph nodes. tarjan edges: graph edges from: #first to: #second. tarjan run. a := tarjan findNode: $a. b := tarjan findNode: $b. c := tarjan findNode: $c. d := tarjan findNode: $d. e := tarjan findNode: $e. f := tarjan findNode: $f. g := tarjan findNode: $g. h := tarjan findNode: $h. self assert: tarjan stronglyConnectedComponents size equals: 5. self assert: tarjan circuits size equals: 2. self deny: a isInCycle. self deny: b isInCycle. self deny: e isInCycle. self assert: c isInCycle. self assert: d isInCycle. self assert: f isInCycle. self assert: g isInCycle. self assert: h isInCycle. self assertCollection: c cycleNodes hasSameElements: (Array with: d with: f). self assertCollection: g cycleNodes hasSameElements: (Array with: h). self assertCollection: h cycleNodes hasSameElements: (Array with: g)! ! !AITarjanTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testCycle | a b c cycleNodesOfA graphType graph| graphType := AICyclicNonWeightedSimpleFixture new. graph := graphType cycleGraph. tarjan nodes: graph nodes. tarjan edges: graph edges from: #first to: #second. tarjan run. a := tarjan findNode: $a. b := tarjan findNode: $b. c := tarjan findNode: $c. cycleNodesOfA := Set with: b with: c. self assert: a isInCycle. self assert: b isInCycle. self assert: c isInCycle. self deny: (tarjan findNode: $d) isInCycle. self assert: (a cycleNodes includesAll: cycleNodesOfA)! ! !AITarjanTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testComplexCycle2 | graphType graph| graphType := AICyclicNonWeightedComplexFixture new. graph := graphType complexCycleGraph2. tarjan nodes: graph nodes. tarjan edges: graph edges from: #first to: #second. tarjan run. #( $a $c $g $h $i ) do: [ :each | self deny: (tarjan findNode: each) isInCycle ]. self assert: tarjan stronglyConnectedComponents size equals: 6. self assert: tarjan circuits size equals: 1. self assertCollection: tarjan circuits first hasSameElements: #( $b $e $d $f )! ! !AITarjanTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testNoCycle | graphType graph| graphType := AINonWeightedDAGFixture new. graph := graphType simpleGraph. tarjan nodes: graph nodes. tarjan edges: graph edges from: #first to: #second. tarjan run. tarjan nodes do: [ :n | self deny: n isInCycle ]! ! !AITarjanTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testStronglyConnectedGraphWithObjects | persons nodeA nodeD nodeF nodeB nodeC nodeE nodeG nodeH graphType graph| graphType := AICyclicNonWeightedComplexFixture new. persons := DummyTestingPerson generateNinePersonArray. graph := graphType stronglyConnectedGraph: persons. tarjan nodes: graph nodes. tarjan edges: graph edges from: #first to: #second. tarjan run. nodeA := tarjan findNode: (persons at: 1). nodeB := tarjan findNode: (persons at: 2). nodeC := tarjan findNode: (persons at: 3). nodeD := tarjan findNode: (persons at: 4). nodeE := tarjan findNode: (persons at: 5). nodeF := tarjan findNode: (persons at: 6). nodeG := tarjan findNode: (persons at: 7). nodeH := tarjan findNode: (persons at: 8). self assert: tarjan stronglyConnectedComponents size equals: 4. self assert: tarjan circuits size equals: 3. self assertCollection: nodeA cycleNodes hasSameElements: { nodeB. nodeC }. self assertCollection: nodeD cycleNodes hasSameElements: { nodeE }. self assertCollection: nodeF cycleNodes hasSameElements: { nodeG. nodeH }! ! !AITarjanTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testStronglyConnectedGraph | nodeA nodeD nodeF nodeB nodeC nodeE nodeG nodeH graphType graph| graphType := AICyclicNonWeightedComplexFixture new. graph := graphType stronglyConnectedGraph. tarjan nodes: graph nodes. tarjan edges: graph edges from: #first to: #second. tarjan run. nodeA := tarjan findNode: $a. nodeB := tarjan findNode: $b. nodeC := tarjan findNode: $c. nodeD := tarjan findNode: $d. nodeE := tarjan findNode: $e. nodeF := tarjan findNode: $f. nodeG := tarjan findNode: $g. nodeH := tarjan findNode: $h. self assert: tarjan stronglyConnectedComponents size equals: 4. self assert: tarjan circuits size equals: 3. self assertCollection: nodeA cycleNodes hasSameElements: { nodeB. nodeC }. self assertCollection: nodeD cycleNodes hasSameElements: { nodeE }. self assertCollection: nodeF cycleNodes hasSameElements: { nodeG. nodeH }! ! !AITopologicalSorting commentStamp: ''! I am Kahn's Algorithm for topological sorting. I do the toplogical sorting in linear time O(V + E). I also detect and raise an error if the graph has any cycles. Because topological sorting is only possible if the graph is a Directed Acyclic Graph (DAG). From Wikipedia: A topological sort or topological ordering of a directed graph is a linear ordering of its vertices such that for every directed edge uv from vertex u to vertex v, u comes before v in the ordering. For instance, the vertices of the graph may represent tasks to be performed, and the edges may represent constraints that one task must be performed before another; in this application, a topological ordering is just a valid sequence for the tasks. A topological ordering is possible if and only if the graph has no directed cycles, that is, if it is a directed acyclic graph (DAG). ## Example Here is an example of use: Let's imagine we have a collection of number from 1 to 10 and 1 and 4 requires 9 to be before, 4 and 6 requires 2 to be before and 3 and 4 requires 7 to be before. We can do our sorting like this: ```st dependencies := Dictionary new at: 9 put: #( 1 4); at: 2 put: #( 4 6); at: 7 put: #( 3 4); yourself. AITopologicalSorting sort: #( 1 2 3 4 5 6 7 8 9 10 ) followingIncomingProperty: [ :int | dependencies at: int ifAbsent: [ #() ] ] ```! !AITopologicalSorting methodsFor: 'adding' stamp: '4/26/2024 09:29'! addIncomingEdgesFollowing: aBlock self edges: (nodes flatCollect: [ :node | (aBlock value: node model) collect: [ :each | node model -> each ] ]) from: #key to: #value! ! !AITopologicalSorting methodsFor: 'private' stamp: '4/26/2024 09:29'! graphHasEdges ^ nodes anySatisfy: [ :node | node adjacentNodes isNotEmpty ]! ! !AITopologicalSorting methodsFor: 'running' stamp: '4/26/2024 09:29'! gatherNoIncomingNodes nodesWithNoIncomingEdges addAll: (nodes select: [ :node | node isLeaf ])! ! !AITopologicalSorting methodsFor: 'configuration' stamp: '4/26/2024 09:29'! nodeClass ^ AINodeWithPrevious! ! !AITopologicalSorting methodsFor: 'accessing' stamp: '4/26/2024 09:29'! topologicalSortedElements ^ topologicalSortedElements! ! !AITopologicalSorting methodsFor: 'running' stamp: '4/26/2024 09:29'! initializeElements topologicalSortedElements := OrderedCollection new. "nodesWithNoIncomingEdge is a queue is a linked list because it has a better time complexity for removing the first element." nodesWithNoIncomingEdges := LinkedList new! ! !AITopologicalSorting methodsFor: 'running' stamp: '4/26/2024 09:29'! run self initializeElements. self gatherNoIncomingNodes. [ nodesWithNoIncomingEdges isNotEmpty ] whileTrue: [ | node | node := nodesWithNoIncomingEdges removeFirst. topologicalSortedElements addLast: node model. self removeEdgesOf: node ]. self graphHasEdges ifTrue: [ AINotADAG signal ]. ^ topologicalSortedElements! ! !AITopologicalSorting methodsFor: 'private' stamp: '4/26/2024 09:29'! removeEdgesOf: aNode aNode adjacentNodes do: [ :node | node incomingNodes remove: aNode. node isLeaf ifTrue: [ nodesWithNoIncomingEdges add: node ] ]. aNode adjacentNodes: #( )! ! !AITopologicalSorting class methodsFor: 'instance creation' stamp: '4/26/2024 09:29'! sort: nodes followingIncomingProperty: aValuable ^ (self nodes: nodes incomingEdgesProperty: aValuable) run! ! !AITopologicalSorting class methodsFor: 'instance creation' stamp: '4/26/2024 09:29'! nodes: aCollection incomingEdgesProperty: aValuable ^ self new nodes: aCollection; addIncomingEdgesFollowing: aValuable; yourself! ! !AITopologicalSortingTest commentStamp: ''! A MalTopologicalSortingTest is a test class for testing the behavior of MalTopologicalSorting! !AITopologicalSortingTest methodsFor: 'running' stamp: '4/26/2024 09:29'! setUp super setUp. sorter := AITopologicalSorting new! ! !AITopologicalSortingTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testSortStringHierarchy | result topologicalOrder | sorter addNodesFrom: String childrenBlock: [ :class | class subclasses ]. result := sorter run asArray. "This is one of the topological orders of the String hierarchy" topologicalOrder := { String. ByteString. Symbol. WideString. ByteSymbol. WideSymbol }. self assertCollection: result equals: topologicalOrder! ! !AITopologicalSortingTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testSortWithReducedGraph | graphReducer result graphType graph| graphReducer := AIGraphReducer new. graphType:= AICyclicNonWeightedComplexFixture new. graph := graphType complexCycleGraph2. graphReducer nodes: graph nodes. graphReducer edges: graph edges from: #first to: #second. sorter addNodesFromDifferentGraph: graphReducer run. result := sorter run. self assert: (result at: 1) equals: $c. self assert: (result at: 2) equals: $g. self assert: (result at: 3) equals: $a. self assert: (result at: 4) equals: $i. self assertCollection: (result at: 5) asArray hasSameElements: #( $e $b $d $f ). self assert: (result at: 6) equals: $h! ! !AITopologicalSortingTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testSimpleGraph | sortedItems graphType graph| graphType := AINonWeightedDAGFixture new. graph := graphType simpleGraph. sorter nodes: graph nodes. sorter edges: graph edges from: #first to: #second. sorter run. sortedItems := sorter topologicalSortedElements. "First level: A, D second level: B third level: C First level comes first, then second level..." self assert: sortedItems asArray equals: #( $a $d $b $c )! ! !AITopologicalSortingTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testWithoutCyclesMediumGraph | sortedItems graphType graph| graphType := AINonWeightedDAGFixture new. graph := graphType withoutCyclesMediumGraph. sorter nodes: graph nodes. sorter edges: graph edges from: #first to: #second. sorter run. sortedItems := sorter topologicalSortedElements. "A, B must come first. E and G come after A. C and H come after B. D comes after H. F comes after D and G." self assert: sortedItems asArray equals: #( $a $b $e $g $c $h $d $f )! ! !AITopologicalSortingTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testWithoutCyclesComplexGraph | sortedItems graphType graph| graphType := AINonWeightedDAGFixture new. graph := graphType withoutCyclesComplexGraph. sorter nodes: graph nodes. sorter edges: graph edges from: #first to: #second. sorter run. sortedItems := sorter topologicalSortedElements. "There are several possible topological orders with this combinations: First level: A, B, J second level: L, K, G, H, C, E third level: M, N D, O, Q fourth level: F, P fifth level: I sixth level: R seventh level: S So, the first nodes are the ones in the first level. Then comes the second level, etc." self assert: sortedItems asArray equals: #( $a $b $j $e $g $c $h $k $l $o $q $d $m $n $p $f $i $r $s )! ! !AITopologicalSortingTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testSortWithCycle | graphType graph| graphType := AICyclicNonWeightedSimpleFixture new. graph := graphType cycleGraph. sorter nodes: graph nodes. sorter edges: graph edges from: #first to: #second. self should: [ sorter run ] raise: Error! ! !AIWeightedDAGFixture commentStamp: ''! Graph Class: 1. ACyclic 2. Positive Weighted 3. Directed graphs! !AIWeightedDAGFixture methodsFor: 'initialization' stamp: '4/26/2024 09:29'! initialize super initialize . weightedDAG := self weightedDAG . withoutCyclesComplexWeightedGraph := self withoutCyclesComplexWeightedGraph .! ! !AIWeightedDAGFixture methodsFor: 'fixtures' stamp: '4/26/2024 09:29'! withoutCyclesComplexWeightedGraph "This is a disconnected graph" "https://i.imgur.com/TCBs0if.jpeg" | nodes edges graph | nodes := #( $a $b $c $d $e $f $g $h $i $j $k $l $m $n $o $p $q $r $s ). edges := #( #( $a $e 6 ) #( $a $g 7 ) #( $b $c 4 ) #( $b $h 10 ) #( $c $o 3 ) #( $c $q 2 ) #( $d $f 30 ) #( $d $i 15 ) #( $f $i 7 ) #( $g $f 8 ) #( $h $d 2 ) #( $i $r 14 ) #( $j $k 7 ) #( $j $l 6 ) #( $l $m 5 ) #( $l $n 3 ) #( $o $p 10 ) #( $q $p 1 ) #( $p $s 3 ) #( $r $s 7 ) ). graph:= AIGraphWeightedFixtureStructure new. graph nodes: nodes. graph edges: edges. ^graph! ! !AIWeightedDAGFixture methodsFor: 'fixtures' stamp: '4/26/2024 09:29'! weightedDAG "https://i.imgur.com/D5zMoQI.png" | nodes edges graph | nodes := $A to: $G. edges := #( #( $A $B 1 ) #( $B $C 5 ) #( $B $E 11 ) #( $B $D 8 ) #( $D $E 6 ) #( $E $F 7 ) #( $G $D 4 ) ). graph:= AIGraphWeightedFixtureStructure new. graph nodes: nodes. graph edges: edges. ^graph! ! !AIWeightedEdge commentStamp: ''! I represent a weighted edge in a graph. Public API and Key Messages - weight Instance Variables weight: ! !AIWeightedEdge methodsFor: 'accessing' stamp: '4/26/2024 09:29'! weight: anObject weight := anObject! ! !AIWeightedEdge methodsFor: 'accessing' stamp: '4/26/2024 09:29'! weight ^ weight! ! !AIWeightedEdge methodsFor: 'accessing' stamp: '4/26/2024 09:29'! asTuple ^ {from model. to model. weight}! ! !AIWeightedEdge methodsFor: 'printing' stamp: '4/26/2024 09:29'! printOn: aStream self from printOn: aStream. aStream nextPutAll: ' -> '. self to printOn: aStream. aStream nextPutAll: ' weight: '. self weight printOn: aStream! ! !AIWeightedHits commentStamp: ''! This is a variation of the normal Hits algorithm. It runs on a weighted graph. There are cases where the Hits algorithm not behaves as expected and sometimes the Hits algorithm puts 0 as values for the hubs and authorities. To bypass this problem a weighted graph can be used. The weights can represent several things and it's a responsibilty of the user to establish those weights. For more information, refer to this papers: - https://cnls.lanl.gov/External/people/highlights/sigir_JMiller.pdf - https://ieeexplore.ieee.org/document/4392647 Where is detailed how using a weighted graph can improve the results of the Hits algorithm.! !AIWeightedHits methodsFor: 'configuration' stamp: '4/26/2024 09:29'! edgeClass ^ AIWeightedEdge! ! !AIWeightedHits methodsFor: 'configuration' stamp: '4/26/2024 09:29'! nodeClass ^ AIWeightedHitsNode! ! !AIWeightedHits methodsFor: 'running' stamp: '4/26/2024 09:29'! computeHubsFor: aNode aNode hub: (aNode outgoingEdges inject: 0 into: [ :sum :edge | sum + (edge weight * edge to auth) ])! ! !AIWeightedHits methodsFor: 'running' stamp: '4/26/2024 09:29'! computeAuthoritiesFor: aNode aNode auth: (aNode incomingEdges inject: 0 into: [ :sum :edge | sum + (edge weight * edge from hub) ])! ! !AIWeightedHitsNode commentStamp: ''! I am a node used for the weighted hits algorithm! !AIWeightedHitsNode methodsFor: 'accessing' stamp: '4/26/2024 09:29'! to: aNode edge: anEdge adjacentNodes add: aNode. outgoingEdges add: anEdge! ! !AIWeightedHitsNode methodsFor: 'initialization' stamp: '4/26/2024 09:29'! initialize super initialize. outgoingEdges := OrderedCollection new. incomingEdges := OrderedCollection new! ! !AIWeightedHitsNode methodsFor: 'accessing' stamp: '4/26/2024 09:29'! incomingEdges ^ incomingEdges! ! !AIWeightedHitsNode methodsFor: 'accessing' stamp: '4/26/2024 09:29'! outgoingEdges ^ outgoingEdges! ! !AIWeightedHitsNode methodsFor: 'accessing' stamp: '4/26/2024 09:29'! label ^ 'WH '! ! !AIWeightedHitsNode methodsFor: 'accessing' stamp: '4/26/2024 09:29'! from: aNode edge: anEdge incomingNodes add: aNode. incomingEdges add: anEdge! ! !AIWeightedHitsTest methodsFor: 'running' stamp: '4/26/2024 09:29'! setUp super setUp. hits := AIWeightedHits new! ! !AIWeightedHitsTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testComplexWeighted | graphType graph | graphType := AICyclicWeightedComplexFixture new. graph :=graphType complexWeightedGraph. hits nodes: graph nodes. hits edges: graph edges from: #first to: #second weight: #third. hits run. hits nodes do: [ :node | self deny: node hub equals: 1. self deny: node auth equals: 1 ]! ! !AIWeightedHitsTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testSimpleW | graphType graph | graphType := AICyclicWeightedSimpleFixture new. graph :=graphType simpleWeightedGraph. hits nodes: graph nodes. hits edges: graph edges from: #first to: #second weight: #third. hits run. hits nodes do: [ :node | self deny: node hub equals: 1. self deny: node auth equals: 1 ]! ! !AIWeightedHitsTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testComplexWeighted2 | graphType graph | graphType := AICyclicWeightedComplexFixture new. graph :=graphType complexWeightedGraph2. hits nodes: graph nodes. hits edges: graph edges from: #first to: #second weight: #third. hits run. hits nodes do: [ :node | self deny: node hub equals: 1. self deny: node auth equals: 1 ]! ! !AIWeightedHitsTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testComplexWeighted3 | graphType graph | graphType := AICyclicWeightedComplexFixture new. graph :=graphType complexWeightedGraph3. hits nodes: graph nodes. hits edges: graph edges from: #first to: #second weight: #third. hits run. hits nodes do: [ :node | self deny: node hub equals: 1. self deny: node auth equals: 1 ]! ! !AIWeightedHitsTest methodsFor: 'tests' stamp: '4/26/2024 09:29'! testWithoutCyclesComplexWeightedGraph | graphType graph | graphType := AIWeightedDAGFixture new. graph :=graphType weightedDAG. hits nodes: graph nodes. hits edges: graph edges from: #first to: #second weight: #third. hits run. hits nodes do: [ :node | self deny: node hub equals: 1. self deny: node auth equals: 1 ]! ! !ASConverter commentStamp: ''! A converter is a kind of parser.! !ASConverter methodsFor: 'accessing' stamp: '4/26/2024 09:29'! noFill ^ ASNoFill soleInstance! ! !ASConverter methodsFor: 'accessing' stamp: '4/26/2024 09:29'! stream: aStream stream := aStream! ! !ASConverter methodsFor: 'parsing' stamp: '4/26/2024 09:29'! parseColor: aString ^ Color fromString: aString! ! !ASConverter methodsFor: 'write and read' stamp: '4/26/2024 09:29'! readInteger | result | (stream atEnd or: [ stream peek isDigit not ]) ifTrue: [ ^ nil ]. result := 0. [ stream peek isNotNil and: [ stream peek isDigit ] ] whileTrue: [ result := result * 10 + (stream next digitValue) ]. ^ result! ! !ASConverter methodsFor: 'operations' stamp: '4/26/2024 09:29'! skipBlanksAndComma [ stream atEnd not and: [ stream peek isSeparator or: [stream peek =$,]] ] whileTrue: [ stream next ]! ! !ASConverter methodsFor: 'accessing' stamp: '4/26/2024 09:29'! stream ^ stream! ! !ASConverter methodsFor: 'operations' stamp: '4/26/2024 09:29'! skipBlanks [ stream atEnd not and: [ stream peek isSeparator ] ] whileTrue: [ stream next ]! ! !ASConverter methodsFor: 'operations' stamp: '4/26/2024 09:29'! readFraction "Read fraction, what is after the decimal point: .12345" | result mul | (stream atEnd or: [ stream peek isDigit not ]) ifTrue: [ ^ nil ]. mul := 1/10. result := 0. [ stream peek isNotNil and: [ stream peek isDigit ] ] whileTrue: [ result := result + ( (stream next digitValue) * mul ). mul := mul / 10 ]. ^ result! ! !ASConverter methodsFor: 'parsing-public' stamp: '4/26/2024 09:29'! nextNumber "read the number from stream or answer nil if not successfull" " (real number value): The specification of real number values is different for property values than for XML attribute values. - CSS2 [CSS2] states that a property value which is a is specified in decimal notation (i.e., a ), which consists of either an , or an optional sign character followed by zero or more digits followed by a dot (.) followed by one or more digits. Thus, for conformance with CSS2, any property in SVG which accepts values is specified in decimal notation only. - For SVG's XML attributes, to provide as much scalability in numeric values as possible, real number values can be provided either in decimal notation or in scientific notation (i.e., a ), which consists of a immediately followed by the letter ''e'' or ''E'' immediately followed by an . Unless stated otherwise for a particular attribute or property, a has the capacity for at least a single- precision floating point number (see [ICC32]) and has a range (at a minimum) of -3.4e+38F to +3.4e+38F. It is recommended that higher precision floating point storage and computation be performed on operations such as coordinate system transformations to provide the best possible precision and to prevent round-off errors. Conforming High-Quality SVG Viewers are required to use at least double-precision floating point (see [ICC32]) for intermediate calculations on certain numerical operations. Within the SVG DOM, a is represented as a float or an SVGAnimatedNumber. " | result sign esign pos int frac exponent | esign := sign := 1. pos := stream position. stream peek = $- ifTrue: [ sign := -1. stream next ]. int := self readInteger. stream peek = $. ifTrue: [ stream next. frac := self readFraction. ]. (stream peek = $e or: [ stream peek = $E ]) ifTrue: [ stream next. stream peek = $- ifTrue: [ esign := -1. stream next ]. exponent := self readInteger * esign ]. "failed" (int isNil and: [ frac isNil ]) ifTrue: [ stream position: pos. ^ nil ]. int ifNil: [ int := 0 ]. frac ifNil: [ frac := 0 ]. exponent ifNil: [ exponent := 0 ]. result := (int + frac * (10 raisedTo: exponent) * sign). result isFraction ifTrue: [ ^ result asFloat ] ifFalse: [ ^ result ]! ! !ASNoFill commentStamp: ''! Fill without any effect! !ASNoFill methodsFor: 'public' stamp: '4/26/2024 09:29'! stroke: aShape on: aCanvas "Do nothing"! ! !ASNoFill methodsFor: 'public' stamp: '4/26/2024 09:29'! fill: aShape on: aCanvas "Do nothing"! ! !ASNoFill methodsFor: 'public' stamp: '4/26/2024 09:29'! resolveIds: aDictionary ^ self! ! !ASNoFill class methodsFor: 'accessing' stamp: '4/26/2024 09:29'! soleInstance ^ soleInstance ifNil: [ soleInstance := self new ]! ! !ASPathConverter commentStamp: ''! The syntax of path data is concise in order to allow for minimal file size and efficient downloads, since many SVG files will be dominated by their path data. Some of the ways that SVG attempts to minimize the size of path data are as follows: ● All instructions are expressed as one character (e.g., a moveto is expressed as an M). ● Superfluous white space and separators such as commas can be eliminated (e.g., "M 100 100 L 200 200" contains unnecessary spaces and could be expressed more compactly as "M100 100L200 200"). ● The command letter can be eliminated on subsequent commands if the same command is used multiple times in a row (e.g., you can drop the second "L" in "M 100 200 L 200 100 L -100 -200" and use "M 100 200 L 200 100 -100 -200" instead). ● Relative versions of all commands are available (uppercase means absolute coordinates, lowercase means relative coordinates). ● Alternate forms of lineto are available to optimize the special cases of horizontal and vertical lines (absolute and relative). ● Alternate forms of curve are available to optimize the special cases where some of the control points on the current segment can be determined automatically from the control points on the previous segment.! !ASPathConverter methodsFor: 'builder commands' stamp: '4/26/2024 09:29'! absolute absolute := true. self addSegment! ! !ASPathConverter methodsFor: 'path commands' stamp: '4/26/2024 09:29'! a self relative; ellipticalArc! ! !ASPathConverter methodsFor: 'operations' stamp: '4/26/2024 09:29'! cubicBezier " C/c (x1 y1 x2 y2 x y)+ Draws a cubic Bezier curve from the current point to (x,y) using (x1,y1) as the control point at the beginning of the curve and (x2,y2) as the control point at the end of the curve. C (uppercase) indicates that absolute coordinates will follow; c (lowercase) indicates that relative coordinates will follow. Multiple sets of coordinates may be specified to draw a polybezier. At the end of the command, the new current point becomes the final (x,y) coordinate pair used in the polybezier. " | p1 p2 p3 | p1 := self readPoint. p2 := self readPoint. p3 := self readPoint. p3 ifNil: [ self error: 'Invalid path data: 3 points expected for cubic bezier ']. self curveVia: p1 and: p2 to: p3. [ (p1 := self readPoint) ifNil: [ ^ self ]. p2 := self readPoint. p3 := self readPoint. p3 ifNil: [ self error: 'Invalid path data: 3 points expected for cubic bezier ']. self curveVia: p1 and: p2 to: p3. ] repeat! ! !ASPathConverter methodsFor: 'operations' stamp: '4/26/2024 09:29'! readPoint "A path data permits specifying points without comma separator" | x y pos | self skipBlanksAndComma. pos := stream position. x := self nextNumber ifNil: [ ^ nil ]. self skipBlanksAndComma. y := self nextNumber ifNil: [ stream position: pos. ^ nil ]. ^ x @ y! ! !ASPathConverter methodsFor: 'builder commands' stamp: '4/26/2024 09:29'! reflectedCurveVia: aPoint to: aPoint2 self addSegment! ! !ASPathConverter methodsFor: 'path commands' stamp: '4/26/2024 09:29'! S self absolute; reflectedCubicBezier! ! !ASPathConverter methodsFor: 'path commands' stamp: '4/26/2024 09:29'! A self absolute; ellipticalArc! ! !ASPathConverter methodsFor: 'accessing' stamp: '4/26/2024 09:29'! bbox ^ 100 @ 100! ! !ASPathConverter methodsFor: 'path commands' stamp: '4/26/2024 09:29'! M "move-to absolute" "Start a new sub-path at the given (x,y) coordinate. M (uppercase) indicates that absolute coordinates will follow; m (lowercase) indicates that relative coordinates will follow. If a relative moveto (m) appears as the first element of the path, then it is treated as a pair of absolute coordinates. If a moveto is followed by multiple pairs of coordinates, the subsequent pairs are treated as implicit lineto commands." self absolute; moveTo! ! !ASPathConverter methodsFor: 'builder commands' stamp: '4/26/2024 09:29'! curveVia: aPoint to: aPoint2 self addSegment! ! !ASPathConverter methodsFor: 'operations' stamp: '4/26/2024 09:29'! quadraticBezier " Q/q (x1 y1 x y)+ Draws a quadratic Bezier curve from the current point to (x,y) using (x1,y1) as the control point. Q (uppercase) indicates that absolute coordinates will follow; q (lowercase) indicates that relative coordinates will follow. Multiple sets of coordinates may be specified to draw a polybézier. At the end of the command, the new current point becomes the final (x,y) coordinate pair used in the polybezier." | p1 p2 | p1 := self readPoint. p2 := self readPoint. p2 ifNil: [ self error: 'Invalid path data: 2 points expected for quadratic bezier ']. self curveVia: p1 to: p2. [ (p1 := self readPoint) ifNil: [ ^ self ]. p2 := self readPoint. p2 ifNil: [ self error: 'Invalid path data: 2 points expected for quadratic bezier ']. self curveVia: p1 to: p2. ] repeat! ! !ASPathConverter methodsFor: 'path commands' stamp: '4/26/2024 09:29'! s self relative; reflectedCubicBezier! ! !ASPathConverter methodsFor: 'adding' stamp: '4/26/2024 09:29'! addSegment | sel args | sel := thisContext sender selector. args := thisContext sender arguments. "update min/max for calculatin bounding box" path add: { sel. args }! ! !ASPathConverter methodsFor: 'operations' stamp: '4/26/2024 09:29'! smoothQuadraticBezier self notYetImplemented! ! !ASPathConverter methodsFor: 'operations' stamp: '4/26/2024 09:29'! moveTo "move-to" " Start a new sub-path at the given (x,y) coordinate. M (uppercase) indicates that absolute coordinates will follow; m (lowercase) indicates that relative coordinates will follow. If a relative moveto (m) appears as the first element of the path, then it is treated as a pair of absolute coordinates. If a moveto is followed by multiple pairs of coordinates, the subsequent pairs are treated as implicit lineto commands. " | pt | pt := self readPoint. pt ifNil: [ self error: 'a point expected following after M/m command']. self moveTo: pt. [ pt := self readPoint. pt isNotNil ] whileTrue: [ self lineTo: pt ]! ! !ASPathConverter methodsFor: 'path commands' stamp: '4/26/2024 09:29'! V self absolute; vLineTo! ! !ASPathConverter methodsFor: 'builder commands' stamp: '4/26/2024 09:29'! curveVia: aPoint and: aPoint2 to: aPoint3 self addSegment! ! !ASPathConverter methodsFor: 'path commands' stamp: '4/26/2024 09:29'! Z self close! ! !ASPathConverter methodsFor: 'path commands' stamp: '4/26/2024 09:29'! L self absolute; lineTo! ! !ASPathConverter methodsFor: 'operations' stamp: '4/26/2024 09:29'! hLineTo "H (absolute) h (relative) x + Draws a horizontal line from the current point (cpx, cpy) to (x, cpy). H (uppercase) indicates that absolute coordinates will follow; h (lowercase) indicates that relative coordinates will follow. Multiple x values can be provided (although usually this doesn't make sense). At the end of the command, the new current point becomes (x, cpy) for the final value of x." | x | self skipBlanks. x := self nextNumber ifNil: [ ^ self error: 'number expected for horizontal line segment' ]. self hLineTo: x. [ self skipBlanks. x := self nextNumber. x isNotNil ] whileTrue: [ self hLineTo: x ]! ! !ASPathConverter methodsFor: 'builder commands' stamp: '4/26/2024 09:29'! lineTo: aPoint self addSegment! ! !ASPathConverter methodsFor: 'path commands' stamp: '4/26/2024 09:29'! q self relative; quadraticBezier! ! !ASPathConverter methodsFor: 'path commands' stamp: '4/26/2024 09:29'! T self absolute; smoothQuadraticBezier! ! !ASPathConverter methodsFor: 'path commands' stamp: '4/26/2024 09:29'! t self relative; smoothQuadraticBezier! ! !ASPathConverter methodsFor: 'builder commands' stamp: '4/26/2024 09:29'! relative absolute := false. self addSegment! ! !ASPathConverter methodsFor: 'path commands' stamp: '4/26/2024 09:29'! v self relative; vLineTo! ! !ASPathConverter methodsFor: 'operations' stamp: '4/26/2024 09:29'! convertPathData path := OrderedCollection new. [ self skipBlanks. stream atEnd ] whileFalse: [ | cmd | cmd := stream next. self assertValidCommand: cmd. self perform: cmd asString asSymbol ]. ^ path! ! !ASPathConverter methodsFor: 'builder commands' stamp: '4/26/2024 09:29'! moveTo: aPoint self addSegment! ! !ASPathConverter methodsFor: 'operations' stamp: '4/26/2024 09:29'! reflectedCubicBezier " S/s (x2 y2 x y)+ cubic Bezier curve from the current point to (x,y). The first control point is assumed to be the reflection of the second control point on the previous command relative to the current point. (If there is no previous command or if the previous command was not an C, c, S or s, assume the first control point is coincident with the current point.) (x2,y2) is the second control point (i.e., the control point at the end of the curve). S (uppercase) indicates that absolute coordinates will follow; s (lowercase) indicates that relative coordinates will follow. Multiple sets of coordinates may be specified to draw a polybézier. At the end of the command, the new current point becomes the final (x,y) coordinate pair used in the polybezier." | p1 p2 | p1 := self readPoint. p2 := self readPoint. p2 ifNil: [ self error: 'Invalid path data: 2 points expected for reflected cubic bezier ']. self reflectedCurveVia: p1 to: p2. [ (p1 := self readPoint) ifNil: [ ^ self ]. p2 := self readPoint. p2 ifNil: [ self error: 'Invalid path data: 2 points expected for reflected cubic bezier ']. self reflectedCurveVia: p1 to: p2. ] repeat! ! !ASPathConverter methodsFor: 'builder commands' stamp: '4/26/2024 09:29'! hLineTo: aNumber self addSegment! ! !ASPathConverter methodsFor: 'operations' stamp: '4/26/2024 09:29'! ellipticalArc: r xrot: xrot large: large sweep: sweep to: pt self addSegment! ! !ASPathConverter methodsFor: 'operations' stamp: '4/26/2024 09:29'! ellipticalArc "A (absolute) a (relative) elliptical arc (rx ry x-axis-rotation large-arc-flag sweep-flag x y)+ Draws an elliptical arc from the current point to (x, y). The size and orientation of the ellipse are defined by two radii (rx, ry) and an x-axis-rotation, which indicates how the ellipse as a whole is rotated relative to the current coordinate system. The center (cx, cy) of the ellipse is calculated automatically to satisfy the constraints imposed by the other parameters. large-arc-flag and sweep- flag contribute to the automatic calculations and help determine how the arc is drawn." | r xrot large sweep pt | [ r := self readPoint. r ifNil: [ ^ self ]. self skipBlanksAndComma. xrot := self nextNumber. self skipBlanksAndComma. large := self nextNumber. self skipBlanksAndComma. sweep := self nextNumber. pt := self readPoint. pt ifNil: [ self error: 'Invalid path data for elliptical arc segment']. self ellipticalArc: r xrot: xrot large: large sweep: sweep to: pt relative: absolute not. ] repeat! ! !ASPathConverter methodsFor: 'operations' stamp: '4/26/2024 09:29'! lineTo " L (absolute) l (relative) lineto (x y)+ Draw a line from the current point to the given (x,y) coordinate which becomes the new current point. L (uppercase) indicates that absolute coordinates will follow; l (lowercase) indicates that relative coordinates will follow. A number of coordinates pairs may be specified to draw a polyline. At the end of the command, the new current point is set to the final set of coordinates provided." | pt | pt := self readPoint. pt ifNil: [ self error: 'point expected for line segment' ]. self lineTo: pt. [ pt := self readPoint. pt isNotNil ] whileTrue: [ self lineTo: pt ]! ! !ASPathConverter methodsFor: 'operations' stamp: '4/26/2024 09:29'! ellipticalArc: r xrot: xrot large: large sweep: sweep to: pt relative: isRelative self addSegment! ! !ASPathConverter methodsFor: 'builder commands' stamp: '4/26/2024 09:29'! close self addSegment! ! !ASPathConverter methodsFor: 'path commands' stamp: '4/26/2024 09:29'! C self absolute; cubicBezier! ! !ASPathConverter methodsFor: 'path commands' stamp: '4/26/2024 09:29'! h self relative; hLineTo! ! !ASPathConverter methodsFor: 'builder commands' stamp: '4/26/2024 09:29'! vLineTo: aNumber self addSegment! ! !ASPathConverter methodsFor: 'path commands' stamp: '4/26/2024 09:29'! l self relative; lineTo! ! !ASPathConverter methodsFor: 'operations' stamp: '4/26/2024 09:29'! lastBezierPoint path reverseDo: [ :arr | arr first caseOf: { ([ #relative ] -> [ "ignore" ]) } ]! ! !ASPathConverter methodsFor: 'path commands' stamp: '4/26/2024 09:29'! z self close! ! !ASPathConverter methodsFor: 'path commands' stamp: '4/26/2024 09:29'! Q self absolute; quadraticBezier! ! !ASPathConverter methodsFor: 'path commands' stamp: '4/26/2024 09:29'! H self absolute; hLineTo! ! !ASPathConverter methodsFor: 'converting' stamp: '4/26/2024 09:29'! assertValidCommand: aCharacter (#( $M $m $Z $z $L $l $H $h $V $v $C $c $S $s $Q $q $T $t $A $a ) includes: aCharacter) ifFalse: [ self error: 'invalid path segment command' ]! ! !ASPathConverter methodsFor: 'path commands' stamp: '4/26/2024 09:29'! c self relative; cubicBezier! ! !ASPathConverter methodsFor: 'path commands' stamp: '4/26/2024 09:29'! m "move-to relative" " Start a new sub-path at the given (x,y) coordinate. M (uppercase) indicates that absolute coordinates will follow; m (lowercase) indicates that relative coordinates will follow. If a relative moveto (m) appears as the first element of the path, then it is treated as a pair of absolute coordinates. If a moveto is followed by multiple pairs of coordinates, the subsequent pairs are treated as implicit lineto commands. " | pt | pt := self readPoint. pt ifNil: [ self error: 'a point expected following after M/m command']. path isEmpty ifTrue: [ self absolute; moveTo: pt; relative ] ifFalse: [ self relative; moveTo: pt ]. [ pt := self readPoint. pt isNotNil ] whileTrue: [ self lineTo: pt ]! ! !ASPathConverter methodsFor: 'operations' stamp: '4/26/2024 09:29'! vLineTo " V (absolute) v (relative) Draws a vertical line from the current point (cpx, cpy) to (cpx, y). V (uppercase) indicates that absolute coordinates will follow; v (lowercase) indicates that relative coordinates will follow. Multiple y values can be provided (although usually this doesn't make sense). At the end of the command, the new current point becomes (cpx, y) for the final value of y." | y | self skipBlanks. y := self nextNumber ifNil: [ ^ self error: 'number expected for horizontal line segment' ]. self vLineTo: y. [ self skipBlanks. y := self nextNumber. y isNotNil ] whileTrue: [ self vLineTo: y ]! ! !ASTCache commentStamp: ''! I am a simple cache for AST nodes corresponding to CompiledMethods in the image. The cache is emptied when the image is saved. The cached #ast is for one interesting for speed (that is, in situations where you ask for it often). The other use-case is if you want to annotate the AST and keep that annotation around (till the next image save, but you can subscribe to ASTCacheReset and re-install the AST in the cache after cleaning. (This is used by MetaLinks to make sure they survive image restart). The last thing that it provides is that we do have a quite powerful mapping between bytecode/text/context and the AST. Regardless of how you navigate, you get the same object. e.g. even this one works: [ 1+2 ] sourceNode == thisContext method ast blockNodes first **NOTE** due to the cached AST, Modification of the AST can be a problem. Code that wants to modify the AST without making sure the compiledMethod is in sync later should use #parseTree. ! !ASTCache methodsFor: 'copying' stamp: '4/26/2024 09:26'! postCopy weakDictionary := weakDictionary copy. statistics := statistics copy! ! !ASTCache methodsFor: 'accessing' stamp: '4/26/2024 09:26'! getASTFor: aCompiledMethod ^ self class cacheMissStrategy getASTFor: aCompiledMethod! ! !ASTCache methodsFor: 'initialization' stamp: '4/26/2024 09:26'! reset self weakDictionary removeAll. weakDictionary := nil. statistics := nil.! ! !ASTCache methodsFor: 'adding' stamp: '4/26/2024 09:26'! addMiss self statistics ifNotNil: [ statistics addMiss ]! ! !ASTCache methodsFor: 'accessing' stamp: '4/26/2024 09:26'! at: aCompiledMethod ifAbsentPut: aBlock "Get an AST using strongly held information, or failback to aBlock (that might compute a new AST)" "For doit methods, the AST is stored in the method property" (aCompiledMethod propertyAt: #ast) ifNotNil: [ :ast | self addHit. ^ ast ]. "Reflective methods have a strongly held AST, return this one" (aCompiledMethod propertyAt: #reflectiveMethod) ifNotNil: [ :rf | self addHit. ^ rf ast ]. "Look in the (almost infinite) cache" self weakDictionary at: aCompiledMethod ifPresent: [ :wa | (wa at: 1) ifNotNil: [ :ast | self addHit. ^ ast ] ]. "We tried everything we could. So compute and store it" self addMiss. ^ self at: aCompiledMethod put: aBlock value! ! !ASTCache methodsFor: 'accessing' stamp: '4/26/2024 09:26'! statistics ^ statistics ifNil: [ "CacheStatistics comes from another package. It does not worth the dependency" self class environment at: #CacheStatistics ifPresent: [ :class | statistics := class new ] ]! ! !ASTCache methodsFor: 'accessing - statistics' stamp: '4/26/2024 09:26'! hitRatio self statistics ifNil: [ ^ 0 ]. ^ self statistics hitRatio! ! !ASTCache methodsFor: 'adding' stamp: '4/26/2024 09:26'! addHit self statistics ifNotNil: [ statistics addHit ]! ! !ASTCache methodsFor: 'accessing' stamp: '4/26/2024 09:26'! at: aCompiledMethod ^ self at: aCompiledMethod ifAbsentPut: [ self getASTFor: aCompiledMethod ]! ! !ASTCache methodsFor: 'accessing' stamp: '4/26/2024 09:26'! weakDictionary ^ weakDictionary ifNil: [ weakDictionary := WeakIdentityKeyDictionary new ]! ! !ASTCache methodsFor: 'accessing' stamp: '4/26/2024 09:26'! at: aCompiledMethod put: aRBMethodNode "Cleanup weak AST. Note `associations` return a copy, so the iteration is safe" | weakRef | self weakDictionary associations do: [ :each | (each value at: 1) ifNil: [ self weakDictionary removeKey: each key ifAbsent: [ "prevent TOCTOU" ] ] ]. weakRef := WeakArray new: 1. weakRef at: 1 put: aRBMethodNode. self weakDictionary at: aCompiledMethod put: weakRef. ^ aRBMethodNode! ! !ASTCache methodsFor: 'printing' stamp: '4/26/2024 09:26'! printOn: aStream super printOn: aStream. aStream nextPutAll: '#'; print: self weakDictionary size; space; print: (self hitRatio * 100.0) rounded; nextPut: $%! ! !ASTCache class methodsFor: 'accessing' stamp: '4/26/2024 09:26'! cacheMissStrategy ^ CacheMissStrategy ifNil: [ CacheMissStrategy := ASTCacheMissStrategy new ]! ! !ASTCache class methodsFor: 'private - announcements' stamp: '4/26/2024 09:26'! announceCacheReset self codeSupportAnnouncer announce: ASTCacheReset new! ! !ASTCache class methodsFor: 'class initialization' stamp: '4/26/2024 09:26'! reset '; lf! ! !DADependenciesHTMLPublisher methodsFor: 'publishing' stamp: '4/26/2024 09:29'! htmlForDependencies: dependencies of: aPackageName ^ String streamContents: [ :str | dependencies do: [ :dependency | str << '' << (self htmlForDependency: dependency of: aPackageName) << '' ] separatedBy: [ str space ] ]! ! !DADependenciesHTMLPublisher methodsFor: 'html utilities' stamp: '4/26/2024 09:29'! warningLabel: aString ^ '' , aString , ''! ! !DADependenciesHTMLPublisher methodsFor: 'publishing' stamp: '4/26/2024 09:29'! publishPackagesToRemoveDependants "Standard dependency report do not care about packages to remove for the bootsrap. Nothing to do."! ! !DADependenciesHTMLPublisher methodsFor: 'publishing' stamp: '4/26/2024 09:29'! htmlForDependency: dependencyPackageName of: aPackageName ^ dependencyPackageName! ! !DADependenciesHTMLPublisher methodsFor: 'publishing' stamp: '4/26/2024 09:29'! publish: aPackageName dependencies: dependencies dependants: dependants | dependantLinks | dependantLinks := dependants sorted collect: [ :name | '' , name , '' ]. stream << ' ' << (self htmlForPackage: aPackageName) << ' ' << (self sizeBadgeFor: dependencies) << Character space << (self htmlForDependencies: dependencies sorted of: aPackageName) << Character space << (self htmlForIgnoredDependenciesOf: aPackageName) << ' ' << (self sizeBadgeFor: dependants) << Character space << (Character space join: dependantLinks) << ' '; lf! ! !DADependenciesHTMLPublisher methodsFor: 'html utilities' stamp: '4/26/2024 09:29'! styleSheet: styleSheetUrl stream << ''; lf! ! !DADependenciesHTMLPublisher methodsFor: 'html utilities' stamp: '4/26/2024 09:29'! accordion: id name: name headingContent: heading body: body stream << '
'. stream << '
'. stream << body << '
'. stream << '
'; lf! ! !DADependenciesHTMLPublisher methodsFor: 'accessing' stamp: '4/26/2024 09:29'! stream ^ stream! ! !DADependenciesHTMLPublisher methodsFor: 'publishing' stamp: '4/26/2024 09:29'! publish self publishHTMLHeader; publishSetup; publishWarnings; publishDependenciesCaption; publishDependencies; publishDependenciesCaption; publishHTMLFooter. stream close! ! !DADependenciesHTMLPublisher methodsFor: 'publishing' stamp: '4/26/2024 09:29'! publishDependenciesCaption self stream lf; << (self warningLabel: 'Ignored dependency'); lf! ! !DADependenciesHTMLPublisher methodsFor: 'publishing' stamp: '4/26/2024 09:29'! publishSetup | body | body := String streamContents: [ :str | str << 'Image version: '; << self imageVersionString; << '
Analysis run on '; << report analysisRunString ; << '
' ]. self accordion: 'accordionSetup' name: 'Setup' headingContent: 'Analysis setup' body: body! ! !DADependenciesHTMLPublisher methodsFor: 'publishing' stamp: '4/26/2024 09:29'! publishHTMLHeader self stream << ''; lf; << ''; lf; << ''; lf; << 'Dependencies Report: '; lf. self styleSheet: 'https://maxcdn.bootstrapcdn.com/bootstrap/3.3.5/css/bootstrap.min.css'. self styleSheet: 'https://cdn.datatables.net/1.10.8/css/jquery.dataTables.min.css'. self javaScript: 'https://code.jquery.com/jquery-1.11.3.min.js'. self javaScript: 'https://cdn.datatables.net/1.10.8/js/jquery.dataTables.min.js'. self javaScript: 'https://maxcdn.bootstrapcdn.com/bootstrap/3.3.5/js/bootstrap.min.js'. stream << ''. self stream lf; << ''; lf; << ''; lf; << '
'; lf; << '

Dependency analysis

'; lf! ! !DADependenciesHTMLPublisher methodsFor: 'initialization' stamp: '4/26/2024 09:29'! initializeWithReport: aCGODependencyReport stream: aStream super initialize. stream := aStream. report := aCGODependencyReport! ! !DADependenciesHTMLPublisher methodsFor: 'publishing' stamp: '4/26/2024 09:29'! htmlForPackage: aPackageName ^ aPackageName! ! !DADependenciesHTMLPublisher methodsFor: 'publishing' stamp: '4/26/2024 09:29'! htmlForIgnoredDependenciesOf: aPackageName ^ String streamContents: [ :str | (self packageOrganizer packageNamed: aPackageName) ignoredDependencies do: [ :dependency | str << (self warningLabel: dependency) ] separatedBy: [ str space ] ]! ! !DADependenciesHTMLPublisher methodsFor: 'publishing' stamp: '4/26/2024 09:29'! publishDependencies stream << ' '; lf. report dependenciesAndKnownDependantsDo: [ :packageName :dependencies :dependants | self publish: packageName dependencies: dependencies dependants: dependants ]. self publishPackagesToRemoveDependants. stream << '
Package Dependencies Dependants
'; lf! ! !DADependenciesHTMLPublisher methodsFor: 'html utilities' stamp: '4/26/2024 09:29'! badgeFor: aString ^ ' ' , aString , ''! ! !DADependenciesHTMLPublisher methodsFor: 'html utilities' stamp: '4/26/2024 09:29'! dangerLabel: aString ^ '' , aString , ''! ! !DADependenciesHTMLPublisher methodsFor: 'publishing' stamp: '4/26/2024 09:29'! publishWarnings | body | body := String streamContents: [ :str | (report warnings sorted: [ :a :b | a package < b package ]) do: [ :warning | str << warning messageText << '
' ] ]. self accordion: 'accordionWarnings' name: 'Warnings' headingContent: 'Warnings ' , (self sizeBadgeFor: report warnings) body: body. stream << '
'; lf! ! !DADependenciesHTMLPublisher class methodsFor: 'publishing' stamp: '4/26/2024 09:29'! generateSystemReport