Sprite rotation

Post your FreeBASIC source, examples, tips and tricks here. Please don’t post code without including an explanation.
Post Reply
badidea
Posts: 2591
Joined: May 24, 2007 22:10
Location: The Netherlands

Sprite rotation

Post by badidea »

Hello all,

For a game I am trying to make, I made a small program which reads a bitmap and makes rotated versions which can be draw with put. One simple rotation an one using bilinear interpolation.

Image

The image I used is:
Image

Code: Select all

const pi as double = 3.1415926535897932
const rad as double = 180 / pi

'bmp header description, copy/pasta from wiki
Type bitmap_header Field = 1
	bfType          As UShort
	bfsize          As ULong
	bfReserved1     As UShort
	bfReserved2     As UShort
	bfOffBits       As ULong
	biSize          As ULong
	biWidth         As ULong
	biHeight        As ULong
	biPlanes        As UShort
	biBitCount      As UShort
	biCompression   As ULong
	biSizeImage     As ULong
	biXPelsPerMeter As ULong
	biYPelsPerMeter As ULong
	biClrUsed       As ULong
	biClrImportant  As ULong
End Type

type rgbc_type
  r as integer
  g as integer
  b as integer
  c as integer
end type

sub colorToRGB(byref colour as rgbc_type)
   colour.b = colour.c and &h000000FF
   colour.g = (colour.c and &h0000FF00) shr 8
   colour.r = (colour.c and &h00FF0000) shr 16
end sub

sub rgbToColor(byref colour as rgbc_type)
   colour.c = rgb(colour.r, colour.g, colour.b)
end sub

declare sub sprite_rotate(srcImg as any ptr, dstImg as any ptr, rotation as single, defaultColour as integer)
declare sub sprite_rotate_bilinear(srcImg as any ptr, dstImg as any ptr, rotation as single, defaultColour as integer)
declare function inLimits(i as integer, iMin as integer, imax as integer) as integer

Dim bmp_header As bitmap_header
dim as any ptr image(1) '1 means 2 images: 0 and 1
dim as single rotation
dim as integer defaultColour
dim as string bmp_file_name = "tank_04.bmp"

screen 19, 32, 2

Open bmp_file_name For Binary As #1
  Get #1, , bmp_header
Close #1

image(0) = imagecreate(bmp_header.biWidth, bmp_header.biHeight)
image(1) = imagecreate(bmp_header.biWidth, bmp_header.biHeight)
bload bmp_file_name, image(0)

put (100, 100), image(0), pset

'defaultColour = &hff7f7f7f
defaultColour = &hffffffff
'defaultColour = &hff000000

rotation = 0' 10 / rad
while inkey$ = ""
  sprite_rotate(image(0), image(1), rotation, defaultColour)
  put (300, 100), image(1), pset
  sprite_rotate_bilinear(image(0), image(1), rotation, defaultColour)
  put (500, 100), image(1), pset
  sleep 20
  rotation += (2 / rad)
wend

imagedestroy(image(0))
imagedestroy(image(1))

sleep

sub sprite_rotate(srcImg as any ptr, dstImg as any ptr, rotation as single, defaultColour as integer)
  dim as integer srcWidth, srcHeight
  dim as single xctr, yctr
  dim as integer x, y
  dim as integer xsrc, ysrc
  dim as integer colour
  dim as integer colourInterpol(3)
  imageInfo srcImg, srcWidth, srcHeight
  xctr = srcWidth / 2
  yctr = srcHeight / 2
  for y = 0 to srcHeight-1
    for x = 0 to srcWidth-1
      xsrc = int((x - xctr) * cos(rotation) - (y - yctr) * sin(rotation) + xctr + 0.5)
      ysrc = int((x - xctr) * sin(rotation) + (y - yctr) * cos(rotation) + yctr + 0.5)
      if inLimits(xsrc, 0, srcWidth-1) and inLimits(ysrc, 0, srcHeight-1) then
        colour = point(xsrc, ysrc, srcImg)
      else
        colour = defaultColour
      end if
      pset dstImg, (x, y), colour
    next
  next
