English Amiga Board


Go Back   English Amiga Board > Coders > Coders. General

 
 
Thread Tools
Old 12 April 2007, 20:35   #1
BippyM
Global Moderator
 
BippyM's Avatar
 
Join Date: Nov 2001
Location: Derby, UK
Age: 48
Posts: 9,355
code explanation

Hi guys

I'm disassembling a program which intercepts keyboard routines and allows cd32 pad to be used instead.

Now i've figured most of it out but the following is a bit confusing (what is it doing)

Code:
ReadJoyPort1
	MOVEM.L	D0-D7/A0-A6,-(SP)
	MOVE.L	#1,D0					;Port to read
	MOVEA.L	(_LowLevelBase).L,A6		;Lowlevel into a6
	JSR		(_LVOReadJoyPort,A6)		;Read the pad
	BSR.W		lbC0000F2			;Check the pad buttons
	MOVEM.L	(SP)+,D0-D7/A0-A6
	LEA		($DFF000).L,A5		;Replace code we overwrote
	dc.w		$4EF9				;Jump to continue game
ContinueAddress
	dc.l		0				; Holds addresss for game to continue

lbC0000F2
	MOVE.L		D0,D1				;Button pressed to d1
	MOVE.L		(lbL00076C).L,D2		;What is this as it is tested
	MOVEA.L	(_KeyBoardRoutine).L,A0	;Start of keyboard routine ingame
	BTST		#$12,D1			;Test for left shoulder pad
	BEQ.W		lbC000126			;No branch ahead
	BTST		#$12,D2			;Tst D2 WHAT IS THIS TESTING FOR?
	BNE.W		lbC000144			;No branch to next button check
	BSET		#$12,D2			;Set bit 12
	MOVE.B		#$64,D0			;Left alt raw keycode
	MOVEM.L	D1/D2/A0,-(SP)		;preserve regs
	JSR		(A0)				;Branch to game
	MOVEM.L	(SP)+,D1/D2/A0		;Restore Regs
	BRA.W		lbC000144			;Check Right shoulder

;WHAT IS THIS NEXT SUBROUTINE DOING EXACTLY?

lbC000126
	BTST		#$12,D2
	BEQ.W		lbC000144
	BCLR		#$12,D2
	MOVE.B		#$E4,D0
	MOVEM.L	D1/D2/A0,-(SP)
	JSR		(A0)
	MOVEM.L	(SP)+,D1/D2/A0
	BRA.W		lbC000144

lbL00076C						;WHAT IS THIS?
	dcb.l	$3F,0
	dcb.l	4,0

Last edited by BippyM; 12 April 2007 at 21:19.
BippyM is offline  
Old 12 April 2007, 21:11   #2
BippyM
Global Moderator
 
BippyM's Avatar
 
Join Date: Nov 2001
Location: Derby, UK
Age: 48
Posts: 9,355
Added More Commenting To The Code
BippyM is offline  
Old 12 April 2007, 21:45   #3
Joe Maroni
Moderator
 
Joe Maroni's Avatar
 
Join Date: Feb 2003
Location: Germany
Age: 44
Posts: 1,303
Send a message via MSN to Joe Maroni
can you please post the code of lbC000144 ???

that would make it more understandable...
Joe Maroni is offline  
Old 12 April 2007, 21:46   #4
BippyM
Global Moderator
 
BippyM's Avatar
 
Join Date: Nov 2001
Location: Derby, UK
Age: 48
Posts: 9,355
that is the same as lbC0000F2 it's just a different button

Code:
lbC000144
	BTST	#$13,D1
	BEQ.W	lbC00016A
	BTST	#$13,D2
	BNE.W	lbC000188
	BSET	#$13,D2
	MOVE.B	#$65,D0	;Right Alt
	MOVEM.L	D1/D2/A0,-(SP)
	JSR	(A0)
	MOVEM.L	(SP)+,D1/D2/A0
	BRA.W	lbC000188
BippyM is offline  
Old 13 April 2007, 00:07   #5
BippyM
Global Moderator
 
BippyM's Avatar
 
Join Date: Nov 2001
Location: Derby, UK
Age: 48
Posts: 9,355
anyone?
BippyM is offline  
Old 13 April 2007, 10:01   #6
Asman
68k
 
Asman's Avatar
 
Join Date: Sep 2005
Location: Somewhere
Posts: 828
Hi

