BASIC programs from TheBackShed on PicoCalc

There are lots of nice programs and code samples on TheBackShed, but most that use graphics commands won’t work without some modifications for the PicoCalc. Sometimes it’s just the display size – many programs there assume at least a 640x480 display. Since the main display targets there seem to be HDMI and VGA rather than LCD, the code regularly uses commands that aren’t available on PicoCalc. Games have additional problems since they often use gamepads wired up to the custom boards, USB keyboards, custom sound hardware, and other things we don’t have availble on the PicoCalc.

I decided to port some of the code and will be posting it here. I’ll also include it in the wiki I’ve been putting together here, but I wanted to post the modified code on the forum so it would be easy to discover and try, and so I’d have a place to link to the code from the wiki. I might eventually add it to a git repo at some point.

Note that none of this code is orginally mine, I’ve just tweaked it to run (or run better) on the PicoCalc. Also, in many cases the screenshots aren’t very representative since there are a lot of animated examples. Some of the colors and plots/drawings have random elements as well, so may look different each time they are run.

1 Like

“Dragon Curve” from vegipete

Originally posted at CMM2 Turtle Graphics Demos.
I also used some code and ideas from andreas’ post and matherp’s post to implement the Turtle routines, since they aren’t available natively in PicoMite/Webmite as they apparently are for the CMM2 build of MMBasic.

Not only is it a cool fractal line drawing, but it uses old school turtle graphics commands to control a pen that draws the fractal. The screenshot doesn’t really do it justice because part of the fun is watching it draw itself, and trying different input values.

If anyone else wants to adapt other turtle graphics code, this might be a good place to start.

Dim penx,peny,pen,pencolor,penheading As integer
Option angle degrees

CLS
TURTLE_reset
Do
 Print @(0,0) "Order: (1-19)"
 Input "0 to quit: "; dord
Loop Until dord >= 0 And dord < 20

Do
 If dord = 0 Then End

 dord = dord - 1
 dist = MM.HRES/2/(Sqr(2)^dord)

 CLS
 TURTLE_reset
 Text 220, 0,"Dragon Curve",,,,RGB(RED)
 Text 220,12,"Order:" + Str$(dord+1),,,,RGB(RED)
 TURTLE_pen_up   ' no line yet
 TURTLE_move MM.HRES * .25, MM.VRES * .55
 TURTLE_pen_down

 TURTLE_heading 90 - (dord Mod 8) * 45
 TURTLE_pen_colour RGB(red)
 DrawDragon(dord,1)

 TURTLE_heading 270 - (dord Mod 8) * 45
 TURTLE_pen_colour RGB(green)
 DrawDragon(dord,1)

 Do
   Text 220, 0,"Dragon Curve",,,,RGB(GREEN)
   Text 220,12,"Order:" + Str$(dord+1),,,,RGB(GREEN)
   Print @(0,0) "Order: (1-19)"
   Input "0 to quit: "; dord
 Loop Until dord >= 0 And dord < 20

Loop

Sub DrawDragon(ord, sig)
 If ord = 0 Then
   TURTLE_forward dist
 Else
   DrawDragon(ord-1,  1)
   TURTLE_turn_right 90 * sig
   DrawDragon(ord-1, -1)
 EndIf
End Sub

Sub TURTLE_reset
 penx=0
 peny=0
 pen=0
 penheading=0
 pencolor = RGB(black)
End Sub

Sub TURTLE_pen_up
 pen=0
End Sub

Sub TURTLE_pen_down
 pen=1
End Sub

Sub TURTLE_move(x,y)
 If pen=1 Then
   Line penx,peny,x,y,,pencolor
 EndIf
 penx = x
 peny = y
End Sub

Sub TURTLE_pen_colour(c)
 pencolor = c
End Sub

Sub TURTLE_heading(h)
 penheading = h
End Sub

Sub TURTLE_turn_right(a)
 Inc penheading,a
 If penheading>360.0 Then Inc penheading,-360.0
End Sub

