News:

MASM32 SDK Description, downloads and other helpful links
MASM32.com New Forum Link
masmforum WebSite

Linking programs

Started by veronicak5678, October 09, 2009, 02:33:44 AM

Previous topic - Next topic

dedndave

well - you have to look at the last download i posted
UPPER and LOWER are passed to NRANDOM on the stack
but, another problem you have is that SEED is defined as seperate data values in NRANDOM and RESEED
it needs to be a single data item
in the file where it is defined, it should be declared as PUBLIC
in the other files, it should be listed as EXTERN SEED:WORD

mikey

It looks like I am in the same class this semester and frankly this teacher is crazy to expect us to figure this stuff out on our own.  The book isn't much help; he's pulling these assignments from a different book he used probably 10+ years ago (he says it's no longer being published).  The code that we're supposed to "not worry about for now" changes with every example, and apparently, we DO need to worry about it this time.  I'd be surprised if half the class got half-credit on this thing, especially with the way he grades.

Sorry, had let off some steam...

dedndave

ok - i had to use an ASSUME directive to let RESEED know which segment DS was in...
i also changed the name of RANDOM.ASM to NRANDOM.ASM to avoid confusion
(the io.lib file has a RANDOM proc in it, as well)

Mikey - many professors suck - lol
this probably isn't the first and won't be the last
he shouldn't be teaching 16-bit code at all - a waste of time, in a way
he should be teaching 32-bit code
it is kinda obvious, he doesn't know 32-bit code
he barely knows 16-bit

still - be thankful
when i went to school, i had to punch thousands of holerith cards
then, wait in a long line to load the program
then - wait some more for the computer to decide to run it
if i had even the slightest mistake - i had to do most of that over again
and - format statements in fortran - easy to make a mistake - lol

EDIT - there must be a better way to handle SEED as an external
it might be something like EXTERN SEED:FAR_DATA:WORD or FAR PTR WORD - i dunno
the last time i did this stuff, i was using MASM version 5.10 and that was a while back - lol

ilian007

Aggree with Mikey....

dedndave: I have the push think in my tree files however it still doesnt work. It seems we are all in one class. We better submit different codes ... So please anybody who use that message board to do his own private changes of the coding in his program.

That's why I would like to make my version to work. I will atach my files I have so far. It still can not compile. Lower and Upper gives me error. Please can you take a look if possible..
the major difference in mine is the clock seed procedure. ohh yeah and I am printing both massives at ones and my statistic is for the 200 numbers ...

thank you dedndave :)

dedndave

i had written the seed routine differently, but Veronica didn't like it - lol
i had something like...

.
.
.
        mov     dx,5555h
        or      bl,bl
        jnz     RExit0

        mov     ah,0
        int     1Ah

RExit0: mov     SEED,dx
        ret

as for the stack parameters LOWER and UPPER, they can be declared in the PROC directive

NRANDOM PROC LOWER:WORD,UPPER:WORD

the assembler will figure out the correct [bp+nnnn] stack pointer for you
but, when i use a stack frame, i prefer to do that myself
back in the days, the assembler didn't do all that fancy stuff - lol

ilian007

I guess the problem of my program is I am using that:

NRANDOM PROC    FAR PUBLIC
         
        ;PUSH    CX                     ;( [BP+8] )
        ;PUSH    DX                     ;( [BP+6] )
        PUSH    DS                     ;( [BP+4] )
        PUSHF                          ;SAVE FLAGS ( [BP+2] )
       
        MOV     AX,FAR_DATA            ;SET DS-REGISTER TO POINT
        MOV     DS,AX                  ;TO FAR DATA SEGMENT
        MOV     AX,SEED             ;X = SEED * MULTIPLIER mod
           MUL     MULTIPLIER          ;                       65536
           ADD     AX,ADDEND           ;SEED = (X + ADDEND) mod 65536
           MOV     SEED,AX
           MOV     CX,UPPER            ;RANGE = UPPER - LOWER + 1
           SUB     CX,LOWER
           INC     CX
           MUL     CX                  ;RANDOM = (SEED*RANGE)/65536
           ADD     DX,LOWER                ;                    + LOWER
        MOV     AX,DX
        ;POP     BP
        POPF                           ;RESTORE FLAGS
        POP     DS                     ;RESTORE REGISTERS
        ;POP     DX
        ;POP     CX
        RET     4                      ;RETURN (RANDOM)
