Michael Coughlan

Home > Other > Michael Coughlan > Page 51


  03 FILLER PIC X(38) VALUE "SDSouth Dakota Pierre 00833354".

  03 FILLER PIC X(38) VALUE "TNTennessee Nashville 06456243".

  03 FILLER PIC X(38) VALUE "TXTexas Austin 26059203".

  03 FILLER PIC X(38) VALUE "UTUtah Salt Lake City02855287".

  03 FILLER PIC X(38) VALUE "VTVermont Montpelier 00626011".

  03 FILLER PIC X(38) VALUE "VAVirginia Richmond 08185867".

  03 FILLER PIC X(38) VALUE "WAWashington Olympia 06897012".

  03 FILLER PIC X(38) VALUE "WVWest Virginia Charleston 01855413".

  03 FILLER PIC X(38) VALUE "WIWisconsin Madison 05726398".

  03 FILLER PIC X(38) VALUE "WYWyoming Cheyenne 00576412".

  02 FILLER REDEFINES StateValues.

  03 State OCCURS 50 TIMES

  INDEXED BY StateIdx.

  04 StateCode PIC XX.

  04 StateName PIC X(14).

  04 StateCapital PIC X(14).

  04 StatePop PIC 9(8).

  LINKAGE SECTION.

  01 StateNum-IO PIC 99.

  88 ValidStateNum VALUE 1 THRU 50.

  01 StateCode-IO PIC XX.

  01 StateName-IO PIC X(14).

  01 StateCapital-IO PIC X(14).

  01 StatePop-IO PIC 9(8).

  01 ErrorFlag PIC 9.

  88 NoErrorFound VALUE ZERO.

  88 InvalidStateNum VALUE 1.

  88 NoSearchItems VALUE 2.

  88 NoSuchStateCode VALUE 3.

  88 NoSuchStateName VALUE 4.

  88 NoSuchCapital VALUE 5.

  PROCEDURE DIVISION USING StateNum-IO, StateCode-IO, StateName-IO,

  StateCapital-IO, StatePop-IO, ErrorFlag.

  415

  Chapter 16 ■ Creating Large SyStemS

  Begin.

  SET NoErrorFound TO TRUE

  SET StateIdx TO 1

  EVALUATE TRUE

  WHEN StateNum-IO NOT EQUAL ZEROS PERFORM SearchUsingStateNum

  WHEN StateCode-IO NOT EQUAL SPACES PERFORM SearchUsingStateCode

  WHEN StateName-IO NOT EQUAL SPACES PERFORM SearchUsingStateName

  WHEN StateCapital-IO NOT EQUAL SPACES PERFORM SearchUsingStateCapital

  WHEN OTHER SET NoSearchItems TO TRUE

  END-EVALUATE

  EXIT PROGRAM.

  SearchUsingStateNum.

  IF NOT ValidStateNum SET InvalidStateNum TO TRUE

  ELSE

  MOVE StateCode(StateNum-IO) TO StateCode-IO

  MOVE StateName(StateNum-IO) TO StateName-IO

  MOVE StateCapital(StateNum-IO) TO StateCapital-IO

  MOVE StatePop(StateNum-IO) TO StatePop-IO

  END-IF.

  SearchUsingStateCode.

  SEARCH State

  AT END SET NoSuchStateCode TO TRUE

  WHEN FUNCTION UPPER-CASE(StateCode(StateIdx)) EQUAL TO

  FUNCTION UPPER-CASE(StateCode-IO)

  SET StateNum-IO TO StateIdx

  MOVE StateCode(StateIdx) TO StateCode-IO

  MOVE StateName(StateIdx) TO StateName-IO

  MOVE StateCapital(StateIdx) TO StateCapital-IO

  MOVE StatePop(StateIdx) TO StatePop-IO

  END-SEARCH.

  SearchUsingStateName.

  SEARCH State

  AT END SET NoSuchStateName TO TRUE

  WHEN FUNCTION UPPER-CASE(StateName(StateIdx)) EQUAL TO

  FUNCTION UPPER-CASE(StateName-IO)

  SET StateNum-IO TO StateIdx

  MOVE StateCode(StateIdx) TO StateCode-IO

  MOVE StateName(StateIdx) TO StateName-IO

  MOVE StateCapital(StateIdx) TO StateCapital-IO

  MOVE StatePop(StateIdx) TO StatePop-IO

  END-SEARCH.

  SearchUsingStateCapital.

  SEARCH State

  AT END SET NoSuchCapital TO TRUE

  WHEN FUNCTION UPPER-CASE(StateCapital(StateIdx)) EQUAL TO

  FUNCTION UPPER-CASE(StateCapital-IO)

  SET StateNum-IO TO StateIdx

  416

  Chapter 16 ■ Creating Large SyStemS

  MOVE StateCode(StateIdx) TO StateCode-IO

  MOVE StateName(StateIdx) TO StateName-IO

  MOVE StateCapital(StateIdx) TO StateCapital-IO

  MOVE StatePop(StateIdx) TO StatePop-IO

  END-SEARCH.

  This program takes as parameters StateNum-IO, StateCode-IO, StateName-IO, StateCapital-IO, StatePop-IO,

  and ErrorFlag. Whichever of the first four parameters has a value is used as the search term to find the other information about the state. For instance, if StateName-IO has a value, then that is used as the search term to find the state number, state code, state capital, and state population.

  If an error condition is detected, such as none of the fields having a value, then the appropriate error condition is set; this results in an error code being returned in the ErrorFlag parameter. If ErrorFlag contains zero, then no error was detected. The errors detected are given by the following condition names:

  88 NoErrorFound VALUE ZERO.

  88 InvalidStateNum VALUE 1.

  88 NoSearchItems VALUE 2.

  88 NoSuchStateCode VALUE 3.

  88 NoSuchStateName VALUE 4.

  88 NoSuchCapital VALUE 5.

  The State Knowledge Game

  Listing 16-5 is a game to test your knowledge of the names, codes, capitals, and populations of American states. It uses the GetStateInfo external subprogram.

  Listing 16-5. A Game to Test Your Knowledge of American States

  IDENTIFICATION DIVISION.

  PROGRAM-ID. Listing16-5.

  AUTHOR. Michael Coughlan.

  DATA DIVISION.

  WORKING-STORAGE SECTION.

  01 Parameters.

  02 StateNum PIC 99.

  02 StateCode PIC XX.

  02 StateName PIC X(14).

  02 StateCapital PIC X(14).

  02 StatePop PIC 9(8).

  02 ErrorFlag PIC 9.

  01 idx PIC 99.

  01 CurrentTime.

  02 FILLER PIC 9(4).

  02 Seed PIC 9(4).

  01 RandState PIC 99.

  01 RandChoice PIC 9.

  417

  Chapter 16 ■ Creating Large SyStemS

  01 Answer PIC X(14).

  01 PopAnswer PIC 9(8).

  01 MinPop PIC 9(8).

  01 MaxPop PIC 9(8).

  01 PrnStatePop PIC ZZ,ZZZ,ZZ9.

  01 StrLength PIC 99.

  PROCEDURE DIVISION.

  Begin.

  ACCEPT CurrentTime FROM TIME

  COMPUTE RandState = FUNCTION RANDOM(Seed)

  PERFORM 8 TIMES

  COMPUTE RandState = (FUNCTION RANDOM * 50) + 1

  COMPUTE RandChoice = (FUNCTION RANDOM * 4) + 1

  CALL "GetStateInfo"

  USING BY REFERENCE RandState, StateCode, StateName,

  StateCapital, StatePop, ErrorFlag

  EVALUATE RandChoice

  WHEN 1 PERFORM TestCapitalFromState

  WHEN 2 PERFORM TestCodeFromState

  WHEN 3 PERFORM TestPopFromState

  WHEN 4 PERFORM TestStateFromCapital

  END-EVALUATE

  DISPLAY SPACES

  END-PERFORM

  STOP RUN.

  TestCapitalFromState.

  CALL "GetStringLength" USING BY CONTENT StateName

  BY REFERENCE StrLength

  DISPLAY "What is the capital of " StateName(1:StrLength) "? "

  WITH NO ADVANCING

  ACCEPT Answer

  IF FUNCTION UPPER-CASE(Answer) = FUNCTION UPPER-CASE(StateCapital)

  DISPLAY "That is correct"

  ELSE

  DISPLAY "That is incorrect. The capital of " StateName(1:StrLength)

  " is " StateCapital

  END-IF.

  TestCodeFromState.

  CALL "GetStringLength" USING BY CONTENT StateName

  BY REFERENCE StrLength

  DISPLAY "What is the state code for " StateName(1:StrLength) "? "

  WITH NO ADVANCING

  ACCEPT Answer

  IF FUNCTION UPPE