Sub TURTLE_turn_left(a)
 Inc penheading,-a
 If penheading<0.0 Then Inc penheading,360.0
End Sub

Sub TURTLE_backward(l)
 Local x=penx-Sin(penheading)*l
 Local y=peny+Cos(penheading)*l
 If pen=1 Then Line penx,peny,x,y,1,pencolor
 penx=x
 peny=y
End Sub

Sub TURTLE_forward(l)
 Local x=penx+Sin(penheading)*l
 Local y=peny-Cos(penheading)*l
 If pen=1 Then Line penx,peny,x,y,1,pencolor
 penx=x
 peny=y
End Sub

“Alien Art” from Womble

Originally posted at CMM2: Alien Art post on Hackaday got me thinking.

This program displays 12 different types of art, all generated from surprisingly simple math.

' AART.BAS based on article on Hackaday and Twitter post by Martin Kleppe@aemkei
' https://hackaday.com/2021/04/13/alien-art-drawn-with-surprisingly-simple-math/
' https://twitter.com/aemkei/status/1378106731386040322
' https://twitter.com/redsteamengine/status/1378868421723623425
' https://bbcmic.ro/# post by baffinsquid / bbcmicrobot
'
' CMM2 port by Womble, 13 April 2021, v1.0
' PicoCalc port by adcockm, 18 June 2025
'

'Recommended Program Practice
Option EXPLICIT          ' Variables must be typed
Option DEFAULT NONE      ' Variables must be declared

CLS

Dim FLOAT X
Dim FLOAT Y
Dim FLOAT YSKIP = 25

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

Print "Alien Art"
For Y=0 To (319-YSKIP)
  For X=0 To 319
     ' Pattern Variations
     ' IF (X XOR Y) MOD 3 = 0 THEN
     ' IF (X XOR Y) MOD 5 = 0 THEN
     If (X Xor Y) Mod 9 = 0 Then     'original pattern from twitter
     ' IF (X XOR Y) MOD 17 = 0 THEN
     ' IF (X XOR Y) MOD 33 = 0 THEN
        Pixel X,Y+YSKIP
     End If
  Next X
Next Y

Print "Pause until ESC is pressed"
Do : Loop Until Inkey$=Chr$(27)
CLS

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

Print "Sierpinski triangles"
For Y=0 To (319-YSKIP)
  For X=0 To 319
     ' Pattern Variations
     If (X Or Y) Mod 7 = 0 Then
     ' IF (X OR Y) MOD 17 = 0 THEN
     ' IF (X OR Y) MOD 29 = 0 THEN
        Pixel X,Y+YSKIP
     End If
  Next X
Next Y

Print "Pause until ESC is pressed"
Do : Loop Until Inkey$=Chr$(27)
CLS

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

Print "Circular Patterns"
For Y=0 To (319-YSKIP)
  For X=0 To 319
     ' Pattern Variations
     ' Enclose logical operations in ()
     ' IF ((X * Y) AND 24) = 0 THEN
     ' IF ((X * Y) AND 47) = 0 THEN
     If ((X * Y) And 64) = 0 Then
        Pixel X,Y+YSKIP
     End If
  Next X
Next Y

Print "Pause until ESC is pressed"
Do : Loop Until Inkey$=Chr$(27)
CLS

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

Print "Steps"
For Y=0 To (319-YSKIP)
  For X=0 To 319
     ' Pattern Variations
     If (X Xor Y) < 77 = 0 Then
     ' IF (X XOR Y) < 120 = 0 THEN
     ' IF (X XOR Y) < 214 = 0 THEN
        Pixel X,Y+YSKIP
     End If
  Next X
Next Y

Print "Pause until ESC is pressed"
Do : Loop Until Inkey$=Chr$(27)
CLS

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

Print "Beams"
For Y=1 To (319-YSKIP)
  For X=1 To 319
     ' Pattern Variations
     If (X Xor 2) Mod Y = 0 Then
     ' IF (X XOR 31) MOD Y = 0 THEN
     ' IF (X XOR 64) MOD Y = 0 THEN
        Pixel X-1,Y+YSKIP-1
     End If
  Next X
