Operating System - OpenVMS
1752815 Members
6116 Online
108789 Solutions
New Discussion

Re: Defining PQL PGFLQUOTA for SYS$CREPRC in FORTRAN

 
Bahreini
Visitor

Defining PQL PGFLQUOTA for SYS$CREPRC in FORTRAN

Hi,

 

I’m trying to increase my PGFL quota in a detached process that is created on another node when calling SYS$CREPRC in this FORTRAN program:

C
      IMPLICIT NONE
C
      INCLUDE '($PRCDEF)'
      INCLUDE '($PQLDEF)'
      INTEGER STATUS,SYS$CREPRC,PID,IDETACH
C
        STRUCTURE /PQL_LIST/
          BYTE      CODE
          INTEGER   VALUE
        END STRUCTURE
C
        RECORD /PQL_LIST/ MYPQL(2)
C
C      EXTERNAL  PRC$M_DETACH
C
      MYPQL(1).CODE = PQL$_PGFLQUOTA
      MYPQL(1).VALUE = 1000000
      MYPQL(2).CODE = PQL$_LISTEND
      MYPQL(2).VALUE = 0
      IDETACH =  PRC$M_DETACH
C

C
      STATUS = SYS$CREPRC (PID,
     &                     'MYIMAGE',                 ! Image
     &                     ,                          ! SYS$INPUT
     &                     'DTC.DAT',                 ! SYS$OUTPUT
     &                     'DTC.DAT',                 ! SYS$ERROR
     &                     ,
     &                     MYPQL,                     !
     &                     'MYPRC',                   ! PRC name
     &                     %VAL(4),                   ! Priority
     &                     ,,                         !    
     &                     %VAL(IDETACH),             ! Detached
     &                     ,
     &                     'MYNODE')                  ! Node
C
      STOP
      END

 

Now my detached process is not created and I get STATUS= 356 or “%SYSTEM-F-IVQUOTAL, invalid quota list” error.

 

If I don’t increase PGFL quota the detached process fails,  generation error: “%SYSTEM-F-EXQUOTA, process quota exceeded “. I know the PGFL is the cause, since when I increased it using SYSGEN the problem was resolved, I don’t want to increase this quota at OS level.

 

 I’m running this on “OpenVMS V7.3-2”.

 

Am I defining my PQL_LIST incorrectly or misaligned, there are some C samples in the web but I couldn’t find any in FORTRAN ?

 

Any comment or help is greatly appreciated.

 

Many thanks,

-Hadi Bahreini



5 REPLIES 5
John Gillings
Honored Contributor

Re: Defining PQL PGFLQUOTA for SYS$CREPRC in FORTRAN

Hadi,

   The $CREPRC PQL structure is one of the worst in all of OpenVMS. Everyone gets it wrong. Indeed, the official course material trying to teach how to use system services got it wrong! (and as far as I know has never been corrected).

 

  The issue is it's an unaligned array of unaligned, odd length elements. Most compilers will silently align fields, making it difficult to define and validate the contents. In Fortran you'll need to specify that the structure is packed. Since you don't want to pack everything, use an options directive affecting just the definition of the structure:

  

  

C CDEC$ OPTIONS /ALIGN=(RECORDS=PACKED,STRUCTURES=PACKED) 
C 
C WARNING - $CREPEC PQL structure and array *MUST* be packed
         STRUCTURE /PQL_LIST/ 
             BYTE CODE 
             INTEGER VALUE 
         END 
         STRUCTURE RECORD /PQL_LIST/ MYPQL(2) 
CDEC$ END OPTIONS

 

 

 To check the PQL is correct, run your program under DEBUG and examine your structure as hex. DON'T just examine the variable, as DEBUG won't show padding, it will show the fields as you declared them, so it will look correct even if it's been aligned.

 

DBG> SET RADIX HEX

DBG> EXAMINE/LONG MYPQL:MYPQL+20

 

Alternative is to examine the fields directly using offsets:

 

DBG> EXAMINE/BYTE MYPQL

DBG> EXAMINE/LONG MYPQL+1

DBG> EXAMINE/BYTE MYPQL+5

DBG> EXAMINE/LONG MYPQL+5+1

DBG> EXAMINE/BYTE MYPQL+5*n

DBG> EXAMINE/LONG MYPQL+5*n+1

 

This will display the raw hex bytes of your structure. Walk through it and verify the alignment and value of each field.

 

