Kernel 0.9.1 : SHELL, CSH style scripting.....(wip)

This commit is contained in:
Rémy GIBERT 2017-10-25 17:34:23 +02:00
parent 0c36c71384
commit cf29180a68
4 changed files with 268 additions and 178 deletions

Binary file not shown.

Binary file not shown.

View File

@ -64,7 +64,7 @@ CSH.Run lda #0
cmp #'}' End of block ? cmp #'}' End of block ?
bne .1 bne .1
jsr CSH.CheckStack must be on stack.... jsr CSH.CheckStack must be something on stack....
bcs .9 bcs .9
jsr CSH.Pop was expected, get stacked Cmd... jsr CSH.Pop was expected, get stacked Cmd...
@ -88,7 +88,8 @@ CSH.Run lda #0
bra .9 error, todo : PREOPS ++ --..... bra .9 error, todo : PREOPS ++ --.....
.3 >LDYA L.CSH.KEYWORDS .3 >LDYA L.CSH.KEYWORDS
jsr CSH.Lookup jsr CSH.LookupID
bcs .4 not an internal CSH keyword.... bcs .4 not an internal CSH keyword....
txa txa
@ -184,63 +185,103 @@ CSH.Quit >LDA.G CSH.hBuf
.8 rts .8 rts
*-------------------------------------- *--------------------------------------
CSH.SavePtr >LDYA ZPCSHBufPtr CSH.WHILE
>STYA.G CSH.BufPtrSave CSH.IF jsr CSH.GetCharNB
bcs .9
cmp #'('
bne .9
jsr CSH.GetNextCharNB
bcs .9
jsr CSH.ExpEval
bcs .99
jsr CSH.GetCharNB
bcs .99
cmp #')'
bne .9
jsr CSH.GetNextCharNB
bcs .99
cmp #'{'
bne .9
jsr CSH.IsACC0
bcc .6 eval returned ACC=0, skip {{....}}
jsr CSH.GetNextCharNB Skip '{'
bcs .99
>LDA.G CSH.CmdSave Push "IF" or "WHILE"
tax
jsr CSH.Keyword.start
bcs .99
lda #'}' Tell '}' is expected at the end of block
jsr CSH.Push
bcs .99
rts rts
*--------------------------------------
CSH.RestorePtr >LDYA.G CSH.BufPtrSave
>STYA ZPCSHBufPtr
rts
*--------------------------------------
CSH.Lookup >STYA ZPPtr1
jsr CSH.GetIdentLen .6 ldx #1 expecting 1 '}' for now....
phy Y = kw len .7 jsr CSH.GetNextChar
bcs .9
ldx #0 cmp #'{'
bne .71
.1 lda (ZPPtr1)
beq .9 Ending 0, not found....
pla
pha Get Back Len
cmp (ZPPtr1) Same Len ?
bne .4
tay
.2 lda (ZPPtr1),y
.3 dey
cmp (ZPCSHBufPtr),y
bne .4
tya
bne .2
pla Found keyword...
clc
adc ZPCSHBufPtr ..advance Ptr to char after it..
sta ZPCSHBufPtr
bcc .8
inc ZPCSHBufPtr+1
clc
.8 rts
.4 inx
inx inx
bra .7
lda ZPPtr1 .71 cmp #'}'
bne .7
txa
beq .9
dex
bne .7
jsr CSH.GetNextChar
clc
rts
.9 lda #CSH.E.SYNTAX
sec sec
adc (ZPPtr1) .99 rts
sta ZPPtr1
bcc .1
inc ZPPtr1+1
bra .1
.9 pla CSH.Keyword.Start
jmp (J.CSH.KEYWORDS.START,x)
*--------------------------------------
CSH.IF.START jmp CSH.Push
*--------------------------------------
CSH.WHILE.START pha
>LDA.G CSH.BufPtrSave+1 WHILE : push loop address...
jsr CSH.Push
>LDA.G CSH.BufPtrSave
jsr CSH.Push
pla
jmp CSH.Push
*--------------------------------------
CSH.IF.END jsr CSH.GetNextChar just skip ending '}'
clc
rts
*--------------------------------------
CSH.WHILE.END jsr CSH.Pop
sta ZPCSHBufPtr
jsr CSH.Pop
sta ZPCSHBufPtr+1
clc
rts
*--------------------------------------
CSH.ELSE
CSH.DO
CSH.FOR
CSH.SWITCH
CSH.CASE
CSH.BREAK
CSH.CONTINUE
lda #CSH.E.SYNTAX
sec sec
rts rts
*-------------------------------------- *--------------------------------------
@ -307,108 +348,71 @@ CSH.TYPE >STA.G CSH.ACCT
sec sec
.99 rts .99 rts
*-------------------------------------- *--------------------------------------
CSH.WHILE CSH.SavePtr >LDYA ZPCSHBufPtr
CSH.IF jsr CSH.GetCharNB >STYA.G CSH.BufPtrSave
bcs .9 rts
cmp #'(' *--------------------------------------
bne .9 CSH.RestorePtr >LDYA.G CSH.BufPtrSave
>STYA ZPCSHBufPtr
rts
*--------------------------------------
CSH.LookupID >STYA ZPPtr1
jsr CSH.GetIDLen
bra CSH.Lookup
jsr CSH.GetNextCharNB CSH.LookupOP >STYA ZPPtr1
bcs .9 jsr CSH.GetOPLen
jsr CSH.ExpEval CSH.Lookup phy Y = len
bcs .99
jsr CSH.GetCharNB ldx #0
bcs .99
cmp #')'
bne .9
jsr CSH.GetNextCharNB .1 lda (ZPPtr1)
bcs .99 beq .9 Ending 0, not found....
cmp #'{'
bne .9
>LDA.G CSH.ACC
iny
ora (pData),y
iny
ora (pData),y
iny
ora (pData),y
beq .6 eval returned false, skip {{....}}
jsr CSH.GetNextCharNB Skip '{'
>LDA.G CSH.CmdSave Push "IF" or "WHILE"
cmp #10 WHILE
beq .1 if "IF", no need to push Saved Ptr
pha
>LDA.G CSH.BufPtrSave+1 WHILE : push loop address...
jsr CSH.Push
>LDA.G CSH.BufPtrSave
jsr CSH.Push
pla pla
pha Get Back Len
.1 jsr CSH.Push cmp (ZPPtr1) Same Len ?
bcs .99 bne .4
lda #'}' Tell '}' is expected at the end of block tay
jsr CSH.Push
bcs .99
rts .2 lda (ZPPtr1),y
.6 ldx #1 expecting 1 '}' for now.... .3 dey
cmp (ZPCSHBufPtr),y
bne .4
tya
.7 jsr CSH.GetNextChar bne .2
bcs .9
cmp #'{'
bne .71
inx
bra .7
.71 cmp #'}'
bne .7
txa
beq .9
dex
bne .7
jsr CSH.GetNextChar
pla Found keyword...
clc clc
rts adc ZPCSHBufPtr ..advance Ptr to char after it..
.9 lda #CSH.E.SYNTAX
sec
.99 rts
*--------------------------------------
CSH.IF.END jsr CSH.GetNextChar just skip ending '}'
clc
rts
*--------------------------------------
CSH.WHILE.END jsr CSH.Pop
sta ZPCSHBufPtr sta ZPCSHBufPtr
jsr CSH.Pop bcc .8
sta ZPCSHBufPtr+1 inc ZPCSHBufPtr+1
clc clc
rts .8 rts
*--------------------------------------
CSH.ELSE
CSH.DO
CSH.FOR
CSH.SWITCH
CSH.CASE
CSH.BREAK
CSH.CONTINUE
lda #CSH.E.SYNTAX .4 inx
inx
lda ZPPtr1
sec
adc (ZPPtr1)
sta ZPPtr1
bcc .1
inc ZPPtr1+1
bra .1
.9 pla
sec sec
rts rts
*-------------------------------------- *--------------------------------------
CSH.ExpEval jsr CSH.ZeroACC CSH.ExpEval jsr CSH.ZeroACC
>STA.G CSH.EXPBOP1 A=0
jsr CSH.GetCharNB jsr CSH.GetCharNB
bcs .9 bcs .9
@ -417,13 +421,14 @@ CSH.ExpEval jsr CSH.ZeroACC
cmp #';' cmp #';'
beq .8 beq .8
jsr CSH.IsLetter Fnc or Var ? .10 jsr CSH.IsLetter Fnc or Var ?
bcs .5 bcs .5
jsr CSH.GetVar jsr CSH.GetVar
bcs .1 bcs .4
>DEBUG
jsr CSH.LoadACCFromVar jsr CSH.LoadACCFromVar
bcs .9 bcs .9
@ -433,12 +438,41 @@ CSH.ExpEval jsr CSH.ZeroACC
bcs .9 bcs .9
>LDYA L.CSH.BOPS >LDYA L.CSH.BOPS
jsr CSH.Lookup jsr CSH.LookupOP
bcs .9
>LDA.G CSH.EXPBOP1 previous OP...
bne .2 go check precedence
txa
>STA.G CSH.EXPBOP1
jsr CSH.ACC2ARG
jsr CSH.GetCharNB
bcc .10
.9 lda #CSH.E.SYNTAX
sec
.99 rts
.2 txa
>STA.G CSH.EXPBOP2
>CMP.G CSH.EXPBOP1
bcs .3
* new OP has precedence, stack ACC
bra .8
.1 bra .10
* Old OP has precedence, compute ACC=ARG <BOP> ACC
.3 >LDA.G CSH.EXPBOP1
jsr CSA.Compute
bcs .9
jsr CSH.GetCharNB
bcc .10
.4
bra .9 bra .9
@ -452,10 +486,9 @@ CSH.ExpEval jsr CSH.ZeroACC
.8 clc .8 clc
rts rts
*--------------------------------------
.9 lda #CSH.E.SYNTAX CSA.Compute tax
sec jmp (J.CSH.BOBS,x)
.99 rts
*-------------------------------------- *--------------------------------------
CSH.GetNumInACC >LDA.G CSH.ACCT CSH.GetNumInACC >LDA.G CSH.ACCT
cmp #CSH.TYPE.FLOAT cmp #CSH.TYPE.FLOAT
@ -487,9 +520,11 @@ CSH.ZeroACC lda #0
rts rts
*-------------------------------------- *--------------------------------------
CSH.ACC2ARG
*--------------------------------------
* Vars... * Vars...
*-------------------------------------- *--------------------------------------
CSH.AddVar jsr CSH.GetIdentLen CSH.AddVar jsr CSH.GetIDLen
sec sec
>ADC.G CSH.SymbolsPtr Enough room to store this symbol ? >ADC.G CSH.SymbolsPtr Enough room to store this symbol ?
@ -511,7 +546,7 @@ CSH.AddVar jsr CSH.GetIdentLen
>LDA.G CSH.SymbolsPtr >LDA.G CSH.SymbolsPtr
pha pha
jsr CSH.GetIdentLen jsr CSH.GetIDLen
ply ply
sta (ZPCSHSymbols),y sta (ZPCSHSymbols),y
@ -556,7 +591,7 @@ CSH.AddVar jsr CSH.GetIdentLen
CSH.GetVar >LDYA ZPCSHSymbols CSH.GetVar >LDYA ZPCSHSymbols
>STYA ZPPtr1 >STYA ZPPtr1
jsr CSH.GetIdentLen jsr CSH.GetIDLen
pha pha
.1 lda (ZPPtr1) .1 lda (ZPPtr1)
@ -627,6 +662,8 @@ CSH.LoadACCFromVar
>LEA.G CSH.ACC >LEA.G CSH.ACC
>STYA ZPPtr1 >STYA ZPPtr1
ldy #0
.1 lda (ZPCSHValue),y .1 lda (ZPCSHValue),y
sta (ZPPtr1) sta (ZPPtr1)
inc ZPPtr1 inc ZPPtr1
@ -656,6 +693,8 @@ CSH.StoreACCToVar
>LEA.G CSH.ACC >LEA.G CSH.ACC
>STYA ZPPtr1 >STYA ZPPtr1
ldy #0
.1 lda (ZPPtr1) .1 lda (ZPPtr1)
inc ZPPtr1 inc ZPPtr1
bne .2 bne .2
@ -672,6 +711,38 @@ CSH.StoreACCToVar
sec sec
rts rts
*-------------------------------------- *--------------------------------------
CSH.IsACC0 >LDA.G CSH.ACCT
cmp #CSH.TYPE.FLOAT
bne .1 char,int,long
>LDA.G CSH.ACC
bne .9
.8 clc
rts
.1 tax
lda CSH.TSIZE,x
tax
lda #0
ldy #CSH.ACC
.2 ora (pData),y
iny
dex
bne .2
tax
beq .8
.9 sec
rts
*--------------------------------------
CSH.BOPS.PLUS
clc
rts
*--------------------------------------
* Stack * Stack
*-------------------------------------- *--------------------------------------
CSH.Push pha CSH.Push pha
@ -738,7 +809,7 @@ CSH.GetOPLen ldy #0
.8 tya .8 tya
rts rts
*-------------------------------------- *--------------------------------------
CSH.GetIdentLen ldy #0 CSH.GetIDLen ldy #0
.1 iny .1 iny
lda (ZPCSHBufPtr),y lda (ZPCSHBufPtr),y

