6502.org Forum  Projects  Code  Documents  Tools  Forum
It is currently Sat Oct 05, 2024 1:26 pm

All times are UTC




Post new topic Reply to topic  [ 14 posts ] 
Author Message
 Post subject: Whats wrong with my code
PostPosted: Wed Aug 07, 2013 11:29 pm 
Offline
User avatar

Joined: Wed Jul 10, 2013 3:13 pm
Posts: 67
Im using Kowalski assembler and I type
Code:
.ORG *= $0300

and when I attempt to assemble I get
Code:
ERROR E002: Unrecognized data--space or label expected. ROW 1, FILE C:\Users\James\Documents\NewFile 1

whats wrong with this code :?: :?:

_________________
JMP $FFD2


Top
 Profile  
Reply with quote  
PostPosted: Wed Aug 07, 2013 11:42 pm 
Offline

Joined: Mon Mar 02, 2009 7:27 pm
Posts: 3258
Location: NC, USA
Type in a space before the "." in ".ORG"

_________________
65Org16:https://github.com/ElEctric-EyE/verilog-6502


Top
 Profile  
Reply with quote  
PostPosted: Wed Aug 07, 2013 11:47 pm 
Offline
User avatar

Joined: Wed Jul 10, 2013 3:13 pm
Posts: 67
now it says
Code:
ERROR E032: Missing .ORG directive--undetermined program begining address. ROW 1, FILE C:\Users\James\Documents\NewFile 1

_________________
JMP $FFD2


Top
 Profile  
Reply with quote  
PostPosted: Wed Aug 07, 2013 11:47 pm 
Offline
User avatar

Joined: Fri Aug 30, 2002 1:09 am
Posts: 8521
Location: Southern California
Does it have a manual with a list of error messages to tell what E002 is? Many assemblers only accept labels in column 1. EE, is the rest ok? Usually ORG or .ORG is followed by a number or and expression that produces a number, and *= does that too. It doesn't seem right to have both, but I'm not familiar with Kowalski's assembler. I would think it should be
Code:
        .ORG  $0300

_________________
http://WilsonMinesCo.com/ lots of 6502 resources
The "second front page" is http://wilsonminesco.com/links.html .
What's an additional VIA among friends, anyhow?


Top
 Profile  
Reply with quote  
PostPosted: Wed Aug 07, 2013 11:52 pm 
Offline

Joined: Mon Mar 02, 2009 7:27 pm
Posts: 3258
Location: NC, USA
Well James needs some bit of code too...
I believe hit 'TAB', then type in NOP opcode for the simplest of all programs to see if it passes assembly.

_________________
65Org16:https://github.com/ElEctric-EyE/verilog-6502


Top
 Profile  
Reply with quote  
PostPosted: Thu Aug 08, 2013 12:38 am 
Offline
User avatar

Joined: Wed Jul 10, 2013 3:13 pm
Posts: 67
Could someone give e a asm program they made with the simulator and I try that
btw I apparently need and ORG

_________________
JMP $FFD2


Top
 Profile  
Reply with quote  
PostPosted: Thu Aug 08, 2013 12:58 am 
Offline

Joined: Mon Mar 02, 2009 7:27 pm
Posts: 3258
Location: NC, USA
Good luck!
Report back with your progress.

_________________
65Org16:https://github.com/ElEctric-EyE/verilog-6502


Top
 Profile  
Reply with quote  
PostPosted: Thu Aug 08, 2013 2:45 am 
Offline
User avatar

Joined: Fri Aug 30, 2002 1:09 am
Posts: 8521
Location: Southern California
I haven't used that assembler or simulator; but did you look at the 6502 primer chapter, "Program-Writing: Where Do I Start?"? It gives the general order of things you need in the source code.

_________________
http://WilsonMinesCo.com/ lots of 6502 resources
The "second front page" is http://wilsonminesco.com/links.html .
What's an additional VIA among friends, anyhow?


Top
 Profile  
Reply with quote  
PostPosted: Thu Aug 08, 2013 4:39 am 
Offline
User avatar

