Thread Rating:
  • 0 Vote(s) - 0 Average
  • 1
  • 2
  • 3
  • 4
  • 5
Geometry Challenge
#1
Make a routine which draws the "n" vertices of a regular polygon. Those vertices must be stored in memory (a shared array or whatever). Use whatever memory representation you need.

The sollution which takes less memory to store the polygon wins. The coordinates should be floating point numbers (SINGLE).

Code:
DIM SHARED PolyData(????) AS SINGLE

SUB DrawPoly(n%)

For example, trivial sollution:

Code:
SUB DrawPoly(n%)
   oldx!=PolyData(0)
   oldy!=PolyData(1)
   FOR i%=1 TO n%
      if i%<n% THEN
         x!=PolyData(i%*2)
         y!=PolyData(i%*2+1)
      ELSE
         x!=PolyData(0)
         y!=PolyData(1)
      ENDIF
      LINE (oldx!, oldy!) - (x!,y!)
      oldx!=x!
      oldy!=y!
   NEXT
END SUB

The above sollution uses n%*4*2 bytes (2 coordinates for each one of the n% vertices, each one taking 4 bytes for being a SINGLE value).

That can be done in a much better way which only would take 12 bytes per poly Wink Can you guess?

If not, try at least to minimize used memory. You have to use SINGLEs.
SCUMM (the band) on Myspace!
ComputerEmuzone Games Studio
underBASIC, homegrown musicians
[img]http://www.ojodepez-fanzine.net/almacen/yoghourtslover.png[/i
Reply
#2
Nathan, This doesn't really meet your challenge, but...anyway...I wrote it to plot the vertices of a polygon...but then decided to fill in the lines rather than just draw the points...and then decided to add rotation...anyway...this doesn't fit your challenge because it doesn't need to store the coordinates...rather it calculates them each time it needs. So...radius controls size, x and y offset controls position, and rotation controls the orientation...

Code:
TYPE poly
  sides AS STRING * 1    ' 1 byte
  x AS INTEGER           ' 2-bytes
  y AS INTEGER           ' 2-bytes
  radius AS INTEGER      ' 2-bytes
  rot AS STRING * 1      ' 1-byte
END TYPE                 '--------------
DIM a AS poly            ' 8-bytes total