You're actually quite lucky to see IVQUOTAL, as it's more common to get crazy incorrect quota values (the OpenVMS System Services course was attempting to set working set parameters but managed to set a CPU limit of some small random delta time)

 

(one has to wonder if the idiot who designed this interface ever tried to actually use it? Spelling checker that doesn't show suspect text in context, Paste using a dialog box!! and code insertion that randomly removes line feeds and isn't editable after posting! Three decades of UI design completely ignored)

A crucible of informative mistakes
Bahreini
Visitor

Re: Defining PQL PGFLQUOTA for SYS$CREPRC in FORTRAN

John,

 

I appreciate your quick response and honor your devotion to help others especially in VMS community. Like many others, I have benefitted from your comments and hints in this forum for years.

 

I took your advice on misalignment and passed all fields in an old fashion way using a BYTE array. I populated elements one by one and it did work. I will post the whole program at bottom again in the hope it may help someone else.

 

Your solution also works. I only got this compiler warning which make sense.

 

%F90-W-WARNING, The structure contains one or more misaligned fields.   [PQL_LI]

 

I also don’t like this new interface, I lost my previous account during migration and today when I tried to give points to your post It assigned 1 and didn’t give me any other option, sorry about that.

 

Many thanks again,

-Hadi

 

C

      IMPLICIT NONE

C

      INCLUDE '($PRCDEF)'

      INCLUDE '($PQLDEF)'

C

      INTEGER STATUS,SYS$CREPRC,PID,IDETACH

C

      BYTE        PQLARY(6),PGFLARY(4)

      INTEGER*4   PGFLVAL

      EQUIVALENCE (PGFLVAL,PGFLARY)

C

      IDETACH =  PRC$M_DETACH

C

      PGFLVAL = 1000000

C

      PQLARY(1) = PQL$_PGFLQUOTA

      PQLARY(2) = PGFLARY(1)

      PQLARY(3) = PGFLARY(2)

      PQLARY(4) = PGFLARY(3)

      PQLARY(5) = PGFLARY(4)

      PQLARY(6) = PQL$_LISTEND

C

      STATUS = SYS$CREPRC (PID,

     &                     'MYIMAGE',                 ! Image

     &                     ,                          ! SYS$INPUT

     &                     'DTC.DAT',                 ! SYS$OUTPUT

     &                     'DTC.DAT',                 ! SYS$ERROR

     &                     ,

     &                     PQLARY,                    !

     &                     'MYPRC',                   ! PRC name

     &                     %VAL(4),                   ! Priority

     &                     ,,                         !    

     &                     %VAL(IDETACH),             ! Detached

     &                     ,

     &                     'MYNODE')                  ! Node

C

      STOP

      END

Mike Kier
Valued Contributor

Re: Defining PQL PGFLQUOTA for SYS$CREPRC in FORTRAN

You can supress that warning with /WARN=NOALIGN

 

I've always thought it was somewhat of a bug for the compiler to issue a warning when you explicitly state NOALIGN either via a directive as John did or via the  /NOALIGN qualifier.

Practice Random Acts of VMS Marketing
John Gillings
Honored Contributor

Re: Defining PQL PGFLQUOTA for SYS$CREPRC in FORTRAN

Hadi (& Mike)

   Here's another way around the alignment warning. The attachment is a small MACRO32 routine to build a PQL list into a buffer supplied by the caller. It returns the address of the buffer, so you can use it in line with the call to $CREPRC. The routine has a variable argument list, so use as many or as few quota entries as you need.

Since Fortran doesn't "see" the misalignment, you don't need to use /WARN=NOALIGN.

 

Example usage:

 

       INCLUDE '($PQLDEF)'
       INTEGER MakePQL    ; function
       BYTE    MyPQL(128) ; "big enough" array
 ...
       STATUS = SYS$CREPRC (PID,
     &                     'MYIMAGE',                 ! Image
     &                     ,                          ! SYS$INPUT
     &                     'DTC.DAT',                 ! SYS$OUTPUT
     &                     'DTC.DAT',                 ! SYS$ERROR
     &                     ,
     &                     %VAL(MakePQL(MyPQL,
     &                        PQL$_PGFLQUOTA,1000000,
     &                        PQL$_ASTLM    ,    100,
     &                        PQL$_TQELM    ,   4096
     &                     )),
     &                     'MYPRC',                   ! PRC name
     &                     %VAL(4),                   ! Priority
     &                     ,,                         !
     &                     %VAL(IDETACH),             ! Detached
     &                     ,
     &                     'MYNODE')                  ! Node

 Easy to add or subtract or modify quota entries, and very obvious what it's doing.

 