Joined: Thu May 28, 2009 9:46 pm
Posts: 8411
Location: Midwestern USA
James_Parsons wrote:
Im using Kowalski assembler and I type
Code:
.ORG *= $0300

.ORG is a pseudo-op that is an alternative to *=. Use one or the other and make sure there is whitespace (a tab will do) between the pseudo-op and the left margin. Here's a program, written to generate 65C816 object code, that illustrates a lot of what you can do in the simulator. Note the extensive use of macros, an assembly language programmer's second best friend:


Code:
   .opt proc65c02,caseinsensitive
;* * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *
;*                                                                                 *
;*                 W65C816S PROOF OF CONCEPT SINGLE-BOARD COMPUTER                 *
;*                                                                                 *
;*                       DISPLAY DATE, TIME OF DAY & UP TIME                       *
;* ——————————————————————————————————————————————————————————————————————————————— *
;*      Copyright ©1991-2013 by BCS Technology Limited.  All rights reserved.      *
;*                                                                                 *
;* Permission is hereby granted to use, copy, modify and distribute this software, *
;* provided this copyright notice remains in the source code and  proper  attribu- *
;* tion is given.  Redistribution, regardless of form, must be at no charge to the *
;* end  user.  This code or any part thereof, including any derivation, MAY NOT be *
;* incorporated into any package intended for sale,  unless written permission has *
;* been given by the copyright holder.                                             *
;*                                                                                 *
;* THERE IS NO WARRANTY OF ANY KIND WITH THIS SOFTWARE.  The user assumes all risk *
;* in connection with the incorporation of this software into any system.          *
;*                                                                                 *
;* * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *
;
   .include "include\816macs.65s"
   .include "include\convenmacs.65s"
   .include "include\atomic.65s"
   .include "include\stdascii.65s"
   .include "include\sys\macros_console.65s"
   .include "include\architecture.65s"
   .include "include\sys\bios.65s"
   .include "lib\date\atomic.65s"
;===============================================================================
;
;LOCAL DECLARATIONS
;
_origin_ =$00c000
;
a_qmark  ='?'                  ;ASC conversion base
n_asc    =3                    ;chars in day or month
n_shfdcd =5                    ;day or month decode shifts
stckptr  =1                    ;base stack offset reference
pbnk     =$0c                  ;transfer bank for experimenting
tbnk     =$1f                  ;data bank for experimenting
_faca_   =$80                  ;accumulator base
;
;
;   accumulator transfer banks...
;
dbnk     =tbnk
sbnk     =pbnk
;
   .include "lib\math\atomic.65s"
;===============================================================================
;
;RTC BUFFER DEFINITIONS
;
rtcsec   =0                    ;seconds
rtcmin   =rtcsec+s_byte        ;minutes
rtchrs   =rtcmin+s_byte        ;hours
rtcdow   =rtchrs+s_byte        ;day of week
rtcdat   =rtcdow+s_byte        ;date
rtcmon   =rtcdat+s_byte        ;month
rtcylo   =rtcmon+s_byte        ;year LSB
rtcyhi   =rtcylo+s_byte        ;year MSB
;
s_rtcbuf =rtcyhi+s_byte        ;RTC buffer size
;
;===============================================================================
;
;LOCAL MACROS
;
mem_faca .macro .s,.m          ;copy integer to FACA
         longr
         ldaw .s
         ldxw .m
         jsr imemfaca
         .endm
;
mem_facb .macro .s,.m          ;copy integer to FACB
         longr
         ldaw .s
         ldxw .m
         jsr imemfacb
         .endm
;
faca_mem .macro .s,.m          ;copy FACA to integer
         longr
         ldaw .s
         ldxw .m
         jsr ifacamem
         .endm
;
;===============================================================================
;
;MAINLINE
;
   * = _origin_