NRANDOM ENDP                           ;END NRANDOM
        END 
NRANDOM ENDP                           ;END NRANDOM
        END 

Instead of [BP+...]
I dont know how to make it with my procedure for clock time .... MOV     CX,[BP+16] is maybe easier for the compiler than MOV CX,UPPER

I am trying to set it with my procedure for clock time but cant ...

dedndave

delete the

LOWER DW ?
UPPER DW ?

then, try this...

NRANDOM PROC    FAR USES CX DX DS LOWER:WORD,UPPER:WORD
.
.
        pushf
.
.
.
        mov     cx,UPPER
        sub     cx,LOWER
.
.
.
        popf
        ret

the assembler should generate all the code to access the variables on the stack, as well as saving/restoring registers
the values UPPER and LOWER are provided by MAIN when it calls NRANDOM (by pushing them onto the stack)
the assembler also generates the RET 4 at the end

ilian007

I guess I cant get it ...

Assembling: main.ASM
Assembling: nrandom.ASM
nrandom.ASM(33): error A2119: language type must be specified
nrandom.ASM(50): error A2006: undefined symbol : UPPER
nrandom.ASM(51): error A2006: undefined symbol : LOWER
nrandom.ASM(54): error A2006: undefined symbol : LOWER
Assembling: reseed.asm

   
;===================================================================
;                   RAND.ASM
;===================================================================
           .MODEL LARGE
;===================================================================
   PUBLIC SEED
   PUBLIC NRANDOM
;===================================================================
; D A T A   S E G M E N T   D E F I N I T I O N
           .FARDATA
SEED       DW      ?                   ;SEED FOR RANDOM NUMBER GEN.
MULTIPLIER DW      25173               ;MULTIPLIER AND
ADDEND     DW      13849               ;ADDEND FOR MIXED
;===================================================================
; C O D E   S E G M E N T   D E F I N I T I O N
;
           .CODE   
           ASSUME  DS:FAR_DATA
;---------------------------------------------------------------------
                   
   
NRANDOM PROC    FAR USES CX DX DS LOWER:WORD,UPPER:WORD

         
        ;PUSH    CX                     ;( [BP+8] )
        ;PUSH    DX                     ;( [BP+6] )
        PUSH    DS                     
        PUSHF                          ;SAVE FLAGS
       
   ;PUSH    BP                     ;( [BP+0] )
        ;MOV     BP,SP
       
   MOV     AX,FAR_DATA            ;SET DS-REGISTER TO POINT
        MOV     DS,AX                  ;TO FAR DATA SEGMENT
        MOV     AX,SEED             ;X = SEED * MULTIPLIER mod
        MUL     MULTIPLIER          ;                       65536
        ADD     AX,ADDEND           ;SEED = (X + ADDEND) mod 65536
        MOV     SEED,AX
        MOV     CX,UPPER            ;RANGE = UPPER - LOWER + 1
        SUB     CX,LOWER
        INC     CX
        MUL     CX                  ;RANDOM = (SEED*RANGE)/65536
        ADD     DX,LOWER                ;                    + LOWER
        MOV     AX,DX
        ;POP     BP
        POPF                           ;RESTORE FLAGS
        POP     DS                     ;RESTORE REGISTERS
        ;POP     DX
        ;POP     CX
        RET         
NRANDOM ENDP                           ;END NRANDOM

dedndave

ok - you can take push/pop ds out - they are taken care of in the proc directive
however, that is not the problem
i am running a test at the moment - it is almost done
let me finish that and we will take a look

