CC:wip, partially working, committing before breaking everything again

This commit is contained in:
burniouf 2022-12-30 17:29:57 +01:00
parent f7681deebe
commit 321b273a0f
20 changed files with 700 additions and 268 deletions

Binary file not shown.

View File

@ -101,14 +101,7 @@ CORE.CompileFile
bcs .9 bcs .9
jsr CORE.CompileLine jsr CORE.CompileLine
bcs .9 bcc CORE.CompileFile
>LDA.G bDebug
bpl CORE.CompileFile
jsr PrintDebugMsg
bra CORE.CompileFile
.9 rts .9 rts
*-------------------------------------- *--------------------------------------
@ -132,9 +125,12 @@ CORE.CompileLine
.2 cmp #'}' End of CPStmt ? .2 cmp #'}' End of CPStmt ?
bne .3 bne .3
jsr CORE.GetNCharNB Skip '}' jsr CORE.GetNCharNBNL Skip '}'
jsr STMT.CPStmt.END jsr STMT.CPStmt.END
bcs .9
jsr CORE.GetCharNBNL
bcc CORE.CompileLine bcc CORE.CompileLine
rts rts
@ -142,7 +138,7 @@ CORE.CompileLine
.3 cmp #';' End of Stmt ? .3 cmp #';' End of Stmt ?
bne .4 bne .4
jsr CORE.GetNCharNB Skip ';' jsr CORE.GetNCharNBNL Skip ';'
jsr STMT.Stmt.END jsr STMT.Stmt.END
bcs .9 bcs .9
@ -410,7 +406,9 @@ CORE.GetCharNBNL
bne CORE.GetNCharNB.RTS bne CORE.GetNCharNB.RTS
jsr FIO.FGetS jsr FIO.FGetS
bcs CORE.GetNCharNB.RTS bcc CORE.GetCharNBNL
rts
*-------------------------------------- *--------------------------------------
CORE.GetNCharNBNL CORE.GetNCharNBNL
jsr CORE.GetNCharNB jsr CORE.GetNCharNB

View File

@ -39,9 +39,7 @@ DECL.TYPEDEF jsr CORE.GetNCharNB
.98 lda #E.CSYN .98 lda #E.CSYN
sec sec
.99 .99 rts
DECL.TYPEDEF.RTS
rts
*-------------------------------------- *--------------------------------------
* X = type qual * X = type qual
*-------------------------------------- *--------------------------------------
@ -86,51 +84,43 @@ DECL.X jsr TYPE.GetTQInYA
.98 lda #E.CSYN .98 lda #E.CSYN
sec sec
.99 rts .99 rts
*--------------------------------------
.7 sec Reset Buffer .7 sec Reset Buffer
*--------------------------------------
DECL.YAC ldx #SYM.SC.STATIC Y,A = Type/Qual DECL.YAC ldx #SYM.SC.STATIC Y,A = Type/Qual
bit bLocalScope
bpl .25
bit #SYM.Q.FUNC someone wants to add a local f() ? bit bLocalScope
bne .98 bpl .22
ldx #SYM.SC.AUTO ldx #SYM.SC.AUTO
.25 jsr SYM.New Y,A=T/Q, X=SC, C=clear/reuse .22 jsr SYM.New Y,A=T/Q, X=SC, C=clear/reuse
bcs .98 OOM or DUP bcs .98 OOM or DUP
.22 jsr CC.GetCharNB jsr SYM.GetTQInYA Y,A = T/Q
bit #SYM.Q.FUNC
bne .8
jsr CC.GetCharNB
bcs .98 bcs .98
cmp #';' cmp #';' no initializer...store SYM
bne .26 beq .28
ldy #SYM.Q cmp #'=' type var = value ?
lda (ZPSymBufPtr),y
and #SYM.Q.FUNC
beq .28 no initializer...store SYM
clc function are already stored
rts
*--------------------------------------
* Initializer
*--------------------------------------
.26 cmp #'=' type var = value ?
bne .98 bne .98
jsr CORE.GetNCharNB skip '=' jsr CORE.GetNCharNB skip '='
bcs .98 bcs .98
jsr SYM.GetTypeInYA expected T/Q jsr SYM.GetTQInYA expected T/Q
jsr EXP.Eval jsr EXP.Eval
bcs .99 bcs .99
jsr SYM.GetAddr1 jsr SYM.GetAddr1
bcs .99 bcs .99
jsr SYM.GetTypeInYA Y,A = T/Q jsr SYM.GetTQInYA Y,A = T/Q
jsr SYM.PopValue Set value to this var jsr SYM.PopValue Set value to this var
.29 bcs .99 .29 bcs .99

View File