;
dpydat   longa
         ldaw dstkptr          ;default stack pointer
         tcs                   ;reset to top of stack
         shortr
         lda #tbnk
         pha
         plb                   ;set default data bank
         ldx #<rtcbuf          ;RTC buffer LSB
         ldy #>rtcbuf          ;RTC buffer MSB
         jsr getdtr            ;get date & time from RTC
         jsr getutim           ;get up time
         stx uptime            ;save up time LSW
         sty uptime+s_word     ;save up time MSW
         shortr                ;8 bit registers
         lda dow               ;day of week
         and #_dayswk_         ;mask out-of range DOW
         tay                   ;day index
         longa
         ldaw dowtab           ;decode table pointer
         ldx #0                ;starting buffer index
         jsr cvtdm             ;convert day
         jsr insrtblk          ;add a blank
         lda month
         jsr bcdbdig           ;convert to binary
         cmp #_monsyr_+1
         bcc .0000010          ;in range
;
         lda #0                ;unknown month
;
.0000010 tay                   ;month index
         longa
         ldaw montab           ;table pointer
         jsr cvtdm             ;convert day
         jsr insrtblk          ;add a blank
         lda date              ;get date
         jsr bcdasc            ;change to ASCII
         beq .0000020          ;skip leading zero
;
         jsr insrtCOM          ;add 10s to buffer
;
.0000020 xba
         jsr insrtCOM          ;add 1s to buffer
         jsr insrtblk
         lda hours             ;get hour
         jsr addtostr          ;add to string
         jsr insrtcol          ;add a colon to string
         lda minutes           ;get minute
         jsr addtostr          ;add to string
         jsr insrtcol          ;add a colon to string
         lda seconds           ;get seconds
         jsr addtostr          ;add to string
         jsr insrtblk          ;add a blank
         ldy #0
;
.0000030 lda timezone,y        ;timezone string
         beq .0000040
;
         sta strgbuf,x         ;add to string
         inx
         iny
         bra .0000030
;
.0000040 jsr insrtblk
         lda yearhi            ;year MSB
         jsr addtostr          ;add to string
         lda yearlo            ;year LSB
         jsr addtostr          ;add to string
         stz strgbuf,x         ;terminate string
         printstr preamble     ;print newline, etc.
         printstr strgbuf      ;print date & time
         printstr uptimea      ;"Up..."
         jsr brkutim           ;break down uptime
         longa
         shortx
         lda udays             ;uptime days
         beq .0000050          ;up less than a day
;
         mem_faca s_dword,udays
         jsr binasc            ;convert days &...
         printstr strgbuf      ;print
         printstr uptdays      ;"day"
         longa
         lda udays             ;uptime days
         jsr pplural           ;pluralize if necessary
         jsr pcomma            ;print a comma
         longa
;
.0000050 lda uhours            ;uptime hours
         beq .0000060          ;zero
;
         mem_faca s_dword,uhours
         jsr binasc            ;convert hours &...
         printstr strgbuf      ;print
         printstr upthours     ;"hour"
         longa
         lda uhours            ;uptime hours
         jsr pplural           ;pluralize if necessary
         jsr pcomma            ;print a comma
         longa
;
.0000060 lda umins             ;uptime minutes
         beq .0000070          ;zero
;
         mem_faca s_dword,umins
         jsr binasc            ;convert minutes &...
         printstr strgbuf      ;print
         printstr uptmins      ;"minute"
         longa
         lda umins             ;uptime minutes
         jsr pplural           ;pluralize if necessary
         jsr pcomma            ;print a comma
         longa
;
.0000070 lda uptime            ;seconds
         beq .0000080          ;zero
;
         mem_faca s_dword,uptime
         jsr binasc            ;convert seconds &...
         printstr strgbuf      ;print
         printstr uptsecs      ;"second"
         longa
         lda uptime            ;seconds
         jsr pplural           ;pluralize if necessary
;
.0000080 printstr endofstg     ;end of string
         .rept 4
             brk
         .endr
;
;================================================================================
;
;CONVERT BCD DIGIT TO ASCII DIGITS
;
bcdasc   pha                   ;save digit
         and #m_bcdlo          ;extract LSN
         ora #m_binasc         ;change to ASCII
         xba                   ;hide units
         pla                   ;get digit
         .rept s_bnybbl        ;extract MSN
             lsr
         .endr
         ora #m_binasc         ;change to ASCII
         cmp #m_binasc         ;condition .Z
         rts
