Você está na página 1de 13

Attribute VB_Name = "Module1" 'FlowNav.

xlsm ' 'Routine to determine shortest path through a directed 'graph subject to node subset inadmissibility. The path is then isolated by ide ntifying the 'set of all next nearest nodes. Multiple, concurrent allocations are permitted. ' '************************************************************************ ' 'Copyright 2014 James A. Uthgenannt ' 'Permission is hereby granted, free of charge, to any person obtaining a copy 'of this software and associated documentation files (the "Software"), to deal 'in the Software without restriction, including without limitation the rights 'to use, copy, modify, merge, publish, distribute, sublicense, and/or sell 'copies of the Software, and to permit persons to whom the Software is 'furnished to do so, subject to the following conditions: ' 'The above copyright notice and this permission notice shall be included in 'all copies or substantial portions of the Software. ' 'THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR 'IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, 'FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE 'AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER 'LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, 'OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN 'THE SOFTWARE. ' '************************************************************************* 'References: '"Network Flow Programming", by Paul A. Jensen and J. Wesley Barnes, Krieger Pub lishing, Malabar, Florida 1987. (see especially chapters 4 and 5) 'J.A. Uthgenannt, "Path and Equipment Allocation for Multiple, Concurrent Proces ses on Networked Process Plant Units", Computers and Chemical Engineering, 20, 1 996. 'J.A. Uthgenannt, "Path and Equipment Allocation for Multiple, Concurrent Proces ses on Networked Process Plant Units - Part 2: Extensions and Code Listings", Sc ribd. Feb 2014. Web. 'http://jorlin.scripts.mit.edu/docs/SolutionManual/Chapter2.pdf (exercise 2.39) '************************************************************************* ' 'INPUTS: ' Read once at initialization ' The network: o(i), t(i), h(i) ' ' Read for each allocation ' The source / destination pair: sn, tn ' (Optional) intermediate nodes on the path, ie. go from sn to tn via inte rmediate node(s) ' (Optional) inadmissable nodes (eg. nodes may be out of service or otherw ise incompatible with desired allocation) '************************************************************************* 'Revision History ' ' Rev. Date. By. Comments ' 1 1994 JAU Original version ' 2.0 Feb. 2014 JAU Ported to Excel 2007 with VBA. Added interme diate destination node capability

' and temporary connection capability. Numero us efficiency, scalability, and readability enhancements. ' '************************************************************************* ' ' #### Declarations #### Option Explicit ' ' Establish maximum scale of the problem Const MAXARCS = 140 'Maximum number of arcs in the network Const MAXALLOC = 5 'Maximum number of concurrent allocation s on the network Const MAXNSPEC = 6 'Maximum number of specified nodes per a llocation (source, destination, and intermediate nodes) Const MAXLONGS = 5 'Maximum number of long integers needed to represent nodes as bits (must be > N/30, safe bet is > M/30) Const DENSITY = 12 'Maximum number of arcs or nodes connect ing any given node Const SETMAX = 24 'Maximum number each in the set of path nodes, isolation nodes, exclusion nodes, flex connections per allocation ' Const ALLOWSUCCESSFLEX = False 'When = True allows path with successive flex connections. When = False, disallow Const PRESORTED = False 'When = True, assumes raw arc data is pr esorted in order of increasing origin node Const FLEXARC = 3 'The arc length value indicating use of a temporary/flexible connection between nodes(NB: match value used in data read for h()) ' 'Arc list - this is where the network topology is configured/stored Dim o(MAXARCS) As Integer 'o(i) logical length m; arc list where o (i) specifies the origin node (tail) of arc i Dim t(MAXARCS) As Integer 't(i) logical length m; arc list where t (i) specifies the terminal node (head) of arc i Dim h(MAXARCS) As Integer 'h(i) length m; arc weights. NB: an arcw eight of FLEXARC indicates a flexible/transient connection ' 'Auxiliary structures that are configured during initialization to facilitate ra pid searches of the network. 'These complete the forward and reverse star representation of the network. Dim po(MAXARCS) As Integer 'po(i) logical length n; po(i) contains the lowest numbered arc which originates from node i Dim lt(MAXARCS) As Integer 'lt(i) logical length m; arcs ordered by increasing terminal node Dim pt(MAXARCS) As Integer 'pt(i) logical length n; pt(i) points to the first entry in lt() that terminates at i ' Dim pb(MAXARCS) As Integer 'pb(i) backpointer: for the shortest pat h tree, the unique arc that terminates at node i Dim s(MAXARCS) As Integer 's(i) logical length n; on entry to Dijk stra, the list of inadmissable nodes to the requested path allocation Dim swrk(MAXARCS) As Integer 'swrk(i) logical length n; the list of i nadmissable nodes to the requested path allocation Dim arclst(MAXARCS) As Integer 'arclst(i) logical length m; arc list in dex Dim lisa(DENSITY) As Integer 'workspace containing the list of arcs o riginating/terminating from/at a given node Dim lisn(DENSITY) As Integer 'workspace containing the list of nodes associated with lisa() Dim znet(MAXLONGS) As Long 'znet(i) bitwise representation of the s

