ffb_accel.c revision 504f16bc
1/*
2 * Acceleration for the Creator and Creator3D framebuffer.
3 *
4 * Copyright (C) 1998,1999,2000 Jakub Jelinek (jakub@redhat.com)
5 * Copyright (C) 1998 Michal Rehacek (majkl@iname.com)
6 * Copyright (C) 1999,2000 David S. Miller (davem@redhat.com)
7 *
8 * Permission is hereby granted, free of charge, to any person obtaining a copy
9 * of this software and associated documentation files (the "Software"), to deal
10 * in the Software without restriction, including without limitation the rights
11 * to use, copy, modify, merge, publish, distribute, sublicense, and/or sell
12 * copies of the Software, and to permit persons to whom the Software is
13 * furnished to do so, subject to the following conditions:
14 *
15 * The above copyright notice and this permission notice shall be included in
16 * all copies or substantial portions of the Software.
17 *
18 * THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR
19 * IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY,
20 * FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT.  IN NO EVENT SHALL
21 * JAKUB JELINEK, MICHAL REHACEK, OR DAVID MILLER BE LIABLE FOR ANY CLAIM,
22 * DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR
23 * OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE
24 * USE OR OTHER DEALINGS IN THE SOFTWARE.
25 *
26 */
27
28#ifdef HAVE_CONFIG_H
29#include "config.h"
30#endif
31
32#include	"scrnintstr.h"
33#include	"pixmapstr.h"
34#include	"regionstr.h"
35#include	"mistruct.h"
36#include	"miline.h"
37#include	"fb.h"
38
39#include	"ffb.h"
40#include	"ffb_fifo.h"
41#include	"ffb_rcache.h"
42#include	"ffb_loops.h"
43#include	"ffb_regs.h"
44
45#ifdef HAVE_XAA_H
46/* VISmoveImage.s */
47extern void VISmoveImageRL(unsigned char *src, unsigned char *dst, long w, long h, long skind, long dkind);
48extern void VISmoveImageLR(unsigned char *src, unsigned char *dst, long w, long h, long skind, long dkind);
49
50/* Indexed by ffb resolution enum. */
51struct fastfill_parms ffb_fastfill_parms[] = {
52	/* fsmall, psmall,  ffh,  ffw,  pfh,  pfw */
53	{  0x00c0, 0x1400, 0x04, 0x08, 0x10, 0x50 },	/* Standard: 1280 x 1024 */
54	{  0x0140, 0x2800, 0x04, 0x10, 0x10, 0xa0 },	/* High:     1920 x 1360 */
55	{  0x0080, 0x0a00, 0x02, 0x08, 0x08, 0x50 },	/* Stereo:   960  x 580  */
56/*XXX*/	{  0x00c0, 0x0a00, 0x04, 0x08, 0x08, 0x50 },	/* Portrait: 1280 x 2048 XXX */
57};
58
59void
60CreatorVtChange (ScreenPtr pScreen, int enter)
61{
62	ScrnInfoPtr pScrn = xf86ScreenToScrn(pScreen);
63	FFBPtr pFfb = GET_FFB_FROM_SCRN (pScrn);
64	ffb_fbcPtr ffb = pFfb->regs;
65
66	pFfb->rp_active = 1;
67	FFBWait(pFfb, ffb);
68	pFfb->fifo_cache = -1;
69	pFfb->fbc_cache = (FFB_FBC_WB_A | FFB_FBC_WM_COMBINED |
70			   FFB_FBC_RB_A | FFB_FBC_SB_BOTH| FFB_FBC_XE_OFF |
71			   FFB_FBC_ZE_OFF | FFB_FBC_YE_OFF | FFB_FBC_RGBE_MASK);
72	pFfb->ppc_cache = (FFB_PPC_FW_DISABLE |
73			   FFB_PPC_VCE_DISABLE | FFB_PPC_APE_DISABLE | FFB_PPC_CS_CONST |
74			   FFB_PPC_XS_CONST | FFB_PPC_YS_CONST | FFB_PPC_ZS_CONST|
75			   FFB_PPC_DCE_DISABLE | FFB_PPC_ABE_DISABLE | FFB_PPC_TBE_OPAQUE);
76
77	pFfb->pmask_cache = ~0;
78	pFfb->rop_cache = FFB_ROP_EDIT_BIT;
79	pFfb->drawop_cache = FFB_DRAWOP_RECTANGLE;
80	pFfb->fg_cache = pFfb->bg_cache = 0;
81	pFfb->fontw_cache = 32;
82	pFfb->fontinc_cache = (1 << 16) | 0;
83	pFfb->laststipple = NULL;
84	FFBFifo(pFfb, 9);
85	ffb->fbc = pFfb->fbc_cache;
86	ffb->ppc = pFfb->ppc_cache;
87	ffb->pmask = pFfb->pmask_cache;
88	ffb->rop = pFfb->rop_cache;
89	ffb->drawop = pFfb->drawop_cache;
90	ffb->fg = pFfb->fg_cache;
91	ffb->bg = pFfb->bg_cache;
92	ffb->fontw = pFfb->fontw_cache;
93	ffb->fontinc = pFfb->fontinc_cache;
94	pFfb->rp_active = 1;
95	FFBWait(pFfb, ffb);
96
97	/* Fixup the FBC/PPC caches to deal with actually using
98	 * a WID for every ROP.
99	 */
100	pFfb->fbc_cache = (FFB_FBC_WB_A | FFB_FBC_WM_COMBINED |
101			   FFB_FBC_RB_A | FFB_FBC_SB_BOTH | FFB_FBC_XE_ON |
102			   FFB_FBC_ZE_OFF | FFB_FBC_YE_OFF | FFB_FBC_RGBE_ON);
103	pFfb->ppc_cache &= ~FFB_PPC_XS_MASK;
104	pFfb->ppc_cache |= FFB_PPC_XS_WID;
105	pFfb->wid_cache = (enter ? pFfb->wid : 0xff);
106	FFBFifo(pFfb, 11);
107	ffb->fbc = pFfb->fbc_cache;
108	ffb->ppc = FFB_PPC_XS_WID;
109	ffb->wid = pFfb->wid_cache;
110	ffb->xpmask = 0xff;
111	ffb->xclip = FFB_XCLIP_TEST_ALWAYS;
112	ffb->cmp = 0x80808080;
113	ffb->matchab = 0x80808080;
114	ffb->magnab = 0x80808080;
115	ffb->blendc = (FFB_BLENDC_FORCE_ONE |
116		       FFB_BLENDC_DF_ONE_M_A |
117		       FFB_BLENDC_SF_A);
118	ffb->blendc1 = 0;
119	ffb->blendc2 = 0;
120	pFfb->rp_active = 1;
121	FFBWait(pFfb, ffb);
122
123	if (enter) {
124		pFfb->drawop_cache = FFB_DRAWOP_RECTANGLE;
125
126		FFBFifo(pFfb, 5);
127		ffb->drawop = pFfb->drawop_cache;
128		FFB_WRITE64(&ffb->by, 0, 0);
129		FFB_WRITE64_2(&ffb->bh, pFfb->psdp->height, pFfb->psdp->width);
130		pFfb->rp_active = 1;
131		FFBWait(pFfb, ffb);
132
133		SET_SYNC_FLAG(pFfb->pXAAInfo);
134	}
135}
136
137#ifdef DEBUG_FFB
138FILE *FDEBUG_FD = NULL;
139#endif
140
141static CARD32 FFBAlphaTextureFormats[2] = { PICT_a8, 0 };
142static CARD32 FFBTextureFormats[2] = { PICT_a8b8g8r8, 0 };
143static CARD32 FFBTextureDstFormats[3] = { PICT_a8b8g8r8, PICT_x8b8g8r8, 0 };
144
145static Bool FFB_SetupForCPUToScreenAlphaTexture(
146	ScrnInfoPtr	pScrn,
147	int		op,
148	CARD16		red,
149	CARD16		green,
150	CARD16		blue,
151	CARD16		alpha,
152	CARD32		maskFormat,
153	CARD32		dstFormat,
154	CARD8		*alphaPtr,
155	int		alphaPitch,
156	int		width,
157	int		height,
158	int		flags
159)
160{
161       FFBPtr pFfb = GET_FFB_FROM_SCRN(pScrn);
162
163       FFBLOG(("FFB_SetupForCPUToScreenAlphaTexture: "
164               "argb[%04x:%04x:%04x:%04x] alpha[T(%x):P(%d)] "
165               "wh[%d:%d] flgs[%x]\n",
166               alpha, red, green, blue,
167               maskFormat, alphaPitch,
168               width, height, flags));
169
170       FFB_SetupTextureAttrs(pFfb);
171
172       pFfb->xaa_tex = (unsigned char *) alphaPtr;
173       pFfb->xaa_tex_pitch = alphaPitch;
174       pFfb->xaa_tex_width = width;
175       pFfb->xaa_tex_height = height;
176       pFfb->xaa_tex_color = (/*((alpha >> 8) << 24) |*/
177                              ((blue >> 8) << 16) |
178                              ((green >> 8) << 8) |
179                              ((red >> 8) << 0));
180       return TRUE;
181}
182
183static void FFB_SubsequentCPUToScreenAlphaTexture(ScrnInfoPtr pScrn,
184                                                 int dstx, int dsty,
185                                                 int srcx, int srcy,
186                                                 int width, int height)
187{
188       FFBPtr pFfb = GET_FFB_FROM_SCRN(pScrn);
189       unsigned char *dst_base, *alpha_base, *sfb32;
190       unsigned int pixel_base;
191       int psz_shift = 2;
192
193       FFBLOG(("FFB_SubsequentCPUToScreenAlphaTexture: "
194               "dst[%d:%d] src[%d:%d] wh[%d:%d]\n",
195               dstx, dsty, srcx, srcy, width, height));
196
197       sfb32 = (unsigned char *) pFfb->sfb32;
198       dst_base = sfb32 + (dsty * (2048 << psz_shift)) + (dstx << psz_shift);
199       alpha_base = pFfb->xaa_tex;
200       alpha_base += srcx;
201       if (srcy)
202               alpha_base += (srcy * pFfb->xaa_tex_pitch);
203       pixel_base = pFfb->xaa_tex_color;
204       while (height--) {
205               unsigned int *dst = (unsigned int *) dst_base;
206               unsigned char *alpha = alpha_base;
207               int w = width;
208
209               while (w--) {
210                       (*dst) = (((unsigned int)*alpha << 24) | pixel_base);
211                       dst++;
212                       alpha++;
213	       }
214	       dst_base += (2048 << psz_shift);
215	       alpha_base += pFfb->xaa_tex_pitch;
216       }
217}
218
219
220static Bool FFB_SetupForCPUToScreenTexture(
221	ScrnInfoPtr	pScrn,
222	int		op,
223	CARD32		srcFormat,
224	CARD32		dstFormat,
225	CARD8		*texPtr,
226	int		texPitch,
227	int		width,
228	int		height,
229	int		flags
230)
231{
232       FFBPtr pFfb = GET_FFB_FROM_SCRN(pScrn);
233
234       FFBLOG(("FFB_SetupForCPUToScreenTexture: "
235               "TEX[T(%x):P(%d)] "
236               "wh[%d:%d] flgs[%x]\n",
237               srcFormat, texPitch,
238               width, height, flags));
239
240       FFB_SetupTextureAttrs(pFfb);
241
242       pFfb->xaa_tex = (unsigned char *) texPtr;
243       pFfb->xaa_tex_pitch = texPitch;
244       pFfb->xaa_tex_width = width;
245       pFfb->xaa_tex_height = height;
246
247       return TRUE;
248}
249
250static void FFB_SubsequentCPUToScreenTexture(ScrnInfoPtr pScrn,
251                                            int dstx, int dsty,
252                                            int srcx, int srcy,
253                                            int width, int height)
254{
255       FFBPtr pFfb = GET_FFB_FROM_SCRN(pScrn);
256       unsigned char *dst_base, *sfb32;
257       unsigned int *tex_base;
258       int psz_shift = 2;
259
260       FFBLOG(("FFB_SubsequentCPUToScreenAlphaTexture: "
261               "dst[%d:%d] src[%d:%d] wh[%d:%d]\n",
262               dstx, dsty, srcx, srcy, width, height));
263
264       sfb32 = (unsigned char *) pFfb->sfb32;
265       dst_base = sfb32 + (dsty * (2048 << psz_shift)) + (dstx << psz_shift);
266       tex_base = (unsigned int *) pFfb->xaa_tex;
267       tex_base += srcx;
268       if (srcy)
269               tex_base += (srcy * pFfb->xaa_tex_pitch);
270       while (height--) {
271               unsigned int *dst = (unsigned int *) dst_base;
272               unsigned int *tex = tex_base;
273               int w = width;
274               while (w--) {
275                       (*dst) = *tex;
276
277                       dst++;
278                       tex++;
279               }
280               dst_base += (2048 << psz_shift);
281               tex_base += pFfb->xaa_tex_pitch;
282       }
283}
284
285static void FFB_WritePixmap(ScrnInfoPtr pScrn,
286                           int x, int y, int w, int h,
287                           unsigned char *src,
288                           int srcwidth,
289                           int rop,
290                           unsigned int planemask,
291                           int trans, int bpp, int depth)
292{
293       FFBPtr pFfb = GET_FFB_FROM_SCRN(pScrn);
294       unsigned char *dst, *sfb32;
295       int psz_shift = 2;
296       ffb_fbcPtr ffb = pFfb->regs;
297
298       FFBLOG(("FFB_WritePixmap: "
299               "x[%d] y[%d] w[%d] h[%d] srcw[%d] rop[%d] pmask[%x] "
300               "trans[%d] bpp[%d] depth[%d]\n",
301               x, y, w, h, srcwidth, rop, planemask,
302               trans, bpp, depth));
303
304       FFB_ATTR_SFB_VAR_XAA(pFfb, planemask, rop);
305       FFBWait(pFfb, ffb);
306
307       sfb32 = (unsigned char *) pFfb->sfb32;
308       dst = sfb32 + (y * (2048 << psz_shift)) + (x << psz_shift);
309       VISmoveImageLR(src, dst, w << psz_shift, h,
310                      srcwidth, (2048 << psz_shift));
311}
312
313static void FFB_SetupForMono8x8PatternFill(ScrnInfoPtr pScrn,
314                                          int pat_word1, int pat_word2,
315                                          int fg, int bg, int rop,
316                                          unsigned int planemask)
317{
318       FFBPtr pFfb = GET_FFB_FROM_SCRN(pScrn);
319       ffb_fbcPtr ffb = pFfb->regs;
320       unsigned int ppc, ppc_mask, fbc;
321       int i;
322
323       FFBLOG(("FFB_SetupForMono8x8PatternFill: "
324               "pat[%08x:%08x] fg[%x] bg[%x] rop[%d] pmask[%x]\n",
325               pat_word1, pat_word2,
326               fg, bg, rop, planemask));
327
328       ppc = FFB_PPC_ABE_DISABLE | FFB_PPC_APE_ENABLE | FFB_PPC_CS_CONST;
329       if (bg < 0)
330               ppc |= FFB_PPC_TBE_TRANSPARENT;
331       else
332               ppc |= FFB_PPC_TBE_OPAQUE;
333       ppc_mask = FFB_PPC_ABE_MASK | FFB_PPC_APE_MASK |
334         FFB_PPC_TBE_MASK | FFB_PPC_CS_MASK;
335       fbc = pFfb->fbc;
336       rop = (rop | FFB_ROP_EDIT_BIT) | (FFB_ROP_NEW << 8);
337
338       FFB_ATTR_RAW(pFfb, ppc, ppc_mask, planemask, rop,
339                    FFB_DRAWOP_RECTANGLE, fg, fbc, pFfb->wid);
340       if (bg >= 0)
341               FFB_WRITE_BG(pFfb, ffb, bg);
342
343       FFBFifo(pFfb, 32);
344       for (i = 0; i < 32; i += 2) {
345               CARD32 val1, val2;
346               int shift = (24 - ((i % 4) * 8));
347
348               if ((i % 8) < 4) {
349                       val1 = (pat_word1 >> shift) & 0xff;
350                       val2 = (pat_word1 >> (shift + 8)) & 0xff;
351               } else {
352                       val1 = (pat_word2 >> shift) & 0xff;
353                       val2 = (pat_word2 >> (shift + 8)) & 0xff;
354               }
355               val1 |= (val1 << 8) | (val1 << 16) | (val1 << 24);
356               val2 |= (val2 << 8) | (val2 << 16) | (val2 << 24);
357               FFB_WRITE64(&ffb->pattern[i], val1, val2);
358       }
359       pFfb->rp_active = 1;
360}
361
362static void FFB_SubsequentMono8x8PatternFillRect(ScrnInfoPtr pScrn,
363                                                int pat_word1, int pat_word2,
364                                                int x, int y, int w, int h)
365{
366       FFBPtr pFfb = GET_FFB_FROM_SCRN(pScrn);
367       ffb_fbcPtr ffb = pFfb->regs;
368
369       FFBLOG(("FFB_SubsequentMono8x8PatternFillRect: "
370               "x[%d] y[%d] w[%d] h[%d]\n", x, y, w, h));
371
372       FFBFifo(pFfb, 4);
373       FFB_WRITE64(&ffb->by, y, x);
374       FFB_WRITE64_2(&ffb->bh, h, w);
375}
376
377static void FFB_SetupForScanlineCPUToScreenColorExpandFill(ScrnInfoPtr pScrn,
378                                                          int fg, int bg,
379                                                          int rop,
380                                                          unsigned int planemask)
381{
382       FFBPtr pFfb = GET_FFB_FROM_SCRN(pScrn);
383       ffb_fbcPtr ffb = pFfb->regs;
384       unsigned int ppc, ppc_mask, fbc;
385
386       FFBLOG(("FFB_SetupForScanlineCPUToScreenColorExpandFill: "
387               "fg[%x] bg[%x] rop[%d] pmask[%x]\n",
388               fg, bg, rop, planemask));
389
390       ppc = FFB_PPC_ABE_DISABLE | FFB_PPC_APE_DISABLE | FFB_PPC_CS_CONST;
391       if (bg < 0)
392               ppc |= FFB_PPC_TBE_TRANSPARENT;
393       else
394               ppc |= FFB_PPC_TBE_OPAQUE;
395       ppc_mask = FFB_PPC_ABE_MASK | FFB_PPC_APE_MASK |
396         FFB_PPC_TBE_MASK | FFB_PPC_CS_MASK;
397       fbc = pFfb->fbc;
398       rop = (rop | FFB_ROP_EDIT_BIT) | (FFB_ROP_NEW << 8);
399
400       if ((pFfb->ppc_cache & ppc_mask) != ppc ||
401           pFfb->fg_cache != fg ||
402           pFfb->fbc_cache != fbc ||
403           pFfb->rop_cache != rop ||
404           pFfb->pmask_cache != planemask ||
405           pFfb->fontinc_cache != ((0<<16) | 32) ||
406           (bg >= 0 && pFfb->bg_cache != bg)) {
407               pFfb->ppc_cache &= ~ppc_mask;
408               pFfb->ppc_cache |= ppc;
409               pFfb->fg_cache = fg;
410               pFfb->fbc_cache = fbc;
411               pFfb->rop_cache = rop;
412               pFfb->pmask_cache = planemask;
413               pFfb->fontinc_cache = ((0<<16) | 32);
414               if (bg >= 0)
415                       pFfb->bg_cache = bg;
416               FFBFifo(pFfb, (bg >= 0 ? 7 : 6));
417               ffb->ppc = ppc;
418               ffb->fg = fg;
419               ffb->fbc = fbc;
420               ffb->rop = rop;
421               ffb->pmask = planemask;
422               ffb->fontinc = ((0 << 16) | 32);
423               if(bg >= 0)
424                       ffb->bg = bg;
425       }
426       pFfb->rp_active = 1;
427}
428
429static void FFB_SubsequentScanlineCPUToScreenColorExpandFill(ScrnInfoPtr pScrn,
430                                                            int x, int y, int w, int h,
431                                                            int skipleft)
432{
433       FFBPtr pFfb = GET_FFB_FROM_SCRN(pScrn);
434       FFBLOG(("FFB_SubsequentCPUToScreenColorExpandFill: "
435               "x[%d] y[%d] w[%d] h[%d] skipleft[%d]\n",
436               x, y, w, h, skipleft));
437
438       pFfb->xaa_scanline_x = x;
439       pFfb->xaa_scanline_y = y;
440       pFfb->xaa_scanline_w = w;
441}
442
443static void FFB_SubsequentColorExpandScanline(ScrnInfoPtr pScrn, int bufno)
444{
445       FFBPtr pFfb = GET_FFB_FROM_SCRN(pScrn);
446       ffb_fbcPtr ffb = pFfb->regs;
447       CARD32 *bits = (CARD32 *) pFfb->xaa_scanline_buffers[bufno];
448       int w;
449
450       FFBFifo(pFfb, 1);
451       ffb->fontxy = ((pFfb->xaa_scanline_y << 16) | pFfb->xaa_scanline_x);
452
453       w = pFfb->xaa_scanline_w;
454       if (w >= 32) {
455               FFB_WRITE_FONTW(pFfb, ffb, 32);
456               FFBFifo(pFfb, (w / 32));
457               do {
458                       ffb->font = *bits++;
459                       w -= 32;
460               } while (w >= 32);
461       }
462       if (w > 0) {
463               FFB_WRITE_FONTW(pFfb, ffb, w);
464               FFBFifo(pFfb, 1);
465               ffb->font = *bits++;
466       }
467
468       pFfb->xaa_scanline_y++;
469}
470
471static void FFB_SetupForDashedLine(ScrnInfoPtr pScrn,
472                                  int fg, int bg, int rop,
473                                  unsigned int planemask,
474                                  int length, unsigned char *pattern)
475{
476       FFBPtr pFfb = GET_FFB_FROM_SCRN(pScrn);
477       CARD32 *pat_ptr = (CARD32 *)pattern;
478       unsigned int ppc, ppc_mask, fbc;
479
480       FFBLOG(("FFB_SetupForDashedLine: "
481               "fg[%x] bg[%x] rop[%d] pmask[%x] patlen[%d] pat[%x]\n",
482               fg, bg, rop, planemask, length, *pat_ptr));
483
484       pFfb->planemask = planemask;
485       pFfb->xaa_rop = rop;
486       pFfb->xaa_linepat =
487               (*pat_ptr << FFB_LPAT_PATTERN_SHIFT) |
488               (1 << FFB_LPAT_SCALEVAL_SHIFT) |
489               ((length & 0xf) << FFB_LPAT_PATLEN_SHIFT);
490
491       fbc = pFfb->fbc;
492       ppc = FFB_PPC_ABE_DISABLE | FFB_PPC_APE_DISABLE | FFB_PPC_CS_CONST | FFB_PPC_XS_WID;
493       ppc_mask = FFB_PPC_ABE_MASK | FFB_PPC_APE_MASK | FFB_PPC_CS_MASK | FFB_PPC_XS_MASK;
494
495       FFB_ATTR_RAW(pFfb, ppc, ppc_mask, planemask,
496                    (FFB_ROP_EDIT_BIT | rop) | (FFB_ROP_NEW << 8),
497                    FFB_DRAWOP_BRLINEOPEN, fg, fbc, pFfb->wid);
498       pFfb->rp_active = 1;
499}
500
501static void FFB_SubsequentDashedTwoPointLine( ScrnInfoPtr pScrn,
502                                             int x1, int y1,
503                                             int x2, int y2,
504                                             int flags, int phase)
505{
506       FFBPtr pFfb = GET_FFB_FROM_SCRN(pScrn);
507       ffb_fbcPtr ffb = pFfb->regs;
508       unsigned int linepat = pFfb->xaa_linepat;
509       unsigned int drawop;
510
511       FFBLOG(("FFB_SubsequentDashedTwoPointLine: "
512               "x1[%d] y1[%d] x2[%d] y2[%d] flgs[%x] phase[%d]\n",
513               x1, y2, x2, y2, flags, phase));
514
515       linepat |= (phase & 0xf) << FFB_LPAT_PATPTR_SHIFT;
516
517       drawop = (flags & OMIT_LAST) ?
518         FFB_DRAWOP_BRLINEOPEN : FFB_DRAWOP_BRLINECAP;
519       FFB_WRITE_DRAWOP(pFfb, ffb, drawop);
520
521       if (pFfb->has_brline_bug) {
522               FFBFifo(pFfb, 6);
523               ffb->ppc = 0;
524       } else
525               FFBFifo(pFfb, 5);
526       ffb->lpat = linepat;
527       FFB_WRITE64(&ffb->by, y1, x1);
528       FFB_WRITE64_2(&ffb->bh, y2, x2);
529}
530
531static void FFB_SetupForSolidLine(ScrnInfoPtr pScrn,
532                                 int color, int rop, unsigned int planemask)
533{
534       FFBPtr pFfb = GET_FFB_FROM_SCRN(pScrn);
535       ffb_fbcPtr ffb = pFfb->regs;
536       unsigned int ppc, ppc_mask, fbc;
537       FFBLOG(("FFB_SetupForSolidLine: "
538               "color[%d] rop[%d] pmask[%x]\n",
539               color, rop, planemask));
540
541       pFfb->planemask = planemask;
542       pFfb->xaa_rop = rop;
543
544       fbc = pFfb->fbc;
545       ppc = FFB_PPC_ABE_DISABLE | FFB_PPC_APE_DISABLE | FFB_PPC_CS_CONST | FFB_PPC_XS_WID;
546       ppc_mask = FFB_PPC_ABE_MASK | FFB_PPC_APE_MASK | FFB_PPC_CS_MASK | FFB_PPC_XS_MASK;
547
548       FFB_ATTR_RAW(pFfb, ppc, ppc_mask, planemask,
549                    (FFB_ROP_EDIT_BIT | rop) | (FFB_ROP_NEW << 8),
550                    FFB_DRAWOP_BRLINEOPEN, color, fbc, pFfb->wid);
551       FFBFifo(pFfb, 1);
552       ffb->lpat = 0;
553       pFfb->rp_active = 1;
554}
555
556static void FFB_SubsequentSolidTwoPointLine(ScrnInfoPtr pScrn,
557                                           int x1, int y1,
558                                           int x2, int y2,
559                                           int flags)
560{
561       FFBPtr pFfb = GET_FFB_FROM_SCRN(pScrn);
562       ffb_fbcPtr ffb = pFfb->regs;
563       int drawop;
564
565       FFBLOG(("FFB_SubsequentSolidTwoPointLine: "
566               "x1[%d] y1[%d] x2[%d] y2[%d] flags[%d]\n",
567               x1, y1, x2, y2, flags));
568
569       drawop = (flags & OMIT_LAST) ?
570         FFB_DRAWOP_BRLINEOPEN : FFB_DRAWOP_BRLINECAP;
571       FFB_WRITE_DRAWOP(pFfb, ffb, drawop);
572
573       if (pFfb->has_brline_bug) {
574               FFBFifo(pFfb, 5);
575               ffb->ppc = 0;
576       } else
577               FFBFifo(pFfb, 4);
578       FFB_WRITE64(&ffb->by, y1, x1);
579       FFB_WRITE64_2(&ffb->bh, y2, x2);
580}
581
582void FFB_SetupForSolidFill(ScrnInfoPtr pScrn,
583                          int color, int rop, unsigned int planemask)
584{
585       FFBPtr pFfb = GET_FFB_FROM_SCRN(pScrn);
586       unsigned int ppc, ppc_mask, fbc;
587
588       FFBLOG(("FFB_SetupForSolidFill: "
589               "color[%d] rop[%d] pmask[%u]\n",
590               color, rop, planemask));
591
592       pFfb->planemask = planemask;
593       pFfb->xaa_rop = rop;
594
595       fbc = pFfb->fbc;
596       if (pFfb->ffb_res == ffb_res_high)
597               fbc |= FFB_FBC_WB_B;
598       ppc = FFB_PPC_ABE_DISABLE | FFB_PPC_APE_DISABLE | FFB_PPC_CS_CONST | FFB_PPC_XS_WID;
599       ppc_mask = FFB_PPC_ABE_MASK | FFB_PPC_APE_MASK | FFB_PPC_CS_MASK | FFB_PPC_XS_MASK;
600
601       FFB_ATTR_RAW(pFfb, ppc, ppc_mask, planemask,
602                    (FFB_ROP_EDIT_BIT | rop) | (FFB_ROP_NEW << 8),
603                    FFB_DRAWOP_RECTANGLE, color, fbc, pFfb->wid);
604       pFfb->rp_active = 1;
605}
606
607void FFB_SubsequentSolidFillRect(ScrnInfoPtr pScrn,
608                                int x, int y,
609                                int w, int h)
610{
611       FFBPtr pFfb = GET_FFB_FROM_SCRN(pScrn);
612       ffb_fbcPtr ffb = pFfb->regs;
613
614       FFBLOG(("FFB_SubsequentSolidFillRect: "
615               "x[%d] y[%d] w[%d] h[%d]\n", x, y, w, h));
616
617       FFBFifo(pFfb, 4);
618       FFB_WRITE64(&ffb->by, y, x);
619       FFB_WRITE64_2(&ffb->bh, h, w);
620}
621
622static void FFB_ScreenToScreenBitBlt(ScrnInfoPtr pScrn,
623                                    int nbox,
624                                    DDXPointPtr pptSrc,
625                                    BoxPtr pbox,
626                                    int xdir, int ydir,
627                                    int rop, unsigned int planemask)
628{
629       FFBPtr pFfb = GET_FFB_FROM_SCRN(pScrn);
630       ffb_fbcPtr ffb = pFfb->regs;
631       int use_vscroll;
632
633       FFBLOG(("FFB_ScreenToScreenBitBlt: "
634               "nbox[%d] xdir[%d] ydir[%d] rop[%d] pmask[%x]\n",
635               nbox, xdir, ydir, rop, planemask));
636
637       use_vscroll = 0;
638       if (!pFfb->disable_vscroll &&
639           rop == GXcopy) {
640               int i;
641
642               for (i = 0; i < nbox; i++)
643                       if (pptSrc[i].x != pbox[i].x1 ||
644                           pptSrc[i].y == pbox[i].y1)
645                               break;
646               if (i == nbox) {
647                       /* If/When double buffer extension is re-enabled
648                        * check buffers here.
649                        */
650                       use_vscroll = 1;
651               }
652       }
653       if (use_vscroll) {
654               FFB_ATTR_VSCROLL_XAA(pFfb, planemask);
655               while (nbox--) {
656                       FFBFifo(pFfb, 7);
657                       ffb->drawop = FFB_DRAWOP_VSCROLL;
658                       FFB_WRITE64(&ffb->by, pptSrc->y, pptSrc->x);
659                       FFB_WRITE64_2(&ffb->dy, pbox->y1, pbox->x1);
660                       FFB_WRITE64_3(&ffb->bh, (pbox->y2 - pbox->y1),
661                                     (pbox->x2 - pbox->x1));
662
663                       pbox++;
664                       pptSrc++;
665               }
666               pFfb->rp_active = 1;
667               SET_SYNC_FLAG(pFfb->pXAAInfo);
668       } else {
669               unsigned char *sfb32 = (unsigned char *) pFfb->sfb32;
670               int psz_shift = 2;
671
672               FFB_ATTR_SFB_VAR_XAA(pFfb, planemask, rop);
673               if (pFfb->use_blkread_prefetch) {
674                       unsigned int bit;
675
676                       if (xdir < 0)
677                               bit = FFB_MER_EDRA;
678                       else
679                               bit = FFB_MER_EIRA;
680                       FFBFifo(pFfb, 1);
681                       ffb->mer = bit;
682                       pFfb->rp_active = 1;
683               }
684               FFBWait(pFfb, ffb);
685
686               while (nbox--) {
687                       unsigned char *src, *dst;
688                       int x1, y1, x2, y2;
689                       int width, height;
690                       int sdkind;
691
692                       x1 = pptSrc->x;
693                       y1 = pptSrc->y;
694                       x2 = pbox->x1;
695                       y2 = pbox->y1;
696                       width = (pbox->x2 - pbox->x1);
697                       height = (pbox->y2 - pbox->y1);
698
699                       src = sfb32 + (y1 * (2048 << psz_shift))
700                               + (x1 << psz_shift);
701                       dst = sfb32 + (y2 * (2048 << psz_shift))
702                               + (x2 << psz_shift);
703                       sdkind = (2048 << psz_shift);
704
705                       if (ydir < 0) {
706                               src += ((height - 1) * (2048 << psz_shift));
707                               dst += ((height - 1) * (2048 << psz_shift));
708                               sdkind = -sdkind;
709                       }
710                       width <<= psz_shift;
711                       if (xdir < 0)
712                               VISmoveImageRL(src, dst, width, height,
713                                              sdkind, sdkind);
714                       else
715                               VISmoveImageLR(src, dst, width, height,
716                                              sdkind, sdkind);
717                       pbox++;
718                       pptSrc++;
719	       }
720               if (pFfb->use_blkread_prefetch) {
721                       FFBFifo(pFfb, 1);
722                       ffb->mer = FFB_MER_DRA;
723                       pFfb->rp_active = 1;
724                       FFBWait(pFfb, ffb);
725               }
726       }
727}
728
729void FFB_SetupForScreenToScreenCopy(ScrnInfoPtr pScrn,
730                                   int xdir, int ydir, int rop,
731                                   unsigned int planemask,
732                                   int trans_color)
733{
734       FFBPtr pFfb = GET_FFB_FROM_SCRN(pScrn);
735       ffb_fbcPtr ffb = pFfb->regs;
736       FFBLOG(("FFB_SetupForScreenToScreenCopy: "
737               "xdir[%d] ydir[%d] rop[%d] pmask[%x] tcolor[%d]\n",
738               xdir, ydir, rop, planemask, trans_color));
739
740       pFfb->planemask = planemask;
741       pFfb->xaa_xdir = xdir;
742       pFfb->xaa_ydir = ydir;
743       pFfb->xaa_rop = rop;
744       FFB_ATTR_SFB_VAR_XAA(pFfb, planemask, rop);
745       FFBWait(pFfb, ffb);
746}
747
748void FFB_SubsequentScreenToScreenCopy(ScrnInfoPtr pScrn,
749                                     int x1, int y1,
750                                     int x2, int y2,
751                                     int width, int height)
752{
753       FFBPtr pFfb = GET_FFB_FROM_SCRN(pScrn);
754       unsigned char *src, *dst, *sfb32;
755       int psz_shift = 2;
756       int sdkind;
757
758       FFBLOG(("FFB_SubsequentScreenToScreenCopy: "
759               "x1[%d] y1[%d] x2[%d] y2[%u] w[%d] h[%d]\n",
760               x1, y1, x2, y2, width, height));
761
762       sfb32 = (unsigned char *) pFfb->sfb32;
763       src = sfb32 + (y1 * (2048 << psz_shift)) + (x1 << psz_shift);
764       dst = sfb32 + (y2 * (2048 << psz_shift)) + (x2 << psz_shift);
765       sdkind = (2048 << psz_shift);
766
767       if (pFfb->xaa_ydir < 0) {
768               src += ((height - 1) * (2048 << psz_shift));
769               dst += ((height - 1) * (2048 << psz_shift));
770               sdkind = -sdkind;
771       }
772
773       width <<= psz_shift;
774       if (pFfb->xaa_xdir < 0)
775               VISmoveImageRL(src, dst, width, height, sdkind, sdkind);
776       else
777               VISmoveImageLR(src, dst, width, height, sdkind, sdkind);
778}
779
780static void FFB_Sync(ScrnInfoPtr pScrn)
781{
782       FFBPtr pFfb = GET_FFB_FROM_SCRN(pScrn);
783       ffb_fbcPtr ffb = pFfb->regs;
784
785       FFB_ATTR_SFB_VAR_XAA(pFfb, 0xffffffff, GXcopy);
786       FFBWait(pFfb, ffb);
787}
788
789#endif
790
791Bool FFBAccelInit(ScreenPtr pScreen, FFBPtr pFfb)
792{
793#ifdef HAVE_XAA_H
794	XAAInfoRecPtr infoRec;
795	ffb_fbcPtr ffb = pFfb->regs;
796
797	pFfb->fbc = (FFB_FBC_WB_A | FFB_FBC_WM_COMBINED | FFB_FBC_RB_A |
798			 FFB_FBC_WE_FORCEON |
799			 FFB_FBC_SB_BOTH |
800			 FFB_FBC_ZE_OFF | FFB_FBC_YE_OFF |
801			 FFB_FBC_RGBE_MASK |
802			 FFB_FBC_XE_ON);
803	pFfb->wid = FFBWidAlloc(pFfb, TrueColor, 0, TRUE);
804	if (pFfb->wid == (unsigned int) -1)
805		return FALSE;
806
807	pFfb->pXAAInfo = infoRec = XAACreateInfoRec();
808	if (!infoRec) {
809		FFBWidFree(pFfb, pFfb->wid);
810		return FALSE;
811	}
812
813	pFfb->xaa_scanline_buffers[0] = malloc(2048 * 4);
814	if (!pFfb->xaa_scanline_buffers[0]) {
815		XAADestroyInfoRec(infoRec);
816		return FALSE;
817	}
818
819	pFfb->xaa_scanline_buffers[1] = malloc(2048 * 4);
820	if (!pFfb->xaa_scanline_buffers[1]) {
821		free(pFfb->xaa_scanline_buffers[0]);
822		XAADestroyInfoRec(infoRec);
823		return FALSE;
824	}
825
826	infoRec->Sync = FFB_Sync;
827
828	/* Use VIS and VSCROLL for screen to screen copies.  */
829	infoRec->ScreenToScreenCopyFlags = NO_TRANSPARENCY;
830	infoRec->SetupForScreenToScreenCopy =
831		FFB_SetupForScreenToScreenCopy;
832	infoRec->SubsequentScreenToScreenCopy =
833		FFB_SubsequentScreenToScreenCopy;
834
835	/* In order to optimize VSCROLL and prefetching properly we
836	 * have to use our own mid-layer routine.
837	 */
838	infoRec->ScreenToScreenBitBltFlags = NO_TRANSPARENCY;
839	infoRec->ScreenToScreenBitBlt =
840		FFB_ScreenToScreenBitBlt;
841
842	infoRec->SolidFillFlags = 0;
843	infoRec->SetupForSolidFill =
844		FFB_SetupForSolidFill;
845	infoRec->SubsequentSolidFillRect =
846		FFB_SubsequentSolidFillRect;
847
848	infoRec->SolidLineFlags = 0;
849	infoRec->SetupForSolidLine =
850		FFB_SetupForSolidLine;
851	infoRec->SubsequentSolidTwoPointLine =
852		FFB_SubsequentSolidTwoPointLine;
853	miSetZeroLineBias(pScreen, OCTANT3 | OCTANT4 | OCTANT6 | OCTANT1);
854
855	infoRec->DashedLineFlags = (TRANSPARENCY_ONLY |
856				    LINE_PATTERN_LSBFIRST_LSBJUSTIFIED);
857	infoRec->DashPatternMaxLength = 16;
858	infoRec->SetupForDashedLine =
859		FFB_SetupForDashedLine;
860	infoRec->SubsequentDashedTwoPointLine =
861		FFB_SubsequentDashedTwoPointLine;
862
863	/* We cannot use the non-scanline color expansion mechanism on FFB
864	 * for two reasons:
865	 *
866	 * 1) A render pass can only render 32-pixels wide on FFB, XAA expects
867	 *    that arbitrary widths are possible per render pass.
868	 *
869	 * 2) The FFB accelerator FIFO is only 100 or so words deep, and
870	 *    XAA gives no way to limit the number of words it writes into
871	 *    the ColorExpandBase register per rendering pass.
872	 */
873	infoRec->ScanlineColorExpandBuffers = pFfb->xaa_scanline_buffers;
874	infoRec->NumScanlineColorExpandBuffers = 2;
875	infoRec->ScanlineCPUToScreenColorExpandFillFlags =
876		CPU_TRANSFER_PAD_DWORD |
877		SCANLINE_PAD_DWORD |
878		CPU_TRANSFER_BASE_FIXED |
879		BIT_ORDER_IN_BYTE_LSBFIRST;
880	infoRec->SetupForScanlineCPUToScreenColorExpandFill =
881		FFB_SetupForScanlineCPUToScreenColorExpandFill;
882	infoRec->SubsequentScanlineCPUToScreenColorExpandFill =
883		FFB_SubsequentScanlineCPUToScreenColorExpandFill;
884	infoRec->SubsequentColorExpandScanline =
885		FFB_SubsequentColorExpandScanline;
886
887	infoRec->Mono8x8PatternFillFlags =
888		HARDWARE_PATTERN_PROGRAMMED_BITS |
889		HARDWARE_PATTERN_SCREEN_ORIGIN |
890		BIT_ORDER_IN_BYTE_LSBFIRST;
891	infoRec->SetupForMono8x8PatternFill =
892		FFB_SetupForMono8x8PatternFill;
893	infoRec->SubsequentMono8x8PatternFillRect =
894		FFB_SubsequentMono8x8PatternFillRect;
895
896	/* Use VIS for pixmap writes.  */
897	infoRec->WritePixmap = FFB_WritePixmap;
898
899	/* RENDER optimizations.  */
900	infoRec->CPUToScreenAlphaTextureFlags =
901		XAA_RENDER_NO_TILE |
902		XAA_RENDER_NO_SRC_ALPHA;
903	infoRec->CPUToScreenAlphaTextureFormats = FFBAlphaTextureFormats;
904	infoRec->CPUToScreenAlphaTextureDstFormats = FFBTextureDstFormats;
905	infoRec->SetupForCPUToScreenAlphaTexture2 =
906		FFB_SetupForCPUToScreenAlphaTexture;
907	infoRec->SubsequentCPUToScreenAlphaTexture =
908		FFB_SubsequentCPUToScreenAlphaTexture;
909
910	infoRec->CPUToScreenTextureFlags =
911		XAA_RENDER_NO_TILE |
912		XAA_RENDER_NO_SRC_ALPHA;
913	infoRec->CPUToScreenTextureFormats = FFBTextureFormats;
914	infoRec->CPUToScreenTextureDstFormats = FFBTextureDstFormats;
915	infoRec->SetupForCPUToScreenTexture2 =
916		FFB_SetupForCPUToScreenTexture;
917	infoRec->SubsequentCPUToScreenTexture =
918		FFB_SubsequentCPUToScreenTexture;
919
920	pFfb->fifo_cache = 0;
921
922	FFB_DEBUG_init();
923	FDEBUG((FDEBUG_FD,
924		"FFB: cfg0(%08x) cfg1(%08x) cfg2(%08x) cfg3(%08x) ppcfg(%08x)\n",
925		ffb->fbcfg0, ffb->fbcfg1, ffb->fbcfg2, ffb->fbcfg3, ffb->ppcfg));
926
927	FFB_HardwareSetup(pFfb);
928
929	pFfb->ppc_cache = (FFB_PPC_FW_DISABLE |
930			   FFB_PPC_VCE_DISABLE | FFB_PPC_APE_DISABLE | FFB_PPC_CS_CONST |
931			   FFB_PPC_XS_WID | FFB_PPC_YS_CONST | FFB_PPC_ZS_CONST |
932			   FFB_PPC_DCE_DISABLE | FFB_PPC_ABE_DISABLE | FFB_PPC_TBE_OPAQUE);
933	pFfb->wid_cache = pFfb->wid;
934	pFfb->pmask_cache = ~0;
935	pFfb->rop_cache = (FFB_ROP_NEW | (FFB_ROP_NEW << 8));
936	pFfb->drawop_cache = FFB_DRAWOP_RECTANGLE;
937	pFfb->fg_cache = pFfb->bg_cache = 0;
938	pFfb->fontw_cache = 32;
939	pFfb->fontinc_cache = (1 << 16) | 0;
940	pFfb->fbc_cache = (FFB_FBC_WB_A | FFB_FBC_WM_COMBINED | FFB_FBC_RB_A |
941			   FFB_FBC_WE_FORCEON |
942			   FFB_FBC_SB_BOTH |
943			   FFB_FBC_ZE_OFF | FFB_FBC_YE_OFF |
944			   FFB_FBC_RGBE_OFF |
945			   FFB_FBC_XE_ON);
946	pFfb->laststipple = NULL;
947
948	/* We will now clear the screen: we'll draw a rectangle covering all the
949	 * viewscreen, using a 'blackness' ROP.
950	 */
951	FFBFifo(pFfb, 22);
952	ffb->fbc = pFfb->fbc_cache;
953	ffb->ppc = pFfb->ppc_cache;
954	ffb->wid = pFfb->wid_cache;
955	ffb->xpmask = 0xff;
956	ffb->pmask = pFfb->pmask_cache;
957	ffb->rop = pFfb->rop_cache;
958	ffb->drawop = pFfb->drawop_cache;
959	ffb->fg = pFfb->fg_cache;
960	ffb->bg = pFfb->bg_cache;
961	ffb->fontw = pFfb->fontw_cache;
962	ffb->fontinc = pFfb->fontinc_cache;
963	ffb->xclip = FFB_XCLIP_TEST_ALWAYS;
964	ffb->cmp = 0x80808080;
965	ffb->matchab = 0x80808080;
966	ffb->magnab = 0x80808080;
967	ffb->blendc = (FFB_BLENDC_FORCE_ONE |
968		       FFB_BLENDC_DF_ONE_M_A |
969		       FFB_BLENDC_SF_A);
970	ffb->blendc1 = 0;
971	ffb->blendc2 = 0;
972	FFB_WRITE64(&ffb->by, 0, 0);
973	FFB_WRITE64_2(&ffb->bh, pFfb->psdp->height, pFfb->psdp->width);
974	pFfb->rp_active = 1;
975	FFBWait(pFfb, ffb);
976
977	FFB_ATTR_SFB_VAR_XAA(pFfb, 0xffffffff, GXcopy);
978	FFBWait(pFfb, ffb);
979
980	if (!XAAInit(pScreen, infoRec)) {
981		XAADestroyInfoRec(infoRec);
982		free(pFfb->xaa_scanline_buffers[0]);
983		free(pFfb->xaa_scanline_buffers[1]);
984		pFfb->pXAAInfo = NULL;
985		FFBWidFree(pFfb, pFfb->wid);
986		return FALSE;
987	}
988	/* Success */
989	return TRUE;
990#else
991	return FALSE;
992#endif
993}
994