Next Y

Print "Pause until ESC is pressed"
Do : Loop Until Inkey$=Chr$(27)
CLS

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

Print "Vanishing Point"
For Y=0 To 150
  For X=0 To 319
     If (((X-128) * 64) Mod (Y-151)) = 0 Then
        Pixel X,Y+YSKIP
     End If
  Next X
Next Y

Print "Pause until ESC is pressed"
Do : Loop Until Inkey$=Chr$(27)
CLS

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

Print "Chequer"
For Y=0 To (319-YSKIP)
  For X=0 To 319
     ' Pattern Variations
     ' IF ((X XOR Y) AND 23) = 0 THEN
     If ((X Xor Y) And 32) = 0 Then
     ' IF ((X XOR Y) AND 72) = 0 THEN
        Pixel X,Y+YSKIP
     End If
  Next X
Next Y

Print "Pause until ESC is pressed"
Do : Loop Until Inkey$=Chr$(27)
CLS

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

Print "Noise"
For Y=1 To (150-YSKIP)
  For X=1 To 319
     If ((X * Y) ^ 4) Mod 7 = 0 Then
        Pixel X-1,Y+YSKIP-1
     End If
  Next X
Next Y

Print "Pause until ESC is pressed"
Do : Loop Until Inkey$=Chr$(27)
CLS

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

Print "Rotate"
For Y=1 To (319-YSKIP)
  For X=1 To 319
     If (X Mod Y) Mod 4 = 0 Then
        Pixel X-1,Y+YSKIP-1
     End If
  Next X
Next Y

Print "Pause until ESC is pressed"
Do : Loop Until Inkey$=Chr$(27)
CLS

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

Print "Red Steam Engines Favourite"
For Y=1 To (319-YSKIP)
  For X=1 To 319
     If (((X * Y) And 243) And ((X Xor Y) And 243)) = 0 Then
        Pixel X-1,Y+YSKIP-1
     End If
  Next X
Next Y

Print "Pause until ESC is pressed"
Do : Loop Until Inkey$=Chr$(27)
CLS

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

Print "Red Steam Engines No.2"
For Y=1 To (319-YSKIP)
  For X=1 To 319
     If (((X * Y) And 255) And ((X \ Y) And 255)) = 0 Then
        Pixel X-1,Y+YSKIP-1
     End If
  Next X
Next Y

Print "Pause until ESC is pressed"
Do : Loop Until Inkey$=Chr$(27)
CLS

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

' (abs(x+y)^abs(x-y)+1)**37 % 7) * 255

Print "Foldsters Example from Python"
For Y=1 To (319-YSKIP)
  For X=1 To 319
     If ((Abs(X + Y) Xor Abs(X - Y) +1) ^ 37 Mod 7) * 255 = 0 Then
        Pixel X-1,Y+YSKIP-1
     End If
  Next X
Next Y

Print "Pause until ESC is pressed"
Do : Loop Until Inkey$=Chr$(27)
CLS

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

' End Program

“PCB Router” from javavi

Originally posted at PicoMiteVGA DEMO.

DefineFont #9
08300C08
00000000 00000000 00000000 667E3C18 C3C3C3C3 183C7E66
18181818 18181818 18181818 00000000 00FFFF00 00000000
18181818 00E0F038 00000000 18181818 00070F1C 00000000
00000000 38F0E000 18181818 00000000 1C0F0700 18181818
End DefineFont
Dim upSet(7)=(&hCB,&hFD,&h36,&hC3,&hCB,&
hCB,&h36,&h36)
Dim lfSet(7)=(&hA7,&hFD,&hA7,&h5A,&hA7,&
h5A,&hA7,&h5A)
Dim upEstr(79)

Font 9: CLS
Do
 lfE=0
 For i=0 To 79
   upE=upEstr(i)
   xxSet=upSet(upE) And lfSet(lfE)
   Do
     tmp=Int(Rnd*8)
   Loop Until xxSet And (1<<tmp)
   lfE=tmp
   upEstr(i)=tmp
   Color RGB(Green)
   If tmp=1 Then Colour RGB(Yellow)
   Print Chr$(tmp+48);
   Pause 1
 Next
