gxb$RMS_JOURNAL_SNAP010.A`RMS_JOURNAL_SNAP010.ABACKUP/NOASSIST/NODISMOUNT/COMMENT=VAX/VMS SPKITBLD Procedure/INTER/LOG/VERIFY KIT$:*.*; KITROOT$:[000000]RMS_JOURNAL_SNAP010.A/LABEL=(RMS_JOURNAL_)/SAVE/BLOCK=9000/GROUP=25VAX/VMS SPKITBLD Procedure LASTOVICA `aT6.2 kit builder  _DPA1: V6.1 $ *[KIT]KITINSTAL.COM;1+, . / 4 -X0123KPWO 562`a7`a89GHHJN$!****************************************************************************N$!* *$$!* copyright 1993 by *N$!* digital equipment corporation, maynard, massachusetts. *N$!* all rights reserved. *N$!* *N$!* this software is furnished under a license and may be used and copied *N$!* only in accordance with the terms of such license and with the *N$!* inclusion of the above copyright notice. this software or any other *N$!* copies thereof may not be provided or otherwise made available to any *N$!* other person. no title to and ownership of the software is hereby *N$!* transferred. *N$!* *N$!* the information in this software is subject to change without notice *N$!* and should not be construed as a commitment by digital equipment *N$!* corporation. *N$!* *N$!* digital assumes no responsibility for the use or reliability of its *N$!* software on equipment which is not supplied by digital. *N$!* *N$!****************************************************************************$!$!8$! RMS_JOURNAL_SNAP Installation Procedure for VMSINSTAL$!$! 20.apr.1993 n. lastovica$!)$! Declare interrupt and error processing$!0$ on control_y then vmi$callback control_y&$ on error then goto exit_status$!$$ if vmi$debug then set verify$!5$ if p1 .eqs. "VMI$_IVP" then exit vmi$_success=$ if p1 .nes. "VMI$_INSTALL" then exit vmi$_unsupported$!/$! figure out if we're installing on AXP or VAX$!)$ if f$getsyi("hw_model") .gt. 1023 $ then $ platform = "AXP"!$ rmsjnlsnap_vms_version = "6.1" $ else $ platform = "VAX"!$ rmsjnlsnap_vms_version = "5.5" $ endif$!$ safedisk = 500$!I$! check on the VMS version and disk space and we don't want to deal with#$! the problems of alternate roots.$!1$ if vmi$alternate_root then goto noaltroot$!R$ vmi$callback check_vms_version rmsjnlsnap$$status 'rmsjnlsnap_vms_version';$ if .not. rmsjnlsnap$$status then goto wrong_version$!G$ vmi$callback check_net_utilization rmsjnlsnap$$status 'reqdisk'5$ if .not. rmsjnlsnap$$status then goto nospace$!P$ vmi$callback check_license rmsjnlsnap$$status rmsjnl dec 1.0 24-SEP-19919$ if .not. rmsjnlsnap$$status then goto needlicense$!*$! Turn on conditional safety installation$!6$ vmi$callback set safety conditional 'safedisk'$!"$ vmi$callback set purge ask$!M$ rename vmi$kwd:rms_journal_snap.exe-'platform' vmi$kwd:rms_journal_snap.exe$!T$ vmi$callback provide_file rmsjnlsnap$ rms_journal_snap_build.com vmi$root:[syshlp]T$ vmi$callback provide_file rmsjnlsnap$ rms_journal_snap.b32 vmi$root:[syshlp]U$ vmi$callback provide_image rmsjnlsnap$ rms_journal_snap.exe vmi$root:[sysexe]7$ vmi$callback provide_dcl_command rms_journal_snap.cld4$ vmi$callback provide_dcl_help rms_journal_snap.hlp$!$ type sys$input:C This installation has modified or supplied the following files:( SYS$COMMON:[SYSEXE]RMS_JOURNAL_SNAP.EXE! SYS$COMMON:[SYSLIB]DCLTABLES.EXE SYS$COMMON:[SYSHLP]HELPLIB.HLB( SYS$COMMON:[SYSHLP]RMS_JOURNAL_SNAP.B32. SYS$COMMON:[SYSHLP]BUILD_RMS_JOURNAL_SNAP.COM$!$ goto exit_success$! $needlicense:#$ vmi$callback message e nojnllic -S "The OpenVMS RMS Journaling license must be loaded in order to install this kit" -@ "Please install the license and then restart this installation"$ goto exit_failure $nospace:f$ vmi$callback message e nospace "System disk does not contain at least ''reqdisk' free blocks."$ goto exit_failure $noaltroot:d$ vmi$callback MESSAGE e noaltroot "This kit cannot be installed in an alternate system root."$ goto exit_failure$wrong_version:$ vmi$callback message e version "This kit must be installed on OpenVMS ''platform' V''rmsjnlsnap_vms_version' or greater."$exit_failure:$ retval == vmi$_failure$ goto exit_retval $exit_status:$ retval == $status$ goto exit_retval$exit_success:$ retval == vmi$_success $exit_retval:$$ if f$verify() then set nover$ exit retval*[KIT]RMS_JOURNAL_SNAP.B32;1+,".</ 4[<9-X0123KPWO=562`a7`a89GHHJ 6%title 'RMS After Image Journal File Snapshot Program'3module rms_journal_snap(main=rms_journal_snap$main, ident = 'V1.0',$ addressing_mode(external=general," nonexternal=word_relative)) =begin!.! copyright 1993 by >! digital equipment corporation, maynard, massachusetts. ! all rights reserved. ! J! this software is furnished under a license and may be used and copied J! only in accordance with the terms of such license and with the J! inclusion of the above copyright notice. this software or any other J! copies thereof may not be provided or otherwise made available to any J! other person. no title to and ownership of the software is hereby ! transferred. ! J! the information in this software is subject to change without notice J! and should not be construed as a commitment by digital equipment ! corporation. ! J! digital assumes no responsibility for the use or reliability of its ?! software on equipment which is not supplied by digital. ! A! rms_journal_snap may be distributed, as an unsupported tool, toE! customers of digital equipment corporation who have a valid vax rms=! journaling license provided that the entire source code andB! documentation delivered are intact including all disclaimers and! copyright information. !++! ! abstract: !J! this program will snapshot (copy and rewind; spool) an RMS after imageI! journal file of a sequential file. the input journal file is copied,C! truncated and then a new backup marker record is written. thisB! program allows the input journal to be open and being actively,! accessed during this snapshot operation.!F! the input journal file is read in three steps. first, the file isJ! opened with no locking (shr=upi) and read and copied to eof. the fileJ! is then closed and opened again with locking and sharing enabled. theG! file is read starting at the previously last read record to to eof.H! finally, the file is locked to prevent journal write access and thenJ! read to the current eof. the snapshot journal file is then closed andH! the existing journal file is rewound and truncated after the journalF! header record and a backup marker record is written. finally, theG! existing journal file is unlocked for journal write access and then ! closed.!J! the output journal snapshot is c`5+$RMS_JOURNAL_SNAP010.A"XIT]RMS_JOURNAL_SNAP.B32;1[<reated with an allocated size equal toG! the current file's end of file block location and with an extensionG! size of 1% of this size or 100 block, whichever is larger. this isG! done to account for an input journal file that is overly allocated.!I! this program requires CMEXEC priv along with read/write access to the-! input and output journal files specified.!G! in order to avoid having a message facility/file, this program usesC! DCL's facility code along with a couple messages from the SHR$_F! facility (these are multi-facility shared messages). in addition,H! rms$_iff (for lack of a better status) is signaled if the input file! is not an rms journal file.!4! the default output journal snapshot file type is'! .RMS$JOURNAL-SNAP_yyyy-mm-dd_hh_mm_ssC! (where yyyy-mm-dd_hh_mm_ss represents the current system time).!:! the .CLD file required for this program is as follows:!O!++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++! module rms_journal_snap! define verb jnlsnap! image rms_journal_snap?! parameter p1, label=input_file, prompt="Input_Journal_File", ! value(type=$file, required)A! parameter p2, label=output_file, prompt="Output_Journal_File", ! value(type=$file, required)O!++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++!N! author: norm lastovica, digital equipment corp, colorado springs, coloradoG! thanks to hein vandenheuvel for suggesting various techniques and! providing code reviews.! ! date: 24.feb.1993!! modification history:! ! 8.mar.1993 n. lastovica8! add additional error reporting capabilities. per heinC! vandenheuvel, read the journal file in 3 passes - the first beingD! with no locking at all (upi mode). this should be much faster forC! the first pass. then open with locking and read to EOF again andC! disconnect, lock, reconnect and read to eof, truncate and unlock.A! add locate mode and write behind also for performance. set the@! output default file type such that it will sort in the correctD! order (make the date field a comparison sort of display). displayD! a timer once the operation is complete. display counts of records>! moved. make sure that the user has cmexec priv. create the<! output file with a default extension quantity of 1% of the3! original size or 100 blocks, whichever is bigger.!! 16.mar.1993 n. lastovicaD! additional error checking. use a local macro to move the rfa withA! a movq instead of a movc3. add more comments. remove .addressD! references and own storage. don't allow opening the input file ifD! isn't an rms journal file. on the re-open, open the file with theB! nam block information (device, directory and file ids) such thatA! it'll be a little faster. avoid disconnect and reconnecting to ! the file.!! 23.mar.1993 n. lastovicaA! do not reposition to the last read rfa when reading the file toC! eof the last time. the eof pointer will be updated automatically/! and won't move after the file lock is gained.!! 12.mar.1993 n. lastovicaD! for performance when writing to tape, set magnetic tape block sizeA! to 65000 bytes. default the output file name to the input fileC! name. add 4 buffers of 127 blocks each to the input file fab and! enable read ahead.!! 13.mar.1993 n. lastovica=! increase buffers to 8 on both the input and output streams.!! 14.oct.1994 n. lastovicaG! changes to support AXP and display banner. alter statistics display.!-- !! table of contents:!forward routine rms_journal_snap$main;!! include files:!library 'sys$library:lib';psect" plit = $$plit (pic, share)," code = $$code (pic, share);! ! macros:!!I! this macro is used to lock or unlock the journal file for journal writeJ! acess. it uses the undocumented interface through sys$modify by settingG! the fab esc flag and putting a 'function' code in the ctx field. seeG! the listings at resd$:[rms.lis]rms0modfy.lis for further information.!I! pass in the journal file fab and the lock state (true to lock; false toJ! unlock). the ctx field of the fab is destroyed and not restored by this! macro.!macro) _lock_journal (jnl_fab, lock_state) = jnl_fab[fab$v_esc] = true;$ jnl_fab[fab$l_ctx] = %if lock_state %then rme$c_keep_lock_on %else rme$c_keep_lock_off %fi;/ _chkrms_sig($modify (fab = jnl_fab), old_fab); jnl_fab[fab$v_esc] = false; %;!F! this macro is used to check the status of an rms operation and if itJ! wasn't successfull, to signal the status long with the sts or stv from a ! fab or rab.!macro _chkrms_sig (oper, struct) = begin local $$chkrms_sig_status;& if not ($$chkrms_sig_status = (oper)) then begin !H ! the structure can be either a fab or a rab. so we need to ensureC ! that the sts and stv fields are at the same positions within ! either structure. !C $assume($byteoffset(fab$l_stv), eqlu, $byteoffset(rab$l_stv));C $assume($byteoffset(fab$l_sts), eqlu, $byteoffset(rab$l_sts)); if not .struct[fab$l_sts] then4 signal(.struct[fab$l_sts], 0, .struct[fab$l_stv]); end; .$$chkrms_sig_status end %; !7! macro to check a status and signal if not successfull! macro _chkerr_sig (exp) = begin local $$chkerr_sig_status;$ if not($$chkerr_sig_status = (exp)) then" signal(.$$chkerr_sig_status); .$$chkerr_sig_status end %;!I! this macro is used to create a character string descriptor 'on the fly'J! without using any own storage or .address references. requires that __d:! already is a defined symbol with 2 longwords of storage.!macro _descriptor(st) = begin __d[1] = uplit byte(st); __d[0] = %charcount(st); __d[0] end %;!M! this macro is used to move 8 bytes of an rfa from one place to another. itK! is implimented this way instead of using ch$mov since ch$mov results in aO! movc3 instruction and this macro results in a (faster) movq instruction. theK! rfa in the rab is followed by a filler word for alignment such that the 8 ! byte move won't harm anything.!macro _move_rfa (source, dest) = begin bind $$src = source : $bblock, $$dst = dest : $bblock;! $assume(rfa_move_size, eqlu, 8); $ $$dst[0,0,32,0] = .$$src[0,0,32,0];$ $$dst[4,0,32,0] = .$$src[4,0,32,0]; end %; !! various string descriptors.!macroL header_fao = _descriptor('!/ RMS_JOURNAL_SNAP !AC (built !%D)!/') %,Y stat_fao_1 = _descriptor('!UL record!%S moved during pass 1 (file not locked)')%,[ stat_fao_2 = _descriptor('!UL record!%S moved during pass 2 (with file locked)') %,6 filein_fao = _descriptor('Copied from !AD') %,. fileout_fao = _descriptor('to !AD') %,K outfilfao = _descriptor('!AD.RMS$JOURNAL-SNAP_!AD-!2ZB-!AD_!AD') %,2 infile_param = _descriptor('INPUT_FILE') %,3 outfile_param = _descriptor('OUTPUT_FILE') %; literal! false = 0, ! false value true = 1, ! true value5 buffer_size = 32767, ! size of the rms bufferH time_string_len = 20, ! length of the string for calling $gettim. dcl_fac = 196608, ! DCL's facility code< tape_block_size = 65000, ! block size for tape output; rfa_move_size = 8; ! number of bytes of rfa to moveliteral !G ! _alpha equates to TRUE if compiling with the BLISS32e or BLISS64eG ! compilers. if this statement fails, then the compiler being usedE ! won't understand these %bliss directives. if this is the case,J ! change the following line to something like "_alpha = 0" since there2 ! is no way that you're running on an AXP box. !2 _alpha = %bliss(bliss32e) or %bliss(bliss64e);own !N ! the read-only month table is used to translate a month string to a month ! number. !9 month_table : psect($$plit) vector[12, long] preset (C [0] = 'JAN-', [1] = 'FEB-', [2] = 'MAR-', [3] = 'APR-',C [4] = 'MAY-', [5] = 'JUN-', [6] = 'JUL-', [7] = 'AUG-',D [8] = 'SEP-', [9] = 'OCT-', [10] = 'NOV-', [11] = 'DEC-');!! external references:!external routine lib$init_timer, lib$show_timer, lib$sys_fao, lib$put_output, lib$sfree1_dd, cli$get_value; *%sbttl 'journal snapshot mairL$RMS_JOURNAL_SNAP010.A"XIT]RMS_JOURNAL_SNAP.B32;1[<"n entry point'Droutine rms_journal_snap$main( transfer_address_array : ref $bblock, cli_dispatcher,( image_header : ref $bblock) =!++! FUNCTIONAL DESCRIPTION:! )! snapshot an existing RMS journal file! ! FORMAL PARAMETERS:! ! none! ! IMPLICIT INPUT PARAMETERS:! ! none! ! IMPLICIT OUTPUT PARAMETERS:! ! none! ! RETURN VALUE:! ! ss$_normal! ! SIDE EFFECTS:! ! None! !--begin local stat, ! status holder3 jpi_iosb : vector[4,word], ! iosb for $getjpi< jpi_itmlst : $itmlst_decl(items=1), ! $getjpi item list0 current_privs : $bblock[8], ! user's privs) month : initial(0), ! month number __d : vector[2, long],) ihd : ref $bblock ! pointer to the* initial(.image_header), ! image header9 moved_locked : initial(0), ! records moved w/o lock9 moved_unlocked : initial(0), ! records moved locked. timebuff : vector[time_string_len, byte],< timedesc : vector[2,long] preset ( [0]=time_string_len, [1]=timebuff[0]),6 desc : $bblock[dsc$k_d_bln], ! random descriptor1 desc1 : $bblock[dsc$k_d_bln], ! another one: save_rfa : $bblock[rfa_move_size], ! temp rfa storage= old_rss : $bblock[nam$c_maxrss], ! old file result name? old_ess : $bblock[nam$c_maxrss], ! old file expanded name> new_rss : $bblock[nam$c_maxrss], ! new file result name ? new_ess : $bblock[nam$c_maxrss], ! new file expended name> header_xab : $bblock[xab$c_fhclen], ! old file header xab? prot_xab : $bblock[xab$c_prolen], ! old/new protection xab2 old_fab : $bblock[fab$c_bln], ! old file fab2 old_rab : $bblock[rab$c_bln], ! old file rab4 old_nam : $bblock[nam$c_bln], ! old name block2 new_fab : $bblock[fab$c_bln], ! new file fab2 new_rab : $bblock[rab$c_bln], ! new file rab4 new_nam : $bblock[nam$c_bln], ! new name block1 buffer : $bblock[buffer_size]; ! I/O buffer !J ! the file header xab is used to get the current eof block as a targetE ! size of the snapshot file. this is used instead of the currentH ! allocation size of the journal file in case the file was purposely ! allocated vary large. !4 $xabfhc_init(xab = header_xab, nxt = prot_xab); !B ! the protection xab is to make the snapshot file have similarF ! protection and ownership as the input file. this xab is used onG ! both the input file fab and the output file fab. this xab is theI ! first one chained to the output file fab. make sure that it is the ! last one in the xab chain. !! $xabpro_init(xab = prot_xab);  !H ! the nam block is used to retrieve the resultant file spec when theJ ! input journal file is opened. since the file will be reopened afterI ! the first time, use the original full spec as the file spec for the ! second open. !: $nam_init(nam = old_nam,rsa=old_rss, ! rss address* rss=%allocation(old_rss),! and size% esa=old_ess, ! ess address+ ess=%allocation(old_ess));! and size O $fab_init(fab = old_fab,shr=,! upi for sharing. we will# ! do no locking the first" ! time the file is being$ ! read. later, it will be" ! re-opened with locking ! enabled.* rtv=255, ! map the entire file0 nam=old_nam, ! get the full file spec7 xab=header_xab, ! header and protection xabs: dnm='.RMS$JOURNAL', ! the default old file name) fac=); ! get access only( $rab_init(rab = old_rab,fab=old_fab,7 rop=, ! in case of locks, wait.& ! there should never be any,$ ! but this is just in case& ! protection. enable locate# ! mode and read-ahead for ! faster access.! mbf=8, ! 8 buffers of& mbc=127, ! 127 blocks each( ubf=buffer, ! buffer pointer* usz=%allocation(buffer));! and size : $nam_init(nam = new_nam,rsa=new_rss, ! rss address* rss=%allocation(new_rss),! and size% esa=new_ess, ! ess address+ ess=%allocation(new_ess));! and sizeL $fab_init(fab = new_fab,journal=journal_file, ! this is a journal file4 bls=tape_block_size, ! block size for tape% nam=new_nam, ! nam pointer5 fac=, ! put and truncate on close$ ! and try to make a contig ! file.* rtv=255, ! map the entire file+ shr=, ! no sharing allowed2 xab=prot_xab, ! get the protection from" ! the input journal file& ! (the xab will be filled in" ! when the input file is$ ! opened and should be the" ! last in the xab chain)4 fop=); ! truncate at end of file( $rab_init(rab = new_rab,fab=new_fab,& mbf=8, ! 8 buffers each of, mbc=127, ! 127 blocks per buffer4 rop=); ! enable asynch write behind !a ! start the run timern !  lib$init_timer (); !e( ! initialize two dynamic descriptors !  $init_dyndesc(desc1);i $init_dyndesc(desc); ! K ! create and display a banner. AXP and VAX image headers differ so thehJ ! image header information needs to be extracted from different placesJ ! depending on the compiler that is being used (this is somewhat of anL ! assumption about what compiler is really being used for producing code ! for a given platform). !  %if _alpha %thenb$ ihd = .ihd + .ihd[eihd$l_imgidoff];X _chkerr_sig(lib$sys_fao(header_fao, 0, desc, ihd[eihi$t_imgid], ihd[eihi$q_linktime])); %else.# ihd = .ihd + .ihd[ihd$w_imgidoff]; V _chkerr_sig(lib$sys_fao(header_fao, 0, desc, ihd[ihi$t_imgid], ihd[ihi$q_linktime])); %fis lib$put_output(desc);i  ! M ! get the current process privs and make sure that we have change mode tob ! exec priv. !l: $itmlst_init(itmlst=jpi_itmlst, (itmcod=jpi$_curpriv,  bufadr=current_privs, ) bufsiz=%allocation(current_privs)));t0 _chkerr_sig($getjpiw ( itmlst = jpi_itmlst, iosb = jpi_iosb));n _chkerr_sig(.jpi_iosb[0]); !lI ! if not chexec, try to turn it on. if that doesn't work then signal  ! a fatal errora !l' if not .current_privs[prv$v_cmexec] then begin7 ch$fill(0, %allocation(current_privs), current_privs);;$ current_privs[prv$v_cmexec] = true; !H ! if this fails, we don't have the priv and are unable to get it. give3 ! up and let them know that they need CMEXEC priv. ! if not $setprv (enbflg = true,l prvadr = current_privs, prmflg = false) thens signal(ss$_nocmexec); end;n !aG ! get the input file name and try to open the existing journal filec ! 3 _chkerr_sig(cli$get_value(infile_param, desc));t. old_fab[fab$l_fna] = .desc[dsc$a_pointer];- old_fab[fab$b_fns] = .desc[dsc$w_length];t if not $open(fab=old_fab)t then begin local= errnam : vector[2,long] preset( [0]=.old_nam[nam$b_esl], " [1]=.old_nam[nam$l_esa]);. signal( shr$_openin + sts$k_severe + dcl_fac, 1, errnam,s .old_fab[fab$l_sts], 0, .old_fab[fab$l_stv]);c end;  !mN ! make sure that the input file is a rms journal file. signal rms$_iff asJ ! a failure status for the time being since there doesn't seem to be a$ ! better looking message around. !a' if not .old_fab[fab$v_journal_file]b then begin local= errnam : vector[2,long] preset( [0]=.old_nam[nam$b_esl], " [1]=.old_nam[nam$l_esa]);. signal( shr$_openin + sts$k_severe + dcl_fac, 1, errnam, rms$_iff); end;  X ! ' ! connect to the input journal file  ! if not $connect(rab=old_rab) then begin local= errnam : vector[2,long] preset( [0]=.old_nam[nam$b_esl], " [1]=.old_nam[nam$l_esa]);. signal( shr$_openin + sts$k_severe + dcl_fac, 1, errnam,e .old_rab[rab$l_sts], 0, .old_rab[rab$l_stv]);  end;s ! L ! create the the default snapshot file type - made up of a prefix string" ! and the current system time. ! J ! get the system time. if the first character of the time string is aN ! space, replace it with a zero. this will happen for the first 9 days ofD ! each month. then replace the 2 colons in the time string with ! underscores+kMy[$RMS_JOURNAL_SNAP010.A"XIT]RMS_JOURNAL_SNAP.B32;1[<ʊ( !+- _chkerr_sig($asctim (timbuf = timedesc));v if .timebuff[0] eqlu ' ' then timebuff[0] = '0';b& timebuff[14] = timebuff[17] = '_'; !vM ! determine the current month number. the 4 byte month string (includingJO ! the trailing dash) is used to compare in the month table, one longword at+ ! a time.+ !+4 ch$move(%allocation(month), timebuff[3], month); incr i from 0 to 11  do !H ! if a matching month is found, set the month number to the table entryG ! index plus 1 (1 = january, 2 = february...). if the month string isb@ ! not found in the table, a bogus month value will be returned. ! if .month_table[.i] eqlu .month thenc begin month = .i + 1; exitloop; end;  !e+ ! build up the default file type stringl ! & _chkerr_sig(lib$sys_fao(outfilfao, 0, ! desc, ! output descriptord3 .old_nam[nam$b_name], ! old file name length , .old_nam[nam$l_name], ! old file name 4, ! year lengths, timebuff[7], ! 4 bytes of year string .month, ! month number 2, ! day length+ timebuff[0], ! 2 bytes of day stringp 8, ! time lengthn0 timebuff[12])); ! 8 bytes of current time ! - ! retrieve the specified output file name. ! 5 _chkerr_sig(cli$get_value(outfile_param, desc1));f !e5 ! fill in the default name and the specified name ! . new_fab[fab$l_dna] = .desc[dsc$a_pointer];- new_fab[fab$b_dns] = .desc[dsc$w_length];h/ new_fab[fab$l_fna] = .desc1[dsc$a_pointer];.. new_fab[fab$b_fns] = .desc1[dsc$w_length]; !aK ! initial allocation is the current end of file size of the input file. M ! this is used instead of allocated size in case the input file is overly)O ! allocated. the default extention quantity is 1% of the current file size ) ! or 100 blocks, whichever is bigger.c !o0 new_fab[fab$l_alq] = .header_xab[xab$l_ebk];@ new_fab[fab$w_deq] = max(.header_xab[xab$l_ebk] / 100, 100); !i ! create the output file !  if not $create(fab=new_fab)r then begin local= errnam : vector[2,long] preset( [0]=.new_nam[nam$b_esl],e" [1]=.new_nam[nam$l_esa]);/ signal( shr$_openout + sts$k_severe + dcl_fac,f 1, errnam,s .new_fab[fab$l_sts], 0, .new_fab[fab$l_stv]); end;  !9, ! connect the rab to the output file fab ! if not $connect(rab=new_rab) then begin local= errnam : vector[2,long] preset( [0]=.new_nam[nam$b_esl],i" [1]=.new_nam[nam$l_esa]);/ signal( shr$_openout + sts$k_severe + dcl_fac,_ 1, errnam, .new_rab[rab$l_sts], 0, .new_rab[rab$l_stv]);c end;  ! H ! read the contents of the existing journal file and write it to theL ! snapshot file. this is done with no locking at all on the input file.O ! the rfa is saved after each record read and will be used to reposition toi& ! that point in the file later on. ! $ while (stat = $get(rab=old_rab)) do begin* new_rab[rab$w_rsz] = .old_rab[rab$w_rsz];* new_rab[rab$l_rbf] = .old_rab[rab$l_rbf];) _chkrms_sig($put(rab=new_rab), new_rab);n !4 ! save the rfa of the last record read at each pass ! 0 _move_rfa(old_rab[rab$r_rfa_fields], save_rfa);& moved_unlocked = .moved_unlocked + 1; end; !b= ! rms$_eof is the only failure status that is acceptable.c !  if .stat nequ rms$_eof then _chkrms_sig(.stat, old_rab);o y ! G ! end of the first pass with the input file. now close it and theno- ! re-open it with record locking enabled.n ! . _chkrms_sig($close(fab=old_fab), old_fab); !tJ ! set the nam bit in the fab so that the file re-open will occur basedJ ! on the device, directory and file id instead of file name. for thisE ! open, allow get and put and access will be get, put, update andb ! truncate.  !  old_fab[fab$v_nam] = true;  old_rab[rab$v_rah] = false; 5 old_fab[fab$b_shr] = fab$m_shrput + fab$m_shrget;!G old_fab[fab$b_fac] = fab$m_get + fab$m_put + fab$m_upd + fab$m_trn;  !eH ! reopen and connect to the file. the file is accessed based on the8 ! FID and DID and device id stored in the nam block. !r/ _chkrms_sig($open(fab = old_fab), old_fab);a2 _chkrms_sig($connect(rab = old_rab), old_rab); !iD ! reposition back the the last previously read record. and thenG ! convert back to sequential mode. 1the $get will transfer data buttE ! this data is ignored; the $get is just to position for the next%I ! record. after reading the record, revert back to sequential accesst ! mode.i !s# old_rab[rab$b_rac] = rab$c_rfa;e3 _move_rfa(save_rfa, old_rab[rab$r_rfa_fields]);o, _chkrms_sig($get(rab=old_rab), old_rab);# old_rab[rab$b_rac] = rab$c_seq;p !sI ! move all the remaining records in the file to eof. this represents I ! any records written since the file was first opened and when it wase ! re-opened. !u$ while (stat = $get(rab=old_rab)) do begin* new_rab[rab$w_rsz] = .old_rab[rab$w_rsz];* new_rab[rab$l_rbf] = .old_rab[rab$l_rbf];) _chkrms_sig($put(rab=new_rab), new_fab);t& moved_unlocked = .moved_unlocked + 1; end; ! < ! rms$_eof is the only failure status that is acceptable !b if .stat nequ rms$_eof then _chkrms_sig(.stat, old_rab);  !B ! the existing contents of the file have now been moved to theE ! snapshot file. get the file lock - noone else can write to the  ! journal file now.i !/! _lock_journal(old_fab, true);'  !tJ ! read to the current end of the existing journal file and write it toE ! the snapshot file. presumably, there won't be many new recordss8 ! written since we last read to the end of the file. !o$ while (stat = $get(rab=old_rab)) do begin* new_rab[rab$w_rsz] = .old_rab[rab$w_rsz];* new_rab[rab$l_rbf] = .old_rab[rab$l_rbf];) _chkrms_sig($put(rab=new_rab), new_rab);F" moved_locked = .moved_locked + 1; end;O !E< ! rms$_eof is the only failure status that is acceptable !  if .stat nequ rms$_eof then _chkrms_sig(.stat, old_rab);b ! O ! close the new journal file to force everything to be written back to diska, ! before the existing file is truncated. ! . _chkrms_sig($close(fab=new_fab), new_fab); !eJ ! leave the header and leader records on the existing journal file and- ! then remove (truncate) everything else.I !rP _chkrms_sig($rewind(rab=old_rab), old_rab); ! point to the start of the fileL _chkrms_sig($find(rab=old_rab), old_rab); ! read header record. read theN _chkrms_sig($find(rab=old_rab), old_rab); ! leader header. can we read theB if (stat = $find(rab=old_rab)) ! next? there might have been$ ! only two records in the file$ ! if this is so, then we don't% ! have to truncate the file (its ! is already empty). then. _chkrms_sig($truncate(rab=old_rab), old_rab); !e$ ! create a journal backup marker ! E ch$fill(0, rjr$k_backuplen, buffer); ! zero out the backup marker ; buffer[rjr$w_facility] = rms$_facility; ! rms' facility'E buffer[rjr$b_jnl_type] = rjr$c_rms_ai; ! after image journal filexB buffer[rjr$b_version] = rjr$c_curver; ! rms journaling version< buffer[rjr$b_entry_type] = rjr$c_backup; ! backup record5 buffer[rjr$b_org] = rjr$c_seq; ! sequential filen8 buffer[rjr$l_jnlidx] = 1; ! it is unclear what theA buffer[rjr$l_backup_seqno] = 1; ! journal index and sequence ! number should be set to.6 $gettim (timadr = buffer[rjr$q_date]); ! timestamp ! ! write the backup markero ! old_rab[rab$l_rbf] = buffer;) old_rab[rab$w_rsz] = rjr$k_backuplen;, _chkrms_sig($put(rab=old_rab), old_rab); !lA ! unlock the existing journal file - allow write access again ! " _lock_journal(old_fab, false); !4 ! close the old journal file ! . _chkrms_sig($close(fab=old_fab), old_fab);  !i% ! display some statistical outputm !  lib$show_timer ();' _chkerr_sig(lib$sys_fao(filein_fao,d 0, desc, .old_nam[nam$b_rss],a .old_nam[nam$l_rsa]));v lib$put_output(desc); ( _chkerr_sig(lib$sys_fao(fileout_fao, 0,a desc, .new_nam[nam$b_rss],  .new_nam[nam$l_rsa]));e lib$put_output(d9$RMS_JOURNAL_SNAP010.A"XIT]RMS_JOURNAL_SNAP.B32;1[<W9esc);2C _chkerr_sig(lib$sys_fao(stat_fao_1, 0, desc, .moved_unlocked));  lib$put_output(desc);!A _chkerr_sig(lib$sys_fao(stat_fao_2, 0, desc, .moved_locked)); lib$put_output(desc);f  !  ! clean up strings used  !  lib$sfree1_dd(desc); lib$sfree1_dd(desc1);s !b ! and exit !  return ss$_normal;end;end eludom*[KIT]RMS_JOURNAL_SNAP.CLD;1+,. / 4" -X0123KPWO 562`a7ࡔ`a89GHHJ module RMS_JOURNAL_SNAPdefine verb jnlsnap image rms_journal_snap! parameter p1, label=input_file, prompt="Input_File", value(type=$file, required)" parameter p2, label=output_file, prompt="Output_File", value(type=$file,required)*[KIT]RMS_JOURNAL_SNAP.EXE-AXP;1+,=./ 4-X0123 KPWO562`a75`a89GHHJ h(_a0Ƿ_aRMS_JOURNAL_SNAPV1.0A11-14$ $ $J$( 4 LIBRTL_0014& LIBOTS_001@]|ESYS$PUBLIC_VECTORS_001JAN-FEB-MAR-APR-MAY-JUN-JUL-AUG-SEP-OCT-NOV-DEC-.RMS$JOURNAL!/ RMS_JOURNAL_SNAP !AC (built !%D)!/INPUT_FILE!AD.RMS$JOURNAL-SNAP_!AD-!2ZB-!AD_!ADOUTPUT_FILECopied from !ADto !AD!UL record!%S moved during pass 1 (file not locked)!UL record!%S moved during pass 2 (with file locked)@> ף` p 00`  XP ` `0 @0 P00 0X  0 #'~0#^G^G~G (0޴8@H>P^XGG>C8B0"BZkGG8B"BZkGG8B"BZkGG8B"BZkGG8B"BZkGG8BH"BZkGG8BP"BZkGG8B"0=BZkG&x"tݲp!?H=}"],! 0=`"1?J4}2_Jݦ}X1"PB== ]!?"=?$_'6Jb! 2GJ17&JzG0 J}!$H"P"QBݶ=B=0"}}#"=5WJݲ?$}4J(]1?JB'D1"=2_J{# }8R""(],"H=0J5wJ="B8!?HPݦ&P]`"D=5@H=`}#L} #;fKh=0JZFBP]'p={#6J!-H;dK"T]P";@Pݶ 'T}"`_":YKh=2wDJ?FbRC_#0J:wFK(Bp=Bt}G5JH"xݲ:WKxBD"]"ݲ ?$P}"}GGG'7H! Gq~Zk&_&G` "h=GBG Hb!>H@`2@d"h=h]"lĢ@@@{Zk4G(BG0bwZkHBh"Pb4GmZk$ G= B!@"}"᳨"GbGGGCAZk4G(B0bGwZk4G0vH(B0bwZkTG="4GPD BGGbGi@Zk ("4G(B0bwZkGTG4 b#"h="TG_@4G(B0bGwZkh4GBqH0Hl=bF="@Zk&" =(]"(B4GpH0b,=G(G}qwZk&"D &(B ]"=4GpH0bs"$= G_wZkhBpb"4GZ@Zk&"=]"(B4GpH0b=GG}IwZkBbp="GGGG~Zk4G(B0bG;wZkxDDD@x]_"}6Jx=G2_J3wJt J=_R"]vB}4G_C#}ZC Z# [G@0C@C0 CD0CAC0 C!;D 0CDC0 CD0C"0 Cø==@"G]#^x= }#Bp J"TG>G >h]"(~GbGGzZk4G(BG0bvZkGtGh "b#`="TG@4G(BG0bvZk@Ghh=Gl}H`]GD @}L1v J``2v@J1%Jd=5J2DJ5F3K2F=|=P"4GHD @C @zGBbtHtF`Zk&"G PT=]"(B4GpH0b=GX}\vZkhB"pb4GZk&"G PT=]"(B4GpH0b =G}vZkHB"Pb4G]Zk4GG0D(=2vJB"0=R HbsS H=SF=PZktG= (B]G0bbvZk0@==?%z)!D tG]@(B]G0bNvZkXB"`b4GEZktG(BG]0b?vZk? !'Hp"B H3fJbD=E@"4GOZktG(BG]0b!vZkhBpb"4GZktG(B]G0bvZk "HB4G$H@Pb ~ZktG(BG]0buZk (I HB"Pb4G~Zk4GG00D(=BRI1v>HrSIb"2F=~ZktGXX(B\]G0buZk0@D tG(B]G0buZkG B'wHb"D4G~ZktG(B]G0buZkEHB"Pb4G~Zk4GG 0E@(=2vJB"0=R HbsS H=SF=~~ZktG= (B]G0buZk0@ E tG@(B]G0buZkXBP"`b4Gy~ZktGX=X (BG\]0bsuZkBb"4G~ZktG= (B]G0bduZkB"b4G7~ZktG= (BG]0bUuZkBb"4G(~ZktG= (B]G0bFuZkB"b4G~ZkB"b4Gk~ZkG=] (B0btG1uZk8B"GG@Zk $ =4G$"xB4G)?Ib(I 4 A=AݲXݲ}Zk\$4G(=]!B"0])v>Ib A(}ZktG(B]G0buZk GB"]4GEb~ZktG= (B]G0btZk"XB4G`bD}ZktG]@(BG]0btZkBGb{Zk GGt#!B"]h]"PH=GbxZk4G(BG0btZkHBh"Pb4GjZkGGGHC!B"h]"LPI]bxZk4G(B0bGtZkHBPbh"4GtjZktGGB "h]"bGGxZk4G(BG0btZkHBh"Pb4G]jZk GGGBc ]"}h]"bGmxZk4G(B0bGtZkHBPbh"4GFjZk4GBbh"qZk4GB`"bqZk4GG]]} (0ݤ8@H=P]X`#k0#G~G^G^GG"@Bg~ZktG="pBPBFBxb G$]]"}ZktG`Bhb"0="]"}{ZkG]]#kG#G> @hGG~^G^G~GG8=pB"5~Zk } B$]""D(4 @bG,=GtG}ZktGB"b@="]"J{ZkTG BG(bGPZk4G8}c `=?@B ]"b="tG}Zk} ]=#v`H"v@Hb@` .qHPJF>G]@r.tRHSrJtFr>G]G]} #k. HP JF>r. RHX:$RMS_JOURNAL_SNAP010.A=X[KIT]RMS_JOURNAL_SNAP.EXE-AXP;18S rJtFr>#G> @hGG~^G^G~GGGB"}Zk4G"D t @$=`G]_B BbL]"H="GtG:}ZkH C"4G@G"4G4GBGC4G7G B0"GG}ZkG0 0=("4GB 4C"@4G/B]`8]c `4G/ ݢB B <="b@]"tG|ZkB"bP="]"tGzZkG]]}0#k #G> @hGGGG~^GAG"Q}Zk4GD @$ }B@ݲA"a0="]"tGgzZkG]#k0#G~G^G^GG" B)}ZktG="PB0`BFBXb G$]]"|ZktG@BHb"0="]"?zZkG]]#kTXx@@ (h0`00@`pPp  @LIBRTL@LIBOTS@SYS$PUBLIC_VECTORS*[KIT]RMS_JOURNAL_SNAP.EXE-VAX;1+, $. / 4 -X0123 KPWO 562`a7C`a89GHHJ0D`0205`aRMS_JOURNAL_SNAPV1.0`a05-13  ?! LIBRTL_001JAN-FEB-MAR-APR-MAY-JUN-JUL-AUG-SEP-OCT-NOV-DEC-.RMS$JOURNAL!/ RMS_JOURNAL_SNAP !AC (built !%D)!/INPUT_FILE!AD.RMS$JOURNAL-SNAP_!AD-!2ZB-!AD_!ADOUTPUT_FILECopied from !ADto !AD!UL record!%S moved during pass 1 (file not locked)!UL record!%S moved during pass 2 (with file locked)P [U ZJ Y0y^~Ь V|Wĭ,n,x,x |,nX X ,n`,`,.ͤ06ͤ8,nPPCx,} ,nD͌D͌Џ͐ͬ Ͱ,n`8`8:ͤ<BͤD,nPPЏ  @ 8,nD͘D͘<͜ ЏԭЏԭ<PPV8(~ψ%؟jPPikPЏ||~|~~ PPi %VMSINSTAL-I-RESTORE, Restoring product save set A ...I %VMSINSTAL-I-RELMOVED, Product's r)$RMS_JOURNAL_SNAP010.AX([KIT]RMS_JOURNAL_SNAP010.RELEASE_NOTES;1P?*[# release notes have been moved to SYS$HELP.K * Do you want to purge files replaced by this installation [YES]? y? This installation has provided the following files:I (continued on next page)I 7  - Example 2 (Cont.) Sample Installation0 SYS$COMMON:[SYSEXE]RMS_JOURNAL_SNAP.EXE) SYS$COMMON:[SYSLIB]DCLTABLES.EXE' SYS$COMMON:[SYSHLP]HELPLIB.HLB0 SYS$COMMON:[SYSHLP]RMS_JOURNAL_SNAP.B326 SYS$COMMON:[SYSHLP]BUILD_RMS_JOURNAL_SNAP.COMG %VMSINSTAL-I-MOVEFILES, Files will now be moved to their target directories...H Installation of RMS_JOURNAL_SNAP V1.0 completed at 18:55 9 The AuthorA RMS_JOURNAL_SNAP was written by Norman J. LastovicaD of Digital Equipment Corporation, US Digital Services,. % Colorado Springs, Colorado, USA. 8!*[KIT]RMS_JOURNAL_SNAP_BUILD.COM;1+,3./ 42j-X0123KPWO562`a7``a89GHHJ0$ bliss/debug/optimize/list rms_journal_snap.b322$ link/notrace/map/full/cross rms_journal_snap.obj$!#$ if f$getsyi("hw_model") .gt. 1023$ then$ platform = "AXP"$ else$ platform = "VAX"$ endif$!-$ rename rms_journal_snap.map .map-'platform'-$ rename rms_journal_snap.exe .exe-'platform'-$ rename rms_journal_snap.lis .lis-'platform' 1l/$RMS_JOURNAL_SNAP010.Ao &7thkzbE_NOTES;1P=8`=?f<YHv%K8/EUu<'+|]W@yQN/k4Ph s5c&zQܕ5C,DyQ,G P֧3/)ZI,/B /Ü# fCXt\m7xav|t&"ENlU~ wH H5OnPN"I[_n4 cWNPi]N5w!--d#cWu)vV~q~H@a3? EL N4$>g# 8lfV+VO~U'0( dD$GsZgcj48Nm=2{Z.4?q;V#DܶbJU?_p -4.ՅTf 8 :s ";![F:+#GYٷ2}*"_J{=ӓeyO_N. t[;" 6#o%iU44a4P'loJhZf@gp%\& :ZR ?&qO%>tEa~B?n7$$N}r]S]h(5OlTzo?mc3J{w'P5} ߞɄ$(Eͺ'hq?]i2=fZ)ch i^kLEŻCI8/k\:,t;XqR~NTQYW7V_~\Wp,|_#&3C+r= 2`W˺}F2"Xr ~W{glcD6jU#&YKulbR8 `]b50n&gci]}$}sy[C1c2$ H =fHq%dC;UjZVc0@(_ Gd@hI= "H5YVai~vJ _Z3!W&Is6*aH PT)]!(j GdRz]_PcotXX [=fn*1` v!2?I49bh JGBRls't(G3#TAT<t ?0!H:<rL}!s3C1{c^/j(:\gpOW.H7A9h!A0vH%H]&,RYu J t'>56af*b_$Sy H0 uE\m8zbgx[+=S$&tWakakF\vePKI}KRS$8v`4hr|jFZD,ce#@O(~Zm (5TY5wJuS+uEP99ne{<,#QEMHwzB?TNX_L V.xq\xZ*7k~%J ZVdPX.6rD nJLc6)eBF!F?loZPoFj~_2TzN|pp[BfY9]W=r3](lW7IK[L (`JJ' $j%"%0Q@="guY5JGH?/m$^F1fRi9A 0K_Q&g ~ɢtXz-72p*@ho}|W7}%OKqCrm80=\NBκBS[F:9:Glq:N(`iWn[:\ * 4j2zfBmI]a$CU!..H#&[<P8E7QJV7kI%:hPw*oEk+maUbI}EFJ@PUsWڻ$$qke>}ve4V- K?ltfh $"$ ;12M25?W$f51)DZ~mOuS`#[YOo qfjQj#d/s3Ɛӌ샘1bjߏŕǑ̝§홈ػŸݐ놥Ȕ߈‹ϑW딑ɣ薾⽞Br3 (-7cPpEx#`4 P)a^Q#M]q^dX>V@+ZnZ%<)E7.gdKEZPwuk|@C\nLh |!T+Hj!K]aFdC JqdLҦ˵H֦ú۩ӵΔ鯃օ婹㽞選Ǜӡ񕯵ވ廦婖ȊϹ؉Ƌ͗ャԋթěꉟνϨޖҌȍچռǫͻܷދӀЄຍrJ 'xCu;$^$TIX\2} 6U^%=84E"89"X%~ ;:Cq a]:Lryk4(W HL^cXvAq/ [u_#(a0'Ho Tzmn%W, j t{{q8g7zA@JV\G6nO LhG6ڝ1_[(,iaul&ΥrD%7ՀZ۱es6̔A?UK/߰Iĭ֙0q8oW\eSñgڄ$椕4c }E=5ܧtߙobi{сbiDX9ujRrLekzU僉KOVg|UgmGQ rQַZ_̉ʜ⇹ lx#Xqp:͗QH ϬsSGsݤe˭;ĊC? LUQ֦V!El!ϯ ݘV z|44QjHe ǺN`Cv͎->m0b^ '<%m-lr_/P:|v*ɻPS:#_]<ܖ⎻е?]w 7tPuڍN܃׿ʗY6`(/{ߏevdȐ} "ܣ\Ųs4aCܘPpnĤ =͂Ĩf0iCV'8O l>.'z҇6ORÁnꔏK aB1$rغ2<[Ym_(dBœ"[ŧE-X5PhʥRTq(?p+iս(IKAS!6d0UZȖNiƤ#t1d7*7_ļ.;;BZ JSnz6ٝlb=`Qc׉I ˆз@0>|@R('n,IXn*ߟp_ 5;s&iְCFAfwӈԍ [{ҍU;쪭~u}qCwD`buoS̠CPvػ)N3Zp]ExNn4(!#)* P%>A-wSj($!k\S}0/BH]h~rοι&ׄ?EP&G_Y\ing֏@X%\N-RxoC~lT߱*Suj.De-VҜ,?P$b76@Py zˌh(A Sť n6 fa\ɶCx^STvVk+c8 ˼?\RPJ |V %<2'#`AΉW{Ge_pLFQ+@: $Z깷L$;R(๹3y'%_Ѫc :H81kSWHS[$\򄄛3A xuPt8w ='><>I^FG?ژ/r9t*!njv0' OE\6QLr+{8!y,6y{O.o2)_Pq(1HlQGa^_t?0r4_#c)G nػ;+X\yfBH2R%xZ|50StD}Ig3pX[iHVI=[QpicH}T%Ӥ.nQ]Wש,eF#- O2}cl74Z6_v .JXt1VgAdX\|x%,* @_#Lb&Rn#| @}@Ĵpr}s^q7Ms([m9(װD`P\U>.|͔yHIv2׌JîM׍h0g(M@\/>sMBxt'2>b݋)韖Ī8E1+uO 4j ^S  ?@ ]GWL^n.yO~~Aoa t,6^ (遐;Lhe5,?1Mُ-)v-M-鬿TSlf/7( FWs1qy' ,j_Vn] I'+12H2Gb˽QpֳN(KrF;*/"ȻP;i ɯԢ !#\ T< x)^Ο ֐3иE {'կkGϿTpaUjxl}szX δWn c<<7A85#EIc6{)]zMj@ UzKsdI,d79Qz?O{Q>ZA..["o-O)2Bv1-/(8V:GGHI=]6%N1X5 cFi hjcT&Ns/:iy4>a HJ pL2"~?&x ]haPhHwze侯^[rp8j^S/]*" e*(t.>g0@ByKpg e9`X.`Y*P$s HbP{ K>'zWHv,J nMlFatou(V1ma};iG{a9ȴYZ *lV9]=ZeGur=`4ϖ#L+lkHY:l\_#t(m7_k(Sogqvmh Œ?PT,.]t tGlf=Q exH!k#37!*,d&TSrO Cl aCvF9m3sdbV`-8[4~xIf01f$"o'j\\ !UYv>~%$Zt9kQtBo-_+rS]V0o{L*h68mM>pv.\j,N"1*&S`H vgY`$TT@B_M؉Y㇄"5'.zqvF pmFEu0YS*3^[|`4 B+Ux$ 9ci(;CqE,,1[ 1>z!Z}FDu,3Zs9W]ug$ntrF6#bjs*=u]_SSM* =IN!lQ>cJk-\M5I5DCvWm=[_ߴ)<_{4FlcVpbN_zfIO%<&3s7]:)-^MSZ.\bx0HyX"Rn`+z 0L}[@ 8 l~Y.Ow>i)zp:-KpI {n-گ%u*,&lAY`O 74?whJ+,B PƏh] , +R\NGN{*<"u'zm y 24|L,M\ ;8yxnd †Lf)2rv%wq%]?? yhm66 (X)G;:I0d=r AQ8"n|:'w&ɴF:y uFX2d PW/zb/!;knPGNpwQƟ y'&Cg[+$K_(R t@V'@)<7-f(s=e*cyK&Z>c0q})!mn!Q 53c3r;< }~(WuDz' m2^FaTFj'e8GeI"U,p%,oNˎL|BH9pLQ=ѸawO,b~@1A,'}[/4F aio@!*x>~pDSrV ; 6tO6U,%9/ -Y&dS%e.6f0yZJ*nSMK%}`h%TYL^8-^>D8Rj0h1>6ow ^?]Tyz{"lQVdI=a)r<s[[kln=_W\k+r%bB'/eEBl"Qa~eb}U@mrdFt e],2ߝ}- }<H:Sg2lK!"F6 EDtk:p(/Ltm 3 =q ~  ݍn@RV"|. 1hgБWjj27)p*${?HM,U@mbRdJliy*Yi}U]&4^B{!hR/n|^5>yHpt +hj.x^q@fl$ /-c}D>0˟ DV g(3CpQeis[*ZXBގ/qcKF}6²2*1\p"Yf;v-u/ʭ\i86}ʉG6}u "9FaeUA L zhvrs3l'`F4[ N'?4|J*oqa$NLo@[A8SG hY6؍l--XTj>uB %|'`-$.FA,DB6tY.tEKw$L@ t1.-'nC0O&d2O`mhFjk2KW_K51yՠMl[=Upe%}"]%@ gY kZ" a>I02uQWtc*W% >^ =i\Op)#qO18nÊKHHkQ Mg< 6D\V7Mz wD[|›ODgJ~ ( .W_UJa^q/.SpodpљY[SYJ/bf!׋Rǒ߆ q0lPN\ eLiFYÇ6y[/E aB ߏf_n0ΏTm", ^V@Itp8?oHZEot7cF7mA.5B`L}X/Ua_P^^jJ#BMO{($Eptc?bEd.zN3]X}a=D*GDsW8 %Tz>2RCD'"s6 *:q# VGJ6:kEBW~.r}Y`29uj[PUI~e%:k$Q:m+BnzDO2Ngcb3 ƟN:.9F=NpL)DXXVLm@L_gXOVED, Product's