R-CASE(Answer) = FUNCTION UPPER-CASE(StateCode)

  DISPLAY "That is correct"

  ELSE

  DISPLAY "That is incorrect. The code for " StateName(1:StrLength)

  " is " StateCode

  END-IF.

  418

  Chapter 16 ■ Creating Large SyStemS

  TestPopFromState.

  CALL "GetStringLength" USING BY CONTENT StateName

  BY REFERENCE StrLength

  DISPLAY "What is the population of " StateName(1:StrLength) "? "

  WITH NO ADVANCING

  ACCEPT PopAnswer

  COMPUTE MinPop = PopAnswer - (PopAnswer * 0.25)

  COMPUTE MaxPop = PopAnswer + (PopAnswer * 0.25)

  MOVE StatePop TO PrnStatePop

  IF StatePop > MinPop AND < MaxPop

  DISPLAY "That answer is close enough. The actual population is " PrnStatePop

  ELSE

  DISPLAY "That is incorrect. The population of " StateName(1:StrLength)

  " is " PrnStatePop

  END-IF.

  TestStateFromCapital.

  CALL "GetStringLength" USING BY CONTENT StateCapital

  BY REFERENCE StrLength

  DISPLAY "Of what state is " StateCapital(1:StrLength) " the capital? "

  WITH NO ADVANCING

  ACCEPT Answer

  IF FUNCTION UPPER-CASE(Answer) = FUNCTION UPPER-CASE(StateName)

  DISPLAY "That is correct"

  ELSE

  DISPLAY "That is incorrect. The state for " StateCapital(1:StrLength)

  " is " StateName

  END-IF.

  IDENTIFICATION DIVISION.

  PROGRAM-ID. GetStringLength IS INITIAL.

  AUTHOR. Michael Coughlan.

  DATA DIVISION.

  WORKING-STORAGE SECTION.

  01 CharCount PIC 99 VALUE ZEROS.

  LINKAGE SECTION.

  01 StringParam PIC X(14).

  01 StringLength PIC 99.

  PROCEDURE DIVISION USING StringParam, StringLength.

  Begin.

  INSPECT FUNCTION REVERSE(StringParam) TALLYING CharCount

  FOR LEADING SPACES

  COMPUTE StringLength = 14 - CharCount

  EXIT PROGRAM.

  END PROGRAM GetStringLength.

  END PROGRAM Listing16-5.

  419

  Chapter 16 ■ Creating Large SyStemS

  This program contains a number of interesting features. First, it uses the RANDOM intrinsic function. The first time RANDOM is invoked, it generates a sequence of pseudo-random numbers using the current time as a seed. Subsequent uses of RANDOM return instances of those numbers.

  The program gets two random numbers: one to choose which state to ask about and the other to choose what

  kind of question to ask. Once the program has chosen the number of the state to ask about, it uses the CALL verb to get all the other information about the state. Depending on what question is asked, the program gets an answer from the user and then compares it with state information returned by the CALL.

  Although most answers must be exact, conversion to uppercase is done so the letter case of the answer is not an issue. And because you can’t expect users to know the exact population of a state, any answer within 25 percent (higher or lower) of the actual value is accepted as correct.

  An interesting problem is caused by displaying state names and capitals when the text does not fill the data item.

  In that case, the data item is space filled, which causes unsightly output when the text is be displayed. For instance, a question about the capital of Delaware might display as follows:

  : Of what state is Dover the capital?

  To solve this issue, reference modification is used to slice out the actual text. To enable this slicing, the program calculates the length of the text. Because this operation is performed a number of times, it is removed to the contained subprogram GetStringLength.

  Getting State Information

  Listing 16-6 also uses the subprogram GetStateInfo, but in a more straightforward way. When the user provides a piece of information, such as a state name, the program displays all the other information about the state. The state number and the state code are two of the items displayed and you might think that having both of these items in the table is redundant. However, the importance of the state code is obvious and when I wrote the game in Listing 16-5

  the state number proved useful because it made it easy to select the state at random. One other advantage of the state number is that you can use it to dump out all the values in the table (see Example 16-5).

  Example 16-5. Fragment Showing How to Display the State Table Values

  PERFORM VARYING idx FROM 1 BY 1 UNTIL idx > 50

  MOVE idx TO StateNum

  CALL "GetStateInfo"

  USING BY REFERENCE StateNum, StateCode, StateName,

  StateCapital, StatePop, ErrorFlag

  DISPLAY StateNum ". " StateCode SPACE StateName

  SPACE StateCapital SPACE StatePop

  END-PERFORM

  Listing 16-6. Using the GetStateInfo Subprogram as Intended

  IDENTIFICATION DIVISION.

  PROGRAM-ID. Listing16-6.

  AUTHOR. Michael Coughlan.

  DATA DIVISION.

  WORKING-STORAGE SECTION.

  01 Parameters.

  02 StateNum PIC 99.

  02 StateCode PIC XX.

  02 StateName PIC X(14).

  420

  Chapter 16 ■ Creating Large SyStemS

  02 StateCapital PIC X(14).

  02 StatePop PIC 9(8).

  02 ErrorFlag PIC 9.

  88 NoError VALUE ZERO.

  01 CurrentTime.

  02 FILLER PIC 9(4).

  02 Seed PIC 9(4).

  01 RandChoice PIC 9.

  01 PrnStatePop PIC ZZ,ZZZ,ZZ9.

  PROCEDURE DIVISION.

  Begin.

  ACCEPT CurrentTime FROM TIME

  COMPUTE RandChoice = FUNCTION RANDOM(Seed)

  PERFORM 8 TIMES

  DISPLAY SPACES

  INITIALIZE Parameters

  COMPUTE RandChoice = (FUNCTION RANDOM * 4) + 1

  EVALUATE RandChoice

  WHEN 1 DISPLAY "Enter a state number - " WITH NO ADVANCING

  ACCEPT StateNum

  WHEN 2 DISPLAY "Enter a two letter code - " WITH NO ADVANCING

  ACCEPT StateCode

  WHEN 3 DISPLAY "Enter a state name - " WITH NO ADVANCING

  ACCEPT StateName

  WHEN 4 DISPLAY "Enter a state capital - " WITH NO ADVANCING

  ACCEPT StateCapital

  END-EVALUATE

  CALL "GetStateInfo"

  USING BY REFERENCE StateNum, StateCode, StateName,

  StateCapital, StatePop, ErrorFlag

  IF NoError

  MOVE StatePop TO PrnStatePop

  DISPLAY StateNum ". " StateCode SPACE StateName

  SPACE StateCapital SPACE PrnStatePop

  ELSE

  DISPLAY "There was an error. Error Code = " ErrorFlag

  END-IF

  END-PERFORM

  STOP RUN.

  In this program the search term type is chosen at random, the user is asked to supply a value for it, and then GetStateInfo is called to return the appropriate values for that search term.

  421

  Chapter 16 ■ Creating Large SyStemS

  The IS EXTERNAL Clause

  The IS GLOBAL clause allows a program and its contained subprograms to share access to a data item. The IS EXTERNAL

  clause does the same for any subprogram in a run-unit (that is, any linked subprogram), but it has restrictions that make it much more cumbersome to use than the IS GLOBAL phrase. Whereas a data item that uses the IS GLOBAL phrase only has to be declared in one place, each of the subprograms that wish to access an EXTERNAL shared item must declare the item—and it must be declared exactly the same way in each subprogram. Figure 16-7 illustrates the IS EXTERNAL

  data-sharing mechanism.

  Figure 16-7.
