WMTransitions.Mod 28 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731732733734735736737738739740741742743744745746747748749750751752753754755756757758759760761762763764765766767768769770771772773774775776777778779780781782783784785786787788789790791792793794795796797798799800801802803804805806807808809810811812813814815816817818819820821822823824825826827828829830831832833834835836837838839840841842843844845846847848849850851852853854855856857858859860861862863864865866867868869870871872873874875876877878879880881882883884885886887888889890891892893894895896897898899900901902903904905906907908909910911912913914915916917918919920921922923924925926927928929930931932933934935936937938939940941942943944945946947948949950951952953954955956957958959960961962963964965966967968969970971972973974975976977978979980981982983984985986987988989990991992993994995996997998999100010011002100310041005100610071008100910101011101210131014101510161017101810191020102110221023102410251026102710281029103010311032103310341035103610371038103910401041
  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 I386 OR AMD64 THEN
  155. IF Machine.MMX IN Machine.features THEN
  156. Calc565MMX(a, b, result, per255);
  157. ELSE
  158. Calc565Opt(a, b, result, per255);
  159. END;
  160. #ELSE
  161. Calc565Opt(a, b, result, per255);
  162. #END
  163. ELSIF (a.fmt.code = Raster.bgr888) & (b.fmt.code = Raster.bgr888) THEN
  164. (****************************************************************
  165. *
  166. * 888-Format (24 Bit): ( case1: MMX, case2: optimized Aos code)
  167. *
  168. ****************************************************************)
  169. #IF I386 OR AMD64 THEN
  170. IF Machine.MMX IN Machine.features THEN
  171. Calc888MMX(a, b, result, per255);
  172. ELSE
  173. Calc888Opt(a, b, result, per255);
  174. END;
  175. #ELSE
  176. Calc888Opt(a, b, result, per255);
  177. #END
  178. ELSIF (a.fmt.code = b.fmt.code) THEN
  179. (****************************************************************
  180. *
  181. * Unknown-Format (16/24/32 Bit): ( in slow generic system calls )
  182. *
  183. ****************************************************************)
  184. CalcGenUnknown(a, b, result, per255);
  185. ELSE
  186. IF (DEBUG) THEN KernelLog.String("Error: source formats not equal!"); KernelLog.Ln; END;
  187. END;
  188. END CalcImage;
  189. END TransitionFade;
  190. (* ***
  191. *
  192. * Calculate a frame of the fade in 565-Mode (optimized version, 2 pixels at once)
  193. *
  194. *** *)
  195. PROCEDURE Calc565Opt(a, b : Raster.Image; VAR result : Raster.Image; per255 : LONGINT);
  196. VAR
  197. x, y : LONGINT;
  198. adra, adrb, adrr : ADDRESS;
  199. ar,ag,ab, br,bg,bb, cr,cg,cb : LONGINT;
  200. height, width : LONGINT;
  201. oddWidth : BOOLEAN; blocksOf4Bytes : LONGINT;
  202. add64, alphaOver2 : LONGINT;
  203. tmpA, tmpB : LONGINT;
  204. BEGIN
  205. IF (DEBUG) THEN KernelLog.String("Fade in 565-Format"); KernelLog.Ln; END;
  206. height := a.height; width := a.width;
  207. IF ( (width MOD 2)=0 ) THEN
  208. oddWidth := FALSE;
  209. blocksOf4Bytes := width DIV 2;
  210. ELSE
  211. oddWidth := TRUE;
  212. blocksOf4Bytes := (width-1) DIV 2;
  213. END;
  214. add64 := BIT.LOR(64, ASH(64, 16));
  215. alphaOver2 := BIT.LOR( (per255 DIV 4), ASH((per255 DIV 4),16) );
  216. FOR y := 0 TO height -1 DO
  217. adra := a.adr + y * a.bpr;
  218. adrb := b.adr + y * b.bpr;
  219. adrr := result.adr + y * result.bpr;
  220. FOR x := 0 TO blocksOf4Bytes DO
  221. (* read two source pixels = 32 bit *)
  222. tmpA := SYSTEM.GET32(adra + x * 4);
  223. tmpB := SYSTEM.GET32(adrb + x * 4);
  224. (* Extract the red channels. *)
  225. ar := BIT.LAND( ASH(tmpA, -11), 001F001FH );
  226. br := BIT.LAND( ASH(tmpB, -11), 001F001FH );
  227. (* Extract the green channels *)
  228. ag := BIT.LAND( ASH(tmpA, -5), 003F003FH );
  229. bg := BIT.LAND( ASH(tmpB, -5), 003F003FH );
  230. (* Extract the blue channel *)
  231. ab := BIT.LAND( tmpA, 001F001FH );
  232. bb := BIT.LAND( tmpB, 001F001FH );
  233. (* Calculate the alpha-blended red channel *)
  234. cr := ASH( BIT.LAND( (ASH(per255*(br+add64-ar), -8) + ar-alphaOver2), 001F001FH) , 11 );
  235. (* Calculate the alpha-blended green channel *)
  236. cg := ASH( BIT.LAND( (ASH(per255*(bg+add64-ag), -8) + ag-alphaOver2), 003F003FH) , 5 );
  237. (* Calculate the alpha-blended blue channel *)
  238. cb := BIT.LAND( (ASH(per255*(bb+add64-ab), -8) + ab-alphaOver2), 001F001FH);
  239. (* write the two pixels back *)
  240. SYSTEM.PUT32(adrr + 4*x, BIT.LOR( BIT.LOR(cr,cg), cb) );
  241. END;
  242. (* check and deal with odd width *)
  243. IF (oddWidth) THEN
  244. (* Read just one pixel *)
  245. tmpA := SYSTEM.GET16(adra + x * 4);
  246. tmpB := SYSTEM.GET16(adrb + x * 4);
  247. (* Extract the red channels *)
  248. ar := BIT.LAND( ASH(tmpA, -11), 1FH);
  249. br := BIT.LAND( ASH(tmpB, -11), 1FH);
  250. (* Extract the green channels *)
  251. ag := BIT.LAND( ASH(tmpA, -5), 3FH);
  252. bg := BIT.LAND( ASH(tmpB, -5), 3FH);
  253. (* Extract the blue channels *)
  254. ab := BIT.LAND(tmpA, 1FH);
  255. bb := BIT.LAND(tmpB, 1FH);
  256. (* Calc and write the pixel back *)
  257. cr := ASH(ASH(per255*(br-ar),-8)+ar, 11);
  258. cg := ASH(ASH(per255*(bg-ag),-8)+ag, 5);
  259. cb := ASH(per255*(bb-ab),-8)+ab;
  260. SYSTEM.PUT16(adrr + 2*x, BIT.LOR( BIT.LOR(cr,cg), cb));
  261. END;
  262. END;
  263. END Calc565Opt;
  264. #IF I386 OR AMD64 THEN
  265. (* ***
  266. *
  267. * Calculate a frame of the fade in 565-Mode (MMX optimized version, 4 pixels at once)
  268. *
  269. *** *)
  270. PROCEDURE Calc565MMX(a, b : Raster.Image; VAR result : Raster.Image; per255 : LONGINT);
  271. VAR
  272. x, y : LONGINT; (* current image coordinates *)
  273. height, width : LONGINT;
  274. remainder : LONGINT;
  275. blocksOf8Bytes : LONGINT;
  276. adra, adrb, adrr : ADDRESS;
  277. alpha64, maskRed64, maskGreen64, maskBlue64 : HUGEINT;
  278. alpha32 : LONGINT;
  279. tmpA, tmpB : LONGINT;
  280. ar, ag, ab, br, bg, bb, cr, cg, cb : LONGINT;
  281. BEGIN
  282. IF (DEBUG) THEN KernelLog.String("Fade in 565-Format (MMX)"); KernelLog.Ln; END;
  283. height := a.height; width := a.width;
  284. remainder := width MOD 4;
  285. blocksOf8Bytes := (width-remainder) DIV 4;
  286. (* Set the bit masks for red, green and blue *)
  287. maskRed64 := 0F800F800F800F800H;
  288. maskGreen64 := 007E007E007E007E0H;
  289. maskBlue64 := 0001F001F001F001FH;
  290. (* Compose the quadruple alpha value and pack it in a 64bit HUGEINT *)
  291. alpha64 := 0;
  292. alpha32 := BIT.LOR( per255, ASH(per255,16) );
  293. SYSTEM.PUT32( ADDRESSOF(alpha64), alpha32);
  294. SYSTEM.PUT32( ADDRESSOF(alpha64)+4, alpha32);
  295. FOR y := 0 TO height -1 DO
  296. adra := a.adr + y * a.bpr;
  297. adrb := b.adr + y * b.bpr;
  298. adrr := result.adr + y * result.bpr;
  299. Calc565MMXLine(adra, adrb, adrr, blocksOf8Bytes, per255, alpha64, maskRed64, maskGreen64, maskBlue64);
  300. (* alpha-blend remaining pixels *)
  301. IF (remainder # 0) THEN
  302. FOR x := 0 TO remainder-1 DO
  303. (* Read just one pixel *)
  304. tmpA := SYSTEM.GET16(adra + blocksOf8Bytes*8 + 2*x);
  305. tmpB := SYSTEM.GET16(adrb + blocksOf8Bytes*8 + 2*x);
  306. (* Extract the red channels *)
  307. ar := BIT.LAND( ASH(tmpA, -11), 1FH);
  308. br := BIT.LAND( ASH(tmpB, -11), 1FH);
  309. (* Extract the green channels *)
  310. ag := BIT.LAND( ASH(tmpA, -5), 3FH);
  311. bg := BIT.LAND( ASH(tmpB, -5), 3FH);
  312. (* Extract the blue channels *)
  313. ab := BIT.LAND(tmpA, 1FH);
  314. bb := BIT.LAND(tmpB, 1FH);
  315. (* Calc and write the pixel back *)
  316. cr := ASH(ASH(per255*(br-ar),-8)+ar, 11);
  317. cg := ASH(ASH(per255*(bg-ag),-8)+ag, 5);
  318. cb := ASH(per255*(bb-ab),-8)+ab;
  319. SYSTEM.PUT16(adrr + blocksOf8Bytes*8 + 2*x, BIT.LOR( BIT.LOR(cr,cg), cb));
  320. END;
  321. END;
  322. END;
  323. END Calc565MMX;
  324. (* ***
  325. *
  326. * Helper Function for Calc565MMX: :Calculate fade for just one line using assembler code (MMX technology)
  327. *
  328. *** *)
  329. PROCEDURE Calc565MMXLine (adra, adrb, adrr: ADDRESS; i, alpha : LONGINT; a64, mr64, mg64, mb64 : HUGEINT);
  330. CODE
  331. #IF I386 THEN
  332. ;
  333. ; Initialize the counter and skip if the latter is equal to zero
  334. ;
  335. PUSH ECX
  336. MOV ECX, [EBP+i]
  337. CMP ECX, 0
  338. JZ skip565
  339. ;
  340. ; Load the frame buffer pointers into the registers
  341. ;
  342. PUSH EDI
  343. PUSH ESI
  344. PUSH EAX
  345. MOV EDI, [EBP+adra] ; source address of image A
  346. MOV ESI, [EBP+adrb] ; source address of image B
  347. MOV EAX, [EBP+adrr] ; destination address of image RESULT
  348. doblend565:
  349. ;
  350. ; Alpha blend four target and source pixels
  351. ;
  352. ;
  353. ; The mmx registers will basically be used in the following way:
  354. ; MMX0: red source value A
  355. ; MMX1: red source value B
  356. ; MMX2: green source value A
  357. ; MMX3: green source value B
  358. ; MMX4: blue source value A
  359. ; MMX5: blue source value B
  360. ; MMX6: original source pixel A
  361. ; MMX7: original source pixel B
  362. ;
  363. ;
  364. ; Note: Two lines together are assumed to pair
  365. ; in the processornd V-pipes
  366. ;
  367. MOVQ MMX6, [EDI] ; Load the original source pixel A
  368. NOP
  369. MOVQ MMX7, [ESI] ; Load the original source pixel B
  370. MOVQ MMX0, MMX6 ; Load the register for the red source A
  371. PAND MMX0, [EBP+mr64] ; Extract the red source A channel
  372. MOVQ MMX1, MMX7 ; Load the register for the red source B
  373. PAND MMX1, [EBP+mr64] ; Extract the red source B channel
  374. PSRLW MMX0, 11 ; Shift down the red source A channel
  375. MOVQ MMX2, MMX6 ; Load the register for the green source A
  376. PSRLW MMX1, 11 ; Shift down the red source B channel
  377. MOVQ MMX3, MMX7 ; Load the register for the green source B
  378. PSUBW MMX1, MMX0 ; Calculate red source B minus red source A
  379. PMULLW MMX1, [EBP+a64] ; Multiply the red result with alpha
  380. NOP
  381. PAND MMX2, [EBP+mg64] ; Extract the green source A channel
  382. NOP
  383. PAND MMX3, [EBP+mg64] ; Extract the green source B channel
  384. PSRAW MMX1, 8 ; Divide the red result by 256
  385. PSRLW MMX2, 5 ; Shift down the green source B channel
  386. PADDW MMX1, MMX0 ; Add the red source B to the red result
  387. PSLLW MMX1, 11 ; Shift up the red source A again
  388. MOVQ MMX4, MMX6 ; Load the register for the blue source A
  389. PSRLW MMX3, 5 ; Shift down the green source B channel
  390. MOVQ MMX5, MMX7 ; Load the register for the blue source B
  391. PAND MMX4, [EBP+mb64] ; Extract the blue source A channel
  392. PSUBW MMX3, MMX2 ; Calculate green source B minus green source A
  393. PAND MMX5, [EBP+mb64] ; Extract the blue source B channel
  394. PMULLW MMX3, [EBP+a64] ; Multiply the green result with alpha
  395. PSUBW MMX5, MMX4 ; Calculate blue source B minus blue source A
  396. NOP
  397. PMULLW MMX5, [EBP+a64] ; Multiply the blue result with alpha
  398. PSRAW MMX3, 8 ; Divide the green result by 256
  399. PADDW MMX3, MMX2 ; Add the green source A to the green result
  400. NOP
  401. PSRAW MMX5, 8 ; Divide the blue result by 256
  402. PSLLW MMX3, 5 ; Shift up the green source B again
  403. PADDW MMX5, MMX4 ; Add the blue source A to the blue result
  404. POR MMX1, MMX3 ; Combine the new red and green values
  405. POR MMX1, MMX5 ; Combine new blue value with the others to RESULT pixel
  406. MOVQ [EAX], MMX1 ; Write back RESULT value
  407. ;
  408. ; Advance to the next four pixels
  409. ;
  410. ADD EDI, 8
  411. ADD ESI, 8
  412. ADD EAX, 8
  413. ;
  414. ; Loop again or break
  415. ;
  416. DEC ECX
  417. JNZ doblend565
  418. ;
  419. ; Clean up
  420. ;
  421. POP EAX
  422. POP ESI
  423. POP EDI
  424. EMMS ; Declare FPU registers free
  425. skip565:
  426. POP ECX
  427. #ELSIF AMD64 THEN
  428. ;
  429. ; Initialize the counter and skip if the latter is equal to zero
  430. ;
  431. MOV ECX, [RBP + i]
  432. CMP ECX, 0
  433. JZ skip565
  434. ;
  435. ; Load the frame buffer pointers into the registers
  436. ;
  437. PUSH RDI
  438. PUSH RSI
  439. PUSH RAX
  440. MOV RDI, [RBP + adra] ; source address of image A
  441. MOV RSI, [RBP + adrb] ; source address of image B
  442. MOV RAX, [RBP + adrr] ; destination address of image RESULT
  443. doblend565:
  444. ;
  445. ; Alpha blend four target and source pixels
  446. ;
  447. ;
  448. ; The mmx registers will basically be used in the following way:
  449. ; MMX0: red source value A
  450. ; MMX1: red source value B
  451. ; MMX2: green source value A
  452. ; MMX3: green source value B
  453. ; MMX4: blue source value A
  454. ; MMX5: blue source value B
  455. ; MMX6: original source pixel A
  456. ; MMX7: original source pixel B
  457. ;
  458. ;
  459. ; Note: Two lines together are assumed to pair
  460. ; in the processornd V-pipes
  461. ;
  462. MOVQ MMX6, [RDI] ; Load the original source pixel A
  463. NOP
  464. MOVQ MMX7, [RSI] ; Load the original source pixel B
  465. MOVQ MMX0, MMX6 ; Load the register for the red source A
  466. PAND MMX0, [RBP + mr64] ; Extract the red source A channel
  467. MOVQ MMX1, MMX7 ; Load the register for the red source B
  468. PAND MMX1, [RBP + mr64] ; Extract the red source B channel
  469. PSRLW MMX0, 11 ; Shift down the red source A channel
  470. MOVQ MMX2, MMX6 ; Load the register for the green source A
  471. PSRLW MMX1, 11 ; Shift down the red source B channel
  472. MOVQ MMX3, MMX7 ; Load the register for the green source B
  473. PSUBW MMX1, MMX0 ; Calculate red source B minus red source A
  474. PMULLW MMX1, [RBP + a64] ; Multiply the red result with alpha
  475. NOP
  476. PAND MMX2, [RBP + mg64] ; Extract the green source A channel
  477. NOP
  478. PAND MMX3, [RBP + mg64] ; Extract the green source B channel
  479. PSRAW MMX1, 8 ; Divide the red result by 256
  480. PSRLW MMX2, 5 ; Shift down the green source B channel
  481. PADDW MMX1, MMX0 ; Add the red source B to the red result
  482. PSLLW MMX1, 11 ; Shift up the red source A again
  483. MOVQ MMX4, MMX6 ; Load the register for the blue source A
  484. PSRLW MMX3, 5 ; Shift down the green source B channel
  485. MOVQ MMX5, MMX7 ; Load the register for the blue source B
  486. PAND MMX4, [RBP + mb64] ; Extract the blue source A channel
  487. PSUBW MMX3, MMX2 ; Calculate green source B minus green source A
  488. PAND MMX5, [RBP + mb64] ; Extract the blue source B channel
  489. PMULLW MMX3, [RBP + a64] ; Multiply the green result with alpha
  490. PSUBW MMX5, MMX4 ; Calculate blue source B minus blue source A
  491. NOP
  492. PMULLW MMX5, [RBP + a64] ; Multiply the blue result with alpha
  493. PSRAW MMX3, 8 ; Divide the green result by 256
  494. PADDW MMX3, MMX2 ; Add the green source A to the green result
  495. NOP
  496. PSRAW MMX5, 8 ; Divide the blue result by 256
  497. PSLLW MMX3, 5 ; Shift up the green source B again
  498. PADDW MMX5, MMX4 ; Add the blue source A to the blue result
  499. POR MMX1, MMX3 ; Combine the new red and green values
  500. POR MMX1, MMX5 ; Combine new blue value with the others to RESULT pixel
  501. MOVQ [RAX], MMX1 ; Write back RESULT value
  502. ;
  503. ; Advance to the next four pixels
  504. ;
  505. ADD RDI, 8
  506. ADD RSI, 8
  507. ADD RAX, 8
  508. ;
  509. ; Loop again or break
  510. ;
  511. DEC ECX
  512. JNZ doblend565
  513. ;
  514. ; Clean up
  515. ;
  516. POP RAX
  517. POP RSI
  518. POP RDI
  519. EMMS ; Declare FPU registers free
  520. skip565:
  521. #ELSE
  522. unimplemented
  523. #END
  524. END Calc565MMXLine;
  525. #END
  526. (* ***
  527. *
  528. * Calculate a frame of the fade in 888-Mode (optimized version, 1 by 1 pixel = 3 Bytes)
  529. *
  530. *** *)
  531. PROCEDURE Calc888Opt(a, b : Raster.Image; VAR result : Raster.Image; per255 : LONGINT);
  532. VAR
  533. x, y : LONGINT; (* current image coordinates *)
  534. height, width : LONGINT;
  535. adra, adrb, adrr : ADDRESS; (* image start addresses *)
  536. ar,ag,ab, br,bg,bb, cr,cg,cb : LONGINT; (* red, green, blue part of the images *)
  537. tmpA, tmpB, tmpR : LONGINT; (* the two source pixels *)
  538. BEGIN
  539. IF (DEBUG) THEN KernelLog.String("Fade in 888-Format"); KernelLog.Ln; END;
  540. height := a.height; width := a.width;
  541. FOR y := 0 TO height -1 DO
  542. adra := a.adr + y * a.bpr;
  543. adrb := b.adr + y * b.bpr;
  544. adrr := result.adr + y * result.bpr;
  545. FOR x := 0 TO width-1 DO
  546. (* read source pixels = 24 bit *)
  547. IF (x = width-1) THEN
  548. (* last pixel would create memory access fault when reading 4 bytes -> 3 bytes in 2 steps *)
  549. tmpA := BIT.LOR( SYSTEM.GET16(adra + x * 3), ASH(SYSTEM.GET8(adra + x * 3 + 2),16) );
  550. tmpB := BIT.LOR( SYSTEM.GET16(adrb + x * 3), ASH(SYSTEM.GET8(adrb + x * 3 + 2),16) );
  551. ELSE
  552. (* normal read inside legal memory range -> 4 Bytes and cut off unneaded bits later *)
  553. tmpA := SYSTEM.GET32(adra + x * 3);
  554. tmpB := SYSTEM.GET32(adrb + x * 3);
  555. END;
  556. (* Extract the red channels. *)
  557. ar := BIT.LAND( ASH(tmpA,-16), 0FFH );
  558. br := BIT.LAND( ASH(tmpB,-16), 0FFH );
  559. (* Extract the green channels *)
  560. ag := BIT.LAND( ASH(tmpA,-8), 0FFH );
  561. bg := BIT.LAND( ASH(tmpB,-8), 0FFH );
  562. (* Extract the blue channel *)
  563. ab := BIT.LAND( tmpA, 0FFH );
  564. bb := BIT.LAND( tmpB, 0FFH );
  565. (* Calculate the alpha-blended red channel *)
  566. cr := ASH ( ASH( per255*(br-ar), -8) + ar , 16);
  567. (* Calculate the alpha-blended green channel *)
  568. cg := ASH ( ASH( per255*(bg-ag), -8) + ag , 8);
  569. (* Calculate the alpha-blended blue channel *)
  570. cb := ASH( per255*(bb-ab), -8) + ab;
  571. (* write back the new pixel (lower 16bits and then higher 8bits *)
  572. tmpR := BIT.LOR( BIT.LOR(cr,cg), cb );
  573. SYSTEM.PUT16(adrr + x * 3 , BIT.LAND(tmpR, 0FFFFH) );
  574. SYSTEM.PUT8 (adrr + x * 3 + 2, ASH(tmpR, -16) );
  575. END;
  576. END;
  577. END Calc888Opt;
  578. #IF I386 OR AMD64 THEN
  579. (* ***
  580. *
  581. * Calculate a frame of the fade in 888-Mode (MMX optimized version)
  582. *
  583. *** *)
  584. PROCEDURE Calc888MMX(a, b : Raster.Image; VAR result : Raster.Image; per255 : LONGINT);
  585. VAR
  586. y : LONGINT; (* current image coordinates *)
  587. height, width : LONGINT;
  588. adra, adrb, adrr : ADDRESS;
  589. alpha64, mask64 : HUGEINT;
  590. BEGIN
  591. IF (DEBUG) THEN KernelLog.String("Fade in 565-Format (MMX)"); KernelLog.Ln; END;
  592. height := a.height; width := a.width;
  593. (* Set a general bit masks *)
  594. mask64 := 0000000000FFFFFFH;
  595. (* Compose the triple alpha value and pack it in a 64bit HUGEINT *)
  596. alpha64 := 0;
  597. SYSTEM.PUT32( ADDRESSOF(alpha64), BIT.LOR( per255, ASH(per255,16)) );
  598. SYSTEM.PUT32( ADDRESSOF(alpha64)+4, per255);
  599. FOR y := 0 TO height -1 DO
  600. adra := a.adr + y * a.bpr;
  601. adrb := b.adr + y * b.bpr;
  602. adrr := result.adr + y * result.bpr;
  603. Calc888MMXLine(adra, adrb, adrr, width, alpha64, mask64);
  604. END;
  605. END Calc888MMX;
  606. (* ***
  607. *
  608. * Helper Function for Calc888MMX: :Calculate fade for just one line using assembler code (MMX technology)
  609. *
  610. *** *)
  611. PROCEDURE Calc888MMXLine (adra, adrb, adrr: ADDRESS; i : LONGINT; a64, m64 : HUGEINT);
  612. CODE
  613. #IF I386 THEN
  614. ; (re)load the width counter
  615. PUSH ECX
  616. MOV ECX, [EBP+i]
  617. ;
  618. ; Load the frame buffer pointers into the registers
  619. ;
  620. PUSH EDI
  621. PUSH ESI
  622. PUSH EBX
  623. MOV EDI, [EBP+adra] ; source address of image A
  624. MOV ESI, [EBP+adrb] ; source address of image B
  625. MOV EBX, [EBP+adrr] ; destination address of image RESULT
  626. ; Load the mask into an mmx register
  627. MOVQ MMX3, [EBP+m64]
  628. ; Load the alpha value into an mmx register
  629. MOVQ MMX5, [EBP+a64]
  630. ; Clear an mmx register to facilitate unpacking
  631. PXOR MMX6, MMX6
  632. doblend24:
  633. ; The mmx registers will basically be used in the following way:
  634. ;
  635. ; MMX0: source value A
  636. ; MMX1: source value B
  637. ; MMX2: working register
  638. ; MMX3: mask ( 0x00ffffff )
  639. ; MMX4: working register
  640. ; MMX5: alpha value
  641. ; MMX6: zero for unpacking
  642. ; MMX7: original result value
  643. ;
  644. ; Note: Two lines together are assumed to pair
  645. ; in the processornd V-pipes
  646. MOVD MMX0, [EDI] ; Load the original source pixel A
  647. MOVQ MMX4, MMX3 ; Reload the mask ( 0x00ffffff )
  648. MOVQ MMX1, [ESI] ; Load the original source pixel B
  649. MOVQ MMX7, MMX0 ; Save the original result pixel
  650. PUNPCKLBW MMX0, MMX6 ; Unpack the source pixel A
  651. PUNPCKLBW MMX1, MMX6 ; Unpack the source pixel B
  652. MOVQ MMX2, MMX0 ; Save the unpacked source A values
  653. NOP
  654. PMULLW MMX0, MMX5 ; Multiply the source A with the alpha value
  655. NOP
  656. PMULLW MMX1, MMX5 ; Multiply the source B with the alpha value
  657. NOP
  658. PSRLW MMX0, 8 ; Divide the source A by 256
  659. NOP
  660. PSRLW MMX1, 8 ; Divide the source B by 256
  661. NOP
  662. PSUBW MMX1, MMX0 ; Calculate the source B minus source A
  663. NOP
  664. PADDW MMX2, MMX1 ; Add former result value to the new result
  665. NOP
  666. PACKUSWB MMX2, MMX2 ; Pack the new result
  667. NOP
  668. PAND MMX2, MMX4 ; Mask of unwanted bytes
  669. NOP
  670. PANDN MMX4, MMX7 ; Get the high order byte we must keep
  671. NOP
  672. POR MMX2, MMX4 ; Assemble the value to write back
  673. NOP
  674. MOVD [EBX], MMX2 ; Write back the new value to result image
  675. ;
  676. ; Advance to the next pixel
  677. ;
  678. ADD EDI, 3
  679. ADD ESI, 3
  680. ADD EBX, 3
  681. ;
  682. ; Loop again or break
  683. ;
  684. DEC ECX
  685. JNZ doblend24
  686. ;
  687. ; Write back the frame buffer pointers and clean up
  688. ;
  689. POP EBX
  690. POP ESI
  691. POP EDI
  692. EMMS ; Declare FPU registers free
  693. POP ECX
  694. #ELSIF AMD64 THEN
  695. #IF COOP THEN
  696. PUSH RBX
  697. #END
  698. ; (re)load the width counter
  699. MOV ECX, [RBP + i]
  700. ;
  701. ; Load the frame buffer pointers into the registers
  702. ;
  703. PUSH RDI
  704. PUSH RSI
  705. PUSH RBX
  706. MOV RDI, [RBP + adra] ; source address of image A
  707. MOV RSI, [RBP + adrb] ; source address of image B
  708. MOV RBX, [RBP + adrr] ; destination address of image RESULT
  709. ; Load the mask into an mmx register
  710. MOVQ MMX3, [RBP + m64]
  711. ; Load the alpha value into an mmx register
  712. MOVQ MMX5, [RBP + a64]
  713. ; Clear an mmx register to facilitate unpacking
  714. PXOR MMX6, MMX6
  715. doblend24:
  716. ; The mmx registers will basically be used in the following way:
  717. ;
  718. ; MMX0: source value A
  719. ; MMX1: source value B
  720. ; MMX2: working register
  721. ; MMX3: mask ( 0x00ffffff )
  722. ; MMX4: working register
  723. ; MMX5: alpha value
  724. ; MMX6: zero for unpacking
  725. ; MMX7: original result value
  726. ;
  727. ; Note: Two lines together are assumed to pair
  728. ; in the processornd V-pipes
  729. MOVD MMX0, [RDI] ; Load the original source pixel A
  730. MOVQ MMX4, MMX3 ; Reload the mask ( 0x00ffffff )
  731. MOVQ MMX1, [RSI] ; Load the original source pixel B
  732. MOVQ MMX7, MMX0 ; Save the original result pixel
  733. PUNPCKLBW MMX0, MMX6 ; Unpack the source pixel A
  734. PUNPCKLBW MMX1, MMX6 ; Unpack the source pixel B
  735. MOVQ MMX2, MMX0 ; Save the unpacked source A values
  736. NOP
  737. PMULLW MMX0, MMX5 ; Multiply the source A with the alpha value
  738. NOP
  739. PMULLW MMX1, MMX5 ; Multiply the source B with the alpha value
  740. NOP
  741. PSRLW MMX0, 8 ; Divide the source A by 256
  742. NOP
  743. PSRLW MMX1, 8 ; Divide the source B by 256
  744. NOP
  745. PSUBW MMX1, MMX0 ; Calculate the source B minus source A
  746. NOP
  747. PADDW MMX2, MMX1 ; Add former result value to the new result
  748. NOP
  749. PACKUSWB MMX2, MMX2 ; Pack the new result
  750. NOP
  751. PAND MMX2, MMX4 ; Mask of unwanted bytes
  752. NOP
  753. PANDN MMX4, MMX7 ; Get the high order byte we must keep
  754. NOP
  755. POR MMX2, MMX4 ; Assemble the value to write back
  756. NOP
  757. MOVD [RBX], MMX2 ; Write back the new value to result image
  758. ;
  759. ; Advance to the next pixel
  760. ;
  761. ADD RDI, 3
  762. ADD RSI, 3
  763. ADD RBX, 3
  764. ;
  765. ; Loop again or break
  766. ;
  767. DEC ECX
  768. JNZ doblend24
  769. ;
  770. ; Write back the frame buffer pointers and clean up
  771. ;
  772. POP RBX
  773. POP RSI
  774. POP RDI
  775. EMMS ; Declare FPU registers free
  776. #IF COOP THEN
  777. POP RBX
  778. #END
  779. #ELSE
  780. unimplemented
  781. #END
  782. END Calc888MMXLine;
  783. #END
  784. (* ***
  785. *
  786. * Calculate a frame of the fade in a Generic-Mode (Packs the result image in a generic buffered canvas object. Very slow!!!)
  787. *
  788. *** *)
  789. PROCEDURE CalcGenUnknown(a, b : Raster.Image; VAR result : Raster.Image; perc : LONGINT);
  790. VAR
  791. x, y : LONGINT; (* current image coordinates *)
  792. mode : Raster.Mode;
  793. canvas : WMGraphics.BufferCanvas;
  794. pix : Raster.Pixel; (* pixel read from a or b *)
  795. ca, cb : WMGraphics.Color; (* color of pixel in a and b *)
  796. red, green, blue, alpha : LONGINT;
  797. BEGIN
  798. IF (DEBUG) THEN
  799. 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;
  800. END;
  801. Raster.InitMode(mode, Raster.srcCopy);
  802. NEW(canvas, result);
  803. IF (canvas = NIL) & (DEBUG) THEN
  804. KernelLog.String("Error during calculating fade: couldn't allocate buffer canvas!"); KernelLog.Ln;
  805. HALT(99);
  806. END;
  807. FOR y := 0 TO a.height -1 DO
  808. FOR x := 0 TO a.width - 1 DO
  809. Raster.Get(a, x, y, pix, mode); Raster.GetRGBA(pix, red, green, blue, alpha); ca := WMGraphics.RGBAToColor(red, green, blue, alpha);
  810. Raster.Get(b, x, y, pix, mode); Raster.GetRGBA(pix, red, green, blue, alpha); cb := WMGraphics.RGBAToColor(red, green, blue, alpha);
  811. canvas.SetPixel(x, y, WMGraphicUtilities.InterpolateColorLinear(ca, cb, perc), WMGraphics.ModeCopy);
  812. END
  813. END;
  814. END CalcGenUnknown;
  815. (* --------------------------------------------------------------------------- *)
  816. PROCEDURE LoadImage(CONST fileName : ARRAY OF CHAR) : Raster.Image;
  817. VAR t, img : Raster.Image;
  818. c : WMGraphics.BufferCanvas;
  819. BEGIN
  820. t := WMGraphics.LoadImage(fileName, TRUE);
  821. IF t # NIL THEN
  822. NEW(img);
  823. Raster.Create(img, t.width, t.height, Raster.BGR565);
  824. NEW(c, img);
  825. c.DrawImage(0, 0, t, WMGraphics.ModeCopy)
  826. END;
  827. RETURN img
  828. END LoadImage;
  829. PROCEDURE Test*;
  830. VAR w : WMWindowManager.BufferWindow;
  831. t : TransitionMask;
  832. a, b, m : Raster.Image;
  833. i : LONGINT;
  834. BEGIN
  835. NEW(t);
  836. a := LoadImage("Reto01.png");
  837. b := LoadImage("Reto02.png");
  838. m := WMGraphics.LoadImage("M_Art1.png", TRUE);
  839. t.Init(a.width, a.height);
  840. NEW(w, a.width, a.height, FALSE);
  841. WMWindowManager.DefaultAddWindow(w);
  842. t.SetMask(m);
  843. FOR i := 0 TO 256 DO
  844. t.CalcImage(a, b, w.img, i );
  845. w.Invalidate(WMRectangles.MakeRect(0, 0, a.width, a.height));
  846. END;
  847. END Test;
  848. PROCEDURE Test2*;
  849. VAR w : WMWindowManager.BufferWindow;
  850. t : TransitionFade;
  851. a, b : Raster.Image;
  852. i : LONGINT;
  853. BEGIN
  854. NEW(t);
  855. a := LoadImage("Reto01.png");
  856. b := LoadImage("Reto02.png");
  857. t.Init(a.width, a.height);
  858. NEW(w, a.width, a.height, FALSE);
  859. WMWindowManager.DefaultAddWindow(w);
  860. FOR i := 0 TO 256 DO
  861. t.CalcImage(a, b, w.img, i );
  862. w.Invalidate(WMRectangles.MakeRect(0, 0, a.width, a.height));
  863. END;
  864. END Test2;
  865. END WMTransitions.
  866. System.Free WMTransitions ~
  867. WMTransitions.Test ~
  868. WMTransitions.Test2 ~