My 1billion row challenge solutions in various languages
1 IDENTIFICATION DIVISION.
2 PROGRAM-ID. 1brc.
3 AUTHOR. Trey Bastian.
4
5 ENVIRONMENT DIVISION.
6 INPUT-OUTPUT SECTION.
7 FILE-CONTROL.
8 SELECT measurements-file ASSIGN TO "./measurements.txt"
9 ORGANIZATION IS LINE SEQUENTIAL.
10 SELECT sorted-measurements ASSIGN TO OUTPUT1.
11 SELECT workfile ASSIGN TO WORK1.
12 DATA DIVISION.
13 FILE SECTION.
14 FD measurements-file.
15 01 measurement.
16 02 line-item PIC X(106).
17 FD sorted-measurements.
18 01 measurement.
19 02 line-item PIC X(106).
20 SD workfile.
21 01 measurement.
22 02 line-item PIC X(106).
23
24 WORKING-STORAGE section.
25 01 pic x.
26 88 eof VALUE "Y".
27 88 eof-n VALUE "N".
28
29 01 pic x.
30 88 is-first VALUE "Y".
31 88 not-first VALUE "N".
32
33 77 s-name PIC X(100).
34 77 temp PIC S9(2)V9.
35
36 77 station-name PIC X(100).
37 77 min-temp PIC S9(2)V9 VALUE ZEROS.
38 77 max-temp PIC S9(2)V9 VALUE ZEROS.
39 77 total PIC S9(11)V9(2) VALUE ZEROS.
40 77 cnt PIC S9(11) VALUE ZEROS.
41
42 77 temp-str PIC -(2)9.9 VALUE ZEROS.
43 77 mean-calc PIC S9(2)V9 VALUE ZEROS.
44
45
46 PROCEDURE DIVISION.
47 SET is-first TO TRUE.
48 OPEN INPUT measurements-file.
49 SORT workfile ON ASCENDING line-item OF workfile
50 USING measurements-file
51 GIVING sorted-measurements
52
53 OPEN INPUT sorted-measurements.
54 SET eof-n TO TRUE.
55 PERFORM UNTIL eof
56 READ sorted-measurements AT END
57 SET eof TO TRUE
58 NOT AT END
59
60 UNSTRING line-item of sorted-measurements DELIMITED BY
61 ";" INTO s-name, temp
62 END-UNSTRING
63
64 IF s-name = station-name THEN
65 IF min-temp > temp THEN
66 MOVE temp to min-temp
67 END-IF
68 IF max-temp < temp THEN
69 MOVE temp to max-temp
70 END-IF
71 ADD temp TO total
72 ADD 1 TO cnt
73 ELSE
74 IF not-first THEN
75 PERFORM display-procedure
76 END-IF
77 MOVE s-name TO station-name
78 MOVE temp TO min-temp
79 MOVE temp TO max-temp
80 MOVE temp to total
81 MOVE 1 to cnt
82 IF is-first THEN
83 SET not-first TO TRUE
84 END-IF
85 END-IF
86 END-READ
87 END-PERFORM.
88 ClOSE sorted-measurements.
89 STOP-RUN.
90
91 display-procedure.
92 DISPLAY FUNCTION TRIM(station-name TRAILING)
93 WITH NO ADVANCING
94 DISPLAY ";" WITH NO ADVANCING
95 MOVE min-temp TO temp-str
96 DISPLAY FUNCTION TRIM(temp-str LEADING)
97 WITH NO ADVANCING
98 DISPLAY ";" WITH NO ADVANCING
99 COMPUTE mean-calc ROUNDED = total / cnt
100 MOVE mean-calc TO temp-str
101 DISPLAY FUNCTION TRIM(temp-str LEADING)
102 WITH NO ADVANCING
103 DISPLAY ";" WITH NO ADVANCING
104 MOVE max-temp TO temp-str
105 DISPLAY FUNCTION TRIM(temp-str LEADING).
106
107
108
109