Re: C$LIST-DIRECTORY requires 'USAGE HANDLE'

[Date Prev][Date Next][Thread Prev][Thread Next][Date Index][Thread Index]

 



Brian Tiffin <bwtiffin@xxxxxxxxx> writes:

>>
>> But it seems I hit a little snag while looking in to the
>> C$LIST-DIRECTORY-request. The API for that function requires a variable
>> with USAGE HANDLE, but if I understand correctly GNU Cobol does not yet
>> have that. There is a wishlist item #77 about it.
>
> Equivalent of USAGE POINTER
>
> Or should be.  If there is more to the structure than that, still no
> problem, just build an 01 record with a couple of sub-fields.  (When
> mapping C struct to COBOL record, adding SYNCHRONIZED (or short as
> SYNCH) the compile will take care that COBOL has the same implicit
> padding between fields as what C would use).
>

I'm sorry, I don't follow. I think we might have misunderstood each
other. What I meant was that any code calling C$LIST-DIRECTORY will have
to do so using a parameter of type HANDLE. This is the example that is
presented on Microfocus' website
(http://supportline.microfocus.com/Documentation/AcucorpProducts/docs/v6_online_doc/gtman4/gt4i38.htm):

   
        WORKING-STORAGE SECTION.   
        copy "def/acucobol.def".   
        01  pattern       pic x(5) value "*.vbs".   
        01  directory     pic x(20) value "/virusscan".   
        01  filename      pic x(128).   
        01  mydir         usage handle.   
        PROCEDURE DIVISION.   
        MAIN.   
        * Call LISTDIR-OPEN to get a directory handle.   
            call "C$LIST-DIRECTORY"    
               using listdir-open, directory, pattern.   
            move return-code to mydir.   
            if mydir = 0   
               stop run   
            end-if.   
        * Call LISTDIR-NEXT to get the names of the files.     
        * Repeat this operation until a filename containing only    
        * spaces is returned.  The filenames are not necessarily    
        * returned in any particular order.  Filenames may be    
        * sorted on some machines and not on others.   
            perform with test after until filename = spaces   
               call "C$LIST-DIRECTORY"    
                  using listdir-next, mydir, filename   
            end-perform.   
        * Call LISTDIR-CLOSE to close the directory and deallocate   
        * memory. Omitting this call will result in memory leaks.   
            call "C$LIST-DIRECTORY" using listdir-close, mydir.   
            stop run.   

But this wont compile with GNU Cobol right? Because of the "usage
handle". 

> Equivalent of USAGE POINTER

Hm, it says in wishlist #77 that a HANDLE should be 4 bytes and aligned
on 4 byte boundaries, so I don't really see how it can be equivalent to a
pointer, at least not in a portable way.

Sorry for the terse mail, I'm trying to learn dvorak, so it took me like
40 minutes to write this :)

Joakim

------------------------------------------------------------------------------
Site24x7 APM Insight: Get Deep Visibility into Application Performance
APM + Mobile APM + RUM: Monitor 3 App instances at just $35/Month
Monitor end-to-end web transactions and take corrective actions now
Troubleshoot faster and improve end-user experience. Signup Now!
http://pubads.g.doubleclick.net/gampad/clk?id=272487151&iu=/4140
_______________________________________________
open-cobol-list mailing list
open-cobol-list@xxxxxxxxxxxxxxxxxxxxx
https://lists.sourceforge.net/lists/listinfo/open-cobol-list



[Index of Archives]     [Gcc Help]     [Linux USB Devel]     [Linux Audio Users]     [Yosemite Info]     [Linux Kernel]     [Linux SCSI]     [Big List of Linux Books]

  Powered by Linux