$TITLE('WD120.P28: iRMX - Winchester Driver Example') $ROM COMPACT OPTIMIZE(3) /*****************************************************************************\ * * Copyright Intel Corporation 1987, 1988 * All rights reserved * * For Intel customers licensed for the iRMX II System 120 under an * Intel Software License Agreement, this source code and object code * derived therefrom are licensed for use on a single central processing * unit for internal use only. Necessary backup copies are permitted. * Object Code derived from this source code is a Class I software product * under the Intel Software License Agreement and is subject to the terms * and conditions of that agreement. * * For the right to make incorporations, or to transfer this software to * third parties, contact Intel corporation. * \****************************************************************************/ $eject /*****************************************************************************\ * * TITLE: WD120.p28 * * HISTORY: 09/25/89 iRMX device driver example - Version 1.0 * * DESCRIPTION: Winchester Device Driver for AT platform. The driver * provides an interface between the RMX Basic I/O System * and the AT or AT compatible hard disk controller. * This driver supports the following products: * - Western Digital WD1003-WA2 * - Western Digital WD1006V-MM1 * - Western Digital WD1006V-MM2 * - System 300SX hard disk controller * * * PROCEDURES: iSYS120$wini$int * iSYS120$wini$init * iSYS120$wini$start * start_read_write * seek * restore_hd * format_trk * get_device_info * start_attach * start_detach * int_format * int_attach * set_params * set_bad_track_info * get_bad_track_info * find_error * set_error * wait_not_busy * wait_data_req * get_part_blk * get_disk_info * get_active_part * get_partition_info * load_interleave_table * get_generic_data * get_non_generic_data \****************************************************************************/ x120wd : DO; $include(:f1:comon.lit) $include(:f1:nutyp.lit) $include(:f0:nuclus.ext) $include(:f1:drinf.lit) $include(:f1:radsf.lit) $include(:f1:ioexc.lit) $include(:f0:error.lit) $include(:f1:iors.lit) $include(:f1:duib.lit) $include(:f1:param.lit) $include(:f1:wd120.lit) $SUBTITLE('iSYS120$wini$init') /**************************************************************************** * * PROC NAME: iSYS120$wini$init * * DESCRIPTION: init procedure for hard disks * * CALL: CALL iSYS120$wini$init(duib_ptr, ddata_ptr, status_ptr) * * INPUTS: duib_ptr - POINTER to Device-Unit Information Block * ddata_ptr - POINTER to device data segment * status_ptr - POINTER to WORD indicating status of operation * * OUTPUTS: none * ****************************************************************************/ iSYS120$wini$init : PROCEDURE(duib_ptr, ddata_ptr, status_ptr) PUBLIC REENTRANT; DECLARE /* params */ duib_ptr POINTER, ddata_ptr POINTER, status_ptr POINTER; DECLARE /* locals */ ddata BASED ddata_ptr ddata_struc, /* driver data */ status BASED status_ptr WORD; ddata.flags = RESTOREREQUIRED; status = E$OK; END iSYS120$wini$init; $SUBTITLE('iSYS120$wini$start') /**************************************************************************** * * PROC NAME: iSYS120$wini$start * * DESCRIPTION: Start procedure for hard disks. Issue appropriate controller * commands if required for operation requested. * * CALL: CALL iSYS120$wini$start(iors_ptr, duib_ptr, ddata_ptr); * * INPUTS: iors_ptr - POINTER to I/O Request/Result segment * duib_ptr - POINTER to Device-Unit Information Block * ddata_ptr - POINTER to device data segment * ****************************************************************************/ iSYS120$wini$start : PROCEDURE(iors_ptr, duib_ptr, ddata_ptr) PUBLIC REENTRANT; DECLARE /* params */ iors_ptr POINTER, duib_ptr POINTER, ddata_ptr POINTER; DECLARE /* locals */ iors BASED iors_ptr IO$REQ$RES$SEG, duib BASED duib_ptr DEV$UNIT$INFO$BLOCK, ddata BASED ddata_ptr ddata_struc, uinfo_ptr POINTER, /* points to unifo block */ uinfo BASED uinfo_ptr HDCINFOBLOCK, /* uinfo block */ dinfo_ptr POINTER, dinfo BASED dinfo_ptr HDC$DEVICE$INFO, u_data BASED ddata_ptr (NUMBEROFUNITS) unit_data, /* info for each unit */ cylinder WORD, /* cylinder number used in seek */ phys_unit BYTE, /* physical unit assoc w/logical unit */ unit BYTE, status WORD; iors.status = E$OK; dinfo_ptr = duib.device$info$p; uinfo_ptr = duib.unit$info$p; unit = duib.unit; IF (iors.funct > f$close) THEN DO; iors.status = E$IDDR; iors.done = TRUE; RETURN; END; DO CASE iors.funct; do$read:DO; CALL start_read_write(iors_ptr, duib_ptr, ddata_ptr); END do$read; do$write:DO; CALL start_read_write(iors_ptr, duib_ptr, ddata_ptr); END do$write; do$seek:DO; IF iors.dev$loc >= u_data(unit).n_sec THEN DO; iors.status = E$SPACE; iors.done = TRUE; RETURN; END; u_data(duib.unit).state = STARTSTATE; cylinder = (iors.dev$loc + u_data(unit).rel_sec)/ (u_data(unit).heads * u_data(unit).sec_per_track); IF NOT seek(unit, dinfo.p_address, ddata_ptr, cylinder) THEN CALL set_error(iors_ptr, IO$OPRINT); END do$seek; do$special: DO; IF iors.subfunct = FS$FORMAT$TRACK THEN DO; phys_unit = unit/UNITSPERDRIVE; /* issue a restore command to controller if last physical unit formatted is different than physical unit being formatted */ IF (ddata.flags AND LASTFORMATTEDMSK) <> phys_unit THEN CALL restore_hd(unit, duib.device$info$p, ddata_ptr, iors_ptr, RESTORESTATE); ELSE DO; IF u_data(unit).state <> HIFORMATSTATE THEN u_data(unit).state = LOFORMATSTATE; CALL format_trk(iors_ptr, duib_ptr, ddata_ptr); END; END; ELSE IF iors.subfunct = FS$DEVICE$LABEL THEN /* get drive parameters */ CALL get_device_info(iors_ptr, duib_ptr, ddata_ptr, iors.aux$p); ELSE IF iors.subfunct = FS$SET$BAD$INFO THEN CALL set_bad_track_info(iors_ptr, ddata_ptr, unit); ELSE IF iors.subfunct = FS$GET$BAD$INFO THEN CALL get_bad_track_info(iors_ptr, ddata_ptr, unit); ELSE DO; iors.status = E$IDDR; iors.done = TRUE; END; END do$special; do$attach: DO; CALL start_attach(iors_ptr, duib_ptr, ddata_ptr); END do$attach; do$detach: DO; CALL start_detach(iors_ptr, ddata_ptr, unit, dinfo.p_address); END do$detach; do$open: DO; iors.done = TRUE; END do$open; do$close: DO; iors.done = TRUE; END do$close; END; /* CASE */ END iSYS120$wini$start; $subtitle('iSYS120$wini$int') /**************************************************************************** * * PROC NAME: iSYS120$wini$int * * DESCRIPTION: Interrupt procedure for wini driver * * CALL: CALL iSYS120$wini$int(iors_ptr, duib_ptr, ddata_ptr); * * INPUTS: iors_ptr - pointer to I/O Request/Result segment * duib_ptr - pointer to Device-Unit Information Block * ddata_ptr - pointer to device data segment * * OUTPUTS: * ****************************************************************************/ iSYS120$wini$int : PROCEDURE(iors_ptr, duib_ptr, ddata_ptr) PUBLIC REENTRANT; DECLARE /* params */ iors_ptr POINTER, duib_ptr POINTER, ddata_ptr POINTER; DECLARE /* locals */ iors BASED iors_ptr IO$REQ$RES$SEG, duib BASED duib_ptr DE$V$UNIT$INFO$BLOCK, ddata BASED ddata_ptr ddata_struc, dinfo$p POINTER, dinfo BASED dinfo$p HDC$DEVICE$INFO, uinfo_ptr POINTER, /* points to unifo block */ uinfo BASED uinfo_ptr HDCINFOBLOCK, /* uinfo block */ p_address WORD, aux_ptr POINTER, format_info BASED aux_ptr FORMAT$INFO$STRUCT, /* format info */ buf$ptr POINTER, u_data BASED ddata_ptr (NUMBEROFUNITS) unit_data, /* info for each unit */ unit BYTE, phys_unit BYTE, /* physical unit */ buffer BASED buf$ptr (*) WORD; IF iors_ptr <> NIL THEN DO; IF iors.funct > F$CLOSE THEN DO; iors.status = E$IDDR; iors.done = TRUE; RETURN; END; IF iors.status = E$OK THEN DO; unit = duib.unit; aux_ptr = iors.aux$p; buf$ptr = iors.buff$p; dinfo$p = duib.device$info$p; uinfo_ptr = duib.unit$info$p; p_address = dinfo.p_address; phys_unit = unit/UNITSPERDRIVE; DO CASE iors.funct; do$read: DO; IF wait_data_req(p_address) THEN DO; /* read the sector into memory */ CALL BLOCK$INWORD(p_address, @buffer(iors.actual/2), duib.dev$gran/2); iors.actual = iors.actual + duib.dev$gran; /* test for error */ IF find_error(iors_ptr, uinfo.max$retry, p_address) THEN RETURN; /* data transfer ready ? */ IF iors.actual >= iors.count THEN DO; iors.status = E$OK; iors.done = TRUE; END; /* else : more interrupts to come */ END; ELSE /* no data request */ CALL set_error(iors_ptr, IO$OPRINT); END; do$write: DO; /* First interrupt occurs after first block written */ /* test for error */ IF find_error(iors_ptr, uinfo.max$retry, p_address) THEN RETURN; iors.actual = iors.actual + duib.dev$gran; IF iors.actual >= iors.count THEN DO; iors.status = E$OK; iors.done = TRUE; END; ELSE DO; /* write next block */ IF wait_data_req(p_address) THEN /* write the buffer and wait for next int */ CALL BLOCK$OUTWORD(p_address, @buffer(iors.actual/2), duib.dev$gran/2); ELSE CALL set_error(iors_ptr, IO$OPRINT); END; /* actual >= count */ END do$write; do$seek: DO; IF NOT find_error(iors_ptr, uinfo.max$retry, p_address) THEN DO; iors.status = E$OK; iors.done = TRUE; END; END do$seek; do$special: DO; IF iors.subfunct = FS$FORMAT$TRACK THEN CALL int_format(iors_ptr, duib_ptr, ddata_ptr); ELSE iors.done = TRUE; END do$special; do$attach: DO; CALL int_attach(iors_ptr,duib_ptr, ddata_ptr, dinfo.p_address); END; do$detach: DO; iors.status = E$OK; iors.done = TRUE; END; do$open: DO;END; do$close: DO;END; END; /* CASE */ END; /* iors.status = E$OK */ END; /* ior$p <> NIL */ END iSYS120$wini$int; $subtitle('start_read_write') /**************************************************************************** * * PROC NAME: start_read_write * * DESCRIPTION: Start a read or write operation. * * CALL: CALL start_read_write(iors_ptr, duib_ptr, ddata_ptr); * * INPUTS: iors_ptr - pointer to I/O Request/Result segment * duib_ptr - pointer to Device-Unit Information Block * ddata_ptr - pointer device data segment * OUTPUTS: none ****************************************************************************/ start_read_write : PROCEDURE(iors_ptr, duib_ptr, ddata_ptr) PUBLIC REENTRANT; DECLARE iors_ptr POINTER, duib_ptr POINTER, ddata_ptr POINTER, dinfo$p POINTER, uinfo_ptr POINTER, /* points to unifo block */ iors BASED iors_ptr IO$REQ$RES$SEG, duib BASED duib_ptr DEV$UNIT$INFO$BLOCK, ddata BASED ddata_ptr ddata_struc, u_data BASED ddata_ptr (NUMBEROFUNITS) unit_data, /* partition info for each unit */ dinfo BASED dinfo$p HDC$DEVICE$INFO, uinfo BASED uinfo_ptr HDCINFOBLOCK, /* uinfo block */ p_address WORD, devloc DWORD, cylinder WORD, head BYTE, sector BYTE, unit BYTE, com$byte (NUMTASKREGS) BYTE, i WORD, buf$p POINTER, buffer BASED buf$p (*) BYTE; /* write buffer */ unit = duib.unit; dinfo$p = duib.device$info$p; uinfo_ptr = duib.unit$info$p; p_address = dinfo.p_address; devloc = iors.devloc; u_data(unit).state = STARTSTATE; IF devloc >= u_data(unit).n_sec THEN DO; iors.status = E$SPACE; iors.done = TRUE; RETURN; END; $eject IF u_data(unit).heads > EXTRAHDOPT THEN OUTPUT(dinfo.control$reg) = EXTRAHDOPT; devloc = devloc + u_data(unit).rel_sec; sector = devloc MOD u_data(unit).sec_per_track; devloc = devloc / u_data(unit).sec_per_track; head = devloc MOD u_data(unit).heads; cylinder = devloc / u_data(unit).heads; /* set up command bytes */ com$byte(WRPRECOMP) = u_data(unit).pre_comp; com$byte(SECTORCNT) = iors.count / duib.dev$gran; com$byte(SECTORNUM) = sector+1; com$byte(LOWCYLNUM) = cylinder; com$byte(HICYLNUM) = HIGH(cylinder) AND HIBYTECYLMSK; com$byte(SDH) = u_data(unit).drive OR head; IF iors.funct = F$READ THEN com$byte(COMMAND) = HREAD; ELSE com$byte(COMMAND) = HWRITE; IF uinfo.max$retry = 0 THEN com$byte(COMMAND) = com$byte(COMMAND) OR RETRYBIT; IF wait_not_busy(p_address) THEN DO; /* wait for hdc not busy */ DO i = 0 TO 6; OUTPUT(p_address + 1 + i) = com$byte(i); END; IF iors.funct = F$WRITE THEN DO; /* output first sector */ buf$p = iors.buff$p; IF wait_data_req(p_address) THEN CALL BLOCK$OUTWORD(p_address, @buffer(0), duib.dev$gran/2); ELSE DO; /* wait data request */ CALL set_error(iors_ptr, IO$OPRINT); RETURN; END; END; END; ELSE CALL set_error(iors_ptr, IO$OPRINT); END start_read_write; $subtitle('read_verify') /**************************************************************************** * * PROC NAME: read_verify * * DESCRIPTION: Start a read verify operation. * * CALL: CALL read_verify(iors_ptr, ddata_ptr, p_address, cyl, head); * * INPUTS: ddata_ptr - pointer device data segment * iors_ptr - pointer to iors * p_address - base task register port * cyl - cylinder of track to verify * head - head of track to verify * * OUTPUTS: none ****************************************************************************/ read_verify: PROCEDURE(iors_ptr, ddata_ptr, unit, p_address, cyl, head) PUBLIC REENTRANT; DECLARE iors_ptr POINTER, ddata_ptr POINTER, unit BYTE, p_address WORD, cyl WORD, head BYTE; DECLARE /* locals */ iors BASED iors_ptr IO$REQ$RES$SEG, ddata BASED ddata_ptr ddata_struc, u_data BASED ddata_ptr (NUMBEROFUNITS) unit_data, /* partition info for each unit */ sector BYTE, com$byte (NUMTASKREGS) BYTE, i WORD; com$byte(WRPRECOMP) = u_data(unit).pre_comp; com$byte(SECTORCNT) = 1; com$byte(SECTORNUM) = 1; com$byte(LOWCYLNUM) = cyl; com$byte(HICYLNUM) = HIGH(cyl) AND HIBYTECYLMSK; com$byte(SDH) = u_data(unit).drive OR head; com$byte(COMMAND) = HREADVERIFY; IF wait_not_busy(p_address) THEN DO; /* wait for hdc not busy */ DO i = 0 TO 6; OUTPUT(p_address + 1 + i) = com$byte(i); END; END; ELSE CALL set_error(iors_ptr, IO$OPRINT); END read_verify; $subtitle('seek') /**************************************************************************** * * PROC NAME: seek * * DESCRIPTION: issue seek command * * CALL: result = seek(unit, p_address, ddata_ptr, cylinder) * * INPUTS: unit - unit number * p_address - base port address of task registers * ddata_ptr - points to driver data * cylinder - cylinder to seek to * * OUTPUTS: none * * RETURNS: TRUE or FALSE depending on whether command completes * ****************************************************************************/ seek: PROCEDURE(unit, p_address, ddata_ptr, cylinder) BYTE REENTRANT; DECLARE unit BYTE, p_address WORD, ddata_ptr POINTER, cylinder WORD; DECLARE u_data BASED ddata_ptr (NUMBEROFUNITS) unit_data; /* partition info */ IF wait_not_busy(p_address) THEN DO; OUTPUT(p_address + WRPRECOMP +1) = u_data(unit).pre_comp; OUTPUT(p_address + HICYLNUM +1) = HIGH(cylinder); OUTPUT(p_address + LOWCYLNUM +1) = LOW(cylinder); OUTPUT(p_address + SDH +1) = u_data(unit).drive; OUTPUT(p_address + COMMAND +1) = HSEEK; RETURN TRUE; END; ELSE RETURN FALSE; END seek; $subtitle('restore_hd') /**************************************************************************** * * PROC NAME: restore_hd * * DESCRIPTION: restore the heads to track 0 * * CALL: CALL restore_hd(duib_ptr udata_ptr, iors_ptr, state) * * INPUTS: duib_ptr - pointer to duib * udata_ptr - pointer to driver data * iors_ptr - pointer to iors * state - state to leave the unit in after restore * * OUTPUTS: none * ****************************************************************************/ restore_hd:PROCEDURE(unit, dinfo_ptr, udata_ptr, iors_ptr, state) REENTRANT; DECLARE unit BYTE, dinfo_ptr POINTER, udata_ptr POINTER, iors_ptr POINTER, state BYTE; DECLARE /* locals */ iors BASED iors_ptr IO$REQ$RES$SEG, u_data BASED udata_ptr (NUMBEROFUNITS) unit_data, dinfo BASED dinfo_ptr HDC$DEVICE$INFO; IF wait_not_busy(dinfo.p_address) THEN DO; u_data(unit).state = state; OUTPUT(dinfo.p_address + SDH +1) = u_data(unit).drive; OUTPUT(dinfo.p_address + COMMAND +1) = HRESTORE; END; ELSE DO; CALL set_error(iors_ptr, IO$OPRINT); u_data(unit).state = STARTSTATE; END; END restore_hd; $subtitle('format_trk') /**************************************************************************** * * PROC NAME: format_trk * * DESCRIPTION: format a track The driver formats tracks in two passes. * During the first pass, tracks associated with heads 0-7 are * formatted. However, the driver checks for an occurrance of * all tracks in the bad track map and reports the presence of * a bad track to the caller by returning an E$NO$SPARES status. * The first pass is completed when a format request is received * where the associated track is greater than the number of tracks * in the unit. The driver then checks whether * the drive has more than 8 heads. If so, the driver resets the * controller and reinitializes the controller and drives before * moving on the the second pass. Otherwise it completes by * returning an E$SPACE to the caller. * * In the second pass, tracks associated with heads 8-F are formatted. * During the second pass, the driver does not report bad tracks. * However it does use bad track information to generate the * correct interleave table. In order for tracks associated * with heads 8-f to be formatted, the track number must be * track_num + num_tracks_in_unit. Thus an E$SPACE is returned * when the track number > 2*num_tracks_in_unit - 2. * * * * CALL: CALL format_trk(iors_ptr, duib_ptr, ddata_ptr, bad_trk) * * INPUTS: iors_ptr - points to iors * duib_ptr - points to duib * ddata_ptr - points to driver data * * OUTPUTS: iors fields if error * * RETURNS: nothing * ****************************************************************************/ format_trk:PROCEDURE(iors_ptr, duib_ptr, ddata_ptr) REENTRANT; DECLARE iors_ptr POINTER, duib_ptr POINTER, ddata_ptr POINTER; $eject DECLARE /* locals */ status WORD, i byte, /* local index */ drive byte, /* positions drive select bit */ p_address word, /* port address of read/write data register */ dinfo_ptr POINTER, /* points to device info table */ aux_ptr POINTER, /* auxilliary pointer in iors */ rel_track WORD, /* number of tracks before rmx partition */ f_track WORD, /* track to be formated */ f_head BYTE, /* head associated with f_track */ f_cyl WORD, /* cylinder associated with f_track */ unit byte, /* unit number of device currently accessed */ block_val BYTE, /* used to specify whether track is bad */ duib BASED duib_ptr DEV$UNIT$INFO$BLOCK, u_data BASED ddata_ptr (NUMBEROFUNITS) unit_data, /* partition info for each unit */ iors BASED iors_ptr IO$REQ$RES$SEG, /* request segment */ ddata BASED ddata_ptr ddata_struc, /* driver data */ dinfo BASED dinfo_ptr HDC$DEVICE$INFO, /* device into table */ format_info BASED aux_ptr FORMAT$INFO$STRUCT, /* format info */ cmd_byte(NUMTASKREGS) byte; /* contains setup values for read command */ unit = duib.unit; aux_ptr = iors.aux$p; dinfo_ptr = duib.device$info$p; p_address = dinfo.p_address; rel_track = u_data(unit).rel_sec/u_data(unit).sec_per_track; f_track = format_info.track$num; $eject /* second pass format request */ IF u_data(unit).state = HIFORMATSTATE OR u_data(unit).state = HIRDVERSTATE THEN DO; IF f_track > 2*u_data(unit).num_tracks - 1 THEN DO; iors.status = E$SPACE; iors.done = TRUE; u_data(unit).state = STARTSTATE; RETURN; END; /* get the actual cylinder and head for the track to be formatted */ f_track = f_track MOD u_data(unit).num_tracks; f_track = rel_track + f_track; f_head = f_track mod u_data(unit).heads; f_cyl = f_track/u_data(unit).heads; /* ignore low head tracks in second pass */ IF f_head < EXTRAHDOPT THEN DO; iors.done = TRUE; iors.status = E$OK; RETURN; END; /* if no bad track map, check if track to be formatted is bad */ IF u_data(unit).bad_trks_ptr = NIL THEN DO; IF u_data(unit).state = HIFORMATSTATE THEN DO; /* check if track to be formatted has already been marked bad */ u_data(unit).state = HIRDVERSTATE; CALL read_verify(iors_ptr, ddata_ptr, unit, p_address, f_cyl, f_head); RETURN; END; ELSE /* returning from a read_verify so change state and continue */ u_data(unit).state = HIFORMATSTATE; END; END; $eject ELSE DO; /* state = LOFORMATSTATE, this is first pass format */ f_track = rel_track + f_track; f_cyl = f_track/u_data(unit).heads; f_head = f_track MOD u_data(unit).heads; IF (f_track > rel_track + u_data(unit).n_sec/u_data(unit).sec_per_track -1) THEN DO; IF u_data(unit).heads > EXTRAHDOPT THEN DO; /* reset the controller and prepare for a second pass because the drive formatted has more than 8 heads */ OUTPUT(dinfo.control$reg) = RESETBIT; CALL RQ$SLEEP(1,@status); OUTPUT(dinfo.control$reg) = EXTRAHDOPT; IF NOT wait_not_busy(p_address) THEN DO; iors.status = E$IO; iors.done = TRUE; iors.unit$status = IO$OPRINT; RETURN; END; u_data(unit).state = FSETUPSTATE1; u_data(unit).num_tracks = format_info.track$num; CALL set_params(unit, ddata_ptr, iors_ptr, p_address); END; ELSE DO; iors.status = E$SPACE; iors.done = TRUE; u_data(unit).state = STARTSTATE; END; RETURN; END; /* if no bad track map, check if track to be formatted is bad */ IF u_data(unit).bad_trks_ptr = NIL THEN DO; IF u_data(unit).state <> LORDVERSTATE THEN DO; u_data(unit).state = LORDVERSTATE; CALL read_verify(iors_ptr, ddata_ptr, unit, p_address, f_cyl, f_head); RETURN; END; ELSE u_data(unit).state = LOFORMATSTATE; END; END; $eject IF track_bad(ddata_ptr, format_info.track$num, unit) THEN DO; IF u_data(unit).state = LOFORMATSTATE AND f_head >= EXTRAHDOPT THEN DO; /* only report bad track, do actual format in next pass */ iors.status = E$IO; iors.unit$status = IO$NO$SPARES; iors.done = TRUE; RETURN; END; block_val = BADTRACK; END; ELSE DO; /* track is good, return if upper head track and we're only formatting lower head tracks */ IF u_data(unit).state = LOFORMATSTATE AND f_head >= EXTRAHDOPT THEN DO; iors.done = TRUE; iors.status = E$OK; RETURN; END; block_val = GOODTRACK; END; IF u_data(unit).state = HIFORMATSTATE THEN OUTPUT(dinfo.control$reg) = EXTRAHDOPT; cmd_byte(WRPRECOMP) = u_data(unit).pre_comp; cmd_byte(SECTORCNT) = u_data(unit).sec_per_track; cmd_byte(LOWCYLNUM) = LOW(f_cyl); cmd_byte(HICYLNUM) = HIGH(f_cyl) AND HIBYTECYLMSK; cmd_byte(SDH) = u_data(unit).drive OR f_head; cmd_byte(COMMAND) = HFORMAT; $eject CALL load_interleave_table(format_info.track$interleave, u_data(unit).sec_per_track, @ddata.buf, block_val); IF wait_not_busy(p_address) THEN DO; DO i = 0 to NUMTASKREGS - 1; OUTPUT(p_address + 1 + i) = cmd_byte(i); END; IF wait_data_req(p_address) THEN DO; IF u_data(duib.unit).state <> HIFORMATSTATE THEN u_data(duib.unit).state = LOFORMATSTATE; CALL BLOCK$OUTWORD(p_address, @ddata.buf, duib.dev$gran/2); END; ELSE DO; /* wait data request */ CALL set_error(iors_ptr, IO$OPRINT); u_data(unit).state = STARTSTATE; RETURN; END; END; ELSE DO; CALL set_error(iors_ptr, IO$OPRINT); u_data(unit).state = STARTSTATE; END; END format_trk; $subtitle('Track_bad') /**************************************************************************** * * PROC NAME: track_bad * * DESCRIPTION: Scan the bad track map for an occurrance of a track. * If the track is in the bad track map, return TRUE * * CALL: result = track_bad(ddata_ptr, track, unit) * * INPUTS: ddata_ptr - points to driver data * track - track number to be searched for in bad track map * unit - unit number * * OUTPUTS: * * RETURNS: TRUE if track is in bad track map, FALSE if otherwise * ****************************************************************************/ track_bad: PROCEDURE(ddata_ptr, track, unit) BOOLEAN REENTRANT; DECLARE ddata_ptr POINTER, track WORD, unit BYTE; DECLARE /* locals */ u_data BASED ddata_ptr (NUMBEROFUNITS) unit_data, /* partition info for each unit */ bt_info_ptr POINTER, /* points to bad track info */ bt_info BASED bt_info_ptr bad_trk_info, /* bad track info structure */ bt_ptr POINTER, /* points to bad tracks */ bad_track BASED bt_ptr(MAXBADTRKS) b_tracks, /* bad track map */ done BYTE, /* indicates whether track found */ phys_track WORD, /* absolute track number */ rel_track WORD, /* offset to be added to track */ cylinder WORD, /* cylinder assoc. w/phys_track */ head BYTE, /* head assoc. w/phys_track */ i BYTE; /* local index */ bt_info_ptr = u_data(unit).bad_trks_ptr; IF bt_info_ptr = NIL THEN RETURN FALSE; $eject IF u_data(unit).state = HIFORMATSTATE THEN phys_track = track MOD u_data(unit).num_tracks; ELSE phys_track = track; rel_track = u_data(unit).rel_sec/u_data(unit).sec_per_track; phys_track = rel_track + phys_track; cylinder = phys_track/u_data(unit).heads; head = phys_track mod u_data(unit).heads; bt_ptr = @bt_info.bad_tracks; i = 0; done = FALSE; DO WHILE (i < bt_info.count) AND (NOT done); IF (bad_track(i).cylinder = cylinder) AND (bad_track(i).head = head) THEN done = true; ELSE i = i+1; END; RETURN done; END track_bad; $subtitle('get_device_info') /**************************************************************************** * * PROC NAME: get_device_info * * DESCRIPTION: Fill in the disk_data fields with appropriate values * * CALL: CALL get_device_info(duib_ptr, ddata_ptr, aux_ptr) * * INPUTS: iors_ptr - points to iors * duib_ptr - points to duib * ddata_ptr - points to driver data * * OUTPUTS: disk_data - based variable used to return device info * ****************************************************************************/ get_device_info: PROCEDURE(iors_ptr, duib_ptr, ddata_ptr, aux_ptr) REENTRANT; DECLARE iors_ptr POINTER, duib_ptr POINTER, ddata_ptr POINTER; DECLARE /* locals */ duib BASED duib_ptr DEV$UNIT$INFO$BLOCK, iors BASED iors_ptr IOREQRESSEG, u_data BASED ddata_ptr (NUMBEROFUNITS) unit_data, /* partition info */ dev_size DWORD, /* device size in bytes */ aux_ptr POINTER, disk_data BASED aux_ptr /* device info returned to requestor */ STRUCTURE ( cylinders WORD, fixed BYTE, pre_comp BYTE, sectors BYTE, sector_size WORD, alternates BYTE); $eject aux_ptr = iors.aux$p; disk_data.cylinders = u_data(duib.unit).no_of_cylinders; disk_data.fixed = u_data(duib.unit).heads; disk_data.pre_comp = u_data(duib.unit).pre_comp; disk_data.sectors = u_data(duib.unit).sec_per_track; disk_data.sector_size = duib.dev$gran; disk_data.alternates = 0; u_data(duib.unit).state = STARTSTATE; IF duib.unit = WHOLEUNIT0 OR duib.unit = WHOLEUNIT1 THEN dev_size = DOUBLE(u_data(duib.unit).no_of_cylinders) * DOUBLE(DOUBLE(u_data(duib.unit).heads)) * DOUBLE(duib.dev$gran) * DOUBLE(DOUBLE(u_data(duib.unit).sec_per_track)); ELSE dev_size = u_data(duib.unit).n_sec * DOUBLE(duib.dev$gran); $IF r_32 iors.count = dev_size; $ELSE iors.count = LOW(dev_size); iors.count$fill = HIGH(dev_size); $ENDIF iors.done = TRUE; END get_device_info; $subtitle('start_attach') /**************************************************************************** * * PROC NAME: start_attach * * DESCRIPTION: Start an attach request. If the unit attached is the entire * physical drive, fill appropriate driver data fields and issue * set parameters command to the controller. If the unit to be * attached is a partition, check if it is already attached as * a generic unit. If not, issue a command to the controller * to read the sector containing the partition table. * * CALL: CALL start_attach(iors_ptr, duib_ptr, ddata_ptr) * * INPUTS: iors_ptr - points to iors * duib_ptr - points to duib * ddata_ptr - points to driver data * * OUTPUTS: * ****************************************************************************/ start_attach: PROCEDURE(iors_ptr, duib_ptr, ddata_ptr) REENTRANT; DECLARE iors_ptr POINTER, duib_ptr POINTER, ddata_ptr POINTER; DECLARE /* locals */ iors BASED iors_ptr IO$REQ$RES$SEG, duib BASED duib_ptr DEV$UNIT$INFO$BLOCK, uinfo_ptr POINTER, /* points to unifo block */ uinfo BASED uinfo_ptr HDCINFOBLOCK, /* uinfo block */ dinfo_ptr POINTER, u_data BASED ddata_ptr (NUMBEROFUNITS) unit_data, /* partition info */ phys_unit BYTE; $eject u_data(duib.unit).state = STARTSTATE; uinfo_ptr = duib.unit$info$p; phys_unit = duib.unit/UNITSPERDRIVE; u_data(duib.unit).drive = SHL(phys_unit, UPNIBBLE) OR SDHSTART; /* check if unit already attached as a generic device */ IF u_data(duib.unit).attached = GENATTACHED THEN DO; iors.status = E$ALREADY$ATTACHED; iors.done = TRUE; RETURN; END; CALL get_part_blk(iors_ptr, duib_ptr, ddata_ptr); END start_attach; $subtitle('start_detach') /**************************************************************************** * * PROC NAME: start_detach * * DESCRIPTION: Start detach operation. Mark the unit detached and if it * has an alias (for generic units), mark the alias detached. * Decrement the number of units attached for the physical * drive. If there are no more attached, issue a command to * the controller to seek to the inner most cylinder. * * * CALL: CALL start_detach(iors_ptr, ddata_ptr, unit, p_address) * * INPUTS: iors_ptr - points to iors * ddata_ptr - points to driver data * unit - unit being detached * p_address - task register base port * * OUTPUTS: u_data - driver data for unit detached * ddata - driver data * iors - completion fields in iors * ****************************************************************************/ start_detach: PROCEDURE(iors_ptr, ddata_ptr, unit, p_address) REENTRANT; DECLARE iors_ptr POINTER, ddata_ptr POINTER, unit BYTE, p_address WORD; DECLARE /* locals */ status WORD, iors BASED iors_ptr IO$REQ$RES$SEG, ddata BASED ddata_ptr ddata_struc, unit_att BYTE, /* generic unit alias */ phys_unit BYTE, /* physical unit associated with logical unit */ u_data BASED ddata_ptr (NUMBEROFUNITS) unit_data; /* partition info */ $eject u_data(unit).state = STARTSTATE; IF unit = AUTORECUNIT0 OR unit = AUTORECUNIT1 THEN DO; unit_att = u_data(unit).attached; u_data(unit_att).attached = FALSE; END; IF u_data(unit).bad_trks_ptr <> NIL THEN DO; CALL rq$delete$segment(SELECTOR$OF(u_data(unit).bad_trks_ptr), @status); u_data(unit).bad_trks_ptr = NIL; END; u_data(unit).attached = FALSE; phys_unit = unit/UNITSPERDRIVE; ddata.num_att(phys_unit) = ddata.num_att(phys_unit) - 1; IF ddata.num_att(phys_unit) = 0 THEN DO; IF seek(unit, p_address, ddata_ptr, u_data(unit).tot_cyl -1) THEN RETURN; END; iors.done = TRUE; iors.status = E$OK; END start_detach; $subtitle('Int_format') /**************************************************************************** * * PROC NAME: int_format * * DESCRIPTION This procedure is called when the controller issues an * interrupt during a format operation. Most of the states * relate to operations required after controller reset. * * * CALL: CALL int_format(iors_ptr, duib_ptr, ddata_ptr) * * INPUTS: iors_ptr - pointer to I/O Request/Result segment * duib_ptr - pointer to Device-Unit Information Block * ddata_ptr - pointer to device data segment * * OUTPUTS: * * RETURNS: * ****************************************************************************/ int_format: PROCEDURE(iors_ptr, duib_ptr, ddata_ptr) PUBLIC REENTRANT; DECLARE iors_ptr POINTER, duib_ptr POINTER, ddata_ptr POINTER; DECLARE /* locals */ iors BASED iors_ptr IO$REQ$RES$SEG, duib BASED duib_ptr DE$V$UNIT$INFO$BLOCK, ddata BASED ddata_ptr ddata_struc, dinfo$p POINTER, dinfo BASED dinfo$p HDC$DEVICE$INFO, uinfo_ptr POINTER, /* points to unifo block */ uinfo BASED uinfo_ptr HDCINFOBLOCK, /* uinfo block */ p_address WORD, aux_ptr POINTER, format_info BASED aux_ptr FORMAT$INFO$STRUCT, /* format info */ u_data BASED ddata_ptr (NUMBEROFUNITS) unit_data, /* info for each unit */ i BYTE, /* local index */ err_val BYTE, off_set BYTE, /* unit select offset */ phys_unit BYTE; /* physical unit */ $eject aux_ptr = iors.aux$p; dinfo$p = duib.device$info$p; uinfo_ptr = duib.unit$info$p; p_address = dinfo.p_address; phys_unit = duib.unit/UNITSPERDRIVE; DO CASE u_data(duib.unit).state; /* restorestate */ DO; ddata.flags = ddata.flags AND FORMATFLGSMSK OR phys_unit; u_data(duib.unit).state = LOFORMATSTATE; CALL format_trk(iors_ptr, duib_ptr, ddata_ptr); END; /* loformatstate */ DO; IF track_bad(ddata_ptr, format_info.track$num, duib.unit) THEN DO; iors.status = E$IO; iors.unit$status = IO$NO$SPARES; END; ELSE iors.status = E$OK; iors.done = TRUE; END; /* hiformatstate */ DO; iors.status = E$OK; iors.done = TRUE; END; /* fsetupstate1 - follows set parameters command after controller reset*/ DO; CALL restore_hd(duib.unit, duib.device$info$p, ddata_ptr, iors_ptr, FRESTORESTATE1); END; $eject /* frestorestate1 - follows restore of unit being formatted after controller reset */ DO; /* check if unit associated with other drive is attached, if so issue restore to it */ IF phys_unit = 0 THEN off_set = UNITSPERDRIVE; ELSE off_set = 0; i = 0; DO WHILE i < UNITSPERDRIVE AND ((u_data(i+off_set).attached = FALSE) OR (u_data(i+off_set).attached = GENATTACHED)); i = i+1; END; IF i < UNITSPERDRIVE THEN DO; u_data(duib.unit).state = FSETUPSTATE2; CALL set_params(i+off_set, ddata_ptr, iors_ptr, p_address); END; ELSE DO; u_data(duib.unit).state = HIFORMATSTATE; CALL format_trk(iors_ptr, duib_ptr, ddata_ptr); RETURN; END; END; /* fsetupstate2 - follows set paramters command for unit not being formatted after controller reset */ DO; CALL restore_hd(duib.unit, duib.device$info$p, ddata_ptr, iors_ptr, FRESTORESTATE2); END; /* frestorestate2 - follows restore of unit not being formatted after controller reset */ DO; u_data(duib.unit).state = HIFORMATSTATE; CALL format_trk(iors_ptr, duib_ptr, ddata_ptr); RETURN; END; $eject /* hirdverstate - preceeds actual formatting of track, checks if track marked bad */ DO; IF (INPUT(p_address + COMMAND +1) AND ERRORBIT)<>0 THEN DO; err_val = INPUT(p_address + ERRORREG); IF (err_val AND BADBLKBIT) = BADBLKBIT THEN DO; u_data(duib.unit).state = HIFORMATSTATE; iors.status = E$OK; iors.done = TRUE; END; ELSE CALL format_trk(iors_ptr, duib_ptr, ddata_ptr); END; ELSE CALL format_trk(iors_ptr, duib_ptr, ddata_ptr); END; /* lordverstate - preceeds actual formatting of track, checks if track marked bad */ DO; IF (INPUT(p_address + COMMAND +1) AND ERRORBIT)<>0 THEN DO; err_val = INPUT(p_address + ERRORREG); IF (err_val AND BADBLKBIT) = BADBLKBIT THEN DO; u_data(duib.unit).state = LOFORMATSTATE; iors.status = E$IO; iors.unit$status = IO$NO$SPARES; iors.done = TRUE; END; ELSE CALL format_trk(iors_ptr, duib_ptr, ddata_ptr); END; ELSE CALL format_trk(iors_ptr, duib_ptr, ddata_ptr); END; END; /* case */ END int_format; $subtitle('int_attach') /**************************************************************************** * * PROC NAME: int_attach * * DESCRIPTION: Called by interrupt routine to do attach functions. * If the interrupt follows a set parameters command, * change state to STARTSTATE and bump the number of attaches * for the physical unit. Otherwise the interrupt follows * a read sector 0 command. Fill in driver data fields * according to whether the unit is generic or not. Then issue * a set parameters command to the controller. * * CALL: CALL int_attach(iors_ptr,duib_ptr, ddata_ptr, p_address); * * INPUTS: iors_ptr - points to iors * duib_ptr - points to duib * ddata_ptr - points to driver data * p_address - base port address of task registers * * OUTPUTS: none * ****************************************************************************/ int_attach:PROCEDURE(iors_ptr, duib_ptr, ddata_ptr, p_address) REENTRANT; DECLARE /* params */ iors_ptr POINTER, duib_ptr POINTER, ddata_ptr POINTER, p_address WORD; DECLARE /* locals */ part_num BYTE, /* partition number */ phys_unit BYTE, /* physical unit associated with unit */ ddata BASED ddata_ptr ddata_struc, iors BASED iors_ptr IO$REQ$RES$SEG, u_data BASED ddata_ptr (NUMBEROFUNITS) unit_data, /* partition info for each unit */ uinfo_ptr POINTER, uinfo BASED uinfo_ptr HDCINFOBLOCK, duib BASED duib_ptr DEV$UNIT$INFO$BLOCK, sig_ptr POINTER, /* points to partition table sig */ sig BASED sig_ptr WORD, /* partition signature */ err_val BYTE, /* value in wini controller err reg */ dinfo_ptr POINTER, dinfo BASED dinfo_ptr HDC$DEVICE$INFO; $eject dinfo_ptr = duib.device$info$p; uinfo_ptr = duib.unit$info$p; phys_unit = duib.unit/UNITSPERDRIVE; IF u_data(duib.unit).state = SETUPSTATE THEN DO; u_data(duib.unit).state = STARTSTATE; ddata.num_att(phys_unit) = ddata.num_att(phys_unit) + 1; iors.status = E$OK; iors.done = TRUE; RETURN; END; /* check if drive online if just back from a read */ IF (INPUT(p_address + COMMAND +1) AND ERRORBIT)<>0 THEN DO; err_val = INPUT(p_address + ERRORREG); IF ((err_val AND NOTACTIVEBIT) = NOTACTIVEBIT) THEN DO; iors.status = E$IO; iors.unit$status = IO$OPRINT; iors.done = TRUE; RETURN; END; END; IF wait_data_req(p_address) THEN DO; CALL BLOCK$INWORD(p_address, @ddata.buf, duib.dev$gran/2); /* if non-partition unit, we dont care about partition table sector, just made sure unit was online */ IF duib.unit = WHOLEUNIT0 OR duib.unit = WHOLEUNIT1 THEN DO; CALL get_disk_info(ddata_ptr, duib.unit, uinfo_ptr); IF ddata.num_att(duib.unit) <> 0 THEN DO; u_data(duib.unit).state = STARTSTATE; ddata.num_att(phys_unit) = ddata.num_att(phys_unit) + 1; iors.status = E$OK; iors.done = TRUE; RETURN; END; u_data(duib.unit).state = SETUPSTATE; CALL set_params(duib.unit, ddata_ptr, iors_ptr, dinfo.p_address); RETURN; END; $eject /* make sure it is a legitimate partition table */ sig_ptr = @ddata.buf(PARTSIGOFFSET); IF sig <> PARTITIONSIG THEN DO; CALL set_error(iors_ptr, IO$OPRINT); RETURN; END; IF duib.unit = AUTORECUNIT0 OR duib.unit = AUTORECUNIT1 THEN DO; /* generic unit */ IF NOT get_generic_data(iors_ptr, ddata_ptr, duib.unit, @part_num) THEN DO; u_data(duib.unit).state = STARTSTATE; RETURN; END; END; /* non-generic unit */ ELSE CALL get_non_generic_data(uinfo_ptr, ddata_ptr, duib.unit, @part_num); /* do for both generic and non-generic partition unit */ CALL get_partition_info(ddata_ptr, phys_unit, part_num, duib.unit); duib.dev$size = u_data(duib.unit).n_sec * DOUBLE(duib.dev$gran); IF ddata.num_att(phys_unit) = 0 THEN DO; u_data(duib.unit).state = SETUPSTATE; CALL set_params(duib.unit, ddata_ptr, iors_ptr, p_address); END; ELSE DO; u_data(duib.unit).state = STARTSTATE; ddata.num_att(phys_unit) = ddata.num_att(phys_unit) + 1; iors.status = E$OK; iors.done = TRUE; RETURN; END; END; ELSE CALL set_error(iors_ptr, IO$OPRINT); END int_attach; $subtitle('set_params') /**************************************************************************** * * PROC NAME: set_params * * DESCRIPTION: This procedure issues a set parameters command to the controller * giving it the number of heads and sectors per track * * CALL: Call set_params(unit, ddata_ptr, iors_ptr, ) * * INPUTS: sectors - sectors per track * num_heads - number of heads in drive * unit - unit number * dinfo_ptr - points to device info table * * OUTPUTS: u_data - driver data for unit being attached * * RETURNS: nothing * ****************************************************************************/ set_params:PROCEDURE(unit, ddata_ptr, iors_ptr, p_address) REENTRANT; DECLARE unit BYTE, ddata_ptr POINTER, iors_ptr POINTER, p_address WORD; DECLARE /* locals */ u_data BASED ddata_ptr (NUMBEROFUNITS) unit_data, /* partition info */ iors BASED iors_ptr IOREQRESSEG, phys_unit BYTE, unit_att BYTE, /* non-generic unit */ sdh_val BYTE; /* sdh parameter value */ $eject phys_unit = unit/UNITSPERDRIVE; sdh_val = phys_unit; sdh_val = SHL(sdh_val, UPNIBBLE); sdh_val = sdh_val OR SDHSTART; sdh_val = sdh_val OR (u_data(unit).heads -1); IF wait_not_busy(p_address) THEN DO; OUTPUT(p_address + SECTORCNT + 1) = u_data(unit).sec_per_track; OUTPUT(p_address + SDH + 1) = sdh_val; OUTPUT(p_address + COMMAND + 1) = HSETPARAMS; END; ELSE DO; IF unit = AUTORECUNIT0 OR unit = AUTORECUNIT1 THEN DO; unit_att = u_data(unit).attached; u_data(unit_att).attached = FALSE; END; u_data(unit).attached = FALSE; CALL set_error(iors_ptr, IO$OPRINT); u_data(unit).state = STARTSTATE; END; END set_params; $subtitle('set_bad_track_info') /**************************************************************************** * * PROC NAME: set_bad_track_info * * DESCRIPTION: Implements set_bad_track_info. Copy bad track info to * a segment local to driver * * CALL: CALL set_bad_track_info(iors_ptr, ddata_ptr, unit) * * INPUTS: iors_ptr - points to iors * ddata_ptr - points to driver data * unit - unit associated with bad track info * * OUTPUTS: sets bad_trk_ptr in u_data * * RETURNS: nothing * ****************************************************************************/ set_bad_track_info: PROCEDURE(iors_ptr, ddata_ptr, unit) REENTRANT; DECLARE iors_ptr POINTER, ddata_ptr POINTER, unit BYTE; DECLARE /* locals */ iors BASED iors_ptr IOREQRESSEG, u_data BASED ddata_ptr (NUMBEROFUNITS) unit_data, /* partition info */ from_bti_ptr POINTER, /* points to bad track info to be copied */ from_bti BASED from_bti_ptr bad_trk_info, /* bad track info */ from_bt_ptr POINTER, /* bad tracks to be copied */ f_bad_trks BASED from_bt_ptr (MAXBADTRKS) b_tracks, /* bad tracks */ to_bt_info_seg TOKEN, /* points to driver bad track seg */ t_bt_info BASED to_bt_info_seg bad_trk_info, /* driver bad track info */ to_bt_ptr POINTER, /* points to driver bad tracks */ t_bad_trks BASED to_bt_ptr (MAXBADTRKS) b_tracks, /* driver bad tracks */ count WORD, /* transfer count */ status WORD; $eject u_data(unit).state = STARTSTATE; from_bti_ptr = iors.aux$p; from_bt_ptr = @from_bti.bad_tracks; IF (from_bti.count = 0) OR (from_bti.count > MAXBADTRKS) THEN DO; iors.done = TRUE; iors.status = E$OK; /* this needs to be changed to reflect condition */ RETURN; END; IF u_data(unit).bad_trks_ptr = NIL THEN DO; to_bt_info_seg = rq$create$segment(SIZE(t_bt_info), @status); IF status <> E$OK THEN DO; iors.done = TRUE; iors.status = status; RETURN; END; u_data(unit).bad_trks_ptr = @t_bt_info; END; ELSE to_bt_info_seg = SELECTOR$OF(u_data(unit).bad_trks_ptr); t_bt_info.count = from_bti.count; to_bt_ptr = @t_bt_info.bad_tracks; count = SIZE(t_bad_trks(0)) * from_bti.count; CALL MOVB(from_bt_ptr, to_bt_ptr, count); iors.done = TRUE; iors.status = E$OK; END set_bad_track_info; $subtitle('Get_bad_track_info') /**************************************************************************** * * PROC NAME: get_bad_track_info * * DESCRIPTION: Implements get_bad_track_info. Copy bad track info to * callers data segment * * CALL: CALL get_bad_track_info(iors_ptr, ddata_ptr, unit) * * INPUTS: iors_ptr - points to iors * ddata_ptr - points to driver data * unit - unit associated with bad track info * * OUTPUTS: user segment pointed to by iors.aux$p * * RETURNS: nothing * ****************************************************************************/ get_bad_track_info: PROCEDURE(iors_ptr, ddata_ptr, unit) REENTRANT; DECLARE /* params */ iors_ptr POINTER, ddata_ptr POINTER, unit BYTE; DECLARE /* locals */ i BYTE, iors BASED iors_ptr IOREQRESSEG, u_data BASED ddata_ptr (NUMBEROFUNITS) unit_data, /* partition info */ from_bti_ptr POINTER, /* points to bad track info to be copied */ from_bti BASED from_bti_ptr bad_trk_info, /* bad track info */ from_bt_ptr POINTER, /* bad tracks to be copied */ to_bt_info_ptr POINTER, /* points to driver bad track seg */ t_bt_info BASED to_bt_info_ptr bad_trk_info, /* driver bad track info */ to_bt_ptr POINTER, /* points to driver bad tracks */ count WORD, /* transfer count */ status WORD; $eject u_data(unit).state = STARTSTATE; from_bti_ptr = u_data(unit).bad_trks_ptr; to_bt_info_ptr = iors.aux$p; IF from_bti_ptr = NIL THEN t_bt_info.count = 0; ELSE DO; from_bt_ptr = @from_bti.bad_tracks; t_bt_info.count = from_bti.count; to_bt_ptr = @t_bt_info.bad_tracks; count = SIZE(t_bt_info.bad_tracks(0)) * from_bti.count; CALL MOVB(from_bt_ptr, to_bt_ptr, count); END; iors.done = TRUE; iors.status = E$OK; END get_bad_track_info; $subtitle('find_error') /**************************************************************************** * * PROC NAME: find_error * * DESCRIPTION: Check if controller error occurred during operation. If * so, fill in appropriate iors fields * * CALL: result = find_error(iors_ptr, max_retry, p_address) * * INPUTS: iors_ptr - points to iors * max_retry - number of retrys on soft error * p_address - base port address of task registers * * OUTPUTS: iors.status, iors.unit$status, iors.done if error has occurred. * * RETURNS: TRUE if error, FALSE if not. * ****************************************************************************/ find_error: PROCEDURE(iors_ptr, max_retry, p_address) BYTE REENTRANT; DECLARE iors_ptr POINTER, max_retry BYTE, p_address WORD; DECLARE /* locals */ iors BASED iors_ptr IO$REQ$RES$SEG, /* iors for this operation */ err_val WORD; /* contains controller error byte */ IF (INPUT(p_address + COMMAND +1) AND ERRORBIT)<>0 THEN DO; iors.status = E$IO; err_val = INPUT(p_address + ERRORREG); err_val = SHL(err_val, BYTELEN); IF max_retry > 0 THEN iors.unit$status = IO$HARD; ELSE iors.unit$status = IO$SOFT; iors.unit$status = iors.unit$status OR err_val; iors.done = TRUE; RETURN TRUE; END; ELSE RETURN FALSE; END find_error; $subtitle('set_error') /**************************************************************************** * * PROC NAME: set_error * * DESCRIPTION: Set iors status fields * * CALL: CALL set_error(iors_ptr, err_val) * * INPUTS: iors_ptr - points to iors * err_val - indicates io error type * * OUTPUTS: iors.status, iors.unit$status, iors.done * ****************************************************************************/ set_error: PROCEDURE(iors_ptr, err_val) REENTRANT; DECLARE iors_ptr POINTER, err_val BYTE; DECLARE /* locals */ iors BASED iors_ptr IO$REQ$RES$SEG; /* iors for this operation */ iors.status=E$IO; iors.unit$status = err_val; iors.done= TRUE; END set_error; $SUBTITLE('wait not busy') /**************************************************************************** * * PROC NAME: wait_not_busy * * DESCRIPTION: wait for the HDC to become ready * * CALL: boolean = wait_not_busy(p_address); * * INPUTS: p_address - base port address of task registers * * RETURNS: TRUE if HDC becomes ready, FALSE if not * ****************************************************************************/ wait_not_busy : PROCEDURE(p_address) BYTE REENTRANT; DECLARE p_address WORD, count DWORD; count = 0; DO WHILE (count < WAITCOUNT); count = count + 1; /* test the busy bit in status register */ IF (INPUT(p_address+STATUSREG) AND BUSYBIT) = 0 THEN RETURN(TRUE); END; RETURN(FALSE); END wait_not_busy; $subtitle('wait_data_req') /**************************************************************************** * * PROC NAME: wait_data_req * * DESCRIPTION: wait for the HDC to become ready * * CALL: boolean = wait_data_req(p_address); * * INPUTS: p_address - base port address of task registers * * RETURNS: TRUE if HDC becomes ready, FALSE if not * ****************************************************************************/ wait_data_req : PROCEDURE(p_address) BYTE REENTRANT; DECLARE p_address WORD, count DWORD; count = 0; DO WHILE (count < WAITCOUNT); count = count + 1; /* test the request bit in status reg. */ IF (INPUT(p_address + STATUSREG) AND DATAREQBIT) <> 0 THEN RETURN(TRUE); END; RETURN(FALSE); END wait_data_req; $subtitle(get_part_blk) /**************************************************************************** * * PROC NAME: get_part_blk * * DESCRIPTION: initiate a single sector read * * CALL: CALL get_part_blk(iors_ptr, duib_ptr, ddata_ptr) * * INPUTS: iors_ptr - POINTER to I/O Request/Result segment * duib_ptr - POINTER to Device-Unit Information Block * ddata_ptr - POINTER to device data segment * * OUTPUTS: none * * RETURNS: nothing * ****************************************************************************/ get_part_blk:PROCEDURE(iors_ptr, duib_ptr, ddata_ptr) REENTRANT; DECLARE /* params */ iors_ptr POINTER, duib_ptr POINTER, ddata_ptr POINTER; DECLARE /* locals */ duib BASED duib_ptr DEV$UNIT$INFO$BLOCK, /* pseudo duib structure for portablity */ u_data BASED ddata_ptr (NUMBEROFUNITS) unit_data, /* partition info for each unit */ cmd_byte(NUMTASKREGS) byte, /* contains setup values for read command */ dinfo_ptr POINTER, /* points to device info table */ dinfo BASED dinfo_ptr HDC$DEVICE$INFO, /* device into table */ uinfo_ptr POINTER, /* points to unit info block */ uinfo BASED uinfo_ptr HDCINFOBLOCK, /* unit information block */ i byte, /* local index */ drive byte, /* positions drive select bit */ p_address word, /* port address of read/write data register */ unit byte; /* unit number of device currently accessed */ $eject uinfo_ptr = duib.unit$info$p; dinfo_ptr = duib.device$info$p; p_address = dinfo.p_address; unit = duib.unit; cmd_byte(WRPRECOMP) = uinfo.write_pre_comp; cmd_byte(SECTORCNT) = 1; cmd_byte(SECTORNUM) = 1; cmd_byte(LOWCYLNUM) = 0; cmd_byte(HICYLNUM) = 0; cmd_byte(SDH) = u_data(unit).drive; cmd_byte(COMMAND) = HREAD; IF wait_not_busy(p_address) THEN DO; DO i = 0 to NUMTASKREGS - 1; OUTPUT(p_address + 1 + i) = cmd_byte(i); END; u_data(unit).state = PARTTABSTATE; END; ELSE DO; CALL set_error(iors_ptr, IO$OPRINT); u_data(unit).state = STARTSTATE; END; END get_part_blk; $subtitle('get_disk_info') /**************************************************************************** * * PROC NAME: get_disk_info * * DESCRIPTION: Fill in the u_data entry for the unit being attached. * This procdure is only called for units attached as whole * disks * * CALL: CALL get_disk_info(ddata_ptr, unit, uinfo_ptr) * * INPUTS: ddata_ptr - points to driver data * unit - unit number of unit being attached * uinfo_ptr - points to unit info table * * OUTPUTS: ddata - In particular, the u_data entry for the unit being * attached is written. Ddata.buf is read. * ****************************************************************************/ get_disk_info: PROCEDURE(ddata_ptr, unit, uinfo_ptr) REENTRANT; DECLARE ddata_ptr POINTER, unit BYTE, /* number of unit being attached */ uinfo_ptr POINTER; DECLARE /* locals */ drive BYTE, /* drive num + flags */ uinfo BASED uinfo_ptr HDCINFOBLOCK, u_data BASED ddata_ptr (NUMBEROFUNITS) unit_data; /* ddata info for each unit */ u_data(unit).rel_sec = 0; drive = unit/UNITSPERDRIVE; drive = SHL(drive, UPNIBBLE); u_data(unit).drive = drive OR SDHSTART; u_data(unit).n_sec = DOUBLE(DOUBLE(uinfo.num_heads))* DOUBLE(uinfo.no_of_cylinders)* DOUBLE(DOUBLE(uinfo.sec_per_track)); u_data(unit).pre_comp = uinfo.write_pre_comp; u_data(unit).no_of_cylinders = uinfo.no_of_cylinders; u_data(unit).tot_cyl = uinfo.no_of_cylinders; u_data(unit).heads = uinfo.num_heads; u_data(unit).sec_per_track = uinfo.sec_per_track; END get_disk_info; $subtitle('get_active_part') /**************************************************************************** * * PROC NAME: get_active_part * * DESCRIPTION: Search the partition table for an active RMX partition. * If one is found return TRUE and put the partition number * in the variable part_num. * * CALL: result = get_active_part(ddata_ptr, part_ptr) * * INPUTS: part_ptr - points to active RMX partition number should one exist * ddata_ptr - points to driver data * * OUTPUTS: part_num - active RMX partition, this is a based variable * RETURNS: TRUE if active RMX partition exists, FALSE if not * ****************************************************************************/ get_active_part: PROCEDURE(ddata_ptr, part_ptr) BYTE REENTRANT; DECLARE ddata_ptr POINTER, part_ptr POINTER; DECLARE /* locals */ i BYTE, /* local index */ ddata BASED ddata_ptr ddata_struc, /* driver data */ part_num BASED part_ptr BYTE, /* partition number */ tab_ptr POINTER, /* partition table pointer */ parttable BASED tab_ptr (NUMPART) part_entry; /* partition table */ tab_ptr = @ddata.buf(PARTOFFSET); i = 0; DO WHILE (i < NUMPART) AND ((parttable(i).sys <> RMXSYS) OR ((parttable(i).boot AND ACTIVEPART) <> ACTIVEPART)); i = i + 1; END; IF i < NUMPART THEN DO; part_num = i + 1; RETURN TRUE; END; ELSE RETURN FALSE; END get_active_part; $subtitle('get_partition_info') /**************************************************************************** * * PROC NAME: get_partition_info * * DESCRIPTION: The partition table has been read into the ddata.buf buffer. * Fill in the u_data entry for the unit being attached with * the partition info from the partition table. * * CALL: CALL get_partition_info * * INPUTS: ddata_ptr - points to driver data area * phys_unit - physical unit 0 or 1 * part_num - partition number, 1-4 * unit - logical unit number, 0-11 * * OUTPUTS: ddata - In particular, the u_data entry for the unit being * attached is written. Ddata.buf is read. * ****************************************************************************/ get_partition_info: PROCEDURE(ddata_ptr, phys_unit, part_num, unit) REENTRANT; DECLARE ddata_ptr POINTER, phys_unit BYTE, part_num BYTE, unit BYTE; DECLARE /* locals */ u_data BASED ddata_ptr (NUMBEROFUNITS) unit_data, /* ddata info for each unit */ ddata BASED ddata_ptr ddata_struc, /* driver data */ part_ptr POINTER,/* points to partition table */ parttable BASED part_ptr (NUMPART) part_entry, /* partition table */ drive BYTE; /* drive number and flags */ part_ptr = @ddata.buf(PARTOFFSET); /* set up partition variables */ u_data(unit).rel_sec = parttable(part_num - 1).num_prec_sec; u_data(unit).n_sec = parttable(part_num - 1).number_sec; drive = phys_unit; drive = SHL(drive, UPNIBBLE); u_data(unit).drive = drive OR SDHSTART; u_data(unit).no_of_cylinders = parttable(part_num -1).number_sec/ (u_data(unit).heads * u_data(unit).sec_per_track); u_data(unit).tot_cyl = u_data(unit).no_of_cylinders; END get_partition_info; $subtitle('load_interleave_table') /**************************************************************************** * * PROC NAME: load_interleave_table * * DESCRIPTION: This routine loads the interleave table with the * appropriate values to acheive the requested interleave when * the disk is formatted. The interleave table is used by the * wini controller in formatting. It is specified as an array * of N entries where N is equal to the number of sectors per * track. Each entry contains two bytes. The first byte is set * to 0 if the entry is valid and 80H if it is not. The second * byte is the sector number. Thus the table would look like * this for a disk with 17 sectors per track and an interleave * of 3: 00,01,00,07,00,0D,00,02,00,08,00,0E,00,03,00,09,00,0F, * 00,04,00,0A,00,10,00,05,00,0B,00,11,00,06,00,0C. * * * CALL: CALL load_interleave_table(interleave, sec_per_track, buf_ptr, block_val) * * INPUTS: interleave - interleave value from format request * sec_per_track - sectors per track * buf_ptr - points to buffer available for interleave table * block_val - used to mark blocks good or bad in interleave table * * OUTPUTS: sector_table - interleave table, this is a based variable * * RETURNS: nothing * ****************************************************************************/ load_interleave_table: PROCEDURE(interleave, sec_per_track, buf_ptr, block_val) REENTRANT; DECLARE interleave WORD, sec_per_track BYTE, buf_ptr POINTER, block_val BYTE; DECLARE /* locals */ step BYTE, tab_idx WORD, /* index into interleave table */ cur_sector BYTE, /* sector entry for current entry being processed */ sector_table BASED buf_ptr (1) STRUCTURE( /* interleave table */ sector_val BYTE, sector_num BYTE); $eject step = 0; tab_idx = 0; cur_sector = 1; DO WHILE step < interleave; DO WHILE tab_idx < sec_per_track; sector_table(tab_idx).sector_val = block_val; sector_table(tab_idx).sector_num = cur_sector; tab_idx = tab_idx + interleave; cur_sector = cur_sector + 1; END; step = step + 1; tab_idx = step; END; END load_interleave_table; $subtitle('get_generic_data') /**************************************************************************** * * PROC NAME: get_generic_data * * DESCRIPTION: Fill in the driver data fields for a generic unit and mark * the generic unit and its alias as attached. The driver data * is obtained from the device$special information on absolute * sector 0. * * CALL: result = get_generic_data(ddata_ptr, unit, pnum_ptr) * * INPUTS: iors_ptr - points to iors * ddata_ptr - points to driver data * unit - unit being attached * pnum_ptr - points to partition number * * OUTPUTS: part_num - based variable indicating partition number * * RETURNS: result - TRUE if routine completes without error, FALSE otherwise * ****************************************************************************/ get_generic_data: PROCEDURE(iors_ptr, ddata_ptr, unit, pnum_ptr) BYTE REENTRANT; DECLARE iors_ptr POINTER, ddata_ptr POINTER, unit BYTE, pnum_ptr POINTER; DECLARE /* locals */ iors BASED iors_ptr IOREQRESSEG, u_data BASED ddata_ptr (NUMBEROFUNITS) unit_data, /* partition info */ ddata BASED ddata_ptr ddata_struc, /* driver data */ unit_att BYTE, /* unit alias for generic unit attached */ phys_unit BYTE, /* physical unit, 0 or 1 */ p_num BASED pnum_ptr BYTE, /* partition number */ d_ptr POINTER, /* points to device$special region in sector buffer */ d_spec BASED d_ptr STRUCTURE ( /* contains volume label device special data */ cylinders WORD, /* number of cylinders on whole disk */ fixed BYTE, /* number of heads */ pre_comp BYTE, /* write precomp/4 */ sectors BYTE, /* sectors per track */ sector_size WORD, /* bytes per sector */ alternates BYTE); /* not used */ $eject IF get_active_part(ddata_ptr, pnum_ptr) THEN DO; /* * Since the unit being attached is generic, we must prevent the actual * partition unit from being attached twice. To do this, we mark the * non-generic unit attached field TRUE and save the non generic unit * number in the attached field of the generic u_data. */ phys_unit = unit/UNITSPERDRIVE; unit_att = phys_unit * UNITSPERDRIVE + p_num; IF u_data(unit_att).attached THEN DO; iors.status = E$ALREADY$ATTACHED; iors.done = TRUE; RETURN FALSE; END; u_data(unit_att).attached = GENATTACHED; u_data(unit).attached = unit_att; /* get unit params from device$special */ d_ptr = @ddata.buf(DEVSPECOFFSET); u_data(unit).heads = d_spec.fixed; u_data(unit).sec_per_track = d_spec.sectors; u_data(unit).pre_comp = d_spec.pre_comp; u_data(unit).tot_cyl = d_spec.cylinders; RETURN TRUE; END; ELSE DO; CALL set_error(iors_ptr, IO$OPRINT); RETURN FALSE; END; END get_generic_data; $subtitle('get_non_generic_data') /**************************************************************************** * * PROC NAME: get_non_generic_data * * DESCRIPTION: Fill in driver data fields for non-generic partition. * The only fields assigned are those whose values are obtained * from a source different from their generic counterparts. * * * CALL: CALL get_non_generic_data(uinfo_ptr, ddata_ptr, unit, pnum_ptr) * * INPUTS: uinfo_ptr - points to unit information * ddata_ptr - points to driver data * unit - unit being attached * pnum_ptr - points to partition number * * OUTPUTS: part_num - based variable, partition number of unit attached * ****************************************************************************/ get_non_generic_data: PROCEDURE(uinfo_ptr, ddata_ptr, unit, pnum_ptr) REENTRANT; DECLARE uinfo_ptr POINTER, ddata_ptr POINTER, unit BYTE, pnum_ptr POINTER; DECLARE /* locals */ part_num BASED pnum_ptr BYTE, /* partition number */ uinfo BASED uinfo_ptr HDCINFOBLOCK, /* uinfo block */ u_data BASED ddata_ptr (NUMBEROFUNITS) unit_data; /* partition info */ part_num = unit mod UNITSPERDRIVE; u_data(unit).attached = TRUE; u_data(unit).pre_comp = uinfo.write_pre_comp; u_data(unit).sec_per_track = uinfo.sec_per_track; u_data(unit).heads = uinfo.num_heads; u_data(unit).tot_cyl = uinfo.no_of_cylinders; END get_non_generic_data; $subtitle('Delay procedure') delay: PROCEDURE REENTRANT; DECLARE i BYTE; i = 1; END delay; END x120wd;