[Search for users] [Overall Top Noters] [List of all Conferences] [Download this site]

Conference noted::hackers_v1

Title:-={ H A C K E R S }=-
Notice:Write locked - see NOTED::HACKERS
Moderator:DIEHRD::MORRIS
Created:Thu Feb 20 1986
Last Modified:Mon Aug 03 1992
Last Successful Update:Fri Jun 06 1997
Number of topics:680
Total number of notes:5456

371.0. "Set process / name = personal" by BISTRO::HEIN (Hein van den Heuvel, Valbonne.) Fri Dec 12 1986 09:21

    I often log in more then once to the same system and I like
    to have a personalized process name. Now if you want the 
    same name for all processes you switch your UIC outside your
    group, set the name, switch UIC back and presto!
    But what if you want a unique name? Trial and ON ERROR?
    What do you think the _best_ (short? fast? clear? kludge?)
    way to produce a unique personalized name? I use the following
    sequence in LOGIN.COM without any privs set.
    
    
$all_names = "Ne Quittez Pas!ACMS (de)BUGGERNice View      Ogenblikje SVP!"
$!            123456789012345123456789012345123456789012345123456789012345 
$ctx = ""
$pid_loop:
$pid = f$pid(ctx)
$if pid .eqs. "" then goto set_proc_name
$all_names = all_names - f$getjpi(pid,"PRCNAM")
$goto pid_loop
$set_proc_name:
$set proc/name="''f$extract(0,15,all_names)'"
T.RTitleUserPersonal
Name
DateLines
371.1SQM::RICOFri Dec 12 1986 12:243
    I take a simpler view.  I don't have several catch sayings for
    process names, so I just use, for example, "xyz", " xyz", "  xyz",
    "   xyz", etc.  This is easy to construct in a command file.
371.2KOALA::ROBINSScott A. Robins, ZKO2-2/R94Fri Dec 12 1986 12:5133
    The following code segment sets my process name to "Scott A. Robins",
    if I am NOT in a sub-process.  If it fails, it sets it to "S.A.R.#n".
    
    Scott

    item_code    := JPI$_OWNER ;
    process_id   := LONGWORD 0 ;
    process_name := LONGWORD 0 ;
    out_string   := "" ; ! Just to be sure it's allocated.

    fn_ret := lib$getjpi( item_code    ,
                          process_id   ,
                          process_name ,
                          out_value    ,
                          out_string   ,
                          out_len     );
    if (fn_ret=(LONGWORD 1))
       then ! Ignore it if it fails, we'll find out soon enough.
            if (out_value=(LONGWORD 0)) 
               then ! We are NOT a sub-process
                    if NOT sys$setprn ("Scott A. Robins")
                       then
                            out_string := "S.A.R." ;
                            for i in 1..100
                            loop
                                exit if sys$setprn(out_string) ;
                                out_string := "S.A.R. #" & string i ;
                            end loop ;
                    end if ;
               else ! We ARE a sub-process.
                    ! Don't bother.
            end if ;
    end if ;
371.3All in a couple of linesBARNA::SOLEPONTJaume, �Barcelona 1992� more than everFri Dec 12 1986 14:042
		$ pid = %X'f$getjpi(0,"pid")
		$ set process/name="Jaume, ''pid'"
371.4From my LOGIN.COMFROST::HARRIMANNo longer a 41 class partFri Dec 12 1986 14:0748
    I have an approach to that which I have used for quite a long while.
    I use version numbers on any parent processes. The subprocesses
    get to use the same version number, since I keep symbols around
    to create subprocesses (SPAWN/NAME=whatever) like my editor, mail,
    notes, etc. 
    
    The code to set up the process name is thus:
    
