Larkin, Power BASIC cannot be THAT good:

.NET is hardly a universal, portable platform. If all you write is text-mode ANSI C, sure, it's fairly portable... as long as you keep your ints and longs and stuff under control.

As an engineer, I'm more interested in number crunching, simulation, graphics, generating embedded code images, stuff like that. There are a few nice collections of Basic subroutines around - curve fitting, FFTs, stuff like that - so I don't always write everything from scratch. And I do often reuse code.

I haven't used a linked list in decades. PCs are so fast these days you can waste enormous numbers of cycles on brute-force methods, like linear searching, to save programming time.

PowerBasic has a blinding fast SORT command, too. The built-in TCP/IP, graphics, string functions, all that stuff, are easy to use... and have excellent HELP a keystroke away. The help you get with a lot of C libraries is "read the source."

Here's a simulation of a vector character generator used in a retrofit for the C130 heads-up display, coded in PowerBasic. The actual product is a VME module that does most of the real work in an FPGA.

ftp://66.117.156.8/GR8.jpg

The imperfections simulate the effects of finite-bandwidth deflection amplifiers. Works great.

John

Reply to
John Larkin
Loading thread data ...

On a sunny day (Mon, 08 Jun 2009 02:59:15 +0100) it happened Nobody wrote in :

These sort of expressions are the things I love about learning English on Usenet. LOL I hope that expression is not copyrighted, I may want to use it some day.

Reply to
Jan Panteltje

John Larkin a écrit :

Well done! You've just got your ticket for a hiring interview at M$ ;-)

--
Thanks,
Fred.
Reply to
Fred Bartoli

range

But my linear searches are 50x as fast as whatever nonsense they are doing.

John

Reply to
John Larkin

How many lines of code is that, John?

I'm willing to bet that there are few other languages that could pull it off in as few lines of code. Even with something like Python, since graphics aren't native, you end up using one of the windowing toolkits such as wxGTK or wxPython, and "just making a stupid plot" tends to consume a lot more code than one might expect.

---Joel

Reply to
Joel Koltner

Aw, c'mon, if you think Python is slow, try Ruby! :-)

Lisp tends to make most people turn tail and run away screaming :-) ... Python is a lot "friendlier" as a first language, but I'd agree with you that, sure, Lisp is just as good as Python... at least for straight "algorithmic" programming.

This is kinda like Ubuntu Linux vs. all the other distributions... they're really all largely the same at the core, but "presentation" means a lot -- particularly to new users.

I'd like to see a high-level language similar to Python become a popular choice for embedded programming... these days it still tends to be either C or various proprietary flavors of BASIC. I suppose some of this is driven by how little RAM many microcontrollers have (e.g., many Atmel AVRs now have >64kB of flash ROM by

Reply to
Joel Koltner

Too bad it's throwaway code.

Reply to
AZ Nomad

464, including whitespace and comments. I comment a lot. It compiles to 44K, not that that matters any more.

I like PowerBasic because almost everything you need is internal to the language and throughly documented.

John

Reply to
John Larkin

The difference is that with other languages, you won't have to start over if you want to port to a new platform.

Reply to
AZ Nomad

464... impressive. I stand beside my comment that I think it's unlikely any "mainstream" language could do it in fewer lines! (Without resorting to "obfuscated" or "packed" code, of course.)
Reply to
Joel Koltner

The design is done, and it's flying on some AC130's, and we've been paid. Why would I want to port it to another platform?

If I did it in C, would the Windows version be directly portable to Linux... graphics and all?

The only sorta-platform independent language I know of that does graphics and such is Java. And it's slow. More importantly, it requires gui interface programming, a lot of hassle.

John

Reply to
John Larkin

You can (and people do) write it in C++ with a cross-platform GUI toolkit such as wxWidgets (free) or qt (not free). The high-level "scripting" languages such as Python and Perl are nominally cross-platform for this same reason. Some versions of Delphi (think, "Pascal on steroids") can also produce cross-platform output.

So, there are more options than Java, but for the program you did, where the likelihood you'll need to re-use the code or port it to another platform is rather slim, I think it's pretty hard to argue that PowerBasic *wasn't* a near-optimal strategy. Code re-use is a great concept in theory that's often nowhere near as beneficial in practice when you're paying people for their time.

---Joel

Reply to
Joel Koltner

It's not. I'm still running PB/Dos programs I wrote 15 years ago. If I ever need to run this HUD simulator in the next 15 years, I don't expect to have a lot of difficulty.