end sub

sub sprite_rotate_bilinear(srcImg as any ptr, dstImg as any ptr, rotation as single, defaultColour as integer)
  dim as integer srcWidth, srcHeight
  dim as single xctr, yctr
  dim as integer x, y
  dim as single xSrc, ySrc, xFact, yFact
  dim as integer xSrcLeft, xSrcRight, ySrcUp, ySrcDown
  dim as rgbc_type colour, cLeftUp, cLeftDown, cRightUp, cRightDown
  imageInfo srcImg, srcWidth, srcHeight
  xctr = srcWidth / 2
  yctr = srcHeight / 2
  for y = 0 to srcHeight-1
    for x = 0 to srcWidth-1
      xSrc = (x - xctr) * cos(rotation) + (y - yctr) * sin(-rotation) + xctr
      ySrc = (x - xctr) * sin(rotation) + (y - yctr) * cos(rotation) + yctr
      
      xSrcLeft = int(xSrc)
      xSrcRight = int(xSrc) + 1
      xFact = xSrc - xSrcLeft
      ySrcUp = int(ySrc)
      ySrcDown = int(ySrc) + 1
      yFact = ySrc - ySrcUp
      
      if inLimits(xSrcLeft, 0, srcWidth-1) and inLimits(ySrcUp, 0, srcHeight-1) then
        cLeftUp.c = point(xSrcLeft, ySrcUp, srcImg)
      else
        cLeftUp.c = defaultColour
      end if
      if inLimits(xSrcRight, 0, srcWidth-1) and inLimits(ySrcUp, 0, srcHeight-1) then
        cRightUp.c = point(xSrcRight, ySrcUp, srcImg)
      else
        cRightUp.c = defaultColour
      end if
      if inLimits(xSrcLeft, 0, srcWidth-1) and inLimits(ySrcDown, 0, srcHeight-1) then
        cLeftDown.c = point(xSrcLeft, ySrcDown, srcImg)
      else
        cLeftDown.c = defaultColour
      end if
      if inLimits(xSrcRight, 0, srcWidth-1) and inLimits(ySrcDown, 0, srcHeight-1) then
        cRightDown.c = point(xSrcRight, ySrcDown, srcImg)
      else
        cRightDown.c = defaultColour
      end if
      
      colorToRGB(cLeftUp)
      colorToRGB(cLeftDown)
      colorToRGB(cRightUp)
      colorToRGB(cRightDown)

      colour.r = cLeftUp.r * (1-xFact) * (1-yFact) + cRightUp.r * xFact * (1-yFact)_
        + cLeftDown.r * (1-xFact) * yFact + cRightDown.r * xFact * yFact
      colour.g = cLeftUp.g * (1-xFact) * (1-yFact) + cRightUp.g * xFact * (1-yFact)_
        + cLeftDown.g * (1-xFact) * yFact + cRightDown.g * xFact * yFact
      colour.b = cLeftUp.b * (1-xFact) * (1-yFact) + cRightUp.b * xFact * (1-yFact)_
        + cLeftDown.b * (1-xFact) * yFact + cRightDown.b * xFact * yFact

      rgbToColor(colour)
      pset dstImg, (x, y), colour.c
    next
  next
end sub

function inLimits(i as integer, iMin as integer, imax as integer) as integer
  if (i < iMin) then return 0
  if (i > iMax) then return 0
  return 1
end function
Edit: Code updated for 64-bit FBC
Last edited by badidea on Jun 20, 2019 20:35, edited 4 times in total.
angros47
Posts: 2326
Joined: Jun 21, 2005 19:04

Post by angros47 »

Cos and Sin are slow: you iterate them many times, and in every loop you call them twice!

Instead off:

Code: Select all

