Building an MMBASIC Utility Library

(updated July 9, 2025)

I’m starting to play around with my PicoCalc, and as it’s been a pretty long time since I’ve done much of anything in MMBASIC, I thought I’d start by rebuilding my library of Subroutines and Functions. The first two are are a file selector and a fixed width input function:
(it’s formatted for readability)

'----------------------------
'Utility library
'----------------------------
Clear
Option base 1
Option EXPLICIT

Dim fontw As integer= MM.FONTWIDTH
Dim fonth As integer= MM.FONTHEIGHT
Dim b As integer=145

test

Sub test2
  Local a$,k$
  CLS
  k$="abcdefghijklmnopqrstuvwxyz"
  k$=k$+"1234567890.-_"
  a$=textinput$(0,20,k$,10)
  Print @(0,0)a$
End Sub

'------------
Sub test
  Local a$
  CLS
  a$= dirwin$(0,50,14,"B:/","")
  Print @(0,0)a$;
End Sub
'-------------

Function dirwin$(x,y,lines,path$,Ext$)
  Const winw=39
  Local fname$(256)
  Local a$,key$,i,n,file$,search$
  Local p$,fcount,top,bottom
  Local ftop,x2,y2,y3,y4,y5
  Local boxw,boxh,o$,o1$
  Local cursor,cmode,endstate
  Local dflags As integer
  dirwin$="999"
  endstate=1
  dflags=2
  key$="abcdefghijklmnop01234567890.-"
  boxw=fontw*winw+6
  boxh=fonth*(lines)+3
  x2=x+3
  y2=y+fonth+3
  y3=y+2
  y4=y2+3
  y5=y2+boxh+2
  Box x,y,boxw,fonth+3,1,666
  Box x,y+fonth+4,boxw,boxh,1,b
  Box x,y5,boxw,fonth+3,1,b
  Print @(x2,y5+2)"[D]rive [S]ort"

  If ext$="" Then
    search$=search$+"*"
  Else
    search$="*."+ext$
  EndIf
  search$=UCase$(search$)
  If path$<>""Then p$=path$ Else p$=Cwd$
  On error skip
  Chdir p$
  If MM.Errno Then p$="A:/":Drive "a:"
  '---------------------------------'
  'Main Loop
  '---------------------------------'
  Do
    'Load dir array
    If endstate=1 Then
      fcount=0
      cmode=0
      cursor =1
      ftop=1
      If Len(p$)>3 Then
        fcount=1
        fname$(1)="1.."
      EndIf
      For i=1 To 2
        On error skip 9
        If i=1 Then
          file$=Dir$("*",DIR)
        Else
          file$=Dir$(search$,file)
        EndIf
        Do While file$<>"" And fcount<256
          Inc fcount,1
          fname$(fcount)=Str$(i)+file$
          file$=Dir$()
        Loop
        If MM.Errno Then Exit Function
      Next i
      Sort fname$(),,dflags,1,fcount
      If Len(p$)>winw Then
        Print @(x2,y3)Left$(p$,2)+"..."+Right$(p$,winw-5)
      Else
        Print @(x2,y3)Left$(p$+Space$(winw),winw)
      EndIf
    EndIf

    Do
      Select Case endstate
        Case 1,2
          top=ftop
          bottom=ftop+lines-1
        Case 3
          top=ftop+cursor-1
          bottom=ftop+lines-1
        Case 4
          top=ftop+cursor-2
          bottom=top+1
      End Select

      For i = top To bottom
        If i<=fcount Then
          n=Len(fname$(i))-1
          a$=Right$(fname$(i),n)
          file$=Left$(a$+Space$(winw-4),winw-4)
          If Left$(fname$(i),1)="1"Then
            file$=file$+"DIR "
          Else
            file$=file$+"FILE"
          EndIf
          If i=ftop-1+cursor Then
            cmode=2
          Else
            cmode=0
          EndIf
        Else
          file$=Space$(winw)
          cmode=0
        EndIf
      Print @(x2,y4+(i-ftop)*fonth,cmode)file$
      Next i

      Do :a$=UCase$(Inkey$):Loop Until a$<>""
        i=Asc(a$)
        endstate=0
        If i=128 And cursor+ftop>2 Then
          If cursor>1 And cursor<=lines Then
          cursor =cursor-1
          endstate=2
          ElseIf cursor=1 And ftop>1 Then
            endstate=3
            Inc ftop,-1
          EndIf
        ElseIf i=129 And (cursor+ftop-1)<fcount Then
          If cursor>=lines Then
            Inc ftop,1
            endstate=2
          ElseIf cursor<lines Then
            Inc cursor,1
            endstate=4
          EndIf
        Else If i=136 Then
          cursor=1
          If ftop-lines<1 Then
            ftop=1
            endstate=3
          Else
            ftop=ftop-lines
            endstate=2
          EndIf
        ElseIf i=137 Then
          endstate=2
          If ftop+lines>fcount Then
            cursor=fcount-ftop+1
            'add new endstate?
          Else
            ftop=ftop+lines
            cursor=1
          EndIf
        ElseIf i= 134 Then
          endstate=2
          ftop=1
          cursor=1
        Else If i=135 Then
          endstate=2
          ftop=fcount\lines*lines
          cursor=fcount Mod lines+1
        ElseIf i=13 Then
          a$=fname$(cursor+ftop-1)
          o$=Right$(a$,Len(a$)-1)
          If Left$(a$,1)="1" Then
            endstate=1
            If o$=".." Then
              On error skip 2
              Chdir ".."
              p$=Cwd$
              If MM.Errno Then Exit Function
            Else
              If Right$(p$,1)<>"/"Then
                p$=p$+"/"+o$
              Else
                p$=p$+o$
              EndIf
              On error skip 1
              Chdir p$
              If MM.Errno Then Exit Function
            EndIf
          Else
            endstate=5
          EndIf
        ElseIf a$="D" Then
          endstate=1
          If Left$(p$,1)="A"Then
            a$="B:"
          Else
            a$="A:"
          EndIf
          On error skip 2
          Drive a$
          p$=Cwd$
          If MM.Errno Then Drive "A:":p$=Cwd$
        ElseIf a$="S" Then
          endstate=1
          If dflags=2 Then
            dflags=3
          Else
            dflags=2
          EndIf
        ElseIf Asc(a$)=27 Then
          endstate=6
          o$=""
        EndIf
      Loop Until endstate > 0
  Loop Until endstate>4
  dirwin$=p$+"$"+o$