CONST pi = 3.141592
CONST circ = 2 * pi
tempsize = 200 'default value
SCREEN 12
DO
  PRINT "This program will draw an n-sided polygon"
  DO
   INPUT "How many sides for your polygon (0 to exit)? ", tempsides
  LOOP WHILE ((tempsides > 255) OR (tempsides < 0))
  IF INT(tempsides) = 0 THEN END
  INPUT "Size of poly (pixels across)"; tempsize
  PRINT "Mapped to center of screen..."
  INPUT "x-coord of poly (integer)"; tempx
  INPUT "y-coord of poly (integer)"; tempy
  INPUT "rotation of poly (degrees)"; temprot
  a.sides = CHR$(ABS(INT(tempsides)))
  IF tempsize = 0 THEN a.radius = 100 ELSE a.radius = tempsize / 2
  a.x = tempx
  a.y = tempy
  a.rot = CHR$((256 * (temprot MOD 360)) / 360) 'rotates backwards, 1.4 degree / click == ((1/256) * 360) degrees / click
  PRINT ASC(a.rot)
  radiansRotate = -1 * circ * (ASC(a.rot) / 256)
  CLS
  PRINT "sides", "radius", "rotation", "x-coord", "y-coord"
  PRINT ASC(a.sides), a.radius, ((ASC(a.rot) / 256) * 360), a.x, a.y
   FOR i# = radiansRotate TO circ + radiansRotate STEP circ / ASC(a.sides)
      PSET (a.x + 320 + (a.radius * SIN(i#)), a.y + 240 + (a.radius * COS(i#)))
   NEXT i#
   LOCATE 24: PRINT "Continue..."
   SLEEP: CLS
   b$ = INKEY$
LOOP
END

edit:: OK...I just changed the non-animated version to use type...makes it easier to see how much space the polygon takes up. It is 12 bytes per polygon. I'm leaving the animated thingie alone for the time being... Cheers

edit(again)::Sorry to keep editing my posts. I just took a byte off of my storage...down to 11-bytes/polygon...by making rotation 1-byte instead of 2....that gives 1.4 degree resolution, which is plenty for 640x480. I've been thinking...(with paper), and I can get a poly (on a 640x480 screen) down to 6 bytes with no problems:

x-coord 10-bits (1024 values should be plenty at these dimensions)
y-coord 9 - bits (512 values should be plenty at these dimensions)
# sides 8-bits (256 values should plenty (seeing how a 50-sided polygon is indistinguishable from a *circle*) at these dimensions)
size 9-bits (0-511) should be plenty at this size
rotation 8-bits (o-256) should be plenty (1.4 degree/click) at these dimensions.

This adds up to 44 bits...requiring just 6 bytes. So as not to waste any bits, we give the extras away, which allows for super big polys that just cross the screen from some offscreen location.

x - 11 bits
y - 10 bits
sides - 8 bits
rotation - 9 bits
size - 10 bits
_______________
total 48-bits (6 bytes)

However, this would be a bit of a pain in the ass to program in QB since we are limited to 8-bit bytes, native words are signed, and there are no bit-shift operators....however, it can be done with an additional 20 or so lines of code.

edit(again)::actually...you can get down to 5-bytes...by trading some rotation bits with sides bits. with sides = 3 you only need to rotate by 360/3 to represent all possible polys (since we are dealing with *regular polygons*). as you increase the # of sides, you decrease the number of possible rotations. Cheers

Code:
SCREEN 12
DO
   INPUT "How many sides in your polygon <zero to exit>"; sides#
   sides# = ABS(INT(sides#))
   CLS : PRINT sides#; "sided polygon"
   offsetx% = 320
   offsety% = 240
   radius% = 100
   rotation# = -3  ' radians
   inc = .005
   pi# = 3.141592
   circ# = 2 * pi#
DO
   FOR t = 1 TO 1000: NEXT t
   PRESET (offsetx% + (radius% * COS(oldrotation#)), offsety% + (radius% * SIN(oldrotation#)))
   FOR i# = oldrotation# TO (circ#) * ((sides# + 1) / sides#) + oldrotation STEP (circ#) / sides#
     LINE -(offsetx% + (radius% * COS(i#)), offsety% + (radius% * SIN(i#))), 0
   NEXT i#

   PRESET (offsetx% + (radius% * COS(rotation#)), offsety% + (radius% * SIN(rotation#)))
   FOR i# = rotation# TO (2 * pi#) * ((sides# + 1) / sides#) + rotation STEP (circ#) / sides#
     LINE -(offsetx% + (radius% * COS(i#)), offsety% + (radius% * SIN(i#)))
   NEXT i#
  
   oldrotation# = rotation#
   IF ((rotation# > 1) OR (rotation# < -6)) THEN inc = inc * -1
   rotation# = rotation# + inc
   a$ = INKEY$
LOOP UNTIL a$ <> ""
LOOP WHILE sides# > 0

Edit:::again...Here's a hack of the original animated thingie...this could make a pretty cool fractal if each sub-circle was surrounded with sub-circles...etc.
Code:
SCREEN 12
DO
   INPUT "How many sides in your polygon <zero to exit>"; sides#
   sides# = ABS(INT(sides#))
   CLS : LOCATE 1, 1: PRINT "Polygon Sides:"; sides#
   offsetx% = 320
   offsety% = 240
   radius% = 100
   rotation# = -3  ' radians
   inc = .005
   pi# = 3.141592
   circ# = 2 * pi#
    oldsides# = sides#
  colora = 10
DO
   LOCATE 1, 15: PRINT sides#;
   offsetx% = offsetx% + 1 - INT(RND * 3)
   offsety% = offsety% + 1 - INT(RND * 3)
   radius% = radius% + 1 - INT(RND * 3)
   colora = colora + .5 - RND
   IF ((colora > 15) OR (colora < 1)) THEN colora = 8
   IF RND > .99 THEN
      sides# = sides# + 1
      IF sides# > 20 THEN sides# = 20
   END IF
   IF RND < .01 THEN
      sides# = sides# - 1
      IF sides# = 0 THEN sides# = 1
  END IF
  ' FOR t = 1 TO 10000
  ' : NEXT t
   'PRESET (oldoffsetx% + (oldradius% * COS(oldrotation#)), oldoffsety% + (oldradius% * SIN(oldrotation#)))
   FOR i# = oldrotation# TO (circ#) * ((oldsides# + 1) / oldsides#) + oldrotation STEP (circ#) / oldsides#
     CIRCLE (oldoffsetx% + (oldradius% * COS(i#)), oldoffsety% + (oldradius% * SIN(i#))), oldradius% / 5, 0
   NEXT i#
    CIRCLE (oldoffsetx%, oldoffsety%), .8 * oldradius%, 0

   'PSET (offsetx% + (radius% * COS(rotation#)), offsety% + (radius% * SIN(rotation#)))
   FOR i# = rotation# TO (2 * pi#) * ((sides# + 1) / sides#) + rotation STEP (circ#) / sides#
     CIRCLE (offsetx% + (radius% * COS(i#)), offsety% + (radius% * SIN(i#))), radius% / 5
   NEXT i#
    CIRCLE (offsetx%, offsety%), .8 * radius%
  
   oldsides# = sides#
   oldradius% = radius%
   oldoffsety% = offsety%
   oldoffsetx% = offsetx%
   oldrotation# = rotation#
   IF ((rotation# > 1) OR (rotation# < -6)) THEN inc = inc * -1
   rotation# = rotation# + inc
   a$ = INKEY$
LOOP UNTIL a$ <> ""
LOOP WHILE sides# > 0

and one more...
Code:
SCREEN 12
DO
   INPUT "How many sides in your polygon <zero to exit>"; sides#
   sides# = ABS(INT(sides#))
   CLS : LOCATE 1, 1: PRINT "Polygon Sides:"; sides#
   offsetx% = 320
   offsety% = 240
   radius% = 100
   rotation# = -3  ' radians
   inc = .005
   pi# = 3.141592
   circ# = 2 * pi#
    oldsides# = sides#
  colora = 10
depth = 6
DO
   LOCATE 1, 15: PRINT sides#;
   depth = depth + .5 - RND
   IF (depth > 20) OR (depth < 0) THEN depth = 10
   offsetx% = offsetx% + 1 - INT(RND * 3)
   offsety% = offsety% + 1 - INT(RND * 3)
   radius% = radius% + 1 - INT(RND * 3)
   colora = colora + .5 - RND
  
   IF ((colora > 15) OR (colora < 1)) THEN colora = 8
   IF RND > .99 THEN
      sides# = sides# + 1
      IF sides# > 20 THEN sides# = 20
   END IF
   IF RND < .01 THEN
      sides# = sides# - 1
      IF sides# = 0 THEN sides# = 1
  END IF
  ' FOR t = 1 TO 10000
  ' : NEXT t
   'PRESET (oldoffsetx% + (oldradius% * COS(oldrotation#)), oldoffsety% + (oldradius% * SIN(oldrotation#)))
radfactor = 1
  FOR p = 1 TO olddepth
   FOR i# = oldrotation# TO (circ#) * ((oldsides# + 1) / oldsides#) + oldrotation STEP (circ#) / oldsides#
     CIRCLE (oldoffsetx% + (oldradius% * radfactor * COS(i#)), oldoffsety% + (oldradius% * radfactor * SIN(i#))), oldradius% * radfactor / 5, 0
   NEXT i#
   radfactor = radfactor * .65
  NEXT p
    'CIRCLE (oldoffsetx%, oldoffsety%), .8 * oldradius%, 0

   'PSET (offsetx% + (radius% * COS(rotation#)), offsety% + (radius% * SIN(rotation#)))
  radfactor = 1
  offset# = rotation# - oldrotation#
  FOR p = 1 TO depth
   FOR i# = rotation# TO (2 * pi#) * ((sides# + 1) / sides#) + rotation STEP (circ#) / sides#
     'CIRCLE (oldoffsetx% + (oldradius% * radfactor * COS(i# + offset#)), oldoffsety% + (oldradius% * radfactor * SIN(i# + offset))), oldradius% * radfactor / 5, 0
     CIRCLE (offsetx% + (radius% * radfactor * COS(i#)), offsety% + (radius% * radfactor * SIN(i#))), radius% * radfactor / 5
   NEXT i#
   radfactor = radfactor * .65
  NEXT p
   ' CIRCLE (offsetx%, offsety%), .8 * radius%
  olddepth = depth
   oldsides# = sides#
   oldradius% = radius%
   oldoffsety% = offsety%
   oldoffsetx% = offsetx%
   oldrotation# = rotation#
   IF ((rotation# > 1) OR (rotation# < -6)) THEN inc = inc * -1
   rotation# = rotation# + inc
   a$ = INKEY$
LOOP UNTIL a$ <> ""
LOOP WHILE sides# > 0
Reply
#3
Quote:Make a routine which draws the "n" vertices of a regular polygon.
come on, man!!! You gave me reason to enjoy my afternoon. Gimme some feedback!!!. This was a fun challenge...I knew how to approach the problem, and it didn't take long to have a v1 running. And didn't take much time from other work. Good clean fun. Smile
Reply
#4
I just remembered something...

Might be able to find it in my HD. If I could read the letters... ;*(

This is a fun challenge.

Mine does not even use arrays. Is that legal?
y smiley is 24 bit.
[Image: anya2.jpg]

Genso's Junkyard:
http://rel.betterwebber.com/
Reply
#5
Sorry, I don't have internet at home.

Great efforts, mango :o . I didn't say that you had to store the actual coordinates (or I didn't intend to say so Wink), I just said that you should find a representation which uses SINGLE variables, floating point, so your Bitwise tricks don't enter (although they are really smart and of course should be taken in account for polygonal representations).

Most of your optimizations are based upon integer angles and stuff (as far as I understand your code), so they don't really fit on the purpose. I wanted to represent polygons using the maximum amount of precission possible (at least with SINGLEs, I could've used DOUBLES but oh, well... Big Grin).

I can think of two representations:

PolyData(0)=x0
PolyData(1)=x1
PolyData(2)=angle

Where (x0,x1) are the starting point, angle is an angle in radians. You just provide "n" to the function to draw the polygon. It would be very similar to your code.

There is another representation that takes 12 bytes as well (3 SINGLE values). Can you figure it out?

And rel: It should use the SHARED PolyData SINGLE array, and the SUB must have the provided prototype (only takes n%).
SCUMM (the band) on Myspace!
ComputerEmuzone Games Studio
underBASIC, homegrown musicians
[img]http://www.ojodepez-fanzine.net/almacen/yoghourtslover.png[/i
Reply
#6
Quote:I can think of two representations:

PolyData(0)=x0
PolyData(1)=x1
PolyData(2)=angle

I may not understand you, but I don't think this is enough info. I think you need:

Location of poly (cartesian, polar coordinates, or whatever)
it's number of sides (an integer)
it's size (length per side or radius of circle, or whatever)
it's "orientation" (degrees, radians, or whatever)

You can, or course play tricks for how you represent...ie you can use the center for location, or the first verticee, but I don't really see how you can represent all possible polygons with less data?
Reply
#7
That's the same way that I see it.
Code:
TYPE PolyType
  n   AS INTEGER            ' Number of sides
  Xc  AS SINGLE             ' Center coordinate
  Yc  AS SINGLE             ' Center coordinate
  r   AS SINGLE             ' Radius of circumscribed circle
  Ang AS SINGLE             ' Angle of first vertex above horizontal
END TYPE
This is 18 bytes, but I can't see how to get it any lower.
hrist Jesus came into the world to save sinners, of whom I am first.(I Timothy 1:15)

For God so loved the world, that He gave His only begotten Son,
that whoever believes in Him should not perish, but have eternal life.(John 3:16)
Reply
#8
oooops. Forgot about this.

Nate: It takes N as argument. And I think I could cook something up in my sis' comp today...
y smiley is 24 bit.
[Image: anya2.jpg]

Genso's Junkyard:
http://rel.betterwebber.com/
Reply
#9
Sorry, I did a mistake. Yeah, you need x0, y0, angle and side. "n" is passed to the drawing routine.

This can be done in another way, and this is what I want you to find.

SCM: "n" is passed to the drawing routine, so you don't need it in the type. What I am asking for is the drawing routine plus the representation. You HAVE to use the PolyData array.
SCUMM (the band) on Myspace!
ComputerEmuzone Games Studio
underBASIC, homegrown musicians
[img]http://www.ojodepez-fanzine.net/almacen/yoghourtslover.png[/i
Reply
#10
na_th_an,
I wasn't intending the Type statement to be a submission. I just thought it was the clearest way to show the needed data. Here is a submission:
Code:
DECLARE SUB DrawRegPoly (n%, P AS ANY, PColor%, Fill%)
DEFINT A-Z

TYPE PolyType
  r AS SINGLE
  Xc AS SINGLE
  Yc AS SINGLE
  Ang AS SINGLE
END TYPE
CONST Pi = 3.14159265358979#

DIM Poly AS PolyType

Poly.r = 80
Poly.Xc = 160
Poly.Yc = 90
Poly.Ang = 0

SCREEN 13

FOR j = 3 TO 20
  CLS
  LINE (0, 0)-(319, 190), , B
  LOCATE 23, 17: PRINT "Sides:"; j;

  DrawRegPoly j, Poly, (j - 1) MOD 7 + 9, (j - 1) MOD 7 + 1
  
  DO: k$ = INKEY$: LOOP WHILE k$ = ""
  IF k$ = CHR$(27) THEN EXIT FOR
NEXT

SUB DrawRegPoly (n, P AS PolyType, PColor, Fill)
  DIM Theta AS SINGLE, AspRatio AS SINGLE
  Theta = P.Ang
  AspRatio = 5 / 6                 ' For SCREEN 13
  X1 = P.Xc + P.r * COS(Theta)
  Y1 = P.Yc + P.r * SIN(Theta) * AspRatio
  PrevX = X1
  PrevY = Y1
  FOR i = 2 TO n
    Theta = Theta + 2 * Pi / n
    X = P.Xc + P.r * COS(Theta)
    Y = P.Yc + P.r * SIN(Theta) * AspRatio
    LINE (X, Y)-(PrevX, PrevY), PColor
    PrevX = X
    PrevY = Y
  NEXT
  LINE (X1, Y1)-(PrevX, PrevY), PColor
  IF Fill <> 0 THEN PAINT (P.Xc, P.Yc), Fill, PColor
END SUB
If you are going to pass n as a parameter, it might be good to pass the angle as a parameter also. For example, in my opinion most poygons look best with a flat bottom (it appeals to my sense of stability). This can be done by setting the angle to ((n - 2) mod 4) * Pi / (2 * n). This depends on the number of sides, so a single angle won't do.
hrist Jesus came into the world to save sinners, of whom I am first.(I Timothy 1:15)

For God so loved the world, that He gave His only begotten Son,
that whoever believes in Him should not perish, but have eternal life.(John 3:16)
Reply


Forum Jump:


Users browsing this thread: 1 Guest(s)