Using the data storage type definedon this page for raster images, and thedraw_line function defined inthis one, draw aquadratic bezier curve(definition on Wikipedia).
INCLUDE "H6:RGBLINE.ACT" ;from task Bresenham's line algorithmINCLUDE "H6:REALMATH.ACT"RGB black,yellow,violet,blueTYPE IntPoint=[INT x,y]PROC QuadraticBezier(RgbImage POINTER img IntPoint POINTER p1,p2,p3 RGB POINTER col) INT i,n=[20],prevX,prevY,nextX,nextY REAL one,two,ri,rn,rt,ra,rb,rc,tmp1,tmp2,tmp3 REAL x1,y1,x2,y2,x3,y3 IntToReal(p1.x,x1) IntToReal(p1.y,y1) IntToReal(p2.x,x2) IntToReal(p2.y,y2) IntToReal(p3.x,x3) IntToReal(p3.y,y3) IntToReal(1,one) IntToReal(2,two) IntToReal(n,rn) FOR i=0 TO n DO prevX=nextX prevY=nextY IntToReal(i,ri) RealDiv(ri,rn,rt) ;t=i/n RealSub(one,rt,tmp1) ;tmp1=1-t RealMult(tmp1,tmp1,ra) ;a=(1-t)^2 RealMult(two,rt,tmp2) ;tmp2=2*t RealMult(tmp2,tmp1,rb) ;b=2*t*(1-t) RealMult(rt,rt,rc) ;c=t^2 RealMult(ra,x1,tmp1) ;tmp1=a*x1 RealMult(rb,x2,tmp2) ;tmp2=b*x2 RealAdd(tmp1,tmp2,tmp3) ;tmp3=a*x1+b*x2 RealMult(rc,x3,tmp1) ;tmp1=c*x3 RealAdd(tmp3,tmp1,tmp2) ;tmp2=a*x1+b*x2+c*x3 nextX=Round(tmp2) RealMult(ra,y1,tmp1) ;tmp1=a*y1 RealMult(rb,y2,tmp2) ;tmp2=b*y2 RealAdd(tmp1,tmp2,tmp3) ;tmp3=a*y1+b*y2 RealMult(rc,y3,tmp1) ;tmp1=c*y3 RealAdd(tmp3,tmp1,tmp2) ;tmp2=a*y1+b*y2+c*y3 nextY=Round(tmp2) IF i>0 THEN RgbLine(img,prevX,prevY,nextX,nextY,col) FI ODRETURNPROC DrawImage(RgbImage POINTER img BYTE x,y) RGB POINTER ptr BYTE i,j ptr=img.data FOR j=0 TO img.h-1 DO FOR i=0 TO img.w-1 DO IF RgbEqual(ptr,yellow) THEN Color=1 ELSEIF RgbEqual(ptr,violet) THEN Color=2 ELSEIF RgbEqual(ptr,blue) THEN Color=3 ELSE Color=0 FI Plot(x+i,y+j) ptr==+RGBSIZE OD OD RETURNPROC Main() RgbImage img BYTE CH=$02FC,width=[70],height=[40] BYTE ARRAY ptr(8400) IntPoint p1,p2,p3 Graphics(7+16) SetColor(0,13,12) ;yellow SetColor(1,4,8) ;violet SetColor(2,8,6) ;blue SetColor(4,0,0) ;black RgbBlack(black) RgbYellow(yellow) RgbViolet(violet) RgbBlue(blue) InitRgbImage(img,width,height,ptr) FillRgbImage(img,black) p1.x=0 p1.y=3 p2.x=47 p2.y=39 p3.x=69 p3.y=12 RgbLine(img,p1.x,p1.y,p2.x,p2.y,blue) RgbLine(img,p2.x,p2.y,p3.x,p3.y,blue) QuadraticBezier(img,p1,p2,p3,yellow) SetRgbPixel(img,p1.x,p1.y,violet) SetRgbPixel(img,p2.x,p2.y,violet) SetRgbPixel(img,p3.x,p3.y,violet) DrawImage(img,(160-width)/2,(96-height)/2) DO UNTIL CH#$FF OD CH=$FFRETURN
Screenshot from Atari 8-bit computer
procedureQuadratic_Bezier(Picture:inoutImage;P1,P2,P3:Point;Color:Pixel;N:Positive:=20)isPoints:array(0..N)ofPoint;beginforIinPoints'RangeloopdeclareT:constantFloat:=Float(I)/Float(N);A:constantFloat:=(1.0-T)**2;B:constantFloat:=2.0*T*(1.0-T);C:constantFloat:=T**2;beginPoints(I).X:=Positive(A*Float(P1.X)+B*Float(P2.X)+C*Float(P3.X));Points(I).Y:=Positive(A*Float(P1.Y)+B*Float(P2.Y)+C*Float(P3.Y));end;endloop;forIinPoints'First..Points'Last-1loopLine(Picture,Points(I),Points(I+1),Color);endloop;endQuadratic_Bezier;
The following test
X:Image(1..16,1..16);beginFill(X,White);Quadratic_Bezier(X,(8,2),(13,8),(2,15),Black);Print(X);
should produce;
H H H H H HH HH H HH HHH HH
Based on...
This uses the ALGOL 68 Bitmap and Bresengems_line_algorithm samples (which are translated from the Ada samplesn of same).
File: prelude/Bitmap.a68 is on Rosetta Code atALGOL 68/prelude#prelude/Bitmap.a68
File: prelude/Bitmap/Bresenhams_line_algorithm.a68is on Rosetta Code atALGOL 68/prelude#prelude/Bitmap/Bresenhams_line_algorithm.a68
BEGIN # draw a quadratic curve using Bresenham's line algoritm # PR READ "prelude/Bitmap.a68" PR; PR READ "prelude/Bitmap/Bresenhams_line_algorithm.a68" PR; PROC quadratic bezier = ( REF IMAGE bm, INT x1, y1, x2, y2, x3, y3, nseg, REAL scale )VOID: BEGIN INT prevx := 0, prevy := 0; FOR i FROM 0 TO nseg DO REAL t = i / nseg; REAL t1 = 1 - t; REAL a = t1 * t1; REAL b = 2 * t * t1; REAL c = t * t; INT currx = ENTIER ( scale * ( a * x1 + b * x2 + c * x3 + 0.5 ) ); INT curry = ENTIER ( scale * ( a * y1 + b * y2 + c * y3 + 0.5 ) ); IF i > 0 THEN ( line OF class image )( bm , ( prevx, prevy ) , ( currx, curry ) , black OF class image ) FI; prevx := currx; prevy := curry OD END # quadratic bezier # ; BEGIN REF IMAGE bm = INIT LOC[ 1 : 60, 1 : 40 ]PIXEL; ( fill OF class image )( bm, white OF class image ); quadratic bezier( bm, 10, 100, 250, 270, 150, 20, 20, 70 / 300 ); # print in monochrome # FOR y FROM 2 UPB bm BY -1 TO 2 LWB bm DO FOR x FROM 1 LWB bm TO 1 UPB bm DO print( ( IF PIXEL( bm[ x, y ] ) /= white OF class image THEN "##" ELSE " " FI ) ) OD; print( ( newline ) ) OD ENDEND
################ ###### #### #### ## #### ## #### ## #### ## #### ## #### ## #### ## ## ## #### ## #### ## ## ## ## ## #### ## ## ## ## ## ## ## ## ## ## ## ## ## ## ## ## ## ## ## ## ## ## ## ##
Width%=200Height%=200REM Set window size:VDU23,22,Width%;Height%;8,16,16,128REM Draw quadratic Bézier curve:PROCbezierquad(10,100,250,270,150,20,20,0,0,0)ENDDEFPROCbezierquad(x1,y1,x2,y2,x3,y3,n%,r%,g%,b%)LOCALi%,t,t1,a,b,c,p{()}DIMp{(n%)x%,y%}FORi%=0TOn%t=i%/n%t1=1-ta=t1^2b=2*t*t1c=t^2p{(i%)}.x%=INT(a*x1+b*x2+c*x3+0.5)p{(i%)}.y%=INT(a*y1+b*y2+c*y3+0.5)NEXTFORi%=0TOn%-1PROCbresenham(p{(i%)}.x%,p{(i%)}.y%,p{(i%+1)}.x%,p{(i%+1)}.y%,\\r%,g%,b%)NEXTENDPROCDEFPROCbresenham(x1%,y1%,x2%,y2%,r%,g%,b%)LOCALdx%,dy%,sx%,sy%,edx%=ABS(x2%-x1%):sx%=SGN(x2%-x1%)dy%=ABS(y2%-y1%):sy%=SGN(y2%-y1%)IFdx%<dy%e=dx%/2ELSEe=dy%/2REPEATPROCsetpixel(x1%,y1%,r%,g%,b%)IFx1%=x2%IFy1%=y2%EXITREPEATIFdx%>dy%THENx1%+=sx%:e-=dy%:IFe<0e+=dx%:y1%+=sy%ELSEy1%+=sy%:e-=dx%:IFe<0e+=dy%:x1%+=sx%ENDIFUNTILFALSEENDPROCDEFPROCsetpixel(x%,y%,r%,g%,b%)COLOUR1,r%,g%,b%GCOL1LINEx%*2,y%*2,x%*2,y%*2ENDPROC
Interface (to be added to all other to make the finalimglib.h):
voidquad_bezier(imageimg,unsignedintx1,unsignedinty1,unsignedintx2,unsignedinty2,unsignedintx3,unsignedinty3,color_componentr,color_componentg,color_componentb);
Implementation:
#include<math.h>/* number of segments for the curve */#define N_SEG 20#define plot(x, y) put_pixel_clip(img, x, y, r, g, b)#define line(x0,y0,x1,y1) draw_line(img, x0,y0,x1,y1, r,g,b)voidquad_bezier(imageimg,unsignedintx1,unsignedinty1,unsignedintx2,unsignedinty2,unsignedintx3,unsignedinty3,color_componentr,color_componentg,color_componentb){unsignedinti;doublepts[N_SEG+1][2];for(i=0;i<=N_SEG;++i){doublet=(double)i/(double)N_SEG;doublea=pow((1.0-t),2.0);doubleb=2.0*t*(1.0-t);doublec=pow(t,2.0);doublex=a*x1+b*x2+c*x3;doubley=a*y1+b*y2+c*y3;pts[i][0]=x;pts[i][1]=y;}#if 0 /* draw only points */ for (i=0; i <= N_SEG; ++i) { plot( pts[i][0], pts[i][1] ); }#else/* draw segments */for(i=0;i<N_SEG;++i){intj=i+1;line(pts[i][0],pts[i][1],pts[j][0],pts[j][1]);}#endif}#undef plot#undef line
10rembeziercurvealgorihm20remtranslatedfrompurebasic30ns=25:remnumsegments40dimpt(ns,2):rempointsinline50sc=1024:remstartofscreenmemory60sw=40:remscreenwidth70sh=25:remscreenheight80pc=42:remplotcharacter'*'90dimbp(2,1):rembeziercurvepoints100bp(0,0)=1:bp(1,0)=70:bp(2,0)=1110bp(0,1)=1:bp(1,1)=8:bp(2,1)=23120dimpt%(ns,2):remindividuallinesincurve130gosub3000140end1000remplotline1010se=0:rem0=steep1=!steep1020ifabs(y1-y0)>abs(x1-x0)thense=1:tp=y0:y0=x0:x0=tp:tp=y1:y1=x1:x1=tp1030ifx0>x1thentp=x1:x1=x0:x0=tp:tp=y1:y1=y0:y0=tp1040dx=x1-x01050dy=abs(y1-y0)1060er=dx/21070y=y01080ys=-11090ify0<y1thenys=11100forx=x0tox11110ifse=1thenp0=y:p1=x:gosub2000:goto11301120p0=x:p1=y:gosub20001130er=er-dy1140ifer<0theny=y+ys:er=er+dx1150nextx1160return2000remplotindividualpoint2010remp0==plotpointx2020remp1==plotpointy2030sl=p0+(p1*sw)2040remmakesurewedontwritebeyondscreenmemory2050ifsl<(sw*sh)thenpokesc+sl,pc2060return3000rembeziercurve3010fori=0tons3020t=i/ns3030t1=1.0-t3040a=t1^23050b=2.0*t*t13060c=t^23070pt(i,0)=a*bp(0,0)+b*bp(1,0)+c*bp(2,0)3080pt(i,1)=a*bp(0,1)+b*bp(1,1)+c*bp(2,1)3090nexti3100fori=0tons-13110x0=int(pt(i,0))3120y0=int(pt(i,1))3130x1=int(pt(i+1,0))3140y1=int(pt(i+1,1))3150gosub10003160nexti3170return
Screenshot of Bézier curve on C64
This solution uses two modules, from the Grayscale image and the Bresenham's line algorithm Tasks.
importgrayscale_image,bitmap_bresenhams_line_algorithm;structPt{intx,y;}// Signed.voidquadraticBezier(size_tnSegments=20,Color)(Image!Colorim,inPtp1,inPtp2,inPtp3,inColorcolor)purenothrow@nogcif(nSegments>0){Pt[nSegments+1]points=void;foreach(immutablei,refp;points){immutabledoublet=i/double(nSegments),a=(1.0-t)^^2,b=2.0*t*(1.0-t),c=t^^2;p=Pt(cast(typeof(Pt.x))(a*p1.x+b*p2.x+c*p3.x),cast(typeof(Pt.y))(a*p1.y+b*p2.y+c*p3.y));}foreach(immutablei,immutablep;points[0..$-1])im.drawLine(p.x,p.y,points[i+1].x,points[i+1].y,color);}voidmain(){autoim=newImage!Gray(20,20);im.clear(Gray.white);im.quadraticBezier(Pt(1,10),Pt(25,27),Pt(15,2),Gray.black);im.textualShow();}
.......................................................#...................#...................#....................#...................#....................#...................#...................#...#...............#....##.............#......##...........#........#..........#.........#.........#..........###......#.............######...............................................................
This code uses a Quadratic Bézier curve to create a Cardinal Spline, which is a much easier spline to use. You just provide a series of points and the spline will honor those points while creating a smooth curline line between the points.
{This code would normally be in a library, but is presented here for clarity}typeT2DVector=packedrecordX,Y:double;end;typeT2DPolygon=arrayofT2DVector;functionVectorSubtract2D(constV1,V2:T2DVector):T2DVector;{Subtract V2 from V1}beginResult.X:=V1.X-V2.X;Result.Y:=V1.Y-V2.Y;end;functionScalarProduct2D(constV:T2DVector;constS:double):T2DVector;{Multiply vector by scalar}beginResult.X:=V.X*S;Result.Y:=V.Y*S;end;functionVectorAdd2D(constV1,V2:T2DVector):T2DVector;{Add V1 and V2}beginResult.X:=V1.X+V2.X;Result.Y:=V1.Y+V2.Y;end;functionScalarDivide2D(constV:T2DVector;constS:double):T2DVector;{Divide vector by scalar}beginResult.X:=V.X/S;Result.Y:=V.Y/S;end;{---------------- Recursive Bezier Quadratic Spline ---------------------------}functionIsZero(constA:double):Boolean;constEpsilon=1E-15*1000;beginResult:=Abs(A)<=Epsilon;end;functionGetEndPointTangent(EndPnt,Adj:T2DVector;tension:double):T2DVector;{ Calculates Bezier points from cardinal spline endpoints.}begin{ tangent at endpoints is the line from the endpoint to the adjacent point}Result:=VectorAdd2D(ScalarProduct2D(VectorSubtract2D(Adj,EndPnt),tension),EndPnt);end;procedureGetInteriorTangent(constpts:T2DPolygon;Tension:double;varP1,P2:T2DVector);{ Calculate incoming and outgoing tangents.}{Pts[0] = Previous point, Pts[1] = Current Point, Pts[2] = Next Point}varDiff,TV:T2DVector;begin{ Tangent Vector = Next Point - Previous Point * Tension}Diff:=VectorSubtract2D(pts[2],pts[0]);TV:=ScalarProduct2D(Diff,Tension);{ Add/Subtract tangent vector to get control points}P1:=VectorSubtract2D(pts[1],TV);P2:=VectorAdd2D(pts[1],TV);end;functionVectorMidPoint(constP1,P2:T2DVector):T2DVector;beginResult:=ScalarDivide2D(VectorAdd2D(P1,P2),2);end;{Don't change item order}typeTBezierPoints=packedrecordBeginPoint,BeginControl,EndControl,EndPoint:T2DVector;end;functionControlBetweenBeginEnd(BeginPoint,BeginControl,EndControl,EndPoint:double):boolean;{ Are control points are between begin and end point}beginResult:=False;ifBeginControl<BeginPointthenbeginifBeginControl<EndPointthenexit;endelseifBeginControl>EndPointthenexit;ifEndControl<BeginPointthenbeginifEndControl<EndPointthenexit;endelseifEndControl>EndPointthenexit;Result:=True;end;functionRecursionDone(constPoints:TBezierPoints):Boolean;{ Function to check that recursion can be terminated}{ Returns true if the recusion can be terminated }constBezierPixel=1;vardx,dy:double;begindx:=Points.EndPoint.x-Points.BeginPoint.x;dy:=Points.EndPoint.y-Points.BeginPoint.y;ifAbs(dy)<=Abs(dx)thenbegin{ shallow line - check that control points are between begin and end}Result:=False;ifnotControlBetweenBeginEnd(Points.BeginPoint.X,Points.BeginControl.X,Points.EndControl.X,Points.EndPoint.X)thenexit;Result:=True;ifIsZero(dx)thenexit;if(Abs(Points.BeginControl.y-Points.BeginPoint.y-(dy/dx)*(Points.BeginControl.x-Points.BeginPoint.x))>BezierPixel)or(Abs(Points.EndControl.y-Points.BeginPoint.y-(dy/dx)*(Points.EndControl.x-Points.BeginPoint.x))>BezierPixel)thenbeginResult:=False;exit;endelsebeginResult:=True;exit;end;endelsebegin{ steep line - check that control points are between begin and end}Result:=False;ifnotControlBetweenBeginEnd(Points.BeginPoint.Y,Points.BeginControl.Y,Points.EndControl.Y,Points.EndPoint.Y)thenexit;Result:=True;ifIsZero(dy)thenexit;if(Abs(Points.BeginControl.x-Points.BeginPoint.x-(dx/dy)*(Points.BeginControl.y-Points.BeginPoint.y))>BezierPixel)or(Abs(Points.EndControl.x-Points.BeginPoint.x-(dx/dy)*(Points.EndControl.y-Points.BeginPoint.y))>BezierPixel)thenbeginResult:=False;exit;endelsebeginResult:=True;exit;end;end;end;procedureBezierRecursion(varPoints:TBezierPoints;varPtsOut:T2DPolygon;varAlloc,OutCount:Integer;level:Integer);{Recursively subdivide the space between the two Bezier end-points}varPoints2:TBezierPoints;{ for the second recursive call}begin{Out of memory?}ifOutCount=Allocthenbegin{then double hte memory allocation}Alloc:=Alloc*2;SetLength(PtsOut,Alloc);end;if(level=0)orRecursionDone(Points)then{ Recursion can be terminated}beginifOutCount=0thenbeginPtsOut[0]:=Points.BeginPoint;OutCount:=1;end;PtsOut[OutCount]:=Points.EndPoint;Inc(OutCount);endelsebegin{Split Points into two halves}Points2.EndPoint:=Points.EndPoint;Points2.EndControl:=VectorMidPoint(Points.EndControl,Points.EndPoint);Points2.BeginPoint:=VectorMidPoint(Points.BeginControl,Points.EndControl);Points2.BeginControl:=VectorMidPoint(Points2.BeginPoint,Points2.EndControl);Points.BeginControl:=VectorMidPoint(Points.BeginPoint,Points.BeginControl);Points.EndControl:=VectorMidPoint(Points.BeginControl,Points2.BeginPoint);Points.EndPoint:=VectorMidPoint(Points.EndControl,Points2.BeginControl);Points2.BeginPoint:=Points.EndPoint;{ Do recursion on the two halves}BezierRecursion(Points,PtsOut,Alloc,OutCount,level-1);BezierRecursion(Points2,PtsOut,Alloc,OutCount,level-1);end;end;procedureDoQuadraticBezier(constSource:T2DPolygon;varDestination:T2DPolygon);{Generate Bezier spline from Source polygon and store result in Destination }{Source Format: P[0] = Start Point, P[1]= Control Point, P[2] = End Point }varB,Alloc,OutCount:Integer;varptBuf:TBezierPoints;beginif(Length(Source)-1)mod3<>0thenexit;OutCount:=0;{Start with allocation of 150 to save allocation overhead}Alloc:=150;SetLength(Destination,Alloc);forB:=0to(Length(Source)-1)div3-1dobeginMove(Source[B*3],ptBuf.BeginPoint,SizeOf(ptBuf));BezierRecursion(ptBuf,Destination,Alloc,OutCount,8);end;{Trim Destination to actual length}SetLength(Destination,OutCount);end;procedureGetCardinalSpline(constSource:T2DPolygon;varDestination:T2DPolygon;Tension:double=0.5);{Generate cardinal spline from Source with result in Destination}{Generate tangents to get the Cardinal Spline}vari:Integer;varpt:T2DPolygon;varP1,P2:T2DVector;begin{We need at least 2 points}ifLength(Source)<=1thenexit;{ The points and tangents require count * 3 - 2 points.}SetLength(pt,Length(Source)*3-2);tension:=tension*0.3;{Calculate Tangents for each point and store results in new array}{Do the first point}pt[0]:=Source[0];pt[1]:=GetEndPointTangent(Source[0],Source[1],tension);{Do intermediates points}fori:=0toLength(Source)-3dobeginGetInteriorTangent(T2DPolygon(@(Source[i])),tension,P1,P2);pt[3*i+2]:=P1;pt[3*i+3]:=Source[i+1];pt[3*i+4]:=P2;end;{Do last point}pt[Length(Pt)-1]:=Source[Length(Source)-1];pt[Length(Pt)-2]:=GetEndPointTangent(Source[Length(Source)-1],Source[Length(Source)-2],Tension);DoQuadraticBezier(pt,Destination);end;procedureDrawPolyline(Image:TImage;constPoints:T2DPolygon);{Draw specified polygon}varI:Integer;beginifLength(Points)<2thenexit;Image.Canvas.MoveTo(Trunc(points[0].X),Trunc(points[0].Y));forI:=1toLength(Points)-1dobeginImage.Canvas.LineTo(Trunc(points[I].X),Trunc(points[I].Y));end;end;procedureDrawCurve(Image:TImage;constPoints:T2DPolygon;Tension:double=0.5);{Draw control points and resulting spline curve }varPt2:T2DPolygon;beginifLength(Points)<=1thenexit;GetCardinalSpline(points,Pt2,tension);{Draw control points}Image.Canvas.Pen.Width:=2;Image.Canvas.Pen.Color:=clBlue;DrawPolyline(Image,Points);{Draw actual spline curve}Image.Canvas.Pen.Color:=clRed;DrawPolyline(Image,Pt2);end;procedureShowQuadBezierCurve(Image:TImage);varPoints:T2DPolygon;begin{Create a set of control points}SetLength(Points,5);Points[0].X:=50;Points[0].Y:=250;Points[1].X:=50;Points[1].Y:=50;Points[2].X:=250;Points[2].Y:=50;Points[3].X:=350;Points[3].Y:=150;Points[4].X:=400;Points[4].Y:=100;DrawCurve(Image,Points);Image.Invalidate;end;
Elapsed Time: 0.647 ms.
sysconf topleftproc quadraticbezier x1 y1 x2 y2 x3 y3 nseg . for i = 0 to nseg t = i / nseg t1 = 1 - t a = t1 * t1 b = 2 * t * t1 c = t * t px = x py = y x = a * x1 + b * x2 + c * x3 + 0.5 y = a * y1 + b * y2 + c * y3 + 0.5 if i > 0 : gline px py x y ..glinewidth 0.5gclearquadraticbezier 1 1 30 37 59 1 100
Some code is shared with the cubic bezier task, but I put it here again to make it simple (hoping the two version don't diverge)Same remark as with cubic bezier, the points could go into a sequence to simplify stack shuffling
USING:arrayskernellocalsmathmath.functionsrosettacode.raster.storagesequences;IN:rosettacode.raster.line! This gives a function::(quadratic-bezier)(P0P1P2--bezier)[:>x1x-sqP0n*v2 1x-x**P1n*vxsqP2n*vv+v+];inline! Same code from the cubic bezier task:t-interval(x--interval)[iota]keep1-[/]currymap;:points-to-lines(seq--seq)duprest[2array]2map;:draw-lines({R,G,B}pointsimage--)[[first2]dipdraw-line]currywitheach;::bezier-lines({R,G,B}P0P1P2image--)100t-intervalP0P1P2(quadratic-bezier)mappoints-to-lines{R,G,B}swapimagedraw-lines;
Windows' graphics origin is located at the bottom-left corner of device bitmap.
Translation of BBC BASIC using pure FBSL's built-in graphics functions:
#DEFINEWM_LBUTTONDOWN513#DEFINEWM_CLOSE16FBSLSETTEXT(ME,"Bezier Quadratic")FBSLSETFORMCOLOR(ME,RGB(0,255,255))' Cyan: persistent background colorDRAWWIDTH(5)' Adjust point sizeFBSL.GETDC(ME)' Use volatile FBSL.GETDC below to avoid extra assignmentsRESIZE(ME,0,0,235,235)CENTER(ME)SHOW(ME)DIMHeightASINTEGERFBSL.GETCLIENTRECT(ME,0,0,0,Height)BEGINEVENTSSELECT CASECBMSGCASEWM_LBUTTONDOWN:BezierQuad(10,100,250,270,150,20,20)' DrawCASEWM_CLOSE:FBSL.RELEASEDC(ME,FBSL.GETDC)' Clean upENDSELECTENDEVENTSSUBBezierQuad(x1,y1,x2,y2,x3,y3,n)TYPEPOINTAPIxASINTEGERyASINTEGERENDTYPEDIMt,t1,a,b,c,p[n]ASPOINTAPIFORDIMi=0TOnt=i/n:t1=1-ta=t1^2b=2*t*t1c=t^2p[i].x=a*x1+b*x2+c*x3+0.5p[i].y=Height-(a*y1+b*y2+c*y3+0.5)NEXTFORi=0TOn-1Bresenham(p[i].x,p[i].y,p[i+1].x,p[i+1].y)NEXTSUBBresenham(x0,y0,x1,y1)DIMdx=ABS(x0-x1),sx=SGN(x0-x1)DIMdy=ABS(y0-y1),sy=SGN(y0-y1)DIMtmp,er=IIF(dx>dy,dx,-dy)/2WHILENOT(x0=x1ANDALSOy0=y1)PSET(FBSL.GETDC,x0,y0,&HFF)' Red: Windows stores colors in BGR ordertmp=erIFtmp>-dxTHEN:er=er-dy:x0=x0+sx:ENDIFIFtmp<+dyTHEN:er=er+dx:y0=y0+sy:ENDIFWENDENDSUBENDSUB
(This subroutine must be inside theRCImagePrimitive
module, seehere)
subroutinequad_bezier(img,p1,p2,p3,color)type(rgbimage),intent(inout)::imgtype(point),intent(in)::p1,p2,p3type(rgb),intent(in)::colorinteger::i,jreal::pts(0:N_SEG,0:1),t,a,b,c,x,ydoi=0,N_SEGt=real(i)/real(N_SEG)a=(1.0-t)**2.0b=2.0*t*(1.0-t)c=t**2.0x=a*p1%x+b*p2%x+c*p3%xy=a*p1%y+b*p2%y+c*p3%ypts(i,0)=xpts(i,1)=yend do doi=0,N_SEG-1j=i+1calldraw_line(img,point(pts(i,0),pts(i,1)),&point(pts(j,0),pts(j,1)),color)end doend subroutinequad_bezier
' version 01-11-2016' compile with: fbc -s console' translation from Bitmap/Bresenham's line algorithm C entrySubBr_line(x0AsInteger,y0AsInteger,x1AsInteger,y1AsInteger,_ColAsUInteger=&HFFFFFF)DimAsIntegerdx=Abs(x1-x0),dy=Abs(y1-y0)DimAsIntegersx=IIf(x0<x1,1,-1)DimAsIntegersy=IIf(y0<y1,1,-1)DimAsIntegerer=IIf(dx>dy,dx,-dy)\2,e2DoPSet(x0,y0),colIf(x0=x1)And(y0=y1)ThenExitDoe2=erIfe2>-dxThenEr-=dy:x0+=sxIfe2<dyThenEr+=dx:y0+=syLoopEndSub' Bitmap/Bézier curves/Quadratic BBC BASIC entrySubbezierquad(x1AsDouble,y1AsDouble,x2AsDouble,y2AsDouble,_x3AsDouble,y3AsDouble,nAsULong,colAsUInteger=&HFFFFFF)Typepoint_xAsIntegeryAsIntegerEndTypeDimAsULongiDimAsDoublet,t1,a,b,c,dDimAspoint_p(n)Fori=0Tont=i/nt1=1-ta=t1^2b=t*t1*2c=t^2p(i).x=Int(a*x1+b*x2+c*x3+.5)p(i).y=Int(a*y1+b*y2+c*y3+.5)NextFori=0Ton-1Br_line(p(i).x,p(i).y,p(i+1).x,p(i+1).y,col)NextEndSub' ------=< MAIN >=------ScreenRes250,250,32' 0,0 in top left cornerbezierquad(10,100,250,270,150,20,20)' empty keyboard bufferWhileInKey<>"":WendPrint:Print"hit any key to end program"SleepEnd
FB has a convenience quadratic Bézier curve function that accepts a start point, end point, left control point, right control point, path stroke width and path color as demonstrated below. Here's a link to an illustration that's helpful in understanding the inputs:Bézier curve function paramters.
_window = 1void local fn BuildWindow window _window, @"Quadratic Bezier Curve", ( 0, 0, 300, 300 ), NSWindowStyleMaskTitled + NSWindowStyleMaskClosable + NSWindowStyleMaskMiniaturizable WindowCenter(1) WindowSubclassContentView( _window ) ViewSetFlipped( _windowContentViewTag, YES ) ViewSetNeedsDisplay( _windowContentViewTag )end fnvoid local fn DrawInView( tag as long ) BezierPathStrokeCurve( fn CGPointMake( 20, 20 ), fn CGPointMake( 280, 20 ), fn CGPointMake( 60, 340 ), fn CGPointMake( 240, 340 ), 4.0, fn ColorRed )end fnvoid local fn DoDialog( ev as long, tag as long ) select ( ev ) case _viewDrawRect : fn DrawInView( tag ) case _windowWillClose : end end selectend fnon dialog fn DoDialogfn BuildWindowHandleEvents
packagerasterconstb2Seg=20func(b*Bitmap)Bézier2(x1,y1,x2,y2,x3,y3int,pPixel){varpx,py[b2Seg+1]intfx1,fy1:=float64(x1),float64(y1)fx2,fy2:=float64(x2),float64(y2)fx3,fy3:=float64(x3),float64(y3)fori:=rangepx{c:=float64(i)/b2Sega:=1-ca,b,c:=a*a,2*c*a,c*cpx[i]=int(a*fx1+b*fx2+c*fx3)py[i]=int(a*fy1+b*fy2+c*fy3)}x0,y0:=px[0],py[0]fori:=1;i<=b2Seg;i++{x1,y1:=px[i],py[i]b.Line(x0,y0,x1,y1,p)x0,y0=x1,y1}}func(b*Bitmap)Bézier2Rgb(x1,y1,x2,y2,x3,y3int,cRgb){b.Bézier2(x1,y1,x2,y2,x3,y3,c.Pixel())}
Demonstration program:
packagemainimport("fmt""raster")funcmain(){b:=raster.NewBitmap(400,300)b.FillRgb(0xdfffef)b.Bézier2Rgb(20,150,500,-100,300,280,raster.Rgb(0x3f8fef))iferr:=b.WritePpmFile("bez2.ppm");err!=nil{fmt.Println(err)}}
{-# LANGUAGE FlexibleInstances, TypeSynonymInstances, ViewPatterns #-}importBitmapimportBitmap.LineimportControl.MonadimportControl.Monad.STtypePoint=(Double,Double)fromPixel(Pixel(x,y))=(toEnumx,toEnumy)toPixel(x,y)=Pixel(roundx,roundy)pmap::(Double->Double)->Point->Pointpmapf(x,y)=(fx,fy)onCoordinates::(Double->Double->Double)->Point->Point->PointonCoordinatesf(xa,ya)(xb,yb)=(fxaxb,fyayb)instanceNumPointwhere(+)=onCoordinates(+)(-)=onCoordinates(-)(*)=onCoordinates(*)negate=pmapnegateabs=pmapabssignum=pmapsignumfromIntegeri=(i',i')wherei'=fromIntegeribézier::Colorc=>Imagesc->Pixel->Pixel->Pixel->c->Int->STs()bézieri(fromPixel->p1)(fromPixel->p2)(fromPixel->p3)csamples=zipWithM_fts(tailts)wherets=map(/top)[0..top]wheretop=toEnum$samples-1curvePointt=pt(t'^^2)p1+pt(2*t*t')p2+pt(t^^2)p3wheret'=1-tptnp=pmap(*n)pf(curvePoint->p1)(curvePoint->p2)=linei(toPixelp1)(toPixelp2)c
SeeCubic bezier curves for a generalized solution.==J ==
Using the BasicBitmapStorage class from theBitmap task to produce a runnable program.
importjava.awt.Color;importjava.awt.Graphics;importjava.awt.Image;importjava.awt.Point;importjava.awt.image.BufferedImage;importjava.awt.image.RenderedImage;importjava.io.File;importjava.io.IOException;importjava.util.ArrayList;importjava.util.List;importjavax.imageio.ImageIO;publicfinalclassBezierQuadratic{publicstaticvoidmain(String[]args)throwsIOException{finalintwidth=320;finalintheight=320;BasicBitmapStoragebitmap=newBasicBitmapStorage(width,height);bitmap.fill(Color.YELLOW);Pointpoint1=newPoint(10,100);Pointpoint2=newPoint(250,270);Pointpoint3=newPoint(150,20);bitmap.quadraticBezier(point1,point2,point3,Color.BLACK,20);FilebezierFile=newFile("QuadraticBezierJava.jpg");ImageIO.write((RenderedImage)bitmap.getImage(),"jpg",bezierFile);}}finalclassBasicBitmapStorage{publicBasicBitmapStorage(intwidth,intheight){image=newBufferedImage(width,height,BufferedImage.TYPE_INT_RGB);}publicvoidfill(Colorcolor){Graphicsgraphics=image.getGraphics();graphics.setColor(color);graphics.fillRect(0,0,image.getWidth(),image.getHeight());}publicColorgetPixel(intx,inty){returnnewColor(image.getRGB(x,y));}publicvoidsetPixel(intx,inty,Colorcolor){image.setRGB(x,y,color.getRGB());}publicImagegetImage(){returnimage;}publicvoidquadraticBezier(Pointpoint1,Pointpoint2,Pointpoint3,Colorcolor,intintermediatePointCount){List<Point>points=newArrayList<Point>();for(inti=0;i<=intermediatePointCount;i++){finaldoublet=(double)i/intermediatePointCount;finaldoubleu=1.0-t;finaldoublea=u*u;finaldoubleb=2.0*t*u;finaldoublec=t*t;finalintx=(int)(a*point1.x+b*point2.x+c*point3.x);finalinty=(int)(a*point1.y+b*point2.y+c*point3.y);points.add(newPoint(x,y));setPixel(x,y,color);}for(inti=0;i<intermediatePointCount;i++){drawLine(points.get(i).x,points.get(i).y,points.get(i+1).x,points.get(i+1).y,color);}}publicvoiddrawLine(intx0,inty0,intx1,inty1,Colorcolor){finalintdx=Math.abs(x1-x0);finalintdy=Math.abs(y1-y0);finalintxIncrement=x0<x1?1:-1;finalintyIncrement=y0<y1?1:-1;interror=(dx>dy?dx:-dy)/2;while(x0!=x1||y0!=y1){setPixel(x0,y0,color);interror2=error;if(error2>-dx){error-=dy;x0+=xIncrement;}if(error2<dy){error+=dx;y0+=yIncrement;}}setPixel(x0,y0,color);}privateBufferedImageimage;}
SeeCubic bezier curves#Julia for a generalized solution.
This incorporates code from other relevant tasks in order to provide a runnable example.
// Version 1.2.40importjava.awt.Colorimportjava.awt.Graphicsimportjava.awt.image.BufferedImageimportkotlin.math.absimportjava.io.Fileimportjavax.imageio.ImageIOclassPoint(varx:Int,vary:Int)classBasicBitmapStorage(width:Int,height:Int){valimage=BufferedImage(width,height,BufferedImage.TYPE_3BYTE_BGR)funfill(c:Color){valg=image.graphicsg.color=cg.fillRect(0,0,image.width,image.height)}funsetPixel(x:Int,y:Int,c:Color)=image.setRGB(x,y,c.getRGB())fungetPixel(x:Int,y:Int)=Color(image.getRGB(x,y))fundrawLine(x0:Int,y0:Int,x1:Int,y1:Int,c:Color){valdx=abs(x1-x0)valdy=abs(y1-y0)valsx=if(x0<x1)1else-1valsy=if(y0<y1)1else-1varxx=x0varyy=y0vare1=(if(dx>dy)dxelse-dy)/2vare2:Intwhile(true){setPixel(xx,yy,c)if(xx==x1&&yy==y1)breake2=e1if(e2>-dx){e1-=dy;xx+=sx}if(e2<dy){e1+=dx;yy+=sy}}}funquadraticBezier(p1:Point,p2:Point,p3:Point,clr:Color,n:Int){valpts=List(n+1){Point(0,0)}for(iin0..n){valt=i.toDouble()/nvalu=1.0-tvala=u*uvalb=2.0*t*uvalc=t*tpts[i].x=(a*p1.x+b*p2.x+c*p3.x).toInt()pts[i].y=(a*p1.y+b*p2.y+c*p3.y).toInt()setPixel(pts[i].x,pts[i].y,clr)}for(iin0untiln){valj=i+1drawLine(pts[i].x,pts[i].y,pts[j].x,pts[j].y,clr)}}}funmain(args:Array<String>){valwidth=320valheight=320valbbs=BasicBitmapStorage(width,height)with(bbs){fill(Color.cyan)valp1=Point(10,100)valp2=Point(250,270)valp3=Point(150,20)quadraticBezier(p1,p2,p3,Color.black,20)valqbFile=File("quadratic_bezier.jpg")ImageIO.write(image,"jpg",qbFile)}}
Starting with the code fromBitmap/Bresenham's line algorithm, then extending:
Bitmap.quadraticbezier=function(self,x1,y1,x2,y2,x3,y3,nseg)nseg=nsegor10localprevx,prevy,currx,curryfori=0,nsegdolocalt=i/nseglocala,b,c=(1-t)^2,2*t*(1-t),t^2prevx,prevy=currx,currycurrx=math.floor(a*x1+b*x2+c*x3+0.5)curry=math.floor(a*y1+b*y2+c*y3+0.5)ifi>0thenself:line(prevx,prevy,currx,curry)endendendlocalbitmap=Bitmap(61,21)bitmap:clear()bitmap:quadraticbezier(1,1,30,37,59,1)bitmap:render({[0x000000]='.',[0xFFFFFFFF]='X'})
..............................................................X.........................................................X...X.......................................................X.....X.....................................................X.......X...................................................X.........X.................................................X...........X...............................................X.............X.............................................X...............X...........................................X.................X.........................................X...................X.......................................X.....................X.....................................X.......................X...................................X.........................X................................XX...........................X.............................XX..............................XX..........................X..................................XX.....................XXX.....................................XXX...............XXX...........................................XXXXX......XXXX...................................................XXXXXX.........................................................................................
modulebezier{FunctionBitmap{defxaslong,yaslong,ImportasbooleanIfmatch("NN")thenReadx,yelse.ifMatch("N")Then\\isafile?Readfaslongbytewhitespace[0]ifnotEof(f)thenget#f,whitespace:P6$=chr$(whitespace[0])get#f,whitespace:P6$+=chr$(whitespace[0])booleangetW=true,getH=true,getV=truelongvIfp6$="P6"Thendoget#f,whitespaceselectcasewhitespace[0]case35{doget#f,whitespaceuntilwhitespace[0]=10}case32,9,13,10{ifgetWandx<>0thengetW=falseelse.ifgetHandy<>0thengetH=falseelse.ifgetVandv<>0thengetV=falseendif}case48to57{ifgetWthenx*=10x+=whitespace[0]-48else.ifgetHtheny*=10y+=whitespace[0]-48else.ifgetVthenv*=10v+=whitespace[0]-48endif}EndSelectiFeof(f)thenError"Not a ppm file"untilgetV=falseelseError"Not a P6 ppm"endifImport=TrueendifelseError"No proper arguments"endififx<1ory<1thenError"Wrong dimensions"structurergb{redasbytegreenasbyteblueasbyte}m=len(rgb)*xmod4ifm>0thenm=4-m' add some bytes to raster linem+=len(rgb)*xStructurerasterline{{padasbyte*m}hlineasrgb*x}StructureRaster{magicasinteger*4wasinteger*4hasinteger*4{linesBasbyte*len(rasterline)*y}linesasrasterline*y}BufferClearImage1asRasterReturnImage1,0!magic:="cDIB",0!w:=Hex$(x,2),0!h:=Hex$(y,2)ifnotImportthenReturnImage1,0!lines:=String$(chrcode$(0xffff),Len(rasterline)*ydiv2)BufferClearPadasByte*4SetPixel=LambdaImage1,Pad,aLines=Len(Raster)-Len(Rasterline),blines=-Len(Rasterline)(x,y,c)->{where=alines+3*x+blines*yifc>0thenc=color(c)c-!ReturnPad,0:=caslongReturnImage1,0!where:=Eval(Pad,2)asbyte,0!where+1:=Eval(Pad,1)asbyte,0!where+2:=Eval(Pad,0)asbyte}GetPixel=LambdaImage1,aLines=Len(Raster)-Len(Rasterline),blines=-Len(Rasterline)(x,y)->{where=alines+3*x+blines*y=color(Eval(image1,where+2asbyte),Eval(image1,where+1asbyte),Eval(image1,whereasbyte))}StrDib$=Lambda$Image1,Raster->{=Eval$(Image1,0,Len(Raster))}CopyImage=LambdaImage1(image$)->{ifleft$(image$,12)=Eval$(Image1,0,24)Then{ReturnImage1,0:=Image$}ElseError"Can't Copy Image"}Export2File=LambdaImage1,x,y(f)->{Print#f,"P6";chr$(10);"# Created using M2000 Interpreter";chr$(10);Print#f,x;" ";y;" 255";chr$(10);x2=x-1:where=0x0=x*3structurergbP6{rasbytegasbytebasbyte}bufferPadasrgbP6*x*yFory1=y-1to0{Returnpad,x*y1:=eval$(image1,0!linesB!where,x0)where+=x0m=wheremod4:ifm<>0thenwhere+=4-m}Forx1=0tox*y-1{PushEval(pad,x1!b):Returnpad,x1!b:=Eval(pad,x1!r),x1!r:=Number}Put#f,pad}ifImportthen{x0=x-1:where=0structurergbP6{rasbyte,gasbyte,basbyte}bufferPad1asrgbP6*x*yGet#f,Pad1Forx1=0tox*y-1{PushEval(pad1,x1!b):Returnpad1,x1!b:=Eval(pad1,x1!r),x1!r:=Number}x1=x*3Fory1=y-1to0{ReturnImage1,0!linesB!where:=Eval$(Pad1,y1*x,x1)where+=3*(x0+1)m=wheremod4:ifm<>0thenwhere+=4-m}}GroupBitmap{type:BitmapSetPixel=SetPixelGetPixel=GetPixelImage$=StrDib$Copy=CopyImageToFile=Export2File}=Bitmap}modulebezier(&ppmasBitmap,x1,y1,x2,y2,x3,y3,n,col=0){Grouppoint_{longx,y}LongiDoublet,t1,a,b,c,dDimp(n+1)=point_Fori=0Tont=i/nt1=1-ta=t1^2b=t*t1*2c=t^2p(i).x=Int(a*x1+b*x2+c*x3+.5)p(i).y=Int(a*y1+b*y2+c*y3+.5)NextFori=0Ton-1Br_line(p(i).x,p(i).y,p(i+1).x,p(i+1).y,col)NextsubBr_line(x0AsLong,y0AsLong,x1AsLong,y1AsLong,Col=0)LocalLongdx=Abs(x1-x0),dy=Abs(y1-y0)LocalLongsx=If(x0<x1->1,-1)LocalLongsy=If(y0<y1->1,-1)LocalLonger=If(dx>dy->dx,-dy)div2,e2DoCallppm.SetPixel(x0,y0,Col)Ifx0=x1Andy0=y1ThenExite2=erIfe2>-dxThenEr-=dy:x0+=sxIfe2<dyThenEr+=dx:y0+=syAlwaysendsub}A=Bitmap(250,250)bezier&A,10,100,220,310,150,20,20move3000,3000:imageA.Image$()Open"curve.ppm"foroutputas#fCallA.tofile(f)close#f}bezier
pts={{0,0},{1,-1},{2,1}};Graphics[{BSplineCurve[pts],Green,Line[pts],Red,Point[pts]}]
Second solution using built-in function BezierCurve.
pts={{0,0},{1,-1},{2,1}};Graphics[{BezierCurve[pts],Green,Line[pts],Red,Point[pts]}]
Note: Store this function in a file named "bezierQuad.mat" in the @Bitmap folder for the Bitmap class definedhere.
functionbezierQuad(obj,pixel_0,pixel_1,pixel_2,color,varargin)if(isempty(varargin))resolution=20;elseresolution=varargin{1};end%Calculate time axistime=(0:1/resolution:1)';timeMinus=1-time;%The formula for the curve is expanded for clarity, the lack of%loops is because its calculation has been vectorizedcurve=(timeMinus.^2)*pixel_0;%First term of polynomialcurve=curve+(2.*time.*timeMinus)*pixel_1;%second term of polynomialcurve=curve+(time.^2)*pixel_2;%third term of polynomialcurve=round(curve);%round each of the points to the nearest integer%connect each of the points in the curve with a line using the%Bresenham Line algorithmfori=(1:length(curve)-1)obj.bresenhamLine(curve(i,:),curve(i+1,:),color);endassignin('caller',inputname(1),obj);%saves the changes to the objectend
Sample usage:This will generate the image example for the Go solution.
>>img=Bitmap(400,300);>>img.fill([223255239]);>>img.bezierQuad([20150],[500-100],[300280],[63143239],21);>>disp(img)
This GUI implementation is for use withMini Micro.
Point={"x":0,"y":0}Point.init=function(x,y)p=newPointp.x=x;p.y=yreturnpendfunctiondrawLine=function(img,x0,y0,x1,y1,colr)sign=function(a,b)ifa<bthenreturn1return-1endfunctiondx=abs(x1-x0)sx=sign(x0,x1)dy=abs(y1-y0)sy=sign(y0,y1)ifdx>dythenerr=dxelseerr=-dyendiferr=floor(err/2)whiletrueimg.setPixelx0,y0,colrifx0==x1andy0==y1thenbreake2=errife2>-dxthenerr-=dyx0+=sxendifife2<dythenerr+=dxy0+=syendifendwhileendfunctionquadraticBezier=function(img,p1,p2,p3,numPoints,colr)points=[]foriinrange(0,numPoints)t=i/numPointsu=1-ta=u*ub=2*t*uc=t*tx=floor(a*p1.x+b*p2.x+c*p3.x)y=floor(a*p1.y+b*p2.y+c*p3.y)points.push(Point.init(x,y))img.setPixelx,y,colrendforforiinrange(1,numPoints)drawLineimg,points[i-1].x,points[i-1].y,points[i].x,points[i].y,colrendforendfunctionbezier=Image.create(480,480)p1=Point.init(50,100)p2=Point.init(200,400)p3=Point.init(360,55)quadraticBezierbezier,p1,p2,p3,20,color.redgfx.cleargfx.drawImagebezier,0,0
We use module “bitmap” for bitmap management and module “bresenham” to draw segments.
importbitmapimportbresenhamimportlenientopsprocdrawQuadraticBezier*(image:Image;pt1,pt2,pt3:Point;color:Color;nseg:Positive=20)=varpoints=newSeq[Point](nseg+1)foriin0..nseg:lett=i/nsegleta=(1-t)*(1-t)letb=2*t*(1-t)letc=t*tpoints[i]=(x:(a*pt1.x+b*pt2.x+c*pt3.x).toInt,y:(a*pt1.y+b*pt2.y+c*pt3.y).toInt)foriin1..points.high:image.drawLine(points[i-1],points[i],color)#———————————————————————————————————————————————————————————————————————————————————————————————————whenisMainModule:varimg=newImage(16,12)img.fill(White)img.drawQuadraticBezier((1,7),(7,12),(14,1),Black)img.print
..............................H..............H...............H..............H..............H..............HH.....HH......H........HH..HHH...........HH..........................................
letquad_bezier~img~color~p1:(_x1,_y1)~p2:(_x2,_y2)~p3:(_x3,_y3)=let(x1,y1,x2,y2,x3,y3)=(float_x1,float_y1,float_x2,float_y2,float_x3,float_y3)inletbzt=leta=(1.0-.t)**2.0andb=2.0*.t*.(1.0-.t)andc=t**2.0inletx=a*.x1+.b*.x2+.c*.x3andy=a*.y1+.b*.y2+.c*.y3in(int_of_floatx,int_of_floaty)inletrecloop_tacc=if_t>20thenaccelsebeginlett=(float_t)/.20.0inletx,y=bztinloop(succ_t)((x,y)::acc)endinletpts=loop0[]in(* (* draw only points *) List.iter (fun (x, y) -> put_pixel img color x y) pts; *)(* draw segments *)letline=draw_line~img~colorinletby_pairlif=ignore(List.fold_left(funprevx->fprevx;x)(List.hdli)(List.tlli))inby_pairpts(funp0p1->line~p0~p1);;;
Output similar toMathematica
Requires new_image() fromBitmap, bresLine() fromBresenham's_line_algorithm, and write_ppm() fromWrite_a_PPM_file.
Results may be verified with demo\rosetta\viewppm.exw
-- demo\rosetta\Bitmap_BezierQuadratic.exwincludeppm.e-- black, green, red, white, new_image(), write_ppm(), bresLine() -- (covers above requirements)functionquadratic_bezier(sequenceimg,atomx1,y1,x2,y2,x3,y3,integercolour,segments)sequencepts=repeat(0,segments*2)fori=0tosegments*2-1by2doatomt=i/segments,t1=1-t,a=power(t1,2),b=2*t*t1,c=power(t,2)pts[i+1]=floor(a*x1+b*x2+c*x3)pts[i+2]=floor(a*y1+b*y2+c*y3)endforfori=1tosegments*2-2by2doimg=bresLine(img,pts[i],pts[i+1],pts[i+2],pts[i+3],colour)endforreturnimgendfunctionsequenceimg=new_image(200,200,black)img=quadratic_bezier(img,0,100,100,200,200,0,white,40)img=bresLine(img,0,100,100,200,green)img=bresLine(img,100,200,200,0,green)img[1][100]=redimg[100][200]=redimg[200][1]=redwrite_ppm("BezierQ.ppm",img)
This uses the 'brez' line drawing function fromBitmap/Bresenham's line algorithm#PicoLisp.
(scl 6)(de quadBezier (Img N X1 Y1 X2 Y2 X3 Y3) (let (R (* N N) X X1 Y Y1 DX 0 DY 0) (for I N (let (J (- N I) A (*/ 1.0 J J R) B (*/ 2.0 I J R) C (*/ 1.0 I I R)) (brez Img X Y (setq DX (- (+ (*/ A X1 1.0) (*/ B X2 1.0) (*/ C X3 1.0)) X)) (setq DY (- (+ (*/ A Y1 1.0) (*/ B Y2 1.0) (*/ C Y3 1.0)) Y)) ) (inc 'X DX) (inc 'Y DY) ) ) ) )
Test:
(let Img (make (do 200 (link (need 300 0)))) # Create image 300 x 200 (quadBezier Img 12 20 100 300 -80 260 180) (out "img.pbm" # Write to bitmap file (prinl "P1") (prinl 300 " " 200) (mapc prinl Img) ) )(call 'display "img.pbm")
Procedurequad_bezier(img,p1x,p1y,p2x,p2y,p3x,p3y,Color,n_seg)ProtectediProtected.fT,t1,a,b,c,dDimpts.POINT(n_seg)Fori=0Ton_segT=i/n_segt1=1.0-Ta=Pow(t1,2)b=2.0*T*t1c=Pow(T,2)pts(i)\x=a*p1x+b*p2x+c*p3xpts(i)\y=a*p1y+b*p2y+c*p3yNextStartDrawing(ImageOutput(img))FrontColor(Color)Fori=0Ton_seg-1BresenhamLine(pts(i)\x,pts(i)\y,pts(i+1)\x,pts(i+1)\y)NextStopDrawing()EndProcedureDefinew,h,imgw=200:h=200:img=1CreateImage(img,w,h);imgisinternalidoftheimageOpenWindow(0,0,0,w,h,"Bezier curve, quadratic",#PB_Window_SystemMenu)quad_bezier(1,80,20,130,80,20,150,RGB(255,255,255),20)ImageGadget(0,0,0,w,h,ImageID(1))DefineeventRepeatevent=WaitWindowEvent()Untilevent=#PB_Event_CloseWindow
SeeCubic bezier curves#Python for a generalized solution.
SeeCubic bezier curves#R for a generalized solution.
#langracket(requireracket/draw)(define(draw-linedcpq)(match*(pq)[((listxy)(listst))(senddcdraw-linexyst)]))(define(draw-linesdcps)(void(for/fold([p0(firstps)])([p(restps)])(draw-linedcp0p)p)))(define(inttpq)(define((int1t)x0x1)(+(*(-1t)x0)(*tx1)))(map(int1t)pq))(define(bezier-pointsp0p1p2)(for/list([t(in-range0.01.0(/1.020))])(intt(inttp0p1)(inttp1p2))))(definebm(make-objectbitmap%1717))(definedc(newbitmap-dc%[bitmapbm]))(senddcset-smoothing'unsmoothed)(senddcset-pen"red"1'solid)(draw-linesdc(bezier-points'(161)'(14)'(316)))bm
(formerly Perl 6)
Uses pieces from Bitmap, and Bresenham's line algorithm tasks. They are included here to make a complete, runnable program.
classPixel {hasUInt ($.R,$.G,$.B) }classBitmap {hasUInt ($.width,$.height);hasPixel@!data;methodfill(Pixel$p) {@!data =$p.clonexx ($!width*$!height) }methodpixel($iwhere ^$!width,$jwhere ^$!height -->Pixel )isrw {@!data[$i +$j *$!width] }methodset-pixel ($i,$j,Pixel$p) {returnif$j >=$!height;self.pixel($i,$j) =$p.clone; }methodget-pixel ($i,$j)returnsPixel {self.pixel($i,$j); }methodline(($x0iscopy,$y0iscopy), ($x1iscopy,$y1iscopy),$pix) {my$steep =abs($y1 -$y0) >abs($x1 -$x0);if$steep { ($x0,$y0) = ($y0,$x0); ($x1,$y1) = ($y1,$x1); }if$x0 >$x1 { ($x0,$x1) = ($x1,$x0); ($y0,$y1) = ($y1,$y0); }my$Δx =$x1 -$x0;my$Δy =abs($y1 -$y0);my$error =0;my$Δerror =$Δy /$Δx;my$y-step =$y0 <$y1 ??1 !! -1;my$y =$y0;for$x0 ..$x1 ->$x {if$steep {self.set-pixel($y,$x,$pix); }else {self.set-pixel($x,$y,$pix); }$error +=$Δerror;if$error >=0.5 {$y +=$y-step;$error -=1.0; } } }methoddot (($px,$py),$pix,$radius =2) {for$px -$radius ..$px +$radius ->$x {for$py -$radius ..$py +$radius ->$y {self.set-pixel($x,$y,$pix)if ($px -$x + ($py -$y) *i ).abs <=$radius; } } }methodquadratic ( ($x1,$y1), ($x2,$y2), ($x3,$y3),$pix,$segments =30 ) {my@line-segments =map ->$t {my \a = (1-$t)²;my \b =$t * (1-$t) *2;my \c =$t²; (a*$x1 +b*$x2 +c*$x3).round(1),(a*$y1 +b*$y2 +c*$y3).round(1) }, (0,1/$segments,2/$segments ...1);for@line-segments.rotor(2=>-1) -> ($p1,$p2) {self.line($p1,$p2,$pix) }; }methoddata {@!data }}rolePPM {methodP6returnsBlob {"P6\n{self.width} {self.height}\n255\n".encode('ascii')~Blob.new:flatmap { .R, .G, .B },self.data }}subcolor($r,$g,$b) {Pixel.new(R =>$r,G =>$g,B =>$b) }myBitmap$b =Bitmap.new(width =>600,height =>400)butPPM;$b.fill(color(2,2,2) );my@points = (65,25), (85,380), (570,15);my%seen;my$c =0;for@points.permutations ->@this {%seen{@this.reverse.join.Str}++;nextif%seen{@this.join.Str};$b.quadratic( |@this,color(255-$c,127,$c+=80) );}@points.map: {$b.dot($_,color(255,0,0),3 )}$*OUT.write:$b.P6;
Seeexample image here, (converted to a .png as .ppm format is not widely supported).
SeeCubic bezier curves#Ruby for a generalized solution.
SeeCubic bezier curves#Tcl for a generalized solution.
Define cubic(p1,p2,p3,segs) = Prgm Local i,t,u,prev,pt 0 → pt For i,1,segs+1 (i-1.0)/segs → t © Decimal to avoid slow exact arithetic (1-t) → u pt → prev u^2*p1 + 2*t*u*p2 + t^2*p3 → pt If i>1 Then PxlLine floor(prev[1,1]), floor(prev[1,2]), floor(pt[1,1]), floor(pt[1,2]) EndIf EndForEndPrgm
This implementation uses de Casteljau's algorithm to recursively split the Bezier curve into two smaller segments until the segment is short enough to be approximated with a straight line.The advantage of this method is that only integer calculations are needed, and the most complex operations are addition and shift right. (I have used multiplication and division here for clarity.)
Constant recursion depth is used here. Recursion depth of 5 seems to give accurate enough result in most situations. In real world implementations, some adaptive method is often used to decide when to stop recursion.
// Daw a Cubic bezier curve// #20, #30 = Start point// #21, #31 = Control point 1// #22, #32 = Control point 2// #23, #33 = end point// #40 = depth of recursion:CUBIC_BEZIER:if (#40 > 0) { #24 = (#20+#21)/2; #34 = (#30+#31)/2 #26 = (#22+#23)/2; #36 = (#32+#33)/2 #27 = (#20+#21*2+#22)/4; #37 = (#30+#31*2+#32)/4 #28 = (#21+#22*2+#23)/4; #38 = (#31+#32*2+#33)/4 #29 = (#20+#21*3+#22*3+#23)/8; #39 = (#30+#31*3+#32*3+#33)/8 Num_Push(20,40) #21 = #24; #31 = #34 // control 1 #22 = #27; #32 = #37 // control 2 #23 = #29; #33 = #39 // end point #40-- Call("CUBIC_BEZIER") // Draw "left" part Num_Pop(20,40) Num_Push(20,40) #20 = #29; #30 = #39 // start point #21 = #28; #31 = #38 // control 1 #22 = #26; #32 = #36 // control 2 #40-- Call("CUBIC_BEZIER") // Draw "right" part Num_Pop(20,40)} else { #1=#20; #2=#30; #3=#23; #4=#33 Call("DRAW_LINE")}return
Requires version 1.3.0 of DOME or later.
import"graphics"forCanvas,ImageData,Color,Pointimport"dome"forWindowclassGame{staticbmpCreate(name,w,h){ImageData.create(name,w,h)}staticbmpFill(name,col){varimage=ImageData[name]for(xin0...image.width){for(yin0...image.height)image.pset(x,y,col)}}staticbmpPset(name,x,y,col){ImageData[name].pset(x,y,col)}staticbmpPget(name,x,y){ImageData[name].pget(x,y)}staticbmpLine(name,x0,y0,x1,y1,col){vardx=(x1-x0).absvardy=(y1-y0).absvarsx=(x0<x1)?1:-1varsy=(y0<y1)?1:-1varerr=((dx>dy?dx:-dy)/2).floorwhile(true){bmpPset(name,x0,y0,col)if(x0==x1&&y0==y1)breakvare2=errif(e2>-dx){err=err-dyx0=x0+sx}if(e2<dy){err=err+dxy0=y0+sy}}}staticbmpQuadraticBezier(name,p1,p2,p3,col,n){varpts=List.filled(n+1,null)for(iin0..n){vart=i/nvaru=1-tvara=u*uvarb=2*t*uvarc=t*tvarpx=(a*p1.x+b*p2.x+c*p3.x).truncatevarpy=(a*p1.y+b*p2.y+c*p3.y).truncatepts[i]=Point.new(px,py,col)}for(iin0...n){varj=i+1bmpLine(name,pts[i].x,pts[i].y,pts[j].x,pts[j].y,col)}}staticinit(){Window.title="Quadratic Bézier curve"varsize=320Window.resize(size,size)Canvas.resize(size,size)varname="quadratic"varbmp=bmpCreate(name,size,size)bmpFill(name,Color.white)varp1=Point.new(10,100)varp2=Point.new(250,270)varp3=Point.new(150,20)bmpQuadraticBezier(name,p1,p2,p3,Color.darkpurple,20)bmp.draw(0,0)}staticupdate(){}staticdraw(alpha){}}
include c:\cxpl\codes; \intrinsic 'code' declarationsproc Bezier(P0, P1, P2); \Draw quadratic Bezier curvereal P0, P1, P2;def Segments = 8;int I;real T, A, B, C, X, Y;[Move(fix(P0(0)), fix(P0(1)));for I:= 1 to Segments do [T:= float(I)/float(Segments); A:= sq(1.-T); B:= 2.*T*(1.-T); C:= sq(T); X:= A*P0(0) + B*P1(0) + C*P2(0); Y:= A*P0(1) + B*P1(1) + C*P2(1); Line(fix(X), fix(Y), $00FFFF); \cyan line segments ];Point(fix(P0(0)), fix(P0(1)), $FF0000); \red control pointsPoint(fix(P1(0)), fix(P1(1)), $FF0000);Point(fix(P2(0)), fix(P2(1)), $FF0000);];[SetVid($112); \set 640x480x24 video graphicsBezier([0., 0.], [80., 100.], [160., 20.]);if ChIn(1) then []; \wait for keystrokeSetVid(3); \restore normal text display]
Uses the PPM class fromhttp://rosettacode.org/wiki/Bitmap/Bresenham%27s_line_algorithm#zkl
Add this to the PPM class:
fcn qBezier(p0x,p0y, p1x,p1y, p2x,p2y, rgb, numPts=500){ numPts.pump(Void,'wrap(t){ // B(t) t=t.toFloat()/numPts; t1:=(1.0 - t); a:=t1*t1; b:=t*t1*2; c:=t*t; x:=a*p0x + b*p1x + c*p2x + 0.5; y:=a*p0y + b*p1y + c*p2y + 0.5; __sSet(rgb,x,y); }); }
Doesn't use line segments, they don't seem like an improvement.
bitmap:=PPM(200,200,0xff|ff|ff);bitmap.qBezier(10,100, 250,270, 150,20, 0);bitmap.write(File("foo.ppm","wb"));