mikey

Well, whichever classmates you guys are, I will see you in about an hour.  I barely got something to work (or it appears to anyway).  I'll post pieces in case someone else reading this is tempted to copy directly.

This is most of my main.asm

;===================================================================
;D A T A   S E G M E N T
;
          .DATA
          PUBLIC  SEED
SEED       DW      5555H
EVENS      DW      0
ODDS       DW      0
HIGHS      DW      0
LOWS       DW      0
;===================================================================
;C O D E   S E G M E N T   D E F I N I T I O N
;
          .CODE
RANDMAIN:
          MOV     AX,DGROUP           ;SET DS AND ES-REGISTER TO
          MOV     DS,AX               ;POINT TO DATA SEGMENT
          MOV     ES,AX               ;
; SET FIRST SEED TO 5555H
          MOV     BL,0                ;
         
SEED_LOOP:
          CALL    RESEED              ;
          PUSH    BX                  ;
          MOV     CX,0                ;INIT. LINE COUNT = 1
LINE_LOOP:
          CMP     CX,10               ;IF LINE COUNT == 10
          JE      END_LINE_LOOP       ;   THEN END LOOP
          INC     CX                  ;COUNT++
          PUSH    CX                  ;
          MOV     CX,0                ;INIT. NUM COUNT = 1
NUM_LOOP:
          CMP     CX,10               ;IF NUM COUNT == 10
          JE      END_NUM_LOOP        ;   THEN END LOOP
          INC     CX                  ;COUNT++
          PUSH    CX                  ;
          MOV     AX,0                ;RAND RANGE, LOWER
          PUSH    AX                  ;
          MOV     AX,9999             ;RAND RANGE, UPPER
          PUSH    AX                  ;
          CALL    RANDOM              ;AX = RANDOM NUMBER
          MOV     BH,1                ;DISP. 16-BIT NUM IN AX
          CALL    PUTDEC$             ;DISP.
          JMP     ADD_STATS           ;
GOT_STATS:
          POP     CX                  ;
          JMP     NUM_LOOP            ;
END_NUM_LOOP:
          CALL    NEWLINE             ;
          POP     CX                  ;
          JMP     LINE_LOOP           ;
END_LINE_LOOP:
; DISPLAY STATS
          LEA     DI,STAT_HDR         ;DISP. STAT_HDR
          MOV     CX,30               ;DISP. 30 CHARS
          CALL    PUTSTRNG            ;DISP.
          CALL    NEWLINE             ;
          MOV     BH,-1               ;DISP. LEFT-JUSTIFY
          MOV     AX,EVENS            ;DISP. EVENS
          CALL    PUTDEC$             ;DISP.
          MOV     AX,ODDS             ;DISP. ODDS
          CALL    PUTDEC$             ;DISP.
          MOV     AX,HIGHS            ;DISP. HIGHS
          CALL    PUTDEC$             ;DISP.
          MOV     AX,LOWS             ;DISP. LOWS
          CALL    PUTDEC$             ;DISP.
         
          MOV     EVENS,0             ;RESET TO ZERO
          MOV     ODDS,0              ;RESET TO ZERO
          MOV     HIGHS,0             ;RESET TO ZERO
          MOV     LOWS,0              ;RESET TO ZERO
         
          POP     BX                  ;IF ALREADY DID CLOCK
          CMP     BL,0                ;SEED, END_SEED_LOOP
          JNE     END_SEED_LOOP       ;ELSE DO CLOCK SEED
          CALL    NEWLINE             ;
          MOV     BL,1                ;
          JMP     SEED_LOOP           ;
END_SEED_LOOP:
          JMP     DONE
         
ADD_STATS:
          PUSH    AX
          PUSH    AX
; IF EVEN, GOTO EVENS
          AND     AX,1
          CMP     AX,0
          JE      IS_EVEN
          INC     ODDS
          JMP     HIGH_LOW
IS_EVEN:
          INC     EVENS
