Import Blitz3D 3D commands to MiniB3D or OpenB3D


Attention! 👉Starting November 2024, BlitzCoder.org will now be BlitzBasic.org.

 

Tweet blitzmax code-archives file-utilities
markcwm

This is the full 3D commands from Blitz3D. I've just written this for Openb3d and decided to try it on Minib3d too. Some of the function links don't work because they were never finished in Blitz3D. Save this file to sidesign.mod/minib3d.mod

Edit: the code didn't actually generate a working functions.bmx (the last function was repeated). I've fixed it now and updated this code. The code also works for Openb3d.
Edit: the code has been updated again and the unfinished links are generated. It also fixes when a function has been Rem'd.
Edit: rewrote the End parser, it now adds non-B3D functions, fixed start/end of file, still a few more things I could add though.
Edit: this should be my final edit, it now leaves all extra comments alone (except if they're between rem and function).

See below for the A to Z links importer, it's for the top of the module page for a quick jump to link option.

' b3ddocs2mini.bmx
' this imports the Blitz3D 3D command reference to Blitzmax Minib3d
' rename functions.bmx to oldfunctions.bmx

SuperStrict

Global bmxsrcfile$="inc/oldfunctions.bmx"
Global bmxdestfile$="inc/functions.bmx"
Global htmldocspath$="../../../help/commands/3d_commands" ' Blitz3D help path

Local t:TBB=New TBB

t.FindImports()

Type TBB

    Global bbdoc$, about$, param$

    Method FindImports$()

        Local file:TStream=ReadFile(bmxsrcfile)
        If Not file RuntimeError "could not open file "+bmxsrcfile

        Local size%=FileSize(bmxsrcfile)
        SeekStream file,0
        Local bmx$=ReadString(file,size)
        CloseStream file

        Local cou%=0,sr%,er%,sf%,ef%,lastef%,rp%,fp%,erp%,efp%,lastefp%,url%,rf%,cp%,cp2%,cp3%
        Local remtext$,functext$,comment$,newbmx$,line$,command$,filepath$,remdfunc$

        Print "Docs imported..."
        While sr>-1
            cou:+1
            lastef=ef
            sr=bmx.Find("Rem",sr+1)
            While bmx[sr-4..sr]="End " Or bmx[sr-3..sr]="End" Or bmx[sr-1..sr]="'"
                sr=bmx.Find("Rem",sr+1)
            Wend
            er=bmx.Find("End",sr+1)
            While bmx[er+3..er+7]<>" Rem" And bmx[er+3..er+6]<>"Rem" Or bmx[er-1..er]="'"
                If bmx[er+3..er+7]=" Rem" Or bmx[er+3..er+6]="Rem" Then Exit
                er=bmx.Find("End",er+1)
            Wend
            sf=bmx.Find("Function",er+1)
            While bmx[sf-4..sf]="End " Or bmx[sf-3..sf]="End" Or bmx[sf-1..sf]="'" 
                sf=bmx.Find("Function",sf+1)
            Wend
            ef=bmx.Find("End",sf+1)
            While bmx[ef+3..ef+12]<>" Function" And bmx[ef+3..ef+11]<>"Function" Or bmx[ef-1..ef]="'"
                If bmx[er+3..er+12]=" Function" Or bmx[er+3..er+11]="Function" Then Exit
                ef=bmx.Find("End",ef+1)
            Wend

            If sr=-1 ' end of file
                efp=bmx.Find("~n",lastef+1)
                newbmx=newbmx+bmx[efp..]
                'Print "eof="+bmx[efp..]+"=="
                Exit
            EndIf

            rp=bmx.Find("~n",sr+1)
            erp=bmx.Find("~n",er+1)
            fp=bmx.Find("~n",sf+1)
            lastefp=efp
            efp=bmx.Find("~n",ef+1)
            line=bmx[sf..fp]
            comment=bmx[sr..erp]
            url=comment.Find("http://",0)
            If url=-1 Then url=comment.Find("https://",0)
            If bmx[sr-1..sr]<>"'"
                remtext=bmx[sr..erp]
                functext=bmx[sf..efp]
                'Print "remtext="+remtext+"=="
            EndIf

            remdfunc=bmx[rp..efp]
            rf=remdfunc.Find("Rem",0)
            While remdfunc[rf-4..rf]="End " Or remdfunc[rf-3..rf]="End" Or remdfunc[rf-1..rf]="'"
                rf=remdfunc.Find("Rem",rf+1)
            Wend

            If line[0..9]="Function "
                cp=line.Find(":",9)
                cp2=line.Find("(",9)
                If cp>-1 And cp<cp2 Then cp2=cp ' use : pos
                cp3=line.Find("#(",9) ' return literals
                If cp3=-1 Then cp3=line.Find("%(",9)
                If cp3=-1 Then cp3=line.Find("$(",9)
                If cp3>-1 Then cp2=cp3 ' use return literal pos
                command=line[9..cp2]
                filepath=FindFile(command)
                'Print "line="+line+"=="
                Print "command="+command+"=="
                Print "filepath="+filepath+"=="
                If FileType(filepath)=1 ' file, html
                    If ExtractExt(filepath)="html" Or ExtractExt(filepath)="htm"
                        HtmlReadHtml(filepath)
                    EndIf
                EndIf
                If sf>er And rf=-1 Then comment=comment+"~n"+functext ' not rem'd function
            EndIf

            newbmx=newbmx+bmx[lastefp..sr]
            If bmx[sr-1..sr]="'" Or url=-1 Or rf>-1 ' commented or rem without link or rem'd function
                newbmx=newbmx+comment+"~n" ' no change
                'Print "comment="+comment+"=="
            Else
                newbmx=newbmx+"Rem"+bbdoc+param+about+"End Rem~n"+functext ' add doc'd function
            EndIf
            'Print "functext="+functext+"=="

        Wend

        Local outfile:TStream=WriteFile(bmxdestfile)
        WriteString outfile,newbmx
        CloseStream outfile

    End Method

    Method FindFile$( fname$ )

        Local dh:Byte Ptr=ReadDir(htmldocspath)
        If Not dh RuntimeError "failed to read current directory"

        Repeat
            Local temp$=NextFile(dh)
            If temp="" Then Exit ' done
            If temp="." Or temp=".." Continue ' skip
            Local cfile$=htmldocspath+"/"+temp ' current file
            Local fls%=cfile.FindLast("/",0)+1 ' last slash
            Local fld%=cfile.Find(".",fls) ' last dot
            If cfile[fls..fld].ToLower()=fname.ToLower() Then Return cfile
        Forever

        CloseDir dh
    End Method

    Function HtmlReadHtml(path$)

        Local fts%,fte%,fnl%,fnl2%,dot%,comma%,fts2%,see%,lastcomma%,brace%
        Local html$,fta$,hash$,fbr$,brake$,link$,also$

        Local file:TStream=ReadFile(path)
        If Not file RuntimeError "could not open html file e19="+path+"="

        html=ReadString(file,FileSize(path))
        Local fp%=html.Find("<h1>Parameters",0)
        Local fd%=html.Find("<h1>Description",fp+1)
        Local fe%=html.Find("<h1>",fd+1)
        If fe=-1 Then fe=html.Find("<a target",fd+1)

        about="@Description: "+html[fd+4+11..fe]
        param="about: ~n@Parameters: "+html[fp+4+10..fd]

        If fp>0 ' file has parameters

            fts=param.Find("<",0)
            fte=param.Find(">",fts+1)
            While fts>-1 ' strip out html tags
                fbr=param[fts..fts+3]
                If fbr="<br" Then brake="~n~n" Else brake=""
                param=param[..fts]+brake+param[fte+1..]

                fts=param.Find("<",fts+1)
                fte=param.Find(">",fts+1)
            Wend

            fnl=param.Find("~n",0)
            fnl2=param.Find("~n",fnl+1)
            While fnl>-1 ' remove extra newlines
                If fnl2-fnl<2
                    param=param[..fnl]+param[fnl2..]
                EndIf

                fnl=param.Find("~n",fnl+1)
                fnl2=param.Find("~n",fnl+1)
            Wend

        EndIf

        If fd>0 ' file has description

            fts=about.Find("<",0)
            fte=about.Find(">",fts+1)
            While fts>-1 ' strip out html tags
                fta=about[fts..fts+3]
                fts2=about.Find("<",fte+1)
                If fta="<a "
                    about=about[..fts]+"<a href=#"+about[fte+1..fts2]+">"+about[fte+1..]
                ElseIf fta="</a"
                    about=about[..fts]+"</a>"+about[fte+1..]
                Else
                    about=about[..fts]+about[fte+1..]
                EndIf

                fts=about.Find("<",fts+1)
                fte=about.Find(">",fts+1)
            Wend

            fnl=about.Find("~n",0)
            fnl2=about.Find("~n",fnl+1)
            While fnl>-1 ' remove extra newlines
                If fnl2-fnl<2
                    about=about[..fnl]+about[fnl+1..]
                EndIf

                fnl=about.Find("~n",fnl+1)
                fnl2=about.Find("~n",fnl+1)
            Wend

            dot=about.Find(".",0)
            comma=about.Find(",",0)
            If comma>-1 And comma<dot Then dot=comma
            fnl=about[..dot].FindLast("~n",0)
            bbdoc="~nbbdoc: "+about[fnl+1..dot]+"~n"

            also="See also:"
            see=about.Find("See also:",0) ' build links if none there
            fnl=about.Find("~n",see+9)
            If see>-1
                lastcomma=see+9
                comma=about.Find(",",see+9)
                If comma=-1 Then comma=about.Find(".",lastcomma+1)

                While comma>-1
                    fta=about.Find("<a ",lastcomma)
                    If fta>-1 Then Exit

                    If fta=-1
                        brace=0
                        link=about[lastcomma+1..comma].Trim()
                        If link>""
                            brace=link.Find("(",brace+1)
                            If brace>-1 Then link=link[..brace]
                            also=also+" <a href=#"+link+">"+link+"</a>"+about[comma..comma+1]
                        EndIf
                    EndIf

                    lastcomma=comma
                    comma=about.Find(",",comma+1)
                    If comma=-1 Then comma=about.Find(".",lastcomma+1)
                Wend

                If fta=-1 Then about=about[..see]+also+about[fnl..]
            EndIf

        EndIf

        'Print "="+bbdoc+"=="
        'Print "="+param+"=="
        'Print "="+about+"=="
        CloseStream file

    End Function

End Type
BlitzCoder commented:

Thanks for sharing Mark! curious though what are features or "pros" that are still not ported over to OpenB3DMax..

I noticed some still prefer minib3d, perhaps more lightweight and quick installation?

markcwm commented:

Hi Ron,
well pretty much everything in Minib3d has been ported to Openb3dmax, but there are some features in Minib3d Extended that aren't in Openb3dmax, I haven't really had a good look yet though as there's lots of other things to do.

Yes, Minib3d has some big advantages over Openb3dmax:

  • It's easier to modify and extended the code base because it's just Blitzmax, other than the collisions.
  • Minib3d has a lot of code written for it in the past, like Adam Redwood's BatchSprites and Leon Drake's Cal3D mod so again it's easier to turn into a custom 3D engine.
  • Openb3dmax has pointers for all it's fields so it you need to add [0] and that could put people off.
  • Minib3d is also easier to write code for because it has the GC managing everything for you, whereas Openb3d has to be manually maintained like Blitz3D.

I'd need to document these differences somewhere really.

BlitzCoder commented:

Ah great info and that's good to know

didn't know the minib3d GC part before that is also nice.

markcwm commented:

Hi Ron,

I've got an update to this code now but it says there's a one week expiry to editing a topic. This is pretty inconvenient as I don't want anyone using that version now, could you change it to a month please? Thanks.

BlitzCoder commented:

Hey Mark, typically this should be a worklog type if eventually there are planned constant changes where the latest post is always on top compared to topics and then perhaps create a separate discussion for feedback or comments.

It's an advantage that will encourage worklog entries (we currently have a few and now dormant) and it perfectly fits with new or constant update of these type of content.

For now I have now made an exception and already set moderators of respective subforums like you, RemiD and others to edit their own topics with this 1 month extended period. cheers.

markcwm commented:

Hey Ron,

thank you for looking at this and for changing the edit time for mods. :)