Loop

“Incredible Knot” from javavi

Originally posted at PicoMiteVGA DEMO.

Font 9
Do
 For n=1 To 1200
   Print Chr$(Rnd*7+32);
 Next
 Pause 2000
 Print @(0,0);
Loop

DefineFont #9
08201010
C003C003 C003C003 C003C003 DFFBDFFB DFFBDFFB C003C003 C003C003 C003C003
C003C003 0000E001 FC03F001 FFF0FFC7 E3FF0FFF 800FC03F 80070000 C003C003
C003C003 C003C003 0000C003 FFFFFFFF FFFFFFFF C0030000 C003C003 C003C003
C003C003 80078007 402F000F 77EF63EF F7C6F7EE F000F402 E001E001 C003C003
C003C003 8007C007 003F800F 1FFC07FE 7FE03FF8 F001FC00 E003E001 C003C003
C003C003 E003E003 FC01F001 7FF8FFE0 0FFE3FFC 800F003F C0078007 C003C003
C003C003 8007C007 003F800F 1FFC07FE 7FE03FF8 F001FC00 E003E001 C003C003
C003C003 E001E003 FC00F001 3FF87FE0 07FE1FFC 800F003F C0078007 C003C003
End DefineFont

“The Mystery of Deep Space” from javavi

Originally posted at PicoMiteVGA DEMO.

Do
CLS
For G=-Rnd*42 To 400
tt=Rnd*99:  qq=Rnd*99
uu=Rnd*320: vv=Rnd*320
A=Rnd*3
R=90/(1+Rnd*100)
Q=1+3*(.5+Rnd/2)
aa=1+3*Rnd^2: M=1
If Rnd*9<4 Then Q=R:T=0:qq=0:A=0:M=Pi/3:
aa=1
C=(1+3*Rnd^2)*R*R
Color Rnd*&hFFFFFF
For i=0 To C
  S=-Log(Rnd):  T=i*M
  U=S*R*Sin(T): V=S*Q*Cos(T)
  T=S*A
  X=U*Cos(T)+V*Sin(T)
  Y=V*Cos(T)-U*Sin(T)
  D=(X*X+Y*Y)/(R*R+Q*Q)
  Z=99*((2.7^-D)+.1)
  Z=Z*(Rnd-.5)^3
  y0=Y*Cos(tt)+Z*Sin(tt)
  Z=Z*Cos(tt)-Y*Sin(tt)
  x0=uu+X*Cos(qq)+y0*Sin(qq)
  y0=vv-X*Sin(qq)+y0*Cos(qq)
  Pixel x0,y0
Next
Next
Loop
2 Likes

“Windows” from javavi

Originally posted at PicoMiteVGA DEMO. Note the changes to the use of FRAMEBUFFER since the original code is not supported on LCD devices like the PicoCalc.

FRAMEBUFFER CREATE
FRAMEBUFFER WRITE F
Dim COL(5)=(RGB(Black),RGB(Red),RGB(Green),RGB(Blue),RGB(Cyan),RGB(Yellow))

Do
 CLS RGB(Cyan)
 For R=0 To 6
   For C=0 To 12
     S=C*1.25+2.5: If C>6 Then S=16
     V=FNA(C+Q)
     X=80+C*12
     Y=40+R*(16+(C<7)*1)+V
     IC=(1+2*(R>3)+(C>9)*((R>3)+1))*(R Mod 3>0)*(C<6 Or C Mod 3>0)
     Clr=COL(IC)
     Z=S/2.5: If C>6 Then Z=V-FNA(C+Q+1)
     X0=X:Y0=Y
     X1=X+S*.8:Y1=Y-Z
     X2=X:Y2=Y+S
     X3=X+S*.8:Y3=Y+S-Z
     Triangle X0,Y0,X1,Y1,X2,Y2,Clr,Clr
     Triangle X1,Y1,X2,Y2,X3,Y3,Clr,Clr
   Next
 Next
 Text 160,200,"Windows 98","CM",5,1,0,RGB(Cyan)
 FRAMEBUFFER COPY F,N
 Pause 5
 Inc Q,0.5