$ myname = "Paul Harriman;"
$ Iteration = 1
$ printable_iteration = f$string(iteration)
$!
$Set_Process_Name:
$!
$ ON ERROR THEN GOTO ADD_ONE
$ Processname = myname + printable_iteration
$ SET PROC/NAME="''Processname'"
$ goto definitions
$!
$Add_One:
$ Iteration = Iteration + 1
$ Printable_Iteration = f$string(iteration)
$ Goto Set_Process_Name
$!
$!  	Done setting Process Name..
$!               
$Definitions:
    
    I'm sure some other structured programmer could improve on this
    or do it in less lines, I personally don't mind the extra couple
    of nanoseconds for it to do this.
    
    I then pass the iteration and my process name result to another
    command procedure which turns the full name (in my case "Paul
    Harriman;1") to "Harriman" and ";1". My TPU processname would then
    turn into "Harriman/TPU;1"; the MAIL subprocess "Harriman/Mail;1",
    and so on. Since I enjoy this sort of thing, I have mapped my keypad
    to attach to these subprocesses by assigning them to the value of
    the symbols I create on startup. This allows (in my case) about
    9 parent processes (which I don't usually get around to doing).
    
    I assume some other more motivated individual can improve this to
    make it all run faster, or make a real executable program to do
    it... however this is an entirely DCL-driven method and the only
    non-generic thing about it is the person's name being used.
    
    /pjh
    
371.5DCL random number generator...CAFEIN::PFAUYou can't get there from hereFri Dec 12 1986 14:2779
$ set noon
$ set mess/nofaci/noseve/notext/noiden
$ exe$gq_systime = %x80002b40
$ inter = f$mode() .eqs. "INTERACTIVE"
$ batch = f$mode() .eqs. "BATCH"
$ if .not. (inter .or. batch) then exit
$ if inter then file = "ut:interactive.dat"
$ if batch then file = "ut:batch.dat"
$ open/read/share/err=fallback foo 'file'
$ line1 = ""
$ if p1 .nes. "" then goto 'p1'
$!
$time:
$ count = 0
$timeloop:
$ tmp = f$fao("!AD",8,exe$gq_systime)
$ tmp = f$cvui(10,4,tmp)
$ number = tmp
$ tmp = f$fao("!1XL",f$integer(tmp))
$ read foo line/key="''tmp'"
$ line = line - "''tmp'"
$ name = line
$ set proc/name="''line'"
$ if $status then goto setdone
$ count = count + 1
$ if count .lt. 10 then goto timeloop
$!
$! Try using the low four bits of the pid as the index
$!
$pid:
$ tmp=f$getjpi(0,"pid")
$ tmp=%x'tmp'.and.15
$ number = tmp
$ tmp=f$fao("!1XL",f$integer(tmp))
$ read foo line1/key="''tmp'"
$ line1=line1-"''tmp'"
$ name = line1
$ set proc/name="''line1'"
$ if $status then goto setdone
$!
$! Try using the low four bits of the terminal unit number
$!
$unit:
$ if f$mode() .eqs. "BATCH" then goto fallback
$ tmp=f$integer(f$getdvi("sys$command","unit")).and.15
$ number = tmp
$ read foo line2/key="''tmp'"
$ line2=line2-"''tmp'"
$ if line2 .eqs. line1 then goto fallback
$ name = line2
$ set proc/name="''line2'"
$ if $status then goto setdone
$!
$! Build a string using the process mode and the pid
$!
$fallback:
$ mode = f$extract(0,5,f$mode())
$ mode = f$edit(mode,"lowercase")
$ mode[0,8] = f$cvui(0,8,mode) - 32
$ if mode .nes. "Inter" then goto get_pid
$ term=f$logical("sys$command")
$ if f$getdvi(term,"tt_modem") then mode = "Dial"
$ if f$extract(2,2,term) .eqs. "RT" then mode = "Remot"
$get_pid:
$ pid = "%X" + f$extract(4,4,f$getjpi("","pid"))
$ octalpid = f$fao("!OW",f$integer(pid))
$ octalpid = f$string(f$integer(octalpid))
$ lenpid = f$length(octalpid) * 3
$ hexpid = f$fao("!#XL",(lenpid+3)/4,%O'octalpid')
$ if f$extract(0,1,hexpid) .eqs. "0" then hexpid = hexpid - "0"
$ name = "Pfau_" + mode + "_" + hexpid
$ set process /name="''name'"
$setdone:
$ if f$type(number) .nes. "" then -
	write sys$output "Process name number ",number,", name is '",name,"'"
$ if f$type(number) .eqs. "" then -
	write sys$output "Process name set to '",name,"'"
$ close foo
$ set mess/text
371.6try it this way....KIM::BARKERMy terminal is the window to the world!Fri Dec 12 1986 16:5024
    I kind've like to stay cryptic, so I use the following:
$SET PROC/NAME=">"
$SET PROC/NAME="->"
$SET PROC/NAME="-->"
$SET PROC/NAME="--->"
$SET PROC/NAME="---->"
$SET PROC/NAME="----->"
$SET PROC/NAME="------>"
$SET PROC/NAME="------->"
$SET PROC/NAME="-------->"
$SET PROC/NAME="--------->"
$SET PROC/NAME="---------->"
$SET PROC/NAME="----------->"
$SET PROC/NAME="------------>"
$SET PROC/NAME="------------->"
$exit

    -------------------------------------------------------------------------------
    whenever I log on again, I automatically get the last name that
    is not in use, (all in use sets error)...
    
    :-{)
    John
        
371.7Group logicals survive logout.STAR::MANNSat Dec 13 1986 17:445
    I use a group logical name to keep track of how many times I've
    logged in since the system booted. 
    
    							Bruce Mann (34)
    
371.8Brute forceSTAR::KAPLANMon Dec 15 1986 20:5330
$!       
$!   I'm sure this can be done more elegantly, but it works. 
$!   It keeps trying to set your personal name by adding a count 
$!   to the value of PERSONAL_NAME
$!    
$ sho proc
$ USERNAME = "xxxxxxx"       ! your username
$ PERSONAL_NAME = "yyyyy"    ! what you'd like for a process name
$ !
$ SETNAME:
$	dup = 0
$	on control_y then goto END_SETNAME
$ 	set message/nofac/nosev/notext/noid
$	on error then goto OPS
$	if f$process().eqs. USERNAME then SET PROCESS /NAME="''PERSONAL_NAME'"
$	goto END_SETNAME
$ 	!
$    	OPS:
$	DUP = DUP + 1
$	on error  then goto OPS
$	SET PROCESS /NAME="''PERSONAL_NAME' ''dup'"
$	on severe then goto DONE
$	!
$	END_SETNAME:
$ 	set message/fac/sev/text/id	! turn messages back on 
$	set noon
$ 	on error then goto done
$ !
$ DONE:
$ sho proc
371.9Login.b32 extractIOSG::YUILLEAndrew YuilleTue Dec 16 1986 05:31281
    This was begining to get a bit COMMAND_PROCEDURESsih - so I thought
    I'd put in my LOGIN.B32. Its a lot faster. Should be obvious enough
    where it needs to be tailored. If the process (my) name is already defined
    for the node / UIC, I set up a string (Andry-xx-n), where xx tells
    me the type of job (BT for batch, etc), and n is a count to make
    it unique. 
    
    Two drawbacks:
    
    On a cluster, it doesn't see the process name set for the same UIC
    on another node. I have to live with that.
    
    The most time consuming factor is setting up my KeyPad. I haven't
    managed to find out how to set this from Bliss, for DCL yet. I would
    be very interested to hear any suggestions on this. SMG only sets
    up the keypad for the duration of the image, which dies when I go
    back to DCL, where I want it!
    
    Here's an extract from my login.b32 (called by login.com)
    ---------------------------------------------------------

MODULE login ( MAIN = login ) =

BEGIN

!++
! LOGIN.B32 - Set up global symbols for process
!--

LIBRARY	'SYS$LIBRARY:STARLET' ;
REQUIRE 'LOGIN' ;

EXTERNAL ROUTINE
    LIB$PUT_OUTPUT  : addressing_mode (general) , ! Output to screen
    SYS$SETPRN      : addressing_mode (general) , ! Set Process Name
    SCR$PUT_SCREEN  : addressing_mode (general) , ! Output to screen
    LIB$SET_LOGICAL : addressing_mode (general) , ! Set up logical name
    LIB$SYS_TRNLOG  : addressing_mode (general) , ! Translate logical name
    SYS$GETJPIW     : addressing_mode (general) , ! Get process name
    STR$CONCAT      : addressing_mode (general) , ! Concatenate strings
    STR$APPEND      : addressing_mode (general) , ! Append strings
    STR$COPY_DX     : addressing_mode (general) , ! Copy strings
    LIB$DAY_OF_WEEK : addressing_mode (general) , ! Get day of week
    LIB$SET_SYMBOL  : addressing_mode (general) ; ! Set global symbol

FIELD $getjpi_fields =
SET
	getjpi_buflen	= [ 0, 0, 16, 0],	! Length available
	getjpi_item	= [ 2, 0, 16, 0],	! Item required
	getjpi_buffaddr	= [ 4, 0, 32, 0],	! Buffer address
	getjpi_retlen	= [ 8, 0, 32, 0],	! Address for returned length
	getjpi_term	= [12, 0, 32, 0]	! List terminator
TES ;


ROUTINE login =
    BEGIN
    LITERAL
	full_length = 100 ,
	msg_len = 100 ,
	p_len = 16 ,
	network = 1 ,		! Process mode types
	batch = 2 ,		! BATCH
	interactive = 3 ,	! INTERACTIVE
	operator = 4 ,		! INTERACTIVE from operator console
	LIB$K_CLI_GLOBAL_SYM =  2 ;
    LOCAL
	ok ,
	Null : INITIAL (0) ,
	Mode ,
	char ,
	proc_retlen ,
	len ,
	proc_ptr ,
	proc_no ,
	$fixed_desc (term, 10) ,
	$fixed_desc (dev, 10) ,
	$fixed_desc (dir, 40) ,
	$dyn_desc   (msg, msg_len) ,
	$fixed_desc (msg2, msg_len) ,
	$fixed_desc (full_name, full_length) ,
	$ptr_desc   (top_dir, 0) ,
	$ptr_desc   (mode_nam, 10) ,
	$text_desc  (my_name, 'Andrew Yuille') ,
	pid : INITIAL (0) ,
	$fixed_desc (proc_mode, p_len) ,
	p_name_buf : BLOCK [16, BYTE] 
		    FIELD ($getjpi_fields)
		      PRESET
			  ( [getjpi_buflen]   = p_len,         ! Length available
			    [getjpi_item]     = JPI$_MODE,     ! Process mode request
			    [getjpi_buffaddr] = proc_modebuf,  ! Text buffer address 
			    [getjpi_retlen]   = proc_retlen,   ! Returned length
			    [getjpi_term]     = 0	       ! Terminator
			  ) ,
	mode_buf : VECTOR [10,BYTE] 
		INITIAL (BYTE  (%C'A', %C'n', %C'd', %C'r', %C'y', 
                        !          0      1      2      3      4
				%C'_', %C'I', %C'N', %C'_', %C'0') ) ,
                        !          5      6      7      8      9
	glob_sym : INITIAL (LIB$K_CLI_GLOBAL_SYM) ;

    ! Get process mode
    SYS$GETJPIW (0, pid, 0, p_name_buf, 0, 0, 0) ;
    Mode = .proc_modebuf ;
    mode_nam [DSC$A_POINTER] = mode_buf ;
    proc_ptr = mode_nam ;
    len = .mode_nam [DSC$W_LENGTH] ;
    proc_no = %C'1' ;

    SELECTONE .Mode OF
	SET
	[INTERACTIVE]:
	    BEGIN
	    ! Get terminal line number 
	    LIB$SYS_TRNLOG (%ASCID 'TT', term [DSC$W_LENGTH], term) ;
	    char = ch$ptr (.term [DSC$A_POINTER]) ;
	    IF ch$find_ch (2, .char, %C'O') NEQ 0 THEN 
		BEGIN
		Mode = Operator ;	! Set flag if at Operator Console
		mode_buf [6] = %C'O' ;
		mode_buf [7] = %C'P' ;
		END
	    ELSE
		BEGIN
		proc_ptr = my_name ;
		len = .my_name [DSC$W_LENGTH] ;
		proc_no = %C'0' ;
		msg [DSC$W_LENGTH] = msg_len ;
		STR$CONCAT (msg, %ASCID '    Line: ', term) ;
		msg [DSC$W_LENGTH] = .term [DSC$W_LENGTH] + 12 ;
		LIB$PUT_OUTPUT (msg) ;		! Output terminal line number
		END ;
	    END ;

	[BATCH]:
	    BEGIN
	    mode_buf [6] = %C'B' ;
	    mode_buf [7] = %C'T' ;
	    END
	TES ;

    mode_buf [9] = .proc_no ;
    msg [DSC$W_LENGTH] = msg_len ;
    STR$COPY_DX (msg, %ASCID '  Other processes: ') ;
    ok = SYS$SETPRN (.proc_ptr) ;
    WHILE .ok EQL SS$_DUPLNAM DO
	BEGIN
	IF .Mode EQL interactive THEN
	    BEGIN
	    IF .proc_no GTR %C'0' THEN STR$APPEND (msg, %ASCID ', ') ;
	    STR$APPEND (msg, .proc_ptr) ;
	    END ;
	proc_no = .proc_no + 1 ;
	mode_buf [9] = .proc_no ;
	proc_ptr = mode_nam ;
	len = .mode_nam [DSC$W_LENGTH] ;
	ok = SYS$SETPRN (.proc_ptr) ;
	IF .proc_no EQL %C'9' THEN EXITLOOP	! Don't handle more than 9...!
	END ;

    IF .Mode EQL interactive THEN
	BEGIN
	msg2 [DSC$W_LENGTH] = msg_len ;
	STR$CONCAT (msg2, %ASCID '  Process: ', .proc_ptr) ;
	msg2 [DSC$W_LENGTH] = .len + 11 ;
	LIB$PUT_OUTPUT (msg2) ;
	IF .proc_no GTR %C'0' THEN LIB$PUT_OUTPUT (msg) ;
	END ;

    ! Get login device and directory
    LIB$SYS_TRNLOG (%ASCID 'SYS$LOGIN_DEVICE', dev [DSC$W_LENGTH], dev) ;
    LIB$SYS_TRNLOG (%ASCID 'SYS$LOGIN', dir [DSC$W_LENGTH], dir) ;
    ! Generate string dev:dir, without last ']', for sub-directories
    top_dir [DSC$A_POINTER] = .dir [DSC$A_POINTER] ;
    top_dir [DSC$W_LENGTH] = .dir [DSC$W_LENGTH] - 1 ;

!+
! General definitions
!-

    ! Set up general logicals

    LIB$SET_LOGICAL (%ASCID 'MY', dir) ;
    LIB$SET_LOGICAL (%ASCID 'TOP', dir) ;
    LIB$SET_LOGICAL (%ASCID 'HERE', dir) ;

    ! Set up C -> sys$login.commands]
    full_name [DSC$W_LENGTH] = full_length ;
    STR$CONCAT (full_name, top_dir, %ASCID '.COMMANDS]') ;
    full_name [DSC$W_LENGTH] = .top_dir [DSC$W_LENGTH] + 10 ;
    LIB$SET_LOGICAL (%ASCID 'C', full_name) ;

    ! Set up lib -> .lib]
    full_name [DSC$W_LENGTH] = full_length ;
    STR$CONCAT (full_name, top_dir, %ASCID '.LIB]') ;
    full_name [DSC$W_LENGTH] = .top_dir [DSC$W_LENGTH] + 5 ;
    LIB$SET_LOGICAL (%ASCID 'LIB', full_name) ;

    ! Set up ml -> .mail]
    full_name [DSC$W_LENGTH] = full_length ;
    STR$CONCAT (full_name, top_dir, %ASCID '.MAIL]') ;
    full_name [DSC$W_LENGTH] = .top_dir [DSC$W_LENGTH] + 6 ;
    LIB$SET_LOGICAL (%ASCID 'ML', full_name) ;

    ! Set up mail$init -> sys$login.mail]mailinit.com
    full_name [DSC$W_LENGTH] = full_length ;
    STR$CONCAT (full_name, top_dir, %ASCID '.MAIL]MAILINIT.COM') ;
    full_name [DSC$W_LENGTH] = .top_dir [DSC$W_LENGTH] + 18 ;
    LIB$SET_LOGICAL (%ASCID 'MAIL$INIT', full_name) ;

    LIB$SET_LOGICAL (%ASCID 'DBG$INIT', %ASCID 'LIB:DBG.DAT') ;
    LIB$SET_LOGICAL (%ASCID 'EDTINI', %ASCID 'LIB:EDTINI.EDT') ;
    LIB$SET_LOGICAL (%ASCID 'EDTINI2', %ASCID 'NLA0:') ;
    LIB$SET_LOGICAL (%ASCID 'EDT', %ASCID 'LIB:XEDT.EXE') ;
    LIB$SET_LOGICAL (%ASCID 'MAIL$EDIT', %ASCID 'CALLABLE_EMACS') ;

    ! Set up general Symbols
    LIB$SET_SYMBOL (%ASCID 'sl', %ASCID 'show logical', glob_sym) ;
    LIB$SET_SYMBOL (%ASCID 'ss', %ASCID 'show symbol', glob_sym) ;
    IF .Mode EQL Interactive THEN 
	LIB$SET_SYMBOL (%ASCID 'kp', %ASCID 'set terminal/application', glob_sym) ;