I don't have a Fortran compiler, so I haven't been able to test the code from Fortran. In theory:

 

$ RENAME MAKEPQL_MAR.TXT MAKEPQL.MAR
$ MACRO MAKEPQL
$ LINK YourProgram+MAKEPQL

 

 

Let me know if you have any trouble making it work, or an explanation for what it's doing.

A crucible of informative mistakes
Richard J Maher
Trusted Contributor

Re: Defining PQL PGFLQUOTA for SYS$CREPRC in FORTRAN

Hi Hadi,

 

Or you could go halfway to John's Macro subroutine and just define the quotas in Macro and overlay them in Fortran (or a.n.other language). You could then choose to default or hard-code them in Macro or populate them in your 3GL before calling $creprc.

 

Something like: -

 

            .library        /sys$library:lib.mlb/

            $uaidef         GLOBAL
            $prcdef         GLOBAL
            $issdef         GLOBAL
            $pqldef

            creprc_flags==<prc$m_detach!prc$m_tcb>

            .psect          creprc_ws,nopic,ovr,rel,gbl,long,noshr,noexe,rd,wrt

evesrv_q:   .byte           pql$_astlm
            .blkw           1
            .word           0
            .byte           pql$_biolm
            .blkw           1
            .word           0
            .byte           pql$_bytlm
            .blkl           1
            .byte           pql$_cpulm
            .blkl           1
            .byte           pql$_diolm
            .blkw           1
            .word           0
            .byte           pql$_enqlm
            .blkw           1
            .word           0
            .byte           pql$_fillm
            .blkw           1
            .word           0
            .byte           pql$_jtquota
            .blkl           1
            .byte           pql$_pgflquota
            .blkl           1
            .byte           pql$_prclm
            .blkl           1
            .byte           pql$_tqelm
            .blkw           1
            .word           0
            .byte           pql$_wsdefault
            .blkl           1
            .byte           pql$_wsextent
            .blkl           1
            .byte           pql$_wsquota
            .blkl           1
            .byte           pql$_listend

            .end

*
01  creprc_ws                                               external.
    03  creprc_quota_def.
        05                          pic x.
        05  qd_astlm                pic 9(4)        comp.
        05                          pic xx.
        05                          pic x.
        05  qd_biolm                pic 9(4)        comp.
        05                          pic xx.
        05                          pic x.
        05  qd_bytlm                pic 9(9)        comp.
        05                          pic x.
        05  qd_cpulm                pic 9(9)        comp.
        05                          pic x.
        05  qd_diolm                pic 9(4)        comp.
        05                          pic xx.
        05                          pic x.
        05  qd_enqlm                pic 9(4)        comp.
        05                          pic xx.
        05                          pic x.
        05  qd_fillm                pic 9(4)        comp.
        05                          pic xx.
        05                          pic x.
        05  qd_jtquota              pic 9(9)        comp.
        05                          pic x.
        05  qd_pgflquota            pic 9(9)        comp.
        05                          pic x.
        05  qd_prclm                pic 9(9)        comp.
        05                          pic x.
        05  qd_tqelm                pic 9(4)        comp.
        05                          pic xx.
        05                          pic x.
        05  qd_wsdefault            pic 9(9)        comp.
        05                          pic x.
        05  qd_wsextent             pic 9(9)        comp.
        05                          pic x.
        05  qd_wsquota              pic 9(9)        comp.
        05                          pic x.
    03                              pic s9(9)       comp.
*
01  creprc_prib                     pic s9(4)       comp.
01  uai_prib                                                redefines       creprc_prib.
    03  base_priority               pic x.
*


    call "sys$creprc"
        using   by reference  out_pid
                by descriptor "sys$system:loginout.exe"
                by descriptor "sys$system:your_input.com"
                by descriptor user_log(1:user_log_log_len)
                by value      0
                by reference  def_priv, creprc_quota_def
                by descriptor prcnam
                by value      creprc_prib, 0, 0, creprc_flags
        giving  out_status.

 

 

BTW, Steve would not do this :-)