Loop

Function FNA(A)
 FNA=Sin(A/2.23)*12
End Function

“Barnsley Fern” from javavi

Originally posted at PicoMiteVGA DEMO.

Do
 Select Case Rnd
   Case Is < .01
       nX = 0
       nY = .16 * Y
   Case .01 To .08
       nX = .2 * X - .26 * Y
       nY = .23 * X + .22 * Y + 1.6
   Case .08 To .15
       nX = -.15 * X + .28 * Y
       nY = .26 * X + .24 * Y + .44
   Case Else
       nX = .85 * X + .04 * Y
       nY = -.04 * X + .85 * Y + 1.6
 End Select

 X = nX
 Y = nY

 pX= 320 * (X + 3) / 6
 pY = 320 - 320 * ((Y + 2) / 14)
 Pixel pX, pY

Loop Until Inkey$ <> ""

“Fractal Star” from javavi

Originally posted at PicoMiteVGA DEMO.

Do
 CLS
 A=2*(.5-Rnd): B=2*(.5-Rnd)
 C=2*(.5-Rnd): D=2*(.5-Rnd)
 X=Rnd: Y=Rnd
Do
 SX=Pi*2*X: SY=Pi*2*Y
 SX4=Pi*4*X: SY4=Pi*4*Y
 X1=A*Sin(SX)+B*Sin(SX)*Cos(SY)+C*Sin(SX4)+D*Sin(Pi*6*X)*Cos(SY4)
 Y1=A*Sin(SY)+B*Sin(SY)*Cos(SX)+C*Sin(SY4)+D*Sin(Pi*6*Y)*Cos(SX4)
 NX=Int(100*X1+160): NY=Int(100*Y1+160)
 Pixel NX,NY
 X=X1: Y=Y1
Loop Until Inkey$<>""
Loop

“Red Chinese Procedural Dragon” from javavi

Originally posted at PicoMiteVGA DEMO.

Dim GCOL(3)=(RGB(YELLOW),RGB(RED),RGB(BLACK),RGB(WHITE))
S=Sin(.03):C=Cos(.03):X=260:Y=20:U=0:V=1
For A=80 To 1200
X=X+U:Y=Y+V:K=Sgn(Cos(A/45)*Cos(A*.0138))
T=U:U=U*C-K*V*S:V=V*C+K*T*S:Z=24-A Mod 10
For B=-Z To Z
R=1-80/A
CI=1+(Int(3*Abs(Cos(B*.3+(A\4 Mod 2)*Pi/2+.4)))=A Mod 4)-(Abs(B)>16)
Colour GCOL(CI)
Pixel 1*Int(X+R*B*V),250-1*(Y-R*B*U)
Next :Next
K=190
For J=0 To K
R=(200-80*Cos(J*3*Pi/K))*(.8+.5*Cos(J*13*Pi/K)*Cos(J*13*Pi/K))
For I=0 To R Step 5
CI=1.2-(I/R)-(J\20=4)*(2*(I\15=3)+1)-(J\12=14)*(I\30=3)
Colour GCOL(Abs(CI))
S=Sin(J*Pi/K):C=Cos(J*Pi/K):V=8*Sin(I/16)
Pixel 160+(I*S+V*C)/4,70-(I*C+V*S)/4
Pixel 160-(I*S+V*C)/4,70-(I*C+V*S)/4
Next : Next
1 Like

“Sierpinski Triangle” from javavi

Originally posted at PicoMiteVGA DEMO.

RX=MM.HRES:RY=MM.VRES:CX=RX\2:CY=RX\2