You dislike Basic on purely emotional grounds. I like it because it gets engineering done.

People use all sorts of stuff to do engineering... Excel, Matlab, Spice, Sonnet, Maple, Mathematica... even LabView. Jillions more. None are especially portable.

John

Reply to
John Larkin

' NEON.BAS V350 Heads-Up Display Simulator ' ' BY JOHN LARKIN ' HIGHLAND TECHNOLOGY, INC ' MAY 21, 2006

' THIS PROGRAM INPUTS A LIST OF X/Y/Z POINTS IN CSV FORM, AND ' PLOTS THE VECTOR CHARACTERS DEFINED THEREIN. ' ' SEE FILE NEON.TXT FOR GORY DETAILS ' ' NEON.BAS IS CODED IN POWERBASIC, PBCC V 4.01 ' ' THIS VERSION ALLOWS INPUT IN 'SCOPE' OR 'CHARSET' FORMATS ' AND INCLUDES FINE-GRAIN FILTERING AND RATE SHADING

' REV 2 IS FAT-PIXEL VERSION

#COMPILE EXE ' THEY MADE ME SAY THAT

' Function to check for a keystroke...

GLOBAL K$

FUNCTION KEYCHEK AS LONG K$ = UCASE$(INKEY$) END FUNCTION

' Function to wait for and get a keystroke...

FUNCTION GETKEY AS LONG K$ = UCASE$(WAITKEY$) END FUNCTION

FUNCTION PBMAIN

' USER DATA STORAGE:

DIM TD(50000) AS SINGLE ' TIME OF POINT DIM BD(50000) AS SINGLE ' BRIGHTUP DATA DIM XD(50000) AS SINGLE ' X DATA DIM YD(50000) AS SINGLE ' Y DATA

REV$ = "Neon rev 2"

CONSOLE SET LOC 40, 120 ' CONTROL PANEL UPPER-LEFT ON DESKTOP CONSOLE NAME REV$ CONSOLE SET SCREEN 32, 50 ' AND NOT VERY BIG

MOUSE ON ' ALLOW CLICKS IN THE CONSOLE WINDOW MOUSE 1 ' TO ABORT A PLOT

ZM! = 40 ' DEFAULT ZOOM FACTOR VF! = 0 ' V350 LOWPASS FACTOR = OFF HF! = 0 ' HUD LOWPASS FACTOR DITTO SK% = 0 ' SHOW BEAM-OFF PATH GM! = 0 ' GAMMA OFF, NO SHADING XO! = 0 ' NO X OFFSET YO! = 0 ' OR Y ' TOP: CONSOLE SET FOCUS ' SHOWTIME! COLOR 15,1 : CLS ' WHITE ON BLUE

IF ZM! < 1 THEN ZM! = 1 ' RATIONALIZE ZOOM IF ZM! > 1000 THEN ZM! = 1000

LOCATE 2,5 : COLOR 15, 3 : PRINT " Highland V350 HUD Display Simulation "; COLOR 15, 1

' SHOW MINI-MENU...

LOCATE 4,5 : PRINT "File " ;

IF F$ = "" THEN PRINT " - none - " ELSE PRINT F$; LOCATE 6, 14 : PRINT USING$("Data points ###,###", N&); LOCATE 7, 14 : PRINT USING$("Time span ###,### us", TSPAN!); LOCATE 8, 14 : PRINT USING$("Time/point ###.### us", DT!); END IF

LOCATE 10,5 PRINT USING$("Zoom #### \\\\ ##.### volts", ZM!, "+-", 10/ZM!);

LOCATE 12,5 : PRINT USING$("V350 filter ###.#", VF!); ' SHOW RAW FILTER FACTORS

IF VF! = 0 THEN ' FF=0 DISABLES FILTER PRINT " off "; ELSEIF DT! > 0 THEN ' DT=0 IS UNLIKELY BUT POSSIBLE PRINT USING$(" ####.## us", VF!*DT!); END IF

LOCATE 14,5 : PRINT USING$("HUD filter ###.#", HF!); ' REPEAT FOR CONJECTURED HUD ' AMPLIFIER RESPONSE TAU IF HF! = 0 THEN PRINT " off "; ELSEIF DT! > 0 THEN PRINT USING$(" ####.## us", HF!*DT!); END IF