End Function

'-----------------------
Function TextInput$(x,y,key$,length)
  Local blink,text1$,cx,a$,c$,px,cmode

  blink = 0
  Text1$=""
  cx=0
  'Fixed Text Input
  Print @(x,y)Space$(length);
   Do
    Do
      a$=Inkey$
      blink=(blink+1) Mod 1000
      c$=a$
      If blink <500 Then cmode = 2 Else cmode =0
      cx=Len(text1$)
      If cx=length Then
        c$=Right$(text1$,1)
      Else
        c$=" "
        Inc cx,1
      EndIf
      px=cx-1
      Print @(x+((px)*fontw),y,cmode)c$;
    Loop While a$=""
    Print @(x+(px*fontw),y,0)c$
    If Asc(a$)=8 And Len(text1$)>0 Then
      Print @(x+px*fontw,y,0)" ";
      Text1$=Left$(text1$,Len(text1$)-1)
    ElseIf Instr(1,key$,a$)>0 And Len(text1$)<length Then
      Text1$=text1$+a$
      Print @(x+px*fontw,y,0)a$;
    EndIf
  Loop Until Asc(a$)=13
  textinput$ = text1$
End Function

I wrote the original code in 2015, and was an all-in-one directory routine, but I don’t entirely remember what my logic was, so paired I it down to the basics and will build it back up. The original directory display routine was simpler, and I update it to something I think is way better, and I added a drive swap with some error protection so it doesn’t bomb if you pull out the SD card. Currently it’s just a file selector, that returns the path and filename, with a $ delimiter between the two. In the original the dialogs were non-destructive popups, but because of the between the Maximite Pico MMBASIC, they don’t work, so I have to come up with another method.

The second function is a fixed width input routine that that only allows characters from a defined set. I originally created this because the standard INPUT function didn’t allow enough control over what was entered or what the max size was.

They work, but they’re a bit of rough work in progress, so I’ve got a lot of cleanup and optimizing to do, and I’m looking for feedback and suggestions.

Your file selector works well and looks nice!

Suggestions:

  • sorting; either sort alphabetically by default, or allow for sorting by alpha/timestamp
  • add a way to scroll up/down by a full “page”; shift+up/down arrow on PicoCalc sends pageup and pagedown, so that might be a good way to map it
  • consider expanding the size to full screen; given the limited display size of the PicoCalc, I’m not sure it would be useful to have anything showing behind the dialog anyway
  • for filenames that are too long (I only had one when I tested – “geometricabstractionism.bas”), consider animating/scrolling the line when highlighted so it can show the full filename; this is less likely to be an issue if the dialog was expanded to full screen
  • since there’s plenty of space on the drive indicator line at the top, consider moving the “[D] Drive” note there and combining it on the single line with the actual drive letter, as this would free up another row
  • consider passing in some colors (foreground, background, frameline) for “theming”, if used with an application that has a very different default color set;.these default colors are fine though, and allowing for theming might just add unnecessary bloat

I’m guessing the input function is still a work in progress? I noticed a few errors inlcuding a typo in the LOCAL line (“.” insead of “,”), an error with KEYDOWN, and some other stuff and decided to not go further looking into it for now. :slight_smile:

1 Like

I played around with it a bit and added:

  • scroll up/down by a full page using shift+up/down
  • expanded size to full screen
  • moved “[D] Drive” to top line, at far right, added divider line, and adjusted “…” path drawing to match
  • also changed some var=var+1 to INC var,1 (faster)

Still to do:

  • sorting
  • handle long filenames (though maybe not necessary now the area is wider)
  • color theming

(Also, I removed the second function and test2 while I edited this.)

'----------------------------
'Utility library
'----------------------------
CLEAR
OPTION base 1
OPTION EXPLICIT

DIM fontw AS integer= MM.FONTWIDTH
DIM fonth AS integer= MM.FONTHEIGHT
DIM b AS integer=145

test

'------------
SUB test
  LOCAL a$
  CLS
  a$= dirwin$(0,0,24,"b:/","")
  PRINT @(0,0)a$;
END SUB
'-------------

