How can I process this array without huge amounts of code? - arrays

I'll start by admitting this is for my homework and I don't expect anything specific just a tip perhaps. The input file is just one 30 byte field that contains names. The output file is two fields 30 bytes each. I'll list the code to show what I mean by this. The program needs to read the input file putting the names into an array and then print them to the two fields in the output file. It would be simple enough if the out put file was like this:
name 1 name 2
name 3 name 4
etc...
but it's supposed to be:
name 1 name 55
name 2 name 56
....
name 54 name 108
I'm not quite understanding how I can code the program to do this without having 54 lines of code (1 for each line in the output). Well here's the code I have so far:
ENVIRONMENT DIVISION.
INPUT-OUTPUT SECTION.
FILE-CONTROL.
SELECT NAMELIST-FILE-IN
ASSIGN TO 'NAMELIST.SEQ'
ORGANIZATION IS LINE SEQUENTIAL.
SELECT NAMELIST-FILE-OUT
ASSIGN TO 'NAMELIST.RPT'
ORGANIZATION IS LINE SEQUENTIAL.
DATA DIVISION.
FILE SECTION.
FD NAMELIST-FILE-IN.
01 NAME-IN PIC X(30).
FD NAMELIST-FILE-OUT.
01 NAME-OUT PIC X(60).
WORKING-STORAGE SECTION.
01 ARE-THERE-MORE-RECORDS PIC X(3) VALUE 'YES'.
01 PAGE-CTR PIC 99 VALUE ZERO.
01 SUB PIC 999 VALUE 1.
01 LEFT-NAME PIC 99 VALUE 54.
01 RIGHT-NAME PIC 9(3) VALUE 108.
01 WS-DATE.
05 RUN-YEAR PIC XX.
05 RUN-MONTH PIC XX.
05 RUN-DAY PIC XX.
01 HEADING-LINE.
05 PIC X(15) VALUE SPACES.
05 PIC X(20)
VALUE 'NAME LIST REPORT'.
05 HL-DATE.
10 DAY-HL PIC XX.
10 PIC X VALUE '/'.
10 MONTH-HL PIC XX.
10 PIC X VALUE '/'.
10 YEAR-HL PIC XX.
05 PIC X(3) VALUE SPACES.
05 PIC X(5) VALUE 'PAGE'.
05 PAGE-NUMBER-HL PIC Z9 VALUE 1.
01 DETAIL-LINE.
05 NAME-LEFT PIC X(30).
05 NAME-RIGHT PIC X(30).
01 NAME-ARRAY.
05 NAME-X OCCURS 108 PIC X(30).
PROCEDURE DIVISION.
100-MAIN.
OPEN INPUT NAMELIST-FILE-IN
OPEN OUTPUT NAMELIST-FILE-OUT
ACCEPT WS-DATE FROM DATE.
MOVE RUN-MONTH TO MONTH-HL
MOVE RUN-DAY TO DAY-HL
MOVE RUN-YEAR TO YEAR-HL
PERFORM 200-ACCEPT-INPUT
CLOSE NAMELIST-FILE-IN
CLOSE NAMELIST-FILE-OUT
STOP RUN.
200-ACCEPT-INPUT.
PERFORM UNTIL SUB > 108
READ NAMELIST-FILE-IN
MOVE NAME-IN TO NAME-X (SUB)
ADD 1 TO SUB
END-PERFORM
PERFORM 300-PRINT-ONE-PAGE.
300-PRINT-ONE-PAGE.
WRITE NAME-OUT FROM HEADING-LINE
AFTER ADVANCING PAGE
ADD 1 TO PAGE-CTR
Here's the final code for this program if anyone is interested in seeing it.
ENVIRONMENT DIVISION.
INPUT-OUTPUT SECTION.
FILE-CONTROL.
SELECT NAMELIST-FILE-IN
ASSIGN TO 'NAMELIST.SEQ'
ORGANIZATION IS LINE SEQUENTIAL.
SELECT NAMELIST-FILE-OUT
ASSIGN TO 'NAMELIST.RPT'
ORGANIZATION IS LINE SEQUENTIAL.
DATA DIVISION.
FILE SECTION.
FD NAMELIST-FILE-IN.
01 NAME-IN PIC X(30).
FD NAMELIST-FILE-OUT.
01 NAME-OUT PIC X(80).
WORKING-STORAGE SECTION.
01 ARE-THERE-MORE-RECORDS PIC X(3) VALUE 'YES'.
01 PAGE-CTR PIC 99 VALUE ZERO.
01 SUB PIC 999.
01 SUB2 PIC 999.
01 LEFT-NAME PIC 99 VALUE 54.
01 RIGHT-NAME PIC 9(3) VALUE 108.
01 WS-DATE.
05 RUN-YEAR PIC XX.
05 RUN-MONTH PIC XX.
05 RUN-DAY PIC XX.
01 HEADING-LINE.
05 PIC X(26) VALUE SPACES.
05 PIC X(35)
VALUE 'NAME LIST REPORT'.
05 HL-DATE.
10 DAY-HL PIC XX.
10 PIC X VALUE '/'.
10 MONTH-HL PIC XX.
10 PIC X VALUE '/'.
10 YEAR-HL PIC XX.
05 PIC X(3) VALUE SPACES.
05 PIC X(5) VALUE 'PAGE'.
05 PAGE-NUMBER-HL PIC Z9.
01 DETAIL-LINE.
05 NAME-LEFT PIC X(40).
05 NAME-RIGHT PIC X(40).
01 NAME-ARRAY.
05 NAME-X OCCURS 108 PIC X(30).
PROCEDURE DIVISION.
100-MAIN.
OPEN INPUT NAMELIST-FILE-IN
OPEN OUTPUT NAMELIST-FILE-OUT
ACCEPT WS-DATE FROM DATE.
MOVE RUN-MONTH TO MONTH-HL
MOVE RUN-DAY TO DAY-HL
MOVE RUN-YEAR TO YEAR-HL
PERFORM UNTIL ARE-THERE-MORE-RECORDS = 'NO'
PERFORM 200-ACCEPT-INPUT
END-PERFORM
CLOSE NAMELIST-FILE-IN
CLOSE NAMELIST-FILE-OUT
STOP RUN.
200-ACCEPT-INPUT.
INITIALIZE NAME-ARRAY
MOVE 1 TO SUB
PERFORM UNTIL SUB > 108 OR ARE-THERE-MORE-RECORDS = 'NO'
READ NAMELIST-FILE-IN
AT END
MOVE 'NO' TO ARE-THERE-MORE-RECORDS
MOVE SPACES TO NAME-IN
END-READ
MOVE NAME-IN TO NAME-X (SUB)
ADD 1 TO SUB
END-PERFORM
PERFORM 300-PRINT-ONE-PAGE.
300-PRINT-ONE-PAGE.
ADD 1 TO PAGE-CTR
MOVE PAGE-CTR TO PAGE-NUMBER-HL
WRITE NAME-OUT FROM HEADING-LINE
AFTER ADVANCING PAGE
MOVE SPACES TO DETAIL-LINE
WRITE NAME-OUT FROM DETAIL-LINE
AFTER ADVANCING 1
PERFORM VARYING SUB FROM 1 BY 1 UNTIL SUB > 54
MOVE NAME-X (SUB) TO NAME-LEFT
COMPUTE SUB2 = SUB + 54
MOVE NAME-X (SUB2) TO NAME-RIGHT
WRITE NAME-OUT FROM DETAIL-LINE
AFTER ADVANCING 1
END-PERFORM.