!+
! VT220 Terminal set ups - skip if OPA0: or BATCH
!-
    IF .Mode EQL interactive THEN 
	BEGIN
	    !	set term/eight
	    !		    F6= D i s c o n n e c t . A l l
	SCR$PUT_SCREEN (%ASCID '�1;1|17/446973636F6E6E65637420416C6C0D�') ;
	    !B
	    !		    F7= C o n n e c t . F O R T Y 2
	SCR$PUT_SCREEN (%ASCID '�1;1|18/436F6E6E65637420464F525459320D�') ;
	    !
	    !               F8= C o n n e c t . I O S G
	SCR$PUT_SCREEN (%ASCID '�1;1|19/436F6E6E65637420494F53470D�') ;
	    !
	    !               F9= s e t . s w i t c h . ^\
	SCR$PUT_SCREEN (%ASCID '�1;1|20/73657420737769746368201C0D�') ;
	    !
	    !		   F10= S h o w . N o d e . F O R T Y 2
	SCR$PUT_SCREEN (%ASCID '�1;1|21/53686F77204E6F646520464F525459320D�') ;
	    !
	    !              F11= ESC
	SCR$PUT_SCREEN (%ASCID '�1;1|23/1B<ST>') ;
	    !
	    !		   F12= S h o w . S e s s i o n s
	SCR$PUT_SCREEN (%ASCID '�1;1|24/53686F772053657373696F6E730D�') ;
	    !
	    !		   F13= S h o w . U s e r s
	SCR$PUT_SCREEN (%ASCID '�1;1|25/53686F772055736572730D�') ;
	    !
	    !		   F14= S h o w . N o d e s
	SCR$PUT_SCREEN (%ASCID '�1;1|26/53686F77204E6F6465730D�') ;
	    !
	    !		   HELP= H e l p
	SCR$PUT_SCREEN (%ASCID '�1;1|28/48656C700D�') ;
	    !
	    !		   F17= S h o w . T e r m i n a l
	SCR$PUT_SCREEN (%ASCID '�1;1|31/53686F77205465726D696E616C0D�') ;
	    !
	    !		   F18= B r o a d c a s t . T e r m i n a l
	SCR$PUT_SCREEN (%ASCID '�1;1|32/42726F616463617374205465726D696E616C20�') ;
	    !
	    !		   F19= Y U I L L E / C O M M A N D =
	SCR$PUT_SCREEN (%ASCID '�1;1|33/5955494C4C452F434F4D4D414E443D�') ;
	    !
	    !		   F20= Y U I L L E / N O C O M M A N D
	SCR$PUT_SCREEN (%ASCID '�1;1|34/5955494C4C452F4E4F434F4D4D414E440D�') ;
	END ;
