1122 lines
48 KiB
Plaintext
Raw Normal View History

2019-06-29 23:17:50 +08:00
;
; File: TFSRFN2.a
;
; Contains: This file contains routines which operate on open files using
; refnums.
;
; Copyright: © 1982-1993 by Apple Computer, Inc., all rights reserved.
;
; Change History (most recent first):
;
; <SM7> 8/27/93 BH Removed <SM6>. The flushing stuff is now in CmdDone.
; <SM6> 8/3/93 BH Flushing critical volume info when changed for a volume in a
; manual-eject drive.
; <SM5> 5/20/93 kc Roll in R58 change from CubeE
; <R58> 6/22/92 csd #100889,1032495 <gbm>: Turned ClosePatch off.
; <SM4> 10/22/92 CSS Change some branch short instructions to branches.
; <SM3> 8/12/92 PN Radar #1036025. Clear the dirty bit of the FCBMdRByt when doing
; PBFlushFile call
; <SM2> 5/21/92 kc Append "Trap" to the names of GetEOFTrap and SetEOFTrap to avoid
; name conflict with the glue.
; <SM1> 4/1/92 kc Roll in DontTruncateMultiForks ComeFromPatchProc.
; Roll in ClosePatch from FileMgrPatches.a
; • Pre-SuperMario comments follow •
; <2> 9/12/91 JSM Add a header.
; <1.3> 4/13/89 DNF Vectored FileClose. When patching, watch out for other HFS code
; which joins (jumps to) FileClose at FClose
; <1.2> 3/2/89 DNF removed references to forROM; HFS now builds identically for ram
; or rom
; <1.1> 11/10/88 CCH Fixed Header.
; <1.0> 11/9/88 CCH Adding to EASE.
; <1.0> 2/11/88 BBM Adding file for the first time into EASE…
; 2/19/87 BB Vectored FClose.
; 2/3/87 BB Replaced use of "FCBEntLen" equate with the use of low memory
; variable "FSFCBLen".
; 12/12/86 BB Removed use of FCBClmpSize in FClose
; 10/27/86 BB Vectored TstMod routine.
; 9/24/86 BB Updated to use new MPW equates.
; 1/14/86 LAK Added ROM75Fix patches: set up A2 in FndFCB for non-indexed
; GetFCBInfo; pass appropriate flags to AllocTFS for FileAlloc;
; changed FClose and SetEOF calls to pass D2 options to
; TruncateFile; TstMod1 entry added and used by FClose which may
; not have a valid A0.
; 11/6/85 PWD Changed GetFCBInfo to skip volume control files when indexing.
; 11/1/85 PWD Fixed GetFCBInfo index FCB search (clobbered index if VRefNum
; specified)
; 10/29/85 LAK Vectored RfnCall, AdjEOF.
; 10/28/85 PWD Changed SetEOF to leave clump size rounding to TruncateFile
; 10/27/85 PWD Gutted LockRng and UnlockRng routines: leave code to check for
; ext. FS etc. but don't do anything for single-user local Mac
; systems.
; 10/21/85 LAK Flush file buffers more frequently (even for data forks of
; files) and close files even on most error conditions.
; 10/20/85 LAK Added flush of control cache for MFS volumes at FClose.
; 10/16/85 PWD Added LockRng and UnlockRng routines.
; 10/13/85 PWD Rewrote FndFCB to reduce code size (at some minor cost in speed)
; Changed SetEOF to interpret H-Bit to mean SetPEOF (vs. SetLEOF).
; 10/1/85 LAK FileAlloc no longer calls MFSFAlloc (code is shared since it was
; the same). AllocContig (Allocate with H-bit set) is finally
; supported. THIS STILL NEEDS SOME WORK. Moved MFSClose code here
; to share more code (flush of cache, clearing FCB space).
; Subroutined out CkFileRfn for FndFCB and RfNCall to share. All
; internal errors are now converted at CmdDone.
; 9/25/85 PWD Backed out of previous Close truncation change: truncate to PEOF
; to make sure space _Allocated is retained.
; 9/22/85 PWD Changed to truncate to LEOF instead of PEOF on Close.
; 9/21/85 LAK Call TrashBlocks instead of FlushCache in SetEOF shorten path.
; 9/6/85 LAK Finished removal of OwnBuf support (in SetEOF shorten path).
; 8/29/85 BB Added support for contiguous allocation (TFS FileAlloc).
; 8/29/85 LAK Don't flush MDB on file flush . . . (whole lotta flushin' going
; on). Also removed support for TFS OwnBuf.
; 8/22/85 PWD Changed to honor file-specific clump sizes
; 6/20/85 PWD Changed to use system CNode equates
; 6/19/85 PWD Changed non-hardware internal errors to FSDSIntErr.
; 6/4/85 PWD Removed SetFCBInfo entry point
; 5/28/85 PWD Added _SetFCBInfo
; 5/21/85 PWD Added _GetFCBInfo
; 5/6/85 PWD Changed FClose to flush FCB extent record to catalog.
; 4/25/85 PWD Changed FClose to truncate files open for write to their PEOF on
; close.
; 4/25/85 PWD Changed to convert all internal errors to IOErr.
; 4/4/85 PWD Expanded FClose to flush/close B*-Tree files
; 8/3/84 GSS Patched SetEOF to include SetEOFix patch from MSFileFix
; 8/2/84 GSS Put patch in RfnCall from MSFileFix (ReqstVol fix)
; 7/5/84 GSS Put FileAlloc patches in line from MSFileFix
; 8/31/83 LAK Subroutined part of FClose to share with GetFileInfo fix.
; 8/30/83 LAK Fixed bug in ADJEOF (A1) -> (A0)
; 3/6/83 LAK Fixed bug in SetEOF with IOLEOF = 0 (now deallocates the disk
; blocks . . .)
; 1/17/83 LAK Last pass changes.
; 12/21/82 LAK Changed to share code with fileclose . . .
; 12/8/82 LAK Reworked all files for new file system data structures. Changed
; refnum validity check in RFnCall.
; 12/7/82 LAK Changed to support mutiple VCB queue; only flushes files -
; FlushVol is used to flush a volume.
;
;_______________________________________________________________________
;
; External Routines: FileClose,FlushFile,SetEOF,GetEOF,GetFCBInfo
; LockRng,UnlockRng,FileAlloc
;
; Internal Routines: RfNCall,AdjEOF,TstMod
;
;_______________________________________________________________________
;_______________________________________________________________________
;
; Routine: FlushFile
; Arguments: A0.L (input) -- I/O parameter block: uses
; IORefnum: file to be flushed
; D0.W (output) -- error code
; Calls: RfNCall,FClose
;
; Function: Flushes the buffers associated with a file and writes any
; changed FCB info out to the disk directory.
;
; Modification History:
; 07 Dec 82 LAK Changed to support mutiple VCB queue; only flushes files -
; FlushVol is used to flush a volume.
; 21 Dec 82 LAK Changed to share code with fileclose . . .
;
; - the volume block map is not flushed; should it be?
;_______________________________________________________________________
BLANKS ON
STRING ASIS
FlushFile BSR FSQueue
ST FlushOnly ; only flush
BRA.S FlCls1
;_______________________________________________________________________
;
; Routine: FileClose
; (c) 1983 Apple Computer, Inc.
;
; Arguments: A0.L (input) -- pointer to parameter block, uses:
; IORefNum = refnum of file to close
; D0.W (output) -- 0 if file closed ok, errcode otherwise
; This call may be executed asynchronously.
; Calls: FSQueue,RFnCall,FClose,CmdDone
; Function: Remove a file from active duty.
;
;
; Modification History:
;
; 02 Dec 82 LAK A3 and A5 set up by FClose, so removed a line.
; Uses DisposBuf to get rid of any allocated buffer.
; 20 Dec 82 LAK Modified for new file system data structures; no longer
; returns buffer memory (buffer supplied by caller at open time);
; checks for resource/regular part of a file.
; 06 Jun 83 LAK Made Flush, Close ok for offline files.
;
; Sharable routines: routine to search a directory block for a file number.
;_______________________________________________________________________
FileClose:
MOVE.L jFileClose,-(SP) ; jumptable entry for vFileClose <dnf v1.3>
RTS ; go there
vFileClose: ; 'vectored' FileClose routine
; From ClosePatch in FileMgrPatches.a
;
; Function: Prevent a file _Close from occuring on a file that was opened by kSystemProcess
; unless we're currently running kSystemProcess. This keeps random people (apps with
; housekeeping code that closes lots of files, for example) from closing system-like
; files out from under us.
ClosePatchRegs reg a0-a2/d0-d1
movem.l ClosePatchRegs,-(sp) ; save regs we use
movea.l sp,a2 ; for safe, quick stack pointer restore
; *** NOTE: THIS PATCH IS DISABLED *** ; <R58>
; This patch was broken in System 7, and fixed with change <53>. The fix ; <R58>
; causes some third-party applications (QuicKeys, Retrospect Remote) to stop ; <R58>
; working because they are unable to close files. For Cube-E, well re-break this ; <R58>
; patch and revisit the entire issue later. ; <R58>
; <R58>
bra.s DoClosePop ; <58> Disable this patch ; <R58>
; check the refnum for validity. and locate the parallel FCB array element
move.w ioRefNum(a0),d0 ; get refnum being closed
bsr RefNumCheck ; is it legit?
bne.s DoClosePop ; if not, let the real trap deal with it
move.w ioRefNum(a0),d0 ; get refnum being closed
bsr ParallelFCBFromRefnum ; a1 = address of parallel FCB element
; check whether we have tagged the file -- this makes sure that we can even call the
; Process Mgr (since files are tagged only when the Process Mgr is available), but is
; cheaper than ProcessMgrExists
tst.l xFCBPid2(a1) ; is low long initialized?
bne.s @NeedToCheck ; jump if so, we need to make the trap calls
tst.l xFCBPid1(a1) ; is high long initialized?
beq.s DoClosePop ; both are uninitialized, OK to close!
; the quicker of the two checks is whether file opened by kSystemProcess, do it first
@NeedToCheck
pea kSystemProcess ; push low long of PSN
clr.l -(sp) ; push high long of PSN
clr.l -(sp) ; allocate storage for boolean and result
pea 4(sp) ; push address of kSystemProcess
pea xFCBPid1(a1) ; push address of PSN from parallel FCB
pea 10(sp) ; push address of Boolean
_SameProcess ; compare FCB PSN to kSystemProcess
addq.l #2,sp ; dump OSErr (Boolean OK on error)
tst.w (sp) ; check Boolean (still false if error)
beq.s DoClosePop ; jump if FCB not opened by kSystemProcess
; OK, file was opened by kSystemProcess, see whether _Close caller is also kSystemProcess
clr.w (sp) ; set Boolean to "false", for easier check later
suba.l #10,sp ; allocate storage for PSN (8 bytes) and result
pea 2(sp) ; push address of PSN storage
_GetSystemClientProcess ; get party responsible for this _Close call
pea 2(sp) ; push address of client PSN
pea 16(sp) ; push address of kSystemProcess
pea 18(sp) ; push address of Boolean
_SameProcess ; is current client same as kSystemProcess?
tst.w 10(sp) ; check boolean
beq.s DontClosePop ; if "false", caller is not kSystemProcess
; file not opened by kSystemProcess, or closer is also kSystemProcess
DoClosePop
movea.l a2,sp ; restore stack
movem.l (sp)+,ClosePatchRegs ; restore regs we used
BSR FSQueue ; wait until ready...
CLR.B FlushOnly ; flush and close the file
FlCls1 BSR RFnCall ; detect if file open, get FCB pointer
BEQ.S @1 ; br if ok
CMP.W #VolOffLinErr,D0 ; was it just off-line? exit for ext fs here
BNE.S ClsExit ; (close is ok for offline files cause
; they've been flushed)
@1 BSR.S FClose ; actually do flush and close now
ClsExit BRA CmdDone ; that's all folks.
; file was opened by kSystemProcess, but is being closed by someone else. Just say no!
DontClosePop
movea.l a2,sp ; restore stack
movem.l (sp)+,ClosePatchRegs ; restore regs we used
moveq.l #permErr,d0 ; set error code
move.w d0,ioResult(a0) ; agree in the iopb
rts ; return to caller
;_______________________________________________________________________
;
; Routine: FClose
;
; Arguments: Enter with (A1,D1) pointing at the FCB.
; FlushOnly (input) -- low memory flag: if 1, then flush only,
; do not close . . .
; All registers except D0 preserved.
; Calls: MyWriteBk,MyReadBk
; Called by: FileClose,FlushVolume,FlushFile
; Function: Called when file system wants to close or flush a file.
; Returns to one level above caller during execution.
;
; Modification History:
;
; 02-Dec-82 LAK Set up A2,A3 and A5 early to save bytes; reworked format.
; Uses Time global for modification date.
; 20-Dec-82 LAK Modified for latest file system changes . . . no longer
; writes directory block out, but marks it dirty . . .
; 21-Dec-82 LAK Uses low memory variable FlushOnly for flush-only flag (if
; zero, then close file, too)
; 17-Jan-83 LAK Modified for new directory entry data structure (no entry
; length byte, physical length in bytes)
; 4-Apr-85 PWD Modfied to close/flush B*-Tree file for TFS
; 25-Apr-85 PWD Changed FClose to truncate files to their PEOF on Close when
; open for write.
; 16-May-85 PWD Added options to FlushCache call, added code to write a copy
; of the file's catalog entry into the resource fork.
; 22-Aug-85 PWD Added code to round to file-specific clump size on truncate.
; 22-Aug-85 PWD Added code to flush out VCB for volume on _FlushFile.
; 22-Sep-85 PWD Changed to truncate to LEOF instead of PEOF on Close.
; 25-Sep-85 PWD Backed out of previous Close truncation change: truncate to
; PEOF to make sure space _Allocated is retained.
; <28Oct85> PWD Changed to save all registers except D0 across call
; <21May86> BB Modified to only call BTClose and BTFlush for system files.
; Note, this fix helps our file server friends but prohibits
; the use of BTClose and BTFlush for other user BTree files.
; ROM75FIX patch #43, Change Log # C8
; <19Aug87> BB/JB (C867) Fixed FClose problem which was not releasing BTCB's
; for eject, offline, and unmount.
;_______________________________________________________________________
FClose:
MOVE.L jFClose,-(SP) ; jump table entry for vFClose <19Feb87>
RTS ; go there <19Feb87>
vFClose ; 'vectored' FClose routine <19Feb87>
MOVE.L (SP)+,-(A6) ; save caller's addr <01Oct85>
MOVEM.L A0-A5/D1-D3,-(A6) ; Store scratch registers <28Oct85>
BSR TFSVCBTst ; Is this a TFS volume? <01Oct85>
BNE MFSClose ; Nope
TST.L FCBBTCBPtr(A1,D1) ; BTCB associated with this open file?
BEQ.S @3 ; No - just an ordinary file
CMPI.L #FSUsrCNID,FCBFlNm(A1,D1) ; a user BTree file? <21May86>
BHS.S @3 ; yes, don't BTFlush or BTClose it <19Aug87>
MOVE.W D1,D0 ; Copy RefNum
TST.B FlushOnly ; Just flushing?
BNE.S @1 ; Yes - don't close the B*-Tree file
JSR BTClose ; Flush & Close the B*-Tree file
BRA.S @2 ;
@1 JSR BTFlush ; Just flush B*-Tree information
@2 BNE FClsDn ; Bad time for errors (from CMGetCN)
@3 MOVEQ #0,D0 ; pass D0=0 to FlDone <21Oct85>
TST.W VCBDrvNum(A2) ; Volume offline?
BEQ FlDone ; If EQ, it is
CMP.L #FSUsrCNID,FCBFlNm(A1,D1) ; Special volume control file?
BLO FlDone ; If so, there's no catalog entry <29Aug85>
BCLR #FCBModBit,FCBMdRByt(A1,D1) ; in case the file is unmodified,
BEQ FlFilBuf ; we need not update the file catalog <21Oct85>
ResetAEOF ;<14Jan86>;TST.B FlushOnly ; Just flushing?
;<14Jan86>;BNE.S UpdFlCat ; If so, don't adjust the EOF
BSR TstMod1 ; Can we actually modify the file? <14Jan86>
; (may have been ejected and locked) <14Jan86>
BNE.S updFlCat ; If not, just update the catalog entry
MOVE.L FCBPLen(A1,D1),D3 ; New end of file <25Sep85>
; BTST #FCBOwnClp,FCBMdRByt(A1,D1) ; Clump size set for file? <12Dec86>
; BEQ.S @1 ; If not, truncate to this position <12Dec86>
; Round to next higher clump size:
; MOVEM.L D0-D1,-(SP) ; Save scratch regs. across call <12Dec86>
; MOVE.L D3,D0 ; Get new EOF <12Dec86>
; MOVE.L FCBClmpSize(A1,D1),D1 ; Get clump size for file <12Dec86>
; BSR RoundAlloc ; Compute new EOF, rounded to clump size <12Dec86>
; MOVE.L VCBAlBlkSiz(A2),D1 ; Pick up vol's aloc. block size <12Dec86>
; MULU D1,D0 ; Compute new EOF in bytes <12Dec86>
; MOVE.L D0,D3 ; Stash it for real-life use <12Dec86>
; MOVEM.L (SP)+,D0-D1 ; Restore scratch registers <12Dec86>
@1 MOVEQ #0,D2 ; Truncate to alloc block <14Jan86>
; from DontTruncateMultiForks <SM1>.start
@Regs reg d1-d4 ; <44>
; Look for other paths to the same fork as the one being closed.
MOVEM.L @Regs,-(SP) ; save input parameters <11Dec90 #17>
MOVE.W D1,D3 ; D3.W = our FCB <11Dec90 #17>
MOVE.L FCBFlNm(A1,D3.W),D2 ; D2.L = our file number <11Dec90 #17>
move.b fcbMdRByt(a1,d3.w),d4 ; d4.b = our fork's misc info <44>
BSR Gt1stFCB ; get (A1,D1) pointing to first FCB <11Dec90 #17>
@2 CMP.W D1,D3 ; same FCB? <11Dec90 #17>
BEQ.S @3 ; skip ourself if it is <11Dec90 #17>
CMP.L FCBFlNm(A1,D1),D2 ; file numbers match? <11Dec90 #17>
BNE.S @3 ; no <11Dec90 #17>
CMP.L FCBVPtr(A1,D1),A2 ; on the same volume? <11Dec90 #17>
bne.s @3 ; no <44>
move.b fcbMdRByt(a1,d1.w),d0 ; grab this forks kind <44>
eor.b d4,d0 ; see how it compares against ours <44>
btst.l #fcbRscBit,d0 ; are we the same? <44>
beq.s @7 ; if so, then there's another open path <44>
@3 BSR GtNxtFCB ; get next one until we run out <11Dec90 #17>
BCS.S @2 ; continue if more <11Dec90 #17>
; No second open path found, so do the truncate
MOVEM.L (SP)+,@Regs ; restore regs and <11Dec90 #17>
JSR TruncateFile ; Truncate to this position
BNE FlFilBErr ; Bad time for errors (from CMGetCN) <21Oct85>
BCLR #FCBModBit,FCBMdRByt(A1,D1) ; mark the FCB clean again in <PN>
BRA.S updFLCat
; A second path was found, so skip the truncation
@7 MOVEM.L (SP)+,@Regs ; we did nothing, but quite successfully <SM1>.end
BCLR #FCBModBit,FCBMdRByt(A1,D1) ; mark the FCB clean again in <14Jan86>
; case marked dirty by TruncateFile <14Jan86>
; Now retrieve the file's catalog entry, and update the information there:
updFlCat MOVE.L A1,-(A6) ; Save A1 across CMGetCN call
MOVE.L FCBDirID(A1,D1),D0 ; Set up parent's DirID
LEA FCBCName(A1,D1),A0 ; Point to file's CName
MOVEQ #0,D2 ; No file hint
JSR CMGetCN ; Look up the file entry in the catalog
MOVEA.L A1,A5 ; Stash file record pointer (same CC)
MOVEA.L (A6)+,A1 ; Restore FCB array pointer (same CC)
BNE FlFilBErr ; Bad time for errors (from CMGetCN) <21Oct85>
MOVEM.L A0-A1,-(SP) ; Save A0,A1 across _BlockMove
LEA FCBExtRec(A1,D1),A0 ; Point to extent record in FCB
LEA filExtRec(A5),A3 ; Point to data fork extent record
BTST #FCBFlgRBit,FCBMdRByt(A1,D1) ; Resource fork?
BEQ.S @1 ; If clear, this is a data fork FCB <29Aug85>
LEA filRExtRec(A5),A3 ; Point to resource fork extent record
@1 MOVEA.L A3,A1 ; Set dest. for _BlockMove
MOVEQ #lenXDR,D0 ; Length of extent record to copy
_BlockMove ; Copy it into the catalog
MOVEM.L (SP)+,A0-A1 ; Restore original A0,A1
LEA filStBlk(A5),A3 ; Update destination for UpDatFlNtry
BSR UpDatFlNtry ; Update the catalog
MOVE.L Time,filMdDat(A5) ; Set date/time modified
JSR CMUpdateCN ; Write out the modified catalog entry
BNE FlFilBErr ; Bad time for errors (from CMGetCN) <SM4> CSS
BTST #FCBFlgRBit,FCBMdRByt(A1,D1) ; Resource fork?
BEQ FlFilBuf ; Br if not <21Oct85> <SM4> CSS
CMP.L #128,FCBEOF(A1,D1) ; Room for a catalog entry copy?
BCS FlFilBuf ; If not, forget it <21Oct85> <SM4> CSS
MOVEM.L A1/D1,-(A6) ; Save FCB pointer across call
MOVE.L A0,A3 ; Save Key pointer
MOVEA.L VCBBufAdr(A2),A1 ; Point to volume cache
MOVE.W D1,D0 ; Set up file refNum
MOVEQ #0,D1 ; No options on GetBlock
MOVEQ #0,D2 ; First block of resource fork
JSR GetBlock ; Read it into the cache
BNE.S @2 ; Br on errors <21Oct85>
MOVE.L A0,-(SP) ; Save block pointer
LEA 48(A0),A1 ; Point into the block to write catalog entry
LEA ckrCName(A3),A0 ; Point to CNode name there
MOVEQ #(lenCKR-4-2),D0 ; Length of key - dirID - length byte+filler
_BlockMove ;
MOVEQ #(lenCKR-4-2),D0 ; Same length again
ADDA.L D0,A1 ; Update destination pointer
LEA filFlags(A5),A0 ; Source: catalog entry
MOVEQ #(filUsrWds+16-filFlags),D0 ; length to copy
_BlockMove ;
MOVEQ #(filUsrWds+16-filFlags),D0 ; length to advance pointer by
ADDA.L D0,A1 ; Update destination pointer
LEA filFndrInfo(A5),A0 ; Point to additional finder info
MOVEQ #16,D0 ; Length of finder info
_BlockMove ;
MOVEQ #16,D0 ; Distance to advance pointer
ADDA.L D0,A1 ; Advance the pointer
MOVE.L filCrDat(A5),(A1)+ ; Copy creation date
MOVE.L filLgLen(A5),(A1)+ ; Copy data fork's logical length
MOVE.L filRLgLen(A5),(A1)+ ; Copy resource fork's logical length
; Release the block again:
MOVEA.L (SP)+,A0 ; Restore block pointer
MOVEA.L VCBBufAdr(A2),A1 ; Cache Queue Header
MOVEQ #kRBDirty,D1 ; Block is dirty <01Oct85>
JSR RelBlock ; Release the block
@2 MOVEM.L (A6)+,A1/D1 ; Restore FCB pointer <21Oct85>
; Whether or not the file has been modified, flush it out so that no cache blocks are
; left around with invalid file refnums (future cache schemes may choose to ignore the
; trash option, but these may still want some indication of open/close for priority).
;
; MFS code rejoins us here . . .
FlFilBuf: MOVEQ #0,D0 ; Report success . . . <21Oct85>
; This entrypoint is used when an error has been encountered earlier. We flush
; Cache blocks for this file and still delete the FCB entry, but an error will
; be reported.
FlFilBErr: MOVEM.L A1/D0-D1,-(A6) ; Save regs across FlushCache <21Oct85>
MOVE.W D1,D0 ; set up to make a flushcache for the file
MOVEQ #0,D1 ; Clear options on FlushCache
TST.B FlushOnly ; Just flushing?
BNE.S @1 ; If so, keep cache blocks after flush
MOVEQ #kFCTrash,D1 ; Set flag to discard flushed cache blocks <01Oct85>
@1 MOVEA.L VCBBufAdr(A2),A1 ; Point to volume buffer
JSR FlushCache
BSR TFSVCBTst ; TFS vol <20Oct85>
BEQ.S @2 ; br if so <20Oct85>
BSR MFSCtlFlush ; flush control buffer for MFS <20Oct85>
@2 MOVEM.L (A6)+,A1/D0-D1 ; Restore FCB pointer, result code <21Oct85>
; D0 = result code here. We remove the entry if we are closing the file . . .
FlDone TST.B FlushOnly ; Check if we're just flushing
BNE.S fClsDn ; If so, we're all set <21Oct85>
LEA 0(A1,D1),A3 ; Point to the FCB entry
MOVEQ #0,D2 ; <03Feb87>
MOVE.W FSFCBLen,D2 ; (FCB length / 2) - 1 <03Feb87>
LSR.W #1,D2 ; <03Feb87>
SUBQ.W #1,D2 ; = number of words to clear <03Feb87>
@1 CLR.W (A3)+ ; First longword cleared marks FCB free
DBRA D2,@1 ; But let's go all out <21Oct85>
; D0 = result code here. We simply exit.
fClsDn MOVEM.L (A6)+,A0-A5/D1-D3 ; Restore scratch registers <28Oct85>
MOVE.L (A6)+,-(SP) ; go to caller with CCR reflecting D0
TST.W D0
RTS
MFSClose:
BCLR #FCBModBit,FCBMdRByt(A1,D1) ; in case the file is unmodified,
BEQ.S FlFilBuf ; we need not update the file catalog <21Oct85>
MOVE.W FCBFlPos(A1,D1),D3 ; file block number put here at open
BSR MFSDirRead ; read in the block to the volume's buffer <01Oct85>
BNE.S FlFilBErr ; this could be a real problem for user. <21Oct85>
; now find file entry within this dir block.
MOVEQ #0,D0 ; init index (should be zero anyway)
MOVE.L FCBFlNm(A1,D1.W),D3 ; look for file with same file num
@1 CMP.L FlFlNum(A5,D0.W),D3 ; this file?
BEQ.S @2 ; yes, got it to close it.
BSR GtNxEntry
BCS.S @1 ;
; if file disappears...
MOVEQ #FNFErr,D0
BRA.S FlFilBErr ; exit if we can't find it . . . <21Oct85>
@2 LEA FlStBlk(A5,D0),A3 ; destination for regular fork
BSR.S UpDatFlNtry ; code saving routine (trashes A3,D3)
MOVE.L Time,FlMdDat(A5,D0) ; use time global var for mod time
JSR MarkA5Block ; mark the block dirtied <01Oct85>
BRA.S FlFilBuf ; rejoin TFS code to flush cache for <01Oct85>
; this file.
; code sharing routine also used by GetFileInfo . . . A3 is reg fork destination
UpDatFlNtry
MOVE.L A4,-(SP) ; preserve A4
LEA FCBMdRByt(A1,D1),A4
MOVE.W (A4)+,D3 ; FCBMdRByt
LSL.W #7,D3 ; get FCBRscBit into carry
BCC.S @1 ; br if not the resource fork
ADD #10,A3 ; destination for rsrc fork is 10 later
@1 MOVE.W (A4)+,(A3)+ ; file start block (FCBSBlk)
MOVE.L (A4)+,(A3)+ ; file logical length (FCBEOF)
MOVE.L (A4)+,(A3)+ ; file physical length (FCBPLen)
MOVE.L (SP)+,A4 ; restore A4
RTS
;_______________________________________________________________________
;
; Routine: GetEOF
; (c) 1983 Apple Computer, Inc.
;
; Arguments: A0.L (input) -- pointer to parameter block, uses:
; IORefNum,IOLEOF
; D0.W (output) -- 0 if file open, errcode otherwise
; This call may be executed asynchronously.
; Calls: FSQueue,RfNCall,CmdDone
; Function: Get logical length information for an opened file.
;
; Modification History:
;
; 21 Dec 82 LAK Modified for new file system data structures.
; 17 Jan 83 LAK No longer returns physical length information.
;_______________________________________________________________________
GetEOFTrap
BSR FSQueue
BSR.S RfNCall ; is refnum for a valid open file?
BNE.S @1 ; br if not . . . (D0=0 if so)
MOVE.L FCBEOF(A1,D1),IOLEOF(A0) ; return the logical EOF
@1 BRA CmdDone
;_______________________________________________________________________
;
; Routine: RfNCall
;
; Arguments: A0.L (input) -- pointer to parameter block
; D0.W (output) -- file not open, bad refnum errs
; D1.W (output) -- offset from (A1) to FCB requested
; (i.e., (A1,D1) points at requested FCB)
; D2.L (output) -- file number
; A1.L (output) -- pointer to FCB buffer start
; A2.L (output) -- VCB pointer
; Status flags set according to D0.
; All other registers are preserved.
; Called by: FileClose,FileRead,GetEOF,TstMod
; Function: Get the refnum from the param list and return a pointer to
; the FCB.
;
; Modification History:
;
; 02 Dec 82 LAK Reworked format.
; 08 Dec 82 LAK Changed refnum validity check. Modified for new FCB structure.
; Status flags set according to D0.
; 20 Dec 82 LAK Changed to return VCB pointer in A2 if all is cool.
; 06 Jun 83 LAK Changed to call ExtOffLinCk (support for offline, ext fs vols)
; 02 Aug 84 GSS Inserted patch from MSFileFix to save VCB ptr in ReqstVol
;_______________________________________________________________________
RfNCall:
MOVE.L jRfNCall,-(SP) ; jumptable entry for vRfNCall <29Oct85>
RTS ; go there <29Oct85>
vRfNCall ; 'vectored' RfNCall routine <29Oct85>
MOVE.L FCBSPtr,A1 ; get ptr to FCBs
MOVEQ #0,D1 ; clear D1 high word
MOVE.W IORefNum(A0),D1 ; get refnum
BSR.S CkFileRfn ; validate the refnum as an FCB index <01Oct85>
BNE.S @1 ; br if bad or file not open <01Oct85>
MOVE.L FCBFlNm(A1,D1),D2 ; get the file's filenum <01Oct85>
MOVE.L FCBVPTR(A1,D1),A2 ; get VCB pointer, too
MOVE.L A2, ReqstVol
BSR ExtOffLinCk ; make sure it's on-line and for us
@1 TST D0 ; zero if refnum is ok . . .
RTS ; that's all folks...
; D1 now holds a valid refNum (?) - check it before returning it...
CkFileRfn:
MOVEQ #RfNumErr,D0 ; Be pessimistic here...
MOVEQ #0,D2 ; Clear upper half of D2
MOVE.W D1,D2 ; Copy for check
DIVU FSFCBLen,D2 ; Divide by FCB size <03Feb87>
SWAP D2 ; Get remainder in low word
SUBQ.W #2,D2 ; Remainder had better be 2 (length word)
BNE.S @2 ; If not, that's a bad refnum
CMP.W (A1),D1 ; Refnum within range?
BCC.S @2 ; If too high, that's too bad.
MOVEQ #FNOpnErr,D0 ; Is this file actually open?
TST.L 0(A1,D1) ; Check File number
BEQ.S @2 ; Sigh - and we were so close...
MOVEQ #0,D0 ; It's open - complete success!
@2 TST.W D0 ; Set condition codes
RTS
;_______________________________________________________________________
;
; Routine: TstMod,TstMod1 (has A1,D1 set up instead of A0)
; (c) 1983 Apple Computer, Inc.
;
; Arguments: A0.L (input) -- pointer to parameter block, uses:
; IORefNum
; D0.W (output) -- 0 if file writable, errcode otherwise
; This call may be executed asynchronously.
; Called By: FileWrite,SetEOF,FileAlloc
; Function: Test if a file is open, and if so, if it may be written to.
;
; Modification History:
;
; 21 Dec 82 LAK Modified for new file system data structures.
; 17 Jan 83 LAK Changed for write bit location change.
;_______________________________________________________________________
TstMod
MOVE.L jTstMod,-(SP) ; jump table entry for vTstMod <27Oct86>
RTS ; go there <27Oct86>
vTstMod ; 'vectored' TstMod routine <27Oct86>
BSR.S RFnCall ; first see if it's open
BNE.S TMExit ; if not, all done
TstMod1 ; entry used by FClose (A0 not set up) <14Jan86>
MOVEQ #WrPermErr,D0 ; check if file opened for write
BTST #FCBWrtBit,FCBMdRByt(A1,D1.W)
BEQ.S TMExit ; exit if no write permission
BSR CVFlgs ; check if vol locked or wr protected
TMExit TST.W D0 ; return status flags set on error
RTS
;_______________________________________________________________________
;
; Routine: GetFCBInfo
; (c) 1985 Apple Computer, Inc.
;
; Arguments: A0.L (input) -- pointer to parameter block, uses:
; IOVRefNum,IORefNum,IOFCBIndx
; D0.W (output) -- 0 if FCB found, errcode otherwise
; This call may be executed asynchronously.
; Calls:
; Function: Return FCB contents
;
;
; Modification History:
;
; 21-May-85 PWD New today.
; 6-Aug-85 PWD Fixed to pass control to external FS AFTER filling in
; I/O PB fields.
; 6-Oct-85 PWD Fixed to save I/O PB pointer in A0 for use by ext. FS
; 13-Oct-85 PWD Changed to reduce code size (at some small cost in speed)
; 01-Nov-85 PWD Fixed index FCB search (clobbered index if VRefNum specified)
; 06-Nov-85 PWD Changed to skip volume control files when indexing.
; <14Jan86> LAK Added ROM75Fix patch (set up A2 in FndFCB for non-indexed GetFCBInfo).
;_______________________________________________________________________
GetFCBInfo:
BSR FSQueue ; Wait our turn
BSR.S FndFCB ; Look for the FCB of interest
BNE.S @95 ; Punt on errors
MOVE.W D1,ioRefNum(A0) ; Return refNum to the caller (indexed case) <01Nov85>
LEA 0(A1,D1),A3 ; Point to FCB
MOVE.L A0,-(SP) ; Save A0
LEA ioFCBFlNm(A0),A1 ; Destination is PB <24Sep86>
MOVEA.L A3,A0 ; Source is FCB
MOVEQ #ioFIStILen,D0 ; Length of information to straight copy
_BlockMove ; Copy the first chunk
MOVEA.L (SP)+,A0 ; Restore IOPB pointer
MOVE.W VCBVRefNum(A2),ioFCBVRefNum(A0) ; Return volume refNum <24Sep86>
MOVE.L FCBClmpSize(A3),ioFCBClpSiz(A0) ; File clump size <24Sep86>
MOVE.L FCBDirID(A3),ioFCBParID(A0) ; Parent directory ID <24Sep86>
MOVE.L ioFileName(A0),D0 ; Pick up file name pointer
BEQ.S @80 ; If zero, we're done
MOVEA.L D0,A1 ; Make it the desination of _BlockMove
MOVE.L A0,-(SP) ; Save PB pointer across _BlockMove <PWD 06Oct85>
LEA FCBCName(A3),A0 ; Source is CName in FCB (loses PB Ptr)
MOVEQ #1,D0 ; Clear upper bytes in D0, add length byte
ADD.B (A0),D0 ; Pick up number of bytes to copy
_BlockMove ; Copy the filename
MOVEA.L (SP)+,A0 ; Restore pointer to I/O PB <PWD 06Oct85>
@80 MOVE.L A2,ReqstVol ; Set up ReqstVol, D1 for external FS <PWD 18Oct85>
MOVE.L A3,D1 ; Point D1 to FCB for ext. fs <PWD 18Oct85>
BSR CkExtFS ; One of our volumes? <PWD 18Oct85>
@95 BRA CmdDone ; Call it a day
FndFCB
MOVE.L FCBsPtr,A1 ; Point to the FCB array <13Oct85>
MOVE.W ioRefNum(A0),D1 ; Pick up the refNum supplied, if any <13Oct85>
MOVE.W ioFCBIndx(A0),D0 ; Get desired FCB by index? <13Oct85>
BEQ.S @90 ; If zero, request is by RefNum <13Oct85>
MOVEQ #0,D2 ; Clear high word <01Nov85>
MOVE.W ioVRefNum(A0),D2 ; Pick up volume refNum, if supplied <13Oct85>
BEQ.S @10 ; If none supplied, that's fine. <13Oct85>
MOVE.W D2,D0 ; Otherwise, set up for search <13Oct85>
BSR DtrmV1 ; Determine desired volume
BNE.S @95 ; Punt on errors
MOVE.L A2,D2 ; Get pointer to VCB <13Oct85>
MOVE.W ioFCBIndx(A0),D0 ; Recover FCB index <01Nov85>
@10 BSR Gt1stFCB ; Point to first FCB
@20 MOVE.L FCBFlNm(A1,D1),D3 ; FCB in use? <06Nov85>
BEQ.S @30 ; If fileNum is zero, it's not
MOVE.L FCBVPtr(A1,D1),A2 ; Point to VCB in question <06Nov85>
BSR TFSVCBTst ; Looking at a TFS volume? <06Nov85>
BNE.S @23 ; If not, consider this FCB <06Nov85>
CMP.L #FSUsrCNID,D3 ; Is this a volume control FCB? <06Nov85>
BCS.S @30 ; If so, skip it. <06Nov85>
@23 TST.L D2 ; Looking for a particular volume? <13Oct85>
BEQ.S @25 ; Nope - it's a match <13Oct85>
CMP.L FCBVPtr(A1,D1),D2 ; Otherwise, right volume? <13Oct85>
BNE.S @30 ; Nope - try next FCB
@25 SUBQ.W #1,D0 ; Match - that's one less to go
BEQ.S @90 ; If index = 0, this is the one desired
@30 BSR GtNxtFCB ; Advance to the next FCB <13Oct85>
BCS.S @20 ; Keep going as long as there are FCBs <13Oct85>
MOVEQ #fnOpnErr,D0 ; we've failed miserably
BRA.S @95
; D1 now holds a valid refNum (?) - check it before returning it...
@90 BSR CkFileRfn ; Validate the refnum <01Oct85>
MOVE.L FCBVPtr(A1,D1),A2 ; Set up VCB pointer (for non-indexed case) <14Jan86>
@95 TST.W D0 ; Set condition codes
RTS
;_______________________________________________________________________
;
; Routine: LockRng
; (c) 1985 Apple Computer, Inc.
;
; Arguments: A0.L (input) -- pointer to parameter block, uses:
; IOVRefNum,IORefNum
; D0.W (output) -- 0 if successful, errcode otherwise
; This call may be executed asynchronously.
; Calls:
; Function: Releases exclusive (write) access to a byte range of an open fork.
;
; Modification History:
;
; 16-Oct-85 PWD New today.
; <27Oct85> PWD Changed to do nothing for local volumes, pending resolution
; of exact semantics desired.
;_______________________________________________________________________
; Since neither LockRng nor _Unlockrng does anything substantial right now . . .
LockRng:
UnlockRng:
BSR FSQueue ; Wait our turn
BSR RfNCall ; Check refNum, ext. FS, etc.
BNE.S LockExit ; If not, punt right here & now
IF 0 THEN ; **************************************** <27Oct85>
MOVE.W FCBFlags(A1,D1),D3 ; Pick up current flag word
BSET #FCBFlgLBit,D3 ; Set range locked bit
BNE.S LockOK ; This is all a NOP if already locked
BSET #FCBFlgWBit,D3 ; Set write permission bit
BNE.S LockOK ; Lock is a NOP if file already open for write
BSR FCBScan ; Check currently open files for other write access paths
BNE.S LockExit ; Punt on errors
OKToLock MOVE.W ioRefNum(A0),D1 ; Recover file RefNum
MOVE.W D3,FCBFlags(A1,D1) ; Set locked/write permission bits
ENDIF ; **************************************** <27Oct85>
LockOK MOVEQ #0,D0
LockExit BRA CmdDone
;_______________________________________________________________________
;
; Routine: UnlockRng
; (c) 1985 Apple Computer, Inc.
;
; Arguments: A0.L (input) -- pointer to parameter block, uses:
; IOVRefNum,IORefNum
; D0.W (output) -- 0 if successful, errcode otherwise
; This call may be executed asynchronously.
; Calls:
; Function: Seizes exclusive (write) access to a byte range of an open fork.
;
; Modification History:
;
; 16-Oct-85 PWD New today.
; <27Oct85> PWD Changed to do nothing for local volumes, pending resolution
; of exact semantics desired.
;_______________________________________________________________________
IF 0 THEN ; **************************************** <27Oct85>
BSR FSQueue ; Wait our turn
BSR.S RfNCall ; Check refNum, ext. FS, etc.
BNE.S LockExit ; If not, punt right here & now
BCLR #FCBWrtLck,FCBMdRByt(A1,D1) ; Clear range locked bit
BEQ.S LockOK ; If not locked, this is a NOP
BCLR #FCBWrtBit,FCBMdRByt(A1,D1) ; If locked, clear write allowed now
BRA.S LockOK ; And complete sucessfully
ENDIF ; **************************************** <27Oct85>
;_______________________________________________________________________
;
; Routine: FileAlloc
; (c) 1983 Apple Computer, Inc.
;
; Arguments: A0.L (input) -- pointer to parameter block, uses:
; IORefNum,IOReqCount,IOActCount
; D0.W (output) -- 0 if file closed ok, errcode otherwise
; This call may be executed asynchronously.
; Calls:
; Function: Allocate more blocks to a file.
;
;
; Modification History:
;
; 21 Dec 82 LAK Modified for new file system data structures; allocates
; space up to the amount of free space on the disk.
; 05 Jul 84 GSS Put the MSFileFix patches in line
; <01Oct85> LAK Combined with MFS file alloc code. Added support for AllocContig.
;_______________________________________________________________________
; Allocate is generally used to reserve space prior to writing to a file. This is common when
; duplicating or copying a file. It is also done to assure some contiguity to a file for
; performance reasons, a forewarning to the file system that this file is going to need
; a certain amount of space.
;
; For MFS allocate, we want to use a different entry point than Alloc since we
; don't really NEED all we ask for (why not change this and really ask for it all? - I
; see little use in allocating a small amount if more is really needed . . . unless
; you want to get all remaining space).
;
; Allocate really could have many flavors. Contiguous allocation should always be
; attempted, and so this use of the H-bit is not so useful. Capps and I think that
; an allocate call which is absolute is more useful: since there is a call to get LEOF
; but not PEOF (except the costly GetFileInfo), a common need might be to ensure an
; absolute amount of space in the file; if the H-bit is set, the input parameter might
; be used as such. My recommendation:
;
; (1) Normal allocate remains relative for compatibility reasons; allocation is attempted
; contiguously, and as much space as possible up to requested space is allocated.
; (2) If H-bit is set, the allocation is absolute: this becomes a SetPEOF call except
; that PEOF must be > current LEOF and >= current PEOF for easiest implementation.
; Allocation is, as always, attempted in a contiguous block. This could also just
; fall into the SEOF code which would support all options w/o setting the LEOF except
; on truncations (maybe H-bit set on SetEOF call could be used to mean SetPEOF instead?).
; If all of allocation cannot be done, then DskFulErr should be returned with no
; allocation done.
;
; Allocation will generally try to exend the file at its end: if this is possible, it
; should always be done. The question is whether, if this fails, it is better to allocate
; in the vicinity of the file (non-contiguously), or as close as possible but contiguously
; at the risk of being far away from the file's current allocation.
toAlloc MOVEQ #0,D0 ; assume vanilla ExtendFile options <14Jan86>
; (also zero for MFS AllocSt call) <14Jan86>
BSR TFSVCBTst ; is it TFS or is it MFS <01Oct85>
BNE AllocSt ; allocate as much space as we can (MFS)<14Jan86>
BSR TFSBitTst ; H-bit set? <14Jan86>
BEQ.S @1 ; br if not <14Jan86>
MOVEQ #kEFContig,D0 ; if H-bit is set, do it contiguous <14Jan86>
@1 BRA AllocTFS ; <14Jan86>
FileAlloc:
BSR FSQueue ; wait our time
BSR TstMod ; test if may modify this file
BNE.S FAlExit ; (also exit for ext fs, offline vols)
MOVEQ #0,D6 ; assume we get none
MOVE.L IOReqCount(A0),D4 ; number of bytes to allocate
BEQ.S @1 ; br on zero request
TST.W VCBFreeBks(A2) ; any free? (this was added as a fix for MFS alloc
; which had a bug in this case: better to fix it there).
BEQ.S @1 ; br if not
BSR.S toAlloc ; allocate as much space as we can <01Oct85>
BNE.S FAlExit ; if we don't get it all, then error
; (we may need to put a TFS option in
; later to get as much as we can)
@1 MOVE.L D6,IOActCount(A0) ; report number actually allocated
BSR.S AdjEOF ; adjust everybody's phys&logical EOF's
MOVEQ #DskFulErr,D0 ; assume we didn't get what we wanted
CMP.L IOReqCount(A0),D6 ; did we?
BCS.S FAlExit ; exit if not
MOVEQ #0,D0 ; no error
FAlExit BRA CmdDone
;_______________________________________________________________________
;
; Routine: SetEOF
; (c) 1983 Apple Computer, Inc.
;
; Arguments: A0.L (input) -- pointer to parameter block, uses:
; IORefNum,IOLEOF
; D0.W (output) -- 0 if EOF set ok, errcode otherwise
; This call may be executed asynchronously.
; Calls: FSQueue,TstMod,GtNxBlk,AdjEOF,DAlBlks,Alloc,CmdDone, GetFilBuf
; Function: Set a new logical EOF for a particular file. The physical
; EOF is set to the next block boundary and the current file
; position will be pinned at this value (this may cause
; blocks to be deallocated or allocated).
;
; This call will reclaim space a file is not using. If the
; LEOF is set beyond the current physical EOF and there is
; not enough space on the disk, no change to the file's EOF
; parameters will be made, and a disk-full error will be reported.
;
;
; Modification History:
;
; 22 Dec 82 LAK Modified for new file system data structures; now only
; takes a logical EOF argument; corrected file shorten
; code.
; 06 Mar 83 LAK Fixed bug in SetEOF with IOLEOF = 0 (now deallocates
; the disk blocks . . .)
; 03 Aug 84 GSS Patched to invalidate deleted file block in file buffer so
; that it will not be written out to disk in a subsequent
; flushfile, etc. This was fixed before in MSFileFix patch
; at label SetEOFix.
; 16 May 85 PWD Set up FlushCache options on call.
; 4-Jun-85 PWD Changed to truncate files at clump boundaries
; <21Sep85> LAK Changed to call TrashBlocks when shortening a file.
; <13Oct85> PWD Changed to interpret H-bit set to mean SetPEOF vs. SetLEOF.
; <28Oct85> PWD Changed to leave clump size rounding to TruncateFile
;_______________________________________________________________________
SetEOFTrap:
BSR FSQueue
BSR TstMod ; test if we may modify this file.
BNE.S SEOFXit ; exit if cannot mod, or not open.
; (also for ext fs, offline vols)
MOVE.L IOLEOF(A0),D7 ; get requested logical end of file
MOVE.L D7,D4 ; and copy it
SUB.L FCBPLen(A1,D1.W),D4 ; compare with current PEOF
BHI.S lngthnFil ; it's longer. alloc blks
BCS.S shrtnFil ; it's shorter. dealloc blks if we can
; same length needs no extra treatment
; The file positions should be ordered <13Oct85>
; <13Oct85>
; CrPs <= LEOF <= PEOF (D7) <13Oct85>
; <13Oct85>
; The LEOF (and consequently, the CrPs) is only adjusted if the new PEOF is LOWER <13Oct85>
SEOFOK BSR TFSBitTST ; Check: was T(H)TFS bit set? <13Oct85>
BEQ.S @3 ; If not, adjust the LEOF as requested <13Oct85>
CMP.L FCBEOF(A1,D1.W),D7 ; Is new PEOF < current LEOF? <13Oct85>
BCC.S @5 ; If not, current LEOF is still valid. <13Oct85>
@3 MOVE.L D7,FCBEOF(A1,D1.W) ; set the new LEOF
CMP.L FCBCrPs(A1,D1.W),D7 ; is current position set past this?
BCC.S @5 ; br if not
MOVE.L D7,FCBCrPs(A1,D1.W) ; if so, pin to this
@5 BSR.S AdjEOF ; adjust any other FCBs for this file
MOVEQ #0,D0
SEOFXit BRA CmdDone
; Shorten the file. If setting length to zero, zero start block, phys EOF fields
; Else mark last block with 001, and dealloc the following blks
shrtnFil BSR TFSVolTst ; is it TFS, no, then let MFS handle
BNE.S MFSShrtnF ; the call
MOVE.L D7,D4 ; Recover requested LEOF
;<28Oct85> MOVEM.L D0-D1,-(SP) ; Save scratch regs. across call <22Sep85>
;<28Oct85> MOVE.L D4,D0 ; Get new EOF <22Sep85>
;<28Oct85> MOVE.L FCBClmpSize(A1,D1),D1 ; Get clump size for file <22Sep85>
;<28Oct85> BSR RoundAlloc ; Compute new EOF, rounded to clump size <22Sep85>
;<28Oct85> MULU VCBAlBlkSize+2(A2),D0 ; Compute new EOF in bytes <22Sep85>
;<28Oct85> MOVE.L D0,D4 ; Stash it for real-life use <22Sep85>
;<28Oct85> MOVEM.L (SP)+,D0-D1 ; Restore scratch registers <22Sep85>
;<28Oct85> CMP.L FCBPLen(A1,D1.W),D4 ; compare with current PEOF
;<28Oct85> BCC.S SEOFOK ; If D4 is >PEOF, leave it alone. <21Sep85>
; Truncate the file space beyond the (rounded) new PEOF:
MOVE.L D4,D3 ; used to figure new physical length
;<14Jan86>;ST FlushOnly ; Set to let TruncateFile round to clump
MOVEQ #kTFTrunExt,D2 ; set "round to extent" to avoid thrashing <14Jan86>
JSR TruncateFile ; truncate peof to leof
BNE.S SEOFXit ; exit if in trouble
ShrtnTrash: ; MFS code rejoins here <01Oct85>
MOVEM.L D0-D2,-(A6) ; now make sure cache is clear <21Sep85>
MOVE.W D1,D0 ; File refnum <21Sep85>
MOVE.L FCBPLen(A1,D1.W),D1 ; new PEOF <21Sep85>
MOVEQ #-1,D2 ; trash all blocks to the end . . . <21Sep85>
JSR TrashBlocks ; <21Sep85>
MOVEM.L (A6)+,D0-D2 ; when they may belong to another file . . .<21Sep85>
BRA.S SEOFOK ; finish up, no errors <21Sep85>
lngthnFil JSR Alloc ; need difference from current phys EOF
BNE.S SEOFXit ; exit if we couldn't get that much
BRA.S SEOFOK ; otherwise, finish up
;_______________________________________________________________________
;
; Routine: AdjEOF
;
; Arguments: (A1,D1) (input) -- FCB pointer
; All registers are preserved.
; Calls: Gt1stFCB,GtNxtFCB
; Called By: FileWrite,SetEOF,FileAlloc
; Function: Scan through the FCBs and update any entries with the
; same filenumber and resouce/regular bit to the same
; start blk, physical EOF, and logical EOF as the FCB
; pointed to by (A1,D1). The FCB is marked as modified.
;
; Modification History:
;
; 22 Dec 82 LAK Modified for new file system data structures; now only
; takes an FCB pointer and preserves all registers.
; 29 Aug 83 LAK Rewrote to take advantage of FCB field order and
; Gt1stMatch, GtNxtMatch subroutines.
; 11-Jul-85 PWD Fixed bug: added code to copy extent record from source FCB
;_______________________________________________________________________
AdjEOF:
MOVE.L jAdjEOF,-(SP) ; jumptable entry for vAdjEOF <29Oct85>
RTS ; go there <29Oct85>
vAdjEOF ; 'vectored' AdjEOF routine <29Oct85>
MOVEM.L D0-D6/A0-A5,-(SP) ; preserve all registers
ADD D1,A1 ; point to entry
MOVE.L (A1)+,D2 ; FCBFlNm
BSET #FCBModBit,(A1) ; mark file modified
MOVE.W (A1),D0 ; save FCBFlags
MOVEM.L (A1)+,D3-D6/A2 ; FCBSBlk,FCBEOF,FCBPLen,(FCBCrPs),FCBVPtr
MOVE.W D0,D6 ; FCBMdRByt (in high byte . . .)
LEA FCBExtRec-FCBBfAdr(A1),A1 ; Point to start of extent record
MOVEM.L (A1)+,A3-A5 ; Save extent record
; now scan thru all FCBs and update those for the same file (we update
; our own file's fields with the same information)
BSR Gt1stMatch ; scan from the beginning
BNE.S @3 ; exit if no matches found
@1 LEA FCBFlags(A1,D1),A0 ;
MOVE.W (A0)+,D0 ; same resource/regular flag bit?
EOR.W D6,D0
LSL.W #7,D0 ; get FCBRscBit in carry
BCS.S @2 ; br if they don't match
MOVE.W D3,(A0)+ ; FCBSBlk
MOVE.L D4,(A0)+ ; FCBEOF
MOVE.L D5,(A0)+ ; FCBPLen (A0 left pointing at FCBCrPs)
LEA FCBExtRec+lenXDR-FCBCrPs(A0),A0 ; Point to end of Extent record
MOVEM.L A3-A5,-(A0) ; Overwrite extent record
@2 BSR GtNxtMatch ; go after the next entry
BEQ.S @1 ; until we've done 'em all
@3 MOVEM.L (SP)+,D0-D6/A0-A5 ; leave registers unchanged
RTS ; that's all folks.