Do
 rs=Int(Rnd(1)*3)
 If rs=1 Then
   fx=CX:fy=0
 ElseIf rs=2 Then
   fx=0:fy=RY
 Else
   fx=RX:fy=RY
 EndIf
 x=(x+fx)\2
 y=(y+fy)\2
 Pixel x,y
Loop Until Inkey$<>""

“Star” from javavi

Originally posted at PicoMiteVGA DEMO.

RX=MM.HRES:RY=MM.VRES:CX=RX\2:CY=RY\2
RR1=150:RR2=-50:RR3=30:K=0.45:Q=0.1

For R1=RR1 To 187 Step 5
 For R2=RR2 To 240 Step 5
   Q=Rnd*2
   For R3=RR3 To 240 Step 5
     COL=Int(Rnd*&hFFFFFF)
     For T=0 To 600 Step Q
       X=Int((R1+R2)*Cos(R2*T/R1)-R3*Cos((R1+R2)/R1*T))
       Y=Int((R1+R2)*Sin(R2*T/R1)-R3*Sin((R1+R2)/R1*T))
       Pixel X*K+CX, Y*K+CY, COL
     Next T
   Next R3
   Pause 1000: CLS
 Next R2
Next R1
End

“EPICYCLOID” from javavi

Originally posted at PicoMiteVGA DEMO.

RX=MM.HRES:RY=MM.VRES:CX=RX\2:CY=RY\2
R1=111:R2=16:R3=131:K=CY/270

For Q=1 To 0 Step -0.01
 CLS
 For T=0 To 600 Step Q
   X=Int((R1+R2)*Cos(R2*T/R1)-R3*Cos((R1+R2)/R1*T))
   Y=Int((R1+R2)*Sin(R2*T/R1)-R3*Sin((R1+R2)/R1*T))
   Pixel X*K+CX, Y*K+CY
 Next T
Next Q
End

“Spirograph” from javavi

Originally posted at PicoMiteVGA DEMO.

Option BASE 0

'Define color lookup table
Dim integer c(15)
c(0) =&H000000
c(1) =&H0000FF:c(2) =&H004000:c(3) =&H0040FF:c(4) =&H008000:c(5) =&H0080FF
c(6) =&H00FF00:c(7) =&H00FFFF:c(8) =&HFF0000:c(9) =&HFF00FF:c(10)=&HFF4000
c(11)=&HFF40FF:c(12)=&HFF8000:c(13)=&HFF80FF:c(14)=&HFFFF00:c(15)=&HFFFFFF

'Set up the Spirograph parameters
r1 = (MM.VRES/8)*3  '180 '90
r2 = (MM.VRES/8)    '60 '30
p =  (MM.VRES/8)*2  '120 '60

'Set up the rotation parameters
cx = MM.HRES/2  '320 or 160
cy = MM.VRES/2+1'240 or 120
angle = 0

Do
  If Rnd<0.5 Then CLS
  p = Rnd * (MM.VRES/4)
  angle_step = Rnd*3

  For i = 1 To 15
    colr = Int(Rnd*16)
    sa = Sin(angle)
    ca = Cos(angle)

    'Calculate the Spirograph path
    For t = 0 To 360 Step 1
       a = (r1-r2)/r2
       x = (r1-r2)*Cos(t) + p*Cos(a*t)
       y = (r1-r2)*Sin(t) - p*Sin(a*t)

       'Rotate the coordinates and draw a pixel
       xp = cx + Int(x*ca - y*sa)
       yp = cy + Int(x*sa + y*ca)
       Pixel xp, yp, c(colr)

   Next t
   'Update the angle and wait a bit before redrawing
   angle = angle + angle_step

  Next i

Loop Until Inkey$ <> ""
1 Like

“Windows Serenity” from javavi

Originally posted at PicoMiteVGA DEMO. Note that MAP() is not supported on LCD devices like the PicoCalc, so the default colors are hard-coded in the first line.

