Skip to content

Commit 40e4462

Browse files
authored
Merge pull request #362 from boriel/bugfix/constant_lbound_on_array_parameter
Fix bug with constant LBOUND/UBOUND in param array
2 parents 2269e47 + f2d378a commit 40e4462

File tree

4 files changed

+346
-1
lines changed

4 files changed

+346
-1
lines changed

api/optimize.py

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -123,6 +123,7 @@ def visit_CONST(self, node):
123123

124124
def visit_FUNCCALL(self, node):
125125
node.args = (yield self.generic_visit(node.args)) # Avoid infinite recursion not visiting node.entry
126+
self._check_if_any_arg_is_an_array_and_needs_lbound_or_ubound(node.entry.params, node.args)
126127
yield node
127128

128129
def visit_CALL(self, node):

tests/functional/lbound13.asm

Lines changed: 331 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,331 @@
1+
org 32768
2+
__START_PROGRAM:
3+
di
4+
push ix
5+
push iy
6+
exx
7+
push hl
8+
exx
9+
ld hl, 0
10+
add hl, sp
11+
ld (__CALL_BACK__), hl
12+
ei
13+
ld hl, _x
14+
push hl
15+
call _maxValue
16+
ld (_y), a
17+
ld hl, 0
18+
ld b, h
19+
ld c, l
20+
__END_PROGRAM:
21+
di
22+
ld hl, (__CALL_BACK__)
23+
ld sp, hl
24+
exx
25+
pop hl
26+
exx
27+
pop iy
28+
pop ix
29+
ei
30+
ret
31+
__CALL_BACK__:
32+
DEFW 0
33+
_maxValue:
34+
push ix
35+
ld ix, 0
36+
add ix, sp
37+
ld hl, 0
38+
push hl
39+
push hl
40+
inc sp
41+
ld hl, 1
42+
push hl
43+
ld l, (ix+4)
44+
ld h, (ix+5)
45+
call __LBOUND
46+
ld (ix-3), l
47+
ld (ix-2), h
48+
jp __LABEL0
49+
__LABEL3:
50+
ld a, (ix-1)
51+
push af
52+
ld l, (ix-3)
53+
ld h, (ix-2)
54+
push hl
55+
push ix
56+
pop hl
57+
ld de, 4
58+
add hl, de
59+
call __ARRAY_PTR
60+
pop af
61+
cp (hl)
62+
jp nc, __LABEL6
63+
ld l, (ix-3)
64+
ld h, (ix-2)
65+
push hl
66+
push ix
67+
pop hl
68+
ld de, 4
69+
add hl, de
70+
call __ARRAY_PTR
71+
ld a, (hl)
72+
ld (ix-1), a
73+
__LABEL6:
74+
__LABEL4:
75+
ld l, (ix-3)
76+
ld h, (ix-2)
77+
inc hl
78+
ld (ix-3), l
79+
ld (ix-2), h
80+
__LABEL0:
81+
ld l, (ix-3)
82+
ld h, (ix-2)
83+
push hl
84+
ld hl, 1
85+
push hl
86+
ld l, (ix+4)
87+
ld h, (ix+5)
88+
call __UBOUND
89+
pop de
90+
or a
91+
sbc hl, de
92+
jp nc, __LABEL3
93+
__LABEL2:
94+
ld a, (ix-1)
95+
_maxValue__leave:
96+
ld sp, ix
97+
pop ix
98+
exx
99+
pop hl
100+
ex (sp), hl
101+
exx
102+
ret
103+
#line 1 "array.asm"
104+
; vim: ts=4:et:sw=4:
105+
; Copyleft (K) by Jose M. Rodriguez de la Rosa
106+
; (a.k.a. Boriel)
107+
; http://www.boriel.com
108+
; -------------------------------------------------------------------
109+
; Simple array Index routine
110+
; Number of total indexes dimensions - 1 at beginning of memory
111+
; HL = Start of array memory (First two bytes contains N-1 dimensions)
112+
; Dimension values on the stack, (top of the stack, highest dimension)
113+
; E.g. A(2, 4) -> PUSH <4>; PUSH <2>
114+
; For any array of N dimension A(aN-1, ..., a1, a0)
115+
; and dimensions D[bN-1, ..., b1, b0], the offset is calculated as
116+
; O = [a0 + b0 * (a1 + b1 * (a2 + ... bN-2(aN-1)))]
117+
; What I will do here is to calculate the following sequence:
118+
; ((aN-1 * bN-2) + aN-2) * bN-3 + ...
119+
#line 1 "mul16.asm"
120+
__MUL16: ; Mutiplies HL with the last value stored into de stack
121+
; Works for both signed and unsigned
122+
PROC
123+
LOCAL __MUL16LOOP
124+
LOCAL __MUL16NOADD
125+
ex de, hl
126+
pop hl ; Return address
127+
ex (sp), hl ; CALLEE caller convention
128+
__MUL16_FAST:
129+
ld b, 16
130+
ld a, h
131+
ld c, l
132+
ld hl, 0
133+
__MUL16LOOP:
134+
add hl, hl ; hl << 1
135+
sla c
136+
rla ; a,c << 1
137+
jp nc, __MUL16NOADD
138+
add hl, de
139+
__MUL16NOADD:
140+
djnz __MUL16LOOP
141+
ret ; Result in hl (16 lower bits)
142+
ENDP
143+
#line 20 "array.asm"
144+
#line 24 "/zxbasic/library-asm/array.asm"
145+
__ARRAY_PTR: ;; computes an array offset from a pointer
146+
ld c, (hl)
147+
inc hl
148+
ld h, (hl)
149+
ld l, c
150+
__ARRAY:
151+
PROC
152+
LOCAL LOOP
153+
LOCAL ARRAY_END
154+
LOCAL RET_ADDRESS ; Stores return address
155+
LOCAL TMP_ARR_PTR ; Stores pointer temporarily
156+
ld e, (hl)
157+
inc hl
158+
ld d, (hl)
159+
inc hl
160+
ld (TMP_ARR_PTR), hl
161+
ex de, hl
162+
ex (sp), hl ; Return address in HL, array address in the stack
163+
ld (RET_ADDRESS + 1), hl ; Stores it for later
164+
exx
165+
pop hl ; Will use H'L' as the pointer
166+
ld c, (hl) ; Loads Number of dimensions from (hl)
167+
inc hl
168+
ld b, (hl)
169+
inc hl ; Ready
170+
exx
171+
ld hl, 0 ; HL = Offset "accumulator"
172+
LOOP:
173+
#line 62 "/zxbasic/library-asm/array.asm"
174+
pop bc ; Get next index (Ai) from the stack
175+
#line 72 "/zxbasic/library-asm/array.asm"
176+
add hl, bc ; Adds current index
177+
exx ; Checks if B'C' = 0
178+
ld a, b ; Which means we must exit (last element is not multiplied by anything)
179+
or c
180+
jr z, ARRAY_END ; if B'Ci == 0 we are done
181+
ld e, (hl) ; Loads next dimension into D'E'
182+
inc hl
183+
ld d, (hl)
184+
inc hl
185+
push de
186+
dec bc ; Decrements loop counter
187+
exx
188+
pop de ; DE = Max bound Number (i-th dimension)
189+
call __FNMUL
190+
jp LOOP
191+
ARRAY_END:
192+
ld a, (hl)
193+
exx
194+
#line 101 "/zxbasic/library-asm/array.asm"
195+
LOCAL ARRAY_SIZE_LOOP
196+
ex de, hl
197+
ld hl, 0
198+
ld b, a
199+
ARRAY_SIZE_LOOP:
200+
add hl, de
201+
djnz ARRAY_SIZE_LOOP
202+
#line 111 "/zxbasic/library-asm/array.asm"
203+
ex de, hl
204+
ld hl, (TMP_ARR_PTR)
205+
ld a, (hl)
206+
inc hl
207+
ld h, (hl)
208+
ld l, a
209+
add hl, de ; Adds element start
210+
RET_ADDRESS:
211+
jp 0
212+
;; Performs a faster multiply for little 16bit numbs
213+
LOCAL __FNMUL, __FNMUL2
214+
__FNMUL:
215+
xor a
216+
or h
217+
jp nz, __MUL16_FAST
218+
or l
219+
ret z
220+
cp 33
221+
jp nc, __MUL16_FAST
222+
ld b, l
223+
ld l, h ; HL = 0
224+
__FNMUL2:
225+
add hl, de
226+
djnz __FNMUL2
227+
ret
228+
TMP_ARR_PTR:
229+
DW 0 ; temporary storage for pointer to tables
230+
ENDP
231+
#line 92 "lbound13.bas"
232+
#line 1 "bound.asm"
233+
; ---------------------------------------------------------
234+
; Copyleft (k)2011 by Jose Rodriguez (a.k.a. Boriel)
235+
; http://www.boriel.com
236+
;
237+
; ZX BASIC Compiler http://www.zxbasic.net
238+
; This code is released under the BSD License
239+
; ---------------------------------------------------------
240+
; Implements both LBOUND(array, N) and UBOUND(array, N) function
241+
; Parameters:
242+
; HL = PTR to array
243+
; [stack - 2] -> N (dimension)
244+
PROC
245+
LOCAL __BOUND
246+
LOCAL __DIM_NOT_EXIST
247+
LOCAL __CONT
248+
__LBOUND:
249+
ld a, 4
250+
jr __BOUND
251+
__UBOUND:
252+
ld a, 6
253+
__BOUND:
254+
ex de, hl ; DE <-- Array ptr
255+
pop hl ; HL <-- Ret address
256+
ex (sp), hl ; CALLEE: HL <-- N, (SP) <-- Ret address
257+
ex de, hl ; DE <-- N, HL <-- ARRAY_PTR
258+
push hl
259+
ld c, (hl)
260+
inc hl
261+
ld h, (hl)
262+
ld l, c ; HL = start of dimension table (first position contains number of dimensions - 1)
263+
ld c, (hl)
264+
inc hl
265+
ld b, (hl)
266+
inc bc ; Number of total dimensions of the array
267+
pop hl ; Recovers ARRAY PTR
268+
ex af, af' ; Saves A for later
269+
ld a, d
270+
or e
271+
jr nz, __CONT ; N = 0 => Return number of dimensions
272+
;; Return the number of dimensions of the array
273+
ld h, b
274+
ld l, c
275+
ret
276+
__CONT:
277+
dec de
278+
ex af, af' ; Recovers A (contains PTR offset)
279+
ex de, hl ; HL = N (dimension asked) - 1, DE = Array PTR
280+
or a
281+
sbc hl, bc ; if no Carry => the user asked for a dimension that does not exist. Return 0
282+
jr nc, __DIM_NOT_EXIST
283+
add hl, bc ; restores HL = (N - 1)
284+
add hl, hl ; hl *= 2
285+
ex de, hl ; hl = ARRAY_PTR + 3, DE jsz = (N - 1) * 2
286+
ld b, 0
287+
ld c, a
288+
add hl, bc ; HL = &BOUND_PTR
289+
ld a, (hl)
290+
inc hl
291+
ld h, (hl)
292+
ld l, a ; LD HL, (HL) => Origin of L/U Bound table
293+
add hl, de ; hl += OFFSET __LBOUND._xxxx
294+
ld e, (hl) ; de = (hl)
295+
inc hl
296+
ld d, (hl)
297+
ex de, hl ; hl = de => returns result in HL
298+
ret
299+
__DIM_NOT_EXIST:
300+
; The dimension requested by the user does not exists. Return 0
301+
ld hl, 0
302+
ret
303+
ENDP
304+
#line 93 "lbound13.bas"
305+
ZXBASIC_USER_DATA:
306+
_y:
307+
DEFB 00
308+
_x:
309+
DEFW __LABEL7
310+
_x.__DATA__.__PTR__:
311+
DEFW _x.__DATA__
312+
DEFW _x.__LBOUND__
313+
DEFW _x.__UBOUND__
314+
_x.__DATA__:
315+
DEFB 01h
316+
DEFB 02h
317+
DEFB 03h
318+
DEFB 04h
319+
DEFB 05h
320+
__LABEL7:
321+
DEFW 0000h
322+
DEFB 01h
323+
_x.__LBOUND__:
324+
DEFW 0000h
325+
_x.__UBOUND__:
326+
DEFW 0004h
327+
; Defines DATA END --> HEAP size is 0
328+
ZXBASIC_USER_DATA_END:
329+
; Defines USER DATA Length in bytes
330+
ZXBASIC_USER_DATA_LEN EQU ZXBASIC_USER_DATA_END - ZXBASIC_USER_DATA
331+
END

tests/functional/lbound13.bas

Lines changed: 13 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,13 @@
1+
2+
FUNCTION maxValue(a() as UByte) as UByte
3+
DIM result as UByte = 0
4+
DIM i as Uinteger
5+
FOR i = LBOUND(a, 1) TO UBOUND(a, 1)
6+
IF result < a(i) THEN result = a(i)
7+
NEXT i
8+
RETURN result
9+
END FUNCTION
10+
11+
DIM x(4) As UByte => {1, 2, 3, 4, 5}
12+
LET y = maxValue(x)
13+

zxb/zxbparser.py

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -3270,7 +3270,7 @@ def p_expr_lbound_expr(p):
32703270
p[0] = None
32713271
return
32723272

3273-
if is_number(num) and entry.scope: # Try constant propagation
3273+
if is_number(num) and entry.scope in (SCOPE.local, SCOPE.global_): # Try constant propagation
32743274
val = num.value
32753275
if val < 0 or val > len(entry.bounds):
32763276
syntax_error(p.lineno(6), "Dimension out of range")

0 commit comments

Comments
 (0)