hortest path nodes Dim ziso(MAXLONGS) As Long 'ziso(i) bitwise representation of nodes which isolate shortest path nodes Dim aflex(MAXALLOC, SETMAX) As Integer 'aflex(,) list of flexible/transient con nections used in each allocation Dim ni(MAXALLOC, SETMAX) As Integer 'ni(,)isolation node list for all alloca tions Dim np(MAXALLOC, SETMAX) As Integer 'np(,)shortest path node list for all al locations Dim znp(MAXALLOC, MAXLONGS) As Long 'znp(,),zni(,) see znet, ziso Dim zni(MAXALLOC, MAXLONGS) As Long 'znp(,),zni(,) see znet, ziso Dim sd(MAXALLOC, MAXNSPEC) As Integer 'sd(,) user specified source node, (inte rmediate nodes), and destination node for all allocations Dim ndim(MAXALLOC, 2) As Integer 'ndim(,) logical dimensions of ni(,),np( ,) for each allocation Dim exn(MAXALLOC, SETMAX) As Integer '(user input) exclusion nodes (echoed fo r display) Dim YSheet As Worksheet Dim I As Integer, J As Integer 'loop indeces Dim M As Integer, N As Integer 'number of arcs in network, highest numb ered node in network (** NB: both M and N < MAXARCS **) Dim Sn As Integer, Tn As Integer 'source node, destination node Dim Dsn As Integer, Dtn As Integer 'intermediate source node, intermediate destination node Dim PFound As Integer 'path found Dim L As Integer Dim Node As Integer Dim NumNode As Integer Dim Nspec As Integer Dim ArcSp As Integer 'arc specification (of a query) Dim Li As Integer Dim Sz As Integer Dim Qq As Integer Dim LoopTest As Integer Dim PathIndx As Integer Dim Ans As Integer 'answer from query Dim FlexT As Boolean Dim KeepGoing As Boolean ' Sub PathNav() ' '***** Initialization ***** 'Read the digraph, sort and index it as necessary, and generate auxiliary data s tructures, lt(), po(), and pt(). '(Create the complete compact forward and reverse star representation of the net work) 'NB: Original arc data, {o(), t(), h()} is sorted according to increasing origin node FlexT = 0 'initialize terminal node of flex connec t False ' Call ReadNet 'read the network ' If Not (PRESORTED) Then Call SortIndx(M, arclst(), o()) 'reorder arclst per increasing origin no de Call ReIndexArcs(M) 'reorder arc data per the reordered arcl st End If '

Call MakeStar 'constructs po(), pt(), and lt() ' Sz = Int((N - 1) / 31) + 1 'the number of long integers needed Call ClrArrays(0) 'Clear all allocation arrays ' For I = 1 To MAXARCS s(I) = 0 pb(I) = 0 Next I KeepGoing = True '***** End of Initialization ***** ' top: I = 0 Do 'find an index of an empty set to store the next path I = I + 1 LoopTest = np(I, 1) Loop Until (LoopTest = 0) Or (I = MAXALLOC) ' If LoopTest <> 0 Then MsgBox "** Maximum concurrent allocations active **" GoTo reslt Else PathIndx = I End If ' For I = 1 To MAXLONGS znet(I) = 0 ziso(I) = 0 Next I ' 'Obtain user input for source, destination, and intermediate nodes Do Sn = Application.InputBox(prompt:="Enter Source Node", Type:=1) If (s(Sn) = 1) Then MsgBox "Source is allocated, choose again" Loop Until (s(Sn) = 0) Tn = Application.InputBox(prompt:="Enter Destination Node", Type:=1) Node = Sn Nspec = 1 'enter intermediate nodes to visit in succession (NOT including source and desti nation) While (Node <> 0) And (Nspec < MAXNSPEC) sd(PathIndx, Nspec) = Node Nspec = Nspec + 1 If (Nspec < MAXNSPEC) Then Node = Application.InputBox(prompt:="Enter Next S uccessive Intermediate Node, 0 for None", Type:=1) Wend sd(PathIndx, Nspec) = Tn 'terminal node is last in the list ' 'Obtain user input for pre-excluded nodes (not including those assigned to activ e allocations) 'They are defined for the present allocation only. I = 0 Do Node = Application.InputBox(prompt:="Enter Node to Exclude (0 for none)" , Type:=1) If (Node > 0) And (Node <= N) Then s(Node) = 1 I = I + 1