@ -1,34 +1,26 @@
NEW NEW
AUTO 3,1 AUTO 3,1
*-------------------------------------- *--------------------------------------
F.Decl ldy #SYM.Q F.Decl stz LocalPtr
lda (ZPSymBufPtr),y
ora #SYM.Q.FUNC
sta (ZPSymBufPtr),y
and #$FC
sta ZPPtr2+1
lda (ZPSymBufPtr) #SYM.T
sta ZPPtr2 T/Q for _RETURN_
stz LocalPtr
jsr SYM.Store Store this f() with no prototype...
bcs .99
jsr SCOPE.New jsr SCOPE.New
bcs .99 bcs .99
lda ZPPtr2+1 #SYM.Q lda (ZPSymBufPtr) #SYM.T
and #$F0 pha
ldy #SYM.Q
lda (ZPSymBufPtr),y
and #SYM.Q.PPPOINTER+SYM.Q.AAARRAY
ply
cpy #SYM.T.VOID
bne .10 bne .10
lda ZPPtr2 #SYM.T tax
cmp #SYM.T.VOID beq .11 function is void
beq .11
.10 jsr F.AddReturnVar .10 jsr F.AddReturnVar Y,A = T/Q
bcs .99 bcs .99
.11 jsr CORE.GetNCharNBNL Skip ( .11 jsr CORE.GetNCharNBNL Skip (
@ -85,20 +77,22 @@ F.Decl ldy #SYM.Q
.6 jsr SYM.Add0000 definition End .6 jsr SYM.Add0000 definition End
bcs .99 bcs .99
ldy #SYM.ArgSize
lda LocalPtr
sta (ZPSymBufPtr),y
jsr CORE.GetNCharNBNL Skip ')' jsr CORE.GetNCharNBNL Skip ')'
bcs .9 bcs .9
cmp #';' cmp #';'
bne .7 bne .7
jsr SCOPE.Close discard local scope jsr SCOPE.Close discard local scope
bcs .99 bcs .99
jmp SYM.Update Store this declaration & exit jsr SYM.Update Store this declaration & exit
bcs .99
jsr CORE.GetNCharNBNL Skip ';'
clc no error even if EOF
rts
*-------------------------------------- *--------------------------------------
.7 cmp #'{' .7 cmp #'{'
bne .9 bne .9
@ -115,7 +109,7 @@ F.Def >LDA.G CC.bInitCode
.1 jsr SYM.SetAddrCCode f() Code starts HERE .1 jsr SYM.SetAddrCCode f() Code starts HERE
jsr SYM.Update jsr SYM.Update Store f() Declaration
bcs .99 bcs .99
lda LocalPtr lda LocalPtr
@ -123,7 +117,18 @@ F.Def >LDA.G CC.bInitCode
bcs .99 bcs .99
>LDYA L.PCC.ENTER >LDYA L.PCC.ENTER
jmp CODE.EmitPCC Store f() Declaration / Start Definition jsr CODE.EmitPCC Start Definition
bcs .99
lda #$ff
>STA.G CC.CmdSave
jsr STMT.New00
bcs .99
jsr STMT.SetTypeCP
bcs .99
.99 rts .99 rts
*-------------------------------------- *--------------------------------------
@ -131,14 +136,15 @@ F.Def.END lda #'X' define EXIT Label
jsr SYM.NewLabelA jsr SYM.NewLabelA
bcs .9 bcs .9
jsr STMT.Close
bcs .9
>LDYA L.PCC.LEAVE >LDYA L.PCC.LEAVE
jsr CODE.EmitPCC jsr CODE.EmitPCC
bcs .9 bcs .9
jsr STMT.Close jsr SCOPE.Close
bcs .9 bcs .9
jmp SCOPE.Close
.9 rts .9 rts
*-------------------------------------- *--------------------------------------
@ -193,6 +199,8 @@ F.AddReturnVar ldx ZPLineBufPtr
ldx ZPLineBufPtr+1 ldx ZPLineBufPtr+1
phx phx
>STYA ZPPtr2 Y,A = T/Q
>LDYA L.CC._RETURN_ >LDYA L.CC._RETURN_
>STYA ZPLineBufPtr >STYA ZPLineBufPtr

View File

@ -102,6 +102,9 @@ FIO.FOpen phy
FIO.FGetS >LDYA.G LineBufPtr FIO.FGetS >LDYA.G LineBufPtr
>STYA ZPLineBufPtr >STYA ZPLineBufPtr
lda #0
sta (ZPLineBufPtr) set to Empty line
>LDA.G LineCntPtr >LDA.G LineCntPtr
tay tay
lda (pData),y lda (pData),y

View File

@ -3,7 +3,7 @@ NEW
*-------------------------------------- *--------------------------------------
* Built in Keywords * Built in Keywords
*-------------------------------------- *--------------------------------------
KW.IF jsr STMT.NewCPS00 KW.IF jsr SCOPE.New
bcs .99 bcs .99
jsr CC.GetCharNB jsr CC.GetCharNB
@ -34,29 +34,27 @@ KW.IF jsr STMT.NewCPS00
cmp #')' cmp #')'
bne .9 bne .9
jmp STMT.SetCPSType jsr STMT.New00
bcs .99
jmp STMT.SetType
.9 lda #E.CSYN .9 lda #E.CSYN
sec sec
.99 rts .99 rts
*-------------------------------------- *--------------------------------------
KW.IF.END jsr CORE.GetCharNBNL KW.IF.END jsr STMT.Close
bcs .1 bcs .99
cmp #';'
beq .1
>LDYA L.CC.KW2.IF Check allowed KW for IF.... >LDYA L.CC.KW2.IF Check allowed KW for IF....
jsr CC.LookupID jsr CC.LookupID
bcc .2 bcc .2
.1 lda #'E' define ELSE Label lda #'E' define ELSE Label
jsr SYM.NewLabelA jsr SYM.NewLabelA
bcs .99 bcs .99
jmp STMT.Close jmp SCOPE.Close
rts
*-------------------------------------- *--------------------------------------
.2 lda #'X' .2 lda #'X'
jsr SYM.LookupLabelA jsr SYM.LookupLabelA
@ -70,11 +68,13 @@ KW.IF.END jsr CORE.GetCharNBNL
jsr SYM.NewLabelA jsr SYM.NewLabelA
bcs .99 bcs .99
lda #KW.ELSE.ID replace IF by ELSE keyword lda #KW.ELSE.ID
ldy CStackPtr >STA.G CC.CmdSave
sta (ZPCCStack),y
jmp STMT.SetCPSType reuse IF STMT jsr STMT.New00
bcs .99
jmp STMT.SetType
.9 lda #E.CSYN .9 lda #E.CSYN
sec sec
@ -84,15 +84,21 @@ KW.ELSE lda #E.CSYN illegal
sec sec
rts rts
*-------------------------------------- *--------------------------------------
KW.ELSE.END lda #'X' define EXIT Label KW.ELSE.END jsr STMT.Close
bcs .99
lda #'X' define EXIT Label
jsr SYM.NewLabelA jsr SYM.NewLabelA
bcs .99 bcs .99
jmp STMT.Close jmp SCOPE.Close
.99 rts .99 rts
*-------------------------------------- *--------------------------------------
KW.WHILE lda #'C' define CONT Label KW.WHILE jsr SCOPE.New
bcs .99
lda #'C' define CONT Label
jsr SYM.NewLabelA jsr SYM.NewLabelA
bcs .99 bcs .99
@ -123,17 +129,20 @@ KW.WHILE lda #'C' define CONT Label
cmp #')' cmp #')'
bne .9 bne .9
jsr STMT.NewCPS00 jsr STMT.New00
bcs .99 bcs .99
jmp STMT.SetCPSType jmp STMT.SetType
.9 lda #E.CSYN .9 lda #E.CSYN
sec sec
.99 rts .99 rts
*-------------------------------------- *--------------------------------------
KW.WHILE.END >LDYA L.PCC.SLEEP KW.WHILE.END jsr STMT.Close
bcs .99
>LDYA L.PCC.SLEEP
jsr CODE.EmitPCC jsr CODE.EmitPCC
bcs .99 bcs .99
@ -147,13 +156,9 @@ KW.WHILE.END >LDYA L.PCC.SLEEP
lda #'B' define BREAK Label lda #'B' define BREAK Label
jsr SYM.NewLabelA jsr SYM.NewLabelA
bcs .99
jsr SCOPE.Close jmp SCOPE.Close
bcs .99
jmp STMT.Close
.99 rts .99 rts
*-------------------------------------- *--------------------------------------
KW.DO jsr SCOPE.New KW.DO jsr SCOPE.New
@ -163,14 +168,17 @@ KW.DO jsr SCOPE.New
jsr SYM.NewLabelA jsr SYM.NewLabelA
bcs .99 bcs .99
jsr STMT.NewCPS00 jsr STMT.New00
bcs .99 bcs .99
jmp STMT.SetCPSType jmp STMT.SetType
.99 rts .99 rts
*-------------------------------------- *--------------------------------------
KW.DO.END >LDYA L.CC.KW2.DO Check allowed KW for DO.... KW.DO.END jsr STMT.Close
bcs .99
>LDYA L.CC.KW2.DO Check allowed KW for DO....
jsr CC.LookupID jsr CC.LookupID
bcs .9 bcs .9
@ -196,23 +204,20 @@ KW.DO.END >LDYA L.CC.KW2.DO Check allowed KW for DO....
jsr CODE.TOABSYX jsr CODE.TOABSYX
bcs .99 bcs .99
lda #'B' define BREAK Label
jsr SYM.NewLabelA
bcs .99
jsr CC.GetCharNB jsr CC.GetCharNB
bcs .99 bcs .99
cmp #')' cmp #')'
bne .9 bne .9
jsr CORE.GetNCharNB jsr CORE.GetNCharNB skip ')'
bcs .9 bcs .9
jsr SCOPE.Close lda #'B' define BREAK Label
jsr SYM.NewLabelA
bcs .99 bcs .99
jmp STMT.Close jmp SCOPE.Close
.9 lda #E.CSYN .9 lda #E.CSYN
sec sec
@ -245,7 +250,7 @@ KW.FOR jsr CC.GetCharNB
jsr SCOPE.New jsr SCOPE.New
bcs .19 bcs .19
>LDYA L.CC.TYPEQUAL >LDYA L.CC.TYPEQUAL
jsr CC.LookupID jsr CC.LookupID
bcs .1 bcs .1
@ -328,10 +333,10 @@ KW.FOR jsr CC.GetCharNB
jsr SYM.NewLabelA jsr SYM.NewLabelA
bcs .99 bcs .99
jsr STMT.NewCPS00 jsr STMT.New00
bcs .9 bcs .9
jmp STMT.SetCPSType jmp STMT.SetType
.9 lda #E.CSYN .9 lda #E.CSYN
sec sec
@ -342,15 +347,15 @@ KW.FOR.END lda #$60
jsr CODE.EmitByte set RTS for JSR code; jsr CODE.EmitByte set RTS for JSR code;
bcs .99 bcs .99
jsr STMT.Close
bcs .99
lda #'B' define BREAK Label lda #'B' define BREAK Label
jsr SYM.NewLabelA jsr SYM.NewLabelA
bcs .99 bcs .99
jsr STMT.Close jmp SCOPE.Close FOR ()
bcs .99
jmp SCOPE.Close
.99 rts .99 rts
*-------------------------------------- *--------------------------------------
KW.SWITCH jsr CC.GetCharNB KW.SWITCH jsr CC.GetCharNB
@ -384,6 +389,7 @@ KW.SWITCH jsr CC.GetCharNB
.1 >LDYAI 256 .1 >LDYAI 256
>SYSCALL GetMem >SYSCALL GetMem
bcs .99 bcs .99
txa txa
jsr CC.Push push CPS.hMEM jsr CC.Push push CPS.hMEM
@ -391,7 +397,7 @@ KW.SWITCH jsr CC.GetCharNB
jsr CC.Push push CPS.MemPtr jsr CC.Push push CPS.MemPtr
bcs .99 bcs .99
jsr STMT.NewCPS jsr STMT.New
bcs .99 bcs .99
jsr CC.GetCharNB jsr CC.GetCharNB
@ -400,15 +406,15 @@ KW.SWITCH jsr CC.GetCharNB
cmp #')' cmp #')'
bne .98 bne .98
jsr STMT.SetType {
bcs .99
lda #'J' lda #'J'
jsr SYM.LookupLabelA jsr SYM.LookupLabelA
bcs .99 bcs .99
lda #$4C emit JMP JmpTable lda #$4C emit JMP JmpTable
jsr CODE.TOABSYX jmp CODE.TOABSYX
bcs .99
jmp STMT.SetCPSType
.97 lda #E.TMISMATCH .97 lda #E.TMISMATCH
sec sec
@ -479,7 +485,7 @@ KW.SWITCH.END lda #'J' define JMP Label
.2 >LDYA L.PCC.Pop16 .2 >LDYA L.PCC.Pop16
jsr CODE.EmitPCC jsr CODE.EmitPCC
bcs .99 bcs .99
lda #'D' lda #'D'
jsr SYM.LookupLabelA jsr SYM.LookupLabelA
bcs .3 bcs .3
@ -500,7 +506,7 @@ KW.SWITCH.END lda #'J' define JMP Label
lda (ZPCCStack),y lda (ZPCCStack),y
>SYSCALL FreeMem >SYSCALL FreeMem
jmp STMT.Close jmp STMT.Close SWITCH ()
.99 rts .99 rts
*-------------------------------------- *--------------------------------------
@ -627,22 +633,22 @@ KW.RETURN ldx ZPLineBufPtr
>LDYA L.CC._RETURN_ >LDYA L.CC._RETURN_
>STYA ZPLineBufPtr >STYA ZPLineBufPtr
jsr SYM.Lookup jsr SYM.Lookup
plx plx
stx ZPLineBufPtr+1 stx ZPLineBufPtr+1
plx plx
stx ZPLineBufPtr stx ZPLineBufPtr
bcs .99 bcs .99
ldy #SYM.Q ldy #SYM.Q
lda (ZPLookupSymPtr),y lda (ZPLookupSymPtr),y
pha pha
lda (ZPLookupSymPtr) SYM.T lda (ZPLookupSymPtr) SYM.T
tay tay
pla pla
jsr EXP.Eval jsr EXP.Eval
bcs .99 bcs .99
@ -665,7 +671,7 @@ KW.RETURN ldx ZPLineBufPtr
.9 lda #E.CSYN .9 lda #E.CSYN
sec sec
.99 rts .99 rts
*-------------------------------------- *--------------------------------------
KW.SIZEOF KW.SIZEOF
lda #E.CSYN lda #E.CSYN

View File

@ -21,7 +21,7 @@ CC.Link >LDYA L.MSG.LINKING
>PUSHB.G CC.hSyms >PUSHB.G CC.hSyms
>PUSHW ZPPtr1 SymID >PUSHW ZPPtr1 SymID
>PUSHW ZPSymBufPtr >PUSHW ZPSymBufPtr
>PUSHWI $ffff All >PUSHWI 65535 All
>PUSHWZ from Start >PUSHWZ from Start
>SYSCALL SListGetData >SYSCALL SListGetData
bcs .99 bcs .99

View File

@ -29,10 +29,18 @@ SCOPE.New ldy ScopeIdx
.DO _DBG_SCOPE=1 .DO _DBG_SCOPE=1
>PUSHW L.MSG.DEBUG.SCIN >PUSHW L.MSG.DEBUG.SCIN
jsr SCOPE.Push jsr SCOPE.Push
lda ScopeIdx
sec
sbc #CC.ScopeIDs
lsr
>PUSHA
>PUSHB LocalPtr >PUSHB LocalPtr
>PUSHB LocalFrame >PUSHB LocalFrame
>PUSHBI 4 >PUSHBI 5
>SYSCALL PrintF >SYSCALL PrintF
* >DEBUG
.FIN .FIN
clc clc
@ -59,12 +67,18 @@ SCOPE.Close .DO _DBG_SCOPE=1
.DO _DBG_SCOPE=1 .DO _DBG_SCOPE=1
lda ScopeIdx
sec
sbc #CC.ScopeIDs
lsr
>PUSHA
>PUSHB LocalPtr >PUSHB LocalPtr
>PUSHB LocalFrame >PUSHB LocalFrame
jsr SCOPE.Push jsr SCOPE.Push
>PUSHBI 6 >PUSHBI 7
>SYSCALL PrintF >SYSCALL PrintF
>DEBUG
.FIN .FIN
clc clc

View File

@ -127,7 +127,7 @@ STMT.Stmt.END ldy CStackPtr
lda (ZPCCStack),y lda (ZPCCStack),y
bmi STMT.POP.8 local F context bmi STMT.POP.8 local F context
* in an istruction ... * in an instruction ...
iny CPS.TERM iny CPS.TERM
lda (ZPCCStack),y lda (ZPCCStack),y
cmp #'}' cmp #'}'
@ -162,14 +162,14 @@ STMT.End ldy CStackPtr CPS.KW
tax tax
jmp (J.CC.KW.END,x) jmp (J.CC.KW.END,x)
*-------------------------------------- *--------------------------------------
STMT.NewCPS00 lda #0 STMT.New00 lda #0
jsr CC.Push CPS.hMEM jsr CC.Push CPS.hMEM
bcs STMT.NewCPS.RTS bcs STMT.New.RTS
jsr CC.Push CPS.MemPtr jsr CC.Push CPS.MemPtr
bcs STMT.NewCPS.RTS bcs STMT.New.RTS
STMT.NewCPS lda LocalFrame STMT.New lda LocalFrame
jsr CC.Push jsr CC.Push
bcs .99 bcs .99
@ -185,44 +185,44 @@ STMT.NewCPS lda LocalFrame
jmp CC.Push jmp CC.Push
.99 .99
STMT.NewCPS.RTS rts STMT.New.RTS rts
*-------------------------------------- *--------------------------------------
STMT.SetCPSType jsr CORE.GetNCharNBNL STMT.SetType jsr CORE.GetNCharNBNL
bcs .9 bcs STMT.SetType.9
ldx #';' ldx #';'
cmp #'{' cmp #'{'
bne .1 bne STMT.SetType.1
jsr CORE.GetNCharNB skip '{' STMT.SetTypeCP jsr CORE.GetNCharNB skip '{'
bcs .99 bcs STMT.SetType.9
jsr SCOPE.New jsr SCOPE.New
bcs .99 bcs STMT.New.RTS
lda #'F' lda #'F'
jsr SYM.LookupLabelA jsr SYM.LookupLabelA
bcs .99 bcs STMT.New.RTS
txa txa
jsr CODE.nAddLocal jsr CODE.nAddLocal
bcs .99 bcs STMT.New.RTS
ldx #'}' ldx #'}'
.1 txa STMT.SetType.1 txa
ldy CStackPtr ldy CStackPtr
iny CPS.TERM iny CPS.TERM
sta (ZPCCStack),y sta (ZPCCStack),y
.8 clc clc
rts rts
.9 lda #E.CSYN STMT.SetType.9 lda #E.CSYN
sec sec
.99 rts rts
*-------------------------------------- *--------------------------------------
STMT.Close ldy CStackPtr CPS.KW STMT.Close ldy CStackPtr CPS.KW
iny CPS.TERM iny CPS.TERM
@ -234,6 +234,10 @@ STMT.Close ldy CStackPtr CPS.KW
jsr SYM.NewLabelA jsr SYM.NewLabelA
bcs .99 bcs .99
lda LocalFrame
jsr CODE.AddLocal
bcs .99
lda CStackPtr lda CStackPtr
clc clc
adc #CPS.LocalPtr adc #CPS.LocalPtr

View File

@ -10,9 +10,29 @@ SYM.New >STYA ZPPtr2 T/Q
stx ZPPtr3 SC stx ZPPtr3 SC
bit bPass2 bit bPass2
bpl SYM.New.1 bmi SYM.New.Pass2
* PASS 2 *--------------------------------------
SYM.New.Pass1 jsr SYM.BufInitYAXC set buf according C
>PUSHB.G CC.hSyms >PUSHB.G CC.hSyms
>PUSHW ZPLineBufPtr
jsr SCOPE.Push
>SYSCALL SListNewKey
bcs SYM.New.9
>STYA.G CC.SymID Y,A = KeyID
jsr CC.SkipX X = KeyLen
.DO _DBG_SYM=1
jsr SYM.DEBUGN
.FIN
bra SYM.New.2
SYM.New.9 rts
*--------------------------------------
SYM.New.Pass2 >PUSHB.G CC.hSyms
>PUSHW ZPLineBufPtr >PUSHW ZPLineBufPtr
jsr SCOPE.Push jsr SCOPE.Push
>SYSCALL SListLookup >SYSCALL SListLookup
@ -28,23 +48,10 @@ SYM.New >STYA ZPPtr2 T/Q
>PUSHWI 65535 all >PUSHWI 65535 all
>PUSHWZ From Start >PUSHWZ From Start
>SYSCALL SListGetData >SYSCALL SListGetData
bcc SYM.New.2 bcs SYM.New.9
SYM.New.9 rts
*--------------------------------------
SYM.New.1 jsr SYM.BufInitYAXC set buf according C
>PUSHB.G CC.hSyms
>PUSHW ZPLineBufPtr
jsr SCOPE.Push
>SYSCALL SListNewKey
bcs SYM.New.9
>STYA.G CC.SymID Y,A = KeyID
jsr CC.SkipX X = KeyLen
.DO _DBG_SYM=1 .DO _DBG_SYM=1
jsr SYM.DEBUG0 jsr SYM.DEBUGG
.FIN .FIN
*-------------------------------------- *--------------------------------------
SYM.New.2 jsr CC.GetCharNB SYM.New.2 jsr CC.GetCharNB
@ -63,6 +70,17 @@ SYM.New.2 jsr CC.GetCharNB
.1 cmp #'(' .1 cmp #'('
bne SYM.NewV bne SYM.NewV
jsr SYM.GetSymSizeOfInAX
jsr SYM.SetSizeOf
ldy #SYM.Q
lda (ZPSymBufPtr),y
ora #SYM.Q.FUNC
sta (ZPSymBufPtr),y
jsr SYM.Store Store this f() with no prototype...
bcs .99
jmp F.Decl jmp F.Decl
.98 lda #E.CSYN .98 lda #E.CSYN
@ -141,12 +159,7 @@ SYM.SetAddr ldy #SYM.SizeOf
jsr SYM.GetSymSizeOfInAX jsr SYM.GetSymSizeOfInAX
jsr SYM.SetSizeOf jsr SYM.SetSizeOf
.1 ldy #SYM.Q .1 ldy #SYM.SC
lda (ZPSymBufPtr),y
and #SYM.Q.FUNC
bne .9
ldy #SYM.SC
lda (ZPSymBufPtr),y lda (ZPSymBufPtr),y
beq SYM.SetAddrG SYM.SC.STATIC beq SYM.SetAddrG SYM.SC.STATIC
@ -186,17 +199,13 @@ SYM.SetAddrL ldy #SYM.SizeOf+1
bne .9 bne .9
lda LocalPtr lda LocalPtr
tax
clc clc
dey SYM.SizeOf dey SYM.SizeOf
adc (ZPSymBufPtr),y adc (ZPSymBufPtr),y
bcs .9 bcs .9
sta LocalPtr sta LocalPtr
txa
ldy #SYM.Addr ldy #SYM.Addr
sta (ZPSymBufPtr),y sta (ZPSymBufPtr),y
@ -466,17 +475,16 @@ SYM.Store clc
bit bPass2 bit bPass2
bmi .8 bmi .8
php php
.DO _DBG_SYM=1 .DO _DBG_SYM=1
bcc .10 bcc .10
jsr SYM.DEBUG1 jsr SYM.DEBUGU
bra .11 bra .11
.10 .10
jsr SYM.DEBUG2 jsr SYM.DEBUGS
.11 .FIN .11 .FIN
>PUSHB.G CC.hSyms >PUSHB.G CC.hSyms
@ -506,8 +514,20 @@ SYM.Store clc
.3 >SYSCALL SListSetData .3 >SYSCALL SListSetData
rts rts
.8 clc .8 bcc .9
rts
>PUSHB.G CC.hSyms
>PUSHW.G CC.SymID
>PUSHW ZPSymBufPtr
>PUSHWI 65535 all
>PUSHWZ From Start
>SYSCALL SListGetData
.DO _DBG_SYM=1
bcs .9
jsr SYM.DEBUGG
.FIN
.9 rts
*-------------------------------------- *--------------------------------------
SYM.Lookup >LDA.G CC.LookupIdx SYM.Lookup >LDA.G CC.LookupIdx
@ -573,15 +593,15 @@ SYM.Lookup >LDA.G CC.LookupIdx
* clc * clc
rts rts
*-------------------------------------- *--------------------------------------
* "B"reak * "_B"reak
* "C"ontinue * "_C"ontinue
* "D"efault * "_D"efault
* "E"lse * "_E"lse
* "F"rameSize * "_F"rameSize
* "J"umptable * "_J"umpTable
* "L"oop * "_L"oop
* "S"statement * "_S"statement
* e"X"it * e"_X"it
*-------------------------------------- *--------------------------------------
SYM.NewLabelA bit bPass2 SYM.NewLabelA bit bPass2
bpl .10 bpl .10
@ -621,7 +641,7 @@ SYM.NewLabelA bit bPass2
.1 jsr SYM.SetAddrCCode .1 jsr SYM.SetAddrCCode
.2 .DO _DBG_SYM=1 .2 .DO _DBG_SYM=1
jsr SYM.DEBUG0 jsr SYM.DEBUGN
.FIN .FIN
>PUSHB.G CC.hSyms >PUSHB.G CC.hSyms
@ -636,7 +656,7 @@ SYM.NewLabelA bit bPass2
.DO _DBG_SYM=1 .DO _DBG_SYM=1
bcs .99 bcs .99
jsr SYM.DEBUG2 jsr SYM.DEBUGS
.FIN .FIN
.99 rts .99 rts
*-------------------------------------- *--------------------------------------
@ -684,20 +704,34 @@ SYM.LookupLabelA
tya tya
>PUSHA KeyID.LO >PUSHA KeyID.LO
>PUSHW ZPSymBufPtr >PUSHWZ allocate
>PUSHWI 65535 all >PUSHWI 65535 all
>PUSHWZ From Start >PUSHWZ From Start
>SYSCALL SListGetData >SYSCALL SListGetData
bcs .99 bcs .99
ldy #SYM.Addr phx
lda (ZPSymBufPtr),y
txa
>SYSCALL GetMemPtr
>STYA ZPLookupPtr
tax plx
ldy #SYM.Addr
lda (ZPLookupPtr),y
pha
iny iny
lda (ZPSymBufPtr),y lda (ZPLookupPtr),y
tay pha
txa
>SYSCALL FreeMem
ply
plx
* clc * clc
@ -804,7 +838,7 @@ SYM.PopValue jsr SYM.GetYASizeOfInAX
*-------------------------------------- *--------------------------------------
* out : Y,A = T/Q * out : Y,A = T/Q
*-------------------------------------- *--------------------------------------
SYM.GetTypeInYA ldy #SYM.Q SYM.GetTQInYA ldy #SYM.Q
lda (ZPSymBufPtr),y lda (ZPSymBufPtr),y
pha pha
lda (ZPSymBufPtr) lda (ZPSymBufPtr)
@ -874,7 +908,7 @@ SYM.GetYASizeOfInAX
clc clc
rts rts
*-------------------------------------- *--------------------------------------
* in/out : A,X,C = size * in/out : A,X = size
*-------------------------------------- *--------------------------------------
SYM.SetSizeOf ldy #SYM.SizeOf SYM.SetSizeOf ldy #SYM.SizeOf
sta (ZPSymBufPtr),y sta (ZPSymBufPtr),y
@ -903,7 +937,7 @@ SYM.SetAddrYA phy
rts rts
*-------------------------------------- *--------------------------------------
.DO _DBG_SYM=1 .DO _DBG_SYM=1
SYM.DEBUG0 >PUSHW L.MSG.DEBUG.SYMN SYM.DEBUGN >PUSHW L.MSG.DEBUG.SYMN
>PUSHW.G CC.SymID >PUSHW.G CC.SymID
jsr SCOPE.Push jsr SCOPE.Push
lda (ZPSymBufPtr) lda (ZPSymBufPtr)
@ -911,30 +945,53 @@ SYM.DEBUG0 >PUSHW L.MSG.DEBUG.SYMN
ldy #1 ldy #1
lda (ZPSymBufPtr),y lda (ZPSymBufPtr),y
>PUSHA >PUSHA
>PUSHBI 6 iny
lda (ZPSymBufPtr),y
>PUSHA
>PUSHBI 7
>SYSCALL Printf >SYSCALL Printf
>DEBUG * >DEBUG
rts rts
SYM.DEBUG1 >PUSHW L.MSG.DEBUG.SYMU SYM.DEBUGU >PUSHW L.MSG.DEBUG.SYMU
>PUSHW.G CC.SymID >PUSHW.G CC.SymID
lda (ZPSymBufPtr) lda (ZPSymBufPtr)
>PUSHA >PUSHA
ldy #1 ldy #1
lda (ZPSymBufPtr),y lda (ZPSymBufPtr),y
>PUSHA >PUSHA
>PUSHBI 4 iny
lda (ZPSymBufPtr),y
>PUSHA
>PUSHBI 5
>SYSCALL Printf >SYSCALL Printf
rts rts
SYM.DEBUG2 >PUSHW L.MSG.DEBUG.SYMS SYM.DEBUGS >PUSHW L.MSG.DEBUG.SYMS
>PUSHW.G CC.SymID >PUSHW.G CC.SymID
lda (ZPSymBufPtr) lda (ZPSymBufPtr)
>PUSHA >PUSHA
ldy #1 ldy #1
lda (ZPSymBufPtr),y lda (ZPSymBufPtr),y
>PUSHA >PUSHA
>PUSHBI 4 iny
lda (ZPSymBufPtr),y
>PUSHA
>PUSHBI 5
>SYSCALL Printf
rts
SYM.DEBUGG >PUSHW L.MSG.DEBUG.SYMG
>PUSHW.G CC.SymID
lda (ZPSymBufPtr)
>PUSHA
ldy #1
lda (ZPSymBufPtr),y
>PUSHA
iny
lda (ZPSymBufPtr),y
>PUSHA
>PUSHBI 5
>SYSCALL Printf >SYSCALL Printf
rts rts
.FIN .FIN

View File

@ -55,7 +55,7 @@ SYM.SizeOf .EQ 4
SYM.Addr .EQ 6 SYM.Addr .EQ 6
SYM.BitO .EQ 8 SYM.BitO .EQ 8
SYM.BitW .EQ 9 SYM.BitW .EQ 9
SYM.ArgSize .EQ 10 SYM.ScopeID .EQ 10
* *
* *
SYM.Def .EQ 14 Funtions : fTQ,a1TQ,a2TQ.... SYM.Def .EQ 14 Funtions : fTQ,a1TQ,a2TQ....
@ -144,11 +144,11 @@ L.MSG.READING .DA MSG.READING
L.MSG.LINKING .DA MSG.LINKING L.MSG.LINKING .DA MSG.LINKING
L.MSG.LINKING2 .DA MSG.LINKING2 L.MSG.LINKING2 .DA MSG.LINKING2
L.MSG.GENERATING .DA MSG.GENERATING L.MSG.GENERATING .DA MSG.GENERATING
L.MSG.DEBUG .DA MSG.DEBUG
.DO _DBG_SYM=1 .DO _DBG_SYM=1
L.MSG.DEBUG.SYMN .DA MSG.DEBUG.SYMN L.MSG.DEBUG.SYMN .DA MSG.DEBUG.SYMN
L.MSG.DEBUG.SYMU .DA MSG.DEBUG.SYMU L.MSG.DEBUG.SYMU .DA MSG.DEBUG.SYMU
L.MSG.DEBUG.SYMS .DA MSG.DEBUG.SYMS L.MSG.DEBUG.SYMS .DA MSG.DEBUG.SYMS
L.MSG.DEBUG.SYMG .DA MSG.DEBUG.SYMG
.FIN .FIN
.DO _DBG_SCOPE=1 .DO _DBG_SCOPE=1
L.MSG.DEBUG.SCIN .DA MSG.DEBUG.SCIN L.MSG.DEBUG.SCIN .DA MSG.DEBUG.SCIN
@ -389,7 +389,7 @@ CS.RUN.CLOOP jsr CORE.CompileFile
*-------------------------------------- *--------------------------------------
.1 jsr PrintSummary .1 jsr PrintSummary
bcs .99 bcs .99
>DEBUG
jsr CC.Link jsr CC.Link
bcs .99 bcs .99
>DEBUG >DEBUG
@ -456,7 +456,7 @@ CS.RUN.ARGS inc ArgIndex
bra .90 bra .90
.2 cpx #4 .2 cpx #2 LIB
bcc .3 bcc .3
inc ArgIndex inc ArgIndex
@ -537,9 +537,16 @@ PrintVerboseMsg
.DO _DBG_SCOPE=1 .DO _DBG_SCOPE=1
>PUSHW L.MSG.DEBUG.SC >PUSHW L.MSG.DEBUG.SC
jsr SCOPE.Push jsr SCOPE.Push
lda ScopeIdx
sec
sbc #CC.ScopeIDs
lsr
>PUSHA
>PUSHB LocalPtr >PUSHB LocalPtr
>PUSHB LocalFrame >PUSHB LocalFrame
>PUSHBI 4 >PUSHBI 5
>SYSCALL PrintF >SYSCALL PrintF
* >DEBUG * >DEBUG
.FIN .FIN
@ -565,49 +572,6 @@ PrintVerboseMsg
rts rts
*-------------------------------------- *--------------------------------------
PrintDebugMsg >PUSHW L.MSG.DEBUG
>PUSHW ZPCCCode
>PUSHW ZPCCConst
>PUSHW ZPCCData
lda pStack
clc
adc #8
pha
lda pStack+1
adc #0
>PUSHA
pla
>PUSHA
>PUSHB LocalPtr
>PUSHW ZPCCStack
>PUSHB CStackPtr
tay
beq .1
lda (ZPCCStack),y
pha
iny
lda (ZPCCStack),y
ply
.1 >PUSHYA
lda ScopeIdx
sec
sbc #CC.ScopeIDs
lsr
>PUSHA
>PUSHBI 15
>SYSCALL PrintF
>DEBUG
rts
*--------------------------------------
PrintErrorMsg >LDA.G CC.hDefineBuf PrintErrorMsg >LDA.G CC.hDefineBuf
beq .10 beq .10
@ -685,24 +649,22 @@ CS.END
*-------------------------------------- *--------------------------------------
MSG.GREETINGS .CZ "\r\nA2osX C Compiler %d.%d\r\n\r\n" MSG.GREETINGS .CZ "\r\nA2osX C Compiler %d.%d\r\n\r\n"
MSG.USAGE .CS "Usage : CC <option> srcfile.c dstfile\r\n" MSG.USAGE .CS "Usage : CC <option> srcfile.c dstfile\r\n"
.CS " -D : Debug mode\r\n"
.CS " -V : Verbose output\r\n" .CS " -V : Verbose output\r\n"
.CZ " -L Libname1 -L Libname2 ...\r\n" .CZ " -L Libname1 -L Libname2 ...\r\n"
MSG.READING .CZ "*** Reading file: %s\r\n" MSG.READING .CZ "*** Reading file: %s\r\n"
MSG.LINKING .CZ "*** Linking..." MSG.LINKING .CZ "*** Linking..."
MSG.LINKING2 .CZ "*** %H:%H:%18s T/Q=%h/%h, SC=%h, Def=%h, SizeOf=%H, @=%H\r\n" MSG.LINKING2 .CZ "*** %H:%H:%18s T/Q=%h/%h, SC=%h, Def=%h, SizeOf=%H, @=%H\r\n"
MSG.GENERATING .CZ "*** Generating: %s\r\n" MSG.GENERATING .CZ "*** Generating: %s\r\n"
MSG.DEBUG .CS "*** pCode=%H, pConst=%H, pData=%H, pStack=%H\r\n"
.CZ " LSP=%h, CSP=%H:%h>%h:%h, ScopeIdx=%h\r\n"
.DO _DBG_SYM=1 .DO _DBG_SYM=1
MSG.DEBUG.SYMN .CZ "New SymID=%H[%H],T=%h,Q=%h " MSG.DEBUG.SYMN .CZ "New SymID=%H[%H],T=%h,Q=%h,SC=%h "
MSG.DEBUG.SYMU .CZ "Upd SymID=%H,T=%h,Q=%h\r\n" MSG.DEBUG.SYMU .CZ "Upd SymID=%H,T=%h,Q=%h,SC=%h\r\n"
MSG.DEBUG.SYMS .CZ "Sto SymID=%H,T=%h,Q=%h\r\n" MSG.DEBUG.SYMS .CZ "Sto SymID=%H,T=%h,Q=%h,SC=%h\r\n"
MSG.DEBUG.SYMG .CZ "Get SymID=%H,T=%h,Q=%h,SC=%h\r\n"
.FIN .FIN
.DO _DBG_SCOPE=1 .DO _DBG_SCOPE=1
MSG.DEBUG.SCIN .CZ "Scope { %H (%h:%h)\r\n" MSG.DEBUG.SCIN .CZ "Scope { %H (%d:%h:%h)\r\n"
MSG.DEBUG.SC .CZ "Scope = %H (%h:%h)\r\n" MSG.DEBUG.SC .CZ "Scope = %H (%d:%h:%h)\r\n"
MSG.DEBUG.SCOUT .CZ "Scope } %H (%h:%h) -> %H\r\n" MSG.DEBUG.SCOUT .CZ "Scope } %H (%d:%h:%h) -> %H\r\n"
.FIN .FIN
.DO _DBG_OUT=1 .DO _DBG_OUT=1
MSG.DEBUG.CSOUT .CZ "\r\n%H-" MSG.DEBUG.CSOUT .CZ "\r\n%H-"
@ -715,8 +677,8 @@ MSG.SUMMARY .CZ "*** Compilation OK : Code size=%5D, Const size=%5D, Data size=
MSG.NOMAIN .CZ "*** No 'main()' function defined." MSG.NOMAIN .CZ "*** No 'main()' function defined."
MSG.ALLDONE .CZ "*** All Done." MSG.ALLDONE .CZ "*** All Done."
*-------------------------------------- *--------------------------------------
OptionList .AS "DdVvLl" OptionList .AS "VvLl"
OptionVars .DA #bDebug,#bDebug,#bVerbose,#bVerbose OptionVars .DA #bVerbose,#bVerbose
*-------------------------------------- *--------------------------------------
ENV.INCLUDE .AZ "INCLUDE" ENV.INCLUDE .AZ "INCLUDE"
ENV.LIB .AZ "LIB" ENV.LIB .AZ "LIB"
@ -1140,7 +1102,7 @@ CC.FPUCALL .PS "pwr"
DS.START DS.START
PathBuf .BS MLI.MAXPATH+1 PathBuf .BS MLI.MAXPATH+1
bDebug .BS 1 *bDebug .BS 1
bVerbose .BS 1 bVerbose .BS 1
LibCount .BS 1 LibCount .BS 1

View File

@ -0,0 +1,10 @@
NEW
AUTO 3,1
#include <stdio.h>
int main(int argc, char *argv[]) {
printf("Hello world!\r\n");
}
MAN
TEXT root/ctest/helloworld.c

55
ROOT/ctest/testargs.c.txt Normal file
View File

@ -0,0 +1,55 @@
NEW
AUTO 3,1
#include <stdio.h>
int testf1() {
puts("testf1 called!");
int r = 1029;
if (r == 1029) {
printf("testf1 will return %D...\r\n", r);
}
return r;
}
int testf2() {
puts("testf2 called!");
return 1000;
}
void testf3(char *msg)
{
puts(msg);
}
int testf4(int arg1, int arg2) {
printf("arg1=%D, arg2=%D\r\n", arg1, arg2);
return arg1 + arg2;
}
int i;
// unreachable code
printf("i=%D\r\n", i);
int main(int argc, char *argv[]) {
printf("argc=%D\r\n", argc);
for(int i=0; i<=argc; i++) {
printf(" argv[%I] : %s\r\n", i, argv[i]);
}
int r=testf1();
printf("testf1() returned %D\r\n", r);
r=testf2();
printf("testf2() returned %D\r\n", r);
testf3("testf3() void function...");
i = testf4(34, 43);
printf("testf4() returned %D\r\n", i);
}
MAN
TEXT root/ctest/testargs.c

37
ROOT/ctest/testf.c.txt Normal file
View File

@ -0,0 +1,37 @@
NEW
AUTO 3,1
#include <stdio.h>
#include <math.h>
int main(int argc, char *argv[]) {
float f1 = 99;
float SQR=sqr(f1);
printf("f1=%e, sqr(f1)=%e\r\n", f1, SQR);
getchar();
float f2 = PI / 3;
printf("f2=%e\r\n", f2);
float COSPI3=cos(f2);
printf("COSPI3=%e\r\n", COSPI3);
float PWR=pwr(16, 3);
printf("PWR=%e\r\n", PWR);
float BILLION=1000000000; //9E6E6B2800
printf("BILLION=%e %h%h%h%h%h\r\n", BILLION, BILLION);
float a = 66 / 3;
printf("a=%e\r\n", a);
a=a+1;
printf("a=%e\r\n", a);
float mul=256*128;
printf("mul=%e\r\n", mul);
puts("Press a key");
getchar();
}
MAN
TEXT root/ctest/testf.c

29
ROOT/ctest/testif.c.txt Normal file
View File

@ -0,0 +1,29 @@
NEW
AUTO 3,1
#include <stdio.h>
int main(int argc, char *argv[])
{
puts("Press a key");
char c=getchar();
printf("char=%d\r\n", c);
if (c == 13)
{
puts("ENTER");
}
else
{
puts("Not ENTER");
}
int i=0;
while (i++ < 10) {
if (i==5) continue;
printf("count1=%I\r\n", i);
}
do {
printf("count2=%I\r\n", i);
} while (i-- > 0);
}
MAN
TEXT root/ctest/testif.c

82
ROOT/ctest/testlib.c.txt Normal file
View File

@ -0,0 +1,82 @@
NEW
AUTO 3,1
#include <stdio.h>
#include <stdlib.h>
#include <libtui.h>
#define EV_SAVE 192
#define EV_OK 193
#define EV_CANCEL 194
short int LBoxVar;
short int CBoxVar;
short int RadioVar;
int main(int argc, char *argv[])
{
short int hCTX = tuiInit();
short int hSCRN = tuiNewScrn(hCTX, F_bTitle+F_bStatus);
tuiSetProp(hSCRN, P_pTitle, "Screen Title");
tuiSetProp(hSCRN, P_pStatus, "Status bar");
char *pBuf = malloc(1024);
pBuf[0]=0;
short int hTBOX = tuiNewTBox(hSCRN, 1, 1, 44, 20, F_bTitle+F_bStatus+F_bHBorder+F_bVBorder, pBuf, 1024);
tuiSetProp(hTBOX, P_pTitle, "Text Box Title");
tuiSetProp(hTBOX, P_pStatus, "Text Box Status");
tuiNewLBox(hSCRN, 50, 1, 20, 9, F_bHBorder+F_bVBorder,
"Item 1\r"
"Item 2\r"
"Item 3\r"
"Item 4\r"
"Item 5\r"
"Item 6 very long line\r"
"Item 7\r"
"Item 8\r"
"Item 9\r"
"Item 10\r"
"Item 11\r"
"Item 12\r"
"Item 13\r"
"Item 14 last one",
&LBoxVar);
char LineBuf[65];
LineBuf[0]=0;
tuiNewLabel(hSCRN, 50, 11, "This is a label.");
tuiNewTLine(hSCRN, 50, 12, 25, &LineBuf, 65);
tuiNewRadio(hSCRN, 50, 14, 0, 0,
"\e[91mRed\r"
"\e[92mGreen\r"
"\e[96mBlue",
&RadioVar);
tuiNewCBox(hSCRN, 50, 18, 0, 0, "Check Me", &CBoxVar);
tuiNewBut(hSCRN, 50, 20, 19, EV_SAVE, "(^S)ave...");
tuiNewBut(hSCRN, 65, 20, 17, EV_QUIT, "(^Q)uit");
tuiDraw(hSCRN);
tuiActivate(hTBOX);
short int e;
do {
e = tuiExec(hSCRN);
if (e == EV_SAVE) {
short int hDLGS = tuiNewDlg(hCTX, 70, 11, "Save As...");
short int hOKBut = tuiNewBut(hDLGS, 50, 7, 13, EV_OK, " OK ");
tuiNewBut(hDLGS, 57, 7, 3, EV_CANCEL, "Cancel");
tuiDraw(hDLGS);
tuiActivate(hOKBut);
tuiExec(hDLGS);
tuiDestroy(hDLGS);
tuiDraw(hSCRN);
}
} while (e != EV_QUIT);
tuiDestroy(hSCRN);
tuiClose(hCTX);
}
MAN
TEXT root/ctest/testlib.c

32
ROOT/ctest/testloop.c.txt Normal file
View File

@ -0,0 +1,32 @@
NEW
AUTO 3,1
#include <stdio.h>
#include <stdlib.h>
#include <string.h>
void *pBuf = malloc(256);
int main(int argc, char *argv[]) {
for (int i=0; i<=argc; i++) printf("argv[%I]=%s\r\n", i, argv[i]);
strcpy(pBuf, argv[0]);
strcat(pBuf, ".c");
printf("Filename=%s\r\n", pBuf);
short int hFile = fopen(pBuf, O_RDONLY, 0, 0);
printf("hFile=%d\r\n", hFile);
int linecnt=0;
while (NULL == fgets(hFile, pBuf, 255)) {
linecnt++;
printf("%5D:%s\r\n", linecnt, pBuf);
}
fclose(hFile);
getchar();
free(pBuf);
puts("All done.");
}
MAN
TEXT root/ctest/testloop.c

76
ROOT/ctest/testptr.c.txt Normal file
View File

@ -0,0 +1,76 @@
NEW
AUTO 3,1
#include <stdio.h>
#include <stdlib.h>
#include <unistd.h>
#include <md5.h>
void *someptr = NULL;
void *pBuf = malloc(256);
int iarray[8];
float farray[4][5];
int *parray[];
int main(int foo, char *bar[]) {
puts("Testptr...");
printf("someptr = %H:%H, pBuf = %H:%H\r\n", &someptr, someptr, &pBuf, pBuf);
getchar();
parray=&iarray;
printf("parray = %H:%H\r\n", &parray, parray);
getchar();
printf("iarray = %H:%H:%H:%H\r\n", &iarray, iarray, iarray[0], iarray[1]);
getchar();
iarray[0]=513;
iarray[1]=1026;
printf("iarray = %H:%H:%H:%H\r\n", &iarray, iarray, iarray[0], iarray[1]);
getchar();
*parray[0]=258;
*parray[1]=516;
printf("parray = %H:%H:%H:%H\r\n", &parray, parray, parray[0], parray[1]);
getchar();
farray[1][1]=3.14;
printf("farray: %e\r\n", farray[1][1]);
printf("foo = %D, bar = %H:%H:%s:%s\r\n", foo, &bar, bar, bar[0], bar[1]);
getchar();
md5("PASSWORD", pBuf);
printf("MD5=%s\r\n", pBuf);
getchar();
getenv("TERM", pBuf);
printf("TERM=%s\r\n", pBuf);
getchar();
setenv("TEST", "Value");
getenv("TEST", pBuf);
printf("TEST=%s\r\n", pBuf);
getchar();
short int hFile = fopen("testptr.c", O_RDONLY, 0, 0);
printf("hFile=%d\r\n", hFile);
int linecnt=0;
while (NULL == fgets(hFile, pBuf, 255)) {
linecnt++;
printf("%5D:%s\r\n", linecnt, pBuf);
}
fclose(hFile);
getchar();
free(pBuf);
puts("All done.");
}
MAN
TEXT root/ctest/testptr.c

23
ROOT/ctest/testsc.c.txt Normal file
View File

@ -0,0 +1,23 @@
NEW
AUTO 3,1
#include <stdio.h>
int main(int argc, char *argv[])
{
char c=getchar();
switch (c)
{
case 13:
puts("ENTER pressed");
break;
case 'C':
case 'c':
puts("'c' or 'C' pressed");
break;
default:
puts("something else pressed");
break;
}
}
MAN
TEXT root/ctest/testsc.c

46
ROOT/ctest/testtdef.c.txt Normal file
View File

@ -0,0 +1,46 @@
NEW
AUTO 3,1
#include <sys/types.h>
#include <stdio.h>
#include <time.h>
typedef char *cp;
cp s;
struct tagS1
{
int i;
float f;
};
struct tagS1 S1;
struct tagS2
{
int i;
float f;
} S2;
struct
{
int i;
float f;
} S3;
struct tm now;
struct tm* tmp;
int main(int argc, char *argv[])
{
dev_t hDEV;
S1.i = 3;
S1.f=3.14;
// time(&tm);
}
MAN
TEXT root/ctest/testtdef.c