View File

@ -85,12 +85,9 @@ J.INTCMDS .DA Cmd.Exec.CD
.DA Cmd.Exec.STARTPROC .DA Cmd.Exec.STARTPROC
.DA Cmd.Exec.TIME .DA Cmd.Exec.TIME
L.CSH.BOPS .DA CSH.BOPS L.CSH.BOPS .DA CSH.BOPS
J.CSH.BOBS .DA CSH.BOPS.PLUS
L.CSH.KEYWORDS .DA CSH.KEYWORDS L.CSH.KEYWORDS .DA CSH.KEYWORDS
J.CSH.KEYWORDS .DA CSH.CHAR J.CSH.KEYWORDS .DA CSH.IF
.DA CSH.INT
.DA CSH.LONG
.DA CSH.FLOAT
.DA CSH.IF
.DA CSH.WHILE .DA CSH.WHILE
.DA CSH.ELSE .DA CSH.ELSE
.DA CSH.DO .DA CSH.DO
@ -99,6 +96,13 @@ J.CSH.KEYWORDS .DA CSH.CHAR
.DA CSH.CASE .DA CSH.CASE
.DA CSH.BREAK .DA CSH.BREAK
.DA CSH.CONTINUE .DA CSH.CONTINUE
.DA CSH.CHAR
.DA CSH.INT
.DA CSH.LONG
.DA CSH.FLOAT
J.CSH.KEYWORDS.START
.DA CSH.IF.START
.DA CSH.WHILE.START
J.CSH.KEYWORDS.END J.CSH.KEYWORDS.END
.DA CSH.IF.END .DA CSH.IF.END
.DA CSH.WHILE.END .DA CSH.WHILE.END
@ -479,6 +483,9 @@ INTCMDS >CSTR "CD"
>CSTR "TIME" >CSTR "TIME"
.HS 00 .HS 00
*-------------------------------------- *--------------------------------------
OPChars.Count .EQ 14
CSH.OPChars >PSTR "!~+-*/%=&|^&<>"
*--------------------------------------
* Pre Operators: + - ! ~ ++ -- * Pre Operators: + - ! ~ ++ --
*-------------------------------------- *--------------------------------------
CSH.PREOOPS >PSTR "+" CSH.PREOOPS >PSTR "+"
@ -491,6 +498,21 @@ CSH.PREOOPS >PSTR "+"
CSH.POSTOPS >PSTR "++" CSH.POSTOPS >PSTR "++"
>PSTR "--" >PSTR "--"
.HS 00 .HS 00
*--------------------------------------
* Assignment Operators: = += -= *= /= %= <<= >>= &= ^= |=
*--------------------------------------
CSH.AOPS >PSTR "="
>PSTR "+="
>PSTR "-="
>PSTR "*="
>PSTR "/="
>PSTR "%="
>PSTR "<<="
>PSTR ">>="
>PSTR "&="
>PSTR "^="
>PSTR "!="
.HS 00
*-- Binary ---- H to L prececence ----- *-- Binary ---- H to L prececence -----
* Arithmetic Operators: * / % * Arithmetic Operators: * / %
* Arithmetic Operators: + - * Arithmetic Operators: + -
@ -521,38 +543,27 @@ CSH.BOPS >PSTR "+"
>PSTR "||" >PSTR "||"
.HS 00 .HS 00
*-------------------------------------- *--------------------------------------
* Assignment Operators: = += -= *= /= %= <<= >>= &= ^= |=
*--------------------------------------
CSH.AOPS >PSTR "="
>PSTR "+="
>PSTR "-="
>PSTR "*="
>PSTR "/="
>PSTR "%="
>PSTR "<<="
>PSTR ">>="
>PSTR "&="
>PSTR "^="
>PSTR "!="
.HS 00
*--------------------------------------
* Reserved Keywords: * Reserved Keywords:
*-------------------------------------- *--------------------------------------
CSH.KEYWORDS >PSTR "char" CSH.KEYWORDS >PSTR "if"
>PSTR "int"
>PSTR "long"
>PSTR "float"
>PSTR "if"
>PSTR "while" >PSTR "while"
>PSTR "else" >PSTR "else"
>PSTR "do" >PSTR "do"
>PSTR "for" >PSTR "for"
>PSTR "switch" >PSTR "switch"
>PSTR "case" >PSTR "case"
>PSTR "break"
>PSTR "continue"
CSH.TYPES >PSTR "char"
>PSTR "int"
>PSTR "long"
>PSTR "float"
.HS 00 .HS 00
*-------------------------------------- *--------------------------------------
OPChars.Count .EQ 14 * int printf ( const char * format, ... );
CSH.OPChars >PSTR "!~+-*/%=&|^&<>" CSH.FUNCTIONS >PSTR "printf"
* float cos ( float x );
>PSTR "cos"
*-------------------------------------- *--------------------------------------
MSG.GREETINGS >CSTR "\r\nA2osX-Shell 0.9.1\r\n\r\n" MSG.GREETINGS >CSTR "\r\nA2osX-Shell 0.9.1\r\n\r\n"
MSG.PROMPT >CSTR "$ " MSG.PROMPT >CSTR "$ "
@ -619,9 +630,17 @@ CSH.hStack .BS 1
CSH.StackPtr .BS 1 CSH.StackPtr .BS 1
CSH.CmdSave .BS 1 CSH.CmdSave .BS 1
CSH.ACCT .BS 1 CSH.ACCT .BS 1
CSH.ACC .BS 5 CSH.ACC .BS 5
CSH.EXPBOP1 .BS 1
CSH.ARGT .BS 1
CSH.ARG .BS 5
CSH.EXPBOP2 .BS 1
DS.END .ED DS.END .ED
*-------------------------------------- *--------------------------------------
MAN MAN