[comp.os.vms] network identifiers

OZZIE@WISCPSL.BITNET (Jim Osborne) (07/18/88)

> > Can somebody tell me if it's possible to put an ACE on a file specifying
> > the node in the identifier field. I.e. can I do the equivalent of:
> >
> >  ACE = (IDENTIFIER=(MYNODE::[100,20]),options=protected,access=read)
> >
> > See what I'm trying to do? Basically, I want to be able to distinguish
> > between a [100,20], say, on one machine, and another [100,20] on a
> > different machine.
>
> If you're talking about DECnet access, you could
> ...
>     2)  Create your own DECnet object for remote  file  access,  have  it  get
>         information  about  the remote node and the remote process, figure out
>         what rightslist identifier it should be using, grant itself  that  ID,
>         then try to access the file.

It's not necessary to create your own object for remote file access. You
can 'NCP SET OBJECT FAL FILE FAL.COM' and then edit SYS$SYSTEM:FAL.COM to
scan a database and grant appropriate identifiers to the server process
before running FAL.EXE. I'd actually recommend that FAL.COM run a program
to do the work.

The program which grants identifiers will probably need to be installed
with CMKRNL and SYSPRV to allow it to access RIGHTSLIST.DAT and to use
the $GRANTID system service for users whose server processes are non-
privileged (like most users).

If the program examines the EXECUTIVE mode translations of SYS$REM_NODE
and SYS$REM_ID to determine the remote source, only users with CMEXEC
privilege will be able to fool it (and they're already priv'd anyway).

Find attached BUILDREMRIGHTS.COM, REMRIGHTS.COM, REMRIGHTSMSG.MSG, and
FAL.COM. They're a hastily written and inadequately tested sample program
which grants identifiers according to a simple (sequential) "database", a
procedure to build and install it, and a modified FAL.COM which runs it.
Maybe you'll find some use for it.

I MAKE NO GUARANTEES REGARDING WHETHER OR NOT THIS PROGRAM WORKS. I OFFER
IT AS INPUT FOR THOSE WHO MIGHT CONSIDER USING SOMETHING LIKE IT. I CAN
TAKE NO RESPONSIBILITY FOR ANY DAMAGE IT MAY DO, OR ANY HOLES IN SECURITY
IT MIGHT CREATE. PLEASE EXAMINE THIS VERY CAREFULLY BEFORE TRYING IT.

Don't let that previous paragraph frighten you. I just can't take any
legal responsibility for anything REMRIGHTS does. It's not really very
complicated.

---------- BUILDREMRIGHTS.COM ----------
$ if P1.nes."" then goto 'P1'
$ BUILD:
$       FORTRAN REMRIGHTS
$       MESSAGE REMRIGHTSMSG
$       LINK/NOTRACE/EXE=SYS$COMMON:[SYSMGR] REMRIGHTS,REMRIGHTSMSG
$       SET PROT=W:RE SYS$COMMON:[SYSMGR]REMRIGHTS.EXE
$       IF F$SEARCH("SYS$MANAGER:REMRIGHTS.DAT").EQS."" THEN -
        WRITE SYS$OUTPUT "Remember to create SYS$MANAGER:REMRIGHTS.DAT!"