For y = 0 To srcHeight-1
    For x = 0 To srcWidth-1
      xSrc = (x - xctr) * Cos(rotation) + (y - yctr) * Sin(-rotation) + xctr
      ySrc = (x - xctr) * Sin(rotation) + (y - yctr) * Cos(rotation) + yctr
You could do something like:

Code: Select all

sine=sin(rotation)
cosine=cos(rotation)
For y = 0 To srcHeight-1
    For x = 0 To srcWidth-1
      xSrc = (x - xctr) *cosine + (y - yctr) * sine + xctr
      ySrc = (x - xctr) * sine + (y - yctr) * cosine + yctr
It should be faster.

Also, instead of 'point' and 'pset', you could gain more speed by directly using screen and buffer pointers.

Have a look at this:
http://www.freebasic.net/forum/viewtopic.php?t=15843

No bilinear interpolation, but it can scale and rotate an image at the same time.
D.J.Peters
Posts: 8586
Joined: May 28, 2005 3:28
Contact:

Post by D.J.Peters »

hello badidea
good job so far

later you can make it faster

Joshy
badidea
Posts: 2591
Joined: May 24, 2007 22:10
Location: The Netherlands

Post by badidea »

It does not need to be fast for my game, because i plan to create the required rotated sprites in advance. So no cos / sin in the main loop, just putting the right image.

However, I do like to make an OOP version later.
badidea
Posts: 2591
Joined: May 24, 2007 22:10
Location: The Netherlands

Post by badidea »

Made some example for my sprite rotation, which may evolve into a real game.

Controls:
Up, Left, Right, Escape.

Needed bitmap:
https://nr100.home.xs4all.nl/badidea/tank_06.bmp

Screenshot:
Image

Code: Select all

#include "fbgfx.bi"

#macro randint(max)
  int(rnd * max)
#endmacro

const pi as double = 3.1415926535897932
const rad as double = 180 / pi

const as string key_esc = chr(27)
const as string key_up = chr(255) + "H"
const as string key_right = chr(255) + "M"
const as string key_down = chr(255) + "P"
const as string key_left = chr(255) + "K"

'bmp header description, copy/pasta from wiki
Type bitmap_header Field = 1
	bfType          As UShort
	bfsize          As ULong
	bfReserved1     As UShort
	bfReserved2     As UShort
	bfOffBits       As ULong
	biSize          As ULong
	biWidth         As ULong
	biHeight        As ULong
	biPlanes        As UShort
	biBitCount      As UShort
	biCompression   As ULong
	biSizeImage     As ULong
	biXPelsPerMeter As ULong
	biYPelsPerMeter As ULong
	biClrUsed       As ULong
	biClrImportant  As ULong
End Type

type rgbc_type
  r as integer
  g as integer
  b as integer
  c as integer
end type

declare sub colorToRGB(byref colour as rgbc_type)
declare sub rgbToColor(byref colour as rgbc_type)
declare sub flipScreen()
declare sub sprite_rotate(srcImg as any ptr, dstImg as any ptr, rotation as single, defaultColour as integer)
declare sub sprite_rotate_bilinear(srcImg as any ptr, dstImg as any ptr, rotation as single, defaultColour as integer)
declare function inLimits(i as integer, iMin as integer, imax as integer) as integer

dim bmp_header as bitmap_header
dim as any ptr tank_sprite(64-1)
dim as single rotation
dim as integer defaultColour = &hffff00ff
dim as string bmp_file_name = "tank_06.bmp"
dim as integer iSprite

dim as integer x, y, i
dim as single xt, yt
dim as integer xTileIndex, yTileIndex
dim as integer xLeftUp, yLeftUp
dim as integer xOffset, yOffset
dim as integer scrW, scrH
dim as integer update = 1
dim as string key
dim as any ptr world(199, 199)
dim as any ptr tile1_sprite
dim as any ptr tile2_sprite
dim as any ptr tile_sprite
dim as any ptr tileEmpty_sprite
dim as single tank_speed = 0, tank_direction = 0

