AMD64.WMTransitions.Mod 22 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731732733734735736737738739740741742743744745746747748749750751752753754755756757758759760761762763764765766767768769770771772773774775776777778779780781782783784785786787788789790791792793794
  1. MODULE WMTransitions;
  2. IMPORT
  3. SYSTEM, BIT, Raster, WMGraphics, WMGraphicUtilities, WMRectangles, WMWindowManager, Machine, KernelLog;
  4. CONST
  5. DEBUG = FALSE;
  6. TYPE
  7. Transition* = OBJECT
  8. PROCEDURE Init*(w, h : LONGINT);
  9. END Init;
  10. PROCEDURE CalcImage*(a, b, result : Raster.Image; per255 : LONGINT);
  11. END CalcImage;
  12. END Transition;
  13. TYPE
  14. TransitionMask* = OBJECT(Transition)
  15. VAR
  16. mW, mH : LONGINT;
  17. mask : POINTER TO ARRAY OF CHAR;
  18. PROCEDURE Init*(w, h : LONGINT);
  19. BEGIN
  20. mW := w; mH := h;
  21. END Init;
  22. PROCEDURE SetMask*(mi : Raster.Image);
  23. VAR x, y, col, i, tr, tg, tb, ta : LONGINT;
  24. adr: ADDRESS;
  25. ti : Raster.Image;
  26. mode : Raster.Mode;
  27. pix : Raster.Pixel;
  28. c : WMGraphics.BufferCanvas;
  29. BEGIN
  30. IF (mi.width # mW) OR (mi.height # mH) THEN
  31. NEW(ti); Raster.Create(ti, mW, mH, Raster.BGR888);
  32. NEW(c, ti);
  33. c.ScaleImage(mi, WMRectangles.MakeRect(0, 0, mi.width - 1, mi.height - 1),
  34. WMRectangles.MakeRect(0, 0, ti.width - 1, ti.height - 1), WMGraphics.ModeCopy, WMGraphics.ScaleBilinear);
  35. mi := ti
  36. END;
  37. NEW(SELF.mask, mW * mH);
  38. i := 0;
  39. IF (mi.fmt.code = Raster.bgr565) THEN
  40. FOR y := 0 TO mi.height -1 DO
  41. adr := mi.adr + y * mi.bpr;
  42. FOR x := 0 TO mi.width - 1 DO
  43. col := SYSTEM.GET16(adr + x * 2);
  44. mask[i] := CHR((col DIV 32 MOD 64) * 4);
  45. INC(i)
  46. END
  47. END
  48. ELSIF (mi.fmt.code = Raster.bgr888) THEN
  49. FOR y := 0 TO mi.height -1 DO
  50. adr := mi.adr + y * mi.bpr;
  51. FOR x := 0 TO mi.width - 1 DO
  52. mask[i] := CHR(SYSTEM.GET8(adr + x * 3 + 1));
  53. INC(i)
  54. END
  55. END
  56. ELSE
  57. Raster.InitMode(mode, Raster.srcCopy);
  58. FOR y := 0 TO mi.height -1 DO
  59. FOR x := 0 TO mi.width - 1 DO
  60. Raster.Get(mi, x, y, pix, mode);
  61. Raster.GetRGBA(pix, tr, tg, tb, ta);
  62. mask[i] := CHR(tg);
  63. INC(i)
  64. END
  65. END
  66. END;
  67. END SetMask;
  68. PROCEDURE DumpMask;
  69. VAR i, x, y : LONGINT;
  70. w : WMWindowManager.BufferWindow;
  71. BEGIN
  72. NEW(w, mW, mH, FALSE);
  73. i := 0;
  74. FOR y := 0 TO mH -1 DO
  75. FOR x := 0 TO mW - 1 DO
  76. w.canvas.SetPixel(x, y, WMGraphics.RGBAToColor(0, ORD(mask[i]), 0, 255), WMGraphics.ModeCopy);
  77. INC(i)
  78. END
  79. END;
  80. WMWindowManager.DefaultAddWindow(w);
  81. END DumpMask;
  82. PROCEDURE CalcImage*(a, b, result : Raster.Image; per255 : LONGINT);
  83. VAR i, x, y, col : LONGINT;
  84. adra, adrb, adrr: ADDRESS;
  85. mode : Raster.Mode;
  86. pix : Raster.Pixel;
  87. BEGIN
  88. IF (a = NIL) OR (b = NIL) OR (result = NIL) OR
  89. (a.height # b.height) OR (a.width # b.width) OR (result.height # result.height) OR
  90. (a.fmt.code # b.fmt.code) OR (a.fmt.code # b.fmt.code) OR (result.fmt.code # result.fmt.code)
  91. THEN
  92. RETURN
  93. END;
  94. i := 0;
  95. IF (a.fmt.code = Raster.bgr565) THEN
  96. FOR y := 0 TO a.height -1 DO
  97. adra := a.adr + y * a.bpr;
  98. adrb := b.adr + y * b.bpr;
  99. adrr := result.adr + y * result.bpr;
  100. FOR x := 0 TO a.width - 1 DO
  101. IF ORD(mask[i]) <= per255 THEN col := SYSTEM.GET16(adra + x * 2)
  102. ELSE col := SYSTEM.GET16(adrb + x * 2)
  103. END;
  104. SYSTEM.PUT16(adrr + x * 2, col);
  105. INC(i)
  106. END
  107. END
  108. ELSIF (a.fmt.code = Raster.bgr888) THEN
  109. FOR y := 0 TO a.height -1 DO
  110. adra := a.adr + y * a.bpr;
  111. adrb := b.adr + y * b.bpr;
  112. adrr := result.adr + y * result.bpr;
  113. FOR x := 0 TO a.width - 1 DO
  114. IF ORD(mask[i]) <= per255 THEN SYSTEM.MOVE(adra + x * 3, adrr + x * 3, 3)
  115. ELSE SYSTEM.MOVE(adrb + x * 3, adrr + x * 3, 3)
  116. END;
  117. INC(i)
  118. END
  119. END
  120. ELSE
  121. Raster.InitMode(mode, Raster.srcCopy);
  122. FOR y := 0 TO a.height -1 DO
  123. FOR x := 0 TO a.width - 1 DO
  124. IF ORD(mask[i]) <= per255 THEN Raster.Get(a, x, y, pix, mode)
  125. ELSE Raster.Get(b, x, y, pix, mode)
  126. END;
  127. Raster.Put(result, x, y, pix, mode);
  128. INC(i)
  129. END
  130. END
  131. END;
  132. END CalcImage;
  133. END TransitionMask;
  134. TransitionFade* = OBJECT(Transition)
  135. VAR
  136. mW, mH : LONGINT;
  137. mode : Raster.Mode;
  138. PROCEDURE Init*(w, h : LONGINT);
  139. BEGIN
  140. mW := w; mH := h;
  141. Raster.InitMode(mode, Raster.srcCopy);
  142. END Init;
  143. PROCEDURE CalcImage*(a, b, result : Raster.Image; per255 : LONGINT);
  144. BEGIN
  145. (* correct outofbound alpha values *)
  146. IF (per255 < 0) THEN per255 := 0; END;
  147. IF (per255 > 255) THEN per255 := 255; END;
  148. IF (a.fmt.code = Raster.bgr565) & (b.fmt.code = Raster.bgr565) THEN
  149. (****************************************************************
  150. *
  151. * 565-Format (16 Bit): ( case1: MMX, case2: optimized Aos code)
  152. *
  153. ****************************************************************)
  154. IF (MMXenabled) THEN
  155. Calc565MMX(a, b, result, per255);
  156. ELSE
  157. Calc565Opt(a, b, result, per255);
  158. END;
  159. ELSIF (a.fmt.code = Raster.bgr888) & (b.fmt.code = Raster.bgr888) THEN
  160. (****************************************************************
  161. *
  162. * 888-Format (24 Bit): ( case1: MMX, case2: optimized Aos code)
  163. *
  164. ****************************************************************)
  165. IF (MMXenabled) THEN
  166. Calc888MMX(a, b, result, per255);
  167. ELSE
  168. Calc888Opt(a, b, result, per255);
  169. END;
  170. ELSIF (a.fmt.code = b.fmt.code) THEN
  171. (****************************************************************
  172. *
  173. * Unknown-Format (16/24/32 Bit): ( in slow generic system calls )
  174. *
  175. ****************************************************************)
  176. CalcGenUnknown(a, b, result, per255);
  177. ELSE
  178. IF (DEBUG) THEN KernelLog.String("Error: source formats not equal!"); KernelLog.Ln; END;
  179. END;
  180. END CalcImage;
  181. END TransitionFade;
  182. VAR
  183. MMXenabled : BOOLEAN;
  184. (* ***
  185. *
  186. * Calculate a frame of the fade in 565-Mode (optimized version, 2 pixels at once)
  187. *
  188. *** *)
  189. PROCEDURE Calc565Opt(a, b : Raster.Image; VAR result : Raster.Image; per255 : LONGINT);
  190. VAR
  191. x, y : LONGINT;
  192. adra, adrb, adrr : ADDRESS;
  193. ar,ag,ab, br,bg,bb, cr,cg,cb : LONGINT;
  194. height, width : LONGINT;
  195. oddWidth : BOOLEAN; blocksOf4Bytes : LONGINT;
  196. add64, alphaOver2 : LONGINT;
  197. tmpA, tmpB : LONGINT;
  198. BEGIN
  199. IF (DEBUG) THEN KernelLog.String("Fade in 565-Format"); KernelLog.Ln; END;
  200. height := a.height; width := a.width;
  201. IF ( (width MOD 2)=0 ) THEN
  202. oddWidth := FALSE;
  203. blocksOf4Bytes := width DIV 2;
  204. ELSE
  205. oddWidth := TRUE;
  206. blocksOf4Bytes := (width-1) DIV 2;
  207. END;
  208. add64 := BIT.LOR(64, ASH(64, 16));
  209. alphaOver2 := BIT.LOR( (per255 DIV 4), ASH((per255 DIV 4),16) );
  210. FOR y := 0 TO height -1 DO
  211. adra := a.adr + y * a.bpr;
  212. adrb := b.adr + y * b.bpr;
  213. adrr := result.adr + y * result.bpr;
  214. FOR x := 0 TO blocksOf4Bytes DO
  215. (* read two source pixels = 32 bit *)
  216. tmpA := SYSTEM.GET32(adra + x * 4);
  217. tmpB := SYSTEM.GET32(adrb + x * 4);
  218. (* Extract the red channels. *)
  219. ar := BIT.LAND( ASH(tmpA, -11), 001F001FH );
  220. br := BIT.LAND( ASH(tmpB, -11), 001F001FH );
  221. (* Extract the green channels *)
  222. ag := BIT.LAND( ASH(tmpA, -5), 003F003FH );
  223. bg := BIT.LAND( ASH(tmpB, -5), 003F003FH );
  224. (* Extract the blue channel *)
  225. ab := BIT.LAND( tmpA, 001F001FH );
  226. bb := BIT.LAND( tmpB, 001F001FH );
  227. (* Calculate the alpha-blended red channel *)
  228. cr := ASH( BIT.LAND( (ASH(per255*(br+add64-ar), -8) + ar-alphaOver2), 001F001FH) , 11 );
  229. (* Calculate the alpha-blended green channel *)
  230. cg := ASH( BIT.LAND( (ASH(per255*(bg+add64-ag), -8) + ag-alphaOver2), 003F003FH) , 5 );
  231. (* Calculate the alpha-blended blue channel *)
  232. cb := BIT.LAND( (ASH(per255*(bb+add64-ab), -8) + ab-alphaOver2), 001F001FH);
  233. (* write the two pixels back *)
  234. SYSTEM.PUT32(adrr + 4*x, BIT.LOR( BIT.LOR(cr,cg), cb) );
  235. END;
  236. (* check and deal with odd width *)
  237. IF (oddWidth) THEN
  238. (* Read just one pixel *)
  239. tmpA := SYSTEM.GET16(adra + x * 4);
  240. tmpB := SYSTEM.GET16(adrb + x * 4);
  241. (* Extract the red channels *)
  242. ar := BIT.LAND( ASH(tmpA, -11), 1FH);
  243. br := BIT.LAND( ASH(tmpB, -11), 1FH);
  244. (* Extract the green channels *)
  245. ag := BIT.LAND( ASH(tmpA, -5), 3FH);
  246. bg := BIT.LAND( ASH(tmpB, -5), 3FH);
  247. (* Extract the blue channels *)
  248. ab := BIT.LAND(tmpA, 1FH);
  249. bb := BIT.LAND(tmpB, 1FH);
  250. (* Calc and write the pixel back *)
  251. cr := ASH(ASH(per255*(br-ar),-8)+ar, 11);
  252. cg := ASH(ASH(per255*(bg-ag),-8)+ag, 5);
  253. cb := ASH(per255*(bb-ab),-8)+ab;
  254. SYSTEM.PUT16(adrr + 2*x, BIT.LOR( BIT.LOR(cr,cg), cb));
  255. END;
  256. END;
  257. END Calc565Opt;
  258. (* ***
  259. *
  260. * Calculate a frame of the fade in 565-Mode (MMX optimized version, 4 pixels at once)
  261. *
  262. *** *)
  263. PROCEDURE Calc565MMX(a, b : Raster.Image; VAR result : Raster.Image; per255 : LONGINT);
  264. VAR
  265. x, y : LONGINT; (* current image coordinates *)
  266. height, width : LONGINT;
  267. remainder : LONGINT;
  268. blocksOf8Bytes : LONGINT;
  269. adra, adrb, adrr : ADDRESS;
  270. alpha64, maskRed64, maskGreen64, maskBlue64 : HUGEINT;
  271. alpha32 : LONGINT;
  272. tmpA, tmpB : LONGINT;
  273. ar, ag, ab, br, bg, bb, cr, cg, cb : LONGINT;
  274. BEGIN
  275. IF (DEBUG) THEN KernelLog.String("Fade in 565-Format (MMX)"); KernelLog.Ln; END;
  276. height := a.height; width := a.width;
  277. remainder := width MOD 4;
  278. blocksOf8Bytes := (width-remainder) DIV 4;
  279. (* Set the bit masks for red, green and blue *)
  280. maskRed64 := 0F800F800F800F800H;
  281. maskGreen64 := 007E007E007E007E0H;
  282. maskBlue64 := 0001F001F001F001FH;
  283. (* Compose the quadruple alpha value and pack it in a 64bit HUGEINT *)
  284. alpha64 := 0;
  285. alpha32 := BIT.LOR( per255, ASH(per255,16) );
  286. SYSTEM.PUT32( ADDRESSOF(alpha64), alpha32);
  287. SYSTEM.PUT32( ADDRESSOF(alpha64)+4, alpha32);
  288. FOR y := 0 TO height -1 DO
  289. adra := a.adr + y * a.bpr;
  290. adrb := b.adr + y * b.bpr;
  291. adrr := result.adr + y * result.bpr;
  292. Calc565MMXLine(adra, adrb, adrr, blocksOf8Bytes, per255, alpha64, maskRed64, maskGreen64, maskBlue64);
  293. (* alpha-blend remaining pixels *)
  294. IF (remainder # 0) THEN
  295. FOR x := 0 TO remainder-1 DO
  296. (* Read just one pixel *)
  297. tmpA := SYSTEM.GET16(adra + blocksOf8Bytes*8 + 2*x);
  298. tmpB := SYSTEM.GET16(adrb + blocksOf8Bytes*8 + 2*x);
  299. (* Extract the red channels *)
  300. ar := BIT.LAND( ASH(tmpA, -11), 1FH);
  301. br := BIT.LAND( ASH(tmpB, -11), 1FH);
  302. (* Extract the green channels *)
  303. ag := BIT.LAND( ASH(tmpA, -5), 3FH);
  304. bg := BIT.LAND( ASH(tmpB, -5), 3FH);
  305. (* Extract the blue channels *)
  306. ab := BIT.LAND(tmpA, 1FH);
  307. bb := BIT.LAND(tmpB, 1FH);
  308. (* Calc and write the pixel back *)
  309. cr := ASH(ASH(per255*(br-ar),-8)+ar, 11);
  310. cg := ASH(ASH(per255*(bg-ag),-8)+ag, 5);
  311. cb := ASH(per255*(bb-ab),-8)+ab;
  312. SYSTEM.PUT16(adrr + blocksOf8Bytes*8 + 2*x, BIT.LOR( BIT.LOR(cr,cg), cb));
  313. END;
  314. END;
  315. END;
  316. END Calc565MMX;
  317. (* ***
  318. *
  319. * Helper Function for Calc565MMX: :Calculate fade for just one line using assembler code (MMX technology)
  320. *
  321. *** *)
  322. PROCEDURE Calc565MMXLine (adra, adrb, adrr: ADDRESS; i, alpha : LONGINT; a64, mr64, mg64, mb64 : HUGEINT);
  323. CODE {SYSTEM.AMD64, SYSTEM.MMX}
  324. ;
  325. ; Initialize the counter and skip if the latter is equal to zero
  326. ;
  327. PUSH ECX
  328. MOV ECX, [RBP + i]
  329. CMP ECX, 0
  330. JZ skip565
  331. ;
  332. ; Load the frame buffer pointers into the registers
  333. ;
  334. PUSH RDI
  335. PUSH RSI
  336. PUSH RAX
  337. MOV RDI, [RBP + adra] ; source address of image A
  338. MOV RSI, [RBP + adrb] ; source address of image B
  339. MOV RAX, [RBP + adrr] ; destination address of image RESULT
  340. doblend565:
  341. ;
  342. ; Alpha blend four target and source pixels
  343. ;
  344. ;
  345. ; The mmx registers will basically be used in the following way:
  346. ; MMX0: red source value A
  347. ; MMX1: red source value B
  348. ; MMX2: green source value A
  349. ; MMX3: green source value B
  350. ; MMX4: blue source value A
  351. ; MMX5: blue source value B
  352. ; MMX6: original source pixel A
  353. ; MMX7: original source pixel B
  354. ;
  355. ;
  356. ; Note: Two lines together are assumed to pair
  357. ; in the processornd V-pipes
  358. ;
  359. MOVQ MMX6, [RDI] ; Load the original source pixel A
  360. NOP
  361. MOVQ MMX7, [RSI] ; Load the original source pixel B
  362. MOVQ MMX0, MMX6 ; Load the register for the red source A
  363. PAND MMX0, [RBP + mr64] ; Extract the red source A channel
  364. MOVQ MMX1, MMX7 ; Load the register for the red source B
  365. PAND MMX1, [RBP + mr64] ; Extract the red source B channel
  366. PSRLW MMX0, 11 ; Shift down the red source A channel
  367. MOVQ MMX2, MMX6 ; Load the register for the green source A
  368. PSRLW MMX1, 11 ; Shift down the red source B channel
  369. MOVQ MMX3, MMX7 ; Load the register for the green source B
  370. PSUBW MMX1, MMX0 ; Calculate red source B minus red source A
  371. PMULLW MMX1, [RBP + a64] ; Multiply the red result with alpha
  372. NOP
  373. PAND MMX2, [RBP + mg64] ; Extract the green source A channel
  374. NOP
  375. PAND MMX3, [RBP + mg64] ; Extract the green source B channel
  376. PSRAW MMX1, 8 ; Divide the red result by 256
  377. PSRLW MMX2, 5 ; Shift down the green source B channel
  378. PADDW MMX1, MMX0 ; Add the red source B to the red result
  379. PSLLW MMX1, 11 ; Shift up the red source A again
  380. MOVQ MMX4, MMX6 ; Load the register for the blue source A
  381. PSRLW MMX3, 5 ; Shift down the green source B channel
  382. MOVQ MMX5, MMX7 ; Load the register for the blue source B
  383. PAND MMX4, [RBP + mb64] ; Extract the blue source A channel
  384. PSUBW MMX3, MMX2 ; Calculate green source B minus green source A
  385. PAND MMX5, [RBP + mb64] ; Extract the blue source B channel
  386. PMULLW MMX3, [RBP + a64] ; Multiply the green result with alpha
  387. PSUBW MMX5, MMX4 ; Calculate blue source B minus blue source A
  388. NOP
  389. PMULLW MMX5, [RBP + a64] ; Multiply the blue result with alpha
  390. PSRAW MMX3, 8 ; Divide the green result by 256
  391. PADDW MMX3, MMX2 ; Add the green source A to the green result
  392. NOP
  393. PSRAW MMX5, 8 ; Divide the blue result by 256
  394. PSLLW MMX3, 5 ; Shift up the green source B again
  395. PADDW MMX5, MMX4 ; Add the blue source A to the blue result
  396. POR MMX1, MMX3 ; Combine the new red and green values
  397. POR MMX1, MMX5 ; Combine new blue value with the others to RESULT pixel
  398. MOVQ [RAX], MMX1 ; Write back RESULT value
  399. ;
  400. ; Advance to the next four pixels
  401. ;
  402. ADD RDI, 8
  403. ADD RSI, 8
  404. ADD RAX, 8
  405. ;
  406. ; Loop again or break
  407. ;
  408. DEC ECX
  409. JNZ doblend565
  410. ;
  411. ; Clean up
  412. ;
  413. POP RAX
  414. POP RSI
  415. POP RDI
  416. EMMS ; Declare FPU registers free
  417. skip565:
  418. POP ECX
  419. END Calc565MMXLine;
  420. (* ***
  421. *
  422. * Calculate a frame of the fade in 888-Mode (optimized version, 1 by 1 pixel = 3 Bytes)
  423. *
  424. *** *)
  425. PROCEDURE Calc888Opt(a, b : Raster.Image; VAR result : Raster.Image; per255 : LONGINT);
  426. VAR
  427. x, y : LONGINT; (* current image coordinates *)
  428. height, width : LONGINT;
  429. adra, adrb, adrr : ADDRESS; (* image start addresses *)
  430. ar,ag,ab, br,bg,bb, cr,cg,cb : LONGINT; (* red, green, blue part of the images *)
  431. tmpA, tmpB, tmpR : LONGINT; (* the two source pixels *)
  432. BEGIN
  433. IF (DEBUG) THEN KernelLog.String("Fade in 888-Format"); KernelLog.Ln; END;
  434. height := a.height; width := a.width;
  435. FOR y := 0 TO height -1 DO
  436. adra := a.adr + y * a.bpr;
  437. adrb := b.adr + y * b.bpr;
  438. adrr := result.adr + y * result.bpr;
  439. FOR x := 0 TO width-1 DO
  440. (* read source pixels = 24 bit *)
  441. IF (x = width-1) THEN
  442. (* last pixel would create memory access fault when reading 4 bytes -> 3 bytes in 2 steps *)
  443. tmpA := BIT.LOR( SYSTEM.GET16(adra + x * 3), ASH(SYSTEM.GET8(adra + x * 3 + 2),16) );
  444. tmpB := BIT.LOR( SYSTEM.GET16(adrb + x * 3), ASH(SYSTEM.GET8(adrb + x * 3 + 2),16) );
  445. ELSE
  446. (* normal read inside legal memory range -> 4 Bytes and cut off unneaded bits later *)
  447. tmpA := SYSTEM.GET32(adra + x * 3);
  448. tmpB := SYSTEM.GET32(adrb + x * 3);
  449. END;
  450. (* Extract the red channels. *)
  451. ar := BIT.LAND( ASH(tmpA,-16), 0FFH );
  452. br := BIT.LAND( ASH(tmpB,-16), 0FFH );
  453. (* Extract the green channels *)
  454. ag := BIT.LAND( ASH(tmpA,-8), 0FFH );
  455. bg := BIT.LAND( ASH(tmpB,-8), 0FFH );
  456. (* Extract the blue channel *)
  457. ab := BIT.LAND( tmpA, 0FFH );
  458. bb := BIT.LAND( tmpB, 0FFH );
  459. (* Calculate the alpha-blended red channel *)
  460. cr := ASH ( ASH( per255*(br-ar), -8) + ar , 16);
  461. (* Calculate the alpha-blended green channel *)
  462. cg := ASH ( ASH( per255*(bg-ag), -8) + ag , 8);
  463. (* Calculate the alpha-blended blue channel *)
  464. cb := ASH( per255*(bb-ab), -8) + ab;
  465. (* write back the new pixel (lower 16bits and then higher 8bits *)
  466. tmpR := BIT.LOR( BIT.LOR(cr,cg), cb );
  467. SYSTEM.PUT16(adrr + x * 3 , BIT.LAND(tmpR, 0FFFFH) );
  468. SYSTEM.PUT8 (adrr + x * 3 + 2, ASH(tmpR, -16) );
  469. END;
  470. END;
  471. END Calc888Opt;
  472. (* ***
  473. *
  474. * Calculate a frame of the fade in 888-Mode (MMX optimized version)
  475. *
  476. *** *)
  477. PROCEDURE Calc888MMX(a, b : Raster.Image; VAR result : Raster.Image; per255 : LONGINT);
  478. VAR
  479. y : LONGINT; (* current image coordinates *)
  480. height, width : LONGINT;
  481. adra, adrb, adrr : ADDRESS;
  482. alpha64, mask64 : HUGEINT;
  483. BEGIN
  484. IF (DEBUG) THEN KernelLog.String("Fade in 565-Format (MMX)"); KernelLog.Ln; END;
  485. height := a.height; width := a.width;
  486. (* Set a general bit masks *)
  487. mask64 := 0000000000FFFFFFH;
  488. (* Compose the triple alpha value and pack it in a 64bit HUGEINT *)
  489. alpha64 := 0;
  490. SYSTEM.PUT32( ADDRESSOF(alpha64), BIT.LOR( per255, ASH(per255,16)) );
  491. SYSTEM.PUT32( ADDRESSOF(alpha64)+4, per255);
  492. FOR y := 0 TO height -1 DO
  493. adra := a.adr + y * a.bpr;
  494. adrb := b.adr + y * b.bpr;
  495. adrr := result.adr + y * result.bpr;
  496. Calc888MMXLine(adra, adrb, adrr, width, alpha64, mask64);
  497. END;
  498. END Calc888MMX;
  499. (* ***
  500. *
  501. * Helper Function for Calc888MMX: :Calculate fade for just one line using assembler code (MMX technology)
  502. *
  503. *** *)
  504. PROCEDURE Calc888MMXLine (adra, adrb, adrr: ADDRESS; i : LONGINT; a64, m64 : HUGEINT);
  505. CODE {SYSTEM.AMD64, SYSTEM.MMX}
  506. ; (re)load the width counter
  507. PUSH ECX
  508. MOV ECX, [RBP + i]
  509. ;
  510. ; Load the frame buffer pointers into the registers
  511. ;
  512. PUSH RDI
  513. PUSH RSI
  514. PUSH RBX
  515. MOV RDI, [RBP + adra] ; source address of image A
  516. MOV RSI, [RBP + adrb] ; source address of image B
  517. MOV RBX, [RBP + adrr] ; destination address of image RESULT
  518. ; Load the mask into an mmx register
  519. MOVQ MMX3, [RBP + m64]
  520. ; Load the alpha value into an mmx register
  521. MOVQ MMX5, [RBP + a64]
  522. ; Clear an mmx register to facilitate unpacking
  523. PXOR MMX6, MMX6
  524. doblend24:
  525. ; The mmx registers will basically be used in the following way:
  526. ;
  527. ; MMX0: source value A
  528. ; MMX1: source value B
  529. ; MMX2: working register
  530. ; MMX3: mask ( 0x00ffffff )
  531. ; MMX4: working register
  532. ; MMX5: alpha value
  533. ; MMX6: zero for unpacking
  534. ; MMX7: original result value
  535. ;
  536. ; Note: Two lines together are assumed to pair
  537. ; in the processornd V-pipes
  538. MOVD MMX0, [RDI] ; Load the original source pixel A
  539. MOVQ MMX4, MMX3 ; Reload the mask ( 0x00ffffff )
  540. MOVQ MMX1, [RSI] ; Load the original source pixel B
  541. MOVQ MMX7, MMX0 ; Save the original result pixel
  542. PUNPCKLBW MMX0, MMX6 ; Unpack the source pixel A
  543. PUNPCKLBW MMX1, MMX6 ; Unpack the source pixel B
  544. MOVQ MMX2, MMX0 ; Save the unpacked source A values
  545. NOP
  546. PMULLW MMX0, MMX5 ; Multiply the source A with the alpha value
  547. NOP
  548. PMULLW MMX1, MMX5 ; Multiply the source B with the alpha value
  549. NOP
  550. PSRLW MMX0, 8 ; Divide the source A by 256
  551. NOP
  552. PSRLW MMX1, 8 ; Divide the source B by 256
  553. NOP
  554. PSUBW MMX1, MMX0 ; Calculate the source B minus source A
  555. NOP
  556. PADDW MMX2, MMX1 ; Add former result value to the new result
  557. NOP
  558. PACKUSWB MMX2, MMX2 ; Pack the new result
  559. NOP
  560. PAND MMX2, MMX4 ; Mask of unwanted bytes
  561. NOP
  562. PANDN MMX4, MMX7 ; Get the high order byte we must keep
  563. NOP
  564. POR MMX2, MMX4 ; Assemble the value to write back
  565. NOP
  566. MOVD [RBX], MMX2 ; Write back the new value to result image
  567. ;
  568. ; Advance to the next pixel
  569. ;
  570. ADD RDI, 3
  571. ADD RSI, 3
  572. ADD RBX, 3
  573. ;
  574. ; Loop again or break
  575. ;
  576. DEC ECX
  577. JNZ doblend24
  578. ;
  579. ; Write back the frame buffer pointers and clean up
  580. ;
  581. POP RBX
  582. POP RSI
  583. POP RDI
  584. EMMS ; Declare FPU registers free
  585. POP ECX
  586. END Calc888MMXLine;
  587. (* ***
  588. *
  589. * Calculate a frame of the fade in a Generic-Mode (Packs the result image in a generic buffered canvas object. Very slow!!!)
  590. *
  591. *** *)
  592. PROCEDURE CalcGenUnknown(a, b : Raster.Image; VAR result : Raster.Image; perc : LONGINT);
  593. VAR
  594. x, y : LONGINT; (* current image coordinates *)
  595. mode : Raster.Mode;
  596. canvas : WMGraphics.BufferCanvas;
  597. pix : Raster.Pixel; (* pixel read from a or b *)
  598. ca, cb : LONGINT; (* color of pixel in a and b *)
  599. red, green, blue, alpha : LONGINT;
  600. BEGIN
  601. IF (DEBUG) THEN
  602. KernelLog.String("Fade in other Format ["); KernelLog.String("a.fmt.code= "); KernelLog.Int(a.fmt.code, 0); KernelLog.String("b.fmt.code= "); KernelLog.Int(b.fmt.code, 0); KernelLog.String("]"); KernelLog.Ln;
  603. END;
  604. Raster.InitMode(mode, Raster.srcCopy);
  605. NEW(canvas, result);
  606. IF (canvas = NIL) & (DEBUG) THEN
  607. KernelLog.String("Error during calculating fade: couldn't allocate buffer canvas!"); KernelLog.Ln;
  608. HALT(99);
  609. END;
  610. FOR y := 0 TO a.height -1 DO
  611. FOR x := 0 TO a.width - 1 DO
  612. Raster.Get(a, x, y, pix, mode); Raster.GetRGBA(pix, red, green, blue, alpha); ca := WMGraphics.RGBAToColor(red, green, blue, alpha);
  613. Raster.Get(b, x, y, pix, mode); Raster.GetRGBA(pix, red, green, blue, alpha); cb := WMGraphics.RGBAToColor(red, green, blue, alpha);
  614. canvas.SetPixel(x, y, WMGraphicUtilities.InterpolateColorLinear(ca, cb, perc), WMGraphics.ModeCopy);
  615. END
  616. END;
  617. END CalcGenUnknown;
  618. (* --------------------------------------------------------------------------- *)
  619. PROCEDURE LoadImage(CONST fileName : ARRAY OF CHAR) : Raster.Image;
  620. VAR t, img : Raster.Image;
  621. c : WMGraphics.BufferCanvas;
  622. BEGIN
  623. t := WMGraphics.LoadImage(fileName, TRUE);
  624. IF t # NIL THEN
  625. NEW(img);
  626. Raster.Create(img, t.width, t.height, Raster.BGR565);
  627. NEW(c, img);
  628. c.DrawImage(0, 0, t, WMGraphics.ModeCopy)
  629. END;
  630. RETURN img
  631. END LoadImage;
  632. PROCEDURE Test*;
  633. VAR w : WMWindowManager.BufferWindow;
  634. t : TransitionMask;
  635. a, b, m : Raster.Image;
  636. i : LONGINT;
  637. BEGIN
  638. NEW(t);
  639. a := LoadImage("Reto01.png");
  640. b := LoadImage("Reto02.png");
  641. m := WMGraphics.LoadImage("M_Art1.png", TRUE);
  642. t.Init(a.width, a.height);
  643. NEW(w, a.width, a.height, FALSE);
  644. WMWindowManager.DefaultAddWindow(w);
  645. t.SetMask(m);
  646. FOR i := 0 TO 256 DO
  647. t.CalcImage(a, b, w.img, i );
  648. w.Invalidate(WMRectangles.MakeRect(0, 0, a.width, a.height));
  649. END;
  650. END Test;
  651. PROCEDURE Test2*;
  652. VAR w : WMWindowManager.BufferWindow;
  653. t : TransitionFade;
  654. a, b : Raster.Image;
  655. i : LONGINT;
  656. BEGIN
  657. NEW(t);
  658. a := LoadImage("Reto01.png");
  659. b := LoadImage("Reto02.png");
  660. t.Init(a.width, a.height);
  661. NEW(w, a.width, a.height, FALSE);
  662. WMWindowManager.DefaultAddWindow(w);
  663. FOR i := 0 TO 256 DO
  664. t.CalcImage(a, b, w.img, i );
  665. w.Invalidate(WMRectangles.MakeRect(0, 0, a.width, a.height));
  666. END;
  667. END Test2;
  668. BEGIN
  669. MMXenabled := 23 IN Machine.features;
  670. END WMTransitions.
  671. SystemTools.Free WMTransitions ~
  672. WMTransitions.Test ~
  673. WMTransitions.Test2 ~