exn(PathIndx, I) = Node End If Loop Until (Node = 0) Or (I = SETMAX) ' ' Call Dijkstra's algorithm successively to find path from source to destination (called once if no intermediate nodes specified) If (Nspec > 2) Then 'more than one call required (number of call s = nspec-1) For I = 1 To N 'save inadmissable nodes swrk(I) = s(I) Next I End If Dsn = sd(PathIndx, 1) 'initialize first source node for search Qq = 2 'initialize loop index FlexT = 0 'initialize terminal node of flex connect Fa lse ' Do Dtn = sd(PathIndx, Qq) 'set the next termination node for search Call Dijkstra(N, Dsn, Dtn, PFound) If (Qq < Nspec) Then 'another search is to be performed If (PFound <> 1) Then 'successful intermediate search - add latest path nodes to inadmissable set prior to next search Node = Dtn swrk(Node) = 1 Do Node = o(pb(Node)) swrk(Node) = 1 Loop Until (Node = Dsn) For I = 1 To N 'assign inadmissable nodes (overwrite previo usly visited nodes from last search) s(I) = swrk(I) Next I End If End If Dsn = Dtn 'next search's source is last search's desti nation... Qq = Qq + 1 Loop Until (PFound = 1) Or (Qq > Nspec) 'continue calling shortest path unti l all specified nodes reached or path deemed infeasible ' If (PFound <> 1) Then 'shortest path f ound Li = 0 Do Li = Li + 1 If (Li = 1) Then Node = Tn 'start with dest ination node and work back Else ArcSp = pb(Node) Node = o(ArcSp) 'point to the ne xt node on the shortest path tree If (h(ArcSp) = FLEXARC) Then 'identify the fl ex link found on the shortest path aflex(PathIndx, Li) = arclst(ArcSp) End If End If np(PathIndx, Li) = Node 'place the node in the shortest path array

J = Int((Node - 1) / 31) + 1 znet(J) = znet(J) Or (2 ^ ((Node - 1) Mod 31)) 'place node on t he shortest path bit array ' 'find all nodes adjacent to the shortest path node and construct zis o ziso(J) = ziso(J) Or znet(J) 'properly sets u p ziso should flex connections be present Call Orig(Node, NumNode) 'all nodes whose arcs originate from the path node Call AdjNode(NumNode) 'isolate these n odes from the path node Call Term(Node, NumNode) 'all nodes whose arcs terminate at the path node Call AdjNode(NumNode) 'isolate these n odes from the path node Loop Until (Node = Sn) 'continue until we've worked back to the source node ' ndim(PathIndx, 1) = Li 'dimension of pa th, ie. the number of nodes on the path Li = 0 For J = 1 To Sz 'make the sets of adjacent nodes and shortest path nodes disjoint (prior to this step, znet is a subset of ziso) znp(PathIndx, J) = znet(J) zni(PathIndx, J) = ziso(J) And (ziso(J) Xor znet(J)) ' 'define the list of isolation nodes (transcribe from bit array to array list rep resentaion) For I = 0 To 30 If (2 ^ I) And zni(PathIndx, J) Then Li = Li + 1 ni(PathIndx, Li) = 31 * (J - 1) + (I + 1) End If Next I Next J ndim(PathIndx, 2) = Li 'dimension of is olation, ie the number of nodes in the isolation Else MsgBox "*** PATH INFEASIBLE ***" End If reslt: Call Results Call Dealloc If KeepGoing Then GoTo top End Sub 'As adapted from Jensen and Barnes (DSHORT algo, pp. 129-130) 'On entry, s() contains the array of inadmissable nodes; on exit, it is augmente d with nodes labelled during the search Sub Dijkstra(N, Dsn, Dtn, PFound) Const WAYBIG = 9999 Dim pi(MAXARCS) As Integer 'pi(i) distance of node i to source node Dim ic As Integer, kk As Integer, jj As Integer, d As Integer, ient As Integer Dim Done As Boolean For I = 1 To N pi(I) = WAYBIG Next I pi(Dsn) = 0 s(Dsn) = 1