FUNCTION dirwin$(x,y,lines,path$,Ext$)
  CONST winw=39
  LOCAL fname$(256) 'length 13
  LOCAL a$,key$,i,n,file$,search$
  LOCAL p$,fcount,top,bottom
  LOCAL ftop,x2,y2,y3,y4,y5
  LOCAL boxw,boxh,o$,o1$
  LOCAL cursor,cmode,endstate
  dirwin$="999"
  endstate=1
  boxw=fontw*winw+6
  boxh=fonth*(lines)+3
  x2=x+3
  y2=y+fonth+3
  y3=y+2
  y4=y2+3
  y5=y2+boxh+2
  BOX x,y,boxw,fonth+3,1,666
  BOX x,y+fonth+4,boxw,boxh,1,b
  PRINT @(fontw*(winw-9),y3)"[D] Drive"
  LINE fontw*(winw-9)-4,y,fontw*(winw-9)-4,fonth+3,1,666

  IF ext$="" THEN
    search$=search$+"*"
  ELSE
    search$="*."+ext$
  ENDIF
  search$=UCASE$(search$)
  IF path$<>""THEN p$=path$ ELSE p$=CWD$
  ON error skip
  CHDIR p$
  IF MM.Errno THEN p$="A:/":DRIVE "a:"
  '---------------------------------'
  'Main Loop
  '---------------------------------'
  DO
    'Load dir array
    IF endstate=1 THEN
      fcount=0
      cmode=0
      cursor=1
      ftop=1
      IF LEN(p$)>3 THEN
        fcount=1
        fname$(1)="1.."
      ENDIF
      FOR i=1 TO 2
        ON error skip 9
        IF I=1 THEN
          file$=DIR$("*",DIR)
        ELSE
          file$=DIR$(search$,file)
        ENDIF
        DO WHILE file$<>"" AND fcount<256
          inc fcount,1
          fname$(fcount)=STR$(i)+file$
          file$=DIR$()
        LOOP
        IF MM.Errno THEN EXIT FUNCTION
      NEXT i
      IF LEN(p$)>winw-10 THEN
        PRINT @(x2,y3)LEFT$(p$,2)+"..."+RIGHT$(p$,winw-15)
      ELSE
        PRINT @(x2,y3)LEFT$(p$+SPACE$(winw-10),winw-10)
      ENDIF
    ENDIF

    '---------- Display directory contents ----------
    DO
      SELECT CASE endstate
        CASE 1,2
          top=ftop
          bottom=ftop+lines-1
        CASE 3
          top=ftop+cursor-1
          bottom=ftop+lines-1
        CASE 4
          top=ftop+cursor-2
          bottom=top+1
      END SELECT

      FOR i = top TO bottom
        IF i<=fcount THEN
          n=LEN(fname$(i))-1
          a$=RIGHT$(fname$(i),n)
          file$=LEFT$(a$+SPACE$(winw-4),winw-4)
          IF LEFT$(fname$(i),1)="1" THEN
            file$=file$+"DIR "
          ELSE
            file$=file$+"FILE"
          ENDIF
          IF i=ftop-1+cursor THEN
            cmode=2
          ELSE
            cmode=0
          ENDIF
        ELSE
          file$=SPACE$(winw)
          cmode=0
        ENDIF
      PRINT @(x2,y4+(i-ftop)*fonth,cmode)file$
      NEXT i

      '---------- Input/Selection loop ----------
      DO :a$=INKEY$:LOOP UNTIL a$<>""
        i=ASC(a$)
        endstate=0
        IF i=128 THEN
          IF cursor>1 AND cursor<=lines THEN
            inc cursor,-1
            endstate=2
          ELSEIF cursor=1 AND ftop>1 THEN
            endstate=3
            inc ftop,-1
          ENDIF
        ELSEIF i=129 AND (cursor+ftop-1)<fcount THEN
          IF cursor>=lines THEN
            inc ftop,1
            endstate=2
          ELSEIF cursor<lines THEN
            inc cursor,1
            endstate=4
          ENDIF
        elseIF i=136 THEN
          ftop=ftop-lines
          if ftop<1 then
            cursor=1
            ftop=1
            endstate=3
          else
            endstate=2
          endif
        ELSEIF i=137 THEN
          ftop=ftop+lines
          IF (cursor+ftop-1)>fcount THEN
            DO
              inc cursor,-1
            LOOP UNTIL ((cursor+ftop-1)<=fcount or (cursor<1))
            IF cursor<1 then
              ftop=ftop-lines
              cursor=fcount-ftop+1
            endif
          ENDIF
          endstate=2
        ELSEIF i=13 THEN
          a$=fname$(cursor+ftop-1)
          o$=RIGHT$(a$,LEN(a$)-1)
          IF LEFT$(a$,1)="1" THEN
            endstate=1
            IF o$=".." THEN
              ON error skip 2
              CHDIR ".."
              p$=CWD$
              IF MM.Errno THEN EXIT FUNCTION
            ELSE
              IF RIGHT$(p$,1)<>"/"THEN
                p$=p$+"/"+o$
              ELSE
                p$=p$+o$
              ENDIF
              ON error skip 1
              IF MM.Errno THEN EXIT FUNCTION
              CHDIR p$
            ENDIF
          ELSE
            endstate=5
          ENDIF
        ELSEIF UCASE$(a$)="D" THEN
          endstate=1
          IF LEFT$(p$,1)="A"THEN
            a$="B:"
          ELSE
            a$="A:"
          ENDIF
          ON error skip 2
          DRIVE a$
          p$=CWD$
          IF MM.Errno THEN DRIVE "A:":p$=CWD$
        ELSEIF ASC(a$)=27 THEN
          endstate=6
          o$=""
        ENDIF
      LOOP UNTIL endstate > 0
  LOOP UNTIL endstate>4
  dirwin$=p$+"$"+o$
END FUNCTION
1 Like

Thanks! The text input worked, but I didn’t tested it after I added the EXPLICIT option. Fixed it in the post and I’ll fire it up to confirm it.

  • I plan on adding a sort, and it’s really easy in this version of MMBASIC, so it the next thing on my to-do.
  • Yes, given the display size, full screen would be better. I normal set the window sizes either through a global variable or though a parameter in the function call. In this case it was set internally to 30 just to see how it looked, and if it self-adjusted correctly.
  • The drive indicator line is actually full, as it’s set up to display long paths… which reminds me I probably should truncate the line at a leading “/” rather then the middle of a directory line… I intend the bottom to have more options, and different ones depending on the mode (Open, Save, Select Dir. etc), as well as being where file names are entered
  • Scrolling long file names is a good idea, and there’s a couple was to handle it, either auto scrolling or using the right & left cursor. I was planning to add a “[I]nfo” option to display more information like file size and date.
  • I pulled the colors temporarily because the Pico version of MMBASIC handles color a bit differently then the Color Maximite, which can be a embeded into stings, sort of like the C64 could. I havent seen any similar, so it means a lot of separate color commands.
1 Like

Thank for the addition! It was another thing I planned on adding.

Good catch the INC, didn’t realized it was an option. I’ve got to print out the user docs because I’m and old-school hardcopy manual guy, and I always miss stuff scrolling through it on my phone.

2 Likes

Ah, it makes sense that you were planning to use the bottom for more options. Sorry I moved the drive selector hint up to the top! Hopefully some of the other code I put in there is useful though. :slight_smile:

Speaking of manuals, I just looked in the PicoMite manual and realized how easy sorting actually is, like you said… It’s just a parameter to the FILES command! (I’m still finding my way through MMBasic.) EDIT: Actually, I guess that won’t work since it if just the command to print the results. I was confusing it with DIR$, which doesn’t appear to have sorting built in. I guess this requires sorting the array. So I guess it’s SORT, then!

1 Like

Took me a bit to figure out SORT as the doc’s kind of makes it look there’s simple default, no parameters, mode, but there isn’t.