;
;================================================================================
;
;CONVERT BCD DIGIT TO BINARY EQUIVALENT
;
bcdbdig  php
         shorta
         cld                   ;ensure binary mode
         xba
         pha                   ;save .B entry value
         xba                   ;recover input value &...
         pha                   ;buffer
         xba                   ;save
         pla                   ;get input value
         and #m_bcdhi          ;extract 10s
         lsr                   ;now *8
         pha                   ;store *8
         lsr
         lsr                   ;now *2
         clc
         adcs 1                ;*8
         stas 1                ;*10
         xba                   ;get original value
         and #m_bcdlo          ;extract units
         clc
         adcs 1                ;add 10s
         xba                   ;protect result
         pla                   ;flush stack
         pla                   ;get old .B &...
         xba                   ;restore it
         plp
         pha                   ;condition .Z
         pla
         rts
;
;===============================================================================
;
;binasc: CONVERT 32 BIT BINARY INTEGER TO ASCII STRING
;
;   ——————————————————————————————————————————
;   Preparatory Ops : value to convert in FACA
;
;   Returns: Null-terminated string in STRGBUF
;
;   Register Returns: All registers used
;
;   MPU Flags: NVmxDIZC
;              ||||||||
;              ||||||++———> undefined
;              |||||+—————> entry value
;              ||||+——————> 0
;              ||++———————> 1
;              ++—————————> undefined
;
;   Notes: 1) FACA is not preserved.  FACB is
;             used.
;   ——————————————————————————————————————————
;
binasc   jsr clrfacb           ;clear sec accum
         longa
         shortx
         sed                   ;decimal addition
         ldy #s_dword*s_bibyte ;bits to process
;
.0000020 phy                   ;save bit counter
         asl faca              ;get a bit from...
         rol faca+s_word       ;binary value
         ldx #0                ;addition index
         ldy #s_ifac/s_word    ;BCD words to process
;
.0000030 lda facb,x            ;propagate new bit...
         adc facb,x            ;throughout sum &...
         sta facb,x            ;double
         .rept s_word          ;step number index
             inx
         .endr
         dey                   ;step word counter
         bne .0000030          ;next
;
         ply                   ;get bit counter
         dey                   ;a bit's been processed
         bne .0000020          ;not done
;
         cld                   ;binary mode
         shorta                ;8 bits at a time
         ldx #s_ifac-s_byte    ;BCD workspace index
         ldy #0                ;string assembly index
;
binasc01 lda facb,x            ;get BCD byte
         bne .0000010          ;non-zero, must convert
;
         cpy #0                ;start of string?
         beq .0000040          ;yes, drop leading zeros
;
.0000010 jsr bcdasc            ;convert BCD to ASCII
         bne .0000020          ;both digits significant
;
         cpy #0                ;start of string?
         beq .0000030          ;yes, drop leading zero
;
.0000020 sta strgbuf,y         ;add 10s numeral to buffer
         iny
;
.0000030 xba
         sta strgbuf,y         ;add 1s numeral to buffer
         iny
;
.0000040 dex
         bpl binasc01          ;next BCD byte
;
         tyx                   ;final string index
         stz strgbuf,x         ;terminate string
         rts
;
;===============================================================================
;
;brkutim: BREAK DOWN UPTIME TO DAYS, HOURS, MINS & SECS
;
;   ————————————————————————————
;   Calculations are as follows:
;
;     DAYS  = INT(SECS/SPD)
;     SECS  = SECS-DAYS*SPD
;     HOURS = INT(SECS/SPH)
;     SECS  = SECS-HOURS*SPH
;     MINS  = INT(SECS/SPM)
;     SECS  = SECS-MINS*SPM
;
;   where:
;
;     SPD = seconds per day
;     SPH = seconds per hour
;     SPM = seconds per minute
;   ————————————————————————————
;    
;
brkutim  mem_faca s_dword,uptime ;SECS to pri accum
         mem_facb s_dword,spd    ;secs-per-day to sec accum
         jsr idiv                ;integer division
         faca_mem s_dword,udays  ;pri accum to DAYS