Node = Dsn PFound = 0 Done = False 'Forward Do Call Orig(Node, L) If (L <> 0) Then For ic = 1 To L kk = lisa(ic) jj = lisn(ic) If (s(jj) = 0) Then d = pi(Node) + h(kk) If (d < pi(jj)) Then pi(jj) = d pb(jj) = kk End If End If Next ic End If 'select next nearest neighbor d = WAYBIG ient = 0 For ic = 1 To N If (s(ic) = 0) Then If (pi(ic) < d) Then d = pi(ic) ient = ic End If End If Next ic 'add If (d < WAYBIG) Then s(ient) = 1 'add the subjected node to the shortest path tree If (ient <> Dtn) Then Node = ient If h(pb(Node)) = FLEXARC Then FlexT = 1 Else FlexT = 0 'test if this node reached by flex connection Else Done = True 'reached the terminal node End If Else 'no path exists Done = True PFound = 1 End If Loop Until (Done = True) End Sub ' 'Returns the list of nodes, lisn(), and list of arcs, lisa(), which originate fr om node ii. 'L is the logical dimension of those lists. 'See Jensen and Barnes (ORIG algo, p. 103) Sub Orig(ii, L) Dim k As Integer, ista As Integer, isto As Integer ista = po(ii) isto = po(ii + 1) - 1 L = 0 If (isto >= ista) Then 'above reference has typo here For k = ista To isto If (FlexT = 0) Or (ALLOWSUCCESSFLEX) Or (h(k) <> FLEXARC) Then 'pre

vent creation of path with 2 successive flex connections L = L + 1 lisa(L) = k lisn(L) = t(k) End If Next k End If End Sub 'Returns the list of nodes, lisn(), and list of arcs, lisa(), which terminate at node ii. L is the logical dimension of those lists. 'See Jensen and Barnes (TERM algo, p. 103) Sub Term(ii, L) Dim k As Integer, kk As Integer, ista As Integer, isto As Integer ista = pt(ii) isto = pt(ii + 1) - 1 'above reference has typo here L = 0 If (isto >= ista) Then 'above reference has typo here For kk = ista To isto k = lt(kk) L = L + 1 lisa(L) = k lisn(L) = o(k) Next kk End If End Sub ' 'Given the number of adjacent nodes and their lisa() and lisn() specifications, 'place the nodes in the isolation bit array (provided the node is not adjacent v ia flex connection) Sub AdjNode(NumNode) Dim jj As Integer, kk As Integer, elem As Integer If (NumNode > 0) Then For jj = 1 To NumNode If (h(lisa(jj)) <> FLEXARC) Then 'if this arc is not a flexible con nection, put the associated node in the isolation set kk = lisn(jj) elem = Int((kk - 1) / 31) + 1 ziso(elem) = ziso(elem) Or (2 ^ ((kk - 1) Mod 31)) End If Next jj End If End Sub ' reorders arc data based on increasing origin node (per indexed arclst) Sub ReIndexArcs(mm) Dim jj As Integer Dim WrkSpce(MAXARCS) As Integer For jj = 1 To mm 'reorder origin nodes WrkSpce(jj) = o(jj) Next jj For jj = 1 To mm o(jj) = WrkSpce(arclst(jj)) Next jj For jj = 1 To mm 'reorder terminal nodes WrkSpce(jj) = t(jj) Next jj For jj = 1 To mm t(jj) = WrkSpce(arclst(jj)) Next jj For jj = 1 To mm 'reorder arc weights/lengths WrkSpce(jj) = h(jj)

