summaryrefslogtreecommitdiff
path: root/v4.0/src/CMD/RESTORE/RTOLD1.C
diff options
context:
space:
mode:
Diffstat (limited to 'v4.0/src/CMD/RESTORE/RTOLD1.C')
-rw-r--r--v4.0/src/CMD/RESTORE/RTOLD1.C657
1 files changed, 657 insertions, 0 deletions
diff --git a/v4.0/src/CMD/RESTORE/RTOLD1.C b/v4.0/src/CMD/RESTORE/RTOLD1.C
new file mode 100644
index 0000000..25df45c
--- /dev/null
+++ b/v4.0/src/CMD/RESTORE/RTOLD1.C
@@ -0,0 +1,657 @@
1
2/*-------------------------------
3/* SOURCE FILE NAME: RTOLD1.C
4/*-------------------------------
5/*  0 */
6
7#include "rt.h"
8#include "rt1.h"
9#include "rt2.h"
10#include "restpars.h" /*;AN000;4*/
11#include "string.h"
12#include "dos.h" /*;AN000;2*/
13#include "comsub.h" /* common subroutine def'n */
14#include "doscalls.h"
15#include "error.h"
16#include "stdio.h"
17
18extern BYTE rtswitch;
19extern BYTE control_flag;
20extern BYTE control_flag2;
21extern char far *buf_pointer;
22extern unsigned src_file_handle;
23extern struct FileFindBuf filefindbuf;
24extern struct FileFindBuf dfilefindbuf;
25BYTE src_fname[MAXFNAME];
26extern struct subst_list sublist; /*;AN000;6 Message substitution list */
27extern char response_buff[5]; /*;AN000;6*/
28struct file_header_old fheadold; /*;AN000;*/
29
30/***************** START OF SPECIFICATION ********************************
31/*
32/* SUBROUTINE NAME : pathmatch
33/*
34/* DESCRIPTIVE NAME : Compare two paths and return TRUE or FALSE
35/* according to whether they match or not.
36/*
37/* NOTES: Global characters * and ? are meaningless in the file path name
38/* Assume both path pattern and path subject are not end with \
39/*
40/* INPUT: (PARAMETERS)
41/* subject - the file path to be compared.
42/* pattern - the file path to be compared against.
43/*
44/********************** END OF SPECIFICATIONS *******************************/
45WORD pathmatch(patterns,subjects)
46
47BYTE *patterns; /* the string to be matched with */
48BYTE *subjects; /* the string to be matched */
49{
50 BYTE *pattern; /* the working pointer to point to the pattern */
51 BYTE *subject; /* the working pointer to point to the subject */
52 int z;
53
54 /*save the pointers to both strings*/
55 pattern = patterns;
56 subject = subjects;
57
58 /* loop until matched or unmatched is determined */
59 for (;;)
60 {
61 if (*pattern == *subject)
62 {
63 if (*pattern != NULLC) /* not finish scanning yet*/
64 {
65 pattern+=1; /* advance the pointer by 1 */
66 subject+=1; /* advance the pointer by 1 */
67 continue; /* continue on comparing again */
68 }
69 else
70 return(TRUE);
71 }
72 else
73 { /* if subject is longer than pattern and SUB flag in rtswitches is on */
74 if (set_reset_test_flag(&rtswitch, SUB, TEST)==TRUE)
75 {
76 if ((*pattern == NULLC && *subject == '\\') ||
77 (patterns[0] == '\\' && patterns[1] == NULLC))
78 return(TRUE);
79 else
80 return(FALSE);
81 }
82 else
83 return(FALSE);
84 }
85 }
86 return(TRUE); /*;AN000;*/
87}
88
89/***************** START OF SPECIFICATION ********************************
90/*
91/* SUBROUTINE NAME : fspecmatch
92/*
93/* DESCRIPTIVE NAME : Compare two file spec. and return TRUE or FALSE
94/* according to whether they match or not.
95/*
96/* FUNCTION: This subroutine compare the file names and file extensions
97/* to determine whether they are match or not.
98/* TRUE is returned if they are match, otherwise, FALSE
99/* is returned.
100/*
101/* NOTES: * and ? are acceptable in the file name and file extension.
102/*
103/********************** END OF SPECIFICATIONS *******************************/
104fspecmatch(patterns, subjects)
105char *patterns;
106char *subjects;
107{
108 char *pattern;
109 char *subject;
110 int z;
111
112 pattern = patterns;
113 subject = subjects;
114
115 for (;;)
116 {
117 if (*pattern == '*')
118 {
119 /*advance pointer in pattern until find '.' or nullc*/
120 for (;*pattern != '.' && *pattern != NULLC; ++pattern);
121 if (*pattern == NULLC)
122 {
123
124 /* pattern has no extension, so make sure subject doesn't either */
125 /* find end or '.' in subject */
126
127 for (;*subject != '.' && *subject != NULLC; ++subject);
128
129 if (*subject == NULLC || *(subject+1) == '.')
130 return(TRUE);
131 else /* subject has extension, so return FALSE */
132 return(FALSE);
133 }
134 else
135 {
136 if ( *(pattern+1) == '*')
137 return(TRUE);
138 else
139 {
140 /*advance pointer in subject until find '.' or nullc*/
141 for (;*subject != '.' && *subject != NULLC; ++subject);
142 if (*subject == NULLC )
143 {
144 if (*(pattern+1) != NULLC)
145 return(FALSE);
146 else
147 return(TRUE);
148 }
149 else
150 {
151 pattern+=1;
152 subject+=1;
153 continue;
154 } /*end of if *subject is not NULL*/
155 } /*end of if *(pattern+1) is not '*' */
156 } /*end of if *pattern == NULLC */
157 }
158 else
159 {
160 if (*pattern == *subject || *pattern == '?')
161 {
162 if (*pattern != NULLC)
163 {
164 pattern+=1;
165 subject+=1;
166 continue;
167 }
168 else
169 return(TRUE);
170 }
171 else
172 if (*pattern == '.' && *(pattern+1) == '*' && *subject == NULLC)
173 return(TRUE);
174 else
175 return(FALSE);
176 }
177
178 } /*end of for loop*/
179
180} /*end of subroutine */
181
182/***************** START OF SPECIFICATION ********************************
183/*
184/* SUBROUTINE NAME : switchmatch
185/*
186/* DESCRIPTIVE NAME : Check the file attributes, and/or file modes
187/* against the switches set in the input command
188/* line.
189/*
190/* FUNCTION: this subroutine search the hard disk for the dest
191/* file first. If dest file is found, the attributs of the
192/* destination file will be used for checking.
193/*
194/* Check the switches set in the input command line one by
195/* one, whenever a switch not match is found, FALSE is returne
196/* In the case a switch is match, TRUE is not returned until al
197/* switches is checked.
198/*
199/*
200/********************** END OF SPECIFICATIONS *******************************/
201WORD switchmatch(finfo, srcd, destd, td)
202struct file_info *finfo;
203BYTE srcd;
204BYTE destd;
205struct timedate *td;
206{
207 WORD yy;
208 WORD mm;
209 WORD dd;
210 WORD hh;
211 WORD mn;
212 WORD ss;
213 WORD action;
214 unsigned file_pointer;
215 WORD retcode;
216 int z;
217
218 /*declaration for dosqfileinfo*/
219 struct FileStatus fileinfo_buf;
220 WORD destdnum;
221 WORD buflen = sizeof(struct FileStatus);
222 unsigned attributes;
223
224 /*declaration for dosfindfirst */
225 unsigned ddirhandle = 0xffff;
226 unsigned attribute = NOTV;
227 unsigned search_cnt = 1;
228 unsigned buf_len = sizeof(struct FileFindBuf);
229 BYTE search_string[MAXPATHF+2];
230 /*end decleration for ffirst and fnext*/
231
232 /***********************************************************************/
233 /* Search hard file for the path and name of file about to be restored */
234 /* and get the file information of the file on the hard disk */
235 /***********************************************************************/
236 search_string[0] = destd;
237 search_string[1] = ':';
238 search_string[2] = NULLC;
239 strcat(search_string, finfo->path);
240 if (strlen(finfo->path) != 1)
241 strcat(search_string, "\\");
242 strcat(search_string, finfo->fname);
243
244 retcode = DOSOPEN( (char far *)&search_string[0],
245 (unsigned far *)&file_pointer,
246 (unsigned far *)&action,
247 (DWORD)0, /*file size*/
248 0, /*file attribute*/
249 0x01, /*if file exist, open*/
250 /*if file not exist, fail*/
251 0x00c0, /*deny write, read write access*/
252 (DWORD)0 ); /*reserved*/
253 /***********************************************************************/
254 /*if open fail (means the file does not exist on the hard disk), then */
255 /* return true */
256 /***********************************************************************/
257 if (retcode != NOERROR) {
258 /*set flag CREATIT*/
259 set_reset_test_flag(&control_flag,CREATIT,SET);
260 /*return TRUE*/
261 return (TRUE);
262 }
263 /*********************************************************************/
264 /* call DosQFileInfo: Request date and time of the dest file */
265 /*********************************************************************/
266 retcode = DOSQFILEINFO (
267 (unsigned)file_pointer, /* File handle */
268 (unsigned)1, /* File info data required */
269 (char far *)&fileinfo_buf, /* File info buffer */
270 (unsigned)buflen); /* File info buffer size */
271
272
273 if (retcode != NOERROR) {
274 com_msg(retcode);
275 unexperror(retcode);
276 }
277
278 if ((retcode = DOSQFILEMODE((char far *)&search_string[0],
279 (unsigned far *) &attributes,
280 (DWORD) 0)) !=0) {
281 com_msg(retcode);
282 unexperror(retcode);
283 }
284
285
286 DOSCLOSE(file_pointer);
287 /***********************************************************************/
288 /*if NOTEXIST flag is on */
289 /***********************************************************************/
290 if (set_reset_test_flag(&rtswitch,NOTEXIST,TEST) == TRUE) {
291 return(FALSE);
292 }
293
294 /***********************************************************************/
295 /*if BEFORE or AFTER is on, convert date into integer form */
296 /***********************************************************************/
297 if (set_reset_test_flag(&rtswitch,BEFORE,TEST) == TRUE ||
298 set_reset_test_flag(&rtswitch,AFTER,TEST) == TRUE ) {
299 /*convert the input date into correct numbers.*/
300 /*Both new and old format have date in the form of date returned from*/
301 /*ffirst*/
302 /*the input date is in the form of: yyyyyyymmmmddddd*/
303 yy = (fileinfo_buf.write_date >> YRSHIFT & YRMASK) + LOYR;
304 mm = fileinfo_buf.write_date >> MOSHIFT & MOMASK;
305 dd = fileinfo_buf.write_date & DYMASK;
306 }
307 /*endif*/
308
309 /***********************************************************************/
310 /*if BEFORE flag is on */
311 /***********************************************************************/
312 if (set_reset_test_flag(&rtswitch,BEFORE,TEST) == TRUE) {
313 if ( yy > td->before_year ) {
314 return(FALSE);
315 }
316
317 if (yy == td->before_year && mm > td->before_month) {
318 return(FALSE);
319 }
320
321 if (yy == td->before_year && mm == td->before_month &&
322 dd > td->before_day) {
323 return(FALSE);
324 }
325 }
326 /*endif*/
327
328 /***********************************************************************/
329 /*if AFTER flag is on */
330 /***********************************************************************/
331 if (set_reset_test_flag(&rtswitch,AFTER,TEST) == TRUE) {
332 if (yy < td->after_year ) {
333 return(FALSE);
334 }
335
336 if (yy == td->after_year && mm < td->after_month) {
337 return(FALSE);
338 }
339
340 if (yy == td->after_year && mm == td->after_month && dd < td->after_day) {
341 return(FALSE);
342 }
343 }
344 /*endif*/
345
346 /***********************************************************************/
347 /*if EARLIER or LATER is on, convert date time into integer form */
348 /***********************************************************************/
349 if (set_reset_test_flag(&rtswitch,EARLIER,TEST) == TRUE ||
350 set_reset_test_flag(&rtswitch,LATER,TEST) == TRUE) {
351 /* convert the input time into correct numbers. */
352 /* Both new and old format have time in the form of date returned */
353 /* from ffirst. */
354 /* the input time is in the form of: hhhhhmmmmmmsssss */
355 hh = fileinfo_buf.write_time >> HRSHIFT & HRMASK;
356 mn = fileinfo_buf.write_time >> MNSHIFT & MNMASK;
357 ss = fileinfo_buf.write_time & SCMASK;
358 }
359 /*endif*/
360
361 /***********************************************************************/
362 /*if EARLIER flag is on */
363 /***********************************************************************/
364 if (set_reset_test_flag(&rtswitch,EARLIER,TEST) == TRUE) {
365 if (hh > td->earlier_hour) {
366 return(FALSE);
367 }
368
369 if (hh == td->earlier_hour && mn > td->earlier_minute) {
370 return(FALSE);
371 }
372
373 if (hh == td->earlier_hour && mn == td->earlier_minute &&
374 ss > td->earlier_second) {
375 return(FALSE);
376 }
377 }
378 /*endif*/
379
380 /***********************************************************************/
381 /*if LATER flag is on */
382 /***********************************************************************/
383 if (set_reset_test_flag(&rtswitch,LATER,TEST) == TRUE) {
384 if (hh < td->later_hour) {
385 return(FALSE);
386 }
387
388 if (hh == td->later_hour && mn < td->later_minute) {
389 return(FALSE);
390 }
391
392 if (hh == td->later_hour && mn == td->later_minute &&
393 ss < td->later_second) {
394 return(FALSE);
395 }
396 }
397 /*endif*/
398
399 /*************************************************************************/
400 /* if Revised flag is on and fileinfo->attrib indicate file has not */
401 /* been Revised, return FALSE */
402 /*************************************************************************/
403 if (set_reset_test_flag(&rtswitch,Revised,TEST) == TRUE) {
404 if((retcode = attributes & 0x0020) != 0x0020) {
405 return(FALSE);
406 }
407 }
408 /*endif*/
409
410 /***********************************************************************/
411 /* if PROMPT and fileinfo->file_attrib indicate READONLY, or CHANGED*/
412 /***********************************************************************/
413 if ((set_reset_test_flag(&rtswitch,PROMPT,TEST) == TRUE) &&
414 (((retcode = attributes & 0x0001) == 0x0001) ||
415 ((retcode = attributes & 0x0020) == 0x0020) ))
416 {
417 /*call subroutine to ask whether the user really wants to restore */
418 retcode = readonly_or_changed(attributes,destd,finfo->fname,finfo->path);
419 if (retcode == FALSE) {
420 return(FALSE);
421 }
422 /*endif*/
423 }
424 /*endif*/
425
426 /***********************************************************************/
427 /* if pass all the switch testing, return TRUE */
428 /***********************************************************************/
429 return(TRUE);
430
431} /*end of subroutine switch_match */
432
433/***************** START OF SPECIFICATION ********************************
434/*
435/* SUBROUTINE NAME : check_flheader_old
436/*
437/* DESCRIPTIVE NAME : Check the information in the file header of
438/* the file to be restored.
439/*
440/* FUNCTION: For old format only, Open the file to be restored, get
441/* header informtion
442/*
443/*
444/********************** END OF SPECIFICATIONS *******************************/
445int check_flheader_old
446 ( finfo,f_name,f_date,f_time,f_attrib,f_len,
447 file_seq_num,srcd,destd,infspec,inpath,dnumwant
448 )
449
450 struct file_info *finfo;
451 unsigned char *f_name; /* name string */
452 unsigned f_date; /* file's date */
453 unsigned f_time; /* file's time */
454 unsigned f_attrib; /* file's attribute */
455 unsigned long f_len; /* file length */
456 unsigned int file_seq_num;
457 BYTE srcd;
458 BYTE destd;
459 BYTE *infspec;
460 BYTE *inpath;
461 unsigned int *dnumwant;
462{
463 WORD temp_dnumwant;
464 WORD numread;
465 WORD action;
466 BYTE file_to_be_opened[15];
467 BYTE string_to_be_separate[79];
468 BYTE path[65];
469 BYTE name[9];
470 BYTE ext[4];
471 BYTE spec[13];
472 WORD i; /*loop counter*/
473 WORD retcode;
474 int z;
475
476 temp_dnumwant = *dnumwant; /*to fix a bug that dosread change the
477 value of dnumwant */
478
479
480 /***********************************************************************/
481 /*open the file to be restored as deny write and read access */
482 /***********************************************************************/
483 strcpy(src_fname,f_name);
484 file_to_be_opened[0] = srcd;
485 file_to_be_opened[1] = ':';
486 file_to_be_opened[2] = NULLC;
487 strcat(file_to_be_opened,f_name);
488 retcode = DOSOPEN( (char far *)&file_to_be_opened[0],
489 (unsigned far *)&src_file_handle,
490 (unsigned far *)&action,
491 (DWORD)0, /*file size*/
492 0, /*file attribute*/
493 0x01, /*if file exist, open it*/
494 /*if file not exist, fail it*/
495 0x00c0, /*deny write, read only*/
496 (DWORD)0 ); /*reserved*/
497
498 /*if open fail*/
499 if (retcode != 0) {
500 /****not able to restore the file****/
501 display_it(NOT_ABLE_TO_RESTORE_FILE,STND_ERR_DEV,0,NO_RESPTYPE,(BYTE)UTIL_MSG); /*;AN000;6*/
502 unexperror(retcode);
503 }
504 /*endif*/
505
506 /***********************************************************************/
507 /*read 128 bytes header information from the file into fheadold */
508 /***********************************************************************/
509 retcode = DOSREAD( src_file_handle,
510 (char far *)&fheadold,
511 HEADLEN,
512 (unsigned far *)&numread);
513 /*if read fail*/
514 if (retcode != 0 )
515 {
516 display_it(NOT_ABLE_TO_RESTORE_FILE,STND_ERR_DEV,0,NO_RESPTYPE,(BYTE)UTIL_MSG); /*;AN000;6*/
517 unexperror(retcode);
518 }
519 /*end of if read fail */
520
521 /*if the number of read is less than HEADLEN, return FALSE */
522 if (numread != HEADLEN)
523 return(FALSE);
524
525 /* save disk number */
526 finfo->dnum = fheadold.disknum[1]* 10 + fheadold.disknum[0];
527
528 if (fheadold.wherefrom[0] != '\\')
529 return(FALSE);
530 strcpy(string_to_be_separate,fheadold.wherefrom);
531 separate(string_to_be_separate,path,name,ext,spec);
532
533 /***********************************************************************/
534 /* match the path and file spec. */
535 /***********************************************************************/
536 if
537 ( pathmatch(inpath,path) == FALSE ||
538 fspecmatch(infspec,spec) == FALSE
539 )
540 {
541 *dnumwant = temp_dnumwant;
542 return(FALSE);
543 }
544
545 /***********************************************************************/
546 /*Store some information from filefindbuf into finfo */
547 /***********************************************************************/
548 finfo->ftime = f_time;
549 finfo->fdate = f_date;
550 finfo->attrib = f_attrib;
551 finfo->partsize = f_len;
552
553 /***********************************************************************/
554 /*Store filename and path information from fheadold into finfo */
555 /***********************************************************************/
556 strcpy(finfo->fname,spec);
557 strcpy(finfo->path,path);
558
559 /***********************************************************************/
560 /* store some other information from fheadold to finfo */
561 /***********************************************************************/
562 if (fheadold.headflg == 0xff)
563 finfo->fflag= LAST_PART;
564 else
565 finfo->fflag= 0;
566
567 *dnumwant = temp_dnumwant;
568 return(TRUE);
569
570 /*return nothing*/
571
572} /*end of subroutine*/
573
574
575/***************** START OF SPECIFICATION ********************************
576/*
577/* SUBROUTINE NAME : readonly_or_changed
578/*
579/* DESCRIPTIVE NAME : handle the situration that a read only file
580/* or is found, or the file has been Revised.
581/*
582/* FUNCTION: In the case that a readonly file is found, or the file
583/* on the destination disk has been Revised since last backup,
584/* this subroutine output a warning message to the user, and
585/* prompt for user to enter yes or no depending on whether
586/* the user wants to proceed restoring the file.
587/*
588/*
589/********************* END OF SPECIFICATIONS ********************************/
590#define CHECK_YES_NO 0x6523 /*;AN000;6*/
591#define YES_NO_RESPTYPE 0xc1 /*;AN000;6*/
592#define YES 1 /*;AN000;6*/
593
594int readonly_or_changed(attrib,destd,fspec,fpath)
595
596 unsigned attrib;
597 unsigned char destd;
598 unsigned char *fspec;
599 unsigned char *fpath;
600{
601
602 union REGS inregs, outregs; /*;AN000;6 Register set */
603 WORD retcode;
604
605 char file_to_be_chmode[MAXPATHF+2];
606 DWORD dw = 0L;
607 int z;
608
609 sublist.value1 = (char far *)fspec; /*;AN000;6 */
610 sublist.flags1 = LEFT_ALIGN + CHAR_FIELD_ASCIIZ; /*;AN000;6 */
611 sublist.max_width1 = (BYTE)strlen(fspec); /*;AN000;6 */
612 sublist.min_width1 = sublist.max_width1; /*;AN000;6 */
613
614 /***********************************************************************/
615 /* if readonly, output msg and wait for user's prompt */
616 /***********************************************************************/
617 do /*;AN000;6*/
618 { /*;AN000;6*/
619 if((retcode = attrib & 0x0001) == 0x0001)
620 display_it(FILE_IS_READONLY,STND_ERR_DEV,1,YES_NO_RESPTYPE,(BYTE)UTIL_MSG); /*;AN000;6*/
621 else
622 display_it(FILE_WAS_CHANGED,STND_ERR_DEV,1,YES_NO_RESPTYPE,(BYTE)UTIL_MSG); /*;AN000;6*/
623
624
625 inregs.x.ax = (unsigned)CHECK_YES_NO; /*;AN000;6*/
626 inregs.h.dl = response_buff[0]; /*;AN000;6*/
627 int86(0x21,&inregs,&outregs); /*;AN000;6*/
628 display_it(CRLF,STND_ERR_DEV,0,NO_RESPTYPE,(BYTE)UTIL_MSG); /*;AN000;6*/
629 } /*;AN000;6*/
630 while (outregs.h.al > 1); /*;AN000;6*/
631
632 /***********************************************************************/
633 /* if user's input is 'Y', return TRUE, else return FALSE */
634 /***********************************************************************/
635 if (outregs.x.ax == YES) /*;AN000;6*/
636 { file_to_be_chmode[0] = destd;
637 file_to_be_chmode[1] = ':';
638 file_to_be_chmode[2] = NULLC;
639 strcat(file_to_be_chmode,fpath);
640 if (strlen(fpath) != 1) {
641 strcat(file_to_be_chmode,"\\");
642 }
643 strcat(file_to_be_chmode,fspec);
644 /* change the file attribute to be 0, that is, reset it */
645 if ((retcode = DOSSETFILEMODE((char far *)file_to_be_chmode,(unsigned) 0x00, dw)) != 0)
646 {
647 com_msg(retcode);
648 unexperror(retcode);
649 }
650 return(TRUE);
651 }
652 else {
653 return(FALSE);
654 }
655 /* endif */
656} /* end of subroutine readonly_or_changed */
657