Please send me full resource file with this code or give me executable with this code then I look at this saturday

Gretz
Asman is offline  
Old 13 April 2007, 10:31   #7
BippyM
Global Moderator
 
BippyM's Avatar
 
Join Date: Nov 2001
Location: Derby, UK
Age: 48
Posts: 9,355
It's already in the zone

I've done more to it since then, and corrected some errors.

It's called SlamTiltCD32.rar

thanks
BippyM is offline  
Old 13 April 2007, 11:38   #8
Asman
68k
 
Asman's Avatar
 
Join Date: Sep 2005
Location: Somewhere
Posts: 828
Hi

After short look I think that lbL00076C is previous_state_of_pad and it's used for generate proper key value ( pressed or not ). You know it's simply bit field. It looks like copy of previous bit field returned by _LVOReadJoyPort.

Gretz
Asman is offline  
Old 13 April 2007, 12:39   #9
BippyM
Global Moderator
 
BippyM's Avatar
 
Join Date: Nov 2001
Location: Derby, UK
Age: 48
Posts: 9,355
can you comment the routine for me as I still don't follow.
BippyM is offline  
Old 13 April 2007, 12:44   #10
Asman
68k
 
Asman's Avatar
 
Join Date: Sep 2005
Location: Somewhere
Posts: 828
Yes, I will do that. I will prepare my version of the SlamTiltAddCD32Pad with my comments.
Asman is offline  
Old 13 April 2007, 12:45   #11
BippyM
Global Moderator
 
BippyM's Avatar
 
Join Date: Nov 2001
Location: Derby, UK
Age: 48
Posts: 9,355
just comment the 1 or 2 routines if you don't mind, I am using it to help me understand etc and want to comment as much as I can
BippyM is offline  
Old 13 April 2007, 13:09   #12
BippyM
Global Moderator
 
BippyM's Avatar
 
Join Date: Nov 2001
Location: Derby, UK
Age: 48
Posts: 9,355
Does d2 contain $000003f4
BippyM is offline  
Old 13 April 2007, 14:24   #13
Asman
68k
 
Asman's Avatar
 
Join Date: Sep 2005
Location: Somewhere
Posts: 828
When patched routine ran first time then D2 = 0, because (lbL00076C) = 0. So

Code:
lbL00076C
        dcb.l	$3F,0
        dcb.l	4,0
