summaryrefslogtreecommitdiff
path: root/v4.0/src/CMD/CHKDSK/CHKDSK1.ASM
diff options
context:
space:
mode:
Diffstat (limited to 'v4.0/src/CMD/CHKDSK/CHKDSK1.ASM')
-rw-r--r--v4.0/src/CMD/CHKDSK/CHKDSK1.ASM682
1 files changed, 682 insertions, 0 deletions
diff --git a/v4.0/src/CMD/CHKDSK/CHKDSK1.ASM b/v4.0/src/CMD/CHKDSK/CHKDSK1.ASM
new file mode 100644
index 0000000..6d85d42
--- /dev/null
+++ b/v4.0/src/CMD/CHKDSK/CHKDSK1.ASM
@@ -0,0 +1,682 @@
1 TITLE CHKDSK - MS-DOS Disk consistancy checker ;
2page ,132 ;
3
4 .xlist
5 include chkseg.inc ;an005;bgb
6 INCLUDE CHKCHNG.INC
7 INCLUDE DOSSYM.INC
8 INCLUDE syscall.inc ;an041;bgb
9 INCLUDE ioctl.inc ;an041;bgb;an041;bgb
10 INCLUDE CHKEQU.INC
11 INCLUDE CHKMACRO.INC
12 include chkdata.inc ;an005;bgb
13 include pathmac.inc
14
15CODE SEGMENT PUBLIC PARA 'CODE'
16ASSUME CS:DG,DS:NOTHING,ES:DG,SS:dg
17 EXTRN INT_23:NEAR, readft:near ;an005;bgb
18 EXTRN FATAL:NEAR, PROMPTYN:NEAR, GET_CURRDIR:NEAR
19 extrn calc_fatmap_seg:near, FINDCHAIN:NEAR, CHECKERR:NEAR, DIRPROC:NEAR
20 extrn CHKMAP:NEAR, Main_Init:Near ;an049;bgb
21 EXTRN CHKCROSS:NEAR, AMDONE:NEAR, UNPACK:NEAR, GET_THISEL2:NEAR
22 EXTRN PRINTF_CRLF:NEAR, DOCRLF:NEAR, REPORT:NEAR
23 extrn init_fatmap:near, CHKPRMT_END:near ;an005;bgb
24 extrn hook_interrupts:near
25 extrn CHECK_DBCS_CHARACTER:NEAR ;an055;bgb
26
27public SETSTACK, OkDrive, DRVISOK, Root_CD_Ok, NOTVOLID, fat16b, SMALLFAT
28public BAD_STACK, RDLOOP, NORETRY1, RDOK, IDOK, ALLDONE, CHECKFILES, GotPath
29public IS_ROOT_DIR, NOT_ROOT_DIR, VALID_PATH, ParseName, ScanFile, FRAGCHK
30public EACHCLUS, LASTCLUS, NXTCHK, GETNXT, MSGCHK, FILSPOK, CDONE, CDONE1
31public PRINTID, FIGREC, Main_Routine, checkit
32 .list
33
34
35 pathlabl chkdsk1
36CHKDSK:
37; find out if we have enough memory to do the job
38 mov cs:save_drive,al ;save drive validity
39;;;;int 12h ;1k blocks (640k = 280h) ;an054;bgb;an050;bgb
40;;;;mov bx,64 ;number of paragraphs ;an054;bgb;an050;bgb
41;;;;mul bx ;640k = a000 ;an054;bgb;an050;bgb
42;;;;mov cs:[mem_size],ax ;returns number of 1k blocks ;an054;bgb;an050;bgb
43 DOS_Call GetCurrentPSP ;Get PSP segment address ;Ac034;bgb
44 mov cs:psp_segment,bx ;ac034;bgb
45 mov ds,bx ;ds points to the psp ;Ac034;bgb
46 Assume DS:Nothing
47 MOV DX,DS:[2] ;High break
48 mov cs:[mem_size],dx ;move it into data area ;an054;bgb
49 MOV BX,0FFFFH ;need at least 64k bytes
50 MOV CX,CS ;get segment of where we are
51 SUB DX,CX ;top-of-mem - pgm = # para left in alloc block
52 CMP DX,0FFFH ; is the space available > 64K ?
53; $IF B
54 JNB $$IF1
55 MOV CX,4 ; Yes, set SP to BX (FFF0)
56 SHL DX,CL ; Convert remaining memory to bytes
57 MOV BX,DX
58; $ENDIF
59$$IF1:
60SETSTACK: ;***Set_Memory*********
61 CLI
62 PUSH CS
63 POP SS
64ASSUME SS:DG
65 MOV SP,BX
66 STI
67 PUSH AX
68 JMP Main_Init ;Go to init routines
69
70
71;**************************************************************************
72; MAIN-ROUTINE
73;
74; called by - main-init
75;
76; LOGIC
77; *****
78; - get the dpb addr
79; - set the default drive to here
80; - save the directory we are on
81; - set the directory to the root of the drive
82; - print the volume name
83; - get the dpb info
84; - get the addr of the fatmap area
85; - calculate the amount of stack space we have
86;**************************************************************************
87Main_Routine:
88 set_data_segment
89OkDrive:
90;get the dpb addr from this drive
91 mov dl,AllDrv ;Get drive number ;AN000;
92 DOS_Call Get_DPB ;func 32 ;Get DPB pointer ;AC000;
93 ASSUME DS:NOTHING,cs:DG
94 CMP AL,-1 ;is this a good drive?
95; $IF Z
96 JNZ $$IF3
97;;;;;;;;JNZ DRVISOK ;Bad drive (should always be ok)
98 LEA DX,BADDRV_arg ;This should never happen ;AC000;
99 push cs
100 pop ds
101 call PRINTf_crlf ; ;AC000;
102 mov ExitStatus,Bad_Exit ;Get return code ;AC000;
103 ret ;Go back to Main_Init ;AC000;
104; $ENDIF
105$$IF3:
106 MOV WORD PTR CS:[THISDPB+2],DS ;get the dpb segment
107 set_data_segment ;reset ds to the pgm
108 MOV WORD PTR [THISDPB],BX ;get the dpb offset
109
110;**Set_Drive_Info*************************************************************
111DRVISOK:
112 push dx
113 push es
114 call hook_interrupts
115 pop es
116 pop dx
117; make this drive the default drive
118 DEC DL ;A=0 b=1 c=2
119 DOS_Call Set_Default_Drive ;func 0e - no return ;AC000;
120
121;get the name of the current directory
122 INC DL ;drive number a=1 b=2 c=3
123 LEA SI,USERDIR+1 ; ;AC000;
124 DOS_Call Current_Dir ; ;AC000;
125;;;;PUSH CS
126;;;;POP ES
127
128;change the current directory to the root
129 lea DX,rootstr ; ;an005;bgb
130 DOS_Call ChDir ; ;AC000;
131; $IF C ;will this ever happen?
132 JNC $$IF5
133;;;;;;;;jnc Root_CD_Ok ; ;AN000;
134 MOV DX,OFFSET DG:BADCD_arg
135 call display_interface ; ;AC000;
136 mov ExitStatus,Bad_Exit ;Get return code ;AC000;
137 ret ;Go back to Main_Init ;AC000;
138; $ENDIF
139$$IF5:
140
141;get the dpb info
142 LDS BX,[THISDPB] ;ds:bx--> dpb area
143 ASSUME DS:NOTHING
144 MOV AX,[BX.dpb_sector_size] ;Bytes/sector
145 MOV [SSIZE],AX ;Sector size in bytes
146 MOV AL,[BX.dpb_cluster_mask]
147 INC AL
148 MOV [CSIZE],AL ;Sectors per cluster
149 MOV AX,[BX.dpb_max_cluster] ; number of clusters in the disk
150 MOV [MCLUS],AX ;Bound for FAT searching
151 DEC AX ;ax= max clusters - 1 ;an005;bgb
152 MOV [DSIZE],AX ;Total data clusters on disk ;an005;bgb
153 CMP AX,4096-8 ;Big or little FAT?
154; $IF NB
155 JB $$IF7
156fat16b: INC es:[BIGFAT] ;set 16-bit fat flag to true
157 MOV es:[EOFVAL],0FFF8H ;set 16-bit compare fields for fat
158 MOV es:[CHAIN_END],0FFFFh ;Marker for end of chain ;AC000;
159 MOV es:[BADVAL],0FFF7H ;set 16-bit compare fields for fat
160; $ENDIF
161$$IF7:
162 mov ax,[bx.dpb_FAT_size] ;Sectors for one fat (DCR) ;an005;bgb
163 mov fatsiz,ax ;Sectors for one fat (DCR) ;an005;bgb
164 MOV CL,[BX.dpb_FAT_count] ;Number of FATs ;an005;bgb
165 mov fatcnt,cl ;an005;bgb
166 MOV DX,[BX.dpb_first_FAT] ;First sector of FAT ;an005;bgb
167 MOV firstfat,dx ;First sector of FAT ;an005;bgb
168 MOV DX,[BX.dpb_first_sector] ;First sector of data ;ac048;bgb
169 MOV firstsec,dx ;First sector of data ;ac048;bgb
170 MOV DX,[BX.dpb_dir_sector] ;First sector of dir ;ac048;bgb
171 MOV dirsec,dx ;First sector of dir ;ac048;bgb
172 MOV DX,[BX.dpb_root_entries] ;First sector of dir ;ac048;bgb
173 MOV root_entries,dx ;First sector of dir ;ac048;bgb
174 set_data_segment ;reset ds to point to data area
175
176;calc fatmap area
177SMALLFAT: ;do this for both size fats
178 ;old calculation
179 ;;;;DEC AX ;ax= max clusters - 1 ;an005;bgb
180 ;;;;MOV [DSIZE],AX ;Total data clusters on disk ;an005;bgb
181 ;;;;MOV AX,[BX.dpb_FAT_size] ;Sectors for one fat (DCR) ;an005;bgb
182 ;;;;MOV CX,AX ;CX = Sectors/Fat ;an005;bgb
183 ;;;;MUL [SSIZE] ;times bytes/sector = bytes per fat ;an005;bgb
184 ;;;;ADD fatmap,AX ;Allocate FAT space ;an005;bgb
185 ;;;;MOV AX,fatmap ; get seg of fatmap ;an005;bgb
186
187Root_CD_Ok: ; ;AN000;
188;set dta area----do i need to do this since we are using int 25?
189;set it to fat table
190 call calc_fatmap_seg ;find the addr of where to put the fat map ;an005;bgb
191;see if we still have enough memory
192 mov ax,mem_size ;get top of memory
193 cmp ax,end_of_fatmap ;mem_size must be greater or equal
194; $IF B ; if not, display error msg
195 JNB $$IF9
196 MOV DX,OFFSET DG:no_mem_arg
197 invoke printf_crlf
198 jmp alldone ;finished with pgm
199; $ENDIF
200$$IF9:
201 push ds ;save ds
202 mov ds,fattbl_seg ;get seg
203 xor dx,dx ;ds:dx--> dta area
204;;;;mov fatmap,dx
205 DOS_Call Set_DMA ;function 1a ;AC000;
206 pop ds ;restore ds
207
208;look for volume entry in dir
209 lea DX,volid ;Look for VOL ID ;an005;bgb
210 DOS_Call Dir_Search_First ;function 11 ;AC000;
211 CMP AL,0 ;did we find it?
212; $IF Z ;yes
213 JNZ $$IF11
214;;;;;;;;JZ NOTVOLID
215 CALL PRINTID ;print volume name, date, time
216; $ENDIF
217$$IF11:
218NOTVOLID:
219 call get_serial_num ;print volume serial number ;an024;bgb
220;;;;call hook_interrupts
221; calculate the place where we run out of ram space ;an005;bgb
222;;;;ADD AX,[MCLUS] ;5000 ;fatmap seg + num of clusters? ;an005;bgb
223;;;;ADD AX,2 ;5002 ;Insurance ;an005;bgb
224;;;;MOV [SECBUF],AX ;Allocate fatmap space ;an005;bgb
225 mov ax, offset dg:chkprmt_end ;this label must be the last thing in the code segment
226 mov [secbuf],AX ;location of read/write buffer for dir entries ;an005;bgb
227;;;;ADD AX,[SSIZE] ;5202 ;an005;bgb
228;;;;ADD AX,20 ;5216 ;Insurance ;an005;bgb
229 mov ax,0ffffh ;get end of segment
230 lea bx,fattbl ;get end of program
231 sub ax,bx ;this is the amount of stack space we have
232 MOV [STACKLIM],AX ;Limit on recursion ;an005;bgb
233; see if we have already overrun the stack
234 MOV DI,SP ;where is the stack pointer now? ;an005;bgb
235 SUB DI,100H ; Want AT LEAST this much stack from ;an005;bgb
236 ; our current location ;an005;bgb
237 CMP DI,AX
238; $IF B
239 JNB $$IF13
240;;;;;;;;JB BAD_STACK ; Already in trouble
241BAD_STACK:
242 MOV BX,OFFSET DG:STACKMES ;Out of stack
243 PUSH CS
244 POP DS
245 JMP FATAL
246; $ENDIF
247$$IF13:
248
249;
250;**Read in FAT*****************************************************************
251;;;;MOV DI,fatsiz ;sectors per fat ;an005;bgb
252;;;;MOV CL,[BX.dpb_FAT_count] ;Number of FATs
253;;;;MOV DX,[BX.dpb_first_FAT] ;First sector of FAT
254 mov cx,fatsiz ;number of sectors to read ;an005;bgb
255 mov dx,firstfat ;starting sector number ;an005;bgb
256 mov es,fattbl_seg ;set up bx for read-disk ;an005;bgb
257 xor bx,bx ;an005;bgb
258 MOV AL,[ALLDRV] ;set up al with drive letter for read-disk
259 DEC AL ;zero based
260;;;;MOV AH,1
261RDLOOP:
262;;;;XCHG CX,DI ;DI has # of Fats
263 call readft ; readft (); ;AN005;bgb
264; $IF C ; could the fat be read from disk? ;AN005;bgb
265 JNC $$IF15
266 inc byte ptr [nul_arg] ;an005;bgb
267;;;;;;;;mov [fatal_arg2],offset dg:baddrvm ;an005;bgb
268 mov [fatmsg2],offset dg:baddrvm ;an005;bgb
269 lea BX,badread ;an022;bgb
270 JMP FATAL ;Couldn't read any FAT, BARF ;an005;bgb
271; $ENDIF ;fat could be read from disk ;AN005;bgb
272$$IF15:
273
274; savereg <dx,cx,di,ax> ;an005;bgb
275; mov Read_Write_Relative.Start_Sector_High,0 ; ;AN000;
276; call Read_Disk ;Read in the FAT ;AC000;
277; $IF C
278;;;;;;;;JNC RDOK
279;;;;;;;;mov [badrw_str],offset dg:reading
280; POP AX ; Get fat# in ah
281; PUSH AX ; Back on stack
282; xchg al,ah ; Fat # to AL
283; xor ah,ah ; Make it a word
284; mov [badrw_num],ax
285; mov dx,offset dg:badr_arg
286; invoke printf_crlf
287; restorereg <ax,cx,di,dx> ;an005;bgb
288; INC AH
289; ADD DX,DI
290; LOOP RDLOOP ;Try next FAT
291;;;;;;;;JMP NORETRY1 ;Couldn't read either ;AC000;
292NORETRY1:
293; inc byte ptr [nul_arg]
294; mov [fatal_arg2],offset dg:baddrvm
295; MOV BX,OFFSET DG:BADRDMES
296; JMP FATAL ;Couldn't read any FAT, BARF
297; $ENDIF
298RDOK: ;**Check_for_FAT_ID**********************************************
299;;;;restorereg <ax,ax,ax,ax> ;Clean up ;an005;bgb
300 mov es,fattbl_seg ;segment of fat-table ;an005;bgb
301 xor si,si ;offset of first byte in fat-table ;an005;bgb
302;;;;LODSB ;Check FAT ID byte
303 mov al,byte ptr es:[si] ;get first byte of fat table
304 CMP AL,0F8H ;is it the correct id byte?
305; $IF B,AND
306 JNB $$IF17
307;;;;;;;;JAE IDOK
308 CMP AL,0F0H ;if not, Is it a "strange" medium?
309; $IF NZ
310 JZ $$IF17
311;;;;;;;;jz IDOK ;neither fat nor strange
312 MOV DX,OFFSET DG:BADIDBYT ;FAT ID bad
313 CALL PROMPTYN ;Ask user to stop or not
314; $IF NZ
315 JZ $$IF18
316;;;;;;;;;;;;JZ IDOK
317 JMP ALLDONE ;User said stop
318; $ENDIF
319$$IF18:
320; $ENDIF
321$$IF17:
322
323;initialize the fatmap area to all zeros
324IDOK:
325 call init_fatmap
326
327;set the dta addr to here for all searches
328 MOV DX,OFFSET DG:DIRBUF ;FOR ALL SEARCHING
329 DOS_Call Set_DMA ; ;AC000;
330 XOR AX,AX ;zero out ax
331 PUSH AX ;I am root
332 PUSH AX ;Parent is root
333;
334 set_data_segment
335checkit:
336 CALL DIRPROC
337 CALL CHKMAP ;Look for badsectors, orphans
338 CALL CHKCROSS ;Check for second pass
339 INVOKE DOCRLF ;display new line
340 CALL REPORT ;finished, display data to screen
341
342;*****************************************************************************
343ALLDONE:
344 CALL AMDONE
345;;;;;MOV AH,EXIT
346;;;;;;;;XOR AL,AL
347;;;;;; ;mov ExitStatus,Bad_Exit ;Get return code ;AC000;
348;;;;;;;;INT 21H
349 ret ;Ret to Main_Init for common exit ;AN000;
350
351ASSUME DS:DG
352;**Extent_Check***************************************************************
353Break <Check for extents in specified files>
354;
355; Search the directory for the files specified on the command line and report
356; the number of fragmented allocation units found in each one. We examine the
357; given path name for a directory. If it is found, we CHDIR to it. In any
358; event, we move to the file name part and do a parseFCB call to convert it
359; into an FCB for a dir_search_first. If the parse did NOT advance the
360; pointer to the null byte terminating the string, then we have a bogus anme
361; and we should report it.
362;
363
364CHECKFILES:
365 set_data_segment
366; see if there is a '\' in the path name
367 MOV DI,OFFSET DG:PATH_NAME
368 MOV SI,DI
369 MOV CX, FNAME_LEN ; ;an011;bgb
370 ADD DI,CX ; ES:DI points to char AFTER last char
371 DEC DI ; Point to last char
372doagain: MOV AL,[DIRCHAR] ;try to find '\' in path name
373 STD
374 REPNE SCASB
375 CLD
376; $IF Z ;a '\' was found in path ;an055;bgb
377 JNZ $$IF21
378 mov al,[di] ;get byte preceding '\' ;an055;bgb
379 call check_dbcs_character ;see if dbcs leading char ;an055;bgb
380; $IF C ;carry means dbcs leading char ;an055;bgb
381 JNC $$IF22
382 jmp doagain ;so ignore ;an055;bgb
383; $ELSE ;an055;bgb
384 JMP SHORT $$EN22
385$$IF22:
386 jmp GotPath ;found a '\' and not dbcs ;an055;bgb
387; $ENDIF ;an055;bgb
388$$EN22:
389; $ENDIF ;an055;bgb
390$$IF21:
391;;;;;;;;;;;;;;;;;;;;;JZ GotPath ; found path char. ;an055;bgb
392; No '\' was found. set up pointers for parse FCB call.
393 MOV DI,OFFSET DG:PATH_NAME
394 CMP BYTE PTR [DI+1],':' ;was a drive letter entered?
395 JNZ ParseName
396 ADD DI,2
397 JMP SHORT ParseName
398
399;*****************************************************************************
400; found a '\' in the path name
401;Change directories and set up the appropriate FCB
402GotPath:
403 INC DI ; DI points AT the path sep
404 PUSH WORD PTR [DI] ; Save two chars here
405 PUSH DI ; Save location
406 SUB SI,DI
407 JZ IS_ROOT_DIR ; SI=DI=First char which is a dirchar
408 NEG SI
409 CMP SI,2
410 JNZ NOT_ROOT_DIR
411 CMP BYTE PTR [DI-1],':' ; d:\ root spec?
412 JNZ NOT_ROOT_DIR ; Nope
413IS_ROOT_DIR:
414 INC DI ; Don't zap the path sep, zap NEXT char
415NOT_ROOT_DIR:
416 MOV BYTE PTR [DI],0
417 MOV DX,OFFSET DG:PATH_NAME
418 DOS_Call Chdir ; ;AC000;
419 POP DI ; Recall loc
420 POP WORD PTR [DI] ; recall chars
421 JNC VALID_PATH
422 INVOKE DOCRLF
423 MOV DX,OFFSET DG:INVPATH_arg
424 invoke printf_crlf
425 JMP CDONE1
426
427;*****************************************************************************
428VALID_PATH:
429 INC [DIR_FIX]
430 INC DI ; Point past path sep to first char of name
431ParseName:
432; parse the filename and get back a formatted fcb for it in es:di
433 MOV SI,DI ; DS:SI points to name
434 MOV DI,offset dg:FCB_copy ; ES:DI points to FCB
435 MOV AL,ALLDRV ; drive number
436 STOSB ; put it into fcb
437 DEC DI ; Back to start of FCB
438 MOV pFileName,SI ; save end of file name
439 MOV AL,00000010B ; tell parse to change drive letter if needed
440 DOS_Call Parse_File_Descriptor ; ;AC000;
441 CMP BYTE PTR [SI],0 ;ds:si should point past filename
442 JZ ScanFile
443;
444; Twiddle the file name to be truly bogus. Zorch the drive letter
445;
446 MOV BYTE PTR es:[DI],-1
447ScanFile:
448 INVOKE DOCRLF
449;set dma pointer to here
450 MOV DX,OFFSET DG:DIRBUF ;FOR ALL SEARCHING
451 MOV BP,DX
452 ADD BP,27 ;bp points to clus in the dir entry
453 DOS_Call Set_DMA ;set dma ptr here for dir search ;AC000;
454;try to find the file specified
455 MOV AH,DIR_SEARCH_FIRST ;Look for the first file
456FRAGCHK:
457 MOV DX,offset dg:FCB_copy
458 INT 21H
459 OR AL,AL ;Did we find it?
460 JNZ MSGCHK ;No -- we're done
461; we found the file
462; look for fragmentation
463 XOR AX,AX ;Initialize the fragment counter
464 MOV SI,[BP] ;Get the first cluster ;an005;bgb
465 CALL UNPACK ;see what that cluster points to
466 CMP DI,[EOFVAL] ;End-of-file?
467 JAE NXTCHK ;Yes -- go report the results
468 INC SI
469 CMP SI,DI
470 JZ EACHCLUS
471 INC AX
472EACHCLUS:
473 MOV [OLDCLUS],DI ;Save the last cluster found
474 MOV SI,DI ;Get the next cluster
475 CALL UNPACK
476 INC [OLDCLUS] ;Bump the old cluster
477 CMP DI,[OLDCLUS] ;Are they the same?
478 JNZ LASTCLUS ;No -- check for end-of-file
479 JMP SHORT EACHCLUS ;Continue processing
480LASTCLUS:
481 CMP DI,[EOFVAL] ;End-of-file?
482 JAE NXTCHK ;Yes -- go report the results
483 INC AX ;No -- found a fragement
484 JMP SHORT EACHCLUS ;Continue processing
485NXTCHK: ;reached the end of a file
486 OR AX,AX ;did we find any fragmentation?
487 JZ GETNXT
488;we found fragmentation
489 MOV [FRAGMENT],2 ;Signal that we output at least one file
490 inc ax ;bump by one for ends
491 mov [block_num],ax
492 mov word ptr rarg1,ax ; ;an011;bgb
493 mov word ptr rarg1+2,0
494 mov si,offset dg:dirbuf ;point to filename ;an011;bgb
495 INC SI ;move pointer past drive letter
496; get the full path name for this file
497 CALL get_THISEL2
498; print it out
499 mov dx,offset dg:extent_arg
500 invoke printf_crlf
501GETNXT:
502 MOV AH,DIR_SEARCH_NEXT ;Look for the next file
503 JMP FRAGCHK
504MSGCHK:
505 CMP AH,DIR_SEARCH_FIRST ;was this the first file searched for?
506 JNZ FILSPOK
507; MOV SI,offset dg:FCB_copy + 1 ;File not found error
508; CALL get_THISEL2
509 MOV SI,pFileName
510 CALL get_currdir
511 mov dx,offset dg:OPNERR_arg
512 invoke printf_crlf ;bad file spec
513 jmp short cdone
514FILSPOK:
515 CMP BYTE PTR [FRAGMENT],2
516 JZ CDONE
517; all files were ok
518 mov dx,offset dg:NOEXT_arg
519 invoke printf_crlf
520CDONE:
521 CMP BYTE PTR [DIR_FIX],0
522 JZ CDONE1
523 MOV DX,OFFSET DG:USERDIR
524 DOS_Call ChDir ; ;AC000;
525CDONE1:
526 RET
527
528
529
530; This is the old parameter passing scheme ;ac048;bgb
531; inputs: AH - the sector number within the cluster ;ac048;bgb
532; BX - cluster number ;ac048;bgb
533; output: DX - absolute sector number ;ac048;bgb
534;***************************************************************************** ;ac048;bgb
535; FIGREC - This procedure calculates the absolute sector number of a logical ;ac048;bgb
536; drive, given any cluster number and the sector within that cluster. ;ac048;bgb
537; You can use this to find the sector number for a file. ;ac048;bgb
538; ;ac048;bgb
539; This procedure was entirely re-written for dos 4.0, since the ;ac048;bgb
540; sector number can now be a DOUBLE word value. ;ac048;bgb
541; ;ac048;bgb
542; called by: getent in chkproc ;ac048;bgb
543; ;ac048;bgb
544; inputs: BX - cluster number ;ac048;bgb
545; AH - sector number within cluster ;ac048;bgb
546; csize - sectors per cluster (from dpb) ;ac048;bgb
547; firstsec - starting sector number of the data area (from dpb) ;ac048;bgb
548; ;ac048;bgb
549;outputs: DX - absolute sector number (low order) ;ac048;bgb
550; INT26.start_sector_high (hi order) ;ac048;bgb
551; ;ac048;bgb
552;regs changed: DX only ;ac048;bgb
553; ;ac048;bgb
554;formula: cluster (3-fff7) * secs/cluster (1-8) = (3-7ffb8) ;ac048;bgb
555; + sector-offset (0-8) + first-sector (1-ffff) = (7ffb9-8ffbf) ;ac048;bgb
556; ;ac048;bgb
557; logic: 1. adjust the cluster number, since the 1st two clusters in the fat ;ac048;bgb
558; are not used. cluster number can be from 3-fff7. ;ac048;bgb
559; 2. get the sectors-per-cluster, and multiply it times cluster number ;ac048;bgb
560; in AX. since this is a word multiply, the high order number goes ;ac048;bgb
561; into DX. ;ac048;bgb
562; 3. add in the sector-number-within-the-cluster. Each cluster ;ac048;bgb
563; (usually) contains several sectors within a cluster. This sector ;ac048;bgb
564; number is that number. It may be from zero to the max number of ;ac048;bgb
565; sectors/cluster (which can be up to 8 so far on IBM systems). ;ac048;bgb
566; Do an ADC in case there is a overflow of the word register. ;ac048;bgb
567; 4. add in the starting cluster number of the data area. This now ;ac048;bgb
568; gives you the logical sector number within that drive. ;ac048;bgb
569;***************************************************************************** ;ac048;bgb
570procedure figrec,NEAR ;ac048;bgb
571 push ax ;save registers ;ac048;bgb
572 push bx ;save registers ;ac048;bgb
573 push cx ;save registers ;ac048;bgb
574 ;ac048;bgb
575 xor ch,ch ;clear out hi byte of sector-offset ;ac048;bgb
576 mov cl,ah ;move sector-offset into cx ;ac048;bgb
577 mov ax,bx ;move cluster number into ax for mult ;ac048;bgb
578 ;ac048;bgb
579 xor bh,bh ;zero out bh ;ac048;bgb
580 mov bl,csize ;get sectors per cluster ;ac048;bgb
581 dec ax ; sub 2 for the 1st 2 unused clus in the fat ;ac048;bgb
582 dec ax ; ;ac048;bgb
583 mul bx ;ax=low word, dx=hi word ;ac048;bgb
584 ;ac048;bgb
585 add ax,cx ;add sector offset ;ac048;bgb
586 adc dx,0 ;inc hi word if overflow ;ac048;bgb
587 add ax,[firstsec] ;add first data sector ;ac048;bgb
588 adc dx,0 ;inc hi word if overflow ;ac048;bgb
589 ;ac048;bgb
590 mov Read_Write_Relative.Start_Sector_High,dx ;save hi value ;ac048;bgb
591 mov dx,ax ;convert to old format- dx=low ;ac048;bgb
592 ;ac048;bgb
593 pop cx ;ac048;bgb
594 pop bx ;ac048;bgb
595 pop ax ;ac048;bgb
596 RET ;ac048;bgb
597endproc figrec ;ac048;bgb
598
599
600;*****************************************************************************
601SUBTTL PRINTID - Print Volume ID info
602PAGE
603PRINTID:
604ASSUME DS:DG
605 call docrlf ; ;AN000;
606;get volume name ;an012;bgb
607 xor si,si ;Point at DTA where find first just done;;an005;bgb
608 lea DI,arg_buf ;Where to put vol name for message ;AC000;
609 add si,DirNam ;Point at the vol label name ;AN000;
610;;;;;;;;lea DI,arg_buf ;Point at vol label location in arg_Buf ;AC000;
611 MOV CX,11 ; Pack the name
612 push ds ;an005;bgb
613 mov ds,fattbl_seg ;an005;bgb
614 REP MOVSB ; Move all of it
615;get the year ;an012;bgb
616 xor si,si ;Get back pointer to FCB ;an009;bgb
617 mov ax,ds:[si].DirDat ;yyyyyyym mmmddddd Put in SysDisp form ;AN009;bgb
618 and ax,Year_Mask ;yyyyyyy0 00000000 ;AN000;
619 shr ax,1 ;0yyyyyyy 00000000 ;AN000;
620 xchg al,ah ;00000000 0yyyyyyy ;AN000;
621 add ax,1980 ; ;AN000;
622 mov es:Sublist_msg_Idmes.Sublist_Offset+(size Sublist_Struc),ax ; ;AN009;bgb
623;get the month ;an012;bgb
624 mov ax,ds:[si].DirDat ;yyyyyyym mmmddddd ;AN009;bgb
625 and ax,Month_Mask ;0000000m mmm00000 ;AN000;
626 mov cl,5 ; ;AN000;
627 shr ax,cl ;00000000 0000mmmm ;AN000;
628 mov cl,al ;0000mmmm ;AN000;
629;get the day ;an012;bgb
630 mov ax,ds:[si].DirDat ;yyyyyyym mmmddddd ;AN009;bgb
631 and ax,Day_Mask ;00000000 000ddddd ;AN000;
632 mov ah,cl ;0000mmmm 000ddddd ;AN000;
633 xchg ah,al ;make it display correctly ;an012;bgb
634 mov es:Sublist_msg_Idmes.Sublist_Segment+(size Sublist_Struc),ax ; ;AN009;bgb
635;get the time ;an012;bgb
636 mov ax,ds:[si].DirTim ;hhhhhmmm mmmsssss ;AN009;bgb
637 and ax,Hour_Mask ;hhhhh000 00000000 ;AN000;
638 mov cl,11 ; ;AN000;
639 shr ax,cl ;00000000 000hhhhh ;AN000;
640 mov ch,al ;000hhhhh ;AN000;
641 mov ax,ds:[si].DirTim ;hhhhhmmm mmmsssss ;AN009;bgb
642 and ax,Minute_Mask ;00000mmm mmm00000 ;AN000;
643 mov cl,3 ; ;AN000;
644 shl ax,cl ;00mmmmmm 00000000 ;AN000;
645 mov al,ch ;00mmmmmm 000hhhhh ;AN000;
646 mov es:Sublist_msg_Idmes.Sublist_Offset+(size Sublist_Struc)+(size Sublist_Struc),ax ;AN009;bgb
647 mov es:Sublist_msg_Idmes.Sublist_Segment+(size Sublist_Struc)+(size Sublist_Struc),0 ;AN009;bgb
648 pop ds ;an009;bgb
649 Message Idmes_Arg ; the parts out as needed ;AC000'
650;;;;;;;;call doCRLF
651 ret ;
652
653
654
655
656;***************************************************************************** ;an024;bgb
657; Get the volume serial number ;an024;bgb
658;***************************************************************************** ;an024;bgb
659; Input: FCB_Drive ;an024;bgb
660; Output: SerNum if no carry ;an024;bgb
661; Notes: Only DOS Version 3.4 and above will contain serial numbers ;an024;bgb
662;***************************************************************************** ;an024;bgb
663 PUBLIC GET_SERIAL_NUM ;an024;bgb
664procedure Get_Serial_Num,NEAR ;AN000;S ;an024;bgb
665 mov al,GENERIC_IOCTL ;AN000;S ;an041;bgb;an024;bgb
666 xor bx,bx ;zero out bx ;an041;bgb;an024;bgb
667 mov bl,alldrv ;AN000;S Which drive to check ;an024;bgb
668 mov ch,rawio ;8 = disk io ;an041;bgb;an024;bgb
669 mov cl,Get_Media_Id ;66h = get media id ;an041;bgb;an024;bgb
670 LEA dx,SerNumBuf ;AN000;S Pt to the buffer ;an024;bgb
671 Dos_call ioctl ;AN000;S Make the call ;an041;bgb;an024;bgb
672; $IF NC
673 JC $$IF26
674 message msgserialnumber ;an024;bgb
675; $ENDIF
676$$IF26:
677 ret ;AN000;S ;an024;bgb
678endproc Get_Serial_Num ;AN000;S ;an024;bgb
679 pathlabl chkdsk1 ;an024;bgb
680CODE ENDS
681 END CHKDSK
682 \ No newline at end of file