+ResRAM
[www.jankratochvil.net.git] / project / ResRAM / ResRAM.asm
1 ;DEBUG  equ     1
2 ;DEBUGX equ     1       ;Requires silly CPU (680[01]0)
3 ;WaitDbg        equ     1       ;Wait for RMB after each debug message
4 ;ModDebug       equ     1       ;Do (Abs|Img)Module debugging
5
6 PathLen equ     256
7 StdBootPri      equ     15
8 StdTaskPri      equ     10
9 StdStackSize    equ     512
10
11 GV_DosBase      equ     $204
12
13         ifd     ModDebug
14 waitit  macro
15         opt     nochkimm
16         push    d0
17 \@a     move.w  d0,$dff180
18         addq.w  #1,d0
19         btst.b  #2,$dff016
20         bne.s   \@a
21 \@b     move.w  d0,$dff180
22         subq.w  #1,d0
23         btst.b  #2,$dff016
24         beq.s   \@b
25         pop     d0
26         opt     chkimm    
27         endm
28         else
29 waitit  macro
30         endm
31         endc
32
33         ifd     DEBUGX
34 amsg    macro   ;Text
35         opt     w-
36         bsr     DPrintf
37         opt     w+
38         bra.s   \@a
39 \@b     dc.b    '\1'
40         ifeq    NARG-1
41         dc.b    10
42         endc
43         dc.b    0
44         even
45 \@a
46         endm
47         else
48 amsg    macro
49         endm
50         endc
51
52         include "SSMac.h"
53
54 _LVOAddBootNode equ     _LVOexpansionUnused
55
56 ;Main part:
57 ;My ResidentTag#
58 ;Word NULL - LongAlign#
59 ;Code#
60 ;Temporary variables
61 ;Static variables#
62 ;ResCmds SegLists+checksums#
63 ;NULL - stop of ResCmds#
64 ;Resident SegLists+checksums#
65 ;MyResident pointer#
66 ;Resident pointers#
67 ;ResidentList successor
68 ;KickMemHeader successor
69 ;KickMemHeader(w/o successor)#
70 ;KickMem(|s) [1-3]#
71 ;RES disk data#
72 ;DosHandler name#
73 ;Volume name#
74 ;ResCmds names#
75
76 MyFORBID        macro   ;[exec]
77         ifne    NARG
78         move.l  4.w,a6
79         endc
80         addq.b  #1,TDNestCnt(a6)
81         endm
82
83         rsreset         ;FileChain for ReadFiles
84 FC_MinNode      rs.b    MLN_SIZE
85 FC_FileSize     rs.b    0       ;FileSize (1 Long)
86 FC_DirList      rs.b    MLH_SIZE
87 FC_ProtBits     rs.b    1       ;Protection Bits (b7=1 -> dir)
88 FC_FileName     rs.b    0       ;FileName (ASCIIZ)
89 FC_SIZEOF       rs.b    0       ;w/o FileName
90
91         rsreset
92 RFC_FileSize    rs.l    1       ;Size of file/dir in bytes
93 RFC_ProtBits    rs.b    1       ;Protection bits (b7=1 -> dir)
94 RFC_FileName    rs.b    0       ;FileName (ASCIIZ)
95 RFC_SIZEOF      rs.b    0       ;w/o FileName
96
97         rsreset         ;Resident chain
98 RC_Next rs.l    1       ;^Next chain or NULL
99 RC_Type rs.w    1       ;Type RCT_#?
100 RC_CmdName      rs.b    0       ;RCT_Cmd -> ^FileName of the PathName
101 RC_Resident     rs.b    0       ;!=RCT_Cmd -> ^ResidentTag
102 RC_Tracker      rs.l    1       ;File tracker
103 RC_CheckSum     rs.b    0       ;Segment values sum (LONG)
104 RC_CheckSummed  rs.w    1       ;BOOL value for summing
105 RC_Hunks        rs.w    1       ;# of hunks
106 RC_SIZEOF       rs.b    0       ;w/o (hunk sizes|hunk pointers)
107
108 RCT_Cmd equ     -1
109 RCT_Lib equ     0
110 RCT_KickMod     equ     1
111
112         dbuf    Anchor,ap_SIZEOF+PathLen
113         dv.l    AnyTrk          ;A! - Must be first
114         dv.l    ChipTrk         ;A!
115         dv.l    ResMemory       ;A! - Tracker of handler's memory
116         dbuf    Root,FC_SIZEOF+1
117         dv.l    RootLock
118         dv.l    ResList         ;Fwd-Linked list of residents
119         dv.l    VolName         ;B!
120         dv.l    DevName         ;B!
121         dv.l    BootPri         ;B!
122         dv.l    OldCurDir
123         dv.l    InhibitEnd      ;Address of terminating 0/':' or NULL
124         dv.l    LinPool
125         dbuf.l  EOFRegs,9
126 HunkBuf equ     EOFRegs         ;Size=20 bytes
127         dbuf    AbsHeader,56
128         dv.w    MEntries
129         dv.w    UnitNum
130         dbuf    StDevName,6
131         dbuf    StVolName,9
132         dv.b    Advisory
133
134         start
135
136         get.l   sv_thistask,a0
137         put.l   pr_CurrentDir(a0),OldCurDir
138         get.l   Arg_Verbose,d0
139         beq.s   NoneVerbose
140         move.l  d0,a2
141         moveq   #0,d2
142 VerbParseMLoop  move.b  (a2)+,d0
143         beq.s   VerbParseDone
144         move.b  d0,d3
145         call    utility,ToUpper
146         gett    VerbParseTab,a1
147 VerbParseCLoop  move.b  (a1)+,d1
148         bne.s   VerbParseChar
149         dtl     <Unrecognised VERBOSE char: ''%c''>,a0
150         move.w  d3,-(sp)        ;I hope RawDoFmt'll ignore b8-b15...
151         bra     ErrorA1SS
152
153 VerbParseChar   cmp.b   (a1)+,d0
154         bne.s   VerbParseCLoop
155         or.b    d1,d2
156         addq.b  #2,d1
157         sne     d1
158         and.b   d1,d2           ;Clear if 254 (None)
159         bra.s   VerbParseMLoop
160
161 VerbParseDone   put.l   d2,Arg_Verbose
162 NoneVerbose     geta    BootPri+4,a4
163         moveq   #StdBootPri,d1
164         get.l   Arg_BootPri,d0
165         beq.s   BootPriStd
166         move.l  d0,a0
167         move.l  (a0),d1
168 BootPriStd      move.l  d1,-(a4)
169         ext.w   d1
170         ext.l   d1
171         cmp.l   (a4),d1
172         dtl     <BootPri value %ld out of range (-128..127)>,a0
173         bne.s   ErrorSSA4
174         move.l  #RT_SIZE+2+ResidentCode+ResidentVars+12+ML_SIZE+ME_SIZE+RFC_SIZEOF+1,d6 ;RAM disk size
175         geta    StDevName,a3
176         moveq   #'0',d4
177         moveq   #'0'-1,d5
178         moveq   #LDF_DEVICES!LDF_READ,d1
179         moveq   #LDF_DEVICES!LDF_READ,d3
180         call    dos,LockDosList
181         move.l  d0,d7
182         get.l   Arg_Device,d0
183         beq     DeviceStd
184         move.l  d0,a2
185         dt      InvalidName,<Invalid device name "%s">
186         tpea    InvalidName
187         move.l  a2,-(a4)
188 TestDevNameLoop tst.b   (a2)
189         beq.s   TestDevError
190         cmp.b   #':',(a2)+
191         bne.s   TestDevNameLoop
192         tst.b   (a2)
193         beq.s   TestDevTerm
194 TestDevError    moveq   #LDF_DEVICES!LDF_READ,d1
195         call    UnLockDosList
196         pop     a0
197 ErrorSSA4       move.l  a4,a1
198         bra     ErrorSS
199
200 TestDevTerm     sub.l   (a4),d6
201         add.l   a2,d6           ;ASCIIZ name length
202         clr.b   -(a2)           ;Cut out ':'
203         move.l  (a4),d2
204         move.l  d7,d1
205         call    FindDosEntry
206         tst.l   d0
207         dt      DevExists,<Device %s: already exists>
208         tpea    DevExists
209         bne.s   TestDevError
210         addq    #8,sp
211         bsr.s   DevNumDigit
212         bra     DevStdOkay
213
214 FindFreeNum     move.l  4.w,a6
215         MyFORBID
216         move.l  KickTagPtr(a6),d0
217         beq.s   DevNumNoTags
218 DevNumTagLoop   bclr.l  #31,d0
219         move.l  d0,a0
220 DevNumTgLoop    move.l  (a0)+,d0
221         beq.s   DevNumNoTags
222         bmi.s   DevNumTagLoop
223         move.l  d0,a1
224         move.l  RT_NAME(a1),a1
225         moveq   #ResNumOne-ResName-1,d0
226         lea     ResName(pc),a2
227 ResNameLoop     move.b  (a1)+,d1
228         beq.s   DevNumTgLoop
229         cmp.b   (a2)+,d1
230         dbne    d0,ResNameLoop
231         bne.s   DevNumTgLoop
232         cmp.b   (a2)+,d4
233         bne.s   DevNumTgLoop
234         cmp.b   (a2)+,d5
235         bne.s   DevNumTgLoop
236         tst.b   (a2)
237         bne.s   DevNumTgLoop
238 DevNumNoTags    call    Permit
239         get.l   dosbase,a6
240         tst.w   d0
241         beq     Return
242 DevNumDigit     cmp.b   #'9',d5
243         bne.s   DevNumDigitL
244         cmp.b   #'9',d4
245         bne.s   DevNumDigitH
246         dt      MaxDisks,<Max. # of RES disks reached>
247         tpea    MaxDisks
248         bra     TestDevError
249
250 DevNumDigitH    addq.b  #1,d4
251         moveq   #'0'-1,d5
252 DevNumDigitL    addq.b  #1,d5
253         bra.s   FindFreeNum
254
255 DeviceStd       move.l  a3,-(a4)
256         move.l  MyDiskTypeAddr(pc),(a3)
257 DevNumLoop      bsr.s   DevNumDigit
258         lea     3(a3),a2
259         cmp.b   #'0',d4
260         beq.s   DevNum1Null
261         move.b  d4,(a2)+
262         bra.s   Digit2Force
263
264 DevNum1Null     cmp.b   d4,d5
265         beq.s   Digit2Null
266 Digit2Force     move.b  d5,(a2)
267 Digit2Null      move.l  a3,d2
268         move.l  d7,d1
269         call    FindDosEntry
270         tst.l   d0
271         bne.s   DevNumLoop
272 DevNumOkay      move.l  a3,a2
273 DevNumLength    tst.b   (a2)+
274         bne.s   DevNumLength
275         sub.l   (a4),a2
276         add.l   a2,d6
277 DevStdOkay      moveq   #LDF_DEVICES!LDF_READ,d1
278         call    UnLockDosList
279         put.b   d4,UnitNum
280         put.b   d5,UnitNum+1
281         get.l   Arg_Name,d0
282         move.l  d0,a0
283         bne.s   VolumeCustom
284         geta    StVolName,a0
285         move.l  a0,a1
286         move.l  #'ResR',(a1)+   ;Standard volume name
287         move.w  #'am',(a1)+
288         lea     3(a3),a2
289 VolNameEnd      move.b  (a2)+,(a1)+
290         bne.s   VolNameEnd
291 VolumeCustom    move.l  a0,-(a4)
292 TestVolName     tst.b   (a0)+
293         bne.s   TestVolName
294         sub.l   (a4),a0
295         add.l   a0,d6
296
297         moveq   #64,d0
298         lsl.l   #6,d0           ;4KBytes Quantum
299         moveq   #MEMF_PUBLIC,d1
300         call    ss,TrackLinPool
301         put.l   d0,LinPool
302         geta    Root+LN_PRED,a1
303         move.l  a1,-(a1)
304         addq    #FC_DirList,a1
305         bsr     InitDir         ;@A4=Parent/Current dir
306         getad   Anchor,a0,d2
307         move.l  #(APF_DOWILD!APF_DODOT)<<24!PathLen,ap_Flags(a0)
308         get.l   Arg_Files,d1
309         call    dos,MatchFirst
310         tst.l   d0
311         beq.s   FileScanFirst
312         cmp.l   #ERROR_NO_MORE_ENTRIES,d0
313 ErrNoMorePtr    equ     *-4
314         bne.s   ErrorScan
315         vpush   Arg_Files
316         dtl     <No files match %s>,a0
317 ErrorA1SS       move.l  sp,a1
318 ErrorSS jump    ss,ExitError
319
320 ErrorScan       dtl     <Error scanning files %s>,a0
321         vpush   Arg_Files
322 SSDosErrorA1    move.l  sp,a1
323         jump    ss,DosError
324
325 PrintDirName    btstv.b #VerbB_Dirs,Arg_Verbose+3
326         beq     Return
327         vpea    Anchor+ap_Buf
328         dtl     <Scanning directory %s ...',13,$9B,'K>,a0
329         move.l  sp,a1
330         call    ss,Printf
331 ReturnSPinc     addq    #4,sp
332         rts
333
334 FileScanFirst   get.l   Anchor+ap_Current,a0
335         move.l  an_Lock(a0),d1
336         call    DupLock
337         put.l   d0,RootLock
338         beq.s   ErrorScan
339         tstv.l  Arg_Verbose
340         beq.s   FileScanLoop
341         dtl     <',$9B,'0 p>,a0
342         call    ss,Puts
343
344 FileScanLoop    tstv.l  Anchor+ap_Info+fib_DirEntryType
345         bpl.s   IsDir
346         btstv.b #VerbB_Files,Arg_Verbose+3
347         sne     d7
348         beq.s   FileVerbOff
349         bsr.s   FileHeader
350 FileVerbOff     tstv.b  Anchor+ap_Info+fib_Protection+3
351         bpl     IsFile
352         tst.b   d7
353         beq.s   NextFile
354         dtl     <Skipped>,a0
355         call    PutsNL
356         bra.s   NextFile
357
358 FileHeader      geta    Anchor+ap_Buf,a0
359         call    ss,Puts
360         dtl     < - >,a0
361         jump    Puts
362
363 IsDir   bclrv.b #APB_DIDDIR,Anchor+ap_Flags
364         bne     WasDir
365         bsetv.b #APB_DODIR,Anchor+ap_Flags
366         tstv.b  Anchor+ap_Info+fib_FileName
367         beq.s   ClimbedUp
368         bsr     AllocateFC
369         call    ss,TestStack
370         push    a4
371         bsr     InitDir
372 ClimbedUp       bsr     PrintDirName
373
374 NextFile        call    ss,TestBreak
375         getad   Anchor,a0,d1
376         call    dos,MatchNext
377         tst.l   d0
378         beq.s   FileScanLoop
379         cmp.l   ErrNoMorePtr(pc),d0
380         bne     ErrorScan
381         bsr     FlushStdout
382         get.l   ResList,d3
383         beq     ListPreNull     ;No resident modules -> No detaching
384 ;Calculate size of the parts for detaching
385         geta    ResMemory,a4
386 ListPreSize     move.l  d3,a2
387         move.l  (a2)+,d3        ;RC_Next
388         addq    #RC_Hunks-RC_Type,a2
389         move.w  (a2)+,d0        ;RC_Hunks
390         bra.s   HunkSizeInto
391
392 HunkSize        move.l  (a2)+,d1
393         addq.l  #2,d1
394         move.l  a4,a0
395         lsl.l   #2,d1
396         bcs.s   HunkSizeChip
397         subq    #4,a0
398 HunkSizeChip    add.l   d1,-(a0)
399 HunkSizeInto    dbra    d0,HunkSize
400         tst.l   d3
401         bne.s   ListPreSize
402 ;Allocate detach part
403         moveq   #MEMF_CHIP,d1
404         move.l  sp,a2
405         dtl     <CHIP>,a3
406         dt      PublicMsg,<PUBLIC>
407 GetDetaches     push    d1
408         move.l  -(a4),d2
409         beq.s   NoPart
410         addq.l  #ME_SIZE,d6     ;(Any|Chip)Detach entry
411         gett    DetachMsg,a0
412         move.l  a3,a1
413         bsr     AllocMemTopF
414         move.l  d1,(a4)
415         move.l  (sp),d1
416         move.l  d0,(sp)
417         addq    #5,a3
418 NoPart  subq.l  #MEMF_CHIP,d1   ;CHIP,void
419         bcc.s   GetDetaches
420 ;Fill in hunk pointers
421         get.l   ResList,d2
422 NextPtrMain     move.l  d2,a0
423         move.l  (a0)+,d2        ;RC_Next
424         addq    #RC_Hunks-RC_Type,a0
425         move.w  (a0)+,d0
426         geta    ResMemory,a2    ;Trashed long
427         bra.s   HunkPtrsInto
428
429 HunkPtrsLoop    move.l  (a0),d1
430         move.l  sp,a3
431         lsl.l   #2,d1
432         bcc.s   HunkPtrsAny
433         addq    #4,a3
434 HunkPtrsAny     move.l  (a3),a1
435         move.l  d1,(a1)
436         addq.l  #8,(a1)+
437         move.l  a1,d3
438         lsr.l   #2,d3
439         move.l  d3,(a2)
440         move.l  a1,a2
441         clr.l   (a1)+
442         move.l  a1,(a0)+
443         add.l   d1,a1
444         move.l  a1,(a3)
445 HunkPtrsInto    dbra    d0,HunkPtrsLoop
446         tst.l   d2
447         bne.s   NextPtrMain
448         addq    #8,sp           ;Trash destination addresses
449 ;LoadSeg the file
450         vmovev.l ResList,EOFRegs
451 LoadSegLoop     get.l   EOFRegs,a4      ;previously D2
452         addq.l  #8,d6           ;SegList+Checksum
453         move.l  (a4)+,d4        ;RC_Next
454         move.w  (a4)+,d3        ;RC_Type
455         bmi.s   LoadSegCmd
456         addq.l  #4,d6           ;^ResidentTag
457 LoadSegCmd      move.l  (a4),a2         ;RC_Tracker
458         lea     trk_ext(a2),a2
459         move.l  (v),a6
460         btstv.b #VerbB_LoadFiles,Arg_Verbose+3
461         beq.s   SkipLoadSegInfo
462         move.l  a2,a1
463         dtl     <LoadSeg of the file %s ...',13,$9B,'K>,a0
464         call    Printf
465 SkipLoadSegInfo move.l  (a2),a0         ;trk_ext
466         move.l  -(a2),d2        ;trk_data
467         moveq   #OPEN_OLD,d0
468         moveq   #0,d1
469         call    TrackOpenBufFH
470         move.l  d4,d2
471         move.l  d0,a2
472         addq    #RC_SIZEOF-RC_Tracker,a4
473         movemv.l d2-d6/a2/a4/a6/sp,EOFRegs
474         moveq   #0,d4
475         moveq   #0,d5
476 ;A4=Hunk pointer table
477 ;A2=File tracker
478 ;D2=Next RC
479 ;D3.W=Type
480 ;D4=Current hunk #*4 - modifiable
481 ;D5=Ptr to current hunk - (A2,D4.l) or NULL for no current hunk - modifiable
482 HunkMainLoop    movemv.l d4/d5,EOFRegs+2*4
483         vmovem.l EOFRegs+5*4,a2/a4/a6
484         lea     FileEnd(pc),a0
485         move.l  a0,bh_eofhook(a2)
486         call    BGetLong
487         lea     HunkError(pc),a0
488         move.l  a0,bh_eofhook(a2)
489         bclr.l  #HUNKB_ADVISORY,d0
490         snev    Advisory
491         sub.w   #HUNK_NAME,d0
492         bcs     BadHunk
493         cmp.w   #HUNK_RELRELOC32-HUNK_NAME+1,d0
494         bcc     BadHunk
495         lsl.l   #1,d0
496         move.w  HunkTable(pc,d0.w),d1
497         swap    d0
498         lsl.w   #2,d0
499         bne     HunkError
500         jsr     HunkTable(pc,d1.w)
501         bra.s   HunkMainLoop
502
503 hunk    macro   ;HUNK_#?[,<routine>]
504         ifne    _hunk-\1
505         fail    Mismatched hunk numbers!
506         endc
507         ifeq    NARG-1
508         dc.w    BadHunk-HunkTable
509         else
510         dc.w    hunk_\2-HunkTable
511         endc
512 _hunk   set     _hunk+1
513         endm
514 _hunk   set     1000
515 HunkTable
516         hunk    HUNK_NAME,skipcnt       ;1000
517         hunk    HUNK_CODE,main          ;1001
518         hunk    HUNK_DATA,main          ;1002
519         hunk    HUNK_BSS,main           ;1003
520         hunk    HUNK_RELOC32,rel32      ;1004
521         hunk    HUNK_RELOC16            ;1005
522         hunk    HUNK_RELOC8             ;1006
523         hunk    HUNK_EXT                ;1007
524         hunk    HUNK_SYMBOL,symbol      ;1008
525         hunk    HUNK_DEBUG,skipcnt      ;1009
526         hunk    HUNK_END,end            ;1010
527         hunk    HUNK_HEADER             ;1011
528         hunk    1012                    ;????
529         hunk    HUNK_OVERLAY            ;1013
530         hunk    HUNK_BREAK              ;1014
531         hunk    HUNK_DREL32,rel16       ;1015
532         hunk    HUNK_DREL16             ;1016
533         hunk    HUNK_DREL8              ;1017
534         hunk    HUNK_LIB                ;1018
535         hunk    HUNK_INDEX              ;1019
536         hunk    HUNK_RELOC32SHORT,rel16 ;1020
537         hunk    HUNK_RELRELOC32,rrel16  ;1021
538         ifne    _hunk-HUNK_RELRELOC32-1
539         fail    Invalid number of hunks!
540         endc
541
542 FileEnd vmovem.l EOFRegs,d2-d6/a2/a4/a6/sp
543         tst.l   d5
544         bne     HunkError
545         move.l  a4,a3
546         lsr.l   #2,d4
547         cmp.w   -(a4),d4        ;RC_Hunks
548         bne     HunkError
549         subq    #RC_Hunks-RC_Tracker,a4
550         move.l  (a4),a0         ;RC_Tracker
551         call    FreeObject      ;Non-buffered tracker
552         move.w  d4,d7
553         tst.w   d3              ;RC_Type
554         bmi.s   LoadEndCmd
555         move.l  a3,d5
556 FindResInto     dbra    d4,FindResLoop
557         push    bh_name(a2)
558         dtl     <No resident tag found in file "%s">,a0
559         bra     ErrorA1SS
560
561 LoadEndCmd      move.l  bh_name(a2),d1
562         call    dos,FilePart
563         move.l  d0,(a4)+        ;RC_CmdName
564         bra.s   LoadEnd
565
566 FindResLoop     move.l  (a3)+,a0
567         move.l  -8(a0),d0       ;Size of the hunk
568         moveq   #RT_SIZE+8,d1
569         sub.l   d1,d0
570         bcs.s   FindResInto
571         lsr.l   #1,d0
572         move.w  d0,d1
573         swap    d0
574 FindResTag1     cmp.w   #RTC_MATCHWORD,(a0)+
575 FindResTag2     dbeq    d1,FindResTag1
576         dbeq    d0,FindResTag1
577         bne.s   FindResInto
578         move.l  a0,d0
579         subq.l  #2,d0
580         cmp.l   (a0),d0
581         bne.s   FindResTag2
582         tst.w   d3              ;RC_Type
583         bne.s   KickMod
584         move.b  RT_FLAGS-RT_MATCHTAG(a0),d0
585         and.b   #$80,d0
586         or.b    #RTF_AFTERDOS,d0
587         move.b  d0,RT_FLAGS-RT_MATCHTAG(a0)
588         move.b  #-128,RT_PRI-RT_MATCHTAG(a0)
589 KickMod move.l  (a0),(a4)+      ;RC_Resident
590         move.l  d5,a3
591 LoadEnd move.l  a2,a0
592         call    ss,FreeObject
593         moveq   #0,d3
594         tst.w   (a4)
595         beq.s   CalcNoSum
596         subq.w  #1,d7
597 CalcSumMod      move.l  (a3)+,a0
598         move.l  -8(a0),d0
599         lsr.l   #2,d0
600         subq.l  #3,d0
601         bmi.s   CalcSumModInto
602         move.w  d0,d1
603         swap    d0
604 CalcSumIt       add.l   (a0)+,d3
605         dbra    d1,CalcSumIt
606         dbra    d0,CalcSumIt
607 CalcSumModInto  dbra    d7,CalcSumMod
608         seq     d0
609         sub.b   d0,d3
610 CalcNoSum       move.l  d3,(a4)+        ;RC_CheckSum
611         move.l  (a4),d0
612         lsr.l   #2,d0
613         subq.l  #1,d0
614         move.l  d0,(a4)
615         tst.l   d2
616         bne     LoadSegLoop
617         bsr     FlushStdout
618 ListPreNull     move.l  d6,d2
619         gett    BlockMsg,a0
620         dtl     <Main>,a1
621         bsr     AllocMemTop
622         put.l   d1,ResMemory
623         move.l  d0,d5
624         move.l  d0,a1
625         move.w  #RTC_MATCHWORD,(a1)+            ;RT_MATCHWORD
626         move.l  #(RTF_COLDSTART<<24)!(1<<16),d7 ;RT_[FVTP]#?
627         lea     ResName-ResidentPart+RT_SIZE-RT_MATCHTAG+2(a1),a0
628         move.l  a0,d2
629         lea     ResID-ResidentPart+RT_SIZE-RT_MATCHTAG+2(a1),a2
630         lea     ResInit-ResidentPart+RT_SIZE-RT_MATCHTAG+2(a1),a3
631         movem.l d0/d4/d7/a0/a2/a3,(a1)
632         lea     RT_SIZE-RT_MATCHTAG+2(a1),a1
633         lea     ResidentPart(pc),a0
634         move.l  #ResidentCode,d0
635         lea     ResidentCode+ResidentVars(a1),a3
636         call    exec,CopyMem
637         get.w   UnitNum,ResNumOne-V-ResidentVars(a3)
638         get.w   UnitNum,ResNumTwo-V-ResidentVars(a3)
639         lea     -ds_SIZEOF(a3),a2
640         move.l  a2,d1
641         call    dos,DateStamp   ;dosbase used below!
642         get.l   ResList,d0
643         beq.s   NoList1
644 Cmds1Loop       move.l  d0,a0
645         move.l  (a0)+,d0        ;RC_Next
646         tst.w   (a0)+           ;RC_Type
647         bpl.s   NoCmdNode1
648         addq    #RC_SIZEOF-RC_CmdName,a0
649         move.l  (a0),(a3)+      ;RC_SIZEOF - SegList
650         move.l  -(a0),(a3)+     ;RC_CheckSum
651 NoCmdNode1      tst.l   d0
652         bne.s   Cmds1Loop
653 NoList1 clr.l   (a3)+
654         get.l   ResList,d0
655         beq.s   NoList3
656 Libs2Loop       move.l  d0,a0
657         move.l  (a0)+,d0        ;RC_Next
658         tst.w   (a0)+           ;RC_Type
659         bmi.s   NoLibNode2
660         addq    #RC_SIZEOF-RC_Resident,a0
661         move.l  (a0),(a3)+      ;SegList
662         move.l  -(a0),(a3)+     ;LibChkSum
663 NoLibNode2      tst.l   d0
664         bne.s   Libs2Loop
665 NoList3 push    a3              ;STACK=^Resident list
666         move.l  a3,-(a2)        ;ResListPtr
667         move.l  d5,(a3)+        ;My resident struct
668
669         get.l   ResList,d0
670         beq.s   NoList2
671 Libs1Loop       move.l  d0,a0
672         move.l  (a0)+,d0        ;RC_Next
673         tst.w   (a0)+           ;RC_Type
674         bmi.s   NoResMod
675         move.l  (a0),(a3)+      ;RC_Resident
676 NoResMod        tst.l   d0
677         bne.s   Libs1Loop
678 NoList2 move.l  a3,-(a2)        ;ResListSucc
679         clr.l   (a3)+
680         clr.l   (a3)+           ;LN_SUCC
681         push    a3              ;STACK=^Resident list succ
682         clr.l   (a3)+           ;LN_PRED
683         move.w  #NT_KICKMEM<<8,(a3)+    ;LN_TYPE+LN_PRI
684         move.l  d2,(a3)+        ;LN_NAME
685         get.w   MEntries,(a3)+  ;ME_NUMENTRIES
686         geta    AnyTrk,a0
687         moveq   #2,d0
688 MEntryLoop      move.l  (a0)+,d1
689         beq.s   NoMEntry
690         move.l  d1,a4
691         move.l  trk_data(a4),(a3)+      ;ME_ADDR
692         move.l  trk_ext(a4),(a3)+       ;ME_LENGTH
693 NoMEntry        dbra    d0,MEntryLoop
694         move.l  a3,-(a2)        ;RootPtr
695         clr.l   -(a2)           ;NumLocks
696         clr.l   -(a2)           ;VolumeNode
697         move.l  MyDiskTypeAddr(pc),-(a2)        ;id_DiskType
698         moveq   #64,d0
699         lsl.l   #3,d0
700         move.l  d0,-(a2)        ;id_BytesPerBlock
701         move.l  a3,a1
702         move.l  -(a1),d0        ;Length
703         move.l  d0,d7
704         add.l   -(a1),d7
705         lsr.l   #8,d0
706         lsr.l   #1,d0           ;BlockSize=512
707         addq.l  #1,d0
708         move.l  d0,-(a2)        ;id_NumBlocksUsed
709         move.l  d0,-(a2)        ;id_NumBlocks
710         moveq   #ID_WRITE_PROTECTED,d0
711         move.l  d0,-(a2)        ;id_DiskState
712         clr.l   -(a2)           ;id_UnitNumber
713         clr.l   -(a2)           ;id_NumSoftErrors
714
715         mpush   a1/a2
716         get.l   RootLock,d1
717         call    dos,CurrentDir
718         geta    Root,a2
719         bsr     ReadFiles
720         bsr     FlushStdout
721         mpop    a1/a2
722
723         move.l  a3,-(a2)        ;DosHName
724         geta    DevName,a1
725         move.l  (a1),a0
726 LenDosHName     tst.b   (a0)+
727         bne.s   LenDosHName
728         sub.l   (a1),a0
729         move.w  a0,d0
730         subq.w  #1,d0
731         move.b  d0,(a3)+
732         move.l  (a1),a0
733         bra.s   CopyDosHNameI
734
735 CopyDosHNameL   move.b  (a0)+,(a3)+
736 CopyDosHNameI   dbra    d0,CopyDosHNameL
737
738         move.l  a3,-(a2)        ;VolumeName
739         move.l  -(a1),a0        ;VolName
740 CopyVolName     move.b  (a0)+,(a3)+
741         bne.s   CopyVolName
742
743         move.l  a3,-(a2)        ;CmdsNames
744         get.l   ResList,d0
745         beq.s   NoCmdsNoNames
746 CmdNamesLoop    move.l  d0,a0
747         move.l  (a0)+,d0
748         tst.w   (a0)+           ;RC_Type
749         bpl.s   NoCmdName
750         move.l  (a0)+,a0        ;RC_CmdName
751 CopyCmdName     move.b  (a0)+,(a3)+
752         bne.s   CopyCmdName
753 NoCmdName       tst.l   d0
754         bne.s   CmdNamesLoop
755 NoCmdsNoNames
756         move.l  d5,a0
757         move.w  #(RT_SIZE+2+ResidentCode)>>2-1,d1
758         moveq   #0,d0
759 GenSumMain      sub.l   (a0)+,d0
760         dbra    d1,GenSumMain
761         move.l  a2,a0
762 GenSumMainE     sub.l   (a0)+,d0
763         cmp.l   a0,d7
764         bne.s   GenSumMainE
765         move.l  d0,-(a2)        ;AnySum
766         get.l   BootPri,-(a2)   ;VarBootPri
767
768 ;### Write out the AbsModule (if wished) ###
769 ;-HEADER- 00000000 00000001 00000000 00000000 *Length* --CODE--
770 ;*Length* 74Ln6014 0000ABCD 00000000 00000000 00000000 00000000
771         move.l  (v),a6
772         pop     a4              ;-(A4)=KickMem, ResListSucc
773         get.l   Arg_GenAbs,d0
774         beq     GenDisk
775         btstv.b #VerbB_SizeMod,Arg_Verbose+3
776         beq.s   NoModVerb
777         push    d0
778         dtl     <Writing AbsModule to the file %s ...>,a0
779         move.l  sp,a1
780         call    Printf
781         bsr     FlushStdout
782         move.l  (v),a6
783         pop     d0
784 NoModVerb       move.l  d0,a0
785         moveq   #OPEN_NEW,d0
786         moveq   #0,d1
787         call    TrackOpenBuf
788         move.l  d0,a3
789         geta    AbsHeader,a0
790         move.l  HeaderPtr(pc),(a0)
791         addq.w  #1,10(a0)
792         moveq   #AbsHdrLength+3,d0
793         geta    AnyTrk,a2
794         moveq   #2,d1
795         move.l  #$60147400!(21+AbsRawLength>>2),d2
796 OutAbsLenLoop   tst.l   (a2)+
797         beq.s   OutAbsLenInto
798         addq.w  #2,d0
799         addq.b  #2,d2
800 OutAbsLenInto   dbra    d1,OutAbsLenLoop
801         move.w  d0,22(a0)
802         subq.w  #1,d0
803         move.w  d0,30(a0)
804         move.w  #HUNK_CODE,26(a0)
805         swap    d2
806         move.l  d2,32(a0)
807         move.w  #$ABCD,38(a0)
808         moveq   #56,d0
809         call    BWrite
810         lea     AbsModule(pc),a0
811         move.l  #AbsRawLength,d0
812         call    BWrite
813         lea     _LVOBPutLong(a6),a1
814         bsr     GenerateEnd
815         move.l  #HUNK_END,(a0)+
816         move.l  #HUNK_OVERLAY,(a0)+
817         clr.l   (a0)+
818         clr.l   (a0)+
819         move.l  #HUNK_BREAK,(a0)+
820         move.l  a0,d0
821         sub.l   d3,d0
822         move.l  d3,a0
823         call    BWrite
824         bsr     ClosenCleanup
825
826 ;### Generate AbsModule to the disk (if wished) ###
827 GenDisk get.l   Arg_GenDisk,d2
828         beq     PrepHandler
829         moveq   #LDF_DEVICES+LDF_READ,d1
830         call    dos,LockDosList
831         move.l  d0,d1
832         move.l  d2,a3
833         moveq   #':',d4
834         moveq   #LDF_DEVICES,d3
835 NextChar        move.b  (a3)+,d0
836         beq     DiskErrorSP
837         cmp.b   d4,d0
838         bne.s   NextChar
839         clr.b   -(a3)
840         call    FindDosEntry
841         tst.l   d0
842         beq     NoDosEntry
843         move.l  d0,a0
844         move.l  dn_Startup(a0),d0
845         beq     NoDosEntry
846         lsl.l   #2,d0
847         move.l  d0,a0
848         push    (a0)+           ;fssm_Unit
849         push    (a0)+           ;fssm_Device
850         move.l  (a0)+,d0        ;fssm_Environ
851         push    (a0)            ;fssm_Flags
852         lsl.l   #2,d0
853         move.l  d0,a0
854         move.l  (a0)+,d6        ;de_TableSize
855         cmp.l   #128,(a0)       ;de_SizeBlock
856         bne.s   NoDosEntry
857         push    de_HighCyl-de_SizeBlock(a0)
858         push    de_LowCyl-de_SizeBlock(a0)
859         push    de_Surfaces-de_SizeBlock(a0)
860         moveq   #MEMF_PUBLIC,d0
861         subq.l  #8,d6
862         subq.l  #4,d6
863         bmi.s   NoBufMemType
864         move.l  de_BufMemType-de_SizeBlock(a0),d0
865 NoBufMemType    put.l   d0,sv_memattr
866         move.l  de_BlocksPerTrack-de_SizeBlock(a0),d0
867         moveq   #3,d1           ;Min. are 3 Blocks/Track
868         cmp.l   d1,d0
869         bcs.s   NoDosEntry
870         lsl.l   #8,d0
871         lsl.l   #1,d0
872         move.l  d0,d6           ;TrackBuffer size
873         get.l   utilitybase,a0
874         lea     _LVOUMult32(a0),a0
875         pop     d1              ;de_Surfaces
876         jsr     (a0)
877         pop     d1              ;de_LowCyl
878         move.l  d0,d7           ;Cylinder size
879         jsr     (a0)
880         exg.l   d0,d7           ;Position offset<->Cylinder size
881         pop     d1              ;de_HighCyl
882         addq.l  #1,d1
883         jsr     (a0)
884         sub.l   d7,d0
885         moveq   #64,d5
886         lsl.l   #3,d5           ;BootBlock size 512
887         geta    AnyTrk,a0
888         moveq   #2,d3
889 LoopDiskTrk     move.l  (a0)+,d1
890         beq.s   NoDiskTrk
891         move.l  d1,a1
892         add.l   trk_ext(a1),d5
893         subq.l  #8,d5
894 NoDiskTrk       dbra    d3,LoopDiskTrk
895         mpush   d0/d5
896         push    d2
897         dtl     <Not enough disk space on the device %s (size %luB, needed %luB)>,a0
898         cmp.l   d5,d0
899         bcs     ErrorA1SS
900         lea     12(sp),sp
901         moveq   #0,d3
902 NoDosEntry      moveq   #LDF_DEVICES+LDF_READ,d1
903         call    UnLockDosList
904 DiskErrorSP     push    d2
905 DiskError       moveq   #err_lock,d0
906         move.l  (sp),a1
907         subq.l  #LDF_DEVICES,d3
908         beq     ReportSS
909         move.b  d4,(a3)
910         move.l  d2,d1
911         moveq   #DOSTRUE,d2
912         call    Inhibit
913         tst.l   d0
914         beq.s   DiskError
915         move.l  (v),a6
916         put.l   a3,InhibitEnd
917         tstv.l  Arg_NoDiskReq
918         bne.s   SkipDiskReq
919         dtl.lc  <Insert disk for the boot image>,a0
920         dt.lc   <into drive %s>
921         dt.l    <All data on it will be overwritten!>
922         move.l  sp,a1
923         dtl     <Okay|Cancel>,a2
924         call    ss,SimpleRequest
925         move.l  d0,d1
926         moveq   #err_break,d0
927         tst.l   d1
928         beq     ReportSS
929 SkipDiskReq     btstv.b #VerbB_SizeMod,Arg_Verbose+3
930         beq.s   NoDiskModVerb
931         dtl     <Generating boot image to the drive %s ...>,a0
932         move.l  sp,a1
933         call    Printf
934         bsr     FlushStdout
935 NoDiskModVerb   addq    #4,sp
936         move.l  d6,d1
937         moveq   #OPEN_NEW,d0
938         move.l  d2,a0
939         call    ss,TrackBufHandle
940         move.l  d0,a3
941         lea     RawDiskWrite(pc),a0
942         move.l  a0,bh_writefunc(a3)
943         mpop    d1/a0   ;fssm_Flags,fssm_Device
944         pop     d0      ;fssm_Unit
945         add.l   a0,a0
946         add.l   a0,a0
947         addq.l  #1,a0
948         sub.l   a1,a1
949         sub.l   a2,a2
950         call    TrackDevice
951         move.l  d1,bh_handle(a3)
952         move.w  #TD_FORMAT,IO_COMMAND(a1)
953         move.l  d7,IO_OFFSET(a1)
954         lea     _LVOBPutLong(a6),a1
955         moveq   #(ImgResList-BootImage)>>2,d0
956         lsl.l   #2,d0
957         lea     BootImage(pc),a0
958         call    BWrite
959         bsr.s   GenerateEnd
960         move.l  a0,d0
961         move.l  d3,a0
962         sub.l   a0,d0
963         moveq   #512-(ImgResList-BootImage)-4,d3
964         sub.l   d0,d3
965         call    BWrite
966         lsr.l   #2,d3
967 FillBoot        moveq   #0,d0
968         call    BPutLong
969         dbra    d3,FillBoot
970         bsr.s   ClosenCleanup
971
972 ;### Prepare handler to be resident ###
973 PrepHandler     pop     a3              ;^ResList
974         get.l   Arg_Reboot,d0
975         beq.s   NoReboot
976         pea     ImgRebootNow(pc)
977 NoReboot        tstv.l  Arg_NoRun
978         bne     Return
979         tst.l   d0
980         bne.s   WellReboot
981         pea     AbsNextRes(pc)
982 WellReboot      geta    AnyTrk,a0
983         moveq   #2,d1
984 KillMemTrks     move.l  (a0)+,d0
985         beq.s   NoMemTrk
986         move.l  d0,a1
987         clr.b   trk_type(a1)
988 NoMemTrk        dbra    d1,KillMemTrks
989         move.l  4.w,a6
990         lea     KickMemPtr(a6),a2
991         MyFORBID
992         move.l  (a2),-(a4)      ;KickMemPtr
993         move.l  a4,(a2)+
994         move.l  (a2),d0         ;KickTagPtr
995         beq.s   NoNextReses
996         bset.l  #31,d0
997 NoNextReses     move.l  d0,-(a4)
998         bra     EndMainInit
999
1000         ifd     DEBUG
1001 EXIT    jump    ss,ExitCleanup
1002         endc
1003
1004 ;################
1005 ;### Routines ###
1006 ;################
1007
1008 GenerateEnd     geta    HunkBuf,a0
1009         move.l  a0,d3
1010         move.l  4(sp),(a0)+
1011         move.l  a4,(a0)+
1012         moveq   #2,d7
1013         geta    AnyTrk,a2
1014         push    a3
1015 OutAddrLoop     move.l  (a2)+,d0
1016         beq.s   OutAddrNo
1017         move.l  d0,a3
1018         move.l  trk_ext(a3),(a0)+
1019         move.l  trk_data(a3),(a0)+
1020 OutAddrNo       dbra    d7,OutAddrLoop
1021         pop     a3
1022         rts
1023
1024 ClosenCleanup   geta    AnyTrk,a2
1025         moveq   #2,d7
1026 OutDataLoop     move.l  (a2)+,d0
1027         beq.s   OutNoTrk
1028         move.l  d0,a0
1029         move.l  trk_ext(a0),d0
1030         subq.l  #8,d0
1031         move.l  trk_data(a0),a0
1032         addq    #8,a0
1033         call    BWrite
1034 OutNoTrk        dbra    d7,OutDataLoop
1035         btstv.b #VerbB_SizeMod,Arg_Verbose+3
1036         beq.s   NoModSizeVerb
1037         move.l  a3,a2
1038         call    BTell
1039         move.l  d0,d1
1040         lsr.l   #8,d1
1041         addq.l  #2,d1
1042         lsr.l   #2,d1
1043         mpush   d0/d1
1044         move.l  sp,a1
1045         dtl.l   < %lu bytes (%luKB)>,a0
1046         call    Printf
1047         addq    #8,sp
1048 NoModSizeVerb   move.l  a3,a0
1049         jump    FreeObject
1050
1051 ;Inputs: A2=Source A3=Destination
1052 ReadFiles       tst.l   (a2)
1053         beq     Return
1054         move.l  (v),a6
1055 ReadFilesRout   move.l  a3,a4           ;As ptr where to fill in DirSize
1056         lea     FC_FileSize(a2),a1
1057         move.l  (a1)+,d2
1058         moveq   #3,d1
1059 PutLongA        rol.l   #8,d2
1060         move.b  d2,(a3)+
1061         dbra    d1,PutLongA
1062         addq    #MLH_SIZE-MLH_TAIL,a1
1063         move.b  (a1)+,(a3)+
1064         move.l  a3,a0
1065 CopyReadName    move.b  (a1)+,(a3)+
1066         bne.s   CopyReadName
1067         tst.b   FC_ProtBits(a2)         ;FileSize (-1 for dir)
1068         bmi.s   CopyDir
1069         btstv.b #VerbB_LoadFiles,Arg_Verbose+3
1070         beq.s   SkipLoadInfo
1071         push    a0
1072         move.l  sp,a1
1073         dtl     <Loading data file %s ...',13,$9B,'K>,a0
1074         call    Printf
1075         pop     a0
1076 SkipLoadInfo    moveq   #OPEN_OLD,d0
1077         call    TrackOpen
1078         move.l  d1,a0           ;Copy tracker for ChkRead
1079         move.l  d2,d0           ;Prepare FileSize
1080         move.l  d1,d2           ;Copy tracker for FreeObject
1081         move.l  a3,a1           ;Get dest
1082         add.l   d0,a3           ;Add FileSize to dest
1083         call    ChkRead
1084         move.l  d2,a0
1085         call    FreeObject
1086 NextObject      move.l  (a2),a2
1087         bra.s   ReadFiles
1088
1089 CopyDir call    TestStack
1090         moveq   #ACCESS_READ,d0
1091         call    TrackLock
1092         push    d1
1093         move.l  d0,d1
1094         call    dos,CurrentDir
1095         mpush   d0/a2/a4
1096         push    a3
1097         move.l  d2,a2
1098         bsr.s   ReadFiles
1099         ;       a3/d0/a2/a4
1100         mpop    d0/d1/a2/a4
1101         sub.l   a3,d0
1102         neg.l   d0
1103         moveq   #3,d2
1104 PutLongB        rol.l   #8,d0
1105         move.b  d0,(a4)+
1106         dbra    d2,PutLongB     ;DirSize filled
1107
1108         call    dos,CurrentDir
1109         pop     a0
1110         call    ss,FreeObject
1111         bra.s   NextObject
1112
1113 IsFile  moveq   #-1,d3          ;Do checksumming flag
1114         geta    Anchor+ap_Info+fib_Comment,a2
1115         move.l  a2,a1
1116 PreCommentLoop  tst.b   (a2)
1117         beq.s   CommentEnd
1118         cmp.b   #':',(a2)+
1119         bne.s   PreCommentLoop
1120         clr.b   -1(a2)
1121         dtl     <4ResRAM>,a0
1122         bsr     CompareString
1123         tst.l   d0
1124         bne.s   CommentEnd
1125 CommentSpcLoop  cmp.b   #' ',(a2)+
1126         beq.s   CommentSpcLoop
1127         subq    #1,a2
1128         move.l  a2,a0
1129 CommentEndLoop  tst.b   (a2)
1130         beq.s   CommentEndOK
1131         cmp.b   #'!',(a2)+
1132         bne.s   CommentEndLoop
1133         clr.b   -(a2)
1134         moveq   #0,d3           ;'!'=>No checksumming
1135 CommentEndOK    tst.b   (a0)
1136         beq.s   CommentEnd
1137         dt      FullExtTable,<Data>
1138         dt      PureCmdMsg,<ResCmd>     ;RCT_Cmd
1139         dt      MinExtTable,<Library>   ;RCT_Lib
1140         dt      <Device>                ;RCT_Lib
1141         dt.c    <KickMod>               ;RCT_KickMod
1142         dt      WordNull,<',0,'>
1143         gett    FullExtTable,a3
1144         bsr.s   GetExtNum
1145         tst.b   (a3)
1146         beq.s   CommentEnd
1147         tst.l   d5
1148         beq     MakeFile
1149         subq.l  #2,d5
1150         bra.s   ChecknCorrect
1151
1152 GetExtNum       move.l  a0,a2
1153         moveq   #0,d5
1154 GetExtNumLoop   move.l  a3,a0
1155         move.l  a2,a1
1156         bsr     CompareString
1157         tst.l   d0
1158         beq     Return
1159         addq.l  #1,d5
1160 SkipExtName     tst.b   (a3)+
1161         bne.s   SkipExtName
1162         tst.b   (a3)
1163         bne.s   GetExtNumLoop
1164         rts
1165
1166 CommentEnd      moveq   #FIBF_PURE!FIBF_EXECUTE,d0
1167         vand.b  Anchor+ap_Info+fib_Protection+3,d0
1168         moveq   #RCT_Cmd,d5
1169         gett    PureCmdMsg,a3
1170         cmp.b   #FIBF_PURE,d0
1171         beq.s   CheckResident
1172         geta    Anchor+ap_Info+fib_FileName,a0
1173         call    ss,GetExtension
1174         gett    MinExtTable,a3
1175         bsr.s   GetExtNum
1176         tst.b   (a3)
1177         beq     MakeFile
1178         tst.l   d5
1179 ChecknCorrect   shi     d0
1180         add.b   d0,d5           ;Library=Device
1181 CheckResident   geta    Anchor+ap_Buf,a2
1182         moveq   #0,d1
1183         bsr     LinAlloc
1184         move.l  d0,a0
1185 CopyOpen        move.b  (a2)+,(a0)+
1186         bne.s   CopyOpen
1187         move.l  d0,d2
1188         get.l   Anchor+ap_Last,a0
1189         move.l  an_Lock(a0),d1
1190         call    dos,CurrentDir
1191         geta    Anchor+ap_Info+fib_FileName,a0
1192         moveq   #OPEN_OLD,d0
1193         call    ss,TrackOpen
1194         push    d1
1195         move.l  d1,a0
1196         move.l  d2,trk_ext(a0)          ;Full PathName of the file
1197         geta    HunkBuf,a1
1198         move.l  a1,a2
1199         moveq   #20,d0
1200         call    ChkTryRead
1201         moveq   #20,d1
1202         cmp.l   d0,d1
1203         bne     TryHunksFail
1204         cmp.l   #HUNK_HEADER,(a2)+
1205 HeaderPtr       equ     *-4
1206         bne     TryHunksFail
1207         tst.l   (a2)+
1208         bne     TryHunksFail
1209         tst.w   (a2)
1210         bne     TryHunksFail
1211         move.l  (a2)+,d1
1212         beq     TryHunksFail
1213         tst.l   (a2)+
1214         bne     TryHunksFail
1215         addq.l  #1,(a2)
1216         cmp.l   (a2),d1
1217         bne     TryHunksFail
1218         move.l  d1,d4
1219         lsl.l   #2,d1
1220         move.l  d1,d2
1221         addq.l  #8,d1
1222         addq.l  #RC_SIZEOF-8,d1
1223         bsr     LinAllocInt
1224         move.l  d0,a1
1225         geta    ResList,a2
1226         move.l  (a2),(a1)+              ;RC_Next
1227         move.w  d5,(a1)+                ;RC_Type
1228         move.l  (sp),(a1)+              ;RC_Tracker
1229         move.w  d3,(a1)+                ;RC_CheckSummed
1230         move.w  d4,(a1)+                ;RC_Hunks
1231         move.l  d0,d3
1232         move.l  d2,d0
1233         move.l  (sp),a0
1234         push    a1
1235         call    ChkTryRead
1236         pop     a0
1237         cmp.l   d0,d2
1238         bne     TryHunksFail
1239         moveq   #8,d1           ;SegList+CheckSum
1240         move.w  d4,d2
1241         subq.l  #1,d4
1242 TestHunkFlg     move.l  (a0)+,d0
1243         rol.l   #2,d0
1244         add.l   d0,d1
1245         and.w   #3,d0
1246         sub.l   d0,d1
1247         addq.l  #8,d1
1248         subq.l  #3,d0
1249         dbeq    d4,TestHunkFlg
1250         beq     TryHunksFail
1251         move.l  d3,(a2)
1252         btstv.b #VerbB_LoadSeg,Arg_Verbose+3
1253         beq.s   NoFileInfo
1254         move.w  d2,-(sp)
1255         push    d1
1256         tst.b   d7
1257         bne.s   HeaderWritten
1258         bsr     FileHeader
1259 HeaderWritten   bsr.s   WriteFileInfo
1260         dtl     <; LoadSeg=%lu; Hunks=%u>,a0
1261         move.l  sp,a1
1262         call    Printf
1263         pop     d0
1264         vcmp.l  Anchor+ap_Info+fib_Size,d0
1265         bls.s   LoadSegSqueeze
1266         dtl     <; Large BSS part!!!>,a0
1267         call    Puts
1268 LoadSegSqueeze  addq    #2,sp
1269         bra.s   DoMsgCR
1270
1271 NoFileInfo      tst.b   d7
1272         beq.s   NoMsgCR
1273         bsr.s   WriteFileInfo
1274 DoMsgCR bsr.s   WriteOutCR
1275 NoMsgCR tst.w   d5
1276         bpl.s   NotCmdIsNoName
1277         geta    Anchor+ap_Info+fib_FileName,a0
1278         move.l  a0,d0
1279 TestResNameLen  tst.b   (a0)+
1280         bne.s   TestResNameLen
1281         sub.l   d0,a0
1282         add.l   a0,d6
1283 NotCmdIsNoName  addq    #4,sp           ;Discard the file tracker
1284         bra     NextFile
1285
1286 WriteOutCR      gett    WordNull,a0
1287         jump    PutsNL
1288
1289 WriteFileInfo   move.l  a3,a0
1290         call    Puts
1291         tst.l   d3
1292         bne.s   HasChkSum
1293         dtl     < (don''t checksum)>,a0
1294         call    Puts
1295 HasChkSum       dtl     <; Size=%lu>,a0
1296         geta    Anchor+ap_Info+fib_Size,a1
1297         jump    Printf
1298
1299 LinAlloc        move.l  a2,a0
1300 TestGlobLen     tst.b   (a0)+
1301         bne.s   TestGlobLen
1302         sub.l   a2,a0
1303         add.l   a0,d1
1304 LinAllocInt     get.l   LinPool,a0
1305         jump    ss,LinearAlloc  ;1/3 may be LinearAllocN, but ...
1306
1307 TryHunksFail    pop     a0
1308         call    FreeObject
1309 MakeFile        tst.b   d7
1310         beq.s   NoFileVerbose
1311         moveq   #-1,d3
1312         gett    FullExtTable,a3
1313         bsr.s   WriteFileInfo
1314         bsr.s   WriteOutCR
1315 NoFileVerbose   bsr.s   AllocateFC
1316         get.l   Anchor+ap_Info+fib_Size,(a1)    ;FC_FileSize
1317         add.l   (a1),d6
1318         bra     NextFile
1319
1320 AllocateFC      geta    Anchor+ap_Info+fib_FileName,a2
1321         moveq   #FC_SIZEOF,d1
1322         bsr.s   LinAlloc
1323         move.l  a4,a0
1324         move.l  d0,a1
1325         lea     FC_ProtBits(a1),a2
1326         call    exec,AddTail
1327         lea     FC_DirList-FC_ProtBits(a2),a1
1328         move.l  a2,d0
1329         get.b   Anchor+ap_Info+fib_Protection+3,(a2)+
1330         geta    Anchor+ap_Info+fib_FileName,a0
1331 CopyFileNameA   move.b  (a0)+,(a2)+
1332         bne.s   CopyFileNameA
1333         sub.l   d0,a2
1334         add.l   a2,d6
1335         addq.l  #RFC_ProtBits,d6
1336         rts             ;A1=FC_FileSize/FC_DirList
1337
1338 WasDir  tstv.b  Anchor+ap_Info+fib_FileName
1339         beq     ClimbedUp
1340         tstv.l  Arg_EmptyDirs
1341         bne.s   ClimbUp
1342         cmp.l   LH_TAILPRED(a4),a4      ;Is list empty?
1343         beq.s   RemoveThatNode
1344 ClimbUp move.l  a4,a0
1345         lea     DirItemCmp(pc),a1
1346         call    ss,SortList
1347 NoDirLength     pop     a4
1348         geta    Anchor+ap_Buf,a2
1349         move.l  a2,d1
1350         call    dos,FilePart
1351         cmp.l   d0,a2
1352         bne.s   LongerPath
1353         clr.b   (a2)
1354         bra     ClimbedUp
1355
1356 LongerPath      move.l  d0,a0
1357         clr.b   -(a0)
1358         bra     ClimbedUp
1359
1360 RemoveThatNode  lea     -FC_DirList(a4),a1
1361         call    exec,Remove
1362         lea     FC_FileName-FC_DirList(a4),a0
1363 DirNameLength   tst.b   (a0)+
1364         bne.s   DirNameLength
1365         sub.l   a4,a0
1366         sub.l   a0,d6
1367         addq.l  #FC_SIZEOF-FC_DirList-RFC_SIZEOF,d6
1368         bra.s   NoDirLength
1369
1370 ;Inputs: A1=FC_DirList
1371 InitDir move.l  a1,a4
1372         addq    #4,a1
1373         move.l  a1,(a4)
1374         clr.l   (a1)+
1375         move.l  a4,(a1)+
1376         bset.b  #7,(a1)
1377         rts
1378
1379 ;Inputs: A0=^^Node1 A1=^^Node2, Results: D0=-1/0/1 (Node1<=>Node2)
1380 DirItemCmp      move.l  (a0),a0
1381         move.l  (a1),a1
1382         lea     FC_ProtBits(a0),a0
1383         lea     FC_ProtBits(a1),a1
1384         tst.b   (a0)+
1385         smi     d0
1386         tst.b   (a1)+
1387         smi     d1
1388         sub.b   d1,d0
1389         beq.s   CompareString
1390         bpl     Return
1391         moveq   #-1,d0
1392         rts
1393
1394 CompareString   push    a6
1395         call    utility,Stricmp
1396         pop     a6
1397         rts
1398
1399 AllocMemTop     moveq   #0,d1
1400 AllocMemTopF    addqv.w #1,MEntries
1401         addq.l  #8,d2
1402         addq.l  #MEM_BLOCKMASK,d2
1403         and.w   #~MEM_BLOCKMASK,d2
1404         or.l    #MEMF_PUBLIC!MEMF_REVERSE!MEMF_KICK,d1
1405         mpush   d1/a0/a1
1406         bclrv.b #err_memory,sv_errsw+3
1407         move.l  d2,d0
1408         call    ss,TrackAllocMem
1409         bsetv.b #err_memory,sv_errsw+3
1410         tst.l   d0
1411         bne.s   AllocMemTopE
1412         move.l  d2,d0
1413         move.l  (sp),d1
1414         eor.w   #MEMF_KICK!MEMF_LOCAL,d1
1415         call    TrackAllocMem
1416 AllocMemTopE    addq    #4,sp
1417         mpop    a0/a1
1418         btstv.b #VerbB_Mem,Arg_Verbose+3
1419         beq.s   NoMemVerbose
1420         push    d1
1421         mpush   d0/d2
1422         push    a1
1423         dt.c    DetachMsg,<Detachable >
1424         dt.l    BlockMsg,<%s memory block allocated at $%08lx, size $%08lx>
1425         move.l  sp,a1
1426         call    Printf
1427         addq    #4,sp
1428         mpop    d0/d2
1429         pop     d1
1430 NoMemVerbose    addq    #8,d0
1431         rts
1432
1433 FlushStdout     get.l   stdout,d1
1434         jump    dos,Flush
1435
1436 Cleanup get.l   OldCurDir,d1
1437         call    dos,CurrentDir
1438         get.l   RootLock,d1
1439         call    UnLock
1440         getad   Anchor,a0,d1
1441         call    MatchEnd        ;after CurrentDir!
1442         tstv.l  Arg_Verbose
1443         beq.s   C_NoVerb
1444         dtl     <',$9B,' p>,a0
1445         call    ss,Puts
1446         bsr.s   FlushStdout
1447 C_NoVerb        get.l   InhibitEnd,d0
1448         beq     Return
1449         move.l  d0,a0
1450         move.b  #':',(a0)
1451         get.l   Arg_GenDisk,d1
1452         moveq   #DOSFALSE,d2
1453         jump    Inhibit
1454
1455 hunk_main       tst.l   d5
1456         bne     HunkError
1457         move.l  (a4,d4.l),d5
1458         push    d0
1459         call    BGetLong
1460         move.l  d5,a3
1461         move.l  -8(a3),d6
1462         cmp.l   #(HUNK_BSS-HUNK_NAME)<<17,(sp)+
1463         beq.s   DoBSS
1464         lsl.l   #2,d0
1465         sub.l   d0,d6
1466         add.l   d0,a3
1467         move.l  d5,a0
1468         call    BRead
1469 DoBSS   lsr.l   #2,d6
1470         subq.l  #2,d6
1471         move.w  d6,d0
1472         swap    d6
1473         bra.s   CPUClearInto
1474 CPUClearLoop    clr.l   (a3)+
1475 CPUClearInto    dbra    d0,CPUClearLoop
1476         dbra    d6,CPUClearLoop
1477         rts
1478
1479 hunk_end        tst.l   d5
1480         beq     HunkError
1481         moveq   #0,d5   ;No CurrHunk
1482         addq.l  #4,d4   ;HunkNum+=4
1483         rts
1484
1485 hunk_rrel16     moveq   #-1,d0
1486         bra.s   HunkReloc
1487 hunk_rel16      moveq   #1,d0
1488         bra.s   HunkReloc
1489 hunk_rel32      moveq   #0,d0
1490 HunkReloc       tst.l   d5
1491         beq.s   HunkError
1492         move.l  d5,a3
1493         move.l  -8(a3),d6
1494         subq.l  #8,d6
1495         move.l  d0,d2           ;RelocType
1496         lea     _LVOBGetLong(a6),a1
1497         beq.s   MainRelocLoop
1498         addq    #6,a1
1499 MainRelocLoop   jsr     (a1)
1500         tst.l   d0
1501         beq.s   RelocDone
1502         move.l  d0,d2
1503         jsr     (a1)
1504         lsl.l   #2,d0
1505         move.l  (a4,d0.l),d3
1506         bra.s   RelocInto
1507
1508 RelocLoop2      swap    d2
1509 RelocLoop1      jsr     (a1)
1510         cmp.l   d6,d0
1511         bcc.s   HunkError
1512         lea     (a3,d0.l),a0
1513         tst.w   d2
1514         bpl.s   NotRelRel
1515         move.l  a3,d0
1516         sub.l   d0,(a0)
1517 NotRelRel       add.l   d3,(a0)
1518 RelocInto       dbra    d2,RelocLoop1
1519         swap    d2
1520         dbra    d2,RelocLoop2
1521         bra.s   MainRelocLoop
1522
1523 RelocDone       call    BTell
1524         ror.b   #2,d0
1525         bcc     Return
1526         jump    BGetWord
1527
1528 hunk_symbol     call    BGetLong
1529         tst.l   d0
1530         beq     Return
1531         addq.l  #1,d0
1532         bsr.s   RelSeekLongs
1533         bra.s   hunk_symbol
1534
1535 BadHunk tstv.b  Advisory
1536         beq.s   HunkError
1537 hunk_skipcnt    call    BGetLong
1538 RelSeekLongs    lsl.l   #2,d0
1539         jump    BRelSeek
1540
1541 HunkError       moveq   #err_read,d0
1542         get.l   EOFRegs+5*4,a0  ;A2=BufFH
1543         move.l  bh_name(a0),a1
1544 ReportSS        jump    ss,ReportError
1545
1546 RawDiskWrite    move.l  bh_bufsize(a0),d1
1547         cmp.l   d1,d0
1548         bcc.s   RDW_Larger
1549         move.l  d1,d0
1550 RDW_Larger      move.l  a1,d1
1551         mpush   d0/d2/a2/a4
1552         bset.b  #0,bh_arg1+3(a0)
1553         bne.s   RDW_OtherWrite
1554         move.w  #255,d2
1555         moveq   #0,d0
1556 RDW_SumLoop     add.l   (a1)+,d0
1557         bcc.s   RDW_SkipX
1558         addq.l  #1,d0
1559 RDW_SkipX       dbra    d2,RDW_SumLoop
1560         not.l   d0
1561         move.l  d0,-1020(a1)
1562 RDW_OtherWrite  move.l  bh_handle(a0),a1        ;DeviceTracker
1563         move.l  trk_data(a1),a2         ;IoRequest
1564         move.l  d1,IO_DATA(a2)          ;^Buffer
1565         move.l  (sp),IO_LENGTH(a2)
1566         sub.l   a0,a0
1567         call    ss,ChkDoIO
1568         pop     d0
1569         add.l   d0,IO_OFFSET(a2)
1570         mpop    d2/a2/a4
1571         rts
1572
1573 ;### AbsModule header ###
1574 AbsModule       ;D2=Position in file to seek/2
1575 AbsModFH        equ     AbsModule-16
1576         ifd     ModDebug
1577         lea     AbsDosName(pc),a1
1578         call    exec,OldOpenLibrary
1579         move.l  d0,d6
1580         else
1581         move.l  GV_DosBase(a2),d6
1582         endc
1583         move.l  AbsModFH(pc),d7
1584         moveq   #OFFSET_BEGINNING,d3
1585         move.l  d7,d1
1586         lsl.l   #2,d2
1587         move.l  d6,a6
1588         call    Seek
1589         call    IoErr
1590         tst.l   d0
1591         bne.s   AbsExitErr
1592         lea     AbsModTab(pc),a3
1593         move.l  sp,d5
1594         clr.l   -(sp)
1595 AbsAllocLoop    move.l  (a3)+,d0
1596         beq.s   AbsAllocEnd
1597         move.l  (a3)+,a1
1598         move.l  d0,d3
1599         call    exec,AllocAbs
1600         move.l  d6,a6
1601         move.l  d0,d2
1602         beq.s   AbsAllocFail
1603         push    d0
1604         push    d3
1605         move.l  d7,d1
1606         addq    #8,d2
1607         subq    #8,d3
1608         call    Read
1609         cmp.l   d0,d3
1610         beq.s   AbsAllocLoop
1611 AbsExitErrFree  pop     d0
1612         beq.s   AbsExitErr
1613         pop     a1
1614         call    exec,FreeMem
1615         bra.s   AbsExitErrFree
1616
1617 AbsExitErr      moveq   #-1,d0
1618         rts
1619
1620 AbsAllocFail    moveq   #103,d1
1621         call    SetIoErr
1622         bra.s   AbsExitErrFree
1623
1624 EndMainInit     move.l  a3,(a2)+
1625         call    SumKickData
1626         move.l  d0,(a2)
1627         call    Permit
1628         jump    CacheClearU
1629
1630 AbsAllocEnd     move.l  d5,sp
1631         move.l  4.w,a6
1632         lea     KickMemPtr(a6),a2
1633         MyFORBID
1634         move.l  AbsKickSucc(pc),a0
1635         move.l  (a2),-(a0)      ;KickMemPtr
1636         move.l  a0,(a2)+
1637         move.l  (a2),d0         ;KickTagPtr
1638         beq.s   AbsNoNextReses
1639         bset.l  #31,d0
1640 AbsNoNextReses  move.l  d0,-(a0)
1641         move.l  AbsResList(pc),a3
1642         bsr.s   EndMainInit
1643
1644 AbsNextRes      move.l  (a3)+,d0
1645         ble.s   AbsNoNextRes
1646         move.l  d0,a2
1647         move.l  RT_NAME(a2),d2
1648         move.l  d2,a1
1649         call    FindResident
1650         bsr.s   AbsChkEnd
1651         lea     LibList(a6),a0
1652         bsr.s   AbsChkList
1653         lea     DeviceList(a6),a0
1654         bsr.s   AbsChkList
1655         move.l  a2,a1
1656         moveq   #0,d1
1657         call    InitResident
1658         bra.s   AbsNextRes
1659
1660 AbsChkList      move.l  d2,a1
1661         MyFORBID
1662         call    FindName
1663         call    Permit
1664 AbsChkEnd       tst.l   d0
1665         beq.s   AbsReturn
1666         addq    #4,sp
1667         bra.s   AbsNextRes
1668
1669 AbsNoNextRes    moveq   #0,d0
1670 AbsReturn       rts
1671
1672         ifd     ModDebug
1673 AbsDosName      dc.b    'dos.library',0
1674         even
1675         endc
1676
1677 AbsResList      equ     *+(*-AbsModule)&2
1678 AbsKickSucc     equ     AbsResList+4
1679 AbsModTab       equ     AbsKickSucc+4
1680
1681 AbsHdrLength    equ     (AbsResList-AbsModule+24)>>2
1682 AbsRawLength    equ     AbsResList-AbsModule
1683
1684 ;### BootBlock of the bootimage disk ###
1685
1686 BootImage       dc.l    'DOS'<<8,0,0
1687         move.l  a1,d4           ;IoRequest
1688         move.w  #CMD_READ,IO_COMMAND(a1)
1689         move.l  #1024,IO_OFFSET(a1)
1690         lea     ImgModTab(pc),a3
1691         lea     BootImage+512(pc),a4
1692         lea     BootImage+1024(pc),a5
1693         move.l  4.w,a6
1694 ImgAllocLoop    move.l  (a3)+,d0
1695         beq     ImgAllocEnd
1696         move.l  (a3)+,a1
1697         move.l  a1,d2
1698         move.l  d0,d3
1699         call    AllocAbs
1700         tst.l   d0
1701         beq.s   ImgAllocFail
1702         addq    #8,d2
1703         subq    #8,d3
1704         move.l  a5,d0
1705         sub.l   a4,d0
1706         cmp.l   d0,d3
1707         bcc.s   ImgCopyBuf
1708         move.l  d3,d0
1709 ImgCopyBuf      move.l  a4,a0
1710         add.l   d0,a4
1711         move.l  d2,a1
1712         add.l   d0,d2
1713         sub.l   d0,d3
1714         call    CopyMemQuick
1715         move.l  d3,d7
1716         and.w   #~511,d3
1717         eor.l   d3,d7
1718         bsr.s   ImgReadDisk
1719         cmp.l   a4,a5
1720         bne.s   ImgAllocLoop
1721         push    d2
1722         lea     BootImage+512(pc),a4
1723         move.l  a4,d2
1724         moveq   #64,d3
1725         lsl.l   #3,d3           ;One sector
1726         bsr.s   ImgReadDisk
1727         pop     d2
1728         move.l  d2,a1
1729         move.l  a4,a0
1730         add.l   d7,a4
1731         move.l  d7,d0
1732         call    CopyMemQuick
1733         bra.s   ImgAllocLoop
1734
1735 ImgReadDisk     move.l  d4,a1
1736         move.l  d2,IO_DATA(a1)
1737         add.l   d3,d2
1738         move.l  d3,IO_LENGTH(a1)
1739         call    DoIO
1740         move.l  d4,a1
1741         move.l  IO_OFFSET(a1),d1
1742         add.l   d3,IO_OFFSET(a1)
1743         tst.l   d0
1744         beq     ImgReturn
1745         push    d0
1746         mpush   d1/d3
1747         lea     ImgReadFailMsg(pc),a0
1748         bra.s   ImgDoAlert
1749
1750 ImgAllocFail    mpush   d2/d3
1751         lea     ImgAllocFailMsg(pc),a0
1752 ;A0=Printf-string, SP=Printf-data
1753 ImgDoAlert      move.l  sp,a1
1754         lea     -80(sp),sp
1755         move.l  sp,a3
1756         lea     ImgAlertHdr(pc),a2
1757 ImgAlertPrefix  move.b  (a2)+,(a3)+
1758         bne.s   ImgAlertPrefix
1759         subq.l  #1,a3
1760         call    RawDoFmt
1761         move.l  d0,a0
1762         clr.b   (a0)
1763         sub.l   sp,d0
1764         moveq   #82,d1
1765         sub.l   d0,d1
1766         lsl.w   #2,d1
1767         move.w  d0,-(sp)
1768         lea     ImgIntuiName(pc),a1
1769         call    OldOpenLibrary
1770         move.l  d0,a6
1771         moveq   #-1,d0
1772         moveq   #29,d1
1773         move.l  sp,a0
1774         call    DisplayAlert
1775         move.l  4.w,a6
1776         bra.s   ImgRebootNow
1777
1778 ImgAllocEnd     lea     KickMemPtr(a6),a2
1779         move.l  ImgKickSucc(pc),a0
1780         MyFORBID
1781         move.l  (a2),-(a0)      ;KickMemPtr
1782         move.l  a0,(a2)+
1783         move.l  (a2),d0         ;KickTagPtr
1784         beq.s   ImgNoNextReses
1785         bset.l  #31,d0
1786 ImgNoNextReses  move.l  d0,-(a0)
1787         move.l  ImgResList(pc),(a2)+
1788         call    SumKickData
1789         move.l  d0,(a2)
1790         call    CacheClearU
1791 ImgRebootNow    jump    ColdReboot
1792
1793 ImgReadFailMsg  dc.b    'Read(offs=%lu, len=%lu) error %ld!',0
1794 ImgAlertHdr     dc.b    16,'ResRAM boot: ',0
1795 ImgPutChar      move.b  d0,(a3)+
1796         clr.b   (a3)
1797 ImgReturn       rts
1798
1799 ImgAllocFailMsg dc.b    'AllocAbs($%08lx,$%08lx) fail!',0
1800 ImgIntuiName    dc.b    'intuition.library',0
1801
1802 ImgResList      equ     *+(4-(*-BootImage)&3)&3
1803 ImgKickSucc     equ     ImgResList+4
1804 ImgModTab       equ     ImgKickSucc+4
1805
1806         ifgt    ImgResList-BootImage+36-512
1807         fail    <Bootblock too big!>
1808         endc
1809
1810 ;### Code, which will be copied to the resident memory ###
1811 lerr    macro
1812         moveq   #255-ERROR_\1,d1
1813         endm
1814
1815 ResidentPart    dc.l    16
1816 ResSegList      dc.l    0
1817
1818 Res     move.l  4.w,a6
1819         amsg    <Entering handler''s code>
1820         lea     V(pc),v
1821
1822         move.l  ThisTask(a6),a0
1823         lea     pr_MsgPort(a0),a0
1824         move.l  a0,(v)                  ;ProcPort
1825
1826         bsr     GetPacketInt
1827
1828         lsl.l   #2,d4
1829         move.l  d4,a0
1830         move.l  (v),dn_Task(a0)
1831         moveq   #-1,d0
1832         moveq   #0,d1
1833         bsr     ReplyInt
1834
1835         amsg    <Startup packet replied>
1836
1837         lea     DosName(pc),a1
1838         call    OldOpenLibrary
1839         put.l   d0,DOSbase
1840         beq     DoOpenDOSAlert  ;ZF=1!
1841         move.l  d0,a6
1842         get.l   VolumeName,d1
1843         moveq   #DLT_VOLUME,d2
1844         call    MakeDosEntry
1845         lea     HInitFail1(pc),a3
1846         bsr     AlertD0Mem
1847         move.l  d0,a0
1848         move.l  d0,d1
1849         lsr.l   #2,d0
1850         geta    VolumeNode,a1
1851         move.l  d0,(a1)
1852         addq    #dl_Task,a0
1853         move.l  (v),(a0)
1854         addq    #dl_VolumeDate-dl_Task,a0
1855         movem.l GDateStamp(v),d0/d2-d3
1856         movem.l d0/d2-d3,(a0)
1857         move.l  -(a1),dl_DiskType-dl_VolumeDate(a0)     ;id_DiskType
1858         call    AddDosEntry
1859         bsr     AlertD0
1860         amsg    <Volume node added>
1861
1862         get.l   CmdsNames,a2
1863         lea     SkipCmdName(pc),a3      ;Okay, we may ignore it
1864         geta    FirstSegment,a4
1865 AddSegLoop      move.l  (a4),d2
1866         beq.s   OpenUtil
1867         amsg    <Adding one resident command>
1868         addq    #8,a4           ;Skip ResCmd checksum
1869         move.l  a2,d1
1870         moveq   #CMD_INTERNAL,d3
1871         call    AddSegment
1872         bsr     AlertD0
1873 SkipCmdName     tst.b   (a2)+
1874         bne.s   SkipCmdName
1875         bra.s   AddSegLoop
1876
1877 OpenUtil        lea     UtilName(pc),a1
1878         call    exec,OldOpenLibrary
1879         addq.l  #AO_UtilityLib-AO_DOSLib,d7
1880         lea     HInitFail2(pc),a3       ;VolumeNode from DosList
1881         bsr     AlertD0
1882         put.l   d0,UTILITYbase
1883
1884 MainLoop        pea     MainLoop(pc)
1885         put.l   sp,ErrSP
1886         amsg    <Calling GetPacket>
1887         bsr.s   GetPacket
1888         amsg    <Packet received>
1889         lea     FuncTable(pc),a2
1890 TableLoop       move.w  (a2)+,d7
1891         move.w  (a2)+,d0
1892         beq.s   NotInTable
1893         ext.l   d0
1894         cmp.l   d0,d1
1895         bne.s   TableLoop
1896         amsg    <Packet is known>
1897 NotInTable      jmp     (a2,d7.w)
1898
1899 ;Returns: D0/A1=ExecMsg, A2=DosPacket, D1=dp_Type, D2-D4=dp_Arg[1-3]
1900 GetLoop move.l  (v),a0
1901         call    WaitPort
1902 GetPacket       move.l  (v),a0
1903 GetPacketInt    call    GetMsg
1904         tst.l   d0
1905         beq.s   GetLoop
1906         move.l  d0,a0
1907         move.l  LN_NAME(a0),a0
1908         move.l  dp_Type(a0),d1
1909         movem.l dp_Arg1(a0),d2-d4
1910         put.l   a0,CurrPacket
1911         rts
1912
1913 ;---------------
1914 F_INFO          ;(lock,info):bool
1915         ifd     DEBUGX
1916         amsg    <INFO(>,0
1917         bsr     PrintLockName
1918         amsg    <)>
1919         endc
1920         move.l  d3,d2
1921 ;---------------
1922 F_DISK_INFO             ;(info):bool
1923         amsg    <DISK_INFO>
1924         lsl.l   #2,d2
1925         move.l  d2,a0
1926         movem.l MyInfoData(v),d0-d7/a1
1927         movem.l d0-d7/a1,(a0)
1928 ;---------------
1929 F_IS_FILESYSTEM         ;():bool
1930         amsg    <IS_FILESYSTEM>
1931 ReplyF0 moveq   #-1,d0
1932 ReplyX0 moveq   #0,d1
1933 ;---------------
1934 ReplyPacket     mpush   d0/d1
1935         move.l  sp,a1
1936         amsg    <Packet value: $%08lx, $%08lx>
1937         get.l   ErrSP,sp
1938 ReplyInt        amsg    <Replying packet>
1939         get.l   CurrPacket,a2
1940         move.l  (a2),a1         ;dp_Link (ExecMsg)
1941 ReplyDie        move.l  d0,dp_Res1(a2)
1942         move.l  d1,dp_Res2(a2)
1943         move.l  dp_Port(a2),a0  ;Port for replying
1944         move.l  (v),dp_Port(a2)
1945         jump    PutMsg
1946 ;---------------
1947 F_CURRENT_VOLUME        ;(arg1):volume
1948         ifd     DEBUGX
1949         amsg    <CURRENT_VOLUME(>,0
1950         bsr     PrintLockName
1951         amsg    <)>
1952         endc
1953         get.l   VolumeNode,d0
1954         bra.s   ReplyX0
1955 ;---------------
1956 F_SAME_LOCK             ;(lock1,lock2):bool
1957         ifd     DEBUGX
1958         amsg    <SAME_LOCK(>,0
1959         bsr     PrintLockName
1960         amsg    <,>,0
1961         move.l  d3,a0
1962         bsr     PrintLockNameX
1963         amsg    <)>
1964         endc
1965         lsl.l   #2,d2
1966         move.l  d2,a0
1967         move.l  fl_Key(a0),d0
1968         lsl.l   #2,d3
1969         move.l  d3,a0
1970         cmp.l   fl_Key(a0),d0
1971         beq.s   ReplyF0
1972 Reply00 moveq   #0,d0
1973         bra.s   ReplyX0
1974 ;---------------
1975 F_NIL
1976         ifd     DEBUGX
1977         move.w  d1,-(sp)
1978         move.l  sp,a1
1979         amsg    <ERROR_ACTION_NOT_KNOWN: #%d>
1980         addq    #2,sp
1981         endc
1982         lerr    ACTION_NOT_KNOWN
1983 Reply0XN        not.b   d1
1984 Reply0X moveq   #0,d0
1985         bra.s   ReplyPacket
1986 ;---------------
1987 F_FINDOUTPUT            ;(fh,lock,name):bool
1988 F_DELETE_OBJECT         ;(lock,name):bool
1989 F_CREATE_DIR            ;(lock,name):lock
1990 F_SET_PROTECT           ;(,lock,name,mask):bool
1991 F_SET_COMMENT           ;(,lock,name,comment):bool
1992 F_RENAME_OBJECT         ;(slock,sname,dlock,dname):bool
1993 F_RENAME_DISK           ;(name):bool
1994 F_SET_DATE              ;(,lock,name,stamp):bool
1995 F_SET_OWNER             ;(,,lock,userinf):bool
1996 F_MAKE_LINK             ;(lock,name,dest!#,soft):bool
1997         lerr    DISK_WRITE_PROTECTED
1998         bra.s   Reply0XN
1999 ;---------------
2000 F_FINDUPDATE            ;(fh,lock,name):bool
2001         moveq   #-1,d6
2002         bra.s   FindUpdateJmp
2003 ;---------------
2004 F_FINDINPUT             ;(fh,lock,name):bool
2005         amsg    <FINDINPUT>
2006         moveq   #0,d6
2007 FindUpdateJmp   push    d2
2008         move.l  d3,d2
2009         move.l  d4,d3
2010         bsr.s   LocateMain
2011         pop     a1
2012 JumpFhFromLock  ;D0=arg1 A1=fh, A0=^DiskObject
2013         tst.b   RFC_ProtBits(a0)
2014         bpl.s   FindInputFile
2015         move.l  d0,d2
2016         bsr.s   FreeLockMain
2017 ObjWrongType    lerr    OBJECT_WRONG_TYPE
2018         bra.s   Reply0XN
2019
2020 FindInputFile   add.l   a1,a1
2021         add.l   a1,a1
2022         clr.l   fh_Interactive(a1)
2023         move.l  d0,fh_Arg1(a1)
2024         bra.s   ReplyF0
2025 ;---------------
2026 F_FREE_LOCK             ;(lock):bool
2027         amsg    <FREE_LOCK>
2028 F_END           ;(arg1):bool
2029         ifd     DEBUGX
2030         amsg    <END(>,0
2031         bsr     PrintLockName
2032         amsg    <)>
2033         endc
2034         pea     ReplyF0(pc)
2035 ;---------------
2036 FreeLockMain    subqv.l #1,NumLocks
2037         lsl.l   #2,d2
2038         move.l  d2,a1
2039         jump    FreeVec
2040 ;---------------
2041 F_LOCATE_OBJECT         ;(lock,name,mode):lock
2042         amsg    <LOCATE_OBJECT>
2043         lerr    OBJECT_IN_USE
2044         addq.l  #-ACCESS_READ,d4
2045         bne.s   Reply0XN
2046         pea     ReplyX0(pc)
2047 ;---------------
2048 ;Inputs: D2=^Lock D3=Name D6=FindUpdate?
2049 LocateMainNoUpd moveq   #0,d6
2050 LocateMain
2051         ifd     DEBUGX
2052         amsg    <LocateMain(>,0
2053         bsr     PrintLockName
2054         move.l  d3,a0
2055         add.l   a0,a0
2056         add.l   a0,a0
2057         moveq   #0,d0
2058         move.b  (a0)+,d0
2059         lea     -30(sp),sp
2060         move.l  sp,a1
2061         bra.s   CopyDbgInto
2062 CopyDbgLoop     move.b  (a0)+,(a1)+
2063 CopyDbgInto     dbra    d0,CopyDbgLoop
2064         clr.b   (a1)
2065         push    sp
2066         move.l  sp,a1
2067         amsg    <,%s)>
2068         lea     34(sp),sp
2069         endc
2070
2071         lsl.l   #2,d3
2072         move.l  d3,a1
2073         moveq   #0,d3
2074         move.b  (a1)+,d3
2075
2076         move.l  a1,a0
2077         move.w  d3,d0
2078         bra.s   ColInto
2079 ColLoop cmp.b   #':',(a0)+
2080 ColInto dbeq    d0,ColLoop
2081         bne.s   ColSkip
2082         move.l  a0,a1
2083         move.w  d0,d3
2084 ColSkip
2085         get.l   RootPtr,a0
2086         lsl.l   #2,d2
2087         beq.s   LockInRoot
2088         amsg    <Lock in UserDir>
2089         move.l  d2,a2
2090         move.l  fl_Key(a2),a0
2091 LockInRoot      tst.b   RFC_ProtBits(a0)
2092         bpl.s   ObjWrongType    ;Given lock is to file
2093
2094 NextComponent   amsg    <NextComponent:>
2095         moveq   #108,d4         ;Name buffer size
2096         geta    NameBuffer,a2
2097         move.l  a2,a4
2098         lerr    INVALID_COMPONENT_NAME
2099         bra.s   NameLoopInto
2100
2101 NameLoop        move.b  (a1)+,d5
2102         cmp.b   #'/',d5
2103         beq.s   SlashFound
2104         subq.l  #1,d4
2105         beq     Reply0XN
2106         move.b  d5,(a2)+
2107 NameLoopInto    dbra    d3,NameLoop
2108         amsg    <End of FilePath reached>
2109         cmp.l   a2,a4
2110         beq.s   LockInternal
2111         amsg    <Locking file in CurrDir>
2112         bsr.s   FindDirItem
2113         amsg    <FindDirItem returned>
2114 ;---------------
2115 ;Inputs: A0=^Object, Results: D0=Lock (BPTR)
2116 LockInternal    mpush   d1/a0-a1
2117         ifd     DEBUGX
2118         amsg    <LockInternal(>,0
2119         push    a2
2120         bsr     PrintObjName
2121         pop     a2
2122         amsg    <)>
2123         endc
2124         moveq   #fl_SIZEOF,d0
2125         moveq   #MEMF_PUBLIC,d1
2126         call    AllocVec
2127         moveq   #ERROR_NO_FREE_STORE,d1
2128         tst.l   d0
2129         beq     Reply0X
2130         addqv.l #1,NumLocks
2131         move.l  d0,a0
2132         clr.l   (a0)+           ;fl_Link
2133         move.l  4(sp),(a0)+     ;fl_Key
2134         moveq   #ACCESS_READ,d1
2135         move.l  d1,(a0)+        ;fl_Access
2136         move.l  (v),(a0)+       ;fl_Task
2137         get.l   VolumeNode,(a0) ;VolumeNode->fl_Volume
2138         lsr.l   #2,d0
2139         mpop    d1/a0-a1
2140         amsg    <LockInternal end>
2141         rts
2142 ;---------------
2143 ;End>Empty>Lock CurrDir (A0)
2144 ;    Else >Lock FileName in CurrDir
2145 ;/  >Empty>Parent of CurrDir->A0
2146 ;    Else >Find FileName in CurrDir->A0 (must be DIR)
2147
2148 SlashFound      amsg    <SlashFound:>
2149         cmp.l   a2,a4
2150         bne.s   NoParent
2151         amsg    <Getting Parent>
2152         bsr.s   GetEntryParent
2153         beq.s   ObjNotFound
2154         amsg    <GetEntryParent returned>
2155         bra.s   NextComponent
2156
2157 NoParent        amsg    <Switching to sub-directory>
2158         bsr.s   FindDirItem
2159         amsg    <FindDirItem returned>
2160         bra.s   LockInRoot
2161
2162 ;---------------
2163 ;Inputs: A2=^End of filename A4=^NameBuffer A0=CurrDir D6=FindUpdate?
2164 ;Results: D0/A0=^DirEntry D5=Size A4=LastDir, Destroys: D2/D4
2165 FindDirItem     clr.b   (a2)
2166         ifd     DEBUGX
2167         mpush   a0-a2
2168         push    a4
2169         move.l  sp,a1
2170         amsg    <FindDirItem(%s,>,0
2171         addq    #4,sp
2172         bsr     PrintObjName
2173         amsg    <)>
2174         mpop    a0-a2
2175         endc
2176         moveq   #3,d2
2177 GetLongC        lsl.l   #8,d5
2178         move.b  (a0)+,d5
2179         dbra    d2,GetLongC
2180         tst.b   (a0)+           ;RFC_ProtBits
2181         bpl     ObjWrongType
2182 SkipNameB       tst.b   (a0)+
2183         bne.s   SkipNameB
2184         move.l  d5,d4
2185         add.l   a0,d4
2186
2187 FindFileLoop    cmp.l   d4,a0           ;D4=Address after current dir
2188         bcs.s   StillInDir
2189         lerr    DISK_WRITE_PROTECTED
2190         tst.l   d6
2191         bne     Reply0XN
2192 ObjNotFound     lerr    OBJECT_NOT_FOUND
2193         bra     Reply0XN
2194
2195 StillInDir      move.l  a0,d0
2196         moveq   #3,d2
2197 GetLongA        lsl.l   #8,d5
2198         move.b  (a0)+,d5
2199         dbra    d2,GetLongA
2200         addq    #RFC_FileName-RFC_ProtBits,a0
2201         mpush   d0-d1/a0-a1/a6
2202         move.l  a4,a1
2203         call    UTILITY,Stricmp
2204         move.l  d0,d2
2205         mpop    d0-d1/a0-a1/a6
2206 SkipNameC       tst.b   (a0)+
2207         bne.s   SkipNameC
2208         add.l   d5,a0
2209         tst.l   d2
2210         bne.s   FindFileLoop
2211         move.l  d0,a0
2212         rts
2213 ;---------------
2214 ;Inputs: A0=^Entry, Results: A0=^Parent entry, ZF=EQ if no parent
2215 GetEntryParent  mpush   d0-d2/a1-a2
2216         get.l   RootPtr,a2
2217         sub.l   a1,a1           ;Parent of Root is 0
2218 NextEntry       amsg    <NextEntry:>
2219         cmp.l   a0,a2
2220         beq.s   ParentReturn
2221         move.l  a2,d2
2222         moveq   #3,d0
2223 GetLongB        lsl.l   #8,d1
2224         move.b  (a2)+,d1
2225         dbra    d0,GetLongB
2226         move.b  (a2)+,d0        ;RFC_ProtBits
2227 ReachEndName    tst.b   (a2)+
2228         bne.s   ReachEndName
2229         amsg    <Name skipped>
2230         add.l   d1,a2
2231         tst.b   d0
2232         bpl.s   NextEntry
2233         amsg    <Obj is directory>
2234         cmp.l   a2,a0
2235         bcc.s   NextEntry
2236         amsg    <Walking into...>
2237         sub.l   d1,a2
2238         move.l  d2,a1           ;Current is parent
2239         bra.s   NextEntry
2240
2241 ParentReturn    amsg    <ParentReturn:>
2242         move.l  a1,a0
2243         move.l  a0,d0
2244         mpop    d0-d2/a1-a2
2245         rts
2246 ;---------------
2247 F_FH_FROM_LOCK          ;(fh,lock):bool
2248         amsg    <FH_FROM_LOCK>
2249         exg     d2,d3
2250 F_PARENT_FH             ;(arg1):lock
2251         amsg    <PARENT_FH>
2252 F_PARENT                ;(lock):lock
2253         amsg    <PARENT>
2254 F_COPY_DIR_FH           ;(arg1):lock
2255         amsg    <COPY_DIR_FH>
2256 F_COPY_DIR              ;(lock):lock
2257         ifd     DEBUGX
2258         amsg    <COPY_DIR(>,0
2259         bsr     PrintLockName
2260         amsg    <)>
2261         endc
2262         lsl.l   #2,d2
2263         move.l  d2,a0
2264         move.l  fl_Key(a0),a0
2265         move.w  d1,d0
2266         lsl.w   #2,d0
2267         and.w   d1,d0
2268         beq.s   DoCopyDir               ;COPY_DIR(|_FH)
2269         amsg    <Getting parent of the lock>    ;PARENT(|_FH)
2270         bsr.s   GetEntryParent
2271         beq     Reply00
2272         amsg    <GetEntryParent returned>
2273 DoCopyDir       bsr     LockInternal
2274         amsg    <PARENT/COPY_DIR locked>
2275         cmp.w   #ACTION_FH_FROM_LOCK,d1
2276         bne     ReplyX0
2277         move.l  d3,a1
2278         bra     JumpFhFromLock
2279 ;---------------
2280 F_SEEK          ;(arg1,pos,mode):oldpos/-1
2281         amsg    <SEEK>
2282 F_READ          ;(arg1,&buf,len):len/-1
2283         ifd     DEBUGX
2284         amsg    <READ(>,0
2285         bsr     PrintLockName
2286         amsg    <)>
2287         endc
2288         lsl.l   #2,d2
2289         move.l  d2,a1
2290         move.l  (a1)+,d5        ;fl_Link - Current position
2291         move.l  (a1),a0         ;fl_Key
2292         moveq   #3,d2
2293 GetLongD        lsl.l   #8,d0
2294         move.b  (a0)+,d0
2295         dbra    d2,GetLongD
2296         tst.b   (a0)+           ;RFC_ProtBits
2297         bpl.s   ObjIsFile
2298         amsg    <Wrong type!>
2299         lerr    OBJECT_WRONG_TYPE
2300 ReplyFXN        not.b   d1
2301 ReplyFX moveq   #-1,d0
2302         bra     ReplyPacket
2303 ;---------------
2304 F_WRITE         ;(arg1,&buf,len):len
2305         lerr    DISK_WRITE_PROTECTED
2306         bra.s   ReplyFXN
2307 ;---------------
2308 ObjIsFile       cmp.w   #ACTION_SEEK,d1
2309         beq.s   ActionIsSeek
2310         sub.l   d5,d0           ;D0=Remaining bytes
2311 SkipNameA       tst.b   (a0)+
2312         bne.s   SkipNameA
2313         add.l   d5,a0           ;a0=^1st byte for copy
2314         cmp.l   d0,d4
2315         bcc.s   DoReadFile
2316         amsg    <Read in range>
2317         move.l  d4,d0
2318 DoReadFile      add.l   d0,-(a1)
2319         move.l  d0,d2
2320         move.l  d3,a1
2321         call    CopyMem
2322         amsg    <Copied>
2323         move.l  d2,d0
2324         bra     ReplyX0
2325
2326 ActionIsSeek    lerr    SEEK_ERROR
2327         addq.l  #1,d4
2328         beq.s   SeekDone        ;OFFSET_BEGINNING=-1
2329         subq.l  #1,d4
2330         beq.s   SeekCurrent     ;OFFSET_CURRENT=0
2331         subq.l  #1,d4
2332         bne.s   ReplyFXN        ;OFFSET_END=1
2333         amsg    <offset_end>
2334         add.l   d0,d3           ;End-of-File
2335 SeekDone        cmp.l   d3,d0
2336         bcs.s   ReplyFXN
2337         move.l  -(a1),d0        ;Old position
2338         move.l  d3,(a1)         ;fl_Link
2339         bra     ReplyX0
2340
2341 SeekCurrent     amsg    <SeekCurrent:>
2342         add.l   d5,d3           ;fl_Link
2343         bra.s   SeekDone
2344 ;---------------
2345 F_EXAMINE_FH            ;(arg1,fib):bool
2346         amsg    <EXAMINE_FH>
2347 F_EXAMINE_OBJECT        ;(lock,fib):bool
2348         amsg    <EXAMINE_OBJECT>
2349 F_EXAMINE_NEXT          ;(lock,fib):bool
2350         ifd     DEBUGX
2351         amsg    <EXAMINE_NEXT(>,0
2352         bsr     PrintLockName
2353         amsg    <)>
2354         endc
2355         lsl.l   #2,d2
2356         move.l  d2,a0
2357         lsl.l   #2,d3
2358         move.l  d3,a1
2359         move.l  fl_Key(a0),a2
2360         pea     ReplyF0(pc)
2361         cmp.w   #ACTION_EXAMINE_NEXT,d1
2362         bne.s   ExamineMain
2363         lerr    NO_MORE_ENTRIES
2364         move.l  (a1),d3         ;fib_DiskKey
2365         beq     Reply0XN        ;ExNext without Examine
2366         moveq   #3,d2
2367 GetLongF        lsl.l   #8,d0
2368         move.b  (a2)+,d0
2369         dbra    d2,GetLongF
2370         tst.b   (a2)+           ;RFC_ProtBits
2371         bpl     ObjWrongType
2372 SkipNameD       tst.b   (a2)+
2373         bne.s   SkipNameD
2374         add.l   a2,d0           ;D0=End of this directory
2375         cmp.l   fl_Key(a0),d3
2376         beq.s   FirstEntryIn    ;A2=Entry to process
2377         move.l  d3,a2
2378         moveq   #3,d2
2379 GetLongG        lsl.l   #8,d3
2380         move.b  (a2)+,d3
2381         dbra    d2,GetLongG
2382         addq    #RFC_FileName-RFC_ProtBits,a2
2383 SkipNameE       tst.b   (a2)+
2384         bne.s   SkipNameE
2385         add.l   d3,a2
2386 FirstEntryIn    cmp.l   a2,d0
2387         beq     Reply0XN        ;No more entries
2388
2389 ;Inputs: A2=^DirEntry A1=^FileInfoBlock
2390 ExamineMain     move.l  a2,(a1)+        ;fib_DiskKey
2391         moveq   #3,d1
2392 GetLongE        lsl.l   #8,d0
2393         move.b  (a2)+,d0
2394         dbra    d1,GetLongE
2395         moveq   #ST_FILE,d1
2396         moveq   #0,d2
2397         move.b  (a2)+,d2
2398         move.l  d0,d4
2399         subq.l  #1,d4
2400         asr.l   #8,d4
2401         asr.l   #1,d4
2402         addq.l  #1,d4
2403         bclr.l  #7,d2
2404         beq.s   EntryTypeDone
2405         moveq   #0,d0           ;Size of directory is zero...
2406         moveq   #1,d4           ;... but the block size is 1 <- Magic
2407         moveq   #ST_USERDIR,d1
2408         tst.b   (a2)
2409         bne.s   EntryTypeDone
2410         moveq   #ST_ROOT,d1
2411         get.l   VolumeName,a2
2412 EntryTypeDone   move.l  d1,(a1)+        ;fib_DirEntryType
2413         lea     fib_Protection-fib_FileName(a1),a3
2414         move.l  a2,d3
2415 TestNameLength  tst.b   (a2)+
2416         bne.s   TestNameLength
2417         sub.l   d3,a2
2418         exg     d3,a2
2419         move.b  d3,(a1)+
2420 CopyFileNameB   move.b  (a2)+,(a1)+     ;RFC_FileName->fib_FileName
2421         bne.s   CopyFileNameB
2422         move.l  d2,(a3)+        ;fib_Protection /vvv-MORE MAGIC!!!
2423         move.l  d1,(a3)+        ;fib_EntryType (=fib_DirEntryType???)
2424         move.l  d0,(a3)+        ;fib_Size
2425         move.l  d4,(a3)+        ;fib_NumBlocks
2426         geta    GDateStamp,a0
2427         move.l  (a0)+,(a3)+     ;GDateStamp->fib_DateStamp
2428         move.l  (a0)+,(a3)+
2429         move.l  (a0),(a3)+
2430         clr.b   (a3)            ;fib_Comment
2431         bra     ReplyF0
2432 ;---------------
2433 F_DIE           ;():bool
2434         amsg    <DIE>
2435         lerr    OBJECT_IN_USE
2436         tstv.l  NumLocks
2437         bne     Reply0XN
2438         amsg    <Replying the DIE packet to my killer>
2439         moveq   #-1,d0
2440         moveq   #0,d1
2441         bsr     ReplyInt
2442         amsg    <Death packet replied, closing UtilLib>
2443         get.l   UTILITYbase,a1
2444         call    exec,CloseLibrary
2445 HInitFail2      moveq   #LDF_VOLUMES!LDF_WRITE,d1
2446         call    DOS,LockDosList
2447         amsg    <LockDosList OK>
2448         get.l   VolumeNode,d2
2449         lsl.l   #2,d2
2450         move.l  d2,d1
2451         amsg    <Calling RemDosEntry>
2452         call    RemDosEntry
2453         amsg    <VolumeNode removed>
2454         moveq   #LDF_VOLUMES!LDF_WRITE,d1
2455         call    UnLockDosList
2456         amsg    <DosList freed>
2457 HInitFail1      amsg    <Forbidding>
2458         MyFORBID exec
2459         amsg    <DieResMod regs load>
2460         get.l   ResListPtr,a2
2461         move.l  (a2),d1
2462         moveq   #31,d2
2463         move.l  ResModules(a6),d0
2464         beq.s   DieResModEnd
2465 DieResModChunk  amsg    <DieResModChunk:>
2466         move.l  d0,a0
2467 DieResModLoop   amsg    <DieResModLoop:>
2468         move.l  (a0),d0
2469         beq.s   DieResModEnd
2470         amsg    <Some entry>
2471         bclr.l  d2,d0
2472         bne.s   DieResModChunk
2473         amsg    <Resident pointer>
2474         cmp.l   (a0)+,d1
2475         bne.s   DieResModLoop
2476         amsg    <Resident is mine>
2477         move.l  a0,d0
2478         bset.l  d2,d0
2479         move.l  d0,-(a0)
2480 DieResModEnd    amsg    <DieTag regs load>
2481         get.l   ResListSucc,a1
2482         lea     KickTagPtr(a6),a0
2483         move.l  (a0)+,d0
2484         bne.s   DieTagInto
2485         amsg    <Empty KickTagPtr>
2486 DieTagNotFound  amsg    <DieTagNotFound:>
2487         and.w   #$7FFF,KickTagPtr(a6)
2488         addq    #4,a1
2489         lea     KickMemPtr(a6),a0
2490 DieMemLoop      amsg    <DieMemLoop:>
2491         move.l  (a0),d0         ;LN_SUCC
2492         beq.s   DieSumKick
2493         cmp.l   d0,a1
2494         beq.s   DieMemFound
2495         move.l  d0,a0
2496         bra.s   DieMemLoop
2497
2498 DieTagFound     amsg    <DieTagFound:>
2499         move.l  (a1),-(a0)
2500         bra.s   DieTagNotFound
2501
2502 DieTagLoop      amsg    <DieTagLoop:>
2503         move.l  (a0)+,d0
2504         beq.s   DieTagNotFound
2505         bpl.s   DieTagLoop
2506         bclr.l  d2,d0
2507 DieTagInto      amsg    <DieTagInto:>
2508         cmp.l   d0,a2
2509         beq.s   DieTagFound
2510         move.l  d0,a0
2511         bra.s   DieTagLoop
2512
2513 DieMemFound     amsg    <DieMemFound:>
2514         move.l  (a1),(a0)
2515 DieSumKick      call    SumKickData
2516         move.l  d0,KickCheckSum(a6)
2517         call    CacheClearU
2518         amsg    <KickCheckSum rewritten>
2519 DiePortLoop     amsg    <DiePortLoop:>
2520         move.l  (v),a0
2521         call    GetMsg
2522         tst.l   d0
2523         beq.s   DiePortOK
2524         amsg    <Some packet got>
2525         move.l  d0,a1           ;ExecMsg
2526         move.l  LN_NAME(a1),a2  ;DosPacket
2527         moveq   #0,d0
2528         lerr    OBJECT_IN_USE
2529         not.b   d1
2530         amsg    <Replying...>
2531         bsr     ReplyDie
2532         amsg    <ReplyDie returned>
2533         bra.s   DiePortLoop
2534
2535 DiePortOK       amsg    <DiePortOK:>
2536         get.l   DevNode,a0
2537         clr.l   dn_Task(a0)
2538         clr.l   dn_SegList(a0)
2539         amsg    <dn_(Task|SegList) cleared>
2540         call    Permit
2541         amsg    <Permit succeeded>
2542         get.l   VolumeNode,d1
2543         lsl.l   #2,d1
2544         call    DOS,FreeDosEntry
2545         amsg    <VolumeNode deallocated>
2546         move.l  a6,a1
2547         call    exec,CloseLibrary
2548         amsg    <DosLib closed>
2549         get.l   ErrSP,sp
2550         addq    #4,sp
2551         amsg    <The Final Forbid>
2552         MyFORBID
2553         get.l   RootPtr,a0
2554         move.l  -(a0),d0        ;ME_LENGTH
2555         move.l  -(a0),a1        ;ME_ADDR
2556         amsg    <Calling FreeMem for myself>
2557         call    FreeMem
2558         amsg    <Running in non-allocated memory!>
2559         moveq   #0,d0
2560         amsg    <Final RTS... shutting down....>
2561         rts
2562
2563 ;---------------
2564 func    macro   ;Function
2565         dc.w    F_\1-*-4,ACTION_\1
2566         endm
2567 FuncTable
2568 ;               ACTION_#?       ;Arg1   Arg2    Arg3    Res1
2569 ;               --------------------------------------------
2570 ;               STARTUP         ;?      startup devnode         bool
2571         func    FINDINPUT       ;fh     lock    name            bool
2572         func    FINDUPDATE      ;fh     lock    name            bool
2573         func    READ            ;arg1   &buf    len             len
2574         func    END             ;arg1                           bool
2575         func    SEEK            ;arg1   pos     mode            oldpos
2576         func    EXAMINE_NEXT    ;lock   fib                     bool
2577         func    EXAMINE_OBJECT  ;lock   fib                     bool
2578         func    INFO            ;lock   info                    bool
2579         func    DISK_INFO       ;info                           bool
2580         func    PARENT          ;lock                           lock
2581         func    LOCATE_OBJECT   ;lock   name    mode            lock
2582         func    COPY_DIR        ;lock                           lock
2583         func    FREE_LOCK       ;lock                           bool
2584         func    CURRENT_VOLUME  ;arg1                           volume
2585         func    SAME_LOCK       ;lock1  lock2                   bool
2586         func    IS_FILESYSTEM   ;                               bool
2587         func    FH_FROM_LOCK    ;fh     lock                    bool
2588         func    PARENT_FH       ;arg1                           lock
2589         func    EXAMINE_FH      ;arg1   fib                     bool
2590         func    COPY_DIR_FH     ;arg1                           lock
2591 ;Write-protected functions
2592         func    WRITE           ;arg1   &buf    len             len
2593         func    FINDOUTPUT      ;fh     lock    name            bool
2594         func    DELETE_OBJECT   ;lock   name                    bool
2595         func    CREATE_DIR      ;lock   name                    lock
2596         func    SET_PROTECT     ;       lock    name    mask    bool
2597         func    SET_COMMENT     ;       lock    name    comment bool
2598         func    RENAME_OBJECT   ;slock  sname   dlock   dname   bool
2599         func    RENAME_DISK     ;name                           bool
2600         func    SET_DATE        ;       lock    name    stamp   bool
2601         func    SET_OWNER       ;               lock    userinf bool
2602         func    MAKE_LINK       ;lock   name    dest!#  soft    bool
2603
2604         func    DIE             ;                               bool
2605         func    NIL     ;End-of-table mark
2606
2607 ;A0=Module with the checksum error
2608 SumError        mpush   a0/a6
2609         lea     ResIntuiName(pc),a1
2610         call    exec,OldOpenLibrary
2611         move.l  #AT_DeadEnd!AG_OpenLib!AO_Intuition,d7
2612         bsr     AlertD0
2613         move.l  d0,a6
2614         move.l  (sp),a0
2615         link    a2,#-$100
2616         lea     -252(sp),sp
2617         move.l  sp,a1
2618 SumErrLoop1     move.b  (a0)+,(a1)+
2619         bne.s   SumErrLoop1
2620         moveq   #53,d0
2621         add.l   sp,d0
2622         sub.l   a1,d0
2623         lsl.b   #2,d0
2624         clr.b   (a1)
2625         moveq   #(SumErrMsgEnd-SumErrMsg)>>2-1,d1
2626         lea     SumErrMsgEnd(pc),a0
2627 SumErrLoop2     push    -(a0)
2628         dbra    d1,SumErrLoop2
2629         move.b  d0,SumErrCenter-SumErrMsg(sp)
2630         move.l  sp,a0
2631         moveq   #0,d0           ;Recovery
2632         moveq   #61,d1
2633         call    DisplayAlert
2634         tst.l   d0
2635         beq.s   UserReboot
2636         unlk    a2
2637         mpop    a0/a6
2638         rts
2639
2640 UserReboot      move.l  4.w,a6
2641         not.l   ChkBase(a6)
2642         call    CacheClearU
2643         jump    ColdReboot
2644
2645 ResInit mpush   d6/d7/a2/a3/a6
2646         ifd     DEBUGX
2647         call    RawIOInit
2648         endc
2649         amsg    <ResidentInit started>
2650
2651         move.l  ResListSucc+V(pc),a0
2652         move.l  (a0)+,d0        ;ResListSucc
2653         add.l   (a0),d0         ;KickMemSucc
2654         lea     ResidentPart-2-RT_SIZE(pc),a1
2655         move.w  #(RT_SIZE+2+ResidentCode)>>2-1,d1
2656 ResSumLoop      sub.l   (a1)+,d0
2657         dbra    d1,ResSumLoop
2658         move.l  RootPtr+V(pc),a0
2659         move.l  -(a0),d1        ;ME_LENGTH
2660         add.l   -(a0),d1        ;ME_ADDR
2661         lea     AnySum+V(pc),a1
2662         clr.l   VolumeNode-AnySum(a1)
2663         clr.l   NumLocks-AnySum(a1)
2664 ResSumLoopE     sub.l   (a1)+,d0
2665         cmp.l   a1,d1
2666         bne.s   ResSumLoopE
2667         tst.l   d0
2668         beq.s   ResSumOkay
2669         lea     ResName(pc),a0
2670         bsr     SumError
2671
2672 ResSumOkay      amsg    <ResRAM checksumming passed, checksumming ResCmds...>
2673         lea     FirstSegment+V(pc),a2
2674         move.l  CmdsNames+V(pc),a0
2675 CmdSumsLoop     move.l  (a2)+,d0
2676         beq.s   CmdSumsDone
2677         bsr.s   SumModInit
2678 SkipResCmdName  tst.b   (a0)+
2679         bne.s   SkipResCmdName
2680         bra.s   CmdSumsLoop
2681
2682 SumModInit
2683         ifd     DEBUGX
2684         push    a0
2685         move.l  sp,a1
2686         amsg    <CheckSumming module "%s">
2687         addq    #4,sp
2688         endc
2689         moveq   #0,d7
2690         tst.l   (a2)
2691         beq.s   SumIncRet
2692         amsg    <This ResModule HAS checksum>
2693 SumOneModule    lsl.l   #2,d0
2694         move.l  d0,a1
2695         move.l  (a1)+,d0
2696         move.l  -8(a1),d1
2697         lsr.l   #2,d1
2698         subq.l  #3,d1
2699         bmi.s   SumOneHunkEnd
2700         move.w  d1,d6
2701         swap    d1
2702 SumOneHunkLoop  add.l   (a1)+,d7
2703         dbra    d6,SumOneHunkLoop
2704         dbra    d1,SumOneHunkLoop
2705 SumOneHunkEnd   tst.l   d0
2706         bne.s   SumOneModule
2707         tst.l   d7
2708         seq     d1
2709         sub.b   d1,d7
2710 SumIncRet       cmp.l   (a2)+,d7
2711         bne     SumError
2712         amsg    <CheckSum okay!>
2713         rts
2714
2715 CmdSumsDone     amsg    <Checksumming libraries and kickmods...>
2716         move.l  ResListPtr+V(pc),a3
2717         addq    #4,a3           ;Skip ^MyResident struct
2718 ResSumsLoop     move.l  (a3)+,d0
2719         ble.s   ResSumsDone
2720         move.l  d0,a0
2721         move.l  RT_NAME(a0),a0
2722         move.l  (a2)+,d0
2723         bsr.s   SumModInit
2724         bra.s   ResSumsLoop
2725
2726 ResSumsDone     amsg    <All checksums done!>
2727         move.l  DosHName+V(pc),a2
2728         moveq   #0,d0
2729         move.b  (a2),d0
2730         addq.l  #2,d0
2731         moveq   #MEMF_PUBLIC,d1
2732         call    AllocVec
2733         lea     ResInitFail(pc),a3
2734         bsr     AlertD0Mem
2735         amsg    <DosHandler name allocated>
2736         move.l  d0,a0
2737         move.l  d0,d6
2738         moveq   #0,d0
2739         move.b  (a2),d0
2740 DosNCopy        move.b  (a2)+,(a0)+
2741         clr.b   (a0)
2742         dbra    d0,DosNCopy
2743         amsg    <DosHandler name copied>
2744
2745         moveq   #(DeviceNode_SIZEOF+FileSysStartupMsg_SIZEOF+de_Baud+1+DeviceNameEnd-DeviceName)>>1,d0
2746         lsl.l   #1,d0
2747         move.l  #MEMF_PUBLIC!MEMF_CLEAR,d1
2748         call    AllocVec
2749         bsr     AlertD0
2750         amsg    <DeviceNode allocated>
2751         move.l  d0,a0
2752         exg     d0,d6
2753         lea     dn_StackSize+2(a0),a0
2754         move.w  #StdStackSize,(a0)+     ;dn_StackSize
2755         addq.l  #8,(a0)
2756         addq.l  #StdTaskPri-8,(a0)+     ;dn_Priority
2757         lea     DeviceNode_SIZEOF-dn_Startup(a0),a1
2758         move.l  a1,d1
2759         lsr.l   #2,d1
2760         move.l  d1,(a0)+        ;dn_Startup
2761         lea     ResSegList(pc),a1
2762         move.l  d6,DevNode+V-ResSegList(a1)
2763         move.l  a1,d1
2764         lsr.l   #2,d1
2765         move.l  d1,(a0)+        ;dn_SegList
2766         not.l   (a0)+           ;dn_GlobalVec
2767         lsr.l   #2,d0
2768         move.l  d0,(a0)         ;dn_Name
2769         addq    #DeviceNode_SIZEOF-dn_Name+fssm_Device-FileSysStartupMsg,a0
2770         lea     FileSysStartupMsg_SIZEOF-fssm_Device+de_Baud-DosEnvec(a0),a1
2771         move.l  a1,d0
2772         lsr.l   #2,d0
2773         move.l  d0,(a0)+        ;fssm_Unit
2774         lea     FileSysStartupMsg_SIZEOF-fssm_Environ+DosEnvec(a0),a1
2775         move.l  a1,d0
2776         lsr.l   #2,d0
2777         move.l  d0,(a0)         ;fssm_Environ
2778         moveq   #DE_DOSTYPE,d0
2779         move.l  d0,(a1)+        ;de_TableSize
2780         lsl.l   #3,d0           ;DE_DOSTYPE(=16)<<3=128
2781         move.l  d0,(a1)         ;de_SizeBlock
2782         addq    #de_Surfaces-de_SizeBlock,a1
2783         addq.l  #1,(a1)+        ;de_Surfaces
2784         addq.l  #1,(a1)+        ;de_SectorPerBlock
2785         addq.l  #1,(a1)         ;de_BlocksPerTrack
2786         lea     de_HighCyl-de_BlocksPerTrack(a1),a0
2787         move.l  MyInfoData+id_NumBlocks+V(pc),(a0)
2788         subq.l  #1,(a0)+        ;de_HighCyl
2789         addq.l  #5,(a0)+        ;de_NumBuffers
2790         addq.l  #MEMF_PUBLIC,(a0)+      ;de_BufMemType
2791         move.l  #1<<31-1,(a0)+  ;de_MaxTransfer
2792         not.l   (a0)+           ;de_Mask
2793         move.l  VarBootPri+V(pc),(a0)+  ;de_BootPri
2794         move.l  #'RES'<<8,(a0)+ ;de_DosType
2795 MyDiskTypeAddr  equ     *-4
2796         lea     DeviceName(pc),a1
2797 CopyDevName     move.b  (a1)+,(a0)+
2798         bne.s   CopyDevName
2799         amsg    <DeviceNode filled>
2800
2801         lea     ExpName(pc),a1
2802         call    OldOpenLibrary
2803         move.l  #AG_OpenLib!AO_ExpansionLib,d7
2804         bsr.s   AlertD0
2805         move.l  d0,a6
2806         amsg    <Expansion opened>
2807
2808         call    AllocConfigDev
2809         lea     ResInitCFail(pc),a3
2810         bsr.s   AlertD0Mem
2811         amsg    <AllocConfigDev succeeded>
2812         move.l  d0,a1
2813         lea     ResName(pc),a0
2814         move.l  a0,LN_NAME(a1)
2815         move.b  #ERT_NEWBOARD!ERTF_DIAGVALID,cd_Rom+er_Type(a1)
2816         lea     MyDiagArea(pc),a0
2817         move.l  a0,cd_Rom+er_Reserved0c(a1)     ;er_Reserved0[c-f]
2818         amsg    <ConfigDev filled>
2819
2820         move.l  d6,a0
2821         move.b  VarBootPri+3+V(pc),d0
2822         moveq   #ADNF_STARTPROC,d1
2823         call    AddBootNode
2824         bsr.s   AlertD0
2825         amsg    <AddBootNode succeeded>
2826 ResInitCFail    move.l  a6,a1
2827         call    exec,CloseLibrary
2828 ResInitFail     amsg    <Initialization finished>
2829         mpop    d6/d7/a2/a3/a6
2830 Return  rts
2831
2832 ;### Debug part of the detach zone ###
2833
2834         ifd     DEBUGX
2835 DPrintf mpush   d0-d1/a0-a3/a6
2836         move.l  28(sp),a0
2837         addq    #2,a0
2838         move.l  4.w,a6
2839         lea     _LVORawPutChar(a6),a2
2840         MyFORBID
2841         call    RawDoFmt
2842         call    Permit
2843         ifd     WaitDbg
2844 Wait1   btst.b  #2,$dff016
2845         bne.s   Wait1
2846 Wait2   btst.b  #2,$dff016
2847         beq.s   Wait2
2848         endc
2849         mpop    d0-d1/a0-a3/a6
2850         rts
2851
2852 ;Inputs: D2=Lock
2853 PrintLockName   tst.l   d2
2854         bne.s   LockNonNull
2855         amsg    <NULL>,0
2856         rts
2857
2858 LockNonNull     push    d2
2859         move.l  sp,a1
2860         amsg    <$%08lx/>,0
2861         addq    #4,sp
2862         move.l  d2,a0
2863 ;Inputs: A0=Lock
2864 PrintLockNameX  add.l   a0,a0
2865         add.l   a0,a0
2866         move.l  fl_Key(a0),a0
2867
2868 ;Inputs: A0=^Object, Destroys: A0-A2 !!! VERY BIG STACK !!!
2869 PrintObjName    lea     -30(sp),sp
2870         move.l  sp,a2
2871         lea     RFC_FileName(a0),a1
2872         move.b  #':',(a2)+
2873 CopyName        move.b  (a1)+,(a2)+
2874         bne.s   CopyName
2875         lea     DPrintf(pc),a1
2876         move.w  #$4E75,(a1)
2877         bsr     GetEntryParent
2878         beq.s   ReachedRoot
2879         vcmp.l  RootPtr,a0
2880         beq.s   ReachedRoot
2881         move.b  #'/',(sp)
2882         bsr.s   PrintObjName
2883 ReachedRoot     lea     DPrintf(pc),a1
2884         move.w  #$48E7,(a1)
2885         push    sp
2886         move.l  sp,a1
2887         amsg    <%s>,0
2888         lea     34(sp),sp
2889         rts
2890         endc
2891
2892 ; ### MyDiagArea - ptr to it is in ConfigDev structure ###
2893 MyDiagArea      dc.b    DAC_BOOTTIME,0          ;da_Config,da_Flags
2894         dc.w    DiagAreaEnd-MyDiagArea  ;da_Size
2895         dc.w    0,DiagBootUp-MyDiagArea ;da_DiagPoint,da_BootPoint
2896         dc.w    ResName-MyDiagArea      ;da_Name
2897         dc.w    0,0                     ;da_Reserved01,da_Reserved02
2898
2899 AlertD0Mem      moveq   #AG_NoMemory>>16,d7
2900         swap    d7
2901 AlertD0 tst.l   d0
2902         bne.s   Return
2903         move.l  a6,(sp)
2904         call    exec,Alert
2905         pop     a6
2906         jmp     (a3)
2907
2908 DiagBootUp      amsg    <DiagBootUp started>
2909         lea     DosName(pc),a1
2910         call    exec,FindResident
2911 DoOpenDOSAlert  move.l  #AT_DeadEnd!AG_OpenLib!AO_DOSLib,d7
2912         bsr.s   AlertD0
2913         move.l  d0,a0
2914         move.l  RT_INIT(a0),a0
2915         amsg    <DiagBootUp - Initializing DOS>
2916         jmp     (a0)
2917 DosName dc.b    'dos.library',0
2918
2919 ResName dc.b    'ResRAM-Handler'
2920         ifne    (*-DosName)&1
2921         fail    <Odd length!>
2922         endc
2923 ResNumOne       dc.b    0,0,0
2924         even
2925 DiagAreaEnd
2926         dc.b    '$VER: '
2927 ResID   dc.b    'ResRAM-Handler 1.0 (5.2.95)',0
2928 ExpName dc.b    'expansion.library',0
2929 UtilName        dc.b    'utility.library',0
2930 DeviceName      dc.b    DeviceNameEnd-DeviceName-2,'none.device',0
2931 DeviceNameEnd
2932         ifne    (DeviceNode_SIZEOF+FileSysStartupMsg_SIZEOF+de_Baud+1+DeviceNameEnd-DeviceName)&1
2933         fail    <Odd length!>
2934         endc
2935 ResIntuiName    dc.b    'intuition.library',0
2936         even
2937 SumErrMsg       dc.b    0,96,28,'!! SYSTEM IS NOW UNRELIABLE -'
2938         dc.b    ' COLD REBOOT RECOMMENDED !!',0,-1
2939         dc.b    0,32,48,'LMB - Continue',0,-1
2940         dc.b    480>>8,480&$FF,48,'RMB - ColdReboot',0,-1,0
2941 SumErrCenter    dc.b    0,16,'ResRAM #'
2942         ifne    (*-SumErrMsg)&1
2943         fail    <Odd length!>
2944         endc
2945 ResNumTwo       dc.b    0,0,': Invalid checksum on '
2946 SumErrMsgEnd
2947         ifne    (SumErrMsgEnd-SumErrMsg)&3
2948         fail    <SumErr not long aligned!!>
2949         endc
2950 V       equ     ResidentPart+(*-ResidentPart+3)&~3
2951 ResidentCode    equ     V-ResidentPart
2952 SYSCNTold       equ     SYSCNT
2953 SYSCNT  set     0
2954         dv.l    ProcPort
2955         dv.l    UTILITYbase
2956         dv.l    CurrPacket
2957         dv.l    ErrSP
2958         dv.l    DOSbase
2959         dv.l    DevNode
2960
2961         dbuf    NameBuffer,108
2962         dv.l    VarBootPri
2963         dv.l    AnySum          ;Checksum of the main part
2964         dv.l    CmdsNames       ;^1st name of Resident Command
2965         dv.l    VolumeName      ;APTR to ASCIIZ of volume name
2966         dv.l    DosHName        ;APTR to BSTR of dos handler name
2967         dbuf    MyInfoData,id_SIZEOF
2968 VolumeNode      equ     MyInfoData+id_VolumeNode        ;BPTR
2969 NumLocks        equ     MyInfoData+id_InUse
2970         dv.l    RootPtr         ;APTR to root entry
2971         dv.l    ResListSucc     ;ResidentList successor
2972         dv.l    ResListPtr      ;^^MyResidentStruct
2973         dbuf    GDateStamp,ds_SIZEOF    ;Global DateStamp
2974         dbuf    FirstSegment,0  ;Label of seg of first ResCmd
2975
2976 ResidentVars    equ     SYSCNT
2977 SYSCNT  set     SYSCNTold
2978
2979 VerbOpt macro   ;<name>,<letter>,<description>
2980         ifc     '\1','All'
2981 VerbF_\1        equ     255
2982         else
2983         ifc     '\1','None'
2984 VerbF_\1        equ     254
2985         else
2986 VerbB_\1        equ     _VerbOpt
2987 VerbF_\1        equ     1<<_VerbOpt
2988 _VerbOpt        set     _VerbOpt+1
2989         endc
2990         endc
2991         dt.c    <',VerbF_\1,'\2>
2992         dc.b    '  \2: \3',10
2993         endm
2994 _VerbOpt        set     0
2995
2996         tags
2997         template <FILES/A,DEVICE,NAME,PRI=BOOTPRI/N/K,EMPTYDIRS/S,GENABS/K,GENDISK/K,NODISKREQ/S,NORUN/S,REBOOT/S,VERBOSE/K>
2998         dv.l    Arg_Files
2999         dv.l    Arg_Device
3000         dv.l    Arg_Name
3001         dv.l    Arg_BootPri
3002         dv.l    Arg_EmptyDirs
3003         dv.l    Arg_GenAbs
3004         dv.l    Arg_GenDisk
3005         dv.l    Arg_NoDiskReq
3006         dv.l    Arg_NoRun
3007         dv.l    Arg_Reboot
3008         dv.l    Arg_Verbose
3009         extrahelp
3010         dc.b    'Resident RAM-Disk loader v1.0 --- (c) 1995 Short Software',10,10
3011         dc.b    'FILES     - Directory/pattern for files to load',10
3012         dc.b    '            (Wildcards in directory names aren''t supported)',10
3013         dc.b    'DEVICE    - DOS device name of RES-Disk (def. RES:)',10
3014         dc.b    'NAME      - Volume name of RES-Disk (def. ResRAM)',10
3015         dc.b    'BOOTPRI   - Boot priority (def. 15)',10
3016         dc.b    'EMPTYDIRS - Don''t discard empty directories',10
3017         dc.b    'GENABS    - Filename where an AbsModule should be written',10
3018         dc.b    'GENDISK   - DOS device name for a boot image (e.g. DF0:)',10
3019         dc.b    'NODISKREQ - Suppress ''Insert disk...'' requester (only for GENDISK)',10
3020         dc.b    'NORUN     - Don''t mount RES-Disk',10
3021         dc.b    'REBOOT    - Reboot machine when the load succeeds',10
3022         dc.b    '            (Doesn''t apply to AbsModules or boot images)',10
3023         dc.b    'VERBOSE   - Verbosity switches (seq. of following letters):',10
3024         dt.c    VerbParseTab,<>
3025         VerbOpt All,A,<Turn all switches on>
3026         VerbOpt None,N,<Turn all switches off>
3027         VerbOpt Dirs,D,<Scanned directories>
3028         VerbOpt Files,F,<Scanned file names & types>
3029         VerbOpt LoadSeg,I,<Scan phase LoadSeg info>
3030         VerbOpt LoadFiles,L,<Files being loaded>
3031         VerbOpt Mem,M,<Memory being allocated>
3032         VerbOpt SizeMod,G,<Sizes of modules being generated>
3033         endhelp
3034         dt      <>
3035         defvar  <ResRAM>
3036         exitrout Cleanup
3037         finish
3038         end