!+
! End of VT220 Terminal set ups
!-

    ss$_normal
    END ;

END		! of LOGIN.B32
ELUDOM
371.10Not to be outdone.BLITZN::PALOErtu vitlaus?Thu Dec 18 1986 15:3521
$ DEFINE/NoLog RIK_NAMES -	! 2^n names
				"""space cowboy""",-
				"""BUGCHECK FATAL""",-
				"""Kernel Mode""",-
				"""George Jetson""",-
				"""Fred Flintstone""",-
				"""Stumpjumper""",-
				"""@(..)@""",-
				"""VAXinated""",-
				"""Hacking Central""",-
				"""euphemisms suck""" ,-
				"""Infatuated &-)""",-
				"""diesel & ethel""",-
				"""fat-tire lover""",-
				"""cheap thrill""",-
				"""wango tango""",-
 				"""Say whahh?"""
$ try_again:
$ on error then goto try_again
$ set proc/name='f$trn("RIK_NAMES",,f$cvt(,,"HUNDREDTH").and.f$trn("RIK_NAMES",,,,,"MAX_INDEX"))
$ set noon
371.11Look at PROCNAME in the toolshedTHEBAY::WAKEMANLACybernetic EtymologistThu Dec 18 1986 18:431
    
371.12regards to all...POGO::CHARRONRed BaronFri Dec 19 1986 00:569
    
    re note -.10 Is it possible to add names to your list ? and what
    is the  ! 2^names at the top of your list mean ? Also is there a
    limit as to how long of a name you can use ?
    
    Oh yes I tried the one memtioned in -.11 and the directory is no
    longer listed so couldn't get to the files.....
    
    Al.