;
         jsr imul                ;DAYS*SPD
         jsr facafacb            ;DAYS*SPD to sec accum
         mem_faca s_dword,uptime
         jsr isub                ;integer subtraction
         faca_mem s_dword,uptime ;pri accum to SECS
;
         mem_facb s_dword,sph    ;secs-per-hour to sec accum
         jsr idiv
         faca_mem s_dword,uhours ;pri accum to HOURS
;
         jsr imul                ;HOURS*SPH
         jsr facafacb
         mem_faca s_dword,uptime
         jsr isub
         faca_mem s_dword,uptime
;
         mem_facb s_dword,spm    ;secs-per-minute to sec accum
         jsr idiv
         faca_mem s_dword,umins  ;pri accum to MINS
;
         jsr imul                ;MINS*SPM
         jsr facafacb
         mem_faca s_dword,uptime
         jsr isub
         faca_mem s_dword,uptime
         shortr
         rts
;
;================================================================================
;
;ADD CHARACTERS TO STRING
;
addtostr jsr bcdasc            ;change BCD to ASCII
         sta strgbuf,x         ;add 10s to buffer
         inx
         xba
         bra insrtCOM          ;add 1s to buffer
;
;===============================================================================
;
;INSERT COLON IN DATE STRING
;
insrtcol lda #':'
         bra insrtCOM
;
;===============================================================================
;
;INSERT BLANK IN DATE STRING
;
insrtblk lda #' '
;
insrtCOM sta strgbuf,x
         inx
         rts
;
;================================================================================
;
;CONVERT DAY or MONTH & ADD TO STRING BUFFER
;
;   ——————————————————————————————————————————————
;   Preparatory Ops : .A: 16 bit table pointer
;                     .X: 8 bit buffer index
;                     .Y: 8 bit day or month index
;
;   Register Returns: .A: used
;                     .B: used
;                     .X: new buffer index
;                     .Y: used
;
;   MPU Flags: NVmxDIZC
;              ||||||||
;              |||||||+———> undefined
;              ||||||+————> undefined
;              |||||+—————> undefined
;              ||||+——————> undefined
;              |||+———————> undefined
;              ||+————————> undefined
;              |+—————————> undefined
;              +——————————> undefined
;   ——————————————————————————————————————————————
;
cvtdm    pha                   ;save table pointer
;
;———————————————————————————————
.table   =1
;———————————————————————————————
;
         shortr                ;8 bit registers
         tya                   ;day or month index
         asl                   ;now table offset
         tay
         ldasi .table          ;get code LSB
         sta miscwork          ;copy to work area
         iny
         ldasi .table          ;get code MSB
         sta miscwork+s_byte   ;copy to work area
         ldy #n_asc            ;chars to be generated
;
.0000010 jsr unpack            ;decode a char &...
         cpy #n_asc            ;1st char?
         beq .0000020          ;no, skip case conversion
;
         ora #a_uctolc         ;convert to lower case
;
.0000020 jsr insrtCOM          ;insert into buffer
         dey
         bne .0000010          ;next
;
         pla                   ;clean up...
         pla                   ;stack
         rts
;
;================================================================================
;
;pplural: PLURALIZE TIME UNIT IF NECESSARY
;
;   ——————————————————————————————————————————————
;   Preparatory Ops : .C: 16 value to test
;
;   Register Returns: .A: used
;                     .B: used
;                     .X: used
;                     .Y: used
;
;   MPU Flags: NVmxDIZC
;              ||||||||
;              |||||||+———> undefined
;              ||||||+————> undefined
;              |||||+—————> entry value
;              ||||+——————> undefined
;              |||+———————> 1
;              ||+————————> 1
;              |+—————————> undefined
;              +——————————> undefined
;   ——————————————————————————————————————————————
;
pplural  longa
         cmpw 1                ;1 unit?
         shortr
         beq .0000010          ;zero or multiple units
