1/*
2   SCSI Tape Driver for Linux version 1.1 and newer. See the accompanying
3   file Documentation/scsi/st.txt for more information.
4
5   History:
6   Rewritten from Dwayne Forsyth's SCSI tape driver by Kai Makisara.
7   Contribution and ideas from several people including (in alphabetical
8   order) Klaus Ehrenfried, Eugene Exarevsky, Eric Lee Green, Wolfgang Denk,
9   Steve Hirsch, Andreas Koppenh"ofer, Michael Leodolter, Eyal Lebedinsky,
10   Michael Schaefer, J"org Weule, and Eric Youngdale.
11
12   Copyright 1992 - 2010 Kai Makisara
13   email Kai.Makisara@kolumbus.fi
14
15   Some small formal changes - aeb, 950809
16
17   Last modified: 18-JAN-1998 Richard Gooch <rgooch@atnf.csiro.au> Devfs support
18 */
19
20static const char *verstr = "20101219";
21
22#include <linux/module.h>
23
24#include <linux/fs.h>
25#include <linux/kernel.h>
26#include <linux/sched.h>
27#include <linux/mm.h>
28#include <linux/init.h>
29#include <linux/string.h>
30#include <linux/slab.h>
31#include <linux/errno.h>
32#include <linux/mtio.h>
33#include <linux/cdrom.h>
34#include <linux/ioctl.h>
35#include <linux/fcntl.h>
36#include <linux/spinlock.h>
37#include <linux/blkdev.h>
38#include <linux/moduleparam.h>
39#include <linux/cdev.h>
40#include <linux/idr.h>
41#include <linux/delay.h>
42#include <linux/mutex.h>
43
44#include <asm/uaccess.h>
45#include <asm/dma.h>
46
47#include <scsi/scsi.h>
48#include <scsi/scsi_dbg.h>
49#include <scsi/scsi_device.h>
50#include <scsi/scsi_driver.h>
51#include <scsi/scsi_eh.h>
52#include <scsi/scsi_host.h>
53#include <scsi/scsi_ioctl.h>
54#include <scsi/sg.h>
55
56
57/* The driver prints some debugging information on the console if DEBUG
58   is defined and non-zero. */
59#define DEBUG 1
60#define NO_DEBUG 0
61
62#define ST_DEB_MSG  KERN_NOTICE
63#if DEBUG
64/* The message level for the debug messages is currently set to KERN_NOTICE
65   so that people can easily see the messages. Later when the debugging messages
66   in the drivers are more widely classified, this may be changed to KERN_DEBUG. */
67#define DEB(a) a
68#define DEBC(a) if (debugging) { a ; }
69#else
70#define DEB(a)
71#define DEBC(a)
72#endif
73
74#define ST_KILOBYTE 1024
75
76#include "st_options.h"
77#include "st.h"
78
79static int buffer_kbs;
80static int max_sg_segs;
81static int try_direct_io = TRY_DIRECT_IO;
82static int try_rdio = 1;
83static int try_wdio = 1;
84static int debug_flag;
85
86static struct class st_sysfs_class;
87static const struct attribute_group *st_dev_groups[];
88
89MODULE_AUTHOR("Kai Makisara");
90MODULE_DESCRIPTION("SCSI tape (st) driver");
91MODULE_LICENSE("GPL");
92MODULE_ALIAS_CHARDEV_MAJOR(SCSI_TAPE_MAJOR);
93MODULE_ALIAS_SCSI_DEVICE(TYPE_TAPE);
94
95/* Set 'perm' (4th argument) to 0 to disable module_param's definition
96 * of sysfs parameters (which module_param doesn't yet support).
97 * Sysfs parameters defined explicitly later.
98 */
99module_param_named(buffer_kbs, buffer_kbs, int, 0);
100MODULE_PARM_DESC(buffer_kbs, "Default driver buffer size for fixed block mode (KB; 32)");
101module_param_named(max_sg_segs, max_sg_segs, int, 0);
102MODULE_PARM_DESC(max_sg_segs, "Maximum number of scatter/gather segments to use (256)");
103module_param_named(try_direct_io, try_direct_io, int, 0);
104MODULE_PARM_DESC(try_direct_io, "Try direct I/O between user buffer and tape drive (1)");
105module_param_named(debug_flag, debug_flag, int, 0);
106MODULE_PARM_DESC(debug_flag, "Enable DEBUG, same as setting debugging=1");
107
108
109/* Extra parameters for testing */
110module_param_named(try_rdio, try_rdio, int, 0);
111MODULE_PARM_DESC(try_rdio, "Try direct read i/o when possible");
112module_param_named(try_wdio, try_wdio, int, 0);
113MODULE_PARM_DESC(try_wdio, "Try direct write i/o when possible");
114
115#ifndef MODULE
116static int write_threshold_kbs;  /* retained for compatibility */
117static struct st_dev_parm {
118	char *name;
119	int *val;
120} parms[] __initdata = {
121	{
122		"buffer_kbs", &buffer_kbs
123	},
124	{       /* Retained for compatibility with 2.4 */
125		"write_threshold_kbs", &write_threshold_kbs
126	},
127	{
128		"max_sg_segs", NULL
129	},
130	{
131		"try_direct_io", &try_direct_io
132	},
133	{
134		"debug_flag", &debug_flag
135	}
136};
137#endif
138
139/* Restrict the number of modes so that names for all are assigned */
140#if ST_NBR_MODES > 16
141#error "Maximum number of modes is 16"
142#endif
143/* Bit reversed order to get same names for same minors with all
144   mode counts */
145static const char *st_formats[] = {
146	"",  "r", "k", "s", "l", "t", "o", "u",
147	"m", "v", "p", "x", "a", "y", "q", "z"};
148
149/* The default definitions have been moved to st_options.h */
150
151#define ST_FIXED_BUFFER_SIZE (ST_FIXED_BUFFER_BLOCKS * ST_KILOBYTE)
152
153/* The buffer size should fit into the 24 bits for length in the
154   6-byte SCSI read and write commands. */
155#if ST_FIXED_BUFFER_SIZE >= (2 << 24 - 1)
156#error "Buffer size should not exceed (2 << 24 - 1) bytes!"
157#endif
158
159static int debugging = DEBUG;
160
161#define MAX_RETRIES 0
162#define MAX_WRITE_RETRIES 0
163#define MAX_READY_RETRIES 0
164#define NO_TAPE  NOT_READY
165
166#define ST_TIMEOUT (900 * HZ)
167#define ST_LONG_TIMEOUT (14000 * HZ)
168
169/* Remove mode bits and auto-rewind bit (7) */
170#define TAPE_NR(x) ( ((iminor(x) & ~255) >> (ST_NBR_MODE_BITS + 1)) | \
171    (iminor(x) & ~(-1 << ST_MODE_SHIFT)) )
172#define TAPE_MODE(x) ((iminor(x) & ST_MODE_MASK) >> ST_MODE_SHIFT)
173
174/* Construct the minor number from the device (d), mode (m), and non-rewind (n) data */
175#define TAPE_MINOR(d, m, n) (((d & ~(255 >> (ST_NBR_MODE_BITS + 1))) << (ST_NBR_MODE_BITS + 1)) | \
176  (d & (255 >> (ST_NBR_MODE_BITS + 1))) | (m << ST_MODE_SHIFT) | ((n != 0) << 7) )
177
178/* Internal ioctl to set both density (uppermost 8 bits) and blocksize (lower
179   24 bits) */
180#define SET_DENS_AND_BLK 0x10001
181
182static int st_fixed_buffer_size = ST_FIXED_BUFFER_SIZE;
183static int st_max_sg_segs = ST_MAX_SG;
184
185static int modes_defined;
186
187static int enlarge_buffer(struct st_buffer *, int, int);
188static void clear_buffer(struct st_buffer *);
189static void normalize_buffer(struct st_buffer *);
190static int append_to_buffer(const char __user *, struct st_buffer *, int);
191static int from_buffer(struct st_buffer *, char __user *, int);
192static void move_buffer_data(struct st_buffer *, int);
193
194static int sgl_map_user_pages(struct st_buffer *, const unsigned int,
195			      unsigned long, size_t, int);
196static int sgl_unmap_user_pages(struct st_buffer *, const unsigned int, int);
197
198static int st_probe(struct device *);
199static int st_remove(struct device *);
200
201static int do_create_sysfs_files(void);
202static void do_remove_sysfs_files(void);
203
204static struct scsi_driver st_template = {
205	.gendrv = {
206		.name		= "st",
207		.owner		= THIS_MODULE,
208		.probe		= st_probe,
209		.remove		= st_remove,
210	},
211};
212
213static int st_compression(struct scsi_tape *, int);
214
215static int find_partition(struct scsi_tape *);
216static int switch_partition(struct scsi_tape *);
217
218static int st_int_ioctl(struct scsi_tape *, unsigned int, unsigned long);
219
220static void scsi_tape_release(struct kref *);
221
222#define to_scsi_tape(obj) container_of(obj, struct scsi_tape, kref)
223
224static DEFINE_MUTEX(st_ref_mutex);
225static DEFINE_SPINLOCK(st_index_lock);
226static DEFINE_SPINLOCK(st_use_lock);
227static DEFINE_IDR(st_index_idr);
228
229
230
231#include "osst_detect.h"
232#ifndef SIGS_FROM_OSST
233#define SIGS_FROM_OSST \
234	{"OnStream", "SC-", "", "osst"}, \
235	{"OnStream", "DI-", "", "osst"}, \
236	{"OnStream", "DP-", "", "osst"}, \
237	{"OnStream", "USB", "", "osst"}, \
238	{"OnStream", "FW-", "", "osst"}
239#endif
240
241static struct scsi_tape *scsi_tape_get(int dev)
242{
243	struct scsi_tape *STp = NULL;
244
245	mutex_lock(&st_ref_mutex);
246	spin_lock(&st_index_lock);
247
248	STp = idr_find(&st_index_idr, dev);
249	if (!STp) goto out;
250
251	kref_get(&STp->kref);
252
253	if (!STp->device)
254		goto out_put;
255
256	if (scsi_device_get(STp->device))
257		goto out_put;
258
259	goto out;
260
261out_put:
262	kref_put(&STp->kref, scsi_tape_release);
263	STp = NULL;
264out:
265	spin_unlock(&st_index_lock);
266	mutex_unlock(&st_ref_mutex);
267	return STp;
268}
269
270static void scsi_tape_put(struct scsi_tape *STp)
271{
272	struct scsi_device *sdev = STp->device;
273
274	mutex_lock(&st_ref_mutex);
275	kref_put(&STp->kref, scsi_tape_release);
276	scsi_device_put(sdev);
277	mutex_unlock(&st_ref_mutex);
278}
279
280struct st_reject_data {
281	char *vendor;
282	char *model;
283	char *rev;
284	char *driver_hint; /* Name of the correct driver, NULL if unknown */
285};
286
287static struct st_reject_data reject_list[] = {
288	/* {"XXX", "Yy-", "", NULL},  example */
289	SIGS_FROM_OSST,
290	{NULL, }};
291
292/* If the device signature is on the list of incompatible drives, the
293   function returns a pointer to the name of the correct driver (if known) */
294static char * st_incompatible(struct scsi_device* SDp)
295{
296	struct st_reject_data *rp;
297
298	for (rp=&(reject_list[0]); rp->vendor != NULL; rp++)
299		if (!strncmp(rp->vendor, SDp->vendor, strlen(rp->vendor)) &&
300		    !strncmp(rp->model, SDp->model, strlen(rp->model)) &&
301		    !strncmp(rp->rev, SDp->rev, strlen(rp->rev))) {
302			if (rp->driver_hint)
303				return rp->driver_hint;
304			else
305				return "unknown";
306		}
307	return NULL;
308}
309
310
311static inline char *tape_name(struct scsi_tape *tape)
312{
313	return tape->disk->disk_name;
314}
315
316#define st_printk(prefix, t, fmt, a...) \
317	sdev_prefix_printk(prefix, (t)->device, tape_name(t), fmt, ##a)
318#ifdef DEBUG
319#define DEBC_printk(t, fmt, a...) \
320	if (debugging) { st_printk(ST_DEB_MSG, t, fmt, ##a ); }
321#else
322#define DEBC_printk(t, fmt, a...)
323#endif
324
325static void st_analyze_sense(struct st_request *SRpnt, struct st_cmdstatus *s)
326{
327	const u8 *ucp;
328	const u8 *sense = SRpnt->sense;
329
330	s->have_sense = scsi_normalize_sense(SRpnt->sense,
331				SCSI_SENSE_BUFFERSIZE, &s->sense_hdr);
332	s->flags = 0;
333
334	if (s->have_sense) {
335		s->deferred = 0;
336		s->remainder_valid =
337			scsi_get_sense_info_fld(sense, SCSI_SENSE_BUFFERSIZE, &s->uremainder64);
338		switch (sense[0] & 0x7f) {
339		case 0x71:
340			s->deferred = 1;
341		case 0x70:
342			s->fixed_format = 1;
343			s->flags = sense[2] & 0xe0;
344			break;
345		case 0x73:
346			s->deferred = 1;
347		case 0x72:
348			s->fixed_format = 0;
349			ucp = scsi_sense_desc_find(sense, SCSI_SENSE_BUFFERSIZE, 4);
350			s->flags = ucp ? (ucp[3] & 0xe0) : 0;
351			break;
352		}
353	}
354}
355
356
357/* Convert the result to success code */
358static int st_chk_result(struct scsi_tape *STp, struct st_request * SRpnt)
359{
360	int result = SRpnt->result;
361	u8 scode;
362	DEB(const char *stp;)
363	char *name = tape_name(STp);
364	struct st_cmdstatus *cmdstatp;
365
366	if (!result)
367		return 0;
368
369	cmdstatp = &STp->buffer->cmdstat;
370	st_analyze_sense(SRpnt, cmdstatp);
371
372	if (cmdstatp->have_sense)
373		scode = STp->buffer->cmdstat.sense_hdr.sense_key;
374	else
375		scode = 0;
376
377	DEB(
378	if (debugging) {
379		st_printk(ST_DEB_MSG, STp,
380			    "Error: %x, cmd: %x %x %x %x %x %x\n", result,
381			    SRpnt->cmd[0], SRpnt->cmd[1], SRpnt->cmd[2],
382			    SRpnt->cmd[3], SRpnt->cmd[4], SRpnt->cmd[5]);
383		if (cmdstatp->have_sense)
384			__scsi_print_sense(STp->device, name,
385					   SRpnt->sense, SCSI_SENSE_BUFFERSIZE);
386	} ) /* end DEB */
387	if (!debugging) { /* Abnormal conditions for tape */
388		if (!cmdstatp->have_sense)
389			st_printk(KERN_WARNING, STp,
390			       "Error %x (driver bt 0x%x, host bt 0x%x).\n",
391			       result, driver_byte(result), host_byte(result));
392		else if (cmdstatp->have_sense &&
393			 scode != NO_SENSE &&
394			 scode != RECOVERED_ERROR &&
395			 /* scode != UNIT_ATTENTION && */
396			 scode != BLANK_CHECK &&
397			 scode != VOLUME_OVERFLOW &&
398			 SRpnt->cmd[0] != MODE_SENSE &&
399			 SRpnt->cmd[0] != TEST_UNIT_READY) {
400
401			__scsi_print_sense(STp->device, name,
402					   SRpnt->sense, SCSI_SENSE_BUFFERSIZE);
403		}
404	}
405
406	if (cmdstatp->fixed_format &&
407	    STp->cln_mode >= EXTENDED_SENSE_START) {  /* Only fixed format sense */
408		if (STp->cln_sense_value)
409			STp->cleaning_req |= ((SRpnt->sense[STp->cln_mode] &
410					       STp->cln_sense_mask) == STp->cln_sense_value);
411		else
412			STp->cleaning_req |= ((SRpnt->sense[STp->cln_mode] &
413					       STp->cln_sense_mask) != 0);
414	}
415	if (cmdstatp->have_sense &&
416	    cmdstatp->sense_hdr.asc == 0 && cmdstatp->sense_hdr.ascq == 0x17)
417		STp->cleaning_req = 1; /* ASC and ASCQ => cleaning requested */
418
419	STp->pos_unknown |= STp->device->was_reset;
420
421	if (cmdstatp->have_sense &&
422	    scode == RECOVERED_ERROR
423#if ST_RECOVERED_WRITE_FATAL
424	    && SRpnt->cmd[0] != WRITE_6
425	    && SRpnt->cmd[0] != WRITE_FILEMARKS
426#endif
427	    ) {
428		STp->recover_count++;
429		STp->recover_reg++;
430
431		DEB(
432		if (debugging) {
433			if (SRpnt->cmd[0] == READ_6)
434				stp = "read";
435			else if (SRpnt->cmd[0] == WRITE_6)
436				stp = "write";
437			else
438				stp = "ioctl";
439			st_printk(ST_DEB_MSG, STp,
440				  "Recovered %s error (%d).\n",
441				  stp, STp->recover_count);
442		} ) /* end DEB */
443
444		if (cmdstatp->flags == 0)
445			return 0;
446	}
447	return (-EIO);
448}
449
450static struct st_request *st_allocate_request(struct scsi_tape *stp)
451{
452	struct st_request *streq;
453
454	streq = kzalloc(sizeof(*streq), GFP_KERNEL);
455	if (streq)
456		streq->stp = stp;
457	else {
458		st_printk(KERN_ERR, stp,
459			  "Can't get SCSI request.\n");
460		if (signal_pending(current))
461			stp->buffer->syscall_result = -EINTR;
462		else
463			stp->buffer->syscall_result = -EBUSY;
464	}
465
466	return streq;
467}
468
469static void st_release_request(struct st_request *streq)
470{
471	kfree(streq);
472}
473
474static void st_scsi_execute_end(struct request *req, int uptodate)
475{
476	struct st_request *SRpnt = req->end_io_data;
477	struct scsi_tape *STp = SRpnt->stp;
478	struct bio *tmp;
479
480	STp->buffer->cmdstat.midlevel_result = SRpnt->result = req->errors;
481	STp->buffer->cmdstat.residual = req->resid_len;
482
483	tmp = SRpnt->bio;
484	if (SRpnt->waiting)
485		complete(SRpnt->waiting);
486
487	blk_rq_unmap_user(tmp);
488	__blk_put_request(req->q, req);
489}
490
491static int st_scsi_execute(struct st_request *SRpnt, const unsigned char *cmd,
492			   int data_direction, void *buffer, unsigned bufflen,
493			   int timeout, int retries)
494{
495	struct request *req;
496	struct rq_map_data *mdata = &SRpnt->stp->buffer->map_data;
497	int err = 0;
498	int write = (data_direction == DMA_TO_DEVICE);
499
500	req = blk_get_request(SRpnt->stp->device->request_queue, write,
501			      GFP_KERNEL);
502	if (IS_ERR(req))
503		return DRIVER_ERROR << 24;
504
505	blk_rq_set_block_pc(req);
506	req->cmd_flags |= REQ_QUIET;
507
508	mdata->null_mapped = 1;
509
510	if (bufflen) {
511		err = blk_rq_map_user(req->q, req, mdata, NULL, bufflen,
512				      GFP_KERNEL);
513		if (err) {
514			blk_put_request(req);
515			return DRIVER_ERROR << 24;
516		}
517	}
518
519	SRpnt->bio = req->bio;
520	req->cmd_len = COMMAND_SIZE(cmd[0]);
521	memset(req->cmd, 0, BLK_MAX_CDB);
522	memcpy(req->cmd, cmd, req->cmd_len);
523	req->sense = SRpnt->sense;
524	req->sense_len = 0;
525	req->timeout = timeout;
526	req->retries = retries;
527	req->end_io_data = SRpnt;
528
529	blk_execute_rq_nowait(req->q, NULL, req, 1, st_scsi_execute_end);
530	return 0;
531}
532
533/* Do the scsi command. Waits until command performed if do_wait is true.
534   Otherwise write_behind_check() is used to check that the command
535   has finished. */
536static struct st_request *
537st_do_scsi(struct st_request * SRpnt, struct scsi_tape * STp, unsigned char *cmd,
538	   int bytes, int direction, int timeout, int retries, int do_wait)
539{
540	struct completion *waiting;
541	struct rq_map_data *mdata = &STp->buffer->map_data;
542	int ret;
543
544	/* if async, make sure there's no command outstanding */
545	if (!do_wait && ((STp->buffer)->last_SRpnt)) {
546		st_printk(KERN_ERR, STp,
547			  "Async command already active.\n");
548		if (signal_pending(current))
549			(STp->buffer)->syscall_result = (-EINTR);
550		else
551			(STp->buffer)->syscall_result = (-EBUSY);
552		return NULL;
553	}
554
555	if (!SRpnt) {
556		SRpnt = st_allocate_request(STp);
557		if (!SRpnt)
558			return NULL;
559	}
560
561	/* If async IO, set last_SRpnt. This ptr tells write_behind_check
562	   which IO is outstanding. It's nulled out when the IO completes. */
563	if (!do_wait)
564		(STp->buffer)->last_SRpnt = SRpnt;
565
566	waiting = &STp->wait;
567	init_completion(waiting);
568	SRpnt->waiting = waiting;
569
570	if (STp->buffer->do_dio) {
571		mdata->page_order = 0;
572		mdata->nr_entries = STp->buffer->sg_segs;
573		mdata->pages = STp->buffer->mapped_pages;
574	} else {
575		mdata->page_order = STp->buffer->reserved_page_order;
576		mdata->nr_entries =
577			DIV_ROUND_UP(bytes, PAGE_SIZE << mdata->page_order);
578		mdata->pages = STp->buffer->reserved_pages;
579		mdata->offset = 0;
580	}
581
582	memcpy(SRpnt->cmd, cmd, sizeof(SRpnt->cmd));
583	STp->buffer->cmdstat.have_sense = 0;
584	STp->buffer->syscall_result = 0;
585
586	ret = st_scsi_execute(SRpnt, cmd, direction, NULL, bytes, timeout,
587			      retries);
588	if (ret) {
589		/* could not allocate the buffer or request was too large */
590		(STp->buffer)->syscall_result = (-EBUSY);
591		(STp->buffer)->last_SRpnt = NULL;
592	} else if (do_wait) {
593		wait_for_completion(waiting);
594		SRpnt->waiting = NULL;
595		(STp->buffer)->syscall_result = st_chk_result(STp, SRpnt);
596	}
597
598	return SRpnt;
599}
600
601
602/* Handle the write-behind checking (waits for completion). Returns -ENOSPC if
603   write has been correct but EOM early warning reached, -EIO if write ended in
604   error or zero if write successful. Asynchronous writes are used only in
605   variable block mode. */
606static int write_behind_check(struct scsi_tape * STp)
607{
608	int retval = 0;
609	struct st_buffer *STbuffer;
610	struct st_partstat *STps;
611	struct st_cmdstatus *cmdstatp;
612	struct st_request *SRpnt;
613
614	STbuffer = STp->buffer;
615	if (!STbuffer->writing)
616		return 0;
617
618	DEB(
619	if (STp->write_pending)
620		STp->nbr_waits++;
621	else
622		STp->nbr_finished++;
623	) /* end DEB */
624
625	wait_for_completion(&(STp->wait));
626	SRpnt = STbuffer->last_SRpnt;
627	STbuffer->last_SRpnt = NULL;
628	SRpnt->waiting = NULL;
629
630	(STp->buffer)->syscall_result = st_chk_result(STp, SRpnt);
631	st_release_request(SRpnt);
632
633	STbuffer->buffer_bytes -= STbuffer->writing;
634	STps = &(STp->ps[STp->partition]);
635	if (STps->drv_block >= 0) {
636		if (STp->block_size == 0)
637			STps->drv_block++;
638		else
639			STps->drv_block += STbuffer->writing / STp->block_size;
640	}
641
642	cmdstatp = &STbuffer->cmdstat;
643	if (STbuffer->syscall_result) {
644		retval = -EIO;
645		if (cmdstatp->have_sense && !cmdstatp->deferred &&
646		    (cmdstatp->flags & SENSE_EOM) &&
647		    (cmdstatp->sense_hdr.sense_key == NO_SENSE ||
648		     cmdstatp->sense_hdr.sense_key == RECOVERED_ERROR)) {
649			/* EOM at write-behind, has all data been written? */
650			if (!cmdstatp->remainder_valid ||
651			    cmdstatp->uremainder64 == 0)
652				retval = -ENOSPC;
653		}
654		if (retval == -EIO)
655			STps->drv_block = -1;
656	}
657	STbuffer->writing = 0;
658
659	DEB(if (debugging && retval)
660		    st_printk(ST_DEB_MSG, STp,
661				"Async write error %x, return value %d.\n",
662				STbuffer->cmdstat.midlevel_result, retval);) /* end DEB */
663
664	return retval;
665}
666
667
668/* Step over EOF if it has been inadvertently crossed (ioctl not used because
669   it messes up the block number). */
670static int cross_eof(struct scsi_tape * STp, int forward)
671{
672	struct st_request *SRpnt;
673	unsigned char cmd[MAX_COMMAND_SIZE];
674
675	cmd[0] = SPACE;
676	cmd[1] = 0x01;		/* Space FileMarks */
677	if (forward) {
678		cmd[2] = cmd[3] = 0;
679		cmd[4] = 1;
680	} else
681		cmd[2] = cmd[3] = cmd[4] = 0xff;	/* -1 filemarks */
682	cmd[5] = 0;
683
684	DEBC_printk(STp, "Stepping over filemark %s.\n",
685		    forward ? "forward" : "backward");
686
687	SRpnt = st_do_scsi(NULL, STp, cmd, 0, DMA_NONE,
688			   STp->device->request_queue->rq_timeout,
689			   MAX_RETRIES, 1);
690	if (!SRpnt)
691		return (STp->buffer)->syscall_result;
692
693	st_release_request(SRpnt);
694	SRpnt = NULL;
695
696	if ((STp->buffer)->cmdstat.midlevel_result != 0)
697		st_printk(KERN_ERR, STp,
698			  "Stepping over filemark %s failed.\n",
699			  forward ? "forward" : "backward");
700
701	return (STp->buffer)->syscall_result;
702}
703
704
705/* Flush the write buffer (never need to write if variable blocksize). */
706static int st_flush_write_buffer(struct scsi_tape * STp)
707{
708	int transfer, blks;
709	int result;
710	unsigned char cmd[MAX_COMMAND_SIZE];
711	struct st_request *SRpnt;
712	struct st_partstat *STps;
713
714	result = write_behind_check(STp);
715	if (result)
716		return result;
717
718	result = 0;
719	if (STp->dirty == 1) {
720
721		transfer = STp->buffer->buffer_bytes;
722		DEBC_printk(STp, "Flushing %d bytes.\n", transfer);
723
724		memset(cmd, 0, MAX_COMMAND_SIZE);
725		cmd[0] = WRITE_6;
726		cmd[1] = 1;
727		blks = transfer / STp->block_size;
728		cmd[2] = blks >> 16;
729		cmd[3] = blks >> 8;
730		cmd[4] = blks;
731
732		SRpnt = st_do_scsi(NULL, STp, cmd, transfer, DMA_TO_DEVICE,
733				   STp->device->request_queue->rq_timeout,
734				   MAX_WRITE_RETRIES, 1);
735		if (!SRpnt)
736			return (STp->buffer)->syscall_result;
737
738		STps = &(STp->ps[STp->partition]);
739		if ((STp->buffer)->syscall_result != 0) {
740			struct st_cmdstatus *cmdstatp = &STp->buffer->cmdstat;
741
742			if (cmdstatp->have_sense && !cmdstatp->deferred &&
743			    (cmdstatp->flags & SENSE_EOM) &&
744			    (cmdstatp->sense_hdr.sense_key == NO_SENSE ||
745			     cmdstatp->sense_hdr.sense_key == RECOVERED_ERROR) &&
746			    (!cmdstatp->remainder_valid ||
747			     cmdstatp->uremainder64 == 0)) { /* All written at EOM early warning */
748				STp->dirty = 0;
749				(STp->buffer)->buffer_bytes = 0;
750				if (STps->drv_block >= 0)
751					STps->drv_block += blks;
752				result = (-ENOSPC);
753			} else {
754				st_printk(KERN_ERR, STp, "Error on flush.\n");
755				STps->drv_block = (-1);
756				result = (-EIO);
757			}
758		} else {
759			if (STps->drv_block >= 0)
760				STps->drv_block += blks;
761			STp->dirty = 0;
762			(STp->buffer)->buffer_bytes = 0;
763		}
764		st_release_request(SRpnt);
765		SRpnt = NULL;
766	}
767	return result;
768}
769
770
771/* Flush the tape buffer. The tape will be positioned correctly unless
772   seek_next is true. */
773static int flush_buffer(struct scsi_tape *STp, int seek_next)
774{
775	int backspace, result;
776	struct st_buffer *STbuffer;
777	struct st_partstat *STps;
778
779	STbuffer = STp->buffer;
780
781	/*
782	 * If there was a bus reset, block further access
783	 * to this device.
784	 */
785	if (STp->pos_unknown)
786		return (-EIO);
787
788	if (STp->ready != ST_READY)
789		return 0;
790	STps = &(STp->ps[STp->partition]);
791	if (STps->rw == ST_WRITING)	/* Writing */
792		return st_flush_write_buffer(STp);
793
794	if (STp->block_size == 0)
795		return 0;
796
797	backspace = ((STp->buffer)->buffer_bytes +
798		     (STp->buffer)->read_pointer) / STp->block_size -
799	    ((STp->buffer)->read_pointer + STp->block_size - 1) /
800	    STp->block_size;
801	(STp->buffer)->buffer_bytes = 0;
802	(STp->buffer)->read_pointer = 0;
803	result = 0;
804	if (!seek_next) {
805		if (STps->eof == ST_FM_HIT) {
806			result = cross_eof(STp, 0);	/* Back over the EOF hit */
807			if (!result)
808				STps->eof = ST_NOEOF;
809			else {
810				if (STps->drv_file >= 0)
811					STps->drv_file++;
812				STps->drv_block = 0;
813			}
814		}
815		if (!result && backspace > 0)
816			result = st_int_ioctl(STp, MTBSR, backspace);
817	} else if (STps->eof == ST_FM_HIT) {
818		if (STps->drv_file >= 0)
819			STps->drv_file++;
820		STps->drv_block = 0;
821		STps->eof = ST_NOEOF;
822	}
823	return result;
824
825}
826
827/* Set the mode parameters */
828static int set_mode_densblk(struct scsi_tape * STp, struct st_modedef * STm)
829{
830	int set_it = 0;
831	unsigned long arg;
832
833	if (!STp->density_changed &&
834	    STm->default_density >= 0 &&
835	    STm->default_density != STp->density) {
836		arg = STm->default_density;
837		set_it = 1;
838	} else
839		arg = STp->density;
840	arg <<= MT_ST_DENSITY_SHIFT;
841	if (!STp->blksize_changed &&
842	    STm->default_blksize >= 0 &&
843	    STm->default_blksize != STp->block_size) {
844		arg |= STm->default_blksize;
845		set_it = 1;
846	} else
847		arg |= STp->block_size;
848	if (set_it &&
849	    st_int_ioctl(STp, SET_DENS_AND_BLK, arg)) {
850		st_printk(KERN_WARNING, STp,
851			  "Can't set default block size to %d bytes "
852			  "and density %x.\n",
853			  STm->default_blksize, STm->default_density);
854		if (modes_defined)
855			return (-EINVAL);
856	}
857	return 0;
858}
859
860
861/* Lock or unlock the drive door. Don't use when st_request allocated. */
862static int do_door_lock(struct scsi_tape * STp, int do_lock)
863{
864	int retval;
865
866	DEBC_printk(STp, "%socking drive door.\n", do_lock ? "L" : "Unl");
867
868	retval = scsi_set_medium_removal(STp->device,
869			do_lock ? SCSI_REMOVAL_PREVENT : SCSI_REMOVAL_ALLOW);
870	if (!retval)
871		STp->door_locked = do_lock ? ST_LOCKED_EXPLICIT : ST_UNLOCKED;
872	else
873		STp->door_locked = ST_LOCK_FAILS;
874	return retval;
875}
876
877
878/* Set the internal state after reset */
879static void reset_state(struct scsi_tape *STp)
880{
881	int i;
882	struct st_partstat *STps;
883
884	STp->pos_unknown = 0;
885	for (i = 0; i < ST_NBR_PARTITIONS; i++) {
886		STps = &(STp->ps[i]);
887		STps->rw = ST_IDLE;
888		STps->eof = ST_NOEOF;
889		STps->at_sm = 0;
890		STps->last_block_valid = 0;
891		STps->drv_block = -1;
892		STps->drv_file = -1;
893	}
894	if (STp->can_partitions) {
895		STp->partition = find_partition(STp);
896		if (STp->partition < 0)
897			STp->partition = 0;
898		STp->new_partition = STp->partition;
899	}
900}
901
902/* Test if the drive is ready. Returns either one of the codes below or a negative system
903   error code. */
904#define CHKRES_READY       0
905#define CHKRES_NEW_SESSION 1
906#define CHKRES_NOT_READY   2
907#define CHKRES_NO_TAPE     3
908
909#define MAX_ATTENTIONS    10
910
911static int test_ready(struct scsi_tape *STp, int do_wait)
912{
913	int attentions, waits, max_wait, scode;
914	int retval = CHKRES_READY, new_session = 0;
915	unsigned char cmd[MAX_COMMAND_SIZE];
916	struct st_request *SRpnt = NULL;
917	struct st_cmdstatus *cmdstatp = &STp->buffer->cmdstat;
918
919	max_wait = do_wait ? ST_BLOCK_SECONDS : 0;
920
921	for (attentions=waits=0; ; ) {
922		memset((void *) &cmd[0], 0, MAX_COMMAND_SIZE);
923		cmd[0] = TEST_UNIT_READY;
924		SRpnt = st_do_scsi(SRpnt, STp, cmd, 0, DMA_NONE,
925				   STp->long_timeout, MAX_READY_RETRIES, 1);
926
927		if (!SRpnt) {
928			retval = (STp->buffer)->syscall_result;
929			break;
930		}
931
932		if (cmdstatp->have_sense) {
933
934			scode = cmdstatp->sense_hdr.sense_key;
935
936			if (scode == UNIT_ATTENTION) { /* New media? */
937				new_session = 1;
938				if (attentions < MAX_ATTENTIONS) {
939					attentions++;
940					continue;
941				}
942				else {
943					retval = (-EIO);
944					break;
945				}
946			}
947
948			if (scode == NOT_READY) {
949				if (waits < max_wait) {
950					if (msleep_interruptible(1000)) {
951						retval = (-EINTR);
952						break;
953					}
954					waits++;
955					continue;
956				}
957				else {
958					if ((STp->device)->scsi_level >= SCSI_2 &&
959					    cmdstatp->sense_hdr.asc == 0x3a)	/* Check ASC */
960						retval = CHKRES_NO_TAPE;
961					else
962						retval = CHKRES_NOT_READY;
963					break;
964				}
965			}
966		}
967
968		retval = (STp->buffer)->syscall_result;
969		if (!retval)
970			retval = new_session ? CHKRES_NEW_SESSION : CHKRES_READY;
971		break;
972	}
973
974	if (SRpnt != NULL)
975		st_release_request(SRpnt);
976	return retval;
977}
978
979
980/* See if the drive is ready and gather information about the tape. Return values:
981   < 0   negative error code from errno.h
982   0     drive ready
983   1     drive not ready (possibly no tape)
984*/
985static int check_tape(struct scsi_tape *STp, struct file *filp)
986{
987	int i, retval, new_session = 0, do_wait;
988	unsigned char cmd[MAX_COMMAND_SIZE], saved_cleaning;
989	unsigned short st_flags = filp->f_flags;
990	struct st_request *SRpnt = NULL;
991	struct st_modedef *STm;
992	struct st_partstat *STps;
993	struct inode *inode = file_inode(filp);
994	int mode = TAPE_MODE(inode);
995
996	STp->ready = ST_READY;
997
998	if (mode != STp->current_mode) {
999		DEBC_printk(STp, "Mode change from %d to %d.\n",
1000			    STp->current_mode, mode);
1001		new_session = 1;
1002		STp->current_mode = mode;
1003	}
1004	STm = &(STp->modes[STp->current_mode]);
1005
1006	saved_cleaning = STp->cleaning_req;
1007	STp->cleaning_req = 0;
1008
1009	do_wait = ((filp->f_flags & O_NONBLOCK) == 0);
1010	retval = test_ready(STp, do_wait);
1011
1012	if (retval < 0)
1013	    goto err_out;
1014
1015	if (retval == CHKRES_NEW_SESSION) {
1016		STp->pos_unknown = 0;
1017		STp->partition = STp->new_partition = 0;
1018		if (STp->can_partitions)
1019			STp->nbr_partitions = 1; /* This guess will be updated later
1020                                                    if necessary */
1021		for (i = 0; i < ST_NBR_PARTITIONS; i++) {
1022			STps = &(STp->ps[i]);
1023			STps->rw = ST_IDLE;
1024			STps->eof = ST_NOEOF;
1025			STps->at_sm = 0;
1026			STps->last_block_valid = 0;
1027			STps->drv_block = 0;
1028			STps->drv_file = 0;
1029		}
1030		new_session = 1;
1031	}
1032	else {
1033		STp->cleaning_req |= saved_cleaning;
1034
1035		if (retval == CHKRES_NOT_READY || retval == CHKRES_NO_TAPE) {
1036			if (retval == CHKRES_NO_TAPE)
1037				STp->ready = ST_NO_TAPE;
1038			else
1039				STp->ready = ST_NOT_READY;
1040
1041			STp->density = 0;	/* Clear the erroneous "residue" */
1042			STp->write_prot = 0;
1043			STp->block_size = 0;
1044			STp->ps[0].drv_file = STp->ps[0].drv_block = (-1);
1045			STp->partition = STp->new_partition = 0;
1046			STp->door_locked = ST_UNLOCKED;
1047			return CHKRES_NOT_READY;
1048		}
1049	}
1050
1051	if (STp->omit_blklims)
1052		STp->min_block = STp->max_block = (-1);
1053	else {
1054		memset((void *) &cmd[0], 0, MAX_COMMAND_SIZE);
1055		cmd[0] = READ_BLOCK_LIMITS;
1056
1057		SRpnt = st_do_scsi(SRpnt, STp, cmd, 6, DMA_FROM_DEVICE,
1058				   STp->device->request_queue->rq_timeout,
1059				   MAX_READY_RETRIES, 1);
1060		if (!SRpnt) {
1061			retval = (STp->buffer)->syscall_result;
1062			goto err_out;
1063		}
1064
1065		if (!SRpnt->result && !STp->buffer->cmdstat.have_sense) {
1066			STp->max_block = ((STp->buffer)->b_data[1] << 16) |
1067			    ((STp->buffer)->b_data[2] << 8) | (STp->buffer)->b_data[3];
1068			STp->min_block = ((STp->buffer)->b_data[4] << 8) |
1069			    (STp->buffer)->b_data[5];
1070			if ( DEB( debugging || ) !STp->inited)
1071				st_printk(KERN_INFO, STp,
1072					  "Block limits %d - %d bytes.\n",
1073					  STp->min_block, STp->max_block);
1074		} else {
1075			STp->min_block = STp->max_block = (-1);
1076			DEBC_printk(STp, "Can't read block limits.\n");
1077		}
1078	}
1079
1080	memset((void *) &cmd[0], 0, MAX_COMMAND_SIZE);
1081	cmd[0] = MODE_SENSE;
1082	cmd[4] = 12;
1083
1084	SRpnt = st_do_scsi(SRpnt, STp, cmd, 12, DMA_FROM_DEVICE,
1085			   STp->device->request_queue->rq_timeout,
1086			   MAX_READY_RETRIES, 1);
1087	if (!SRpnt) {
1088		retval = (STp->buffer)->syscall_result;
1089		goto err_out;
1090	}
1091
1092	if ((STp->buffer)->syscall_result != 0) {
1093		DEBC_printk(STp, "No Mode Sense.\n");
1094		STp->block_size = ST_DEFAULT_BLOCK;	/* Educated guess (?) */
1095		(STp->buffer)->syscall_result = 0;	/* Prevent error propagation */
1096		STp->drv_write_prot = 0;
1097	} else {
1098		DEBC_printk(STp,"Mode sense. Length %d, "
1099			    "medium %x, WBS %x, BLL %d\n",
1100			    (STp->buffer)->b_data[0],
1101			    (STp->buffer)->b_data[1],
1102			    (STp->buffer)->b_data[2],
1103			    (STp->buffer)->b_data[3]);
1104
1105		if ((STp->buffer)->b_data[3] >= 8) {
1106			STp->drv_buffer = ((STp->buffer)->b_data[2] >> 4) & 7;
1107			STp->density = (STp->buffer)->b_data[4];
1108			STp->block_size = (STp->buffer)->b_data[9] * 65536 +
1109			    (STp->buffer)->b_data[10] * 256 + (STp->buffer)->b_data[11];
1110			DEBC_printk(STp, "Density %x, tape length: %x, "
1111				    "drv buffer: %d\n",
1112				    STp->density,
1113				    (STp->buffer)->b_data[5] * 65536 +
1114				    (STp->buffer)->b_data[6] * 256 +
1115				    (STp->buffer)->b_data[7],
1116				    STp->drv_buffer);
1117		}
1118		STp->drv_write_prot = ((STp->buffer)->b_data[2] & 0x80) != 0;
1119		if (!STp->drv_buffer && STp->immediate_filemark) {
1120			st_printk(KERN_WARNING, STp,
1121				  "non-buffered tape: disabling "
1122				  "writing immediate filemarks\n");
1123			STp->immediate_filemark = 0;
1124		}
1125	}
1126	st_release_request(SRpnt);
1127	SRpnt = NULL;
1128	STp->inited = 1;
1129
1130	if (STp->block_size > 0)
1131		(STp->buffer)->buffer_blocks =
1132			(STp->buffer)->buffer_size / STp->block_size;
1133	else
1134		(STp->buffer)->buffer_blocks = 1;
1135	(STp->buffer)->buffer_bytes = (STp->buffer)->read_pointer = 0;
1136
1137	DEBC_printk(STp, "Block size: %d, buffer size: %d (%d blocks).\n",
1138		    STp->block_size, (STp->buffer)->buffer_size,
1139		    (STp->buffer)->buffer_blocks);
1140
1141	if (STp->drv_write_prot) {
1142		STp->write_prot = 1;
1143
1144		DEBC_printk(STp, "Write protected\n");
1145
1146		if (do_wait &&
1147		    ((st_flags & O_ACCMODE) == O_WRONLY ||
1148		     (st_flags & O_ACCMODE) == O_RDWR)) {
1149			retval = (-EROFS);
1150			goto err_out;
1151		}
1152	}
1153
1154	if (STp->can_partitions && STp->nbr_partitions < 1) {
1155		/* This code is reached when the device is opened for the first time
1156		   after the driver has been initialized with tape in the drive and the
1157		   partition support has been enabled. */
1158		DEBC_printk(STp, "Updating partition number in status.\n");
1159		if ((STp->partition = find_partition(STp)) < 0) {
1160			retval = STp->partition;
1161			goto err_out;
1162		}
1163		STp->new_partition = STp->partition;
1164		STp->nbr_partitions = 1; /* This guess will be updated when necessary */
1165	}
1166
1167	if (new_session) {	/* Change the drive parameters for the new mode */
1168		STp->density_changed = STp->blksize_changed = 0;
1169		STp->compression_changed = 0;
1170		if (!(STm->defaults_for_writes) &&
1171		    (retval = set_mode_densblk(STp, STm)) < 0)
1172		    goto err_out;
1173
1174		if (STp->default_drvbuffer != 0xff) {
1175			if (st_int_ioctl(STp, MTSETDRVBUFFER, STp->default_drvbuffer))
1176				st_printk(KERN_WARNING, STp,
1177					  "Can't set default drive "
1178					  "buffering to %d.\n",
1179					  STp->default_drvbuffer);
1180		}
1181	}
1182
1183	return CHKRES_READY;
1184
1185 err_out:
1186	return retval;
1187}
1188
1189
1190/* Open the device. Needs to take the BKL only because of incrementing the SCSI host
1191   module count. */
1192static int st_open(struct inode *inode, struct file *filp)
1193{
1194	int i, retval = (-EIO);
1195	int resumed = 0;
1196	struct scsi_tape *STp;
1197	struct st_partstat *STps;
1198	int dev = TAPE_NR(inode);
1199
1200	/*
1201	 * We really want to do nonseekable_open(inode, filp); here, but some
1202	 * versions of tar incorrectly call lseek on tapes and bail out if that
1203	 * fails.  So we disallow pread() and pwrite(), but permit lseeks.
1204	 */
1205	filp->f_mode &= ~(FMODE_PREAD | FMODE_PWRITE);
1206
1207	if (!(STp = scsi_tape_get(dev))) {
1208		return -ENXIO;
1209	}
1210
1211	filp->private_data = STp;
1212
1213	spin_lock(&st_use_lock);
1214	if (STp->in_use) {
1215		spin_unlock(&st_use_lock);
1216		scsi_tape_put(STp);
1217		DEBC_printk(STp, "Device already in use.\n");
1218		return (-EBUSY);
1219	}
1220
1221	STp->in_use = 1;
1222	spin_unlock(&st_use_lock);
1223	STp->rew_at_close = STp->autorew_dev = (iminor(inode) & 0x80) == 0;
1224
1225	if (scsi_autopm_get_device(STp->device) < 0) {
1226		retval = -EIO;
1227		goto err_out;
1228	}
1229	resumed = 1;
1230	if (!scsi_block_when_processing_errors(STp->device)) {
1231		retval = (-ENXIO);
1232		goto err_out;
1233	}
1234
1235	/* See that we have at least a one page buffer available */
1236	if (!enlarge_buffer(STp->buffer, PAGE_SIZE, STp->restr_dma)) {
1237		st_printk(KERN_WARNING, STp,
1238			  "Can't allocate one page tape buffer.\n");
1239		retval = (-EOVERFLOW);
1240		goto err_out;
1241	}
1242
1243	(STp->buffer)->cleared = 0;
1244	(STp->buffer)->writing = 0;
1245	(STp->buffer)->syscall_result = 0;
1246
1247	STp->write_prot = ((filp->f_flags & O_ACCMODE) == O_RDONLY);
1248
1249	STp->dirty = 0;
1250	for (i = 0; i < ST_NBR_PARTITIONS; i++) {
1251		STps = &(STp->ps[i]);
1252		STps->rw = ST_IDLE;
1253	}
1254	STp->try_dio_now = STp->try_dio;
1255	STp->recover_count = 0;
1256	DEB( STp->nbr_waits = STp->nbr_finished = 0;
1257	     STp->nbr_requests = STp->nbr_dio = STp->nbr_pages = 0; )
1258
1259	retval = check_tape(STp, filp);
1260	if (retval < 0)
1261		goto err_out;
1262	if ((filp->f_flags & O_NONBLOCK) == 0 &&
1263	    retval != CHKRES_READY) {
1264		if (STp->ready == NO_TAPE)
1265			retval = (-ENOMEDIUM);
1266		else
1267			retval = (-EIO);
1268		goto err_out;
1269	}
1270	return 0;
1271
1272 err_out:
1273	normalize_buffer(STp->buffer);
1274	spin_lock(&st_use_lock);
1275	STp->in_use = 0;
1276	spin_unlock(&st_use_lock);
1277	if (resumed)
1278		scsi_autopm_put_device(STp->device);
1279	scsi_tape_put(STp);
1280	return retval;
1281
1282}
1283
1284
1285/* Flush the tape buffer before close */
1286static int st_flush(struct file *filp, fl_owner_t id)
1287{
1288	int result = 0, result2;
1289	unsigned char cmd[MAX_COMMAND_SIZE];
1290	struct st_request *SRpnt;
1291	struct scsi_tape *STp = filp->private_data;
1292	struct st_modedef *STm = &(STp->modes[STp->current_mode]);
1293	struct st_partstat *STps = &(STp->ps[STp->partition]);
1294
1295	if (file_count(filp) > 1)
1296		return 0;
1297
1298	if (STps->rw == ST_WRITING && !STp->pos_unknown) {
1299		result = st_flush_write_buffer(STp);
1300		if (result != 0 && result != (-ENOSPC))
1301			goto out;
1302	}
1303
1304	if (STp->can_partitions &&
1305	    (result2 = switch_partition(STp)) < 0) {
1306		DEBC_printk(STp, "switch_partition at close failed.\n");
1307		if (result == 0)
1308			result = result2;
1309		goto out;
1310	}
1311
1312	DEBC( if (STp->nbr_requests)
1313		st_printk(KERN_DEBUG, STp,
1314			  "Number of r/w requests %d, dio used in %d, "
1315			  "pages %d.\n", STp->nbr_requests, STp->nbr_dio,
1316			  STp->nbr_pages));
1317
1318	if (STps->rw == ST_WRITING && !STp->pos_unknown) {
1319		struct st_cmdstatus *cmdstatp = &STp->buffer->cmdstat;
1320
1321#if DEBUG
1322		DEBC_printk(STp, "Async write waits %d, finished %d.\n",
1323			    STp->nbr_waits, STp->nbr_finished);
1324#endif
1325		memset(cmd, 0, MAX_COMMAND_SIZE);
1326		cmd[0] = WRITE_FILEMARKS;
1327		if (STp->immediate_filemark)
1328			cmd[1] = 1;
1329		cmd[4] = 1 + STp->two_fm;
1330
1331		SRpnt = st_do_scsi(NULL, STp, cmd, 0, DMA_NONE,
1332				   STp->device->request_queue->rq_timeout,
1333				   MAX_WRITE_RETRIES, 1);
1334		if (!SRpnt) {
1335			result = (STp->buffer)->syscall_result;
1336			goto out;
1337		}
1338
1339		if (STp->buffer->syscall_result == 0 ||
1340		    (cmdstatp->have_sense && !cmdstatp->deferred &&
1341		     (cmdstatp->flags & SENSE_EOM) &&
1342		     (cmdstatp->sense_hdr.sense_key == NO_SENSE ||
1343		      cmdstatp->sense_hdr.sense_key == RECOVERED_ERROR) &&
1344		     (!cmdstatp->remainder_valid || cmdstatp->uremainder64 == 0))) {
1345			/* Write successful at EOM */
1346			st_release_request(SRpnt);
1347			SRpnt = NULL;
1348			if (STps->drv_file >= 0)
1349				STps->drv_file++;
1350			STps->drv_block = 0;
1351			if (STp->two_fm)
1352				cross_eof(STp, 0);
1353			STps->eof = ST_FM;
1354		}
1355		else { /* Write error */
1356			st_release_request(SRpnt);
1357			SRpnt = NULL;
1358			st_printk(KERN_ERR, STp,
1359				  "Error on write filemark.\n");
1360			if (result == 0)
1361				result = (-EIO);
1362		}
1363
1364		DEBC_printk(STp, "Buffer flushed, %d EOF(s) written\n", cmd[4]);
1365	} else if (!STp->rew_at_close) {
1366		STps = &(STp->ps[STp->partition]);
1367		if (!STm->sysv || STps->rw != ST_READING) {
1368			if (STp->can_bsr)
1369				result = flush_buffer(STp, 0);
1370			else if (STps->eof == ST_FM_HIT) {
1371				result = cross_eof(STp, 0);
1372				if (result) {
1373					if (STps->drv_file >= 0)
1374						STps->drv_file++;
1375					STps->drv_block = 0;
1376					STps->eof = ST_FM;
1377				} else
1378					STps->eof = ST_NOEOF;
1379			}
1380		} else if ((STps->eof == ST_NOEOF &&
1381			    !(result = cross_eof(STp, 1))) ||
1382			   STps->eof == ST_FM_HIT) {
1383			if (STps->drv_file >= 0)
1384				STps->drv_file++;
1385			STps->drv_block = 0;
1386			STps->eof = ST_FM;
1387		}
1388	}
1389
1390      out:
1391	if (STp->rew_at_close) {
1392		result2 = st_int_ioctl(STp, MTREW, 1);
1393		if (result == 0)
1394			result = result2;
1395	}
1396	return result;
1397}
1398
1399
1400/* Close the device and release it. BKL is not needed: this is the only thread
1401   accessing this tape. */
1402static int st_release(struct inode *inode, struct file *filp)
1403{
1404	int result = 0;
1405	struct scsi_tape *STp = filp->private_data;
1406
1407	if (STp->door_locked == ST_LOCKED_AUTO)
1408		do_door_lock(STp, 0);
1409
1410	normalize_buffer(STp->buffer);
1411	spin_lock(&st_use_lock);
1412	STp->in_use = 0;
1413	spin_unlock(&st_use_lock);
1414	scsi_autopm_put_device(STp->device);
1415	scsi_tape_put(STp);
1416
1417	return result;
1418}
1419
1420/* The checks common to both reading and writing */
1421static ssize_t rw_checks(struct scsi_tape *STp, struct file *filp, size_t count)
1422{
1423	ssize_t retval = 0;
1424
1425	/*
1426	 * If we are in the middle of error recovery, don't let anyone
1427	 * else try and use this device.  Also, if error recovery fails, it
1428	 * may try and take the device offline, in which case all further
1429	 * access to the device is prohibited.
1430	 */
1431	if (!scsi_block_when_processing_errors(STp->device)) {
1432		retval = (-ENXIO);
1433		goto out;
1434	}
1435
1436	if (STp->ready != ST_READY) {
1437		if (STp->ready == ST_NO_TAPE)
1438			retval = (-ENOMEDIUM);
1439		else
1440			retval = (-EIO);
1441		goto out;
1442	}
1443
1444	if (! STp->modes[STp->current_mode].defined) {
1445		retval = (-ENXIO);
1446		goto out;
1447	}
1448
1449
1450	/*
1451	 * If there was a bus reset, block further access
1452	 * to this device.
1453	 */
1454	if (STp->pos_unknown) {
1455		retval = (-EIO);
1456		goto out;
1457	}
1458
1459	if (count == 0)
1460		goto out;
1461
1462	DEB(
1463	if (!STp->in_use) {
1464		st_printk(ST_DEB_MSG, STp,
1465			  "Incorrect device.\n");
1466		retval = (-EIO);
1467		goto out;
1468	} ) /* end DEB */
1469
1470	if (STp->can_partitions &&
1471	    (retval = switch_partition(STp)) < 0)
1472		goto out;
1473
1474	if (STp->block_size == 0 && STp->max_block > 0 &&
1475	    (count < STp->min_block || count > STp->max_block)) {
1476		retval = (-EINVAL);
1477		goto out;
1478	}
1479
1480	if (STp->do_auto_lock && STp->door_locked == ST_UNLOCKED &&
1481	    !do_door_lock(STp, 1))
1482		STp->door_locked = ST_LOCKED_AUTO;
1483
1484 out:
1485	return retval;
1486}
1487
1488
1489static int setup_buffering(struct scsi_tape *STp, const char __user *buf,
1490			   size_t count, int is_read)
1491{
1492	int i, bufsize, retval = 0;
1493	struct st_buffer *STbp = STp->buffer;
1494
1495	if (is_read)
1496		i = STp->try_dio_now && try_rdio;
1497	else
1498		i = STp->try_dio_now && try_wdio;
1499
1500	if (i && ((unsigned long)buf & queue_dma_alignment(
1501					STp->device->request_queue)) == 0) {
1502		i = sgl_map_user_pages(STbp, STbp->use_sg, (unsigned long)buf,
1503				       count, (is_read ? READ : WRITE));
1504		if (i > 0) {
1505			STbp->do_dio = i;
1506			STbp->buffer_bytes = 0;   /* can be used as transfer counter */
1507		}
1508		else
1509			STbp->do_dio = 0;  /* fall back to buffering with any error */
1510		STbp->sg_segs = STbp->do_dio;
1511		DEB(
1512		     if (STbp->do_dio) {
1513			STp->nbr_dio++;
1514			STp->nbr_pages += STbp->do_dio;
1515		     }
1516		)
1517	} else
1518		STbp->do_dio = 0;
1519	DEB( STp->nbr_requests++; )
1520
1521	if (!STbp->do_dio) {
1522		if (STp->block_size)
1523			bufsize = STp->block_size > st_fixed_buffer_size ?
1524				STp->block_size : st_fixed_buffer_size;
1525		else {
1526			bufsize = count;
1527			/* Make sure that data from previous user is not leaked even if
1528			   HBA does not return correct residual */
1529			if (is_read && STp->sili && !STbp->cleared)
1530				clear_buffer(STbp);
1531		}
1532
1533		if (bufsize > STbp->buffer_size &&
1534		    !enlarge_buffer(STbp, bufsize, STp->restr_dma)) {
1535			st_printk(KERN_WARNING, STp,
1536				  "Can't allocate %d byte tape buffer.\n",
1537				  bufsize);
1538			retval = (-EOVERFLOW);
1539			goto out;
1540		}
1541		if (STp->block_size)
1542			STbp->buffer_blocks = bufsize / STp->block_size;
1543	}
1544
1545 out:
1546	return retval;
1547}
1548
1549
1550/* Can be called more than once after each setup_buffer() */
1551static void release_buffering(struct scsi_tape *STp, int is_read)
1552{
1553	struct st_buffer *STbp;
1554
1555	STbp = STp->buffer;
1556	if (STbp->do_dio) {
1557		sgl_unmap_user_pages(STbp, STbp->do_dio, is_read);
1558		STbp->do_dio = 0;
1559		STbp->sg_segs = 0;
1560	}
1561}
1562
1563
1564/* Write command */
1565static ssize_t
1566st_write(struct file *filp, const char __user *buf, size_t count, loff_t * ppos)
1567{
1568	ssize_t total;
1569	ssize_t i, do_count, blks, transfer;
1570	ssize_t retval;
1571	int undone, retry_eot = 0, scode;
1572	int async_write;
1573	unsigned char cmd[MAX_COMMAND_SIZE];
1574	const char __user *b_point;
1575	struct st_request *SRpnt = NULL;
1576	struct scsi_tape *STp = filp->private_data;
1577	struct st_modedef *STm;
1578	struct st_partstat *STps;
1579	struct st_buffer *STbp;
1580
1581	if (mutex_lock_interruptible(&STp->lock))
1582		return -ERESTARTSYS;
1583
1584	retval = rw_checks(STp, filp, count);
1585	if (retval || count == 0)
1586		goto out;
1587
1588	/* Write must be integral number of blocks */
1589	if (STp->block_size != 0 && (count % STp->block_size) != 0) {
1590		st_printk(KERN_WARNING, STp,
1591			  "Write not multiple of tape block size.\n");
1592		retval = (-EINVAL);
1593		goto out;
1594	}
1595
1596	STm = &(STp->modes[STp->current_mode]);
1597	STps = &(STp->ps[STp->partition]);
1598
1599	if (STp->write_prot) {
1600		retval = (-EACCES);
1601		goto out;
1602	}
1603
1604
1605	if (STps->rw == ST_READING) {
1606		retval = flush_buffer(STp, 0);
1607		if (retval)
1608			goto out;
1609		STps->rw = ST_WRITING;
1610	} else if (STps->rw != ST_WRITING &&
1611		   STps->drv_file == 0 && STps->drv_block == 0) {
1612		if ((retval = set_mode_densblk(STp, STm)) < 0)
1613			goto out;
1614		if (STm->default_compression != ST_DONT_TOUCH &&
1615		    !(STp->compression_changed)) {
1616			if (st_compression(STp, (STm->default_compression == ST_YES))) {
1617				st_printk(KERN_WARNING, STp,
1618					  "Can't set default compression.\n");
1619				if (modes_defined) {
1620					retval = (-EINVAL);
1621					goto out;
1622				}
1623			}
1624		}
1625	}
1626
1627	STbp = STp->buffer;
1628	i = write_behind_check(STp);
1629	if (i) {
1630		if (i == -ENOSPC)
1631			STps->eof = ST_EOM_OK;
1632		else
1633			STps->eof = ST_EOM_ERROR;
1634	}
1635
1636	if (STps->eof == ST_EOM_OK) {
1637		STps->eof = ST_EOD_1;  /* allow next write */
1638		retval = (-ENOSPC);
1639		goto out;
1640	}
1641	else if (STps->eof == ST_EOM_ERROR) {
1642		retval = (-EIO);
1643		goto out;
1644	}
1645
1646	/* Check the buffer readability in cases where copy_user might catch
1647	   the problems after some tape movement. */
1648	if (STp->block_size != 0 &&
1649	    !STbp->do_dio &&
1650	    (copy_from_user(&i, buf, 1) != 0 ||
1651	     copy_from_user(&i, buf + count - 1, 1) != 0)) {
1652		retval = (-EFAULT);
1653		goto out;
1654	}
1655
1656	retval = setup_buffering(STp, buf, count, 0);
1657	if (retval)
1658		goto out;
1659
1660	total = count;
1661
1662	memset(cmd, 0, MAX_COMMAND_SIZE);
1663	cmd[0] = WRITE_6;
1664	cmd[1] = (STp->block_size != 0);
1665
1666	STps->rw = ST_WRITING;
1667
1668	b_point = buf;
1669	while (count > 0 && !retry_eot) {
1670
1671		if (STbp->do_dio) {
1672			do_count = count;
1673		}
1674		else {
1675			if (STp->block_size == 0)
1676				do_count = count;
1677			else {
1678				do_count = STbp->buffer_blocks * STp->block_size -
1679					STbp->buffer_bytes;
1680				if (do_count > count)
1681					do_count = count;
1682			}
1683
1684			i = append_to_buffer(b_point, STbp, do_count);
1685			if (i) {
1686				retval = i;
1687				goto out;
1688			}
1689		}
1690		count -= do_count;
1691		b_point += do_count;
1692
1693		async_write = STp->block_size == 0 && !STbp->do_dio &&
1694			STm->do_async_writes && STps->eof < ST_EOM_OK;
1695
1696		if (STp->block_size != 0 && STm->do_buffer_writes &&
1697		    !(STp->try_dio_now && try_wdio) && STps->eof < ST_EOM_OK &&
1698		    STbp->buffer_bytes < STbp->buffer_size) {
1699			STp->dirty = 1;
1700			/* Don't write a buffer that is not full enough. */
1701			if (!async_write && count == 0)
1702				break;
1703		}
1704
1705	retry_write:
1706		if (STp->block_size == 0)
1707			blks = transfer = do_count;
1708		else {
1709			if (!STbp->do_dio)
1710				blks = STbp->buffer_bytes;
1711			else
1712				blks = do_count;
1713			blks /= STp->block_size;
1714			transfer = blks * STp->block_size;
1715		}
1716		cmd[2] = blks >> 16;
1717		cmd[3] = blks >> 8;
1718		cmd[4] = blks;
1719
1720		SRpnt = st_do_scsi(SRpnt, STp, cmd, transfer, DMA_TO_DEVICE,
1721				   STp->device->request_queue->rq_timeout,
1722				   MAX_WRITE_RETRIES, !async_write);
1723		if (!SRpnt) {
1724			retval = STbp->syscall_result;
1725			goto out;
1726		}
1727		if (async_write && !STbp->syscall_result) {
1728			STbp->writing = transfer;
1729			STp->dirty = !(STbp->writing ==
1730				       STbp->buffer_bytes);
1731			SRpnt = NULL;  /* Prevent releasing this request! */
1732			DEB( STp->write_pending = 1; )
1733			break;
1734		}
1735
1736		if (STbp->syscall_result != 0) {
1737			struct st_cmdstatus *cmdstatp = &STp->buffer->cmdstat;
1738
1739			DEBC_printk(STp, "Error on write:\n");
1740			if (cmdstatp->have_sense && (cmdstatp->flags & SENSE_EOM)) {
1741				scode = cmdstatp->sense_hdr.sense_key;
1742				if (cmdstatp->remainder_valid)
1743					undone = (int)cmdstatp->uremainder64;
1744				else if (STp->block_size == 0 &&
1745					 scode == VOLUME_OVERFLOW)
1746					undone = transfer;
1747				else
1748					undone = 0;
1749				if (STp->block_size != 0)
1750					undone *= STp->block_size;
1751				if (undone <= do_count) {
1752					/* Only data from this write is not written */
1753					count += undone;
1754					b_point -= undone;
1755					do_count -= undone;
1756					if (STp->block_size)
1757						blks = (transfer - undone) / STp->block_size;
1758					STps->eof = ST_EOM_OK;
1759					/* Continue in fixed block mode if all written
1760					   in this request but still something left to write
1761					   (retval left to zero)
1762					*/
1763					if (STp->block_size == 0 ||
1764					    undone > 0 || count == 0)
1765						retval = (-ENOSPC); /* EOM within current request */
1766					DEBC_printk(STp, "EOM with %d "
1767						    "bytes unwritten.\n",
1768						    (int)count);
1769				} else {
1770					/* EOT within data buffered earlier (possible only
1771					   in fixed block mode without direct i/o) */
1772					if (!retry_eot && !cmdstatp->deferred &&
1773					    (scode == NO_SENSE || scode == RECOVERED_ERROR)) {
1774						move_buffer_data(STp->buffer, transfer - undone);
1775						retry_eot = 1;
1776						if (STps->drv_block >= 0) {
1777							STps->drv_block += (transfer - undone) /
1778								STp->block_size;
1779						}
1780						STps->eof = ST_EOM_OK;
1781						DEBC_printk(STp, "Retry "
1782							    "write of %d "
1783							    "bytes at EOM.\n",
1784							    STp->buffer->buffer_bytes);
1785						goto retry_write;
1786					}
1787					else {
1788						/* Either error within data buffered by driver or
1789						   failed retry */
1790						count -= do_count;
1791						blks = do_count = 0;
1792						STps->eof = ST_EOM_ERROR;
1793						STps->drv_block = (-1); /* Too cautious? */
1794						retval = (-EIO);	/* EOM for old data */
1795						DEBC_printk(STp, "EOM with "
1796							    "lost data.\n");
1797					}
1798				}
1799			} else {
1800				count += do_count;
1801				STps->drv_block = (-1);		/* Too cautious? */
1802				retval = STbp->syscall_result;
1803			}
1804
1805		}
1806
1807		if (STps->drv_block >= 0) {
1808			if (STp->block_size == 0)
1809				STps->drv_block += (do_count > 0);
1810			else
1811				STps->drv_block += blks;
1812		}
1813
1814		STbp->buffer_bytes = 0;
1815		STp->dirty = 0;
1816
1817		if (retval || retry_eot) {
1818			if (count < total)
1819				retval = total - count;
1820			goto out;
1821		}
1822	}
1823
1824	if (STps->eof == ST_EOD_1)
1825		STps->eof = ST_EOM_OK;
1826	else if (STps->eof != ST_EOM_OK)
1827		STps->eof = ST_NOEOF;
1828	retval = total - count;
1829
1830 out:
1831	if (SRpnt != NULL)
1832		st_release_request(SRpnt);
1833	release_buffering(STp, 0);
1834	mutex_unlock(&STp->lock);
1835
1836	return retval;
1837}
1838
1839/* Read data from the tape. Returns zero in the normal case, one if the
1840   eof status has changed, and the negative error code in case of a
1841   fatal error. Otherwise updates the buffer and the eof state.
1842
1843   Does release user buffer mapping if it is set.
1844*/
1845static long read_tape(struct scsi_tape *STp, long count,
1846		      struct st_request ** aSRpnt)
1847{
1848	int transfer, blks, bytes;
1849	unsigned char cmd[MAX_COMMAND_SIZE];
1850	struct st_request *SRpnt;
1851	struct st_modedef *STm;
1852	struct st_partstat *STps;
1853	struct st_buffer *STbp;
1854	int retval = 0;
1855
1856	if (count == 0)
1857		return 0;
1858
1859	STm = &(STp->modes[STp->current_mode]);
1860	STps = &(STp->ps[STp->partition]);
1861	if (STps->eof == ST_FM_HIT)
1862		return 1;
1863	STbp = STp->buffer;
1864
1865	if (STp->block_size == 0)
1866		blks = bytes = count;
1867	else {
1868		if (!(STp->try_dio_now && try_rdio) && STm->do_read_ahead) {
1869			blks = (STp->buffer)->buffer_blocks;
1870			bytes = blks * STp->block_size;
1871		} else {
1872			bytes = count;
1873			if (!STbp->do_dio && bytes > (STp->buffer)->buffer_size)
1874				bytes = (STp->buffer)->buffer_size;
1875			blks = bytes / STp->block_size;
1876			bytes = blks * STp->block_size;
1877		}
1878	}
1879
1880	memset(cmd, 0, MAX_COMMAND_SIZE);
1881	cmd[0] = READ_6;
1882	cmd[1] = (STp->block_size != 0);
1883	if (!cmd[1] && STp->sili)
1884		cmd[1] |= 2;
1885	cmd[2] = blks >> 16;
1886	cmd[3] = blks >> 8;
1887	cmd[4] = blks;
1888
1889	SRpnt = *aSRpnt;
1890	SRpnt = st_do_scsi(SRpnt, STp, cmd, bytes, DMA_FROM_DEVICE,
1891			   STp->device->request_queue->rq_timeout,
1892			   MAX_RETRIES, 1);
1893	release_buffering(STp, 1);
1894	*aSRpnt = SRpnt;
1895	if (!SRpnt)
1896		return STbp->syscall_result;
1897
1898	STbp->read_pointer = 0;
1899	STps->at_sm = 0;
1900
1901	/* Something to check */
1902	if (STbp->syscall_result) {
1903		struct st_cmdstatus *cmdstatp = &STp->buffer->cmdstat;
1904
1905		retval = 1;
1906		DEBC_printk(STp,
1907			    "Sense: %2x %2x %2x %2x %2x %2x %2x %2x\n",
1908			    SRpnt->sense[0], SRpnt->sense[1],
1909			    SRpnt->sense[2], SRpnt->sense[3],
1910			    SRpnt->sense[4], SRpnt->sense[5],
1911			    SRpnt->sense[6], SRpnt->sense[7]);
1912		if (cmdstatp->have_sense) {
1913
1914			if (cmdstatp->sense_hdr.sense_key == BLANK_CHECK)
1915				cmdstatp->flags &= 0xcf;	/* No need for EOM in this case */
1916
1917			if (cmdstatp->flags != 0) { /* EOF, EOM, or ILI */
1918				/* Compute the residual count */
1919				if (cmdstatp->remainder_valid)
1920					transfer = (int)cmdstatp->uremainder64;
1921				else
1922					transfer = 0;
1923				if (STp->block_size == 0 &&
1924				    cmdstatp->sense_hdr.sense_key == MEDIUM_ERROR)
1925					transfer = bytes;
1926
1927				if (cmdstatp->flags & SENSE_ILI) {	/* ILI */
1928					if (STp->block_size == 0 &&
1929					    transfer < 0) {
1930						st_printk(KERN_NOTICE, STp,
1931							  "Failed to read %d "
1932							  "byte block with %d "
1933							  "byte transfer.\n",
1934							  bytes - transfer,
1935							  bytes);
1936						if (STps->drv_block >= 0)
1937							STps->drv_block += 1;
1938						STbp->buffer_bytes = 0;
1939						return (-ENOMEM);
1940					} else if (STp->block_size == 0) {
1941						STbp->buffer_bytes = bytes - transfer;
1942					} else {
1943						st_release_request(SRpnt);
1944						SRpnt = *aSRpnt = NULL;
1945						if (transfer == blks) {	/* We did not get anything, error */
1946							st_printk(KERN_NOTICE, STp,
1947								  "Incorrect "
1948								  "block size.\n");
1949							if (STps->drv_block >= 0)
1950								STps->drv_block += blks - transfer + 1;
1951							st_int_ioctl(STp, MTBSR, 1);
1952							return (-EIO);
1953						}
1954						/* We have some data, deliver it */
1955						STbp->buffer_bytes = (blks - transfer) *
1956						    STp->block_size;
1957						DEBC_printk(STp, "ILI but "
1958							    "enough data "
1959							    "received %ld "
1960							    "%d.\n", count,
1961							    STbp->buffer_bytes);
1962						if (STps->drv_block >= 0)
1963							STps->drv_block += 1;
1964						if (st_int_ioctl(STp, MTBSR, 1))
1965							return (-EIO);
1966					}
1967				} else if (cmdstatp->flags & SENSE_FMK) {	/* FM overrides EOM */
1968					if (STps->eof != ST_FM_HIT)
1969						STps->eof = ST_FM_HIT;
1970					else
1971						STps->eof = ST_EOD_2;
1972					if (STp->block_size == 0)
1973						STbp->buffer_bytes = 0;
1974					else
1975						STbp->buffer_bytes =
1976						    bytes - transfer * STp->block_size;
1977					DEBC_printk(STp, "EOF detected (%d "
1978						    "bytes read).\n",
1979						    STbp->buffer_bytes);
1980				} else if (cmdstatp->flags & SENSE_EOM) {
1981					if (STps->eof == ST_FM)
1982						STps->eof = ST_EOD_1;
1983					else
1984						STps->eof = ST_EOM_OK;
1985					if (STp->block_size == 0)
1986						STbp->buffer_bytes = bytes - transfer;
1987					else
1988						STbp->buffer_bytes =
1989						    bytes - transfer * STp->block_size;
1990
1991					DEBC_printk(STp, "EOM detected (%d "
1992						    "bytes read).\n",
1993						    STbp->buffer_bytes);
1994				}
1995			}
1996			/* end of EOF, EOM, ILI test */
1997			else {	/* nonzero sense key */
1998				DEBC_printk(STp, "Tape error while reading.\n");
1999				STps->drv_block = (-1);
2000				if (STps->eof == ST_FM &&
2001				    cmdstatp->sense_hdr.sense_key == BLANK_CHECK) {
2002					DEBC_printk(STp, "Zero returned for "
2003						    "first BLANK CHECK "
2004						    "after EOF.\n");
2005					STps->eof = ST_EOD_2;	/* First BLANK_CHECK after FM */
2006				} else	/* Some other extended sense code */
2007					retval = (-EIO);
2008			}
2009
2010			if (STbp->buffer_bytes < 0)  /* Caused by bogus sense data */
2011				STbp->buffer_bytes = 0;
2012		}
2013		/* End of extended sense test */
2014		else {		/* Non-extended sense */
2015			retval = STbp->syscall_result;
2016		}
2017
2018	}
2019	/* End of error handling */
2020	else {			/* Read successful */
2021		STbp->buffer_bytes = bytes;
2022		if (STp->sili) /* In fixed block mode residual is always zero here */
2023			STbp->buffer_bytes -= STp->buffer->cmdstat.residual;
2024	}
2025
2026	if (STps->drv_block >= 0) {
2027		if (STp->block_size == 0)
2028			STps->drv_block++;
2029		else
2030			STps->drv_block += STbp->buffer_bytes / STp->block_size;
2031	}
2032	return retval;
2033}
2034
2035
2036/* Read command */
2037static ssize_t
2038st_read(struct file *filp, char __user *buf, size_t count, loff_t * ppos)
2039{
2040	ssize_t total;
2041	ssize_t retval = 0;
2042	ssize_t i, transfer;
2043	int special, do_dio = 0;
2044	struct st_request *SRpnt = NULL;
2045	struct scsi_tape *STp = filp->private_data;
2046	struct st_modedef *STm;
2047	struct st_partstat *STps;
2048	struct st_buffer *STbp = STp->buffer;
2049
2050	if (mutex_lock_interruptible(&STp->lock))
2051		return -ERESTARTSYS;
2052
2053	retval = rw_checks(STp, filp, count);
2054	if (retval || count == 0)
2055		goto out;
2056
2057	STm = &(STp->modes[STp->current_mode]);
2058	if (STp->block_size != 0 && (count % STp->block_size) != 0) {
2059		if (!STm->do_read_ahead) {
2060			retval = (-EINVAL);	/* Read must be integral number of blocks */
2061			goto out;
2062		}
2063		STp->try_dio_now = 0;  /* Direct i/o can't handle split blocks */
2064	}
2065
2066	STps = &(STp->ps[STp->partition]);
2067	if (STps->rw == ST_WRITING) {
2068		retval = flush_buffer(STp, 0);
2069		if (retval)
2070			goto out;
2071		STps->rw = ST_READING;
2072	}
2073	DEB(
2074	if (debugging && STps->eof != ST_NOEOF)
2075		st_printk(ST_DEB_MSG, STp,
2076			  "EOF/EOM flag up (%d). Bytes %d\n",
2077			  STps->eof, STbp->buffer_bytes);
2078	) /* end DEB */
2079
2080	retval = setup_buffering(STp, buf, count, 1);
2081	if (retval)
2082		goto out;
2083	do_dio = STbp->do_dio;
2084
2085	if (STbp->buffer_bytes == 0 &&
2086	    STps->eof >= ST_EOD_1) {
2087		if (STps->eof < ST_EOD) {
2088			STps->eof += 1;
2089			retval = 0;
2090			goto out;
2091		}
2092		retval = (-EIO);	/* EOM or Blank Check */
2093		goto out;
2094	}
2095
2096	if (do_dio) {
2097		/* Check the buffer writability before any tape movement. Don't alter
2098		   buffer data. */
2099		if (copy_from_user(&i, buf, 1) != 0 ||
2100		    copy_to_user(buf, &i, 1) != 0 ||
2101		    copy_from_user(&i, buf + count - 1, 1) != 0 ||
2102		    copy_to_user(buf + count - 1, &i, 1) != 0) {
2103			retval = (-EFAULT);
2104			goto out;
2105		}
2106	}
2107
2108	STps->rw = ST_READING;
2109
2110
2111	/* Loop until enough data in buffer or a special condition found */
2112	for (total = 0, special = 0; total < count && !special;) {
2113
2114		/* Get new data if the buffer is empty */
2115		if (STbp->buffer_bytes == 0) {
2116			special = read_tape(STp, count - total, &SRpnt);
2117			if (special < 0) {	/* No need to continue read */
2118				retval = special;
2119				goto out;
2120			}
2121		}
2122
2123		/* Move the data from driver buffer to user buffer */
2124		if (STbp->buffer_bytes > 0) {
2125			DEB(
2126			if (debugging && STps->eof != ST_NOEOF)
2127				st_printk(ST_DEB_MSG, STp,
2128					  "EOF up (%d). Left %d, needed %d.\n",
2129					  STps->eof, STbp->buffer_bytes,
2130					  (int)(count - total));
2131			) /* end DEB */
2132			transfer = STbp->buffer_bytes < count - total ?
2133			    STbp->buffer_bytes : count - total;
2134			if (!do_dio) {
2135				i = from_buffer(STbp, buf, transfer);
2136				if (i) {
2137					retval = i;
2138					goto out;
2139				}
2140			}
2141			buf += transfer;
2142			total += transfer;
2143		}
2144
2145		if (STp->block_size == 0)
2146			break;	/* Read only one variable length block */
2147
2148	}			/* for (total = 0, special = 0;
2149                                   total < count && !special; ) */
2150
2151	/* Change the eof state if no data from tape or buffer */
2152	if (total == 0) {
2153		if (STps->eof == ST_FM_HIT) {
2154			STps->eof = ST_FM;
2155			STps->drv_block = 0;
2156			if (STps->drv_file >= 0)
2157				STps->drv_file++;
2158		} else if (STps->eof == ST_EOD_1) {
2159			STps->eof = ST_EOD_2;
2160			STps->drv_block = 0;
2161			if (STps->drv_file >= 0)
2162				STps->drv_file++;
2163		} else if (STps->eof == ST_EOD_2)
2164			STps->eof = ST_EOD;
2165	} else if (STps->eof == ST_FM)
2166		STps->eof = ST_NOEOF;
2167	retval = total;
2168
2169 out:
2170	if (SRpnt != NULL) {
2171		st_release_request(SRpnt);
2172		SRpnt = NULL;
2173	}
2174	if (do_dio) {
2175		release_buffering(STp, 1);
2176		STbp->buffer_bytes = 0;
2177	}
2178	mutex_unlock(&STp->lock);
2179
2180	return retval;
2181}
2182
2183
2184
2185DEB(
2186/* Set the driver options */
2187static void st_log_options(struct scsi_tape * STp, struct st_modedef * STm)
2188{
2189	if (debugging) {
2190		st_printk(KERN_INFO, STp,
2191			  "Mode %d options: buffer writes: %d, "
2192			  "async writes: %d, read ahead: %d\n",
2193			  STp->current_mode, STm->do_buffer_writes,
2194			  STm->do_async_writes, STm->do_read_ahead);
2195		st_printk(KERN_INFO, STp,
2196			  "    can bsr: %d, two FMs: %d, "
2197			  "fast mteom: %d, auto lock: %d,\n",
2198			  STp->can_bsr, STp->two_fm, STp->fast_mteom,
2199			  STp->do_auto_lock);
2200		st_printk(KERN_INFO, STp,
2201			  "    defs for wr: %d, no block limits: %d, "
2202			  "partitions: %d, s2 log: %d\n",
2203			  STm->defaults_for_writes, STp->omit_blklims,
2204			  STp->can_partitions, STp->scsi2_logical);
2205		st_printk(KERN_INFO, STp,
2206			  "    sysv: %d nowait: %d sili: %d "
2207			  "nowait_filemark: %d\n",
2208			  STm->sysv, STp->immediate, STp->sili,
2209			  STp->immediate_filemark);
2210		st_printk(KERN_INFO, STp, "    debugging: %d\n", debugging);
2211	}
2212}
2213	)
2214
2215
2216static int st_set_options(struct scsi_tape *STp, long options)
2217{
2218	int value;
2219	long code;
2220	struct st_modedef *STm;
2221	struct cdev *cd0, *cd1;
2222	struct device *d0, *d1;
2223
2224	STm = &(STp->modes[STp->current_mode]);
2225	if (!STm->defined) {
2226		cd0 = STm->cdevs[0];
2227		cd1 = STm->cdevs[1];
2228		d0  = STm->devs[0];
2229		d1  = STm->devs[1];
2230		memcpy(STm, &(STp->modes[0]), sizeof(struct st_modedef));
2231		STm->cdevs[0] = cd0;
2232		STm->cdevs[1] = cd1;
2233		STm->devs[0]  = d0;
2234		STm->devs[1]  = d1;
2235		modes_defined = 1;
2236		DEBC_printk(STp, "Initialized mode %d definition from mode 0\n",
2237			    STp->current_mode);
2238	}
2239
2240	code = options & MT_ST_OPTIONS;
2241	if (code == MT_ST_BOOLEANS) {
2242		STm->do_buffer_writes = (options & MT_ST_BUFFER_WRITES) != 0;
2243		STm->do_async_writes = (options & MT_ST_ASYNC_WRITES) != 0;
2244		STm->defaults_for_writes = (options & MT_ST_DEF_WRITES) != 0;
2245		STm->do_read_ahead = (options & MT_ST_READ_AHEAD) != 0;
2246		STp->two_fm = (options & MT_ST_TWO_FM) != 0;
2247		STp->fast_mteom = (options & MT_ST_FAST_MTEOM) != 0;
2248		STp->do_auto_lock = (options & MT_ST_AUTO_LOCK) != 0;
2249		STp->can_bsr = (options & MT_ST_CAN_BSR) != 0;
2250		STp->omit_blklims = (options & MT_ST_NO_BLKLIMS) != 0;
2251		if ((STp->device)->scsi_level >= SCSI_2)
2252			STp->can_partitions = (options & MT_ST_CAN_PARTITIONS) != 0;
2253		STp->scsi2_logical = (options & MT_ST_SCSI2LOGICAL) != 0;
2254		STp->immediate = (options & MT_ST_NOWAIT) != 0;
2255		STp->immediate_filemark = (options & MT_ST_NOWAIT_EOF) != 0;
2256		STm->sysv = (options & MT_ST_SYSV) != 0;
2257		STp->sili = (options & MT_ST_SILI) != 0;
2258		DEB( debugging = (options & MT_ST_DEBUGGING) != 0;
2259		     st_log_options(STp, STm); )
2260	} else if (code == MT_ST_SETBOOLEANS || code == MT_ST_CLEARBOOLEANS) {
2261		value = (code == MT_ST_SETBOOLEANS);
2262		if ((options & MT_ST_BUFFER_WRITES) != 0)
2263			STm->do_buffer_writes = value;
2264		if ((options & MT_ST_ASYNC_WRITES) != 0)
2265			STm->do_async_writes = value;
2266		if ((options & MT_ST_DEF_WRITES) != 0)
2267			STm->defaults_for_writes = value;
2268		if ((options & MT_ST_READ_AHEAD) != 0)
2269			STm->do_read_ahead = value;
2270		if ((options & MT_ST_TWO_FM) != 0)
2271			STp->two_fm = value;
2272		if ((options & MT_ST_FAST_MTEOM) != 0)
2273			STp->fast_mteom = value;
2274		if ((options & MT_ST_AUTO_LOCK) != 0)
2275			STp->do_auto_lock = value;
2276		if ((options & MT_ST_CAN_BSR) != 0)
2277			STp->can_bsr = value;
2278		if ((options & MT_ST_NO_BLKLIMS) != 0)
2279			STp->omit_blklims = value;
2280		if ((STp->device)->scsi_level >= SCSI_2 &&
2281		    (options & MT_ST_CAN_PARTITIONS) != 0)
2282			STp->can_partitions = value;
2283		if ((options & MT_ST_SCSI2LOGICAL) != 0)
2284			STp->scsi2_logical = value;
2285		if ((options & MT_ST_NOWAIT) != 0)
2286			STp->immediate = value;
2287		if ((options & MT_ST_NOWAIT_EOF) != 0)
2288			STp->immediate_filemark = value;
2289		if ((options & MT_ST_SYSV) != 0)
2290			STm->sysv = value;
2291		if ((options & MT_ST_SILI) != 0)
2292			STp->sili = value;
2293		DEB(
2294		if ((options & MT_ST_DEBUGGING) != 0)
2295			debugging = value;
2296			st_log_options(STp, STm); )
2297	} else if (code == MT_ST_WRITE_THRESHOLD) {
2298		/* Retained for compatibility */
2299	} else if (code == MT_ST_DEF_BLKSIZE) {
2300		value = (options & ~MT_ST_OPTIONS);
2301		if (value == ~MT_ST_OPTIONS) {
2302			STm->default_blksize = (-1);
2303			DEBC_printk(STp, "Default block size disabled.\n");
2304		} else {
2305			STm->default_blksize = value;
2306			DEBC_printk(STp,"Default block size set to "
2307				    "%d bytes.\n", STm->default_blksize);
2308			if (STp->ready == ST_READY) {
2309				STp->blksize_changed = 0;
2310				set_mode_densblk(STp, STm);
2311			}
2312		}
2313	} else if (code == MT_ST_TIMEOUTS) {
2314		value = (options & ~MT_ST_OPTIONS);
2315		if ((value & MT_ST_SET_LONG_TIMEOUT) != 0) {
2316			STp->long_timeout = (value & ~MT_ST_SET_LONG_TIMEOUT) * HZ;
2317			DEBC_printk(STp, "Long timeout set to %d seconds.\n",
2318				    (value & ~MT_ST_SET_LONG_TIMEOUT));
2319		} else {
2320			blk_queue_rq_timeout(STp->device->request_queue,
2321					     value * HZ);
2322			DEBC_printk(STp, "Normal timeout set to %d seconds.\n",
2323				    value);
2324		}
2325	} else if (code == MT_ST_SET_CLN) {
2326		value = (options & ~MT_ST_OPTIONS) & 0xff;
2327		if (value != 0 &&
2328			(value < EXTENDED_SENSE_START ||
2329				value >= SCSI_SENSE_BUFFERSIZE))
2330			return (-EINVAL);
2331		STp->cln_mode = value;
2332		STp->cln_sense_mask = (options >> 8) & 0xff;
2333		STp->cln_sense_value = (options >> 16) & 0xff;
2334		st_printk(KERN_INFO, STp,
2335			  "Cleaning request mode %d, mask %02x, value %02x\n",
2336			  value, STp->cln_sense_mask, STp->cln_sense_value);
2337	} else if (code == MT_ST_DEF_OPTIONS) {
2338		code = (options & ~MT_ST_CLEAR_DEFAULT);
2339		value = (options & MT_ST_CLEAR_DEFAULT);
2340		if (code == MT_ST_DEF_DENSITY) {
2341			if (value == MT_ST_CLEAR_DEFAULT) {
2342				STm->default_density = (-1);
2343				DEBC_printk(STp,
2344					    "Density default disabled.\n");
2345			} else {
2346				STm->default_density = value & 0xff;
2347				DEBC_printk(STp, "Density default set to %x\n",
2348					    STm->default_density);
2349				if (STp->ready == ST_READY) {
2350					STp->density_changed = 0;
2351					set_mode_densblk(STp, STm);
2352				}
2353			}
2354		} else if (code == MT_ST_DEF_DRVBUFFER) {
2355			if (value == MT_ST_CLEAR_DEFAULT) {
2356				STp->default_drvbuffer = 0xff;
2357				DEBC_printk(STp,
2358					    "Drive buffer default disabled.\n");
2359			} else {
2360				STp->default_drvbuffer = value & 7;
2361				DEBC_printk(STp,
2362					    "Drive buffer default set to %x\n",
2363					    STp->default_drvbuffer);
2364				if (STp->ready == ST_READY)
2365					st_int_ioctl(STp, MTSETDRVBUFFER, STp->default_drvbuffer);
2366			}
2367		} else if (code == MT_ST_DEF_COMPRESSION) {
2368			if (value == MT_ST_CLEAR_DEFAULT) {
2369				STm->default_compression = ST_DONT_TOUCH;
2370				DEBC_printk(STp,
2371					    "Compression default disabled.\n");
2372			} else {
2373				if ((value & 0xff00) != 0) {
2374					STp->c_algo = (value & 0xff00) >> 8;
2375					DEBC_printk(STp, "Compression "
2376						    "algorithm set to 0x%x.\n",
2377						    STp->c_algo);
2378				}
2379				if ((value & 0xff) != 0xff) {
2380					STm->default_compression = (value & 1 ? ST_YES : ST_NO);
2381					DEBC_printk(STp, "Compression default "
2382						    "set to %x\n",
2383						    (value & 1));
2384					if (STp->ready == ST_READY) {
2385						STp->compression_changed = 0;
2386						st_compression(STp, (STm->default_compression == ST_YES));
2387					}
2388				}
2389			}
2390		}
2391	} else
2392		return (-EIO);
2393
2394	return 0;
2395}
2396
2397#define MODE_HEADER_LENGTH  4
2398
2399/* Mode header and page byte offsets */
2400#define MH_OFF_DATA_LENGTH     0
2401#define MH_OFF_MEDIUM_TYPE     1
2402#define MH_OFF_DEV_SPECIFIC    2
2403#define MH_OFF_BDESCS_LENGTH   3
2404#define MP_OFF_PAGE_NBR        0
2405#define MP_OFF_PAGE_LENGTH     1
2406
2407/* Mode header and page bit masks */
2408#define MH_BIT_WP              0x80
2409#define MP_MSK_PAGE_NBR        0x3f
2410
2411/* Don't return block descriptors */
2412#define MODE_SENSE_OMIT_BDESCS 0x08
2413
2414#define MODE_SELECT_PAGE_FORMAT 0x10
2415
2416/* Read a mode page into the tape buffer. The block descriptors are included
2417   if incl_block_descs is true. The page control is ored to the page number
2418   parameter, if necessary. */
2419static int read_mode_page(struct scsi_tape *STp, int page, int omit_block_descs)
2420{
2421	unsigned char cmd[MAX_COMMAND_SIZE];
2422	struct st_request *SRpnt;
2423
2424	memset(cmd, 0, MAX_COMMAND_SIZE);
2425	cmd[0] = MODE_SENSE;
2426	if (omit_block_descs)
2427		cmd[1] = MODE_SENSE_OMIT_BDESCS;
2428	cmd[2] = page;
2429	cmd[4] = 255;
2430
2431	SRpnt = st_do_scsi(NULL, STp, cmd, cmd[4], DMA_FROM_DEVICE,
2432			   STp->device->request_queue->rq_timeout, 0, 1);
2433	if (SRpnt == NULL)
2434		return (STp->buffer)->syscall_result;
2435
2436	st_release_request(SRpnt);
2437
2438	return STp->buffer->syscall_result;
2439}
2440
2441
2442/* Send the mode page in the tape buffer to the drive. Assumes that the mode data
2443   in the buffer is correctly formatted. The long timeout is used if slow is non-zero. */
2444static int write_mode_page(struct scsi_tape *STp, int page, int slow)
2445{
2446	int pgo;
2447	unsigned char cmd[MAX_COMMAND_SIZE];
2448	struct st_request *SRpnt;
2449	int timeout;
2450
2451	memset(cmd, 0, MAX_COMMAND_SIZE);
2452	cmd[0] = MODE_SELECT;
2453	cmd[1] = MODE_SELECT_PAGE_FORMAT;
2454	pgo = MODE_HEADER_LENGTH + (STp->buffer)->b_data[MH_OFF_BDESCS_LENGTH];
2455	cmd[4] = pgo + (STp->buffer)->b_data[pgo + MP_OFF_PAGE_LENGTH] + 2;
2456
2457	/* Clear reserved fields */
2458	(STp->buffer)->b_data[MH_OFF_DATA_LENGTH] = 0;
2459	(STp->buffer)->b_data[MH_OFF_MEDIUM_TYPE] = 0;
2460	(STp->buffer)->b_data[MH_OFF_DEV_SPECIFIC] &= ~MH_BIT_WP;
2461	(STp->buffer)->b_data[pgo + MP_OFF_PAGE_NBR] &= MP_MSK_PAGE_NBR;
2462
2463	timeout = slow ?
2464		STp->long_timeout : STp->device->request_queue->rq_timeout;
2465	SRpnt = st_do_scsi(NULL, STp, cmd, cmd[4], DMA_TO_DEVICE,
2466			   timeout, 0, 1);
2467	if (SRpnt == NULL)
2468		return (STp->buffer)->syscall_result;
2469
2470	st_release_request(SRpnt);
2471
2472	return STp->buffer->syscall_result;
2473}
2474
2475
2476#define COMPRESSION_PAGE        0x0f
2477#define COMPRESSION_PAGE_LENGTH 16
2478
2479#define CP_OFF_DCE_DCC          2
2480#define CP_OFF_C_ALGO           7
2481
2482#define DCE_MASK  0x80
2483#define DCC_MASK  0x40
2484#define RED_MASK  0x60
2485
2486
2487/* Control the compression with mode page 15. Algorithm not changed if zero.
2488
2489   The block descriptors are read and written because Sony SDT-7000 does not
2490   work without this (suggestion from Michael Schaefer <Michael.Schaefer@dlr.de>).
2491   Including block descriptors should not cause any harm to other drives. */
2492
2493static int st_compression(struct scsi_tape * STp, int state)
2494{
2495	int retval;
2496	int mpoffs;  /* Offset to mode page start */
2497	unsigned char *b_data = (STp->buffer)->b_data;
2498
2499	if (STp->ready != ST_READY)
2500		return (-EIO);
2501
2502	/* Read the current page contents */
2503	retval = read_mode_page(STp, COMPRESSION_PAGE, 0);
2504	if (retval) {
2505		DEBC_printk(STp, "Compression mode page not supported.\n");
2506		return (-EIO);
2507	}
2508
2509	mpoffs = MODE_HEADER_LENGTH + b_data[MH_OFF_BDESCS_LENGTH];
2510	DEBC_printk(STp, "Compression state is %d.\n",
2511		    (b_data[mpoffs + CP_OFF_DCE_DCC] & DCE_MASK ? 1 : 0));
2512
2513	/* Check if compression can be changed */
2514	if ((b_data[mpoffs + CP_OFF_DCE_DCC] & DCC_MASK) == 0) {
2515		DEBC_printk(STp, "Compression not supported.\n");
2516		return (-EIO);
2517	}
2518
2519	/* Do the change */
2520	if (state) {
2521		b_data[mpoffs + CP_OFF_DCE_DCC] |= DCE_MASK;
2522		if (STp->c_algo != 0)
2523			b_data[mpoffs + CP_OFF_C_ALGO] = STp->c_algo;
2524	}
2525	else {
2526		b_data[mpoffs + CP_OFF_DCE_DCC] &= ~DCE_MASK;
2527		if (STp->c_algo != 0)
2528			b_data[mpoffs + CP_OFF_C_ALGO] = 0; /* no compression */
2529	}
2530
2531	retval = write_mode_page(STp, COMPRESSION_PAGE, 0);
2532	if (retval) {
2533		DEBC_printk(STp, "Compression change failed.\n");
2534		return (-EIO);
2535	}
2536	DEBC_printk(STp, "Compression state changed to %d.\n", state);
2537
2538	STp->compression_changed = 1;
2539	return 0;
2540}
2541
2542
2543/* Process the load and unload commands (does unload if the load code is zero) */
2544static int do_load_unload(struct scsi_tape *STp, struct file *filp, int load_code)
2545{
2546	int retval = (-EIO), timeout;
2547	unsigned char cmd[MAX_COMMAND_SIZE];
2548	struct st_partstat *STps;
2549	struct st_request *SRpnt;
2550
2551	if (STp->ready != ST_READY && !load_code) {
2552		if (STp->ready == ST_NO_TAPE)
2553			return (-ENOMEDIUM);
2554		else
2555			return (-EIO);
2556	}
2557
2558	memset(cmd, 0, MAX_COMMAND_SIZE);
2559	cmd[0] = START_STOP;
2560	if (load_code)
2561		cmd[4] |= 1;
2562	/*
2563	 * If arg >= 1 && arg <= 6 Enhanced load/unload in HP C1553A
2564	 */
2565	if (load_code >= 1 + MT_ST_HPLOADER_OFFSET
2566	    && load_code <= 6 + MT_ST_HPLOADER_OFFSET) {
2567		DEBC_printk(STp, " Enhanced %sload slot %2d.\n",
2568			    (cmd[4]) ? "" : "un",
2569			    load_code - MT_ST_HPLOADER_OFFSET);
2570		cmd[3] = load_code - MT_ST_HPLOADER_OFFSET; /* MediaID field of C1553A */
2571	}
2572	if (STp->immediate) {
2573		cmd[1] = 1;	/* Don't wait for completion */
2574		timeout = STp->device->request_queue->rq_timeout;
2575	}
2576	else
2577		timeout = STp->long_timeout;
2578
2579	DEBC(
2580		if (!load_code)
2581			st_printk(ST_DEB_MSG, STp, "Unloading tape.\n");
2582		else
2583			st_printk(ST_DEB_MSG, STp, "Loading tape.\n");
2584		);
2585
2586	SRpnt = st_do_scsi(NULL, STp, cmd, 0, DMA_NONE,
2587			   timeout, MAX_RETRIES, 1);
2588	if (!SRpnt)
2589		return (STp->buffer)->syscall_result;
2590
2591	retval = (STp->buffer)->syscall_result;
2592	st_release_request(SRpnt);
2593
2594	if (!retval) {	/* SCSI command successful */
2595
2596		if (!load_code) {
2597			STp->rew_at_close = 0;
2598			STp->ready = ST_NO_TAPE;
2599		}
2600		else {
2601			STp->rew_at_close = STp->autorew_dev;
2602			retval = check_tape(STp, filp);
2603			if (retval > 0)
2604				retval = 0;
2605		}
2606	}
2607	else {
2608		STps = &(STp->ps[STp->partition]);
2609		STps->drv_file = STps->drv_block = (-1);
2610	}
2611
2612	return retval;
2613}
2614
2615#if DEBUG
2616#define ST_DEB_FORWARD  0
2617#define ST_DEB_BACKWARD 1
2618static void deb_space_print(struct scsi_tape *STp, int direction, char *units, unsigned char *cmd)
2619{
2620	s32 sc;
2621
2622	if (!debugging)
2623		return;
2624
2625	sc = cmd[2] & 0x80 ? 0xff000000 : 0;
2626	sc |= (cmd[2] << 16) | (cmd[3] << 8) | cmd[4];
2627	if (direction)
2628		sc = -sc;
2629	st_printk(ST_DEB_MSG, STp, "Spacing tape %s over %d %s.\n",
2630		  direction ? "backward" : "forward", sc, units);
2631}
2632#else
2633#define ST_DEB_FORWARD  0
2634#define ST_DEB_BACKWARD 1
2635static void deb_space_print(struct scsi_tape *STp, int direction, char *units, unsigned char *cmd) {}
2636#endif
2637
2638
2639/* Internal ioctl function */
2640static int st_int_ioctl(struct scsi_tape *STp, unsigned int cmd_in, unsigned long arg)
2641{
2642	int timeout;
2643	long ltmp;
2644	int ioctl_result;
2645	int chg_eof = 1;
2646	unsigned char cmd[MAX_COMMAND_SIZE];
2647	struct st_request *SRpnt;
2648	struct st_partstat *STps;
2649	int fileno, blkno, at_sm, undone;
2650	int datalen = 0, direction = DMA_NONE;
2651
2652	WARN_ON(STp->buffer->do_dio != 0);
2653	if (STp->ready != ST_READY) {
2654		if (STp->ready == ST_NO_TAPE)
2655			return (-ENOMEDIUM);
2656		else
2657			return (-EIO);
2658	}
2659	timeout = STp->long_timeout;
2660	STps = &(STp->ps[STp->partition]);
2661	fileno = STps->drv_file;
2662	blkno = STps->drv_block;
2663	at_sm = STps->at_sm;
2664
2665	memset(cmd, 0, MAX_COMMAND_SIZE);
2666	switch (cmd_in) {
2667	case MTFSFM:
2668		chg_eof = 0;	/* Changed from the FSF after this */
2669	case MTFSF:
2670		cmd[0] = SPACE;
2671		cmd[1] = 0x01;	/* Space FileMarks */
2672		cmd[2] = (arg >> 16);
2673		cmd[3] = (arg >> 8);
2674		cmd[4] = arg;
2675		deb_space_print(STp, ST_DEB_FORWARD, "filemarks", cmd);
2676		if (fileno >= 0)
2677			fileno += arg;
2678		blkno = 0;
2679		at_sm &= (arg == 0);
2680		break;
2681	case MTBSFM:
2682		chg_eof = 0;	/* Changed from the FSF after this */
2683	case MTBSF:
2684		cmd[0] = SPACE;
2685		cmd[1] = 0x01;	/* Space FileMarks */
2686		ltmp = (-arg);
2687		cmd[2] = (ltmp >> 16);
2688		cmd[3] = (ltmp >> 8);
2689		cmd[4] = ltmp;
2690		deb_space_print(STp, ST_DEB_BACKWARD, "filemarks", cmd);
2691		if (fileno >= 0)
2692			fileno -= arg;
2693		blkno = (-1);	/* We can't know the block number */
2694		at_sm &= (arg == 0);
2695		break;
2696	case MTFSR:
2697		cmd[0] = SPACE;
2698		cmd[1] = 0x00;	/* Space Blocks */
2699		cmd[2] = (arg >> 16);
2700		cmd[3] = (arg >> 8);
2701		cmd[4] = arg;
2702		deb_space_print(STp, ST_DEB_FORWARD, "blocks", cmd);
2703		if (blkno >= 0)
2704			blkno += arg;
2705		at_sm &= (arg == 0);
2706		break;
2707	case MTBSR:
2708		cmd[0] = SPACE;
2709		cmd[1] = 0x00;	/* Space Blocks */
2710		ltmp = (-arg);
2711		cmd[2] = (ltmp >> 16);
2712		cmd[3] = (ltmp >> 8);
2713		cmd[4] = ltmp;
2714		deb_space_print(STp, ST_DEB_BACKWARD, "blocks", cmd);
2715		if (blkno >= 0)
2716			blkno -= arg;
2717		at_sm &= (arg == 0);
2718		break;
2719	case MTFSS:
2720		cmd[0] = SPACE;
2721		cmd[1] = 0x04;	/* Space Setmarks */
2722		cmd[2] = (arg >> 16);
2723		cmd[3] = (arg >> 8);
2724		cmd[4] = arg;
2725		deb_space_print(STp, ST_DEB_FORWARD, "setmarks", cmd);
2726		if (arg != 0) {
2727			blkno = fileno = (-1);
2728			at_sm = 1;
2729		}
2730		break;
2731	case MTBSS:
2732		cmd[0] = SPACE;
2733		cmd[1] = 0x04;	/* Space Setmarks */
2734		ltmp = (-arg);
2735		cmd[2] = (ltmp >> 16);
2736		cmd[3] = (ltmp >> 8);
2737		cmd[4] = ltmp;
2738		deb_space_print(STp, ST_DEB_BACKWARD, "setmarks", cmd);
2739		if (arg != 0) {
2740			blkno = fileno = (-1);
2741			at_sm = 1;
2742		}
2743		break;
2744	case MTWEOF:
2745	case MTWEOFI:
2746	case MTWSM:
2747		if (STp->write_prot)
2748			return (-EACCES);
2749		cmd[0] = WRITE_FILEMARKS;
2750		if (cmd_in == MTWSM)
2751			cmd[1] = 2;
2752		if (cmd_in == MTWEOFI ||
2753		    (cmd_in == MTWEOF && STp->immediate_filemark))
2754			cmd[1] |= 1;
2755		cmd[2] = (arg >> 16);
2756		cmd[3] = (arg >> 8);
2757		cmd[4] = arg;
2758		timeout = STp->device->request_queue->rq_timeout;
2759		DEBC(
2760			if (cmd_in != MTWSM)
2761				st_printk(ST_DEB_MSG, STp,
2762					  "Writing %d filemarks.\n",
2763					  cmd[2] * 65536 +
2764					  cmd[3] * 256 +
2765					  cmd[4]);
2766			else
2767				st_printk(ST_DEB_MSG, STp,
2768					  "Writing %d setmarks.\n",
2769					  cmd[2] * 65536 +
2770					  cmd[3] * 256 +
2771					  cmd[4]);
2772		)
2773		if (fileno >= 0)
2774			fileno += arg;
2775		blkno = 0;
2776		at_sm = (cmd_in == MTWSM);
2777		break;
2778	case MTREW:
2779		cmd[0] = REZERO_UNIT;
2780		if (STp->immediate) {
2781			cmd[1] = 1;	/* Don't wait for completion */
2782			timeout = STp->device->request_queue->rq_timeout;
2783		}
2784		DEBC_printk(STp, "Rewinding tape.\n");
2785		fileno = blkno = at_sm = 0;
2786		break;
2787	case MTNOP:
2788		DEBC_printk(STp, "No op on tape.\n");
2789		return 0;	/* Should do something ? */
2790		break;
2791	case MTRETEN:
2792		cmd[0] = START_STOP;
2793		if (STp->immediate) {
2794			cmd[1] = 1;	/* Don't wait for completion */
2795			timeout = STp->device->request_queue->rq_timeout;
2796		}
2797		cmd[4] = 3;
2798		DEBC_printk(STp, "Retensioning tape.\n");
2799		fileno = blkno = at_sm = 0;
2800		break;
2801	case MTEOM:
2802		if (!STp->fast_mteom) {
2803			/* space to the end of tape */
2804			ioctl_result = st_int_ioctl(STp, MTFSF, 0x7fffff);
2805			fileno = STps->drv_file;
2806			if (STps->eof >= ST_EOD_1)
2807				return 0;
2808			/* The next lines would hide the number of spaced FileMarks
2809			   That's why I inserted the previous lines. I had no luck
2810			   with detecting EOM with FSF, so we go now to EOM.
2811			   Joerg Weule */
2812		} else
2813			fileno = (-1);
2814		cmd[0] = SPACE;
2815		cmd[1] = 3;
2816		DEBC_printk(STp, "Spacing to end of recorded medium.\n");
2817		blkno = -1;
2818		at_sm = 0;
2819		break;
2820	case MTERASE:
2821		if (STp->write_prot)
2822			return (-EACCES);
2823		cmd[0] = ERASE;
2824		cmd[1] = (arg ? 1 : 0);	/* Long erase with non-zero argument */
2825		if (STp->immediate) {
2826			cmd[1] |= 2;	/* Don't wait for completion */
2827			timeout = STp->device->request_queue->rq_timeout;
2828		}
2829		else
2830			timeout = STp->long_timeout * 8;
2831
2832		DEBC_printk(STp, "Erasing tape.\n");
2833		fileno = blkno = at_sm = 0;
2834		break;
2835	case MTSETBLK:		/* Set block length */
2836	case MTSETDENSITY:	/* Set tape density */
2837	case MTSETDRVBUFFER:	/* Set drive buffering */
2838	case SET_DENS_AND_BLK:	/* Set density and block size */
2839		chg_eof = 0;
2840		if (STp->dirty || (STp->buffer)->buffer_bytes != 0)
2841			return (-EIO);	/* Not allowed if data in buffer */
2842		if ((cmd_in == MTSETBLK || cmd_in == SET_DENS_AND_BLK) &&
2843		    (arg & MT_ST_BLKSIZE_MASK) != 0 &&
2844		    STp->max_block > 0 &&
2845		    ((arg & MT_ST_BLKSIZE_MASK) < STp->min_block ||
2846		     (arg & MT_ST_BLKSIZE_MASK) > STp->max_block)) {
2847			st_printk(KERN_WARNING, STp, "Illegal block size.\n");
2848			return (-EINVAL);
2849		}
2850		cmd[0] = MODE_SELECT;
2851		if ((STp->use_pf & USE_PF))
2852			cmd[1] = MODE_SELECT_PAGE_FORMAT;
2853		cmd[4] = datalen = 12;
2854		direction = DMA_TO_DEVICE;
2855
2856		memset((STp->buffer)->b_data, 0, 12);
2857		if (cmd_in == MTSETDRVBUFFER)
2858			(STp->buffer)->b_data[2] = (arg & 7) << 4;
2859		else
2860			(STp->buffer)->b_data[2] =
2861			    STp->drv_buffer << 4;
2862		(STp->buffer)->b_data[3] = 8;	/* block descriptor length */
2863		if (cmd_in == MTSETDENSITY) {
2864			(STp->buffer)->b_data[4] = arg;
2865			STp->density_changed = 1;	/* At least we tried ;-) */
2866		} else if (cmd_in == SET_DENS_AND_BLK)
2867			(STp->buffer)->b_data[4] = arg >> 24;
2868		else
2869			(STp->buffer)->b_data[4] = STp->density;
2870		if (cmd_in == MTSETBLK || cmd_in == SET_DENS_AND_BLK) {
2871			ltmp = arg & MT_ST_BLKSIZE_MASK;
2872			if (cmd_in == MTSETBLK)
2873				STp->blksize_changed = 1; /* At least we tried ;-) */
2874		} else
2875			ltmp = STp->block_size;
2876		(STp->buffer)->b_data[9] = (ltmp >> 16);
2877		(STp->buffer)->b_data[10] = (ltmp >> 8);
2878		(STp->buffer)->b_data[11] = ltmp;
2879		timeout = STp->device->request_queue->rq_timeout;
2880		DEBC(
2881			if (cmd_in == MTSETBLK || cmd_in == SET_DENS_AND_BLK)
2882				st_printk(ST_DEB_MSG, STp,
2883					  "Setting block size to %d bytes.\n",
2884					  (STp->buffer)->b_data[9] * 65536 +
2885					  (STp->buffer)->b_data[10] * 256 +
2886					  (STp->buffer)->b_data[11]);
2887			if (cmd_in == MTSETDENSITY || cmd_in == SET_DENS_AND_BLK)
2888				st_printk(ST_DEB_MSG, STp,
2889					  "Setting density code to %x.\n",
2890					  (STp->buffer)->b_data[4]);
2891			if (cmd_in == MTSETDRVBUFFER)
2892				st_printk(ST_DEB_MSG, STp,
2893					  "Setting drive buffer code to %d.\n",
2894					  ((STp->buffer)->b_data[2] >> 4) & 7);
2895		)
2896		break;
2897	default:
2898		return (-ENOSYS);
2899	}
2900
2901	SRpnt = st_do_scsi(NULL, STp, cmd, datalen, direction,
2902			   timeout, MAX_RETRIES, 1);
2903	if (!SRpnt)
2904		return (STp->buffer)->syscall_result;
2905
2906	ioctl_result = (STp->buffer)->syscall_result;
2907
2908	if (!ioctl_result) {	/* SCSI command successful */
2909		st_release_request(SRpnt);
2910		SRpnt = NULL;
2911		STps->drv_block = blkno;
2912		STps->drv_file = fileno;
2913		STps->at_sm = at_sm;
2914
2915		if (cmd_in == MTBSFM)
2916			ioctl_result = st_int_ioctl(STp, MTFSF, 1);
2917		else if (cmd_in == MTFSFM)
2918			ioctl_result = st_int_ioctl(STp, MTBSF, 1);
2919
2920		if (cmd_in == MTSETBLK || cmd_in == SET_DENS_AND_BLK) {
2921			STp->block_size = arg & MT_ST_BLKSIZE_MASK;
2922			if (STp->block_size != 0) {
2923				(STp->buffer)->buffer_blocks =
2924				    (STp->buffer)->buffer_size / STp->block_size;
2925			}
2926			(STp->buffer)->buffer_bytes = (STp->buffer)->read_pointer = 0;
2927			if (cmd_in == SET_DENS_AND_BLK)
2928				STp->density = arg >> MT_ST_DENSITY_SHIFT;
2929		} else if (cmd_in == MTSETDRVBUFFER)
2930			STp->drv_buffer = (arg & 7);
2931		else if (cmd_in == MTSETDENSITY)
2932			STp->density = arg;
2933
2934		if (cmd_in == MTEOM)
2935			STps->eof = ST_EOD;
2936		else if (cmd_in == MTFSF)
2937			STps->eof = ST_FM;
2938		else if (chg_eof)
2939			STps->eof = ST_NOEOF;
2940
2941		if (cmd_in == MTWEOF || cmd_in == MTWEOFI)
2942			STps->rw = ST_IDLE;  /* prevent automatic WEOF at close */
2943	} else { /* SCSI command was not completely successful. Don't return
2944                    from this block without releasing the SCSI command block! */
2945		struct st_cmdstatus *cmdstatp = &STp->buffer->cmdstat;
2946
2947		if (cmdstatp->flags & SENSE_EOM) {
2948			if (cmd_in != MTBSF && cmd_in != MTBSFM &&
2949			    cmd_in != MTBSR && cmd_in != MTBSS)
2950				STps->eof = ST_EOM_OK;
2951			STps->drv_block = 0;
2952		}
2953
2954		if (cmdstatp->remainder_valid)
2955			undone = (int)cmdstatp->uremainder64;
2956		else
2957			undone = 0;
2958
2959		if ((cmd_in == MTWEOF || cmd_in == MTWEOFI) &&
2960		    cmdstatp->have_sense &&
2961		    (cmdstatp->flags & SENSE_EOM)) {
2962			if (cmdstatp->sense_hdr.sense_key == NO_SENSE ||
2963			    cmdstatp->sense_hdr.sense_key == RECOVERED_ERROR) {
2964				ioctl_result = 0;	/* EOF(s) written successfully at EOM */
2965				STps->eof = ST_NOEOF;
2966			} else {  /* Writing EOF(s) failed */
2967				if (fileno >= 0)
2968					fileno -= undone;
2969				if (undone < arg)
2970					STps->eof = ST_NOEOF;
2971			}
2972			STps->drv_file = fileno;
2973		} else if ((cmd_in == MTFSF) || (cmd_in == MTFSFM)) {
2974			if (fileno >= 0)
2975				STps->drv_file = fileno - undone;
2976			else
2977				STps->drv_file = fileno;
2978			STps->drv_block = -1;
2979			STps->eof = ST_NOEOF;
2980		} else if ((cmd_in == MTBSF) || (cmd_in == MTBSFM)) {
2981			if (arg > 0 && undone < 0)  /* Some drives get this wrong */
2982				undone = (-undone);
2983			if (STps->drv_file >= 0)
2984				STps->drv_file = fileno + undone;
2985			STps->drv_block = 0;
2986			STps->eof = ST_NOEOF;
2987		} else if (cmd_in == MTFSR) {
2988			if (cmdstatp->flags & SENSE_FMK) {	/* Hit filemark */
2989				if (STps->drv_file >= 0)
2990					STps->drv_file++;
2991				STps->drv_block = 0;
2992				STps->eof = ST_FM;
2993			} else {
2994				if (blkno >= undone)
2995					STps->drv_block = blkno - undone;
2996				else
2997					STps->drv_block = (-1);
2998				STps->eof = ST_NOEOF;
2999			}
3000		} else if (cmd_in == MTBSR) {
3001			if (cmdstatp->flags & SENSE_FMK) {	/* Hit filemark */
3002				STps->drv_file--;
3003				STps->drv_block = (-1);
3004			} else {
3005				if (arg > 0 && undone < 0)  /* Some drives get this wrong */
3006					undone = (-undone);
3007				if (STps->drv_block >= 0)
3008					STps->drv_block = blkno + undone;
3009			}
3010			STps->eof = ST_NOEOF;
3011		} else if (cmd_in == MTEOM) {
3012			STps->drv_file = (-1);
3013			STps->drv_block = (-1);
3014			STps->eof = ST_EOD;
3015		} else if (cmd_in == MTSETBLK ||
3016			   cmd_in == MTSETDENSITY ||
3017			   cmd_in == MTSETDRVBUFFER ||
3018			   cmd_in == SET_DENS_AND_BLK) {
3019			if (cmdstatp->sense_hdr.sense_key == ILLEGAL_REQUEST &&
3020			    !(STp->use_pf & PF_TESTED)) {
3021				/* Try the other possible state of Page Format if not
3022				   already tried */
3023				STp->use_pf = (STp->use_pf ^ USE_PF) | PF_TESTED;
3024				st_release_request(SRpnt);
3025				SRpnt = NULL;
3026				return st_int_ioctl(STp, cmd_in, arg);
3027			}
3028		} else if (chg_eof)
3029			STps->eof = ST_NOEOF;
3030
3031		if (cmdstatp->sense_hdr.sense_key == BLANK_CHECK)
3032			STps->eof = ST_EOD;
3033
3034		st_release_request(SRpnt);
3035		SRpnt = NULL;
3036	}
3037
3038	return ioctl_result;
3039}
3040
3041
3042/* Get the tape position. If bt == 2, arg points into a kernel space mt_loc
3043   structure. */
3044
3045static int get_location(struct scsi_tape *STp, unsigned int *block, int *partition,
3046			int logical)
3047{
3048	int result;
3049	unsigned char scmd[MAX_COMMAND_SIZE];
3050	struct st_request *SRpnt;
3051
3052	if (STp->ready != ST_READY)
3053		return (-EIO);
3054
3055	memset(scmd, 0, MAX_COMMAND_SIZE);
3056	if ((STp->device)->scsi_level < SCSI_2) {
3057		scmd[0] = QFA_REQUEST_BLOCK;
3058		scmd[4] = 3;
3059	} else {
3060		scmd[0] = READ_POSITION;
3061		if (!logical && !STp->scsi2_logical)
3062			scmd[1] = 1;
3063	}
3064	SRpnt = st_do_scsi(NULL, STp, scmd, 20, DMA_FROM_DEVICE,
3065			   STp->device->request_queue->rq_timeout,
3066			   MAX_READY_RETRIES, 1);
3067	if (!SRpnt)
3068		return (STp->buffer)->syscall_result;
3069
3070	if ((STp->buffer)->syscall_result != 0 ||
3071	    (STp->device->scsi_level >= SCSI_2 &&
3072	     ((STp->buffer)->b_data[0] & 4) != 0)) {
3073		*block = *partition = 0;
3074		DEBC_printk(STp, " Can't read tape position.\n");
3075		result = (-EIO);
3076	} else {
3077		result = 0;
3078		if ((STp->device)->scsi_level < SCSI_2) {
3079			*block = ((STp->buffer)->b_data[0] << 16)
3080			    + ((STp->buffer)->b_data[1] << 8)
3081			    + (STp->buffer)->b_data[2];
3082			*partition = 0;
3083		} else {
3084			*block = ((STp->buffer)->b_data[4] << 24)
3085			    + ((STp->buffer)->b_data[5] << 16)
3086			    + ((STp->buffer)->b_data[6] << 8)
3087			    + (STp->buffer)->b_data[7];
3088			*partition = (STp->buffer)->b_data[1];
3089			if (((STp->buffer)->b_data[0] & 0x80) &&
3090			    (STp->buffer)->b_data[1] == 0)	/* BOP of partition 0 */
3091				STp->ps[0].drv_block = STp->ps[0].drv_file = 0;
3092		}
3093		DEBC_printk(STp, "Got tape pos. blk %d part %d.\n",
3094			    *block, *partition);
3095	}
3096	st_release_request(SRpnt);
3097	SRpnt = NULL;
3098
3099	return result;
3100}
3101
3102
3103/* Set the tape block and partition. Negative partition means that only the
3104   block should be set in vendor specific way. */
3105static int set_location(struct scsi_tape *STp, unsigned int block, int partition,
3106			int logical)
3107{
3108	struct st_partstat *STps;
3109	int result, p;
3110	unsigned int blk;
3111	int timeout;
3112	unsigned char scmd[MAX_COMMAND_SIZE];
3113	struct st_request *SRpnt;
3114
3115	if (STp->ready != ST_READY)
3116		return (-EIO);
3117	timeout = STp->long_timeout;
3118	STps = &(STp->ps[STp->partition]);
3119
3120	DEBC_printk(STp, "Setting block to %d and partition to %d.\n",
3121		    block, partition);
3122	DEB(if (partition < 0)
3123		return (-EIO); )
3124
3125	/* Update the location at the partition we are leaving */
3126	if ((!STp->can_partitions && partition != 0) ||
3127	    partition >= ST_NBR_PARTITIONS)
3128		return (-EINVAL);
3129	if (partition != STp->partition) {
3130		if (get_location(STp, &blk, &p, 1))
3131			STps->last_block_valid = 0;
3132		else {
3133			STps->last_block_valid = 1;
3134			STps->last_block_visited = blk;
3135			DEBC_printk(STp, "Visited block %d for "
3136				    "partition %d saved.\n",
3137				    blk, STp->partition);
3138		}
3139	}
3140
3141	memset(scmd, 0, MAX_COMMAND_SIZE);
3142	if ((STp->device)->scsi_level < SCSI_2) {
3143		scmd[0] = QFA_SEEK_BLOCK;
3144		scmd[2] = (block >> 16);
3145		scmd[3] = (block >> 8);
3146		scmd[4] = block;
3147		scmd[5] = 0;
3148	} else {
3149		scmd[0] = SEEK_10;
3150		scmd[3] = (block >> 24);
3151		scmd[4] = (block >> 16);
3152		scmd[5] = (block >> 8);
3153		scmd[6] = block;
3154		if (!logical && !STp->scsi2_logical)
3155			scmd[1] = 4;
3156		if (STp->partition != partition) {
3157			scmd[1] |= 2;
3158			scmd[8] = partition;
3159			DEBC_printk(STp, "Trying to change partition "
3160				    "from %d to %d\n", STp->partition,
3161				    partition);
3162		}
3163	}
3164	if (STp->immediate) {
3165		scmd[1] |= 1;		/* Don't wait for completion */
3166		timeout = STp->device->request_queue->rq_timeout;
3167	}
3168
3169	SRpnt = st_do_scsi(NULL, STp, scmd, 0, DMA_NONE,
3170			   timeout, MAX_READY_RETRIES, 1);
3171	if (!SRpnt)
3172		return (STp->buffer)->syscall_result;
3173
3174	STps->drv_block = STps->drv_file = (-1);
3175	STps->eof = ST_NOEOF;
3176	if ((STp->buffer)->syscall_result != 0) {
3177		result = (-EIO);
3178		if (STp->can_partitions &&
3179		    (STp->device)->scsi_level >= SCSI_2 &&
3180		    (p = find_partition(STp)) >= 0)
3181			STp->partition = p;
3182	} else {
3183		if (STp->can_partitions) {
3184			STp->partition = partition;
3185			STps = &(STp->ps[partition]);
3186			if (!STps->last_block_valid ||
3187			    STps->last_block_visited != block) {
3188				STps->at_sm = 0;
3189				STps->rw = ST_IDLE;
3190			}
3191		} else
3192			STps->at_sm = 0;
3193		if (block == 0)
3194			STps->drv_block = STps->drv_file = 0;
3195		result = 0;
3196	}
3197
3198	st_release_request(SRpnt);
3199	SRpnt = NULL;
3200
3201	return result;
3202}
3203
3204
3205/* Find the current partition number for the drive status. Called from open and
3206   returns either partition number of negative error code. */
3207static int find_partition(struct scsi_tape *STp)
3208{
3209	int i, partition;
3210	unsigned int block;
3211
3212	if ((i = get_location(STp, &block, &partition, 1)) < 0)
3213		return i;
3214	if (partition >= ST_NBR_PARTITIONS)
3215		return (-EIO);
3216	return partition;
3217}
3218
3219
3220/* Change the partition if necessary */
3221static int switch_partition(struct scsi_tape *STp)
3222{
3223	struct st_partstat *STps;
3224
3225	if (STp->partition == STp->new_partition)
3226		return 0;
3227	STps = &(STp->ps[STp->new_partition]);
3228	if (!STps->last_block_valid)
3229		STps->last_block_visited = 0;
3230	return set_location(STp, STps->last_block_visited, STp->new_partition, 1);
3231}
3232
3233/* Functions for reading and writing the medium partition mode page. */
3234
3235#define PART_PAGE   0x11
3236#define PART_PAGE_FIXED_LENGTH 8
3237
3238#define PP_OFF_MAX_ADD_PARTS   2
3239#define PP_OFF_NBR_ADD_PARTS   3
3240#define PP_OFF_FLAGS           4
3241#define PP_OFF_PART_UNITS      6
3242#define PP_OFF_RESERVED        7
3243
3244#define PP_BIT_IDP             0x20
3245#define PP_MSK_PSUM_MB         0x10
3246
3247/* Get the number of partitions on the tape. As a side effect reads the
3248   mode page into the tape buffer. */
3249static int nbr_partitions(struct scsi_tape *STp)
3250{
3251	int result;
3252
3253	if (STp->ready != ST_READY)
3254		return (-EIO);
3255
3256	result = read_mode_page(STp, PART_PAGE, 1);
3257
3258	if (result) {
3259		DEBC_printk(STp, "Can't read medium partition page.\n");
3260		result = (-EIO);
3261	} else {
3262		result = (STp->buffer)->b_data[MODE_HEADER_LENGTH +
3263					      PP_OFF_NBR_ADD_PARTS] + 1;
3264		DEBC_printk(STp, "Number of partitions %d.\n", result);
3265	}
3266
3267	return result;
3268}
3269
3270
3271/* Partition the tape into two partitions if size > 0 or one partition if
3272   size == 0.
3273
3274   The block descriptors are read and written because Sony SDT-7000 does not
3275   work without this (suggestion from Michael Schaefer <Michael.Schaefer@dlr.de>).
3276
3277   My HP C1533A drive returns only one partition size field. This is used to
3278   set the size of partition 1. There is no size field for the default partition.
3279   Michael Schaefer's Sony SDT-7000 returns two descriptors and the second is
3280   used to set the size of partition 1 (this is what the SCSI-3 standard specifies).
3281   The following algorithm is used to accommodate both drives: if the number of
3282   partition size fields is greater than the maximum number of additional partitions
3283   in the mode page, the second field is used. Otherwise the first field is used.
3284
3285   For Seagate DDS drives the page length must be 8 when no partitions is defined
3286   and 10 when 1 partition is defined (information from Eric Lee Green). This is
3287   is acceptable also to some other old drives and enforced if the first partition
3288   size field is used for the first additional partition size.
3289 */
3290static int partition_tape(struct scsi_tape *STp, int size)
3291{
3292	int result;
3293	int pgo, psd_cnt, psdo;
3294	unsigned char *bp;
3295
3296	result = read_mode_page(STp, PART_PAGE, 0);
3297	if (result) {
3298		DEBC_printk(STp, "Can't read partition mode page.\n");
3299		return result;
3300	}
3301	/* The mode page is in the buffer. Let's modify it and write it. */
3302	bp = (STp->buffer)->b_data;
3303	pgo = MODE_HEADER_LENGTH + bp[MH_OFF_BDESCS_LENGTH];
3304	DEBC_printk(STp, "Partition page length is %d bytes.\n",
3305		    bp[pgo + MP_OFF_PAGE_LENGTH] + 2);
3306
3307	psd_cnt = (bp[pgo + MP_OFF_PAGE_LENGTH] + 2 - PART_PAGE_FIXED_LENGTH) / 2;
3308	psdo = pgo + PART_PAGE_FIXED_LENGTH;
3309	if (psd_cnt > bp[pgo + PP_OFF_MAX_ADD_PARTS]) {
3310		bp[psdo] = bp[psdo + 1] = 0xff;  /* Rest of the tape */
3311		psdo += 2;
3312	}
3313	memset(bp + psdo, 0, bp[pgo + PP_OFF_NBR_ADD_PARTS] * 2);
3314
3315	DEBC_printk(STp, "psd_cnt %d, max.parts %d, nbr_parts %d\n",
3316		    psd_cnt, bp[pgo + PP_OFF_MAX_ADD_PARTS],
3317		    bp[pgo + PP_OFF_NBR_ADD_PARTS]);
3318
3319	if (size <= 0) {
3320		bp[pgo + PP_OFF_NBR_ADD_PARTS] = 0;
3321		if (psd_cnt <= bp[pgo + PP_OFF_MAX_ADD_PARTS])
3322		    bp[pgo + MP_OFF_PAGE_LENGTH] = 6;
3323		DEBC_printk(STp, "Formatting tape with one partition.\n");
3324	} else {
3325		bp[psdo] = (size >> 8) & 0xff;
3326		bp[psdo + 1] = size & 0xff;
3327		bp[pgo + 3] = 1;
3328		if (bp[pgo + MP_OFF_PAGE_LENGTH] < 8)
3329		    bp[pgo + MP_OFF_PAGE_LENGTH] = 8;
3330		DEBC_printk(STp, "Formatting tape with two partitions "
3331			    "(1 = %d MB).\n", size);
3332	}
3333	bp[pgo + PP_OFF_PART_UNITS] = 0;
3334	bp[pgo + PP_OFF_RESERVED] = 0;
3335	bp[pgo + PP_OFF_FLAGS] = PP_BIT_IDP | PP_MSK_PSUM_MB;
3336
3337	result = write_mode_page(STp, PART_PAGE, 1);
3338	if (result) {
3339		st_printk(KERN_INFO, STp, "Partitioning of tape failed.\n");
3340		result = (-EIO);
3341	}
3342
3343	return result;
3344}
3345
3346
3347
3348/* The ioctl command */
3349static long st_ioctl(struct file *file, unsigned int cmd_in, unsigned long arg)
3350{
3351	int i, cmd_nr, cmd_type, bt;
3352	int retval = 0;
3353	unsigned int blk;
3354	struct scsi_tape *STp = file->private_data;
3355	struct st_modedef *STm;
3356	struct st_partstat *STps;
3357	void __user *p = (void __user *)arg;
3358
3359	if (mutex_lock_interruptible(&STp->lock))
3360		return -ERESTARTSYS;
3361
3362	DEB(
3363	if (debugging && !STp->in_use) {
3364		st_printk(ST_DEB_MSG, STp, "Incorrect device.\n");
3365		retval = (-EIO);
3366		goto out;
3367	} ) /* end DEB */
3368
3369	STm = &(STp->modes[STp->current_mode]);
3370	STps = &(STp->ps[STp->partition]);
3371
3372	/*
3373	 * If we are in the middle of error recovery, don't let anyone
3374	 * else try and use this device.  Also, if error recovery fails, it
3375	 * may try and take the device offline, in which case all further
3376	 * access to the device is prohibited.
3377	 */
3378	retval = scsi_ioctl_block_when_processing_errors(STp->device, cmd_in,
3379			file->f_flags & O_NDELAY);
3380	if (retval)
3381		goto out;
3382
3383	cmd_type = _IOC_TYPE(cmd_in);
3384	cmd_nr = _IOC_NR(cmd_in);
3385
3386	if (cmd_type == _IOC_TYPE(MTIOCTOP) && cmd_nr == _IOC_NR(MTIOCTOP)) {
3387		struct mtop mtc;
3388
3389		if (_IOC_SIZE(cmd_in) != sizeof(mtc)) {
3390			retval = (-EINVAL);
3391			goto out;
3392		}
3393
3394		i = copy_from_user(&mtc, p, sizeof(struct mtop));
3395		if (i) {
3396			retval = (-EFAULT);
3397			goto out;
3398		}
3399
3400		if (mtc.mt_op == MTSETDRVBUFFER && !capable(CAP_SYS_ADMIN)) {
3401			st_printk(KERN_WARNING, STp,
3402				  "MTSETDRVBUFFER only allowed for root.\n");
3403			retval = (-EPERM);
3404			goto out;
3405		}
3406		if (!STm->defined &&
3407		    (mtc.mt_op != MTSETDRVBUFFER &&
3408		     (mtc.mt_count & MT_ST_OPTIONS) == 0)) {
3409			retval = (-ENXIO);
3410			goto out;
3411		}
3412
3413		if (!STp->pos_unknown) {
3414
3415			if (STps->eof == ST_FM_HIT) {
3416				if (mtc.mt_op == MTFSF || mtc.mt_op == MTFSFM ||
3417                                    mtc.mt_op == MTEOM) {
3418					mtc.mt_count -= 1;
3419					if (STps->drv_file >= 0)
3420						STps->drv_file += 1;
3421				} else if (mtc.mt_op == MTBSF || mtc.mt_op == MTBSFM) {
3422					mtc.mt_count += 1;
3423					if (STps->drv_file >= 0)
3424						STps->drv_file += 1;
3425				}
3426			}
3427
3428			if (mtc.mt_op == MTSEEK) {
3429				/* Old position must be restored if partition will be
3430                                   changed */
3431				i = !STp->can_partitions ||
3432				    (STp->new_partition != STp->partition);
3433			} else {
3434				i = mtc.mt_op == MTREW || mtc.mt_op == MTOFFL ||
3435				    mtc.mt_op == MTRETEN || mtc.mt_op == MTEOM ||
3436				    mtc.mt_op == MTLOCK || mtc.mt_op == MTLOAD ||
3437				    mtc.mt_op == MTFSF || mtc.mt_op == MTFSFM ||
3438				    mtc.mt_op == MTBSF || mtc.mt_op == MTBSFM ||
3439				    mtc.mt_op == MTCOMPRESSION;
3440			}
3441			i = flush_buffer(STp, i);
3442			if (i < 0) {
3443				retval = i;
3444				goto out;
3445			}
3446			if (STps->rw == ST_WRITING &&
3447			    (mtc.mt_op == MTREW || mtc.mt_op == MTOFFL ||
3448			     mtc.mt_op == MTSEEK ||
3449			     mtc.mt_op == MTBSF || mtc.mt_op == MTBSFM)) {
3450				i = st_int_ioctl(STp, MTWEOF, 1);
3451				if (i < 0) {
3452					retval = i;
3453					goto out;
3454				}
3455				if (mtc.mt_op == MTBSF || mtc.mt_op == MTBSFM)
3456					mtc.mt_count++;
3457				STps->rw = ST_IDLE;
3458			     }
3459
3460		} else {
3461			/*
3462			 * If there was a bus reset, block further access
3463			 * to this device.  If the user wants to rewind the tape,
3464			 * then reset the flag and allow access again.
3465			 */
3466			if (mtc.mt_op != MTREW &&
3467			    mtc.mt_op != MTOFFL &&
3468			    mtc.mt_op != MTRETEN &&
3469			    mtc.mt_op != MTERASE &&
3470			    mtc.mt_op != MTSEEK &&
3471			    mtc.mt_op != MTEOM) {
3472				retval = (-EIO);
3473				goto out;
3474			}
3475			reset_state(STp);
3476			/* remove this when the midlevel properly clears was_reset */
3477			STp->device->was_reset = 0;
3478		}
3479
3480		if (mtc.mt_op != MTNOP && mtc.mt_op != MTSETBLK &&
3481		    mtc.mt_op != MTSETDENSITY && mtc.mt_op != MTWSM &&
3482		    mtc.mt_op != MTSETDRVBUFFER && mtc.mt_op != MTSETPART)
3483			STps->rw = ST_IDLE;	/* Prevent automatic WEOF and fsf */
3484
3485		if (mtc.mt_op == MTOFFL && STp->door_locked != ST_UNLOCKED)
3486			do_door_lock(STp, 0);	/* Ignore result! */
3487
3488		if (mtc.mt_op == MTSETDRVBUFFER &&
3489		    (mtc.mt_count & MT_ST_OPTIONS) != 0) {
3490			retval = st_set_options(STp, mtc.mt_count);
3491			goto out;
3492		}
3493
3494		if (mtc.mt_op == MTSETPART) {
3495			if (!STp->can_partitions ||
3496			    mtc.mt_count < 0 || mtc.mt_count >= ST_NBR_PARTITIONS) {
3497				retval = (-EINVAL);
3498				goto out;
3499			}
3500			if (mtc.mt_count >= STp->nbr_partitions &&
3501			    (STp->nbr_partitions = nbr_partitions(STp)) < 0) {
3502				retval = (-EIO);
3503				goto out;
3504			}
3505			if (mtc.mt_count >= STp->nbr_partitions) {
3506				retval = (-EINVAL);
3507				goto out;
3508			}
3509			STp->new_partition = mtc.mt_count;
3510			retval = 0;
3511			goto out;
3512		}
3513
3514		if (mtc.mt_op == MTMKPART) {
3515			if (!STp->can_partitions) {
3516				retval = (-EINVAL);
3517				goto out;
3518			}
3519			if ((i = st_int_ioctl(STp, MTREW, 0)) < 0 ||
3520			    (i = partition_tape(STp, mtc.mt_count)) < 0) {
3521				retval = i;
3522				goto out;
3523			}
3524			for (i = 0; i < ST_NBR_PARTITIONS; i++) {
3525				STp->ps[i].rw = ST_IDLE;
3526				STp->ps[i].at_sm = 0;
3527				STp->ps[i].last_block_valid = 0;
3528			}
3529			STp->partition = STp->new_partition = 0;
3530			STp->nbr_partitions = 1;	/* Bad guess ?-) */
3531			STps->drv_block = STps->drv_file = 0;
3532			retval = 0;
3533			goto out;
3534		}
3535
3536		if (mtc.mt_op == MTSEEK) {
3537			i = set_location(STp, mtc.mt_count, STp->new_partition, 0);
3538			if (!STp->can_partitions)
3539				STp->ps[0].rw = ST_IDLE;
3540			retval = i;
3541			goto out;
3542		}
3543
3544		if (mtc.mt_op == MTUNLOAD || mtc.mt_op == MTOFFL) {
3545			retval = do_load_unload(STp, file, 0);
3546			goto out;
3547		}
3548
3549		if (mtc.mt_op == MTLOAD) {
3550			retval = do_load_unload(STp, file, max(1, mtc.mt_count));
3551			goto out;
3552		}
3553
3554		if (mtc.mt_op == MTLOCK || mtc.mt_op == MTUNLOCK) {
3555			retval = do_door_lock(STp, (mtc.mt_op == MTLOCK));
3556			goto out;
3557		}
3558
3559		if (STp->can_partitions && STp->ready == ST_READY &&
3560		    (i = switch_partition(STp)) < 0) {
3561			retval = i;
3562			goto out;
3563		}
3564
3565		if (mtc.mt_op == MTCOMPRESSION)
3566			retval = st_compression(STp, (mtc.mt_count & 1));
3567		else
3568			retval = st_int_ioctl(STp, mtc.mt_op, mtc.mt_count);
3569		goto out;
3570	}
3571	if (!STm->defined) {
3572		retval = (-ENXIO);
3573		goto out;
3574	}
3575
3576	if ((i = flush_buffer(STp, 0)) < 0) {
3577		retval = i;
3578		goto out;
3579	}
3580	if (STp->can_partitions &&
3581	    (i = switch_partition(STp)) < 0) {
3582		retval = i;
3583		goto out;
3584	}
3585
3586	if (cmd_type == _IOC_TYPE(MTIOCGET) && cmd_nr == _IOC_NR(MTIOCGET)) {
3587		struct mtget mt_status;
3588
3589		if (_IOC_SIZE(cmd_in) != sizeof(struct mtget)) {
3590			 retval = (-EINVAL);
3591			 goto out;
3592		}
3593
3594		mt_status.mt_type = STp->tape_type;
3595		mt_status.mt_dsreg =
3596		    ((STp->block_size << MT_ST_BLKSIZE_SHIFT) & MT_ST_BLKSIZE_MASK) |
3597		    ((STp->density << MT_ST_DENSITY_SHIFT) & MT_ST_DENSITY_MASK);
3598		mt_status.mt_blkno = STps->drv_block;
3599		mt_status.mt_fileno = STps->drv_file;
3600		if (STp->block_size != 0) {
3601			if (STps->rw == ST_WRITING)
3602				mt_status.mt_blkno +=
3603				    (STp->buffer)->buffer_bytes / STp->block_size;
3604			else if (STps->rw == ST_READING)
3605				mt_status.mt_blkno -=
3606                                        ((STp->buffer)->buffer_bytes +
3607                                         STp->block_size - 1) / STp->block_size;
3608		}
3609
3610		mt_status.mt_gstat = 0;
3611		if (STp->drv_write_prot)
3612			mt_status.mt_gstat |= GMT_WR_PROT(0xffffffff);
3613		if (mt_status.mt_blkno == 0) {
3614			if (mt_status.mt_fileno == 0)
3615				mt_status.mt_gstat |= GMT_BOT(0xffffffff);
3616			else
3617				mt_status.mt_gstat |= GMT_EOF(0xffffffff);
3618		}
3619		mt_status.mt_erreg = (STp->recover_reg << MT_ST_SOFTERR_SHIFT);
3620		mt_status.mt_resid = STp->partition;
3621		if (STps->eof == ST_EOM_OK || STps->eof == ST_EOM_ERROR)
3622			mt_status.mt_gstat |= GMT_EOT(0xffffffff);
3623		else if (STps->eof >= ST_EOM_OK)
3624			mt_status.mt_gstat |= GMT_EOD(0xffffffff);
3625		if (STp->density == 1)
3626			mt_status.mt_gstat |= GMT_D_800(0xffffffff);
3627		else if (STp->density == 2)
3628			mt_status.mt_gstat |= GMT_D_1600(0xffffffff);
3629		else if (STp->density == 3)
3630			mt_status.mt_gstat |= GMT_D_6250(0xffffffff);
3631		if (STp->ready == ST_READY)
3632			mt_status.mt_gstat |= GMT_ONLINE(0xffffffff);
3633		if (STp->ready == ST_NO_TAPE)
3634			mt_status.mt_gstat |= GMT_DR_OPEN(0xffffffff);
3635		if (STps->at_sm)
3636			mt_status.mt_gstat |= GMT_SM(0xffffffff);
3637		if (STm->do_async_writes ||
3638                    (STm->do_buffer_writes && STp->block_size != 0) ||
3639		    STp->drv_buffer != 0)
3640			mt_status.mt_gstat |= GMT_IM_REP_EN(0xffffffff);
3641		if (STp->cleaning_req)
3642			mt_status.mt_gstat |= GMT_CLN(0xffffffff);
3643
3644		i = copy_to_user(p, &mt_status, sizeof(struct mtget));
3645		if (i) {
3646			retval = (-EFAULT);
3647			goto out;
3648		}
3649
3650		STp->recover_reg = 0;		/* Clear after read */
3651		retval = 0;
3652		goto out;
3653	}			/* End of MTIOCGET */
3654	if (cmd_type == _IOC_TYPE(MTIOCPOS) && cmd_nr == _IOC_NR(MTIOCPOS)) {
3655		struct mtpos mt_pos;
3656		if (_IOC_SIZE(cmd_in) != sizeof(struct mtpos)) {
3657			 retval = (-EINVAL);
3658			 goto out;
3659		}
3660		if ((i = get_location(STp, &blk, &bt, 0)) < 0) {
3661			retval = i;
3662			goto out;
3663		}
3664		mt_pos.mt_blkno = blk;
3665		i = copy_to_user(p, &mt_pos, sizeof(struct mtpos));
3666		if (i)
3667			retval = (-EFAULT);
3668		goto out;
3669	}
3670	mutex_unlock(&STp->lock);
3671	switch (cmd_in) {
3672		case SCSI_IOCTL_GET_IDLUN:
3673		case SCSI_IOCTL_GET_BUS_NUMBER:
3674			break;
3675		default:
3676			if ((cmd_in == SG_IO ||
3677			     cmd_in == SCSI_IOCTL_SEND_COMMAND ||
3678			     cmd_in == CDROM_SEND_PACKET) &&
3679			    !capable(CAP_SYS_RAWIO))
3680				i = -EPERM;
3681			else
3682				i = scsi_cmd_ioctl(STp->disk->queue, STp->disk,
3683						   file->f_mode, cmd_in, p);
3684			if (i != -ENOTTY)
3685				return i;
3686			break;
3687	}
3688	retval = scsi_ioctl(STp->device, cmd_in, p);
3689	if (!retval && cmd_in == SCSI_IOCTL_STOP_UNIT) { /* unload */
3690		STp->rew_at_close = 0;
3691		STp->ready = ST_NO_TAPE;
3692	}
3693	return retval;
3694
3695 out:
3696	mutex_unlock(&STp->lock);
3697	return retval;
3698}
3699
3700#ifdef CONFIG_COMPAT
3701static long st_compat_ioctl(struct file *file, unsigned int cmd, unsigned long arg)
3702{
3703	struct scsi_tape *STp = file->private_data;
3704	struct scsi_device *sdev = STp->device;
3705	int ret = -ENOIOCTLCMD;
3706	if (sdev->host->hostt->compat_ioctl) {
3707
3708		ret = sdev->host->hostt->compat_ioctl(sdev, cmd, (void __user *)arg);
3709
3710	}
3711	return ret;
3712}
3713#endif
3714
3715
3716
3717/* Try to allocate a new tape buffer. Calling function must not hold
3718   dev_arr_lock. */
3719static struct st_buffer *new_tape_buffer(int need_dma, int max_sg)
3720{
3721	struct st_buffer *tb;
3722
3723	tb = kzalloc(sizeof(struct st_buffer), GFP_ATOMIC);
3724	if (!tb) {
3725		printk(KERN_NOTICE "st: Can't allocate new tape buffer.\n");
3726		return NULL;
3727	}
3728	tb->frp_segs = 0;
3729	tb->use_sg = max_sg;
3730	tb->dma = need_dma;
3731	tb->buffer_size = 0;
3732
3733	tb->reserved_pages = kzalloc(max_sg * sizeof(struct page *),
3734				     GFP_ATOMIC);
3735	if (!tb->reserved_pages) {
3736		kfree(tb);
3737		return NULL;
3738	}
3739
3740	return tb;
3741}
3742
3743
3744/* Try to allocate enough space in the tape buffer */
3745#define ST_MAX_ORDER 6
3746
3747static int enlarge_buffer(struct st_buffer * STbuffer, int new_size, int need_dma)
3748{
3749	int segs, max_segs, b_size, order, got;
3750	gfp_t priority;
3751
3752	if (new_size <= STbuffer->buffer_size)
3753		return 1;
3754
3755	if (STbuffer->buffer_size <= PAGE_SIZE)
3756		normalize_buffer(STbuffer);  /* Avoid extra segment */
3757
3758	max_segs = STbuffer->use_sg;
3759
3760	priority = GFP_KERNEL | __GFP_NOWARN;
3761	if (need_dma)
3762		priority |= GFP_DMA;
3763
3764	if (STbuffer->cleared)
3765		priority |= __GFP_ZERO;
3766
3767	if (STbuffer->frp_segs) {
3768		order = STbuffer->reserved_page_order;
3769		b_size = PAGE_SIZE << order;
3770	} else {
3771		for (b_size = PAGE_SIZE, order = 0;
3772		     order < ST_MAX_ORDER &&
3773			     max_segs * (PAGE_SIZE << order) < new_size;
3774		     order++, b_size *= 2)
3775			;  /* empty */
3776		STbuffer->reserved_page_order = order;
3777	}
3778	if (max_segs * (PAGE_SIZE << order) < new_size) {
3779		if (order == ST_MAX_ORDER)
3780			return 0;
3781		normalize_buffer(STbuffer);
3782		return enlarge_buffer(STbuffer, new_size, need_dma);
3783	}
3784
3785	for (segs = STbuffer->frp_segs, got = STbuffer->buffer_size;
3786	     segs < max_segs && got < new_size;) {
3787		struct page *page;
3788
3789		page = alloc_pages(priority, order);
3790		if (!page) {
3791			DEB(STbuffer->buffer_size = got);
3792			normalize_buffer(STbuffer);
3793			return 0;
3794		}
3795
3796		STbuffer->frp_segs += 1;
3797		got += b_size;
3798		STbuffer->buffer_size = got;
3799		STbuffer->reserved_pages[segs] = page;
3800		segs++;
3801	}
3802	STbuffer->b_data = page_address(STbuffer->reserved_pages[0]);
3803
3804	return 1;
3805}
3806
3807
3808/* Make sure that no data from previous user is in the internal buffer */
3809static void clear_buffer(struct st_buffer * st_bp)
3810{
3811	int i;
3812
3813	for (i=0; i < st_bp->frp_segs; i++)
3814		memset(page_address(st_bp->reserved_pages[i]), 0,
3815		       PAGE_SIZE << st_bp->reserved_page_order);
3816	st_bp->cleared = 1;
3817}
3818
3819
3820/* Release the extra buffer */
3821static void normalize_buffer(struct st_buffer * STbuffer)
3822{
3823	int i, order = STbuffer->reserved_page_order;
3824
3825	for (i = 0; i < STbuffer->frp_segs; i++) {
3826		__free_pages(STbuffer->reserved_pages[i], order);
3827		STbuffer->buffer_size -= (PAGE_SIZE << order);
3828	}
3829	STbuffer->frp_segs = 0;
3830	STbuffer->sg_segs = 0;
3831	STbuffer->reserved_page_order = 0;
3832	STbuffer->map_data.offset = 0;
3833}
3834
3835
3836/* Move data from the user buffer to the tape buffer. Returns zero (success) or
3837   negative error code. */
3838static int append_to_buffer(const char __user *ubp, struct st_buffer * st_bp, int do_count)
3839{
3840	int i, cnt, res, offset;
3841	int length = PAGE_SIZE << st_bp->reserved_page_order;
3842
3843	for (i = 0, offset = st_bp->buffer_bytes;
3844	     i < st_bp->frp_segs && offset >= length; i++)
3845		offset -= length;
3846	if (i == st_bp->frp_segs) {	/* Should never happen */
3847		printk(KERN_WARNING "st: append_to_buffer offset overflow.\n");
3848		return (-EIO);
3849	}
3850	for (; i < st_bp->frp_segs && do_count > 0; i++) {
3851		struct page *page = st_bp->reserved_pages[i];
3852		cnt = length - offset < do_count ? length - offset : do_count;
3853		res = copy_from_user(page_address(page) + offset, ubp, cnt);
3854		if (res)
3855			return (-EFAULT);
3856		do_count -= cnt;
3857		st_bp->buffer_bytes += cnt;
3858		ubp += cnt;
3859		offset = 0;
3860	}
3861	if (do_count) /* Should never happen */
3862		return (-EIO);
3863
3864	return 0;
3865}
3866
3867
3868/* Move data from the tape buffer to the user buffer. Returns zero (success) or
3869   negative error code. */
3870static int from_buffer(struct st_buffer * st_bp, char __user *ubp, int do_count)
3871{
3872	int i, cnt, res, offset;
3873	int length = PAGE_SIZE << st_bp->reserved_page_order;
3874
3875	for (i = 0, offset = st_bp->read_pointer;
3876	     i < st_bp->frp_segs && offset >= length; i++)
3877		offset -= length;
3878	if (i == st_bp->frp_segs) {	/* Should never happen */
3879		printk(KERN_WARNING "st: from_buffer offset overflow.\n");
3880		return (-EIO);
3881	}
3882	for (; i < st_bp->frp_segs && do_count > 0; i++) {
3883		struct page *page = st_bp->reserved_pages[i];
3884		cnt = length - offset < do_count ? length - offset : do_count;
3885		res = copy_to_user(ubp, page_address(page) + offset, cnt);
3886		if (res)
3887			return (-EFAULT);
3888		do_count -= cnt;
3889		st_bp->buffer_bytes -= cnt;
3890		st_bp->read_pointer += cnt;
3891		ubp += cnt;
3892		offset = 0;
3893	}
3894	if (do_count) /* Should never happen */
3895		return (-EIO);
3896
3897	return 0;
3898}
3899
3900
3901/* Move data towards start of buffer */
3902static void move_buffer_data(struct st_buffer * st_bp, int offset)
3903{
3904	int src_seg, dst_seg, src_offset = 0, dst_offset;
3905	int count, total;
3906	int length = PAGE_SIZE << st_bp->reserved_page_order;
3907
3908	if (offset == 0)
3909		return;
3910
3911	total=st_bp->buffer_bytes - offset;
3912	for (src_seg=0; src_seg < st_bp->frp_segs; src_seg++) {
3913		src_offset = offset;
3914		if (src_offset < length)
3915			break;
3916		offset -= length;
3917	}
3918
3919	st_bp->buffer_bytes = st_bp->read_pointer = total;
3920	for (dst_seg=dst_offset=0; total > 0; ) {
3921		struct page *dpage = st_bp->reserved_pages[dst_seg];
3922		struct page *spage = st_bp->reserved_pages[src_seg];
3923
3924		count = min(length - dst_offset, length - src_offset);
3925		memmove(page_address(dpage) + dst_offset,
3926			page_address(spage) + src_offset, count);
3927		src_offset += count;
3928		if (src_offset >= length) {
3929			src_seg++;
3930			src_offset = 0;
3931		}
3932		dst_offset += count;
3933		if (dst_offset >= length) {
3934			dst_seg++;
3935			dst_offset = 0;
3936		}
3937		total -= count;
3938	}
3939}
3940
3941/* Validate the options from command line or module parameters */
3942static void validate_options(void)
3943{
3944	if (buffer_kbs > 0)
3945		st_fixed_buffer_size = buffer_kbs * ST_KILOBYTE;
3946	if (max_sg_segs >= ST_FIRST_SG)
3947		st_max_sg_segs = max_sg_segs;
3948}
3949
3950#ifndef MODULE
3951/* Set the boot options. Syntax is defined in Documenation/scsi/st.txt.
3952 */
3953static int __init st_setup(char *str)
3954{
3955	int i, len, ints[5];
3956	char *stp;
3957
3958	stp = get_options(str, ARRAY_SIZE(ints), ints);
3959
3960	if (ints[0] > 0) {
3961		for (i = 0; i < ints[0] && i < ARRAY_SIZE(parms); i++)
3962			if (parms[i].val)
3963				*parms[i].val = ints[i + 1];
3964	} else {
3965		while (stp != NULL) {
3966			for (i = 0; i < ARRAY_SIZE(parms); i++) {
3967				len = strlen(parms[i].name);
3968				if (!strncmp(stp, parms[i].name, len) &&
3969				    (*(stp + len) == ':' || *(stp + len) == '=')) {
3970					if (parms[i].val)
3971						*parms[i].val =
3972							simple_strtoul(stp + len + 1, NULL, 0);
3973					else
3974						printk(KERN_WARNING "st: Obsolete parameter %s\n",
3975						       parms[i].name);
3976					break;
3977				}
3978			}
3979			if (i >= ARRAY_SIZE(parms))
3980				 printk(KERN_WARNING "st: invalid parameter in '%s'\n",
3981					stp);
3982			stp = strchr(stp, ',');
3983			if (stp)
3984				stp++;
3985		}
3986	}
3987
3988	validate_options();
3989
3990	return 1;
3991}
3992
3993__setup("st=", st_setup);
3994
3995#endif
3996
3997static const struct file_operations st_fops =
3998{
3999	.owner =	THIS_MODULE,
4000	.read =		st_read,
4001	.write =	st_write,
4002	.unlocked_ioctl = st_ioctl,
4003#ifdef CONFIG_COMPAT
4004	.compat_ioctl = st_compat_ioctl,
4005#endif
4006	.open =		st_open,
4007	.flush =	st_flush,
4008	.release =	st_release,
4009	.llseek =	noop_llseek,
4010};
4011
4012static int create_one_cdev(struct scsi_tape *tape, int mode, int rew)
4013{
4014	int i, error;
4015	dev_t cdev_devno;
4016	struct cdev *cdev;
4017	struct device *dev;
4018	struct st_modedef *STm = &(tape->modes[mode]);
4019	char name[10];
4020	int dev_num = tape->index;
4021
4022	cdev_devno = MKDEV(SCSI_TAPE_MAJOR, TAPE_MINOR(dev_num, mode, rew));
4023
4024	cdev = cdev_alloc();
4025	if (!cdev) {
4026		pr_err("st%d: out of memory. Device not attached.\n", dev_num);
4027		error = -ENOMEM;
4028		goto out;
4029	}
4030	cdev->owner = THIS_MODULE;
4031	cdev->ops = &st_fops;
4032
4033	error = cdev_add(cdev, cdev_devno, 1);
4034	if (error) {
4035		pr_err("st%d: Can't add %s-rewind mode %d\n", dev_num,
4036		       rew ? "non" : "auto", mode);
4037		pr_err("st%d: Device not attached.\n", dev_num);
4038		goto out_free;
4039	}
4040	STm->cdevs[rew] = cdev;
4041
4042	i = mode << (4 - ST_NBR_MODE_BITS);
4043	snprintf(name, 10, "%s%s%s", rew ? "n" : "",
4044		 tape->disk->disk_name, st_formats[i]);
4045
4046	dev = device_create(&st_sysfs_class, &tape->device->sdev_gendev,
4047			    cdev_devno, &tape->modes[mode], "%s", name);
4048	if (IS_ERR(dev)) {
4049		pr_err("st%d: device_create failed\n", dev_num);
4050		error = PTR_ERR(dev);
4051		goto out_free;
4052	}
4053
4054	STm->devs[rew] = dev;
4055
4056	return 0;
4057out_free:
4058	cdev_del(STm->cdevs[rew]);
4059	STm->cdevs[rew] = NULL;
4060out:
4061	return error;
4062}
4063
4064static int create_cdevs(struct scsi_tape *tape)
4065{
4066	int mode, error;
4067	for (mode = 0; mode < ST_NBR_MODES; ++mode) {
4068		error = create_one_cdev(tape, mode, 0);
4069		if (error)
4070			return error;
4071		error = create_one_cdev(tape, mode, 1);
4072		if (error)
4073			return error;
4074	}
4075
4076	return sysfs_create_link(&tape->device->sdev_gendev.kobj,
4077				 &tape->modes[0].devs[0]->kobj, "tape");
4078}
4079
4080static void remove_cdevs(struct scsi_tape *tape)
4081{
4082	int mode, rew;
4083	sysfs_remove_link(&tape->device->sdev_gendev.kobj, "tape");
4084	for (mode = 0; mode < ST_NBR_MODES; mode++) {
4085		struct st_modedef *STm = &(tape->modes[mode]);
4086		for (rew = 0; rew < 2; rew++) {
4087			if (STm->cdevs[rew])
4088				cdev_del(STm->cdevs[rew]);
4089			if (STm->devs[rew])
4090				device_unregister(STm->devs[rew]);
4091		}
4092	}
4093}
4094
4095static int st_probe(struct device *dev)
4096{
4097	struct scsi_device *SDp = to_scsi_device(dev);
4098	struct gendisk *disk = NULL;
4099	struct scsi_tape *tpnt = NULL;
4100	struct st_modedef *STm;
4101	struct st_partstat *STps;
4102	struct st_buffer *buffer;
4103	int i, error;
4104	char *stp;
4105
4106	if (SDp->type != TYPE_TAPE)
4107		return -ENODEV;
4108	if ((stp = st_incompatible(SDp))) {
4109		sdev_printk(KERN_INFO, SDp, "Found incompatible tape\n");
4110		sdev_printk(KERN_INFO, SDp,
4111			    "st: The suggested driver is %s.\n", stp);
4112		return -ENODEV;
4113	}
4114
4115	scsi_autopm_get_device(SDp);
4116	i = queue_max_segments(SDp->request_queue);
4117	if (st_max_sg_segs < i)
4118		i = st_max_sg_segs;
4119	buffer = new_tape_buffer((SDp->host)->unchecked_isa_dma, i);
4120	if (buffer == NULL) {
4121		sdev_printk(KERN_ERR, SDp,
4122			    "st: Can't allocate new tape buffer. "
4123			    "Device not attached.\n");
4124		goto out;
4125	}
4126
4127	disk = alloc_disk(1);
4128	if (!disk) {
4129		sdev_printk(KERN_ERR, SDp,
4130			    "st: out of memory. Device not attached.\n");
4131		goto out_buffer_free;
4132	}
4133
4134	tpnt = kzalloc(sizeof(struct scsi_tape), GFP_ATOMIC);
4135	if (tpnt == NULL) {
4136		sdev_printk(KERN_ERR, SDp,
4137			    "st: Can't allocate device descriptor.\n");
4138		goto out_put_disk;
4139	}
4140	kref_init(&tpnt->kref);
4141	tpnt->disk = disk;
4142	disk->private_data = &tpnt->driver;
4143	disk->queue = SDp->request_queue;
4144	/* SCSI tape doesn't register this gendisk via add_disk().  Manually
4145	 * take queue reference that release_disk() expects. */
4146	if (!blk_get_queue(disk->queue))
4147		goto out_put_disk;
4148	tpnt->driver = &st_template;
4149
4150	tpnt->device = SDp;
4151	if (SDp->scsi_level <= 2)
4152		tpnt->tape_type = MT_ISSCSI1;
4153	else
4154		tpnt->tape_type = MT_ISSCSI2;
4155
4156	tpnt->buffer = buffer;
4157	tpnt->buffer->last_SRpnt = NULL;
4158
4159	tpnt->inited = 0;
4160	tpnt->dirty = 0;
4161	tpnt->in_use = 0;
4162	tpnt->drv_buffer = 1;	/* Try buffering if no mode sense */
4163	tpnt->restr_dma = (SDp->host)->unchecked_isa_dma;
4164	tpnt->use_pf = (SDp->scsi_level >= SCSI_2);
4165	tpnt->density = 0;
4166	tpnt->do_auto_lock = ST_AUTO_LOCK;
4167	tpnt->can_bsr = (SDp->scsi_level > 2 ? 1 : ST_IN_FILE_POS); /* BSR mandatory in SCSI3 */
4168	tpnt->can_partitions = 0;
4169	tpnt->two_fm = ST_TWO_FM;
4170	tpnt->fast_mteom = ST_FAST_MTEOM;
4171	tpnt->scsi2_logical = ST_SCSI2LOGICAL;
4172	tpnt->sili = ST_SILI;
4173	tpnt->immediate = ST_NOWAIT;
4174	tpnt->immediate_filemark = 0;
4175	tpnt->default_drvbuffer = 0xff;		/* No forced buffering */
4176	tpnt->partition = 0;
4177	tpnt->new_partition = 0;
4178	tpnt->nbr_partitions = 0;
4179	blk_queue_rq_timeout(tpnt->device->request_queue, ST_TIMEOUT);
4180	tpnt->long_timeout = ST_LONG_TIMEOUT;
4181	tpnt->try_dio = try_direct_io && !SDp->host->unchecked_isa_dma;
4182
4183	for (i = 0; i < ST_NBR_MODES; i++) {
4184		STm = &(tpnt->modes[i]);
4185		STm->defined = 0;
4186		STm->sysv = ST_SYSV;
4187		STm->defaults_for_writes = 0;
4188		STm->do_async_writes = ST_ASYNC_WRITES;
4189		STm->do_buffer_writes = ST_BUFFER_WRITES;
4190		STm->do_read_ahead = ST_READ_AHEAD;
4191		STm->default_compression = ST_DONT_TOUCH;
4192		STm->default_blksize = (-1);	/* No forced size */
4193		STm->default_density = (-1);	/* No forced density */
4194		STm->tape = tpnt;
4195	}
4196
4197	for (i = 0; i < ST_NBR_PARTITIONS; i++) {
4198		STps = &(tpnt->ps[i]);
4199		STps->rw = ST_IDLE;
4200		STps->eof = ST_NOEOF;
4201		STps->at_sm = 0;
4202		STps->last_block_valid = 0;
4203		STps->drv_block = (-1);
4204		STps->drv_file = (-1);
4205	}
4206
4207	tpnt->current_mode = 0;
4208	tpnt->modes[0].defined = 1;
4209
4210	tpnt->density_changed = tpnt->compression_changed =
4211	    tpnt->blksize_changed = 0;
4212	mutex_init(&tpnt->lock);
4213
4214	idr_preload(GFP_KERNEL);
4215	spin_lock(&st_index_lock);
4216	error = idr_alloc(&st_index_idr, tpnt, 0, ST_MAX_TAPES + 1, GFP_NOWAIT);
4217	spin_unlock(&st_index_lock);
4218	idr_preload_end();
4219	if (error < 0) {
4220		pr_warn("st: idr allocation failed: %d\n", error);
4221		goto out_put_queue;
4222	}
4223	tpnt->index = error;
4224	sprintf(disk->disk_name, "st%d", tpnt->index);
4225
4226	dev_set_drvdata(dev, tpnt);
4227
4228
4229	error = create_cdevs(tpnt);
4230	if (error)
4231		goto out_remove_devs;
4232	scsi_autopm_put_device(SDp);
4233
4234	sdev_printk(KERN_NOTICE, SDp,
4235		    "Attached scsi tape %s\n", tape_name(tpnt));
4236	sdev_printk(KERN_INFO, SDp, "%s: try direct i/o: %s (alignment %d B)\n",
4237		    tape_name(tpnt), tpnt->try_dio ? "yes" : "no",
4238		    queue_dma_alignment(SDp->request_queue) + 1);
4239
4240	return 0;
4241
4242out_remove_devs:
4243	remove_cdevs(tpnt);
4244	spin_lock(&st_index_lock);
4245	idr_remove(&st_index_idr, tpnt->index);
4246	spin_unlock(&st_index_lock);
4247out_put_queue:
4248	blk_put_queue(disk->queue);
4249out_put_disk:
4250	put_disk(disk);
4251	kfree(tpnt);
4252out_buffer_free:
4253	kfree(buffer);
4254out:
4255	scsi_autopm_put_device(SDp);
4256	return -ENODEV;
4257};
4258
4259
4260static int st_remove(struct device *dev)
4261{
4262	struct scsi_tape *tpnt = dev_get_drvdata(dev);
4263	int index = tpnt->index;
4264
4265	scsi_autopm_get_device(to_scsi_device(dev));
4266	remove_cdevs(tpnt);
4267
4268	mutex_lock(&st_ref_mutex);
4269	kref_put(&tpnt->kref, scsi_tape_release);
4270	mutex_unlock(&st_ref_mutex);
4271	spin_lock(&st_index_lock);
4272	idr_remove(&st_index_idr, index);
4273	spin_unlock(&st_index_lock);
4274	return 0;
4275}
4276
4277/**
4278 *      scsi_tape_release - Called to free the Scsi_Tape structure
4279 *      @kref: pointer to embedded kref
4280 *
4281 *      st_ref_mutex must be held entering this routine.  Because it is
4282 *      called on last put, you should always use the scsi_tape_get()
4283 *      scsi_tape_put() helpers which manipulate the semaphore directly
4284 *      and never do a direct kref_put().
4285 **/
4286static void scsi_tape_release(struct kref *kref)
4287{
4288	struct scsi_tape *tpnt = to_scsi_tape(kref);
4289	struct gendisk *disk = tpnt->disk;
4290
4291	tpnt->device = NULL;
4292
4293	if (tpnt->buffer) {
4294		normalize_buffer(tpnt->buffer);
4295		kfree(tpnt->buffer->reserved_pages);
4296		kfree(tpnt->buffer);
4297	}
4298
4299	disk->private_data = NULL;
4300	put_disk(disk);
4301	kfree(tpnt);
4302	return;
4303}
4304
4305static struct class st_sysfs_class = {
4306	.name = "scsi_tape",
4307	.dev_groups = st_dev_groups,
4308};
4309
4310static int __init init_st(void)
4311{
4312	int err;
4313
4314	validate_options();
4315
4316	printk(KERN_INFO "st: Version %s, fixed bufsize %d, s/g segs %d\n",
4317		verstr, st_fixed_buffer_size, st_max_sg_segs);
4318
4319	debugging = (debug_flag > 0) ? debug_flag : NO_DEBUG;
4320	if (debugging) {
4321		printk(KERN_INFO "st: Debugging enabled debug_flag = %d\n",
4322			debugging);
4323	}
4324
4325	err = class_register(&st_sysfs_class);
4326	if (err) {
4327		pr_err("Unable register sysfs class for SCSI tapes\n");
4328		return err;
4329	}
4330
4331	err = register_chrdev_region(MKDEV(SCSI_TAPE_MAJOR, 0),
4332				     ST_MAX_TAPE_ENTRIES, "st");
4333	if (err) {
4334		printk(KERN_ERR "Unable to get major %d for SCSI tapes\n",
4335		       SCSI_TAPE_MAJOR);
4336		goto err_class;
4337	}
4338
4339	err = scsi_register_driver(&st_template.gendrv);
4340	if (err)
4341		goto err_chrdev;
4342
4343	err = do_create_sysfs_files();
4344	if (err)
4345		goto err_scsidrv;
4346
4347	return 0;
4348
4349err_scsidrv:
4350	scsi_unregister_driver(&st_template.gendrv);
4351err_chrdev:
4352	unregister_chrdev_region(MKDEV(SCSI_TAPE_MAJOR, 0),
4353				 ST_MAX_TAPE_ENTRIES);
4354err_class:
4355	class_unregister(&st_sysfs_class);
4356	return err;
4357}
4358
4359static void __exit exit_st(void)
4360{
4361	do_remove_sysfs_files();
4362	scsi_unregister_driver(&st_template.gendrv);
4363	unregister_chrdev_region(MKDEV(SCSI_TAPE_MAJOR, 0),
4364				 ST_MAX_TAPE_ENTRIES);
4365	class_unregister(&st_sysfs_class);
4366	printk(KERN_INFO "st: Unloaded.\n");
4367}
4368
4369module_init(init_st);
4370module_exit(exit_st);
4371
4372
4373/* The sysfs driver interface. Read-only at the moment */
4374static ssize_t st_try_direct_io_show(struct device_driver *ddp, char *buf)
4375{
4376	return snprintf(buf, PAGE_SIZE, "%d\n", try_direct_io);
4377}
4378static DRIVER_ATTR(try_direct_io, S_IRUGO, st_try_direct_io_show, NULL);
4379
4380static ssize_t st_fixed_buffer_size_show(struct device_driver *ddp, char *buf)
4381{
4382	return snprintf(buf, PAGE_SIZE, "%d\n", st_fixed_buffer_size);
4383}
4384static DRIVER_ATTR(fixed_buffer_size, S_IRUGO, st_fixed_buffer_size_show, NULL);
4385
4386static ssize_t st_max_sg_segs_show(struct device_driver *ddp, char *buf)
4387{
4388	return snprintf(buf, PAGE_SIZE, "%d\n", st_max_sg_segs);
4389}
4390static DRIVER_ATTR(max_sg_segs, S_IRUGO, st_max_sg_segs_show, NULL);
4391
4392static ssize_t st_version_show(struct device_driver *ddd, char *buf)
4393{
4394	return snprintf(buf, PAGE_SIZE, "[%s]\n", verstr);
4395}
4396static DRIVER_ATTR(version, S_IRUGO, st_version_show, NULL);
4397
4398static int do_create_sysfs_files(void)
4399{
4400	struct device_driver *sysfs = &st_template.gendrv;
4401	int err;
4402
4403	err = driver_create_file(sysfs, &driver_attr_try_direct_io);
4404	if (err)
4405		return err;
4406	err = driver_create_file(sysfs, &driver_attr_fixed_buffer_size);
4407	if (err)
4408		goto err_try_direct_io;
4409	err = driver_create_file(sysfs, &driver_attr_max_sg_segs);
4410	if (err)
4411		goto err_attr_fixed_buf;
4412	err = driver_create_file(sysfs, &driver_attr_version);
4413	if (err)
4414		goto err_attr_max_sg;
4415
4416	return 0;
4417
4418err_attr_max_sg:
4419	driver_remove_file(sysfs, &driver_attr_max_sg_segs);
4420err_attr_fixed_buf:
4421	driver_remove_file(sysfs, &driver_attr_fixed_buffer_size);
4422err_try_direct_io:
4423	driver_remove_file(sysfs, &driver_attr_try_direct_io);
4424	return err;
4425}
4426
4427static void do_remove_sysfs_files(void)
4428{
4429	struct device_driver *sysfs = &st_template.gendrv;
4430
4431	driver_remove_file(sysfs, &driver_attr_version);
4432	driver_remove_file(sysfs, &driver_attr_max_sg_segs);
4433	driver_remove_file(sysfs, &driver_attr_fixed_buffer_size);
4434	driver_remove_file(sysfs, &driver_attr_try_direct_io);
4435}
4436
4437/* The sysfs simple class interface */
4438static ssize_t
4439defined_show(struct device *dev, struct device_attribute *attr, char *buf)
4440{
4441	struct st_modedef *STm = dev_get_drvdata(dev);
4442	ssize_t l = 0;
4443
4444	l = snprintf(buf, PAGE_SIZE, "%d\n", STm->defined);
4445	return l;
4446}
4447static DEVICE_ATTR_RO(defined);
4448
4449static ssize_t
4450default_blksize_show(struct device *dev, struct device_attribute *attr,
4451		     char *buf)
4452{
4453	struct st_modedef *STm = dev_get_drvdata(dev);
4454	ssize_t l = 0;
4455
4456	l = snprintf(buf, PAGE_SIZE, "%d\n", STm->default_blksize);
4457	return l;
4458}
4459static DEVICE_ATTR_RO(default_blksize);
4460
4461static ssize_t
4462default_density_show(struct device *dev, struct device_attribute *attr,
4463		     char *buf)
4464{
4465	struct st_modedef *STm = dev_get_drvdata(dev);
4466	ssize_t l = 0;
4467	char *fmt;
4468
4469	fmt = STm->default_density >= 0 ? "0x%02x\n" : "%d\n";
4470	l = snprintf(buf, PAGE_SIZE, fmt, STm->default_density);
4471	return l;
4472}
4473static DEVICE_ATTR_RO(default_density);
4474
4475static ssize_t
4476default_compression_show(struct device *dev, struct device_attribute *attr,
4477			 char *buf)
4478{
4479	struct st_modedef *STm = dev_get_drvdata(dev);
4480	ssize_t l = 0;
4481
4482	l = snprintf(buf, PAGE_SIZE, "%d\n", STm->default_compression - 1);
4483	return l;
4484}
4485static DEVICE_ATTR_RO(default_compression);
4486
4487static ssize_t
4488options_show(struct device *dev, struct device_attribute *attr, char *buf)
4489{
4490	struct st_modedef *STm = dev_get_drvdata(dev);
4491	struct scsi_tape *STp = STm->tape;
4492	int options;
4493	ssize_t l = 0;
4494
4495	options = STm->do_buffer_writes ? MT_ST_BUFFER_WRITES : 0;
4496	options |= STm->do_async_writes ? MT_ST_ASYNC_WRITES : 0;
4497	options |= STm->do_read_ahead ? MT_ST_READ_AHEAD : 0;
4498	DEB( options |= debugging ? MT_ST_DEBUGGING : 0 );
4499	options |= STp->two_fm ? MT_ST_TWO_FM : 0;
4500	options |= STp->fast_mteom ? MT_ST_FAST_MTEOM : 0;
4501	options |= STm->defaults_for_writes ? MT_ST_DEF_WRITES : 0;
4502	options |= STp->can_bsr ? MT_ST_CAN_BSR : 0;
4503	options |= STp->omit_blklims ? MT_ST_NO_BLKLIMS : 0;
4504	options |= STp->can_partitions ? MT_ST_CAN_PARTITIONS : 0;
4505	options |= STp->scsi2_logical ? MT_ST_SCSI2LOGICAL : 0;
4506	options |= STm->sysv ? MT_ST_SYSV : 0;
4507	options |= STp->immediate ? MT_ST_NOWAIT : 0;
4508	options |= STp->immediate_filemark ? MT_ST_NOWAIT_EOF : 0;
4509	options |= STp->sili ? MT_ST_SILI : 0;
4510
4511	l = snprintf(buf, PAGE_SIZE, "0x%08x\n", options);
4512	return l;
4513}
4514static DEVICE_ATTR_RO(options);
4515
4516static struct attribute *st_dev_attrs[] = {
4517	&dev_attr_defined.attr,
4518	&dev_attr_default_blksize.attr,
4519	&dev_attr_default_density.attr,
4520	&dev_attr_default_compression.attr,
4521	&dev_attr_options.attr,
4522	NULL,
4523};
4524ATTRIBUTE_GROUPS(st_dev);
4525
4526/* The following functions may be useful for a larger audience. */
4527static int sgl_map_user_pages(struct st_buffer *STbp,
4528			      const unsigned int max_pages, unsigned long uaddr,
4529			      size_t count, int rw)
4530{
4531	unsigned long end = (uaddr + count + PAGE_SIZE - 1) >> PAGE_SHIFT;
4532	unsigned long start = uaddr >> PAGE_SHIFT;
4533	const int nr_pages = end - start;
4534	int res, i, j;
4535	struct page **pages;
4536	struct rq_map_data *mdata = &STbp->map_data;
4537
4538	/* User attempted Overflow! */
4539	if ((uaddr + count) < uaddr)
4540		return -EINVAL;
4541
4542	/* Too big */
4543        if (nr_pages > max_pages)
4544		return -ENOMEM;
4545
4546	/* Hmm? */
4547	if (count == 0)
4548		return 0;
4549
4550	if ((pages = kmalloc(max_pages * sizeof(*pages), GFP_KERNEL)) == NULL)
4551		return -ENOMEM;
4552
4553        /* Try to fault in all of the necessary pages */
4554        /* rw==READ means read from drive, write into memory area */
4555	res = get_user_pages_unlocked(
4556		current,
4557		current->mm,
4558		uaddr,
4559		nr_pages,
4560		rw == READ,
4561		0, /* don't force */
4562		pages);
4563
4564	/* Errors and no page mapped should return here */
4565	if (res < nr_pages)
4566		goto out_unmap;
4567
4568        for (i=0; i < nr_pages; i++) {
4569                /* FIXME: flush superflous for rw==READ,
4570                 * probably wrong function for rw==WRITE
4571                 */
4572		flush_dcache_page(pages[i]);
4573        }
4574
4575	mdata->offset = uaddr & ~PAGE_MASK;
4576	STbp->mapped_pages = pages;
4577
4578	return nr_pages;
4579 out_unmap:
4580	if (res > 0) {
4581		for (j=0; j < res; j++)
4582			page_cache_release(pages[j]);
4583		res = 0;
4584	}
4585	kfree(pages);
4586	return res;
4587}
4588
4589
4590/* And unmap them... */
4591static int sgl_unmap_user_pages(struct st_buffer *STbp,
4592				const unsigned int nr_pages, int dirtied)
4593{
4594	int i;
4595
4596	for (i=0; i < nr_pages; i++) {
4597		struct page *page = STbp->mapped_pages[i];
4598
4599		if (dirtied)
4600			SetPageDirty(page);
4601		/* FIXME: cache flush missing for rw==READ
4602		 * FIXME: call the correct reference counting function
4603		 */
4604		page_cache_release(page);
4605	}
4606	kfree(STbp->mapped_pages);
4607	STbp->mapped_pages = NULL;
4608
4609	return 0;
4610}
4611