371.13BISTRO::HEINHein van den Heuvel, Valbonne.Fri Dec 19 1986 03:3214
    re .10.
    
    Hmmm, now if we combine yours & mine (.0) we get:
    A long (10+) list of potential names from which we subtract any
    name currently in use, and then psuedo randomly select one by
    using the lowest digit of the current time. That would be an almost
    scientifical solution to a nonsense problem as opposed to the
    rough trial and ON ERROR so often proposed.  :-)  :-)
    
     re.12
    
    15 Characters limit. That's why I have the 'ruler' in a comment
    line in .0.
               Hein.
371.14Here's why 2^nREGINA::OSMANand silos to fill before I feep, and silos to fill before I feepFri Dec 19 1986 13:098
The reason there are 2^n names is so the ".and." expression uses all binary
1's on its righthand side, hence masking the hundreths to the number of
elements in the list.

Please note, however, that if you make the list too long, you'll need
more than hundreths to include them all !

/Eric
371.15How to get PROCNAMETHEBAY::WAKEMANLACybernetic EtymologistFri Dec 19 1986 14:2776
    re: .12
    
From:	CAD::FANEUF "Earl, Hl02-2/H13 (pole G11) DTN 225-4847 SPICE SUPPORT  08-Dec-1986 2132"  8-DEC-1986 20:42
To:	@procname.dis,FANEUF      
Subj:	New PROCNAME release!

 +---+---+---+---+---+---+---+
 | d | i | g | i | t | a | l |    I N T E R O F F I C E   M E M O
 +---+---+---+---+---+---+---+



