HP3000-L Archives

March 1998, Week 4

HP3000-L@RAVEN.UTC.EDU

Options: Use Monospaced Font
Show Text Part by Default
Show All Mail Headers

Message: [<< First] [< Prev] [Next >] [Last >>]
Topic: [<< First] [< Prev] [Next >] [Last >>]
Author: [<< First] [< Prev] [Next >] [Last >>]

Print Reply
Subject:
From:
Hans van de Spijker <[log in to unmask]>
Reply To:
Hans van de Spijker <[log in to unmask]>
Date:
Thu, 26 Mar 1998 10:06:15 +0100
Content-Type:
text/plain
Parts/Attachments:
text/plain (69 lines)
Michael Anderson wrote in message <[log in to unmask]>...
>I am converting many CM progs to NM, and ran into dead-end with
>FGETINFO. I have a subroutine that is called by many different
>applications, it calls FGETINFO to get the records size of the FNUM
>passed to it. When compiled in CM the FGETINFO call works perfect.
>However, when compiled in NM it always returns zero as the record size.
>Reading the Intrinsic Manual, I found that FGETINFO shouldn't  be used
>in NM progs, to use FFILEINFO instead. OK, so I changed the routine to
>
>CALL "FFILEINFO" USING FNUM \67\ RECSIZE.
>
>Using item 67, RECSIZE is now a 32 bit integer. However, it still
>returns zero as the record size. So I decided to use item 4, which would
>make RECSIZE a 16 bit integer like it used to be.
>
>CALL "FFILEINFO" USING FNUM \4\ RECSIZE.
>
>Still returns zero as the record size.
>
>Seems like a reasonable request, I just want the record size of a
>specific FNUM. Does anyone have any clue or pointers for me?  I'm out of
>idea's.
>
>Thanks in Advance,
>Michael Anderson

An example of calling FFGETINFO:

<< WORKING STORAGE >>
 01 BNR-FILE.
    03 BNRFILE-FNUM           PIC S9(4)  COMP.
    03 BNRFILE-RECSIZE        PIC S9(4)  COMP.
    03 BNRFILE-EOF            PIC S9(9)  COMP.


<< PROCEDURE DIVISION >>
     CALL INTRINSIC 'FOPEN' USING BNRFILE-NAME
                                  \1\ \0\
                           GIVING BNRFILE-FNUM
     IF CC <> ZERO
       CALL INTRINSIC 'PRINTFILEINFO' USING BNRFILE-FNUM
     ELSE
       CALL INTRINSIC 'FFILEINFO' USING BNRFILE-FNUM
                                        \4\
                                        BNRFILE-RECSIZE
                                        \10\
                                        BNRFILE-EOF
       IF CC <> ZERO
         DISPLAY 'error FFILEINFO' BNRFILE-NAME
         CALL INTRINSIC 'PRINTFILEINFO' USING BNRFILE-FNUM
         CALL INTRINSIC 'QUIT' USING \40\
       END-IF
     END-IF
     .

Kind regards,

Hans van de Spijker
[log in to unmask]


begin 666 Hans van de Spijker.vcf
M0D5'24XZ5D-!4D0-"DXZ4W!I:FME<CM(86YS.W9A;B!D90T*1DXZ2&%N<R!V
M86X@9&4@4W!I:FME<@T*14U!24P[24Y415).150Z:&%N<RYS<&EJ:V5R0"YN
M970N2$-#+FYL#0I%34%)3#M04D5&.TE.5$523D54.FAA;G- 8W-D+G1N;RYN
.; T*14Y$.E9#05)$#0H`
`
end

ATOM RSS1 RSS2