I must apologize, I cannot think of a way to guide you without giving away the answer. I guess this is a spoiler alert.
One possible method you could use would be to add a variable SUB2 to Working-Storage and...
Perform Varying SUB From 1 By 1 Until SUB > 54
Move NAME-X(SUB) to NAME-LEFT
Compute SUB2 = SUB + 54
MOVE NAME-X(SUB2) to NAME-RIGHT
Write NAME-OUT from DETAIL-LINE After Advancing 1 Line
End-Perform
This is kind of kludgy and ties you to an array of 108 elements. You could use a record counter that you increment by 1 for each record read and then compute the values I show hardcoded in the sample above (54 is simply half of 108).
I don't show the page break logic, so perhaps I didn't give the whole show away.
I hope this helps you.

I would have 2 arrays.
One containing the whole file.
01 DETAIL-LINE-ARRAY.
02 DETAIL-LINE OCCURS 54.
05 NAME-LEFT PIC X(30).
05 NAME-RIGHT PIC X(30).
Another like you did with NAME-ARRAY
Then I would populate first the DETAIL-LINE-ARRAY.
I would read twice DETAIL-LINE-ARRAY to fill NAME-ARRAY
Then you can read sequentially NAME-ARRAY
==========================================================================
Another solution:
You can read the file twice. While the first read, you take care only of the left name and populate NAME-ARRAY.
While the second reading, you take care only of the right name and continue to populate NAME-ARRAY.
After the first and second read, you can read your array NAME-ARRAY.
==========================================================================
There is a problem with both last solutions : you have to know how much lines contains your file. Yep, you can have dynamic programming in cobol too :-)
You have to use SORT.
In FILE SECTION add
SD SORT-WORK
01 SORT-RECORD.
05 SR-ORDER PIC 9(09).
05 SR-NAME PIC X(30).
In your PROCEDURE DIVISION add (in pseude-code, you'll need to add some variables in your working storage section.
SORT SORT-WORK
ASCENDING SORT-ORDER
INPUT PROCEDURE IS 1000-INPUT
OUTPUT PROCEDURE IS 2000-OUTPUT
1000-INPUT SECTION.
MOVE 0 TO I.
PERFORM until end-of-file of NAMELIST-FILE-IN
ADD 1 TO I
READ left-name
MOVE I TO SORT-ORDER
MOVE left-name TO SR-NAME
* This operation populates the sort file...
RELEASE SORT-RECORD
END-PERFORM.
PERFORM until end-of-file of NAMELIST-FILE-IN
ADD 1 TO I
READ right-name
MOVE I TO SORT-ORDER
MOVE right-name TO SR-NAME
* This operation populates the sort file...
RELEASE SORT-RECORD
END-PERFORM.
MOVE I TO WS-NB-NAMES.
2000-OUTPUT SECTION.
PERFORM VARYING I FROM 1 BY 1 UNTIL I > WS-NB-NAMES
* This operation returns the "next" record. It begins by the first, second...
RETURN SORT-RECORD
MOVE SR-NAME TO NAME-LEFT
RETURN SORT-RECORD
MOVE SR-NAME TO NAME-RIGHT
WRITE NAMELIST-FILE-OUT FROM DETAIL-LINE
END-PERFORM.
You have some example here for SORT
Have fun !

Related

Cobol - Date loop

How can I implement a loop that will display subsequent months (01/01/2018, 01/02/2018 etc.) x-times? Additionally, how can I set day,month,year as a variable? By the way, I'm new to Cobol.
This is my code I wrote so far
01 YYYYMMDD Pic 9(8).
01 Integer-Form Pic S9(9).
Move Function Current-Date(1:8) to YYYYMMDD
Compute Integer-Form = Function Integer-of-Date(YYYYMMDD)
Add 12 to Integer-Form
Compute YYYYMMDD = Function Date-of-Integer(Integer-Form)
Display 'Date: ' YYYYMMDD.
EDIT!
PERFORM VARYING Number-Periods FROM 0 BY 1 UNTIL Number-Periods > 36
DISPLAY ws-current-day, "/", ws-current-month, "/", ws-current-year
ADD 1 TO WS-current-month
IF ws-current-month > 12 THEN
COMPUTE ws-current-month = 1
ADD 1 TO WS-current-year
END-IF
END-PERFORM
Best to use redefines and 88 to check month:
01 YYYYMMDD PIC 9(8).
01 YYYYMMDD-R REDEFINES YYYYMMDD.
05 YYYY PIC 9(4).
05 MM PIC 9(2).
88 VALID-MONTH VALUE 1 2 3 4 5 6
7 8 9 10 11 12.
05 DD PIC 9(2).
Then you can use the 88 in the check (within the PERFORM VARYING as you discovered):
IF NOT VALID-MONTH
... increment year

LIBMODBUS: Writing to a double register?

Is there a way I can write one value to a double register using LIBMODBUS? For example writing value 100,000 to be spread across one register. Currently using modbus_write_registers to write 10,000 I am sending the modbus message
rc = modbus_write_registers(ctx, 4, 2, tab_reg); (Where tab_reg[0] = 10,000 and tab_reg[1] = 0)
0A 10 00 04 00 02 04 27 10 00 00 DC 09
Ideally the message i believe I would like to send would not send the 00 00 for the zero value. Is this possible to utilise using Libmodbus?
NB - I have also attempted using modbus_write_register() and this produced a much longer message so I am inclined to believe write registerS is the way to go.

combine string in python pandas

I got a problem when analyzing dataset about combining string together.
The data frame looks like the one below:
IP Event
01 check
01 redo
01 view
02 check
02 check
03 review
04 delete
As you can see, the IP contains duplicates. My question is, how can I get the results of combining the Event group by each IP in order.For example, the result I'm looking for is:
IP result
01 check->redo->view
02 check->check
03 review
04 delete
try this:
In [27]: df.groupby('IP').agg('->'.join).reset_index()
Out[27]:
IP Event
0 01 check->redo->view
1 02 check->check
2 03 review
3 04 delete
or
In [26]: df.groupby('IP').agg('->'.join)
Out[26]:
Event
IP
01 check->redo->view
02 check->check
03 review
04 delete
Try this with lambda:
df.groupby("IP")['Event'].apply(lambda x: '->'.join(x)).reset_index()
# IP Event
# 0 1 check->redo->view
# 1 2 check->check
# 2 3 review
# 3 4 delete

Detecting I-frame data in an MPEG-4 transport stream

I am testing a project. I need to break the payload data(making zero some bytes) of the MPEG-4 ts packets by a percentage coming from the user. I am doing it by reading the ".ts" file packet by packet(188 bytes). But the video is changing to really mud after process. (By the way I'm writing the program in C)
So I decided to find the data/packets that belongs to I-frames, then not touching them but scrambling the other datas by percentage. I could find below
(in hex)
00 00 00 01 E0 start of video PES packet
..
..
00 00 01 B8 start of group of pictures header
..
..
00 00 01 00 the picture start code. This is 32 bits. The 10 bits immediately following this is called as the temporal reference. So temporal reference will include the byte following the picture start code and the first two bits of the second byte after the picture start code ie one byte(8 bits) + 2 bits. These we need to skip. Now the three bits present(3, 4 and 5th bits of the second byte from the picture start code) will indicate the Frame type ie I, B or P. So to get this simply logical AND & the second byte from the picture start code with 0x38 and right shift >> with 3.
For example the data is like that;
00 00 01 00 00 0F FF F8 00 00 01 B5........... and so on.
Here the first four bytes 00 00 01 00 is the picture start code.
The fifth byte and the first two bits of the sixth byte is the temporal reference.
So our concern is in the sixth byte --> 0F
((0F & 38)>>3)
Frame type = 1 ==> I Frame
Frame type 000 forbidden
Frame type 001 intra-coded (I) - iframe
Frame type 010 predictive-coded (P) - p frame
Frame type 011 bidirectionally-predictive-coded (B) - b frame
But this is for MPEG-2. Is there some patterns like that so I recognize and get the frame type with bitwise operations for MPEG-4 transport stream(extension is ".ts")?
And I need to get how many bytes or packets belong to that frame?
Thanks a lot for your help
I would parse the complete TS packet. So first determine what PID your video stream belongs to (by parsing the PAT and PMT). Then find keyframes by looking for the 'Random Access indicator' bit in the Adaptation Field.
uint8_t *pkt = <your 188 byte TS packet>;
assert( 0x47 == pkt[0] );
int16_t pid = ( ( pkt[1] & 0x1F) << 8 ) | pkt[2];
if ( pid == video_pid ) {
// found video stream
if( ( pkt[3] & 0x20 ) && ( pkt[4] > 0 ) ) {
// have AF
if ( pkt[5] & 0x40 ) {
// found keyframe
} } }
If you are using H.264 there should be specific byte stream for I and P frame ..
Like 0x0000000165 for I frame and 0x00000001XX for P frame ..
So just parse and look for continuous such byte stream in such a way you can identify I or P frame..
Again above byte stream is codec implementation dependent ..
For more information you can look into FFMPEG..

COBOL - copy an array to another array

how to copy an array to another array in cobol ?
A PIC 9999 occurs 5.
B PIC 9999 occurs 5.
i need to copy A to B. anyone can help me ?
Thanks All.
Working Storage
01 AA.
03 A PIC 9999 occurs 5.
01 BB.
03 B PIC 9999 occurs 5.
Procedure:
MOVE AA TO BB.
HTH!
If you were looking for a loop:
01 AA-Length Pic S9(8) Binary value +0.
01 BB-Length Pic S9(8) Binary value +0.
01 II Pic S9(8) Binary value +0.
...and...
Compute AA-Length = Length of AA / Length of A(1)
Compute BB-Length = Length of BB / Length of B(1)
Perform varying II from 1 by 1
until II > AA-Length or II > BB-Length
Move A (II) to B (II)
End-Perform

Resources