TO:  PROCNAME Users                    DATE:  08 DEC , 1986
                                       FROM:  Earl Faneuf
                                       DEPT:  SEG-CAD
                                       EXT:   225-4847
                                       LOC/MAIL STOP:  HLO2-2/H13


SUBJ:  PROCNAME Version V2.2 Release Notice



This is to document the  release  of  PROCNAME  version V2.2

Upon installation of PROCNAME on your  machine,  this  release  memo
will  be  placed in PROCNAME$DIR:PROCNAME022.release_notes.

INSTALLATION:
A private installation is now done using a non-privaledged mode of
a standard digital product called VMSINSTAL. Both system installations
and private installations use the same files, which makes easier and
and far less bugs in the installation procedures.

NOTE: /REINSTALL will not preform this installtion.

 *******************************************************
TO INSTALL PRIVATELY:
   At DCL --
   
   $ COPY CAD::F$TOOLS:[PUBLIC]PROCNAME_INSTALL.COM []
   $ SPAWN   ! done to retain your private symbols.
   $ @PROCNAME_INSTALL
   $ LOGOUT  ! this logs you out of the SPAWN

Then follow the instructions. If you have any trouble to install the
tool, send me a mail and I will guide you with more exact information.
The procedure is very simple, and similar to the previous installation
method.
 ******************************************************