;
         lda #'s'
         jmp bsouta            ;"units"
;
.0000010 rts
;
;================================================================================
;
;PRINT A COMMA & BLANK
;
pcomma   ldx #<comma           ;", "
         ldy #>comma
         jmp sprint
;
;================================================================================
;
;UNPACK DAY or MONTH CODE
;
;   —————————————————————————————————————————————
;   MISCWORK = packed code in little-endian order
;   —————————————————————————————————————————————
;   .A = unpacked character
;   .X = entry value
;   .Y = entry value
;   ——————————————————————————————————————————————————————————————————————
;   Each call to this subroutine decodes a character & returns it as lower
;   case ASCII in the range $61 - $6A.
;
;   The packed code consists of 2 bytes, into which bits 0-4 of  an  ASCII
;   character have been shifted 5 times.  The result is that 3  characters
;   are compressed into 2 bytes.
;   ——————————————————————————————————————————————————————————————————————
;
unpack   phy                   ;protect counter
         lda #0                ;starting character
         ldy #n_shfdcd         ;iterations to unpack
;
.0000010 asl miscwork          ;left shifts will extract...
         rol miscwork+s_byte   ;the bits needed to form...
         rol                   ;a UC character
         dey
         bne .0000010
;
         clc
         adc #a_qmark          ;convert to UC ASCII
         ply                   ;restore counter
         rts
;
   .include "lib\math\clrfac.65s"
   .include "lib\math\clrovrfl.65s"
   .include "lib\math\facafacb.65s"
   .include "lib\math\ifacamem.65s"
   .include "lib\math\imemfaca.65s"
   .include "lib\math\imemfacb.65s"
   .include "lib\math\idiv.65s"
   .include "lib\math\imul.65s"
   .include "lib\math\isub.65s"
;===============================================================================
;
;STATIC DATA
;
spd      dwordadr _secday_     ;seconds per day
sph      dwordadr _sechr_      ;seconds per hour
spm      dwordadr _secmin_     ;seconds per minute
;
dowtab   .byte $00,$00         ;invalid
         .byte $9e,$a5         ;Sun
         .byte $1e,$74         ;Mon
         .byte $8c,$ad         ;Tue
         .byte $8a,$c1         ;Wed
         .byte $6c,$aa         ;Thu
         .byte $d4,$3c         ;Fri
         .byte $aa,$a0         ;Sat
;
montab   .byte $00,$00         ;invalid
         .byte $9e,$58         ;Jan
         .byte $86,$39         ;Feb
         .byte $a6,$70         ;Mar
         .byte $66,$14         ;Apr
         .byte $b4,$70         ;May
         .byte $9e,$5d         ;Jun
         .byte $9a,$5d         ;Jul
         .byte $90,$15         ;Aug
         .byte $a2,$a1         ;Sep
         .byte $2a,$81         ;Oct
         .byte $2e,$7c         ;Nov
         .byte $88,$29         ;Dec
;
;===============================================================================
;
;TEXT STRINGS
;
preamble .byte a_cr
         bf
         .byte " ",0
;
timezone .byte "UTC",0
;
uptimea  .byte " "
         lf
         .byte " Up ",0
;
uptdays  .byte " day",0
;
upthours .byte " hour",0
;
uptmins  .byte " minute",0
;
uptsecs  .byte " second",0
;
comma    .byte ", ",0
;
endofstg .byte " "
         er
         .byte 0
;
;===============================================================================
;
;STORAGE
;
uptime   =*                    ;uptime from BIOS
         *=*+s_utcnt
udays    =*                    ;uptime days
         *=*+s_dword
uhours   =*                    ;uptime hours
         *=*+s_dword
umins    =*                    ;uptime minutes
         *=*+s_dword
miscwork =*                    ;scratch work area
         *=*+s_word