I integrated the changes you suggested slightly differently, and added HOME and END… as well as trying to clean out the vestigial junk that was in the old version… which I’ll dropped into the original post.

1 Like

Drats! Lol, muffed the math on the END move… can’t seem to edit the first post anymore…stated adding color options so. ill put that up later.

1 Like

Suggestions, comments, and general roasting:

Ok, Color is stated, more of a pain in Pico MMBASIC, but it’s coming along. Current I’m setting is as a an overall theme, so like with other MMBASIC I’ve made in the past, it’s possible to customize and save personal preferences. There in constants them moment, but once I get the colors where i like them, ill change them to universal constants.

I figured a fairly simple way to display long filename which uses the left & right cursor keys to move through the name. I know how i would step it up to auto scroll the long filenames when highlighted, but as fast as MMBASIC is, is still BASIC, so it may add a good amount of lag to scrolling through the directory listings.

The next module I’m going to start working on is a variation of a drop-down/popup option menu subroutine i created. Previously, it was more hardcoded, so you had to create a function/sub for each one, but i think I see a way just to pass the option strings and option redirects as parameters, so you’d only need one, which saves a ton of space… which I actually ran out of in my Maximite programs.

Along with that addition, I’m trying to figure out the best way to implement non destructive popups ad drop downs. On the Maximite I came up with a way of writing out the screen memory of the area the dialog covered to disk, and then reading it back when it closed. I think I can do the same with SAVE IMAGE & LOAD IMAGE.

Hi!
I’m new to the group and just happen to stumble into this conversation. If you don’t mind I further refined the utility code. This updated code significantly enhances the file browser by replacing “magic numbers” with descriptive constants for improved readability and maintainability. Key navigation has been upgraded with explicit sorting, dedicated Home and End key support, and refined Page Up/Down logic for more predictable scrolling. The TextInput$ function is now much more user-friendly, featuring **arrow key navigation, character insertion, and **case-sensitive input. Additionally, the ‘dirwin$’ function introduces an interactive “F” key filter, displays the file/directory count, ensures clearer redrawing of the file list, and implements more robust error handling with centralized error messages for path and drive operations. Finally, the user interface now includes better labels in the command bar, making all new features easily discoverable.

'----------------------------
'Utility library - Enhanced
'----------------------------
CLEAR
OPTION base 1
OPTION EXPLICIT

’ — Global Constants —
CONST COLOR_BACKGROUND_LIST = 145 ’ A typical light blue/gray
CONST COLOR_BOX_BORDER = 666 ’ A darker border color
CONST DIR_LIST_WIDTH = 39 ’ Width of the directory listing area in characters

CONST KEY_UP = 128
CONST KEY_DOWN = 129
CONST KEY_PAGE_UP = 136
CONST KEY_PAGE_DOWN = 137
CONST KEY_HOME = 134
CONST KEY_END = 135
CONST KEY_ENTER = 13
CONST KEY_ESCAPE = 27
CONST KEY_BACKSPACE = 8 ’ Assuming this is 8 for backspace

CONST DIR_ENTRY_PREFIX = “1” ’ Prefix for directory entries in fname$()
CONST FILE_ENTRY_PREFIX = “2” ’ Prefix for file entries in fname$()

CONST SORT_MODE_DIRS_FIRST = 2 ’ Sort directories before files
CONST SORT_MODE_ALL_ALPHA = 3 ’ Sort all alphabetically

’ — Global Variables —
DIM fontw AS INTEGER= MM.FONTWIDTH
DIM fonth AS INTEGER= MM.FONTHEIGHT

’ — Main Program Entry Point —
CALL MainProgram

SUB MainProgram
LOCAL selectedItemPath$
CLS
PRINT “Welcome to the Enhanced File Browser!”
PRINT “”
PRINT “Press any key to open the file browser…”
DO : LOOP WHILE INKEY$ = “” ’ Wait for a key press

' Example usage of the enhanced dirwin$
' It returns the full path and selected item name, separated by '$'
selectedItemPath$ = DirWindow$(0, 0, 24, "B:/", "") ' Start in B:\, showing 24 lines

IF LEFT$(selectedItemPath$, 3) = "999" THEN ' Check for cancellation string
    PRINT @(0, fonth * 26) "Operation cancelled."
ELSE
    LOCAL currentPath$, selectedItemName$
    currentPath$ = LEFT$(selectedItemPath$, INSTR(1, selectedItemPath$, "$") - 1)
    selectedItemName$ = RIGHT$(selectedItemPath$, LEN(selectedItemPath$) - INSTR(1, selectedItemPath$, "$"))
    PRINT @(0, fonth * 26) "Selected Path: " + currentPath$
    PRINT @(0, fonth * 27) "Selected Item: " + selectedItemName$
END IF

PRINT ""
PRINT "Press any key to exit."
DO : LOOP WHILE INKEY$ = ""
END

END SUB


SUB test ’ Original test kept for reference (now calls DirWindow$)
LOCAL result$
CLS
result$ = DirWindow$(0, 0, 24, “B:/”, “”)
PRINT @(0, 0) result$;
END SUB
'-------------

'-------------------------------------------------------------------------------
’ FUNCTION DirWindow$ (x, y, lines, initialPath$, fileExtensionFilter$)
’ Displays a file/directory browser window.
’ Parameters:
’ x, y: Top-left coordinates of the window.
’ lines: Number of lines to display in the file list area.
’ initialPath$: Starting directory path.
’ fileExtensionFilter$: Optional file extension filter (e.g., “TXT”, “JPG”).
’ Returns:
’ A string containing “Path$SelectedItemName$” or “999” if cancelled.
'-------------------------------------------------------------------------------
FUNCTION DirWindow$(x, y, lines, initialPath$, fileExtensionFilter$)
CONST MAX_FILES_DISPLAY = 256 ’ Max number of files/dirs to display
CONST PATH_DISPLAY_TRUNCATE_LENGTH = DIR_LIST_WIDTH - 15 ’ Space for path + “[D] Drive”