$       EXIT
$ INSTALL:
$       INSTALL="$SYS$SYSTEM:INSTALL/COMMAND_MODE"
$       C="CREATE"
$       IF F$FILE("SYS$MANAGER:REMRIGHTS.EXE","KNOWN") THEN C="REPLACE"
$       INSTALL 'C' SYS$MANAGER:REMRIGHTS/PRIV=(CMKRNL,SYSPRV)
$       EXIT
---------- REMRIGHTS.FOR (TABs converted to spaces, sorry) ----------
! Grant identifiers to a remote user's network server process. This
! program examines the EXECUTIVE mode translations of SYS$REM_NODE and
! SYS$REM_ID in LNM$JOB and then finds the matching entry(s) for that
! node::user combination in the text file, SYS$MANAGER:REMRIGHTS.DAT.
!
! The format of SYS$MANAGER:REMRIGHTS.DAT is as follows:
!
! node::user ident1[,ident2[,...]]   [! Comment]
!
! node::user may contain wildcards
! node::user must be separated from identifier(s) by one or more
!     spaces or TABs
! identifiers must be separated by ONLY A COMMA, no spaces or TABs
! identifiers may be modified with /RESOURCE and/or /DYNAMIC to set
! the corresponding attributes.
!
! For example:
!
! *::*        REMOTE_NET_ACCESS
! MYNODE::*   LOCAL_NET_ACCESS
! FUZZ::JOE   OPERATOR/RESOURCE/DYNAMIC,DECNET_MANAGER
!
! This program doesn't check that it is run by a NETWORK process, since
! normal users can't define EXECUTIVE mode logical names.
!
! This program must be installed with CMKRNL for $GRANTID to work, and
! with SYSPRV to give it access to the system RIGHTSLIST.
!
!               NOTE
!
! I didn't actually implement /RESOURCE and /DYNAMIC because I got
! really weary of FORTRAN's string-handling.
!
! 17-JUL-1988 OZ@WISCPSL
!       Yet Another Useless Utility is born

        program REMRIGHTS
        implicit none
        include '($LNMDEF)'
        include '($PSLDEF)'
        include '($STSDEF)'
        include '($SYSSRVNAM)'
        structure /ITMLST3/
            union
                map
                    integer*2 BUFLEN,ITMCOD
                endmap
                map
                    integer*4 EOL
                endmap
            endunion
            integer*4 BUFADR,RETLEN
        endstructure !ITMLST3!
        record /ITMLST3/ LNMITM(2)
        character REMNODE*8,REMUSER*16,REMID*24,LINE*80
        integer*2 REMNODEL,REMUSERL,REMIDL,LINEL,I,J,K,L
        integer RC,LENGTH,STR$FIND_FIRST_IN_SET,STR$MATCH_WILD
        integer STR$FIND_FIRST_NOT_IN_SET,IOS,STS,STV
        external REMRIGHT_REMNODE,REMRIGHT_REMID,REMRIGHT_OPENIN
        external REMRIGHT_BADENTRY1,REMRIGHT_BADENTRY2
        external REMRIGHT_GRANTED,REMRIGHT_GRANTID
        integer WORSTSTS
        common /EXITSTATUS/ WORSTSTS
        external STS_SAVER

        WORSTSTS=1
        call LIB$ESTABLISH(STS_SAVER)

! Get EXECUTIVE mode translations of SYS$REM_xxx in LNM$JOB.

        LNMITM(1).ITMCOD=LNM$_STRING
        LNMITM(1).BUFLEN=len(REMNODE)
        LNMITM(1).BUFADR=%loc(REMNODE)
        LNMITM(1).RETLEN=%loc(REMNODEL)
        LNMITM(2).EOL=0
        RC=SYS$TRNLNM(,'LNM$JOB','SYS$REM_NODE',PSL$C_EXEC,LNMITM)
        if (.not.RC) call LIB$STOP(REMRIGHT_REMNODE,%val(0),%val(RC))
        LNMITM(1).BUFLEN=len(REMUSER)
        LNMITM(1).BUFADR=%loc(REMUSER)
        LNMITM(1).RETLEN=%loc(REMUSERL)
        RC=SYS$TRNLNM(,'LNM$JOB','SYS$REM_ID',PSL$C_EXEC,LNMITM)
        if (.not.RC) call LIB$STOP(REMRIGHT_REMID,%val(0),%val(RC))

! Concatenate them to get the remote node::user.

        REMNODEL=LENGTH(REMNODE(1:REMNODEL))
        REMUSERL=LENGTH(REMUSER(1:REMUSERL))
        REMID=REMNODE(1:REMNODEL)//REMUSER(1:REMUSERL)
        REMIDL=REMNODEL+REMUSERL