screen 19, 32, 2
screenset 0, 0
screeninfo scrW, scrH

tile1_sprite = imagecreate(32, 32)
tile2_sprite = imagecreate(32, 32)
tileEmpty_sprite = imagecreate(32, 32, &hff7f7f7f)

Open bmp_file_name For Binary As #1
  Get #1, , bmp_header
Close #1

for i = 0 to 64-1
  tank_sprite(i) = imagecreate(bmp_header.biWidth, bmp_header.biHeight)
next
bload bmp_file_name, tank_sprite(0)

for i = 0 to 64-1
  rotation = (i / 64) * 360 / rad
  'sprite_rotate_bilinear(image(0), image(i), rotation, defaultColour)
  sprite_rotate(tank_sprite(0), tank_sprite(i), rotation, defaultColour)
next

'init sprites
for y = 0 to 31
  for x = 0 to 31
    pset tile1_sprite, (x, y), rgb (randint(100)+50, randint(100) + 100, randint(50))
    pset tile2_sprite, (x, y), rgb (randint(100)+100, randint(100) + 50, randint(50))
  next
next

'init world
for x = 0 to 199
  for y = 0 to 199
    if randint(2) = 1 then world(x, y) = tile1_sprite else world(x, y) = tile2_sprite
  next
next

xt = 3123
yt = 2123

while not multikey(FB.SC_ESCAPE)

  if multikey(FB.SC_RIGHT) then
    tank_direction -= .002
    if (tank_direction < 0) then tank_direction += 2 * pi
    update = 1
  end if
  if multikey(FB.SC_LEFT) then
    tank_direction += .002
    if (tank_direction > 2 * pi) then tank_direction -= 2 * pi
    update = 1
  end if
  if multikey(FB.SC_UP) then
    tank_speed += .0002
    if (tank_speed > 0.2) then tank_speed = 0.2
    update = 1
  else
    tank_speed -= .0002
    if (tank_speed < 0.0) then
      tank_speed = 0.0
    else
      update = 1
    end if
  end if

'  xt += tank_speed * -sin(tank_direction)
'  yt += tank_speed * -cos(tank_direction)
  iSprite = int ((tank_direction / (2 * pi)) * 64)
  if (iSprite < 0) then iSprite = 0
  if (iSprite > 64-1) then iSprite = 64-1
  xt += tank_speed * -sin((iSprite / 64) * 2 * pi)
  yt += tank_speed * -cos((iSprite / 64) * 2 * pi)

  if update = 1 then
    update = 0
    xLeftUp = (xt - scrW \ 2)
    yLeftUp = (yt - scrH \ 2)
    xOffset = xLeftUp mod 32
    yOffset = yLeftUp mod 32
    xTileIndex = xLeftUp \ 32
    yTileIndex = yLeftUp \ 32
        
    for x = 0 to scrW \ 32
      for y = 0 to scrH \ 32 + 1
        tile_sprite = tileEmpty_sprite
        if (xTileIndex + x) > 0 and (xTileIndex + x) < 200 then
          if (yTileIndex + y) > 0 and (yTileIndex + y) < 200 then
            tile_sprite = world(xTileIndex + x, yTileIndex + y)
          end if
        end if
        put (x * 32 - xOffset, y * 32 - yOffset), tile_sprite, pset
      next
    next
    put (scrW \ 2, scrH \ 2), tank_sprite(iSprite), trans
    locate 1,1: print iSprite
    locate 2,1: print using "##.##"; tank_direction
    locate 3,1: print using "##.##"; tank_speed
    flipscreen()
    'sleep 10
  else
    sleep 10
  end if
  
wend

imagedestroy(tile1_sprite)
imagedestroy(tile2_sprite)
imagedestroy(tileEmpty_sprite)

for i = 0 to 64-1
  imagedestroy(tank_sprite(i))
next


while inkey = "": wend
Locate 1,1: Print "end"
flipscreen()
sleep

'---------------------- Subroutines ----------------------