LOCAL fileNames$(MAX_FILES_DISPLAY)
LOCAL inputChar$, i, n, currentFile$, searchPattern$
LOCAL currentPath$, fileCount, topVisibleLine, bottomVisibleLine
LOCAL firstLineToDisplay, x2, y2, y3, y4, y5
LOCAL boxWidth, boxHeight, selectedItemName$, cancelledSignal$
LOCAL cursorIndex, displayMode, exitState
LOCAL sortOrder AS INTEGER ' Renamed dflags to sortOrder
LOCAL filterText$ ' For the interactive filter

DirWindow$ = "999" ' Default return value for cancellation
exitState = 1       ' Initial state: load directory
sortOrder = SORT_MODE_DIRS_FIRST ' Default sort order (directories first)
filterText$ = fileExtensionFilter$ ' Initialize filter with passed value

' --- Calculate UI dimensions ---
boxWidth = fontw * DIR_LIST_WIDTH + 6
boxHeight = fonth * lines + 3
x2 = x + 3
y2 = y + fonth + 3
y3 = y + 2
y4 = y2 + 3
y5 = y2 + boxHeight + 2

' --- Draw UI Boxes ---
BOX x, y, boxWidth, fonth + 3, 1, COLOR_BOX_BORDER           ' Path display box
BOX x, y + fonth + 4, boxWidth, boxHeight, 1, COLOR_BACKGROUND_LIST ' File list box
BOX x, y5, boxWidth, fonth + 3, 1, COLOR_BACKGROUND_LIST      ' Command bar box

' --- Draw command labels and separators ---
PRINT @(fontw * (DIR_LIST_WIDTH - 9), y3) "[D] Drive"
LINE fontw * (DIR_LIST_WIDTH - 9) - 4, y, fontw * (DIR_LIST_WIDTH - 9) - 4, fonth + 3, 1, COLOR_BOX_BORDER
PRINT @(x + 3, y5 + 2) "[S]ort [F]ilter [H]ome [E]nd [PgUp] [PgDn] [Esc] Exit"


' --- Set search pattern ---
IF filterText$ = "" THEN
    searchPattern$ = "*"
ELSE
    ' Ensure filter is uppercase for comparison
    searchPattern$ = UCASE$(filterText$)
    IF INSTR(1, searchPattern$, "*") = 0 AND INSTR(1, searchPattern$, ".") = 0 THEN
        searchPattern$ = "*." + searchPattern$ ' Assume it's an extension if no wildcard/dot
    END IF
END IF

' --- Set initial path ---
IF initialPath$ <> "" THEN
    currentPath$ = initialPath$
ELSE
    currentPath$ = CWD$ ' Current working directory
END IF

' Try to change to initial path, handle error
ON ERROR GOTO HandlePathError
CHDIR currentPath$
ON ERROR GOTO 0 ' Reset error handling