! Scan the REMRIGHTS database for entries that match this node::user.

        open (unit=1,file='REMRIGHTS',status='OLD',readonly,
        1       defaultfile='SYS$MANAGER:REMRIGHTS.DAT',iostat=IOS)
        if (IOS.ne.0) then
            call ERRSNS(,STS,STV,,)
            call LIB$STOP(REMRIGHT_OPENIN,%val(0),%val(STS),%val(STV))
        endif
        do while (.TRUE.)
            read (1,'(Q,A)',end=700) LINEL,LINE
            call STR$UPCASE(LINE(1:LINEL),LINE(1:LINEL))
            I=index(LINE(1:LINEL),'!')  ! Trim comments.
            if (I.ne.0) LINEL=I-1
            LINEL=LENGTH(LINE(1:LINEL))
            if (LINEL.eq.0) goto 100    ! If line is blank, discard.
            I=STR$FIND_FIRST_IN_SET(LINE(1:LINEL),' '//char(9))
            if (I.eq.0) then
                call LIB$SIGNAL(REMRIGHT_BADENTRY1,%val(1),LINE(1:LINEL))
                goto 100
            endif
            if (.not.STR$MATCH_WILD(REMID(1:REMIDL),LINE(1:I-1))) goto 100
            I=STR$FIND_FIRST_NOT_IN_SET(LINE(I:LINEL),' '//char(9))+I-1

! Loop to grant all specified identifiers.

            do while (I.le.LINEL)
                J=index(LINE(I:LINEL),',')+I-1-1! find next ','
                if (J.lt.I) J=LINEL             ! if none, use rest of line
                K=J                             ! remember end of ident
                L=index(LINE(I:J),'/')+I-1      ! look for '/'
                if (L.ge.I) J=L-1               ! if found, trim qualifiers
                if (J.lt.I) then
                    call LIB$SIGNAL(REMRIGHT_BADENTRY2,%val(2),
        1               LINE(1:LINEL),%val(I+1))
                    goto 100
                endif
                RC=SYS$GRANTID(,,,LINE(I:J),)
                if (RC) then
                    call LIB$SIGNAL(REMRIGHT_GRANTED,%val(1),LINE(I:J))
                else
                    call LIB$SIGNAL(REMRIGHT_GRANTID,
        1               %val(1),LINE(I:J),%val(RC))
                endif
                I=K+2
            enddo
100         continue
        enddo

700     continue
        call SYS$EXIT(%val(WORSTSTS.or.STS$M_INHIB_MSG))

        end









! Save worst status that's signalled through us.

        integer function STS_SAVER(SIG,MCH)
        implicit none
        include '($SSDEF)'
        include '($STSDEF)'
        integer SIG(*),MCH(*)
        integer SEV,WORSTSEV,WORSTSTS
        common /EXITSTATUS/ WORSTSTS

        SEV=ibits(SIG(2),STS$V_SEVERITY,STS$S_SEVERITY)
        WORSTSEV=ibits(WORSTSTS,STS$V_SEVERITY,STS$S_SEVERITY)
        if ((WORSTSEV.and.(.not.SEV)).or.(SEV.gt.WORSTSEV)) WORSTSTS=SIG(2)
        STS_SAVER=SS$_RESIGNAL
        return

        end









! Find the length of a string with blanks, TABs, and NULs trimmed.

        integer function LENGTH(STR)
        implicit none
        character*(*) STR

        do LENGTH=len(STR),1,-1
            if (index(' '//char(9)//char(0),
        1       STR(LENGTH:LENGTH)).eq.0) return
        enddo
        LENGTH=0
        return

        end
---------- REMRIGHTSMSG.MSG ----------
        .facility REMRIGHT,1/PREFIX=REMRIGHT_

REMNODE/FATAL "error translating SYS$REM_NODE"
REMID/FATAL "error translating SYS$REM_ID"
OPENIN/FATAL "error opening REMRIGHTS database for input"
BADENTRY1/IDENT=BADENTRY/WARNING "missing space or TAB!/\!AS\"/FAO=1
BADENTRY2/IDENT=BADENTRY/WARNING "missing identifier!/\!AS\!/!#* ^- about here"/
FAO=2
GRANTED/SUCCESS "granted identifier \!AS\"/FAO=1
GRANTID/ERROR "error granting identifier \!AS\"/FAO=1
---------- FAL.COM ----------
$ !  Copyright (c) 1987 Digital Equipment Corporation.  All rights reserved.
$ SET NOON
$ IF "''FAL$COMMAND'" .NES. "" THEN FAL$COMMAND
$ RUN SYS$MANAGER:REMRIGHTS             ! grant identifiers
$ RUN SYS$SYSTEM:FAL.EXE
---------- Ugh ----------