LOCATE 16,5 : PRINT "Skipmode "; ' SKIPMODE DOESN'T PLOT IF SK% THEN PRINT " ON "; ELSE PRINT "off "; ' NON-BU POINTS

LOCATE 21,5 : PRINT USING$("Gamma ###.##", GM!) ' DISPLAY SEMI-USELESS BRIGHTNESS FACTOR

LOCATE 28,5 : PRINT "Plot Quit"

GETKEY ' ALLOW USER INPUT, AT LAST LOCATE 30,5 ' POSITION CURSOR FOR PROMPTS

SELECT CASE K$ CASE "Z" : GOTO KZOOM ' ZOOM CASE "Q" : GOTO PREND ' EXIT PROGRAM CASE "V" : GOTO VFILT ' SET V350 LOWPASS CASE "H" : GOTO HFILT ' SET HUD LOWPASS CASE "P" : GOTO GROUT ' PLOT CASE "F" : GOTO KFILE ' IMPORT DATA CASE "S" : GOTO SKIPIT ' TOGGLE BU SKIP MODE CASE "G" : GOTO GAMMA ' SET INTENSITY SCALER END SELECT

BEEP : GOTO TOP ' ' SET GAMMA, THE INTENSITY SCALER ' NUMBERS LIKE 6-8 SEEM TO DO SOMETHING

GAMMA: LINE INPUT "Gamma, us : "; Z$ IF Z$ "" THEN GM! = VAL(Z$) GOTO TOP

' SET THE ZOOM FACTOR

KZOOM: LINE INPUT "zoom 1..1000 : "; Z$ IF Z$ "" THEN ZM! = VAL(Z$) GOTO TOP

' SET OUR INTERNAL V350 LOWPASS FILTER TAU

VFILT: LINE INPUT "V350 filter factor : "; S$ IF S$ "" THEN VF! = VAL(S$) GOTO TOP

' SET THE HUD LOWPASS FILTER TAU

HFILT: LINE INPUT "HUD filter factor : "; S$ IF S$ "" THEN HF! = VAL(S$) GOTO TOP

' TOGGLE SKIP MODE, SO'S WE DON'T PLOT THE NON-BU POINTS

SKIPIT: SK% = SK% XOR 1 GOTO TOP

' ' OPEN A FILE AND SCOOP UP DATA ' ' 'SCOPE' DATA IS CSV AS TIME, BRIGHTUP, Y, X ' ' 'CHARSET' DATA IS CSV AS X, Y, BRIGHTUP ' ' WE ALSO ALLOW ZOOM 10 ' VFIL 10 ' HFIL 35 ' NOTE comment ' SKIP 1 ' XOFF -4 ' YOFF 1.3 ' GAMM 3

KFILE:

LINE INPUT "data file name : ", F$ ' DEFAULT .CSV IF INSTR(F$, ".") = 0 THEN F$ = F$ + ".csv"

IF DIR$(F$) = "" THEN ' CHECK FOR ACTUAL FILE! BEEP F$ = "" GOTO TOP END IF

N& = 0 ' BLAST POINT COUNT XO! = 0 ' AND OFFSETS YO! = 0

OPEN F$ FOR INPUT AS # 1

' OK, FETCH AND MASH LINES...

KLINE: IF ( EOF(1) OR N& > 49999 ) THEN GOTO KLENEX ' CHECK FOR END OF FILE

LINE INPUT #1, L$ ' NAB A LINE L$ = UCASE$(L$) ' AND CLEAN UP GENERALLY L$ = TRIM$(L$) '

C$ = LEFT$(L$,4) ' SNIP POSSIBLE 4-LETTER COMMAND J! = VAL(MID$(L$,5)) ' AND POSSIBLE NUMERIC ARG ' SELECT CASE C$ ' CHECK OUT THE COMMANDS...

CASE "NOTE" ' IGNORE COMMENTS CASE "TIME" ' IGNORE HEADER LINE CASE "ZOOM" : ZM! = J! ' SET ZOOM FACTOR CASE "XOFF" : XO! = J! ' SET X OFFSET CASE "YOFF" : YO! = J! ' SET Y OFFSET CASE "GAMM" : GM! = J! ' SET INTENSITY GAMMA CASE "VFIL" : VF! = J! ' V350 FILTER TAU CASE "HFIL" : HF! = J! ' HUD FILTER TAU CASE "SKIP" : SK% = J! AND 1 ' SET BU SKIP MODE 0 OR 1