rtcbuf   =*                    ;date & time buffer...
;
seconds      =rtcbuf+rtcsec    ;seconds
minutes      =rtcbuf+rtcmin    ;minutes
hours        =rtcbuf+rtchrs    ;hours
dow          =rtcbuf+rtcdow    ;day of week
date         =rtcbuf+rtcdat    ;date
month        =rtcbuf+rtcmon    ;month
yearlo       =rtcbuf+rtcylo    ;year LSB
yearhi       =rtcbuf+rtcyhi    ;year MSB
         *=*+s_rtcbuf
;
strgbuf  =*                    ;string assembly buffer
;
;===============================================================================
   .end

The above example also illustrates a style of code entry that you may find useful. Be sure to include the very first line in all programs you write in the Kowalski simulator. It tells the simulator that all non-quoted text is to be treated the same regardless of case, and that 65C02 instructions are legal (change 65C02 to 6502 for accurate NMOS simulation).

See below for a list of the simulator's pseudo-ops.


Code:
KOWALSKI SIMULATOR ASSEMBLER DIRECTIVES — BigDumbDinosaur 2012/07/01

 IO_AREA           ;define console I/O area address (no leading dot in IO_AREA)
 .ASCII .BYTE .DB  ;generate static data, such as strings, tables, etc.
 .ASCIS            ;generate character string w/bit 7 of last byte set
 .DBYTE .DD        ;assemble big-endian word
 .DCB              ;equivalent to * = * + N, where N is arg to .DCB,...
                   ;w/optional initialization pattern, e.g., .DCB 10,$FF, which will
                   ;reserve 10 bytes & fill them with $FF
 .DS .RS           ;equivalent to * = * + N, where N is arg to .DS or .RS
 .DW .WORD         ;assemble little-endian word
 .ELSE             ;conditional assembly directive
 .END              ;mark end of source file, optional
 .ENDIF            ;mark end of conditional assembly
 .ENDM             ;mark end of macro definition
 .ENDR             ;mark end of repeated text
 .ERROR            ;emit an error message & halt assembly,...
                   ;e.g., .ERROR "!!! operand out of range !!!"
 .EXITM            ;halt macro expansion
 .IF               ;start conditional assembly
 .INCLUDE          ;insert contents of named source file...
                   ;e.g., .INCLUDE "include\atomic.65s"
 .IO_WND           ;define console I/O window size (cols, rows)
 .MACRO            ;mark start of macro definition, w/optional comma-separated parameters
 .OPT              ;set global assembly options
 .ORG              ;set start of assembly address, same as * = <addr>
 .PARAMTYPE        ;determine macro parameter type: 1 = numeric, 2 = string,...
                   ;.IF .PARAMTYPE(.op) == 1
 .REF              ;determine if label/symbol was defined,...
                   ;e.g., .IF .REF(ABC) evaluates true if...
                   ;ABC has been defined; logic can be reversed...
                   ;with !.REF (ABC)
 .REPEAT .REPT     ;repeat following text N times
 .ROM_AREA         ;set simulator's write-protected address range
 .SET              ;(re)define variable value, e.g., .SET .=
 .START            ;set simulator start of execution address
 .STR .STRING      ;generate text string, 1st byte is length, 255 bytes maximum
 .STRLEN           ;determine macro parameter string length

.IF evaluations can use the following binary operators:

    ==  is equal to
    !=  is not equal to
    >   is greater than
    <   is less than

.IF .op means "if .op is non-zero".


_________________
x86?  We ain't got no x86.  We don't NEED no stinking x86!


Last edited by BigDumbDinosaur on Thu Aug 08, 2013 9:17 pm, edited 1 time in total.

Top
 Profile  
Reply with quote  
PostPosted: Thu Aug 08, 2013 5:02 am 
Offline
User avatar

Joined: Thu May 28, 2009 9:46 pm
Posts: 8411
Location: Midwestern USA
Here's the assembler's output listing for the above program, which will give you an idea of what to expect when you successfully assemble a program.


Attachments:
File comment: Kowalski Assembler Listing Output
aout.txt [103.89 KiB]
Downloaded 92 times

_________________
x86?  We ain't got no x86.  We don't NEED no stinking x86!
Top
 Profile  