sub colorToRGB(byref colour as rgbc_type)
   colour.b = colour.c and &h000000FF
   colour.g = (colour.c and &h0000FF00) shr 8
   colour.r = (colour.c and &h00FF0000) shr 16
end sub

sub rgbToColor(byref colour as rgbc_type)
   colour.c = rgb(colour.r, colour.g, colour.b)
end sub

sub flipScreen()
  static as integer page1 = 0
  static as integer page2 = 1
  page1 = page1 xor 1
  page2 = page2 xor 1
  screenset page1, page2
end sub

sub sprite_rotate(srcImg as any ptr, dstImg as any ptr, rotation as single, defaultColour as integer)
  dim as integer srcWidth, srcHeight
  dim as single xctr, yctr
  dim as integer x, y
  dim as integer xsrc, ysrc
  dim as integer colour
  dim as integer colourInterpol(3)
  imageInfo srcImg, srcWidth, srcHeight
  xctr = srcWidth / 2
  yctr = srcHeight / 2
  for y = 0 to srcHeight-1
    for x = 0 to srcWidth-1
      xsrc = int((x - xctr) * cos(rotation) - (y - yctr) * sin(rotation) + xctr + 0.5)
      ysrc = int((x - xctr) * sin(rotation) + (y - yctr) * cos(rotation) + yctr + 0.5)
      if inLimits(xsrc, 0, srcWidth-1) and inLimits(ysrc, 0, srcHeight-1) then
        colour = point(xsrc, ysrc, srcImg)
      else
        colour = defaultColour
      end if
      pset dstImg, (x, y), colour
    next
  next
end sub

sub sprite_rotate_bilinear(srcImg as any ptr, dstImg as any ptr, rotation as single, defaultColour as integer)
  dim as integer srcWidth, srcHeight
  dim as single xctr, yctr
  dim as integer x, y
  dim as single xSrc, ySrc, xFact, yFact
  dim as integer xSrcLeft, xSrcRight, ySrcUp, ySrcDown
  dim as rgbc_type colour, cLeftUp, cLeftDown, cRightUp, cRightDown
  imageInfo srcImg, srcWidth, srcHeight
  xctr = srcWidth / 2
  yctr = srcHeight / 2
  for y = 0 to srcHeight-1
    for x = 0 to srcWidth-1
      xSrc = (x - xctr) * cos(rotation) + (y - yctr) * sin(-rotation) + xctr
      ySrc = (x - xctr) * sin(rotation) + (y - yctr) * cos(rotation) + yctr
      
      xSrcLeft = int(xSrc)
      xSrcRight = int(xSrc) + 1
      xFact = xSrc - xSrcLeft
      ySrcUp = int(ySrc)
      ySrcDown = int(ySrc) + 1
      yFact = ySrc - ySrcUp
      
      if inLimits(xSrcLeft, 0, srcWidth-1) and inLimits(ySrcUp, 0, srcHeight-1) then
        cLeftUp.c = point(xSrcLeft, ySrcUp, srcImg)
      else
        cLeftUp.c = defaultColour
      end if
      if inLimits(xSrcRight, 0, srcWidth-1) and inLimits(ySrcUp, 0, srcHeight-1) then
        cRightUp.c = point(xSrcRight, ySrcUp, srcImg)
      else
        cRightUp.c = defaultColour
      end if
      if inLimits(xSrcLeft, 0, srcWidth-1) and inLimits(ySrcDown, 0, srcHeight-1) then
        cLeftDown.c = point(xSrcLeft, ySrcDown, srcImg)
      else
        cLeftDown.c = defaultColour
      end if
      if inLimits(xSrcRight, 0, srcWidth-1) and inLimits(ySrcDown, 0, srcHeight-1) then
        cRightDown.c = point(xSrcRight, ySrcDown, srcImg)
      else
        cRightDown.c = defaultColour
      end if
      
      colorToRGB(cLeftUp)
      colorToRGB(cLeftDown)
      colorToRGB(cRightUp)
      colorToRGB(cRightDown)

      colour.r = cLeftUp.r * (1-xFact) * (1-yFact) + cRightUp.r * xFact * (1-yFact)_
        + cLeftDown.r * (1-xFact) * yFact + cRightDown.r * xFact * yFact
      colour.g = cLeftUp.g * (1-xFact) * (1-yFact) + cRightUp.g * xFact * (1-yFact)_
        + cLeftDown.g * (1-xFact) * yFact + cRightDown.g * xFact * yFact
      colour.b = cLeftUp.b * (1-xFact) * (1-yFact) + cRightUp.b * xFact * (1-yFact)_
        + cLeftDown.b * (1-xFact) * yFact + cRightDown.b * xFact * yFact

      rgbToColor(colour)
      pset dstImg, (x, y), colour.c
    next
  next