HIGH_LOW:
; IF HIGH, GOTO HIGHS
          POP     AX
          CMP     AX,4999
          JA      IS_HIGH
          INC     LOWS
          JMP     END_ADD_STATS
IS_HIGH:
          INC     HIGHS
END_ADD_STATS:
          POP     AX
          JMP     GOT_STATS


This is the section of my reseed.asm that seems to allow me to access SEED and whatnot

          .DATA
          EXTRN   SEED:WORD
          PUBLIC  MULTIPLIER,ADDEND
MULTIPLIER DW      25173               ;MULTIPLIER AND
ADDEND     DW      13849               ;ADDEND FOR MIXED
                                      ;LINEAR CONGRUENTIAL METHOD
;===================================================================
; C O D E   S E G M E N T
;
          .CODE
          PUBLIC  RESEED
RESEED     PROC    FAR PUBLIC USES BX CX DX DS
                                      ;SAVE REGISTERS (USES LIST)
          PUSHF                       ;SAVE FLAGS
          MOV     AX,DGROUP           ;SET DS-REGISTER TO POINT
          MOV     DS,AX               ;TO LOCAL DATA SEGMENT
          MOV     ES,AX


Here's part of rand.asm, again, the critical part for me that got the variables working

;===================================================================
          .MODEL  SMALL,BASIC
;===================================================================
; D A T A   S E G M E N T  
          .DATA
          EXTRN   SEED:WORD
          EXTRN   MULTIPLIER:WORD
          EXTRN   ADDEND:WORD
;===================================================================
; C O D E   S E G M E N T  
;
          .CODE
          PUBLIC  RANDOM
RANDOM     PROC    FAR PUBLIC USES CX DX DS,
                  LOWER:WORD, UPPER:WORD
                                   ;FUNCTION RANDOM(LOWER,UPPER)
                                      ;SAVE REGISTERS (USES LIST)
          PUSHF                       ;SAVE FLAGS
          MOV     AX,DGROUP           ;SET DS-REGISTER TO POINT
          MOV     DS,AX               ;TO LOCAL DATA SEGMENT
          MOV     ES,AX


I'm sure it looks very ugly to experienced eyes but I'm using what I have available to me.  Like Veronica, I also didn't want to stray too far from the teacher's teachings for fear of losing more points.

dedndave

lol - good job Mikey

ilian:
the PROC directive wants to see a language specified - let me look that up in the handy MASM manual...

dedndave

#101
this one assembles and works
i added the language BASIC to the .MODEL directive...
to follow the BASIC calling convention, i had to swap the order of LOWER and UPPER

;===================================================================
;                   NRANDOM.ASM
;      r a n d o m   n u m b e r   g e n e r a t o r
; GENERATES PSEUDO-RANDOM INTEGERS IN THE RANGE LOWER TO UPPER
; INPUT:  TWO STACK PARAMETERS - LOWER AND UPPER ENDS OF RANGE
; OUTPUT: AX-REG CONTAINS RANDOM INTEGER
; CALLING SEQUENCE:     PUSH    <UPPER END OF RANGE>
;                       PUSH    <LOWER END OF RANGE>
;                       CALL    RANDOM
;===================================================================
         .MODEL  LARGE,BASIC
;===================================================================
        PUBLIC  SEED
        PUBLIC  NRANDOM
;===================================================================
; D A T A   S E G M E N T   D E F I N I T I O N
        .FARDATA
SEED       DW      ?                   ;SEED FOR RANDOM NUMBER GEN.
MULTIPLIER DW      25173               ;MULTIPLIER AND
ADDEND     DW      13849               
;===================================================================
; C O D E   S E G M E N T   D E F I N I T I O N
        .CODE
        ASSUME  DS:FAR_DATA
;===================================================================