Next jj For jj = 1 To mm h(jj) = WrkSpce(arclst(jj)) Next jj End Sub Sub SortIndx(mm, indx() As Integer, arry() As Integer) 'reorders indx to represent the sorted arry. On exit arry may be listed in incr easing order as arry(indx(1)), arry(indx(2)), etc. 'sort is done via shell's method Dim Done As Boolean Dim gap As Integer, LoopMax As Integer, lm As Integer, ii As Integer, ti As Inte ger gap = 1 Do While gap <= mm gap = 3 * gap + 1 Loop gap = Int(gap / 3) Do While (gap >= 1) Do Done = True LoopMax = mm - gap For ii = 1 To LoopMax lm = ii + gap If (arry(indx(lm)) < arry(indx(ii))) Then ti = indx(ii) indx(ii) = indx(lm) indx(lm) = ti Done = False End If Next ii Loop Until (Done = True) gap = Int(gap / 3) Loop End Sub ' Sub ReadNet() Const STARTROW = 6 'worksheet row in which data first appears Dim tst As Integer, itmp As Integer, StartColumn As Integer Set YSheet = ThisWorkbook.Sheets("Flowsheet Configuration") ' StartColumn = 1 Ans = Application.InputBox(prompt:="Enter 1 for Pharma flowsheet input, 0 for Bl ending", Type:=1) If (Ans = 1) Then StartColumn = 6 ' itmp = STARTROW 'the row in which data f irst appears tst = YSheet.Cells(STARTROW, StartColumn).Value 'the origin node of the first arc M = 0 N = 0 Do While tst > 0 M = M + 1 o(M) = tst 'the origin node of arc, m t(M) = YSheet.Cells(itmp, StartColumn + 1).Value 'the terminal node of ar c, m h(M) = YSheet.Cells(itmp, StartColumn + 2).Value 'the cost of arc, m. arclst(M) = M 'initialize arclst

N = Maxi(N, o(M), t(M)) 'return the highest numb ered node itmp = M + STARTROW 'update the row number f or the next data tst = YSheet.Cells(itmp, StartColumn).Value 'test for more data in t he next origin node cell Loop End Sub Sub Results() Dim itmp As Integer, tst As Integer Dim pathnodes As String Dim specnodes As String Dim isonodes As String Dim flexarcs As String Dim exnodes As String Set YSheet = ThisWorkbook.Sheets("Path Results") itmp = 3 For I = 1 To MAXALLOC itmp = itmp + 1 If (ndim(I, 1) <> 0) Then ' Display output on worksheet YSheet.Cells(itmp, 5).Value = I 'The allocation number ( Print "Allocation # ", i) tst = ndim(I, 1) If (tst < ndim(I, 2)) Then tst = ndim(I, 2) End If ' Construct strings to display output pathnodes = "{" specnodes = "{" isonodes = "{" flexarcs = "{" exnodes = "{" For J = 1 To Nspec specnodes = specnodes & CStr(sd(I, J)) & " " Next J For J = 1 To tst If (np(I, J) > 0) Then pathnodes = pathnodes & CStr(np(I, J)) & " " End If If (ni(I, J) > 0) Then isonodes = isonodes & CStr(ni(I, J)) & " " End If If (aflex(I, J) > 0) Then flexarcs = flexarcs & CStr(aflex(I, J)) & " " End If Next J For J = 1 To SETMAX If (exn(I, J) > 0) Then exnodes = exnodes & CStr(exn(I, J)) & " " End If Next J pathnodes = RTrim(pathnodes) & "}" specnodes = RTrim(specnodes) & "}" isonodes = RTrim(isonodes) & "}" flexarcs = RTrim(flexarcs) & "}" exnodes = RTrim(exnodes) & "}" If (flexarcs = "{}") Then flexarcs = "" If (exnodes = "{}") Then exnodes = "" ' Display output on worksheet