end sub

function inLimits(i as integer, iMin as integer, imax as integer) as integer
  if (i < iMin) then return 0
  if (i > iMax) then return 0
  return 1
end function
Edit: Code updated for FBC 64-bit
Last edited by badidea on Jun 20, 2019 20:36, edited 4 times in total.
KristopherWindsor
Posts: 2428
Joined: Jul 19, 2006 19:17
Location: Sunnyvale, CA
Contact:

Post by KristopherWindsor »

Looks nice.
Another approach I once used is to enlarge the image, rotate with a fast function (I think I used Multiput in Orb), then shrink the image. I think that produces a higher-quality result.
Dr_D
Posts: 2451
Joined: May 27, 2005 4:59
Contact:

Post by Dr_D »

badidea
Posts: 2591
Joined: May 24, 2007 22:10
Location: The Netherlands

Re: Sprite rotation

Post by badidea »

I have updated my old code (sprite rotation with bilinear interpolation) so that it can be used with transparency image (with &00FF00FF as transparent colour).

Code: Select all

const pi as double = 3.1415926535897932
const rad as double = 180 / pi

union rgba_union
	dim as ulong v 'value
	type 
		dim as ubyte b, g, r, a
	end type
end union

sub sprite_rotate_bilinear(srcImg as any ptr, dstImg as any ptr, rotation as single)
	dim as integer srcWidth, srcHeight
	dim as single xctr, yctr 'center
	dim as integer x, y
	dim as single xSrc, ySrc, xFact, yFact, fraction, factor
	dim as integer xSrcLeft, xSrcRight, ySrcUp, ySrcDown
	dim as rgba_union colour
	dim as single sumR, sumG, sumB
	dim as single sinRot = sin(rotation), cosRot = cos(rotation)
	imageInfo srcImg, srcWidth, srcHeight
	xctr = (srcWidth - 1) / 2
	yctr = (srcHeight - 1) / 2
	for y = 0 to srcHeight-1
		for x = 0 to srcWidth-1
			xSrc = (x - xctr) * cosRot - (y - yctr) * sinRot + xctr
			ySrc = (x - xctr) * sinRot + (y - yctr) * cosRot + yctr

			xSrcLeft = int(xSrc)
			xSrcRight = int(xSrc) + 1
			xFact = xSrc - xSrcLeft
			ySrcUp = int(ySrc)
			ySrcDown = int(ySrc) + 1
			yFact = ySrc - ySrcUp

			sumR = 0
			sumG = 0
			sumB = 0
			fraction = 0
			
			if (xSrcLeft >= 0) and (xSrcLeft <= srcWidth-1) then
				if (ySrcUp >= 0) and (ySrcUp <= srcHeight-1) then
					colour.v = point(xSrcLeft, ySrcUp, srcImg)
					if colour.v <> rgb(255, 0, 255) then
						factor = (1-xFact) * (1-yFact)
						fraction += factor
						sumR += colour.r * factor
						sumG += colour.g * factor
						sumB += colour.b * factor
					endif
				end if
				if (ySrcDown >= 0) and (ySrcDown <= srcHeight-1) then
					colour.v = point(xSrcLeft, ySrcDown, srcImg)
					if colour.v <> rgb(255, 0, 255) then
						factor = (1-xFact) * yFact
						fraction += (1-xFact) * yFact
						sumR += colour.r * factor
						sumG += colour.g * factor
						sumB += colour.b * factor
					end if
				end if
			end if

			if (xSrcRight >= 0) and (xSrcRight <= srcWidth-1) then
				if (ySrcUp >= 0) and (ySrcUp <= srcHeight-1) then
					colour.v = point(xSrcRight, ySrcUp, srcImg)
					if colour.v <> rgb(255, 0, 255) then
						factor = xFact * (1-yFact)
						fraction += factor
						sumR += colour.r * factor
						sumG += colour.g * factor
						sumB += colour.b * factor
					end if
				end if
				if (ySrcDown >= 0) and (ySrcDown <= srcHeight-1) then
					colour.v = point(xSrcRight, ySrcDown, srcImg)
					if colour.v <> rgb(255, 0, 255) then
						factor = xFact * yFact
						fraction += factor
						sumR += colour.r * factor
						sumG += colour.g * factor
						sumB += colour.b * factor
					end if
				end if
			end if

			 'in total more then half a pixel?
			if fraction > 0.5 then
				sumR /= fraction
				sumG /= fraction
				sumB /= fraction
				colour.r = sumR
				colour.g = sumG
				colour.b = sumB
			else
				colour.v = &h00ff00ff
			end if
			pset dstImg, (x, y), colour.v
		next
	next