'---------------------------------'
' Main Loop
'---------------------------------'
DO
    ' --- Load dir array if state requires it ---
    IF exitState = 1 THEN ' Full redraw and directory re-scan
        fileCount = 0
        displayMode = 0
        cursorIndex = 1
        firstLineToDisplay = 1

        ' Clear previous list display before loading new one
        FOR i = 0 TO lines - 1
            PRINT @(x2, y4 + i * fonth, 0) SPACE$(DIR_LIST_WIDTH);
        NEXT i

        ' Add ".." entry if not at root (assuming X:\ is 3 chars)
        IF LEN(currentPath$) > 3 THEN
            fileCount = 1
            fileNames$(1) = DIR_ENTRY_PREFIX + ".."
        END IF

        ' Get directories
        ON ERROR RESUME NEXT ' Temporarily ignore errors during Dir$
        currentFile$ = DIR$("*", DIR)
        DO WHILE currentFile$ <> "" AND fileCount < MAX_FILES_DISPLAY
            INC fileCount, 1
            fileNames$(fileCount) = DIR_ENTRY_PREFIX + currentFile$
            currentFile$ = DIR$()
        LOOP

        ' Get files
        currentFile$ = DIR$(searchPattern$, FILE)
        DO WHILE currentFile$ <> "" AND fileCount < MAX_FILES_DISPLAY
            INC fileCount, 1
            fileNames$(fileCount) = FILE_ENTRY_PREFIX + currentFile$
            currentFile$ = DIR$()
        LOOP
        ON ERROR GOTO 0 ' Reset error handling

        ' Sort the file list
        SORT fileNames$(),, sortOrder, 1, fileCount

        ' Display current path and file count
        LOCAL displayPath$
        IF LEN(currentPath$) > PATH_DISPLAY_TRUNCATE_LENGTH THEN
            displayPath$ = LEFT$(currentPath$, 2) + "..." + RIGHT$(currentPath$, PATH_DISPLAY_TRUNCATE_LENGTH - 5)
        ELSE
            displayPath$ = LEFT$(currentPath$ + SPACE$(PATH_DISPLAY_TRUNCATE_LENGTH), PATH_DISPLAY_TRUNCATE_LENGTH)
        END IF
        PRINT @(x2, y3) displayPath$;
        PRINT @(x + boxWidth - fontw * 10, y3) "Files:" + LTRIM$(STR$(fileCount)); ' Display file count
    END IF

    '---------- Display directory contents ----------
    DO
        SELECT CASE exitState
            CASE 1, 2 ' Full redraw or simple cursor move/scroll
                topVisibleLine = firstLineToDisplay
                bottomVisibleLine = firstLineToDisplay + lines - 1
            CASE 3    ' Cursor moved up and list scrolled up (handled by cursor moving to top of screen)
                topVisibleLine = firstLineToDisplay
                bottomVisibleLine = firstLineToDisplay + lines - 1
            CASE 4    ' Cursor moved down and list scrolled down (handled by cursor moving to bottom of screen)
                topVisibleLine = firstLineToDisplay
                bottomVisibleLine = firstLineToDisplay + lines - 1
        END SELECT

        FOR i = topVisibleLine TO bottomVisibleLine
            LOCAL displayFileName$, itemType$
            IF i <= fileCount THEN
                LOCAL rawFileName$, fileNameLength
                rawFileName$ = RIGHT$(fileNames$(i), LEN(fileNames$(i)) - 1)
                fileNameLength = LEN(rawFileName$)

                displayFileName$ = LEFT$(rawFileName$ + SPACE$(DIR_LIST_WIDTH - 4), DIR_LIST_WIDTH - 4)

                IF LEFT$(fileNames$(i), 1) = DIR_ENTRY_PREFIX THEN
                    itemType$ = "DIR "
                ELSE
                    itemType$ = "FILE"
                END IF
                displayFileName$ = displayFileName$ + itemType$

                IF i = firstLineToDisplay - 1 + cursorIndex THEN
                    displayMode = 2 ' Highlight selected item
                ELSE
                    displayMode = 0 ' Normal text
                END IF
            ELSE
                displayFileName$ = SPACE$(DIR_LIST_WIDTH) ' Blank line
                displayMode = 0
            END IF
            PRINT @(x2, y4 + (i - firstLineToDisplay) * fonth, displayMode) displayFileName$
        NEXT i

        ' --- Wait for user input ---
        DO : inputChar$ = INKEY$: LOOP UNTIL inputChar$ <> ""
        LOCAL asciiValue AS INTEGER = ASC(UCASE$(inputChar$)) ' UCASE for commands
        exitState = 0 ' Reset state, assume no major change

        ' --- Handle user input ---
        SELECT CASE asciiValue
            CASE KEY_UP ' Up Arrow
                IF cursorIndex > 1 THEN
                    INC cursorIndex, -1
                    exitState = 2 ' Cursor moved, partial redraw
                ELSEIF firstLineToDisplay > 1 THEN
                    INC firstLineToDisplay, -1
                    exitState = 2 ' Scrolled up, full list redraw
                END IF
            CASE KEY_DOWN ' Down Arrow
                IF (cursorIndex + firstLineToDisplay - 1) < fileCount THEN
                    IF cursorIndex < lines THEN
                        INC cursorIndex, 1
                        exitState = 2 ' Cursor moved, partial redraw
                    ELSEIF (firstLineToDisplay + lines - 1) < fileCount THEN
                        INC firstLineToDisplay, 1
                        exitState = 2 ' Scrolled down, full list redraw
                    END IF
                END IF
            CASE KEY_PAGE_UP ' Page Up
                IF firstLineToDisplay > 1 THEN
                    firstLineToDisplay = MAX(1, firstLineToDisplay - lines)
                    cursorIndex = 1 ' Reset cursor to top of page
                    exitState = 2
                END IF
            CASE KEY_PAGE_DOWN ' Page Down
                IF (firstLineToDisplay + lines - 1) < fileCount THEN
                    firstLineToDisplay = MIN(fileCount - lines + 1, firstLineToDisplay + lines)
                    IF firstLineToDisplay < 1 THEN firstLineToDisplay = 1 ' Ensure it doesn't go negative
                    cursorIndex = 1 ' Reset cursor to top of page
                    exitState = 2
                END IF
            CASE KEY_HOME ' Home
                firstLineToDisplay = 1
                cursorIndex = 1
                exitState = 2
            CASE KEY_END ' End
                firstLineToDisplay = MAX(1, fileCount - lines + 1)
                cursorIndex = fileCount - firstLineToDisplay + 1
                exitState = 2
            CASE KEY_ENTER ' Enter
                selectedItemName$ = RIGHT$(fileNames$(cursorIndex + firstLineToDisplay - 1), LEN(fileNames$(cursorIndex + firstLineToDisplay - 1)) - 1)

                IF LEFT$(fileNames$(cursorIndex + firstLineToDisplay - 1), 1) = DIR_ENTRY_PREFIX THEN ' It's a directory
                    exitState = 1 ' Re-scan directory

                    IF selectedItemName$ = ".." THEN
                        ON ERROR GOTO HandlePathError
                        CHDIR ".."
                        currentPath$ = CWD$
                        ON ERROR GOTO 0
                    ELSE
                        IF RIGHT$(currentPath$, 1) <> "/" AND RIGHT$(currentPath$, 1) <> "\" THEN
                            currentPath$ = currentPath$ + "/" + selectedItemName$
                        ELSE
                            currentPath$ = currentPath$ + selectedItemName$
                        END IF
                        ON ERROR GOTO HandlePathError
                        CHDIR currentPath$
                        ON ERROR GOTO 0
                    END IF
                ELSE ' It's a file
                    exitState = 5 ' Exit with file selected
                END IF
            CASE ASC("D") ' Change Drive
                exitState = 1
                LOCAL newDrive$
                IF LEFT$(currentPath$, 1) = "A" THEN
                    newDrive$ = "B:"
                ELSE
                    newDrive$ = "A:"
                END IF
                ON ERROR GOTO HandlePathError
                DRIVE newDrive$
                currentPath$ = CWD$
                ON ERROR GOTO 0
            CASE ASC("S") ' Sort Toggle
                exitState = 1
                IF sortOrder = SORT_MODE_DIRS_FIRST THEN
                    sortOrder = SORT_MODE_ALL_ALPHA
                ELSE
                    sortOrder = SORT_MODE_DIRS_FIRST
                END IF
            CASE ASC("F") ' Filter
                LOCAL newFilterInput$
                newFilterInput$ = TextInput$(x + 3, y5 + 2, "ABCDEFGHIJKLMNOPQRSTUVWXYZ0123456789.-_*", 10)
                IF newFilterInput$ <> "" THEN
                    filterText$ = newFilterInput$ ' Update the filter
                ELSE
                    filterText$ = "" ' Clear filter if empty input
                END IF
                ' Re-draw command bar to clear input box
                PRINT @(x + 3, y5 + 2) LEFT$("[S]ort [F]ilter [H]ome [E]nd [PgUp] [PgDn] [Esc] Exit" + SPACE$(DIR_LIST_WIDTH), DIR_LIST_WIDTH);
                exitState = 1 ' Re-scan after filter change
            CASE KEY_ESCAPE ' Escape
                exitState = 6
                selectedItemName$ = "" ' Clear selection for cancellation
        END SELECT
    LOOP UNTIL exitState > 0 ' Loop until a significant state change (e.g., directory change, file selection, exit)
LOOP UNTIL exitState > 4 ' Loop until selected file (5) or cancelled (6)

DirWindow$ = currentPath$ + "$" + selectedItemName$ ' Return path and selected item
EXIT FUNCTION ' Exit function normally