CASE ELSE ' ANYTHING ELSE IS PROBABLY DATA

PC% = PARSECOUNT(L$,",") ' SEE HOW MANY FIELDS WE HAVE

IF PC% = 4 THEN ' 4 FIELDS IS TEK SCOPE DATA

INCR N& TD(N&) = VAL(PARSE$(L$, ",", 1)) ' EXTRACT TIME BD(N&) = VAL(PARSE$(L$, ",", 2)) ' EXTRACT BRIGHTUP VALUE YD(N&) = VAL(PARSE$(L$, ",", 3)) + YO! ' EXTRACT Y VALUE; OFFSET XD(N&) = VAL(PARSE$(L$, ",", 4)) + XO! ' EXTRACT X VALUE

END IF

IF PC% = 3 THEN ' 3 FIELDS IS 'CHARSET' DATA ' SPANNED TO +-32767 INCR N&

R! = 10/32768 ' RENORMALIZE CHARSET DATA TO +-10 VOLTS

TD(N&) = 1E-6 * N& ' FAKE 'TIME' AS INTEGER USEC BD(N&) = VAL(PARSE$(L$, ",", 3)) ' EXTRACT BRIGHTUP VALUE, 0 OR 1 YD(N&) = VAL(PARSE$(L$, ",", 2)) * R! + YO! ' EXTRACT Y VALUE XD(N&) = VAL(PARSE$(L$, ",", 1)) * R! + XO! ' EXTRACT X VALUE

END IF

END SELECT

GOTO KLINE

KLENEX: IF N& > 2 THEN ' CALC TOTAL TIME SPREAD TSPAN! = (TD(N&) - TD(1)) * 1E6 ' IN MICROSECONDS! DT! = TSPAN! / (N&-1) ' AND STEP SIZE ELSE TSPAN! = 1 ' BUT DO NOTHING SILLY DT! = 1 END IF

CLOSE # 1 GOTO TOP ' ' OPEN THE GRAPHICS WINDOW

GROUT: IF F$ = "" THEN BEEP : GOTO TOP ' SORRY, NO FILE!

LOCATE 28, 15 : COLOR 15,4 : PRINT " PLOTTING ";

' OPEN GRAPHICS WINDOW IF NOT ALREADY OPEN

IF HANDL& = 0 THEN GRAPHIC WINDOW REV$, 450, 80, 500, 600 TO HANDL& END IF

GRAPHIC ATTACH HANDL&, 0

' SWITCH TO WORLD COORDINATES

GRAPHIC SCALE (-11,16) - (11,-11) GRAPHIC COLOR %WHITE, RGB(40,40,40) ' BACKGROUND SORTA CHARCOAL GRAPHIC CLEAR

GRAPHIC COLOR RGB(0,100,100) ' DULL CYAN SORTA

' USE BOXES TO DEFINE THE TEXT AND HUD AREAS

GRAPHIC BOX (-10,10.5) - (10,15), 10 ' TEXT BOX GRAPHIC BOX (-10,-10) - (10,10), 5 ' HUD

' DRAW A FEW CURSOR LINES IN HUDSPACE

GRAPHIC LINE (-10,0) - (10,0) ' HORIZ GRAPHIC LINE (0,10) - (0,-10) ' VERT

' SHOW PLOT CONTEXT IN UPPER BOX

GRAPHIC COLOR %WHITE GRAPHIC SET POS (-9,14.7) GRAPHIC PRINT USING$("FILE : \\ \\ Points ##### \\ \\ \\ \\", F$, N&, DATE$, TIME$)

GRAPHIC SET POS (-9,12.7) GRAPHIC PRINT USING$("Timespan ###,### us DT ###.## us", TSPAN!, DT!);

GRAPHIC SET POS (-9,11.7) GRAPHIC PRINT USING$("Zoom ###.# Gamma ##.#", ZM!, GM!);

GRAPHIC SET POS (3,12.7) GRAPHIC PRINT USING$("V350 filter ###.#", VF!); ' SHOW RAW FILTER FACTORS

IF VF! = 0 THEN ' FF=1 DISABLES FILTER GRAPHIC PRINT " off "; ELSEIF DT! > 0 THEN ' AND DT=1 IS JUST SILLY GRAPHIC PRINT USING$(" ####.## us", VF!*DT!); END IF