end sub

'-------------------------------------------------------------------------------

const SCRN_W = 800, SCRN_H = 600

sub setScreen(w as integer, h as integer)
	screenres w, h, 32
	width w \ 8, h \ 16
end sub

sub clearScreen(w as integer, h as integer, c as ulong)
	line(0, 0)-(w-1, h-1), c, bf
end sub

setScreen(SCRN_W, SCRN_H)

dim as integer x, y, r = 25
dim as any ptr pImgScr(0 to 9)
dim as any ptr pImgDst(0 to 9)

clearScreen(SCRN_W, SCRN_H, rgb(255, 0, 255))
for i as integer = 0 to 9
	pImgScr(i) = imagecreate(r * 2 + 1, r * 2 + 1)
	pImgDst(i) = imagecreate(r * 2 + 1, r * 2 + 1)
	x = 50 + i * (2 * r + 10)
	y = 100
	circle (x + r, y + r), r, rgb(127, 127, 0),,,,f
	line(x + 5,y + 15)-step(r * 2 - 10, r * 2 - 30), rgb(200, 200, 127), bf
	draw string (x + r - 3, y + r - 7), str(i), rgb(255, 255, 0)
	get (x, y)-step(r * 2, r * 2), pImgScr(i)
next

locate 1,1 : : print "Press any key for next step"
while inkey = "" : wend

dim as single angle = 0
while inkey = ""
	screenlock
	clearScreen(SCRN_W, SCRN_H, rgb(0, 0, 128))
	for i as integer = 0 to 9
		sprite_rotate_bilinear(pImgScr(i), pImgDst(i), angle + (i / 10) * pi )
		x = 50 + i * (2 * r + 10)
		y = 200
		put(x, y), pImgDst(i), trans
	next
	locate 1,1 : print "Press any key to freeze"
	screenunlock
	sleep 15
	angle += pi / 100
wend

for i as integer = 0 to 9
	imagedestroy(pImgScr(i))
	pImgScr(i) = 0
	imagedestroy(pImgDst(i))
	pImgDst(i) = 0
next

locate 1,1 : print "Press any key to exit..."
while inkey = "" : wend
To be speed optimised by direct memory access pointer...

The edges are rough. No interpolation there. Alfa channel not used.
Image
Also rough with internal transparency. Cannot do colour interpolation with the pink transparency colour.
Image
Post Reply