ide-cd.c revision 3bb4663bd82e6d536a4b46166b00e93d5072e656
1/*
2 * ATAPI CD-ROM driver.
3 *
4 * Copyright (C) 1994-1996  Scott Snyder <snyder@fnald0.fnal.gov>
5 * Copyright (C) 1996-1998  Erik Andersen <andersee@debian.org>
6 * Copyright (C) 1998-2000  Jens Axboe <axboe@suse.de>
7 * Copyright (C)      2007  Bartlomiej Zolnierkiewicz
8 *
9 * May be copied or modified under the terms of the GNU General Public
10 * License.  See linux/COPYING for more information.
11 *
12 * See Documentation/cdrom/ide-cd for usage information.
13 *
14 * Suggestions are welcome. Patches that work are more welcome though. ;-)
15 * For those wishing to work on this driver, please be sure you download
16 * and comply with the latest Mt. Fuji (SFF8090 version 4) and ATAPI
17 * (SFF-8020i rev 2.6) standards. These documents can be obtained by
18 * anonymous ftp from:
19 * ftp://fission.dt.wdc.com/pub/standards/SFF_atapi/spec/SFF8020-r2.6/PS/8020r26.ps
20 * ftp://ftp.avc-pioneer.com/Mtfuji4/Spec/Fuji4r10.pdf
21 *
22 * For historical changelog please see:
23 *	Documentation/ide/ChangeLog.ide-cd.1994-2004
24 */
25
26#define IDECD_VERSION "5.00"
27
28#include <linux/module.h>
29#include <linux/types.h>
30#include <linux/kernel.h>
31#include <linux/delay.h>
32#include <linux/timer.h>
33#include <linux/slab.h>
34#include <linux/interrupt.h>
35#include <linux/errno.h>
36#include <linux/cdrom.h>
37#include <linux/ide.h>
38#include <linux/completion.h>
39#include <linux/mutex.h>
40#include <linux/bcd.h>
41
42#include <scsi/scsi.h>	/* For SCSI -> ATAPI command conversion */
43
44#include <asm/irq.h>
45#include <asm/io.h>
46#include <asm/byteorder.h>
47#include <asm/uaccess.h>
48#include <asm/unaligned.h>
49
50#include "ide-cd.h"
51
52static DEFINE_MUTEX(idecd_ref_mutex);
53
54#define to_ide_cd(obj) container_of(obj, struct cdrom_info, kref)
55
56#define ide_cd_g(disk) \
57	container_of((disk)->private_data, struct cdrom_info, driver)
58
59static struct cdrom_info *ide_cd_get(struct gendisk *disk)
60{
61	struct cdrom_info *cd = NULL;
62
63	mutex_lock(&idecd_ref_mutex);
64	cd = ide_cd_g(disk);
65	if (cd)
66		kref_get(&cd->kref);
67	mutex_unlock(&idecd_ref_mutex);
68	return cd;
69}
70
71static void ide_cd_release(struct kref *);
72
73static void ide_cd_put(struct cdrom_info *cd)
74{
75	mutex_lock(&idecd_ref_mutex);
76	kref_put(&cd->kref, ide_cd_release);
77	mutex_unlock(&idecd_ref_mutex);
78}
79
80/****************************************************************************
81 * Generic packet command support and error handling routines.
82 */
83
84/* Mark that we've seen a media change, and invalidate our internal
85   buffers. */
86static void cdrom_saw_media_change (ide_drive_t *drive)
87{
88	struct cdrom_info *cd = drive->driver_data;
89
90	cd->cd_flags |= IDE_CD_FLAG_MEDIA_CHANGED;
91	cd->cd_flags &= ~IDE_CD_FLAG_TOC_VALID;
92	cd->nsectors_buffered = 0;
93}
94
95static int cdrom_log_sense(ide_drive_t *drive, struct request *rq,
96			   struct request_sense *sense)
97{
98	int log = 0;
99
100	if (!sense || !rq || (rq->cmd_flags & REQ_QUIET))
101		return 0;
102
103	switch (sense->sense_key) {
104		case NO_SENSE: case RECOVERED_ERROR:
105			break;
106		case NOT_READY:
107			/*
108			 * don't care about tray state messages for
109			 * e.g. capacity commands or in-progress or
110			 * becoming ready
111			 */
112			if (sense->asc == 0x3a || sense->asc == 0x04)
113				break;
114			log = 1;
115			break;
116		case ILLEGAL_REQUEST:
117			/*
118			 * don't log START_STOP unit with LoEj set, since
119			 * we cannot reliably check if drive can auto-close
120			 */
121			if (rq->cmd[0] == GPCMD_START_STOP_UNIT && sense->asc == 0x24)
122				break;
123			log = 1;
124			break;
125		case UNIT_ATTENTION:
126			/*
127			 * Make good and sure we've seen this potential media
128			 * change. Some drives (i.e. Creative) fail to present
129			 * the correct sense key in the error register.
130			 */
131			cdrom_saw_media_change(drive);
132			break;
133		default:
134			log = 1;
135			break;
136	}
137	return log;
138}
139
140static
141void cdrom_analyze_sense_data(ide_drive_t *drive,
142			      struct request *failed_command,
143			      struct request_sense *sense)
144{
145	unsigned long sector;
146	unsigned long bio_sectors;
147	unsigned long valid;
148	struct cdrom_info *info = drive->driver_data;
149
150	if (!cdrom_log_sense(drive, failed_command, sense))
151		return;
152
153	/*
154	 * If a read toc is executed for a CD-R or CD-RW medium where
155	 * the first toc has not been recorded yet, it will fail with
156	 * 05/24/00 (which is a confusing error)
157	 */
158	if (failed_command && failed_command->cmd[0] == GPCMD_READ_TOC_PMA_ATIP)
159		if (sense->sense_key == 0x05 && sense->asc == 0x24)
160			return;
161
162 	if (sense->error_code == 0x70) {	/* Current Error */
163 		switch(sense->sense_key) {
164		case MEDIUM_ERROR:
165		case VOLUME_OVERFLOW:
166		case ILLEGAL_REQUEST:
167			if (!sense->valid)
168				break;
169			if (failed_command == NULL ||
170					!blk_fs_request(failed_command))
171				break;
172			sector = (sense->information[0] << 24) |
173				 (sense->information[1] << 16) |
174				 (sense->information[2] <<  8) |
175				 (sense->information[3]);
176
177			bio_sectors = bio_sectors(failed_command->bio);
178			if (bio_sectors < 4)
179				bio_sectors = 4;
180			if (drive->queue->hardsect_size == 2048)
181				sector <<= 2;	/* Device sector size is 2K */
182			sector &= ~(bio_sectors -1);
183			valid = (sector - failed_command->sector) << 9;
184
185			if (valid < 0)
186				valid = 0;
187			if (sector < get_capacity(info->disk) &&
188				drive->probed_capacity - sector < 4 * 75) {
189				set_capacity(info->disk, sector);
190			}
191 		}
192 	}
193
194	ide_cd_log_error(drive->name, failed_command, sense);
195}
196
197/*
198 * Initialize a ide-cd packet command request
199 */
200void ide_cd_init_rq(ide_drive_t *drive, struct request *rq)
201{
202	struct cdrom_info *cd = drive->driver_data;
203
204	ide_init_drive_cmd(rq);
205	rq->cmd_type = REQ_TYPE_ATA_PC;
206	rq->rq_disk = cd->disk;
207}
208
209static void cdrom_queue_request_sense(ide_drive_t *drive, void *sense,
210				      struct request *failed_command)
211{
212	struct cdrom_info *info		= drive->driver_data;
213	struct request *rq		= &info->request_sense_request;
214
215	if (sense == NULL)
216		sense = &info->sense_data;
217
218	/* stuff the sense request in front of our current request */
219	ide_cd_init_rq(drive, rq);
220
221	rq->data = sense;
222	rq->cmd[0] = GPCMD_REQUEST_SENSE;
223	rq->cmd[4] = rq->data_len = 18;
224
225	rq->cmd_type = REQ_TYPE_SENSE;
226
227	/* NOTE! Save the failed command in "rq->buffer" */
228	rq->buffer = (void *) failed_command;
229
230	(void) ide_do_drive_cmd(drive, rq, ide_preempt);
231}
232
233static void cdrom_end_request (ide_drive_t *drive, int uptodate)
234{
235	struct request *rq = HWGROUP(drive)->rq;
236	int nsectors = rq->hard_cur_sectors;
237
238	if (blk_sense_request(rq) && uptodate) {
239		/*
240		 * For REQ_TYPE_SENSE, "rq->buffer" points to the original
241		 * failed request
242		 */
243		struct request *failed = (struct request *) rq->buffer;
244		struct cdrom_info *info = drive->driver_data;
245		void *sense = &info->sense_data;
246		unsigned long flags;
247
248		if (failed) {
249			if (failed->sense) {
250				sense = failed->sense;
251				failed->sense_len = rq->sense_len;
252			}
253			cdrom_analyze_sense_data(drive, failed, sense);
254			/*
255			 * now end failed request
256			 */
257			if (blk_fs_request(failed)) {
258				if (ide_end_dequeued_request(drive, failed, 0,
259						failed->hard_nr_sectors))
260					BUG();
261			} else {
262				spin_lock_irqsave(&ide_lock, flags);
263				if (__blk_end_request(failed, -EIO,
264						      failed->data_len))
265					BUG();
266				spin_unlock_irqrestore(&ide_lock, flags);
267			}
268		} else
269			cdrom_analyze_sense_data(drive, NULL, sense);
270	}
271
272	if (!rq->current_nr_sectors && blk_fs_request(rq))
273		uptodate = 1;
274	/* make sure it's fully ended */
275	if (blk_pc_request(rq))
276		nsectors = (rq->data_len + 511) >> 9;
277	if (!nsectors)
278		nsectors = 1;
279
280	ide_end_request(drive, uptodate, nsectors);
281}
282
283static void ide_dump_status_no_sense(ide_drive_t *drive, const char *msg, u8 stat)
284{
285	if (stat & 0x80)
286		return;
287	ide_dump_status(drive, msg, stat);
288}
289
290/* Returns 0 if the request should be continued.
291   Returns 1 if the request was ended. */
292static int cdrom_decode_status(ide_drive_t *drive, int good_stat, int *stat_ret)
293{
294	struct request *rq = HWGROUP(drive)->rq;
295	int stat, err, sense_key;
296
297	/* Check for errors. */
298	stat = HWIF(drive)->INB(IDE_STATUS_REG);
299	if (stat_ret)
300		*stat_ret = stat;
301
302	if (OK_STAT(stat, good_stat, BAD_R_STAT))
303		return 0;
304
305	/* Get the IDE error register. */
306	err = HWIF(drive)->INB(IDE_ERROR_REG);
307	sense_key = err >> 4;
308
309	if (rq == NULL) {
310		printk("%s: missing rq in cdrom_decode_status\n", drive->name);
311		return 1;
312	}
313
314	if (blk_sense_request(rq)) {
315		/* We got an error trying to get sense info
316		   from the drive (probably while trying
317		   to recover from a former error).  Just give up. */
318
319		rq->cmd_flags |= REQ_FAILED;
320		cdrom_end_request(drive, 0);
321		ide_error(drive, "request sense failure", stat);
322		return 1;
323
324	} else if (blk_pc_request(rq) || rq->cmd_type == REQ_TYPE_ATA_PC) {
325		/* All other functions, except for READ. */
326
327		/*
328		 * if we have an error, pass back CHECK_CONDITION as the
329		 * scsi status byte
330		 */
331		if (blk_pc_request(rq) && !rq->errors)
332			rq->errors = SAM_STAT_CHECK_CONDITION;
333
334		/* Check for tray open. */
335		if (sense_key == NOT_READY) {
336			cdrom_saw_media_change (drive);
337		} else if (sense_key == UNIT_ATTENTION) {
338			/* Check for media change. */
339			cdrom_saw_media_change (drive);
340			/*printk("%s: media changed\n",drive->name);*/
341			return 0;
342 		} else if ((sense_key == ILLEGAL_REQUEST) &&
343 			   (rq->cmd[0] == GPCMD_START_STOP_UNIT)) {
344 			/*
345 			 * Don't print error message for this condition--
346 			 * SFF8090i indicates that 5/24/00 is the correct
347 			 * response to a request to close the tray if the
348 			 * drive doesn't have that capability.
349 			 * cdrom_log_sense() knows this!
350 			 */
351		} else if (!(rq->cmd_flags & REQ_QUIET)) {
352			/* Otherwise, print an error. */
353			ide_dump_status(drive, "packet command error", stat);
354		}
355
356		rq->cmd_flags |= REQ_FAILED;
357
358		/*
359		 * instead of playing games with moving completions around,
360		 * remove failed request completely and end it when the
361		 * request sense has completed
362		 */
363		goto end_request;
364
365	} else if (blk_fs_request(rq)) {
366		int do_end_request = 0;
367
368		/* Handle errors from READ and WRITE requests. */
369
370		if (blk_noretry_request(rq))
371			do_end_request = 1;
372
373		if (sense_key == NOT_READY) {
374			/* Tray open. */
375			if (rq_data_dir(rq) == READ) {
376				cdrom_saw_media_change (drive);
377
378				/* Fail the request. */
379				printk ("%s: tray open\n", drive->name);
380				do_end_request = 1;
381			} else {
382				struct cdrom_info *info = drive->driver_data;
383
384				/* allow the drive 5 seconds to recover, some
385				 * devices will return this error while flushing
386				 * data from cache */
387				if (!rq->errors)
388					info->write_timeout = jiffies + ATAPI_WAIT_WRITE_BUSY;
389				rq->errors = 1;
390				if (time_after(jiffies, info->write_timeout))
391					do_end_request = 1;
392				else {
393					unsigned long flags;
394
395					/*
396					 * take a breather relying on the
397					 * unplug timer to kick us again
398					 */
399					spin_lock_irqsave(&ide_lock, flags);
400					blk_plug_device(drive->queue);
401					spin_unlock_irqrestore(&ide_lock,flags);
402					return 1;
403				}
404			}
405		} else if (sense_key == UNIT_ATTENTION) {
406			/* Media change. */
407			cdrom_saw_media_change (drive);
408
409			/* Arrange to retry the request.
410			   But be sure to give up if we've retried
411			   too many times. */
412			if (++rq->errors > ERROR_MAX)
413				do_end_request = 1;
414		} else if (sense_key == ILLEGAL_REQUEST ||
415			   sense_key == DATA_PROTECT) {
416			/* No point in retrying after an illegal
417			   request or data protect error.*/
418			ide_dump_status_no_sense (drive, "command error", stat);
419			do_end_request = 1;
420		} else if (sense_key == MEDIUM_ERROR) {
421			/* No point in re-trying a zillion times on a bad
422			 * sector...  If we got here the error is not correctable */
423			ide_dump_status_no_sense (drive, "media error (bad sector)", stat);
424			do_end_request = 1;
425		} else if (sense_key == BLANK_CHECK) {
426			/* Disk appears blank ?? */
427			ide_dump_status_no_sense (drive, "media error (blank)", stat);
428			do_end_request = 1;
429		} else if ((err & ~ABRT_ERR) != 0) {
430			/* Go to the default handler
431			   for other errors. */
432			ide_error(drive, "cdrom_decode_status", stat);
433			return 1;
434		} else if ((++rq->errors > ERROR_MAX)) {
435			/* We've racked up too many retries.  Abort. */
436			do_end_request = 1;
437		}
438
439		/* End a request through request sense analysis when we have
440		   sense data. We need this in order to perform end of media
441		   processing */
442
443		if (do_end_request)
444			goto end_request;
445
446		/*
447		 * If we got a CHECK_CONDITION status,
448		 * queue a request sense command.
449		 */
450		if (stat & ERR_STAT)
451			cdrom_queue_request_sense(drive, NULL, NULL);
452	} else {
453		blk_dump_rq_flags(rq, "ide-cd: bad rq");
454		cdrom_end_request(drive, 0);
455	}
456
457	/* Retry, or handle the next request. */
458	return 1;
459
460end_request:
461	if (stat & ERR_STAT) {
462		unsigned long flags;
463
464		spin_lock_irqsave(&ide_lock, flags);
465		blkdev_dequeue_request(rq);
466		HWGROUP(drive)->rq = NULL;
467		spin_unlock_irqrestore(&ide_lock, flags);
468
469		cdrom_queue_request_sense(drive, rq->sense, rq);
470	} else
471		cdrom_end_request(drive, 0);
472
473	return 1;
474}
475
476static int cdrom_timer_expiry(ide_drive_t *drive)
477{
478	struct request *rq = HWGROUP(drive)->rq;
479	unsigned long wait = 0;
480
481	/*
482	 * Some commands are *slow* and normally take a long time to
483	 * complete. Usually we can use the ATAPI "disconnect" to bypass
484	 * this, but not all commands/drives support that. Let
485	 * ide_timer_expiry keep polling us for these.
486	 */
487	switch (rq->cmd[0]) {
488		case GPCMD_BLANK:
489		case GPCMD_FORMAT_UNIT:
490		case GPCMD_RESERVE_RZONE_TRACK:
491		case GPCMD_CLOSE_TRACK:
492		case GPCMD_FLUSH_CACHE:
493			wait = ATAPI_WAIT_PC;
494			break;
495		default:
496			if (!(rq->cmd_flags & REQ_QUIET))
497				printk(KERN_INFO "ide-cd: cmd 0x%x timed out\n", rq->cmd[0]);
498			wait = 0;
499			break;
500	}
501	return wait;
502}
503
504/* Set up the device registers for transferring a packet command on DEV,
505   expecting to later transfer XFERLEN bytes.  HANDLER is the routine
506   which actually transfers the command to the drive.  If this is a
507   drq_interrupt device, this routine will arrange for HANDLER to be
508   called when the interrupt from the drive arrives.  Otherwise, HANDLER
509   will be called immediately after the drive is prepared for the transfer. */
510
511static ide_startstop_t cdrom_start_packet_command(ide_drive_t *drive,
512						  int xferlen,
513						  ide_handler_t *handler)
514{
515	ide_startstop_t startstop;
516	struct cdrom_info *info = drive->driver_data;
517	ide_hwif_t *hwif = drive->hwif;
518
519	/* Wait for the controller to be idle. */
520	if (ide_wait_stat(&startstop, drive, 0, BUSY_STAT, WAIT_READY))
521		return startstop;
522
523	/* FIXME: for Virtual DMA we must check harder */
524	if (info->dma)
525		info->dma = !hwif->dma_setup(drive);
526
527	/* Set up the controller registers. */
528	ide_pktcmd_tf_load(drive, IDE_TFLAG_OUT_NSECT | IDE_TFLAG_OUT_LBAL |
529			   IDE_TFLAG_NO_SELECT_MASK, xferlen, info->dma);
530
531	if (info->cd_flags & IDE_CD_FLAG_DRQ_INTERRUPT) {
532		/* waiting for CDB interrupt, not DMA yet. */
533		if (info->dma)
534			drive->waiting_for_dma = 0;
535
536		/* packet command */
537		ide_execute_command(drive, WIN_PACKETCMD, handler, ATAPI_WAIT_PC, cdrom_timer_expiry);
538		return ide_started;
539	} else {
540		unsigned long flags;
541
542		/* packet command */
543		spin_lock_irqsave(&ide_lock, flags);
544		hwif->OUTBSYNC(drive, WIN_PACKETCMD, IDE_COMMAND_REG);
545		ndelay(400);
546		spin_unlock_irqrestore(&ide_lock, flags);
547
548		return (*handler) (drive);
549	}
550}
551
552/* Send a packet command to DRIVE described by CMD_BUF and CMD_LEN.
553   The device registers must have already been prepared
554   by cdrom_start_packet_command.
555   HANDLER is the interrupt handler to call when the command completes
556   or there's data ready. */
557#define ATAPI_MIN_CDB_BYTES 12
558static ide_startstop_t cdrom_transfer_packet_command (ide_drive_t *drive,
559					  struct request *rq,
560					  ide_handler_t *handler)
561{
562	ide_hwif_t *hwif = drive->hwif;
563	int cmd_len;
564	struct cdrom_info *info = drive->driver_data;
565	ide_startstop_t startstop;
566
567	if (info->cd_flags & IDE_CD_FLAG_DRQ_INTERRUPT) {
568		/* Here we should have been called after receiving an interrupt
569		   from the device.  DRQ should how be set. */
570
571		/* Check for errors. */
572		if (cdrom_decode_status(drive, DRQ_STAT, NULL))
573			return ide_stopped;
574
575		/* Ok, next interrupt will be DMA interrupt. */
576		if (info->dma)
577			drive->waiting_for_dma = 1;
578	} else {
579		/* Otherwise, we must wait for DRQ to get set. */
580		if (ide_wait_stat(&startstop, drive, DRQ_STAT,
581				BUSY_STAT, WAIT_READY))
582			return startstop;
583	}
584
585	/* Arm the interrupt handler. */
586	ide_set_handler(drive, handler, rq->timeout, cdrom_timer_expiry);
587
588	/* ATAPI commands get padded out to 12 bytes minimum */
589	cmd_len = COMMAND_SIZE(rq->cmd[0]);
590	if (cmd_len < ATAPI_MIN_CDB_BYTES)
591		cmd_len = ATAPI_MIN_CDB_BYTES;
592
593	/* Send the command to the device. */
594	HWIF(drive)->atapi_output_bytes(drive, rq->cmd, cmd_len);
595
596	/* Start the DMA if need be */
597	if (info->dma)
598		hwif->dma_start(drive);
599
600	return ide_started;
601}
602
603/****************************************************************************
604 * Block read functions.
605 */
606
607typedef void (xfer_func_t)(ide_drive_t *, void *, u32);
608
609static void ide_cd_pad_transfer(ide_drive_t *drive, xfer_func_t *xf, int len)
610{
611	while (len > 0) {
612		int dum = 0;
613		xf(drive, &dum, sizeof(dum));
614		len -= sizeof(dum);
615	}
616}
617
618static void ide_cd_drain_data(ide_drive_t *drive, int nsects)
619{
620	while (nsects > 0) {
621		static char dum[SECTOR_SIZE];
622
623		drive->hwif->atapi_input_bytes(drive, dum, sizeof(dum));
624		nsects--;
625	}
626}
627
628/*
629 * Buffer up to SECTORS_TO_TRANSFER sectors from the drive in our sector
630 * buffer.  Once the first sector is added, any subsequent sectors are
631 * assumed to be continuous (until the buffer is cleared).  For the first
632 * sector added, SECTOR is its sector number.  (SECTOR is then ignored until
633 * the buffer is cleared.)
634 */
635static void cdrom_buffer_sectors (ide_drive_t *drive, unsigned long sector,
636                                  int sectors_to_transfer)
637{
638	struct cdrom_info *info = drive->driver_data;
639
640	/* Number of sectors to read into the buffer. */
641	int sectors_to_buffer = min_t(int, sectors_to_transfer,
642				     (SECTOR_BUFFER_SIZE >> SECTOR_BITS) -
643				       info->nsectors_buffered);
644
645	char *dest;
646
647	/* If we couldn't get a buffer, don't try to buffer anything... */
648	if (info->buffer == NULL)
649		sectors_to_buffer = 0;
650
651	/* If this is the first sector in the buffer, remember its number. */
652	if (info->nsectors_buffered == 0)
653		info->sector_buffered = sector;
654
655	/* Read the data into the buffer. */
656	dest = info->buffer + info->nsectors_buffered * SECTOR_SIZE;
657	while (sectors_to_buffer > 0) {
658		HWIF(drive)->atapi_input_bytes(drive, dest, SECTOR_SIZE);
659		--sectors_to_buffer;
660		--sectors_to_transfer;
661		++info->nsectors_buffered;
662		dest += SECTOR_SIZE;
663	}
664
665	/* Throw away any remaining data. */
666	ide_cd_drain_data(drive, sectors_to_transfer);
667}
668
669/*
670 * Check the contents of the interrupt reason register from the cdrom
671 * and attempt to recover if there are problems.  Returns  0 if everything's
672 * ok; nonzero if the request has been terminated.
673 */
674static
675int ide_cd_check_ireason(ide_drive_t *drive, int len, int ireason, int rw)
676{
677	/*
678	 * ireason == 0: the drive wants to receive data from us
679	 * ireason == 2: the drive is expecting to transfer data to us
680	 */
681	if (ireason == (!rw << 1))
682		return 0;
683	else if (ireason == (rw << 1)) {
684		ide_hwif_t *hwif = drive->hwif;
685		xfer_func_t *xf;
686
687		/* Whoops... */
688		printk(KERN_ERR "%s: %s: wrong transfer direction!\n",
689				drive->name, __FUNCTION__);
690
691		xf = rw ? hwif->atapi_output_bytes : hwif->atapi_input_bytes;
692		ide_cd_pad_transfer(drive, xf, len);
693	} else  if (rw == 0 && ireason == 1) {
694		/* Some drives (ASUS) seem to tell us that status
695		 * info is available. just get it and ignore.
696		 */
697		(void) HWIF(drive)->INB(IDE_STATUS_REG);
698		return 0;
699	} else {
700		/* Drive wants a command packet, or invalid ireason... */
701		printk(KERN_ERR "%s: %s: bad interrupt reason 0x%02x\n",
702				drive->name, __FUNCTION__, ireason);
703	}
704
705	cdrom_end_request(drive, 0);
706	return -1;
707}
708
709/*
710 * Assume that the drive will always provide data in multiples of at least
711 * SECTOR_SIZE, as it gets hairy to keep track of the transfers otherwise.
712 */
713static int ide_cd_check_transfer_size(ide_drive_t *drive, int len)
714{
715	struct cdrom_info *cd = drive->driver_data;
716
717	if ((len % SECTOR_SIZE) == 0)
718		return 0;
719
720	printk(KERN_ERR "%s: %s: Bad transfer size %d\n",
721			drive->name, __FUNCTION__, len);
722
723	if (cd->cd_flags & IDE_CD_FLAG_LIMIT_NFRAMES)
724		printk(KERN_ERR "  This drive is not supported by "
725				"this version of the driver\n");
726	else {
727		printk(KERN_ERR "  Trying to limit transfer sizes\n");
728		cd->cd_flags |= IDE_CD_FLAG_LIMIT_NFRAMES;
729	}
730
731	return 1;
732}
733
734/*
735 * Try to satisfy some of the current read request from our cached data.
736 * Returns nonzero if the request has been completed, zero otherwise.
737 */
738static int cdrom_read_from_buffer (ide_drive_t *drive)
739{
740	struct cdrom_info *info = drive->driver_data;
741	struct request *rq = HWGROUP(drive)->rq;
742	unsigned short sectors_per_frame;
743
744	sectors_per_frame = queue_hardsect_size(drive->queue) >> SECTOR_BITS;
745
746	/* Can't do anything if there's no buffer. */
747	if (info->buffer == NULL) return 0;
748
749	/* Loop while this request needs data and the next block is present
750	   in our cache. */
751	while (rq->nr_sectors > 0 &&
752	       rq->sector >= info->sector_buffered &&
753	       rq->sector < info->sector_buffered + info->nsectors_buffered) {
754		if (rq->current_nr_sectors == 0)
755			cdrom_end_request(drive, 1);
756
757		memcpy (rq->buffer,
758			info->buffer +
759			(rq->sector - info->sector_buffered) * SECTOR_SIZE,
760			SECTOR_SIZE);
761		rq->buffer += SECTOR_SIZE;
762		--rq->current_nr_sectors;
763		--rq->nr_sectors;
764		++rq->sector;
765	}
766
767	/* If we've satisfied the current request,
768	   terminate it successfully. */
769	if (rq->nr_sectors == 0) {
770		cdrom_end_request(drive, 1);
771		return -1;
772	}
773
774	/* Move on to the next buffer if needed. */
775	if (rq->current_nr_sectors == 0)
776		cdrom_end_request(drive, 1);
777
778	/* If this condition does not hold, then the kluge i use to
779	   represent the number of sectors to skip at the start of a transfer
780	   will fail.  I think that this will never happen, but let's be
781	   paranoid and check. */
782	if (rq->current_nr_sectors < bio_cur_sectors(rq->bio) &&
783	    (rq->sector & (sectors_per_frame - 1))) {
784		printk(KERN_ERR "%s: cdrom_read_from_buffer: buffer botch (%ld)\n",
785			drive->name, (long)rq->sector);
786		cdrom_end_request(drive, 0);
787		return -1;
788	}
789
790	return 0;
791}
792
793static ide_startstop_t cdrom_newpc_intr(ide_drive_t *);
794
795/*
796 * Routine to send a read/write packet command to the drive.
797 * This is usually called directly from cdrom_start_{read,write}().
798 * However, for drq_interrupt devices, it is called from an interrupt
799 * when the drive is ready to accept the command.
800 */
801static ide_startstop_t cdrom_start_rw_cont(ide_drive_t *drive)
802{
803	struct request *rq = HWGROUP(drive)->rq;
804
805	if (rq_data_dir(rq) == READ) {
806		unsigned short sectors_per_frame =
807			queue_hardsect_size(drive->queue) >> SECTOR_BITS;
808		int nskip = rq->sector & (sectors_per_frame - 1);
809
810		/*
811		 * If the requested sector doesn't start on a frame boundary,
812		 * we must adjust the start of the transfer so that it does,
813		 * and remember to skip the first few sectors.
814		 *
815		 * If the rq->current_nr_sectors field is larger than the size
816		 * of the buffer, it will mean that we're to skip a number of
817		 * sectors equal to the amount by which rq->current_nr_sectors
818		 * is larger than the buffer size.
819		 */
820		if (nskip > 0) {
821			/* Sanity check... */
822			if (rq->current_nr_sectors !=
823			    bio_cur_sectors(rq->bio)) {
824				printk(KERN_ERR "%s: %s: buffer botch (%u)\n",
825						drive->name, __FUNCTION__,
826						rq->current_nr_sectors);
827				cdrom_end_request(drive, 0);
828				return ide_stopped;
829			}
830			rq->current_nr_sectors += nskip;
831		}
832	}
833#if 0
834	else
835		/* the immediate bit */
836		rq->cmd[1] = 1 << 3;
837#endif
838	/* Set up the command */
839	rq->timeout = ATAPI_WAIT_PC;
840
841	/* Send the command to the drive and return. */
842	return cdrom_transfer_packet_command(drive, rq, cdrom_newpc_intr);
843}
844
845#define IDECD_SEEK_THRESHOLD	(1000)			/* 1000 blocks */
846#define IDECD_SEEK_TIMER	(5 * WAIT_MIN_SLEEP)	/* 100 ms */
847#define IDECD_SEEK_TIMEOUT	(2 * WAIT_CMD)		/* 20 sec */
848
849static ide_startstop_t cdrom_seek_intr (ide_drive_t *drive)
850{
851	struct cdrom_info *info = drive->driver_data;
852	int stat;
853	static int retry = 10;
854
855	if (cdrom_decode_status(drive, 0, &stat))
856		return ide_stopped;
857
858	info->cd_flags |= IDE_CD_FLAG_SEEKING;
859
860	if (retry && time_after(jiffies, info->start_seek + IDECD_SEEK_TIMER)) {
861		if (--retry == 0) {
862			/*
863			 * this condition is far too common, to bother
864			 * users about it
865			 */
866			/* printk("%s: disabled DSC seek overlap\n", drive->name);*/
867			drive->dsc_overlap = 0;
868		}
869	}
870	return ide_stopped;
871}
872
873static ide_startstop_t cdrom_start_seek_continuation (ide_drive_t *drive)
874{
875	struct request *rq = HWGROUP(drive)->rq;
876	sector_t frame = rq->sector;
877
878	sector_div(frame, queue_hardsect_size(drive->queue) >> SECTOR_BITS);
879
880	memset(rq->cmd, 0, sizeof(rq->cmd));
881	rq->cmd[0] = GPCMD_SEEK;
882	put_unaligned(cpu_to_be32(frame), (unsigned int *) &rq->cmd[2]);
883
884	rq->timeout = ATAPI_WAIT_PC;
885	return cdrom_transfer_packet_command(drive, rq, &cdrom_seek_intr);
886}
887
888static ide_startstop_t cdrom_start_seek (ide_drive_t *drive, unsigned int block)
889{
890	struct cdrom_info *info = drive->driver_data;
891
892	info->dma = 0;
893	info->start_seek = jiffies;
894	return cdrom_start_packet_command(drive, 0, cdrom_start_seek_continuation);
895}
896
897/* Fix up a possibly partially-processed request so that we can
898   start it over entirely, or even put it back on the request queue. */
899static void restore_request (struct request *rq)
900{
901	if (rq->buffer != bio_data(rq->bio)) {
902		sector_t n = (rq->buffer - (char *) bio_data(rq->bio)) / SECTOR_SIZE;
903
904		rq->buffer = bio_data(rq->bio);
905		rq->nr_sectors += n;
906		rq->sector -= n;
907	}
908	rq->hard_cur_sectors = rq->current_nr_sectors = bio_cur_sectors(rq->bio);
909	rq->hard_nr_sectors = rq->nr_sectors;
910	rq->hard_sector = rq->sector;
911	rq->q->prep_rq_fn(rq->q, rq);
912}
913
914/****************************************************************************
915 * Execute all other packet commands.
916 */
917
918static void ide_cd_request_sense_fixup(struct request *rq)
919{
920	/*
921	 * Some of the trailing request sense fields are optional,
922	 * and some drives don't send them.  Sigh.
923	 */
924	if (rq->cmd[0] == GPCMD_REQUEST_SENSE &&
925	    rq->data_len > 0 && rq->data_len <= 5)
926		while (rq->data_len > 0) {
927			*(u8 *)rq->data++ = 0;
928			--rq->data_len;
929		}
930}
931
932int ide_cd_queue_pc(ide_drive_t *drive, struct request *rq)
933{
934	struct request_sense sense;
935	int retries = 10;
936	unsigned int flags = rq->cmd_flags;
937
938	if (rq->sense == NULL)
939		rq->sense = &sense;
940
941	/* Start of retry loop. */
942	do {
943		int error;
944		unsigned long time = jiffies;
945		rq->cmd_flags = flags;
946
947		error = ide_do_drive_cmd(drive, rq, ide_wait);
948		time = jiffies - time;
949
950		/* FIXME: we should probably abort/retry or something
951		 * in case of failure */
952		if (rq->cmd_flags & REQ_FAILED) {
953			/* The request failed.  Retry if it was due to a unit
954			   attention status
955			   (usually means media was changed). */
956			struct request_sense *reqbuf = rq->sense;
957
958			if (reqbuf->sense_key == UNIT_ATTENTION)
959				cdrom_saw_media_change(drive);
960			else if (reqbuf->sense_key == NOT_READY &&
961				 reqbuf->asc == 4 && reqbuf->ascq != 4) {
962				/* The drive is in the process of loading
963				   a disk.  Retry, but wait a little to give
964				   the drive time to complete the load. */
965				ssleep(2);
966			} else {
967				/* Otherwise, don't retry. */
968				retries = 0;
969			}
970			--retries;
971		}
972
973		/* End of retry loop. */
974	} while ((rq->cmd_flags & REQ_FAILED) && retries >= 0);
975
976	/* Return an error if the command failed. */
977	return (rq->cmd_flags & REQ_FAILED) ? -EIO : 0;
978}
979
980/*
981 * Called from blk_end_request_callback() after the data of the request
982 * is completed and before the request is completed.
983 * By returning value '1', blk_end_request_callback() returns immediately
984 * without completing the request.
985 */
986static int cdrom_newpc_intr_dummy_cb(struct request *rq)
987{
988	return 1;
989}
990
991static ide_startstop_t cdrom_newpc_intr(ide_drive_t *drive)
992{
993	struct cdrom_info *info = drive->driver_data;
994	struct request *rq = HWGROUP(drive)->rq;
995	xfer_func_t *xferfunc;
996	ide_expiry_t *expiry = NULL;
997	int dma_error = 0, dma, stat, ireason, len, thislen, uptodate = 0;
998	int write = (rq_data_dir(rq) == WRITE) ? 1 : 0;
999	unsigned int timeout;
1000	u8 lowcyl, highcyl;
1001
1002	/* Check for errors. */
1003	dma = info->dma;
1004	if (dma) {
1005		info->dma = 0;
1006		dma_error = HWIF(drive)->ide_dma_end(drive);
1007		if (dma_error) {
1008			printk(KERN_ERR "%s: DMA %s error\n", drive->name,
1009					write ? "write" : "read");
1010			ide_dma_off(drive);
1011		}
1012	}
1013
1014	if (cdrom_decode_status(drive, 0, &stat))
1015		return ide_stopped;
1016
1017	/*
1018	 * using dma, transfer is complete now
1019	 */
1020	if (dma) {
1021		if (dma_error)
1022			return ide_error(drive, "dma error", stat);
1023		if (blk_fs_request(rq)) {
1024			ide_end_request(drive, 1, rq->nr_sectors);
1025			return ide_stopped;
1026		}
1027		goto end_request;
1028	}
1029
1030	/*
1031	 * ok we fall to pio :/
1032	 */
1033	ireason = HWIF(drive)->INB(IDE_IREASON_REG) & 0x3;
1034	lowcyl  = HWIF(drive)->INB(IDE_BCOUNTL_REG);
1035	highcyl = HWIF(drive)->INB(IDE_BCOUNTH_REG);
1036
1037	len = lowcyl + (256 * highcyl);
1038
1039	thislen = blk_fs_request(rq) ? len : rq->data_len;
1040	if (thislen > len)
1041		thislen = len;
1042
1043	/*
1044	 * If DRQ is clear, the command has completed.
1045	 */
1046	if ((stat & DRQ_STAT) == 0) {
1047		if (blk_fs_request(rq)) {
1048			/*
1049			 * If we're not done reading/writing, complain.
1050			 * Otherwise, complete the command normally.
1051			 */
1052			uptodate = 1;
1053			if (rq->current_nr_sectors > 0) {
1054				printk(KERN_ERR "%s: %s: data underrun "
1055						"(%d blocks)\n",
1056						drive->name, __FUNCTION__,
1057						rq->current_nr_sectors);
1058				if (!write)
1059					rq->cmd_flags |= REQ_FAILED;
1060				uptodate = 0;
1061			}
1062			cdrom_end_request(drive, uptodate);
1063			return ide_stopped;
1064		} else if (!blk_pc_request(rq)) {
1065			ide_cd_request_sense_fixup(rq);
1066			/* Complain if we still have data left to transfer. */
1067			uptodate = rq->data_len ? 0 : 1;
1068		}
1069		goto end_request;
1070	}
1071
1072	/*
1073	 * check which way to transfer data
1074	 */
1075	if (blk_fs_request(rq) || blk_pc_request(rq)) {
1076		if (ide_cd_check_ireason(drive, len, ireason, write))
1077			return ide_stopped;
1078
1079		if (blk_fs_request(rq) && write == 0) {
1080			int nskip;
1081
1082			if (ide_cd_check_transfer_size(drive, len)) {
1083				cdrom_end_request(drive, 0);
1084				return ide_stopped;
1085			}
1086
1087			/*
1088			 * First, figure out if we need to bit-bucket
1089			 * any of the leading sectors.
1090			 */
1091			nskip = min_t(int, rq->current_nr_sectors
1092					   - bio_cur_sectors(rq->bio),
1093					   thislen >> 9);
1094			if (nskip > 0) {
1095				ide_cd_drain_data(drive, nskip);
1096				rq->current_nr_sectors -= nskip;
1097				thislen -= (nskip << 9);
1098			}
1099		}
1100	}
1101
1102	if (ireason == 0) {
1103		write = 1;
1104		xferfunc = HWIF(drive)->atapi_output_bytes;
1105	} else if (ireason == 2 || (ireason == 1 &&
1106		   (blk_fs_request(rq) || blk_pc_request(rq)))) {
1107		write = 0;
1108		xferfunc = HWIF(drive)->atapi_input_bytes;
1109	} else {
1110		printk(KERN_ERR "%s: %s: The drive "
1111				"appears confused (ireason = 0x%02x). "
1112				"Trying to recover by ending request.\n",
1113				drive->name, __FUNCTION__, ireason);
1114		goto end_request;
1115	}
1116
1117	/*
1118	 * transfer data
1119	 */
1120	while (thislen > 0) {
1121		u8 *ptr = blk_fs_request(rq) ? NULL : rq->data;
1122		int blen = rq->data_len;
1123
1124		/*
1125		 * bio backed?
1126		 */
1127		if (rq->bio) {
1128			if (blk_fs_request(rq)) {
1129				ptr = rq->buffer;
1130				blen = rq->current_nr_sectors << 9;
1131			} else {
1132				ptr = bio_data(rq->bio);
1133				blen = bio_iovec(rq->bio)->bv_len;
1134			}
1135		}
1136
1137		if (!ptr) {
1138			if (blk_fs_request(rq) && !write)
1139				/*
1140				 * If the buffers are full, cache the rest
1141				 * of the data in our internal buffer.
1142				 */
1143				cdrom_buffer_sectors(drive, rq->sector,
1144						     thislen >> 9);
1145			else {
1146				printk(KERN_ERR "%s: confused, missing data\n",
1147						drive->name);
1148				blk_dump_rq_flags(rq, rq_data_dir(rq)
1149						  ? "cdrom_newpc_intr, write"
1150						  : "cdrom_newpc_intr, read");
1151			}
1152			break;
1153		}
1154
1155		if (blen > thislen)
1156			blen = thislen;
1157
1158		xferfunc(drive, ptr, blen);
1159
1160		thislen -= blen;
1161		len -= blen;
1162
1163		if (blk_fs_request(rq)) {
1164			rq->buffer += blen;
1165			rq->nr_sectors -= (blen >> 9);
1166			rq->current_nr_sectors -= (blen >> 9);
1167			rq->sector += (blen >> 9);
1168
1169			if (rq->current_nr_sectors == 0 && rq->nr_sectors)
1170				cdrom_end_request(drive, 1);
1171		} else {
1172			rq->data_len -= blen;
1173
1174			/*
1175			 * The request can't be completed until DRQ is cleared.
1176			 * So complete the data, but don't complete the request
1177			 * using the dummy function for the callback feature
1178			 * of blk_end_request_callback().
1179			 */
1180			if (rq->bio)
1181				blk_end_request_callback(rq, 0, blen,
1182						 cdrom_newpc_intr_dummy_cb);
1183			else
1184				rq->data += blen;
1185		}
1186	}
1187
1188	if (write && blk_sense_request(rq))
1189		rq->sense_len += thislen;
1190
1191	/*
1192	 * pad, if necessary
1193	 */
1194	if (!blk_fs_request(rq) && len > 0)
1195		ide_cd_pad_transfer(drive, xferfunc, len);
1196
1197	if (blk_pc_request(rq)) {
1198		timeout = rq->timeout;
1199	} else {
1200		timeout = ATAPI_WAIT_PC;
1201		if (!blk_fs_request(rq))
1202			expiry = cdrom_timer_expiry;
1203	}
1204
1205	ide_set_handler(drive, cdrom_newpc_intr, timeout, expiry);
1206	return ide_started;
1207
1208end_request:
1209	if (blk_pc_request(rq)) {
1210		unsigned long flags;
1211
1212		spin_lock_irqsave(&ide_lock, flags);
1213		if (__blk_end_request(rq, 0, rq->data_len))
1214			BUG();
1215		HWGROUP(drive)->rq = NULL;
1216		spin_unlock_irqrestore(&ide_lock, flags);
1217	} else {
1218		if (!uptodate)
1219			rq->cmd_flags |= REQ_FAILED;
1220		cdrom_end_request(drive, uptodate);
1221	}
1222	return ide_stopped;
1223}
1224
1225static ide_startstop_t cdrom_start_rw(ide_drive_t *drive, struct request *rq)
1226{
1227	struct cdrom_info *cd = drive->driver_data;
1228	int write = rq_data_dir(rq) == WRITE;
1229	unsigned short sectors_per_frame =
1230		queue_hardsect_size(drive->queue) >> SECTOR_BITS;
1231
1232	if (write) {
1233		/*
1234		 * disk has become write protected
1235		 */
1236		if (cd->disk->policy) {
1237			cdrom_end_request(drive, 0);
1238			return ide_stopped;
1239		}
1240	} else {
1241		/*
1242		 * We may be retrying this request after an error.  Fix up any
1243		 * weirdness which might be present in the request packet.
1244		 */
1245		restore_request(rq);
1246
1247		/* Satisfy whatever we can of this request from our cache. */
1248		if (cdrom_read_from_buffer(drive))
1249			return ide_stopped;
1250	}
1251
1252	/*
1253	 * use DMA, if possible / writes *must* be hardware frame aligned
1254	 */
1255	if ((rq->nr_sectors & (sectors_per_frame - 1)) ||
1256	    (rq->sector & (sectors_per_frame - 1))) {
1257		if (write) {
1258			cdrom_end_request(drive, 0);
1259			return ide_stopped;
1260		}
1261		cd->dma = 0;
1262	} else
1263		cd->dma = drive->using_dma;
1264
1265	/* Clear the local sector buffer. */
1266	cd->nsectors_buffered = 0;
1267
1268	if (write)
1269		cd->devinfo.media_written = 1;
1270
1271	/* Start sending the read/write request to the drive. */
1272	return cdrom_start_packet_command(drive, 32768, cdrom_start_rw_cont);
1273}
1274
1275static ide_startstop_t cdrom_do_newpc_cont(ide_drive_t *drive)
1276{
1277	struct request *rq = HWGROUP(drive)->rq;
1278
1279	if (!rq->timeout)
1280		rq->timeout = ATAPI_WAIT_PC;
1281
1282	return cdrom_transfer_packet_command(drive, rq, cdrom_newpc_intr);
1283}
1284
1285static ide_startstop_t cdrom_do_block_pc(ide_drive_t *drive, struct request *rq)
1286{
1287	struct cdrom_info *info = drive->driver_data;
1288
1289	if (blk_pc_request(rq))
1290		rq->cmd_flags |= REQ_QUIET;
1291	else
1292		rq->cmd_flags &= ~REQ_FAILED;
1293
1294	info->dma = 0;
1295
1296	/*
1297	 * sg request
1298	 */
1299	if (rq->bio) {
1300		int mask = drive->queue->dma_alignment;
1301		unsigned long addr = (unsigned long) page_address(bio_page(rq->bio));
1302
1303		info->dma = drive->using_dma;
1304
1305		/*
1306		 * check if dma is safe
1307		 *
1308		 * NOTE! The "len" and "addr" checks should possibly have
1309		 * separate masks.
1310		 */
1311		if ((rq->data_len & 15) || (addr & mask))
1312			info->dma = 0;
1313	}
1314
1315	/* Start sending the command to the drive. */
1316	return cdrom_start_packet_command(drive, rq->data_len, cdrom_do_newpc_cont);
1317}
1318
1319/****************************************************************************
1320 * cdrom driver request routine.
1321 */
1322static ide_startstop_t
1323ide_do_rw_cdrom (ide_drive_t *drive, struct request *rq, sector_t block)
1324{
1325	ide_startstop_t action;
1326	struct cdrom_info *info = drive->driver_data;
1327
1328	if (blk_fs_request(rq)) {
1329		if (info->cd_flags & IDE_CD_FLAG_SEEKING) {
1330			unsigned long elapsed = jiffies - info->start_seek;
1331			int stat = HWIF(drive)->INB(IDE_STATUS_REG);
1332
1333			if ((stat & SEEK_STAT) != SEEK_STAT) {
1334				if (elapsed < IDECD_SEEK_TIMEOUT) {
1335					ide_stall_queue(drive, IDECD_SEEK_TIMER);
1336					return ide_stopped;
1337				}
1338				printk (KERN_ERR "%s: DSC timeout\n", drive->name);
1339			}
1340			info->cd_flags &= ~IDE_CD_FLAG_SEEKING;
1341		}
1342		if ((rq_data_dir(rq) == READ) && IDE_LARGE_SEEK(info->last_block, block, IDECD_SEEK_THRESHOLD) && drive->dsc_overlap) {
1343			action = cdrom_start_seek(drive, block);
1344		} else
1345			action = cdrom_start_rw(drive, rq);
1346		info->last_block = block;
1347		return action;
1348	} else if (blk_sense_request(rq) || blk_pc_request(rq) ||
1349		   rq->cmd_type == REQ_TYPE_ATA_PC) {
1350		return cdrom_do_block_pc(drive, rq);
1351	} else if (blk_special_request(rq)) {
1352		/*
1353		 * right now this can only be a reset...
1354		 */
1355		cdrom_end_request(drive, 1);
1356		return ide_stopped;
1357	}
1358
1359	blk_dump_rq_flags(rq, "ide-cd bad flags");
1360	cdrom_end_request(drive, 0);
1361	return ide_stopped;
1362}
1363
1364
1365
1366/****************************************************************************
1367 * Ioctl handling.
1368 *
1369 * Routines which queue packet commands take as a final argument a pointer
1370 * to a request_sense struct.  If execution of the command results
1371 * in an error with a CHECK CONDITION status, this structure will be filled
1372 * with the results of the subsequent request sense command.  The pointer
1373 * can also be NULL, in which case no sense information is returned.
1374 */
1375
1376static
1377void msf_from_bcd (struct atapi_msf *msf)
1378{
1379	msf->minute = BCD2BIN(msf->minute);
1380	msf->second = BCD2BIN(msf->second);
1381	msf->frame  = BCD2BIN(msf->frame);
1382}
1383
1384static int cdrom_check_status(ide_drive_t *drive, struct request_sense *sense)
1385{
1386	struct request req;
1387	struct cdrom_info *info = drive->driver_data;
1388	struct cdrom_device_info *cdi = &info->devinfo;
1389
1390	ide_cd_init_rq(drive, &req);
1391
1392	req.sense = sense;
1393	req.cmd[0] = GPCMD_TEST_UNIT_READY;
1394	req.cmd_flags |= REQ_QUIET;
1395
1396	/*
1397	 * Sanyo 3 CD changer uses byte 7 of TEST_UNIT_READY to
1398	 * switch CDs instead of supporting the LOAD_UNLOAD opcode.
1399	 */
1400	req.cmd[7] = cdi->sanyo_slot % 3;
1401
1402	return ide_cd_queue_pc(drive, &req);
1403}
1404
1405/* Lock the door if LOCKFLAG is nonzero; unlock it otherwise. */
1406int ide_cd_lockdoor(ide_drive_t *drive, int lockflag,
1407		    struct request_sense *sense)
1408{
1409	struct cdrom_info *cd = drive->driver_data;
1410	struct request_sense my_sense;
1411	struct request req;
1412	int stat;
1413
1414	if (sense == NULL)
1415		sense = &my_sense;
1416
1417	/* If the drive cannot lock the door, just pretend. */
1418	if (cd->cd_flags & IDE_CD_FLAG_NO_DOORLOCK) {
1419		stat = 0;
1420	} else {
1421		ide_cd_init_rq(drive, &req);
1422		req.sense = sense;
1423		req.cmd[0] = GPCMD_PREVENT_ALLOW_MEDIUM_REMOVAL;
1424		req.cmd[4] = lockflag ? 1 : 0;
1425		stat = ide_cd_queue_pc(drive, &req);
1426	}
1427
1428	/* If we got an illegal field error, the drive
1429	   probably cannot lock the door. */
1430	if (stat != 0 &&
1431	    sense->sense_key == ILLEGAL_REQUEST &&
1432	    (sense->asc == 0x24 || sense->asc == 0x20)) {
1433		printk (KERN_ERR "%s: door locking not supported\n",
1434			drive->name);
1435		cd->cd_flags |= IDE_CD_FLAG_NO_DOORLOCK;
1436		stat = 0;
1437	}
1438
1439	/* no medium, that's alright. */
1440	if (stat != 0 && sense->sense_key == NOT_READY && sense->asc == 0x3a)
1441		stat = 0;
1442
1443	if (stat == 0) {
1444		if (lockflag)
1445			cd->cd_flags |= IDE_CD_FLAG_DOOR_LOCKED;
1446		else
1447			cd->cd_flags &= ~IDE_CD_FLAG_DOOR_LOCKED;
1448	}
1449
1450	return stat;
1451}
1452
1453
1454/* Eject the disk if EJECTFLAG is 0.
1455   If EJECTFLAG is 1, try to reload the disk. */
1456static int cdrom_eject(ide_drive_t *drive, int ejectflag,
1457		       struct request_sense *sense)
1458{
1459	struct cdrom_info *cd = drive->driver_data;
1460	struct cdrom_device_info *cdi = &cd->devinfo;
1461	struct request req;
1462	char loej = 0x02;
1463
1464	if ((cd->cd_flags & IDE_CD_FLAG_NO_EJECT) && !ejectflag)
1465		return -EDRIVE_CANT_DO_THIS;
1466
1467	/* reload fails on some drives, if the tray is locked */
1468	if ((cd->cd_flags & IDE_CD_FLAG_DOOR_LOCKED) && ejectflag)
1469		return 0;
1470
1471	ide_cd_init_rq(drive, &req);
1472
1473	/* only tell drive to close tray if open, if it can do that */
1474	if (ejectflag && (cdi->mask & CDC_CLOSE_TRAY))
1475		loej = 0;
1476
1477	req.sense = sense;
1478	req.cmd[0] = GPCMD_START_STOP_UNIT;
1479	req.cmd[4] = loej | (ejectflag != 0);
1480
1481	return ide_cd_queue_pc(drive, &req);
1482}
1483
1484static int cdrom_read_capacity(ide_drive_t *drive, unsigned long *capacity,
1485			       unsigned long *sectors_per_frame,
1486			       struct request_sense *sense)
1487{
1488	struct {
1489		__u32 lba;
1490		__u32 blocklen;
1491	} capbuf;
1492
1493	int stat;
1494	struct request req;
1495
1496	ide_cd_init_rq(drive, &req);
1497
1498	req.sense = sense;
1499	req.cmd[0] = GPCMD_READ_CDVD_CAPACITY;
1500	req.data = (char *)&capbuf;
1501	req.data_len = sizeof(capbuf);
1502	req.cmd_flags |= REQ_QUIET;
1503
1504	stat = ide_cd_queue_pc(drive, &req);
1505	if (stat == 0) {
1506		*capacity = 1 + be32_to_cpu(capbuf.lba);
1507		*sectors_per_frame =
1508			be32_to_cpu(capbuf.blocklen) >> SECTOR_BITS;
1509	}
1510
1511	return stat;
1512}
1513
1514static int cdrom_read_tocentry(ide_drive_t *drive, int trackno, int msf_flag,
1515				int format, char *buf, int buflen,
1516				struct request_sense *sense)
1517{
1518	struct request req;
1519
1520	ide_cd_init_rq(drive, &req);
1521
1522	req.sense = sense;
1523	req.data =  buf;
1524	req.data_len = buflen;
1525	req.cmd_flags |= REQ_QUIET;
1526	req.cmd[0] = GPCMD_READ_TOC_PMA_ATIP;
1527	req.cmd[6] = trackno;
1528	req.cmd[7] = (buflen >> 8);
1529	req.cmd[8] = (buflen & 0xff);
1530	req.cmd[9] = (format << 6);
1531
1532	if (msf_flag)
1533		req.cmd[1] = 2;
1534
1535	return ide_cd_queue_pc(drive, &req);
1536}
1537
1538/* Try to read the entire TOC for the disk into our internal buffer. */
1539int ide_cd_read_toc(ide_drive_t *drive, struct request_sense *sense)
1540{
1541	int stat, ntracks, i;
1542	struct cdrom_info *info = drive->driver_data;
1543	struct cdrom_device_info *cdi = &info->devinfo;
1544	struct atapi_toc *toc = info->toc;
1545	struct {
1546		struct atapi_toc_header hdr;
1547		struct atapi_toc_entry  ent;
1548	} ms_tmp;
1549	long last_written;
1550	unsigned long sectors_per_frame = SECTORS_PER_FRAME;
1551
1552	if (toc == NULL) {
1553		/* Try to allocate space. */
1554		toc = kmalloc(sizeof(struct atapi_toc), GFP_KERNEL);
1555		if (toc == NULL) {
1556			printk (KERN_ERR "%s: No cdrom TOC buffer!\n", drive->name);
1557			return -ENOMEM;
1558		}
1559		info->toc = toc;
1560	}
1561
1562	/* Check to see if the existing data is still valid.
1563	   If it is, just return. */
1564	(void) cdrom_check_status(drive, sense);
1565
1566	if (info->cd_flags & IDE_CD_FLAG_TOC_VALID)
1567		return 0;
1568
1569	/* Try to get the total cdrom capacity and sector size. */
1570	stat = cdrom_read_capacity(drive, &toc->capacity, &sectors_per_frame,
1571				   sense);
1572	if (stat)
1573		toc->capacity = 0x1fffff;
1574
1575	set_capacity(info->disk, toc->capacity * sectors_per_frame);
1576	/* Save a private copy of te TOC capacity for error handling */
1577	drive->probed_capacity = toc->capacity * sectors_per_frame;
1578
1579	blk_queue_hardsect_size(drive->queue,
1580				sectors_per_frame << SECTOR_BITS);
1581
1582	/* First read just the header, so we know how long the TOC is. */
1583	stat = cdrom_read_tocentry(drive, 0, 1, 0, (char *) &toc->hdr,
1584				    sizeof(struct atapi_toc_header), sense);
1585	if (stat)
1586		return stat;
1587
1588	if (info->cd_flags & IDE_CD_FLAG_TOCTRACKS_AS_BCD) {
1589		toc->hdr.first_track = BCD2BIN(toc->hdr.first_track);
1590		toc->hdr.last_track  = BCD2BIN(toc->hdr.last_track);
1591	}
1592
1593	ntracks = toc->hdr.last_track - toc->hdr.first_track + 1;
1594	if (ntracks <= 0)
1595		return -EIO;
1596	if (ntracks > MAX_TRACKS)
1597		ntracks = MAX_TRACKS;
1598
1599	/* Now read the whole schmeer. */
1600	stat = cdrom_read_tocentry(drive, toc->hdr.first_track, 1, 0,
1601				  (char *)&toc->hdr,
1602				   sizeof(struct atapi_toc_header) +
1603				   (ntracks + 1) *
1604				   sizeof(struct atapi_toc_entry), sense);
1605
1606	if (stat && toc->hdr.first_track > 1) {
1607		/* Cds with CDI tracks only don't have any TOC entries,
1608		   despite of this the returned values are
1609		   first_track == last_track = number of CDI tracks + 1,
1610		   so that this case is indistinguishable from the same
1611		   layout plus an additional audio track.
1612		   If we get an error for the regular case, we assume
1613		   a CDI without additional audio tracks. In this case
1614		   the readable TOC is empty (CDI tracks are not included)
1615		   and only holds the Leadout entry. Heiko Eißfeldt */
1616		ntracks = 0;
1617		stat = cdrom_read_tocentry(drive, CDROM_LEADOUT, 1, 0,
1618					   (char *)&toc->hdr,
1619					   sizeof(struct atapi_toc_header) +
1620					   (ntracks + 1) *
1621					   sizeof(struct atapi_toc_entry),
1622					   sense);
1623		if (stat)
1624			return stat;
1625
1626		if (info->cd_flags & IDE_CD_FLAG_TOCTRACKS_AS_BCD) {
1627			toc->hdr.first_track = (u8)BIN2BCD(CDROM_LEADOUT);
1628			toc->hdr.last_track = (u8)BIN2BCD(CDROM_LEADOUT);
1629		} else {
1630			toc->hdr.first_track = CDROM_LEADOUT;
1631			toc->hdr.last_track = CDROM_LEADOUT;
1632		}
1633	}
1634
1635	if (stat)
1636		return stat;
1637
1638	toc->hdr.toc_length = ntohs (toc->hdr.toc_length);
1639
1640	if (info->cd_flags & IDE_CD_FLAG_TOCTRACKS_AS_BCD) {
1641		toc->hdr.first_track = BCD2BIN(toc->hdr.first_track);
1642		toc->hdr.last_track  = BCD2BIN(toc->hdr.last_track);
1643	}
1644
1645	for (i = 0; i <= ntracks; i++) {
1646		if (info->cd_flags & IDE_CD_FLAG_TOCADDR_AS_BCD) {
1647			if (info->cd_flags & IDE_CD_FLAG_TOCTRACKS_AS_BCD)
1648				toc->ent[i].track = BCD2BIN(toc->ent[i].track);
1649			msf_from_bcd(&toc->ent[i].addr.msf);
1650		}
1651		toc->ent[i].addr.lba = msf_to_lba (toc->ent[i].addr.msf.minute,
1652						   toc->ent[i].addr.msf.second,
1653						   toc->ent[i].addr.msf.frame);
1654	}
1655
1656	/* Read the multisession information. */
1657	if (toc->hdr.first_track != CDROM_LEADOUT) {
1658		/* Read the multisession information. */
1659		stat = cdrom_read_tocentry(drive, 0, 0, 1, (char *)&ms_tmp,
1660					   sizeof(ms_tmp), sense);
1661		if (stat)
1662			return stat;
1663
1664		toc->last_session_lba = be32_to_cpu(ms_tmp.ent.addr.lba);
1665	} else {
1666		ms_tmp.hdr.first_track = ms_tmp.hdr.last_track = CDROM_LEADOUT;
1667		toc->last_session_lba = msf_to_lba(0, 2, 0); /* 0m 2s 0f */
1668	}
1669
1670	if (info->cd_flags & IDE_CD_FLAG_TOCADDR_AS_BCD) {
1671		/* Re-read multisession information using MSF format */
1672		stat = cdrom_read_tocentry(drive, 0, 1, 1, (char *)&ms_tmp,
1673					   sizeof(ms_tmp), sense);
1674		if (stat)
1675			return stat;
1676
1677		msf_from_bcd (&ms_tmp.ent.addr.msf);
1678		toc->last_session_lba = msf_to_lba(ms_tmp.ent.addr.msf.minute,
1679					  	   ms_tmp.ent.addr.msf.second,
1680						   ms_tmp.ent.addr.msf.frame);
1681	}
1682
1683	toc->xa_flag = (ms_tmp.hdr.first_track != ms_tmp.hdr.last_track);
1684
1685	/* Now try to get the total cdrom capacity. */
1686	stat = cdrom_get_last_written(cdi, &last_written);
1687	if (!stat && (last_written > toc->capacity)) {
1688		toc->capacity = last_written;
1689		set_capacity(info->disk, toc->capacity * sectors_per_frame);
1690		drive->probed_capacity = toc->capacity * sectors_per_frame;
1691	}
1692
1693	/* Remember that we've read this stuff. */
1694	info->cd_flags |= IDE_CD_FLAG_TOC_VALID;
1695
1696	return 0;
1697}
1698
1699/* the generic packet interface to cdrom.c */
1700static int ide_cdrom_packet(struct cdrom_device_info *cdi,
1701			    struct packet_command *cgc)
1702{
1703	struct request req;
1704	ide_drive_t *drive = cdi->handle;
1705
1706	if (cgc->timeout <= 0)
1707		cgc->timeout = ATAPI_WAIT_PC;
1708
1709	/* here we queue the commands from the uniform CD-ROM
1710	   layer. the packet must be complete, as we do not
1711	   touch it at all. */
1712	ide_cd_init_rq(drive, &req);
1713	memcpy(req.cmd, cgc->cmd, CDROM_PACKET_SIZE);
1714	if (cgc->sense)
1715		memset(cgc->sense, 0, sizeof(struct request_sense));
1716	req.data = cgc->buffer;
1717	req.data_len = cgc->buflen;
1718	req.timeout = cgc->timeout;
1719
1720	if (cgc->quiet)
1721		req.cmd_flags |= REQ_QUIET;
1722
1723	req.sense = cgc->sense;
1724	cgc->stat = ide_cd_queue_pc(drive, &req);
1725	if (!cgc->stat)
1726		cgc->buflen -= req.data_len;
1727	return cgc->stat;
1728}
1729
1730static
1731int ide_cdrom_tray_move (struct cdrom_device_info *cdi, int position)
1732{
1733	ide_drive_t *drive = cdi->handle;
1734	struct request_sense sense;
1735
1736	if (position) {
1737		int stat = ide_cd_lockdoor(drive, 0, &sense);
1738
1739		if (stat)
1740			return stat;
1741	}
1742
1743	return cdrom_eject(drive, !position, &sense);
1744}
1745
1746int ide_cdrom_get_capabilities(ide_drive_t *drive, u8 *buf)
1747{
1748	struct cdrom_info *info = drive->driver_data;
1749	struct cdrom_device_info *cdi = &info->devinfo;
1750	struct packet_command cgc;
1751	int stat, attempts = 3, size = ATAPI_CAPABILITIES_PAGE_SIZE;
1752
1753	if ((info->cd_flags & IDE_CD_FLAG_FULL_CAPS_PAGE) == 0)
1754		size -= ATAPI_CAPABILITIES_PAGE_PAD_SIZE;
1755
1756	init_cdrom_command(&cgc, buf, size, CGC_DATA_UNKNOWN);
1757	do { /* we seem to get stat=0x01,err=0x00 the first time (??) */
1758		stat = cdrom_mode_sense(cdi, &cgc, GPMODE_CAPABILITIES_PAGE, 0);
1759		if (!stat)
1760			break;
1761	} while (--attempts);
1762	return stat;
1763}
1764
1765void ide_cdrom_update_speed(ide_drive_t *drive, u8 *buf)
1766{
1767	struct cdrom_info *cd = drive->driver_data;
1768	u16 curspeed, maxspeed;
1769
1770	curspeed = *(u16 *)&buf[8 + 14];
1771	maxspeed = *(u16 *)&buf[8 +  8];
1772
1773	if (cd->cd_flags & IDE_CD_FLAG_LE_SPEED_FIELDS) {
1774		curspeed = le16_to_cpu(curspeed);
1775		maxspeed = le16_to_cpu(maxspeed);
1776	} else {
1777		curspeed = be16_to_cpu(curspeed);
1778		maxspeed = be16_to_cpu(maxspeed);
1779	}
1780
1781	cd->current_speed = (curspeed + (176/2)) / 176;
1782	cd->max_speed = (maxspeed + (176/2)) / 176;
1783}
1784
1785/*
1786 * add logic to try GET_EVENT command first to check for media and tray
1787 * status. this should be supported by newer cd-r/w and all DVD etc
1788 * drives
1789 */
1790static
1791int ide_cdrom_drive_status (struct cdrom_device_info *cdi, int slot_nr)
1792{
1793	ide_drive_t *drive = cdi->handle;
1794	struct media_event_desc med;
1795	struct request_sense sense;
1796	int stat;
1797
1798	if (slot_nr != CDSL_CURRENT)
1799		return -EINVAL;
1800
1801	stat = cdrom_check_status(drive, &sense);
1802	if (!stat || sense.sense_key == UNIT_ATTENTION)
1803		return CDS_DISC_OK;
1804
1805	if (!cdrom_get_media_event(cdi, &med)) {
1806		if (med.media_present)
1807			return CDS_DISC_OK;
1808		else if (med.door_open)
1809			return CDS_TRAY_OPEN;
1810		else
1811			return CDS_NO_DISC;
1812	}
1813
1814	if (sense.sense_key == NOT_READY && sense.asc == 0x04 && sense.ascq == 0x04)
1815		return CDS_DISC_OK;
1816
1817	/*
1818	 * If not using Mt Fuji extended media tray reports,
1819	 * just return TRAY_OPEN since ATAPI doesn't provide
1820	 * any other way to detect this...
1821	 */
1822	if (sense.sense_key == NOT_READY) {
1823		if (sense.asc == 0x3a && sense.ascq == 1)
1824			return CDS_NO_DISC;
1825		else
1826			return CDS_TRAY_OPEN;
1827	}
1828	return CDS_DRIVE_NOT_READY;
1829}
1830
1831/****************************************************************************
1832 * Other driver requests (open, close, check media change).
1833 */
1834
1835static
1836int ide_cdrom_check_media_change_real (struct cdrom_device_info *cdi,
1837				       int slot_nr)
1838{
1839	ide_drive_t *drive = cdi->handle;
1840	struct cdrom_info *cd = drive->driver_data;
1841	int retval;
1842
1843	if (slot_nr == CDSL_CURRENT) {
1844		(void) cdrom_check_status(drive, NULL);
1845		retval = (cd->cd_flags & IDE_CD_FLAG_MEDIA_CHANGED) ? 1 : 0;
1846		cd->cd_flags &= ~IDE_CD_FLAG_MEDIA_CHANGED;
1847		return retval;
1848	} else {
1849		return -EINVAL;
1850	}
1851}
1852
1853
1854static
1855int ide_cdrom_open_real (struct cdrom_device_info *cdi, int purpose)
1856{
1857	return 0;
1858}
1859
1860/*
1861 * Close down the device.  Invalidate all cached blocks.
1862 */
1863
1864static
1865void ide_cdrom_release_real (struct cdrom_device_info *cdi)
1866{
1867	ide_drive_t *drive = cdi->handle;
1868	struct cdrom_info *cd = drive->driver_data;
1869
1870	if (!cdi->use_count)
1871		cd->cd_flags &= ~IDE_CD_FLAG_TOC_VALID;
1872}
1873
1874#define IDE_CD_CAPABILITIES \
1875	(CDC_CLOSE_TRAY | CDC_OPEN_TRAY | CDC_LOCK | CDC_SELECT_SPEED | \
1876	 CDC_SELECT_DISC | CDC_MULTI_SESSION | CDC_MCN | CDC_MEDIA_CHANGED | \
1877	 CDC_PLAY_AUDIO | CDC_RESET | CDC_DRIVE_STATUS | CDC_CD_R | \
1878	 CDC_CD_RW | CDC_DVD | CDC_DVD_R | CDC_DVD_RAM | CDC_GENERIC_PACKET | \
1879	 CDC_MO_DRIVE | CDC_MRW | CDC_MRW_W | CDC_RAM)
1880
1881static struct cdrom_device_ops ide_cdrom_dops = {
1882	.open			= ide_cdrom_open_real,
1883	.release		= ide_cdrom_release_real,
1884	.drive_status		= ide_cdrom_drive_status,
1885	.media_changed		= ide_cdrom_check_media_change_real,
1886	.tray_move		= ide_cdrom_tray_move,
1887	.lock_door		= ide_cdrom_lock_door,
1888	.select_speed		= ide_cdrom_select_speed,
1889	.get_last_session	= ide_cdrom_get_last_session,
1890	.get_mcn		= ide_cdrom_get_mcn,
1891	.reset			= ide_cdrom_reset,
1892	.audio_ioctl		= ide_cdrom_audio_ioctl,
1893	.capability		= IDE_CD_CAPABILITIES,
1894	.generic_packet		= ide_cdrom_packet,
1895};
1896
1897static int ide_cdrom_register (ide_drive_t *drive, int nslots)
1898{
1899	struct cdrom_info *info = drive->driver_data;
1900	struct cdrom_device_info *devinfo = &info->devinfo;
1901
1902	devinfo->ops = &ide_cdrom_dops;
1903	devinfo->speed = info->current_speed;
1904	devinfo->capacity = nslots;
1905	devinfo->handle = drive;
1906	strcpy(devinfo->name, drive->name);
1907
1908	if (info->cd_flags & IDE_CD_FLAG_NO_SPEED_SELECT)
1909		devinfo->mask |= CDC_SELECT_SPEED;
1910
1911	devinfo->disk = info->disk;
1912	return register_cdrom(devinfo);
1913}
1914
1915static
1916int ide_cdrom_probe_capabilities (ide_drive_t *drive)
1917{
1918	struct cdrom_info *cd = drive->driver_data;
1919	struct cdrom_device_info *cdi = &cd->devinfo;
1920	u8 buf[ATAPI_CAPABILITIES_PAGE_SIZE];
1921	mechtype_t mechtype;
1922	int nslots = 1;
1923
1924	cdi->mask = (CDC_CD_R | CDC_CD_RW | CDC_DVD | CDC_DVD_R |
1925		     CDC_DVD_RAM | CDC_SELECT_DISC | CDC_PLAY_AUDIO |
1926		     CDC_MO_DRIVE | CDC_RAM);
1927
1928	if (drive->media == ide_optical) {
1929		cdi->mask &= ~(CDC_MO_DRIVE | CDC_RAM);
1930		printk(KERN_ERR "%s: ATAPI magneto-optical drive\n", drive->name);
1931		return nslots;
1932	}
1933
1934	if (cd->cd_flags & IDE_CD_FLAG_PRE_ATAPI12) {
1935		cd->cd_flags &= ~IDE_CD_FLAG_NO_EJECT;
1936		cdi->mask &= ~CDC_PLAY_AUDIO;
1937		return nslots;
1938	}
1939
1940	/*
1941	 * we have to cheat a little here. the packet will eventually
1942	 * be queued with ide_cdrom_packet(), which extracts the
1943	 * drive from cdi->handle. Since this device hasn't been
1944	 * registered with the Uniform layer yet, it can't do this.
1945	 * Same goes for cdi->ops.
1946	 */
1947	cdi->handle = drive;
1948	cdi->ops = &ide_cdrom_dops;
1949
1950	if (ide_cdrom_get_capabilities(drive, buf))
1951		return 0;
1952
1953	if ((buf[8 + 6] & 0x01) == 0)
1954		cd->cd_flags |= IDE_CD_FLAG_NO_DOORLOCK;
1955	if (buf[8 + 6] & 0x08)
1956		cd->cd_flags &= ~IDE_CD_FLAG_NO_EJECT;
1957	if (buf[8 + 3] & 0x01)
1958		cdi->mask &= ~CDC_CD_R;
1959	if (buf[8 + 3] & 0x02)
1960		cdi->mask &= ~(CDC_CD_RW | CDC_RAM);
1961	if (buf[8 + 2] & 0x38)
1962		cdi->mask &= ~CDC_DVD;
1963	if (buf[8 + 3] & 0x20)
1964		cdi->mask &= ~(CDC_DVD_RAM | CDC_RAM);
1965	if (buf[8 + 3] & 0x10)
1966		cdi->mask &= ~CDC_DVD_R;
1967	if ((buf[8 + 4] & 0x01) || (cd->cd_flags & IDE_CD_FLAG_PLAY_AUDIO_OK))
1968		cdi->mask &= ~CDC_PLAY_AUDIO;
1969
1970	mechtype = buf[8 + 6] >> 5;
1971	if (mechtype == mechtype_caddy || mechtype == mechtype_popup)
1972		cdi->mask |= CDC_CLOSE_TRAY;
1973
1974	if (cdi->sanyo_slot > 0) {
1975		cdi->mask &= ~CDC_SELECT_DISC;
1976		nslots = 3;
1977	} else if (mechtype == mechtype_individual_changer ||
1978		   mechtype == mechtype_cartridge_changer) {
1979		nslots = cdrom_number_of_slots(cdi);
1980		if (nslots > 1)
1981			cdi->mask &= ~CDC_SELECT_DISC;
1982	}
1983
1984	ide_cdrom_update_speed(drive, buf);
1985
1986	printk(KERN_INFO "%s: ATAPI", drive->name);
1987
1988	/* don't print speed if the drive reported 0 */
1989	if (cd->max_speed)
1990		printk(KERN_CONT " %dX", cd->max_speed);
1991
1992	printk(KERN_CONT " %s", (cdi->mask & CDC_DVD) ? "CD-ROM" : "DVD-ROM");
1993
1994	if ((cdi->mask & CDC_DVD_R) == 0 || (cdi->mask & CDC_DVD_RAM) == 0)
1995		printk(KERN_CONT " DVD%s%s",
1996				 (cdi->mask & CDC_DVD_R) ? "" : "-R",
1997				 (cdi->mask & CDC_DVD_RAM) ? "" : "-RAM");
1998
1999	if ((cdi->mask & CDC_CD_R) == 0 || (cdi->mask & CDC_CD_RW) == 0)
2000		printk(KERN_CONT " CD%s%s",
2001				 (cdi->mask & CDC_CD_R) ? "" : "-R",
2002				 (cdi->mask & CDC_CD_RW) ? "" : "/RW");
2003
2004	if ((cdi->mask & CDC_SELECT_DISC) == 0)
2005		printk(KERN_CONT " changer w/%d slots", nslots);
2006	else
2007		printk(KERN_CONT " drive");
2008
2009	printk(KERN_CONT ", %dkB Cache\n", be16_to_cpu(*(u16 *)&buf[8 + 12]));
2010
2011	return nslots;
2012}
2013
2014#ifdef CONFIG_IDE_PROC_FS
2015static void ide_cdrom_add_settings(ide_drive_t *drive)
2016{
2017	ide_add_setting(drive, "dsc_overlap", SETTING_RW, TYPE_BYTE, 0, 1, 1, 1, &drive->dsc_overlap, NULL);
2018}
2019#else
2020static inline void ide_cdrom_add_settings(ide_drive_t *drive) { ; }
2021#endif
2022
2023/*
2024 * standard prep_rq_fn that builds 10 byte cmds
2025 */
2026static int ide_cdrom_prep_fs(struct request_queue *q, struct request *rq)
2027{
2028	int hard_sect = queue_hardsect_size(q);
2029	long block = (long)rq->hard_sector / (hard_sect >> 9);
2030	unsigned long blocks = rq->hard_nr_sectors / (hard_sect >> 9);
2031
2032	memset(rq->cmd, 0, sizeof(rq->cmd));
2033
2034	if (rq_data_dir(rq) == READ)
2035		rq->cmd[0] = GPCMD_READ_10;
2036	else
2037		rq->cmd[0] = GPCMD_WRITE_10;
2038
2039	/*
2040	 * fill in lba
2041	 */
2042	rq->cmd[2] = (block >> 24) & 0xff;
2043	rq->cmd[3] = (block >> 16) & 0xff;
2044	rq->cmd[4] = (block >>  8) & 0xff;
2045	rq->cmd[5] = block & 0xff;
2046
2047	/*
2048	 * and transfer length
2049	 */
2050	rq->cmd[7] = (blocks >> 8) & 0xff;
2051	rq->cmd[8] = blocks & 0xff;
2052	rq->cmd_len = 10;
2053	return BLKPREP_OK;
2054}
2055
2056/*
2057 * Most of the SCSI commands are supported directly by ATAPI devices.
2058 * This transform handles the few exceptions.
2059 */
2060static int ide_cdrom_prep_pc(struct request *rq)
2061{
2062	u8 *c = rq->cmd;
2063
2064	/*
2065	 * Transform 6-byte read/write commands to the 10-byte version
2066	 */
2067	if (c[0] == READ_6 || c[0] == WRITE_6) {
2068		c[8] = c[4];
2069		c[5] = c[3];
2070		c[4] = c[2];
2071		c[3] = c[1] & 0x1f;
2072		c[2] = 0;
2073		c[1] &= 0xe0;
2074		c[0] += (READ_10 - READ_6);
2075		rq->cmd_len = 10;
2076		return BLKPREP_OK;
2077	}
2078
2079	/*
2080	 * it's silly to pretend we understand 6-byte sense commands, just
2081	 * reject with ILLEGAL_REQUEST and the caller should take the
2082	 * appropriate action
2083	 */
2084	if (c[0] == MODE_SENSE || c[0] == MODE_SELECT) {
2085		rq->errors = ILLEGAL_REQUEST;
2086		return BLKPREP_KILL;
2087	}
2088
2089	return BLKPREP_OK;
2090}
2091
2092static int ide_cdrom_prep_fn(struct request_queue *q, struct request *rq)
2093{
2094	if (blk_fs_request(rq))
2095		return ide_cdrom_prep_fs(q, rq);
2096	else if (blk_pc_request(rq))
2097		return ide_cdrom_prep_pc(rq);
2098
2099	return 0;
2100}
2101
2102struct cd_list_entry {
2103	const char	*id_model;
2104	const char	*id_firmware;
2105	unsigned int	cd_flags;
2106};
2107
2108static const struct cd_list_entry ide_cd_quirks_list[] = {
2109	/* Limit transfer size per interrupt. */
2110	{ "SAMSUNG CD-ROM SCR-2430", NULL,   IDE_CD_FLAG_LIMIT_NFRAMES	    },
2111	{ "SAMSUNG CD-ROM SCR-2432", NULL,   IDE_CD_FLAG_LIMIT_NFRAMES	    },
2112	/* SCR-3231 doesn't support the SET_CD_SPEED command. */
2113	{ "SAMSUNG CD-ROM SCR-3231", NULL,   IDE_CD_FLAG_NO_SPEED_SELECT    },
2114	/* Old NEC260 (not R) was released before ATAPI 1.2 spec. */
2115	{ "NEC CD-ROM DRIVE:260",    "1.01", IDE_CD_FLAG_TOCADDR_AS_BCD |
2116					     IDE_CD_FLAG_PRE_ATAPI12,	    },
2117	/* Vertos 300, some versions of this drive like to talk BCD. */
2118	{ "V003S0DS",		     NULL,   IDE_CD_FLAG_VERTOS_300_SSD,    },
2119	/* Vertos 600 ESD. */
2120	{ "V006E0DS",		     NULL,   IDE_CD_FLAG_VERTOS_600_ESD,    },
2121	/*
2122	 * Sanyo 3 CD changer uses a non-standard command for CD changing
2123	 * (by default standard ATAPI support for CD changers is used).
2124	 */
2125	{ "CD-ROM CDR-C3 G",	     NULL,   IDE_CD_FLAG_SANYO_3CD	    },
2126	{ "CD-ROM CDR-C3G",	     NULL,   IDE_CD_FLAG_SANYO_3CD	    },
2127	{ "CD-ROM CDR_C36",	     NULL,   IDE_CD_FLAG_SANYO_3CD	    },
2128	/* Stingray 8X CD-ROM. */
2129	{ "STINGRAY 8422 IDE 8X CD-ROM 7-27-95", NULL, IDE_CD_FLAG_PRE_ATAPI12},
2130	/*
2131	 * ACER 50X CD-ROM and WPI 32X CD-ROM require the full spec length
2132	 * mode sense page capabilities size, but older drives break.
2133	 */
2134	{ "ATAPI CD ROM DRIVE 50X MAX",	NULL,	IDE_CD_FLAG_FULL_CAPS_PAGE  },
2135	{ "WPI CDS-32X",		NULL,	IDE_CD_FLAG_FULL_CAPS_PAGE  },
2136	/* ACER/AOpen 24X CD-ROM has the speed fields byte-swapped. */
2137	{ "",			     "241N", IDE_CD_FLAG_LE_SPEED_FIELDS    },
2138	/*
2139	 * Some drives used by Apple don't advertise audio play
2140	 * but they do support reading TOC & audio datas.
2141	 */
2142	{ "MATSHITADVD-ROM SR-8187", NULL,   IDE_CD_FLAG_PLAY_AUDIO_OK	    },
2143	{ "MATSHITADVD-ROM SR-8186", NULL,   IDE_CD_FLAG_PLAY_AUDIO_OK	    },
2144	{ "MATSHITADVD-ROM SR-8176", NULL,   IDE_CD_FLAG_PLAY_AUDIO_OK	    },
2145	{ "MATSHITADVD-ROM SR-8174", NULL,   IDE_CD_FLAG_PLAY_AUDIO_OK	    },
2146	{ NULL, NULL, 0 }
2147};
2148
2149static unsigned int ide_cd_flags(struct hd_driveid *id)
2150{
2151	const struct cd_list_entry *cle = ide_cd_quirks_list;
2152
2153	while (cle->id_model) {
2154		if (strcmp(cle->id_model, id->model) == 0 &&
2155		    (cle->id_firmware == NULL ||
2156		     strstr(id->fw_rev, cle->id_firmware)))
2157			return cle->cd_flags;
2158		cle++;
2159	}
2160
2161	return 0;
2162}
2163
2164static
2165int ide_cdrom_setup (ide_drive_t *drive)
2166{
2167	struct cdrom_info *cd = drive->driver_data;
2168	struct cdrom_device_info *cdi = &cd->devinfo;
2169	struct hd_driveid *id = drive->id;
2170	int nslots;
2171
2172	blk_queue_prep_rq(drive->queue, ide_cdrom_prep_fn);
2173	blk_queue_dma_alignment(drive->queue, 31);
2174	drive->queue->unplug_delay = (1 * HZ) / 1000;
2175	if (!drive->queue->unplug_delay)
2176		drive->queue->unplug_delay = 1;
2177
2178	drive->special.all	= 0;
2179
2180	cd->cd_flags = IDE_CD_FLAG_MEDIA_CHANGED | IDE_CD_FLAG_NO_EJECT |
2181		       ide_cd_flags(id);
2182
2183	if ((id->config & 0x0060) == 0x20)
2184		cd->cd_flags |= IDE_CD_FLAG_DRQ_INTERRUPT;
2185
2186	if ((cd->cd_flags & IDE_CD_FLAG_VERTOS_300_SSD) &&
2187	    id->fw_rev[4] == '1' && id->fw_rev[6] <= '2')
2188		cd->cd_flags |= (IDE_CD_FLAG_TOCTRACKS_AS_BCD |
2189				 IDE_CD_FLAG_TOCADDR_AS_BCD);
2190	else if ((cd->cd_flags & IDE_CD_FLAG_VERTOS_600_ESD) &&
2191		 id->fw_rev[4] == '1' && id->fw_rev[6] <= '2')
2192		cd->cd_flags |= IDE_CD_FLAG_TOCTRACKS_AS_BCD;
2193	else if (cd->cd_flags & IDE_CD_FLAG_SANYO_3CD)
2194		cdi->sanyo_slot = 3;	/* 3 => use CD in slot 0 */
2195
2196	nslots = ide_cdrom_probe_capabilities (drive);
2197
2198	/*
2199	 * set correct block size
2200	 */
2201	blk_queue_hardsect_size(drive->queue, CD_FRAMESIZE);
2202
2203	if (drive->autotune == IDE_TUNE_DEFAULT ||
2204	    drive->autotune == IDE_TUNE_AUTO)
2205		drive->dsc_overlap = (drive->next != drive);
2206
2207	if (ide_cdrom_register(drive, nslots)) {
2208		printk (KERN_ERR "%s: ide_cdrom_setup failed to register device with the cdrom driver.\n", drive->name);
2209		cd->devinfo.handle = NULL;
2210		return 1;
2211	}
2212	ide_cdrom_add_settings(drive);
2213	return 0;
2214}
2215
2216#ifdef CONFIG_IDE_PROC_FS
2217static
2218sector_t ide_cdrom_capacity (ide_drive_t *drive)
2219{
2220	unsigned long capacity, sectors_per_frame;
2221
2222	if (cdrom_read_capacity(drive, &capacity, &sectors_per_frame, NULL))
2223		return 0;
2224
2225	return capacity * sectors_per_frame;
2226}
2227#endif
2228
2229static void ide_cd_remove(ide_drive_t *drive)
2230{
2231	struct cdrom_info *info = drive->driver_data;
2232
2233	ide_proc_unregister_driver(drive, info->driver);
2234
2235	del_gendisk(info->disk);
2236
2237	ide_cd_put(info);
2238}
2239
2240static void ide_cd_release(struct kref *kref)
2241{
2242	struct cdrom_info *info = to_ide_cd(kref);
2243	struct cdrom_device_info *devinfo = &info->devinfo;
2244	ide_drive_t *drive = info->drive;
2245	struct gendisk *g = info->disk;
2246
2247	kfree(info->buffer);
2248	kfree(info->toc);
2249	if (devinfo->handle == drive && unregister_cdrom(devinfo))
2250		printk(KERN_ERR "%s: %s failed to unregister device from the cdrom "
2251				"driver.\n", __FUNCTION__, drive->name);
2252	drive->dsc_overlap = 0;
2253	drive->driver_data = NULL;
2254	blk_queue_prep_rq(drive->queue, NULL);
2255	g->private_data = NULL;
2256	put_disk(g);
2257	kfree(info);
2258}
2259
2260static int ide_cd_probe(ide_drive_t *);
2261
2262#ifdef CONFIG_IDE_PROC_FS
2263static int proc_idecd_read_capacity
2264	(char *page, char **start, off_t off, int count, int *eof, void *data)
2265{
2266	ide_drive_t *drive = data;
2267	int len;
2268
2269	len = sprintf(page,"%llu\n", (long long)ide_cdrom_capacity(drive));
2270	PROC_IDE_READ_RETURN(page,start,off,count,eof,len);
2271}
2272
2273static ide_proc_entry_t idecd_proc[] = {
2274	{ "capacity", S_IFREG|S_IRUGO, proc_idecd_read_capacity, NULL },
2275	{ NULL, 0, NULL, NULL }
2276};
2277#endif
2278
2279static ide_driver_t ide_cdrom_driver = {
2280	.gen_driver = {
2281		.owner		= THIS_MODULE,
2282		.name		= "ide-cdrom",
2283		.bus		= &ide_bus_type,
2284	},
2285	.probe			= ide_cd_probe,
2286	.remove			= ide_cd_remove,
2287	.version		= IDECD_VERSION,
2288	.media			= ide_cdrom,
2289	.supports_dsc_overlap	= 1,
2290	.do_request		= ide_do_rw_cdrom,
2291	.end_request		= ide_end_request,
2292	.error			= __ide_error,
2293	.abort			= __ide_abort,
2294#ifdef CONFIG_IDE_PROC_FS
2295	.proc			= idecd_proc,
2296#endif
2297};
2298
2299static int idecd_open(struct inode * inode, struct file * file)
2300{
2301	struct gendisk *disk = inode->i_bdev->bd_disk;
2302	struct cdrom_info *info;
2303	int rc = -ENOMEM;
2304
2305	if (!(info = ide_cd_get(disk)))
2306		return -ENXIO;
2307
2308	if (!info->buffer)
2309		info->buffer = kmalloc(SECTOR_BUFFER_SIZE, GFP_KERNEL|__GFP_REPEAT);
2310
2311	if (info->buffer)
2312		rc = cdrom_open(&info->devinfo, inode, file);
2313
2314	if (rc < 0)
2315		ide_cd_put(info);
2316
2317	return rc;
2318}
2319
2320static int idecd_release(struct inode * inode, struct file * file)
2321{
2322	struct gendisk *disk = inode->i_bdev->bd_disk;
2323	struct cdrom_info *info = ide_cd_g(disk);
2324
2325	cdrom_release (&info->devinfo, file);
2326
2327	ide_cd_put(info);
2328
2329	return 0;
2330}
2331
2332static int idecd_set_spindown(struct cdrom_device_info *cdi, unsigned long arg)
2333{
2334	struct packet_command cgc;
2335	char buffer[16];
2336	int stat;
2337	char spindown;
2338
2339	if (copy_from_user(&spindown, (void __user *)arg, sizeof(char)))
2340		return -EFAULT;
2341
2342	init_cdrom_command(&cgc, buffer, sizeof(buffer), CGC_DATA_UNKNOWN);
2343
2344	stat = cdrom_mode_sense(cdi, &cgc, GPMODE_CDROM_PAGE, 0);
2345	if (stat)
2346		return stat;
2347
2348	buffer[11] = (buffer[11] & 0xf0) | (spindown & 0x0f);
2349	return cdrom_mode_select(cdi, &cgc);
2350}
2351
2352static int idecd_get_spindown(struct cdrom_device_info *cdi, unsigned long arg)
2353{
2354	struct packet_command cgc;
2355	char buffer[16];
2356	int stat;
2357 	char spindown;
2358
2359	init_cdrom_command(&cgc, buffer, sizeof(buffer), CGC_DATA_UNKNOWN);
2360
2361	stat = cdrom_mode_sense(cdi, &cgc, GPMODE_CDROM_PAGE, 0);
2362	if (stat)
2363		return stat;
2364
2365	spindown = buffer[11] & 0x0f;
2366	if (copy_to_user((void __user *)arg, &spindown, sizeof (char)))
2367		return -EFAULT;
2368	return 0;
2369}
2370
2371static int idecd_ioctl (struct inode *inode, struct file *file,
2372			unsigned int cmd, unsigned long arg)
2373{
2374	struct block_device *bdev = inode->i_bdev;
2375	struct cdrom_info *info = ide_cd_g(bdev->bd_disk);
2376	int err;
2377
2378	switch (cmd) {
2379 	case CDROMSETSPINDOWN:
2380		return idecd_set_spindown(&info->devinfo, arg);
2381 	case CDROMGETSPINDOWN:
2382		return idecd_get_spindown(&info->devinfo, arg);
2383	default:
2384		break;
2385 	}
2386
2387	err = generic_ide_ioctl(info->drive, file, bdev, cmd, arg);
2388	if (err == -EINVAL)
2389		err = cdrom_ioctl(file, &info->devinfo, inode, cmd, arg);
2390
2391	return err;
2392}
2393
2394static int idecd_media_changed(struct gendisk *disk)
2395{
2396	struct cdrom_info *info = ide_cd_g(disk);
2397	return cdrom_media_changed(&info->devinfo);
2398}
2399
2400static int idecd_revalidate_disk(struct gendisk *disk)
2401{
2402	struct cdrom_info *info = ide_cd_g(disk);
2403	struct request_sense sense;
2404
2405	ide_cd_read_toc(info->drive, &sense);
2406
2407	return  0;
2408}
2409
2410static struct block_device_operations idecd_ops = {
2411	.owner		= THIS_MODULE,
2412	.open		= idecd_open,
2413	.release	= idecd_release,
2414	.ioctl		= idecd_ioctl,
2415	.media_changed	= idecd_media_changed,
2416	.revalidate_disk= idecd_revalidate_disk
2417};
2418
2419/* options */
2420static char *ignore = NULL;
2421
2422module_param(ignore, charp, 0400);
2423MODULE_DESCRIPTION("ATAPI CD-ROM Driver");
2424
2425static int ide_cd_probe(ide_drive_t *drive)
2426{
2427	struct cdrom_info *info;
2428	struct gendisk *g;
2429	struct request_sense sense;
2430
2431	if (!strstr("ide-cdrom", drive->driver_req))
2432		goto failed;
2433	if (!drive->present)
2434		goto failed;
2435	if (drive->media != ide_cdrom && drive->media != ide_optical)
2436		goto failed;
2437	/* skip drives that we were told to ignore */
2438	if (ignore != NULL) {
2439		if (strstr(ignore, drive->name)) {
2440			printk(KERN_INFO "ide-cd: ignoring drive %s\n", drive->name);
2441			goto failed;
2442		}
2443	}
2444	if (drive->scsi) {
2445		printk(KERN_INFO "ide-cd: passing drive %s to ide-scsi emulation.\n", drive->name);
2446		goto failed;
2447	}
2448	info = kzalloc(sizeof(struct cdrom_info), GFP_KERNEL);
2449	if (info == NULL) {
2450		printk(KERN_ERR "%s: Can't allocate a cdrom structure\n", drive->name);
2451		goto failed;
2452	}
2453
2454	g = alloc_disk(1 << PARTN_BITS);
2455	if (!g)
2456		goto out_free_cd;
2457
2458	ide_init_disk(g, drive);
2459
2460	ide_proc_register_driver(drive, &ide_cdrom_driver);
2461
2462	kref_init(&info->kref);
2463
2464	info->drive = drive;
2465	info->driver = &ide_cdrom_driver;
2466	info->disk = g;
2467
2468	g->private_data = &info->driver;
2469
2470	drive->driver_data = info;
2471
2472	g->minors = 1;
2473	g->driverfs_dev = &drive->gendev;
2474	g->flags = GENHD_FL_CD | GENHD_FL_REMOVABLE;
2475	if (ide_cdrom_setup(drive)) {
2476		ide_proc_unregister_driver(drive, &ide_cdrom_driver);
2477		ide_cd_release(&info->kref);
2478		goto failed;
2479	}
2480
2481	ide_cd_read_toc(drive, &sense);
2482	g->fops = &idecd_ops;
2483	g->flags |= GENHD_FL_REMOVABLE;
2484	add_disk(g);
2485	return 0;
2486
2487out_free_cd:
2488	kfree(info);
2489failed:
2490	return -ENODEV;
2491}
2492
2493static void __exit ide_cdrom_exit(void)
2494{
2495	driver_unregister(&ide_cdrom_driver.gen_driver);
2496}
2497
2498static int __init ide_cdrom_init(void)
2499{
2500	return driver_register(&ide_cdrom_driver.gen_driver);
2501}
2502
2503MODULE_ALIAS("ide:*m-cdrom*");
2504MODULE_ALIAS("ide-cd");
2505module_init(ide_cdrom_init);
2506module_exit(ide_cdrom_exit);
2507MODULE_LICENSE("GPL");
2508