GRAPHIC SET POS (3,11.7) GRAPHIC PRINT USING$("HUD filter ###.#", HF!); ' REPEAT FOR CONJECTURED HUD ' AMPLIFIER RESPONSE IF HF! = 0 THEN GRAPHIC PRINT " off "; ELSEIF DT! > 0 THEN GRAPHIC PRINT USING$(" ####.## us", HF!*DT!); END IF ' ' PLOT THE DATASET

RP% = 0 ' ZAP PROGRESS BAR REFERENCE

X1! = 0 : Y1! = 0 ' DISCHARGE BOTH XF! = 0 : YF! = 0 ' LOWPASS FILTERS

XR! = 0 : YR! = 0 ' ZAP GAMMA REFERENCE POINTS

FOR M& = 1 TO N&

' PLUCK RAW X,Y DATA FROM ARRAY

X! = XD(M&) * ZM! Y! = YD(M&) * ZM!

IF (VF! = 0 AND HF! = 0) THEN ' IF NEITHER FILTER IS ENABLED, XF! = X! ' FAKE FILTERED YF! = Y! ' DATA, GOSUB PIFFL ' PLOT THE POINT GOTO PROG ' AND BAIL END IF

' TO ALLOW FILTERING OF COARSE DATAPOINTS, WE MUST PLOT AT A ' SMALLER TIME INCREMENT THAN THE ACTUAL DATA. ' SO WE'LL PLOT 10 INTERMEDIATE POINTS, SLOWLY!

FOR IP% = 1 TO 10

' APPLY THE V350 LOWPASS FILTER

IF VF! > 0 THEN J! = 0.1/VF! ' FILTER X1! = X1! + (X!-X1!) * J! Y1! = Y1! + (Y!-Y1!) * J! ELSE X1! = X! ' OR DON'T Y1! = Y! END IF

' THEN APPLY THE HUD LOWPASS FILTER!

IF HF! > 0 THEN J! = 0.1/HF! XF! = XF! + (X1!-XF!) * J! YF! = YF! + (Y1!-YF!) * J! ELSE XF! = X1! YF! = Y1! END IF

GOSUB PIFFL ' PLOT A PIX!

NEXT IP%

' ' SHOW A PLOT PROGRESS BAR...

PROG:

P% = 100.0 * M& / N& ' PROGRESS, 0..100

IF P% RP% THEN GRAPHIC COLOR %CYAN GRAPHIC LINE (P%/5-10,-10.5) - ((P%+1)/5-10,-10.5) RP% = P% END IF

KEYCHEK ' KEY OR MOUSE CLICK BAILS IF K$ "" THEN EXIT FOR ' FROM PLOT LOOP

NEXT M&

GOTO TOP

'

' SUB TO PLOT A POINT IF IT'S IN OUR WINDOW ' ' XR! AND YR! ARE SAVED PREVIOUS POINT ' IF WE'RE IN GAMMA MODE, WE COMPUTE DISTANCE FROM ' THE LAST POINT AND SCALE BRIGHTNESS

' GAMMA IS THE VELOCITY IN MILLIVOLTS/MICROSECOND THAT CORRESPONDS ' TO 100% BRIGHTNESS, FULL WHITE. SSAI'S CHAR SET SEEMS TO LIKE ' 20-PIXEL BASIC STEPS, WHICH IS JUST ABOUT 3 MILLIVOLTS. IF WE SCALE, ' SAY, 1 mV/us TO FULL BRIGHT, AND ASSUME 1 US/POINT, GAMMA = 1

' WEIRD STUFF HAPPENS IF GAMMA MODE IS ON AND FILTERING IS OFF. ' DON'T DO THAT.

PIFFL:

IF ( (ABS(XF!) > 10) OR (ABS (YF!) > 10) ) THEN GOTO NOPE

IF BD!(M&) < 0.5 THEN ' IF BRIGHTUP IS OFF,

IF SK% THEN GOTO NOPE ' SKIP PLOT IF THAT'S IN VOGUE GRAPHIC COLOR RGB(0,100,0) ' OR PLOT BEAM-OFF PATH SORTA DIM RAD! = 0.05 ' GREEN AND SMALLISH

ELSEIF GM! = 0 THEN

GRAPHIC COLOR RGB(230,0,70) ' NO GAMMA, BRIGHTUP IS ON: USE RED RAD! = 0.14 ' AND FAT PIXEL

ELSE ' GAMMA, BRIGHTUP CASE:

W! = SQR( (XR!-XF!)^2 + (YR!-YF!)^2 ) ' COMPUTE VECTOR LENGTH, VOLTS W! = W! * 1000 ' NOW MILLIVOLTS IF W! = 0 THEN W! = 0.01 ' HANDLE SPECIAL CASE, NO MOTION XR! = XF! : YR! = YF! ' UPDATE REFERENCE POINTS FOR NEXT TIME

L! = 255 * GM! / W! ' COMPUTE BRIGHTNESS, SHORTER=BRIGHTER IF L! > 255 THEN L! = 255 ' OOPS, PHOSPHOR SATURATION!

GRAPHIC COLOR RGB(L!,L!,L!) ' XLATE TO GREYSCALE RAD! = 0.14 ' AND USE FAT PIXEL

END IF

' PLOT A FAT DOT...

GRAPHIC ELLIPSE (XF!-RAD!,YF!+RAD!)-(XF!+RAD!,YF!-RAD!),-1,-1

NOPE:

RETURN

' END OF PROGRAM!

PREND:

END FUNCTION

Reply to
John Larkin

On a sunny day (Mon, 08 Jun 2009 12:59:42 -0700) it happened John Larkin wrote in :

or

Well, it all depends. I dunno about the Power BASIC build in routines, but it seems to me in that example you are simply doing a xyplot.

I did the xyplot in C for xlib a hundred or so years ago (;-) like this, after porting it from a Linux system without X server, using vgalib, the 'vga' label is still there, and that was ported from YES CP/M code. The function of the array is just as a readback. The 's3' was ported from direct graphics I/O to a s3 graphics card. The whole 'xglgraphi.c' source in C is 209 lines, including comments and empty lines.

Anyways what I am saying is: It is very easy usually to plot a dot at x,y in some color in ANY system. xvtx-p, the program that uses the xyplot, displays videotext (Ceefax for the UK). What this does you can see here: ftp://panteltje.com/pub/xvtx-p.gif

I have marked the calls to xlib in the below code. There is some more overhead to allocate a display buffer, but the basic code to draw anything in X is very simple.

If you want to go fast with graphics in C in Linux, have a look at TinyPTC:

formatting link
works on MS windows, Mac, Linux, OSx, BEOS, DOS. I have only tried the Linux version, that prints the surface of mars in 3D from ESA files, I mean real 3D, with shutter glasses.
formatting link
Cannot promise it works for you, and you have to join ESA to get the data files... It does sequential left right eye, sometimes LR sync is lost, needs some work. Have not felt the urge to look into that, as I did not write that lib... I'd rather debug my own code :-) And I think they never intended it for 3D.

int s3getpixel(int x, int y) { int color; color = vga_memory[x + y * HSIZE]; return color; }

void s3plot(int x, int y, int color)/*plot 1 dot*/ { static int previouscolor; /* avoid 're appearing' at left and top */ if(x >= HSIZE)return; if(y >= VSIZE)return; if(color != previouscolor) { XSetForeground(mydisplay, xptestgc, color); //

Reply to
Jan Panteltje

MatPlotLib (matplotlib.sourceforge.net) seems to have become the standard plotting library for Python. NumPy and SciPy (scipy.org) are also useful tools.

But if you're cobbling together a program for a specific task and for personal use, the optimal language is usually whichever one you're most fluent in.

Reply to
Nobody

Reply to
Nobody

message=20

deflection

it off=20

graphics=20

wxGTK or=20

code=20

How about PostScript? Manual available here:

formatting link

Reply to
JosephKK

BASIC is

the

that

Eh, maybe. Procedural language is not necessarily a good fit for a state machine, nor for relay ladder logic. How good a fit is Haskell? Can you demonstrate?

*
Reply to
JosephKK

range

Yes. I expect someone just like Larkin is responsible for the glacially slow graphics and charting in XL2007 (and also for degrading the chart trend line polynomial fit to give the same wrong answer as LINEST).

Even if that were true then a decent Shell sort worst case O(N^1.5) algorithm would beat your poxy O(N^2) algorithm when N > 2500. In a real example with random unsorted data as input Shell's sort would be more like O(N^1.3).

And an O(Nlog2N) sort would beat it hollow at N > ~500 You really are clueless about algorithms and their relative speeds.

Linear search or sort by straight insertion is typically only faster for N

Reply to
Martin Brown

ElectronDepot website is not affiliated with any of the manufacturers or service providers discussed here. All logos and trade names are the property of their respective owners.