NRANDOM PROC    FAR USES CX DX DS UPPER:WORD,LOWER:WORD

        PUSHF                          ;SAVE FLAGS
        MOV     AX,FAR_DATA            ;SET DS-REGISTER TO POINT
        MOV     DS,AX                  ;TO FAR DATA SEGMENT
        MOV     AX,SEED                ;X = SEED * MULTIPLIER mod 65536
        MUL     MULTIPLIER
        ADD     AX,ADDEND              ;SEED = (X + ADDEND) mod 65536
        MOV     SEED,AX
        MOV     CX,UPPER               ;UPPER - RANGE = UPPER - LOWER + 1
        SUB     CX,LOWER               ;LOWER
        INC     CX
        MUL     CX                     ;RANDOM = (SEED*RANGE)/65536
        ADD     DX,LOWER               ;                    + LOWER
        MOV     AX,DX
        POPF                           ;RESTORE FLAGS
        RET                            ;RETURN (NRANDOM)

NRANDOM ENDP                           ;END NRANDOM

        END

ilian007

Thank you DEDNDAVE it all works now. Thanks ! :)

dedndave

#103
well - i know that ASSUME DS:SEG SEED can be done a better way
that would be clumsy if we had to reference several variables in the RESEED module
we just need to figure out how to tell the assembler that SEED is in the FAR_DATA segment
it can probably be specified in the EXTERN directive somehow
then we can use ASSUME DS:FAR_DATA and MOV AX,FAR_DATA
maybe MichaelW or Steve (FORTRANS) can help us out

;===================================================================
;                   RESEED.ASM
; INPUT: BL = 0 - gets a seed value from the time-of day counter
;        BL <> 0 - sets the test seed value of 5555h
;
;===================================================================
        .MODEL  LARGE
;===================================================================
        EXTERN  SEED:WORD
        PUBLIC  RESEED
;===================================================================
; C O D E   S E G M E N T   D E F I N I T I O N
        .CODE
        ASSUME  DS:SEG SEED
;===================================================================

RESEED  PROC    FAR PUBLIC USES AX CX DX DS

        MOV     AX,SEG SEED            ;SET DS-REGISTER TO POINT
        MOV     DS,AX                  ;TO FAR DATA SEGMENT
        MOV     DX,5555h
        OR      BL,BL
        JNZ     NOTZERO

        MOV     AH,0                   ;     SEED = LOWER HALF OF
        INT     1AH                    ;            TIME OF DAY CLOCK

NOTZERO:
        MOV     SEED,DX
        RET

RESEED  ENDP

        END

ilian007

in fact I've changed it to DS:DGROUP and AX,DGROUP and it still works I guess NRANDOM is getting values thru the EXTRNals. originally the teachers procedure has set the DS in NRANDOM that way:

- - - -
  .MODEL  SMALL,BASIC
;===================================================================
FALSE      EQU     0                   ;CONSTANT FALSE
TRUE       EQU     1                   ;CONSTANT TRUE
;===================================================================
; D A T A   S E G M E N T   D E F I N I T I O N
           .FARDATA RAND_DATA
SEED       DW      ?                   ;SEED FOR RANDOM NUMBER GEN.
MULTIPLIER DW      25173               ;MULTIPLIER AND
ADDEND     DW      13849               ;ADDEND FOR MIXED
LOWER      DW      0                           ;LINEAR CONGRUENTIAL UPPER      DW      9999
METHOD
FIRST_CALL DB      TRUE                ;FIRST CALL FLAG
;===================================================================
; C O D E   S E G M E N T   D E F I N I T I O N
;
           .CODE   RAND
           ASSUME  DS:RAND_DATA
;
RANDOM     PROC    FAR PUBLIC USES CX DX DS,
                   LOWER:WORD, UPPER:WORD
                                    ;FUNCTION RANDOM(LOWER,UPPER)
                                       ;SAVE REGISTERS (USES LIST)
           PUSHF                       ;SAVE FLAGS
           MOV     AX,SEG RAND_DATA    ;SET DS-REGISTER TO POINT
           MOV     DS,AX               ;TO LOCAL DATA SEGMENT

- - ->
- - ->