skip navigation access key s Access Key Details


sdlBasic

(This page is archived at https://tinyurl.com/sdlbasic)
If you have been reading my articles for the TI99/4a Home Computer you will have realised my interest in strange graphics. Moving on to a modern PC, there isn't too much available to allow you to have fun with these little programs, but at last I found a very old language- although far more recent than the 1979 TI Basic. This is sdlBasic, a cross platform language (Atari, Windows, Mac, Unix (Linux) etc. There are 2005 and 2007 versions and even a 2012 version but the one I landed on first was the Mandriva 2010 build of the 2004 version. Speedy and easy.

There is a 2005 rpm build on Sourceforge but that one caused me problems, whereas the 2007 rpm build also from Sourceforge (not apparently built for any particular Linux distro) went in like a treat and is the one I now use. At the time of writing there is no rpm package of the 2012 version.

There is a discrepancy between my sdlbasic and the documentation- in theory rnd() should return a number up to 999999999, but in practice it returns a number up to 32 bit signed maxint. To solve this I have used rnd(999999999) instead of rnd().

More sdl basic listings can be found on: My 2nd sdlbasic page   ||   My 3rd sdlbasic page
Alphabetical index to SDL programs on this site
Chris Burch has converted some of these routines to another programming language you may want to look at, OpenEuphoria versions by Chris Burch

Main sdlBasic homepage || sdlBasic Online Documentation

Anyway, on this page I will place my sdlBasic versions of TI Extended Basic graphics programs. Probably fairly easy to adapt these to other languages. The small images are portions of the displayed screen.

Bifurcating lines

Bifurcating lines quickly head into chaos with this one:
' high resolution graphics using
' sdlBasic (Windows, Unix etc etc) -requires SDL.
bifurcating lines ' after brooks, harding etc
setdisplay(800,800,16,2)
cls
' ORBITDGM PROGRAM
FOR C=-2 TO 0.01 STEP .0005
    X=0
    M=500*(C+2)
      FOR I=0 TO 200
      X=X*X+C
        IF I>50 THEN
        N=(800/4)*(2-X)
        dot(M,N)
        END IF
      END FOR
END FOR
prints("Any key to end")
WAITKEY
END

Different Bifurcation routine

There is more than one way to calculate bifurcating lines....
'  image  using sdlBasic (Windows, Unix etc etc)
'   from ti*mes 31  BIFURCATION PLOT GENERATOR
'   (an idea from Clifford Pickover
' "Computers Pattern Chaos and Beauty" (1990))
'          S Shaw, 2014
SetDisplay(800,800,16,2)

randomize 
bifurcating lines 2
cls
fprints("ESC to end, R for random next")
MN=5 :  MX=83
' FULL-ISH PIC WOULD BE 0 TO 125 
' CHAOS RULES FROM 59 UP
BETA=5
' LOW beta VALUE 3 MAKES CHAOS FARTHER AWAY
'  HIGHER VALUE INCREASES CHAOS
RS=270
' RS is  PLOT RESOLUTION
X0=1.95
' START VALUE FOR Xt [t=0]
N=250
'  ITERATION COUNT USE HIGHER FOR MORE CHAOS
RSC=2.8*RS/ (MX-MN)  :  CS=80

WHILE INKEY<>k_esc
    FOR LA=MN TO MX STEP (MX-MN)/RS
    X=X0
        FOR I=1 TO N+10
        X=LA*X*(1+X)^(-BETA)
            IF I>10  THEN
            dot ((LA-MN)*RSC+21 , X*CS+91)
            end if
        NEXT
    NEXT
WAITKEY
IF INKEY=82 OR INKEY=114 THEN
    MN=RND(150) : MX=MN+RND(100)+2 : BETA=3+RND(3) 
    X0=RND(3)+0.01 : RSC=2.8*RS/ (MX-MN) : CLS 
    fprints("ESC to end, R for random next")
    END IF

Connett circles

Fractal Report Issue 10 pdf
Connett circles-

' high resolution graphics using  sdlBasic 
'  (Windows, Unix etc etc)
' from Wallpaper by Peter Moon of Stockton on Tees,
' Fractal Report issue 10, August 1990
'  also see "wallpaper on your screen" 
' Louis D Magguilli,  Algorithm 4.2 (June 1993)
' CIRCLES from JE Connett, PWH Moon, S Shaw, 1990
SetDisplay(1000,900,16,2)
randomize  
overlaid circles
SIDE=15
WHILE INKEY<>k_esc
  cls
  FOR I=1  TO 1000
    FOR J=1 TO 900
      X=I*SIDE/600
      Y=J*SIDE/600
      C=INT(X*X+Y*Y)
      D=C/2
      IF D-INT(D)<0.11 THEN
        DOT(I+1,J+1)
      END IF
    END FOR
  END FOR
prints ("ESC to end, r for random new one, s to zoom back to start, any other to zoom out ")
fprints ("Side=") : fprints(SIDE)
  SIDE=SIDE*1.15
  WAITKEY
IF INKEY=82 OR INKEY=114 THEN
   SIDE=RND(160)
   END IF
 IF INKEY=83 OR INKEY=115 THEN
  SIDE=15
   END IF
 WEND
END 
ESCape key to exit, any other key to zoom. Where do the circles come from? There is no use of sin, cos or tan etc.

gingerbread man

This chaotic set was described by Robert L Devaney in the Springer-Verlag book "The Science of Fractal Images" (1988) (see p 149, section 3.2.3). My code is based upon "Ginger Bread Men" by Tom Marlow, in Fractal Report issue 10 (August 1990). Also to be found in "The gingerbreadman" by Robert L Devaney in Algorithm 3.1 (January 1992).
Fractal Report Issue 10 pdf
' BIPED GRAPHIC PROGRAM USING THREE DIFFERENT LOOPS
' WHEN FLAG IS SET TO  0 1 OR 2
two legged creature
setdisplay(800,800,16,2)
cls
' MAG sets the size of the image
 MAG=21
' H and V set the image offset from top and side
 H=330 : V=260
 X=6.10 :  Y=6.00
 FLAG=0
   WHILE FLAG<3
       IF FLAG=1 THEN
       X=8.30 : Y=8.02
	 END IF
       IF FLAG=2 THEN
       X=8.56 : Y=3.76
         END IF
           FOR L=1 TO 3299
           NX=1-Y+ABS(X): NY=X : X=NX : Y=NY
           A=H+X*MAG-Y*MAG
           B=V+X*MAG+Y*MAG
           dot(A,B)
           NEXT
       FLAG=FLAG+1
   END WHILE
prints("press a key to end")
WAITKEY
END
Notice that sdlBasic supports numerous alternatives, so you can use WEND or END WHILE. You may also choose to use NEXT or instead use END FOR - and they have the same effect.

Random Biped

Just using a WAITKEY below ran the loops too quickly, and there isn't an easy way to see if a new key is pressed - except that as the keycode is passed when a key is RELEASED we can test INKEY<>0 after the WAITKEY, and move the test for the ESCape key to this section, wrapping the whole in a simple DO...LOOP. Notice that there are two ENDs! There must be one at the end but you can otherwise have them anywhere.
' biped variable graphic program
setdisplay(800,800,16,2)
' mag sets the size of the image
mag=21
' h and v set the image offset from top and side
h=350 : v=220
' x and y determine the pattern that will be drawn
' seems best between 6 and 9 but try anything!
randomize
do
	xr=rnd(10000)/10000*3 : yr=rnd(10000)/10000*3
	cls
	x=6+xr : y=6+yr
	for l=1 to 3299
		nx=1-y+abs(x): ny=x : x=nx : y=ny
		a=h+x*mag-y*mag
		b=v+x*mag+y*mag
		dot(a,b)
	end for
	fprints(xr) : fprints("   ")
fprints(yr) : fprints(" hold escape key to terminate and touch other key for new image")
	waitkey
	   if inkey=k_esc then
		end
	   end if
	while inkey<>0
	end while
loop
end

Starry Shapes

The first listing is from "Complex Curves from Simple Math" by Rastislav Telgarsky published in Volume 3 (August 1988) of The Journal of Chaos and Graphics (Ed: Clifford Pickover).
' high resolution graphics using sdlBasic 
' (Windows, Unix etc etc)
' starry shapes  S Shaw, 1990
SetDisplay(1000,1000,16,2)
SC=5
starry shapes
WHILE INKEY<>k_esc
  cls
  FOR I=1  TO 1000  
  FOR J=1 TO 1000
      A=I/SC
      C=INT(A*SQR(A*J/SC)+0.5)
        IF C/2<>INT(C/2)  THEN
        ' the same graphic is produced using 
        ' IF ANDBIT(C,2) THEN
        DOT(J+1,I+1)
        END IF
    END FOR
  END FOR
fprints ("ESC to end - any other to zoom in     ")
fprints ("scalar=  ") : fprints(SC)
WAITKEY
SC=SC*1.1
WEND
END    
======================

Producing a similar graphic but instead of using I*SQR(I*J) here we use I^2*J -this variant is from Clifford Pickover "Computers Pattern Chaos and Beauty" page 324.
Also here we change the bitwise operator instead of zooming in :
' starry shapes  2   - S Shaw, 1990
SetDisplay(800,800,16,2)
starry shapes
SHIFT=4
WHILE INKEY<>k_esc
  cls
  FOR I=1  TO 800
    FOR J=1 TO 800
T=((I/20)^2)*J
IF ANDBIT(T,2^SHIFT) THEN
    DOT(J,I)
	END IF
    END FOR
  END FOR
fprints ("ESC to end - any other to increase bit shift ")
fprints ("shift=  ") : fprints(SHIFT)
WAITKEY
SHIFT=SHIFT+1
IF SHIFT>10 THEN
SHIFT=4
END IF
WEND
END

Sierpinski Gasket

The Sierpinski Gasket or Sieve or Triangle was described by Waclaw Sierpinski in 1915. It can be ontained by several mathematical methods including Pascals Triangle (mod 2) which gives what is described as an approximation. This listing was inspired by "What is a Sierpinski Gasket" by Clifford Pickover in Volume 3 (August 1988) of The Journal of Chaos and Graphics (Ed: Clifford Pickover)
' high resolution graphics using sdlBasic 
' (Windows, Unix etc etc)
' sierpinski gasket from pascals triangle 
' from clifford pickover. Modified S Shaw, 1990
SetDisplay(800,800,16,2)
SC=3
DIM P[800],C[800]
WHILE INKEY<>k_esc
   cls
   FOR L=0 TO 800
   P[L]=1 :  C[L]=0
   END FOR
   FOR N=2 TO 800
serpinski gasket
      FOR R=2 TO N
      VAR=P[R]+P[R-1]
      C[R]=VAR MOD SC
         IF C[R]=0 THEN
         DOT(N,R)
         END IF
      END FOR
      FOR L=1 TO 800
      P[L]=C[L]
      END FOR 
   END FOR
locate(5,52) : fprints ("ESC to end - any other to increase modulus ")
fprints ("MODULUS  ") : fprints(SC)
WAITKEY
SC=SC+1
WEND
END      
' note that N MOD Q is the same as INT(N-Q*INT(N/Q))

Feather shape

' feather fractal using sdlBasic (Windows, Unix etc etc)
' strange attractor: Clifford A Pickover, Mazes for the Mind 1992
' also Clifford Pickover, Unseen Worlds, in Algorithm No 3.3, July 1992
' S Shaw, 1992
SetDisplay(800,800,16,2)
SC=1 : N=1
  WHILE INKEY<>k_esc
  cls
feather shape
  AA=-0.48 : B=0.93 : C=2-2*AA : X=3 : Y=0
  W=AA*X+C*X*X/(1+X*X)
  fprints ("  zoom=") : fprints (SC) 
  fprints (" ...a moment...")
    WHILE N<400000
' gives a reasonable image with this number of dots plotted
    N=N+1
    DOT (Y*25*SC+400,X*25*SC+500)
    Z=X : X=B*Y+W : U=X*X : W=AA*X+C*U/(1+U) : Y=W-Z
       WEND
fprints ("ESC to exit or any other key to zoom in/out")
WAITKEY
SC=(SC<>1)+(SC<>2.5)*2.5 : N=1
' above line toggles the value of SC and resets counter
  WEND
END

Random Attraction

Playing around with these little programs can be good if simple fun. Here is a variation on the above which allows random images with zoom in and out. In this case to demonstrate the variety better, click on the top thumbnail for a larger image.
If you have a fast computer or good patience, see what happens when you increase the number of dots plotted (the limiter on the variable N)- sometimes the image is stable very quickly, sometimes after a number of plots it will suddenly grow another layer. Some images will only have a few dots, just go on to the next image.
Tiny variations in coding can result in quite different results. Try this one.

' random attraction using sdlBasic (Windows, Unix etc etc)
' S Shaw, 1990-2013
random attractor thumbnail
SetDisplay(800,800,16,2)
RANDOMIZE
SC=0.5
A=rnd(999999999)/1000000000
IF RND(3)<2 THEN
   B=1
   ELSE
   B=0.933
   END IF
WHILE INKEY<>k_esc
CLS
FPRINTS(A) : FPRINTS(" -  ") : PRINTS(B)
LOCATE(1,1) : PRINTS ("  working  ")
C=2-2*A  :  X=3  : Y=0 : W=A*X+C*X*X/(1+X*X)
 FOR N=0 TO 500000
random attractor
IF ABS(X)<0.0001 THEN
   X=RND(10)
   END IF
    DOT(X*50*SC+350,Y*50*SC+450)
    Z=X : X=B*Y+W : U=X*X : W=A*X+C*U/(1+U) : Y=W-Z
 NEXT
 locate(1,1)
 fprints ("ESC to exit, i to zoom in,")
 prints("  o to zoom out, or SPACE for another  ")
  WAITKEY
IF INKEY=73 OR INKEY=105 THEN
random attractor lines
   SC=SC*1.4
   END IF
 IF INKEY=79 OR INKEY=111 THEN
   SC=SC*0.6
   END IF
IF INKEY=32 THEN
   rnd(999999999)/1000000000
   IF RND(3)<2 THEN
   B=1
   ELSE
   B=0.933
   END IF
END IF
WEND
END

simple plot 1

' high resolution graphics using sdlBasic 
' (Windows, Unix etc etc)
' plot S Shaw, 1990
distorted mesh
' change x and y multipliers and offsets for 
' detailed zoom (200 and 400 below)
' X varies between -1.7 and +1.7, Y from -1.1 to + 1.1
SetDisplay(800,800,16,2)
WHILE INKEY<>k_esc
   cls
   prints(" working...")
FOR T=0 TO 7000 STEP 0.006
X=SIN(0.99*T)-0.7*COS(3.01*T)
Y=COS(1.01*T)+0.1*SIN(15.03*T)
X=X*200+400 : Y=Y*200+400
DOT(Y,X)
NEXT
locate(0,0)
prints("ESC key to exit program, any other to run again")
waitkey
END WHILE
end

Egg Tile Generation

We are here defining the size of the graphic and then filling it in, so zooming in and out does not affect the pattern, and is rather pointless! However some interesting patterns from quite a short code. Try very small variations of each of the variables in turn, one at a time.

Variables:
r= number of pixels down and across of pic.
b1,b2=phase shift of sine wave, minor adjustments
g= frequency of sine wave, main pattern determinator.
a=degree of disorder, low a=good order
m=modulus, degree of pattern density- m low=more pixels on. Also affects pattern.

'  image  using sdlBasic (Windows, Unix etc etc)
'   (from egg tile generator page 242 of Computers 
 '          Chaos Pattern and Beauty
'   by Clifford A Pickover).(1990)
'          for ti by S Shaw 1990  - SDL BASIC 2014 
egg tile
SetDisplay(800,800,16,2)
randomize
cls
fprints("ESC to end, R for random next")
 R=700 :  B1=-6 :  B2=6  :  G=314
 A=5  :  M=3
WHILE INKEY<>k_esc
FOR I=1 TO R
   FOR J=1 TO R
      X=B1+(G*I)  :  Y=B2+(G*J)
      Z=A*(SIN(X)+SIN(Y))
      C=INT(Z)
      IF C/M<>INT(C/M) THEN
        DOT (I+20,J+20)
      END IF
   NEXT
NEXT

WAITKEY
IF INKEY=82 OR INKEY=114 THEN
CLS : B1=INT(RND(6))+6*-1 : B2=INT (RND(9))+12*-1 : SC=1
G=INT (RND(260))+60 : A=INT(RND(7))+4 : M=INT(RND(4))+4
fprints("ESC to end, R for random next")
END IF
WEND
END

Feigenbaum Diagram

Based upon Fractal Report Number 10. - total 320 subscribers. (Volume 2 no 10 First published August 1990. published by Reeves Telecommunications Laboratories. Publisher John de Rivaz placed the available text freely available online on Geocities). Issue 10 is the one with the front cover autograph by Arthur C Clarke.

The next program is based on work by M Feigenbaum in 1979 and produces some interesting pictures, depending on the limits you set when the program starts. Sometimes looking VERY closely (maximum magnification) will produce an interesting result, at other times it pays to stand back a little. Towards the bottom of the overall plot is chaos, on which can be found some overlying non-chaotic detail.

'  image  using sdlBasic (Windows, Unix etc etc)
'   feigenbaum  - Fractal Report 10
'
'          for ti by S Shaw 1990  - SDL BASIC 2014
'
SetDisplay(800,800,16,2)
pi=3.1415926
RANDOMIZE
WIDE=750 : : DEEP=400
bottom=1.14 : top=1.171 : LEFTS=2.53 : RIGHTS=2.586


VISIBLE=90 : INVISIBLE=10
SCALE=(RIGHTS-LEFTS)/WIDE

WHILE INKEY<>k_esc
cls
prints("ESC to end, a=visible+ b=visible- c & d move up and down")
fprints(" e=increase scale f=decrease scale g & h move left and right")
image of eigenbaum diagram
FOR RANGE=1 TO WIDE
   K=LEFTS+RANGE*SCALE
   P=0.3
   FOR I=0 TO INVISIBLE
      P=P+K*P*(1-P) :
      NEXT
   FOR I=0 TO VISIBLE
   ROW=(P-BOTTOM)*DEEP/(TOP-BOTTOM)
   COL=(K-LEFTS)*WIDE/(RIGHTS -LEFTS)
   dot(ROW,COL)
   P=P+K*P*(1-P)
   NEXT
NEXT
 WAITKEY

' increase visible a
IF INKEY=65 OR INKEY=97 THEN
   CLS
   VISIBLE=VISIBLE+5 : INVISIBLE=INVISIBLE-5
END IF
'decrease visible =b
IF INKEY=66 OR INKEY=98 THEN
   CLS
   VISIBLE=VISIBLE-5 : INVISIBLE=INVISIBLE+5
END IF
' up/down = c
IF INKEY=67 OR INKEY=99 THEN
    CLS
    LEFTS=LEFTS+0.01 : RIGHTS=RIGHTS+.01
END IF
' down/up=d
IF INKEY=68 OR INKEY=100 THEN
    LEFTS=LEFTS-0.01 : RIGHTS=RIGHTS-.01
    CLS
END IF
' increase wide=e
IF INKEY=69 OR INKEY=101 THEN
     CLS
     LEFTS=LEFTS-0.001 : RIGHTS=RIGHTS+0.001
     SCALE=(RIGHTS-LEFTS)/WIDE
END IF
' decrease wide=f
IF INKEY=70 OR INKEY=102 THEN
   CLS
   LEFTS=LEFTS+0.001 : RIGHTS=RIGHTS-0.001
   SCALE=(RIGHTS-LEFTS)/WIDE
END IF
'  left/right  = g
IF INKEY=71 OR INKEY=103 THEN
    CLS
    BOTTOM=BOTTOM+0.001 : TOP=TOP+0.001
END IF
' right / left =h
IF INKEY=72 OR INKEY=104 THEN
    CLS
    BOTTOM=BOTTOM-0.001 : TOP=TOP-0.001
END IF

WEND
END

Fluted Scallops

Image of fluted scallops Click image for larger version.
' fluted scallops - joe jacobson 1988
' journal of chaos and graphics august 1988
' for ti-99/4a January 1991 by stephen shaw
' for sdlbasic 2017 stephen shaw
setdisplay(800,800,16,2)
cls
RANDOMIZE(timer)
p=3.1415
S=400
m=3
   WHILE INKEY<>k_esc
   cls
   L=INT(60*(rnd(9999)/10000)+3)
      FOR B=16 TO 76  STEP 2
         FOR A=0 TO 360 STEP 5
           R3=SIN((L*A)/180*p)
           R=B*(1+(ABS(R3)/4))
           X=R*COS(A/180*p)
           Y=R*SIN(A/180*p)
           IF A=0 THEN
            DOT(S+m*X,S+m*Y)
            OLDX=X
            OLDY=Y
              ELSE
            LINE(S+OLDX*m,S+OLDY*m,S+X*m,S+Y*m)
	    OLDX=X
	    OLDY=Y
            END IF
         NEXT
      NEXT
WAITKEY
  IF INKEY=78 OR INKEY=110 THEN
  cls
  L=INT(60*(rnd(9999)/10000)+3)
fprints("ESC to end, any other key for random next")
  end if
FOR I=1 TO 400000
 j=cos(i)
 NEXT
 'AVOID FLICKER
WEND
END

Access Key Details