mean allocate $3f+4 longwords ( I don't know why resourcer optimize to $3f and not show proper $43 ) and set to zeroes. Old assemblers like seka use "blk" instead of "dcb" for allocate and fill memory. Check Asm-One guide or Barfly guide.
I don't know why programmer allocate $3f+4 = $43 longwords, because as I see only first longword is used ( maybe for future ). Keep in the mind that this patch is ran every frame ( my assumption ), but i think that you know
Asman is offline  
Old 26 April 2007, 08:48   #14
Asman
68k
 
Asman's Avatar
 
Join Date: Sep 2005
Location: Somewhere
Posts: 828
Hi

This is the source with my comments ( not finished ). Because i think that oryginal source from SlamTilitCd32Pad has bugs ( some jumps and keycodes are wrong ) I have show you fixed version. ( see MACRO emulate_key )

Code:
;
; $Id: SlamTiltAddCD32Pad.asm 1.5 2007/04/22 20:12:56 Asman Exp Asman $
;
;%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%

	INCDIR	Includes:

	INCLUDE	lvo/exec.i
	INCLUDE	lvo/dos.i
	INCLUDE	lvo/intuition.i	
	INCLUDE	lvo/lowlevel.i

	INCLUDE	intuition/intuition.i
	INCLUDE	libraries/lowlevel.i

;%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%

;; direction
;
;JPB_JOY_RIGHT		= 0
;JPB_JOY_LEFT		= 1
;JPB_JOY_DOWN		= 2
;JPB_JOY_UP		= 3
;
;
;; buttons
;
;JPB_BUTTON_PLAY	= $11
;JPB_BUTTON_REVERSE	= $12
;JPB_BUTTON_FORWARD	= $13
;JPB_BUTTON_GREEN	= $14
;JPB_BUTTON_YELLOW	= $15
;JPB_BUTTON_RED		= $16
;JPB_BUTTON_BLUE	= $17

;%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%

Emulate_Key	MACRO

;\1 JPB bit from lowlevel.i ( for example JPB_BUTTON_PLAY )
;\2 key ( rawkey ) ( for example KEY_ALT or $64 )


	;button or direct was pressed ?
		btst	#JPB_\1,d1
		beq.w	.free_key\@

	;if last time the same was pressed then jump to next key
		btst	#JPB_\1,d2
		bne.w	.next_key\@

	;set appropriate bit in prev / last cd32pad bit state
		bset	#JPB_\1,d2

	;emulate key ( press )
		move.b	#\2,d0

	;call routine from SlamTilt ( decode key routine )
		movem.l	d1/d2/a0,-(sp)
		jsr	(a0)
		movem.l	(sp)+,d1/d2/a0

		bra.w	.next_key\@

.free_key\@

	;is this real reason to emulate ( unpressed key )
		btst	#JPB_\1,d2
		beq.w	.next_key\@

	;clean proper bit in prev / last cd32pad bit state
		bclr	#JPB_\1,d2

	;emulate key ( unpress )
		move.b	#\2+$80,d0

	;call routine form SlamTilt ( decode key routine )
		movem.l	d1/d2/a0,-(sp)
		jsr	(a0)
		movem.l	(sp)+,d1/d2/a0
		
		bra.w	.next_key\@


.next_key\@



	ENDM


;%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%

	SECTION	CodeSlamTiltAddCD32Pad,CODE

ProgStart
		movem.l	d0-d7/a0-a6,-(sp)

		bsr.w	show_author_window

	; open lovlevel library
		moveq	#0,d0
		lea	(LowLevelName).l,a1
		movea.l	(4).w,a6
		jsr	(_LVOOpenLibrary,a6)
		move.l	d0,(LowLevelBase).l
		beq.w	.exit

	; open dos library
		moveq	#0,d0
		lea	(DosName).l,a1
		jsr	(_LVOOpenLibrary,a6)
		move.l	d0,(DosBase).l
		beq.w	.closeLowLevel

	; load exe
		move.l	#game_name,d1
		movea.l	(DosBase).l,a6
		jsr	(_LVOLoadSeg,a6)
		move.l	d0,(game_seglist).l
		beq.w	.closeDos

		lsl.l	#2,d0
		addq.l	#4,d0
		move.l	d0,(start_game_adr).l
		move.l	d0,d1
		addi.l	#$ED2,d0
		movea.l	d0,a0
		move.w	#$4EF9,(a0)
		move.l	#patch_CD32,(2,a0)
		lea	(6,a0),a1	;a1 = game.exe + $ed2+6 
		move.l	a1,(back_from_patch_adr).l
		addi.l	#$52F0,d1
		move.l	d1,(DecodeKeyRoutineAdr).l
		movem.l	(sp)+,d0-d7/a0-a6
		movea.l	(start_game_adr).l,a1
		jsr	(a1)
		movem.l	d0-d7/a0-a6,-(sp)
		move.l	(game_seglist).l,d1
		movea.l	(DosBase).l,a6
		jsr	(_LVOUnLoadSeg,a6)

.closeDos	movea.l	(DosBase).l,a1
		movea.l	(4).w,a6
		jsr	(_LVOCloseLibrary,a6)

.closeLowLevel	movea.l	(LowLevelBase).l,a1
		movea.l	(4).w,a6
		jsr	(_LVOCloseLibrary,a6)

.exit	movem.l	(sp)+,d0-d7/a0-a6
		rts

;/%/%/%/%/%/%/%/%/%/%/%/%/%/%/%/%/%/%/%/%/%/%/%/%/%/%/%/%/%/%/%/%/%/%/%/%/%/%/

patch_CD32	movem.l	d0-d7/a0-a6,-(sp)
		move.l	#1,d0			;port number
		movea.l	(LowLevelBase).l,a6
		jsr	(_LVOReadJoyPort,a6)
	;d0 =

	;JPB_

		bsr.w	convert_pad_buttons
		movem.l	(sp)+,d0-d7/a0-a6
		lea	($DFF000).l,a5	;oryginal code from game.exe
		dc.w	$4EF9
back_from_patch_adr	dc.l	0


;; direction
;
;JPB_JOY_RIGHT		= 0
;JPB_JOY_LEFT		= 1
;JPB_JOY_DOWN		= 2
;JPB_JOY_UP		= 3
;
;
;; buttons
;
;JPB_BUTTON_PLAY	= $11
;JPB_BUTTON_REVERSE	= $12
;JPB_BUTTON_FORWARD	= $13
;JPB_BUTTON_GREEN	= $14
;JPB_BUTTON_YELLOW	= $15
;JPB_BUTTON_RED		= $16
;JPB_BUTTON_BLUE	= $17

KEY_LEFT_ALT	= $64
KEY_RIGHT_ALT	= $65
KEY_SPACE	= $40
KEY_LEFT_AMIGA	= $66
KEY_RIGHT_AMIGA	= $67
KEY_LEFT_SHIFT	= $60
KEY_RIGHT_SHIFT = $61
KEY_ENTER	= $44
KEY_P		= $19
KEY_DEL		= $46
KEY_HELP	= $57





; CD32 buttons --> keyboard
;
convert_pad_buttons
		move.l	d0,d1
		move.l	(Previous_ReadJoyPort).l,d2
		movea.l	(DecodeKeyRoutineAdr).l,a0


		Emulate_Key	BUTTON_REVERSE,$64	;left alt
		Emulate_Key	BUTTON_FORWARD,$65	;right alt


		Emulate_Key	JOY_UP,$40		;space
		Emulate_Key	JOY_LEFT,$66		;left amiga
		Emulate_Key	JOY_RIGHT,$67		;right amiga


		Emulate_Key	BUTTON_GREEN,$60	;left shift
		Emulate_Key	BUTTON_YELLOW,$61	;right shift

		Emulate_Key	JOY_DOWN,$44		;enter

		Emulate_Key	BUTTON_PLAY,$19		;key 'p'
		Emulate_Key	BUTTON_RED,$46		;DEL

		Emulate_Key	BUTTON_BLUE,$57		;HELP


	;recognize pause and unpause

lbC0003EC	btst	#$11,d1
		beq.w	lbC000426
		tst.b	d1
		beq.w	lbC000450
		tst.b	(lbB000878).l
		bne.w	lbC000450
		move.l	a0,-(sp)
		lea	(lbB000878).l,a0
		move.b	(a0,d1.w),d0
		movea.l	(sp)+,a0
		move.b	d0,(lbB000878).l
		movem.l	d1/d2/a0,-(sp)
		jsr	(a0)
		movem.l	(sp)+,d1/d2/a0
		bra.w	lbC000450
lbC000426	tst.b	(lbB000878).l
		beq.w	lbC000450
		move.b	(lbB000878).l,d0
		addi.b	#$80,d0
		move.b	#0,(lbB000878).l
		movem.l	d1/d2/a0,-(sp)
		jsr	(a0)
		movem.l	(sp)+,d1/d2/a0
		bra.w	lbC000450

lbC000450	move.l	d2,(Previous_ReadJoyPort).l
		rts
lbC000458	rts


;/%/%/%/%/%/%/%/%/%/%/%/%/%/%/%/%/%/%/%/%/%/%/%/%/%/%/%/%/%/%/%/%/%/%/%/%/%/%/

show_author_window
		movem.l	d0-d7/a0-a6,-(sp)
		
	;open intuition library
		moveq	#0,d0
		lea	(IntuitionName).l,a1
		movea.l	(4).w,a6
		jsr	(_LVOOpenLibrary,a6)
		move.l	d0,(IntuiBase).l
		beq.w	.exit

	;open window
		lea	(NewWindowStruct).l,a0
		movea.l	(IntuiBase).l,a6
		jsr	(_LVOOpenWindow,a6)
		move.l	d0,(window).l
		beq.w	.close_intuition
	
		bsr.w	print_author_info

	;window loop ( wait for close window or press any key )
		movea.l	(window).l,a0
		movea.l	(wd_UserPort,a0),a0
		movea.l	a0,a2
.loop		movea.l	a2,a0
		movea.l	(4).w,a6
		jsr	(_LVOWaitPort,a6)
		movea.l	a2,a0
		movea.l	(4).w,a6
		jsr	(_LVOGetMsg,a6)
		movea.l	d0,a1
		movea.l	d0,a3
		movea.l	(4).w,a6
		jsr	(_LVOReplyMsg,a6)
		cmpi.l	#IDCMP_CLOSEWINDOW,(im_Class,a3)
		beq.b	.closeWindow
		cmpi.l	#IDCMP_RAWKEY,(im_Class,a3)
		bne.w	.loop

.closeWindow	movea.l	(window).l,a0
		movea.l	(IntuiBase).l,a6
		jsr	(_LVOCloseWindow,a6)

	;close intuition library
		movea.l	(IntuiBase).l,a1
		movea.l	(4).w,a6
		jsr	(_LVOCloseLibrary,a6)
		movem.l	(sp)+,d0-d7/a0-a6
		rts

.close_intuition
		movea.l	(IntuiBase).l,a1
		movea.l	(4).w,a6
		jsr	(_LVOCloseLibrary,a6)

.exit		movem.l	(sp)+,d0-d7/a0-a6
		rts


;/%/%/%/%/%/%/%/%/%/%/%/%/%/%/%/%/%/%/%/%/%/%/%/%/%/%/%/%/%/%/%/%/%/%/%/%/%/%/

print_author_info
		moveq	#8,d0	;left offset
		moveq	#$14,d1	;top offset

.loop		movea.l	(tab_ptr).l,a0
		move.l	(a0),(IText_ptr).l
		beq.w	.exit

		adda.l	#4,a0
		move.l	a0,(tab_ptr).l

	;print one line on window
		movem.l	d0/d1,-(sp)
		movea.l	(window).l,a0
		movea.l	(wd_RPort,a0),a0		;a0 = rastport of win
		lea	(IntuiTextStruct).l,a1
		movea.l	(IntuiBase).l,a6
		jsr	(_LVOPrintIText,a6)
		movem.l	(sp)+,d0/d1

		addi.l	#8,d1	;8 pixels down
		bra.w	.loop

.exit		rts

	;!!!unused word
		dc.w	0

;%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%

	SECTION	DataSlamTiltAddCD32Pad,DATA

IntuiBase	dc.l	0
IntuitionName	dc.b	'intuition.library',0
tab_ptr	dc.l	tab_text_ptr
tab_text_ptr	dc.l	TextLine_0
		dc.l	TextLine_1
		dc.l	TextLine_2
		dc.l	TextLine_3
		dc.l	TextLine_4
		dc.l	TextLine_5
		dc.l	TextLine_6
		dc.l	TextLine_7
		dc.l	TextLine_8
		dc.l	TextLine_9
		dc.l	TextLine_10
		dc.l	TextLine_11
		dc.l	TextLine_12
		dc.l	TextLine_13
		dc.l	0

TextLine_0	dc.b	'<bing>(Advertisment)',0
TextLine_1	dc.b	'If you like this patch and want to give me s'
		dc.b	'omething in',0
TextLine_2	dc.b	'return please snail mail me a tape of music '
		dc.b	'artist/s you',0
TextLine_3	dc.b	'like(only Alternative music please,no mainst'
		dc.b	'ream or over',0
TextLine_4	dc.b	'repetitive techno/trance/hardcore)',0
TextLine_5	dc.w	0
TextLine_6	dc.b	' ',0
TextLine_7	dc.b	'My @snail mail address:',0
TextLine_8	dc.b	' ',0
TextLine_9	dc.b	'Andre Barton',0
TextLine_10	dc.b	'60 Purchas St',0
TextLine_11	dc.b	'St Albans',0
TextLine_12	dc.b	'Christchurch',0
TextLine_13	dc.b	'New Zealand',0

window	dc.l	0

NewWindowStruct	dc.w	$4B	;leftEdge
		dc.w	$32	;topEdge
		dc.w	480	;Width
		dc.w	150	;Height
		dc.b	$FF	;DetailPen
		dc.b	$FF	;BlockPen
		dc.l	(IDCMP_NEWSIZE|IDCMP_RAWKEY)	;IDCMP_flags
		dc.l	(WFLG_SIZEGADGET|WFLG_DRAGBAR|WFLG_DEPTHGADGET|WFLG_CLOSEGADGET)
		dc.l	0	;FirstGadget
		dc.l	0	;CheckMark
		dc.l	WinTitle	;Title
		dc.l	0	;Screen
		dc.l	0	;Bitmap
		dc.w	14	;MinWidth
		dc.w	14	;MinHeight
		dc.w	$168	;MaxWidth
		dc.w	$100	;MaxHeight
		dc.w	WBENCHSCREEN	;Type

WinTitle	dc.b	'SlamTiltAddCD32Pad',0,0


IntuiTextStruct	dc.b	1
		dcb.b	3,0
		dcb.w	2,0
		dc.l	0
IText_ptr	dcb.l	2,0

LowLevelBase	dc.l	0
DosBase	dc.l	0
game_seglist	dcb.l	2,0
start_game_adr	dc.l	0
DecodeKeyRoutineAdr	dc.l	lbC000458
		dc.l	0
Previous_ReadJoyPort
		dcb.l	$3F,0
		dcb.l	4,0
lbB000878	dc.b	0
		dc.b	$52
		dc.b	$56
		dc.b	0
		dc.b	$54
		dc.b	$53
		dc.b	$55
		dc.b	0
		dc.b	$50
		dc.b	$51
		dc.b	$57
		dc.b	0
LowLevelName	dc.b	'lowlevel.library',0
DosName		dc.b	'dos.library',0
game_name	dc.b	'game.exe',0

; version information
		dc.b	'SlamTiltExtrabuttons v1.0 by Andre Barton',0
Any question are welcome.
Asman is offline  
Old 26 April 2007, 09:38   #15
BippyM
Global Moderator
 
BippyM's Avatar
 
Join Date: Nov 2001
Location: Derby, UK
Age: 48
Posts: 9,355
Asman that is cool

I have also commented mine, tho not quite finished yet.. I'm not going to look at yours because I want to do this myself and have it checked before improving the prog
BippyM is offline  
Old 30 April 2007, 17:45   #16
Asman
68k
 
Asman's Avatar
 
Join Date: Sep 2005
Location: Somewhere
Posts: 828
Hi

I check oryginal version SlamTiltCd32Pad and this patch don't work properly.
( do tests on my amiga + cd32 pad )
So this patch works only when you choose table and press F1 or other F keys. For CD32 users this is not enough or useless ( how go to the table ? ).
I think that new version of this patch is necessary.

Gretz
Asman is offline  
Old 30 April 2007, 17:47   #17
BippyM
Global Moderator
 
BippyM's Avatar
 
Join Date: Nov 2001
Location: Derby, UK
Age: 48
Posts: 9,355
this is why i am dis-assembling it

I plan to implement the missing stuff from menu's
BippyM is offline  
Old 30 April 2007, 17:51   #18
Asman
68k
 
Asman's Avatar
 
Join Date: Sep 2005
Location: Somewhere
Posts: 828
I do tests with patch and add cursors as some buttons and still don't work. Thats mean that exist another routine for keyboard in title menu. You must resource game.exe
Asman is offline  
Old 30 April 2007, 18:42   #19
BippyM
Global Moderator
 
BippyM's Avatar
 
Join Date: Nov 2001
Location: Derby, UK
Age: 48
Posts: 9,355
yeah i'll do it with winuae debugger

i'm going to be offline for a week or 2 soon so I'll need something to do
BippyM is offline  
Old 01 May 2007, 14:12   #20
Asman
68k
 
Asman's Avatar
 
Join Date: Sep 2005
Location: Somewhere
Posts: 828
hi

I have upload to the Zone final version of SlamTiltCD32Pad ( source )

Gretz

Last edited by Asman; 01 May 2007 at 14:23.
Asman is offline  
 


Currently Active Users Viewing This Thread: 1 (0 members and 1 guests)
 
Thread Tools

Similar Threads
Thread Thread Starter Forum Replies Last Post
Need explanation of a demo effect - screen zoom/rotate Dunny support.Demos 21 21 April 2023 20:47
Connecting Amiga to TV - Explanation needed for a moron (me) vroom6sri support.Hardware 16 01 October 2010 09:18
whdload decent explanation ? marcolau project.WHDLoad 5 01 December 2009 16:43
Selling the lot. eBay links and explanation skote MarketPlace 3 07 June 2008 21:10
Error explanation?? ORSM T support.Hardware 7 01 June 2007 07:36

Posting Rules
You may not post new threads
You may not post replies
You may not post attachments
You may not edit your posts

BB code is On
Smilies are On
[IMG] code is On
HTML code is Off

Forum Jump


All times are GMT +2. The time now is 12:47.

Top

Powered by vBulletin® Version 3.8.11
Copyright ©2000 - 2024, vBulletin Solutions Inc.
Page generated in 0.09506 seconds with 15 queries