Menu

A question about "string management"

2018-12-30
2019-01-02
1 2 > >> (Page 1 of 2)
  • Eugenio Di Lorenzo

    Hi, to all the GnuCOBOLl gurus a question.
    I have the following string C:\aaa\bbbbbbbb\cc\ddddddddd\e\fffffff
    I would like to get with a cobol statement the string
    C:\aaa\bbbbbbbb\cc\ddddddddd\e
    and then the string
    C:\aaa\bbbbbbbb\cc\ddddddddd
    and then the string
    C:\aaa\bbbbbbbb\cc
    and then the string
    C:\aaa\bbbbbbbb
    For the moment I solved by looping through the string one character at a time from right to left. putting a blank until I meet the '\' character. But the question is as follows.
    Is it possible to obtain this same result in a simpler way with an instruction or with a cobol function?
    (the unstring does not seem to me suitable).
    Ciao.

     
    • Simon Sobisch

      Simon Sobisch - 2018-12-30

      You should get a minimal better performance if you loop until you find the next "\" and then MOVE SPACES TO field(strpoint:) instead of moving a single space each time.

       
    • Mário Matos

      Mário Matos - 2018-12-31

      Just for fun,

             >>SET SOURCEFORMAT "FIXED"
             IDENTIFICATION DIVISION.
             PROGRAM-ID. "test".
            * A C function should be (much) better than this sh*t :-)
            * Well, this is a sample anyway (and it's fast) !!!
      
             ENVIRONMENT DIVISION.
             CONFIGURATION SECTION.
             SPECIAL-NAMES.
      
            *    CALL-CONVENTION 74 IS WINAPI.
      
             REPOSITORY.
                 FUNCTION ALL INTRINSIC
             .
      
             DATA DIVISION.
             WORKING-STORAGE SECTION.
      
             78  NL                   VALUE X"0A".   *> Helpfull on a single DISPLAY :-)
      
             78  MAX-PATH             VALUE 240.     *> This is the maximum length of a Windows file path
      
            *77  i                    BINARY-LONG.
             77  j                    BINARY-LONG.   *> Pointer used for INSPECT ... TALLYING
             77  k                    BINARY-LONG.   *> Intermediate value to set a new length to 'sPath'
      
             77  cSep                 PIC X.         *> Separator character
             77  nSep                 PIC 9.         *> # of separators found
      
             77  nTok                 BINARY-LONG.   *> Token to be found
      
            *    This string *MUST* be defined with variable size
            *    We are going to mess with it a *LOT* (using 'nLen)
             77  nLen                 BINARY-LONG.
             01  sPath.               *> Directory with MAX-PATH characters
                 03                   PIC X
                                      OCCURS 1 TO MAX-PATH
                                      DEPENDING nLen.
      
             PROCEDURE DIVISION.
             Begin-Program.
      
                 MOVE "\" TO cSep.    *> Default token separator
                 MOVE 7 TO nTok.      *> Target token # (from right to left)
      
                 MOVE MAX-PATH TO nLen.
                 MOVE "C:\aaa\bbbbbbbb\cc\ddddddddd\e\fffffff\\" TO sPath.
            *          <--------------------------------------- Tokens counted from right to left
                 MOVE STORED-CHAR-LENGTH(sPath) TO nLen.      *> Ignore trailinh spaces
      
                 INSPECT sPath TALLYING nSep FOR ALL cSep.    *> # of backslashes found
      
                 DISPLAY
                    "# of separators found: " nSep NL
                    "Original String: '" sPath "'"
                 END-DISPLAY.
      
                 MOVE REVERSE(sPath) TO sPath.          *> Reverse the string (we are going backwards!!!)
      
                 DISPLAY
                    "Reversed string: '" sPath "'" NL
                 END-DISPLAY.
      
            *    LOOPING THROUGH THE STRING USING TOKENS (words between separators)!!!
      
                 PERFORM VARYING nSep FROM 1 BY 1 UNTIL nSep = nTok
      
                    MOVE
                       0 TO j            *> Initialize tally pointer (this is a must before each INSPECT ... TALLYING)
            *       END-MOVE
                    INSPECT sPath        *> How much back backslashes do we have NOW ?
                       TALLYING j FOR CHARACTERS
                       BEFORE INITIAL cSep
            *       END-INSPECT
                    MOVE
                       REVERSE(sPath) TO sPath    *> Reverse the string again for readability
            *       END-MOVE
                    COMPUTE
                       k = nLen - (j + 1)         *> The string length should be smaller (or not)
                    END-COMPUTE
                    IF k > 0                      *> If all goes well ...
                    THEN
                       MOVE k TO nLen             *> ... the string size have been changed accordingly
                       DISPLAY
                          "Tally# " nSep ": " j NL
                          "String: '" sPath "'"   *> We use quotes to be sure
                       END-DISPLAY
                    END-IF
                    MOVE
                       REVERSE(sPath) TO sPath    *> Back to straight format
            *       END-MOVE
      
                 END-PERFORM.
      
             End-Program.
                 GOBACK.
      
             END PROGRAM "test".
      

      I'll not take any responsibility for any virus this code may have :-)

      Cheers,
      MM

      Mod edit to align fixed form highlighter

       

      Last edit: Brian Tiffin 2018-12-31
      • Mário Matos

        Mário Matos - 2018-12-31

        Forgot the result:

        ####### of separators found: 8
        Original String: 'C:\aaa\bbbbbbbb\cc\ddddddddd\e\fffffff\\\'
        Reversed string: '\\\fffffff\e\ddddddddd\cc\bbbbbbbb\aaa\:C'
        
        Tally# 1: +0000000000
        String: 'C:\aaa\bbbbbbbb\cc\ddddddddd\e\fffffff\'
        Tally# 2: +0000000000
        String: 'C:\aaa\bbbbbbbb\cc\ddddddddd\e\fffffff'
        Tally# 3: +0000000007
        String: 'C:\aaa\bbbbbbbb\cc\ddddddddd\e'
        Tally# 4: +0000000001
        String: 'C:\aaa\bbbbbbbb\cc\ddddddddd'
        Tally# 5: +0000000009
        String: 'C:\aaa\bbbbbbbb\cc'
        Tally# 6: +0000000002
        String: 'C:\aaa\bbbbbbbb'
        

        This editor makes me a crazy person
        :-)

        Mod edit for style, and the going crazy part, it is crazy making

         

        Last edit: Brian Tiffin 2018-12-31
  • Gregory A Failing

    This looks suspiciously like it could use a 'dirname' type intrinsic but alas none exists that I know of.

    This conversation from a few years ago may be of interest ...

    https://sourceforge.net/p/open-cobol/discussion/cobol/thread/476051e1/?limit=25#bcc7

    I have rolled my own 'dirname' and 'basename' functions which work fine but are really no more efficient than what you mention - looping from the end of the string back to the first seperator or position 1.

    But even though that sounds inefficient consider this: iterative work is what computers do well and they do it very quickly. Unless you have a job that processes millions of strings, saving a few pico-seconds here and there is not worth spending 3 days writing the most efficient function known to man.

    It took me decades to come to that realization but maybe I'm just hard-headed.

    Good Luck in any case ...

    G

     
    • Brian Tiffin

      Brian Tiffin - 2018-12-31

      Drift:

      This is just for future reference on a dirname, basename. And it really is cheating, I guess. But if counting cycles is not the priority (seriously, initiating this FLI is not cheap)

      First the one liner

      display function python("import os; spec = 'C:\\path\\dir\\file.ext'; print(spec); COBOL = spec.split('\\')").
      

      With the warnings about assumed divisions during compile dropped to the nul device...

      prompt$ cobc -xj -free -frelax-syn pathsplitone.cob 2>/dev/null
      C:\path\dir\file.ext
      ['C:', 'path', 'dir', 'file.ext']
      

      Now a slightly more readable cut, but I'll admit to flailing a little. Python running on POSIX doesn't easily create Windows friendly demonstrations. You can't force a Windows style filename on a POSIX system, even if it just for display, at least not that I've found yet.

            *>-<*
            *> Author: Brian Tiffin
            *> Dedicated to the public domain
            *>
            *> Date started: December 2018
            *> Modified: 2018-12-30/23:07-0500 btiffin
            *>+<*
            *>
            *> pathsplit, leverage Python to split a pathname into parts
            *> Tectonics:
            *>   cobc -xj pathsplit.cob
            *>
             >>SOURCE FORMAT IS FREE
             identification division.
             program-id. pathsplit.
      
             REPLACE ==newline== BY ==& x'0a' &==.
      
             environment division.
             configuration section.
             repository.
                 function all intrinsic.
      
             data division.
             working-storage section.
             01 indexes pic 9.
             01 indexer pic 9.
      
            *> Hard to show the Windows conversions when running on POSIX
             01 pathname.
                05 value "c:/dirname/nested/filename.txt".
      
             procedure division.
             pathsplit-main.
      
            *> turn on exception reports
             move python(4) to tally
      
             display "Starting with """ pathname """"
             display space
      
            *> split a path, normalized for Windows, into a python list
             display python("import os, sys" newline
                 "spec = sys.argv[1]" newline
                 "windrive = os.path.splitdrive(spec)" newline
                 "norm = os.path.normpath(windrive[0] + windrive[1])" newline
                 "parts = norm.split(os.sep)" newline
                 "COBOL = parts",
                 pathname)
      
             display space
             display "Each part:"
             display python("COBOL = parts[0]")
             display python("COBOL = parts[1]")
             display python("COBOL = parts[2]")
             display python("COBOL = parts[3]")
      
             display space
             display "Each part from a loop:"
             move python("COBOL = len(parts)") to indexes
             perform varying indexer from 0 by 1 until indexer > indexes - 1
                 display python("COBOL = parts[int(sys.argv[1])]", indexer)
             end-perform
      
            *> Unsure how to best demo a Windows filename on POSIX Python
             display space
             display " ... more cross platform learning to do ..."
             display "Drive spec (will be empty on POSIX system)"
             display python("COBOL = os.path.splitdrive('c:\\top\\file')[0]")
      
            *> Can't fudge it, it seems (this is Python 3, 3.4+)
             display "Explicit build of Windows path, may abend on POSIX"
             display python("import pathlib" newline
                 "pathlib.WindowsPath('C:\\WINDOWS\\FILENAME.TXT')")
      
            *> There is a way, somewhere in Python stdlib space, I'm sure
             goback.
             end program pathsplit.
      

      Giving:

      prompt$ cobc -xj pathsplit.cob
      Starting with "c:/dirname/nested/filename.txt"
      
      ['c:', 'dirname', 'nested', 'filename.txt']
      
      Each part:
      c:
      dirname
      nested
      filename.txt
      
      Each part from a loop:
      c:
      dirname
      nested
      filename.txt
      
       ... more cross platform learning to do ...
      Drive spec (will be empty on POSIX system)
      
      Explicit build of Windows path, may abend on POSIX
      Traceback (most recent call last):
        File "<string>", line 2, in <module>
        File "/usr/lib64/python3.6/pathlib.py", line 1002, in __new__
          % (cls.__name__,))
      NotImplementedError: cannot instantiate 'WindowsPath' on your system
      

      The C: is taken as part of the root in the POSIX case, but I was trying to mix something that doesn't want to mix given the OS the demo ran on.

      Excuse the drift

      Have good,
      Blue

       

      Last edit: Brian Tiffin 2018-12-31
      • Rod Gobby

        Rod Gobby - 2018-12-31

        Brian

        I understand the novelty of being able to solve the problem by invoking other languages, but wouldn't it be just as easy to write a simple function in GC? I've found that mixing languages within an application is not without its risks. And future maintenance can be a problem if the alien language changes or becomes obsolete.

        Even without the benefit of dynamic strings, GnuCOBOL has more than enough string functionality to perform this simple task. The user function can be made as simple or complex as the application needs. And like all good COBOL code, it can be used in all future applications.

        Rod

         

        Last edit: Rod Gobby 2018-12-31
        • Brian Tiffin

          Brian Tiffin - 2018-12-31

          True. That post was a drift.

          And I was serious about the performance hit. If you profile or trace Python startup, it hits the filesystem something like 1,300 times as it searches for base imports; a very expensive routine that could be written to compile down to a few dozen machine instructions.

          And yep, there should be more shareable COBOL library functions. And there are probably thousands of in-house closed COBOL solutions for breaking a pathname into components. Free software COBOL craves developments for public consumption.

          I'd wager that COBOL as a good 40 years behind in sharing core algorithm code, relative to other standard and user written library archives. The vast majority of COBOL is closed, not discussed, and used in one shop at a time, debugged over decades. Repeated from scratch for each of thousands of shops.

          So, we start in and try to add a couple of handy modules each; 10 years later it might look like a thing. Maybe,

          Cheers,
          Blue

           
  • Rod Gobby

    Rod Gobby - 2018-12-30

    Greg

    I agree.

    Eons ago, when I worked with 1960's mainframes, I quickly came to realize that, except for very rare situations, there is nothing to be gained in counting cpu cycles spent in user code. Even back then, we figured that at least 80-90% of the time was spent plodding around in the OS. Who knows what it is today, especially when OS code tends to be written in a high level language rather than Assembler.

    Back in the mid 80s I patched the MS-DOS COBOL-80 runtime, with lots of assembler code, to enhance the SCREEN SECTION features and to replace the built-in ISAM with my own isam software. Speedwise, it made no difference.

    These days, I replicate missing features using the same language that I'm using for the application. So now I'm using COBJAPI (lots of graphics overhead, no doubt) instead of a screen section, and my in-house isam is written in GnuCOBOL. And by adding about 10 lines of code to a module I can turn it into a class.

    And guess what? I doesn't make any difference. My programs still work, my customers are still happy, and the sun still rises in the morning (except in Ontario, where we haven't seen the sun in months).

    Rod

     

    Last edit: Rod Gobby 2018-12-30
  • Eugenio Di Lorenzo

    Thanks a lot to all of you but ... the question was different , as follows.
    "Is it possible to obtain same result in a simpler way with only a cobol verb or with a cobol function? "
    No matter of code performance ... just to have a simpler cobol source (if possible).

    As I said "for the moment I solved by looping through the string one character at a time from right to left, putting a blank until I meet the '\' character ".
    This is the code (from GC54FILEPICKER.COB in contribution\trunk\tools\TUI-TOOLS folder):

    ....
    01 wDIR-Ind pic 9999 value zero.
    01 wDIR.
       03 wDir-Ele occurs 256 pic X.
    ....
    
    perform DirectoryUp thru DirectoryUpEx
    ....
    
    DirectoryUp.
       move 256 to wDir-Ind
       continue.
    DirectoryUpLoop.
       if wDir-Ele(wDir-Ind) = '\'
          move space to wDir-Ele(wDir-Ind)
          go to DirectoryUpEx
       else
          move space to wDir-Ele(wDir-Ind)
          compute wDir-Ind = wDir-Ind - 1
          go to DirectoryUpLoop
       end-if
       continue.
    DirectoryUpEx. exit.
    

    quite simple to write and to understand from anyone.

    My goal is to have something like

    inspect wDir 
            replacing trailing "any character" by space 
            before initial '\' 
    

    or at least something like

    function reverse (wDir) 
    inspect wDir 
            converting  'abcdefghijklmnopqrstuvwxyz\'  to space 
            before initial '\'
    function reverse (wDir) 
    

    If (as I understand) the verb INSPECT is not already suitable for that,
    may be we can develop a GnuCOBOL extension ?
    or (better) may be an extension to be proposed to a new COBOL standard ?

     
  • László Erdős

    László Erdős - 2018-12-31

    Hi Eugenio,

    I understand you, but you can put your code in your own cobol function, then you have it.

    László

     
    • Eugenio Di Lorenzo

      Sure Laszlo, I know.
      however, it would be an unnecessary function if there is a solution with the cobol verbs.
      this was my question.
      I got the idea from the various posts that were sent (thx to all of you) and after some tests I found a solution that seems to me simple and clean.
      I will show you here the source code cobol for those interested.

             >>SOURCE FORMAT IS FREE
      IDENTIFICATION  DIVISION.
      program-id.     INSPECT1 is initial.
      ENVIRONMENT     DIVISION.
      CONFIGURATION   SECTION.
      REPOSITORY.     FUNCTION ALL INTRINSIC.
      DATA DIVISION.
      WORKING-STORAGE SECTION.
      01  wDIR  pic x(60) value 'C:\aaa\bbbbbbbb\cc\ddddddddddddddd\e\fffffff\g\hhhhh'.
      01  wInd  pic 999   value zero.
      
      PROCEDURE       DIVISION.
          display wDIR at 0101 accept omitted
          perform varying wInd from 3 by 1 until wInd > 10
      
                  *> following 4 lines are the solution ***********************
                  move function reverse(wDIR) to wDIR
                  inspect wDIR replacing characters by space before initial '\'
                  inspect wDIR replacing first '\'  by space  
                  move function reverse(wDIR) to wDIR
                  *> ***********************************************************
      
                  display wDIR at line wInd col 01 accept omitted
          end-perform
          goback.  
      

      In the screenshot are the results.
      Ciao.

       
      👍
      1
      • Mickey White

        Mickey White - 2019-01-01

        Nice, and short !

         
      • Mário Matos

        Mário Matos - 2019-01-02

        See? Even stupid code can help to get new ideias :-)

        Cheers,
        MM

         
  • Eugenio Di Lorenzo

    Same results with:

    PROCEDURE       DIVISION.
    display wDIR at 0101 accept omitted            
    move reverse(wDIR) to wDIR
    
    perform varying wInd from 3 by 1 until wInd > 10
            inspect wDIR replacing characters by space before initial '\'
            inspect wDIR replacing first '\'  by space  
    
            display reverse(wDIR) at line wInd col 01 accept omitted
    end-perform
    goback.  
    

    I do not know why but strangely this does not work but it should
    (the compiler reports syntax error, may be is it a bug ?)

    inspect reverse(wDIR) replacing characters by space before initial '\'
    
     
    • Mário Matos

      Mário Matos - 2019-01-02

      How come?

      I've already used an older version of GC from Arnold Trembley and it runs as expected!

      MM@PIMM64A: set_env

      Setting environment for GnuCOBOL 2.0 RC-2 with MinGW binaries
      (GCC 5.3.0, PDcurses 3.4, GMP 6.1.1, VBISAM 2.0)

      cobc (GnuCOBOL) 2.0.0
      Copyright (C) 2016 Free Software Foundation, Inc.
      License GPLv3+: GNU GPL version 3 or later http://gnu.org/licenses/gpl.html
      This is free software; see the source for copying conditions. There is NO
      warranty; not even for MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.
      Written by Keisuke Nishida, Roger While, Ron Norman, Simon Sobisch, Edward Hart
      Built Dec 05 2016 02:28:01
      Packaged Nov 06 2016 22:36:19 UTC
      C version "5.3.0"

      [D:\DEV\GC20RC2]
      MM@PIMM64A: cobc -x t.cbl

      [D:\DEV\GC20RC2]
      MM@PIMM64A: t
      C:\aaa\bbbbbbbb\cc\ddddddddddddddd\e\fffffff\g\hhhhh
      C:\aaa\bbbbbbbb\cc\ddddddddddddddd\e\fffffff\g
      C:\aaa\bbbbbbbb\cc\ddddddddddddddd\e\fffffff
      C:\aaa\bbbbbbbb\cc\ddddddddddddddd\e
      C:\aaa\bbbbbbbb\cc\ddddddddddddddd
      C:\aaa\bbbbbbbb\cc
      C:\aaa\bbbbbbbb
      C:\aaa
      C:

      NOTE: I created a brand new source name to "t.cbl" (with copy/paste) and removed your "pdcurses" line/column from the "DISPLAY" statements.

      It seems to be ok to me :-)

      MM

       
    • Brian Tiffin

      Brian Tiffin - 2019-01-02

      Edit: Original post - which will be in email, elided as not on the right track

      Yes it should work, and I'm pretty sure the root solution is adding a parser option to some verbs with source fields in the syntax, and let the compiler allow source field or function.

      At least that is first guess at how complex adding function sources to the verbs that don't currently compile with intrinsics would be.

      Or, it could be a delicate beast of a change to the parse tree, with delicate and exponentional effect on the generated parser.c and I'll admit trepidation in the not knowing.

      This is really nice code by the way, Eugenio.

      Umm, hrmm,

      There is a REPLACING action, here. Intrinsic function results are not in-place modifiable as far as I understand, they are not receiving fields.

      My orginal post was a recollection of long past days; the syntax for that inspect will allow for function result as source data, but the compiler is not allowing a write back to the transient result data space.

      I think.

      Have good,
      Blue

       

      Last edit: Brian Tiffin 2019-01-02
      • Mário Matos

        Mário Matos - 2019-01-02

        Well, resuming, "He has made a big shi(f)t" meanwhile!!! Chronologicaly, the older screenshot from 3 hours ago is the very same I got "now". The problem came after the "screenshot". So, ...
        TEST, TEST AND TEST!!! And then, test again!!! As if I was going to do that, meh :-)

         
        • Mário Matos

          Mário Matos - 2019-01-02

          The next try will be the string size!!!

          As aI was expecting:

          MM@PIMM64A: t
          "C:\aaa\bbbbbbbb\cc\ddddddddddddddd\e\fffffff\g\hhhhh "
          "C:\aaa\bbbbbbbb\cc\ddddddddddddddd\e\fffffff\g " ''C:\aaa\bbbbbbbb\cc\ddddddddddddddd\e\fffffff "
          "C:\aaa\bbbbbbbb\cc\ddddddddddddddd\e "
          "C:\aaa\bbbbbbbb\cc\ddddddddddddddd "
          "C:\aaa\bbbbbbbb\cc "
          "C:\aaa\bbbbbbbb "
          "C:\aaa "
          "C: "

          NOTE: One must edit to see the trailing SPACES. Even this damn editor has the hability to make assumptions with strings between quotes :-)

          There's no problem though (we have the TRIM function) :-)

           

          Last edit: Mário Matos 2019-01-02
          • Mickey White

            Mickey White - 2019-01-02

            Allow for larger directory path name...

            >>SOURCE FORMAT IS FREE
            IDENTIFICATION DIVISION.
            program-id. dsplyslash2 is initial.
            ENVIRONMENT DIVISION.
            CONFIGURATION SECTION.
            REPOSITORY. FUNCTION ALL INTRINSIC.
            DATA DIVISION.
            WORKING-STORAGE SECTION.
            01 wDIR pic x(255) value 'C:\aaa\bbbbbbbb\cc\ddddddddddddddd\e\fffffff\g\hhhhh\iiii\jjj\kkkkk\ll\mm\nnnn\oo'.
            01 wCnt comp-5 pic 9(04).
            01 wInd pic 999 value zero.
            PROCEDURE DIVISION.
            display wDIR
            inspect wDIR TALLYING wCnt for all "\"
            compute wCnt = wCnt + 2
            perform varying wInd from 3 by 1 until wInd > wCnt
            
                    *> following 4 lines are the solution ***********************
                    move function reverse(wDIR) to wDIR
                    inspect wDIR replacing characters by space before initial '\'
                    inspect wDIR replacing first '\'  by space
                    move function reverse(wDIR) to wDIR
                    *> ***********************************************************
            
                    display wDIR
            end-perform
            goback.
            
             

            Last edit: Mickey White 2019-01-02
            • Anonymous

              Anonymous - 2019-01-02

              This is Windows OS (with MinGW), remember? Use path sizes with caution, mainly with versions below "Windows 10, version 1607" (with this version, apparently, the hardcoded MAX_PATH, which was 260, has been removed in this Windows version (this is good news). But we must repect legacy, mustn't we? So, "the directory name cannot exceed MAX_PATH minus 12" which is 248 :-)

              The only exception to this is using mandatory UTF-16 paths with their very long paths which: "permit an extended-length path for a maximum total path length of 32,767 characters" And we can use them with a string PIC N(65,534) : H'FFFE' and the proper WIDE system calls using WINAPI in GnuCOBOL :-).

              Naming Files, Paths, and Namespaces
              https://docs.microsoft.com/en-us/windows/desktop/fileio/naming-a-file#maximum-path-length-limitation

              Cheers,
              MM

               
      • Mário Matos

        Mário Matos - 2019-01-02

        Of course, and I didn't even see that silly thing (only after the Simon's comment on this).
        One can use the TALLYING clause, but not with REPLACING.
        GnuCOBOL must be pissed off :-)

         
    • Simon Sobisch

      Simon Sobisch - 2019-01-02

      I think you meant that

      inspect reverse(wDIR) replacing characters by space before initial '\'
      

      should work, correct? As Brian already said all functions create a value so they can only be source fields, not a target.

      The message current GnuCOBOL gives is:

      error: invalid target for CONVERTING

      Which is a nice and clean error message, isn't it?

      @Eugenio: please drop a note if I've understood correctly what you meant.

       
      • Eugenio Di Lorenzo

        Hi Simon, you got it right ... and it would have been really nice to be able to do it.
        I was intrigued by the syntax of the INSPECT verb that allows the use of a "function".

        INSPECT Syntax
         
        INSPECT {literal-1}
                               {identifier-1}
                               {function-reference-1}
        

        however in the manual a little further on it is also specified that

        *If =f unction-reference-1 = is specified, it must be an invocation of an intrinsic function that returns a string result. Additionally, only the "TALLYING" clause may be specified.

         
  • Mário Matos

    Mário Matos - 2019-01-02

    Typo from previous "Anonymous" mail:
    Replace "PIC N(65,534)" with "PIC X(65,534)"

    Cheers,
    MM

     
1 2 > >> (Page 1 of 2)

Anonymous
Anonymous

Add attachments
Cancel