Reply with quote  
PostPosted: Thu Aug 08, 2013 6:44 pm 
Offline
User avatar

Joined: Thu Dec 11, 2008 1:28 pm
Posts: 10947
Location: England
James, I went to the Kowalski download page and right next to the download link there's a link to a zip file of code samples.

Please do a little research before jumping on the forum with another new topic: this isn't a chat room, it's a forum. Conversations here take longer and stay around forever. Search the forum too, and feel free to post to a previous relevant topic. (And, always use a sensible post title so that future searches are more likely to find the right results.)

What you have here is a small audience of die-hard fans, who have a lot of knowledge but hope to see something interesting when a new thread is opened up. Questions are welcome, when they are well-worded and demonstrate some effort to explain what it is they are asking. If you have confusion, take the trouble to explain what your mental model is and how it differs from reality. You have our time: do us the favour of not wasting it.

Cheers
Ed


Top
 Profile  
Reply with quote  
PostPosted: Thu Aug 08, 2013 7:59 pm 
Offline
User avatar

Joined: Wed Jul 10, 2013 3:13 pm
Posts: 67
Sorry I didn't get it from that page and id didn't have the examples

_________________
JMP $FFD2


Top
 Profile  
Reply with quote  
PostPosted: Thu Aug 08, 2013 8:28 pm 
Offline
User avatar

Joined: Thu Dec 11, 2008 1:28 pm
Posts: 10947
Location: England
Note that I found the page by googling for "kowalski assembler" but "kowalski 6502" does just as well. The lesson is: start by searching, then compose your thoughts, and then post your question.

The nature of working with microprocessors at the assembly language and soldering iron level is that you have to be able to think about what you're doing, and you have to be able read and digest the materials that are out there. It's not possible to jump in and understand it without trying, and it's not possible to answer a question in a short reply when it demands book length. Garth has gone to the trouble of writing a book-length website, and other books such as Leventhal and Zaks are easy to find, as is the WDC reference which you've already been pointed at.

Slow down a bit, and be prepared to try and fail.

Cheers
Ed


Top
 Profile  
Reply with quote  
PostPosted: Thu Aug 08, 2013 9:13 pm 
Offline
User avatar

Joined: Thu May 28, 2009 9:46 pm
Posts: 8411
Location: Midwestern USA
BigEd wrote:
Note that I found the page by googling for "kowalski assembler" but "kowalski 6502" does just as well. The lesson is: start by searching, then compose your thoughts, and then post your question.

In my earlier post, I had pointed James directly to the final version of the simulator (1.2.12). It's a link to the actual ZIP file, and has not been published anywhere, as far as I know. So he would not have seen the code examples that are on the page where V1.2.11 would be found (I do have a local copy on one of my servers). My belated realization of that led me to post the above matter.

Quote:
The nature of working with microprocessors at the assembly language and soldering iron level is that you have to be able to think about what you're doing, and you have to be able read and digest the materials that are out there...Slow down a bit, and be prepared to try and fail.

James, Ed is giving you good advice. There's a huge amount of material here (and elsewhere, such as at Garth's site) that relates to what you want to do. The average public library has nothing on 6502.org when it comes to all-around information about microprocessors, hardware, writing code, construction techniques, etc. Please look at all of it. Also, please visit André Fachat's pages, Daryl Rictor's (8BIT) site, and perhaps mine as well. Do like I did when I first came here: lurk and study for a while, and then you'll be better prepared to pose questions and get into the discussion.

There's a lot to learn, but nothing quite beats the satisfaction of possessing knowledge that enables you to do things that others think are magic.

_________________
x86?  We ain't got no x86.  We don't NEED no stinking x86!


Top
 Profile  
Reply with quote  
Display posts from previous:  Sort by  
Post new topic Reply to topic  [ 14 posts ] 

All times are UTC


Who is online

Users browsing this forum: No registered users and 5 guests


You cannot post new topics in this forum
You cannot reply to topics in this forum
You cannot edit your posts in this forum
You cannot delete your posts in this forum
You cannot post attachments in this forum

Search for:
Jump to:  
cron