HandlePathError:
PRINT @(x2, y3) “Error: Access Denied or Invalid Path!” + SPACE$(LEN(currentPath$)) ’ Overwrite path with error msg
currentPath$ = “A:/” ’ Attempt to fallback to A:
DRIVE “A:”
currentPath$ = CWD$
RESUME NEXT ’ Continue execution after error
END FUNCTION

'-------------------------------------------------------------------------------
’ FUNCTION TextInput$ (x, y, allowedKeys$, maxLength)
’ Displays a single-line text input field.
’ Parameters:
’ x, y: Top-left coordinates of the input field.
’ allowedKeys$: String of characters allowed for input.
’ maxLength: Maximum length of the input string.
’ Returns:
’ The string entered by the user.
'-------------------------------------------------------------------------------
FUNCTION TextInput$(x, y, allowedKeys$, maxLength)
LOCAL blinkTimer, currentText$, cursorCol, inputChar$, charAtCursor$, displayMode

blinkTimer = 0
currentText$ = ""
cursorCol = 0 ' Represents the column position of the cursor (0-based)

' Clear the display area for the input field
PRINT @(x, y) SPACE$(maxLength);

DO
    DO
        inputChar$ = INKEY$
        blinkTimer = (blinkTimer + 1) MOD 1000
        IF blinkTimer < 500 THEN displayMode = 2 ELSE displayMode = 0 ' Blinking cursor mode

        ' Display blinking cursor at current position
        IF cursorCol < LEN(currentText$) THEN
            charAtCursor$ = MID$(currentText$, cursorCol + 1, 1)
        ELSE
            charAtCursor$ = " " ' Blank space if cursor at end
        END IF
        PRINT @(x + (cursorCol * fontw), y, displayMode) charAtCursor$;

    LOOP WHILE inputChar$ = "" ' Wait for a key press

    ' Reset character at cursor to normal display before processing new input
    IF cursorCol < LEN(currentText$) THEN
        PRINT @(x + (cursorCol * fontw), y, 0) MID$(currentText$, cursorCol + 1, 1);
    ELSE
        PRINT @(x + (cursorCol * fontw), y, 0) " ";
    END IF

    LOCAL asciiVal AS INTEGER = ASC(inputChar$) ' Do not UCASE here, allow case-sensitive input

    SELECT CASE asciiVal
        CASE KEY_BACKSPACE
            IF cursorCol > 0 THEN
                currentText$ = LEFT$(currentText$, cursorCol - 1) + RIGHT$(currentText$, LEN(currentText$) - cursorCol)
                cursorCol = cursorCol - 1
                PRINT @(x, y) LEFT$(currentText$ + SPACE$(maxLength), maxLength); ' Redraw the full string
            END IF
        CASE KEY_ENTER
            EXIT DO ' User pressed Enter, finish input
        ' Assuming 130 and 131 are Left and Right arrow keys - VERIFY THESE!
        CASE 130 ' KEY_LEFT (example, verify ASCII for your environment)
            IF cursorCol > 0 THEN
                cursorCol = cursorCol - 1
            END IF
        CASE 131 ' KEY_RIGHT (example, verify ASCII for your environment)
            IF cursorCol < LEN(currentText$) THEN
                cursorCol = cursorCol + 1
            END IF
        CASE ELSE
            IF INSTR(1, allowedKeys$, inputChar$) > 0 AND LEN(currentText$) < maxLength THEN
                ' Insert character at cursor position
                currentText$ = LEFT$(currentText$, cursorCol) + inputChar$ + RIGHT$(currentText$, LEN(currentText$) - cursorCol)
                cursorCol = cursorCol + 1
                PRINT @(x, y) LEFT$(currentText$ + SPACE$(maxLength), maxLength); ' Redraw the full string
            END IF
    END SELECT
LOOP

TextInput$ = currentText$

END FUNCTION

1 Like

Thanks for the additions, I’ll try integrating them!

The variable name are truncated for a couple reasons. When I program in compiled languages, I use a verbose naming convention because they’re lables that are only relevant in the source. In interpreted languages, like MMBASIC, where every byte counts, I’ve written programs large enough were I’ve had to remove every remark, space between operators, and shorten variable names just to get the last lines of coded to fit in. The segments I listed came from a Maximite MMBASIC I wrote that used 100% of the code space. It was such a problem that I had to write a sepetate program just to compact the program I was working on.

Another reason for terse names is that I’m programming all this on the PicoCalc itself, and the line length is limited… I’m hesitant to invoke the underscore line continuation because it’s a system level option and I wanted to keep it generically compatable… so long var/function names make it hard to read. Even with the abbreviations I’m not entirely happy with a lot of the lines being cut off, but its a necessary compromise for the time being.

Unless there’s an OPTION setting I don’t see, and I’m new to the PicoCalc as well, there is no GOTO option in this version of MMBASIC. When I started trying to add some errors handling, I was looking to do basicly the same thing you did, but found it wasn’t an feature. The only option is to use ON ERROR SKIP to temporary ignore errors in potentially problematic upcoming code, like file system access, and then check for an error state right afterwards.

Thanks for the clarifications and prompt reply.

This MMBasic code has been meticulously optimized to address the severe memory constraints inherent to the PicoCalc/Maximite environment. The strategy prioritizes minimizing raw byte count, which necessitates deviations from standard readability conventions.

My approach involved:

  • Aggressively stripping all comments and non-essential whitespace.
  • Truncating variable and parameter names to their shortest possible forms.
  • Consolidating multiple statements onto single lines using colons (:), a critical technique given the absence of underscore line continuation.
  • Implementing error handling via ON ERROR SKIP, adhering to the specific behavior outlined for this MMBasic interpreter.

While this highly optimized code is presented based on a deep understanding of embedded BASIC programming, direct testing on the PicoCalc hardware is pending. Based on my extensive experience with various BASIC dialects in constrained embedded systems, however, provides a strong foundation for the effectiveness of these optimizations.

Stripping all comments and unnecessary whitespace.

Truncating variable and parameter names.

Combining multiple statements per line using colons (:), given the absence of underscore line continuation and GOTO for error handling.

Leveraging the ON ERROR SKIP behavior as described for the specific MMBasic implementation.