Yes this code is a WIP (I'm still not finished) but it's not something I'll be spending that long on, a month or two. I've tagged it as a code archive and I'm wondering if you could set code archives with an extended edit time, as I often used that as a place to store my code on Blitzbasic.com and depending on the type of code I would maybe re-edit it months later, maybe 3 months would do. I realize I was a bit spoilt by Blitzbasic.com as they had no time limit to editing a topic, code archive or worklog but I've seen what can happen when you allow that so I understand the need for it. I would think you need a bit longer for editing a worklog as projects can take years, so maybe 6 months there. My opinion is you don't want to make the edit times too short or you will loose a lot of potential contributors.

markcwm commented:

This is the A to Z links importer. It uses most of the same parsing code as the 3d commands importer and just edits the module about section in the main minib3d.bmx file. This is for convenience to quickly jump to a function without scrolling down the list. Remember to run makedocs after this.

Edit: this should be finished now too, fixed non-Blitz3d functions not added to list (like BackBufferToTex).

' b3ddocsaz2mini.bmx
' this just adds A to Z links to the Minib3d module about section

SuperStrict

Global bmxsrcfile$="inc/functions.bmx"
Global bmxdestfile$="minib3d.bmx"
Global htmldocspath$="../../../help/commands/3d_commands" ' Blitz3D help path

Local t:TBB=New TBB

t.FindImports()

Type TBB

    Global az:TList=CreateList()
    Global azlower:TList=CreateList()
    Global title$="Jump to: "

    Method FindImports$()

        Local file:TStream=ReadFile(bmxsrcfile)
        If Not file RuntimeError "could not open file "+bmxsrcfile

        Local size%=FileSize(bmxsrcfile)
        SeekStream file,0
        Local bmx$=ReadString(file,size)
        CloseStream file

        Local cou%=0,sr%,er%,sf%,ef%,lastef%,rp%,fp%,erp%,efp%,lastefp%,url%,rf%,cp%,cp2%,cp3%
        Local remtext$,functext$,comment$,newbmx$,line$,command$,filepath$,remdfunc$,links$,lastcom$

        Print "Doc A to Z links imported..."
        While sr>-1
            cou:+1
            lastef=ef
            sr=bmx.Find("Rem",sr+1)
            While bmx[sr-4..sr]="End " Or bmx[sr-3..sr]="End" Or bmx[sr-1..sr]="'"
                sr=bmx.Find("Rem",sr+1)
            Wend
            er=bmx.Find("End",sr+1)
            While bmx[er+3..er+7]<>" Rem" And bmx[er+3..er+6]<>"Rem" Or bmx[er-1..er]="'"
                If bmx[er+3..er+7]=" Rem" Or bmx[er+3..er+6]="Rem" Then Exit
                er=bmx.Find("End",er+1)
            Wend
            sf=bmx.Find("Function",sr+1)
            While bmx[sf-4..sf]="End " Or bmx[sf-3..sf]="End" Or bmx[sf-1..sf]="'" 
                sf=bmx.Find("Function",sf+1)
            Wend
            ef=bmx.Find("End",sf+1)
            While bmx[ef+3..ef+12]<>" Function" And bmx[ef+3..ef+11]<>"Function" Or bmx[ef-1..ef]="'"
                If bmx[er+3..er+12]=" Function" Or bmx[er+3..er+11]="Function" Then Exit
                ef=bmx.Find("End",ef+1)
            Wend

            If sr=-1 ' end of file
                Exit
            EndIf

            rp=bmx.Find("~n",sr+1)
            erp=bmx.Find("~n",er+1)
            fp=bmx.Find("~n",sf+1)
            lastefp=efp
            efp=bmx.Find("~n",ef+1)
            line=bmx[sf..fp]
            comment=bmx[sr..erp]
            url=comment.Find("http://",0)
            If url=-1 Then url=comment.Find("https://",0)
            If bmx[sr-1..sr]<>"'"
                remtext=bmx[sr..erp]
                functext=bmx[sf..efp]
                'Print "remtext="+remtext+"=="
            EndIf

            remdfunc=bmx[rp..efp]
            rf=remdfunc.Find("Rem",0)
            While remdfunc[rf-4..rf]="End " Or remdfunc[rf-3..rf]="End" Or remdfunc[rf-1..rf]="'"
                rf=remdfunc.Find("Rem",rf+1)
            Wend

            If line[0..9]="Function "
                cp=line.Find(":",9)
                cp2=line.Find("(",9)
                If cp>-1 And cp<cp2 Then cp2=cp ' use : pos
                cp3=line.Find("#(",9) ' return literals
                If cp3=-1 Then cp3=line.Find("%(",9)
                If cp3=-1 Then cp3=line.Find("$(",9)
                If cp3>-1 Then cp2=cp3 ' use return literal pos
                command=line[9..cp2]
                filepath=FindFile(command)
                'Print "line="+line+"=="
                'Print "command="+command+"=="
                'Print "filepath="+filepath+"=="
                If FileType(filepath)=1 Or (sf>er And rf=-1) ' file or not rem'd function
                    ListAddLast az,command
                    ListAddLast azlower,command.ToLower()
                EndIf
            EndIf

        Wend

        SortList azlower
        links=""
        For Local item:Object=EachIn azlower
            command=String(item)
            'Print "i="+command
            If lastcom[..1]<>command[..1] ' first function name for letter
                For Local item2:Object=EachIn az
                    line=String(item2)
                    If command=line.ToLower()
                        Print line[..1]+"="+line+"=="
                        links:+"<a href=#"+line+">"+line[..1].ToUpper()+"</a> &nbsp;"
                        Exit
                    EndIf
                Next
            EndIf
            lastcom=command
        Next

        Local outfile:TStream=OpenFile(bmxdestfile)
        size=FileSize(bmxdestfile)
        SeekStream outfile,0
        bmx=ReadString(outfile,size)

        line=""
        sr=bmx.Find("Rem",sr+1)
        er=bmx.Find("End Rem",sr+1)
        If er=-1 Then bmx.Find("EndRem",sr+1)
        sf=bmx.Find("about:",sr+1)
        If sf=-1 Then sf=er ; line="about: ~n"
        ef=bmx.Find(title,sr+1)
        If ef=-1 Then ef=er
        newbmx=bmx[..sf]+line+bmx[sf..ef]+title+links+"~n"+bmx[er..]

        SeekStream outfile,0
        WriteString outfile,newbmx
        CloseStream outfile

    End Method

    Method FindFile$( fname$ )

        Local dh:Byte Ptr=ReadDir(htmldocspath)
        If Not dh RuntimeError "failed to read current directory"

        Repeat
            Local temp$=NextFile(dh)
            If temp="" Then Exit ' done
            If temp="." Or temp=".." Continue ' skip
            Local cfile$=htmldocspath+"/"+temp ' current file
            Local fls%=cfile.FindLast("/",0)+1 ' last slash
            Local fld%=cfile.Find(".",fls) ' last dot
            If cfile[fls..fld].ToLower()=fname.ToLower() Then Return cfile
        Forever

        CloseDir dh
    End Method

End Type
BlitzCoder commented:

Sure thing and I see. Ok, will be extending edit time for topics under code archive on my next site update.

I think this will be closer to what the old forums and at the same time have some form of managing existing content or contribution.

By the way, having an older version of the code is also good thing as this acts as a version history or branch.. and fast forward now there are gists (github) which has this version feature and perhaps just provide a link on the topic.

markcwm commented:

Thanks Ron, that will be cool.

Yes, I don't really know what gists are, but yes version control is better, just as long as you can hide the older versions.

Also, I've finished this code now.

BlitzCoder commented:

cheers, just bumped it to 3 months the other day.

Yes, I don't really know what gists are, but yes version control is better, just as long as you can hide the older versions.

https://gist.github.com
as any url resource a unique link will be generated for each gist and there's a Revision tab on the left side in case someone needs to see or use the older versions of your code .

Reply To Topic (minimum 10 characters)

Please log in to reply