Topological sort: Difference between revisions

adding fortran 77
(CoffeeScript)
(adding fortran 77)
Line 648:
 
Output: <code>["std", "synopsys", "ieee", "dware", "gtech", "ramlib", "std_cell_lib", "dw02", "dw05", "dw06", "dw07", "dw01", "des_system_lib", "dw03", "dw04"]</code>
=={{header|Fortran}}==
===FORTRAN 77===
Main routine for topological sort.
''Input'' : IDEP is an array ND x 2 of dependencies, with IDEP(I,1) depending on IDEP(I,2).
NL is the number of libraries to sort, ND the number of dependencies, one for each pair of ordered libraries.
Array IPOS is used internally by the routine, to maintain a list of positions of libraries in IORD.
''Output'' : IORD(1:NO) is the compile order, and IORD(NO+1:NL) contains unordered libraries.
 
This implementation is not optimal: for each ''level'' of dependency (for example A -> B -> C counts has two levels), there is a loop through all dependencies in IDEP. It would be possible to optimize a bit, without changing the main idea, by first sorting IDEP according to first column, and using more temporary space, keeping track of where is located data in IDEP for each library (all dependencies of a same library being grouped).
<lang fortran> SUBROUTINE TSORT(NL,ND,IDEP,IORD,IPOS,NO)
IMPLICIT NONE
INTEGER NL,ND,NO,IDEP(ND,2),IORD(NL),IPOS(NL),I,J,K,IL,IR,IPL,IPR
DO 10 I=1,NL
IORD(I)=I
10 IPOS(I)=I
K=1
20 J=K
K=NL+1
DO 30 I=1,ND
IL=IDEP(I,1)
IR=IDEP(I,2)
IPL=IPOS(IL)
IPR=IPOS(IR)
IF(IL.EQ.IR .OR. IPL.GE.K .OR. IPL.LT.J .OR. IPR.LT.J) GO TO 30
K=K-1
IPOS(IORD(K))=IPL
IPOS(IL)=K
IORD(IPL)=IORD(K)
IORD(K)=IL
30 CONTINUE
IF(K.GT.J) GO TO 20
NO=J-1
END</lang>
 
An example. Dependencies are encoded to make program shorter (in array ICODE).
 
<lang fortran> PROGRAM EX_TSORT
IMPLICIT NONE
INTEGER NL,ND,NC,NO,IDEP,IORD,IPOS,ICODE,I,J,IL,IR
PARAMETER(NL=15,ND=44,NC=69)
CHARACTER*(20) LABEL
DIMENSION IDEP(ND,2),LABEL(NL),IORD(NL),IPOS(NL),ICODE(NC)
DATA LABEL/'DES_SYSTEM_LIB','DW01','DW02','DW03','DW04','DW05',
1 'DW06','DW07','DWARE','GTECH','RAMLIB','STD_CELL_LIB','SYNOPSYS',
2 'STD','IEEE'/
DATA ICODE/1,14,13,12,1,3,2,11,15,0,2,15,2,9,10,0,3,15,3,9,0,4,14,
213,9,4,3,2,15,10,0,5,5,15,2,9,10,0,6,6,15,9,0,7,7,15,9,0,8,15,9,0,
39,15,9,0,10,15,10,0,11,14,15,0,12,15,12,0,0/
 
C DECODE DEPENDENCIES AND BUILD IDEP ARRAY
I=0
J=0
10 I=I+1
IL=ICODE(I)
IF(IL.EQ.0) GO TO 30
20 I=I+1
IR=ICODE(I)
IF(IR.EQ.0) GO TO 10
J=J+1
IDEP(J,1)=IL
IDEP(J,2)=IR
GO TO 20
30 CONTINUE
 
C SORT LIBRARIES ACCORDING TO DEPENDENCIES (TOPOLOGICAL SORT)
CALL TSORT(NL,ND,IDEP,IORD,IPOS,NO)
 
PRINT*,'COMPILE ORDER'
DO 40 I=1,NO
40 PRINT*,LABEL(IORD(I))
PRINT*,'UNORDERED LIBRARIES'
DO 50 I=NO+1,NL
50 PRINT*,LABEL(IORD(I))
END</lang>
 
Output:
<pre>
COMPILE ORDER
IEEE
STD
SYNOPSYS
STD_CELL_LIB
RAMLIB
GTECH
DWARE
DW07
DW06
DW05
DW02
DW01
DW04
DW03
DES_SYSTEM_LIB
UNORDERED LIBRARIES
</pre>
 
Output with alternate input (DW01 depends also on DW04):
<pre>
COMPILE ORDER
IEEE
STD
SYNOPSYS
STD_CELL_LIB
RAMLIB
GTECH
DWARE
DW07
DW06
DW05
DW02
UNORDERED LIBRARIES
DW04
DW03
DW01
DES_SYSTEM_LIB
</pre>
 
=={{header|Go}}==
A straightforward solution, for ease of understanding rather than execution speed.
Anonymous user