Tek-Tips is the largest IT community on the Internet today!

Members share and learn making Tek-Tips Forums the best source of peer-reviewed technical information on the Internet!

  • Congratulations SkipVought on being selected by the Tek-Tips community for having the most helpful posts in the forums last week. Way to Go!

Removing spaces form a Message

Status
Not open for further replies.

anirbanc

Programmer
Dec 22, 2008
2
0
0
IN
I have a i/p message line,consisting of some writing,some nos.etc. Now, anywhere in the msg there can be more than one space. I want to remove the spaces to one space if the
spaces are not at starting,or if its at staring then I
dont need any space.
for eg.
'a/c balace is $200.00 name is smith' sholud be
''a/c balace is $200.00 name is smith'

and if
' 'a/c balace is $200.00',I need it to be
'a/c balace is $200.00'

Please suggest me a way out.




 
Have a look at the UNSTRING statement.

Hope This Helps, PH.
FAQ219-2884
FAQ181-2886
 
...or have a look at the INSPECT statement to replace two spaces by one. If you want to replace multiple spaces by one you could use INSPECT in a loop.
 
How to use the INSPECT loop? can u write a scribble that?it would b helpful...
 
INSPECT has REPLACING, CONVERTING and TALYING, but with REPLACING you can replace only some definite characters with another, e.g.
INSPECT MY-STRING REPLACING ALL 'XY' BY 'AB'
or
Code:
INSPECT MY-STRING REPLACING ALL SPACE BY '*'
But then you will get for example instead of
Code:
'a/c balace is $200.00      name    is    smith'
this
Code:
'a/c*balace*is*$200.00******name****is****smith'
and this si not, what we need - we want reduce all spaces to one space only.
I don't know if this can be done simply with INSPECT, but instead of exploring the INSPECT alchemy you can code your own algorithm, like this
Code:
       [COLOR=#804040][b]IDENTIFICATION[/b][/color][COLOR=#804040][b] DIVISION[/b][/color].
       [COLOR=#804040][b]PROGRAM-ID[/b][/color].                  RMVSPACES.
       [COLOR=#804040][b]AUTHOR[/b][/color].                      MIKROM.
       [COLOR=#804040][b]ENVIRONMENT[/b][/color][COLOR=#804040][b] DIVISION[/b][/color].

       [COLOR=#804040][b]DATA[/b][/color][COLOR=#804040][b] DIVISION[/b][/color].
       [COLOR=#804040][b]WORKING-STORAGE[/b][/color][COLOR=#804040][b] SECTION[/b][/color].
       [COLOR=#2e8b57][b]01 [/b][/color]MY-INPUT-STRING          [COLOR=#804040][b]PIC[/b][/color] X([COLOR=#ff00ff]200[/color])
      [COLOR=#6a5acd]        [/color][COLOR=#804040][b]VALUE[/b][/color] [COLOR=#ff00ff]'a/c balace is $200.00      name    is    smith'[/color].
       [COLOR=#2e8b57][b]01 [/b][/color]MY-OUTPUT-STRING         [COLOR=#804040][b]PIC[/b][/color] X([COLOR=#ff00ff]200[/color]).

       [COLOR=#2e8b57][b]01 [/b][/color]WS-FIELDS.
          [COLOR=#2e8b57][b]05 [/b][/color] WS-DATA                     [COLOR=#804040][b]PIC[/b][/color] X([COLOR=#ff00ff]200[/color]).
          [COLOR=#2e8b57][b]05 [/b][/color] WS-DATA-LENGTH              [COLOR=#804040][b]PIC[/b][/color] [COLOR=#ff00ff]9[/color]([COLOR=#ff00ff]3[/color]).
          [COLOR=#2e8b57][b]05 [/b][/color] X                           [COLOR=#804040][b]PIC[/b][/color] [COLOR=#ff00ff]9[/color]([COLOR=#ff00ff]3[/color]).
          [COLOR=#2e8b57][b]05 [/b][/color] J                           [COLOR=#804040][b]PIC[/b][/color] [COLOR=#ff00ff]9[/color]([COLOR=#ff00ff]3[/color]).
          [COLOR=#2e8b57][b]05 [/b][/color] K                           [COLOR=#804040][b]PIC[/b][/color] [COLOR=#ff00ff]9[/color]([COLOR=#ff00ff]3[/color]).
          [COLOR=#2e8b57][b]05 [/b][/color] N                           [COLOR=#804040][b]PIC[/b][/color] [COLOR=#ff00ff]9[/color]([COLOR=#ff00ff]3[/color]).
          [COLOR=#2e8b57][b]05 [/b][/color] S                           [COLOR=#804040][b]PIC[/b][/color] [COLOR=#ff00ff]9[/color]([COLOR=#ff00ff]3[/color]).

       [COLOR=#804040][b]PROCEDURE[/b][/color][COLOR=#804040][b] DIVISION[/b][/color].
       [COLOR=#804040][b]MAIN[/b][/color].
      [COLOR=#6a5acd]     [/color][COLOR=#804040][b]INITIALIZE[/b][/color] WS-FIELDS

      [COLOR=#6a5acd]     [/color][COLOR=#804040][b]MOVE[/b][/color] MY-INPUT-STRING [COLOR=#804040][b]TO[/b][/color] WS-DATA
      [COLOR=#6a5acd]     [/color][COLOR=#008080]PERFORM[/color] COMPUTE-LENGTH-OF-THE-DATA
      [COLOR=#6a5acd]     [/color][COLOR=#804040][b]DISPLAY[/b][/color] [COLOR=#ff00ff]'MY-INPUT-STRING = '[/color]
      [COLOR=#6a5acd]              [/color]QUOTE
      [COLOR=#6a5acd]              [/color]MY-INPUT-STRING([COLOR=#ff00ff]1[/color]:WS-DATA-LENGTH)
      [COLOR=#6a5acd]              [/color]QUOTE
      [COLOR=#6a5acd]     [/color]END-DISPLAY
      [COLOR=#6a5acd]     [/color][COLOR=#804040][b]DISPLAY[/b][/color] [COLOR=#ff00ff]'LENGTH OF STRING = '[/color] WS-DATA-LENGTH

      [COLOR=#6a5acd]     [/color][COLOR=#008080]PERFORM[/color] FORMAT-STRING-WITH-SPACES

      [COLOR=#6a5acd]     [/color][COLOR=#008080]PERFORM[/color] COMPUTE-LENGTH-OF-THE-DATA
      [COLOR=#6a5acd]     [/color][COLOR=#804040][b]MOVE[/b][/color] WS-DATA [COLOR=#804040][b]TO[/b][/color] MY-OUTPUT-STRING
      [COLOR=#6a5acd]     [/color][COLOR=#804040][b]DISPLAY[/b][/color] [COLOR=#ff00ff]'MY-OUTPUT-STRING = '[/color]
      [COLOR=#6a5acd]              [/color]QUOTE
      [COLOR=#6a5acd]              [/color]MY-OUTPUT-STRING([COLOR=#ff00ff]1[/color]:WS-DATA-LENGTH)
      [COLOR=#6a5acd]              [/color]QUOTE
      [COLOR=#6a5acd]     [/color]END-DISPLAY
      [COLOR=#6a5acd]     [/color][COLOR=#804040][b]DISPLAY[/b][/color] [COLOR=#ff00ff]'LENGTH OF STRING = '[/color] WS-DATA-LENGTH

      [COLOR=#0000ff]*    End[/color]
      [COLOR=#6a5acd]     [/color][COLOR=#008080]GOBACK[/color]
      [COLOR=#6a5acd]     [/color].

       [COLOR=#804040][b]COMPUTE-LENGTH-OF-THE-DATA[/b][/color].
      [COLOR=#6a5acd]     [/color][COLOR=#804040][b]COMPUTE[/b][/color] X = [COLOR=#ff00ff]0[/color].
      [COLOR=#6a5acd]     [/color][COLOR=#804040][b]INSPECT[/b][/color] FUNCTION REVERSE(WS-DATA)
      [COLOR=#6a5acd]     [/color][COLOR=#804040][b]TALLYING[/b][/color] X
      [COLOR=#6a5acd]     [/color][COLOR=#804040][b]FOR[/b][/color] [COLOR=#804040][b]LEADING[/b][/color] [COLOR=#ff00ff]SPACES[/color].
      [COLOR=#6a5acd]     [/color][COLOR=#804040][b]COMPUTE[/b][/color] WS-DATA-LENGTH = [COLOR=#804040][b]LENGTH[/b][/color] [COLOR=#804040][b]OF[/b][/color] WS-DATA - X
      [COLOR=#6a5acd]     [/color].

       [COLOR=#804040][b]FORMAT-STRING-WITH-SPACES[/b][/color].
      [COLOR=#6a5acd]     [/color][COLOR=#804040][b]MOVE[/b][/color] WS-DATA-LENGTH [COLOR=#804040][b]TO[/b][/color] N
      [COLOR=#6a5acd]     [/color][COLOR=#008080]PERFORM[/color] [COLOR=#6a5acd]VARYING[/color] J [COLOR=#804040][b]FROM[/b][/color] [COLOR=#ff00ff]1[/color] [COLOR=#804040][b]BY[/b][/color] [COLOR=#ff00ff]1[/color] [COLOR=#804040][b]UNTIL[/b][/color] J > N
      [COLOR=#6a5acd]       [/color][COLOR=#804040][b]IF[/b][/color] WS-DATA(J : [COLOR=#ff00ff]1[/color]) = [COLOR=#ff00ff]SPACE[/color] [COLOR=#804040][b]AND[/b][/color] WS-DATA(J + [COLOR=#ff00ff]1[/color] : [COLOR=#ff00ff]1[/color]) = [COLOR=#ff00ff]SPACE[/color]
      [COLOR=#6a5acd]         [/color][COLOR=#804040][b]COMPUTE[/b][/color] J = J + [COLOR=#ff00ff]1[/color]
      [COLOR=#6a5acd]         [/color][COLOR=#804040][b]MOVE[/b][/color] J [COLOR=#804040][b]TO[/b][/color] K
      [COLOR=#0000ff]*        S - number of superfluous Spaces[/color]
      [COLOR=#6a5acd]         [/color][COLOR=#804040][b]INITIALIZE[/b][/color] S
      [COLOR=#0000ff]*        Search from position J+1 for Not-Space-Characters[/color]
      [COLOR=#6a5acd]         [/color][COLOR=#008080]PERFORM[/color] [COLOR=#804040][b]UNTIL[/b][/color] WS-DATA(K:[COLOR=#ff00ff]1[/color]) [COLOR=#804040][b]NOT[/b][/color] = [COLOR=#ff00ff]SPACE[/color]
      [COLOR=#6a5acd]           [/color][COLOR=#804040][b]ADD[/b][/color] [COLOR=#ff00ff]1[/color] [COLOR=#804040][b]TO[/b][/color] K
      [COLOR=#6a5acd]           [/color][COLOR=#804040][b]ADD[/b][/color] [COLOR=#ff00ff]1[/color] [COLOR=#804040][b]TO[/b][/color] S
      [COLOR=#6a5acd]         [/color][COLOR=#008080]END-PERFORM[/color]
      [COLOR=#0000ff]*        Shift substring left from position K to J[/color]
      [COLOR=#6a5acd]         [/color][COLOR=#804040][b]MOVE[/b][/color] WS-DATA(K : N - K + [COLOR=#ff00ff]1[/color]) [COLOR=#804040][b]TO[/b][/color] WS-DATA(J : N - K + [COLOR=#ff00ff]1[/color])
      [COLOR=#0000ff]*        Adjust new length[/color]
      [COLOR=#6a5acd]         [/color][COLOR=#804040][b]COMPUTE[/b][/color] N = N - S
      [COLOR=#0000ff]*        Clear last characters in String[/color]
      [COLOR=#6a5acd]         [/color][COLOR=#804040][b]MOVE[/b][/color] [COLOR=#ff00ff]SPACE[/color] [COLOR=#804040][b]TO[/b][/color] WS-DATA(N + [COLOR=#ff00ff]1[/color] : S)
      [COLOR=#6a5acd]       [/color][COLOR=#804040][b]END-IF[/b][/color]
      [COLOR=#6a5acd]     [/color][COLOR=#008080]END-PERFORM[/color]
      [COLOR=#6a5acd]     [/color][COLOR=#804040][b]MOVE[/b][/color] N [COLOR=#804040][b]TO[/b][/color] WS-DATA-LENGTH
      [COLOR=#6a5acd]     [/color].

Output
Code:
> call rmvspaces                                           
  MY-INPUT-STRING = 'a/c balace is $200.00      name    is 
    smith'                                                 
  LENGTH OF STRING = 046                                   
  MY-OUTPUT-STRING = 'a/c balace is $200.00 name is smith' 
  LENGTH OF STRING = 035

 
@mikrom: you're right of course. INSPECT ... REPLACING cannot be used in this case.
 
I have a subroutine in COBOL which does three things with a string of up to 999 bytes: 1), converts the case to upper, lower or title (or no conversion), 2) Justifies the string left, right or center (or no justification), 3) tests the string for caracters outside the range of 32 (space) through 126 (~), or 0-9, A-Z.
 
Since we're posting programs now:

Code:
 IDENTIFICATION DIVISION.
 PROGRAM-ID. REMSPACES.
 ENVIRONMENT DIVISION.
 DATA DIVISION.
 WORKING-STORAGE SECTION.
 01  INPUT-VARIABLES. 
     04  INPUT-STRING1             PIC X(80) VALUE
         "a/c balace is $200.00      name    is    smith".
     04  INPUT-STRING2             PIC X(80) VALUE
         "    a/c balace is      $200.00".
 01  PROCESSING-VARIABLES.
     04  PROC-STRING               PIC X(80).
     04  PARTS-WHOLE.
         08  PARTS-TABLE           PIC X(20) OCCURS 9 TIMES INDEXED BY PARTS-NDX.
     04  SPACE-COUNT               PIC S9(4) BINARY.
 01  OUTPUT-VARIABLES.
     04  OUTPUT-STRING             PIC X(80).

 PROCEDURE DIVISION.
 0000-MAIN SECTION.
     MOVE INPUT-STRING1 TO PROC-STRING.
     DISPLAY " INPUT: " PROC-STRING.
     PERFORM 1000-PROC-STR.
     DISPLAY "OUTPUT: " OUTPUT-STRING.
     DISPLAY " ".

     MOVE INPUT-STRING2 TO PROC-STRING.
     DISPLAY " INPUT: " PROC-STRING.
     PERFORM 1000-PROC-STR.
     DISPLAY "OUTPUT: " OUTPUT-STRING.
     DISPLAY " ".

     GOBACK.

 1000-PROC-STR SECTION.
* INITIALIZE VARIABLES.
     MOVE 0 TO SPACE-COUNT.
     MOVE SPACES TO PARTS-WHOLE.
     MOVE SPACES TO OUTPUT-STRING.
* REMOVE LEADING SPACES
     INSPECT PROC-STRING 
        TALLYING SPACE-COUNT FOR LEADING SPACES.
     MOVE PROC-STRING (SPACE-COUNT + 1:80) TO PROC-STRING.
* UNSTRING DATA
     UNSTRING PROC-STRING 
       DELIMITED BY ALL SPACES
       INTO PARTS-TABLE (1) PARTS-TABLE (2) PARTS-TABLE (3) PARTS-TABLE (4)
            PARTS-TABLE (5) PARTS-TABLE (6) PARTS-TABLE (7) PARTS-TABLE (8)
            PARTS-TABLE (9)
     END-UNSTRING.
* STRING DATA BACK
     STRING PARTS-TABLE (1) DELIMITED BY SPACES SPACE DELIMITED BY SIZE
            PARTS-TABLE (2) DELIMITED BY SPACES SPACE DELIMITED BY SIZE
            PARTS-TABLE (3) DELIMITED BY SPACES SPACE DELIMITED BY SIZE
            PARTS-TABLE (4) DELIMITED BY SPACES SPACE DELIMITED BY SIZE
            PARTS-TABLE (5) DELIMITED BY SPACES SPACE DELIMITED BY SIZE
            PARTS-TABLE (6) DELIMITED BY SPACES SPACE DELIMITED BY SIZE
            PARTS-TABLE (7) DELIMITED BY SPACES SPACE DELIMITED BY SIZE
            PARTS-TABLE (8) DELIMITED BY SPACES SPACE DELIMITED BY SIZE
            PARTS-TABLE (9) DELIMITED BY SPACES SPACE DELIMITED BY SIZE
       INTO OUTPUT-STRING
     END-STRING.

Output is:
Code:
 Input: a/c balace is $200.00      name    is    smith                                  
Output: a/c balace is $200.00 name is smith                                             
 Input:    a/c balace is      $200.00                                                  
Output: a/c balace is $200.00

Measurement is not management.
 
The output got mangled somewhere between copying and posting, it shouldn't have those additional lines.

Measurement is not management.
 
Hi Glenn9999,
Before I wrote the piece of code I posted above, I tried it first to solve with UNSTRING but I used probably DELIMITED BY SPACE instead of DELIMITED BY ALL SPACES and so I got in end effect what I don't expected - a space in some table elements.
:)
But the disadvantage with using STRING and UNSTRING is, that you need to know maximal possible number of words in the string.
 
anirbanc

this subject has been dealt with numerous times in this forum. If you do a Search (see tab at top of this message thread, right next to Forum) for UNSTRING you will find many useful threads dealing with this topic.

mikrom

mikrom said:
the disadvantage with using STRING and UNSTRING is, that you need to know maximal possible number of words in the string.

I disagree. You only need to know the maximum length of any input string you wish to handle. You can do it with 3 areas (input, temporary holding, output) where the temp and output areas are at least as large as the input field.

Code:
           MOVE SPACES                 TO OUTDATA
           MOVE 1                      TO POS-OUT
           MOVE 1                      TO POS-IN
           PERFORM WITH TEST AFTER
               UNTIL POS-IN  >= LENGTH OF INDATA
               OR    POS-OUT >= LENGTH OF OUTDATA
               OR    TEMP (1:LEN) = SPACES
                   UNSTRING INDATA     DELIMITED BY ALL SPACES
                                                 OR ALL TAB-CHAR
                                                 OR ALL LINE-FEED
                                                 OR ALL FORM-FEED
                       INTO TEMP       DELIMITER IN DLM
                                       COUNT     IN LEN
                                       POINTER   POS-IN
                   END-UNSTRING
                   IF  LEN > ZERO
                       IF  POS-OUT + LEN + 1 >= LENGTH OF OUTDATA
                           PERFORM DISPLAY-OUTDATA
                       END-IF
                       STRING TEMP (1:LEN) DELIMITED BY SIZE
                              DLM          DELIMITED BY SIZE
                         INTO OUTDATA      POINTER POS-OUT
                       END-STRING
                   ELSE
                       MOVE HIGH-VALUES    TO TEMP
                       MOVE 1              TO LEN
                   END-IF
           END-PERFORM
           .
      *
       DISPLAY-OUTDATA.
           ADD  1                          TO LINE-OUT
           DISPLAY OUTDATA                 LINE     LINE-OUT
                                           POSITION COL-OUT
           MOVE SPACES                     TO OUTDATA
           MOVE 1                          TO POS-OUT
           .

Code what you mean,
and mean what you code!
But by all means post your code!

Razalas
 
Hi razalas,

Thanks for the suggestions.
Your code is very interesting, for example I have never seen using OR with DELIMITED before.

But I need to compile and debug your code, so I understand it better - if I only look at it now, it seems to be complicated for me
:)
 
mikrom,

sorry I was/am a bit rushed when I responded earlier so I didn't post the full program. It might be easier to understand if I put the working storage out there too. I'll try to do tonight after I get home. I was hoping the procedure division would be enough to shed some light on how to do this if you don't know in advance how many individual words you might have to expect.

Code what you mean,
and mean what you code!
But by all means post your code!

Razalas
 
razalas,

It's not a big problem for me to add the working storage to the procedure division you posted here.
But I don't have the COBOL compiler at my hands now, because here in Europe it's about 22.35 and I'm at home. I only have COBOL compiler at my work, so I can try your example first tomorrow.
:)

But if you want to post the complete example it would be easier.

 
I think your making this harder than it is.

Tom

Code:
000010**PROGRAM1      
000020 IDENTIFICATION DIVISION.
000030 PROGRAM-ID. Program1 AS "Debug_Cobol_Applications_General.Program1".
000040 DATA DIVISION.
000050 WORKING-STORAGE SECTION.
000060 01  SUB1                        PIC 999 VALUE 1.
000070 01  SUB2                        PIC 999 VALUE 1.
000080 01  INPUT-DATA. 
000090     05 FILLER                   PIC X(100) VALUE 
000100         "THIS             IS          A TEST       ".
000110 01  OUTPUT-DATA                 PIC X(100) VALUE SPACES.     
000120
000130 PROCEDURE DIVISION.
000140 START-IT-ALL1.
000150     MOVE INPUT-DATA(SUB1:1) TO OUTPUT-DATA(SUB2:1)                
000160     PERFORM 
000170       VARYING SUB1 FROM 2 BY 1 
000180          UNTIL SUB1 > 100 OR INPUT-DATA(SUB1:) = SPACES
000190     IF INPUT-DATA(SUB1:1) NOT = SPACES OR OUTPUT-DATA(SUB2:1) NOT = SPACES 
000200          ADD 1 TO SUB2
000210          MOVE INPUT-DATA(SUB1:1) TO OUTPUT-DATA(SUB2:1)                
000220      END-IF
000230     END-PERFORM.
000240 
000250     DISPLAY "INPUT  :" INPUT-DATA.
000260     DISPLAY "OUTPUT :" OUTPUT-DATA.
000270     STOP RUN.
000280    
000290     
000300 END PROGRAM PROGRAM1.
000310
 
You're quite right, TLeaders. That is the algorithm I have used over the years. Of course, back in the old days, we didn't have referance modification available to us, so we had to redefine the strings as arrays of bytes; but the basic algorithm remains the same.
 
webrabbit

I know what you mean. Sometimes you just have to love these new fangeled gadgets.

Tom
 
mikrom said:
But the disadvantage with using STRING and UNSTRING is, that you need to know maximal possible number of words in the string.

Not really. I learned a little trick as you will see in this and in another thread.

webrabbit said:
Of course, back in the old days, we didn't have referance modification available to us, so we had to redefine the strings as arrays of bytes; but the basic algorithm remains the same.

Of course, the problem is the "new fangled gadgets" are what you have to use to make things efficient in the end. COBOL is very horrible when it comes to table access and reference modification. I've had time on programs be cut in half time-wise to go away from this kind of thing to the "new fangled gadgets". Although, this problem won't show much difference compared to some others.

Not related to what I said, but here's another way to do it:

Code:
 IDENTIFICATION DIVISION.
 PROGRAM-ID. NEWFILE1.
 ENVIRONMENT DIVISION.
 INPUT-OUTPUT SECTION.
 FILE-CONTROL.
     SELECT INFILE ASSIGN TO "INDATA.TXT"
     ORGANIZATION IS LINE SEQUENTIAL.
     SELECT OUTFILE ASSIGN TO "OUTDATA.TXT"
     ORGANIZATION IS LINE SEQUENTIAL.
 DATA DIVISION.
 FILE SECTION.
 FD  INFILE
     Record Varying in Size from 1 to 80
      	Depending on WS-Char-Cnt
     BLOCK CONTAINS 0 RECORDS.
 01  INFILE-REC.
     05  Char Occurs 1 to 80 times
    	Depending on WS-Char-Cnt.
        10  Each-Char   	Pic X.
 FD  OUTFILE
     BLOCK CONTAINS 0 RECORDS.
 01  OUTFILE-REC  PIC X(80).

 WORKING-STORAGE SECTION.
 01  TIMING-PROC.
     04  Start-Time       Pic 99/99/99/99.
     04  End-Time         Pic 99/99/99/99.
 01  PROCESSING-VARIABLES.
     04  WS-CHAR-CNT               PIC 9(4) COMP-5.
     04  PROC-STRING               PIC X(80).
     04  TV1                       PIC X(80).
     04  TV2                       PIC X(80).
     04  PV1                       PIC S9(4) COMP-5.
     04  EOF-DATA                  PIC X VALUE "N".
 01  OUTPUT-VARIABLES.
     04  OUTPUT-STRING             PIC X(80).

 PROCEDURE DIVISION.
 0000-MAIN SECTION.
     Move Function Current-Date (9:8) 	To Start-Time.

     OPEN INPUT INFILE
          OUTPUT OUTFILE.
     READ INFILE INTO PROC-STRING
       AT END MOVE "Y" TO EOF-DATA
     END-READ.
     PERFORM UNTIL EOF-DATA = "Y"
       PERFORM 1000-PROC-STR
       WRITE OUTFILE-REC FROM OUTPUT-STRING 
       READ INFILE INTO PROC-STRING
         AT END MOVE "Y" TO EOF-DATA
       END-READ
     END-PERFORM.
     CLOSE INFILE OUTFILE.
     Move Function Current-Date (9:8) 	To END-Time.
     DISPLAY "END: " END-TIME.
     DISPLAY "START: " START-TIME.
     GOBACK.

 1000-PROC-STR SECTION.
     MOVE 1 TO PV1.
     MOVE SPACES TO OUTPUT-STRING.
     PERFORM UNTIL PV1 > 80
       UNSTRING PROC-STRING DELIMITED BY ALL SPACES INTO TV1
             WITH POINTER PV1
       END-UNSTRING
       MOVE SPACES TO TV2
       STRING OUTPUT-STRING DELIMITED BY SPACES
              "*" DELIMITED BY SIZE
              TV1 DELIMITED BY SPACES
         INTO TV2
       END-STRING
       MOVE TV2 TO OUTPUT-STRING
     END-PERFORM.
     INSPECT OUTPUT-STRING REPLACING ALL "*" BY " ".
* REMOVE LEADING SPACES
     MOVE 0 TO PV1.
     INSPECT OUTPUT-STRING 
       TALLYING PV1 FOR LEADING SPACES.
     MOVE OUTPUT-STRING (PV1 + 1:) TO OUTPUT-STRING.

Measurement is not management.
 
Glenn, you say that COBOL is horrible in table access and reference modification. My experience has been that this is not true, as long a you avoid stupid things like non-binary subscripts and pointers. Indices help too. I don's know about pc COBOL as I only know mainframe assembly, so I can't really comment on pc COBOL, but Liant's technical support say there's no problem there either. Perhaps you could document what you mean by "horrible.".

Your code fails if the input string contains an "*", or whatever other character you might use for a marker. Furthermore, you have both a String and an Unstring inside a Perform loop. Both of these statements have very high overhead, much more than referance modification could have. In addition, there is a great deal of redundant data movement inside the loop. I watched the data move around and it is very bewildering.
 
Status
Not open for further replies.

Part and Inventory Search

Sponsor

Back
Top