Dim CM(15)=(RGB(0,0,0),RGB(0,0,255),RGB(0,64,0),RGB(0,64,255),RGB(0,128,0),RGB(0,128,255),RGB(0,255,0),RGB(0,255,255),RGB(255,0,0),RGB(255,0,255),RGB(255,64,0),RGB(255,64,255),RGB(255,128,0),RGB(255,128,255),RGB(255,255,0),RGB(255,255,255))
W=0:E=Sqr(3):F=Sqr(7):Dim S(180)

For I=0 To 180: S(I)=Sin(Rad(2*I)): Next

For X=0 To 319
 For Y=0 To 240
   K=32:G=0

   For H=1 To 2
     A=(X+180)/K: B=Y/K: C=Int(A): D=Int(B)
     G=G+(FNS(C,D)+FNS(C+1,D)+FNS(C,D+1)+FNS(C+1,D+1))
     K=K/2
   Next

   G=Int((G+W+X/320)/3)*15
   If G=0 Then
     G=7
     If (X+Y)/416>W Then G=1
   EndIf

   If Y<20*(S((X*.4+20)Mod 180)+3) Then
     G=6
     If S(((X+3*Y)/4+10)Mod 180)<W Then G=2
   EndIf

   Color CM(G)
   Pixel X,240-Y

   W=W+E-Int(W+E)
 Next
Next

Function FNS(U,V)
 Q=(U*E+V*F)-Int(U*E+V*F)
 T=1-(A-U)*(A-U)-(B-V)*(B-V)
 If T<=0 Then FNS=0 Else FNS=(3-2*T)*T*T*Q
End Function

“Bubble Universe” from javavi

Originally posted at PicoMiteVGA DEMO. Note that MAP() is not supported on LCD devices like the PicoCalc, so the default colors are hard-coded in the first line.

Dim CM(15)=(RGB(0,0,0),RGB(0,0,255),RGB(0,64,0),RGB(0,64,255),RGB(0,128,0),RGB(0,128,255),RGB(0,255,0),RGB(0,255,255),RGB(255,0,0),RGB(255,0,255),RGB(255,64,0),RGB(255,64,255),RGB(255,128,0),RGB(255,128,255),RGB(255,255,0),RGB(255,255,255))
CX=MM.HRes\2:CY=MM.VRes\2
SC=MM.VRes/4
r=(2*Pi)/25
x=0:v=0:t=0

FRAMEBUFFER LAYER
FRAMEBUFFER WRITE L
Do
 CLS
 col=1
 For i=50 To 80 Step 2
   For j=50 To 70 Step 1
     u=Sin(i+v)+Sin(r*i+x)
     v=Cos(i+v)+Cos(r*i+x)
     x=u+t
     Pixel CX+SC*u,CY+SC*v,CM(col)
   Next j
   Inc col: If col>15 Then col=1
 Next i
 Inc t,.025
 FRAMEBUFFER COPY L,N
Loop

“Polygons” from javavi

Originally posted at PicoMiteVGA DEMO. Note that MAP() is not supported on LCD devices like the PicoCalc, so the default colors are hard-coded in the first line.

Dim CM(15)=(RGB(0,0,0),RGB(0,0,255),RGB(0,64,0),RGB(0,64,255),RGB(0,128,0),RGB(0,128,255),RGB(0,255,0),RGB(0,255,255),RGB(255,0,0),RGB(255,0,255),RGB(255,64,0),RGB(255,64,255),RGB(255,128,0),RGB(255,128,255),RGB(255,255,0),RGB(255,255,255))
CX=MM.HRes\2:CY=MM.VRes\2
Dim PX(6),PY(6)

R=128
D=2*R :S=R*Sqr(3)
K=512^2
For V=-20 To 20
 For H=-19 To 18
   CC=1+Abs(V*H/4)Mod 15
   I=0
   For L=-Pi To Pi Step Pi/3
     A=R+(1 And V)*R+H*D+Sin(L)*R
     B=V*S+Cos(L)*R
     C=K/(A*A+B*B)
     X=CX+B*C :Y=CY+A*C
     PX(I)=X:PY(I)=Y
     Inc I
   Next
   Line GRAPH PX(),PY(),CM(CC)
 Next
Next

