$ save_ver = 'f$verify(0)' $!++ $!*************************************************************************** $!* * $!* COPYRIGHT (c) 1996 BY * $!* DIGITAL EQUIPMENT CORPORATION, MAYNARD, MASSACHUSETTS. * $!* ALL RIGHTS RESERVED. * $!* * $!* THIS SOFTWARE IS FURNISHED UNDER A LICENSE AND MAY BE USED AND COPIED * $!* ONLY IN ACCORDANCE WITH THE TERMS OF SUCH LICENSE AND WITH THE * $!* INCLUSION OF THE ABOVE COPYRIGHT NOTICE. THIS SOFTWARE OR ANY OTHER * $!* COPIES THEREOF MAY NOT BE PROVIDED OR OTHERWISE MADE AVAILABLE TO ANY * $!* OTHER PERSON. NO TITLE TO AND OWNERSHIP OF THE SOFTWARE IS HEREBY * $!* TRANSFERRED. * $!* * $!* THE INFORMATION IN THIS SOFTWARE IS SUBJECT TO CHANGE WITHOUT NOTICE * $!* AND SHOULD NOT BE CONSTRUED AS A COMMITMENT BY DIGITAL EQUIPMENT * $!* CORPORATION. * $!* * $!* DIGITAL ASSUMES NO RESPONSIBILITY FOR THE USE OR RELIABILITY OF ITS * $!* SOFTWARE ON EQUIPMENT WHICH IS NOT SUPPLIED BY DIGITAL. * $!* * $!* * $!*************************************************************************** $!-- $! Module: LAN$POPULATE.COM $! $! Facility: LAN - (Local Area Network Device Drivers) $! $! Abstract: $! $! This procedure will create a command file LAN$DEFINE.COM which can be used $! to initially populate LANCP with MOP information. This procedure will $! obtain MOP data from either DECnet Phase IV or DECnet Phase V. $! $! Developer's Note: $! $! Execute this procedure without parameters for help about using the P1 $! parameter. The P2 parameter (not explained by Help) is intended for the $! developer's use only: DEBUG enables more extensive display output for $! Phase V processing, and VERIFY will "set verify" after initial housekeeping. $! $! Define symbols $! $ set symbol/scope=(nolocal,noglobal) $ success = 0 $ eof = 0 $ found_total = 0 ! Number of entries added to LAN$DEFINE.COM $ mop_list = "" ! Input file or work file name $ mop_temp = "" ! Work file name $ ws = "write sys$output" $! $! Figure out if we want to watch the commands being $! entered into LAN$DEFINE.COM. $! $ do_verify = "N" $ watch = "N" $ devo_option = f$edit(p2,"COMPRESS,TRIM,UPCASE") $ If f$extract(0,1,devo_option) .eqs. "D" then watch = "Y" $ If f$extract(0,1,devo_option) .eqs. "V" then do_verify = "Y" $! $! Determine if migration is from DECnet Phase IV or Phase V $! $ user_spec = f$edit(p1,"COMPRESS,TRIM,UPCASE") $ phasev = (f$extract(2,2,f$getsyi("DECNET_VERSION")).eqs."05") ! This node $ If user_spec .eqs. "" $ then $ If .NOT. f$getdvi("_NET0","EXISTS") then goto Net_Not_Running $ else $ If f$type(user_spec) .eqs. "INTEGER" $ then $ If phasev then goto Usage_Conflict $ phasev = 0 ! Can only operate for current Phase IV node, specified area $ If .NOT. f$getdvi("_NET0","EXISTS") then goto Net_Not_Running $ else $ phasev = 1 ! Operating on data from a Phase V node (maybe not this one) $ endif ! (this is the only case in which DECnet need not be running) $ endif $ If phaseV $ then $ net_type = "Phase V" $ else $ net_type = "Phase IV" $ endif $! $ on error then goto Error_Termination $ on control_y then goto User_Abort $! $! Provide Optional Help. $! $ type sys$input LAN$POPULATE - V1.4 $ If user_spec .eqs. "" $ then $ read/prompt="Do you want help (Y/N) : " sys$command junk $ junk = f$edit(junk,"COMPRESS,TRIM,UPCASE") $ If junk .eqs. "" then junk = "N" $ If junk $ then $ ws "" $ ws " LAN$POPULATE.COM - This procedure scans the current setup for MOP" $ ws " downline loading, based on one of the following:" $ ws "" $ ws " o the current ''net_type' node" $ If phasev $ then $ ws " (output of NCL SHOW MOP CLIENT * ALL) $ else $ ws " (NETNODE_REMOTE.DAT)" $ endif $ ws " o Phase V NCL MOP client setup information" $ type sys$input LAN$DEFINE.COM and LAN$DECNET_MOP_CLEANUP.COM are generated in the current default directory. Execute LAN$DEFINE.COM to populate LANCP downline loading information for MOP clients, thus migrating from DECnet to LANCP for MOP downline loading. Verify that downline loading occurs properly from LANCP for all of your satellites. If you wish, execute LAN$DECNET_MOP_CLEANUP.COM later to remove the clients' MOP downline loading information from the DECnet database. We recommend that you review LAN$DEFINE.COM and LAN$DECNET_MOP_CLEANUP.COM. Remove any obsolete entries before executing them. $ If phasev $ then $ ws "" $ ws " Also, edit NCL scripts to remove MOP client downline loading info." $ endif $ read/prompt="Press to continue" sys$command junk $ type sys$input Phase IV (current node only) [P1] DECnet area number. If specified, this confines LAN migration to the designated area. If not specified, all DECnet areas (1 - 63) are processed. Scanning all areas may take a long time for large networks. Example: @LAN$POPULATE 23 Phase V (current node unless P1 is specified) [P1] Name of an ASCII text file containing the output of NCL command SHOW MOP CLIENT * ALL. If specified, a LAN$DEFINE.COM procedure is produced for the node where the NCL command was executed. If omitted, the NCL database on the current node is used to produce LAN$DEFINE.COM. Example: @LAN$POPULATE mynode_nclmop.txt $! DEVO NOTE: For debugging, P2 = Debug for more output, Verify to Set Verify $! $! Ensure the user wants to proceed. $! $ read/prompt="Do you wish to proceed (Y/N) : " sys$command junk $ junk = f$edit(junk,"COMPRESS,TRIM,UPCASE") $ If junk .eqs. "" then junk = "N" $ If .not. junk then exit ! 'f$verify(save_ver)' $ endif ! If junk ... $ endif ! If user_spec .eqs. "" ... $! $! Create fresh output files and init a count $! $ If do_verify then set verify $ on control_y then continue $ create LAN$DEFINE.COM $ create LAN$DECNET_MOP_CLEANUP.COM $ open/append/error=No_LAN_Output result LAN$DEFINE.COM $ OPEN/append/error=No_Net_Output net_wipe LAN$DECNET_MOP_CLEANUP.COM $ on control_y then goto Migration_Abort $ write result "$ ! LAN$DEFINE.COM - LAN MOP Client Setup" $ write result "$ ! $ write result "$ ! This file was generated by LAN$POPULATE.COM at ",''F$TIME()'" $ write result "$ ! on node ''F$GETSYI("NODENAME")'." $ write result "$ !" $ write result "$ SET NOON" $ write result "$ WRITE SYS$OUTPUT ""Setting up MOP DLL clients in LANCP..." $ write result "$ MCR LANCP" $! $ write net_wipe "$ ! LAN$DECNET_MOP_CLEANUP.COM - DECnet MOP Client Cleanup" $ write net_wipe "$ !" $ write net_wipe "$ ! This file was generated by LAN$POPULATE.COM at ",''F$TIME()'" $ write net_wipe "$ ! on node ''F$GETSYI("NODENAME")'." $ write net_wipe "$ !" $ write net_wipe "$ SET NOON" $ write net_wipe "$ WRITE SYS$OUTPUT ""Removing MOP DLL clients from DECnet database...""" $! $ If phaseV then GOTO Convert_PhaseV $! $!************************ $! Convert DECnet Phase IV $!************************ $! $! Figure out what area(s) to scan: all, or the area specified in P1 $! $ area = 0 $ one_area = 0 $ if p1 .nes. "" $ then $ if (p1 .lt. 1) .or. (p1 .gt. 63) then goto bad_area $ area = f$integer(p1) $ one_area = 1 $ write result "! Only DECnet Area ''P1' was scanned." $ else $ write result "! All DECnet Areas were scanned." $ endif $ write net_wipe "$ MCR NCP" $! $! Main loop - iterate once per DECnet area $! $ main_loop: $ if one_area then goto 5$ $ area = area + 1 $ $5$: $ if .NOT. one_area then ws "Scanning DECnet Area ''area'..." $ mop_list = "lan$pop" + f$getjpi("","PID") + ".tmp" $ mop_temp = "lan$pop" + f$getjpi("","PID") + ".tmp_1" $ If f$search("''mop_list'") .nes. "" then delete/nolog 'mop_list';* $ If f$search("''mop_temp'") .nes. "" then delete/nolog 'mop_temp';* $ mcr ncp show node 'area'.* characteristics to 'mop_temp' $! $! For speed allow SEARCH to roughly parse the NCP file $! $ set message/notext/noseverity/nofacility/noidentification $ search 'mop_temp' /window=(3,3) "Hardware address"/exact /output='mop_list' $ set message/text/severity/facility/identification $ delete/nolog 'mop_temp';* $! $! Open the SEARCH output file $! $ open/read/error=mop_client_open_error mop_data 'mop_list' $ found = 0 $! $! Scan through the SEARCH output file. Iterate at 10$ for each node $! $10$: $! $! Look for node name: $! $ read/error=30$/end=20$ mop_data rec $ if f$extract(0,6,rec) .nes. "Remote" then goto 10$ $ node := - 'f$extract(f$locate("(",rec)+1,f$locate(")",rec)-f$locate("(",rec)-1,rec) $ node = f$fao("!8AS",f$edit(node,"COLLAPSE")) ! tidy it up a bit $! $! Clear down characteristic strings $! $ address := "" $ t_loader := "" $ laa := "" $ lap := "" $ load_file := "" $ host := "" $! $! Skip the next line in the SEARCH output file, which is always blank $! $ read/error=30$/end=20$ mop_data rec $! $! Read another 5 lines, parsing each one identically... $! $ read/error=30$/end=20$ mop_data rec $ gosub parse $ read/error=30$/end=20$ mop_data rec $ gosub parse $ read/error=30$/end=20$ mop_data rec $ gosub parse $ read/error=30$/end=20$ mop_data rec $ gosub parse $ read/error=30$/end=19$ mop_data rec $ gosub parse $! $! Output the LANCP commands. $! $19$: $ gosub write_commands $ found = found + 1 $ goto 10$ ! Iterate to next node for this area $! $! Error exit for Phase IV processing $! $30$: $ ws " ERROR: Problem encountered scanning DECnet MOP client list." $ Ws " Migration procedures may be incomplete." $! $! Common exit for Phase IV processing $! $20$: $ if .not. one_area then ws f$fao("!4UL MOP definition!%S found.",found) $ found_total = found_total + found $ if .not. (one_area .or. (area .eq. 63)) then goto Main_Loop $ success = 1 $ goto Output_Closeout $! $!*************** $ CONVERT_PHASEV: $!*************** $!++ $! Convert DECnet Phase V NCL output. $!-- $! $ found_total = 0 $ success = 0 $ mop_list = f$edit(p1,"COMPRESS,TRIM,UPCASE") $! $! If an input file is not specified $! $ If mop_list .eqs. "" $ then $ do_this_node = 1 $ ws " LAN$DEFINE.COM will be generated for this node." $ mop_list = "lan$pop" + f$getjpi("","PID") + ".tmp" $ mop_temp = "lan$pop" + f$getjpi("","PID") + ".tmp_1" $ If f$search("''mop_list'") .nes. "" then delete/nolog 'mop_list';* $ If f$search("''mop_temp'") .nes. "" then delete/nolog 'mop_temp';* $! $! Capture a list of MOP clients $! $ ws " Obtaining a list of MOP clients..." $ define/user sys$error 'mop_temp' $ define/user sys$output 'mop_list' $ mcr ncl show mop client * all $ error_code = $status $ If .not. error_code $ then $ ws f$message(error_code) $ type 'mop_temp' $ goto MOP_CLIENT_FIND_ERROR $ endif $ else $ do_this_node = 0 $ write result "$ ! Generated from NCL information in ''mop_list'" $ write result "$ !" $ endif $! $! Use the following to parse MOP DLL listing: $! $! Tag Reject? Variable Token ID $! ------------------------------------------------------------ $! MOP Client n/a node 0 $! Name Host Name node 1 $! Addresses n/a address 2 $! Tertiary Loader n/a t_loader 3 $! System Image n/a system_image 4 $! Phase IV Host Name n/a host 5 (for future use) $! Phase IV Host Address n/a host_address 6 (for future use) $! Phase IV Client Name n/a client_name 7 $! Phase IV Client Address n/a client_address 8 $! Dump File n/a dump_file 9 (for future use) $! $! Descriptions $! Tag: String to look for, announces a value of interest in the listing $! Reject: If tag occurs on same line as reject string, it is not a tag match $! Variable: Name of symbol that will hold a value of interest $! Token_ID: Element number in the table above $! $ tag_list = "MOP Client|Name|Addresses|Tertiary Loader|System Image|" + - "Phase IV Host Name|Phase IV Host Address|Phase IV Client Name|" + - "Phase IV Client Address|Dump File" $ reject_filters = "|Host Name||||||||" $ variable_list = "node|node|address|t_loader|system_image|host|" + - "host_address|client_name|client_address|dump_file" $! $! Initialize variables $! $ wiper = 0 $PhaseV_LAN_Init: $ varname = f$element(wiper,"|",variable_list) $ If varname .eqs. "|" then goto PhaseV_LAN_Init_Done $ 'varname' = "" $ wiper = wiper + 1 $ goto PhaseV_LAN_Init $! $PhaseV_LAN_Init_Done: $ primed = 0 ! 1 = no longer searching for start of info in report $ extract_value = 0 ! 1 = use next item that is not =, { or a tag as token $ ! value; if tag is encountered next, reset search $ current_token = 0 ! token id for most recently found tag $ buffer = "" $! $! Open the NCL MOP client report (read) $! $PhaseV_Mop_List_Check: $ If f$search("''mop_list'") .eqs. "" then goto Output_Closeout $ If f$file("''mop_list'","EOF") .GT. 0 then goto PhaseV_Mop_List_Open $ delete/nolog 'mop_list';0 $ goto PhaseV_Mop_List_Check $PhaseV_Mop_List_Open: $ on control_y then continue $ OPEN/error=MOP_CLIENT_OPEN_ERROR/read mop_data 'mop_list' $ on control_y then goto Migration_Abort $ write net_wipe "$ MCR NCL" $! $! Loop through the MOP client list looking for the next node $! $PhaseV_Mop_Client: $ If buffer .eqs. "" $ then $ READ/End_of_file=PhaseV_Done/error=MOP_CLIENT_READ_ERROR Mop_Data Input_String $ else $ input_string = buffer $ buffer = "" $ endif $ input_string = f$edit(input_string,"COMPRESS,TRIM") $ If input_string .eqs. "" then goto PhaseV_Mop_Client $! $PhaseV_Pattern_Loop: $! $!Check for a tag $! $ gosub PhaseV_Pattern_Match $! $!Until primed, search for first MOP client info before any other processing $! $ primed = primed .or. match $ If .not. primed then goto PhaseV_Mop_Client $! $!If a tag is found $! $ If match $ then $! $! If new MOP client, finish migration work for previous MOP client $! $ If token_id .eq. 0 then gosub PhaseV_Finish_Client ! tag is "MOP Client" $! $! Capture token id for use until next tag is found & start looking for value $! $ current_token = token_id $ extract_value = 1 $! $! Next non-blank info other than "=" or "{" is value for token $! $ varname = f$element(current_token,"|",variable_list) $ If trailer .nes. "" $ then $ 'varname' = "''trailer'" ! visible when debugging $PhaseV_Remove_Quotes_1: $ 'varname' = 'varname' - """" $ If f$locate("""",'varname') .lt. f$length('varname') then - $ goto PhaseV_Remove_Quotes_1 $ 'varname' = f$edit('varname',"COMPRESS,TRIM,UPCASE") $ If f$locate(" ",'varname') .lt. f$length('varname') $ then $ buffer = f$extract(locn+1,f$length('varname')-locn-1,'varname') + " " + buffer $ 'varname' = f$element(0," ",'varname') $ endif $ extract_value = 0 $ If current_token .eq. 0 $ then $ If watch then ws "" $ ws " Processing ''node'" $ endif $ endif $ endif $! $!If value extracted from line that contains current tag, look for next tag $! $ If .not. extract_value then goto PhaseV_Mop_Client $! $!If value is found, extract it; if it is in quotation marks, strip them off $! $ If trailer .nes. "" $ then $ 'varname' = trailer $PhaseV_Remove_Quotes_2: $ 'varname' = 'varname' - """" $ If f$locate("""",'varname') .lt. f$length('varname') then - $ goto PhaseV_Remove_Quotes_2 $ 'varname' = f$edit('varname',"COMPRESS,TRIM,UPCASE") $ If f$locate(" ",'varname') .lt. f$length('varname') $ then $ buffer = f$extract(locn+1,f$length('varname')-locn-1,'varname') + " " + buffer $ 'varname' = f$element(0," ",'varname') $ endif $! $! In case any of value was in double quotes, must repeat f$edit call $! $ 'varname' = f$edit('varname',"COMPRESS,TRIM,UPCASE") $ extract_value = 0 $ If current_token .eq. 0 $ then $ If watch then ws "" $ ws " Processing ''node'" $ endif $ endif $! $!Process next NCL report record $! $ goto PhaseV_Mop_Client $! $!Done: Entire MOP client list has been processed $! $PhaseV_Done: $ current_token = 0 $ gosub PhaseV_Finish_Client ! Process migration of last MOP client $ success = 1 $ goto Output_Closeout $! $!************* $! SUBROUTINES $!************* $! $ Write_Commands: $!+ $! (Phase IV only) Check to see if this is a cluster satellite. $!- $ if lap .eqs. "" then goto 30$ ! load assist param = satellite $! $! Build the LANCP define command for a satellite $! $ if (load_file .eqs. "" .and. t_loader .nes. "") then load_file := 't_loader' $ boot_type := "" $ if f$locate("APB.EXE","''f$edit(load_file,"UPCASE")'") .nes. f$length(load_file) $ then $ boot_type := "Alpha_Satellite" $ load_file := "APB.EXE" $ endif $ if f$locate("VMB.EXE","''f$edit(load_file,"UPCASE")'") .nes. f$length(load_file) $ then $ boot_type := "VAX_Satellite" $ load_file := "NISCS_LOAD.EXE" $ endif $ write result "Set Node ''node'/Address=''address' /File=''load_file' -" $ write result " /Root=''lap' /Boot_type=''boot_type'" $ write result "Define Node ''node'/Address=''address' /File=''load_file' -" $ write result " /Root=''lap' /Boot_type=''boot_type'" $ if watch $ then $ ws "Set Node ''node'/Address=''address' /File=''load_file' -" $ ws " /Root=''lap' /Boot_type=''boot_type'" $ ws "Define Node ''node'/Address=''address' /File=''load_file' -" $ ws " /Root=''lap' /Boot_type=''boot_type'" $ endif $! $! Write the DECnet Phase IV cleanup commands for a satellite $! $ write net_wipe "PURGE NODE ''node' HARDWARE ADDRESS" $ write net_wipe "PURGE NODE ''node' LOAD ASSIST AGENT" $ write net_wipe "PURGE NODE ''node' LOAD ASSIST PARAMETER" $ if f$extract(0,1,boot_type) .eqs. "A" then - $ write net_wipe "PURGE NODE ''node' LOAD FILE" $ write net_wipe "PURGE NODE ''node' TERTIARY LOADER" $ write net_wipe "CLEAR NODE ''node' HARDWARE ADDRESS" $ write net_wipe "CLEAR NODE ''node' LOAD ASSIST AGENT" $ write net_wipe "CLEAR NODE ''node' LOAD ASSIST PARAMETER" $ if f$extract(0,1,boot_type) .eqs. "A" then - $ write net_wipe "CLEAR NODE ''node' LOAD FILE" $ write net_wipe "CLEAR NODE ''node' TERTIARY LOADER" $ goto 35$ $! $! Build the LANCP command for a non-satellite $! $30$: $ write result "Define Node ''node'/Address=''address' /File=''load_file'" $ if watch then ws "Define Node ''node'/Address=''address' /File=''load_file'" $ $35$: $ return $! $ Parse: $!+ $! (Phase IV only) Parse Phase IV data. $!- $ if f$locate("Hardware address",rec) .eq. 0 then address := 'f$extract(f$locate("=",rec)+2,f$length(rec)-f$locate("=",rec)+2,rec) $ if f$locate("Tertiary loader",rec) .eq. 0 then t_loader := 'f$extract(f$locate("=",rec)+2,f$length(rec)-f$locate("=",rec)+2,rec) $ if f$locate("Load Assist Agent",rec) .eq. 0 then laa := 'f$extract(f$locate("=",rec)+2,f$length(rec)-f$locate("=",rec)+2,rec) $ if f$locate("Load Assist Parameter",rec) .eq. 0 then lap := 'f$extract(f$locate("=",rec)+2,f$length(rec)-f$locate("=",rec)+2,rec) $ if f$locate("Load file",rec) .eq. 0 then load_file := 'f$extract(f$locate("=",rec)+2,f$length(rec)-f$locate("=",rec)+2,rec) $ if f$locate("Host",rec) .eq. 0 then host := 'f$extract(f$locate("=",rec)+2,f$length(rec)-f$locate("=",rec)+2,rec) $ return $! $PhaseV_Pattern_Match: $!+ $! Inputs: $! Input_String String to search $! Tag_List List of match patterns to search for $! Reject_Filters List of reject strings associated with match patterns $! (reject a match if its reject string is found) $! $! Outputs: $! Token_ID Offset in pattern list of pattern that has been matched $! (only valid if Match = 1) $! Match 0 = match not found or match rejected $! 1 = match found $! Trailer if Match = 1: $! Characters from input_string after pattern_string, $! if Match = 0: $! Input_String $! after any "=" or "{" beyond pattern_string, $! before any " " or "}" $! Buffer Any contents of input string after trailer $!- $ token_id = 0 $ match = 0 $ trailer = "" $ in_string = input_string ! UPCASE later $ If do_verify $ then $ set noverify $ ws "-------------------------------------------------------------------" $ ws in_string $ ws "-------------------------------------------------------------------" $ set verify $ endif $! $! If input string is too short, return with no match $! $ If f$length(in_string) .le. 1 then goto PhaseV_Pattern_Done $PhaseV_Pattern_Loop: $ ps = f$element(token_id,"|",tag_list) $! $! If entire list of patterns has been sought, return with no match $! $ If ps .eqs. "|" then goto PhaseV_Pattern_No_Match $ save_input = in_string $! $! Make sure pattern search will be insensitive about case $! $ in_string = f$edit(in_string,"UPCASE") $ ps = f$edit(ps,"COMPRESS,TRIM,UPCASE") $ locn = f$locate("''ps'",in_string) $! $! If desired pattern is found $! $ If locn .lt. f$length(in_string) $ then $! $! If undesirable pattern must be looked for $! $ rs = f$element(token_id,"|",reject_filters) $ If f$length(rs) .gt. 0 $ then $! $! When undesirable pattern is absent, report a match $! $ rs = f$edit(rs,"COMPRESS,TRIM,UPCASE") $ If f$locate("''rs'","''in_string'").ge.f$length(in_string) then match = 1 $! $! Else no other pattern must be checked $! $ else $! $! Desired pattern found, report a match $! $ match = 1 $ endif $ endif $! $ If .not. match $ then $ token_id = token_id + 1 $ goto PhaseV_Pattern_Loop $ endif $PhaseV_Pattern_No_Match: $ If match $ then $ locn = locn + f$length(ps) $ trailer = f$edit(f$extract(locn,f$length(save_input)-locn,save_input),"COMPRESS,TRIM") $ else $ trailer = f$edit(save_input,"COMPRESS,TRIM") $ endif $ buffer = "" $ locn = f$locate("=",trailer) $ if locn .lt. f$length(trailer) then - $ trailer = f$edit(f$extract(locn+1,f$length(trailer)-locn-1,trailer),"COMPRESS,TRIM") $ locn = f$locate("{",trailer) $ if locn .lt. f$length(trailer) then - $ trailer = f$edit(f$extract(locn+1,f$length(trailer)-locn-1,trailer),"COMPRESS,TRIM") $ locn = f$locate("}",trailer) $ if locn .lt. f$length(trailer) $ then $ buffer = f$extract(locn+1,f$length(trailer)-locn-1,trailer) $ trailer = f$edit(f$element(0,"}",trailer),"COMPRESS,TRIM") $ endif $ locn = f$locate(" ",trailer) $ if locn .lt. f$length(trailer) $ then $ buffer = f$extract(locn+1,f$length(trailer)-locn-1,trailer) + " " + buffer $ trailer = f$edit(f$element(0," ",trailer),"COMPRESS,TRIM") $ endif $PhaseV_Pattern_Done: $ return $! $PhaseV_Finish_Client: $!+ $! Finish migration work for latest MOP client that has been fully processed. $! $! Inputs: $! All the variables in "variable_list". $! $! Outputs: $! Updates in the Phase V to LAN migration procedure file. $! $!- $ If node .eqs. "" then return $ migrate = "NODE ''node' " $ root_name = "" $ If system_image .nes. "" .and. - f$locate("@NET$NISCS_LAA(",system_image).lt.f$length(system_image) then - $ root_name = f$element(1,"(",system_image) - ")" $ If address .nes. "" then migrate = migrate + "/ADDRESS=''address'" $ boot_type = "" $ boot_file = "" $ If t_loader .nes. "" $ then $ If f$locate("VMB.EXE",t_loader) .lt. f$length(t_loader) $ then $ boot_type = "VAX_satellite" $ boot_file = "NISCS_LOAD.EXE" $ else $ If f$locate("APB.EXE",t_loader) .lt. f$length(t_loader) $ then $ boot_type = "ALPHA_satellite" $ boot_file = "APB.EXE" $ endif $ endif $ endif $ If system_image .nes. "" .and. - f$locate("@NET$NISCS_LAA(",system_image).ge.f$length(system_image) then - $ boot_file = system_image $ If root_name .nes. "" then migrate = migrate + "/ROOT=''root_name'" $ If boot_type .nes. "" then migrate = migrate + "/BOOT_TYPE=''boot_type'" $ If boot_file .nes. "" then migrate = migrate + "/FILE=''boot_file'" $ If client_name .nes. "" $ then $ name_holder = client_name $ else $ name_holder = node $ endif $! $! Write to migration procedures $! $ incomplete_command = 0 $ If address .eqs. "" .or. boot_type .eqs. "" .or. root_name .eqs. "" $ then $ If address .nes. "" $ then $ incomplete_command = 1 ! address is known $ write result "!" $ write result "! NEXT ENTRY: LANCP commands based on NCL setup may be incomplete" $ else $ incomplete_command = 2 ! address not known, do not migrate $ endif $ endif $ If incomplete_command .lt. 2 $ then $ found_total = found_total + 1 $ write result "SET ''migrate'" ! for volatile LAN database $ write result "DEFINE ''migrate'" ! for permanent LAN database $ write net_wipe "DELETE NODE 0 MOP CLIENT ''name_holder'" $ endif $! $! Clear the variables that hold setup values for a MOP client $! $ wiper = 0 $PhaseV_LAN_Write_Loop: $ varname = f$element(wiper,"|",variable_list) $ If varname .eqs. "|" then goto PhaseV_Write_Done $ If 'varname' .nes. "" $ then $ If watch $ then $ spacer = " " $ If f$length(varname) .le. 9 then spacer = spacer + " " $ ws " ''varname':''spacer'" + 'varname' $ endif $ 'varname' = "" $ endif $ wiper = wiper + 1 $ goto PhaseV_LAN_Write_Loop $PhaseV_Write_Done: $ If watch $ then $ spacer = " " $ If root_name .nes. "" then ws " root_name:''spacer'" + root_name $ endif $ If incomplete_command .gt. 0 $ then $ ws "" $ If incomplete_command .eq. 1 $ then $ ws " WARNING: LANCP setup commands for client ''name_holder' may be incomplete" $ else $ ws " WARNING: MOP client ''name_holder' not migrated to LANCP, no adapter address" $ endif $ If .not. watch then ws "" $ endif $ return $! $!************************************************ $! Errors and exits common to Phase IV and Phase V $!************************************************ $No_LAN_Output: $ ws " ERROR: The LAN$DEFINE.COM output file could not be created." $ goto Error_Termination $No_Net_Output: $ ws " ERROR: The LAN$DECNET_MOP_CLEANUP.COM output file could not be created." $ goto Error_Termination $Net_Not_Running: $ ws " ERROR: DECnet is not running. Start it before running this procedure." $ goto Error_Termination $Usage_Conflict: $ ws " ERROR: This system is running DECnet Phase V. Cannot fulfill request" $ ws " to migrate DECnet Phase IV area ''p1'. Please request a Phase V" $ ws " to LANCP migration." $ goto Error_Termination $Mop_Client_Open_Error: $ ws "" $ ws " ERROR: Problem opening list of MOP clients ''mop_list'." $ ws " Migration not attempted." $ exit ! 'f$verify(save_ver)' $! $!************************************************ $! Phase IV Specific Errors $!************************************************ $! $Bad_Area: $ ws "" $ ws " ERROR: The DECnet Area Parameter must be from 1 to 63." $ ws " The value entered was ","""''P1'""" $ goto Error_Termination $! $!************************************************ $! Phase V Specific Errors $!************************************************ $! $Mop_Client_Find_Error: $ ws "" $ ws " ERROR: Cannot find NCL MOP client list ''mop_list'. $ ws "" $ If p1 .eqs. "" $ then $ ws " Verify MOP has been started. If MOP was not started, please start" $ ws " it and try again. To start MOP:" $ ws "" $ ws " manually $ @SYS$SYSTEM:STARTUP NETWORK MOP" $ ws "" $ ws " automatically in Uncomment in SYS$MANAGER:NET$LOGICALS.COM" $ ws " DECnet-Plus startup $ DEFINE/SYSTEM/NOLOG NET$STARTUP_MOP TRUE" $ else $ ws " Please check the name of the NCL MOP client report file and try again." $ endif $! $Error_Termination: $ ws " Migration procedure NOT completed due to an error. Exiting..." $ exit ! 'f$verify(save_ver)' $! $Output_Closeout: $ If success $ then $ write result "EXIT" $ write result "$ !" $ write result "$ WRITE SYS$OUTPUT ""DECnet ''net_type' to LAN MOPDLL client migration complete!""" $ write result "$ EXIT" $! $ write net_wipe "EXIT" $ write net_wipe "$ !" $ write net_wipe "$ WRITE SYS$OUTPUT ""DECnet ''net_type' MOPDLL client cleanup complete!""" $ write net_wipe "$ EXIT" $ else $ write result "$ ! LAN$DEFINE.COM generation aborted!" $ write net_wipe "$ ! LAN$DECNET_MOP_CLEANUP.COM generation aborted!" $ endif $ set message/notext/noseverity/nofacility/noidentification $ close result $ close net_wipe $ close mop_data $ if mop_temp .nes. "" .and. f$search("''mop_temp'") .nes. "" then - $ delete/nolog 'mop_temp';* $ if mop_list .nes. "" .and. f$search("''mop_list'") .nes. "" then - $ delete/nolog 'mop_list';* $ set message/text/severity/facility/identification $ If success $ then $ If found_total .gt. 0 $ then $ ws "" $ ws " LAN$DEFINE.COM and LAN$DECNET_MOP_CLEANUP.COM were successfully generated." $ ws "" $ ws " We recommend that you review these procedures and remove any obsolete" $ ws " entries prior to executing them." $ ws "" $ ws " To apply the node definitions to the LANCP permanent database, $ ws " invoke the created LAN$DEFINE.COM command procedure. After you are" $ ws " satisfied that LAN MOP downline loading is properly set up, invoke" $ ws " LAN$DECNET_MOP_CLEANUP.COM to clean out MOP client setups from your network" $ ws " database." $ ws "" $ if found_total .ne. 1 $ then $ ws f$fao(" A total of !UL MOP definitions were entered into LAN$DEFINE.COM"- ,found_total) $ else $ ws f$fao(" A total of !UL MOP definition was entered into LAN$DEFINE.COM"- ,found_total) $ endif $ else $ ws " No MOP client entries were found to be migrated." $ ws " LAN$DEFINE.COM and LAN$DECNET_MOP_CLEANUP.COM were not generated." $ if f$search("lan$define.com") .nes. "" then - $ delete/nolog lan$define.com;0 $ if f$search("lan$decnet_mop_cleanup.com") .nes. "" then - $ delete/nolog lan$decnet_mop_cleanup.com;0 $ endif $ endif $ exit ! 'f$verify(save_ver)' $Migration_Abort: $ ws " Processing aborted! LAN$DEFINE.COM and LAN$DECNET_MOP_CLEANUP.COM are incomplete." $ goto Output_Closeout $User_Abort: $ ws " Migration procedure NOT completed due to user abort. Exiting..." $ goto Output_Closeout