The goal was to maximize code within tight memory limits, reflecting the unique challenges of embedded programming on this platform.

Clear:Option Base 1:Option Explicit
Dim fw As integer=MM.FONTWIDTH
Dim fh As integer=MM.FONTHEIGHT
Dim b As integer=145
test

Sub test2
Local a$,k$:CLS:k$=“abcdefghijklmnopqrstuvwxyz”:k$=k$+“1234567890.-_”:a$=TextInput$(0,20,k$,10):Print @(0,0)a$
End Sub

Sub test
Local a$:CLS:a$=dirwin$(0,50,14,“B:/”,“”):Print @(0,0)a$;
End Sub

Function dirwin$(x,y,ln,p$,e$)
Const ww=39
Local f$(256),a$,k$,i,n,fl$,s$,pl$,fc,t,bt,ft,x2,y2,y3,y4,y5,bw,bh,o$,cu,cm,es,df As integer
dw$=“999”:es=1:df=2:k$=“abcdefghijklmnop01234567890.-”
bw=fwww+6:bh=fhln+3
x2=x+3:y2=y+fh+3:y3=y+2:y4=y2+3:y5=y2+bh+2
Box x,y,bw,fh+3,1,666:Box x,y+fh+4,bw,bh,1,b:Box x,y5,bw,fh+3,1,b
Print @(x2,y5+2)“[D]rive [S]ort”
If e$=““Then s$=s$+”" Else s$=".”+e$
s$=UCase$(s$)
If p$<>““Then pl$=p$ Else pl$=Cwd$
On Error Skip:Chdir pl$
If MM.Errno Then pl$=“A:/”:Drive “a:”
Do 'Main Loop
If es=1 Then 'Load dir array
fc=0:cm=0:cu=1:ft=1
If Len(pl$)>3 Then fc=1:f$(1)=“1..”
For i=1 To 2
On Error Skip
If i=1 Then fl$=Dir$(”*”,DIR) Else fl$=Dir$(s$,file)
Do While fl$<>“” And fc<256
Inc fc,1:f$(fc)=Str$(i)+fl$:fl$=Dir$()
Loop
If MM.Errno Then Exit Function
Next i
Sort f$(),df,1,fc
If Len(pl$)>ww Then Print @(x2,y3)Left$(pl$,2)+“…”+Right$(pl$,ww-5) Else Print @(x2,y3)Left$(pl$+Space$(ww),ww)
EndIf

Do
  Select Case es
    Case 1,2:t=ft:bt=ft+ln-1
    Case 3:t=ft+cu-1:bt=ft+ln-1
    Case 4:t=ft+cu-2:bt=t+1
  End Select

  For i=t To bt
    If i<=fc Then
      n=Len(f$(i))-1:a$=Right$(f$(i),n)
      fl$=Left$(a$+Space$(ww-4),ww-4)
      If Left$(f$(i),1)="1"Then fl$=fl$+"DIR " Else fl$=fl$+"FILE"
      If i=ft-1+cu Then cm=2 Else cm=0
    Else
      fl$=Space$(ww):cm=0
    EndIf
  Print @(x2,y4+(i-ft)*fh,cm)fl$
  Next i

  Do:a$=UCase$(Inkey$):Loop Until a$<>""
    i=Asc(a$)
    es=0
    If i=128 And cu+ft>2 Then If cu>1 And cu<=ln Then cu=cu-1:es=2 ElseIf cu=1 And ft>1 Then es=3:Inc ft,-1
    ElseIf i=129 And (cu+ft-1)<fc Then If cu>=ln Then Inc ft,1:es=2 ElseIf cu<ln Then Inc cu,1:es=4
    ElseIf i=136 Then cu=1:If ft-ln<1 Then ft=1:es=3 Else ft=ft-ln:es=2
    ElseIf i=137 Then es=2:If ft+ln>fc Then cu=fc-ft+1 Else ft=ft+ln:cu=1
    ElseIf i=134 Then es=2:ft=1:cu=1
    ElseIf i=135 Then es=2:ft=fc\ln*ln:cu=fc Mod ln+1
    ElseIf i=13 Then
      a$=f$(cu+ft-1):o$=Right$(a$,Len(a$)-1)
      If Left$(a$,1)="1" Then
        es=1
        If o$=".." Then On Error Skip:Chdir "..":pl$=Cwd$:If MM.Errno Then Exit Function
        Else If Right$(pl$,1)<>"/"Then pl$=pl$+"/"+o$ Else pl$=pl$+o$
        On Error Skip:Chdir pl$:If MM.Errno Then Exit Function
        End If 'Matches If o$=".." Then
      Else
        es=5
      EndIf
    ElseIf a$="D" Then
      es=1
      If Left$(pl$,1)="A"Then a$="B:" Else a$="A:"
      On Error Skip:Drive a$:pl$=Cwd$
      If MM.Errno Then On Error Skip:Drive "A:":pl$=Cwd$
    ElseIf a$="S" Then es=1:If df=2 Then df=3 Else df=2
    ElseIf Asc(a$)=27 Then es=6:o$=""
    EndIf
Loop Until es > 0

Loop Until es>4
dw$=pl$+“$”+o$
End Function

Function TextInput$(x,y,k$,lg)
Local bl,t1$,cx,a$,c$,px,cm
bl=0:t1$=“”:cx=0
Print @(x,y)Space$(lg);
Do
Do:a$=Inkey$:bl=(bl+1)Mod 1000:c$=a$
If bl<500 Then cm=2 Else cm=0
cx=Len(t1$)
If cx=lg Then c$=Right$(t1$,1) Else c$=" ":Inc cx,1
px=cx-1
Print @(x+(pxfw),y,cm)c$;
Loop While a$=“”
Print @(x+(px
fw),y,0)c$
If Asc(a$)=8 And Len(t1$)>0 Then Print @(x+pxfw,y,0)" ":t1$=Left$(t1$,Len(t1$)-1)
ElseIf Instr(1,k$,a$)>0 And Len(t1$)<lg Then t1$=t1$+a$:Print @(x+px
fw,y,0)a$;
Loop Until Asc(a$)=13
ti$=t1$
End Function