Guest User

Untitled

a guest
Aug 9th, 2018
205
0
Never
Not a member of Pastebin yet? Sign Up, it unlocks many cool features!
COBOL 16.72 KB | None | 0 0
  1.        IDENTIFICATION DIVISION.
  2.        PROGRAM-ID. UC2 INITIAL.
  3.        AUTHOR. Robbin Verbist.
  4.        ENVIRONMENT DIVISION.
  5.        INPUT-OUTPUT SECTION.
  6.        FILE-CONTROL.
  7.        COPY 'log_bestandbeschrijving'.
  8.        SELECT in-parameters ASSIGN TO parameterPath
  9.                 ORGANIZATION IS LINE SEQUENTIAL
  10.                 ACCESS MODE IS SEQUENTIAL.
  11.        SELECT out-temp ASSIGN TO 'temp'
  12.                 ORGANIZATION IS LINE SEQUENTIAL
  13.                 ACCESS MODE IS SEQUENTIAL.
  14.        SELECT out-csv ASSIGN TO 'overview.csv'
  15.                 ORGANIZATION IS LINE SEQUENTIAL
  16.                 ACCESS MODE IS SEQUENTIAL.
  17.        SELECT out-printer ASSIGN TO PRINTER
  18.                 ORGANIZATION IS LINE SEQUENTIAL
  19.                 ACCESS MODE IS SEQUENTIAL.
  20.        DATA DIVISION.
  21.        FILE SECTION.
  22.        COPY 'log_beschrijving'.
  23.        FD in-parameters.
  24.        01 in-parameters-line            PIC X(1024).
  25.         88 in-parameter-eof              VALUE HIGH-VALUES.
  26.        FD out-temp.
  27.        01 out-temp-line                 PIC X(1024).
  28.         88 out-temp-eof                  VALUE HIGH-VALUES.
  29.        FD out-csv.
  30.        01 out-csv-line                  PIC X(1024).
  31.         88 out-csv-eof                   VALUE HIGH-VALUES.
  32.        FD out-printer.
  33.        01 out-printer-line              PIC X(1024).
  34.         88 out-printer-eof               VALUE HIGH-VALUES.
  35.        WORKING-STORAGE SECTION.
  36.        01 settings.
  37.     ** Defines the behaviour of the application when a statement is executed
  38.     ** with a warning. Options:
  39.     **       - Y: ignores any warnings, execution continues
  40.     **       - N: bails on warnings, execution halts
  41.     ** See DO-EXECUTE-STATEMENT
  42.         03 query-warning-policy         PIC X VALUE 'N'.
  43.          88 exit-on-warning              VALUE 'N'.
  44.          88 ignore-on-warning            VALUE 'Y'.
  45.     ** Defines the behaviour of the application when a statement is executed
  46.     ** with an error. Options:
  47.     **       - Y: ignores any errors, execution continues
  48.     **       - N: bails on errors, execution halts
  49.     ** See DO-EXECUTE-STATEMENT
  50.         03 query-error-policy       PIC X VALUE 'N'.
  51.          88 exit-on-error                VALUE 'N'.
  52.          88 ignore-on-error              VALUE 'Y'.
  53.     ** Table 'class' - holds state for table-based operations
  54.     ** See TABLE-ADD-VALUE, TABLE-CLEAR, TABLE-PRINT
  55.        01 tablemodel.
  56.         03 table-seperator              PIC X VALUE ';'.
  57.         03 table-row occurs 50.
  58.          05 table-row-usage             PIC 9 VALUE 0.
  59.           88 table-row-unused           VALUE 0.
  60.           88 table-row-used             VALUE 1.
  61.          05 table-column occurs 50.
  62.           07 table-column-usage         PIC 9 VALUE 0.
  63.            88 table-column-unused       VALUE 0.
  64.            88 table-column-used         VALUE 1.
  65.           07 table-value                PIC X(10).
  66.         03 variables.
  67.          05 index-row                   PIC 99.
  68.          05 index-col                   PIC 99.
  69.          05 index-row-value             PIC X(80).
  70.          05 index-col-value             PIC X(10).
  71.          05 table-print-index           PIC 999.
  72.      
  73.        01 parameter-data.
  74.         03 db-url                       PIC X(1024).
  75.         03 db-statement                 PIC X(1024).
  76.         03 db-connection-status         PIC X VALUE 'N'.
  77.          88 db-connected                 VALUE 'Y'.
  78.          88 db-disconnected              VALUE 'N'.
  79.         03 gameId                       PIC 9(4).
  80.         03 rapport-type                 PIC X(20).
  81.          88 rapport-totaal               VALUE "totaal".
  82.          88 rapport-deel                 VALUE "deel".
  83.          88 rapport-detail               VALUE "detail".
  84.         03 output-type                  PIC X(20).
  85.          88 output-print                 VALUE "print".
  86.          88 output-csv                   VALUE "csv".
  87.         03 detail-args                  PIC X(1024).
  88.        EXEC SQL
  89.          BEGIN DECLARE SECTION
  90.        END-EXEC
  91.        01 SQLCODE PIC S9(3).
  92.        01 SQLSTATE PIC X(5).
  93.        01 query-totaalscores.
  94.         03 team-name                    PIC X(20).
  95.         03 OGS-score                    PIC 99v99.
  96.         03 OHS-score                    PIC 99v99.
  97.         03 OSS-score                    PIC 99v99.
  98.         03 ODQS-score                   PIC 99v99.
  99.        EXEC SQL
  100.          END DECLARE SECTION
  101.        END-EXEC
  102.        LINKAGE SECTION.
  103.     ** The path to the parameter file, required.
  104.        01 parameterPath                 PIC X(1024) VALUE LOW-VALUES.
  105.         88 parameterPathEmpty            VALUE LOW-VALUES.
  106.        PROCEDURE DIVISION USING parameterPath.
  107.        
  108. ******* Function: MAIN-PARAGRAPH
  109. ******* Arguments: N/A
  110. ******* Main application loop
  111.        MAIN-PARAGRAPH.
  112.        OPEN OUTPUT in-log
  113.        IF parameterPathEmpty THEN
  114.         MOVE "# ERROR: Please supply a parameter file path."
  115.         TO in-log-line
  116.         PERFORM DO-LOG
  117.         PERFORM DO-EXIT
  118.         EXIT PROGRAM
  119.        END-IF
  120.        OPEN INPUT in-parameters
  121.     ** parse the parameter file: read the database URL
  122.        READ in-parameters
  123.         AT END
  124.          MOVE "# ERROR: Incorrect file format." TO in-log-line
  125.          PERFORM DO-LOG
  126.          PERFORM DO-EXIT
  127.          EXIT PROGRAM
  128.        END-READ
  129.        MOVE in-parameters-line TO db-url
  130.     ** parse the parameter file: read the Game ID
  131.        READ in-parameters
  132.         AT END
  133.          MOVE "# ERROR: Incorrect file format." TO in-log-line
  134.          PERFORM DO-LOG
  135.          PERFORM DO-EXIT
  136.          EXIT PROGRAM
  137.        END-READ
  138.        MOVE in-parameters-line TO gameId
  139.     ** parse the parameter file: read and validate the report type
  140.        READ in-parameters
  141.         AT END
  142.          MOVE "# ERROR: Incorrect file format." TO in-log-line
  143.          PERFORM DO-LOG
  144.          PERFORM DO-EXIT
  145.          EXIT PROGRAM
  146.        END-READ
  147.        MOVE in-parameters-line TO rapport-type
  148.        IF NOT (rapport-totaal OR rapport-deel OR rapport-detail)
  149.        THEN
  150.         MOVE "# ERROR: Invalid rapport type option." to in-log-line
  151.         PERFORM DO-LOG
  152.         PERFORM DO-EXIT
  153.         EXIT PROGRAM
  154.        END-IF
  155.     ** parse the parameter file: read and validate the output type
  156.        READ in-parameters
  157.         AT END
  158.          MOVE "# ERROR: Incorrect file format." TO in-log-line
  159.          PERFORM DO-LOG
  160.          PERFORM DO-EXIT
  161.          EXIT PROGRAM
  162.        END-READ
  163.        MOVE in-parameters-line TO output-type
  164.        IF NOT (output-print OR output-csv)
  165.        THEN
  166.         MOVE "# ERROR: Invalid output type option." to in-log-line
  167.         PERFORM DO-LOG
  168.         PERFORM DO-EXIT
  169.         EXIT PROGRAM
  170.        END-IF
  171.       * create report(s)
  172.        IF output-print THEN MOVE ' ' TO table-seperator END-IF
  173.        IF output-csv THEN MOVE ';' TO table-seperator END-IF
  174.        OPEN OUTPUT out-temp
  175.        IF rapport-totaal THEN PERFORM DO-RAPPORT-TOTAAL END-IF
  176.        IF rapport-deel THEN PERFORM DO-RAPPORT-DEEL END-IF
  177.        IF rapport-detail THEN PERFORM DO-RAPPORT-DETAIL END-IF
  178.        CLOSE out-temp
  179.        IF output-print THEN PERFORM DO-OUTPUT-PRINTER END-IF
  180.        IF output-csv THEN PERFORM DO-OUTPUT-CSV END-IF
  181.        
  182.       * cleanup resources
  183.        PERFORM DO-EXIT
  184.        EXIT PROGRAM.
  185.              
  186.        DO-RAPPORT-TOTAAL.
  187.     ** Connect to the database, declare a cursor and open it
  188.     ** this cursor will get the relevant scores of the last period
  189.     ** for each team in the given game. (note: the query can probably
  190.     ** be optimized to avoid aggregates, but who has the time?!)
  191.        PERFORM DO-CONNECT
  192.        EXEC SQL
  193.         DECLARE scores CURSOR FOR
  194.         SELECT tgamGameTeams.Name AS Name,
  195.          sum(tgamTeamPeriods.ScoreCumulativeOverallGame) AS OGS,
  196.          sum(tgamTeamPeriods.ScoreCumulativeHardSkills) AS OHS,
  197.          sum(tgamTeamPeriods.ScoreCumulativeSoftSkills) AS OSS,
  198.          sum(tgamTeamPeriods.ScoreCumulativeDocumentQuality) AS ODQS
  199.         FROM tgamTeamPeriods
  200.      INNER JOIN tgamGameTeams
  201.      ON tgamTeamPeriods.TeamId = tgamGameTeams.Id
  202.      INNER JOIN tgamGames
  203.      ON tgamGameTeams.GameId = tgamGames.Id
  204.         WHERE tgamGames.Id = :gameId AND
  205.               tgamTeamPeriods.PeriodId = tgamGames.CurrentPeriodId
  206.         GROUP BY tgamGameTeams.Name
  207.        END-EXEC
  208.        EXEC SQL
  209.         OPEN scores
  210.        END-EXEC
  211.     ** Clear the table buffer and create a header row
  212.        PERFORM TABLE-CLEAR
  213.        MOVE "Team Name" TO index-col-value
  214.        PERFORM TABLE-ADD-VALUE
  215.        ADD 1 TO index-col
  216.        MOVE "OG Score" TO index-col-value
  217.        PERFORM TABLE-ADD-VALUE
  218.        ADD 1 TO index-col
  219.        MOVE "OH Score" TO index-col-value
  220.        PERFORM TABLE-ADD-VALUE
  221.        ADD 1 TO index-col
  222.        MOVE "OS Score" TO index-col-value
  223.        PERFORM TABLE-ADD-VALUE
  224.        ADD 1 TO index-col
  225.        MOVE "ODQ Score" TO index-col-value
  226.        PERFORM TABLE-ADD-VALUE
  227.     ** Move each query result into a new content row.
  228.        ADD 1 TO index-row
  229.        EXEC SQL
  230.         FETCH scores INTO :team-name, :OGS-score, :OHS-score,
  231.                           :OSS-score, :ODQS-score
  232.        END-EXEC
  233.        PERFORM UNTIL SQLCODE = 100
  234.         MOVE 1 TO index-col
  235.         MOVE team-name TO index-col-value
  236.         PERFORM TABLE-ADD-VALUE
  237.         ADD 1 TO index-col
  238.         MOVE OGS-score TO index-col-value
  239.         PERFORM TABLE-ADD-VALUE
  240.         ADD 1 TO index-col
  241.         MOVE OHS-score TO index-col-value
  242.         PERFORM TABLE-ADD-VALUE
  243.         ADD 1 TO index-col
  244.         MOVE OSS-score TO index-col-value
  245.         PERFORM TABLE-ADD-VALUE
  246.         ADD 1 TO index-col
  247.         MOVE ODQS-score TO index-col-value
  248.         PERFORM TABLE-ADD-VALUE
  249.         ADD 1 TO index-row
  250.         EXEC SQL
  251.          FETCH scores INTO :team-name, :OGS-score, :OHS-score,
  252.                            :OSS-score, :ODQS-score
  253.         END-EXEC
  254.        END-PERFORM
  255.        EXEC SQL
  256.         CLOSE scores
  257.        END-EXEC
  258.        PERFORM DO-DISCONNECT
  259.     ** Print the table
  260.        PERFORM TABLE-PRINT.
  261.        
  262.        DO-RAPPORT-DEEL.
  263.         MOVE "# DO-RAPPORT-DEEL." to in-log-line
  264.         PERFORM DO-LOG.
  265.        
  266.        DO-RAPPORT-DETAIL.
  267.         MOVE "# DO-RAPPORT-DETAIL." to in-log-line
  268.         PERFORM DO-LOG.
  269.        
  270. ******* Function: DO-OUTPUT-CSV
  271. ******* Arguments: N/A
  272. ******* Writes the contents of the temporary file to the csv file.
  273.        DO-OUTPUT-CSV.
  274.         OPEN INPUT out-temp
  275.         OPEN OUTPUT out-csv
  276.         READ out-temp
  277.          AT END SET out-temp-eof TO TRUE
  278.         END-READ
  279.         PERFORM UNTIL out-temp-eof
  280.          MOVE out-temp-line to out-csv-line
  281.          WRITE out-csv-line
  282.          READ out-temp
  283.           AT END SET out-temp-eof TO TRUE
  284.          END-READ
  285.         END-PERFORM
  286.         CLOSE out-csv
  287.         CLOSE out-temp.
  288.        
  289. ******* Function: DO-OUTPUT-PRINTER
  290. ******* Arguments: N/A
  291. ******* Writes the contents of the temporary file to the printer.
  292.        DO-OUTPUT-PRINTER.
  293.         OPEN INPUT out-temp
  294.         OPEN OUTPUT out-printer
  295.         READ out-temp
  296.          AT END SET out-temp-eof TO TRUE
  297.         END-READ
  298.         PERFORM UNTIL out-temp-eof
  299.          MOVE out-temp-line to out-printer-line
  300.          WRITE out-printer-line
  301.          READ out-temp
  302.           AT END SET out-temp-eof TO TRUE
  303.          END-READ
  304.         END-PERFORM
  305.         CLOSE out-printer
  306.         CLOSE out-temp.
  307.        
  308. ******* Function: DO-LOG
  309. ******* Arguments: in-log-line
  310. ******* Provides a hook into the logging system for debugging purposes.
  311.        DO-LOG.
  312.        WRITE in-log-line.
  313.        
  314. ******* Function: DO-CONNECT
  315. ******* Arguments: db-url
  316. ******* Connects to the database using the given connection string.
  317.        DO-CONNECT.
  318.        IF db-disconnected THEN
  319.         EXEC SQL
  320.          CONNECT
  321.            TO :db-url        
  322.            DRIVER "com.microsoft.sqlserver.jdbc.SQLServerDriver"                
  323.         END-EXEC
  324.         IF SQLCODE <> 0 THEN
  325.          MOVE "# ERROR: Unable to connect to database." TO in-log-line
  326.          PERFORM DO-LOG
  327.          MOVE db-url TO in-log-line
  328.          PERFORM DO-LOG
  329.          PERFORM DO-EXIT
  330.          EXIT PROGRAM
  331.         END-IF
  332.         SET db-connected TO TRUE
  333.        ELSE
  334.         MOVE "# WARNING: Database is already open." TO in-log-line
  335.         PERFORM DO-LOG
  336.        END-IF.
  337.        
  338. ******* Function: DO-EXECUTE-STATEMENT
  339. ******* Arguments: db-statement
  340. ******* Executes the statement on the database.
  341.        DO-EXECUTE-STATEMENT.
  342.        IF db-connected THEN
  343.         EXEC SQL
  344.          EXECUTE IMMEDIATE :db-statement
  345.         END-EXEC
  346.         IF SQLCODE < 0 THEN
  347.          MOVE "# ERROR: Error executing the query." TO in-log-line
  348.          PERFORM DO-LOG
  349.          MOVE db-statement TO in-log-line
  350.          PERFORM DO-LOG
  351.          IF exit-on-error THEN
  352.           PERFORM DO-EXIT
  353.           EXIT PROGRAM
  354.          END-IF
  355.         END-IF
  356.         IF SQLCODE > 0 THEN
  357.          MOVE "# ERROR: Warning executing the query." TO in-log-line
  358.          PERFORM DO-LOG
  359.          MOVE db-statement TO in-log-line
  360.          PERFORM DO-LOG
  361.          IF exit-on-warning THEN
  362.           PERFORM DO-EXIT
  363.           EXIT PROGRAM
  364.          END-IF
  365.         END-IF
  366.        ELSE
  367.         MOVE "# WARNING: Database is closed." TO in-log-line
  368.         PERFORM DO-LOG
  369.        END-IF.
  370.        
  371. ******* Function: DO-EXECUTE-STATEMENT
  372. ******* Arguments: N/A
  373. ******* Disconnects from the database.
  374.        DO-DISCONNECT.
  375.        IF db-connected THEN
  376.         EXEC SQL
  377.          DISCONNECT
  378.         END-EXEC
  379.         IF SQLCODE <> 0 THEN
  380.          MOVE "# ERROR: Unable to disconnect from database."
  381.          TO in-log-line
  382.          PERFORM DO-LOG
  383.         END-IF
  384.         SET db-disconnected TO TRUE
  385.        END-IF.
  386.        
  387. ******* Name: DO-EXIT
  388. ******* Arguments: N/A
  389. ******* Cleans up any acquired resources and exits the application.
  390.        DO-EXIT.
  391.        PERFORM DO-DISCONNECT
  392.        CLOSE in-parameters
  393.        CLOSE in-log.
  394.        
  395. ******* Function: TABLE-ADD-VALUE
  396. ******* Arguments: index-row, index-col, index-col-value
  397. ******* Sets the value at the given row, column index and marks the location
  398. ******* as used. Note that the row, column indices must be [1, 50]
  399.        TABLE-ADD-VALUE.
  400.        IF 1 <= index-row AND index-row <= 50 THEN
  401.         IF 1 <= index-col AND index-col <= 50 THEN
  402.          SET table-row-used(index-row) TO TRUE
  403.          SET table-column-used(index-row, index-col) TO TRUE
  404.          MOVE index-col-value TO table-value(index-row, index-col)
  405.         END-IF
  406.        END-IF.
  407.        
  408. ******* Function: TABLE-CLEAR
  409. ******* Arguments: N/A
  410. ******* Clears the table by marking all row, column pairs as unused.
  411. ******* Moves the row, column cursor to 1, 1
  412.        TABLE-CLEAR.
  413.        MOVE SPACES TO index-row-value
  414.        MOVE SPACES TO index-col-value
  415.        PERFORM VARYING index-row FROM 1 BY 1 UNTIL index-row>50
  416.        SET table-row-unused(index-row) TO TRUE
  417.         PERFORM VARYING index-col FROM 1 BY 1 UNTIL index-col>50
  418.          SET table-column-unused(index-row, index-col) TO TRUE
  419.          MOVE SPACES TO table-value(index-row, index-col)
  420.         END-PERFORM
  421.        END-PERFORM
  422.        MOVE 1 TO index-row
  423.        MOVE 1 TO index-col.
  424.        
  425. ******* Function: TABLE-PRINT
  426. ******* Arguments: N/A
  427. ******* Iterates over each used column in each used row in the table.
  428. ******* Joins the column values with the given seperator AND delegates the
  429. ******* processing of the result to -ONCOLUMNRESULT AND -ONROWRESULT.
  430. ******* (Template Method Design Pattern)
  431.        TABLE-PRINT.
  432.        PERFORM VARYING index-row FROM 1 BY 1 UNTIL index-row>50
  433.         IF table-row-used(index-row) THEN
  434.          MOVE SPACES TO index-row-value
  435.          MOVE 1 TO table-print-index
  436.          PERFORM VARYING index-col FROM 1 BY 1 UNTIL index-col>50
  437.           IF table-column-used(index-row, index-col) THEN
  438.            MOVE SPACES TO index-col-value
  439.            MOVE table-value(index-row, index-col) TO index-col-value
  440.            PERFORM TABLE-PRINT-ONCOLUMNRESULT
  441.            STRING index-col-value DELIMITED BY SIZE
  442.             INTO index-row-value WITH POINTER table-print-index
  443.            END-STRING
  444.            STRING table-seperator DELIMITED BY SIZE
  445.             INTO index-row-value WITH POINTER table-print-index
  446.            END-STRING
  447.           END-IF
  448.          END-PERFORM
  449.          PERFORM TABLE-PRINT-ONROWRESULT
  450.         END-IF
  451.        END-PERFORM.
  452.        
  453. ******* Function: TABLE-PRINT-ONCOLUMNRESULT
  454. ******* Arguments: index-col, index-col-value
  455. ******* Occurs when a column has been processed.
  456.        TABLE-PRINT-ONCOLUMNRESULT.
  457.        
  458. ******* Function: TABLE-PRINT-ONROWRESULT
  459. ******* Arguments: index-row, index-row-value
  460. ******* Occurs when a row has been processed.
  461.        TABLE-PRINT-ONROWRESULT.
  462.        MOVE index-row-value TO out-temp-line
  463.        WRITE out-temp-line.
Add Comment
Please, Sign In to add comment