“Morph” from javavi

Originally posted at PicoMiteVGA DEMO. Note that MAP() is not supported on LCD devices like the PicoCalc, so the default colors are hard-coded in the first line.

Dim CM(15)=(RGB(0,0,0),RGB(0,0,255),RGB(0,64,0),RGB(0,64,255),RGB(0,128,0),RGB(0,128,255),RGB(0,255,0),RGB(0,255,255),RGB(255,0,0),RGB(255,0,255),RGB(255,64,0),RGB(255,64,255),RGB(255,128,0),RGB(255,128,255),RGB(255,255,0),RGB(255,255,255))
W=MM.HRes:H=MM.VRes
C=-0.77:D=0.27015
For X%=0 To W Step 1
 For Y%=0 To H Step 1
   U=3*(X%-W/2)/W
   V=2*(Y%-H/2)/H
   I%=16
   Do
     I%=I%-1
     A=U*U:B=V*V
     T=A-B+C
     V=2*U*V+D
     U=T
   Loop Until A+B>2.2 Or I%<1
   Colour CM(I%)
   Pixel X%,Y%
   Pixel W-X%,H-Y%
 Next
Next

“Geometric Abstractionism” from javavi

Originally posted at PicoMiteVGA DEMO. Note that MAP() is not supported on LCD devices like the PicoCalc, so the default colors are hard-coded in the first line.

Dim CM(15)=(RGB(0,0,0),RGB(0,0,255),RGB(0,64,0),RGB(0,64,255),RGB(0,128,0),RGB(0,128,255),RGB(0,255,0),RGB(0,255,255),RGB(255,0,0),RGB(255,0,255),RGB(255,64,0),RGB(255,64,255),RGB(255,128,0),RGB(255,128,255),RGB(255,255,0),RGB(255,255,255))
Do :CLS
 For K=1 To 200
   Q=Int(Rnd*5+3): If Q=7 Then Q=30
   A=Rad(360/Q): S=Sin(A): C=Cos(A)
   X=Rnd*MM.HRes: Y=Rnd*MM.VRes
   R=Rnd*(Sqr(Y+X)/20)*20+16
   For L=-R/5 To R/5
     N=(Abs(L)<R/8)*Int(Rnd*16)
     U=R+L: V=U
     X1=X+U: Y1=Y+V
     For I=1 To Q
       T=V*C-U*S: U=V*S+U*C: V=T
       X2=X+U: Y2=Y+V
       Line X1,Y1,X2,Y2,,CM(N)
       X1=X2: Y1=Y2
     Next I
   Next
 Next
 Pause 1000
Loop
1 Like

“Galaxian” from javavi

Originally posted at PicoMiteVGA DEMO. Note that MAP() is not supported on LCD devices like the PicoCalc, so the default colors are hard-coded in the first line.

Dim CM(15)=(RGB(0,0,0),RGB(0,0,255),RGB(0,64,0),RGB(0,64,255),RGB(0,128,0),RGB(0,128,255),RGB(0,255,0),RGB(0,255,255),RGB(255,0,0),RGB(255,0,255),RGB(255,64,0),RGB(255,64,255),RGB(255,128,0),RGB(255,128,255),RGB(255,255,0),RGB(255,255,255))
Text 160,0,"000000","CT",7,1
For R=0 To 2: Proc(16*R,238,6,1):Next
Proc(140,230,12,7):Proc(150,192,2,7):Proc(154,50,17,6)
For R=1 To 8
Proc(32*R,150,9,8):Proc(32*R,120,10,9):Proc(32*R,90,8,14)
Next
End

Sub Proc(X0,Y0,Q,C)
Color CM(C)
A=1:W=X0:U=W+2*Q
For X=1 To (Q+2)/2
 Y=Y0:I=1
 Do
   If I And A Then Box W,Y,2,2: Box U,Y,2,2
   Inc Y,-2:Inc I,I
 Loop Until I>A
 A=A*(Q+1-X)/X
 Inc W,2:Inc U,-2
Next
End Sub
1 Like