YSheet.Cells(itmp, 6).Value = specnodes 'The set of specified nodes for the allocation (source, intermediate, destination) YSheet.Cells(itmp, 7).Value = exnodes 'The set of specified nodes for the allocation (source, intermediate, destination) YSheet.Cells(itmp, 8).Value = pathnodes 'The set of path nodes for t he allocation YSheet.Cells(itmp, 9).Value = isonodes 'The set of isolation nodes for the allocation YSheet.Cells(itmp, 10).Value = flexarcs 'The set of isolation nodes for the allocation End If Next I MsgBox "Click OK to Continue" End Sub Sub Dealloc() Ans = 0 Do ' Deallocate paths when finished and reinitialize associated path/allocation dat a Ans = Application.InputBox(prompt:="Enter path to deallocate, 0 for none", Type:=1) If (Ans <> 0) And (Ans <= MAXALLOC) Then Call ClrArrays(Ans) 'Clear specified allocation YSheet.Cells(Ans + 3, 5).ClearContents 'The allocation number YSheet.Cells(Ans + 3, 6).ClearContents 'The set of specified nodes fo r the allocation (source, intermediate, destination) YSheet.Cells(Ans + 3, 7).ClearContents 'The set of specified nodes fo r the allocation (source, intermediate, destination) YSheet.Cells(Ans + 3, 8).ClearContents 'The set of path nodes for the allocation YSheet.Cells(Ans + 3, 9).ClearContents 'The set of isolation nodes fo r the allocation YSheet.Cells(Ans + 3, 10).ClearContents 'The set of flex connections f or the allocation End If Loop Until (Ans = 0) ' allocate another? Ans = Application.InputBox(prompt:="enter 1 for new transfer, 0 to quit", Type:= 1) If Ans = 1 Then 'determine the set of inadmissable n odes before allowing a new allocation For I = 1 To MAXARCS s(I) = 0 'clear the set of inadmissable (visi ted) nodes pb(I) = 0 'clear the backpointer of shortest p ath nodes Next I For I = 1 To MAXALLOC If (ndim(I, 1) <> 0) Then For J = 1 To ndim(I, 1) s(np(I, J)) = 1 'populate inadmissable nodes set wit h nodes of all active allocations and... Next J For J = 1 To ndim(I, 2) s(ni(I, J)) = 1 '... the isolation nodes of all acti ve allocations. Next J End If Next I KeepGoing = True

Else KeepGoing = False End If End Sub Sub ClrArrays(kk) Dim ibegin As Integer, iend As Integer, ii As Integer, jj As Integer If (kk = 0) Then 'clear all allocations ibegin = 1 iend = MAXALLOC Else 'clear specified allocation ibegin = kk iend = kk End If For ii = ibegin To iend 'initialize/clear arrays in which pa th information is stored For jj = 1 To MAXLONGS znp(ii, jj) = 0 zni(ii, jj) = 0 Next jj For jj = 1 To MAXNSPEC sd(ii, jj) = 0 Next jj For jj = 1 To 2 ndim(ii, jj) = 0 Next jj For jj = 1 To SETMAX ni(ii, jj) = 0 np(ii, jj) = 0 aflex(ii, jj) = 0 exn(ii, jj) = 0 Next jj Next ii End Sub 'Routine to finish construction of the forward and reverse star data structures Sub MakeStar() Dim ii As Integer, jj As Integer, xl As Integer Dim degree(MAXARCS) As Integer Dim Tnext(MAXARCS) As Integer po(1) = 1 pt(1) = 1 'make po(), where po(i) contains the index of the lowest numbered arc originatin g from node i 'if no arc originates at node i, po(i)=po(i+1) 'po() is used for quickly finding those arcs which originate from a given node For ii = 1 To N degree(ii) = 0 Next ii For ii = 1 To M degree(o(ii)) = degree(o(ii)) + 1 Next ii For ii = 1 To N po(ii + 1) = po(ii) + degree(ii) Next ii 'make pt(), where pt(i) points to the first entry in lt() that terminates at nod e i. 'if no arc terminates at node i, pt(i)=pt(i+1) 'pt() is used for quickly finding those arcs which terminate at a given node For ii = 1 To N degree(ii) = 0 Next ii

For ii = 1 To M degree(t(ii)) = degree(t(ii)) + 1 Next ii For ii = 1 To N pt(ii + 1) = pt(ii) + degree(ii) Tnext(ii) = pt(ii) Next ii For ii = 1 To M xl = t(ii) lt(Tnext(xl)) = ii Tnext(xl) = Tnext(xl) + 1 Next ii ' po(N + 1) = M + 1 pt(N + 1) = M + 1 End Sub ' Function Maxi(a, b, c) As Integer Dim ii As Integer ii = a If b > ii Then ii = b If c > ii Then ii = c Maxi = ii End Function

Você também pode gostar