The IS EXTERNAL data-sharing mechanism

  Figure 16-7 shows the calling structure of a run-unit that consists of four linked programs: a main program (ProgramA) and three subprograms. In the illustration, ProgramB and ProgramD share data using the IS EXTERNAL

  mechanism. In order to share the data, both subprograms must declare the data, and the declarations have to be exactly the same. That is, they must each have the following declaration:

  01 SharedRec IS EXTERNAL.

  02 Stock-Id PIC 9(7).

  02 Manf-Id PIC X(5).

  In this system, ProgramB communicates with ProgramD by passing it data through the shared data item

  SharedRec. This might work as follows: ProgramA does some work and then calls ProgramB, which moves a value into SharedRec as part of its work. When control returns to ProgramA, it does some more work, calls ProgramC to do some work, and then calls ProgramD. ProgramD then uses the data from the shared area SharedRec to perform its task.

  422

  Chapter 16 ■ Creating Large SyStemS

  IS EXTERNAL Problems

  The problem with using the IS EXTERNAL phrase is that the transfer of data between ProgramB and ProgramD is detectable only by inspecting B and D. Even though ProgramA invokes B and D, a programmer inspecting A will not realize that B and D are secretly communicating. Even worse, at some point in the future, a maintenance programmer may decide that ProgramC needs to communicate with ProgramD using the shared area and may overwrite the data placed there by ProgramB.

  The kind of hidden data communication between subprograms that you see when you use the IS EXTERNAL

  clause is generally regarded as very poor practice. According to the measures of module goodness discussed by Myers1 common coupling is almost the worst kind of data connection you can have between modules. Subprograms that use the IS EXTERNAL clause to create shared data items are common coupled. Common-coupled modules exhibit a number of problems, such as naming dependencies, creation of dummy structures, and exposure to unnecessary data. Most of these issues are caused by the requirement that each subprogram that wants to use the shared area must describe it exactly the same way.

  To illustrate the problem, consider the following scenario. A programmer creates a module to do check digit validation for the Stock-Id. Instead of using the parameter list to get the number to be validated, the programmer takes advantage of the fact that the Stock-Id is an EXTERNAL shared data item and gets access to the Stock-Id using this shared area. The first problem the programmer has is to make sure that their module is not overwriting the data moved into the shared area by some other subprogram. The second problem the programmer has is that their module has to describe the shared area as follows:

 

‹ Prev