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 gkittelson on being selected by the Tek-Tips community for having the most helpful posts in the forums last week. Way to Go!

Remove SPACES using INSPECT ?

Status
Not open for further replies.

Yanndewael

Programmer
Mar 14, 2003
12
GB
Hello,

I would like to remove spaces from a variable (ex: "This is the value" being convert into "Thisisthevalue" without having to use PERFORM checking all characters of the variable. I suspect it could be possible using the command INSPECT, but I don't know how. I tried
INSPECT VARIABLE REPLACING " " BY ""
but it don't work.

Any idea?

Thank you in advance

Yann
 
Nope.

Inspect will replace one string with another of the same size.

Look at using the command string in conjunction with command unstring.

Somehing on these lines.
loop until no more text to separate
move spaces to fieldy
unstring fieldx delimited by all spaces into fieldy
pointer pointer1
string fieldy delimited by spaces
into fieldz
pointer pointer2
next


Regards

Frederico Fonseca
SysSoft Integrated Ltd
 
I was just in a lazy creative mood...
Thought something like this might be fun...
It may work but is probably not so efficient...
I haven't tried it...it was just a quick thought...

05 thePointer PIC 9(03) BINARY.
05 theEnd PIC 9(03) BINARY.
05 theField PIC X(100)
VALUE ' field contains some data '.

MOVE 1 TO thePointer
MOVE LENGTH OF theField TO theEnd

PERFORM UNTIL thePointer > theEnd
,
, IF theField(thePointer :1 ) = SPACE
, , MOVE theField(thePointer + 1: )
, , TO theField(thePointer : )
, , SUBTRACT 1 FROM theEnd
, ,
, ELSE
, , ADD 1 TO thePointer
, ,
, END-IF
,
END-PERFORM
 
Couldn't be easier ...

Code:
       01  source-field    pic x(999).
       01  source-index    pic 9(004).
       01  source-size     pic 9(004) value 999.
       
       01  target-field    pic x(999).
       01  target-index    pic 9(004).
       
           move spaces to target-field.
           move zeroes to target-index
           perform varying source-index from 1 by 1 
                   until source-index > source-size
               if source-field(source-index:1) > space
                  add 1 to target-index
                  move source-field(source-index:1) to
                       target-field(target-index:1)
               end-if
           end-perform.


It may not be elegant but it works!

gafling
 
I have always used a PERFORM. I would be interested if someone comes up with a different way.
 
I don't think this is possible using COBOL (without using perform)...but I am still thinking about it (challenge!).

But this might be possible in REXX (though I don't think that is your intention).

REXX has many sophisticated string manipulation instructions (n.b. the last time I used REXX was in 1996!).

Regards, Wim.
 
Wim,

I haven't used Rexx this century either and can't remember the precise syntax off the top of my head, but it's hardly a challenge in Rexx and needs, at most, two lines.

In Cobol I would think that Frederico's Unstring/String solution is the best non-Perform method.

Enjoy,
Tony

--------------------------------------------------------------------------------------------
We want to help you; help us to do it by reading this: Before you ask a question.
 
Working example.

Note the fact that the "if vtemp not = spaces" is commented.
This is not required on this case as we are using a delimited by spaces, but should the delimiter be other it might be needed.

Note the a perform is always required if we wish to have a good code.
If not a series of if's would also work, but that would be bad programming on my opinion. e.g. replace the perform with a series of " if p1 not > 11 unstring/string end if"

Code:
       IDENTIFICATION DIVISION.
       PROGRAM-ID.  testing.
       ENVIRONMENT DIVISION.
       DATA DIVISION.
       WORKING-STORAGE SECTION.
       01 V1            pic x(11) value "ABC-DEF-GHI".
       01 V2            pic x(11) value "ABC-DEF GHI".
       01 V3            pic x(11) value " ABCDEF GHI".
       01 V4            pic x(11) value "ABCD FGHI  ".
       01 V5            pic x(11) value " ABCD FGHI ".
       01 V6            pic x(11) value " A  DE GHI ".
       01 V7            pic x(11) value "ABC  EF  HI".
       01 V8            pic x(11) value " ABCDE  GHI".
       01 V9            pic x(11) value "AB   F  I  ".
       01 VOUT          PIC X(11).
       01 VWORK         PIC X(11).
       01 VTEMP         PIC X(11).
       01 p1 pic 99.
       01 p2 pic 99.

       PROCEDURE       DIVISION.
       MAIN.
           MOVE V1 to VWORK
           PERFORM UNSTRING1.
           MOVE V1 to VWORK
           PERFORM UNSTRING1.
           MOVE V2 to VWORK
           PERFORM UNSTRING1.
           MOVE V3 to VWORK
           PERFORM UNSTRING1.
           MOVE V4 to VWORK
           PERFORM UNSTRING1.
           MOVE V5 to VWORK
           PERFORM UNSTRING1.
           MOVE V6 to VWORK
           PERFORM UNSTRING1.
           MOVE V7 to VWORK
           PERFORM UNSTRING1.
           MOVE V8 to VWORK
           PERFORM UNSTRING1.
           MOVE V9 to VWORK
           PERFORM UNSTRING1.
           ACCEPT P1.
           GOBACK.
       UNSTRING1.
           MOVE 1 TO P1 P2.
           MOVE SPACES TO VOUT VTEMP.
           PERFORM UNTIL P1 > 11
           MOVE SPACES TO VOUT VTEMP.
           PERFORM UNTIL P1 > 11
              UNSTRING VWORK DELIMITED BY ALL SPACES
                  INTO VTEMP
               POINTER P1
      *       IF VTEMP NOT = SPACES
                 STRING VTEMP DELIMITED BY SPACES
                   INTO VOUT
                 POINTER P2
      *       END-IF
           END-PERFORM.
           DISPLAY "Input var = " VWORK " == Output Var = " VOUT.

Regards

Frederico Fonseca
SysSoft Integrated Ltd
 
Oops. Cut & paste error.

remove the first
MOVE SPACES TO VOUT VTEMP.
PERFORM UNTIL P1 > 11
for the code to work.


And although the one perform is required this is not doing a "char by char" perform which was to avoid as per required.

Regards

Frederico Fonseca
SysSoft Integrated Ltd
 
I haven't created the code yet (much less tested it). However, you COULD do an INSPECT to tally the number of characters before the first space, then reference modify a move of all "trailing characters" to the original space location, then repeat until all spaces are at end of non-space data.

Other than meeting the "challenge" to use INSPECT and not PERFORM, I don't see much advantage to this, but it COULD be done.

Bill Klein
 
Yeah, Morrison, I did notice.

For this particular problem a solution without PERFORM is impractical and very likely much slower than something like what I wrote. I am not advocating my code as the 'best' solution; you could 'sex it up' by pre-computing the source field length or reference-mod comparing to see if there are any more non-spaces after the last character moved. But all of these involve examining each character anyway. So, IMHO, the best way to do it is to pass the data only once.

Besides, a machine-language generating compiler will optimize much of that code and be very efficient. I realize that RM-COBOL is POPS code, but it would still be more efficient to do a single pass of the data.
 
Frederico,

He/she is responding to my pointing out that the Original Poster desired a solution without a PERFORM looking at each character, I think. Yours is the way I would do it, I think.

Tom
 
[tt]

Example 1A; Remove spaces without utilizing go to, per byte
performs or per-byte moves. For compilers that allow
intrafield moves utilizing reference modifiers.

Compiled 11jun2004 on VC820R-P3 with Micro Focus COBOL2
Version 3.0.23


[/tt]
Code:
       IDENTIFICATION DIVISION.
       PROGRAM-ID.   EXAMP1A.
       ENVIRONMENT DIVISION.
       DATA DIVISION.
       FILE SECTION.

       WORKING-STORAGE SECTION.
       01 WK-LOCAL-STOR.
           02 PACK-DATA           PIC X(999).
           02 PACK-LEN            PIC 999.
           02 PACK-PTR            PIC 999.

       PROCEDURE DIVISION.
       OOOO-INIT.
           DISPLAY SPACES AT 0101 WITH FOREGROUND-COLOR IS 7
             BLANK SCREEN
           END-DISPLAY
           INITIALIZE WK-LOCAL-STOR
           MOVE "Remove All Of My Spaces" TO PACK-DATA.


       5000-PACKME.
           INSPECT FUNCTION REVERSE(PACK-DATA) 
             TALLYING PACK-LEN FOR LEADING SPACE
           SUBTRACT PACK-LEN FROM 999 GIVING PACK-LEN
           PERFORM UNTIL PACK-PTR NOT LESS THAN PACK-LEN
            ADD 0 TO 0 GIVING PACK-PTR
            INSPECT PACK-DATA TALLYING PACK-PTR FOR CHARACTERS
              BEFORE INITIAL SPACE
            ADD 1 TO PACK-PTR
            IF PACK-PTR LESS THAN PACK-LEN
             THEN
              MOVE PACK-DATA 
              ((PACK-PTR + 1):(PACK-LEN - PACK-PTR))
               TO PACK-DATA (PACK-PTR:)
              MOVE SPACE TO PACK-DATA (PACK-LEN:1)
              SUBTRACT 1 FROM PACK-LEN
            END-IF
           END-PERFORM.


       8000-DISPLAY.
           DISPLAY PACK-DATA AT 0502
           DISPLAY ' ' AT 0601
           END-DISPLAY.

       9999-END.
           STOP RUN.
[tt]

Example 1B; Remove spaces without utilizing go to, per byte
performs or per-byte moves. For compilers that do not allow
intrafield moves utilizing reference modifiers.

Compiled 11jun2004 on D875PBZ-P4 with Fujitsu COBOL97
Version 6.1L10

[/tt]
Code:
       IDENTIFICATION DIVISION.
       PROGRAM-ID.   EXAMP2B.
       ENVIRONMENT DIVISION.
       DATA DIVISION.
       FILE SECTION.

       WORKING-STORAGE SECTION.
       01 WK-LOCAL-STOR.
           02 PACK-IN             PIC X(999).
           02 PACK-OUT            PIC X(999).
           02 PACK-LEN            PIC 999.
           02 PACK-PTR            PIC 999.

       PROCEDURE DIVISION.
       OOOO-INIT.
           INITIALIZE WK-LOCAL-STOR
           MOVE "Remove All Of My Spaces"
            TO PACK-IN PACK-OUT.


       5000-PACKME.
           INSPECT FUNCTION REVERSE(PACK-IN) TALLYING PACK-LEN
             FOR LEADING SPACE
           SUBTRACT PACK-LEN FROM 999 GIVING PACK-LEN
           PERFORM UNTIL PACK-PTR NOT LESS THAN PACK-LEN
            ADD 0 TO 0 GIVING PACK-PTR
            INSPECT PACK-IN TALLYING PACK-PTR FOR 
             CHARACTERS BEFORE INITIAL SPACE
            ADD 1 TO PACK-PTR
            IF PACK-PTR LESS THAN PACK-LEN
             THEN
              MOVE PACK-IN ((PACK-PTR + 1):) TO 
               PACK-OUT (PACK-PTR:)
              MOVE SPACE TO PACK-OUT (PACK-LEN:1)
              SUBTRACT 1 FROM PACK-LEN
              MOVE PACK-OUT TO PACK-IN
            END-IF
           END-PERFORM.

       8000-DISPLAY.
           DISPLAY PACK-OUT
           END-DISPLAY.

       9999-END.
           STOP RUN.
[tt]

Example 2A; Remove spaces without utilizing go to, per byte
performs, per-byte moves or redundant inspects. For
compilers that allow intrafield moves utilizing reference
modifiers.

Compiled 11jun2004 on VC820R-P3 with Micro Focus COBOL2
Version 3.0.23

[/tt]
Code:
       IDENTIFICATION DIVISION.
       PROGRAM-ID.   EXAMP2A.
       ENVIRONMENT DIVISION.
       DATA DIVISION.
       FILE SECTION.

       WORKING-STORAGE SECTION.
       01 WK-LOCAL-STOR.
           02 PACK-DATA           PIC X(999).
           02 PACK-LEN            PIC 999.
           02 PACK-PTR            PIC 999.
           02 PACK-CNT            PIC 999.

       PROCEDURE DIVISION.
       OOOO-INIT.
           DISPLAY SPACES AT 0101 WITH FOREGROUND-COLOR IS 7
             BLANK SCREEN
           END-DISPLAY
           INITIALIZE WK-LOCAL-STOR
           ADD 1 TO PACK-PTR
           MOVE "Remove All Of My Spaces" TO PACK-DATA.


       5000-PACKME.
           INSPECT FUNCTION REVERSE(PACK-DATA) 
             TALLYING PACK-LEN FOR LEADING SPACE
           SUBTRACT PACK-LEN FROM 999 GIVING PACK-LEN
           PERFORM UNTIL PACK-PTR NOT LESS THAN PACK-LEN
            ADD 0 TO 0 GIVING PACK-CNT
            INSPECT PACK-DATA (PACK-PTR:) TALLYING 
              PACK-CNT FOR CHARACTERS BEFORE INITIAL SPACE
            ADD PACK-CNT TO PACK-PTR
            IF PACK-PTR LESS THAN PACK-LEN
             THEN
              MOVE PACK-DATA 
                ((PACK-PTR + 1):(PACK-LEN - PACK-PTR))
                TO PACK-DATA (PACK-PTR:)
              MOVE SPACE TO PACK-DATA (PACK-LEN:1)
              SUBTRACT 1 FROM PACK-LEN
            END-IF
           END-PERFORM.


       8000-DISPLAY.
           DISPLAY PACK-DATA at 0502
           END-DISPLAY.

       9999-END.
           STOP RUN.
[tt]

Example 2B; Remove spaces without utilizing go to, per byte
performs, per-byte moves or redundant inspects. For
compilers do not allow intrafield moves utilizing reference
modifiers.

Compiled 11jun2004 on D875PBZ-P4 with Fujitsu COBOL97
Version 6.1L10

[/tt]
Code:
       IDENTIFICATION DIVISION.
       PROGRAM-ID.   EXAMP2B.
       ENVIRONMENT DIVISION.
       DATA DIVISION.
       FILE SECTION.

       WORKING-STORAGE SECTION.
       01 WK-LOCAL-STOR.
           02 PACK-IN             PIC X(999).
           02 PACK-OUT            PIC X(999).
           02 PACK-LEN            PIC 999.
           02 PACK-PTR            PIC 999.
           02 PACK-CNT            PIC 999.

       PROCEDURE DIVISION.
       OOOO-INIT.
           INITIALIZE WK-LOCAL-STOR
           ADD 1 TO 0 GIVING PACK-PTR
           MOVE "Remove All Of My Spaces" TO PACK-IN PACK-OUT.


       5000-PACKME.
           INSPECT FUNCTION REVERSE(PACK-IN) TALLYING 
             PACK-LEN FOR LEADING SPACE
           SUBTRACT PACK-LEN FROM 999 GIVING PACK-LEN.
           PERFORM UNTIL PACK-PTR NOT LESS THAN PACK-LEN
            ADD 0 TO 0 GIVING PACK-CNT
            INSPECT PACK-IN (PACK-PTR:) TALLYING PACK-CNT FOR
              CHARACTERS BEFORE INITIAL SPACE
            ADD PACK-CNT TO PACK-PTR
            IF PACK-PTR LESS THAN PACK-LEN
             THEN
              MOVE PACK-IN ((PACK-PTR + 1):) TO 
                PACK-OUT (PACK-PTR:)
              MOVE SPACE TO PACK-OUT (PACK-LEN:1)
              SUBTRACT 1 FROM PACK-LEN
              MOVE PACK-OUT TO PACK-IN
            END-IF
           END-PERFORM.


       8000-DISPLAY.
           DISPLAY PACK-OUT
           END-DISPLAY.

       9999-END.
           STOP RUN.
 
Thank you all for your answer. But since it appears that I have to use a PERFORM, here is the solution I took:

03 IDTBAN-T57-MSM PIC X(35).
03 I PIC 9(02).
03 I2 PIC 9(02).
03 TMPCHR PIC X(01).
03 TMPVAR PIC X(35).


MOVE ZEROES TO I2 OF WORKER.
MOVE SPACES TO TMPVAR OF WORKER.
PERFORM VARYING I FROM 1 BY 1
UNTIL I > 35
MOVE IDTBAN-T57-MSM OF WORKER(I:1) TO TMPCHR OF WORKER
IF TMPCHR OF WORKER NOT = " "
ADD 1 TO I2 OF WORKER
GIVING I2 OF WORKER
MOVE TMPCHR OF WORKER TO TMPVAR OF WORKER(I2:1)
END-IF
END-PERFORM.


The code is quite short and works correctly.

Yann
 
Yann,

Your solution is clean, but if you are doing this MANY times in a row using the unstring/unstring is faster.

In your code I would also remove the giving part from the add (no need for it), and eventually I would also add the following to the perform evaluation

UNTIL I > 35
or IDTBAN-T57-MSM OF WORKER(I:) = spaces

This bit I would only do if your names are normally less than half of the available PIC size.




Regards

Frederico Fonseca
SysSoft Integrated Ltd
 
Looks like you settled for code that uses a PERFORM and goes through each byte of the input value one at a time. How about trying this? It uses a PERFORM but not to go thru the input one byte at a time. It uses INSPECT to count the characters before a space and then basically moves one word at a time to the output area and gets rid of the imbedded spaces. After moving the word, the input field is shifted to the left to start over with the second word.

01 ACCUMULATOR-AREAS.
03 AA-START PIC S9(03).
03 AA-CHAR PIC S9(03).
01 INPUT-RECORD.
03 IR-FIELD-1.
05 FILLER VALUE 'THIS IS A ' PIC X(10).
05 FILLER VALUE 'TEST PHRASE' PIC X(11).
05 FILLER VALUE SPACES PIC X(04).
01 SAVE-AREA.
03 SA-OUT-AREA PIC X(25).

PROCEDURE DIVISION.
1000-TEST.
DISPLAY 'INPUT=' INPUT-RECORD
MOVE SPACES TO SA-OUT-AREA
MOVE +1 TO AA-START
PERFORM 2000-REMOVE-SPACES
UNTIL IR-FIELD-1 = SPACES
DISPLAY 'OUTPUT=' SA-OUT-AREA.
STOP RUN.
2000-REMOVE-SPACES.
MOVE +0 TO AA-CHAR
INSPECT IR-FIELD-1
TALLYING AA-CHAR FOR CHARACTERS
BEFORE INITIAL SPACE
MOVE IR-FIELD-1(1:AA-CHAR)
TO SA-OUT-AREA (AA-START:AA-CHAR)
ADD AA-CHAR TO AA-START
IF (AA-CHAR + 2) > LENGTH OF IR-FIELD-1
MOVE SPACES TO IR-FIELD-1
ELSE
MOVE IR-FIELD-1 (AA-CHAR + 2:)
TO IR-FIELD-1
END-F.

 
If the size of the field is relatively small, you could consider using the following. Assuming a space between each word, then the maximum number of words is half the field size.
Code:
IDENTIFICATION DIVISION.                        
PROGRAM-ID. MICKEY.                             
DATA DIVISION.                                  
WORKING-STORAGE SECTION.                        
01  WS-WORK.                                    
    05 WS-MISC                        PIC X(20) 
       VALUE 'THIS  IS A TEST  '.               
    05 WS-MISC2                       PIC X(20) 
       VALUE SPACES.                            
                                                
01 WS-WORDS VALUE SPACES.                       
    05 WS-WORD1                       PIC X(20).
    05 WS-WORD2                       PIC X(20).
    05 WS-WORD3                       PIC X(20).
    05 WS-WORD4                       PIC X(20).
    05 WS-WORD5                       PIC X(20).
    05 WS-WORD5                       PIC X(20).
    05 WS-WORD6                       PIC X(20).
    05 WS-WORD7                       PIC X(20).
    05 WS-WORD8                       PIC X(20).
    05 WS-WORD9                       PIC X(20).
    05 WS-WORD10                      PIC X(20).
                                                
PROCEDURE DIVISION.                             
                                                
    MOVE SPACES TO WS-MISC2                     
    UNSTRING WS-MISC                            
       DELIMITED BY ALL SPACES                  
       INTO WS-WORD1 WS-WORD2 WS-WORD3 WS-WORD4      
            WS-WORD5 WS-WORD6 WS-WORD7 WS-WORD8      
            WS-WORD9 WS-WORD10     
    END-UNSTRING          
                          
    STRING  WS-WORD1 WS-WORD2 WS-WORD3 WS-WORD4 
            WS-WORD5 WS-WORD6 WS-WORD7 WS-WORD8 
            WS-WORD9 WS-WORD10
       DELIMITED BY SPACES       
   INTO WS-MISC2             
END-STRING                   
                             
DISPLAY 'MISC2 ===>' WS-MISC2
STOP RUN.
 
Status
Not open for further replies.

Part and Inventory Search

Sponsor

Back
Top