FOR A SYSTEM INSTALLATION, you will use VMSINSTAL directly, and must
feed vmsinstal the standard info about location of this kit.
LOCATION OF SAVE_SETS: CAD::F$TOOLS:[PUBLIC]
SAVE_SET 'A' NAME      : PROCNAME022.A
 ******************************************************

The differences between this version and version V2.1 are as
follows:

	o corrected the failure of the RANDOM function to do true
          random functionality.

*	o corrected a bug introduced by the previous version of the 
	  compiler which caused some accounts to log-off with out
	  any warning. 

	o created this more efficient VMSINSTAL kit format for both
	  system and private installs.

	o Removed the /REINSTALL qualifier because it was too difficult
	  to impliment with my new VMSINSTAL style of installations. This
          will be re-implimented in a future release.

        o corrected the error in the implimentation of the CALLABLE_EMACS
	  ml file. It now correctly works with emacs when used as described.
    
371.16BLITZN::PALOErtu vitlaus?Sun Dec 21 1986 12:405
    Good idea, Hein...  Go for it!
    
    	a bientot.
    
    		\rik
371.17ddca_username works for meWROGM1::MERRELLGreg Merrell/DTN 521-4553Sun Dec 28 1986 03:4513
    Since the systems which I work on tend to have usernames which are
    9 characters or less, it has always worked to prepend the terminal
    name and an _ to the username when first logging in. This creates
    processnames of the form TXA7_MERRELL. 
    
    With the introduction of terminal servers, it becomes necessary to
    chop off the end of the name when the unit numbers go above 999
    on the VTA device.
    
    The advantage of this is that you can tell which process is running
    on which terminal without doing any thinking.
    
    Greg
371.18Little things please little mindsISWSW::DOOLITTANThis brain intentionally left blankMon Feb 02 1987 02:039
    When I was working (?) at Lockheed in Sunnyvale, circa V3, I wrote
    a Macro program that I included in the system-wide login.com that
    set all process names for interactive processes to "WALDO_n" and
    all batch processes to "FARBO_n" where n was the lowest unused number
    in the group.  Caused massive confusion first time someone did "$sho
    sys".  Working with a bunch of engineers and mathematicians who
    were "too busy" to learn the machine had its advantages.
    
    andy